postgresql-syntax-0.4.1.1: PostgreSQL AST parsing and rendering
Safe HaskellSafe-Inferred
LanguageHaskell2010

PostgresqlSyntax.Ast

Description

Names for nodes mostly resemble the according definitions in the gram.y original Postgres parser file, except for the cases where we can optimize on that.

For reasoning see the docs of the parsing module of this project.

Synopsis

Statement

data PreparableStmt Source #

References

PreparableStmt:
  |  SelectStmt
  |  InsertStmt
  |  UpdateStmt
  |  DeleteStmt
  |  CallStmt

Instances

Instances details
Generic PreparableStmt Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep PreparableStmt :: Type -> Type #

Show PreparableStmt Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq PreparableStmt Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord PreparableStmt Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep PreparableStmt Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep PreparableStmt = D1 ('MetaData "PreparableStmt" "PostgresqlSyntax.Ast" "postgresql-syntax-0.4.1.1-1agduNP8gtd9DXmzqkx25k" 'False) ((C1 ('MetaCons "SelectPreparableStmt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SelectStmt)) :+: C1 ('MetaCons "InsertPreparableStmt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 InsertStmt))) :+: (C1 ('MetaCons "UpdatePreparableStmt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UpdateStmt)) :+: (C1 ('MetaCons "DeletePreparableStmt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DeleteStmt)) :+: C1 ('MetaCons "CallPreparableStmt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CallStmt)))))

Call

newtype CallStmt Source #

Instances

Instances details
Generic CallStmt Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep CallStmt :: Type -> Type #

Methods

from :: CallStmt -> Rep CallStmt x #

to :: Rep CallStmt x -> CallStmt #

Show CallStmt Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq CallStmt Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord CallStmt Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep CallStmt Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep CallStmt = D1 ('MetaData "CallStmt" "PostgresqlSyntax.Ast" "postgresql-syntax-0.4.1.1-1agduNP8gtd9DXmzqkx25k" 'True) (C1 ('MetaCons "CallStmt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FuncApplication)))

Insert

data InsertStmt Source #

References

InsertStmt:
  | opt_with_clause INSERT INTO insert_target insert_rest
      opt_on_conflict returning_clause

Instances

Instances details
Generic InsertStmt Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep InsertStmt :: Type -> Type #

Show InsertStmt Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq InsertStmt Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord InsertStmt Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep InsertStmt Source # 
Instance details

Defined in PostgresqlSyntax.Ast

data InsertTarget Source #

References

insert_target:
  | qualified_name
  | qualified_name AS ColId

Instances

Instances details
Generic InsertTarget Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep InsertTarget :: Type -> Type #

Show InsertTarget Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq InsertTarget Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord InsertTarget Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep InsertTarget Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep InsertTarget = D1 ('MetaData "InsertTarget" "PostgresqlSyntax.Ast" "postgresql-syntax-0.4.1.1-1agduNP8gtd9DXmzqkx25k" 'False) (C1 ('MetaCons "InsertTarget" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 QualifiedName) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ColId))))

data InsertRest Source #

References

insert_rest:
  | SelectStmt
  | OVERRIDING override_kind VALUE_P SelectStmt
  | '(' insert_column_list ')' SelectStmt
  | '(' insert_column_list ')' OVERRIDING override_kind VALUE_P SelectStmt
  | DEFAULT VALUES

Instances

Instances details
Generic InsertRest Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep InsertRest :: Type -> Type #

Show InsertRest Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq InsertRest Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord InsertRest Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep InsertRest Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep InsertRest = D1 ('MetaData "InsertRest" "PostgresqlSyntax.Ast" "postgresql-syntax-0.4.1.1-1agduNP8gtd9DXmzqkx25k" 'False) (C1 ('MetaCons "SelectInsertRest" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe InsertColumnList)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe OverrideKind)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SelectStmt))) :+: C1 ('MetaCons "DefaultValuesInsertRest" 'PrefixI 'False) (U1 :: Type -> Type))

data OverrideKind Source #

References

override_kind:
  | USER
  | SYSTEM_P

Instances

Instances details
Bounded OverrideKind Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Enum OverrideKind Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic OverrideKind Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep OverrideKind :: Type -> Type #

Show OverrideKind Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq OverrideKind Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord OverrideKind Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep OverrideKind Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep OverrideKind = D1 ('MetaData "OverrideKind" "PostgresqlSyntax.Ast" "postgresql-syntax-0.4.1.1-1agduNP8gtd9DXmzqkx25k" 'False) (C1 ('MetaCons "UserOverrideKind" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SystemOverrideKind" 'PrefixI 'False) (U1 :: Type -> Type))

type InsertColumnList = NonEmpty InsertColumnItem Source #

References

insert_column_list:
  | insert_column_item
  | insert_column_list ',' insert_column_item

data InsertColumnItem Source #

References

insert_column_item:
  | ColId opt_indirection

Instances

Instances details
Generic InsertColumnItem Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep InsertColumnItem :: Type -> Type #

Show InsertColumnItem Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq InsertColumnItem Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord InsertColumnItem Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep InsertColumnItem Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep InsertColumnItem = D1 ('MetaData "InsertColumnItem" "PostgresqlSyntax.Ast" "postgresql-syntax-0.4.1.1-1agduNP8gtd9DXmzqkx25k" 'False) (C1 ('MetaCons "InsertColumnItem" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ColId) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Indirection))))

data OnConflict Source #

References

opt_on_conflict:
  | ON CONFLICT opt_conf_expr DO UPDATE SET set_clause_list where_clause
  | ON CONFLICT opt_conf_expr DO NOTHING
  | EMPTY

Instances

Instances details
Generic OnConflict Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep OnConflict :: Type -> Type #

Show OnConflict Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq OnConflict Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord OnConflict Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep OnConflict Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep OnConflict = D1 ('MetaData "OnConflict" "PostgresqlSyntax.Ast" "postgresql-syntax-0.4.1.1-1agduNP8gtd9DXmzqkx25k" 'False) (C1 ('MetaCons "OnConflict" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ConfExpr)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 OnConflictDo)))

data OnConflictDo Source #

References

opt_on_conflict:
  | ON CONFLICT opt_conf_expr DO UPDATE SET set_clause_list where_clause
  | ON CONFLICT opt_conf_expr DO NOTHING
  | EMPTY

Instances

Instances details
Generic OnConflictDo Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep OnConflictDo :: Type -> Type #

Show OnConflictDo Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq OnConflictDo Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord OnConflictDo Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep OnConflictDo Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep OnConflictDo = D1 ('MetaData "OnConflictDo" "PostgresqlSyntax.Ast" "postgresql-syntax-0.4.1.1-1agduNP8gtd9DXmzqkx25k" 'False) (C1 ('MetaCons "UpdateOnConflictDo" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SetClauseList) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe WhereClause))) :+: C1 ('MetaCons "NothingOnConflictDo" 'PrefixI 'False) (U1 :: Type -> Type))

data ConfExpr Source #

References

opt_conf_expr:
  | '(' index_params ')' where_clause
  | ON CONSTRAINT name
  | EMPTY

Instances

Instances details
Generic ConfExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep ConfExpr :: Type -> Type #

Methods

from :: ConfExpr -> Rep ConfExpr x #

to :: Rep ConfExpr x -> ConfExpr #

Show ConfExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq ConfExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord ConfExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep ConfExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep ConfExpr = D1 ('MetaData "ConfExpr" "PostgresqlSyntax.Ast" "postgresql-syntax-0.4.1.1-1agduNP8gtd9DXmzqkx25k" 'False) (C1 ('MetaCons "WhereConfExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 IndexParams) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe WhereClause))) :+: C1 ('MetaCons "ConstraintConfExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name)))

type ReturningClause = TargetList Source #

References

returning_clause:
  | RETURNING target_list
  | EMPTY

Update

data UpdateStmt Source #

References

UpdateStmt:
  | opt_with_clause UPDATE relation_expr_opt_alias
      SET set_clause_list
      from_clause
      where_or_current_clause
      returning_clause

Instances

Instances details
Generic UpdateStmt Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep UpdateStmt :: Type -> Type #

Show UpdateStmt Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq UpdateStmt Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord UpdateStmt Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep UpdateStmt Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type SetClauseList = NonEmpty SetClause Source #

References

set_clause_list:
  | set_clause
  | set_clause_list ',' set_clause

data SetClause Source #

References

set_clause:
  | set_target '=' a_expr
  | '(' set_target_list ')' '=' a_expr

Instances

Instances details
Generic SetClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep SetClause :: Type -> Type #

Show SetClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq SetClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord SetClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep SetClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

data SetTarget Source #

References

set_target:
  | ColId opt_indirection

Instances

Instances details
Generic SetTarget Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep SetTarget :: Type -> Type #

Show SetTarget Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq SetTarget Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord SetTarget Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep SetTarget Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep SetTarget = D1 ('MetaData "SetTarget" "PostgresqlSyntax.Ast" "postgresql-syntax-0.4.1.1-1agduNP8gtd9DXmzqkx25k" 'False) (C1 ('MetaCons "SetTarget" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ColId) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Indirection))))

type SetTargetList = NonEmpty SetTarget Source #

References

set_target_list:
  | set_target
  | set_target_list ',' set_target

Delete

data DeleteStmt Source #

References

DeleteStmt:
  | opt_with_clause DELETE_P FROM relation_expr_opt_alias
      using_clause where_or_current_clause returning_clause

Instances

Instances details
Generic DeleteStmt Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep DeleteStmt :: Type -> Type #

Show DeleteStmt Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq DeleteStmt Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord DeleteStmt Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep DeleteStmt Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type UsingClause = FromList Source #

References

using_clause:
  | USING from_list
  | EMPTY

Select

type SelectStmt = Either SelectNoParens SelectWithParens Source #

References

SelectStmt:
  |  select_no_parens
  |  select_with_parens

data SelectWithParens Source #

References

select_with_parens:
  |  '(' select_no_parens ')'
  |  '(' select_with_parens ')'

Instances

Instances details
Generic SelectWithParens Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep SelectWithParens :: Type -> Type #

Show SelectWithParens Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq SelectWithParens Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord SelectWithParens Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep SelectWithParens Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep SelectWithParens = D1 ('MetaData "SelectWithParens" "PostgresqlSyntax.Ast" "postgresql-syntax-0.4.1.1-1agduNP8gtd9DXmzqkx25k" 'False) (C1 ('MetaCons "NoParensSelectWithParens" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SelectNoParens)) :+: C1 ('MetaCons "WithParensSelectWithParens" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SelectWithParens)))

data SelectNoParens Source #

Covers the following cases:

select_no_parens:
  |  simple_select
  |  select_clause sort_clause
  |  select_clause opt_sort_clause for_locking_clause opt_select_limit
  |  select_clause opt_sort_clause select_limit opt_for_locking_clause
  |  with_clause select_clause
  |  with_clause select_clause sort_clause
  |  with_clause select_clause opt_sort_clause for_locking_clause opt_select_limit
  |  with_clause select_clause opt_sort_clause select_limit opt_for_locking_clause

Instances

Instances details
Generic SelectNoParens Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep SelectNoParens :: Type -> Type #

Show SelectNoParens Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq SelectNoParens Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord SelectNoParens Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep SelectNoParens Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type SelectClause = Either SimpleSelect SelectWithParens Source #

select_clause:
  |  simple_select
  |  select_with_parens

data SimpleSelect Source #

References

simple_select:
  |  SELECT opt_all_clause opt_target_list
      into_clause from_clause where_clause
      group_clause having_clause window_clause
  |  SELECT distinct_clause target_list
      into_clause from_clause where_clause
      group_clause having_clause window_clause
  |  values_clause
  |  TABLE relation_expr
  |  select_clause UNION all_or_distinct select_clause
  |  select_clause INTERSECT all_or_distinct select_clause
  |  select_clause EXCEPT all_or_distinct select_clause

Instances

Instances details
Generic SimpleSelect Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep SimpleSelect :: Type -> Type #

Show SimpleSelect Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq SimpleSelect Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord SimpleSelect Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep SimpleSelect Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep SimpleSelect = D1 ('MetaData "SimpleSelect" "PostgresqlSyntax.Ast" "postgresql-syntax-0.4.1.1-1agduNP8gtd9DXmzqkx25k" 'False) ((C1 ('MetaCons "NormalSimpleSelect" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Targeting)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe IntoClause)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FromClause)))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe WhereClause)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe GroupClause))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe HavingClause)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe WindowClause))))) :+: C1 ('MetaCons "ValuesSimpleSelect" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ValuesClause))) :+: (C1 ('MetaCons "TableSimpleSelect" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RelationExpr)) :+: C1 ('MetaCons "BinSimpleSelect" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SelectBinOp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SelectClause)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SelectClause)))))

data Targeting Source #

Covers these parts of spec:

References

simple_select:
  |  SELECT opt_all_clause opt_target_list
      into_clause from_clause where_clause
      group_clause having_clause window_clause
  |  SELECT distinct_clause target_list
      into_clause from_clause where_clause
      group_clause having_clause window_clause

distinct_clause:
  |  DISTINCT
  |  DISTINCT ON '(' expr_list ')'

Instances

Instances details
Generic Targeting Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep Targeting :: Type -> Type #

Show Targeting Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq Targeting Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord Targeting Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep Targeting Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type TargetList = NonEmpty TargetEl Source #

References

target_list:
  | target_el
  | target_list ',' target_el

data TargetEl Source #

References

target_el:
  |  a_expr AS ColLabel
  |  a_expr IDENT
  |  a_expr
  |  *

Instances

Instances details
Generic TargetEl Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep TargetEl :: Type -> Type #

Methods

from :: TargetEl -> Rep TargetEl x #

to :: Rep TargetEl x -> TargetEl #

Show TargetEl Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq TargetEl Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord TargetEl Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep TargetEl Source # 
Instance details

Defined in PostgresqlSyntax.Ast

data SelectBinOp Source #

References

  |  select_clause UNION all_or_distinct select_clause
  |  select_clause INTERSECT all_or_distinct select_clause
  |  select_clause EXCEPT all_or_distinct select_clause

Instances

Instances details
Generic SelectBinOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep SelectBinOp :: Type -> Type #

Show SelectBinOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq SelectBinOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord SelectBinOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep SelectBinOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep SelectBinOp = D1 ('MetaData "SelectBinOp" "PostgresqlSyntax.Ast" "postgresql-syntax-0.4.1.1-1agduNP8gtd9DXmzqkx25k" 'False) (C1 ('MetaCons "UnionSelectBinOp" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "IntersectSelectBinOp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ExceptSelectBinOp" 'PrefixI 'False) (U1 :: Type -> Type)))

data WithClause Source #

References

with_clause:
  |  WITH cte_list
  |  WITH_LA cte_list
  |  WITH RECURSIVE cte_list

Instances

Instances details
Generic WithClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep WithClause :: Type -> Type #

Show WithClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq WithClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord WithClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep WithClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep WithClause = D1 ('MetaData "WithClause" "PostgresqlSyntax.Ast" "postgresql-syntax-0.4.1.1-1agduNP8gtd9DXmzqkx25k" 'False) (C1 ('MetaCons "WithClause" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NonEmpty CommonTableExpr))))

data CommonTableExpr Source #

References

common_table_expr:
  |  name opt_name_list AS opt_materialized '(' PreparableStmt ')'
opt_materialized:
  | MATERIALIZED
  | NOT MATERIALIZED
  | EMPTY

Instances

Instances details
Generic CommonTableExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep CommonTableExpr :: Type -> Type #

Show CommonTableExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq CommonTableExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord CommonTableExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep CommonTableExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

data OptTempTableName Source #

References

OptTempTableName:
  |  TEMPORARY opt_table qualified_name
  |  TEMP opt_table qualified_name
  |  LOCAL TEMPORARY opt_table qualified_name
  |  LOCAL TEMP opt_table qualified_name
  |  GLOBAL TEMPORARY opt_table qualified_name
  |  GLOBAL TEMP opt_table qualified_name
  |  UNLOGGED opt_table qualified_name
  |  TABLE qualified_name
  |  qualified_name

Instances

Instances details
Generic OptTempTableName Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep OptTempTableName :: Type -> Type #

Show OptTempTableName Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq OptTempTableName Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord OptTempTableName Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep OptTempTableName Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep OptTempTableName = D1 ('MetaData "OptTempTableName" "PostgresqlSyntax.Ast" "postgresql-syntax-0.4.1.1-1agduNP8gtd9DXmzqkx25k" 'False) (((C1 ('MetaCons "TemporaryOptTempTableName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 QualifiedName)) :+: C1 ('MetaCons "TempOptTempTableName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 QualifiedName))) :+: (C1 ('MetaCons "LocalTemporaryOptTempTableName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 QualifiedName)) :+: C1 ('MetaCons "LocalTempOptTempTableName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 QualifiedName)))) :+: ((C1 ('MetaCons "GlobalTemporaryOptTempTableName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 QualifiedName)) :+: C1 ('MetaCons "GlobalTempOptTempTableName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 QualifiedName))) :+: (C1 ('MetaCons "UnloggedOptTempTableName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 QualifiedName)) :+: (C1 ('MetaCons "TableOptTempTableName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 QualifiedName)) :+: C1 ('MetaCons "QualifedOptTempTableName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 QualifiedName))))))

data GroupByItem Source #

References

group_by_item:
  |  a_expr
  |  empty_grouping_set
  |  cube_clause
  |  rollup_clause
  |  grouping_sets_clause
empty_grouping_set:
  |  '(' ')'
rollup_clause:
  |  ROLLUP '(' expr_list ')'
cube_clause:
  |  CUBE '(' expr_list ')'
grouping_sets_clause:
  |  GROUPING SETS '(' group_by_list ')'

Instances

Instances details
Generic GroupByItem Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep GroupByItem :: Type -> Type #

Show GroupByItem Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq GroupByItem Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord GroupByItem Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep GroupByItem Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep GroupByItem = D1 ('MetaData "GroupByItem" "PostgresqlSyntax.Ast" "postgresql-syntax-0.4.1.1-1agduNP8gtd9DXmzqkx25k" 'False) ((C1 ('MetaCons "ExprGroupByItem" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AExpr)) :+: C1 ('MetaCons "EmptyGroupingSetGroupByItem" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "RollupGroupByItem" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ExprList)) :+: (C1 ('MetaCons "CubeGroupByItem" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ExprList)) :+: C1 ('MetaCons "GroupingSetsGroupByItem" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NonEmpty GroupByItem))))))

type HavingClause = AExpr Source #

having_clause:
  |  HAVING a_expr
  |  EMPTY

type WindowClause = NonEmpty WindowDefinition Source #

window_clause:
  |  WINDOW window_definition_list
  |  EMPTY

window_definition_list:
  |  window_definition
  |  window_definition_list ',' window_definition

data WindowDefinition Source #

window_definition:
  |  ColId AS window_specification

Instances

Instances details
Generic WindowDefinition Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep WindowDefinition :: Type -> Type #

Show WindowDefinition Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq WindowDefinition Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord WindowDefinition Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep WindowDefinition Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep WindowDefinition = D1 ('MetaData "WindowDefinition" "PostgresqlSyntax.Ast" "postgresql-syntax-0.4.1.1-1agduNP8gtd9DXmzqkx25k" 'False) (C1 ('MetaCons "WindowDefinition" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ident) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 WindowSpecification)))

data WindowSpecification Source #

window_specification:
  |  '(' opt_existing_window_name opt_partition_clause
            opt_sort_clause opt_frame_clause ')'

opt_existing_window_name:
  |  ColId
  |  EMPTY

opt_partition_clause:
  |  PARTITION BY expr_list
  |  EMPTY

Instances

Instances details
Generic WindowSpecification Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep WindowSpecification :: Type -> Type #

Show WindowSpecification Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq WindowSpecification Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord WindowSpecification Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep WindowSpecification Source # 
Instance details

Defined in PostgresqlSyntax.Ast

data FrameClause Source #

References

opt_frame_clause:
  |  RANGE frame_extent opt_window_exclusion_clause
  |  ROWS frame_extent opt_window_exclusion_clause
  |  GROUPS frame_extent opt_window_exclusion_clause
  |  EMPTY

Instances

Instances details
Generic FrameClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep FrameClause :: Type -> Type #

Show FrameClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq FrameClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord FrameClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep FrameClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

data FrameClauseMode Source #

References

opt_frame_clause:
  |  RANGE frame_extent opt_window_exclusion_clause
  |  ROWS frame_extent opt_window_exclusion_clause
  |  GROUPS frame_extent opt_window_exclusion_clause
  |  EMPTY

Instances

Instances details
Generic FrameClauseMode Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep FrameClauseMode :: Type -> Type #

Show FrameClauseMode Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq FrameClauseMode Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord FrameClauseMode Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep FrameClauseMode Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep FrameClauseMode = D1 ('MetaData "FrameClauseMode" "PostgresqlSyntax.Ast" "postgresql-syntax-0.4.1.1-1agduNP8gtd9DXmzqkx25k" 'False) (C1 ('MetaCons "RangeFrameClauseMode" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "RowsFrameClauseMode" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GroupsFrameClauseMode" 'PrefixI 'False) (U1 :: Type -> Type)))

data FrameExtent Source #

References

frame_extent:
  |  frame_bound
  |  BETWEEN frame_bound AND frame_bound

Instances

Instances details
Generic FrameExtent Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep FrameExtent :: Type -> Type #

Show FrameExtent Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq FrameExtent Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord FrameExtent Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep FrameExtent Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep FrameExtent = D1 ('MetaData "FrameExtent" "PostgresqlSyntax.Ast" "postgresql-syntax-0.4.1.1-1agduNP8gtd9DXmzqkx25k" 'False) (C1 ('MetaCons "SingularFrameExtent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FrameBound)) :+: C1 ('MetaCons "BetweenFrameExtent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FrameBound) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FrameBound)))

data FrameBound Source #

References

frame_bound:
  |  UNBOUNDED PRECEDING
  |  UNBOUNDED FOLLOWING
  |  CURRENT_P ROW
  |  a_expr PRECEDING
  |  a_expr FOLLOWING

Instances

Instances details
Generic FrameBound Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep FrameBound :: Type -> Type #

Show FrameBound Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq FrameBound Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord FrameBound Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep FrameBound Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep FrameBound = D1 ('MetaData "FrameBound" "PostgresqlSyntax.Ast" "postgresql-syntax-0.4.1.1-1agduNP8gtd9DXmzqkx25k" 'False) ((C1 ('MetaCons "UnboundedPrecedingFrameBound" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "UnboundedFollowingFrameBound" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "CurrentRowFrameBound" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PrecedingFrameBound" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AExpr)) :+: C1 ('MetaCons "FollowingFrameBound" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AExpr)))))

data WindowExclusionClause Source #

References

opt_window_exclusion_clause:
  |  EXCLUDE CURRENT_P ROW
  |  EXCLUDE GROUP_P
  |  EXCLUDE TIES
  |  EXCLUDE NO OTHERS
  |  EMPTY

Instances

Instances details
Generic WindowExclusionClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep WindowExclusionClause :: Type -> Type #

Show WindowExclusionClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq WindowExclusionClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord WindowExclusionClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep WindowExclusionClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep WindowExclusionClause = D1 ('MetaData "WindowExclusionClause" "PostgresqlSyntax.Ast" "postgresql-syntax-0.4.1.1-1agduNP8gtd9DXmzqkx25k" 'False) ((C1 ('MetaCons "CurrentRowWindowExclusionClause" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GroupWindowExclusionClause" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "TiesWindowExclusionClause" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NoOthersWindowExclusionClause" 'PrefixI 'False) (U1 :: Type -> Type)))

type ValuesClause = NonEmpty ExprList Source #

References

values_clause:
  |  VALUES '(' expr_list ')'
  |  values_clause ',' '(' expr_list ')'

type SortClause = NonEmpty SortBy Source #

sort_clause: | ORDER BY sortby_list

sortby_list: | sortby | sortby_list ',' sortby

data SortBy Source #

References

sortby:
  |  a_expr USING qual_all_Op opt_nulls_order
  |  a_expr opt_asc_desc opt_nulls_order

Instances

Instances details
Generic SortBy Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep SortBy :: Type -> Type #

Methods

from :: SortBy -> Rep SortBy x #

to :: Rep SortBy x -> SortBy #

Show SortBy Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq SortBy Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Methods

(==) :: SortBy -> SortBy -> Bool #

(/=) :: SortBy -> SortBy -> Bool #

Ord SortBy Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep SortBy Source # 
Instance details

Defined in PostgresqlSyntax.Ast

data SelectLimit Source #

References

select_limit:
  | limit_clause offset_clause
  | offset_clause limit_clause
  | limit_clause
  | offset_clause

Instances

Instances details
Generic SelectLimit Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep SelectLimit :: Type -> Type #

Show SelectLimit Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq SelectLimit Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord SelectLimit Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep SelectLimit Source # 
Instance details

Defined in PostgresqlSyntax.Ast

data LimitClause Source #

References

limit_clause:
  | LIMIT select_limit_value
  | LIMIT select_limit_value ',' select_offset_value
  | FETCH first_or_next select_fetch_first_value row_or_rows ONLY
  | FETCH first_or_next row_or_rows ONLY
select_offset_value:
  | a_expr
first_or_next:
  | FIRST_P
  | NEXT
row_or_rows:
  | ROW
  | ROWS

Instances

Instances details
Generic LimitClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep LimitClause :: Type -> Type #

Show LimitClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq LimitClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord LimitClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep LimitClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

data SelectFetchFirstValue Source #

References

select_fetch_first_value:
  | c_expr
  | + I_or_F_const
  | - I_or_F_const

Instances

Instances details
Generic SelectFetchFirstValue Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep SelectFetchFirstValue :: Type -> Type #

Show SelectFetchFirstValue Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq SelectFetchFirstValue Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord SelectFetchFirstValue Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep SelectFetchFirstValue Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep SelectFetchFirstValue = D1 ('MetaData "SelectFetchFirstValue" "PostgresqlSyntax.Ast" "postgresql-syntax-0.4.1.1-1agduNP8gtd9DXmzqkx25k" 'False) (C1 ('MetaCons "ExprSelectFetchFirstValue" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CExpr)) :+: C1 ('MetaCons "NumSelectFetchFirstValue" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Either Int64 Double))))

data SelectLimitValue Source #

References

select_limit_value:
  | a_expr
  | ALL

Instances

Instances details
Generic SelectLimitValue Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep SelectLimitValue :: Type -> Type #

Show SelectLimitValue Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq SelectLimitValue Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord SelectLimitValue Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep SelectLimitValue Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep SelectLimitValue = D1 ('MetaData "SelectLimitValue" "PostgresqlSyntax.Ast" "postgresql-syntax-0.4.1.1-1agduNP8gtd9DXmzqkx25k" 'False) (C1 ('MetaCons "ExprSelectLimitValue" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AExpr)) :+: C1 ('MetaCons "AllSelectLimitValue" 'PrefixI 'False) (U1 :: Type -> Type))

data OffsetClause Source #

References

offset_clause:
  | OFFSET select_offset_value
  | OFFSET select_fetch_first_value row_or_rows
select_offset_value:
  | a_expr
row_or_rows:
  | ROW
  | ROWS

Instances

Instances details
Generic OffsetClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep OffsetClause :: Type -> Type #

Show OffsetClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq OffsetClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord OffsetClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep OffsetClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep OffsetClause = D1 ('MetaData "OffsetClause" "PostgresqlSyntax.Ast" "postgresql-syntax-0.4.1.1-1agduNP8gtd9DXmzqkx25k" 'False) (C1 ('MetaCons "ExprOffsetClause" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AExpr)) :+: C1 ('MetaCons "FetchFirstOffsetClause" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SelectFetchFirstValue) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))

For Locking

data ForLockingClause Source #

References

for_locking_clause:
  | for_locking_items
  | FOR READ ONLY
for_locking_items:
  | for_locking_item
  | for_locking_items for_locking_item

Instances

Instances details
Generic ForLockingClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep ForLockingClause :: Type -> Type #

Show ForLockingClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq ForLockingClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord ForLockingClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep ForLockingClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep ForLockingClause = D1 ('MetaData "ForLockingClause" "PostgresqlSyntax.Ast" "postgresql-syntax-0.4.1.1-1agduNP8gtd9DXmzqkx25k" 'False) (C1 ('MetaCons "ItemsForLockingClause" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NonEmpty ForLockingItem))) :+: C1 ('MetaCons "ReadOnlyForLockingClause" 'PrefixI 'False) (U1 :: Type -> Type))

data ForLockingItem Source #

References

for_locking_item:
  | for_locking_strength locked_rels_list opt_nowait_or_skip
locked_rels_list:
  | OF qualified_name_list
  | EMPTY
opt_nowait_or_skip:
  | NOWAIT
  | SKIP LOCKED
  | EMPTY

Instances

Instances details
Generic ForLockingItem Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep ForLockingItem :: Type -> Type #

Show ForLockingItem Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq ForLockingItem Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord ForLockingItem Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep ForLockingItem Source # 
Instance details

Defined in PostgresqlSyntax.Ast

data ForLockingStrength Source #

References

for_locking_strength:
  | FOR UPDATE
  | FOR NO KEY UPDATE
  | FOR SHARE
  | FOR KEY SHARE

Instances

Instances details
Generic ForLockingStrength Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep ForLockingStrength :: Type -> Type #

Show ForLockingStrength Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq ForLockingStrength Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord ForLockingStrength Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep ForLockingStrength Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep ForLockingStrength = D1 ('MetaData "ForLockingStrength" "PostgresqlSyntax.Ast" "postgresql-syntax-0.4.1.1-1agduNP8gtd9DXmzqkx25k" 'False) ((C1 ('MetaCons "UpdateForLockingStrength" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NoKeyUpdateForLockingStrength" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ShareForLockingStrength" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KeyForLockingStrength" 'PrefixI 'False) (U1 :: Type -> Type)))

Table references and joining

type FromList = NonEmpty TableRef Source #

References

from_list:
  | table_ref
  | from_list ',' table_ref

data TableRef Source #

References

| relation_expr opt_alias_clause
| relation_expr opt_alias_clause tablesample_clause
| func_table func_alias_clause
| LATERAL_P func_table func_alias_clause
| xmltable opt_alias_clause
| LATERAL_P xmltable opt_alias_clause
| select_with_parens opt_alias_clause
| LATERAL_P select_with_parens opt_alias_clause
| joined_table
| '(' joined_table ')' alias_clause

TODO: Add xmltable

Constructors

RelationExprTableRef RelationExpr (Maybe AliasClause) (Maybe TablesampleClause)
   | relation_expr opt_alias_clause
   | relation_expr opt_alias_clause tablesample_clause
FuncTableRef Bool FuncTable (Maybe FuncAliasClause)
   | func_table func_alias_clause
   | LATERAL_P func_table func_alias_clause
SelectTableRef Bool SelectWithParens (Maybe AliasClause)
   | select_with_parens opt_alias_clause
   | LATERAL_P select_with_parens opt_alias_clause
JoinTableRef JoinedTable (Maybe AliasClause)
   | joined_table
   | '(' joined_table ')' alias_clause

Instances

Instances details
Generic TableRef Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep TableRef :: Type -> Type #

Methods

from :: TableRef -> Rep TableRef x #

to :: Rep TableRef x -> TableRef #

Show TableRef Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq TableRef Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord TableRef Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep TableRef Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep TableRef = D1 ('MetaData "TableRef" "PostgresqlSyntax.Ast" "postgresql-syntax-0.4.1.1-1agduNP8gtd9DXmzqkx25k" 'False) ((C1 ('MetaCons "RelationExprTableRef" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RelationExpr) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe AliasClause)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe TablesampleClause)))) :+: C1 ('MetaCons "FuncTableRef" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FuncTable) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FuncAliasClause))))) :+: (C1 ('MetaCons "SelectTableRef" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SelectWithParens) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe AliasClause)))) :+: C1 ('MetaCons "JoinTableRef" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JoinedTable) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe AliasClause)))))

data RelationExpr Source #

References

| qualified_name
| qualified_name *
| ONLY qualified_name
| ONLY '(' qualified_name ')'

Constructors

SimpleRelationExpr 

Fields

OnlyRelationExpr 

Fields

Instances

Instances details
Generic RelationExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep RelationExpr :: Type -> Type #

Show RelationExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq RelationExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord RelationExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep RelationExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

data RelationExprOptAlias Source #

References

relation_expr_opt_alias:
  | relation_expr
  | relation_expr ColId
  | relation_expr AS ColId

Instances

Instances details
Generic RelationExprOptAlias Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep RelationExprOptAlias :: Type -> Type #

Show RelationExprOptAlias Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq RelationExprOptAlias Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord RelationExprOptAlias Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep RelationExprOptAlias Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep RelationExprOptAlias = D1 ('MetaData "RelationExprOptAlias" "PostgresqlSyntax.Ast" "postgresql-syntax-0.4.1.1-1agduNP8gtd9DXmzqkx25k" 'False) (C1 ('MetaCons "RelationExprOptAlias" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RelationExpr) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Bool, ColId)))))

data TablesampleClause Source #

References

tablesample_clause:
  | TABLESAMPLE func_name '(' expr_list ')' opt_repeatable_clause

Instances

Instances details
Generic TablesampleClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep TablesampleClause :: Type -> Type #

Show TablesampleClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq TablesampleClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord TablesampleClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep TablesampleClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type RepeatableClause = AExpr Source #

References

opt_repeatable_clause:
  | REPEATABLE '(' a_expr ')'
  | EMPTY

data FuncTable Source #

References

func_table:
  | func_expr_windowless opt_ordinality
  | ROWS FROM '(' rowsfrom_list ')' opt_ordinality

Instances

Instances details
Generic FuncTable Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep FuncTable :: Type -> Type #

Show FuncTable Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq FuncTable Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord FuncTable Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep FuncTable Source # 
Instance details

Defined in PostgresqlSyntax.Ast

data RowsfromItem Source #

References

rowsfrom_item:
  | func_expr_windowless opt_col_def_list

Instances

Instances details
Generic RowsfromItem Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep RowsfromItem :: Type -> Type #

Show RowsfromItem Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq RowsfromItem Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord RowsfromItem Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep RowsfromItem Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep RowsfromItem = D1 ('MetaData "RowsfromItem" "PostgresqlSyntax.Ast" "postgresql-syntax-0.4.1.1-1agduNP8gtd9DXmzqkx25k" 'False) (C1 ('MetaCons "RowsfromItem" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FuncExprWindowless) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ColDefList))))

type RowsfromList = NonEmpty RowsfromItem Source #

References

rowsfrom_list:
  | rowsfrom_item
  | rowsfrom_list ',' rowsfrom_item

type ColDefList = TableFuncElementList Source #

References

opt_col_def_list:
  | AS '(' TableFuncElementList ')'
  | EMPTY

type OptOrdinality = Bool Source #

References

opt_ordinality:
  | WITH_LA ORDINALITY
  | EMPTY

type TableFuncElementList = NonEmpty TableFuncElement Source #

References

TableFuncElementList:
  | TableFuncElement
  | TableFuncElementList ',' TableFuncElement

data TableFuncElement Source #

References

TableFuncElement:
  | ColId Typename opt_collate_clause

Instances

Instances details
Generic TableFuncElement Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep TableFuncElement :: Type -> Type #

Show TableFuncElement Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq TableFuncElement Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord TableFuncElement Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep TableFuncElement Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type CollateClause = AnyName Source #

References

opt_collate_clause:
  | COLLATE any_name
  | EMPTY

data AliasClause Source #

References

alias_clause:
  |  AS ColId '(' name_list ')'
  |  AS ColId
  |  ColId '(' name_list ')'
  |  ColId

Instances

Instances details
Generic AliasClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep AliasClause :: Type -> Type #

Show AliasClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq AliasClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord AliasClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep AliasClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

data FuncAliasClause Source #

References

func_alias_clause:
  | alias_clause
  | AS '(' TableFuncElementList ')'
  | AS ColId '(' TableFuncElementList ')'
  | ColId '(' TableFuncElementList ')'
  | EMPTY

Instances

Instances details
Generic FuncAliasClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep FuncAliasClause :: Type -> Type #

Show FuncAliasClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq FuncAliasClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord FuncAliasClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep FuncAliasClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

data JoinedTable Source #

References

| '(' joined_table ')'
| table_ref CROSS JOIN table_ref
| table_ref join_type JOIN table_ref join_qual
| table_ref JOIN table_ref join_qual
| table_ref NATURAL join_type JOIN table_ref
| table_ref NATURAL JOIN table_ref

The options are covered by the JoinMeth type.

Instances

Instances details
Generic JoinedTable Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep JoinedTable :: Type -> Type #

Show JoinedTable Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq JoinedTable Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord JoinedTable Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep JoinedTable Source # 
Instance details

Defined in PostgresqlSyntax.Ast

data JoinMeth Source #

References

| table_ref CROSS JOIN table_ref
| table_ref join_type JOIN table_ref join_qual
| table_ref JOIN table_ref join_qual
| table_ref NATURAL join_type JOIN table_ref
| table_ref NATURAL JOIN table_ref

Instances

Instances details
Generic JoinMeth Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep JoinMeth :: Type -> Type #

Methods

from :: JoinMeth -> Rep JoinMeth x #

to :: Rep JoinMeth x -> JoinMeth #

Show JoinMeth Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq JoinMeth Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord JoinMeth Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep JoinMeth Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep JoinMeth = D1 ('MetaData "JoinMeth" "PostgresqlSyntax.Ast" "postgresql-syntax-0.4.1.1-1agduNP8gtd9DXmzqkx25k" 'False) (C1 ('MetaCons "CrossJoinMeth" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "QualJoinMeth" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe JoinType)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JoinQual)) :+: C1 ('MetaCons "NaturalJoinMeth" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe JoinType)))))

data JoinType Source #

References

| FULL join_outer
| LEFT join_outer
| RIGHT join_outer
| INNER_P

Instances

Instances details
Generic JoinType Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep JoinType :: Type -> Type #

Methods

from :: JoinType -> Rep JoinType x #

to :: Rep JoinType x -> JoinType #

Show JoinType Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq JoinType Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord JoinType Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep JoinType Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep JoinType = D1 ('MetaData "JoinType" "PostgresqlSyntax.Ast" "postgresql-syntax-0.4.1.1-1agduNP8gtd9DXmzqkx25k" 'False) ((C1 ('MetaCons "FullJoinType" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)) :+: C1 ('MetaCons "LeftJoinType" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))) :+: (C1 ('MetaCons "RightJoinType" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)) :+: C1 ('MetaCons "InnerJoinType" 'PrefixI 'False) (U1 :: Type -> Type)))

data JoinQual Source #

References

join_qual:
  |  USING '(' name_list ')'
  |  ON a_expr

Instances

Instances details
Generic JoinQual Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep JoinQual :: Type -> Type #

Methods

from :: JoinQual -> Rep JoinQual x #

to :: Rep JoinQual x -> JoinQual #

Show JoinQual Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq JoinQual Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord JoinQual Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep JoinQual Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep JoinQual = D1 ('MetaData "JoinQual" "PostgresqlSyntax.Ast" "postgresql-syntax-0.4.1.1-1agduNP8gtd9DXmzqkx25k" 'False) (C1 ('MetaCons "UsingJoinQual" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NonEmpty Ident))) :+: C1 ('MetaCons "OnJoinQual" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AExpr)))

Where

data WhereOrCurrentClause Source #

References

| WHERE a_expr
| WHERE CURRENT_P OF cursor_name
| *EMPTY*

Instances

Instances details
Generic WhereOrCurrentClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep WhereOrCurrentClause :: Type -> Type #

Show WhereOrCurrentClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq WhereOrCurrentClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord WhereOrCurrentClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep WhereOrCurrentClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep WhereOrCurrentClause = D1 ('MetaData "WhereOrCurrentClause" "PostgresqlSyntax.Ast" "postgresql-syntax-0.4.1.1-1agduNP8gtd9DXmzqkx25k" 'False) (C1 ('MetaCons "ExprWhereOrCurrentClause" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AExpr)) :+: C1 ('MetaCons "CursorWhereOrCurrentClause" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CursorName)))

Expression

data AExpr Source #

References

a_expr:
  | c_expr
  | a_expr TYPECAST Typename
  | a_expr COLLATE any_name
  | a_expr AT TIME ZONE a_expr
  | + a_expr
  | - a_expr
  | a_expr + a_expr
  | a_expr - a_expr
  | a_expr * a_expr
  | a_expr / a_expr
  | a_expr % a_expr
  | a_expr ^ a_expr
  | a_expr < a_expr
  | a_expr > a_expr
  | a_expr '=' a_expr
  | a_expr LESS_EQUALS a_expr
  | a_expr GREATER_EQUALS a_expr
  | a_expr NOT_EQUALS a_expr
  | a_expr qual_Op a_expr
  | qual_Op a_expr
  | a_expr qual_Op
  | a_expr AND a_expr
  | a_expr OR a_expr
  | NOT a_expr
  | NOT_LA a_expr
  | a_expr LIKE a_expr
  | a_expr LIKE a_expr ESCAPE a_expr
  | a_expr NOT_LA LIKE a_expr
  | a_expr NOT_LA LIKE a_expr ESCAPE a_expr
  | a_expr ILIKE a_expr
  | a_expr ILIKE a_expr ESCAPE a_expr
  | a_expr NOT_LA ILIKE a_expr
  | a_expr NOT_LA ILIKE a_expr ESCAPE a_expr
  | a_expr SIMILAR TO a_expr
  | a_expr SIMILAR TO a_expr ESCAPE a_expr
  | a_expr NOT_LA SIMILAR TO a_expr
  | a_expr NOT_LA SIMILAR TO a_expr ESCAPE a_expr
  | a_expr IS NULL_P
  | a_expr ISNULL
  | a_expr IS NOT NULL_P
  | a_expr NOTNULL
  | row OVERLAPS row
  | a_expr IS TRUE_P
  | a_expr IS NOT TRUE_P
  | a_expr IS FALSE_P
  | a_expr IS NOT FALSE_P
  | a_expr IS UNKNOWN
  | a_expr IS NOT UNKNOWN
  | a_expr IS DISTINCT FROM a_expr
  | a_expr IS NOT DISTINCT FROM a_expr
  | a_expr IS OF '(' type_list ')'
  | a_expr IS NOT OF '(' type_list ')'
  | a_expr BETWEEN opt_asymmetric b_expr AND a_expr
  | a_expr NOT_LA BETWEEN opt_asymmetric b_expr AND a_expr
  | a_expr BETWEEN SYMMETRIC b_expr AND a_expr
  | a_expr NOT_LA BETWEEN SYMMETRIC b_expr AND a_expr
  | a_expr IN_P in_expr
  | a_expr NOT_LA IN_P in_expr
  | a_expr subquery_Op sub_type select_with_parens
  | a_expr subquery_Op sub_type '(' a_expr ')'
  | UNIQUE select_with_parens
  | a_expr IS DOCUMENT_P
  | a_expr IS NOT DOCUMENT_P
  | DEFAULT

Instances

Instances details
Generic AExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep AExpr :: Type -> Type #

Methods

from :: AExpr -> Rep AExpr x #

to :: Rep AExpr x -> AExpr #

Show AExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Methods

showsPrec :: Int -> AExpr -> ShowS #

show :: AExpr -> String #

showList :: [AExpr] -> ShowS #

Eq AExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Methods

(==) :: AExpr -> AExpr -> Bool #

(/=) :: AExpr -> AExpr -> Bool #

Ord AExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Methods

compare :: AExpr -> AExpr -> Ordering #

(<) :: AExpr -> AExpr -> Bool #

(<=) :: AExpr -> AExpr -> Bool #

(>) :: AExpr -> AExpr -> Bool #

(>=) :: AExpr -> AExpr -> Bool #

max :: AExpr -> AExpr -> AExpr #

min :: AExpr -> AExpr -> AExpr #

type Rep AExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep AExpr = D1 ('MetaData "AExpr" "PostgresqlSyntax.Ast" "postgresql-syntax-0.4.1.1-1agduNP8gtd9DXmzqkx25k" 'False) ((((C1 ('MetaCons "CExprAExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CExpr)) :+: C1 ('MetaCons "TypecastAExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AExpr) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Typename))) :+: (C1 ('MetaCons "CollateAExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AExpr) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AnyName)) :+: (C1 ('MetaCons "AtTimeZoneAExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AExpr) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AExpr)) :+: C1 ('MetaCons "PlusAExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AExpr))))) :+: ((C1 ('MetaCons "MinusAExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AExpr)) :+: C1 ('MetaCons "SymbolicBinOpAExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AExpr) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SymbolicExprBinOp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AExpr)))) :+: (C1 ('MetaCons "PrefixQualOpAExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 QualOp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AExpr)) :+: (C1 ('MetaCons "SuffixQualOpAExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AExpr) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 QualOp)) :+: C1 ('MetaCons "AndAExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AExpr) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AExpr)))))) :+: (((C1 ('MetaCons "OrAExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AExpr) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AExpr)) :+: C1 ('MetaCons "NotAExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AExpr))) :+: (C1 ('MetaCons "VerbalExprBinOpAExpr" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AExpr) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 VerbalExprBinOp) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AExpr) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe AExpr))))) :+: (C1 ('MetaCons "ReversableOpAExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AExpr) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AExprReversableOp))) :+: C1 ('MetaCons "IsnullAExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AExpr))))) :+: ((C1 ('MetaCons "NotnullAExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AExpr)) :+: C1 ('MetaCons "OverlapsAExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Row) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Row))) :+: (C1 ('MetaCons "SubqueryAExpr" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AExpr) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SubqueryOp)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SubType) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Either SelectWithParens AExpr)))) :+: (C1 ('MetaCons "UniqueAExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SelectWithParens)) :+: C1 ('MetaCons "DefaultAExpr" 'PrefixI 'False) (U1 :: Type -> Type))))))

data BExpr Source #

References

b_expr:
  | c_expr
  | b_expr TYPECAST Typename
  | + b_expr
  | - b_expr
  | b_expr + b_expr
  | b_expr - b_expr
  | b_expr * b_expr
  | b_expr / b_expr
  | b_expr % b_expr
  | b_expr ^ b_expr
  | b_expr < b_expr
  | b_expr > b_expr
  | b_expr '=' b_expr
  | b_expr LESS_EQUALS b_expr
  | b_expr GREATER_EQUALS b_expr
  | b_expr NOT_EQUALS b_expr
  | b_expr qual_Op b_expr
  | qual_Op b_expr
  | b_expr qual_Op
  | b_expr IS DISTINCT FROM b_expr
  | b_expr IS NOT DISTINCT FROM b_expr
  | b_expr IS OF '(' type_list ')'
  | b_expr IS NOT OF '(' type_list ')'
  | b_expr IS DOCUMENT_P
  | b_expr IS NOT DOCUMENT_P

Instances

Instances details
Generic BExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep BExpr :: Type -> Type #

Methods

from :: BExpr -> Rep BExpr x #

to :: Rep BExpr x -> BExpr #

Show BExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Methods

showsPrec :: Int -> BExpr -> ShowS #

show :: BExpr -> String #

showList :: [BExpr] -> ShowS #

Eq BExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Methods

(==) :: BExpr -> BExpr -> Bool #

(/=) :: BExpr -> BExpr -> Bool #

Ord BExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Methods

compare :: BExpr -> BExpr -> Ordering #

(<) :: BExpr -> BExpr -> Bool #

(<=) :: BExpr -> BExpr -> Bool #

(>) :: BExpr -> BExpr -> Bool #

(>=) :: BExpr -> BExpr -> Bool #

max :: BExpr -> BExpr -> BExpr #

min :: BExpr -> BExpr -> BExpr #

type Rep BExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep BExpr = D1 ('MetaData "BExpr" "PostgresqlSyntax.Ast" "postgresql-syntax-0.4.1.1-1agduNP8gtd9DXmzqkx25k" 'False) ((C1 ('MetaCons "CExprBExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CExpr)) :+: (C1 ('MetaCons "TypecastBExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BExpr) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Typename)) :+: C1 ('MetaCons "PlusBExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BExpr)))) :+: ((C1 ('MetaCons "MinusBExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BExpr)) :+: C1 ('MetaCons "SymbolicBinOpBExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BExpr) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SymbolicExprBinOp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BExpr)))) :+: (C1 ('MetaCons "QualOpBExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 QualOp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BExpr)) :+: C1 ('MetaCons "IsOpBExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BExpr) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BExprIsOp))))))

data CExpr Source #

References

c_expr:
  | columnref
  | AexprConst
  | PARAM opt_indirection
  | '(' a_expr ')' opt_indirection
  | case_expr
  | func_expr
  | select_with_parens
  | select_with_parens indirection
  | EXISTS select_with_parens
  | ARRAY select_with_parens
  | ARRAY array_expr
  | explicit_row
  | implicit_row
  | GROUPING '(' expr_list ')'

Instances

Instances details
Generic CExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep CExpr :: Type -> Type #

Methods

from :: CExpr -> Rep CExpr x #

to :: Rep CExpr x -> CExpr #

Show CExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Methods

showsPrec :: Int -> CExpr -> ShowS #

show :: CExpr -> String #

showList :: [CExpr] -> ShowS #

Eq CExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Methods

(==) :: CExpr -> CExpr -> Bool #

(/=) :: CExpr -> CExpr -> Bool #

Ord CExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Methods

compare :: CExpr -> CExpr -> Ordering #

(<) :: CExpr -> CExpr -> Bool #

(<=) :: CExpr -> CExpr -> Bool #

(>) :: CExpr -> CExpr -> Bool #

(>=) :: CExpr -> CExpr -> Bool #

max :: CExpr -> CExpr -> CExpr #

min :: CExpr -> CExpr -> CExpr #

type Rep CExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep CExpr = D1 ('MetaData "CExpr" "PostgresqlSyntax.Ast" "postgresql-syntax-0.4.1.1-1agduNP8gtd9DXmzqkx25k" 'False) (((C1 ('MetaCons "ColumnrefCExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Columnref)) :+: (C1 ('MetaCons "AexprConstCExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AexprConst)) :+: C1 ('MetaCons "ParamCExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Indirection))))) :+: (C1 ('MetaCons "InParensCExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AExpr) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Indirection))) :+: (C1 ('MetaCons "CaseCExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CaseExpr)) :+: C1 ('MetaCons "FuncCExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FuncExpr))))) :+: ((C1 ('MetaCons "SelectWithParensCExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SelectWithParens) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Indirection))) :+: (C1 ('MetaCons "ExistsCExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SelectWithParens)) :+: C1 ('MetaCons "ArrayCExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Either SelectWithParens ArrayExpr))))) :+: (C1 ('MetaCons "ExplicitRowCExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ExplicitRow)) :+: (C1 ('MetaCons "ImplicitRowCExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ImplicitRow)) :+: C1 ('MetaCons "GroupingCExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ExprList))))))

