[Haskell-cafe] CBN, CBV, Lazy in the same final tagless framework

Felipe Lessa felipe.lessa at gmail.com
Fri Oct 9 13:39:19 EDT 2009


On Fri, Oct 09, 2009 at 01:27:57PM -0400, David Menendez wrote:
> On Fri, Oct 9, 2009 at 11:12 AM, Felipe Lessa <felipe.lessa at gmail.com> wrote:
> > That's really nice, Oleg, thanks!  I just wanted to comment that
> > I'd prefer to write
> >
> > share :: IO a -> IO (IO a)
> > share m = mdo r <- newIORef (do x <- m
> >                                writeIORef r (return x)
> >                                return x)
> >              return (readIORef r >>= id)
> >
> > which unfortunately needs {-# LANGUAGE RecursiveDo #-} or
> > some ugliness from mfix
> >
> > share :: IO a -> IO (IO a)
> > share m = do r <- mfix $ \r -> newIORef (do x <- m
> >                                            writeIORef r (return x)
> >                                            return x)
> >             return (readIORef r >>= id)
> >
>
> Alternatively,
>
> share m = do
>     r <- newIORef undefined
>     writeIORef r $ do
>         x <- m
>         writeIORef r (return x)
>         return x
>     return $ readIORef r >>= id
>
> Which is basically the same as your version, but only needs one IORef.

Hmmm, but my version also needs only one IORef, right?  In fact I
first wrote the same code as yours but I've frowned upon the need
of having that 'undefined' and an extra 'writeIORef'.

Thanks,

--
Felipe.


More information about the Haskell-Cafe mailing list