domaindriven-0.5.0: Batteries included event sourcing and CQRS
Safe HaskellSafe-Inferred
LanguageHaskell2010

DomainDriven.Server.Config

Synopsis

Documentation

class HasApiOptions (action :: Action) where Source #

Minimal complete definition

Nothing

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.

Constructors

ServerConfig 

Fields

Instances

Instances details
Generic ServerConfig Source # 
Instance details

Defined in DomainDriven.Server.Config

Associated Types

type Rep ServerConfig :: Type -> Type #

Show ServerConfig Source # 
Instance details

Defined in DomainDriven.Server.Config

type Rep ServerConfig Source # 
Instance details

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))))

mkServerConfig :: String -> Q [Dec] Source #

Generate a server configuration and give it the specified name

getApiOptionsMap :: Q Exp Source #

Generates `Map String ApiOptions` Containing the ApiOptions of all types with an ApiOpts instance

data Name #

An abstract type representing names in the syntax tree.

Names can be constructed in several ways, which come with different name-capture guarantees (see Language.Haskell.TH.Syntax for an explanation of name capture):

  • the built-in syntax 'f and ''T can be used to construct names, The expression 'f gives a Name which refers to the value f currently in scope, and ''T gives a Name which refers to the type T currently in scope. These names can never be captured.
  • lookupValueName and lookupTypeName are similar to 'f and ''T respectively, but the Names are looked up at the point where the current splice is being run. These names can never be captured.
  • newName monadically generates a new name, which can never be captured.
  • mkName generates a capturable name.

Names constructed using newName and mkName may be used in bindings (such as let x = ... or x -> ...), but names constructed using lookupValueName, lookupTypeName, 'f, ''T may not.

Instances

Instances details
Data Name 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Name -> c Name #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Name #

toConstr :: Name -> Constr #

dataTypeOf :: Name -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Name) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Name) #

gmapT :: (forall b. Data b => b -> b) -> Name -> Name #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Name -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Name -> r #

gmapQ :: (forall d. Data d => d -> u) -> Name -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Name -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Name -> m Name #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Name -> m Name #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Name -> m Name #

Generic Name 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Name :: Type -> Type #

Methods

from :: Name -> Rep Name x #

to :: Rep Name x -> Name #

Show Name 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

showsPrec :: Int -> Name -> ShowS #

show :: Name -> String #

showList :: [Name] -> ShowS #

Eq Name 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

(==) :: Name -> Name -> Bool #

(/=) :: Name -> Name -> Bool #

Ord Name 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

compare :: Name -> Name -> Ordering #

(<) :: Name -> Name -> Bool #

(<=) :: Name -> Name -> Bool #

(>) :: Name -> Name -> Bool #

(>=) :: Name -> Name -> Bool #

max :: Name -> Name -> Name #

min :: Name -> Name -> Name #

Ppr Name 
Instance details

Defined in Language.Haskell.TH.Ppr

Methods

ppr :: Name -> Doc #

ppr_list :: [Name] -> Doc #

type Rep Name 
Instance details

Defined in Language.Haskell.TH.Syntax