| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Hydra.Langs.Kusto.Kql
Description
A partial KQL (Kusto Query Language) model, based on examples from the documentation. Not normative.
Synopsis
- data BetweenExpression = BetweenExpression {}
- _BetweenExpression :: Name
- _BetweenExpression_not :: Name
- _BetweenExpression_expression :: Name
- _BetweenExpression_lowerBound :: Name
- _BetweenExpression_upperBound :: Name
- data BinaryExpression = BinaryExpression {}
- _BinaryExpression :: Name
- _BinaryExpression_left :: Name
- _BinaryExpression_operator :: Name
- _BinaryExpression_right :: Name
- data BinaryOperator
- = BinaryOperatorCaseInsensitiveEqual
- | BinaryOperatorContains
- | BinaryOperatorDivide
- | BinaryOperatorEndsWith
- | BinaryOperatorEqual
- | BinaryOperatorGreater
- | BinaryOperatorGreaterOrEqual
- | BinaryOperatorHas
- | BinaryOperatorHasPrefix
- | BinaryOperatorHasSuffix
- | BinaryOperatorLess
- | BinaryOperatorLessOrEqual
- | BinaryOperatorMatchesRegex
- | BinaryOperatorMinus
- | BinaryOperatorNotEqual
- | BinaryOperatorPlus
- | BinaryOperatorStartsWith
- | BinaryOperatorTimes
- _BinaryOperator :: Name
- _BinaryOperator_caseInsensitiveEqual :: Name
- _BinaryOperator_contains :: Name
- _BinaryOperator_divide :: Name
- _BinaryOperator_endsWith :: Name
- _BinaryOperator_equal :: Name
- _BinaryOperator_greater :: Name
- _BinaryOperator_greaterOrEqual :: Name
- _BinaryOperator_has :: Name
- _BinaryOperator_hasPrefix :: Name
- _BinaryOperator_hasSuffix :: Name
- _BinaryOperator_less :: Name
- _BinaryOperator_lessOrEqual :: Name
- _BinaryOperator_matchesRegex :: Name
- _BinaryOperator_minus :: Name
- _BinaryOperator_notEqual :: Name
- _BinaryOperator_plus :: Name
- _BinaryOperator_startsWith :: Name
- _BinaryOperator_times :: Name
- data BuiltInFunction
- = BuiltInFunctionAgo
- | BuiltInFunctionBin
- | BuiltInFunctionCount
- | BuiltInFunctionDcount
- | BuiltInFunctionEndofday
- | BuiltInFunctionExtract
- | BuiltInFunctionFormat_datetime
- | BuiltInFunctionMaterialize
- | BuiltInFunctionNow
- | BuiltInFunctionRange
- | BuiltInFunctionStartofday
- | BuiltInFunctionStrcat
- | BuiltInFunctionTodynamic
- _BuiltInFunction :: Name
- _BuiltInFunction_ago :: Name
- _BuiltInFunction_bin :: Name
- _BuiltInFunction_count :: Name
- _BuiltInFunction_dcount :: Name
- _BuiltInFunction_endofday :: Name
- _BuiltInFunction_extract :: Name
- _BuiltInFunction_format_datetime :: Name
- _BuiltInFunction_materialize :: Name
- _BuiltInFunction_now :: Name
- _BuiltInFunction_range :: Name
- _BuiltInFunction_startofday :: Name
- _BuiltInFunction_strcat :: Name
- _BuiltInFunction_todynamic :: Name
- data ColumnAlias = ColumnAlias {}
- _ColumnAlias :: Name
- _ColumnAlias_column :: Name
- _ColumnAlias_alias :: Name
- data ColumnAssignment = ColumnAssignment {}
- _ColumnAssignment :: Name
- _ColumnAssignment_column :: Name
- _ColumnAssignment_expression :: Name
- newtype ColumnName = ColumnName {}
- _ColumnName :: Name
- data Columns
- _Columns :: Name
- _Columns_all :: Name
- _Columns_single :: Name
- 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
- _Command :: Name
- _Command_count :: Name
- _Command_distinct :: Name
- _Command_extend :: Name
- _Command_join :: Name
- _Command_limit :: Name
- _Command_mvexpand :: Name
- _Command_orderBy :: Name
- _Command_parse :: Name
- _Command_print :: Name
- _Command_project :: Name
- _Command_projectAway :: Name
- _Command_projectRename :: Name
- _Command_render :: Name
- _Command_search :: Name
- _Command_sortBy :: Name
- _Command_summarize :: Name
- _Command_take :: Name
- _Command_top :: Name
- _Command_union :: Name
- _Command_where :: Name
- newtype Datetime = Datetime {
- unDatetime :: String
- _Datetime :: Name
- data Duration = Duration {}
- _Duration :: Name
- _Duration_value :: Name
- _Duration_unit :: Name
- data DurationUnit
- _DurationUnit :: Name
- _DurationUnit_second :: Name
- _DurationUnit_minute :: Name
- _DurationUnit_hour :: Name
- 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
- _Expression :: Name
- _Expression_and :: Name
- _Expression_any :: Name
- _Expression_between :: Name
- _Expression_binary :: Name
- _Expression_braces :: Name
- _Expression_column :: Name
- _Expression_dataset :: Name
- _Expression_index :: Name
- _Expression_list :: Name
- _Expression_literal :: Name
- _Expression_or :: Name
- _Expression_parentheses :: Name
- _Expression_property :: Name
- _Expression_unary :: Name
- data Function
- _Function :: Name
- _Function_builtIn :: Name
- _Function_custom :: Name
- data FunctionExpression = FunctionExpression {}
- _FunctionExpression :: Name
- _FunctionExpression_function :: Name
- _FunctionExpression_arguments :: Name
- newtype FunctionName = FunctionName {}
- _FunctionName :: Name
- data IndexExpression = IndexExpression {}
- _IndexExpression :: Name
- _IndexExpression_expression :: Name
- _IndexExpression_index :: Name
- data JoinCommand = JoinCommand {}
- _JoinCommand :: Name
- _JoinCommand_kind :: Name
- _JoinCommand_expression :: Name
- _JoinCommand_on :: Name
- data JoinKind
- _JoinKind :: Name
- _JoinKind_leftouter :: Name
- _JoinKind_leftsemi :: Name
- _JoinKind_leftanti :: Name
- _JoinKind_fullouter :: Name
- _JoinKind_inner :: Name
- _JoinKind_innerunique :: Name
- _JoinKind_rightouter :: Name
- _JoinKind_rightsemi :: Name
- _JoinKind_rightanti :: Name
- data KeyValuePair = KeyValuePair {}
- _KeyValuePair :: Name
- _KeyValuePair_key :: Name
- _KeyValuePair_value :: Name
- data LetBinding = LetBinding {}
- _LetBinding :: Name
- _LetBinding_name :: Name
- _LetBinding_expression :: Name
- data LetExpression = LetExpression {}
- _LetExpression :: Name
- _LetExpression_bindings :: Name
- _LetExpression_expression :: Name
- data Literal
- _Literal :: Name
- _Literal_duration :: Name
- _Literal_datetime :: Name
- _Literal_string :: Name
- _Literal_int :: Name
- _Literal_long :: Name
- _Literal_double :: Name
- _Literal_boolean :: Name
- data Order
- _Order :: Name
- _Order_ascending :: Name
- _Order_descending :: Name
- data Parameter = Parameter {}
- _Parameter :: Name
- _Parameter_key :: Name
- _Parameter_value :: Name
- data ParseCommand = ParseCommand {}
- _ParseCommand :: Name
- _ParseCommand_column :: Name
- _ParseCommand_pairs :: Name
- newtype PipelineExpression = PipelineExpression {}
- _PipelineExpression :: Name
- data PrintCommand = PrintCommand {}
- _PrintCommand :: Name
- _PrintCommand_column :: Name
- _PrintCommand_expression :: Name
- data Projection = Projection {}
- _Projection :: Name
- _Projection_expression :: Name
- _Projection_alias :: Name
- data PropertyExpression = PropertyExpression {}
- _PropertyExpression :: Name
- _PropertyExpression_expression :: Name
- _PropertyExpression_property :: Name
- newtype Query = Query {}
- _Query :: Name
- data SearchCommand = SearchCommand {}
- _SearchCommand :: Name
- _SearchCommand_datasets :: Name
- _SearchCommand_pattern :: Name
- data SummarizeCommand = SummarizeCommand {}
- _SummarizeCommand :: Name
- _SummarizeCommand_columns :: Name
- _SummarizeCommand_by :: Name
- newtype TableName = TableName {}
- _TableName :: Name
- data TopCommand = TopCommand {
- topCommandCount :: Int
- topCommandSort :: [SortBy]
- _TopCommand :: Name
- _TopCommand_count :: Name
- _TopCommand_sort :: Name
- data SortBy = SortBy {}
- _SortBy :: Name
- _SortBy_column :: Name
- _SortBy_order :: Name
- data TabularExpression
- _TabularExpression :: Name
- _TabularExpression_command :: Name
- _TabularExpression_pipeline :: Name
- _TabularExpression_let :: Name
- _TabularExpression_table :: Name
- data UnaryExpression = UnaryExpression {}
- _UnaryExpression :: Name
- _UnaryExpression_operator :: Name
- _UnaryExpression_expression :: Name
- data UnaryOperator = UnaryOperatorNot
- _UnaryOperator :: Name
- _UnaryOperator_not :: Name
- data UnionCommand = UnionCommand {}
- _UnionCommand :: Name
- _UnionCommand_parameters :: Name
- _UnionCommand_kind :: Name
- _UnionCommand_withSource :: Name
- _UnionCommand_isFuzzy :: Name
- _UnionCommand_tables :: Name
- data UnionKind
- _UnionKind :: Name
- _UnionKind_inner :: Name
- _UnionKind_outer :: Name
Documentation
data BetweenExpression Source #
Constructors
| BetweenExpression | |
Instances
data BinaryExpression Source #
Constructors
| BinaryExpression | |
Instances
data BinaryOperator Source #
Constructors
Instances
| Read BinaryOperator Source # | |
Defined in Hydra.Langs.Kusto.Kql Methods readsPrec :: Int -> ReadS BinaryOperator # readList :: ReadS [BinaryOperator] # | |
| Show BinaryOperator Source # | |
Defined in Hydra.Langs.Kusto.Kql Methods showsPrec :: Int -> BinaryOperator -> ShowS # show :: BinaryOperator -> String # showList :: [BinaryOperator] -> ShowS # | |
| Eq BinaryOperator Source # | |
Defined in Hydra.Langs.Kusto.Kql Methods (==) :: BinaryOperator -> BinaryOperator -> Bool # (/=) :: BinaryOperator -> BinaryOperator -> Bool # | |
| Ord BinaryOperator Source # | |
Defined in Hydra.Langs.Kusto.Kql Methods compare :: BinaryOperator -> BinaryOperator -> Ordering # (<) :: BinaryOperator -> BinaryOperator -> Bool # (<=) :: BinaryOperator -> BinaryOperator -> Bool # (>) :: BinaryOperator -> BinaryOperator -> Bool # (>=) :: BinaryOperator -> BinaryOperator -> Bool # max :: BinaryOperator -> BinaryOperator -> BinaryOperator # min :: BinaryOperator -> BinaryOperator -> BinaryOperator # | |
data BuiltInFunction Source #
Constructors
Instances
| Read BuiltInFunction Source # | |
Defined in Hydra.Langs.Kusto.Kql Methods readsPrec :: Int -> ReadS BuiltInFunction # readList :: ReadS [BuiltInFunction] # | |
| Show BuiltInFunction Source # | |
Defined in Hydra.Langs.Kusto.Kql Methods showsPrec :: Int -> BuiltInFunction -> ShowS # show :: BuiltInFunction -> String # showList :: [BuiltInFunction] -> ShowS # | |
| Eq BuiltInFunction Source # | |
Defined in Hydra.Langs.Kusto.Kql Methods (==) :: BuiltInFunction -> BuiltInFunction -> Bool # (/=) :: BuiltInFunction -> BuiltInFunction -> Bool # | |
| Ord BuiltInFunction Source # | |
Defined in Hydra.Langs.Kusto.Kql Methods compare :: BuiltInFunction -> BuiltInFunction -> Ordering # (<) :: BuiltInFunction -> BuiltInFunction -> Bool # (<=) :: BuiltInFunction -> BuiltInFunction -> Bool # (>) :: BuiltInFunction -> BuiltInFunction -> Bool # (>=) :: BuiltInFunction -> BuiltInFunction -> Bool # max :: BuiltInFunction -> BuiltInFunction -> BuiltInFunction # min :: BuiltInFunction -> BuiltInFunction -> BuiltInFunction # | |
data ColumnAlias Source #
Constructors
| ColumnAlias | |
Fields | |
Instances
| Read ColumnAlias Source # | |
Defined in Hydra.Langs.Kusto.Kql Methods readsPrec :: Int -> ReadS ColumnAlias # readList :: ReadS [ColumnAlias] # readPrec :: ReadPrec ColumnAlias # readListPrec :: ReadPrec [ColumnAlias] # | |
| Show ColumnAlias Source # | |
Defined in Hydra.Langs.Kusto.Kql Methods showsPrec :: Int -> ColumnAlias -> ShowS # show :: ColumnAlias -> String # showList :: [ColumnAlias] -> ShowS # | |
| Eq ColumnAlias Source # | |
Defined in Hydra.Langs.Kusto.Kql | |
| Ord ColumnAlias Source # | |
Defined in Hydra.Langs.Kusto.Kql Methods compare :: ColumnAlias -> ColumnAlias -> Ordering # (<) :: ColumnAlias -> ColumnAlias -> Bool # (<=) :: ColumnAlias -> ColumnAlias -> Bool # (>) :: ColumnAlias -> ColumnAlias -> Bool # (>=) :: ColumnAlias -> ColumnAlias -> Bool # max :: ColumnAlias -> ColumnAlias -> ColumnAlias # min :: ColumnAlias -> ColumnAlias -> ColumnAlias # | |
_ColumnAlias :: Name Source #
data ColumnAssignment Source #
Constructors
| ColumnAssignment | |
Instances
newtype ColumnName Source #
Constructors
| ColumnName | |
Fields | |
Instances
| Read ColumnName Source # | |
Defined in Hydra.Langs.Kusto.Kql Methods readsPrec :: Int -> ReadS ColumnName # readList :: ReadS [ColumnName] # readPrec :: ReadPrec ColumnName # readListPrec :: ReadPrec [ColumnName] # | |
| Show ColumnName Source # | |
Defined in Hydra.Langs.Kusto.Kql Methods showsPrec :: Int -> ColumnName -> ShowS # show :: ColumnName -> String # showList :: [ColumnName] -> ShowS # | |
| Eq ColumnName Source # | |
Defined in Hydra.Langs.Kusto.Kql | |
| Ord ColumnName Source # | |
Defined in Hydra.Langs.Kusto.Kql Methods compare :: ColumnName -> ColumnName -> Ordering # (<) :: ColumnName -> ColumnName -> Bool # (<=) :: ColumnName -> ColumnName -> Bool # (>) :: ColumnName -> ColumnName -> Bool # (>=) :: ColumnName -> ColumnName -> Bool # max :: ColumnName -> ColumnName -> ColumnName # min :: ColumnName -> ColumnName -> ColumnName # | |
_ColumnName :: Name Source #
Constructors
| ColumnsAll | |
| ColumnsSingle ColumnName |
_Columns_all :: Name Source #
Constructors
_Command_join :: Name Source #
_Command_take :: Name Source #
_Command_top :: Name Source #
Constructors
| Datetime | |
Fields
| |
Constructors
| Duration | |
Fields | |
data DurationUnit Source #
Constructors
| DurationUnitSecond | |
| DurationUnitMinute | |
| DurationUnitHour |
Instances
| Read DurationUnit Source # | |
Defined in Hydra.Langs.Kusto.Kql Methods readsPrec :: Int -> ReadS DurationUnit # readList :: ReadS [DurationUnit] # | |
| Show DurationUnit Source # | |
Defined in Hydra.Langs.Kusto.Kql Methods showsPrec :: Int -> DurationUnit -> ShowS # show :: DurationUnit -> String # showList :: [DurationUnit] -> ShowS # | |
| Eq DurationUnit Source # | |
Defined in Hydra.Langs.Kusto.Kql | |
| Ord DurationUnit Source # | |
Defined in Hydra.Langs.Kusto.Kql Methods compare :: DurationUnit -> DurationUnit -> Ordering # (<) :: DurationUnit -> DurationUnit -> Bool # (<=) :: DurationUnit -> DurationUnit -> Bool # (>) :: DurationUnit -> DurationUnit -> Bool # (>=) :: DurationUnit -> DurationUnit -> Bool # max :: DurationUnit -> DurationUnit -> DurationUnit # min :: DurationUnit -> DurationUnit -> DurationUnit # | |
_DurationUnit :: Name Source #
data Expression Source #
Constructors
Instances
| Read Expression Source # | |
Defined in Hydra.Langs.Kusto.Kql Methods readsPrec :: Int -> ReadS Expression # readList :: ReadS [Expression] # readPrec :: ReadPrec Expression # readListPrec :: ReadPrec [Expression] # | |
| Show Expression Source # | |
Defined in Hydra.Langs.Kusto.Kql Methods showsPrec :: Int -> Expression -> ShowS # show :: Expression -> String # showList :: [Expression] -> ShowS # | |
| Eq Expression Source # | |
Defined in Hydra.Langs.Kusto.Kql | |
| Ord Expression Source # | |
Defined in Hydra.Langs.Kusto.Kql Methods compare :: Expression -> Expression -> Ordering # (<) :: Expression -> Expression -> Bool # (<=) :: Expression -> Expression -> Bool # (>) :: Expression -> Expression -> Bool # (>=) :: Expression -> Expression -> Bool # max :: Expression -> Expression -> Expression # min :: Expression -> Expression -> Expression # | |
_Expression :: Name Source #
Constructors
| FunctionBuiltIn BuiltInFunction | |
| FunctionCustom FunctionName |
data FunctionExpression Source #
Constructors
| FunctionExpression | |
Instances
newtype FunctionName Source #
Constructors
| FunctionName | |
Fields | |
Instances
| Read FunctionName Source # | |
Defined in Hydra.Langs.Kusto.Kql Methods readsPrec :: Int -> ReadS FunctionName # readList :: ReadS [FunctionName] # | |
| Show FunctionName Source # | |
Defined in Hydra.Langs.Kusto.Kql Methods showsPrec :: Int -> FunctionName -> ShowS # show :: FunctionName -> String # showList :: [FunctionName] -> ShowS # | |
| Eq FunctionName Source # | |
Defined in Hydra.Langs.Kusto.Kql | |
| Ord FunctionName Source # | |
Defined in Hydra.Langs.Kusto.Kql Methods compare :: FunctionName -> FunctionName -> Ordering # (<) :: FunctionName -> FunctionName -> Bool # (<=) :: FunctionName -> FunctionName -> Bool # (>) :: FunctionName -> FunctionName -> Bool # (>=) :: FunctionName -> FunctionName -> Bool # max :: FunctionName -> FunctionName -> FunctionName # min :: FunctionName -> FunctionName -> FunctionName # | |
_FunctionName :: Name Source #
data IndexExpression Source #
Constructors
| IndexExpression | |
Instances
| Read IndexExpression Source # | |
Defined in Hydra.Langs.Kusto.Kql Methods readsPrec :: Int -> ReadS IndexExpression # readList :: ReadS [IndexExpression] # | |
| Show IndexExpression Source # | |
Defined in Hydra.Langs.Kusto.Kql Methods showsPrec :: Int -> IndexExpression -> ShowS # show :: IndexExpression -> String # showList :: [IndexExpression] -> ShowS # | |
| Eq IndexExpression Source # | |
Defined in Hydra.Langs.Kusto.Kql Methods (==) :: IndexExpression -> IndexExpression -> Bool # (/=) :: IndexExpression -> IndexExpression -> Bool # | |
| Ord IndexExpression Source # | |
Defined in Hydra.Langs.Kusto.Kql Methods compare :: IndexExpression -> IndexExpression -> Ordering # (<) :: IndexExpression -> IndexExpression -> Bool # (<=) :: IndexExpression -> IndexExpression -> Bool # (>) :: IndexExpression -> IndexExpression -> Bool # (>=) :: IndexExpression -> IndexExpression -> Bool # max :: IndexExpression -> IndexExpression -> IndexExpression # min :: IndexExpression -> IndexExpression -> IndexExpression # | |
data JoinCommand Source #
Constructors
| JoinCommand | |
Fields | |
Instances
| Read JoinCommand Source # | |
Defined in Hydra.Langs.Kusto.Kql Methods readsPrec :: Int -> ReadS JoinCommand # readList :: ReadS [JoinCommand] # readPrec :: ReadPrec JoinCommand # readListPrec :: ReadPrec [JoinCommand] # | |
| Show JoinCommand Source # | |
Defined in Hydra.Langs.Kusto.Kql Methods showsPrec :: Int -> JoinCommand -> ShowS # show :: JoinCommand -> String # showList :: [JoinCommand] -> ShowS # | |
| Eq JoinCommand Source # | |
Defined in Hydra.Langs.Kusto.Kql | |
| Ord JoinCommand Source # | |
Defined in Hydra.Langs.Kusto.Kql Methods compare :: JoinCommand -> JoinCommand -> Ordering # (<) :: JoinCommand -> JoinCommand -> Bool # (<=) :: JoinCommand -> JoinCommand -> Bool # (>) :: JoinCommand -> JoinCommand -> Bool # (>=) :: JoinCommand -> JoinCommand -> Bool # max :: JoinCommand -> JoinCommand -> JoinCommand # min :: JoinCommand -> JoinCommand -> JoinCommand # | |
_JoinCommand :: Name Source #
Constructors
| JoinKindLeftouter | |
| JoinKindLeftsemi | |
| JoinKindLeftanti | |
| JoinKindFullouter | |
| JoinKindInner | |
| JoinKindInnerunique | |
| JoinKindRightouter | |
| JoinKindRightsemi | |
| JoinKindRightanti |
data KeyValuePair Source #
Constructors
| KeyValuePair | |
Fields | |
Instances
| Read KeyValuePair Source # | |
Defined in Hydra.Langs.Kusto.Kql Methods readsPrec :: Int -> ReadS KeyValuePair # readList :: ReadS [KeyValuePair] # | |
| Show KeyValuePair Source # | |
Defined in Hydra.Langs.Kusto.Kql Methods showsPrec :: Int -> KeyValuePair -> ShowS # show :: KeyValuePair -> String # showList :: [KeyValuePair] -> ShowS # | |
| Eq KeyValuePair Source # | |
Defined in Hydra.Langs.Kusto.Kql | |
| Ord KeyValuePair Source # | |
Defined in Hydra.Langs.Kusto.Kql Methods compare :: KeyValuePair -> KeyValuePair -> Ordering # (<) :: KeyValuePair -> KeyValuePair -> Bool # (<=) :: KeyValuePair -> KeyValuePair -> Bool # (>) :: KeyValuePair -> KeyValuePair -> Bool # (>=) :: KeyValuePair -> KeyValuePair -> Bool # max :: KeyValuePair -> KeyValuePair -> KeyValuePair # min :: KeyValuePair -> KeyValuePair -> KeyValuePair # | |
_KeyValuePair :: Name Source #
data LetBinding Source #
Constructors
| LetBinding | |
Fields | |
Instances
| Read LetBinding Source # | |
Defined in Hydra.Langs.Kusto.Kql Methods readsPrec :: Int -> ReadS LetBinding # readList :: ReadS [LetBinding] # readPrec :: ReadPrec LetBinding # readListPrec :: ReadPrec [LetBinding] # | |
| Show LetBinding Source # | |
Defined in Hydra.Langs.Kusto.Kql Methods showsPrec :: Int -> LetBinding -> ShowS # show :: LetBinding -> String # showList :: [LetBinding] -> ShowS # | |
| Eq LetBinding Source # | |
Defined in Hydra.Langs.Kusto.Kql | |
| Ord LetBinding Source # | |
Defined in Hydra.Langs.Kusto.Kql Methods compare :: LetBinding -> LetBinding -> Ordering # (<) :: LetBinding -> LetBinding -> Bool # (<=) :: LetBinding -> LetBinding -> Bool # (>) :: LetBinding -> LetBinding -> Bool # (>=) :: LetBinding -> LetBinding -> Bool # max :: LetBinding -> LetBinding -> LetBinding # min :: LetBinding -> LetBinding -> LetBinding # | |
_LetBinding :: Name Source #
data LetExpression Source #
Constructors
| LetExpression | |
Instances
| Read LetExpression Source # | |
Defined in Hydra.Langs.Kusto.Kql Methods readsPrec :: Int -> ReadS LetExpression # readList :: ReadS [LetExpression] # | |
| Show LetExpression Source # | |
Defined in Hydra.Langs.Kusto.Kql Methods showsPrec :: Int -> LetExpression -> ShowS # show :: LetExpression -> String # showList :: [LetExpression] -> ShowS # | |
| Eq LetExpression Source # | |
Defined in Hydra.Langs.Kusto.Kql Methods (==) :: LetExpression -> LetExpression -> Bool # (/=) :: LetExpression -> LetExpression -> Bool # | |
| Ord LetExpression Source # | |
Defined in Hydra.Langs.Kusto.Kql Methods compare :: LetExpression -> LetExpression -> Ordering # (<) :: LetExpression -> LetExpression -> Bool # (<=) :: LetExpression -> LetExpression -> Bool # (>) :: LetExpression -> LetExpression -> Bool # (>=) :: LetExpression -> LetExpression -> Bool # max :: LetExpression -> LetExpression -> LetExpression # min :: LetExpression -> LetExpression -> LetExpression # | |
Constructors
| LiteralDuration Duration | |
| LiteralDatetime Datetime | |
| LiteralString String | |
| LiteralInt Int | |
| LiteralLong Int64 | |
| LiteralDouble Double | |
| LiteralBoolean Bool |
_Literal_int :: Name Source #
_Literal_long :: Name Source #
Constructors
| OrderAscending | |
| OrderDescending |
Constructors
| Parameter | |
Fields | |
Instances
| Read Parameter Source # | |
| Show Parameter Source # | |
| Eq Parameter Source # | |
| Ord Parameter Source # | |
_Parameter :: Name Source #
data ParseCommand Source #
Constructors
| ParseCommand | |
Fields | |
Instances
| Read ParseCommand Source # | |
Defined in Hydra.Langs.Kusto.Kql Methods readsPrec :: Int -> ReadS ParseCommand # readList :: ReadS [ParseCommand] # | |
| Show ParseCommand Source # | |
Defined in Hydra.Langs.Kusto.Kql Methods showsPrec :: Int -> ParseCommand -> ShowS # show :: ParseCommand -> String # showList :: [ParseCommand] -> ShowS # | |
| Eq ParseCommand Source # | |
Defined in Hydra.Langs.Kusto.Kql | |
| Ord ParseCommand Source # | |
Defined in Hydra.Langs.Kusto.Kql Methods compare :: ParseCommand -> ParseCommand -> Ordering # (<) :: ParseCommand -> ParseCommand -> Bool # (<=) :: ParseCommand -> ParseCommand -> Bool # (>) :: ParseCommand -> ParseCommand -> Bool # (>=) :: ParseCommand -> ParseCommand -> Bool # max :: ParseCommand -> ParseCommand -> ParseCommand # min :: ParseCommand -> ParseCommand -> ParseCommand # | |
_ParseCommand :: Name Source #
newtype PipelineExpression Source #
Constructors
| PipelineExpression | |
Fields | |
Instances
data PrintCommand Source #
Constructors
| PrintCommand | |
Instances
| Read PrintCommand Source # | |
Defined in Hydra.Langs.Kusto.Kql Methods readsPrec :: Int -> ReadS PrintCommand # readList :: ReadS [PrintCommand] # | |
| Show PrintCommand Source # | |
Defined in Hydra.Langs.Kusto.Kql Methods showsPrec :: Int -> PrintCommand -> ShowS # show :: PrintCommand -> String # showList :: [PrintCommand] -> ShowS # | |
| Eq PrintCommand Source # | |
Defined in Hydra.Langs.Kusto.Kql | |
| Ord PrintCommand Source # | |
Defined in Hydra.Langs.Kusto.Kql Methods compare :: PrintCommand -> PrintCommand -> Ordering # (<) :: PrintCommand -> PrintCommand -> Bool # (<=) :: PrintCommand -> PrintCommand -> Bool # (>) :: PrintCommand -> PrintCommand -> Bool # (>=) :: PrintCommand -> PrintCommand -> Bool # max :: PrintCommand -> PrintCommand -> PrintCommand # min :: PrintCommand -> PrintCommand -> PrintCommand # | |
_PrintCommand :: Name Source #
data Projection Source #
Constructors
| Projection | |
Fields | |
Instances
| Read Projection Source # | |
Defined in Hydra.Langs.Kusto.Kql Methods readsPrec :: Int -> ReadS Projection # readList :: ReadS [Projection] # readPrec :: ReadPrec Projection # readListPrec :: ReadPrec [Projection] # | |
| Show Projection Source # | |
Defined in Hydra.Langs.Kusto.Kql Methods showsPrec :: Int -> Projection -> ShowS # show :: Projection -> String # showList :: [Projection] -> ShowS # | |
| Eq Projection Source # | |
Defined in Hydra.Langs.Kusto.Kql | |
| Ord Projection Source # | |
Defined in Hydra.Langs.Kusto.Kql Methods compare :: Projection -> Projection -> Ordering # (<) :: Projection -> Projection -> Bool # (<=) :: Projection -> Projection -> Bool # (>) :: Projection -> Projection -> Bool # (>=) :: Projection -> Projection -> Bool # max :: Projection -> Projection -> Projection # min :: Projection -> Projection -> Projection # | |
_Projection :: Name Source #
data PropertyExpression Source #
Constructors
| PropertyExpression | |
Instances
Constructors
| Query | |
Fields | |
data SearchCommand Source #
Search across all datasets and columns or, if provided, specific datasets and/or columns
Constructors
| SearchCommand | |
Fields | |
Instances
| Read SearchCommand Source # | |
Defined in Hydra.Langs.Kusto.Kql Methods readsPrec :: Int -> ReadS SearchCommand # readList :: ReadS [SearchCommand] # | |
| Show SearchCommand Source # | |
Defined in Hydra.Langs.Kusto.Kql Methods showsPrec :: Int -> SearchCommand -> ShowS # show :: SearchCommand -> String # showList :: [SearchCommand] -> ShowS # | |
| Eq SearchCommand Source # | |
Defined in Hydra.Langs.Kusto.Kql Methods (==) :: SearchCommand -> SearchCommand -> Bool # (/=) :: SearchCommand -> SearchCommand -> Bool # | |
| Ord SearchCommand Source # | |
Defined in Hydra.Langs.Kusto.Kql Methods compare :: SearchCommand -> SearchCommand -> Ordering # (<) :: SearchCommand -> SearchCommand -> Bool # (<=) :: SearchCommand -> SearchCommand -> Bool # (>) :: SearchCommand -> SearchCommand -> Bool # (>=) :: SearchCommand -> SearchCommand -> Bool # max :: SearchCommand -> SearchCommand -> SearchCommand # min :: SearchCommand -> SearchCommand -> SearchCommand # | |
data SummarizeCommand Source #
Constructors
| SummarizeCommand | |
Fields | |
Instances
Constructors
| TableName | |
Fields | |
Instances
| Read TableName Source # | |
| Show TableName Source # | |
| Eq TableName Source # | |
| Ord TableName Source # | |
_TableName :: Name Source #
data TopCommand Source #
Constructors
| TopCommand | |
Fields
| |
Instances
| Read TopCommand Source # | |
Defined in Hydra.Langs.Kusto.Kql Methods readsPrec :: Int -> ReadS TopCommand # readList :: ReadS [TopCommand] # readPrec :: ReadPrec TopCommand # readListPrec :: ReadPrec [TopCommand] # | |
| Show TopCommand Source # | |
Defined in Hydra.Langs.Kusto.Kql Methods showsPrec :: Int -> TopCommand -> ShowS # show :: TopCommand -> String # showList :: [TopCommand] -> ShowS # | |
| Eq TopCommand Source # | |
Defined in Hydra.Langs.Kusto.Kql | |
| Ord TopCommand Source # | |
Defined in Hydra.Langs.Kusto.Kql Methods compare :: TopCommand -> TopCommand -> Ordering # (<) :: TopCommand -> TopCommand -> Bool # (<=) :: TopCommand -> TopCommand -> Bool # (>) :: TopCommand -> TopCommand -> Bool # (>=) :: TopCommand -> TopCommand -> Bool # max :: TopCommand -> TopCommand -> TopCommand # min :: TopCommand -> TopCommand -> TopCommand # | |
_TopCommand :: Name Source #
Constructors
| SortBy | |
Fields | |
_SortBy_order :: Name Source #
data TabularExpression Source #
Constructors
| TabularExpressionCommand Command | |
| TabularExpressionPipeline PipelineExpression | |
| TabularExpressionLet LetExpression | |
| TabularExpressionTable TableName |
Instances
data UnaryExpression Source #
Constructors
| UnaryExpression | |
Instances
| Read UnaryExpression Source # | |
Defined in Hydra.Langs.Kusto.Kql Methods readsPrec :: Int -> ReadS UnaryExpression # readList :: ReadS [UnaryExpression] # | |
| Show UnaryExpression Source # | |
Defined in Hydra.Langs.Kusto.Kql Methods showsPrec :: Int -> UnaryExpression -> ShowS # show :: UnaryExpression -> String # showList :: [UnaryExpression] -> ShowS # | |
| Eq UnaryExpression Source # | |
Defined in Hydra.Langs.Kusto.Kql Methods (==) :: UnaryExpression -> UnaryExpression -> Bool # (/=) :: UnaryExpression -> UnaryExpression -> Bool # | |
| Ord UnaryExpression Source # | |
Defined in Hydra.Langs.Kusto.Kql Methods compare :: UnaryExpression -> UnaryExpression -> Ordering # (<) :: UnaryExpression -> UnaryExpression -> Bool # (<=) :: UnaryExpression -> UnaryExpression -> Bool # (>) :: UnaryExpression -> UnaryExpression -> Bool # (>=) :: UnaryExpression -> UnaryExpression -> Bool # max :: UnaryExpression -> UnaryExpression -> UnaryExpression # min :: UnaryExpression -> UnaryExpression -> UnaryExpression # | |
data UnaryOperator Source #
Constructors
| UnaryOperatorNot |
Instances
| Read UnaryOperator Source # | |
Defined in Hydra.Langs.Kusto.Kql Methods readsPrec :: Int -> ReadS UnaryOperator # readList :: ReadS [UnaryOperator] # | |
| Show UnaryOperator Source # | |
Defined in Hydra.Langs.Kusto.Kql Methods showsPrec :: Int -> UnaryOperator -> ShowS # show :: UnaryOperator -> String # showList :: [UnaryOperator] -> ShowS # | |
| Eq UnaryOperator Source # | |
Defined in Hydra.Langs.Kusto.Kql Methods (==) :: UnaryOperator -> UnaryOperator -> Bool # (/=) :: UnaryOperator -> UnaryOperator -> Bool # | |
| Ord UnaryOperator Source # | |
Defined in Hydra.Langs.Kusto.Kql Methods compare :: UnaryOperator -> UnaryOperator -> Ordering # (<) :: UnaryOperator -> UnaryOperator -> Bool # (<=) :: UnaryOperator -> UnaryOperator -> Bool # (>) :: UnaryOperator -> UnaryOperator -> Bool # (>=) :: UnaryOperator -> UnaryOperator -> Bool # max :: UnaryOperator -> UnaryOperator -> UnaryOperator # min :: UnaryOperator -> UnaryOperator -> UnaryOperator # | |
data UnionCommand Source #
Constructors
| UnionCommand | |
Instances
| Read UnionCommand Source # | |
Defined in Hydra.Langs.Kusto.Kql Methods readsPrec :: Int -> ReadS UnionCommand # readList :: ReadS [UnionCommand] # | |
| Show UnionCommand Source # | |
Defined in Hydra.Langs.Kusto.Kql Methods showsPrec :: Int -> UnionCommand -> ShowS # show :: UnionCommand -> String # showList :: [UnionCommand] -> ShowS # | |
| Eq UnionCommand Source # | |
Defined in Hydra.Langs.Kusto.Kql | |
| Ord UnionCommand Source # | |
Defined in Hydra.Langs.Kusto.Kql Methods compare :: UnionCommand -> UnionCommand -> Ordering # (<) :: UnionCommand -> UnionCommand -> Bool # (<=) :: UnionCommand -> UnionCommand -> Bool # (>) :: UnionCommand -> UnionCommand -> Bool # (>=) :: UnionCommand -> UnionCommand -> Bool # max :: UnionCommand -> UnionCommand -> UnionCommand # min :: UnionCommand -> UnionCommand -> UnionCommand # | |
_UnionCommand :: Name Source #
Constructors
| UnionKindInner | |
| UnionKindOuter |
Instances
| Read UnionKind Source # | |
| Show UnionKind Source # | |
| Eq UnionKind Source # | |
| Ord UnionKind Source # | |
_UnionKind :: Name Source #