{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE OverloadedStrings #-}
{-# OPTIONS_HADDOCK hide, prune #-}
module Network.Http.Internal (
Hostname,
Port,
Request(..),
EntityBody(..),
ExpectMode(..),
Response(..),
StatusCode,
TransferEncoding(..),
ContentEncoding(..),
getStatusCode,
getStatusMessage,
getHeader,
getHeaderMap,
Method(..),
Headers,
emptyHeaders,
updateHeader,
removeHeader,
buildHeaders,
lookupHeader,
retrieveHeaders,
HttpType (getHeaders),
HttpParseException(..),
hasBrotli,
composeRequestBytes,
composeResponseBytes
) where
import Prelude hiding (lookup)
import Blaze.ByteString.Builder (Builder)
import qualified Blaze.ByteString.Builder as Builder (copyByteString,
copyByteString,
fromByteString,
fromByteString,
toByteString)
import qualified Blaze.ByteString.Builder.Char8 as Builder (fromChar,
fromShow,
fromString)
import Control.Exception (Exception)
import Data.ByteString (ByteString)
import qualified Data.ByteString.Char8 as S
import Data.CaseInsensitive (CI, mk, original)
import qualified Data.Map.Strict as Map
import Data.Map (Map)
import Data.Int (Int64)
import Data.List (foldl')
import Data.Monoid as Mon (mconcat, mempty)
import Data.Typeable (Typeable)
import Data.Word (Word16)
type Hostname = ByteString
type Port = Word16
{-# INLINE hasBrotli #-}
hasBrotli :: Bool
#if defined(MIN_VERSION_brotli_streams)
hasBrotli = True
#else
hasBrotli = False
#endif
data Method
= GET
| HEAD
| POST
| PUT
| DELETE
| TRACE
| OPTIONS
| CONNECT
| PATCH
| Method ByteString
deriving (Show, Read, Ord)
instance Eq Method where
GET == GET = True
HEAD == HEAD = True
POST == POST = True
PUT == PUT = True
DELETE == DELETE = True
TRACE == TRACE = True
OPTIONS == OPTIONS = True
CONNECT == CONNECT = True
PATCH == PATCH = True
GET == Method "GET" = True
HEAD == Method "HEAD" = True
POST == Method "POST" = True
PUT == Method "PUT" = True
DELETE == Method "DELETE" = True
TRACE == Method "TRACE" = True
OPTIONS == Method "OPTIONS" = True
CONNECT == Method "CONNECT" = True
PATCH == Method "PATCH" = True
Method a == Method b = a == b
m@(Method _) == other = other == m
_ == _ = False
data Request
= Request {
qMethod :: !Method,
qHost :: !(Maybe ByteString),
qPath :: !ByteString,
qBody :: !EntityBody,
qExpect :: !ExpectMode,
qHeaders :: !Headers
} deriving (Eq)
instance Show Request where
show q = {-# SCC "Request.show" #-}
S.unpack $ S.filter (/= '\r') $ Builder.toByteString $ composeRequestBytes q "<default>"
data EntityBody = Empty | Chunking | Static Int64 deriving (Show, Eq, Ord)
data ExpectMode = Normal | Continue deriving (Show, Eq, Ord)
composeRequestBytes :: Request -> ByteString -> Builder
composeRequestBytes q h' =
mconcat
[requestline,
hostLine,
headerFields,
crlf]
where
requestline = Mon.mconcat
[method,
sp,
uri,
sp,
version,
crlf]
method = case qMethod q of
GET -> Builder.fromString "GET"
HEAD -> Builder.fromString "HEAD"
POST -> Builder.fromString "POST"
PUT -> Builder.fromString "PUT"
DELETE -> Builder.fromString "DELETE"
TRACE -> Builder.fromString "TRACE"
OPTIONS -> Builder.fromString "OPTIONS"
CONNECT -> Builder.fromString "CONNECT"
PATCH -> Builder.fromString "PATCH"
(Method x) -> Builder.fromByteString x
uri = case qPath q of
"" -> Builder.fromChar '/'
path -> Builder.copyByteString path
version = Builder.fromString "HTTP/1.1"
hostLine = mconcat
[Builder.fromString "Host: ",
hostname,
crlf]
hostname = case qHost q of
Just x' -> Builder.copyByteString x'
Nothing -> Builder.copyByteString h'
headerFields = joinHeaders $ unWrap $ qHeaders q
crlf = Builder.fromString "\r\n"
sp = Builder.fromChar ' '
type StatusCode = Int
data Response
= Response {
pStatusCode :: !StatusCode,
pStatusMsg :: !ByteString,
pTransferEncoding :: !TransferEncoding,
pContentEncoding :: !ContentEncoding,
pContentLength :: !(Maybe Int64),
pHeaders :: !Headers
}
instance Show Response where
show p = {-# SCC "Response.show" #-}
S.unpack $ S.filter (/= '\r') $ Builder.toByteString $ composeResponseBytes p
data TransferEncoding = None | Chunked
data ContentEncoding = Identity | Gzip | Deflate | Br | UnknownCE !ByteString
deriving (Show)
getStatusCode :: Response -> StatusCode
getStatusCode = pStatusCode
{-# INLINE getStatusCode #-}
getStatusMessage :: Response -> ByteString
getStatusMessage = pStatusMsg
{-# INLINE getStatusMessage #-}
getHeader :: Response -> ByteString -> Maybe ByteString
getHeader p k =
lookupHeader h k
where
h = pHeaders p
getHeaderMap :: Response -> Map (CI ByteString) ByteString
getHeaderMap = unWrap . pHeaders
class HttpType τ where
getHeaders :: τ -> Headers
instance HttpType Request where
getHeaders q = qHeaders q
instance HttpType Response where
getHeaders p = pHeaders p
composeResponseBytes :: Response -> Builder
composeResponseBytes p =
mconcat
[statusline,
headerFields,
crlf]
where
statusline = mconcat
[version,
sp,
code,
sp,
message,
crlf]
code = Builder.fromShow $ pStatusCode p
message = Builder.copyByteString $ pStatusMsg p
version = Builder.fromString "HTTP/1.1"
headerFields = joinHeaders $ unWrap $ pHeaders p
newtype Headers = Wrap {
unWrap :: Map (CI ByteString) ByteString
} deriving (Eq)
instance Show Headers where
show x = S.unpack $ S.filter (/= '\r') $ Builder.toByteString $ joinHeaders $ unWrap x
joinHeaders :: Map (CI ByteString) ByteString -> Builder
joinHeaders m = Map.foldrWithKey combine Mon.mempty m
combine :: CI ByteString -> ByteString -> Builder -> Builder
combine k v acc =
mconcat [acc, key, Builder.fromString ": ", value, crlf]
where
key = Builder.copyByteString $ original k
value = Builder.fromByteString v
{-# INLINE combine #-}
emptyHeaders :: Headers
emptyHeaders =
Wrap Map.empty
updateHeader :: Headers -> ByteString -> ByteString -> Headers
updateHeader x k v =
Wrap result
where
!result = Map.insert (mk k) v m
!m = unWrap x
removeHeader :: Headers -> ByteString -> Headers
removeHeader x k =
Wrap result
where
!result = Map.delete (mk k) m
!m = unWrap x
buildHeaders :: [(ByteString, ByteString)] -> Headers
buildHeaders hs =
Wrap result
where
result = foldl' addHeader Map.empty hs
addHeader
:: Map (CI ByteString) ByteString
-> (ByteString,ByteString)
-> Map (CI ByteString) ByteString
addHeader m (k,v) =
Map.insertWith f (mk k) v m
where
f new old = S.concat [old, ",", new]
lookupHeader :: Headers -> ByteString -> Maybe ByteString
lookupHeader x k =
Map.lookup (mk k) m
where
!m = unWrap x
retrieveHeaders :: Headers -> [(ByteString, ByteString)]
retrieveHeaders x =
map down $ Map.toList m
where
!m = unWrap x
down :: (CI ByteString, ByteString) -> (ByteString, ByteString)
down (k, v) =
(original k, v)
data HttpParseException = HttpParseException String
deriving (Typeable, Show)
instance Exception HttpParseException