Re: [Haskell] Control.Monad.Writer as Python generator

2005-04-15 Thread ChrisK
You are correct.  Moand.Cont yield even runs without -O optimizing, 
just slower:

Monad.Writer counts 10^9 zeros in 99 seconds (user time)
Monad.Cont counts 10^8 zero in 35 seconds user time.
So the writer is 3.5 times faster without '-O'
With -O
Monad.Writer counts 10^9 zeros in 105 seconds
Monad.Cont counts 10^8 zeros in 11 seconds, 10^9 zeros in 110 seconds.
So with '-O' they are the same speed.  Nice.
Anyone have an idea why ghci can't garbage collect it?
Is this an actual bug or an innate quirk of the REPL ?
--
Chris
On Apr 15, 2005, at 12:43 AM, Cale Gibbard wrote:
However, after compiling with optimisations turned on, there is no
such problem with the continuation-based version, memory usage appears
constant.
 - Cale
On 4/14/05, ChrisK [EMAIL PROTECTED] wrote:
Thanks for the Cont example, David.  But...
The MonadCont is clever and it works ... but then fails -- ghci does
not garbage collect and it blows up.
With the MonadCont version I can count up to 10^7 zeros:
*Main length $ take (10^7) zerosInf
1000
(26.20 secs, 0 bytes)
But this increases RSIZE of ghc-6.4 to 165MB.  The 10^8 version goes 
to
swap space and I had to kill it.  My original MonadWriter version does
not increase RSIZE when run (constant space), so the garbage 
collection
must be working, and it is O(N) in the # of zeros counted:

*Main length $ take (10^7) zerosInf
1000
(1.22 secs, 0 bytes)
*Main length $ take (10^8) zerosInf
1
(10.05 secs, 0 bytes)
*Main length $ take (10^9) zerosInf
10
(109.83 secs, 6 bytes)
--
Chris
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Control.Monad.Writer as Python generator

2005-04-15 Thread ChrisK
You are correct.  Moand.Cont yield even runs without -O optimizing,
just slower
...
Anyone have an idea why ghci can't garbage collect it?
Is this an actual bug or an innate quirk of the REPL ?
GHCi does not compile with optimizations, without -O the strictness 
analyzer
isn't run.
The optimizer is irrelevant to whether it runs in constant space, as 
ghc without '-O' runs it just fine.  The optimizer is only useful for 
speed, which is not the issue.

 The difference is most likely due to strictness analysis.  A well
placed strictness annotation or two should be able to make it work in 
GHCi as
well.
In this code, adding a strictness $! did not work.
A similar situation occurs with sum: in GHCi for large inputs it
overflows the stack, but when compiled with -O it works correctly, 
this is
because sum is defined with foldl and not foldl' in GHC.
As for adding one strictness annotation, the brute for approach to 
adding '$!' did not work:

