How does the expression `ap zip tail` work - haskell

I wondered how to write f x = zip x (tail x) in point free. So I used the pointfree program and the result was f = ap zip tail. ap being a function from Control.Monad
I do not understand how the point free definition works. I hope I can figure it out if I can comprehend it from the perspective of types.
import Control.Monad (ap)
let f = ap zip tail
let g = ap zip
:info ap zip tail f g
ap :: Monad m => m (a -> b) -> m a -> m b
-- Defined in `Control.Monad'
zip :: [a] -> [b] -> [(a, b)] -- Defined in `GHC.List'
tail :: [a] -> [a] -- Defined in `GHC.List'
f :: [b] -> [(b, b)] -- Defined at <interactive>:3:5
g :: ([a] -> [b]) -> [a] -> [(a, b)]
-- Defined at <interactive>:4:5
By looking at the expression ap zip tail I would think that zip is the first parameter of ap and tail is the second parameter of ap.
Monad m => m (a -> b) -> m a -> m b
\--------/ \---/
zip tail
But this is not possible, because the types of zip and tail are completely different than what the function ap requires. Even with taking into consideration that the list is a monad of sorts.

So the type signature of ap is Monad m => m (a -> b) -> m a -> m b. You've given it zip and tail as arguments, so let's look at their type signatures.
Starting with tail :: [a] -> [a] ~ (->) [a] [a] (here ~ is the equality operator for types), if we compare this type against the type of the second argument for ap,
(->) [x] [x] ~ m a
((->) [x]) [x] ~ m a
we get a ~ [x] and m ~ ((->) [x]) ~ ((->) a). Already we can see that the monad we're in is (->) [x], not []. If we substitute what we can into the type signature of ap we get:
(((->) [x]) ([x] -> b)) -> (((->) [x]) [x]) -> (((->) [x]) b)
Since this is not very readable, it can more normally be written as
([x] -> ([x] -> b)) -> ([x] -> [x]) -> ([x] -> b)
~ ([x] -> [x] -> b ) -> ([x] -> [x]) -> ([x] -> b)
The type of zip is [x] -> [y] -> [(x, y)]. We can already see that this lines up with the first argument to ap where
[x] ~ [x]
[y] ~ [x]
[(x, y)] ~ b
Here I've listed the types vertically so that you can easily see which types line up. So obviously x ~ x, y ~ x, and [(x, y)] ~ [(x, x)] ~ b, so we can finish substituting b ~ [(x, x)] into ap's type signature and get
([x] -> [x] -> [(x, x)]) -> ([x] -> [x]) -> ([x] -> [(x, x)])
-- zip tail ( ap zip tail )
-- ap zip tail u = zip u (tail u)
I hope that clears things up for you.
EDIT: As danvari pointed out in the comments, the monad (->) a is sometimes called the reader monad.

There are two aspects to understanding this:
The type magic
The information flow of the implementation
Firstly, this helped me understand the type magic:
1) zip : [a] → ( [a] → [(a,a)] )
2) tail : [a] → [a]
3) zip <*> tail : [a] → [(a,a)]
4) <*> : Applicative f ⇒ f (p → q) → f p → f q
In this case, for <*>,
5) f x = y → x
Note that in 5, f is a type constructor. Applying f to x produces a type. Also, here = is overloaded to mean equivalence of types.
y is currently a place-holder, in this case, it is [a], which means
6) f x = [a] -> x
Using 6, we can rewrite 1,2 and 3 as follows:
7) zip : f ([a] → [(a,a)])
8) tail : f [a]
9) zip <*> tail : f ([a] → [(a,a)]) → f [a] → f [(a,a)]
So, looking at 4, we are substituting as follows:
10) p = [a]
11) q = [(a,a)]
12) f x = [a] → x
(Repetition of 6 here again as 12 )
Secondly, the information flow, i.e. the actual functionality. This is easier, it is clear from the definition of <*> for the Applicative instance of y →, which is rewritten here with different identifier names and using infix style:
13) g <*> h $ xs = g xs (h xs)
Substituting as follows:
14) g = zip
15) h = tail
Gives:
zip <*> tail $ xs (Using 14 and 15)
==
zip xs (tail xs) (Using 13 )

Related

Mapping while showing intermediate states

I need a function that does this:
>>> func (+1) [1,2,3]
[[2,2,3],[2,3,3],[2,3,4]]
My real case is more complex, but this example shows the gist of the problem. The main difference is that in reality using indexes would be infeasible. The List should be a Traversable or Foldable.
EDIT: This should be the signature of the function:
func :: Traversable t => (a -> a) -> t a -> [t a]
And closer to what I really want is the same signature to traverse but can't figure out the function I have to use, to get the desired result.
func :: (Traversable t, Applicative f) :: (a -> f a) -> t a -> f (t a)
It looks like #Benjamin Hodgson misread your question and thought you wanted f applied to a single element in each partial result. Because of this, you've ended up thinking his approach doesn't apply to your problem, but I think it does. Consider the following variation:
import Control.Monad.State
indexed :: (Traversable t) => t a -> (t (Int, a), Int)
indexed t = runState (traverse addIndex t) 0
where addIndex x = state (\k -> ((k, x), k+1))
scanMap :: (Traversable t) => (a -> a) -> t a -> [t a]
scanMap f t =
let (ti, n) = indexed (fmap (\x -> (x, f x)) t)
partial i = fmap (\(k, (x, y)) -> if k < i then y else x) ti
in map partial [1..n]
Here, indexed operates in the state monad to add an incrementing index to elements of a traversable object (and gets the length "for free", whatever that means):
> indexed ['a','b','c']
([(0,'a'),(1,'b'),(2,'c')],3)
and, again, as Ben pointed out, it could also be written using mapAccumL:
indexed = swap . mapAccumL (\k x -> (k+1, (k, x))) 0
Then, scanMap takes the traversable object, fmaps it to a similar structure of before/after pairs, uses indexed to index it, and applies a sequence of partial functions, where partial i selects "afters" for the first i elements and "befores" for the rest.
> scanMap (*2) [1,2,3]
[[2,2,3],[2,4,3],[2,4,6]]
As for generalizing this from lists to something else, I can't figure out exactly what you're trying to do with your second signature:
func :: (Traversable t, Applicative f) => (a -> f a) -> t a -> f (t a)
because if you specialize this to a list you get:
func' :: (Traversable t) => (a -> [a]) -> t a -> [t a]
and it's not at all clear what you'd want this to do here.
On lists, I'd use the following. Feel free to discard the first element, if not wanted.
> let mymap f [] = [[]] ; mymap f ys#(x:xs) = ys : map (f x:) (mymap f xs)
> mymap (+1) [1,2,3]
[[1,2,3],[2,2,3],[2,3,3],[2,3,4]]
This can also work on Foldable, of course, after one uses toList to convert the foldable to a list. One might still want a better implementation that would avoid that step, though, especially if we want to preserve the original foldable type, and not just obtain a list.
I just called it func, per your question, because I couldn't think of a better name.
import Control.Monad.State
func f t = [evalState (traverse update t) n | n <- [0..length t - 1]]
where update x = do
n <- get
let y = if n == 0 then f x else x
put (n-1)
return y
The idea is that update counts down from n, and when it reaches 0 we apply f. We keep n in the state monad so that traverse can plumb n through as you walk across the traversable.
ghci> func (+1) [1,1,1]
[[2,1,1],[1,2,1],[1,1,2]]
You could probably save a few keystrokes using mapAccumL, a HOF which captures the pattern of traversing in the state monad.
This sounds a little like a zipper without a focus; maybe something like this:
data Zippy a b = Zippy { accum :: [b] -> [b], rest :: [a] }
mapZippy :: (a -> b) -> [a] -> [Zippy a b]
mapZippy f = go id where
go a [] = []
go a (x:xs) = Zippy b xs : go b xs where
b = a . (f x :)
instance (Show a, Show b) => Show (Zippy a b) where
show (Zippy xs ys) = show (xs [], ys)
mapZippy succ [1,2,3]
-- [([2],[2,3]),([2,3],[3]),([2,3,4],[])]
(using difference lists here for efficiency's sake)
To convert to a fold looks a little like a paramorphism:
para :: (a -> [a] -> b -> b) -> b -> [a] -> b
para f b [] = b
para f b (x:xs) = f x xs (para f b xs)
mapZippy :: (a -> b) -> [a] -> [Zippy a b]
mapZippy f xs = para g (const []) xs id where
g e zs r d = Zippy nd zs : r nd where
nd = d . (f e:)
For arbitrary traversals, there's a cool time-travelling state transformer called Tardis that lets you pass state forwards and backwards:
mapZippy :: Traversable t => (a -> b) -> t a -> t (Zippy a b)
mapZippy f = flip evalTardis ([],id) . traverse g where
g x = do
modifyBackwards (x:)
modifyForwards (. (f x:))
Zippy <$> getPast <*> getFuture

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

Recursion scheme in Haskell for repeatedly breaking datatypes into "head" and "tail" and yielding a structure of results

In Haskell, I recently found the following function useful:
listCase :: (a -> [a] -> b) -> [a] -> [b]
listCase f [] = []
listCase f (x:xs) = f x xs : listCase f xs
I used it to generate sliding windows of size 3 from a list, like this:
*Main> listCase (\_ -> take 3) [1..5]
[[2,3,4],[3,4,5],[4,5],[5],[]]
Is there a more general recursion scheme which captures this pattern? More specifically, that allows you to generate a some structure of results by repeatedly breaking data into a "head" and "tail"?
What you are asking for is a comonad. This may sound scarier than monad, but is a simpler concept (YMMV).
Comonads are Functors with additional structure:
class Functor w => Comonad w where
extract :: w a -> a
duplicate :: w a -> w (w a)
extend :: (w a -> b) -> w a -> w b
(extendand duplicate can be defined in terms of each other)
and laws similar to the monad laws:
duplicate . extract = id
duplicate . fmap extract = id
duplicate . duplicate = fmap duplicate . duplicate
Specifically, the signature (a -> [a] -> b) takes non-empty Lists of type a. The usual type [a] is not an instance of a comonad, but the non-empty lists are:
data NE a = T a | a :. NE a deriving Functor
instance Comonad NE where
extract (T x) = x
extract (x :. _) = x
duplicate z#(T _) = T z
duplicate z#(_ :. xs) = z :. duplicate xs
The comonad laws allow only this instance for non-empty lists (actually a second one).
Your function then becomes
extend (take 3 . drop 1 . toList)
Where toList :: NE a -> [a] is obvious.
This is worse than the original, but extend can be written as =>> which is simpler if applied repeatedly.
For further information, you may start at What is the Comonad typeclass in Haskell?.
This looks like a special case of a (jargon here but it can help with googling) paramorphism, a generalisation of primitive recursion to all initial algebras.
Reimplementing ListCase
Let's have a look at how to reimplement your function using such a combinator. First we define the notion of paramorphism: a recursion principle where not only the result of the recursive call is available but also the entire substructure this call was performed on:
The type of paraList tells me that in the (:) case, I will have access to the head, the tail and the value of the recursive call on the tail and that I need to provide a value for the base case.
module ListCase where
paraList :: (a -> [a] -> b -> b) -- cons
-> b -- nil
-> [a] -> b -- resulting function on lists
paraList c n [] = n
paraList c n (x : xs) = c x xs $ paraList c n xs
We can now give an alternative definition of listCase:
listCase' :: (a -> [a] -> b) -> [a] -> [b]
listCase' c = paraList (\ x xs tl -> c x xs : tl) []
Considering the general case
In the general case, we are interested in building a definition of paramorphism for all data structures defined as the fixpoint of a (strictly positive) functor. We use the traditional fixpoint operator:
newtype Fix f = Fix { unFix :: f (Fix f) }
This builds an inductive structure layer by layer. The layers have an f shape which maybe better grasped by recalling the definition of List using this formalism. A layer is either Nothing (we're done!) or Just (head, tail):
newtype ListF a as = ListF { unListF :: Maybe (a, as) }
type List a = Fix (ListF a)
nil :: List a
nil = Fix $ ListF $ Nothing
cons :: a -> List a -> List a
cons = curry $ Fix . ListF .Just
Now that we have this general framework, we can define para generically for all Fix f where f is a functor:
para :: Functor f => (f (Fix f, b) -> b) -> Fix f -> b
para alg = alg . fmap (\ rec -> (rec, para alg rec)) . unFix
Of course, ListF a is a functor. Meaning we could use para to reimplement paraList and listCase.
instance Functor (ListF a) where fmap f = ListF . fmap (fmap f) . unListF
paraList' :: (a -> List a -> b -> b) -> b -> List a -> b
paraList' c n = para $ maybe n (\ (a, (as, b)) -> c a as b) . unListF
listCase'' :: (a -> List a -> b) -> List a -> List b
listCase'' c = paraList' (\ x xs tl -> cons (c x xs) tl) nil
You can implement a simple bijection toList, fromList to test it if you want. I could not be bothered to reimplement take so it's pretty ugly:
toList :: [a] -> List a
toList = foldr cons nil
fromList :: List a -> [a]
fromList = paraList' (\ x _ tl -> x : tl) []
*ListCase> fmap fromList . fromList . listCase'' (\ _ as -> toList $ take 3 $ fromList as). toList $ [1..5]
[[2,3,4],[3,4,5],[4,5],[5],[]]

Why can you reverse list with foldl, but not with foldr in Haskell

Why can you reverse a list with the foldl?
reverse' :: [a] -> [a]
reverse' xs = foldl (\acc x-> x : acc) [] xs
But this one gives me a compile error.
reverse' :: [a] -> [a]
reverse' xs = foldr (\acc x-> x : acc) [] xs
Error
Couldn't match expected type `a' with actual type `[a]'
`a' is a rigid type variable bound by
the type signature for reverse' :: [a] -> [a] at foldl.hs:33:13
Relevant bindings include
x :: [a] (bound at foldl.hs:34:27)
acc :: [a] (bound at foldl.hs:34:23)
xs :: [a] (bound at foldl.hs:34:10)
reverse' :: [a] -> [a] (bound at foldl.hs:34:1)
In the first argument of `(:)', namely `x'
In the expression: x : acc
Every foldl is a foldr.
Let's remember the definitions.
foldr :: (a -> s -> s) -> s -> [a] -> s
foldr f s [] = s
foldr f s (a : as) = f a (foldr f s as)
That's the standard issue one-step iterator for lists. I used to get my students to bang on the tables and chant "What do you do with the empty list? What do you do with a : as"? And that's how you figure out what s and f are, respectively.
If you think about what's happening, you see that foldr effectively computes a big composition of f a functions, then applies that composition to s.
foldr f s [1, 2, 3]
= f 1 . f 2 . f 3 . id $ s
Now, let's check out foldl
foldl :: (t -> a -> t) -> t -> [a] -> t
foldl g t [] = t
foldl g t (a : as) = foldl g (g t a) as
That's also a one-step iteration over a list, but with an accumulator which changes as we go. Let's move it last, so that everything to the left of the list argument stays the same.
flip . foldl :: (t -> a -> t) -> [a] -> t -> t
flip (foldl g) [] t = t
flip (foldl g) (a : as) t = flip (foldl g) as (g t a)
Now we can see the one-step iteration if we move the = one place leftward.
flip . foldl :: (t -> a -> t) -> [a] -> t -> t
flip (foldl g) [] = \ t -> t
flip (foldl g) (a : as) = \ t -> flip (foldl g) as (g t a)
In each case, we compute what we would do if we knew the accumulator, abstracted with \ t ->. For [], we would return t. For a : as, we would process the tail with g t a as the accumulator.
But now we can transform flip (foldl g) into a foldr. Abstract out the recursive call.
flip . foldl :: (t -> a -> t) -> [a] -> t -> t
flip (foldl g) [] = \ t -> t
flip (foldl g) (a : as) = \ t -> s (g t a)
where s = flip (foldl g) as
And now we're good to turn it into a foldr where type s is instantiated with t -> t.
flip . foldl :: (t -> a -> t) -> [a] -> t -> t
flip (foldl g) = foldr (\ a s -> \ t -> s (g t a)) (\ t -> t)
So s says "what as would do with the accumulator" and we give back \ t -> s (g t a) which is "what a : as does with the accumulator". Flip back.
foldl :: (t -> a -> t) -> t -> [a] -> t
foldl g = flip (foldr (\ a s -> \ t -> s (g t a)) (\ t -> t))
Eta-expand.
foldl :: (t -> a -> t) -> t -> [a] -> t
foldl g t as = flip (foldr (\ a s -> \ t -> s (g t a)) (\ t -> t)) t as
Reduce the flip.
foldl :: (t -> a -> t) -> t -> [a] -> t
foldl g t as = foldr (\ a s -> \ t -> s (g t a)) (\ t -> t) as t
So we compute "what we'd do if we knew the accumulator", and then we feed it the initial accumulator.
It's moderately instructive to golf that down a little. We can get rid of \ t ->.
foldl :: (t -> a -> t) -> t -> [a] -> t
foldl g t as = foldr (\ a s -> s . (`g` a)) id as t
Now let me reverse that composition using >>> from Control.Arrow.
foldl :: (t -> a -> t) -> t -> [a] -> t
foldl g t as = foldr (\ a s -> (`g` a) >>> s) id as t
That is, foldl computes a big reverse composition. So, for example, given [1,2,3], we get
foldr (\ a s -> (`g` a) >>> s) id [1,2,3] t
= ((`g` 1) >>> (`g` 2) >>> (`g` 3) >>> id) t
where the "pipeline" feeds its argument in from the left, so we get
((`g` 1) >>> (`g` 2) >>> (`g` 3) >>> id) t
= ((`g` 2) >>> (`g` 3) >>> id) (g t 1)
= ((`g` 3) >>> id) (g (g t 1) 2)
= id (g (g (g t 1) 2) 3)
= g (g (g t 1) 2) 3
and if you take g = flip (:) and t = [] you get
flip (:) (flip (:) (flip (:) [] 1) 2) 3
= flip (:) (flip (:) (1 : []) 2) 3
= flip (:) (2 : 1 : []) 3
= 3 : 2 : 1 : []
= [3, 2, 1]
That is,
reverse as = foldr (\ a s -> (a :) >>> s) id as []
by instantiating the general transformation of foldl to foldr.
For mathochists only. Do cabal install newtype and import Data.Monoid, Data.Foldable and Control.Newtype. Add the tragically missing instance:
instance Newtype (Dual o) o where
pack = Dual
unpack = getDual
Observe that, on the one hand, we can implement foldMap by foldr
foldMap :: Monoid x => (a -> x) -> [a] -> x
foldMap f = foldr (mappend . f) mempty
but also vice versa
foldr :: (a -> b -> b) -> b -> [a] -> b
foldr f = flip (ala' Endo foldMap f)
so that foldr accumulates in the monoid of composing endofunctions, but now to get foldl, we tell foldMap to work in the Dual monoid.
foldl :: (b -> a -> b) -> b -> [a] -> b
foldl g = flip (ala' Endo (ala' Dual foldMap) (flip g))
What is mappend for Dual (Endo b)? Modulo wrapping, it's exactly the reverse composition, >>>.
For a start, the type signatures don't line up:
foldl :: (o -> i -> o) -> o -> [i] -> o
foldr :: (i -> o -> o) -> o -> [i] -> o
So if you swap your argument names:
reverse' xs = foldr (\ x acc -> x : acc) [] xs
Now it compiles. It won't work, but it compiles now.
The thing is, foldl, works from left to right (i.e., backwards), whereas foldr works right to left (i.e., forwards). And that's kind of why foldl lets you reverse a list; it hands you stuff in reverse order.
Having said all that, you can do
reverse' xs = foldr (\ x acc -> acc ++ [x]) [] xs
It'll be really slow, however. (Quadratic complexity rather than linear complexity.)
You can use foldr to reverse a list efficiently (well, most of the time in GHC 7.9—it relies on some compiler optimizations), but it's a little weird:
reverse xs = foldr (\x k -> \acc -> k (x:acc)) id xs []
I wrote an explanation of how this works on the Haskell Wiki.
foldr basically deconstructs a list, in the canonical way: foldr f initial is the same as a function with patterns:(this is basically the definition of foldr)
ff [] = initial
ff (x:xs) = f x $ ff xs
i.e. it un-conses the elements one by one and feeds them to f. Well, if all f does is cons them back again, then you get the list you originally had! (Another way to say that: foldr (:) [] ≡ id.
foldl "deconstructs" the list in inverse order, so if you cons back the elements you get the reverse list. To achieve the same result with foldr, you need to append to the "wrong" end – either as MathematicalOrchid showed, inefficiently with ++, or by using a difference list:
reverse'' :: [a] -> [a]
reverse'' l = dl2list $ foldr (\x accDL -> accDL ++. (x:)) empty l
type DList a = [a]->[a]
(++.) :: DList a -> DList a -> DList a
(++.) = (.)
emptyDL :: DList a
emptyDL = id
dl2list :: DLList a -> [a]
dl2list = ($[])
Which can be compactly written as
reverse''' l = foldr (flip(.) . (:)) id l []
This is what foldl op acc does with a list with, say, 6 elements:
(((((acc `op` x1) `op` x2) `op` x3) `op` x4) `op` x5 ) `op` x6
while foldr op acc does this:
x1 `op` (x2 `op` (x3 `op` (x4 `op` (x5 `op` (x6 `op` acc)))))
When you look at this, it becomes clear that if you want foldl to reverse the list, op should be a "stick the right operand to the beginning of the left operand" operator. Which is just (:) with arguments reversed, i.e.
reverse' = foldl (flip (:)) []
(this is the same as your version but using built-in functions).
When you want foldr to reverse the list, you need a "stick the left operand to the end of the right operand" operator. I don't know of a built-in function that does that; if you want you can write it as flip (++) . return.
reverse'' = foldr (flip (++) . return) []
or if you prefer to write it yourself
reverse'' = foldr (\x acc -> acc ++ [x]) []
This would be slow though.
A slight but significant generalization of several of these answers is that you can implement foldl with foldr, which I think is a clearer way of explaining what's going on in them:
myMap :: (a -> b) -> [a] -> [b]
myMap f = foldr step []
where step a bs = f a : bs
-- To fold from the left, we:
--
-- 1. Map each list element to an *endomorphism* (a function from one
-- type to itself; in this case, the type is `b`);
--
-- 2. Take the "flipped" (left-to-right) composition of these
-- functions;
--
-- 3. Apply the resulting function to the `z` argument.
--
myfoldl :: (b -> a -> b) -> b -> [a] -> b
myfoldl f z as = foldr (flip (.)) id (toEndos f as) z
where
toEndos :: (b -> a -> b) -> [a] -> [b -> b]
toEndos f = myMap (flip f)
myReverse :: [a] -> [a]
myReverse = myfoldl (flip (:)) []
For more explanation of the ideas here, I'd recommend reading Tom Ellis' "What is foldr made of?" and Brent Yorgey's "foldr is made of monoids".

Is it possible to fold <*> in haskell?

I want to realize something like
fun1 f a_ziplist
for example
getZipList $ (\x y z -> x*y+z) <$> ZipList [4,7] <*> ZipList [6,9] <*> ZipList [5,10]
f = (\x y z -> x*y+z)
ziplist = [[4,7],[6,9],[5,10]]
To do this, I want to recursively apply <*> like
foldx (h:w) = h <*> foldx w
foldx (w:[]) = w
but it seems impossible to make <*> recursive.
Let's play with the types in ghci, to see where they carry us.
λ import Control.Applicative
The type of (<*>)
λ :t (<*>)
(<*>) :: Applicative f => f (a -> b) -> f a -> f b
The type of foldr:
λ :t Prelude.foldr
Prelude.foldr :: (a -> b -> b) -> b -> [a] -> b
Perhaps we could use (<*>) as the function that is passed as the first parameter of foldr. What would be the type?
λ :t Prelude.foldr (<*>)
Prelude.foldr (<*>) :: Applicative f => f a -> [f (a -> a)] -> f a
So it seems that it takes an initial value in an applicative context, and a list of functions in an applicative context, and returns another applicative.
For example, using ZipList as the applicative:
λ getZipList $ Prelude.foldr (<*>) (ZipList [2,3]) [ ZipList [succ,pred], ZipList [(*2)] ]
The result is:
[5]
I'm not sure if this is what the question intended, but it seems like a natural way to fold using (<*>).
If the ziplist argument has to be a plain list, it looks impossible. This is because fold f [a1,...,an] must be well typed for every n, hence f must be a function type taking at least n arguments for every n, hence infinitely many.
However, if you use a GADT list type, in which values expose their length as a type-level natural you can achieve something similar to what you want.
{-# LANGUAGE DataKinds, KindSignatures, TypeFamilies, GADTs #-}
import Control.Applicative
-- | Type-level naturals
data Nat = Z | S Nat
-- | Type family for n-ary functions
type family Fn (n :: Nat) a b
type instance Fn Z a b = b
type instance Fn (S n) a b = a -> Fn n a b
-- | Lists exposing their length in their type
data List a (n :: Nat) where
Nil :: List a Z
Cons :: a -> List a n -> List a (S n)
-- | General <*> applied to a list of arguments of the right length
class Apply (n :: Nat) where
foldF :: Applicative f => f (Fn n a b) -> List (f a) n -> f b
instance Apply Z where
foldF f0 Nil = f0
instance Apply n => Apply (S n) where
foldF fn (Cons x xs) = foldF (fn <*> x) xs
test :: [(Integer,Integer,Integer)]
test = foldF (pure (,,)) (Cons [10,11] (Cons [20,21] (Cons [30,31] Nil)))
-- Result: [(10,20,30),(10,20,31),(10,21,30),(10,21,31)
-- ,(11,20,30),(11,20,31),(11,21,30),(11,21,31)]
In general folding (<*>) is tricky because of types, as others have mentioned. But for your specific example, where your ziplist elements are all of the same type, you can use a different method and make your calculation work with a small change to f to make it take a list argument instead of single elements:
import Data.Traversable
import Control.Applicative
f = (\[x,y,z] -> x*y+z)
ziplist = [[4,7],[6,9],[5,10]]
fun1 f l = getZipList $ f <$> traverse ZipList l
It's even possible to achieve this with just Data.List and Prelude functions:
fun1 f = map f . transpose
To do this, I want to recursively apply <*> like
foldx (h:w) = h <*> foldx w
foldx (w:[]) = w
but it seems impossible to make <*> recursive.
I think you're getting confused over left- vs. right-associativity. danidiaz reformulates this in terms of foldr (<*>), which is quite useful for this analysis. The documentation gives a useful definition of foldr in terms of expansion:
foldr f z [x1, x2, ..., xn] == x1 `f` (x2 `f` ... (xn `f` z) ...)
So applying that to your case:
foldr (<*>) z [x1, x2, ..., xn] == x1 <*> (x2 <*> ... (xn <*> z) ...)
Note the parens. <*> is left-associative, so the foldr expansion is different from:
x1 <*> x2 <*> ... <*> xn <*> z == ((... (x1 <*> x2) <*> ...) <*> xn) <*> z
Let's think also a bit more about what foldr (<*>) means. Another way of thinking of this is to rewrite it just slightly:
flip (foldr (<*>)) :: Applicative f :: [f (a -> a)] -> f a -> f a
Types of the form (a -> a) are often called endomorphisms, and they form a monoid, with composition as the operation and id as the identity. There's a newtype wrapper in Data.Monoid for these:
newtype Endo a = Endo { appEndo :: a -> a }
instance Monoid (Endo a) where
mempty = id
mappend = (.)
This gives us yet another way to think of foldr (<*>), by formulating it in terms of Endo:
toEndo :: Applicative f => f (a -> a) -> Endo (f a)
toEndo ff = Endo (ff <*>)
And then what foldr (<*>) does, basically, is reduce this monoid:
foldrStar :: Applicative f => [f (a -> a)] -> Endo (f a)
foldrStar fs = mconcat $ map toMonoid fs
what you have is equivalent to zipWith3 (\x y z -> x*y+z) [4,7] [6,9] [5,10].
it's impossible to foldl the <*> (and you do need foldl as <*> associates to the left) because foldl :: (a -> b -> a) -> a -> [b] -> a i.e. it's the same a in a -> b -> a, but when you apply your ternary function on first list of numbers, you get a list of binary functions, and then unary functions at the next step, and only finally, numbers (all different types, then):
>> let xs = map ZipList [[4,7],[6,9],[5,10]]
>> getZipList $ pure (\x y z -> x*y+z) <*> (xs!!0) <*> (xs!!1) <*> (xs!!2)
[29,73]
>> foldl (<*>) (pure (\x y z -> x*y+z)) xs
<interactive>:1:6:
Occurs check: cannot construct the infinite type: b = a -> b
Expected type: f (a -> b)
Inferred type: f b
In the first argument of `foldl', namely `(<*>)'
In the expression: foldl (<*>) (pure (\ x y z -> x * y + z)) xs
>> :t foldl
foldl :: ( a -> b -> a ) -> a -> [b] -> a
>> :t (<*>)
(<*>) :: (Applicative f) => f (a -> b) -> f a -> f b -- f (a -> b) = f b
The answer by chi addresses this, but the arity is fixed (for a particular code). In effect, what that answer really does is defining (a restricted version of) zipWithN (well, here, when used with the ZipList applicative - obviously, it works with any applicative in general) for any N (but just for the a -> a -> a -> ... -> a type of functions), whereas e.g.
zipWith7 :: (a -> b -> c -> d -> e -> f -> g -> h) ->
[a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [g] -> [h]
(in other words, zipWith3 (,,) [10,11] ([20,21]::[Integer]) ([30,31]::[Int]) works).

Resources