airship-0.1.0.0: A Webmachine-inspired HTTP library

Safe HaskellNone
LanguageHaskell2010

Airship.Types

Synopsis

Documentation

data ETag Source

Instances

type Handler s m a = Monad m => Webmachine s m a Source

A convenience synonym that writes the Monad type constraint for you.

data Request m Source

Very similar to WAI's Request type, except generalized to an arbitrary monad m.

Constructors

Request 

Fields

requestMethod :: Method

The request method -- GET, POST, DELETE, et cetera.

httpVersion :: HttpVersion

The HTTP version (usually 1.1; hopefully someday 2.0).

rawPathInfo :: ByteString

The unparsed path information yielded from the WAI server. You probably want pathInfo.

rawQueryString :: ByteString

The query string, if any, yielded from the WAI server. You probably want queryString.

requestHeaders :: RequestHeaders

An association list of (headername, value) pairs. See Network.HTTP.Types.Header for the possible values.

isSecure :: Bool

Was this request made over SSL/TLS?

remoteHost :: SockAddr

The address information of the client.

pathInfo :: [Text]

The URL, stripped of hostname and port, split on forward-slashes

queryString :: Query

Parsed query string information.

requestBody :: m ByteString

A monadic action that extracts a (possibly-empty) chunk of the request body.

requestBodyLength :: RequestBodyLength

Either ChunkedBody or a KnownLength Word64.

requestHeaderHost :: Maybe ByteString

Contains the Host header.

requestHeaderRange :: Maybe ByteString

Contains the Range header.

data ResponseBody m Source

Basically Wai's unexported Response type, but generalized to any monad, m.

entireRequestBody :: Monad m => Request m -> m ByteString Source

Reads the entirety of the request body in a single string. This turns the chunks obtained from repeated invocations of requestBody into a lazy ByteString.

eitherResponse :: Monad m => UTCTime -> HashMap Text Text -> Request m -> s -> Handler s m (Response m) -> m (Response m, Trace) Source

escapedResponse :: Text -> ResponseBody m Source

Helper function for building a ResponseBuilder out of HTML-escaped text.

runWebmachine :: Monad m => UTCTime -> HashMap Text Text -> Request m -> s -> Handler s m a -> m (Either (Response m) a, Trace) Source

request :: Handler s m (Request m) Source

Returns the Request that this Handler is currently processing.

requestTime :: Handler s m UTCTime Source

Returns the time at which this request began processing.

getState :: Handler s m s Source

Returns the user state (of type s) in the provided Handler s m.

putState :: s -> Handler s m () Source

Sets the user state.

modifyState :: (s -> s) -> Handler s m () Source

Applies the provided function to the user state.

getResponseHeaders :: Handler s m ResponseHeaders Source

Returns the ResponseHeaders stored in the current Handler.

getResponseBody :: Handler s m (ResponseBody m) Source

Returns the current ResponseBody that this Handler is storing.

params :: Handler s m (HashMap Text Text) Source

Returns the bound routing parameters extracted from the routing system (see Airship.Route).

putResponseBody :: ResponseBody m -> Handler s m () Source

Given a new ResponseBody, replaces the stored body with the new one.

putResponseBS :: ByteString -> Handler s m () Source

Stores the provided ByteString as the responseBody. This is a shortcut for creating a response body with a ResponseBuilder and a bytestring Builder.

halt :: Status -> Handler m s a Source

Immediately halts processing with the provided Status code. The contents of the Handler's response body will be streamed back to the client. This is a shortcut for constructing a Response with getResponseHeaders and getResponseBody and passing that response to finishWith.

finishWith :: Response m -> Handler s m a Source

Immediately halts processing and writes the provided Response back to the client.

(#>) :: MonadWriter [(k, v)] m => k -> v -> m () Source

The #> operator provides syntactic sugar for the construction of association lists. For example, the following assoc list:

    [("run", "jewels"), ("blue", "suede"), ("zion", "wolf")]

can be represented as such:

    execWriter $ do
      "run" #> "jewels"
      "blue" #> "suede"
      "zion" #> "wolf"

It used in RoutingSpec declarations to indicate that a particular Route maps to a given Resource, but can be used in many other places where association lists are expected, such as contentTypesProvided.