Combining fragments of Haskell Code to get the bigger picture - haskell

This is the code that I came upon somewhere but want to know how this works:
findIndices :: (a -> Bool) -> [a] -> [Int]
findIndices _ [] = []
findIndices pred xs = map fst (filter (pred . snd) (zip [0..] xs))
Output: findIndices (== 0) [1,2,0,3,0] == [2,4], where pred is (==0) & xs is [1,2,0,3,0]
I'll show some of my understanding:
(zip [0..] xs)
What the above line does is put indices to everything in the list. For the input given above, it would look like this: [(0,1),(1,2),(2,0),(3,3),(4,0)].
(pred . snd)
I found that this means something like pred (snd (x)). My question is, is x the list made from the zip line? I'm leaning towards yes but my guess is flimsy.
Next, is my understanding of fst and snd. I know that
fst(1,2) = 1
and
snd(1,2) = 2
How do these two commands make sense in the code?
My understanding of filter is that it returns a list of items that match a condition. For instance,
listBiggerThen5 = filter (>5) [1,2,3,4,5,6,7,8,9,10]
would give [6,7,8,9,10]
My understanding of map is that it applies a function to every item on the list. For instance,
times4 :: Int -> Int
times4 x = x * 4
listTimes4 = map times4 [1,2,3,4,5]
would give [4,8,12,16,20]
How does this work overall? I think I have been comprehensive in what I know so far but can't quite put the pieces together. Can anybody help me out?

I found that this means something like pred (snd (x)). My question is, is x the list made from the zip line? I'm leaning towards yes but my guess is flimsy.
Well pred . snd, means \x -> pred (snd x). So this basically constructs a function that maps an element x on pred (snd x).
This thus means that the expression looks like:
filter (\x -> pred (snd x)) (zip [0..] xs)
Here x is thus a 2-tuple generated by zip. So in order to know if (0, 1), (1,2), (2, 0), etc. are retained in the result, snd x will take the second element of these 2-tuples (so 1, 2, 0, etc.), and check if the pred on tha element is satisfied or not. If it is satisfied, it will retain the element, otherwise that element (the 2-tuple) is filtered out.
So if (== 0) is the predicate, then filter (pred . snd) (zip [0..] xs) will contain the 2-tuples [(2, 0), (4, 0)].
But now the result is a list of 2-tuples. If we want the indices, we somehow need to get rid of the 2-tuple, and the second element of these 2-tuples. We use fst :: (a, b) -> a for that: this maps a 2-tuple on its first element. So for a list [(2, 0), (4, 0)], map fst [(2, 0), (4, 0)] will return [2, 4].

In Haskell we like to say, follow the types. Indeed the pieces connect as if by wires going from type to corresponding type:
( first, function composition is:
(f >>> g) x = (g . f) x = g (f x)
(f >>> g) = (g . f) = \x -> g (f x)
and function composition type inference rule is:
f :: a -> b -- x :: a
g :: b -> c -- f x :: b
------------------------- -- g (f x) :: c
f >>> g :: a -> c
g . f :: a -> c
Now, )
findIndices :: (b -> Bool) -> [b] -> [Int]
findIndices pred = \xs -> map fst ( filter (pred . snd) ( zip [0..] xs ))
= map fst . filter (pred . snd) . zip [0..]
= zip [0..] >>> filter (snd >>> pred) >>> map fst
---------------------------------------------------------------------------
zip :: [a] -> [b] -> [(a, b)]
zip [0..] :: [b] -> [(Int,b)]
---------------------------------------------------------------------------
snd :: (a,b) -> b
pred :: b -> Bool
------------------------------------
(snd >>> pred) :: (a,b) -> Bool
---------------------------------------------------------------------------
filter :: (t -> Bool) -> [t] -> [t]
filter (snd >>> pred) :: [(a,b)] -> [(a,b)]
filter (snd >>> pred) :: [(Int,b)] -> [(Int,b)]
---------------------------------------------------------------------------
fst :: (a, b) -> a
map :: (t -> s) -> [t] -> [s]
map fst :: [(a,b)] -> [a]
map fst :: [(Int,b)] -> [Int]
so, overall,
zip [0..] :: [b] -> [(Int,b)]
filter (snd >>> pred) :: [(Int,b)] -> [(Int,b)]
map fst :: [(Int,b)] -> [Int]
---------------------------------------------------------------------------
findIndices pred :: [b] -> [Int]
You've asked, how do these pieces fit together?
This is how.
With list comprehensions, your function is written as
findIndices pred xs = [ i | (i,x) <- zip [0..] xs, pred x ]
which in pseudocode reads:
"result list contains i for each (i,x) in zip [0..] xs such that pred x holds".
It does this by turning the n-long
xs = [a,b,...,z] = [a] ++ [b] ++ ... ++ [z]
into
[0 | pred a] ++ [1 | pred b] ++ ... ++ [n-1 | pred z]
where [a | True] is [a] and [a | False] is [].

