Make ComprehensiveAPI part of public API

We cannot simply tweak it, it will break tests of other packages.
Including packages not in this repository.
This commit is contained in:
Oleg Grenrus 2018-11-06 13:32:36 +02:00
parent 3f56b86218
commit 7634e08352
8 changed files with 67 additions and 57 deletions

View File

@ -64,7 +64,7 @@ import Servant.API
DeleteNoContent, EmptyAPI, FormUrlEncoded, Get, Header,
Headers, JSON, NoContent (NoContent), Post, Put, QueryFlag,
QueryParam, QueryParams, Raw, ReqBody, addHeader, getHeaders)
import Servant.API.Internal.Test.ComprehensiveAPI
import Servant.Test.ComprehensiveAPI
import Servant.Client
import qualified Servant.Client.Core.Internal.Auth as Auth
import qualified Servant.Client.Core.Internal.Request as Req

View File

@ -21,7 +21,7 @@ import GHC.Generics
import Test.Hspec
import Servant.API
import Servant.API.Internal.Test.ComprehensiveAPI
import Servant.Test.ComprehensiveAPI
import Servant.Docs.Internal
-- * comprehensive api

View File

@ -14,7 +14,7 @@ module Servant.ForeignSpec where
import Data.Monoid
((<>))
import Data.Proxy
import Servant.API.Internal.Test.ComprehensiveAPI
import Servant.Test.ComprehensiveAPI
import Servant.Foreign
import Servant.Types.SourceT
(SourceT)

View File

@ -51,7 +51,7 @@ import Servant.API
PlainText, Post, Put, QueryFlag, QueryParam, QueryParams, Raw,
RemoteHost, ReqBody, StdMethod (..), Stream,
SourceIO, Verb, addHeader)
import Servant.API.Internal.Test.ComprehensiveAPI
import Servant.Test.ComprehensiveAPI
import Servant.Server
(Context ((:.), EmptyContext), Handler, Server, Tagged (..),
emptyServer, err401, err403, err404, serve, serveWithContext)

View File

@ -48,7 +48,6 @@ library
Servant.API.Generic
Servant.API.Header
Servant.API.HttpVersion
Servant.API.Internal.Test.ComprehensiveAPI
Servant.API.IsSecure
Servant.API.Modifiers
Servant.API.QueryParam
@ -67,6 +66,10 @@ library
exposed-modules:
Servant.Types.SourceT
-- Test stuff
exposed-modules:
Servant.Test.ComprehensiveAPI
-- Safe links
exposed-modules:
Servant.Links
@ -74,6 +77,7 @@ library
-- Deprecated modules, to be removed in late 2019
exposed-modules:
Servant.Utils.Links
Servant.API.Internal.Test.ComprehensiveAPI
-- Bundled with GHC: Lower bound to not force re-installs
-- text and mtl are bundled starting with GHC-8.4

View File

