Re: [Haskell-cafe] Splitting a list

2004-04-23 Thread Steve Schafer
On Wed, 21 Apr 2004 14:57:57 +0100, you wrote:

How about implementing a directly recursive solution?  Simply
accumulate the sum so far, together with the list elements you have
already peeled off.  Once the sum plus the next element would exceed
the threshold, emit the accumulated elements, and reset the sum
to zero.

splitlist threshold xs = split 0 [] xs
  where
split n acc [] = reverse acc: []
split n acc (x:xs)
| x = threshold  = error (show x++ exceeds threshold )
| n+x  threshold = reverse acc : split 0 [] (x:xs)
| otherwise   = split (n+x) (x:acc) xs

Thanks. Apart from a small off-by-one problem (the x = threshold test
needs to be x  threshold instead), it works fine.

I had actually started along those lines, but got bogged down in the
details of passing the accumulator around, and ended up painting myself
into a corner, so I abandoned that approach (prematurely, as it turns
out).

And thanks to everyone else who replied--I don't want to clutter the
list with a lot of individual replies. As you can probably tell, I've
only recently begun playing with Haskell, and the process of
reconfiguring my neurons into recursive loops has not yet been
completed.

-Steve

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Splitting a list

2004-04-22 Thread Ronny Wichers Schreur
Steve Schafer writes (in the Haskell Cafe):

I have a list of integers, e.g.:

 [1,5,3,17,8,9]

I want to split it into a pair of lists, with the criterion being that
the sum of the elements in the first list is as large as possible, but
not exceeding a threshold value. For example, if the threshold is 10,
the result should be:
 ([1,5,3],[17,8,9])

and then I want to recursively apply this process to the remainder of
the list, with the end result being a list of lists of integers. Using
the same list along with a threshold of 18, I would get:
 [[1,5,3],[17],[8,9]]
I would get

   [[1,5,3], [17], [8,9], [], [], [] ..]

Cheers,

Ronny Wichers Schreur
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Splitting a list

2004-04-22 Thread Joe Fasel
This is a classic greedy algorithm, much like the text-wrapping
problem.

My main suggestion would be that you're not making use of some standard
list functions that would simplify things.  For example, your
runningSum is just scanl1 (+) .  Similarly, splitAll should use
unfoldr.  Another thing is that I would reverse the order of
arguments of splitFirst and splitAll, since curried applications
are probably more useful that way:

splitAll :: (Real a) = a - [a] - [[a]]
splitAll = unfoldr . split
   where split _ [] = Nothing
 split n xs = let (ys,zs) = break (( n) . snd)
  (zip xs (scanl1 (+) xs))
  in Just (map fst ys, map fst zs)

Now, if you're concerned about all that zipping and projecting,
you can instead define split via a straightforward recursion,
or you could use a different kind of unfold that preserves the
terminating value:

unfoldrG :: (b - Either (a,b) b) - b - ([a],b)
unfoldrG f = unfold
 where unfold x = case f x of
Right y - ([],y)
Left (a,y) - let (bs,z) = unfold y
  in (a:bs,z)

Here, you will define split by unfolding a pair consisting of a
running sum and remaining list.

Cheers,
--Joe

On 2004.04.21 07:42, Steve Schafer wrote:
 I have a list of integers, e.g.:
 
  [1,5,3,17,8,9]
 
 I want to split it into a pair of lists, with the criterion being that
 the sum of the elements in the first list is as large as possible, but
 not exceeding a threshold value. For example, if the threshold is 10,
 the result should be:
 
  ([1,5,3],[17,8,9])
 
 and then I want to recursively apply this process to the remainder of
 the list, with the end result being a list of lists of integers. Using
 the same list along with a threshold of 18, I would get:
 
  [[1,5,3],[17],[8,9]]
 
 I have devised a means of doing this:
 
 1) Create an auxiliary list of integers, where the n'th element is equal
 to the sum of the first n elements of the original list.
 
 2) Zip the auxiliary list with the original list.
 
 3) Use span to break the list in two according to the threshold.
 
 4) Unzip the two resulting lists and discard the auxiliary portions.
 
 5) Repeat from step 1, operating on the tail of the list, until there's
 nothing left.
 
 Here's the code that implements this:
 
 runningSum   ::  (Ord a, Num a) = [a] - [a]
 runningSum []=   []
 runningSum (i:[])=   i : []
 runningSum (i:j:js)  =   i : runningSum (i+j : js)
 
 zipWithSum   ::  (Ord a, Num a) = [a] - [(a,a)]
 zipWithSum xs=   zip (runningSum xs) xs
 
 threshold::  (Ord a, Num a) = [a] - a - ([(a,a)],[(a,a)])
 threshold xs t   =   let test x = (t = (fst x))
  in span test (zipWithSum xs)
 
 splitFirst   ::  (Ord a, Num a) = [a] - a - ([a],[a])
 splitFirst xs t  =   let (ys,zs) = threshold xs t
  in (snd (unzip ys), snd (unzip zs))
 
 splitAll ::  (Ord a, Num a) = [a] - a - [[a]]
 splitAll [] _=   []
 splitAll xs t=   let (ys, zs) = splitFirst xs t
  in ys : (splitAll zs t)
 
 (One thing that's missing from this code is a check to verify that no
 single element in the list is greater than the threshold, which should
 raise an error, rather than get stuck in an infinite loop.)
 
 The algorithm as implemented works fine, but it seems overly complicated
 and not very elegant. I get the feeling that I'm missing some obvious
 simplification, but I can't find it. Any ideas?
 
 Thanks,
 
 -Steve Schafer
 
 ___
 Haskell-Cafe mailing list
 [EMAIL PROTECTED]
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 
 

