module Control.SessionTypes.Codensity where
import Control.SessionTypes.STTerm
import Control.SessionTypes.MonadSession
import Control.SessionTypes.Indexed hiding (abs)
newtype IxC m s r a = IxC { runIxC :: forall b k. (a -> STTerm m r k b) -> STTerm m s k b }
instance IxFunctor (IxC m) where
fmap f (IxC x) = IxC $ \c -> x (c . f)
instance IxApplicative (IxC m) where
pure = return
(<*>) = ap
instance IxMonad (IxC m) where
return a = IxC $ \h -> h a
(IxC h) >>= f = IxC $ \c -> h $ \a -> runIxC (f a) c
instance Monad m => MonadSession (IxC m) where
send a = IxC $ \h -> send a >>= h
recv = IxC $ \h -> recv >>= h
sel1 = IxC $ \h -> sel1 >>= h
sel2 = IxC $ \h -> sel2 >>= h
offZ (IxC f) = IxC $ \h -> offZ (f h)
offS (IxC f) (IxC g) = IxC $ \h -> offS (f h) (g h)
recurse (IxC f) = IxC $ \h -> recurse $ f h
weaken (IxC f) = IxC $ \h -> weaken $ f h
var (IxC f) = IxC $ \h -> var $ f h
eps a = IxC $ \h -> h a
abs :: Monad m => IxC m s r a -> STTerm m s r a
abs (IxC f) = f $ \a -> return a
rep :: Monad m => STTerm m s r a -> IxC m s r a
rep m = IxC $ \h -> m >>= h