Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- match :: Matcher Value -> Value -> Either (NonEmpty Error) (HashMap Text Value)
- qq :: QuasiQuoter
- data Error
- data TypeMismatch = MkTypeMismatch {}
- data Mismatch = MkMismatch {}
- data MissingPathElem = MkMissingPathElem {}
- data ExtraArrayValues = MkExtraArrayValues {}
- data ExtraObjectValues = MkExtraObjectValues {}
- prettyError :: Error -> String
- data Matcher ext
- type Array ext = Box (Vector (Matcher ext))
- type Object ext = Box (HashMap Text (Matcher ext))
- data Box a = Box {}
- data HoleSig = HoleSig {}
- data Type
- newtype Path = Path {}
- data PathElem
- parse :: ByteString -> Either String (Matcher Exp)
Documentation
qq :: QuasiQuoter Source #
Construct a Matcher
.
Various errors that can happen when a matcher tries to match a Value
.
Mismatch Mismatch | The type of the value is correct, but the value itself is wrong |
Mistype TypeMismatch | 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 pPrintPrec :: PrettyLevel -> Rational -> Error -> Doc # pPrintList :: PrettyLevel -> [Error] -> Doc # |
data TypeMismatch Source #
This error type covers the case where the type of the value does not match.
Instances
ToJSON TypeMismatch Source # | |
Defined in Aeson.Match.QQ.Internal.Match toJSON :: TypeMismatch -> Value # toEncoding :: TypeMismatch -> Encoding # toJSONList :: [TypeMismatch] -> Value # toEncodingList :: [TypeMismatch] -> Encoding # | |
Show TypeMismatch Source # | |
Defined in Aeson.Match.QQ.Internal.Match showsPrec :: Int -> TypeMismatch -> ShowS # show :: TypeMismatch -> String # showList :: [TypeMismatch] -> ShowS # | |
Eq TypeMismatch Source # | |
Defined in Aeson.Match.QQ.Internal.Match (==) :: TypeMismatch -> TypeMismatch -> Bool # (/=) :: TypeMismatch -> TypeMismatch -> Bool # | |
Pretty TypeMismatch Source # | |
Defined in Aeson.Match.QQ.Internal.Match pPrintPrec :: PrettyLevel -> Rational -> TypeMismatch -> Doc # pPrint :: TypeMismatch -> Doc # pPrintList :: PrettyLevel -> [TypeMismatch] -> Doc # |
This error type covers the case where the type matches but the value does not.
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 pPrintPrec :: PrettyLevel -> Rational -> Mismatch -> Doc # pPrintList :: PrettyLevel -> [Mismatch] -> Doc # |
data MissingPathElem Source #
This error type covers the case where the requested path simply does not exist
in a Value
.
Instances
ToJSON MissingPathElem Source # | |
Defined in Aeson.Match.QQ.Internal.Match toJSON :: MissingPathElem -> Value # toEncoding :: MissingPathElem -> Encoding # toJSONList :: [MissingPathElem] -> Value # toEncodingList :: [MissingPathElem] -> Encoding # | |
Show MissingPathElem Source # | |
Defined in Aeson.Match.QQ.Internal.Match showsPrec :: Int -> MissingPathElem -> ShowS # show :: MissingPathElem -> String # showList :: [MissingPathElem] -> ShowS # | |
Eq MissingPathElem Source # | |
Defined in Aeson.Match.QQ.Internal.Match (==) :: MissingPathElem -> MissingPathElem -> Bool # (/=) :: MissingPathElem -> MissingPathElem -> Bool # | |
Pretty MissingPathElem Source # | |
Defined in Aeson.Match.QQ.Internal.Match pPrintPrec :: PrettyLevel -> Rational -> MissingPathElem -> Doc # pPrint :: MissingPathElem -> Doc # pPrintList :: PrettyLevel -> [MissingPathElem] -> Doc # |
data ExtraArrayValues Source #
Unless an permissive 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 toJSON :: ExtraArrayValues -> Value # toEncoding :: ExtraArrayValues -> Encoding # toJSONList :: [ExtraArrayValues] -> Value # toEncodingList :: [ExtraArrayValues] -> Encoding # | |
Show ExtraArrayValues Source # | |
Defined in Aeson.Match.QQ.Internal.Match showsPrec :: Int -> ExtraArrayValues -> ShowS # show :: ExtraArrayValues -> String # showList :: [ExtraArrayValues] -> ShowS # | |
Eq ExtraArrayValues Source # | |
Defined in Aeson.Match.QQ.Internal.Match (==) :: ExtraArrayValues -> ExtraArrayValues -> Bool # (/=) :: ExtraArrayValues -> ExtraArrayValues -> Bool # | |
Pretty ExtraArrayValues Source # | |
Defined in Aeson.Match.QQ.Internal.Match pPrintPrec :: PrettyLevel -> Rational -> ExtraArrayValues -> Doc # pPrint :: ExtraArrayValues -> Doc # pPrintList :: PrettyLevel -> [ExtraArrayValues] -> Doc # |
data ExtraObjectValues Source #
Unless an permissive 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 toJSON :: ExtraObjectValues -> Value # toEncoding :: ExtraObjectValues -> Encoding # toJSONList :: [ExtraObjectValues] -> Value # toEncodingList :: [ExtraObjectValues] -> Encoding # | |
Show ExtraObjectValues Source # | |
Defined in Aeson.Match.QQ.Internal.Match showsPrec :: Int -> ExtraObjectValues -> ShowS # show :: ExtraObjectValues -> String # showList :: [ExtraObjectValues] -> ShowS # | |
Eq ExtraObjectValues Source # | |
Defined in Aeson.Match.QQ.Internal.Match (==) :: ExtraObjectValues -> ExtraObjectValues -> Bool # (/=) :: ExtraObjectValues -> ExtraObjectValues -> Bool # | |
Pretty ExtraObjectValues Source # | |
Defined in Aeson.Match.QQ.Internal.Match pPrintPrec :: PrettyLevel -> Rational -> ExtraObjectValues -> Doc # pPrint :: ExtraObjectValues -> Doc # pPrintList :: PrettyLevel -> [ExtraObjectValues] -> Doc # |
A value constructed using qq
that attempts to match
a JSON document.
Hole (Maybe HoleSig) (Maybe Text) | Optionally typed, optionally named _hole. If a type is provided, the _hole only matches those values that have that type. If a name is provided, the matched value is returned to the user. |
Null | |
Bool Bool | |
Number Scientific | |
String Text | |
StringCI (CI Text) | Case-insensitive strings |
Array (Array ext) | |
ArrayUO (Array ext) | Unordered arrays |
Object (Object ext) | |
Ext ext | External values spliced into a |
A wrapper for those matchers that support the ...
syntax.
_hole type signature
_hole type
BoolT | _ : bool |
NumberT | _ : number |
StringT | _ : string |
StringCIT | _ : ci-string |
ArrayT | _ : array |
ArrayUOT | _ : unordered-array |
ObjectT | _ : object |
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 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 fromString :: String -> PathElem # | |
Show PathElem Source # | |
Eq PathElem Source # | |
Pretty PathElem Source # | |
Defined in Aeson.Match.QQ.Internal.Match pPrintPrec :: PrettyLevel -> Rational -> PathElem -> Doc # pPrintList :: PrettyLevel -> [PathElem] -> Doc # |