On Sat, 3 Jan 2009, Henning Thielemann wrote:
On Thu, 1 Jan 2009, Brandon S. Allbery KF8NH wrote:
On 2009 Jan 1, at 16:44, Henning Thielemann wrote:
If it is generally possible to use unsafeInterleaveIO such that it
executes actions in the right order, wouldn't this allow the definition
of a general lazy IO monad?
I thought unsafeInterleaveIO and users of it (readFile, hGetContents)
didn't guarantee the order of actions relative to independent IO actions
(that is, those performed outside the unsafeInterleaveIO) and this was why
it is generally disrecommended. For example the recurring situation where
people try to readFile f >>= writeFile . someTransform and the writeFile
fails with a "file locked" exception.
Sure, it's dangerous. But for what I want to do, this situation cannot occur.
I can come up with a simple example which might be generalized. It simulates
what hGetContents does.
liftLazy2 :: (a -> b -> c) -> IO a -> IO b -> IO c
liftLazy2 f x y =
fmap (\ ~(xr, ~(yr,())) -> f xr yr) $
unsafeInterleaveIO $ liftM2 (,) x $
unsafeInterleaveIO $ liftM2 (,) y $
return ()
I think I now have general Applicative functionality:
apply :: (a -> b, ()) -> (a,()) -> (b,())
apply (f,fs) a =
let (a0,as) = case fs of () -> a
in (f a0, as)
lazyIO :: IO a -> IO (a,())
lazyIO = unsafeInterleaveIO . fmap (\x -> (x,()))
liftLazy2 :: (a -> b -> c) -> IO a -> IO b -> IO c
liftLazy2 f x y =
liftM2
(\xr yr -> fst $ (f,()) `apply` xr `apply` yr)
(lazyIO x) (lazyIO y)
The () is used to enforce the order of evaluation.
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe