Re: [Haskell-cafe] finally going on Solaris

2005-09-30 Thread Christian Maeder

Malcolm Wallace wrote:

Brian McQueen [EMAIL PROTECTED] writes:


For some reason, the compilation of
HTMLMonad98.hs is taking forever - and  I mean forever.


See

http://cvs.haskell.org/cgi-bin/cvsweb.cgi/fptools/ghc/compiler/utils/UniqFM.lhs

particularly the comment for revision 1.42.  It might be helpful for
you to merge that patch into your copy of the compiler.


This patch is already part of (and included in) the ghc-6.4.1 (source 
and binary) distribution. (UniqFM.lhs rev 1.39.6.1)


Still, make on WASH-2.3.1 takes a while due to the large files 
HTMLMonad98.hs and HTMLPrelude98.hs.


Christian

real15m11.406s
user14m5.128s
sys 0m22.841s
[EMAIL PROTECTED] - uname -a
SunOS leo 5.10 Generic_118822-18 sun4u sparc SUNW,Sun-Fire-280R
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] how to break foldl' ?

2005-09-30 Thread gary ng
Hi,

say if I want to sum a list of numbers but only until
it hits a max limit. 

Currently, I control it through the function and
basically do nothing when the max is hit. However, if
the list is very long, would this mean the same
function would be called for the rest of the list
which can be a waste of cycle ? In an imperative
language, I just break/return in the middle of the
loop.

thanks for any help in advance.

gary



__ 
Yahoo! Mail - PC Magazine Editors' Choice 2005 
http://mail.yahoo.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] how to break foldl' ?

2005-09-30 Thread Henning Thielemann

On Fri, 30 Sep 2005, gary ng wrote:

 Hi,

 say if I want to sum a list of numbers but only until
 it hits a max limit.

 Currently, I control it through the function and
 basically do nothing when the max is hit. However, if
 the list is very long, would this mean the same
 function would be called for the rest of the list
 which can be a waste of cycle ?

Depends on how you implemented it. If your implementation ignores the
result of the rest of the list, then it won't be computed.

This should work as expected:
  takeWhile (maxX) (scanl (+) 0 xs)


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] how to break foldl' ?

2005-09-30 Thread Malcolm Wallace
 say if I want to sum a list of numbers but only until
 it hits a max limit. 
 
 Currently, I control it through the function and
 basically do nothing when the max is hit. However, if
 the list is very long, would this mean the same
 function would be called for the rest of the list
 which can be a waste of cycle ? In an imperative
 language, I just break/return in the middle of the
 loop.

If you are using foldl or foldl', then yes, the definition tells you
that 'foldl' itself will be applied as many times as the length of
the list:

foldl f z [] =  z
foldl f z (x:xs) =  foldl f (f z x) xs

For your situation, foldr is better:

foldr f z [] =  z
foldr f z (x:xs) =  f x (foldr f z xs)

The function 'f' is the outermost application, therefore it can decide
to ignore its second argument, meaning that the recursive call to
foldr is never computed.

Regards,
Malcolm
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] how to break foldl' ?

2005-09-30 Thread Thomas Davie


On 30 Sep 2005, at 11:33, gary ng wrote:



Hi,

say if I want to sum a list of numbers but only until
it hits a max limit.

Currently, I control it through the function and
basically do nothing when the max is hit. However, if
the list is very long, would this mean the same
function would be called for the rest of the list
which can be a waste of cycle ? In an imperative
language, I just break/return in the middle of the
loop.



No - lazy evaluation guarantees that if a reduct is never needed, it  
is never reduced.  So as your function never needs the latter values  
in the list, it is never evaluated.


Bob

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] how to break foldl' ?

2005-09-30 Thread gary ng
Still a bit confused.

My function is simply

f x y = if x  100 then x + y else x

Sure the rest of y will not be touched(so if it is a
file reading operation, no actual i/o will ever be
performed) as they are not needed. But how would foldl
knows that my logic won't need some other item in the
list till the end ? So won't it call (f) X times even
though all these X times just do a test and return ?

--- Thomas Davie [EMAIL PROTECTED] wrote:

 
 
 No - lazy evaluation guarantees that if a reduct is
 never needed, it  
 is never reduced.  So as your function never needs
 the latter values  
 in the list, it is never evaluated.
 
 Bob
 
 




