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/
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 ] )
___
Haskell-Cafe mailing lis
On 23 December 2010 22:01, Henning Thielemann
wrote:
>
> 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
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
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 (skippi
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, ...
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 <-
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 resul
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.
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
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 resul
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
12 matches
Mail list logo