Simon L Peyton Jones, you wrote:
>
> Lennart, Fergus,
>
> re this stdin issue you're missing the point I was trying to make.
Yes, I am indeed missing your point.
> It really only bites badly when you have concurrency. I enclose the relevant
> message, which gives an example of the extra expressiveness non-constant
> stdin etc buys you -- I don't know which bit you disagree with, so the best
> I can do is simply repeat it.
[...]
> Suppose I import a module written by someone else which exports
> the function toUpper:
>
> -- toUpper reads stdin, converts all characters to upper
> -- case, and sends them to stdout
> toUpper :: IO ()
>
> Now I import another module which exports sort:
>
> -- sort reads stdin, divides it into lines, sorts the lines
> -- and sends them to stdout
> sort :: IO ()
>
> Now suppose I want to arrange to connect toUpper and sort together.
> I might hope to do it like this:
>
> module Main where
> import M1( toUpper )
> import M2( sort )
>
> main = do
> (in,out) <- pipe;
> forkIO (withStdOut in toUpper);
> withStdIn out sort
>
> The new functions are
>
> pipe :: IO (Handle,Handle)
> withStdOut, withStdIn :: Handle -> IO () -> IO ()
>
> The point here is that toUpper and sort each work with *different* mappings
> of stdin, stdout.
OK, so what's wrong with that?
The *mappings* are part of the thread state.
stdin and stdout can still be constant.
> This example uses concurrency, which Haskell doesn't have.
> In the absence of concurrency you can hack it like this:
>
> main = do
> (in,out) <- pipe;
> old_stdout <- setStdOut in;
> toUpper;
> setStdOut old_stdout;
> setStdIn out;
> sort
>
> But it's a hack, isn't it.
Uh, could you be more specific about what you don't like about it?
Looks fine to me. I wouldn't describe it as a hack.
> And it doesn't extend to concurrency.
Why not?
Oh, I see, you were assuming that setStdOut affects the global
mappings, rather than the thread-local mappings. Fine. Just add a
setThreadStdOut function (which can be defined in terms of a new
builtin threadReconnect, just as setStdOut can be defined in terms of
Lennart's reconnect function). Then you can define withStdOut and
withStdIn in terms of setThreadStdOut and setThreadStdIn:
withStdOut, withStdIn :: Handle -> IO () -> IO ()
withStdOut new_stdout proc = do
old_stdout <- setThreadStdOut new_stdout;
proc;
setThreadStdOut old_stdout
withStdIn new_stdin proc = do
old_stdin <- setThreadStdIn new_stdin;
proc;
setThreadStdOut old_stdin
Did I miss something?
--
Fergus Henderson <[EMAIL PROTECTED]> | "I have always known that the pursuit
WWW: <http://www.cs.mu.oz.au/~fjh> | of excellence is a lethal habit"
PGP: finger [EMAIL PROTECTED] | -- the last words of T. S. Garp.