Fix dot in function name issue.
This commit is contained in:
parent
d106989d62
commit
58b27cd957
4 changed files with 46 additions and 2 deletions
|
@ -54,3 +54,16 @@ executable counter
|
||||||
, transformers
|
, transformers
|
||||||
, warp
|
, warp
|
||||||
default-language: Haskell2010
|
default-language: Haskell2010
|
||||||
|
|
||||||
|
test-suite spec
|
||||||
|
type: exitcode-stdio-1.0
|
||||||
|
hs-source-dirs: test
|
||||||
|
ghc-options: -Wall
|
||||||
|
main-is: Spec.hs
|
||||||
|
build-depends:
|
||||||
|
base == 4.*
|
||||||
|
, servant-jquery
|
||||||
|
, servant
|
||||||
|
, hspec >= 2.0
|
||||||
|
, language-ecmascript == 0.16.*
|
||||||
|
default-language: Haskell2010
|
||||||
|
|
|
@ -214,4 +214,4 @@ instance (KnownSymbol path, HasJQ sublayout)
|
||||||
req & reqUrl.path <>~ [Static str]
|
req & reqUrl.path <>~ [Static str]
|
||||||
& funcName %~ (str <>)
|
& funcName %~ (str <>)
|
||||||
|
|
||||||
where str = symbolVal (Proxy :: Proxy path)
|
where str = map (\c -> if c == '.' then '_' else c) $ symbolVal (Proxy :: Proxy path)
|
||||||
|
|
29
test/Servant/JQuerySpec.hs
Normal file
29
test/Servant/JQuerySpec.hs
Normal file
|
@ -0,0 +1,29 @@
|
||||||
|
{-# LANGUAGE TypeOperators #-}
|
||||||
|
{-# LANGUAGE QuasiQuotes #-}
|
||||||
|
{-# OPTIONS_GHC -fno-warn-orphans #-}
|
||||||
|
module Servant.JQuerySpec where
|
||||||
|
|
||||||
|
import Data.Either (isRight)
|
||||||
|
import Data.Proxy
|
||||||
|
import Language.ECMAScript3.Parser (parseFromString)
|
||||||
|
import Test.Hspec
|
||||||
|
|
||||||
|
import Servant.API
|
||||||
|
import Servant.JQuery
|
||||||
|
|
||||||
|
type TestAPI = [sitemap|
|
||||||
|
POST /simple String -> Bool
|
||||||
|
GET /has.extension Bool
|
||||||
|
|]
|
||||||
|
|
||||||
|
spec :: Spec
|
||||||
|
spec = describe "Servant.JQuery"
|
||||||
|
generateJSSpec
|
||||||
|
|
||||||
|
generateJSSpec :: Spec
|
||||||
|
generateJSSpec = describe "generateJS" $
|
||||||
|
it "should always generate valid javascript" $ do
|
||||||
|
let (postSimple :<|> getHasExtension) = jquery (Proxy :: Proxy TestAPI)
|
||||||
|
parseFromString (generateJS postSimple) `shouldSatisfy` isRight
|
||||||
|
parseFromString (generateJS getHasExtension) `shouldSatisfy` isRight
|
||||||
|
|
2
test/Spec.hs
Normal file
2
test/Spec.hs
Normal file
|
@ -0,0 +1,2 @@
|
||||||
|
{-# OPTIONS_GHC -F -pgmF hspec-discover #-}
|
||||||
|
|
Loading…
Reference in a new issue