drop the dependency on interpolate and hence on haskell-src-exts, it's becoming too annoying to keep

This commit is contained in:
Alp Mestanogullari 2014-12-01 17:23:25 +01:00
parent 91fc74b70e
commit 3e76058d25
3 changed files with 15 additions and 24 deletions

View file

@ -19,9 +19,6 @@ newtype Counter = Counter { value :: Int }
instance ToJSON Counter
instance ToSample Counter where
toSample = Just 0
-- * Shared counter operations
-- Creating a counter that starts from 0
@ -42,7 +39,6 @@ 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
@ -58,7 +54,6 @@ www = "examples/www"
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
@ -70,7 +65,7 @@ runServer var port = run port (serve testApi $ server var)
incCounterNamed :: FunctionName -> AjaxReq
currentValueNamed :: FunctionName -> AjaxReq
incCounterNamed :<|> currentValueNamed :<|> _ :<|> _ = jquery testApi
incCounterNamed :<|> currentValueNamed :<|> _ = jquery testApi
writeJS :: FilePath -> [AjaxReq] -> IO ()
writeJS fp functions = writeFile fp $

View file

@ -16,7 +16,7 @@ library
exposed-modules: Servant.JQuery
other-modules: Servant.JQuery.Internal
-- other-extensions:
build-depends: base >=4.5 && <5, servant >= 0.2, lens >= 4, interpolate
build-depends: base >=4.5 && <5, servant >= 0.2, lens >= 4
hs-source-dirs: src
default-language: Haskell2010
ghc-options: -O2 -Wall

View file

@ -1,5 +1,4 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE FlexibleInstances #-}
-----------------------------------------------------------------------------
@ -10,8 +9,6 @@
-- Maintainer : Alp Mestanogullari <alpmestan@gmail.com>
-- Stability : experimental
-- Portability : non-portable
--
-- Usage:
module Servant.JQuery
( jquery
, generateJS
@ -21,8 +18,8 @@ module Servant.JQuery
import Control.Lens
import Data.List
import Data.Monoid
import Data.Proxy
import Data.String.Interpolate
import Servant.JQuery.Internal
jquery :: HasJQ layout => Proxy layout -> JQ layout
@ -30,18 +27,17 @@ jquery p = jqueryFor p defReq
-- js codegen
generateJS :: AjaxReq -> String
generateJS req =
[i|
function #{fname}(#{argsStr})
{
$.ajax(
{ url: #{url}
, success: onSuccess #{dataBody}
, error: onError
, type: '#{method}'
});
}
|]
generateJS req = "\n" <>
"function " <> fname <> "(" <> argsStr <> ")\n"
<> "{\n"
<> " $.ajax(\n"
<> " { url: " <> url <> "\n"
<> " , success: onSuccess\n"
<> dataBody
<> " , error: onError\n"
<> " , type: '" <> method <> "'\n"
<> " });\n"
<> "}\n"
where argsStr = intercalate ", " args
args = captures
@ -61,7 +57,7 @@ function #{fname}(#{argsStr})
dataBody =
if req ^. reqBody
then "\n , data: JSON.stringify(body)"
then "\n , data: JSON.stringify(body)\n"
else ""
fname = req ^. funcName