
{-# LANGUAGE NoMonomorphismRestriction #-} import Data.List import Control.Monad import Control.Applicative -- Can the function below be tweaked to quit on blank input, provisioned in the applicative style? -- which function(s) needs to be rewritten to make it so? -- Can you tell/guess which function(s) is the problem just by looking at the code below? -- If so, can you explain what the strategy for doing so is? notQuiteRight = takeWhile (not . blank) <$> ( sequence . repeat $ echo ) echo = do l <- getLine putStrLn l return l -- this seems to work... is there a way to make it work Applicatively, with lifted takeWhile? seemsToWork = sequenceWhile_ (not . blank) (repeat echo) sequenceWhile_ p [] = return () sequenceWhile_ p (mx:mxs) = do x <- mx if p x then do sequenceWhile_ p mxs else return () blank x = "" == x

Hi Thomas This is "iffy versus miffy", a standard applicative problem. When you use the result of one computation to choose the next computation (e.g., to decide whether you want to keep doing-and-taking), that's when you need yer actual monad. It's the join of a monad that lets you compute computations. The applicative interface does not allow any interference between the value and computation layers. It's enough for effects which facilitate but do not determine the flow of computation (e.g. threading an environment, counting how often something happens, etc...). So, you ask a sensible... On 4 May 2009, at 22:15, Thomas Hartman wrote:
{-# LANGUAGE NoMonomorphismRestriction #-} import Data.List import Control.Monad import Control.Applicative
-- Can the function below be tweaked to quit on blank input, provisioned in the applicative style? -- which function(s) needs to be rewritten to make it so? -- Can you tell/guess which function(s) is the problem just by looking at the code below? -- If so, can you explain what the strategy for doing so is?
...nostril question.
notQuiteRight = takeWhile (not . blank) <$> ( sequence . repeat $ echo )
^^^ Here, we're doing all the computations, then post-processing the values with a pure function. There's no way the pure function can tell the computation to stop bothering.
echo = do l <- getLine putStrLn l return l
-- this seems to work... is there a way to make it work Applicatively, with lifted takeWhile? seemsToWork = sequenceWhile_ (not . blank) (repeat echo)
sequenceWhile_ p [] = return () sequenceWhile_ p (mx:mxs) = do x <- mx if p x ^^^ Here, you're exactly using the result of a computation to choose which computations come next. That's a genuinely monadic thing to do: miffy not iffy.
then do sequenceWhile_ p mxs else return ()
If you're wondering what I'm talking about, let me remind/inform you of the definitions. iffy :: Applicative a => a Bool -> a t -> a t -> a t iffy test yes no = cond <$> test <*> yes <*> no where cond b y n = if b then y else n miffy :: Monad m => m Bool -> m t -> m t -> m t miffy test yes no = do b <- test if b then yes else no Apologies for slang/pop-culture references, but "iffy" means dubious, questionable, untrustworthy "miffy" is a cute Dutch cartoon character drawn by Dick Bruna The effect of iffy askPresident launchMissiles seekUNResolution is to ask the President, then launch the missiles, then lobby the UN, then decide that the result of seeking a UN resolution is preferable. Remember folks: Missiles need miffy! Cheers Conor

On Mon, May 04, 2009 at 10:49:56PM +0100, Conor McBride wrote:
The effect of
iffy askPresident launchMissiles seekUNResolution
is to ask the President, then launch the missiles, then lobby the UN, then decide that the result of seeking a UN resolution is preferable.
Remember folks: Missiles need miffy!
Haha, you made my day! This e-mail has to be saved somewhere :). Cheers, -- Felipe.

Conor McBride
Remember folks: Missiles need miffy!
Hmmmm. Iff you have something like CoPointed or Foldable, you can thread your own, Applicative, tail back into yourself and decide what you are by inspecting it. That makes foldr the join of Hask itself, or something. Bear with me, I'm merely attempting to delurk our resident category theorists by giving them headaches. -- (c) this sig last receiving data processing entity. Inspect headers for copyright history. All rights reserved. Copying, hiring, renting, performance and/or quoting of this signature prohibited.

Hi Achim On 5 May 2009, at 01:26, Achim Schneider wrote:
Conor McBride
wrote: Remember folks: Missiles need miffy!
Hmmmm. Iff you have something like CoPointed or Foldable, you can thread your own, Applicative, tail back into yourself and decide what you are by inspecting it.
Yeah, Applicative on its own is kind of "effects without control", or in Lindley-Wadler-Yallop parlance "oblivious". The fun starts when you just chuck in a little bit more. Copointed might be overdoing it. Even Alternative gives you quite a lot of control, without going as far as Monad.
That makes foldr the join of Hask itself, or something. Bear with me, I'm merely attempting to delurk our resident category theorists by giving them headaches.
Good luck Conor

Thomas Hartman wrote:
-- Can the function below be tweaked to quit on blank input, provisioned in the applicative style?
No. Applicative on its own does not support to decide which action to take based on the result of some previous action. It is therefore not possible to look at the last line read, and read another line or stop processing depending on whether the last line was empty or not. You need something beyond Applicative to do that.
-- Can you tell/guess which function(s) is the problem just by looking at the code below?
repeat creates an infinite list, and sequence is strict, so ( sequence . repeat $ ...) diverges. fmap for IO is strict in its second argument, so notQuiteRight diverges. repeat, sequence and fmap work together to make this expression diverge, so I would not say that one of them is more problematic then the others.
-- If so, can you explain what the strategy for doing so is?
No.
notQuiteRight = takeWhile (not . blank) <$> ( sequence . repeat $ echo )
echo = do l <- getLine putStrLn l return l
-- this seems to work... is there a way to make it work Applicatively, with lifted takeWhile? seemsToWork = sequenceWhile_ (not . blank) (repeat echo)
sequenceWhile_ p [] = return () sequenceWhile_ p (mx:mxs) = do x <- mx if p x then do sequenceWhile_ p mxs else return ()
While this should work and looks like a reasonable implementation, it is clearly not in Applicative style, since you use bind to look at the x. Tillmann

On 4 May 2009, at 23:15, Thomas Hartman wrote:
{-# LANGUAGE NoMonomorphismRestriction #-} import Data.List import Control.Monad import Control.Applicative
-- Can the function below be tweaked to quit on blank input, provisioned in the applicative style? -- which function(s) needs to be rewritten to make it so? -- Can you tell/guess which function(s) is the problem just by looking at the code below? -- If so, can you explain what the strategy for doing so is? notQuiteRight = takeWhile (not . blank) <$> ( sequence . repeat $ echo )
echo = do l <- getLine putStrLn l return l
-- this seems to work... is there a way to make it work Applicatively, with lifted takeWhile? seemsToWork = sequenceWhile_ (not . blank) (repeat echo)
sequenceWhile_ p [] = return () sequenceWhile_ p (mx:mxs) = do x <- mx if p x then do sequenceWhile_ p mxs else return ()
Conor's already give you a comprehensive explanation of why Applicative can't be used to do this, but that doesn't mean you can't use applicative style! How about... echo = unlines . takeWhile (not . blank) . lines seemsToWork = interact echo Bob

That's slick, but is there some way to use interact twice in the same program?
t10 =
let f = unlines . takeWhile (not . blank) . lines
in do putStrLn "first time"
interact f
putStrLn "second time"
interact f
this results in *** Exception: <stdin>: hGetContents: illegal
operation (handle is closed) -}
I also tried
t15 =
let grabby = unlines . takeWhile (not . blank) . lines
top = ("first time: " ++) . grabby . ("second time: " ++) . grabby
in interact top
but that didn't work either:
thartman@ubuntu:~/haskell-learning/lazy-n-strict>runghc sequencing.hs
a
first time: second time: a
b
b
If someone can explain the subtleties of using interact when you run
out of stdio here, it would be nice to incorporate this into
http://www.haskell.org/haskellwiki/Haskell_IO_for_Imperative_Programmers#IO
where it talks about how using interact is the easy way to approach
these types of problems. Not *that* easy though, as this scenario
suggests.
2009/5/5 Thomas Davie
On 4 May 2009, at 23:15, Thomas Hartman wrote:
{-# LANGUAGE NoMonomorphismRestriction #-} import Data.List import Control.Monad import Control.Applicative
-- Can the function below be tweaked to quit on blank input, provisioned in the applicative style? -- which function(s) needs to be rewritten to make it so? -- Can you tell/guess which function(s) is the problem just by looking at the code below? -- If so, can you explain what the strategy for doing so is? notQuiteRight = takeWhile (not . blank) <$> ( sequence . repeat $ echo )
echo = do l <- getLine putStrLn l return l
-- this seems to work... is there a way to make it work Applicatively, with lifted takeWhile? seemsToWork = sequenceWhile_ (not . blank) (repeat echo)
sequenceWhile_ p [] = return () sequenceWhile_ p (mx:mxs) = do x <- mx if p x then do sequenceWhile_ p mxs else return ()
Conor's already give you a comprehensive explanation of why Applicative can't be used to do this, but that doesn't mean you can't use applicative style!
How about...
echo = unlines . takeWhile (not . blank) . lines
seemsToWork = interact echo
Bob

Thomas Hartman
That's slick, but is there some way to use interact twice in the same program?
No :-)
t10 = let f = unlines . takeWhile (not . blank) . lines in do putStrLn "first time" interact f putStrLn "second time" interact f
this results in *** Exception: <stdin>: hGetContents: illegal operation (handle is closed) -}
Yes. Interacting uses hGetContents, and hGetContents semi-closes (or fully-closes) the handle. If you do it from GHCi, you only get to run your program once.
I also tried
t15 = let grabby = unlines . takeWhile (not . blank) . lines top = ("first time: " ++) . grabby . ("second time: " ++) . grabby in interact top
but that didn't work either: thartman@ubuntu:~/haskell-learning/lazy-n-strict>runghc sequencing.hs a first time: second time: a b b
Well - the input to the leftmost grabby is "second time" prepended to the input from the first, and then you prepend "first time" - so this makes sense. Something like this, perhaps: interact (\s -> let (first,second) = span (not . null) (lines s) in unlines ("first":first++"second":takeWhile (not.null) second))
If someone can explain the subtleties of using interact when you run out of stdio here, it would be nice to incorporate this into
hGetContents - there can only be one. -k -- If I haven't seen further, it is by standing in the footprints of giants

