module Hydra.Langs.Kusto.Kql where
import qualified Hydra.Core as Core
import Data.Int
import Data.List as L
import Data.Map as M
import Data.Set as S
data BetweenExpression =
BetweenExpression {
BetweenExpression -> Bool
betweenExpressionNot :: Bool,
BetweenExpression -> Expression
betweenExpressionExpression :: Expression,
BetweenExpression -> Expression
betweenExpressionLowerBound :: Expression,
BetweenExpression -> Expression
betweenExpressionUpperBound :: Expression}
deriving (BetweenExpression -> BetweenExpression -> Bool
(BetweenExpression -> BetweenExpression -> Bool)
-> (BetweenExpression -> BetweenExpression -> Bool)
-> Eq BetweenExpression
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: BetweenExpression -> BetweenExpression -> Bool
== :: BetweenExpression -> BetweenExpression -> Bool
$c/= :: BetweenExpression -> BetweenExpression -> Bool
/= :: BetweenExpression -> BetweenExpression -> Bool
Eq, Eq BetweenExpression
Eq BetweenExpression =>
(BetweenExpression -> BetweenExpression -> Ordering)
-> (BetweenExpression -> BetweenExpression -> Bool)
-> (BetweenExpression -> BetweenExpression -> Bool)
-> (BetweenExpression -> BetweenExpression -> Bool)
-> (BetweenExpression -> BetweenExpression -> Bool)
-> (BetweenExpression -> BetweenExpression -> BetweenExpression)
-> (BetweenExpression -> BetweenExpression -> BetweenExpression)
-> Ord BetweenExpression
BetweenExpression -> BetweenExpression -> Bool
BetweenExpression -> BetweenExpression -> Ordering
BetweenExpression -> BetweenExpression -> BetweenExpression
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: BetweenExpression -> BetweenExpression -> Ordering
compare :: BetweenExpression -> BetweenExpression -> Ordering
$c< :: BetweenExpression -> BetweenExpression -> Bool
< :: BetweenExpression -> BetweenExpression -> Bool
$c<= :: BetweenExpression -> BetweenExpression -> Bool
<= :: BetweenExpression -> BetweenExpression -> Bool
$c> :: BetweenExpression -> BetweenExpression -> Bool
> :: BetweenExpression -> BetweenExpression -> Bool
$c>= :: BetweenExpression -> BetweenExpression -> Bool
>= :: BetweenExpression -> BetweenExpression -> Bool
$cmax :: BetweenExpression -> BetweenExpression -> BetweenExpression
max :: BetweenExpression -> BetweenExpression -> BetweenExpression
$cmin :: BetweenExpression -> BetweenExpression -> BetweenExpression
min :: BetweenExpression -> BetweenExpression -> BetweenExpression
Ord, ReadPrec [BetweenExpression]
ReadPrec BetweenExpression
Int -> ReadS BetweenExpression
ReadS [BetweenExpression]
(Int -> ReadS BetweenExpression)
-> ReadS [BetweenExpression]
-> ReadPrec BetweenExpression
-> ReadPrec [BetweenExpression]
-> Read BetweenExpression
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS BetweenExpression
readsPrec :: Int -> ReadS BetweenExpression
$creadList :: ReadS [BetweenExpression]
readList :: ReadS [BetweenExpression]
$creadPrec :: ReadPrec BetweenExpression
readPrec :: ReadPrec BetweenExpression
$creadListPrec :: ReadPrec [BetweenExpression]
readListPrec :: ReadPrec [BetweenExpression]
Read, Int -> BetweenExpression -> ShowS
[BetweenExpression] -> ShowS
BetweenExpression -> String
(Int -> BetweenExpression -> ShowS)
-> (BetweenExpression -> String)
-> ([BetweenExpression] -> ShowS)
-> Show BetweenExpression
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> BetweenExpression -> ShowS
showsPrec :: Int -> BetweenExpression -> ShowS
$cshow :: BetweenExpression -> String
show :: BetweenExpression -> String
$cshowList :: [BetweenExpression] -> ShowS
showList :: [BetweenExpression] -> ShowS
Show)
_BetweenExpression :: Name
_BetweenExpression = (String -> Name
Core.Name String
"hydra/langs/kusto/kql.BetweenExpression")
_BetweenExpression_not :: Name
_BetweenExpression_not = (String -> Name
Core.Name String
"not")
_BetweenExpression_expression :: Name
_BetweenExpression_expression = (String -> Name
Core.Name String
"expression")
_BetweenExpression_lowerBound :: Name
_BetweenExpression_lowerBound = (String -> Name
Core.Name String
"lowerBound")
_BetweenExpression_upperBound :: Name
_BetweenExpression_upperBound = (String -> Name
Core.Name String
"upperBound")
data BinaryExpression =
BinaryExpression {
BinaryExpression -> Expression
binaryExpressionLeft :: Expression,
BinaryExpression -> BinaryOperator
binaryExpressionOperator :: BinaryOperator,
BinaryExpression -> Expression
binaryExpressionRight :: Expression}
deriving (BinaryExpression -> BinaryExpression -> Bool
(BinaryExpression -> BinaryExpression -> Bool)
-> (BinaryExpression -> BinaryExpression -> Bool)
-> Eq BinaryExpression
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: BinaryExpression -> BinaryExpression -> Bool
== :: BinaryExpression -> BinaryExpression -> Bool
$c/= :: BinaryExpression -> BinaryExpression -> Bool
/= :: BinaryExpression -> BinaryExpression -> Bool
Eq, Eq BinaryExpression
Eq BinaryExpression =>
(BinaryExpression -> BinaryExpression -> Ordering)
-> (BinaryExpression -> BinaryExpression -> Bool)
-> (BinaryExpression -> BinaryExpression -> Bool)
-> (BinaryExpression -> BinaryExpression -> Bool)
-> (BinaryExpression -> BinaryExpression -> Bool)
-> (BinaryExpression -> BinaryExpression -> BinaryExpression)
-> (BinaryExpression -> BinaryExpression -> BinaryExpression)
-> Ord BinaryExpression
BinaryExpression -> BinaryExpression -> Bool
BinaryExpression -> BinaryExpression -> Ordering
BinaryExpression -> BinaryExpression -> BinaryExpression
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: BinaryExpression -> BinaryExpression -> Ordering
compare :: BinaryExpression -> BinaryExpression -> Ordering
$c< :: BinaryExpression -> BinaryExpression -> Bool
< :: BinaryExpression -> BinaryExpression -> Bool
$c<= :: BinaryExpression -> BinaryExpression -> Bool
<= :: BinaryExpression -> BinaryExpression -> Bool
$c> :: BinaryExpression -> BinaryExpression -> Bool
> :: BinaryExpression -> BinaryExpression -> Bool
$c>= :: BinaryExpression -> BinaryExpression -> Bool
>= :: BinaryExpression -> BinaryExpression -> Bool
$cmax :: BinaryExpression -> BinaryExpression -> BinaryExpression
max :: BinaryExpression -> BinaryExpression -> BinaryExpression
$cmin :: BinaryExpression -> BinaryExpression -> BinaryExpression
min :: BinaryExpression -> BinaryExpression -> BinaryExpression
Ord, ReadPrec [BinaryExpression]
ReadPrec BinaryExpression
Int -> ReadS BinaryExpression
ReadS [BinaryExpression]
(Int -> ReadS BinaryExpression)
-> ReadS [BinaryExpression]
-> ReadPrec BinaryExpression
-> ReadPrec [BinaryExpression]
-> Read BinaryExpression
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS BinaryExpression
readsPrec :: Int -> ReadS BinaryExpression
$creadList :: ReadS [BinaryExpression]
readList :: ReadS [BinaryExpression]
$creadPrec :: ReadPrec BinaryExpression
readPrec :: ReadPrec BinaryExpression
$creadListPrec :: ReadPrec [BinaryExpression]
readListPrec :: ReadPrec [BinaryExpression]
Read, Int -> BinaryExpression -> ShowS
[BinaryExpression] -> ShowS
BinaryExpression -> String
(Int -> BinaryExpression -> ShowS)
-> (BinaryExpression -> String)
-> ([BinaryExpression] -> ShowS)
-> Show BinaryExpression
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> BinaryExpression -> ShowS
showsPrec :: Int -> BinaryExpression -> ShowS
$cshow :: BinaryExpression -> String
show :: BinaryExpression -> String
$cshowList :: [BinaryExpression] -> ShowS
showList :: [BinaryExpression] -> ShowS
Show)
_BinaryExpression :: Name
_BinaryExpression = (String -> Name
Core.Name String
"hydra/langs/kusto/kql.BinaryExpression")
_BinaryExpression_left :: Name
_BinaryExpression_left = (String -> Name
Core.Name String
"left")
_BinaryExpression_operator :: Name
_BinaryExpression_operator = (String -> Name
Core.Name String
"operator")
_BinaryExpression_right :: Name
_BinaryExpression_right = (String -> Name
Core.Name String
"right")
data BinaryOperator =
BinaryOperatorCaseInsensitiveEqual |
BinaryOperatorContains |
BinaryOperatorDivide |
BinaryOperatorEndsWith |
BinaryOperatorEqual |
BinaryOperatorGreater |
BinaryOperatorGreaterOrEqual |
BinaryOperatorHas |
BinaryOperatorHasPrefix |
BinaryOperatorHasSuffix |
BinaryOperatorLess |
BinaryOperatorLessOrEqual |
BinaryOperatorMatchesRegex |
BinaryOperatorMinus |
BinaryOperatorNotEqual |
BinaryOperatorPlus |
BinaryOperatorStartsWith |
BinaryOperatorTimes
deriving (BinaryOperator -> BinaryOperator -> Bool
(BinaryOperator -> BinaryOperator -> Bool)
-> (BinaryOperator -> BinaryOperator -> Bool) -> Eq BinaryOperator
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: BinaryOperator -> BinaryOperator -> Bool
== :: BinaryOperator -> BinaryOperator -> Bool
$c/= :: BinaryOperator -> BinaryOperator -> Bool
/= :: BinaryOperator -> BinaryOperator -> Bool
Eq, Eq BinaryOperator
Eq BinaryOperator =>
(BinaryOperator -> BinaryOperator -> Ordering)
-> (BinaryOperator -> BinaryOperator -> Bool)
-> (BinaryOperator -> BinaryOperator -> Bool)
-> (BinaryOperator -> BinaryOperator -> Bool)
-> (BinaryOperator -> BinaryOperator -> Bool)
-> (BinaryOperator -> BinaryOperator -> BinaryOperator)
-> (BinaryOperator -> BinaryOperator -> BinaryOperator)
-> Ord BinaryOperator
BinaryOperator -> BinaryOperator -> Bool
BinaryOperator -> BinaryOperator -> Ordering
BinaryOperator -> BinaryOperator -> BinaryOperator
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: BinaryOperator -> BinaryOperator -> Ordering
compare :: BinaryOperator -> BinaryOperator -> Ordering
$c< :: BinaryOperator -> BinaryOperator -> Bool
< :: BinaryOperator -> BinaryOperator -> Bool
$c<= :: BinaryOperator -> BinaryOperator -> Bool
<= :: BinaryOperator -> BinaryOperator -> Bool
$c> :: BinaryOperator -> BinaryOperator -> Bool
> :: BinaryOperator -> BinaryOperator -> Bool
$c>= :: BinaryOperator -> BinaryOperator -> Bool
>= :: BinaryOperator -> BinaryOperator -> Bool
$cmax :: BinaryOperator -> BinaryOperator -> BinaryOperator
max :: BinaryOperator -> BinaryOperator -> BinaryOperator
$cmin :: BinaryOperator -> BinaryOperator -> BinaryOperator
min :: BinaryOperator -> BinaryOperator -> BinaryOperator
Ord, ReadPrec [BinaryOperator]
ReadPrec BinaryOperator
Int -> ReadS BinaryOperator
ReadS [BinaryOperator]
(Int -> ReadS BinaryOperator)
-> ReadS [BinaryOperator]
-> ReadPrec BinaryOperator
-> ReadPrec [BinaryOperator]
-> Read BinaryOperator
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS BinaryOperator
readsPrec :: Int -> ReadS BinaryOperator
$creadList :: ReadS [BinaryOperator]
readList :: ReadS [BinaryOperator]
$creadPrec :: ReadPrec BinaryOperator
readPrec :: ReadPrec BinaryOperator
$creadListPrec :: ReadPrec [BinaryOperator]
readListPrec :: ReadPrec [BinaryOperator]
Read, Int -> BinaryOperator -> ShowS
[BinaryOperator] -> ShowS
BinaryOperator -> String
(Int -> BinaryOperator -> ShowS)
-> (BinaryOperator -> String)
-> ([BinaryOperator] -> ShowS)
-> Show BinaryOperator
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> BinaryOperator -> ShowS
showsPrec :: Int -> BinaryOperator -> ShowS
$cshow :: BinaryOperator -> String
show :: BinaryOperator -> String
$cshowList :: [BinaryOperator] -> ShowS
showList :: [BinaryOperator] -> ShowS
Show)
_BinaryOperator :: Name
_BinaryOperator = (String -> Name
Core.Name String
"hydra/langs/kusto/kql.BinaryOperator")
_BinaryOperator_caseInsensitiveEqual :: Name
_BinaryOperator_caseInsensitiveEqual = (String -> Name
Core.Name String
"caseInsensitiveEqual")
_BinaryOperator_contains :: Name
_BinaryOperator_contains = (String -> Name
Core.Name String
"contains")
_BinaryOperator_divide :: Name
_BinaryOperator_divide = (String -> Name
Core.Name String
"divide")
_BinaryOperator_endsWith :: Name
_BinaryOperator_endsWith = (String -> Name
Core.Name String
"endsWith")
_BinaryOperator_equal :: Name
_BinaryOperator_equal = (String -> Name
Core.Name String
"equal")
_BinaryOperator_greater :: Name
_BinaryOperator_greater = (String -> Name
Core.Name String
"greater")
_BinaryOperator_greaterOrEqual :: Name
_BinaryOperator_greaterOrEqual = (String -> Name
Core.Name String
"greaterOrEqual")
_BinaryOperator_has :: Name
_BinaryOperator_has = (String -> Name
Core.Name String
"has")
_BinaryOperator_hasPrefix :: Name
_BinaryOperator_hasPrefix = (String -> Name
Core.Name String
"hasPrefix")
_BinaryOperator_hasSuffix :: Name
_BinaryOperator_hasSuffix = (String -> Name
Core.Name String
"hasSuffix")
_BinaryOperator_less :: Name
_BinaryOperator_less = (String -> Name
Core.Name String
"less")
_BinaryOperator_lessOrEqual :: Name
_BinaryOperator_lessOrEqual = (String -> Name
Core.Name String
"lessOrEqual")
_BinaryOperator_matchesRegex :: Name
_BinaryOperator_matchesRegex = (String -> Name
Core.Name String
"matchesRegex")
_BinaryOperator_minus :: Name
_BinaryOperator_minus = (String -> Name
Core.Name String
"minus")
_BinaryOperator_notEqual :: Name
_BinaryOperator_notEqual = (String -> Name
Core.Name String
"notEqual")
_BinaryOperator_plus :: Name
_BinaryOperator_plus = (String -> Name
Core.Name String
"plus")
_BinaryOperator_startsWith :: Name
_BinaryOperator_startsWith = (String -> Name
Core.Name String
"startsWith")
_BinaryOperator_times :: Name
_BinaryOperator_times = (String -> Name
Core.Name String
"times")
data BuiltInFunction =
BuiltInFunctionAgo |
BuiltInFunctionBin |
BuiltInFunctionCount |
BuiltInFunctionDcount |
BuiltInFunctionEndofday |
|
BuiltInFunctionFormat_datetime |
BuiltInFunctionMaterialize |
BuiltInFunctionNow |
BuiltInFunctionRange |
BuiltInFunctionStartofday |
BuiltInFunctionStrcat |
BuiltInFunctionTodynamic
deriving (BuiltInFunction -> BuiltInFunction -> Bool
(BuiltInFunction -> BuiltInFunction -> Bool)
-> (BuiltInFunction -> BuiltInFunction -> Bool)
-> Eq BuiltInFunction
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: BuiltInFunction -> BuiltInFunction -> Bool
== :: BuiltInFunction -> BuiltInFunction -> Bool
$c/= :: BuiltInFunction -> BuiltInFunction -> Bool
/= :: BuiltInFunction -> BuiltInFunction -> Bool
Eq, Eq BuiltInFunction
Eq BuiltInFunction =>
(BuiltInFunction -> BuiltInFunction -> Ordering)
-> (BuiltInFunction -> BuiltInFunction -> Bool)
-> (BuiltInFunction -> BuiltInFunction -> Bool)
-> (BuiltInFunction -> BuiltInFunction -> Bool)
-> (BuiltInFunction -> BuiltInFunction -> Bool)
-> (BuiltInFunction -> BuiltInFunction -> BuiltInFunction)
-> (BuiltInFunction -> BuiltInFunction -> BuiltInFunction)
-> Ord BuiltInFunction
BuiltInFunction -> BuiltInFunction -> Bool
BuiltInFunction -> BuiltInFunction -> Ordering
BuiltInFunction -> BuiltInFunction -> BuiltInFunction
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: BuiltInFunction -> BuiltInFunction -> Ordering
compare :: BuiltInFunction -> BuiltInFunction -> Ordering
$c< :: BuiltInFunction -> BuiltInFunction -> Bool
< :: BuiltInFunction -> BuiltInFunction -> Bool
$c<= :: BuiltInFunction -> BuiltInFunction -> Bool
<= :: BuiltInFunction -> BuiltInFunction -> Bool
$c> :: BuiltInFunction -> BuiltInFunction -> Bool
> :: BuiltInFunction -> BuiltInFunction -> Bool
$c>= :: BuiltInFunction -> BuiltInFunction -> Bool
>= :: BuiltInFunction -> BuiltInFunction -> Bool
$cmax :: BuiltInFunction -> BuiltInFunction -> BuiltInFunction
max :: BuiltInFunction -> BuiltInFunction -> BuiltInFunction
$cmin :: BuiltInFunction -> BuiltInFunction -> BuiltInFunction
min :: BuiltInFunction -> BuiltInFunction -> BuiltInFunction
Ord, ReadPrec [BuiltInFunction]
ReadPrec BuiltInFunction
Int -> ReadS BuiltInFunction
ReadS [BuiltInFunction]
(Int -> ReadS BuiltInFunction)
-> ReadS [BuiltInFunction]
-> ReadPrec BuiltInFunction
-> ReadPrec [BuiltInFunction]
-> Read BuiltInFunction
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS BuiltInFunction
readsPrec :: Int -> ReadS BuiltInFunction
$creadList :: ReadS [BuiltInFunction]
readList :: ReadS [BuiltInFunction]
$creadPrec :: ReadPrec BuiltInFunction
readPrec :: ReadPrec BuiltInFunction
$creadListPrec :: ReadPrec [BuiltInFunction]
readListPrec :: ReadPrec [BuiltInFunction]
Read, Int -> BuiltInFunction -> ShowS
[BuiltInFunction] -> ShowS
BuiltInFunction -> String
(Int -> BuiltInFunction -> ShowS)
-> (BuiltInFunction -> String)
-> ([BuiltInFunction] -> ShowS)
-> Show BuiltInFunction
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> BuiltInFunction -> ShowS
showsPrec :: Int -> BuiltInFunction -> ShowS
$cshow :: BuiltInFunction -> String
show :: BuiltInFunction -> String
$cshowList :: [BuiltInFunction] -> ShowS
showList :: [BuiltInFunction] -> ShowS
Show)
_BuiltInFunction :: Name
_BuiltInFunction = (String -> Name
Core.Name String
"hydra/langs/kusto/kql.BuiltInFunction")
_BuiltInFunction_ago :: Name
_BuiltInFunction_ago = (String -> Name
Core.Name String
"ago")
_BuiltInFunction_bin :: Name
_BuiltInFunction_bin = (String -> Name
Core.Name String
"bin")
_BuiltInFunction_count :: Name
_BuiltInFunction_count = (String -> Name
Core.Name String
"count")
_BuiltInFunction_dcount :: Name
_BuiltInFunction_dcount = (String -> Name
Core.Name String
"dcount")
_BuiltInFunction_endofday :: Name
_BuiltInFunction_endofday = (String -> Name
Core.Name String
"endofday")
= (String -> Name
Core.Name String
"extract")
_BuiltInFunction_format_datetime :: Name
_BuiltInFunction_format_datetime = (String -> Name
Core.Name String
"format_datetime")
_BuiltInFunction_materialize :: Name
_BuiltInFunction_materialize = (String -> Name
Core.Name String
"materialize")
_BuiltInFunction_now :: Name
_BuiltInFunction_now = (String -> Name
Core.Name String
"now")
_BuiltInFunction_range :: Name
_BuiltInFunction_range = (String -> Name
Core.Name String
"range")
_BuiltInFunction_startofday :: Name
_BuiltInFunction_startofday = (String -> Name
Core.Name String
"startofday")
_BuiltInFunction_strcat :: Name
_BuiltInFunction_strcat = (String -> Name
Core.Name String
"strcat")
_BuiltInFunction_todynamic :: Name
_BuiltInFunction_todynamic = (String -> Name
Core.Name String
"todynamic")
data ColumnAlias =
ColumnAlias {
ColumnAlias -> ColumnName
columnAliasColumn :: ColumnName,
ColumnAlias -> ColumnName
columnAliasAlias :: ColumnName}
deriving (ColumnAlias -> ColumnAlias -> Bool
(ColumnAlias -> ColumnAlias -> Bool)
-> (ColumnAlias -> ColumnAlias -> Bool) -> Eq ColumnAlias
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ColumnAlias -> ColumnAlias -> Bool
== :: ColumnAlias -> ColumnAlias -> Bool
$c/= :: ColumnAlias -> ColumnAlias -> Bool
/= :: ColumnAlias -> ColumnAlias -> Bool
Eq, Eq ColumnAlias
Eq ColumnAlias =>
(ColumnAlias -> ColumnAlias -> Ordering)
-> (ColumnAlias -> ColumnAlias -> Bool)
-> (ColumnAlias -> ColumnAlias -> Bool)
-> (ColumnAlias -> ColumnAlias -> Bool)
-> (ColumnAlias -> ColumnAlias -> Bool)
-> (ColumnAlias -> ColumnAlias -> ColumnAlias)
-> (ColumnAlias -> ColumnAlias -> ColumnAlias)
-> Ord ColumnAlias
ColumnAlias -> ColumnAlias -> Bool
ColumnAlias -> ColumnAlias -> Ordering
ColumnAlias -> ColumnAlias -> ColumnAlias
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ColumnAlias -> ColumnAlias -> Ordering
compare :: ColumnAlias -> ColumnAlias -> Ordering
$c< :: ColumnAlias -> ColumnAlias -> Bool
< :: ColumnAlias -> ColumnAlias -> Bool
$c<= :: ColumnAlias -> ColumnAlias -> Bool
<= :: ColumnAlias -> ColumnAlias -> Bool
$c> :: ColumnAlias -> ColumnAlias -> Bool
> :: ColumnAlias -> ColumnAlias -> Bool
$c>= :: ColumnAlias -> ColumnAlias -> Bool
>= :: ColumnAlias -> ColumnAlias -> Bool
$cmax :: ColumnAlias -> ColumnAlias -> ColumnAlias
max :: ColumnAlias -> ColumnAlias -> ColumnAlias
$cmin :: ColumnAlias -> ColumnAlias -> ColumnAlias
min :: ColumnAlias -> ColumnAlias -> ColumnAlias
Ord, ReadPrec [ColumnAlias]
ReadPrec ColumnAlias
Int -> ReadS ColumnAlias
ReadS [ColumnAlias]
(Int -> ReadS ColumnAlias)
-> ReadS [ColumnAlias]
-> ReadPrec ColumnAlias
-> ReadPrec [ColumnAlias]
-> Read ColumnAlias
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ColumnAlias
readsPrec :: Int -> ReadS ColumnAlias
$creadList :: ReadS [ColumnAlias]
readList :: ReadS [ColumnAlias]
$creadPrec :: ReadPrec ColumnAlias
readPrec :: ReadPrec ColumnAlias
$creadListPrec :: ReadPrec [ColumnAlias]
readListPrec :: ReadPrec [ColumnAlias]
Read, Int -> ColumnAlias -> ShowS
[ColumnAlias] -> ShowS
ColumnAlias -> String
(Int -> ColumnAlias -> ShowS)
-> (ColumnAlias -> String)
-> ([ColumnAlias] -> ShowS)
-> Show ColumnAlias
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ColumnAlias -> ShowS
showsPrec :: Int -> ColumnAlias -> ShowS
$cshow :: ColumnAlias -> String
show :: ColumnAlias -> String
$cshowList :: [ColumnAlias] -> ShowS
showList :: [ColumnAlias] -> ShowS
Show)
_ColumnAlias :: Name
_ColumnAlias = (String -> Name
Core.Name String
"hydra/langs/kusto/kql.ColumnAlias")
_ColumnAlias_column :: Name
_ColumnAlias_column = (String -> Name
Core.Name String
"column")
_ColumnAlias_alias :: Name
_ColumnAlias_alias = (String -> Name
Core.Name String
"alias")
data ColumnAssignment =
ColumnAssignment {
ColumnAssignment -> ColumnName
columnAssignmentColumn :: ColumnName,
ColumnAssignment -> Expression
columnAssignmentExpression :: Expression}
deriving (ColumnAssignment -> ColumnAssignment -> Bool
(ColumnAssignment -> ColumnAssignment -> Bool)
-> (ColumnAssignment -> ColumnAssignment -> Bool)
-> Eq ColumnAssignment
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ColumnAssignment -> ColumnAssignment -> Bool
== :: ColumnAssignment -> ColumnAssignment -> Bool
$c/= :: ColumnAssignment -> ColumnAssignment -> Bool
/= :: ColumnAssignment -> ColumnAssignment -> Bool
Eq, Eq ColumnAssignment
Eq ColumnAssignment =>
(ColumnAssignment -> ColumnAssignment -> Ordering)
-> (ColumnAssignment -> ColumnAssignment -> Bool)
-> (ColumnAssignment -> ColumnAssignment -> Bool)
-> (ColumnAssignment -> ColumnAssignment -> Bool)
-> (ColumnAssignment -> ColumnAssignment -> Bool)
-> (ColumnAssignment -> ColumnAssignment -> ColumnAssignment)
-> (ColumnAssignment -> ColumnAssignment -> ColumnAssignment)
-> Ord ColumnAssignment
ColumnAssignment -> ColumnAssignment -> Bool
ColumnAssignment -> ColumnAssignment -> Ordering
ColumnAssignment -> ColumnAssignment -> ColumnAssignment
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ColumnAssignment -> ColumnAssignment -> Ordering
compare :: ColumnAssignment -> ColumnAssignment -> Ordering
$c< :: ColumnAssignment -> ColumnAssignment -> Bool
< :: ColumnAssignment -> ColumnAssignment -> Bool
$c<= :: ColumnAssignment -> ColumnAssignment -> Bool
<= :: ColumnAssignment -> ColumnAssignment -> Bool
$c> :: ColumnAssignment -> ColumnAssignment -> Bool
> :: ColumnAssignment -> ColumnAssignment -> Bool
$c>= :: ColumnAssignment -> ColumnAssignment -> Bool
>= :: ColumnAssignment -> ColumnAssignment -> Bool
$cmax :: ColumnAssignment -> ColumnAssignment -> ColumnAssignment
max :: ColumnAssignment -> ColumnAssignment -> ColumnAssignment
$cmin :: ColumnAssignment -> ColumnAssignment -> ColumnAssignment
min :: ColumnAssignment -> ColumnAssignment -> ColumnAssignment
Ord, ReadPrec [ColumnAssignment]
ReadPrec ColumnAssignment
Int -> ReadS ColumnAssignment
ReadS [ColumnAssignment]
(Int -> ReadS ColumnAssignment)
-> ReadS [ColumnAssignment]
-> ReadPrec ColumnAssignment
-> ReadPrec [ColumnAssignment]
-> Read ColumnAssignment
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ColumnAssignment
readsPrec :: Int -> ReadS ColumnAssignment
$creadList :: ReadS [ColumnAssignment]
readList :: ReadS [ColumnAssignment]
$creadPrec :: ReadPrec ColumnAssignment
readPrec :: ReadPrec ColumnAssignment
$creadListPrec :: ReadPrec [ColumnAssignment]
readListPrec :: ReadPrec [ColumnAssignment]
Read, Int -> ColumnAssignment -> ShowS
[ColumnAssignment] -> ShowS
ColumnAssignment -> String
(Int -> ColumnAssignment -> ShowS)
-> (ColumnAssignment -> String)
-> ([ColumnAssignment] -> ShowS)
-> Show ColumnAssignment
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ColumnAssignment -> ShowS
showsPrec :: Int -> ColumnAssignment -> ShowS
$cshow :: ColumnAssignment -> String
show :: ColumnAssignment -> String
$cshowList :: [ColumnAssignment] -> ShowS
showList :: [ColumnAssignment] -> ShowS
Show)
_ColumnAssignment :: Name
_ColumnAssignment = (String -> Name
Core.Name String
"hydra/langs/kusto/kql.ColumnAssignment")
_ColumnAssignment_column :: Name
_ColumnAssignment_column = (String -> Name
Core.Name String
"column")
_ColumnAssignment_expression :: Name
_ColumnAssignment_expression = (String -> Name
Core.Name String
"expression")
newtype ColumnName =
ColumnName {
ColumnName -> String
unColumnName :: String}
deriving (ColumnName -> ColumnName -> Bool
(ColumnName -> ColumnName -> Bool)
-> (ColumnName -> ColumnName -> Bool) -> Eq ColumnName
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ColumnName -> ColumnName -> Bool
== :: ColumnName -> ColumnName -> Bool
$c/= :: ColumnName -> ColumnName -> Bool
/= :: ColumnName -> ColumnName -> Bool
Eq, Eq ColumnName
Eq ColumnName =>
(ColumnName -> ColumnName -> Ordering)
-> (ColumnName -> ColumnName -> Bool)
-> (ColumnName -> ColumnName -> Bool)
-> (ColumnName -> ColumnName -> Bool)
-> (ColumnName -> ColumnName -> Bool)
-> (ColumnName -> ColumnName -> ColumnName)
-> (ColumnName -> ColumnName -> ColumnName)
-> Ord ColumnName
ColumnName -> ColumnName -> Bool
ColumnName -> ColumnName -> Ordering
ColumnName -> ColumnName -> ColumnName
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ColumnName -> ColumnName -> Ordering
compare :: ColumnName -> ColumnName -> Ordering
$c< :: ColumnName -> ColumnName -> Bool
< :: ColumnName -> ColumnName -> Bool
$c<= :: ColumnName -> ColumnName -> Bool
<= :: ColumnName -> ColumnName -> Bool
$c> :: ColumnName -> ColumnName -> Bool
> :: ColumnName -> ColumnName -> Bool
$c>= :: ColumnName -> ColumnName -> Bool
>= :: ColumnName -> ColumnName -> Bool
$cmax :: ColumnName -> ColumnName -> ColumnName
max :: ColumnName -> ColumnName -> ColumnName
$cmin :: ColumnName -> ColumnName -> ColumnName
min :: ColumnName -> ColumnName -> ColumnName
Ord, ReadPrec [ColumnName]
ReadPrec ColumnName
Int -> ReadS ColumnName
ReadS [ColumnName]
(Int -> ReadS ColumnName)
-> ReadS [ColumnName]
-> ReadPrec ColumnName
-> ReadPrec [ColumnName]
-> Read ColumnName
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ColumnName
readsPrec :: Int -> ReadS ColumnName
$creadList :: ReadS [ColumnName]
readList :: ReadS [ColumnName]
$creadPrec :: ReadPrec ColumnName
readPrec :: ReadPrec ColumnName
$creadListPrec :: ReadPrec [ColumnName]
readListPrec :: ReadPrec [ColumnName]
Read, Int -> ColumnName -> ShowS
[ColumnName] -> ShowS
ColumnName -> String
(Int -> ColumnName -> ShowS)
-> (ColumnName -> String)
-> ([ColumnName] -> ShowS)
-> Show ColumnName
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ColumnName -> ShowS
showsPrec :: Int -> ColumnName -> ShowS
$cshow :: ColumnName -> String
show :: ColumnName -> String
$cshowList :: [ColumnName] -> ShowS
showList :: [ColumnName] -> ShowS
Show)
_ColumnName :: Name
_ColumnName = (String -> Name
Core.Name String
"hydra/langs/kusto/kql.ColumnName")
data Columns =
ColumnsAll |
ColumnsSingle ColumnName
deriving (Columns -> Columns -> Bool
(Columns -> Columns -> Bool)
-> (Columns -> Columns -> Bool) -> Eq Columns
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Columns -> Columns -> Bool
== :: Columns -> Columns -> Bool
$c/= :: Columns -> Columns -> Bool
/= :: Columns -> Columns -> Bool
Eq, Eq Columns
Eq Columns =>
(Columns -> Columns -> Ordering)
-> (Columns -> Columns -> Bool)
-> (Columns -> Columns -> Bool)
-> (Columns -> Columns -> Bool)
-> (Columns -> Columns -> Bool)
-> (Columns -> Columns -> Columns)
-> (Columns -> Columns -> Columns)
-> Ord Columns
Columns -> Columns -> Bool
Columns -> Columns -> Ordering
Columns -> Columns -> Columns
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Columns -> Columns -> Ordering
compare :: Columns -> Columns -> Ordering
$c< :: Columns -> Columns -> Bool
< :: Columns -> Columns -> Bool
$c<= :: Columns -> Columns -> Bool
<= :: Columns -> Columns -> Bool
$c> :: Columns -> Columns -> Bool
> :: Columns -> Columns -> Bool
$c>= :: Columns -> Columns -> Bool
>= :: Columns -> Columns -> Bool
$cmax :: Columns -> Columns -> Columns
max :: Columns -> Columns -> Columns
$cmin :: Columns -> Columns -> Columns
min :: Columns -> Columns -> Columns
Ord, ReadPrec [Columns]
ReadPrec Columns
Int -> ReadS Columns
ReadS [Columns]
(Int -> ReadS Columns)
-> ReadS [Columns]
-> ReadPrec Columns
-> ReadPrec [Columns]
-> Read Columns
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Columns
readsPrec :: Int -> ReadS Columns
$creadList :: ReadS [Columns]
readList :: ReadS [Columns]
$creadPrec :: ReadPrec Columns
readPrec :: ReadPrec Columns
$creadListPrec :: ReadPrec [Columns]
readListPrec :: ReadPrec [Columns]
Read, Int -> Columns -> ShowS
[Columns] -> ShowS
Columns -> String
(Int -> Columns -> ShowS)
-> (Columns -> String) -> ([Columns] -> ShowS) -> Show Columns
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Columns -> ShowS
showsPrec :: Int -> Columns -> ShowS
$cshow :: Columns -> String
show :: Columns -> String
$cshowList :: [Columns] -> ShowS
showList :: [Columns] -> ShowS
Show)
_Columns :: Name
_Columns = (String -> Name
Core.Name String
"hydra/langs/kusto/kql.Columns")
_Columns_all :: Name
_Columns_all = (String -> Name
Core.Name String
"all")
_Columns_single :: Name
_Columns_single = (String -> Name
Core.Name String
"single")
data Command =
CommandCount |
CommandDistinct [ColumnName] |
CommandExtend [ColumnAssignment] |
CommandJoin JoinCommand |
CommandLimit Int |
CommandMvexpand ColumnName |
CommandOrderBy [SortBy] |
CommandParse ParseCommand |
CommandPrint PrintCommand |
CommandProject [Projection] |
CommandProjectAway [ColumnName] |
CommandProjectRename [ColumnAlias] |
CommandRender String |
CommandSearch SearchCommand |
CommandSortBy [SortBy] |
CommandSummarize SummarizeCommand |
CommandTake Int |
CommandTop TopCommand |
CommandUnion UnionCommand |
CommandWhere Expression
deriving (Command -> Command -> Bool
(Command -> Command -> Bool)
-> (Command -> Command -> Bool) -> Eq Command
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Command -> Command -> Bool
== :: Command -> Command -> Bool
$c/= :: Command -> Command -> Bool
/= :: Command -> Command -> Bool
Eq, Eq Command
Eq Command =>
(Command -> Command -> Ordering)
-> (Command -> Command -> Bool)
-> (Command -> Command -> Bool)
-> (Command -> Command -> Bool)
-> (Command -> Command -> Bool)
-> (Command -> Command -> Command)
-> (Command -> Command -> Command)
-> Ord Command
Command -> Command -> Bool
Command -> Command -> Ordering
Command -> Command -> Command
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Command -> Command -> Ordering
compare :: Command -> Command -> Ordering
$c< :: Command -> Command -> Bool
< :: Command -> Command -> Bool
$c<= :: Command -> Command -> Bool
<= :: Command -> Command -> Bool
$c> :: Command -> Command -> Bool
> :: Command -> Command -> Bool
$c>= :: Command -> Command -> Bool
>= :: Command -> Command -> Bool
$cmax :: Command -> Command -> Command
max :: Command -> Command -> Command
$cmin :: Command -> Command -> Command
min :: Command -> Command -> Command
Ord, ReadPrec [Command]
ReadPrec Command
Int -> ReadS Command
ReadS [Command]
(Int -> ReadS Command)
-> ReadS [Command]
-> ReadPrec Command
-> ReadPrec [Command]
-> Read Command
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Command
readsPrec :: Int -> ReadS Command
$creadList :: ReadS [Command]
readList :: ReadS [Command]
$creadPrec :: ReadPrec Command
readPrec :: ReadPrec Command
$creadListPrec :: ReadPrec [Command]
readListPrec :: ReadPrec [Command]
Read, Int -> Command -> ShowS
[Command] -> ShowS
Command -> String
(Int -> Command -> ShowS)
-> (Command -> String) -> ([Command] -> ShowS) -> Show Command
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Command -> ShowS
showsPrec :: Int -> Command -> ShowS
$cshow :: Command -> String
show :: Command -> String
$cshowList :: [Command] -> ShowS
showList :: [Command] -> ShowS
Show)
_Command :: Name
_Command = (String -> Name
Core.Name String
"hydra/langs/kusto/kql.Command")
_Command_count :: Name
_Command_count = (String -> Name
Core.Name String
"count")
_Command_distinct :: Name
_Command_distinct = (String -> Name
Core.Name String
"distinct")
_Command_extend :: Name
_Command_extend = (String -> Name
Core.Name String
"extend")
_Command_join :: Name
_Command_join = (String -> Name
Core.Name String
"join")
_Command_limit :: Name
_Command_limit = (String -> Name
Core.Name String
"limit")
_Command_mvexpand :: Name
_Command_mvexpand = (String -> Name
Core.Name String
"mvexpand")
_Command_orderBy :: Name
_Command_orderBy = (String -> Name
Core.Name String
"orderBy")
_Command_parse :: Name
_Command_parse = (String -> Name
Core.Name String
"parse")
_Command_print :: Name
_Command_print = (String -> Name
Core.Name String
"print")
_Command_project :: Name
_Command_project = (String -> Name
Core.Name String
"project")
_Command_projectAway :: Name
_Command_projectAway = (String -> Name
Core.Name String
"projectAway")
_Command_projectRename :: Name
_Command_projectRename = (String -> Name
Core.Name String
"projectRename")
_Command_render :: Name
_Command_render = (String -> Name
Core.Name String
"render")
_Command_search :: Name
_Command_search = (String -> Name
Core.Name String
"search")
_Command_sortBy :: Name
_Command_sortBy = (String -> Name
Core.Name String
"sortBy")
_Command_summarize :: Name
_Command_summarize = (String -> Name
Core.Name String
"summarize")
_Command_take :: Name
_Command_take = (String -> Name
Core.Name String
"take")
_Command_top :: Name
_Command_top = (String -> Name
Core.Name String
"top")
_Command_union :: Name
_Command_union = (String -> Name
Core.Name String
"union")
_Command_where :: Name
_Command_where = (String -> Name
Core.Name String
"where")
newtype Datetime =
Datetime {
Datetime -> String
unDatetime :: String}
deriving (Datetime -> Datetime -> Bool
(Datetime -> Datetime -> Bool)
-> (Datetime -> Datetime -> Bool) -> Eq Datetime
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Datetime -> Datetime -> Bool
== :: Datetime -> Datetime -> Bool
$c/= :: Datetime -> Datetime -> Bool
/= :: Datetime -> Datetime -> Bool
Eq, Eq Datetime
Eq Datetime =>
(Datetime -> Datetime -> Ordering)
-> (Datetime -> Datetime -> Bool)
-> (Datetime -> Datetime -> Bool)
-> (Datetime -> Datetime -> Bool)
-> (Datetime -> Datetime -> Bool)
-> (Datetime -> Datetime -> Datetime)
-> (Datetime -> Datetime -> Datetime)
-> Ord Datetime
Datetime -> Datetime -> Bool
Datetime -> Datetime -> Ordering
Datetime -> Datetime -> Datetime
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Datetime -> Datetime -> Ordering
compare :: Datetime -> Datetime -> Ordering
$c< :: Datetime -> Datetime -> Bool
< :: Datetime -> Datetime -> Bool
$c<= :: Datetime -> Datetime -> Bool
<= :: Datetime -> Datetime -> Bool
$c> :: Datetime -> Datetime -> Bool
> :: Datetime -> Datetime -> Bool
$c>= :: Datetime -> Datetime -> Bool
>= :: Datetime -> Datetime -> Bool
$cmax :: Datetime -> Datetime -> Datetime
max :: Datetime -> Datetime -> Datetime
$cmin :: Datetime -> Datetime -> Datetime
min :: Datetime -> Datetime -> Datetime
Ord, ReadPrec [Datetime]
ReadPrec Datetime
Int -> ReadS Datetime
ReadS [Datetime]
(Int -> ReadS Datetime)
-> ReadS [Datetime]
-> ReadPrec Datetime
-> ReadPrec [Datetime]
-> Read Datetime
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Datetime
readsPrec :: Int -> ReadS Datetime
$creadList :: ReadS [Datetime]
readList :: ReadS [Datetime]
$creadPrec :: ReadPrec Datetime
readPrec :: ReadPrec Datetime
$creadListPrec :: ReadPrec [Datetime]
readListPrec :: ReadPrec [Datetime]
Read, Int -> Datetime -> ShowS
[Datetime] -> ShowS
Datetime -> String
(Int -> Datetime -> ShowS)
-> (Datetime -> String) -> ([Datetime] -> ShowS) -> Show Datetime
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Datetime -> ShowS
showsPrec :: Int -> Datetime -> ShowS
$cshow :: Datetime -> String
show :: Datetime -> String
$cshowList :: [Datetime] -> ShowS
showList :: [Datetime] -> ShowS
Show)
_Datetime :: Name
_Datetime = (String -> Name
Core.Name String
"hydra/langs/kusto/kql.Datetime")
data Duration =
Duration {
Duration -> Int
durationValue :: Int,
Duration -> DurationUnit
durationUnit :: DurationUnit}
deriving (Duration -> Duration -> Bool
(Duration -> Duration -> Bool)
-> (Duration -> Duration -> Bool) -> Eq Duration
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Duration -> Duration -> Bool
== :: Duration -> Duration -> Bool
$c/= :: Duration -> Duration -> Bool
/= :: Duration -> Duration -> Bool
Eq, Eq Duration
Eq Duration =>
(Duration -> Duration -> Ordering)
-> (Duration -> Duration -> Bool)
-> (Duration -> Duration -> Bool)
-> (Duration -> Duration -> Bool)
-> (Duration -> Duration -> Bool)
-> (Duration -> Duration -> Duration)
-> (Duration -> Duration -> Duration)
-> Ord Duration
Duration -> Duration -> Bool
Duration -> Duration -> Ordering
Duration -> Duration -> Duration
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Duration -> Duration -> Ordering
compare :: Duration -> Duration -> Ordering
$c< :: Duration -> Duration -> Bool
< :: Duration -> Duration -> Bool
$c<= :: Duration -> Duration -> Bool
<= :: Duration -> Duration -> Bool
$c> :: Duration -> Duration -> Bool
> :: Duration -> Duration -> Bool
$c>= :: Duration -> Duration -> Bool
>= :: Duration -> Duration -> Bool
$cmax :: Duration -> Duration -> Duration
max :: Duration -> Duration -> Duration
$cmin :: Duration -> Duration -> Duration
min :: Duration -> Duration -> Duration
Ord, ReadPrec [Duration]
ReadPrec Duration
Int -> ReadS Duration
ReadS [Duration]
(Int -> ReadS Duration)
-> ReadS [Duration]
-> ReadPrec Duration
-> ReadPrec [Duration]
-> Read Duration
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Duration
readsPrec :: Int -> ReadS Duration
$creadList :: ReadS [Duration]
readList :: ReadS [Duration]
$creadPrec :: ReadPrec Duration
readPrec :: ReadPrec Duration
$creadListPrec :: ReadPrec [Duration]
readListPrec :: ReadPrec [Duration]
Read, Int -> Duration -> ShowS
[Duration] -> ShowS
Duration -> String
(Int -> Duration -> ShowS)
-> (Duration -> String) -> ([Duration] -> ShowS) -> Show Duration
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Duration -> ShowS
showsPrec :: Int -> Duration -> ShowS
$cshow :: Duration -> String
show :: Duration -> String
$cshowList :: [Duration] -> ShowS
showList :: [Duration] -> ShowS
Show)
_Duration :: Name
_Duration = (String -> Name
Core.Name String
"hydra/langs/kusto/kql.Duration")
_Duration_value :: Name
_Duration_value = (String -> Name
Core.Name String
"value")
_Duration_unit :: Name
_Duration_unit = (String -> Name
Core.Name String
"unit")
data DurationUnit =
DurationUnitSecond |
DurationUnitMinute |
DurationUnitHour
deriving (DurationUnit -> DurationUnit -> Bool
(DurationUnit -> DurationUnit -> Bool)
-> (DurationUnit -> DurationUnit -> Bool) -> Eq DurationUnit
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DurationUnit -> DurationUnit -> Bool
== :: DurationUnit -> DurationUnit -> Bool
$c/= :: DurationUnit -> DurationUnit -> Bool
/= :: DurationUnit -> DurationUnit -> Bool
Eq, Eq DurationUnit
Eq DurationUnit =>
(DurationUnit -> DurationUnit -> Ordering)
-> (DurationUnit -> DurationUnit -> Bool)
-> (DurationUnit -> DurationUnit -> Bool)
-> (DurationUnit -> DurationUnit -> Bool)
-> (DurationUnit -> DurationUnit -> Bool)
-> (DurationUnit -> DurationUnit -> DurationUnit)
-> (DurationUnit -> DurationUnit -> DurationUnit)
-> Ord DurationUnit
DurationUnit -> DurationUnit -> Bool
DurationUnit -> DurationUnit -> Ordering
DurationUnit -> DurationUnit -> DurationUnit
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: DurationUnit -> DurationUnit -> Ordering
compare :: DurationUnit -> DurationUnit -> Ordering
$c< :: DurationUnit -> DurationUnit -> Bool
< :: DurationUnit -> DurationUnit -> Bool
$c<= :: DurationUnit -> DurationUnit -> Bool
<= :: DurationUnit -> DurationUnit -> Bool
$c> :: DurationUnit -> DurationUnit -> Bool
> :: DurationUnit -> DurationUnit -> Bool
$c>= :: DurationUnit -> DurationUnit -> Bool
>= :: DurationUnit -> DurationUnit -> Bool
$cmax :: DurationUnit -> DurationUnit -> DurationUnit
max :: DurationUnit -> DurationUnit -> DurationUnit
$cmin :: DurationUnit -> DurationUnit -> DurationUnit
min :: DurationUnit -> DurationUnit -> DurationUnit
Ord, ReadPrec [DurationUnit]
ReadPrec DurationUnit
Int -> ReadS DurationUnit
ReadS [DurationUnit]
(Int -> ReadS DurationUnit)
-> ReadS [DurationUnit]
-> ReadPrec DurationUnit
-> ReadPrec [DurationUnit]
-> Read DurationUnit
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS DurationUnit
readsPrec :: Int -> ReadS DurationUnit
$creadList :: ReadS [DurationUnit]
readList :: ReadS [DurationUnit]
$creadPrec :: ReadPrec DurationUnit
readPrec :: ReadPrec DurationUnit
$creadListPrec :: ReadPrec [DurationUnit]
readListPrec :: ReadPrec [DurationUnit]
Read, Int -> DurationUnit -> ShowS
[DurationUnit] -> ShowS
DurationUnit -> String
(Int -> DurationUnit -> ShowS)
-> (DurationUnit -> String)
-> ([DurationUnit] -> ShowS)
-> Show DurationUnit
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DurationUnit -> ShowS
showsPrec :: Int -> DurationUnit -> ShowS
$cshow :: DurationUnit -> String
show :: DurationUnit -> String
$cshowList :: [DurationUnit] -> ShowS
showList :: [DurationUnit] -> ShowS
Show)
_DurationUnit :: Name
_DurationUnit = (String -> Name
Core.Name String
"hydra/langs/kusto/kql.DurationUnit")
_DurationUnit_second :: Name
_DurationUnit_second = (String -> Name
Core.Name String
"second")
_DurationUnit_minute :: Name
_DurationUnit_minute = (String -> Name
Core.Name String
"minute")
_DurationUnit_hour :: Name
_DurationUnit_hour = (String -> Name
Core.Name String
"hour")
data Expression =
ExpressionAnd [Expression] |
ExpressionAny |
ExpressionBetween BetweenExpression |
ExpressionBinary BinaryExpression |
ExpressionBraces Expression |
ExpressionColumn ColumnName |
ExpressionDataset TableName |
ExpressionIndex IndexExpression |
ExpressionList [Expression] |
ExpressionLiteral Literal |
ExpressionOr [Expression] |
ExpressionParentheses Expression |
ExpressionProperty PropertyExpression |
ExpressionUnary UnaryExpression
deriving (Expression -> Expression -> Bool
(Expression -> Expression -> Bool)
-> (Expression -> Expression -> Bool) -> Eq Expression
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Expression -> Expression -> Bool
== :: Expression -> Expression -> Bool
$c/= :: Expression -> Expression -> Bool
/= :: Expression -> Expression -> Bool
Eq, Eq Expression
Eq Expression =>
(Expression -> Expression -> Ordering)
-> (Expression -> Expression -> Bool)
-> (Expression -> Expression -> Bool)
-> (Expression -> Expression -> Bool)
-> (Expression -> Expression -> Bool)
-> (Expression -> Expression -> Expression)
-> (Expression -> Expression -> Expression)
-> Ord Expression
Expression -> Expression -> Bool
Expression -> Expression -> Ordering
Expression -> Expression -> Expression
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Expression -> Expression -> Ordering
compare :: Expression -> Expression -> Ordering
$c< :: Expression -> Expression -> Bool
< :: Expression -> Expression -> Bool
$c<= :: Expression -> Expression -> Bool
<= :: Expression -> Expression -> Bool
$c> :: Expression -> Expression -> Bool
> :: Expression -> Expression -> Bool
$c>= :: Expression -> Expression -> Bool
>= :: Expression -> Expression -> Bool
$cmax :: Expression -> Expression -> Expression
max :: Expression -> Expression -> Expression
$cmin :: Expression -> Expression -> Expression
min :: Expression -> Expression -> Expression
Ord, ReadPrec [Expression]
ReadPrec Expression
Int -> ReadS Expression
ReadS [Expression]
(Int -> ReadS Expression)
-> ReadS [Expression]
-> ReadPrec Expression
-> ReadPrec [Expression]
-> Read Expression
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Expression
readsPrec :: Int -> ReadS Expression
$creadList :: ReadS [Expression]
readList :: ReadS [Expression]
$creadPrec :: ReadPrec Expression
readPrec :: ReadPrec Expression
$creadListPrec :: ReadPrec [Expression]
readListPrec :: ReadPrec [Expression]
Read, Int -> Expression -> ShowS
[Expression] -> ShowS
Expression -> String
(Int -> Expression -> ShowS)
-> (Expression -> String)
-> ([Expression] -> ShowS)
-> Show Expression
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Expression -> ShowS
showsPrec :: Int -> Expression -> ShowS
$cshow :: Expression -> String
show :: Expression -> String
$cshowList :: [Expression] -> ShowS
showList :: [Expression] -> ShowS
Show)
_Expression :: Name
_Expression = (String -> Name
Core.Name String
"hydra/langs/kusto/kql.Expression")
_Expression_and :: Name
_Expression_and = (String -> Name
Core.Name String
"and")
_Expression_any :: Name
_Expression_any = (String -> Name
Core.Name String
"any")
_Expression_between :: Name
_Expression_between = (String -> Name
Core.Name String
"between")
_Expression_binary :: Name
_Expression_binary = (String -> Name
Core.Name String
"binary")
_Expression_braces :: Name
_Expression_braces = (String -> Name
Core.Name String
"braces")
_Expression_column :: Name
_Expression_column = (String -> Name
Core.Name String
"column")
_Expression_dataset :: Name
_Expression_dataset = (String -> Name
Core.Name String
"dataset")
_Expression_index :: Name
_Expression_index = (String -> Name
Core.Name String
"index")
_Expression_list :: Name
_Expression_list = (String -> Name
Core.Name String
"list")
_Expression_literal :: Name
_Expression_literal = (String -> Name
Core.Name String
"literal")
_Expression_or :: Name
_Expression_or = (String -> Name
Core.Name String
"or")
_Expression_parentheses :: Name
_Expression_parentheses = (String -> Name
Core.Name String
"parentheses")
_Expression_property :: Name
_Expression_property = (String -> Name
Core.Name String
"property")
_Expression_unary :: Name
_Expression_unary = (String -> Name
Core.Name String
"unary")
data Function =
FunctionBuiltIn BuiltInFunction |
FunctionCustom FunctionName
deriving (Function -> Function -> Bool
(Function -> Function -> Bool)
-> (Function -> Function -> Bool) -> Eq Function
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Function -> Function -> Bool
== :: Function -> Function -> Bool
$c/= :: Function -> Function -> Bool
/= :: Function -> Function -> Bool
Eq, Eq Function
Eq Function =>
(Function -> Function -> Ordering)
-> (Function -> Function -> Bool)
-> (Function -> Function -> Bool)
-> (Function -> Function -> Bool)
-> (Function -> Function -> Bool)
-> (Function -> Function -> Function)
-> (Function -> Function -> Function)
-> Ord Function
Function -> Function -> Bool
Function -> Function -> Ordering
Function -> Function -> Function
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Function -> Function -> Ordering
compare :: Function -> Function -> Ordering
$c< :: Function -> Function -> Bool
< :: Function -> Function -> Bool
$c<= :: Function -> Function -> Bool
<= :: Function -> Function -> Bool
$c> :: Function -> Function -> Bool
> :: Function -> Function -> Bool
$c>= :: Function -> Function -> Bool
>= :: Function -> Function -> Bool
$cmax :: Function -> Function -> Function
max :: Function -> Function -> Function
$cmin :: Function -> Function -> Function
min :: Function -> Function -> Function
Ord, ReadPrec [Function]
ReadPrec Function
Int -> ReadS Function
ReadS [Function]
(Int -> ReadS Function)
-> ReadS [Function]
-> ReadPrec Function
-> ReadPrec [Function]
-> Read Function
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Function
readsPrec :: Int -> ReadS Function
$creadList :: ReadS [Function]
readList :: ReadS [Function]
$creadPrec :: ReadPrec Function
readPrec :: ReadPrec Function
$creadListPrec :: ReadPrec [Function]
readListPrec :: ReadPrec [Function]
Read, Int -> Function -> ShowS
[Function] -> ShowS
Function -> String
(Int -> Function -> ShowS)
-> (Function -> String) -> ([Function] -> ShowS) -> Show Function
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Function -> ShowS
showsPrec :: Int -> Function -> ShowS
$cshow :: Function -> String
show :: Function -> String
$cshowList :: [Function] -> ShowS
showList :: [Function] -> ShowS
Show)
_Function :: Name
_Function = (String -> Name
Core.Name String
"hydra/langs/kusto/kql.Function")
_Function_builtIn :: Name
_Function_builtIn = (String -> Name
Core.Name String
"builtIn")
_Function_custom :: Name
_Function_custom = (String -> Name
Core.Name String
"custom")
data FunctionExpression =
FunctionExpression {
FunctionExpression -> Function
functionExpressionFunction :: Function,
FunctionExpression -> [Expression]
functionExpressionArguments :: [Expression]}
deriving (FunctionExpression -> FunctionExpression -> Bool
(FunctionExpression -> FunctionExpression -> Bool)
-> (FunctionExpression -> FunctionExpression -> Bool)
-> Eq FunctionExpression
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FunctionExpression -> FunctionExpression -> Bool
== :: FunctionExpression -> FunctionExpression -> Bool
$c/= :: FunctionExpression -> FunctionExpression -> Bool
/= :: FunctionExpression -> FunctionExpression -> Bool
Eq, Eq FunctionExpression
Eq FunctionExpression =>
(FunctionExpression -> FunctionExpression -> Ordering)
-> (FunctionExpression -> FunctionExpression -> Bool)
-> (FunctionExpression -> FunctionExpression -> Bool)
-> (FunctionExpression -> FunctionExpression -> Bool)
-> (FunctionExpression -> FunctionExpression -> Bool)
-> (FunctionExpression -> FunctionExpression -> FunctionExpression)
-> (FunctionExpression -> FunctionExpression -> FunctionExpression)
-> Ord FunctionExpression
FunctionExpression -> FunctionExpression -> Bool
FunctionExpression -> FunctionExpression -> Ordering
FunctionExpression -> FunctionExpression -> FunctionExpression
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: FunctionExpression -> FunctionExpression -> Ordering
compare :: FunctionExpression -> FunctionExpression -> Ordering
$c< :: FunctionExpression -> FunctionExpression -> Bool
< :: FunctionExpression -> FunctionExpression -> Bool
$c<= :: FunctionExpression -> FunctionExpression -> Bool
<= :: FunctionExpression -> FunctionExpression -> Bool
$c> :: FunctionExpression -> FunctionExpression -> Bool
> :: FunctionExpression -> FunctionExpression -> Bool
$c>= :: FunctionExpression -> FunctionExpression -> Bool
>= :: FunctionExpression -> FunctionExpression -> Bool
$cmax :: FunctionExpression -> FunctionExpression -> FunctionExpression
max :: FunctionExpression -> FunctionExpression -> FunctionExpression
$cmin :: FunctionExpression -> FunctionExpression -> FunctionExpression
min :: FunctionExpression -> FunctionExpression -> FunctionExpression
Ord, ReadPrec [FunctionExpression]
ReadPrec FunctionExpression
Int -> ReadS FunctionExpression
ReadS [FunctionExpression]
(Int -> ReadS FunctionExpression)
-> ReadS [FunctionExpression]
-> ReadPrec FunctionExpression
-> ReadPrec [FunctionExpression]
-> Read FunctionExpression
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS FunctionExpression
readsPrec :: Int -> ReadS FunctionExpression
$creadList :: ReadS [FunctionExpression]
readList :: ReadS [FunctionExpression]
$creadPrec :: ReadPrec FunctionExpression
readPrec :: ReadPrec FunctionExpression
$creadListPrec :: ReadPrec [FunctionExpression]
readListPrec :: ReadPrec [FunctionExpression]
Read, Int -> FunctionExpression -> ShowS
[FunctionExpression] -> ShowS
FunctionExpression -> String
(Int -> FunctionExpression -> ShowS)
-> (FunctionExpression -> String)
-> ([FunctionExpression] -> ShowS)
-> Show FunctionExpression
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FunctionExpression -> ShowS
showsPrec :: Int -> FunctionExpression -> ShowS
$cshow :: FunctionExpression -> String
show :: FunctionExpression -> String
$cshowList :: [FunctionExpression] -> ShowS
showList :: [FunctionExpression] -> ShowS
Show)
_FunctionExpression :: Name
_FunctionExpression = (String -> Name
Core.Name String
"hydra/langs/kusto/kql.FunctionExpression")
_FunctionExpression_function :: Name
_FunctionExpression_function = (String -> Name
Core.Name String
"function")
_FunctionExpression_arguments :: Name
_FunctionExpression_arguments = (String -> Name
Core.Name String
"arguments")
newtype FunctionName =
FunctionName {
FunctionName -> String
unFunctionName :: String}
deriving (FunctionName -> FunctionName -> Bool
(FunctionName -> FunctionName -> Bool)
-> (FunctionName -> FunctionName -> Bool) -> Eq FunctionName
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FunctionName -> FunctionName -> Bool
== :: FunctionName -> FunctionName -> Bool
$c/= :: FunctionName -> FunctionName -> Bool
/= :: FunctionName -> FunctionName -> Bool
Eq, Eq FunctionName
Eq FunctionName =>
(FunctionName -> FunctionName -> Ordering)
-> (FunctionName -> FunctionName -> Bool)
-> (FunctionName -> FunctionName -> Bool)
-> (FunctionName -> FunctionName -> Bool)
-> (FunctionName -> FunctionName -> Bool)
-> (FunctionName -> FunctionName -> FunctionName)
-> (FunctionName -> FunctionName -> FunctionName)
-> Ord FunctionName
FunctionName -> FunctionName -> Bool
FunctionName -> FunctionName -> Ordering
FunctionName -> FunctionName -> FunctionName
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: FunctionName -> FunctionName -> Ordering
compare :: FunctionName -> FunctionName -> Ordering
$c< :: FunctionName -> FunctionName -> Bool
< :: FunctionName -> FunctionName -> Bool
$c<= :: FunctionName -> FunctionName -> Bool
<= :: FunctionName -> FunctionName -> Bool
$c> :: FunctionName -> FunctionName -> Bool
> :: FunctionName -> FunctionName -> Bool
$c>= :: FunctionName -> FunctionName -> Bool
>= :: FunctionName -> FunctionName -> Bool
$cmax :: FunctionName -> FunctionName -> FunctionName
max :: FunctionName -> FunctionName -> FunctionName
$cmin :: FunctionName -> FunctionName -> FunctionName
min :: FunctionName -> FunctionName -> FunctionName
Ord, ReadPrec [FunctionName]
ReadPrec FunctionName
Int -> ReadS FunctionName
ReadS [FunctionName]
(Int -> ReadS FunctionName)
-> ReadS [FunctionName]
-> ReadPrec FunctionName
-> ReadPrec [FunctionName]
-> Read FunctionName
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS FunctionName
readsPrec :: Int -> ReadS FunctionName
$creadList :: ReadS [FunctionName]
readList :: ReadS [FunctionName]
$creadPrec :: ReadPrec FunctionName
readPrec :: ReadPrec FunctionName
$creadListPrec :: ReadPrec [FunctionName]
readListPrec :: ReadPrec [FunctionName]
Read, Int -> FunctionName -> ShowS
[FunctionName] -> ShowS
FunctionName -> String
(Int -> FunctionName -> ShowS)
-> (FunctionName -> String)
-> ([FunctionName] -> ShowS)
-> Show FunctionName
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FunctionName -> ShowS
showsPrec :: Int -> FunctionName -> ShowS
$cshow :: FunctionName -> String
show :: FunctionName -> String
$cshowList :: [FunctionName] -> ShowS
showList :: [FunctionName] -> ShowS
Show)
_FunctionName :: Name
_FunctionName = (String -> Name
Core.Name String
"hydra/langs/kusto/kql.FunctionName")
data IndexExpression =
IndexExpression {
IndexExpression -> Expression
indexExpressionExpression :: Expression,
IndexExpression -> String
indexExpressionIndex :: String}
deriving (IndexExpression -> IndexExpression -> Bool
(IndexExpression -> IndexExpression -> Bool)
-> (IndexExpression -> IndexExpression -> Bool)
-> Eq IndexExpression
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: IndexExpression -> IndexExpression -> Bool
== :: IndexExpression -> IndexExpression -> Bool
$c/= :: IndexExpression -> IndexExpression -> Bool
/= :: IndexExpression -> IndexExpression -> Bool
Eq, Eq IndexExpression
Eq IndexExpression =>
(IndexExpression -> IndexExpression -> Ordering)
-> (IndexExpression -> IndexExpression -> Bool)
-> (IndexExpression -> IndexExpression -> Bool)
-> (IndexExpression -> IndexExpression -> Bool)
-> (IndexExpression -> IndexExpression -> Bool)
-> (IndexExpression -> IndexExpression -> IndexExpression)
-> (IndexExpression -> IndexExpression -> IndexExpression)
-> Ord IndexExpression
IndexExpression -> IndexExpression -> Bool
IndexExpression -> IndexExpression -> Ordering
IndexExpression -> IndexExpression -> IndexExpression
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: IndexExpression -> IndexExpression -> Ordering
compare :: IndexExpression -> IndexExpression -> Ordering
$c< :: IndexExpression -> IndexExpression -> Bool
< :: IndexExpression -> IndexExpression -> Bool
$c<= :: IndexExpression -> IndexExpression -> Bool
<= :: IndexExpression -> IndexExpression -> Bool
$c> :: IndexExpression -> IndexExpression -> Bool
> :: IndexExpression -> IndexExpression -> Bool
$c>= :: IndexExpression -> IndexExpression -> Bool
>= :: IndexExpression -> IndexExpression -> Bool
$cmax :: IndexExpression -> IndexExpression -> IndexExpression
max :: IndexExpression -> IndexExpression -> IndexExpression
$cmin :: IndexExpression -> IndexExpression -> IndexExpression
min :: IndexExpression -> IndexExpression -> IndexExpression
Ord, ReadPrec [IndexExpression]
ReadPrec IndexExpression
Int -> ReadS IndexExpression
ReadS [IndexExpression]
(Int -> ReadS IndexExpression)
-> ReadS [IndexExpression]
-> ReadPrec IndexExpression
-> ReadPrec [IndexExpression]
-> Read IndexExpression
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS IndexExpression
readsPrec :: Int -> ReadS IndexExpression
$creadList :: ReadS [IndexExpression]
readList :: ReadS [IndexExpression]
$creadPrec :: ReadPrec IndexExpression
readPrec :: ReadPrec IndexExpression
$creadListPrec :: ReadPrec [IndexExpression]
readListPrec :: ReadPrec [IndexExpression]
Read, Int -> IndexExpression -> ShowS
[IndexExpression] -> ShowS
IndexExpression -> String
(Int -> IndexExpression -> ShowS)
-> (IndexExpression -> String)
-> ([IndexExpression] -> ShowS)
-> Show IndexExpression
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> IndexExpression -> ShowS
showsPrec :: Int -> IndexExpression -> ShowS
$cshow :: IndexExpression -> String
show :: IndexExpression -> String
$cshowList :: [IndexExpression] -> ShowS
showList :: [IndexExpression] -> ShowS
Show)
_IndexExpression :: Name
_IndexExpression = (String -> Name
Core.Name String
"hydra/langs/kusto/kql.IndexExpression")
_IndexExpression_expression :: Name
_IndexExpression_expression = (String -> Name
Core.Name String
"expression")
_IndexExpression_index :: Name
_IndexExpression_index = (String -> Name
Core.Name String
"index")
data JoinCommand =
JoinCommand {
JoinCommand -> JoinKind
joinCommandKind :: JoinKind,
JoinCommand -> TableName
joinCommandExpression :: TableName,
JoinCommand -> Expression
joinCommandOn :: Expression}
deriving (JoinCommand -> JoinCommand -> Bool
(JoinCommand -> JoinCommand -> Bool)
-> (JoinCommand -> JoinCommand -> Bool) -> Eq JoinCommand
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: JoinCommand -> JoinCommand -> Bool
== :: JoinCommand -> JoinCommand -> Bool
$c/= :: JoinCommand -> JoinCommand -> Bool
/= :: JoinCommand -> JoinCommand -> Bool
Eq, Eq JoinCommand
Eq JoinCommand =>
(JoinCommand -> JoinCommand -> Ordering)
-> (JoinCommand -> JoinCommand -> Bool)
-> (JoinCommand -> JoinCommand -> Bool)
-> (JoinCommand -> JoinCommand -> Bool)
-> (JoinCommand -> JoinCommand -> Bool)
-> (JoinCommand -> JoinCommand -> JoinCommand)
-> (JoinCommand -> JoinCommand -> JoinCommand)
-> Ord JoinCommand
JoinCommand -> JoinCommand -> Bool
JoinCommand -> JoinCommand -> Ordering
JoinCommand -> JoinCommand -> JoinCommand
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: JoinCommand -> JoinCommand -> Ordering
compare :: JoinCommand -> JoinCommand -> Ordering
$c< :: JoinCommand -> JoinCommand -> Bool
< :: JoinCommand -> JoinCommand -> Bool
$c<= :: JoinCommand -> JoinCommand -> Bool
<= :: JoinCommand -> JoinCommand -> Bool
$c> :: JoinCommand -> JoinCommand -> Bool
> :: JoinCommand -> JoinCommand -> Bool
$c>= :: JoinCommand -> JoinCommand -> Bool
>= :: JoinCommand -> JoinCommand -> Bool
$cmax :: JoinCommand -> JoinCommand -> JoinCommand
max :: JoinCommand -> JoinCommand -> JoinCommand
$cmin :: JoinCommand -> JoinCommand -> JoinCommand
min :: JoinCommand -> JoinCommand -> JoinCommand
Ord, ReadPrec [JoinCommand]
ReadPrec JoinCommand
Int -> ReadS JoinCommand
ReadS [JoinCommand]
(Int -> ReadS JoinCommand)
-> ReadS [JoinCommand]
-> ReadPrec JoinCommand
-> ReadPrec [JoinCommand]
-> Read JoinCommand
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS JoinCommand
readsPrec :: Int -> ReadS JoinCommand
$creadList :: ReadS [JoinCommand]
readList :: ReadS [JoinCommand]
$creadPrec :: ReadPrec JoinCommand
readPrec :: ReadPrec JoinCommand
$creadListPrec :: ReadPrec [JoinCommand]
readListPrec :: ReadPrec [JoinCommand]
Read, Int -> JoinCommand -> ShowS
[JoinCommand] -> ShowS
JoinCommand -> String
(Int -> JoinCommand -> ShowS)
-> (JoinCommand -> String)
-> ([JoinCommand] -> ShowS)
-> Show JoinCommand
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> JoinCommand -> ShowS
showsPrec :: Int -> JoinCommand -> ShowS
$cshow :: JoinCommand -> String
show :: JoinCommand -> String
$cshowList :: [JoinCommand] -> ShowS
showList :: [JoinCommand] -> ShowS
Show)
_JoinCommand :: Name
_JoinCommand = (String -> Name
Core.Name String
"hydra/langs/kusto/kql.JoinCommand")
_JoinCommand_kind :: Name
_JoinCommand_kind = (String -> Name
Core.Name String
"kind")
_JoinCommand_expression :: Name
_JoinCommand_expression = (String -> Name
Core.Name String
"expression")
_JoinCommand_on :: Name
_JoinCommand_on = (String -> Name
Core.Name String
"on")
data JoinKind =
JoinKindLeftouter |
JoinKindLeftsemi |
JoinKindLeftanti |
JoinKindFullouter |
JoinKindInner |
JoinKindInnerunique |
JoinKindRightouter |
JoinKindRightsemi |
JoinKindRightanti
deriving (JoinKind -> JoinKind -> Bool
(JoinKind -> JoinKind -> Bool)
-> (JoinKind -> JoinKind -> Bool) -> Eq JoinKind
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: JoinKind -> JoinKind -> Bool
== :: JoinKind -> JoinKind -> Bool
$c/= :: JoinKind -> JoinKind -> Bool
/= :: JoinKind -> JoinKind -> Bool
Eq, Eq JoinKind
Eq JoinKind =>
(JoinKind -> JoinKind -> Ordering)
-> (JoinKind -> JoinKind -> Bool)
-> (JoinKind -> JoinKind -> Bool)
-> (JoinKind -> JoinKind -> Bool)
-> (JoinKind -> JoinKind -> Bool)
-> (JoinKind -> JoinKind -> JoinKind)
-> (JoinKind -> JoinKind -> JoinKind)
-> Ord JoinKind
JoinKind -> JoinKind -> Bool
JoinKind -> JoinKind -> Ordering
JoinKind -> JoinKind -> JoinKind
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: JoinKind -> JoinKind -> Ordering
compare :: JoinKind -> JoinKind -> Ordering
$c< :: JoinKind -> JoinKind -> Bool
< :: JoinKind -> JoinKind -> Bool
$c<= :: JoinKind -> JoinKind -> Bool
<= :: JoinKind -> JoinKind -> Bool
$c> :: JoinKind -> JoinKind -> Bool
> :: JoinKind -> JoinKind -> Bool
$c>= :: JoinKind -> JoinKind -> Bool
>= :: JoinKind -> JoinKind -> Bool
$cmax :: JoinKind -> JoinKind -> JoinKind
max :: JoinKind -> JoinKind -> JoinKind
$cmin :: JoinKind -> JoinKind -> JoinKind
min :: JoinKind -> JoinKind -> JoinKind
Ord, ReadPrec [JoinKind]
ReadPrec JoinKind
Int -> ReadS JoinKind
ReadS [JoinKind]
(Int -> ReadS JoinKind)
-> ReadS [JoinKind]
-> ReadPrec JoinKind
-> ReadPrec [JoinKind]
-> Read JoinKind
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS JoinKind
readsPrec :: Int -> ReadS JoinKind
$creadList :: ReadS [JoinKind]
readList :: ReadS [JoinKind]
$creadPrec :: ReadPrec JoinKind
readPrec :: ReadPrec JoinKind
$creadListPrec :: ReadPrec [JoinKind]
readListPrec :: ReadPrec [JoinKind]
Read, Int -> JoinKind -> ShowS
[JoinKind] -> ShowS
JoinKind -> String
(Int -> JoinKind -> ShowS)
-> (JoinKind -> String) -> ([JoinKind] -> ShowS) -> Show JoinKind
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> JoinKind -> ShowS
showsPrec :: Int -> JoinKind -> ShowS
$cshow :: JoinKind -> String
show :: JoinKind -> String
$cshowList :: [JoinKind] -> ShowS
showList :: [JoinKind] -> ShowS
Show)
_JoinKind :: Name
_JoinKind = (String -> Name
Core.Name String
"hydra/langs/kusto/kql.JoinKind")
_JoinKind_leftouter :: Name
_JoinKind_leftouter = (String -> Name
Core.Name String
"leftouter")
_JoinKind_leftsemi :: Name
_JoinKind_leftsemi = (String -> Name
Core.Name String
"leftsemi")
_JoinKind_leftanti :: Name
_JoinKind_leftanti = (String -> Name
Core.Name String
"leftanti")
_JoinKind_fullouter :: Name
_JoinKind_fullouter = (String -> Name
Core.Name String
"fullouter")
_JoinKind_inner :: Name
_JoinKind_inner = (String -> Name
Core.Name String
"inner")
_JoinKind_innerunique :: Name
_JoinKind_innerunique = (String -> Name
Core.Name String
"innerunique")
_JoinKind_rightouter :: Name
_JoinKind_rightouter = (String -> Name
Core.Name String
"rightouter")
_JoinKind_rightsemi :: Name
_JoinKind_rightsemi = (String -> Name
Core.Name String
"rightsemi")
_JoinKind_rightanti :: Name
_JoinKind_rightanti = (String -> Name
Core.Name String
"rightanti")
data KeyValuePair =
KeyValuePair {
KeyValuePair -> String
keyValuePairKey :: String,
KeyValuePair -> Expression
keyValuePairValue :: Expression}
deriving (KeyValuePair -> KeyValuePair -> Bool
(KeyValuePair -> KeyValuePair -> Bool)
-> (KeyValuePair -> KeyValuePair -> Bool) -> Eq KeyValuePair
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: KeyValuePair -> KeyValuePair -> Bool
== :: KeyValuePair -> KeyValuePair -> Bool
$c/= :: KeyValuePair -> KeyValuePair -> Bool
/= :: KeyValuePair -> KeyValuePair -> Bool
Eq, Eq KeyValuePair
Eq KeyValuePair =>
(KeyValuePair -> KeyValuePair -> Ordering)
-> (KeyValuePair -> KeyValuePair -> Bool)
-> (KeyValuePair -> KeyValuePair -> Bool)
-> (KeyValuePair -> KeyValuePair -> Bool)
-> (KeyValuePair -> KeyValuePair -> Bool)
-> (KeyValuePair -> KeyValuePair -> KeyValuePair)
-> (KeyValuePair -> KeyValuePair -> KeyValuePair)
-> Ord KeyValuePair
KeyValuePair -> KeyValuePair -> Bool
KeyValuePair -> KeyValuePair -> Ordering
KeyValuePair -> KeyValuePair -> KeyValuePair
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: KeyValuePair -> KeyValuePair -> Ordering
compare :: KeyValuePair -> KeyValuePair -> Ordering
$c< :: KeyValuePair -> KeyValuePair -> Bool
< :: KeyValuePair -> KeyValuePair -> Bool
$c<= :: KeyValuePair -> KeyValuePair -> Bool
<= :: KeyValuePair -> KeyValuePair -> Bool
$c> :: KeyValuePair -> KeyValuePair -> Bool
> :: KeyValuePair -> KeyValuePair -> Bool
$c>= :: KeyValuePair -> KeyValuePair -> Bool
>= :: KeyValuePair -> KeyValuePair -> Bool
$cmax :: KeyValuePair -> KeyValuePair -> KeyValuePair
max :: KeyValuePair -> KeyValuePair -> KeyValuePair
$cmin :: KeyValuePair -> KeyValuePair -> KeyValuePair
min :: KeyValuePair -> KeyValuePair -> KeyValuePair
Ord, ReadPrec [KeyValuePair]
ReadPrec KeyValuePair
Int -> ReadS KeyValuePair
ReadS [KeyValuePair]
(Int -> ReadS KeyValuePair)
-> ReadS [KeyValuePair]
-> ReadPrec KeyValuePair
-> ReadPrec [KeyValuePair]
-> Read KeyValuePair
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS KeyValuePair
readsPrec :: Int -> ReadS KeyValuePair
$creadList :: ReadS [KeyValuePair]
readList :: ReadS [KeyValuePair]
$creadPrec :: ReadPrec KeyValuePair
readPrec :: ReadPrec KeyValuePair
$creadListPrec :: ReadPrec [KeyValuePair]
readListPrec :: ReadPrec [KeyValuePair]
Read, Int -> KeyValuePair -> ShowS
[KeyValuePair] -> ShowS
KeyValuePair -> String
(Int -> KeyValuePair -> ShowS)
-> (KeyValuePair -> String)
-> ([KeyValuePair] -> ShowS)
-> Show KeyValuePair
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> KeyValuePair -> ShowS
showsPrec :: Int -> KeyValuePair -> ShowS
$cshow :: KeyValuePair -> String
show :: KeyValuePair -> String
$cshowList :: [KeyValuePair] -> ShowS
showList :: [KeyValuePair] -> ShowS
Show)
_KeyValuePair :: Name
_KeyValuePair = (String -> Name
Core.Name String
"hydra/langs/kusto/kql.KeyValuePair")
_KeyValuePair_key :: Name
_KeyValuePair_key = (String -> Name
Core.Name String
"key")
_KeyValuePair_value :: Name
_KeyValuePair_value = (String -> Name
Core.Name String
"value")
data LetBinding =
LetBinding {
LetBinding -> ColumnName
letBindingName :: ColumnName,
LetBinding -> Expression
letBindingExpression :: Expression}
deriving (LetBinding -> LetBinding -> Bool
(LetBinding -> LetBinding -> Bool)
-> (LetBinding -> LetBinding -> Bool) -> Eq LetBinding
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: LetBinding -> LetBinding -> Bool
== :: LetBinding -> LetBinding -> Bool
$c/= :: LetBinding -> LetBinding -> Bool
/= :: LetBinding -> LetBinding -> Bool
Eq, Eq LetBinding
Eq LetBinding =>
(LetBinding -> LetBinding -> Ordering)
-> (LetBinding -> LetBinding -> Bool)
-> (LetBinding -> LetBinding -> Bool)
-> (LetBinding -> LetBinding -> Bool)
-> (LetBinding -> LetBinding -> Bool)
-> (LetBinding -> LetBinding -> LetBinding)
-> (LetBinding -> LetBinding -> LetBinding)
-> Ord LetBinding
LetBinding -> LetBinding -> Bool
LetBinding -> LetBinding -> Ordering
LetBinding -> LetBinding -> LetBinding
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: LetBinding -> LetBinding -> Ordering
compare :: LetBinding -> LetBinding -> Ordering
$c< :: LetBinding -> LetBinding -> Bool
< :: LetBinding -> LetBinding -> Bool
$c<= :: LetBinding -> LetBinding -> Bool
<= :: LetBinding -> LetBinding -> Bool
$c> :: LetBinding -> LetBinding -> Bool
> :: LetBinding -> LetBinding -> Bool
$c>= :: LetBinding -> LetBinding -> Bool
>= :: LetBinding -> LetBinding -> Bool
$cmax :: LetBinding -> LetBinding -> LetBinding
max :: LetBinding -> LetBinding -> LetBinding
$cmin :: LetBinding -> LetBinding -> LetBinding
min :: LetBinding -> LetBinding -> LetBinding
Ord, ReadPrec [LetBinding]
ReadPrec LetBinding
Int -> ReadS LetBinding
ReadS [LetBinding]
(Int -> ReadS LetBinding)
-> ReadS [LetBinding]
-> ReadPrec LetBinding
-> ReadPrec [LetBinding]
-> Read LetBinding
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS LetBinding
readsPrec :: Int -> ReadS LetBinding
$creadList :: ReadS [LetBinding]
readList :: ReadS [LetBinding]
$creadPrec :: ReadPrec LetBinding
readPrec :: ReadPrec LetBinding
$creadListPrec :: ReadPrec [LetBinding]
readListPrec :: ReadPrec [LetBinding]
Read, Int -> LetBinding -> ShowS
[LetBinding] -> ShowS
LetBinding -> String
(Int -> LetBinding -> ShowS)
-> (LetBinding -> String)
-> ([LetBinding] -> ShowS)
-> Show LetBinding
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> LetBinding -> ShowS
showsPrec :: Int -> LetBinding -> ShowS
$cshow :: LetBinding -> String
show :: LetBinding -> String
$cshowList :: [LetBinding] -> ShowS
showList :: [LetBinding] -> ShowS
Show)
_LetBinding :: Name
_LetBinding = (String -> Name
Core.Name String
"hydra/langs/kusto/kql.LetBinding")
_LetBinding_name :: Name
_LetBinding_name = (String -> Name
Core.Name String
"name")
_LetBinding_expression :: Name
_LetBinding_expression = (String -> Name
Core.Name String
"expression")
data LetExpression =
LetExpression {
LetExpression -> [LetBinding]
letExpressionBindings :: [LetBinding],
LetExpression -> TabularExpression
letExpressionExpression :: TabularExpression}
deriving (LetExpression -> LetExpression -> Bool
(LetExpression -> LetExpression -> Bool)
-> (LetExpression -> LetExpression -> Bool) -> Eq LetExpression
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: LetExpression -> LetExpression -> Bool
== :: LetExpression -> LetExpression -> Bool
$c/= :: LetExpression -> LetExpression -> Bool
/= :: LetExpression -> LetExpression -> Bool
Eq, Eq LetExpression
Eq LetExpression =>
(LetExpression -> LetExpression -> Ordering)
-> (LetExpression -> LetExpression -> Bool)
-> (LetExpression -> LetExpression -> Bool)
-> (LetExpression -> LetExpression -> Bool)
-> (LetExpression -> LetExpression -> Bool)
-> (LetExpression -> LetExpression -> LetExpression)
-> (LetExpression -> LetExpression -> LetExpression)
-> Ord LetExpression
LetExpression -> LetExpression -> Bool
LetExpression -> LetExpression -> Ordering
LetExpression -> LetExpression -> LetExpression
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: LetExpression -> LetExpression -> Ordering
compare :: LetExpression -> LetExpression -> Ordering
$c< :: LetExpression -> LetExpression -> Bool
< :: LetExpression -> LetExpression -> Bool
$c<= :: LetExpression -> LetExpression -> Bool
<= :: LetExpression -> LetExpression -> Bool
$c> :: LetExpression -> LetExpression -> Bool
> :: LetExpression -> LetExpression -> Bool
$c>= :: LetExpression -> LetExpression -> Bool
>= :: LetExpression -> LetExpression -> Bool
$cmax :: LetExpression -> LetExpression -> LetExpression
max :: LetExpression -> LetExpression -> LetExpression
$cmin :: LetExpression -> LetExpression -> LetExpression
min :: LetExpression -> LetExpression -> LetExpression
Ord, ReadPrec [LetExpression]
ReadPrec LetExpression
Int -> ReadS LetExpression
ReadS [LetExpression]
(Int -> ReadS LetExpression)
-> ReadS [LetExpression]
-> ReadPrec LetExpression
-> ReadPrec [LetExpression]
-> Read LetExpression
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS LetExpression
readsPrec :: Int -> ReadS LetExpression
$creadList :: ReadS [LetExpression]
readList :: ReadS [LetExpression]
$creadPrec :: ReadPrec LetExpression
readPrec :: ReadPrec LetExpression
$creadListPrec :: ReadPrec [LetExpression]
readListPrec :: ReadPrec [LetExpression]
Read, Int -> LetExpression -> ShowS
[LetExpression] -> ShowS
LetExpression -> String
(Int -> LetExpression -> ShowS)
-> (LetExpression -> String)
-> ([LetExpression] -> ShowS)
-> Show LetExpression
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> LetExpression -> ShowS
showsPrec :: Int -> LetExpression -> ShowS
$cshow :: LetExpression -> String
show :: LetExpression -> String
$cshowList :: [LetExpression] -> ShowS
showList :: [LetExpression] -> ShowS
Show)
_LetExpression :: Name
_LetExpression = (String -> Name
Core.Name String
"hydra/langs/kusto/kql.LetExpression")
_LetExpression_bindings :: Name
_LetExpression_bindings = (String -> Name
Core.Name String
"bindings")
_LetExpression_expression :: Name
_LetExpression_expression = (String -> Name
Core.Name String
"expression")
data Literal =
LiteralDuration Duration |
LiteralDatetime Datetime |
LiteralString String |
LiteralInt Int |
LiteralLong Int64 |
LiteralDouble Double |
LiteralBoolean Bool
deriving (Literal -> Literal -> Bool
(Literal -> Literal -> Bool)
-> (Literal -> Literal -> Bool) -> Eq Literal
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Literal -> Literal -> Bool
== :: Literal -> Literal -> Bool
$c/= :: Literal -> Literal -> Bool
/= :: Literal -> Literal -> Bool
Eq, Eq Literal
Eq Literal =>
(Literal -> Literal -> Ordering)
-> (Literal -> Literal -> Bool)
-> (Literal -> Literal -> Bool)
-> (Literal -> Literal -> Bool)
-> (Literal -> Literal -> Bool)
-> (Literal -> Literal -> Literal)
-> (Literal -> Literal -> Literal)
-> Ord Literal
Literal -> Literal -> Bool
Literal -> Literal -> Ordering
Literal -> Literal -> Literal
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Literal -> Literal -> Ordering
compare :: Literal -> Literal -> Ordering
$c< :: Literal -> Literal -> Bool
< :: Literal -> Literal -> Bool
$c<= :: Literal -> Literal -> Bool
<= :: Literal -> Literal -> Bool
$c> :: Literal -> Literal -> Bool
> :: Literal -> Literal -> Bool
$c>= :: Literal -> Literal -> Bool
>= :: Literal -> Literal -> Bool
$cmax :: Literal -> Literal -> Literal
max :: Literal -> Literal -> Literal
$cmin :: Literal -> Literal -> Literal
min :: Literal -> Literal -> Literal
Ord, ReadPrec [Literal]
ReadPrec Literal
Int -> ReadS Literal
ReadS [Literal]
(Int -> ReadS Literal)
-> ReadS [Literal]
-> ReadPrec Literal
-> ReadPrec [Literal]
-> Read Literal
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Literal
readsPrec :: Int -> ReadS Literal
$creadList :: ReadS [Literal]
readList :: ReadS [Literal]
$creadPrec :: ReadPrec Literal
readPrec :: ReadPrec Literal
$creadListPrec :: ReadPrec [Literal]
readListPrec :: ReadPrec [Literal]
Read, Int -> Literal -> ShowS
[Literal] -> ShowS
Literal -> String
(Int -> Literal -> ShowS)
-> (Literal -> String) -> ([Literal] -> ShowS) -> Show Literal
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Literal -> ShowS
showsPrec :: Int -> Literal -> ShowS
$cshow :: Literal -> String
show :: Literal -> String
$cshowList :: [Literal] -> ShowS
showList :: [Literal] -> ShowS
Show)
_Literal :: Name
_Literal = (String -> Name
Core.Name String
"hydra/langs/kusto/kql.Literal")
_Literal_duration :: Name
_Literal_duration = (String -> Name
Core.Name String
"duration")
_Literal_datetime :: Name
_Literal_datetime = (String -> Name
Core.Name String
"datetime")
_Literal_string :: Name
_Literal_string = (String -> Name
Core.Name String
"string")
_Literal_int :: Name
_Literal_int = (String -> Name
Core.Name String
"int")
_Literal_long :: Name
_Literal_long = (String -> Name
Core.Name String
"long")
_Literal_double :: Name
_Literal_double = (String -> Name
Core.Name String
"double")
_Literal_boolean :: Name
_Literal_boolean = (String -> Name
Core.Name String
"boolean")
data Order =
OrderAscending |
OrderDescending
deriving (Order -> Order -> Bool
(Order -> Order -> Bool) -> (Order -> Order -> Bool) -> Eq Order
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Order -> Order -> Bool
== :: Order -> Order -> Bool
$c/= :: Order -> Order -> Bool
/= :: Order -> Order -> Bool
Eq, Eq Order
Eq Order =>
(Order -> Order -> Ordering)
-> (Order -> Order -> Bool)
-> (Order -> Order -> Bool)
-> (Order -> Order -> Bool)
-> (Order -> Order -> Bool)
-> (Order -> Order -> Order)
-> (Order -> Order -> Order)
-> Ord Order
Order -> Order -> Bool
Order -> Order -> Ordering
Order -> Order -> Order
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Order -> Order -> Ordering
compare :: Order -> Order -> Ordering
$c< :: Order -> Order -> Bool
< :: Order -> Order -> Bool
$c<= :: Order -> Order -> Bool
<= :: Order -> Order -> Bool
$c> :: Order -> Order -> Bool
> :: Order -> Order -> Bool
$c>= :: Order -> Order -> Bool
>= :: Order -> Order -> Bool
$cmax :: Order -> Order -> Order
max :: Order -> Order -> Order
$cmin :: Order -> Order -> Order
min :: Order -> Order -> Order
Ord, ReadPrec [Order]
ReadPrec Order
Int -> ReadS Order
ReadS [Order]
(Int -> ReadS Order)
-> ReadS [Order]
-> ReadPrec Order
-> ReadPrec [Order]
-> Read Order
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Order
readsPrec :: Int -> ReadS Order
$creadList :: ReadS [Order]
readList :: ReadS [Order]
$creadPrec :: ReadPrec Order
readPrec :: ReadPrec Order
$creadListPrec :: ReadPrec [Order]
readListPrec :: ReadPrec [Order]
Read, Int -> Order -> ShowS
[Order] -> ShowS
Order -> String
(Int -> Order -> ShowS)
-> (Order -> String) -> ([Order] -> ShowS) -> Show Order
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Order -> ShowS
showsPrec :: Int -> Order -> ShowS
$cshow :: Order -> String
show :: Order -> String
$cshowList :: [Order] -> ShowS
showList :: [Order] -> ShowS
Show)
_Order :: Name
_Order = (String -> Name
Core.Name String
"hydra/langs/kusto/kql.Order")
_Order_ascending :: Name
_Order_ascending = (String -> Name
Core.Name String
"ascending")
_Order_descending :: Name
_Order_descending = (String -> Name
Core.Name String
"descending")
data Parameter =
Parameter {
Parameter -> String
parameterKey :: String,
Parameter -> Literal
parameterValue :: Literal}
deriving (Parameter -> Parameter -> Bool
(Parameter -> Parameter -> Bool)
-> (Parameter -> Parameter -> Bool) -> Eq Parameter
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Parameter -> Parameter -> Bool
== :: Parameter -> Parameter -> Bool
$c/= :: Parameter -> Parameter -> Bool
/= :: Parameter -> Parameter -> Bool
Eq, Eq Parameter
Eq Parameter =>
(Parameter -> Parameter -> Ordering)
-> (Parameter -> Parameter -> Bool)
-> (Parameter -> Parameter -> Bool)
-> (Parameter -> Parameter -> Bool)
-> (Parameter -> Parameter -> Bool)
-> (Parameter -> Parameter -> Parameter)
-> (Parameter -> Parameter -> Parameter)
-> Ord Parameter
Parameter -> Parameter -> Bool
Parameter -> Parameter -> Ordering
Parameter -> Parameter -> Parameter
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Parameter -> Parameter -> Ordering
compare :: Parameter -> Parameter -> Ordering
$c< :: Parameter -> Parameter -> Bool
< :: Parameter -> Parameter -> Bool
$c<= :: Parameter -> Parameter -> Bool
<= :: Parameter -> Parameter -> Bool
$c> :: Parameter -> Parameter -> Bool
> :: Parameter -> Parameter -> Bool
$c>= :: Parameter -> Parameter -> Bool
>= :: Parameter -> Parameter -> Bool
$cmax :: Parameter -> Parameter -> Parameter
max :: Parameter -> Parameter -> Parameter
$cmin :: Parameter -> Parameter -> Parameter
min :: Parameter -> Parameter -> Parameter
Ord, ReadPrec [Parameter]
ReadPrec Parameter
Int -> ReadS Parameter
ReadS [Parameter]
(Int -> ReadS Parameter)
-> ReadS [Parameter]
-> ReadPrec Parameter
-> ReadPrec [Parameter]
-> Read Parameter
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Parameter
readsPrec :: Int -> ReadS Parameter
$creadList :: ReadS [Parameter]
readList :: ReadS [Parameter]
$creadPrec :: ReadPrec Parameter
readPrec :: ReadPrec Parameter
$creadListPrec :: ReadPrec [Parameter]
readListPrec :: ReadPrec [Parameter]
Read, Int -> Parameter -> ShowS
[Parameter] -> ShowS
Parameter -> String
(Int -> Parameter -> ShowS)
-> (Parameter -> String)
-> ([Parameter] -> ShowS)
-> Show Parameter
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Parameter -> ShowS
showsPrec :: Int -> Parameter -> ShowS
$cshow :: Parameter -> String
show :: Parameter -> String
$cshowList :: [Parameter] -> ShowS
showList :: [Parameter] -> ShowS
Show)
_Parameter :: Name
_Parameter = (String -> Name
Core.Name String
"hydra/langs/kusto/kql.Parameter")
_Parameter_key :: Name
_Parameter_key = (String -> Name
Core.Name String
"key")
_Parameter_value :: Name
_Parameter_value = (String -> Name
Core.Name String
"value")
data ParseCommand =
ParseCommand {
ParseCommand -> ColumnName
parseCommandColumn :: ColumnName,
ParseCommand -> [KeyValuePair]
parseCommandPairs :: [KeyValuePair]}
deriving (ParseCommand -> ParseCommand -> Bool
(ParseCommand -> ParseCommand -> Bool)
-> (ParseCommand -> ParseCommand -> Bool) -> Eq ParseCommand
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ParseCommand -> ParseCommand -> Bool
== :: ParseCommand -> ParseCommand -> Bool
$c/= :: ParseCommand -> ParseCommand -> Bool
/= :: ParseCommand -> ParseCommand -> Bool
Eq, Eq ParseCommand
Eq ParseCommand =>
(ParseCommand -> ParseCommand -> Ordering)
-> (ParseCommand -> ParseCommand -> Bool)
-> (ParseCommand -> ParseCommand -> Bool)
-> (ParseCommand -> ParseCommand -> Bool)
-> (ParseCommand -> ParseCommand -> Bool)
-> (ParseCommand -> ParseCommand -> ParseCommand)
-> (ParseCommand -> ParseCommand -> ParseCommand)
-> Ord ParseCommand
ParseCommand -> ParseCommand -> Bool
ParseCommand -> ParseCommand -> Ordering
ParseCommand -> ParseCommand -> ParseCommand
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ParseCommand -> ParseCommand -> Ordering
compare :: ParseCommand -> ParseCommand -> Ordering
$c< :: ParseCommand -> ParseCommand -> Bool
< :: ParseCommand -> ParseCommand -> Bool
$c<= :: ParseCommand -> ParseCommand -> Bool
<= :: ParseCommand -> ParseCommand -> Bool
$c> :: ParseCommand -> ParseCommand -> Bool
> :: ParseCommand -> ParseCommand -> Bool
$c>= :: ParseCommand -> ParseCommand -> Bool
>= :: ParseCommand -> ParseCommand -> Bool
$cmax :: ParseCommand -> ParseCommand -> ParseCommand
max :: ParseCommand -> ParseCommand -> ParseCommand
$cmin :: ParseCommand -> ParseCommand -> ParseCommand
min :: ParseCommand -> ParseCommand -> ParseCommand
Ord, ReadPrec [ParseCommand]
ReadPrec ParseCommand
Int -> ReadS ParseCommand
ReadS [ParseCommand]
(Int -> ReadS ParseCommand)
-> ReadS [ParseCommand]
-> ReadPrec ParseCommand
-> ReadPrec [ParseCommand]
-> Read ParseCommand
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ParseCommand
readsPrec :: Int -> ReadS ParseCommand
$creadList :: ReadS [ParseCommand]
readList :: ReadS [ParseCommand]
$creadPrec :: ReadPrec ParseCommand
readPrec :: ReadPrec ParseCommand
$creadListPrec :: ReadPrec [ParseCommand]
readListPrec :: ReadPrec [ParseCommand]
Read, Int -> ParseCommand -> ShowS
[ParseCommand] -> ShowS
ParseCommand -> String
(Int -> ParseCommand -> ShowS)
-> (ParseCommand -> String)
-> ([ParseCommand] -> ShowS)
-> Show ParseCommand
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ParseCommand -> ShowS
showsPrec :: Int -> ParseCommand -> ShowS
$cshow :: ParseCommand -> String
show :: ParseCommand -> String
$cshowList :: [ParseCommand] -> ShowS
showList :: [ParseCommand] -> ShowS
Show)
_ParseCommand :: Name
_ParseCommand = (String -> Name
Core.Name String
"hydra/langs/kusto/kql.ParseCommand")
_ParseCommand_column :: Name
_ParseCommand_column = (String -> Name
Core.Name String
"column")
_ParseCommand_pairs :: Name
_ParseCommand_pairs = (String -> Name
Core.Name String
"pairs")
newtype PipelineExpression =
PipelineExpression {
PipelineExpression -> [TabularExpression]
unPipelineExpression :: [TabularExpression]}
deriving (PipelineExpression -> PipelineExpression -> Bool
(PipelineExpression -> PipelineExpression -> Bool)
-> (PipelineExpression -> PipelineExpression -> Bool)
-> Eq PipelineExpression
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PipelineExpression -> PipelineExpression -> Bool
== :: PipelineExpression -> PipelineExpression -> Bool
$c/= :: PipelineExpression -> PipelineExpression -> Bool
/= :: PipelineExpression -> PipelineExpression -> Bool
Eq, Eq PipelineExpression
Eq PipelineExpression =>
(PipelineExpression -> PipelineExpression -> Ordering)
-> (PipelineExpression -> PipelineExpression -> Bool)
-> (PipelineExpression -> PipelineExpression -> Bool)
-> (PipelineExpression -> PipelineExpression -> Bool)
-> (PipelineExpression -> PipelineExpression -> Bool)
-> (PipelineExpression -> PipelineExpression -> PipelineExpression)
-> (PipelineExpression -> PipelineExpression -> PipelineExpression)
-> Ord PipelineExpression
PipelineExpression -> PipelineExpression -> Bool
PipelineExpression -> PipelineExpression -> Ordering
PipelineExpression -> PipelineExpression -> PipelineExpression
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: PipelineExpression -> PipelineExpression -> Ordering
compare :: PipelineExpression -> PipelineExpression -> Ordering
$c< :: PipelineExpression -> PipelineExpression -> Bool
< :: PipelineExpression -> PipelineExpression -> Bool
$c<= :: PipelineExpression -> PipelineExpression -> Bool
<= :: PipelineExpression -> PipelineExpression -> Bool
$c> :: PipelineExpression -> PipelineExpression -> Bool
> :: PipelineExpression -> PipelineExpression -> Bool
$c>= :: PipelineExpression -> PipelineExpression -> Bool
>= :: PipelineExpression -> PipelineExpression -> Bool
$cmax :: PipelineExpression -> PipelineExpression -> PipelineExpression
max :: PipelineExpression -> PipelineExpression -> PipelineExpression
$cmin :: PipelineExpression -> PipelineExpression -> PipelineExpression
min :: PipelineExpression -> PipelineExpression -> PipelineExpression
Ord, ReadPrec [PipelineExpression]
ReadPrec PipelineExpression
Int -> ReadS PipelineExpression
ReadS [PipelineExpression]
(Int -> ReadS PipelineExpression)
-> ReadS [PipelineExpression]
-> ReadPrec PipelineExpression
-> ReadPrec [PipelineExpression]
-> Read PipelineExpression
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS PipelineExpression
readsPrec :: Int -> ReadS PipelineExpression
$creadList :: ReadS [PipelineExpression]
readList :: ReadS [PipelineExpression]
$creadPrec :: ReadPrec PipelineExpression
readPrec :: ReadPrec PipelineExpression
$creadListPrec :: ReadPrec [PipelineExpression]
readListPrec :: ReadPrec [PipelineExpression]
Read, Int -> PipelineExpression -> ShowS
[PipelineExpression] -> ShowS
PipelineExpression -> String
(Int -> PipelineExpression -> ShowS)
-> (PipelineExpression -> String)
-> ([PipelineExpression] -> ShowS)
-> Show PipelineExpression
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PipelineExpression -> ShowS
showsPrec :: Int -> PipelineExpression -> ShowS
$cshow :: PipelineExpression -> String
show :: PipelineExpression -> String
$cshowList :: [PipelineExpression] -> ShowS
showList :: [PipelineExpression] -> ShowS
Show)
_PipelineExpression :: Name
_PipelineExpression = (String -> Name
Core.Name String
"hydra/langs/kusto/kql.PipelineExpression")
data PrintCommand =
PrintCommand {
PrintCommand -> Maybe ColumnName
printCommandColumn :: (Maybe ColumnName),
PrintCommand -> Expression
printCommandExpression :: Expression}
deriving (PrintCommand -> PrintCommand -> Bool
(PrintCommand -> PrintCommand -> Bool)
-> (PrintCommand -> PrintCommand -> Bool) -> Eq PrintCommand
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PrintCommand -> PrintCommand -> Bool
== :: PrintCommand -> PrintCommand -> Bool
$c/= :: PrintCommand -> PrintCommand -> Bool
/= :: PrintCommand -> PrintCommand -> Bool
Eq, Eq PrintCommand
Eq PrintCommand =>
(PrintCommand -> PrintCommand -> Ordering)
-> (PrintCommand -> PrintCommand -> Bool)
-> (PrintCommand -> PrintCommand -> Bool)
-> (PrintCommand -> PrintCommand -> Bool)
-> (PrintCommand -> PrintCommand -> Bool)
-> (PrintCommand -> PrintCommand -> PrintCommand)
-> (PrintCommand -> PrintCommand -> PrintCommand)
-> Ord PrintCommand
PrintCommand -> PrintCommand -> Bool
PrintCommand -> PrintCommand -> Ordering
PrintCommand -> PrintCommand -> PrintCommand
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: PrintCommand -> PrintCommand -> Ordering
compare :: PrintCommand -> PrintCommand -> Ordering
$c< :: PrintCommand -> PrintCommand -> Bool
< :: PrintCommand -> PrintCommand -> Bool
$c<= :: PrintCommand -> PrintCommand -> Bool
<= :: PrintCommand -> PrintCommand -> Bool
$c> :: PrintCommand -> PrintCommand -> Bool
> :: PrintCommand -> PrintCommand -> Bool
$c>= :: PrintCommand -> PrintCommand -> Bool
>= :: PrintCommand -> PrintCommand -> Bool
$cmax :: PrintCommand -> PrintCommand -> PrintCommand
max :: PrintCommand -> PrintCommand -> PrintCommand
$cmin :: PrintCommand -> PrintCommand -> PrintCommand
min :: PrintCommand -> PrintCommand -> PrintCommand
Ord, ReadPrec [PrintCommand]
ReadPrec PrintCommand
Int -> ReadS PrintCommand
ReadS [PrintCommand]
(Int -> ReadS PrintCommand)
-> ReadS [PrintCommand]
-> ReadPrec PrintCommand
-> ReadPrec [PrintCommand]
-> Read PrintCommand
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS PrintCommand
readsPrec :: Int -> ReadS PrintCommand
$creadList :: ReadS [PrintCommand]
readList :: ReadS [PrintCommand]
$creadPrec :: ReadPrec PrintCommand
readPrec :: ReadPrec PrintCommand
$creadListPrec :: ReadPrec [PrintCommand]
readListPrec :: ReadPrec [PrintCommand]
Read, Int -> PrintCommand -> ShowS
[PrintCommand] -> ShowS
PrintCommand -> String
(Int -> PrintCommand -> ShowS)
-> (PrintCommand -> String)
-> ([PrintCommand] -> ShowS)
-> Show PrintCommand
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PrintCommand -> ShowS
showsPrec :: Int -> PrintCommand -> ShowS
$cshow :: PrintCommand -> String
show :: PrintCommand -> String
$cshowList :: [PrintCommand] -> ShowS
showList :: [PrintCommand] -> ShowS
Show)
_PrintCommand :: Name
_PrintCommand = (String -> Name
Core.Name String
"hydra/langs/kusto/kql.PrintCommand")
_PrintCommand_column :: Name
_PrintCommand_column = (String -> Name
Core.Name String
"column")
_PrintCommand_expression :: Name
_PrintCommand_expression = (String -> Name
Core.Name String
"expression")
data Projection =
Projection {
Projection -> Expression
projectionExpression :: Expression,
Projection -> Maybe ColumnName
projectionAlias :: (Maybe ColumnName)}
deriving (Projection -> Projection -> Bool
(Projection -> Projection -> Bool)
-> (Projection -> Projection -> Bool) -> Eq Projection
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Projection -> Projection -> Bool
== :: Projection -> Projection -> Bool
$c/= :: Projection -> Projection -> Bool
/= :: Projection -> Projection -> Bool
Eq, Eq Projection
Eq Projection =>
(Projection -> Projection -> Ordering)
-> (Projection -> Projection -> Bool)
-> (Projection -> Projection -> Bool)
-> (Projection -> Projection -> Bool)
-> (Projection -> Projection -> Bool)
-> (Projection -> Projection -> Projection)
-> (Projection -> Projection -> Projection)
-> Ord Projection
Projection -> Projection -> Bool
Projection -> Projection -> Ordering
Projection -> Projection -> Projection
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Projection -> Projection -> Ordering
compare :: Projection -> Projection -> Ordering
$c< :: Projection -> Projection -> Bool
< :: Projection -> Projection -> Bool
$c<= :: Projection -> Projection -> Bool
<= :: Projection -> Projection -> Bool
$c> :: Projection -> Projection -> Bool
> :: Projection -> Projection -> Bool
$c>= :: Projection -> Projection -> Bool
>= :: Projection -> Projection -> Bool
$cmax :: Projection -> Projection -> Projection
max :: Projection -> Projection -> Projection
$cmin :: Projection -> Projection -> Projection
min :: Projection -> Projection -> Projection
Ord, ReadPrec [Projection]
ReadPrec Projection
Int -> ReadS Projection
ReadS [Projection]
(Int -> ReadS Projection)
-> ReadS [Projection]
-> ReadPrec Projection
-> ReadPrec [Projection]
-> Read Projection
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Projection
readsPrec :: Int -> ReadS Projection
$creadList :: ReadS [Projection]
readList :: ReadS [Projection]
$creadPrec :: ReadPrec Projection
readPrec :: ReadPrec Projection
$creadListPrec :: ReadPrec [Projection]
readListPrec :: ReadPrec [Projection]
Read, Int -> Projection -> ShowS
[Projection] -> ShowS
Projection -> String
(Int -> Projection -> ShowS)
-> (Projection -> String)
-> ([Projection] -> ShowS)
-> Show Projection
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Projection -> ShowS
showsPrec :: Int -> Projection -> ShowS
$cshow :: Projection -> String
show :: Projection -> String
$cshowList :: [Projection] -> ShowS
showList :: [Projection] -> ShowS
Show)
_Projection :: Name
_Projection = (String -> Name
Core.Name String
"hydra/langs/kusto/kql.Projection")
_Projection_expression :: Name
_Projection_expression = (String -> Name
Core.Name String
"expression")
_Projection_alias :: Name
_Projection_alias = (String -> Name
Core.Name String
"alias")
data PropertyExpression =
PropertyExpression {
PropertyExpression -> Expression
propertyExpressionExpression :: Expression,
PropertyExpression -> String
propertyExpressionProperty :: String}
deriving (PropertyExpression -> PropertyExpression -> Bool
(PropertyExpression -> PropertyExpression -> Bool)
-> (PropertyExpression -> PropertyExpression -> Bool)
-> Eq PropertyExpression
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PropertyExpression -> PropertyExpression -> Bool
== :: PropertyExpression -> PropertyExpression -> Bool
$c/= :: PropertyExpression -> PropertyExpression -> Bool
/= :: PropertyExpression -> PropertyExpression -> Bool
Eq, Eq PropertyExpression
Eq PropertyExpression =>
(PropertyExpression -> PropertyExpression -> Ordering)
-> (PropertyExpression -> PropertyExpression -> Bool)
-> (PropertyExpression -> PropertyExpression -> Bool)
-> (PropertyExpression -> PropertyExpression -> Bool)
-> (PropertyExpression -> PropertyExpression -> Bool)
-> (PropertyExpression -> PropertyExpression -> PropertyExpression)
-> (PropertyExpression -> PropertyExpression -> PropertyExpression)
-> Ord PropertyExpression
PropertyExpression -> PropertyExpression -> Bool
PropertyExpression -> PropertyExpression -> Ordering
PropertyExpression -> PropertyExpression -> PropertyExpression
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: PropertyExpression -> PropertyExpression -> Ordering
compare :: PropertyExpression -> PropertyExpression -> Ordering
$c< :: PropertyExpression -> PropertyExpression -> Bool
< :: PropertyExpression -> PropertyExpression -> Bool
$c<= :: PropertyExpression -> PropertyExpression -> Bool
<= :: PropertyExpression -> PropertyExpression -> Bool
$c> :: PropertyExpression -> PropertyExpression -> Bool
> :: PropertyExpression -> PropertyExpression -> Bool
$c>= :: PropertyExpression -> PropertyExpression -> Bool
>= :: PropertyExpression -> PropertyExpression -> Bool
$cmax :: PropertyExpression -> PropertyExpression -> PropertyExpression
max :: PropertyExpression -> PropertyExpression -> PropertyExpression
$cmin :: PropertyExpression -> PropertyExpression -> PropertyExpression
min :: PropertyExpression -> PropertyExpression -> PropertyExpression
Ord, ReadPrec [PropertyExpression]
ReadPrec PropertyExpression
Int -> ReadS PropertyExpression
ReadS [PropertyExpression]
(Int -> ReadS PropertyExpression)
-> ReadS [PropertyExpression]
-> ReadPrec PropertyExpression
-> ReadPrec [PropertyExpression]
-> Read PropertyExpression
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS PropertyExpression
readsPrec :: Int -> ReadS PropertyExpression
$creadList :: ReadS [PropertyExpression]
readList :: ReadS [PropertyExpression]
$creadPrec :: ReadPrec PropertyExpression
readPrec :: ReadPrec PropertyExpression
$creadListPrec :: ReadPrec [PropertyExpression]
readListPrec :: ReadPrec [PropertyExpression]
Read, Int -> PropertyExpression -> ShowS
[PropertyExpression] -> ShowS
PropertyExpression -> String
(Int -> PropertyExpression -> ShowS)
-> (PropertyExpression -> String)
-> ([PropertyExpression] -> ShowS)
-> Show PropertyExpression
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PropertyExpression -> ShowS
showsPrec :: Int -> PropertyExpression -> ShowS
$cshow :: PropertyExpression -> String
show :: PropertyExpression -> String
$cshowList :: [PropertyExpression] -> ShowS
showList :: [PropertyExpression] -> ShowS
Show)
_PropertyExpression :: Name
_PropertyExpression = (String -> Name
Core.Name String
"hydra/langs/kusto/kql.PropertyExpression")
_PropertyExpression_expression :: Name
_PropertyExpression_expression = (String -> Name
Core.Name String
"expression")
_PropertyExpression_property :: Name
_PropertyExpression_property = (String -> Name
Core.Name String
"property")
newtype Query =
Query {
Query -> TabularExpression
unQuery :: TabularExpression}
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, Eq Query
Eq Query =>
(Query -> Query -> Ordering)
-> (Query -> Query -> Bool)
-> (Query -> Query -> Bool)
-> (Query -> Query -> Bool)
-> (Query -> Query -> Bool)
-> (Query -> Query -> Query)
-> (Query -> Query -> Query)
-> Ord Query
Query -> Query -> Bool
Query -> Query -> Ordering
Query -> Query -> Query
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Query -> Query -> Ordering
compare :: Query -> Query -> Ordering
$c< :: Query -> Query -> Bool
< :: Query -> Query -> Bool
$c<= :: Query -> Query -> Bool
<= :: Query -> Query -> Bool
$c> :: Query -> Query -> Bool
> :: Query -> Query -> Bool
$c>= :: Query -> Query -> Bool
>= :: Query -> Query -> Bool
$cmax :: Query -> Query -> Query
max :: Query -> Query -> Query
$cmin :: Query -> Query -> Query
min :: Query -> Query -> Query
Ord, ReadPrec [Query]
ReadPrec Query
Int -> ReadS Query
ReadS [Query]
(Int -> ReadS Query)
-> ReadS [Query]
-> ReadPrec Query
-> ReadPrec [Query]
-> Read Query
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Query
readsPrec :: Int -> ReadS Query
$creadList :: ReadS [Query]
readList :: ReadS [Query]
$creadPrec :: ReadPrec Query
readPrec :: ReadPrec Query
$creadListPrec :: ReadPrec [Query]
readListPrec :: ReadPrec [Query]
Read, 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)
_Query :: Name
_Query = (String -> Name
Core.Name String
"hydra/langs/kusto/kql.Query")
data SearchCommand =
SearchCommand {
SearchCommand -> [TableName]
searchCommandDatasets :: [TableName],
SearchCommand -> Expression
searchCommandPattern :: Expression}
deriving (SearchCommand -> SearchCommand -> Bool
(SearchCommand -> SearchCommand -> Bool)
-> (SearchCommand -> SearchCommand -> Bool) -> Eq SearchCommand
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SearchCommand -> SearchCommand -> Bool
== :: SearchCommand -> SearchCommand -> Bool
$c/= :: SearchCommand -> SearchCommand -> Bool
/= :: SearchCommand -> SearchCommand -> Bool
Eq, Eq SearchCommand
Eq SearchCommand =>
(SearchCommand -> SearchCommand -> Ordering)
-> (SearchCommand -> SearchCommand -> Bool)
-> (SearchCommand -> SearchCommand -> Bool)
-> (SearchCommand -> SearchCommand -> Bool)
-> (SearchCommand -> SearchCommand -> Bool)
-> (SearchCommand -> SearchCommand -> SearchCommand)
-> (SearchCommand -> SearchCommand -> SearchCommand)
-> Ord SearchCommand
SearchCommand -> SearchCommand -> Bool
SearchCommand -> SearchCommand -> Ordering
SearchCommand -> SearchCommand -> SearchCommand
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: SearchCommand -> SearchCommand -> Ordering
compare :: SearchCommand -> SearchCommand -> Ordering
$c< :: SearchCommand -> SearchCommand -> Bool
< :: SearchCommand -> SearchCommand -> Bool
$c<= :: SearchCommand -> SearchCommand -> Bool
<= :: SearchCommand -> SearchCommand -> Bool
$c> :: SearchCommand -> SearchCommand -> Bool
> :: SearchCommand -> SearchCommand -> Bool
$c>= :: SearchCommand -> SearchCommand -> Bool
>= :: SearchCommand -> SearchCommand -> Bool
$cmax :: SearchCommand -> SearchCommand -> SearchCommand
max :: SearchCommand -> SearchCommand -> SearchCommand
$cmin :: SearchCommand -> SearchCommand -> SearchCommand
min :: SearchCommand -> SearchCommand -> SearchCommand
Ord, ReadPrec [SearchCommand]
ReadPrec SearchCommand
Int -> ReadS SearchCommand
ReadS [SearchCommand]
(Int -> ReadS SearchCommand)
-> ReadS [SearchCommand]
-> ReadPrec SearchCommand
-> ReadPrec [SearchCommand]
-> Read SearchCommand
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS SearchCommand
readsPrec :: Int -> ReadS SearchCommand
$creadList :: ReadS [SearchCommand]
readList :: ReadS [SearchCommand]
$creadPrec :: ReadPrec SearchCommand
readPrec :: ReadPrec SearchCommand
$creadListPrec :: ReadPrec [SearchCommand]
readListPrec :: ReadPrec [SearchCommand]
Read, Int -> SearchCommand -> ShowS
[SearchCommand] -> ShowS
SearchCommand -> String
(Int -> SearchCommand -> ShowS)
-> (SearchCommand -> String)
-> ([SearchCommand] -> ShowS)
-> Show SearchCommand
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SearchCommand -> ShowS
showsPrec :: Int -> SearchCommand -> ShowS
$cshow :: SearchCommand -> String
show :: SearchCommand -> String
$cshowList :: [SearchCommand] -> ShowS
showList :: [SearchCommand] -> ShowS
Show)
_SearchCommand :: Name
_SearchCommand = (String -> Name
Core.Name String
"hydra/langs/kusto/kql.SearchCommand")
_SearchCommand_datasets :: Name
_SearchCommand_datasets = (String -> Name
Core.Name String
"datasets")
_SearchCommand_pattern :: Name
_SearchCommand_pattern = (String -> Name
Core.Name String
"pattern")
data SummarizeCommand =
SummarizeCommand {
SummarizeCommand -> [ColumnAssignment]
summarizeCommandColumns :: [ColumnAssignment],
SummarizeCommand -> [ColumnName]
summarizeCommandBy :: [ColumnName]}
deriving (SummarizeCommand -> SummarizeCommand -> Bool
(SummarizeCommand -> SummarizeCommand -> Bool)
-> (SummarizeCommand -> SummarizeCommand -> Bool)
-> Eq SummarizeCommand
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SummarizeCommand -> SummarizeCommand -> Bool
== :: SummarizeCommand -> SummarizeCommand -> Bool
$c/= :: SummarizeCommand -> SummarizeCommand -> Bool
/= :: SummarizeCommand -> SummarizeCommand -> Bool
Eq, Eq SummarizeCommand
Eq SummarizeCommand =>
(SummarizeCommand -> SummarizeCommand -> Ordering)
-> (SummarizeCommand -> SummarizeCommand -> Bool)
-> (SummarizeCommand -> SummarizeCommand -> Bool)
-> (SummarizeCommand -> SummarizeCommand -> Bool)
-> (SummarizeCommand -> SummarizeCommand -> Bool)
-> (SummarizeCommand -> SummarizeCommand -> SummarizeCommand)
-> (SummarizeCommand -> SummarizeCommand -> SummarizeCommand)
-> Ord SummarizeCommand
SummarizeCommand -> SummarizeCommand -> Bool
SummarizeCommand -> SummarizeCommand -> Ordering
SummarizeCommand -> SummarizeCommand -> SummarizeCommand
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: SummarizeCommand -> SummarizeCommand -> Ordering
compare :: SummarizeCommand -> SummarizeCommand -> Ordering
$c< :: SummarizeCommand -> SummarizeCommand -> Bool
< :: SummarizeCommand -> SummarizeCommand -> Bool
$c<= :: SummarizeCommand -> SummarizeCommand -> Bool
<= :: SummarizeCommand -> SummarizeCommand -> Bool
$c> :: SummarizeCommand -> SummarizeCommand -> Bool
> :: SummarizeCommand -> SummarizeCommand -> Bool
$c>= :: SummarizeCommand -> SummarizeCommand -> Bool
>= :: SummarizeCommand -> SummarizeCommand -> Bool
$cmax :: SummarizeCommand -> SummarizeCommand -> SummarizeCommand
max :: SummarizeCommand -> SummarizeCommand -> SummarizeCommand
$cmin :: SummarizeCommand -> SummarizeCommand -> SummarizeCommand
min :: SummarizeCommand -> SummarizeCommand -> SummarizeCommand
Ord, ReadPrec [SummarizeCommand]
ReadPrec SummarizeCommand
Int -> ReadS SummarizeCommand
ReadS [SummarizeCommand]
(Int -> ReadS SummarizeCommand)
-> ReadS [SummarizeCommand]
-> ReadPrec SummarizeCommand
-> ReadPrec [SummarizeCommand]
-> Read SummarizeCommand
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS SummarizeCommand
readsPrec :: Int -> ReadS SummarizeCommand
$creadList :: ReadS [SummarizeCommand]
readList :: ReadS [SummarizeCommand]
$creadPrec :: ReadPrec SummarizeCommand
readPrec :: ReadPrec SummarizeCommand
$creadListPrec :: ReadPrec [SummarizeCommand]
readListPrec :: ReadPrec [SummarizeCommand]
Read, Int -> SummarizeCommand -> ShowS
[SummarizeCommand] -> ShowS
SummarizeCommand -> String
(Int -> SummarizeCommand -> ShowS)
-> (SummarizeCommand -> String)
-> ([SummarizeCommand] -> ShowS)
-> Show SummarizeCommand
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SummarizeCommand -> ShowS
showsPrec :: Int -> SummarizeCommand -> ShowS
$cshow :: SummarizeCommand -> String
show :: SummarizeCommand -> String
$cshowList :: [SummarizeCommand] -> ShowS
showList :: [SummarizeCommand] -> ShowS
Show)
_SummarizeCommand :: Name
_SummarizeCommand = (String -> Name
Core.Name String
"hydra/langs/kusto/kql.SummarizeCommand")
_SummarizeCommand_columns :: Name
_SummarizeCommand_columns = (String -> Name
Core.Name String
"columns")
_SummarizeCommand_by :: Name
_SummarizeCommand_by = (String -> Name
Core.Name String
"by")
newtype TableName =
TableName {
TableName -> String
unTableName :: String}
deriving (TableName -> TableName -> Bool
(TableName -> TableName -> Bool)
-> (TableName -> TableName -> Bool) -> Eq TableName
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TableName -> TableName -> Bool
== :: TableName -> TableName -> Bool
$c/= :: TableName -> TableName -> Bool
/= :: TableName -> TableName -> Bool
Eq, Eq TableName
Eq TableName =>
(TableName -> TableName -> Ordering)
-> (TableName -> TableName -> Bool)
-> (TableName -> TableName -> Bool)
-> (TableName -> TableName -> Bool)
-> (TableName -> TableName -> Bool)
-> (TableName -> TableName -> TableName)
-> (TableName -> TableName -> TableName)
-> Ord TableName
TableName -> TableName -> Bool
TableName -> TableName -> Ordering
TableName -> TableName -> TableName
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: TableName -> TableName -> Ordering
compare :: TableName -> TableName -> Ordering
$c< :: TableName -> TableName -> Bool
< :: TableName -> TableName -> Bool
$c<= :: TableName -> TableName -> Bool
<= :: TableName -> TableName -> Bool
$c> :: TableName -> TableName -> Bool
> :: TableName -> TableName -> Bool
$c>= :: TableName -> TableName -> Bool
>= :: TableName -> TableName -> Bool
$cmax :: TableName -> TableName -> TableName
max :: TableName -> TableName -> TableName
$cmin :: TableName -> TableName -> TableName
min :: TableName -> TableName -> TableName
Ord, ReadPrec [TableName]
ReadPrec TableName
Int -> ReadS TableName
ReadS [TableName]
(Int -> ReadS TableName)
-> ReadS [TableName]
-> ReadPrec TableName
-> ReadPrec [TableName]
-> Read TableName
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS TableName
readsPrec :: Int -> ReadS TableName
$creadList :: ReadS [TableName]
readList :: ReadS [TableName]
$creadPrec :: ReadPrec TableName
readPrec :: ReadPrec TableName
$creadListPrec :: ReadPrec [TableName]
readListPrec :: ReadPrec [TableName]
Read, Int -> TableName -> ShowS
[TableName] -> ShowS
TableName -> String
(Int -> TableName -> ShowS)
-> (TableName -> String)
-> ([TableName] -> ShowS)
-> Show TableName
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TableName -> ShowS
showsPrec :: Int -> TableName -> ShowS
$cshow :: TableName -> String
show :: TableName -> String
$cshowList :: [TableName] -> ShowS
showList :: [TableName] -> ShowS
Show)
_TableName :: Name
_TableName = (String -> Name
Core.Name String
"hydra/langs/kusto/kql.TableName")
data TopCommand =
TopCommand {
TopCommand -> Int
topCommandCount :: Int,
TopCommand -> [SortBy]
topCommandSort :: [SortBy]}
deriving (TopCommand -> TopCommand -> Bool
(TopCommand -> TopCommand -> Bool)
-> (TopCommand -> TopCommand -> Bool) -> Eq TopCommand
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TopCommand -> TopCommand -> Bool
== :: TopCommand -> TopCommand -> Bool
$c/= :: TopCommand -> TopCommand -> Bool
/= :: TopCommand -> TopCommand -> Bool
Eq, Eq TopCommand
Eq TopCommand =>
(TopCommand -> TopCommand -> Ordering)
-> (TopCommand -> TopCommand -> Bool)
-> (TopCommand -> TopCommand -> Bool)
-> (TopCommand -> TopCommand -> Bool)
-> (TopCommand -> TopCommand -> Bool)
-> (TopCommand -> TopCommand -> TopCommand)
-> (TopCommand -> TopCommand -> TopCommand)
-> Ord TopCommand
TopCommand -> TopCommand -> Bool
TopCommand -> TopCommand -> Ordering
TopCommand -> TopCommand -> TopCommand
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: TopCommand -> TopCommand -> Ordering
compare :: TopCommand -> TopCommand -> Ordering
$c< :: TopCommand -> TopCommand -> Bool
< :: TopCommand -> TopCommand -> Bool
$c<= :: TopCommand -> TopCommand -> Bool
<= :: TopCommand -> TopCommand -> Bool
$c> :: TopCommand -> TopCommand -> Bool
> :: TopCommand -> TopCommand -> Bool
$c>= :: TopCommand -> TopCommand -> Bool
>= :: TopCommand -> TopCommand -> Bool
$cmax :: TopCommand -> TopCommand -> TopCommand
max :: TopCommand -> TopCommand -> TopCommand
$cmin :: TopCommand -> TopCommand -> TopCommand
min :: TopCommand -> TopCommand -> TopCommand
Ord, ReadPrec [TopCommand]
ReadPrec TopCommand
Int -> ReadS TopCommand
ReadS [TopCommand]
(Int -> ReadS TopCommand)
-> ReadS [TopCommand]
-> ReadPrec TopCommand
-> ReadPrec [TopCommand]
-> Read TopCommand
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS TopCommand
readsPrec :: Int -> ReadS TopCommand
$creadList :: ReadS [TopCommand]
readList :: ReadS [TopCommand]
$creadPrec :: ReadPrec TopCommand
readPrec :: ReadPrec TopCommand
$creadListPrec :: ReadPrec [TopCommand]
readListPrec :: ReadPrec [TopCommand]
Read, Int -> TopCommand -> ShowS
[TopCommand] -> ShowS
TopCommand -> String
(Int -> TopCommand -> ShowS)
-> (TopCommand -> String)
-> ([TopCommand] -> ShowS)
-> Show TopCommand
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TopCommand -> ShowS
showsPrec :: Int -> TopCommand -> ShowS
$cshow :: TopCommand -> String
show :: TopCommand -> String
$cshowList :: [TopCommand] -> ShowS
showList :: [TopCommand] -> ShowS
Show)
_TopCommand :: Name
_TopCommand = (String -> Name
Core.Name String
"hydra/langs/kusto/kql.TopCommand")
_TopCommand_count :: Name
_TopCommand_count = (String -> Name
Core.Name String
"count")
_TopCommand_sort :: Name
_TopCommand_sort = (String -> Name
Core.Name String
"sort")
data SortBy =
SortBy {
SortBy -> ColumnName
sortByColumn :: ColumnName,
SortBy -> Maybe Order
sortByOrder :: (Maybe Order)}
deriving (SortBy -> SortBy -> Bool
(SortBy -> SortBy -> Bool)
-> (SortBy -> SortBy -> Bool) -> Eq SortBy
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SortBy -> SortBy -> Bool
== :: SortBy -> SortBy -> Bool
$c/= :: SortBy -> SortBy -> Bool
/= :: SortBy -> SortBy -> Bool
Eq, Eq SortBy
Eq SortBy =>
(SortBy -> SortBy -> Ordering)
-> (SortBy -> SortBy -> Bool)
-> (SortBy -> SortBy -> Bool)
-> (SortBy -> SortBy -> Bool)
-> (SortBy -> SortBy -> Bool)
-> (SortBy -> SortBy -> SortBy)
-> (SortBy -> SortBy -> SortBy)
-> Ord SortBy
SortBy -> SortBy -> Bool
SortBy -> SortBy -> Ordering
SortBy -> SortBy -> SortBy
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: SortBy -> SortBy -> Ordering
compare :: SortBy -> SortBy -> Ordering
$c< :: SortBy -> SortBy -> Bool
< :: SortBy -> SortBy -> Bool
$c<= :: SortBy -> SortBy -> Bool
<= :: SortBy -> SortBy -> Bool
$c> :: SortBy -> SortBy -> Bool
> :: SortBy -> SortBy -> Bool
$c>= :: SortBy -> SortBy -> Bool
>= :: SortBy -> SortBy -> Bool
$cmax :: SortBy -> SortBy -> SortBy
max :: SortBy -> SortBy -> SortBy
$cmin :: SortBy -> SortBy -> SortBy
min :: SortBy -> SortBy -> SortBy
Ord, ReadPrec [SortBy]
ReadPrec SortBy
Int -> ReadS SortBy
ReadS [SortBy]
(Int -> ReadS SortBy)
-> ReadS [SortBy]
-> ReadPrec SortBy
-> ReadPrec [SortBy]
-> Read SortBy
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS SortBy
readsPrec :: Int -> ReadS SortBy
$creadList :: ReadS [SortBy]
readList :: ReadS [SortBy]
$creadPrec :: ReadPrec SortBy
readPrec :: ReadPrec SortBy
$creadListPrec :: ReadPrec [SortBy]
readListPrec :: ReadPrec [SortBy]
Read, Int -> SortBy -> ShowS
[SortBy] -> ShowS
SortBy -> String
(Int -> SortBy -> ShowS)
-> (SortBy -> String) -> ([SortBy] -> ShowS) -> Show SortBy
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SortBy -> ShowS
showsPrec :: Int -> SortBy -> ShowS
$cshow :: SortBy -> String
show :: SortBy -> String
$cshowList :: [SortBy] -> ShowS
showList :: [SortBy] -> ShowS
Show)
_SortBy :: Name
_SortBy = (String -> Name
Core.Name String
"hydra/langs/kusto/kql.SortBy")
_SortBy_column :: Name
_SortBy_column = (String -> Name
Core.Name String
"column")
_SortBy_order :: Name
_SortBy_order = (String -> Name
Core.Name String
"order")
data TabularExpression =
TabularExpressionCommand Command |
TabularExpressionPipeline PipelineExpression |
TabularExpressionLet LetExpression |
TabularExpressionTable TableName
deriving (TabularExpression -> TabularExpression -> Bool
(TabularExpression -> TabularExpression -> Bool)
-> (TabularExpression -> TabularExpression -> Bool)
-> Eq TabularExpression
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TabularExpression -> TabularExpression -> Bool
== :: TabularExpression -> TabularExpression -> Bool
$c/= :: TabularExpression -> TabularExpression -> Bool
/= :: TabularExpression -> TabularExpression -> Bool
Eq, Eq TabularExpression
Eq TabularExpression =>
(TabularExpression -> TabularExpression -> Ordering)
-> (TabularExpression -> TabularExpression -> Bool)
-> (TabularExpression -> TabularExpression -> Bool)
-> (TabularExpression -> TabularExpression -> Bool)
-> (TabularExpression -> TabularExpression -> Bool)
-> (TabularExpression -> TabularExpression -> TabularExpression)
-> (TabularExpression -> TabularExpression -> TabularExpression)
-> Ord TabularExpression
TabularExpression -> TabularExpression -> Bool
TabularExpression -> TabularExpression -> Ordering
TabularExpression -> TabularExpression -> TabularExpression
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: TabularExpression -> TabularExpression -> Ordering
compare :: TabularExpression -> TabularExpression -> Ordering
$c< :: TabularExpression -> TabularExpression -> Bool
< :: TabularExpression -> TabularExpression -> Bool
$c<= :: TabularExpression -> TabularExpression -> Bool
<= :: TabularExpression -> TabularExpression -> Bool
$c> :: TabularExpression -> TabularExpression -> Bool
> :: TabularExpression -> TabularExpression -> Bool
$c>= :: TabularExpression -> TabularExpression -> Bool
>= :: TabularExpression -> TabularExpression -> Bool
$cmax :: TabularExpression -> TabularExpression -> TabularExpression
max :: TabularExpression -> TabularExpression -> TabularExpression
$cmin :: TabularExpression -> TabularExpression -> TabularExpression
min :: TabularExpression -> TabularExpression -> TabularExpression
Ord, ReadPrec [TabularExpression]
ReadPrec TabularExpression
Int -> ReadS TabularExpression
ReadS [TabularExpression]
(Int -> ReadS TabularExpression)
-> ReadS [TabularExpression]
-> ReadPrec TabularExpression
-> ReadPrec [TabularExpression]
-> Read TabularExpression
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS TabularExpression
readsPrec :: Int -> ReadS TabularExpression
$creadList :: ReadS [TabularExpression]
readList :: ReadS [TabularExpression]
$creadPrec :: ReadPrec TabularExpression
readPrec :: ReadPrec TabularExpression
$creadListPrec :: ReadPrec [TabularExpression]
readListPrec :: ReadPrec [TabularExpression]
Read, Int -> TabularExpression -> ShowS
[TabularExpression] -> ShowS
TabularExpression -> String
(Int -> TabularExpression -> ShowS)
-> (TabularExpression -> String)
-> ([TabularExpression] -> ShowS)
-> Show TabularExpression
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TabularExpression -> ShowS
showsPrec :: Int -> TabularExpression -> ShowS
$cshow :: TabularExpression -> String
show :: TabularExpression -> String
$cshowList :: [TabularExpression] -> ShowS
showList :: [TabularExpression] -> ShowS
Show)
_TabularExpression :: Name
_TabularExpression = (String -> Name
Core.Name String
"hydra/langs/kusto/kql.TabularExpression")
_TabularExpression_command :: Name
_TabularExpression_command = (String -> Name
Core.Name String
"command")
_TabularExpression_pipeline :: Name
_TabularExpression_pipeline = (String -> Name
Core.Name String
"pipeline")
_TabularExpression_let :: Name
_TabularExpression_let = (String -> Name
Core.Name String
"let")
_TabularExpression_table :: Name
_TabularExpression_table = (String -> Name
Core.Name String
"table")
data UnaryExpression =
UnaryExpression {
UnaryExpression -> UnaryOperator
unaryExpressionOperator :: UnaryOperator,
UnaryExpression -> Expression
unaryExpressionExpression :: Expression}
deriving (UnaryExpression -> UnaryExpression -> Bool
(UnaryExpression -> UnaryExpression -> Bool)
-> (UnaryExpression -> UnaryExpression -> Bool)
-> Eq UnaryExpression
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: UnaryExpression -> UnaryExpression -> Bool
== :: UnaryExpression -> UnaryExpression -> Bool
$c/= :: UnaryExpression -> UnaryExpression -> Bool
/= :: UnaryExpression -> UnaryExpression -> Bool
Eq, Eq UnaryExpression
Eq UnaryExpression =>
(UnaryExpression -> UnaryExpression -> Ordering)
-> (UnaryExpression -> UnaryExpression -> Bool)
-> (UnaryExpression -> UnaryExpression -> Bool)
-> (UnaryExpression -> UnaryExpression -> Bool)
-> (UnaryExpression -> UnaryExpression -> Bool)
-> (UnaryExpression -> UnaryExpression -> UnaryExpression)
-> (UnaryExpression -> UnaryExpression -> UnaryExpression)
-> Ord UnaryExpression
UnaryExpression -> UnaryExpression -> Bool
UnaryExpression -> UnaryExpression -> Ordering
UnaryExpression -> UnaryExpression -> UnaryExpression
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: UnaryExpression -> UnaryExpression -> Ordering
compare :: UnaryExpression -> UnaryExpression -> Ordering
$c< :: UnaryExpression -> UnaryExpression -> Bool
< :: UnaryExpression -> UnaryExpression -> Bool
$c<= :: UnaryExpression -> UnaryExpression -> Bool
<= :: UnaryExpression -> UnaryExpression -> Bool
$c> :: UnaryExpression -> UnaryExpression -> Bool
> :: UnaryExpression -> UnaryExpression -> Bool
$c>= :: UnaryExpression -> UnaryExpression -> Bool
>= :: UnaryExpression -> UnaryExpression -> Bool
$cmax :: UnaryExpression -> UnaryExpression -> UnaryExpression
max :: UnaryExpression -> UnaryExpression -> UnaryExpression
$cmin :: UnaryExpression -> UnaryExpression -> UnaryExpression
min :: UnaryExpression -> UnaryExpression -> UnaryExpression
Ord, ReadPrec [UnaryExpression]
ReadPrec UnaryExpression
Int -> ReadS UnaryExpression
ReadS [UnaryExpression]
(Int -> ReadS UnaryExpression)
-> ReadS [UnaryExpression]
-> ReadPrec UnaryExpression
-> ReadPrec [UnaryExpression]
-> Read UnaryExpression
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS UnaryExpression
readsPrec :: Int -> ReadS UnaryExpression
$creadList :: ReadS [UnaryExpression]
readList :: ReadS [UnaryExpression]
$creadPrec :: ReadPrec UnaryExpression
readPrec :: ReadPrec UnaryExpression
$creadListPrec :: ReadPrec [UnaryExpression]
readListPrec :: ReadPrec [UnaryExpression]
Read, Int -> UnaryExpression -> ShowS
[UnaryExpression] -> ShowS
UnaryExpression -> String
(Int -> UnaryExpression -> ShowS)
-> (UnaryExpression -> String)
-> ([UnaryExpression] -> ShowS)
-> Show UnaryExpression
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> UnaryExpression -> ShowS
showsPrec :: Int -> UnaryExpression -> ShowS
$cshow :: UnaryExpression -> String
show :: UnaryExpression -> String
$cshowList :: [UnaryExpression] -> ShowS
showList :: [UnaryExpression] -> ShowS
Show)
_UnaryExpression :: Name
_UnaryExpression = (String -> Name
Core.Name String
"hydra/langs/kusto/kql.UnaryExpression")
_UnaryExpression_operator :: Name
_UnaryExpression_operator = (String -> Name
Core.Name String
"operator")
_UnaryExpression_expression :: Name
_UnaryExpression_expression = (String -> Name
Core.Name String
"expression")
data UnaryOperator =
UnaryOperatorNot
deriving (UnaryOperator -> UnaryOperator -> Bool
(UnaryOperator -> UnaryOperator -> Bool)
-> (UnaryOperator -> UnaryOperator -> Bool) -> Eq UnaryOperator
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: UnaryOperator -> UnaryOperator -> Bool
== :: UnaryOperator -> UnaryOperator -> Bool
$c/= :: UnaryOperator -> UnaryOperator -> Bool
/= :: UnaryOperator -> UnaryOperator -> Bool
Eq, Eq UnaryOperator
Eq UnaryOperator =>
(UnaryOperator -> UnaryOperator -> Ordering)
-> (UnaryOperator -> UnaryOperator -> Bool)
-> (UnaryOperator -> UnaryOperator -> Bool)
-> (UnaryOperator -> UnaryOperator -> Bool)
-> (UnaryOperator -> UnaryOperator -> Bool)
-> (UnaryOperator -> UnaryOperator -> UnaryOperator)
-> (UnaryOperator -> UnaryOperator -> UnaryOperator)
-> Ord UnaryOperator
UnaryOperator -> UnaryOperator -> Bool
UnaryOperator -> UnaryOperator -> Ordering
UnaryOperator -> UnaryOperator -> UnaryOperator
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: UnaryOperator -> UnaryOperator -> Ordering
compare :: UnaryOperator -> UnaryOperator -> Ordering
$c< :: UnaryOperator -> UnaryOperator -> Bool
< :: UnaryOperator -> UnaryOperator -> Bool
$c<= :: UnaryOperator -> UnaryOperator -> Bool
<= :: UnaryOperator -> UnaryOperator -> Bool
$c> :: UnaryOperator -> UnaryOperator -> Bool
> :: UnaryOperator -> UnaryOperator -> Bool
$c>= :: UnaryOperator -> UnaryOperator -> Bool
>= :: UnaryOperator -> UnaryOperator -> Bool
$cmax :: UnaryOperator -> UnaryOperator -> UnaryOperator
max :: UnaryOperator -> UnaryOperator -> UnaryOperator
$cmin :: UnaryOperator -> UnaryOperator -> UnaryOperator
min :: UnaryOperator -> UnaryOperator -> UnaryOperator
Ord, ReadPrec [UnaryOperator]
ReadPrec UnaryOperator
Int -> ReadS UnaryOperator
ReadS [UnaryOperator]
(Int -> ReadS UnaryOperator)
-> ReadS [UnaryOperator]
-> ReadPrec UnaryOperator
-> ReadPrec [UnaryOperator]
-> Read UnaryOperator
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS UnaryOperator
readsPrec :: Int -> ReadS UnaryOperator
$creadList :: ReadS [UnaryOperator]
readList :: ReadS [UnaryOperator]
$creadPrec :: ReadPrec UnaryOperator
readPrec :: ReadPrec UnaryOperator
$creadListPrec :: ReadPrec [UnaryOperator]
readListPrec :: ReadPrec [UnaryOperator]
Read, Int -> UnaryOperator -> ShowS
[UnaryOperator] -> ShowS
UnaryOperator -> String
(Int -> UnaryOperator -> ShowS)
-> (UnaryOperator -> String)
-> ([UnaryOperator] -> ShowS)
-> Show UnaryOperator
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> UnaryOperator -> ShowS
showsPrec :: Int -> UnaryOperator -> ShowS
$cshow :: UnaryOperator -> String
show :: UnaryOperator -> String
$cshowList :: [UnaryOperator] -> ShowS
showList :: [UnaryOperator] -> ShowS
Show)
_UnaryOperator :: Name
_UnaryOperator = (String -> Name
Core.Name String
"hydra/langs/kusto/kql.UnaryOperator")
_UnaryOperator_not :: Name
_UnaryOperator_not = (String -> Name
Core.Name String
"not")
data UnionCommand =
UnionCommand {
UnionCommand -> [Parameter]
unionCommandParameters :: [Parameter],
UnionCommand -> Maybe UnionKind
unionCommandKind :: (Maybe UnionKind),
UnionCommand -> Maybe ColumnName
unionCommandWithSource :: (Maybe ColumnName),
UnionCommand -> Maybe Bool
unionCommandIsFuzzy :: (Maybe Bool),
UnionCommand -> [TableName]
unionCommandTables :: [TableName]}
deriving (UnionCommand -> UnionCommand -> Bool
(UnionCommand -> UnionCommand -> Bool)
-> (UnionCommand -> UnionCommand -> Bool) -> Eq UnionCommand
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: UnionCommand -> UnionCommand -> Bool
== :: UnionCommand -> UnionCommand -> Bool
$c/= :: UnionCommand -> UnionCommand -> Bool
/= :: UnionCommand -> UnionCommand -> Bool
Eq, Eq UnionCommand
Eq UnionCommand =>
(UnionCommand -> UnionCommand -> Ordering)
-> (UnionCommand -> UnionCommand -> Bool)
-> (UnionCommand -> UnionCommand -> Bool)
-> (UnionCommand -> UnionCommand -> Bool)
-> (UnionCommand -> UnionCommand -> Bool)
-> (UnionCommand -> UnionCommand -> UnionCommand)
-> (UnionCommand -> UnionCommand -> UnionCommand)
-> Ord UnionCommand
UnionCommand -> UnionCommand -> Bool
UnionCommand -> UnionCommand -> Ordering
UnionCommand -> UnionCommand -> UnionCommand
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: UnionCommand -> UnionCommand -> Ordering
compare :: UnionCommand -> UnionCommand -> Ordering
$c< :: UnionCommand -> UnionCommand -> Bool
< :: UnionCommand -> UnionCommand -> Bool
$c<= :: UnionCommand -> UnionCommand -> Bool
<= :: UnionCommand -> UnionCommand -> Bool
$c> :: UnionCommand -> UnionCommand -> Bool
> :: UnionCommand -> UnionCommand -> Bool
$c>= :: UnionCommand -> UnionCommand -> Bool
>= :: UnionCommand -> UnionCommand -> Bool
$cmax :: UnionCommand -> UnionCommand -> UnionCommand
max :: UnionCommand -> UnionCommand -> UnionCommand
$cmin :: UnionCommand -> UnionCommand -> UnionCommand
min :: UnionCommand -> UnionCommand -> UnionCommand
Ord, ReadPrec [UnionCommand]
ReadPrec UnionCommand
Int -> ReadS UnionCommand
ReadS [UnionCommand]
(Int -> ReadS UnionCommand)
-> ReadS [UnionCommand]
-> ReadPrec UnionCommand
-> ReadPrec [UnionCommand]
-> Read UnionCommand
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS UnionCommand
readsPrec :: Int -> ReadS UnionCommand
$creadList :: ReadS [UnionCommand]
readList :: ReadS [UnionCommand]
$creadPrec :: ReadPrec UnionCommand
readPrec :: ReadPrec UnionCommand
$creadListPrec :: ReadPrec [UnionCommand]
readListPrec :: ReadPrec [UnionCommand]
Read, Int -> UnionCommand -> ShowS
[UnionCommand] -> ShowS
UnionCommand -> String
(Int -> UnionCommand -> ShowS)
-> (UnionCommand -> String)
-> ([UnionCommand] -> ShowS)
-> Show UnionCommand
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> UnionCommand -> ShowS
showsPrec :: Int -> UnionCommand -> ShowS
$cshow :: UnionCommand -> String
show :: UnionCommand -> String
$cshowList :: [UnionCommand] -> ShowS
showList :: [UnionCommand] -> ShowS
Show)
_UnionCommand :: Name
_UnionCommand = (String -> Name
Core.Name String
"hydra/langs/kusto/kql.UnionCommand")
_UnionCommand_parameters :: Name
_UnionCommand_parameters = (String -> Name
Core.Name String
"parameters")
_UnionCommand_kind :: Name
_UnionCommand_kind = (String -> Name
Core.Name String
"kind")
_UnionCommand_withSource :: Name
_UnionCommand_withSource = (String -> Name
Core.Name String
"withSource")
_UnionCommand_isFuzzy :: Name
_UnionCommand_isFuzzy = (String -> Name
Core.Name String
"isFuzzy")
_UnionCommand_tables :: Name
_UnionCommand_tables = (String -> Name
Core.Name String
"tables")
data UnionKind =
UnionKindInner |
UnionKindOuter
deriving (UnionKind -> UnionKind -> Bool
(UnionKind -> UnionKind -> Bool)
-> (UnionKind -> UnionKind -> Bool) -> Eq UnionKind
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: UnionKind -> UnionKind -> Bool
== :: UnionKind -> UnionKind -> Bool
$c/= :: UnionKind -> UnionKind -> Bool
/= :: UnionKind -> UnionKind -> Bool
Eq, Eq UnionKind
Eq UnionKind =>
(UnionKind -> UnionKind -> Ordering)
-> (UnionKind -> UnionKind -> Bool)
-> (UnionKind -> UnionKind -> Bool)
-> (UnionKind -> UnionKind -> Bool)
-> (UnionKind -> UnionKind -> Bool)
-> (UnionKind -> UnionKind -> UnionKind)
-> (UnionKind -> UnionKind -> UnionKind)
-> Ord UnionKind
UnionKind -> UnionKind -> Bool
UnionKind -> UnionKind -> Ordering
UnionKind -> UnionKind -> UnionKind
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: UnionKind -> UnionKind -> Ordering
compare :: UnionKind -> UnionKind -> Ordering
$c< :: UnionKind -> UnionKind -> Bool
< :: UnionKind -> UnionKind -> Bool
$c<= :: UnionKind -> UnionKind -> Bool
<= :: UnionKind -> UnionKind -> Bool
$c> :: UnionKind -> UnionKind -> Bool
> :: UnionKind -> UnionKind -> Bool
$c>= :: UnionKind -> UnionKind -> Bool
>= :: UnionKind -> UnionKind -> Bool
$cmax :: UnionKind -> UnionKind -> UnionKind
max :: UnionKind -> UnionKind -> UnionKind
$cmin :: UnionKind -> UnionKind -> UnionKind
min :: UnionKind -> UnionKind -> UnionKind
Ord, ReadPrec [UnionKind]
ReadPrec UnionKind
Int -> ReadS UnionKind
ReadS [UnionKind]
(Int -> ReadS UnionKind)
-> ReadS [UnionKind]
-> ReadPrec UnionKind
-> ReadPrec [UnionKind]
-> Read UnionKind
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS UnionKind
readsPrec :: Int -> ReadS UnionKind
$creadList :: ReadS [UnionKind]
readList :: ReadS [UnionKind]
$creadPrec :: ReadPrec UnionKind
readPrec :: ReadPrec UnionKind
$creadListPrec :: ReadPrec [UnionKind]
readListPrec :: ReadPrec [UnionKind]
Read, Int -> UnionKind -> ShowS
[UnionKind] -> ShowS
UnionKind -> String
(Int -> UnionKind -> ShowS)
-> (UnionKind -> String)
-> ([UnionKind] -> ShowS)
-> Show UnionKind
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> UnionKind -> ShowS
showsPrec :: Int -> UnionKind -> ShowS
$cshow :: UnionKind -> String
show :: UnionKind -> String
$cshowList :: [UnionKind] -> ShowS
showList :: [UnionKind] -> ShowS
Show)
_UnionKind :: Name
_UnionKind = (String -> Name
Core.Name String
"hydra/langs/kusto/kql.UnionKind")
_UnionKind_inner :: Name
_UnionKind_inner = (String -> Name
Core.Name String
"inner")
_UnionKind_outer :: Name
_UnionKind_outer = (String -> Name
Core.Name String
"outer")