Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data RequestType (accessType :: ModelAccess) (contentTypes :: [Type]) (verb :: Type -> Type)
- data ModelAccess
- type Cmd = RequestType 'Direct '[JSON] (Verb 'POST 200 '[JSON])
- type CbCmd = RequestType 'Callback '[JSON] (Verb 'POST 200 '[JSON])
- type Query = RequestType 'Direct '[JSON] (Verb 'GET 200 '[JSON])
- type CbQuery = RequestType 'Callback '[JSON] (Verb 'GET 200 '[JSON])
- type Action = ParamPart -> Type -> Type -> Type
- type family CanMutate method :: Bool where ...
- data ParamPart
- type family P (x :: ParamPart) (name :: Symbol) (a :: Type) where ...
- type family GetModelAccess method :: ModelAccess where ...
- data HandlerType method model event m a where
- Query :: (CanMutate method ~ 'False, GetModelAccess method ~ 'Direct) => (model -> m a) -> HandlerType method model event m a
- CbQuery :: (CanMutate method ~ 'False, GetModelAccess method ~ 'Callback) => (m model -> m a) -> HandlerType method model event m a
- Cmd :: (CanMutate method ~ 'True, GetModelAccess method ~ 'Direct) => (model -> m (model -> a, [event])) -> HandlerType method model event m a
- CbCmd :: (CanMutate method ~ 'True, GetModelAccess method ~ 'Callback) => ((forall x. (model -> m (model -> x, [event])) -> m x) -> m a) -> HandlerType method model event m a
- type CmdCallback model event (m :: Type -> Type) = forall a. model -> m (a, [event])
- mapModel :: forall m event model0 model1 method a. Monad m => (model0 -> model1) -> HandlerType method model1 event m a -> HandlerType method model0 event m a
- mapEvent :: forall m e0 e1 a method model. Monad m => (e0 -> e1) -> HandlerType method model e0 m a -> HandlerType method model e1 m a
- mapResult :: Monad m => (r0 -> r1) -> HandlerType method model e m r0 -> HandlerType method model e m r1
- type ActionHandler model event m c = forall method a. c 'ParamType method a -> HandlerType method model event m a
- type ActionRunner m c = forall method a. MonadUnliftIO m => c 'ParamType method a -> m a
- runAction :: (MonadUnliftIO m, WriteModel p, model ~ Model p, event ~ Event p) => p -> ActionHandler model event m cmd -> cmd 'ParamType method ret -> m ret
Documentation
data RequestType (accessType :: ModelAccess) (contentTypes :: [Type]) (verb :: Type -> Type) Source #
data ModelAccess Source #
type Action = ParamPart -> Type -> Type -> Type Source #
The kind of an Action, defined with a GADT as: data MyAction :: Action where ThisAction :: P x "count" Int -> MyAction x 'Cmd Int ThatAction :: P x "description" Text -> MyAction x 'Cmd ()
type family CanMutate method :: Bool where ... Source #
CanMutate (RequestType a c (Verb 'GET code cts)) = 'False | |
CanMutate (RequestType a c (Verb 'POST code cts)) = 'True | |
CanMutate (RequestType a c (Verb 'PUT code cts)) = 'True | |
CanMutate (RequestType a c (Verb 'PATCH code cts)) = 'True | |
CanMutate (RequestType a c (Verb 'DELETE code cts)) = 'True |
Used as a parameter to the P
type family on order to determine the focus.
type family P (x :: ParamPart) (name :: Symbol) (a :: Type) where ... Source #
P is used for specifying the parameters of the model. The name will be used as the name in the JSON encoding or the query parameter of the generated server.
type family GetModelAccess method :: ModelAccess where ... Source #
GetModelAccess (RequestType a b c) = a |
data HandlerType method model event m a where Source #
Query :: (CanMutate method ~ 'False, GetModelAccess method ~ 'Direct) => (model -> m a) -> HandlerType method model event m a | |
CbQuery :: (CanMutate method ~ 'False, GetModelAccess method ~ 'Callback) => (m model -> m a) -> HandlerType method model event m a | |
Cmd :: (CanMutate method ~ 'True, GetModelAccess method ~ 'Direct) => (model -> m (model -> a, [event])) -> HandlerType method model event m a | |
CbCmd :: (CanMutate method ~ 'True, GetModelAccess method ~ 'Callback) => ((forall x. (model -> m (model -> x, [event])) -> m x) -> m a) -> HandlerType method model event m a |
type CmdCallback model event (m :: Type -> Type) = forall a. model -> m (a, [event]) Source #
mapModel :: forall m event model0 model1 method a. Monad m => (model0 -> model1) -> HandlerType method model1 event m a -> HandlerType method model0 event m a Source #
mapEvent :: forall m e0 e1 a method model. Monad m => (e0 -> e1) -> HandlerType method model e0 m a -> HandlerType method model e1 m a Source #
mapResult :: Monad m => (r0 -> r1) -> HandlerType method model e m r0 -> HandlerType method model e m r1 Source #
type ActionHandler model event m c = forall method a. c 'ParamType method a -> HandlerType method model event m a Source #
Action handler
Expects a command, specified using a one-parameter GADT where the parameter specifies the return type.
When implementing the handler you have access to IO, but in order for the library to ensure thread safety of state updates you do not have direct access to the current state. Instead the handler returns a continuation, telling the library how to perform the evaluations on the model.
The resulting events will be applied to the current state so that no other command can run and generate events on the same state.
type ActionRunner m c = forall method a. MonadUnliftIO m => c 'ParamType method a -> m a Source #
runAction :: (MonadUnliftIO m, WriteModel p, model ~ Model p, event ~ Event p) => p -> ActionHandler model event m cmd -> cmd 'ParamType method ret -> m ret Source #