| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Data.JSONPath.Types
Synopsis
- data BeginningPoint
- data Condition
- data Comparable
- data JSONPathElement
- = KeyChild Text
- | IndexChild Int
- | AnyChild
- | Slice (Maybe Int) (Maybe Int) (Maybe Int)
- | Union [UnionElement]
- | Filter FilterExpr
- | Search [JSONPathElement]
- data UnionElement
- data FilterExpr
- data SingularPathElement
- data SingularPath = SingularPath BeginningPoint [SingularPathElement]
Documentation
data BeginningPoint Source #
Constructors
| Root | |
| CurrentObject |
Instances
| Eq BeginningPoint Source # | |
Defined in Data.JSONPath.Types Methods (==) :: BeginningPoint -> BeginningPoint -> Bool # (/=) :: BeginningPoint -> BeginningPoint -> Bool # | |
| Show BeginningPoint Source # | |
Defined in Data.JSONPath.Types Methods showsPrec :: Int -> BeginningPoint -> ShowS # show :: BeginningPoint -> String # showList :: [BeginningPoint] -> ShowS # | |
data Comparable Source #
Constructors
| CmpNumber Scientific | |
| CmpString Text | |
| CmpBool Bool | |
| CmpNull | |
| CmpPath SingularPath |
Instances
| Eq Comparable Source # | |
Defined in Data.JSONPath.Types | |
| Show Comparable Source # | |
Defined in Data.JSONPath.Types Methods showsPrec :: Int -> Comparable -> ShowS # show :: Comparable -> String # showList :: [Comparable] -> ShowS # | |
data JSONPathElement Source #
A JSONPath is a list of JSONPathElements.
Constructors
| KeyChild Text | '$.foo' or '$["foo"]' |
| IndexChild Int | '$[1]' |
| AnyChild | '$[*]' |
| Slice (Maybe Int) (Maybe Int) (Maybe Int) | '$[1:7]', '$[0:10:2]', '$[::2]', '$[::]', etc. |
| Union [UnionElement] | '$[0,1,9]' or '$[0, 1:2, "foo", "bar"]' |
| Filter FilterExpr | '$[?( |
| Search [JSONPathElement] | '$..foo.bar' |
Instances
| Eq JSONPathElement Source # | |
Defined in Data.JSONPath.Types Methods (==) :: JSONPathElement -> JSONPathElement -> Bool # (/=) :: JSONPathElement -> JSONPathElement -> Bool # | |
| Show JSONPathElement Source # | |
Defined in Data.JSONPath.Types Methods showsPrec :: Int -> JSONPathElement -> ShowS # show :: JSONPathElement -> String # showList :: [JSONPathElement] -> ShowS # | |
data UnionElement Source #
Elements which can occur inside a union
Instances
| Eq UnionElement Source # | |
Defined in Data.JSONPath.Types | |
| Show UnionElement Source # | |
Defined in Data.JSONPath.Types Methods showsPrec :: Int -> UnionElement -> ShowS # show :: UnionElement -> String # showList :: [UnionElement] -> ShowS # | |
data FilterExpr Source #
Constructors
| ExistsExpr SingularPath | |
| ComparisonExpr Comparable Condition Comparable | |
| And FilterExpr FilterExpr | |
| Or FilterExpr FilterExpr | |
| Not FilterExpr |
Instances
| Eq FilterExpr Source # | |
Defined in Data.JSONPath.Types | |
| Show FilterExpr Source # | |
Defined in Data.JSONPath.Types Methods showsPrec :: Int -> FilterExpr -> ShowS # show :: FilterExpr -> String # showList :: [FilterExpr] -> ShowS # | |
data SingularPathElement Source #
Instances
| Eq SingularPathElement Source # | |
Defined in Data.JSONPath.Types Methods (==) :: SingularPathElement -> SingularPathElement -> Bool # (/=) :: SingularPathElement -> SingularPathElement -> Bool # | |
| Show SingularPathElement Source # | |
Defined in Data.JSONPath.Types Methods showsPrec :: Int -> SingularPathElement -> ShowS # show :: SingularPathElement -> String # showList :: [SingularPathElement] -> ShowS # | |
data SingularPath Source #
A JSONPath which finds at max one value, given a beginning point. Used by
FilterExpr for ExistsExpr and ComparisonExpr.
Constructors
| SingularPath BeginningPoint [SingularPathElement] |
Instances
| Eq SingularPath Source # | |
Defined in Data.JSONPath.Types | |
| Show SingularPath Source # | |
Defined in Data.JSONPath.Types Methods showsPrec :: Int -> SingularPath -> ShowS # show :: SingularPath -> String # showList :: [SingularPath] -> ShowS # | |