porpoise-0.1.0.0: A minimalist HTTP server framework written on top of wai

Copyright(c) Samuel Schlesinger 2020
LicenseMIT
Maintainersgschlesinger@gmail.com
Stabilityexperimental
PortabilityPOSIX, Windows
Safe HaskellNone
LanguageHaskell2010

Web.Porpoise

Contents

Description

A very minimal HTTP server framework wrapping wai.

Synopsis

Server Language

newtype Server m request response Source #

A server application which receives a request and responds.

Constructors

Server 

Fields

Instances
Functor m => Profunctor (Server m) Source # 
Instance details

Defined in Web.Porpoise

Methods

dimap :: (a -> b) -> (c -> d) -> Server m b c -> Server m a d #

lmap :: (a -> b) -> Server m b c -> Server m a c #

rmap :: (b -> c) -> Server m a b -> Server m a c #

(#.) :: Coercible c b => q b c -> Server m a b -> Server m a c #

(.#) :: Coercible b a => Server m b c -> q a b -> Server m a c #

Monad m => Category (Server m :: Type -> Type -> Type) Source # 
Instance details

Defined in Web.Porpoise

Methods

id :: Server m a a #

(.) :: Server m b c -> Server m a b -> Server m a c #

Monad (Server m request) Source # 
Instance details

Defined in Web.Porpoise

Methods

(>>=) :: Server m request a -> (a -> Server m request b) -> Server m request b #

(>>) :: Server m request a -> Server m request b -> Server m request b #

return :: a -> Server m request a #

fail :: String -> Server m request a #

Functor (Server m request) Source # 
Instance details

Defined in Web.Porpoise

Methods

fmap :: (a -> b) -> Server m request a -> Server m request b #

(<$) :: a -> Server m request b -> Server m request a #

MonadFail m => MonadFail (Server m request) Source # 
Instance details

Defined in Web.Porpoise

Methods

fail :: String -> Server m request a #

Applicative (Server m request) Source # 
Instance details

Defined in Web.Porpoise

Methods

pure :: a -> Server m request a #

(<*>) :: Server m request (a -> b) -> Server m request a -> Server m request b #

liftA2 :: (a -> b -> c) -> Server m request a -> Server m request b -> Server m request c #

(*>) :: Server m request a -> Server m request b -> Server m request b #

(<*) :: Server m request a -> Server m request b -> Server m request a #

MonadIO m => MonadIO (Server m request) Source # 
Instance details

Defined in Web.Porpoise

Methods

liftIO :: IO a -> Server m request a #

MonadCont (Server m request) Source # 
Instance details

Defined in Web.Porpoise

Methods

callCC :: ((a -> Server m request b) -> Server m request a) -> Server m request a #

toApplication :: Server IO Request Response -> Application Source #

Compile a Server a runnable wai application.

liftS :: Monad m => m response -> Server m request response Source #

Lift a computation from the base monad into the Server monad. This is provided because this library prefers to use the second to last type variable position for the contravariant component in the Profunctor instance, and so we are able to write a Category instance.

serverIO :: MonadUnliftIO m => m (Server m request response -> Server IO request response) Source #

In any monad that has an instance of MonadUnliftIO, we can retrieve a function allowing our Server to operate in IO. The resulting function is expected to be used to transform the Server prior to calling toApplication.

class Profunctor (p :: Type -> Type -> Type) where #

Formally, the class Profunctor represents a profunctor from Hask -> Hask.

Intuitively it is a bifunctor where the first argument is contravariant and the second argument is covariant.

You can define a Profunctor by either defining dimap or by defining both lmap and rmap.

If you supply dimap, you should ensure that:

dimap id idid

If you supply lmap and rmap, ensure:

lmap idid
rmap idid

If you supply both, you should also ensure:

dimap f g ≡ lmap f . rmap g

These ensure by parametricity:

dimap (f . g) (h . i) ≡ dimap g h . dimap f i
lmap (f . g) ≡ lmap g . lmap f
rmap (f . g) ≡ rmap f . rmap g

Minimal complete definition

dimap | lmap, rmap

Methods

dimap :: (a -> b) -> (c -> d) -> p b c -> p a d #

Map over both arguments at the same time.

dimap f g ≡ lmap f . rmap g

lmap :: (a -> b) -> p b c -> p a c #

Map the first argument contravariantly.

lmap f ≡ dimap f id

rmap :: (b -> c) -> p a b -> p a c #

Map the second argument covariantly.

rmapdimap id
Instances
Monad m => Profunctor (Kleisli m) 
Instance details

Defined in Data.Profunctor.Unsafe

Methods

dimap :: (a -> b) -> (c -> d) -> Kleisli m b c -> Kleisli m a d #

lmap :: (a -> b) -> Kleisli m b c -> Kleisli m a c #

rmap :: (b -> c) -> Kleisli m a b -> Kleisli m a c #

(#.) :: Coercible c b => q b c -> Kleisli m a b -> Kleisli m a c #

(.#) :: Coercible b a => Kleisli m b c -> q a b -> Kleisli m a c #

Profunctor (Tagged :: Type -> Type -> Type) 
Instance details

Defined in Data.Profunctor.Unsafe

Methods

dimap :: (a -> b) -> (c -> d) -> Tagged b c -> Tagged a d #

lmap :: (a -> b) -> Tagged b c -> Tagged a c #

rmap :: (b -> c) -> Tagged a b -> Tagged a c #

(#.) :: Coercible c b => q b c -> Tagged a b -> Tagged a c #

(.#) :: Coercible b a => Tagged b c -> q a b -> Tagged a c #

Functor m => Profunctor (Server m) Source # 
Instance details

Defined in Web.Porpoise

Methods

dimap :: (a -> b) -> (c -> d) -> Server m b c -> Server m a d #

lmap :: (a -> b) -> Server m b c -> Server m a c #

rmap :: (b -> c) -> Server m a b -> Server m a c #

(#.) :: Coercible c b => q b c -> Server m a b -> Server m a c #

(.#) :: Coercible b a => Server m b c -> q a b -> Server m a c #

Profunctor ((->) :: Type -> Type -> Type) 
Instance details

Defined in Data.Profunctor.Unsafe

Methods

dimap :: (a -> b) -> (c -> d) -> (b -> c) -> a -> d #

lmap :: (a -> b) -> (b -> c) -> a -> c #

rmap :: (b -> c) -> (a -> b) -> a -> c #

(#.) :: Coercible c b => q b c -> (a -> b) -> a -> c #

(.#) :: Coercible b a => (b -> c) -> q a b -> a -> c #

Functor w => Profunctor (Cokleisli w) 
Instance details

Defined in Data.Profunctor.Unsafe

Methods

dimap :: (a -> b) -> (c -> d) -> Cokleisli w b c -> Cokleisli w a d #

lmap :: (a -> b) -> Cokleisli w b c -> Cokleisli w a c #

rmap :: (b -> c) -> Cokleisli w a b -> Cokleisli w a c #

(#.) :: Coercible c b => q b c -> Cokleisli w a b -> Cokleisli w a c #

(.#) :: Coercible b a => Cokleisli w b c -> q a b -> Cokleisli w a c #

Functor f => Profunctor (Joker f :: Type -> Type -> Type) 
Instance details

Defined in Data.Profunctor.Unsafe

Methods

dimap :: (a -> b) -> (c -> d) -> Joker f b c -> Joker f a d #

lmap :: (a -> b) -> Joker f b c -> Joker f a c #

rmap :: (b -> c) -> Joker f a b -> Joker f a c #

(#.) :: Coercible c b => q b c -> Joker f a b -> Joker f a c #

(.#) :: Coercible b a => Joker f b c -> q a b -> Joker f a c #

Contravariant f => Profunctor (Clown f :: Type -> Type -> Type) 
Instance details

Defined in Data.Profunctor.Unsafe

Methods

dimap :: (a -> b) -> (c -> d) -> Clown f b c -> Clown f a d #

lmap :: (a -> b) -> Clown f b c -> Clown f a c #

rmap :: (b -> c) -> Clown f a b -> Clown f a c #

(#.) :: Coercible c b => q b c -> Clown f a b -> Clown f a c #

(.#) :: Coercible b a => Clown f b c -> q a b -> Clown f a c #

(Profunctor p, Profunctor q) => Profunctor (Sum p q) 
Instance details

Defined in Data.Profunctor.Unsafe

Methods

dimap :: (a -> b) -> (c -> d) -> Sum p q b c -> Sum p q a d #

lmap :: (a -> b) -> Sum p q b c -> Sum p q a c #

rmap :: (b -> c) -> Sum p q a b -> Sum p q a c #

(#.) :: Coercible c b => q0 b c -> Sum p q a b -> Sum p q a c #

(.#) :: Coercible b a => Sum p q b c -> q0 a b -> Sum p q a c #

(Profunctor p, Profunctor q) => Profunctor (Product p q) 
Instance details

Defined in Data.Profunctor.Unsafe

Methods

dimap :: (a -> b) -> (c -> d) -> Product p q b c -> Product p q a d #

lmap :: (a -> b) -> Product p q b c -> Product p q a c #

rmap :: (b -> c) -> Product p q a b -> Product p q a c #

(#.) :: Coercible c b => q0 b c -> Product p q a b -> Product p q a c #

(.#) :: Coercible b a => Product p q b c -> q0 a b -> Product p q a c #

(Functor f, Profunctor p) => Profunctor (Tannen f p) 
Instance details

Defined in Data.Profunctor.Unsafe

Methods

dimap :: (a -> b) -> (c -> d) -> Tannen f p b c -> Tannen f p a d #

lmap :: (a -> b) -> Tannen f p b c -> Tannen f p a c #

rmap :: (b -> c) -> Tannen f p a b -> Tannen f p a c #

(#.) :: Coercible c b => q b c -> Tannen f p a b -> Tannen f p a c #

(.#) :: Coercible b a => Tannen f p b c -> q a b -> Tannen f p a c #

(Profunctor p, Functor f, Functor g) => Profunctor (Biff p f g) 
Instance details

Defined in Data.Profunctor.Unsafe

Methods

dimap :: (a -> b) -> (c -> d) -> Biff p f g b c -> Biff p f g a d #

lmap :: (a -> b) -> Biff p f g b c -> Biff p f g a c #

rmap :: (b -> c) -> Biff p f g a b -> Biff p f g a c #

(#.) :: Coercible c b => q b c -> Biff p f g a b -> Biff p f g a c #

(.#) :: Coercible b a => Biff p f g b c -> q a b -> Biff p f g a c #

class Category (cat :: k -> k -> Type) where #

A class for categories. Instances should satisfy the laws

f . id  =  f  -- (right identity)
id . f  =  f  -- (left identity)
f . (g . h)  =  (f . g) . h  -- (associativity)

Methods

id :: cat a a #

the identity morphism

(.) :: cat b c -> cat a b -> cat a c infixr 9 #

morphism composition

Instances
Category (Coercion :: k -> k -> Type)

Since: base-4.7.0.0

Instance details

Defined in Control.Category

Methods

id :: Coercion a a #

(.) :: Coercion b c -> Coercion a b -> Coercion a c #

Category ((:~:) :: k -> k -> Type)

Since: base-4.7.0.0

Instance details

Defined in Control.Category

Methods

id :: a :~: a #

(.) :: (b :~: c) -> (a :~: b) -> a :~: c #

Category ((:~~:) :: k -> k -> Type)

Since: base-4.10.0.0

Instance details

Defined in Control.Category

Methods

id :: a :~~: a #

(.) :: (b :~~: c) -> (a :~~: b) -> a :~~: c #

(Category p, Category q) => Category (Product p q :: k -> k -> Type) 
Instance details

Defined in Data.Bifunctor.Product

Methods

id :: Product p q a a #

(.) :: Product p q b c -> Product p q a b -> Product p q a c #

(Applicative f, Category p) => Category (Tannen f p :: k -> k -> Type) 
Instance details

Defined in Data.Bifunctor.Tannen

Methods

id :: Tannen f p a a #

(.) :: Tannen f p b c -> Tannen f p a b -> Tannen f p a c #

Monad m => Category (Kleisli m :: Type -> Type -> Type)

Since: base-3.0

Instance details

Defined in Control.Arrow

Methods

id :: Kleisli m a a #

(.) :: Kleisli m b c -> Kleisli m a b -> Kleisli m a c #

(Applicative f, Monad f) => Category (WhenMissing f :: Type -> Type -> Type)

Since: containers-0.5.9

Instance details

Defined in Data.IntMap.Internal

Methods

id :: WhenMissing f a a #

(.) :: WhenMissing f b c -> WhenMissing f a b -> WhenMissing f a c #

Monad m => Category (Server m :: Type -> Type -> Type) Source # 
Instance details

Defined in Web.Porpoise

Methods

id :: Server m a a #

(.) :: Server m b c -> Server m a b -> Server m a c #

Category ((->) :: Type -> Type -> Type)

Since: base-3.0

Instance details

Defined in Control.Category

Methods

id :: a -> a #

(.) :: (b -> c) -> (a -> b) -> a -> c #

(Monad f, Applicative f) => Category (WhenMatched f x :: Type -> Type -> Type)

Since: containers-0.5.9

Instance details

Defined in Data.IntMap.Internal

Methods

id :: WhenMatched f x a a #

(.) :: WhenMatched f x b c -> WhenMatched f x a b -> WhenMatched f x a c #

(Applicative f, Monad f) => Category (WhenMissing f k :: Type -> Type -> Type)

Since: containers-0.5.9

Instance details

Defined in Data.Map.Internal

Methods

id :: WhenMissing f k a a #

(.) :: WhenMissing f k b c -> WhenMissing f k a b -> WhenMissing f k a c #

(Monad f, Applicative f) => Category (WhenMatched f k x :: Type -> Type -> Type)

Since: containers-0.5.9

Instance details

Defined in Data.Map.Internal

Methods

id :: WhenMatched f k x a a #

(.) :: WhenMatched f k x b c -> WhenMatched f k x a b -> WhenMatched f k x a c #

class MonadIO m => MonadUnliftIO (m :: Type -> Type) where #

Monads which allow their actions to be run in IO.

While MonadIO allows an IO action to be lifted into another monad, this class captures the opposite concept: allowing you to capture the monadic context. Note that, in order to meet the laws given below, the intuition is that a monad must have no monadic state, but may have monadic context. This essentially limits MonadUnliftIO to ReaderT and IdentityT transformers on top of IO.

Laws. For any value u returned by askUnliftIO, it must meet the monad transformer laws as reformulated for MonadUnliftIO:

  • unliftIO u . return = return
  • unliftIO u (m >>= f) = unliftIO u m >>= unliftIO u . f

Instances of MonadUnliftIO must also satisfy the idempotency law:

  • askUnliftIO >>= \u -> (liftIO . unliftIO u) m = m

This law showcases two properties. First, askUnliftIO doesn't change the monadic context, and second, liftIO . unliftIO u is equivalent to id IF called in the same monadic context as askUnliftIO.

Since: unliftio-core-0.1.0.0

Methods

withRunInIO :: ((forall a. m a -> IO a) -> IO b) -> m b #

Convenience function for capturing the monadic context and running an IO action with a runner function. The runner function is used to run a monadic action m in IO.

Since: unliftio-core-0.1.0.0

Instances
MonadUnliftIO IO 
Instance details

Defined in Control.Monad.IO.Unlift

Methods

withRunInIO :: ((forall a. IO a -> IO a) -> IO b) -> IO b #

MonadUnliftIO m => MonadUnliftIO (IdentityT m) 
Instance details

Defined in Control.Monad.IO.Unlift

Methods

withRunInIO :: ((forall a. IdentityT m a -> IO a) -> IO b) -> IdentityT m b #

MonadUnliftIO m => MonadUnliftIO (ReaderT r m) 
Instance details

Defined in Control.Monad.IO.Unlift

Methods

withRunInIO :: ((forall a. ReaderT r m a -> IO a) -> IO b) -> ReaderT r m b #

data ResponseReceived #

A special datatype to indicate that the WAI handler has received the response. This is to avoid the need for Rank2Types in the definition of Application.

It is highly advised that only WAI handlers import and use the data constructor for this data type.

Since 3.0.0

type Application = Request -> (Response -> IO ResponseReceived) -> IO ResponseReceived #

The WAI application.

Note that, since WAI 3.0, this type is structured in continuation passing style to allow for proper safe resource handling. This was handled in the past via other means (e.g., ResourceT). As a demonstration:

app :: Application
app req respond = bracket_
    (putStrLn "Allocating scarce resource")
    (putStrLn "Cleaning up")
    (respond $ responseLBS status200 [] "Hello World")

Observing a Request

data Request #

Information on the request sent by the client. This abstracts away the details of the underlying implementation.

Instances
Show Request 
Instance details

Defined in Network.Wai.Internal

requestMethod :: Request -> Method #

Request method such as GET.

httpVersion :: Request -> HttpVersion #

HTTP version such as 1.1.

rawPathInfo :: Request -> ByteString #

Extra path information sent by the client. The meaning varies slightly depending on backend; in a standalone server setting, this is most likely all information after the domain name. In a CGI application, this would be the information following the path to the CGI executable itself.

Middlewares and routing tools should not modify this raw value, as it may be used for such things as creating redirect destinations by applications. Instead, if you are writing a middleware or routing framework, modify the pathInfo instead. This is the approach taken by systems like Yesod subsites.

Note: At the time of writing this documentation, there is at least one system (Network.Wai.UrlMap from wai-extra) that does not follow the above recommendation. Therefore, it is recommended that you test the behavior of your application when using rawPathInfo and any form of library that might modify the Request.

rawQueryString :: Request -> ByteString #

If no query string was specified, this should be empty. This value will include the leading question mark. Do not modify this raw value - modify queryString instead.

requestHeaders :: Request -> RequestHeaders #

A list of headers (a pair of key and value) in an HTTP request.

isSecure :: Request -> Bool #

Was this request made over an SSL connection?

Note that this value will not tell you if the client originally made this request over SSL, but rather whether the current connection is SSL. The distinction lies with reverse proxies. In many cases, the client will connect to a load balancer over SSL, but connect to the WAI handler without SSL. In such a case, isSecure will be False, but from a user perspective, there is a secure connection.

remoteHost :: Request -> SockAddr #

The client's host information.

pathInfo :: Request -> [Text] #

Path info in individual pieces - the URL without a hostname/port and without a query string, split on forward slashes.

queryString :: Request -> Query #

Parsed query string information.

getRequestBodyChunk :: Request -> IO ByteString #

Get the next chunk of the body. Returns empty when the body is fully consumed.

Since: wai-3.2.2

vault :: Request -> Vault #

A location for arbitrary data to be shared by applications and middleware.

requestBodyLength :: Request -> RequestBodyLength #

The size of the request body. In the case of a chunked request body, this may be unknown.

Since 1.4.0

requestHeaderHost :: Request -> Maybe ByteString #

The value of the Host header in a HTTP request.

Since 2.0.0

requestHeaderRange :: Request -> Maybe ByteString #

The value of the Range header in a HTTP request.

Since 2.0.0

requestHeaderReferer :: Request -> Maybe ByteString #

The value of the Referer header in a HTTP request.

Since 3.2.0

requestHeaderUserAgent :: Request -> Maybe ByteString #

The value of the User-Agent header in a HTTP request.

Since 3.2.0

strictRequestBody :: Request -> IO ByteString #

Get the request body as a lazy ByteString. However, do not use any lazy I/O, instead reading the entire body into memory strictly.

Since 3.0.1

lazyRequestBody :: Request -> IO ByteString #

Get the request body as a lazy ByteString. This uses lazy I/O under the surface, and therefore all typical warnings regarding lazy I/O apply.

Since 1.4.1

data RequestBodyLength #

The size of the request body. In the case of chunked bodies, the size will not be known.

Since 1.4.0

Building a Response

data Response #

data FilePart #

Information on which part to be sent. Sophisticated application handles Range (and If-Range) then create FilePart.

Instances
Show FilePart 
Instance details

Defined in Network.Wai.Internal

responseLBS :: Status -> ResponseHeaders -> ByteString -> Response #

Creating Response from ByteString. This is a wrapper for responseBuilder.

responseStream :: Status -> ResponseHeaders -> StreamingBody -> Response #

Creating Response from a stream of values.

In order to allocate resources in an exception-safe manner, you can use the bracket pattern outside of the call to responseStream. As a trivial example:

app :: Application
app req respond = bracket_
    (putStrLn "Allocating scarce resource")
    (putStrLn "Cleaning up")
    $ respond $ responseStream status200 [] $ \write flush -> do
        write $ byteString "Hello\n"
        flush
        write $ byteString "World\n"

Note that in some cases you can use bracket from inside responseStream as well. However, placing the call on the outside allows your status value and response headers to depend on the scarce resource.

Since 3.0.0

responseRaw :: (IO ByteString -> (ByteString -> IO ()) -> IO ()) -> Response -> Response #

Create a response for a raw application. This is useful for "upgrade" situations such as WebSockets, where an application requests for the server to grant it raw network access.

This function requires a backup response to be provided, for the case where the handler in question does not support such upgrading (e.g., CGI apps).

In the event that you read from the request body before returning a responseRaw, behavior is undefined.

Since 2.1.0

responseBuilder :: Status -> ResponseHeaders -> Builder -> Response #

Creating Response from Builder.

Some questions and answers about the usage of Builder here:

Q1. Shouldn't it be at the user's discretion to use Builders internally and then create a stream of ByteStrings?

A1. That would be less efficient, as we wouldn't get cheap concatenation with the response headers.

Q2. Isn't it really inefficient to convert from ByteString to Builder, and then right back to ByteString?

A2. No. If the ByteStrings are small, then they will be copied into a larger buffer, which should be a performance gain overall (less system calls). If they are already large, then an insert operation is used to avoid copying.

Q3. Doesn't this prevent us from creating comet-style servers, since data will be cached?

A3. You can force a Builder to output a ByteString before it is an optimal size by sending a flush command.

type StreamingBody = (Builder -> IO ()) -> IO () -> IO () #

Represents a streaming HTTP response body. It's a function of two parameters; the first parameter provides a means of sending another chunk of data, and the second parameter provides a means of flushing the data to the client.

Since 3.0.0

Miscellaneous re-exports

data Status #

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.

Instances
Bounded Status 
Instance details

Defined in Network.HTTP.Types.Status

Enum Status 
Instance details

Defined in Network.HTTP.Types.Status

Eq Status 
Instance details

Defined in Network.HTTP.Types.Status

Methods

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

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

Ord Status 
Instance details

Defined in Network.HTTP.Types.Status

Show Status 
Instance details

Defined in Network.HTTP.Types.Status

mkStatus :: Int -> ByteString -> Status #

Create a Status from status code and message.

type Header = (HeaderName, ByteString) #

Header

type HeaderName = CI ByteString #

Header name

type ResponseHeaders = [Header] #

Response Headers

type RequestHeaders = [Header] #

Request Headers

hOrigin :: HeaderName #

HTTP Header names according to https://tools.ietf.org/html/rfc6454

hPrefer :: HeaderName #

HTTP Header names according to https://tools.ietf.org/html/rfc7240

data ByteRange #

RFC 2616 Byte range (individual).

Negative indices are not allowed!

Instances
Eq ByteRange 
Instance details

Defined in Network.HTTP.Types.Header

Data ByteRange 
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 :: (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 #

Ord ByteRange 
Instance details

Defined in Network.HTTP.Types.Header

Show ByteRange 
Instance details

Defined in Network.HTTP.Types.Header

type ByteRanges = [ByteRange] #

RFC 2616 Byte ranges (set).

parseByteRanges :: ByteString -> Maybe ByteRanges #

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]

data HttpVersion #

HTTP Version.

Note that the Show instance is intended merely for debugging.

Constructors

HttpVersion 

Fields

http09 :: HttpVersion #

HTTP 0.9

http10 :: HttpVersion #

HTTP 1.0

http11 :: HttpVersion #

HTTP 1.1

http20 :: HttpVersion #

HTTP 2.0

type Method = ByteString #

HTTP method (flat string type).

methodGet :: Method #

HTTP Method constants.

methodPost :: Method #

HTTP Method constants.

methodHead :: Method #

HTTP Method constants.

methodPut :: Method #

HTTP Method constants.

methodDelete :: Method #

HTTP Method constants.

methodTrace :: Method #

HTTP Method constants.

methodConnect :: Method #

HTTP Method constants.

methodOptions :: Method #

HTTP Method constants.

methodPatch :: Method #

HTTP Method constants.

data StdMethod #

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

Constructors

GET 
POST 
HEAD 
PUT 
DELETE 
TRACE 
CONNECT 
OPTIONS 
PATCH 
Instances
Bounded StdMethod 
Instance details

Defined in Network.HTTP.Types.Method

Enum StdMethod 
Instance details

Defined in Network.HTTP.Types.Method

Eq StdMethod 
Instance details

Defined in Network.HTTP.Types.Method

Ord StdMethod 
Instance details

Defined in Network.HTTP.Types.Method

Read StdMethod 
Instance details

Defined in Network.HTTP.Types.Method

Show StdMethod 
Instance details

Defined in Network.HTTP.Types.Method

Ix StdMethod 
Instance details

Defined in Network.HTTP.Types.Method

parseMethod :: Method -> Either ByteString StdMethod #

Convert a method ByteString to a StdMethod if possible.

renderMethod :: Either ByteString StdMethod -> Method #

Convert an algebraic method to a ByteString.

renderStdMethod :: StdMethod -> Method #

Convert a StdMethod to a ByteString.

type QueryItem = (ByteString, Maybe ByteString) #

Query item

type Query = [QueryItem] #

Query.

General form: a=b&c=d, but if the value is Nothing, it becomes a&c=d.

urlEncode #

Arguments

:: Bool

Whether to decode '+' to ' '

-> ByteString

The ByteString to encode as URL

-> ByteString

The encoded URL

Percent-encoding for URLs.

urlDecode #

Arguments

:: Bool

Whether to decode '+' to ' '

-> ByteString 
-> ByteString 

Percent-decoding.

urlEncodeBuilder #

Arguments

:: Bool

Whether input is in query string. True: Query string, False: Path element

-> ByteString 
-> Builder 

Percent-encoding for URLs (using Builder).

extractPath :: ByteString -> ByteString #

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

>>> extractPath "/path"
"/path"
>>> extractPath "http://example.com:8080/path"
"/path"
>>> extractPath "http://example.com"
"/"
>>> extractPath ""
"/"

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

Decode a whole path (path segments + query).

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

Encode a whole path (path segments + query).

data SockAddr #

Socket addresses. The existence of a constructor does not necessarily imply that that socket address type is supported on your system: see isSupportedSockAddr.

Instances
Eq SockAddr 
Instance details

Defined in Network.Socket.Types

Ord SockAddr 
Instance details

Defined in Network.Socket.Types

NFData SockAddr 
Instance details

Defined in Network.Socket.Types

Methods

rnf :: SockAddr -> () #

SocketAddress SockAddr 
Instance details

Defined in Network.Socket.Types

type Vault = Vault RealWorld #

A persistent store for values of arbitrary types.

This variant is the simplest and creates keys in the IO monad. See the module Data.Vault.ST if you want to use it with the ST monad instead.