__ 
Yahoo! Mail - PC Magazine Editors' Choice 2005 
http://mail.yahoo.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] how to break foldl' ?

2005-09-30 Thread gary ng
Thanks. But how would I think about using scanl
instead of foldl(or foldl') when I want is the sum,
but not the progressive result. Once again show me
that I need to throw away all imperative stuff.

Oh, BTW, the reason I asked is that I was playing with
python which has a reduce function that looks like
foldl, and I tried to practice some FP style
programming and came up with this issue. There is no
scanl though, better use for loop and break.

 
 This should work as expected:
   takeWhile (maxX) (scanl (+) 0 xs)
 
 
 




__ 
Yahoo! Mail - PC Magazine Editors' Choice 2005 
http://mail.yahoo.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] how to break foldl' ?

2005-09-30 Thread Henning Thielemann

On Fri, 30 Sep 2005, gary ng wrote:

  This should work as expected:
takeWhile (maxX) (scanl (+) 0 xs)

 Thanks. But how would I think about using scanl
 instead of foldl(or foldl') when I want is the sum,
 but not the progressive result. Once again show me
 that I need to throw away all imperative stuff.

No problem:
  last (takeWhile (maxX) (scanl (+) 0 xs))
Convinced?

The first sum which exceeds the limit could be computed with
  head (dropWhile (=maxX) (scanl (+) 0 xs))

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] how to break foldl' ?

2005-09-30 Thread gary ng
Once again, many thanks to all who taught me about
this small little problem. Don't even know there is
init/last and thought there is only head/tail.

But just for my curiosity, would the takeWhile still
store the intermediate result till my result is
reached ? If so, and my list is really very long(and I
need to go to 1/2 of its length), I would still use a
lot more memory than imperative method or even the
foldl one(where in both case, I just take one element)
?

--- Henning Thielemann [EMAIL PROTECTED]
wrote:

 No problem:
   last (takeWhile (maxX) (scanl (+) 0 xs))
 Convinced?
 
 The first sum which exceeds the limit could be
 computed with
   head (dropWhile (=maxX) (scanl (+) 0 xs))
 
 




__ 
Yahoo! Mail - PC Magazine Editors' Choice 2005 
http://mail.yahoo.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] how to break foldl' ?

2005-09-30 Thread Thomas Davie
Again, it depends how takeWhile is implemented -- if it's not tail  
recursive, the compiler will usually manage to run such functions in  
constant space.


Bob

On 30 Sep 2005, at 16:02, gary ng wrote:


Once again, many thanks to all who taught me about
this small little problem. Don't even know there is
init/last and thought there is only head/tail.

But just for my curiosity, would the takeWhile still
store the intermediate result till my result is
reached ? If so, and my list is really very long(and I
need to go to 1/2 of its length), I would still use a
lot more memory than imperative method or even the
foldl one(where in both case, I just take one element)
?

--- Henning Thielemann [EMAIL PROTECTED]
wrote:



No problem:
  last (takeWhile (maxX) (scanl (+) 0 xs))
Convinced?

The first sum which exceeds the limit could be
computed with
  head (dropWhile (=maxX) (scanl (+) 0 xs))








__
Yahoo! Mail - PC Magazine Editors' Choice 2005
http://mail.yahoo.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] how to break foldl' ?

2005-09-30 Thread Henning Thielemann


On Fri, 30 Sep 2005, gary ng wrote:


Once again, many thanks to all who taught me about
this small little problem. Don't even know there is
init/last and thought there is only head/tail.


http://www.haskell.org/ghc/docs/6.4/html/libraries/base/Data.List.html


But just for my curiosity, would the takeWhile still
store the intermediate result till my result is
reached ? If so, and my list is really very long(and I
need to go to 1/2 of its length), I would still use a
lot more memory than imperative method or even the
foldl one(where in both case, I just take one element)
?


If you don't trust the compiler you can at least test if the rest of the 
list is ignored: Run with an infinite list.


E.g.
 last (takeWhile (10) (scanl (+) 0 (repeat 1)))
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] how to break foldl' ?

