Added JSON Path jets (#75)

* Updated ConstructReportJet variables

* changed ConstructReportJet yet more

* Added support for Union in jets

* Extracted jet args

* observeJetShowErrs'

* Complex Arguments

* Added branching

* Added JSON path jets

* Simplified things

* Better type rendering in report
This commit is contained in:
iko 2021-06-08 17:57:13 +03:00 committed by GitHub
parent 218336b11e
commit 5fd5a1cd78
No known key found for this signature in database
GPG Key ID: 4AEE18F83AFDEB23
13 changed files with 204 additions and 60 deletions

1
.gitignore vendored
View File

@ -2,3 +2,4 @@
TAGS TAGS
.vscode .vscode
.dir-locals.el .dir-locals.el
test/golden/common/prod

View File

@ -64,6 +64,9 @@ common common-options
, yaml , yaml
, hashable , hashable
, pandoc-types , pandoc-types
, open-union
, type-fun
, free
default-extensions: ApplicativeDo default-extensions: ApplicativeDo
, BangPatterns , BangPatterns
@ -137,6 +140,7 @@ library
, OpenAPI.Checker.Validate.SecurityScheme , OpenAPI.Checker.Validate.SecurityScheme
, OpenAPI.Checker.Validate.OAuth2Flows , OpenAPI.Checker.Validate.OAuth2Flows
, OpenAPI.Checker.Report , OpenAPI.Checker.Report
, Data.OpenUnion.Extra
executable openapi-diff executable openapi-diff
import: common-options import: common-options

View File

@ -0,0 +1,43 @@
module Data.OpenUnion.Extra
( (@@>)
, TryLiftUnion (..)
, pattern SingletonUnion
)
where
import Control.Applicative
import Data.Dynamic
import Data.OpenUnion.Internal
import Data.Typeable
import TypeFun.Data.List hiding (Union)
class TryLiftUnion xs where
tryLiftUnion :: (Alternative m, Typeable x) => x -> m (Union xs)
instance TryLiftUnion '[] where
tryLiftUnion _ = empty
instance
(Typeable y, SubList ys (y : ys), TryLiftUnion ys)
=> TryLiftUnion (y ': ys)
where
tryLiftUnion (x :: x) = case eqT @x @y of
Nothing -> reUnion <$> tryLiftUnion @ys x
Just Refl -> pure $ liftUnion x
-- | Like '@>', but enforces a specific type list order.
-- (Useful for deconstruction-directed type inference.)
(@@>) :: Typeable a => (a -> b) -> (Union xs -> b) -> Union (a ': xs) -> b
r @@> l = either l r . restrict'
where
restrict' :: Typeable a => Union (a ': aa) -> Either (Union aa) a
restrict' (Union d) = maybe (Left $ Union d) Right $ fromDynamic d
{-# INLINE (@@>) #-}
infixr 2 @@>
pattern SingletonUnion :: (Typeable a, Elem a s) => a -> Union s
pattern SingletonUnion x <-
((\(Union y) -> fromDynamic y) -> Just x)
where
SingletonUnion x = liftUnion x

View File

@ -3,14 +3,22 @@ module OpenAPI.Checker.Report
) )
where where
import Control.Applicative
import Control.Monad.Free hiding (unfoldM)
import Control.Monad.Reader import Control.Monad.Reader
import Control.Monad.Writer import Control.Monad.Writer
import Data.Either
import Data.Foldable import Data.Foldable
import Data.Function
import Data.Functor import Data.Functor
import Data.List.NonEmpty
import qualified Data.List.NonEmpty as NE
import qualified Data.Map as M import qualified Data.Map as M
import Data.Maybe import Data.Maybe
import Data.OpenUnion
import Data.OpenUnion.Extra
import Data.Text (Text)
import qualified Data.Text as T import qualified Data.Text as T
import Data.Traversable
import Data.TypeRepMap hiding (empty) import Data.TypeRepMap hiding (empty)
import Data.Typeable import Data.Typeable
import OpenAPI.Checker.Behavior import OpenAPI.Checker.Behavior
@ -18,6 +26,7 @@ import OpenAPI.Checker.Paths
import OpenAPI.Checker.PathsPrefixTree hiding (empty) import OpenAPI.Checker.PathsPrefixTree hiding (empty)
import qualified OpenAPI.Checker.PathsPrefixTree as P hiding (empty) import qualified OpenAPI.Checker.PathsPrefixTree as P hiding (empty)
import OpenAPI.Checker.Validate.OpenApi import OpenAPI.Checker.Validate.OpenApi
import OpenAPI.Checker.Validate.Schema
import Text.Pandoc.Builder import Text.Pandoc.Builder
generateReport :: Either (P.PathsPrefixTree Behave AnIssue 'APILevel) () -> Pandoc generateReport :: Either (P.PathsPrefixTree Behave AnIssue 'APILevel) () -> Pandoc
@ -25,13 +34,13 @@ generateReport (Right ()) = doc $ header 1 "No breaking changes found ✨"
generateReport (Left errs) = doc $ runReportMonad jets $ showErrs errs generateReport (Left errs) = doc $ runReportMonad jets $ showErrs errs
data ReportState = ReportState data ReportState = ReportState
{ sourceJets :: [SomeReportJet Behave] { sourceJets :: [ReportJet' Behave Inlines]
, headerLevel :: Int , headerLevel :: Int
} }
type ReportMonad = ReaderT ReportState (Writer Blocks) type ReportMonad = ReaderT ReportState (Writer Blocks)
runReportMonad :: [SomeReportJet Behave] -> ReportMonad () -> Blocks runReportMonad :: [ReportJet' Behave Inlines] -> ReportMonad () -> Blocks
runReportMonad jts = runReportMonad jts =
execWriter execWriter
. flip . flip
@ -46,11 +55,11 @@ smartHeader i = do
h <- asks headerLevel h <- asks headerLevel
tell $ header h i tell $ header h i
showErrs :: Typeable a => P.PathsPrefixTree Behave AnIssue a -> ReportMonad () showErrs :: P.PathsPrefixTree Behave AnIssue a -> ReportMonad ()
showErrs x@(P.PathsPrefixNode currentIssues _) = do showErrs x@(P.PathsPrefixNode currentIssues _) = do
jts <- asks sourceJets jts <- asks sourceJets
for_ currentIssues $ \(AnIssue i) -> tell . describeIssue $ i for_ currentIssues $ \(AnIssue i) -> tell . describeIssue $ i
unfoldM x (observeSomeJetShowErrs <$> jts) $ \(P.PathsPrefixNode _ subIssues) -> do unfoldM x (observeJetShowErrs <$> jts) $ \(P.PathsPrefixNode _ subIssues) -> do
for_ subIssues $ \(WrapTypeable (AStep m)) -> for_ subIssues $ \(WrapTypeable (AStep m)) ->
for_ (M.toList m) $ \(bhv, subErrors) -> do for_ (M.toList m) $ \(bhv, subErrors) -> do
unless (P.null subErrors) $ do unless (P.null subErrors) $ do
@ -63,74 +72,140 @@ unfoldM a (f : ff) g = do
a' <- f a a' <- f a
unfoldM a' ff g unfoldM a' ff g
observeSomeJetShowErrs observeJetShowErrs
:: forall a. :: ReportJet' Behave Inlines
Typeable a
=> SomeReportJet Behave
-> P.PathsPrefixTree Behave AnIssue a -> P.PathsPrefixTree Behave AnIssue a
-> ReportMonad (P.PathsPrefixTree Behave AnIssue a) -> ReportMonad (P.PathsPrefixTree Behave AnIssue a)
observeSomeJetShowErrs (SomeReportJet (Proxy :: Proxy a') f) x observeJetShowErrs jet p = case observeJetShowErrs' jet p of
| Just Refl <- eqT @a @a' = observeJetShowErrs f x Just m -> m
observeSomeJetShowErrs _ x = pure x Nothing -> pure p
observeJetShowErrs :: ReportJet Behave a -> P.PathsPrefixTree Behave AnIssue a -> ReportMonad (P.PathsPrefixTree Behave AnIssue a) observeJetShowErrs'
observeJetShowErrs jet (P.PathsPrefixNode currentIssues subIssues) = do :: forall a.
rest <- fmap (fold . join) $ ReportJet' Behave Inlines
for subIssues $ \(WrapTypeable (AStep m)) -> fmap catMaybes $ -> P.PathsPrefixTree Behave AnIssue a
for (M.toList m) $ \(bhv, subErrs) -> -> Maybe (ReportMonad (P.PathsPrefixTree Behave AnIssue a))
case applyReportJet jet bhv of observeJetShowErrs' (ReportJet jet) (P.PathsPrefixNode currentIssues subIssues) =
Just (Left h) -> do let results =
smartHeader h subIssues >>= \(WrapTypeable (AStep m)) ->
incrementHeaders $ showErrs subErrs M.toList m <&> \(bhv, subErrs) ->
return Nothing maybe (Left $ embed (step bhv) subErrs) Right . listToMaybe $
Just (Right jet') -> do jet @_ @_ @[] bhv
rest <- observeJetShowErrs jet' subErrs & mapMaybe
return $ Just $ embed (step bhv) rest (\case
Nothing -> return $ Just $ embed (step bhv) subErrs Free jet' -> fmap (embed $ step bhv) <$> observeJetShowErrs' jet' subErrs
return $ PathsPrefixNode currentIssues mempty <> rest Pure h -> Just $ do
smartHeader h
incrementHeaders $ showErrs subErrs
return mempty)
in (fmap . fmap) (PathsPrefixNode currentIssues mempty <>) $
if any isRight results
then
Just $
catMapM
(\case
Left e -> pure e
Right m -> m)
results
else Nothing
catMapM :: (Monad m, Monoid b) => (a -> m b) -> [a] -> m b
catMapM f xs = mconcat <$> mapM f xs
-- | A "jet" is a way of simplifying expressions from "outside". The "jetted" -- | A "jet" is a way of simplifying expressions from "outside". The "jetted"
-- expressions should still be completely valid and correct without the jets. -- expressions should still be completely valid and correct without the jets.
-- Jets just make the expression more "optimized" by identifying patterns and -- Jets just make the expression more "optimized" by identifying patterns and
-- replacing the expressions with "better" ones that have the same sematics. -- replacing the expressions with "better" ones that have the same sematics.
-- --
-- The tem "jet" in this context was introduced in the Urbit project: -- The term "jet" in this context was introduced in the Urbit project:
-- https://urbit.org/docs/vere/jetting/ -- https://urbit.org/docs/vere/jetting/
-- --
-- The pattern fits well for simplifying 'Behaviour' tree paths. -- The pattern fits well for simplifying 'Behaviour' tree paths.
class ConstructReportJet f a b c where class ConstructReportJet x f where
constructReportJet :: (f a b -> c) -> ReportJet f a constructReportJet :: x -> ReportJetResult f Inlines
instance (ConstructReportJet f b c d, Typeable b) => ConstructReportJet f a b (f b c -> d) where instance (ConstructReportJet b f, JetArg a) => ConstructReportJet (a -> b) f where
constructReportJet f = ReportJet Proxy $ \x -> constructReportJet $ f x constructReportJet f = Free (fmap f <$> consumeJetArg @a) >>= constructReportJet
instance Typeable b => ConstructReportJet f a b Inlines where instance ConstructReportJet Inlines f where
constructReportJet f = TerminalJet Proxy f constructReportJet x = Pure x
constructSomeReportJet :: (ConstructReportJet f a b c, Typeable a) => (f a b -> c) -> SomeReportJet f class JetArg a where
constructSomeReportJet = SomeReportJet Proxy . constructReportJet consumeJetArg :: ReportJet' f a
data ReportJet f a where instance Typeable (f a b) => JetArg (f a b) where
ReportJet :: Typeable b => Proxy b -> (f a b -> ReportJet f b) -> ReportJet f a consumeJetArg =
TerminalJet :: Typeable b => Proxy b -> (f a b -> Inlines) -> ReportJet f a ReportJet $ \(x :: x) ->
case eqT @(f a b) @x of
Nothing -> empty
Just Refl -> pure $ Pure x
data SomeReportJet f where instance TryLiftUnion xs => JetArg (Union xs) where
SomeReportJet :: Typeable a => Proxy a -> ReportJet f a -> SomeReportJet f consumeJetArg = ReportJet $ fmap Pure . tryLiftUnion
applyReportJet :: forall f a b. Typeable b => ReportJet f a -> f a b -> Maybe (Either Inlines (ReportJet f b)) instance JetArg x => JetArg (NonEmpty x) where
applyReportJet (TerminalJet (Proxy :: Proxy b') f) x = eqT @b @b' <&> \Refl -> Left $ f x consumeJetArg =
applyReportJet (ReportJet (Proxy :: Proxy b') f) x = eqT @b @b' <&> \Refl -> Right $ f x let (ReportJet f) = (consumeJetArg @x)
in ReportJet $ \a -> do
u <- f a
pure (u >>= \y -> Free $ fmap (NE.cons y) <$> consumeJetArg)
<|> pure (pure <$> u)
type ReportJetResult f = Free (ReportJet f)
-- Not a true 'Applicative'
newtype ReportJet f x = ReportJet (forall a b m. (Typeable (f a b), Alternative m, Monad m) => f a b -> m x)
deriving stock (Functor)
type ReportJet' f a = ReportJet f (Free (ReportJet f) a)
incrementHeaders :: ReportMonad x -> ReportMonad x incrementHeaders :: ReportMonad x -> ReportMonad x
incrementHeaders m = do incrementHeaders m = do
l <- asks headerLevel l <- asks headerLevel
local (\x -> x {headerLevel = l + 1}) m local (\x -> x {headerLevel = l + 1}) m
jets :: [SomeReportJet Behave] jets :: [ReportJet' Behave Inlines]
jets = jets =
[ constructSomeReportJet $ \p@(AtPath _) op@(InOperation _) -> unwrapReportJetResult
strong (describeBehaviour op) <> " " <> describeBehaviour p :: Inlines <$> [ constructReportJet jsonPathJet
, constructSomeReportJet $ \InRequest InPayload PayloadSchema -> "JSON Request" :: Inlines , constructReportJet $ \p@(AtPath _) op@(InOperation _) ->
, constructSomeReportJet $ \(WithStatusCode c) ResponsePayload PayloadSchema -> strong (describeBehaviour op) <> " " <> describeBehaviour p :: Inlines
"JSON Response " <> str (T.pack . show $ c) :: Inlines , constructReportJet $ \InRequest InPayload PayloadSchema -> "JSON Request" :: Inlines
] , constructReportJet $ \(WithStatusCode c) ResponsePayload PayloadSchema ->
"JSON Response " <> str (T.pack . show $ c) :: Inlines
]
where
unwrapReportJetResult :: ReportJetResult Behave x -> ReportJet' Behave x
unwrapReportJetResult (Pure _) = error "There really shouldn't be any results here."
unwrapReportJetResult (Free f) = f
jsonPathJet
:: NonEmpty
( Union
'[ Behave 'SchemaLevel 'TypedSchemaLevel
, Behave 'TypedSchemaLevel 'SchemaLevel
]
)
-> Inlines
jsonPathJet x = code $ "$" <> showParts (NE.toList x)
where
showParts
:: [ Union
'[ Behave 'SchemaLevel 'TypedSchemaLevel
, Behave 'TypedSchemaLevel 'SchemaLevel
]
]
-> Text
showParts [] = mempty
showParts (SingletonUnion (OfType Object) : xs@((SingletonUnion (InProperty _)) : _)) = showParts xs
showParts (SingletonUnion (OfType Object) : xs@((SingletonUnion InAdditionalProperty) : _)) = showParts xs
showParts (SingletonUnion (OfType Array) : xs@(SingletonUnion InItems : _)) = showParts xs
showParts (y : ys) =
((\(OfType t) -> "(" <> describeJSONType t <> ")")
@@> (\case
InItems -> "[*]"
InProperty p -> "." <> p
InAdditionalProperty -> ".*")
@@> typesExhausted)
y
<> showParts ys

View File

@ -10,6 +10,8 @@ module OpenAPI.Checker.Validate.Schema
, Bound (..) , Bound (..)
, schemaToFormula , schemaToFormula
, foldLattice , foldLattice
, Behave (..)
, describeJSONType
) )
where where
@ -39,6 +41,7 @@ import Data.Ord
import Data.Ratio import Data.Ratio
import Data.Scientific import Data.Scientific
import qualified Data.Set as S import qualified Data.Set as S
import Data.String
import Data.Text (Text) import Data.Text (Text)
import qualified Data.Text as T hiding (singleton) import qualified Data.Text as T hiding (singleton)
import qualified Data.Text.Encoding as T import qualified Data.Text.Encoding as T
@ -1110,7 +1113,7 @@ instance Behavable 'SchemaLevel 'TypedSchemaLevel where
describeBehaviour (OfType t) = describeJSONType t describeBehaviour (OfType t) = describeJSONType t
describeJSONType :: JsonType -> Inlines describeJSONType :: IsString s => JsonType -> s
describeJSONType = \case describeJSONType = \case
Null -> "Null" Null -> "Null"
Boolean -> "Boolean" Boolean -> "Boolean"

View File

@ -1 +1,5 @@
resolver: nightly-2021-06-01 resolver: nightly-2021-06-01
extra-deps:
- open-union-0.4.0.0
- type-fun-0.1.3

View File

@ -3,7 +3,21 @@
# For more information, please see the documentation at: # For more information, please see the documentation at:
# https://docs.haskellstack.org/en/stable/lock_files # https://docs.haskellstack.org/en/stable/lock_files
packages: [] packages:
- completed:
hackage: open-union-0.4.0.0@sha256:1c8f8090054b0974e95e44bed88e74fff956ba2120aade6e8deea92d65ef5e49,3503
pantry-tree:
size: 329
sha256: e01838ec41f7aa2a97aa2c3586c8188c4ad093ba0b2be41229ab7b8dbd33869e
original:
hackage: open-union-0.4.0.0
- completed:
hackage: type-fun-0.1.3@sha256:336b851757792f201078043210aec180021ac052f0955c71fa330a5fe11b0604,1765
pantry-tree:
size: 583
sha256: b977d42525f0b4223959918d18e7905085283e937493c395077b608cd19b42c1
original:
hackage: type-fun-0.1.3
snapshots: snapshots:
- completed: - completed:
size: 587963 size: 587963

View File

@ -2,6 +2,6 @@
## JSON Request ## JSON Request
### Number ### `$(Number)`
Expected upper bound 3.0 inclusive but but found 2.0 inclusive. Expected upper bound 3.0 inclusive but but found 2.0 inclusive.

View File

@ -4,6 +4,6 @@
### JSON Schema ### JSON Schema
#### String #### `$(String)`
Expected the type to be allowed, but it wasn't. Expected the type to be allowed, but it wasn't.

View File

@ -2,6 +2,6 @@
## JSON Request ## JSON Request
### String ### `$(String)`
Expected the type to be allowed, but it wasn't. Expected the type to be allowed, but it wasn't.

View File

@ -2,6 +2,6 @@
## JSON Response 200 ## JSON Response 200
### Number ### `$(Number)`
Expected the type to be allowed, but it wasn't. Expected the type to be allowed, but it wasn't.

View File

@ -2,12 +2,12 @@
## JSON Request ## JSON Request
### Object ### `$(Object)`
Expected the property `property2` to be allowed, but it wasn't. Expected the property `property2` to be allowed, but it wasn't.
## JSON Response 200 ## JSON Response 200
### Object ### `$(Object)`
Don't have a required property `property2`. Don't have a required property `property2`.

View File

@ -2,6 +2,6 @@
## JSON Request ## JSON Request
### Object ### `$(Object)`
Don't have a required property `property2`. Don't have a required property `property2`.