Spock-0.7.3.0: Another Haskell web framework for rapid development

Safe HaskellNone
LanguageHaskell98

Web.Spock.Simple

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 a = SpockT (WebStateM conn sess st) a Source

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 application with custom underlying monad

data SpockT m a Source

Instances

data ActionT m a Source

spockApp :: MonadIO m => (forall a. m a -> IO a) -> SpockT m () -> IO Application Source

Convert a Spock-App to a wai-application

Defining routes

(<#>) :: SpockRoute -> SpockRoute -> SpockRoute Source

Combine two route components safely "foo" # "bar" ===> "foobar" "foo" # "bar" ===> "foobar" "foo # "bar" ===> "foo/bar"

Hooking routes

subcomponent :: Monad m => SpockRoute -> SpockT m () -> SpockT m () Source

Define a subcomponent. Usage example:

subcomponent "/site" $
  do get "/home" homeHandler
     get "/misc/:param" $ -- ...
subcomponent "/admin" $
  do get "/home" adminHomeHandler

The request sitehome will be routed to homeHandler and the request adminhome will be routed to adminHomeHandler

get :: MonadIO m => SpockRoute -> 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 => SpockRoute -> 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 => SpockRoute -> 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 => SpockRoute -> 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 => SpockRoute -> 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 => SpockRoute -> ActionT m () -> SpockT m () Source

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

hookRoute :: Monad m => StdMethod -> SpockRoute -> ActionT m () -> SpockT m () Source

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

hookAny :: Monad m => StdMethod -> ([Text] -> ActionT m ()) -> SpockT m () Source

Specify an action that will be run when a HTTP verb matches but no defined route matches. The full path is passed as an argument

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 

Adding Wai.Middleware

middleware :: Monad m => Middleware -> SpockT m () Source

Hook wai middleware into Spock

Using Spock as middleware

spockMiddleware :: MonadIO m => (forall a. m a -> IO a) -> SpockT m () -> IO Middleware Source

Convert a Spock-App to a wai-middleware

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.