postgresql-syntax-0.3.0.3: PostgreSQL AST parsing and rendering

Safe HaskellNone
LanguageHaskell2010

PostgresqlSyntax.Ast

Contents

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 #

Instances
Eq PreparableStmt Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord PreparableStmt Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show PreparableStmt Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic PreparableStmt Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep PreparableStmt :: Type -> Type #

type Rep PreparableStmt Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Insert

data InsertStmt Source #

Instances
Eq InsertStmt Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord InsertStmt Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show InsertStmt Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic InsertStmt Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep InsertStmt :: Type -> Type #

type Rep InsertStmt Source # 
Instance details

Defined in PostgresqlSyntax.Ast

data InsertTarget Source #

Instances
Eq InsertTarget Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord InsertTarget Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show InsertTarget Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic InsertTarget Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep InsertTarget :: Type -> Type #

type Rep InsertTarget Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep InsertTarget = D1 (MetaData "InsertTarget" "PostgresqlSyntax.Ast" "postgresql-syntax-0.3.0.3-6W4EHkEby9aEZp0MA2bT4A" 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 #

Instances
Eq InsertRest Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord InsertRest Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show InsertRest Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic InsertRest Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep InsertRest :: Type -> Type #

type Rep InsertRest Source # 
Instance details

Defined in PostgresqlSyntax.Ast

data OverrideKind Source #

Instances
Bounded OverrideKind Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Enum 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

Show OverrideKind Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic OverrideKind Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep OverrideKind :: Type -> Type #

type Rep OverrideKind Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep OverrideKind = D1 (MetaData "OverrideKind" "PostgresqlSyntax.Ast" "postgresql-syntax-0.3.0.3-6W4EHkEby9aEZp0MA2bT4A" False) (C1 (MetaCons "UserOverrideKind" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "SystemOverrideKind" PrefixI False) (U1 :: Type -> Type))

data InsertColumnItem Source #

Instances
Eq InsertColumnItem Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord InsertColumnItem Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show InsertColumnItem Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic InsertColumnItem Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep InsertColumnItem :: Type -> Type #

type Rep InsertColumnItem Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep InsertColumnItem = D1 (MetaData "InsertColumnItem" "PostgresqlSyntax.Ast" "postgresql-syntax-0.3.0.3-6W4EHkEby9aEZp0MA2bT4A" 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 #

Instances
Eq OnConflict Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord OnConflict Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show OnConflict Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic OnConflict Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep OnConflict :: Type -> Type #

type Rep OnConflict Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep OnConflict = D1 (MetaData "OnConflict" "PostgresqlSyntax.Ast" "postgresql-syntax-0.3.0.3-6W4EHkEby9aEZp0MA2bT4A" 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 #

Instances
Eq OnConflictDo Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord OnConflictDo Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show OnConflictDo Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic OnConflictDo Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep OnConflictDo :: Type -> Type #

type Rep OnConflictDo Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep OnConflictDo = D1 (MetaData "OnConflictDo" "PostgresqlSyntax.Ast" "postgresql-syntax-0.3.0.3-6W4EHkEby9aEZp0MA2bT4A" 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 #

Instances
Eq ConfExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord ConfExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show ConfExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

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 #

type Rep ConfExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Update

data UpdateStmt Source #

Instances
Eq UpdateStmt Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord UpdateStmt Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show UpdateStmt Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic UpdateStmt Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep UpdateStmt :: Type -> Type #

type Rep UpdateStmt Source # 
Instance details

Defined in PostgresqlSyntax.Ast

data SetClause Source #

Instances
Eq SetClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord SetClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show SetClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic SetClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep SetClause :: Type -> Type #

type Rep SetClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

data SetTarget Source #

Instances
Eq SetTarget Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord SetTarget Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show SetTarget Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic SetTarget Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep SetTarget :: Type -> Type #

type Rep SetTarget Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep SetTarget = D1 (MetaData "SetTarget" "PostgresqlSyntax.Ast" "postgresql-syntax-0.3.0.3-6W4EHkEby9aEZp0MA2bT4A" 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))))

Delete

data DeleteStmt Source #

Instances
Eq DeleteStmt Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord DeleteStmt Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show DeleteStmt Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic DeleteStmt Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep DeleteStmt :: Type -> Type #

type Rep DeleteStmt Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Select

data SelectWithParens Source #

Instances
Eq SelectWithParens Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord SelectWithParens Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show SelectWithParens Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic SelectWithParens Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep SelectWithParens :: Type -> Type #

type Rep SelectWithParens Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep SelectWithParens = D1 (MetaData "SelectWithParens" "PostgresqlSyntax.Ast" "postgresql-syntax-0.3.0.3-6W4EHkEby9aEZp0MA2bT4A" 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
Eq SelectNoParens Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord SelectNoParens Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show SelectNoParens Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic SelectNoParens Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep SelectNoParens :: Type -> Type #

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 #

Instances
Eq SimpleSelect Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord SimpleSelect Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show SimpleSelect Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic SimpleSelect Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep SimpleSelect :: Type -> Type #

type Rep SimpleSelect Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep SimpleSelect = D1 (MetaData "SimpleSelect" "PostgresqlSyntax.Ast" "postgresql-syntax-0.3.0.3-6W4EHkEby9aEZp0MA2bT4A" 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:

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
Eq Targeting Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord Targeting Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show Targeting Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic Targeting Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep Targeting :: Type -> Type #

type Rep Targeting Source # 
Instance details

Defined in PostgresqlSyntax.Ast

data TargetEl Source #

Instances
Eq TargetEl Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord TargetEl Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show TargetEl Source # 
Instance details

Defined in PostgresqlSyntax.Ast

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 #

type Rep TargetEl Source # 
Instance details

Defined in PostgresqlSyntax.Ast

data SelectBinOp Source #

Instances
Eq SelectBinOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord SelectBinOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show SelectBinOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic SelectBinOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep SelectBinOp :: Type -> Type #

type Rep SelectBinOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep SelectBinOp = D1 (MetaData "SelectBinOp" "PostgresqlSyntax.Ast" "postgresql-syntax-0.3.0.3-6W4EHkEby9aEZp0MA2bT4A" 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 #

Instances
Eq WithClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord WithClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show WithClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic WithClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep WithClause :: Type -> Type #

type Rep WithClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep WithClause = D1 (MetaData "WithClause" "PostgresqlSyntax.Ast" "postgresql-syntax-0.3.0.3-6W4EHkEby9aEZp0MA2bT4A" 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 #

Instances
Eq CommonTableExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord CommonTableExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show CommonTableExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic CommonTableExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep CommonTableExpr :: Type -> Type #

type Rep CommonTableExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

data OptTempTableName Source #

Instances
Eq OptTempTableName Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord OptTempTableName Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show OptTempTableName Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic OptTempTableName Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep OptTempTableName :: Type -> Type #

type Rep OptTempTableName Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep OptTempTableName = D1 (MetaData "OptTempTableName" "PostgresqlSyntax.Ast" "postgresql-syntax-0.3.0.3-6W4EHkEby9aEZp0MA2bT4A" 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 #

Instances
Eq GroupByItem Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord GroupByItem Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show GroupByItem Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic GroupByItem Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep GroupByItem :: Type -> Type #

type Rep GroupByItem Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep GroupByItem = D1 (MetaData "GroupByItem" "PostgresqlSyntax.Ast" "postgresql-syntax-0.3.0.3-6W4EHkEby9aEZp0MA2bT4A" 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
Eq WindowDefinition Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord WindowDefinition Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show WindowDefinition Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic WindowDefinition Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep WindowDefinition :: Type -> Type #

type Rep WindowDefinition Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep WindowDefinition = D1 (MetaData "WindowDefinition" "PostgresqlSyntax.Ast" "postgresql-syntax-0.3.0.3-6W4EHkEby9aEZp0MA2bT4A" 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
Eq WindowSpecification Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord WindowSpecification Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show WindowSpecification Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic WindowSpecification Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep WindowSpecification :: Type -> Type #

type Rep WindowSpecification Source # 
Instance details

Defined in PostgresqlSyntax.Ast

data FrameClause Source #

Instances
Eq FrameClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord FrameClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show FrameClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic FrameClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep FrameClause :: Type -> Type #

type Rep FrameClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

data FrameClauseMode Source #

Instances
Eq FrameClauseMode Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord FrameClauseMode Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show FrameClauseMode Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic FrameClauseMode Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep FrameClauseMode :: Type -> Type #

type Rep FrameClauseMode Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep FrameClauseMode = D1 (MetaData "FrameClauseMode" "PostgresqlSyntax.Ast" "postgresql-syntax-0.3.0.3-6W4EHkEby9aEZp0MA2bT4A" 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 #

Instances
Eq FrameExtent Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord FrameExtent Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show FrameExtent Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic FrameExtent Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep FrameExtent :: Type -> Type #

type Rep FrameExtent Source # 
Instance details

Defined in PostgresqlSyntax.Ast

data FrameBound Source #

Instances
Eq FrameBound Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord FrameBound Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show FrameBound Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic FrameBound Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep FrameBound :: Type -> Type #

type Rep FrameBound Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep FrameBound = D1 (MetaData "FrameBound" "PostgresqlSyntax.Ast" "postgresql-syntax-0.3.0.3-6W4EHkEby9aEZp0MA2bT4A" 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 #

Instances
Eq WindowExclusionClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord WindowExclusionClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show WindowExclusionClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic WindowExclusionClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep WindowExclusionClause :: Type -> Type #

type Rep WindowExclusionClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep WindowExclusionClause = D1 (MetaData "WindowExclusionClause" "PostgresqlSyntax.Ast" "postgresql-syntax-0.3.0.3-6W4EHkEby9aEZp0MA2bT4A" 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 SortClause = NonEmpty SortBy Source #

sort_clause: | ORDER BY sortby_list

sortby_list: | sortby | sortby_list ',' sortby

data SortBy Source #

Instances
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

Show SortBy Source # 
Instance details

Defined in PostgresqlSyntax.Ast

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 #

type Rep SortBy Source # 
Instance details

Defined in PostgresqlSyntax.Ast

data SelectLimit Source #

Instances
Eq SelectLimit Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord SelectLimit Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show SelectLimit Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic SelectLimit Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep SelectLimit :: Type -> Type #

type Rep SelectLimit Source # 
Instance details

Defined in PostgresqlSyntax.Ast

data LimitClause Source #

Instances
Eq LimitClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord LimitClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show LimitClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic LimitClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep LimitClause :: Type -> Type #

type Rep LimitClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

data SelectFetchFirstValue Source #

Instances
Eq SelectFetchFirstValue Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord SelectFetchFirstValue Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show SelectFetchFirstValue Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic SelectFetchFirstValue Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep SelectFetchFirstValue :: Type -> Type #

type Rep SelectFetchFirstValue Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep SelectFetchFirstValue = D1 (MetaData "SelectFetchFirstValue" "PostgresqlSyntax.Ast" "postgresql-syntax-0.3.0.3-6W4EHkEby9aEZp0MA2bT4A" 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 #

Instances
Eq SelectLimitValue Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord SelectLimitValue Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show SelectLimitValue Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic SelectLimitValue Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep SelectLimitValue :: Type -> Type #

type Rep SelectLimitValue Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep SelectLimitValue = D1 (MetaData "SelectLimitValue" "PostgresqlSyntax.Ast" "postgresql-syntax-0.3.0.3-6W4EHkEby9aEZp0MA2bT4A" 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 #

Instances
Eq OffsetClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord OffsetClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show OffsetClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic OffsetClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep OffsetClause :: Type -> Type #

type Rep OffsetClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

For Locking

data ForLockingClause Source #

Instances
Eq ForLockingClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord ForLockingClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show ForLockingClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic ForLockingClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep ForLockingClause :: Type -> Type #

type Rep ForLockingClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep ForLockingClause = D1 (MetaData "ForLockingClause" "PostgresqlSyntax.Ast" "postgresql-syntax-0.3.0.3-6W4EHkEby9aEZp0MA2bT4A" 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 #

Instances
Eq ForLockingItem Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord ForLockingItem Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show ForLockingItem Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic ForLockingItem Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep ForLockingItem :: Type -> Type #

type Rep ForLockingItem Source # 
Instance details

Defined in PostgresqlSyntax.Ast

data ForLockingStrength Source #

Instances
Eq ForLockingStrength Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord ForLockingStrength Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show ForLockingStrength Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic ForLockingStrength Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep ForLockingStrength :: Type -> Type #

type Rep ForLockingStrength Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep ForLockingStrength = D1 (MetaData "ForLockingStrength" "PostgresqlSyntax.Ast" "postgresql-syntax-0.3.0.3-6W4EHkEby9aEZp0MA2bT4A" 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

data TableRef Source #

Instances
Eq TableRef Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord TableRef Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show TableRef Source # 
Instance details

Defined in PostgresqlSyntax.Ast

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 #

type Rep TableRef Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep TableRef = D1 (MetaData "TableRef" "PostgresqlSyntax.Ast" "postgresql-syntax-0.3.0.3-6W4EHkEby9aEZp0MA2bT4A" 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 #

Instances
Eq RelationExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord RelationExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show RelationExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic RelationExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep RelationExpr :: Type -> Type #

type Rep RelationExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

data RelationExprOptAlias Source #

Instances
Eq RelationExprOptAlias Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord RelationExprOptAlias Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show RelationExprOptAlias Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic RelationExprOptAlias Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep RelationExprOptAlias :: Type -> Type #

type Rep RelationExprOptAlias Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep RelationExprOptAlias = D1 (MetaData "RelationExprOptAlias" "PostgresqlSyntax.Ast" "postgresql-syntax-0.3.0.3-6W4EHkEby9aEZp0MA2bT4A" 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 #

Instances
Eq TablesampleClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord TablesampleClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show TablesampleClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic TablesampleClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep TablesampleClause :: Type -> Type #

type Rep TablesampleClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

data FuncTable Source #

Instances
Eq FuncTable Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord FuncTable Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show FuncTable Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic FuncTable Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep FuncTable :: Type -> Type #

type Rep FuncTable Source # 
Instance details

Defined in PostgresqlSyntax.Ast

data RowsfromItem Source #

Instances
Eq RowsfromItem Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord RowsfromItem Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show RowsfromItem Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic RowsfromItem Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep RowsfromItem :: Type -> Type #

type Rep RowsfromItem Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep RowsfromItem = D1 (MetaData "RowsfromItem" "PostgresqlSyntax.Ast" "postgresql-syntax-0.3.0.3-6W4EHkEby9aEZp0MA2bT4A" 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))))

data TableFuncElement Source #

Instances
Eq TableFuncElement Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord TableFuncElement Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show TableFuncElement Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic TableFuncElement Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep TableFuncElement :: Type -> Type #

type Rep TableFuncElement Source # 
Instance details

Defined in PostgresqlSyntax.Ast

data AliasClause Source #

Instances
Eq AliasClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord AliasClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show AliasClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic AliasClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep AliasClause :: Type -> Type #

type Rep AliasClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

data FuncAliasClause Source #

Instances
Eq FuncAliasClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord FuncAliasClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show FuncAliasClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic FuncAliasClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep FuncAliasClause :: Type -> Type #

type Rep FuncAliasClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

data JoinedTable Source #

Instances
Eq JoinedTable Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord JoinedTable Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show JoinedTable Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic JoinedTable Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep JoinedTable :: Type -> Type #

type Rep JoinedTable Source # 
Instance details

Defined in PostgresqlSyntax.Ast

data JoinMeth Source #

Instances
Eq JoinMeth Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord JoinMeth Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show JoinMeth Source # 
Instance details

Defined in PostgresqlSyntax.Ast

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 #

type Rep JoinMeth Source # 
Instance details

Defined in PostgresqlSyntax.Ast

data JoinType Source #

Instances
Eq JoinType Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord JoinType Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show JoinType Source # 
Instance details

Defined in PostgresqlSyntax.Ast

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 #

type Rep JoinType Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep JoinType = D1 (MetaData "JoinType" "PostgresqlSyntax.Ast" "postgresql-syntax-0.3.0.3-6W4EHkEby9aEZp0MA2bT4A" 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 #

Instances
Eq JoinQual Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord JoinQual Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show JoinQual Source # 
Instance details

Defined in PostgresqlSyntax.Ast

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 #

type Rep JoinQual Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep JoinQual = D1 (MetaData "JoinQual" "PostgresqlSyntax.Ast" "postgresql-syntax-0.3.0.3-6W4EHkEby9aEZp0MA2bT4A" 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 #

Instances
Eq WhereOrCurrentClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord WhereOrCurrentClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show WhereOrCurrentClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic WhereOrCurrentClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep WhereOrCurrentClause :: Type -> Type #

type Rep WhereOrCurrentClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep WhereOrCurrentClause = D1 (MetaData "WhereOrCurrentClause" "PostgresqlSyntax.Ast" "postgresql-syntax-0.3.0.3-6W4EHkEby9aEZp0MA2bT4A" 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 #

Instances
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 #

Show AExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Methods

showsPrec :: Int -> AExpr -> ShowS #

show :: AExpr -> String #

showList :: [AExpr] -> ShowS #

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 #

type Rep AExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep AExpr = D1 (MetaData "AExpr" "PostgresqlSyntax.Ast" "postgresql-syntax-0.3.0.3-6W4EHkEby9aEZp0MA2bT4A" 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 #

Instances
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 #

Show BExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Methods

showsPrec :: Int -> BExpr -> ShowS #

show :: BExpr -> String #

showList :: [BExpr] -> ShowS #

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 #

type Rep BExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep BExpr = D1 (MetaData "BExpr" "PostgresqlSyntax.Ast" "postgresql-syntax-0.3.0.3-6W4EHkEby9aEZp0MA2bT4A" 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 #

Instances
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 #

Show CExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Methods

showsPrec :: Int -> CExpr -> ShowS #

show :: CExpr -> String #

showList :: [CExpr] -> ShowS #

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 #

type Rep CExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep CExpr = D1 (MetaData "CExpr" "PostgresqlSyntax.Ast" "postgresql-syntax-0.3.0.3-6W4EHkEby9aEZp0MA2bT4A" 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 #

Instances
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

Show InExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

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 #

type Rep InExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep InExpr = D1 (MetaData "InExpr" "PostgresqlSyntax.Ast" "postgresql-syntax-0.3.0.3-6W4EHkEby9aEZp0MA2bT4A" 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 #

Instances
Bounded SubType Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Enum 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

Show 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 #

type Rep SubType Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep SubType = D1 (MetaData "SubType" "PostgresqlSyntax.Ast" "postgresql-syntax-0.3.0.3-6W4EHkEby9aEZp0MA2bT4A" 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 #

Instances
Eq ArrayExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord ArrayExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show ArrayExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic ArrayExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep ArrayExpr :: Type -> Type #

type Rep ArrayExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep ArrayExpr = D1 (MetaData "ArrayExpr" "PostgresqlSyntax.Ast" "postgresql-syntax-0.3.0.3-6W4EHkEby9aEZp0MA2bT4A" 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)))

data Row Source #

Instances
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 #

Show Row Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Methods

showsPrec :: Int -> Row -> ShowS #

show :: Row -> String #

showList :: [Row] -> ShowS #

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 #

type Rep Row Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep Row = D1 (MetaData "Row" "PostgresqlSyntax.Ast" "postgresql-syntax-0.3.0.3-6W4EHkEby9aEZp0MA2bT4A" 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)))

data ImplicitRow Source #

Constructors

ImplicitRow ExprList AExpr 

data FuncExpr Source #

Instances
Eq FuncExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord FuncExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show FuncExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

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 #

type Rep FuncExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

data FuncExprWindowless Source #

Instances
Eq FuncExprWindowless Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord FuncExprWindowless Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show FuncExprWindowless Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic FuncExprWindowless Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep FuncExprWindowless :: Type -> Type #

type Rep FuncExprWindowless Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep FuncExprWindowless = D1 (MetaData "FuncExprWindowless" "PostgresqlSyntax.Ast" "postgresql-syntax-0.3.0.3-6W4EHkEby9aEZp0MA2bT4A" 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)))

data OverClause Source #

Instances
Eq OverClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord OverClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show OverClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic OverClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep OverClause :: Type -> Type #

type Rep OverClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep OverClause = D1 (MetaData "OverClause" "PostgresqlSyntax.Ast" "postgresql-syntax-0.3.0.3-6W4EHkEby9aEZp0MA2bT4A" 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 #

Instances
Eq FuncExprCommonSubexpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord FuncExprCommonSubexpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show FuncExprCommonSubexpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic FuncExprCommonSubexpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep FuncExprCommonSubexpr :: Type -> Type #

type Rep FuncExprCommonSubexpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep FuncExprCommonSubexpr = D1 (MetaData "FuncExprCommonSubexpr" "PostgresqlSyntax.Ast" "postgresql-syntax-0.3.0.3-6W4EHkEby9aEZp0MA2bT4A" 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 #

data ExtractArg Source #

Instances
Eq ExtractArg Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord ExtractArg Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show ExtractArg Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic ExtractArg Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep ExtractArg :: Type -> Type #

type Rep ExtractArg Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep ExtractArg = D1 (MetaData "ExtractArg" "PostgresqlSyntax.Ast" "postgresql-syntax-0.3.0.3-6W4EHkEby9aEZp0MA2bT4A" 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 #

Instances
Eq OverlayList Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord OverlayList Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show OverlayList Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic OverlayList Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep OverlayList :: Type -> Type #

type Rep OverlayList Source # 
Instance details

Defined in PostgresqlSyntax.Ast

data PositionList Source #

Constructors

PositionList BExpr BExpr 
Instances
Eq PositionList Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord PositionList Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show PositionList Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic PositionList Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep PositionList :: Type -> Type #

type Rep PositionList Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep PositionList = D1 (MetaData "PositionList" "PostgresqlSyntax.Ast" "postgresql-syntax-0.3.0.3-6W4EHkEby9aEZp0MA2bT4A" 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 #

Instances
Eq SubstrList Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord SubstrList Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show SubstrList Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic SubstrList Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep SubstrList :: Type -> Type #

type Rep SubstrList Source # 
Instance details

Defined in PostgresqlSyntax.Ast

data SubstrListFromFor Source #

Instances
Eq SubstrListFromFor Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord SubstrListFromFor Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show SubstrListFromFor Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic SubstrListFromFor Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep SubstrListFromFor :: Type -> Type #

type Rep SubstrListFromFor Source # 
Instance details

Defined in PostgresqlSyntax.Ast

data TrimModifier Source #

Instances
Bounded TrimModifier Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Enum 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

Show TrimModifier Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic TrimModifier Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep TrimModifier :: Type -> Type #

type Rep TrimModifier Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep TrimModifier = D1 (MetaData "TrimModifier" "PostgresqlSyntax.Ast" "postgresql-syntax-0.3.0.3-6W4EHkEby9aEZp0MA2bT4A" 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 #

Instances
Eq TrimList Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord TrimList Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show TrimList Source # 
Instance details

Defined in PostgresqlSyntax.Ast

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 #

type Rep TrimList Source # 
Instance details

Defined in PostgresqlSyntax.Ast

data CaseExpr Source #

Instances
Eq CaseExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord CaseExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show CaseExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

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 #

type Rep CaseExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

data WhenClause Source #

Constructors

WhenClause AExpr AExpr 
Instances
Eq WhenClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord WhenClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show WhenClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic WhenClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep WhenClause :: Type -> Type #

type Rep WhenClause Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep WhenClause = D1 (MetaData "WhenClause" "PostgresqlSyntax.Ast" "postgresql-syntax-0.3.0.3-6W4EHkEby9aEZp0MA2bT4A" 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 #

Instances
Eq FuncApplication Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord FuncApplication Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show FuncApplication Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic FuncApplication Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep FuncApplication :: Type -> Type #

type Rep FuncApplication Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep FuncApplication = D1 (MetaData "FuncApplication" "PostgresqlSyntax.Ast" "postgresql-syntax-0.3.0.3-6W4EHkEby9aEZp0MA2bT4A" 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 #

Instances
Eq FuncApplicationParams Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord FuncApplicationParams Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show FuncApplicationParams Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic FuncApplicationParams Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep FuncApplicationParams :: Type -> Type #

type Rep FuncApplicationParams Source # 
Instance details

Defined in PostgresqlSyntax.Ast

data FuncArgExpr Source #

Instances
Eq FuncArgExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord FuncArgExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show FuncArgExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic FuncArgExpr Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep FuncArgExpr :: Type -> Type #

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
Eq AexprConst Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord AexprConst Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show AexprConst Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic AexprConst Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep AexprConst :: Type -> Type #

type Rep AexprConst Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep AexprConst = D1 (MetaData "AexprConst" "PostgresqlSyntax.Ast" "postgresql-syntax-0.3.0.3-6W4EHkEby9aEZp0MA2bT4A" 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 #

Instances
Eq FuncConstArgs Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord FuncConstArgs Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show FuncConstArgs Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic FuncConstArgs Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep FuncConstArgs :: Type -> Type #

type Rep FuncConstArgs Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep FuncConstArgs = D1 (MetaData "FuncConstArgs" "PostgresqlSyntax.Ast" "postgresql-syntax-0.3.0.3-6W4EHkEby9aEZp0MA2bT4A" 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 #

Instances
Eq ConstTypename Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord ConstTypename Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show ConstTypename Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic ConstTypename Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep ConstTypename :: Type -> Type #

type Rep ConstTypename Source # 
Instance details

Defined in PostgresqlSyntax.Ast

data Numeric Source #

Instances
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

Show Numeric Source # 
Instance details

Defined in PostgresqlSyntax.Ast

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 #

type Rep Numeric Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep Numeric = D1 (MetaData "Numeric" "PostgresqlSyntax.Ast" "postgresql-syntax-0.3.0.3-6W4EHkEby9aEZp0MA2bT4A" 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 #

Constructors

Bit OptVarying (Maybe ExprList) 
Instances
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 #

Show Bit Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Methods

showsPrec :: Int -> Bit -> ShowS #

show :: Bit -> String #

showList :: [Bit] -> ShowS #

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 #

type Rep Bit Source # 
Instance details

Defined in PostgresqlSyntax.Ast

data ConstCharacter Source #

Instances
Eq ConstCharacter Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord ConstCharacter Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show ConstCharacter Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic ConstCharacter Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep ConstCharacter :: Type -> Type #

type Rep ConstCharacter Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep ConstCharacter = D1 (MetaData "ConstCharacter" "PostgresqlSyntax.Ast" "postgresql-syntax-0.3.0.3-6W4EHkEby9aEZp0MA2bT4A" 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 #

Instances
Eq Character Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord Character Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show Character Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic Character Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep Character :: Type -> Type #

type Rep Character Source # 
Instance details

Defined in PostgresqlSyntax.Ast

data ConstDatetime Source #

Instances
Eq ConstDatetime Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord ConstDatetime Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show ConstDatetime Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic ConstDatetime Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep ConstDatetime :: Type -> Type #

type Rep ConstDatetime Source # 
Instance details

Defined in PostgresqlSyntax.Ast

data Interval Source #

Instances
Eq Interval Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord Interval Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show Interval Source # 
Instance details

Defined in PostgresqlSyntax.Ast

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 #

type Rep Interval Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep Interval = D1 (MetaData "Interval" "PostgresqlSyntax.Ast" "postgresql-syntax-0.3.0.3-6W4EHkEby9aEZp0MA2bT4A" 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))))))

Names & References

data Ident Source #

Instances
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 #

Show Ident Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Methods

showsPrec :: Int -> Ident -> ShowS #

show :: Ident -> String #

showList :: [Ident] -> ShowS #

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 #

type Rep Ident Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep Ident = D1 (MetaData "Ident" "PostgresqlSyntax.Ast" "postgresql-syntax-0.3.0.3-6W4EHkEby9aEZp0MA2bT4A" 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)))

data Columnref Source #

Instances
Eq Columnref Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord Columnref Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show Columnref Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic Columnref Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep Columnref :: Type -> Type #

type Rep Columnref Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep Columnref = D1 (MetaData "Columnref" "PostgresqlSyntax.Ast" "postgresql-syntax-0.3.0.3-6W4EHkEby9aEZp0MA2bT4A" 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 #

Constructors

AnyName ColId (Maybe Attrs) 
Instances
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

Show AnyName Source # 
Instance details

Defined in PostgresqlSyntax.Ast

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 #

type Rep AnyName Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep AnyName = D1 (MetaData "AnyName" "PostgresqlSyntax.Ast" "postgresql-syntax-0.3.0.3-6W4EHkEby9aEZp0MA2bT4A" 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 #

Instances
Eq FuncName Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord FuncName Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show FuncName Source # 
Instance details

Defined in PostgresqlSyntax.Ast

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 #

type Rep FuncName Source # 
Instance details

Defined in PostgresqlSyntax.Ast

data QualifiedName Source #

Instances
Eq QualifiedName Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord QualifiedName Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show QualifiedName Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic QualifiedName Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep QualifiedName :: Type -> Type #

type Rep QualifiedName Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep QualifiedName = D1 (MetaData "QualifiedName" "PostgresqlSyntax.Ast" "postgresql-syntax-0.3.0.3-6W4EHkEby9aEZp0MA2bT4A" 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)))

data IndirectionEl Source #

Instances
Eq IndirectionEl Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord IndirectionEl Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show IndirectionEl Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic IndirectionEl Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep IndirectionEl :: Type -> Type #

type Rep IndirectionEl Source # 
Instance details

Defined in PostgresqlSyntax.Ast

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.

Constructors

Typename 

Fields

Instances
Eq Typename Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord Typename Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show Typename Source # 
Instance details

Defined in PostgresqlSyntax.Ast

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 #

type Rep Typename Source # 
Instance details

Defined in PostgresqlSyntax.Ast

data TypenameArrayDimensions Source #

Instances
Eq TypenameArrayDimensions Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord TypenameArrayDimensions Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show TypenameArrayDimensions Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic TypenameArrayDimensions Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep TypenameArrayDimensions :: Type -> Type #

type Rep TypenameArrayDimensions Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep TypenameArrayDimensions = D1 (MetaData "TypenameArrayDimensions" "PostgresqlSyntax.Ast" "postgresql-syntax-0.3.0.3-6W4EHkEby9aEZp0MA2bT4A" 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))))

data SimpleTypename Source #

Instances
Eq SimpleTypename Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord SimpleTypename Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show SimpleTypename Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic SimpleTypename Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep SimpleTypename :: Type -> Type #

type Rep SimpleTypename Source # 
Instance details

Defined in PostgresqlSyntax.Ast

data GenericType Source #

Instances
Eq GenericType Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord GenericType Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show GenericType Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic GenericType Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep GenericType :: Type -> Type #

type Rep GenericType Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Operators

data QualOp Source #

Instances
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

Show QualOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

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 #

type Rep QualOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep QualOp = D1 (MetaData "QualOp" "PostgresqlSyntax.Ast" "postgresql-syntax-0.3.0.3-6W4EHkEby9aEZp0MA2bT4A" 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 #

Instances
Eq QualAllOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord QualAllOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show QualAllOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic QualAllOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep QualAllOp :: Type -> Type #

type Rep QualAllOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep QualAllOp = D1 (MetaData "QualAllOp" "PostgresqlSyntax.Ast" "postgresql-syntax-0.3.0.3-6W4EHkEby9aEZp0MA2bT4A" 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 #

data AnyOperator Source #

Instances
Eq AnyOperator Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord AnyOperator Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show AnyOperator Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic AnyOperator Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep AnyOperator :: Type -> Type #

type Rep AnyOperator Source # 
Instance details

Defined in PostgresqlSyntax.Ast

data AllOp Source #

Constructors

OpAllOp Op 
MathAllOp MathOp 
Instances
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 #

Show AllOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Methods

showsPrec :: Int -> AllOp -> ShowS #

show :: AllOp -> String #

showList :: [AllOp] -> ShowS #

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 #

type Rep AllOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep AllOp = D1 (MetaData "AllOp" "PostgresqlSyntax.Ast" "postgresql-syntax-0.3.0.3-6W4EHkEby9aEZp0MA2bT4A" 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 #

Instances
Bounded MathOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Enum 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

Show 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 #

type Rep MathOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep MathOp = D1 (MetaData "MathOp" "PostgresqlSyntax.Ast" "postgresql-syntax-0.3.0.3-6W4EHkEby9aEZp0MA2bT4A" 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
Eq SymbolicExprBinOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord SymbolicExprBinOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show SymbolicExprBinOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic SymbolicExprBinOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep SymbolicExprBinOp :: Type -> Type #

type Rep SymbolicExprBinOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep SymbolicExprBinOp = D1 (MetaData "SymbolicExprBinOp" "PostgresqlSyntax.Ast" "postgresql-syntax-0.3.0.3-6W4EHkEby9aEZp0MA2bT4A" 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
Bounded VerbalExprBinOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Enum 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

Show VerbalExprBinOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic VerbalExprBinOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep VerbalExprBinOp :: Type -> Type #

type Rep VerbalExprBinOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep VerbalExprBinOp = D1 (MetaData "VerbalExprBinOp" "PostgresqlSyntax.Ast" "postgresql-syntax-0.3.0.3-6W4EHkEby9aEZp0MA2bT4A" 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 #

Instances
Eq AExprReversableOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord AExprReversableOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show AExprReversableOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic AExprReversableOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep AExprReversableOp :: Type -> Type #

type Rep AExprReversableOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep AExprReversableOp = D1 (MetaData "AExprReversableOp" "PostgresqlSyntax.Ast" "postgresql-syntax-0.3.0.3-6W4EHkEby9aEZp0MA2bT4A" 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 #

Instances
Eq BExprIsOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord BExprIsOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show BExprIsOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic BExprIsOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep BExprIsOp :: Type -> Type #

type Rep BExprIsOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep BExprIsOp = D1 (MetaData "BExprIsOp" "PostgresqlSyntax.Ast" "postgresql-syntax-0.3.0.3-6W4EHkEby9aEZp0MA2bT4A" 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 #

Instances
Eq SubqueryOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord SubqueryOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show SubqueryOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic SubqueryOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep SubqueryOp :: Type -> Type #

type Rep SubqueryOp Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Indexes

data IndexElem Source #

Instances
Eq IndexElem Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord IndexElem Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show IndexElem Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic IndexElem Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep IndexElem :: Type -> Type #

type Rep IndexElem Source # 
Instance details

Defined in PostgresqlSyntax.Ast

data IndexElemDef Source #

Instances
Eq IndexElemDef Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Ord IndexElemDef Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Show IndexElemDef Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic IndexElemDef Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep IndexElemDef :: Type -> Type #

type Rep IndexElemDef Source # 
Instance details

Defined in PostgresqlSyntax.Ast

data AscDesc Source #

Constructors

AscAscDesc 
DescAscDesc 
Instances
Bounded AscDesc Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Enum 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

Show 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 #

type Rep AscDesc Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep AscDesc = D1 (MetaData "AscDesc" "PostgresqlSyntax.Ast" "postgresql-syntax-0.3.0.3-6W4EHkEby9aEZp0MA2bT4A" False) (C1 (MetaCons "AscAscDesc" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "DescAscDesc" PrefixI False) (U1 :: Type -> Type))

data NullsOrder Source #

Instances
Bounded NullsOrder Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Enum 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

Show NullsOrder Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Generic NullsOrder Source # 
Instance details

Defined in PostgresqlSyntax.Ast

Associated Types

type Rep NullsOrder :: Type -> Type #

type Rep NullsOrder Source # 
Instance details

Defined in PostgresqlSyntax.Ast

type Rep NullsOrder = D1 (MetaData "NullsOrder" "PostgresqlSyntax.Ast" "postgresql-syntax-0.3.0.3-6W4EHkEby9aEZp0MA2bT4A" False) (C1 (MetaCons "FirstNullsOrder" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "LastNullsOrder" PrefixI False) (U1 :: Type -> Type))