[Haskell-cafe] Trying to make a Typeable instance

Neil Mitchell ndmitchell at gmail.com
Sat Jul 7 05:31:47 EDT 2007


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 <ahey at iee.org> wrote:
> 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 at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>


More information about the Haskell-Cafe mailing list