airship-0.9.3: A Webmachine-inspired HTTP library

Safe HaskellNone
LanguageHaskell2010

Airship.Types

Synopsis

Documentation

data ETag Source #

Instances

Eq ETag Source # 

Methods

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

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

Ord ETag Source # 

Methods

compare :: ETag -> ETag -> Ordering #

(<) :: ETag -> ETag -> Bool #

(<=) :: ETag -> ETag -> Bool #

(>) :: ETag -> ETag -> Bool #

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

max :: ETag -> ETag -> ETag #

min :: ETag -> ETag -> ETag #

Show ETag Source # 

Methods

showsPrec :: Int -> ETag -> ShowS #

show :: ETag -> String #

showList :: [ETag] -> ShowS #

data Webmachine m a Source #

Instances

MonadTrans Webmachine Source # 

Methods

lift :: Monad m => m a -> Webmachine m a #

MonadBase b m => MonadBase b (Webmachine m) Source # 

Methods

liftBase :: b α -> Webmachine m α #

MonadBaseControl b m => MonadBaseControl b (Webmachine m) Source # 

Associated Types

type StM (Webmachine m :: * -> *) a :: * #

Methods

liftBaseWith :: (RunInBase (Webmachine m) b -> b a) -> Webmachine m a #

restoreM :: StM (Webmachine m) a -> Webmachine m a #

Monad m => MonadState ResponseState (Webmachine m) Source # 
Monad m => MonadReader RequestReader (Webmachine m) Source # 
Monad m => Monad (Webmachine m) Source # 

Methods

(>>=) :: Webmachine m a -> (a -> Webmachine m b) -> Webmachine m b #

(>>) :: Webmachine m a -> Webmachine m b -> Webmachine m b #

return :: a -> Webmachine m a #

fail :: String -> Webmachine m a #

Functor m => Functor (Webmachine m) Source # 

Methods

fmap :: (a -> b) -> Webmachine m a -> Webmachine m b #

(<$) :: a -> Webmachine m b -> Webmachine m a #

Monad m => Applicative (Webmachine m) Source # 

Methods

pure :: a -> Webmachine m a #

(<*>) :: Webmachine m (a -> b) -> Webmachine m a -> Webmachine m b #

liftA2 :: (a -> b -> c) -> Webmachine m a -> Webmachine m b -> Webmachine m c #

(*>) :: Webmachine m a -> Webmachine m b -> Webmachine m b #

(<*) :: Webmachine m a -> Webmachine m b -> Webmachine m a #

MonadIO m => MonadIO (Webmachine m) Source # 

Methods

liftIO :: IO a -> Webmachine m a #

type StM (Webmachine m) a Source # 
type StM (Webmachine m) a

data Request :: * #

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

Instances

addTrace :: Monad m => ByteString -> Webmachine m () Source #

Adds the provided ByteString to the Airship-Trace header.

defaultRequest :: Request #

A default, blank request.

Since 2.0.0

entireRequestBody :: MonadIO m => Request -> 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.

escapedResponse :: Text -> ResponseBody Source #

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

mapWebmachine :: (m1 (Either Response a1, ResponseState) -> m2 (Either Response a2, ResponseState)) -> Webmachine m1 a1 -> Webmachine m2 a2 Source #

Map both the return value and wrapped computation m.

request :: Monad m => Webmachine m Request Source #

Returns the Request that is currently being processed.

requestTime :: Monad m => Webmachine m UTCTime Source #

Returns the time at which this request began processing.

routePath :: Monad m => Webmachine m Text Source #

Returns the route path that was matched during route evaluation. This is not the path specified in the request, but rather the route in the RoutingSpec that matched the request URL. Variables names are prefixed with :, and free ("star") paths are designated with *.

params :: Monad m => Webmachine m (HashMap Text Text) Source #

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

putResponseBody :: Monad m => ResponseBody -> Webmachine m () Source #

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

putResponseBS :: Monad m => ByteString -> Webmachine 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 :: Monad m => Status -> Webmachine m a Source #

Immediately halts processing with the provided Status code. The contents of the Webmachine'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 :: Monad m => Response -> Webmachine m a Source #

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