apiary-2.1.2: Simple and type safe web framework that generate web API documentation.

Safe HaskellNone
LanguageHaskell2010

Control.Monad.Apiary.Action

Contents

Synopsis

Documentation

data ActionT exts prms m a Source #

Instances

MonadBase b m => MonadBase b (ActionT exts prms m) Source # 

Methods

liftBase :: b α -> ActionT exts prms m α #

MonadBaseControl b m => MonadBaseControl b (ActionT exts prms m) Source # 

Associated Types

type StM (ActionT exts prms m :: * -> *) a :: * #

Methods

liftBaseWith :: (RunInBase (ActionT exts prms m) b -> b a) -> ActionT exts prms m a #

restoreM :: StM (ActionT exts prms m) a -> ActionT exts prms m a #

MonadReader r m => MonadReader r (ActionT exts prms m) Source # 

Methods

ask :: ActionT exts prms m r #

local :: (r -> r) -> ActionT exts prms m a -> ActionT exts prms m a #

reader :: (r -> a) -> ActionT exts prms m a #

Monad m => MonadExts exts (ActionT exts prms m) Source # 

Methods

getExts :: ActionT exts prms m (Extensions exts) Source #

MonadTrans (ActionT exts prms) Source # 

Methods

lift :: Monad m => m a -> ActionT exts prms m a #

MonadTransControl (ActionT exts prms) Source # 

Associated Types

type StT (ActionT exts prms :: (* -> *) -> * -> *) a :: * #

Methods

liftWith :: Monad m => (Run (ActionT exts prms) -> m a) -> ActionT exts prms m a #

restoreT :: Monad m => m (StT (ActionT exts prms) a) -> ActionT exts prms m a #

Monad m => Monad (ActionT exts prms m) Source # 

Methods

(>>=) :: ActionT exts prms m a -> (a -> ActionT exts prms m b) -> ActionT exts prms m b #

(>>) :: ActionT exts prms m a -> ActionT exts prms m b -> ActionT exts prms m b #

return :: a -> ActionT exts prms m a #

fail :: String -> ActionT exts prms m a #

Functor (ActionT exts prms m) Source # 

Methods

fmap :: (a -> b) -> ActionT exts prms m a -> ActionT exts prms m b #

(<$) :: a -> ActionT exts prms m b -> ActionT exts prms m a #

Applicative (ActionT exts prms m) Source # 

Methods

pure :: a -> ActionT exts prms m a #

(<*>) :: ActionT exts prms m (a -> b) -> ActionT exts prms m a -> ActionT exts prms m b #

(*>) :: ActionT exts prms m a -> ActionT exts prms m b -> ActionT exts prms m b #

(<*) :: ActionT exts prms m a -> ActionT exts prms m b -> ActionT exts prms m a #

(Monad m, Functor m) => Alternative (ActionT exts prms m) Source # 

Methods

empty :: ActionT exts prms m a #

(<|>) :: ActionT exts prms m a -> ActionT exts prms m a -> ActionT exts prms m a #

some :: ActionT exts prms m a -> ActionT exts prms m [a] #

many :: ActionT exts prms m a -> ActionT exts prms m [a] #

Monad m => MonadPlus (ActionT exts prms m) Source # 

Methods

mzero :: ActionT exts prms m a #

mplus :: ActionT exts prms m a -> ActionT exts prms m a -> ActionT exts prms m a #

MonadIO m => MonadIO (ActionT exts prms m) Source # 

Methods

liftIO :: IO a -> ActionT exts prms m a #

MonadThrow m => MonadThrow (ActionT exts prms m) Source # 

Methods

throwM :: Exception e => e -> ActionT exts prms m a #

MonadCatch m => MonadCatch (ActionT exts prms m) Source # 

Methods

catch :: Exception e => ActionT exts prms m a -> (e -> ActionT exts prms m a) -> ActionT exts prms m a #

MonadMask m => MonadMask (ActionT exts prms m) Source # 

Methods

mask :: ((forall a. ActionT exts prms m a -> ActionT exts prms m a) -> ActionT exts prms m b) -> ActionT exts prms m b #

