[Haskell-cafe] Surprising behavior with wildcard pattern and unlifted type
Tom Ellis
tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk
Mon Jan 2 19:01:24 UTC 2023
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
More information about the Haskell-Cafe
mailing list