Ouch ... that looks ... not great. I don't know if that was intentional, but it's weird enough to deserve a bug report.
Is there supposed to be this surprising difference between ex1 and ex2?
{-# LANGUAGE UnliftedDatatypes #-}
{-# OPTIONS_GHC -Wall #-}
module Main where
import GHC.Exts (UnliftedType)
type T :: UnliftedType
data T = T
ex1 :: ()
ex1 = let _ = undefined :: T in ()
ex2 :: ()
ex2 = let _a = undefined :: T in ()
ghci> ex1
()
ghci> ex2
*** Exception: Prelude.undefined
CallStack (from HasCallStack):
undefined, called at test17.hs:53:16 in fake-package-0-inplace:Main
_______________________________________________
Haskell-Cafe mailing list
To (un)subscribe, modify options or view archives go to:
http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
Only members subscribed via the mailman list are allowed to post.