{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE PolyKinds #-}
module Servant.API.Verbs
( module Servant.API.Verbs
, StdMethod(GET, POST, HEAD, PUT, DELETE, TRACE, CONNECT, OPTIONS, PATCH)
) where
import Data.Proxy
(Proxy)
import Data.Typeable
(Typeable)
import GHC.Generics
(Generic)
import GHC.TypeLits
(Nat)
import Network.HTTP.Types.Method
(Method, StdMethod (..), methodConnect, methodDelete,
methodGet, methodHead, methodOptions, methodPatch, methodPost,
methodPut, methodTrace)
data Verb (method :: k1) (statusCode :: Nat) (contentTypes :: [*]) (a :: *)
deriving (Typeable, (forall x.
Verb method statusCode contentTypes a
-> Rep (Verb method statusCode contentTypes a) x)
-> (forall x.
Rep (Verb method statusCode contentTypes a) x
-> Verb method statusCode contentTypes a)
-> Generic (Verb method statusCode contentTypes a)
forall x.
Rep (Verb method statusCode contentTypes a) x
-> Verb method statusCode contentTypes a
forall x.
Verb method statusCode contentTypes a
-> Rep (Verb method statusCode contentTypes a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall k1 (method :: k1) (statusCode :: Nat) (contentTypes :: [*])
a x.
Rep (Verb method statusCode contentTypes a) x
-> Verb method statusCode contentTypes a
forall k1 (method :: k1) (statusCode :: Nat) (contentTypes :: [*])
a x.
Verb method statusCode contentTypes a
-> Rep (Verb method statusCode contentTypes a) x
$cto :: forall k1 (method :: k1) (statusCode :: Nat) (contentTypes :: [*])
a x.
Rep (Verb method statusCode contentTypes a) x
-> Verb method statusCode contentTypes a
$cfrom :: forall k1 (method :: k1) (statusCode :: Nat) (contentTypes :: [*])
a x.
Verb method statusCode contentTypes a
-> Rep (Verb method statusCode contentTypes a) x
Generic)
data NoContentVerb (method :: k1)
deriving (Typeable, (forall x. NoContentVerb method -> Rep (NoContentVerb method) x)
-> (forall x. Rep (NoContentVerb method) x -> NoContentVerb method)
-> Generic (NoContentVerb method)
forall x. Rep (NoContentVerb method) x -> NoContentVerb method
forall x. NoContentVerb method -> Rep (NoContentVerb method) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall k1 (method :: k1) x.
Rep (NoContentVerb method) x -> NoContentVerb method
forall k1 (method :: k1) x.
NoContentVerb method -> Rep (NoContentVerb method) x
$cto :: forall k1 (method :: k1) x.
Rep (NoContentVerb method) x -> NoContentVerb method
$cfrom :: forall k1 (method :: k1) x.
NoContentVerb method -> Rep (NoContentVerb method) x
Generic)
type Get = Verb 'GET 200
type Post = Verb 'POST 200
type Put = Verb 'PUT 200
type Delete = Verb 'DELETE 200
type Patch = Verb 'PATCH 200
type PostCreated = Verb 'POST 201
type PutCreated = Verb 'PUT 201
type GetAccepted = Verb 'GET 202
type PostAccepted = Verb 'POST 202
type DeleteAccepted = Verb 'DELETE 202
type PatchAccepted = Verb 'PATCH 202
type PutAccepted = Verb 'PUT 202
type GetNonAuthoritative = Verb 'GET 203
type PostNonAuthoritative = Verb 'POST 203
type DeleteNonAuthoritative = Verb 'DELETE 203
type PatchNonAuthoritative = Verb 'PATCH 203
type PutNonAuthoritative = Verb 'PUT 203
type GetNoContent = NoContentVerb 'GET
type PostNoContent = NoContentVerb 'POST
type DeleteNoContent = NoContentVerb 'DELETE
type PatchNoContent = NoContentVerb 'PATCH
type PutNoContent = NoContentVerb 'PUT
type GetResetContent = Verb 'GET 205
type PostResetContent = Verb 'POST 205
type DeleteResetContent = Verb 'DELETE 205
type PatchResetContent = Verb 'PATCH 205
type PutResetContent = Verb 'PUT 205
type GetPartialContent = Verb 'GET 206
class ReflectMethod a where
reflectMethod :: Proxy a -> Method
instance ReflectMethod 'GET where
reflectMethod :: Proxy 'GET -> Method
reflectMethod Proxy 'GET
_ = Method
methodGet
instance ReflectMethod 'POST where
reflectMethod :: Proxy 'POST -> Method
reflectMethod Proxy 'POST
_ = Method
methodPost
instance ReflectMethod 'PUT where
reflectMethod :: Proxy 'PUT -> Method
reflectMethod Proxy 'PUT
_ = Method
methodPut
instance ReflectMethod 'DELETE where
reflectMethod :: Proxy 'DELETE -> Method
reflectMethod Proxy 'DELETE
_ = Method
methodDelete
instance ReflectMethod 'PATCH where
reflectMethod :: Proxy 'PATCH -> Method
reflectMethod Proxy 'PATCH
_ = Method
methodPatch
instance ReflectMethod 'HEAD where
reflectMethod :: Proxy 'HEAD -> Method
reflectMethod Proxy 'HEAD
_ = Method
methodHead
instance ReflectMethod 'OPTIONS where
reflectMethod :: Proxy 'OPTIONS -> Method
reflectMethod Proxy 'OPTIONS
_ = Method
methodOptions
instance ReflectMethod 'TRACE where
reflectMethod :: Proxy 'TRACE -> Method
reflectMethod Proxy 'TRACE
_ = Method
methodTrace
instance ReflectMethod 'CONNECT where
reflectMethod :: Proxy 'CONNECT -> Method
reflectMethod Proxy 'CONNECT
_ = Method
methodConnect