Get wrong result by substituting through value - haskell

I have following function:
meh :: (Functor m, Monad m) => [a] -> (a -> m b) -> m [b]
meh [] _ = return []
meh (x:xs) f = do
x' <- f x
fmap ((:) x') (meh xs f)
then I try it out in prelude as follow and I've got:
*ExerciseMonad Control.Monad> meh [3,4,5] (\x -> Just x)
Just [3,4,5]
But I do expect [Just 3, Just 4, Just 5].
To find out, what went wrong, I did substitution:
meh [3,4,5] (\x -> Just x) = Just [3,4,5]
meh (3:[4,5])] (\x -> Just x) =
Just 3 <- (\3 -> Just 3)
fmap ((:) (Just 3)) (meh [4,5] (\x -> Just x))
meh (4:[5])] (\x -> Just x) =
Just 4 <- (\4 -> Just 4)
fmap ((:) (Just 4)) (meh [5] (\x -> Just x))
meh ([5])] (\x -> Just x) =
Just 5 <- (\5 -> Just 5]
fmap ((:) (Just 5)) (meh [] (\x -> Just x))
meh [] _ = return []
--all the way back
meh ([5])] (\x -> Just x) = fmap ((:) (Just 5)) []
meh (4:[5])] (\x -> Just x) = fmap ((:) (Just 4)) [Just 5] <- result [Just 4, Just 5]
meh (3:[4,5])] (\x -> Just x) = fmap ((:) (Just 3)) [Just 4, Just 5] <- result [Just 4, Just 5]
meh [3,4,5] (\x -> Just x) = [Just 3,Just 4, Just 5]
As you can see, the substitution does not match to the right result:
Just [3,4,5] != [Just 3,Just 4, Just 5]
My question, what did I wrong with the substitution? That I've got the wrong result?