seems to be the same behavior whether in ghci or compiled with ghc.
2009/5/5 Ketil Malde
Thomas Hartman
writes: That's slick, but is there some way to use interact twice in the same program?
No :-)
t10 = let f = unlines . takeWhile (not . blank) . lines in do putStrLn "first time" interact f putStrLn "second time" interact f
this results in *** Exception: <stdin>: hGetContents: illegal operation (handle is closed) -}
Yes. Interacting uses hGetContents, and hGetContents semi-closes (or fully-closes) the handle. If you do it from GHCi, you only get to run your program once.
I also tried
t15 = let grabby = unlines . takeWhile (not . blank) . lines top = ("first time: " ++) . grabby . ("second time: " ++) . grabby in interact top
but that didn't work either: thartman@ubuntu:~/haskell-learning/lazy-n-strict>runghc sequencing.hs a first time: second time: a b b
Well - the input to the leftmost grabby is "second time" prepended to the input from the first, and then you prepend "first time" - so this makes sense.
Something like this, perhaps:
interact (\s -> let (first,second) = span (not . null) (lines s) in unlines ("first":first++"second":takeWhile (not.null) second))
If someone can explain the subtleties of using interact when you run out of stdio here, it would be nice to incorporate this into
hGetContents - there can only be one.
-k -- If I haven't seen further, it is by standing in the footprints of giants

