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.Query.Types
Description
This module contains the data structures.
Synopsis
- data Query = Query {}
- data QueryType
- data Segment
- data QuerySegment = QuerySegment {}
- data SegmentType
- = Child
- | Descendant
- data Selector
- = Name Text
- | Index Int
- | ArraySlice (Maybe Int, Maybe Int, Int)
- | Filter LogicalOrExpr
- | WildcardSelector
- newtype LogicalOrExpr = LogicalOr [LogicalAndExpr]
- newtype LogicalAndExpr = LogicalAnd [BasicExpr]
- data BasicExpr
- type TestExpr = Query
- data ComparisonExpr = Comp Comparable ComparisonOp Comparable
- data ComparisonOp
- data Comparable
- data SingularQuery = SingularQuery {}
- data SingularQueryType
- data SingularQuerySegment
Documentation
Constructors
Query | |
Fields
|
Constructors
Bracketed [Selector] | |
Dotted Text | |
WildcardSegment |
data QuerySegment Source #
Constructors
QuerySegment | |
Fields
|
Instances
Queryable QuerySegment Source # | |
Defined in Data.Aeson.JSONPath.Query | |
Show QuerySegment Source # | |
Defined in Data.Aeson.JSONPath.Query.Types Methods showsPrec :: Int -> QuerySegment -> ShowS # show :: QuerySegment -> String # showList :: [QuerySegment] -> ShowS # | |
Eq QuerySegment Source # | |
Defined in Data.Aeson.JSONPath.Query.Types | |
Lift QuerySegment Source # | |
Defined in Data.Aeson.JSONPath.Query.Types Methods lift :: Quote m => QuerySegment -> m Exp # liftTyped :: forall (m :: Type -> Type). Quote m => QuerySegment -> Code m QuerySegment # |
data SegmentType Source #
Constructors
Child | |
Descendant |
Instances
Show SegmentType Source # | |
Defined in Data.Aeson.JSONPath.Query.Types Methods showsPrec :: Int -> SegmentType -> ShowS # show :: SegmentType -> String # showList :: [SegmentType] -> ShowS # | |
Eq SegmentType Source # | |
Defined in Data.Aeson.JSONPath.Query.Types | |
Lift SegmentType Source # | |
Defined in Data.Aeson.JSONPath.Query.Types 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 | |
WildcardSelector |
newtype LogicalOrExpr Source #
Constructors
LogicalOr [LogicalAndExpr] |
Instances
Show LogicalOrExpr Source # | |
Defined in Data.Aeson.JSONPath.Query.Types Methods showsPrec :: Int -> LogicalOrExpr -> ShowS # show :: LogicalOrExpr -> String # showList :: [LogicalOrExpr] -> ShowS # | |
Eq LogicalOrExpr Source # | |
Defined in Data.Aeson.JSONPath.Query.Types Methods (==) :: LogicalOrExpr -> LogicalOrExpr -> Bool # (/=) :: LogicalOrExpr -> LogicalOrExpr -> Bool # | |
Lift LogicalOrExpr Source # | |
Defined in Data.Aeson.JSONPath.Query.Types Methods lift :: Quote m => LogicalOrExpr -> m Exp # liftTyped :: forall (m :: Type -> Type). Quote m => LogicalOrExpr -> Code m LogicalOrExpr # |
newtype LogicalAndExpr Source #
Constructors
LogicalAnd [BasicExpr] |
Instances
Show LogicalAndExpr Source # | |
Defined in Data.Aeson.JSONPath.Query.Types Methods showsPrec :: Int -> LogicalAndExpr -> ShowS # show :: LogicalAndExpr -> String # showList :: [LogicalAndExpr] -> ShowS # | |
Eq LogicalAndExpr Source # | |
Defined in Data.Aeson.JSONPath.Query.Types Methods (==) :: LogicalAndExpr -> LogicalAndExpr -> Bool # (/=) :: LogicalAndExpr -> LogicalAndExpr -> Bool # | |
Lift LogicalAndExpr Source # | |
Defined in Data.Aeson.JSONPath.Query.Types Methods lift :: Quote m => LogicalAndExpr -> m Exp # liftTyped :: forall (m :: Type -> Type). Quote m => LogicalAndExpr -> Code m LogicalAndExpr # |
Constructors
Paren LogicalOrExpr | |
NotParen LogicalOrExpr | |
Test TestExpr | |
NotTest TestExpr | |
Comparison ComparisonExpr |
data ComparisonExpr Source #
Constructors
Comp Comparable ComparisonOp Comparable |
Instances
Show ComparisonExpr Source # | |
Defined in Data.Aeson.JSONPath.Query.Types Methods showsPrec :: Int -> ComparisonExpr -> ShowS # show :: ComparisonExpr -> String # showList :: [ComparisonExpr] -> ShowS # | |
Eq ComparisonExpr Source # | |
Defined in Data.Aeson.JSONPath.Query.Types Methods (==) :: ComparisonExpr -> ComparisonExpr -> Bool # (/=) :: ComparisonExpr -> ComparisonExpr -> Bool # | |
Lift ComparisonExpr Source # | |
Defined in Data.Aeson.JSONPath.Query.Types 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.Query.Types Methods showsPrec :: Int -> ComparisonOp -> ShowS # show :: ComparisonOp -> String # showList :: [ComparisonOp] -> ShowS # | |
Eq ComparisonOp Source # | |
Defined in Data.Aeson.JSONPath.Query.Types | |
Lift ComparisonOp Source # | |
Defined in Data.Aeson.JSONPath.Query.Types Methods lift :: Quote m => ComparisonOp -> m Exp # liftTyped :: forall (m :: Type -> Type). Quote m => ComparisonOp -> Code m ComparisonOp # |
data Comparable Source #
Constructors
CompLitString Text | |
CompLitNum Scientific | |
CompLitBool Bool | |
CompLitNull | |
CompSQ SingularQuery |
Instances
Show Comparable Source # | |
Defined in Data.Aeson.JSONPath.Query.Types Methods showsPrec :: Int -> Comparable -> ShowS # show :: Comparable -> String # showList :: [Comparable] -> ShowS # | |
Eq Comparable Source # | |
Defined in Data.Aeson.JSONPath.Query.Types | |
Lift Comparable Source # | |
Defined in Data.Aeson.JSONPath.Query.Types Methods lift :: Quote m => Comparable -> m Exp # liftTyped :: forall (m :: Type -> Type). Quote m => Comparable -> Code m Comparable # |
data SingularQuery Source #
Constructors
SingularQuery | |
Instances
Show SingularQuery Source # | |
Defined in Data.Aeson.JSONPath.Query.Types Methods showsPrec :: Int -> SingularQuery -> ShowS # show :: SingularQuery -> String # showList :: [SingularQuery] -> ShowS # | |
Eq SingularQuery Source # | |
Defined in Data.Aeson.JSONPath.Query.Types Methods (==) :: SingularQuery -> SingularQuery -> Bool # (/=) :: SingularQuery -> SingularQuery -> Bool # | |
Lift SingularQuery Source # | |
Defined in Data.Aeson.JSONPath.Query.Types Methods lift :: Quote m => SingularQuery -> m Exp # liftTyped :: forall (m :: Type -> Type). Quote m => SingularQuery -> Code m SingularQuery # |
data SingularQueryType Source #
Instances
Show SingularQueryType Source # | |
Defined in Data.Aeson.JSONPath.Query.Types Methods showsPrec :: Int -> SingularQueryType -> ShowS # show :: SingularQueryType -> String # showList :: [SingularQueryType] -> ShowS # | |
Eq SingularQueryType Source # | |
Defined in Data.Aeson.JSONPath.Query.Types Methods (==) :: SingularQueryType -> SingularQueryType -> Bool # (/=) :: SingularQueryType -> SingularQueryType -> Bool # | |
Lift SingularQueryType Source # | |
Defined in Data.Aeson.JSONPath.Query.Types Methods lift :: Quote m => SingularQueryType -> m Exp # liftTyped :: forall (m :: Type -> Type). Quote m => SingularQueryType -> Code m SingularQueryType # |
data SingularQuerySegment Source #
Constructors
NameSQSeg Text | |
IndexSQSeg Int |
Instances
Show SingularQuerySegment Source # | |
Defined in Data.Aeson.JSONPath.Query.Types Methods showsPrec :: Int -> SingularQuerySegment -> ShowS # show :: SingularQuerySegment -> String # showList :: [SingularQuerySegment] -> ShowS # | |
Eq SingularQuerySegment Source # | |
Defined in Data.Aeson.JSONPath.Query.Types Methods (==) :: SingularQuerySegment -> SingularQuerySegment -> Bool # (/=) :: SingularQuerySegment -> SingularQuerySegment -> Bool # | |
Lift SingularQuerySegment Source # | |
Defined in Data.Aeson.JSONPath.Query.Types Methods lift :: Quote m => SingularQuerySegment -> m Exp # liftTyped :: forall (m :: Type -> Type). Quote m => SingularQuerySegment -> Code m SingularQuerySegment # |