Polymorphic lists...
Hal Daume III
hdaume at ISI.EDU
Tue Mar 9 06:38:13 EST 2004
Though I haven't tried it, the explicit 'Sat' dictionary representation
would probably work here, something like:
> data ShowD a = ShowD { showD :: a -> String }
> -- our explicit dictionary for show, would need one of
> -- these for each class we care about
>
> -- the satisfaction class:
> class Sat t where dict :: t
>
> -- an instance for show:
> instance Show a => Sat (ShowD a) where dict = ShowD { showD = show }
> instance Sat (ShowD a) => Show a where show = showD dict
manually generating datatypes and instances is tedious, but could easily
be automated. you should be able to use this to write:
> satFold :: forall c b . Sat c b =>
> (forall a . Sat (c a) => a -> i -> i) ->
> b -> r -> b
or something similar. probably worth a shot.
On Tue, 9 Mar 2004, MR K P SCHUPKE wrote:
>
> I have written a first attempt at a fold function for the heterogenious list:
>
> class RFold i r where
> rFold :: (forall a . a -> i -> i) -> i -> r -> i
> instance RFold i RNil where
> rFold f i RNil = i
> instance RFold i r => RFold i (a `RCons` r) where
> rFold f i (x `RCons` xs) = f x (rFold f i xs)
>
> This works providing the folded 'op' has the type: forall a . a -> i -> i
> which means it does not work for functions like show :: forall a . Show a => a -> i -> i
> as the types are different. I have not figured out a way to make it accept a constraint
> like Show for example. Here is an example:
>
> length = rFold (\_ -> (+1)) 0 relation
>
> The use of such a function seems limited, if constraints like Show cannot be used, as
> most useful applications of fold would require some kind of class membership for example:
>
> string = rFold shows "" relation
>
> This fails to compile because shows has type:
>
> shows :: forall a . Show a => a -> i -> i
>
> but fold expects
>
> op :: forall a . a -> i -> i
>
> Regards,
> Keean Schupke.
> _______________________________________________
> Glasgow-haskell-users mailing list
> Glasgow-haskell-users at haskell.org
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
>
--
Hal Daume III | hdaume at isi.edu
"Arrest this man, he talks in maths." | www.isi.edu/~hdaume
More information about the Glasgow-haskell-users
mailing list