Replace servant-jquery with servant-js in remaining files
This commit is contained in:
parent
6a4c967590
commit
b88981cf14
3 changed files with 29 additions and 24 deletions
|
@ -2,11 +2,14 @@
|
||||||
|
|
||||||
![servant](https://raw.githubusercontent.com/haskell-servant/servant/master/servant.png)
|
![servant](https://raw.githubusercontent.com/haskell-servant/servant/master/servant.png)
|
||||||
|
|
||||||
This library lets you derive automatically (JQuery based) Javascript functions that let you query each endpoint of a *servant* webservice.
|
This library lets you derive automatically Javascript functions that let you query each endpoint of a *servant* webservice.
|
||||||
|
|
||||||
|
It contains a powerful system allowing you to generate functions for several frameworks (Angular, AXios, JQuery) as well as
|
||||||
|
vanilla (framework-free) javascript code.
|
||||||
|
|
||||||
## Example
|
## Example
|
||||||
|
|
||||||
Read more about the following example [here](https://github.com/haskell-servant/servant/tree/master/servant-jquery/tree/master/examples#examples).
|
Read more about the following example [here](https://github.com/haskell-servant/servant/tree/master/servant-js/tree/master/examples#examples).
|
||||||
|
|
||||||
``` haskell
|
``` haskell
|
||||||
{-# LANGUAGE DataKinds #-}
|
{-# LANGUAGE DataKinds #-}
|
||||||
|
@ -21,7 +24,7 @@ import Data.Proxy
|
||||||
import GHC.Generics
|
import GHC.Generics
|
||||||
import Network.Wai.Handler.Warp (run)
|
import Network.Wai.Handler.Warp (run)
|
||||||
import Servant
|
import Servant
|
||||||
import Servant.JQuery
|
import Servant.JS
|
||||||
import System.FilePath
|
import System.FilePath
|
||||||
|
|
||||||
-- * A simple Counter data type
|
-- * A simple Counter data type
|
||||||
|
@ -48,13 +51,21 @@ currentValue :: MonadIO m => TVar Counter -> m Counter
|
||||||
currentValue counter = liftIO $ readTVarIO counter
|
currentValue counter = liftIO $ readTVarIO counter
|
||||||
|
|
||||||
-- * Our API type
|
-- * Our API type
|
||||||
type TestApi = "counter" :> Post Counter -- endpoint for increasing the counter
|
type TestApi = "counter" :> Post '[JSON] Counter -- endpoint for increasing the counter
|
||||||
:<|> "counter" :> Get Counter -- endpoint to get the current value
|
:<|> "counter" :> Get '[JSON] Counter -- endpoint to get the current value
|
||||||
:<|> Raw -- used for serving static files
|
|
||||||
|
|
||||||
|
type TestApi' = TestApi -- The API we want a JS handler for
|
||||||
|
:<|> Raw -- used for serving static files
|
||||||
|
|
||||||
|
-- this proxy only targets the proper endpoints of our API,
|
||||||
|
-- not the static file serving bit
|
||||||
testApi :: Proxy TestApi
|
testApi :: Proxy TestApi
|
||||||
testApi = Proxy
|
testApi = Proxy
|
||||||
|
|
||||||
|
-- this proxy targets everything
|
||||||
|
testApi' :: Proxy TestApi'
|
||||||
|
testApi' = Proxy
|
||||||
|
|
||||||
-- * Server-side handler
|
-- * Server-side handler
|
||||||
|
|
||||||
-- where our static files reside
|
-- where our static files reside
|
||||||
|
@ -65,26 +76,20 @@ www = "examples/www"
|
||||||
server :: TVar Counter -> Server TestApi
|
server :: TVar Counter -> Server TestApi
|
||||||
server counter = counterPlusOne counter -- (+1) on the TVar
|
server counter = counterPlusOne counter -- (+1) on the TVar
|
||||||
:<|> currentValue counter -- read the TVar
|
:<|> currentValue counter -- read the TVar
|
||||||
|
|
||||||
|
server' :: TVar Counter -> Server TestApi'
|
||||||
|
server counter = server counter
|
||||||
:<|> serveDirectory www -- serve static files
|
:<|> serveDirectory www -- serve static files
|
||||||
|
|
||||||
runServer :: TVar Counter -- ^ shared variable for the counter
|
runServer :: TVar Counter -- ^ shared variable for the counter
|
||||||
-> Int -- ^ port the server should listen on
|
-> Int -- ^ port the server should listen on
|
||||||
-> IO ()
|
-> IO ()
|
||||||
runServer var port = run port (serve testApi $ server var)
|
runServer var port = run port (serve testApi' $ server' var)
|
||||||
|
|
||||||
-- * Generating the JQuery code
|
|
||||||
|
|
||||||
incCounterJS :<|> currentValueJS :<|> _ = jquery testApi
|
|
||||||
|
|
||||||
writeJS :: FilePath -> [AjaxReq] -> IO ()
|
|
||||||
writeJS fp functions = writeFile fp $
|
|
||||||
concatMap generateJS functions
|
|
||||||
|
|
||||||
main :: IO ()
|
main :: IO ()
|
||||||
main = do
|
main = do
|
||||||
-- write the JS code to www/api.js at startup
|
-- write the JS code to www/api.js at startup
|
||||||
writeJS (www </> "api.js")
|
writeJSForAPI testApi jquery (www </> "api.js")
|
||||||
[ incCounterJS, currentValueJS ]
|
|
||||||
|
|
||||||
-- setup a shared counter
|
-- setup a shared counter
|
||||||
cnt <- newCounter
|
cnt <- newCounter
|
||||||
|
|
|
@ -1,4 +1,4 @@
|
||||||
SERVANT_DIR=/tmp/servant-jquery-gh-pages
|
SERVANT_DIR=/tmp/servant-js-gh-pages
|
||||||
|
|
||||||
# Make a temporary clone
|
# Make a temporary clone
|
||||||
|
|
||||||
|
@ -10,7 +10,7 @@ cd $SERVANT_DIR
|
||||||
|
|
||||||
# Make sure to pull the latest
|
# Make sure to pull the latest
|
||||||
|
|
||||||
git remote add haskell-servant git@github.com:haskell-servant/servant-jquery.git
|
git remote add haskell-servant git@github.com:haskell-servant/servant-js.git
|
||||||
|
|
||||||
git fetch haskell-servant
|
git fetch haskell-servant
|
||||||
|
|
||||||
|
@ -36,7 +36,7 @@ cd $SERVANT_DIR
|
||||||
|
|
||||||
rm *
|
rm *
|
||||||
rm -rf build
|
rm -rf build
|
||||||
mv doc/html/servant-jquery/* .
|
mv doc/html/servant-js/* .
|
||||||
rm -r doc/
|
rm -r doc/
|
||||||
|
|
||||||
# Add everything
|
# Add everything
|
||||||
|
|
|
@ -2,15 +2,15 @@ name: servant-js
|
||||||
version: 0.5
|
version: 0.5
|
||||||
synopsis: Automatically derive javascript functions to query servant webservices.
|
synopsis: Automatically derive javascript functions to query servant webservices.
|
||||||
description:
|
description:
|
||||||
Automatically derive jquery-based javascript functions to query servant webservices.
|
Automatically derive javascript functions to query servant webservices.
|
||||||
.
|
.
|
||||||
Supports deriving functions using vanilla javascript AJAX requests, Angular or JQuery.
|
Supports deriving functions using vanilla javascript AJAX requests, Angulari, Axios or JQuery.
|
||||||
.
|
.
|
||||||
You can find an example <https://github.com/haskell-servant/servant/blob/master/servant-jquery/examples/counter.hs here>
|
You can find an example <https://github.com/haskell-servant/servant/blob/master/servant-js/examples/counter.hs here>
|
||||||
which serves the generated javascript to a webpage that allows you to trigger
|
which serves the generated javascript to a webpage that allows you to trigger
|
||||||
webservice calls.
|
webservice calls.
|
||||||
.
|
.
|
||||||
<https://github.com/haskell-servant/servant/blob/master/servant-jquery/CHANGELOG.md CHANGELOG>
|
<https://github.com/haskell-servant/servant/blob/master/servant-js/CHANGELOG.md CHANGELOG>
|
||||||
license: BSD3
|
license: BSD3
|
||||||
license-file: LICENSE
|
license-file: LICENSE
|
||||||
author: Alp Mestanogullari
|
author: Alp Mestanogullari
|
||||||
|
|
Loading…
Reference in a new issue