* Simon Marlow: >> What about handles from System.Process? Do they count as well? > > Sure - we hopefully don't consider System.Process to be unsafe.
Here's a demonstration that lazy input has an observable effect. It needs the Perl helper script included below. Of course, this example is constructed, but there are similar issues to consider when network IO is involved. For instance, not reading the lazy structure to its end causes the server to keep the connection open longer than necessary. ---------------------------------------------------------------------- -- Based on Oleg Kiselyov's example in: -- <http://www.haskell.org/pipermail/haskell/2009-March/021064.html> module Main where import System.IO (hGetContents) import System.Process (runInteractiveProcess) f1, f2:: String -> String -> String f1 e1 e2 = e1 `seq` e2 `seq` e1 f2 e1 e2 = e2 `seq` e1 `seq` e1 f = head . tail . lines spawn :: () -> IO String spawn () = do (inp,out,err,pid) <- runInteractiveProcess "perl" ["magic.pl"] Nothing Nothing hGetContents out main = do s1 <- spawn () s2 <- spawn () print $ f1 (f s1) (f s2) -- print $ f2 (f s1) (f s2) ---------------------------------------------------------------------- #!/usr/bin/perl # Magic program to demonstrate that lazy I/O leads to observable # differences in behavior. use strict; use warnings; use Fcntl ':flock'; open my $self, '<', $0 or die "opening $0: $!\n"; # use this file as lock flock($self, LOCK_SH) or die "flock(LOCK_SH): $!\n"; print "x" x 100_000 . "\n"; # blocks if reader blocks print flock($self, LOCK_EX | LOCK_NB) ? "locked\n" : "failed\n"; # only succeeds if the other process has exited _______________________________________________ Haskell-prime mailing list Haskell-prime@haskell.org http://www.haskell.org/mailman/listinfo/haskell-prime