[Haskell-cafe] applicative challenge
Thomas Hartman
tphyahoo at gmail.com
Mon May 4 17:15:52 EDT 2009
{-# 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
More information about the Haskell-Cafe
mailing list