Trying to make a Typeable instance

Hello, I'm trying to make the type (ListGT map k a) an instance of Typeable, where map is kind (* -> *). data ListGT map k a = Empt | BraF ![k] a !(map (ListGT map k a)) | BraE ![k] !(map (ListGT map k a)) I thought I'd cracked it with something like this.. instance (Typeable (map (ListGT map k a)), Typeable k, Typeable a) => Typeable (ListGT map k a) where typeOf lgt = mkTyConApp (mkTyCon "Data.Trie.General.ListGT") [mTypeRep, kTypeRep, aTypeRep] where BraF [k] a m = lgt -- This is just to get types for k a m !! kTypeRep = typeOf k aTypeRep = typeOf a mTypeRep = typeOf m However, showing the resulting TypRep gives a stack overflow. I wasn't too surprised about this, so I tried replacing the last line with.. mTypeRep = mkTyConApp (typeRepTyCon (typeOf m)) [] ..thinking that this would make it terminate. But it doesn't. Could someone explain how to do this? Thanks -- Adrian Hey

Adrian Hey wrote:
Hello,
I'm trying to make the type (ListGT map k a) an instance of Typeable, where map is kind (* -> *).
data ListGT map k a = Empt | BraF ![k] a !(map (ListGT map k a)) | BraE ![k] !(map (ListGT map k a))
I thought I'd cracked it with something like this..
instance (Typeable (map (ListGT map k a)), Typeable k, Typeable a) => Typeable (ListGT map k a) where typeOf lgt = mkTyConApp (mkTyCon "Data.Trie.General.ListGT") [mTypeRep, kTypeRep, aTypeRep] where BraF [k] a m = lgt -- This is just to get types for k a m !! kTypeRep = typeOf k aTypeRep = typeOf a mTypeRep = typeOf m
However, showing the resulting TypRep gives a stack overflow. I wasn't too surprised about this, so I tried replacing the last line with.. mTypeRep = mkTyConApp (typeRepTyCon (typeOf m)) [] ..thinking that this would make it terminate. But it doesn't.
Could someone explain how to do this?
(Answering my own question) this seems to do the trick.. instance (Typeable1 map, Typeable k, Typeable a) => Typeable (ListGT map k a) where typeOf lgt = mkTyConApp (mkTyCon "Data.Trie.General.ListGT") [mTypeRep, kTypeRep, aTypeRep] where BraF [k] a m = lgt -- This is just to get types for k a m !! kTypeRep = typeOf k aTypeRep = typeOf a mTypeRep = typeOf1 m Regards -- Adrian Hey

