mirror of
https://github.com/ilyakooo0/compaREST.git
synced 2024-11-23 22:12:16 +03:00
Non-schema golden tests (#40)
* req body media * refac * wip * fix * wip * response media type object * parameters stuff * fix code * param schema * fix * Prods * Sums * wip * wip (compiles not works) * wip * rework responses * wip operations * PathItem done * path fragments done * matching done * fixups * path matching and other stuff * comment out * better error * Nope * tests ok * fix bug with responses * all works as usual * all tests ok * warnings * fix tests
This commit is contained in:
parent
95f82e1828
commit
1d27fd17f3
@ -112,11 +112,13 @@ library
|
||||
, OpenAPI.Checker.Validate.Param
|
||||
, OpenAPI.Checker.Validate.PathFragment
|
||||
, OpenAPI.Checker.Validate.ProcessedPathItem
|
||||
, OpenAPI.Checker.Validate.Products
|
||||
, OpenAPI.Checker.Validate.RequestBody
|
||||
, OpenAPI.Checker.Validate.Responses
|
||||
, OpenAPI.Checker.Validate.Schema
|
||||
, OpenAPI.Checker.Validate.SecurityRequirement
|
||||
, OpenAPI.Checker.Validate.Server
|
||||
, OpenAPI.Checker.Validate.Sums
|
||||
|
||||
executable openapi-diff
|
||||
import: common-options
|
||||
|
@ -21,7 +21,10 @@ deriving stock instance Ord AdditionalProperties
|
||||
deriving stock instance Ord Discriminator
|
||||
deriving stock instance Ord Xml
|
||||
deriving stock instance Ord OpenApiType
|
||||
deriving stock instance Ord Style
|
||||
deriving stock instance Ord OpenApiItems
|
||||
deriving stock instance Ord ParamLocation
|
||||
|
||||
|
||||
instance (Ord k, Ord v) => Ord (IOHM.InsOrdHashMap k v) where
|
||||
compare xs ys = compare (IOHM.toList xs) (IOHM.toList ys)
|
||||
|
@ -3,13 +3,16 @@
|
||||
module OpenAPI.Checker.Validate.MediaTypeObject () where
|
||||
|
||||
import Data.Foldable as F
|
||||
import Data.Functor
|
||||
import Data.HList
|
||||
import Data.HashMap.Strict.InsOrd as IOHM
|
||||
import Data.Map.Strict as M
|
||||
import Data.OpenApi
|
||||
import Data.Text (Text)
|
||||
import Network.HTTP.Media (MediaType, mainType, subType)
|
||||
import OpenAPI.Checker.Subtree
|
||||
import OpenAPI.Checker.Trace
|
||||
import OpenAPI.Checker.Validate.Products
|
||||
import OpenAPI.Checker.Validate.Schema ()
|
||||
|
||||
instance Subtree MediaTypeObject where
|
||||
@ -18,37 +21,37 @@ instance Subtree MediaTypeObject where
|
||||
, ProdCons (Definitions Schema)
|
||||
]
|
||||
data CheckIssue MediaTypeObject
|
||||
= MediaEncodingMissing
|
||||
= MediaEncodingMissing Text
|
||||
| MediaEncodingIncompat
|
||||
| MediaTypeSchemaRequired
|
||||
deriving (Eq, Ord, Show)
|
||||
checkCompatibility env (ProdCons p c) = do
|
||||
tryCheckEncoding
|
||||
checkSchema
|
||||
pure ()
|
||||
where
|
||||
mediaType = getH @MediaType env
|
||||
tryCheckEncoding =
|
||||
if | "multipart" == mainType mediaType -> checkEncoding
|
||||
| "application" == mainType mediaType &&
|
||||
"x-www-form-urlencoded" == subType mediaType -> checkEncoding
|
||||
| otherwise -> pure ()
|
||||
where
|
||||
-- Each parameter encoded by the producer must be parsed by the
|
||||
-- consumer
|
||||
checkEncoding = for_ (IOHM.toList $ _mediaTypeObjectEncoding p) $ \(paramName, prodEncoding) ->
|
||||
case IOHM.lookup paramName $ _mediaTypeObjectEncoding c of
|
||||
Nothing -> issueAt consumer MediaEncodingMissing
|
||||
Just consEncoding -> localStep (MediaTypeParamEncoding paramName)
|
||||
$ checkCompatibility HNil
|
||||
$ ProdCons prodEncoding consEncoding
|
||||
-- If consumer requires schema then producer must produce compatible
|
||||
-- request
|
||||
checkSchema = for_ (_mediaTypeObjectSchema c) $ \consRef ->
|
||||
checkCompatibility env prodCons@(ProdCons p c) = do
|
||||
if | "multipart" == mainType mediaType -> checkEncoding
|
||||
| "application" == mainType mediaType &&
|
||||
"x-www-form-urlencoded" == subType mediaType -> checkEncoding
|
||||
| otherwise -> pure ()
|
||||
-- If consumer requires schema then producer must produce compatible
|
||||
-- request
|
||||
for_ (_mediaTypeObjectSchema c) $ \consRef ->
|
||||
case _mediaTypeObjectSchema p of
|
||||
Nothing -> issueAt producer MediaTypeSchemaRequired
|
||||
Just prodRef -> localStep MediaTypeSchema
|
||||
$ checkCompatibility env $ ProdCons prodRef consRef
|
||||
pure ()
|
||||
where
|
||||
mediaType = getH @MediaType env
|
||||
checkEncoding =
|
||||
let
|
||||
-- Parameters of the media type are product-like entities
|
||||
getEncoding mt = M.fromList
|
||||
$ (IOHM.toList $ _mediaTypeObjectEncoding mt) <&> \(k, enc) ->
|
||||
( k
|
||||
, ProductLike
|
||||
{ traced = Traced (step $ MediaTypeParamEncoding k) enc
|
||||
, required = True } )
|
||||
encProdCons = getEncoding <$> prodCons
|
||||
in checkProducts MediaEncodingMissing
|
||||
(const $ checkCompatibility HNil) encProdCons
|
||||
|
||||
instance Subtree Encoding where
|
||||
type CheckEnv Encoding = '[]
|
||||
|
@ -1,123 +1,181 @@
|
||||
{-# OPTIONS_GHC -Wno-orphans #-}
|
||||
{-# OPTIONS_GHC -Wno-name-shadowing #-}
|
||||
|
||||
module OpenAPI.Checker.Validate.Operation (Step (..)) where
|
||||
module OpenAPI.Checker.Validate.Operation
|
||||
( MatchedOperation(..)
|
||||
) where
|
||||
|
||||
import Data.Foldable
|
||||
|
||||
import Data.Foldable as F
|
||||
import Data.Functor
|
||||
import Data.HList
|
||||
import qualified Data.HashMap.Strict.InsOrd as IOHM
|
||||
import qualified Data.List as L
|
||||
import Data.Map.Strict as M
|
||||
import Data.Maybe
|
||||
import Data.OpenApi
|
||||
import Data.Text (Text)
|
||||
import OpenAPI.Checker.References
|
||||
import OpenAPI.Checker.Subtree
|
||||
import OpenAPI.Checker.Trace
|
||||
import OpenAPI.Checker.Validate.Param ()
|
||||
import OpenAPI.Checker.Validate.PathFragment
|
||||
import OpenAPI.Checker.Validate.Products
|
||||
import OpenAPI.Checker.Validate.RequestBody ()
|
||||
import OpenAPI.Checker.Validate.Responses ()
|
||||
import OpenAPI.Checker.Validate.SecurityRequirement ()
|
||||
import OpenAPI.Checker.Validate.Server ()
|
||||
|
||||
instance Subtree Operation where
|
||||
type
|
||||
CheckEnv Operation =
|
||||
'[ ProdCons (Definitions Param)
|
||||
, ProdCons (Definitions RequestBody)
|
||||
, ProdCons (Definitions SecurityScheme)
|
||||
, ProdCons (Definitions Response)
|
||||
, ProdCons (Definitions Header)
|
||||
, ProdCons (Definitions Schema)
|
||||
]
|
||||
data CheckIssue Operation
|
||||
= ParamNotMatched Text -- Param name
|
||||
-- data ParamKey
|
||||
|
||||
data MatchedOperation = MatchedOperation
|
||||
{ operation :: !Operation
|
||||
, pathParams :: ![Traced OpenApi Param]
|
||||
-- ^ Params from the PathItem
|
||||
, getPathFragments :: !([Traced OpenApi Param] -> [Traced OpenApi PathFragmentParam])
|
||||
-- ^ Path fragments traced from PathItem. Takes full list of
|
||||
-- operation-specific parameters
|
||||
}
|
||||
|
||||
type ParamKey = (ParamLocation, Text)
|
||||
|
||||
paramKey :: Param -> ParamKey
|
||||
paramKey param = (_paramIn param, _paramName param)
|
||||
|
||||
instance Subtree MatchedOperation where
|
||||
type CheckEnv MatchedOperation =
|
||||
'[ ProdCons (Definitions Param)
|
||||
, ProdCons (Definitions RequestBody)
|
||||
, ProdCons (Definitions SecurityScheme)
|
||||
, ProdCons (Definitions Response)
|
||||
, ProdCons (Definitions Header)
|
||||
, ProdCons (Definitions Schema)
|
||||
]
|
||||
data CheckIssue MatchedOperation
|
||||
= ParamNotMatched ParamLocation Text
|
||||
-- ^ Non-path param has no pair
|
||||
| PathFragmentNotMatched Int
|
||||
-- ^ Path fragment with given position has no match
|
||||
| NoRequestBody
|
||||
| CallbacksNotSupported
|
||||
| SecurityRequirementNotMet Int -- security indexs
|
||||
| ServerNotConsumed Int -- server index
|
||||
deriving (Eq, Ord, Show)
|
||||
checkCompatibility env prodCons = do
|
||||
let ProdCons {producer = pNonPathParams, consumer = cNonPathParams} = do
|
||||
op <- _operationParameters <$> prodCons
|
||||
defParams <- getH @(ProdCons (Definitions Param)) env
|
||||
pure $
|
||||
filter ((/= ParamPath) . _paramIn . getTraced)
|
||||
. fmap (dereference defParams)
|
||||
$ op
|
||||
reqBody = do
|
||||
op <- _operationRequestBody <$> prodCons
|
||||
reqDefs <- getH @(ProdCons (Definitions RequestBody)) env
|
||||
pure $ fmap (dereference reqDefs) op
|
||||
for_ pNonPathParams $ \p@(Traced _ param) ->
|
||||
anyOfAt
|
||||
producer
|
||||
(ParamNotMatched $ _paramName param)
|
||||
[ checkProdCons HNil . fmap (retrace (step OperationParamsStep)) $ ProdCons p c
|
||||
| c <- cNonPathParams
|
||||
]
|
||||
case reqBody of
|
||||
ProdCons Nothing Nothing -> pure ()
|
||||
ProdCons (Just pBody) (Just cBody) ->
|
||||
localStep OperationRequestBodyStep $
|
||||
checkProdCons env (ProdCons pBody cBody)
|
||||
ProdCons Nothing (Just _) -> issueAt producer NoRequestBody
|
||||
ProdCons (Just _) Nothing -> issueAt consumer NoRequestBody
|
||||
localStep OperationResponsesStep $
|
||||
checkCompatibility env $ _operationResponses <$> prodCons
|
||||
-- FIXME: https://github.com/typeable/openapi-diff/issues/27
|
||||
case IOHM.null . _operationCallbacks <$> prodCons of
|
||||
(ProdCons True True) -> pure ()
|
||||
(ProdCons False _) -> issueAt producer CallbacksNotSupported
|
||||
(ProdCons _ False) -> issueAt consumer CallbacksNotSupported
|
||||
-- FIXME: https://github.com/typeable/openapi-diff/issues/28
|
||||
sequenceA_
|
||||
[ anyOfAt
|
||||
producer
|
||||
(SecurityRequirementNotMet i)
|
||||
[ localStep OperationSecurityRequirementStep $
|
||||
checkCompatibility env $ ProdCons prodSecurity consSecurity
|
||||
| consSecurity <- _operationSecurity . consumer $ prodCons
|
||||
]
|
||||
| (i, prodSecurity) <- zip [0 ..] . _operationSecurity . producer $ prodCons
|
||||
]
|
||||
-- FIXME: https://github.com/typeable/openapi-diff/issues/29s
|
||||
sequenceA_
|
||||
[ anyOfAt
|
||||
producer
|
||||
(ServerNotConsumed i)
|
||||
[ localStep OperationServerStep $
|
||||
checkCompatibility env $ ProdCons pServer cServer
|
||||
| cServer <- _operationServers . consumer $ prodCons
|
||||
]
|
||||
| (i, pServer) <- zip [0 ..] . _operationServers . producer $ prodCons
|
||||
]
|
||||
checkCompatibility env prodCons = withTrace $ \myTrace -> do
|
||||
checkParameters myTrace
|
||||
checkRequestBodies
|
||||
checkResponses
|
||||
checkCallbacks
|
||||
checkOperationSecurity
|
||||
checkServers
|
||||
pure ()
|
||||
where
|
||||
checkParameters myTrace = do
|
||||
let
|
||||
-- Merged parameters got from Operation and PathItem in one
|
||||
-- place. First element is path params, second is non-path params
|
||||
tracedParams :: ProdCons ([Traced OpenApi Param], [Traced OpenApi Param])
|
||||
tracedParams = getParams <$> myTrace <*> paramDefs <*> prodCons
|
||||
getParams root defs mp =
|
||||
let
|
||||
operationParamsMap :: Map ParamKey (Traced OpenApi Param)
|
||||
operationParamsMap = M.fromList $ do
|
||||
paramRef <- _operationParameters $ operation mp
|
||||
let
|
||||
tracedParam = retrace root
|
||||
$ dereferenceTraced defs
|
||||
$ Traced (step $ OperationParamsStep) paramRef
|
||||
key = paramKey $ getTraced tracedParam
|
||||
pure (key, tracedParam)
|
||||
pathParamsMap :: Map ParamKey (Traced OpenApi Param)
|
||||
pathParamsMap = M.fromList $ do
|
||||
param <- pathParams mp
|
||||
pure (paramKey $ getTraced param, param)
|
||||
params = M.elems $ M.union operationParamsMap pathParamsMap
|
||||
-- We prefer params from Operation
|
||||
splitted = L.partition
|
||||
(\p -> (_paramIn $ getTraced p) == ParamPath) params
|
||||
in splitted
|
||||
checkNonPathParams $ snd <$> tracedParams
|
||||
checkPathParams $ fst <$> tracedParams
|
||||
pure ()
|
||||
checkNonPathParams :: ProdCons [Traced OpenApi Param] -> CompatFormula MatchedOperation ()
|
||||
checkNonPathParams params = do
|
||||
let
|
||||
elements = getEls <$> params
|
||||
getEls traced = M.fromList $ do
|
||||
p <- traced
|
||||
let
|
||||
param = getTraced p
|
||||
k = (_paramIn param, _paramName param)
|
||||
v = ProductLike
|
||||
{ traced = p
|
||||
, required = fromMaybe False $ _paramRequired param
|
||||
}
|
||||
pure (k, v)
|
||||
check _ param = do
|
||||
checkCompatibility @Param (singletonH schemaDefs) param
|
||||
checkProducts' (uncurry ParamNotMatched) check elements
|
||||
checkPathParams pathParams = do
|
||||
let
|
||||
fragments :: ProdCons [Traced OpenApi PathFragmentParam]
|
||||
fragments = getFragments <$> pathParams <*> prodCons
|
||||
getFragments params mop = (getPathFragments mop) params
|
||||
-- Feed path parameters to the fragments getter
|
||||
check _ frags = checkCompatibility @PathFragmentParam env frags
|
||||
elements = fragments <&> \frags -> M.fromList $ zip [0..] $ do
|
||||
frag <- frags
|
||||
pure $ ProductLike
|
||||
{ traced = frag
|
||||
, required = True }
|
||||
checkProducts' PathFragmentNotMatched check elements
|
||||
checkRequestBodies = do
|
||||
let
|
||||
check _ reqBody = checkCompatibility @RequestBody env reqBody
|
||||
elements = getReqBody <$> bodyDefs <*> prodCons
|
||||
getReqBody bodyDef mop = M.fromList $ do
|
||||
bodyRef <- F.toList $ _operationRequestBody $ operation mop
|
||||
let
|
||||
traced = dereferenceTraced bodyDef
|
||||
$ Traced (step $ OperationRequestBodyStep) bodyRef
|
||||
required = fromMaybe False
|
||||
$ _requestBodyRequired $ getTraced traced
|
||||
elt = ProductLike { traced, required }
|
||||
-- Single element map
|
||||
pure ((), elt)
|
||||
checkProducts (const NoRequestBody) check elements
|
||||
checkResponses = do
|
||||
let
|
||||
resps = (_operationResponses . operation) <$> prodCons
|
||||
respEnv = HCons (swapProdCons respDefs)
|
||||
$ HCons (swapProdCons headerDefs)
|
||||
$ HCons (swapProdCons schemaDefs) HNil
|
||||
localStep OperationResponsesStep
|
||||
$ swapRoles $ checkCompatibility respEnv $ swapProdCons resps
|
||||
checkCallbacks = pure () -- (error "FIXME: not implemented")
|
||||
checkOperationSecurity = pure () -- (error "FIXME: not implemented")
|
||||
checkServers = pure () -- (error "FIXME: not implemented")
|
||||
bodyDefs = getH @(ProdCons (Definitions RequestBody)) env
|
||||
respDefs = getH @(ProdCons (Definitions Response)) env
|
||||
headerDefs = getH @(ProdCons (Definitions Header)) env
|
||||
schemaDefs = getH @(ProdCons (Definitions Schema)) env
|
||||
paramDefs = getH @(ProdCons (Definitions Param)) env
|
||||
|
||||
instance Steppable PathItem Operation where
|
||||
data Step PathItem Operation
|
||||
= GetStep
|
||||
| PutStep
|
||||
| PostStep
|
||||
| DeleteStep
|
||||
| OptionsStep
|
||||
| HeadStep
|
||||
| PatchStep
|
||||
| TraceStep
|
||||
instance Steppable MatchedOperation (Referenced Param) where
|
||||
data Step MatchedOperation (Referenced Param) = OperationParamsStep
|
||||
deriving (Eq, Ord, Show)
|
||||
|
||||
instance Steppable Operation (Referenced Param) where
|
||||
data Step Operation (Referenced Param) = OperationParamsStep
|
||||
instance Steppable MatchedOperation (Referenced RequestBody) where
|
||||
data Step MatchedOperation (Referenced RequestBody) = OperationRequestBodyStep
|
||||
deriving (Eq, Ord, Show)
|
||||
|
||||
instance Steppable Operation (Referenced RequestBody) where
|
||||
data Step Operation (Referenced RequestBody) = OperationRequestBodyStep
|
||||
instance Steppable MatchedOperation Responses where
|
||||
data Step MatchedOperation Responses = OperationResponsesStep
|
||||
deriving (Eq, Ord, Show)
|
||||
|
||||
instance Steppable Operation Responses where
|
||||
data Step Operation Responses = OperationResponsesStep
|
||||
instance Steppable MatchedOperation SecurityRequirement where
|
||||
data Step MatchedOperation SecurityRequirement = OperationSecurityRequirementStep
|
||||
deriving (Eq, Ord, Show)
|
||||
|
||||
instance Steppable Operation SecurityRequirement where
|
||||
data Step Operation SecurityRequirement = OperationSecurityRequirementStep
|
||||
deriving (Eq, Ord, Show)
|
||||
|
||||
instance Steppable Operation Server where
|
||||
data Step Operation Server = OperationServerStep
|
||||
instance Steppable MatchedOperation Server where
|
||||
data Step MatchedOperation Server = OperationServerStep
|
||||
deriving (Eq, Ord, Show)
|
||||
|
@ -1,31 +1,83 @@
|
||||
{-# OPTIONS_GHC -Wno-orphans #-}
|
||||
{-# OPTIONS_GHC -fno-warn-name-shadowing #-}
|
||||
|
||||
module OpenAPI.Checker.Validate.Param () where
|
||||
|
||||
import Data.OpenApi
|
||||
import Control.Monad
|
||||
import Data.Maybe
|
||||
import Data.OpenApi
|
||||
import OpenAPI.Checker.Orphans
|
||||
import OpenAPI.Checker.Subtree
|
||||
import OpenAPI.Checker.Trace
|
||||
import OpenAPI.Checker.Validate.Schema ()
|
||||
|
||||
-- | The type is normalized encoding style of the parameter. If two encoding
|
||||
-- styles are equal then parameters are compatible with their encoding style
|
||||
data EncodingStyle = EncodingStyle
|
||||
{ style :: Style
|
||||
, explode :: Bool
|
||||
, allowReserved :: Maybe Bool
|
||||
-- ^ Nothing when @in@ parameter is not @query@
|
||||
} deriving (Eq, Ord, Show)
|
||||
|
||||
paramEncoding :: Param -> EncodingStyle
|
||||
paramEncoding p = EncodingStyle
|
||||
{ style, explode, allowReserved }
|
||||
where
|
||||
style = fromMaybe defaultStyle $ _paramStyle p
|
||||
defaultStyle = case _paramIn p of
|
||||
ParamQuery -> StyleForm
|
||||
ParamPath -> StyleSimple
|
||||
ParamHeader -> StyleSimple
|
||||
ParamCookie -> StyleForm
|
||||
explode = fromMaybe defaultExplode $ _paramExplode p
|
||||
defaultExplode = case style of
|
||||
StyleForm -> True
|
||||
_ -> False
|
||||
allowReserved = case _paramIn p of
|
||||
ParamQuery -> Just $ fromMaybe False $ _paramAllowReserved p
|
||||
_ -> Nothing
|
||||
|
||||
instance Subtree Param where
|
||||
type CheckEnv Param = '[]
|
||||
type CheckEnv Param = '[ProdCons (Definitions Schema)]
|
||||
data CheckIssue Param
|
||||
= ParamNameMismatch
|
||||
-- ^ Params have different names
|
||||
| ParamOptionalityIncompatible
|
||||
-- ^ Consumer requires non-empty param, but producer gives optional
|
||||
| ParamEmptinessIncompatible
|
||||
-- ^ Consumer requires non-empty param, but producer gives emptyable
|
||||
| ParamRequired
|
||||
-- ^ Consumer requires mandatory parm, but producer optional
|
||||
| ParamPlaceIncompatible
|
||||
| ParamStyleMismatch
|
||||
-- ^ Params encoded in different styles
|
||||
| ParamSchemaMismatch
|
||||
-- ^ One of schemas not presented
|
||||
deriving (Eq, Ord, Show)
|
||||
checkCompatibility env (ProdCons p c) = do
|
||||
when (_paramName p /= _paramName c)
|
||||
$ issueAt producer ParamNameMismatch
|
||||
when ((fromMaybe False $ _paramRequired c) &&
|
||||
not (fromMaybe False $ _paramRequired p))
|
||||
$ issueAt producer ParamRequired
|
||||
case (_paramIn p, _paramIn c) of
|
||||
(ParamQuery, ParamQuery) -> do
|
||||
-- Emptiness is only for query params
|
||||
when ((fromMaybe False $ _paramAllowEmptyValue p)
|
||||
&& not (fromMaybe False $ _paramAllowEmptyValue c))
|
||||
$ issueAt producer ParamEmptinessIncompatible
|
||||
(a, b) | a == b -> pure ()
|
||||
_ -> issueAt producer ParamPlaceIncompatible
|
||||
unless (paramEncoding p == paramEncoding c)
|
||||
$ issueAt producer ParamStyleMismatch
|
||||
case (_paramSchema p, _paramSchema c) of
|
||||
(Just prodSchema, Just consSchema) -> localStep ParamSchema
|
||||
$ checkCompatibility env (ProdCons prodSchema consSchema)
|
||||
(Nothing, Nothing) -> pure ()
|
||||
(Nothing, Just _consSchema) -> issueAt producer ParamSchemaMismatch
|
||||
(Just _prodSchema, Nothing) -> pure ()
|
||||
-- If consumer doesn't care then why we should?
|
||||
pure ()
|
||||
|
||||
instance Steppable Param (Referenced Schema) where
|
||||
data Step Param (Referenced Schema) = ParamSchema
|
||||
deriving (Eq, Ord, Show)
|
||||
checkCompatibility _ (ProdCons p c) = case ( _paramIn p, _paramIn c) of
|
||||
(ParamQuery, ParamQuery) ->
|
||||
namesCompatible $
|
||||
if (fromMaybe False $ _paramAllowEmptyValue p)
|
||||
&& not (fromMaybe False $ _paramAllowEmptyValue c)
|
||||
then issueAt producer ParamOptionalityIncompatible
|
||||
else pure ()
|
||||
(a, b) | a == b -> namesCompatible $ pure ()
|
||||
_ -> issueAt producer ParamPlaceIncompatible
|
||||
where
|
||||
namesCompatible next =
|
||||
if _paramName p /= _paramName c
|
||||
then issueAt producer ParamNameMismatch
|
||||
else next
|
||||
|
@ -1,96 +1,71 @@
|
||||
module OpenAPI.Checker.Validate.PathFragment
|
||||
( PathParamRefs
|
||||
, TracedReferences
|
||||
, getPathParamRefs
|
||||
, parsePath
|
||||
( parsePath
|
||||
, PathFragment (..)
|
||||
, PathFragmentParam
|
||||
)
|
||||
where
|
||||
|
||||
import Control.Lens
|
||||
import Control.Monad.Reader
|
||||
import qualified Data.Aeson as A
|
||||
import Data.HList
|
||||
import qualified Data.List.NonEmpty as NE
|
||||
import Data.Map.Strict (Map)
|
||||
import qualified Data.Map.Strict as M
|
||||
import Data.Maybe
|
||||
import Data.OpenApi
|
||||
import Data.Text (Text)
|
||||
import qualified Data.Text as T
|
||||
import OpenAPI.Checker.References
|
||||
import Data.Typeable
|
||||
import OpenAPI.Checker.Subtree
|
||||
import OpenAPI.Checker.Trace
|
||||
import OpenAPI.Checker.Validate.Param ()
|
||||
|
||||
getPathParamRefs
|
||||
:: Definitions Param
|
||||
-> [Referenced Param]
|
||||
-> Map Reference (Traced (Referenced Param) Param)
|
||||
getPathParamRefs defs xs =
|
||||
M.fromList $ do
|
||||
x <- xs
|
||||
let (Traced t param) = dereference defs x
|
||||
guard (_paramIn param == ParamPath)
|
||||
return (Reference $ _paramName param, Traced t param)
|
||||
|
||||
-- TODO: templates can be only part of the PathFragment. Currently only supports templates as full PathFragment.
|
||||
-- https://github.com/typeable/openapi-diff/issues/23
|
||||
parsePath :: FilePath -> [PathFragment]
|
||||
parsePath :: FilePath -> [PathFragment Text]
|
||||
parsePath = fmap partition . T.splitOn "/" . T.pack
|
||||
where
|
||||
partition :: Text -> PathFragment
|
||||
partition :: Text -> PathFragment Text
|
||||
partition t
|
||||
| Just ('{', rest) <- T.uncons t
|
||||
, Just (ref, '}') <- T.unsnoc rest =
|
||||
DynamicPath $ Reference ref
|
||||
DynamicPath ref
|
||||
partition t = StaticPath t
|
||||
|
||||
data PathFragment
|
||||
-- | Fragment parameterized by parameter. The dynamic part may be either
|
||||
-- reference to some parameter (in context of operation) or dereferenced
|
||||
-- parameter itself.
|
||||
data PathFragment param
|
||||
= StaticPath Text
|
||||
| DynamicPath Reference
|
||||
| DynamicPath param
|
||||
deriving stock (Eq, Ord)
|
||||
|
||||
instance Steppable PathFragment Param where
|
||||
data Step PathFragment Param = StaticPathParam
|
||||
type PathFragmentParam = PathFragment (Traced OpenApi Param)
|
||||
|
||||
instance (Typeable param) => Steppable (PathFragment param) Param where
|
||||
data Step (PathFragment param) Param = StaticPathParam Text
|
||||
deriving (Eq, Ord, Show)
|
||||
|
||||
type PathParamRefs = TracedReferences PathFragment Param
|
||||
|
||||
instance Subtree PathFragment where
|
||||
type CheckEnv PathFragment = '[ProdCons PathParamRefs]
|
||||
data CheckIssue PathFragment = PathFragmentsDontMatch Text Text
|
||||
instance Subtree PathFragmentParam where
|
||||
type CheckEnv PathFragmentParam =
|
||||
'[ ProdCons (Definitions Schema) ]
|
||||
data CheckIssue PathFragmentParam =
|
||||
PathFragmentsDontMatch Text Text
|
||||
deriving (Eq, Ord, Show)
|
||||
|
||||
-- This case isn't strictly needed. It is here for optimization.
|
||||
checkCompatibility _ ProdCons {producer = (StaticPath x), consumer = (StaticPath y)} =
|
||||
if x == y
|
||||
then pure ()
|
||||
else issueAt consumer (PathFragmentsDontMatch x y)
|
||||
checkCompatibility env prodCons = do
|
||||
let (t, param) =
|
||||
fsplit . fmap deTraced $
|
||||
dePathFragment
|
||||
<$> (singletonH <$> getH @(ProdCons PathParamRefs) env)
|
||||
<*> prodCons
|
||||
localTrace t $ checkCompatibility env param
|
||||
|
||||
-- | A clearer name for 'NE.unzip' that can be used without qualifying it.
|
||||
fsplit :: Functor f => f (a, b) -> (f a, f b)
|
||||
fsplit = NE.unzip
|
||||
|
||||
dePathFragment :: Has PathParamRefs xs => HList xs -> PathFragment -> Traced PathFragment Param
|
||||
dePathFragment (getH @PathParamRefs -> params) = \case
|
||||
(StaticPath s) ->
|
||||
Traced (step StaticPathParam) $
|
||||
mempty
|
||||
{ _paramRequired = Just True
|
||||
, _paramIn = ParamPath
|
||||
, _paramAllowEmptyValue = Just False
|
||||
, _paramAllowReserved = Just False
|
||||
, _paramSchema = Just $ Inline $ staticStringSchema s
|
||||
}
|
||||
(DynamicPath ref) -> M.lookup ref params & fromMaybe (error $ show ref <> " not found.")
|
||||
checkCompatibility env prodCons = withTrace $ \myTrace -> do
|
||||
let
|
||||
tracedParams = dePathFragment <$> myTrace <*> prodCons
|
||||
dePathFragment root = \case
|
||||
StaticPath s -> retrace root $ Traced (step $ StaticPathParam s)
|
||||
$ mempty
|
||||
{ _paramRequired = Just True
|
||||
, _paramIn = ParamPath
|
||||
, _paramAllowEmptyValue = Just False
|
||||
, _paramAllowReserved = Just False
|
||||
, _paramSchema = Just $ Inline $ staticStringSchema s }
|
||||
DynamicPath p -> p
|
||||
params = getTraced <$> tracedParams
|
||||
paramTrace = getTrace <$> tracedParams
|
||||
localTrace' paramTrace $ checkCompatibility env params
|
||||
|
||||
staticStringSchema :: Text -> Schema
|
||||
staticStringSchema t =
|
||||
|
@ -1,4 +1,5 @@
|
||||
{-# OPTIONS_GHC -Wno-orphans #-}
|
||||
{-# OPTIONS_GHC -Wno-name-shadowing #-}
|
||||
|
||||
module OpenAPI.Checker.Validate.ProcessedPathItem
|
||||
( ProcessedPathItem (..)
|
||||
@ -8,16 +9,21 @@ module OpenAPI.Checker.Validate.ProcessedPathItem
|
||||
)
|
||||
where
|
||||
|
||||
import Data.Foldable
|
||||
import Control.Monad
|
||||
import Data.Foldable as F
|
||||
import Data.Functor
|
||||
import Data.HList
|
||||
import qualified Data.List as L
|
||||
import Data.Map.Strict as M
|
||||
import Data.Maybe
|
||||
import Data.OpenApi
|
||||
import Generic.Data
|
||||
import Data.Text as T
|
||||
import OpenAPI.Checker.References
|
||||
import OpenAPI.Checker.Subtree
|
||||
import OpenAPI.Checker.Trace
|
||||
import OpenAPI.Checker.Validate.Operation
|
||||
import OpenAPI.Checker.Validate.PathFragment
|
||||
import OpenAPI.Checker.Validate.Sums
|
||||
|
||||
-- FIXME: There's probably a better name for this, but `PathItem` is already taken ;(
|
||||
data ProcessedPathItem = ProcessedPathItem
|
||||
@ -28,7 +34,8 @@ data ProcessedPathItem = ProcessedPathItem
|
||||
processPathItems :: [(FilePath, PathItem)] -> ProcessedPathItems
|
||||
processPathItems = ProcessedPathItems . fmap (uncurry ProcessedPathItem)
|
||||
|
||||
newtype ProcessedPathItems = ProcessedPathItems {unProcessedPathItems :: [ProcessedPathItem]}
|
||||
newtype ProcessedPathItems =
|
||||
ProcessedPathItems {unProcessedPathItems :: [ProcessedPathItem]}
|
||||
|
||||
instance Subtree ProcessedPathItems where
|
||||
type
|
||||
@ -40,48 +47,54 @@ instance Subtree ProcessedPathItems where
|
||||
, ProdCons (Definitions Header)
|
||||
, ProdCons (Definitions Schema)
|
||||
]
|
||||
data CheckIssue ProcessedPathItems = NoPathsMatched | WrongNumberOfFragments
|
||||
data CheckIssue ProcessedPathItems
|
||||
= NoPathsMatched FilePath
|
||||
| AllPathsFailed FilePath
|
||||
-- When several paths match given but all checks failed
|
||||
deriving (Eq, Ord, Show)
|
||||
checkCompatibility env prodCons = do
|
||||
let ProdCons {producer = p, consumer = c} =
|
||||
(\paramDefs -> fmap (processPathItem paramDefs) . unProcessedPathItems)
|
||||
<$> getH @(ProdCons (Definitions Param)) env
|
||||
<*> prodCons
|
||||
sequenceA_
|
||||
[ anyOf'
|
||||
[ localTrace (step <$> ProdCons pSPath cSPath) $ do
|
||||
-- make sure every path fragment is compatible
|
||||
sequenceA_
|
||||
[ localTrace (pure . step $ PathFragmentStep i) $
|
||||
checkCompatibility (singletonH $ ProdCons pPathFragmentParams cPathFragmentParams) pair
|
||||
| (i, pair) <- zip [0 ..] pathFragments
|
||||
]
|
||||
-- make sure the operation is compatible.
|
||||
localTrace (pure . step $ getter stepProcessedPathItem) $
|
||||
checkCompatibility env $ ProdCons pOperation cOperation
|
||||
pure ()
|
||||
| (cSPath, cPath, cPathItem) <- c
|
||||
, -- ... and try to match it with every endpoint in the consumer.
|
||||
--
|
||||
-- This is required because the meaning of path fragments can change on
|
||||
-- a per-method basis even within the same 'PathItem'
|
||||
--
|
||||
-- Here we only need to look for the method that the current producer
|
||||
-- endpoint is using.
|
||||
(cParams, cOperation) <- maybeToList $ getter cPathItem
|
||||
, let cPathFragmentParams = retrace (step PathFragmentParentStep) <$> cParams
|
||||
, -- make sure the paths are the same length
|
||||
pathFragments <- maybeToList $ zipAllWith ProdCons pPath cPath
|
||||
]
|
||||
| (pSPath, pPath, pPathItem) <- p
|
||||
, -- look at every endpoint in the producer ...
|
||||
(ProcessedPathItemGetter getter, (pParams, pOperation)) <-
|
||||
toList (fmap . (,) <$> processedPathItemGetters <*> pPathItem) >>= maybeToList
|
||||
, let pPathFragmentParams = retrace (step PathFragmentParentStep) <$> pParams
|
||||
]
|
||||
checkCompatibility env (ProdCons p c) = do
|
||||
-- Each path generated by producer must be handled by consumer with exactly
|
||||
-- one way
|
||||
for_ (unProcessedPathItems p) $ \ prodItem -> do
|
||||
let
|
||||
prodPath = path prodItem
|
||||
matchedItems = do
|
||||
consItem <- unProcessedPathItems c
|
||||
matched <- F.toList $ matchingPathItems $ ProdCons prodItem consItem
|
||||
return matched
|
||||
case matchedItems of
|
||||
[] -> issueAt producer $ NoPathsMatched prodPath
|
||||
[matched] -> do
|
||||
-- Checking exact match with no wrapper
|
||||
let trace = matchedTrace <$> matched
|
||||
localTrace trace $ checkCompatibility env matched
|
||||
matches -> anyOfAt consumer (AllPathsFailed prodPath) $ do
|
||||
match <- matches
|
||||
let trace = matchedTrace <$> match
|
||||
pure $ localTrace trace $ checkCompatibility env match
|
||||
where
|
||||
anyOf' [x] = x -- preserve errors if there's only one choice
|
||||
anyOf' xs = anyOfAt producer NoPathsMatched xs
|
||||
matchedTrace :: MatchedPathItem -> Trace ProcessedPathItems MatchedPathItem
|
||||
matchedTrace mpi = step $ MatchedPathStep $ matchedPath mpi
|
||||
|
||||
-- | Preliminary checks two paths for compatibility. Returns Nothing if two
|
||||
-- paths obviously do not match: static parts differ or count of path elements
|
||||
-- is not equal
|
||||
matchingPathItems :: ProdCons ProcessedPathItem -> Maybe (ProdCons MatchedPathItem)
|
||||
matchingPathItems prodCons = do
|
||||
let frags = parsePath . path <$> prodCons
|
||||
guard $ fragsMatch frags
|
||||
let
|
||||
mkMatchedItems frag ppi = MatchedPathItem
|
||||
{ pathItem = item ppi
|
||||
, matchedPath = path ppi
|
||||
, pathFragments = frag }
|
||||
return $ mkMatchedItems <$> frags <*> prodCons
|
||||
|
||||
fragsMatch :: ProdCons [PathFragment Text] -> Bool
|
||||
fragsMatch (ProdCons p c) = maybe False and $ zipAllWith check p c
|
||||
where
|
||||
check (StaticPath s1) (StaticPath s2) = s1 == s2
|
||||
check _ _ = True
|
||||
|
||||
zipAllWith :: (a -> b -> c) -> [a] -> [b] -> Maybe [c]
|
||||
zipAllWith _ [] [] = Just []
|
||||
@ -89,96 +102,102 @@ zipAllWith f (x : xs) (y : ys) = (f x y :) <$> zipAllWith f xs ys
|
||||
zipAllWith _ (_ : _) [] = Nothing
|
||||
zipAllWith _ [] (_ : _) = Nothing
|
||||
|
||||
processPathItem
|
||||
:: Definitions Param -- ^ from components
|
||||
-> ProcessedPathItem
|
||||
-> ( Step ProcessedPathItems PathItem
|
||||
, [PathFragment]
|
||||
, ForeachOperation (Maybe (TracedReferences PathItem Param, Operation))
|
||||
)
|
||||
processPathItem componentParams ProcessedPathItem {path = pathS, item = pathItem} =
|
||||
let path = parsePath pathS
|
||||
commonPathParams =
|
||||
retrace (step PathItemParametersStep)
|
||||
<$> getPathParamRefs componentParams (_pathItemParameters pathItem)
|
||||
processOperation (s :: Step PathItem Operation) op =
|
||||
let operationParams =
|
||||
retrace (Root `Snoc` s `Snoc` OperationParamsStep)
|
||||
<$> getPathParamRefs componentParams (_operationParameters op)
|
||||
pathParams =
|
||||
operationParams <> commonPathParams
|
||||
in (pathParams, op)
|
||||
in ( PathStep pathS
|
||||
, path
|
||||
, fmap . processOperation
|
||||
<$> stepProcessedPathItem
|
||||
<*> ForeachOperation
|
||||
{ processedPathItemGet = _pathItemGet pathItem
|
||||
, processedPathItemPut = _pathItemPut pathItem
|
||||
, processedPathItemPost = _pathItemPost pathItem
|
||||
, processedPathItemDelete = _pathItemDelete pathItem
|
||||
, processedPathItemOptions = _pathItemOptions pathItem
|
||||
, processedPathItemHead = _pathItemHead pathItem
|
||||
, processedPathItemPatch = _pathItemPatch pathItem
|
||||
, processedPathItemTrace = _pathItemTrace pathItem
|
||||
}
|
||||
)
|
||||
|
||||
instance Steppable ProcessedPathItems PathItem where
|
||||
data Step ProcessedPathItems PathItem = PathStep FilePath
|
||||
deriving (Eq, Ord, Show)
|
||||
|
||||
instance Steppable PathItem PathFragment where
|
||||
data Step PathItem PathFragment
|
||||
= -- | The index of the path item
|
||||
PathFragmentStep Int
|
||||
deriving (Eq, Ord, Show)
|
||||
|
||||
instance Steppable PathFragment PathItem where
|
||||
data Step PathFragment PathItem = PathFragmentParentStep
|
||||
deriving (Eq, Ord, Show)
|
||||
|
||||
instance Steppable PathItem (Referenced Param) where
|
||||
data Step PathItem (Referenced Param) = PathItemParametersStep
|
||||
deriving (Eq, Ord, Show)
|
||||
|
||||
data ForeachOperation a = ForeachOperation
|
||||
{ processedPathItemGet :: a
|
||||
, processedPathItemPut :: a
|
||||
, processedPathItemPost :: a
|
||||
, processedPathItemDelete :: a
|
||||
, processedPathItemOptions :: a
|
||||
, processedPathItemHead :: a
|
||||
, processedPathItemPatch :: a
|
||||
, processedPathItemTrace :: a
|
||||
data MatchedPathItem = MatchedPathItem
|
||||
{ pathItem :: !PathItem
|
||||
, matchedPath :: !FilePath
|
||||
, pathFragments :: ![PathFragment Text]
|
||||
-- ^ Pre-parsed path from PathItem
|
||||
}
|
||||
deriving stock (Functor, Generic1)
|
||||
deriving (Applicative, Foldable) via Generically1 ForeachOperation
|
||||
|
||||
newtype ProcessedPathItemGetter = ProcessedPathItemGetter (forall a. ForeachOperation a -> a)
|
||||
instance Subtree MatchedPathItem where
|
||||
type CheckEnv MatchedPathItem =
|
||||
'[ ProdCons (Definitions Param)
|
||||
, ProdCons (Definitions RequestBody)
|
||||
, ProdCons (Definitions SecurityScheme)
|
||||
, ProdCons (Definitions Response)
|
||||
, ProdCons (Definitions Header)
|
||||
, ProdCons (Definitions Schema)
|
||||
]
|
||||
data CheckIssue MatchedPathItem
|
||||
= OperationMissing (Step MatchedPathItem MatchedOperation)
|
||||
deriving (Eq, Ord, Show)
|
||||
checkCompatibility env prodCons = withTrace $ \rootTrace -> do
|
||||
let
|
||||
paramDefs = getH @(ProdCons (Definitions Param)) env
|
||||
pathTracedParams = getPathParams <$> rootTrace <*> paramDefs <*> prodCons
|
||||
getPathParams
|
||||
:: Trace OpenApi MatchedPathItem
|
||||
-> Definitions Param
|
||||
-> MatchedPathItem
|
||||
-> [Traced OpenApi Param]
|
||||
getPathParams root defs mpi = do
|
||||
paramRef <- _pathItemParameters $ pathItem mpi
|
||||
let
|
||||
traced = dereferenceTraced defs
|
||||
$ Traced (step PathItemParam) paramRef
|
||||
res = retrace root traced
|
||||
pure res
|
||||
pathTracedFragments = mkPathFragments <$> rootTrace <*> prodCons
|
||||
mkPathFragments myRoot mpi operationParams =
|
||||
-- operationParams will be known on Operation check stage, so we give a
|
||||
-- function, returning fragments
|
||||
let
|
||||
paramsMap :: Map Text (Traced OpenApi Param)
|
||||
paramsMap = M.fromList $ do
|
||||
tracedParam <- operationParams
|
||||
let pname = _paramName $ getTraced tracedParam
|
||||
pure (pname, tracedParam)
|
||||
fragments :: [PathFragmentParam]
|
||||
fragments = (pathFragments mpi) <&> \case
|
||||
StaticPath t -> StaticPath t
|
||||
DynamicPath pname -> DynamicPath
|
||||
$ fromMaybe (error $ "Param not found " <> T.unpack pname)
|
||||
$ M.lookup pname paramsMap
|
||||
tracedFragments :: [Traced OpenApi PathFragmentParam]
|
||||
tracedFragments = L.zip [0..] fragments <&> \(pos, frag) ->
|
||||
retrace myRoot $ Traced (step $ PathFragmentStep pos) frag
|
||||
in tracedFragments
|
||||
operations = getOperations <$> pathTracedParams <*> pathTracedFragments <*> prodCons
|
||||
getOperations pathParams getPathFragments mpi = M.fromList $ do
|
||||
(getOp, s) <-
|
||||
[ (_pathItemGet, GetStep)
|
||||
, (_pathItemPut, PutStep)
|
||||
, (_pathItemPost, PostStep)
|
||||
, (_pathItemDelete, DeleteStep)
|
||||
, (_pathItemOptions, OptionsStep)
|
||||
, (_pathItemHead, HeadStep)
|
||||
, (_pathItemPatch, PatchStep)
|
||||
, (_pathItemTrace, TraceStep) ]
|
||||
operation <- F.toList $ getOp $ pathItem mpi
|
||||
-- Got only Justs here
|
||||
let mop = MatchedOperation { operation , pathParams, getPathFragments }
|
||||
pure (s, Traced (step s) mop)
|
||||
check _ pc = checkCompatibility @MatchedOperation env pc
|
||||
-- Operations are sum-like entities. Use step to operation as key because
|
||||
-- why not
|
||||
checkSums OperationMissing check operations
|
||||
|
||||
processedPathItemGetters :: ForeachOperation ProcessedPathItemGetter
|
||||
processedPathItemGetters =
|
||||
ForeachOperation
|
||||
{ processedPathItemGet = ProcessedPathItemGetter processedPathItemGet
|
||||
, processedPathItemPut = ProcessedPathItemGetter processedPathItemPut
|
||||
, processedPathItemPost = ProcessedPathItemGetter processedPathItemPost
|
||||
, processedPathItemDelete = ProcessedPathItemGetter processedPathItemDelete
|
||||
, processedPathItemOptions = ProcessedPathItemGetter processedPathItemOptions
|
||||
, processedPathItemHead = ProcessedPathItemGetter processedPathItemHead
|
||||
, processedPathItemPatch = ProcessedPathItemGetter processedPathItemPatch
|
||||
, processedPathItemTrace = ProcessedPathItemGetter processedPathItemTrace
|
||||
}
|
||||
|
||||
stepProcessedPathItem :: ForeachOperation (Step PathItem Operation)
|
||||
stepProcessedPathItem =
|
||||
ForeachOperation
|
||||
{ processedPathItemGet = GetStep
|
||||
, processedPathItemPut = PutStep
|
||||
, processedPathItemPost = PostStep
|
||||
, processedPathItemDelete = DeleteStep
|
||||
, processedPathItemOptions = OptionsStep
|
||||
, processedPathItemHead = HeadStep
|
||||
, processedPathItemPatch = PatchStep
|
||||
, processedPathItemTrace = TraceStep
|
||||
}
|
||||
instance Steppable ProcessedPathItems MatchedPathItem where
|
||||
data Step ProcessedPathItems MatchedPathItem = MatchedPathStep FilePath
|
||||
deriving (Eq, Ord, Show)
|
||||
|
||||
instance Steppable MatchedPathItem MatchedOperation where
|
||||
data Step MatchedPathItem MatchedOperation
|
||||
= GetStep
|
||||
| PutStep
|
||||
| PostStep
|
||||
| DeleteStep
|
||||
| OptionsStep
|
||||
| HeadStep
|
||||
| PatchStep
|
||||
| TraceStep
|
||||
deriving (Eq, Ord, Show)
|
||||
|
||||
instance Steppable MatchedPathItem (Referenced Param) where
|
||||
data Step MatchedPathItem (Referenced Param) = PathItemParam
|
||||
deriving (Eq, Ord, Show)
|
||||
|
||||
instance Steppable MatchedPathItem PathFragmentParam where
|
||||
data Step MatchedPathItem PathFragmentParam = PathFragmentStep Int
|
||||
deriving (Eq, Ord, Show)
|
||||
|
71
src/OpenAPI/Checker/Validate/Products.hs
Normal file
71
src/OpenAPI/Checker/Validate/Products.hs
Normal file
@ -0,0 +1,71 @@
|
||||
{- | Checks product-like entities. The key is some identificator for the product
|
||||
element. Each element may be required or optional.
|
||||
|
||||
One example of product is request parameters. There are optional and required
|
||||
parameters. The client and server have possibly different set of
|
||||
parameters. What we must check is if server requires some request parameter,
|
||||
then this parameter must be presented by client and their schemas must match.
|
||||
|
||||
So when we checking products we are checking from the server's (consumer)
|
||||
perspective, ensuring that all parameters are provided by the client (producer)
|
||||
and their schemas match.
|
||||
|
||||
This module abstracts this logic for arbitrary elements -}
|
||||
|
||||
module OpenAPI.Checker.Validate.Products
|
||||
( checkProducts
|
||||
, checkProducts'
|
||||
, ProductLike(..)
|
||||
) where
|
||||
|
||||
import Data.Foldable
|
||||
import Data.Functor
|
||||
import Data.Map.Strict (Map)
|
||||
import qualified Data.Map.Strict as M
|
||||
import Data.OpenApi.Internal
|
||||
import OpenAPI.Checker.Subtree
|
||||
import OpenAPI.Checker.Trace
|
||||
|
||||
-- | Some entity which is product-like
|
||||
data ProductLike root a = ProductLike
|
||||
{ traced :: Traced root a
|
||||
, required :: Bool
|
||||
}
|
||||
|
||||
checkProducts'
|
||||
:: forall k root t
|
||||
. (Subtree root, Ord k)
|
||||
=> (k -> CheckIssue root)
|
||||
-- ^ No required element found
|
||||
-> (k -> ProdCons t -> CompatFormula t ())
|
||||
-> ProdCons (Map k (ProductLike OpenApi t))
|
||||
-> CompatFormula root ()
|
||||
checkProducts' noElt check (ProdCons p c) = for_ (M.toList c) $ \(key, consElt) ->
|
||||
case M.lookup key p of
|
||||
Nothing -> case required consElt of
|
||||
True -> issueAt producer $ noElt key
|
||||
False -> pure ()
|
||||
Just prodElt -> do
|
||||
let
|
||||
elts :: ProdCons (ProductLike OpenApi t)
|
||||
elts = ProdCons prodElt consElt
|
||||
trace = getTrace . traced <$> elts
|
||||
elements = getTraced . traced <$> elts
|
||||
localTrace' trace $ check key elements
|
||||
|
||||
checkProducts
|
||||
:: forall k root t
|
||||
. (Subtree root, Ord k)
|
||||
=> (k -> CheckIssue root)
|
||||
-- ^ No required element found
|
||||
-> (k -> ProdCons t -> CompatFormula t ())
|
||||
-> ProdCons (Map k (ProductLike root t))
|
||||
-> CompatFormula root ()
|
||||
checkProducts noElt check prodCons = withTrace $ \myTrace ->
|
||||
let
|
||||
retracedPC = retracePC <$> myTrace <*> prodCons
|
||||
retracePC rootTrace els = els <&> \productLike ->
|
||||
ProductLike
|
||||
{ traced = retrace rootTrace $ traced productLike
|
||||
, required = required productLike }
|
||||
in checkProducts' noElt check retracedPC
|
@ -5,15 +5,17 @@ module OpenAPI.Checker.Validate.RequestBody
|
||||
)
|
||||
where
|
||||
|
||||
import Data.Foldable as F
|
||||
import Data.Functor
|
||||
import Data.HList
|
||||
import Data.HashMap.Strict.InsOrd as IOHM
|
||||
import Data.Map.Strict as M
|
||||
import Data.Maybe
|
||||
import Data.OpenApi
|
||||
import Network.HTTP.Media (MediaType)
|
||||
import OpenAPI.Checker.Subtree
|
||||
import OpenAPI.Checker.Trace
|
||||
import OpenAPI.Checker.Validate.MediaTypeObject ()
|
||||
import OpenAPI.Checker.Validate.Sums
|
||||
|
||||
instance Subtree RequestBody where
|
||||
type CheckEnv RequestBody =
|
||||
@ -22,19 +24,23 @@ instance Subtree RequestBody where
|
||||
= RequestBodyRequired
|
||||
| RequestMediaTypeNotFound MediaType
|
||||
deriving (Eq, Ord, Show)
|
||||
checkCompatibility env (ProdCons p c) =
|
||||
checkCompatibility env prodCons@(ProdCons p c) =
|
||||
if not (fromMaybe False $ _requestBodyRequired p)
|
||||
&& (fromMaybe False $ _requestBodyRequired c)
|
||||
then issueAt producer RequestBodyRequired
|
||||
else
|
||||
-- Each media type generated by the producer must be parsed by the
|
||||
-- consumer
|
||||
for_ (IOHM.toList $ _requestBodyContent p) $ \(mediaType, prodMedia) ->
|
||||
case IOHM.lookup mediaType $ _requestBodyContent c of
|
||||
Nothing -> issueAt consumer (RequestMediaTypeNotFound mediaType)
|
||||
Just consMedia -> localStep (MediaTypeStep mediaType) $
|
||||
checkCompatibility (HCons mediaType env) (ProdCons prodMedia consMedia)
|
||||
-- Media type object are sums-like entities.
|
||||
let
|
||||
check mediaType pc = checkCompatibility @MediaTypeObject (HCons mediaType env) pc
|
||||
sumElts = getSum <$> prodCons
|
||||
getSum rb = M.fromList
|
||||
$ (IOHM.toList $ _requestBodyContent rb) <&> \(mt, mto) ->
|
||||
( mt
|
||||
, Traced
|
||||
{ getTraced = mto
|
||||
, getTrace = step $ RequestMediaTypeObject mt })
|
||||
in checkSums RequestMediaTypeNotFound check sumElts
|
||||
|
||||
instance Steppable RequestBody MediaTypeObject where
|
||||
data Step RequestBody MediaTypeObject = MediaTypeStep MediaType
|
||||
data Step RequestBody MediaTypeObject = RequestMediaTypeObject MediaType
|
||||
deriving (Eq, Ord, Show)
|
||||
|
@ -1,4 +1,5 @@
|
||||
{-# OPTIONS_GHC -Wno-orphans #-}
|
||||
{-# OPTIONS_GHC -fno-warn-name-shadowing #-}
|
||||
|
||||
module OpenAPI.Checker.Validate.Responses
|
||||
(
|
||||
@ -8,6 +9,7 @@ where
|
||||
import Data.Foldable
|
||||
import Data.HList
|
||||
import Data.HashMap.Strict.InsOrd as IOHM
|
||||
import Data.Map.Strict as M
|
||||
import Data.Maybe
|
||||
import Data.OpenApi
|
||||
import Network.HTTP.Media (MediaType)
|
||||
@ -15,7 +17,9 @@ import OpenAPI.Checker.References
|
||||
import OpenAPI.Checker.Subtree
|
||||
import OpenAPI.Checker.Trace
|
||||
import OpenAPI.Checker.Validate.MediaTypeObject ()
|
||||
import OpenAPI.Checker.Validate.Products
|
||||
import OpenAPI.Checker.Validate.Schema ()
|
||||
import OpenAPI.Checker.Validate.Sums
|
||||
|
||||
instance Subtree Responses where
|
||||
type CheckEnv Responses =
|
||||
@ -25,19 +29,21 @@ instance Subtree Responses where
|
||||
]
|
||||
data CheckIssue Responses = ResponseCodeNotFound HttpStatusCode
|
||||
deriving (Eq, Ord, Show)
|
||||
-- Here we are checking responses, so, the consumer and producer swap their
|
||||
-- roles. The consumer now generates the response and producer consumes
|
||||
-- it. So, the logic is swapped.
|
||||
checkCompatibility env (ProdCons p c) = do
|
||||
let defs = getH @(ProdCons (Definitions Response)) env
|
||||
for_ (IOHM.toList $ _responsesResponses c) $ \(prodStatus, consRef) ->
|
||||
case IOHM.lookup prodStatus $ _responsesResponses p of
|
||||
Nothing -> issueAt producer $ ResponseCodeNotFound prodStatus
|
||||
Just prodRef -> do
|
||||
let tracedRefs = dereference <$> defs <*> ProdCons prodRef consRef
|
||||
localStep (ResponseCodeStep prodStatus)
|
||||
$ checkProdCons env tracedRefs
|
||||
-- FIXME: Do we need to check "default" fields somehow here?
|
||||
-- Roles are already swapped. Producer is a server and consumer is a
|
||||
-- client. Response codes are sum-like entity because we can answer with only
|
||||
-- one element
|
||||
checkCompatibility env prodCons = do
|
||||
let
|
||||
defs = getH @(ProdCons (Definitions Response)) env
|
||||
check _ resps = checkCompatibility @Response env resps
|
||||
elements = getEls <$> defs <*> prodCons
|
||||
getEls respDef resps = M.fromList $ do
|
||||
(code, respRef) <- IOHM.toList $ _responsesResponses resps
|
||||
let
|
||||
traced = dereferenceTraced respDef
|
||||
$ Traced (step $ ResponseCodeStep code) respRef
|
||||
pure (code, traced)
|
||||
checkSums ResponseCodeNotFound check elements
|
||||
|
||||
instance Subtree Response where
|
||||
type CheckEnv Response =
|
||||
@ -48,37 +54,40 @@ instance Subtree Response where
|
||||
= ResponseMediaTypeMissing MediaType
|
||||
| ResponseHeaderMissing HeaderName
|
||||
deriving (Eq, Ord, Show)
|
||||
-- Here we are checking responses, so, the consumer and producer swap their
|
||||
-- roles. The consumer now generates the response and producer consumes
|
||||
-- it. So, the logic is swapped.
|
||||
checkCompatibility env (ProdCons p c) = do
|
||||
checkCompatibility env prodCons = do
|
||||
-- Roles are already swapped. Producer is a server and consumer is a client
|
||||
checkMediaTypes
|
||||
checkHeaders
|
||||
pure ()
|
||||
where
|
||||
-- Each response type, generated by the consumer must be parseable by the
|
||||
-- producer
|
||||
checkMediaTypes = do
|
||||
for_ (IOHM.toList $ _responseContent c) $ \ (mediaType, consMediaObject) ->
|
||||
case IOHM.lookup mediaType $ _responseContent p of
|
||||
Nothing -> issueAt producer $ ResponseMediaTypeMissing mediaType
|
||||
Just prodMediaObject -> localStep (ResponseMediaObject mediaType)
|
||||
$ swapRoles
|
||||
$ checkCompatibility @MediaTypeObject (mediaType `HCons` swapProdCons schemaRefs `HCons` HNil)
|
||||
$ ProdCons consMediaObject prodMediaObject
|
||||
-- Each header expected by the producer must be provided by the
|
||||
-- consumer. Assume, that extra consumer headers are ignored.
|
||||
-- Media types are sum-like entity
|
||||
let
|
||||
check mediaType mtObj =
|
||||
let mtEnv = HCons mediaType $ env
|
||||
in checkCompatibility @MediaTypeObject mtEnv mtObj
|
||||
elements = getEls <$> prodCons
|
||||
getEls resp = M.fromList $ do
|
||||
(mediaType, mtObj) <- IOHM.toList $ _responseContent resp
|
||||
let traced = Traced (step $ ResponseMediaObject mediaType) mtObj
|
||||
pure (mediaType, traced)
|
||||
checkSums ResponseMediaTypeMissing check elements
|
||||
|
||||
checkHeaders = do
|
||||
for_ (IOHM.toList $ _responseHeaders p) $ \ (hname, prodRef) ->
|
||||
case IOHM.lookup hname $ _responseHeaders c of
|
||||
Nothing -> issueAt consumer $ ResponseHeaderMissing hname
|
||||
Just consRef -> do
|
||||
let headerRefs = dereference <$> headerDefs <*> ProdCons prodRef consRef
|
||||
localStep (ResponseHeader hname)
|
||||
$ swapRoles
|
||||
$ checkProdCons (singletonH $ swapProdCons schemaRefs) $ swapProdCons headerRefs
|
||||
-- Headers are product-like entities
|
||||
let
|
||||
check _hname hdrs = checkCompatibility @Header env hdrs
|
||||
elements = getEls <$> headerDefs <*> prodCons
|
||||
getEls headerDef resp = M.fromList $ do
|
||||
(hname, headerRef) <- IOHM.toList $ _responseHeaders resp
|
||||
let
|
||||
traced = dereferenceTraced headerDef
|
||||
$ Traced (step $ ResponseHeader hname) headerRef
|
||||
required = fromMaybe False $ _headerRequired $ getTraced traced
|
||||
elt = ProductLike { traced, required }
|
||||
pure (hname, elt)
|
||||
checkProducts ResponseHeaderMissing check elements
|
||||
headerDefs = getH @(ProdCons (Definitions Header)) env
|
||||
schemaRefs = getH @(ProdCons (Definitions Schema)) env
|
||||
|
||||
instance Subtree Header where
|
||||
type CheckEnv Header = '[ProdCons (Definitions Schema)]
|
||||
@ -100,6 +109,10 @@ instance Subtree Header where
|
||||
$ checkCompatibility env $ ProdCons prodRef consRef
|
||||
pure ()
|
||||
|
||||
instance Steppable Responses (Referenced Response) where
|
||||
data Step Responses (Referenced Response) = ResponseCodeStep HttpStatusCode
|
||||
deriving (Eq, Ord, Show)
|
||||
|
||||
instance Steppable Header (Referenced Schema) where
|
||||
data Step Header (Referenced Schema) = HeaderSchema
|
||||
deriving (Eq, Ord, Show)
|
||||
@ -111,7 +124,3 @@ instance Steppable Response (Referenced Header) where
|
||||
instance Steppable Response MediaTypeObject where
|
||||
data Step Response MediaTypeObject = ResponseMediaObject MediaType
|
||||
deriving (Eq, Ord, Show)
|
||||
|
||||
instance Steppable Responses (Referenced Response) where
|
||||
data Step Responses (Referenced Response) = ResponseCodeStep HttpStatusCode
|
||||
deriving (Eq, Ord, Show)
|
||||
|
28
src/OpenAPI/Checker/Validate/Sums.hs
Normal file
28
src/OpenAPI/Checker/Validate/Sums.hs
Normal file
@ -0,0 +1,28 @@
|
||||
module OpenAPI.Checker.Validate.Sums
|
||||
( checkSums
|
||||
) where
|
||||
|
||||
import Data.Foldable
|
||||
import Data.Map.Strict (Map)
|
||||
import qualified Data.Map.Strict as M
|
||||
import OpenAPI.Checker.Subtree
|
||||
import OpenAPI.Checker.Trace
|
||||
|
||||
|
||||
checkSums
|
||||
:: forall k root t
|
||||
. (Ord k, Subtree root)
|
||||
=> (k -> CheckIssue root)
|
||||
-> (k -> ProdCons t -> CompatFormula t ())
|
||||
-> ProdCons (Map k (Traced root t))
|
||||
-> CompatFormula root ()
|
||||
checkSums noElt check (ProdCons p c) = for_ (M.toList p) $ \(key, prodElt) ->
|
||||
case M.lookup key c of
|
||||
Nothing -> issueAt consumer $ noElt key
|
||||
Just consElt ->
|
||||
let
|
||||
sumElts :: ProdCons (Traced root t)
|
||||
sumElts = ProdCons prodElt consElt
|
||||
trace = getTrace <$> sumElts
|
||||
elements = getTraced <$> sumElts
|
||||
in localTrace trace $ check key elements
|
@ -1,10 +1,10 @@
|
||||
Left:
|
||||
OpenApiPathsStep:
|
||||
PathStep "/test":
|
||||
MatchedPathStep "/test":
|
||||
PostStep:
|
||||
OperationRequestBodyStep:
|
||||
InlineStep:
|
||||
MediaTypeStep application/json:
|
||||
RequestMediaTypeObject application/json:
|
||||
MediaTypeSchema:
|
||||
ReferencedStep (Reference {getReference = "Test"}):
|
||||
MaximumFields: MatchingMaximumWeak (Inclusive 2.0) (Inclusive 3.0)
|
||||
|
@ -0,0 +1,19 @@
|
||||
openapi: "3.0.0"
|
||||
info:
|
||||
version: 1.0.0
|
||||
title: Swagger Petstore
|
||||
license:
|
||||
name: MIT
|
||||
servers:
|
||||
- url: http://petstore.swagger.io/v1
|
||||
paths:
|
||||
/test:
|
||||
post:
|
||||
parameters:
|
||||
- name: test1
|
||||
in: query
|
||||
allowEmptyValue: true
|
||||
responses:
|
||||
"200":
|
||||
description: "Test"
|
||||
components: {}
|
@ -0,0 +1,19 @@
|
||||
openapi: "3.0.0"
|
||||
info:
|
||||
version: 1.0.0
|
||||
title: Swagger Petstore
|
||||
license:
|
||||
name: MIT
|
||||
servers:
|
||||
- url: http://petstore.swagger.io/v1
|
||||
paths:
|
||||
/test:
|
||||
post:
|
||||
parameters:
|
||||
- name: test1
|
||||
in: query
|
||||
allowEmptyValue: false
|
||||
responses:
|
||||
"200":
|
||||
description: "Test"
|
||||
components: {}
|
@ -0,0 +1,6 @@
|
||||
Left:
|
||||
OpenApiPathsStep:
|
||||
MatchedPathStep "/test":
|
||||
PostStep:
|
||||
OperationParamsStep:
|
||||
InlineStep: ParamEmptinessIncompatible
|
@ -0,0 +1,19 @@
|
||||
openapi: "3.0.0"
|
||||
info:
|
||||
version: 1.0.0
|
||||
title: Swagger Petstore
|
||||
license:
|
||||
name: MIT
|
||||
servers:
|
||||
- url: http://petstore.swagger.io/v1
|
||||
paths:
|
||||
/test:
|
||||
post:
|
||||
parameters:
|
||||
- name: test1
|
||||
in: query
|
||||
allowEmptyValue: false
|
||||
responses:
|
||||
"200":
|
||||
description: "Test"
|
||||
components: {}
|
@ -0,0 +1,19 @@
|
||||
openapi: "3.0.0"
|
||||
info:
|
||||
version: 1.0.0
|
||||
title: Swagger Petstore
|
||||
license:
|
||||
name: MIT
|
||||
servers:
|
||||
- url: http://petstore.swagger.io/v1
|
||||
paths:
|
||||
/test:
|
||||
post:
|
||||
parameters:
|
||||
- name: test1
|
||||
in: query
|
||||
allowEmptyValue: true
|
||||
responses:
|
||||
"200":
|
||||
description: "Test"
|
||||
components: {}
|
@ -0,0 +1 @@
|
||||
Right: []
|
@ -0,0 +1,20 @@
|
||||
openapi: "3.0.0"
|
||||
info:
|
||||
version: 1.0.0
|
||||
title: Swagger Petstore
|
||||
license:
|
||||
name: MIT
|
||||
servers:
|
||||
- url: http://petstore.swagger.io/v1
|
||||
paths:
|
||||
/test:
|
||||
post:
|
||||
parameters:
|
||||
- name: test
|
||||
in: query
|
||||
schema:
|
||||
type: "string"
|
||||
responses:
|
||||
"200":
|
||||
description: "Test"
|
||||
components: {}
|
@ -0,0 +1,20 @@
|
||||
openapi: "3.0.0"
|
||||
info:
|
||||
version: 1.0.0
|
||||
title: Swagger Petstore
|
||||
license:
|
||||
name: MIT
|
||||
servers:
|
||||
- url: http://petstore.swagger.io/v1
|
||||
paths:
|
||||
/test:
|
||||
post:
|
||||
parameters:
|
||||
- name: test
|
||||
in: query
|
||||
schema:
|
||||
type: "number"
|
||||
responses:
|
||||
"200":
|
||||
description: "Test"
|
||||
components: {}
|
@ -0,0 +1,8 @@
|
||||
Left:
|
||||
OpenApiPathsStep:
|
||||
MatchedPathStep "/test":
|
||||
PostStep:
|
||||
OperationParamsStep:
|
||||
InlineStep:
|
||||
ParamSchema:
|
||||
InlineStep: NoContradiction
|
@ -0,0 +1,18 @@
|
||||
openapi: "3.0.0"
|
||||
info:
|
||||
version: 1.0.0
|
||||
title: Swagger Petstore
|
||||
license:
|
||||
name: MIT
|
||||
servers:
|
||||
- url: http://petstore.swagger.io/v1
|
||||
paths:
|
||||
/test:
|
||||
post:
|
||||
parameters:
|
||||
- name: test1
|
||||
in: query
|
||||
responses:
|
||||
"200":
|
||||
description: "Test"
|
||||
components: {}
|
@ -0,0 +1,20 @@
|
||||
openapi: "3.0.0"
|
||||
info:
|
||||
version: 1.0.0
|
||||
title: Swagger Petstore
|
||||
license:
|
||||
name: MIT
|
||||
servers:
|
||||
- url: http://petstore.swagger.io/v1
|
||||
paths:
|
||||
/test:
|
||||
post:
|
||||
parameters:
|
||||
- name: test1
|
||||
in: query
|
||||
- name: test2
|
||||
in: query
|
||||
responses:
|
||||
"200":
|
||||
description: "Test"
|
||||
components: {}
|
@ -0,0 +1 @@
|
||||
Right: []
|
@ -0,0 +1,20 @@
|
||||
openapi: "3.0.0"
|
||||
info:
|
||||
version: 1.0.0
|
||||
title: Swagger Petstore
|
||||
license:
|
||||
name: MIT
|
||||
servers:
|
||||
- url: http://petstore.swagger.io/v1
|
||||
paths:
|
||||
/test:
|
||||
post:
|
||||
parameters:
|
||||
- name: test1
|
||||
in: query
|
||||
- name: test2
|
||||
in: query
|
||||
responses:
|
||||
"200":
|
||||
description: "Test"
|
||||
components: {}
|
@ -0,0 +1,18 @@
|
||||
openapi: "3.0.0"
|
||||
info:
|
||||
version: 1.0.0
|
||||
title: Swagger Petstore
|
||||
license:
|
||||
name: MIT
|
||||
servers:
|
||||
- url: http://petstore.swagger.io/v1
|
||||
paths:
|
||||
/test:
|
||||
post:
|
||||
parameters:
|
||||
- name: test1
|
||||
in: query
|
||||
responses:
|
||||
"200":
|
||||
description: "Test"
|
||||
components: {}
|
@ -0,0 +1 @@
|
||||
Right: []
|
@ -0,0 +1,19 @@
|
||||
openapi: "3.0.0"
|
||||
info:
|
||||
version: 1.0.0
|
||||
title: Swagger Petstore
|
||||
license:
|
||||
name: MIT
|
||||
servers:
|
||||
- url: http://petstore.swagger.io/v1
|
||||
paths:
|
||||
/test:
|
||||
post:
|
||||
parameters:
|
||||
- name: test1
|
||||
in: query
|
||||
required: true
|
||||
responses:
|
||||
"200":
|
||||
description: "Test"
|
||||
components: {}
|
@ -0,0 +1,19 @@
|
||||
openapi: "3.0.0"
|
||||
info:
|
||||
version: 1.0.0
|
||||
title: Swagger Petstore
|
||||
license:
|
||||
name: MIT
|
||||
servers:
|
||||
- url: http://petstore.swagger.io/v1
|
||||
paths:
|
||||
/test:
|
||||
post:
|
||||
parameters:
|
||||
- name: test1
|
||||
in: query
|
||||
required: false
|
||||
responses:
|
||||
"200":
|
||||
description: "Test"
|
||||
components: {}
|
@ -0,0 +1 @@
|
||||
Right: []
|
@ -0,0 +1,19 @@
|
||||
openapi: "3.0.0"
|
||||
info:
|
||||
version: 1.0.0
|
||||
title: Swagger Petstore
|
||||
license:
|
||||
name: MIT
|
||||
servers:
|
||||
- url: http://petstore.swagger.io/v1
|
||||
paths:
|
||||
/test:
|
||||
post:
|
||||
parameters:
|
||||
- name: test1
|
||||
in: query
|
||||
required: false
|
||||
responses:
|
||||
"200":
|
||||
description: "Test"
|
||||
components: {}
|
@ -0,0 +1,19 @@
|
||||
openapi: "3.0.0"
|
||||
info:
|
||||
version: 1.0.0
|
||||
title: Swagger Petstore
|
||||
license:
|
||||
name: MIT
|
||||
servers:
|
||||
- url: http://petstore.swagger.io/v1
|
||||
paths:
|
||||
/test:
|
||||
post:
|
||||
parameters:
|
||||
- name: test1
|
||||
in: query
|
||||
required: true
|
||||
responses:
|
||||
"200":
|
||||
description: "Test"
|
||||
components: {}
|
@ -0,0 +1,6 @@
|
||||
Left:
|
||||
OpenApiPathsStep:
|
||||
MatchedPathStep "/test":
|
||||
PostStep:
|
||||
OperationParamsStep:
|
||||
InlineStep: ParamRequired
|
@ -0,0 +1,18 @@
|
||||
openapi: "3.0.0"
|
||||
info:
|
||||
version: 1.0.0
|
||||
title: Swagger Petstore
|
||||
license:
|
||||
name: MIT
|
||||
servers:
|
||||
- url: http://petstore.swagger.io/v1
|
||||
paths:
|
||||
/test:
|
||||
post:
|
||||
parameters:
|
||||
- name: test1
|
||||
in: query
|
||||
responses:
|
||||
"200":
|
||||
description: "Test"
|
||||
components: {}
|
@ -0,0 +1,21 @@
|
||||
openapi: "3.0.0"
|
||||
info:
|
||||
version: 1.0.0
|
||||
title: Swagger Petstore
|
||||
license:
|
||||
name: MIT
|
||||
servers:
|
||||
- url: http://petstore.swagger.io/v1
|
||||
paths:
|
||||
/test:
|
||||
post:
|
||||
parameters:
|
||||
- name: test1
|
||||
in: query
|
||||
- name: test2
|
||||
in: query
|
||||
required: true
|
||||
responses:
|
||||
"200":
|
||||
description: "Test"
|
||||
components: {}
|
@ -0,0 +1,4 @@
|
||||
Left:
|
||||
OpenApiPathsStep:
|
||||
MatchedPathStep "/test":
|
||||
PostStep: ParamNotMatched ParamQuery "test2"
|
@ -0,0 +1,21 @@
|
||||
openapi: "3.0.0"
|
||||
info:
|
||||
version: 1.0.0
|
||||
title: Swagger Petstore
|
||||
license:
|
||||
name: MIT
|
||||
servers:
|
||||
- url: http://petstore.swagger.io/v1
|
||||
paths:
|
||||
/test:
|
||||
post:
|
||||
parameters:
|
||||
- name: test1
|
||||
in: query
|
||||
- name: test2
|
||||
in: query
|
||||
required: true
|
||||
responses:
|
||||
"200":
|
||||
description: "Test"
|
||||
components: {}
|
@ -0,0 +1,18 @@
|
||||
openapi: "3.0.0"
|
||||
info:
|
||||
version: 1.0.0
|
||||
title: Swagger Petstore
|
||||
license:
|
||||
name: MIT
|
||||
servers:
|
||||
- url: http://petstore.swagger.io/v1
|
||||
paths:
|
||||
/test:
|
||||
post:
|
||||
parameters:
|
||||
- name: test1
|
||||
in: query
|
||||
responses:
|
||||
"200":
|
||||
description: "Test"
|
||||
components: {}
|
@ -0,0 +1 @@
|
||||
Right: []
|
@ -0,0 +1,20 @@
|
||||
openapi: "3.0.0"
|
||||
info:
|
||||
version: 1.0.0
|
||||
title: Swagger Petstore
|
||||
license:
|
||||
name: MIT
|
||||
servers:
|
||||
- url: http://petstore.swagger.io/v1
|
||||
paths:
|
||||
/test:
|
||||
post:
|
||||
requestBody:
|
||||
content:
|
||||
"application/json" :
|
||||
schema:
|
||||
type: "string"
|
||||
responses:
|
||||
"200":
|
||||
description: "Test"
|
||||
components: {}
|
@ -0,0 +1,23 @@
|
||||
openapi: "3.0.0"
|
||||
info:
|
||||
version: 1.0.0
|
||||
title: Swagger Petstore
|
||||
license:
|
||||
name: MIT
|
||||
servers:
|
||||
- url: http://petstore.swagger.io/v1
|
||||
paths:
|
||||
/test:
|
||||
post:
|
||||
requestBody:
|
||||
content:
|
||||
"application/json" :
|
||||
schema:
|
||||
type: "string"
|
||||
"application/x-www-form-urlencoded":
|
||||
schema:
|
||||
type: "string"
|
||||
responses:
|
||||
"200":
|
||||
description: "Test"
|
||||
components: {}
|
@ -0,0 +1 @@
|
||||
Right: []
|
@ -0,0 +1,20 @@
|
||||
openapi: "3.0.0"
|
||||
info:
|
||||
version: 1.0.0
|
||||
title: Swagger Petstore
|
||||
license:
|
||||
name: MIT
|
||||
servers:
|
||||
- url: http://petstore.swagger.io/v1
|
||||
paths:
|
||||
/test:
|
||||
post:
|
||||
requestBody:
|
||||
content:
|
||||
"application/json" :
|
||||
schema:
|
||||
type: "string"
|
||||
responses:
|
||||
"200":
|
||||
description: "Test"
|
||||
components: {}
|
@ -0,0 +1,20 @@
|
||||
openapi: "3.0.0"
|
||||
info:
|
||||
version: 1.0.0
|
||||
title: Swagger Petstore
|
||||
license:
|
||||
name: MIT
|
||||
servers:
|
||||
- url: http://petstore.swagger.io/v1
|
||||
paths:
|
||||
/test:
|
||||
post:
|
||||
requestBody:
|
||||
content:
|
||||
"application/json" :
|
||||
schema:
|
||||
type: "number"
|
||||
responses:
|
||||
"200":
|
||||
description: "Test"
|
||||
components: {}
|
@ -0,0 +1,9 @@
|
||||
Left:
|
||||
OpenApiPathsStep:
|
||||
MatchedPathStep "/test":
|
||||
PostStep:
|
||||
OperationRequestBodyStep:
|
||||
InlineStep:
|
||||
RequestMediaTypeObject application/json:
|
||||
MediaTypeSchema:
|
||||
InlineStep: NoContradiction
|
@ -0,0 +1,23 @@
|
||||
openapi: "3.0.0"
|
||||
info:
|
||||
version: 1.0.0
|
||||
title: Swagger Petstore
|
||||
license:
|
||||
name: MIT
|
||||
servers:
|
||||
- url: http://petstore.swagger.io/v1
|
||||
paths:
|
||||
/test:
|
||||
post:
|
||||
requestBody:
|
||||
content:
|
||||
"application/json" :
|
||||
schema:
|
||||
type: "string"
|
||||
"application/x-www-form-urlencoded":
|
||||
schema:
|
||||
type: "string"
|
||||
responses:
|
||||
"200":
|
||||
description: "Test"
|
||||
components: {}
|
@ -0,0 +1,20 @@
|
||||
openapi: "3.0.0"
|
||||
info:
|
||||
version: 1.0.0
|
||||
title: Swagger Petstore
|
||||
license:
|
||||
name: MIT
|
||||
servers:
|
||||
- url: http://petstore.swagger.io/v1
|
||||
paths:
|
||||
/test:
|
||||
post:
|
||||
requestBody:
|
||||
content:
|
||||
"application/json" :
|
||||
schema:
|
||||
type: "string"
|
||||
responses:
|
||||
"200":
|
||||
description: "Test"
|
||||
components: {}
|
@ -0,0 +1,6 @@
|
||||
Left:
|
||||
OpenApiPathsStep:
|
||||
MatchedPathStep "/test":
|
||||
PostStep:
|
||||
OperationRequestBodyStep:
|
||||
InlineStep: RequestMediaTypeNotFound application/x-www-form-urlencoded
|
@ -0,0 +1,21 @@
|
||||
openapi: "3.0.0"
|
||||
info:
|
||||
version: 1.0.0
|
||||
title: Swagger Petstore
|
||||
license:
|
||||
name: MIT
|
||||
servers:
|
||||
- url: http://petstore.swagger.io/v1
|
||||
paths:
|
||||
/test:
|
||||
post:
|
||||
requestBody:
|
||||
content:
|
||||
"application/json" :
|
||||
schema:
|
||||
type: "string"
|
||||
required: true
|
||||
responses:
|
||||
"200":
|
||||
description: "Test"
|
||||
components: {}
|
@ -0,0 +1,21 @@
|
||||
openapi: "3.0.0"
|
||||
info:
|
||||
version: 1.0.0
|
||||
title: Swagger Petstore
|
||||
license:
|
||||
name: MIT
|
||||
servers:
|
||||
- url: http://petstore.swagger.io/v1
|
||||
paths:
|
||||
/test:
|
||||
post:
|
||||
requestBody:
|
||||
content:
|
||||
"application/json" :
|
||||
schema:
|
||||
type: "string"
|
||||
required: false
|
||||
responses:
|
||||
"200":
|
||||
description: "Test"
|
||||
components: {}
|
@ -0,0 +1 @@
|
||||
Right: []
|
@ -0,0 +1,21 @@
|
||||
openapi: "3.0.0"
|
||||
info:
|
||||
version: 1.0.0
|
||||
title: Swagger Petstore
|
||||
license:
|
||||
name: MIT
|
||||
servers:
|
||||
- url: http://petstore.swagger.io/v1
|
||||
paths:
|
||||
/test:
|
||||
post:
|
||||
requestBody:
|
||||
content:
|
||||
"application/json" :
|
||||
schema:
|
||||
type: "string"
|
||||
required: false
|
||||
responses:
|
||||
"200":
|
||||
description: "Test"
|
||||
components: {}
|
@ -0,0 +1,21 @@
|
||||
openapi: "3.0.0"
|
||||
info:
|
||||
version: 1.0.0
|
||||
title: Swagger Petstore
|
||||
license:
|
||||
name: MIT
|
||||
servers:
|
||||
- url: http://petstore.swagger.io/v1
|
||||
paths:
|
||||
/test:
|
||||
post:
|
||||
requestBody:
|
||||
content:
|
||||
"application/json" :
|
||||
schema:
|
||||
type: "string"
|
||||
required: true
|
||||
responses:
|
||||
"200":
|
||||
description: "Test"
|
||||
components: {}
|
@ -0,0 +1,6 @@
|
||||
Left:
|
||||
OpenApiPathsStep:
|
||||
MatchedPathStep "/test":
|
||||
PostStep:
|
||||
OperationRequestBodyStep:
|
||||
InlineStep: RequestBodyRequired
|
21
test/golden/common/pathItem/operation/responses/add/a.yaml
Normal file
21
test/golden/common/pathItem/operation/responses/add/a.yaml
Normal file
@ -0,0 +1,21 @@
|
||||
openapi: "3.0.0"
|
||||
info:
|
||||
version: 1.0.0
|
||||
title: Swagger Petstore
|
||||
license:
|
||||
name: MIT
|
||||
servers:
|
||||
- url: http://petstore.swagger.io/v1
|
||||
paths:
|
||||
/test:
|
||||
post:
|
||||
requestBody:
|
||||
content:
|
||||
"application/json" :
|
||||
schema:
|
||||
type: "string"
|
||||
required: false
|
||||
responses:
|
||||
"200":
|
||||
description: "Test"
|
||||
components: {}
|
23
test/golden/common/pathItem/operation/responses/add/b.yaml
Normal file
23
test/golden/common/pathItem/operation/responses/add/b.yaml
Normal file
@ -0,0 +1,23 @@
|
||||
openapi: "3.0.0"
|
||||
info:
|
||||
version: 1.0.0
|
||||
title: Swagger Petstore
|
||||
license:
|
||||
name: MIT
|
||||
servers:
|
||||
- url: http://petstore.swagger.io/v1
|
||||
paths:
|
||||
/test:
|
||||
post:
|
||||
requestBody:
|
||||
content:
|
||||
"application/json" :
|
||||
schema:
|
||||
type: "string"
|
||||
required: false
|
||||
responses:
|
||||
"200":
|
||||
description: "Test"
|
||||
"500":
|
||||
description: "Added"
|
||||
components: {}
|
@ -0,0 +1,5 @@
|
||||
Left:
|
||||
OpenApiPathsStep:
|
||||
MatchedPathStep "/test":
|
||||
PostStep:
|
||||
OperationResponsesStep: ResponseCodeNotFound 500
|
@ -0,0 +1,25 @@
|
||||
openapi: "3.0.0"
|
||||
info:
|
||||
version: 1.0.0
|
||||
title: Swagger Petstore
|
||||
license:
|
||||
name: MIT
|
||||
servers:
|
||||
- url: http://petstore.swagger.io/v1
|
||||
paths:
|
||||
/test:
|
||||
post:
|
||||
requestBody:
|
||||
content:
|
||||
"application/json" :
|
||||
schema:
|
||||
type: "string"
|
||||
required: false
|
||||
responses:
|
||||
"200":
|
||||
description: "Test"
|
||||
headers:
|
||||
"Test":
|
||||
description: "Test header"
|
||||
required: true
|
||||
components: {}
|
@ -0,0 +1,28 @@
|
||||
openapi: "3.0.0"
|
||||
info:
|
||||
version: 1.0.0
|
||||
title: Swagger Petstore
|
||||
license:
|
||||
name: MIT
|
||||
servers:
|
||||
- url: http://petstore.swagger.io/v1
|
||||
paths:
|
||||
/test:
|
||||
post:
|
||||
requestBody:
|
||||
content:
|
||||
"application/json" :
|
||||
schema:
|
||||
type: "string"
|
||||
required: false
|
||||
responses:
|
||||
"200":
|
||||
description: "Test"
|
||||
headers:
|
||||
"Test":
|
||||
description: "Test header"
|
||||
required: true
|
||||
"Test2":
|
||||
description: "Test2 header"
|
||||
required: true
|
||||
components: {}
|
@ -0,0 +1 @@
|
||||
Right: []
|
@ -0,0 +1,28 @@
|
||||
openapi: "3.0.0"
|
||||
info:
|
||||
version: 1.0.0
|
||||
title: Swagger Petstore
|
||||
license:
|
||||
name: MIT
|
||||
servers:
|
||||
- url: http://petstore.swagger.io/v1
|
||||
paths:
|
||||
/test:
|
||||
post:
|
||||
requestBody:
|
||||
content:
|
||||
"application/json" :
|
||||
schema:
|
||||
type: "string"
|
||||
required: false
|
||||
responses:
|
||||
"200":
|
||||
description: "Test"
|
||||
headers:
|
||||
"Test":
|
||||
description: "Test header"
|
||||
required: true
|
||||
"Test2":
|
||||
description: "Test2 header"
|
||||
required: true
|
||||
components: {}
|
@ -0,0 +1,25 @@
|
||||
openapi: "3.0.0"
|
||||
info:
|
||||
version: 1.0.0
|
||||
title: Swagger Petstore
|
||||
license:
|
||||
name: MIT
|
||||
servers:
|
||||
- url: http://petstore.swagger.io/v1
|
||||
paths:
|
||||
/test:
|
||||
post:
|
||||
requestBody:
|
||||
content:
|
||||
"application/json" :
|
||||
schema:
|
||||
type: "string"
|
||||
required: false
|
||||
responses:
|
||||
"200":
|
||||
description: "Test"
|
||||
headers:
|
||||
"Test":
|
||||
description: "Test header"
|
||||
required: true
|
||||
components: {}
|
@ -0,0 +1,7 @@
|
||||
Left:
|
||||
OpenApiPathsStep:
|
||||
MatchedPathStep "/test":
|
||||
PostStep:
|
||||
OperationResponsesStep:
|
||||
ResponseCodeStep 200:
|
||||
InlineStep: ResponseHeaderMissing "Test2"
|
@ -0,0 +1,24 @@
|
||||
openapi: "3.0.0"
|
||||
info:
|
||||
version: 1.0.0
|
||||
title: Swagger Petstore
|
||||
license:
|
||||
name: MIT
|
||||
servers:
|
||||
- url: http://petstore.swagger.io/v1
|
||||
paths:
|
||||
/test:
|
||||
post:
|
||||
requestBody:
|
||||
content:
|
||||
"application/json" :
|
||||
schema:
|
||||
type: "string"
|
||||
required: false
|
||||
responses:
|
||||
"200":
|
||||
description: "Test"
|
||||
headers:
|
||||
"Test":
|
||||
description: "Test header"
|
||||
components: {}
|
@ -0,0 +1,26 @@
|
||||
openapi: "3.0.0"
|
||||
info:
|
||||
version: 1.0.0
|
||||
title: Swagger Petstore
|
||||
license:
|
||||
name: MIT
|
||||
servers:
|
||||
- url: http://petstore.swagger.io/v1
|
||||
paths:
|
||||
/test:
|
||||
post:
|
||||
requestBody:
|
||||
content:
|
||||
"application/json" :
|
||||
schema:
|
||||
type: "string"
|
||||
required: false
|
||||
responses:
|
||||
"200":
|
||||
description: "Test"
|
||||
headers:
|
||||
"Test":
|
||||
description: "Test header"
|
||||
"Test2":
|
||||
description: "Test2 header"
|
||||
components: {}
|
@ -0,0 +1 @@
|
||||
Right: []
|
@ -0,0 +1,26 @@
|
||||
openapi: "3.0.0"
|
||||
info:
|
||||
version: 1.0.0
|
||||
title: Swagger Petstore
|
||||
license:
|
||||
name: MIT
|
||||
servers:
|
||||
- url: http://petstore.swagger.io/v1
|
||||
paths:
|
||||
/test:
|
||||
post:
|
||||
requestBody:
|
||||
content:
|
||||
"application/json" :
|
||||
schema:
|
||||
type: "string"
|
||||
required: false
|
||||
responses:
|
||||
"200":
|
||||
description: "Test"
|
||||
headers:
|
||||
"Test":
|
||||
description: "Test header"
|
||||
"Test2":
|
||||
description: "Test2 header"
|
||||
components: {}
|
@ -0,0 +1,24 @@
|
||||
openapi: "3.0.0"
|
||||
info:
|
||||
version: 1.0.0
|
||||
title: Swagger Petstore
|
||||
license:
|
||||
name: MIT
|
||||
servers:
|
||||
- url: http://petstore.swagger.io/v1
|
||||
paths:
|
||||
/test:
|
||||
post:
|
||||
requestBody:
|
||||
content:
|
||||
"application/json" :
|
||||
schema:
|
||||
type: "string"
|
||||
required: false
|
||||
responses:
|
||||
"200":
|
||||
description: "Test"
|
||||
headers:
|
||||
"Test":
|
||||
description: "Test header"
|
||||
components: {}
|
@ -0,0 +1 @@
|
||||
Right: []
|
@ -0,0 +1,25 @@
|
||||
openapi: "3.0.0"
|
||||
info:
|
||||
version: 1.0.0
|
||||
title: Swagger Petstore
|
||||
license:
|
||||
name: MIT
|
||||
servers:
|
||||
- url: http://petstore.swagger.io/v1
|
||||
paths:
|
||||
/test:
|
||||
post:
|
||||
requestBody:
|
||||
content:
|
||||
"application/json" :
|
||||
schema:
|
||||
type: "string"
|
||||
required: false
|
||||
responses:
|
||||
"200":
|
||||
description: "Test"
|
||||
content:
|
||||
"application/json":
|
||||
schema:
|
||||
type: "string"
|
||||
components: {}
|
@ -0,0 +1,28 @@
|
||||
openapi: "3.0.0"
|
||||
info:
|
||||
version: 1.0.0
|
||||
title: Swagger Petstore
|
||||
license:
|
||||
name: MIT
|
||||
servers:
|
||||
- url: http://petstore.swagger.io/v1
|
||||
paths:
|
||||
/test:
|
||||
post:
|
||||
requestBody:
|
||||
content:
|
||||
"application/json" :
|
||||
schema:
|
||||
type: "string"
|
||||
required: false
|
||||
responses:
|
||||
"200":
|
||||
description: "Test"
|
||||
content:
|
||||
"application/json":
|
||||
schema:
|
||||
type: "string"
|
||||
"application/x-www-form-urlencoded":
|
||||
schema:
|
||||
type: "string"
|
||||
components: {}
|
@ -0,0 +1,7 @@
|
||||
Left:
|
||||
OpenApiPathsStep:
|
||||
MatchedPathStep "/test":
|
||||
PostStep:
|
||||
OperationResponsesStep:
|
||||
ResponseCodeStep 200:
|
||||
InlineStep: ResponseMediaTypeMissing application/x-www-form-urlencoded
|
@ -0,0 +1,25 @@
|
||||
openapi: "3.0.0"
|
||||
info:
|
||||
version: 1.0.0
|
||||
title: Swagger Petstore
|
||||
license:
|
||||
name: MIT
|
||||
servers:
|
||||
- url: http://petstore.swagger.io/v1
|
||||
paths:
|
||||
/test:
|
||||
post:
|
||||
requestBody:
|
||||
content:
|
||||
"application/json" :
|
||||
schema:
|
||||
type: "string"
|
||||
required: false
|
||||
responses:
|
||||
"200":
|
||||
description: "Test"
|
||||
content:
|
||||
"application/json":
|
||||
schema:
|
||||
type: "string"
|
||||
components: {}
|
@ -0,0 +1,25 @@
|
||||
openapi: "3.0.0"
|
||||
info:
|
||||
version: 1.0.0
|
||||
title: Swagger Petstore
|
||||
license:
|
||||
name: MIT
|
||||
servers:
|
||||
- url: http://petstore.swagger.io/v1
|
||||
paths:
|
||||
/test:
|
||||
post:
|
||||
requestBody:
|
||||
content:
|
||||
"application/json" :
|
||||
schema:
|
||||
type: "string"
|
||||
required: false
|
||||
responses:
|
||||
"200":
|
||||
description: "Test"
|
||||
content:
|
||||
"application/json":
|
||||
schema:
|
||||
type: "number"
|
||||
components: {}
|
@ -0,0 +1,10 @@
|
||||
Left:
|
||||
OpenApiPathsStep:
|
||||
MatchedPathStep "/test":
|
||||
PostStep:
|
||||
OperationResponsesStep:
|
||||
ResponseCodeStep 200:
|
||||
InlineStep:
|
||||
ResponseMediaObject application/json:
|
||||
MediaTypeSchema:
|
||||
InlineStep: NoContradiction
|
@ -0,0 +1,28 @@
|
||||
openapi: "3.0.0"
|
||||
info:
|
||||
version: 1.0.0
|
||||
title: Swagger Petstore
|
||||
license:
|
||||
name: MIT
|
||||
servers:
|
||||
- url: http://petstore.swagger.io/v1
|
||||
paths:
|
||||
/test:
|
||||
post:
|
||||
requestBody:
|
||||
content:
|
||||
"application/json" :
|
||||
schema:
|
||||
type: "string"
|
||||
required: false
|
||||
responses:
|
||||
"200":
|
||||
description: "Test"
|
||||
content:
|
||||
"application/json":
|
||||
schema:
|
||||
type: "string"
|
||||
"application/x-www-form-urlencoded":
|
||||
schema:
|
||||
type: "string"
|
||||
components: {}
|
@ -0,0 +1,25 @@
|
||||
openapi: "3.0.0"
|
||||
info:
|
||||
version: 1.0.0
|
||||
title: Swagger Petstore
|
||||
license:
|
||||
name: MIT
|
||||
servers:
|
||||
- url: http://petstore.swagger.io/v1
|
||||
paths:
|
||||
/test:
|
||||
post:
|
||||
requestBody:
|
||||
content:
|
||||
"application/json" :
|
||||
schema:
|
||||
type: "string"
|
||||
required: false
|
||||
responses:
|
||||
"200":
|
||||
description: "Test"
|
||||
content:
|
||||
"application/json":
|
||||
schema:
|
||||
type: "string"
|
||||
components: {}
|
@ -0,0 +1 @@
|
||||
Right: []
|
23
test/golden/common/pathItem/operation/responses/del/a.yaml
Normal file
23
test/golden/common/pathItem/operation/responses/del/a.yaml
Normal file
@ -0,0 +1,23 @@
|
||||
openapi: "3.0.0"
|
||||
info:
|
||||
version: 1.0.0
|
||||
title: Swagger Petstore
|
||||
license:
|
||||
name: MIT
|
||||
servers:
|
||||
- url: http://petstore.swagger.io/v1
|
||||
paths:
|
||||
/test:
|
||||
post:
|
||||
requestBody:
|
||||
content:
|
||||
"application/json" :
|
||||
schema:
|
||||
type: "string"
|
||||
required: false
|
||||
responses:
|
||||
"200":
|
||||
description: "Test"
|
||||
"500":
|
||||
description: "Added"
|
||||
components: {}
|
21
test/golden/common/pathItem/operation/responses/del/b.yaml
Normal file
21
test/golden/common/pathItem/operation/responses/del/b.yaml
Normal file
@ -0,0 +1,21 @@
|
||||
openapi: "3.0.0"
|
||||
info:
|
||||
version: 1.0.0
|
||||
title: Swagger Petstore
|
||||
license:
|
||||
name: MIT
|
||||
servers:
|
||||
- url: http://petstore.swagger.io/v1
|
||||
paths:
|
||||
/test:
|
||||
post:
|
||||
requestBody:
|
||||
content:
|
||||
"application/json" :
|
||||
schema:
|
||||
type: "string"
|
||||
required: false
|
||||
responses:
|
||||
"200":
|
||||
description: "Test"
|
||||
components: {}
|
@ -0,0 +1 @@
|
||||
Right: []
|
@ -1,6 +1,6 @@
|
||||
Left:
|
||||
OpenApiPathsStep:
|
||||
PathStep "/test":
|
||||
MatchedPathStep "/test":
|
||||
PostStep:
|
||||
OperationResponsesStep:
|
||||
ResponseCodeStep 200:
|
||||
@ -11,7 +11,7 @@ Left:
|
||||
PropertiesFields: PropertyNowRequired "property2"
|
||||
OperationRequestBodyStep:
|
||||
InlineStep:
|
||||
MediaTypeStep application/json:
|
||||
RequestMediaTypeObject application/json:
|
||||
MediaTypeSchema:
|
||||
ReferencedStep (Reference {getReference = "Test"}):
|
||||
PropertiesFields: UnexpectedProperty "property2"
|
||||
|
@ -1,10 +1,10 @@
|
||||
Left:
|
||||
OpenApiPathsStep:
|
||||
PathStep "/test":
|
||||
MatchedPathStep "/test":
|
||||
PostStep:
|
||||
OperationRequestBodyStep:
|
||||
InlineStep:
|
||||
MediaTypeStep application/json:
|
||||
RequestMediaTypeObject application/json:
|
||||
MediaTypeSchema:
|
||||
ReferencedStep (Reference {getReference = "Test"}):
|
||||
PropertiesFields: PropertyNowRequired "property2"
|
||||
|
Loading…
Reference in New Issue
Block a user