
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