servant-0.18.3: A family of combinators for defining webservices APIs
Safe HaskellSafe-Inferred
LanguageHaskell2010

Servant.API.Verbs

Synopsis

Documentation

class ReflectMethod a where Source #

Instances

Instances details
ReflectMethod 'PATCH Source # 
Instance details

Defined in Servant.API.Verbs

ReflectMethod 'OPTIONS Source # 
Instance details

Defined in Servant.API.Verbs

ReflectMethod 'CONNECT Source # 
Instance details

Defined in Servant.API.Verbs

ReflectMethod 'TRACE Source # 
Instance details

Defined in Servant.API.Verbs

ReflectMethod 'DELETE Source # 
Instance details

Defined in Servant.API.Verbs

ReflectMethod 'PUT Source # 
Instance details

Defined in Servant.API.Verbs

ReflectMethod 'HEAD Source # 
Instance details

Defined in Servant.API.Verbs

ReflectMethod 'POST Source # 
Instance details

Defined in Servant.API.Verbs

ReflectMethod 'GET Source # 
Instance details

Defined in Servant.API.Verbs

type GetPartialContent = Verb 'GET 206 Source #

GET with 206 status code.

type PutResetContent = Verb 'PUT 205 Source #

PUT with 205 status code.

type PatchResetContent = Verb 'PATCH 205 Source #

PATCH with 205 status code.

type DeleteResetContent = Verb 'DELETE 205 Source #

DELETE with 205 status code.

type PostResetContent = Verb 'POST 205 Source #

POST with 205 status code.

type GetResetContent = Verb 'GET 205 Source #

GET with 205 status code.

type PutNoContent = NoContentVerb 'PUT Source #

PUT with 204 status code.

type PatchNoContent = NoContentVerb 'PATCH Source #

PATCH with 204 status code.

type DeleteNoContent = NoContentVerb 'DELETE Source #

DELETE with 204 status code.

type PostNoContent = NoContentVerb 'POST Source #

POST with 204 status code.

type GetNoContent = NoContentVerb 'GET Source #

GET with 204 status code.

type PutNonAuthoritative = Verb 'PUT 203 Source #

PUT with 203 status code.

type PatchNonAuthoritative = Verb 'PATCH 203 Source #

PATCH with 203 status code.

type DeleteNonAuthoritative = Verb 'DELETE 203 Source #

DELETE with 203 status code.

type PostNonAuthoritative = Verb 'POST 203 Source #

POST with 203 status code.

type GetNonAuthoritative = Verb 'GET 203 Source #

GET with 203 status code.

type PutAccepted = Verb 'PUT 202 Source #

PUT with 202 status code.

type PatchAccepted = Verb 'PATCH 202 Source #

PATCH with 202 status code.

type DeleteAccepted = Verb 'DELETE 202 Source #

DELETE with 202 status code.

type PostAccepted = Verb 'POST 202 Source #

POST with 202 status code.

type GetAccepted = Verb 'GET 202 Source #

GET with 202 status code.

type PutCreated = Verb 'PUT 201 Source #

PUT with 201 status code.

type PostCreated = Verb 'POST 201 Source #

POST with 201 status code.

type Patch = Verb 'PATCH 200 Source #

PATCH with 200 status code.

type Delete = Verb 'DELETE 200 Source #

DELETE with 200 status code.

type Put = Verb 'PUT 200 Source #

PUT with 200 status code.

type Post = Verb 'POST 200 Source #

POST with 200 status code.

type Get = Verb 'GET 200 Source #

GET with 200 status code.

data NoContentVerb (method :: k1) Source #

