servant-util-0.2: Servant servers utilities.
Safe HaskellNone
LanguageHaskell2010

Servant.Util.Combinators.Tag

Synopsis

Documentation

data Tag (name :: Symbol) Source #

Attaches a tag to swagger documentation. Server implementation remains intact.

Instances

Instances details
HasClient m subApi => HasClient m (Tag name :> subApi) Source # 
Instance details

Defined in Servant.Util.Combinators.Tag

Associated Types

type Client m (Tag name :> subApi) #

Methods

clientWithRoute :: Proxy m -> Proxy (Tag name :> subApi) -> Request -> Client m (Tag name :> subApi) #

hoistClientMonad :: Proxy m -> Proxy (Tag name :> subApi) -> (forall x. mon x -> mon' x) -> Client mon (Tag name :> subApi) -> Client mon' (Tag name :> subApi) #

HasLoggingServer config lcontext subApi ctx => HasLoggingServer (config :: Type) lcontext (Tag name :> subApi :: Type) ctx Source # 
Instance details

Defined in Servant.Util.Combinators.Tag

Methods

routeWithLog :: Proxy (LoggingApiRec config lcontext (Tag name :> subApi)) -> Context ctx -> Delayed env (Server (LoggingApiRec config lcontext (Tag name :> subApi))) -> Router env Source #

(HasSwagger subApi, KnownSymbol name) => HasSwagger (Tag name :> subApi :: Type) Source # 
Instance details

Defined in Servant.Util.Combinators.Tag

Methods

toSwagger :: Proxy (Tag name :> subApi) -> Swagger #

HasServer subApi ctx => HasServer (Tag name :> subApi :: Type) ctx Source # 
Instance details

Defined in Servant.Util.Combinators.Tag

Associated Types

type ServerT (Tag name :> subApi) m #

Methods

route :: Proxy (Tag name :> subApi) -> Context ctx -> Delayed env (Server (Tag name :> subApi)) -> Router env #

hoistServerWithContext :: Proxy (Tag name :> subApi) -> Proxy ctx -> (forall x. m x -> n x) -> ServerT (Tag name :> subApi) m -> ServerT (Tag name :> subApi) n #

type Client m (Tag name :> subApi) Source # 
Instance details

Defined in Servant.Util.Combinators.Tag

type Client m (Tag name :> subApi) = Client m subApi
type ServerT (Tag name :> subApi :: Type) m Source # 
Instance details

Defined in Servant.Util.Combinators.Tag

type ServerT (Tag name :> subApi :: Type) m = ServerT subApi m

data TagDescriptions (verify :: TagsVerification) (mapping :: [TyNamedParam Symbol]) Source #

Attaches descriptions to tags according to the given name -> description mapping. Unused elements of mapping will cause a compile error; tags which have no mapping declared are not allowed as well.

Instances

Instances details
HasClient m subApi => HasClient m (TagDescriptions ver mapping :> subApi) Source # 
Instance details

Defined in Servant.Util.Combinators.Tag

Associated Types

type Client m (TagDescriptions ver mapping :> subApi) #

Methods

clientWithRoute :: Proxy m -> Proxy (TagDescriptions ver mapping :> subApi) -> Request -> Client m (TagDescriptions ver mapping :> subApi) #

hoistClientMonad :: Proxy m -> Proxy (TagDescriptions ver mapping :> subApi) -> (forall x. mon x -> mon' x) -> Client mon (TagDescriptions ver mapping :> subApi) -> Client mon' (TagDescriptions ver mapping :> subApi) #

HasLoggingServer config context subApi ctx => HasLoggingServer (config :: Type) context (TagDescriptions ver mapping :> subApi :: Type) ctx Source # 
Instance details

Defined in Servant.Util.Combinators.Tag

Methods

routeWithLog :: Proxy (LoggingApiRec config context (TagDescriptions ver mapping :> subApi)) -> Context ctx -> Delayed env (Server (LoggingApiRec config context (TagDescriptions ver mapping :> subApi))) -> Router env Source #

(HasSwagger api, ReifyTagsFromMapping mapping, missingMapping ~ (AllApiTags api // TyNamedParamsNames mapping), If (missingMapping == ('[] :: [Symbol])) () (TypeError ('Text "Following tags have no mapping specified in TagDescriptions: " :<>: 'ShowType missingMapping) :: Constraint), extraMapping ~ (TyNamedParamsNames mapping // AllApiTags api), If (extraMapping == ('[] :: [Symbol])) () (TypeError ('Text "Mappings for the following names specified in TagDescriptions are unused: " :<>: 'ShowType extraMapping) :: Constraint)) => HasSwagger (TagDescriptions 'VerifyTags mapping :> api :: Type) Source # 
Instance details

Defined in Servant.Util.Combinators.Tag

Methods

toSwagger :: Proxy (TagDescriptions 'VerifyTags mapping :> api) -> Swagger #

(HasSwagger api, ReifyTagsFromMapping mapping) => HasSwagger (TagDescriptions 'NoVerifyTags mapping :> api :: Type) Source # 
Instance details

Defined in Servant.Util.Combinators.Tag

Methods

toSwagger :: Proxy (TagDescriptions 'NoVerifyTags mapping :> api) -> Swagger #

HasServer subApi ctx => HasServer (TagDescriptions ver mapping :> subApi :: Type) ctx Source # 
Instance details

Defined in Servant.Util.Combinators.Tag

Associated Types

type ServerT (TagDescriptions ver mapping :> subApi) m #

Methods

route :: Proxy (TagDescriptions ver mapping :> subApi) -> Context ctx -> Delayed env (Server (TagDescriptions ver mapping :> subApi)) -> Router env #

hoistServerWithContext :: Proxy (TagDescriptions ver mapping :> subApi) -> Proxy ctx -> (forall x. m x -> n x) -> ServerT (TagDescriptions ver mapping :> subApi) m -> ServerT (TagDescriptions ver mapping :> subApi) n #

type Client m (TagDescriptions ver mapping :> subApi) Source # 
Instance details

Defined in Servant.Util.Combinators.Tag

type Client m (TagDescriptions ver mapping :> subApi) = Client m subApi
type ServerT (TagDescriptions ver mapping :> subApi :: Type) m Source # 
Instance details

Defined in Servant.Util.Combinators.Tag

type ServerT (TagDescriptions ver mapping :> subApi :: Type) m = ServerT subApi m

data TagsVerification Source #

Whether to enable some type-level checks for Tags and TagsDescriptions correspondence.

Constructors

VerifyTags

Ensure that mappings are specified exactly for those tags which appear in API. This may slow down compilation dramatically starting from ~15 tags.

NoVerifyTags

Do not check anything.