Created
January 5, 2021 05:38
-
-
Save cdepillabout/985cb741d0cc408386c0dbcac66e9bc1 to your computer and use it in GitHub Desktop.
Examples of playing around with continuations in Haskell
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
{-# LANGUAGE RankNTypes #-} | |
{-# LANGUAGE ScopedTypeVariables #-} | |
module Example where | |
import Control.Concurrent.MVar | |
import Control.Monad.IO.Class | |
import Control.Monad.Trans.Cont | |
import Data.Foldable | |
import Data.Monoid | |
import Data.Traversable | |
-- | Save a computation in an MVar. It can be taken from the MVar and run | |
-- again. | |
-- | |
-- Similar to the example in https://beautifulracket.com/explainer/continuations.html | |
-- with let/cc. | |
example2 :: forall r. IO (MVar (Int -> ContT String IO Int)) | |
example2 = do | |
mvar :: MVar (Int -> ContT String IO Int) <- newEmptyMVar | |
let myContT = do | |
let fourPlusSetMVar :: ContT String IO Int | |
fourPlusSetMVar = callCC f | |
where | |
f :: (Int -> ContT String IO Int) -> ContT String IO Int | |
f k = do | |
liftIO $ putMVar mvar k | |
pure 4 | |
(+) <$> pure 3 <*> fourPlusSetMVar | |
runContT myContT (\i -> pure (show i)) | |
pure mvar | |
-- | Show how example2 can be used. | |
example3 :: IO () | |
example3 = do | |
mvar <- example2 | |
k :: Int -> ContT String IO Int <- takeMVar mvar | |
runContT (k 100) (pure . show) >>= print | |
runContT (k 200) (pure . show) >>= print | |
-- | Simple continuation. | |
-- | |
-- >>> runCont example4 (\i -> show i) | |
-- "4" | |
-- >>> runCont example4 (\i -> "") | |
-- "" | |
example4 :: Cont String Int | |
example4 = ContT $ \int2str -> | |
int2str 4 | |
-- | Slightly more complicated continuation. | |
-- | |
-- >>> evalCont example5 | |
-- 7 | |
-- | |
-- >>> runCont example5 (\i -> 100) | |
-- 103 | |
example5 :: Cont Int Int | |
example5 = ContT $ \int2int -> 3 + int2int 4 | |
-- | Trying to play around with shift / reset, but I don't know how they work. | |
example6 :: Cont Int Int | |
example6 = do | |
res <- example5 | |
reset $ do | |
example6 | |
-- | Continuations can be used to inject a new value into them and continue | |
-- with the computation with the new value. | |
-- | |
-- Use the default value: | |
-- | |
-- >>> evalCont example8 | |
-- 15 | |
-- | |
-- Inject a new value and continue the computation with that value: | |
-- | |
-- >>> runCont example8 (\_ -> 100) | |
-- 111 | |
example8 :: Cont Int Int | |
example8 = cont f | |
where | |
f :: (Int -> Int) -> Int | |
-- This k is the continuation that can be used to set where the new value can | |
-- be injected in. | |
f k = | |
getSum $ | |
foldMap | |
(\(i :: Int) -> | |
if i == 4 | |
then | |
-- Call the continuation here, which would let the user inject a | |
-- value other than 4 here, and have the computation continue from | |
-- that point. | |
Sum (k i) | |
else | |
Sum i | |
) | |
[1..5] | |
-- This doesn't work because the r type in the Cont is not the same as the | |
-- result a type. It only works above because r and a are both the same type. | |
-- example9 :: Cont String Int | |
-- example9 = cont $ \(k :: Int -> String) -> | |
-- getSum $ foldMap (\(i :: Int) -> if i == 4 then Sum (k i) else Sum i) [1..5] | |
-- Implementation of callCC from transformers. | |
-- callCC :: ((a -> ContT r m b) -> ContT r m a) -> ContT r m a | |
-- callCC f = ContT $ \ c -> runContT (f (\ x -> ContT $ \ _ -> c x)) c | |
-- | This is a specialization of callCC to Cont (instead of ContT). However, | |
-- this isn't necessary, as you can see below. | |
-- | |
-- callCC doesn't actually use the m anywhere. | |
callCC' :: forall r a b. ((a -> Cont r b) -> Cont r a) -> Cont r a | |
callCC' f = cont $ \k -> runCont (f (\a -> cont $ \xxx -> k a)) k | |
-- | callCC gives us an way to do an "early return". Calling it with a value | |
-- just immediately returns from that continuation. | |
example10 :: Cont Int Int | |
example10 = callCC f | |
where | |
f :: (Int -> Cont Int ()) -> Cont Int Int | |
f retF = do | |
for_ [1..50] $ \i -> if i == 20 then retF i else pure () | |
pure 1000 |
Sign up for free
to join this conversation on GitHub.
Already have an account?
Sign in to comment
I ran this with GHC-8.8.4 with the built-in transformers-0.5.6.2.