"generalised" scanl - haskell

I am trying to write a sort of scanl like function of type:
general_scanl' :: (a->b->a)->(a->b->[c])->a->[b]->[c]
The function is intended to output the same as the following two monstrosities:
general_scanl' f g x y = snd $ foldl' (\(p,q) r -> (f p r,q ++ g p r)) (x,[]) y
or,
general_scanl' f g x y = concat $ zipWith g (scanl f x y) y
The disadvantage of the first definition is that it contains a handwritten lambda.
The disadvantage of the second definition is that it accumulates a list of lists (scanl f x y) which isn't necessary...
My question: is there a cleaner way to define this function?
Many thanks,

You have
Prelude> let general_scanl2 f g z xs = concat $ zipWith g (scanl f z xs) xs
-- :: [a]
Prelude> :t general_scanl2
general_scanl2 :: (a -> b -> a) -- f
-> (a -> b -> [c]) -- g
-> a -- z
-> [b] -- xs
-> [c]
Prelude Data.List> :t mapAccumL
mapAccumL :: (a -> b -> (a, y)) -> a -> [b] -> (a, [y])
So, another way to write this seems to be
import Data.List
g_scanl3 :: (a -> b -> a) -> (a -> b -> [c]) -> a -> [b] -> [c]
g_scanl3 f g z xs = concat . snd $
mapAccumL (\a b-> (f a b, g a b)) z xs

Related

A map function that operates on pairs

I am trying to write a function which is like map, but which takes functions of type (a, a) -> b as its first argument. However, I get the error
<interactive>:474:11: error:
Parse error in pattern: \ (x, y) -> f x y
with the following code:
Prelude> :{
Prelude| mappairs :: ((a, a) -> b) -> [a] -> [b]
Prelude| mappairs (\(x,y) -> f x y) xs = foldr (\(x, y) acc -> (f x y : acc)) [] xs
Prelude| :}
What is the problem?
The pattern:
\(x,y) -> f x y
in the clause:
mappairs (\(x,y) -> f x y) xs = foldr (\(x, y) acc -> (f x y : acc)) [] xs
is indeed not valid, since (->) is not a data constructor.
You can however use zipWith :: (a -> b -> c) -> [a] -> [b] -> [c] here:
mappairs :: ((a, a) -> b) -> [a] -> [b]
mappairs _ [] = []
mappairs f xa#(_:xs) = zipWith (curry f) xa xs
For example:
> mappairs (\(x,y) -> x+y) [1,4,2,5]
[5,6,7]
But it looks more "Haskell-ish" to omit the tuples, and thus use a function directly:
mappairs :: (a -> a -> b) -> [a] -> [b]
mappairs _ [] = []
mappairs f xa#(_:xs) = zipWith f xa xs

Why does zipWith.zipWith work?

I am implementing a function combine :: [[a]] -> [[b]] -> (a -> b -> c) -> [[c]] which given two 2D lists, applies a given function f :: a -> b -> c to the entries of the 2D list. In other words:
[[a, b, c], [[r, s, t], [[f a r, f b s, f c t],
combine [d, e, g], [u, v, w], f = [f d u, f e v, f g w],
[h, i, j]] [x, y, z]] [f h x, f i y, f j z]]
Now I suspect that combine = zipWith . zipWith, because I have tried it out and it is giving me the intended results, e.g.
(zipWith . zipWith) (\x y -> x+y) [[1,2,3],[4,5,6]] [[7,8,9],[10,11,12]]
gives the expected result [[8,10,12],[14,16,18]], but I cannot understand why this works, because I don't understand how the type of zipWith . zipWith turns out to be (a -> b -> c) -> [[a]] -> [[b]] -> [[c]].
Is (.) here still carrying out the usual function composition? If so, can you explain how this applies to zipWith?
To infer the type of an expression such as zipWith . zipWith, you can simulate the unification in your head the following way.
The first zipWith has type (a -> b -> c) -> ([a] -> [b] -> [c]), the second (s -> t -> u) -> ([s] -> [t] -> [u]) and (.) has type (m -> n) -> (o -> m) -> (o -> n).
For it to typecheck, you need:
m = (a -> b -> c)
n = ([a] -> [b] -> [c])
o = (s -> t -> u)
m = ([s] -> [t] -> [u]) => a = [s], b = [t], c = [u] because of the first constraint
Then the returned type is o -> n which is (s -> t -> u) -> ([a] -> [b] -> [c]) from the constraints and going one step further (s -> t -> u) -> ([[s]] -> [[t]] -> [[u]]).
Another way of seeing it is that lists with the zipping operation form an Applicative, and the composition (nesting) of Applicatives is still Applicative:
λ import Control.Applicative
λ import Data.Functor.Compose
λ let l1 = ZipList [ZipList [1,2,3], ZipList [4,5,6]]
λ let l2 = ZipList [ZipList [7,8,9], ZipList [10,11,12]]
λ getCompose $ (+) <$> Compose l1 <*> Compose l2
ZipList {getZipList = [ZipList {getZipList = [8,10,12]},
ZipList {getZipList = [14,16,18]}]}
The ZipList newtype is required because "bare" lists have a different Applicative instance, which forms all combinations instead of zipping.
Yes, . is the normal function composition operator:
Prelude> :type (.)
(.) :: (b -> c) -> (a -> b) -> a -> c
One way to look at it is that it takes an a value, first calls the a -> b function, and then uses the return value of that function to call the b -> c function. The result is a c value.
Another way to look at (zipWith . zipWith), then, is to perform an eta expansion:
Prelude> :type (zipWith . zipWith)
(zipWith . zipWith) :: (a -> b -> c) -> [[a]] -> [[b]] -> [[c]]
Prelude> :t (\x -> zipWith $ zipWith x)
(\x -> zipWith $ zipWith x)
:: (a -> b -> c) -> [[a]] -> [[b]] -> [[c]]
Prelude> :t (\x -> zipWith (zipWith x))
(\x -> zipWith (zipWith x))
:: (a -> b -> c) -> [[a]] -> [[b]] -> [[c]]
The type of zipWith itself:
Prelude> :type zipWith
zipWith :: (a -> b -> c) -> [a] -> [b] -> [c]
So, in the above lambda expression, x must be (a -> b -> c), and hence zipWith x must have the type [a] -> [b] -> [c].
The outer zipWith also needs a function (a1 -> b1 -> c1), which matches zipWith x if a1 is [a], b1 is [b], and c1 is [c].
So, by replacement, zipWith (zipWith x) must have the type [[a]] -> [[b]] -> [[c]], and therefore the type of the lambda expression is (a -> b -> c) -> [[a]] -> [[b]] -> [[c]].

