Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Aeson.Match.QQ
Synopsis
- match :: Value Value -> Value -> Either (NonEmpty Error) (HashMap Text Value)
- qq :: QuasiQuoter
- data Error
- data Mismatch = MkMismatch {}
- data MissingPathElem = MkMissingPathElem {}
- data ExtraArrayValues = MkExtraArrayValues {}
- data ExtraObjectValues = MkExtraObjectValues {}
- prettyError :: Error -> String
- data Value ext
- type Array ext = Box (Vector (Value ext))
- type Object ext = Box (HashMap Text (Value ext))
- data Box a = Box {
- knownValues :: a
- extendable :: Bool
- data TypeSig = TypeSig {}
- data Type
- data Nullable
- newtype Path = Path {}
- data PathElem
Documentation
Arguments
:: Value Value | A matcher, constructed with |
-> Value | A |
-> Either (NonEmpty Error) (HashMap Text Value) | Either a non-empty list of errors, or a mapping from _holes to their values. |
Test if a matcher matches a Value
.
qq :: QuasiQuoter Source #
Construct a matcher Value
.
Various errors that can happen when a matcher tries to match a Value
.
Constructors
Mismatch Mismatch | The type of the value is correct, but the value itself is wrong |
Mistype Mismatch | The type of the value is wrong |
MissingPathElem MissingPathElem | The request path is missing in the value |
ExtraArrayValues ExtraArrayValues | Unexpected extra values in an array |
ExtraObjectValues ExtraObjectValues | Unexpected extra key-value pairs in an object |
Instances
ToJSON Error Source # | |
Defined in Aeson.Match.QQ.Internal.Match | |
Show Error Source # | |
Eq Error Source # | |
Pretty Error Source # | |
Defined in Aeson.Match.QQ.Internal.Match Methods pPrintPrec :: PrettyLevel -> Rational -> Error -> Doc # pPrintList :: PrettyLevel -> [Error] -> Doc # |
A generic error that covers cases where either the type of the value is wrong, or the value itself does not match.
Instances
ToJSON Mismatch Source # | |
Defined in Aeson.Match.QQ.Internal.Match | |
Show Mismatch Source # | |
Eq Mismatch Source # | |
Pretty Mismatch Source # | |
Defined in Aeson.Match.QQ.Internal.Match Methods pPrintPrec :: PrettyLevel -> Rational -> Mismatch -> Doc # pPrintList :: PrettyLevel -> [Mismatch] -> Doc # |
data MissingPathElem Source #
This error covers the case where the requested path simply does not exist
in a Value
.
Constructors
MkMissingPathElem | |
Instances
ToJSON MissingPathElem Source # | |
Defined in Aeson.Match.QQ.Internal.Match Methods toJSON :: MissingPathElem -> Value # toEncoding :: MissingPathElem -> Encoding # toJSONList :: [MissingPathElem] -> Value # toEncodingList :: [MissingPathElem] -> Encoding # | |
Show MissingPathElem Source # | |
Defined in Aeson.Match.QQ.Internal.Match Methods showsPrec :: Int -> MissingPathElem -> ShowS # show :: MissingPathElem -> String # showList :: [MissingPathElem] -> ShowS # | |
Eq MissingPathElem Source # | |
Defined in Aeson.Match.QQ.Internal.Match Methods (==) :: MissingPathElem -> MissingPathElem -> Bool # (/=) :: MissingPathElem -> MissingPathElem -> Bool # | |
Pretty MissingPathElem Source # | |
Defined in Aeson.Match.QQ.Internal.Match Methods pPrintPrec :: PrettyLevel -> Rational -> MissingPathElem -> Doc # pPrint :: MissingPathElem -> Doc # pPrintList :: PrettyLevel -> [MissingPathElem] -> Doc # |
data ExtraArrayValues Source #
Unless an extendable matcher is used, any extra values in an array missing in the matcher will trigger this error.
Instances
ToJSON ExtraArrayValues Source # | |
Defined in Aeson.Match.QQ.Internal.Match Methods toJSON :: ExtraArrayValues -> Value # toEncoding :: ExtraArrayValues -> Encoding # toJSONList :: [ExtraArrayValues] -> Value # toEncodingList :: [ExtraArrayValues] -> Encoding # | |
Show ExtraArrayValues Source # | |
Defined in Aeson.Match.QQ.Internal.Match Methods showsPrec :: Int -> ExtraArrayValues -> ShowS # show :: ExtraArrayValues -> String # showList :: [ExtraArrayValues] -> ShowS # | |
Eq ExtraArrayValues Source # | |
Defined in Aeson.Match.QQ.Internal.Match Methods (==) :: ExtraArrayValues -> ExtraArrayValues -> Bool # (/=) :: ExtraArrayValues -> ExtraArrayValues -> Bool # | |
Pretty ExtraArrayValues Source # | |
Defined in Aeson.Match.QQ.Internal.Match Methods pPrintPrec :: PrettyLevel -> Rational -> ExtraArrayValues -> Doc # pPrint :: ExtraArrayValues -> Doc # pPrintList :: PrettyLevel -> [ExtraArrayValues] -> Doc # |
data ExtraObjectValues Source #
Unless an extendable matcher is used, any extra key-value pairs in an object missing in the matcher will trigger this error.
Instances
ToJSON ExtraObjectValues Source # | |
Defined in Aeson.Match.QQ.Internal.Match Methods toJSON :: ExtraObjectValues -> Value # toEncoding :: ExtraObjectValues -> Encoding # toJSONList :: [ExtraObjectValues] -> Value # toEncodingList :: [ExtraObjectValues] -> Encoding # | |
Show ExtraObjectValues Source # | |
Defined in Aeson.Match.QQ.Internal.Match Methods showsPrec :: Int -> ExtraObjectValues -> ShowS # show :: ExtraObjectValues -> String # showList :: [ExtraObjectValues] -> ShowS # | |
Eq ExtraObjectValues Source # | |
Defined in Aeson.Match.QQ.Internal.Match Methods (==) :: ExtraObjectValues -> ExtraObjectValues -> Bool # (/=) :: ExtraObjectValues -> ExtraObjectValues -> Bool # | |
Pretty ExtraObjectValues Source # | |
Defined in Aeson.Match.QQ.Internal.Match Methods pPrintPrec :: PrettyLevel -> Rational -> ExtraObjectValues -> Doc # pPrint :: ExtraObjectValues -> Doc # pPrintList :: PrettyLevel -> [ExtraObjectValues] -> Doc # |
Constructors
Any (Maybe TypeSig) (Maybe Text) | |
Null | |
Bool Bool | |
Number Scientific | |
String Text | |
StringCI (CI Text) | |
Array (Array ext) | |
ArrayUO (Array ext) | |
Object (Object ext) | |
Ext ext |
Instances
ext ~ Exp => Lift (Value ext :: Type) Source # | Convert `Value Exp` to `Value Aeson.Value`. This uses a roundabout way to get
|
ToJSON ext => ToJSON (Value ext) Source # | |
Defined in Aeson.Match.QQ.Internal.Value | |
Show ext => Show (Value ext) Source # | |
Eq ext => Eq (Value ext) Source # | |
Constructors
Box | |
Fields
|
Constructors
Nullable | |
NonNullable |
A path is a list of path elements.
Instances
ToJSON Path Source # | |
Defined in Aeson.Match.QQ.Internal.Match | |
IsList Path Source # | |
Show Path Source # | |
Eq Path Source # | |
Pretty Path Source # | |
Defined in Aeson.Match.QQ.Internal.Match Methods pPrintPrec :: PrettyLevel -> Rational -> Path -> Doc # pPrintList :: PrettyLevel -> [Path] -> Doc # | |
type Item Path Source # | |
Defined in Aeson.Match.QQ.Internal.Match |
A path element is either a key lookup in an object, or an index lookup in an array.
Instances
ToJSON PathElem Source # | |
Defined in Aeson.Match.QQ.Internal.Match | |
IsString PathElem Source # | |
Defined in Aeson.Match.QQ.Internal.Match Methods fromString :: String -> PathElem # | |
Show PathElem Source # | |
Eq PathElem Source # | |
Pretty PathElem Source # | |
Defined in Aeson.Match.QQ.Internal.Match Methods pPrintPrec :: PrettyLevel -> Rational -> PathElem -> Doc # pPrintList :: PrettyLevel -> [PathElem] -> Doc # |