Related

Error on matching the type signature on function for a list of pairs

I am trying to write a function that takes a list of pairs, ex. [(1,2),(1,4),(2,5),(3,4),(1,8)] and it returns the list of the sum of the second values of each pair, for each of first value in a sorted manner. ex.[14,5,4].
To do this I made a comprehension list to fold the second values from a list of pairs, and a comprehension list where the list of pairs is filtered by the first value.
addSec :: (Num a, Num b) => [(a,b)] -> b
addSec a = foldr (+) 0 (map snd a)
listf ::(Num a,Enum a,Eq a,Fractional a,RealFrac a)=> a ->[a]
listf g = [ a | x <- [0..g], a <- addSec(filter ((== x ).fst) z ) ]
where
z=[ (x,y) | x <-reverse [1..553],
let s = x * (fromIntegral (ceiling(504 / x))) - 504,
y <- [s..g] ]
I have tried the functions
foldr (+) 0 (map snd a)
filter ((== x ).fst) z
separately on Prelude> and they work as intended but I get this sort of error in a program:
try.hs:20:36: error:
* Occurs check: cannot construct the infinite type: a ~ [a]
* In the expression: addSec (filter ((== x) . fst) z)
In a stmt of a list comprehension:
a <- addSec (filter ((== x) . fst) z)
In the expression:
[a | x <- [0 .. g], a <- addSec (filter ((== x) . fst) z)]
* Relevant bindings include
x :: a (bound at try.hs:20:18)
z :: [(a, a)] (bound at try.hs:22:25)
g :: a (bound at try.hs:20:7)
listf :: a -> [a] (bound at try.hs:20:1)
|
20 | listf g = [ a | x <- [0..g], a <- addSec(filter ((== x ).fst) z ) ]
| ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
Failed, no modules loaded.
I get similar errors even when the type signature is:
addSec :: [(a,b)] -> a
So I am not sure what to change. Thank you very much, I appreciate any help.

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

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

If I can define a function in terms of foldl, would it make it tail recursive?

