Solved, thanks for your help Simon.
I was assuming that dataConRepType would return a core type, i.e. with
the predicates translated to actual dictionaries. With that assumption
out of the way, everything fits in its place.
pepe
On 28/08/2008, at 15:50, Simon Peyton-Jones wrote:
> class Eq a => Eq2 a where eq :: a -> a -> Bool
Based on the runtime representation above, I expect the type of
Main.:DEq2 to be
Main.:DEq2 :: GHC.Base.:TEq a -> (a -> a -> Bool) -> Main.:TEq2 a
but GHC tells me, via (fmap dataConRepType . tcLookupDatacon), the
following
Main.:DEq2 :: (a -> a -> Bool) -> Main.:TEq2 a
Why does the type of :DEq2 differ from what :print sees at runtime ?
Are you sure it’s different? Here’s what I get (below). Note the
type of :DEq2.
Can you tell me how to reproduce what you are seeing?
Simon
module Foo where
class Eq a => Eq2 a where
op :: a -> a -> Bool
ghc -c -ddump-types Foo.hs -dppr-debug
TYPE SIGNATURES
main:Foo.$p1Eq2{v r5P} [gid] :: forall a{tv a5D} [tv].
(main:Foo.Eq2{tc r5z} a{tv a5D}
[tv]) =>
<pred>base:GHC.Base.Eq{tc 23}
a{tv a5D} [tv]
main:Foo.:DEq2{v r5R} [gid] :: forall a{tv a5D} [tv].
(base:GHC.Base.Eq{tc 23} a{tv
a5D} [tv]) =>
(a{tv a5D} [tv] -> a{tv a5D} [tv]
-> base:GHC.Base.Bool{(w) tc 3c})
-> (main:Foo.:TEq2{tc r5Q}) a{tv
a5D} [tv]
main:Foo.op{v r5B} [gid] :: forall a{tv a5D} [tv].
(main:Foo.Eq2{tc r5z} a{tv a5D}
[tv]) =>
a{tv a5D} [tv] -> a{tv a5D} [tv] ->
base:GHC.Base.Bool{(w) tc 3c}
TYPE CONSTRUCTORS
data (:TEq2{tc}) a
RecFlag NonRecursive
Generics: no
= :DEq2{d} :: forall a.
base:GHC.Base.Eq{tc 23} a =>
(a -> a -> base:GHC.Base.Bool{(w) tc 3c}) -
> :TEq2{tc} a
Stricts: _
FamilyInstance: none
Tycons with generics:
Dependent modules: []
Dependent packages: [base]
bash-3.2$
_______________________________________________
Cvs-ghc mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-ghc