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

Aeson.Match.QQ

Synopsis

Documentation

match Source #

Arguments

:: Value Value

A matcher, constructed with qq

-> Value

A Value from aeson

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

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

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 Mismatch Source #

A generic error that covers cases where either the type of the value is wrong, or the value itself does not match.

Constructors

MkMismatch 

Fields

data ExtraArrayValues Source #

Unless an extendable 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 extendable 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 Value ext Source #

Instances

Instances details
ext ~ Exp => Lift (Value ext :: Type) Source #

Convert `Value Exp` to `Value Aeson.Value`. This uses a roundabout way to get Value from toEncoding to avoid calling toJSON which may be undefined for some datatypes.

Instance details

Defined in Aeson.Match.QQ.Internal.Value

Methods

lift :: Quote m => Value ext -> m Exp #

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

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

Defined in Aeson.Match.QQ.Internal.Value

Methods

toJSON :: Value ext -> Value0 #

toEncoding :: Value ext -> Encoding #

toJSONList :: [Value ext] -> Value0 #

toEncodingList :: [Value ext] -> Encoding #

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

Defined in Aeson.Match.QQ.Internal.Value

Methods

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

show :: Value ext -> String #

showList :: [Value ext] -> ShowS #

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

Defined in Aeson.Match.QQ.Internal.Value

Methods

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

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

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

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

data Box a Source #

Constructors

Box 

Fields

Instances

Instances details
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 TypeSig Source #

Constructors

TypeSig 

Fields

Instances

Instances details
ToJSON TypeSig Source # 
Instance details

Defined in Aeson.Match.QQ.Internal.Value

Show TypeSig Source # 
Instance details

Defined in Aeson.Match.QQ.Internal.Value

Eq TypeSig Source # 
Instance details

Defined in Aeson.Match.QQ.Internal.Value

Methods

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

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

Lift TypeSig Source # 
Instance details

Defined in Aeson.Match.QQ.Internal.Value

Methods

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

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

data Type Source #

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 #

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 #

data Nullable Source #

Constructors

Nullable 
NonNullable 

Instances

Instances details
ToJSON Nullable Source # 
Instance details

Defined in Aeson.Match.QQ.Internal.Value

Show Nullable Source # 
Instance details

Defined in Aeson.Match.QQ.Internal.Value

Eq Nullable Source # 
Instance details

Defined in Aeson.Match.QQ.Internal.Value

Lift Nullable Source # 
Instance details

Defined in Aeson.Match.QQ.Internal.Value

Methods

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

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

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