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