Lazy bind...
MR K P SCHUPKE
k.schupke@ic.ac.uk
Tue, 30 Jul 2002 14:11:12 +0100
Okay here goes... I am trying to write a monad-transformer for a consumer
based parser. As such the normal (non monad-transformer version)
would look like:
(Parser p) >>= q = Parser $ \cs -> case p cs of
Rejected -> Rejected
Accepted accept -> Accepted $ case accept of
Fail y -> Fail y
Empty -> Empty
Ok cs' x -> case (\(Parser z) -> z) (q x) cs' of
Accepted c' -> c'
Rejected -> Fail noMsg
however when rewriting as a monad transformer we end up with:-
(ParserT p) >>= q = ParserT $ \cs -> do
a <- p cs
case a of
Rejected -> return Rejected
Accepted accept -> do
reply <- case accept of
Fail y -> return (Fail y)
Empty -> return (Empty)
Ok cs' x -> do
b <- runParserT (q x) cs'
case b of
Accepted c' -> return c'
Rejected -> return (Fail noMsg)
return (Accepted $ reply)
if we run a computation in say (ParserT IO) the Accepted is not returned
until after the last IO operation...
whereas what I want is the accepted returned ASAP, with the full reply after
the last IO operation.
I have tried defining liftIO as the following:
liftIO = lift . liftIO . unsafeInterleaveIO
but this is too lazy as IO operations don't get run until their result is
used.
what I really need is to replace the bind: "reply <- case accept of" with
"reply <- $ case accept of"
(which of course is not valid). The alternative is to produce a specialised
instance for (ParserT IO) using
"reply <- unsafeInterleaveIO $ case accept of" but this is not a general
solution as it does not deal with
(ParserT SomeMonadT IO) etc...
Keean Schupke
Department of Electrical & Electronic Engineering,
Imperial College London.
Martin Norbäck wrote:
> Remember that the syntax
>
> a <- getLine
> return (Constructor a)
>
> is just sugar for
>
> getLine >>= \a -> return (Constructor a)
>
> so actually the bind is already lazy (lamba binding is lazy). The
> laziness of the construction here will depend on your definition of >>=
> for the monad in question. Since the point of the IO monad is to
> sequentialize IO operations, >>= will definititely not be lazy there.
>
> Perhaps if you give a concrete example of what you want to do, people
> could help you more.
>
> Regards,
>
> Martin
>
> --
> Martin Norbäck d95mback@dtek.chalmers.se
> Kapplandsgatan 40 +46 (0)708 26 33 60
> S-414 78 GÖTEBORG http://www.dtek.chalmers.se/~d95mback/
> SWEDEN OpenPGP ID: 3FA8580B
>
> ------------------------------------------------------------------------
>
> signature.ascName: signature.asc
> Type: application/pgp-signature