interact (\s -> let (first,second) = span (not . null) (lines s) in unlines ("first":first++"second":takeWhile (not.null) second))
So, that didn't quite do the right thing, and it seemed like using
span/break wouldn't scale well for more than two iterations. Here's
another attempt, which is a little closer I think, except that it
seems to be using some sort of half-assed state without being explicit
about it:
module Main where
t17 = interact f17
f17 s = let (first,rest) = grabby s
(second,_) = grabby rest
in "first\n" ++ first ++ "second\n" ++ second
grabby :: String -> (String,String)
grabby s =
let (beg,end) = break null . lines $ s
in (unlines beg, (unlines . drop 2 $ end))
2009/5/5 Ketil Malde
Thomas Hartman
writes: That's slick, but is there some way to use interact twice in the same program?
No :-)
t10 = let f = unlines . takeWhile (not . blank) . lines in do putStrLn "first time" interact f putStrLn "second time" interact f
this results in *** Exception: <stdin>: hGetContents: illegal operation (handle is closed) -}
Yes. Interacting uses hGetContents, and hGetContents semi-closes (or fully-closes) the handle. If you do it from GHCi, you only get to run your program once.
I also tried
t15 = let grabby = unlines . takeWhile (not . blank) . lines top = ("first time: " ++) . grabby . ("second time: " ++) . grabby in interact top
but that didn't work either: thartman@ubuntu:~/haskell-learning/lazy-n-strict>runghc sequencing.hs a first time: second time: a b b
Well - the input to the leftmost grabby is "second time" prepended to the input from the first, and then you prepend "first time" - so this makes sense.
Something like this, perhaps:
interact (\s -> let (first,second) = span (not . null) (lines s) in unlines ("first":first++"second":takeWhile (not.null) second))
If someone can explain the subtleties of using interact when you run out of stdio here, it would be nice to incorporate this into
hGetContents - there can only be one.
-k -- If I haven't seen further, it is by standing in the footprints of giants

