{-# options_haddock prune #-}
module Ribosome.Host.Data.RpcHandler where
import Data.MessagePack (Object)
import Exon (exon)
import Text.Show (showParen, showsPrec)
import Ribosome.Host.Data.Execution (Execution)
import Ribosome.Host.Data.Report (Report, resumeReport, Report)
import Ribosome.Host.Data.Request (RpcMethod (RpcMethod))
import Ribosome.Host.Data.RpcError (RpcError)
import Ribosome.Host.Data.RpcName (RpcName (RpcName))
import qualified Ribosome.Host.Data.RpcType as RpcType
import Ribosome.Host.Data.RpcType (RpcType)
import Ribosome.Host.Effect.Rpc (Rpc)
type Handler r a =
Sem (Stop Report : r) a
type RpcHandlerFun r =
[Object] -> Handler r Object
data RpcHandler r =
RpcHandler {
forall (r :: [(* -> *) -> * -> *]). RpcHandler r -> RpcType
rpcType :: RpcType,
forall (r :: [(* -> *) -> * -> *]). RpcHandler r -> RpcName
rpcName :: RpcName,
forall (r :: [(* -> *) -> * -> *]). RpcHandler r -> Execution
rpcExecution :: Execution,
forall (r :: [(* -> *) -> * -> *]). RpcHandler r -> RpcHandlerFun r
rpcHandler :: RpcHandlerFun r
}
deriving stock ((forall x. RpcHandler r -> Rep (RpcHandler r) x)
-> (forall x. Rep (RpcHandler r) x -> RpcHandler r)
-> Generic (RpcHandler r)
forall (r :: [(* -> *) -> * -> *]) x.
Rep (RpcHandler r) x -> RpcHandler r
forall (r :: [(* -> *) -> * -> *]) x.
RpcHandler r -> Rep (RpcHandler r) x
forall x. Rep (RpcHandler r) x -> RpcHandler r
forall x. RpcHandler r -> Rep (RpcHandler r) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall (r :: [(* -> *) -> * -> *]) x.
Rep (RpcHandler r) x -> RpcHandler r
$cfrom :: forall (r :: [(* -> *) -> * -> *]) x.
RpcHandler r -> Rep (RpcHandler r) x
Generic)
instance Show (RpcHandler m) where
showsPrec :: Int -> RpcHandler m -> ShowS
showsPrec Int
p (RpcHandler RpcType
t RpcName
n Execution
e RpcHandlerFun m
_) =
Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
10) [exon|RpcHandler #{showsPrec 11 t} #{showsPrec 11 n} #{showsPrec 11 e}|]
hoistRpcHandler ::
(∀ x . Sem (Stop Report : r) x -> Sem (Stop Report : r1) x) ->
RpcHandler r ->
RpcHandler r1
hoistRpcHandler :: forall (r :: [(* -> *) -> * -> *]) (r1 :: [(* -> *) -> * -> *]).
(forall x. Sem (Stop Report : r) x -> Sem (Stop Report : r1) x)
-> RpcHandler r -> RpcHandler r1
hoistRpcHandler forall x. Sem (Stop Report : r) x -> Sem (Stop Report : r1) x
f RpcHandler {Execution
RpcName
RpcType
RpcHandlerFun r
rpcHandler :: RpcHandlerFun r
rpcExecution :: Execution
rpcName :: RpcName
rpcType :: RpcType
$sel:rpcHandler:RpcHandler :: forall (r :: [(* -> *) -> * -> *]). RpcHandler r -> RpcHandlerFun r
$sel:rpcExecution:RpcHandler :: forall (r :: [(* -> *) -> * -> *]). RpcHandler r -> Execution
$sel:rpcName:RpcHandler :: forall (r :: [(* -> *) -> * -> *]). RpcHandler r -> RpcName
$sel:rpcType:RpcHandler :: forall (r :: [(* -> *) -> * -> *]). RpcHandler r -> RpcType
..} =
RpcHandler :: forall (r :: [(* -> *) -> * -> *]).
RpcType -> RpcName -> Execution -> RpcHandlerFun r -> RpcHandler r
RpcHandler {$sel:rpcHandler:RpcHandler :: RpcHandlerFun r1
rpcHandler = Sem (Stop Report : r) Object -> Sem (Stop Report : r1) Object
forall x. Sem (Stop Report : r) x -> Sem (Stop Report : r1) x
f (Sem (Stop Report : r) Object -> Sem (Stop Report : r1) Object)
-> RpcHandlerFun r -> RpcHandlerFun r1
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RpcHandlerFun r
rpcHandler, Execution
RpcName
RpcType
rpcExecution :: Execution
rpcName :: RpcName
rpcType :: RpcType
$sel:rpcExecution:RpcHandler :: Execution
$sel:rpcName:RpcHandler :: RpcName
$sel:rpcType:RpcHandler :: RpcType
..}
hoistRpcHandlers ::
(∀ x . Sem (Stop Report : r) x -> Sem (Stop Report : r1) x) ->
[RpcHandler r] ->
[RpcHandler r1]
hoistRpcHandlers :: forall (r :: [(* -> *) -> * -> *]) (r1 :: [(* -> *) -> * -> *]).
(forall x. Sem (Stop Report : r) x -> Sem (Stop Report : r1) x)
-> [RpcHandler r] -> [RpcHandler r1]
hoistRpcHandlers forall x. Sem (Stop Report : r) x -> Sem (Stop Report : r1) x
f =
(RpcHandler r -> RpcHandler r1)
-> [RpcHandler r] -> [RpcHandler r1]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((forall x. Sem (Stop Report : r) x -> Sem (Stop Report : r1) x)
-> RpcHandler r -> RpcHandler r1
forall (r :: [(* -> *) -> * -> *]) (r1 :: [(* -> *) -> * -> *]).
(forall x. Sem (Stop Report : r) x -> Sem (Stop Report : r1) x)
-> RpcHandler r -> RpcHandler r1
hoistRpcHandler forall x. Sem (Stop Report : r) x -> Sem (Stop Report : r1) x
f)
rpcMethod ::
RpcType ->
RpcName ->
RpcMethod
rpcMethod :: RpcType -> RpcName -> RpcMethod
rpcMethod RpcType
rpcType (RpcName Text
name) =
Text -> RpcMethod
RpcMethod [exon|#{RpcType.methodPrefix rpcType}:#{name}|]
rpcHandlerMethod :: RpcHandler r -> RpcMethod
rpcHandlerMethod :: forall (r :: [(* -> *) -> * -> *]). RpcHandler r -> RpcMethod
rpcHandlerMethod RpcHandler {RpcType
rpcType :: RpcType
$sel:rpcType:RpcHandler :: forall (r :: [(* -> *) -> * -> *]). RpcHandler r -> RpcType
rpcType, RpcName
rpcName :: RpcName
$sel:rpcName:RpcHandler :: forall (r :: [(* -> *) -> * -> *]). RpcHandler r -> RpcName
rpcName} =
RpcType -> RpcName -> RpcMethod
rpcMethod RpcType
rpcType RpcName
rpcName
simpleHandler ::
Member (Rpc !! RpcError) r =>
Sem (Rpc : Stop Report : r) a ->
Handler r a
simpleHandler :: forall (r :: [(* -> *) -> * -> *]) a.
Member (Rpc !! RpcError) r =>
Sem (Rpc : Stop Report : r) a -> Handler r a
simpleHandler =
Sem (Rpc : Stop Report : r) a -> Sem (Stop Report : r) a
forall (eff :: (* -> *) -> * -> *) e (r :: [(* -> *) -> * -> *]) a.
(Reportable e, Members '[eff !! e, Stop Report] r) =>
Sem (eff : r) a -> Sem r a
resumeReport