
Hi, I'm playing a little bit with pointfree and function composition and I would like to ask you if the following is theoretical correct and how can I express it in haskell. Imagine that I have the following functions f :: a -> b -> c -> d g :: d -> e I want to compose these two functions such that: (g . f) :: a -> b -> c -> e in which a, b and c are arguments of the composition. Is this theoretically correct? I tried this in haskell and ghc gives me an error saying that the function g should be of type b -> c -> d. With this I assume that when I specify f :: a -> b -> c -> d I'm really specifying f :: a -> (b -> c -> d) and such the composition doesn't work, but is it possible to overcome this? Kind regards, Tiago

On 10/3/07, Tiago Miguel Laureano Alves
Imagine that I have the following functions f :: a -> b -> c -> d g :: d -> e
I want to compose these two functions such that: (g . f) :: a -> b -> c -> e
Here's a pointfree derivation of the composition function you are talking about: compose g f a b c = g (f a b c) = g ((f a b) c) = (g . (f a b)) c compose g f a b = g . f a b = (.) g (f a b) = ((.) g) ((f a) b) = ((.) g . f a) b compose g f a = ((.) g) . f a = (.) ((.) g) (f a) = ((.) ((.) g) . f) a compose g f = (.) ((.) g) . f = (.) (g .) . f = ((g .) .) . f In ghci: Prelude> :set -fglasgow-exts Prelude> :t ((?g .) .) . ?f ((?g .) .) . ?f :: forall b c a a1 a2. (?g::b -> c, ?f::a2 -> a1 -> a -> b) => a2 -> a1 -> a -> c -- ryan

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 ----------------

On 10/4/07, Dominic Steinitz
Look at the type of (.).(.).(.)
Indeed, this generalizes to functions of any arity on the "RHS": Prelude> :t (.) (.) :: (b -> c) -> (a -> b) -> a -> c Prelude> :t (.).(.) (.).(.) :: (b -> c) -> (a -> a1 -> b) -> a -> a1 -> c Prelude> :t (.).(.).(.) (.).(.).(.) :: (b -> c) -> (a -> a1 -> a2 -> b) -> a -> a1 -> a2 -> c Prelude> :t (.).(.).(.).(.) (.).(.).(.).(.) :: (b -> c) -> (a -> a1 -> a2 -> a3 -> b) -> a -> a1 -> a2 -> a3 -> c Of course, if you want higher-arity functions anywhere *other* than the head of your composition chain, you'll have to resort to tupling and uncurrying. Stuart

Adapting my previous class sample with these ideas, we have: class Multicompose t1 t2 t3 | t1 t2 -> t3 where infixr 9 +. (+.)::t1 -> t2 -> t3 instance Multicompose t1 t2 t3 => Multicompose t1 (a -> t2) (a -> t3) where (+.) = (.).(+.) instance Multicompose (b -> c) (a -> b) (a -> c) where (+.) = (.) The only advantage is having the compiler calculate the number of compositions. Cheers, Jorge. Stuart Cook escreveu:
On 10/4/07, Dominic Steinitz
wrote: Look at the type of (.).(.).(.)
Indeed, this generalizes to functions of any arity on the "RHS":
Prelude> :t (.) (.) :: (b -> c) -> (a -> b) -> a -> c
Prelude> :t (.).(.) (.).(.) :: (b -> c) -> (a -> a1 -> b) -> a -> a1 -> c
Prelude> :t (.).(.).(.) (.).(.).(.) :: (b -> c) -> (a -> a1 -> a2 -> b) -> a -> a1 -> a2 -> c
Prelude> :t (.).(.).(.).(.) (.).(.).(.).(.) :: (b -> c) -> (a -> a1 -> a2 -> a3 -> b) -> a -> a1 -> a2 -> a3 -> c
Of course, if you want higher-arity functions anywhere *other* than the head of your composition chain, you'll have to resort to tupling and uncurrying.
Stuart _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Jorge M. Pelizzoni ICMC - Universidade de São Paulo
participants (5)
-
Dominic Steinitz
-
Jorge Marques Pelizzoni
-
Ryan Ingram
-
Stuart Cook
-
Tiago Miguel Laureano Alves