[Haskell-cafe] Re: Where do I put the seq?

David Menendez dave at zednenem.com
Fri Aug 21 12:53:41 EDT 2009


On Fri, Aug 21, 2009 at 4:37 AM, Peter Verswyvelen<bugfact at gmail.com> wrote:
> On Fri, Aug 21, 2009 at 5:03 AM, David Menendez <dave at zednenem.com> wrote:
>>
>> I'm not sure I understand your question, but I think it's possible to
>> use interact in the way you want. For example, this code behaves
>> correctly for me:
>>
>>    foo i =
>>        let i1 = lines i
>>        in "Enter your name: " ++
>>            (case i1 of
>>                [] -> error "EOF"
>>                name:i2 -> "Welcome " ++ name ++ "\n")
>>
>> Prelude> interact foo
>> Enter your name: Bob
>> Welcome Bob
>
> Yes but this also enforce strictness, since you're pattern matching against
> the input, forcing it to be evaluated. If for example the empty string would
> be valid input, this wouldn't work, and seq would be needed again no?

You would still need to determine whether you've reached EOF or not,
which forces the input to be determined up to the first line-break or
EOF.

> This suffers from the same strictness problem on the input, e.g. when making
> getLine less strict, as in:
> import Prelude hiding (getLine)
> import Control.Monad.Cont
> type Behavior = [String] -> String
> type MyIO = Cont Behavior
> putLine :: String -> MyIO ()
> putLine s = Cont $ \k ss -> s ++ k () ss
> getLine :: MyIO String
> -- Was: getLine = Cont $ \k (s:ss) -> k s ss
> getLine = Cont $ \k ss -> k (head ss) (tail ss)

Technically, these are both wrong, because they don't allow for EOF.
getLine should be more like this:

getLine = Cont $ \k ss -> if null ss then error "EOF" else k (head ss) (tail ss)

> run :: MyIO () -> Behavior
> run m = runCont m (\_ _ -> [])
> foo = do
>    putLine "Enter name: "
>    name <- getLine
>    putLine ("Welcome " ++ name ++ "\n")
> main = interact (run foo . lines)
> You get the "Welcome" before the name again.
> To be honest I don't fully understand why this is a horrible hack.

It isn't. Some people dislike seq because it lets you force strictness
in cases where pattern matching cannot (like function arguments), but
hardly anyone objects to pattern matching.

(I just read a paper arguing that pattern matching is bad because it
introduces interpretation. The proposed solution, Church encoding
everything, seemed impractical.)

> I do understand much more now, thanks. The best solution for making this IO
> pure remains MonadPrompt I guess.

Or the trace technique I mentioned earlier. I believe they're
equivalent in expressive power.

> Too bad that something extremely simple like console text IO doesn't seem to
> be a good start for introducing FRP, or maybe seen from another angle (using
> Reactive) it might still be, dono

Are you writing an introduction to using FRP, or an introduction to
implementing FRP? Every Haskell FRP implementation I'm aware of uses
the IO monad internally.

If you want to be able to run in an entirely pure manner, you might
investigate IOSpec.

<http://hackage.haskell.org/package/IOSpec>

-- 
Dave Menendez <dave at zednenem.com>
<http://www.eyrie.org/~zednenem/>


More information about the Haskell-Cafe mailing list