Spock-0.9.0.1: Another Haskell web framework for rapid development

Safe HaskellNone
LanguageHaskell98

Web.Spock.Shared

Contents

Synopsis

Helpers for running Spock

runSpock :: Port -> IO Middleware -> IO () Source

Run a Spock application. Basically just a wrapper aroung Warp.run.

spockAsApp :: IO Middleware -> IO Application Source

Convert a middleware to an application. All failing requests will result in a 404 page

Action types

type SpockAction conn sess st = SpockActionCtx () conn sess st Source

The SpockAction is a specialisation of SpockActionCtx with a '()' context.

type SpockActionCtx ctx conn sess st = ActionCtxT ctx (WebStateM conn sess st) Source

The SpockActionCtx is the monad of all route-actions. You have access to the context of the request and database, session and state of your application.

data ActionCtxT ctx m a Source

Instances

MonadTrans (ActionCtxT ctx) 
(Monad m, Functor m) => Alternative (ActionCtxT ctx m) 
Monad m => Monad (ActionCtxT ctx m) 
Functor m => Functor (ActionCtxT ctx m) 
(Monad m, Functor m) => Applicative (ActionCtxT ctx m) 
MonadIO m => MonadIO (ActionCtxT ctx m) 

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

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

Read a cookie

reqMethod :: MonadIO m => ActionCtxT ctx m StdMethod 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 500 status code on error

files :: MonadIO m => ActionCtxT ctx m (HashMap Text UploadedFile) Source

Get uploaded files

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

Get all request params

param :: (PathPiece p, MonadIO m) => Text -> ActionCtxT ctx m (Maybe p) Source

Read a request param. Spock looks in route captures first (in simple routing), then in POST variables and at last in GET variables

param' :: (PathPiece 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

setCookie :: MonadIO m => Text -> Text -> NominalDiffTime -> ActionCtxT ctx m () Source

Set a cookie living for a given number of seconds

setCookie' :: MonadIO m => Text -> Text -> UTCTime -> ActionCtxT ctx m () Source

Set a cookie living until a specific UTCTime

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

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.

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

Configuration

data SpockCfg conn sess st Source

Spock configuration

Constructors

SpockCfg 

Fields

spc_initialState :: st

initial application global state

spc_database :: PoolOrConn conn

See PoolOrConn

spc_sessionCfg :: SessionCfg sess

See SessionCfg

spc_maxRequestSize :: Maybe Word64

Maximum request size in bytes. Nothing means no limit. Defaults to 5 MB in defaultSpockCfg.

defaultSpockCfg :: sess -> PoolOrConn conn -> st -> SpockCfg conn sess st Source

Spock configuration with reasonable defaults

Database

data PoolOrConn a where Source

You can feed Spock with either a connection pool, or instructions on how to build a connection pool. See ConnBuilder

Constructors

PCPool :: Pool a -> PoolOrConn a 
PCConn :: ConnBuilder a -> PoolOrConn a 
PCNoDatabase :: PoolOrConn () 

data ConnBuilder a Source

The ConnBuilder instructs Spock how to create or close a database connection.

Constructors

ConnBuilder 

data PoolCfg Source

If Spock should take care of connection pooling, you need to configure it depending on what you need.

Accessing Database and State

class HasSpock m where Source

Minimal complete definition

runQuery, getState, getSessMgr

Associated Types

type SpockConn m :: * Source

type SpockState m :: * Source

type SpockSession m :: * Source

Methods

runQuery :: (SpockConn m -> IO a) -> m a Source

Give you access to a database connectin from the connection pool. The connection is released back to the pool once the function terminates.

getState :: m (SpockState m) Source

Read the application's state. If you wish to have mutable state, you could use a TVar from the STM packge.

Instances

MonadTrans t => HasSpock (t (WebStateM conn sess st)) 
HasSpock (WebStateM conn sess st) 

Basic HTTP-Auth

requireBasicAuth :: MonadIO m => Text -> (Text -> Text -> m Bool) -> ActionCtxT ctx m a -> ActionCtxT ctx m a Source

Basic authentification provide a title for the prompt and a function to validate user and password. Usage example:

get "/my-secret-page" $
  requireBasicAuth "Secret Page" (\user pass -> return (user == "admin" && pass == "1234")) $
  do html "This is top secret content. Login using that secret code I provided ;-)"

Sessions

defaultSessionCfg :: a -> SessionCfg a Source

Session configuration with reasonable defaults

data SessionCfg a Source

Configuration for the session manager

Constructors

SessionCfg 

Fields

sc_cookieName :: Text

name of the client side cookie

sc_sessionTTL :: NominalDiffTime

how long shoud a client session live

sc_sessionIdEntropy :: Int

entropy of the session id sent to the client

sc_sessionExpandTTL :: Bool

if this is true, every page reload will renew the session time to live counter

sc_emptySession :: a

initial session for visitors

sc_persistCfg :: Maybe (SessionPersistCfg a)

persistence interface for sessions

sc_housekeepingInterval :: NominalDiffTime

how often should the session manager check for dangeling dead sessions

sc_hooks :: SessionHooks a

hooks into the session manager

data SessionHooks a Source

Hook into the session manager to trigger custom behavior

Constructors

SessionHooks 

Fields

sh_removed :: HashMap SessionId a -> IO ()
 

data SessionPersistCfg a Source

Constructors

SessionPersistCfg 

Fields

spc_load :: IO [(SessionId, UTCTime, a)]
 
spc_store :: [(SessionId, UTCTime, a)] -> IO ()
 

readShowSessionPersist :: (Read a, Show a) => FilePath -> SessionPersistCfg a Source

Simple session persisting configuration. DO NOT USE IN PRODUCTION

getSessionId :: SpockActionCtx ctx conn sess st SessionId Source

Get the current users sessionId. Note that this ID should only be shown to it's owner as otherwise sessions can be hijacked.

readSession :: SpockActionCtx ctx conn sess st sess Source

Read the stored session

writeSession :: sess -> SpockActionCtx ctx conn sess st () Source

Write to the current session. Note that all data is stored on the server. The user only reciedes a sessionId to be identified.

modifySession :: (sess -> sess) -> SpockActionCtx ctx conn sess st () Source

Modify the stored session

modifySession' :: (sess -> (sess, a)) -> SpockActionCtx ctx conn sess st a Source

Modify the stored session and return a value

modifyReadSession :: (sess -> sess) -> SpockActionCtx ctx conn sess st sess Source

Modify the stored session and return the new value after modification

mapAllSessions :: (sess -> STM sess) -> SpockActionCtx ctx conn sess st () Source

Apply a transformation to all sessions. Be careful with this, as this may cause many STM transaction retries.

clearAllSessions :: SpockActionCtx ctx conn sess st () Source

Globally delete all existing sessions. This is useful for example if you want to require all users to relogin

Internals for extending Spock

getSpockHeart :: MonadTrans t => t (WebStateM conn sess st) (WebState conn sess st) Source

Read the heart of Spock. This is useful if you want to construct your own monads that work with runQuery and getState using "runSpockIO"

runSpockIO :: WebState conn sess st -> WebStateM conn sess st a -> IO a Source

Run an action inside of Spocks core monad. This allows you to use runQuery and getState

type WebStateM conn sess st = WebStateT conn sess st (ResourceT IO) Source

data WebState conn sess st Source