Re: [Haskell-cafe] IO, sequence, lazyness, takeWhile

2010-12-19 Thread Brandon S Allbery KF8NH
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

On 12/13/10 09:15 , Jacek Generowicz wrote:
 untilQuit' = (fmap (takeWhile (/= quit))) (sequence $ map (= report)
 (repeat getLine))
 
 -- The latter version shows the report, but it doesn't stop at the
 -- appropriate place, so I'm guessing that I'm being bitten by my
 -- ignorance about the interaction of actions and lazyness.

The reason this doesn't stop where you expect it to is that sequence is
effectively strict (that is, it will keep going until the list is
exhausted), but repeat creates an infinite list.  You want the stop
condition between the map-report and the repeat-getLine.

- -- 
brandon s. allbery [linux,solaris,freebsd,perl]  allb...@kf8nh.com
system administrator  [openafs,heimdal,too many hats]  allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon university  KF8NH
-BEGIN PGP SIGNATURE-
Version: GnuPG v2.0.10 (Darwin)
Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org/

iEYEARECAAYFAk0OWJQACgkQIn7hlCsL25Wb2gCgw3GKF/rBdXL2LIsV5qUVSa1M
ZfEAoL5Vzd9+F7+NDqOAP7s2pyxtmJ0S
=bU/D
-END PGP SIGNATURE-

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


Re: [Haskell-cafe] IO, sequence, lazyness, takeWhile

2010-12-19 Thread Jacek Generowicz


On 2010 Dec 19, at 20:10, Brandon S Allbery KF8NH wrote:


-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

On 12/13/10 09:15 , Jacek Generowicz wrote:
untilQuit' = (fmap (takeWhile (/= quit))) (sequence $ map (=  
report)

(repeat getLine))

-- The latter version shows the report, but it doesn't stop at the
-- appropriate place, so I'm guessing that I'm being bitten by my
-- ignorance about the interaction of actions and lazyness.


The reason this doesn't stop where you expect it to is that sequence  
is

effectively strict


That would explain it. Thank you.

Where is this fact documented? I mostly rely on Hoogle, which gets me to

http://hackage.haskell.org/packages/archive/base/latest/doc/html/Prelude.html#v 
:sequence


which says nothing about strictness.

How could I have known this without having to bother anyone else?

You want the stop condition between the map-report and the repeat- 
getLine.


Or, more generally speaking, between sequence, and whatever generates  
the infinite list. But can this be done in a similar style? Could I  
still use takeWhile and somehow lift it into IO?



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


Re: [Haskell-cafe] IO, sequence, lazyness, takeWhile

2010-12-19 Thread Daniel Fischer
On Sunday 19 December 2010 22:18:59, Jacek Generowicz wrote:
 
  The reason this doesn't stop where you expect it to is that sequence
  is
  effectively strict

 That would explain it. Thank you.

 Where is this fact documented? I mostly rely on Hoogle, which gets me to

 
 http://hackage.haskell.org/packages/archive/base/latest/doc/html/Prelude
.html#v

 :sequence

 which says nothing about strictness.

 How could I have known this without having to bother anyone else?


Well, you can deduce it from sequence's type. That's of course not 
something you immediately see, but in hindsight, it's pretty easy to 
understand.

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

So, basically all sequence can do is use (=) and return.
Reasonably,

sequence [] = return []

is the only thing that's possible. For nonempty lists,

sequence (x:xs) = ?

Well, what can sequence do? It has to do something with x and something 
with xs, the only reasonable thing is to call sequence on the tail and run 
x, combining x's result and the result of sequence xs.

One can choose the order, but

sequence (x:xs) = do
   a - x
   as - sequence xs
   return (a:as)

is the most sensible thing.

Now, that means before sequence can deliver anything, it has to run all 
actions (because if any action fails, sequence fails and that can't be 
known before all actions have been run).


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


Re: [Haskell-cafe] IO, sequence, lazyness, takeWhile

2010-12-19 Thread Carl Howells
Sequence isn't necessarily strict.  Sequence, rather necessarily,
depends on the semantics of (=) in that monad.

Prelude Control.Monad.Identity runIdentity $ take 10 `liftM` sequence
(map return $ repeat 5)
[5,5,5,5,5,5,5,5,5,5]

What matters is if (=) is strict in its first argument.  The
Identity Monad provided by mtl and transformers is not strict in the
first argument of (=).  Hence sequence isn't strict in that Identity
Monad.

Compare to IO, where (=) is strict in its first argument:

