On Thu, Aug 20, 2009 at 6:57 PM, Peter Verswyvelen<
bugfact@gmail.com> wrote:
>
> On Thu, Aug 20, 2009 at 11:23 PM, David Menendez <
dave@zednenem.com> wrote:
>>
>> The important things to note are (1) getChar# depends on the token
>> returned by putChar#, thus guaranteeing that putChar# gets executed
>> first, and (2) putChar# and getChar# are impure and cannot normally be
>> defined in Haskell.
>
> Ok, that I understand. But if getChar# and putChar# would be pure functions
> that just generate some output string / consume some input string, then this
> realworld token passing would not work when used with interact, since
> neither the output or input string really depends on the dummy token, unless
> using a seq again (or strictness annotation, which was explained to be just
> syntactic sugar for seq)?
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?
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)
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. From a pure point of view, the behavior is the same, weither or not the input is made strict. When side effects are present (interactive input/output from the user), it does matter, but aren't all space/time leaks to be considered as some sort of "operational effects"? In a pure mathematical world, space and time leaks would not really matter?
I do understand much more now, thanks. The best solution for making this IO pure remains MonadPrompt I guess.
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