uninterruptibleMask :: ((forall a. ActionT exts prms m a -> ActionT exts prms m a) -> ActionT exts prms m b) -> ActionT exts prms m b #

type StT (ActionT exts prms) a Source # 
type StT (ActionT exts prms) a
type StM (ActionT exts prms m) a Source # 
type StM (ActionT exts prms m) a = ComposeSt (ActionT exts prms) m a

hoistActionT :: (Monad m, Monad n) => (forall b. m b -> n b) -> ActionT exts prms m a -> ActionT exts prms n a Source #

n must be Monad, so cant be MFunctor.

stop action

application :: Monad m => Application -> ActionT exts prms m a Source #

stop and proxy current request to a Application, since 2.0.0.

stop :: Monad m => ActionT exts prms m a Source #

stop handler and send current state. since 0.3.3.0.

getter

param :: (Member k v prms, Monad m) => proxy k -> ActionT exts prms m v Source #

get parameter. since 1.0.0.

example:

param [key|foo|]

params :: QuasiQuoter Source #

get parameters. since 1.0.0.

[params|foo,bar|] == do { a <- param [key|foo|]; b <- param [key|bar|]; return (a, b) }

setter

status :: Monad m => Status -> ActionT exts prms m () Source #

set status code. since 0.1.0.0.

response header

addHeader :: Monad m => HeaderName -> ByteString -> ActionT exts prms m () Source #

add response header. since 0.1.0.0.

Don't set Content-Type using this function. Use contentType.

setHeaders :: Monad m => ResponseHeaders -> ActionT exts prms m () Source #

set response headers. since 0.1.0.0.

Don't set Content-Type using this function. Use contentType.

modifyHeader :: Monad m => (ResponseHeaders -> ResponseHeaders) -> ActionT exts prms m () Source #

modify response header. since 0.1.0.0.

Don't set Content-Type using this function. Use contentType.

contentType :: Monad m => ContentType -> ActionT exts prms m () Source #

set content-type header.

if content-type header already exists, replace it. since 0.1.0.0.

response body

reset :: Monad m => ActionT exts prms m () Source #

reset response body to no response. since v0.15.2.

builder :: Monad m => Builder -> ActionT exts prms m () Source #

set response body from builder. since 0.1.0.0.

bytes :: Monad m => ByteString -> ActionT exts prms m () Source #

set response body from strict bytestring. since 0.15.2.

lazyBytes :: Monad m => ByteString -> ActionT exts prms m () Source #

set response body from lazy bytestring. since 0.15.2.

text :: Monad m => Text -> ActionT exts prms m () Source #

set response body from strict text. encoding UTF-8. since 0.15.2.

lazyText :: Monad m => Text -> ActionT exts prms m () Source #

set response body from lazy text. encoding UTF-8. since 0.15.2.

showing :: (Monad m, Show a) => a -> ActionT exts prms m () Source #

set response body from show. encoding UTF-8. since 0.15.2.

json :: (Monad m, ToJSON a) => a -> ActionT exts prms m () Source #

set response body from ToJSON with content-type set to application/json. since 2.0.2

string :: Monad m => String -> ActionT exts prms m () Source #

set response body from string. encoding UTF-8. since 0.15.2.

char :: Monad m => Char -> ActionT exts prms m () Source #

set response body from char. encoding UTF-8. since 0.15.2.

appendBuilder :: Monad m => Builder -> ActionT exts prms m () Source #

append response body from builder. since 1.2.0.

appendBytes :: Monad m => ByteString -> ActionT exts prms m () Source #

append response body from strict bytestring. since 1.2.0.

appendLazyBytes :: Monad m => ByteString -> ActionT exts prms m () Source #

append response body from lazy bytestring. since 1.2.0.

appendText :: Monad m => Text -> ActionT exts prms m () Source #

append response body from strict text. encoding UTF-8. since 1.2.0.

appendLazyText :: Monad m => Text -> ActionT exts prms m () Source #

append response body from lazy text. encoding UTF-8. since 1.2.0.

appendShowing :: (Monad m, Show a) => a -> ActionT exts prms m () Source #

append response body from show. encoding UTF-8. since 1.2.0.

appendString :: Monad m => String -> ActionT exts prms m () Source #

