Copyright | (c) 2024-2025 Taimoor Zaeem |
---|---|
License | MIT |
Maintainer | Taimoor Zaeem <[email protected]> |
Stability | Experimental |
Portability | Portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Data.Aeson.JSONPath.Types
Description
This module contains all the data structures related to JSONPath
Synopsis
- data Query = Query {}
- data QueryType
- data QueryState = QueryState {
- rootVal :: Value
- curVal :: Value
- executeQuery :: Query -> QueryState -> Vector Value
- data Segment a
- = Bracketed [Selector a]
- | Dotted Text
- | WildcardSegment
- data QuerySegment a = QuerySegment {
- segmentType :: SegmentType
- segment :: Segment a
- data SegmentType
- = Child
- | Descendant
- data Selector a
- = Name Text
- | Index Int
- | ArraySlice (Maybe Int, Maybe Int, Int)
- | Filter (LogicalOrExpr a)
- | WildcardSelector
- newtype LogicalOrExpr a = LogicalOr [LogicalAndExpr a]
- newtype LogicalAndExpr a = LogicalAnd [BasicExpr a]
- data BasicExpr a
- = Paren (LogicalOrExpr a)
- | NotParen (LogicalOrExpr a)
- | Test (TestExpr a)
- | NotTest (TestExpr a)
- | Comparison ComparisonExpr
- newtype TestExpr a = FilterQuery a
- data ComparisonExpr = Comp Comparable ComparisonOp Comparable
- data ComparisonOp
- data Comparable
- data Literal
- data SingularQueryType
- data SingularQuery = SingularQuery {}
- data SingularQuerySegment
Documentation
Constructors
Query | |
Fields
|
data QueryState Source #
Constructors
QueryState | |
Fields
|
Constructors
Bracketed [Selector a] | |
Dotted Text | |
WildcardSegment |
data QuerySegment a Source #
Constructors
QuerySegment | |
Fields
|
Instances
Lift a => Lift (QuerySegment a :: Type) Source # | |
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 # | |
Defined in Data.Aeson.JSONPath.Types.Segment Methods showsPrec :: Int -> QuerySegment a -> ShowS # show :: QuerySegment a -> String # showList :: [QuerySegment a] -> ShowS # | |
Eq a => Eq (QuerySegment a) Source # | |
Defined in Data.Aeson.JSONPath.Types.Segment Methods (==) :: QuerySegment a -> QuerySegment a -> Bool # (/=) :: QuerySegment a -> QuerySegment a -> Bool # |
data SegmentType Source #
Constructors
Child | |
Descendant |
Instances
Show SegmentType Source # | |
Defined in Data.Aeson.JSONPath.Types.Segment Methods showsPrec :: Int -> SegmentType -> ShowS # show :: SegmentType -> String # showList :: [SegmentType] -> ShowS # | |
Eq SegmentType Source # | |
Defined in Data.Aeson.JSONPath.Types.Segment | |
Lift SegmentType Source # | |
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 # |
Constructors
Name Text | |
Index Int | |
ArraySlice (Maybe Int, Maybe Int, Int) | |
Filter (LogicalOrExpr a) | |
WildcardSelector |
newtype LogicalOrExpr a Source #
Constructors
LogicalOr [LogicalAndExpr a] |
Instances
Lift a => Lift (LogicalOrExpr a :: Type) Source # | |
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 # | |
Defined in Data.Aeson.JSONPath.Types.Filter Methods showsPrec :: Int -> LogicalOrExpr a -> ShowS # show :: LogicalOrExpr a -> String # showList :: [LogicalOrExpr a] -> ShowS # | |
Eq a => Eq (LogicalOrExpr a) Source # | |
Defined in Data.Aeson.JSONPath.Types.Filter Methods (==) :: LogicalOrExpr a -> LogicalOrExpr a -> Bool # (/=) :: LogicalOrExpr a -> LogicalOrExpr a -> Bool # |
newtype LogicalAndExpr a Source #
Constructors
LogicalAnd [BasicExpr a] |
Instances
Lift a => Lift (LogicalAndExpr a :: Type) Source # | |
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 # | |
Defined in Data.Aeson.JSONPath.Types.Filter Methods showsPrec :: Int -> LogicalAndExpr a -> ShowS # show :: LogicalAndExpr a -> String # showList :: [LogicalAndExpr a] -> ShowS # | |
Eq a => Eq (LogicalAndExpr a) Source # | |
Defined in Data.Aeson.JSONPath.Types.Filter Methods (==) :: LogicalAndExpr a -> LogicalAndExpr a -> Bool # (/=) :: LogicalAndExpr a -> LogicalAndExpr a -> Bool # |
Constructors
Paren (LogicalOrExpr a) | |
NotParen (LogicalOrExpr a) | |
Test (TestExpr a) | |
NotTest (TestExpr a) | |
Comparison ComparisonExpr |
Constructors
FilterQuery a |
data ComparisonExpr Source #
Constructors
Comp Comparable ComparisonOp Comparable |
Instances
Show ComparisonExpr Source # | |
Defined in Data.Aeson.JSONPath.Types.Filter Methods showsPrec :: Int -> ComparisonExpr -> ShowS # show :: ComparisonExpr -> String # showList :: [ComparisonExpr] -> ShowS # | |
Eq ComparisonExpr Source # | |
Defined in Data.Aeson.JSONPath.Types.Filter Methods (==) :: ComparisonExpr -> ComparisonExpr -> Bool # (/=) :: ComparisonExpr -> ComparisonExpr -> Bool # | |
Lift ComparisonExpr Source # | |
Defined in Data.Aeson.JSONPath.Types.Filter Methods lift :: Quote m => ComparisonExpr -> m Exp # liftTyped :: forall (m :: Type -> Type). Quote m => ComparisonExpr -> Code m ComparisonExpr # |
data ComparisonOp Source #
Constructors
Less | |
LessOrEqual | |
Greater | |
GreaterOrEqual | |
Equal | |
NotEqual |
Instances
Show ComparisonOp Source # | |
Defined in Data.Aeson.JSONPath.Types.Filter Methods showsPrec :: Int -> ComparisonOp -> ShowS # show :: ComparisonOp -> String # showList :: [ComparisonOp] -> ShowS # | |
Eq ComparisonOp Source # | |
Defined in Data.Aeson.JSONPath.Types.Filter | |
Lift ComparisonOp Source # | |
Defined in Data.Aeson.JSONPath.Types.Filter Methods lift :: Quote m => ComparisonOp -> m Exp # liftTyped :: forall (m :: Type -> Type). Quote m => ComparisonOp -> Code m ComparisonOp # |
data Comparable Source #
Constructors
CompLit Literal | |
CompSQ SingularQuery |
Instances
Show Comparable Source # | |
Defined in Data.Aeson.JSONPath.Types.Filter Methods showsPrec :: Int -> Comparable -> ShowS # show :: Comparable -> String # showList :: [Comparable] -> ShowS # | |
Eq Comparable Source # | |
Defined in Data.Aeson.JSONPath.Types.Filter | |
Lift Comparable Source # | |
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 SingularQueryType Source #
Instances
Show SingularQueryType Source # | |
Defined in Data.Aeson.JSONPath.Types.Filter Methods showsPrec :: Int -> SingularQueryType -> ShowS # show :: SingularQueryType -> String # showList :: [SingularQueryType] -> ShowS # | |
Eq SingularQueryType Source # | |
Defined in Data.Aeson.JSONPath.Types.Filter Methods (==) :: SingularQueryType -> SingularQueryType -> Bool # (/=) :: SingularQueryType -> SingularQueryType -> Bool # | |
Lift SingularQueryType Source # | |
Defined in Data.Aeson.JSONPath.Types.Filter Methods lift :: Quote m => SingularQueryType -> m Exp # liftTyped :: forall (m :: Type -> Type). Quote m => SingularQueryType -> Code m SingularQueryType # |
data SingularQuery Source #
Constructors
SingularQuery | |
Instances
Show SingularQuery Source # | |
Defined in Data.Aeson.JSONPath.Types.Filter Methods showsPrec :: Int -> SingularQuery -> ShowS # show :: SingularQuery -> String # showList :: [SingularQuery] -> ShowS # | |
Eq SingularQuery Source # | |
Defined in Data.Aeson.JSONPath.Types.Filter Methods (==) :: SingularQuery -> SingularQuery -> Bool # (/=) :: SingularQuery -> SingularQuery -> Bool # | |
Lift SingularQuery Source # | |
Defined in Data.Aeson.JSONPath.Types.Filter Methods lift :: Quote m => SingularQuery -> m Exp # liftTyped :: forall (m :: Type -> Type). Quote m => SingularQuery -> Code m SingularQuery # |
data SingularQuerySegment Source #
Constructors
NameSQSeg Text | |
IndexSQSeg Int |
Instances
Show SingularQuerySegment Source # | |
Defined in Data.Aeson.JSONPath.Types.Filter Methods showsPrec :: Int -> SingularQuerySegment -> ShowS # show :: SingularQuerySegment -> String # showList :: [SingularQuerySegment] -> ShowS # | |
Eq SingularQuerySegment Source # | |
Defined in Data.Aeson.JSONPath.Types.Filter Methods (==) :: SingularQuerySegment -> SingularQuerySegment -> Bool # (/=) :: SingularQuerySegment -> SingularQuerySegment -> Bool # | |
Lift SingularQuerySegment Source # | |
Defined in Data.Aeson.JSONPath.Types.Filter Methods lift :: Quote m => SingularQuerySegment -> m Exp # liftTyped :: forall (m :: Type -> Type). Quote m => SingularQuerySegment -> Code m SingularQuerySegment # |