add ComprehensiveAPI to test whether we're missing instances

Some of the combinators are commented atm, because we *are* missing combinators.
This commit is contained in:
Sönke Hahn 2016-01-16 19:17:46 +01:00
parent b8d70e303a
commit e5974ec94d
9 changed files with 92 additions and 1 deletions

View File

@ -49,9 +49,12 @@ import Test.HUnit
import Test.QuickCheck
import Servant.API
import Servant.API.Internal.Test.ComprehensiveAPI
import Servant.Client
import Servant.Server
_ = client comprehensiveAPI
spec :: Spec
spec = describe "Servant.Client" $ do
sucessSpec

View File

@ -1,7 +1,7 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeOperators #-}
@ -18,8 +18,24 @@ import GHC.Generics
import Test.Hspec
import Servant.API
import Servant.API.Internal.Test.ComprehensiveAPI
import Servant.Docs.Internal
-- * comprehensive api
_ = docs comprehensiveAPI
instance ToParam (QueryParam "foo" Int) where
toParam = error "unused"
instance ToParam (QueryParams "foo" Int) where
toParam = error "unused"
instance ToParam (QueryFlag "foo") where
toParam = error "unused"
instance ToCapture (Capture "foo" Int) where
toCapture = error "unused"
-- * specs
spec :: Spec
spec = describe "Servant.Docs" $ do

View File

@ -21,6 +21,7 @@ import qualified Data.Text as T
import Language.ECMAScript3.Parser (program, parse)
import Test.Hspec hiding (shouldContain, shouldNotContain)
import Servant.API.Internal.Test.ComprehensiveAPI
import Servant.JS
import Servant.JS.Internal
import qualified Servant.JS.Angular as NG
@ -29,6 +30,12 @@ import qualified Servant.JS.JQuery as JQ
import qualified Servant.JS.Vanilla as JS
import Servant.JSSpec.CustomHeaders
-- * comprehensive api
_ = (jsForAPI comprehensiveAPI vanillaJS :: Text)
-- * specs
type TestAPI = "simple" :> ReqBody '[JSON,FormUrlEncoded] Text :> Post '[JSON] Bool
:<|> "has.extension" :> Get '[FormUrlEncoded,JSON] Bool

View File

@ -45,3 +45,18 @@ executable mock-app
buildable: True
else
buildable: False
test-suite spec
type: exitcode-stdio-1.0
ghc-options:
-Wall -fno-warn-name-shadowing
default-language: Haskell2010
hs-source-dirs: test
main-is: Spec.hs
other-modules:
Servant.MockSpec
build-depends:
base,
hspec,
servant,
servant-mock

View File

@ -0,0 +1,12 @@
module Servant.MockSpec where
import Test.Hspec
import Servant.API.Internal.Test.ComprehensiveAPI
import Servant.Mock
_ = mock comprehensiveAPI
spec :: Spec
spec = return ()

View File

@ -0,0 +1 @@
{-# OPTIONS_GHC -F -pgmF hspec-discover #-}

View File

@ -46,6 +46,7 @@ import Servant.API ((:<|>) (..), (:>), Capture, Delete,
QueryFlag, QueryParam, QueryParams,
Raw, RemoteHost, ReqBody,
StdMethod (..), Verb, addHeader)
import Servant.API.Internal.Test.ComprehensiveAPI
import Servant.Server (ServantErr (..), Server, err404,
serve)
import Test.Hspec (Spec, context, describe, it,
@ -60,6 +61,9 @@ import Servant.Server.Internal.Router
(tweakResponse, runRouter,
Router, Router'(LeafRouter))
-- * comprehensive api test
_ = serve comprehensiveAPI (error "unused") (error "unused")
-- * Specs

View File

@ -31,6 +31,7 @@ library
Servant.API.ContentTypes
Servant.API.Header
Servant.API.HttpVersion
Servant.API.Internal.Test.ComprehensiveAPI
Servant.API.IsSecure
Servant.API.QueryParam
Servant.API.Raw

View File

@ -0,0 +1,32 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeOperators #-}
module Servant.API.Internal.Test.ComprehensiveAPI where
import Data.Proxy
import Servant.API
type GET = Get '[JSON] ()
type ComprehensiveAPI =
GET :<|>
Get '[JSON] Int :<|>
Capture "foo" Int :> GET :<|>
Header "foo" Int :> GET :<|>
-- HttpVersion :> GET :<|>
IsSecure :> GET :<|>
QueryParam "foo" Int :> GET :<|>
QueryParams "foo" Int :> GET :<|>
QueryFlag "foo" :> GET :<|>
-- Raw :<|>
-- RemoteHost :<|>
ReqBody '[JSON] Int :> GET :<|>
-- Get '[JSON] (Headers '[Header "foo" Int] ()) :<|>
"foo" :> GET :<|>
Vault :> GET :<|>
Verb 'POST 204 '[JSON] () :<|>
Verb 'POST 204 '[JSON] Int
comprehensiveAPI :: Proxy ComprehensiveAPI
comprehensiveAPI = Proxy