{-# 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

-- | HTTP method (flat string type).
type Method = B.ByteString

-- | HTTP Method constants.
methodGet, methodPost, methodHead, methodPut, methodDelete, methodTrace, methodConnect, methodOptions, methodPatch :: Method
methodGet :: Method
methodGet     = StdMethod -> Method
renderStdMethod StdMethod
GET
methodPost :: Method
methodPost    = StdMethod -> Method
renderStdMethod StdMethod
POST
methodHead :: Method
methodHead    = StdMethod -> Method
renderStdMethod StdMethod
HEAD
methodPut :: Method
methodPut     = StdMethod -> Method
renderStdMethod StdMethod
PUT
methodDelete :: Method
methodDelete  = StdMethod -> Method
renderStdMethod StdMethod
DELETE
methodTrace :: Method
methodTrace   = StdMethod -> Method
renderStdMethod StdMethod
TRACE
methodConnect :: Method
methodConnect = StdMethod -> Method
renderStdMethod StdMethod
CONNECT
methodOptions :: Method
methodOptions = StdMethod -> Method
renderStdMethod StdMethod
OPTIONS
methodPatch :: Method
methodPatch   = StdMethod -> Method
renderStdMethod StdMethod
PATCH

-- | HTTP standard method (as defined by RFC 2616, and PATCH which is defined
--   by RFC 5789).
data StdMethod
    = GET
    | POST
    | HEAD
    | PUT
    | DELETE
    | TRACE
    | CONNECT
    | OPTIONS
    | PATCH
    deriving (ReadPrec [StdMethod]
ReadPrec StdMethod
Int -> ReadS StdMethod
ReadS [StdMethod]
(Int -> ReadS StdMethod)
-> ReadS [StdMethod]
-> ReadPrec StdMethod
-> ReadPrec [StdMethod]
-> Read StdMethod
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS StdMethod
readsPrec :: Int -> ReadS StdMethod
$creadList :: ReadS [StdMethod]
readList :: ReadS [StdMethod]
$creadPrec :: ReadPrec StdMethod
readPrec :: ReadPrec StdMethod
$creadListPrec :: ReadPrec [StdMethod]
readListPrec :: ReadPrec [StdMethod]
Read, Int -> StdMethod -> ShowS
[StdMethod] -> ShowS
StdMethod -> String
(Int -> StdMethod -> ShowS)
-> (StdMethod -> String)
-> ([StdMethod] -> ShowS)
-> Show StdMethod
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> StdMethod -> ShowS
showsPrec :: Int -> StdMethod -> ShowS
$cshow :: StdMethod -> String
show :: StdMethod -> String
$cshowList :: [StdMethod] -> ShowS
showList :: [StdMethod] -> ShowS
Show, StdMethod -> StdMethod -> Bool
(StdMethod -> StdMethod -> Bool)
-> (StdMethod -> StdMethod -> Bool) -> Eq StdMethod
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: StdMethod -> StdMethod -> Bool
== :: StdMethod -> StdMethod -> Bool
$c/= :: StdMethod -> StdMethod -> Bool
/= :: StdMethod -> StdMethod -> Bool
Eq, Eq StdMethod
Eq StdMethod
-> (StdMethod -> StdMethod -> Ordering)
-> (StdMethod -> StdMethod -> Bool)
-> (StdMethod -> StdMethod -> Bool)
-> (StdMethod -> StdMethod -> Bool)
-> (StdMethod -> StdMethod -> Bool)
-> (StdMethod -> StdMethod -> StdMethod)
-> (StdMethod -> StdMethod -> StdMethod)
-> Ord StdMethod
StdMethod -> StdMethod -> Bool
StdMethod -> StdMethod -> Ordering
StdMethod -> StdMethod -> StdMethod
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: StdMethod -> StdMethod -> Ordering
compare :: StdMethod -> StdMethod -> Ordering
$c< :: StdMethod -> StdMethod -> Bool
< :: StdMethod -> StdMethod -> Bool
$c<= :: StdMethod -> StdMethod -> Bool
<= :: StdMethod -> StdMethod -> Bool
$c> :: StdMethod -> StdMethod -> Bool
> :: StdMethod -> StdMethod -> Bool
$c>= :: StdMethod -> StdMethod -> Bool
>= :: StdMethod -> StdMethod -> Bool
$cmax :: StdMethod -> StdMethod -> StdMethod
max :: StdMethod -> StdMethod -> StdMethod
$cmin :: StdMethod -> StdMethod -> StdMethod
min :: StdMethod -> StdMethod -> StdMethod
Ord, Int -> StdMethod
StdMethod -> Int
StdMethod -> [StdMethod]
StdMethod -> StdMethod
StdMethod -> StdMethod -> [StdMethod]
StdMethod -> StdMethod -> StdMethod -> [StdMethod]
(StdMethod -> StdMethod)
-> (StdMethod -> StdMethod)
-> (Int -> StdMethod)
-> (StdMethod -> Int)
-> (StdMethod -> [StdMethod])
-> (StdMethod -> StdMethod -> [StdMethod])
-> (StdMethod -> StdMethod -> [StdMethod])
-> (StdMethod -> StdMethod -> StdMethod -> [StdMethod])
-> Enum StdMethod
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: StdMethod -> StdMethod
succ :: StdMethod -> StdMethod
$cpred :: StdMethod -> StdMethod
pred :: StdMethod -> StdMethod
$ctoEnum :: Int -> StdMethod
toEnum :: Int -> StdMethod
$cfromEnum :: StdMethod -> Int
fromEnum :: StdMethod -> Int
$cenumFrom :: StdMethod -> [StdMethod]
enumFrom :: StdMethod -> [StdMethod]
$cenumFromThen :: StdMethod -> StdMethod -> [StdMethod]
enumFromThen :: StdMethod -> StdMethod -> [StdMethod]
$cenumFromTo :: StdMethod -> StdMethod -> [StdMethod]
enumFromTo :: StdMethod -> StdMethod -> [StdMethod]
$cenumFromThenTo :: StdMethod -> StdMethod -> StdMethod -> [StdMethod]
enumFromThenTo :: StdMethod -> StdMethod -> StdMethod -> [StdMethod]
Enum, StdMethod
StdMethod -> StdMethod -> Bounded StdMethod
forall a. a -> a -> Bounded a
$cminBound :: StdMethod
minBound :: StdMethod
$cmaxBound :: StdMethod
maxBound :: StdMethod
Bounded, Ord StdMethod
Ord StdMethod
-> ((StdMethod, StdMethod) -> [StdMethod])
-> ((StdMethod, StdMethod) -> StdMethod -> Int)
-> ((StdMethod, StdMethod) -> StdMethod -> Int)
-> ((StdMethod, StdMethod) -> StdMethod -> Bool)
-> ((StdMethod, StdMethod) -> Int)
-> ((StdMethod, StdMethod) -> Int)
-> Ix StdMethod
(StdMethod, StdMethod) -> Int
(StdMethod, StdMethod) -> [StdMethod]
(StdMethod, StdMethod) -> StdMethod -> Bool
(StdMethod, StdMethod) -> StdMethod -> Int
forall a.
Ord a
-> ((a, a) -> [a])
-> ((a, a) -> a -> Int)
-> ((a, a) -> a -> Int)
-> ((a, a) -> a -> Bool)
-> ((a, a) -> Int)
-> ((a, a) -> Int)
-> Ix a
$crange :: (StdMethod, StdMethod) -> [StdMethod]
range :: (StdMethod, StdMethod) -> [StdMethod]
$cindex :: (StdMethod, StdMethod) -> StdMethod -> Int
index :: (StdMethod, StdMethod) -> StdMethod -> Int
$cunsafeIndex :: (StdMethod, StdMethod) -> StdMethod -> Int
unsafeIndex :: (StdMethod, StdMethod) -> StdMethod -> Int
$cinRange :: (StdMethod, StdMethod) -> StdMethod -> Bool
inRange :: (StdMethod, StdMethod) -> StdMethod -> Bool
$crangeSize :: (StdMethod, StdMethod) -> Int
rangeSize :: (StdMethod, StdMethod) -> Int
$cunsafeRangeSize :: (StdMethod, StdMethod) -> Int
unsafeRangeSize :: (StdMethod, StdMethod) -> Int
Ix, Typeable)
-- These are ordered by suspected frequency. More popular methods should go first.
-- The reason is that methodList is used with lookup.
-- lookup is probably faster for these few cases than setting up an elaborate data structure.

methodArray :: Array StdMethod Method
methodArray :: Array StdMethod Method
methodArray = (StdMethod, StdMethod) -> [Method] -> Array StdMethod Method
forall i e. Ix i => (i, i) -> [e] -> Array i e
listArray (StdMethod
forall a. Bounded a => a
minBound, StdMethod
forall a. Bounded a => a
maxBound) ([Method] -> Array StdMethod Method)
-> [Method] -> Array StdMethod Method
forall a b. (a -> b) -> a -> b
$ (StdMethod -> Method) -> [StdMethod] -> [Method]
forall a b. (a -> b) -> [a] -> [b]
map (String -> Method
B8.pack (String -> Method) -> (StdMethod -> String) -> StdMethod -> Method
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StdMethod -> String
forall a. Show a => a -> String
show) [StdMethod
forall a. Bounded a => a
minBound :: StdMethod .. StdMethod
forall a. Bounded a => a
maxBound]

methodList :: [(Method, StdMethod)]
methodList :: [(Method, StdMethod)]
methodList = ((StdMethod, Method) -> (Method, StdMethod))
-> [(StdMethod, Method)] -> [(Method, StdMethod)]
forall a b. (a -> b) -> [a] -> [b]
map (\(StdMethod
a, Method
b) -> (Method
b, StdMethod
a)) (Array StdMethod Method -> [(StdMethod, Method)]
forall i e. Ix i => Array i e -> [(i, e)]
assocs Array StdMethod Method
methodArray)

-- | Convert a method 'ByteString' to a 'StdMethod' if possible.
parseMethod :: Method -> Either B.ByteString StdMethod
parseMethod :: Method -> Either Method StdMethod
parseMethod Method
bs = Either Method StdMethod
-> (StdMethod -> Either Method StdMethod)
-> Maybe StdMethod
-> Either Method StdMethod
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Method -> Either Method StdMethod
forall a b. a -> Either a b
Left Method
bs) StdMethod -> Either Method StdMethod
forall a b. b -> Either a b
Right (Maybe StdMethod -> Either Method StdMethod)
-> Maybe StdMethod -> Either Method StdMethod
forall a b. (a -> b) -> a -> b
$ Method -> [(Method, StdMethod)] -> Maybe StdMethod
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Method
bs [(Method, StdMethod)]
methodList

-- | Convert an algebraic method to a 'ByteString'.
renderMethod :: Either B.ByteString StdMethod -> Method
renderMethod :: Either Method StdMethod -> Method
renderMethod = Method -> Method
forall a. a -> a
id (Method -> Method)
-> (StdMethod -> Method) -> Either Method StdMethod -> Method
forall b d c. (b -> d) -> (c -> d) -> Either b c -> d
forall (a :: * -> * -> *) b d c.
ArrowChoice a =>
a b d -> a c d -> a (Either b c) d
||| StdMethod -> Method
renderStdMethod

-- | Convert a 'StdMethod' to a 'ByteString'.
renderStdMethod :: StdMethod -> Method
renderStdMethod :: StdMethod -> Method
renderStdMethod StdMethod
m = Array StdMethod Method
methodArray Array StdMethod Method -> StdMethod -> Method
forall i e. Ix i => Array i e -> i -> e
! StdMethod
m