File: Method.hs

package info (click to toggle)
haskell-http-types 0.12.4-1
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid, trixie
  • size: 156 kB
  • sloc: haskell: 1,314; makefile: 7
file content (154 lines) | stat: -rw-r--r-- 3,818 bytes parent folder | download
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}

-- | Types and constants for HTTP methods.
--
-- The HTTP standard defines a set of standard methods, when to use them,
-- and how to handle them. The standard set has been provided as a separate
-- data type 'StdMethod', but since you can also use custom methods, the
-- basic type 'Method' is just a synonym for 'ByteString'.
module Network.HTTP.Types.Method (
    -- * HTTP methods
    Method,

    -- ** Constants
    methodGet,
    methodPost,
    methodHead,
    methodPut,
    methodDelete,
    methodTrace,
    methodConnect,
    methodOptions,
    methodPatch,

    -- ** Standard Methods

    -- | One data type that holds all standard HTTP methods.
    StdMethod (..),
    parseMethod,
    renderMethod,
    renderStdMethod,
)
where

import Control.Arrow ((|||))
import Data.Array (Array, Ix, assocs, listArray, (!))
import qualified Data.ByteString as B
import qualified Data.ByteString.Char8 as B8
import Data.Data (Data)
import Data.Typeable (Typeable)
import GHC.Generics (Generic)

-- $setup
-- >>> import Data.ByteString.Char8 (ByteString)
-- >>> import Data.Text (pack)
-- >>> import Data.Text.Encoding (encodeUtf8)
-- >>> import Test.QuickCheck
-- >>> :{
-- instance Arbitrary ByteString where
--     arbitrary = encodeUtf8 . pack <$> arbitrary
-- :}

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

-- | HTTP GET Method
methodGet :: Method
methodGet = renderStdMethod GET

-- | HTTP POST Method
methodPost :: Method
methodPost = renderStdMethod POST

-- | HTTP HEAD Method
methodHead :: Method
methodHead = renderStdMethod HEAD

-- | HTTP PUT Method
methodPut :: Method
methodPut = renderStdMethod PUT

-- | HTTP DELETE Method
methodDelete :: Method
methodDelete = renderStdMethod DELETE

-- | HTTP TRACE Method
methodTrace :: Method
methodTrace = renderStdMethod TRACE

-- | HTTP CONNECT Method
methodConnect :: Method
methodConnect = renderStdMethod CONNECT

-- | HTTP OPTIONS Method
methodOptions :: Method
methodOptions = renderStdMethod OPTIONS

-- | HTTP PATCH Method
--
-- @since 0.8.0
methodPatch :: Method
methodPatch = renderStdMethod PATCH

-- | HTTP standard method (as defined by RFC 2616, and PATCH which is defined
--   by RFC 5789).
--
-- @since 0.2.0
data StdMethod
    = GET
    | POST
    | HEAD
    | PUT
    | DELETE
    | TRACE
    | CONNECT
    | OPTIONS
    | -- | @since 0.8.0
      PATCH
    deriving
        ( Read
        , Show
        , Eq
        , Ord
        , Enum
        , Bounded
        , Ix
        , Typeable
        , -- | @since 0.12.4
          Generic
        , -- | @since 0.12.4
          Data
        )

-- 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.

-- FIXME: listArray (minBound, maxBound) $ fmap fst methodList
methodArray :: Array StdMethod Method
methodArray = listArray (minBound, maxBound) $ map (B8.pack . show) [minBound :: StdMethod .. maxBound]

-- FIXME: map (\m -> (B8.pack $ show m, m)) [minBound .. maxBound]
methodList :: [(Method, StdMethod)]
methodList = map (\(a, b) -> (b, a)) (assocs methodArray)

-- | Convert a method 'ByteString' to a 'StdMethod' if possible.
--
-- @since 0.2.0
parseMethod :: Method -> Either B.ByteString StdMethod
parseMethod bs = maybe (Left bs) Right $ lookup bs methodList

-- | Convert an algebraic method to a 'ByteString'.
--
-- prop> renderMethod (parseMethod bs) == bs
--
-- @since 0.3.0
renderMethod :: Either B.ByteString StdMethod -> Method
renderMethod = id ||| renderStdMethod

-- | Convert a 'StdMethod' to a 'ByteString'.
--
-- @since 0.2.0
renderStdMethod :: StdMethod -> Method
renderStdMethod m = methodArray ! m