http-types-0.12.4: Generic HTTP types for Haskell (for both client and server code).
Safe HaskellSafe-Inferred
LanguageHaskell2010

Network.HTTP.Types

Synopsis

Methods

For more information: Network.HTTP.Types.Method

type Method = ByteString Source #

HTTP method (flat ByteString type).

Constants

methodGet :: Method Source #

HTTP GET Method

methodPost :: Method Source #

HTTP POST Method

methodHead :: Method Source #

HTTP HEAD Method

methodPut :: Method Source #

HTTP PUT Method

methodDelete :: Method Source #

HTTP DELETE Method

methodTrace :: Method Source #

HTTP TRACE Method

methodConnect :: Method Source #

HTTP CONNECT Method

methodOptions :: Method Source #

HTTP OPTIONS Method

methodPatch :: Method Source #

HTTP PATCH Method

Since: 0.8.0

data StdMethod Source #

HTTP standard method (as defined by RFC 2616, and PATCH which is defined by RFC 5789).

Since: 0.2.0

Constructors

GET 
POST 
HEAD 
PUT 
DELETE 
TRACE 
CONNECT 
OPTIONS 
PATCH

Since: 0.8.0

Instances

Instances details
Data StdMethod Source #

Since: 0.12.4

Instance details

Defined in Network.HTTP.Types.Method

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StdMethod -> c StdMethod #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c StdMethod #

toConstr :: StdMethod -> Constr #

dataTypeOf :: StdMethod -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c StdMethod) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c StdMethod) #

gmapT :: (forall b. Data b => b -> b) -> StdMethod -> StdMethod #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StdMethod -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StdMethod -> r #

gmapQ :: (forall d. Data d => d -> u) -> StdMethod -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> StdMethod -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> StdMethod -> m StdMethod #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StdMethod -> m StdMethod #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StdMethod -> m StdMethod #

Bounded StdMethod Source # 
Instance details

Defined in Network.HTTP.Types.Method

Enum StdMethod Source # 
Instance details

Defined in Network.HTTP.Types.Method

Generic StdMethod Source # 
Instance details

Defined in Network.HTTP.Types.Method

Associated Types

type Rep StdMethod :: Type -> Type #

Ix StdMethod Source # 
Instance details

Defined in Network.HTTP.Types.Method

Read StdMethod Source # 
Instance details

Defined in Network.HTTP.Types.Method

Show StdMethod Source # 
Instance details

Defined in Network.HTTP.Types.Method

Eq StdMethod Source # 
Instance details

Defined in Network.HTTP.Types.Method

Ord StdMethod Source # 
Instance details

Defined in Network.HTTP.Types.Method

type Rep StdMethod Source #

Since: 0.12.4

Instance details

Defined in Network.HTTP.Types.Method

