Hello!

I attach a program which I suspect demonstrates a bug in GHC. The important lines are:

  showType :: forall a . Expr a -> String
  showType (Lit _) = show (typeOf (undefined :: a))

  test1 = showType (mk     :: Expr BOOL) -- Prints "Bool" (wrong?)
  test2 = showType (Lit mk :: Expr BOOL) -- Prints "Main.BOOL" (correct)

test1 and test2 give different results, even though showType shouldn't be able to tell them apart. It seems that the Typeable context packed with the Lit constructor is wrong in test2.

I had to use two extra classes and newtype deriving to trigger this behavior. Note that if I change

  deriving instance B BOOL

to

  instance B BOOL

the result is correct.

Tested with both 6.12.3 and 7.0.1.

Should I report this as a bug?

Thanks!

/ Emil

import Data.Typeable

data Expr a where
    Lit :: Typeable a => a -> Expr a

class A a where
    mk :: a

class (Typeable a, A a) => B a where
    mkExpr :: Expr a
    mkExpr = Lit mk

instance B a => A (Expr a) where
    mk = mkExpr

instance A Bool where
    mk = True

newtype BOOL = BOOL Bool
  deriving (Typeable, A)

instance B Bool
deriving instance B BOOL

showType :: forall a . Expr a -> String
showType (Lit _) = show (typeOf (undefined :: a))

test1 = showType (mk     :: Expr BOOL) -- Prints "Bool" (wrong?)
test2 = showType (Lit mk :: Expr BOOL) -- Prints "Main.BOOL" (correct)

_______________________________________________
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Reply via email to