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

David Menendez dave at zednenem.com
Fri Oct 9 13:27:57 EDT 2009


On Fri, Oct 9, 2009 at 11:12 AM, Felipe Lessa <felipe.lessa at gmail.com> wrote:
> On Thu, Oct 08, 2009 at 12:54:14AM -0700, oleg at okmij.org wrote:
>> Actually it is possible to implement all three evaluation orders
>> within the same final tagless framework, using the same interpretation
>> of types and reusing most of the code save the semantics of lam. That
>> is where the three orders differ, by their own definition.
>
> 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.

-- 
Dave Menendez <dave at zednenem.com>
<http://www.eyrie.org/~zednenem/>


More information about the Haskell-Cafe mailing list