type Rep StdMethod = D1 ('MetaData "StdMethod" "Network.HTTP.Types.Method" "http-types-0.12.4-8sVzaiF2LjrERDtipkARMD" 'False) (((C1 ('MetaCons "GET" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "POST" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "HEAD" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PUT" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "DELETE" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TRACE" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "CONNECT" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "OPTIONS" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PATCH" 'PrefixI 'False) (U1 :: Type -> Type)))))

Parsing and redering methods

parseMethod :: Method -> Either ByteString StdMethod Source #

Convert a method ByteString to a StdMethod if possible.

Since: 0.2.0

renderMethod :: Either ByteString StdMethod -> Method Source #

Convert an algebraic method to a ByteString.

renderMethod (parseMethod bs) == bs

Since: 0.3.0

renderStdMethod :: StdMethod -> Method Source #

Convert a StdMethod to a ByteString.

Since: 0.2.0

Versions

For more information: Network.HTTP.Types.Version

data HttpVersion Source #

HTTP Version.

Note that the Show instance is intended merely for debugging.

Constructors

HttpVersion 

Fields

Instances

Instances details
Data HttpVersion Source #

Since: 0.12.4

Instance details

Defined in Network.HTTP.Types.Version

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HttpVersion -> c HttpVersion #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HttpVersion #

toConstr :: HttpVersion -> Constr #

dataTypeOf :: HttpVersion -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c HttpVersion) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HttpVersion) #

gmapT :: (forall b. Data b => b -> b) -> HttpVersion -> HttpVersion #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HttpVersion -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HttpVersion -> r #

gmapQ :: (forall d. Data d => d -> u) -> HttpVersion -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HttpVersion -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HttpVersion -> m HttpVersion #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HttpVersion -> m HttpVersion #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HttpVersion -> m HttpVersion #

Generic HttpVersion Source # 
Instance details

Defined in Network.HTTP.Types.Version

Associated Types

type Rep HttpVersion :: Type -> Type #

Show HttpVersion Source #
>>> show http11
"HTTP/1.1"
Instance details

Defined in Network.HTTP.Types.Version

Eq HttpVersion Source # 
Instance details

Defined in Network.HTTP.Types.Version

Ord HttpVersion Source # 
Instance details

Defined in Network.HTTP.Types.Version

type Rep HttpVersion Source #

Since: 0.12.4

Instance details

Defined in Network.HTTP.Types.Version

type Rep HttpVersion = D1 ('MetaData "HttpVersion" "Network.HTTP.Types.Version" "http-types-0.12.4-8sVzaiF2LjrERDtipkARMD" 'False) (C1 ('MetaCons "HttpVersion" 'PrefixI 'True) (S1 ('MetaSel ('Just "httpMajor") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Just "httpMinor") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int)))

http20 :: HttpVersion Source #

HTTP 2.0

Since: 0.10

Status

For more information: Network.HTTP.Types.Status

data Status Source #

HTTP Status.

Only the statusCode is used for comparisons.

Please use mkStatus to create status codes from code and message, or the Enum instance or the status code constants (like ok200). There might be additional record members in the future.

Note that the Show instance is only for debugging.

Constructors

Status 

Instances

Instances details
Data Status Source #

Since: 0.12.4

Instance details

Defined in Network.HTTP.Types.Status

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Status -> c Status #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Status #

toConstr :: Status -> Constr #

dataTypeOf :: Status -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Status) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Status) #

gmapT :: (forall b. Data b => b -> b) -> Status -> Status #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Status -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Status -> r #

gmapQ :: (forall d. Data d => d -> u) -> Status -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Status -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Status -> m Status #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Status -> m Status #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Status -> m Status #

Bounded Status Source #

Since: 0.11

Instance details

Defined in Network.HTTP.Types.Status

Enum Status Source #

Be advised, that when using the "enumFrom*" family of methods or ranges in lists, it will generate all possible status codes.

E.g. [status100 .. status200] generates Statuses of 100, 101, 102 .. 198, 199, 200

The statuses not included in this library will have an empty message.

Since: 0.7.3

Instance details

Defined in Network.HTTP.Types.Status

Generic Status Source # 
Instance details

Defined in Network.HTTP.Types.Status

Associated Types

type Rep Status :: Type -> Type #

Methods

from :: Status -> Rep Status x #

to :: Rep Status x -> Status #

Show Status Source # 
Instance details

Defined in Network.HTTP.Types.Status

Eq Status Source #

A Status is equal to another Status if the status codes are equal.

Instance details

Defined in Network.HTTP.Types.Status

Methods

(==) :: Status -> Status -> Bool #

(/=) :: Status -> Status -> Bool #

Ord Status Source #

Statuses are ordered according to their status codes only.

Instance details

Defined in Network.HTTP.Types.Status

type Rep Status Source #

Since: 0.12.4

Instance details

Defined in Network.HTTP.Types.Status

type Rep Status = D1 ('MetaData "Status" "Network.HTTP.Types.Status" "http-types-0.12.4-8sVzaiF2LjrERDtipkARMD" 'False) (C1 ('MetaCons "Status" 'PrefixI 'True) (S1 ('MetaSel ('Just "statusCode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "statusMessage") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)))

Constants

mkStatus :: Int -> ByteString -> Status Source #

Create a Status from a status code and message.

status100 :: Status Source #

Continue 100

Since: 0.6.6

continue100 :: Status Source #

Continue 100

Since: 0.6.6

status101 :: Status Source #

Switching Protocols 101

Since: 0.6.6

switchingProtocols101 :: Status Source #

Switching Protocols 101

Since: 0.6.6

ok200 :: Status Source #

OK 200

status201 :: Status Source #

Created 201

created201 :: Status Source #

Created 201

status202 :: Status Source #

Accepted 202

Since: 0.6.6

accepted202 :: Status Source #

Accepted 202

Since: 0.6.6

status203 :: Status Source #

Non-Authoritative Information 203

Since: 0.6.6

nonAuthoritative203 :: Status Source #

Non-Authoritative Information 203

Since: 0.6.6

status204 :: Status Source #

No Content 204

Since: 0.6.6

noContent204 :: Status Source #

No Content 204

Since: 0.6.6

status205 :: Status Source #

Reset Content 205

Since: 0.6.6

resetContent205 :: Status Source #

Reset Content 205

Since: 0.6.6

status206 :: Status Source #

Partial Content 206

Since: 0.5.1

partialContent206 :: Status Source #

Partial Content 206

Since: 0.5.1

status300 :: Status Source #

Multiple Choices 300

multipleChoices300 :: Status Source #

Multiple Choices 300

status301 :: Status Source #

Moved Permanently 301

movedPermanently301 :: Status Source #

Moved Permanently 301

status302 :: Status Source #

Found 302

found302 :: Status Source #

Found 302

status303 :: Status Source #

See Other 303

seeOther303 :: Status Source #

See Other 303

status304 :: Status Source #

Not Modified 304

Since: 0.6.1

notModified304 :: Status Source #

Not Modified 304

Since: 0.6.1

status305 :: Status Source #

Use Proxy 305

Since: 0.6.6

useProxy305 :: Status Source #

Use Proxy 305

Since: 0.6.6

status307 :: Status Source #

Temporary Redirect 307

Since: 0.6.6

temporaryRedirect307 :: Status Source #

Temporary Redirect 307

Since: 0.6.6

status308 :: Status Source #

Permanent Redirect 308

Since: 0.9

permanentRedirect308 :: Status Source #

Permanent Redirect 308

Since: 0.9

status400 :: Status Source #

Bad Request 400

badRequest400 :: Status Source #

Bad Request 400

status401 :: Status Source #

Unauthorized 401

unauthorized401 :: Status Source #

Unauthorized 401

status402 :: Status Source #

Payment Required 402

Since: 0.6.6

paymentRequired402 :: Status Source #

Payment Required 402

Since: 0.6.6

status403 :: Status Source #

Forbidden 403

forbidden403 :: Status Source #

Forbidden 403

status404 :: Status Source #

Not Found 404

notFound404 :: Status Source #

Not Found 404

status405 :: Status Source #

Method Not Allowed 405

methodNotAllowed405 :: Status Source #

Method Not Allowed 405

status406 :: Status Source #

Not Acceptable 406

Since: 0.6.6

notAcceptable406 :: Status Source #

Not Acceptable 406

Since: 0.6.6

status407 :: Status Source #

Proxy Authentication Required 407

Since: 0.6.6

proxyAuthenticationRequired407 :: Status Source #

Proxy Authentication Required 407

Since: 0.6.6

status408 :: Status Source #

Request Timeout 408

Since: 0.6.6

requestTimeout408 :: Status Source #

Request Timeout 408

Since: 0.6.6

status409 :: Status Source #

Conflict 409

Since: 0.6.6

conflict409 :: Status Source #

Conflict 409

Since: 0.6.6

status410 :: Status Source #

Gone 410

Since: 0.6.6

gone410 :: Status Source #

Gone 410

Since: 0.6.6

status411 :: Status Source #

Length Required 411

Since: 0.6.6

lengthRequired411 :: Status Source #

Length Required 411

Since: 0.6.6

status412 :: Status Source #

Precondition Failed 412

Since: 0.6.1

preconditionFailed412 :: Status Source #

Precondition Failed 412

Since: 0.6.1

status413 :: Status Source #

Request Entity Too Large 413

Since: 0.6.6

requestEntityTooLarge413 :: Status Source #

Request Entity Too Large 413

Since: 0.6.6

status414 :: Status Source #

Request-URI Too Long 414

Since: 0.6.6

requestURITooLong414 :: Status Source #

Request-URI Too Long 414

Since: 0.6.6

status415 :: Status Source #

Unsupported Media Type 415

Since: 0.6.6

unsupportedMediaType415 :: Status Source #

Unsupported Media Type 415

Since: 0.6.6

status416 :: Status Source #

Requested Range Not Satisfiable 416

Since: 0.6.1

requestedRangeNotSatisfiable416 :: Status Source #

Requested Range Not Satisfiable 416

Since: 0.6.1

status417 :: Status Source #

Expectation Failed 417

Since: 0.6.6

expectationFailed417 :: Status Source #

Expectation Failed 417

Since: 0.6.6

status418 :: Status Source #

I'm a teapot 418

Since: 0.6.6

imATeapot418 :: Status Source #

I'm a teapot 418

Since: 0.6.6

status422 :: Status Source #

Unprocessable Entity 422 (RFC 4918)

Since: 0.9.1

unprocessableEntity422 :: Status Source #

Unprocessable Entity 422 (RFC 4918)

Since: 0.9.1

status428 :: Status Source #

Precondition Required 428 (RFC 6585)

Since: 0.8.5

preconditionRequired428 :: Status Source #

Precondition Required 428 (RFC 6585)

Since: 0.8.5

status429 :: Status Source #

Too Many Requests 429 (RFC 6585)

Since: 0.8.5

tooManyRequests429 :: Status Source #

Too Many Requests 429 (RFC 6585)

Since: 0.8.5

status431 :: Status Source #

Request Header Fields Too Large 431 (RFC 6585)

Since: 0.8.5

requestHeaderFieldsTooLarge431 :: Status Source #

Request Header Fields Too Large 431 (RFC 6585)

Since: 0.8.5

status500 :: Status Source #

Internal Server Error 500

internalServerError500 :: Status Source #

Internal Server Error 500

status501 :: Status Source #

Not Implemented 501

Since: 0.6.1

notImplemented501 :: Status Source #

Not Implemented 501

Since: 0.6.1

status502 :: Status Source #

Bad Gateway 502

Since: 0.6.6

badGateway502 :: Status Source #

Bad Gateway 502

Since: 0.6.6

status503 :: Status Source #

Service Unavailable 503

Since: 0.6.6

serviceUnavailable503 :: Status Source #

Service Unavailable 503

Since: 0.6.6

status504 :: Status Source #

Gateway Timeout 504

Since: 0.6.6

gatewayTimeout504 :: Status Source #

Gateway Timeout 504

Since: 0.6.6

status505 :: Status Source #

HTTP Version Not Supported 505

Since: 0.6.6

httpVersionNotSupported505 :: Status Source #

HTTP Version Not Supported 505

Since: 0.6.6

status511 :: Status Source #

Network Authentication Required 511 (RFC 6585)

Since: 0.8.5

networkAuthenticationRequired511 :: Status Source #

Network Authentication Required 511 (RFC 6585)

Since: 0.8.5

statusIsInformational :: Status -> Bool Source #

Informational class

Checks if the status is in the 1XX range.

Since: 0.8.0

statusIsSuccessful :: Status -> Bool Source #

Successful class

Checks if the status is in the 2XX range.

Since: 0.8.0

statusIsRedirection :: Status -> Bool Source #

Redirection class

Checks if the status is in the 3XX range.

Since: 0.8.0

statusIsClientError :: Status -> Bool Source #

Client Error class

Checks if the status is in the 4XX range.

Since: 0.8.0

statusIsServerError :: Status -> Bool Source #

Server Error class

Checks if the status is in the 5XX range.

Since: 0.8.0

Headers

For more information: Network.HTTP.Types.Header

Types

type Header = (HeaderName, ByteString) Source #

A full HTTP header field with the name and value separated.

E.g. "Content-Length: 28" parsed into a Header would turn into ("Content-Length", "28")

type HeaderName = CI ByteString Source #

A case-insensitive name of a header field.

This is the part of the header field before the colon: HeaderName: some value

type RequestHeaders = [Header] Source #

A list of Headers.

Same type as ResponseHeaders, but useful to differentiate in type signatures.

type ResponseHeaders = [Header] Source #

A list of Headers.

Same type as RequestHeaders, but useful to differentiate in type signatures.

Common headers

hContentMD5 :: HeaderName Source #

Content-MD5

This header has been obsoleted in RFC 9110.

Since: 0.7.0

hDate :: HeaderName Source #

Date

Since: 0.7.0

Byte ranges

data ByteRange Source #

An individual byte range.

Negative indices are not allowed!

Since: 0.6.11

Instances

Instances details
Data ByteRange Source #

Since: 0.8.4

Instance details

Defined in Network.HTTP.Types.Header

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ByteRange -> c ByteRange #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ByteRange #

toConstr :: ByteRange -> Constr #

dataTypeOf :: ByteRange -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ByteRange) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ByteRange) #

gmapT :: (forall b. Data b => b -> b) -> ByteRange -> ByteRange #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ByteRange -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ByteRange -> r #

gmapQ :: (forall d. Data d => d -> u) -> ByteRange -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ByteRange -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ByteRange -> m ByteRange #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ByteRange -> m ByteRange #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ByteRange -> m ByteRange #

Generic ByteRange Source # 
Instance details

Defined in Network.HTTP.Types.Header

Associated Types

type Rep ByteRange :: Type -> Type #

Show ByteRange Source #

Since: 0.8.4

Instance details

Defined in Network.HTTP.Types.Header

Eq ByteRange Source #

Since: 0.8.4

Instance details

Defined in Network.HTTP.Types.Header

Ord ByteRange Source #

Since: 0.8.4

Instance details

Defined in Network.HTTP.Types.Header

type Rep ByteRange Source #

Since: 0.12.4

Instance details

Defined in Network.HTTP.Types.Header

renderByteRangeBuilder :: ByteRange -> Builder Source #

Turns a byte range into a byte string Builder.

Since: 0.6.11

renderByteRange :: ByteRange -> ByteString Source #

Renders a byte range into a ByteString.

>>> renderByteRange (ByteRangeFrom 2048)
"2048-"

Since: 0.6.11

type ByteRanges = [ByteRange] Source #

A list of byte ranges.

Since: 0.6.11

renderByteRangesBuilder :: ByteRanges -> Builder Source #

Turns a list of byte ranges into a byte string Builder.

Since: 0.6.11

renderByteRanges :: ByteRanges -> ByteString Source #

Renders a list of byte ranges into a ByteString.

>>> renderByteRanges [ByteRangeFrom 2048, ByteRangeSuffix 20]
"bytes=2048-,-20"

Since: 0.6.11

parseByteRanges :: ByteString -> Maybe ByteRanges Source #

Parse the value of a Range header into a ByteRanges.

>>> parseByteRanges "error"
Nothing
>>> parseByteRanges "bytes=0-499"
Just [ByteRangeFromTo 0 499]
>>> parseByteRanges "bytes=500-999"
Just [ByteRangeFromTo 500 999]
>>> parseByteRanges "bytes=-500"
Just [ByteRangeSuffix 500]
>>> parseByteRanges "bytes=9500-"
Just [ByteRangeFrom 9500]
>>> parseByteRanges "bytes=0-0,-1"
Just [ByteRangeFromTo 0 0,ByteRangeSuffix 1]
>>> parseByteRanges "bytes=500-600,601-999"
Just [ByteRangeFromTo 500 600,ByteRangeFromTo 601 999]
>>> parseByteRanges "bytes=500-700,601-999"
Just [ByteRangeFromTo 500 700,ByteRangeFromTo 601 999]

Since: 0.9.1

URI

For more extensive information: Network.HTTP.Types.URI

Query strings

Query

type Query = [QueryItem] Source #

A sequence of QueryItems.

type QueryItem = (ByteString, Maybe ByteString) Source #

An item from the query string, split up into two parts.

The second part should be Nothing if there was no key-value separator after the query item name.

Since: 0.2.0

renderQuery :: Bool -> Query -> ByteString Source #

Renders the given Query into a ByteString.

If you want a question mark (?) added to the front of the result, use True.

Since: 0.2.0

renderQueryBuilder :: Bool -> Query -> Builder Source #

Renders the given Query into a Builder.

If you want a question mark (?) added to the front of the result, use True.

Since: 0.5

parseQuery :: ByteString -> Query Source #

Split out the query string into a list of keys and values. A few importants points:

  • The result returned is still bytestrings, since we perform no character decoding here. Most likely, you will want to use UTF-8 decoding, but this is left to the user of the library.
  • Percent decoding errors are ignored. In particular, "%Q" will be output as "%Q".
  • It decodes '+' characters to ' '

Since: 0.2.0

parseQueryReplacePlus :: Bool -> ByteString -> Query Source #

Same functionality as parseQuery, but with the option to decode '+' characters to ' ' or to preserve any '+' encountered.

If you want to replace any '+' with a space, use True.

Since: 0.12.2

Text query string (UTF8 encoded)

type QueryText = [(Text, Maybe Text)] Source #

Like Query, but with Text instead of ByteString (UTF8-encoded).

Since: 0.5.2

queryTextToQuery :: QueryText -> Query Source #

Convert QueryText to Query.

Since: 0.5.2

queryToQueryText :: Query -> QueryText Source #

Convert Query to QueryText (leniently decoding the UTF-8).

Since: 0.5.2

renderQueryText :: Bool -> QueryText -> Builder Source #

Convert QueryText to a Builder.

If you want a question mark (?) added to the front of the result, use True.

Since: 0.5.2

SimpleQuery

type SimpleQueryItem = (ByteString, ByteString) Source #

Simplified query item type without support for parameter-less items.

Since: 0.2.0

renderSimpleQuery :: Bool -> SimpleQuery -> ByteString Source #

Render the given SimpleQuery into a ByteString.

If you want a question mark (?) added to the front of the result, use True.

Since: 0.2.0

parseSimpleQuery :: ByteString -> SimpleQuery Source #

Parse SimpleQuery from a ByteString.

This uses parseQuery under the hood, and will transform any Nothing values into an empty ByteString.

Since: 0.2.0

PartialEscapeQuery

type PartialEscapeQuery = [PartialEscapeQueryItem] Source #

Query with some characters that should not be escaped.

General form: a=b&c=d:e+f&g=h

Since: 0.12.1

type PartialEscapeQueryItem = (ByteString, [EscapeItem]) Source #

Partially escaped query item.

The key will always be encoded using 'urlEncode True', but the value will be encoded depending on which EscapeItems are used.

Since: 0.12.1

data EscapeItem Source #

Section of a query item value that decides whether to use regular URL encoding (using 'urlEncode True') with QE, or to not encode anything with QN.

Since: 0.12.1

Constructors

QE ByteString

will be URL encoded

QN ByteString

will NOT at all be URL encoded

renderQueryPartialEscape :: Bool -> PartialEscapeQuery -> ByteString Source #

Convert PartialEscapeQuery to ByteString.

If you want a question mark (?) added to the front of the result, use True.

>>> renderQueryPartialEscape True [("a", [QN "x:z + ", QE (encodeUtf8 "They said: \"שלום\"")])]
"?a=x:z + They%20said%3A%20%22%D7%A9%D7%9C%D7%95%D7%9D%22"

Since: 0.12.1

renderQueryBuilderPartialEscape :: Bool -> PartialEscapeQuery -> Builder Source #

Convert a PartialEscapeQuery to a Builder.

If you want a question mark (?) added to the front of the result, use True.

Since: 0.12.1

Generalized query types

class QueryLike a where Source #

Types which can, and commonly are, converted to Query are in this class.

You can use lists of simple key value pairs, with ByteString (strict, or lazy: ByteString), Text, or String as the key/value types. You can also have the value type lifted into a Maybe to support keys without values; and finally it is possible to put each pair into a Maybe for key-value pairs that aren't always present.

Since: 0.7.0

Methods

toQuery :: a -> Query Source #

Convert to Query.

Instances

Instances details
(QueryKeyLike k, QueryValueLike v) => QueryLike [Maybe (k, v)] Source # 
Instance details

Defined in Network.HTTP.Types.QueryLike

Methods

toQuery :: [Maybe (k, v)] -> Query Source #

(QueryKeyLike k, QueryValueLike v) => QueryLike [(k, v)] Source # 
Instance details

Defined in Network.HTTP.Types.QueryLike

Methods

toQuery :: [(k, v)] -> Query Source #

Path

Segments + Query String

extractPath :: ByteString -> ByteString Source #

Extract whole path (path segments + query) from a RFC 2616 Request-URI.

Though a more accurate description of this function's behaviour is that it removes the domain/origin if the string starts with an HTTP protocol. (i.e. http:// or https://)

This function will not change anything when given any other ByteString. (except return a root path "/" if given an empty string)

>>> extractPath "/path"
"/path"
>>> extractPath "http://example.com:8080/path"
"/path"
>>> extractPath "http://example.com"
"/"
>>> extractPath ""
"/"
>>> extractPath "www.google.com/some/path"
"www.google.com/some/path"

Since: 0.8.5

encodePath :: [Text] -> Query -> Builder Source #

Encode a whole path (path segments + query).

Since: 0.5

decodePath :: ByteString -> ([Text], Query) Source #

Decode a whole path (path segments + query).

Since: 0.5

Path Segments

encodePathSegments :: [Text] -> Builder Source #

Encodes a list of path segments into a valid URL fragment.

This function takes the following three steps:

  • UTF-8 encodes the characters.
  • Prepends each segment with a slash.
  • Performs percent-encoding on all characters that are not:

    • alphanumeric (i.e. A-Z and a-z)
    • digits (i.e. 0-9)
    • a dash '-', an underscore '_', a dot '.', or a tilde '~'

For example:

>>> encodePathSegments ["foo", "bar1", "~baz"]
"/foo/bar1/~baz"
>>> encodePathSegments ["foo bar", "baz/bin"]
"/foo%20bar/baz%2Fbin"
>>> encodePathSegments ["שלום"]
"/%D7%A9%D7%9C%D7%95%D7%9D"

Huge thanks to Jeremy Shaw who created the original implementation of this function in web-routes and did such thorough research to determine all correct escaping procedures.

Since: 0.5

encodePathSegmentsRelative :: [Text] -> Builder Source #

Like encodePathSegments, but without the initial slash.

Since: 0.6.10

decodePathSegments :: ByteString -> [Text] Source #

Parse a list of path segments from a valid URL fragment.

Will also decode any percent-encoded characters.

Since: 0.5

URL encoding / decoding

urlEncode :: Bool -> ByteString -> ByteString Source #

Percent-encoding for URLs.

In short:

  • if you're encoding (parts of) a path element, use False.
  • if you're encoding (parts of) a query string, use True.

In-depth explanation

Expand

This will substitute every byte with its percent-encoded equivalent unless:

  • The byte is alphanumeric. (i.e. A-Z, a-z, or 0-9)
  • The byte is either a dash '-', an underscore '_', a dot '.', or a tilde '~'
  • If False is used, the following will also not be percent-encoded:

    • colon ':', at sign '@', ampersand '&', equals sign '=', plus sign '+', dollar sign '$' or a comma ','

Since: 0.2.0

urlEncodeBuilder :: Bool -> ByteString -> Builder Source #

Percent-encoding for URLs.

Like urlEncode, but only makes the Builder.

Since: 0.5

urlDecode :: Bool -> ByteString -> ByteString Source #

Percent-decoding.

If you want to replace any '+' with a space, use True.

Since: 0.2.0