Safe Haskell | None |
---|
Web.Spock
Contents
- spock :: Int -> SessionCfg sess -> PoolOrConn conn -> st -> SpockM conn sess st () -> IO ()
- type SpockM conn sess st a = ScottyT Text (WebStateM conn sess st) a
- type SpockAction conn sess st a = ActionT Text (WebStateM conn sess st) a
- data PoolOrConn a
- = PCPool (Pool a)
- | PCConduitPool (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
- data SessionCfg a = SessionCfg {}
- readSession :: SpockAction conn sess st sess
- writeSession :: sess -> SpockAction conn sess st ()
- modifySession :: (sess -> sess) -> SpockAction conn sess st ()
- setCookie :: (SpockError e, MonadIO m) => Text -> Text -> NominalDiffTime -> ActionT e m ()
- setCookie' :: (SpockError e, MonadIO m) => Text -> Text -> UTCTime -> ActionT e m ()
- getCookie :: (SpockError e, MonadIO m) => Text -> ActionT e m (Maybe Text)
- get :: (ScottyError e, MonadIO m) => RoutePattern -> ActionT e m () -> ScottyT e m ()
- post :: (ScottyError e, MonadIO m) => RoutePattern -> ActionT e m () -> ScottyT e m ()
- put :: (ScottyError e, MonadIO m) => RoutePattern -> ActionT e m () -> ScottyT e m ()
- delete :: (ScottyError e, MonadIO m) => RoutePattern -> ActionT e m () -> ScottyT e m ()
- patch :: (ScottyError e, MonadIO m) => RoutePattern -> ActionT e m () -> ScottyT e m ()
- addroute :: (ScottyError e, MonadIO m) => StdMethod -> RoutePattern -> ActionT e m () -> ScottyT e m ()
- data StdMethod
- middleware :: Monad m => Middleware -> ScottyT e m ()
- matchAny :: (ScottyError e, MonadIO m) => RoutePattern -> ActionT e m () -> ScottyT e m ()
- notFound :: (ScottyError e, MonadIO m) => ActionT e m () -> ScottyT e m ()
- request :: (ScottyError e, Monad m) => ActionT e m Request
- reqHeader :: (ScottyError e, Monad m) => Text -> ActionT e m (Maybe Text)
- body :: (ScottyError e, Monad m) => ActionT e m ByteString
- param :: (Parsable a, ScottyError e, Monad m) => Text -> ActionT e m a
- params :: (ScottyError e, Monad m) => ActionT e m [Param]
- jsonData :: (FromJSON a, ScottyError e, Monad m) => ActionT e m a
- files :: (ScottyError e, Monad m) => ActionT e m [File]
- status :: (ScottyError e, Monad m) => Status -> ActionT e m ()
- addHeader :: (ScottyError e, Monad m) => Text -> Text -> ActionT e m ()
- setHeader :: (ScottyError e, Monad m) => Text -> Text -> ActionT e m ()
- redirect :: (ScottyError e, Monad m) => Text -> ActionT e m a
- text :: (ScottyError e, Monad m) => Text -> ActionT e m ()
- html :: (ScottyError e, Monad m) => Text -> ActionT e m ()
- file :: (ScottyError e, Monad m) => FilePath -> ActionT e m ()
- json :: (ToJSON a, ScottyError e, Monad m) => a -> ActionT e m ()
- source :: (ScottyError e, Monad m) => Source IO (Flush Builder) -> ActionT e m ()
- raw :: (ScottyError e, Monad m) => ByteString -> ActionT e m ()
- raise :: (ScottyError e, Monad m) => e -> ActionT e m a
- rescue :: (ScottyError e, Monad m) => ActionT e m a -> (e -> ActionT e m a) -> ActionT e m a
- next :: (ScottyError e, Monad m) => ActionT e m a
- data RoutePattern
- paramPathPiece :: PathPiece s => Text -> SpockAction conn sess st s
- 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
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 = ScottyT Text (WebStateM conn sess st) aSource
Spock is supercharged Scotty, that's why the SpockM
is built on the
ScottyT monad. Insive the SpockM monad, you may define routes and middleware.
type SpockAction conn sess st a = ActionT Text (WebStateM conn sess st) aSource
The SpockAction is the monad of all route-actions. You have access to the database, session and state of your application.
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) | |
PCConduitPool (Pool a) | |
PCConn (ConnBuilder a) |
data ConnBuilder a Source
The ConnBuilder instructs Spock how to create or close a database connection.
Constructors
ConnBuilder | |
Fields
|
If Spock should take care of connection pooling, you need to configure it depending on what you need.
Constructors
PoolCfg | |
Fields |
Accessing Database and State
Methods
runQuery :: (SpockConn m -> IO a) -> m aSource
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
readSession :: SpockAction conn sess st sessSource
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
Cookies
setCookie :: (SpockError e, MonadIO m) => Text -> Text -> NominalDiffTime -> ActionT e m ()Source
Set a cookie living for a given number of seconds
setCookie' :: (SpockError e, MonadIO m) => Text -> Text -> UTCTime -> ActionT e m ()Source
Set a cookie living until a specific UTCTime
getCookie :: (SpockError e, MonadIO m) => Text -> ActionT e m (Maybe Text)Source
Read a cookie previously set in the users browser for your site
General Routing
get :: (ScottyError e, MonadIO m) => RoutePattern -> ActionT e m () -> ScottyT e m ()
post :: (ScottyError e, MonadIO m) => RoutePattern -> ActionT e m () -> ScottyT e m ()
put :: (ScottyError e, MonadIO m) => RoutePattern -> ActionT e m () -> ScottyT e m ()
delete :: (ScottyError e, MonadIO m) => RoutePattern -> ActionT e m () -> ScottyT e m ()
patch :: (ScottyError e, MonadIO m) => RoutePattern -> ActionT e m () -> ScottyT e m ()
addroute :: (ScottyError e, MonadIO m) => StdMethod -> RoutePattern -> ActionT e m () -> ScottyT e m ()
Define a route with a StdMethod
, Text
value representing the path spec,
and a body (Action
) which modifies the response.
addroute GET "/" $ text "beam me up!"
The path spec can include values starting with a colon, which are interpreted
as captures. These are named wildcards that can be looked up with param
.
addroute GET "/foo/:bar" $ do v <- param "bar" text v
>>>
curl http://localhost:3000/foo/something
something
data StdMethod
HTTP standard method (as defined by RFC 2616, and PATCH which is defined by RFC 5789).
Other reexports from scotty
middleware :: Monad m => Middleware -> ScottyT e m ()
Use given middleware. Middleware is nested such that the first declared is the outermost middleware (it has first dibs on the request and last action on the response). Every middleware is run on each request.
matchAny :: (ScottyError e, MonadIO m) => RoutePattern -> ActionT e m () -> ScottyT e m ()
Add a route that matches regardless of the HTTP verb.
notFound :: (ScottyError e, MonadIO m) => ActionT e m () -> ScottyT e m ()
Specify an action to take if nothing else is found. Note: this _always_ matches, so should generally be the last route specified.
reqHeader :: (ScottyError e, Monad m) => Text -> ActionT e m (Maybe Text)
Get a request header. Header name is case-insensitive.
body :: (ScottyError e, Monad m) => ActionT e m ByteString
Get the request body.
param :: (Parsable a, ScottyError e, Monad m) => Text -> ActionT e m a
Get a parameter. First looks in captures, then form data, then query parameters.
params :: (ScottyError e, Monad m) => ActionT e m [Param]
Get all parameters from capture, form and query (in that order).
jsonData :: (FromJSON a, ScottyError e, Monad m) => ActionT e m a
Parse the request body as a JSON object and return it. Raises an exception if parse is unsuccessful.
files :: (ScottyError e, Monad m) => ActionT e m [File]
Get list of uploaded files.
status :: (ScottyError e, Monad m) => Status -> ActionT e m ()
Set the HTTP response status. Default is 200.
addHeader :: (ScottyError e, Monad m) => Text -> Text -> ActionT e m ()
Add to the response headers. Header names are case-insensitive.
setHeader :: (ScottyError e, Monad m) => Text -> Text -> ActionT e m ()
Set one of the response headers. Will override any previously set value for that header. Header names are case-insensitive.
redirect :: (ScottyError e, Monad m) => Text -> ActionT e m a
Redirect to given URL. Like throwing an uncatchable exception. Any code after the call to redirect will not be run.
redirect "http://www.google.com"
OR
redirect "/foo/bar"
text :: (ScottyError e, Monad m) => Text -> ActionT e m ()
Set the body of the response to the given Text
value. Also sets "Content-Type"
header to "text/plain".
html :: (ScottyError e, Monad m) => Text -> ActionT e m ()
Set the body of the response to the given Text
value. Also sets "Content-Type"
header to "text/html".
file :: (ScottyError e, Monad m) => FilePath -> ActionT e m ()
Send a file as the response. Doesn't set the "Content-Type" header, so you probably
want to do that on your own with setHeader
.
json :: (ToJSON a, ScottyError e, Monad m) => a -> ActionT e m ()
Set the body of the response to the JSON encoding of the given value. Also sets "Content-Type" header to "application/json".
source :: (ScottyError e, Monad m) => Source IO (Flush Builder) -> ActionT e m ()
Set the body of the response to a Source. Doesn't set the
"Content-Type" header, so you probably want to do that on your
own with setHeader
.
raw :: (ScottyError e, Monad m) => ByteString -> ActionT e m ()
Set the body of the response to the given ByteString
value. Doesn't set the
"Content-Type" header, so you probably want to do that on your
own with setHeader
.
raise :: (ScottyError e, Monad m) => e -> ActionT e m a
Throw an exception, which can be caught with rescue
. Uncaught exceptions
turn into HTTP 500 responses.
rescue :: (ScottyError e, Monad m) => ActionT e m a -> (e -> ActionT e m a) -> ActionT e m a
Catch an exception thrown by raise
.
raise "just kidding" `rescue` (\msg -> text msg)
next :: (ScottyError e, Monad m) => ActionT e m a
Abort execution of this action and continue pattern matching routes.
Like an exception, any code after next
is not executed.
As an example, these two routes overlap. The only way the second one will
ever run is if the first one calls next
.
get "/foo/:bar" $ do w :: Text <- param "bar" unless (w == "special") next text "You made a request to /foo/special" get "/foo/:baz" $ do w <- param "baz" text $ "You made a request to: " <> w
data RoutePattern
Instances
Spock utilities
paramPathPiece :: PathPiece s => Text -> SpockAction conn sess st sSource
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 aSource
Run an action inside of Spocks core monad. This allows you to use runQuery and getState
data WebStateM conn sess st a Source
Instances
MonadBaseControl IO (WebStateM conn sess st) | |
MonadBase 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) |
data WebState conn sess st Source
Instances
MonadReader (WebState conn sess st) (WebStateM conn sess st) |