Surprising behavior with wildcard pattern and unlifted type

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

Ouch ... that looks ... not great. I don't know if that was intentional, but it's weird enough to deserve a bug report. On Mon, Jan 2, 2023, 2:01 PM Tom Ellis < tom-lists-haskell-cafe-2017@jaguarpaw.co.uk> wrote:
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.

On Tue, Jan 03, 2023 at 03:09:58AM -0500, David Feuer wrote:
Ouch ... that looks ... not great. I don't know if that was intentional, but it's weird enough to deserve a bug report.
Bug report filed: https://gitlab.haskell.org/ghc/ghc/-/issues/22719
On Mon, Jan 2, 2023, 2:01 PM Tom Ellis < tom-lists-haskell-cafe-2017@jaguarpaw.co.uk> wrote:
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
participants (2)
-
David Feuer
-
Tom Ellis