half-assed state
for a real state solution, there's follow up here:
http://groups.google.com/group/haskell-cafe/browse_thread/thread/d6143504c0e...
2009/5/5 Thomas Hartman
interact (\s -> let (first,second) = span (not . null) (lines s) in unlines ("first":first++"second":takeWhile (not.null) second))
So, that didn't quite do the right thing, and it seemed like using span/break wouldn't scale well for more than two iterations. Here's another attempt, which is a little closer I think, except that it seems to be using some sort of half-assed state without being explicit about it:
module Main where
t17 = interact f17 f17 s = let (first,rest) = grabby s (second,_) = grabby rest in "first\n" ++ first ++ "second\n" ++ second
grabby :: String -> (String,String) grabby s = let (beg,end) = break null . lines $ s in (unlines beg, (unlines . drop 2 $ end))
2009/5/5 Ketil Malde
: Thomas Hartman
writes: That's slick, but is there some way to use interact twice in the same program?
No :-)
t10 = let f = unlines . takeWhile (not . blank) . lines in do putStrLn "first time" interact f putStrLn "second time" interact f
this results in *** Exception: <stdin>: hGetContents: illegal operation (handle is closed) -}
Yes. Interacting uses hGetContents, and hGetContents semi-closes (or fully-closes) the handle. If you do it from GHCi, you only get to run your program once.
I also tried
t15 = let grabby = unlines . takeWhile (not . blank) . lines top = ("first time: " ++) . grabby . ("second time: " ++) . grabby in interact top
but that didn't work either: thartman@ubuntu:~/haskell-learning/lazy-n-strict>runghc sequencing.hs a first time: second time: a b b
Well - the input to the leftmost grabby is "second time" prepended to the input from the first, and then you prepend "first time" - so this makes sense.
Something like this, perhaps:
interact (\s -> let (first,second) = span (not . null) (lines s) in unlines ("first":first++"second":takeWhile (not.null) second))
If someone can explain the subtleties of using interact when you run out of stdio here, it would be nice to incorporate this into
hGetContents - there can only be one.
-k -- If I haven't seen further, it is by standing in the footprints of giants

I also tried
t15 = let grabby = unlines . takeWhile (not . blank) . lines top = ("first time: " ++) . grabby . ("second time: " ++) . grabby in interact top
but that didn't work either:
thartman@ubuntu:~/haskell-learning/lazy-n-strict>runghc sequencing.hs a first time: second time: a b b
If someone can explain the subtleties of using interact when you run out of stdio here, it would be nice to incorporate this into
Essentially, what's happening here is that interact consumes *all* of standard input, and runs your function on it. This means that as you've realised here, your function must do *all* of the processing of input in one go – but this is good! This means our IO is restricted to one tiny little corner of the program, and we get to write pure Haskell everywhere else :) What's going on with your top function on the other hand is that (.) is not `after` in the sense you're thinking. If you want one grabby to consume some of the input, but not all of it you'd need to return a pair containing the output, and the unconsumed input.
where it talks about how using interact is the easy way to approach these types of problems. Not *that* easy though, as this scenario suggests.
The key here is that it's more composable than using IO – IO can change all kinds of wierd state, and result in two functions doing totally different things depending on when they're called. This means you can't reliably stick bits of IO code together. With pure functional code though, referential transparency guarentees that you can. Bob
participants (8)
-
Achim Schneider
-
Conor McBride
-
david48
-
Felipe Lessa
-
Ketil Malde
-
Thomas Davie
-
Thomas Hartman
-
Tillmann Rendel