servant-swagger-1.1.6: Generate Swagger specification for your servant API.

Safe HaskellNone
LanguageHaskell2010

Servant.Swagger.Internal.Test

Contents

Synopsis

Documentation

>>> import Control.Applicative
>>> import GHC.Generics
>>> import Test.QuickCheck
>>> :set -XDeriveGeneric
>>> :set -XGeneralizedNewtypeDeriving
>>> :set -XDataKinds
>>> :set -XTypeOperators

validateEveryToJSON Source #

Arguments

:: TMap (Every [Typeable, Show, Arbitrary, ToJSON, ToSchema]) (BodyTypes JSON api) 
=> proxy api

Servant API.

-> Spec 

Verify that every type used with JSON content type in a servant API has compatible ToJSON and ToSchema instances using validateToJSON.

NOTE: validateEveryToJSON does not perform string pattern validation. See validateEveryToJSONWithPatternChecker.

validateEveryToJSON will produce one prop specification for every type in the API. Each type only gets one test, even if it occurs multiple times in the API.

>>> data User = User { name :: String, age :: Maybe Int } deriving (Show, Generic, Typeable)
>>> newtype UserId = UserId String deriving (Show, Generic, Typeable, ToJSON, Arbitrary)
>>> instance ToJSON User
>>> instance ToSchema User
>>> instance ToSchema UserId
>>> instance Arbitrary User where arbitrary = User <$> arbitrary <*> arbitrary
>>> type UserAPI = (Capture "user_id" UserId :> Get '[JSON] User) :<|> (ReqBody '[JSON] User :> Post '[JSON] UserId)
>>> hspec $ context "ToJSON matches ToSchema" $ validateEveryToJSON (Proxy :: Proxy UserAPI)

ToJSON matches ToSchema
  User
...
  UserId
...
Finished in ... seconds
2 examples, 0 failures

For the test to compile all body types should have the following instances:

If any of the instances is missing, you'll get a descriptive type error:

>>> data Contact = Contact { fullname :: String, phone :: Integer } deriving (Show, Generic)
>>> instance ToJSON Contact
>>> instance ToSchema Contact
>>> type ContactAPI = Get '[JSON] Contact
>>> hspec $ validateEveryToJSON (Proxy :: Proxy ContactAPI)
...
...No instance for (Arbitrary Contact)
...  arising from a use of ‘validateEveryToJSON’
...

validateEveryToJSONWithPatternChecker Source #

Arguments

:: TMap (Every [Typeable, Show, Arbitrary, ToJSON, ToSchema]) (BodyTypes JSON api) 
=> (Pattern -> Text -> Bool)

Pattern checker.

-> proxy api

Servant API.

-> Spec 

Verify that every type used with JSON content type in a servant API has compatible ToJSON and ToSchema instances using validateToJSONWithPatternChecker.

For validation without patterns see validateEveryToJSON.

QuickCheck-related stuff

props Source #

Arguments

:: TMap (Every (Typeable ': (Show ': (Arbitrary ': cs)))) xs 
=> p cs

A list of constraints.

-> (forall x. EveryTF cs x => x -> Property)

Property predicate.

-> p'' xs

A list of types.

-> Spec 

Construct property tests for each type in a list. The name for each property is the name of the corresponding type.

>>> :{
 hspec $
   context "read . show == id" $
     props
       (Proxy :: Proxy [Eq, Show, Read])
       (\x -> read (show x) === x)
       (Proxy :: Proxy [Bool, Int, String])
:}

read . show == id
  Bool
...
  Int
...
  [Char]
...
Finished in ... seconds
3 examples, 0 failures

prettyValidateWith :: forall a. (ToJSON a, ToSchema a) => (a -> [ValidationError]) -> a -> Maybe String Source #

Pretty print validation errors together with actual JSON and Swagger Schema (using encodePretty).

>>> import Data.Aeson
>>> import Data.Foldable (traverse_)
>>> data Person = Person { name :: String, phone :: Integer } deriving (Generic)
>>> instance ToJSON Person where toJSON p = object [ "name" .= name p ]
>>> instance ToSchema Person
>>> let person = Person { name = "John", phone = 123456 }
>>> traverse_ putStrLn $ prettyValidateWith validateToJSON person
Validation against the schema fails:
  * property "phone" is required, but not found in "{\"name\":\"John\"}"

JSON value:
{
    "name": "John"
}

Swagger Schema:
{
    "required": [
        "name",
        "phone"
    ],
    "type": "object",
    "properties": {
        "phone": {
            "type": "integer"
        },
        "name": {
            "type": "string"
        }
    }
}

FIXME: this belongs in Data.Swagger.Schema.Validation (in swagger2).

maybeCounterExample :: Maybe String -> Property Source #

Provide a counterexample if there is any.