module Control.Distributed.Session.Session (
Session(..),
SessionInfo(..),
runSession,
liftP,
liftST
) where
import Control.SessionTypes
import Control.SessionTypes.Codensity
import Control.SessionTypes.Indexed hiding (abs)
import Control.Distributed.Session.STChannel (UTChan)
import Control.Distributed.Process as P (Process, ProcessId, NodeId, liftIO)
newtype Session s r a = Session { runSessionC :: Maybe SessionInfo -> IxC Process s r a }
data SessionInfo = SessionInfo {
othPid :: ProcessId,
othNode :: NodeId,
utchan :: UTChan
}
runSession :: Session s r a -> Maybe SessionInfo -> STTerm Process s r a
runSession (Session c) si = abs $ c si
instance IxFunctor Session where
fmap f sess = Session $ \si -> fmap f $ runSessionC sess si
instance IxApplicative Session where
pure = return
f <*> g = Session $ \si -> (runSessionC f si) <*> (runSessionC g si)
instance IxMonad Session where
return a = Session $ \_ -> return a
(Session s) >>= f = Session $ \si -> do
a <- s si
let (Session r) = f a
r si
instance MonadSession Session where
send a = Session $ const $ send a
recv = Session $ const recv
sel1 = Session $ const sel1
sel2 = Session $ const sel2
offZ (Session f) = Session $ offZ . f
offS (Session f) (Session g) = Session $ \si -> offS (f si) (g si)
recurse (Session f) = Session $ \si -> recurse (f si)
weaken (Session f) = Session $ \si -> weaken (f si)
var (Session f) = Session $ \si -> var $ f si
eps a = Session $ const $ eps a
instance IxMonadReader (Maybe SessionInfo) Session where
ask = Session $ \si -> return si
local f m = Session $ \si -> runSessionC m (f si)
reader f = Session $ \si -> return (f si)
instance IxMonadIO Session where
liftIO = liftP . P.liftIO
liftP :: Process a -> Session s s a
liftP p = Session $ \_ -> rep $ lift p
liftST :: STTerm Process s r a -> Session s r a
liftST st = Session $ \_ -> rep st