Joseph H. Fasel, Ph.D.  email: [EMAIL PROTECTED]
Systems Planning and Analysis   phone: +1 505 667 7158
University of Californiafax: +1 505 667 2960
Los Alamos National Laboratory  post: D-2 MS F609; Los Alamos, NM 87545
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Splitting a list

2004-04-22 Thread Joe Fasel

On 2004.04.22 15:02, I wrote:
 splitAll :: (Real a) = a - [a] - [[a]]
 splitAll = unfoldr . split
  where split _ [] = Nothing
  split n xs = let (ys,zs) = break (( n) . snd)
   (zip xs (scanl1 (+) xs))
   in Just (map fst ys, map fst zs)

a slight improvement:

splitAll :: (Real a) = a - [a] - [[a]]
splitAll n = unfoldr split
 where split [] = Nothing
   split xs = let (ys,zs) = break (( n) . snd)
  (zip xs (scanl1 (+) xs))
  in Just (map fst ys, map fst zs)

But in fact, I think you can do better still by not holding n
constant but using a higher threshold on each split and not
projecting out the values of the second component, thus only
zipping the whole list once.

--Joe

Joseph H. Fasel, Ph.D.  email: [EMAIL PROTECTED]
Systems Planning and Analysis   phone: +1 505 667 7158
University of Californiafax: +1 505 667 2960
Los Alamos National Laboratory  post: D-2 MS F609; Los Alamos, NM 87545
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Splitting a list

2004-04-21 Thread Steve Schafer
I have a list of integers, e.g.:

 [1,5,3,17,8,9]

I want to split it into a pair of lists, with the criterion being that
the sum of the elements in the first list is as large as possible, but
not exceeding a threshold value. For example, if the threshold is 10,
the result should be:

 ([1,5,3],[17,8,9])

and then I want to recursively apply this process to the remainder of
the list, with the end result being a list of lists of integers. Using
the same list along with a threshold of 18, I would get:

 [[1,5,3],[17],[8,9]]

I have devised a means of doing this:

1) Create an auxiliary list of integers, where the n'th element is equal
to the sum of the first n elements of the original list.

2) Zip the auxiliary list with the original list.

3) Use span to break the list in two according to the threshold.

4) Unzip the two resulting lists and discard the auxiliary portions.

5) Repeat from step 1, operating on the tail of the list, until there's
nothing left.

Here's the code that implements this:

runningSum   ::  (Ord a, Num a) = [a] - [a]
runningSum []=   []
runningSum (i:[])=   i : []
runningSum (i:j:js)  =   i : runningSum (i+j : js)

zipWithSum   ::  (Ord a, Num a) = [a] - [(a,a)]
zipWithSum xs=   zip (runningSum xs) xs

threshold::  (Ord a, Num a) = [a] - a - ([(a,a)],[(a,a)])
threshold xs t   =   let test x = (t = (fst x))
 in span test (zipWithSum xs)

splitFirst   ::  (Ord a, Num a) = [a] - a - ([a],[a])
splitFirst xs t  =   let (ys,zs) = threshold xs t
 in (snd (unzip ys), snd (unzip zs))

splitAll ::  (Ord a, Num a) = [a] - a - [[a]]
splitAll [] _=   []
splitAll xs t=   let (ys, zs) = splitFirst xs t
 in ys : (splitAll zs t)

