[Haskell-cafe] applicative challenge

Thomas Hartman tphyahoo at gmail.com
Tue May 5 09:48:20 EDT 2009


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 at 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 <tom.davie at gmail.com>:
>
> 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
>
>


More information about the Haskell-Cafe mailing list