module Hreq.Core.API.Verb
  ( module Hreq.Core.API.Verb
    
  , StdMethod (..)
  , Method
  ) where
import Data.Proxy (Proxy)
import Data.Typeable (Typeable)
import Network.HTTP.Types.Method (Method, StdMethod (..), methodConnect, methodDelete, methodGet,
                                  methodHead, methodOptions, methodPatch, methodPost, methodPut,
                                  methodTrace)
data Verb (method :: k1) (contents:: [k2])
  deriving (Typeable)
type GET = 'GET
type Get = Verb GET
type POST = 'POST
type Post = Verb 'POST
type PUT = 'PUT
type Put = Verb PUT
type DELETE = 'DELETE
type Delete = Verb 'DELETE
type PATCH = 'PATCH
type Patch = Verb 'PATCH
class ReflectMethod a where
    reflectMethod :: Proxy a -> Method
instance ReflectMethod 'GET where
    reflectMethod _ = methodGet
instance ReflectMethod 'POST where
    reflectMethod _ = methodPost
instance ReflectMethod 'PUT where
    reflectMethod _ = methodPut
instance ReflectMethod 'DELETE where
    reflectMethod _ = methodDelete
instance ReflectMethod 'PATCH where
    reflectMethod _ = methodPatch
instance ReflectMethod 'HEAD where
    reflectMethod _ = methodHead
instance ReflectMethod 'OPTIONS where
    reflectMethod _ = methodOptions
instance ReflectMethod 'TRACE where
    reflectMethod _ = methodTrace
instance ReflectMethod 'CONNECT where
    reflectMethod _ = methodConnect