map function using foldl or foldr in Haskell

I am writing a function my_map which takes a unary function and a list and returns the list resulting from mapping the function over all elements of the input list.
Main> my_map (^3) [1..5]
[1,8,27,64,125]
I tried it like this:
my_map :: (a -> b) -> [a] -> [b]
my_map f [] = []
my_map f (x:xs) = foldr (\x xs -> (f x):xs) [] xs
But after running above, I get only [8,27,64,125]. the first number 1 is not displaying in output.
Can anybody help me?
You are using the (x:xs) pattern in your arguments, but when you apply the fold, you only apply it to the xs part, which means your first element i.e. the one that x represents never gets processed. You need to change it to this:
my_map :: (a -> b) -> [a] -> [b]
my_map f xs = foldr (\y ys -> (f y):ys) [] xs
Since you are using foldr, you do not need to explicitly handle the empty list case. Moreoever, you do not need to specify the list in (x:xs) format.
Finally, my own preference is to avoid using the same name for function inputs and any helper functions or expressions in the function definition.That is why, I have used xs for the input list and y and ys for the parameters passed to the lambda.
"shree.pat18" is perfectly right, and also the comments are valuable. I learned a lot from that. Just make it better visible, and to explain the alternatives...
Answer
-- The problem is here ....................... vv
my_map f (x:xs) = foldr (\x xs -> (f x):xs) [] xs
-- --
The remaining part xs is aplied to foldr.
To fix just this, apply the whole list. This can be done by placing xx# before (x:xs). By that, the whole list is bound to xx.
-- vvv ........... see here ............... vv
my_map f xx#(x:xs) = foldr (\x xs -> (f x):xs) [] xx
-- --- --
Recommended impovement
Note: foldr can already deal with [] as input. Hence, my_map f [] = [] is not needed. But foldr would not be called when you apply [] to my_map. To get rid of my_map f [] = [], you need to remove the pattern matching, because (x:xs) matches only to lists with at least one element.
main :: IO ()
main = print $ my_map (^(3 :: Int)) ([1..5] :: [Integer])
my_map :: (a -> b) -> [a] -> [b]
my_map f xx = foldr (\x xs -> (f x):xs) [] xx
The answer is complete here. The rest below is for pleasure.
Further reductions
Simple expression instead of lambda expression
If you want to reduce the lambda expression (\x xs -> (f x):xs), as suggested by "Aadit M Shah"...
(:) is equal to (\x xs -> x:xs), because : is an operator and its function is (:)
. can be used to combine the function f with (:), hence (\x xs -> (f x):xs) is equal to ((:) . f)
main :: IO ()
main = print $ my_map (^(3 :: Int)) ([] :: [Integer])
my_map :: (a -> b) -> [a] -> [b]
my_map f xx = foldr ((:) . f) [] xx
Currying
A function of the form
-- v v
f a b c = .... c
can be reduced to
-- v v
f a b = ....
and a function of the form
-- v v v v
f a b c = .... b c
can be reduced to
-- v v v v
f a = ....
and so on, by currying.
Hence, my_map f xx = foldr ((:) . f) [] xx equals my_map f = foldr ((:) . f) [].
Combination and flip
flip flips the first two parameters.
Example, the following functions are equal:
f' a b c = (\c' b' a' -> ((a' - b') / c')) b a c
f'' a b c = flip (\c' b' a' -> ((a' - b') / c')) a b c
f''' = flip (\c' b' a' -> ((a' - b') / c'))
Hence, the following code works as well.
main :: IO ()
main = print $ my_map (^(3 :: Int)) ([1..5] :: [Integer])
my_map :: (a -> b) -> [a] -> [b]
my_map f = flip foldr [] ((:) . f)
But we can not get rid of f as above, because of the form in the expression flip foldr [] ((:) . f).
If we remove f ...
`((:) . f)` has type `a -> [a] -> [a]
-- v
`((:) . )` has type `(a -> a) -> a -> [a] -> [a]`
and
`flip foldr []` has type `Foldable t => (a1 -> [a2] -> [a2]) -> t a1 -> [a2]`
hence
f :: a -> a
is passed to
((:) . )
becomming
a -> [a] -> [a]
is passed to
flip foldr []
becomming
t a1 -> [a2]
Hence,
main :: IO ()
main = print $ my_map (^(3 :: Int)) ([1..5] :: [Integer])
my_map :: (a -> b) -> [a] -> [b]
my_map = flip foldr [] . ((:) . )
works nicely.

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

How does the expression `ap zip tail` work

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 )

Resources