How to use foldr to add variables to each other in a list? - list

When given a list [x0, x1, x2, . . . , xn−1], the function
should return the list [y0, y1, y2, . . . , yn−1] where y0 = x0, y1 = x0 + x1, ...
So if you had [1,2,3] as input, you would get [1,3,6] as output
I don't completely understand foldr, so maybe if I could get some help in trying to figure out how to change that last line to get the right answer.
scan :: [Integer] -> [Integer]
scan [] = []
scan [x] = [x]
scan (x:xs) = x : foldr (/y -> y (+) x) 0 (scan xs)
My initial solution (that works) uses the map function.
scan :: [Integer] -> [Integer]
scan [] = []
scan [x] = [x]
scan (x:xs) = x : map (+x) (scan xs)

EDIT, I added this first section to better address your two implementations.
First, addressing your issue with your implementation using foldr, here are a few remarks:
Lambdas start with a backslash in Haskell, not a slash. That's because backslashes kind of look like the lambda greek letter (λ).
Functions named using only special characters, like +, are infix by default. If you use parens around them, it turns them into prefix functions:
$> (+) 1 5
$> 6
The function passed to foldr takes two argument, whereas you're only supplying one in your lambda. If you really want to ignore the second one, you can use a _ instead of binding it to a variable (\x _ -> x).
I think this you're going down a rabbit hole with this implementation. See the discussion below for my take on the right way to tackle this issue.
Note: It is possible to implement map using foldr (source), that's one way you could use foldr in your working (second) implementation.
Implementing this with foldr is not optimal, since it folds, as the name implies, from the right:
foldr1 (+) [1..5]
--is equivalent to:
(1+(2+(3+(4+5))))
As you can see, the summing operation is done starting from the tail of the list, which is not what you're looking for. To make this work, you would have to "cheat", and reverse your list twice, once before folding it and once after:
scan = tail . reverse . foldr step [0] . reverse where
step e acc#(a:_) = (e + a) : acc
You can make this better using a left fold, which folds from the left:
foldl1 (+) [1..5]
--is equivalent to:
((((1+2)+3)+4)+5)
This, however, still isn't ideal, because to keep the order of elements in your accumulator the same, you would have to use the ++ function, which amounts to quadratic time complexity in such a function. A compromise is to use the : function, but then you still have to reverse your accumulator list after the fold, which is only linear complexity:
scan' :: [Integer] -> [Integer]
scan' = tail . reverse . foldl step [0] where
step acc#(a:_) e = (e + a) : acc
This still isn't very good, since the reverse adds an extra computation. The ideal solution would therefore be to use scanl1, which, as a bonus, doesn't require you to give a starting value ([0] in the examples above):
scan'' :: [Integer] -> [Integer]
scan'' = scanl1 (+)
scanl1 is implemented in terms of scanl, which is defined roughly like this:
scanl f init list = init : (case list of
[] -> []
x:xs -> scanl f (f init x) xs)
You can therefore simply do:
$> scanl1 (+) [1..3]
$> [1,3,6]
As a final note, your scan function is unnecessarily specialized to Integer, as it only requires a Num constraint:
scan :: Num a => [a] -> [a]
This might even lead to an increase in performance, but that's where my abilities end, so I won't go any further :)

Related

Generate list of Ints in Haskell by adding Ints from a pattern list

