Safe Haskell | None |
---|---|
Language | Haskell98 |
This module implements the type safe routing aproach. It should be used by all new Spock powered applications. To learn more about the routing, read the corresponding blog post available at http://www.spock.li/2015/04/19/type-safe_routing.html
- spock :: SpockCfg conn sess st -> SpockM conn sess st () -> IO Middleware
- type SpockM conn sess st = SpockCtxM () conn sess st
- type SpockCtxM ctx conn sess st = SpockCtxT ctx (WebStateM conn sess st)
- spockT :: MonadIO m => (forall a. m a -> IO a) -> SpockT m () -> IO Middleware
- spockLimT :: forall m. MonadIO m => Maybe Word64 -> (forall a. m a -> IO a) -> SpockT m () -> IO Middleware
- type SpockT = SpockCtxT ()
- data SpockCtxT ctx m a
- data Path as :: [*] -> *
- root :: Path ([] *)
- type Var a = Path ((:) * a ([] *))
- var :: (Typeable * a, PathPiece a) => Path ((:) * a ([] *))
- static :: String -> Path ([] *)
- (<//>) :: Path as -> Path bs -> Path (Append as bs)
- renderRoute :: Path as -> HVectElim as Text
- subcomponent :: Monad m => Path `[]` -> SpockCtxT ctx m () -> SpockCtxT ctx m ()
- prehook :: forall m ctx ctx'. MonadIO m => ActionCtxT ctx m ctx' -> SpockCtxT ctx' m () -> SpockCtxT ctx m ()
- get :: (HasRep xs, MonadIO m) => Path xs -> HVectElim xs (ActionCtxT ctx m ()) -> SpockCtxT ctx m ()
- post :: (HasRep xs, MonadIO m) => Path xs -> HVectElim xs (ActionCtxT ctx m ()) -> SpockCtxT ctx m ()
- getpost :: (HasRep xs, MonadIO m) => Path xs -> HVectElim xs (ActionCtxT ctx m ()) -> SpockCtxT ctx m ()
- head :: (HasRep xs, MonadIO m) => Path xs -> HVectElim xs (ActionCtxT ctx m ()) -> SpockCtxT ctx m ()
- put :: (HasRep xs, MonadIO m) => Path xs -> HVectElim xs (ActionCtxT ctx m ()) -> SpockCtxT ctx m ()
- delete :: (HasRep xs, MonadIO m) => Path xs -> HVectElim xs (ActionCtxT ctx m ()) -> SpockCtxT ctx m ()
- patch :: (HasRep xs, MonadIO m) => Path xs -> HVectElim xs (ActionCtxT ctx m ()) -> SpockCtxT ctx m ()
- hookRoute :: forall xs ctx m. (HasRep xs, Monad m) => StdMethod -> Path xs -> HVectElim xs (ActionCtxT ctx m ()) -> SpockCtxT ctx m ()
- hookAny :: Monad m => StdMethod -> ([Text] -> ActionCtxT ctx m ()) -> SpockCtxT ctx m ()
- data StdMethod :: *
- middleware :: Monad m => Middleware -> SpockCtxT ctx m ()
- class (Hashable a, Eq a, Typeable a) => SafeAction conn sess st a where
- runSafeAction :: a -> SpockAction conn sess st ()
- 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
- module Web.Spock.Shared
Spock's route definition monad
spock :: SpockCfg conn sess st -> SpockM conn sess st () -> IO Middleware Source
Create a spock application using 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.
Use runSpock
to run the app or spockAsApp
to create a Wai.Application
spockT :: MonadIO m => (forall a. m a -> IO a) -> SpockT m () -> IO Middleware Source
Create a raw spock application with custom underlying monad
Use runSpock
to run the app or spockAsApp
to create a Wai.Application
The first argument is request size limit in bytes. Set to Nothing
to disable.
spockLimT :: forall m. MonadIO m => Maybe Word64 -> (forall a. m a -> IO a) -> SpockT m () -> IO Middleware Source
Like spockT
, but first argument is request size limit in bytes. Set to Nothing
to disable.
Defining routes
Rendering routes
renderRoute :: Path as -> HVectElim as Text Source
Render a route applying path pieces
Hooking routes
subcomponent :: Monad m => Path `[]` -> SpockCtxT ctx m () -> SpockCtxT ctx m () Source
Define a subcomponent. Usage example:
subcomponent "site" $ do get "home" homeHandler get ("misc" <//> var) $ -- ... subcomponent "admin" $ do get "home" adminHomeHandler
The request /site/home will be routed to homeHandler and the request /admin/home will be routed to adminHomeHandler
prehook :: forall m ctx ctx'. MonadIO m => ActionCtxT ctx m ctx' -> SpockCtxT ctx' m () -> SpockCtxT ctx m () Source
Specify an action that will be run before all subroutes. It can modify the requests current context
get :: (HasRep xs, MonadIO m) => Path xs -> HVectElim xs (ActionCtxT ctx m ()) -> SpockCtxT ctx m () Source
Specify an action that will be run when the HTTP verb GET
and the given route match
post :: (HasRep xs, MonadIO m) => Path xs -> HVectElim xs (ActionCtxT ctx m ()) -> SpockCtxT ctx m () Source
Specify an action that will be run when the HTTP verb POST
and the given route match
getpost :: (HasRep xs, MonadIO m) => Path xs -> HVectElim xs (ActionCtxT ctx m ()) -> SpockCtxT ctx m () Source
Specify an action that will be run when the HTTP verb 'GET'/'POST' and the given route match
head :: (HasRep xs, MonadIO m) => Path xs -> HVectElim xs (ActionCtxT ctx m ()) -> SpockCtxT ctx m () Source
Specify an action that will be run when the HTTP verb HEAD
and the given route match
put :: (HasRep xs, MonadIO m) => Path xs -> HVectElim xs (ActionCtxT ctx m ()) -> SpockCtxT ctx m () Source
Specify an action that will be run when the HTTP verb PUT
and the given route match
delete :: (HasRep xs, MonadIO m) => Path xs -> HVectElim xs (ActionCtxT ctx m ()) -> SpockCtxT ctx m () Source
Specify an action that will be run when the HTTP verb DELETE
and the given route match
patch :: (HasRep xs, MonadIO m) => Path xs -> HVectElim xs (ActionCtxT ctx m ()) -> SpockCtxT ctx m () Source
Specify an action that will be run when the HTTP verb PATCH
and the given route match
hookRoute :: forall xs ctx m. (HasRep xs, Monad m) => StdMethod -> Path xs -> HVectElim xs (ActionCtxT ctx m ()) -> SpockCtxT ctx m () Source
Specify an action that will be run when a HTTP verb and the given route match
hookAny :: Monad m => StdMethod -> ([Text] -> ActionCtxT ctx m ()) -> SpockCtxT ctx 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).
Adding Wai.Middleware
middleware :: Monad m => Middleware -> SpockCtxT ctx m () Source
Hook wai middleware into Spock
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
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" <//> var) $ \userId -> do deleteUrl <- safeActionPath (DeleteUser userId) html $ "Click <a href='" <> deleteUrl <> "'>here</a> to delete user!"
Note that safeActions currently only support GET and POST requests.
module Web.Spock.Shared