2005-09-30 Thread Daniel Fischer
Am Freitag, 30. September 2005 17:14 schrieb Henning Thielemann:
 On Fri, 30 Sep 2005, gary ng wrote:
  Once again, many thanks to all who taught me about
  this small little problem. Don't even know there is
  init/last and thought there is only head/tail.

 http://www.haskell.org/ghc/docs/6.4/html/libraries/base/Data.List.html

  But just for my curiosity, would the takeWhile still
  store the intermediate result till my result is
  reached ? If so, and my list is really very long(and I
  need to go to 1/2 of its length), I would still use a
  lot more memory than imperative method or even the
  foldl one(where in both case, I just take one element)
  ?

 If you don't trust the compiler you can at least test if the rest of the
 list is ignored: Run with an infinite list.

 E.g.
   last (takeWhile (10) (scanl (+) 0 (repeat 1)))

I think Gary wanted to know whether the initial part of scanl's result is 
stored. I think, it shouldn't, because of the 'last'.

However, when profiling your versions versus

testFoldl :: (a - Bool) - (a - b - a) - a - [b] - a
testFoldl _ _ z [] = z
testFoldl p _ z _ | p z = z
testFoldl p f z (x:xs) = testFoldl p f (f z x) xs,

I found that your 
head (dropWhile ... )
took about twice as long and allocated roughly 2.6 times as much memory as 
mine
and 
last (takeWhile ... )
was a bit worse.
Still, it didn't use near enough memory to store
takeWhile (= 5*10^7) (scanl (+) 0 (repeat 1)),
all three used (if I interpret the profiling graphs [-hc, -hb] correctly) 
about 16.5 k of memory for practically the complete runtime.

Besides, 
head (dropWhile (10) (scanl (+) 0 (replicate 9 1)))
will raise an error, as will
last (takeWhile ...)
if the starting value satisfies the break-condition.

Cheers,
Daniel
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] how to break foldl' ?

2005-09-30 Thread Udo Stenzel
gary ng wrote:
 Still a bit confused.
 
 My function is simply
 
 f x y = if x  100 then x + y else x

Try this:

sum_to_100 xs = foldr (\x k a - if a  100 then k $! (x+a) else a) id xs 0

As expected, (sum_to_100 [1..]) gives 105, without trying to find the
end of an infinite list.  You get your early-out semantics combined with
strict evaluation.


Udo.


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


[Haskell-cafe] Confused about types

2005-09-30 Thread Lanny Ripple
I thought I was doing ok with haskell until I tried to program in 
it.  :/  I figured the first thing to tackle was something easy 
so I hacked up newton's method.  Worked great for Double's.  Then 
I figured I would extend it to work with different types of 
Fractionals.  What a pain.  I finally got that working for Floats 
and Rationals but I'm drawing a blank on Complex.


I've got:

Newton.hs
import Data.Complex
import Data.Ratio
import Debug.Trace

main = putStrLn $ answer =  ++ show (newton myd $ -5)

newton :: (Fractional a, Ord a) = (a - a) - a - a
newton f x = newton_h f x 1.0e-6

newton_h, next_x_h, dy_h :: (Fractional a, Ord a) = (a - a) - 
a - a - a

newton_h f x h = until ((= h) . abs . f) (next_x_h f h) x

next_x_h f h x = trace (next_x =  ++ show foo) foo
where foo = x - (f x) / (dy_h f x h)

dy_h f x h = ( (f $ x + h) - f x ) / h

-- roundTo :: Fractional a = a - a - a
-- roundTo x eps = ((fromRational . toRational) (round $ x / 
eps)) * eps


myd :: Double - Double
myd x = ((x/100 + 1) * x + 1) * x - 10

myf :: Float - Float
myf x = ((x/100 + 1) * x + 1) * x - 10

myr :: Rational - Rational
myr x = approxRational myr' 1e-6
where myr' = ((x/100 + 1) * x + 1) * x - 10

myc :: RealFloat a = Complex a - Complex a
myc x = x * x + 1
/Newton.hs

When I try

  newton myc 5

in ghci I get a warning about newton wanting Ords.  Complex 
aren't ordered.  I figure I need to specify a newton_h that can 
handle complex


  newton_h f (Complex x) h =
  until ((= h) . realPart . abs . f) (next_x_h f h) x

laughs at me.  So does

  newton_h f (:+ r im) h =
  until ((= h) .realPart . abs . f) (next_x_h f h) (:+ r im)

although I sure thought I had read that constructors could be 
used in pattern matching.  I've been working on this for too long 
and getting frustrated.  Can someone clue me in?


  Thanks,
  -ljr

--
Lanny Ripple [EMAIL PROTECTED]
CC Tools / Cisco Systems, Inc.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe