compaREST-0.1.0.1: Compatibility checker for OpenAPI
Safe HaskellNone
LanguageHaskell2010

Data.OpenApi.Compare.Behavior

Synopsis

Documentation

class (Ord (Behave a b), Show (Behave a b)) => Behavable (a :: BehaviorLevel) (b :: BehaviorLevel) where Source #

Associated Types

data Behave a b Source #

Instances

Instances details
Behavable 'APILevel 'PathLevel Source # 
Instance details

Defined in Data.OpenApi.Compare.Validate.Operation

Associated Types

data Behave 'APILevel 'PathLevel Source #

Behavable 'SecurityRequirementLevel 'SecuritySchemeLevel Source # 
Instance details

Defined in Data.OpenApi.Compare.Validate.OAuth2Flows

Behavable 'PathLevel 'OperationLevel Source # 
Instance details

Defined in Data.OpenApi.Compare.Validate.Operation

Associated Types

data Behave 'PathLevel 'OperationLevel Source #

Behavable 'OperationLevel 'ServerLevel Source # 
Instance details

Defined in Data.OpenApi.Compare.Validate.Server

Associated Types

data Behave 'OperationLevel 'ServerLevel Source #

Behavable 'OperationLevel 'SecurityRequirementLevel Source # 
Instance details

Defined in Data.OpenApi.Compare.Validate.Operation

Behavable 'OperationLevel 'PathFragmentLevel Source # 
Instance details

Defined in Data.OpenApi.Compare.Validate.Operation

Behavable 'OperationLevel 'RequestLevel Source # 
Instance details

Defined in Data.OpenApi.Compare.Validate.Operation

Associated Types

data Behave 'OperationLevel 'RequestLevel Source #

Behavable 'OperationLevel 'ResponseLevel Source # 
Instance details

Defined in Data.OpenApi.Compare.Validate.MediaTypeObject

Associated Types

data Behave 'OperationLevel 'ResponseLevel Source #

Behavable 'OperationLevel 'CallbackLevel Source # 
Instance details

Defined in Data.OpenApi.Compare.Validate.Operation

Associated Types

data Behave 'OperationLevel 'CallbackLevel Source #

Behavable 'PathFragmentLevel 'SchemaLevel Source # 
Instance details

Defined in Data.OpenApi.Compare.Validate.Param

Behavable 'RequestLevel 'PayloadLevel Source # 
Instance details

Defined in Data.OpenApi.Compare.Validate.RequestBody

Associated Types

data Behave 'RequestLevel 'PayloadLevel Source #

Behavable 'ResponseLevel 'HeaderLevel Source # 
Instance details

Defined in Data.OpenApi.Compare.Validate.Responses

Associated Types

data Behave 'ResponseLevel 'HeaderLevel Source #

Behavable 'ResponseLevel 'PayloadLevel Source # 
Instance details

Defined in Data.OpenApi.Compare.Validate.Responses

Associated Types

data Behave 'ResponseLevel 'PayloadLevel Source #

Behavable 'HeaderLevel 'SchemaLevel Source # 
Instance details

Defined in Data.OpenApi.Compare.Validate.Header

Associated Types

data Behave 'HeaderLevel 'SchemaLevel Source #

Behavable 'PayloadLevel 'SchemaLevel Source # 
Instance details

Defined in Data.OpenApi.Compare.Validate.MediaTypeObject

Associated Types

data Behave 'PayloadLevel 'SchemaLevel Source #

Behavable 'SchemaLevel 'TypedSchemaLevel Source # 
Instance details

Defined in Data.OpenApi.Compare.Validate.Schema.Issues

Associated Types

data Behave 'SchemaLevel 'TypedSchemaLevel Source #

Behavable 'TypedSchemaLevel 'SchemaLevel Source # 
Instance details

Defined in Data.OpenApi.Compare.Validate.Schema.Issues

Associated Types

data Behave 'TypedSchemaLevel 'SchemaLevel Source #

Behavable 'TypedSchemaLevel 'TypedSchemaLevel Source # 
Instance details

Defined in Data.OpenApi.Compare.Validate.Schema.Issues

data IssueKind Source #

Constructors

CertainIssue

This is certainly an issue, we can demonstrate a "counterexample"

ProbablyIssue

Change looks breaking but we don't have a complete comprehension of the problem

Unsupported

We don't really support this feature at all, outside structural comparison

Comment

This is not an issue in itself, but a clarifying comment providing context for some other issues

SchemaInvalid

We detected an issue with one of the input schemata itself

class (Typeable l, Ord (Issue l), Show (Issue l)) => Issuable (l :: BehaviorLevel) where Source #

Minimal complete definition

describeIssue, issueKind

Associated Types

data Issue l :: Type Source #

Methods

describeIssue :: Orientation -> Issue l -> Blocks Source #

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).