I'm playing around with Haskell, mostly trying to learn some new techniques to solve problems. Without any real application in mind I came to think about an interesting thing I can't find a satisfying solution to. Maybe someone has any better ideas?
The problem:
Let's say we want to generate a list of Ints using a starting value and a list of Ints, representing the pattern of numbers to be added in the specified order. So the first value is given, then second value should be the starting value plus the first value in the list, the third that value plus the second value of the pattern, and so on. When the pattern ends, it should start over.
For example: Say we have a starting value v and a pattern [x,y], we'd like the list [v,v+x,v+x+y,v+2x+y,v+2x+2y, ...]. In other words, with a two-valued pattern, next value is created by alternatingly adding x and y to the number last calculated.
If the pattern is short enough (2-3 values?), one could generate separate lists:
[v,v,v,...]
[0,x,x,2x,2x,3x, ...]
[0,0,y,y,2y,2y,...]
and then zip them together with addition. However, as soon as the pattern is longer this gets pretty tedious. My best attempt at a solution would be something like this:
generateLstByPattern :: Int -> [Int] -> [Int]
generateLstByPattern v pattern = v : (recGen v pattern)
where
recGen :: Int -> [Int] -> [Int]
recGen lastN (x:[]) = (lastN + x) : (recGen (lastN + x) pattern)
recGen lastN (x:xs) = (lastN + x) : (recGen (lastN + x) xs)
It works as intended - but I have a feeling there is a bit more elegant Haskell solution somewhere (there almost always is!). What do you think? Maybe a cool list-comprehension? A higher-order function I've forgotten about?
Separate the concerns. First look a just a list to process once. Get that working, test it. Hint: “going through the list elements with some accumulator” is in general a good fit for a fold.
Then all that's left to is to repeat the list of inputs and feed it into the pass-once function. Conveniently, there's a standard function for that purpose. Just make sure your once-processor is lazy enough to handle the infinite list input.
What you describe is
foo :: Num a => a -> [a] -> [a]
foo v pattern = scanl (+) v (cycle pattern)
which would normally be written even as just
foo :: Num a => a -> [a] -> [a]
foo v = scanl (+) v . cycle
scanl (+) v xs is the standard way to calculate the partial sums of (v:xs), and cycle is the standard way to repeat a given list cyclically. This is what you describe.
This works for a pattern list of any positive length, as you wanted.
Your way of generating it is inventive, but it's almost too clever for its own good (i.e. it seems overly complicated). It can be expressed with some list comprehensions, as
foo v pat =
let -- the lists, as you describe them:
lists = repeat v :
[ replicate i 0 ++
[ y | x <- [p, p+p ..]
, y <- map (const x) pat ]
| (p,i) <- zip pat [1..] ]
in
-- OK, so what do we do with that? How do we zipWith
-- over an arbitrary amount of lists?
-- with a fold!
foldr (zipWith (+)) (repeat 0) lists
map (const x) pat is a "clever" way of writing replicate (length pat) x. It can be further shortened to x <$ pat since (<$) x xs == map (const x) xs by definition. It might seem obfuscated, until you've become accustomed to it, and then it seems clear and obvious. :)
Surprised noone's mentioned the silly way yet.
mylist x xs = x : zipWith (+) (mylist x xs) (cycle xs)
(If you squint a bit you can see the connection to scanl answer).
When it is about generating series my first approach would be iterate or unfoldr. iterate is for simple series and unfoldr is for those who carry kind of state but without using any State monad.
In this particular case I think unfoldr is ideal.
series :: Int -> [Int] -> [Int]
series s [x,y] = unfoldr (\(f,s) -> Just (f*x + s*y, (s+1,f))) (s,0)
λ> take 10 $ series 1 [1,1]
[1,2,3,4,5,6,7,8,9,10]
λ> take 10 $ series 3 [1,1]
[3,4,5,6,7,8,9,10,11,12]
λ> take 10 $ series 0 [1,2]
[0,1,3,4,6,7,9,10,12,13]
It is probably better to implement the lists separately, for example the list with x can be implement with:
xseq :: (Enum a, Num a) => a -> [a]
xseq x = 0 : ([x, x+x ..] >>= replicate 2)
Whereas the sequence for y can be implemented as:
yseq :: (Enum a, Num a) => a -> [a]
yseq y = [0,y ..] >>= replicate 2
Then you can use zipWith :: (a -> b -> c) -> [a] -> [b] -> [c] to add the two lists together and add v to it:
mylist :: (Enum a, Num a) => a -> a -> a -> [a]
mylist v x y = zipWith ((+) . (v +)) (xseq x) (yseq y)
So for v = 1, x = 2, and y = 3, we obtain:
Prelude> take 10 (mylist 1 2 3)
[1,3,6,8,11,13,16,18,21,23]
An alternative is to see as pattern that we each time first add x and then y. We thus can make an infinite list [(x+), (y+)], and use scanl :: (b -> a -> b) -> b -> [a] -> [b] to each time apply one of the functions and yield the intermediate result:
mylist :: Num a => a -> a -> a -> [a]
mylist v x y = scanl (flip ($)) v (cycle [(x+), (y+)])
this yields the same result:
Prelude> take 10 $ mylist 1 2 3
[1,3,6,8,11,13,16,18,21,23]
Now the only thing left to do is to generalize this to a list. So for example if the list of additions is given, then you can impelement this as:
mylist :: Num a => [a] -> [a]
mylist v xs = scanl (flip ($)) v (cycle (map (+) xs))
or for a list of functions:
mylist :: Num a => [a -> a] -> [a]
mylist v xs = scanl (flip ($)) v (cycle (xs))

