servant/servant-js/test/Servant/JSSpec.hs

180 lines
7.3 KiB
Haskell
Raw Normal View History

{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
2014-12-24 13:55:25 +01:00
{-# OPTIONS_GHC -fno-warn-orphans #-}
module Servant.JSSpec where
2014-12-24 13:55:25 +01:00
import Data.Either (isRight)
import Data.Proxy
import Language.ECMAScript3.Parser (parseFromString)
import Test.Hspec
import Servant.API
import Servant.JS
import qualified Servant.JS.Vanilla as JS
import qualified Servant.JS.JQuery as JQ
import qualified Servant.JS.Angular as NG
2015-07-27 16:49:52 +02:00
import qualified Servant.JS.Axios as AX
import Servant.JSSpec.CustomHeaders
2014-12-24 13:55:25 +01:00
2015-03-03 22:59:36 +01:00
type TestAPI = "simple" :> ReqBody '[JSON,FormUrlEncoded] String :> Post '[JSON] Bool
:<|> "has.extension" :> Get '[FormUrlEncoded,JSON] Bool
2014-12-24 13:55:25 +01:00
type TopLevelRawAPI = "something" :> Get '[JSON] Int
2015-01-02 10:46:21 +01:00
:<|> Raw
type HeaderHandlingAPI = "something" :> Header "Foo" String
:> Get '[JSON] Int
type CustomAuthAPI = "something" :> Authorization "Basic" String
:> Get '[JSON] Int
type CustomHeaderAPI = "something" :> MyLovelyHorse String
:> Get '[JSON] Int
type CustomHeaderAPI2 = "something" :> WhatsForDinner String
:> Get '[JSON] Int
headerHandlingProxy :: Proxy HeaderHandlingAPI
headerHandlingProxy = Proxy
customAuthProxy :: Proxy CustomAuthAPI
customAuthProxy = Proxy
customHeaderProxy :: Proxy CustomHeaderAPI
customHeaderProxy = Proxy
customHeaderProxy2 :: Proxy CustomHeaderAPI2
customHeaderProxy2 = Proxy
data TestNames = Vanilla
| VanillaCustom
| JQuery
| JQueryCustom
| Angular
| AngularCustom
2015-07-27 16:49:52 +02:00
| Axios
| AxiosCustom
deriving (Show, Eq)
customOptions :: CommonGeneratorOptions
2015-07-28 15:06:00 +02:00
customOptions = defCommonGeneratorOptions
{ successCallback = "okCallback"
, errorCallback = "errorCallback"
}
2014-12-24 13:55:25 +01:00
spec :: Spec
spec = describe "Servant.JQuery" $ do
2015-07-23 13:47:44 +02:00
generateJSSpec Vanilla JS.generateVanillaJS
generateJSSpec VanillaCustom (JS.generateVanillaJSWith customOptions)
generateJSSpec JQuery JQ.generateJQueryJS
generateJSSpec JQueryCustom (JQ.generateJQueryJSWith customOptions)
generateJSSpec Angular (NG.generateAngularJS NG.defAngularOptions)
generateJSSpec AngularCustom (NG.generateAngularJSWith NG.defAngularOptions customOptions)
2015-07-28 15:06:00 +02:00
generateJSSpec Axios (AX.generateAxiosJS AX.defAxiosOptions)
generateJSSpec AxiosCustom (AX.generateAxiosJSWith (AX.defAxiosOptions { withCredentials = True }) customOptions)
2015-07-23 13:47:44 +02:00
angularSpec Angular
2015-07-28 15:44:55 +02:00
axiosSpec
2015-07-28 15:06:00 +02:00
--angularSpec AngularCustom
2015-07-28 15:44:55 +02:00
axiosSpec :: Spec
axiosSpec = describe specLabel $ do
it "should add withCredentials when needed" $ do
let jsText = genJS withCredOpts $ listFromAPI (Proxy :: Proxy TestAPI)
output jsText
jsText `shouldContain` ("withCredentials: true")
it "should add xsrfCookieName when needed" $ do
let jsText = genJS cookieOpts $ listFromAPI (Proxy :: Proxy TestAPI)
output jsText
jsText `shouldContain` ("xsrfCookieName: 'MyXSRFcookie'")
it "should add withCredentials when needed" $ do
let jsText = genJS headerOpts $ listFromAPI (Proxy :: Proxy TestAPI)
output jsText
jsText `shouldContain` ("xsrfHeaderName: 'MyXSRFheader'")
where
specLabel = "Axios"
output _ = return ()
withCredOpts = AX.defAxiosOptions { AX.withCredentials = True }
cookieOpts = AX.defAxiosOptions { AX.xsrfCookieName = Just "MyXSRFcookie" }
headerOpts = AX.defAxiosOptions { AX.xsrfHeaderName = Just "MyXSRFheader" }
genJS :: AxiosOptions -> [AjaxReq] -> String
genJS opts req = concat $ map (AX.generateAxiosJS opts) req
angularSpec :: TestNames -> Spec
angularSpec test = describe specLabel $ do
it "should implement a service globally" $ do
let jsText = genJS $ listFromAPI (Proxy :: Proxy TestAPI)
output jsText
jsText `shouldContain` (".service('" ++ testName ++ "'")
it "should depend on $http service globally" $ do
let jsText = genJS $ listFromAPI (Proxy :: Proxy TestAPI)
output jsText
jsText `shouldContain` ("('" ++ testName ++ "', function($http) {")
it "should not depend on $http service in handlers" $ do
let jsText = genJS $ listFromAPI (Proxy :: Proxy TestAPI)
output jsText
jsText `shouldNotContain` "getsomething($http, "
where
2015-07-28 15:44:55 +02:00
specLabel = "AngularJS(" ++ (show test) ++ ")"
output _ = return ()
testName = "MyService"
ngOpts = NG.defAngularOptions { NG.serviceName = testName }
genJS req = NG.angularService ngOpts req
generateJSSpec :: TestNames -> (AjaxReq -> String) -> Spec
generateJSSpec n gen = describe specLabel $ do
2015-01-02 10:46:21 +01:00
it "should generate valid javascript" $ do
let s = jsForAPI (Proxy :: Proxy TestAPI) (concat . map gen)
parseFromString s `shouldSatisfy` isRight
2015-01-02 10:46:21 +01:00
it "should use non-empty function names" $ do
let (_ :<|> topLevel) = javascript (Proxy :: Proxy TopLevelRawAPI)
output $ genJS (topLevel "GET")
parseFromString (genJS $ topLevel "GET") `shouldSatisfy` isRight
2014-12-24 13:55:25 +01:00
it "should handle simple HTTP headers" $ do
let jsText = genJS $ javascript headerHandlingProxy
output jsText
parseFromString jsText `shouldSatisfy` isRight
jsText `shouldContain` "headerFoo"
jsText `shouldContain` (header n "Foo" $ "headerFoo")
it "should handle complex HTTP headers" $ do
let jsText = genJS $ javascript customAuthProxy
output jsText
parseFromString jsText `shouldSatisfy` isRight
jsText `shouldContain` "headerAuthorization"
jsText `shouldContain` (header n "Authorization" $ "\"Basic \" + headerAuthorization")
it "should handle complex, custom HTTP headers" $ do
let jsText = genJS $ javascript customHeaderProxy
output jsText
parseFromString jsText `shouldSatisfy` isRight
jsText `shouldContain` "headerXMyLovelyHorse"
jsText `shouldContain` (header n "X-MyLovelyHorse" $ "\"I am good friends with \" + headerXMyLovelyHorse")
it "should handle complex, custom HTTP headers (template replacement)" $ do
let jsText = genJS $ javascript customHeaderProxy2
output jsText
parseFromString jsText `shouldSatisfy` isRight
jsText `shouldContain` "headerXWhatsForDinner"
jsText `shouldContain` (header n "X-WhatsForDinner" $ "\"I would like \" + headerXWhatsForDinner + \" with a cherry on top.\"")
2015-04-19 11:56:29 +02:00
it "can generate the whole javascript code string at once with jsForAPI" $ do
let jsStr = jsForAPI (Proxy :: Proxy TestAPI) (concat . map gen)
2015-04-19 11:56:29 +02:00
parseFromString jsStr `shouldSatisfy` isRight
where
specLabel = "generateJS(" ++ (show n) ++ ")"
2015-07-28 01:27:20 +02:00
output _ = return ()
genJS req = gen req
header :: TestNames -> String -> String -> String
header v headerName headerValue
| v `elem` [Vanilla, VanillaCustom] = "xhr.setRequestHeader(\"" ++ headerName ++ "\", " ++ headerValue ++ ");\n"
| otherwise = "headers: { \"" ++ headerName ++ "\": " ++ headerValue ++ " }\n"