{-# LANGUAGE DeriveDataTypeable #-}
module Network.HTTP.Types.Method
(
Method
, methodGet
, methodPost
, methodHead
, methodPut
, methodDelete
, methodTrace
, methodConnect
, methodOptions
, methodPatch
, StdMethod(..)
, parseMethod
, renderMethod
, renderStdMethod
)
where
import Control.Arrow ((|||))
import Data.Array
import qualified Data.ByteString as B
import qualified Data.ByteString.Char8 as B8
import Data.Typeable
type Method = B.ByteString
methodGet, methodPost, methodHead, methodPut, methodDelete, methodTrace, methodConnect, methodOptions, methodPatch :: Method
methodGet = renderStdMethod GET
methodPost = renderStdMethod POST
methodHead = renderStdMethod HEAD
methodPut = renderStdMethod PUT
methodDelete = renderStdMethod DELETE
methodTrace = renderStdMethod TRACE
methodConnect = renderStdMethod CONNECT
methodOptions = renderStdMethod OPTIONS
methodPatch = renderStdMethod PATCH
data StdMethod
= GET
| POST
| HEAD
| PUT
| DELETE
| TRACE
| CONNECT
| OPTIONS
| PATCH
deriving (Read, Show, Eq, Ord, Enum, Bounded, Ix, Typeable)
methodArray :: Array StdMethod Method
methodArray = listArray (minBound, maxBound) $ map (B8.pack . show) [minBound :: StdMethod .. maxBound]
methodList :: [(Method, StdMethod)]
methodList = map (\(a, b) -> (b, a)) (assocs methodArray)
parseMethod :: Method -> Either B.ByteString StdMethod
parseMethod bs = maybe (Left bs) Right $ lookup bs methodList
renderMethod :: Either B.ByteString StdMethod -> Method
renderMethod = id ||| renderStdMethod
renderStdMethod :: StdMethod -> Method
renderStdMethod m = methodArray ! m