[Haskell-cafe] List of instantiated types
Mirko Rahn
rahn at ira.uka.de
Thu Mar 30 07:54:43 EST 2006
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/ ---
More information about the Haskell-Cafe
mailing list