Spock-core-0.14.0.1: Another Haskell web framework for rapid development
Safe HaskellNone
LanguageHaskell2010

Web.Spock.Action

Synopsis

Action types

data ActionCtxT ctx m a Source #

Instances

Instances details
MonadBase b m => MonadBase b (ActionCtxT ctx m) Source # 
Instance details

Defined in Web.Spock.Internal.Wire

Methods

liftBase :: b α -> ActionCtxT ctx m α #

MonadBaseControl b m => MonadBaseControl b (ActionCtxT ctx m) Source # 
Instance details

Defined in Web.Spock.Internal.Wire

Associated Types

type StM (ActionCtxT ctx m) a #

Methods

liftBaseWith :: (RunInBase (ActionCtxT ctx m) b -> b a) -> ActionCtxT ctx m a #

restoreM :: StM (ActionCtxT ctx m) a -> ActionCtxT ctx m a #

MonadTrans (ActionCtxT ctx) Source # 
Instance details

Defined in Web.Spock.Internal.Wire

Methods

lift :: Monad m => m a -> ActionCtxT ctx m a #

MonadTransControl (ActionCtxT ctx) Source # 
Instance details

Defined in Web.Spock.Internal.Wire

Associated Types

type StT (ActionCtxT ctx) a #

Methods

liftWith :: Monad m => (Run (ActionCtxT ctx) -> m a) -> ActionCtxT ctx m a #

restoreT :: Monad m => m (StT (ActionCtxT ctx) a) -> ActionCtxT ctx m a #

MFunctor (ActionCtxT ctx :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Web.Spock.Internal.Wire

Methods

hoist :: forall m n (b :: k). Monad m => (forall a. m a -> n a) -> ActionCtxT ctx m b -> ActionCtxT ctx n b #

Monad m => Monad (ActionCtxT ctx m) Source # 
Instance details

Defined in Web.Spock.Internal.Wire

Methods

(>>=) :: ActionCtxT ctx m a -> (a -> ActionCtxT ctx m b) -> ActionCtxT ctx m b #

(>>) :: ActionCtxT ctx m a -> ActionCtxT ctx m b -> ActionCtxT ctx m b #

return :: a -> ActionCtxT ctx m a #

Functor m => Functor (ActionCtxT ctx m) Source # 
Instance details

Defined in Web.Spock.Internal.Wire

Methods

fmap :: (a -> b) -> ActionCtxT ctx m a -> ActionCtxT ctx m b #

(<$) :: a -> ActionCtxT ctx m b -> ActionCtxT ctx m a #

Monad m => Applicative (ActionCtxT ctx m) Source # 
Instance details

Defined in Web.Spock.Internal.Wire

Methods

pure :: a -> ActionCtxT ctx m a #

(<*>) :: ActionCtxT ctx m (a -> b) -> ActionCtxT ctx m a -> ActionCtxT ctx m b #

liftA2 :: (a -> b -> c) -> ActionCtxT ctx m a -> ActionCtxT ctx m b -> ActionCtxT ctx m c #

(*>) :: ActionCtxT ctx m a -> ActionCtxT ctx m b -> ActionCtxT ctx m b #

(<*) :: ActionCtxT ctx m a -> ActionCtxT ctx m b -> ActionCtxT ctx m a #

Monad m => Alternative (ActionCtxT ctx m) Source # 
Instance details

Defined in Web.Spock.Internal.Wire

Methods

empty :: ActionCtxT ctx m a #

(<|>) :: ActionCtxT ctx m a -> ActionCtxT ctx m a -> ActionCtxT ctx m a #

some :: ActionCtxT ctx m a -> ActionCtxT ctx m [a] #

many :: ActionCtxT ctx m a -> ActionCtxT ctx m [a] #

MonadIO m => MonadIO (ActionCtxT ctx m) Source # 
Instance details

Defined in Web.Spock.Internal.Wire

Methods

liftIO :: IO a -> ActionCtxT ctx m a #

type StT (ActionCtxT ctx) a Source # 
Instance details

Defined in Web.Spock.Internal.Wire

type StT (ActionCtxT ctx) a
type StM (ActionCtxT ctx m) a Source # 
Instance details

Defined in Web.Spock.Internal.Wire

type StM (ActionCtxT ctx m) a = ComposeSt (ActionCtxT ctx) m a

Handling requests

request :: MonadIO m => ActionCtxT ctx m Request Source #

Get the original Wai Request object

header :: MonadIO m => Text -> ActionCtxT ctx m (Maybe Text) Source #

Read a header

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

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 #

Instances

Instances details
Show UploadedFile Source # 
Instance details

Defined in Web.Spock.Internal.Wire

params :: MonadIO m => ActionCtxT ctx m [(Text, Text)] Source #

Get all request (POST + GET) params

paramsGet :: MonadIO m => ActionCtxT ctx m [(Text, Text)] Source #

Get all request GET params

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

setStatus :: MonadIO m => Status -> ActionCtxT ctx m () Source #

Set a response status

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.

redirect :: MonadIO m => Text -> ActionCtxT ctx m a Source #

Redirect to a given url

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 "/"
  }

data CookieEOL Source #

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 #

Instances

Instances details
Bounded MultiHeader Source # 
Instance details

Defined in Web.Spock.Internal.Wire

Enum MultiHeader Source # 
Instance details

Defined in Web.Spock.Internal.Wire

Eq MultiHeader Source # 
Instance details

Defined in Web.Spock.Internal.Wire

Show MultiHeader Source # 
Instance details

Defined in Web.Spock.Internal.Wire

Generic MultiHeader Source # 
Instance details

Defined in Web.Spock.Internal.Wire

Associated Types

type Rep MultiHeader :: Type -> Type #

Hashable MultiHeader Source # 
Instance details

Defined in Web.Spock.Internal.Wire

type Rep MultiHeader Source # 
Instance details

Defined in Web.Spock.Internal.Wire

type Rep MultiHeader = D1 ('MetaData "MultiHeader" "Web.Spock.Internal.Wire" "Spock-core-0.14.0.1-5rOXvWUo7l4A8Kg2mWqGE7" 'False) (((C1 ('MetaCons "MultiHeaderCacheControl" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "MultiHeaderConnection" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MultiHeaderContentEncoding" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "MultiHeaderContentLanguage" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "MultiHeaderPragma" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MultiHeaderProxyAuthenticate" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "MultiHeaderTrailer" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "MultiHeaderTransferEncoding" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MultiHeaderUpgrade" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "MultiHeaderVia" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MultiHeaderWarning" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "MultiHeaderWWWAuth" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MultiHeaderSetCookie" 'PrefixI 'False) (U1 :: Type -> Type)))))

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"

file :: MonadIO m => Text -> FilePath -> ActionCtxT ctx m a Source #

Send a file as response

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