servant/test/Servant/JQuerySpec.hs

70 lines
2.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.JQuerySpec where
import Data.Either (isRight)
import Data.Proxy
import Language.ECMAScript3.Parser (parseFromString)
import Test.Hspec
import Servant.API
import Servant.JQuery
import Servant.JQuerySpec.CustomHeaders
2014-12-24 13:55:25 +01:00
type TestAPI = [sitemap|
POST /simple String -> Bool
GET /has.extension Bool
|]
2015-01-02 10:46:21 +01:00
type TopLevelRawAPI = "something" :> Get Int
:<|> Raw
type HeaderHandlingAPI = "something" :> Header "Foo" String
:> Get Int
type CustomAuthAPI = "something" :> Authorization "Basic" String
:> Get Int
headerHandlingProxy :: Proxy HeaderHandlingAPI
headerHandlingProxy = Proxy
customAuthProxy :: Proxy CustomAuthAPI
customAuthProxy = 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
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"
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"