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.




_______________________________________________
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Reply via email to