Simon Marlow wrote: > Ah yes, if you have two lazy input streams both referring to the same > underlying stream, that is enough to demonstrate a problem. As for > whether Oleg's example is within the rules, it depends whether you > consider fdToHandle as "unsafe"
I wasn't aware of the rules. Fortunately, UNIX (FreeBSD and Linux) give plenty of opportunities to shoot oneself. Here is the code from the earlier message without the offending fdToHandle: > {- Haskell98! -} > > module Main where > > import System.IO > > -- f1 and f2 are both pure functions, with the pure type. > -- Both compute the result of the subtraction e1 - e2. > -- The only difference between them is the sequence of > -- evaluating their arguments, e1 `seq` e2 vs. e2 `seq` e1 > -- For really pure functions, that difference should not be observable > > f1, f2:: Int ->Int ->Int > > f1 e1 e2 = e1 `seq` e2 `seq` e1 - e2 > f2 e1 e2 = e2 `seq` e1 `seq` e1 - e2 > > read_int s = read . head . words $ s > > main = do > let h1 = stdin > h2 <- openFile "/dev/stdin" ReadMode > s1 <- hGetContents h1 > s2 <- hGetContents h2 > -- print $ f1 (read_int s1) (read_int s2) > print $ f2 (read_int s1) (read_int s2) It exhibits the same behavior that was described in http://www.haskell.org/pipermail/haskell/2009-March/021064.html I think Windows may have something similar. > The reason it's hard is that to demonstrate a difference you have to get > the lazy I/O to commute with some other I/O, and GHC will never do that. The keyword here is GHC. I may well believe that GHC is able to divine programmer's true intent and so it always does the right thing. But writing in the language standard ``do what the version x.y.z of GHC does'' does not seem very appropriate, or helpful to other implementors. > Haskell's IO library is carefully designed to not run into this > problem on its own. It's normally not possible to get two Handles > with the same FD... Is this behavior is specified somewhere, or is this just an artifact of a particular GHC implementation? _______________________________________________ Haskell-prime mailing list Haskell-prime@haskell.org http://www.haskell.org/mailman/listinfo/haskell-prime