yield :: a - Cont [a] ()
-- original
--yield x = Cont (\c - x : c () )
-- original in prefix form
--yield x = Cont (\c - (((:) x) (c (-- memory exhaustion
-- non-trivial
--yield x = Cont (\c - (((:) x) $! (c ( -- stack overflow
-- silly
--yield x = Cont (\c - (((:) $! x) (c ( -- memory exhaustion
-- definitely silly
--yield x = Cont (\c - (((:) x) (c $! ( -- memory exhaustion
So adding two '$!' to the above looks like a non-starter.  The 
asGenerator definition is

asGenerator :: Cont [a] v - [a]
asGenerator (Cont f) = f (const [])
which has no useful place to insert a '$!'.  So to use continuations in 
GHCI, it may be necessary to build a new version of Cont and its 
internals, or maybe use the callCC interface?  And I had not luck 
adding '$!' to callCC/Cont or callCC/mapCC versions:

-- yield using callCC
yieldCC x = callCC genContCCArg
where
genContCCArg = (\oldGenContFunc -
let
  newCont  = Cont { runCont = newRunCont }
  newRunCont =  (\contFunc - (x:(oldRunCont 
contFunc)))
  oldRunCont = runCont oldCont
  oldCont = oldGenContFunc ()
in newCont
   )

-- Use the mysterious mapCont function
yieldM x = callCC genContCCArg
where
genContCCArg = (\genContFunc - mapCont (\xs - x:xs) (genContFunc 
()))

I found no useful explanation of mapCont via Google.  It was another 
case of deriving the function's action from the type.

Since this is now a gchi problem, should this be taken to the ghc 
mailing list as well? instead?

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


Re: [Haskell] Control.Monad.Writer as Python generator

2005-04-15 Thread Jan-Willem Maessen
On Apr 15, 2005, at 6:07 PM, ChrisK wrote:
You are correct.  Moand.Cont yield even runs without -O optimizing,
just slower
...
Anyone have an idea why ghci can't garbage collect it?
Is this an actual bug or an innate quirk of the REPL ?
GHCi does not compile with optimizations, without -O the strictness 
analyzer
isn't run.
The optimizer is irrelevant to whether it runs in constant space, as 
ghc without '-O' runs it just fine.  The optimizer is only useful for 
speed, which is not the issue.
Not true!  The optimizer can change the asymptotic space consumption of 
your program.  The example of sum is particularly germaine.  If we 
write:

x = foldl (+) 0 [1..n]
this will, as it is evaluated, generate the suspended computation
(((0 + 1) + 2) + 3) + ...) + n
This require O(n) space.
Whereas the strict foldl' will evaluate each parenthesized expression 
as it is encountered:
(0+1) = 1
(1+2) = 3
(3+3) = 6
(6+4) = 10
...
(... + n) = your answer

If only we all used mostly-eager evaluation, these kinds of confusions 
would [almost] never happen.

-Jan-Willem Maessen

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


Re: [Haskell] Control.Monad.Writer as Python generator

2005-04-14 Thread ChrisK
Thanks for the Cont example, David.  But...
The MonadCont is clever and it works ... but then fails -- ghci does 
not garbage collect and it blows up.
With the MonadCont version I can count up to 10^7 zeros:

*Main length $ take (10^7) zerosInf
1000
(26.20 secs, 0 bytes)
But this increases RSIZE of ghc-6.4 to 165MB.  The 10^8 version goes to 
swap space and I had to kill it.  My original MonadWriter version does 
not increase RSIZE when run (constant space), so the garbage collection 
must be working, and it is O(N) in the # of zeros counted:

*Main length $ take (10^7) zerosInf
1000
(1.22 secs, 0 bytes)
*Main length $ take (10^8) zerosInf
1
(10.05 secs, 0 bytes)
*Main length $ take (10^9) zerosInf
10
(109.83 secs, 6 bytes)
--
Chris
On Apr 14, 2005, at 1:05 AM, David Menendez wrote:
ChrisK writes:
I was thinking to myself:
What in Haskell would give me a yield command like a Python
generator?
And the answer was tell in Control.Monad.Writer -- and I wrote some
simple examples (see below).
Another possibility would be a continuation monad.
import Control.Monad.Cont
yield :: a - Cont [a] ()
yield x = Cont (\c - x : c ())
asGenerator :: Cont [a] v - [a]
asGenerator (Cont f) = f (const [])
--
David Menendez [EMAIL PROTECTED] | In this house, we obey the 
laws
http://www.eyrie.org/~zednenem  |of thermodynamics!
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Control.Monad.Writer as Python generator

2005-04-13 Thread David Menendez
ChrisK writes:

 I was thinking to myself:
 What in Haskell would give me a yield command like a Python
 generator?
 
 And the answer was tell in Control.Monad.Writer -- and I wrote some
 simple examples (see below).

Another possibility would be a continuation monad.

import Control.Monad.Cont

yield :: a - Cont [a] ()
yield x = Cont (\c - x : c ())

asGenerator :: Cont [a] v - [a]
asGenerator (Cont f) = f (const [])
-- 
David Menendez [EMAIL PROTECTED] | In this house, we obey the laws
http://www.eyrie.org/~zednenem  |of thermodynamics!
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


[Haskell] Control.Monad.Writer as Python generator

2005-04-12 Thread ChrisK
Hi,
I was thinking to myself:
What in Haskell would give me a yield command like a Python generator?
And the answer was tell in Control.Monad.Writer -- and I wrote some  
simple examples (see below).

Most Python code using yield would be translated to something much more  
idiomatic in Haskell than using Writer, or to something more  
complicated if it needed IO.

I thought this interesting enough to put on the haskell mailing list  
and wiki since it seemed to be in neither place (I searched, but your  
searching may be better than mine).

If there are no objections then I'll put this example on the wiki; any  
suggestions where on wiki to place it (e.g. MonadWriter)?

=== CUT HERE ===
import Control.Monad.Writer
-- Some type signatures would need -fglasgow-exts to compile
-- We only care about the Writer output, not the function return value
asGenerator :: Writer [a] v - [a]
asGenerator writer = values where (_,values) = runWriter writer
--yield :: (MonadWriter [a] m) = a - m ()
yield x = tell [x]
-- This allows several items to be yielded with one command
--yieldMany :: (MonadWriter [a] m) = [a] - m ()
yieldMany = tell
zeros :: [Integer]
zeros = asGenerator (do yield 0
yield 0
yield 0)
zerosInf :: [Integer]
zerosInf = asGenerator zeros'
where zeros' = (yield 0 zeros')
-- The Collatz sequence function
foo :: (Integral a) = a - a
foo x = case (x `mod` 2) of
 0 - x `div` 2
 1 - (3*x+1)
-- Uses return () to end the list when 1 is reached
--collatzW :: (MonadWriter [a] m, Integral a) = a - m ()
collatzW x = do
   yield x
   case x of
 1 - return ()
 _ - collatzW (foo x)
-- Keeps going, will repeat 1,4,2,1,.. if 1 is reached
--collatzInfW :: (MonadWriter [a] m, Integral a) = a - m t
collatzInfW x = do
  yield x
  collatzInfW (foo x)
--collatzGen :: (MonadWriter [a] (Writer [a]), Integral a) = a - [a]
collatzGen x = asGenerator (collatzW x)
--collatzInfGen :: (MonadWriter [a] (Writer [a]), Integral a) = a -  
[a]
collatzInfGen x = asGenerator (collatzInfW x)

-- And these can be combined
collatz1 x = asGenerator (collatzW x  yield 0  collatzW (x+1))
=== CUT HERE ===
*Main zeros
[0,0,0]
*Main take 10 zerosInf
[0,0,0,0,0,0,0,0,0,0]
*Main collatzGen 13
[13,40,20,10,5,16,8,4,2,1]
*Main take 100 $ collatzInfGen 13
[13,40,20,10,5,16,8,4,2,1,4,2,1,4,2,1,4,2,1,4,2,1,4,2,1,4,2,1,4,2,1,4,2, 
1,4,2,1,4,2,1,4,2,1,4,2,1,4,2,1,4,2,1,4,2,1,4,2,1,4,2,1,4,2,1,4,2,1,4,2, 
1,4,2,1,4,2,1,4,2,1,4,2,1,4,2,1,4,2,1,4,2,1,4,2,1,4,2,1,4,2,1]

*Main collatz1 12
[12,6,3,10,5,16,8,4,2,1,0,13,40,20,10,5,16,8,4,2,1]
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell