Spock-0.6.6.0: Another Haskell web framework for rapid development

Safe HaskellNone
LanguageHaskell98

Web.Spock

Contents

Synopsis

Spock's core

spock :: Int -> SessionCfg sess -> PoolOrConn conn -> st -> SpockM conn sess st () -> IO () Source

Run a spock application using the warp server, a given db storageLayer and an initial state. Spock works with database libraries that already implement connection pooling and with those that don't come with it out of the box. For more see the PoolOrConn type.

type SpockM conn sess st = SpockT (WebStateM conn sess st) Source

Inside the SpockM monad, you may define routes and middleware.

type SpockAction conn sess st = ActionT (WebStateM conn sess st) Source

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

spockT :: MonadIO m => Port -> (forall a. m a -> IO a) -> SpockT m () -> IO () Source

Run a raw spock server on a defined port. If you don't need a custom base monad you can just supply id as lift function.

Defining routes

get :: MonadIO m => Text -> ActionT m () -> SpockT m () Source

Specify an action that will be run when the HTTP verb GET and the given route match

post :: MonadIO m => Text -> ActionT m () -> SpockT m () Source

Specify an action that will be run when the HTTP verb POST and the given route match

head :: MonadIO m => Text -> ActionT m () -> SpockT m () Source

Specify an action that will be run when the HTTP verb HEAD and the given route match

put :: MonadIO m => Text -> ActionT m () -> SpockT m () Source

Specify an action that will be run when the HTTP verb PUT and the given route match

delete :: MonadIO m => Text -> ActionT m () -> SpockT m () Source

Specify an action that will be run when the HTTP verb DELETE and the given route match

patch :: MonadIO m => Text -> ActionT m () -> SpockT m () Source

Specify an action that will be run when the HTTP verb PATCH and the given route match

defRoute :: MonadIO m => StdMethod -> Text -> ActionT m () -> SpockT m () Source

Define a route matching a provided StdMethod and route

subcomponent :: MonadIO m => Text -> SpockT m a -> SpockT m a Source

Define a subcomponent

subcomponent "/api" $
   do get "/user" $ text "USER"
      post "/new-user" $ text "OK!"
>>> curl http://localhost:8080/api/user
USER

data StdMethod :: *

HTTP standard method (as defined by RFC 2616, and PATCH which is defined by RFC 5789).

Constructors

GET 
POST 
HEAD 
PUT 
DELETE 
TRACE 
CONNECT 
OPTIONS 
PATCH 

combineRoute :: Text -> Text -> Text Source

Combine two routes, ensuring that the slashes don't get messed up

Handeling requests

request :: MonadIO m => ActionT m Request Source

Get the original Wai Request object

header :: MonadIO m => Text -> ActionT m (Maybe Text) Source

Read a header

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

Read a cookie

body :: MonadIO m => ActionT m ByteString Source

Get the raw request body

jsonBody :: (MonadIO m, FromJSON a) => ActionT m (Maybe a) Source

Parse the request body as json

jsonBody' :: (MonadIO m, FromJSON a) => ActionT m a Source

Parse the request body as json and fails with 500 status code on error

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

Get uploaded files

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

Get all request params

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

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

param' :: (PathPiece p, MonadIO m) => Text -> ActionT m p Source

Like param, but outputs an error when a param is missing

Sending responses

setStatus :: MonadIO m => Status -> ActionT m () Source

Set a response status

setHeader :: MonadIO m => Text -> Text -> ActionT m () Source

Set a response header. Overwrites already defined headers

redirect :: MonadIO m => Text -> ActionT m a Source

Redirect to a given url

jumpNext :: MonadIO m => ActionT m a Source

Abort the current action and jump the next one matching the route

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

Set a cookie living for a given number of seconds

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

Set a cookie living until a specific UTCTime

bytes :: MonadIO m => ByteString -> ActionT m a Source

Send a ByteString as response body. Provide your own Content-Type

lazyBytes :: MonadIO m => ByteString -> ActionT m a Source

Send a lazy ByteString as response body. Provide your own Content-Type

text :: MonadIO m => Text -> ActionT m a Source

Send text as a response body. Content-Type will be "text/plain"

html :: MonadIO m => Text -> ActionT m a Source

Send a text as response body. Content-Type will be "text/plain"

file :: MonadIO m => Text -> FilePath -> ActionT m a Source

Send a file as response

json :: (ToJSON a, MonadIO m) => a -> ActionT m b Source

Send json as response. Content-Type will be "application/json"

blaze :: MonadIO m => Html -> ActionT m a Source

Send blaze html as response. Content-Type will be "text/html"

Adding middleware

Database

data PoolOrConn a 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) 
PCConn (ConnBuilder a) 

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) 

Sessions

data SessionCfg a Source

Configuration for the session manager

readSession :: SpockAction conn sess st sess Source

Read the stored session

writeSession :: sess -> SpockAction 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) -> SpockAction conn sess st () Source

Modify the stored session

clearAllSessions :: SpockAction conn sess st () Source

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

Basic HTTP-Auth

requireBasicAuth :: MonadIO m => Text -> (Text -> Text -> m Bool) -> ActionT m a -> ActionT 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 ;-)"

Safe actions

class (Hashable a, Eq a, Typeable a) => SafeAction conn sess st a where Source

SafeActions are actions that need to be protected from csrf attacks

Methods

runSafeAction :: a -> SpockAction conn sess st () Source

The body of the safe action. Either GET or POST

safeActionPath :: forall conn sess st a. (SafeAction conn sess st a, HasSpock (SpockAction conn sess st), SpockConn (SpockAction conn sess st) ~ conn, SpockSession (SpockAction conn sess st) ~ sess, SpockState (SpockAction conn sess st) ~ st) => a -> SpockAction conn sess st Text Source

Wire up a safe action: Safe actions are actions that are protected from csrf attacks. Here's a usage example:

newtype DeleteUser = DeleteUser Int deriving (Hashable, Typeable, Eq)

instance SafeAction Connection () () DeleteUser where
   runSafeAction (DeleteUser i) =
      do runQuery $ deleteUserFromDb i
         redirect "/user-list"

get "/user-details/:userId" $
  do userId <- param' "userId"
     deleteUrl <- safeActionPath (DeleteUser userId)
     html $ "Click <a href='" <> deleteUrl <> "'>here</a> to delete user!"

Note that safeActions currently only support GET and POST requests.

Digestive Functors

runForm Source

Arguments

:: (Functor m, MonadIO m) 
=> Text

form name

-> Form v (ActionT m) a 
-> ActionT m (View v, Maybe a) 

Run a digestive functors form

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

data WebStateM conn sess st a Source

Instances

MonadBase IO (WebStateM conn sess st) 
MonadBaseControl IO (WebStateM conn sess st) 
MonadTrans t => HasSpock (t (WebStateM conn sess st)) 
Monad (WebStateM conn sess st) 
Functor (WebStateM conn sess st) 
Applicative (WebStateM conn sess st) 
MonadIO (WebStateM conn sess st) 
HasSpock (WebStateM conn sess st) 
MonadReader (WebState conn sess st) (WebStateM conn sess st) 
type SpockConn (t (WebStateM conn sess st)) = conn 
type SpockState (t (WebStateM conn sess st)) = st 
type SpockSession (t (WebStateM conn sess st)) = sess 
data StM (WebStateM conn sess st) = WStM {} 
type SpockConn (WebStateM conn sess st) = conn 
type SpockState (WebStateM conn sess st) = st 
type SpockSession (WebStateM conn sess st) = sess 

data WebState conn sess st Source

Instances

MonadReader (WebState conn sess st) (WebStateM conn sess st)