(One thing that's missing from this code is a check to verify that no
single element in the list is greater than the threshold, which should
raise an error, rather than get stuck in an infinite loop.)

The algorithm as implemented works fine, but it seems overly complicated
and not very elegant. I get the feeling that I'm missing some obvious
simplification, but I can't find it. Any ideas?

Thanks,

-Steve Schafer

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Splitting a list

2004-04-21 Thread Henning Thielemann

On Wed, 21 Apr 2004, Steve Schafer wrote:

 runningSum   ::  (Ord a, Num a) = [a] - [a]
 runningSum []=   []
 runningSum (i:[])=   i : []
 runningSum (i:j:js)  =   i : runningSum (i+j : js)

this is certainly the same as

scanl1 (+)

 zipWithSum   ::  (Ord a, Num a) = [a] - [(a,a)]
 zipWithSum xs=   zip (runningSum xs) xs
 
 threshold::  (Ord a, Num a) = [a] - a - ([(a,a)],[(a,a)])
 threshold xs t   =   let test x = (t = (fst x))
  in span test (zipWithSum xs)

In general you should make the threshold 't' the first argument of your
functions, since it will have different values less often than 'xs'.

 splitFirst   ::  (Ord a, Num a) = [a] - a - ([a],[a])
 splitFirst xs t  =   let (ys,zs) = threshold xs t
  in (snd (unzip ys), snd (unzip zs))
 
 splitAll ::  (Ord a, Num a) = [a] - a - [[a]]
 splitAll [] _=   []
 splitAll xs t=   let (ys, zs) = splitFirst xs t
  in ys : (splitAll zs t)

With swapped arguments of splitFirst and Maybe value you could invoke it
with 'unfoldr' in splitAll.

Though a recursive algorithm may be more elegant here. 


___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Splitting a list

2004-04-21 Thread Doaitse Swierstra
How about:

splitList weight l
 = munch l weight
   where munch [] _ = [[]]
 munch p@(x:xs) w  = if w = x
 then  let (r:rr) = munch xs (w-x)
   in  (x:r):rr
 else  []:munch p weight
main = print (splitList 18  [1,5,3,17,8,9])

Doaitse Swierstra

PS: note that your problem is a bit underspecified:

 -- what to return for an empty list
 -- what to do if a number is larger than the weight
On 2004 apr 21, at 15:42, Steve Schafer wrote:

I have a list of integers, e.g.:

 [1,5,3,17,8,9]

I want to split it into a pair of lists, with the criterion being that
the sum of the elements in the first list is as large as possible, but
not exceeding a threshold value. For example, if the threshold is 10,
the result should be:
 ([1,5,3],[17,8,9])

and then I want to recursively apply this process to the remainder of
the list, with the end result being a list of lists of integers. Using
the same list along with a threshold of 18, I would get:
 [[1,5,3],[17],[8,9]]

I have devised a means of doing this:

1) Create an auxiliary list of integers, where the n'th element is 
equal
to the sum of the first n elements of the original list.

2) Zip the auxiliary list with the original list.

3) Use span to break the list in two according to the threshold.

4) Unzip the two resulting lists and discard the auxiliary portions.

5) Repeat from step 1, operating on the tail of the list, until there's
nothing left.
Here's the code that implements this:

runningSum   ::  (Ord a, Num a) = [a] - [a]
runningSum []=   []
runningSum (i:[])=   i : []
runningSum (i:j:js)  =   i : runningSum (i+j : js)
zipWithSum   ::  (Ord a, Num a) = [a] - [(a,a)]
zipWithSum xs=   zip (runningSum xs) xs
threshold::  (Ord a, Num a) = [a] - a - 
([(a,a)],[(a,a)])
threshold xs t   =   let test x = (t = (fst x))
 in span test (zipWithSum xs)

splitFirst   ::  (Ord a, Num a) = [a] - a - ([a],[a])
splitFirst xs t  =   let (ys,zs) = threshold xs t
 in (snd (unzip ys), snd (unzip zs))
splitAll ::  (Ord a, Num a) = [a] - a - [[a]]
splitAll [] _=   []
splitAll xs t=   let (ys, zs) = splitFirst xs t
 in ys : (splitAll zs t)
(One thing that's missing from this code is a check to verify that no
single element in the list is greater than the threshold, which should
raise an error, rather than get stuck in an infinite loop.)
The algorithm as implemented works fine, but it seems overly 
complicated
and not very elegant. I get the feeling that I'm missing some obvious
simplification, but I can't find it. Any ideas?

Thanks,

-Steve Schafer

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe