
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.

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@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
-- Hal Daume III | hdaume@isi.edu "Arrest this man, he talks in maths." | www.isi.edu/~hdaume

Ok... After playing with these types, I could not get it to work with the satFold below. However it did inspire me to try something else, and this seems to work quite well. First redefine the RFold function to use RFoldFn class as its operator. Then create instances of RFoldFn to do what you like. The clever bit is the use of an abstract data-type to select which instance to use. class RFold t i r where rFold :: t -> i -> r -> i instance RFold t i RNil where rFold _ i RNil = i instance (RFoldFn t a i,RFold t i r) => RFold t i (a `RCons` r) where rFold t i (x `RCons` xs) = rFoldFn t x (rFold t i xs) class RFoldFn t a i where rFoldFn :: t -> a -> i -> i Here's some examples: data ShowFn = ShowFn instance Show a => RFoldFn ShowFn a String where rFoldFn ShowFn x y = shows x y putStrLn $ show $ rFold ShowFn "" r data SumFn = SumFn instance Num i => RFoldFn SumFn a i where rFoldFn SumFn _ s = 1 + s putStrLn $ show $ rFold SumFn 0 r I think this is pretty neat, and the mechanism fits in well with how the rest of the module works... Regards, Keean Schupke. Hal Daume III wrote:
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.
participants (2)
-
Hal Daume III
-
MR K P SCHUPKE