Surprised to type in (1+n) as a type index!
Ahn, Ki Yung
kyagrd at gmail.com
Tue Feb 3 00:44:53 EST 2009
I was writing a document in lhs form and typed in something like this.
> data Exp n where
> Atom :: Exp ()
> List :: [Exp n] -> Exp (1+n)
I wasn't expecting this to actually load up on GHCi,
but when I load this up with the magical -fglasgow-exts option,
it just worked !!!
*Main> :t Atom
Atom :: Exp ()
*Main> :t List [Atom, Atom]
List [Atom, Atom] :: forall (+ :: * -> * -> *).
Exp (+ GHC.Generics.Unit ())
It seems GHC is treating + as just a type variable for binary type
constructor of kind * -> * -> *.
*Main> :t List [Atom, Atom]
List [Atom, Atom] :: forall (+ :: * -> * -> *).
Exp (+ GHC.Generics.Unit ())
*Main> :t List [List [Atom, Atom], List []]
List [List [Atom, Atom], List []] :: forall (+ :: * -> * -> *)
(+1 :: * -> * -> *).
Exp (+1 GHC.Generics.Unit (+
GHC.Generics.Unit ()))
*Main> :t List [List [List [Atom, Atom], List []]]
List [List [List [Atom, Atom], List []]] :: forall (+ :: *
-> *
-> *)
(+1 :: * -> * -> *)
(+2 :: * -> * -> *).
Exp
(+2 GHC.Generics.Unit (+1
GHC.Generics.Unit (+ GHC.Generics.Unit ())))
But, what is this GHC.Generics.Unit thing and where is this documented?
Thanks,
Ahn, Ki Yung
More information about the Glasgow-haskell-users
mailing list