Check if a list of lists has two or more identical elements

I need to write a function which checks if a list has two or more same elements and returns true or false.
For example [3,3,6,1] should return true, but [3,8] should return false.
Here is my code:
identical :: [Int] -> Bool
identical x = (\n-> filter (>= 2) n )( group x )
I know this is bad, and it does not work.
I wanted to group the list into list of lists, and if the length of a list is >= 2, then it is should return with true otherwise false.
Use any to get a Bool result.
any ( . . . ) ( group x )
Don’t forget to sort the list, group works on consecutive elements.
any ( . . . ) ( group ( sort x ) )
You can use (not . null . tail) for a predicate, as one of the options.
Just yesterday I posted a similar algorithm here. A possible way to go about it is,
generate the sequence of cumulative sets of elements
{}, {x0}, {x0,x1}, {x0,x1,x2} ...
pair the original sequence of elements with the cumulative sets
x0, x1 , x2 , x3 ...
{}, {x0}, {x0,x1}, {x0,x1,x2} ...
check repeated insertions, i.e.
xi such that xi ∈ {x0..xi-1}
This can be implemented for instance, via the functions below.
First we use scanl to iteratively add the elements of the list to a set, producing the cumulative sequence of these iterations.
sets :: [Int] -> [Set Int]
sets = scanl (\s x -> insert x s) empty
Then we zip the original list with this sequence, so each xi is paired with {x0...xi-1}.
elsets :: [Int] -> [(Int, Set Int)]
elsets xs = zip xs (sets xs)
Finally we use find to search for an element that is "about to be inserted" in a set which already contains it. The function find returns the pair element / set, and we pattern match to keep only the element, and return it.
result :: [Int] -> Maybe Int
result xs = do (x,_) <- find(\(y,s)->y `elem` s) (elsets xs)
return x
The another way to do that using Data.Map as below is not efficient than ..group . sort.. solution, it is still O(n log n) but able to work with infinite list.
import Data.Map.Lazy as Map (empty, lookup, insert)
identical :: [Int] -> Bool
identical = loop Map.empty
where loop _ [] = False
loop m (x:xs) = if Map.lookup x m == Nothing
then loop (insert x 0 m) xs
else True
OK basically this is one of the rare cases where you really need sort for efficiency. In fact Data.List.Unique package has a repeated function just for this job and if the source is checked one can see that sort and group strategy is chosen. I guess this is not the most efficient algorithm. I will come to how we can make sort even more efficient but for the time being let's enjoy a little since this is a nice question.
So we have the tails :: [a] -> [[a]] functions in Data.List package. Accordingly;
*Main> tails [3,3,6,1]
[[3,3,6,1],[3,6,1],[6,1],[1],[]]
As you may quickly notice we can zipWith the tail of tails list which is [[3,6,1],[6,1],[1],[]], with the given original list by applying a function to check if all item are different. This function could be a list comprehension or simply the all :: Foldable t => (a -> Bool) -> t a -> Bool function. The thing is, I would like to short circuit zipWith so that once i meet the first dupe let's just stop zipWith doing wasteful work by checking the rest. For this purpose i can use the monadic version of zipWith, namely zipWithM :: Applicative m => (a -> b -> m c) -> [a] -> [b] -> m [c] which lives in Control.Monad package. The reason being, from it's type signature we understand that it shall stop calculating any further when it accounts for a Nothing or Left whatever in the middle if my monad happens to be Maybe or Either.
Oh..! In Haskell I also love to use the bool :: a -> a -> Bool -> a function instead of if and then. bool is the ternary operation of Haskell which goes like
bool "work time" "coffee break" isCoffeeTime
The negative choice is on the left and the positive one is on the right where isCoffeeTime :: Bool is a function to return True if it is coffee time. Very composable as well.. so cool..!
So since we now have all the background knowledge we may proceed with the code
import Control.Monad (zipWithM)
import Data.List (tails)
import Data.Bool (bool)
anyDupe :: Eq a => [a] -> Either a [a]
anyDupe xs = zipWithM f xs ts
where ts = tail $ tails xs
f = \x t -> bool (Left x) (Right x) $ all (x /=) t
*Main> anyDupe [1,2,3,4,5]
Right [1,2,3,4,5] -- no dupes so we get the `Right` with the original list
*Main> anyDupe [3,3,6,1]
Left 3 -- here we have the first duplicate since zipWithM short circuits.
*Main> anyDupe $ 10^7:[1..10^7]
Left 10000000 -- wow zipWithM worked and returned reasonably fast.
But again.. as i said, this is still a naive approach because theoretically we are doing n(n+1)/2 operations. Yes zipWithM cuts redundancy down greatly if the first met dupe is close to the head but still this algorithm is O(n^2).
I believe it would be best to use the heavenly sort algorithm of Haskell (which is not merge sort as we know it by the way) in this particular case.
Now the algorithm award goes to -> drum roll here -> sort and fold -> applause. Sorry no grouping.
So now... once again we will use a monadic trick to utilize short circuits. We will use foldM :: (Foldable t, Monad m) => (b -> a -> m b) -> b -> t a -> m b. This, when used with Either monad also allows us to return a more meaningful result. OK lets do it. Any Left n means n is the first dupe and no more calculations while any Right _ means there are no dupes.
import Control.Monad (foldM)
import Data.List (sort)
import Data.Bool (bool)
anyDupe' :: (Eq a, Ord a, Enum a) => [a] -> Either a a
anyDupe' xs = foldM f i $ sort xs
where i = succ $ head xs -- prevent the initial value to be equal with the value at the head
f = \b a -> bool (Left a) (Right a) (a /= b)
*Main> anyDupe' [1,2,3,4,5]
Right 5
*Main> anyDupe' [3,3,6,1]
Left 3
*Main> anyDupe' $ 1:[10^7,(10^7-1)..1]
Left 1
(2.97 secs, 1,040,110,448 bytes)
*Main> anyDupe $ 1:[10^7,(10^7-1)..1]
Left 1
(2.94 secs, 1,440,112,888 bytes)
*Main> anyDupe' $ [1..10^7]++[10^7]
Left 10000000
(5.71 secs, 3,600,116,808 bytes) -- winner by far
*Main> anyDupe $ [1..10^7]++[10^7] -- don't try at home, it's waste of energy
In real world scenarios anyDupe' should always be the winner.

