Safe Haskell | None |
---|---|
Language | Haskell2010 |
Data.OpenApi.Compare.Validate.Operation
Synopsis
- data MatchedOperation = MatchedOperation {
- operation :: !Operation
- pathParams :: ![Traced Param]
- getPathFragments :: !([Traced Param] -> [Traced PathFragmentParam])
- data OperationMethod
- pathItemMethod :: OperationMethod -> PathItem -> Maybe Operation
- data ProcessedPathItem = ProcessedPathItem {}
- newtype ProcessedPathItems = ProcessedPathItems {}
- processPathItems :: [(FilePath, PathItem)] -> ProcessedPathItems
- data family Step a b :: Type
- data family Behave a b
- data family Issue l :: Type
Operation
data MatchedOperation Source #
Constructors
MatchedOperation | |
Fields
|
Instances
data OperationMethod Source #
Constructors
GetMethod | |
PutMethod | |
PostMethod | |
DeleteMethod | |
OptionsMethod | |
HeadMethod | |
PatchMethod | |
TraceMethod |
Instances
Eq OperationMethod Source # | |
Defined in Data.OpenApi.Compare.Validate.Operation Methods (==) :: OperationMethod -> OperationMethod -> Bool # (/=) :: OperationMethod -> OperationMethod -> Bool # | |
Ord OperationMethod Source # | |
Defined in Data.OpenApi.Compare.Validate.Operation Methods compare :: OperationMethod -> OperationMethod -> Ordering # (<) :: OperationMethod -> OperationMethod -> Bool # (<=) :: OperationMethod -> OperationMethod -> Bool # (>) :: OperationMethod -> OperationMethod -> Bool # (>=) :: OperationMethod -> OperationMethod -> Bool # max :: OperationMethod -> OperationMethod -> OperationMethod # min :: OperationMethod -> OperationMethod -> OperationMethod # | |
Show OperationMethod Source # | |
Defined in Data.OpenApi.Compare.Validate.Operation Methods showsPrec :: Int -> OperationMethod -> ShowS # show :: OperationMethod -> String # showList :: [OperationMethod] -> ShowS # |
pathItemMethod :: OperationMethod -> PathItem -> Maybe Operation Source #
ProcessedPathItem
data ProcessedPathItem Source #
Constructors
ProcessedPathItem | |
Instances
Eq ProcessedPathItem Source # | |
Defined in Data.OpenApi.Compare.Validate.Operation Methods (==) :: ProcessedPathItem -> ProcessedPathItem -> Bool # (/=) :: ProcessedPathItem -> ProcessedPathItem -> Bool # | |
Show ProcessedPathItem Source # | |
Defined in Data.OpenApi.Compare.Validate.Operation Methods showsPrec :: Int -> ProcessedPathItem -> ShowS # show :: ProcessedPathItem -> String # showList :: [ProcessedPathItem] -> ShowS # |
newtype ProcessedPathItems Source #
Constructors
ProcessedPathItems | |
Fields |
Instances
processPathItems :: [(FilePath, PathItem)] -> ProcessedPathItems Source #
data family Step a b :: Type Source #
How to get from an a
node to a b
node
Instances
data family Behave a b Source #
Instances
data family Issue l :: Type Source #