Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data ApiSpec = ApiSpec {}
- data VarBindings = VarBindings {}
- data ApiOptions = ApiOptions {}
- defaultApiOptions :: ApiOptions
- data Mutability
- data ApiPiece
- data HandlerSettings = HandlerSettings {
- contentTypes :: Type
- verb :: Type
- newtype ConstructorName = ConstructorName Name
- newtype EpReturnType = EpReturnType Type
- newtype GadtName = GadtName Name
- newtype GadtType = GadtType Type
- newtype UrlSegment = UrlSegment String
- newtype ConstructorArgs = ConstructorArgs [(String, Type)]
- newtype Runner = Runner Type
- data ServerInfo = ServerInfo {}
- data ServerGenState = ServerGenState {}
- newtype ServerGenM a = ServerGenM {}
- data Pmatch = Pmatch {}
- data ConstructorMatch = ConstructorMatch {}
- data SubActionMatch = SubActionMatch {
- constructorName :: Name
- parameters :: [Pmatch]
- subActionName :: Name
- subActionType :: Type
- data SubActionTypeMatch = SubActionTypeMatch
- data FinalConstructorTypeMatch = FinalConstructorTypeMatch {}
- data RequestTypeMatch = RequestTypeMatch {
- accessType :: Type
- contentTypes :: Type
- verb :: Type
Documentation
ApiSpec | |
|
Instances
Generic ApiSpec Source # | |
Show ApiSpec Source # | |
type Rep ApiSpec Source # | |
Defined in DomainDriven.Server.Types type Rep ApiSpec = D1 ('MetaData "ApiSpec" "DomainDriven.Server.Types" "domaindriven-0.5.0-DXvek89qD5M1xwQ4V40Syp" 'False) (C1 ('MetaCons "ApiSpec" 'PrefixI 'True) ((S1 ('MetaSel ('Just "gadtName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 GadtName) :*: S1 ('MetaSel ('Just "gadtType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 GadtType)) :*: (S1 ('MetaSel ('Just "allVarBindings") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 VarBindings) :*: (S1 ('MetaSel ('Just "endpoints") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ApiPiece]) :*: S1 ('MetaSel ('Just "options") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ApiOptions))))) |
data VarBindings Source #
Instances
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 Mutability Source #
Instances
Show Mutability Source # | |
Defined in DomainDriven.Server.Types showsPrec :: Int -> Mutability -> ShowS # show :: Mutability -> String # showList :: [Mutability] -> ShowS # | |
Eq Mutability Source # | |
Defined in DomainDriven.Server.Types (==) :: Mutability -> Mutability -> Bool # (/=) :: Mutability -> Mutability -> Bool # |
Endpoint ConstructorName ConstructorArgs VarBindings HandlerSettings Mutability EpReturnType | |
SubApi ConstructorName ConstructorArgs ApiSpec |
Instances
data HandlerSettings Source #
HandlerSettings | |
|
Instances
newtype ConstructorName Source #
Instances
Generic ConstructorName Source # | |
Defined in DomainDriven.Server.Types type Rep ConstructorName :: Type -> Type # from :: ConstructorName -> Rep ConstructorName x # to :: Rep ConstructorName x -> ConstructorName # | |
Show ConstructorName Source # | |
Defined in DomainDriven.Server.Types showsPrec :: Int -> ConstructorName -> ShowS # show :: ConstructorName -> String # showList :: [ConstructorName] -> ShowS # | |
Eq ConstructorName Source # | |
Defined in DomainDriven.Server.Types (==) :: ConstructorName -> ConstructorName -> Bool # (/=) :: ConstructorName -> ConstructorName -> Bool # | |
type Rep ConstructorName Source # | |
Defined in DomainDriven.Server.Types type Rep ConstructorName = D1 ('MetaData "ConstructorName" "DomainDriven.Server.Types" "domaindriven-0.5.0-DXvek89qD5M1xwQ4V40Syp" 'True) (C1 ('MetaCons "ConstructorName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name))) |
newtype EpReturnType Source #
Instances
Generic EpReturnType Source # | |
Defined in DomainDriven.Server.Types type Rep EpReturnType :: Type -> Type # from :: EpReturnType -> Rep EpReturnType x # to :: Rep EpReturnType x -> EpReturnType # | |
Show EpReturnType Source # | |
Defined in DomainDriven.Server.Types showsPrec :: Int -> EpReturnType -> ShowS # show :: EpReturnType -> String # showList :: [EpReturnType] -> ShowS # | |
Eq EpReturnType Source # | |
Defined in DomainDriven.Server.Types (==) :: EpReturnType -> EpReturnType -> Bool # (/=) :: EpReturnType -> EpReturnType -> Bool # | |
type Rep EpReturnType Source # | |
Defined in DomainDriven.Server.Types type Rep EpReturnType = D1 ('MetaData "EpReturnType" "DomainDriven.Server.Types" "domaindriven-0.5.0-DXvek89qD5M1xwQ4V40Syp" 'True) (C1 ('MetaCons "EpReturnType" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type))) |
newtype UrlSegment Source #
Instances
Generic UrlSegment Source # | |
Defined in DomainDriven.Server.Types type Rep UrlSegment :: Type -> Type # from :: UrlSegment -> Rep UrlSegment x # to :: Rep UrlSegment x -> UrlSegment # | |
Show UrlSegment Source # | |
Defined in DomainDriven.Server.Types showsPrec :: Int -> UrlSegment -> ShowS # show :: UrlSegment -> String # showList :: [UrlSegment] -> ShowS # | |
Eq UrlSegment Source # | |
Defined in DomainDriven.Server.Types (==) :: UrlSegment -> UrlSegment -> Bool # (/=) :: UrlSegment -> UrlSegment -> Bool # | |
type Rep UrlSegment Source # | |
Defined in DomainDriven.Server.Types type Rep UrlSegment = D1 ('MetaData "UrlSegment" "DomainDriven.Server.Types" "domaindriven-0.5.0-DXvek89qD5M1xwQ4V40Syp" 'True) (C1 ('MetaCons "UrlSegment" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))) |
newtype ConstructorArgs Source #
ConstructorArgs [(String, Type)] |
Instances
Generic ConstructorArgs Source # | |
Defined in DomainDriven.Server.Types type Rep ConstructorArgs :: Type -> Type # from :: ConstructorArgs -> Rep ConstructorArgs x # to :: Rep ConstructorArgs x -> ConstructorArgs # | |
Show ConstructorArgs Source # | |
Defined in DomainDriven.Server.Types showsPrec :: Int -> ConstructorArgs -> ShowS # show :: ConstructorArgs -> String # showList :: [ConstructorArgs] -> ShowS # | |
Eq ConstructorArgs Source # | |
Defined in DomainDriven.Server.Types (==) :: ConstructorArgs -> ConstructorArgs -> Bool # (/=) :: ConstructorArgs -> ConstructorArgs -> Bool # | |
type Rep ConstructorArgs Source # | |
Defined in DomainDriven.Server.Types type Rep ConstructorArgs = D1 ('MetaData "ConstructorArgs" "DomainDriven.Server.Types" "domaindriven-0.5.0-DXvek89qD5M1xwQ4V40Syp" 'True) (C1 ('MetaCons "ConstructorArgs" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(String, Type)]))) |
data ServerInfo Source #
Carries information regarding how the API looks at the place we're currently at.
ServerInfo | |
|
Instances
data ServerGenState Source #
Instances
newtype ServerGenM a Source #
Instances
Instances
Generic Pmatch Source # | |
Show Pmatch Source # | |
type Rep Pmatch Source # | |
Defined in DomainDriven.Server.Types type Rep Pmatch = D1 ('MetaData "Pmatch" "DomainDriven.Server.Types" "domaindriven-0.5.0-DXvek89qD5M1xwQ4V40Syp" 'False) (C1 ('MetaCons "Pmatch" 'PrefixI 'True) (S1 ('MetaSel ('Just "paramPart") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: (S1 ('MetaSel ('Just "paramName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Just "paramType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type)))) |
data ConstructorMatch Source #
ConstructorMatch | |
|
Instances
data SubActionMatch Source #
SubActionMatch | |
|
Instances
data SubActionTypeMatch Source #
Instances
Generic SubActionTypeMatch Source # | |
Defined in DomainDriven.Server.Types type Rep SubActionTypeMatch :: Type -> Type # from :: SubActionTypeMatch -> Rep SubActionTypeMatch x # to :: Rep SubActionTypeMatch x -> SubActionTypeMatch # | |
Show SubActionTypeMatch Source # | |
Defined in DomainDriven.Server.Types showsPrec :: Int -> SubActionTypeMatch -> ShowS # show :: SubActionTypeMatch -> String # showList :: [SubActionTypeMatch] -> ShowS # | |
type Rep SubActionTypeMatch Source # | |
data FinalConstructorTypeMatch Source #
Instances
Generic FinalConstructorTypeMatch Source # | |
Defined in DomainDriven.Server.Types type Rep FinalConstructorTypeMatch :: Type -> Type # | |
Show FinalConstructorTypeMatch Source # | |
Defined in DomainDriven.Server.Types showsPrec :: Int -> FinalConstructorTypeMatch -> ShowS # show :: FinalConstructorTypeMatch -> String # showList :: [FinalConstructorTypeMatch] -> ShowS # | |
type Rep FinalConstructorTypeMatch Source # | |
Defined in DomainDriven.Server.Types type Rep FinalConstructorTypeMatch = D1 ('MetaData "FinalConstructorTypeMatch" "DomainDriven.Server.Types" "domaindriven-0.5.0-DXvek89qD5M1xwQ4V40Syp" 'False) (C1 ('MetaCons "FinalConstructorTypeMatch" 'PrefixI 'True) (S1 ('MetaSel ('Just "requestType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RequestTypeMatch) :*: S1 ('MetaSel ('Just "returnType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type))) |
data RequestTypeMatch Source #
RequestTypeMatch | |
|
Instances
Generic RequestTypeMatch Source # | |
Defined in DomainDriven.Server.Types type Rep RequestTypeMatch :: Type -> Type # from :: RequestTypeMatch -> Rep RequestTypeMatch x # to :: Rep RequestTypeMatch x -> RequestTypeMatch # | |
Show RequestTypeMatch Source # | |
Defined in DomainDriven.Server.Types showsPrec :: Int -> RequestTypeMatch -> ShowS # show :: RequestTypeMatch -> String # showList :: [RequestTypeMatch] -> ShowS # | |
type Rep RequestTypeMatch Source # | |
Defined in DomainDriven.Server.Types type Rep RequestTypeMatch = D1 ('MetaData "RequestTypeMatch" "DomainDriven.Server.Types" "domaindriven-0.5.0-DXvek89qD5M1xwQ4V40Syp" 'False) (C1 ('MetaCons "RequestTypeMatch" 'PrefixI 'True) (S1 ('MetaSel ('Just "accessType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type) :*: (S1 ('MetaSel ('Just "contentTypes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type) :*: S1 ('MetaSel ('Just "verb") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type)))) |