append response body from string. encoding UTF-8. since 1.2.0.

appendChar :: Monad m => Char -> ActionT exts prms m () Source #

append response body from char. encoding UTF-8. since 1.2.0.

file :: MonadIO m => FilePath -> Maybe FilePart -> ActionT exts prms m () Source #

set response body file content and detect Content-Type by extension. since 0.1.0.0.

file modification check since 0.17.2.

file' :: MonadIO m => FilePath -> Maybe FilePart -> ActionT exts prms m () Source #

set response body file content, without set Content-Type. since 0.1.0.0.

monolithic action

redirect

redirect :: Monad m => ByteString -> ActionT exts prms m () Source #

redirect with:

303 See Other (HTTP/1.1) or 302 Moved Temporarily (Other)

since 0.6.2.0.

redirectPermanently :: Monad m => ByteString -> ActionT exts prms m () Source #

redirect with 301 Moved Permanently. since 0.3.3.0.

redirectTemporary :: Monad m => ByteString -> ActionT exts prms m () Source #

redirect with:

307 Temporary Redirect (HTTP/1.1) or 302 Moved Temporarily (Other)

since 0.3.3.0.

documentation

defaultDocumentationAction :: Monad m => DefaultDocumentConfig -> ActionT exts prms m () Source #

auto generated document.

not export from Web.Apiary

stopWith :: Monad m => Response -> ActionT exts prms m a Source #

stop with response. since 0.4.2.0.

applyDict :: Dict prms -> ActionT exts prms m a -> ActionT exts '[] m a Source #

getter

getRequest :: Monad m => ActionT exts prms m Request Source #

get raw request. since 0.1.0.0.

getHeaders :: Monad m => ActionT exts prms m RequestHeaders Source #

get all request headers. since 0.6.0.0.

getParams :: Monad m => ActionT exts prms m (Dict prms) Source #

getQueryParams :: Monad m => ActionT exts prms m Query Source #

only get parameters in query string.

getReqBody :: MonadIO m => ActionT exts prms m ActionReqBody Source #

parse request body into ActionReqBody and return it. since 1.2.2.

getReqBodyParams :: MonadIO m => ActionT exts prms m [Param] Source #

parse request body and return params. since 1.0.0.

getReqBodyFiles :: MonadIO m => ActionT exts prms m [File] Source #

parse request body and return files. since 0.9.0.0.

getReqBodyJSON :: (MonadIO m, FromJSON a) => ActionT exts prms m (Maybe a) Source #

parse request body and try parse it as JSON.

it's recommended to use jsonReqBody filter to leverage type level routing instead of getReqBodyJSON. since 2.0.0.

setter

devFile :: MonadIO m => FilePath -> ActionT exts prms m () Source #

send file contents as lazy bytestring response. since v1.1.4.

devFile' :: MonadIO m => FilePath -> ActionT exts prms m () Source #

stream :: Monad m => StreamingBody -> ActionT exts prms m () Source #

set response body source. since 0.9.0.0.

rawResponse :: Monad m => (Status -> ResponseHeaders -> Response) -> ActionT exts prms m () Source #

set raw response constructor. since 0.10.

example(use pipes-wai)

producer :: Monad m => Producer (Flush Builder) IO () -> ActionT' exts m ()
producer = response (s h -> responseProducer s h)

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

vault

lookupVault :: Key a -> ActionT exts prms m (Maybe a) Source #

lookup extensional state. since v1.2.0.

modifyVault :: (Vault -> Vault) -> ActionT exts prms m () Source #

modify extensional state. since v1.2.0.

insertVault :: Key a -> a -> ActionT exts prms m () Source #

insert extensional state. since v1.2.0.

adjustVault :: (a -> a) -> Key a -> ActionT exts prms m () Source #

adjust extensional state. since v1.2.0.

deleteVault :: Key a -> ActionT exts prms m () Source #

delete extensional state. since v1.2.0.

redirect

redirectWith Source #

Arguments

:: Monad m 
=> Status 
-> ByteString

Location redirect to

-> ActionT exts prms m () 

redirect handler

set status and add location header. since 0.3.3.0.

rename from redirect in 0.6.2.0.