| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
Network.HTTP.Semantics
Description
Library for HTTP Semantics (RFC9110), version-independent common parts. For low-level headers, Token is used. For upper-level headers, HeaderName should be used.
Synopsis
- data InpObj = InpObj {}
- type InpBody = IO (ByteString, Bool)
- data OutObj = OutObj {}
- data OutBody- = OutBodyNone
- | OutBodyStreaming ((Builder -> IO ()) -> IO () -> IO ())
- | OutBodyStreamingIface (OutBodyIface -> IO ())
- | OutBodyBuilder Builder
- | OutBodyFile FileSpec
 
- data OutBodyIface = OutBodyIface {- outBodyUnmask :: forall x. IO x -> IO x
- outBodyPush :: Builder -> IO ()
- outBodyPushFinal :: Builder -> IO ()
- outBodyCancel :: Maybe SomeException -> IO ()
- outBodyFlush :: IO ()
 
- type TrailersMaker = Maybe ByteString -> IO NextTrailersMaker
- defaultTrailersMaker :: TrailersMaker
- data NextTrailersMaker
- type FileOffset = Int64
- type ByteCount = Int64
- data FileSpec = FileSpec FilePath FileOffset ByteCount
- type Scheme = ByteString
- type Authority = String
- type Path = ByteString
- type FieldName = ByteString
- type FieldValue = ByteString
- type TokenHeader = (Token, FieldValue)
- type TokenHeaderList = [TokenHeader]
- type TokenHeaderTable = (TokenHeaderList, ValueTable)
- type ValueTable = Array Int (Maybe FieldValue)
- getFieldValue :: Token -> ValueTable -> Maybe FieldValue
- type HeaderTable = (TokenHeaderList, ValueTable)
- type HeaderValue = ByteString
- getHeaderValue :: Token -> ValueTable -> Maybe FieldValue
- data Token = Token {- tokenIx :: Int
- shouldBeIndexed :: Bool
- isPseudo :: Bool
- tokenKey :: HeaderName
 
- tokenCIKey :: Token -> ByteString
- tokenFoldedKey :: Token -> ByteString
- toToken :: ByteString -> Token
- minTokenIx :: Int
- maxStaticTokenIx :: Int
- maxTokenIx :: Int
- cookieTokenIx :: Int
- isMaxTokenIx :: Int -> Bool
- isCookieTokenIx :: Int -> Bool
- isStaticTokenIx :: Int -> Bool
- isStaticToken :: Token -> Bool
- tokenAuthority :: Token
- tokenMethod :: Token
- tokenPath :: Token
- tokenScheme :: Token
- tokenStatus :: Token
- tokenAcceptCharset :: Token
- tokenAcceptEncoding :: Token
- tokenAcceptLanguage :: Token
- tokenAcceptRanges :: Token
- tokenAccept :: Token
- tokenAccessControlAllowOrigin :: Token
- tokenAge :: Token
- tokenAllow :: Token
- tokenAuthorization :: Token
- tokenCacheControl :: Token
- tokenContentDisposition :: Token
- tokenContentEncoding :: Token
- tokenContentLanguage :: Token
- tokenContentLength :: Token
- tokenContentLocation :: Token
- tokenContentRange :: Token
- tokenContentType :: Token
- tokenCookie :: Token
- tokenDate :: Token
- tokenEtag :: Token
- tokenExpect :: Token
- tokenExpires :: Token
- tokenFrom :: Token
- tokenHost :: Token
- tokenIfMatch :: Token
- tokenIfModifiedSince :: Token
- tokenIfNoneMatch :: Token
- tokenIfRange :: Token
- tokenIfUnmodifiedSince :: Token
- tokenLastModified :: Token
- tokenLink :: Token
- tokenLocation :: Token
- tokenMaxForwards :: Token
- tokenProxyAuthenticate :: Token
- tokenProxyAuthorization :: Token
- tokenRange :: Token
- tokenReferer :: Token
- tokenRefresh :: Token
- tokenRetryAfter :: Token
- tokenServer :: Token
- tokenSetCookie :: Token
- tokenStrictTransportSecurity :: Token
- tokenTransferEncoding :: Token
- tokenUserAgent :: Token
- tokenVary :: Token
- tokenVia :: Token
- tokenWwwAuthenticate :: Token
- tokenConnection :: Token
- tokenTE :: Token
- tokenMax :: Token
- tokenAccessControlAllowCredentials :: Token
- tokenAccessControlAllowHeaders :: Token
- tokenAccessControlAllowMethods :: Token
- tokenAccessControlExposeHeaders :: Token
- tokenAccessControlRequestHeaders :: Token
- tokenAccessControlRequestMethod :: Token
- tokenAltSvc :: Token
- tokenContentSecurityPolicy :: Token
- tokenEarlyData :: Token
- tokenExpectCt :: Token
- tokenForwarded :: Token
- tokenOrigin :: Token
- tokenPurpose :: Token
- tokenTimingAllowOrigin :: Token
- tokenUpgradeInsecureRequests :: Token
- tokenXContentTypeOptions :: Token
- tokenXForwardedFor :: Token
- tokenXFrameOptions :: Token
- tokenXXssProtection :: Token
Request/response as input
Input object
Constructors
| InpObj | |
| Fields 
 | |
Request/response as output
Output object
Constructors
| OutObj | |
| Fields 
 | |
Constructors
| OutBodyNone | |
| OutBodyStreaming ((Builder -> IO ()) -> IO () -> IO ()) | Streaming body takes a write action and a flush action. | 
| OutBodyStreamingIface (OutBodyIface -> IO ()) | Generalization of  | 
| OutBodyBuilder Builder | |
| OutBodyFile FileSpec | 
data OutBodyIface Source #
Constructors
| OutBodyIface | |
| Fields 
 | |
Trailers maker
type TrailersMaker = Maybe ByteString -> IO NextTrailersMaker Source #
Trailers maker. A chunks of the response body is passed
   with Just. The maker should update internal state
   with the ByteString and return the next trailers maker.
   When response body reaches its end,
   Nothing is passed and the maker should generate
   trailers. An example:
{-# LANGUAGE BangPatterns #-}
import Data.ByteString (ByteString)
import qualified Data.ByteString.Char8 as C8
import Crypto.Hash (Context, SHA1) -- cryptonite
import qualified Crypto.Hash as CH
-- Strictness is important for Context.
trailersMaker :: Context SHA1 -> Maybe ByteString -> IO NextTrailersMaker
trailersMaker ctx Nothing = return $ Trailers [("X-SHA1", sha1)]
  where
    !sha1 = C8.pack $ show $ CH.hashFinalize ctx
trailersMaker ctx (Just bs) = return $ NextTrailersMaker $ trailersMaker ctx'
  where
    !ctx' = CH.hashUpdate ctx bsUsage example:
let h2rsp = responseFile ...
    maker = trailersMaker (CH.hashInit :: Context SHA1)
    h2rsp' = setResponseTrailersMaker h2rsp makerdefaultTrailersMaker :: TrailersMaker Source #
TrailersMake to create no trailers.
data NextTrailersMaker Source #
Either the next trailers maker or final trailers.
Constructors
| NextTrailersMaker TrailersMaker | |
| Trailers [Header] | 
File spec
type FileOffset = Int64 Source #
Offset for file.
File specification.
Constructors
| FileSpec FilePath FileOffset ByteCount | 
Types
type Scheme = ByteString Source #
"http" or "https".
type Path = ByteString Source #
Path.
Low-level headers.
type FieldName = ByteString Source #
Field name. Internal usage only.
type FieldValue = ByteString Source #
Field value.
type TokenHeader = (Token, FieldValue) Source #
TokenBased header.
type TokenHeaderList = [TokenHeader] Source #
TokenBased header list.
type TokenHeaderTable = (TokenHeaderList, ValueTable) Source #
A pair of token list and value table.
Value table
type ValueTable = Array Int (Maybe FieldValue) Source #
An array to get FieldValue quickly.
   getHeaderValue should be used.
   Internally, the key is tokenIx.
getFieldValue :: Token -> ValueTable -> Maybe FieldValue Source #
Accessing FieldValue with Token.
Deprecated
type HeaderTable = (TokenHeaderList, ValueTable) Source #
Deprecated: use TokenHeaderTable instead
A pair of token list and value table.
type HeaderValue = ByteString Source #
Deprecated: use FieldValue instead
Header value.
getHeaderValue :: Token -> ValueTable -> Maybe FieldValue Source #
Deprecated: use geFieldValue instead
Accessing FieldValue with Token.
Data type
Internal representation for header keys.
Constructors
| Token | |
| Fields 
 | |
tokenCIKey :: Token -> ByteString Source #
Extracting a case insensitive header key from a token.
tokenFoldedKey :: Token -> ByteString Source #
Extracting a folded header key from a token.
toToken :: ByteString -> Token Source #
Making a token from a header key.
>>>toToken ":authority" == tokenAuthorityTrue>>>toToken "foo"Token {tokenIx = 73, shouldBeIndexed = True, isPseudo = False, tokenKey = "foo"}>>>toToken ":bar"Token {tokenIx = 73, shouldBeIndexed = True, isPseudo = True, tokenKey = ":bar"}
Ix
minTokenIx :: Int Source #
Minimum token index.
maxStaticTokenIx :: Int Source #
Maximun token index defined in the static table.
maxTokenIx :: Int Source #
Maximum token index.
cookieTokenIx :: Int Source #
Token index for tokenCookie.
Utilities
isMaxTokenIx :: Int -> Bool Source #
Is this token ix to be held in the place holder?
isCookieTokenIx :: Int -> Bool Source #
Is this token ix for Cookie?
isStaticTokenIx :: Int -> Bool Source #
Is this token ix for a header not defined in the static table?
isStaticToken :: Token -> Bool Source #
Is this token for a header not defined in the static table?
Defined tokens
tokenMethod :: Token Source #
tokenScheme :: Token Source #
tokenStatus :: Token Source #
tokenAccept :: Token Source #
tokenAllow :: Token Source #
tokenCookie :: Token Source #
tokenExpect :: Token Source #
tokenExpires :: Token Source #
tokenIfMatch :: Token Source #
tokenIfRange :: Token Source #
tokenRange :: Token Source #
tokenReferer :: Token Source #
tokenRefresh :: Token Source #
tokenServer :: Token Source #
tokenConnection :: Token Source #
A place holder to hold header keys not defined in the static table. | For Warp
tokenAccessControlAllowCredentials :: Token Source #
For QPACK
tokenAltSvc :: Token Source #
tokenOrigin :: Token Source #
tokenPurpose :: Token Source #