add an example for servant-jquery: a shared counter whose value is updated via a button in an HTML page
This commit is contained in:
parent
e3af6a6af3
commit
327006e25f
9 changed files with 230 additions and 30 deletions
|
@ -1,25 +0,0 @@
|
|||
{-# LANGUAGE DataKinds #-}
|
||||
{-# LANGUAGE TypeOperators #-}
|
||||
|
||||
import Data.Proxy
|
||||
import Servant
|
||||
import Servant.JQuery
|
||||
|
||||
data Greet = Greet
|
||||
|
||||
type TestApi =
|
||||
"hello" :> Capture "name" String :> QueryParam "capital" Bool :> QueryParam "q" String :> Get Greet
|
||||
:<|> "greet" :> ReqBody Greet :> Post Greet
|
||||
:<|> "delete" :> Capture "greetid" String :> "haha" :> Delete
|
||||
|
||||
testApi :: Proxy TestApi
|
||||
testApi = Proxy
|
||||
|
||||
getHello :<|> postGreet :<|> deleteGreet = jquery testApi
|
||||
|
||||
main :: IO ()
|
||||
main =
|
||||
mapM_ printJS [ getHello "getHello"
|
||||
, postGreet "postGreet"
|
||||
, deleteGreet "deleteGreet"
|
||||
]
|
17
examples/README.md
Normal file
17
examples/README.md
Normal file
|
@ -0,0 +1,17 @@
|
|||
# Examples
|
||||
|
||||
## counter
|
||||
|
||||
This example demonstrates a *servant* server that holds a shared variable (using a `TVar`) and exposes an endpoint for reading its current value and another one for increasing its current value by 1.
|
||||
|
||||
In addition to that, it shows how you can generate the jquery-powered javascript functions corresponding to each endpoint, i.e one for reading the current value and one for increasing the value, and integrates all of that in a very simple HTML page. All these static files are served using the `serveDirectory` function from *servant*.
|
||||
|
||||
To see this all in action, simply run:
|
||||
|
||||
``` bash
|
||||
$ cabal run counter
|
||||
```
|
||||
|
||||
And point your browser to [http://localhost:8080/index.html](http://localhost:8080/index.html).
|
||||
|
||||
A copy of the generated docs is included in `counter.md` in this folder.
|
91
examples/counter.hs
Normal file
91
examples/counter.hs
Normal file
|
@ -0,0 +1,91 @@
|
|||
{-# LANGUAGE DataKinds #-}
|
||||
{-# LANGUAGE TypeOperators #-}
|
||||
{-# LANGUAGE DeriveGeneric #-}
|
||||
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
|
||||
|
||||
import Control.Concurrent.STM
|
||||
import Control.Monad.IO.Class
|
||||
import Data.Aeson
|
||||
import Data.Proxy
|
||||
import GHC.Generics
|
||||
import Network.Wai.Handler.Warp (run)
|
||||
import Servant
|
||||
import Servant.JQuery
|
||||
import System.FilePath
|
||||
|
||||
-- * A simple Counter data type
|
||||
newtype Counter = Counter { value :: Int }
|
||||
deriving (Generic, Show, Num)
|
||||
|
||||
instance ToJSON Counter
|
||||
|
||||
instance ToSample Counter where
|
||||
toSample = Just 0
|
||||
|
||||
-- * Shared counter operations
|
||||
|
||||
-- Creating a counter that starts from 0
|
||||
newCounter :: IO (TVar Counter)
|
||||
newCounter = newTVarIO 0
|
||||
|
||||
-- Increasing the counter by 1
|
||||
counterPlusOne :: MonadIO m => TVar Counter -> m Counter
|
||||
counterPlusOne counter = liftIO . atomically $ do
|
||||
oldValue <- readTVar counter
|
||||
let newValue = oldValue + 1
|
||||
writeTVar counter newValue
|
||||
return newValue
|
||||
|
||||
currentValue :: MonadIO m => TVar Counter -> m Counter
|
||||
currentValue counter = liftIO $ readTVarIO counter
|
||||
|
||||
-- * Our API type
|
||||
type TestApi = "counter" :> Post Counter -- endpoint for increasing the counter
|
||||
:<|> "counter" :> Get Counter -- endpoint to get the current value
|
||||
:<|> "doc" :> Raw -- serve the documentation
|
||||
:<|> Raw -- used for serving static files
|
||||
|
||||
testApi :: Proxy TestApi
|
||||
testApi = Proxy
|
||||
|
||||
-- * Server-side handler
|
||||
|
||||
-- where our static files reside
|
||||
www :: FilePath
|
||||
www = "examples/www"
|
||||
|
||||
-- defining handlers
|
||||
server :: TVar Counter -> Server TestApi
|
||||
server counter = counterPlusOne counter -- (+1) on the TVar
|
||||
:<|> currentValue counter -- read the TVar
|
||||
:<|> serveDocumentation testApi -- serve the API docs
|
||||
:<|> serveDirectory www -- serve static files
|
||||
|
||||
runServer :: TVar Counter -- ^ shared variable for the counter
|
||||
-> Int -- ^ port the server should listen on
|
||||
-> IO ()
|
||||
runServer var port = run port (serve testApi $ server var)
|
||||
|
||||
-- * Generating the JQuery code
|
||||
incCounterNamed :: FunctionName -> AjaxReq
|
||||
currentValueNamed :: FunctionName -> AjaxReq
|
||||
|
||||
incCounterNamed :<|> currentValueNamed :<|> _ :<|> _ = jquery testApi
|
||||
|
||||
writeJS :: FilePath -> [AjaxReq] -> IO ()
|
||||
writeJS fp functions = writeFile fp $
|
||||
concatMap generateJS functions
|
||||
|
||||
main :: IO ()
|
||||
main = do
|
||||
-- write the JS code to www/api.js at startup
|
||||
writeJS (www </> "api.js")
|
||||
[ incCounterNamed "increaseCounter"
|
||||
, currentValueNamed "getCurrentValue"
|
||||
]
|
||||
|
||||
-- setup a shared counter
|
||||
cnt <- newCounter
|
||||
|
||||
-- listen to requests on port 8080
|
||||
runServer cnt 8080
|
39
examples/counter.md
Normal file
39
examples/counter.md
Normal file
|
@ -0,0 +1,39 @@
|
|||
POST /counter
|
||||
-------------
|
||||
|
||||
**Response**:
|
||||
|
||||
- Status code 201
|
||||
- Response body as below.
|
||||
|
||||
``` javascript
|
||||
{"value":0}
|
||||
```
|
||||
|
||||
GET /doc
|
||||
--------
|
||||
|
||||
**Response**:
|
||||
|
||||
- Status code 200
|
||||
- No response body
|
||||
|
||||
GET /counter
|
||||
------------
|
||||
|
||||
**Response**:
|
||||
|
||||
- Status code 200
|
||||
- Response body as below.
|
||||
|
||||
``` javascript
|
||||
{"value":0}
|
||||
```
|
||||
|
||||
GET /
|
||||
-----
|
||||
|
||||
**Response**:
|
||||
|
||||
- Status code 200
|
||||
- No response body
|
21
examples/www/api.js
Normal file
21
examples/www/api.js
Normal file
|
@ -0,0 +1,21 @@
|
|||
|
||||
function increaseCounter(onSuccess, onError)
|
||||
{
|
||||
$.ajax(
|
||||
{ url: '/counter'
|
||||
, success: onSuccess
|
||||
, error: onError
|
||||
, type: 'POST'
|
||||
});
|
||||
}
|
||||
|
||||
function getCurrentValue(onSuccess, onError)
|
||||
{
|
||||
$.ajax(
|
||||
{ url: '/counter'
|
||||
, success: onSuccess
|
||||
, error: onError
|
||||
, type: 'GET'
|
||||
});
|
||||
}
|
||||
|
40
examples/www/index.html
Normal file
40
examples/www/index.html
Normal file
|
@ -0,0 +1,40 @@
|
|||
<html>
|
||||
<head>
|
||||
<title>Servant: counter</title>
|
||||
<style>
|
||||
body { text-align: center; }
|
||||
#counter { color: green; }
|
||||
#inc { margin: 0px 20px; background-color: green; color: white; }
|
||||
</style>
|
||||
</head>
|
||||
<body>
|
||||
<span id="counter">Counter: 0</span>
|
||||
<button id="inc">Increase</button>
|
||||
or <a href="/doc">view the docs</a>
|
||||
|
||||
<script src="/jquery.min.js" type="text/javascript"></script>
|
||||
<script src="/api.js" type="text/javascript"></script>
|
||||
<script type="text/javascript">
|
||||
$(document).ready(function() {
|
||||
// we get the current value stored by the server when the page is loaded
|
||||
getCurrentValue(updateCounter, alert);
|
||||
|
||||
// we update the value every 1sec, in the same way
|
||||
window.setInterval(function() {
|
||||
getCurrentValue(updateCounter, alert);
|
||||
}, 1000);
|
||||
});
|
||||
|
||||
function updateCounter(response)
|
||||
{
|
||||
$('#counter').html('Counter: ' + response.value);
|
||||
}
|
||||
|
||||
// when the button is clicked, ask the server to increase
|
||||
// the value by one
|
||||
$('#inc').click(function() {
|
||||
increaseCounter(updateCounter, alert);
|
||||
});
|
||||
</script>
|
||||
</body>
|
||||
</html>
|
4
examples/www/jquery.min.js
vendored
Normal file
4
examples/www/jquery.min.js
vendored
Normal file
File diff suppressed because one or more lines are too long
|
@ -21,9 +21,17 @@ library
|
|||
default-language: Haskell2010
|
||||
ghc-options: -O2 -Wall
|
||||
|
||||
executable greet
|
||||
main-is: greet.hs
|
||||
executable counter
|
||||
main-is: counter.hs
|
||||
ghc-options: -O2 -Wall
|
||||
hs-source-dirs: example
|
||||
build-depends: base, servant, servant-jquery
|
||||
hs-source-dirs: examples
|
||||
build-depends:
|
||||
aeson
|
||||
, base
|
||||
, filepath
|
||||
, servant
|
||||
, servant-jquery
|
||||
, stm
|
||||
, transformers
|
||||
, warp
|
||||
default-language: Haskell2010
|
||||
|
|
|
@ -12,7 +12,12 @@
|
|||
-- Portability : non-portable
|
||||
--
|
||||
-- Usage:
|
||||
module Servant.JQuery where
|
||||
module Servant.JQuery
|
||||
( jquery
|
||||
, generateJS
|
||||
, printJS
|
||||
, module Servant.JQuery.Internal
|
||||
) where
|
||||
|
||||
import Control.Lens
|
||||
import Data.List
|
||||
|
|
Loading…
Reference in a new issue