[Haskell-cafe] CBN, CBV, Lazy in the same final tagless framework
Jacques Carette
carette at mcmaster.ca
Thu Oct 15 12:22:16 EDT 2009
Just a short note to show how the 3 evaluation orders can be written in
a very symmetric manner:
oleg at okmij.org wrote these as:
> In call-by-name, we have
> lam f = S . return $ (unS . f . S)
>
> In call-by-value, we have
> lam f = S . return $ (\x -> x >>= unS . f . S . return)
>
> In call-by-need, we have
> lam f = S . return $ (\x -> share x >>= unS . f . S)
>
These can be rewritten as
call-by-name (eta-expanded and application made visible):
lam f = S . return $ (\x -> unS . f . S $ x)
call-by-value (flip)
lam f = S . return $ (\x -> unS . f . S . return =<< x)
call-by-need (flip)
lam f = S . return $ (\x -> unS . f . S =<< share x )
This pushes us to write two helper functions:
execS :: (IO a -> IO b) -> IO a -> IO b
execS g x = g =<< share x
execM :: Monad m => (m a -> m b) -> m a -> m b
execM g x = g . return =<< x
And now, with the magic of slices, we can truly display those 3 in
highly symmetric fashion:
call-by-name:
lam f = S . return $ ((unS . f . S) $)
call-by-value (flip)
lam f = S . return $ ((unS . f . S) `execM`)
call-by-need (flip)
lam f = S . return $ ((unS . f . S ) `execS`)
(the redundant $ is left in to make the symmetry explicit)
And now we see the pattern:
lam f = wrap . lift $ ((unwrap . f . wrap) `apply`)
where the names above are meant to be suggestive rather than 'actual' names.
Jacques
More information about the Haskell-Cafe
mailing list