Safe Haskell | None |
---|
- spock :: Int -> StorageLayer conn -> st -> SpockM conn sess st () -> IO ()
- authed :: StdMethod -> [Text] -> RoutePattern -> (conn -> sess -> IO (Maybe user)) -> (conn -> user -> [Text] -> IO Bool) -> (user -> ActionT (WebStateM conn sess st) ()) -> SpockM conn sess st ()
- runQuery :: MonadTrans t => (conn -> IO a) -> t (WebStateM conn sess st) a
- getState :: MonadTrans t => t (WebStateM conn sess st) st
- data StdMethod
- type SpockM conn sess st a = ScottyT (WebStateM conn sess st) a
- authedUser :: user -> (user -> sess) -> ActionT (WebStateM conn sess st) ()
- unauthCurrent :: ActionT (WebStateM conn sess st) ()
- data StorageLayer a = StorageLayer {
- sl_createConn :: IO a
- sl_closeConn :: a -> IO ()
- middleware :: Monad m => Middleware -> ScottyT m ()
- get :: MonadIO m => RoutePattern -> ActionT m () -> ScottyT m ()
- post :: MonadIO m => RoutePattern -> ActionT m () -> ScottyT m ()
- put :: MonadIO m => RoutePattern -> ActionT m () -> ScottyT m ()
- delete :: MonadIO m => RoutePattern -> ActionT m () -> ScottyT m ()
- patch :: MonadIO m => RoutePattern -> ActionT m () -> ScottyT m ()
- addroute :: MonadIO m => StdMethod -> RoutePattern -> ActionT m () -> ScottyT m ()
- matchAny :: MonadIO m => RoutePattern -> ActionT m () -> ScottyT m ()
- notFound :: MonadIO m => ActionT m () -> ScottyT m ()
- request :: Monad m => ActionT m Request
- reqHeader :: Monad m => Text -> ActionT m (Maybe Text)
- body :: Monad m => ActionT m ByteString
- param :: (Parsable a, Monad m) => Text -> ActionT m a
- params :: Monad m => ActionT m [Param]
- jsonData :: (FromJSON a, Monad m) => ActionT m a
- files :: Monad m => ActionT m [File]
- status :: Monad m => Status -> ActionT m ()
- addHeader :: Monad m => Text -> Text -> ActionT m ()
- setHeader :: Monad m => Text -> Text -> ActionT m ()
- redirect :: Monad m => Text -> ActionT m a
- text :: Monad m => Text -> ActionT m ()
- html :: Monad m => Text -> ActionT m ()
- file :: Monad m => FilePath -> ActionT m ()
- json :: (ToJSON a, Monad m) => a -> ActionT m ()
- source :: Monad m => Source (ResourceT IO) (Flush Builder) -> ActionT m ()
- raw :: Monad m => ByteString -> ActionT m ()
- raise :: Monad m => Text -> ActionT m a
- rescue :: Monad m => ActionT m a -> (Text -> ActionT m a) -> ActionT m a
- next :: Monad m => ActionT m a
Spock's core functions, types and helpers
spock :: Int -> StorageLayer conn -> st -> SpockM conn sess st () -> IO ()Source
Run a spock application using the warp server, a given db storageLayer and an initial state
authed :: StdMethod -> [Text] -> RoutePattern -> (conn -> sess -> IO (Maybe user)) -> (conn -> user -> [Text] -> IO Bool) -> (user -> ActionT (WebStateM conn sess st) ()) -> SpockM conn sess st ()Source
Before the request is performed, you can check if the signed in user has permissions to view the contents of the request. You may want to define a helper function that proxies this function to not pass around loadUser and checkRights all the time
runQuery :: MonadTrans t => (conn -> IO a) -> t (WebStateM conn sess st) aSource
getState :: MonadTrans t => t (WebStateM conn sess st) stSource
data StdMethod
HTTP standard method (as defined by RFC 2616, and PATCH which is defined by RFC 5789).
authedUser :: user -> (user -> sess) -> ActionT (WebStateM conn sess st) ()Source
After checking that a login was successfull, register the usersId into the session and create a session cookie for later authed requests to work properly
unauthCurrent :: ActionT (WebStateM conn sess st) ()Source
Destroy the current users session
data StorageLayer a Source
StorageLayer | |
|
Reexports from scotty
middleware :: Monad m => Middleware -> ScottyT 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.
addroute :: MonadIO m => StdMethod -> RoutePattern -> ActionT m () -> ScottyT 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
matchAny :: MonadIO m => RoutePattern -> ActionT m () -> ScottyT m ()
Add a route that matches regardless of the HTTP verb.
notFound :: MonadIO m => ActionT m () -> ScottyT m ()
Specify an action to take if nothing else is found. Note: this _always_ matches, so should generally be the last route specified.
reqHeader :: Monad m => Text -> ActionT m (Maybe Text)
Get a request header. Header name is case-insensitive.
body :: Monad m => ActionT m ByteString
Get the request body.
param :: (Parsable a, Monad m) => Text -> ActionT m a
Get a parameter. First looks in captures, then form data, then query parameters.
params :: Monad m => ActionT m [Param]
Get all parameters from capture, form and query (in that order).
jsonData :: (FromJSON a, Monad m) => ActionT m a
Parse the request body as a JSON object and return it. Raises an exception if parse is unsuccessful.
addHeader :: Monad m => Text -> Text -> ActionT m ()
Add to the response headers. Header names are case-insensitive.
setHeader :: Monad m => Text -> Text -> ActionT m ()
Set one of the response headers. Will override any previously set value for that header. Header names are case-insensitive.
redirect :: Monad m => Text -> ActionT 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 :: Monad m => Text -> ActionT m ()
Set the body of the response to the given Text
value. Also sets "Content-Type"
header to "text/plain".
html :: Monad m => Text -> ActionT m ()
Set the body of the response to the given Text
value. Also sets "Content-Type"
header to "text/html".
file :: Monad m => FilePath -> ActionT 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 header
.
json :: (ToJSON a, Monad m) => a -> ActionT m ()
Set the body of the response to the JSON encoding of the given value. Also sets "Content-Type" header to "application/json".
source :: Monad m => Source (ResourceT IO) (Flush Builder) -> ActionT 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 header
.
raw :: Monad m => ByteString -> ActionT 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 header
.
raise :: Monad m => Text -> ActionT m a
Throw an exception, which can be caught with rescue
. Uncaught exceptions
turn into HTTP 500 responses.
rescue :: Monad m => ActionT m a -> (Text -> ActionT m a) -> ActionT m a
Catch an exception thrown by raise
.
raise "just kidding" `rescue` (\msg -> text msg)
next :: Monad m => ActionT 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/:number" $ do n <- param "number" unless (all isDigit n) $ next text "a number" get "/foo/:bar" $ do bar <- param "bar" text "not a number"