Hi Adrian
You can use Data.Derive to do this for you:
http://www-users.cs.york.ac.uk/~ndm/derive/
Or DrIFT: http://repetae.net/~john/computer/haskell/DrIFT/
Thanks
Neil
On 7/7/07, Adrian Hey
Adrian Hey wrote:
Hello,
I'm trying to make the type (ListGT map k a) an instance of Typeable, where map is kind (* -> *).
data ListGT map k a = Empt | BraF ![k] a !(map (ListGT map k a)) | BraE ![k] !(map (ListGT map k a))
I thought I'd cracked it with something like this..
instance (Typeable (map (ListGT map k a)), Typeable k, Typeable a) => Typeable (ListGT map k a) where typeOf lgt = mkTyConApp (mkTyCon "Data.Trie.General.ListGT") [mTypeRep, kTypeRep, aTypeRep] where BraF [k] a m = lgt -- This is just to get types for k a m !! kTypeRep = typeOf k aTypeRep = typeOf a mTypeRep = typeOf m
However, showing the resulting TypRep gives a stack overflow. I wasn't too surprised about this, so I tried replacing the last line with.. mTypeRep = mkTyConApp (typeRepTyCon (typeOf m)) [] ..thinking that this would make it terminate. But it doesn't.
Could someone explain how to do this?
(Answering my own question) this seems to do the trick..
instance (Typeable1 map, Typeable k, Typeable a) => Typeable (ListGT map k a) where typeOf lgt = mkTyConApp (mkTyCon "Data.Trie.General.ListGT") [mTypeRep, kTypeRep, aTypeRep] where BraF [k] a m = lgt -- This is just to get types for k a m !! kTypeRep = typeOf k aTypeRep = typeOf a mTypeRep = typeOf1 m
Regards -- Adrian Hey
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Can you just write:
data ListGT map k a
= Empt
| BraF ![k] a !(map (ListGT map k a))
| BraE ![k] !(map (ListGT map k a))
deriving( Typeable )
?
On 7/7/07, Adrian Hey
Hello,
I'm trying to make the type (ListGT map k a) an instance of Typeable, where map is kind (* -> *).
data ListGT map k a = Empt | BraF ![k] a !(map (ListGT map k a)) | BraE ![k] !(map (ListGT map k a))
I thought I'd cracked it with something like this..
instance (Typeable (map (ListGT map k a)), Typeable k, Typeable a) => Typeable (ListGT map k a) where typeOf lgt = mkTyConApp (mkTyCon "Data.Trie.General.ListGT") [mTypeRep, kTypeRep, aTypeRep] where BraF [k] a m = lgt -- This is just to get types for k a m !! kTypeRep = typeOf k aTypeRep = typeOf a mTypeRep = typeOf m
However, showing the resulting TypRep gives a stack overflow. I wasn't too surprised about this, so I tried replacing the last line with.. mTypeRep = mkTyConApp (typeRepTyCon (typeOf m)) [] ..thinking that this would make it terminate. But it doesn't.
Could someone explain how to do this?
Thanks -- Adrian Hey
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Hi
data ListGT map k a = Empt | BraF ![k] a !(map (ListGT map k a)) | BraE ![k] !(map (ListGT map k a)) deriving( Typeable )
Not in Haskell, only in GHC. Thanks Neil
?
On 7/7/07, Adrian Hey
wrote: Hello,
I'm trying to make the type (ListGT map k a) an instance of Typeable, where map is kind (* -> *).
data ListGT map k a = Empt | BraF ![k] a !(map (ListGT map k a)) | BraE ![k] !(map (ListGT map k a))
I thought I'd cracked it with something like this..
instance (Typeable (map (ListGT map k a)), Typeable k, Typeable a) => Typeable (ListGT map k a) where typeOf lgt = mkTyConApp (mkTyCon " Data.Trie.General.ListGT") [mTypeRep, kTypeRep, aTypeRep] where BraF [k] a m = lgt -- This is just to get types for k a m !! kTypeRep = typeOf k aTypeRep = typeOf a mTypeRep = typeOf m
However, showing the resulting TypRep gives a stack overflow. I wasn't too surprised about this, so I tried replacing the last line with.. mTypeRep = mkTyConApp (typeRepTyCon (typeOf m)) [] ..thinking that this would make it terminate. But it doesn't.
Could someone explain how to do this?
Thanks -- Adrian Hey
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Neil Mitchell wrote:
data ListGT map k a = Empt | BraF ![k] a !(map (ListGT map k a)) | BraE ![k] !(map (ListGT map k a)) deriving( Typeable )
Not in Haskell, only in GHC.
Thanks for the suggestions from Hugh and Neil. I tried this anyway and it doesn't work even with ghc I'm afraid..
Can't make a derived instance of `Typeable (ListGT map k a)' (`ListGT' has arguments of kind other than `*') When deriving instances for `ListGT'
So it seems ghc doesn't like kinds (* -> *) either :-( Actually, AFAICT the problem seems to be with Data.Typeable itself rather than ghc. There is no proper TypeRep for (ListGT map k a) because map is not a type. Or maybe I'm missing something. Is it possible to make correct instances of Typeable for types like this? What would Data.Derive make of this? Thanks for any thoughts or insight -- Adrian Hey

Hi Adrian,
2007/7/8, Adrian Hey
So it seems ghc doesn't like kinds (* -> *) either :-(
Actually, AFAICT the problem seems to be with Data.Typeable itself rather than ghc. There is no proper TypeRep for (ListGT map k a) because map is not a type.
Have you tried using (Typeable1 map) as the constraint? - Benja

Benja Fallenstein wrote:
Hi Adrian,
2007/7/8, Adrian Hey
: So it seems ghc doesn't like kinds (* -> *) either :-(
Actually, AFAICT the problem seems to be with Data.Typeable itself rather than ghc. There is no proper TypeRep for (ListGT map k a) because map is not a type.
Have you tried using (Typeable1 map) as the constraint?
Yes, see my earlier post. This seems to "work" in that the code compiles and showing the resulting TypeRep at least terminates in the tests I did so far. But I don't see how it can be regarded correct as AFAICT types like this just aren't properly representable as a TypeRep (as provided by Data.Typeable). But I might be wrong. As is often the case, the documentation for Data.Typeable is somewhat terse and inadequate IMO, so it's not at all clear to me how it should be used or what other users can reasonably expect from "sane" instances. Typeable1 etc.. seem problematic in that although the typeOf methods apparently return TypeReps, I don't see how they can possibly be correct. Surely they must be returning a representation of a type constructor that's masquerading as a TypeRep? In fact that's exactly what the macros in Typeable.h seem to do so I guess this is generally accepted as correct, but it seems wrong to me :-( AFAICT it's unsafe to assume that a TypeRep represents an actual proper type (I.E. the type that a monomorphic expression may have). Maybe that's intentional, I dunno. It'd be nice if the Data.Typeable Haddock made it clear exactly what a "TypeRep" is supposed to be a representation of :-) Regards -- Adrian Hey
participants (4)
-
Adrian Hey
-
Benja Fallenstein
-
Hugh Perkins
-
Neil Mitchell