[Template-haskell] [Bug?] AST representation of type-synonyms with phantom parameters

Alfonso Acosta alfonso.acosta at gmail.com
Mon Oct 29 09:14:52 EDT 2007


Hi,

There seems to be a bug in the type representation of type synonyms
with phantom parameters

=== Phantom.hs ===
module Phantom where

-- non-phantom type synonym
type List a = [a]

type PhantomSyn a  = Int

data PhantomData a = PhantomData Int
==================

~/ghc/ghc/compiler/stage2$ ./ghc-inplace -fth --interactive /tmp/Phantom.hs
GHCi, version 6.9.20071025: http://www.haskell.org/ghc/  :? for help
Loading package base ... linking ... done.
[1 of 1] Compiling Phantom          ( /tmp/Phantom.hs, interpreted )
Ok, modules loaded: Phantom.
*Phantom> let {syn = undefined :: List a; phanSyn = undefined ::
PhantomSyn a; phanData = undefined :: PhantomData a}
*Phantom> :m +Language.Haskell.TH
*Phantom Language.Haskell.TH> let showType name = do {VarI _ t _ _ <-
reify name ; runIO $ putStrLn (pprint t);  [| 1 |]}
Loading package array-0.1 ... linking ... done.
Loading package packedstring-0.1 ... linking ... done.
Loading package containers-0.1 ... linking ... done.
Loading package pretty-1.0 ... linking ... done.
Loading package template-haskell ... linking ... done.
*Phantom Language.Haskell.TH> $(showType (mkName "syn"))
forall a_0 . Phantom.List a_0
forall a_0 . Phantom.List a_0
forall a_0 . Phantom.List a_0
forall a_0 . Phantom.List a_0
1
*Phantom Language.Haskell.TH> $(showType (mkName "phanSyn"))
Phantom.PhantomSyn GHC.Prim.Any
Phantom.PhantomSyn GHC.Prim.Any
Phantom.PhantomSyn GHC.Prim.Any
Phantom.PhantomSyn GHC.Prim.Any
1
*Phantom Language.Haskell.TH> $(showType (mkName "phanData"))
forall a_0 . Phantom.PhantomData a_0
forall a_0 . Phantom.PhantomData a_0
forall a_0 . Phantom.PhantomData a_0
forall a_0 . Phantom.PhantomData a_0
1


The output makes sense for "forall a_0 . Phantom.List a_0" and "forall
a_0 . Phantom.PhantomData a_0" but why "Phantom.PhantomSyn
GHC.Prim.Any"? (just  for information purposes, ghc 6.6 uses "()"
instead of "Any")

Shouldn't it be  "forall a_0 . Phantom.PhantomSyn a_0"?


Best Regards,

Fons


PS: BTW, $(showType 'phanSyn) works fine in ghci6.6 but gives a Stage
error in HEAD. That's why I used

mkName "phanSyn"

Is that another bug? (I couldn't find a related ticket in GHC's trac)


More information about the template-haskell mailing list