rest-core-0.38: Rest API library.

Safe HaskellNone
LanguageHaskell98

Rest.Handler

Contents

Description

Handlers for endpoints in a Resource.

Synopsis

Single handlers.

mkHandler :: (Monad m, i ~ FromMaybe () i', o ~ FromMaybe () o', e ~ FromMaybe Void e') => Modifier h p i' o' e' -> (Env h p i -> ExceptT (Reason e) m o) -> Handler m Source

Create a handler for a single resource. Takes the entire environmend as input.

mkInputHandler :: (Monad m, i ~ FromMaybe () i', o ~ FromMaybe () o', e ~ FromMaybe Void e') => Modifier () () i' o' e' -> (i -> ExceptT (Reason e) m o) -> Handler m Source

Create a handler for a single resource. Takes only the body information as input.

mkConstHandler :: (Monad m, o ~ FromMaybe () o', e ~ FromMaybe Void e') => Modifier () () Nothing o' e' -> ExceptT (Reason e) m o -> Handler m Source

Create a handler for a single resource. Doesn't take any input.

mkIdHandler :: (MonadReader id m, i ~ FromMaybe () i', o ~ FromMaybe () o', e ~ FromMaybe Void e') => Modifier h p i' o' e' -> (i -> id -> ExceptT (Reason e) m o) -> Handler m Source

Create a handler for a single resource. Take body information and the resource identifier as input. The monad m must be a Reader-like type containing the idenfier.

Listings.

mkListing :: (Monad m, o ~ FromMaybe () o', e ~ FromMaybe Void e') => Modifier h p Nothing o' e' -> (Range -> ExceptT (Reason e) m [o]) -> ListHandler m Source

Smart constructor for creating a list handler. Restricts the type of the Input dictionary to None

mkOrderedListing :: (Monad m, o ~ FromMaybe () o', e ~ FromMaybe Void e') => Modifier h p Nothing o' e' -> ((Range, Maybe String, Maybe String) -> ExceptT (Reason e) m [o]) -> ListHandler m Source

Create a list handler that accepts ordering information. Restricts the type of the Input dictionary to None

Parameter parsers for listings.

data Range :: *

Data type for representing the requested range in list handlers.

Constructors

Range 

Fields

offset :: Int
 
count :: Int
 

range :: Param Range Source

Dictionary for taking Range parameters. Allows two query parameters, offset and count. If not passed, the defaults are 0 and 100. The maximum range that can be passed is 1000.

orderedRange :: Param (Range, Maybe String, Maybe String) Source

Dictionary for taking ordering information. In addition to the parameters accepted by range, this accepts order and direction.

Generic handlers and core data types.

data Env h p i Source

An environment of inputs passed to a handler. Contains information from the headers, the parameters and the body input.

Constructors

Env 

Fields

header :: h
 
param :: p
 
input :: i
 

data GenHandler m f where Source

A handler for some endpoint. The input and output types are specified by the dictionary, which can be created using the combinators from Rest.Dictionary.Combinators. The inputs (headers, parameters and body) are passed as an Env to the handler. This handler runs in monad m, combined with the ability to throw errors. The result is either the output value, or a list of them for list handlers. If the secure flag is set, this suggests to clients that the resource should only be served over https. It has no effect when running the API.

Constructors

GenHandler :: (i ~ FromMaybe () i', o ~ FromMaybe () o', e ~ FromMaybe Void e') => Dict h p i' o' e' -> (Env h p i -> ExceptT (Reason e) m (Apply f o)) -> Bool -> GenHandler m f 

Fields

dictionary :: Dict h p i' o' e'
 
handler :: Env h p i -> ExceptT (Reason e) m (Apply f o)
 
secure :: Bool
 

mkGenHandler :: (Monad m, i ~ FromMaybe () i', o ~ FromMaybe () o', e ~ FromMaybe Void e') => Modifier h p i' o' e' -> (Env h p i -> ExceptT (Reason e) m (Apply f o)) -> GenHandler m f Source

Construct a GenHandler using a Modifier instead of a Dict. The secure flag will be False.

type family Apply f a :: * Source

Apply a Functor f to a type a. In general will result in f a, except if f is Identity, in which case it will result in a. This prevents a lot of Identity wrapping/unwrapping.

Instances

type Apply [] a = [a] Source 
type Apply Identity a = a Source 

type Handler m = GenHandler m Identity Source

A Handler returning a single item.

type ListHandler m = GenHandler m [] Source

A Handler returning a list of items.

Convenience functions.