Multiple folds in one pass using generic tuple function - haskell

How can I write a function which takes a tuple of functions of type ai -> b -> ai and returns a function which takes a tuple of elements of type ai, one element of type b, and combines each of the elements into a new tuple of ai:
That is the signature should be like
f :: (a1 -> b -> a1, a2 -> b -> a2, ... , an -> b -> an) ->
(a1, a2, ... , an) ->
b ->
(a1, a2, ... , an)
Such that:
f (min, max, (+), (*)) (1,2,3,4) 5 = (1, 5, 8, 20)
The point of this is so I can write:
foldlMult' t = foldl' (f t)
And then do something like:
foldlMult' (min, max, (+), (*)) (head x, head x, 0, 0) x
to do multiple folds in one pass. GHC extensions are okay.

If I understand your examples right, the types are ai -> b -> ai, not ai -> b -> a as you first wrote. Let's rewrite the types to a -> ri -> ri, just because it helps me think.
First thing to observe is this correspondence:
(a -> r1 -> r1, ..., a -> rn -> rn) ~ a -> (r1 -> r1, ..., rn -> rn)
This allows you to write these two functions, which are inverses:
pullArg :: (a -> r1 -> r1, a -> r2 -> r2) -> a -> (r1 -> r1, r2 -> r2)
pullArg (f, g) = \a -> (f a, g a)
pushArg :: (a -> (r1 -> r1, r2 -> r2)) -> (a -> r1 -> r1, a -> r2 -> r2)
pushArg f = (\a -> fst (f a), \a -> snd (f a))
Second observation: types of the form ri -> ri are sometimes called endomorphisms, and each of these types has a monoid with composition as the associative operation and the identity function as the identity. The Data.Monoid package has this wrapper for that:
newtype Endo a = Endo { appEndo :: a -> a }
instance Monoid (Endo a) where
mempty = id
mappend = (.)
This allows you to rewrite the earlier pullArg to this:
pullArg :: (a -> r1 -> r1, a -> r2 -> r2) -> a -> (Endo r1, Endo r2)
pullArg (f, g) = \a -> (Endo $ f a, Endo $ g a)
Third observation: the product of two monoids is also a monoid, as per this instance also from Data.Monoid:
instance (Monoid a, Monoid b) => Monoid (a, b) where
mempty = (mempty, mempty)
(a, b) `mappend` (c, d) = (a `mappend` c, b `mappend d)
Likewise for tuples of any number of arguments.
Fourth observation: What are folds made of? Answer: folds are made of monoids!
import Data.Monoid
fold :: Monoid m => (a -> m) -> [a] -> m
fold f = mconcat . map f
This fold is just a specialization of foldMap from Data.Foldable, so in reality we don't need to define it, we can just import its more general version:
foldMap :: (Foldable t, Monoid m) => (a -> m) -> t a -> m
If you fold with Endo, that's the same as folding from the right. To fold from the left, you want to fold with the Dual (Endo r) monoid:
myfoldl :: (a -> Dual (Endo r)) -> r -> -> [a] -> r
myfoldl f z xs = appEndo (getDual (fold f xs)) z
-- From `Data.Monoid`. This just flips the order of `mappend`.
newtype Dual m = Dual { getDual :: m }
instance Monoid m => Monoid (Dual m) where
mempty = Dual mempty
Dual a `mappend` Dual b = Dual $ b `mappend` a
Remember our pullArg function? Let's revise it a bit more, since you're folding from the left:
pullArg :: (a -> r1 -> r1, a -> r2 -> r2) -> a -> Dual (Endo r1, Endo r2)
pullArg (f, g) = \a -> Dual (Endo $ f a, Endo $ g a)
And this, I claim, is the 2-tuple version of your f, or at least isomorphic to it. You can refactor your fold functions into the form a -> Endo ri, and then do:
let (f'1, ..., f'n) = foldMap (pullArgn f1 ... fn) xs
in (f'1 z1, ..., f'n zn)
Also worth looking at: Composable Streaming Folds, which is a further elaboration of these ideas.

For a direct approach, you can just define the equivalents of Control.Arrow's (***) and (&&&) explicitly, for each N (e.g. N == 4):
prod4 (f1,f2,f3,f4) (x1,x2,x3,x4) = (f1 x1,f2 x2,f3 x3,f4 x4) -- cf (***)
call4 (f1,f2,f3,f4) x = (f1 x, f2 x, f3 x, f4 x ) -- cf (&&&)
uncurry4 f (x1,x2,x3,x4) = f x1 x2 x3 x4
Then,
foldr4 :: (b -> a1 -> a1, b -> a2 -> a2,
b -> a3 -> a3, b -> a4 -> a4)
-> (a1, a2, a3, a4) -> [b]
-> (a1, a2, a3, a4) -- (f .: g) x y = f (g x y)
foldr4 t z xs = foldr (prod4 . call4 t) z xs -- foldr . (prod4 .: call4)
-- f x1 (f x2 (... (f xn z) ...)) -- foldr . (($) .: ($))
So the tuple's functions in foldr4's are flipped versions of what you wanted. Testing:
Prelude> g xs = foldr4 (min, max, (+), (*)) (head xs, head xs, 0, 1) xs
Prelude> g [1..5]
(1,5,15,120)
foldl4' is a tweak away. Since
foldr f z xs == foldl (\k x r-> k (f x r)) id xs z
foldl f z xs == foldr (\x k a-> k (f a x)) id xs z
we have
foldl4, foldl4' :: (t -> a -> t, t1 -> a -> t1,
t2 -> a -> t2, t3 -> a -> t3)
-> (t, t1, t2, t3) -> [a]
-> (t, t1, t2, t3)
foldl4 t z xs = foldr (\x k a-> k (call4 (prod4 t a) x))
(prod4 (id,id,id,id)) xs z
foldl4' t z xs = foldr (\x k a-> k (call4 (prod4' t a) x))
(prod4 (id,id,id,id)) xs z
prod4' (f1,f2,f3,f4) (x1,x2,x3,x4) = (f1 $! x1,f2 $! x2,f3 $! x3,f4 $! x4)
We've even got the types as you wanted, for the tuple's functions.
A stricter version of prod4 had to be used to force the arguments early in foldl4'.

Related

Understanding types in Haskell (lambda epxressions and higher order functions)

I'm currently doing a course in Haskell, and I have a lot of difficulty understanding the types of functions, particularly when there's function application or lambda expressions. Say for instance the following:
f = (\x -> \y -> \z -> [x (y z), y z])
or
g = \x -> \y -> \z -> x.y.z
I can sort of make some assumptions about the fact that x and y are functions, but I don't have a concrete method for figuring out the types of these functions.
Similarly for the following:
h = foldr (&&)
I try to guess and then check via :t in the interpreter, but I'm usually off by quite a bit.
Is there any particular method I can use to find the types of such functions?
You start by assigning type variables to the inputs and the result
f = (\x -> \y -> \z -> [x (y z), y z])
and conclude
f :: a -> b -> c -> d -- (A0)
-- or even (f is not needed)
\x -> \y -> \z -> [x (y z), y z] :: a -> b -> c -> d
that is
x :: a -- (1)
y :: b -- (2)
z :: c -- (3)
[x (y z), y z] :: d -- (4)
You can continue with (4) and conclude
that the type d is a list of d1s, i.e. d ~ [d1] (5)
f :: a -> b -> c -> [d1] -- (A1)
and that the values of the list are of type d1, i.e.
x (y z) :: d1 -- (6)
y z :: d1 -- (7)
From (6) you learn that
x :: e -> d1 -- (8)
y z :: e -- (9)
(1) and (8) unify, i.e. a ~ (e -> d1) and
f :: (e -> d1) -> b -> c -> [d1] -- (A2)
You play this game until you get bored and use GHCi to arrive at
f :: (d1 -> d1) -> (f -> d1) -> f -> [d1] -- (A3)
-- and renaming
f :: (a -> a) -> (b -> a) -> b -> [a] -- (A4)
If you want to learn more and read a paper you can start with Principal type-schemes for functional programs.
Prelude> :t h
h :: Foldable t => Bool -> t Bool -> Bool
Prelude> :t foldr
foldr :: Foldable t => (a -> b -> b) -> b -> t a -> b
Prelude> :t (&&)
(&&) :: Bool -> Bool -> Bool
Prelude>
By "plugging in" (&&) you have removed (a -> b -> b)
so you need to provide the rest to the function
b -> t a -> b
That is restricted by (&&) to be a bool as second param to it, and the second parameter is the t a which is also restricted to being a bool. since a and b needs to be the same type as in the (a->b->b) function.

Point free composition of multivariate functions

Say, we want to introduce the notion of sum of functions of different arguments (let's call it <+>), which behaves like the that: (f1 <+> f2)(x1, x2) == f1(x1) + f2(x2).
While this can be easily written out manually, it makes sense to use point-free style with the help of the notion of cartesian product of functions. The latter is defined below and seems alright and quite general to me:
x :: (x1 -> y1) -> (x2 -> y2) -> (x1 -> x2 -> (y1, y2))
x f1 f2 = \x1 x2 -> (f1(x1), f2(x2))
Then we can write:
(<+>):: Num a => (a -> a) -> (a -> a) -> (a -> a -> a)
(<+>) = (uncurry (+)) . x
And the code above seems fine to me too, but GHC thinks otherwise:
* Couldn't match type: (x20 -> y20) -> a -> x20 -> (a, y20)
with: ((a -> a) -> a -> a -> a, (a -> a) -> a -> a -> a)
Expected: (a -> a)
-> ((a -> a) -> a -> a -> a, (a -> a) -> a -> a -> a)
Actual: (a -> a) -> (x20 -> y20) -> a -> x20 -> (a, y20)
* Probable cause: `x' is applied to too few arguments
In the second argument of `(.)', namely `x'
In the expression: (uncurry (+)) . x
In an equation for `<+>': (<+>) = (uncurry (+)) . x
* Relevant bindings include
(<+>) :: (a -> a) -> (a -> a) -> a -> a -> a
It feels like the compiler cannot infer the second function's type, but why? And what am I supposed to do, is this even possible to do?
If you supply two arguments, you will see what has gone wrong.
(<+>) = uncurry (+) . x
(<+>) a = (uncurry (+) . x) a
= uncurry (+) (x a)
(<+>) a b = uncurry (+) (x a) b
Whoops! That b gets passed to uncurry as a third argument, rather than x as a second argument as you probably intended. The third and fourth arguments are also supposed to go to x rather than uncurry, as in:
(<+>) a b c d = uncurry (+) (x a b c d)
Here's the correct way to point-free-ify a four-argument composition.
\a b c d -> f (g a b c d)
= \a b c d -> (f . g a b c) d
= \a b c -> f . g a b c
= \a b c -> ((.) f . g a b) c
= \a b -> (.) f . g a b
= \a b -> ((.) ((.) f) . g a) b
= \a -> (.) ((.) f) . g a
= \a -> ((.) ((.) ((.) f)) . g) a
= (.) ((.) ((.) f)) . g
Most people then write this with section syntax as (((f .) .) .) . g. Applying this new fact to your case:
\a b c d -> uncurry (+) (x a b c d)
= (((uncurry (+) .) .) .) . x
The . operator is only for composing functions with a single argument, but the function x has four arguments, so you have to use . four times:
(<+>) = (((uncurry (+) .) .) .) . x
Do keep in mind that this is not considered good style in actual code.
Define
compose2 :: (b -> c -> t) -> (a -> b) -> (d -> c) -> a -> d -> t
compose2 p f g x y = p (f x) (g y)
Now, compose2 (+) is your <+>:
> :t compose2 (+)
compose2 (+) :: Num t => (a -> t) -> (d -> t) -> a -> d -> t
As you can see its type is a bit more general than you thought.
compose2 already exists.

Grouping parameters

Say I have functions which accept the same parameters and I want to test if their outputs are equivalent for the same input.
f :: a -> b -> c
g :: a -> b -> c
f a b == g a b
How can I package the parameters a and b in x so I can write the following instead.
f x == g x
What are the best ways to accomplish this without needing to wrap the functions themselves?
The only way to do exactly what you’re asking is to use uncurry:
let
x = (a, b)
in uncurry f x == uncurry g x
(Or uncurryN for N arguments.)
However, instead of packaging the arguments in a tuple, you could use the (->) x instance of Applicative (i.e., functions taking x as input) to implicitly “spread” the arguments to the parameters of both functions, so at least you only have to mention them once. This instance is commonly used in point-free code.
For example, using liftA2 specialised to this instance:
-- General type:
liftA2 :: Applicative f => (a -> b -> c) -> f a -> f b -> f c
-- Specialised to ‘(->) x’ (using TypeApplications syntax):
liftA2 #((->) _) :: (a -> b -> c) -> (x -> a) -> (x -> b) -> (x -> c)
You get this pattern:
liftA2 h f g x
-- =
(h <$> f <*> g) x
-- =
h (f x) (g x)
To lift more arguments, you add another liftA2 or … <$> … <*> …:
liftA2 (liftA2 h) f g x y
-- =
(liftA2 h <$> f <*> g) x y
-- =
h (f x y) (g x y)
So in a case like yours:
f, g :: Int -> Char -> Bool
f i c = chr i == c
g i c = i == ord c
(liftA2 . liftA2) (==) f g :: Int -> Char -> Bool
-- =
liftA2 (liftA2 (==)) f g
-- =
(\ x y -> f x y == g x y)
The N in liftAN corresponds to the number of functions; the number of liftAN calls corresponds to the number of arguments.

Histomorphisms, Zygomorphisms and Futumorphisms specialised to lists

I ended up figuring it out. See the video and slides of a talk I gave:
slides/pdf
video
Original question:
In my effort to understand generic recursion schemes (i.e., that use Fix) I have found it useful to write list-only versions of the various schemes. It makes it much easier to understand the actual schemes (without the additional overhead of the Fix stuff).
However, I have not yet figured out how to define list-only versions of zygo and futu.
Here are my specialised definitions so far:
cataL :: (a -> b -> b) -> b -> [a] -> b
cataL f b (a : as) = f a (cataL f b as)
cataL _ b [] = b
paraL :: (a -> [a] -> b -> b) -> b -> [a] -> b
paraL f b (a : as) = f a as (paraL f b as)
paraL _ b [] = b
-- TODO: histo
-- DONE: zygo (see below)
anaL :: (b -> (a, b)) -> b -> [a]
anaL f b = let (a, b') = f b in a : anaL f b'
anaL' :: (b -> Maybe (a, b)) -> b -> [a]
anaL' f b = case f b of
Just (a, b') -> a : anaL' f b'
Nothing -> []
apoL :: ([b] -> Maybe (a, Either [b] [a])) -> [b] -> [a]
apoL f b = case f b of
Nothing -> []
Just (x, Left c) -> x : apoL f c
Just (x, Right e) -> x : e
-- DONE: futu (see below)
hyloL :: (a -> c -> c) -> c -> (b -> Maybe (a, b)) -> b -> c
hyloL f z g = cataL f z . anaL' g
hyloL' :: (a -> c -> c) -> c -> (c -> Maybe (a, c)) -> c
hyloL' f z g = case g z of
Nothing -> z
Just (x,z') -> f x (hyloL' f z' g)
How do you define histo, zygo and futu for lists?
Zygomorphism is the high-falutin' mathsy name we give to folds built from two semi-mutually recursive functions. I'll give an example.
Imagine a function pm :: [Int] -> Int (for plus-minus) which intersperses + and - alternately through a list of numbers, such that pm [v,w,x,y,z] = v - (w + (x - (y + z))). You can write it out using primitive recursion:
lengthEven :: [a] -> Bool
lengthEven = even . length
pm0 [] = 0
pm0 (x:xs) = if lengthEven xs
then x - pm0 xs
else x + pm0 xs
Clearly pm0 is not compositional - you need to inspect the length of the whole list at each position to determine whether you're adding or subtracting. Paramorphism models primitive recursion of this sort, when the folding function needs to traverse the whole subtree at each iteration of the fold. So we can at least rewrite the code to conform to an established pattern.
paraL :: (a -> [a] -> b -> b) -> b -> [a] -> b
paraL f z [] = z
paraL f z (x:xs) = f x xs (paraL f z xs)
pm1 = paraL (\x xs acc -> if lengthEven xs then x - acc else x + acc) 0
But this is inefficient. lengthEven traverses the whole list at each iteration of the paramorphism resulting in an O(n2) algorithm.
We can make progress by noting that both lengthEven and para can be expressed as a catamorphism with foldr...
cataL = foldr
lengthEven' = cataL (\_ p -> not p) True
paraL' f z = snd . cataL (\x (xs, acc) -> (x:xs, f x xs acc)) ([], z)
... which suggests that we may be able to fuse the two operations into a single pass over the list.
pm2 = snd . cataL (\x (isEven, total) -> (not isEven, if isEven
then x - total
else x + total)) (True, 0)
We had a fold which depended on the result of another fold, and we were able to fuse them into one traversal of the list. Zygomorphism captures exactly this pattern.
zygoL :: (a -> b -> b) -> -- a folding function
(a -> b -> c -> c) -> -- a folding function which depends on the result of the other fold
b -> c -> -- zeroes for the two folds
[a] -> c
zygoL f g z e = snd . cataL (\x (p, q) -> (f x p, g x p q)) (z, e)
On each iteration of the fold, f sees its answer from the last iteration as in a catamorphism, but g gets to see both functions' answers. g entangles itself with f.
We'll write pm as a zygomorphism by using the first folding function to count whether the list is even or odd in length and the second one to calculate the total.
pm3 = zygoL (\_ p -> not p) (\x isEven total -> if isEven
then x - total
else x + total) True 0
This is classic functional programming style. We have a higher order function doing the heavy lifting of consuming the list; all we had to do was plug in the logic to aggregate results. The construction evidently terminates (you need only prove termination for foldr), and it's more efficient than the original hand-written version to boot.
Aside: #AlexR points out in the comments that zygomorphism has a big sister called mutumorphism, which captures mutual recursion in all
its glory. mutu generalises zygo in that both the folding
functions are allowed to inspect the other's result from the previous
iteration.
mutuL :: (a -> b -> c -> b) ->
(a -> b -> c -> c) ->
b -> c ->
[a] -> c
mutuL f g z e = snd . cataL (\x (p, q) -> (f x p q, g x p q)) (z, e)
You recover zygo from mutu simply by ignoring the extra argument.
zygoL f = mutuL (\x p q -> f x p)
Of course, all of these folding patterns generalise from lists to the fixed point of an arbitrary functor:
newtype Fix f = Fix { unFix :: f (Fix f) }
cata :: Functor f => (f a -> a) -> Fix f -> a
cata f = f . fmap (cata f) . unFix
para :: Functor f => (f (Fix f, a) -> a) -> Fix f -> a
para f = snd . cata (\x -> (Fix $ fmap fst x, f x))
zygo :: Functor f => (f b -> b) -> (f (b, a) -> a) -> Fix f -> a
zygo f g = snd . cata (\x -> (f $ fmap fst x, g x))
mutu :: Functor f => (f (b, a) -> b) -> (f (b, a) -> a) -> Fix f -> a
mutu f g = snd . cata (\x -> (f x, g x))
Compare the definition of zygo with that of zygoL. Also note that zygo Fix = para, and that the latter three folds can be implemented in terms of cata. In foldology everything is related to everything else.
You can recover the list version from the generalised version.
data ListF a r = Nil_ | Cons_ a r deriving Functor
type List a = Fix (ListF a)
zygoL' :: (a -> b -> b) -> (a -> b -> c -> c) -> b -> c -> List a -> c
zygoL' f g z e = zygo k l
where k Nil_ = z
k (Cons_ x y) = f x y
l Nil_ = e
l (Cons_ x (y, z)) = g x y z
pm4 = zygoL' (\_ p -> not p) (\x isEven total -> if isEven
then x - total
else x + total) True 0
Histomorphism models dynamic programming, the technique of tabulating the results of previous subcomputations. (It's sometimes called course-of-value induction.) In a histomorphism, the folding function has access to a table of the results of earlier iterations of the fold. Compare this with the catamorphism, where the folding function can only see the result of the last iteration. The histomorphism has the benefit of hindsight - you can see all of history.
Here's the idea. As we consume the input list, the folding algebra will output a sequence of bs. histo will jot down each b as it emerges, attaching it to the table of results. The number of items in the history is equal to the number of list layers you've processed - by the time you've torn down the whole list, the history of your operation will have a length equal to that of the list.
This is what the history of iterating a list(ory) looks like:
data History a b = Ancient b | Age a b (History a b)
History is a list of pairs of things and results, with an extra result at the end corresponding to the []-thing. We'll pair up each layer of the input list with its corresponding result.
cataL = foldr
history :: (a -> History a b -> b) -> b -> [a] -> History a b
history f z = cataL (\x h -> Age x (f x h) h) (Ancient z)
Once you've folded up the whole list from right to left, your final result will be at the top of the stack.
headH :: History a b -> b
headH (Ancient x) = x
headH (Age _ x _) = x
histoL :: (a -> History a b -> b) -> b -> [a] -> b
histoL f z = headH . history f z
(It happens that History a is a comonad, but headH (née extract) is all we need to define histoL.)
History labels each layer of the input list with its corresponding result. The cofree comonad captures the pattern of labelling each layer of an arbitrary structure.
data Cofree f a = Cofree { headC :: a, tailC :: f (Cofree f a) }
(I came up with History by plugging ListF into Cofree and simplifying.)
Compare this with the free monad,
data Free f a = Free (f (Free f a))
| Return a
Free is a coproduct type; Cofree is a product type. Free layers up a lasagne of fs, with values a at the bottom of the lasagne. Cofree layers up the lasagne with values a at each layer. Free monads are generalised externally-labelled trees; cofree comonads are generalised internally-labelled trees.
With Cofree in hand, we can generalise from lists to the fixpoint of an arbitrary functor,
newtype Fix f = Fix { unFix :: f (Fix f) }
cata :: Functor f => (f b -> b) -> Fix f -> b
cata f = f . fmap (cata f) . unFix
histo :: Functor f => (f (Cofree f b) -> b) -> Fix f -> b
histo f = headC . cata (\x -> Cofree (f x) x)
and once more recover the list version.
data ListF a r = Nil_ | Cons_ a r deriving Functor
type List a = Fix (ListF a)
type History' a b = Cofree (ListF a) b
histoL' :: (a -> History' a b -> b) -> b -> List a -> b
histoL' f z = histo g
where g Nil_ = z
g (Cons_ x h) = f x h
Aside: histo is the dual of futu. Look at their types.
histo :: Functor f => (f (Cofree f a) -> a) -> (Fix f -> a)
futu :: Functor f => (a -> f (Free f a)) -> (a -> Fix f)
futu is histo with the arrows flipped and with Free replaced by
Cofree. Histomorphisms see the past; futumorphisms predict the future.
And much like cata f . ana g can be fused into a hylomorphism,
histo f . futu g can be fused into a
chronomorphism.
Even if you skip the mathsy parts, this paper by Hinze and Wu features a good, example-driven tutorial on histomorphisms and their usage.
Since no one else has answered for futu yet, I'll try to stumble my way through. I'm going to use ListF a b = Base [a] = ConsF a b | NilF
Taking the type in recursion-schemes: futu :: Unfoldable t => (a -> Base t (Free (Base t) a)) -> a -> t.
I'm going to ignore the Unfoldable constraint and substitute [b] in for t.
(a -> Base [b] (Free (Base [b]) a)) -> a -> [b]
(a -> ListF b (Free (ListF b) a)) -> a -> [b]
Free (ListF b) a) is a list, possibly with an a-typed hole at the end. This means that it's isomorphic to ([b], Maybe a). So now we have:
(a -> ListF b ([b], Maybe a)) -> a -> [b]
Eliminating the last ListF, noticing that ListF a b is isomorphic to Maybe (a, b):
(a -> Maybe (b, ([b], Maybe a))) -> a -> [b]
Now, I'm pretty sure that playing type-tetris leads to the only sensible implementation:
futuL f x = case f x of
Nothing -> []
Just (y, (ys, mz)) -> y : (ys ++ fz)
where fz = case mz of
Nothing -> []
Just z -> futuL f z
Summarizing the resulting function, futuL takes a seed value and a function which may produce at least one result, and possibly a new seed value if it produced a result.
At first I thought this was equivalent to
notFutuL :: (a -> ([b], Maybe a)) -> a -> [b]
notFutuL f x = case f x of
(ys, mx) -> ys ++ case mx of
Nothing -> []
Just x' -> notFutuL f x'
And in practice, perhaps it is, more or less, but the one significant difference is that the real futu guarantees productivity (i.e. if f always returns, you will never be stuck waiting forever for the next list element).

How can I understand "(.) . (.)"?

I believe I understand fmap . fmap for Functors, but on functions it's hurting my head for months now.
I've seen that you can just apply the definition of (.) to (.) . (.), but I've forgot how to do that.
When I try it myself it always turns out wrong:
(.) f g = \x -> f (g x)
(.) (.) (.) = \x -> (.) ((.) x)
\x f -> (.) ((.) x) f
\x f y -> (((.)(f y)) x)
\x f y g-> (((.)(f y) g) x)
\x f y g-> ((f (g y)) x)
\x f y g-> ((f (g y)) x):: t2 -> (t1 -> t2 -> t) -> t3 -> (t3 -> t1) -> t
If "just applying the definition" is the only way of doing it, how did anybody come up with (.) . (.)?
There must be some deeper understanding or intuition I'm missing.
Coming up with (.) . (.) is actually pretty straightforward, it's the intuition behind what it does that is quite tricky to understand.
(.) gets you very far when rewriting expression into the "pipe" style computations (think of | in shell). However, it becomes awkward to use once you try to compose a function that takes multiple arguments with a function that only takes one. As an example, let's have a definition of concatMap:
concatMap :: (a -> [b]) -> [a] -> [b]
concatMap f xs = concat (map f xs)
Getting rid of xs is just a standard operation:
concatMap f = concat . map f
However, there's no "nice" way of getting rid of f. This is caused by the fact, that map takes two arguments and we'd like to apply concat on its final result.
You can of course apply some pointfree tricks and get away with just (.):
concatMap f = (.) concat (map f)
concatMap f = (.) concat . map $ f
concatMap = (.) concat . map
concatMap = (concat .) . map
But alas, readability of this code is mostly gone. Instead, we introduce a new combinator, that does exactly what we need: apply the second function to the final result of first one.
-- .: is fairly standard name for this combinator
(.:) :: (c -> d) -> (a -> b -> c) -> a -> b -> d
(f .: g) x y = f (g x y)
concatMap = concat .: map
Fine, that's it for motivation. Let's get to the pointfree business.
(.:) = \f g x y -> f (g x y)
= \f g x y -> f ((g x) y)
= \f g x y -> f . g x $ y
= \f g x -> f . g x
Now, here comes the interesting part. This is yet another of the pointfree tricks that usually helps when you get stuck: we rewrite . into its prefix form and try to continue from there.
= \f g x -> (.) f (g x)
= \f g x -> (.) f . g $ x
= \f g -> (.) f . g
= \f g -> (.) ((.) f) g
= \f -> (.) ((.) f)
= \f -> (.) . (.) $ f
= (.) . (.)
As for intuition, there's this very nice article that you should read. I'll paraphrase the part about (.):
Let's think again about what our combinator should do: it should apply f to the result of result of g (I've been using final result in the part before on purpose, it's really what you get when you fully apply - modulo unifying type variables with another function type - the g function, result here is just application g x for some x).
What it means for us to apply f to the result of g? Well, once we apply g to some value, we'll take the result and apply f to it. Sounds familiar: that's what (.) does.
result :: (b -> c) -> ((a -> b) -> (a -> c))
result = (.)
Now, it turns out that composition (our of word) of those combinators is just a function composition, that is:
(.:) = result . result -- the result of result
You can also use your understanding of fmap . fmap.
If you have two Functors foo and bar, then
fmap . fmap :: (a -> b) -> foo (bar a) -> foo (bar b)
fmap . fmap takes a function and produces an induced function for the composition of the two Functors.
Now, for any type t, (->) t is a Functor, and the fmap for that Functor is (.).
So (.) . (.) is fmap . fmap for the case where the two Functors are (->) s and (->) t, and thus
(.) . (.) :: (a -> b) -> ((->) s) ((->) t a) -> ((->) s) ((->) t b)
= (a -> b) -> (s -> (t -> a)) -> (s -> (t -> b))
= (a -> b) -> (s -> t -> a ) -> (s -> t -> b )
it "composes" a function f :: a -> b with a function of two arguments, g :: s -> t -> a,
((.) . (.)) f g = \x y -> f (g x y)
That view also makes it clear that, and how, the pattern extends to functions taking more arguments,
(.) :: (a -> b) -> (s -> a) -> (s -> b)
(.) . (.) :: (a -> b) -> (s -> t -> a) -> (s -> t -> b)
(.) . (.) . (.) :: (a -> b) -> (s -> t -> u -> a) -> (s -> t -> u -> b)
etc.
Your solution diverges when you introduce y. It should be
\x f y -> ((.) ((.) x) f) y :: (c -> d) -> (a -> b -> c) -> a -> b -> d
\x f y z -> ((.) ((.) x) f) y z :: (c -> d) -> (a -> b -> c) -> a -> b -> d
\x f y z -> ((.) x (f y)) z :: (c -> d) -> (a -> b -> c) -> a -> b -> d
-- Or alternately:
\x f y z -> (x . f y) z :: (c -> d) -> (a -> b -> c) -> a -> b -> d
\x f y z -> (x (f y z)) :: (c -> d) -> (a -> b -> c) -> a -> b -> d
Which matches the original type signature: (.) . (.) :: (c -> d) -> (a -> b -> c) -> a -> b -> d
(It's easiest to do the expansion in ghci, where you can check each step with :t expression)
Edit:
The deeper intution is this:
(.) is simply defined as
\f g -> \x -> f (g x)
Which we can simplify to
\f g x -> f (g x)
So when you supply it two arguments, it's curried and still needs another argument to resolve.
Each time you use (.) with 2 arguments, you create a "need" for one more argument.
(.) . (.) is of course just (.) (.) (.), so let's expand it:
(\f0 g0 x0 -> f0 (g0 x0)) (\f1 g1 x1 -> f1 (g1 x1)) (\f2 g2 x2 -> f2 (g2 x2))
We can beta-reduce on f0 and g0 (but we don't have an x0!):
\x0 -> (\f1 g1 x1 -> f1 (g1 x1)) ((\f2 g2 x2 -> f2 (g2 x2)) x0)
Substitute the 2nd expression for f1...
\x0 -> \g1 x1 -> ((\f2 g2 x2 -> f2 (g2 x2)) x0) (g1 x1)
Now it "flips back"! (beta-reduction on f2):
This is the interesting step - x0 is substituted for f2 -- This means that x, which could have been data, is instead a function.
This is what (.) . (.) provides -- the "need" for the extra argument.
\x0 -> \g1 x1 -> (\g2 x2 -> x0 (g2 x2)) (g1 x1)
This is starting to look normal...
Let's beta-reduce a last time (on g2):
\x0 -> \g1 x1 -> (\x2 -> x0 ((g1 x1) x2))
So we're left with simply
\x0 g1 x1 x2 -> x0 ((g1 x1) x2)
, where the arguments are nicely still in order.
So, this is what I get when I do a slightly more incremental expansion
(.) f g = \x -> f (g x)
(.) . g = \x -> (.) (g x)
= \x -> \y -> (.) (g x) y
= \x -> \y -> \z -> (g x) (y z)
= \x y z -> (g x) (y z)
(.) . (.) = \x y z -> ((.) x) (y z)
= \x y z -> \k -> x (y z k)
= \x y z k -> x (y z k)
Which, according to ghci has the correct type
Prelude> :t (.) . (.)
(.) . (.) :: (b -> c) -> (a -> a1 -> b) -> a -> a1 -> c
Prelude> :t \x y z k -> x (y z k)
\x y z k -> x (y z k)
:: (t1 -> t) -> (t2 -> t3 -> t1) -> t2 -> t3 -> t
Prelude>
While I don't know the origins of this combinator, it is likely that it was
developed for use in combinatory logic, where you work strictly with combinators,
so you can't define things using more convenient lambda expressions. There may be
some intuition that goes with figuring these things out, but I haven't found it.
Most likely, you would develop some level of intuition if you had to do it enough.
It's easiest to write equations, combinators-style, instead of lambda-expressions: a b c = (\x -> ... body ...) is equivalent to a b c x = ... body ..., and vice versa, provided that x does not appear among {a,b,c}. So,
-- _B = (.)
_B f g x = f (g x)
_B _B _B f g x y = _B (_B f) g x y
= (_B f) (g x) y
= _B f (g x) y
= f ((g x) y)
= f (g x y)
You discover this if, given f (g x y), you want to convert it into a combinatory form (get rid of all the parentheses and variable repetitions). Then you apply patterns corresponding to the combinators' definitions, hopefully tracing this derivation backwards. This is much less mechanical/automatic though.

Resources