Haskell - Append to a list inside a list of lists and return the lists of lists updated - list

Having spent hours looking for ways to manipulate [[a]] into [[a]], I thought this would be the best solution to my problem. The problem consists of appending a to [a] and returning [[a]] with the new change.
For example: xs = [[a],[b],[c]] and y = d.
I want to append y to xs!!0 . I cannot use xs!!0 ++ y because it will return just [a,d], I know this is because of Haskell's immutability.
How would I go about appending a value to a sublist and returning the list of lists? - [[a,d],[b],[c]] using the example from above to illustrate this.

let { xs = [[1]] ; y = 2 ; zs = [(xs!!0) ++ [y]] } in zs is one example to try at the GHCi prompt.
It returns [[1,2]].
And for the case of e.g. [[1],[2,3],[4]] and the like, we can do
appendToFirst :: [[a]] -> a -> [[a]]
appendToFirst (xs:r) y = (xs ++ [y]) : r
so that
> appendToFirst [[1],[2,3],[4]] 0
[[1,0],[2,3],[4]]
The (xs:r) on the left of the equal sign is a pattern.
The (:) in the ( (...) : r) on the right of the equal sign is a "cons" operation, a data constructor, (:) :: t -> [t] -> [t].
xs is bound to the input list's "head" i.e. its first element, and r is bound to the rest of the input list, in the pattern; and thus xs's value is used in creating the updated version of the list, with the first sublist changed by appending a value to its end, and r remaining as is.
xs ++ [y] creates a new entity, new list, while xs and y continue to refer to the same old values they were defined as. Since Haskell's values and variables are immutable, as you indeed have mentioned.
edit: If you want to add new element at the end of some sublist in the middle, not the first one as shown above, this can be done with e.g. splitAt function, like
appendInTheMiddle :: Int -> a -> [[a]] -> [[a]]
appendInTheMiddle i y xs =
let
(a,b) = splitAt i xs
in
init a ++ [last a ++ [y]] ++ b
Trying it out:
> appendInTheMiddle 2 0 [[1],[2],[3],[4]]
[[1],[2,0],[3],[4]]
Adding the error-handling, bounds checking, and adjusting the indexing if 0-based one is desired (that one would lead to a simpler and faster code, by the way), is left as an exercise for the reader.
Syntactically, this can be streamlined with "view patterns", as
{-# LANGUAGE ViewPatterns #-}
appendInTheMiddle :: Int -> a -> [[a]] -> [[a]]
appendInTheMiddle i y (splitAt i -> (a,b)) =
init a ++ [last a ++ [y]] ++ b

Related

Haskell - using foldl or foldr instead of pattern matching for updating a list with a new value at a given index

I have implemented a function (!!=) that given a list and a tuple containing an index in the list and a
new value, updates the given list with the new value at the given
index.
(!!=) :: [a] -> (Int,a) -> [a]
(!!=) xs (0, a) = a : tail xs
(!!=) [] (i, a) = error "Index not in the list"
(!!=) (x:xs) (i, a) = x : xs !!= (i-1, a)
Being a beginner with the concept of folding I was wondering if there is a way to achieve the same result using foldl or foldr instead?
Thanks a lot in advance.
I'll give you the foldl version which is easier to understand I think and the easiest / most straight-forward version I can think of.
But please note that you should not use foldl (use foldl': https://wiki.haskell.org/Foldr_Foldl_Foldl') - nor should you use ++ like this (use : and reverse after) ;)
Anway this is the idea:
(!!=) xs (i, a) = snd $ foldl
(\(j, ys) x -> (j+1, if j == i then ys ++ [a] else ys ++ [x]))
(0, [])
xs
as the state/accumulator for the fold I take a tuple of the current index and the accumulated result list (therefore the snd because I only want this in the end)
then the folding function just have to look if we are at the index and exchange the element - returning the next index and the new accumulated list
as an exercise you can try to:
use : instead of ++ and a reverse
rewrite as foldr
look at zipWith and rewrite this using this (zipWith (...) [0..] xs) instead of the fold (this is similar to using a map with index
Neither foldl nor foldr can do this particular job efficiently (unless you "cheat" by pattern matching on the list as you fold over it), though foldr can do it a bit less badly. No, what you really need is a different style of fold, sometimes called para:
para :: (a -> [a] -> b -> b) -> b -> [a] -> b
para _f n [] = n
para f n (a : as) = f a as (para f n as)
para is very similar to foldr. Each of them takes a combining function and, for each element, passes the combining function that element and the result of folding up the rest of the list. But para adds something extra: it also passes in the rest of the list! So there's no need to reconstruct the tail of the list once you've reached the replacement point.
But ... how do you count from the beginning with foldr or para? That brings in a classic trick, sometimes called a "higher-order fold". Instead of para go stop xs producing a list, it's going to produce a function that takes the insertion position as an argument.
(!!=) :: [a] -> (Int, a) -> [a]
xs0 !!= (i0, new) = para go stop xs0 i0
where
-- If the list is empty, then no matter what index
-- you seek, it's not there.
stop = \_ -> error "Index not in the list"
-- We produce a function that takes an index. If the
-- index is 0, we combine the new element with "the rest of the list".
-- Otherwise we apply the function we get from folding up the rest of
-- the list to the predecessor of the index, and tack on the current
-- element.
go x xs r = \i -> case i of
0 -> new : xs
_ -> x : r (i - 1)
Note that para is easily powerful enough to implement foldr:
foldr c = para (\a _ b -> c a b)
What's perhaps less obvious is that foldr can implement a (very inefficient version of) para:
para f n = snd . foldr go ([], n)
where
go x ~(xs, r) = (x : xs, f x xs r)
Lest you get the wrong idea and think that para is "better than" foldr, know that when its extra power isn't needed, foldr is simpler to use and will very often be compiled to more efficient code.

Breaking a list into sublists of a specified size using foldr

I'm taking a functional programming class and I'm having a hard time leaving the OOP mindset behind and finding answers to a lot of my questions.
I have to create a function that takes an ordered list and converts it into specified size sublists using a variation of fold.
This isn't right, but it's what I have:
splitList :: (Ord a) => Int -> [a] -> [[a]]
splitList size xs
| [condition] = foldr (\item subList -> item:subList) [] xs
| otherwise =
I've been searching and I found out that foldr is the variation that works better for what I want, and I think I've understood how fold works, I just don't know how I'll set up the guards so that when length sublist == size haskell resets the accumulator and goes on to the next list.
If I didn't explain myself correctly, here's the result I want:
> splitList 3 [1..10]
> [[1,2,3],[4,5,6],[7,8,9],[10]]
Thanks!
While Fabián's and chi's answers are entirely correct, there is actually an option to solve this puzzle using foldr. Consider the following code:
splitList :: Int -> [a] -> [[a]]
splitList n =
foldr (\el acc -> case acc of
[] -> [[el]]
(h : t) | length h < n -> (el : h) : t
_ -> [el] : acc
) []
The strategy here is to build up a list by extending its head as long as its length is lesser than desired. This solution has, however, two drawbacks:
It does something slightly different than in your example;
splitList 3 [1..10] produces [[1],[2,3,4],[5,6,7],[8,9,10]]
It's complexity is O(n * length l), as we measure length of up to n–sized list on each of the element which yields linear number of linear operations.
Let's first take care of first issue. In order to start counting at the beginning we need to traverse the list left–to–right, while foldr does it right–to–left. There is a common trick called "continuation passing" which will allow us to reverse the direction of the walk:
splitList :: Int -> [a] -> [[a]]
splitList n l = map reverse . reverse $
foldr (\el cont acc ->
case acc of
[] -> cont [[el]]
(h : t) | length h < n -> cont ((el : h) : t)
_ -> cont ([el] : acc)
) id l []
Here, instead of building the list in the accumulator we build up a function that will transform the list in the right direction. See this question for details. The side effect is reversing the list so we need to counter that by reverse application to the whole list and all of its elements. This goes linearly and tail-recursively tho.
Now let's work on the performance issue. The problem was that the length is linear on casual lists. There are two solutions for this:
Use another structure that caches length for a constant time access
Cache the value by ourselves
Because I guess it is a list exercise, let's go for the latter option:
splitList :: Int -> [a] -> [[a]]
splitList n l = map reverse . reverse . snd $
foldr (\el cont (countAcc, listAcc) ->
case listAcc of
[] -> cont (countAcc, [[el]])
(h : t) | countAcc < n -> cont (countAcc + 1, (el : h) : t)
(h : t) -> cont (1, [el] : (h : t))
) id l (1, [])
Here we extend our computational state with a counter that at each points stores the current length of the list. This gives us a constant check on each element and results in linear time complexity in the end.
A way to simplify this problem would be to split this into multiple functions. There are two things you need to do:
take n elements from the list, and
keep taking from the list as much as possible.
Lets try taking first:
taking :: Int -> [a] -> [a]
taking n [] = undefined
taking n (x:xs) = undefined
If there are no elemensts then we cannot take any more elements so we can only return an empty list, on the other hand if we do have an element then we can think of taking n (x:xs) as x : taking (n-1) xs, we would only need to check that n > 0.
taking n (x:xs)
| n > 0 = x :taking (n-1) xs
| otherwise = []
Now, we need to do that multiple times with the remainder so we should probably also return whatever remains from taking n elements from a list, in this case it would be whatever remains when n = 0 so we could try to adapt it to
| otherwise = ([], x:xs)
and then you would need to modify the type signature to return ([a], [a]) and the other 2 definitions to ensure you do return whatever remained after taking n.
With this approach your splitList would look like:
splitList n [] = []
splitList n l = chunk : splitList n remainder
where (chunk, remainder) = taking n l
Note however that folding would not be appropriate since it "flattens" whatever you are working on, for example given a [Int] you could fold to produce a sum which would be an Int. (foldr :: (a -> b -> b) -> b -> [a] -> b or "foldr function zero list produces an element of the function return type")
You want:
splitList 3 [1..10]
> [[1,2,3],[4,5,6],[7,8,9],[10]]
Since the "remainder" [10] in on the tail, I recommend you use foldl instead. E.g.
splitList :: (Ord a) => Int -> [a] -> [[a]]
splitList size xs
| size > 0 = foldl go [] xs
| otherwise = error "need a positive size"
where go acc x = ....
What should go do? Essentially, on your example, we must have:
splitList 3 [1..10]
= go (splitList 3 [1..9]) 10
= go [[1,2,3],[4,5,6],[7,8,9]] 10
= [[1,2,3],[4,5,6],[7,8,9],[10]]
splitList 3 [1..9]
= go (splitList 3 [1..8]) 9
= go [[1,2,3],[4,5,6],[7,8]] 9
= [[1,2,3],[4,5,6],[7,8,9]]
splitList 3 [1..8]
= go (splitList 3 [1..7]) 8
= go [[1,2,3],[4,5,6],[7]] 8
= [[1,2,3],[4,5,6],[7,8]]
and
splitList 3 [1]
= go [] 1
= [[1]]
Hence, go acc x should
check if acc is empty, if so, produce a singleton list [[x]].
otherwise, check the last list in acc:
if its length is less than size, append x
otherwise, append a new list [x] to acc
Try doing this by hand on your example to understand all the cases.
This will not be efficient, but it will work.
You don't really need the Ord a constraint.
Checking the accumulator's first sublist's length would lead to information flow from the right and the first chunk ending up the shorter one, potentially, instead of the last. Such function won't work on infinite lists either (not to mention the foldl-based variants).
A standard way to arrange for the information flow from the left with foldr is using an additional argument. The general scheme is
subLists n xs = foldr g z xs n
where
g x r i = cons x i (r (i-1))
....
The i argument to cons will guide its decision as to where to add the current element into. The i-1 decrements the counter on the way forward from the left, instead of on the way back from the right. z must have the same type as r and as the foldr itself as a whole, so,
z _ = [[]]
This means there must be a post-processing step, and some edge cases must be handled as well,
subLists n xs = post . foldr g z xs $ n
where
z _ = [[]]
g x r i | i == 1 = cons x i (r n)
g x r i = cons x i (r (i-1))
....
cons must be lazy enough not to force the results of the recursive call prematurely.
I leave it as an exercise finishing this up.
For a simpler version with a pre-processing step instead, see this recent answer of mine.
Just going to give another answer: this is quite similar to trying to write groupBy as a fold, and actually has a couple gotchas w.r.t. laziness that you have to bear in mind for an efficient and correct implementation. The following is the fastest version I found that maintains all the relevant laziness properties:
splitList :: Int -> [a] -> [[a]]
splitList m xs = snd (foldr f (const ([],[])) xs 1)
where
f x a i
| i <= 1 = let (ys,zs) = a m in ([], (x : ys) : zs)
| otherwise = let (ys,zs) = a (i-1) in (x : ys , zs)
The ys and the zs gotten from the recursive processing of the rest of list indicate the first and the rest of the groups into which the rest of the list will be broken up, by said recursive processing. So we either prepend the current element before that first subgroup if it is still shorter than needed, or we prepend before the first subgroup when it is just right and start a new, empty subgroup.

Creating a lists of lists with new element in each position

i'm new in the haskell world and i'd like to know how to insert a value in each position of a list in haskell, and return a lists of sublists containing the value in each position. For example:
insert' :: a -> [a] -> [[a]]
insert' a [] = [[a]]
insert' a list = ??
To get something like:
insert' 7 [1,2,3] = [[7,1,2,3],[1,7,2,3],[1,2,7,3],[1,2,3,7]]
insert' :: a -> [a] -> [[a]]
insert' y [] = [[y]]
insert' y xss#(x:xs) = (y : xss) : map (x :) (insert' y xs)
While the empty list case comes natural, let's take a look at insert' y xss#(x:xs). We essentially have two cases we need to cover:
y appears in front of x. Then we can just use y : xss.
y appears somewhere after x. We therefore just insert it in the rest of our list and make sure that x is the first element with map (x:).
Although #delta's answer is definitely more elegant, here a solution with difference lists. If we insert an element x on every location of list ys = [y1,y2,...,yn], the first time we will insert it as head, so that means we can construct x : ys.
. For the second element of the resulting list, we want to construct a list [y1,x,y2,...,yn]. We can do this like y1 : x : y2s. The next lists will all have a structure y1 : ....
The question is: how can we write a recursive structure that keeps track of the fact that we want to put elements in the head. We can use a function for that: we start with a function id. If we now call id (x:ys) then we will of course generate the list (x:ys).
We can however, based on the id function, construct a new function id2 = \z -> id (y1:z). This function will thus put y1 in the head of the list and then add the list with which we call id2 as tail. Next we can construct id3 = \z -> id2 (y2:z). This will put y1 and y2 as first elements followed by the tail z.
So we can put this into the following recursive format:
insert' :: a -> [a] -> [[a]]
insert' x = go id
where go d [] = [d [x]]
go d ys#(yh:yt) = (d (x : ys)) : go (d . (yh :)) yt
So we redirect insert' to go where the initial difference list is simply the id function. Each time we check if we have reached the end of the given list. If that is the case, we return the basecase: we call [x] (as tail) on the difference list, and thus construct a list where we append x as last element.
In case we have not yet reached the last element, we will first emit d (x : ys): we prepend x to the list and provide this as argument to the difference list d. d will prepend y1 : y2 : ... : yk up to the point where we insert x. Furthermore we call recursively go (d . (yh :)) yt on the tail of the list: we thus construct a new difference list, wehere we insert (yh :) as tail of the list. We thus produce a new function with one argument: the tail after the yh element.
This function produces the expected results:
*Main> insert' 4 []
[[4]]
*Main> insert' 4 [1,2,5]
[[4,1,2,5],[1,4,2,5],[1,2,4,5],[1,2,5,4]]
*Main> insert' 7 [1,2,3]
[[7,1,2,3],[1,7,2,3],[1,2,7,3],[1,2,3,7]]
You may also do as follows;
import Data.List
spread :: a -> [a] -> [[a]]
spread x xs = zipWith (++) (inits xs) ((x:) <$> tails xs)
*Main> spread 7 [1,2,3]
[[7,1,2,3],[1,7,2,3],[1,2,7,3],[1,2,3,7]]
*Main> spread 7 []
[[7]]
So this is about three stages.
(x:) <$> tails xs is all about applying the (x:) function to all elements of tails xs function. So tails [1,2,3] would return [[1,2,3],[2,3],[3],[]] and we are to apply an fmap which is designated by <$> in the inline form. This is going to be the third argument of the zipWith function.
(inits xs) which would return [[],[1],[1,2],[1,2,3]], is going to be the second argument to zipWith.
zipWith (++) is obviously will zip two list of lists by concatenating the list elements.
So we may also express the same functionality with applicative function functors as follows;
spread :: a -> [a] -> [[a]]
spread x = zipWith (++) <$> inits <*> fmap (x:) . tails
In this case we fmap the zipWith (++) function with type [[a]] -> [[a]] -> [[a]] over inits and then apply it over to fmap (x:) . tails.
It could get more pointfree but becomes more complicated to read through (at least for me). In my opinion this is as best as it gets.

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.

