{-# LANGUAGE DeriveLift #-}
module Data.Aeson.JSONPath.Query.Types
(Query (..)
, QueryType (..)
, Segment (..)
, QuerySegment (..)
, SegmentType (..)
, Selector (..)
, LogicalOrExpr (..)
, LogicalAndExpr (..)
, BasicExpr (..)
, TestExpr
, ComparisonExpr (..)
, ComparisonOp (..)
, Comparable(..)
, SingularQuery (..)
, SingularQueryType (..)
, SingularQuerySegment (..)
)
where
import Data.Text (Text)
import Data.Scientific (Scientific)
import Language.Haskell.TH.Syntax (Lift)
import Prelude
data QueryType
= Root
| Current
deriving (QueryType -> QueryType -> Bool
(QueryType -> QueryType -> Bool)
-> (QueryType -> QueryType -> Bool) -> Eq QueryType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: QueryType -> QueryType -> Bool
== :: QueryType -> QueryType -> Bool
$c/= :: QueryType -> QueryType -> Bool
/= :: QueryType -> QueryType -> Bool
Eq, Int -> QueryType -> ShowS
[QueryType] -> ShowS
QueryType -> String
(Int -> QueryType -> ShowS)
-> (QueryType -> String)
-> ([QueryType] -> ShowS)
-> Show QueryType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> QueryType -> ShowS
showsPrec :: Int -> QueryType -> ShowS
$cshow :: QueryType -> String
show :: QueryType -> String
$cshowList :: [QueryType] -> ShowS
showList :: [QueryType] -> ShowS
Show, (forall (m :: * -> *). Quote m => QueryType -> m Exp)
-> (forall (m :: * -> *). Quote m => QueryType -> Code m QueryType)
-> Lift QueryType
forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => QueryType -> m Exp
forall (m :: * -> *). Quote m => QueryType -> Code m QueryType
$clift :: forall (m :: * -> *). Quote m => QueryType -> m Exp
lift :: forall (m :: * -> *). Quote m => QueryType -> m Exp
$cliftTyped :: forall (m :: * -> *). Quote m => QueryType -> Code m QueryType
liftTyped :: forall (m :: * -> *). Quote m => QueryType -> Code m QueryType
Lift)
data Query = Query
{ Query -> QueryType
queryType :: QueryType
, Query -> [QuerySegment]
querySegments :: [QuerySegment]
} deriving (Query -> Query -> Bool
(Query -> Query -> Bool) -> (Query -> Query -> Bool) -> Eq Query
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Query -> Query -> Bool
== :: Query -> Query -> Bool
$c/= :: Query -> Query -> Bool
/= :: Query -> Query -> Bool
Eq, Int -> Query -> ShowS
[Query] -> ShowS
Query -> String
(Int -> Query -> ShowS)
-> (Query -> String) -> ([Query] -> ShowS) -> Show Query
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Query -> ShowS
showsPrec :: Int -> Query -> ShowS
$cshow :: Query -> String
show :: Query -> String
$cshowList :: [Query] -> ShowS
showList :: [Query] -> ShowS
Show, (forall (m :: * -> *). Quote m => Query -> m Exp)
-> (forall (m :: * -> *). Quote m => Query -> Code m Query)
-> Lift Query
forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => Query -> m Exp
forall (m :: * -> *). Quote m => Query -> Code m Query
$clift :: forall (m :: * -> *). Quote m => Query -> m Exp
lift :: forall (m :: * -> *). Quote m => Query -> m Exp
$cliftTyped :: forall (m :: * -> *). Quote m => Query -> Code m Query
liftTyped :: forall (m :: * -> *). Quote m => Query -> Code m Query
Lift)
data SegmentType
= Child
| Descendant
deriving (SegmentType -> SegmentType -> Bool
(SegmentType -> SegmentType -> Bool)
-> (SegmentType -> SegmentType -> Bool) -> Eq SegmentType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SegmentType -> SegmentType -> Bool
== :: SegmentType -> SegmentType -> Bool
$c/= :: SegmentType -> SegmentType -> Bool
/= :: SegmentType -> SegmentType -> Bool
Eq, Int -> SegmentType -> ShowS
[SegmentType] -> ShowS
SegmentType -> String
(Int -> SegmentType -> ShowS)
-> (SegmentType -> String)
-> ([SegmentType] -> ShowS)
-> Show SegmentType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SegmentType -> ShowS
showsPrec :: Int -> SegmentType -> ShowS
$cshow :: SegmentType -> String
show :: SegmentType -> String
$cshowList :: [SegmentType] -> ShowS
showList :: [SegmentType] -> ShowS
Show, (forall (m :: * -> *). Quote m => SegmentType -> m Exp)
-> (forall (m :: * -> *).
Quote m =>
SegmentType -> Code m SegmentType)
-> Lift SegmentType
forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => SegmentType -> m Exp
forall (m :: * -> *). Quote m => SegmentType -> Code m SegmentType
$clift :: forall (m :: * -> *). Quote m => SegmentType -> m Exp
lift :: forall (m :: * -> *). Quote m => SegmentType -> m Exp
$cliftTyped :: forall (m :: * -> *). Quote m => SegmentType -> Code m SegmentType
liftTyped :: forall (m :: * -> *). Quote m => SegmentType -> Code m SegmentType
Lift)
data QuerySegment = QuerySegment
{ QuerySegment -> SegmentType
segmentType :: SegmentType
, QuerySegment -> Segment
segment :: Segment
} deriving (QuerySegment -> QuerySegment -> Bool
(QuerySegment -> QuerySegment -> Bool)
-> (QuerySegment -> QuerySegment -> Bool) -> Eq QuerySegment
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: QuerySegment -> QuerySegment -> Bool
== :: QuerySegment -> QuerySegment -> Bool
$c/= :: QuerySegment -> QuerySegment -> Bool
/= :: QuerySegment -> QuerySegment -> Bool
Eq, Int -> QuerySegment -> ShowS
[QuerySegment] -> ShowS
QuerySegment -> String
(Int -> QuerySegment -> ShowS)
-> (QuerySegment -> String)
-> ([QuerySegment] -> ShowS)
-> Show QuerySegment
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> QuerySegment -> ShowS
showsPrec :: Int -> QuerySegment -> ShowS
$cshow :: QuerySegment -> String
show :: QuerySegment -> String
$cshowList :: [QuerySegment] -> ShowS
showList :: [QuerySegment] -> ShowS
Show, (forall (m :: * -> *). Quote m => QuerySegment -> m Exp)
-> (forall (m :: * -> *).
Quote m =>
QuerySegment -> Code m QuerySegment)
-> Lift QuerySegment
forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => QuerySegment -> m Exp
forall (m :: * -> *).
Quote m =>
QuerySegment -> Code m QuerySegment
$clift :: forall (m :: * -> *). Quote m => QuerySegment -> m Exp
lift :: forall (m :: * -> *). Quote m => QuerySegment -> m Exp
$cliftTyped :: forall (m :: * -> *).
Quote m =>
QuerySegment -> Code m QuerySegment
liftTyped :: forall (m :: * -> *).
Quote m =>
QuerySegment -> Code m QuerySegment
Lift)
data Segment
= Bracketed [Selector]
| Dotted Text
| WildcardSegment
deriving (Segment -> Segment -> Bool
(Segment -> Segment -> Bool)
-> (Segment -> Segment -> Bool) -> Eq Segment
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Segment -> Segment -> Bool
== :: Segment -> Segment -> Bool
$c/= :: Segment -> Segment -> Bool
/= :: Segment -> Segment -> Bool
Eq, Int -> Segment -> ShowS
[Segment] -> ShowS
Segment -> String
(Int -> Segment -> ShowS)
-> (Segment -> String) -> ([Segment] -> ShowS) -> Show Segment
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Segment -> ShowS
showsPrec :: Int -> Segment -> ShowS
$cshow :: Segment -> String
show :: Segment -> String
$cshowList :: [Segment] -> ShowS
showList :: [Segment] -> ShowS
Show, (forall (m :: * -> *). Quote m => Segment -> m Exp)
-> (forall (m :: * -> *). Quote m => Segment -> Code m Segment)
-> Lift Segment
forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => Segment -> m Exp
forall (m :: * -> *). Quote m => Segment -> Code m Segment
$clift :: forall (m :: * -> *). Quote m => Segment -> m Exp
lift :: forall (m :: * -> *). Quote m => Segment -> m Exp
$cliftTyped :: forall (m :: * -> *). Quote m => Segment -> Code m Segment
liftTyped :: forall (m :: * -> *). Quote m => Segment -> Code m Segment
Lift)
data Selector
= Name Text
| Index Int
| ArraySlice (Maybe Int, Maybe Int, Int)
| Filter LogicalOrExpr
| WildcardSelector
deriving (Selector -> Selector -> Bool
(Selector -> Selector -> Bool)
-> (Selector -> Selector -> Bool) -> Eq Selector
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Selector -> Selector -> Bool
== :: Selector -> Selector -> Bool
$c/= :: Selector -> Selector -> Bool
/= :: Selector -> Selector -> Bool
Eq, Int -> Selector -> ShowS
[Selector] -> ShowS
Selector -> String
(Int -> Selector -> ShowS)
-> (Selector -> String) -> ([Selector] -> ShowS) -> Show Selector
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Selector -> ShowS
showsPrec :: Int -> Selector -> ShowS
$cshow :: Selector -> String
show :: Selector -> String
$cshowList :: [Selector] -> ShowS
showList :: [Selector] -> ShowS
Show, (forall (m :: * -> *). Quote m => Selector -> m Exp)
-> (forall (m :: * -> *). Quote m => Selector -> Code m Selector)
-> Lift Selector
forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => Selector -> m Exp
forall (m :: * -> *). Quote m => Selector -> Code m Selector
$clift :: forall (m :: * -> *). Quote m => Selector -> m Exp
lift :: forall (m :: * -> *). Quote m => Selector -> m Exp
$cliftTyped :: forall (m :: * -> *). Quote m => Selector -> Code m Selector
liftTyped :: forall (m :: * -> *). Quote m => Selector -> Code m Selector
Lift)
newtype LogicalOrExpr
= LogicalOr [LogicalAndExpr]
deriving (LogicalOrExpr -> LogicalOrExpr -> Bool
(LogicalOrExpr -> LogicalOrExpr -> Bool)
-> (LogicalOrExpr -> LogicalOrExpr -> Bool) -> Eq LogicalOrExpr
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: LogicalOrExpr -> LogicalOrExpr -> Bool
== :: LogicalOrExpr -> LogicalOrExpr -> Bool
$c/= :: LogicalOrExpr -> LogicalOrExpr -> Bool
/= :: LogicalOrExpr -> LogicalOrExpr -> Bool
Eq, Int -> LogicalOrExpr -> ShowS
[LogicalOrExpr] -> ShowS
LogicalOrExpr -> String
(Int -> LogicalOrExpr -> ShowS)
-> (LogicalOrExpr -> String)
-> ([LogicalOrExpr] -> ShowS)
-> Show LogicalOrExpr
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> LogicalOrExpr -> ShowS
showsPrec :: Int -> LogicalOrExpr -> ShowS
$cshow :: LogicalOrExpr -> String
show :: LogicalOrExpr -> String
$cshowList :: [LogicalOrExpr] -> ShowS
showList :: [LogicalOrExpr] -> ShowS
Show, (forall (m :: * -> *). Quote m => LogicalOrExpr -> m Exp)
-> (forall (m :: * -> *).
Quote m =>
LogicalOrExpr -> Code m LogicalOrExpr)
-> Lift LogicalOrExpr
forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => LogicalOrExpr -> m Exp
forall (m :: * -> *).
Quote m =>
LogicalOrExpr -> Code m LogicalOrExpr
$clift :: forall (m :: * -> *). Quote m => LogicalOrExpr -> m Exp
lift :: forall (m :: * -> *). Quote m => LogicalOrExpr -> m Exp
$cliftTyped :: forall (m :: * -> *).
Quote m =>
LogicalOrExpr -> Code m LogicalOrExpr
liftTyped :: forall (m :: * -> *).
Quote m =>
LogicalOrExpr -> Code m LogicalOrExpr
Lift)
newtype LogicalAndExpr
= LogicalAnd [BasicExpr]
deriving (LogicalAndExpr -> LogicalAndExpr -> Bool
(LogicalAndExpr -> LogicalAndExpr -> Bool)
-> (LogicalAndExpr -> LogicalAndExpr -> Bool) -> Eq LogicalAndExpr
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: LogicalAndExpr -> LogicalAndExpr -> Bool
== :: LogicalAndExpr -> LogicalAndExpr -> Bool
$c/= :: LogicalAndExpr -> LogicalAndExpr -> Bool
/= :: LogicalAndExpr -> LogicalAndExpr -> Bool
Eq, Int -> LogicalAndExpr -> ShowS
[LogicalAndExpr] -> ShowS
LogicalAndExpr -> String
(Int -> LogicalAndExpr -> ShowS)
-> (LogicalAndExpr -> String)
-> ([LogicalAndExpr] -> ShowS)
-> Show LogicalAndExpr
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> LogicalAndExpr -> ShowS
showsPrec :: Int -> LogicalAndExpr -> ShowS
$cshow :: LogicalAndExpr -> String
show :: LogicalAndExpr -> String
$cshowList :: [LogicalAndExpr] -> ShowS
showList :: [LogicalAndExpr] -> ShowS
Show, (forall (m :: * -> *). Quote m => LogicalAndExpr -> m Exp)
-> (forall (m :: * -> *).
Quote m =>
LogicalAndExpr -> Code m LogicalAndExpr)
-> Lift LogicalAndExpr
forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => LogicalAndExpr -> m Exp
forall (m :: * -> *).
Quote m =>
LogicalAndExpr -> Code m LogicalAndExpr
$clift :: forall (m :: * -> *). Quote m => LogicalAndExpr -> m Exp
lift :: forall (m :: * -> *). Quote m => LogicalAndExpr -> m Exp
$cliftTyped :: forall (m :: * -> *).
Quote m =>
LogicalAndExpr -> Code m LogicalAndExpr
liftTyped :: forall (m :: * -> *).
Quote m =>
LogicalAndExpr -> Code m LogicalAndExpr
Lift)
data BasicExpr
= Paren LogicalOrExpr
| NotParen LogicalOrExpr
| Test TestExpr
| NotTest TestExpr
| Comparison ComparisonExpr
deriving (BasicExpr -> BasicExpr -> Bool
(BasicExpr -> BasicExpr -> Bool)
-> (BasicExpr -> BasicExpr -> Bool) -> Eq BasicExpr
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: BasicExpr -> BasicExpr -> Bool
== :: BasicExpr -> BasicExpr -> Bool
$c/= :: BasicExpr -> BasicExpr -> Bool
/= :: BasicExpr -> BasicExpr -> Bool
Eq, Int -> BasicExpr -> ShowS
[BasicExpr] -> ShowS
BasicExpr -> String
(Int -> BasicExpr -> ShowS)
-> (BasicExpr -> String)
-> ([BasicExpr] -> ShowS)
-> Show BasicExpr
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> BasicExpr -> ShowS
showsPrec :: Int -> BasicExpr -> ShowS
$cshow :: BasicExpr -> String
show :: BasicExpr -> String
$cshowList :: [BasicExpr] -> ShowS
showList :: [BasicExpr] -> ShowS
Show, (forall (m :: * -> *). Quote m => BasicExpr -> m Exp)
-> (forall (m :: * -> *). Quote m => BasicExpr -> Code m BasicExpr)
-> Lift BasicExpr
forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => BasicExpr -> m Exp
forall (m :: * -> *). Quote m => BasicExpr -> Code m BasicExpr
$clift :: forall (m :: * -> *). Quote m => BasicExpr -> m Exp
lift :: forall (m :: * -> *). Quote m => BasicExpr -> m Exp
$cliftTyped :: forall (m :: * -> *). Quote m => BasicExpr -> Code m BasicExpr
liftTyped :: forall (m :: * -> *). Quote m => BasicExpr -> Code m BasicExpr
Lift)
type TestExpr = Query
data ComparisonExpr
= Comp Comparable ComparisonOp Comparable
deriving (ComparisonExpr -> ComparisonExpr -> Bool
(ComparisonExpr -> ComparisonExpr -> Bool)
-> (ComparisonExpr -> ComparisonExpr -> Bool) -> Eq ComparisonExpr
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ComparisonExpr -> ComparisonExpr -> Bool
== :: ComparisonExpr -> ComparisonExpr -> Bool
$c/= :: ComparisonExpr -> ComparisonExpr -> Bool
/= :: ComparisonExpr -> ComparisonExpr -> Bool
Eq, Int -> ComparisonExpr -> ShowS
[ComparisonExpr] -> ShowS
ComparisonExpr -> String
(Int -> ComparisonExpr -> ShowS)
-> (ComparisonExpr -> String)
-> ([ComparisonExpr] -> ShowS)
-> Show ComparisonExpr
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ComparisonExpr -> ShowS
showsPrec :: Int -> ComparisonExpr -> ShowS
$cshow :: ComparisonExpr -> String
show :: ComparisonExpr -> String
$cshowList :: [ComparisonExpr] -> ShowS
showList :: [ComparisonExpr] -> ShowS
Show, (forall (m :: * -> *). Quote m => ComparisonExpr -> m Exp)
-> (forall (m :: * -> *).
Quote m =>
ComparisonExpr -> Code m ComparisonExpr)
-> Lift ComparisonExpr
forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => ComparisonExpr -> m Exp
forall (m :: * -> *).
Quote m =>
ComparisonExpr -> Code m ComparisonExpr
$clift :: forall (m :: * -> *). Quote m => ComparisonExpr -> m Exp
lift :: forall (m :: * -> *). Quote m => ComparisonExpr -> m Exp
$cliftTyped :: forall (m :: * -> *).
Quote m =>
ComparisonExpr -> Code m ComparisonExpr
liftTyped :: forall (m :: * -> *).
Quote m =>
ComparisonExpr -> Code m ComparisonExpr
Lift)
data ComparisonOp
= Less
| LessOrEqual
| Greater
| GreaterOrEqual
| Equal
| NotEqual
deriving (ComparisonOp -> ComparisonOp -> Bool
(ComparisonOp -> ComparisonOp -> Bool)
-> (ComparisonOp -> ComparisonOp -> Bool) -> Eq ComparisonOp
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ComparisonOp -> ComparisonOp -> Bool
== :: ComparisonOp -> ComparisonOp -> Bool
$c/= :: ComparisonOp -> ComparisonOp -> Bool
/= :: ComparisonOp -> ComparisonOp -> Bool
Eq, Int -> ComparisonOp -> ShowS
[ComparisonOp] -> ShowS
ComparisonOp -> String
(Int -> ComparisonOp -> ShowS)
-> (ComparisonOp -> String)
-> ([ComparisonOp] -> ShowS)
-> Show ComparisonOp
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ComparisonOp -> ShowS
showsPrec :: Int -> ComparisonOp -> ShowS
$cshow :: ComparisonOp -> String
show :: ComparisonOp -> String
$cshowList :: [ComparisonOp] -> ShowS
showList :: [ComparisonOp] -> ShowS
Show, (forall (m :: * -> *). Quote m => ComparisonOp -> m Exp)
-> (forall (m :: * -> *).
Quote m =>
ComparisonOp -> Code m ComparisonOp)
-> Lift ComparisonOp
forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => ComparisonOp -> m Exp
forall (m :: * -> *).
Quote m =>
ComparisonOp -> Code m ComparisonOp
$clift :: forall (m :: * -> *). Quote m => ComparisonOp -> m Exp
lift :: forall (m :: * -> *). Quote m => ComparisonOp -> m Exp
$cliftTyped :: forall (m :: * -> *).
Quote m =>
ComparisonOp -> Code m ComparisonOp
liftTyped :: forall (m :: * -> *).
Quote m =>
ComparisonOp -> Code m ComparisonOp
Lift)
data Comparable
= CompLitString Text
| CompLitNum Scientific
| CompLitBool Bool
| CompLitNull
| CompSQ SingularQuery
deriving (Comparable -> Comparable -> Bool
(Comparable -> Comparable -> Bool)
-> (Comparable -> Comparable -> Bool) -> Eq Comparable
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Comparable -> Comparable -> Bool
== :: Comparable -> Comparable -> Bool
$c/= :: Comparable -> Comparable -> Bool
/= :: Comparable -> Comparable -> Bool
Eq, Int -> Comparable -> ShowS
[Comparable] -> ShowS
Comparable -> String
(Int -> Comparable -> ShowS)
-> (Comparable -> String)
-> ([Comparable] -> ShowS)
-> Show Comparable
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Comparable -> ShowS
showsPrec :: Int -> Comparable -> ShowS
$cshow :: Comparable -> String
show :: Comparable -> String
$cshowList :: [Comparable] -> ShowS
showList :: [Comparable] -> ShowS
Show, (forall (m :: * -> *). Quote m => Comparable -> m Exp)
-> (forall (m :: * -> *).
Quote m =>
Comparable -> Code m Comparable)
-> Lift Comparable
forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => Comparable -> m Exp
forall (m :: * -> *). Quote m => Comparable -> Code m Comparable
$clift :: forall (m :: * -> *). Quote m => Comparable -> m Exp
lift :: forall (m :: * -> *). Quote m => Comparable -> m Exp
$cliftTyped :: forall (m :: * -> *). Quote m => Comparable -> Code m Comparable
liftTyped :: forall (m :: * -> *). Quote m => Comparable -> Code m Comparable
Lift)
data SingularQueryType = RootSQ | CurrentSQ
deriving (SingularQueryType -> SingularQueryType -> Bool
(SingularQueryType -> SingularQueryType -> Bool)
-> (SingularQueryType -> SingularQueryType -> Bool)
-> Eq SingularQueryType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SingularQueryType -> SingularQueryType -> Bool
== :: SingularQueryType -> SingularQueryType -> Bool
$c/= :: SingularQueryType -> SingularQueryType -> Bool
/= :: SingularQueryType -> SingularQueryType -> Bool
Eq, Int -> SingularQueryType -> ShowS
[SingularQueryType] -> ShowS
SingularQueryType -> String
(Int -> SingularQueryType -> ShowS)
-> (SingularQueryType -> String)
-> ([SingularQueryType] -> ShowS)
-> Show SingularQueryType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SingularQueryType -> ShowS
showsPrec :: Int -> SingularQueryType -> ShowS
$cshow :: SingularQueryType -> String
show :: SingularQueryType -> String
$cshowList :: [SingularQueryType] -> ShowS
showList :: [SingularQueryType] -> ShowS
Show, (forall (m :: * -> *). Quote m => SingularQueryType -> m Exp)
-> (forall (m :: * -> *).
Quote m =>
SingularQueryType -> Code m SingularQueryType)
-> Lift SingularQueryType
forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => SingularQueryType -> m Exp
forall (m :: * -> *).
Quote m =>
SingularQueryType -> Code m SingularQueryType
$clift :: forall (m :: * -> *). Quote m => SingularQueryType -> m Exp
lift :: forall (m :: * -> *). Quote m => SingularQueryType -> m Exp
$cliftTyped :: forall (m :: * -> *).
Quote m =>
SingularQueryType -> Code m SingularQueryType
liftTyped :: forall (m :: * -> *).
Quote m =>
SingularQueryType -> Code m SingularQueryType
Lift)
data SingularQuery = SingularQuery
{ SingularQuery -> SingularQueryType
singularQueryType :: SingularQueryType
, SingularQuery -> [SingularQuerySegment]
singularQuerySegments :: [SingularQuerySegment]
} deriving (SingularQuery -> SingularQuery -> Bool
(SingularQuery -> SingularQuery -> Bool)
-> (SingularQuery -> SingularQuery -> Bool) -> Eq SingularQuery
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SingularQuery -> SingularQuery -> Bool
== :: SingularQuery -> SingularQuery -> Bool
$c/= :: SingularQuery -> SingularQuery -> Bool
/= :: SingularQuery -> SingularQuery -> Bool
Eq, Int -> SingularQuery -> ShowS
[SingularQuery] -> ShowS
SingularQuery -> String
(Int -> SingularQuery -> ShowS)
-> (SingularQuery -> String)
-> ([SingularQuery] -> ShowS)
-> Show SingularQuery
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SingularQuery -> ShowS
showsPrec :: Int -> SingularQuery -> ShowS
$cshow :: SingularQuery -> String
show :: SingularQuery -> String
$cshowList :: [SingularQuery] -> ShowS
showList :: [SingularQuery] -> ShowS
Show, (forall (m :: * -> *). Quote m => SingularQuery -> m Exp)
-> (forall (m :: * -> *).
Quote m =>
SingularQuery -> Code m SingularQuery)
-> Lift SingularQuery
forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => SingularQuery -> m Exp
forall (m :: * -> *).
Quote m =>
SingularQuery -> Code m SingularQuery
$clift :: forall (m :: * -> *). Quote m => SingularQuery -> m Exp
lift :: forall (m :: * -> *). Quote m => SingularQuery -> m Exp
$cliftTyped :: forall (m :: * -> *).
Quote m =>
SingularQuery -> Code m SingularQuery
liftTyped :: forall (m :: * -> *).
Quote m =>
SingularQuery -> Code m SingularQuery
Lift)
data SingularQuerySegment
= NameSQSeg Text
| IndexSQSeg Int
deriving (SingularQuerySegment -> SingularQuerySegment -> Bool
(SingularQuerySegment -> SingularQuerySegment -> Bool)
-> (SingularQuerySegment -> SingularQuerySegment -> Bool)
-> Eq SingularQuerySegment
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SingularQuerySegment -> SingularQuerySegment -> Bool
== :: SingularQuerySegment -> SingularQuerySegment -> Bool
$c/= :: SingularQuerySegment -> SingularQuerySegment -> Bool
/= :: SingularQuerySegment -> SingularQuerySegment -> Bool
Eq, Int -> SingularQuerySegment -> ShowS
[SingularQuerySegment] -> ShowS
SingularQuerySegment -> String
(Int -> SingularQuerySegment -> ShowS)
-> (SingularQuerySegment -> String)
-> ([SingularQuerySegment] -> ShowS)
-> Show SingularQuerySegment
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SingularQuerySegment -> ShowS
showsPrec :: Int -> SingularQuerySegment -> ShowS
$cshow :: SingularQuerySegment -> String
show :: SingularQuerySegment -> String
$cshowList :: [SingularQuerySegment] -> ShowS
showList :: [SingularQuerySegment] -> ShowS
Show, (forall (m :: * -> *). Quote m => SingularQuerySegment -> m Exp)
-> (forall (m :: * -> *).
Quote m =>
SingularQuerySegment -> Code m SingularQuerySegment)
-> Lift SingularQuerySegment
forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => SingularQuerySegment -> m Exp
forall (m :: * -> *).
Quote m =>
SingularQuerySegment -> Code m SingularQuerySegment
$clift :: forall (m :: * -> *). Quote m => SingularQuerySegment -> m Exp
lift :: forall (m :: * -> *). Quote m => SingularQuerySegment -> m Exp
$cliftTyped :: forall (m :: * -> *).
Quote m =>
SingularQuerySegment -> Code m SingularQuerySegment
liftTyped :: forall (m :: * -> *).
Quote m =>
SingularQuerySegment -> Code m SingularQuerySegment
Lift)