According to the type, everything works fine
meh :: (Functor m, Monad m) => [a] -> (a -> m b) -> m [b]
If you're expecting [Just 3, Just 4, Just 5] you might need something like:
meh :: (Functor m, Monad m) => [a] -> (a -> m b) -> [m b]
Or just
meh :: (Functor m) => [a] -> (a -> m b) -> [m b]
Because you don't need the monad instance if you're not going to join values.
meh' :: (Functor m, Monad m) => [a] -> (a -> m b) -> [m b]
meh' [] _ = []
meh' (x:xs) f =
(f x) : (meh' xs f)
Calling meh' [3,4,5] Just returns [Just 3, Just 4, Just 5]
Calling meh [3,4,5] Just returns Just [3,4,5]
Talking about a substitution (starting from the empty list):
meh [] _ = Just [], because meh [] _ = return [] returns an empty list wrapped into a monadic structure (in this case Maybe monad)
meh (5:[]) (\x -> Just x) = do
x' <- (\x -> Just x) 5
fmap ((:) x') (meh [] (\x -> Just x))
In this step x' <- (x -> Just x) 5 binds x' to 5. That's why meh [5] Just transforms into fmap ((:) 5) (Just []) that equals Just [5], rather than fmap ((:) (Just 5)) [] which indeed equals [Just 5]

As I commented before your type signature is wrong:
If you check the type for [Just 1, Just 2, ...] would be like [m b] not m [].
Also, you cant simplify your function to:
meh :: (Functor m, Monad m) => [a] -> (a -> m b) -> [m b]
meh l f = fmap f l
Here you have a life example
Your substitution is wrong on this step:
x' <- f x
Since you are working inside a monad you are binding (with <-) to x' the Value inside
the monad (Just in this case) so 'x'' will be 3 (4, 5, ...) not Just 3

Related

Find two elements in a list, order them by their occurence

I'm writing a function that takes a list and two elements that can possibly be contained in the list. The function should return the two elements in a structure that sorts them by their occurrence in the list.
So, for number we'd have something like this:
xs = [4,6,3,2,1,8]
f (3,1) --> (Just 3, Just 1)
f (1,3) --> (Just 3, Just 1)
f (9,1) --> (Just 1, Nothing)
f (9,9) --> (Nothing, Nothing)
and so on..
I used tuples up there since I'm actually only interested in those two values instead of an arbitrary number. But if there are reasons, modeling it as list would be ok as well.
Anyways, here's the function I came up with:
f :: Eq a => [a] -> (a, a) -> (Maybe a, Maybe a)
f xs (a, b) = foldl g (Nothing, Nothing) xs where
g (Nothing, Nothing) x | x == a = (Just a, Nothing)
g (Nothing, Nothing) x | x == b = (Just b, Nothing)
g (Just a', Nothing) x | a' == a && x == b = (Just a, Just b)
g (Just b', Nothing) x | b' == b && x == a = (Just b, Just a)
g m x = m
Its working, but I think it's quite a lot of pattern matching in there, it's sort of error-prone. So, does anybody have a better abstraction for the problem?
If you want to decrease number of pattern matchings then it's better to never pass pair (Maybe a, Maybe a) recursively and pattern match on it. You can just split your function into two recursive functions where first functions finds first element and calls second function with the other. This can be done like this:
f :: Eq a => (a, a) -> [a] -> (Maybe a, Maybe a)
f (a, b) = goFirst
where
goFirst [] = (Nothing, Nothing)
goFirst (x:xs)
| x == a = (Just a, goSecond b xs)
| x == b = (Just b, goSecond a xs)
| otherwise = goFirst xs
goSecond _ [] = Nothing
goSecond y (x:xs)
| x == y = Just y
| otherwise = goSecond y xs
This is not so short and elegant as you may want but it's readable, fast (I want to add that you should never ever use foldl function) and less error-prone.
If you're looking for some abstractions, you may look at First monoid with pair monoid. Using monoid instance for First data type you can start with something like this:
import Data.Bifunctor (bimap)
import Data.Monoid (First (..), mconcat)
g :: Eq a => (a, a) -> [a] -> (Maybe a, Maybe a)
g (a, b) = bimap getFirst getFirst . mconcat . map fMapper
where
fMapper x
| x == a = (First (Just a), mempty)
| x == b = (mempty, First (Just b))
| otherwise = mempty
Though this function doesn't do exactly what you want:
ghci> let xs = [4,6,3,2,1,8]
ghci> g (3, 1) xs
(Just 3,Just 1)
ghci> g (1, 3) xs
(Just 1,Just 3)
To achieve initial goal with this approach you can add indices to each element and then sort pairs under First by indices but this solution is scary and ugly. Using First monoid is tempting but I don't know how it can be used here elegantly.
But you can combine ideas from first and second solutions:
import Data.Bool (bool)
import Data.Monoid (First (..))
h :: Eq a => (a, a) -> [a] -> (Maybe a, Maybe a)
h (a, b) = goFirst
where
goFirst [] = (Nothing, Nothing)
goFirst (x:xs)
| x == a = (Just a, goSecond b xs)
| x == b = (Just b, goSecond a xs)
| otherwise = goFirst xs
goSecond y = getFirst . foldMap (bool mempty (First (Just y)) . (== y))
Here’s one possible solution with lists, of the following type:
f :: Eq a => [a] -> [a] -> [Maybe a]
I’ll call the list to be searched the haystack and the elements to search for the needles. First, we can search the haystack for each needle and return a pair of the value and the index where it was found, if any, using findIndex:
findIndices needles haystack =
[ (needle, findIndex (== needle) haystack)
| needle <- needles
]
findIndices [1, 3] xs == [(1, Just 4), (3, Just 2)]
(Note that this always uses the index of the first occurrence—I’m not sure if that’s what you want. You can extend this into a fold that removes each occurrence as it’s found.)
Then sort this list by the index:
sortBy (comparing snd) [(1, Just 4), (3, Just 2)]
==
[(3, Just 2), (1, Just 4)]
And finally extract the value for each index that was actually present, using (<$) :: Functor f => a -> f b -> f a:
[value <$ mIndex | (value, mIndex) <- [(3, Just 2), (1, Just 4)]]
==
[Just 3, Just 1]
(x <$ f is equivalent to const x <$> f.)
But when we try this on an input where some elements aren’t found, we get the wrong result, where the Nothings come at the beginning rather than the end:
findIndices [9, 1] xs == [(9, Nothing), (1, Just 4)]
sortBy (comparing snd) [(9, Nothing), (1, Just 4)]
==
[(9, Nothing), (1, Just 4)]
This is because Nothing is considered less than any Just value. Since we want the opposite, we can reverse the sort order of the Maybe using the Down newtype from Data.Ord, by passing Down . snd instead of snd as the comparator:
sortBy (comparing (Down . snd)) [(9, Nothing), (1, Just 4)]
==
[(1, Just 4), (9, Nothing)]
But this also reverses the sort order of the indices themselves, which we don’t want:
sortBy (comparing (Down . snd)) [(1, Just 4), (3, Just 2)]
==
[(1, Just 4), (3, Just 2)]
So we can just add another Down around the indices:
findIndices needles haystack =
[ (needle, Down <$> findIndex (== needle) haystack)
| needle <- needles
]
sortBy (comparing Down) [Just (Down 2), Nothing, Just (Down 1)]
==
[Just (Down 1), Just (Down 2), Nothing]
sortBy (comparing (Down . snd))
[(1, Down (Just 4)), (3, Down (Just 2))]
==
[(3, Down (Just 2)), (1, Down (Just 4))]
And finally put it all together:
f :: (Eq a) => [a] -> [a] -> [Maybe a]
f needles haystack =
[ value <$ index
| (value, index) <- sortBy (comparing (Down . snd))
[ (needle, Down <$> findIndex (== needle) haystack)
| needle <- needles
]
]
f [1, 3] xs == [Just 3, Just 1]
f [3, 1] xs == [Just 3, Just 1]
f [1, 9] xs == [Just 1, Nothing]
f [9, 9] xs == [Nothing, Nothing]
Or, without list comprehensions and with shorter names:
f :: (Eq a) => [a] -> [a] -> [Maybe a]
f ns hs
= map (\ (v, i) -> v <$ i)
$ sortBy (comparing (Down . snd))
$ map (\ n -> (n, Down <$> findIndex (== n) hs)) ns
\ (v, i) -> v <$ i can also be written as uncurry (<$), but that might be a bit cryptic if you’re not accustomed to point-free style. In addition, if you don’t care about the Nothings, you can use mapMaybe instead of map, changing the return type from [Maybe a] to just [a].
I don't know how much better you will think these are, but you can do some things making more use of list functions.
I initially thought of filtering out the irrelevant
items first, and grouping:
f :: Eq a => [a] -> (a,a) -> (Maybe a, Maybe a)
f xs (a, b) =
case (map head . group . filter (`elem` [a,b])) xs of
[] -> (Nothing, Nothing)
[c] -> (Just c, Nothing)
(c:d:_) -> (Just c, Just d)
But this doesn't do the same as your implementation on, for example,
f [8,9,9] (9,9), so you'd need to special-case that if it's a case
you care about.
Another way is with dropWhile:
f' :: Eq a => [a] -> (a,a) -> (Maybe a, Maybe a)
f' xs (a, b) =
case dropWhile (`notElem` [a, b]) xs of
[] -> (Nothing, Nothing)
(y:ys) -> (Just y, next)
where
next = case dropWhile (/=other) ys of
[] -> Nothing
(z:_) -> Just z
other = if y == a then b else a
And the inner case is really just a find so it can be simplified a
little more:
f'' :: Eq a => [a] -> (a,a) -> (Maybe a, Maybe a)
f'' xs (a, b) =
case dropWhile (`notElem` [a, b]) xs of
[] -> (Nothing, Nothing)
(y:ys) -> (Just y, find (==other) ys)
where
other = if y == a then b else a
Note: these functions never return a result of the form (Nothing, Just _). This suggests that a return type of Maybe (a, Maybe a)
might be better. Or a custom type like None | One a | Two a a.
Alternatively, we could generalize to a list version which allows as
many target values as you like. It makes a nice unfold:
f''' :: Eq a => [a] -> [a] -> [a]
f''' xs ts = unfoldr g (xs, ts)
where
g (ys, us) = case dropWhile (`notElem` us) ys of
[] -> Nothing
(z:zs) -> Just (z, (zs, delete z us))
Which works like this:
λ> f''' [4,2,5,3,1] [1,2,3]
[2,3,1]
λ> f''' [4,2,5,3,1] [1,2,6]
[2,1]
λ> f''' [7,9,8,9] [9,9]
[9,9]
I'm almost reinventing intersect here but not quite. It has the behaviour we want of preserving the order from the first list, but it isn't the same on duplicates - e.g. intersect [4,2,2,5] [1,2] is [2,2].

Does Haskell have a greedy zip (one preserving all elements)?

I'm not exactly sure if my nomenclature is correct here, but I was wondering if there was a zip function in Haskell that was greedy. This means that if I had
a = [1, 2, 3]
b = [4, 5]
zip' a b
#=> [(Just 1, Just 4),(Just 2, Just 5),(Just 3, Nothing)]
...where zip' is the greedy zip function, it would return a list of tuples the length of the longer list, and where the longer list has an element, but the shorter list does not Nothing is put in the respective tuple position. I am not asking how to write this, but instead was wondering if this exists as a built-in.
Here is my implementation (which is probably not great)
zip' :: [a] -> [b] -> [(Maybe a, Maybe b)]
zip' (a:xs) [] = (Just a, Nothing) : zip' xs []
zip' [] (b:ys) = (Nothing, Just b) : zip' [] ys
zip' [] _ = []
zip' (a:xs) (b:ys) = (Just a, Just b) : zip' xs ys
A greedy zip can be neatly expressed through a non-exclusive disjunction type (as opposed to Either, which is an exclusive disjunction). Two popular packages offer that. One is the minimalist, dependency-free data-or:
GHCi> import Data.Or
GHCi> :t zipOr
zipOr :: [a] -> [b] -> [Or a b]
GHCi> zipOr [1, 2, 3] [4, 5]
[Both 1 4,Both 2 5,Fst 3]
The other is these, which comes with lots of bells and whistles:
GHCi> import Data.These
GHCi> import Data.Align
GHCi> :t align
align :: Align f => f a -> f b -> f (These a b)
GHCi> align [1, 2, 3] [4, 5]
[These 1 4,These 2 5,This 3]
I believe Or a b and These a b express your intent better than (Maybe a, Maybe b) (the latter type includes (Nothing, Nothing), which a greedy zip will never produce). Still, you can express your zip' using either zipOrWith from Data.Or...
import Data.Or
zip' :: [a] -> [b] -> [(Maybe a, Maybe b)]
zip' = zipOrWith $ \xy -> case xy of
Both x y -> (Just x, Just y)
Fst x -> (Just x, Nothing)
Snd y -> (Nothing, Just y)
... or alignWith from Data.Align:
import Data.These
import Data.Align
zip' :: Align f => f a -> f b -> f (Maybe a, Maybe b)
zip' = alignWith $ \xy -> case xy of
These x y -> (Just x, Just y)
This x -> (Just x, Nothing)
That y -> (Nothing, Just y)
Data.Align, in fact, provides your function under the name of padZip.

Haskell recursive function to apply different functions to even and odd numbered index

I have been struggling with following problem for sometime. I spent many hours on the internet to find a viable algorithm in Haskell using recursive functions only but no success.
Define a recursive function funkyMap :: (a -> b) -> (a -> b) -> [a] -> [b] that takes as arguments two functions f and g and a list xs, and applies f to all elements at even positions ([0, 2..]) in xs and g to all elements at odd positions ([1, 3..]) in xs.
Example: funkyMap (+10) (+100) [1, 2, 3, 4, 5] = [(+10) 1, (+100) 2, (+10) 3, (+100) 4, (+10) 5].
To above problem, I attempted following solution, but HUGS give me compilation error "unification would give infinite type".
mapEven :: (a->a) -> [a] -> [a]
mapEven f [] = []
mapEven f (x:xs) = f x : mapOdd f xs
mapOdd :: (a->a) -> [a] -> [a]
mapOdd g [] = []
mapOdd g (x:xs) = x : mapEven g xs
funkyMap :: (a -> b) -> (a -> b) -> [a] -> [b]
funkyMap f g [] = []
funkyMap f g (x:xs) = (mapEven f x) ++ (mapOdd g xs)
Please suggest an alternate working solution.
Thanks
This line has a problem:
funkyMap f g (x:xs) = (mapEven f x) ++ (mapOdd g xs)
x is an element of the list (ie type a), while xs is another list (type [a]). But you are treating them the same. The error you are getting is because the only way to make sense of a list and an element being the same type is if it's a list of lists of lists of lists of lists...
By God's mercy, I got some inspiration and I seemed to have cracked this problem.
Please review the following solution:
h1 p q [] = []
h1 p q ((cnt, val) : xs) = (if odd cnt then (q val) else (p val) ) : h1 p q xs
funkyMap f g xs = h1 f g ( zip [0..] xs)
If I try funkyMap (+10) (+100) [1, 2, 3, 4, 5] I get [11,102,13,104,15] which is expected.
Also funkyMap (+100) (+2) [1] gives
[101]
and funkyMap (+100) (+2) [] gives
[]
Please review this solution and let me know your feedback.
Thanks

Haskell Control.Arrow: trying to write a filterA function

I am trying to write a filterA :: (ArrowChoice arr) => arr a Bool -> arr [a] [a] function that removes every element from a list for which f :: arr a Bool returns False. This is what I have so far
listcase [] = Left ()
listcase (x:xs) = Right (x, xs)
filterA f = arr listcase >>>
arr (const []) ||| (first (f &&& arr id) >>>
arr (\((b,x),xs) -> if b then
x : (filterA f xs)
else filterA f xs
))
Now this works when testing it with (->) a Arrows, like this:
λ> filterA (== 8) [8,9]
[8]
It doesn't work however, for Kleisli Arrows like
λ> runKleisli (Kleisli $ filterA (== 8)) (return [8,9] :: [IO Int])
<interactive>:160:47:
Couldn't match expected type `IO Int' with actual type `[t0]'
In the first argument of `return', namely `[8, 9]'
In the second argument of `runKleisli', namely
`(return [8, 9] :: [IO Int])'
In the expression:
runKleisli (Kleisli $ filterA (== 8)) (return [8, 9] :: [IO Int])
And when adding a type signature filterA :: (Arrow arr) => arr a Bool -> arr [a] [a] or filterA :: (ArrowChoice arr) => arr a Bool -> arr [a] [a], it throws this error:
arrows.hs:11:22:
Could not deduce (arr ~ (->))
from the context (Arrow arr)
bound by the type signature for
filterA :: Arrow arr => arr a Bool -> arr [a] [a]
at arrows.hs:7:12-51
`arr' is a rigid type variable bound by
the type signature for
filterA :: Arrow arr => arr a Bool -> arr [a] [a]
at arrows.hs:7:12
Expected type: [a] -> [a]
Actual type: arr [a] [a]
The function `filterA' is applied to two arguments,
but its type `arr a Bool -> arr [a] [a]' has only one
In the second argument of `(:)', namely `(filterA f xs)'
In the expression: x : (filterA f xs)
I do not understand why. Did I miss something?
Edit:
#jaket's comment worked (I guess that was kinda stupid) but the type signature still doesn't match.
I also updated the code to be more compact (still getting the same error though)
filterA f = arr listcase >>>
arr (const []) ||| (arr toEither >>>
(filterA f) ||| (second (filterA f) >>> arr uncurry (:)))
where toEither (x, xs) = if f x then Right (x, xs) else Left xs
GHC infers the type as filterA :: (a -> Bool) -> [a] -> [a], by the way.
Your problem is that you're trying to do the recursion inside the function definition that you wrap with arr, and you call filterA f as though it were a function in this line:
x : (filterA f xs)
That only works if the arrow type is (->), which is what one of the type errors is telling you.
Instead, you need to do the recursion at the arrow level, as in:
listcase :: [t] -> Either () (t, [t])
listcase [] = Left ()
listcase (x:xs) = Right (x, xs)
filterA :: (ArrowChoice arr) => arr a Bool -> arr [a] [a]
filterA f = listcase ^>>
arr (const []) ||| ((f &&& arr id) *** filterA f >>^
(\((b, x), xs) -> if b then x:xs else xs))
(which does compile)
Your runKleisli example is a bit confused, you meant to say:
runKleisli (filterA $ Kleisli $ return . (== 8)) [8,9]
or
runKleisli (filterA $ arr (== 8)) [8,9] :: IO [Int]
That's straight from looking at the types.
Just to complement the other answers: Using the Arrow syntax (see also the GHC manual, Chapter Arrow notation) you can write function somewhat more readable:
{-# LANGUAGE Arrows #-}
import Control.Arrow
filterA :: (ArrowChoice arr) => arr a Bool -> arr [a] [a]
filterA f = farr
where
farr = proc xs ->
case xs of
[] -> returnA -< []
(x:xs') -> do
b <- f -< x
ys' <- farr -< xs'
returnA -< if b then x : ys' else ys'
The result translated internally to the arrow notation will be probably somewhat less concise, but hopefully the compiler will optimize for you.
As mentioned in my comment:
runKleisli (Kleisli $ filterA (== 8)) [8, 9]
Next you need to lift f :: a -> b into an arrow arr a b
(first (arr f &&& arr id)
^^^
in your function:
filterA :: ArrowChoice arr => (a -> Bool) -> arr [a] [a]
filterA f = arr listcase >>>
arr (const []) ||| (first (f &&& arr id) >>>
arr (\((b,x),xs) -> if b then
x : (filterA f xs)
else filterA f xs
))

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

Resources