module Control.Eff.Concurrent.Protocol.EffectfulServer
( Server(..)
, Event(..)
, start
, startLink
, protocolServerLoop
)
where
import Control.Applicative
import Control.DeepSeq
import Control.Eff
import Control.Eff.Concurrent.Misc
import Control.Eff.Extend ()
import Control.Eff.Concurrent.Process
import Control.Eff.Concurrent.Process.Timer
import Control.Eff.Concurrent.Protocol
import Control.Eff.Concurrent.Protocol.Wrapper
import Control.Eff.Log
import Control.Lens
import Data.Kind
import Data.String
import Data.Typeable
import Data.Type.Pretty
import qualified Data.Text as T
import GHC.Stack (HasCallStack)
class Server (a :: Type) (e :: [Type -> Type])
where
data Init a
type ServerPdu a :: Type
type ServerPdu a = a
type ServerEffects a e :: [Type -> Type]
type ServerEffects a e = e
serverTitle :: Init a -> ProcessTitle
default serverTitle :: Typeable a => Init a -> ProcessTitle
serverTitle _ = fromString $ showSTypeable @a ""
runEffects :: Endpoint (ServerPdu a) -> Init a -> Eff (ServerEffects a e) x -> Eff e x
default runEffects :: ServerEffects a e ~ e => Endpoint (ServerPdu a) -> Init a -> Eff (ServerEffects a e) x -> Eff e x
runEffects _ = const id
onEvent :: Endpoint (ServerPdu a) -> Init a -> Event (ServerPdu a) -> Eff (ServerEffects a e) ()
default onEvent :: (Show (Init a), Member Logs (ServerEffects a e)) => Endpoint (ServerPdu a) -> Init a -> Event (ServerPdu a) -> Eff (ServerEffects a e) ()
onEvent _ i e = logInfo ("unhandled: " <> T.pack (show i) <> " " <> T.pack (show e))
start
:: forall a r q
. ( Server a (Processes q)
, Typeable a
, Typeable (ServerPdu a)
, FilteredLogging (Processes q)
, HasProcesses (ServerEffects a (Processes q)) q
, HasProcesses r q
, HasCallStack)
=> Init a
-> Eff r (Endpoint (ServerPdu a))
start a = asEndpoint <$> spawn (serverTitle @_ @(Processes q) a) (protocolServerLoop a)
startLink
:: forall a r q
. ( Typeable a
, Typeable (ServerPdu a)
, Server a (Processes q)
, FilteredLogging (Processes q)
, HasProcesses (ServerEffects a (Processes q)) q
, HasProcesses r q
, HasCallStack)
=> Init a
-> Eff r (Endpoint (ServerPdu a))
startLink a = asEndpoint <$> spawnLink (serverTitle @_ @(Processes q) a) (protocolServerLoop a)
protocolServerLoop
:: forall q a
. ( Server a (Processes q)
, FilteredLogging (Processes q)
, HasProcesses (ServerEffects a (Processes q)) q
, Typeable a
, Typeable (ServerPdu a)
)
=> Init a -> Eff (Processes q) ()
protocolServerLoop a = do
myEp <- asEndpoint @(ServerPdu a) <$> self
logDebug ("starting")
runEffects myEp a (receiveSelectedLoop sel (mainLoop myEp))
return ()
where
sel :: MessageSelector (Event (ServerPdu a))
sel = onRequest <$> selectMessage @(Request (ServerPdu a))
<|> OnDown <$> selectMessage @ProcessDown
<|> OnTimeOut <$> selectMessage @TimerElapsed
<|> OnMessage <$> selectAnyMessage
where
onRequest :: Request (ServerPdu a) -> Event (ServerPdu a)
onRequest (Call o m) = OnCall (replyTarget (MkSerializer toStrictDynamic) o) m
onRequest (Cast m) = OnCast m
handleInt myEp i = onEvent @_ @(Processes q) myEp a (OnInterrupt i) *> pure Nothing
mainLoop :: (Typeable a)
=> Endpoint (ServerPdu a)
-> Either (Interrupt 'Recoverable) (Event (ServerPdu a))
-> Eff (ServerEffects a (Processes q)) (Maybe ())
mainLoop myEp (Left i) = handleInt myEp i
mainLoop myEp (Right i) = onEvent @_ @(Processes q) myEp a i *> pure Nothing
data Event a where
OnCall
:: forall a r. (Tangible r, TangiblePdu a ('Synchronous r))
=> ReplyTarget a r
-> Pdu a ('Synchronous r)
-> Event a
OnCast
:: forall a. TangiblePdu a 'Asynchronous
=> Pdu a 'Asynchronous
-> Event a
OnInterrupt :: Interrupt 'Recoverable -> Event a
OnDown :: ProcessDown -> Event a
OnTimeOut :: TimerElapsed -> Event a
OnMessage :: StrictDynamic -> Event a
deriving Typeable
instance Show (Event a) where
showsPrec d e =
showParen (d>=10) $
showString "event: "
. case e of
OnCall o p -> shows (Call (view replyTargetOrigin o) p)
OnCast p -> shows (Cast p)
OnInterrupt r -> shows r
OnDown r -> shows r
OnTimeOut r -> shows r
OnMessage r -> shows r
instance NFData a => NFData (Event a) where
rnf = \case
OnCall o p -> rnf o `seq` rnf p
OnCast p -> rnf p
OnInterrupt r -> rnf r
OnDown r -> rnf r
OnTimeOut r -> rnf r
OnMessage r -> r `seq` ()
type instance ToPretty (Event a) = ToPretty a <+> PutStr "event"