adapt to the servant/servant-server split, prepare new release

This commit is contained in:
Alp Mestanogullari 2014-12-10 16:29:50 +01:00
parent c660b9cb0b
commit d106989d62
2 changed files with 69 additions and 88 deletions

52
docs.sh Normal file
View File

@ -0,0 +1,52 @@
SERVANT_DIR=/tmp/servant-jquery-gh-pages
# Make a temporary clone
rm -rf $SERVANT_DIR
git clone . $SERVANT_DIR
cd $SERVANT_DIR
# Make sure to pull the latest
git remote add haskell-servant git@github.com:haskell-servant/servant-jquery.git
git fetch haskell-servant
git reset --hard haskell-servant/gh-pages
# Clear everything away
git rm -rf $SERVANT_DIR/*
# Switch back and build the haddocks
cd -
cabal configure --builddir=$SERVANT_DIR
cabal haddock --hoogle --hyperlink-source --html-location='https://hackage.haskell.org/package/$pkg-$version/docs' --builddir=$SERVANT_DIR
commit_hash=$(git rev-parse HEAD)
# Move the HTML docs to the root
cd $SERVANT_DIR
rm *
rm -rf build
mv doc/html/servant-jquery/* .
rm -r doc/
# Add everything
git add .
git commit -m "Built from $commit_hash"
# Push to update the pages
git push haskell-servant HEAD:gh-pages
rm -rf $SERVANT_DIR

View File

@ -1,94 +1,11 @@
name: servant-jquery
version: 0.2
version: 0.2.1
synopsis: Automatically derive jquery-based javascript functions to query servant webservices
description:
Automatically derive jquery-based javascript functions to query servant webservices.
.
Example below that serves the generated javascript to a webpage that lets you
Example <https://github.com/haskell-servant/servant-jquery/blob/master/examples/counter.hs here> that serves the generated javascript to a webpage that lets you
trigger webservice calls.
.
> {-# 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
>
> -- * 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
> :<|> 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
> :<|> 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
>
> incCounterJS :<|> currentValueJS :<|> _ = 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")
> [ incCounterJS, currentValueJS ]
>
> -- setup a shared counter
> cnt <- newCounter
>
> -- listen to requests on port 8080
> runServer cnt 8080
license: BSD3
license-file: LICENSE
author: Alp Mestanogullari
@ -103,10 +20,15 @@ source-repository head
type: git
location: http://github.com/haskell-servant/servant-jquery.git
flag example
description: Build the example too
manual: True
default: False
library
exposed-modules: Servant.JQuery
other-modules: Servant.JQuery.Internal
build-depends: base >=4.5 && <5, servant >= 0.2, lens >= 4
build-depends: base >=4.5 && <5, servant >= 0.2.1, lens >= 4
hs-source-dirs: src
default-language: Haskell2010
ghc-options: -Wall
@ -115,12 +37,19 @@ executable counter
main-is: counter.hs
ghc-options: -O2 -Wall
hs-source-dirs: examples
if flag(example)
buildable: True
else
buildable: False
build-depends:
aeson
, base
, filepath
, servant >= 0.2
, servant-jquery >= 0.2
, servant >= 0.2.1
, servant-server >= 0.2.1
, servant-jquery >= 0.2.1
, stm
, transformers
, warp