Prelude Control.Monad.Identity take 10 `liftM` sequence (map return $
repeat 5) :: IO [Int]
^CInterrupted.

After a while, I got bored and interrupted it.

Anyway.  There's no documentation on the (non-)strictness of sequence,
because it isn't actually defined.  It depends on the choice of m.

Carl Howells

On Sun, Dec 19, 2010 at 1:58 PM, Daniel Fischer
daniel.is.fisc...@googlemail.com wrote:
 On Sunday 19 December 2010 22:18:59, Jacek Generowicz wrote:
 
  The reason this doesn't stop where you expect it to is that sequence
  is
  effectively strict

 That would explain it. Thank you.

 Where is this fact documented? I mostly rely on Hoogle, which gets me to


 http://hackage.haskell.org/packages/archive/base/latest/doc/html/Prelude
.html#v

 :sequence

 which says nothing about strictness.

 How could I have known this without having to bother anyone else?


 Well, you can deduce it from sequence's type. That's of course not
 something you immediately see, but in hindsight, it's pretty easy to
 understand.

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

 So, basically all sequence can do is use (=) and return.
 Reasonably,

 sequence [] = return []

 is the only thing that's possible. For nonempty lists,

 sequence (x:xs) = ?

 Well, what can sequence do? It has to do something with x and something
 with xs, the only reasonable thing is to call sequence on the tail and run
 x, combining x's result and the result of sequence xs.

 One can choose the order, but

 sequence (x:xs) = do
   a - x
   as - sequence xs
   return (a:as)

 is the most sensible thing.

 Now, that means before sequence can deliver anything, it has to run all
 actions (because if any action fails, sequence fails and that can't be
 known before all actions have been run).


 ___
 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


[Haskell-cafe] IO, sequence, lazyness, takeWhile

2010-12-13 Thread Jacek Generowicz

-- Is it possible to rewrite code written in this style

untilQuit = do
  text - getLine
  report text
  if text == quit
 then return ()
 else untilQuit

-- in a style using higher order functions for abstract iteration? For
-- example, something along these lines:

untilQuit' = (fmap (takeWhile (/= quit))) (sequence $ map (=  
report) (repeat getLine))


-- The latter version shows the report, but it doesn't stop at the
-- appropriate place, so I'm guessing that I'm being bitten by my
-- ignorance about the interaction of actions and lazyness.


-- For completeness, here's a definition of report
report text = do
  putStrLn $ You wrote  ++ text
  return text


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


Re: [Haskell-cafe] IO, sequence, lazyness, takeWhile

2010-12-13 Thread Luke Palmer
On Mon, Dec 13, 2010 at 7:15 AM, Jacek Generowicz
jacek.generow...@cern.ch wrote:
 -- Is it possible to rewrite code written in this style

 untilQuit = do
  text - getLine
  report text
  if text == quit
     then return ()
     else untilQuit

 -- in a style using higher order functions for abstract iteration? For
 -- example, something along these lines:

 untilQuit' = (fmap (takeWhile (/= quit))) (sequence $ map (= report)
 (repeat getLine))

You are asking about standard library functions?  Probably, but I
think it is cleanest to just write a HOF to encapsulate this pattern.
I have used this one before:

whileM_ :: (Monad m) = (a - Bool) - m a - m ()
whileM_ p m = bool (return ()) (whileM p m) . p = m

bool :: a - a - Bool - a
bool t f True = t
bool t f False = f

untilQuit = whileM_ (/= quit) (getLine = liftM2 () report return)

I find a variant of whileM that returns m [a] particularly handy for
collecting events in an event loop.

Luke

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


Re: [Haskell-cafe] IO, sequence, lazyness, takeWhile

2010-12-13 Thread Gregory Crosswhite

 Take a look at the monad-loops package.

Cheers,
Greg

On 12/13/2010 06:15 AM, Jacek Generowicz wrote:

-- Is it possible to rewrite code written in this style

untilQuit = do
  text - getLine
  report text
  if text == quit
 then return ()
 else untilQuit

-- in a style using higher order functions for abstract iteration? For
-- example, something along these lines:

untilQuit' = (fmap (takeWhile (/= quit))) (sequence $ map (= 
report) (repeat getLine))


-- The latter version shows the report, but it doesn't stop at the
-- appropriate place, so I'm guessing that I'm being bitten by my
-- ignorance about the interaction of actions and lazyness.


-- For completeness, here's a definition of report
report text = do
  putStrLn $ You wrote  ++ text
  return text


___
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