Re: [Haskell-cafe] foldlWhile

2004-11-20 Thread Jorge Adriano Aires
(opss just noticed I did a reply-to)

> > The following is closer to the original, but doesn't work when the whole
> > list is folded (i.e., p always satisfied):
> > foldlWhile f p a = head . dropWhile p . scanl f a
>
> Serge's version returns the last 'a' that satisfies 'p', while yours
Not really.

> returns the first 'a' that does not satisfy 'p'.  This should be an
> equivalent version:
Yeap, just like his, 

foldlWhile :: (a -> b -> a) -> (a -> Bool) -> a -> [b] -> a
foldlWhilefp  abs  =

(_, False) -> a


It tests the accumulator with p, and returns it on "false".

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


Re: [Haskell-cafe] foldlWhile

2004-11-20 Thread Dylan Thurston
On Sat, Nov 20, 2004 at 03:48:23PM +, Jorge Adriano Aires wrote:
> > On Sat, Nov 20, 2004 at 12:47:58PM +0300, Serge D. Mechveliani wrote:
> > >   foldlWhile :: (a -> b -> a) -> (a -> Bool) -> a -> [b] -> a
> > >   foldlWhilefp  abs  =
> > > case
> > > (bs, p a)
> > > of
> > > ([],_) -> a
> > > (_, False) -> a
> > > (b:bs', _) -> foldlWhile f p (f a b) bs'
> >
> > Why not just
> >   foldlWhile f p a bs = takeWhile p $ foldl f a bs
> 
> Quite different. The former stops a foldl when the accumulating parameter no 
> longer satisfies p, the later assumes the accumulating parameter of the foldl 
> is a list, and takes the portion of the list that does satisfy p.

Yes, this was a mistake.

> The following is closer to the original, but doesn't work when the whole list 
> is folded (i.e., p always satisfied):  
> foldlWhile f p a = head . dropWhile p . scanl f a

Serge's version returns the last 'a' that satisfies 'p', while yours
returns the first 'a' that does not satisfy 'p'.  This should be an
equivalent version:

  foldlWhile f p a = tail . takeWhile p . scanl f a

But what about the version with Maybe?  There ought to be a concise way
to write that too.

Peace,
Dylan


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


Re: [Haskell-cafe] foldlWhile

2004-11-20 Thread Dylan Thurston
On Sat, Nov 20, 2004 at 12:47:58PM +0300, Serge D. Mechveliani wrote:
> Is such a function familia to the Haskell users?
> 
>   foldlWhile :: (a -> b -> a) -> (a -> Bool) -> a -> [b] -> a
>   foldlWhilefp  abs  =
> case
> (bs, p a)
> of
> ([],_) -> a
> (_, False) -> a
> (b:bs', _) -> foldlWhile f p (f a b) bs'
> 
> foldl  does not seem to cover this.

Why not just

  foldlWhile f p a bs = takeWhile p $ foldl f a bs

?

> More `generic' variant:
> 
>   foldlWhileJust :: (a -> b -> Maybe a) -> a -> [b] -> a 
>   foldlWhileJustf  abs  =  case bs of
> 
>[]-> a
>b:bs' -> case f a b of Just a' -> foldlWhileJust f a' bs'
>   _   -> a

I don't know a short way to rewrite this one yet.

Peace,
Dylan


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


[Haskell-cafe] foldlWhile

2004-11-20 Thread Serge D. Mechveliani
Is such a function familia to the Haskell users?

  foldlWhile :: (a -> b -> a) -> (a -> Bool) -> a -> [b] -> a
  foldlWhilefp  abs  =
case
(bs, p a)
of
([],_) -> a
(_, False) -> a
(b:bs', _) -> foldlWhile f p (f a b) bs'

foldl  does not seem to cover this.

Example.  Sum the list while the sum is less than bound:

  boundSum :: Integer -> [Integer] -> Integer
  boundSumb =  
  foldlWhile (+) (< b) 0

Example:  boundSum 100 $ map (^2) [1 ..] 

Is this reasonable? 

More `generic' variant:

  foldlWhileJust :: (a -> b -> Maybe a) -> a -> [b] -> a 
  foldlWhileJustf  abs  =  case bs of

   []-> a
   b:bs' -> case f a b of Just a' -> foldlWhileJust f a' bs'
  _   -> a


Please, copy the replies to  [EMAIL PROTECTED]

-
Serge Mechveliani
[EMAIL PROTECTED]


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