Safe Haskell | None |
---|---|
Language | Haskell2010 |
- data ActionT exts prms m a
- stop :: Monad m => ActionT exts prms m a
- param :: (Member k v prms, Monad m) => proxy k -> ActionT exts prms m v
- params :: QuasiQuoter
- status :: Monad m => Status -> ActionT exts prms m ()
- addHeader :: Monad m => HeaderName -> ByteString -> ActionT exts prms m ()
- setHeaders :: Monad m => ResponseHeaders -> ActionT exts prms m ()
- modifyHeader :: Monad m => (ResponseHeaders -> ResponseHeaders) -> ActionT exts prms m ()
- contentType :: Monad m => ContentType -> ActionT exts prms m ()
- reset :: Monad m => ActionT exts prms m ()
- builder :: Monad m => Builder -> ActionT exts prms m ()
- bytes :: Monad m => ByteString -> ActionT exts prms m ()
- lazyBytes :: Monad m => ByteString -> ActionT exts prms m ()
- text :: Monad m => Text -> ActionT exts prms m ()
- lazyText :: Monad m => Text -> ActionT exts prms m ()
- showing :: (Monad m, Show a) => a -> ActionT exts prms m ()
- string :: Monad m => String -> ActionT exts prms m ()
- char :: Monad m => Char -> ActionT exts prms m ()
- appendBuilder :: Monad m => Builder -> ActionT exts prms m ()
- appendBytes :: Monad m => ByteString -> ActionT exts prms m ()
- appendLazyBytes :: Monad m => ByteString -> ActionT exts prms m ()
- appendText :: Monad m => Text -> ActionT exts prms m ()
- appendLazyText :: Monad m => Text -> ActionT exts prms m ()
- appendShowing :: (Monad m, Show a) => a -> ActionT exts prms m ()
- appendString :: Monad m => String -> ActionT exts prms m ()
- appendChar :: Monad m => Char -> ActionT exts prms m ()
- file :: MonadIO m => FilePath -> Maybe FilePart -> ActionT exts prms m ()
- file' :: MonadIO m => FilePath -> Maybe FilePart -> ActionT exts prms m ()
- redirect :: Monad m => ByteString -> ActionT exts prms m ()
- redirectPermanently :: Monad m => ByteString -> ActionT exts prms m ()
- redirectTemporary :: Monad m => ByteString -> ActionT exts prms m ()
- defaultDocumentationAction :: Monad m => DefaultDocumentConfig -> ActionT exts prms m ()
- data DefaultDocumentConfig = DefaultDocumentConfig {}
- type ContentType = ByteString
- stopWith :: Monad m => Response -> ActionT exts prms m a
- getRequest :: Monad m => ActionT exts prms m Request
- getHeaders :: Monad m => ActionT exts prms m RequestHeaders
- getParams :: Monad m => ActionT exts prms m (Dict prms)
- getQueryParams :: Monad m => ActionT exts prms m Query
- getReqBodyParams :: MonadIO m => ActionT exts prms m [Param]
- getReqBodyFiles :: MonadIO m => ActionT exts prms m [File]
- devFile :: MonadIO m => FilePath -> ActionT exts prms m ()
- devFile' :: MonadIO m => FilePath -> ActionT exts prms m ()
- stream :: Monad m => StreamingBody -> ActionT exts prms m ()
- rawResponse :: Monad m => (Status -> ResponseHeaders -> Response) -> ActionT exts prms m ()
- type StreamingBody = (Builder -> IO ()) -> IO () -> IO ()
- lookupVault :: Key a -> ActionT exts prms m (Maybe a)
- modifyVault :: (Vault -> Vault) -> ActionT exts prms m ()
- insertVault :: Key a -> a -> ActionT exts prms m ()
- adjustVault :: (a -> a) -> Key a -> ActionT exts prms m ()
- deleteVault :: Key a -> ActionT exts prms m ()
- redirectWith :: Monad m => Status -> ByteString -> ActionT exts prms m ()
Documentation
data ActionT exts prms m a Source
MonadBase b m => MonadBase b (ActionT exts prms m) | |
MonadBaseControl b m => MonadBaseControl b (ActionT exts prms m) | |
MonadReader r m => MonadReader r (ActionT exts prms m) | |
Monad m => MonadExts exts (ActionT exts prms m) | |
MonadTrans (ActionT exts prms) | |
MonadTransControl (ActionT exts prms) | |
(Monad m, Functor m) => Alternative (ActionT exts prms m) | |
Monad m => Monad (ActionT exts prms m) | |
Functor (ActionT exts prms m) | |
Monad m => MonadPlus (ActionT exts prms m) | |
Applicative (ActionT exts prms m) | |
MonadThrow m => MonadThrow (ActionT exts prms m) | |
MonadCatch m => MonadCatch (ActionT exts prms m) | |
MonadMask m => MonadMask (ActionT exts prms m) | |
MonadIO m => MonadIO (ActionT exts prms m) | |
data StT (ActionT exts prms) = StActionT {
| |
data StM (ActionT exts prms m) = StMActionT {
|
stop action
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|]
get parameters. since 1.0.0.
[params|foo,bar|] == do { a <- param [key|foo|]; b <- param [key|bar|]; return (a, b) }
setter
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
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.
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.
data DefaultDocumentConfig Source
DefaultDocumentConfig | |
|
not export from Web.Apiary
type ContentType = ByteString 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.
getQueryParams :: Monad m => ActionT exts prms m Query Source
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.
setter
devFile :: MonadIO m => FilePath -> ActionT exts prms m () Source
send file contents as lazy bytestring response. since v1.1.4.
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
:: 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.