Examples below have been tested with Spock-0.12.
A “hello world” example
{-# LANGUAGE OverloadedStrings #-}
module Main where
import Data.Monoid ((<>))
import Web.Spock
import Web.Spock.Config
main :: IO ()
main = do
config <- defaultSpockCfg () PCNoDatabase ()
runSpock 8080 $ spock config app
app :: SpockM () () () ()
app = do
-- When “/” is requested, show “Hello world!”
get root $
text "Hello world!"
-- When “/hello/<name>” is requested, show “Hello <name>!”
get ("hello" <//> var) $ \name ->
text ("Hello " <> name <> "!")
Parts of this example are explained in detail in the official Spock tutorial. In a nutshell:
-
We create a Spock config with defaultSpockCfg
. Our session type is ()
and our state type is ()
as well (because we don't have any state or sessions).
-
runSpock <port> . spock config
runs a SpockM
action. You can register handlers inside SpockM
– e.g. get
registers a handler for a GET request.
-
Handlers run in the ActionT
monad. In this monad you can do various things (this is an incomplete list):
- get the request body with
body
or json
- get a query/form parameter with
param
or param'
- add something to the response that is going to be sent back (with
text
or bytes
or html
)
- set a header (e.g. content-type) with
setHeader
- set up a redirect with
redirect
-
Routes can include var
into them. Thanks to some type-level magic, when you include var
into a route, get
/post
/etc will automatically take that piece of the route and provide it to the handler as a lambda parameter. Moreover, if your handler requires e.g. Int
, the piece will be automatically converted to Int
.
Persistent textbox
A more complicated example – a page with a textbox that is saved on server when you type anything into it.
We're going to store our text in an IORef
(no databases yet, let's keep it in memory), and we'll use lucid for HTML generation.
{-# LANGUAGE OverloadedStrings #-}
module Main (main) where
-- Monads
import Control.Monad.Trans
-- IO
import Data.IORef
-- Text
import Data.Text (Text)
import qualified Data.Text.Lazy as TL
-- Web
import Lucid
import Web.Spock
import Web.Spock.Config
-- Take a Lucid action that generates HTML, and write that HTML to a page.
lucid :: MonadIO m => HtmlT m a -> ActionT m a
lucid x = do
rendered <- lift (renderTextT x)
html (TL.toStrict rendered)
main :: IO ()
main = do
-- Create a variable that would hold the contents of the textbox
textVar <- newIORef ("" :: Text)
-- Run the app
config <- defaultSpockCfg () PCNoDatabase textVar
runSpock 8080 $ spock config app
app :: SpockM () () (IORef Text) ()
app = do
-- On “/store”: receive text from the POST parameter and update the variable
post "store" $ do
content <- param' "content"
textVar <- getState
liftIO $ writeIORef textVar content
-- On “/”: render the main page
get root $ lucid $ do
-- Include jQuery (it's overkill for a small example like this one, but
-- I wanted to show how to include scripts)
head_ $ do
script_ [src_ "https://code.jquery.com/jquery-2.2.2.min.js"] ("" :: Text)
-- Read the text variable and render a textbox containing the text; the
-- textbox has an event handler attached to it that makes a POST request
-- whenever the contents of the editbox change
body_ $ do
textVar <- getState
content <- liftIO $ readIORef textVar
let inputHandler = "$.post('/store', {content: this.value})"
textarea_ [oninput_ inputHandler] (toHtml content)
Sessions
A session is just a value that the server keeps in memory for each visitor; the visitor is identified by storing a cookie in the browser.
Here's a simple example that records the number of times the visitor was on the main page:
{-# LANGUAGE OverloadedStrings #-}
module Main where
import Data.Monoid
import Web.Spock
import qualified Data.Text as T
main :: IO ()
main = do
-- “0” will be the default session value for each new user.
config <- defaultSpockCfg 0 PCNoDatabase ()
runSpock 8080 $ spock config app
app :: SpockM () Int () ()
app = do
get root $ do
-- Increase the stored number and return the new number.
n <- modifyReadSession (+1)
text ("You visited this page " <> T.pack (show n) <> " times.")
Gotchas
-
By default Spock prints “Spock is running on port N” – if you don't want it, use runSpockNoBanner
instead of runSpock
.
-
After you've output anything (with text
or bytes
or something else), the action finishes. So, text
/bytes
/html
should be the last function you call.