Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- mkServer :: ServerConfig -> Name -> Q [Dec]
- getApiOptions :: ServerConfig -> GadtName -> Q ApiOptions
- getActionDec :: GadtName -> Q (Dec, VarBindings)
- getSubActionDec :: VarBindings -> SubActionMatch -> Q (Dec, VarBindings)
- replaceVarT :: Map Name Name -> Type -> Either String Type
- guardMethodVar :: TyVarBndr flag -> Q ()
- getMutabilityOf :: Type -> Q Mutability
- guardReturnVar :: Show flag => TyVarBndr flag -> Q ()
- getConstructors :: Dec -> Q [Con]
- toTyVarBndr :: VarBindings -> [TyVarBndr ()]
- mkVarBindings :: Show flag => [TyVarBndr flag] -> Either String VarBindings
- matchNormalConstructor :: Con -> Either String ConstructorMatch
- matchSubActionConstructor :: Con -> Either String SubActionMatch
- matchFinalConstructorType :: Type -> Either String FinalConstructorTypeMatch
- matchRequestType :: Type -> Either String RequestTypeMatch
- matchP :: Type -> Either String Pmatch
- mkApiPiece :: ServerConfig -> VarBindings -> Con -> Q ApiPiece
- mkServerSpec :: ServerConfig -> GadtName -> Q ApiSpec
- gadtToAction :: GadtType -> Either String Type
- mkSubServerSpec :: ServerConfig -> VarBindings -> SubActionMatch -> Q ApiSpec
- askApiNameAndParams :: ApiSpec -> ServerGenM (Name, [TyVarBndr ()])
- apiPieceTyVars :: ApiPiece -> [TyVarBndr ()]
- apiSpecTyVars :: ApiSpec -> [TyVarBndr ()]
- mkApiTypeDecs :: ApiSpec -> ServerGenM [Dec]
- applyTyVars :: Type -> [TyVarBndr ()] -> Type
- mkEndpointApiType :: ApiPiece -> ServerGenM (Type, [TyVarBndr ()])
- mkHandlerTypeDec :: ApiPiece -> ServerGenM [Dec]
- guardUniqueParamName :: String -> ServerGenM ()
- mkQueryParams :: ConstructorArgs -> ServerGenM [QueryParamType]
- type QueryParamType = Type
- updateConstructorTypes :: (Type -> Type) -> Con -> Con
- mkVerb :: HandlerSettings -> Type -> Type
- mkServerDec :: ApiSpec -> ServerGenM [Dec]
- getUsedTyVars :: forall flag. [TyVarBndr flag] -> Type -> [TyVarBndr flag]
- getUsedTyVarNames :: Type -> [Name]
- withForall :: [TyVarBndr ()] -> Type -> Type
- actionRunner :: Type -> Type
- runnerMonadName :: Name
- mkNamedFieldsType :: ConstructorName -> ConstructorArgs -> ServerGenM (Maybe Type)
- mkQueryHandlerSignature :: GadtType -> ConstructorArgs -> EpReturnType -> Type
- mkCmdHandlerSignature :: GadtType -> ConstructorName -> ConstructorArgs -> EpReturnType -> ServerGenM Type
- mkFunction :: [Type] -> Type
- sortAndExcludeBindings :: [TyVarBndr Specificity] -> Type -> Either String [TyVarBndr Specificity]
- varNameOrder :: Type -> Either String [Name]
- gadtTypeParams :: GadtType -> Either String [TyVarBndr ()]
- mkApiPieceHandler :: GadtType -> ApiPiece -> ServerGenM [Dec]
- mkServerFromSpec :: ApiSpec -> ServerGenM [Dec]
- mkReturnType :: EpReturnType -> Type
- prependServerEndpointName :: UrlSegment -> Type -> Q Type
- mkReqBody :: HandlerSettings -> ConstructorName -> ConstructorArgs -> ServerGenM (Maybe Type)
Documentation
config ''MyAction)
getApiOptions :: ServerConfig -> GadtName -> Q ApiOptions Source #
getActionDec :: GadtName -> Q (Dec, VarBindings) Source #
getSubActionDec :: VarBindings -> SubActionMatch -> Q (Dec, VarBindings) Source #
guardMethodVar :: TyVarBndr flag -> Q () Source #
getMutabilityOf :: Type -> Q Mutability Source #
toTyVarBndr :: VarBindings -> [TyVarBndr ()] Source #
mkVarBindings :: Show flag => [TyVarBndr flag] -> Either String VarBindings Source #
matchP :: Type -> Either String Pmatch Source #
Tries to match a Type to a more easily readable Pmatch.
Successful match means the type is representing the type family P
mkApiPiece :: ServerConfig -> VarBindings -> Con -> Q ApiPiece Source #
mkServerSpec :: ServerConfig -> GadtName -> Q ApiSpec Source #
Create a ApiSpec from a GADT The GADT must have one parameter representing the return type
mkSubServerSpec :: ServerConfig -> VarBindings -> SubActionMatch -> Q ApiSpec Source #
askApiNameAndParams :: ApiSpec -> ServerGenM (Name, [TyVarBndr ()]) Source #
Name and type variables used by API
apiPieceTyVars :: ApiPiece -> [TyVarBndr ()] Source #
apiSpecTyVars :: ApiSpec -> [TyVarBndr ()] Source #
mkApiTypeDecs :: ApiSpec -> ServerGenM [Dec] Source #
mkEndpointApiType :: ApiPiece -> ServerGenM (Type, [TyVarBndr ()]) Source #
Create endpoint types to be referenced in the API * For Endpoint this is just a reference to the handler type * For SubApi we apply the path parameters before referencing the SubApi
mkHandlerTypeDec :: ApiPiece -> ServerGenM [Dec] Source #
Defines the servant types for the endpoints For SubApi it will trigger the full creating of the sub server with types and all
Result will be something like: ``` type Customer_CreateEndpoint = Create :> ReqBody '[JSON] (NamedField1 Customer_Create Name Email) :> Post '[JSON] CustomerKey
guardUniqueParamName :: String -> ServerGenM () Source #
type QueryParamType = Type Source #
mkServerDec :: ApiSpec -> ServerGenM [Dec] Source #
Declare then handlers for the API
getUsedTyVars :: forall flag. [TyVarBndr flag] -> Type -> [TyVarBndr flag] Source #
Get the subset of type varaibes used ty a type, in the roder they're applied Used to avoid rendundant type variables in the forall statement of sub-servers
getUsedTyVarNames :: Type -> [Name] Source #
Get the type variables (VarT) used in a type, returned in the order they're referenced
actionRunner :: Type -> Type Source #
mkQueryHandlerSignature :: GadtType -> ConstructorArgs -> EpReturnType -> Type Source #
mkCmdHandlerSignature :: GadtType -> ConstructorName -> ConstructorArgs -> EpReturnType -> ServerGenM Type Source #
Makes command handler, e.g. counterCmd_AddToCounterHandler :: ActionRunner m CounterCmd -> NamedFields1 CounterCmd_AddToCounter Int -> m Int
mkFunction :: [Type] -> Type Source #
sortAndExcludeBindings :: [TyVarBndr Specificity] -> Type -> Either String [TyVarBndr Specificity] Source #
mkApiPieceHandler :: GadtType -> ApiPiece -> ServerGenM [Dec] Source #
Define the servant handler for an enpoint or referens the subapi with path parameters applied
mkServerFromSpec :: ApiSpec -> ServerGenM [Dec] Source #
mkReturnType :: EpReturnType -> Type Source #
Handles the special case of ()
being transformed into NoContent
prependServerEndpointName :: UrlSegment -> Type -> Q Type Source #
mkReqBody :: HandlerSettings -> ConstructorName -> ConstructorArgs -> ServerGenM (Maybe Type) Source #