Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
Recalc.Server
Description
This module implements a reactor pattern for Recalc
, ensuring asynchronous
processing of spreadsheet updates and computations. A single threaded loop
listens for JSON-RPC messages and maintains jobs.
Jobs are picked up by multiple "worker" threads such that long-running computations do not block messaging.
Example
type Protocol type Api = ToApi Protocol initialState = ... main :: IO () main = runHandlerApi initialState $ state -> hoist
Api (runReaderT
state) (namedHandlers server) where server :: Protocol (AsServerT (Handler EngineState)) server = Protocol { ... }
Synopsis
- type Handler engine = ReaderT (State engine) IO
- liftEngine :: State engine a -> Handler engine a
- sendIO :: ToJSON a => a -> IO ()
- debug :: Show a => String -> a -> Handler engine ()
- dumpEngineState :: Show engine => Handler engine ()
- scheduleJob :: ReaderT (State engine) IO () -> Handler engine ()
- runHandler :: forall api engine. HasHandler api => engine -> (State engine -> HandlerT api IO) -> IO ()
- type Id = Word64
- data JsonRpcRequest params = JsonRpcRequest {
- request'method :: String
- request'id :: Maybe Id
- request'params :: params
- pattern JsonRpcNotification :: String -> params -> JsonRpcRequest params
- data JsonRpc (sym :: Symbol) (params :: Type) (rsp :: Type)
- class HasHandler api
- type family HandlerT api (m :: Type -> Type)
- handle :: forall api. HasHandler api => JsonRpcRequest Value -> Handler api -> Either String (IO Value)
- hoist :: HasHandler api => (forall x. m x -> n x) -> HandlerT api m -> HandlerT api n
- class GenericMode mode where
- data AsServerT (m :: Type -> Type)
- type AsServer = AsServerT IO
- data AsApi
- type ToApi api' = GToSum (Rep (api' AsApi))
- namedHandlers :: (GenericMode m, Generic (api' m), GSum (Rep (api' m))) => api' m -> GToSum (Rep (api' m))
- data (path :: Symbol) :> (a :: Type) :: Type
- data a :<|> b = a :<|> b
- data Nullable t
- aesonOptions :: Options
Documentation
type Handler engine = ReaderT (State engine) IO Source #
handler threads are in IO and have access to the state
liftEngine :: State engine a -> Handler engine a Source #
sendIO :: ToJSON a => a -> IO () Source #
send JSON-RPC message on stdout (locked to prevent interleaving)
dumpEngineState :: Show engine => Handler engine () Source #
runHandler :: forall api engine. HasHandler api => engine -> (State engine -> HandlerT api IO) -> IO () Source #
reads lines from stdin and maintains a channel of reactor inputs with new requests, handler threads deal with requests by reading from the request channel.
data JsonRpcRequest params Source #
Constructors
JsonRpcRequest | |
Fields
|
Instances
pattern JsonRpcNotification :: String -> params -> JsonRpcRequest params Source #
data JsonRpc (sym :: Symbol) (params :: Type) (rsp :: Type) Source #
Instances
(KnownSymbol sym, FromJSON params, ToJSON rsp, Typeable params) => HasHandler (JsonRpc sym params rsp :: Type) Source # | |
Defined in Recalc.Server.Generic | |
type HandlerT (JsonRpc sym params rsp :: Type) m Source # | |
class HasHandler api Source #
Minimal complete definition
handle', hoist
Instances
(HasHandler a, HasHandler b) => HasHandler (a :<|> b :: Type) Source # | |
(KnownSymbol path, HasHandler api) => HasHandler (path :> api :: Type) Source # | |
(KnownSymbol sym, FromJSON params, ToJSON rsp, Typeable params) => HasHandler (JsonRpc sym params rsp :: Type) Source # | |
Defined in Recalc.Server.Generic |
handle :: forall api. HasHandler api => JsonRpcRequest Value -> Handler api -> Either String (IO Value) Source #
class GenericMode mode Source #
generic modes for protocol datatypes
Instances
GenericMode AsApi Source # | |
Defined in Recalc.Server.Generic | |
GenericMode (AsServerT m :: Type) Source # | |
Defined in Recalc.Server.Generic |
namedHandlers :: (GenericMode m, Generic (api' m), GSum (Rep (api' m))) => api' m -> GToSum (Rep (api' m)) Source #
data (path :: Symbol) :> (a :: Type) :: Type infixr 4 Source #
Instances
(KnownSymbol path, HasHandler api) => HasHandler (path :> api :: Type) Source # | |
type HandlerT (path :> api :: Type) m Source # | |
Defined in Recalc.Server.Generic |
data a :<|> b infixr 3 Source #
Constructors
a :<|> b infixr 3 |
Instances
(HasHandler a, HasHandler b) => HasHandler (a :<|> b :: Type) Source # | |
type HandlerT (a :<|> b :: Type) m Source # | |
Instances
FromJSON t => FromJSON (Nullable t) Source # | |
Defined in Recalc.Server.Types | |
ToJSON t => ToJSON (Nullable t) Source # | |
Show t => Show (Nullable t) Source # | |
Eq t => Eq (Nullable t) Source # | |
Ord t => Ord (Nullable t) Source # | |
Defined in Recalc.Server.Types |
aesonOptions :: Options Source #
JSON Instances