Haskell map until first condition met - haskell

I want to map a conditional function only on the first item that passes.
map (>5) [1,2,3,4,5,6,7,8,9]
would result in
[False,False,False,False,False,True,True,True,True]
I'm looking for something that would result in
[False,False,False,False,False,True,False,False,False]
So only the first occurrence of being greater than 5 results in True.
I tried scanl, various folds and tried to roll my own mapUntil kind of thing.
Seems like a simple problem but I'm drawing a blank.

break specifically separates the list in 2 parts where the first part is all False, the opposite of span.
break (>5) [1,2,3,8,2,5,1,7,9]
>>> ([1,2,3],[8,2,5,1,7,9])
Then it's just what chi did:
oneTrue f lst = map (const False) a ++ rest b
where (a,b) = break f lst
rest [] = []
rest (x:xs) = True : map (const False) xs

A basic solution:
mapUntil p = onlyOne . map p
where
onlyOne [] = []
onlyOne (x:xs)
| x = True : map (const False) xs
| otherwise = False : onlyOne xs
With library helpers:
mapUntil p = snd . mapAccumL (\x y -> (x||y, not x && y)) False . map p
Above x is a boolean standing for "have seen a true before?", as a kind-of state. y is the list element. x||y is the new state, while not x && y is the new list element.
Alternatively (using Control.Arrow.second):
mapUntil p = uncurry (++) . second go . break id . map p
where
go [] = []
go (x:xs) = x : map (const False) xs

I would use the mapAccumL tool like;
λ> Data.List.mapAccumL (\b n -> if b then (b, (not b)) else (n > 5, n > 5)) False [1,2,3,4,5,6,7,8,9]
(True,[False,False,False,False,False,True,False,False,False])
Here we carry the b as the state of our interim calculations and in every step decide according to it's previous state. Obviously you need the snd part of the final result.
Edit : After reading the new comment of #Gord under his question I decided to extend my answer to cover his true problem.
Rephrasing the case event of branch that starts with pointerPress (x,y) into...
To start with, you never use x or y from the pattern match (x,y) so lets call it c. Then...
PointerPress c -> State circleCoords circleColors circleDraggeds c
where
bools = fmap checkMouseOverlaps $ (,) <$> circleCoords <*> [c]
circleDraggeds = snd $ mapAccumL (\a b -> if a then (a, not a)
else (b,b)) False bools
What's happening part;
(,) <$> circleCoords <*> [c]
circleCoords is a list of coordinates like [c0,c1,c2] and we fmap (the infix version (<$>) here) (,) function to it and it becomes an applicative of coordinates like [(c0,),(c1,),(c2,)]. Then we apply it to [c] aka [(x,y)] to turn it into [(c0,c),(c1,c),(c2,c)].
fmap checkMouseOverlaps $ toAbove
obviously yields to
[checkMouseOverlaps (c0,c), checkMouseOverlaps (c1,c), checkMouseOverlaps (c2,c)]
which is bools :: [Bool].
The the rest follows the logic explained at the top of my answer.
circleDraggeds = snd $ mapAccumL (\a b -> if a then (a, not a)
else (b,b)) False bools

This can be solve directly with recursion. Similar to chi's solution but without function composition
mapUntil :: (a -> Bool) -> [a] -> [Bool]
mapUntil _ [] = []
mapUntil f (x:xs) =
let b = f x -- calculate f x
in if b -- if true
then b : map (const False) xs -- prepend to the solution and map False to the rest of the list (b is True)
else b : mapUntil f xs -- keep applying mapUntil (b is False)
>>> mapUntil (>5) [1,2,3,4,5,6,7,8,9]
[False,False,False,False,False,True,False,False,False]