Replace an element in a list only once - Haskell

I want to replace an element in a list with a new value only at first time occurrence.
I wrote the code below but using it, all the matched elements will change.
replaceX :: [Int] -> Int -> Int -> [Int]
replaceX items old new = map check items where
check item | item == old = new
| otherwise = item
How can I modify the code so that the changing only happen at first matched item?
Thanks for helping!
The point is that map and f (check in your example) only communicate regarding how to transform individual elements. They don't communicate about how far down the list to transform elements: map always carries on all the way to the end.
map :: (a -> b) -> [a] -> [b]
map _ [] = []
map f (x:xs) = f x : map f xs
Let's write a new version of map --- I'll call it mapOnce because I can't think of a better name.
mapOnce :: (a -> Maybe a) -> [a] -> [a]
There are two things to note about this type signature:
Because we may stop applying f part-way down the list, the input list and the output list must have the same type. (With map, because the entire list will always be mapped, the type can change.)
The type of f hasn't changed to a -> a, but to a -> Maybe a.
Nothing will mean "leave this element unchanged, continue down the list"
Just y will mean "change this element, and leave the remaining elements unaltered"
So:
mapOnce _ [] = []
mapOnce f (x:xs) = case f x of
Nothing -> x : mapOnce f xs
Just y -> y : xs
Your example is now:
replaceX :: [Int] -> Int -> Int -> [Int]
replaceX items old new = mapOnce check items where
check item | item == old = Just new
| otherwise = Nothing
You can easily write this as a recursive iteration like so:
rep :: Eq a => [a] -> a -> a -> [a]
rep items old new = rep' items
where rep' (x:xs) | x == old = new : xs
| otherwise = x : rep' xs
rep' [] = []
A direct implementation would be
rep :: Eq a => a -> a -> [a] -> [a]
rep _ _ [] = []
rep a b (x:xs) = if x == a then b:xs else x:rep a b xs
I like list as last argument to do something like
myRep = rep 3 5 . rep 7 8 . rep 9 1
An alternative using the Lens library.
>import Control.Lens
>import Control.Applicative
>_find :: (a -> Bool) -> Simple Traversal [a] a
>_find _ _ [] = pure []
>_find pred f (a:as) = if pred a
> then (: as) <$> f a
> else (a:) <$> (_find pred f as)
This function takes a (a -> Bool) which is a function that should return True on an type 'a' that you wan to modify.
If the first number greater then 5 needs to be doubled then we could write:
>over (_find (>5)) (*2) [4, 5, 3, 2, 20, 0, 8]
[4,5,3,2,40,0,8]
The great thing about lens is that you can combine them together by composing them (.). So if we want to zero the first number <100 in the 2th sub list we could:
>over ((element 1).(_find (<100))) (const 0) [[1,2,99],[101,456,50,80,4],[1,2,3,4]]
[[1,2,99],[101,456,0,80,4],[1,2,3,4]]
To be blunt, I don't like most of the answers so far. dave4420 presents some nice insights on map that I second, but I also don't like his solution.
Why don't I like those answers? Because you should be learning to solve problems like these by breaking them down into smaller problems that can be solved by simpler functions, preferably library functions. In this case, the library is Data.List, and the function is break:
break, applied to a predicate p and a list xs, returns a tuple where first element is longest prefix (possibly empty) of xs of elements that do not satisfy p and second element is the remainder of the list.
Armed with that, we can attack the problem like this:
Split the list into two pieces: all the elements before the first occurence of old, and the rest.
The "rest" list will either be empty, or its first element will be the first occurrence of old. Both of these cases are easy to handle.
So we have this solution:
import Data.List (break)
replaceX :: Eq a => a -> a -> [a] -> [a]
replaceX old new xs = beforeOld ++ replaceFirst oldAndRest
where (beforeOld, oldAndRest) = break (==old) xs
replaceFirst [] = []
replaceFirst (_:rest) = new:rest
Example:
*Main> replaceX 5 7 ([1..7] ++ [1..7])
[1,2,3,4,7,6,7,1,2,3,4,5,6,7]
So my advice to you:
Learn how to import libraries.
Study library documentation and learn standard functions. Data.List is a great place to start.
Try to use those library functions as much as you can.
As a self study exercise, you can pick some of the standard functions from Data.List and write your own versions of them.
When you run into a problem that can't be solved with a combination of library functions, try to invent your own generic function that would be useful.
EDIT: I just realized that break is actually a Prelude function, and doesn't need to be imported. Still, Data.List is one of the best libraries to study.
Maybe not the fastest solution, but easy to understand:
rep xs x y =
let (left, (_ : right)) = break (== x) xs
in left ++ [y] ++ right
[Edit]
As Dave commented, this will fail if x is not in the list. A safe version would be:
rep xs x y =
let (left, right) = break (== x) xs
in left ++ [y] ++ drop 1 right
[Edit]
Arrgh!!!
rep xs x y = left ++ r right where
(left, right) = break (== x) xs
r (_:rs) = y:rs
r [] = []
replaceValue :: Int -> Int -> [Int] -> [Int]
replaceValue a b (x:xs)
|(a == x) = [b] ++ xs
|otherwise = [x] ++ replaceValue a b xs
Here's an imperative way to do it, using State Monad:
import Control.Monad.State
replaceOnce :: Eq a => a -> a -> [a] -> [a]
replaceOnce old new items = flip evalState False $ do
forM items $ \item -> do
replacedBefore <- get
if item == old && not replacedBefore
then do
put True
return new
else
return old