[Haskell-cafe] Is it possible to make lazy combinators for IO? (Was: (no subject))
David Feuer
david.feuer at gmail.com
Mon Apr 25 00:16:28 UTC 2016
Spectacular! That looks like just what I wanted! Unless there are some
hidden gotchas, it might be worth making a package of that. The bit
that's strangest to me is how stToIO (seems to) make sure that all the
actions actually get performed.
David
On Sun, Apr 24, 2016 at 6:08 PM, Bertram Felgenhauer
<bertram.felgenhauer at googlemail.com> wrote:
> I see what I missed here: The IO part of `y` should also force the IO part
> of `x` to be performed, and that is not captured by `unsafeInterleaveIO`,
> since it preserves the order of the IO actions. In fact such a monad
> already exists in the form of the lazy ST monad. So...
>
> import Control.Monad.ST.Lazy as LST
> import Control.Monad.ST.Lazy.Unsafe as LSTU
> import Control.Monad.IO.Class
> import Control.Monad.Fix
>
> newtype MyIO a = MyIO (LST.ST RealWorld a)
> deriving (Functor, Applicative, Monad, MonadFix)
>
> instance MonadIO MyIO where
> liftIO = MyIO . LSTU.unsafeIOToST
>
> runMyIO :: MyIO a -> IO a
> runMyIO (MyIO f) = stToIO f
>
> main = runMyIO $ do
> l <- (2:) `fmap` liftIO readLn
> m <- replicateM (head l) (liftIO readLn)
> liftIO (print (l :: [Int],m :: [Int]))
>
> Cheers,
>
> Bertram
More information about the Haskell-Cafe
mailing list