List of numbers to list of ranges

Hi all, Here's my attempt to convert a list of integers to a list of range tuples - Given [1,2,3,6,8,9,10], I need [(1,3),(6,6),8,10)] My attempt using foldl yields me the output in reverse. I can ofcourse reverse the result, but what would be a better way? f xs = foldl ff [] xs where [] `ff` i = [(i,i)] ((s,e):ns) `ff` i = if i == e+1 then (s,i):ns else (i,i):(s,e):ns Regards, Kashyap

On Thursday 23 December 2010 18:27:43, C K Kashyap wrote:
Hi all,
Here's my attempt to convert a list of integers to a list of range tuples -
Given [1,2,3,6,8,9,10], I need [(1,3),(6,6),8,10)]
My attempt using foldl yields me the output in reverse. I can ofcourse reverse the result, but what would be a better way?
f xs = foldl ff [] xs where [] `ff` i = [(i,i)] ((s,e):ns) `ff` i = if i == e+1 then (s,i):ns else (i,i):(s,e):ns
A right fold? It's easier, at least: Prelude> let foo k [] = [(k,k)]; foo k xs@((l,h):t) = if l == k+1 then (k,h):t else (k,k):xs Prelude> foldr foo [] [1,2,3,6,8,9,10] [(1,3),(6,6),(8,10)]
Regards, Kashyap

On Thu, 23 Dec 2010, Daniel Fischer wrote:
On Thursday 23 December 2010 18:27:43, C K Kashyap wrote:
Hi all,
Here's my attempt to convert a list of integers to a list of range tuples -
Given [1,2,3,6,8,9,10], I need [(1,3),(6,6),8,10)]
My attempt using foldl yields me the output in reverse. I can ofcourse reverse the result, but what would be a better way?
f xs = foldl ff [] xs where [] `ff` i = [(i,i)] ((s,e):ns) `ff` i = if i == e+1 then (s,i):ns else (i,i):(s,e):ns
A right fold? It's easier, at least:
Prelude> let foo k [] = [(k,k)]; foo k xs@((l,h):t) = if l == k+1 then (k,h):t else (k,k):xs Prelude> foldr foo [] [1,2,3,6,8,9,10] [(1,3),(6,6),(8,10)]
I admit your solution is much more comprehensible than my one. However, my second complicated solution should be more efficient and especially works as good as possible on infinite lists: Prelude> List.unfoldr (...) [1..] [(1, I try other ones (using Data.List.HT from utility-ht): Prelude> map (\xs -> (head xs, last xs)) $ Data.List.HT.groupBy (\a b -> a+1==b) [1,2,3,6,8,9,10] [(1,3),(6,6),(8,10)] Prelude> map (\xs@(x:_) -> (x, x + length xs - 1)) $ Data.List.HT.groupBy (\a b -> a+1==b) [1,2,3,6,8,9,10] [(1,3),(6,6),(8,10)] The second one should not have a memory leak, like the first one. If you prefer an explicit recursive solution, how about this one: Prelude> let ranges xs = (case xs of [] -> []; y:ys -> aux0 y ys); aux0 y ys = let (end,remainder) = aux1 y ys in (y,end) : remainder; aux1 predec xs = case xs of [] -> (predec, []); y:ys -> if predec+1 == y then aux1 y ys else (predec, aux0 y ys) Prelude> ranges [1,2,3,6,8,9,10] [(1,3),(6,6),(8,10)]

On Thu, 23 Dec 2010, C K Kashyap wrote:
Here's my attempt to convert a list of integers to a list of range tuples -
Given [1,2,3,6,8,9,10], I need [(1,3),(6,6),8,10)]
That's an interesting problem! My first attempt:
List.unfoldr (\xs -> case xs of [] -> Nothing; y:ys -> case span (uncurry (==)) $ zip xs [y..] of (matching, remainder) -> Just ((y, fst $ last matching), map fst remainder)) [1,2,3,6,8,9,10] [(1,3),(6,6),(8,10)]
However, the use of 'last' will course a memory leak for long ranges, and the (map fst remainder) reconstructs the remainder of the list, and thus needs linear time instead of constant one. Here is my second attempt, developed in GHCi and variable names that should be improved ... List.unfoldr (\xs -> case xs of [] -> Nothing; y:ys -> case dropWhile (\(a,b,t) -> case t of [] -> False; h:_ -> a==h) $ zip3 [y+1..] xs (List.tails ys) of ~((_, end, remainder):_) -> Just ((y, end), remainder)) [1,2,3,6,8,9,10] Using zip3 I have bundled all information that I need after 'dropWhile' in order to proceed: The end of the current range and the remaining numbers.

On Thursday 23 December 2010 18:27:43, C K Kashyap wrote:
Hi all,
Here's my attempt to convert a list of integers to a list of range tuples -
Given [1,2,3,6,8,9,10], I need [(1,3),(6,6),8,10)]
My attempt using foldl yields me the output in reverse. I can ofcourse reverse the result, but what would be a better way?
f xs = foldl ff [] xs where [] `ff` i = [(i,i)] ((s,e):ns) `ff` i = if i == e+1 then (s,i):ns else (i,i):(s,e):ns
Regards, Kashyap
I suggested:
Prelude> let foo k [] = [(k,k)]; foo k xs@((l,h):t) = if l == k+1 then (k,h):t else (k,k):xs Prelude> foldr foo [] [1,2,3,6,8,9,10] [(1,3),(6,6),(8,10)]
Lazier is better: bar k xs = (k,m):t where (m,t) = case xs of [] -> (k,[]) (l,h):u | l == k+1 -> (h,u) | otherwise -> (k,xs) Prelude> foldr foo [] [1 .. 1000000] [(1,1000000)] (15.46 secs, 226229904 bytes) Prelude> foldr bar [] [1 .. 1000000] [(1,1000000)] (3.47 secs, 242992364 bytes)

