Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
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 #
Instances
Eq BeginningPoint Source # | |
Defined in Data.JSONPath.Types (==) :: BeginningPoint -> BeginningPoint -> Bool # (/=) :: BeginningPoint -> BeginningPoint -> Bool # | |
Show BeginningPoint Source # | |
Defined in Data.JSONPath.Types showsPrec :: Int -> BeginningPoint -> ShowS # show :: BeginningPoint -> String # showList :: [BeginningPoint] -> ShowS # |
Instances
data Comparable Source #
Instances
Eq Comparable Source # | |
Defined in Data.JSONPath.Types (==) :: Comparable -> Comparable -> Bool # (/=) :: Comparable -> Comparable -> Bool # | |
Show Comparable Source # | |
Defined in Data.JSONPath.Types showsPrec :: Int -> Comparable -> ShowS # show :: Comparable -> String # showList :: [Comparable] -> ShowS # |
data JSONPathElement Source #
A JSONPath
is a list of JSONPathElement
s.
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 (==) :: JSONPathElement -> JSONPathElement -> Bool # (/=) :: JSONPathElement -> JSONPathElement -> Bool # | |
Show JSONPathElement Source # | |
Defined in Data.JSONPath.Types 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 (==) :: UnionElement -> UnionElement -> Bool # (/=) :: UnionElement -> UnionElement -> Bool # | |
Show UnionElement Source # | |
Defined in Data.JSONPath.Types showsPrec :: Int -> UnionElement -> ShowS # show :: UnionElement -> String # showList :: [UnionElement] -> ShowS # |
data FilterExpr Source #
ExistsExpr SingularPath | |
ComparisonExpr Comparable Condition Comparable | |
And FilterExpr FilterExpr | |
Or FilterExpr FilterExpr | |
Not FilterExpr |
Instances
Eq FilterExpr Source # | |
Defined in Data.JSONPath.Types (==) :: FilterExpr -> FilterExpr -> Bool # (/=) :: FilterExpr -> FilterExpr -> Bool # | |
Show FilterExpr Source # | |
Defined in Data.JSONPath.Types showsPrec :: Int -> FilterExpr -> ShowS # show :: FilterExpr -> String # showList :: [FilterExpr] -> ShowS # |
data SingularPathElement Source #
Instances
Eq SingularPathElement Source # | |
Defined in Data.JSONPath.Types (==) :: SingularPathElement -> SingularPathElement -> Bool # (/=) :: SingularPathElement -> SingularPathElement -> Bool # | |
Show SingularPathElement Source # | |
Defined in Data.JSONPath.Types 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
.
Instances
Eq SingularPath Source # | |
Defined in Data.JSONPath.Types (==) :: SingularPath -> SingularPath -> Bool # (/=) :: SingularPath -> SingularPath -> Bool # | |
Show SingularPath Source # | |
Defined in Data.JSONPath.Types showsPrec :: Int -> SingularPath -> ShowS # show :: SingularPath -> String # showList :: [SingularPath] -> ShowS # |