| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
Servant.API.Verbs
Synopsis
- class ReflectMethod a where
- reflectMethod :: Proxy a -> Method
 
 - type GetPartialContent = Verb 'GET 206
 - type PutResetContent = Verb 'PUT 205
 - type PatchResetContent = Verb 'PATCH 205
 - type DeleteResetContent = Verb 'DELETE 205
 - type PostResetContent = Verb 'POST 205
 - type GetResetContent = Verb 'GET 205
 - type PutNoContent = NoContentVerb 'PUT
 - type PatchNoContent = NoContentVerb 'PATCH
 - type DeleteNoContent = NoContentVerb 'DELETE
 - type PostNoContent = NoContentVerb 'POST
 - type GetNoContent = NoContentVerb 'GET
 - type PutNonAuthoritative = Verb 'PUT 203
 - type PatchNonAuthoritative = Verb 'PATCH 203
 - type DeleteNonAuthoritative = Verb 'DELETE 203
 - type PostNonAuthoritative = Verb 'POST 203
 - type GetNonAuthoritative = Verb 'GET 203
 - type PutAccepted = Verb 'PUT 202
 - type PatchAccepted = Verb 'PATCH 202
 - type DeleteAccepted = Verb 'DELETE 202
 - type PostAccepted = Verb 'POST 202
 - type GetAccepted = Verb 'GET 202
 - type PutCreated = Verb 'PUT 201
 - type PostCreated = Verb 'POST 201
 - type Patch = Verb 'PATCH 200
 - type Delete = Verb 'DELETE 200
 - type Put = Verb 'PUT 200
 - type Post = Verb 'POST 200
 - type Get = Verb 'GET 200
 - data NoContentVerb (method :: k1)
 - data Verb (method :: k1) (statusCode :: Nat) (contentTypes :: [*]) (a :: *)
 - data StdMethod
 
Documentation
class ReflectMethod a where Source #
Methods
reflectMethod :: Proxy a -> Method Source #
Instances
| ReflectMethod 'PATCH Source # | |
Defined in Servant.API.Verbs  | |
| ReflectMethod 'OPTIONS Source # | |
Defined in Servant.API.Verbs  | |
| ReflectMethod 'CONNECT Source # | |
Defined in Servant.API.Verbs  | |
| ReflectMethod 'TRACE Source # | |
Defined in Servant.API.Verbs  | |
| ReflectMethod 'DELETE Source # | |
Defined in Servant.API.Verbs  | |
| ReflectMethod 'PUT Source # | |
Defined in Servant.API.Verbs  | |
| ReflectMethod 'HEAD Source # | |
Defined in Servant.API.Verbs  | |
| ReflectMethod 'POST Source # | |
Defined in Servant.API.Verbs  | |
| ReflectMethod 'GET Source # | |
Defined in Servant.API.Verbs  | |
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.
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
| HasLink (NoContentVerb m :: Type) Source # | |
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 # | |
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 # | |
Defined in Servant.Links  | |
| type Rep (NoContentVerb method) Source # | |
Defined in Servant.API.Verbs  | |
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
| HasLink (Verb m s ct a :: Type) Source # | |
| Generic (Verb method statusCode contentTypes a) Source # | |
Defined in Servant.API.Verbs  | |
| AtLeastOneFragment (Verb m s ct typ) Source # | If fragment appeared in API endpoint twice, compile-time error would be raised. 
  | 
Defined in Servant.API.TypeLevel  | |
| type MkLink (Verb m s ct a :: Type) r Source # | |
Defined in Servant.Links  | |
| type Rep (Verb method statusCode contentTypes a) Source # | |
HTTP standard method (as defined by RFC 2616, and PATCH which is defined by RFC 5789).