Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- mkId :: MonadIO m => m UUID
- type family Event p
- type family Model p
- class ReadModel p where
- class ReadModel p => WriteModel p where
- transactionalUpdate :: MonadUnliftIO m => p -> (Model p -> m (Model p -> a, [Event p])) -> m a
- data Stored a = Stored {
- storedEvent :: a
- storedTimestamp :: UTCTime
- storedUUID :: UUID
- data UUID
- data NF9 (name :: Symbol) (f1 :: Symbol) a1 (f2 :: Symbol) a2 (f3 :: Symbol) a3 (f4 :: Symbol) a4 (f5 :: Symbol) a5 (f6 :: Symbol) a6 (f7 :: Symbol) a7 (f8 :: Symbol) a8 (f9 :: Symbol) a9 = NF9 a1 a2 a3 a4 a5 a6 a7 a8 a9
- data NF8 (name :: Symbol) (f1 :: Symbol) a1 (f2 :: Symbol) a2 (f3 :: Symbol) a3 (f4 :: Symbol) a4 (f5 :: Symbol) a5 (f6 :: Symbol) a6 (f7 :: Symbol) a7 (f8 :: Symbol) a8 = NF8 a1 a2 a3 a4 a5 a6 a7 a8
- data NF7 (name :: Symbol) (f1 :: Symbol) a1 (f2 :: Symbol) a2 (f3 :: Symbol) a3 (f4 :: Symbol) a4 (f5 :: Symbol) a5 (f6 :: Symbol) a6 (f7 :: Symbol) a7 = NF7 a1 a2 a3 a4 a5 a6 a7
- data NF6 (name :: Symbol) (f1 :: Symbol) a1 (f2 :: Symbol) a2 (f3 :: Symbol) a3 (f4 :: Symbol) a4 (f5 :: Symbol) a5 (f6 :: Symbol) a6 = NF6 a1 a2 a3 a4 a5 a6
- data NF5 (name :: Symbol) (f1 :: Symbol) a1 (f2 :: Symbol) a2 (f3 :: Symbol) a3 (f4 :: Symbol) a4 (f5 :: Symbol) a5 = NF5 a1 a2 a3 a4 a5
- data NF4 (name :: Symbol) (f1 :: Symbol) a1 (f2 :: Symbol) a2 (f3 :: Symbol) a3 (f4 :: Symbol) a4 = NF4 a1 a2 a3 a4
- data NF3 (name :: Symbol) (f1 :: Symbol) a1 (f2 :: Symbol) a2 (f3 :: Symbol) a3 = NF3 a1 a2 a3
- data NF2 (name :: Symbol) (f1 :: Symbol) a1 (f2 :: Symbol) a2 = NF2 a1 a2
- data NF1 (name :: Symbol) (f1 :: Symbol) ty = NF1 ty
- type ActionRunner m c = forall method a. MonadUnliftIO m => c 'ParamType method a -> m a
- type ActionHandler model event m c = forall method a. c 'ParamType method a -> HandlerType method model event m a
- 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 family P (x :: ParamPart) (name :: Symbol) (a :: Type) where ...
- data ParamPart
- type family CanMutate method :: Bool where ...
- type Action = ParamPart -> Type -> Type -> Type
- type Query = RequestType 'Direct '[JSON] (Verb 'GET 200 '[JSON])
- type CbCmd = RequestType 'Callback '[JSON] (Verb 'POST 200 '[JSON])
- type Cmd = RequestType 'Direct '[JSON] (Verb 'POST 200 '[JSON])
- data ModelAccess
- data RequestType (accessType :: ModelAccess) (contentTypes :: [Type]) (verb :: Type -> Type)
- 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
- runAction :: (MonadUnliftIO m, WriteModel p, model ~ Model p, event ~ Event p) => p -> ActionHandler model event m cmd -> cmd 'ParamType method ret -> m ret
- data ApiOptions = ApiOptions {}
- defaultApiOptions :: ApiOptions
- class HasApiOptions (action :: Action) where
- data ServerConfig
- mkServerConfig :: String -> Q [Dec]
- mkServer :: ServerConfig -> Name -> Q [Dec]
Documentation
class ReadModel p => WriteModel p where #
transactionalUpdate :: MonadUnliftIO m => p -> (Model p -> m (Model p -> a, [Event p])) -> m a #
Wrapper for stored data This ensures all events have a unique ID and a timestamp, without having to deal with that when implementing the model.
Stored | |
|
Instances
Type representing Universally Unique Identifiers (UUID) as specified in RFC 4122.
Instances
FromJSON UUID | |
FromJSONKey UUID | |
Defined in Data.Aeson.Types.FromJSON | |
ToJSON UUID | |
Defined in Data.Aeson.Types.ToJSON | |
ToJSONKey UUID | |
Defined in Data.Aeson.Types.ToJSON | |
Data UUID | |
Defined in Data.UUID.Types.Internal gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UUID -> c UUID # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UUID # dataTypeOf :: UUID -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c UUID) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UUID) # gmapT :: (forall b. Data b => b -> b) -> UUID -> UUID # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UUID -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UUID -> r # gmapQ :: (forall d. Data d => d -> u) -> UUID -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> UUID -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> UUID -> m UUID # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UUID -> m UUID # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UUID -> m UUID # | |
Storable UUID | This |
Defined in Data.UUID.Types.Internal | |
Read UUID | |
Show UUID | Pretty prints a
|
Binary UUID | This |
NFData UUID | |
Defined in Data.UUID.Types.Internal | |
Eq UUID | |
Ord UUID | |
Hashable UUID | |
Defined in Data.UUID.Types.Internal | |
FromHttpApiData UUID | |
Defined in Web.Internal.HttpApiData parseUrlPiece :: Text -> Either Text UUID # parseHeader :: ByteString -> Either Text UUID # | |
ToHttpApiData UUID | |
Defined in Web.Internal.HttpApiData toUrlPiece :: UUID -> Text # toEncodedUrlPiece :: UUID -> Builder # toHeader :: UUID -> ByteString # toQueryParam :: UUID -> Text # | |
ToParamSchema UUID | |
Defined in Data.OpenApi.Internal.ParamSchema toParamSchema :: Proxy UUID -> Schema # | |
ToSchema UUID | For |
Defined in Data.OpenApi.Internal.Schema | |
Random UUID | This |
Uniform UUID | |
Defined in Data.UUID.Types.Internal uniformM :: StatefulGen g m => g -> m UUID # | |
Lift UUID | |
data NF9 (name :: Symbol) (f1 :: Symbol) a1 (f2 :: Symbol) a2 (f3 :: Symbol) a3 (f4 :: Symbol) a4 (f5 :: Symbol) a5 (f6 :: Symbol) a6 (f7 :: Symbol) a7 (f8 :: Symbol) a8 (f9 :: Symbol) a9 Source #
NF9 a1 a2 a3 a4 a5 a6 a7 a8 a9 |
Instances
data NF8 (name :: Symbol) (f1 :: Symbol) a1 (f2 :: Symbol) a2 (f3 :: Symbol) a3 (f4 :: Symbol) a4 (f5 :: Symbol) a5 (f6 :: Symbol) a6 (f7 :: Symbol) a7 (f8 :: Symbol) a8 Source #
NF8 a1 a2 a3 a4 a5 a6 a7 a8 |
Instances
data NF7 (name :: Symbol) (f1 :: Symbol) a1 (f2 :: Symbol) a2 (f3 :: Symbol) a3 (f4 :: Symbol) a4 (f5 :: Symbol) a5 (f6 :: Symbol) a6 (f7 :: Symbol) a7 Source #
NF7 a1 a2 a3 a4 a5 a6 a7 |
Instances
data NF6 (name :: Symbol) (f1 :: Symbol) a1 (f2 :: Symbol) a2 (f3 :: Symbol) a3 (f4 :: Symbol) a4 (f5 :: Symbol) a5 (f6 :: Symbol) a6 Source #
NF6 a1 a2 a3 a4 a5 a6 |
Instances
data NF5 (name :: Symbol) (f1 :: Symbol) a1 (f2 :: Symbol) a2 (f3 :: Symbol) a3 (f4 :: Symbol) a4 (f5 :: Symbol) a5 Source #
NF5 a1 a2 a3 a4 a5 |
Instances
data NF4 (name :: Symbol) (f1 :: Symbol) a1 (f2 :: Symbol) a2 (f3 :: Symbol) a3 (f4 :: Symbol) a4 Source #
NF4 a1 a2 a3 a4 |
Instances
data NF3 (name :: Symbol) (f1 :: Symbol) a1 (f2 :: Symbol) a2 (f3 :: Symbol) a3 Source #
NF3 a1 a2 a3 |
Instances
data NF2 (name :: Symbol) (f1 :: Symbol) a1 (f2 :: Symbol) a2 Source #
NF2 a1 a2 |
Instances
data NF1 (name :: Symbol) (f1 :: Symbol) ty Source #
NF1 ty |
Instances
(KnownSymbol name, KnownSymbol f1, FromJSON a1) => FromJSON (NF1 name f1 a1) Source # | |
(KnownSymbol f1, ToJSON a1) => ToJSON (NF1 name f1 a1) Source # | |
Defined in DomainDriven.Internal.NamedFields | |
Generic (NF1 name f1 ty) Source # | |
Show ty => Show (NF1 name f1 ty) Source # | |
(KnownSymbol name, KnownSymbol f1, ToSchema a1) => ToSchema (NF1 name f1 a1) Source # | |
Defined in DomainDriven.Internal.NamedFields declareNamedSchema :: Proxy (NF1 name f1 a1) -> Declare (Definitions Schema) NamedSchema # | |
type Rep (NF1 name f1 ty) Source # | |
Defined in DomainDriven.Internal.NamedFields |
type ActionRunner m c = forall method a. MonadUnliftIO m => c 'ParamType method a -> m a 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.
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 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.
Used as a parameter to the P
type family on order to determine the focus.
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 |
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 ()
data ModelAccess Source #
data RequestType (accessType :: ModelAccess) (contentTypes :: [Type]) (verb :: Type -> Type) 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 #
runAction :: (MonadUnliftIO m, WriteModel p, model ~ Model p, event ~ Event p) => p -> ActionHandler model event m cmd -> cmd 'ParamType method ret -> m ret Source #
data ApiOptions Source #
ApiOptions | |
|
Instances
Generic ApiOptions Source # | |
Defined in DomainDriven.Server.Types type Rep ApiOptions :: Type -> Type # from :: ApiOptions -> Rep ApiOptions x # to :: Rep ApiOptions x -> ApiOptions # | |
Show ApiOptions Source # | |
Defined in DomainDriven.Server.Types showsPrec :: Int -> ApiOptions -> ShowS # show :: ApiOptions -> String # showList :: [ApiOptions] -> ShowS # | |
type Rep ApiOptions Source # | |
Defined in DomainDriven.Server.Types type Rep ApiOptions = D1 ('MetaData "ApiOptions" "DomainDriven.Server.Types" "domaindriven-0.5.0-DXvek89qD5M1xwQ4V40Syp" 'False) (C1 ('MetaCons "ApiOptions" 'PrefixI 'True) (S1 ('MetaSel ('Just "renameConstructor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (String -> String)) :*: (S1 ('MetaSel ('Just "typenameSeparator") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Just "bodyNameBase") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String))))) |
data ServerConfig Source #
Configuration used to generate server
This is expected to be generated by mkServerConfig
. It is only explicit due to
the GHC stage restrictions.
Instances
Generic ServerConfig Source # | |
Defined in DomainDriven.Server.Config type Rep ServerConfig :: Type -> Type # from :: ServerConfig -> Rep ServerConfig x # to :: Rep ServerConfig x -> ServerConfig # | |
Show ServerConfig Source # | |
Defined in DomainDriven.Server.Config showsPrec :: Int -> ServerConfig -> ShowS # show :: ServerConfig -> String # showList :: [ServerConfig] -> ShowS # | |
type Rep ServerConfig Source # | |
Defined in DomainDriven.Server.Config type Rep ServerConfig = D1 ('MetaData "ServerConfig" "DomainDriven.Server.Config" "domaindriven-0.5.0-DXvek89qD5M1xwQ4V40Syp" 'False) (C1 ('MetaCons "ServerConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "allApiOptions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map String ApiOptions)))) |