NoContentVerb is a specific type to represent NoContent responses. It does not require either a list of content types (because there's no content) or a status code (because it should always be 204).

Instances

Instances details
HasLink (NoContentVerb m :: Type) Source # 
Instance details

Defined in Servant.Links

Associated Types

type MkLink (NoContentVerb m) a Source #

Methods

toLink :: (Link -> a) -> Proxy (NoContentVerb m) -> Link -> MkLink (NoContentVerb m) a Source #

Generic (NoContentVerb method) Source # 
Instance details

Defined in Servant.API.Verbs

Associated Types

type Rep (NoContentVerb method) :: Type -> Type #

Methods

from :: NoContentVerb method -> Rep (NoContentVerb method) x #

to :: Rep (NoContentVerb method) x -> NoContentVerb method #

type MkLink (NoContentVerb m :: Type) r Source # 
Instance details

Defined in Servant.Links

type MkLink (NoContentVerb m :: Type) r = r
type Rep (NoContentVerb method) Source # 
Instance details

Defined in Servant.API.Verbs

type Rep (NoContentVerb method) = D1 ('MetaData "NoContentVerb" "Servant.API.Verbs" "servant-0.18.3-GUJwwHCYukAE9mgDRQwnap" 'False) (V1 :: Type -> Type)

data Verb (method :: k1) (statusCode :: Nat) (contentTypes :: [*]) (a :: *) Source #

Verb is a general type for representing HTTP verbs (a.k.a. methods). For convenience, type synonyms for each verb with a 200 response code are provided, but you are free to define your own:

>>> type Post204 contentTypes a = Verb 'POST 204 contentTypes a

Instances

Instances details
HasLink (Verb m s ct a :: Type) Source # 
Instance details

Defined in Servant.Links

Associated Types

type MkLink (Verb m s ct a) a Source #

Methods

toLink :: (Link -> a0) -> Proxy (Verb m s ct a) -> Link -> MkLink (Verb m s ct a) a0 Source #

Generic (Verb method statusCode contentTypes a) Source # 
Instance details

Defined in Servant.API.Verbs

Associated Types

type Rep (Verb method statusCode contentTypes a) :: Type -> Type #

Methods

from :: Verb method statusCode contentTypes a -> Rep (Verb method statusCode contentTypes a) x #

to :: Rep (Verb method statusCode contentTypes a) x -> Verb method statusCode contentTypes a #

AtLeastOneFragment (Verb m s ct typ) Source #

If fragment appeared in API endpoint twice, compile-time error would be raised.

>>> -- type FailAPI = Fragment Bool :> Fragment Int :> Get '[JSON] NoContent
>>> instance AtLeastOneFragment FailAPI
...
...Only one Fragment allowed per endpoint in api...
...
...In the instance declaration for...
Instance details

Defined in Servant.API.TypeLevel

type MkLink (Verb m s ct a :: Type) r Source # 
Instance details

Defined in Servant.Links

type MkLink (Verb m s ct a :: Type) r = r
type Rep (Verb method statusCode contentTypes a) Source # 
Instance details

Defined in Servant.API.Verbs

type Rep (Verb method statusCode contentTypes a) = D1 ('MetaData "Verb" "Servant.API.Verbs" "servant-0.18.3-GUJwwHCYukAE9mgDRQwnap" 'False) (V1 :: Type -> Type)

data StdMethod #

HTTP standard method (as defined by RFC 2616, and PATCH which is defined by RFC 5789).

Constructors

GET 
POST 
HEAD 
PUT 
DELETE 
TRACE 
CONNECT 
OPTIONS 
PATCH 

Instances

Instances details
Bounded StdMethod 
Instance details

Defined in Network.HTTP.Types.Method

Enum StdMethod 
Instance details

Defined in Network.HTTP.Types.Method

Eq StdMethod 
Instance details

Defined in Network.HTTP.Types.Method

Ord StdMethod 
Instance details

Defined in Network.HTTP.Types.Method

Read StdMethod 
Instance details

Defined in Network.HTTP.Types.Method

Show StdMethod 
Instance details

Defined in Network.HTTP.Types.Method

Ix StdMethod 
Instance details

Defined in Network.HTTP.Types.Method

ReflectMethod 'PATCH Source # 
Instance details

Defined in Servant.API.Verbs

ReflectMethod 'OPTIONS Source # 
Instance details

Defined in Servant.API.Verbs

ReflectMethod 'CONNECT Source # 
Instance details

Defined in Servant.API.Verbs

ReflectMethod 'TRACE Source # 
Instance details

Defined in Servant.API.Verbs

ReflectMethod 'DELETE Source # 
Instance details

Defined in Servant.API.Verbs

ReflectMethod 'PUT Source # 
Instance details

Defined in Servant.API.Verbs

ReflectMethod 'HEAD Source # 
Instance details

Defined in Servant.API.Verbs

ReflectMethod 'POST Source # 
Instance details

Defined in Servant.API.Verbs

ReflectMethod 'GET Source # 
Instance details

Defined in Servant.API.Verbs