data InExpr Source #

References

in_expr:
  | select_with_parens
  | '(' expr_list ')'

Instances

Instances details
Generic InExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep InExpr :: Type -> Type #

Methods

from :: InExpr -> Rep InExpr x #

to :: Rep InExpr x -> InExpr #

Show InExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq InExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Methods

(==) :: InExpr -> InExpr -> Bool #

(/=) :: InExpr -> InExpr -> Bool #

Ord InExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep InExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep InExpr = D1 ('MetaData "InExpr" "PostgresqlSyntax.Ast" "postgresql-syntax-0.4.1.1-1agduNP8gtd9DXmzqkx25k" 'False) (C1 ('MetaCons "SelectInExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SelectWithParens)) :+: C1 ('MetaCons "ExprListInExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ExprList)))

data SubType Source #

References

sub_type:
  | ANY
  | SOME
  | ALL

Instances

Instances details
Bounded SubType Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Enum SubType Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic SubType Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep SubType :: Type -> Type #

Methods

from :: SubType -> Rep SubType x #

to :: Rep SubType x -> SubType #

Show SubType Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq SubType Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Methods

(==) :: SubType -> SubType -> Bool #

(/=) :: SubType -> SubType -> Bool #

Ord SubType Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep SubType Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep SubType = D1 ('MetaData "SubType" "PostgresqlSyntax.Ast" "postgresql-syntax-0.4.1.1-1agduNP8gtd9DXmzqkx25k" 'False) (C1 ('MetaCons "AnySubType" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "SomeSubType" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AllSubType" 'PrefixI 'False) (U1 :: Type -> Type)))

data ArrayExpr Source #

References

array_expr:
  | '[' expr_list ']'
  | '[' array_expr_list ']'
  | '[' ']'

Instances

Instances details
Generic ArrayExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep ArrayExpr :: Type -> Type #

Show ArrayExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq ArrayExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord ArrayExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep ArrayExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep ArrayExpr = D1 ('MetaData "ArrayExpr" "PostgresqlSyntax.Ast" "postgresql-syntax-0.4.1.1-1agduNP8gtd9DXmzqkx25k" 'False) (C1 ('MetaCons "ExprListArrayExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ExprList)) :+: (C1 ('MetaCons "ArrayExprListArrayExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ArrayExprList)) :+: C1 ('MetaCons "EmptyArrayExpr" 'PrefixI 'False) (U1 :: Type -> Type)))

type ArrayExprList = NonEmpty ArrayExpr Source #

References

array_expr_list:
  | array_expr
  | array_expr_list ',' array_expr

data Row Source #

References

row:
  | ROW '(' expr_list ')'
  | ROW '(' ')'
  | '(' expr_list ',' a_expr ')'

Instances

Instances details
Generic Row Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep Row :: Type -> Type #

Methods

from :: Row -> Rep Row x #

to :: Rep Row x -> Row #

Show Row Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Methods

showsPrec :: Int -> Row -> ShowS #

show :: Row -> String #

showList :: [Row] -> ShowS #

Eq Row Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Methods

(==) :: Row -> Row -> Bool #

(/=) :: Row -> Row -> Bool #

Ord Row Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Methods

compare :: Row -> Row -> Ordering #

(<) :: Row -> Row -> Bool #

(<=) :: Row -> Row -> Bool #

(>) :: Row -> Row -> Bool #

(>=) :: Row -> Row -> Bool #

max :: Row -> Row -> Row #

min :: Row -> Row -> Row #

type Rep Row Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep Row = D1 ('MetaData "Row" "PostgresqlSyntax.Ast" "postgresql-syntax-0.4.1.1-1agduNP8gtd9DXmzqkx25k" 'False) (C1 ('MetaCons "ExplicitRowRow" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ExplicitRow)) :+: C1 ('MetaCons "ImplicitRowRow" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ImplicitRow)))

type ExplicitRow = Maybe ExprList Source #

References

explicit_row:
  | ROW '(' expr_list ')'
  | ROW '(' ')'

data ImplicitRow Source #

References

implicit_row:
  | '(' expr_list ',' a_expr ')'

Constructors

ImplicitRow ExprList AExpr 

Instances

Instances details
Generic ImplicitRow Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep ImplicitRow :: Type -> Type #

Show ImplicitRow Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq ImplicitRow Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord ImplicitRow Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep ImplicitRow Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep ImplicitRow = D1 ('MetaData "ImplicitRow" "PostgresqlSyntax.Ast" "postgresql-syntax-0.4.1.1-1agduNP8gtd9DXmzqkx25k" 'False) (C1 ('MetaCons "ImplicitRow" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ExprList) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AExpr)))

data FuncExpr Source #

References

func_expr:
  | func_application within_group_clause filter_clause over_clause
  | func_expr_common_subexpr

Instances

Instances details
Generic FuncExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep FuncExpr :: Type -> Type #

Methods

from :: FuncExpr -> Rep FuncExpr x #

to :: Rep FuncExpr x -> FuncExpr #

Show FuncExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq FuncExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord FuncExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep FuncExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

data FuncExprWindowless Source #

References

func_expr_windowless:
  | func_application
  | func_expr_common_subexpr

Instances

Instances details
Generic FuncExprWindowless Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep FuncExprWindowless :: Type -> Type #

Show FuncExprWindowless Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq FuncExprWindowless Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord FuncExprWindowless Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep FuncExprWindowless Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep FuncExprWindowless = D1 ('MetaData "FuncExprWindowless" "PostgresqlSyntax.Ast" "postgresql-syntax-0.4.1.1-1agduNP8gtd9DXmzqkx25k" 'False) (C1 ('MetaCons "ApplicationFuncExprWindowless" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FuncApplication)) :+: C1 ('MetaCons "CommonSubexprFuncExprWindowless" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FuncExprCommonSubexpr)))

type WithinGroupClause = SortClause Source #

References

within_group_clause:
  | WITHIN GROUP_P '(' sort_clause ')'
  | EMPTY

type FilterClause = AExpr Source #

References

filter_clause:
  | FILTER '(' WHERE a_expr ')'
  | EMPTY

data OverClause Source #

References

over_clause:
  | OVER window_specification
  | OVER ColId
  | EMPTY

Instances

Instances details
Generic OverClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep OverClause :: Type -> Type #

Show OverClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq OverClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord OverClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep OverClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep OverClause = D1 ('MetaData "OverClause" "PostgresqlSyntax.Ast" "postgresql-syntax-0.4.1.1-1agduNP8gtd9DXmzqkx25k" 'False) (C1 ('MetaCons "WindowOverClause" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 WindowSpecification)) :+: C1 ('MetaCons "ColIdOverClause" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ColId)))

data FuncExprCommonSubexpr Source #

References

func_expr_common_subexpr:
  | COLLATION FOR '(' a_expr ')'
  | CURRENT_DATE
  | CURRENT_TIME
  | CURRENT_TIME '(' Iconst ')'
  | CURRENT_TIMESTAMP
  | CURRENT_TIMESTAMP '(' Iconst ')'
  | LOCALTIME
  | LOCALTIME '(' Iconst ')'
  | LOCALTIMESTAMP
  | LOCALTIMESTAMP '(' Iconst ')'
  | CURRENT_ROLE
  | CURRENT_USER
  | SESSION_USER
  | USER
  | CURRENT_CATALOG
  | CURRENT_SCHEMA
  | CAST '(' a_expr AS Typename ')'
  | EXTRACT '(' extract_list ')'
  | OVERLAY '(' overlay_list ')'
  | POSITION '(' position_list ')'
  | SUBSTRING '(' substr_list ')'
  | TREAT '(' a_expr AS Typename ')'
  | TRIM '(' BOTH trim_list ')'
  | TRIM '(' LEADING trim_list ')'
  | TRIM '(' TRAILING trim_list ')'
  | TRIM '(' trim_list ')'
  | NULLIF '(' a_expr ',' a_expr ')'
  | COALESCE '(' expr_list ')'
  | GREATEST '(' expr_list ')'
  | LEAST '(' expr_list ')'
  | XMLCONCAT '(' expr_list ')'
  | XMLELEMENT '(' NAME_P ColLabel ')'
  | XMLELEMENT '(' NAME_P ColLabel ',' xml_attributes ')'
  | XMLELEMENT '(' NAME_P ColLabel ',' expr_list ')'
  | XMLELEMENT '(' NAME_P ColLabel ',' xml_attributes ',' expr_list ')'
  | XMLEXISTS '(' c_expr xmlexists_argument ')'
  | XMLFOREST '(' xml_attribute_list ')'
  | XMLPARSE '(' document_or_content a_expr xml_whitespace_option ')'
  | XMLPI '(' NAME_P ColLabel ')'
  | XMLPI '(' NAME_P ColLabel ',' a_expr ')'
  | XMLROOT '(' a_expr ',' xml_root_version opt_xml_root_standalone ')'
  | XMLSERIALIZE '(' document_or_content a_expr AS SimpleTypename ')'

TODO: Implement the XML cases

Instances

Instances details
Generic FuncExprCommonSubexpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep FuncExprCommonSubexpr :: Type -> Type #

Show FuncExprCommonSubexpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq FuncExprCommonSubexpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord FuncExprCommonSubexpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep FuncExprCommonSubexpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep FuncExprCommonSubexpr = D1 ('MetaData "FuncExprCommonSubexpr" "PostgresqlSyntax.Ast" "postgresql-syntax-0.4.1.1-1agduNP8gtd9DXmzqkx25k" 'False) ((((C1 ('MetaCons "CollationForFuncExprCommonSubexpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AExpr)) :+: C1 ('MetaCons "CurrentDateFuncExprCommonSubexpr" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "CurrentTimeFuncExprCommonSubexpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int64))) :+: (C1 ('MetaCons "CurrentTimestampFuncExprCommonSubexpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int64))) :+: C1 ('MetaCons "LocalTimeFuncExprCommonSubexpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int64)))))) :+: ((C1 ('MetaCons "LocalTimestampFuncExprCommonSubexpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int64))) :+: (C1 ('MetaCons "CurrentRoleFuncExprCommonSubexpr" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CurrentUserFuncExprCommonSubexpr" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "SessionUserFuncExprCommonSubexpr" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "UserFuncExprCommonSubexpr" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CurrentCatalogFuncExprCommonSubexpr" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "CurrentSchemaFuncExprCommonSubexpr" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "CastFuncExprCommonSubexpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AExpr) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Typename)) :+: C1 ('MetaCons "ExtractFuncExprCommonSubexpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ExtractList))))) :+: (C1 ('MetaCons "OverlayFuncExprCommonSubexpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 OverlayList)) :+: (C1 ('MetaCons "PositionFuncExprCommonSubexpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe PositionList))) :+: C1 ('MetaCons "SubstringFuncExprCommonSubexpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe SubstrList)))))) :+: ((C1 ('MetaCons "TreatFuncExprCommonSubexpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AExpr) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Typename)) :+: (C1 ('MetaCons "TrimFuncExprCommonSubexpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe TrimModifier)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TrimList)) :+: C1 ('MetaCons "NullIfFuncExprCommonSubexpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AExpr) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AExpr)))) :+: (C1 ('MetaCons "CoalesceFuncExprCommonSubexpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ExprList)) :+: (C1 ('MetaCons "GreatestFuncExprCommonSubexpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ExprList)) :+: C1 ('MetaCons "LeastFuncExprCommonSubexpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ExprList)))))))

data ExtractList Source #

References

extract_list:
  | extract_arg FROM a_expr
  | EMPTY

Instances

Instances details
Generic ExtractList Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep ExtractList :: Type -> Type #

Show ExtractList Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq ExtractList Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord ExtractList Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep ExtractList Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep ExtractList = D1 ('MetaData "ExtractList" "PostgresqlSyntax.Ast" "postgresql-syntax-0.4.1.1-1agduNP8gtd9DXmzqkx25k" 'False) (C1 ('MetaCons "ExtractList" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ExtractArg) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AExpr)))

data ExtractArg Source #

References

extract_arg:
  | IDENT
  | YEAR_P
  | MONTH_P
  | DAY_P
  | HOUR_P
  | MINUTE_P
  | SECOND_P
  | Sconst

Instances

Instances details
Generic ExtractArg Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep ExtractArg :: Type -> Type #

Show ExtractArg Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq ExtractArg Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord ExtractArg Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep ExtractArg Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep ExtractArg = D1 ('MetaData "ExtractArg" "PostgresqlSyntax.Ast" "postgresql-syntax-0.4.1.1-1agduNP8gtd9DXmzqkx25k" 'False) (((C1 ('MetaCons "IdentExtractArg" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ident)) :+: C1 ('MetaCons "YearExtractArg" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "MonthExtractArg" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DayExtractArg" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "HourExtractArg" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MinuteExtractArg" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "SecondExtractArg" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SconstExtractArg" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Sconst)))))

data OverlayList Source #

References

overlay_list:
  | a_expr overlay_placing substr_from substr_for
  | a_expr overlay_placing substr_from

Instances

Instances details
Generic OverlayList Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep OverlayList :: Type -> Type #

Show OverlayList Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq OverlayList Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord OverlayList Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep OverlayList Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type OverlayPlacing = AExpr Source #

References

overlay_placing:
  | PLACING a_expr

data PositionList Source #

References

position_list:
  | b_expr IN_P b_expr
  | EMPTY

Constructors

PositionList BExpr BExpr 

Instances

Instances details
Generic PositionList Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep PositionList :: Type -> Type #

Show PositionList Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq PositionList Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord PositionList Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep PositionList Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep PositionList = D1 ('MetaData "PositionList" "PostgresqlSyntax.Ast" "postgresql-syntax-0.4.1.1-1agduNP8gtd9DXmzqkx25k" 'False) (C1 ('MetaCons "PositionList" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BExpr) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BExpr)))

data SubstrList Source #

References

substr_list:
  | a_expr substr_from substr_for
  | a_expr substr_for substr_from
  | a_expr substr_from
  | a_expr substr_for
  | expr_list
  | EMPTY

Instances

Instances details
Generic SubstrList Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep SubstrList :: Type -> Type #

Show SubstrList Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq SubstrList Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord SubstrList Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep SubstrList Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep SubstrList = D1 ('MetaData "SubstrList" "PostgresqlSyntax.Ast" "postgresql-syntax-0.4.1.1-1agduNP8gtd9DXmzqkx25k" 'False) (C1 ('MetaCons "ExprSubstrList" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AExpr) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SubstrListFromFor)) :+: C1 ('MetaCons "ExprListSubstrList" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ExprList)))

data SubstrListFromFor Source #

References

  | a_expr substr_from substr_for
  | a_expr substr_for substr_from
  | a_expr substr_from
  | a_expr substr_for

Instances

Instances details
Generic SubstrListFromFor Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep SubstrListFromFor :: Type -> Type #

Show SubstrListFromFor Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq SubstrListFromFor Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord SubstrListFromFor Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep SubstrListFromFor Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type SubstrFrom = AExpr Source #

References

substr_from:
  | FROM a_expr

type SubstrFor = AExpr Source #

References

substr_for:
  | FOR a_expr

data TrimModifier Source #

References

  | TRIM '(' BOTH trim_list ')'
  | TRIM '(' LEADING trim_list ')'
  | TRIM '(' TRAILING trim_list ')'

Instances

Instances details
Bounded TrimModifier Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Enum TrimModifier Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic TrimModifier Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep TrimModifier :: Type -> Type #

Show TrimModifier Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq TrimModifier Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord TrimModifier Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep TrimModifier Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep TrimModifier = D1 ('MetaData "TrimModifier" "PostgresqlSyntax.Ast" "postgresql-syntax-0.4.1.1-1agduNP8gtd9DXmzqkx25k" 'False) (C1 ('MetaCons "BothTrimModifier" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "LeadingTrimModifier" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TrailingTrimModifier" 'PrefixI 'False) (U1 :: Type -> Type)))

data TrimList Source #

References

trim_list:
  | a_expr FROM expr_list
  | FROM expr_list
  | expr_list

Instances

Instances details
Generic TrimList Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep TrimList :: Type -> Type #

Methods

from :: TrimList -> Rep TrimList x #

to :: Rep TrimList x -> TrimList #

Show TrimList Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq TrimList Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord TrimList Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep TrimList Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep TrimList = D1 ('MetaData "TrimList" "PostgresqlSyntax.Ast" "postgresql-syntax-0.4.1.1-1agduNP8gtd9DXmzqkx25k" 'False) (C1 ('MetaCons "ExprFromExprListTrimList" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AExpr) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ExprList)) :+: (C1 ('MetaCons "FromExprListTrimList" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ExprList)) :+: C1 ('MetaCons "ExprListTrimList" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ExprList))))

data CaseExpr Source #

References

case_expr:
  | CASE case_arg when_clause_list case_default END_P

Instances

Instances details
Generic CaseExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep CaseExpr :: Type -> Type #

Methods

from :: CaseExpr -> Rep CaseExpr x #

to :: Rep CaseExpr x -> CaseExpr #

Show CaseExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq CaseExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord CaseExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep CaseExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type CaseArg = AExpr Source #

References

case_arg:
  | a_expr
  | EMPTY

type WhenClauseList = NonEmpty WhenClause Source #

References

when_clause_list:
  | when_clause
  | when_clause_list when_clause

type CaseDefault = AExpr Source #

References

case_default:
  | ELSE a_expr
  | EMPTY

data WhenClause Source #

References

when_clause:
  |  WHEN a_expr THEN a_expr

Constructors

WhenClause AExpr AExpr 

Instances

Instances details
Generic WhenClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep WhenClause :: Type -> Type #

Show WhenClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq WhenClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord WhenClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep WhenClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep WhenClause = D1 ('MetaData "WhenClause" "PostgresqlSyntax.Ast" "postgresql-syntax-0.4.1.1-1agduNP8gtd9DXmzqkx25k" 'False) (C1 ('MetaCons "WhenClause" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AExpr) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AExpr)))

data FuncApplication Source #

References

func_application:
  |  func_name '(' ')'
  |  func_name '(' func_arg_list opt_sort_clause ')'
  |  func_name '(' VARIADIC func_arg_expr opt_sort_clause ')'
  |  func_name '(' func_arg_list ',' VARIADIC func_arg_expr opt_sort_clause ')'
  |  func_name '(' ALL func_arg_list opt_sort_clause ')'
  |  func_name '(' DISTINCT func_arg_list opt_sort_clause ')'
  |  func_name '(' * ')'

Instances

Instances details
Generic FuncApplication Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep FuncApplication :: Type -> Type #

Show FuncApplication Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq FuncApplication Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord FuncApplication Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep FuncApplication Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep FuncApplication = D1 ('MetaData "FuncApplication" "PostgresqlSyntax.Ast" "postgresql-syntax-0.4.1.1-1agduNP8gtd9DXmzqkx25k" 'False) (C1 ('MetaCons "FuncApplication" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FuncName) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FuncApplicationParams))))

data FuncApplicationParams Source #

References

func_application:
  |  func_name '(' ')'
  |  func_name '(' func_arg_list opt_sort_clause ')'
  |  func_name '(' VARIADIC func_arg_expr opt_sort_clause ')'
  |  func_name '(' func_arg_list ',' VARIADIC func_arg_expr opt_sort_clause ')'
  |  func_name '(' ALL func_arg_list opt_sort_clause ')'
  |  func_name '(' DISTINCT func_arg_list opt_sort_clause ')'
  |  func_name '(' * ')'

Instances

Instances details
Generic FuncApplicationParams Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep FuncApplicationParams :: Type -> Type #

Show FuncApplicationParams Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq FuncApplicationParams Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord FuncApplicationParams Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep FuncApplicationParams Source # 
Instance details

Defined in PostgresqlSyntax.Ast

data FuncArgExpr Source #

Instances

Instances details
Generic FuncArgExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep FuncArgExpr :: Type -> Type #

Show FuncArgExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq FuncArgExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord FuncArgExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep FuncArgExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Constants

data AexprConst Source #

AexprConst: | Iconst | FCONST | Sconst | BCONST | XCONST | func_name Sconst | func_name '(' func_arg_list opt_sort_clause ')' Sconst | ConstTypename Sconst | ConstInterval Sconst opt_interval | ConstInterval '(' Iconst ')' Sconst | TRUE_P | FALSE_P | NULL_P

Instances

Instances details
Generic AexprConst Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep AexprConst :: Type -> Type #

Show AexprConst Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq AexprConst Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord AexprConst Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep AexprConst Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep AexprConst = D1 ('MetaData "AexprConst" "PostgresqlSyntax.Ast" "postgresql-syntax-0.4.1.1-1agduNP8gtd9DXmzqkx25k" 'False) (((C1 ('MetaCons "IAexprConst" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Iconst)) :+: C1 ('MetaCons "FAexprConst" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Fconst))) :+: (C1 ('MetaCons "SAexprConst" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Sconst)) :+: (C1 ('MetaCons "BAexprConst" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bconst)) :+: C1 ('MetaCons "XAexprConst" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Xconst))))) :+: ((C1 ('MetaCons "FuncAexprConst" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FuncName) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FuncConstArgs)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Sconst))) :+: (C1 ('MetaCons "ConstTypenameAexprConst" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ConstTypename) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Sconst)) :+: C1 ('MetaCons "StringIntervalAexprConst" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Sconst) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Interval))))) :+: (C1 ('MetaCons "IntIntervalAexprConst" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Iconst) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Sconst)) :+: (C1 ('MetaCons "BoolAexprConst" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)) :+: C1 ('MetaCons "NullAexprConst" 'PrefixI 'False) (U1 :: Type -> Type)))))

data FuncConstArgs Source #

References

  |  func_name '(' func_arg_list opt_sort_clause ')' Sconst

Instances

Instances details
Generic FuncConstArgs Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep FuncConstArgs :: Type -> Type #

Show FuncConstArgs Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq FuncConstArgs Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord FuncConstArgs Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep FuncConstArgs Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep FuncConstArgs = D1 ('MetaData "FuncConstArgs" "PostgresqlSyntax.Ast" "postgresql-syntax-0.4.1.1-1agduNP8gtd9DXmzqkx25k" 'False) (C1 ('MetaCons "FuncConstArgs" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NonEmpty FuncArgExpr)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe SortClause))))

data ConstTypename Source #

References

ConstTypename:
  | Numeric
  | ConstBit
  | ConstCharacter
  | ConstDatetime

Instances

Instances details
Generic ConstTypename Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep ConstTypename :: Type -> Type #

Show ConstTypename Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq ConstTypename Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord ConstTypename Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep ConstTypename Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep ConstTypename = D1 ('MetaData "ConstTypename" "PostgresqlSyntax.Ast" "postgresql-syntax-0.4.1.1-1agduNP8gtd9DXmzqkx25k" 'False) ((C1 ('MetaCons "NumericConstTypename" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Numeric)) :+: C1 ('MetaCons "ConstBitConstTypename" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ConstBit))) :+: (C1 ('MetaCons "ConstCharacterConstTypename" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ConstCharacter)) :+: C1 ('MetaCons "ConstDatetimeConstTypename" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ConstDatetime))))

data Numeric Source #

References

Numeric:
  | INT_P
  | INTEGER
  | SMALLINT
  | BIGINT
  | REAL
  | FLOAT_P opt_float
  | DOUBLE_P PRECISION
  | DECIMAL_P opt_type_modifiers
  | DEC opt_type_modifiers
  | NUMERIC opt_type_modifiers
  | BOOLEAN_P
opt_float:
  | '(' Iconst ')'
  | EMPTY
opt_type_modifiers:
  | '(' expr_list ')'
  | EMPTY

Instances

Instances details
Generic Numeric Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep Numeric :: Type -> Type #

Methods

from :: Numeric -> Rep Numeric x #

to :: Rep Numeric x -> Numeric #

Show Numeric Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq Numeric Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Methods

(==) :: Numeric -> Numeric -> Bool #

(/=) :: Numeric -> Numeric -> Bool #

Ord Numeric Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep Numeric Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep Numeric = D1 ('MetaData "Numeric" "PostgresqlSyntax.Ast" "postgresql-syntax-0.4.1.1-1agduNP8gtd9DXmzqkx25k" 'False) (((C1 ('MetaCons "IntNumeric" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "IntegerNumeric" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "SmallintNumeric" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "BigintNumeric" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RealNumeric" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "FloatNumeric" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int64))) :+: (C1 ('MetaCons "DoublePrecisionNumeric" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DecimalNumeric" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe TypeModifiers))))) :+: (C1 ('MetaCons "DecNumeric" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe TypeModifiers))) :+: (C1 ('MetaCons "NumericNumeric" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe TypeModifiers))) :+: C1 ('MetaCons "BooleanNumeric" 'PrefixI 'False) (U1 :: Type -> Type)))))

data Bit Source #

References

Bit:
  | BitWithLength
  | BitWithoutLength
ConstBit:
  | BitWithLength
  | BitWithoutLength
BitWithLength:
  | BIT opt_varying '(' expr_list ')'
BitWithoutLength:
  | BIT opt_varying

Constructors

Bit OptVarying (Maybe ExprList) 

Instances

Instances details
Generic Bit Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep Bit :: Type -> Type #

Methods

from :: Bit -> Rep Bit x #

to :: Rep Bit x -> Bit #

Show Bit Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Methods

showsPrec :: Int -> Bit -> ShowS #

show :: Bit -> String #

showList :: [Bit] -> ShowS #

Eq Bit Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Methods

(==) :: Bit -> Bit -> Bool #

(/=) :: Bit -> Bit -> Bool #

Ord Bit Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Methods

compare :: Bit -> Bit -> Ordering #

(<) :: Bit -> Bit -> Bool #

(<=) :: Bit -> Bit -> Bool #

(>) :: Bit -> Bit -> Bool #

(>=) :: Bit -> Bit -> Bool #

max :: Bit -> Bit -> Bit #

min :: Bit -> Bit -> Bit #

type Rep Bit Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep Bit = D1 ('MetaData "Bit" "PostgresqlSyntax.Ast" "postgresql-syntax-0.4.1.1-1agduNP8gtd9DXmzqkx25k" 'False) (C1 ('MetaCons "Bit" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 OptVarying) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ExprList))))

type OptVarying = Bool Source #

References

opt_varying:
  | VARYING
  | EMPTY

data ConstCharacter Source #

References

Character:
  | CharacterWithLength
  | CharacterWithoutLength
ConstCharacter:
  | CharacterWithLength
  | CharacterWithoutLength
CharacterWithLength:
  | character '(' Iconst ')'
CharacterWithoutLength:
  | character

Instances

Instances details
Generic ConstCharacter Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep ConstCharacter :: Type -> Type #

Show ConstCharacter Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq ConstCharacter Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord ConstCharacter Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep ConstCharacter Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep ConstCharacter = D1 ('MetaData "ConstCharacter" "PostgresqlSyntax.Ast" "postgresql-syntax-0.4.1.1-1agduNP8gtd9DXmzqkx25k" 'False) (C1 ('MetaCons "ConstCharacter" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Character) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int64))))

data Character Source #

References

character:
  | CHARACTER opt_varying
  | CHAR_P opt_varying
  | VARCHAR
  | NATIONAL CHARACTER opt_varying
  | NATIONAL CHAR_P opt_varying
  | NCHAR opt_varying

Instances

Instances details
Generic Character Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep Character :: Type -> Type #

Show Character Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq Character Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord Character Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep Character Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep Character = D1 ('MetaData "Character" "PostgresqlSyntax.Ast" "postgresql-syntax-0.4.1.1-1agduNP8gtd9DXmzqkx25k" 'False) ((C1 ('MetaCons "CharacterCharacter" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 OptVarying)) :+: (C1 ('MetaCons "CharCharacter" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 OptVarying)) :+: C1 ('MetaCons "VarcharCharacter" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "NationalCharacterCharacter" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 OptVarying)) :+: (C1 ('MetaCons "NationalCharCharacter" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 OptVarying)) :+: C1 ('MetaCons "NcharCharacter" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 OptVarying)))))

data ConstDatetime Source #

References

ConstDatetime:
  | TIMESTAMP '(' Iconst ')' opt_timezone
  | TIMESTAMP opt_timezone
  | TIME '(' Iconst ')' opt_timezone
  | TIME opt_timezone

Instances

Instances details
Generic ConstDatetime Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep ConstDatetime :: Type -> Type #

Show ConstDatetime Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq ConstDatetime Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord ConstDatetime Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep ConstDatetime Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Timezone = Bool Source #

References

opt_timezone:
  | WITH_LA TIME ZONE
  | WITHOUT TIME ZONE
  | EMPTY

data Interval Source #

References

opt_interval:
  | YEAR_P
  | MONTH_P
  | DAY_P
  | HOUR_P
  | MINUTE_P
  | interval_second
  | YEAR_P TO MONTH_P
  | DAY_P TO HOUR_P
  | DAY_P TO MINUTE_P
  | DAY_P TO interval_second
  | HOUR_P TO MINUTE_P
  | HOUR_P TO interval_second
  | MINUTE_P TO interval_second
  | EMPTY

Instances

Instances details
Generic Interval Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep Interval :: Type -> Type #

Methods

from :: Interval -> Rep Interval x #

to :: Rep Interval x -> Interval #

Show Interval Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq Interval Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord Interval Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep Interval Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep Interval = D1 ('MetaData "Interval" "PostgresqlSyntax.Ast" "postgresql-syntax-0.4.1.1-1agduNP8gtd9DXmzqkx25k" 'False) (((C1 ('MetaCons "YearInterval" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "MonthInterval" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DayInterval" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "HourInterval" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "MinuteInterval" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SecondInterval" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 IntervalSecond))))) :+: ((C1 ('MetaCons "YearToMonthInterval" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "DayToHourInterval" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DayToMinuteInterval" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "DayToSecondInterval" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 IntervalSecond)) :+: C1 ('MetaCons "HourToMinuteInterval" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "HourToSecondInterval" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 IntervalSecond)) :+: C1 ('MetaCons "MinuteToSecondInterval" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 IntervalSecond))))))

type IntervalSecond = Maybe Int64 Source #

References

interval_second:
  | SECOND_P
  | SECOND_P '(' Iconst ')'

Names & References

data Ident Source #

References

IDENT

Instances

Instances details
Generic Ident Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep Ident :: Type -> Type #

Methods

from :: Ident -> Rep Ident x #

to :: Rep Ident x -> Ident #

Show Ident Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Methods

showsPrec :: Int -> Ident -> ShowS #

show :: Ident -> String #

showList :: [Ident] -> ShowS #

Eq Ident Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Methods

(==) :: Ident -> Ident -> Bool #

(/=) :: Ident -> Ident -> Bool #

Ord Ident Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Methods

compare :: Ident -> Ident -> Ordering #

(<) :: Ident -> Ident -> Bool #

(<=) :: Ident -> Ident -> Bool #

(>) :: Ident -> Ident -> Bool #

(>=) :: Ident -> Ident -> Bool #

max :: Ident -> Ident -> Ident #

min :: Ident -> Ident -> Ident #

type Rep Ident Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep Ident = D1 ('MetaData "Ident" "PostgresqlSyntax.Ast" "postgresql-syntax-0.4.1.1-1agduNP8gtd9DXmzqkx25k" 'False) (C1 ('MetaCons "QuotedIdent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: C1 ('MetaCons "UnquotedIdent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

type ColId = Ident Source #

References

ColId:
  | IDENT
  | unreserved_keyword
  | col_name_keyword

type ColLabel = Ident Source #

References

ColLabel:
  | IDENT
  | unreserved_keyword
  | col_name_keyword
  | type_func_name_keyword
  | reserved_keyword

type Name = ColId Source #

References

name:
  | ColId

type NameList = NonEmpty Name Source #

References

name_list:
  | name
  | name_list ',' name

type CursorName = Name Source #

References

cursor_name:
  | name

data Columnref Source #

References

columnref:
  | ColId
  | ColId indirection

Instances

Instances details
Generic Columnref Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep Columnref :: Type -> Type #

Show Columnref Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq Columnref Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord Columnref Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep Columnref Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep Columnref = D1 ('MetaData "Columnref" "PostgresqlSyntax.Ast" "postgresql-syntax-0.4.1.1-1agduNP8gtd9DXmzqkx25k" 'False) (C1 ('MetaCons "Columnref" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ColId) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Indirection))))

data AnyName Source #

References

any_name:
  | ColId
  | ColId attrs

Constructors

AnyName ColId (Maybe Attrs) 

Instances

Instances details
Generic AnyName Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep AnyName :: Type -> Type #

Methods

from :: AnyName -> Rep AnyName x #

to :: Rep AnyName x -> AnyName #

Show AnyName Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq AnyName Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Methods

(==) :: AnyName -> AnyName -> Bool #

(/=) :: AnyName -> AnyName -> Bool #

Ord AnyName Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep AnyName Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep AnyName = D1 ('MetaData "AnyName" "PostgresqlSyntax.Ast" "postgresql-syntax-0.4.1.1-1agduNP8gtd9DXmzqkx25k" 'False) (C1 ('MetaCons "AnyName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ColId) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Attrs))))

data FuncName Source #

References

func_name:
  | type_function_name
  | ColId indirection

Instances

Instances details
Generic FuncName Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep FuncName :: Type -> Type #

Methods

from :: FuncName -> Rep FuncName x #

to :: Rep FuncName x -> FuncName #

Show FuncName Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq FuncName Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord FuncName Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep FuncName Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep FuncName = D1 ('MetaData "FuncName" "PostgresqlSyntax.Ast" "postgresql-syntax-0.4.1.1-1agduNP8gtd9DXmzqkx25k" 'False) (C1 ('MetaCons "TypeFuncName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TypeFunctionName)) :+: C1 ('MetaCons "IndirectedFuncName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ColId) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Indirection)))

type TypeFunctionName = Ident Source #

References

type_function_name:
  | IDENT
  | unreserved_keyword
  | type_func_name_keyword

data QualifiedName Source #

References

columnref:
  | ColId
  | ColId indirection
qualified_name:
  | ColId
  | ColId indirection

Instances

Instances details
Generic QualifiedName Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep QualifiedName :: Type -> Type #

Show QualifiedName Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq QualifiedName Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord QualifiedName Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep QualifiedName Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep QualifiedName = D1 ('MetaData "QualifiedName" "PostgresqlSyntax.Ast" "postgresql-syntax-0.4.1.1-1agduNP8gtd9DXmzqkx25k" 'False) (C1 ('MetaCons "SimpleQualifiedName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ident)) :+: C1 ('MetaCons "IndirectedQualifiedName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ident) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Indirection)))

type Indirection = NonEmpty IndirectionEl Source #

References

indirection:
  |  indirection_el
  |  indirection indirection_el

data IndirectionEl Source #

References

indirection_el:
  |  . attr_name
  |  . *
  |  '[' a_expr ']'
  |  '[' opt_slice_bound : opt_slice_bound ']'
opt_slice_bound:
  |  a_expr
  |  EMPTY

Instances

Instances details
Generic IndirectionEl Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep IndirectionEl :: Type -> Type #

Show IndirectionEl Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq IndirectionEl Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord IndirectionEl Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep IndirectionEl Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep IndirectionEl = D1 ('MetaData "IndirectionEl" "PostgresqlSyntax.Ast" "postgresql-syntax-0.4.1.1-1agduNP8gtd9DXmzqkx25k" 'False) ((C1 ('MetaCons "AttrNameIndirectionEl" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ident)) :+: C1 ('MetaCons "AllIndirectionEl" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ExprIndirectionEl" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AExpr)) :+: C1 ('MetaCons "SliceIndirectionEl" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe AExpr)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe AExpr)))))

Types

data Typename Source #

Typename definition extended with custom question-marks for nullability specification.

To match the standard Postgres syntax simply interpret their presence as a parsing error.

References

Typename:
  | SimpleTypename opt_array_bounds
  | SETOF SimpleTypename opt_array_bounds
  | SimpleTypename ARRAY '[' Iconst ']'
  | SETOF SimpleTypename ARRAY '[' Iconst ']'
  | SimpleTypename ARRAY
  | SETOF SimpleTypename ARRAY

Constructors

Typename 

Fields

Instances

Instances details
Generic Typename Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep Typename :: Type -> Type #

Methods

from :: Typename -> Rep Typename x #

to :: Rep Typename x -> Typename #

Show Typename Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq Typename Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord Typename Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep Typename Source # 
Instance details

Defined in PostgresqlSyntax.Ast

data TypenameArrayDimensions Source #

References

Part of the Typename specification responsible for the choice between the following:
  | opt_array_bounds
  | ARRAY '[' Iconst ']'
  | ARRAY

Instances

Instances details
Generic TypenameArrayDimensions Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep TypenameArrayDimensions :: Type -> Type #

Show TypenameArrayDimensions Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq TypenameArrayDimensions Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord TypenameArrayDimensions Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep TypenameArrayDimensions Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep TypenameArrayDimensions = D1 ('MetaData "TypenameArrayDimensions" "PostgresqlSyntax.Ast" "postgresql-syntax-0.4.1.1-1agduNP8gtd9DXmzqkx25k" 'False) (C1 ('MetaCons "BoundsTypenameArrayDimensions" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ArrayBounds)) :+: C1 ('MetaCons "ExplicitTypenameArrayDimensions" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Iconst))))

type ArrayBounds = NonEmpty (Maybe Iconst) Source #

References

opt_array_bounds:
  | opt_array_bounds '[' ']'
  | opt_array_bounds '[' Iconst ']'
  | EMPTY

data SimpleTypename Source #

References

SimpleTypename:
  | GenericType
  | Numeric
  | Bit
  | Character
  | ConstDatetime
  | ConstInterval opt_interval
  | ConstInterval '(' Iconst ')'
ConstInterval:
  | INTERVAL

Instances

Instances details
Generic SimpleTypename Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep SimpleTypename :: Type -> Type #

Show SimpleTypename Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq SimpleTypename Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord SimpleTypename Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep SimpleTypename Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep SimpleTypename = D1 ('MetaData "SimpleTypename" "PostgresqlSyntax.Ast" "postgresql-syntax-0.4.1.1-1agduNP8gtd9DXmzqkx25k" 'False) ((C1 ('MetaCons "GenericTypeSimpleTypename" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 GenericType)) :+: (C1 ('MetaCons "NumericSimpleTypename" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Numeric)) :+: C1 ('MetaCons "BitSimpleTypename" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bit)))) :+: (C1 ('MetaCons "CharacterSimpleTypename" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Character)) :+: (C1 ('MetaCons "ConstDatetimeSimpleTypename" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ConstDatetime)) :+: C1 ('MetaCons "ConstIntervalSimpleTypename" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Either (Maybe Interval) Iconst))))))

data GenericType Source #

References

GenericType:
  | type_function_name opt_type_modifiers
  | type_function_name attrs opt_type_modifiers

Instances

Instances details
Generic GenericType Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep GenericType :: Type -> Type #

Show GenericType Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq GenericType Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord GenericType Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep GenericType Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Attrs = NonEmpty AttrName Source #

References

attrs:
  | . attr_name
  | attrs . attr_name

type AttrName = ColLabel Source #

References

attr_name:
  | ColLabel

type TypeModifiers = ExprList Source #

References

opt_type_modifiers:
  | '(' expr_list ')'
  | EMPTY

type TypeList = NonEmpty Typename Source #

References

type_list:
  | Typename
  | type_list ',' Typename

Operators

data QualOp Source #

References

qual_Op:
  | Op
  | OPERATOR '(' any_operator ')'

Instances

Instances details
Generic QualOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep QualOp :: Type -> Type #

Methods

from :: QualOp -> Rep QualOp x #

to :: Rep QualOp x -> QualOp #

Show QualOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq QualOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Methods

(==) :: QualOp -> QualOp -> Bool #

(/=) :: QualOp -> QualOp -> Bool #

Ord QualOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep QualOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep QualOp = D1 ('MetaData "QualOp" "PostgresqlSyntax.Ast" "postgresql-syntax-0.4.1.1-1agduNP8gtd9DXmzqkx25k" 'False) (C1 ('MetaCons "OpQualOp" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Op)) :+: C1 ('MetaCons "OperatorQualOp" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AnyOperator)))

data QualAllOp Source #

References

qual_all_Op:
  | all_Op
  | OPERATOR '(' any_operator ')'

Instances

Instances details
Generic QualAllOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep QualAllOp :: Type -> Type #

Show QualAllOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq QualAllOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord QualAllOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep QualAllOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep QualAllOp = D1 ('MetaData "QualAllOp" "PostgresqlSyntax.Ast" "postgresql-syntax-0.4.1.1-1agduNP8gtd9DXmzqkx25k" 'False) (C1 ('MetaCons "AllQualAllOp" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AllOp)) :+: C1 ('MetaCons "AnyQualAllOp" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AnyOperator)))

type Op = Text Source #

References

The operator name is a sequence of up to NAMEDATALEN-1 (63 by default)
characters from the following list:

+ - * /  = ~ !  # % ^ & | ` ?

There are a few restrictions on your choice of name:
-- and /* cannot appear anywhere in an operator name,
since they will be taken as the start of a comment.

A multicharacter operator name cannot end in + or -,
unless the name also contains at least one of these characters:

~ !  # % ^ & | ` ?

For example, @- is an allowed operator name, but *- is not.
This restriction allows PostgreSQL to parse SQL-compliant
commands without requiring spaces between tokens.
The use of => as an operator name is deprecated.
It may be disallowed altogether in a future release.

The operator != is mapped to <> on input,
so these two names are always equivalent.

data AnyOperator Source #

References

any_operator:
  | all_Op
  | ColId . any_operator

Instances

Instances details
Generic AnyOperator Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep AnyOperator :: Type -> Type #

Show AnyOperator Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq AnyOperator Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord AnyOperator Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep AnyOperator Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep AnyOperator = D1 ('MetaData "AnyOperator" "PostgresqlSyntax.Ast" "postgresql-syntax-0.4.1.1-1agduNP8gtd9DXmzqkx25k" 'False) (C1 ('MetaCons "AllOpAnyOperator" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AllOp)) :+: C1 ('MetaCons "QualifiedAnyOperator" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ColId) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AnyOperator)))

data AllOp Source #

References

all_Op:
  | Op
  | MathOp

Constructors

OpAllOp Op 
MathAllOp MathOp 

Instances

Instances details
Generic AllOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep AllOp :: Type -> Type #

Methods

from :: AllOp -> Rep AllOp x #

to :: Rep AllOp x -> AllOp #

Show AllOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Methods

showsPrec :: Int -> AllOp -> ShowS #

show :: AllOp -> String #

showList :: [AllOp] -> ShowS #

Eq AllOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Methods

(==) :: AllOp -> AllOp -> Bool #

(/=) :: AllOp -> AllOp -> Bool #

Ord AllOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Methods

compare :: AllOp -> AllOp -> Ordering #

(<) :: AllOp -> AllOp -> Bool #

(<=) :: AllOp -> AllOp -> Bool #

(>) :: AllOp -> AllOp -> Bool #

(>=) :: AllOp -> AllOp -> Bool #

max :: AllOp -> AllOp -> AllOp #

min :: AllOp -> AllOp -> AllOp #

type Rep AllOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep AllOp = D1 ('MetaData "AllOp" "PostgresqlSyntax.Ast" "postgresql-syntax-0.4.1.1-1agduNP8gtd9DXmzqkx25k" 'False) (C1 ('MetaCons "OpAllOp" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Op)) :+: C1 ('MetaCons "MathAllOp" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MathOp)))

data MathOp Source #

References

MathOp:
  | +
  | -
  | *
  | /
  | %
  | ^
  | <
  | >
  | '='
  | LESS_EQUALS
  | GREATER_EQUALS
  | NOT_EQUALS

Instances

Instances details
Bounded MathOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Enum MathOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic MathOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep MathOp :: Type -> Type #

Methods

from :: MathOp -> Rep MathOp x #

to :: Rep MathOp x -> MathOp #

Show MathOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq MathOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Methods

(==) :: MathOp -> MathOp -> Bool #

(/=) :: MathOp -> MathOp -> Bool #

Ord MathOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep MathOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep MathOp = D1 ('MetaData "MathOp" "PostgresqlSyntax.Ast" "postgresql-syntax-0.4.1.1-1agduNP8gtd9DXmzqkx25k" 'False) (((C1 ('MetaCons "PlusMathOp" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "MinusMathOp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AsteriskMathOp" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "SlashMathOp" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PercentMathOp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ArrowUpMathOp" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "ArrowLeftMathOp" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ArrowRightMathOp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EqualsMathOp" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "LessEqualsMathOp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GreaterEqualsMathOp" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ArrowLeftArrowRightMathOp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ExclamationEqualsMathOp" 'PrefixI 'False) (U1 :: Type -> Type)))))

data SymbolicExprBinOp Source #

Instances

Instances details
Generic SymbolicExprBinOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep SymbolicExprBinOp :: Type -> Type #

Show SymbolicExprBinOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq SymbolicExprBinOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord SymbolicExprBinOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep SymbolicExprBinOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep SymbolicExprBinOp = D1 ('MetaData "SymbolicExprBinOp" "PostgresqlSyntax.Ast" "postgresql-syntax-0.4.1.1-1agduNP8gtd9DXmzqkx25k" 'False) (C1 ('MetaCons "MathSymbolicExprBinOp" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MathOp)) :+: C1 ('MetaCons "QualSymbolicExprBinOp" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 QualOp)))

data VerbalExprBinOp Source #

Instances

Instances details
Bounded VerbalExprBinOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Enum VerbalExprBinOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic VerbalExprBinOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep VerbalExprBinOp :: Type -> Type #

Show VerbalExprBinOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq VerbalExprBinOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord VerbalExprBinOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep VerbalExprBinOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep VerbalExprBinOp = D1 ('MetaData "VerbalExprBinOp" "PostgresqlSyntax.Ast" "postgresql-syntax-0.4.1.1-1agduNP8gtd9DXmzqkx25k" 'False) (C1 ('MetaCons "LikeVerbalExprBinOp" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "IlikeVerbalExprBinOp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SimilarToVerbalExprBinOp" 'PrefixI 'False) (U1 :: Type -> Type)))

data AExprReversableOp Source #

References

  | a_expr IS NULL_P
  | a_expr IS TRUE_P
  | a_expr IS FALSE_P
  | a_expr IS UNKNOWN
  | a_expr IS DISTINCT FROM a_expr
  | a_expr IS OF '(' type_list ')'
  | a_expr BETWEEN opt_asymmetric b_expr AND a_expr
  | a_expr BETWEEN SYMMETRIC b_expr AND a_expr
  | a_expr IN_P in_expr
  | a_expr IS DOCUMENT_P

Instances

Instances details
Generic AExprReversableOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep AExprReversableOp :: Type -> Type #

Show AExprReversableOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq AExprReversableOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord AExprReversableOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep AExprReversableOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep AExprReversableOp = D1 ('MetaData "AExprReversableOp" "PostgresqlSyntax.Ast" "postgresql-syntax-0.4.1.1-1agduNP8gtd9DXmzqkx25k" 'False) (((C1 ('MetaCons "NullAExprReversableOp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TrueAExprReversableOp" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "FalseAExprReversableOp" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "UnknownAExprReversableOp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DistinctFromAExprReversableOp" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AExpr))))) :+: ((C1 ('MetaCons "OfAExprReversableOp" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TypeList)) :+: C1 ('MetaCons "BetweenAExprReversableOp" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BExpr) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AExpr)))) :+: (C1 ('MetaCons "BetweenSymmetricAExprReversableOp" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BExpr) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AExpr)) :+: (C1 ('MetaCons "InAExprReversableOp" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 InExpr)) :+: C1 ('MetaCons "DocumentAExprReversableOp" 'PrefixI 'False) (U1 :: Type -> Type)))))

data BExprIsOp Source #

References

  | b_expr IS DISTINCT FROM b_expr
  | b_expr IS NOT DISTINCT FROM b_expr
  | b_expr IS OF '(' type_list ')'
  | b_expr IS NOT OF '(' type_list ')'
  | b_expr IS DOCUMENT_P
  | b_expr IS NOT DOCUMENT_P

Instances

Instances details
Generic BExprIsOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep BExprIsOp :: Type -> Type #

Show BExprIsOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq BExprIsOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord BExprIsOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep BExprIsOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep BExprIsOp = D1 ('MetaData "BExprIsOp" "PostgresqlSyntax.Ast" "postgresql-syntax-0.4.1.1-1agduNP8gtd9DXmzqkx25k" 'False) (C1 ('MetaCons "DistinctFromBExprIsOp" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BExpr)) :+: (C1 ('MetaCons "OfBExprIsOp" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TypeList)) :+: C1 ('MetaCons "DocumentBExprIsOp" 'PrefixI 'False) (U1 :: Type -> Type)))

data SubqueryOp Source #

References

subquery_Op:
  | all_Op
  | OPERATOR '(' any_operator ')'
  | LIKE
  | NOT_LA LIKE
  | ILIKE
  | NOT_LA ILIKE

Instances

Instances details
Generic SubqueryOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep SubqueryOp :: Type -> Type #

Show SubqueryOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq SubqueryOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord SubqueryOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep SubqueryOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep SubqueryOp = D1 ('MetaData "SubqueryOp" "PostgresqlSyntax.Ast" "postgresql-syntax-0.4.1.1-1agduNP8gtd9DXmzqkx25k" 'False) ((C1 ('MetaCons "AllSubqueryOp" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AllOp)) :+: C1 ('MetaCons "AnySubqueryOp" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AnyOperator))) :+: (C1 ('MetaCons "LikeSubqueryOp" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)) :+: C1 ('MetaCons "IlikeSubqueryOp" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))))

Indexes

type IndexParams = NonEmpty IndexElem Source #

References

index_params:
  | index_elem
  | index_params ',' index_elem

data IndexElem Source #

References

index_elem:
  | ColId opt_collate opt_class opt_asc_desc opt_nulls_order
  | func_expr_windowless opt_collate opt_class opt_asc_desc opt_nulls_order
  | '(' a_expr ')' opt_collate opt_class opt_asc_desc opt_nulls_order

Instances

Instances details
Generic IndexElem Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep IndexElem :: Type -> Type #

Show IndexElem Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq IndexElem Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord IndexElem Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep IndexElem Source # 
Instance details

Defined in PostgresqlSyntax.Ast

data IndexElemDef Source #

References

  | ColId opt_collate opt_class opt_asc_desc opt_nulls_order
  | func_expr_windowless opt_collate opt_class opt_asc_desc opt_nulls_order
  | '(' a_expr ')' opt_collate opt_class opt_asc_desc opt_nulls_order

Instances

Instances details
Generic IndexElemDef Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep IndexElemDef :: Type -> Type #

Show IndexElemDef Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq IndexElemDef Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord IndexElemDef Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep IndexElemDef Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep IndexElemDef = D1 ('MetaData "IndexElemDef" "PostgresqlSyntax.Ast" "postgresql-syntax-0.4.1.1-1agduNP8gtd9DXmzqkx25k" 'False) (C1 ('MetaCons "IdIndexElemDef" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ColId)) :+: (C1 ('MetaCons "FuncIndexElemDef" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FuncExprWindowless)) :+: C1 ('MetaCons "ExprIndexElemDef" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AExpr))))

type Collate = AnyName Source #

References

opt_collate:
  | COLLATE any_name
  | EMPTY

type Class = AnyName Source #

References

opt_class:
  | any_name
  | EMPTY

data AscDesc Source #

References

opt_asc_desc:
  | ASC
  | DESC
  | EMPTY

Constructors

AscAscDesc 
DescAscDesc 

Instances

Instances details
Bounded AscDesc Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Enum AscDesc Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic AscDesc Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep AscDesc :: Type -> Type #

Methods

from :: AscDesc -> Rep AscDesc x #

to :: Rep AscDesc x -> AscDesc #

Show AscDesc Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq AscDesc Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Methods

(==) :: AscDesc -> AscDesc -> Bool #

(/=) :: AscDesc -> AscDesc -> Bool #

Ord AscDesc Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep AscDesc Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep AscDesc = D1 ('MetaData "AscDesc" "PostgresqlSyntax.Ast" "postgresql-syntax-0.4.1.1-1agduNP8gtd9DXmzqkx25k" 'False) (C1 ('MetaCons "AscAscDesc" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DescAscDesc" 'PrefixI 'False) (U1 :: Type -> Type))

data NullsOrder Source #

References

opt_nulls_order:
  | NULLS_LA FIRST_P
  | NULLS_LA LAST_P
  | EMPTY

Instances

Instances details
Bounded NullsOrder Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Enum NullsOrder Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic NullsOrder Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep NullsOrder :: Type -> Type #

Show NullsOrder Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Eq NullsOrder Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord NullsOrder Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep NullsOrder Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep NullsOrder = D1 ('MetaData "NullsOrder" "PostgresqlSyntax.Ast" "postgresql-syntax-0.4.1.1-1agduNP8gtd9DXmzqkx25k" 'False) (C1 ('MetaCons "FirstNullsOrder" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LastNullsOrder" 'PrefixI 'False) (U1 :: Type -> Type))