2015-01-21 08:27:25 +01:00
|
|
|
{-# 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.JQuerySpec where
|
|
|
|
|
|
|
|
import Data.Either (isRight)
|
|
|
|
import Data.Proxy
|
|
|
|
import Language.ECMAScript3.Parser (parseFromString)
|
|
|
|
import Test.Hspec
|
|
|
|
|
|
|
|
import Servant.API
|
|
|
|
import Servant.JQuery
|
2015-01-21 08:47:23 +01:00
|
|
|
import Servant.JQuerySpec.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
|
|
|
|
2015-02-19 01:36:31 +01:00
|
|
|
type TopLevelRawAPI = "something" :> Get '[JSON] Int
|
2015-01-02 10:46:21 +01:00
|
|
|
:<|> Raw
|
|
|
|
|
2015-01-21 08:27:25 +01:00
|
|
|
type HeaderHandlingAPI = "something" :> Header "Foo" String
|
2015-02-19 01:36:31 +01:00
|
|
|
:> Get '[JSON] Int
|
2015-01-21 08:27:25 +01:00
|
|
|
|
2015-01-21 08:47:23 +01:00
|
|
|
type CustomAuthAPI = "something" :> Authorization "Basic" String
|
2015-02-19 01:36:31 +01:00
|
|
|
:> Get '[JSON] Int
|
2015-01-21 08:47:23 +01:00
|
|
|
|
2015-01-21 09:32:06 +01:00
|
|
|
type CustomHeaderAPI = "something" :> MyLovelyHorse String
|
2015-02-19 01:36:31 +01:00
|
|
|
:> Get '[JSON] Int
|
2015-01-21 09:32:06 +01:00
|
|
|
|
2015-01-22 01:41:06 +01:00
|
|
|
type CustomHeaderAPI2 = "something" :> WhatsForDinner String
|
2015-02-19 01:36:31 +01:00
|
|
|
:> Get '[JSON] Int
|
2015-01-22 01:41:06 +01:00
|
|
|
|
2015-01-21 08:27:25 +01:00
|
|
|
headerHandlingProxy :: Proxy HeaderHandlingAPI
|
|
|
|
headerHandlingProxy = Proxy
|
|
|
|
|
2015-01-21 08:47:23 +01:00
|
|
|
customAuthProxy :: Proxy CustomAuthAPI
|
|
|
|
customAuthProxy = Proxy
|
|
|
|
|
2015-01-21 09:32:06 +01:00
|
|
|
customHeaderProxy :: Proxy CustomHeaderAPI
|
|
|
|
customHeaderProxy = Proxy
|
|
|
|
|
2015-01-22 01:41:06 +01:00
|
|
|
customHeaderProxy2 :: Proxy CustomHeaderAPI2
|
|
|
|
customHeaderProxy2 = Proxy
|
|
|
|
|
2014-12-24 13:55:25 +01:00
|
|
|
spec :: Spec
|
|
|
|
spec = describe "Servant.JQuery"
|
|
|
|
generateJSSpec
|
|
|
|
|
|
|
|
generateJSSpec :: Spec
|
2015-01-02 10:46:21 +01:00
|
|
|
generateJSSpec = describe "generateJS" $ do
|
|
|
|
it "should generate valid javascript" $ do
|
|
|
|
let (postSimple :<|> getHasExtension ) = jquery (Proxy :: Proxy TestAPI)
|
2014-12-24 13:55:25 +01:00
|
|
|
parseFromString (generateJS postSimple) `shouldSatisfy` isRight
|
|
|
|
parseFromString (generateJS getHasExtension) `shouldSatisfy` isRight
|
2015-01-02 10:46:21 +01:00
|
|
|
print $ generateJS getHasExtension
|
|
|
|
|
|
|
|
it "should use non-empty function names" $ do
|
|
|
|
let (_ :<|> topLevel) = jquery (Proxy :: Proxy TopLevelRawAPI)
|
|
|
|
print $ generateJS $ topLevel "GET"
|
|
|
|
parseFromString (generateJS $ topLevel "GET") `shouldSatisfy` isRight
|
2014-12-24 13:55:25 +01:00
|
|
|
|
2015-01-21 08:27:25 +01:00
|
|
|
it "should handle simple HTTP headers" $ do
|
|
|
|
let jsText = generateJS $ jquery headerHandlingProxy
|
|
|
|
print jsText
|
|
|
|
parseFromString jsText `shouldSatisfy` isRight
|
|
|
|
jsText `shouldContain` "headerFoo"
|
|
|
|
jsText `shouldContain` "headers: { \"Foo\": headerFoo }\n"
|
|
|
|
|
2015-01-21 08:47:23 +01:00
|
|
|
it "should handle complex HTTP headers" $ do
|
|
|
|
let jsText = generateJS $ jquery customAuthProxy
|
|
|
|
print jsText
|
|
|
|
parseFromString jsText `shouldSatisfy` isRight
|
|
|
|
jsText `shouldContain` "headerAuthorization"
|
|
|
|
jsText `shouldContain` "headers: { \"Authorization\": \"Basic \" + headerAuthorization }\n"
|
|
|
|
|
2015-01-21 09:32:06 +01:00
|
|
|
it "should handle complex, custom HTTP headers" $ do
|
|
|
|
let jsText = generateJS $ jquery customHeaderProxy
|
|
|
|
print jsText
|
|
|
|
parseFromString jsText `shouldSatisfy` isRight
|
|
|
|
jsText `shouldContain` "headerXMyLovelyHorse"
|
|
|
|
jsText `shouldContain` "headers: { \"X-MyLovelyHorse\": \"I am good friends with \" + headerXMyLovelyHorse }\n"
|
2015-01-22 01:41:06 +01:00
|
|
|
|
|
|
|
it "should handle complex, custom HTTP headers (template replacement)" $ do
|
|
|
|
let jsText = generateJS $ jquery customHeaderProxy2
|
|
|
|
print jsText
|
|
|
|
parseFromString jsText `shouldSatisfy` isRight
|
|
|
|
jsText `shouldContain` "headerXWhatsForDinner"
|
|
|
|
jsText `shouldContain` "headers: { \"X-WhatsForDinner\": \"I would like \" + headerXWhatsForDinner + \" with a cherry on top.\" }\n"
|
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)
|
|
|
|
parseFromString jsStr `shouldSatisfy` isRight
|