aeson-jsonpath-0.3.0.2: Parse and run JSONPath queries on Aeson documents
Copyright(c) 2024-2025 Taimoor Zaeem
LicenseMIT
MaintainerTaimoor Zaeem <[email protected]>
StabilityExperimental
PortabilityPortable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Aeson.JSONPath.Types

Description

This module contains all the data structures related to JSONPath

Synopsis

Documentation

data Query Source #

 

Instances

Instances details
Show Query Source # 
Instance details

Defined in Data.Aeson.JSONPath.Types.Query

Methods

showsPrec :: Int -> Query -> ShowS #

show :: Query -> String #

showList :: [Query] -> ShowS #

Eq Query Source # 
Instance details

Defined in Data.Aeson.JSONPath.Types.Query

Methods

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

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

Lift Query Source # 
Instance details

Defined in Data.Aeson.JSONPath.Types.Query

Methods

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

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

data QueryType Source #

 

Constructors

Root 
Current 

Instances

Instances details
Show QueryType Source # 
Instance details

Defined in Data.Aeson.JSONPath.Types.Query

Eq QueryType Source # 
Instance details

Defined in Data.Aeson.JSONPath.Types.Query

Lift QueryType Source # 
Instance details

Defined in Data.Aeson.JSONPath.Types.Query

Methods

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

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

data Segment a Source #

 

Instances

Instances details
Lift a => Lift (Segment a :: Type) Source # 
Instance details

Defined in Data.Aeson.JSONPath.Types.Segment

Methods

lift :: Quote m => Segment a -> m Exp #

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

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

Defined in Data.Aeson.JSONPath.Types.Segment

Methods

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

show :: Segment a -> String #

showList :: [Segment a] -> ShowS #

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

Defined in Data.Aeson.JSONPath.Types.Segment

Methods

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

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

data QuerySegment a Source #

 

Constructors

QuerySegment 

Instances

Instances details
Lift a => Lift (QuerySegment a :: Type) Source # 
Instance details

Defined in Data.Aeson.JSONPath.Types.Segment

Methods

lift :: Quote m => QuerySegment a -> m Exp #

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

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

Defined in Data.Aeson.JSONPath.Types.Segment

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

Defined in Data.Aeson.JSONPath.Types.Segment

data SegmentType Source #

 

Constructors

Child 
Descendant 

Instances

Instances details
Show SegmentType Source # 
Instance details

Defined in Data.Aeson.JSONPath.Types.Segment

Eq SegmentType Source # 
Instance details

Defined in Data.Aeson.JSONPath.Types.Segment

Lift SegmentType Source # 
Instance details

Defined in Data.Aeson.JSONPath.Types.Segment

Methods

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

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

data Selector a Source #

 

Instances

Instances details
Lift a => Lift (Selector a :: Type) Source # 
Instance details

Defined in Data.Aeson.JSONPath.Types.Selector

Methods

lift :: Quote m => Selector a -> m Exp #

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

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

Defined in Data.Aeson.JSONPath.Types.Selector

Methods

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

show :: Selector a -> String #

showList :: [Selector a] -> ShowS #

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

Defined in Data.Aeson.JSONPath.Types.Selector

Methods

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

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

newtype LogicalOrExpr a Source #

 

Constructors

LogicalOr [LogicalAndExpr a] 

Instances

Instances details
Lift a => Lift (LogicalOrExpr a :: Type) Source # 
Instance details

Defined in Data.Aeson.JSONPath.Types.Filter

Methods

lift :: Quote m => LogicalOrExpr a -> m Exp #

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

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

Defined in Data.Aeson.JSONPath.Types.Filter

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

Defined in Data.Aeson.JSONPath.Types.Filter

newtype LogicalAndExpr a Source #

 

Constructors

LogicalAnd [BasicExpr a] 

Instances

Instances details
Lift a => Lift (LogicalAndExpr a :: Type) Source # 
Instance details

Defined in Data.Aeson.JSONPath.Types.Filter

Methods

lift :: Quote m => LogicalAndExpr a -> m Exp #

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

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

Defined in Data.Aeson.JSONPath.Types.Filter

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

Defined in Data.Aeson.JSONPath.Types.Filter

data BasicExpr a Source #

 

Instances

Instances details
Lift a => Lift (BasicExpr a :: Type) Source # 
Instance details

Defined in Data.Aeson.JSONPath.Types.Filter

Methods

lift :: Quote m => BasicExpr a -> m Exp #

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

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

Defined in Data.Aeson.JSONPath.Types.Filter

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

Defined in Data.Aeson.JSONPath.Types.Filter

Methods

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

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

newtype TestExpr a Source #

 

Constructors

FilterQuery a 

Instances

Instances details
Lift a => Lift (TestExpr a :: Type) Source # 
Instance details

Defined in Data.Aeson.JSONPath.Types.Filter

Methods

lift :: Quote m => TestExpr a -> m Exp #

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

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

Defined in Data.Aeson.JSONPath.Types.Filter

Methods

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

show :: TestExpr a -> String #

showList :: [TestExpr a] -> ShowS #

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

Defined in Data.Aeson.JSONPath.Types.Filter

Methods

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

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

data Comparable Source #

 

Instances

Instances details
Show Comparable Source # 
Instance details

Defined in Data.Aeson.JSONPath.Types.Filter

Eq Comparable Source # 
Instance details

Defined in Data.Aeson.JSONPath.Types.Filter

Lift Comparable Source # 
Instance details

Defined in Data.Aeson.JSONPath.Types.Filter

Methods

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

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

data Literal Source #

 

Instances

Instances details
Show Literal Source # 
Instance details

Defined in Data.Aeson.JSONPath.Types.Filter

Eq Literal Source # 
Instance details

Defined in Data.Aeson.JSONPath.Types.Filter

Methods

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

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

Lift Literal Source # 
Instance details

Defined in Data.Aeson.JSONPath.Types.Filter

Methods

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

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