If _consumer_ doesn't have something, the element was "removed". If _producer_ doesn't have something, the element was "added".

issueKind :: Issue l -> IssueKind Source #

relatedIssues :: Issue l -> Issue l -> Bool Source #

An equivalence relation designating whether two issues are talking about the aspect of the schema. This is used to remove duplicates from the "reverse" error tree we get when we look for non-breaking changes. Generally if checking X->Y raises issue I, and checking Y->X raises issue J, I and J should be related.

Instances

Instances details
Issuable 'APILevel Source # 
Instance details

Defined in Data.OpenApi.Compare.Validate.Operation

Associated Types

data Issue 'APILevel Source #

Issuable 'ServerLevel Source # 
Instance details

Defined in Data.OpenApi.Compare.Validate.Server

Associated Types

data Issue 'ServerLevel Source #

Issuable 'SecurityRequirementLevel Source # 
Instance details

Defined in Data.OpenApi.Compare.Validate.OAuth2Flows

Associated Types

data Issue 'SecurityRequirementLevel Source #

Issuable 'SecuritySchemeLevel Source # 
Instance details

Defined in Data.OpenApi.Compare.Validate.OAuth2Flows

Associated Types

data Issue 'SecuritySchemeLevel Source #

Issuable 'PathLevel Source # 
Instance details

Defined in Data.OpenApi.Compare.Validate.Operation

Associated Types

data Issue 'PathLevel Source #

Issuable 'OperationLevel Source # 
Instance details

Defined in Data.OpenApi.Compare.Validate.MediaTypeObject

Associated Types

data Issue 'OperationLevel Source #

Issuable 'PathFragmentLevel Source # 
Instance details

Defined in Data.OpenApi.Compare.Validate.Param

Associated Types

data Issue 'PathFragmentLevel Source #

Issuable 'RequestLevel Source # 
Instance details

Defined in Data.OpenApi.Compare.Validate.RequestBody

Associated Types

data Issue 'RequestLevel Source #

Issuable 'ResponseLevel Source # 
Instance details

Defined in Data.OpenApi.Compare.Validate.Responses

Associated Types

data Issue 'ResponseLevel Source #

Issuable 'HeaderLevel Source # 
Instance details

Defined in Data.OpenApi.Compare.Validate.Header

Associated Types

data Issue 'HeaderLevel Source #

Issuable 'PayloadLevel Source # 
Instance details

Defined in Data.OpenApi.Compare.Validate.MediaTypeObject

Associated Types

data Issue 'PayloadLevel Source #

Issuable 'SchemaLevel Source # 
Instance details

Defined in Data.OpenApi.Compare.Validate.Schema.Issues

Associated Types

data Issue 'SchemaLevel Source #

Issuable 'TypedSchemaLevel Source # 
Instance details

Defined in Data.OpenApi.Compare.Validate.Schema.Issues

Associated Types

data Issue 'TypedSchemaLevel Source #

Issuable 'LinkLevel Source # 
Instance details

Defined in Data.OpenApi.Compare.Validate.Link

Associated Types

data Issue 'LinkLevel Source #

Issuable 'CallbackLevel Source # 
Instance details

Defined in Data.OpenApi.Compare.Validate.Operation

Associated Types

data Issue 'CallbackLevel Source #

type Behavior = Paths Behave 'APILevel Source #

A set of interactions having common unifying features

data AnIssue (l :: BehaviorLevel) where Source #

Constructors

AnIssue :: Issuable l => Orientation -> Issue l -> AnIssue l 

Instances

Instances details
Eq (AnIssue l) Source # 
Instance details

Defined in Data.OpenApi.Compare.Behavior

Methods

(==) :: AnIssue l -> AnIssue l -> Bool #

(/=) :: AnIssue l -> AnIssue l -> Bool #

Ord (AnIssue l) Source # 
Instance details

Defined in Data.OpenApi.Compare.Behavior

Methods

compare :: AnIssue l -> AnIssue l -> Ordering #

(<) :: AnIssue l -> AnIssue l -> Bool #

(<=) :: AnIssue l -> AnIssue l -> Bool #

(>) :: AnIssue l -> AnIssue l -> Bool #

(>=) :: AnIssue l -> AnIssue l -> Bool #

max :: AnIssue l -> AnIssue l -> AnIssue l #

min :: AnIssue l -> AnIssue l -> AnIssue l #

Show (AnIssue l) Source # 
Instance details

Defined in Data.OpenApi.Compare.Behavior

Methods

showsPrec :: Int -> AnIssue l -> ShowS #

show :: AnIssue l -> String #

showList :: [AnIssue l] -> ShowS #

ToJSON (AnIssue l) Source # 
Instance details

Defined in Data.OpenApi.Compare.Behavior

withClass :: Eq b => (a -> a -> Bool) -> (a -> Maybe b) -> a -> a -> Bool Source #