Safe Haskell | None |
---|---|
Language | Haskell2010 |
Web.Spock.Action
Synopsis
- type ActionT = ActionCtxT ()
- data ActionCtxT ctx m a
- request :: MonadIO m => ActionCtxT ctx m Request
- header :: MonadIO m => Text -> ActionCtxT ctx m (Maybe Text)
- rawHeader :: MonadIO m => HeaderName -> ActionCtxT ctx m (Maybe ByteString)
- cookies :: MonadIO m => ActionCtxT ctx m [(Text, Text)]
- cookie :: MonadIO m => Text -> ActionCtxT ctx m (Maybe Text)
- reqMethod :: MonadIO m => ActionCtxT ctx m SpockMethod
- preferredFormat :: MonadIO m => ActionCtxT ctx m ClientPreferredFormat
- data ClientPreferredFormat
- body :: MonadIO m => ActionCtxT ctx m ByteString
- jsonBody :: (MonadIO m, FromJSON a) => ActionCtxT ctx m (Maybe a)
- jsonBody' :: (MonadIO m, FromJSON a) => ActionCtxT ctx m a
- files :: MonadIO m => ActionCtxT ctx m (HashMap Text UploadedFile)
- data UploadedFile = UploadedFile {
- uf_name :: !Text
- uf_contentType :: !Text
- uf_tempLocation :: !FilePath
- params :: MonadIO m => ActionCtxT ctx m [(Text, Text)]
- paramsGet :: MonadIO m => ActionCtxT ctx m [(Text, Text)]
- paramsPost :: MonadIO m => ActionCtxT ctx m [(Text, Text)]
- param :: (FromHttpApiData p, MonadIO m) => Text -> ActionCtxT ctx m (Maybe p)
- param' :: (FromHttpApiData p, MonadIO m) => Text -> ActionCtxT ctx m p
- getContext :: MonadIO m => ActionCtxT ctx m ctx
- runInContext :: MonadIO m => ctx' -> ActionCtxT ctx' m a -> ActionCtxT ctx m a
- setStatus :: MonadIO m => Status -> ActionCtxT ctx m ()
- setHeader :: MonadIO m => Text -> Text -> ActionCtxT ctx m ()
- redirect :: MonadIO m => Text -> ActionCtxT ctx m a
- jumpNext :: MonadIO m => ActionCtxT ctx m a
- data CookieSettings = CookieSettings {}
- defaultCookieSettings :: CookieSettings
- data CookieEOL
- setCookie :: MonadIO m => Text -> Text -> CookieSettings -> ActionCtxT ctx m ()
- deleteCookie :: MonadIO m => Text -> ActionCtxT ctx m ()
- bytes :: MonadIO m => ByteString -> ActionCtxT ctx m a
- lazyBytes :: MonadIO m => ByteString -> ActionCtxT ctx m a
- setRawMultiHeader :: MonadIO m => MultiHeader -> ByteString -> ActionCtxT ctx m ()
- data MultiHeader
- = MultiHeaderCacheControl
- | MultiHeaderConnection
- | MultiHeaderContentEncoding
- | MultiHeaderContentLanguage
- | MultiHeaderPragma
- | MultiHeaderProxyAuthenticate
- | MultiHeaderTrailer
- | MultiHeaderTransferEncoding
- | MultiHeaderUpgrade
- | MultiHeaderVia
- | MultiHeaderWarning
- | MultiHeaderWWWAuth
- | MultiHeaderSetCookie
- text :: MonadIO m => Text -> ActionCtxT ctx m a
- html :: MonadIO m => Text -> ActionCtxT ctx m a
- file :: MonadIO m => Text -> FilePath -> ActionCtxT ctx m a
- json :: (ToJSON a, MonadIO m) => a -> ActionCtxT ctx m b
- stream :: MonadIO m => StreamingBody -> ActionCtxT ctx m a
- response :: MonadIO m => (Status -> ResponseHeaders -> Response) -> ActionCtxT ctx m a
- respondApp :: Monad m => Application -> ActionCtxT ctx m a
- respondMiddleware :: Monad m => Middleware -> ActionCtxT ctx m a
- middlewarePass :: MonadIO m => ActionCtxT ctx m a
- modifyVault :: MonadIO m => (Vault -> Vault) -> ActionCtxT ctx m ()
- queryVault :: MonadIO m => Key a -> ActionCtxT ctx m (Maybe a)
- requireBasicAuth :: MonadIO m => Text -> (Text -> Text -> ActionCtxT ctx m b) -> (b -> ActionCtxT ctx m a) -> ActionCtxT ctx m a
- withBasicAuthData :: MonadIO m => (Maybe (Text, Text) -> ActionCtxT ctx m a) -> ActionCtxT ctx m a
Action types
type ActionT = ActionCtxT () Source #
data ActionCtxT ctx m a Source #
Instances
Handling requests
rawHeader :: MonadIO m => HeaderName -> ActionCtxT ctx m (Maybe ByteString) Source #
Read a header without converting it to text
cookies :: MonadIO m => ActionCtxT ctx m [(Text, Text)] Source #
Read all cookies. The cookie value will already be urldecoded.
cookie :: MonadIO m => Text -> ActionCtxT ctx m (Maybe Text) Source #
Read a cookie. The cookie value will already be urldecoded. Note that it is
more efficient to use cookies
if you need do access many cookies during a request
handler.
reqMethod :: MonadIO m => ActionCtxT ctx m SpockMethod Source #
Returns the current request method, e.g. GET
preferredFormat :: MonadIO m => ActionCtxT ctx m ClientPreferredFormat Source #
Tries to dected the preferred format of the response using the Accept header
data ClientPreferredFormat Source #
Constructors
PrefJSON | |
PrefXML | |
PrefHTML | |
PrefText | |
PrefUnknown |
Instances
Eq ClientPreferredFormat Source # | |
Defined in Web.Spock.Internal.Util Methods (==) :: ClientPreferredFormat -> ClientPreferredFormat -> Bool # (/=) :: ClientPreferredFormat -> ClientPreferredFormat -> Bool # | |
Show ClientPreferredFormat Source # | |
Defined in Web.Spock.Internal.Util Methods showsPrec :: Int -> ClientPreferredFormat -> ShowS # show :: ClientPreferredFormat -> String # showList :: [ClientPreferredFormat] -> ShowS # |
body :: MonadIO m => ActionCtxT ctx m ByteString Source #
Get the raw request body
jsonBody :: (MonadIO m, FromJSON a) => ActionCtxT ctx m (Maybe a) Source #
Parse the request body as json
jsonBody' :: (MonadIO m, FromJSON a) => ActionCtxT ctx m a Source #
Parse the request body as json and fails with 400 status code on error
files :: MonadIO m => ActionCtxT ctx m (HashMap Text UploadedFile) Source #
Get uploaded files
data UploadedFile Source #
Constructors
UploadedFile | |
Fields
|
Instances
Show UploadedFile Source # | |
Defined in Web.Spock.Internal.Wire Methods showsPrec :: Int -> UploadedFile -> ShowS # show :: UploadedFile -> String # showList :: [UploadedFile] -> ShowS # |
paramsPost :: MonadIO m => ActionCtxT ctx m [(Text, Text)] Source #
Get all request POST params
param :: (FromHttpApiData p, MonadIO m) => Text -> ActionCtxT ctx m (Maybe p) Source #
Read a request param. Spock looks POST variables first and then in GET variables
param' :: (FromHttpApiData p, MonadIO m) => Text -> ActionCtxT ctx m p Source #
Like param
, but outputs an error when a param is missing
Working with context
getContext :: MonadIO m => ActionCtxT ctx m ctx Source #
Get the context of the current request
runInContext :: MonadIO m => ctx' -> ActionCtxT ctx' m a -> ActionCtxT ctx m a Source #
Run an Action in a different context
Sending responses
setHeader :: MonadIO m => Text -> Text -> ActionCtxT ctx m () Source #
Set a response header. If the response header
is allowed to occur multiple times (as in RFC 2616), it will
be appended. Otherwise the previous value is overwritten.
See setMultiHeader
.
jumpNext :: MonadIO m => ActionCtxT ctx m a Source #
Abort the current action and jump the next one matching the route
data CookieSettings Source #
Cookie settings
Constructors
CookieSettings | |
Fields
|
defaultCookieSettings :: CookieSettings Source #
Default cookie settings, equals
CookieSettings { cs_EOL = CookieValidForSession , cs_HTTPOnly = False , cs_secure = False , cs_domain = Nothing , cs_path = Just "/" }
Setting cookie expiration
Constructors
CookieValidUntil UTCTime | a point in time in UTC until the cookie is valid |
CookieValidFor NominalDiffTime | a period (in seconds) for which the cookie is valid |
CookieValidForSession | the cookie expires with the browser session |
CookieValidForever | the cookie will have an expiration date in the far future |
setCookie :: MonadIO m => Text -> Text -> CookieSettings -> ActionCtxT ctx m () Source #
Set a cookie. The cookie value will be urlencoded.
deleteCookie :: MonadIO m => Text -> ActionCtxT ctx m () Source #
Delete a cookie
bytes :: MonadIO m => ByteString -> ActionCtxT ctx m a Source #
Send a ByteString
as response body. Provide your own "Content-Type"
lazyBytes :: MonadIO m => ByteString -> ActionCtxT ctx m a Source #
Send a lazy ByteString
as response body. Provide your own "Content-Type"
setRawMultiHeader :: MonadIO m => MultiHeader -> ByteString -> ActionCtxT ctx m () Source #
Set a response header that can occur multiple times. (eg: Cache-Control)
data MultiHeader Source #
Constructors
Instances
text :: MonadIO m => Text -> ActionCtxT ctx m a Source #
Send text as a response body. Content-Type will be "text/plain"
html :: MonadIO m => Text -> ActionCtxT ctx m a Source #
Send a text as response body. Content-Type will be "text/html"
json :: (ToJSON a, MonadIO m) => a -> ActionCtxT ctx m b Source #
Send json as response. Content-Type will be "application/json"
stream :: MonadIO m => StreamingBody -> ActionCtxT ctx m a Source #
Use a StreamingBody
to generate a response.
response :: MonadIO m => (Status -> ResponseHeaders -> Response) -> ActionCtxT ctx m a Source #
Use a custom Response
generator as response body.
respondApp :: Monad m => Application -> ActionCtxT ctx m a Source #
Respond to the request by running an Application
. This is
usefull in combination with wildcard routes. This can not be used
in combination with other request consuming combinators
like jsonBody
, body
, paramsPost
, ...
respondMiddleware :: Monad m => Middleware -> ActionCtxT ctx m a Source #
Respond to the request by running a Middleware
. This is
usefull in combination with wildcard routes. This can not be used
in combination with other request consuming combinators
like jsonBody
, body
, paramsPost
, ...
Middleware helpers
middlewarePass :: MonadIO m => ActionCtxT ctx m a Source #
If the Spock application is used as a middleware, you can use this to pass request handling to the underlying application. If Spock is not uses as a middleware, or there is no underlying application this will result in 404 error.
modifyVault :: MonadIO m => (Vault -> Vault) -> ActionCtxT ctx m () Source #
Modify the vault (useful for sharing data between middleware and app)
queryVault :: MonadIO m => Key a -> ActionCtxT ctx m (Maybe a) Source #
Query the vault
Basic HTTP-Auth
requireBasicAuth :: MonadIO m => Text -> (Text -> Text -> ActionCtxT ctx m b) -> (b -> ActionCtxT ctx m a) -> ActionCtxT ctx m a Source #
Convenience Basic authentification provide a title for the prompt and a function to validate user and password. Usage example:
get ("auth" <//> var <//> var) $ \user pass -> let checker user' pass' = unless (user == user' && pass == pass') $ do setStatus status401 text "err" in requireBasicAuth "Foo" checker $ \() -> text "ok"
withBasicAuthData :: MonadIO m => (Maybe (Text, Text) -> ActionCtxT ctx m a) -> ActionCtxT ctx m a Source #
"Lower level" basic authentification handeling. Does not set any headers that will promt browser users, only looks for an Authorization header in the request and breaks it into username and passwort component if present