[Haskell] Sequencing of input and output, troubles in kdevelop
A.J. Bonnema
abonnema at xs4all.nl
Fri Aug 27 08:19:23 EDT 2004
Ketil Malde wrote:
> "A.J. Bonnema" <abonnema at xs4all.nl> writes:
>
>
>>Why doesn't kdevelop generate code, that executes the statements in
>>order? Or should I be looking at ghc? Or is it an option I am missing?
>
>
> GHCi behaves like Hugs. My guess would be that kdevelop attaches
> pipes for standard input and output, and GHC or whatever backend it
> uses realizes it is not talking to a terminal, and applies buffering.
Actually, I asked kdevelop to run in an external terminal. Also, if I
run the command "./prog" (where prog is the name), the program behaves
the same. So, ghc should not assume anything else than having input from
standard input....
>
> Note that the output is constant (i.e. always the two strings), so in
> a sense they can be output at any time without changing the meaning of
> the program.
I am not sure here. Isn't the output dependant on the input, because it
depends on which filenames I enter? If I enter an erroneous input
filename, the readFile should never be executed correctly. The same for
the output filename. (I'll copy the code again for reference).
module Main where
main = do putStr "naam invoerbestand?"
inf <- getLine
txt <- readFile inf
putStr "naam uitvoerbestand?"
outf <- getLine
writeFile outf txt
Anyway, in my text on Haskell it says that IO creates a sort of
imperative sublanguage within Haskell without compromising the rest of
the modules. It uses a monad to do that.
Now, I only just started learning, so I might well be wrong, but isn't
the point about IO that statements *are* sequence dependent and there
*are* side-effects? F.i. the effects of "x <- getChar; y <- getChar" may
be different from "y <- getChar; x <- getChar", because there are side
effects. So, sequence should be important.
Well, as I said, I'm just starting......
Guus.
--
A.J. Bonnema, Leiden The Netherlands,
user #328198 (Linux Counter http://counter.li.org)
More information about the Haskell
mailing list