aeson-match-qq-1.7.0: Declarative JSON matchers.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Aeson.Match.QQ

Synopsis

Documentation

match Source #

Arguments

:: Matcher Value 
-> Value 
-> Either (NonEmpty Error) (HashMap Text Value)

Either a non-empty list of errors, or a mapping from named _holes to their values.

Test if a Matcher matches a Value.

qq :: QuasiQuoter Source #

Construct a Matcher.

data Error Source #

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

Instances details
ToJSON Error Source # 
Instance details

Defined in Aeson.Match.QQ.Internal.Match

Show Error Source # 
Instance details

Defined in Aeson.Match.QQ.Internal.Match

Methods

showsPrec :: Int -> Error -> ShowS #

show :: Error -> String #

showList :: [Error] -> ShowS #

Eq Error Source # 
Instance details

Defined in Aeson.Match.QQ.Internal.Match

Methods

(==) :: Error -> Error -> Bool #

(/=) :: Error -> Error -> Bool #

Pretty Error Source # 
Instance details

Defined in Aeson.Match.QQ.Internal.Match

data TypeMismatch Source #

This error type covers the case where the type of the value does not match.

Constructors

MkTypeMismatch 

data Mismatch Source #

This error type covers the case where the type matches but the value does not.

Constructors

MkMismatch 

Fields

data ExtraArrayValues Source #

Unless an permissive matcher is used, any extra values in an array missing in the matcher will trigger this error.

Constructors

MkExtraArrayValues 

Fields

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.

Constructors

MkExtraObjectValues 

Fields

prettyError :: Error -> String Source #

Pretty print an Error.

data Matcher ext Source #

A value constructed using qq that attempts to match a JSON document.

Constructors

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 Matcher using the `#{}` syntax

Instances

Instances details
Functor Matcher Source # 
Instance details

Defined in Aeson.Match.QQ.Internal.Value

Methods

fmap :: (a -> b) -> Matcher a -> Matcher b #

(<$) :: a -> Matcher b -> Matcher a #

ToJSON ext => ToJSON (Matcher ext) Source # 
Instance details

Defined in Aeson.Match.QQ.Internal.Value

Show ext => Show (Matcher ext) Source # 
Instance details

Defined in Aeson.Match.QQ.Internal.Value

Methods

showsPrec :: Int -> Matcher ext -> ShowS #

show :: Matcher ext -> String #

showList :: [Matcher ext] -> ShowS #

Eq ext => Eq (Matcher ext) Source # 
Instance details

Defined in Aeson.Match.QQ.Internal.Value

Methods

(==) :: Matcher ext -> Matcher ext -> Bool #

(/=) :: Matcher ext -> Matcher ext -> Bool #

type Array ext = Box (Vector (Matcher ext)) Source #

type Object ext = Box (HashMap Text (Matcher ext)) Source #

data Box a Source #

A wrapper for those matchers that support the ... syntax.

Constructors

Box 

Fields

Instances

Instances details
Functor Box Source # 
Instance details

Defined in Aeson.Match.QQ.Internal.Value

Methods

fmap :: (a -> b) -> Box a -> Box b #

(<$) :: a -> Box b -> Box a #

ToJSON a => ToJSON (Box a) Source # 
Instance details

Defined in Aeson.Match.QQ.Internal.Value

Methods

toJSON :: Box a -> Value #

toEncoding :: Box a -> Encoding #

toJSONList :: [Box a] -> Value #

toEncodingList :: [Box a] -> Encoding #

Show a => Show (Box a) Source # 
Instance details

Defined in Aeson.Match.QQ.Internal.Value

Methods

showsPrec :: Int -> Box a -> ShowS #

show :: Box a -> String #

showList :: [Box a] -> ShowS #

Eq a => Eq (Box a) Source # 
Instance details

Defined in Aeson.Match.QQ.Internal.Value

Methods

(==) :: Box a -> Box a -> Bool #

(/=) :: Box a -> Box a -> Bool #

data HoleSig Source #

_hole type signature

Constructors

HoleSig 

Fields

Instances

Instances details
ToJSON HoleSig Source # 
Instance details

Defined in Aeson.Match.QQ.Internal.Value

Show HoleSig Source # 
Instance details

Defined in Aeson.Match.QQ.Internal.Value

Eq HoleSig Source # 
Instance details

Defined in Aeson.Match.QQ.Internal.Value

Methods

(==) :: HoleSig -> HoleSig -> Bool #

(/=) :: HoleSig -> HoleSig -> Bool #

Lift HoleSig Source # 
Instance details

Defined in Aeson.Match.QQ.Internal.Value

Methods

lift :: Quote m => HoleSig -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => HoleSig -> Code m HoleSig #

data Type Source #

_hole type

Constructors

BoolT
_ : bool
NumberT
_ : number
StringT
_ : string
StringCIT
_ : ci-string
ArrayT
_ : array
ArrayUOT
_ : unordered-array
ObjectT
_ : object

Instances

Instances details
ToJSON Type Source # 
Instance details

Defined in Aeson.Match.QQ.Internal.Value

Show Type Source # 
Instance details

Defined in Aeson.Match.QQ.Internal.Value

Methods

showsPrec :: Int -> Type -> ShowS #

show :: Type -> String #

showList :: [Type] -> ShowS #

Eq Type Source # 
Instance details

Defined in Aeson.Match.QQ.Internal.Value

Methods

(==) :: Type -> Type -> Bool #

(/=) :: Type -> Type -> Bool #

Pretty Type Source # 
Instance details

Defined in Aeson.Match.QQ.Internal.Value

Lift Type Source # 
Instance details

Defined in Aeson.Match.QQ.Internal.Value

Methods

lift :: Quote m => Type -> m Exp #

liftTyped :: forall (m :: Type0 -> Type0). Quote m => Type -> Code m Type #

newtype Path Source #

A path is a list of path elements.

Constructors

Path 

Fields

Instances

Instances details
ToJSON Path Source # 
Instance details

Defined in Aeson.Match.QQ.Internal.Match

IsList Path Source # 
Instance details

Defined in Aeson.Match.QQ.Internal.Match

Associated Types

type Item Path #

Methods

fromList :: [Item Path] -> Path #

fromListN :: Int -> [Item Path] -> Path #

toList :: Path -> [Item Path] #

Show Path Source # 
Instance details

Defined in Aeson.Match.QQ.Internal.Match

Methods

showsPrec :: Int -> Path -> ShowS #

show :: Path -> String #

showList :: [Path] -> ShowS #

Eq Path Source # 
Instance details

Defined in Aeson.Match.QQ.Internal.Match

Methods

(==) :: Path -> Path -> Bool #

(/=) :: Path -> Path -> Bool #

Pretty Path Source # 
Instance details

Defined in Aeson.Match.QQ.Internal.Match

type Item Path Source # 
Instance details

Defined in Aeson.Match.QQ.Internal.Match

data PathElem Source #

A path element is either a key lookup in an object, or an index lookup in an array.

Constructors

Key Text 
Idx Int 

parse :: ByteString -> Either String (Matcher Exp) Source #

An attoparsec parser for a Matcher.

Note: consumes spaces before and after the matcher.