I was given an assignment in my functional programming course that asks me to rewrite several functions, like map and filter to be tail recursive.
I'm not 100% sure how to go about this yet but I know that you can define functions by calling foldr and foldl. I know foldl is tail recursive, so if I can define say, filter with foldl, would it become tail recursive, too?
There are two ways to make a recursive function tail recursive:
Convert the function to accumulator passing style. This only works in some cases.
Convert the function to continuation passing style. This works in all cases.
Consider the definition of the map function:
map :: (a -> b) -> [a] -> [b]
map _ [] = []
map f (x:xs) = f x : map f xs
In accumulator passing style, we have an additional argument which accumulates the result:
mapA :: (a -> b) -> [a] -> [b] -> [b]
mapA _ [] = id
mapA f (x:xs) = mapA f xs . (f x :)
The original map function can be recovered as follows:
map :: (a -> b) -> [a] -> [b]
map f xs = reverse $ mapA f xs []
Note that we need to reverse the result. This is because mapA accumulates the result in reverse:
> mapA (+1) [1,2,3,4,5] []
> mapA (+1) [2,3,4,5] [2]
> mapA (+1) [3,4,5] [3,2]
> mapA (+1) [3,5] [4,3,2]
> mapA (+1) [5] [5,4,3,2]
> mapA (+1) [] [6,5,4,3,2]
> [6,5,4,3,2]
Now, consider continuation passing style:
mapK :: (a -> b) -> [a] -> ([b] -> r) -> r
mapK _ [] k = k []
mapK f (x:xs) k = mapK f xs (k . (f x :))
The original map function can be recovered as follows:
map :: (a -> b) -> [a] -> [b]
map f xs = mapK f xs id
Note that we do not need to reverse the result. This is because although mapK accumulates the continuations in reverse, yet when finally applied to the base case the continuations are unfolded to produce the result in the correct order:
> mapK (+1) [1,2,3,4,5] id
> mapK (+1) [2,3,4,5] (id . (2:))
> mapK (+1) [3,4,5] (id . (2:) . (3:))
> mapK (+1) [4,5] (id . (2:) . (3:) . (4:))
> mapK (+1) [5] (id . (2:) . (3:) . (4:) . (5:))
> mapK (+1) [] (id . (2:) . (3:) . (4:) . (5:) . (6:))
> (id . (2:) . (3:) . (4:) . (5:) . (6:)) []
> (id . (2:) . (3:) . (4:) . (5:)) [6]
> (id . (2:) . (3:) . (4:)) [5,6]
> (id . (2:) . (3:)) [4,5,6]
> (id . (2:)) [3,4,5,6]
> id [2,3,4,5,6]
> [2,3,4,5,6]
Note, that in both cases we're doing twice the required amount of work:
First, we accumulate an intermediate result in reverse order.
Next, we produce the final result in the correct order.
Some functions can be written efficiently in the accumulator passing style (e.g. the sum function):
sumA :: Num a => [a] -> a -> a
sumA [] = id
sumA (x:xs) = sumA xs . (+ x)
The original sum function can be recovered as follows:
sum :: Num a => [a] -> a
sum xs = sumA xs 0
Note that we don't need to do any post processing on the result.
However, list functions written in tail recursive style always need to be reversed. Hence, we do not write list functions in tail recursive style. Instead, we depend upon laziness to process only as much of the list as required.
It should be noted that continuation passing style is just a special case of accumulator passing style. Since foldl is both tail recursive and uses an accumulator, you can write mapA and mapK using foldl as follows:
mapA :: (a -> b) -> [a] -> [b] -> [b]
mapA f xs acc = foldl (\xs x -> f x : xs) acc xs
mapK :: ([b] -> r) -> (a -> b) -> [a] -> r
mapK k f xs = foldl (\k x xs -> k (f x : xs)) k xs []
For, mapK if you take the k to be id then you get map:
map :: (a -> b) -> [a] -> [b]
map f xs = foldl (\k x xs -> k (f x : xs)) id xs []
Similarly, for filter:
filter :: (a -> Bool) -> [a] -> [a]
filter p xs = foldl (\k x xs -> k (if p x then x : xs else xs)) id xs []
There you have it, tail recursive map and filter functions. However, don't forget that they are actually doing twice the work. In addition, they won't work for infinite lists because the result will not be generated until the end of the list is reached (which will never happen for infinite lists).
I'm suspecting the professor/lecturer is expecting solutions where tail recursion is used "directly", i.e. lexically, within the source code of the function, not indirectly, or "dynamically", where tail recursion only happens at runtime within the scope of some subroutine call.
Otherwise, you might as well supply e.g. Prelude.foldl as the implementation for a custom foldl of yours, since it, possibly, uses tail recursion under the hood, and thus does yours:
import Prelude as P
foldl = P.foldl
but obviously something like that wouldn't be accepted.

Haskell: List Comprehensions and higher-order functions

I've tried to transform the following list comprehension:
f xs = [ x+8 | (x,_) <- xs ]
using higher-order functions.
My first solution was:
f' xs = map (\(x,_) -> x+8) xs
After I tried various other approaches, I found out that the following also works:
f' xs = map((+8).fst) xs
Both versions of f' give the same (correct) output, but I don't understand why (+8).fst is equal to \(x,_) -> x+8 when using map on a list of tuples.
The definition of fst is
fst :: (a, b) -> a
fst (a, _) = a
and the definition of (.) is
(.) :: (b -> c) -> (a -> b) -> a -> c
(f . g) = \x -> f (g x)
If we use these definitions to expand your function, we get
f' xs = map ((+8) . fst) xs
f' xs = map (\x -> (+8) (fst x)) xs -- definition of (.)
f' xs = map (\x -> (+8) ((\(a, _) -> a) x)) -- definition of fst
f' xs = map (\(a, _) -> (+8) a) -- we can move the pattern matching
f' xs = map (\(a, _) -> a + 8) -- expand section
Both versions of f' give the same (correct) output, but I don't understand why (+8).fst is equal to (x,_) -> x+8 when using map on a list of tuples.
The type of fst is:
fst :: (a, b) -> a
and what it does is it takes the first element of a pair (a tuple of two elements).
The type of (+8) is:
(+8) :: Num a => a -> a
and what it does is it takes as input a Num, applies + 8 to it and returns the result.
Now, the type of (+8) . fst is:
((+8).fst) :: Num c => (c, b) -> c
which is the composition of fst and (+8). Specifically it's the function that takes as input a pair, extracts the first element and adds 8 to it.
This can be easily seen by seen an example:
((+8).fst) (3, 'a')
-- 11
The same thing happens with \ (x, _) -> x + 8. You take a pair as input (in the lambda), pattern match the first argument to x, increment it by 8 and return it:
(\ (x, _) -> x + 8) (3, 'a')
-- 11

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