mirror of
https://github.com/ilyakooo0/servant-quickcheck.git
synced 2024-11-22 23:27:08 +03:00
Cleanup
This commit is contained in:
parent
1a24673206
commit
0682e353d6
@ -69,10 +69,10 @@ module Servant.QuickCheck
|
||||
|
||||
) where
|
||||
|
||||
import Data.Proxy (Proxy (..))
|
||||
import Servant.Client (BaseUrl (..), Scheme (..))
|
||||
import Servant.QuickCheck.Internal
|
||||
import Servant.Client (BaseUrl(..), Scheme(..))
|
||||
import Test.QuickCheck (Args(..), stdArgs)
|
||||
import Data.Proxy (Proxy(..))
|
||||
import Test.QuickCheck (Args (..), stdArgs)
|
||||
|
||||
-- | QuickCheck @Args@ with 1000 rather than 100 test cases.
|
||||
--
|
||||
|
@ -1,7 +1,7 @@
|
||||
module Servant.QuickCheck.Internal (module X) where
|
||||
|
||||
import Servant.QuickCheck.Internal.Equality as X
|
||||
import Servant.QuickCheck.Internal.ErrorTypes as X
|
||||
import Servant.QuickCheck.Internal.HasGenRequest as X
|
||||
import Servant.QuickCheck.Internal.Predicates as X
|
||||
import Servant.QuickCheck.Internal.QuickCheck as X
|
||||
import Servant.QuickCheck.Internal.Equality as X
|
||||
import Servant.QuickCheck.Internal.ErrorTypes as X
|
||||
import Servant.QuickCheck.Internal.Predicates as X
|
||||
import Servant.QuickCheck.Internal.QuickCheck as X
|
||||
|
@ -1,8 +1,8 @@
|
||||
module Servant.QuickCheck.Internal.Equality where
|
||||
|
||||
import Data.Function (on)
|
||||
import Network.HTTP.Client (Response, responseBody)
|
||||
import Prelude.Compat
|
||||
import Data.Function (on)
|
||||
import Network.HTTP.Client (Response, responseBody)
|
||||
import Prelude.Compat
|
||||
|
||||
newtype ResponseEquality b
|
||||
= ResponseEquality { getResponseEquality :: Response b -> Response b -> Bool }
|
||||
|
@ -10,6 +10,28 @@ import Network.HTTP.Types (Header, statusCode)
|
||||
import Prelude.Compat
|
||||
import Text.PrettyPrint
|
||||
|
||||
data PredicateFailure
|
||||
= PredicateFailure T.Text (Maybe C.Request) (C.Response LBS.ByteString)
|
||||
deriving (Generic)
|
||||
|
||||
instance Exception ServerEqualityFailure where
|
||||
|
||||
instance Show PredicateFailure where
|
||||
show = render . prettyPredicateFailure
|
||||
|
||||
|
||||
data ServerEqualityFailure
|
||||
= ServerEqualityFailure C.Request (C.Response LBS.ByteString) (C.Response LBS.ByteString)
|
||||
deriving (Generic)
|
||||
|
||||
instance Show ServerEqualityFailure where
|
||||
show = render . prettyServerEqualityFailure
|
||||
|
||||
|
||||
instance Exception PredicateFailure where
|
||||
|
||||
-- * Pretty printing
|
||||
|
||||
prettyHeaders :: [Header] -> Doc
|
||||
prettyHeaders hdrs = vcat $ prettyHdr <$> hdrs
|
||||
where
|
||||
@ -35,12 +57,6 @@ prettyResp r =
|
||||
$$ text "Body:" <+> (nest 5 $ text . cs $ C.responseBody r))
|
||||
|
||||
|
||||
-- The error that occurred.
|
||||
data PredicateFailure = PredicateFailure T.Text (Maybe C.Request) (C.Response LBS.ByteString)
|
||||
deriving (Generic)
|
||||
|
||||
data ServerEqualityFailure = ServerEqualityFailure C.Request (C.Response LBS.ByteString) (C.Response LBS.ByteString)
|
||||
deriving (Generic)
|
||||
|
||||
prettyServerEqualityFailure :: ServerEqualityFailure -> Doc
|
||||
prettyServerEqualityFailure (ServerEqualityFailure req resp1 resp2) =
|
||||
@ -61,12 +77,3 @@ prettyPredicateFailure (PredicateFailure predicate req resp) =
|
||||
Nothing -> text ""
|
||||
Just v -> prettyReq v
|
||||
|
||||
instance Show ServerEqualityFailure where
|
||||
show = render . prettyServerEqualityFailure
|
||||
|
||||
instance Exception ServerEqualityFailure where
|
||||
|
||||
instance Show PredicateFailure where
|
||||
show = render . prettyPredicateFailure
|
||||
|
||||
instance Exception PredicateFailure where
|
||||
|
@ -1,20 +1,20 @@
|
||||
{-# LANGUAGE PolyKinds #-}
|
||||
module Servant.QuickCheck.Internal.HasGenRequest where
|
||||
|
||||
import Data.Default.Class (def)
|
||||
import Data.Monoid ((<>))
|
||||
import Data.String (fromString)
|
||||
import Data.String.Conversions (cs)
|
||||
import GHC.TypeLits (KnownSymbol, Nat, symbolVal)
|
||||
import Network.HTTP.Client (Request, RequestBody (..), host,
|
||||
method, path, port, queryString,
|
||||
requestBody, requestHeaders, secure)
|
||||
import Network.HTTP.Media (renderHeader)
|
||||
import Prelude.Compat
|
||||
import Servant
|
||||
import Servant.API.ContentTypes (AllMimeRender (..))
|
||||
import Servant.Client (BaseUrl (..), Scheme (..))
|
||||
import Test.QuickCheck (Arbitrary (..), Gen, elements, oneof)
|
||||
import Data.Default.Class (def)
|
||||
import Data.Monoid ((<>))
|
||||
import Data.String (fromString)
|
||||
import Data.String.Conversions (cs)
|
||||
import GHC.TypeLits (KnownSymbol, Nat, symbolVal)
|
||||
import Network.HTTP.Client (Request, RequestBody (..), host, method, path,
|
||||
port, queryString, requestBody, requestHeaders,
|
||||
secure)
|
||||
import Network.HTTP.Media (renderHeader)
|
||||
import Prelude.Compat
|
||||
import Servant
|
||||
import Servant.API.ContentTypes (AllMimeRender (..))
|
||||
import Servant.Client (BaseUrl (..), Scheme (..))
|
||||
import Test.QuickCheck (Arbitrary (..), Gen, elements, oneof)
|
||||
|
||||
|
||||
class HasGenRequest a where
|
||||
|
@ -1,11 +1,10 @@
|
||||
module Servant.QuickCheck.Internal.Predicates where
|
||||
|
||||
import Control.Exception (catch, SomeException, throw)
|
||||
import Control.Monad (liftM2, guard, ap)
|
||||
import Control.Exception (SomeException, catch, throw)
|
||||
import Control.Monad (ap, guard, liftM2)
|
||||
import Control.Monad.Reader
|
||||
import Data.Aeson (Object, decode)
|
||||
import Data.Bifunctor (Bifunctor (..))
|
||||
import Prelude.Compat
|
||||
import qualified Data.ByteString as SBS
|
||||
import qualified Data.ByteString.Char8 as SBSC
|
||||
import qualified Data.ByteString.Lazy as LBS
|
||||
@ -22,9 +21,10 @@ import Network.HTTP.Client (Manager, Request, Response, httpLbs,
|
||||
responseStatus)
|
||||
import Network.HTTP.Media (matchAccept)
|
||||
import Network.HTTP.Types (methodGet, methodHead, parseMethod,
|
||||
renderStdMethod, status200, status201,
|
||||
status300, status401, status405,
|
||||
status500, status100)
|
||||
renderStdMethod, status100, status200,
|
||||
status201, status300, status401,
|
||||
status405, status500)
|
||||
import Prelude.Compat
|
||||
|
||||
import Servant.QuickCheck.Internal.ErrorTypes
|
||||
|
||||
|
@ -1,6 +1,8 @@
|
||||
{-# LANGUAGE RecordWildCards #-}
|
||||
module Servant.QuickCheck.Internal.QuickCheck where
|
||||
|
||||
import Control.Concurrent (modifyMVar_, newMVar, readMVar)
|
||||
import Control.Monad (unless)
|
||||
import qualified Data.ByteString.Lazy as LBS
|
||||
import Data.Proxy (Proxy)
|
||||
import Data.String (IsString (..))
|
||||
@ -16,15 +18,14 @@ import System.IO.Unsafe (unsafePerformIO)
|
||||
import Test.Hspec (Expectation, expectationFailure)
|
||||
import Test.QuickCheck (Args (..), Result (..),
|
||||
quickCheckWithResult)
|
||||
import Test.QuickCheck.Monadic (assert, forAllM, monadicIO, run, monitor)
|
||||
import Test.QuickCheck.Monadic (assert, forAllM, monadicIO, monitor,
|
||||
run)
|
||||
import Test.QuickCheck.Property (counterexample)
|
||||
import Control.Monad (unless)
|
||||
import Control.Concurrent (newMVar, modifyMVar_, readMVar)
|
||||
|
||||
import Servant.QuickCheck.Internal.Equality
|
||||
import Servant.QuickCheck.Internal.ErrorTypes
|
||||
import Servant.QuickCheck.Internal.HasGenRequest
|
||||
import Servant.QuickCheck.Internal.Predicates
|
||||
import Servant.QuickCheck.Internal.ErrorTypes
|
||||
|
||||
|
||||
-- | Start a servant application on an open port, run the provided function,
|
||||
|
@ -7,8 +7,7 @@ import Prelude.Compat
|
||||
import Servant
|
||||
import Servant.API.Internal.Test.ComprehensiveAPI (comprehensiveAPI)
|
||||
import Test.Hspec (Spec, context, describe, it,
|
||||
pending, shouldBe,
|
||||
shouldContain)
|
||||
shouldBe, shouldContain)
|
||||
import Test.Hspec.Core.Spec (Arg, Example, Result (..),
|
||||
defaultParams,
|
||||
evaluateExample)
|
||||
|
Loading…
Reference in New Issue
Block a user