@ -1,52 +1,6 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeOperators #-}
module Servant.API.Internal.Test.ComprehensiveAPI
{-# DEPRECATED "Use Servant.TestComprehensiveAPI" #-}
( module Servant.Test.ComprehensiveAPI )
where
-- | This is a module containing an API with all `Servant.API` combinators. It
-- is used for testing only (in particular, checking that instances exist for
-- the core servant classes for each combinator), and should not be imported.
module Servant.API.Internal.Test.ComprehensiveAPI where
import Data.Proxy
(Proxy (..))
import Servant.API
import Servant.Types.SourceT
(SourceT)
type GET = Get '[JSON] NoContent
type ComprehensiveAPI =
ComprehensiveAPIWithoutRaw :<|>
Raw
comprehensiveAPI :: Proxy ComprehensiveAPI
comprehensiveAPI = Proxy
type ComprehensiveAPIWithoutRaw =
GET :<|>
Get '[JSON] Int :<|>
Capture' '[Description "example description"] "foo" Int :> GET :<|>
Header "foo" Int :> GET :<|>
Header' '[Required, Lenient] "bar" Int :> GET :<|>
HttpVersion :> GET :<|>
IsSecure :> GET :<|>
QueryParam "foo" Int :> GET :<|>
QueryParam' '[Required, Lenient] "bar" Int :> GET :<|>
QueryParams "foo" Int :> GET :<|>
QueryFlag "foo" :> GET :<|>
RemoteHost :> GET :<|>
ReqBody '[JSON] Int :> GET :<|>
ReqBody' '[Lenient] '[JSON] Int :> GET :<|>
Get '[JSON] (Headers '[Header "foo" Int] NoContent) :<|>
"foo" :> GET :<|>
Vault :> GET :<|>
Verb 'POST 204 '[JSON] NoContent :<|>
Verb 'POST 204 '[JSON] Int :<|>
StreamBody NetstringFraming JSON (SourceT IO Int) :> Stream 'GET 200 NetstringFraming JSON (SourceT IO Int) :<|>
WithNamedContext "foo" '[] GET :<|>
CaptureAll "foo" Int :> GET :<|>
Summary "foo" :> GET :<|>
Description "foo" :> GET :<|>
EmptyAPI
comprehensiveAPIWithoutRaw :: Proxy ComprehensiveAPIWithoutRaw
comprehensiveAPIWithoutRaw = Proxy
import Servant.Test.ComprehensiveAPI

View File

@ -0,0 +1,52 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeOperators #-}
-- | This is a module containing an API with all `Servant.API` combinators. It
-- is used for testing only (in particular, checking that instances exist for
-- the core servant classes for each combinator).
module Servant.Test.ComprehensiveAPI where
import Data.Proxy
(Proxy (..))
import Servant.API
import Servant.Types.SourceT
(SourceT)
type GET = Get '[JSON] NoContent
type ComprehensiveAPI =
ComprehensiveAPIWithoutRaw :<|>
Raw
comprehensiveAPI :: Proxy ComprehensiveAPI
comprehensiveAPI = Proxy
type ComprehensiveAPIWithoutRaw =
GET :<|>
Get '[JSON] Int :<|>
Capture' '[Description "example description"] "foo" Int :> GET :<|>
Header "foo" Int :> GET :<|>
Header' '[Required, Lenient] "bar" Int :> GET :<|>
HttpVersion :> GET :<|>
IsSecure :> GET :<|>
QueryParam "foo" Int :> GET :<|>
QueryParam' '[Required, Lenient] "bar" Int :> GET :<|>
QueryParams "foo" Int :> GET :<|>
QueryFlag "foo" :> GET :<|>
RemoteHost :> GET :<|>
ReqBody '[JSON] Int :> GET :<|>
ReqBody' '[Lenient] '[JSON] Int :> GET :<|>
Get '[JSON] (Headers '[Header "foo" Int] NoContent) :<|>
"foo" :> GET :<|>
Vault :> GET :<|>
Verb 'POST 204 '[JSON] NoContent :<|>
Verb 'POST 204 '[JSON] Int :<|>
StreamBody NetstringFraming JSON (SourceT IO Int) :> Stream 'GET 200 NetstringFraming JSON (SourceT IO Int) :<|>
WithNamedContext "foo" '[] GET :<|>
CaptureAll "foo" Int :> GET :<|>
Summary "foo" :> GET :<|>
Description "foo" :> GET :<|>
EmptyAPI
comprehensiveAPIWithoutRaw :: Proxy ComprehensiveAPIWithoutRaw
comprehensiveAPIWithoutRaw = Proxy

View File

@ -13,7 +13,7 @@ import Test.Hspec
(Expectation, Spec, describe, it, shouldBe)
import Servant.API
import Servant.API.Internal.Test.ComprehensiveAPI
import Servant.Test.ComprehensiveAPI
(comprehensiveAPIWithoutRaw)
import Servant.Links