Map the condition over the list, then zip the result with the False prefix of the result concatenated with a True followed by an infinite list of Falses:
{-# LANGUAGE BlockArguments, ApplicativeDo, ViewPatterns #-}
import Control.Applicative (ZipList(..))
f :: (a -> Bool) -> [a] -> [Bool]
f cond (map cond -> bs) = getZipList do
r <- ZipList $ takeWhile not bs ++ [True] ++ repeat False
_ <- ZipList $ bs
pure r
or, equivalently:
f' :: (a -> Bool) -> [a] -> [Bool]
f' cond (map cond -> bs) = zipWith const (takeWhile not bs ++ [True] ++ repeat False) bs

Related

Split a list into non-empty sub-lists in Haskell

I have to split the given list into non-empty sub-lists each of which
is either in strictly ascending order, in strictly descending order, or contains all equal elements. For example, [5,6,7,2,1,1,1] should become [[5,6,7],[2,1],[1,1]].
Here is what I have done so far:
splitSort :: Ord a => [a] -> [[a]]
splitSort ns = foldr k [] ns
where
k a [] = [[a]]
k a ns'#(y:ys) | a <= head y = (a:y):ys
| otherwise = [a]:ns'
I think I am quite close but when I use it it outputs [[5,6,7],[2],[1,1,1]] instead of [[5,6,7],[2,1],[1,1]].
Here is a kinda ugly solution, with three reverse in one line of code :).
addElement :: Ord a => a -> [[a]] -> [[a]]
addElement a [] = [[a]]
addElement a (x:xss) = case x of
(x1:x2:xs)
| any (check a x1 x2) [(==),(<),(>)] -> (a:x1:x2:xs):xss
| otherwise -> [a]:(x:xss)
_ -> (a:x):xss
where
check x1 x2 x3 op = (x1 `op` x2) && (x2 `op` x3)
splitSort xs = reverse $ map reverse $ foldr addElement [] (reverse xs)
You can possibly get rid of all the reversing if you modify addElement a bit.
EDIT:
Here is a less reversing version (even works for infinite lists):
splitSort2 [] = []
splitSort2 [x] = [[x]]
splitSort2 (x:y:xys) = (x:y:map snd here):splitSort2 (map snd later)
where
(here,later) = span ((==c) . uncurry compare) (zip (y:xys) xys)
c = compare x y
EDIT 2:
Finally, here is a solution based on a single decorating/undecorating, that avoids comparing any two values more than once and is probably a lot more efficient.
splitSort xs = go (decorate xs) where
decorate :: Ord a => [a] -> [(Ordering,a)]
decorate xs = zipWith (\x y -> (compare x y,y)) (undefined:xs) xs
go :: [(Ordering,a)] -> [[a]]
go ((_,x):(c,y):xys) = let (here, later) = span ((==c) . fst) xys in
(x : y : map snd here) : go later
go xs = map (return . snd) xs -- Deal with both base cases
Every ordered prefix is already in some order, and you don't care in which, as long as it is the longest:
import Data.List (group, unfoldr)
foo :: Ord t => [t] -> [[t]]
foo = unfoldr f
where
f [] = Nothing
f [x] = Just ([x], [])
f xs = Just $ splitAt (length g + 1) xs
where
(g : _) = group $ zipWith compare xs (tail xs)
length can be fused in to make the splitAt count in unary essentially, and thus not be as strict (unnecessarily, as Jonas Duregård rightly commented):
....
f xs = Just $ foldr c z g xs
where
(g : _) = group $ zipWith compare xs (tail xs)
c _ r (x:xs) = let { (a,b) = r xs } in (x:a, b)
z (x:xs) = ([x], xs)
The initial try turned out to be lengthy probably inefficient but i will keep it striked for the sake of integrity with the comments. You best just skip to the end for the answer.
Nice question... but turns out to be a little hard candy. My approach is in segments, those of each i will explain;
import Data.List (groupBy)
splitSort :: Ord a => [a] -> [[a]]
splitSort (x:xs) = (:) <$> (x :) . head <*> tail $ interim
where
pattern = zipWith compare <$> init <*> tail
tuples = zipWith (,) <$> tail <*> pattern
groups = groupBy (\p c -> snd p == snd c) . tuples $ (x:xs)
interim = groups >>= return . map fst
*Main> splitSort [5,6,7,2,1,1,1]
[[5,6,7],[2,1],[1,1]]
The pattern function (zipWith compare <$> init <*> tail) is of type Ord a => [a] -> [Ordering] when fed with [5,6,7,2,1,1,1] compares the init of it by the tail of it by zipWith. So the result would be [LT,LT,GT,GT,EQ,EQ]. This is the pattern we need.
The tuples function will take the tail of our list and will tuple up it's elements with the corresponding elements from the result of pattern. So we will end up with something like [(6,LT),(7,LT),(2,GT),(1,GT),(1,EQ),(1,EQ)].
The groups function utilizes Data.List.groupBy over the second items of the tuples and generates the required sublists such as [[(6,LT),(7,LT)],[(2,GT),(1,GT)],[(1,EQ),(1,EQ)]]
Interim is where we monadically get rid of the Ordering type values and tuples. The result of interim is [[6,7],[2,1],[1,1]].
Finally at the main function body (:) <$> (x :) . head <*> tail $ interim appends the first item of our list (x) to the sublist at head (it has to be there whatever the case) and gloriously present the solution.
Edit: So investigating the [0,1,0,1] resulting [[0,1],[0],[1]] problem that #Jonas Duregård discovered, we can conclude that in the result there shall be no sub lists with a length of 1 except for the last one when singled out. I mean for an input like [0,1,0,1,0,1,0] the above code produces [[0,1],[0],[1],[0],[1],[0]] while it should [[0,1],[0,1],[0,1],[0]]. So I believe adding a squeeze function at the very last stage should correct the logic.
import Data.List (groupBy)
splitSort :: Ord a => [a] -> [[a]]
splitSort [] = []
splitSort [x] = [[x]]
splitSort (x:xs) = squeeze $ (:) <$> (x :) . head <*> tail $ interim
where
pattern = zipWith compare <$> init <*> tail
tuples = zipWith (,) <$> tail <*> pattern
groups = groupBy (\p c -> snd p == snd c) $ tuples (x:xs)
interim = groups >>= return . map fst
squeeze [] = []
squeeze [y] = [y]
squeeze ([n]:[m]:ys) = [n,m] : squeeze ys
squeeze ([n]:(m1:m2:ms):ys) | compare n m1 == compare m1 m2 = (n:m1:m2:ms) : squeeze ys
| otherwise = [n] : (m1:m2:ms) : squeeze ys
squeeze (y:ys) = y : squeeze s
*Main> splitSort [0,1, 0, 1, 0, 1, 0]
[[0,1],[0,1],[0,1],[0]]
*Main> splitSort [5,6,7,2,1,1,1]
[[5,6,7],[2,1],[1,1]]
*Main> splitSort [0,0,1,0,-1]
[[0,0],[1,0,-1]]
Yes; as you will also agree the code has turned out to be a little too lengthy and possibly not so efficient.
The Answer: I have to trust the back of my head when it keeps telling me i am not on the right track. Sometimes, like in this case, the problem reduces down to a single if then else instruction, much simpler than i had initially anticipated.
runner :: Ord a => Maybe Ordering -> [a] -> [[a]]
runner _ [] = []
runner _ [p] = [[p]]
runner mo (p:q:rs) = let mo' = Just (compare p q)
(s:ss) = runner mo' (q:rs)
in if mo == mo' || mo == Nothing then (p:s):ss
else [p] : runner Nothing (q:rs)
splitSort :: Ord a => [a] -> [[a]]
splitSort = runner Nothing
My test cases
*Main> splitSort [0,1, 0, 1, 0, 1, 0]
[[0,1],[0,1],[0,1],[0]]
*Main> splitSort [5,6,7,2,1,1,1]
[[5,6,7],[2,1],[1,1]]
*Main> splitSort [0,0,1,0,-1]
[[0,0],[1,0,-1]]
*Main> splitSort [1,2,3,5,2,0,0,0,-1,-1,0]
[[1,2,3,5],[2,0],[0,0],[-1,-1],[0]]
For this solution I am making the assumption that you want the "longest rally". By that I mean:
splitSort [0, 1, 0, 1] = [[0,1], [0,1]] -- This is OK
splitSort [0, 1, 0, 1] = [[0,1], [0], [1]] -- This is not OK despite of fitting your requirements
Essentially, There are two pieces:
Firstly, split the list in two parts: (a, b). Part a is the longest rally considering the order of the two first elements. Part b is the rest of the list.
Secondly, apply splitSort on b and put all list into one list of list
Taking the longest rally is surprisingly messy but straight. Given the list x:y:xs: by construction x and y will belong to the rally. The elements in xs belonging to the rally depends on whether or not they follow the Ordering of x and y. To check this point, you zip every element with the Ordering is has compared against its previous element and split the list when the Ordering changes. (edge cases are pattern matched) In code:
import Data.List
import Data.Function
-- This function split the list in two (Longest Rally, Rest of the list)
splitSort' :: Ord a => [a] -> ([a], [a])
splitSort' [] = ([], [])
splitSort' (x:[]) = ([x],[])
splitSort' l#(x:y:xs) = case span ( (o ==) . snd) $ zip (y:xs) relativeOrder of
(f, s) -> (x:map fst f, map fst s)
where relativeOrder = zipWith compare (y:xs) l
o = compare y x
-- This applies the previous recursively
splitSort :: Ord a => [a] -> [[a]]
splitSort [] = []
splitSort (x:[]) = [[x]]
splitSort (x:y:[]) = [[x,y]]
splitSort l#(x:y:xs) = fst sl:splitSort (snd sl)
where sl = splitSort' l
I wonder whether this question can be solve using foldr if splits and groups a list from
[5,6,7,2,1,1,1]
to
[[5,6,7],[2,1],[1,1]]
instead of
[[5,6,7],[2],[1,1,1]]
The problem is in each step of foldr, we only know the sorted sub-list on right-hand side and a number to be processed. e.g. after read [1,1] of [5,6,7,2,1,1,1] and next step, we have
1, [[1, 1]]
There are no enough information to determine whether make a new group of 1 or group 1 to [[1,1]]
And therefore, we may construct required sorted sub-lists by reading elements of list from left to right, and why foldl to be used. Here is a solution without optimization of speed.
EDIT:
As the problems that #Jonas Duregård pointed out on comment, some redundant code has been removed, and beware that it is not a efficient solution.
splitSort::Ord a=>[a]->[[a]]
splitSort numList = foldl step [] numList
where step [] n = [[n]]
step sublists n = groupSublist (init sublists) (last sublists) n
groupSublist sublists [n1] n2 = sublists ++ [[n1, n2]]
groupSublist sublists sortedList#(n1:n2:ns) n3
| isEqual n1 n2 = groupIf (isEqual n2 n3) sortedList n3
| isAscen n1 n2 = groupIfNull isAscen sortedList n3
| isDesce n1 n2 = groupIfNull isDesce sortedList n3
| otherwise = mkNewGroup sortedList n3
where groupIfNull check sublist#(n1:n2:ns) n3
| null ns = groupIf (check n2 n3) [n1, n2] n3
| otherwise = groupIf (check (last ns) n3) sublist n3
groupIf isGroup | isGroup = addToGroup
| otherwise = mkNewGroup
addToGroup gp n = sublists ++ [(gp ++ [n])]
mkNewGroup gp n = sublists ++ [gp] ++ [[n]]
isEqual x y = x == y
isAscen x y = x < y
isDesce x y = x > y
My initial thought looks like:
ordruns :: Ord a => [a] -> [[a]]
ordruns = foldr extend []
where
extend a [ ] = [ [a] ]
extend a ( [b] : runs) = [a,b] : runs
extend a (run#(b:c:etc) : runs)
| compare a b == compare b c = (a:run) : runs
| otherwise = [a] : run : runs
This eagerly fills from the right, while maintaining the Ordering in all neighbouring pairs for each sublist. Thus only the first result can end up with a single item in it.
The thought process is this: an Ordering describes the three types of subsequence we're looking for: ascending LT, equal EQ or descending GT. Keeping it the same every time we add on another item means it will match throughout the subsequence. So we know we need to start a new run whenever the Ordering does not match. Furthermore, it's impossible to compare 0 or 1 items, so every run we create contains at least 1 and if there's only 1 we do add the new item.
We could add more rules, such as a preference for filling left or right. A reasonable optimization is to store the ordering for a sequence instead of comparing the leading two items twice per item. And we could also use more expressive types. I also think this version is inefficient (and inapplicable to infinite lists) due to the way it collects from the right; that was mostly so I could use cons (:) to build the lists.
Second thought: I could collect the lists from the left using plain recursion.
ordruns :: Ord a => [a] -> [[a]]
ordruns [] = []
ordruns [a] = [[a]]
ordruns (a1:a2:as) = run:runs
where
runs = ordruns rest
order = compare a1 a2
run = a1:a2:runcontinuation
(runcontinuation, rest) = collectrun a2 order as
collectrun _ _ [] = ([], [])
collectrun last order (a:as)
| order == compare last a =
let (more,rest) = collectrun a order as
in (a:more, rest)
| otherwise = ([], a:as)
More exercises. What if we build the list of comparisons just once, for use in grouping?
import Data.List
ordruns3 [] = []
ordruns3 [a] = [[a]]
ordruns3 xs = unfoldr collectrun marked
where
pairOrder = zipWith compare xs (tail xs)
marked = zip (head pairOrder : pairOrder) xs
collectrun [] = Nothing
collectrun ((o,x):xs) = Just (x:map snd markedgroup, rest)
where (markedgroup, rest) = span ((o==).fst) xs
And then there's the part where there's a groupBy :: (a -> a -> Bool) -> [a] -> [[a]] but no groupOn :: Eq b => (a -> b) -> [a] -> [[a]]. We can use a wrapper type to handle that.
import Data.List
data Grouped t = Grouped Ordering t
instance Eq (Grouped t) where
(Grouped o1 _) == (Grouped o2 _) = o1 == o2
ordruns4 [] = []
ordruns4 [a] = [[a]]
ordruns4 xs = unmarked
where
pairOrder = zipWith compare xs (tail xs)
marked = group $ zipWith Grouped (head pairOrder : pairOrder) xs
unmarked = map (map (\(Grouped _ t) -> t)) marked
Of course, the wrapper type's test can be converted into a function to use groupBy instead:
import Data.List
ordruns5 [] = []
ordruns5 [a] = [[a]]
ordruns5 xs = map (map snd) marked
where
pairOrder = zipWith compare xs (tail xs)
marked = groupBy (\a b -> fst a == fst b) $
zip (head pairOrder : pairOrder) xs
These marking versions arrive at the same decoration concept Jonas Duregård applied.

How to apply a function to a specific element of a list

How can I apply a function to only a single element of a list?
Any suggestion?
Example:
let list = [1,2,3,4,3,6]
function x = x * 2
in ...
I want to apply function only to the first occurance of 3 and stop there.
Output:
List = [1,2,6,4,3,6] -- [1, 2, function 3, 4, 3, 6]
To map or not to map, that is the question.
Better not to map.
Why? Because map id == id anyway, and you only want to map through one element, the first one found to be equal to the argument given.
Thus, split the list in two, change the found element, and glue them all back together. Simple.
See: span :: (a -> Bool) -> [a] -> ([a], [a]).
Write: revappend (xs :: [a]) (ys :: [a]) == append (reverse xs) ys, only efficient.
Or fuse all the pieces together into one function. You can code it directly with manual recursion, or using foldr. Remember,
map f xs = foldr (\x r -> f x : r) [] xs
takeWhile p xs = foldr (\x r -> if p x then x : r else []) [] xs
takeUntil p xs = foldr (\x r -> if p x then [x] else x : r) [] xs
filter p xs = foldr (\x r -> if p x then x : r else r) [] xs
duplicate xs = foldr (\x r -> x : x : r) [] xs
mapFirstThat p f xs = -- ... your function
etc. Although, foldr won't be a direct fit, as you need the combining function of the (\x xs r -> ...) variety. That is known as paramorphism, and can be faked by feeding tails xs to the foldr, instead.
you need to maintain some type of state to indicate the first instance of the value, since map will apply the function to all values.
Perhaps something like this
map (\(b,x) -> if (b) then f x else x) $ markFirst 3 [1,2,3,4,3,6]
and
markFirst :: a -> [a] -> [(Boolean,a)]
markFirst a [] = []
markFirst a (x:xs) | x==a = (True,x): zip (repeat False) xs
| otherwise = (False,x): markFirst a xs
I'm sure there is an easier way, but that's the best I came up with at this time on the day before Thanksgiving.
Here is another approach based on the comment below
> let leftap f (x,y) = f x ++ y
leftap (map (\x -> if(x==3) then f x else x)) $ splitAt 3 [1,2,3,4,3,6]
You can just create a simple function which multiples a number by two:
times_two :: (Num a) => a -> a
times_two x = x * 2
Then simply search for the specified element in the list, and apply times_two to it. Something like this could work:
map_one_element :: (Eq a, Num a) => a -> (a -> a) -> [a] -> [a]
-- base case
map_one_element _ _ [] = []
-- recursive case
map_one_element x f (y:ys)
-- ff element is found, apply f to it and add rest of the list normally
| x == y = f y : ys
-- first occurence hasnt been found, keep recursing
| otherwise = y : map_one_element x f ys
Which works as follows:
*Main> map_one_element 3 times_two [1,2,3,4,3,6]
[1,2,6,4,3,6]

Haskell - converting High Order Function to recursive function

requirement:write function single - Tests whether exactly one element of a list satisfies a given condition.
single :: (a -> Bool) -> [a] -> Bool
I wrote this function:
single p xs = count p xs == 1
where count pred = length . filter pred
Question: What is the easy (correct) way to convert the above functions into one recursive function without using " High Order Functions"?
You can do like that:
single p = lookupFirst
where
lookupFirst [] = False
lookupFirst (x:xs) | p x = lookupSecond xs
| otherwise = lookupFirst xs
lookupSecond [] = True
lookupSecond (x:xs) | p x = False
| otherwise = lookupSecond xs
We can use a none predicate that checks if the remainder of the list does not satisfy the condition:
single :: (a -> Bool) -> [a] -> Bool
single p [] = False
single p (x:xs) | p x = none p xs
| otherwise = single p xs
none :: (a -> Bool) -> [a] -> Bool
none _ [] = True
none p (x:xs) = not (p x) && none p xs
We thus also defined a none function that checks that no element in the given list satisfies a given predicate.
Or without passing the predicate through the recursion:
single :: (a -> Bool) -> [a] -> Bool
single p = helper
where helper [] = False
helper (x:xs) | p x = none xs
| otherwise = helper xs
none [] = True
none (x:xs) = not (p x) && none xs
The above written functions will also immediately stop from the moment a second item is found that satisfies the predicate. This can be useful if we work for instance with an infinite list. If there is a second item that satisfies the constraint, then the function will stop, if no such element or only one such element will ever be generated, we will however get stuck in an infinite loop (there is no much we can do about this). For example:
*Main> single even [1..] -- two or more elements satisfy the constraint
False
*Main> single even [1,3..] -- no element satisfies the constraint
^CInterrupted.
*Main> single even ([1,2]++[3,5..]) -- one element satisfies the constraint
^CInterrupted.
xor and foldl
The most intuitive thing I can thing of is to just fold xor (exclusive or) and your function f thru the list. In case you're not familiar with the binary function xor, it returns True only when (at most) 1 of its arguments are True; otherwise False
xor :: Bool -> Bool -> Bool
xor True b = not b
xor False b = b
single :: (a -> Bool) -> [a] -> Bool
single f [] = False
single f xs = foldl (\acc -> xor acc . f) False xs
main = do
putStrLn $ show (single even []) -- False
putStrLn $ show (single even [1]) -- False
putStrLn $ show (single even [2]) -- True
putStrLn $ show (single even [1,2]) -- True
putStrLn $ show (single even [1,2,3]) -- True
putStrLn $ show (single even [1,2,3,4]) -- False
Xor monoid
xor can be nicely encoded as a Monoid tho, which lends single to a more algebraic implementation using foldMap.
data Xor = Xor Bool
instance Monoid Xor where
mempty = Xor False
mappend (Xor True) (Xor b) = Xor (not b)
mappend (Xor False) (Xor b) = Xor b
single f xs = aux $ foldMap (Xor . f) xs
where
aux (Xor b) = b
main = do
putStrLn $ show (single even []) -- False
putStrLn $ show (single even [1]) -- False
putStrLn $ show (single even [2]) -- True
putStrLn $ show (single even [1,2]) -- True
putStrLn $ show (single even [1,2,3]) -- True
putStrLn $ show (single even [1,2,3,4]) -- False
auxiliary helper
This is another way you can do it with an auxiliary helper. This one has an added benefit in that it exits immediately (stops iteration thru the list) after an answer is determined
single :: (a -> Bool) -> [a] -> Bool
single f xs = aux False f xs
where
aux b f [] = b
aux True f (x:xs) = if (f x) then False else aux True f (xs)
aux False f (x:xs) = aux (f x) f xs
main = do
putStrLn $ show (single even []) -- False
putStrLn $ show (single even [1]) -- False
putStrLn $ show (single even [2]) -- True
putStrLn $ show (single even [1,2]) -- True
putStrLn $ show (single even [1,2,3]) -- True
putStrLn $ show (single even [1,2,3,4]) -- False
feedback welcome!
I'm a Haskell newbie but maybe these ideas are interesting to you. Or maybe they're bad! Leave me a comment if there's anything I can do to improve the answer ^_^

How to partition a list in Haskell?

I want to take a list (or a string) and split it into sub-lists of N elements. How do I do it in Haskell?
Example:
mysteryFunction 2 "abcdefgh"
["ab", "cd", "ef", "gh"]
cabal update
cabal install split
And then use chunksOf from Data.List.Split
Here's one option:
partition :: Int -> [a] -> [[a]]
partition _ [] = []
partition n xs = (take n xs) : (partition n (drop n xs))
And here's a tail recursive version of that function:
partition :: Int -> [a] -> [[a]]
partition n xs = partition' n xs []
where
partition' _ [] acc = reverse acc
partition' n xs acc = partition' n (drop n xs) ((take n xs) : acc)
You could use:
mysteryFunction :: Int -> [a] -> [[a]]
mysteryFunction n list = unfoldr takeList list
where takeList [] = Nothing
takeList l = Just $ splitAt n l
or alternatively:
mysteryFunction :: Int -> [a] -> [[a]]
mysteryFunction n list = unfoldr (\l -> if null l then Nothing else Just $ splitAt n l) list
Note this puts any remaining elements in the last list, for example
mysteryFunction 2 "abcdefg" = ["ab", "cd", "ef", "g"]
import Data.List
import Data.Function
mysteryFunction n = map (map snd) . groupBy ((==) `on` fst) . zip ([0..] >>= replicate n)
... just kidding...
mysteryFunction x "" = []
mysteryFunction x s = take x s : mysteryFunction x (drop x s)
Probably not the elegant solution you had in mind.
There's already
Prelude Data.List> :t either
either :: (a -> c) -> (b -> c) -> Either a b -> c
and
Prelude Data.List> :t maybe
maybe :: b -> (a -> b) -> Maybe a -> b
so there really should be
list :: t -> ([a] -> t) -> [a] -> t
list n _ [] = n
list _ c xs = c xs
as well. With it,
import Data.List (unfoldr)
g n = unfoldr $ list Nothing (Just . splitAt n)
without it,
g n = takeWhile (not.null) . unfoldr (Just . splitAt n)
A fancy answer.
In the answers above you have to use splitAt, which is recursive, too. Let's see how we can build a recursive solution from scratch.
Functor L(X)=1+A*X can map X into a 1 or split it into a pair of A and X, and has List(A) as its minimal fixed point: List(A) can be mapped into 1+A*List(A) and back using a isomorphism; in other words, we have one way to decompose a non-empty list, and only one way to represent a empty list.
Functor F(X)=List(A)+A*X is similar, but the tail of the list is no longer a empty list - "1" - so the functor is able to extract a value A or turn X into a list of As. Then List(A) is its fixed point (but no longer the minimal fixed point), the functor can represent any given list as a List, or as a pair of a element and a list. In effect, any coalgebra can "stop" decomposing the list "at will".
{-# LANGUAGE DeriveFunctor #-}
import Data.Functor.Foldable
data N a x = Z [a] | S a x deriving (Functor)
(which is the same as adding the following trivial instance):
instance Functor (N a) where
fmap f (Z xs) = Z xs
fmap f (S x y) = S x $ f y
Consider the definition of hylomorphism:
hylo :: (f b -> b) -> (c -> f c) -> c -> b
hylo psi phi = psi . fmap (hylo psi phi) . phi
Given a seed value, it uses phi to produce f c, to which fmap applies hylo psi phi recursively, and psi then extracts b from the fmapped structure f b.
A hylomorphism for the pair of (co)algebras for this functor is a splitAt:
splitAt :: Int -> [a] -> ([a],[a])
splitAt n xs = hylo psi phi (n, xs) where
phi (n, []) = Z []
phi (0, xs) = Z xs
phi (n, (x:xs)) = S x (n-1, xs)
This coalgebra extracts a head, as long as there is a head to extract and the counter of extracted elements is not zero. This is because of how the functor was defined: as long as phi produces S x y, hylo will feed y into phi as the next seed; once Z xs is produced, functor no longer applies hylo psi phi to it, and the recursion stops.
At the same time hylo will re-map the structure into a pair of lists:
psi (Z ys) = ([], ys)
psi (S h (t, b)) = (h:t, b)
So now we know how splitAt works. We can extend that to splitList using apomorphism:
splitList :: Int -> [a] -> [[a]]
splitList n xs = apo (hylo psi phi) (n, xs) where
phi (n, []) = Z []
phi (0, xs) = Z xs
phi (n, (x:xs)) = S x (n-1, xs)
psi (Z []) = Cons [] $ Left []
psi (Z ys) = Cons [] $ Right (n, ys)
psi (S h (Cons t b)) = Cons (h:t) b
This time the re-mapping is fitted for use with apomorphism: as long as it is Right, apomorphism will keep using hylo psi phi to produce the next element of the list; if it is Left, it produces the rest of the list in one step (in this case, just finishes off the list with []).

Recursively sort non-contiguous list to list of contiguous lists

I've been trying to learn a bit of functional programming (with Haskell & Erlang) lately and I'm always amazed at the succinct solutions people can come up with when they can think recursively and know the tools.
I want a function to convert a list of sorted, unique, non-contiguous integers into a list of contiguous lists, i.e:
[1,2,3,6,7,8,10,11]
to:
[[1,2,3], [6,7,8], [10,11]
This was the best I could come up with in Haskell (two functions)::
make_ranges :: [[Int]] -> [Int] -> [[Int]]
make_ranges ranges [] = ranges
make_ranges [] (x:xs)
| null xs = [[x]]
| otherwise = make_ranges [[x]] xs
make_ranges ranges (x:xs)
| (last (last ranges)) + 1 == x =
make_ranges ((init ranges) ++ [(last ranges ++ [x])]) xs
| otherwise = make_ranges (ranges ++ [[x]]) xs
rangify :: [Int] -> [[Int]]
rangify lst = make_ranges [] lst
It might be a bit subjective but I'd be interested to see a better, more elegant, solution to this in either Erlang or Haskell (other functional languages too but I might not understand it.) Otherwise, points for just fixing my crappy beginner's Haskell style!
Most straightforward way in my mind is a foldr:
ranges = foldr step []
where step x [] = [[x]]
step x acc#((y:ys):zs) | y == x + 1 = (x:y:ys):zs
| otherwise = [x]:acc
Or, more concisely:
ranges = foldr step []
where step x ((y:ys):zs) | y == x + 1 = (x:y:ys):zs
step x acc = [x]:acc
But wait, there's more!
abstractRanges f = foldr step []
where step x ((y:ys):zs) | f x y = (x:y:ys):zs
step x acc = [x]:acc
ranges = abstractRanges (\x y -> y == x + 1)
powerRanges = abstractRanges (\x y -> y == x*x) -- mighty morphin
By turning the guard function into a parameter, you can group more interesting things than just +1 sequences.
*Main> powerRanges [1,1,1,2,4,16,3,9,81,5,25]
[[1,1,1],[2,4,16],[3,9,81],[5,25]]
The utility of this particular function is questionable...but fun!
I can't believe I got the shortest solution. I know this is no code golf, but I think it is still quite readable:
import GHC.Exts
range xs = map (map fst) $ groupWith snd $ zipWith (\a b -> (a, a-b)) xs [0..]
or pointfree
range = map (map snd) . groupWith fst . zipWith (\a b -> (b-a, b)) [0..]
BTW, groupWith snd can be replaced with groupBy (\a b -> snd a == snd b) if you prefer Data.List over GHC.Exts
[Edit]
BTW: Is there a nicer way to get rid of the lambda (\a b -> (b-a, b)) than (curry $ (,) <$> ((-) <$> snd <*> fst) <*> snd) ?
[Edit 2]
Yeah, I forgot (,) is a functor. So here is the obfuscated version:
range = map (map fst) . groupWith snd . (flip $ zipWith $ curry $ fmap <$> (-).fst <*> id) [0..]
Suggestions are welcome...
import Data.List (groupBy)
ranges xs = (map.map) snd
. groupBy (const fst)
. zip (True : zipWith ((==) . succ) xs (tail xs))
$ xs
As to how to come up with such a thing: I started with the zipWith f xs (tail xs), which is a common idiom when you want to do something on consecutive elements of a list. Likewise is zipping up a list with information about the list, and then acting (groupBy) upon it. The rest is plumbing.
Then, of course, you can feed it through #pl and get:
import Data.List (groupBy)
import Control.Monad (ap)
import Control.Monad.Instances()
ranges = (((map.map) snd)
. groupBy (const fst))
.) =<< zip
. (True:)
. ((zipWith ((==) . succ)) `ap` tail)
, which, by my authoritative definition, is evil due to Mondad ((->) a). Twice, even. The data flow is meandering too much to lay it out in any sensible way. zipaptail is an Aztec god, and Aztec gods aren't to be messed with.
Another version in Erlang:
part(List) -> part(List,[]).
part([H1,H2|T],Acc) when H1 =:= H2 - 1 ->
part([H2|T],[H1|Acc]);
part([H1|T],Acc) ->
[lists:reverse([H1|Acc]) | part(T,[])];
part([],Acc) -> Acc.
k z = map (fst <$>) . groupBy (const snd) .
zip z . (False:) . (zipWith ((==) . succ) <*> tail) $ z
Try reusing standard functions.
import Data.List (groupBy)
rangeify :: (Num a) => [a] -> [[a]]
rangeify l = map (map fst) $ groupBy (const snd) $ zip l contigPoints
where contigPoints = False : zipWith (==) (map (+1) l) (drop 1 l)
Or, following (mixed) advice to use unfoldr, stop abusing groupBy, and be happy using partial functions when it doesn't matter:
import Control.Arrow ((***))
import Data.List (unfoldr)
spanContig :: (Num a) => [a] -> [[a]]
spanContig l =
map fst *** map fst $ span (\(a, b) -> a == b + 1) $ zip l (head l - 1 : l)
rangeify :: (Num a) => [a] -> [[a]]
rangeify = unfoldr $ \l -> if null l then Nothing else Just $ spanContig l
Erlang using foldr:
ranges(List) ->
lists:foldr(fun (X, [[Y | Ys], Acc]) when Y == X + 1 ->
[[X, Y | Ys], Acc];
(X, Acc) ->
[[X] | Acc]
end, [], List).
This is my v0.1 and I can probably make it better:
makeCont :: [Int] -> [[Int]]
makeCont [] = []
makeCont [a] = [[a]]
makeCont (a:b:xs) = if b - a == 1
then (a : head next) : tail next
else [a] : next
where
next :: [[Int]]
next = makeCont (b:xs)
And I will try and make it better. Edits coming I think.
As a comparison, here's an implementation in Erlang:
partition(L) -> [lists:reverse(T) || T <- lists:reverse(partition(L, {[], []}))].
partition([E|L], {R, [EL|_] = T}) when E == EL + 1 -> partition(L, {R, [E|T]});
partition([E|L], {R, []}) -> partition(L, {R, [E]});
partition([E|L], {R, T}) -> partition(L, {[T|R], [E]});
partition([], {R, []}) -> R;
partition([], {R, T}) -> [T|R].
The standard paramorphism recursion scheme isn't in Haskell's Data.List module, though I think it should be. Here's a solution using a paramorphism, because you are building a list-of-lists from a list, the cons-ing is a little tricksy:
contig :: (Eq a, Num a) => [a] -> [[a]]
contig = para phi [] where
phi x ((y:_),(a:acc)) | x + 1 == y = (x:a):acc
phi x (_, acc) = [x]:acc
Paramorphism is general recursion or a fold with lookahead:
para :: (a -> ([a], b) -> b) -> b -> [a] -> b
para phi b [] = b
para phi b (x:xs) = phi x (xs, para phi b xs)
It can be pretty clear and simple in the Erlang:
partition([]) -> [];
partition([A|T]) -> partition(T, [A]).
partition([A|T], [B|_]=R) when A =:= B+1 -> partition(T, [A|R]);
partition(L, P) -> [lists:reverse(P)|partition(L)].
Edit: Just for curiosity I have compared mine and Lukas's version and mine seems about 10% faster either in native either in bytecode version on testing set what I generated by lists:usort([random:uniform(1000000)||_<-lists:seq(1,1000000)]) on R14B01 64b version at mine notebook. (Testing set is 669462 long and has been partitioned to 232451 sublists.)
Edit2: Another test data lists:usort([random:uniform(1000000)||_<-lists:seq(1,10000000)]), length 999963 and 38 partitions makes bigger diference in native code. Mine version finish in less than half of time. Bytecode version is only about 20% faster.
Edit3: Some microoptimizations which provides additional performance but leads to more ugly and less maintainable code:
part4([]) -> [];
part4([A|T]) -> part4(T, A, []).
part4([A|T], B, R) when A =:= B+1 -> part4(T, A, [B|R]);
part4([A|T], B, []) -> [[B]|part4(T, A, [])];
part4([A|T], B, R) -> [lists:reverse(R, [B])|part4(T, A, [])];
part4([], B, R) -> [lists:reverse(R,[B])].
Here's an attempt from a haskell noob
ranges ls = let (a, r) = foldl (\(r, a#(h:t)) e -> if h + 1 == e then (r, e:a) else (a:r, [e])) ([], [head ls]) (tail ls)
in reverse . map reverse $ r : a

Resources