[Haskell-cafe] unsafeInterleaveIO respecting order of actions

2009-01-01 Thread Henning Thielemann
I think I have a very similar problem to the currently discussed
"WriterT [w] IO is not lazy in reading [w]".

I want to defer IO actions, until they are needed, but they shall be
executed in order. If I call unsafeInterleaveIO, they can be executed in
any order. I understand that hGetContents does not defer the hGetChar
operations but instead defers the call of the (:) constructors, thus
preserving the order of the hGetChar calls. In the general case this is
not so simple, since the result of a monadic block might not be a list
and the result of particular actions might not be needed at all, e.g. ().
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?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] unsafeInterleaveIO respecting order of actions

2009-01-01 Thread Brandon S. Allbery KF8NH

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.


--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allb...@kf8nh.com
system administrator [openafs,heimdal,too many hats] allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon universityKF8NH


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] unsafeInterleaveIO respecting order of actions

2009-01-03 Thread Henning Thielemann


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 ()

test0, test1 :: IO String
test0 = liftLazy2 (const)  getLine getLine
test1 = liftLazy2 (flip const) getLine getLine


test0 only requests the first line,
test1 expects two lines as user input.

However, with liftLazy2 we have only Applicative functionality, not Monad, 
and it is not composable.


For example:
  fmap (\((x,y),z) -> z) $ liftLazy2A (,) (liftLazy2A (,) getLine getLine) 
getLine

This requests only one line, but should three ones. The reason is that the 
first two getLines are defered even until the last one. Thus, it is not 
enough that liftLazy2 returns (IO c). Instead it must return (IO 
(c,(a,(b,() and these pair emulated lists must somehow be combined in 
order to preserve the order of execution. This looks somehow like a writer 
monad transformer.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] unsafeInterleaveIO respecting order of actions

2009-01-03 Thread Henning Thielemann


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


Re: [Haskell-cafe] unsafeInterleaveIO respecting order of actions

2009-01-04 Thread Henning Thielemann


On Sat, 3 Jan 2009, Henning Thielemann wrote:


I think I now have general Applicative functionality ...


I hope the following is a proper Monad implementation. In contrast to 
Applicative a Writer for sequencing actions does no longer work, instead I 
need a State monad.



newtype LazyIO a = LazyIO {runLazyIO :: StateT RunAll IO a}

data RunAll = RunAll
   deriving Show

instance Monad LazyIO where
   return x = LazyIO $ return x
   x >>= f = LazyIO $
  mapStateT unsafeInterleaveIO . runLazyIO . f =<<
  mapStateT unsafeInterleaveIO (runLazyIO x)

instance MonadIO LazyIO where
   liftIO m = LazyIO $ StateT $ \RunAll -> fmap (\x->(x,RunAll)) m

evalLazyIO :: LazyIO a -> IO a
evalLazyIO =
   flip evalStateT RunAll . runLazyIO


I'll write some tests and upload it to Hackage.

Thank you for being a patient audience. ;-)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe