Re: [Haskell-cafe] Strictness leak

2007-10-31 Thread Ketil Malde
Jeff Polakow [EMAIL PROTECTED] writes:

 Besides anything else, sequence will diverge on an infinite list. 

Argh, of course.  Thanks!

 It is necessary to compute all of the computations in the list before 
 returning
 any of the pure resulting list.

Replacing sequence with sequence', given as:

 sequence' ms = foldr k (return []) ms
 where
   k m m' = do { x - m; xs - unsafeInterleaveIO m'; return (x:xs) }

seems to solve it.
 
-k
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Strictness leak

2007-10-30 Thread Ketil Malde

Some time ago, I posted this code:

 countIO :: String - String - Int - [a] - IO [a]
 countIO msg post step xs = sequence $ map unsafeInterleaveIO ((blank  
 outmsg (0::Int)  c):cs)
where (c:cs) = ct 0 xs
  output   = hPutStr stderr
  blank= output ('\r':take 70 (repeat ' '))
  outmsg x = output ('\r':msg++show x)  hFlush stderr
  ct s ys = let (a,b) = splitAt (step-1) ys
next  = s+step
in case b of [b1] - map return a ++ [outmsg (s+step)  
 hPutStr stderr post  return b1]
 []   - map return (init a) ++ [outmsg 
 (s+length a)  hPutStr stderr post  return (last a)]
 _ - map return a ++ [outmsg s  return 
 (head b)] ++ ct next (tail b)

It wraps a list with IO operations, so that progress can be reported
while evaluating the list elements.  Unfortunately, there seems to be
a stricness leak here - and consequently, it does not work on an
infinite list. 

I'm not sure why this happens, can anybody else see it?

-k
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Strictness leak

2007-10-30 Thread Jeff Polakow
Hello,

  countIO :: String - String - Int - [a] - IO [a]
  countIO msg post step xs = sequence $ map unsafeInterleaveIO 
 ((blank  outmsg (0::Int)  c):cs)
 where (c:cs) = ct 0 xs
   output   = hPutStr stderr
   blank= output ('\r':take 70 (repeat ' '))
   outmsg x = output ('\r':msg++show x)  hFlush stderr
   ct s ys = let (a,b) = splitAt (step-1) ys
 next  = s+step
 in case b of [b1] - map return a ++ [outmsg 
 (s+step)  hPutStr stderr post  return b1]
  []   - map return (init a) ++ 
 [outmsg (s+length a)  hPutStr stderr post  return (last a)]
  _ - map return a ++ [outmsg s  
 return (head b)] ++ ct next (tail b)
 
 It wraps a list with IO operations, so that progress can be reported
 while evaluating the list elements.  Unfortunately, there seems to be
 a stricness leak here - and consequently, it does not work on an
 infinite list. 
 
Besides anything else, sequence will diverge on an infinite list. This can 
be seen directly from the type:

sequence :: Monad m = [m a] - m [a] 

It is necessary to compute all of the computations in the list before 
returning any of the pure resulting list.

-Jeff


---

This e-mail may contain confidential and/or privileged information. If you 
are not the intended recipient (or have received this e-mail in error) 
please notify the sender immediately and destroy this e-mail. Any 
unauthorized copying, disclosure or distribution of the material in this 
e-mail is strictly forbidden.___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Strictness leak

2007-10-30 Thread Emil Axelsson

You mean for the IO monad, right?

  take 10 $ execWriter $ sequence $ repeat $ tell ([3]::[Int])

/ Emil



On 10/30/2007 02:04 PM, Jeff Polakow wrote:


Hello,

   countIO :: String - String - Int - [a] - IO [a]
   countIO msg post step xs = sequence $ map unsafeInterleaveIO
  ((blank  outmsg (0::Int)  c):cs)
  where (c:cs) = ct 0 xs
output   = hPutStr stderr
blank= output ('\r':take 70 (repeat ' '))
outmsg x = output ('\r':msg++show x)  hFlush stderr
ct s ys = let (a,b) = splitAt (step-1) ys
  next  = s+step
  in case b of [b1] - map return a ++ [outmsg
  (s+step)  hPutStr stderr post  return b1]
   []   - map return (init a) ++
  [outmsg (s+length a)  hPutStr stderr post  return (last a)]
   _ - map return a ++ [outmsg s 
  return (head b)] ++ ct next (tail b)
 
  It wraps a list with IO operations, so that progress can be reported
  while evaluating the list elements.  Unfortunately, there seems to be
  a stricness leak here - and consequently, it does not work on an
  infinite list.
 
Besides anything else, sequence will diverge on an infinite list. This 
can be seen directly from the type:


sequence :: Monad m = [m a] - m [a]

It is necessary to compute all of the computations in the list before 
returning any of the pure resulting list.


-Jeff

---

This e-mail may contain confidential and/or privileged information. If you
are not the intended recipient (or have received this e-mail in error)
please notify the sender immediately and destroy this e-mail. Any
unauthorized copying, disclosure or distribution of the material in this
e-mail is strictly forbidden.




___
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] Strictness leak

2007-10-30 Thread Jeff Polakow
I forgot to send this reponse to haskell-cafe earlier...

Hello,

 You mean for the IO monad, right?
 
Sorry. I meant divergence is unavoidable for any strict Monad, such as IO. 


However, sequence will always compute over the entire list; if the 
resulting computation itself is lazy then the result can be inspected 
lazily.

take 10 $ execWriter $ sequence $ repeat $ tell ([3]::[Int])
 
This is a good example. Note that the computation of sequence itself is 
infinite.

snd $ runWriter $ sequence (repeat $ tell [3]) = return . take 10

will result in an infinite list, but

fst $ runWriter $ sequence (repeat $ tell [3]) = return . take 10

will return a 10 element list.

-Jeff


---

This e-mail may contain confidential and/or privileged information. If you 
are not the intended recipient (or have received this e-mail in error) 
please notify the sender immediately and destroy this e-mail. Any 
unauthorized copying, disclosure or distribution of the material in this 
e-mail is strictly forbidden.___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe