[Haskell-cafe] List of instantiated types

Jared Updike jupdike at gmail.com
Thu Mar 30 10:46:49 EST 2006


My understanding is that type classes in Haskell are meant to be
"open", so that any code that uses your type class will work with any
new instances of that type class. This inherent open endedness causes
a problem if you are trying to enumerate all instances because at any
time someone can create a new instance of your class in their code.

There is a ticket for Haskell' talking about Closed Classes but I'm
not sure it would be adopted anytime soon (and I'm pretty sure it's
not implemented in GHC):
  http://hackage.haskell.org/trac/haskell-prime/wiki/ClosedClasses

What you're trying to do *may* be possible but it would require some
way of having the runtime query the compiler/linker for information
about all modules being linked against.
This kind of hacking may require hs-plugins, Template Haskell, or the
GHC API (i.e. some kind of metaprogramming).

What I mean is, I'm not sure how to make it so you can gather all
information about your type class in one central place; I think for
type classes the information flows in the other direction. There might
still be a totally different way to accomplish this but you'll have to
wait for a guru to answer that...

Hope that helps,
  Jared.

On 3/30/06, Mirko Rahn <rahn at ira.uka.de> wrote:
>
> Hello,
>
> please suppose the following setting: (see [1] too)
>
> {-# OPTIONS_GHC -fglasgow-exts #-}
> module C where
>
> class C a where name :: a -> String ; pre :: a -> a
>
> data Cs = forall a . (C a) => Cs a
>
> instance C Cs where name (Cs a) = name a ; pre (Cs a) = Cs (pre a)
>
> mkCs :: C a => a -> Cs
> mkCs = Cs
>
> instance C Int where name = show ; pre = \ _ -> 0
> instance C Char where name = return ; pre = \ _ -> 'A'
>
> all_Cs = [ mkCs (undefined :: Int), mkCs (undefined :: Char) ]
>
> Note that despite I served undefined values only I can type
>
> *C> map (name . pre) all_Cs
> ["0","A"]
>
> to extract some information. But, when several instances spreads over
> some modules, writing down 'all_Cs' is an error-prone task, in
> particular when using some third party modules.
>
> So my question is: Is it possible to construct 'all_Cs' automatically?
>
> I think such a list cannot be constructed at compile-time, but at link-
> and run-time a complete list of instantiated types should be available.
> But is this list accessible somehow? Is there a possibility to write
>
> foreach type t that is an instance of C:
>     return (mkCs (undefined :: t))
>
> What is the general problem?
>
> Thanks, MR
>
> [1] http://www.haskell.org/pipermail/haskell-cafe/2006-March/014947.html
>
> --
> -- Mirko Rahn -- Tel +49-721 608 7504 --
> --- http://liinwww.ira.uka.de/~rahn/ ---
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>


--
http://www.updike.org/~jared/
reverse ")-:"


More information about the Haskell-Cafe mailing list