servant/servant-foreign/test/Servant/ForeignSpec.hs

110 lines
3.3 KiB
Haskell
Raw Normal View History

2016-02-17 22:47:30 +01:00
{-# LANGUAGE CPP #-}
2016-01-06 18:20:20 +01:00
#include "overlapping-compat.h"
module Servant.ForeignSpec where
2015-12-02 13:28:04 +01:00
import Data.Monoid ((<>))
import Data.Proxy
import Servant.Foreign
import Data.Text (Text(..))
import Test.Hspec
spec :: Spec
spec = describe "Servant.Foreign" $ do
camelCaseSpec
2015-12-02 13:28:04 +01:00
listFromAPISpec
camelCaseSpec :: Spec
camelCaseSpec = describe "camelCase" $ do
it "converts FunctionNames to camelCase" $ do
2016-02-17 22:47:30 +01:00
camelCase (FunctionName ["post", "counter", "inc"])
`shouldBe` "postCounterInc"
camelCase (FunctionName ["get", "hyphen-ated", "counter"])
`shouldBe` "getHyphenatedCounter"
2015-12-02 13:28:04 +01:00
----------------------------------------------------------------------
data LangX
instance HasForeignType LangX () where
2016-02-17 22:47:30 +01:00
typeFor _ _ = ForeignType "voidX"
2015-12-02 13:28:04 +01:00
instance HasForeignType LangX Int where
typeFor _ _ = "intX"
2015-12-02 13:28:04 +01:00
instance HasForeignType LangX Bool where
typeFor _ _ = "boolX"
2016-01-06 18:20:20 +01:00
instance OVERLAPPING_ HasForeignType LangX String where
typeFor _ _ = "stringX"
2016-01-06 18:20:20 +01:00
instance OVERLAPPABLE_ HasForeignType LangX a => HasForeignType LangX [a] where
typeFor lang _ = "listX of " <> typeFor lang (Proxy :: Proxy a)
2015-12-02 13:28:04 +01:00
type TestApi
= "test" :> Header "header" [String] :> QueryFlag "flag" :> Get '[JSON] Int
:<|> "test" :> QueryParam "param" Int :> ReqBody '[JSON] [String] :> Post '[JSON] ()
:<|> "test" :> QueryParams "params" Int :> ReqBody '[JSON] String :> Put '[JSON] ()
:<|> "test" :> Capture "id" Int :> Delete '[JSON] ()
testApi :: [Req Text]
2015-12-02 13:28:04 +01:00
testApi = listFromAPI (Proxy :: Proxy LangX) (Proxy :: Proxy TestApi)
listFromAPISpec :: Spec
listFromAPISpec = describe "listFromAPI" $ do
it "generates 4 endpoints for TestApi" $ do
length testApi `shouldBe` 4
let [getReq, postReq, putReq, deleteReq] = testApi
it "collects all info for get request" $ do
shouldBe getReq $ defReq
{ _reqUrl = Url
[ Segment $ Static "test" ]
2016-02-17 22:47:30 +01:00
[ QueryArg (Arg "flag" "boolX") Flag ]
, _reqMethod = "GET"
2016-02-17 22:47:30 +01:00
, _reqHeaders = [HeaderArg $ Arg "header" "listX of stringX"]
, _reqBody = Nothing
, _reqReturnType = "intX"
2016-02-17 22:47:30 +01:00
, _reqFuncName = FunctionName ["get", "test"]
}
it "collects all info for post request" $ do
shouldBe postReq $ defReq
{ _reqUrl = Url
[ Segment $ Static "test" ]
2016-02-17 22:47:30 +01:00
[ QueryArg (Arg "param" "intX") Normal ]
, _reqMethod = "POST"
, _reqHeaders = []
, _reqBody = Just "listX of stringX"
, _reqReturnType = "voidX"
2016-02-17 22:47:30 +01:00
, _reqFuncName = FunctionName ["post", "test"]
}
it "collects all info for put request" $ do
shouldBe putReq $ defReq
{ _reqUrl = Url
[ Segment $ Static "test" ]
-- Shoud this be |intX| or |listX of intX| ?
2016-02-17 22:47:30 +01:00
[ QueryArg (Arg "params" "listX of intX") List ]
, _reqMethod = "PUT"
, _reqHeaders = []
, _reqBody = Just "stringX"
, _reqReturnType = "voidX"
2016-02-17 22:47:30 +01:00
, _reqFuncName = FunctionName ["put", "test"]
}
it "collects all info for delete request" $ do
shouldBe deleteReq $ defReq
{ _reqUrl = Url
[ Segment $ Static "test"
2016-02-17 22:47:30 +01:00
, Segment $ Cap (Arg "id" "intX") ]
[]
, _reqMethod = "DELETE"
, _reqHeaders = []
, _reqBody = Nothing
, _reqReturnType = "voidX"
2016-02-17 22:47:30 +01:00
, _reqFuncName = FunctionName ["delete", "test", "by", "id"]
}