Need to partition a list into lists based on breaks in ascending order of elements (Haskell)

Say I have any list like this:
[4,5,6,7,1,2,3,4,5,6,1,2]
I need a Haskell function that will transform this list into a list of lists which are composed of the segments of the original list which form a series in ascending order. So the result should look like this:
[[4,5,6,7],[1,2,3,4,5,6],[1,2]]
Any suggestions?
You can do this by resorting to manual recursion, but I like to believe Haskell is a more evolved language. Let's see if we can develop a solution that uses existing recursion strategies. First some preliminaries.
{-# LANGUAGE NoMonomorphismRestriction #-}
-- because who wants to write type signatures, amirite?
import Data.List.Split -- from package split on Hackage
Step one is to observe that we want to split the list based on a criteria that looks at two elements of the list at once. So we'll need a new list with elements representing a "previous" and "next" value. There's a very standard trick for this:
previousAndNext xs = zip xs (drop 1 xs)
However, for our purposes, this won't quite work: this function always outputs a list that's shorter than the input, and we will always want a list of the same length as the input (and in particular we want some output even when the input is a list of length one). So we'll modify the standard trick just a bit with a "null terminator".
pan xs = zip xs (map Just (drop 1 xs) ++ [Nothing])
Now we're going to look through this list for places where the previous element is bigger than the next element (or the next element doesn't exist). Let's write a predicate that does that check.
bigger (x, y) = maybe False (x >) y
Now let's write the function that actually does the split. Our "delimiters" will be values that satisfy bigger; and we never want to throw them away, so let's keep them.
ascendingTuples = split . keepDelimsR $ whenElt bigger
The final step is just to throw together the bit that constructs the tuples, the bit that splits the tuples, and a last bit of munging to throw away the bits of the tuples we don't care about:
ascending = map (map fst) . ascendingTuples . pan
Let's try it out in ghci:
*Main> ascending [4,5,6,7,1,2,3,4,5,6,1,2]
[[4,5,6,7],[1,2,3,4,5,6],[1,2]]
*Main> ascending [7,6..1]
[[7],[6],[5],[4],[3],[2],[1]]
*Main> ascending []
[[]]
*Main> ascending [1]
[[1]]
P.S. In the current release of split, keepDelimsR is slightly stricter than it needs to be, and as a result ascending currently doesn't work with infinite lists. I've submitted a patch that makes it lazier, though.
ascend :: Ord a => [a] -> [[a]]
ascend xs = foldr f [] xs
where
f a [] = [[a]]
f a xs'#(y:ys) | a < head y = (a:y):ys
| otherwise = [a]:xs'
In ghci
*Main> ascend [4,5,6,7,1,2,3,4,5,6,1,2]
[[4,5,6,7],[1,2,3,4,5,6],[1,2]]
This problem is a natural fit for a paramorphism-based solution. Having (as defined in that post)
para :: (a -> [a] -> b -> b) -> b -> [a] -> b
foldr :: (a -> b -> b) -> b -> [a] -> b
para c n (x : xs) = c x xs (para c n xs)
foldr c n (x : xs) = c x (foldr c n xs)
para c n [] = n
foldr c n [] = n
we can write
partition_asc xs = para c [] xs where
c x (y:_) ~(a:b) | x<y = (x:a):b
c x _ r = [x]:r
Trivial, since the abstraction fits.
BTW they have two kinds of map in Common Lisp - mapcar
(processing elements of an input list one by one)
and maplist (processing "tails" of a list). With this idea we get
import Data.List (tails)
partition_asc2 xs = foldr c [] . init . tails $ xs where
c (x:y:_) ~(a:b) | x<y = (x:a):b
c (x:_) r = [x]:r
Lazy patterns in both versions make it work with infinite input lists
in a productive manner (as first shown in Daniel Fischer's answer).
update 2020-05-08: not so trivial after all. Both head . head . partition_asc $ [4] ++ undefined and the same for partition_asc2 fail with *** Exception: Prelude.undefined. The combining function g forces the next element y prematurely. It needs to be more carefully written to be productive right away before ever looking at the next element, as e.g. for the second version,
partition_asc2' xs = foldr c [] . init . tails $ xs where
c (x:ys) r#(~(a:b)) = (x:g):gs
where
(g,gs) | not (null ys)
&& x < head ys = (a,b)
| otherwise = ([],r)
(again, as first shown in Daniel's answer).
You can use a right fold to break up the list at down-steps:
foldr foo [] xs
where
foo x yss = (x:zs) : ws
where
(zs, ws) = case yss of
(ys#(y:_)) : rest
| x < y -> (ys,rest)
| otherwise -> ([],yss)
_ -> ([],[])
(It's a bit complicated in order to have the combining function lazy in the second argument, so that it works well for infinite lists too.)
One other way of approaching this task (which, in fact lays the fundamentals of a very efficient sorting algorithm) is using the Continuation Passing Style a.k.a CPS which, in this particular case applied to folding from right; foldr.
As is, this answer would only chunk up the ascending chunks however, it would be nice to chunk up the descending ones at the same time... preferably in reverse order all in O(n) which would leave us with only binary merging of the obtained chunks for a perfectly sorted output. Yet that's another answer for another question.
chunks :: Ord a => [a] -> [[a]]
chunks xs = foldr go return xs $ []
where
go :: Ord a => a -> ([a] -> [[a]]) -> ([a] -> [[a]])
go c f = \ps -> let (r:rs) = f [c]
in case ps of
[] -> r:rs
[p] -> if c > p then (p:r):rs else [p]:(r:rs)
*Main> chunks [4,5,6,7,1,2,3,4,5,6,1,2]
[[4,5,6,7],[1,2,3,4,5,6],[1,2]]
*Main> chunks [4,5,6,7,1,2,3,4,5,4,3,2,6,1,2]
[[4,5,6,7],[1,2,3,4,5],[4],[3],[2,6],[1,2]]
In the above code c stands for current and p is for previous and again, remember we are folding from right so previous, is actually the next item to process.

Using Haskell's map function to calculate the sum of a list

Haskell
addm::[Int]->Int
addm (x:xs) = sum(x:xs)
I was able to achieve to get a sum of a list using sum function but is it possible to get the sum of a list using map function? Also what the use of map function?
You can't really use map to sum up a list, because map treats each list element independently from the others. You can use map for example to increment each value in a list like in
map (+1) [1,2,3,4] -- gives [2,3,4,5]
Another way to implement your addm would be to use foldl:
addm' = foldl (+) 0
Here it is, the supposedly impossible definition of sum in terms of map:
sum' xs = let { ys = 0 : map (\(a,b) -> a + b) (zip xs ys) } in last ys
this actually shows how scanl can be implemented in terms of map (and zip and last), the above being equivalent to foldl (+) 0 xs === last $ scanl (+) 0 xs:
scanl' f z xs = let { ys = z : map (uncurry f) (zip ys xs) } in ys
I expect one can calculate many things with map, arranging for all kinds of information flow through zip.
edit: the above is just a zipWith in disguise of course (and zipWith is kind of a map2):
sum' xs = let { ys = 0 : zipWith (+) ys xs } in last ys
This seems to suggest that scanl is more versatile than foldl.
It is not possible to use map to reduce a list to its sum. That recursive pattern is a fold.
sum :: [Int] -> Int
sum = foldr (+) 0
As an aside, note that you can define map as a fold as well:
map :: (a -> b) -> ([a] -> [b])
map f = fold (\x xs -> f x : xs) []
This is because foldr is the canonical recursive function on lists.
References: A tutorial on the universality and expressiveness of fold, Graham Hutton, J. Functional Programming 9 (4): 355–372, July 1999.
After some insights I have to add another answer: You can't get the sum of a list with map, but you can get the sum with its monadic version mapM. All you need to do is to use a Writer monad (see LYAHFGG) over the Sum monoid (see LYAHFGG).
I wrote a specialized version, which is probably easier to understand:
data Adder a = Adder a Int
instance Monad Adder where
return x = Adder x 0
(Adder x s) >>= f = let Adder x' s' = f x
in Adder x' (s + s')
toAdder x = Adder x x
sum' xs = let Adder _ s = mapM toAdder xs in s
main = print $ sum' [1..100]
--5050
Adder is just a wrapper around some type which also keeps a "running sum." We can make Adder a monad, and here it does some work: When the operation >>= (a.k.a. "bind") is executed, it returns the new result and the value of the running sum of that result plus the original running sum. The toAdder function takes an Int and creates an Adder that holds that argument both as wrapped value and as running sum (actually we're not interested in the value, but only in the sum part). Then in sum' mapM can do its magic: While it works similar to map for the values embedded in the monad, it executes "monadic" functions like toAdder, and chains these calls (it uses sequence to do this). At this point, we get through the "backdoor" of our monad the interaction between list elements that the standard map is missing.
Map "maps" each element of your list to an element in your output:
let f(x) = x*x
map f [1,2,3]
This will return a list of the squares.
To sum all elements in a list, use fold:
foldl (+) 0 [1,2,3]
+ is the function you want to apply, and 0 is the initial value (0 for sum, 1 for product etc)
As the other answers point out, the "normal" way is to use one of the fold functions. However it is possible to write something pretty similar to a while loop in imperative languages:
sum' [] = 0
sum' xs = head $ until single loop xs where
single [_] = True
single _ = False
loop (x1 : x2 : xs) = (x1 + x2) : xs
It adds the first two elements of the list together until it ends up with a one-element list, and returns that value (using head).
I realize this question has been answered, but I wanted to add this thought...
listLen2 :: [a] -> Int
listLen2 = sum . map (const 1)
I believe it returns the constant 1 for each item in the list, and returns the sum!
Might not be the best coding practice, but it was an example my professor gave to us students that seems to relate to this question well.
map can never be the primary tool for summing the elements of a container, in much the same way that a screwdriver can never be the primary tool for watching a movie. But you can use a screwdriver to fix a movie projector. If you really want, you can write
import Data.Monoid
import Data.Foldable
mySum :: (Foldable f, Functor f, Num a)
=> f a -> a
mySum = getSum . fold . fmap Sum
Of course, this is silly. You can get a more general, and possibly more efficient, version:
mySum' :: (Foldable f, Num a) => f a -> a
mySum' = getSum . foldMap Sum
Or better, just use sum, because its actually made for the job.

Apply "permutations" of a function over a list

Creating the permutations of a list or set is simple enough. I need to apply a function to each element of all subsets of all elements in a list, in the order in which they occur. For instance:
apply f [x,y] = { [x,y], [f x, y], [x, f y], [f x, f y] }
The code I have is a monstrous pipeline or expensive computations, and I'm not sure how to proceed, or if it's correct. I'm sure there must be a better way to accomplish this task - perhaps in the list monad - but I'm not sure. This is my code:
apply :: Ord a => (a -> Maybe a) -> [a] -> Set [a]
apply p xs = let box = take (length xs + 1) . map (take $ length xs) in
(Set.fromList . map (catMaybes . zipWith (flip ($)) xs) . concatMap permutations
. box . map (flip (++) (repeat Just)) . flip iterate []) ((:) p)
The general idea was:
(1) make the list
[[], [f], [f,f], [f,f,f], ... ]
(2) map (++ repeat Just) over the list to obtain
[[Just, Just, Just, Just, ... ],
[f , Just, Just, Just, ... ],
[f , f , Just, Just, ... ],
... ]
(3) find all permutations of each list in (2) shaved to the length of the input list
(4) apply the permuted lists to the original list, garnering all possible applications
of the function f to each (possibly empty) subset of the original list, preserving
the original order.
I'm sure there's a better way to do it, though. I just don't know it. This way is expensive, messy, and rather prone to error. The Justs are there because of the intended application.
To do this, you can leverage the fact that lists represent non-deterministic values when using applicatives and monads. It then becomes as simple as:
apply f = mapM (\x -> [x, f x])
It basically reads as follows: "Map each item in a list to itself and the result of applying f to it. Finally, return a list of all the possible combinations of these two values across the whole list."
If I understand your problem correctly, it's best not to describe it in terms of permutations. Rather, it's closer to generating powersets.
powerset (x:xs) = let pxs = powerset xs in pxs ++ map (x :) pxs
powerset [] = [[]]
Each time you add another member to the head of the list, the powerset doubles in size. The second half of the powerset is exactly like the first, but with x included.
For your problem, the choice is not whether to include or exclude x, but whether to apply or not apply f.
powersetapp f (x:xs) = let pxs = powersetapp f xs in map (x:) pxs ++ map (f x:) pxs
powersetapp f [] = [[]]
This does what your "apply" function does, modulo making a Set out of the result.
Paul's and Heatsink's answers are good, but error out when you try to run them on infinite lists.
Here's a different method that works on both infinite and finite lists:
apply _ [] = [ [] ]
apply f (x:xs) = (x:ys):(x':ys):(double yss)
where x' = f x
(ys:yss) = apply f xs
double [] = []
double (ys:yss) = (x:ys):(x':ys):(double yss)
This works as expected - though you'll note it produces a different order to the permutations than Paul's and Heatsink's
ghci> -- on an infinite list
ghci> map (take 4) $ take 16 $ apply (+1) [0,0..]
[[0,0,0,0],[1,0,0,0],[0,1,0,0],[1,1,0,0],[0,0,1,0],...,[1,1,1,1]]
ghci> -- on a finite list
ghci> apply (+1) [0,0,0,0]
[[0,0,0,0],[1,0,0,0],[0,1,0,0],[1,1,0,0],[0,0,1,0],...,[1,1,1,1]]
Here is an alternative phrasing of rampion's infinite-input-handling solution:
-- sequence a list of nonempty lists
sequenceList :: [[a]] -> [[a]]
sequenceList [] = [[]]
sequenceList (m:ms) = do
xs <- nonempty (sequenceList ms)
x <- nonempty m
return (x:xs)
where
nonempty ~(x:xs) = x:xs
Then we can define apply in Paul's idiomatic style:
apply f = sequenceList . map (\x -> [x, f x])
Contrast sequenceList with the usual definition of sequence:
sequence :: (Monad m) => [m a] -> m [a]
sequence [] = [[]]
sequence (m:ms) = do
x <- m
xs <- sequence ms
return (x:xs)
The order of binding is reversed in sequenceList so that the variations of the first element are the "inner loop", i.e. we vary the head faster than the tail. Varying the end of an infinite list is a waste of time.
The other key change is nonempty, the promise that we won't bind an empty list. If any of the inputs were empty, or if the result of the recursive call to sequenceList were ever empty, then we would be forced to return an empty list. We can't tell in advance whether any of inputs is empty (because there are infinitely many of them to check), so the only way for this function to output anything at all is to promise that they won't be.
Anyway, this is fun subtle stuff. Don't stress about it on your first day :-)