| E.g., the type below is generated for :DNum, the datacon of a Num
| dictionary.
| At least, this is what :print obtains from a tcLookupDatacon on :DNum.
|
| :DNum :: (a -> a -> a)
| -> (a -> a -> a)
| -> (a -> a -> a)
| -> (a -> a)
| -> (a -> a)
| -> (a -> a)
| -> (GHC.Integer.Integer -> a)
| -> (GHC.Num.:TNum) a)
|
| There is one element for every function in Num.
| But where did the dictionaries for the (Eq a, Show a) context go ?
They are certainly there! I compiled the Foo.hs below and asked for the type
of DB:
*Foo> :i DB
data Dict a where
DB :: forall a. (Eq a) => (a -> a) -> (a -> Int) -> Dict a
-- Defined at Foo.hs:10:2-3
*Foo>
I don't know how :print works, but the data constructor certainly has those
arguments, both in its type and in its runtime representation.
If you can refine your question I'll try to help.
Simon
{-# LANGUAGE GADTs #-}
module Foo where
class Eq a => Bar a where
op1 :: a -> a
op2 :: a -> Int
data Dict a where
DB :: Eq a => (a->a) -> (a->Int) -> Dict a
_______________________________________________
Cvs-ghc mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-ghc