[Haskell-cafe] Simple question about the function composition operator

wren ng thornton wren at freegeek.org
Sat Sep 25 19:21:22 EDT 2010


On 9/24/10 5:35 AM, Axel Benz wrote:
> Can anybody explain why this happens and how I can compose f and g?
>
> Hint: It works fine if f is defined as an unary function.

As already mentioned: (g . f) x y = (\z-> g (f z)) x y = g (f x) y

In order to get it to work you need to say that you want to pass two 
arguments to f. The immediate answer is ((g .) . f) but that doesn't 
really give you a general pattern to use. The general pattern is,

     -- | Binary composition.
     (...) :: (c -> d) -> (a -> b -> c) -> (a -> b -> d)
     (...) = (.) . (.)
     {-# INLINE (...) #-}
     infixl 8 ...

and then (g ... f) x y = g (f x y). Note that the fixity is set up so 
that (...) plays nicely with (.). You may also be interested in,

     -- | Compose on second arg.
     (.^) :: (a -> c -> d) -> (b -> c) -> (a -> b -> d)
     (.^) = flip ... (.) . flip
     {-# INLINE (.^) #-}
     infix 9 .^

     -- | Function composition which calls the right-hand
     -- function eagerly.
     (.!) :: (b -> c) -> (a -> b) -> a -> c
     (.!) = (.) . ($!)
     {-# INLINE (.!) #-}
     infixr 9 .!


-- 
Live well,
~wren


More information about the Haskell-Cafe mailing list