On Thu, Dec 23, 2010 at 10:57:43PM +0530, C K Kashyap wrote:
Here's my attempt to convert a list of integers to a list of range tuples -
Given [1,2,3,6,8,9,10], I need [(1,3),(6,6),8,10)]
import Data.Function import Data.List ranges ns = [(head gp, last gp) | gp <- map (map fst) $ groupBy ((==) `on` snd) $ zip ns (zipWith (-) ns [1..])]

I'd go with direct recursion for this one - the pattern of consumption and production that generates the answer doesn't seem to neatly match any of the standard recursion combinators (map, unfold, fold, mapAccum, ...) nor exotic ones (skipping streams c.f. the Stream fusion paper, apomorphisms, ...). Direct recursion might be prosaic, but it is pleasantly obvious: ranges :: (Num a, Eq a) => [a] -> [(a,a)] ranges [] = [] ranges (a:as) = step (a,a) as where step (i,j) [] = [(i,j)] step (i,j) (x:xs) | j+1 == x = step (i,x) xs step (i,j) (x:xs) = (i,j) : step (x,x) xs

On 23 December 2010 21:12, Stephen Tetley
I'd go with direct recursion for this one - the pattern of consumption and production that generates the answer doesn't seem to neatly match any of the standard recursion combinators (map, unfold, fold, mapAccum, ...) nor exotic ones (skipping streams c.f. the Stream fusion paper, apomorphisms, ...).
Here's a synthesized functional that matches the needed behaviour. It takes from: a) apomorphism - has a final flush operation b) skipping streams (the Stream fusion paper) - a skipping Next case, though in this case there is no Done c) unfoldMap - itself a synthetic combination of unfold and map, which is unfolding against a list as well as state (the unfold equivalent of mapAccumL). Unimaginatively I've called it "lessproductive" as it can produce less than it consumes, though as it has no Done it must consume everything... data Step st a = Yield a !st | Next !st lessproductive :: (st -> a -> Step st b) -> (st -> b) -> st -> [a] -> [b] lessproductive phi flush = step where step st [] = [flush st] step st (x:xs) = case phi st x of Next st' -> step st' xs Yield b st' -> b : step st' xs ranges :: (Num a, Eq a) => [a] -> [(a,a)] ranges [] = [] ranges (x:xs) = lessproductive phi id (x,x) xs where phi (i,j) n | j+1 == n = Next (i,n) phi ans n = Yield ans (n,n)

On Thu, 23 Dec 2010, Stephen Tetley wrote:
On 23 December 2010 21:12, Stephen Tetley
wrote: I'd go with direct recursion for this one - the pattern of consumption and production that generates the answer doesn't seem to neatly match any of the standard recursion combinators (map, unfold, fold, mapAccum, ...) nor exotic ones (skipping streams c.f. the Stream fusion paper, apomorphisms, ...).
Here's a synthesized functional that matches the needed behaviour.
It takes from:
a) apomorphism - has a final flush operation b) skipping streams (the Stream fusion paper) - a skipping Next case, though in this case there is no Done c) unfoldMap - itself a synthetic combination of unfold and map, which is unfolding against a list as well as state (the unfold equivalent of mapAccumL).
Unimaginatively I've called it "lessproductive" as it can produce less than it consumes, though as it has no Done it must consume everything...
data Step st a = Yield a !st | Next !st
This could be seen as "type Step st a = (Maybe a, st)". I have thought about mapping from [Int] to [Maybe (Int, Int)] by mapAccumL, then compressing the result with catMaybes. However we need to append a final pair when the end of the list is reached, which risks a memory leak.

On 23 December 2010 22:01, Henning Thielemann
This could be seen as "type Step st a = (Maybe a, st)". I have thought about mapping from [Int] to [Maybe (Int, Int)] by mapAccumL, then compressing the result with catMaybes. However we need to append a final pair when the end of the list is reached, which risks a memory leak.
Hi Henning Thanks - that's an extra nesting of constructors though. Note the flush in the original was always doomed to be productive - this revision might be better, the flush now has the option of producing nothing or many: lessproductive :: (st -> a -> Step st b) -> (st -> [b]) -> st -> [a] -> [b] lessproductive phi flush = step where step st [] = flush st step st (x:xs) = case phi st x of Next st' -> step st' xs Yield b st' -> b : step st' xs ranges2 :: (Num a, Eq a) => [a] -> [(a,a)] ranges2 [] = [] ranges2 (x:xs) = lessproductive phi (\a -> [a]) (x,x) xs where phi (i,j) n | j+1 == n = Next (i,n) phi ans n = Yield ans (n,n)

This one looks somewhat symmetrical: f xs = let xys = filter ( \ (x,y) -> y - x > 1 ) $ zip xs ( tail xs ) in zip ( [ head xs ] ++ map snd xys ) ( map fst xys ++ [ last xs ] )

All the previous solutions seem to assume that the list of numbers is already sorted. In cases where this assumption cannot be made, an alternative solution is to simply insert the numbers into a diet. eecs.oregonstate.edu/~erwig/papers/abstracts.html#JFP98 eecs.oregonstate.edu/~erwig/diet -- Martin
participants (7)
-
C K Kashyap
-
Daniel Fischer
-
Henning Thielemann
-
Johannes Waldmann
-
Martin Erwig
-
Ross Paterson
-
Stephen Tetley