[Haskell-cafe] Function composition
Jorge Marques Pelizzoni
jpeliz at icmc.usp.br
Wed Oct 3 15:05:01 EDT 2007
Here is a generalized version, using type classes and some extensions.
Tiago, in order to compile this you'll have to use:
-fglasgow-exts -fallow-undecidable-instances -fallow-overlapping-instances
Cheers,
Jorge.
-------------
module Main where
class Pipeline t1 t2 t3 | t1 t2 -> t3 where
pipeline::t1 -> t2 -> t3
instance Pipeline t1 t2 t3 => Pipeline (a -> t1) t2 (a -> t3) where
pipeline f g a = pipeline (f a) g
-- same as: pipeline f g = \a -> pipeline (f a) g
instance Pipeline (a -> b) (b -> c) (a -> c) where
pipeline = flip (.)
f a b c = even (a+b+c)
h = pipeline f not
main = do
putStrLn . show $ h 1 2 3
----------------
More information about the Haskell-Cafe
mailing list