Safe Haskell | None |
---|---|
Language | Haskell98 |
- runSpock :: Port -> IO Middleware -> IO ()
- spockAsApp :: IO Middleware -> IO Application
- request :: MonadIO m => ActionT m Request
- header :: MonadIO m => Text -> ActionT m (Maybe Text)
- cookie :: MonadIO m => Text -> ActionT m (Maybe Text)
- preferredFormat :: MonadIO m => ActionT m ClientPreferredFormat
- data ClientPreferredFormat
- body :: MonadIO m => ActionT m ByteString
- jsonBody :: (MonadIO m, FromJSON a) => ActionT m (Maybe a)
- jsonBody' :: (MonadIO m, FromJSON a) => ActionT m a
- files :: MonadIO m => ActionT m (HashMap Text UploadedFile)
- data UploadedFile = UploadedFile {}
- params :: MonadIO m => ActionT m [(Text, Text)]
- param :: (PathPiece p, MonadIO m) => Text -> ActionT m (Maybe p)
- param' :: (PathPiece p, MonadIO m) => Text -> ActionT m p
- setStatus :: MonadIO m => Status -> ActionT m ()
- setHeader :: MonadIO m => Text -> Text -> ActionT m ()
- redirect :: MonadIO m => Text -> ActionT m a
- jumpNext :: MonadIO m => ActionT m a
- setCookie :: MonadIO m => Text -> Text -> NominalDiffTime -> ActionT m ()
- setCookie' :: MonadIO m => Text -> Text -> UTCTime -> ActionT m ()
- bytes :: MonadIO m => ByteString -> ActionT m a
- lazyBytes :: MonadIO m => ByteString -> ActionT m a
- text :: MonadIO m => Text -> ActionT m a
- html :: MonadIO m => Text -> ActionT m a
- file :: MonadIO m => Text -> FilePath -> ActionT m a
- json :: (ToJSON a, MonadIO m) => a -> ActionT m b
- blaze :: MonadIO m => Html -> ActionT m a
- middlewarePass :: MonadIO m => ActionT m a
- modifyVault :: MonadIO m => (Vault -> Vault) -> ActionT m ()
- queryVault :: MonadIO m => Key a -> ActionT m (Maybe a)
- data PoolOrConn a
- = PCPool (Pool a)
- | PCConn (ConnBuilder a)
- data ConnBuilder a = ConnBuilder {
- cb_createConn :: IO a
- cb_destroyConn :: a -> IO ()
- cb_poolConfiguration :: PoolCfg
- data PoolCfg = PoolCfg {}
- class HasSpock m where
- type SpockConn m :: *
- type SpockState m :: *
- type SpockSession m :: *
- runQuery :: (SpockConn m -> IO a) -> m a
- getState :: m (SpockState m)
- requireBasicAuth :: MonadIO m => Text -> (Text -> Text -> m Bool) -> ActionT m a -> ActionT m a
- data SessionCfg a = SessionCfg {}
- type SessionId = Text
- getSessionId :: SpockAction conn sess st SessionId
- readSession :: SpockAction conn sess st sess
- writeSession :: sess -> SpockAction conn sess st ()
- modifySession :: (sess -> sess) -> SpockAction conn sess st ()
- clearAllSessions :: SpockAction conn sess st ()
- runForm :: (Functor m, MonadIO m) => Text -> Form v (ActionT m) a -> ActionT m (View v, Maybe a)
- getSpockHeart :: MonadTrans t => t (WebStateM conn sess st) (WebState conn sess st)
- runSpockIO :: WebState conn sess st -> WebStateM conn sess st a -> IO a
- data WebStateM conn sess st a
- data WebState conn sess st
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
Handeling requests
preferredFormat :: MonadIO m => ActionT m ClientPreferredFormat Source
Tries to dected the preferred format of the response using the Accept header
body :: MonadIO m => ActionT m ByteString Source
Get the raw request body
jsonBody' :: (MonadIO m, FromJSON a) => ActionT m a Source
Parse the request body as json and fails with 500 status code on error
data UploadedFile Source
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
setHeader :: MonadIO m => Text -> Text -> ActionT m () Source
Set a response header. Overwrites already defined headers
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/html"
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"
Middleware helpers
middlewarePass :: MonadIO m => ActionT m a Source
If the Spock application is used as a middleware, you can use this to pass request handeling 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) -> ActionT m () Source
Modify the vault (useful for sharing data between middleware and app)
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
PCPool (Pool a) | |
PCConn (ConnBuilder a) |
data ConnBuilder a Source
The ConnBuilder instructs Spock how to create or close a database connection.
ConnBuilder | |
|
If Spock should take care of connection pooling, you need to configure it depending on what you need.
Accessing Database and State
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.
MonadTrans t => HasSpock (t (WebStateM conn sess st)) | |
HasSpock (WebStateM conn sess st) |
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 ;-)"
Sessions
data SessionCfg a Source
Configuration for the session manager
getSessionId :: SpockAction 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 :: 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
Digestive Functors
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
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 | |
type SpockConn (WebStateM conn sess st) = conn | |
type SpockState (WebStateM conn sess st) = st | |
type SpockSession (WebStateM conn sess st) = sess | |
type StM (WebStateM conn sess st) a |
data WebState conn sess st Source
MonadReader (WebState conn sess st) (WebStateM conn sess st) |