webgear-server-0.1.0: Composable, type-safe library to build HTTP API servers
Copyright(c) Raghu Kaippully 2020
LicenseMPL-2.0
Maintainerrkaippully@gmail.com
Safe HaskellNone
LanguageHaskell2010

WebGear.Types

Description

Common types and functions used throughout WebGear.

Synopsis

WebGear Request

WebGear requests are WAI requests. This module reexports a number of useful functions that operate on requests from Network.Wai module.

data Request #

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

Instances

Instances details
Show Request 
Instance details

Defined in Network.Wai.Internal

(Monad m, IsStdMethod t) => Trait (Method t :: Type) Request m Source # 
Instance details

Defined in WebGear.Trait.Method

Associated Types

type Val (Method t) Request Source #

type Fail (Method t) Request Source #

(KnownSymbol s, Monad m) => Trait (Path s :: Type) Request m Source # 
Instance details

Defined in WebGear.Trait.Path

Associated Types

type Val (Path s) Request Source #

type Fail (Path s) Request Source #

(FromJSON t, MonadIO m) => Trait (JSONRequestBody t :: Type) Request m Source # 
Instance details

Defined in WebGear.Trait.Body

(KnownSymbol s, KnownSymbol t, Monad m) => Trait (HeaderMatch s t :: Type) Request m Source # 
Instance details

Defined in WebGear.Trait.Header

Associated Types

type Val (HeaderMatch s t) Request Source #

type Fail (HeaderMatch s t) Request Source #

(KnownSymbol s, FromHttpApiData t, Monad m) => Trait (Header s t :: Type) Request m Source # 
Instance details

Defined in WebGear.Trait.Header

Associated Types

type Val (Header s t) Request Source #

type Fail (Header s t) Request Source #

Methods

check :: Request -> m (CheckResult (Header s t) Request) Source #

(FromHttpApiData val, Monad m) => Trait (PathVar tag val :: Type) Request m Source # 
Instance details

Defined in WebGear.Trait.Path

Associated Types

type Val (PathVar tag val) Request Source #

type Fail (PathVar tag val) Request Source #

Methods

check :: Request -> m (CheckResult (PathVar tag val) Request) Source #

type Val (Method t :: Type) Request Source # 
Instance details

Defined in WebGear.Trait.Method

type Val (Method t :: Type) Request = Method
type Val (Path s :: Type) Request Source # 
Instance details

Defined in WebGear.Trait.Path

type Val (Path s :: Type) Request = ()
type Val (JSONRequestBody t :: Type) Request Source # 
Instance details

Defined in WebGear.Trait.Body

type Fail (Method t :: Type) Request Source # 
Instance details

Defined in WebGear.Trait.Method

type Fail (Path s :: Type) Request Source # 
Instance details

Defined in WebGear.Trait.Path

type Fail (Path s :: Type) Request = ()
type Fail (JSONRequestBody t :: Type) Request Source # 
Instance details

Defined in WebGear.Trait.Body

type Val (HeaderMatch s t :: Type) Request Source # 
Instance details

Defined in WebGear.Trait.Header

type Val (Header s t :: Type) Request Source # 
Instance details

Defined in WebGear.Trait.Header

type Val (Header s t :: Type) Request = t
type Fail (HeaderMatch s t :: Type) Request Source # 
Instance details

Defined in WebGear.Trait.Header

type Fail (Header s t :: Type) Request Source # 
Instance details

Defined in WebGear.Trait.Header

type Val (PathVar tag val :: Type) Request Source # 
Instance details

Defined in WebGear.Trait.Path

type Val (PathVar tag val :: Type) Request = val
type Fail (PathVar tag val :: Type) Request Source # 
Instance details

Defined in WebGear.Trait.Path

type Fail (PathVar tag val :: Type) Request = PathVarFail

remoteHost :: Request -> SockAddr #

The client's host information.

httpVersion :: Request -> HttpVersion #

HTTP version such as 1.1.

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.

requestMethod :: Request -> Method #

Request method such as GET.

pathInfo :: Request -> [Text] #

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

setPathInfo :: [Text] -> Request -> Request Source #

Get request with an updated URL path info.

queryString :: Request -> Query #

Parsed query string information.

requestHeaders :: Request -> RequestHeaders #

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

requestHeader :: HeaderName -> Request -> Maybe ByteString Source #

Get the value of a request header

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

getRequestBodyChunk :: Request -> IO ByteString #

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

Since: wai-3.2.2

WebGear Response

data Response a Source #

A response sent from the server to the client.

The response contains a status, optional headers and an optional body of type a.

Constructors

Response 

Fields

Instances

Instances details
Monad m => MonadRouter (RouterT m) Source # 
Instance details

Defined in WebGear.Route

waiResponse :: Response ByteString -> Response Source #

Convert a WebGear response to a WAI Response.

addResponseHeader :: Header -> Response a -> Response a Source #

Create or update a response header.

type Handler m req res a = Kleisli m (Linked req Request) (Linked res (Response a)) Source #

A handler is a function from a request to response in a monadic context. Both the request and the response can have linked traits.

The type level list req contains all the traits expected to be present in the request. The handler will produce a response that satisfies all the traits in the type level list res.

type Middleware m req req' res' res a' a = Handler m req' res' a' -> Handler m req res a Source #

A middleware takes a handler as input and produces another handler that usually adds some functionality.

A middleware can do a number of things with the request handling such as:

  • Change the request traits before invoking the handler.
  • Change the response traits before passing it back to its caller.
  • Use the linked value of any of the request or response traits.
  • Change the response body.

type RequestMiddleware m req req' res a = Middleware m req req' res res a a Source #

A middleware that manipulates only the request traits and leaves the response unchanged.

type ResponseMiddleware m req res' res a = Middleware m req req res' res a a Source #

A middleware that manipulates only the response traits and leaves the request unchanged.