From 2440f23829a1180e293a08180003f1ffe6104fbe Mon Sep 17 00:00:00 2001 From: iko Date: Mon, 21 Jun 2021 20:52:48 +0300 Subject: [PATCH] Added non-breaking changes to reports (#82) * bumped resolver * Added non-breaking changes to report * Removed dead file * Added backward issue descriptions * Issue description reversing * Changed wording slightly --- app/Main.hs | 39 +++-- openapi-diff.cabal | 4 +- src/OpenAPI/Checker/Behavior.hs | 20 ++- src/OpenAPI/Checker/Report.hs | 145 ++++++++++++------ src/OpenAPI/Checker/Run.hs | 30 ++++ src/OpenAPI/Checker/Subtree/Deriving.hs | 6 - src/OpenAPI/Checker/Validate/Header.hs | 8 +- src/OpenAPI/Checker/Validate/Link.hs | 2 +- .../Checker/Validate/MediaTypeObject.hs | 20 ++- src/OpenAPI/Checker/Validate/OAuth2Flows.hs | 48 +++--- src/OpenAPI/Checker/Validate/Operation.hs | 11 +- src/OpenAPI/Checker/Validate/Param.hs | 16 +- src/OpenAPI/Checker/Validate/RequestBody.hs | 8 +- src/OpenAPI/Checker/Validate/Responses.hs | 8 +- src/OpenAPI/Checker/Validate/Schema.hs | 86 +++++++---- src/OpenAPI/Checker/Validate/Server.hs | 13 +- stack.yaml | 2 +- stack.yaml.lock | 8 +- test/Spec.hs | 2 +- test/Spec/Golden/TraceTree.hs | 19 +-- test/golden/common/enum-anyof/report.md | 6 +- test/golden/common/enum-anyof/trace-tree.yaml | 3 +- test/golden/common/id/report.md | 6 +- test/golden/common/id/trace-tree.yaml | 3 +- test/golden/common/json/recursive/report.md | 6 +- .../common/json/recursive/trace-tree.yaml | 3 +- test/golden/common/maximum-lowered/report.md | 18 ++- .../common/maximum-lowered/trace-tree.yaml | 10 +- .../allowEmptyValue/reset/report.md | 8 +- .../allowEmptyValue/reset/trace-tree.yaml | 3 +- .../parameters/allowEmptyValue/set/report.md | 14 +- .../allowEmptyValue/set/trace-tree.yaml | 6 +- .../operation/parameters/change/report.md | 18 ++- .../parameters/change/trace-tree.yaml | 8 +- .../parameters/required/false/add/report.md | 6 +- .../required/false/add/trace-tree.yaml | 3 +- .../parameters/required/false/del/report.md | 6 +- .../required/false/del/trace-tree.yaml | 3 +- .../parameters/required/reset/report.md | 14 +- .../parameters/required/reset/trace-tree.yaml | 6 +- .../parameters/required/set/report.md | 6 +- .../parameters/required/set/trace-tree.yaml | 3 +- .../parameters/required/true/add/report.md | 6 +- .../required/true/add/trace-tree.yaml | 3 +- .../parameters/required/true/del/report.md | 12 +- .../required/true/del/trace-tree.yaml | 5 +- .../requestBody/mediaTypeObject/add/report.md | 14 +- .../mediaTypeObject/add/trace-tree.yaml | 6 +- .../mediaTypeObject/change/report.md | 18 ++- .../mediaTypeObject/change/trace-tree.yaml | 9 +- .../requestBody/mediaTypeObject/del/report.md | 6 +- .../mediaTypeObject/del/trace-tree.yaml | 3 +- .../requestBody/required/reset/report.md | 14 +- .../required/reset/trace-tree.yaml | 6 +- .../requestBody/required/set/report.md | 6 +- .../requestBody/required/set/trace-tree.yaml | 3 +- .../operation/responses/add/report.md | 6 +- .../operation/responses/add/trace-tree.yaml | 3 +- .../change/headers/mandatory/add/report.md | 14 +- .../headers/mandatory/add/trace-tree.yaml | 6 +- .../change/headers/mandatory/del/report.md | 8 +- .../headers/mandatory/del/trace-tree.yaml | 3 +- .../change/headers/optional/add/report.md | 6 +- .../headers/optional/add/trace-tree.yaml | 3 +- .../change/headers/optional/del/report.md | 6 +- .../headers/optional/del/trace-tree.yaml | 3 +- .../change/mediaTypeObject/add/report.md | 6 +- .../mediaTypeObject/add/trace-tree.yaml | 3 +- .../change/mediaTypeObject/change/report.md | 18 ++- .../mediaTypeObject/change/trace-tree.yaml | 9 +- .../change/mediaTypeObject/del/report.md | 14 +- .../mediaTypeObject/del/trace-tree.yaml | 6 +- .../operation/responses/del/report.md | 12 +- .../operation/responses/del/trace-tree.yaml | 5 +- .../common/property-removed-additional/a.yaml | 32 ++++ .../common/property-removed-additional/b.yaml | 29 ++++ .../property-removed-additional/report.md | 25 +++ .../trace-tree.yaml | 14 ++ test/golden/common/property-removed/report.md | 28 +++- .../common/property-removed/trace-tree.yaml | 13 +- .../golden/common/property-required/report.md | 18 ++- .../common/property-required/trace-tree.yaml | 9 +- test/golden/common/recursive/report.md | 20 ++- test/golden/common/recursive/trace-tree.yaml | 15 +- test/golden/common/security-scheme/report.md | 16 +- .../common/security-scheme/trace-tree.yaml | 7 +- test/golden/common/servers/report.md | 14 +- test/golden/common/servers/trace-tree.yaml | 7 +- .../common/unguarded-recursive/report.md | 8 +- .../unguarded-recursive/trace-tree.yaml | 8 +- 90 files changed, 872 insertions(+), 287 deletions(-) create mode 100644 src/OpenAPI/Checker/Run.hs delete mode 100644 src/OpenAPI/Checker/Subtree/Deriving.hs create mode 100644 test/golden/common/property-removed-additional/a.yaml create mode 100644 test/golden/common/property-removed-additional/b.yaml create mode 100644 test/golden/common/property-removed-additional/report.md create mode 100644 test/golden/common/property-removed-additional/trace-tree.yaml diff --git a/app/Main.hs b/app/Main.hs index 78e76cd..725b760 100644 --- a/app/Main.hs +++ b/app/Main.hs @@ -5,19 +5,14 @@ import Control.Monad.Except import Data.Aeson import qualified Data.ByteString.Lazy as BSL import Data.Default -import Data.HList import qualified Data.Text.IO as T import qualified Data.Yaml as Yaml import FormatHeuristic -import OpenAPI.Checker.Behavior import OpenAPI.Checker.Options -import OpenAPI.Checker.Paths -import OpenAPI.Checker.PathsPrefixTree -import OpenAPI.Checker.Report -import OpenAPI.Checker.Subtree +import OpenAPI.Checker.Run import System.Exit import System.IO -import Text.Pandoc +import Text.Pandoc hiding (report) main :: IO () main = do @@ -33,23 +28,27 @@ main = do fail "Exiting" Right s -> pure s Right s -> pure s - a <- traced (step ClientSchema) <$> parseSchema (clientFile opts) - b <- traced (step ServerSchema) <$> parseSchema (serverFile opts) - let result = runCompatFormula $ checkCompatibility HNil Root (ProdCons a b) - runPandocIO :: PandocIO a -> ExceptT Errors IO a + a <- parseSchema (clientFile opts) + b <- parseSchema (serverFile opts) + let runPandocIO :: PandocIO a -> ExceptT Errors IO a runPandocIO x = lift (runIO x) >>= either (throwError . DocumentError) pure options = def {writerExtensions = githubMarkdownExtensions} - output :: Either (PathsPrefixTree Behave AnIssue 'APILevel) () -> ExceptT Errors IO () - output = case outputMode opts of - StdoutMode -> lift . T.putStrLn <=< runPandocIO . writeMarkdown options . generateReport + write :: Pandoc -> ExceptT Errors IO () + write = case outputMode opts of + StdoutMode -> lift . T.putStrLn <=< runPandocIO . writeMarkdown options FileMode f -> case formatFromFilePath f of Nothing -> \_ -> throwError UnknownOutputFormat - Just (TextWriter writer) -> lift . T.writeFile f <=< runPandocIO . writer options . generateReport - Just (ByteStringWriter writer) -> lift . BSL.writeFile f <=< runPandocIO . writer options . generateReport - either handler pure <=< runExceptT $ output result - case result of - Right () -> exitSuccess - Left _ -> exitWith $ ExitFailure 1 + Just (TextWriter writer) -> lift . T.writeFile f <=< runPandocIO . writer options + Just (ByteStringWriter writer) -> lift . BSL.writeFile f <=< runPandocIO . writer options + -- output :: Either (PathsPrefixTree Behave AnIssue 'APILevel) () -> ExceptT Errors IO () + -- output inp = do + -- undefined + (report, status) = runReport (a, b) + either handler pure <=< runExceptT $ write report + case status of + NoBreakingChanges -> exitSuccess + BreakingChanges -> exitWith $ ExitFailure 1 + OnlyUnsupportedChanges -> exitWith $ ExitFailure 2 data Errors = DocumentError PandocError diff --git a/openapi-diff.cabal b/openapi-diff.cabal index 34302f9..fdcbbe5 100644 --- a/openapi-diff.cabal +++ b/openapi-diff.cabal @@ -35,7 +35,7 @@ common common-options -Wno-missing-local-signatures -Wno-unsafe default-language: Haskell2010 - build-depends: base >= 4.12.0.0 && < 4.15 + build-depends: base >= 4.12.0.0 && < 4.16 , bytestring , text @@ -104,6 +104,7 @@ library , transformers , mtl , aeson + , generic-data hs-source-dirs: src exposed-modules: Data.HList , OpenAPI.Checker.Behavior @@ -134,6 +135,7 @@ library , OpenAPI.Checker.Report , Data.OpenUnion.Extra , OpenAPI.Checker.Report.Jet + , OpenAPI.Checker.Run executable openapi-diff import: common-options diff --git a/src/OpenAPI/Checker/Behavior.hs b/src/OpenAPI/Checker/Behavior.hs index 5d2f783..5e3ecd6 100644 --- a/src/OpenAPI/Checker/Behavior.hs +++ b/src/OpenAPI/Checker/Behavior.hs @@ -2,6 +2,8 @@ module OpenAPI.Checker.Behavior ( BehaviorLevel (..) , Behavable (..) , Issuable (..) + , Orientation (..) + , toggleOrientation , Behavior , AnIssue (..) ) @@ -43,9 +45,25 @@ type instance AdditionalQuiverConstraints Behave a b = Behavable a b class (Typeable l, Ord (Issue l), Show (Issue l)) => Issuable (l :: BehaviorLevel) where data Issue l :: Type - describeIssue :: Issue l -> Blocks + + -- | The same issues can be rendered in multiple places and might + -- require different ways of represnting them to the user. + -- + -- In practice each issue requires a maximum of two different representations: + -- based on the context the issue might need to be rendered as "opposite" ('Backward') + -- – for example when rendering non-breaking changes everything should be + -- reversed (a consequence of the way we generate non-breaking changes). + describeIssue :: Orientation -> Issue l -> Blocks + issueIsUnsupported :: Issue l -> Bool +data Orientation = Forward | Backward + deriving stock (Eq, Ord) + +toggleOrientation :: Orientation -> Orientation +toggleOrientation Forward = Backward +toggleOrientation Backward = Forward + -- | A set of interactions having common unifying features type Behavior = Paths Behave 'APILevel diff --git a/src/OpenAPI/Checker/Report.hs b/src/OpenAPI/Checker/Report.hs index dc1f80d..d77a5e6 100644 --- a/src/OpenAPI/Checker/Report.hs +++ b/src/OpenAPI/Checker/Report.hs @@ -1,15 +1,20 @@ module OpenAPI.Checker.Report ( generateReport + , ReportInput (..) + , ReportStatus (..) + , Pandoc ) where import Control.Monad.Free hiding (unfoldM) import Control.Monad.Reader import Control.Monad.Writer +import Data.Aeson (ToJSON) import Data.Either import Data.Foldable import Data.Function import Data.Functor +import Data.Functor.Const import Data.List.NonEmpty import qualified Data.List.NonEmpty as NE import qualified Data.Map as M @@ -22,6 +27,7 @@ import Data.Text (Text) import qualified Data.Text as T import Data.TypeRepMap hiding (empty) import Data.Typeable +import Generic.Data import OpenAPI.Checker.Behavior import OpenAPI.Checker.Paths import OpenAPI.Checker.PathsPrefixTree hiding (empty) @@ -31,27 +37,79 @@ import OpenAPI.Checker.Validate.OpenApi import OpenAPI.Checker.Validate.Schema import Text.Pandoc.Builder -generateReport :: Either (P.PathsPrefixTree Behave AnIssue 'APILevel) () -> Pandoc -generateReport (Right ()) = doc $ header 1 "No breaking changes found ✨" -generateReport (Left errs) = doc $ - runReportMonad jets $ do - let (unsupported, breaking) = P.partition (\(AnIssue i) -> issueIsUnsupported i) errs - breakingChangesPresent = not $ P.null breaking - unsupportedChangesPresent = not $ P.null unsupported - smartHeader "Summary" - tell $ - simpleTable - (para - <$> [ refOpt breakingChangesPresent breakingChangesId "⚠️ Breaking changes" - , refOpt unsupportedChangesPresent unsupportedChangesId "🤷 Unsupported feature changes" - ]) - [para . show' <$> [P.size breaking, P.size unsupported]] - when breakingChangesPresent $ do - smartHeader $ anchor breakingChangesId <> "⚠️ Breaking changes" - incrementHeaders $ showErrs breaking - when unsupportedChangesPresent $ do - smartHeader $ anchor unsupportedChangesId <> "🤷 Unsupported feature changes" - incrementHeaders $ showErrs unsupported +type Changes = P.PathsPrefixTree Behave AnIssue 'APILevel + +type ProcessedChanges a = P.PathsPrefixTree Behave (FunctorTuple (Const Orientation) AnIssue) a + +data FunctorTuple f g a = FunctorTuple (f a) (g a) + deriving stock (Eq, Ord) + +data ReportInput = ReportInput + { breakingChanges :: Changes + , nonBreakingChanges :: Changes + } + deriving stock (Generic) + deriving (Semigroup, Monoid) via (Generically ReportInput) + deriving anyclass (ToJSON) + +data ReportStatus + = BreakingChanges + | NoBreakingChanges + | -- | All changes that could be breaking are unsupported – we don't know if + -- there actually are any breaking changes. + OnlyUnsupportedChanges + +preprocessChanges :: Orientation -> Changes -> ProcessedChanges 'APILevel +preprocessChanges initialO = P.fromList . fmap process . P.toList + where + process :: AnItem Behave AnIssue 'APILevel -> AnItem Behave (FunctorTuple (Const Orientation) AnIssue) 'APILevel + process (AnItem paths issue) = AnItem paths $ FunctorTuple (Const $ toggle initialO) issue + where + (Endo toggle) = togglePaths paths + + togglePaths :: Paths Behave a c -> Endo Orientation + togglePaths Root = mempty + togglePaths (rest `Snoc` (_ :: Behave b c)) = case eqT @c @'ResponseLevel of + Just Refl -> Endo toggleOrientation <> togglePaths rest + Nothing -> togglePaths rest + +generateReport :: ReportInput -> (Pandoc, ReportStatus) +generateReport inp = + let partitionUnsupported = P.partition (\(AnIssue i) -> issueIsUnsupported i) + (bUnsupported, preprocessChanges Forward -> breaking) = + partitionUnsupported $ breakingChanges inp + (nbUnsupported, preprocessChanges Backward -> nonBreaking) = + partitionUnsupported $ nonBreakingChanges inp + unsupported = preprocessChanges Forward $ bUnsupported <> nbUnsupported + breakingChangesPresent = not $ P.null breaking + nonBreakingChangesPresent = not $ P.null nonBreaking + unsupportedChangesPresent = not $ P.null unsupported + report = doc $ + runReportMonad jets $ do + smartHeader "Summary" + tell $ + simpleTable + (para + <$> [ refOpt breakingChangesPresent breakingChangesId "⚠️ Breaking changes" + , refOpt nonBreakingChangesPresent nonBreakingChangesId "🙆 Non-breaking changes" + , refOpt unsupportedChangesPresent unsupportedChangesId "🤷 Unsupported feature changes" + ]) + [para . show' <$> [P.size breaking, P.size nonBreaking, P.size unsupported]] + when breakingChangesPresent $ do + smartHeader $ anchor breakingChangesId <> "⚠️ Breaking changes" + incrementHeaders $ showErrs breaking + when nonBreakingChangesPresent $ do + smartHeader $ anchor nonBreakingChangesId <> "🙆 Non-breaking changes" + incrementHeaders $ showErrs nonBreaking + when unsupportedChangesPresent $ do + smartHeader $ anchor unsupportedChangesId <> "🤷 Unsupported feature changes" + incrementHeaders $ showErrs unsupported + status = + if + | breakingChangesPresent -> BreakingChanges + | unsupportedChangesPresent -> OnlyUnsupportedChanges + | otherwise -> NoBreakingChanges + in (report, status) where anchor :: Text -> Inlines anchor a = spanWith (a, [], []) mempty @@ -60,11 +118,10 @@ generateReport (Left errs) = doc $ refOpt False _ i = i refOpt True a i = link ("#" <> a) "" i - breakingChangesId :: Text + breakingChangesId, nonBreakingChangesId, unsupportedChangesId :: Text breakingChangesId = "breaking-changes" - - unsupportedChangesId :: Text unsupportedChangesId = "unsupported-changes" + nonBreakingChangesId = "non-breaking-changes" data ReportState = ReportState { sourceJets :: [ReportJet' Behave Inlines] @@ -88,22 +145,24 @@ smartHeader i = do h <- asks headerLevel tell $ header h i -showErrs :: forall a. Typeable a => P.PathsPrefixTree Behave AnIssue a -> ReportMonad () +showErrs :: forall a. Typeable a => ProcessedChanges a -> ReportMonad () showErrs x@(P.PathsPrefixNode currentIssues _) = do let -- Extract this pattern if more cases like this arise - (removedPaths :: [Issue 'APILevel], otherIssues :: Set (AnIssue a)) = case eqT @a @'APILevel of - Just Refl -> - let (p, o) = - S.partition - (\(AnIssue u) -> case u of - NoPathsMatched {} -> True - AllPathsFailed {} -> True) - currentIssues - p' = S.toList p <&> (\(AnIssue i) -> i) - in (p', o) - Nothing -> (mempty, currentIssues) + ( removedPaths :: [Issue 'APILevel] + , otherIssues :: Set (FunctorTuple (Const Orientation) AnIssue a) + ) = case eqT @a @'APILevel of + Just Refl -> + let (p, o) = + S.partition + (\(FunctorTuple _ (AnIssue u)) -> case u of + NoPathsMatched {} -> True + AllPathsFailed {} -> True) + currentIssues + p' = S.toList p <&> (\(FunctorTuple _ (AnIssue i)) -> i) + in (p', o) + Nothing -> (mempty, currentIssues) jts <- asks sourceJets - for_ otherIssues $ \(AnIssue i) -> tell . describeIssue $ i + for_ otherIssues $ \(FunctorTuple (Const ori) (AnIssue i)) -> tell . describeIssue ori $ i unless ([] == removedPaths) $ do smartHeader "Removed paths" tell $ @@ -135,9 +194,9 @@ jets = <$> [ constructReportJet jsonPathJet , constructReportJet $ \p@(AtPath _) op@(InOperation _) -> strong (describeBehaviour op) <> " " <> describeBehaviour p :: Inlines - , constructReportJet $ \InRequest InPayload PayloadSchema -> "JSON Request" :: Inlines + , constructReportJet $ \InRequest InPayload PayloadSchema -> "📱➡️ JSON Request" :: Inlines , constructReportJet $ \(WithStatusCode c) ResponsePayload PayloadSchema -> - "JSON Response – " <> str (T.pack . show $ c) :: Inlines + "📱⬅️ JSON Response – " <> str (T.pack . show $ c) :: Inlines ] where unwrapReportJetResult :: ReportJetResult Behave x -> ReportJet' Behave x @@ -177,8 +236,8 @@ jets = observeJetShowErrs :: ReportJet' Behave Inlines - -> P.PathsPrefixTree Behave AnIssue a - -> ReportMonad (P.PathsPrefixTree Behave AnIssue a) + -> ProcessedChanges a + -> ReportMonad (ProcessedChanges a) observeJetShowErrs jet p = case observeJetShowErrs' jet p of Just m -> m Nothing -> pure p @@ -186,8 +245,8 @@ observeJetShowErrs jet p = case observeJetShowErrs' jet p of observeJetShowErrs' :: forall a. ReportJet' Behave Inlines - -> P.PathsPrefixTree Behave AnIssue a - -> Maybe (ReportMonad (P.PathsPrefixTree Behave AnIssue a)) + -> ProcessedChanges a + -> Maybe (ReportMonad (ProcessedChanges a)) observeJetShowErrs' (ReportJet jet) (P.PathsPrefixNode currentIssues subIssues) = let results = subIssues >>= \(WrapTypeable (AStep m)) -> diff --git a/src/OpenAPI/Checker/Run.hs b/src/OpenAPI/Checker/Run.hs new file mode 100644 index 0000000..3c2e67a --- /dev/null +++ b/src/OpenAPI/Checker/Run.hs @@ -0,0 +1,30 @@ +module OpenAPI.Checker.Run + ( runChecker + , runReport + , module OpenAPI.Checker.Report + ) +where + +import Data.HList +import Data.OpenApi (OpenApi) +import OpenAPI.Checker.Paths +import OpenAPI.Checker.Report +import OpenAPI.Checker.Subtree +import OpenAPI.Checker.Validate.OpenApi () + +runChecker :: (OpenApi, OpenApi) -> ReportInput +runChecker (client, server) = + ReportInput + { breakingChanges = run client server + , nonBreakingChanges = run server client + } + where + toPC p c = + ProdCons + { producer = traced (step ClientSchema) p + , consumer = traced (step ServerSchema) c + } + run p c = either id mempty . runCompatFormula . checkCompatibility HNil Root $ toPC p c + +runReport :: (OpenApi, OpenApi) -> (Pandoc, ReportStatus) +runReport = generateReport . runChecker diff --git a/src/OpenAPI/Checker/Subtree/Deriving.hs b/src/OpenAPI/Checker/Subtree/Deriving.hs deleted file mode 100644 index 5bf7916..0000000 --- a/src/OpenAPI/Checker/Subtree/Deriving.hs +++ /dev/null @@ -1,6 +0,0 @@ -module OpenAPI.Checker.Subtree.Deriving (EqSubtree (..)) where - -import Control.Monad -import OpenAPI.Checker.Subtree - -newtype EqSubtree t = EqSubtree t diff --git a/src/OpenAPI/Checker/Validate/Header.hs b/src/OpenAPI/Checker/Validate/Header.hs index c5dfde2..e6ab657 100644 --- a/src/OpenAPI/Checker/Validate/Header.hs +++ b/src/OpenAPI/Checker/Validate/Header.hs @@ -51,9 +51,11 @@ instance Issuable 'HeaderLevel where | HeaderSchemaRequired deriving stock (Eq, Ord, Show) issueIsUnsupported _ = False - describeIssue RequiredHeaderMissing = para "Header has become required." - describeIssue NonEmptyHeaderRequired = para "The header does not allow empty values anymore." - describeIssue HeaderSchemaRequired = para "Expected header schema, but it is not present." + describeIssue Forward RequiredHeaderMissing = para "Header has become required." + describeIssue Backward RequiredHeaderMissing = para "Header is no longer required." + describeIssue Forward NonEmptyHeaderRequired = para "The header does not allow empty values anymore." + describeIssue Backward NonEmptyHeaderRequired = para "The header now allows empty values." + describeIssue _ HeaderSchemaRequired = para "Expected header schema, but it is not present." instance Behavable 'HeaderLevel 'SchemaLevel where data Behave 'HeaderLevel 'SchemaLevel diff --git a/src/OpenAPI/Checker/Validate/Link.hs b/src/OpenAPI/Checker/Validate/Link.hs index 04ce014..dc0b77e 100644 --- a/src/OpenAPI/Checker/Validate/Link.hs +++ b/src/OpenAPI/Checker/Validate/Link.hs @@ -19,4 +19,4 @@ instance Issuable 'LinkLevel where deriving stock (Eq, Ord, Show) issueIsUnsupported = \case LinksUnsupported -> True - describeIssue LinksUnsupported = para "OpenApi Diff does not currently support Link Objects." + describeIssue _ LinksUnsupported = para "OpenApi Diff does not currently support Link Objects." diff --git a/src/OpenAPI/Checker/Validate/MediaTypeObject.hs b/src/OpenAPI/Checker/Validate/MediaTypeObject.hs index 5ea0004..71eaa8b 100644 --- a/src/OpenAPI/Checker/Validate/MediaTypeObject.hs +++ b/src/OpenAPI/Checker/Validate/MediaTypeObject.hs @@ -42,9 +42,10 @@ instance Issuable 'PayloadLevel where EncodingNotSupported -> True _ -> False - describeIssue MediaTypeSchemaRequired = para "Media type expected, but was not specified." - describeIssue (MediaEncodingMissing enc) = para $ "Media encoding " <> str enc <> " added." - describeIssue EncodingNotSupported = para "OpenApi Diff does not currently support media encodings other than JSON." + describeIssue _ MediaTypeSchemaRequired = para "Media type expected, but was not specified." + describeIssue Forward (MediaEncodingMissing enc) = para $ "Media encoding " <> str enc <> " has been removed." + describeIssue Backward (MediaEncodingMissing enc) = para $ "Media encoding " <> str enc <> " added." + describeIssue _ EncodingNotSupported = para "OpenApi Diff does not currently support media encodings other than JSON." instance Behavable 'PayloadLevel 'SchemaLevel where data Behave 'PayloadLevel 'SchemaLevel @@ -153,11 +154,16 @@ instance Issuable 'OperationLevel where deriving stock (Eq, Ord, Show) issueIsUnsupported = \case _ -> False - describeIssue (ResponseCodeNotFound c) = + describeIssue Forward (ResponseCodeNotFound c) = para $ "Reponse code " <> (str . T.pack . show $ c) <> " has been added." - describeIssue (ParamNotMatched param) = + describeIssue Backward (ResponseCodeNotFound c) = + para $ "Reponse code " <> (str . T.pack . show $ c) <> " has been removed." + describeIssue Forward (ParamNotMatched param) = para $ "Parameter " <> code param <> " has become required." - describeIssue (PathFragmentNotMatched i) = + describeIssue Backward (ParamNotMatched param) = + para $ "Parameter " <> code param <> " is no longer required." + describeIssue _ (PathFragmentNotMatched i) = -- TODO: Indices are meaningless in this context. Replace with a better error. para $ "Path fragment " <> (str . T.pack . show $ i) <> " not matched." - describeIssue NoRequestBody = para "Request body has been added." + describeIssue Forward NoRequestBody = para "Request body has been added." + describeIssue Backward NoRequestBody = para "Request body has been removed." diff --git a/src/OpenAPI/Checker/Validate/OAuth2Flows.hs b/src/OpenAPI/Checker/Validate/OAuth2Flows.hs index d103540..14e7e3f 100644 --- a/src/OpenAPI/Checker/Validate/OAuth2Flows.hs +++ b/src/OpenAPI/Checker/Validate/OAuth2Flows.hs @@ -104,8 +104,9 @@ instance Issuable 'SecurityRequirementLevel where | UndefinedSecurityScheme Text deriving stock (Eq, Ord, Show) issueIsUnsupported _ = False - describeIssue SecurityRequirementNotMet = para "Security scheme has been removed." - describeIssue (UndefinedSecurityScheme k) = para $ "Security scheme " <> code k <> " is not defined." + describeIssue Forward SecurityRequirementNotMet = para "Security scheme has been removed." + describeIssue Backward SecurityRequirementNotMet = para "Security scheme was added." + describeIssue _ (UndefinedSecurityScheme k) = para $ "Security scheme " <> code k <> " is not defined." instance Issuable 'SecuritySchemeLevel where data Issue 'SecuritySchemeLevel @@ -129,26 +130,33 @@ instance Issuable 'SecuritySchemeLevel where | ScopeNotDefined Text deriving stock (Eq, Ord, Show) issueIsUnsupported _ = False - describeIssue RefreshUrlsDontMatch = para "Refresh URL changed." - describeIssue (HttpSchemeTypesDontMatch _ _) = para "HTTP scheme type changed." - describeIssue (ApiKeyParamsDontMatch _ _) = para "API Key parameters changed." - describeIssue (OpenIdConnectUrlsDontMatch _ _) = para "OpenaId Connect URL changed." - describeIssue (CustomHttpSchemesDontMatch e a) = + describeIssue _ RefreshUrlsDontMatch = para "Refresh URL changed." + describeIssue _ (HttpSchemeTypesDontMatch _ _) = para "HTTP scheme type changed." + describeIssue _ (ApiKeyParamsDontMatch _ _) = para "API Key parameters changed." + describeIssue _ (OpenIdConnectUrlsDontMatch _ _) = para "OpenaId Connect URL changed." + describeIssue _ (CustomHttpSchemesDontMatch e a) = para $ "Changed HTTP scheme from " <> code e <> " to " <> code a <> "." - describeIssue ConsumerDoesNotSupportImplicitFlow = para "Implicit flow support has been removed." - describeIssue ConsumerDoesNotSupportPasswordFlow = para "Password flow support has been removed." - describeIssue ConsumerDoesNotSupportClientCridentialsFlow = para "Client Cridentials flow support has been removed." - describeIssue ConsumerDoesNotSupportAuthorizationCodeFlow = para "Authorization Code flow support has been removed." - describeIssue SecuritySchemeNotMatched = para "Security scheme has been removed." - describeIssue OAuth2ImplicitFlowNotEqual = para "Implicit Flow changed." - describeIssue OAuth2PasswordFlowNotEqual = para "Password Flow changed." - describeIssue OAuth2ClientCredentialsFlowNotEqual = para "Client Cridentials Flow changed." - describeIssue OAuth2AuthorizationCodeFlowNotEqual = para "Authorization Code Flow changed." - describeIssue (ScopesMissing ss) = + describeIssue Forward ConsumerDoesNotSupportImplicitFlow = para "Implicit flow support has been removed." + describeIssue Backward ConsumerDoesNotSupportImplicitFlow = para "Implicit flow support has been added." + describeIssue Forward ConsumerDoesNotSupportPasswordFlow = para "Password flow support has been removed." + describeIssue Backward ConsumerDoesNotSupportPasswordFlow = para "Password flow support has been added." + describeIssue Forward ConsumerDoesNotSupportClientCridentialsFlow = para "Client Cridentials flow support has been removed." + describeIssue Backward ConsumerDoesNotSupportClientCridentialsFlow = para "Client Cridentials flow support has been added." + describeIssue Forward ConsumerDoesNotSupportAuthorizationCodeFlow = para "Authorization Code flow support has been removed." + describeIssue Backward ConsumerDoesNotSupportAuthorizationCodeFlow = para "Authorization Code flow support has been added." + describeIssue Forward SecuritySchemeNotMatched = para "Security scheme has been removed." + describeIssue Backward SecuritySchemeNotMatched = para "Security scheme has been added." + describeIssue _ OAuth2ImplicitFlowNotEqual = para "Implicit Flow changed." + describeIssue _ OAuth2PasswordFlowNotEqual = para "Password Flow changed." + describeIssue _ OAuth2ClientCredentialsFlowNotEqual = para "Client Cridentials Flow changed." + describeIssue _ OAuth2AuthorizationCodeFlowNotEqual = para "Authorization Code Flow changed." + describeIssue Forward (ScopesMissing ss) = para "New scopes required:" <> bulletList (S.toList ss <&> codeBlock) - describeIssue DifferentSecuritySchemes = para "Completely different security scheme types." - describeIssue CanNotHaveScopes = para "The specified security scheme can not have scopes." - describeIssue (ScopeNotDefined k) = para $ "Scope with key " <> code k <> " is not defined." + describeIssue Backward (ScopesMissing ss) = + para "Scopes no longer required:" <> bulletList (S.toList ss <&> codeBlock) + describeIssue _ DifferentSecuritySchemes = para "Completely different security scheme types." + describeIssue _ CanNotHaveScopes = para "The specified security scheme can not have scopes." + describeIssue _ (ScopeNotDefined k) = para $ "Scope with key " <> code k <> " is not defined." instance Behavable 'SecurityRequirementLevel 'SecuritySchemeLevel where data Behave 'SecurityRequirementLevel 'SecuritySchemeLevel diff --git a/src/OpenAPI/Checker/Validate/Operation.hs b/src/OpenAPI/Checker/Validate/Operation.hs index 54c5abe..6faccc9 100644 --- a/src/OpenAPI/Checker/Validate/Operation.hs +++ b/src/OpenAPI/Checker/Validate/Operation.hs @@ -359,8 +359,10 @@ instance Issuable 'APILevel where -- When several paths match given but all checks failed deriving stock (Eq, Ord, Show) issueIsUnsupported _ = False - describeIssue (NoPathsMatched p) = para $ "The path " <> (code . T.pack) p <> " has been removed." - describeIssue (AllPathsFailed p) = para $ "The path " <> (code . T.pack) p <> " has been removed." + describeIssue Forward (NoPathsMatched p) = para $ "The path " <> (code . T.pack) p <> " has been removed." + describeIssue Backward (NoPathsMatched p) = para $ "The path " <> (code . T.pack) p <> " has been added." + describeIssue Forward (AllPathsFailed p) = para $ "The path " <> (code . T.pack) p <> " has been removed." + describeIssue Backward (AllPathsFailed p) = para $ "The path " <> (code . T.pack) p <> " has been added." instance Behavable 'APILevel 'PathLevel where data Behave 'APILevel 'PathLevel @@ -462,7 +464,8 @@ instance Issuable 'PathLevel where = OperationMissing OperationMethod deriving stock (Eq, Ord, Show) issueIsUnsupported _ = False - describeIssue (OperationMissing op) = para $ "Method " <> strong (showMethod op) <> " has been removed." + describeIssue Forward (OperationMissing op) = para $ "Method " <> strong (showMethod op) <> " has been removed." + describeIssue Backward (OperationMissing op) = para $ "Method " <> strong (showMethod op) <> " has been added." instance Behavable 'PathLevel 'OperationLevel where data Behave 'PathLevel 'OperationLevel @@ -579,7 +582,7 @@ instance Issuable 'CallbackLevel where deriving stock (Eq, Ord, Show) issueIsUnsupported = \case CallbacksUnsupported -> True - describeIssue CallbacksUnsupported = para "OpenApi Diff does not currently support callbacks." + describeIssue _ CallbacksUnsupported = para "OpenApi Diff does not currently support callbacks." tracedCallbackPathItems :: Traced Callback -> Traced ProcessedPathItems tracedCallbackPathItems (Traced t (Callback x)) = diff --git a/src/OpenAPI/Checker/Validate/Param.hs b/src/OpenAPI/Checker/Validate/Param.hs index 60ae25f..91ea86f 100644 --- a/src/OpenAPI/Checker/Validate/Param.hs +++ b/src/OpenAPI/Checker/Validate/Param.hs @@ -69,13 +69,15 @@ instance Issuable 'PathFragmentLevel where | PathFragmentsDontMatch Text Text deriving stock (Eq, Ord, Show) issueIsUnsupported _ = False - describeIssue ParamNameMismatch = para "The path fragments don't match." - describeIssue ParamEmptinessIncompatible = para "Expected that an empty parameter is allowed, but it isn't." - describeIssue ParamRequired = para "Parameter has become required." - describeIssue ParamPlaceIncompatible = para "Parameters in incompatible locations." - describeIssue ParamStyleMismatch = para "Different parameter styles (encodings)." - describeIssue ParamSchemaMismatch = para "Expected a schema, but didn't find one." - describeIssue (PathFragmentsDontMatch e a) = para $ "Parameter changed from " <> code e <> " to " <> code a <> "." + describeIssue _ ParamNameMismatch = para "The path fragments don't match." + describeIssue Forward ParamEmptinessIncompatible = para "The parameter can no longer be empty." + describeIssue Backward ParamEmptinessIncompatible = para "The parameter can now be empty." + describeIssue Forward ParamRequired = para "Parameter has become required." + describeIssue Backward ParamRequired = para "Parameter is no longer required." + describeIssue _ ParamPlaceIncompatible = para "Parameters in incompatible locations." + describeIssue _ ParamStyleMismatch = para "Different parameter styles (encodings)." + describeIssue _ ParamSchemaMismatch = para "Expected a schema, but didn't find one." + describeIssue _ (PathFragmentsDontMatch e a) = para $ "Parameter changed from " <> code e <> " to " <> code a <> "." instance Behavable 'PathFragmentLevel 'SchemaLevel where data Behave 'PathFragmentLevel 'SchemaLevel diff --git a/src/OpenAPI/Checker/Validate/RequestBody.hs b/src/OpenAPI/Checker/Validate/RequestBody.hs index 50148fb..fb1291b 100644 --- a/src/OpenAPI/Checker/Validate/RequestBody.hs +++ b/src/OpenAPI/Checker/Validate/RequestBody.hs @@ -31,10 +31,14 @@ instance Issuable 'RequestLevel where | RequestMediaTypeNotFound MediaType deriving stock (Eq, Ord, Show) issueIsUnsupported _ = False - describeIssue RequestBodyRequired = + describeIssue Forward RequestBodyRequired = para "Request body has become required." - describeIssue (RequestMediaTypeNotFound t) = + describeIssue Backward RequestBodyRequired = + para "Request body is no longer required." + describeIssue Forward (RequestMediaTypeNotFound t) = para $ "Media type " <> (code . T.pack . show $ t) <> " has been removed." + describeIssue Backward (RequestMediaTypeNotFound t) = + para $ "Media type " <> (code . T.pack . show $ t) <> " has been added." instance Behavable 'RequestLevel 'PayloadLevel where data Behave 'RequestLevel 'PayloadLevel diff --git a/src/OpenAPI/Checker/Validate/Responses.hs b/src/OpenAPI/Checker/Validate/Responses.hs index cd79d81..3ab9c91 100644 --- a/src/OpenAPI/Checker/Validate/Responses.hs +++ b/src/OpenAPI/Checker/Validate/Responses.hs @@ -72,10 +72,14 @@ instance Issuable 'ResponseLevel where | ResponseHeaderMissing HeaderName deriving stock (Eq, Ord, Show) issueIsUnsupported _ = False - describeIssue (ResponseMediaTypeMissing t) = + describeIssue Forward (ResponseMediaTypeMissing t) = + para $ "Media type was removed: " <> (code . T.pack . show $ t) <> "." + describeIssue Backward (ResponseMediaTypeMissing t) = para $ "New media type was added: " <> (code . T.pack . show $ t) <> "." - describeIssue (ResponseHeaderMissing h) = + describeIssue Forward (ResponseHeaderMissing h) = para $ "New header was added " <> code h <> "." + describeIssue Backward (ResponseHeaderMissing h) = + para $ "Header was removed " <> code h <> "." instance Behavable 'ResponseLevel 'PayloadLevel where data Behave 'ResponseLevel 'PayloadLevel diff --git a/src/OpenAPI/Checker/Validate/Schema.hs b/src/OpenAPI/Checker/Validate/Schema.hs index 660b666..d2e1c6f 100644 --- a/src/OpenAPI/Checker/Validate/Schema.hs +++ b/src/OpenAPI/Checker/Validate/Schema.hs @@ -1057,38 +1057,58 @@ instance Issuable 'TypedSchemaLevel where NoContradiction deriving stock (Eq, Ord, Show) issueIsUnsupported _ = False - describeIssue (EnumDoesntSatisfy v) = para "The following enum value was added:" <> showJSONValue v - describeIssue (NoMatchingEnum v) = para "The following enum value has been removed:" <> showJSONValue v - describeIssue (NoMatchingMaximum b) = para $ "Upper bound has been added:" <> showBound b <> "." - describeIssue (MatchingMaximumWeak (ProdCons p c)) = para $ "Upper bound changed from " <> showBound p <> " to " <> showBound c <> "." - describeIssue (NoMatchingMinimum b) = para $ "Lower bound has been added: " <> showBound b <> "." - describeIssue (MatchingMinimumWeak (ProdCons p c)) = para $ "Lower bound changed from " <> showBound p <> " to " <> showBound c <> "." - describeIssue (NoMatchingMultipleOf n) = para $ "Value is now a multiple of " <> show' n <> "." - describeIssue (MatchingMultipleOfWeak (ProdCons p c)) = para $ "Value changed from being a multiple of " <> show' p <> " to being a multiple of " <> show' c <> "." - describeIssue (NoMatchingFormat f) = para $ "Format added: " <> code f <> "." - describeIssue (NoMatchingMaxLength n) = para $ "Maximum length added: " <> show' n <> "." - describeIssue (MatchingMaxLengthWeak (ProdCons p c)) = para $ "Maximum length of the string changed from " <> show' p <> " to " <> show' c <> "." - describeIssue (NoMatchingMinLength n) = para $ "Minimum length of the string added: " <> show' n <> "." - describeIssue (MatchingMinLengthWeak (ProdCons p c)) = para $ "Minimum length of the string changed from " <> show' p <> " to " <> show' c <> "." - describeIssue (NoMatchingPattern p) = para "Pattern (regular expression) added: " <> codeBlock p - describeIssue NoMatchingItems = para "Array item schema has been added." - describeIssue (NoMatchingMaxItems n) = para $ "Maximum length of the array has been added " <> show' n <> "." - describeIssue (MatchingMaxItemsWeak (ProdCons p c)) = para $ "Maximum length of the array changed from " <> show' p <> " to " <> show' c <> "." - describeIssue (NoMatchingMinItems n) = para $ "Minimum length of the array added: " <> show' n <> "." - describeIssue (MatchingMinItemsWeak (ProdCons p c)) = para $ "Minimum length of the array changed from " <> show' p <> " to " <> show' c <> "." - describeIssue NoMatchingUniqueItems = para "Items are now required to be unique." - describeIssue NoMatchingProperties = para "Property added." - describeIssue (UnexpectedProperty p) = para $ "Property " <> code p <> " has been removed." - describeIssue (PropertyNowRequired p) = para $ "Property " <> code p <> " has become required." - describeIssue NoAdditionalProperties = para "Additional properties have been removed." - describeIssue (NoMatchingMaxProperties n) = para $ "Maximum number of properties has been added: " <> show' n <> "." - describeIssue (MatchingMaxPropertiesWeak (ProdCons p c)) = para $ "Maximum number of properties has changed from " <> show' p <> " to " <> show' c <> "." - describeIssue (NoMatchingMinProperties n) = para $ "Minimum number of properties added: " <> show' n <> "." - describeIssue (MatchingMinPropertiesWeak (ProdCons p c)) = para $ "Minimum number of properties has changed from " <> show' p <> " to " <> show' c <> "." - describeIssue (NoMatchingCondition conds) = + describeIssue Forward (EnumDoesntSatisfy v) = para "The following enum value was added:" <> showJSONValue v + describeIssue Backward (EnumDoesntSatisfy v) = para "The following enum value was removed:" <> showJSONValue v + describeIssue Forward (NoMatchingEnum v) = para "The following enum value has been removed:" <> showJSONValue v + describeIssue Backward (NoMatchingEnum v) = para "The following enum value has been added:" <> showJSONValue v + describeIssue Forward (NoMatchingMaximum b) = para $ "Upper bound has been added:" <> showBound b <> "." + describeIssue Backward (NoMatchingMaximum b) = para $ "Upper bound has been removed:" <> showBound b <> "." + describeIssue _ (MatchingMaximumWeak (ProdCons p c)) = para $ "Upper bound changed from " <> showBound p <> " to " <> showBound c <> "." + describeIssue Forward (NoMatchingMinimum b) = para $ "Lower bound has been added: " <> showBound b <> "." + describeIssue Backward (NoMatchingMinimum b) = para $ "Lower bound has been removed: " <> showBound b <> "." + describeIssue _ (MatchingMinimumWeak (ProdCons p c)) = para $ "Lower bound changed from " <> showBound p <> " to " <> showBound c <> "." + describeIssue Forward (NoMatchingMultipleOf n) = para $ "Value is now a multiple of " <> show' n <> "." + describeIssue Backward (NoMatchingMultipleOf n) = para $ "Value is no longer a multiple of " <> show' n <> "." + describeIssue _ (MatchingMultipleOfWeak (ProdCons p c)) = para $ "Value changed from being a multiple of " <> show' p <> " to being a multiple of " <> show' c <> "." + describeIssue Forward (NoMatchingFormat f) = para $ "Format added: " <> code f <> "." + describeIssue Backward (NoMatchingFormat f) = para $ "Format removed: " <> code f <> "." + describeIssue Forward (NoMatchingMaxLength n) = para $ "Maximum length added: " <> show' n <> "." + describeIssue Backward (NoMatchingMaxLength n) = para $ "Maximum length removed: " <> show' n <> "." + describeIssue _ (MatchingMaxLengthWeak (ProdCons p c)) = para $ "Maximum length of the string changed from " <> show' p <> " to " <> show' c <> "." + describeIssue Forward (NoMatchingMinLength n) = para $ "Minimum length of the string added: " <> show' n <> "." + describeIssue Backward (NoMatchingMinLength n) = para $ "Minimum length of the string removed: " <> show' n <> "." + describeIssue _ (MatchingMinLengthWeak (ProdCons p c)) = para $ "Minimum length of the string changed from " <> show' p <> " to " <> show' c <> "." + describeIssue Forward (NoMatchingPattern p) = para "Pattern (regular expression) added: " <> codeBlock p + describeIssue Backward (NoMatchingPattern p) = para "Pattern (regular expression) removed: " <> codeBlock p + describeIssue Forward NoMatchingItems = para "Array item schema has been added." + describeIssue Backward NoMatchingItems = para "Array item schema has been removed." + describeIssue Forward (NoMatchingMaxItems n) = para $ "Maximum length of the array has been added " <> show' n <> "." + describeIssue Backward (NoMatchingMaxItems n) = para $ "Maximum length of the array has been removed " <> show' n <> "." + describeIssue _ (MatchingMaxItemsWeak (ProdCons p c)) = para $ "Maximum length of the array changed from " <> show' p <> " to " <> show' c <> "." + describeIssue Forward (NoMatchingMinItems n) = para $ "Minimum length of the array added: " <> show' n <> "." + describeIssue Backward (NoMatchingMinItems n) = para $ "Minimum length of the array removed: " <> show' n <> "." + describeIssue _ (MatchingMinItemsWeak (ProdCons p c)) = para $ "Minimum length of the array changed from " <> show' p <> " to " <> show' c <> "." + describeIssue Forward NoMatchingUniqueItems = para "Items are now required to be unique." + describeIssue Backward NoMatchingUniqueItems = para "Items are no longer required to be unique." + describeIssue Forward NoMatchingProperties = para "Property added." + describeIssue Backward NoMatchingProperties = para "Property removed." + describeIssue Forward (UnexpectedProperty p) = para $ "Property " <> code p <> " has been removed." + describeIssue Backward (UnexpectedProperty p) = para $ "Property " <> code p <> " has been added." + describeIssue Forward (PropertyNowRequired p) = para $ "Property " <> code p <> " has become required." + describeIssue Backward (PropertyNowRequired p) = para $ "Property " <> code p <> " may not be present." + describeIssue Forward NoAdditionalProperties = para "Additional properties have been removed." + describeIssue Backward NoAdditionalProperties = para "Additional properties have been added." + describeIssue Forward (NoMatchingMaxProperties n) = para $ "Maximum number of properties has been added: " <> show' n <> "." + describeIssue Backward (NoMatchingMaxProperties n) = para $ "Maximum number of properties has been removed: " <> show' n <> "." + describeIssue _ (MatchingMaxPropertiesWeak (ProdCons p c)) = para $ "Maximum number of properties has changed from " <> show' p <> " to " <> show' c <> "." + describeIssue Forward (NoMatchingMinProperties n) = para $ "Minimum number of properties added: " <> show' n <> "." + describeIssue Backward (NoMatchingMinProperties n) = para $ "Minimum number of properties removed: " <> show' n <> "." + describeIssue _ (MatchingMinPropertiesWeak (ProdCons p c)) = para $ "Minimum number of properties has changed from " <> show' p <> " to " <> show' c <> "." + describeIssue _ (NoMatchingCondition conds) = para "Expected the following conditions to hold, but they didn't (please file a bug if you see this):" <> bulletList ((\(SomeCondition c) -> showCondition c) <$> conds) - describeIssue NoContradiction = para "The type has been removed." + describeIssue Forward NoContradiction = para "The type has been removed." + describeIssue Backward NoContradiction = para "The type has been added." showJSONValue :: A.Value -> Blocks showJSONValue v = codeBlockWith ("", ["json"], mempty) (T.decodeUtf8 . BSL.toStrict . A.encode $ v) @@ -1111,11 +1131,11 @@ instance Issuable 'SchemaLevel where deriving stock (Eq, Ord, Show) issueIsUnsupported _ = True - describeIssue (NotSupported i) = + describeIssue _ (NotSupported i) = para (emph "Encountered a feature that OpenApi Diff does not support: " <> text i <> ".") - describeIssue (InvalidSchema i) = + describeIssue _ (InvalidSchema i) = para (emph "The schema is invalid: " <> text i <> ".") - describeIssue UnguardedRecursion = + describeIssue _ UnguardedRecursion = para "Encountered recursion that is too complex for OpenApi Diff to untangle." instance Behavable 'SchemaLevel 'TypedSchemaLevel where diff --git a/src/OpenAPI/Checker/Validate/Server.hs b/src/OpenAPI/Checker/Validate/Server.hs index 7cf5798..b4d68ce 100644 --- a/src/OpenAPI/Checker/Validate/Server.hs +++ b/src/OpenAPI/Checker/Validate/Server.hs @@ -134,13 +134,18 @@ instance Issuable 'ServerLevel where | ServerNotMatched deriving stock (Eq, Ord, Show) issueIsUnsupported _ = False - describeIssue (EnumValueNotConsumed _ v) = + describeIssue Forward (EnumValueNotConsumed _ v) = para $ "Enum value " <> code v <> " has been removed." - describeIssue (ConsumerNotOpen _) = + describeIssue Backward (EnumValueNotConsumed _ v) = + para $ "Enum value " <> code v <> " has been added." + describeIssue Forward (ConsumerNotOpen _) = para $ "A variable has been changed from being open to being closed." - describeIssue (ServerVariableNotDefined k) = + describeIssue Backward (ConsumerNotOpen _) = + para $ "A variable has been changed from being closed to being open." + describeIssue _ (ServerVariableNotDefined k) = para $ "Variable " <> code k <> " is not defined." - describeIssue ServerNotMatched = para $ "The server was removed." + describeIssue Forward ServerNotMatched = para $ "The server was removed." + describeIssue Backward ServerNotMatched = para $ "The server was added." instance Subtree ProcessedServer where type SubtreeLevel ProcessedServer = 'ServerLevel diff --git a/stack.yaml b/stack.yaml index 81538bb..60cb077 100644 --- a/stack.yaml +++ b/stack.yaml @@ -1,4 +1,4 @@ -resolver: nightly-2021-06-10 +resolver: lts-18.0 extra-deps: - open-union-0.4.0.0 diff --git a/stack.yaml.lock b/stack.yaml.lock index 3c461b6..141b324 100644 --- a/stack.yaml.lock +++ b/stack.yaml.lock @@ -20,7 +20,7 @@ packages: hackage: type-fun-0.1.3 snapshots: - completed: - size: 585361 - url: https://raw.githubusercontent.com/commercialhaskell/stackage-snapshots/master/nightly/2021/6/10.yaml - sha256: ef53458d54ca6084c6d8eb5219d03b38878e999af607cf006d5be86669d9a696 - original: nightly-2021-06-10 + size: 585393 + url: https://raw.githubusercontent.com/commercialhaskell/stackage-snapshots/master/lts/18/0.yaml + sha256: c632012da648385b9fa3c29f4e0afd56ead299f1c5528ee789058be410e883c0 + original: lts-18.0 diff --git a/test/Spec.hs b/test/Spec.hs index 128e8bf..7bdcd77 100644 --- a/test/Spec.hs +++ b/test/Spec.hs @@ -9,4 +9,4 @@ main = defaultMain =<< tests tests :: IO TestTree tests = do goldenReportTree <- Spec.Golden.TraceTree.tests - return . localOption (mkTimeout 1000000) $ goldenReportTree + return . localOption (mkTimeout 5000000) $ goldenReportTree diff --git a/test/Spec/Golden/TraceTree.hs b/test/Spec/Golden/TraceTree.hs index 3950de0..34ce818 100644 --- a/test/Spec/Golden/TraceTree.hs +++ b/test/Spec/Golden/TraceTree.hs @@ -7,16 +7,10 @@ import Control.Category import Control.Exception import qualified Data.ByteString.Lazy as BSL import Data.Default -import Data.HList -import Data.OpenApi import Data.Text (Text) import qualified Data.Text.Encoding as T import qualified Data.Yaml as Yaml -import OpenAPI.Checker.Behavior -import OpenAPI.Checker.Paths -import OpenAPI.Checker.PathsPrefixTree -import OpenAPI.Checker.Report -import OpenAPI.Checker.Subtree +import OpenAPI.Checker.Run import OpenAPI.Checker.Validate.OpenApi () import Spec.Golden.Extra import Test.Tasty (TestTree, testGroup) @@ -43,18 +37,9 @@ tests = do "report.md" ("a.yaml", "b.yaml") Yaml.decodeFileThrow - (runPandoc . writeMarkdown def {writerExtensions = githubMarkdownExtensions} . generateReport . runChecker) + (runPandoc . writeMarkdown def {writerExtensions = githubMarkdownExtensions} . fst . runReport) return $ testGroup "Golden tests" [traceTreeTests, reportTests] runPandoc :: PandocPure Text -> IO BSL.ByteString runPandoc = either throwIO (pure . BSL.fromStrict . T.encodeUtf8) . runPure - -runChecker :: (OpenApi, OpenApi) -> Either (PathsPrefixTree Behave AnIssue 'APILevel) () -runChecker = runCompatFormula . checkCompatibility HNil Root . toPC - where - toPC (c, s) = - ProdCons - { producer = traced (step ClientSchema) c - , consumer = traced (step ServerSchema) s - } diff --git a/test/golden/common/enum-anyof/report.md b/test/golden/common/enum-anyof/report.md index 4211f70..70b7698 100644 --- a/test/golden/common/enum-anyof/report.md +++ b/test/golden/common/enum-anyof/report.md @@ -1 +1,5 @@ -# No breaking changes found ✨ +# Summary + +| ⚠️ Breaking changes | 🙆 Non-breaking changes | 🤷 Unsupported feature changes | +|---------------------|------------------------|-------------------------------| +| 0 | 0 | 0 | diff --git a/test/golden/common/enum-anyof/trace-tree.yaml b/test/golden/common/enum-anyof/trace-tree.yaml index 5d14c1e..b9b681e 100644 --- a/test/golden/common/enum-anyof/trace-tree.yaml +++ b/test/golden/common/enum-anyof/trace-tree.yaml @@ -1 +1,2 @@ -Right: [] +breakingChanges: {} +nonBreakingChanges: {} diff --git a/test/golden/common/id/report.md b/test/golden/common/id/report.md index 4211f70..70b7698 100644 --- a/test/golden/common/id/report.md +++ b/test/golden/common/id/report.md @@ -1 +1,5 @@ -# No breaking changes found ✨ +# Summary + +| ⚠️ Breaking changes | 🙆 Non-breaking changes | 🤷 Unsupported feature changes | +|---------------------|------------------------|-------------------------------| +| 0 | 0 | 0 | diff --git a/test/golden/common/id/trace-tree.yaml b/test/golden/common/id/trace-tree.yaml index 5d14c1e..b9b681e 100644 --- a/test/golden/common/id/trace-tree.yaml +++ b/test/golden/common/id/trace-tree.yaml @@ -1 +1,2 @@ -Right: [] +breakingChanges: {} +nonBreakingChanges: {} diff --git a/test/golden/common/json/recursive/report.md b/test/golden/common/json/recursive/report.md index 4211f70..70b7698 100644 --- a/test/golden/common/json/recursive/report.md +++ b/test/golden/common/json/recursive/report.md @@ -1 +1,5 @@ -# No breaking changes found ✨ +# Summary + +| ⚠️ Breaking changes | 🙆 Non-breaking changes | 🤷 Unsupported feature changes | +|---------------------|------------------------|-------------------------------| +| 0 | 0 | 0 | diff --git a/test/golden/common/json/recursive/trace-tree.yaml b/test/golden/common/json/recursive/trace-tree.yaml index 5d14c1e..b9b681e 100644 --- a/test/golden/common/json/recursive/trace-tree.yaml +++ b/test/golden/common/json/recursive/trace-tree.yaml @@ -1 +1,2 @@ -Right: [] +breakingChanges: {} +nonBreakingChanges: {} diff --git a/test/golden/common/maximum-lowered/report.md b/test/golden/common/maximum-lowered/report.md index 199513a..186cd0c 100644 --- a/test/golden/common/maximum-lowered/report.md +++ b/test/golden/common/maximum-lowered/report.md @@ -1,14 +1,24 @@ # Summary -| [⚠️ Breaking changes](#breaking-changes) | 🤷 Unsupported feature changes | -|------------------------------------------|-------------------------------| -| 1 | 0 | +| [⚠️ Breaking changes](#breaking-changes) | [🙆 Non-breaking changes](#non-breaking-changes) | 🤷 Unsupported feature changes | +|------------------------------------------|-------------------------------------------------|-------------------------------| +| 1 | 1 | 0 | # ⚠️ Breaking changes ## **POST** /test -### JSON Request +### 📱➡️ JSON Request + +#### `$(Number)` + +Upper bound changed from 3.0 inclusive to 2.0 inclusive. + +# 🙆 Non-breaking changes + +## **POST** /test + +### 📱⬅️ JSON Response – 200 #### `$(Number)` diff --git a/test/golden/common/maximum-lowered/trace-tree.yaml b/test/golden/common/maximum-lowered/trace-tree.yaml index bddbc8b..fae9fd7 100644 --- a/test/golden/common/maximum-lowered/trace-tree.yaml +++ b/test/golden/common/maximum-lowered/trace-tree.yaml @@ -1,4 +1,4 @@ -Left: +breakingChanges: AtPath "/test": InOperation PostMethod: InRequest: @@ -6,3 +6,11 @@ Left: PayloadSchema: OfType Number: MatchingMaximumWeak (ProdCons {producer = Inclusive 3.0, consumer = Inclusive 2.0}) +nonBreakingChanges: + AtPath "/test": + InOperation PostMethod: + WithStatusCode 200: + ResponsePayload: + PayloadSchema: + OfType Number: MatchingMaximumWeak (ProdCons {producer = Inclusive 3.0, + consumer = Inclusive 2.0}) diff --git a/test/golden/common/pathItem/operation/parameters/allowEmptyValue/reset/report.md b/test/golden/common/pathItem/operation/parameters/allowEmptyValue/reset/report.md index b788d40..084ed09 100644 --- a/test/golden/common/pathItem/operation/parameters/allowEmptyValue/reset/report.md +++ b/test/golden/common/pathItem/operation/parameters/allowEmptyValue/reset/report.md @@ -1,8 +1,8 @@ # Summary -| [⚠️ Breaking changes](#breaking-changes) | 🤷 Unsupported feature changes | -|------------------------------------------|-------------------------------| -| 1 | 0 | +| [⚠️ Breaking changes](#breaking-changes) | 🙆 Non-breaking changes | 🤷 Unsupported feature changes | +|------------------------------------------|------------------------|-------------------------------| +| 1 | 0 | 0 | # ⚠️ Breaking changes @@ -10,4 +10,4 @@ ### Parameter test1 -Expected that an empty parameter is allowed, but it isn't. +The parameter can no longer be empty. diff --git a/test/golden/common/pathItem/operation/parameters/allowEmptyValue/reset/trace-tree.yaml b/test/golden/common/pathItem/operation/parameters/allowEmptyValue/reset/trace-tree.yaml index 52a0aff..84ebe69 100644 --- a/test/golden/common/pathItem/operation/parameters/allowEmptyValue/reset/trace-tree.yaml +++ b/test/golden/common/pathItem/operation/parameters/allowEmptyValue/reset/trace-tree.yaml @@ -1,4 +1,5 @@ -Left: +breakingChanges: AtPath "/test": InOperation PostMethod: InParam "test1": ParamEmptinessIncompatible +nonBreakingChanges: {} diff --git a/test/golden/common/pathItem/operation/parameters/allowEmptyValue/set/report.md b/test/golden/common/pathItem/operation/parameters/allowEmptyValue/set/report.md index 4211f70..df37459 100644 --- a/test/golden/common/pathItem/operation/parameters/allowEmptyValue/set/report.md +++ b/test/golden/common/pathItem/operation/parameters/allowEmptyValue/set/report.md @@ -1 +1,13 @@ -# No breaking changes found ✨ +# Summary + +| ⚠️ Breaking changes | [🙆 Non-breaking changes](#non-breaking-changes) | 🤷 Unsupported feature changes | +|---------------------|-------------------------------------------------|-------------------------------| +| 0 | 1 | 0 | + +# 🙆 Non-breaking changes + +## **POST** /test + +### Parameter test1 + +The parameter can now be empty. diff --git a/test/golden/common/pathItem/operation/parameters/allowEmptyValue/set/trace-tree.yaml b/test/golden/common/pathItem/operation/parameters/allowEmptyValue/set/trace-tree.yaml index 5d14c1e..84d21b9 100644 --- a/test/golden/common/pathItem/operation/parameters/allowEmptyValue/set/trace-tree.yaml +++ b/test/golden/common/pathItem/operation/parameters/allowEmptyValue/set/trace-tree.yaml @@ -1 +1,5 @@ -Right: [] +breakingChanges: {} +nonBreakingChanges: + AtPath "/test": + InOperation PostMethod: + InParam "test1": ParamEmptinessIncompatible diff --git a/test/golden/common/pathItem/operation/parameters/change/report.md b/test/golden/common/pathItem/operation/parameters/change/report.md index 2d9c3ec..24ee5e4 100644 --- a/test/golden/common/pathItem/operation/parameters/change/report.md +++ b/test/golden/common/pathItem/operation/parameters/change/report.md @@ -1,8 +1,8 @@ # Summary -| [⚠️ Breaking changes](#breaking-changes) | 🤷 Unsupported feature changes | -|------------------------------------------|-------------------------------| -| 1 | 0 | +| [⚠️ Breaking changes](#breaking-changes) | [🙆 Non-breaking changes](#non-breaking-changes) | 🤷 Unsupported feature changes | +|------------------------------------------|-------------------------------------------------|-------------------------------| +| 1 | 1 | 0 | # ⚠️ Breaking changes @@ -15,3 +15,15 @@ ##### `$(String)` The type has been removed. + +# 🙆 Non-breaking changes + +## **POST** /test + +### Parameter test + +#### JSON Schema + +##### `$(Number)` + +The type has been added. diff --git a/test/golden/common/pathItem/operation/parameters/change/trace-tree.yaml b/test/golden/common/pathItem/operation/parameters/change/trace-tree.yaml index a2eb624..a9d1cb9 100644 --- a/test/golden/common/pathItem/operation/parameters/change/trace-tree.yaml +++ b/test/golden/common/pathItem/operation/parameters/change/trace-tree.yaml @@ -1,6 +1,12 @@ -Left: +breakingChanges: AtPath "/test": InOperation PostMethod: InParam "test": InParamSchema: OfType String: NoContradiction +nonBreakingChanges: + AtPath "/test": + InOperation PostMethod: + InParam "test": + InParamSchema: + OfType Number: NoContradiction diff --git a/test/golden/common/pathItem/operation/parameters/required/false/add/report.md b/test/golden/common/pathItem/operation/parameters/required/false/add/report.md index 4211f70..70b7698 100644 --- a/test/golden/common/pathItem/operation/parameters/required/false/add/report.md +++ b/test/golden/common/pathItem/operation/parameters/required/false/add/report.md @@ -1 +1,5 @@ -# No breaking changes found ✨ +# Summary + +| ⚠️ Breaking changes | 🙆 Non-breaking changes | 🤷 Unsupported feature changes | +|---------------------|------------------------|-------------------------------| +| 0 | 0 | 0 | diff --git a/test/golden/common/pathItem/operation/parameters/required/false/add/trace-tree.yaml b/test/golden/common/pathItem/operation/parameters/required/false/add/trace-tree.yaml index 5d14c1e..b9b681e 100644 --- a/test/golden/common/pathItem/operation/parameters/required/false/add/trace-tree.yaml +++ b/test/golden/common/pathItem/operation/parameters/required/false/add/trace-tree.yaml @@ -1 +1,2 @@ -Right: [] +breakingChanges: {} +nonBreakingChanges: {} diff --git a/test/golden/common/pathItem/operation/parameters/required/false/del/report.md b/test/golden/common/pathItem/operation/parameters/required/false/del/report.md index 4211f70..70b7698 100644 --- a/test/golden/common/pathItem/operation/parameters/required/false/del/report.md +++ b/test/golden/common/pathItem/operation/parameters/required/false/del/report.md @@ -1 +1,5 @@ -# No breaking changes found ✨ +# Summary + +| ⚠️ Breaking changes | 🙆 Non-breaking changes | 🤷 Unsupported feature changes | +|---------------------|------------------------|-------------------------------| +| 0 | 0 | 0 | diff --git a/test/golden/common/pathItem/operation/parameters/required/false/del/trace-tree.yaml b/test/golden/common/pathItem/operation/parameters/required/false/del/trace-tree.yaml index 5d14c1e..b9b681e 100644 --- a/test/golden/common/pathItem/operation/parameters/required/false/del/trace-tree.yaml +++ b/test/golden/common/pathItem/operation/parameters/required/false/del/trace-tree.yaml @@ -1 +1,2 @@ -Right: [] +breakingChanges: {} +nonBreakingChanges: {} diff --git a/test/golden/common/pathItem/operation/parameters/required/reset/report.md b/test/golden/common/pathItem/operation/parameters/required/reset/report.md index 4211f70..6fedc96 100644 --- a/test/golden/common/pathItem/operation/parameters/required/reset/report.md +++ b/test/golden/common/pathItem/operation/parameters/required/reset/report.md @@ -1 +1,13 @@ -# No breaking changes found ✨ +# Summary + +| ⚠️ Breaking changes | [🙆 Non-breaking changes](#non-breaking-changes) | 🤷 Unsupported feature changes | +|---------------------|-------------------------------------------------|-------------------------------| +| 0 | 1 | 0 | + +# 🙆 Non-breaking changes + +## **POST** /test + +### Parameter test1 + +Parameter is no longer required. diff --git a/test/golden/common/pathItem/operation/parameters/required/reset/trace-tree.yaml b/test/golden/common/pathItem/operation/parameters/required/reset/trace-tree.yaml index 5d14c1e..c898388 100644 --- a/test/golden/common/pathItem/operation/parameters/required/reset/trace-tree.yaml +++ b/test/golden/common/pathItem/operation/parameters/required/reset/trace-tree.yaml @@ -1 +1,5 @@ -Right: [] +breakingChanges: {} +nonBreakingChanges: + AtPath "/test": + InOperation PostMethod: + InParam "test1": ParamRequired diff --git a/test/golden/common/pathItem/operation/parameters/required/set/report.md b/test/golden/common/pathItem/operation/parameters/required/set/report.md index 3a58d19..cded916 100644 --- a/test/golden/common/pathItem/operation/parameters/required/set/report.md +++ b/test/golden/common/pathItem/operation/parameters/required/set/report.md @@ -1,8 +1,8 @@ # Summary -| [⚠️ Breaking changes](#breaking-changes) | 🤷 Unsupported feature changes | -|------------------------------------------|-------------------------------| -| 1 | 0 | +| [⚠️ Breaking changes](#breaking-changes) | 🙆 Non-breaking changes | 🤷 Unsupported feature changes | +|------------------------------------------|------------------------|-------------------------------| +| 1 | 0 | 0 | # ⚠️ Breaking changes diff --git a/test/golden/common/pathItem/operation/parameters/required/set/trace-tree.yaml b/test/golden/common/pathItem/operation/parameters/required/set/trace-tree.yaml index e484608..7166f59 100644 --- a/test/golden/common/pathItem/operation/parameters/required/set/trace-tree.yaml +++ b/test/golden/common/pathItem/operation/parameters/required/set/trace-tree.yaml @@ -1,4 +1,5 @@ -Left: +breakingChanges: AtPath "/test": InOperation PostMethod: InParam "test1": ParamRequired +nonBreakingChanges: {} diff --git a/test/golden/common/pathItem/operation/parameters/required/true/add/report.md b/test/golden/common/pathItem/operation/parameters/required/true/add/report.md index 6817026..d8c6989 100644 --- a/test/golden/common/pathItem/operation/parameters/required/true/add/report.md +++ b/test/golden/common/pathItem/operation/parameters/required/true/add/report.md @@ -1,8 +1,8 @@ # Summary -| [⚠️ Breaking changes](#breaking-changes) | 🤷 Unsupported feature changes | -|------------------------------------------|-------------------------------| -| 1 | 0 | +| [⚠️ Breaking changes](#breaking-changes) | 🙆 Non-breaking changes | 🤷 Unsupported feature changes | +|------------------------------------------|------------------------|-------------------------------| +| 1 | 0 | 0 | # ⚠️ Breaking changes diff --git a/test/golden/common/pathItem/operation/parameters/required/true/add/trace-tree.yaml b/test/golden/common/pathItem/operation/parameters/required/true/add/trace-tree.yaml index e4be5d6..a24a2a6 100644 --- a/test/golden/common/pathItem/operation/parameters/required/true/add/trace-tree.yaml +++ b/test/golden/common/pathItem/operation/parameters/required/true/add/trace-tree.yaml @@ -1,3 +1,4 @@ -Left: +breakingChanges: AtPath "/test": InOperation PostMethod: ParamNotMatched "test2" +nonBreakingChanges: {} diff --git a/test/golden/common/pathItem/operation/parameters/required/true/del/report.md b/test/golden/common/pathItem/operation/parameters/required/true/del/report.md index 4211f70..09f725d 100644 --- a/test/golden/common/pathItem/operation/parameters/required/true/del/report.md +++ b/test/golden/common/pathItem/operation/parameters/required/true/del/report.md @@ -1 +1,11 @@ -# No breaking changes found ✨ +# Summary + +| ⚠️ Breaking changes | [🙆 Non-breaking changes](#non-breaking-changes) | 🤷 Unsupported feature changes | +|---------------------|-------------------------------------------------|-------------------------------| +| 0 | 1 | 0 | + +# 🙆 Non-breaking changes + +## **POST** /test + +Parameter `test2` is no longer required. diff --git a/test/golden/common/pathItem/operation/parameters/required/true/del/trace-tree.yaml b/test/golden/common/pathItem/operation/parameters/required/true/del/trace-tree.yaml index 5d14c1e..02e313b 100644 --- a/test/golden/common/pathItem/operation/parameters/required/true/del/trace-tree.yaml +++ b/test/golden/common/pathItem/operation/parameters/required/true/del/trace-tree.yaml @@ -1 +1,4 @@ -Right: [] +breakingChanges: {} +nonBreakingChanges: + AtPath "/test": + InOperation PostMethod: ParamNotMatched "test2" diff --git a/test/golden/common/pathItem/operation/requestBody/mediaTypeObject/add/report.md b/test/golden/common/pathItem/operation/requestBody/mediaTypeObject/add/report.md index 4211f70..b07e363 100644 --- a/test/golden/common/pathItem/operation/requestBody/mediaTypeObject/add/report.md +++ b/test/golden/common/pathItem/operation/requestBody/mediaTypeObject/add/report.md @@ -1 +1,13 @@ -# No breaking changes found ✨ +# Summary + +| ⚠️ Breaking changes | [🙆 Non-breaking changes](#non-breaking-changes) | 🤷 Unsupported feature changes | +|---------------------|-------------------------------------------------|-------------------------------| +| 0 | 1 | 0 | + +# 🙆 Non-breaking changes + +## **POST** /test + +### Request + +Media type `application/x-www-form-urlencoded` has been added. diff --git a/test/golden/common/pathItem/operation/requestBody/mediaTypeObject/add/trace-tree.yaml b/test/golden/common/pathItem/operation/requestBody/mediaTypeObject/add/trace-tree.yaml index 5d14c1e..2e1bb62 100644 --- a/test/golden/common/pathItem/operation/requestBody/mediaTypeObject/add/trace-tree.yaml +++ b/test/golden/common/pathItem/operation/requestBody/mediaTypeObject/add/trace-tree.yaml @@ -1 +1,5 @@ -Right: [] +breakingChanges: {} +nonBreakingChanges: + AtPath "/test": + InOperation PostMethod: + InRequest: RequestMediaTypeNotFound application/x-www-form-urlencoded diff --git a/test/golden/common/pathItem/operation/requestBody/mediaTypeObject/change/report.md b/test/golden/common/pathItem/operation/requestBody/mediaTypeObject/change/report.md index 54e2921..05fa47b 100644 --- a/test/golden/common/pathItem/operation/requestBody/mediaTypeObject/change/report.md +++ b/test/golden/common/pathItem/operation/requestBody/mediaTypeObject/change/report.md @@ -1,15 +1,25 @@ # Summary -| [⚠️ Breaking changes](#breaking-changes) | 🤷 Unsupported feature changes | -|------------------------------------------|-------------------------------| -| 1 | 0 | +| [⚠️ Breaking changes](#breaking-changes) | [🙆 Non-breaking changes](#non-breaking-changes) | 🤷 Unsupported feature changes | +|------------------------------------------|-------------------------------------------------|-------------------------------| +| 1 | 1 | 0 | # ⚠️ Breaking changes ## **POST** /test -### JSON Request +### 📱➡️ JSON Request #### `$(String)` The type has been removed. + +# 🙆 Non-breaking changes + +## **POST** /test + +### 📱➡️ JSON Request + +#### `$(Number)` + +The type has been added. diff --git a/test/golden/common/pathItem/operation/requestBody/mediaTypeObject/change/trace-tree.yaml b/test/golden/common/pathItem/operation/requestBody/mediaTypeObject/change/trace-tree.yaml index 41b98f9..ced3434 100644 --- a/test/golden/common/pathItem/operation/requestBody/mediaTypeObject/change/trace-tree.yaml +++ b/test/golden/common/pathItem/operation/requestBody/mediaTypeObject/change/trace-tree.yaml @@ -1,7 +1,14 @@ -Left: +breakingChanges: AtPath "/test": InOperation PostMethod: InRequest: InPayload: PayloadSchema: OfType String: NoContradiction +nonBreakingChanges: + AtPath "/test": + InOperation PostMethod: + InRequest: + InPayload: + PayloadSchema: + OfType Number: NoContradiction diff --git a/test/golden/common/pathItem/operation/requestBody/mediaTypeObject/del/report.md b/test/golden/common/pathItem/operation/requestBody/mediaTypeObject/del/report.md index 63b6dfb..b8feef4 100644 --- a/test/golden/common/pathItem/operation/requestBody/mediaTypeObject/del/report.md +++ b/test/golden/common/pathItem/operation/requestBody/mediaTypeObject/del/report.md @@ -1,8 +1,8 @@ # Summary -| [⚠️ Breaking changes](#breaking-changes) | 🤷 Unsupported feature changes | -|------------------------------------------|-------------------------------| -| 1 | 0 | +| [⚠️ Breaking changes](#breaking-changes) | 🙆 Non-breaking changes | 🤷 Unsupported feature changes | +|------------------------------------------|------------------------|-------------------------------| +| 1 | 0 | 0 | # ⚠️ Breaking changes diff --git a/test/golden/common/pathItem/operation/requestBody/mediaTypeObject/del/trace-tree.yaml b/test/golden/common/pathItem/operation/requestBody/mediaTypeObject/del/trace-tree.yaml index 3b6684f..2515517 100644 --- a/test/golden/common/pathItem/operation/requestBody/mediaTypeObject/del/trace-tree.yaml +++ b/test/golden/common/pathItem/operation/requestBody/mediaTypeObject/del/trace-tree.yaml @@ -1,4 +1,5 @@ -Left: +breakingChanges: AtPath "/test": InOperation PostMethod: InRequest: RequestMediaTypeNotFound application/x-www-form-urlencoded +nonBreakingChanges: {} diff --git a/test/golden/common/pathItem/operation/requestBody/required/reset/report.md b/test/golden/common/pathItem/operation/requestBody/required/reset/report.md index 4211f70..ebe67f6 100644 --- a/test/golden/common/pathItem/operation/requestBody/required/reset/report.md +++ b/test/golden/common/pathItem/operation/requestBody/required/reset/report.md @@ -1 +1,13 @@ -# No breaking changes found ✨ +# Summary + +| ⚠️ Breaking changes | [🙆 Non-breaking changes](#non-breaking-changes) | 🤷 Unsupported feature changes | +|---------------------|-------------------------------------------------|-------------------------------| +| 0 | 1 | 0 | + +# 🙆 Non-breaking changes + +## **POST** /test + +### Request + +Request body is no longer required. diff --git a/test/golden/common/pathItem/operation/requestBody/required/reset/trace-tree.yaml b/test/golden/common/pathItem/operation/requestBody/required/reset/trace-tree.yaml index 5d14c1e..0c5d8ad 100644 --- a/test/golden/common/pathItem/operation/requestBody/required/reset/trace-tree.yaml +++ b/test/golden/common/pathItem/operation/requestBody/required/reset/trace-tree.yaml @@ -1 +1,5 @@ -Right: [] +breakingChanges: {} +nonBreakingChanges: + AtPath "/test": + InOperation PostMethod: + InRequest: RequestBodyRequired diff --git a/test/golden/common/pathItem/operation/requestBody/required/set/report.md b/test/golden/common/pathItem/operation/requestBody/required/set/report.md index c38e075..73beda5 100644 --- a/test/golden/common/pathItem/operation/requestBody/required/set/report.md +++ b/test/golden/common/pathItem/operation/requestBody/required/set/report.md @@ -1,8 +1,8 @@ # Summary -| [⚠️ Breaking changes](#breaking-changes) | 🤷 Unsupported feature changes | -|------------------------------------------|-------------------------------| -| 1 | 0 | +| [⚠️ Breaking changes](#breaking-changes) | 🙆 Non-breaking changes | 🤷 Unsupported feature changes | +|------------------------------------------|------------------------|-------------------------------| +| 1 | 0 | 0 | # ⚠️ Breaking changes diff --git a/test/golden/common/pathItem/operation/requestBody/required/set/trace-tree.yaml b/test/golden/common/pathItem/operation/requestBody/required/set/trace-tree.yaml index 759e4f9..b3fc0c3 100644 --- a/test/golden/common/pathItem/operation/requestBody/required/set/trace-tree.yaml +++ b/test/golden/common/pathItem/operation/requestBody/required/set/trace-tree.yaml @@ -1,4 +1,5 @@ -Left: +breakingChanges: AtPath "/test": InOperation PostMethod: InRequest: RequestBodyRequired +nonBreakingChanges: {} diff --git a/test/golden/common/pathItem/operation/responses/add/report.md b/test/golden/common/pathItem/operation/responses/add/report.md index db889ce..6b7791f 100644 --- a/test/golden/common/pathItem/operation/responses/add/report.md +++ b/test/golden/common/pathItem/operation/responses/add/report.md @@ -1,8 +1,8 @@ # Summary -| [⚠️ Breaking changes](#breaking-changes) | 🤷 Unsupported feature changes | -|------------------------------------------|-------------------------------| -| 1 | 0 | +| [⚠️ Breaking changes](#breaking-changes) | 🙆 Non-breaking changes | 🤷 Unsupported feature changes | +|------------------------------------------|------------------------|-------------------------------| +| 1 | 0 | 0 | # ⚠️ Breaking changes diff --git a/test/golden/common/pathItem/operation/responses/add/trace-tree.yaml b/test/golden/common/pathItem/operation/responses/add/trace-tree.yaml index ea7c116..3794904 100644 --- a/test/golden/common/pathItem/operation/responses/add/trace-tree.yaml +++ b/test/golden/common/pathItem/operation/responses/add/trace-tree.yaml @@ -1,3 +1,4 @@ -Left: +breakingChanges: AtPath "/test": InOperation PostMethod: ResponseCodeNotFound 500 +nonBreakingChanges: {} diff --git a/test/golden/common/pathItem/operation/responses/change/headers/mandatory/add/report.md b/test/golden/common/pathItem/operation/responses/change/headers/mandatory/add/report.md index 4211f70..6e05bde 100644 --- a/test/golden/common/pathItem/operation/responses/change/headers/mandatory/add/report.md +++ b/test/golden/common/pathItem/operation/responses/change/headers/mandatory/add/report.md @@ -1 +1,13 @@ -# No breaking changes found ✨ +# Summary + +| ⚠️ Breaking changes | [🙆 Non-breaking changes](#non-breaking-changes) | 🤷 Unsupported feature changes | +|---------------------|-------------------------------------------------|-------------------------------| +| 0 | 1 | 0 | + +# 🙆 Non-breaking changes + +## **POST** /test + +### Response code 200 + +New header was added `Test2`. diff --git a/test/golden/common/pathItem/operation/responses/change/headers/mandatory/add/trace-tree.yaml b/test/golden/common/pathItem/operation/responses/change/headers/mandatory/add/trace-tree.yaml index 5d14c1e..7d5c7cf 100644 --- a/test/golden/common/pathItem/operation/responses/change/headers/mandatory/add/trace-tree.yaml +++ b/test/golden/common/pathItem/operation/responses/change/headers/mandatory/add/trace-tree.yaml @@ -1 +1,5 @@ -Right: [] +breakingChanges: {} +nonBreakingChanges: + AtPath "/test": + InOperation PostMethod: + WithStatusCode 200: ResponseHeaderMissing "Test2" diff --git a/test/golden/common/pathItem/operation/responses/change/headers/mandatory/del/report.md b/test/golden/common/pathItem/operation/responses/change/headers/mandatory/del/report.md index ba901e8..e9aa73b 100644 --- a/test/golden/common/pathItem/operation/responses/change/headers/mandatory/del/report.md +++ b/test/golden/common/pathItem/operation/responses/change/headers/mandatory/del/report.md @@ -1,8 +1,8 @@ # Summary -| [⚠️ Breaking changes](#breaking-changes) | 🤷 Unsupported feature changes | -|------------------------------------------|-------------------------------| -| 1 | 0 | +| [⚠️ Breaking changes](#breaking-changes) | 🙆 Non-breaking changes | 🤷 Unsupported feature changes | +|------------------------------------------|------------------------|-------------------------------| +| 1 | 0 | 0 | # ⚠️ Breaking changes @@ -10,4 +10,4 @@ ### Response code 200 -New header was added `Test2`. +Header was removed `Test2`. diff --git a/test/golden/common/pathItem/operation/responses/change/headers/mandatory/del/trace-tree.yaml b/test/golden/common/pathItem/operation/responses/change/headers/mandatory/del/trace-tree.yaml index a8f6d76..b92aef2 100644 --- a/test/golden/common/pathItem/operation/responses/change/headers/mandatory/del/trace-tree.yaml +++ b/test/golden/common/pathItem/operation/responses/change/headers/mandatory/del/trace-tree.yaml @@ -1,4 +1,5 @@ -Left: +breakingChanges: AtPath "/test": InOperation PostMethod: WithStatusCode 200: ResponseHeaderMissing "Test2" +nonBreakingChanges: {} diff --git a/test/golden/common/pathItem/operation/responses/change/headers/optional/add/report.md b/test/golden/common/pathItem/operation/responses/change/headers/optional/add/report.md index 4211f70..70b7698 100644 --- a/test/golden/common/pathItem/operation/responses/change/headers/optional/add/report.md +++ b/test/golden/common/pathItem/operation/responses/change/headers/optional/add/report.md @@ -1 +1,5 @@ -# No breaking changes found ✨ +# Summary + +| ⚠️ Breaking changes | 🙆 Non-breaking changes | 🤷 Unsupported feature changes | +|---------------------|------------------------|-------------------------------| +| 0 | 0 | 0 | diff --git a/test/golden/common/pathItem/operation/responses/change/headers/optional/add/trace-tree.yaml b/test/golden/common/pathItem/operation/responses/change/headers/optional/add/trace-tree.yaml index 5d14c1e..b9b681e 100644 --- a/test/golden/common/pathItem/operation/responses/change/headers/optional/add/trace-tree.yaml +++ b/test/golden/common/pathItem/operation/responses/change/headers/optional/add/trace-tree.yaml @@ -1 +1,2 @@ -Right: [] +breakingChanges: {} +nonBreakingChanges: {} diff --git a/test/golden/common/pathItem/operation/responses/change/headers/optional/del/report.md b/test/golden/common/pathItem/operation/responses/change/headers/optional/del/report.md index 4211f70..70b7698 100644 --- a/test/golden/common/pathItem/operation/responses/change/headers/optional/del/report.md +++ b/test/golden/common/pathItem/operation/responses/change/headers/optional/del/report.md @@ -1 +1,5 @@ -# No breaking changes found ✨ +# Summary + +| ⚠️ Breaking changes | 🙆 Non-breaking changes | 🤷 Unsupported feature changes | +|---------------------|------------------------|-------------------------------| +| 0 | 0 | 0 | diff --git a/test/golden/common/pathItem/operation/responses/change/headers/optional/del/trace-tree.yaml b/test/golden/common/pathItem/operation/responses/change/headers/optional/del/trace-tree.yaml index 5d14c1e..b9b681e 100644 --- a/test/golden/common/pathItem/operation/responses/change/headers/optional/del/trace-tree.yaml +++ b/test/golden/common/pathItem/operation/responses/change/headers/optional/del/trace-tree.yaml @@ -1 +1,2 @@ -Right: [] +breakingChanges: {} +nonBreakingChanges: {} diff --git a/test/golden/common/pathItem/operation/responses/change/mediaTypeObject/add/report.md b/test/golden/common/pathItem/operation/responses/change/mediaTypeObject/add/report.md index a836e84..1a6632a 100644 --- a/test/golden/common/pathItem/operation/responses/change/mediaTypeObject/add/report.md +++ b/test/golden/common/pathItem/operation/responses/change/mediaTypeObject/add/report.md @@ -1,8 +1,8 @@ # Summary -| [⚠️ Breaking changes](#breaking-changes) | 🤷 Unsupported feature changes | -|------------------------------------------|-------------------------------| -| 1 | 0 | +| [⚠️ Breaking changes](#breaking-changes) | 🙆 Non-breaking changes | 🤷 Unsupported feature changes | +|------------------------------------------|------------------------|-------------------------------| +| 1 | 0 | 0 | # ⚠️ Breaking changes diff --git a/test/golden/common/pathItem/operation/responses/change/mediaTypeObject/add/trace-tree.yaml b/test/golden/common/pathItem/operation/responses/change/mediaTypeObject/add/trace-tree.yaml index 1051d3c..c4dd13c 100644 --- a/test/golden/common/pathItem/operation/responses/change/mediaTypeObject/add/trace-tree.yaml +++ b/test/golden/common/pathItem/operation/responses/change/mediaTypeObject/add/trace-tree.yaml @@ -1,4 +1,5 @@ -Left: +breakingChanges: AtPath "/test": InOperation PostMethod: WithStatusCode 200: ResponseMediaTypeMissing application/x-www-form-urlencoded +nonBreakingChanges: {} diff --git a/test/golden/common/pathItem/operation/responses/change/mediaTypeObject/change/report.md b/test/golden/common/pathItem/operation/responses/change/mediaTypeObject/change/report.md index 9a21882..c66da10 100644 --- a/test/golden/common/pathItem/operation/responses/change/mediaTypeObject/change/report.md +++ b/test/golden/common/pathItem/operation/responses/change/mediaTypeObject/change/report.md @@ -1,15 +1,25 @@ # Summary -| [⚠️ Breaking changes](#breaking-changes) | 🤷 Unsupported feature changes | -|------------------------------------------|-------------------------------| -| 1 | 0 | +| [⚠️ Breaking changes](#breaking-changes) | [🙆 Non-breaking changes](#non-breaking-changes) | 🤷 Unsupported feature changes | +|------------------------------------------|-------------------------------------------------|-------------------------------| +| 1 | 1 | 0 | # ⚠️ Breaking changes ## **POST** /test -### JSON Response – 200 +### 📱⬅️ JSON Response – 200 #### `$(Number)` +The type has been added. + +# 🙆 Non-breaking changes + +## **POST** /test + +### 📱⬅️ JSON Response – 200 + +#### `$(String)` + The type has been removed. diff --git a/test/golden/common/pathItem/operation/responses/change/mediaTypeObject/change/trace-tree.yaml b/test/golden/common/pathItem/operation/responses/change/mediaTypeObject/change/trace-tree.yaml index 051d29a..7f00915 100644 --- a/test/golden/common/pathItem/operation/responses/change/mediaTypeObject/change/trace-tree.yaml +++ b/test/golden/common/pathItem/operation/responses/change/mediaTypeObject/change/trace-tree.yaml @@ -1,7 +1,14 @@ -Left: +breakingChanges: AtPath "/test": InOperation PostMethod: WithStatusCode 200: ResponsePayload: PayloadSchema: OfType Number: NoContradiction +nonBreakingChanges: + AtPath "/test": + InOperation PostMethod: + WithStatusCode 200: + ResponsePayload: + PayloadSchema: + OfType String: NoContradiction diff --git a/test/golden/common/pathItem/operation/responses/change/mediaTypeObject/del/report.md b/test/golden/common/pathItem/operation/responses/change/mediaTypeObject/del/report.md index 4211f70..f3b858f 100644 --- a/test/golden/common/pathItem/operation/responses/change/mediaTypeObject/del/report.md +++ b/test/golden/common/pathItem/operation/responses/change/mediaTypeObject/del/report.md @@ -1 +1,13 @@ -# No breaking changes found ✨ +# Summary + +| ⚠️ Breaking changes | [🙆 Non-breaking changes](#non-breaking-changes) | 🤷 Unsupported feature changes | +|---------------------|-------------------------------------------------|-------------------------------| +| 0 | 1 | 0 | + +# 🙆 Non-breaking changes + +## **POST** /test + +### Response code 200 + +Media type was removed: `application/x-www-form-urlencoded`. diff --git a/test/golden/common/pathItem/operation/responses/change/mediaTypeObject/del/trace-tree.yaml b/test/golden/common/pathItem/operation/responses/change/mediaTypeObject/del/trace-tree.yaml index 5d14c1e..100fd97 100644 --- a/test/golden/common/pathItem/operation/responses/change/mediaTypeObject/del/trace-tree.yaml +++ b/test/golden/common/pathItem/operation/responses/change/mediaTypeObject/del/trace-tree.yaml @@ -1 +1,5 @@ -Right: [] +breakingChanges: {} +nonBreakingChanges: + AtPath "/test": + InOperation PostMethod: + WithStatusCode 200: ResponseMediaTypeMissing application/x-www-form-urlencoded diff --git a/test/golden/common/pathItem/operation/responses/del/report.md b/test/golden/common/pathItem/operation/responses/del/report.md index 4211f70..5d86dc4 100644 --- a/test/golden/common/pathItem/operation/responses/del/report.md +++ b/test/golden/common/pathItem/operation/responses/del/report.md @@ -1 +1,11 @@ -# No breaking changes found ✨ +# Summary + +| ⚠️ Breaking changes | [🙆 Non-breaking changes](#non-breaking-changes) | 🤷 Unsupported feature changes | +|---------------------|-------------------------------------------------|-------------------------------| +| 0 | 1 | 0 | + +# 🙆 Non-breaking changes + +## **POST** /test + +Reponse code 500 has been removed. diff --git a/test/golden/common/pathItem/operation/responses/del/trace-tree.yaml b/test/golden/common/pathItem/operation/responses/del/trace-tree.yaml index 5d14c1e..a19b676 100644 --- a/test/golden/common/pathItem/operation/responses/del/trace-tree.yaml +++ b/test/golden/common/pathItem/operation/responses/del/trace-tree.yaml @@ -1 +1,4 @@ -Right: [] +breakingChanges: {} +nonBreakingChanges: + AtPath "/test": + InOperation PostMethod: ResponseCodeNotFound 500 diff --git a/test/golden/common/property-removed-additional/a.yaml b/test/golden/common/property-removed-additional/a.yaml new file mode 100644 index 0000000..2cc1b51 --- /dev/null +++ b/test/golden/common/property-removed-additional/a.yaml @@ -0,0 +1,32 @@ +openapi: "3.0.0" +info: + version: 1.0.0 + title: Test +servers: + - url: http://localhost/ +paths: + /test: + post: + requestBody: + content: + application/json: + schema: + $ref: "#/components/schemas/Test" + responses: + "200": + description: test + content: + application/json: + schema: + $ref: "#/components/schemas/Test" +components: + schemas: + Test: + required: + - property1 + - property2 + properties: + property1: + type: string + property2: + type: number diff --git a/test/golden/common/property-removed-additional/b.yaml b/test/golden/common/property-removed-additional/b.yaml new file mode 100644 index 0000000..3e702c8 --- /dev/null +++ b/test/golden/common/property-removed-additional/b.yaml @@ -0,0 +1,29 @@ +openapi: "3.0.0" +info: + version: 1.0.0 + title: Test +servers: + - url: http://localhost/ +paths: + /test: + post: + requestBody: + content: + application/json: + schema: + $ref: "#/components/schemas/Test" + responses: + "200": + description: test + content: + application/json: + schema: + $ref: "#/components/schemas/Test" +components: + schemas: + Test: + required: + - property1 + properties: + property1: + type: string diff --git a/test/golden/common/property-removed-additional/report.md b/test/golden/common/property-removed-additional/report.md new file mode 100644 index 0000000..ab08c6e --- /dev/null +++ b/test/golden/common/property-removed-additional/report.md @@ -0,0 +1,25 @@ +# Summary + +| [⚠️ Breaking changes](#breaking-changes) | [🙆 Non-breaking changes](#non-breaking-changes) | 🤷 Unsupported feature changes | +|------------------------------------------|-------------------------------------------------|-------------------------------| +| 1 | 1 | 0 | + +# ⚠️ Breaking changes + +## **POST** /test + +### 📱⬅️ JSON Response – 200 + +#### `$(Object)` + +Property `property2` may not be present. + +# 🙆 Non-breaking changes + +## **POST** /test + +### 📱➡️ JSON Request + +#### `$(Object)` + +Property `property2` may not be present. diff --git a/test/golden/common/property-removed-additional/trace-tree.yaml b/test/golden/common/property-removed-additional/trace-tree.yaml new file mode 100644 index 0000000..3755e39 --- /dev/null +++ b/test/golden/common/property-removed-additional/trace-tree.yaml @@ -0,0 +1,14 @@ +breakingChanges: + AtPath "/test": + InOperation PostMethod: + WithStatusCode 200: + ResponsePayload: + PayloadSchema: + OfType Object: PropertyNowRequired "property2" +nonBreakingChanges: + AtPath "/test": + InOperation PostMethod: + InRequest: + InPayload: + PayloadSchema: + OfType Object: PropertyNowRequired "property2" diff --git a/test/golden/common/property-removed/report.md b/test/golden/common/property-removed/report.md index d55e815..ad13022 100644 --- a/test/golden/common/property-removed/report.md +++ b/test/golden/common/property-removed/report.md @@ -1,21 +1,37 @@ # Summary -| [⚠️ Breaking changes](#breaking-changes) | 🤷 Unsupported feature changes | -|------------------------------------------|-------------------------------| -| 2 | 0 | +| [⚠️ Breaking changes](#breaking-changes) | [🙆 Non-breaking changes](#non-breaking-changes) | 🤷 Unsupported feature changes | +|------------------------------------------|-------------------------------------------------|-------------------------------| +| 2 | 2 | 0 | # ⚠️ Breaking changes ## **POST** /test -### JSON Request +### 📱➡️ JSON Request #### `$(Object)` Property `property2` has been removed. -### JSON Response – 200 +### 📱⬅️ JSON Response – 200 #### `$(Object)` -Property `property2` has become required. +Property `property2` may not be present. + +# 🙆 Non-breaking changes + +## **POST** /test + +### 📱➡️ JSON Request + +#### `$(Object)` + +Property `property2` may not be present. + +### 📱⬅️ JSON Response – 200 + +#### `$(Object)` + +Property `property2` has been removed. diff --git a/test/golden/common/property-removed/trace-tree.yaml b/test/golden/common/property-removed/trace-tree.yaml index db439b7..0741f65 100644 --- a/test/golden/common/property-removed/trace-tree.yaml +++ b/test/golden/common/property-removed/trace-tree.yaml @@ -1,4 +1,4 @@ -Left: +breakingChanges: AtPath "/test": InOperation PostMethod: InRequest: @@ -9,3 +9,14 @@ Left: ResponsePayload: PayloadSchema: OfType Object: PropertyNowRequired "property2" +nonBreakingChanges: + AtPath "/test": + InOperation PostMethod: + InRequest: + InPayload: + PayloadSchema: + OfType Object: PropertyNowRequired "property2" + WithStatusCode 200: + ResponsePayload: + PayloadSchema: + OfType Object: UnexpectedProperty "property2" diff --git a/test/golden/common/property-required/report.md b/test/golden/common/property-required/report.md index 943b3f5..66c038c 100644 --- a/test/golden/common/property-required/report.md +++ b/test/golden/common/property-required/report.md @@ -1,14 +1,24 @@ # Summary -| [⚠️ Breaking changes](#breaking-changes) | 🤷 Unsupported feature changes | -|------------------------------------------|-------------------------------| -| 1 | 0 | +| [⚠️ Breaking changes](#breaking-changes) | [🙆 Non-breaking changes](#non-breaking-changes) | 🤷 Unsupported feature changes | +|------------------------------------------|-------------------------------------------------|-------------------------------| +| 1 | 1 | 0 | # ⚠️ Breaking changes ## **POST** /test -### JSON Request +### 📱➡️ JSON Request + +#### `$(Object)` + +Property `property2` has become required. + +# 🙆 Non-breaking changes + +## **POST** /test + +### 📱⬅️ JSON Response – 200 #### `$(Object)` diff --git a/test/golden/common/property-required/trace-tree.yaml b/test/golden/common/property-required/trace-tree.yaml index 10b4293..949ffb5 100644 --- a/test/golden/common/property-required/trace-tree.yaml +++ b/test/golden/common/property-required/trace-tree.yaml @@ -1,7 +1,14 @@ -Left: +breakingChanges: AtPath "/test": InOperation PostMethod: InRequest: InPayload: PayloadSchema: OfType Object: PropertyNowRequired "property2" +nonBreakingChanges: + AtPath "/test": + InOperation PostMethod: + WithStatusCode 200: + ResponsePayload: + PayloadSchema: + OfType Object: PropertyNowRequired "property2" diff --git a/test/golden/common/recursive/report.md b/test/golden/common/recursive/report.md index 4211f70..5dfc26f 100644 --- a/test/golden/common/recursive/report.md +++ b/test/golden/common/recursive/report.md @@ -1 +1,19 @@ -# No breaking changes found ✨ +# Summary + +| ⚠️ Breaking changes | [🙆 Non-breaking changes](#non-breaking-changes) | 🤷 Unsupported feature changes | +|---------------------|-------------------------------------------------|-------------------------------| +| 0 | 1 | 0 | + +# 🙆 Non-breaking changes + +## **GET** /api/foo + +### 📱⬅️ JSON Response – 200 + +#### `$.leaf.value.foo(String)` + +The following enum value has been removed: + +``` json +"a" +``` diff --git a/test/golden/common/recursive/trace-tree.yaml b/test/golden/common/recursive/trace-tree.yaml index 5d14c1e..9ce3f0d 100644 --- a/test/golden/common/recursive/trace-tree.yaml +++ b/test/golden/common/recursive/trace-tree.yaml @@ -1 +1,14 @@ -Right: [] +breakingChanges: {} +nonBreakingChanges: + AtPath "/api/foo": + InOperation GetMethod: + WithStatusCode 200: + ResponsePayload: + PayloadSchema: + OfType Object: + InProperty "leaf": + OfType Object: + InProperty "value": + OfType Object: + InProperty "foo": + OfType String: NoMatchingEnum (String "a") diff --git a/test/golden/common/security-scheme/report.md b/test/golden/common/security-scheme/report.md index 4d2c023..b711c46 100644 --- a/test/golden/common/security-scheme/report.md +++ b/test/golden/common/security-scheme/report.md @@ -1,8 +1,8 @@ # Summary -| [⚠️ Breaking changes](#breaking-changes) | 🤷 Unsupported feature changes | -|------------------------------------------|-------------------------------| -| 2 | 0 | +| [⚠️ Breaking changes](#breaking-changes) | [🙆 Non-breaking changes](#non-breaking-changes) | 🤷 Unsupported feature changes | +|------------------------------------------|-------------------------------------------------|-------------------------------| +| 2 | 1 | 0 | # ⚠️ Breaking changes @@ -21,3 +21,13 @@ Security scheme has been removed. #### oauth Security scheme has been removed. + +# 🙆 Non-breaking changes + +## **POST** /oauth/check + +### Security requirement 0 + +#### spa-oauth + +Security scheme has been added. diff --git a/test/golden/common/security-scheme/trace-tree.yaml b/test/golden/common/security-scheme/trace-tree.yaml index e2cc7ee..26290d0 100644 --- a/test/golden/common/security-scheme/trace-tree.yaml +++ b/test/golden/common/security-scheme/trace-tree.yaml @@ -1,4 +1,4 @@ -Left: +breakingChanges: AtPath "/oauth/sign_out": InOperation GetMethod: SecurityRequirementStep 1: @@ -7,3 +7,8 @@ Left: InOperation PostMethod: SecurityRequirementStep 0: SecuritySchemeStep "oauth": SecuritySchemeNotMatched +nonBreakingChanges: + AtPath "/oauth/check": + InOperation PostMethod: + SecurityRequirementStep 0: + SecuritySchemeStep "spa-oauth": SecuritySchemeNotMatched diff --git a/test/golden/common/servers/report.md b/test/golden/common/servers/report.md index 2880c9f..d14292e 100644 --- a/test/golden/common/servers/report.md +++ b/test/golden/common/servers/report.md @@ -1,8 +1,8 @@ # Summary -| [⚠️ Breaking changes](#breaking-changes) | 🤷 Unsupported feature changes | -|------------------------------------------|-------------------------------| -| 3 | 0 | +| [⚠️ Breaking changes](#breaking-changes) | [🙆 Non-breaking changes](#non-breaking-changes) | 🤷 Unsupported feature changes | +|------------------------------------------|-------------------------------------------------|-------------------------------| +| 3 | 1 | 0 | # ⚠️ Breaking changes @@ -17,3 +17,11 @@ The server was removed. Enum value `a` has been removed. A variable has been changed from being open to being closed. + +# 🙆 Non-breaking changes + +## **GET** /pets + +### Server `http://{x}variable.path/{y}/{openVariable1}/{openVariable2}` + +Enum value `bbb` has been added. diff --git a/test/golden/common/servers/trace-tree.yaml b/test/golden/common/servers/trace-tree.yaml index 2b0d629..b504af6 100644 --- a/test/golden/common/servers/trace-tree.yaml +++ b/test/golden/common/servers/trace-tree.yaml @@ -1,7 +1,12 @@ -Left: +breakingChanges: AtPath "/pets": InOperation GetMethod: InServer "http://{x}variable.path/{y}/{openVariable1}/{openVariable2}": - EnumValueNotConsumed 1 "a" - ConsumerNotOpen 7 InServer "http://missing.url": ServerNotMatched +nonBreakingChanges: + AtPath "/pets": + InOperation GetMethod: + InServer "http://{x}variable.path/{y}/{openVariable1}/{openVariable2}": EnumValueNotConsumed + 3 "bbb" diff --git a/test/golden/common/unguarded-recursive/report.md b/test/golden/common/unguarded-recursive/report.md index 1aea61d..43fd067 100644 --- a/test/golden/common/unguarded-recursive/report.md +++ b/test/golden/common/unguarded-recursive/report.md @@ -1,13 +1,13 @@ # Summary -| ⚠️ Breaking changes | [🤷 Unsupported feature changes](#unsupported-changes) | -|---------------------|-------------------------------------------------------| -| 0 | 1 | +| ⚠️ Breaking changes | 🙆 Non-breaking changes | [🤷 Unsupported feature changes](#unsupported-changes) | +|---------------------|------------------------|-------------------------------------------------------| +| 0 | 0 | 1 | # 🤷 Unsupported feature changes ## **GET** /api/foo -### JSON Response – 200 +### 📱⬅️ JSON Response – 200 Encountered recursion that is too complex for OpenApi Diff to untangle. diff --git a/test/golden/common/unguarded-recursive/trace-tree.yaml b/test/golden/common/unguarded-recursive/trace-tree.yaml index 590caf5..beb3b6b 100644 --- a/test/golden/common/unguarded-recursive/trace-tree.yaml +++ b/test/golden/common/unguarded-recursive/trace-tree.yaml @@ -1,4 +1,10 @@ -Left: +breakingChanges: + AtPath "/api/foo": + InOperation GetMethod: + WithStatusCode 200: + ResponsePayload: + PayloadSchema: UnguardedRecursion +nonBreakingChanges: AtPath "/api/foo": InOperation GetMethod: WithStatusCode 200: