-- |
-- 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.
module PostgresqlSyntax.Ast where

import PostgresqlSyntax.Prelude hiding (Op, Order)

-- * Statement

-- |
-- ==== References
-- @
-- PreparableStmt:
--   |  SelectStmt
--   |  InsertStmt
--   |  UpdateStmt
--   |  DeleteStmt
--   |  CallStmt
-- @
data PreparableStmt
  = SelectPreparableStmt SelectStmt
  | InsertPreparableStmt InsertStmt
  | UpdatePreparableStmt UpdateStmt
  | DeletePreparableStmt DeleteStmt
  | CallPreparableStmt CallStmt
  deriving (Int -> PreparableStmt -> ShowS
[PreparableStmt] -> ShowS
PreparableStmt -> String
(Int -> PreparableStmt -> ShowS)
-> (PreparableStmt -> String)
-> ([PreparableStmt] -> ShowS)
-> Show PreparableStmt
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PreparableStmt] -> ShowS
$cshowList :: [PreparableStmt] -> ShowS
show :: PreparableStmt -> String
$cshow :: PreparableStmt -> String
showsPrec :: Int -> PreparableStmt -> ShowS
$cshowsPrec :: Int -> PreparableStmt -> ShowS
Show, (forall x. PreparableStmt -> Rep PreparableStmt x)
-> (forall x. Rep PreparableStmt x -> PreparableStmt)
-> Generic PreparableStmt
forall x. Rep PreparableStmt x -> PreparableStmt
forall x. PreparableStmt -> Rep PreparableStmt x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PreparableStmt x -> PreparableStmt
$cfrom :: forall x. PreparableStmt -> Rep PreparableStmt x
Generic, PreparableStmt -> PreparableStmt -> Bool
(PreparableStmt -> PreparableStmt -> Bool)
-> (PreparableStmt -> PreparableStmt -> Bool) -> Eq PreparableStmt
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PreparableStmt -> PreparableStmt -> Bool
$c/= :: PreparableStmt -> PreparableStmt -> Bool
== :: PreparableStmt -> PreparableStmt -> Bool
$c== :: PreparableStmt -> PreparableStmt -> Bool
Eq, Eq PreparableStmt
Eq PreparableStmt
-> (PreparableStmt -> PreparableStmt -> Ordering)
-> (PreparableStmt -> PreparableStmt -> Bool)
-> (PreparableStmt -> PreparableStmt -> Bool)
-> (PreparableStmt -> PreparableStmt -> Bool)
-> (PreparableStmt -> PreparableStmt -> Bool)
-> (PreparableStmt -> PreparableStmt -> PreparableStmt)
-> (PreparableStmt -> PreparableStmt -> PreparableStmt)
-> Ord PreparableStmt
PreparableStmt -> PreparableStmt -> Bool
PreparableStmt -> PreparableStmt -> Ordering
PreparableStmt -> PreparableStmt -> PreparableStmt
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: PreparableStmt -> PreparableStmt -> PreparableStmt
$cmin :: PreparableStmt -> PreparableStmt -> PreparableStmt
max :: PreparableStmt -> PreparableStmt -> PreparableStmt
$cmax :: PreparableStmt -> PreparableStmt -> PreparableStmt
>= :: PreparableStmt -> PreparableStmt -> Bool
$c>= :: PreparableStmt -> PreparableStmt -> Bool
> :: PreparableStmt -> PreparableStmt -> Bool
$c> :: PreparableStmt -> PreparableStmt -> Bool
<= :: PreparableStmt -> PreparableStmt -> Bool
$c<= :: PreparableStmt -> PreparableStmt -> Bool
< :: PreparableStmt -> PreparableStmt -> Bool
$c< :: PreparableStmt -> PreparableStmt -> Bool
compare :: PreparableStmt -> PreparableStmt -> Ordering
$ccompare :: PreparableStmt -> PreparableStmt -> Ordering
$cp1Ord :: Eq PreparableStmt
Ord)

-- * Call

newtype CallStmt
  = CallStmt FuncApplication
  deriving (Int -> CallStmt -> ShowS
[CallStmt] -> ShowS
CallStmt -> String
(Int -> CallStmt -> ShowS)
-> (CallStmt -> String) -> ([CallStmt] -> ShowS) -> Show CallStmt
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CallStmt] -> ShowS
$cshowList :: [CallStmt] -> ShowS
show :: CallStmt -> String
$cshow :: CallStmt -> String
showsPrec :: Int -> CallStmt -> ShowS
$cshowsPrec :: Int -> CallStmt -> ShowS
Show, (forall x. CallStmt -> Rep CallStmt x)
-> (forall x. Rep CallStmt x -> CallStmt) -> Generic CallStmt
forall x. Rep CallStmt x -> CallStmt
forall x. CallStmt -> Rep CallStmt x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CallStmt x -> CallStmt
$cfrom :: forall x. CallStmt -> Rep CallStmt x
Generic, CallStmt -> CallStmt -> Bool
(CallStmt -> CallStmt -> Bool)
-> (CallStmt -> CallStmt -> Bool) -> Eq CallStmt
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CallStmt -> CallStmt -> Bool
$c/= :: CallStmt -> CallStmt -> Bool
== :: CallStmt -> CallStmt -> Bool
$c== :: CallStmt -> CallStmt -> Bool
Eq, Eq CallStmt
Eq CallStmt
-> (CallStmt -> CallStmt -> Ordering)
-> (CallStmt -> CallStmt -> Bool)
-> (CallStmt -> CallStmt -> Bool)
-> (CallStmt -> CallStmt -> Bool)
-> (CallStmt -> CallStmt -> Bool)
-> (CallStmt -> CallStmt -> CallStmt)
-> (CallStmt -> CallStmt -> CallStmt)
-> Ord CallStmt
CallStmt -> CallStmt -> Bool
CallStmt -> CallStmt -> Ordering
CallStmt -> CallStmt -> CallStmt
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CallStmt -> CallStmt -> CallStmt
$cmin :: CallStmt -> CallStmt -> CallStmt
max :: CallStmt -> CallStmt -> CallStmt
$cmax :: CallStmt -> CallStmt -> CallStmt
>= :: CallStmt -> CallStmt -> Bool
$c>= :: CallStmt -> CallStmt -> Bool
> :: CallStmt -> CallStmt -> Bool
$c> :: CallStmt -> CallStmt -> Bool
<= :: CallStmt -> CallStmt -> Bool
$c<= :: CallStmt -> CallStmt -> Bool
< :: CallStmt -> CallStmt -> Bool
$c< :: CallStmt -> CallStmt -> Bool
compare :: CallStmt -> CallStmt -> Ordering
$ccompare :: CallStmt -> CallStmt -> Ordering
$cp1Ord :: Eq CallStmt
Ord)

-- * Insert

-- |
-- ==== References
-- @
-- InsertStmt:
--   | opt_with_clause INSERT INTO insert_target insert_rest
--       opt_on_conflict returning_clause
-- @
data InsertStmt = InsertStmt (Maybe WithClause) InsertTarget InsertRest (Maybe OnConflict) (Maybe ReturningClause)
  deriving (Int -> InsertStmt -> ShowS
[InsertStmt] -> ShowS
InsertStmt -> String
(Int -> InsertStmt -> ShowS)
-> (InsertStmt -> String)
-> ([InsertStmt] -> ShowS)
-> Show InsertStmt
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InsertStmt] -> ShowS
$cshowList :: [InsertStmt] -> ShowS
show :: InsertStmt -> String
$cshow :: InsertStmt -> String
showsPrec :: Int -> InsertStmt -> ShowS
$cshowsPrec :: Int -> InsertStmt -> ShowS
Show, (forall x. InsertStmt -> Rep InsertStmt x)
-> (forall x. Rep InsertStmt x -> InsertStmt) -> Generic InsertStmt
forall x. Rep InsertStmt x -> InsertStmt
forall x. InsertStmt -> Rep InsertStmt x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep InsertStmt x -> InsertStmt
$cfrom :: forall x. InsertStmt -> Rep InsertStmt x
Generic, InsertStmt -> InsertStmt -> Bool
(InsertStmt -> InsertStmt -> Bool)
-> (InsertStmt -> InsertStmt -> Bool) -> Eq InsertStmt
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InsertStmt -> InsertStmt -> Bool
$c/= :: InsertStmt -> InsertStmt -> Bool
== :: InsertStmt -> InsertStmt -> Bool
$c== :: InsertStmt -> InsertStmt -> Bool
Eq, Eq InsertStmt
Eq InsertStmt
-> (InsertStmt -> InsertStmt -> Ordering)
-> (InsertStmt -> InsertStmt -> Bool)
-> (InsertStmt -> InsertStmt -> Bool)
-> (InsertStmt -> InsertStmt -> Bool)
-> (InsertStmt -> InsertStmt -> Bool)
-> (InsertStmt -> InsertStmt -> InsertStmt)
-> (InsertStmt -> InsertStmt -> InsertStmt)
-> Ord InsertStmt
InsertStmt -> InsertStmt -> Bool
InsertStmt -> InsertStmt -> Ordering
InsertStmt -> InsertStmt -> InsertStmt
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: InsertStmt -> InsertStmt -> InsertStmt
$cmin :: InsertStmt -> InsertStmt -> InsertStmt
max :: InsertStmt -> InsertStmt -> InsertStmt
$cmax :: InsertStmt -> InsertStmt -> InsertStmt
>= :: InsertStmt -> InsertStmt -> Bool
$c>= :: InsertStmt -> InsertStmt -> Bool
> :: InsertStmt -> InsertStmt -> Bool
$c> :: InsertStmt -> InsertStmt -> Bool
<= :: InsertStmt -> InsertStmt -> Bool
$c<= :: InsertStmt -> InsertStmt -> Bool
< :: InsertStmt -> InsertStmt -> Bool
$c< :: InsertStmt -> InsertStmt -> Bool
compare :: InsertStmt -> InsertStmt -> Ordering
$ccompare :: InsertStmt -> InsertStmt -> Ordering
$cp1Ord :: Eq InsertStmt
Ord)

-- |
-- ==== References
-- @
-- insert_target:
--   | qualified_name
--   | qualified_name AS ColId
-- @
data InsertTarget = InsertTarget QualifiedName (Maybe ColId)
  deriving (Int -> InsertTarget -> ShowS
[InsertTarget] -> ShowS
InsertTarget -> String
(Int -> InsertTarget -> ShowS)
-> (InsertTarget -> String)
-> ([InsertTarget] -> ShowS)
-> Show InsertTarget
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InsertTarget] -> ShowS
$cshowList :: [InsertTarget] -> ShowS
show :: InsertTarget -> String
$cshow :: InsertTarget -> String
showsPrec :: Int -> InsertTarget -> ShowS
$cshowsPrec :: Int -> InsertTarget -> ShowS
Show, (forall x. InsertTarget -> Rep InsertTarget x)
-> (forall x. Rep InsertTarget x -> InsertTarget)
-> Generic InsertTarget
forall x. Rep InsertTarget x -> InsertTarget
forall x. InsertTarget -> Rep InsertTarget x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep InsertTarget x -> InsertTarget
$cfrom :: forall x. InsertTarget -> Rep InsertTarget x
Generic, InsertTarget -> InsertTarget -> Bool
(InsertTarget -> InsertTarget -> Bool)
-> (InsertTarget -> InsertTarget -> Bool) -> Eq InsertTarget
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InsertTarget -> InsertTarget -> Bool
$c/= :: InsertTarget -> InsertTarget -> Bool
== :: InsertTarget -> InsertTarget -> Bool
$c== :: InsertTarget -> InsertTarget -> Bool
Eq, Eq InsertTarget
Eq InsertTarget
-> (InsertTarget -> InsertTarget -> Ordering)
-> (InsertTarget -> InsertTarget -> Bool)
-> (InsertTarget -> InsertTarget -> Bool)
-> (InsertTarget -> InsertTarget -> Bool)
-> (InsertTarget -> InsertTarget -> Bool)
-> (InsertTarget -> InsertTarget -> InsertTarget)
-> (InsertTarget -> InsertTarget -> InsertTarget)
-> Ord InsertTarget
InsertTarget -> InsertTarget -> Bool
InsertTarget -> InsertTarget -> Ordering
InsertTarget -> InsertTarget -> InsertTarget
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: InsertTarget -> InsertTarget -> InsertTarget
$cmin :: InsertTarget -> InsertTarget -> InsertTarget
max :: InsertTarget -> InsertTarget -> InsertTarget
$cmax :: InsertTarget -> InsertTarget -> InsertTarget
>= :: InsertTarget -> InsertTarget -> Bool
$c>= :: InsertTarget -> InsertTarget -> Bool
> :: InsertTarget -> InsertTarget -> Bool
$c> :: InsertTarget -> InsertTarget -> Bool
<= :: InsertTarget -> InsertTarget -> Bool
$c<= :: InsertTarget -> InsertTarget -> Bool
< :: InsertTarget -> InsertTarget -> Bool
$c< :: InsertTarget -> InsertTarget -> Bool
compare :: InsertTarget -> InsertTarget -> Ordering
$ccompare :: InsertTarget -> InsertTarget -> Ordering
$cp1Ord :: Eq InsertTarget
Ord)

-- |
-- ==== References
-- @
-- insert_rest:
--   | SelectStmt
--   | OVERRIDING override_kind VALUE_P SelectStmt
--   | '(' insert_column_list ')' SelectStmt
--   | '(' insert_column_list ')' OVERRIDING override_kind VALUE_P SelectStmt
--   | DEFAULT VALUES
-- @
data InsertRest
  = SelectInsertRest (Maybe InsertColumnList) (Maybe OverrideKind) SelectStmt
  | DefaultValuesInsertRest
  deriving (Int -> InsertRest -> ShowS
[InsertRest] -> ShowS
InsertRest -> String
(Int -> InsertRest -> ShowS)
-> (InsertRest -> String)
-> ([InsertRest] -> ShowS)
-> Show InsertRest
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InsertRest] -> ShowS
$cshowList :: [InsertRest] -> ShowS
show :: InsertRest -> String
$cshow :: InsertRest -> String
showsPrec :: Int -> InsertRest -> ShowS
$cshowsPrec :: Int -> InsertRest -> ShowS
Show, (forall x. InsertRest -> Rep InsertRest x)
-> (forall x. Rep InsertRest x -> InsertRest) -> Generic InsertRest
forall x. Rep InsertRest x -> InsertRest
forall x. InsertRest -> Rep InsertRest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep InsertRest x -> InsertRest
$cfrom :: forall x. InsertRest -> Rep InsertRest x
Generic, InsertRest -> InsertRest -> Bool
(InsertRest -> InsertRest -> Bool)
-> (InsertRest -> InsertRest -> Bool) -> Eq InsertRest
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InsertRest -> InsertRest -> Bool
$c/= :: InsertRest -> InsertRest -> Bool
== :: InsertRest -> InsertRest -> Bool
$c== :: InsertRest -> InsertRest -> Bool
Eq, Eq InsertRest
Eq InsertRest
-> (InsertRest -> InsertRest -> Ordering)
-> (InsertRest -> InsertRest -> Bool)
-> (InsertRest -> InsertRest -> Bool)
-> (InsertRest -> InsertRest -> Bool)
-> (InsertRest -> InsertRest -> Bool)
-> (InsertRest -> InsertRest -> InsertRest)
-> (InsertRest -> InsertRest -> InsertRest)
-> Ord InsertRest
InsertRest -> InsertRest -> Bool
InsertRest -> InsertRest -> Ordering
InsertRest -> InsertRest -> InsertRest
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: InsertRest -> InsertRest -> InsertRest
$cmin :: InsertRest -> InsertRest -> InsertRest
max :: InsertRest -> InsertRest -> InsertRest
$cmax :: InsertRest -> InsertRest -> InsertRest
>= :: InsertRest -> InsertRest -> Bool
$c>= :: InsertRest -> InsertRest -> Bool
> :: InsertRest -> InsertRest -> Bool
$c> :: InsertRest -> InsertRest -> Bool
<= :: InsertRest -> InsertRest -> Bool
$c<= :: InsertRest -> InsertRest -> Bool
< :: InsertRest -> InsertRest -> Bool
$c< :: InsertRest -> InsertRest -> Bool
compare :: InsertRest -> InsertRest -> Ordering
$ccompare :: InsertRest -> InsertRest -> Ordering
$cp1Ord :: Eq InsertRest
Ord)

-- |
-- ==== References
-- @
-- override_kind:
--   | USER
--   | SYSTEM_P
-- @
data OverrideKind = UserOverrideKind | SystemOverrideKind
  deriving (Int -> OverrideKind -> ShowS
[OverrideKind] -> ShowS
OverrideKind -> String
(Int -> OverrideKind -> ShowS)
-> (OverrideKind -> String)
-> ([OverrideKind] -> ShowS)
-> Show OverrideKind
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [OverrideKind] -> ShowS
$cshowList :: [OverrideKind] -> ShowS
show :: OverrideKind -> String
$cshow :: OverrideKind -> String
showsPrec :: Int -> OverrideKind -> ShowS
$cshowsPrec :: Int -> OverrideKind -> ShowS
Show, (forall x. OverrideKind -> Rep OverrideKind x)
-> (forall x. Rep OverrideKind x -> OverrideKind)
-> Generic OverrideKind
forall x. Rep OverrideKind x -> OverrideKind
forall x. OverrideKind -> Rep OverrideKind x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep OverrideKind x -> OverrideKind
$cfrom :: forall x. OverrideKind -> Rep OverrideKind x
Generic, OverrideKind -> OverrideKind -> Bool
(OverrideKind -> OverrideKind -> Bool)
-> (OverrideKind -> OverrideKind -> Bool) -> Eq OverrideKind
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OverrideKind -> OverrideKind -> Bool
$c/= :: OverrideKind -> OverrideKind -> Bool
== :: OverrideKind -> OverrideKind -> Bool
$c== :: OverrideKind -> OverrideKind -> Bool
Eq, Eq OverrideKind
Eq OverrideKind
-> (OverrideKind -> OverrideKind -> Ordering)
-> (OverrideKind -> OverrideKind -> Bool)
-> (OverrideKind -> OverrideKind -> Bool)
-> (OverrideKind -> OverrideKind -> Bool)
-> (OverrideKind -> OverrideKind -> Bool)
-> (OverrideKind -> OverrideKind -> OverrideKind)
-> (OverrideKind -> OverrideKind -> OverrideKind)
-> Ord OverrideKind
OverrideKind -> OverrideKind -> Bool
OverrideKind -> OverrideKind -> Ordering
OverrideKind -> OverrideKind -> OverrideKind
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: OverrideKind -> OverrideKind -> OverrideKind
$cmin :: OverrideKind -> OverrideKind -> OverrideKind
max :: OverrideKind -> OverrideKind -> OverrideKind
$cmax :: OverrideKind -> OverrideKind -> OverrideKind
>= :: OverrideKind -> OverrideKind -> Bool
$c>= :: OverrideKind -> OverrideKind -> Bool
> :: OverrideKind -> OverrideKind -> Bool
$c> :: OverrideKind -> OverrideKind -> Bool
<= :: OverrideKind -> OverrideKind -> Bool
$c<= :: OverrideKind -> OverrideKind -> Bool
< :: OverrideKind -> OverrideKind -> Bool
$c< :: OverrideKind -> OverrideKind -> Bool
compare :: OverrideKind -> OverrideKind -> Ordering
$ccompare :: OverrideKind -> OverrideKind -> Ordering
$cp1Ord :: Eq OverrideKind
Ord, Int -> OverrideKind
OverrideKind -> Int
OverrideKind -> [OverrideKind]
OverrideKind -> OverrideKind
OverrideKind -> OverrideKind -> [OverrideKind]
OverrideKind -> OverrideKind -> OverrideKind -> [OverrideKind]
(OverrideKind -> OverrideKind)
-> (OverrideKind -> OverrideKind)
-> (Int -> OverrideKind)
-> (OverrideKind -> Int)
-> (OverrideKind -> [OverrideKind])
-> (OverrideKind -> OverrideKind -> [OverrideKind])
-> (OverrideKind -> OverrideKind -> [OverrideKind])
-> (OverrideKind -> OverrideKind -> OverrideKind -> [OverrideKind])
-> Enum OverrideKind
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: OverrideKind -> OverrideKind -> OverrideKind -> [OverrideKind]
$cenumFromThenTo :: OverrideKind -> OverrideKind -> OverrideKind -> [OverrideKind]
enumFromTo :: OverrideKind -> OverrideKind -> [OverrideKind]
$cenumFromTo :: OverrideKind -> OverrideKind -> [OverrideKind]
enumFromThen :: OverrideKind -> OverrideKind -> [OverrideKind]
$cenumFromThen :: OverrideKind -> OverrideKind -> [OverrideKind]
enumFrom :: OverrideKind -> [OverrideKind]
$cenumFrom :: OverrideKind -> [OverrideKind]
fromEnum :: OverrideKind -> Int
$cfromEnum :: OverrideKind -> Int
toEnum :: Int -> OverrideKind
$ctoEnum :: Int -> OverrideKind
pred :: OverrideKind -> OverrideKind
$cpred :: OverrideKind -> OverrideKind
succ :: OverrideKind -> OverrideKind
$csucc :: OverrideKind -> OverrideKind
Enum, OverrideKind
OverrideKind -> OverrideKind -> Bounded OverrideKind
forall a. a -> a -> Bounded a
maxBound :: OverrideKind
$cmaxBound :: OverrideKind
minBound :: OverrideKind
$cminBound :: OverrideKind
Bounded)

-- |
-- ==== References
-- @
-- insert_column_list:
--   | insert_column_item
--   | insert_column_list ',' insert_column_item
-- @
type InsertColumnList = NonEmpty InsertColumnItem

-- |
-- ==== References
-- @
-- insert_column_item:
--   | ColId opt_indirection
-- @
data InsertColumnItem = InsertColumnItem ColId (Maybe Indirection)
  deriving (Int -> InsertColumnItem -> ShowS
[InsertColumnItem] -> ShowS
InsertColumnItem -> String
(Int -> InsertColumnItem -> ShowS)
-> (InsertColumnItem -> String)
-> ([InsertColumnItem] -> ShowS)
-> Show InsertColumnItem
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InsertColumnItem] -> ShowS
$cshowList :: [InsertColumnItem] -> ShowS
show :: InsertColumnItem -> String
$cshow :: InsertColumnItem -> String
showsPrec :: Int -> InsertColumnItem -> ShowS
$cshowsPrec :: Int -> InsertColumnItem -> ShowS
Show, (forall x. InsertColumnItem -> Rep InsertColumnItem x)
-> (forall x. Rep InsertColumnItem x -> InsertColumnItem)
-> Generic InsertColumnItem
forall x. Rep InsertColumnItem x -> InsertColumnItem
forall x. InsertColumnItem -> Rep InsertColumnItem x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep InsertColumnItem x -> InsertColumnItem
$cfrom :: forall x. InsertColumnItem -> Rep InsertColumnItem x
Generic, InsertColumnItem -> InsertColumnItem -> Bool
(InsertColumnItem -> InsertColumnItem -> Bool)
-> (InsertColumnItem -> InsertColumnItem -> Bool)
-> Eq InsertColumnItem
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InsertColumnItem -> InsertColumnItem -> Bool
$c/= :: InsertColumnItem -> InsertColumnItem -> Bool
== :: InsertColumnItem -> InsertColumnItem -> Bool
$c== :: InsertColumnItem -> InsertColumnItem -> Bool
Eq, Eq InsertColumnItem
Eq InsertColumnItem
-> (InsertColumnItem -> InsertColumnItem -> Ordering)
-> (InsertColumnItem -> InsertColumnItem -> Bool)
-> (InsertColumnItem -> InsertColumnItem -> Bool)
-> (InsertColumnItem -> InsertColumnItem -> Bool)
-> (InsertColumnItem -> InsertColumnItem -> Bool)
-> (InsertColumnItem -> InsertColumnItem -> InsertColumnItem)
-> (InsertColumnItem -> InsertColumnItem -> InsertColumnItem)
-> Ord InsertColumnItem
InsertColumnItem -> InsertColumnItem -> Bool
InsertColumnItem -> InsertColumnItem -> Ordering
InsertColumnItem -> InsertColumnItem -> InsertColumnItem
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: InsertColumnItem -> InsertColumnItem -> InsertColumnItem
$cmin :: InsertColumnItem -> InsertColumnItem -> InsertColumnItem
max :: InsertColumnItem -> InsertColumnItem -> InsertColumnItem
$cmax :: InsertColumnItem -> InsertColumnItem -> InsertColumnItem
>= :: InsertColumnItem -> InsertColumnItem -> Bool
$c>= :: InsertColumnItem -> InsertColumnItem -> Bool
> :: InsertColumnItem -> InsertColumnItem -> Bool
$c> :: InsertColumnItem -> InsertColumnItem -> Bool
<= :: InsertColumnItem -> InsertColumnItem -> Bool
$c<= :: InsertColumnItem -> InsertColumnItem -> Bool
< :: InsertColumnItem -> InsertColumnItem -> Bool
$c< :: InsertColumnItem -> InsertColumnItem -> Bool
compare :: InsertColumnItem -> InsertColumnItem -> Ordering
$ccompare :: InsertColumnItem -> InsertColumnItem -> Ordering
$cp1Ord :: Eq InsertColumnItem
Ord)

-- |
-- ==== References
-- @
-- opt_on_conflict:
--   | ON CONFLICT opt_conf_expr DO UPDATE SET set_clause_list where_clause
--   | ON CONFLICT opt_conf_expr DO NOTHING
--   | EMPTY
-- @
data OnConflict = OnConflict (Maybe ConfExpr) OnConflictDo
  deriving (Int -> OnConflict -> ShowS
[OnConflict] -> ShowS
OnConflict -> String
(Int -> OnConflict -> ShowS)
-> (OnConflict -> String)
-> ([OnConflict] -> ShowS)
-> Show OnConflict
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [OnConflict] -> ShowS
$cshowList :: [OnConflict] -> ShowS
show :: OnConflict -> String
$cshow :: OnConflict -> String
showsPrec :: Int -> OnConflict -> ShowS
$cshowsPrec :: Int -> OnConflict -> ShowS
Show, (forall x. OnConflict -> Rep OnConflict x)
-> (forall x. Rep OnConflict x -> OnConflict) -> Generic OnConflict
forall x. Rep OnConflict x -> OnConflict
forall x. OnConflict -> Rep OnConflict x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep OnConflict x -> OnConflict
$cfrom :: forall x. OnConflict -> Rep OnConflict x
Generic, OnConflict -> OnConflict -> Bool
(OnConflict -> OnConflict -> Bool)
-> (OnConflict -> OnConflict -> Bool) -> Eq OnConflict
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OnConflict -> OnConflict -> Bool
$c/= :: OnConflict -> OnConflict -> Bool
== :: OnConflict -> OnConflict -> Bool
$c== :: OnConflict -> OnConflict -> Bool
Eq, Eq OnConflict
Eq OnConflict
-> (OnConflict -> OnConflict -> Ordering)
-> (OnConflict -> OnConflict -> Bool)
-> (OnConflict -> OnConflict -> Bool)
-> (OnConflict -> OnConflict -> Bool)
-> (OnConflict -> OnConflict -> Bool)
-> (OnConflict -> OnConflict -> OnConflict)
-> (OnConflict -> OnConflict -> OnConflict)
-> Ord OnConflict
OnConflict -> OnConflict -> Bool
OnConflict -> OnConflict -> Ordering
OnConflict -> OnConflict -> OnConflict
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: OnConflict -> OnConflict -> OnConflict
$cmin :: OnConflict -> OnConflict -> OnConflict
max :: OnConflict -> OnConflict -> OnConflict
$cmax :: OnConflict -> OnConflict -> OnConflict
>= :: OnConflict -> OnConflict -> Bool
$c>= :: OnConflict -> OnConflict -> Bool
> :: OnConflict -> OnConflict -> Bool
$c> :: OnConflict -> OnConflict -> Bool
<= :: OnConflict -> OnConflict -> Bool
$c<= :: OnConflict -> OnConflict -> Bool
< :: OnConflict -> OnConflict -> Bool
$c< :: OnConflict -> OnConflict -> Bool
compare :: OnConflict -> OnConflict -> Ordering
$ccompare :: OnConflict -> OnConflict -> Ordering
$cp1Ord :: Eq OnConflict
Ord)

-- |
-- ==== References
-- @
-- opt_on_conflict:
--   | ON CONFLICT opt_conf_expr DO UPDATE SET set_clause_list where_clause
--   | ON CONFLICT opt_conf_expr DO NOTHING
--   | EMPTY
-- @
data OnConflictDo
  = UpdateOnConflictDo SetClauseList (Maybe WhereClause)
  | NothingOnConflictDo
  deriving (Int -> OnConflictDo -> ShowS
[OnConflictDo] -> ShowS
OnConflictDo -> String
(Int -> OnConflictDo -> ShowS)
-> (OnConflictDo -> String)
-> ([OnConflictDo] -> ShowS)
-> Show OnConflictDo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [OnConflictDo] -> ShowS
$cshowList :: [OnConflictDo] -> ShowS
show :: OnConflictDo -> String
$cshow :: OnConflictDo -> String
showsPrec :: Int -> OnConflictDo -> ShowS
$cshowsPrec :: Int -> OnConflictDo -> ShowS
Show, (forall x. OnConflictDo -> Rep OnConflictDo x)
-> (forall x. Rep OnConflictDo x -> OnConflictDo)
-> Generic OnConflictDo
forall x. Rep OnConflictDo x -> OnConflictDo
forall x. OnConflictDo -> Rep OnConflictDo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep OnConflictDo x -> OnConflictDo
$cfrom :: forall x. OnConflictDo -> Rep OnConflictDo x
Generic, OnConflictDo -> OnConflictDo -> Bool
(OnConflictDo -> OnConflictDo -> Bool)
-> (OnConflictDo -> OnConflictDo -> Bool) -> Eq OnConflictDo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OnConflictDo -> OnConflictDo -> Bool
$c/= :: OnConflictDo -> OnConflictDo -> Bool
== :: OnConflictDo -> OnConflictDo -> Bool
$c== :: OnConflictDo -> OnConflictDo -> Bool
Eq, Eq OnConflictDo
Eq OnConflictDo
-> (OnConflictDo -> OnConflictDo -> Ordering)
-> (OnConflictDo -> OnConflictDo -> Bool)
-> (OnConflictDo -> OnConflictDo -> Bool)
-> (OnConflictDo -> OnConflictDo -> Bool)
-> (OnConflictDo -> OnConflictDo -> Bool)
-> (OnConflictDo -> OnConflictDo -> OnConflictDo)
-> (OnConflictDo -> OnConflictDo -> OnConflictDo)
-> Ord OnConflictDo
OnConflictDo -> OnConflictDo -> Bool
OnConflictDo -> OnConflictDo -> Ordering
OnConflictDo -> OnConflictDo -> OnConflictDo
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: OnConflictDo -> OnConflictDo -> OnConflictDo
$cmin :: OnConflictDo -> OnConflictDo -> OnConflictDo
max :: OnConflictDo -> OnConflictDo -> OnConflictDo
$cmax :: OnConflictDo -> OnConflictDo -> OnConflictDo
>= :: OnConflictDo -> OnConflictDo -> Bool
$c>= :: OnConflictDo -> OnConflictDo -> Bool
> :: OnConflictDo -> OnConflictDo -> Bool
$c> :: OnConflictDo -> OnConflictDo -> Bool
<= :: OnConflictDo -> OnConflictDo -> Bool
$c<= :: OnConflictDo -> OnConflictDo -> Bool
< :: OnConflictDo -> OnConflictDo -> Bool
$c< :: OnConflictDo -> OnConflictDo -> Bool
compare :: OnConflictDo -> OnConflictDo -> Ordering
$ccompare :: OnConflictDo -> OnConflictDo -> Ordering
$cp1Ord :: Eq OnConflictDo
Ord)

-- |
-- ==== References
-- @
-- opt_conf_expr:
--   | '(' index_params ')' where_clause
--   | ON CONSTRAINT name
--   | EMPTY
-- @
data ConfExpr
  = WhereConfExpr IndexParams (Maybe WhereClause)
  | ConstraintConfExpr Name
  deriving (Int -> ConfExpr -> ShowS
[ConfExpr] -> ShowS
ConfExpr -> String
(Int -> ConfExpr -> ShowS)
-> (ConfExpr -> String) -> ([ConfExpr] -> ShowS) -> Show ConfExpr
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ConfExpr] -> ShowS
$cshowList :: [ConfExpr] -> ShowS
show :: ConfExpr -> String
$cshow :: ConfExpr -> String
showsPrec :: Int -> ConfExpr -> ShowS
$cshowsPrec :: Int -> ConfExpr -> ShowS
Show, (forall x. ConfExpr -> Rep ConfExpr x)
-> (forall x. Rep ConfExpr x -> ConfExpr) -> Generic ConfExpr
forall x. Rep ConfExpr x -> ConfExpr
forall x. ConfExpr -> Rep ConfExpr x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ConfExpr x -> ConfExpr
$cfrom :: forall x. ConfExpr -> Rep ConfExpr x
Generic, ConfExpr -> ConfExpr -> Bool
(ConfExpr -> ConfExpr -> Bool)
-> (ConfExpr -> ConfExpr -> Bool) -> Eq ConfExpr
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ConfExpr -> ConfExpr -> Bool
$c/= :: ConfExpr -> ConfExpr -> Bool
== :: ConfExpr -> ConfExpr -> Bool
$c== :: ConfExpr -> ConfExpr -> Bool
Eq, Eq ConfExpr
Eq ConfExpr
-> (ConfExpr -> ConfExpr -> Ordering)
-> (ConfExpr -> ConfExpr -> Bool)
-> (ConfExpr -> ConfExpr -> Bool)
-> (ConfExpr -> ConfExpr -> Bool)
-> (ConfExpr -> ConfExpr -> Bool)
-> (ConfExpr -> ConfExpr -> ConfExpr)
-> (ConfExpr -> ConfExpr -> ConfExpr)
-> Ord ConfExpr
ConfExpr -> ConfExpr -> Bool
ConfExpr -> ConfExpr -> Ordering
ConfExpr -> ConfExpr -> ConfExpr
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ConfExpr -> ConfExpr -> ConfExpr
$cmin :: ConfExpr -> ConfExpr -> ConfExpr
max :: ConfExpr -> ConfExpr -> ConfExpr
$cmax :: ConfExpr -> ConfExpr -> ConfExpr
>= :: ConfExpr -> ConfExpr -> Bool
$c>= :: ConfExpr -> ConfExpr -> Bool
> :: ConfExpr -> ConfExpr -> Bool
$c> :: ConfExpr -> ConfExpr -> Bool
<= :: ConfExpr -> ConfExpr -> Bool
$c<= :: ConfExpr -> ConfExpr -> Bool
< :: ConfExpr -> ConfExpr -> Bool
$c< :: ConfExpr -> ConfExpr -> Bool
compare :: ConfExpr -> ConfExpr -> Ordering
$ccompare :: ConfExpr -> ConfExpr -> Ordering
$cp1Ord :: Eq ConfExpr
Ord)

-- |
-- ==== References
-- @
-- returning_clause:
--   | RETURNING target_list
--   | EMPTY
-- @
type ReturningClause = TargetList

-- * Update

-- |
-- ==== References
-- @
-- UpdateStmt:
--   | opt_with_clause UPDATE relation_expr_opt_alias
--       SET set_clause_list
--       from_clause
--       where_or_current_clause
--       returning_clause
-- @
data UpdateStmt = UpdateStmt (Maybe WithClause) RelationExprOptAlias SetClauseList (Maybe FromClause) (Maybe WhereOrCurrentClause) (Maybe ReturningClause)
  deriving (Int -> UpdateStmt -> ShowS
[UpdateStmt] -> ShowS
UpdateStmt -> String
(Int -> UpdateStmt -> ShowS)
-> (UpdateStmt -> String)
-> ([UpdateStmt] -> ShowS)
-> Show UpdateStmt
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateStmt] -> ShowS
$cshowList :: [UpdateStmt] -> ShowS
show :: UpdateStmt -> String
$cshow :: UpdateStmt -> String
showsPrec :: Int -> UpdateStmt -> ShowS
$cshowsPrec :: Int -> UpdateStmt -> ShowS
Show, (forall x. UpdateStmt -> Rep UpdateStmt x)
-> (forall x. Rep UpdateStmt x -> UpdateStmt) -> Generic UpdateStmt
forall x. Rep UpdateStmt x -> UpdateStmt
forall x. UpdateStmt -> Rep UpdateStmt x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateStmt x -> UpdateStmt
$cfrom :: forall x. UpdateStmt -> Rep UpdateStmt x
Generic, UpdateStmt -> UpdateStmt -> Bool
(UpdateStmt -> UpdateStmt -> Bool)
-> (UpdateStmt -> UpdateStmt -> Bool) -> Eq UpdateStmt
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateStmt -> UpdateStmt -> Bool
$c/= :: UpdateStmt -> UpdateStmt -> Bool
== :: UpdateStmt -> UpdateStmt -> Bool
$c== :: UpdateStmt -> UpdateStmt -> Bool
Eq, Eq UpdateStmt
Eq UpdateStmt
-> (UpdateStmt -> UpdateStmt -> Ordering)
-> (UpdateStmt -> UpdateStmt -> Bool)
-> (UpdateStmt -> UpdateStmt -> Bool)
-> (UpdateStmt -> UpdateStmt -> Bool)
-> (UpdateStmt -> UpdateStmt -> Bool)
-> (UpdateStmt -> UpdateStmt -> UpdateStmt)
-> (UpdateStmt -> UpdateStmt -> UpdateStmt)
-> Ord UpdateStmt
UpdateStmt -> UpdateStmt -> Bool
UpdateStmt -> UpdateStmt -> Ordering
UpdateStmt -> UpdateStmt -> UpdateStmt
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: UpdateStmt -> UpdateStmt -> UpdateStmt
$cmin :: UpdateStmt -> UpdateStmt -> UpdateStmt
max :: UpdateStmt -> UpdateStmt -> UpdateStmt
$cmax :: UpdateStmt -> UpdateStmt -> UpdateStmt
>= :: UpdateStmt -> UpdateStmt -> Bool
$c>= :: UpdateStmt -> UpdateStmt -> Bool
> :: UpdateStmt -> UpdateStmt -> Bool
$c> :: UpdateStmt -> UpdateStmt -> Bool
<= :: UpdateStmt -> UpdateStmt -> Bool
$c<= :: UpdateStmt -> UpdateStmt -> Bool
< :: UpdateStmt -> UpdateStmt -> Bool
$c< :: UpdateStmt -> UpdateStmt -> Bool
compare :: UpdateStmt -> UpdateStmt -> Ordering
$ccompare :: UpdateStmt -> UpdateStmt -> Ordering
$cp1Ord :: Eq UpdateStmt
Ord)

-- |
-- ==== References
-- @
-- set_clause_list:
--   | set_clause
--   | set_clause_list ',' set_clause
-- @
type SetClauseList = NonEmpty SetClause

-- |
-- ==== References
-- @
-- set_clause:
--   | set_target '=' a_expr
--   | '(' set_target_list ')' '=' a_expr
-- @
data SetClause
  = TargetSetClause SetTarget AExpr
  | TargetListSetClause SetTargetList AExpr
  deriving (Int -> SetClause -> ShowS
[SetClause] -> ShowS
SetClause -> String
(Int -> SetClause -> ShowS)
-> (SetClause -> String)
-> ([SetClause] -> ShowS)
-> Show SetClause
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SetClause] -> ShowS
$cshowList :: [SetClause] -> ShowS
show :: SetClause -> String
$cshow :: SetClause -> String
showsPrec :: Int -> SetClause -> ShowS
$cshowsPrec :: Int -> SetClause -> ShowS
Show, (forall x. SetClause -> Rep SetClause x)
-> (forall x. Rep SetClause x -> SetClause) -> Generic SetClause
forall x. Rep SetClause x -> SetClause
forall x. SetClause -> Rep SetClause x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SetClause x -> SetClause
$cfrom :: forall x. SetClause -> Rep SetClause x
Generic, SetClause -> SetClause -> Bool
(SetClause -> SetClause -> Bool)
-> (SetClause -> SetClause -> Bool) -> Eq SetClause
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SetClause -> SetClause -> Bool
$c/= :: SetClause -> SetClause -> Bool
== :: SetClause -> SetClause -> Bool
$c== :: SetClause -> SetClause -> Bool
Eq, Eq SetClause
Eq SetClause
-> (SetClause -> SetClause -> Ordering)
-> (SetClause -> SetClause -> Bool)
-> (SetClause -> SetClause -> Bool)
-> (SetClause -> SetClause -> Bool)
-> (SetClause -> SetClause -> Bool)
-> (SetClause -> SetClause -> SetClause)
-> (SetClause -> SetClause -> SetClause)
-> Ord SetClause
SetClause -> SetClause -> Bool
SetClause -> SetClause -> Ordering
SetClause -> SetClause -> SetClause
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: SetClause -> SetClause -> SetClause
$cmin :: SetClause -> SetClause -> SetClause
max :: SetClause -> SetClause -> SetClause
$cmax :: SetClause -> SetClause -> SetClause
>= :: SetClause -> SetClause -> Bool
$c>= :: SetClause -> SetClause -> Bool
> :: SetClause -> SetClause -> Bool
$c> :: SetClause -> SetClause -> Bool
<= :: SetClause -> SetClause -> Bool
$c<= :: SetClause -> SetClause -> Bool
< :: SetClause -> SetClause -> Bool
$c< :: SetClause -> SetClause -> Bool
compare :: SetClause -> SetClause -> Ordering
$ccompare :: SetClause -> SetClause -> Ordering
$cp1Ord :: Eq SetClause
Ord)

-- |
-- ==== References
-- @
-- set_target:
--   | ColId opt_indirection
-- @
data SetTarget = SetTarget ColId (Maybe Indirection)
  deriving (Int -> SetTarget -> ShowS
[SetTarget] -> ShowS
SetTarget -> String
(Int -> SetTarget -> ShowS)
-> (SetTarget -> String)
-> ([SetTarget] -> ShowS)
-> Show SetTarget
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SetTarget] -> ShowS
$cshowList :: [SetTarget] -> ShowS
show :: SetTarget -> String
$cshow :: SetTarget -> String
showsPrec :: Int -> SetTarget -> ShowS
$cshowsPrec :: Int -> SetTarget -> ShowS
Show, (forall x. SetTarget -> Rep SetTarget x)
-> (forall x. Rep SetTarget x -> SetTarget) -> Generic SetTarget
forall x. Rep SetTarget x -> SetTarget
forall x. SetTarget -> Rep SetTarget x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SetTarget x -> SetTarget
$cfrom :: forall x. SetTarget -> Rep SetTarget x
Generic, SetTarget -> SetTarget -> Bool
(SetTarget -> SetTarget -> Bool)
-> (SetTarget -> SetTarget -> Bool) -> Eq SetTarget
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SetTarget -> SetTarget -> Bool
$c/= :: SetTarget -> SetTarget -> Bool
== :: SetTarget -> SetTarget -> Bool
$c== :: SetTarget -> SetTarget -> Bool
Eq, Eq SetTarget
Eq SetTarget
-> (SetTarget -> SetTarget -> Ordering)
-> (SetTarget -> SetTarget -> Bool)
-> (SetTarget -> SetTarget -> Bool)
-> (SetTarget -> SetTarget -> Bool)
-> (SetTarget -> SetTarget -> Bool)
-> (SetTarget -> SetTarget -> SetTarget)
-> (SetTarget -> SetTarget -> SetTarget)
-> Ord SetTarget
SetTarget -> SetTarget -> Bool
SetTarget -> SetTarget -> Ordering
SetTarget -> SetTarget -> SetTarget
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: SetTarget -> SetTarget -> SetTarget
$cmin :: SetTarget -> SetTarget -> SetTarget
max :: SetTarget -> SetTarget -> SetTarget
$cmax :: SetTarget -> SetTarget -> SetTarget
>= :: SetTarget -> SetTarget -> Bool
$c>= :: SetTarget -> SetTarget -> Bool
> :: SetTarget -> SetTarget -> Bool
$c> :: SetTarget -> SetTarget -> Bool
<= :: SetTarget -> SetTarget -> Bool
$c<= :: SetTarget -> SetTarget -> Bool
< :: SetTarget -> SetTarget -> Bool
$c< :: SetTarget -> SetTarget -> Bool
compare :: SetTarget -> SetTarget -> Ordering
$ccompare :: SetTarget -> SetTarget -> Ordering
$cp1Ord :: Eq SetTarget
Ord)

-- |
-- ==== References
-- @
-- set_target_list:
--   | set_target
--   | set_target_list ',' set_target
-- @
type SetTargetList = NonEmpty SetTarget

-- * Delete

-- |
-- ==== References
-- @
-- DeleteStmt:
--   | opt_with_clause DELETE_P FROM relation_expr_opt_alias
--       using_clause where_or_current_clause returning_clause
-- @
data DeleteStmt = DeleteStmt (Maybe WithClause) RelationExprOptAlias (Maybe UsingClause) (Maybe WhereOrCurrentClause) (Maybe ReturningClause)
  deriving (Int -> DeleteStmt -> ShowS
[DeleteStmt] -> ShowS
DeleteStmt -> String
(Int -> DeleteStmt -> ShowS)
-> (DeleteStmt -> String)
-> ([DeleteStmt] -> ShowS)
-> Show DeleteStmt
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteStmt] -> ShowS
$cshowList :: [DeleteStmt] -> ShowS
show :: DeleteStmt -> String
$cshow :: DeleteStmt -> String
showsPrec :: Int -> DeleteStmt -> ShowS
$cshowsPrec :: Int -> DeleteStmt -> ShowS
Show, (forall x. DeleteStmt -> Rep DeleteStmt x)
-> (forall x. Rep DeleteStmt x -> DeleteStmt) -> Generic DeleteStmt
forall x. Rep DeleteStmt x -> DeleteStmt
forall x. DeleteStmt -> Rep DeleteStmt x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteStmt x -> DeleteStmt
$cfrom :: forall x. DeleteStmt -> Rep DeleteStmt x
Generic, DeleteStmt -> DeleteStmt -> Bool
(DeleteStmt -> DeleteStmt -> Bool)
-> (DeleteStmt -> DeleteStmt -> Bool) -> Eq DeleteStmt
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteStmt -> DeleteStmt -> Bool
$c/= :: DeleteStmt -> DeleteStmt -> Bool
== :: DeleteStmt -> DeleteStmt -> Bool
$c== :: DeleteStmt -> DeleteStmt -> Bool
Eq, Eq DeleteStmt
Eq DeleteStmt
-> (DeleteStmt -> DeleteStmt -> Ordering)
-> (DeleteStmt -> DeleteStmt -> Bool)
-> (DeleteStmt -> DeleteStmt -> Bool)
-> (DeleteStmt -> DeleteStmt -> Bool)
-> (DeleteStmt -> DeleteStmt -> Bool)
-> (DeleteStmt -> DeleteStmt -> DeleteStmt)
-> (DeleteStmt -> DeleteStmt -> DeleteStmt)
-> Ord DeleteStmt
DeleteStmt -> DeleteStmt -> Bool
DeleteStmt -> DeleteStmt -> Ordering
DeleteStmt -> DeleteStmt -> DeleteStmt
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: DeleteStmt -> DeleteStmt -> DeleteStmt
$cmin :: DeleteStmt -> DeleteStmt -> DeleteStmt
max :: DeleteStmt -> DeleteStmt -> DeleteStmt
$cmax :: DeleteStmt -> DeleteStmt -> DeleteStmt
>= :: DeleteStmt -> DeleteStmt -> Bool
$c>= :: DeleteStmt -> DeleteStmt -> Bool
> :: DeleteStmt -> DeleteStmt -> Bool
$c> :: DeleteStmt -> DeleteStmt -> Bool
<= :: DeleteStmt -> DeleteStmt -> Bool
$c<= :: DeleteStmt -> DeleteStmt -> Bool
< :: DeleteStmt -> DeleteStmt -> Bool
$c< :: DeleteStmt -> DeleteStmt -> Bool
compare :: DeleteStmt -> DeleteStmt -> Ordering
$ccompare :: DeleteStmt -> DeleteStmt -> Ordering
$cp1Ord :: Eq DeleteStmt
Ord)

-- |
-- ==== References
-- @
-- using_clause:
--   | USING from_list
--   | EMPTY
-- @
type UsingClause = FromList

-- * Select

-- |
-- ==== References
-- @
-- SelectStmt:
--   |  select_no_parens
--   |  select_with_parens
-- @
type SelectStmt = Either SelectNoParens SelectWithParens

-- |
-- ==== References
-- @
-- select_with_parens:
--   |  '(' select_no_parens ')'
--   |  '(' select_with_parens ')'
-- @
data SelectWithParens
  = NoParensSelectWithParens SelectNoParens
  | WithParensSelectWithParens SelectWithParens
  deriving (Int -> SelectWithParens -> ShowS
[SelectWithParens] -> ShowS
SelectWithParens -> String
(Int -> SelectWithParens -> ShowS)
-> (SelectWithParens -> String)
-> ([SelectWithParens] -> ShowS)
-> Show SelectWithParens
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SelectWithParens] -> ShowS
$cshowList :: [SelectWithParens] -> ShowS
show :: SelectWithParens -> String
$cshow :: SelectWithParens -> String
showsPrec :: Int -> SelectWithParens -> ShowS
$cshowsPrec :: Int -> SelectWithParens -> ShowS
Show, (forall x. SelectWithParens -> Rep SelectWithParens x)
-> (forall x. Rep SelectWithParens x -> SelectWithParens)
-> Generic SelectWithParens
forall x. Rep SelectWithParens x -> SelectWithParens
forall x. SelectWithParens -> Rep SelectWithParens x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SelectWithParens x -> SelectWithParens
$cfrom :: forall x. SelectWithParens -> Rep SelectWithParens x
Generic, SelectWithParens -> SelectWithParens -> Bool
(SelectWithParens -> SelectWithParens -> Bool)
-> (SelectWithParens -> SelectWithParens -> Bool)
-> Eq SelectWithParens
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SelectWithParens -> SelectWithParens -> Bool
$c/= :: SelectWithParens -> SelectWithParens -> Bool
== :: SelectWithParens -> SelectWithParens -> Bool
$c== :: SelectWithParens -> SelectWithParens -> Bool
Eq, Eq SelectWithParens
Eq SelectWithParens
-> (SelectWithParens -> SelectWithParens -> Ordering)
-> (SelectWithParens -> SelectWithParens -> Bool)
-> (SelectWithParens -> SelectWithParens -> Bool)
-> (SelectWithParens -> SelectWithParens -> Bool)
-> (SelectWithParens -> SelectWithParens -> Bool)
-> (SelectWithParens -> SelectWithParens -> SelectWithParens)
-> (SelectWithParens -> SelectWithParens -> SelectWithParens)
-> Ord SelectWithParens
SelectWithParens -> SelectWithParens -> Bool
SelectWithParens -> SelectWithParens -> Ordering
SelectWithParens -> SelectWithParens -> SelectWithParens
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: SelectWithParens -> SelectWithParens -> SelectWithParens
$cmin :: SelectWithParens -> SelectWithParens -> SelectWithParens
max :: SelectWithParens -> SelectWithParens -> SelectWithParens
$cmax :: SelectWithParens -> SelectWithParens -> SelectWithParens
>= :: SelectWithParens -> SelectWithParens -> Bool
$c>= :: SelectWithParens -> SelectWithParens -> Bool
> :: SelectWithParens -> SelectWithParens -> Bool
$c> :: SelectWithParens -> SelectWithParens -> Bool
<= :: SelectWithParens -> SelectWithParens -> Bool
$c<= :: SelectWithParens -> SelectWithParens -> Bool
< :: SelectWithParens -> SelectWithParens -> Bool
$c< :: SelectWithParens -> SelectWithParens -> Bool
compare :: SelectWithParens -> SelectWithParens -> Ordering
$ccompare :: SelectWithParens -> SelectWithParens -> Ordering
$cp1Ord :: Eq SelectWithParens
Ord)

-- |
-- 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
-- @
data SelectNoParens
  = SelectNoParens (Maybe WithClause) SelectClause (Maybe SortClause) (Maybe SelectLimit) (Maybe ForLockingClause)
  deriving (Int -> SelectNoParens -> ShowS
[SelectNoParens] -> ShowS
SelectNoParens -> String
(Int -> SelectNoParens -> ShowS)
-> (SelectNoParens -> String)
-> ([SelectNoParens] -> ShowS)
-> Show SelectNoParens
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SelectNoParens] -> ShowS
$cshowList :: [SelectNoParens] -> ShowS
show :: SelectNoParens -> String
$cshow :: SelectNoParens -> String
showsPrec :: Int -> SelectNoParens -> ShowS
$cshowsPrec :: Int -> SelectNoParens -> ShowS
Show, (forall x. SelectNoParens -> Rep SelectNoParens x)
-> (forall x. Rep SelectNoParens x -> SelectNoParens)
-> Generic SelectNoParens
forall x. Rep SelectNoParens x -> SelectNoParens
forall x. SelectNoParens -> Rep SelectNoParens x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SelectNoParens x -> SelectNoParens
$cfrom :: forall x. SelectNoParens -> Rep SelectNoParens x
Generic, SelectNoParens -> SelectNoParens -> Bool
(SelectNoParens -> SelectNoParens -> Bool)
-> (SelectNoParens -> SelectNoParens -> Bool) -> Eq SelectNoParens
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SelectNoParens -> SelectNoParens -> Bool
$c/= :: SelectNoParens -> SelectNoParens -> Bool
== :: SelectNoParens -> SelectNoParens -> Bool
$c== :: SelectNoParens -> SelectNoParens -> Bool
Eq, Eq SelectNoParens
Eq SelectNoParens
-> (SelectNoParens -> SelectNoParens -> Ordering)
-> (SelectNoParens -> SelectNoParens -> Bool)
-> (SelectNoParens -> SelectNoParens -> Bool)
-> (SelectNoParens -> SelectNoParens -> Bool)
-> (SelectNoParens -> SelectNoParens -> Bool)
-> (SelectNoParens -> SelectNoParens -> SelectNoParens)
-> (SelectNoParens -> SelectNoParens -> SelectNoParens)
-> Ord SelectNoParens
SelectNoParens -> SelectNoParens -> Bool
SelectNoParens -> SelectNoParens -> Ordering
SelectNoParens -> SelectNoParens -> SelectNoParens
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: SelectNoParens -> SelectNoParens -> SelectNoParens
$cmin :: SelectNoParens -> SelectNoParens -> SelectNoParens
max :: SelectNoParens -> SelectNoParens -> SelectNoParens
$cmax :: SelectNoParens -> SelectNoParens -> SelectNoParens
>= :: SelectNoParens -> SelectNoParens -> Bool
$c>= :: SelectNoParens -> SelectNoParens -> Bool
> :: SelectNoParens -> SelectNoParens -> Bool
$c> :: SelectNoParens -> SelectNoParens -> Bool
<= :: SelectNoParens -> SelectNoParens -> Bool
$c<= :: SelectNoParens -> SelectNoParens -> Bool
< :: SelectNoParens -> SelectNoParens -> Bool
$c< :: SelectNoParens -> SelectNoParens -> Bool
compare :: SelectNoParens -> SelectNoParens -> Ordering
$ccompare :: SelectNoParens -> SelectNoParens -> Ordering
$cp1Ord :: Eq SelectNoParens
Ord)

-- |
-- @
-- select_clause:
--   |  simple_select
--   |  select_with_parens
-- @
type SelectClause = Either SimpleSelect SelectWithParens

-- |
-- ==== References
-- @
-- simple_select:
--   |  SELECT opt_all_clause opt_target_list
--       into_clause from_clause where_clause
--       group_clause having_clause window_clause
--   |  SELECT distinct_clause target_list
--       into_clause from_clause where_clause
--       group_clause having_clause window_clause
--   |  values_clause
--   |  TABLE relation_expr
--   |  select_clause UNION all_or_distinct select_clause
--   |  select_clause INTERSECT all_or_distinct select_clause
--   |  select_clause EXCEPT all_or_distinct select_clause
-- @
data SimpleSelect
  = NormalSimpleSelect (Maybe Targeting) (Maybe IntoClause) (Maybe FromClause) (Maybe WhereClause) (Maybe GroupClause) (Maybe HavingClause) (Maybe WindowClause)
  | ValuesSimpleSelect ValuesClause
  | TableSimpleSelect RelationExpr
  | BinSimpleSelect SelectBinOp SelectClause (Maybe Bool) SelectClause
  deriving (Int -> SimpleSelect -> ShowS
[SimpleSelect] -> ShowS
SimpleSelect -> String
(Int -> SimpleSelect -> ShowS)
-> (SimpleSelect -> String)
-> ([SimpleSelect] -> ShowS)
-> Show SimpleSelect
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SimpleSelect] -> ShowS
$cshowList :: [SimpleSelect] -> ShowS
show :: SimpleSelect -> String
$cshow :: SimpleSelect -> String
showsPrec :: Int -> SimpleSelect -> ShowS
$cshowsPrec :: Int -> SimpleSelect -> ShowS
Show, (forall x. SimpleSelect -> Rep SimpleSelect x)
-> (forall x. Rep SimpleSelect x -> SimpleSelect)
-> Generic SimpleSelect
forall x. Rep SimpleSelect x -> SimpleSelect
forall x. SimpleSelect -> Rep SimpleSelect x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SimpleSelect x -> SimpleSelect
$cfrom :: forall x. SimpleSelect -> Rep SimpleSelect x
Generic, SimpleSelect -> SimpleSelect -> Bool
(SimpleSelect -> SimpleSelect -> Bool)
-> (SimpleSelect -> SimpleSelect -> Bool) -> Eq SimpleSelect
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SimpleSelect -> SimpleSelect -> Bool
$c/= :: SimpleSelect -> SimpleSelect -> Bool
== :: SimpleSelect -> SimpleSelect -> Bool
$c== :: SimpleSelect -> SimpleSelect -> Bool
Eq, Eq SimpleSelect
Eq SimpleSelect
-> (SimpleSelect -> SimpleSelect -> Ordering)
-> (SimpleSelect -> SimpleSelect -> Bool)
-> (SimpleSelect -> SimpleSelect -> Bool)
-> (SimpleSelect -> SimpleSelect -> Bool)
-> (SimpleSelect -> SimpleSelect -> Bool)
-> (SimpleSelect -> SimpleSelect -> SimpleSelect)
-> (SimpleSelect -> SimpleSelect -> SimpleSelect)
-> Ord SimpleSelect
SimpleSelect -> SimpleSelect -> Bool
SimpleSelect -> SimpleSelect -> Ordering
SimpleSelect -> SimpleSelect -> SimpleSelect
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: SimpleSelect -> SimpleSelect -> SimpleSelect
$cmin :: SimpleSelect -> SimpleSelect -> SimpleSelect
max :: SimpleSelect -> SimpleSelect -> SimpleSelect
$cmax :: SimpleSelect -> SimpleSelect -> SimpleSelect
>= :: SimpleSelect -> SimpleSelect -> Bool
$c>= :: SimpleSelect -> SimpleSelect -> Bool
> :: SimpleSelect -> SimpleSelect -> Bool
$c> :: SimpleSelect -> SimpleSelect -> Bool
<= :: SimpleSelect -> SimpleSelect -> Bool
$c<= :: SimpleSelect -> SimpleSelect -> Bool
< :: SimpleSelect -> SimpleSelect -> Bool
$c< :: SimpleSelect -> SimpleSelect -> Bool
compare :: SimpleSelect -> SimpleSelect -> Ordering
$ccompare :: SimpleSelect -> SimpleSelect -> Ordering
$cp1Ord :: Eq SimpleSelect
Ord)

-- |
-- Covers these parts of spec:
--
-- ==== References
-- @
-- simple_select:
--   |  SELECT opt_all_clause opt_target_list
--       into_clause from_clause where_clause
--       group_clause having_clause window_clause
--   |  SELECT distinct_clause target_list
--       into_clause from_clause where_clause
--       group_clause having_clause window_clause
--
-- distinct_clause:
--   |  DISTINCT
--   |  DISTINCT ON '(' expr_list ')'
-- @
data Targeting
  = NormalTargeting TargetList
  | AllTargeting (Maybe TargetList)
  | DistinctTargeting (Maybe ExprList) TargetList
  deriving (Int -> Targeting -> ShowS
[Targeting] -> ShowS
Targeting -> String
(Int -> Targeting -> ShowS)
-> (Targeting -> String)
-> ([Targeting] -> ShowS)
-> Show Targeting
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Targeting] -> ShowS
$cshowList :: [Targeting] -> ShowS
show :: Targeting -> String
$cshow :: Targeting -> String
showsPrec :: Int -> Targeting -> ShowS
$cshowsPrec :: Int -> Targeting -> ShowS
Show, (forall x. Targeting -> Rep Targeting x)
-> (forall x. Rep Targeting x -> Targeting) -> Generic Targeting
forall x. Rep Targeting x -> Targeting
forall x. Targeting -> Rep Targeting x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Targeting x -> Targeting
$cfrom :: forall x. Targeting -> Rep Targeting x
Generic, Targeting -> Targeting -> Bool
(Targeting -> Targeting -> Bool)
-> (Targeting -> Targeting -> Bool) -> Eq Targeting
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Targeting -> Targeting -> Bool
$c/= :: Targeting -> Targeting -> Bool
== :: Targeting -> Targeting -> Bool
$c== :: Targeting -> Targeting -> Bool
Eq, Eq Targeting
Eq Targeting
-> (Targeting -> Targeting -> Ordering)
-> (Targeting -> Targeting -> Bool)
-> (Targeting -> Targeting -> Bool)
-> (Targeting -> Targeting -> Bool)
-> (Targeting -> Targeting -> Bool)
-> (Targeting -> Targeting -> Targeting)
-> (Targeting -> Targeting -> Targeting)
-> Ord Targeting
Targeting -> Targeting -> Bool
Targeting -> Targeting -> Ordering
Targeting -> Targeting -> Targeting
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Targeting -> Targeting -> Targeting
$cmin :: Targeting -> Targeting -> Targeting
max :: Targeting -> Targeting -> Targeting
$cmax :: Targeting -> Targeting -> Targeting
>= :: Targeting -> Targeting -> Bool
$c>= :: Targeting -> Targeting -> Bool
> :: Targeting -> Targeting -> Bool
$c> :: Targeting -> Targeting -> Bool
<= :: Targeting -> Targeting -> Bool
$c<= :: Targeting -> Targeting -> Bool
< :: Targeting -> Targeting -> Bool
$c< :: Targeting -> Targeting -> Bool
compare :: Targeting -> Targeting -> Ordering
$ccompare :: Targeting -> Targeting -> Ordering
$cp1Ord :: Eq Targeting
Ord)

-- |
-- ==== References
-- @
-- target_list:
--   | target_el
--   | target_list ',' target_el
-- @
type TargetList = NonEmpty TargetEl

-- |
-- ==== References
-- @
-- target_el:
--   |  a_expr AS ColLabel
--   |  a_expr IDENT
--   |  a_expr
--   |  '*'
-- @
data TargetEl
  = AliasedExprTargetEl AExpr Ident
  | ImplicitlyAliasedExprTargetEl AExpr Ident
  | ExprTargetEl AExpr
  | AsteriskTargetEl
  deriving (Int -> TargetEl -> ShowS
[TargetEl] -> ShowS
TargetEl -> String
(Int -> TargetEl -> ShowS)
-> (TargetEl -> String) -> ([TargetEl] -> ShowS) -> Show TargetEl
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TargetEl] -> ShowS
$cshowList :: [TargetEl] -> ShowS
show :: TargetEl -> String
$cshow :: TargetEl -> String
showsPrec :: Int -> TargetEl -> ShowS
$cshowsPrec :: Int -> TargetEl -> ShowS
Show, (forall x. TargetEl -> Rep TargetEl x)
-> (forall x. Rep TargetEl x -> TargetEl) -> Generic TargetEl
forall x. Rep TargetEl x -> TargetEl
forall x. TargetEl -> Rep TargetEl x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TargetEl x -> TargetEl
$cfrom :: forall x. TargetEl -> Rep TargetEl x
Generic, TargetEl -> TargetEl -> Bool
(TargetEl -> TargetEl -> Bool)
-> (TargetEl -> TargetEl -> Bool) -> Eq TargetEl
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TargetEl -> TargetEl -> Bool
$c/= :: TargetEl -> TargetEl -> Bool
== :: TargetEl -> TargetEl -> Bool
$c== :: TargetEl -> TargetEl -> Bool
Eq, Eq TargetEl
Eq TargetEl
-> (TargetEl -> TargetEl -> Ordering)
-> (TargetEl -> TargetEl -> Bool)
-> (TargetEl -> TargetEl -> Bool)
-> (TargetEl -> TargetEl -> Bool)
-> (TargetEl -> TargetEl -> Bool)
-> (TargetEl -> TargetEl -> TargetEl)
-> (TargetEl -> TargetEl -> TargetEl)
-> Ord TargetEl
TargetEl -> TargetEl -> Bool
TargetEl -> TargetEl -> Ordering
TargetEl -> TargetEl -> TargetEl
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: TargetEl -> TargetEl -> TargetEl
$cmin :: TargetEl -> TargetEl -> TargetEl
max :: TargetEl -> TargetEl -> TargetEl
$cmax :: TargetEl -> TargetEl -> TargetEl
>= :: TargetEl -> TargetEl -> Bool
$c>= :: TargetEl -> TargetEl -> Bool
> :: TargetEl -> TargetEl -> Bool
$c> :: TargetEl -> TargetEl -> Bool
<= :: TargetEl -> TargetEl -> Bool
$c<= :: TargetEl -> TargetEl -> Bool
< :: TargetEl -> TargetEl -> Bool
$c< :: TargetEl -> TargetEl -> Bool
compare :: TargetEl -> TargetEl -> Ordering
$ccompare :: TargetEl -> TargetEl -> Ordering
$cp1Ord :: Eq TargetEl
Ord)

-- |
-- ==== References
-- @
--   |  select_clause UNION all_or_distinct select_clause
--   |  select_clause INTERSECT all_or_distinct select_clause
--   |  select_clause EXCEPT all_or_distinct select_clause
-- @
data SelectBinOp = UnionSelectBinOp | IntersectSelectBinOp | ExceptSelectBinOp
  deriving (Int -> SelectBinOp -> ShowS
[SelectBinOp] -> ShowS
SelectBinOp -> String
(Int -> SelectBinOp -> ShowS)
-> (SelectBinOp -> String)
-> ([SelectBinOp] -> ShowS)
-> Show SelectBinOp
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SelectBinOp] -> ShowS
$cshowList :: [SelectBinOp] -> ShowS
show :: SelectBinOp -> String
$cshow :: SelectBinOp -> String
showsPrec :: Int -> SelectBinOp -> ShowS
$cshowsPrec :: Int -> SelectBinOp -> ShowS
Show, (forall x. SelectBinOp -> Rep SelectBinOp x)
-> (forall x. Rep SelectBinOp x -> SelectBinOp)
-> Generic SelectBinOp
forall x. Rep SelectBinOp x -> SelectBinOp
forall x. SelectBinOp -> Rep SelectBinOp x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SelectBinOp x -> SelectBinOp
$cfrom :: forall x. SelectBinOp -> Rep SelectBinOp x
Generic, SelectBinOp -> SelectBinOp -> Bool
(SelectBinOp -> SelectBinOp -> Bool)
-> (SelectBinOp -> SelectBinOp -> Bool) -> Eq SelectBinOp
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SelectBinOp -> SelectBinOp -> Bool
$c/= :: SelectBinOp -> SelectBinOp -> Bool
== :: SelectBinOp -> SelectBinOp -> Bool
$c== :: SelectBinOp -> SelectBinOp -> Bool
Eq, Eq SelectBinOp
Eq SelectBinOp
-> (SelectBinOp -> SelectBinOp -> Ordering)
-> (SelectBinOp -> SelectBinOp -> Bool)
-> (SelectBinOp -> SelectBinOp -> Bool)
-> (SelectBinOp -> SelectBinOp -> Bool)
-> (SelectBinOp -> SelectBinOp -> Bool)
-> (SelectBinOp -> SelectBinOp -> SelectBinOp)
-> (SelectBinOp -> SelectBinOp -> SelectBinOp)
-> Ord SelectBinOp
SelectBinOp -> SelectBinOp -> Bool
SelectBinOp -> SelectBinOp -> Ordering
SelectBinOp -> SelectBinOp -> SelectBinOp
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: SelectBinOp -> SelectBinOp -> SelectBinOp
$cmin :: SelectBinOp -> SelectBinOp -> SelectBinOp
max :: SelectBinOp -> SelectBinOp -> SelectBinOp
$cmax :: SelectBinOp -> SelectBinOp -> SelectBinOp
>= :: SelectBinOp -> SelectBinOp -> Bool
$c>= :: SelectBinOp -> SelectBinOp -> Bool
> :: SelectBinOp -> SelectBinOp -> Bool
$c> :: SelectBinOp -> SelectBinOp -> Bool
<= :: SelectBinOp -> SelectBinOp -> Bool
$c<= :: SelectBinOp -> SelectBinOp -> Bool
< :: SelectBinOp -> SelectBinOp -> Bool
$c< :: SelectBinOp -> SelectBinOp -> Bool
compare :: SelectBinOp -> SelectBinOp -> Ordering
$ccompare :: SelectBinOp -> SelectBinOp -> Ordering
$cp1Ord :: Eq SelectBinOp
Ord)

-- |
-- ==== References
-- @
-- with_clause:
--   |  WITH cte_list
--   |  WITH_LA cte_list
--   |  WITH RECURSIVE cte_list
-- @
data WithClause = WithClause Bool (NonEmpty CommonTableExpr)
  deriving (Int -> WithClause -> ShowS
[WithClause] -> ShowS
WithClause -> String
(Int -> WithClause -> ShowS)
-> (WithClause -> String)
-> ([WithClause] -> ShowS)
-> Show WithClause
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WithClause] -> ShowS
$cshowList :: [WithClause] -> ShowS
show :: WithClause -> String
$cshow :: WithClause -> String
showsPrec :: Int -> WithClause -> ShowS
$cshowsPrec :: Int -> WithClause -> ShowS
Show, (forall x. WithClause -> Rep WithClause x)
-> (forall x. Rep WithClause x -> WithClause) -> Generic WithClause
forall x. Rep WithClause x -> WithClause
forall x. WithClause -> Rep WithClause x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep WithClause x -> WithClause
$cfrom :: forall x. WithClause -> Rep WithClause x
Generic, WithClause -> WithClause -> Bool
(WithClause -> WithClause -> Bool)
-> (WithClause -> WithClause -> Bool) -> Eq WithClause
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WithClause -> WithClause -> Bool
$c/= :: WithClause -> WithClause -> Bool
== :: WithClause -> WithClause -> Bool
$c== :: WithClause -> WithClause -> Bool
Eq, Eq WithClause
Eq WithClause
-> (WithClause -> WithClause -> Ordering)
-> (WithClause -> WithClause -> Bool)
-> (WithClause -> WithClause -> Bool)
-> (WithClause -> WithClause -> Bool)
-> (WithClause -> WithClause -> Bool)
-> (WithClause -> WithClause -> WithClause)
-> (WithClause -> WithClause -> WithClause)
-> Ord WithClause
WithClause -> WithClause -> Bool
WithClause -> WithClause -> Ordering
WithClause -> WithClause -> WithClause
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: WithClause -> WithClause -> WithClause
$cmin :: WithClause -> WithClause -> WithClause
max :: WithClause -> WithClause -> WithClause
$cmax :: WithClause -> WithClause -> WithClause
>= :: WithClause -> WithClause -> Bool
$c>= :: WithClause -> WithClause -> Bool
> :: WithClause -> WithClause -> Bool
$c> :: WithClause -> WithClause -> Bool
<= :: WithClause -> WithClause -> Bool
$c<= :: WithClause -> WithClause -> Bool
< :: WithClause -> WithClause -> Bool
$c< :: WithClause -> WithClause -> Bool
compare :: WithClause -> WithClause -> Ordering
$ccompare :: WithClause -> WithClause -> Ordering
$cp1Ord :: Eq WithClause
Ord)

-- |
-- ==== References
-- @
-- common_table_expr:
--   |  name opt_name_list AS opt_materialized '(' PreparableStmt ')'
-- opt_materialized:
--   | MATERIALIZED
--   | NOT MATERIALIZED
--   | EMPTY
-- @
data CommonTableExpr = CommonTableExpr Ident (Maybe (NonEmpty Ident)) (Maybe Bool) PreparableStmt
  deriving (Int -> CommonTableExpr -> ShowS
[CommonTableExpr] -> ShowS
CommonTableExpr -> String
(Int -> CommonTableExpr -> ShowS)
-> (CommonTableExpr -> String)
-> ([CommonTableExpr] -> ShowS)
-> Show CommonTableExpr
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CommonTableExpr] -> ShowS
$cshowList :: [CommonTableExpr] -> ShowS
show :: CommonTableExpr -> String
$cshow :: CommonTableExpr -> String
showsPrec :: Int -> CommonTableExpr -> ShowS
$cshowsPrec :: Int -> CommonTableExpr -> ShowS
Show, (forall x. CommonTableExpr -> Rep CommonTableExpr x)
-> (forall x. Rep CommonTableExpr x -> CommonTableExpr)
-> Generic CommonTableExpr
forall x. Rep CommonTableExpr x -> CommonTableExpr
forall x. CommonTableExpr -> Rep CommonTableExpr x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CommonTableExpr x -> CommonTableExpr
$cfrom :: forall x. CommonTableExpr -> Rep CommonTableExpr x
Generic, CommonTableExpr -> CommonTableExpr -> Bool
(CommonTableExpr -> CommonTableExpr -> Bool)
-> (CommonTableExpr -> CommonTableExpr -> Bool)
-> Eq CommonTableExpr
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CommonTableExpr -> CommonTableExpr -> Bool
$c/= :: CommonTableExpr -> CommonTableExpr -> Bool
== :: CommonTableExpr -> CommonTableExpr -> Bool
$c== :: CommonTableExpr -> CommonTableExpr -> Bool
Eq, Eq CommonTableExpr
Eq CommonTableExpr
-> (CommonTableExpr -> CommonTableExpr -> Ordering)
-> (CommonTableExpr -> CommonTableExpr -> Bool)
-> (CommonTableExpr -> CommonTableExpr -> Bool)
-> (CommonTableExpr -> CommonTableExpr -> Bool)
-> (CommonTableExpr -> CommonTableExpr -> Bool)
-> (CommonTableExpr -> CommonTableExpr -> CommonTableExpr)
-> (CommonTableExpr -> CommonTableExpr -> CommonTableExpr)
-> Ord CommonTableExpr
CommonTableExpr -> CommonTableExpr -> Bool
CommonTableExpr -> CommonTableExpr -> Ordering
CommonTableExpr -> CommonTableExpr -> CommonTableExpr
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CommonTableExpr -> CommonTableExpr -> CommonTableExpr
$cmin :: CommonTableExpr -> CommonTableExpr -> CommonTableExpr
max :: CommonTableExpr -> CommonTableExpr -> CommonTableExpr
$cmax :: CommonTableExpr -> CommonTableExpr -> CommonTableExpr
>= :: CommonTableExpr -> CommonTableExpr -> Bool
$c>= :: CommonTableExpr -> CommonTableExpr -> Bool
> :: CommonTableExpr -> CommonTableExpr -> Bool
$c> :: CommonTableExpr -> CommonTableExpr -> Bool
<= :: CommonTableExpr -> CommonTableExpr -> Bool
$c<= :: CommonTableExpr -> CommonTableExpr -> Bool
< :: CommonTableExpr -> CommonTableExpr -> Bool
$c< :: CommonTableExpr -> CommonTableExpr -> Bool
compare :: CommonTableExpr -> CommonTableExpr -> Ordering
$ccompare :: CommonTableExpr -> CommonTableExpr -> Ordering
$cp1Ord :: Eq CommonTableExpr
Ord)

type IntoClause = OptTempTableName

-- |
-- ==== References
-- @
-- OptTempTableName:
--   |  TEMPORARY opt_table qualified_name
--   |  TEMP opt_table qualified_name
--   |  LOCAL TEMPORARY opt_table qualified_name
--   |  LOCAL TEMP opt_table qualified_name
--   |  GLOBAL TEMPORARY opt_table qualified_name
--   |  GLOBAL TEMP opt_table qualified_name
--   |  UNLOGGED opt_table qualified_name
--   |  TABLE qualified_name
--   |  qualified_name
-- @
data OptTempTableName
  = TemporaryOptTempTableName Bool QualifiedName
  | TempOptTempTableName Bool QualifiedName
  | LocalTemporaryOptTempTableName Bool QualifiedName
  | LocalTempOptTempTableName Bool QualifiedName
  | GlobalTemporaryOptTempTableName Bool QualifiedName
  | GlobalTempOptTempTableName Bool QualifiedName
  | UnloggedOptTempTableName Bool QualifiedName
  | TableOptTempTableName QualifiedName
  | QualifedOptTempTableName QualifiedName
  deriving (Int -> OptTempTableName -> ShowS
[OptTempTableName] -> ShowS
OptTempTableName -> String
(Int -> OptTempTableName -> ShowS)
-> (OptTempTableName -> String)
-> ([OptTempTableName] -> ShowS)
-> Show OptTempTableName
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [OptTempTableName] -> ShowS
$cshowList :: [OptTempTableName] -> ShowS
show :: OptTempTableName -> String
$cshow :: OptTempTableName -> String
showsPrec :: Int -> OptTempTableName -> ShowS
$cshowsPrec :: Int -> OptTempTableName -> ShowS
Show, (forall x. OptTempTableName -> Rep OptTempTableName x)
-> (forall x. Rep OptTempTableName x -> OptTempTableName)
-> Generic OptTempTableName
forall x. Rep OptTempTableName x -> OptTempTableName
forall x. OptTempTableName -> Rep OptTempTableName x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep OptTempTableName x -> OptTempTableName
$cfrom :: forall x. OptTempTableName -> Rep OptTempTableName x
Generic, OptTempTableName -> OptTempTableName -> Bool
(OptTempTableName -> OptTempTableName -> Bool)
-> (OptTempTableName -> OptTempTableName -> Bool)
-> Eq OptTempTableName
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OptTempTableName -> OptTempTableName -> Bool
$c/= :: OptTempTableName -> OptTempTableName -> Bool
== :: OptTempTableName -> OptTempTableName -> Bool
$c== :: OptTempTableName -> OptTempTableName -> Bool
Eq, Eq OptTempTableName
Eq OptTempTableName
-> (OptTempTableName -> OptTempTableName -> Ordering)
-> (OptTempTableName -> OptTempTableName -> Bool)
-> (OptTempTableName -> OptTempTableName -> Bool)
-> (OptTempTableName -> OptTempTableName -> Bool)
-> (OptTempTableName -> OptTempTableName -> Bool)
-> (OptTempTableName -> OptTempTableName -> OptTempTableName)
-> (OptTempTableName -> OptTempTableName -> OptTempTableName)
-> Ord OptTempTableName
OptTempTableName -> OptTempTableName -> Bool
OptTempTableName -> OptTempTableName -> Ordering
OptTempTableName -> OptTempTableName -> OptTempTableName
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: OptTempTableName -> OptTempTableName -> OptTempTableName
$cmin :: OptTempTableName -> OptTempTableName -> OptTempTableName
max :: OptTempTableName -> OptTempTableName -> OptTempTableName
$cmax :: OptTempTableName -> OptTempTableName -> OptTempTableName
>= :: OptTempTableName -> OptTempTableName -> Bool
$c>= :: OptTempTableName -> OptTempTableName -> Bool
> :: OptTempTableName -> OptTempTableName -> Bool
$c> :: OptTempTableName -> OptTempTableName -> Bool
<= :: OptTempTableName -> OptTempTableName -> Bool
$c<= :: OptTempTableName -> OptTempTableName -> Bool
< :: OptTempTableName -> OptTempTableName -> Bool
$c< :: OptTempTableName -> OptTempTableName -> Bool
compare :: OptTempTableName -> OptTempTableName -> Ordering
$ccompare :: OptTempTableName -> OptTempTableName -> Ordering
$cp1Ord :: Eq OptTempTableName
Ord)

type FromClause = NonEmpty TableRef

type GroupClause = NonEmpty GroupByItem

-- |
-- ==== References
-- @
-- group_by_item:
--   |  a_expr
--   |  empty_grouping_set
--   |  cube_clause
--   |  rollup_clause
--   |  grouping_sets_clause
-- empty_grouping_set:
--   |  '(' ')'
-- rollup_clause:
--   |  ROLLUP '(' expr_list ')'
-- cube_clause:
--   |  CUBE '(' expr_list ')'
-- grouping_sets_clause:
--   |  GROUPING SETS '(' group_by_list ')'
-- @
data GroupByItem
  = ExprGroupByItem AExpr
  | EmptyGroupingSetGroupByItem
  | RollupGroupByItem ExprList
  | CubeGroupByItem ExprList
  | GroupingSetsGroupByItem (NonEmpty GroupByItem)
  deriving (Int -> GroupByItem -> ShowS
[GroupByItem] -> ShowS
GroupByItem -> String
(Int -> GroupByItem -> ShowS)
-> (GroupByItem -> String)
-> ([GroupByItem] -> ShowS)
-> Show GroupByItem
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GroupByItem] -> ShowS
$cshowList :: [GroupByItem] -> ShowS
show :: GroupByItem -> String
$cshow :: GroupByItem -> String
showsPrec :: Int -> GroupByItem -> ShowS
$cshowsPrec :: Int -> GroupByItem -> ShowS
Show, (forall x. GroupByItem -> Rep GroupByItem x)
-> (forall x. Rep GroupByItem x -> GroupByItem)
-> Generic GroupByItem
forall x. Rep GroupByItem x -> GroupByItem
forall x. GroupByItem -> Rep GroupByItem x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GroupByItem x -> GroupByItem
$cfrom :: forall x. GroupByItem -> Rep GroupByItem x
Generic, GroupByItem -> GroupByItem -> Bool
(GroupByItem -> GroupByItem -> Bool)
-> (GroupByItem -> GroupByItem -> Bool) -> Eq GroupByItem
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GroupByItem -> GroupByItem -> Bool
$c/= :: GroupByItem -> GroupByItem -> Bool
== :: GroupByItem -> GroupByItem -> Bool
$c== :: GroupByItem -> GroupByItem -> Bool
Eq, Eq GroupByItem
Eq GroupByItem
-> (GroupByItem -> GroupByItem -> Ordering)
-> (GroupByItem -> GroupByItem -> Bool)
-> (GroupByItem -> GroupByItem -> Bool)
-> (GroupByItem -> GroupByItem -> Bool)
-> (GroupByItem -> GroupByItem -> Bool)
-> (GroupByItem -> GroupByItem -> GroupByItem)
-> (GroupByItem -> GroupByItem -> GroupByItem)
-> Ord GroupByItem
GroupByItem -> GroupByItem -> Bool
GroupByItem -> GroupByItem -> Ordering
GroupByItem -> GroupByItem -> GroupByItem
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: GroupByItem -> GroupByItem -> GroupByItem
$cmin :: GroupByItem -> GroupByItem -> GroupByItem
max :: GroupByItem -> GroupByItem -> GroupByItem
$cmax :: GroupByItem -> GroupByItem -> GroupByItem
>= :: GroupByItem -> GroupByItem -> Bool
$c>= :: GroupByItem -> GroupByItem -> Bool
> :: GroupByItem -> GroupByItem -> Bool
$c> :: GroupByItem -> GroupByItem -> Bool
<= :: GroupByItem -> GroupByItem -> Bool
$c<= :: GroupByItem -> GroupByItem -> Bool
< :: GroupByItem -> GroupByItem -> Bool
$c< :: GroupByItem -> GroupByItem -> Bool
compare :: GroupByItem -> GroupByItem -> Ordering
$ccompare :: GroupByItem -> GroupByItem -> Ordering
$cp1Ord :: Eq GroupByItem
Ord)

-- |
-- @
-- having_clause:
--   |  HAVING a_expr
--   |  EMPTY
-- @
type HavingClause = AExpr

-- |
-- @
-- window_clause:
--   |  WINDOW window_definition_list
--   |  EMPTY
--
-- window_definition_list:
--   |  window_definition
--   |  window_definition_list ',' window_definition
-- @
type WindowClause = NonEmpty WindowDefinition

-- |
-- @
-- window_definition:
--   |  ColId AS window_specification
-- @
data WindowDefinition = WindowDefinition Ident WindowSpecification
  deriving (Int -> WindowDefinition -> ShowS
[WindowDefinition] -> ShowS
WindowDefinition -> String
(Int -> WindowDefinition -> ShowS)
-> (WindowDefinition -> String)
-> ([WindowDefinition] -> ShowS)
-> Show WindowDefinition
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WindowDefinition] -> ShowS
$cshowList :: [WindowDefinition] -> ShowS
show :: WindowDefinition -> String
$cshow :: WindowDefinition -> String
showsPrec :: Int -> WindowDefinition -> ShowS
$cshowsPrec :: Int -> WindowDefinition -> ShowS
Show, (forall x. WindowDefinition -> Rep WindowDefinition x)
-> (forall x. Rep WindowDefinition x -> WindowDefinition)
-> Generic WindowDefinition
forall x. Rep WindowDefinition x -> WindowDefinition
forall x. WindowDefinition -> Rep WindowDefinition x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep WindowDefinition x -> WindowDefinition
$cfrom :: forall x. WindowDefinition -> Rep WindowDefinition x
Generic, WindowDefinition -> WindowDefinition -> Bool
(WindowDefinition -> WindowDefinition -> Bool)
-> (WindowDefinition -> WindowDefinition -> Bool)
-> Eq WindowDefinition
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WindowDefinition -> WindowDefinition -> Bool
$c/= :: WindowDefinition -> WindowDefinition -> Bool
== :: WindowDefinition -> WindowDefinition -> Bool
$c== :: WindowDefinition -> WindowDefinition -> Bool
Eq, Eq WindowDefinition
Eq WindowDefinition
-> (WindowDefinition -> WindowDefinition -> Ordering)
-> (WindowDefinition -> WindowDefinition -> Bool)
-> (WindowDefinition -> WindowDefinition -> Bool)
-> (WindowDefinition -> WindowDefinition -> Bool)
-> (WindowDefinition -> WindowDefinition -> Bool)
-> (WindowDefinition -> WindowDefinition -> WindowDefinition)
-> (WindowDefinition -> WindowDefinition -> WindowDefinition)
-> Ord WindowDefinition
WindowDefinition -> WindowDefinition -> Bool
WindowDefinition -> WindowDefinition -> Ordering
WindowDefinition -> WindowDefinition -> WindowDefinition
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: WindowDefinition -> WindowDefinition -> WindowDefinition
$cmin :: WindowDefinition -> WindowDefinition -> WindowDefinition
max :: WindowDefinition -> WindowDefinition -> WindowDefinition
$cmax :: WindowDefinition -> WindowDefinition -> WindowDefinition
>= :: WindowDefinition -> WindowDefinition -> Bool
$c>= :: WindowDefinition -> WindowDefinition -> Bool
> :: WindowDefinition -> WindowDefinition -> Bool
$c> :: WindowDefinition -> WindowDefinition -> Bool
<= :: WindowDefinition -> WindowDefinition -> Bool
$c<= :: WindowDefinition -> WindowDefinition -> Bool
< :: WindowDefinition -> WindowDefinition -> Bool
$c< :: WindowDefinition -> WindowDefinition -> Bool
compare :: WindowDefinition -> WindowDefinition -> Ordering
$ccompare :: WindowDefinition -> WindowDefinition -> Ordering
$cp1Ord :: Eq WindowDefinition
Ord)

-- |
-- @
-- 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
-- @
data WindowSpecification = WindowSpecification (Maybe ExistingWindowName) (Maybe PartitionClause) (Maybe SortClause) (Maybe FrameClause)
  deriving (Int -> WindowSpecification -> ShowS
[WindowSpecification] -> ShowS
WindowSpecification -> String
(Int -> WindowSpecification -> ShowS)
-> (WindowSpecification -> String)
-> ([WindowSpecification] -> ShowS)
-> Show WindowSpecification
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WindowSpecification] -> ShowS
$cshowList :: [WindowSpecification] -> ShowS
show :: WindowSpecification -> String
$cshow :: WindowSpecification -> String
showsPrec :: Int -> WindowSpecification -> ShowS
$cshowsPrec :: Int -> WindowSpecification -> ShowS
Show, (forall x. WindowSpecification -> Rep WindowSpecification x)
-> (forall x. Rep WindowSpecification x -> WindowSpecification)
-> Generic WindowSpecification
forall x. Rep WindowSpecification x -> WindowSpecification
forall x. WindowSpecification -> Rep WindowSpecification x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep WindowSpecification x -> WindowSpecification
$cfrom :: forall x. WindowSpecification -> Rep WindowSpecification x
Generic, WindowSpecification -> WindowSpecification -> Bool
(WindowSpecification -> WindowSpecification -> Bool)
-> (WindowSpecification -> WindowSpecification -> Bool)
-> Eq WindowSpecification
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WindowSpecification -> WindowSpecification -> Bool
$c/= :: WindowSpecification -> WindowSpecification -> Bool
== :: WindowSpecification -> WindowSpecification -> Bool
$c== :: WindowSpecification -> WindowSpecification -> Bool
Eq, Eq WindowSpecification
Eq WindowSpecification
-> (WindowSpecification -> WindowSpecification -> Ordering)
-> (WindowSpecification -> WindowSpecification -> Bool)
-> (WindowSpecification -> WindowSpecification -> Bool)
-> (WindowSpecification -> WindowSpecification -> Bool)
-> (WindowSpecification -> WindowSpecification -> Bool)
-> (WindowSpecification
    -> WindowSpecification -> WindowSpecification)
-> (WindowSpecification
    -> WindowSpecification -> WindowSpecification)
-> Ord WindowSpecification
WindowSpecification -> WindowSpecification -> Bool
WindowSpecification -> WindowSpecification -> Ordering
WindowSpecification -> WindowSpecification -> WindowSpecification
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: WindowSpecification -> WindowSpecification -> WindowSpecification
$cmin :: WindowSpecification -> WindowSpecification -> WindowSpecification
max :: WindowSpecification -> WindowSpecification -> WindowSpecification
$cmax :: WindowSpecification -> WindowSpecification -> WindowSpecification
>= :: WindowSpecification -> WindowSpecification -> Bool
$c>= :: WindowSpecification -> WindowSpecification -> Bool
> :: WindowSpecification -> WindowSpecification -> Bool
$c> :: WindowSpecification -> WindowSpecification -> Bool
<= :: WindowSpecification -> WindowSpecification -> Bool
$c<= :: WindowSpecification -> WindowSpecification -> Bool
< :: WindowSpecification -> WindowSpecification -> Bool
$c< :: WindowSpecification -> WindowSpecification -> Bool
compare :: WindowSpecification -> WindowSpecification -> Ordering
$ccompare :: WindowSpecification -> WindowSpecification -> Ordering
$cp1Ord :: Eq WindowSpecification
Ord)

type ExistingWindowName = ColId

type PartitionClause = ExprList

-- |
-- ==== References
-- @
-- opt_frame_clause:
--   |  RANGE frame_extent opt_window_exclusion_clause
--   |  ROWS frame_extent opt_window_exclusion_clause
--   |  GROUPS frame_extent opt_window_exclusion_clause
--   |  EMPTY
-- @
data FrameClause = FrameClause FrameClauseMode FrameExtent (Maybe WindowExclusionClause)
  deriving (Int -> FrameClause -> ShowS
[FrameClause] -> ShowS
FrameClause -> String
(Int -> FrameClause -> ShowS)
-> (FrameClause -> String)
-> ([FrameClause] -> ShowS)
-> Show FrameClause
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FrameClause] -> ShowS
$cshowList :: [FrameClause] -> ShowS
show :: FrameClause -> String
$cshow :: FrameClause -> String
showsPrec :: Int -> FrameClause -> ShowS
$cshowsPrec :: Int -> FrameClause -> ShowS
Show, (forall x. FrameClause -> Rep FrameClause x)
-> (forall x. Rep FrameClause x -> FrameClause)
-> Generic FrameClause
forall x. Rep FrameClause x -> FrameClause
forall x. FrameClause -> Rep FrameClause x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep FrameClause x -> FrameClause
$cfrom :: forall x. FrameClause -> Rep FrameClause x
Generic, FrameClause -> FrameClause -> Bool
(FrameClause -> FrameClause -> Bool)
-> (FrameClause -> FrameClause -> Bool) -> Eq FrameClause
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FrameClause -> FrameClause -> Bool
$c/= :: FrameClause -> FrameClause -> Bool
== :: FrameClause -> FrameClause -> Bool
$c== :: FrameClause -> FrameClause -> Bool
Eq, Eq FrameClause
Eq FrameClause
-> (FrameClause -> FrameClause -> Ordering)
-> (FrameClause -> FrameClause -> Bool)
-> (FrameClause -> FrameClause -> Bool)
-> (FrameClause -> FrameClause -> Bool)
-> (FrameClause -> FrameClause -> Bool)
-> (FrameClause -> FrameClause -> FrameClause)
-> (FrameClause -> FrameClause -> FrameClause)
-> Ord FrameClause
FrameClause -> FrameClause -> Bool
FrameClause -> FrameClause -> Ordering
FrameClause -> FrameClause -> FrameClause
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: FrameClause -> FrameClause -> FrameClause
$cmin :: FrameClause -> FrameClause -> FrameClause
max :: FrameClause -> FrameClause -> FrameClause
$cmax :: FrameClause -> FrameClause -> FrameClause
>= :: FrameClause -> FrameClause -> Bool
$c>= :: FrameClause -> FrameClause -> Bool
> :: FrameClause -> FrameClause -> Bool
$c> :: FrameClause -> FrameClause -> Bool
<= :: FrameClause -> FrameClause -> Bool
$c<= :: FrameClause -> FrameClause -> Bool
< :: FrameClause -> FrameClause -> Bool
$c< :: FrameClause -> FrameClause -> Bool
compare :: FrameClause -> FrameClause -> Ordering
$ccompare :: FrameClause -> FrameClause -> Ordering
$cp1Ord :: Eq FrameClause
Ord)

-- |
-- ==== References
-- @
-- opt_frame_clause:
--   |  RANGE frame_extent opt_window_exclusion_clause
--   |  ROWS frame_extent opt_window_exclusion_clause
--   |  GROUPS frame_extent opt_window_exclusion_clause
--   |  EMPTY
-- @
data FrameClauseMode = RangeFrameClauseMode | RowsFrameClauseMode | GroupsFrameClauseMode
  deriving (Int -> FrameClauseMode -> ShowS
[FrameClauseMode] -> ShowS
FrameClauseMode -> String
(Int -> FrameClauseMode -> ShowS)
-> (FrameClauseMode -> String)
-> ([FrameClauseMode] -> ShowS)
-> Show FrameClauseMode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FrameClauseMode] -> ShowS
$cshowList :: [FrameClauseMode] -> ShowS
show :: FrameClauseMode -> String
$cshow :: FrameClauseMode -> String
showsPrec :: Int -> FrameClauseMode -> ShowS
$cshowsPrec :: Int -> FrameClauseMode -> ShowS
Show, (forall x. FrameClauseMode -> Rep FrameClauseMode x)
-> (forall x. Rep FrameClauseMode x -> FrameClauseMode)
-> Generic FrameClauseMode
forall x. Rep FrameClauseMode x -> FrameClauseMode
forall x. FrameClauseMode -> Rep FrameClauseMode x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep FrameClauseMode x -> FrameClauseMode
$cfrom :: forall x. FrameClauseMode -> Rep FrameClauseMode x
Generic, FrameClauseMode -> FrameClauseMode -> Bool
(FrameClauseMode -> FrameClauseMode -> Bool)
-> (FrameClauseMode -> FrameClauseMode -> Bool)
-> Eq FrameClauseMode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FrameClauseMode -> FrameClauseMode -> Bool
$c/= :: FrameClauseMode -> FrameClauseMode -> Bool
== :: FrameClauseMode -> FrameClauseMode -> Bool
$c== :: FrameClauseMode -> FrameClauseMode -> Bool
Eq, Eq FrameClauseMode
Eq FrameClauseMode
-> (FrameClauseMode -> FrameClauseMode -> Ordering)
-> (FrameClauseMode -> FrameClauseMode -> Bool)
-> (FrameClauseMode -> FrameClauseMode -> Bool)
-> (FrameClauseMode -> FrameClauseMode -> Bool)
-> (FrameClauseMode -> FrameClauseMode -> Bool)
-> (FrameClauseMode -> FrameClauseMode -> FrameClauseMode)
-> (FrameClauseMode -> FrameClauseMode -> FrameClauseMode)
-> Ord FrameClauseMode
FrameClauseMode -> FrameClauseMode -> Bool
FrameClauseMode -> FrameClauseMode -> Ordering
FrameClauseMode -> FrameClauseMode -> FrameClauseMode
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: FrameClauseMode -> FrameClauseMode -> FrameClauseMode
$cmin :: FrameClauseMode -> FrameClauseMode -> FrameClauseMode
max :: FrameClauseMode -> FrameClauseMode -> FrameClauseMode
$cmax :: FrameClauseMode -> FrameClauseMode -> FrameClauseMode
>= :: FrameClauseMode -> FrameClauseMode -> Bool
$c>= :: FrameClauseMode -> FrameClauseMode -> Bool
> :: FrameClauseMode -> FrameClauseMode -> Bool
$c> :: FrameClauseMode -> FrameClauseMode -> Bool
<= :: FrameClauseMode -> FrameClauseMode -> Bool
$c<= :: FrameClauseMode -> FrameClauseMode -> Bool
< :: FrameClauseMode -> FrameClauseMode -> Bool
$c< :: FrameClauseMode -> FrameClauseMode -> Bool
compare :: FrameClauseMode -> FrameClauseMode -> Ordering
$ccompare :: FrameClauseMode -> FrameClauseMode -> Ordering
$cp1Ord :: Eq FrameClauseMode
Ord)

-- |
-- ==== References
-- @
-- frame_extent:
--   |  frame_bound
--   |  BETWEEN frame_bound AND frame_bound
-- @
data FrameExtent = SingularFrameExtent FrameBound | BetweenFrameExtent FrameBound FrameBound
  deriving (Int -> FrameExtent -> ShowS
[FrameExtent] -> ShowS
FrameExtent -> String
(Int -> FrameExtent -> ShowS)
-> (FrameExtent -> String)
-> ([FrameExtent] -> ShowS)
-> Show FrameExtent
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FrameExtent] -> ShowS
$cshowList :: [FrameExtent] -> ShowS
show :: FrameExtent -> String
$cshow :: FrameExtent -> String
showsPrec :: Int -> FrameExtent -> ShowS
$cshowsPrec :: Int -> FrameExtent -> ShowS
Show, (forall x. FrameExtent -> Rep FrameExtent x)
-> (forall x. Rep FrameExtent x -> FrameExtent)
-> Generic FrameExtent
forall x. Rep FrameExtent x -> FrameExtent
forall x. FrameExtent -> Rep FrameExtent x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep FrameExtent x -> FrameExtent
$cfrom :: forall x. FrameExtent -> Rep FrameExtent x
Generic, FrameExtent -> FrameExtent -> Bool
(FrameExtent -> FrameExtent -> Bool)
-> (FrameExtent -> FrameExtent -> Bool) -> Eq FrameExtent
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FrameExtent -> FrameExtent -> Bool
$c/= :: FrameExtent -> FrameExtent -> Bool
== :: FrameExtent -> FrameExtent -> Bool
$c== :: FrameExtent -> FrameExtent -> Bool
Eq, Eq FrameExtent
Eq FrameExtent
-> (FrameExtent -> FrameExtent -> Ordering)
-> (FrameExtent -> FrameExtent -> Bool)
-> (FrameExtent -> FrameExtent -> Bool)
-> (FrameExtent -> FrameExtent -> Bool)
-> (FrameExtent -> FrameExtent -> Bool)
-> (FrameExtent -> FrameExtent -> FrameExtent)
-> (FrameExtent -> FrameExtent -> FrameExtent)
-> Ord FrameExtent
FrameExtent -> FrameExtent -> Bool
FrameExtent -> FrameExtent -> Ordering
FrameExtent -> FrameExtent -> FrameExtent
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: FrameExtent -> FrameExtent -> FrameExtent
$cmin :: FrameExtent -> FrameExtent -> FrameExtent
max :: FrameExtent -> FrameExtent -> FrameExtent
$cmax :: FrameExtent -> FrameExtent -> FrameExtent
>= :: FrameExtent -> FrameExtent -> Bool
$c>= :: FrameExtent -> FrameExtent -> Bool
> :: FrameExtent -> FrameExtent -> Bool
$c> :: FrameExtent -> FrameExtent -> Bool
<= :: FrameExtent -> FrameExtent -> Bool
$c<= :: FrameExtent -> FrameExtent -> Bool
< :: FrameExtent -> FrameExtent -> Bool
$c< :: FrameExtent -> FrameExtent -> Bool
compare :: FrameExtent -> FrameExtent -> Ordering
$ccompare :: FrameExtent -> FrameExtent -> Ordering
$cp1Ord :: Eq FrameExtent
Ord)

-- |
-- ==== References
-- @
-- frame_bound:
--   |  UNBOUNDED PRECEDING
--   |  UNBOUNDED FOLLOWING
--   |  CURRENT_P ROW
--   |  a_expr PRECEDING
--   |  a_expr FOLLOWING
-- @
data FrameBound
  = UnboundedPrecedingFrameBound
  | UnboundedFollowingFrameBound
  | CurrentRowFrameBound
  | PrecedingFrameBound AExpr
  | FollowingFrameBound AExpr
  deriving (Int -> FrameBound -> ShowS
[FrameBound] -> ShowS
FrameBound -> String
(Int -> FrameBound -> ShowS)
-> (FrameBound -> String)
-> ([FrameBound] -> ShowS)
-> Show FrameBound
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FrameBound] -> ShowS
$cshowList :: [FrameBound] -> ShowS
show :: FrameBound -> String
$cshow :: FrameBound -> String
showsPrec :: Int -> FrameBound -> ShowS
$cshowsPrec :: Int -> FrameBound -> ShowS
Show, (forall x. FrameBound -> Rep FrameBound x)
-> (forall x. Rep FrameBound x -> FrameBound) -> Generic FrameBound
forall x. Rep FrameBound x -> FrameBound
forall x. FrameBound -> Rep FrameBound x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep FrameBound x -> FrameBound
$cfrom :: forall x. FrameBound -> Rep FrameBound x
Generic, FrameBound -> FrameBound -> Bool
(FrameBound -> FrameBound -> Bool)
-> (FrameBound -> FrameBound -> Bool) -> Eq FrameBound
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FrameBound -> FrameBound -> Bool
$c/= :: FrameBound -> FrameBound -> Bool
== :: FrameBound -> FrameBound -> Bool
$c== :: FrameBound -> FrameBound -> Bool
Eq, Eq FrameBound
Eq FrameBound
-> (FrameBound -> FrameBound -> Ordering)
-> (FrameBound -> FrameBound -> Bool)
-> (FrameBound -> FrameBound -> Bool)
-> (FrameBound -> FrameBound -> Bool)
-> (FrameBound -> FrameBound -> Bool)
-> (FrameBound -> FrameBound -> FrameBound)
-> (FrameBound -> FrameBound -> FrameBound)
-> Ord FrameBound
FrameBound -> FrameBound -> Bool
FrameBound -> FrameBound -> Ordering
FrameBound -> FrameBound -> FrameBound
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: FrameBound -> FrameBound -> FrameBound
$cmin :: FrameBound -> FrameBound -> FrameBound
max :: FrameBound -> FrameBound -> FrameBound
$cmax :: FrameBound -> FrameBound -> FrameBound
>= :: FrameBound -> FrameBound -> Bool
$c>= :: FrameBound -> FrameBound -> Bool
> :: FrameBound -> FrameBound -> Bool
$c> :: FrameBound -> FrameBound -> Bool
<= :: FrameBound -> FrameBound -> Bool
$c<= :: FrameBound -> FrameBound -> Bool
< :: FrameBound -> FrameBound -> Bool
$c< :: FrameBound -> FrameBound -> Bool
compare :: FrameBound -> FrameBound -> Ordering
$ccompare :: FrameBound -> FrameBound -> Ordering
$cp1Ord :: Eq FrameBound
Ord)

-- |
-- ==== References
-- @
-- opt_window_exclusion_clause:
--   |  EXCLUDE CURRENT_P ROW
--   |  EXCLUDE GROUP_P
--   |  EXCLUDE TIES
--   |  EXCLUDE NO OTHERS
--   |  EMPTY
-- @
data WindowExclusionClause
  = CurrentRowWindowExclusionClause
  | GroupWindowExclusionClause
  | TiesWindowExclusionClause
  | NoOthersWindowExclusionClause
  deriving (Int -> WindowExclusionClause -> ShowS
[WindowExclusionClause] -> ShowS
WindowExclusionClause -> String
(Int -> WindowExclusionClause -> ShowS)
-> (WindowExclusionClause -> String)
-> ([WindowExclusionClause] -> ShowS)
-> Show WindowExclusionClause
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WindowExclusionClause] -> ShowS
$cshowList :: [WindowExclusionClause] -> ShowS
show :: WindowExclusionClause -> String
$cshow :: WindowExclusionClause -> String
showsPrec :: Int -> WindowExclusionClause -> ShowS
$cshowsPrec :: Int -> WindowExclusionClause -> ShowS
Show, (forall x. WindowExclusionClause -> Rep WindowExclusionClause x)
-> (forall x. Rep WindowExclusionClause x -> WindowExclusionClause)
-> Generic WindowExclusionClause
forall x. Rep WindowExclusionClause x -> WindowExclusionClause
forall x. WindowExclusionClause -> Rep WindowExclusionClause x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep WindowExclusionClause x -> WindowExclusionClause
$cfrom :: forall x. WindowExclusionClause -> Rep WindowExclusionClause x
Generic, WindowExclusionClause -> WindowExclusionClause -> Bool
(WindowExclusionClause -> WindowExclusionClause -> Bool)
-> (WindowExclusionClause -> WindowExclusionClause -> Bool)
-> Eq WindowExclusionClause
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WindowExclusionClause -> WindowExclusionClause -> Bool
$c/= :: WindowExclusionClause -> WindowExclusionClause -> Bool
== :: WindowExclusionClause -> WindowExclusionClause -> Bool
$c== :: WindowExclusionClause -> WindowExclusionClause -> Bool
Eq, Eq WindowExclusionClause
Eq WindowExclusionClause
-> (WindowExclusionClause -> WindowExclusionClause -> Ordering)
-> (WindowExclusionClause -> WindowExclusionClause -> Bool)
-> (WindowExclusionClause -> WindowExclusionClause -> Bool)
-> (WindowExclusionClause -> WindowExclusionClause -> Bool)
-> (WindowExclusionClause -> WindowExclusionClause -> Bool)
-> (WindowExclusionClause
    -> WindowExclusionClause -> WindowExclusionClause)
-> (WindowExclusionClause
    -> WindowExclusionClause -> WindowExclusionClause)
-> Ord WindowExclusionClause
WindowExclusionClause -> WindowExclusionClause -> Bool
WindowExclusionClause -> WindowExclusionClause -> Ordering
WindowExclusionClause
-> WindowExclusionClause -> WindowExclusionClause
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: WindowExclusionClause
-> WindowExclusionClause -> WindowExclusionClause
$cmin :: WindowExclusionClause
-> WindowExclusionClause -> WindowExclusionClause
max :: WindowExclusionClause
-> WindowExclusionClause -> WindowExclusionClause
$cmax :: WindowExclusionClause
-> WindowExclusionClause -> WindowExclusionClause
>= :: WindowExclusionClause -> WindowExclusionClause -> Bool
$c>= :: WindowExclusionClause -> WindowExclusionClause -> Bool
> :: WindowExclusionClause -> WindowExclusionClause -> Bool
$c> :: WindowExclusionClause -> WindowExclusionClause -> Bool
<= :: WindowExclusionClause -> WindowExclusionClause -> Bool
$c<= :: WindowExclusionClause -> WindowExclusionClause -> Bool
< :: WindowExclusionClause -> WindowExclusionClause -> Bool
$c< :: WindowExclusionClause -> WindowExclusionClause -> Bool
compare :: WindowExclusionClause -> WindowExclusionClause -> Ordering
$ccompare :: WindowExclusionClause -> WindowExclusionClause -> Ordering
$cp1Ord :: Eq WindowExclusionClause
Ord)

-- |
-- ==== References
-- @
-- values_clause:
--   |  VALUES '(' expr_list ')'
--   |  values_clause ',' '(' expr_list ')'
-- @
type ValuesClause = NonEmpty ExprList

-- |
--
-- sort_clause:
--   |  ORDER BY sortby_list
--
-- sortby_list:
--   |  sortby
--   |  sortby_list ',' sortby
type SortClause = NonEmpty SortBy

-- |
-- ==== References
-- @
-- sortby:
--   |  a_expr USING qual_all_Op opt_nulls_order
--   |  a_expr opt_asc_desc opt_nulls_order
-- @
data SortBy
  = UsingSortBy AExpr QualAllOp (Maybe NullsOrder)
  | AscDescSortBy AExpr (Maybe AscDesc) (Maybe NullsOrder)
  deriving (Int -> SortBy -> ShowS
[SortBy] -> ShowS
SortBy -> String
(Int -> SortBy -> ShowS)
-> (SortBy -> String) -> ([SortBy] -> ShowS) -> Show SortBy
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SortBy] -> ShowS
$cshowList :: [SortBy] -> ShowS
show :: SortBy -> String
$cshow :: SortBy -> String
showsPrec :: Int -> SortBy -> ShowS
$cshowsPrec :: Int -> SortBy -> ShowS
Show, (forall x. SortBy -> Rep SortBy x)
-> (forall x. Rep SortBy x -> SortBy) -> Generic SortBy
forall x. Rep SortBy x -> SortBy
forall x. SortBy -> Rep SortBy x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SortBy x -> SortBy
$cfrom :: forall x. SortBy -> Rep SortBy x
Generic, SortBy -> SortBy -> Bool
(SortBy -> SortBy -> Bool)
-> (SortBy -> SortBy -> Bool) -> Eq SortBy
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SortBy -> SortBy -> Bool
$c/= :: SortBy -> SortBy -> Bool
== :: SortBy -> SortBy -> Bool
$c== :: SortBy -> SortBy -> Bool
Eq, Eq SortBy
Eq SortBy
-> (SortBy -> SortBy -> Ordering)
-> (SortBy -> SortBy -> Bool)
-> (SortBy -> SortBy -> Bool)
-> (SortBy -> SortBy -> Bool)
-> (SortBy -> SortBy -> Bool)
-> (SortBy -> SortBy -> SortBy)
-> (SortBy -> SortBy -> SortBy)
-> Ord SortBy
SortBy -> SortBy -> Bool
SortBy -> SortBy -> Ordering
SortBy -> SortBy -> SortBy
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: SortBy -> SortBy -> SortBy
$cmin :: SortBy -> SortBy -> SortBy
max :: SortBy -> SortBy -> SortBy
$cmax :: SortBy -> SortBy -> SortBy
>= :: SortBy -> SortBy -> Bool
$c>= :: SortBy -> SortBy -> Bool
> :: SortBy -> SortBy -> Bool
$c> :: SortBy -> SortBy -> Bool
<= :: SortBy -> SortBy -> Bool
$c<= :: SortBy -> SortBy -> Bool
< :: SortBy -> SortBy -> Bool
$c< :: SortBy -> SortBy -> Bool
compare :: SortBy -> SortBy -> Ordering
$ccompare :: SortBy -> SortBy -> Ordering
$cp1Ord :: Eq SortBy
Ord)

-- |
-- ==== References
-- @
-- select_limit:
--   | limit_clause offset_clause
--   | offset_clause limit_clause
--   | limit_clause
--   | offset_clause
-- @
data SelectLimit
  = LimitOffsetSelectLimit LimitClause OffsetClause
  | OffsetLimitSelectLimit OffsetClause LimitClause
  | LimitSelectLimit LimitClause
  | OffsetSelectLimit OffsetClause
  deriving (Int -> SelectLimit -> ShowS
[SelectLimit] -> ShowS
SelectLimit -> String
(Int -> SelectLimit -> ShowS)
-> (SelectLimit -> String)
-> ([SelectLimit] -> ShowS)
-> Show SelectLimit
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SelectLimit] -> ShowS
$cshowList :: [SelectLimit] -> ShowS
show :: SelectLimit -> String
$cshow :: SelectLimit -> String
showsPrec :: Int -> SelectLimit -> ShowS
$cshowsPrec :: Int -> SelectLimit -> ShowS
Show, (forall x. SelectLimit -> Rep SelectLimit x)
-> (forall x. Rep SelectLimit x -> SelectLimit)
-> Generic SelectLimit
forall x. Rep SelectLimit x -> SelectLimit
forall x. SelectLimit -> Rep SelectLimit x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SelectLimit x -> SelectLimit
$cfrom :: forall x. SelectLimit -> Rep SelectLimit x
Generic, SelectLimit -> SelectLimit -> Bool
(SelectLimit -> SelectLimit -> Bool)
-> (SelectLimit -> SelectLimit -> Bool) -> Eq SelectLimit
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SelectLimit -> SelectLimit -> Bool
$c/= :: SelectLimit -> SelectLimit -> Bool
== :: SelectLimit -> SelectLimit -> Bool
$c== :: SelectLimit -> SelectLimit -> Bool
Eq, Eq SelectLimit
Eq SelectLimit
-> (SelectLimit -> SelectLimit -> Ordering)
-> (SelectLimit -> SelectLimit -> Bool)
-> (SelectLimit -> SelectLimit -> Bool)
-> (SelectLimit -> SelectLimit -> Bool)
-> (SelectLimit -> SelectLimit -> Bool)
-> (SelectLimit -> SelectLimit -> SelectLimit)
-> (SelectLimit -> SelectLimit -> SelectLimit)
-> Ord SelectLimit
SelectLimit -> SelectLimit -> Bool
SelectLimit -> SelectLimit -> Ordering
SelectLimit -> SelectLimit -> SelectLimit
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: SelectLimit -> SelectLimit -> SelectLimit
$cmin :: SelectLimit -> SelectLimit -> SelectLimit
max :: SelectLimit -> SelectLimit -> SelectLimit
$cmax :: SelectLimit -> SelectLimit -> SelectLimit
>= :: SelectLimit -> SelectLimit -> Bool
$c>= :: SelectLimit -> SelectLimit -> Bool
> :: SelectLimit -> SelectLimit -> Bool
$c> :: SelectLimit -> SelectLimit -> Bool
<= :: SelectLimit -> SelectLimit -> Bool
$c<= :: SelectLimit -> SelectLimit -> Bool
< :: SelectLimit -> SelectLimit -> Bool
$c< :: SelectLimit -> SelectLimit -> Bool
compare :: SelectLimit -> SelectLimit -> Ordering
$ccompare :: SelectLimit -> SelectLimit -> Ordering
$cp1Ord :: Eq SelectLimit
Ord)

-- |
-- ==== References
-- @
-- limit_clause:
--   | LIMIT select_limit_value
--   | LIMIT select_limit_value ',' select_offset_value
--   | FETCH first_or_next select_fetch_first_value row_or_rows ONLY
--   | FETCH first_or_next row_or_rows ONLY
-- select_offset_value:
--   | a_expr
-- first_or_next:
--   | FIRST_P
--   | NEXT
-- row_or_rows:
--   | ROW
--   | ROWS
-- @
data LimitClause
  = LimitLimitClause SelectLimitValue (Maybe AExpr)
  | FetchOnlyLimitClause Bool (Maybe SelectFetchFirstValue) Bool
  deriving (Int -> LimitClause -> ShowS
[LimitClause] -> ShowS
LimitClause -> String
(Int -> LimitClause -> ShowS)
-> (LimitClause -> String)
-> ([LimitClause] -> ShowS)
-> Show LimitClause
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LimitClause] -> ShowS
$cshowList :: [LimitClause] -> ShowS
show :: LimitClause -> String
$cshow :: LimitClause -> String
showsPrec :: Int -> LimitClause -> ShowS
$cshowsPrec :: Int -> LimitClause -> ShowS
Show, (forall x. LimitClause -> Rep LimitClause x)
-> (forall x. Rep LimitClause x -> LimitClause)
-> Generic LimitClause
forall x. Rep LimitClause x -> LimitClause
forall x. LimitClause -> Rep LimitClause x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep LimitClause x -> LimitClause
$cfrom :: forall x. LimitClause -> Rep LimitClause x
Generic, LimitClause -> LimitClause -> Bool
(LimitClause -> LimitClause -> Bool)
-> (LimitClause -> LimitClause -> Bool) -> Eq LimitClause
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LimitClause -> LimitClause -> Bool
$c/= :: LimitClause -> LimitClause -> Bool
== :: LimitClause -> LimitClause -> Bool
$c== :: LimitClause -> LimitClause -> Bool
Eq, Eq LimitClause
Eq LimitClause
-> (LimitClause -> LimitClause -> Ordering)
-> (LimitClause -> LimitClause -> Bool)
-> (LimitClause -> LimitClause -> Bool)
-> (LimitClause -> LimitClause -> Bool)
-> (LimitClause -> LimitClause -> Bool)
-> (LimitClause -> LimitClause -> LimitClause)
-> (LimitClause -> LimitClause -> LimitClause)
-> Ord LimitClause
LimitClause -> LimitClause -> Bool
LimitClause -> LimitClause -> Ordering
LimitClause -> LimitClause -> LimitClause
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: LimitClause -> LimitClause -> LimitClause
$cmin :: LimitClause -> LimitClause -> LimitClause
max :: LimitClause -> LimitClause -> LimitClause
$cmax :: LimitClause -> LimitClause -> LimitClause
>= :: LimitClause -> LimitClause -> Bool
$c>= :: LimitClause -> LimitClause -> Bool
> :: LimitClause -> LimitClause -> Bool
$c> :: LimitClause -> LimitClause -> Bool
<= :: LimitClause -> LimitClause -> Bool
$c<= :: LimitClause -> LimitClause -> Bool
< :: LimitClause -> LimitClause -> Bool
$c< :: LimitClause -> LimitClause -> Bool
compare :: LimitClause -> LimitClause -> Ordering
$ccompare :: LimitClause -> LimitClause -> Ordering
$cp1Ord :: Eq LimitClause
Ord)

-- |
-- ==== References
-- @
-- select_fetch_first_value:
--   | c_expr
--   | '+' I_or_F_const
--   | '-' I_or_F_const
-- @
data SelectFetchFirstValue
  = ExprSelectFetchFirstValue CExpr
  | NumSelectFetchFirstValue Bool (Either Int64 Double)
  deriving (Int -> SelectFetchFirstValue -> ShowS
[SelectFetchFirstValue] -> ShowS
SelectFetchFirstValue -> String
(Int -> SelectFetchFirstValue -> ShowS)
-> (SelectFetchFirstValue -> String)
-> ([SelectFetchFirstValue] -> ShowS)
-> Show SelectFetchFirstValue
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SelectFetchFirstValue] -> ShowS
$cshowList :: [SelectFetchFirstValue] -> ShowS
show :: SelectFetchFirstValue -> String
$cshow :: SelectFetchFirstValue -> String
showsPrec :: Int -> SelectFetchFirstValue -> ShowS
$cshowsPrec :: Int -> SelectFetchFirstValue -> ShowS
Show, (forall x. SelectFetchFirstValue -> Rep SelectFetchFirstValue x)
-> (forall x. Rep SelectFetchFirstValue x -> SelectFetchFirstValue)
-> Generic SelectFetchFirstValue
forall x. Rep SelectFetchFirstValue x -> SelectFetchFirstValue
forall x. SelectFetchFirstValue -> Rep SelectFetchFirstValue x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SelectFetchFirstValue x -> SelectFetchFirstValue
$cfrom :: forall x. SelectFetchFirstValue -> Rep SelectFetchFirstValue x
Generic, SelectFetchFirstValue -> SelectFetchFirstValue -> Bool
(SelectFetchFirstValue -> SelectFetchFirstValue -> Bool)
-> (SelectFetchFirstValue -> SelectFetchFirstValue -> Bool)
-> Eq SelectFetchFirstValue
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SelectFetchFirstValue -> SelectFetchFirstValue -> Bool
$c/= :: SelectFetchFirstValue -> SelectFetchFirstValue -> Bool
== :: SelectFetchFirstValue -> SelectFetchFirstValue -> Bool
$c== :: SelectFetchFirstValue -> SelectFetchFirstValue -> Bool
Eq, Eq SelectFetchFirstValue
Eq SelectFetchFirstValue
-> (SelectFetchFirstValue -> SelectFetchFirstValue -> Ordering)
-> (SelectFetchFirstValue -> SelectFetchFirstValue -> Bool)
-> (SelectFetchFirstValue -> SelectFetchFirstValue -> Bool)
-> (SelectFetchFirstValue -> SelectFetchFirstValue -> Bool)
-> (SelectFetchFirstValue -> SelectFetchFirstValue -> Bool)
-> (SelectFetchFirstValue
    -> SelectFetchFirstValue -> SelectFetchFirstValue)
-> (SelectFetchFirstValue
    -> SelectFetchFirstValue -> SelectFetchFirstValue)
-> Ord SelectFetchFirstValue
SelectFetchFirstValue -> SelectFetchFirstValue -> Bool
SelectFetchFirstValue -> SelectFetchFirstValue -> Ordering
SelectFetchFirstValue
-> SelectFetchFirstValue -> SelectFetchFirstValue
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: SelectFetchFirstValue
-> SelectFetchFirstValue -> SelectFetchFirstValue
$cmin :: SelectFetchFirstValue
-> SelectFetchFirstValue -> SelectFetchFirstValue
max :: SelectFetchFirstValue
-> SelectFetchFirstValue -> SelectFetchFirstValue
$cmax :: SelectFetchFirstValue
-> SelectFetchFirstValue -> SelectFetchFirstValue
>= :: SelectFetchFirstValue -> SelectFetchFirstValue -> Bool
$c>= :: SelectFetchFirstValue -> SelectFetchFirstValue -> Bool
> :: SelectFetchFirstValue -> SelectFetchFirstValue -> Bool
$c> :: SelectFetchFirstValue -> SelectFetchFirstValue -> Bool
<= :: SelectFetchFirstValue -> SelectFetchFirstValue -> Bool
$c<= :: SelectFetchFirstValue -> SelectFetchFirstValue -> Bool
< :: SelectFetchFirstValue -> SelectFetchFirstValue -> Bool
$c< :: SelectFetchFirstValue -> SelectFetchFirstValue -> Bool
compare :: SelectFetchFirstValue -> SelectFetchFirstValue -> Ordering
$ccompare :: SelectFetchFirstValue -> SelectFetchFirstValue -> Ordering
$cp1Ord :: Eq SelectFetchFirstValue
Ord)

-- |
-- ==== References
-- @
-- select_limit_value:
--   | a_expr
--   | ALL
-- @
data SelectLimitValue
  = ExprSelectLimitValue AExpr
  | AllSelectLimitValue
  deriving (Int -> SelectLimitValue -> ShowS
[SelectLimitValue] -> ShowS
SelectLimitValue -> String
(Int -> SelectLimitValue -> ShowS)
-> (SelectLimitValue -> String)
-> ([SelectLimitValue] -> ShowS)
-> Show SelectLimitValue
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SelectLimitValue] -> ShowS
$cshowList :: [SelectLimitValue] -> ShowS
show :: SelectLimitValue -> String
$cshow :: SelectLimitValue -> String
showsPrec :: Int -> SelectLimitValue -> ShowS
$cshowsPrec :: Int -> SelectLimitValue -> ShowS
Show, (forall x. SelectLimitValue -> Rep SelectLimitValue x)
-> (forall x. Rep SelectLimitValue x -> SelectLimitValue)
-> Generic SelectLimitValue
forall x. Rep SelectLimitValue x -> SelectLimitValue
forall x. SelectLimitValue -> Rep SelectLimitValue x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SelectLimitValue x -> SelectLimitValue
$cfrom :: forall x. SelectLimitValue -> Rep SelectLimitValue x
Generic, SelectLimitValue -> SelectLimitValue -> Bool
(SelectLimitValue -> SelectLimitValue -> Bool)
-> (SelectLimitValue -> SelectLimitValue -> Bool)
-> Eq SelectLimitValue
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SelectLimitValue -> SelectLimitValue -> Bool
$c/= :: SelectLimitValue -> SelectLimitValue -> Bool
== :: SelectLimitValue -> SelectLimitValue -> Bool
$c== :: SelectLimitValue -> SelectLimitValue -> Bool
Eq, Eq SelectLimitValue
Eq SelectLimitValue
-> (SelectLimitValue -> SelectLimitValue -> Ordering)
-> (SelectLimitValue -> SelectLimitValue -> Bool)
-> (SelectLimitValue -> SelectLimitValue -> Bool)
-> (SelectLimitValue -> SelectLimitValue -> Bool)
-> (SelectLimitValue -> SelectLimitValue -> Bool)
-> (SelectLimitValue -> SelectLimitValue -> SelectLimitValue)
-> (SelectLimitValue -> SelectLimitValue -> SelectLimitValue)
-> Ord SelectLimitValue
SelectLimitValue -> SelectLimitValue -> Bool
SelectLimitValue -> SelectLimitValue -> Ordering
SelectLimitValue -> SelectLimitValue -> SelectLimitValue
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: SelectLimitValue -> SelectLimitValue -> SelectLimitValue
$cmin :: SelectLimitValue -> SelectLimitValue -> SelectLimitValue
max :: SelectLimitValue -> SelectLimitValue -> SelectLimitValue
$cmax :: SelectLimitValue -> SelectLimitValue -> SelectLimitValue
>= :: SelectLimitValue -> SelectLimitValue -> Bool
$c>= :: SelectLimitValue -> SelectLimitValue -> Bool
> :: SelectLimitValue -> SelectLimitValue -> Bool
$c> :: SelectLimitValue -> SelectLimitValue -> Bool
<= :: SelectLimitValue -> SelectLimitValue -> Bool
$c<= :: SelectLimitValue -> SelectLimitValue -> Bool
< :: SelectLimitValue -> SelectLimitValue -> Bool
$c< :: SelectLimitValue -> SelectLimitValue -> Bool
compare :: SelectLimitValue -> SelectLimitValue -> Ordering
$ccompare :: SelectLimitValue -> SelectLimitValue -> Ordering
$cp1Ord :: Eq SelectLimitValue
Ord)

-- |
-- ==== References
-- @
-- offset_clause:
--   | OFFSET select_offset_value
--   | OFFSET select_fetch_first_value row_or_rows
-- select_offset_value:
--   | a_expr
-- row_or_rows:
--   | ROW
--   | ROWS
-- @
data OffsetClause
  = ExprOffsetClause AExpr
  | FetchFirstOffsetClause SelectFetchFirstValue Bool
  deriving (Int -> OffsetClause -> ShowS
[OffsetClause] -> ShowS
OffsetClause -> String
(Int -> OffsetClause -> ShowS)
-> (OffsetClause -> String)
-> ([OffsetClause] -> ShowS)
-> Show OffsetClause
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [OffsetClause] -> ShowS
$cshowList :: [OffsetClause] -> ShowS
show :: OffsetClause -> String
$cshow :: OffsetClause -> String
showsPrec :: Int -> OffsetClause -> ShowS
$cshowsPrec :: Int -> OffsetClause -> ShowS
Show, (forall x. OffsetClause -> Rep OffsetClause x)
-> (forall x. Rep OffsetClause x -> OffsetClause)
-> Generic OffsetClause
forall x. Rep OffsetClause x -> OffsetClause
forall x. OffsetClause -> Rep OffsetClause x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep OffsetClause x -> OffsetClause
$cfrom :: forall x. OffsetClause -> Rep OffsetClause x
Generic, OffsetClause -> OffsetClause -> Bool
(OffsetClause -> OffsetClause -> Bool)
-> (OffsetClause -> OffsetClause -> Bool) -> Eq OffsetClause
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OffsetClause -> OffsetClause -> Bool
$c/= :: OffsetClause -> OffsetClause -> Bool
== :: OffsetClause -> OffsetClause -> Bool
$c== :: OffsetClause -> OffsetClause -> Bool
Eq, Eq OffsetClause
Eq OffsetClause
-> (OffsetClause -> OffsetClause -> Ordering)
-> (OffsetClause -> OffsetClause -> Bool)
-> (OffsetClause -> OffsetClause -> Bool)
-> (OffsetClause -> OffsetClause -> Bool)
-> (OffsetClause -> OffsetClause -> Bool)
-> (OffsetClause -> OffsetClause -> OffsetClause)
-> (OffsetClause -> OffsetClause -> OffsetClause)
-> Ord OffsetClause
OffsetClause -> OffsetClause -> Bool
OffsetClause -> OffsetClause -> Ordering
OffsetClause -> OffsetClause -> OffsetClause
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: OffsetClause -> OffsetClause -> OffsetClause
$cmin :: OffsetClause -> OffsetClause -> OffsetClause
max :: OffsetClause -> OffsetClause -> OffsetClause
$cmax :: OffsetClause -> OffsetClause -> OffsetClause
>= :: OffsetClause -> OffsetClause -> Bool
$c>= :: OffsetClause -> OffsetClause -> Bool
> :: OffsetClause -> OffsetClause -> Bool
$c> :: OffsetClause -> OffsetClause -> Bool
<= :: OffsetClause -> OffsetClause -> Bool
$c<= :: OffsetClause -> OffsetClause -> Bool
< :: OffsetClause -> OffsetClause -> Bool
$c< :: OffsetClause -> OffsetClause -> Bool
compare :: OffsetClause -> OffsetClause -> Ordering
$ccompare :: OffsetClause -> OffsetClause -> Ordering
$cp1Ord :: Eq OffsetClause
Ord)

-- * For Locking

-- |
-- ==== References
-- @
-- for_locking_clause:
--   | for_locking_items
--   | FOR READ ONLY
-- for_locking_items:
--   | for_locking_item
--   | for_locking_items for_locking_item
-- @
data ForLockingClause
  = ItemsForLockingClause (NonEmpty ForLockingItem)
  | ReadOnlyForLockingClause
  deriving (Int -> ForLockingClause -> ShowS
[ForLockingClause] -> ShowS
ForLockingClause -> String
(Int -> ForLockingClause -> ShowS)
-> (ForLockingClause -> String)
-> ([ForLockingClause] -> ShowS)
-> Show ForLockingClause
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ForLockingClause] -> ShowS
$cshowList :: [ForLockingClause] -> ShowS
show :: ForLockingClause -> String
$cshow :: ForLockingClause -> String
showsPrec :: Int -> ForLockingClause -> ShowS
$cshowsPrec :: Int -> ForLockingClause -> ShowS
Show, (forall x. ForLockingClause -> Rep ForLockingClause x)
-> (forall x. Rep ForLockingClause x -> ForLockingClause)
-> Generic ForLockingClause
forall x. Rep ForLockingClause x -> ForLockingClause
forall x. ForLockingClause -> Rep ForLockingClause x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ForLockingClause x -> ForLockingClause
$cfrom :: forall x. ForLockingClause -> Rep ForLockingClause x
Generic, ForLockingClause -> ForLockingClause -> Bool
(ForLockingClause -> ForLockingClause -> Bool)
-> (ForLockingClause -> ForLockingClause -> Bool)
-> Eq ForLockingClause
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ForLockingClause -> ForLockingClause -> Bool
$c/= :: ForLockingClause -> ForLockingClause -> Bool
== :: ForLockingClause -> ForLockingClause -> Bool
$c== :: ForLockingClause -> ForLockingClause -> Bool
Eq, Eq ForLockingClause
Eq ForLockingClause
-> (ForLockingClause -> ForLockingClause -> Ordering)
-> (ForLockingClause -> ForLockingClause -> Bool)
-> (ForLockingClause -> ForLockingClause -> Bool)
-> (ForLockingClause -> ForLockingClause -> Bool)
-> (ForLockingClause -> ForLockingClause -> Bool)
-> (ForLockingClause -> ForLockingClause -> ForLockingClause)
-> (ForLockingClause -> ForLockingClause -> ForLockingClause)
-> Ord ForLockingClause
ForLockingClause -> ForLockingClause -> Bool
ForLockingClause -> ForLockingClause -> Ordering
ForLockingClause -> ForLockingClause -> ForLockingClause
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ForLockingClause -> ForLockingClause -> ForLockingClause
$cmin :: ForLockingClause -> ForLockingClause -> ForLockingClause
max :: ForLockingClause -> ForLockingClause -> ForLockingClause
$cmax :: ForLockingClause -> ForLockingClause -> ForLockingClause
>= :: ForLockingClause -> ForLockingClause -> Bool
$c>= :: ForLockingClause -> ForLockingClause -> Bool
> :: ForLockingClause -> ForLockingClause -> Bool
$c> :: ForLockingClause -> ForLockingClause -> Bool
<= :: ForLockingClause -> ForLockingClause -> Bool
$c<= :: ForLockingClause -> ForLockingClause -> Bool
< :: ForLockingClause -> ForLockingClause -> Bool
$c< :: ForLockingClause -> ForLockingClause -> Bool
compare :: ForLockingClause -> ForLockingClause -> Ordering
$ccompare :: ForLockingClause -> ForLockingClause -> Ordering
$cp1Ord :: Eq ForLockingClause
Ord)

-- |
-- ==== References
-- @
-- for_locking_item:
--   | for_locking_strength locked_rels_list opt_nowait_or_skip
-- locked_rels_list:
--   | OF qualified_name_list
--   | EMPTY
-- opt_nowait_or_skip:
--   | NOWAIT
--   | SKIP LOCKED
--   | EMPTY
-- @
data ForLockingItem = ForLockingItem ForLockingStrength (Maybe (NonEmpty QualifiedName)) (Maybe Bool)
  deriving (Int -> ForLockingItem -> ShowS
[ForLockingItem] -> ShowS
ForLockingItem -> String
(Int -> ForLockingItem -> ShowS)
-> (ForLockingItem -> String)
-> ([ForLockingItem] -> ShowS)
-> Show ForLockingItem
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ForLockingItem] -> ShowS
$cshowList :: [ForLockingItem] -> ShowS
show :: ForLockingItem -> String
$cshow :: ForLockingItem -> String
showsPrec :: Int -> ForLockingItem -> ShowS
$cshowsPrec :: Int -> ForLockingItem -> ShowS
Show, (forall x. ForLockingItem -> Rep ForLockingItem x)
-> (forall x. Rep ForLockingItem x -> ForLockingItem)
-> Generic ForLockingItem
forall x. Rep ForLockingItem x -> ForLockingItem
forall x. ForLockingItem -> Rep ForLockingItem x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ForLockingItem x -> ForLockingItem
$cfrom :: forall x. ForLockingItem -> Rep ForLockingItem x
Generic, ForLockingItem -> ForLockingItem -> Bool
(ForLockingItem -> ForLockingItem -> Bool)
-> (ForLockingItem -> ForLockingItem -> Bool) -> Eq ForLockingItem
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ForLockingItem -> ForLockingItem -> Bool
$c/= :: ForLockingItem -> ForLockingItem -> Bool
== :: ForLockingItem -> ForLockingItem -> Bool
$c== :: ForLockingItem -> ForLockingItem -> Bool
Eq, Eq ForLockingItem
Eq ForLockingItem
-> (ForLockingItem -> ForLockingItem -> Ordering)
-> (ForLockingItem -> ForLockingItem -> Bool)
-> (ForLockingItem -> ForLockingItem -> Bool)
-> (ForLockingItem -> ForLockingItem -> Bool)
-> (ForLockingItem -> ForLockingItem -> Bool)
-> (ForLockingItem -> ForLockingItem -> ForLockingItem)
-> (ForLockingItem -> ForLockingItem -> ForLockingItem)
-> Ord ForLockingItem
ForLockingItem -> ForLockingItem -> Bool
ForLockingItem -> ForLockingItem -> Ordering
ForLockingItem -> ForLockingItem -> ForLockingItem
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ForLockingItem -> ForLockingItem -> ForLockingItem
$cmin :: ForLockingItem -> ForLockingItem -> ForLockingItem
max :: ForLockingItem -> ForLockingItem -> ForLockingItem
$cmax :: ForLockingItem -> ForLockingItem -> ForLockingItem
>= :: ForLockingItem -> ForLockingItem -> Bool
$c>= :: ForLockingItem -> ForLockingItem -> Bool
> :: ForLockingItem -> ForLockingItem -> Bool
$c> :: ForLockingItem -> ForLockingItem -> Bool
<= :: ForLockingItem -> ForLockingItem -> Bool
$c<= :: ForLockingItem -> ForLockingItem -> Bool
< :: ForLockingItem -> ForLockingItem -> Bool
$c< :: ForLockingItem -> ForLockingItem -> Bool
compare :: ForLockingItem -> ForLockingItem -> Ordering
$ccompare :: ForLockingItem -> ForLockingItem -> Ordering
$cp1Ord :: Eq ForLockingItem
Ord)

-- |
-- ==== References
-- @
-- for_locking_strength:
--   | FOR UPDATE
--   | FOR NO KEY UPDATE
--   | FOR SHARE
--   | FOR KEY SHARE
-- @
data ForLockingStrength
  = UpdateForLockingStrength
  | NoKeyUpdateForLockingStrength
  | ShareForLockingStrength
  | KeyForLockingStrength
  deriving (Int -> ForLockingStrength -> ShowS
[ForLockingStrength] -> ShowS
ForLockingStrength -> String
(Int -> ForLockingStrength -> ShowS)
-> (ForLockingStrength -> String)
-> ([ForLockingStrength] -> ShowS)
-> Show ForLockingStrength
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ForLockingStrength] -> ShowS
$cshowList :: [ForLockingStrength] -> ShowS
show :: ForLockingStrength -> String
$cshow :: ForLockingStrength -> String
showsPrec :: Int -> ForLockingStrength -> ShowS
$cshowsPrec :: Int -> ForLockingStrength -> ShowS
Show, (forall x. ForLockingStrength -> Rep ForLockingStrength x)
-> (forall x. Rep ForLockingStrength x -> ForLockingStrength)
-> Generic ForLockingStrength
forall x. Rep ForLockingStrength x -> ForLockingStrength
forall x. ForLockingStrength -> Rep ForLockingStrength x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ForLockingStrength x -> ForLockingStrength
$cfrom :: forall x. ForLockingStrength -> Rep ForLockingStrength x
Generic, ForLockingStrength -> ForLockingStrength -> Bool
(ForLockingStrength -> ForLockingStrength -> Bool)
-> (ForLockingStrength -> ForLockingStrength -> Bool)
-> Eq ForLockingStrength
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ForLockingStrength -> ForLockingStrength -> Bool
$c/= :: ForLockingStrength -> ForLockingStrength -> Bool
== :: ForLockingStrength -> ForLockingStrength -> Bool
$c== :: ForLockingStrength -> ForLockingStrength -> Bool
Eq, Eq ForLockingStrength
Eq ForLockingStrength
-> (ForLockingStrength -> ForLockingStrength -> Ordering)
-> (ForLockingStrength -> ForLockingStrength -> Bool)
-> (ForLockingStrength -> ForLockingStrength -> Bool)
-> (ForLockingStrength -> ForLockingStrength -> Bool)
-> (ForLockingStrength -> ForLockingStrength -> Bool)
-> (ForLockingStrength -> ForLockingStrength -> ForLockingStrength)
-> (ForLockingStrength -> ForLockingStrength -> ForLockingStrength)
-> Ord ForLockingStrength
ForLockingStrength -> ForLockingStrength -> Bool
ForLockingStrength -> ForLockingStrength -> Ordering
ForLockingStrength -> ForLockingStrength -> ForLockingStrength
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ForLockingStrength -> ForLockingStrength -> ForLockingStrength
$cmin :: ForLockingStrength -> ForLockingStrength -> ForLockingStrength
max :: ForLockingStrength -> ForLockingStrength -> ForLockingStrength
$cmax :: ForLockingStrength -> ForLockingStrength -> ForLockingStrength
>= :: ForLockingStrength -> ForLockingStrength -> Bool
$c>= :: ForLockingStrength -> ForLockingStrength -> Bool
> :: ForLockingStrength -> ForLockingStrength -> Bool
$c> :: ForLockingStrength -> ForLockingStrength -> Bool
<= :: ForLockingStrength -> ForLockingStrength -> Bool
$c<= :: ForLockingStrength -> ForLockingStrength -> Bool
< :: ForLockingStrength -> ForLockingStrength -> Bool
$c< :: ForLockingStrength -> ForLockingStrength -> Bool
compare :: ForLockingStrength -> ForLockingStrength -> Ordering
$ccompare :: ForLockingStrength -> ForLockingStrength -> Ordering
$cp1Ord :: Eq ForLockingStrength
Ord)

-- * Table references and joining

-- |
-- ==== References
-- @
-- from_list:
--   | table_ref
--   | from_list ',' table_ref
-- @
type FromList = NonEmpty TableRef

-- |
-- ==== References
-- @
-- | relation_expr opt_alias_clause
-- | relation_expr opt_alias_clause tablesample_clause
-- | func_table func_alias_clause
-- | LATERAL_P func_table func_alias_clause
-- | xmltable opt_alias_clause
-- | LATERAL_P xmltable opt_alias_clause
-- | select_with_parens opt_alias_clause
-- | LATERAL_P select_with_parens opt_alias_clause
-- | joined_table
-- | '(' joined_table ')' alias_clause
--
-- TODO: Add xmltable
-- @
data TableRef
  = -- |
    -- @
    --    | relation_expr opt_alias_clause
    --    | relation_expr opt_alias_clause tablesample_clause
    -- @
    RelationExprTableRef RelationExpr (Maybe AliasClause) (Maybe TablesampleClause)
  | -- |
    -- @
    --    | func_table func_alias_clause
    --    | LATERAL_P func_table func_alias_clause
    -- @
    FuncTableRef Bool FuncTable (Maybe FuncAliasClause)
  | -- |
    -- @
    --    | select_with_parens opt_alias_clause
    --    | LATERAL_P select_with_parens opt_alias_clause
    -- @
    SelectTableRef Bool SelectWithParens (Maybe AliasClause)
  | -- |
    -- @
    --    | joined_table
    --    | '(' joined_table ')' alias_clause
    -- @
    JoinTableRef JoinedTable (Maybe AliasClause)
  deriving (Int -> TableRef -> ShowS
[TableRef] -> ShowS
TableRef -> String
(Int -> TableRef -> ShowS)
-> (TableRef -> String) -> ([TableRef] -> ShowS) -> Show TableRef
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TableRef] -> ShowS
$cshowList :: [TableRef] -> ShowS
show :: TableRef -> String
$cshow :: TableRef -> String
showsPrec :: Int -> TableRef -> ShowS
$cshowsPrec :: Int -> TableRef -> ShowS
Show, (forall x. TableRef -> Rep TableRef x)
-> (forall x. Rep TableRef x -> TableRef) -> Generic TableRef
forall x. Rep TableRef x -> TableRef
forall x. TableRef -> Rep TableRef x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TableRef x -> TableRef
$cfrom :: forall x. TableRef -> Rep TableRef x
Generic, TableRef -> TableRef -> Bool
(TableRef -> TableRef -> Bool)
-> (TableRef -> TableRef -> Bool) -> Eq TableRef
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TableRef -> TableRef -> Bool
$c/= :: TableRef -> TableRef -> Bool
== :: TableRef -> TableRef -> Bool
$c== :: TableRef -> TableRef -> Bool
Eq, Eq TableRef
Eq TableRef
-> (TableRef -> TableRef -> Ordering)
-> (TableRef -> TableRef -> Bool)
-> (TableRef -> TableRef -> Bool)
-> (TableRef -> TableRef -> Bool)
-> (TableRef -> TableRef -> Bool)
-> (TableRef -> TableRef -> TableRef)
-> (TableRef -> TableRef -> TableRef)
-> Ord TableRef
TableRef -> TableRef -> Bool
TableRef -> TableRef -> Ordering
TableRef -> TableRef -> TableRef
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: TableRef -> TableRef -> TableRef
$cmin :: TableRef -> TableRef -> TableRef
max :: TableRef -> TableRef -> TableRef
$cmax :: TableRef -> TableRef -> TableRef
>= :: TableRef -> TableRef -> Bool
$c>= :: TableRef -> TableRef -> Bool
> :: TableRef -> TableRef -> Bool
$c> :: TableRef -> TableRef -> Bool
<= :: TableRef -> TableRef -> Bool
$c<= :: TableRef -> TableRef -> Bool
< :: TableRef -> TableRef -> Bool
$c< :: TableRef -> TableRef -> Bool
compare :: TableRef -> TableRef -> Ordering
$ccompare :: TableRef -> TableRef -> Ordering
$cp1Ord :: Eq TableRef
Ord)

-- |
-- ==== References
-- @
-- | qualified_name
-- | qualified_name '*'
-- | ONLY qualified_name
-- | ONLY '(' qualified_name ')'
-- @
data RelationExpr
  = SimpleRelationExpr
      QualifiedName
      -- ^ Name.
      Bool
      -- ^ Is asterisk present?
  | OnlyRelationExpr
      QualifiedName
      -- ^ Name.
      Bool
      -- ^ Are parentheses present?
  deriving (Int -> RelationExpr -> ShowS
[RelationExpr] -> ShowS
RelationExpr -> String
(Int -> RelationExpr -> ShowS)
-> (RelationExpr -> String)
-> ([RelationExpr] -> ShowS)
-> Show RelationExpr
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RelationExpr] -> ShowS
$cshowList :: [RelationExpr] -> ShowS
show :: RelationExpr -> String
$cshow :: RelationExpr -> String
showsPrec :: Int -> RelationExpr -> ShowS
$cshowsPrec :: Int -> RelationExpr -> ShowS
Show, (forall x. RelationExpr -> Rep RelationExpr x)
-> (forall x. Rep RelationExpr x -> RelationExpr)
-> Generic RelationExpr
forall x. Rep RelationExpr x -> RelationExpr
forall x. RelationExpr -> Rep RelationExpr x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RelationExpr x -> RelationExpr
$cfrom :: forall x. RelationExpr -> Rep RelationExpr x
Generic, RelationExpr -> RelationExpr -> Bool
(RelationExpr -> RelationExpr -> Bool)
-> (RelationExpr -> RelationExpr -> Bool) -> Eq RelationExpr
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RelationExpr -> RelationExpr -> Bool
$c/= :: RelationExpr -> RelationExpr -> Bool
== :: RelationExpr -> RelationExpr -> Bool
$c== :: RelationExpr -> RelationExpr -> Bool
Eq, Eq RelationExpr
Eq RelationExpr
-> (RelationExpr -> RelationExpr -> Ordering)
-> (RelationExpr -> RelationExpr -> Bool)
-> (RelationExpr -> RelationExpr -> Bool)
-> (RelationExpr -> RelationExpr -> Bool)
-> (RelationExpr -> RelationExpr -> Bool)
-> (RelationExpr -> RelationExpr -> RelationExpr)
-> (RelationExpr -> RelationExpr -> RelationExpr)
-> Ord RelationExpr
RelationExpr -> RelationExpr -> Bool
RelationExpr -> RelationExpr -> Ordering
RelationExpr -> RelationExpr -> RelationExpr
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: RelationExpr -> RelationExpr -> RelationExpr
$cmin :: RelationExpr -> RelationExpr -> RelationExpr
max :: RelationExpr -> RelationExpr -> RelationExpr
$cmax :: RelationExpr -> RelationExpr -> RelationExpr
>= :: RelationExpr -> RelationExpr -> Bool
$c>= :: RelationExpr -> RelationExpr -> Bool
> :: RelationExpr -> RelationExpr -> Bool
$c> :: RelationExpr -> RelationExpr -> Bool
<= :: RelationExpr -> RelationExpr -> Bool
$c<= :: RelationExpr -> RelationExpr -> Bool
< :: RelationExpr -> RelationExpr -> Bool
$c< :: RelationExpr -> RelationExpr -> Bool
compare :: RelationExpr -> RelationExpr -> Ordering
$ccompare :: RelationExpr -> RelationExpr -> Ordering
$cp1Ord :: Eq RelationExpr
Ord)

-- |
-- ==== References
-- @
-- relation_expr_opt_alias:
--   | relation_expr
--   | relation_expr ColId
--   | relation_expr AS ColId
-- @
data RelationExprOptAlias = RelationExprOptAlias RelationExpr (Maybe (Bool, ColId))
  deriving (Int -> RelationExprOptAlias -> ShowS
[RelationExprOptAlias] -> ShowS
RelationExprOptAlias -> String
(Int -> RelationExprOptAlias -> ShowS)
-> (RelationExprOptAlias -> String)
-> ([RelationExprOptAlias] -> ShowS)
-> Show RelationExprOptAlias
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RelationExprOptAlias] -> ShowS
$cshowList :: [RelationExprOptAlias] -> ShowS
show :: RelationExprOptAlias -> String
$cshow :: RelationExprOptAlias -> String
showsPrec :: Int -> RelationExprOptAlias -> ShowS
$cshowsPrec :: Int -> RelationExprOptAlias -> ShowS
Show, (forall x. RelationExprOptAlias -> Rep RelationExprOptAlias x)
-> (forall x. Rep RelationExprOptAlias x -> RelationExprOptAlias)
-> Generic RelationExprOptAlias
forall x. Rep RelationExprOptAlias x -> RelationExprOptAlias
forall x. RelationExprOptAlias -> Rep RelationExprOptAlias x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RelationExprOptAlias x -> RelationExprOptAlias
$cfrom :: forall x. RelationExprOptAlias -> Rep RelationExprOptAlias x
Generic, RelationExprOptAlias -> RelationExprOptAlias -> Bool
(RelationExprOptAlias -> RelationExprOptAlias -> Bool)
-> (RelationExprOptAlias -> RelationExprOptAlias -> Bool)
-> Eq RelationExprOptAlias
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RelationExprOptAlias -> RelationExprOptAlias -> Bool
$c/= :: RelationExprOptAlias -> RelationExprOptAlias -> Bool
== :: RelationExprOptAlias -> RelationExprOptAlias -> Bool
$c== :: RelationExprOptAlias -> RelationExprOptAlias -> Bool
Eq, Eq RelationExprOptAlias
Eq RelationExprOptAlias
-> (RelationExprOptAlias -> RelationExprOptAlias -> Ordering)
-> (RelationExprOptAlias -> RelationExprOptAlias -> Bool)
-> (RelationExprOptAlias -> RelationExprOptAlias -> Bool)
-> (RelationExprOptAlias -> RelationExprOptAlias -> Bool)
-> (RelationExprOptAlias -> RelationExprOptAlias -> Bool)
-> (RelationExprOptAlias
    -> RelationExprOptAlias -> RelationExprOptAlias)
-> (RelationExprOptAlias
    -> RelationExprOptAlias -> RelationExprOptAlias)
-> Ord RelationExprOptAlias
RelationExprOptAlias -> RelationExprOptAlias -> Bool
RelationExprOptAlias -> RelationExprOptAlias -> Ordering
RelationExprOptAlias
-> RelationExprOptAlias -> RelationExprOptAlias
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: RelationExprOptAlias
-> RelationExprOptAlias -> RelationExprOptAlias
$cmin :: RelationExprOptAlias
-> RelationExprOptAlias -> RelationExprOptAlias
max :: RelationExprOptAlias
-> RelationExprOptAlias -> RelationExprOptAlias
$cmax :: RelationExprOptAlias
-> RelationExprOptAlias -> RelationExprOptAlias
>= :: RelationExprOptAlias -> RelationExprOptAlias -> Bool
$c>= :: RelationExprOptAlias -> RelationExprOptAlias -> Bool
> :: RelationExprOptAlias -> RelationExprOptAlias -> Bool
$c> :: RelationExprOptAlias -> RelationExprOptAlias -> Bool
<= :: RelationExprOptAlias -> RelationExprOptAlias -> Bool
$c<= :: RelationExprOptAlias -> RelationExprOptAlias -> Bool
< :: RelationExprOptAlias -> RelationExprOptAlias -> Bool
$c< :: RelationExprOptAlias -> RelationExprOptAlias -> Bool
compare :: RelationExprOptAlias -> RelationExprOptAlias -> Ordering
$ccompare :: RelationExprOptAlias -> RelationExprOptAlias -> Ordering
$cp1Ord :: Eq RelationExprOptAlias
Ord)

-- |
-- ==== References
-- @
-- tablesample_clause:
--   | TABLESAMPLE func_name '(' expr_list ')' opt_repeatable_clause
-- @
data TablesampleClause = TablesampleClause FuncName ExprList (Maybe RepeatableClause)
  deriving (Int -> TablesampleClause -> ShowS
[TablesampleClause] -> ShowS
TablesampleClause -> String
(Int -> TablesampleClause -> ShowS)
-> (TablesampleClause -> String)
-> ([TablesampleClause] -> ShowS)
-> Show TablesampleClause
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TablesampleClause] -> ShowS
$cshowList :: [TablesampleClause] -> ShowS
show :: TablesampleClause -> String
$cshow :: TablesampleClause -> String
showsPrec :: Int -> TablesampleClause -> ShowS
$cshowsPrec :: Int -> TablesampleClause -> ShowS
Show, (forall x. TablesampleClause -> Rep TablesampleClause x)
-> (forall x. Rep TablesampleClause x -> TablesampleClause)
-> Generic TablesampleClause
forall x. Rep TablesampleClause x -> TablesampleClause
forall x. TablesampleClause -> Rep TablesampleClause x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TablesampleClause x -> TablesampleClause
$cfrom :: forall x. TablesampleClause -> Rep TablesampleClause x
Generic, TablesampleClause -> TablesampleClause -> Bool
(TablesampleClause -> TablesampleClause -> Bool)
-> (TablesampleClause -> TablesampleClause -> Bool)
-> Eq TablesampleClause
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TablesampleClause -> TablesampleClause -> Bool
$c/= :: TablesampleClause -> TablesampleClause -> Bool
== :: TablesampleClause -> TablesampleClause -> Bool
$c== :: TablesampleClause -> TablesampleClause -> Bool
Eq, Eq TablesampleClause
Eq TablesampleClause
-> (TablesampleClause -> TablesampleClause -> Ordering)
-> (TablesampleClause -> TablesampleClause -> Bool)
-> (TablesampleClause -> TablesampleClause -> Bool)
-> (TablesampleClause -> TablesampleClause -> Bool)
-> (TablesampleClause -> TablesampleClause -> Bool)
-> (TablesampleClause -> TablesampleClause -> TablesampleClause)
-> (TablesampleClause -> TablesampleClause -> TablesampleClause)
-> Ord TablesampleClause
TablesampleClause -> TablesampleClause -> Bool
TablesampleClause -> TablesampleClause -> Ordering
TablesampleClause -> TablesampleClause -> TablesampleClause
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: TablesampleClause -> TablesampleClause -> TablesampleClause
$cmin :: TablesampleClause -> TablesampleClause -> TablesampleClause
max :: TablesampleClause -> TablesampleClause -> TablesampleClause
$cmax :: TablesampleClause -> TablesampleClause -> TablesampleClause
>= :: TablesampleClause -> TablesampleClause -> Bool
$c>= :: TablesampleClause -> TablesampleClause -> Bool
> :: TablesampleClause -> TablesampleClause -> Bool
$c> :: TablesampleClause -> TablesampleClause -> Bool
<= :: TablesampleClause -> TablesampleClause -> Bool
$c<= :: TablesampleClause -> TablesampleClause -> Bool
< :: TablesampleClause -> TablesampleClause -> Bool
$c< :: TablesampleClause -> TablesampleClause -> Bool
compare :: TablesampleClause -> TablesampleClause -> Ordering
$ccompare :: TablesampleClause -> TablesampleClause -> Ordering
$cp1Ord :: Eq TablesampleClause
Ord)

-- |
-- ==== References
-- @
-- opt_repeatable_clause:
--   | REPEATABLE '(' a_expr ')'
--   | EMPTY
-- @
type RepeatableClause = AExpr

-- |
-- ==== References
-- @
-- func_table:
--   | func_expr_windowless opt_ordinality
--   | ROWS FROM '(' rowsfrom_list ')' opt_ordinality
-- @
data FuncTable
  = FuncExprFuncTable FuncExprWindowless OptOrdinality
  | RowsFromFuncTable RowsfromList OptOrdinality
  deriving (Int -> FuncTable -> ShowS
[FuncTable] -> ShowS
FuncTable -> String
(Int -> FuncTable -> ShowS)
-> (FuncTable -> String)
-> ([FuncTable] -> ShowS)
-> Show FuncTable
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FuncTable] -> ShowS
$cshowList :: [FuncTable] -> ShowS
show :: FuncTable -> String
$cshow :: FuncTable -> String
showsPrec :: Int -> FuncTable -> ShowS
$cshowsPrec :: Int -> FuncTable -> ShowS
Show, (forall x. FuncTable -> Rep FuncTable x)
-> (forall x. Rep FuncTable x -> FuncTable) -> Generic FuncTable
forall x. Rep FuncTable x -> FuncTable
forall x. FuncTable -> Rep FuncTable x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep FuncTable x -> FuncTable
$cfrom :: forall x. FuncTable -> Rep FuncTable x
Generic, FuncTable -> FuncTable -> Bool
(FuncTable -> FuncTable -> Bool)
-> (FuncTable -> FuncTable -> Bool) -> Eq FuncTable
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FuncTable -> FuncTable -> Bool
$c/= :: FuncTable -> FuncTable -> Bool
== :: FuncTable -> FuncTable -> Bool
$c== :: FuncTable -> FuncTable -> Bool
Eq, Eq FuncTable
Eq FuncTable
-> (FuncTable -> FuncTable -> Ordering)
-> (FuncTable -> FuncTable -> Bool)
-> (FuncTable -> FuncTable -> Bool)
-> (FuncTable -> FuncTable -> Bool)
-> (FuncTable -> FuncTable -> Bool)
-> (FuncTable -> FuncTable -> FuncTable)
-> (FuncTable -> FuncTable -> FuncTable)
-> Ord FuncTable
FuncTable -> FuncTable -> Bool
FuncTable -> FuncTable -> Ordering
FuncTable -> FuncTable -> FuncTable
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: FuncTable -> FuncTable -> FuncTable
$cmin :: FuncTable -> FuncTable -> FuncTable
max :: FuncTable -> FuncTable -> FuncTable
$cmax :: FuncTable -> FuncTable -> FuncTable
>= :: FuncTable -> FuncTable -> Bool
$c>= :: FuncTable -> FuncTable -> Bool
> :: FuncTable -> FuncTable -> Bool
$c> :: FuncTable -> FuncTable -> Bool
<= :: FuncTable -> FuncTable -> Bool
$c<= :: FuncTable -> FuncTable -> Bool
< :: FuncTable -> FuncTable -> Bool
$c< :: FuncTable -> FuncTable -> Bool
compare :: FuncTable -> FuncTable -> Ordering
$ccompare :: FuncTable -> FuncTable -> Ordering
$cp1Ord :: Eq FuncTable
Ord)

-- |
-- ==== References
-- @
-- rowsfrom_item:
--   | func_expr_windowless opt_col_def_list
-- @
data RowsfromItem = RowsfromItem FuncExprWindowless (Maybe ColDefList)
  deriving (Int -> RowsfromItem -> ShowS
[RowsfromItem] -> ShowS
RowsfromItem -> String
(Int -> RowsfromItem -> ShowS)
-> (RowsfromItem -> String)
-> ([RowsfromItem] -> ShowS)
-> Show RowsfromItem
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RowsfromItem] -> ShowS
$cshowList :: [RowsfromItem] -> ShowS
show :: RowsfromItem -> String
$cshow :: RowsfromItem -> String
showsPrec :: Int -> RowsfromItem -> ShowS
$cshowsPrec :: Int -> RowsfromItem -> ShowS
Show, (forall x. RowsfromItem -> Rep RowsfromItem x)
-> (forall x. Rep RowsfromItem x -> RowsfromItem)
-> Generic RowsfromItem
forall x. Rep RowsfromItem x -> RowsfromItem
forall x. RowsfromItem -> Rep RowsfromItem x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RowsfromItem x -> RowsfromItem
$cfrom :: forall x. RowsfromItem -> Rep RowsfromItem x
Generic, RowsfromItem -> RowsfromItem -> Bool
(RowsfromItem -> RowsfromItem -> Bool)
-> (RowsfromItem -> RowsfromItem -> Bool) -> Eq RowsfromItem
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RowsfromItem -> RowsfromItem -> Bool
$c/= :: RowsfromItem -> RowsfromItem -> Bool
== :: RowsfromItem -> RowsfromItem -> Bool
$c== :: RowsfromItem -> RowsfromItem -> Bool
Eq, Eq RowsfromItem
Eq RowsfromItem
-> (RowsfromItem -> RowsfromItem -> Ordering)
-> (RowsfromItem -> RowsfromItem -> Bool)
-> (RowsfromItem -> RowsfromItem -> Bool)
-> (RowsfromItem -> RowsfromItem -> Bool)
-> (RowsfromItem -> RowsfromItem -> Bool)
-> (RowsfromItem -> RowsfromItem -> RowsfromItem)
-> (RowsfromItem -> RowsfromItem -> RowsfromItem)
-> Ord RowsfromItem
RowsfromItem -> RowsfromItem -> Bool
RowsfromItem -> RowsfromItem -> Ordering
RowsfromItem -> RowsfromItem -> RowsfromItem
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: RowsfromItem -> RowsfromItem -> RowsfromItem
$cmin :: RowsfromItem -> RowsfromItem -> RowsfromItem
max :: RowsfromItem -> RowsfromItem -> RowsfromItem
$cmax :: RowsfromItem -> RowsfromItem -> RowsfromItem
>= :: RowsfromItem -> RowsfromItem -> Bool
$c>= :: RowsfromItem -> RowsfromItem -> Bool
> :: RowsfromItem -> RowsfromItem -> Bool
$c> :: RowsfromItem -> RowsfromItem -> Bool
<= :: RowsfromItem -> RowsfromItem -> Bool
$c<= :: RowsfromItem -> RowsfromItem -> Bool
< :: RowsfromItem -> RowsfromItem -> Bool
$c< :: RowsfromItem -> RowsfromItem -> Bool
compare :: RowsfromItem -> RowsfromItem -> Ordering
$ccompare :: RowsfromItem -> RowsfromItem -> Ordering
$cp1Ord :: Eq RowsfromItem
Ord)

-- |
-- ==== References
-- @
-- rowsfrom_list:
--   | rowsfrom_item
--   | rowsfrom_list ',' rowsfrom_item
-- @
type RowsfromList = NonEmpty RowsfromItem

-- |
-- ==== References
-- @
-- opt_col_def_list:
--   | AS '(' TableFuncElementList ')'
--   | EMPTY
-- @
type ColDefList = TableFuncElementList

-- |
-- ==== References
-- @
-- opt_ordinality:
--   | WITH_LA ORDINALITY
--   | EMPTY
-- @
type OptOrdinality = Bool

-- |
-- ==== References
-- @
-- TableFuncElementList:
--   | TableFuncElement
--   | TableFuncElementList ',' TableFuncElement
-- @
type TableFuncElementList = NonEmpty TableFuncElement

-- |
-- ==== References
-- @
-- TableFuncElement:
--   | ColId Typename opt_collate_clause
-- @
data TableFuncElement = TableFuncElement ColId Typename (Maybe CollateClause)
  deriving (Int -> TableFuncElement -> ShowS
[TableFuncElement] -> ShowS
TableFuncElement -> String
(Int -> TableFuncElement -> ShowS)
-> (TableFuncElement -> String)
-> ([TableFuncElement] -> ShowS)
-> Show TableFuncElement
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TableFuncElement] -> ShowS
$cshowList :: [TableFuncElement] -> ShowS
show :: TableFuncElement -> String
$cshow :: TableFuncElement -> String
showsPrec :: Int -> TableFuncElement -> ShowS
$cshowsPrec :: Int -> TableFuncElement -> ShowS
Show, (forall x. TableFuncElement -> Rep TableFuncElement x)
-> (forall x. Rep TableFuncElement x -> TableFuncElement)
-> Generic TableFuncElement
forall x. Rep TableFuncElement x -> TableFuncElement
forall x. TableFuncElement -> Rep TableFuncElement x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TableFuncElement x -> TableFuncElement
$cfrom :: forall x. TableFuncElement -> Rep TableFuncElement x
Generic, TableFuncElement -> TableFuncElement -> Bool
(TableFuncElement -> TableFuncElement -> Bool)
-> (TableFuncElement -> TableFuncElement -> Bool)
-> Eq TableFuncElement
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TableFuncElement -> TableFuncElement -> Bool
$c/= :: TableFuncElement -> TableFuncElement -> Bool
== :: TableFuncElement -> TableFuncElement -> Bool
$c== :: TableFuncElement -> TableFuncElement -> Bool
Eq, Eq TableFuncElement
Eq TableFuncElement
-> (TableFuncElement -> TableFuncElement -> Ordering)
-> (TableFuncElement -> TableFuncElement -> Bool)
-> (TableFuncElement -> TableFuncElement -> Bool)
-> (TableFuncElement -> TableFuncElement -> Bool)
-> (TableFuncElement -> TableFuncElement -> Bool)
-> (TableFuncElement -> TableFuncElement -> TableFuncElement)
-> (TableFuncElement -> TableFuncElement -> TableFuncElement)
-> Ord TableFuncElement
TableFuncElement -> TableFuncElement -> Bool
TableFuncElement -> TableFuncElement -> Ordering
TableFuncElement -> TableFuncElement -> TableFuncElement
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: TableFuncElement -> TableFuncElement -> TableFuncElement
$cmin :: TableFuncElement -> TableFuncElement -> TableFuncElement
max :: TableFuncElement -> TableFuncElement -> TableFuncElement
$cmax :: TableFuncElement -> TableFuncElement -> TableFuncElement
>= :: TableFuncElement -> TableFuncElement -> Bool
$c>= :: TableFuncElement -> TableFuncElement -> Bool
> :: TableFuncElement -> TableFuncElement -> Bool
$c> :: TableFuncElement -> TableFuncElement -> Bool
<= :: TableFuncElement -> TableFuncElement -> Bool
$c<= :: TableFuncElement -> TableFuncElement -> Bool
< :: TableFuncElement -> TableFuncElement -> Bool
$c< :: TableFuncElement -> TableFuncElement -> Bool
compare :: TableFuncElement -> TableFuncElement -> Ordering
$ccompare :: TableFuncElement -> TableFuncElement -> Ordering
$cp1Ord :: Eq TableFuncElement
Ord)

-- |
-- ==== References
-- @
-- opt_collate_clause:
--   | COLLATE any_name
--   | EMPTY
-- @
type CollateClause = AnyName

-- |
-- ==== References
-- @
-- alias_clause:
--   |  AS ColId '(' name_list ')'
--   |  AS ColId
--   |  ColId '(' name_list ')'
--   |  ColId
-- @
data AliasClause = AliasClause Bool ColId (Maybe NameList)
  deriving (Int -> AliasClause -> ShowS
[AliasClause] -> ShowS
AliasClause -> String
(Int -> AliasClause -> ShowS)
-> (AliasClause -> String)
-> ([AliasClause] -> ShowS)
-> Show AliasClause
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AliasClause] -> ShowS
$cshowList :: [AliasClause] -> ShowS
show :: AliasClause -> String
$cshow :: AliasClause -> String
showsPrec :: Int -> AliasClause -> ShowS
$cshowsPrec :: Int -> AliasClause -> ShowS
Show, (forall x. AliasClause -> Rep AliasClause x)
-> (forall x. Rep AliasClause x -> AliasClause)
-> Generic AliasClause
forall x. Rep AliasClause x -> AliasClause
forall x. AliasClause -> Rep AliasClause x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AliasClause x -> AliasClause
$cfrom :: forall x. AliasClause -> Rep AliasClause x
Generic, AliasClause -> AliasClause -> Bool
(AliasClause -> AliasClause -> Bool)
-> (AliasClause -> AliasClause -> Bool) -> Eq AliasClause
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AliasClause -> AliasClause -> Bool
$c/= :: AliasClause -> AliasClause -> Bool
== :: AliasClause -> AliasClause -> Bool
$c== :: AliasClause -> AliasClause -> Bool
Eq, Eq AliasClause
Eq AliasClause
-> (AliasClause -> AliasClause -> Ordering)
-> (AliasClause -> AliasClause -> Bool)
-> (AliasClause -> AliasClause -> Bool)
-> (AliasClause -> AliasClause -> Bool)
-> (AliasClause -> AliasClause -> Bool)
-> (AliasClause -> AliasClause -> AliasClause)
-> (AliasClause -> AliasClause -> AliasClause)
-> Ord AliasClause
AliasClause -> AliasClause -> Bool
AliasClause -> AliasClause -> Ordering
AliasClause -> AliasClause -> AliasClause
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: AliasClause -> AliasClause -> AliasClause
$cmin :: AliasClause -> AliasClause -> AliasClause
max :: AliasClause -> AliasClause -> AliasClause
$cmax :: AliasClause -> AliasClause -> AliasClause
>= :: AliasClause -> AliasClause -> Bool
$c>= :: AliasClause -> AliasClause -> Bool
> :: AliasClause -> AliasClause -> Bool
$c> :: AliasClause -> AliasClause -> Bool
<= :: AliasClause -> AliasClause -> Bool
$c<= :: AliasClause -> AliasClause -> Bool
< :: AliasClause -> AliasClause -> Bool
$c< :: AliasClause -> AliasClause -> Bool
compare :: AliasClause -> AliasClause -> Ordering
$ccompare :: AliasClause -> AliasClause -> Ordering
$cp1Ord :: Eq AliasClause
Ord)

-- |
-- ==== References
-- @
-- func_alias_clause:
--   | alias_clause
--   | AS '(' TableFuncElementList ')'
--   | AS ColId '(' TableFuncElementList ')'
--   | ColId '(' TableFuncElementList ')'
--   | EMPTY
-- @
data FuncAliasClause
  = AliasFuncAliasClause AliasClause
  | AsFuncAliasClause TableFuncElementList
  | AsColIdFuncAliasClause ColId TableFuncElementList
  | ColIdFuncAliasClause ColId TableFuncElementList
  deriving (Int -> FuncAliasClause -> ShowS
[FuncAliasClause] -> ShowS
FuncAliasClause -> String
(Int -> FuncAliasClause -> ShowS)
-> (FuncAliasClause -> String)
-> ([FuncAliasClause] -> ShowS)
-> Show FuncAliasClause
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FuncAliasClause] -> ShowS
$cshowList :: [FuncAliasClause] -> ShowS
show :: FuncAliasClause -> String
$cshow :: FuncAliasClause -> String
showsPrec :: Int -> FuncAliasClause -> ShowS
$cshowsPrec :: Int -> FuncAliasClause -> ShowS
Show, (forall x. FuncAliasClause -> Rep FuncAliasClause x)
-> (forall x. Rep FuncAliasClause x -> FuncAliasClause)
-> Generic FuncAliasClause
forall x. Rep FuncAliasClause x -> FuncAliasClause
forall x. FuncAliasClause -> Rep FuncAliasClause x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep FuncAliasClause x -> FuncAliasClause
$cfrom :: forall x. FuncAliasClause -> Rep FuncAliasClause x
Generic, FuncAliasClause -> FuncAliasClause -> Bool
(FuncAliasClause -> FuncAliasClause -> Bool)
-> (FuncAliasClause -> FuncAliasClause -> Bool)
-> Eq FuncAliasClause
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FuncAliasClause -> FuncAliasClause -> Bool
$c/= :: FuncAliasClause -> FuncAliasClause -> Bool
== :: FuncAliasClause -> FuncAliasClause -> Bool
$c== :: FuncAliasClause -> FuncAliasClause -> Bool
Eq, Eq FuncAliasClause
Eq FuncAliasClause
-> (FuncAliasClause -> FuncAliasClause -> Ordering)
-> (FuncAliasClause -> FuncAliasClause -> Bool)
-> (FuncAliasClause -> FuncAliasClause -> Bool)
-> (FuncAliasClause -> FuncAliasClause -> Bool)
-> (FuncAliasClause -> FuncAliasClause -> Bool)
-> (FuncAliasClause -> FuncAliasClause -> FuncAliasClause)
-> (FuncAliasClause -> FuncAliasClause -> FuncAliasClause)
-> Ord FuncAliasClause
FuncAliasClause -> FuncAliasClause -> Bool
FuncAliasClause -> FuncAliasClause -> Ordering
FuncAliasClause -> FuncAliasClause -> FuncAliasClause
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: FuncAliasClause -> FuncAliasClause -> FuncAliasClause
$cmin :: FuncAliasClause -> FuncAliasClause -> FuncAliasClause
max :: FuncAliasClause -> FuncAliasClause -> FuncAliasClause
$cmax :: FuncAliasClause -> FuncAliasClause -> FuncAliasClause
>= :: FuncAliasClause -> FuncAliasClause -> Bool
$c>= :: FuncAliasClause -> FuncAliasClause -> Bool
> :: FuncAliasClause -> FuncAliasClause -> Bool
$c> :: FuncAliasClause -> FuncAliasClause -> Bool
<= :: FuncAliasClause -> FuncAliasClause -> Bool
$c<= :: FuncAliasClause -> FuncAliasClause -> Bool
< :: FuncAliasClause -> FuncAliasClause -> Bool
$c< :: FuncAliasClause -> FuncAliasClause -> Bool
compare :: FuncAliasClause -> FuncAliasClause -> Ordering
$ccompare :: FuncAliasClause -> FuncAliasClause -> Ordering
$cp1Ord :: Eq FuncAliasClause
Ord)

-- |
-- ==== References
-- @
-- | '(' joined_table ')'
-- | table_ref CROSS JOIN table_ref
-- | table_ref join_type JOIN table_ref join_qual
-- | table_ref JOIN table_ref join_qual
-- | table_ref NATURAL join_type JOIN table_ref
-- | table_ref NATURAL JOIN table_ref
--
-- The options are covered by the `JoinMeth` type.
-- @
data JoinedTable
  = InParensJoinedTable JoinedTable
  | MethJoinedTable JoinMeth TableRef TableRef
  deriving (Int -> JoinedTable -> ShowS
[JoinedTable] -> ShowS
JoinedTable -> String
(Int -> JoinedTable -> ShowS)
-> (JoinedTable -> String)
-> ([JoinedTable] -> ShowS)
-> Show JoinedTable
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [JoinedTable] -> ShowS
$cshowList :: [JoinedTable] -> ShowS
show :: JoinedTable -> String
$cshow :: JoinedTable -> String
showsPrec :: Int -> JoinedTable -> ShowS
$cshowsPrec :: Int -> JoinedTable -> ShowS
Show, (forall x. JoinedTable -> Rep JoinedTable x)
-> (forall x. Rep JoinedTable x -> JoinedTable)
-> Generic JoinedTable
forall x. Rep JoinedTable x -> JoinedTable
forall x. JoinedTable -> Rep JoinedTable x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep JoinedTable x -> JoinedTable
$cfrom :: forall x. JoinedTable -> Rep JoinedTable x
Generic, JoinedTable -> JoinedTable -> Bool
(JoinedTable -> JoinedTable -> Bool)
-> (JoinedTable -> JoinedTable -> Bool) -> Eq JoinedTable
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: JoinedTable -> JoinedTable -> Bool
$c/= :: JoinedTable -> JoinedTable -> Bool
== :: JoinedTable -> JoinedTable -> Bool
$c== :: JoinedTable -> JoinedTable -> Bool
Eq, Eq JoinedTable
Eq JoinedTable
-> (JoinedTable -> JoinedTable -> Ordering)
-> (JoinedTable -> JoinedTable -> Bool)
-> (JoinedTable -> JoinedTable -> Bool)
-> (JoinedTable -> JoinedTable -> Bool)
-> (JoinedTable -> JoinedTable -> Bool)
-> (JoinedTable -> JoinedTable -> JoinedTable)
-> (JoinedTable -> JoinedTable -> JoinedTable)
-> Ord JoinedTable
JoinedTable -> JoinedTable -> Bool
JoinedTable -> JoinedTable -> Ordering
JoinedTable -> JoinedTable -> JoinedTable
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: JoinedTable -> JoinedTable -> JoinedTable
$cmin :: JoinedTable -> JoinedTable -> JoinedTable
max :: JoinedTable -> JoinedTable -> JoinedTable
$cmax :: JoinedTable -> JoinedTable -> JoinedTable
>= :: JoinedTable -> JoinedTable -> Bool
$c>= :: JoinedTable -> JoinedTable -> Bool
> :: JoinedTable -> JoinedTable -> Bool
$c> :: JoinedTable -> JoinedTable -> Bool
<= :: JoinedTable -> JoinedTable -> Bool
$c<= :: JoinedTable -> JoinedTable -> Bool
< :: JoinedTable -> JoinedTable -> Bool
$c< :: JoinedTable -> JoinedTable -> Bool
compare :: JoinedTable -> JoinedTable -> Ordering
$ccompare :: JoinedTable -> JoinedTable -> Ordering
$cp1Ord :: Eq JoinedTable
Ord)

-- |
-- ==== References
-- @
-- | table_ref CROSS JOIN table_ref
-- | table_ref join_type JOIN table_ref join_qual
-- | table_ref JOIN table_ref join_qual
-- | table_ref NATURAL join_type JOIN table_ref
-- | table_ref NATURAL JOIN table_ref
-- @
data JoinMeth
  = CrossJoinMeth
  | QualJoinMeth (Maybe JoinType) JoinQual
  | NaturalJoinMeth (Maybe JoinType)
  deriving (Int -> JoinMeth -> ShowS
[JoinMeth] -> ShowS
JoinMeth -> String
(Int -> JoinMeth -> ShowS)
-> (JoinMeth -> String) -> ([JoinMeth] -> ShowS) -> Show JoinMeth
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [JoinMeth] -> ShowS
$cshowList :: [JoinMeth] -> ShowS
show :: JoinMeth -> String
$cshow :: JoinMeth -> String
showsPrec :: Int -> JoinMeth -> ShowS
$cshowsPrec :: Int -> JoinMeth -> ShowS
Show, (forall x. JoinMeth -> Rep JoinMeth x)
-> (forall x. Rep JoinMeth x -> JoinMeth) -> Generic JoinMeth
forall x. Rep JoinMeth x -> JoinMeth
forall x. JoinMeth -> Rep JoinMeth x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep JoinMeth x -> JoinMeth
$cfrom :: forall x. JoinMeth -> Rep JoinMeth x
Generic, JoinMeth -> JoinMeth -> Bool
(JoinMeth -> JoinMeth -> Bool)
-> (JoinMeth -> JoinMeth -> Bool) -> Eq JoinMeth
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: JoinMeth -> JoinMeth -> Bool
$c/= :: JoinMeth -> JoinMeth -> Bool
== :: JoinMeth -> JoinMeth -> Bool
$c== :: JoinMeth -> JoinMeth -> Bool
Eq, Eq JoinMeth
Eq JoinMeth
-> (JoinMeth -> JoinMeth -> Ordering)
-> (JoinMeth -> JoinMeth -> Bool)
-> (JoinMeth -> JoinMeth -> Bool)
-> (JoinMeth -> JoinMeth -> Bool)
-> (JoinMeth -> JoinMeth -> Bool)
-> (JoinMeth -> JoinMeth -> JoinMeth)
-> (JoinMeth -> JoinMeth -> JoinMeth)
-> Ord JoinMeth
JoinMeth -> JoinMeth -> Bool
JoinMeth -> JoinMeth -> Ordering
JoinMeth -> JoinMeth -> JoinMeth
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: JoinMeth -> JoinMeth -> JoinMeth
$cmin :: JoinMeth -> JoinMeth -> JoinMeth
max :: JoinMeth -> JoinMeth -> JoinMeth
$cmax :: JoinMeth -> JoinMeth -> JoinMeth
>= :: JoinMeth -> JoinMeth -> Bool
$c>= :: JoinMeth -> JoinMeth -> Bool
> :: JoinMeth -> JoinMeth -> Bool
$c> :: JoinMeth -> JoinMeth -> Bool
<= :: JoinMeth -> JoinMeth -> Bool
$c<= :: JoinMeth -> JoinMeth -> Bool
< :: JoinMeth -> JoinMeth -> Bool
$c< :: JoinMeth -> JoinMeth -> Bool
compare :: JoinMeth -> JoinMeth -> Ordering
$ccompare :: JoinMeth -> JoinMeth -> Ordering
$cp1Ord :: Eq JoinMeth
Ord)

-- |
-- ==== References
-- @
-- | FULL join_outer
-- | LEFT join_outer
-- | RIGHT join_outer
-- | INNER_P
-- @
data JoinType
  = FullJoinType Bool
  | LeftJoinType Bool
  | RightJoinType Bool
  | InnerJoinType
  deriving (Int -> JoinType -> ShowS
[JoinType] -> ShowS
JoinType -> String
(Int -> JoinType -> ShowS)
-> (JoinType -> String) -> ([JoinType] -> ShowS) -> Show JoinType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [JoinType] -> ShowS
$cshowList :: [JoinType] -> ShowS
show :: JoinType -> String
$cshow :: JoinType -> String
showsPrec :: Int -> JoinType -> ShowS
$cshowsPrec :: Int -> JoinType -> ShowS
Show, (forall x. JoinType -> Rep JoinType x)
-> (forall x. Rep JoinType x -> JoinType) -> Generic JoinType
forall x. Rep JoinType x -> JoinType
forall x. JoinType -> Rep JoinType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep JoinType x -> JoinType
$cfrom :: forall x. JoinType -> Rep JoinType x
Generic, JoinType -> JoinType -> Bool
(JoinType -> JoinType -> Bool)
-> (JoinType -> JoinType -> Bool) -> Eq JoinType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: JoinType -> JoinType -> Bool
$c/= :: JoinType -> JoinType -> Bool
== :: JoinType -> JoinType -> Bool
$c== :: JoinType -> JoinType -> Bool
Eq, Eq JoinType
Eq JoinType
-> (JoinType -> JoinType -> Ordering)
-> (JoinType -> JoinType -> Bool)
-> (JoinType -> JoinType -> Bool)
-> (JoinType -> JoinType -> Bool)
-> (JoinType -> JoinType -> Bool)
-> (JoinType -> JoinType -> JoinType)
-> (JoinType -> JoinType -> JoinType)
-> Ord JoinType
JoinType -> JoinType -> Bool
JoinType -> JoinType -> Ordering
JoinType -> JoinType -> JoinType
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: JoinType -> JoinType -> JoinType
$cmin :: JoinType -> JoinType -> JoinType
max :: JoinType -> JoinType -> JoinType
$cmax :: JoinType -> JoinType -> JoinType
>= :: JoinType -> JoinType -> Bool
$c>= :: JoinType -> JoinType -> Bool
> :: JoinType -> JoinType -> Bool
$c> :: JoinType -> JoinType -> Bool
<= :: JoinType -> JoinType -> Bool
$c<= :: JoinType -> JoinType -> Bool
< :: JoinType -> JoinType -> Bool
$c< :: JoinType -> JoinType -> Bool
compare :: JoinType -> JoinType -> Ordering
$ccompare :: JoinType -> JoinType -> Ordering
$cp1Ord :: Eq JoinType
Ord)

-- |
-- ==== References
-- @
-- join_qual:
--   |  USING '(' name_list ')'
--   |  ON a_expr
-- @
data JoinQual
  = UsingJoinQual (NonEmpty Ident)
  | OnJoinQual AExpr
  deriving (Int -> JoinQual -> ShowS
[JoinQual] -> ShowS
JoinQual -> String
(Int -> JoinQual -> ShowS)
-> (JoinQual -> String) -> ([JoinQual] -> ShowS) -> Show JoinQual
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [JoinQual] -> ShowS
$cshowList :: [JoinQual] -> ShowS
show :: JoinQual -> String
$cshow :: JoinQual -> String
showsPrec :: Int -> JoinQual -> ShowS
$cshowsPrec :: Int -> JoinQual -> ShowS
Show, (forall x. JoinQual -> Rep JoinQual x)
-> (forall x. Rep JoinQual x -> JoinQual) -> Generic JoinQual
forall x. Rep JoinQual x -> JoinQual
forall x. JoinQual -> Rep JoinQual x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep JoinQual x -> JoinQual
$cfrom :: forall x. JoinQual -> Rep JoinQual x
Generic, JoinQual -> JoinQual -> Bool
(JoinQual -> JoinQual -> Bool)
-> (JoinQual -> JoinQual -> Bool) -> Eq JoinQual
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: JoinQual -> JoinQual -> Bool
$c/= :: JoinQual -> JoinQual -> Bool
== :: JoinQual -> JoinQual -> Bool
$c== :: JoinQual -> JoinQual -> Bool
Eq, Eq JoinQual
Eq JoinQual
-> (JoinQual -> JoinQual -> Ordering)
-> (JoinQual -> JoinQual -> Bool)
-> (JoinQual -> JoinQual -> Bool)
-> (JoinQual -> JoinQual -> Bool)
-> (JoinQual -> JoinQual -> Bool)
-> (JoinQual -> JoinQual -> JoinQual)
-> (JoinQual -> JoinQual -> JoinQual)
-> Ord JoinQual
JoinQual -> JoinQual -> Bool
JoinQual -> JoinQual -> Ordering
JoinQual -> JoinQual -> JoinQual
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: JoinQual -> JoinQual -> JoinQual
$cmin :: JoinQual -> JoinQual -> JoinQual
max :: JoinQual -> JoinQual -> JoinQual
$cmax :: JoinQual -> JoinQual -> JoinQual
>= :: JoinQual -> JoinQual -> Bool
$c>= :: JoinQual -> JoinQual -> Bool
> :: JoinQual -> JoinQual -> Bool
$c> :: JoinQual -> JoinQual -> Bool
<= :: JoinQual -> JoinQual -> Bool
$c<= :: JoinQual -> JoinQual -> Bool
< :: JoinQual -> JoinQual -> Bool
$c< :: JoinQual -> JoinQual -> Bool
compare :: JoinQual -> JoinQual -> Ordering
$ccompare :: JoinQual -> JoinQual -> Ordering
$cp1Ord :: Eq JoinQual
Ord)

-- * Where

type WhereClause = AExpr

-- |
-- ==== References
-- @
-- | WHERE a_expr
-- | WHERE CURRENT_P OF cursor_name
-- | /*EMPTY*/
-- @
data WhereOrCurrentClause
  = ExprWhereOrCurrentClause AExpr
  | CursorWhereOrCurrentClause CursorName
  deriving (Int -> WhereOrCurrentClause -> ShowS
[WhereOrCurrentClause] -> ShowS
WhereOrCurrentClause -> String
(Int -> WhereOrCurrentClause -> ShowS)
-> (WhereOrCurrentClause -> String)
-> ([WhereOrCurrentClause] -> ShowS)
-> Show WhereOrCurrentClause
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WhereOrCurrentClause] -> ShowS
$cshowList :: [WhereOrCurrentClause] -> ShowS
show :: WhereOrCurrentClause -> String
$cshow :: WhereOrCurrentClause -> String
showsPrec :: Int -> WhereOrCurrentClause -> ShowS
$cshowsPrec :: Int -> WhereOrCurrentClause -> ShowS
Show, (forall x. WhereOrCurrentClause -> Rep WhereOrCurrentClause x)
-> (forall x. Rep WhereOrCurrentClause x -> WhereOrCurrentClause)
-> Generic WhereOrCurrentClause
forall x. Rep WhereOrCurrentClause x -> WhereOrCurrentClause
forall x. WhereOrCurrentClause -> Rep WhereOrCurrentClause x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep WhereOrCurrentClause x -> WhereOrCurrentClause
$cfrom :: forall x. WhereOrCurrentClause -> Rep WhereOrCurrentClause x
Generic, WhereOrCurrentClause -> WhereOrCurrentClause -> Bool
(WhereOrCurrentClause -> WhereOrCurrentClause -> Bool)
-> (WhereOrCurrentClause -> WhereOrCurrentClause -> Bool)
-> Eq WhereOrCurrentClause
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WhereOrCurrentClause -> WhereOrCurrentClause -> Bool
$c/= :: WhereOrCurrentClause -> WhereOrCurrentClause -> Bool
== :: WhereOrCurrentClause -> WhereOrCurrentClause -> Bool
$c== :: WhereOrCurrentClause -> WhereOrCurrentClause -> Bool
Eq, Eq WhereOrCurrentClause
Eq WhereOrCurrentClause
-> (WhereOrCurrentClause -> WhereOrCurrentClause -> Ordering)
-> (WhereOrCurrentClause -> WhereOrCurrentClause -> Bool)
-> (WhereOrCurrentClause -> WhereOrCurrentClause -> Bool)
-> (WhereOrCurrentClause -> WhereOrCurrentClause -> Bool)
-> (WhereOrCurrentClause -> WhereOrCurrentClause -> Bool)
-> (WhereOrCurrentClause
    -> WhereOrCurrentClause -> WhereOrCurrentClause)
-> (WhereOrCurrentClause
    -> WhereOrCurrentClause -> WhereOrCurrentClause)
-> Ord WhereOrCurrentClause
WhereOrCurrentClause -> WhereOrCurrentClause -> Bool
WhereOrCurrentClause -> WhereOrCurrentClause -> Ordering
WhereOrCurrentClause
-> WhereOrCurrentClause -> WhereOrCurrentClause
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: WhereOrCurrentClause
-> WhereOrCurrentClause -> WhereOrCurrentClause
$cmin :: WhereOrCurrentClause
-> WhereOrCurrentClause -> WhereOrCurrentClause
max :: WhereOrCurrentClause
-> WhereOrCurrentClause -> WhereOrCurrentClause
$cmax :: WhereOrCurrentClause
-> WhereOrCurrentClause -> WhereOrCurrentClause
>= :: WhereOrCurrentClause -> WhereOrCurrentClause -> Bool
$c>= :: WhereOrCurrentClause -> WhereOrCurrentClause -> Bool
> :: WhereOrCurrentClause -> WhereOrCurrentClause -> Bool
$c> :: WhereOrCurrentClause -> WhereOrCurrentClause -> Bool
<= :: WhereOrCurrentClause -> WhereOrCurrentClause -> Bool
$c<= :: WhereOrCurrentClause -> WhereOrCurrentClause -> Bool
< :: WhereOrCurrentClause -> WhereOrCurrentClause -> Bool
$c< :: WhereOrCurrentClause -> WhereOrCurrentClause -> Bool
compare :: WhereOrCurrentClause -> WhereOrCurrentClause -> Ordering
$ccompare :: WhereOrCurrentClause -> WhereOrCurrentClause -> Ordering
$cp1Ord :: Eq WhereOrCurrentClause
Ord)

-- * Expression

type ExprList = NonEmpty AExpr

-- |
-- ==== References
-- @
-- a_expr:
--   | c_expr
--   | a_expr TYPECAST Typename
--   | a_expr COLLATE any_name
--   | a_expr AT TIME ZONE a_expr
--   | '+' a_expr
--   | '-' a_expr
--   | a_expr '+' a_expr
--   | a_expr '-' a_expr
--   | a_expr '*' a_expr
--   | a_expr '/' a_expr
--   | a_expr '%' a_expr
--   | a_expr '^' a_expr
--   | a_expr '<' a_expr
--   | a_expr '>' a_expr
--   | a_expr '=' a_expr
--   | a_expr LESS_EQUALS a_expr
--   | a_expr GREATER_EQUALS a_expr
--   | a_expr NOT_EQUALS a_expr
--   | a_expr qual_Op a_expr
--   | qual_Op a_expr
--   | a_expr qual_Op
--   | a_expr AND a_expr
--   | a_expr OR a_expr
--   | NOT a_expr
--   | NOT_LA a_expr
--   | a_expr LIKE a_expr
--   | a_expr LIKE a_expr ESCAPE a_expr
--   | a_expr NOT_LA LIKE a_expr
--   | a_expr NOT_LA LIKE a_expr ESCAPE a_expr
--   | a_expr ILIKE a_expr
--   | a_expr ILIKE a_expr ESCAPE a_expr
--   | a_expr NOT_LA ILIKE a_expr
--   | a_expr NOT_LA ILIKE a_expr ESCAPE a_expr
--   | a_expr SIMILAR TO a_expr
--   | a_expr SIMILAR TO a_expr ESCAPE a_expr
--   | a_expr NOT_LA SIMILAR TO a_expr
--   | a_expr NOT_LA SIMILAR TO a_expr ESCAPE a_expr
--   | a_expr IS NULL_P
--   | a_expr ISNULL
--   | a_expr IS NOT NULL_P
--   | a_expr NOTNULL
--   | row OVERLAPS row
--   | a_expr IS TRUE_P
--   | a_expr IS NOT TRUE_P
--   | a_expr IS FALSE_P
--   | a_expr IS NOT FALSE_P
--   | a_expr IS UNKNOWN
--   | a_expr IS NOT UNKNOWN
--   | a_expr IS DISTINCT FROM a_expr
--   | a_expr IS NOT DISTINCT FROM a_expr
--   | a_expr IS OF '(' type_list ')'
--   | a_expr IS NOT OF '(' type_list ')'
--   | a_expr BETWEEN opt_asymmetric b_expr AND a_expr
--   | a_expr NOT_LA BETWEEN opt_asymmetric b_expr AND a_expr
--   | a_expr BETWEEN SYMMETRIC b_expr AND a_expr
--   | a_expr NOT_LA BETWEEN SYMMETRIC b_expr AND a_expr
--   | a_expr IN_P in_expr
--   | a_expr NOT_LA IN_P in_expr
--   | a_expr subquery_Op sub_type select_with_parens
--   | a_expr subquery_Op sub_type '(' a_expr ')'
--   | UNIQUE select_with_parens
--   | a_expr IS DOCUMENT_P
--   | a_expr IS NOT DOCUMENT_P
--   | DEFAULT
-- @
data AExpr
  = CExprAExpr CExpr
  | TypecastAExpr AExpr Typename
  | CollateAExpr AExpr AnyName
  | AtTimeZoneAExpr AExpr AExpr
  | PlusAExpr AExpr
  | MinusAExpr AExpr
  | SymbolicBinOpAExpr AExpr SymbolicExprBinOp AExpr
  | PrefixQualOpAExpr QualOp AExpr
  | SuffixQualOpAExpr AExpr QualOp
  | AndAExpr AExpr AExpr
  | OrAExpr AExpr AExpr
  | NotAExpr AExpr
  | VerbalExprBinOpAExpr AExpr Bool VerbalExprBinOp AExpr (Maybe AExpr)
  | ReversableOpAExpr AExpr Bool AExprReversableOp
  | IsnullAExpr AExpr
  | NotnullAExpr AExpr
  | OverlapsAExpr Row Row
  | SubqueryAExpr AExpr SubqueryOp SubType (Either SelectWithParens AExpr)
  | UniqueAExpr SelectWithParens
  | DefaultAExpr
  deriving (Int -> AExpr -> ShowS
[AExpr] -> ShowS
AExpr -> String
(Int -> AExpr -> ShowS)
-> (AExpr -> String) -> ([AExpr] -> ShowS) -> Show AExpr
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AExpr] -> ShowS
$cshowList :: [AExpr] -> ShowS
show :: AExpr -> String
$cshow :: AExpr -> String
showsPrec :: Int -> AExpr -> ShowS
$cshowsPrec :: Int -> AExpr -> ShowS
Show, (forall x. AExpr -> Rep AExpr x)
-> (forall x. Rep AExpr x -> AExpr) -> Generic AExpr
forall x. Rep AExpr x -> AExpr
forall x. AExpr -> Rep AExpr x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AExpr x -> AExpr
$cfrom :: forall x. AExpr -> Rep AExpr x
Generic, AExpr -> AExpr -> Bool
(AExpr -> AExpr -> Bool) -> (AExpr -> AExpr -> Bool) -> Eq AExpr
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AExpr -> AExpr -> Bool
$c/= :: AExpr -> AExpr -> Bool
== :: AExpr -> AExpr -> Bool
$c== :: AExpr -> AExpr -> Bool
Eq, Eq AExpr
Eq AExpr
-> (AExpr -> AExpr -> Ordering)
-> (AExpr -> AExpr -> Bool)
-> (AExpr -> AExpr -> Bool)
-> (AExpr -> AExpr -> Bool)
-> (AExpr -> AExpr -> Bool)
-> (AExpr -> AExpr -> AExpr)
-> (AExpr -> AExpr -> AExpr)
-> Ord AExpr
AExpr -> AExpr -> Bool
AExpr -> AExpr -> Ordering
AExpr -> AExpr -> AExpr
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: AExpr -> AExpr -> AExpr
$cmin :: AExpr -> AExpr -> AExpr
max :: AExpr -> AExpr -> AExpr
$cmax :: AExpr -> AExpr -> AExpr
>= :: AExpr -> AExpr -> Bool
$c>= :: AExpr -> AExpr -> Bool
> :: AExpr -> AExpr -> Bool
$c> :: AExpr -> AExpr -> Bool
<= :: AExpr -> AExpr -> Bool
$c<= :: AExpr -> AExpr -> Bool
< :: AExpr -> AExpr -> Bool
$c< :: AExpr -> AExpr -> Bool
compare :: AExpr -> AExpr -> Ordering
$ccompare :: AExpr -> AExpr -> Ordering
$cp1Ord :: Eq AExpr
Ord)

-- |
-- ==== References
-- @
-- b_expr:
--   | c_expr
--   | b_expr TYPECAST Typename
--   | '+' b_expr
--   | '-' b_expr
--   | b_expr '+' b_expr
--   | b_expr '-' b_expr
--   | b_expr '*' b_expr
--   | b_expr '/' b_expr
--   | b_expr '%' b_expr
--   | b_expr '^' b_expr
--   | b_expr '<' b_expr
--   | b_expr '>' b_expr
--   | b_expr '=' b_expr
--   | b_expr LESS_EQUALS b_expr
--   | b_expr GREATER_EQUALS b_expr
--   | b_expr NOT_EQUALS b_expr
--   | b_expr qual_Op b_expr
--   | qual_Op b_expr
--   | b_expr qual_Op
--   | b_expr IS DISTINCT FROM b_expr
--   | b_expr IS NOT DISTINCT FROM b_expr
--   | b_expr IS OF '(' type_list ')'
--   | b_expr IS NOT OF '(' type_list ')'
--   | b_expr IS DOCUMENT_P
--   | b_expr IS NOT DOCUMENT_P
-- @
data BExpr
  = CExprBExpr CExpr
  | TypecastBExpr BExpr Typename
  | PlusBExpr BExpr
  | MinusBExpr BExpr
  | SymbolicBinOpBExpr BExpr SymbolicExprBinOp BExpr
  | QualOpBExpr QualOp BExpr
  | IsOpBExpr BExpr Bool BExprIsOp
  deriving (Int -> BExpr -> ShowS
[BExpr] -> ShowS
BExpr -> String
(Int -> BExpr -> ShowS)
-> (BExpr -> String) -> ([BExpr] -> ShowS) -> Show BExpr
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BExpr] -> ShowS
$cshowList :: [BExpr] -> ShowS
show :: BExpr -> String
$cshow :: BExpr -> String
showsPrec :: Int -> BExpr -> ShowS
$cshowsPrec :: Int -> BExpr -> ShowS
Show, (forall x. BExpr -> Rep BExpr x)
-> (forall x. Rep BExpr x -> BExpr) -> Generic BExpr
forall x. Rep BExpr x -> BExpr
forall x. BExpr -> Rep BExpr x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep BExpr x -> BExpr
$cfrom :: forall x. BExpr -> Rep BExpr x
Generic, BExpr -> BExpr -> Bool
(BExpr -> BExpr -> Bool) -> (BExpr -> BExpr -> Bool) -> Eq BExpr
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BExpr -> BExpr -> Bool
$c/= :: BExpr -> BExpr -> Bool
== :: BExpr -> BExpr -> Bool
$c== :: BExpr -> BExpr -> Bool
Eq, Eq BExpr
Eq BExpr
-> (BExpr -> BExpr -> Ordering)
-> (BExpr -> BExpr -> Bool)
-> (BExpr -> BExpr -> Bool)
-> (BExpr -> BExpr -> Bool)
-> (BExpr -> BExpr -> Bool)
-> (BExpr -> BExpr -> BExpr)
-> (BExpr -> BExpr -> BExpr)
-> Ord BExpr
BExpr -> BExpr -> Bool
BExpr -> BExpr -> Ordering
BExpr -> BExpr -> BExpr
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: BExpr -> BExpr -> BExpr
$cmin :: BExpr -> BExpr -> BExpr
max :: BExpr -> BExpr -> BExpr
$cmax :: BExpr -> BExpr -> BExpr
>= :: BExpr -> BExpr -> Bool
$c>= :: BExpr -> BExpr -> Bool
> :: BExpr -> BExpr -> Bool
$c> :: BExpr -> BExpr -> Bool
<= :: BExpr -> BExpr -> Bool
$c<= :: BExpr -> BExpr -> Bool
< :: BExpr -> BExpr -> Bool
$c< :: BExpr -> BExpr -> Bool
compare :: BExpr -> BExpr -> Ordering
$ccompare :: BExpr -> BExpr -> Ordering
$cp1Ord :: Eq BExpr
Ord)

-- |
-- ==== References
-- @
-- c_expr:
--   | columnref
--   | AexprConst
--   | PARAM opt_indirection
--   | '(' a_expr ')' opt_indirection
--   | case_expr
--   | func_expr
--   | select_with_parens
--   | select_with_parens indirection
--   | EXISTS select_with_parens
--   | ARRAY select_with_parens
--   | ARRAY array_expr
--   | explicit_row
--   | implicit_row
--   | GROUPING '(' expr_list ')'
-- @
data CExpr
  = ColumnrefCExpr Columnref
  | AexprConstCExpr AexprConst
  | ParamCExpr Int (Maybe Indirection)
  | InParensCExpr AExpr (Maybe Indirection)
  | CaseCExpr CaseExpr
  | FuncCExpr FuncExpr
  | SelectWithParensCExpr SelectWithParens (Maybe Indirection)
  | ExistsCExpr SelectWithParens
  | ArrayCExpr (Either SelectWithParens ArrayExpr)
  | ExplicitRowCExpr ExplicitRow
  | ImplicitRowCExpr ImplicitRow
  | GroupingCExpr ExprList
  deriving (Int -> CExpr -> ShowS
[CExpr] -> ShowS
CExpr -> String
(Int -> CExpr -> ShowS)
-> (CExpr -> String) -> ([CExpr] -> ShowS) -> Show CExpr
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CExpr] -> ShowS
$cshowList :: [CExpr] -> ShowS
show :: CExpr -> String
$cshow :: CExpr -> String
showsPrec :: Int -> CExpr -> ShowS
$cshowsPrec :: Int -> CExpr -> ShowS
Show, (forall x. CExpr -> Rep CExpr x)
-> (forall x. Rep CExpr x -> CExpr) -> Generic CExpr
forall x. Rep CExpr x -> CExpr
forall x. CExpr -> Rep CExpr x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CExpr x -> CExpr
$cfrom :: forall x. CExpr -> Rep CExpr x
Generic, CExpr -> CExpr -> Bool
(CExpr -> CExpr -> Bool) -> (CExpr -> CExpr -> Bool) -> Eq CExpr
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CExpr -> CExpr -> Bool
$c/= :: CExpr -> CExpr -> Bool
== :: CExpr -> CExpr -> Bool
$c== :: CExpr -> CExpr -> Bool
Eq, Eq CExpr
Eq CExpr
-> (CExpr -> CExpr -> Ordering)
-> (CExpr -> CExpr -> Bool)
-> (CExpr -> CExpr -> Bool)
-> (CExpr -> CExpr -> Bool)
-> (CExpr -> CExpr -> Bool)
-> (CExpr -> CExpr -> CExpr)
-> (CExpr -> CExpr -> CExpr)
-> Ord CExpr
CExpr -> CExpr -> Bool
CExpr -> CExpr -> Ordering
CExpr -> CExpr -> CExpr
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CExpr -> CExpr -> CExpr
$cmin :: CExpr -> CExpr -> CExpr
max :: CExpr -> CExpr -> CExpr
$cmax :: CExpr -> CExpr -> CExpr
>= :: CExpr -> CExpr -> Bool
$c>= :: CExpr -> CExpr -> Bool
> :: CExpr -> CExpr -> Bool
$c> :: CExpr -> CExpr -> Bool
<= :: CExpr -> CExpr -> Bool
$c<= :: CExpr -> CExpr -> Bool
< :: CExpr -> CExpr -> Bool
$c< :: CExpr -> CExpr -> Bool
compare :: CExpr -> CExpr -> Ordering
$ccompare :: CExpr -> CExpr -> Ordering
$cp1Ord :: Eq CExpr
Ord)

-- **

-- |
-- ==== References
-- @
-- in_expr:
--   | select_with_parens
--   | '(' expr_list ')'
-- @
data InExpr
  = SelectInExpr SelectWithParens
  | ExprListInExpr ExprList
  deriving (Int -> InExpr -> ShowS
[InExpr] -> ShowS
InExpr -> String
(Int -> InExpr -> ShowS)
-> (InExpr -> String) -> ([InExpr] -> ShowS) -> Show InExpr
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InExpr] -> ShowS
$cshowList :: [InExpr] -> ShowS
show :: InExpr -> String
$cshow :: InExpr -> String
showsPrec :: Int -> InExpr -> ShowS
$cshowsPrec :: Int -> InExpr -> ShowS
Show, (forall x. InExpr -> Rep InExpr x)
-> (forall x. Rep InExpr x -> InExpr) -> Generic InExpr
forall x. Rep InExpr x -> InExpr
forall x. InExpr -> Rep InExpr x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep InExpr x -> InExpr
$cfrom :: forall x. InExpr -> Rep InExpr x
Generic, InExpr -> InExpr -> Bool
(InExpr -> InExpr -> Bool)
-> (InExpr -> InExpr -> Bool) -> Eq InExpr
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InExpr -> InExpr -> Bool
$c/= :: InExpr -> InExpr -> Bool
== :: InExpr -> InExpr -> Bool
$c== :: InExpr -> InExpr -> Bool
Eq, Eq InExpr
Eq InExpr
-> (InExpr -> InExpr -> Ordering)
-> (InExpr -> InExpr -> Bool)
-> (InExpr -> InExpr -> Bool)
-> (InExpr -> InExpr -> Bool)
-> (InExpr -> InExpr -> Bool)
-> (InExpr -> InExpr -> InExpr)
-> (InExpr -> InExpr -> InExpr)
-> Ord InExpr
InExpr -> InExpr -> Bool
InExpr -> InExpr -> Ordering
InExpr -> InExpr -> InExpr
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: InExpr -> InExpr -> InExpr
$cmin :: InExpr -> InExpr -> InExpr
max :: InExpr -> InExpr -> InExpr
$cmax :: InExpr -> InExpr -> InExpr
>= :: InExpr -> InExpr -> Bool
$c>= :: InExpr -> InExpr -> Bool
> :: InExpr -> InExpr -> Bool
$c> :: InExpr -> InExpr -> Bool
<= :: InExpr -> InExpr -> Bool
$c<= :: InExpr -> InExpr -> Bool
< :: InExpr -> InExpr -> Bool
$c< :: InExpr -> InExpr -> Bool
compare :: InExpr -> InExpr -> Ordering
$ccompare :: InExpr -> InExpr -> Ordering
$cp1Ord :: Eq InExpr
Ord)

-- |
-- ==== References
-- @
-- sub_type:
--   | ANY
--   | SOME
--   | ALL
-- @
data SubType = AnySubType | SomeSubType | AllSubType
  deriving (Int -> SubType -> ShowS
[SubType] -> ShowS
SubType -> String
(Int -> SubType -> ShowS)
-> (SubType -> String) -> ([SubType] -> ShowS) -> Show SubType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SubType] -> ShowS
$cshowList :: [SubType] -> ShowS
show :: SubType -> String
$cshow :: SubType -> String
showsPrec :: Int -> SubType -> ShowS
$cshowsPrec :: Int -> SubType -> ShowS
Show, (forall x. SubType -> Rep SubType x)
-> (forall x. Rep SubType x -> SubType) -> Generic SubType
forall x. Rep SubType x -> SubType
forall x. SubType -> Rep SubType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SubType x -> SubType
$cfrom :: forall x. SubType -> Rep SubType x
Generic, SubType -> SubType -> Bool
(SubType -> SubType -> Bool)
-> (SubType -> SubType -> Bool) -> Eq SubType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SubType -> SubType -> Bool
$c/= :: SubType -> SubType -> Bool
== :: SubType -> SubType -> Bool
$c== :: SubType -> SubType -> Bool
Eq, Eq SubType
Eq SubType
-> (SubType -> SubType -> Ordering)
-> (SubType -> SubType -> Bool)
-> (SubType -> SubType -> Bool)
-> (SubType -> SubType -> Bool)
-> (SubType -> SubType -> Bool)
-> (SubType -> SubType -> SubType)
-> (SubType -> SubType -> SubType)
-> Ord SubType
SubType -> SubType -> Bool
SubType -> SubType -> Ordering
SubType -> SubType -> SubType
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: SubType -> SubType -> SubType
$cmin :: SubType -> SubType -> SubType
max :: SubType -> SubType -> SubType
$cmax :: SubType -> SubType -> SubType
>= :: SubType -> SubType -> Bool
$c>= :: SubType -> SubType -> Bool
> :: SubType -> SubType -> Bool
$c> :: SubType -> SubType -> Bool
<= :: SubType -> SubType -> Bool
$c<= :: SubType -> SubType -> Bool
< :: SubType -> SubType -> Bool
$c< :: SubType -> SubType -> Bool
compare :: SubType -> SubType -> Ordering
$ccompare :: SubType -> SubType -> Ordering
$cp1Ord :: Eq SubType
Ord, Int -> SubType
SubType -> Int
SubType -> [SubType]
SubType -> SubType
SubType -> SubType -> [SubType]
SubType -> SubType -> SubType -> [SubType]
(SubType -> SubType)
-> (SubType -> SubType)
-> (Int -> SubType)
-> (SubType -> Int)
-> (SubType -> [SubType])
-> (SubType -> SubType -> [SubType])
-> (SubType -> SubType -> [SubType])
-> (SubType -> SubType -> SubType -> [SubType])
-> Enum SubType
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: SubType -> SubType -> SubType -> [SubType]
$cenumFromThenTo :: SubType -> SubType -> SubType -> [SubType]
enumFromTo :: SubType -> SubType -> [SubType]
$cenumFromTo :: SubType -> SubType -> [SubType]
enumFromThen :: SubType -> SubType -> [SubType]
$cenumFromThen :: SubType -> SubType -> [SubType]
enumFrom :: SubType -> [SubType]
$cenumFrom :: SubType -> [SubType]
fromEnum :: SubType -> Int
$cfromEnum :: SubType -> Int
toEnum :: Int -> SubType
$ctoEnum :: Int -> SubType
pred :: SubType -> SubType
$cpred :: SubType -> SubType
succ :: SubType -> SubType
$csucc :: SubType -> SubType
Enum, SubType
SubType -> SubType -> Bounded SubType
forall a. a -> a -> Bounded a
maxBound :: SubType
$cmaxBound :: SubType
minBound :: SubType
$cminBound :: SubType
Bounded)

-- |
-- ==== References
-- @
-- array_expr:
--   | '[' expr_list ']'
--   | '[' array_expr_list ']'
--   | '[' ']'
-- @
data ArrayExpr
  = ExprListArrayExpr ExprList
  | ArrayExprListArrayExpr ArrayExprList
  | EmptyArrayExpr
  deriving (Int -> ArrayExpr -> ShowS
[ArrayExpr] -> ShowS
ArrayExpr -> String
(Int -> ArrayExpr -> ShowS)
-> (ArrayExpr -> String)
-> ([ArrayExpr] -> ShowS)
-> Show ArrayExpr
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ArrayExpr] -> ShowS
$cshowList :: [ArrayExpr] -> ShowS
show :: ArrayExpr -> String
$cshow :: ArrayExpr -> String
showsPrec :: Int -> ArrayExpr -> ShowS
$cshowsPrec :: Int -> ArrayExpr -> ShowS
Show, (forall x. ArrayExpr -> Rep ArrayExpr x)
-> (forall x. Rep ArrayExpr x -> ArrayExpr) -> Generic ArrayExpr
forall x. Rep ArrayExpr x -> ArrayExpr
forall x. ArrayExpr -> Rep ArrayExpr x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ArrayExpr x -> ArrayExpr
$cfrom :: forall x. ArrayExpr -> Rep ArrayExpr x
Generic, ArrayExpr -> ArrayExpr -> Bool
(ArrayExpr -> ArrayExpr -> Bool)
-> (ArrayExpr -> ArrayExpr -> Bool) -> Eq ArrayExpr
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ArrayExpr -> ArrayExpr -> Bool
$c/= :: ArrayExpr -> ArrayExpr -> Bool
== :: ArrayExpr -> ArrayExpr -> Bool
$c== :: ArrayExpr -> ArrayExpr -> Bool
Eq, Eq ArrayExpr
Eq ArrayExpr
-> (ArrayExpr -> ArrayExpr -> Ordering)
-> (ArrayExpr -> ArrayExpr -> Bool)
-> (ArrayExpr -> ArrayExpr -> Bool)
-> (ArrayExpr -> ArrayExpr -> Bool)
-> (ArrayExpr -> ArrayExpr -> Bool)
-> (ArrayExpr -> ArrayExpr -> ArrayExpr)
-> (ArrayExpr -> ArrayExpr -> ArrayExpr)
-> Ord ArrayExpr
ArrayExpr -> ArrayExpr -> Bool
ArrayExpr -> ArrayExpr -> Ordering
ArrayExpr -> ArrayExpr -> ArrayExpr
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ArrayExpr -> ArrayExpr -> ArrayExpr
$cmin :: ArrayExpr -> ArrayExpr -> ArrayExpr
max :: ArrayExpr -> ArrayExpr -> ArrayExpr
$cmax :: ArrayExpr -> ArrayExpr -> ArrayExpr
>= :: ArrayExpr -> ArrayExpr -> Bool
$c>= :: ArrayExpr -> ArrayExpr -> Bool
> :: ArrayExpr -> ArrayExpr -> Bool
$c> :: ArrayExpr -> ArrayExpr -> Bool
<= :: ArrayExpr -> ArrayExpr -> Bool
$c<= :: ArrayExpr -> ArrayExpr -> Bool
< :: ArrayExpr -> ArrayExpr -> Bool
$c< :: ArrayExpr -> ArrayExpr -> Bool
compare :: ArrayExpr -> ArrayExpr -> Ordering
$ccompare :: ArrayExpr -> ArrayExpr -> Ordering
$cp1Ord :: Eq ArrayExpr
Ord)

-- |
-- ==== References
-- @
-- array_expr_list:
--   | array_expr
--   | array_expr_list ',' array_expr
-- @
type ArrayExprList = NonEmpty ArrayExpr

-- |
-- ==== References
-- @
-- row:
--   | ROW '(' expr_list ')'
--   | ROW '(' ')'
--   | '(' expr_list ',' a_expr ')'
-- @
data Row
  = ExplicitRowRow ExplicitRow
  | ImplicitRowRow ImplicitRow
  deriving (Int -> Row -> ShowS
[Row] -> ShowS
Row -> String
(Int -> Row -> ShowS)
-> (Row -> String) -> ([Row] -> ShowS) -> Show Row
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Row] -> ShowS
$cshowList :: [Row] -> ShowS
show :: Row -> String
$cshow :: Row -> String
showsPrec :: Int -> Row -> ShowS
$cshowsPrec :: Int -> Row -> ShowS
Show, (forall x. Row -> Rep Row x)
-> (forall x. Rep Row x -> Row) -> Generic Row
forall x. Rep Row x -> Row
forall x. Row -> Rep Row x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Row x -> Row
$cfrom :: forall x. Row -> Rep Row x
Generic, Row -> Row -> Bool
(Row -> Row -> Bool) -> (Row -> Row -> Bool) -> Eq Row
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Row -> Row -> Bool
$c/= :: Row -> Row -> Bool
== :: Row -> Row -> Bool
$c== :: Row -> Row -> Bool
Eq, Eq Row
Eq Row
-> (Row -> Row -> Ordering)
-> (Row -> Row -> Bool)
-> (Row -> Row -> Bool)
-> (Row -> Row -> Bool)
-> (Row -> Row -> Bool)
-> (Row -> Row -> Row)
-> (Row -> Row -> Row)
-> Ord Row
Row -> Row -> Bool
Row -> Row -> Ordering
Row -> Row -> Row
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Row -> Row -> Row
$cmin :: Row -> Row -> Row
max :: Row -> Row -> Row
$cmax :: Row -> Row -> Row
>= :: Row -> Row -> Bool
$c>= :: Row -> Row -> Bool
> :: Row -> Row -> Bool
$c> :: Row -> Row -> Bool
<= :: Row -> Row -> Bool
$c<= :: Row -> Row -> Bool
< :: Row -> Row -> Bool
$c< :: Row -> Row -> Bool
compare :: Row -> Row -> Ordering
$ccompare :: Row -> Row -> Ordering
$cp1Ord :: Eq Row
Ord)

-- |
-- ==== References
-- @
-- explicit_row:
--   | ROW '(' expr_list ')'
--   | ROW '(' ')'
-- @
type ExplicitRow = Maybe ExprList

-- |
-- ==== References
-- @
-- implicit_row:
--   | '(' expr_list ',' a_expr ')'
-- @
data ImplicitRow = ImplicitRow ExprList AExpr
  deriving (Int -> ImplicitRow -> ShowS
[ImplicitRow] -> ShowS
ImplicitRow -> String
(Int -> ImplicitRow -> ShowS)
-> (ImplicitRow -> String)
-> ([ImplicitRow] -> ShowS)
-> Show ImplicitRow
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ImplicitRow] -> ShowS
$cshowList :: [ImplicitRow] -> ShowS
show :: ImplicitRow -> String
$cshow :: ImplicitRow -> String
showsPrec :: Int -> ImplicitRow -> ShowS
$cshowsPrec :: Int -> ImplicitRow -> ShowS
Show, (forall x. ImplicitRow -> Rep ImplicitRow x)
-> (forall x. Rep ImplicitRow x -> ImplicitRow)
-> Generic ImplicitRow
forall x. Rep ImplicitRow x -> ImplicitRow
forall x. ImplicitRow -> Rep ImplicitRow x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ImplicitRow x -> ImplicitRow
$cfrom :: forall x. ImplicitRow -> Rep ImplicitRow x
Generic, ImplicitRow -> ImplicitRow -> Bool
(ImplicitRow -> ImplicitRow -> Bool)
-> (ImplicitRow -> ImplicitRow -> Bool) -> Eq ImplicitRow
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ImplicitRow -> ImplicitRow -> Bool
$c/= :: ImplicitRow -> ImplicitRow -> Bool
== :: ImplicitRow -> ImplicitRow -> Bool
$c== :: ImplicitRow -> ImplicitRow -> Bool
Eq, Eq ImplicitRow
Eq ImplicitRow
-> (ImplicitRow -> ImplicitRow -> Ordering)
-> (ImplicitRow -> ImplicitRow -> Bool)
-> (ImplicitRow -> ImplicitRow -> Bool)
-> (ImplicitRow -> ImplicitRow -> Bool)
-> (ImplicitRow -> ImplicitRow -> Bool)
-> (ImplicitRow -> ImplicitRow -> ImplicitRow)
-> (ImplicitRow -> ImplicitRow -> ImplicitRow)
-> Ord ImplicitRow
ImplicitRow -> ImplicitRow -> Bool
ImplicitRow -> ImplicitRow -> Ordering
ImplicitRow -> ImplicitRow -> ImplicitRow
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ImplicitRow -> ImplicitRow -> ImplicitRow
$cmin :: ImplicitRow -> ImplicitRow -> ImplicitRow
max :: ImplicitRow -> ImplicitRow -> ImplicitRow
$cmax :: ImplicitRow -> ImplicitRow -> ImplicitRow
>= :: ImplicitRow -> ImplicitRow -> Bool
$c>= :: ImplicitRow -> ImplicitRow -> Bool
> :: ImplicitRow -> ImplicitRow -> Bool
$c> :: ImplicitRow -> ImplicitRow -> Bool
<= :: ImplicitRow -> ImplicitRow -> Bool
$c<= :: ImplicitRow -> ImplicitRow -> Bool
< :: ImplicitRow -> ImplicitRow -> Bool
$c< :: ImplicitRow -> ImplicitRow -> Bool
compare :: ImplicitRow -> ImplicitRow -> Ordering
$ccompare :: ImplicitRow -> ImplicitRow -> Ordering
$cp1Ord :: Eq ImplicitRow
Ord)

-- |
-- ==== References
-- @
-- func_expr:
--   | func_application within_group_clause filter_clause over_clause
--   | func_expr_common_subexpr
-- @
data FuncExpr
  = ApplicationFuncExpr FuncApplication (Maybe WithinGroupClause) (Maybe FilterClause) (Maybe OverClause)
  | SubexprFuncExpr FuncExprCommonSubexpr
  deriving (Int -> FuncExpr -> ShowS
[FuncExpr] -> ShowS
FuncExpr -> String
(Int -> FuncExpr -> ShowS)
-> (FuncExpr -> String) -> ([FuncExpr] -> ShowS) -> Show FuncExpr
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FuncExpr] -> ShowS
$cshowList :: [FuncExpr] -> ShowS
show :: FuncExpr -> String
$cshow :: FuncExpr -> String
showsPrec :: Int -> FuncExpr -> ShowS
$cshowsPrec :: Int -> FuncExpr -> ShowS
Show, (forall x. FuncExpr -> Rep FuncExpr x)
-> (forall x. Rep FuncExpr x -> FuncExpr) -> Generic FuncExpr
forall x. Rep FuncExpr x -> FuncExpr
forall x. FuncExpr -> Rep FuncExpr x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep FuncExpr x -> FuncExpr
$cfrom :: forall x. FuncExpr -> Rep FuncExpr x
Generic, FuncExpr -> FuncExpr -> Bool
(FuncExpr -> FuncExpr -> Bool)
-> (FuncExpr -> FuncExpr -> Bool) -> Eq FuncExpr
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FuncExpr -> FuncExpr -> Bool
$c/= :: FuncExpr -> FuncExpr -> Bool
== :: FuncExpr -> FuncExpr -> Bool
$c== :: FuncExpr -> FuncExpr -> Bool
Eq, Eq FuncExpr
Eq FuncExpr
-> (FuncExpr -> FuncExpr -> Ordering)
-> (FuncExpr -> FuncExpr -> Bool)
-> (FuncExpr -> FuncExpr -> Bool)
-> (FuncExpr -> FuncExpr -> Bool)
-> (FuncExpr -> FuncExpr -> Bool)
-> (FuncExpr -> FuncExpr -> FuncExpr)
-> (FuncExpr -> FuncExpr -> FuncExpr)
-> Ord FuncExpr
FuncExpr -> FuncExpr -> Bool
FuncExpr -> FuncExpr -> Ordering
FuncExpr -> FuncExpr -> FuncExpr
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: FuncExpr -> FuncExpr -> FuncExpr
$cmin :: FuncExpr -> FuncExpr -> FuncExpr
max :: FuncExpr -> FuncExpr -> FuncExpr
$cmax :: FuncExpr -> FuncExpr -> FuncExpr
>= :: FuncExpr -> FuncExpr -> Bool
$c>= :: FuncExpr -> FuncExpr -> Bool
> :: FuncExpr -> FuncExpr -> Bool
$c> :: FuncExpr -> FuncExpr -> Bool
<= :: FuncExpr -> FuncExpr -> Bool
$c<= :: FuncExpr -> FuncExpr -> Bool
< :: FuncExpr -> FuncExpr -> Bool
$c< :: FuncExpr -> FuncExpr -> Bool
compare :: FuncExpr -> FuncExpr -> Ordering
$ccompare :: FuncExpr -> FuncExpr -> Ordering
$cp1Ord :: Eq FuncExpr
Ord)

-- |
-- ==== References
-- @
-- func_expr_windowless:
--   | func_application
--   | func_expr_common_subexpr
-- @
data FuncExprWindowless
  = ApplicationFuncExprWindowless FuncApplication
  | CommonSubexprFuncExprWindowless FuncExprCommonSubexpr
  deriving (Int -> FuncExprWindowless -> ShowS
[FuncExprWindowless] -> ShowS
FuncExprWindowless -> String
(Int -> FuncExprWindowless -> ShowS)
-> (FuncExprWindowless -> String)
-> ([FuncExprWindowless] -> ShowS)
-> Show FuncExprWindowless
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FuncExprWindowless] -> ShowS
$cshowList :: [FuncExprWindowless] -> ShowS
show :: FuncExprWindowless -> String
$cshow :: FuncExprWindowless -> String
showsPrec :: Int -> FuncExprWindowless -> ShowS
$cshowsPrec :: Int -> FuncExprWindowless -> ShowS
Show, (forall x. FuncExprWindowless -> Rep FuncExprWindowless x)
-> (forall x. Rep FuncExprWindowless x -> FuncExprWindowless)
-> Generic FuncExprWindowless
forall x. Rep FuncExprWindowless x -> FuncExprWindowless
forall x. FuncExprWindowless -> Rep FuncExprWindowless x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep FuncExprWindowless x -> FuncExprWindowless
$cfrom :: forall x. FuncExprWindowless -> Rep FuncExprWindowless x
Generic, FuncExprWindowless -> FuncExprWindowless -> Bool
(FuncExprWindowless -> FuncExprWindowless -> Bool)
-> (FuncExprWindowless -> FuncExprWindowless -> Bool)
-> Eq FuncExprWindowless
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FuncExprWindowless -> FuncExprWindowless -> Bool
$c/= :: FuncExprWindowless -> FuncExprWindowless -> Bool
== :: FuncExprWindowless -> FuncExprWindowless -> Bool
$c== :: FuncExprWindowless -> FuncExprWindowless -> Bool
Eq, Eq FuncExprWindowless
Eq FuncExprWindowless
-> (FuncExprWindowless -> FuncExprWindowless -> Ordering)
-> (FuncExprWindowless -> FuncExprWindowless -> Bool)
-> (FuncExprWindowless -> FuncExprWindowless -> Bool)
-> (FuncExprWindowless -> FuncExprWindowless -> Bool)
-> (FuncExprWindowless -> FuncExprWindowless -> Bool)
-> (FuncExprWindowless -> FuncExprWindowless -> FuncExprWindowless)
-> (FuncExprWindowless -> FuncExprWindowless -> FuncExprWindowless)
-> Ord FuncExprWindowless
FuncExprWindowless -> FuncExprWindowless -> Bool
FuncExprWindowless -> FuncExprWindowless -> Ordering
FuncExprWindowless -> FuncExprWindowless -> FuncExprWindowless
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: FuncExprWindowless -> FuncExprWindowless -> FuncExprWindowless
$cmin :: FuncExprWindowless -> FuncExprWindowless -> FuncExprWindowless
max :: FuncExprWindowless -> FuncExprWindowless -> FuncExprWindowless
$cmax :: FuncExprWindowless -> FuncExprWindowless -> FuncExprWindowless
>= :: FuncExprWindowless -> FuncExprWindowless -> Bool
$c>= :: FuncExprWindowless -> FuncExprWindowless -> Bool
> :: FuncExprWindowless -> FuncExprWindowless -> Bool
$c> :: FuncExprWindowless -> FuncExprWindowless -> Bool
<= :: FuncExprWindowless -> FuncExprWindowless -> Bool
$c<= :: FuncExprWindowless -> FuncExprWindowless -> Bool
< :: FuncExprWindowless -> FuncExprWindowless -> Bool
$c< :: FuncExprWindowless -> FuncExprWindowless -> Bool
compare :: FuncExprWindowless -> FuncExprWindowless -> Ordering
$ccompare :: FuncExprWindowless -> FuncExprWindowless -> Ordering
$cp1Ord :: Eq FuncExprWindowless
Ord)

-- |
-- ==== References
-- @
-- within_group_clause:
--   | WITHIN GROUP_P '(' sort_clause ')'
--   | EMPTY
-- @
type WithinGroupClause = SortClause

-- |
-- ==== References
-- @
-- filter_clause:
--   | FILTER '(' WHERE a_expr ')'
--   | EMPTY
-- @
type FilterClause = AExpr

-- |
-- ==== References
-- @
-- over_clause:
--   | OVER window_specification
--   | OVER ColId
--   | EMPTY
-- @
data OverClause
  = WindowOverClause WindowSpecification
  | ColIdOverClause ColId
  deriving (Int -> OverClause -> ShowS
[OverClause] -> ShowS
OverClause -> String
(Int -> OverClause -> ShowS)
-> (OverClause -> String)
-> ([OverClause] -> ShowS)
-> Show OverClause
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [OverClause] -> ShowS
$cshowList :: [OverClause] -> ShowS
show :: OverClause -> String
$cshow :: OverClause -> String
showsPrec :: Int -> OverClause -> ShowS
$cshowsPrec :: Int -> OverClause -> ShowS
Show, (forall x. OverClause -> Rep OverClause x)
-> (forall x. Rep OverClause x -> OverClause) -> Generic OverClause
forall x. Rep OverClause x -> OverClause
forall x. OverClause -> Rep OverClause x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep OverClause x -> OverClause
$cfrom :: forall x. OverClause -> Rep OverClause x
Generic, OverClause -> OverClause -> Bool
(OverClause -> OverClause -> Bool)
-> (OverClause -> OverClause -> Bool) -> Eq OverClause
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OverClause -> OverClause -> Bool
$c/= :: OverClause -> OverClause -> Bool
== :: OverClause -> OverClause -> Bool
$c== :: OverClause -> OverClause -> Bool
Eq, Eq OverClause
Eq OverClause
-> (OverClause -> OverClause -> Ordering)
-> (OverClause -> OverClause -> Bool)
-> (OverClause -> OverClause -> Bool)
-> (OverClause -> OverClause -> Bool)
-> (OverClause -> OverClause -> Bool)
-> (OverClause -> OverClause -> OverClause)
-> (OverClause -> OverClause -> OverClause)
-> Ord OverClause
OverClause -> OverClause -> Bool
OverClause -> OverClause -> Ordering
OverClause -> OverClause -> OverClause
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: OverClause -> OverClause -> OverClause
$cmin :: OverClause -> OverClause -> OverClause
max :: OverClause -> OverClause -> OverClause
$cmax :: OverClause -> OverClause -> OverClause
>= :: OverClause -> OverClause -> Bool
$c>= :: OverClause -> OverClause -> Bool
> :: OverClause -> OverClause -> Bool
$c> :: OverClause -> OverClause -> Bool
<= :: OverClause -> OverClause -> Bool
$c<= :: OverClause -> OverClause -> Bool
< :: OverClause -> OverClause -> Bool
$c< :: OverClause -> OverClause -> Bool
compare :: OverClause -> OverClause -> Ordering
$ccompare :: OverClause -> OverClause -> Ordering
$cp1Ord :: Eq OverClause
Ord)

-- |
-- ==== References
-- @
-- func_expr_common_subexpr:
--   | COLLATION FOR '(' a_expr ')'
--   | CURRENT_DATE
--   | CURRENT_TIME
--   | CURRENT_TIME '(' Iconst ')'
--   | CURRENT_TIMESTAMP
--   | CURRENT_TIMESTAMP '(' Iconst ')'
--   | LOCALTIME
--   | LOCALTIME '(' Iconst ')'
--   | LOCALTIMESTAMP
--   | LOCALTIMESTAMP '(' Iconst ')'
--   | CURRENT_ROLE
--   | CURRENT_USER
--   | SESSION_USER
--   | USER
--   | CURRENT_CATALOG
--   | CURRENT_SCHEMA
--   | CAST '(' a_expr AS Typename ')'
--   | EXTRACT '(' extract_list ')'
--   | OVERLAY '(' overlay_list ')'
--   | POSITION '(' position_list ')'
--   | SUBSTRING '(' substr_list ')'
--   | TREAT '(' a_expr AS Typename ')'
--   | TRIM '(' BOTH trim_list ')'
--   | TRIM '(' LEADING trim_list ')'
--   | TRIM '(' TRAILING trim_list ')'
--   | TRIM '(' trim_list ')'
--   | NULLIF '(' a_expr ',' a_expr ')'
--   | COALESCE '(' expr_list ')'
--   | GREATEST '(' expr_list ')'
--   | LEAST '(' expr_list ')'
--   | XMLCONCAT '(' expr_list ')'
--   | XMLELEMENT '(' NAME_P ColLabel ')'
--   | XMLELEMENT '(' NAME_P ColLabel ',' xml_attributes ')'
--   | XMLELEMENT '(' NAME_P ColLabel ',' expr_list ')'
--   | XMLELEMENT '(' NAME_P ColLabel ',' xml_attributes ',' expr_list ')'
--   | XMLEXISTS '(' c_expr xmlexists_argument ')'
--   | XMLFOREST '(' xml_attribute_list ')'
--   | XMLPARSE '(' document_or_content a_expr xml_whitespace_option ')'
--   | XMLPI '(' NAME_P ColLabel ')'
--   | XMLPI '(' NAME_P ColLabel ',' a_expr ')'
--   | XMLROOT '(' a_expr ',' xml_root_version opt_xml_root_standalone ')'
--   | XMLSERIALIZE '(' document_or_content a_expr AS SimpleTypename ')'
--
-- TODO: Implement the XML cases
-- @
data FuncExprCommonSubexpr
  = CollationForFuncExprCommonSubexpr AExpr
  | CurrentDateFuncExprCommonSubexpr
  | CurrentTimeFuncExprCommonSubexpr (Maybe Int64)
  | CurrentTimestampFuncExprCommonSubexpr (Maybe Int64)
  | LocalTimeFuncExprCommonSubexpr (Maybe Int64)
  | LocalTimestampFuncExprCommonSubexpr (Maybe Int64)
  | CurrentRoleFuncExprCommonSubexpr
  | CurrentUserFuncExprCommonSubexpr
  | SessionUserFuncExprCommonSubexpr
  | UserFuncExprCommonSubexpr
  | CurrentCatalogFuncExprCommonSubexpr
  | CurrentSchemaFuncExprCommonSubexpr
  | CastFuncExprCommonSubexpr AExpr Typename
  | ExtractFuncExprCommonSubexpr (Maybe ExtractList)
  | OverlayFuncExprCommonSubexpr OverlayList
  | PositionFuncExprCommonSubexpr (Maybe PositionList)
  | SubstringFuncExprCommonSubexpr (Maybe SubstrList)
  | TreatFuncExprCommonSubexpr AExpr Typename
  | TrimFuncExprCommonSubexpr (Maybe TrimModifier) TrimList
  | NullIfFuncExprCommonSubexpr AExpr AExpr
  | CoalesceFuncExprCommonSubexpr ExprList
  | GreatestFuncExprCommonSubexpr ExprList
  | LeastFuncExprCommonSubexpr ExprList
  deriving (Int -> FuncExprCommonSubexpr -> ShowS
[FuncExprCommonSubexpr] -> ShowS
FuncExprCommonSubexpr -> String
(Int -> FuncExprCommonSubexpr -> ShowS)
-> (FuncExprCommonSubexpr -> String)
-> ([FuncExprCommonSubexpr] -> ShowS)
-> Show FuncExprCommonSubexpr
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FuncExprCommonSubexpr] -> ShowS
$cshowList :: [FuncExprCommonSubexpr] -> ShowS
show :: FuncExprCommonSubexpr -> String
$cshow :: FuncExprCommonSubexpr -> String
showsPrec :: Int -> FuncExprCommonSubexpr -> ShowS
$cshowsPrec :: Int -> FuncExprCommonSubexpr -> ShowS
Show, (forall x. FuncExprCommonSubexpr -> Rep FuncExprCommonSubexpr x)
-> (forall x. Rep FuncExprCommonSubexpr x -> FuncExprCommonSubexpr)
-> Generic FuncExprCommonSubexpr
forall x. Rep FuncExprCommonSubexpr x -> FuncExprCommonSubexpr
forall x. FuncExprCommonSubexpr -> Rep FuncExprCommonSubexpr x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep FuncExprCommonSubexpr x -> FuncExprCommonSubexpr
$cfrom :: forall x. FuncExprCommonSubexpr -> Rep FuncExprCommonSubexpr x
Generic, FuncExprCommonSubexpr -> FuncExprCommonSubexpr -> Bool
(FuncExprCommonSubexpr -> FuncExprCommonSubexpr -> Bool)
-> (FuncExprCommonSubexpr -> FuncExprCommonSubexpr -> Bool)
-> Eq FuncExprCommonSubexpr
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FuncExprCommonSubexpr -> FuncExprCommonSubexpr -> Bool
$c/= :: FuncExprCommonSubexpr -> FuncExprCommonSubexpr -> Bool
== :: FuncExprCommonSubexpr -> FuncExprCommonSubexpr -> Bool
$c== :: FuncExprCommonSubexpr -> FuncExprCommonSubexpr -> Bool
Eq, Eq FuncExprCommonSubexpr
Eq FuncExprCommonSubexpr
-> (FuncExprCommonSubexpr -> FuncExprCommonSubexpr -> Ordering)
-> (FuncExprCommonSubexpr -> FuncExprCommonSubexpr -> Bool)
-> (FuncExprCommonSubexpr -> FuncExprCommonSubexpr -> Bool)
-> (FuncExprCommonSubexpr -> FuncExprCommonSubexpr -> Bool)
-> (FuncExprCommonSubexpr -> FuncExprCommonSubexpr -> Bool)
-> (FuncExprCommonSubexpr
    -> FuncExprCommonSubexpr -> FuncExprCommonSubexpr)
-> (FuncExprCommonSubexpr
    -> FuncExprCommonSubexpr -> FuncExprCommonSubexpr)
-> Ord FuncExprCommonSubexpr
FuncExprCommonSubexpr -> FuncExprCommonSubexpr -> Bool
FuncExprCommonSubexpr -> FuncExprCommonSubexpr -> Ordering
FuncExprCommonSubexpr
-> FuncExprCommonSubexpr -> FuncExprCommonSubexpr
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: FuncExprCommonSubexpr
-> FuncExprCommonSubexpr -> FuncExprCommonSubexpr
$cmin :: FuncExprCommonSubexpr
-> FuncExprCommonSubexpr -> FuncExprCommonSubexpr
max :: FuncExprCommonSubexpr
-> FuncExprCommonSubexpr -> FuncExprCommonSubexpr
$cmax :: FuncExprCommonSubexpr
-> FuncExprCommonSubexpr -> FuncExprCommonSubexpr
>= :: FuncExprCommonSubexpr -> FuncExprCommonSubexpr -> Bool
$c>= :: FuncExprCommonSubexpr -> FuncExprCommonSubexpr -> Bool
> :: FuncExprCommonSubexpr -> FuncExprCommonSubexpr -> Bool
$c> :: FuncExprCommonSubexpr -> FuncExprCommonSubexpr -> Bool
<= :: FuncExprCommonSubexpr -> FuncExprCommonSubexpr -> Bool
$c<= :: FuncExprCommonSubexpr -> FuncExprCommonSubexpr -> Bool
< :: FuncExprCommonSubexpr -> FuncExprCommonSubexpr -> Bool
$c< :: FuncExprCommonSubexpr -> FuncExprCommonSubexpr -> Bool
compare :: FuncExprCommonSubexpr -> FuncExprCommonSubexpr -> Ordering
$ccompare :: FuncExprCommonSubexpr -> FuncExprCommonSubexpr -> Ordering
$cp1Ord :: Eq FuncExprCommonSubexpr
Ord)

-- |
-- ==== References
-- @
-- extract_list:
--   | extract_arg FROM a_expr
--   | EMPTY
-- @
data ExtractList = ExtractList ExtractArg AExpr
  deriving (Int -> ExtractList -> ShowS
[ExtractList] -> ShowS
ExtractList -> String
(Int -> ExtractList -> ShowS)
-> (ExtractList -> String)
-> ([ExtractList] -> ShowS)
-> Show ExtractList
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ExtractList] -> ShowS
$cshowList :: [ExtractList] -> ShowS
show :: ExtractList -> String
$cshow :: ExtractList -> String
showsPrec :: Int -> ExtractList -> ShowS
$cshowsPrec :: Int -> ExtractList -> ShowS
Show, (forall x. ExtractList -> Rep ExtractList x)
-> (forall x. Rep ExtractList x -> ExtractList)
-> Generic ExtractList
forall x. Rep ExtractList x -> ExtractList
forall x. ExtractList -> Rep ExtractList x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ExtractList x -> ExtractList
$cfrom :: forall x. ExtractList -> Rep ExtractList x
Generic, ExtractList -> ExtractList -> Bool
(ExtractList -> ExtractList -> Bool)
-> (ExtractList -> ExtractList -> Bool) -> Eq ExtractList
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ExtractList -> ExtractList -> Bool
$c/= :: ExtractList -> ExtractList -> Bool
== :: ExtractList -> ExtractList -> Bool
$c== :: ExtractList -> ExtractList -> Bool
Eq, Eq ExtractList
Eq ExtractList
-> (ExtractList -> ExtractList -> Ordering)
-> (ExtractList -> ExtractList -> Bool)
-> (ExtractList -> ExtractList -> Bool)
-> (ExtractList -> ExtractList -> Bool)
-> (ExtractList -> ExtractList -> Bool)
-> (ExtractList -> ExtractList -> ExtractList)
-> (ExtractList -> ExtractList -> ExtractList)
-> Ord ExtractList
ExtractList -> ExtractList -> Bool
ExtractList -> ExtractList -> Ordering
ExtractList -> ExtractList -> ExtractList
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ExtractList -> ExtractList -> ExtractList
$cmin :: ExtractList -> ExtractList -> ExtractList
max :: ExtractList -> ExtractList -> ExtractList
$cmax :: ExtractList -> ExtractList -> ExtractList
>= :: ExtractList -> ExtractList -> Bool
$c>= :: ExtractList -> ExtractList -> Bool
> :: ExtractList -> ExtractList -> Bool
$c> :: ExtractList -> ExtractList -> Bool
<= :: ExtractList -> ExtractList -> Bool
$c<= :: ExtractList -> ExtractList -> Bool
< :: ExtractList -> ExtractList -> Bool
$c< :: ExtractList -> ExtractList -> Bool
compare :: ExtractList -> ExtractList -> Ordering
$ccompare :: ExtractList -> ExtractList -> Ordering
$cp1Ord :: Eq ExtractList
Ord)

-- |
-- ==== References
-- @
-- extract_arg:
--   | IDENT
--   | YEAR_P
--   | MONTH_P
--   | DAY_P
--   | HOUR_P
--   | MINUTE_P
--   | SECOND_P
--   | Sconst
-- @
data ExtractArg
  = IdentExtractArg Ident
  | YearExtractArg
  | MonthExtractArg
  | DayExtractArg
  | HourExtractArg
  | MinuteExtractArg
  | SecondExtractArg
  | SconstExtractArg Sconst
  deriving (Int -> ExtractArg -> ShowS
[ExtractArg] -> ShowS
ExtractArg -> String
(Int -> ExtractArg -> ShowS)
-> (ExtractArg -> String)
-> ([ExtractArg] -> ShowS)
-> Show ExtractArg
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ExtractArg] -> ShowS
$cshowList :: [ExtractArg] -> ShowS
show :: ExtractArg -> String
$cshow :: ExtractArg -> String
showsPrec :: Int -> ExtractArg -> ShowS
$cshowsPrec :: Int -> ExtractArg -> ShowS
Show, (forall x. ExtractArg -> Rep ExtractArg x)
-> (forall x. Rep ExtractArg x -> ExtractArg) -> Generic ExtractArg
forall x. Rep ExtractArg x -> ExtractArg
forall x. ExtractArg -> Rep ExtractArg x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ExtractArg x -> ExtractArg
$cfrom :: forall x. ExtractArg -> Rep ExtractArg x
Generic, ExtractArg -> ExtractArg -> Bool
(ExtractArg -> ExtractArg -> Bool)
-> (ExtractArg -> ExtractArg -> Bool) -> Eq ExtractArg
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ExtractArg -> ExtractArg -> Bool
$c/= :: ExtractArg -> ExtractArg -> Bool
== :: ExtractArg -> ExtractArg -> Bool
$c== :: ExtractArg -> ExtractArg -> Bool
Eq, Eq ExtractArg
Eq ExtractArg
-> (ExtractArg -> ExtractArg -> Ordering)
-> (ExtractArg -> ExtractArg -> Bool)
-> (ExtractArg -> ExtractArg -> Bool)
-> (ExtractArg -> ExtractArg -> Bool)
-> (ExtractArg -> ExtractArg -> Bool)
-> (ExtractArg -> ExtractArg -> ExtractArg)
-> (ExtractArg -> ExtractArg -> ExtractArg)
-> Ord ExtractArg
ExtractArg -> ExtractArg -> Bool
ExtractArg -> ExtractArg -> Ordering
ExtractArg -> ExtractArg -> ExtractArg
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ExtractArg -> ExtractArg -> ExtractArg
$cmin :: ExtractArg -> ExtractArg -> ExtractArg
max :: ExtractArg -> ExtractArg -> ExtractArg
$cmax :: ExtractArg -> ExtractArg -> ExtractArg
>= :: ExtractArg -> ExtractArg -> Bool
$c>= :: ExtractArg -> ExtractArg -> Bool
> :: ExtractArg -> ExtractArg -> Bool
$c> :: ExtractArg -> ExtractArg -> Bool
<= :: ExtractArg -> ExtractArg -> Bool
$c<= :: ExtractArg -> ExtractArg -> Bool
< :: ExtractArg -> ExtractArg -> Bool
$c< :: ExtractArg -> ExtractArg -> Bool
compare :: ExtractArg -> ExtractArg -> Ordering
$ccompare :: ExtractArg -> ExtractArg -> Ordering
$cp1Ord :: Eq ExtractArg
Ord)

-- |
-- ==== References
-- @
-- overlay_list:
--   | a_expr overlay_placing substr_from substr_for
--   | a_expr overlay_placing substr_from
-- @
data OverlayList = OverlayList AExpr OverlayPlacing SubstrFrom (Maybe SubstrFor)
  deriving (Int -> OverlayList -> ShowS
[OverlayList] -> ShowS
OverlayList -> String
(Int -> OverlayList -> ShowS)
-> (OverlayList -> String)
-> ([OverlayList] -> ShowS)
-> Show OverlayList
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [OverlayList] -> ShowS
$cshowList :: [OverlayList] -> ShowS
show :: OverlayList -> String
$cshow :: OverlayList -> String
showsPrec :: Int -> OverlayList -> ShowS
$cshowsPrec :: Int -> OverlayList -> ShowS
Show, (forall x. OverlayList -> Rep OverlayList x)
-> (forall x. Rep OverlayList x -> OverlayList)
-> Generic OverlayList
forall x. Rep OverlayList x -> OverlayList
forall x. OverlayList -> Rep OverlayList x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep OverlayList x -> OverlayList
$cfrom :: forall x. OverlayList -> Rep OverlayList x
Generic, OverlayList -> OverlayList -> Bool
(OverlayList -> OverlayList -> Bool)
-> (OverlayList -> OverlayList -> Bool) -> Eq OverlayList
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OverlayList -> OverlayList -> Bool
$c/= :: OverlayList -> OverlayList -> Bool
== :: OverlayList -> OverlayList -> Bool
$c== :: OverlayList -> OverlayList -> Bool
Eq, Eq OverlayList
Eq OverlayList
-> (OverlayList -> OverlayList -> Ordering)
-> (OverlayList -> OverlayList -> Bool)
-> (OverlayList -> OverlayList -> Bool)
-> (OverlayList -> OverlayList -> Bool)
-> (OverlayList -> OverlayList -> Bool)
-> (OverlayList -> OverlayList -> OverlayList)
-> (OverlayList -> OverlayList -> OverlayList)
-> Ord OverlayList
OverlayList -> OverlayList -> Bool
OverlayList -> OverlayList -> Ordering
OverlayList -> OverlayList -> OverlayList
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: OverlayList -> OverlayList -> OverlayList
$cmin :: OverlayList -> OverlayList -> OverlayList
max :: OverlayList -> OverlayList -> OverlayList
$cmax :: OverlayList -> OverlayList -> OverlayList
>= :: OverlayList -> OverlayList -> Bool
$c>= :: OverlayList -> OverlayList -> Bool
> :: OverlayList -> OverlayList -> Bool
$c> :: OverlayList -> OverlayList -> Bool
<= :: OverlayList -> OverlayList -> Bool
$c<= :: OverlayList -> OverlayList -> Bool
< :: OverlayList -> OverlayList -> Bool
$c< :: OverlayList -> OverlayList -> Bool
compare :: OverlayList -> OverlayList -> Ordering
$ccompare :: OverlayList -> OverlayList -> Ordering
$cp1Ord :: Eq OverlayList
Ord)

-- |
-- ==== References
-- @
-- overlay_placing:
--   | PLACING a_expr
-- @
type OverlayPlacing = AExpr

-- |
-- ==== References
-- @
-- position_list:
--   | b_expr IN_P b_expr
--   | EMPTY
-- @
data PositionList = PositionList BExpr BExpr
  deriving (Int -> PositionList -> ShowS
[PositionList] -> ShowS
PositionList -> String
(Int -> PositionList -> ShowS)
-> (PositionList -> String)
-> ([PositionList] -> ShowS)
-> Show PositionList
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PositionList] -> ShowS
$cshowList :: [PositionList] -> ShowS
show :: PositionList -> String
$cshow :: PositionList -> String
showsPrec :: Int -> PositionList -> ShowS
$cshowsPrec :: Int -> PositionList -> ShowS
Show, (forall x. PositionList -> Rep PositionList x)
-> (forall x. Rep PositionList x -> PositionList)
-> Generic PositionList
forall x. Rep PositionList x -> PositionList
forall x. PositionList -> Rep PositionList x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PositionList x -> PositionList
$cfrom :: forall x. PositionList -> Rep PositionList x
Generic, PositionList -> PositionList -> Bool
(PositionList -> PositionList -> Bool)
-> (PositionList -> PositionList -> Bool) -> Eq PositionList
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PositionList -> PositionList -> Bool
$c/= :: PositionList -> PositionList -> Bool
== :: PositionList -> PositionList -> Bool
$c== :: PositionList -> PositionList -> Bool
Eq, Eq PositionList
Eq PositionList
-> (PositionList -> PositionList -> Ordering)
-> (PositionList -> PositionList -> Bool)
-> (PositionList -> PositionList -> Bool)
-> (PositionList -> PositionList -> Bool)
-> (PositionList -> PositionList -> Bool)
-> (PositionList -> PositionList -> PositionList)
-> (PositionList -> PositionList -> PositionList)
-> Ord PositionList
PositionList -> PositionList -> Bool
PositionList -> PositionList -> Ordering
PositionList -> PositionList -> PositionList
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: PositionList -> PositionList -> PositionList
$cmin :: PositionList -> PositionList -> PositionList
max :: PositionList -> PositionList -> PositionList
$cmax :: PositionList -> PositionList -> PositionList
>= :: PositionList -> PositionList -> Bool
$c>= :: PositionList -> PositionList -> Bool
> :: PositionList -> PositionList -> Bool
$c> :: PositionList -> PositionList -> Bool
<= :: PositionList -> PositionList -> Bool
$c<= :: PositionList -> PositionList -> Bool
< :: PositionList -> PositionList -> Bool
$c< :: PositionList -> PositionList -> Bool
compare :: PositionList -> PositionList -> Ordering
$ccompare :: PositionList -> PositionList -> Ordering
$cp1Ord :: Eq PositionList
Ord)

-- |
-- ==== References
-- @
-- substr_list:
--   | a_expr substr_from substr_for
--   | a_expr substr_for substr_from
--   | a_expr substr_from
--   | a_expr substr_for
--   | expr_list
--   | EMPTY
-- @
data SubstrList
  = ExprSubstrList AExpr SubstrListFromFor
  | ExprListSubstrList ExprList
  deriving (Int -> SubstrList -> ShowS
[SubstrList] -> ShowS
SubstrList -> String
(Int -> SubstrList -> ShowS)
-> (SubstrList -> String)
-> ([SubstrList] -> ShowS)
-> Show SubstrList
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SubstrList] -> ShowS
$cshowList :: [SubstrList] -> ShowS
show :: SubstrList -> String
$cshow :: SubstrList -> String
showsPrec :: Int -> SubstrList -> ShowS
$cshowsPrec :: Int -> SubstrList -> ShowS
Show, (forall x. SubstrList -> Rep SubstrList x)
-> (forall x. Rep SubstrList x -> SubstrList) -> Generic SubstrList
forall x. Rep SubstrList x -> SubstrList
forall x. SubstrList -> Rep SubstrList x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SubstrList x -> SubstrList
$cfrom :: forall x. SubstrList -> Rep SubstrList x
Generic, SubstrList -> SubstrList -> Bool
(SubstrList -> SubstrList -> Bool)
-> (SubstrList -> SubstrList -> Bool) -> Eq SubstrList
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SubstrList -> SubstrList -> Bool
$c/= :: SubstrList -> SubstrList -> Bool
== :: SubstrList -> SubstrList -> Bool
$c== :: SubstrList -> SubstrList -> Bool
Eq, Eq SubstrList
Eq SubstrList
-> (SubstrList -> SubstrList -> Ordering)
-> (SubstrList -> SubstrList -> Bool)
-> (SubstrList -> SubstrList -> Bool)
-> (SubstrList -> SubstrList -> Bool)
-> (SubstrList -> SubstrList -> Bool)
-> (SubstrList -> SubstrList -> SubstrList)
-> (SubstrList -> SubstrList -> SubstrList)
-> Ord SubstrList
SubstrList -> SubstrList -> Bool
SubstrList -> SubstrList -> Ordering
SubstrList -> SubstrList -> SubstrList
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: SubstrList -> SubstrList -> SubstrList
$cmin :: SubstrList -> SubstrList -> SubstrList
max :: SubstrList -> SubstrList -> SubstrList
$cmax :: SubstrList -> SubstrList -> SubstrList
>= :: SubstrList -> SubstrList -> Bool
$c>= :: SubstrList -> SubstrList -> Bool
> :: SubstrList -> SubstrList -> Bool
$c> :: SubstrList -> SubstrList -> Bool
<= :: SubstrList -> SubstrList -> Bool
$c<= :: SubstrList -> SubstrList -> Bool
< :: SubstrList -> SubstrList -> Bool
$c< :: SubstrList -> SubstrList -> Bool
compare :: SubstrList -> SubstrList -> Ordering
$ccompare :: SubstrList -> SubstrList -> Ordering
$cp1Ord :: Eq SubstrList
Ord)

-- |
-- ==== References
-- @
--   | a_expr substr_from substr_for
--   | a_expr substr_for substr_from
--   | a_expr substr_from
--   | a_expr substr_for
-- @
data SubstrListFromFor
  = FromForSubstrListFromFor SubstrFrom SubstrFor
  | ForFromSubstrListFromFor SubstrFor SubstrFrom
  | FromSubstrListFromFor SubstrFrom
  | ForSubstrListFromFor SubstrFor
  deriving (Int -> SubstrListFromFor -> ShowS
[SubstrListFromFor] -> ShowS
SubstrListFromFor -> String
(Int -> SubstrListFromFor -> ShowS)
-> (SubstrListFromFor -> String)
-> ([SubstrListFromFor] -> ShowS)
-> Show SubstrListFromFor
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SubstrListFromFor] -> ShowS
$cshowList :: [SubstrListFromFor] -> ShowS
show :: SubstrListFromFor -> String
$cshow :: SubstrListFromFor -> String
showsPrec :: Int -> SubstrListFromFor -> ShowS
$cshowsPrec :: Int -> SubstrListFromFor -> ShowS
Show, (forall x. SubstrListFromFor -> Rep SubstrListFromFor x)
-> (forall x. Rep SubstrListFromFor x -> SubstrListFromFor)
-> Generic SubstrListFromFor
forall x. Rep SubstrListFromFor x -> SubstrListFromFor
forall x. SubstrListFromFor -> Rep SubstrListFromFor x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SubstrListFromFor x -> SubstrListFromFor
$cfrom :: forall x. SubstrListFromFor -> Rep SubstrListFromFor x
Generic, SubstrListFromFor -> SubstrListFromFor -> Bool
(SubstrListFromFor -> SubstrListFromFor -> Bool)
-> (SubstrListFromFor -> SubstrListFromFor -> Bool)
-> Eq SubstrListFromFor
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SubstrListFromFor -> SubstrListFromFor -> Bool
$c/= :: SubstrListFromFor -> SubstrListFromFor -> Bool
== :: SubstrListFromFor -> SubstrListFromFor -> Bool
$c== :: SubstrListFromFor -> SubstrListFromFor -> Bool
Eq, Eq SubstrListFromFor
Eq SubstrListFromFor
-> (SubstrListFromFor -> SubstrListFromFor -> Ordering)
-> (SubstrListFromFor -> SubstrListFromFor -> Bool)
-> (SubstrListFromFor -> SubstrListFromFor -> Bool)
-> (SubstrListFromFor -> SubstrListFromFor -> Bool)
-> (SubstrListFromFor -> SubstrListFromFor -> Bool)
-> (SubstrListFromFor -> SubstrListFromFor -> SubstrListFromFor)
-> (SubstrListFromFor -> SubstrListFromFor -> SubstrListFromFor)
-> Ord SubstrListFromFor
SubstrListFromFor -> SubstrListFromFor -> Bool
SubstrListFromFor -> SubstrListFromFor -> Ordering
SubstrListFromFor -> SubstrListFromFor -> SubstrListFromFor
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: SubstrListFromFor -> SubstrListFromFor -> SubstrListFromFor
$cmin :: SubstrListFromFor -> SubstrListFromFor -> SubstrListFromFor
max :: SubstrListFromFor -> SubstrListFromFor -> SubstrListFromFor
$cmax :: SubstrListFromFor -> SubstrListFromFor -> SubstrListFromFor
>= :: SubstrListFromFor -> SubstrListFromFor -> Bool
$c>= :: SubstrListFromFor -> SubstrListFromFor -> Bool
> :: SubstrListFromFor -> SubstrListFromFor -> Bool
$c> :: SubstrListFromFor -> SubstrListFromFor -> Bool
<= :: SubstrListFromFor -> SubstrListFromFor -> Bool
$c<= :: SubstrListFromFor -> SubstrListFromFor -> Bool
< :: SubstrListFromFor -> SubstrListFromFor -> Bool
$c< :: SubstrListFromFor -> SubstrListFromFor -> Bool
compare :: SubstrListFromFor -> SubstrListFromFor -> Ordering
$ccompare :: SubstrListFromFor -> SubstrListFromFor -> Ordering
$cp1Ord :: Eq SubstrListFromFor
Ord)

-- |
-- ==== References
-- @
-- substr_from:
--   | FROM a_expr
-- @
type SubstrFrom = AExpr

-- |
-- ==== References
-- @
-- substr_for:
--   | FOR a_expr
-- @
type SubstrFor = AExpr

-- |
-- ==== References
-- @
--   | TRIM '(' BOTH trim_list ')'
--   | TRIM '(' LEADING trim_list ')'
--   | TRIM '(' TRAILING trim_list ')'
-- @
data TrimModifier = BothTrimModifier | LeadingTrimModifier | TrailingTrimModifier
  deriving (Int -> TrimModifier -> ShowS
[TrimModifier] -> ShowS
TrimModifier -> String
(Int -> TrimModifier -> ShowS)
-> (TrimModifier -> String)
-> ([TrimModifier] -> ShowS)
-> Show TrimModifier
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TrimModifier] -> ShowS
$cshowList :: [TrimModifier] -> ShowS
show :: TrimModifier -> String
$cshow :: TrimModifier -> String
showsPrec :: Int -> TrimModifier -> ShowS
$cshowsPrec :: Int -> TrimModifier -> ShowS
Show, (forall x. TrimModifier -> Rep TrimModifier x)
-> (forall x. Rep TrimModifier x -> TrimModifier)
-> Generic TrimModifier
forall x. Rep TrimModifier x -> TrimModifier
forall x. TrimModifier -> Rep TrimModifier x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TrimModifier x -> TrimModifier
$cfrom :: forall x. TrimModifier -> Rep TrimModifier x
Generic, TrimModifier -> TrimModifier -> Bool
(TrimModifier -> TrimModifier -> Bool)
-> (TrimModifier -> TrimModifier -> Bool) -> Eq TrimModifier
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TrimModifier -> TrimModifier -> Bool
$c/= :: TrimModifier -> TrimModifier -> Bool
== :: TrimModifier -> TrimModifier -> Bool
$c== :: TrimModifier -> TrimModifier -> Bool
Eq, Eq TrimModifier
Eq TrimModifier
-> (TrimModifier -> TrimModifier -> Ordering)
-> (TrimModifier -> TrimModifier -> Bool)
-> (TrimModifier -> TrimModifier -> Bool)
-> (TrimModifier -> TrimModifier -> Bool)
-> (TrimModifier -> TrimModifier -> Bool)
-> (TrimModifier -> TrimModifier -> TrimModifier)
-> (TrimModifier -> TrimModifier -> TrimModifier)
-> Ord TrimModifier
TrimModifier -> TrimModifier -> Bool
TrimModifier -> TrimModifier -> Ordering
TrimModifier -> TrimModifier -> TrimModifier
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: TrimModifier -> TrimModifier -> TrimModifier
$cmin :: TrimModifier -> TrimModifier -> TrimModifier
max :: TrimModifier -> TrimModifier -> TrimModifier
$cmax :: TrimModifier -> TrimModifier -> TrimModifier
>= :: TrimModifier -> TrimModifier -> Bool
$c>= :: TrimModifier -> TrimModifier -> Bool
> :: TrimModifier -> TrimModifier -> Bool
$c> :: TrimModifier -> TrimModifier -> Bool
<= :: TrimModifier -> TrimModifier -> Bool
$c<= :: TrimModifier -> TrimModifier -> Bool
< :: TrimModifier -> TrimModifier -> Bool
$c< :: TrimModifier -> TrimModifier -> Bool
compare :: TrimModifier -> TrimModifier -> Ordering
$ccompare :: TrimModifier -> TrimModifier -> Ordering
$cp1Ord :: Eq TrimModifier
Ord, Int -> TrimModifier
TrimModifier -> Int
TrimModifier -> [TrimModifier]
TrimModifier -> TrimModifier
TrimModifier -> TrimModifier -> [TrimModifier]
TrimModifier -> TrimModifier -> TrimModifier -> [TrimModifier]
(TrimModifier -> TrimModifier)
-> (TrimModifier -> TrimModifier)
-> (Int -> TrimModifier)
-> (TrimModifier -> Int)
-> (TrimModifier -> [TrimModifier])
-> (TrimModifier -> TrimModifier -> [TrimModifier])
-> (TrimModifier -> TrimModifier -> [TrimModifier])
-> (TrimModifier -> TrimModifier -> TrimModifier -> [TrimModifier])
-> Enum TrimModifier
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: TrimModifier -> TrimModifier -> TrimModifier -> [TrimModifier]
$cenumFromThenTo :: TrimModifier -> TrimModifier -> TrimModifier -> [TrimModifier]
enumFromTo :: TrimModifier -> TrimModifier -> [TrimModifier]
$cenumFromTo :: TrimModifier -> TrimModifier -> [TrimModifier]
enumFromThen :: TrimModifier -> TrimModifier -> [TrimModifier]
$cenumFromThen :: TrimModifier -> TrimModifier -> [TrimModifier]
enumFrom :: TrimModifier -> [TrimModifier]
$cenumFrom :: TrimModifier -> [TrimModifier]
fromEnum :: TrimModifier -> Int
$cfromEnum :: TrimModifier -> Int
toEnum :: Int -> TrimModifier
$ctoEnum :: Int -> TrimModifier
pred :: TrimModifier -> TrimModifier
$cpred :: TrimModifier -> TrimModifier
succ :: TrimModifier -> TrimModifier
$csucc :: TrimModifier -> TrimModifier
Enum, TrimModifier
TrimModifier -> TrimModifier -> Bounded TrimModifier
forall a. a -> a -> Bounded a
maxBound :: TrimModifier
$cmaxBound :: TrimModifier
minBound :: TrimModifier
$cminBound :: TrimModifier
Bounded)

-- |
-- ==== References
-- @
-- trim_list:
--   | a_expr FROM expr_list
--   | FROM expr_list
--   | expr_list
-- @
data TrimList
  = ExprFromExprListTrimList AExpr ExprList
  | FromExprListTrimList ExprList
  | ExprListTrimList ExprList
  deriving (Int -> TrimList -> ShowS
[TrimList] -> ShowS
TrimList -> String
(Int -> TrimList -> ShowS)
-> (TrimList -> String) -> ([TrimList] -> ShowS) -> Show TrimList
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TrimList] -> ShowS
$cshowList :: [TrimList] -> ShowS
show :: TrimList -> String
$cshow :: TrimList -> String
showsPrec :: Int -> TrimList -> ShowS
$cshowsPrec :: Int -> TrimList -> ShowS
Show, (forall x. TrimList -> Rep TrimList x)
-> (forall x. Rep TrimList x -> TrimList) -> Generic TrimList
forall x. Rep TrimList x -> TrimList
forall x. TrimList -> Rep TrimList x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TrimList x -> TrimList
$cfrom :: forall x. TrimList -> Rep TrimList x
Generic, TrimList -> TrimList -> Bool
(TrimList -> TrimList -> Bool)
-> (TrimList -> TrimList -> Bool) -> Eq TrimList
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TrimList -> TrimList -> Bool
$c/= :: TrimList -> TrimList -> Bool
== :: TrimList -> TrimList -> Bool
$c== :: TrimList -> TrimList -> Bool
Eq, Eq TrimList
Eq TrimList
-> (TrimList -> TrimList -> Ordering)
-> (TrimList -> TrimList -> Bool)
-> (TrimList -> TrimList -> Bool)
-> (TrimList -> TrimList -> Bool)
-> (TrimList -> TrimList -> Bool)
-> (TrimList -> TrimList -> TrimList)
-> (TrimList -> TrimList -> TrimList)
-> Ord TrimList
TrimList -> TrimList -> Bool
TrimList -> TrimList -> Ordering
TrimList -> TrimList -> TrimList
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: TrimList -> TrimList -> TrimList
$cmin :: TrimList -> TrimList -> TrimList
max :: TrimList -> TrimList -> TrimList
$cmax :: TrimList -> TrimList -> TrimList
>= :: TrimList -> TrimList -> Bool
$c>= :: TrimList -> TrimList -> Bool
> :: TrimList -> TrimList -> Bool
$c> :: TrimList -> TrimList -> Bool
<= :: TrimList -> TrimList -> Bool
$c<= :: TrimList -> TrimList -> Bool
< :: TrimList -> TrimList -> Bool
$c< :: TrimList -> TrimList -> Bool
compare :: TrimList -> TrimList -> Ordering
$ccompare :: TrimList -> TrimList -> Ordering
$cp1Ord :: Eq TrimList
Ord)

-- |
-- ==== References
-- @
-- case_expr:
--   | CASE case_arg when_clause_list case_default END_P
-- @
data CaseExpr = CaseExpr (Maybe CaseArg) WhenClauseList (Maybe CaseDefault)
  deriving (Int -> CaseExpr -> ShowS
[CaseExpr] -> ShowS
CaseExpr -> String
(Int -> CaseExpr -> ShowS)
-> (CaseExpr -> String) -> ([CaseExpr] -> ShowS) -> Show CaseExpr
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CaseExpr] -> ShowS
$cshowList :: [CaseExpr] -> ShowS
show :: CaseExpr -> String
$cshow :: CaseExpr -> String
showsPrec :: Int -> CaseExpr -> ShowS
$cshowsPrec :: Int -> CaseExpr -> ShowS
Show, (forall x. CaseExpr -> Rep CaseExpr x)
-> (forall x. Rep CaseExpr x -> CaseExpr) -> Generic CaseExpr
forall x. Rep CaseExpr x -> CaseExpr
forall x. CaseExpr -> Rep CaseExpr x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CaseExpr x -> CaseExpr
$cfrom :: forall x. CaseExpr -> Rep CaseExpr x
Generic, CaseExpr -> CaseExpr -> Bool
(CaseExpr -> CaseExpr -> Bool)
-> (CaseExpr -> CaseExpr -> Bool) -> Eq CaseExpr
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CaseExpr -> CaseExpr -> Bool
$c/= :: CaseExpr -> CaseExpr -> Bool
== :: CaseExpr -> CaseExpr -> Bool
$c== :: CaseExpr -> CaseExpr -> Bool
Eq, Eq CaseExpr
Eq CaseExpr
-> (CaseExpr -> CaseExpr -> Ordering)
-> (CaseExpr -> CaseExpr -> Bool)
-> (CaseExpr -> CaseExpr -> Bool)
-> (CaseExpr -> CaseExpr -> Bool)
-> (CaseExpr -> CaseExpr -> Bool)
-> (CaseExpr -> CaseExpr -> CaseExpr)
-> (CaseExpr -> CaseExpr -> CaseExpr)
-> Ord CaseExpr
CaseExpr -> CaseExpr -> Bool
CaseExpr -> CaseExpr -> Ordering
CaseExpr -> CaseExpr -> CaseExpr
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CaseExpr -> CaseExpr -> CaseExpr
$cmin :: CaseExpr -> CaseExpr -> CaseExpr
max :: CaseExpr -> CaseExpr -> CaseExpr
$cmax :: CaseExpr -> CaseExpr -> CaseExpr
>= :: CaseExpr -> CaseExpr -> Bool
$c>= :: CaseExpr -> CaseExpr -> Bool
> :: CaseExpr -> CaseExpr -> Bool
$c> :: CaseExpr -> CaseExpr -> Bool
<= :: CaseExpr -> CaseExpr -> Bool
$c<= :: CaseExpr -> CaseExpr -> Bool
< :: CaseExpr -> CaseExpr -> Bool
$c< :: CaseExpr -> CaseExpr -> Bool
compare :: CaseExpr -> CaseExpr -> Ordering
$ccompare :: CaseExpr -> CaseExpr -> Ordering
$cp1Ord :: Eq CaseExpr
Ord)

-- |
-- ==== References
-- @
-- case_arg:
--   | a_expr
--   | EMPTY
-- @
type CaseArg = AExpr

-- |
-- ==== References
-- @
-- when_clause_list:
--   | when_clause
--   | when_clause_list when_clause
-- @
type WhenClauseList = NonEmpty WhenClause

-- |
-- ==== References
-- @
-- case_default:
--   | ELSE a_expr
--   | EMPTY
-- @
type CaseDefault = AExpr

-- |
-- ==== References
-- @
-- when_clause:
--   |  WHEN a_expr THEN a_expr
-- @
data WhenClause = WhenClause AExpr AExpr
  deriving (Int -> WhenClause -> ShowS
[WhenClause] -> ShowS
WhenClause -> String
(Int -> WhenClause -> ShowS)
-> (WhenClause -> String)
-> ([WhenClause] -> ShowS)
-> Show WhenClause
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WhenClause] -> ShowS
$cshowList :: [WhenClause] -> ShowS
show :: WhenClause -> String
$cshow :: WhenClause -> String
showsPrec :: Int -> WhenClause -> ShowS
$cshowsPrec :: Int -> WhenClause -> ShowS
Show, (forall x. WhenClause -> Rep WhenClause x)
-> (forall x. Rep WhenClause x -> WhenClause) -> Generic WhenClause
forall x. Rep WhenClause x -> WhenClause
forall x. WhenClause -> Rep WhenClause x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep WhenClause x -> WhenClause
$cfrom :: forall x. WhenClause -> Rep WhenClause x
Generic, WhenClause -> WhenClause -> Bool
(WhenClause -> WhenClause -> Bool)
-> (WhenClause -> WhenClause -> Bool) -> Eq WhenClause
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WhenClause -> WhenClause -> Bool
$c/= :: WhenClause -> WhenClause -> Bool
== :: WhenClause -> WhenClause -> Bool
$c== :: WhenClause -> WhenClause -> Bool
Eq, Eq WhenClause
Eq WhenClause
-> (WhenClause -> WhenClause -> Ordering)
-> (WhenClause -> WhenClause -> Bool)
-> (WhenClause -> WhenClause -> Bool)
-> (WhenClause -> WhenClause -> Bool)
-> (WhenClause -> WhenClause -> Bool)
-> (WhenClause -> WhenClause -> WhenClause)
-> (WhenClause -> WhenClause -> WhenClause)
-> Ord WhenClause
WhenClause -> WhenClause -> Bool
WhenClause -> WhenClause -> Ordering
WhenClause -> WhenClause -> WhenClause
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: WhenClause -> WhenClause -> WhenClause
$cmin :: WhenClause -> WhenClause -> WhenClause
max :: WhenClause -> WhenClause -> WhenClause
$cmax :: WhenClause -> WhenClause -> WhenClause
>= :: WhenClause -> WhenClause -> Bool
$c>= :: WhenClause -> WhenClause -> Bool
> :: WhenClause -> WhenClause -> Bool
$c> :: WhenClause -> WhenClause -> Bool
<= :: WhenClause -> WhenClause -> Bool
$c<= :: WhenClause -> WhenClause -> Bool
< :: WhenClause -> WhenClause -> Bool
$c< :: WhenClause -> WhenClause -> Bool
compare :: WhenClause -> WhenClause -> Ordering
$ccompare :: WhenClause -> WhenClause -> Ordering
$cp1Ord :: Eq WhenClause
Ord)

-- |
-- ==== References
-- @
-- func_application:
--   |  func_name '(' ')'
--   |  func_name '(' func_arg_list opt_sort_clause ')'
--   |  func_name '(' VARIADIC func_arg_expr opt_sort_clause ')'
--   |  func_name '(' func_arg_list ',' VARIADIC func_arg_expr opt_sort_clause ')'
--   |  func_name '(' ALL func_arg_list opt_sort_clause ')'
--   |  func_name '(' DISTINCT func_arg_list opt_sort_clause ')'
--   |  func_name '(' '*' ')'
-- @
data FuncApplication = FuncApplication FuncName (Maybe FuncApplicationParams)
  deriving (Int -> FuncApplication -> ShowS
[FuncApplication] -> ShowS
FuncApplication -> String
(Int -> FuncApplication -> ShowS)
-> (FuncApplication -> String)
-> ([FuncApplication] -> ShowS)
-> Show FuncApplication
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FuncApplication] -> ShowS
$cshowList :: [FuncApplication] -> ShowS
show :: FuncApplication -> String
$cshow :: FuncApplication -> String
showsPrec :: Int -> FuncApplication -> ShowS
$cshowsPrec :: Int -> FuncApplication -> ShowS
Show, (forall x. FuncApplication -> Rep FuncApplication x)
-> (forall x. Rep FuncApplication x -> FuncApplication)
-> Generic FuncApplication
forall x. Rep FuncApplication x -> FuncApplication
forall x. FuncApplication -> Rep FuncApplication x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep FuncApplication x -> FuncApplication
$cfrom :: forall x. FuncApplication -> Rep FuncApplication x
Generic, FuncApplication -> FuncApplication -> Bool
(FuncApplication -> FuncApplication -> Bool)
-> (FuncApplication -> FuncApplication -> Bool)
-> Eq FuncApplication
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FuncApplication -> FuncApplication -> Bool
$c/= :: FuncApplication -> FuncApplication -> Bool
== :: FuncApplication -> FuncApplication -> Bool
$c== :: FuncApplication -> FuncApplication -> Bool
Eq, Eq FuncApplication
Eq FuncApplication
-> (FuncApplication -> FuncApplication -> Ordering)
-> (FuncApplication -> FuncApplication -> Bool)
-> (FuncApplication -> FuncApplication -> Bool)
-> (FuncApplication -> FuncApplication -> Bool)
-> (FuncApplication -> FuncApplication -> Bool)
-> (FuncApplication -> FuncApplication -> FuncApplication)
-> (FuncApplication -> FuncApplication -> FuncApplication)
-> Ord FuncApplication
FuncApplication -> FuncApplication -> Bool
FuncApplication -> FuncApplication -> Ordering
FuncApplication -> FuncApplication -> FuncApplication
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: FuncApplication -> FuncApplication -> FuncApplication
$cmin :: FuncApplication -> FuncApplication -> FuncApplication
max :: FuncApplication -> FuncApplication -> FuncApplication
$cmax :: FuncApplication -> FuncApplication -> FuncApplication
>= :: FuncApplication -> FuncApplication -> Bool
$c>= :: FuncApplication -> FuncApplication -> Bool
> :: FuncApplication -> FuncApplication -> Bool
$c> :: FuncApplication -> FuncApplication -> Bool
<= :: FuncApplication -> FuncApplication -> Bool
$c<= :: FuncApplication -> FuncApplication -> Bool
< :: FuncApplication -> FuncApplication -> Bool
$c< :: FuncApplication -> FuncApplication -> Bool
compare :: FuncApplication -> FuncApplication -> Ordering
$ccompare :: FuncApplication -> FuncApplication -> Ordering
$cp1Ord :: Eq FuncApplication
Ord)

-- |
-- ==== References
-- @
-- func_application:
--   |  func_name '(' ')'
--   |  func_name '(' func_arg_list opt_sort_clause ')'
--   |  func_name '(' VARIADIC func_arg_expr opt_sort_clause ')'
--   |  func_name '(' func_arg_list ',' VARIADIC func_arg_expr opt_sort_clause ')'
--   |  func_name '(' ALL func_arg_list opt_sort_clause ')'
--   |  func_name '(' DISTINCT func_arg_list opt_sort_clause ')'
--   |  func_name '(' '*' ')'
-- @
data FuncApplicationParams
  = NormalFuncApplicationParams (Maybe Bool) (NonEmpty FuncArgExpr) (Maybe SortClause)
  | VariadicFuncApplicationParams (Maybe (NonEmpty FuncArgExpr)) FuncArgExpr (Maybe SortClause)
  | StarFuncApplicationParams
  deriving (Int -> FuncApplicationParams -> ShowS
[FuncApplicationParams] -> ShowS
FuncApplicationParams -> String
(Int -> FuncApplicationParams -> ShowS)
-> (FuncApplicationParams -> String)
-> ([FuncApplicationParams] -> ShowS)
-> Show FuncApplicationParams
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FuncApplicationParams] -> ShowS
$cshowList :: [FuncApplicationParams] -> ShowS
show :: FuncApplicationParams -> String
$cshow :: FuncApplicationParams -> String
showsPrec :: Int -> FuncApplicationParams -> ShowS
$cshowsPrec :: Int -> FuncApplicationParams -> ShowS
Show, (forall x. FuncApplicationParams -> Rep FuncApplicationParams x)
-> (forall x. Rep FuncApplicationParams x -> FuncApplicationParams)
-> Generic FuncApplicationParams
forall x. Rep FuncApplicationParams x -> FuncApplicationParams
forall x. FuncApplicationParams -> Rep FuncApplicationParams x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep FuncApplicationParams x -> FuncApplicationParams
$cfrom :: forall x. FuncApplicationParams -> Rep FuncApplicationParams x
Generic, FuncApplicationParams -> FuncApplicationParams -> Bool
(FuncApplicationParams -> FuncApplicationParams -> Bool)
-> (FuncApplicationParams -> FuncApplicationParams -> Bool)
-> Eq FuncApplicationParams
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FuncApplicationParams -> FuncApplicationParams -> Bool
$c/= :: FuncApplicationParams -> FuncApplicationParams -> Bool
== :: FuncApplicationParams -> FuncApplicationParams -> Bool
$c== :: FuncApplicationParams -> FuncApplicationParams -> Bool
Eq, Eq FuncApplicationParams
Eq FuncApplicationParams
-> (FuncApplicationParams -> FuncApplicationParams -> Ordering)
-> (FuncApplicationParams -> FuncApplicationParams -> Bool)
-> (FuncApplicationParams -> FuncApplicationParams -> Bool)
-> (FuncApplicationParams -> FuncApplicationParams -> Bool)
-> (FuncApplicationParams -> FuncApplicationParams -> Bool)
-> (FuncApplicationParams
    -> FuncApplicationParams -> FuncApplicationParams)
-> (FuncApplicationParams
    -> FuncApplicationParams -> FuncApplicationParams)
-> Ord FuncApplicationParams
FuncApplicationParams -> FuncApplicationParams -> Bool
FuncApplicationParams -> FuncApplicationParams -> Ordering
FuncApplicationParams
-> FuncApplicationParams -> FuncApplicationParams
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: FuncApplicationParams
-> FuncApplicationParams -> FuncApplicationParams
$cmin :: FuncApplicationParams
-> FuncApplicationParams -> FuncApplicationParams
max :: FuncApplicationParams
-> FuncApplicationParams -> FuncApplicationParams
$cmax :: FuncApplicationParams
-> FuncApplicationParams -> FuncApplicationParams
>= :: FuncApplicationParams -> FuncApplicationParams -> Bool
$c>= :: FuncApplicationParams -> FuncApplicationParams -> Bool
> :: FuncApplicationParams -> FuncApplicationParams -> Bool
$c> :: FuncApplicationParams -> FuncApplicationParams -> Bool
<= :: FuncApplicationParams -> FuncApplicationParams -> Bool
$c<= :: FuncApplicationParams -> FuncApplicationParams -> Bool
< :: FuncApplicationParams -> FuncApplicationParams -> Bool
$c< :: FuncApplicationParams -> FuncApplicationParams -> Bool
compare :: FuncApplicationParams -> FuncApplicationParams -> Ordering
$ccompare :: FuncApplicationParams -> FuncApplicationParams -> Ordering
$cp1Ord :: Eq FuncApplicationParams
Ord)

data FuncArgExpr
  = ExprFuncArgExpr AExpr
  | ColonEqualsFuncArgExpr Ident AExpr
  | EqualsGreaterFuncArgExpr Ident AExpr
  deriving (Int -> FuncArgExpr -> ShowS
[FuncArgExpr] -> ShowS
FuncArgExpr -> String
(Int -> FuncArgExpr -> ShowS)
-> (FuncArgExpr -> String)
-> ([FuncArgExpr] -> ShowS)
-> Show FuncArgExpr
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FuncArgExpr] -> ShowS
$cshowList :: [FuncArgExpr] -> ShowS
show :: FuncArgExpr -> String
$cshow :: FuncArgExpr -> String
showsPrec :: Int -> FuncArgExpr -> ShowS
$cshowsPrec :: Int -> FuncArgExpr -> ShowS
Show, (forall x. FuncArgExpr -> Rep FuncArgExpr x)
-> (forall x. Rep FuncArgExpr x -> FuncArgExpr)
-> Generic FuncArgExpr
forall x. Rep FuncArgExpr x -> FuncArgExpr
forall x. FuncArgExpr -> Rep FuncArgExpr x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep FuncArgExpr x -> FuncArgExpr
$cfrom :: forall x. FuncArgExpr -> Rep FuncArgExpr x
Generic, FuncArgExpr -> FuncArgExpr -> Bool
(FuncArgExpr -> FuncArgExpr -> Bool)
-> (FuncArgExpr -> FuncArgExpr -> Bool) -> Eq FuncArgExpr
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FuncArgExpr -> FuncArgExpr -> Bool
$c/= :: FuncArgExpr -> FuncArgExpr -> Bool
== :: FuncArgExpr -> FuncArgExpr -> Bool
$c== :: FuncArgExpr -> FuncArgExpr -> Bool
Eq, Eq FuncArgExpr
Eq FuncArgExpr
-> (FuncArgExpr -> FuncArgExpr -> Ordering)
-> (FuncArgExpr -> FuncArgExpr -> Bool)
-> (FuncArgExpr -> FuncArgExpr -> Bool)
-> (FuncArgExpr -> FuncArgExpr -> Bool)
-> (FuncArgExpr -> FuncArgExpr -> Bool)
-> (FuncArgExpr -> FuncArgExpr -> FuncArgExpr)
-> (FuncArgExpr -> FuncArgExpr -> FuncArgExpr)
-> Ord FuncArgExpr
FuncArgExpr -> FuncArgExpr -> Bool
FuncArgExpr -> FuncArgExpr -> Ordering
FuncArgExpr -> FuncArgExpr -> FuncArgExpr
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: FuncArgExpr -> FuncArgExpr -> FuncArgExpr
$cmin :: FuncArgExpr -> FuncArgExpr -> FuncArgExpr
max :: FuncArgExpr -> FuncArgExpr -> FuncArgExpr
$cmax :: FuncArgExpr -> FuncArgExpr -> FuncArgExpr
>= :: FuncArgExpr -> FuncArgExpr -> Bool
$c>= :: FuncArgExpr -> FuncArgExpr -> Bool
> :: FuncArgExpr -> FuncArgExpr -> Bool
$c> :: FuncArgExpr -> FuncArgExpr -> Bool
<= :: FuncArgExpr -> FuncArgExpr -> Bool
$c<= :: FuncArgExpr -> FuncArgExpr -> Bool
< :: FuncArgExpr -> FuncArgExpr -> Bool
$c< :: FuncArgExpr -> FuncArgExpr -> Bool
compare :: FuncArgExpr -> FuncArgExpr -> Ordering
$ccompare :: FuncArgExpr -> FuncArgExpr -> Ordering
$cp1Ord :: Eq FuncArgExpr
Ord)

-- * Constants

type Sconst = Text

type Iconst = Int64

type Fconst = Double

type Bconst = Text

type Xconst = Text

-- |
-- 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
data AexprConst
  = IAexprConst Iconst
  | FAexprConst Fconst
  | SAexprConst Sconst
  | BAexprConst Bconst
  | XAexprConst Xconst
  | FuncAexprConst FuncName (Maybe FuncConstArgs) Sconst
  | ConstTypenameAexprConst ConstTypename Sconst
  | StringIntervalAexprConst Sconst (Maybe Interval)
  | IntIntervalAexprConst Iconst Sconst
  | BoolAexprConst Bool
  | NullAexprConst
  deriving (Int -> AexprConst -> ShowS
[AexprConst] -> ShowS
AexprConst -> String
(Int -> AexprConst -> ShowS)
-> (AexprConst -> String)
-> ([AexprConst] -> ShowS)
-> Show AexprConst
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AexprConst] -> ShowS
$cshowList :: [AexprConst] -> ShowS
show :: AexprConst -> String
$cshow :: AexprConst -> String
showsPrec :: Int -> AexprConst -> ShowS
$cshowsPrec :: Int -> AexprConst -> ShowS
Show, (forall x. AexprConst -> Rep AexprConst x)
-> (forall x. Rep AexprConst x -> AexprConst) -> Generic AexprConst
forall x. Rep AexprConst x -> AexprConst
forall x. AexprConst -> Rep AexprConst x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AexprConst x -> AexprConst
$cfrom :: forall x. AexprConst -> Rep AexprConst x
Generic, AexprConst -> AexprConst -> Bool
(AexprConst -> AexprConst -> Bool)
-> (AexprConst -> AexprConst -> Bool) -> Eq AexprConst
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AexprConst -> AexprConst -> Bool
$c/= :: AexprConst -> AexprConst -> Bool
== :: AexprConst -> AexprConst -> Bool
$c== :: AexprConst -> AexprConst -> Bool
Eq, Eq AexprConst
Eq AexprConst
-> (AexprConst -> AexprConst -> Ordering)
-> (AexprConst -> AexprConst -> Bool)
-> (AexprConst -> AexprConst -> Bool)
-> (AexprConst -> AexprConst -> Bool)
-> (AexprConst -> AexprConst -> Bool)
-> (AexprConst -> AexprConst -> AexprConst)
-> (AexprConst -> AexprConst -> AexprConst)
-> Ord AexprConst
AexprConst -> AexprConst -> Bool
AexprConst -> AexprConst -> Ordering
AexprConst -> AexprConst -> AexprConst
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: AexprConst -> AexprConst -> AexprConst
$cmin :: AexprConst -> AexprConst -> AexprConst
max :: AexprConst -> AexprConst -> AexprConst
$cmax :: AexprConst -> AexprConst -> AexprConst
>= :: AexprConst -> AexprConst -> Bool
$c>= :: AexprConst -> AexprConst -> Bool
> :: AexprConst -> AexprConst -> Bool
$c> :: AexprConst -> AexprConst -> Bool
<= :: AexprConst -> AexprConst -> Bool
$c<= :: AexprConst -> AexprConst -> Bool
< :: AexprConst -> AexprConst -> Bool
$c< :: AexprConst -> AexprConst -> Bool
compare :: AexprConst -> AexprConst -> Ordering
$ccompare :: AexprConst -> AexprConst -> Ordering
$cp1Ord :: Eq AexprConst
Ord)

-- |
-- ==== References
-- @
--   |  func_name '(' func_arg_list opt_sort_clause ')' Sconst
-- @
data FuncConstArgs = FuncConstArgs (NonEmpty FuncArgExpr) (Maybe SortClause)
  deriving (Int -> FuncConstArgs -> ShowS
[FuncConstArgs] -> ShowS
FuncConstArgs -> String
(Int -> FuncConstArgs -> ShowS)
-> (FuncConstArgs -> String)
-> ([FuncConstArgs] -> ShowS)
-> Show FuncConstArgs
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FuncConstArgs] -> ShowS
$cshowList :: [FuncConstArgs] -> ShowS
show :: FuncConstArgs -> String
$cshow :: FuncConstArgs -> String
showsPrec :: Int -> FuncConstArgs -> ShowS
$cshowsPrec :: Int -> FuncConstArgs -> ShowS
Show, (forall x. FuncConstArgs -> Rep FuncConstArgs x)
-> (forall x. Rep FuncConstArgs x -> FuncConstArgs)
-> Generic FuncConstArgs
forall x. Rep FuncConstArgs x -> FuncConstArgs
forall x. FuncConstArgs -> Rep FuncConstArgs x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep FuncConstArgs x -> FuncConstArgs
$cfrom :: forall x. FuncConstArgs -> Rep FuncConstArgs x
Generic, FuncConstArgs -> FuncConstArgs -> Bool
(FuncConstArgs -> FuncConstArgs -> Bool)
-> (FuncConstArgs -> FuncConstArgs -> Bool) -> Eq FuncConstArgs
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FuncConstArgs -> FuncConstArgs -> Bool
$c/= :: FuncConstArgs -> FuncConstArgs -> Bool
== :: FuncConstArgs -> FuncConstArgs -> Bool
$c== :: FuncConstArgs -> FuncConstArgs -> Bool
Eq, Eq FuncConstArgs
Eq FuncConstArgs
-> (FuncConstArgs -> FuncConstArgs -> Ordering)
-> (FuncConstArgs -> FuncConstArgs -> Bool)
-> (FuncConstArgs -> FuncConstArgs -> Bool)
-> (FuncConstArgs -> FuncConstArgs -> Bool)
-> (FuncConstArgs -> FuncConstArgs -> Bool)
-> (FuncConstArgs -> FuncConstArgs -> FuncConstArgs)
-> (FuncConstArgs -> FuncConstArgs -> FuncConstArgs)
-> Ord FuncConstArgs
FuncConstArgs -> FuncConstArgs -> Bool
FuncConstArgs -> FuncConstArgs -> Ordering
FuncConstArgs -> FuncConstArgs -> FuncConstArgs
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: FuncConstArgs -> FuncConstArgs -> FuncConstArgs
$cmin :: FuncConstArgs -> FuncConstArgs -> FuncConstArgs
max :: FuncConstArgs -> FuncConstArgs -> FuncConstArgs
$cmax :: FuncConstArgs -> FuncConstArgs -> FuncConstArgs
>= :: FuncConstArgs -> FuncConstArgs -> Bool
$c>= :: FuncConstArgs -> FuncConstArgs -> Bool
> :: FuncConstArgs -> FuncConstArgs -> Bool
$c> :: FuncConstArgs -> FuncConstArgs -> Bool
<= :: FuncConstArgs -> FuncConstArgs -> Bool
$c<= :: FuncConstArgs -> FuncConstArgs -> Bool
< :: FuncConstArgs -> FuncConstArgs -> Bool
$c< :: FuncConstArgs -> FuncConstArgs -> Bool
compare :: FuncConstArgs -> FuncConstArgs -> Ordering
$ccompare :: FuncConstArgs -> FuncConstArgs -> Ordering
$cp1Ord :: Eq FuncConstArgs
Ord)

-- |
-- ==== References
-- @
-- ConstTypename:
--   | Numeric
--   | ConstBit
--   | ConstCharacter
--   | ConstDatetime
-- @
data ConstTypename
  = NumericConstTypename Numeric
  | ConstBitConstTypename ConstBit
  | ConstCharacterConstTypename ConstCharacter
  | ConstDatetimeConstTypename ConstDatetime
  deriving (Int -> ConstTypename -> ShowS
[ConstTypename] -> ShowS
ConstTypename -> String
(Int -> ConstTypename -> ShowS)
-> (ConstTypename -> String)
-> ([ConstTypename] -> ShowS)
-> Show ConstTypename
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ConstTypename] -> ShowS
$cshowList :: [ConstTypename] -> ShowS
show :: ConstTypename -> String
$cshow :: ConstTypename -> String
showsPrec :: Int -> ConstTypename -> ShowS
$cshowsPrec :: Int -> ConstTypename -> ShowS
Show, (forall x. ConstTypename -> Rep ConstTypename x)
-> (forall x. Rep ConstTypename x -> ConstTypename)
-> Generic ConstTypename
forall x. Rep ConstTypename x -> ConstTypename
forall x. ConstTypename -> Rep ConstTypename x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ConstTypename x -> ConstTypename
$cfrom :: forall x. ConstTypename -> Rep ConstTypename x
Generic, ConstTypename -> ConstTypename -> Bool
(ConstTypename -> ConstTypename -> Bool)
-> (ConstTypename -> ConstTypename -> Bool) -> Eq ConstTypename
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ConstTypename -> ConstTypename -> Bool
$c/= :: ConstTypename -> ConstTypename -> Bool
== :: ConstTypename -> ConstTypename -> Bool
$c== :: ConstTypename -> ConstTypename -> Bool
Eq, Eq ConstTypename
Eq ConstTypename
-> (ConstTypename -> ConstTypename -> Ordering)
-> (ConstTypename -> ConstTypename -> Bool)
-> (ConstTypename -> ConstTypename -> Bool)
-> (ConstTypename -> ConstTypename -> Bool)
-> (ConstTypename -> ConstTypename -> Bool)
-> (ConstTypename -> ConstTypename -> ConstTypename)
-> (ConstTypename -> ConstTypename -> ConstTypename)
-> Ord ConstTypename
ConstTypename -> ConstTypename -> Bool
ConstTypename -> ConstTypename -> Ordering
ConstTypename -> ConstTypename -> ConstTypename
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ConstTypename -> ConstTypename -> ConstTypename
$cmin :: ConstTypename -> ConstTypename -> ConstTypename
max :: ConstTypename -> ConstTypename -> ConstTypename
$cmax :: ConstTypename -> ConstTypename -> ConstTypename
>= :: ConstTypename -> ConstTypename -> Bool
$c>= :: ConstTypename -> ConstTypename -> Bool
> :: ConstTypename -> ConstTypename -> Bool
$c> :: ConstTypename -> ConstTypename -> Bool
<= :: ConstTypename -> ConstTypename -> Bool
$c<= :: ConstTypename -> ConstTypename -> Bool
< :: ConstTypename -> ConstTypename -> Bool
$c< :: ConstTypename -> ConstTypename -> Bool
compare :: ConstTypename -> ConstTypename -> Ordering
$ccompare :: ConstTypename -> ConstTypename -> Ordering
$cp1Ord :: Eq ConstTypename
Ord)

-- |
-- ==== References
-- @
-- Numeric:
--   | INT_P
--   | INTEGER
--   | SMALLINT
--   | BIGINT
--   | REAL
--   | FLOAT_P opt_float
--   | DOUBLE_P PRECISION
--   | DECIMAL_P opt_type_modifiers
--   | DEC opt_type_modifiers
--   | NUMERIC opt_type_modifiers
--   | BOOLEAN_P
-- opt_float:
--   | '(' Iconst ')'
--   | EMPTY
-- opt_type_modifiers:
--   | '(' expr_list ')'
--   | EMPTY
-- @
data Numeric
  = IntNumeric
  | IntegerNumeric
  | SmallintNumeric
  | BigintNumeric
  | RealNumeric
  | FloatNumeric (Maybe Int64)
  | DoublePrecisionNumeric
  | DecimalNumeric (Maybe TypeModifiers)
  | DecNumeric (Maybe TypeModifiers)
  | NumericNumeric (Maybe TypeModifiers)
  | BooleanNumeric
  deriving (Int -> Numeric -> ShowS
[Numeric] -> ShowS
Numeric -> String
(Int -> Numeric -> ShowS)
-> (Numeric -> String) -> ([Numeric] -> ShowS) -> Show Numeric
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Numeric] -> ShowS
$cshowList :: [Numeric] -> ShowS
show :: Numeric -> String
$cshow :: Numeric -> String
showsPrec :: Int -> Numeric -> ShowS
$cshowsPrec :: Int -> Numeric -> ShowS
Show, (forall x. Numeric -> Rep Numeric x)
-> (forall x. Rep Numeric x -> Numeric) -> Generic Numeric
forall x. Rep Numeric x -> Numeric
forall x. Numeric -> Rep Numeric x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Numeric x -> Numeric
$cfrom :: forall x. Numeric -> Rep Numeric x
Generic, Numeric -> Numeric -> Bool
(Numeric -> Numeric -> Bool)
-> (Numeric -> Numeric -> Bool) -> Eq Numeric
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Numeric -> Numeric -> Bool
$c/= :: Numeric -> Numeric -> Bool
== :: Numeric -> Numeric -> Bool
$c== :: Numeric -> Numeric -> Bool
Eq, Eq Numeric
Eq Numeric
-> (Numeric -> Numeric -> Ordering)
-> (Numeric -> Numeric -> Bool)
-> (Numeric -> Numeric -> Bool)
-> (Numeric -> Numeric -> Bool)
-> (Numeric -> Numeric -> Bool)
-> (Numeric -> Numeric -> Numeric)
-> (Numeric -> Numeric -> Numeric)
-> Ord Numeric
Numeric -> Numeric -> Bool
Numeric -> Numeric -> Ordering
Numeric -> Numeric -> Numeric
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Numeric -> Numeric -> Numeric
$cmin :: Numeric -> Numeric -> Numeric
max :: Numeric -> Numeric -> Numeric
$cmax :: Numeric -> Numeric -> Numeric
>= :: Numeric -> Numeric -> Bool
$c>= :: Numeric -> Numeric -> Bool
> :: Numeric -> Numeric -> Bool
$c> :: Numeric -> Numeric -> Bool
<= :: Numeric -> Numeric -> Bool
$c<= :: Numeric -> Numeric -> Bool
< :: Numeric -> Numeric -> Bool
$c< :: Numeric -> Numeric -> Bool
compare :: Numeric -> Numeric -> Ordering
$ccompare :: Numeric -> Numeric -> Ordering
$cp1Ord :: Eq Numeric
Ord)

-- |
-- ==== References
-- @
-- Bit:
--   | BitWithLength
--   | BitWithoutLength
-- ConstBit:
--   | BitWithLength
--   | BitWithoutLength
-- BitWithLength:
--   | BIT opt_varying '(' expr_list ')'
-- BitWithoutLength:
--   | BIT opt_varying
-- @
data Bit = Bit OptVarying (Maybe ExprList)
  deriving (Int -> Bit -> ShowS
[Bit] -> ShowS
Bit -> String
(Int -> Bit -> ShowS)
-> (Bit -> String) -> ([Bit] -> ShowS) -> Show Bit
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Bit] -> ShowS
$cshowList :: [Bit] -> ShowS
show :: Bit -> String
$cshow :: Bit -> String
showsPrec :: Int -> Bit -> ShowS
$cshowsPrec :: Int -> Bit -> ShowS
Show, (forall x. Bit -> Rep Bit x)
-> (forall x. Rep Bit x -> Bit) -> Generic Bit
forall x. Rep Bit x -> Bit
forall x. Bit -> Rep Bit x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Bit x -> Bit
$cfrom :: forall x. Bit -> Rep Bit x
Generic, Bit -> Bit -> Bool
(Bit -> Bit -> Bool) -> (Bit -> Bit -> Bool) -> Eq Bit
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Bit -> Bit -> Bool
$c/= :: Bit -> Bit -> Bool
== :: Bit -> Bit -> Bool
$c== :: Bit -> Bit -> Bool
Eq, Eq Bit
Eq Bit
-> (Bit -> Bit -> Ordering)
-> (Bit -> Bit -> Bool)
-> (Bit -> Bit -> Bool)
-> (Bit -> Bit -> Bool)
-> (Bit -> Bit -> Bool)
-> (Bit -> Bit -> Bit)
-> (Bit -> Bit -> Bit)
-> Ord Bit
Bit -> Bit -> Bool
Bit -> Bit -> Ordering
Bit -> Bit -> Bit
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Bit -> Bit -> Bit
$cmin :: Bit -> Bit -> Bit
max :: Bit -> Bit -> Bit
$cmax :: Bit -> Bit -> Bit
>= :: Bit -> Bit -> Bool
$c>= :: Bit -> Bit -> Bool
> :: Bit -> Bit -> Bool
$c> :: Bit -> Bit -> Bool
<= :: Bit -> Bit -> Bool
$c<= :: Bit -> Bit -> Bool
< :: Bit -> Bit -> Bool
$c< :: Bit -> Bit -> Bool
compare :: Bit -> Bit -> Ordering
$ccompare :: Bit -> Bit -> Ordering
$cp1Ord :: Eq Bit
Ord)

type ConstBit = Bit

-- |
-- ==== References
-- @
-- opt_varying:
--   | VARYING
--   | EMPTY
-- @
type OptVarying = Bool

-- |
-- ==== References
-- @
-- Character:
--   | CharacterWithLength
--   | CharacterWithoutLength
-- ConstCharacter:
--   | CharacterWithLength
--   | CharacterWithoutLength
-- CharacterWithLength:
--   | character '(' Iconst ')'
-- CharacterWithoutLength:
--   | character
-- @
data ConstCharacter = ConstCharacter Character (Maybe Int64)
  deriving (Int -> ConstCharacter -> ShowS
[ConstCharacter] -> ShowS
ConstCharacter -> String
(Int -> ConstCharacter -> ShowS)
-> (ConstCharacter -> String)
-> ([ConstCharacter] -> ShowS)
-> Show ConstCharacter
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ConstCharacter] -> ShowS
$cshowList :: [ConstCharacter] -> ShowS
show :: ConstCharacter -> String
$cshow :: ConstCharacter -> String
showsPrec :: Int -> ConstCharacter -> ShowS
$cshowsPrec :: Int -> ConstCharacter -> ShowS
Show, (forall x. ConstCharacter -> Rep ConstCharacter x)
-> (forall x. Rep ConstCharacter x -> ConstCharacter)
-> Generic ConstCharacter
forall x. Rep ConstCharacter x -> ConstCharacter
forall x. ConstCharacter -> Rep ConstCharacter x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ConstCharacter x -> ConstCharacter
$cfrom :: forall x. ConstCharacter -> Rep ConstCharacter x
Generic, ConstCharacter -> ConstCharacter -> Bool
(ConstCharacter -> ConstCharacter -> Bool)
-> (ConstCharacter -> ConstCharacter -> Bool) -> Eq ConstCharacter
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ConstCharacter -> ConstCharacter -> Bool
$c/= :: ConstCharacter -> ConstCharacter -> Bool
== :: ConstCharacter -> ConstCharacter -> Bool
$c== :: ConstCharacter -> ConstCharacter -> Bool
Eq, Eq ConstCharacter
Eq ConstCharacter
-> (ConstCharacter -> ConstCharacter -> Ordering)
-> (ConstCharacter -> ConstCharacter -> Bool)
-> (ConstCharacter -> ConstCharacter -> Bool)
-> (ConstCharacter -> ConstCharacter -> Bool)
-> (ConstCharacter -> ConstCharacter -> Bool)
-> (ConstCharacter -> ConstCharacter -> ConstCharacter)
-> (ConstCharacter -> ConstCharacter -> ConstCharacter)
-> Ord ConstCharacter
ConstCharacter -> ConstCharacter -> Bool
ConstCharacter -> ConstCharacter -> Ordering
ConstCharacter -> ConstCharacter -> ConstCharacter
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ConstCharacter -> ConstCharacter -> ConstCharacter
$cmin :: ConstCharacter -> ConstCharacter -> ConstCharacter
max :: ConstCharacter -> ConstCharacter -> ConstCharacter
$cmax :: ConstCharacter -> ConstCharacter -> ConstCharacter
>= :: ConstCharacter -> ConstCharacter -> Bool
$c>= :: ConstCharacter -> ConstCharacter -> Bool
> :: ConstCharacter -> ConstCharacter -> Bool
$c> :: ConstCharacter -> ConstCharacter -> Bool
<= :: ConstCharacter -> ConstCharacter -> Bool
$c<= :: ConstCharacter -> ConstCharacter -> Bool
< :: ConstCharacter -> ConstCharacter -> Bool
$c< :: ConstCharacter -> ConstCharacter -> Bool
compare :: ConstCharacter -> ConstCharacter -> Ordering
$ccompare :: ConstCharacter -> ConstCharacter -> Ordering
$cp1Ord :: Eq ConstCharacter
Ord)

-- |
-- ==== References
-- @
-- character:
--   | CHARACTER opt_varying
--   | CHAR_P opt_varying
--   | VARCHAR
--   | NATIONAL CHARACTER opt_varying
--   | NATIONAL CHAR_P opt_varying
--   | NCHAR opt_varying
-- @
data Character
  = CharacterCharacter OptVarying
  | CharCharacter OptVarying
  | VarcharCharacter
  | NationalCharacterCharacter OptVarying
  | NationalCharCharacter OptVarying
  | NcharCharacter OptVarying
  deriving (Int -> Character -> ShowS
[Character] -> ShowS
Character -> String
(Int -> Character -> ShowS)
-> (Character -> String)
-> ([Character] -> ShowS)
-> Show Character
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Character] -> ShowS
$cshowList :: [Character] -> ShowS
show :: Character -> String
$cshow :: Character -> String
showsPrec :: Int -> Character -> ShowS
$cshowsPrec :: Int -> Character -> ShowS
Show, (forall x. Character -> Rep Character x)
-> (forall x. Rep Character x -> Character) -> Generic Character
forall x. Rep Character x -> Character
forall x. Character -> Rep Character x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Character x -> Character
$cfrom :: forall x. Character -> Rep Character x
Generic, Character -> Character -> Bool
(Character -> Character -> Bool)
-> (Character -> Character -> Bool) -> Eq Character
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Character -> Character -> Bool
$c/= :: Character -> Character -> Bool
== :: Character -> Character -> Bool
$c== :: Character -> Character -> Bool
Eq, Eq Character
Eq Character
-> (Character -> Character -> Ordering)
-> (Character -> Character -> Bool)
-> (Character -> Character -> Bool)
-> (Character -> Character -> Bool)
-> (Character -> Character -> Bool)
-> (Character -> Character -> Character)
-> (Character -> Character -> Character)
-> Ord Character
Character -> Character -> Bool
Character -> Character -> Ordering
Character -> Character -> Character
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Character -> Character -> Character
$cmin :: Character -> Character -> Character
max :: Character -> Character -> Character
$cmax :: Character -> Character -> Character
>= :: Character -> Character -> Bool
$c>= :: Character -> Character -> Bool
> :: Character -> Character -> Bool
$c> :: Character -> Character -> Bool
<= :: Character -> Character -> Bool
$c<= :: Character -> Character -> Bool
< :: Character -> Character -> Bool
$c< :: Character -> Character -> Bool
compare :: Character -> Character -> Ordering
$ccompare :: Character -> Character -> Ordering
$cp1Ord :: Eq Character
Ord)

-- |
-- ==== References
-- @
-- ConstDatetime:
--   | TIMESTAMP '(' Iconst ')' opt_timezone
--   | TIMESTAMP opt_timezone
--   | TIME '(' Iconst ')' opt_timezone
--   | TIME opt_timezone
-- @
data ConstDatetime
  = TimestampConstDatetime (Maybe Int64) (Maybe Timezone)
  | TimeConstDatetime (Maybe Int64) (Maybe Timezone)
  deriving (Int -> ConstDatetime -> ShowS
[ConstDatetime] -> ShowS
ConstDatetime -> String
(Int -> ConstDatetime -> ShowS)
-> (ConstDatetime -> String)
-> ([ConstDatetime] -> ShowS)
-> Show ConstDatetime
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ConstDatetime] -> ShowS
$cshowList :: [ConstDatetime] -> ShowS
show :: ConstDatetime -> String
$cshow :: ConstDatetime -> String
showsPrec :: Int -> ConstDatetime -> ShowS
$cshowsPrec :: Int -> ConstDatetime -> ShowS
Show, (forall x. ConstDatetime -> Rep ConstDatetime x)
-> (forall x. Rep ConstDatetime x -> ConstDatetime)
-> Generic ConstDatetime
forall x. Rep ConstDatetime x -> ConstDatetime
forall x. ConstDatetime -> Rep ConstDatetime x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ConstDatetime x -> ConstDatetime
$cfrom :: forall x. ConstDatetime -> Rep ConstDatetime x
Generic, ConstDatetime -> ConstDatetime -> Bool
(ConstDatetime -> ConstDatetime -> Bool)
-> (ConstDatetime -> ConstDatetime -> Bool) -> Eq ConstDatetime
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ConstDatetime -> ConstDatetime -> Bool
$c/= :: ConstDatetime -> ConstDatetime -> Bool
== :: ConstDatetime -> ConstDatetime -> Bool
$c== :: ConstDatetime -> ConstDatetime -> Bool
Eq, Eq ConstDatetime
Eq ConstDatetime
-> (ConstDatetime -> ConstDatetime -> Ordering)
-> (ConstDatetime -> ConstDatetime -> Bool)
-> (ConstDatetime -> ConstDatetime -> Bool)
-> (ConstDatetime -> ConstDatetime -> Bool)
-> (ConstDatetime -> ConstDatetime -> Bool)
-> (ConstDatetime -> ConstDatetime -> ConstDatetime)
-> (ConstDatetime -> ConstDatetime -> ConstDatetime)
-> Ord ConstDatetime
ConstDatetime -> ConstDatetime -> Bool
ConstDatetime -> ConstDatetime -> Ordering
ConstDatetime -> ConstDatetime -> ConstDatetime
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ConstDatetime -> ConstDatetime -> ConstDatetime
$cmin :: ConstDatetime -> ConstDatetime -> ConstDatetime
max :: ConstDatetime -> ConstDatetime -> ConstDatetime
$cmax :: ConstDatetime -> ConstDatetime -> ConstDatetime
>= :: ConstDatetime -> ConstDatetime -> Bool
$c>= :: ConstDatetime -> ConstDatetime -> Bool
> :: ConstDatetime -> ConstDatetime -> Bool
$c> :: ConstDatetime -> ConstDatetime -> Bool
<= :: ConstDatetime -> ConstDatetime -> Bool
$c<= :: ConstDatetime -> ConstDatetime -> Bool
< :: ConstDatetime -> ConstDatetime -> Bool
$c< :: ConstDatetime -> ConstDatetime -> Bool
compare :: ConstDatetime -> ConstDatetime -> Ordering
$ccompare :: ConstDatetime -> ConstDatetime -> Ordering
$cp1Ord :: Eq ConstDatetime
Ord)

-- |
-- ==== References
-- @
-- opt_timezone:
--   | WITH_LA TIME ZONE
--   | WITHOUT TIME ZONE
--   | EMPTY
-- @
type Timezone = Bool

-- |
-- ==== References
-- @
-- opt_interval:
--   | YEAR_P
--   | MONTH_P
--   | DAY_P
--   | HOUR_P
--   | MINUTE_P
--   | interval_second
--   | YEAR_P TO MONTH_P
--   | DAY_P TO HOUR_P
--   | DAY_P TO MINUTE_P
--   | DAY_P TO interval_second
--   | HOUR_P TO MINUTE_P
--   | HOUR_P TO interval_second
--   | MINUTE_P TO interval_second
--   | EMPTY
-- @
data Interval
  = YearInterval
  | MonthInterval
  | DayInterval
  | HourInterval
  | MinuteInterval
  | SecondInterval IntervalSecond
  | YearToMonthInterval
  | DayToHourInterval
  | DayToMinuteInterval
  | DayToSecondInterval IntervalSecond
  | HourToMinuteInterval
  | HourToSecondInterval IntervalSecond
  | MinuteToSecondInterval IntervalSecond
  deriving (Int -> Interval -> ShowS
[Interval] -> ShowS
Interval -> String
(Int -> Interval -> ShowS)
-> (Interval -> String) -> ([Interval] -> ShowS) -> Show Interval
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Interval] -> ShowS
$cshowList :: [Interval] -> ShowS
show :: Interval -> String
$cshow :: Interval -> String
showsPrec :: Int -> Interval -> ShowS
$cshowsPrec :: Int -> Interval -> ShowS
Show, (forall x. Interval -> Rep Interval x)
-> (forall x. Rep Interval x -> Interval) -> Generic Interval
forall x. Rep Interval x -> Interval
forall x. Interval -> Rep Interval x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Interval x -> Interval
$cfrom :: forall x. Interval -> Rep Interval x
Generic, Interval -> Interval -> Bool
(Interval -> Interval -> Bool)
-> (Interval -> Interval -> Bool) -> Eq Interval
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Interval -> Interval -> Bool
$c/= :: Interval -> Interval -> Bool
== :: Interval -> Interval -> Bool
$c== :: Interval -> Interval -> Bool
Eq, Eq Interval
Eq Interval
-> (Interval -> Interval -> Ordering)
-> (Interval -> Interval -> Bool)
-> (Interval -> Interval -> Bool)
-> (Interval -> Interval -> Bool)
-> (Interval -> Interval -> Bool)
-> (Interval -> Interval -> Interval)
-> (Interval -> Interval -> Interval)
-> Ord Interval
Interval -> Interval -> Bool
Interval -> Interval -> Ordering
Interval -> Interval -> Interval
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Interval -> Interval -> Interval
$cmin :: Interval -> Interval -> Interval
max :: Interval -> Interval -> Interval
$cmax :: Interval -> Interval -> Interval
>= :: Interval -> Interval -> Bool
$c>= :: Interval -> Interval -> Bool
> :: Interval -> Interval -> Bool
$c> :: Interval -> Interval -> Bool
<= :: Interval -> Interval -> Bool
$c<= :: Interval -> Interval -> Bool
< :: Interval -> Interval -> Bool
$c< :: Interval -> Interval -> Bool
compare :: Interval -> Interval -> Ordering
$ccompare :: Interval -> Interval -> Ordering
$cp1Ord :: Eq Interval
Ord)

-- |
-- ==== References
-- @
-- interval_second:
--   | SECOND_P
--   | SECOND_P '(' Iconst ')'
-- @
type IntervalSecond = Maybe Int64

-- * Names & References

-- |
-- ==== References
-- @
-- IDENT
-- @
data Ident = QuotedIdent Text | UnquotedIdent Text
  deriving (Int -> Ident -> ShowS
[Ident] -> ShowS
Ident -> String
(Int -> Ident -> ShowS)
-> (Ident -> String) -> ([Ident] -> ShowS) -> Show Ident
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Ident] -> ShowS
$cshowList :: [Ident] -> ShowS
show :: Ident -> String
$cshow :: Ident -> String
showsPrec :: Int -> Ident -> ShowS
$cshowsPrec :: Int -> Ident -> ShowS
Show, (forall x. Ident -> Rep Ident x)
-> (forall x. Rep Ident x -> Ident) -> Generic Ident
forall x. Rep Ident x -> Ident
forall x. Ident -> Rep Ident x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Ident x -> Ident
$cfrom :: forall x. Ident -> Rep Ident x
Generic, Ident -> Ident -> Bool
(Ident -> Ident -> Bool) -> (Ident -> Ident -> Bool) -> Eq Ident
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Ident -> Ident -> Bool
$c/= :: Ident -> Ident -> Bool
== :: Ident -> Ident -> Bool
$c== :: Ident -> Ident -> Bool
Eq, Eq Ident
Eq Ident
-> (Ident -> Ident -> Ordering)
-> (Ident -> Ident -> Bool)
-> (Ident -> Ident -> Bool)
-> (Ident -> Ident -> Bool)
-> (Ident -> Ident -> Bool)
-> (Ident -> Ident -> Ident)
-> (Ident -> Ident -> Ident)
-> Ord Ident
Ident -> Ident -> Bool
Ident -> Ident -> Ordering
Ident -> Ident -> Ident
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Ident -> Ident -> Ident
$cmin :: Ident -> Ident -> Ident
max :: Ident -> Ident -> Ident
$cmax :: Ident -> Ident -> Ident
>= :: Ident -> Ident -> Bool
$c>= :: Ident -> Ident -> Bool
> :: Ident -> Ident -> Bool
$c> :: Ident -> Ident -> Bool
<= :: Ident -> Ident -> Bool
$c<= :: Ident -> Ident -> Bool
< :: Ident -> Ident -> Bool
$c< :: Ident -> Ident -> Bool
compare :: Ident -> Ident -> Ordering
$ccompare :: Ident -> Ident -> Ordering
$cp1Ord :: Eq Ident
Ord)

-- |
-- ==== References
-- @
-- ColId:
--   | IDENT
--   | unreserved_keyword
--   | col_name_keyword
-- @
type ColId = Ident

-- |
-- ==== References
-- @
-- ColLabel:
--   | IDENT
--   | unreserved_keyword
--   | col_name_keyword
--   | type_func_name_keyword
--   | reserved_keyword
-- @
type ColLabel = Ident

-- |
-- ==== References
-- @
-- name:
--   | ColId
-- @
type Name = ColId

-- |
-- ==== References
-- @
-- name_list:
--   | name
--   | name_list ',' name
-- @
type NameList = NonEmpty Name

-- |
-- ==== References
-- @
-- cursor_name:
--   | name
-- @
type CursorName = Name

-- |
-- ==== References
-- @
-- columnref:
--   | ColId
--   | ColId indirection
-- @
data Columnref = Columnref ColId (Maybe Indirection)
  deriving (Int -> Columnref -> ShowS
[Columnref] -> ShowS
Columnref -> String
(Int -> Columnref -> ShowS)
-> (Columnref -> String)
-> ([Columnref] -> ShowS)
-> Show Columnref
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Columnref] -> ShowS
$cshowList :: [Columnref] -> ShowS
show :: Columnref -> String
$cshow :: Columnref -> String
showsPrec :: Int -> Columnref -> ShowS
$cshowsPrec :: Int -> Columnref -> ShowS
Show, (forall x. Columnref -> Rep Columnref x)
-> (forall x. Rep Columnref x -> Columnref) -> Generic Columnref
forall x. Rep Columnref x -> Columnref
forall x. Columnref -> Rep Columnref x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Columnref x -> Columnref
$cfrom :: forall x. Columnref -> Rep Columnref x
Generic, Columnref -> Columnref -> Bool
(Columnref -> Columnref -> Bool)
-> (Columnref -> Columnref -> Bool) -> Eq Columnref
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Columnref -> Columnref -> Bool
$c/= :: Columnref -> Columnref -> Bool
== :: Columnref -> Columnref -> Bool
$c== :: Columnref -> Columnref -> Bool
Eq, Eq Columnref
Eq Columnref
-> (Columnref -> Columnref -> Ordering)
-> (Columnref -> Columnref -> Bool)
-> (Columnref -> Columnref -> Bool)
-> (Columnref -> Columnref -> Bool)
-> (Columnref -> Columnref -> Bool)
-> (Columnref -> Columnref -> Columnref)
-> (Columnref -> Columnref -> Columnref)
-> Ord Columnref
Columnref -> Columnref -> Bool
Columnref -> Columnref -> Ordering
Columnref -> Columnref -> Columnref
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Columnref -> Columnref -> Columnref
$cmin :: Columnref -> Columnref -> Columnref
max :: Columnref -> Columnref -> Columnref
$cmax :: Columnref -> Columnref -> Columnref
>= :: Columnref -> Columnref -> Bool
$c>= :: Columnref -> Columnref -> Bool
> :: Columnref -> Columnref -> Bool
$c> :: Columnref -> Columnref -> Bool
<= :: Columnref -> Columnref -> Bool
$c<= :: Columnref -> Columnref -> Bool
< :: Columnref -> Columnref -> Bool
$c< :: Columnref -> Columnref -> Bool
compare :: Columnref -> Columnref -> Ordering
$ccompare :: Columnref -> Columnref -> Ordering
$cp1Ord :: Eq Columnref
Ord)

-- |
-- ==== References
-- @
-- any_name:
--   | ColId
--   | ColId attrs
-- @
data AnyName = AnyName ColId (Maybe Attrs)
  deriving (Int -> AnyName -> ShowS
[AnyName] -> ShowS
AnyName -> String
(Int -> AnyName -> ShowS)
-> (AnyName -> String) -> ([AnyName] -> ShowS) -> Show AnyName
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AnyName] -> ShowS
$cshowList :: [AnyName] -> ShowS
show :: AnyName -> String
$cshow :: AnyName -> String
showsPrec :: Int -> AnyName -> ShowS
$cshowsPrec :: Int -> AnyName -> ShowS
Show, (forall x. AnyName -> Rep AnyName x)
-> (forall x. Rep AnyName x -> AnyName) -> Generic AnyName
forall x. Rep AnyName x -> AnyName
forall x. AnyName -> Rep AnyName x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AnyName x -> AnyName
$cfrom :: forall x. AnyName -> Rep AnyName x
Generic, AnyName -> AnyName -> Bool
(AnyName -> AnyName -> Bool)
-> (AnyName -> AnyName -> Bool) -> Eq AnyName
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AnyName -> AnyName -> Bool
$c/= :: AnyName -> AnyName -> Bool
== :: AnyName -> AnyName -> Bool
$c== :: AnyName -> AnyName -> Bool
Eq, Eq AnyName
Eq AnyName
-> (AnyName -> AnyName -> Ordering)
-> (AnyName -> AnyName -> Bool)
-> (AnyName -> AnyName -> Bool)
-> (AnyName -> AnyName -> Bool)
-> (AnyName -> AnyName -> Bool)
-> (AnyName -> AnyName -> AnyName)
-> (AnyName -> AnyName -> AnyName)
-> Ord AnyName
AnyName -> AnyName -> Bool
AnyName -> AnyName -> Ordering
AnyName -> AnyName -> AnyName
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: AnyName -> AnyName -> AnyName
$cmin :: AnyName -> AnyName -> AnyName
max :: AnyName -> AnyName -> AnyName
$cmax :: AnyName -> AnyName -> AnyName
>= :: AnyName -> AnyName -> Bool
$c>= :: AnyName -> AnyName -> Bool
> :: AnyName -> AnyName -> Bool
$c> :: AnyName -> AnyName -> Bool
<= :: AnyName -> AnyName -> Bool
$c<= :: AnyName -> AnyName -> Bool
< :: AnyName -> AnyName -> Bool
$c< :: AnyName -> AnyName -> Bool
compare :: AnyName -> AnyName -> Ordering
$ccompare :: AnyName -> AnyName -> Ordering
$cp1Ord :: Eq AnyName
Ord)

-- |
-- ==== References
-- @
-- func_name:
--   | type_function_name
--   | ColId indirection
-- @
data FuncName
  = TypeFuncName TypeFunctionName
  | IndirectedFuncName ColId Indirection
  deriving (Int -> FuncName -> ShowS
[FuncName] -> ShowS
FuncName -> String
(Int -> FuncName -> ShowS)
-> (FuncName -> String) -> ([FuncName] -> ShowS) -> Show FuncName
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FuncName] -> ShowS
$cshowList :: [FuncName] -> ShowS
show :: FuncName -> String
$cshow :: FuncName -> String
showsPrec :: Int -> FuncName -> ShowS
$cshowsPrec :: Int -> FuncName -> ShowS
Show, (forall x. FuncName -> Rep FuncName x)
-> (forall x. Rep FuncName x -> FuncName) -> Generic FuncName
forall x. Rep FuncName x -> FuncName
forall x. FuncName -> Rep FuncName x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep FuncName x -> FuncName
$cfrom :: forall x. FuncName -> Rep FuncName x
Generic, FuncName -> FuncName -> Bool
(FuncName -> FuncName -> Bool)
-> (FuncName -> FuncName -> Bool) -> Eq FuncName
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FuncName -> FuncName -> Bool
$c/= :: FuncName -> FuncName -> Bool
== :: FuncName -> FuncName -> Bool
$c== :: FuncName -> FuncName -> Bool
Eq, Eq FuncName
Eq FuncName
-> (FuncName -> FuncName -> Ordering)
-> (FuncName -> FuncName -> Bool)
-> (FuncName -> FuncName -> Bool)
-> (FuncName -> FuncName -> Bool)
-> (FuncName -> FuncName -> Bool)
-> (FuncName -> FuncName -> FuncName)
-> (FuncName -> FuncName -> FuncName)
-> Ord FuncName
FuncName -> FuncName -> Bool
FuncName -> FuncName -> Ordering
FuncName -> FuncName -> FuncName
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: FuncName -> FuncName -> FuncName
$cmin :: FuncName -> FuncName -> FuncName
max :: FuncName -> FuncName -> FuncName
$cmax :: FuncName -> FuncName -> FuncName
>= :: FuncName -> FuncName -> Bool
$c>= :: FuncName -> FuncName -> Bool
> :: FuncName -> FuncName -> Bool
$c> :: FuncName -> FuncName -> Bool
<= :: FuncName -> FuncName -> Bool
$c<= :: FuncName -> FuncName -> Bool
< :: FuncName -> FuncName -> Bool
$c< :: FuncName -> FuncName -> Bool
compare :: FuncName -> FuncName -> Ordering
$ccompare :: FuncName -> FuncName -> Ordering
$cp1Ord :: Eq FuncName
Ord)

-- |
-- ==== References
-- @
-- type_function_name:
--   | IDENT
--   | unreserved_keyword
--   | type_func_name_keyword
-- @
type TypeFunctionName = Ident

-- |
-- ==== References
-- @
-- columnref:
--   | ColId
--   | ColId indirection
-- qualified_name:
--   | ColId
--   | ColId indirection
-- @
data QualifiedName
  = SimpleQualifiedName Ident
  | IndirectedQualifiedName Ident Indirection
  deriving (Int -> QualifiedName -> ShowS
[QualifiedName] -> ShowS
QualifiedName -> String
(Int -> QualifiedName -> ShowS)
-> (QualifiedName -> String)
-> ([QualifiedName] -> ShowS)
-> Show QualifiedName
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [QualifiedName] -> ShowS
$cshowList :: [QualifiedName] -> ShowS
show :: QualifiedName -> String
$cshow :: QualifiedName -> String
showsPrec :: Int -> QualifiedName -> ShowS
$cshowsPrec :: Int -> QualifiedName -> ShowS
Show, (forall x. QualifiedName -> Rep QualifiedName x)
-> (forall x. Rep QualifiedName x -> QualifiedName)
-> Generic QualifiedName
forall x. Rep QualifiedName x -> QualifiedName
forall x. QualifiedName -> Rep QualifiedName x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep QualifiedName x -> QualifiedName
$cfrom :: forall x. QualifiedName -> Rep QualifiedName x
Generic, QualifiedName -> QualifiedName -> Bool
(QualifiedName -> QualifiedName -> Bool)
-> (QualifiedName -> QualifiedName -> Bool) -> Eq QualifiedName
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: QualifiedName -> QualifiedName -> Bool
$c/= :: QualifiedName -> QualifiedName -> Bool
== :: QualifiedName -> QualifiedName -> Bool
$c== :: QualifiedName -> QualifiedName -> Bool
Eq, Eq QualifiedName
Eq QualifiedName
-> (QualifiedName -> QualifiedName -> Ordering)
-> (QualifiedName -> QualifiedName -> Bool)
-> (QualifiedName -> QualifiedName -> Bool)
-> (QualifiedName -> QualifiedName -> Bool)
-> (QualifiedName -> QualifiedName -> Bool)
-> (QualifiedName -> QualifiedName -> QualifiedName)
-> (QualifiedName -> QualifiedName -> QualifiedName)
-> Ord QualifiedName
QualifiedName -> QualifiedName -> Bool
QualifiedName -> QualifiedName -> Ordering
QualifiedName -> QualifiedName -> QualifiedName
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: QualifiedName -> QualifiedName -> QualifiedName
$cmin :: QualifiedName -> QualifiedName -> QualifiedName
max :: QualifiedName -> QualifiedName -> QualifiedName
$cmax :: QualifiedName -> QualifiedName -> QualifiedName
>= :: QualifiedName -> QualifiedName -> Bool
$c>= :: QualifiedName -> QualifiedName -> Bool
> :: QualifiedName -> QualifiedName -> Bool
$c> :: QualifiedName -> QualifiedName -> Bool
<= :: QualifiedName -> QualifiedName -> Bool
$c<= :: QualifiedName -> QualifiedName -> Bool
< :: QualifiedName -> QualifiedName -> Bool
$c< :: QualifiedName -> QualifiedName -> Bool
compare :: QualifiedName -> QualifiedName -> Ordering
$ccompare :: QualifiedName -> QualifiedName -> Ordering
$cp1Ord :: Eq QualifiedName
Ord)

-- |
-- ==== References
-- @
-- indirection:
--   |  indirection_el
--   |  indirection indirection_el
-- @
type Indirection = NonEmpty IndirectionEl

-- |
-- ==== References
-- @
-- indirection_el:
--   |  '.' attr_name
--   |  '.' '*'
--   |  '[' a_expr ']'
--   |  '[' opt_slice_bound ':' opt_slice_bound ']'
-- opt_slice_bound:
--   |  a_expr
--   |  EMPTY
-- @
data IndirectionEl
  = AttrNameIndirectionEl Ident
  | AllIndirectionEl
  | ExprIndirectionEl AExpr
  | SliceIndirectionEl (Maybe AExpr) (Maybe AExpr)
  deriving (Int -> IndirectionEl -> ShowS
[IndirectionEl] -> ShowS
IndirectionEl -> String
(Int -> IndirectionEl -> ShowS)
-> (IndirectionEl -> String)
-> ([IndirectionEl] -> ShowS)
-> Show IndirectionEl
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [IndirectionEl] -> ShowS
$cshowList :: [IndirectionEl] -> ShowS
show :: IndirectionEl -> String
$cshow :: IndirectionEl -> String
showsPrec :: Int -> IndirectionEl -> ShowS
$cshowsPrec :: Int -> IndirectionEl -> ShowS
Show, (forall x. IndirectionEl -> Rep IndirectionEl x)
-> (forall x. Rep IndirectionEl x -> IndirectionEl)
-> Generic IndirectionEl
forall x. Rep IndirectionEl x -> IndirectionEl
forall x. IndirectionEl -> Rep IndirectionEl x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep IndirectionEl x -> IndirectionEl
$cfrom :: forall x. IndirectionEl -> Rep IndirectionEl x
Generic, IndirectionEl -> IndirectionEl -> Bool
(IndirectionEl -> IndirectionEl -> Bool)
-> (IndirectionEl -> IndirectionEl -> Bool) -> Eq IndirectionEl
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IndirectionEl -> IndirectionEl -> Bool
$c/= :: IndirectionEl -> IndirectionEl -> Bool
== :: IndirectionEl -> IndirectionEl -> Bool
$c== :: IndirectionEl -> IndirectionEl -> Bool
Eq, Eq IndirectionEl
Eq IndirectionEl
-> (IndirectionEl -> IndirectionEl -> Ordering)
-> (IndirectionEl -> IndirectionEl -> Bool)
-> (IndirectionEl -> IndirectionEl -> Bool)
-> (IndirectionEl -> IndirectionEl -> Bool)
-> (IndirectionEl -> IndirectionEl -> Bool)
-> (IndirectionEl -> IndirectionEl -> IndirectionEl)
-> (IndirectionEl -> IndirectionEl -> IndirectionEl)
-> Ord IndirectionEl
IndirectionEl -> IndirectionEl -> Bool
IndirectionEl -> IndirectionEl -> Ordering
IndirectionEl -> IndirectionEl -> IndirectionEl
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: IndirectionEl -> IndirectionEl -> IndirectionEl
$cmin :: IndirectionEl -> IndirectionEl -> IndirectionEl
max :: IndirectionEl -> IndirectionEl -> IndirectionEl
$cmax :: IndirectionEl -> IndirectionEl -> IndirectionEl
>= :: IndirectionEl -> IndirectionEl -> Bool
$c>= :: IndirectionEl -> IndirectionEl -> Bool
> :: IndirectionEl -> IndirectionEl -> Bool
$c> :: IndirectionEl -> IndirectionEl -> Bool
<= :: IndirectionEl -> IndirectionEl -> Bool
$c<= :: IndirectionEl -> IndirectionEl -> Bool
< :: IndirectionEl -> IndirectionEl -> Bool
$c< :: IndirectionEl -> IndirectionEl -> Bool
compare :: IndirectionEl -> IndirectionEl -> Ordering
$ccompare :: IndirectionEl -> IndirectionEl -> Ordering
$cp1Ord :: Eq IndirectionEl
Ord)

-- * Types

-- |
-- Typename definition extended with custom question-marks for nullability specification.
--
-- To match the standard Postgres syntax simply interpret their presence as a parsing error.
--
-- ==== References
-- @
-- Typename:
--   | SimpleTypename opt_array_bounds
--   | SETOF SimpleTypename opt_array_bounds
--   | SimpleTypename ARRAY '[' Iconst ']'
--   | SETOF SimpleTypename ARRAY '[' Iconst ']'
--   | SimpleTypename ARRAY
--   | SETOF SimpleTypename ARRAY
-- @
data Typename
  = Typename
      Bool
      -- ^ SETOF
      SimpleTypename
      Bool
      -- ^ Question mark
      (Maybe (TypenameArrayDimensions, Bool))
      -- ^ Array dimensions possibly followed by a question mark
  deriving (Int -> Typename -> ShowS
[Typename] -> ShowS
Typename -> String
(Int -> Typename -> ShowS)
-> (Typename -> String) -> ([Typename] -> ShowS) -> Show Typename
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Typename] -> ShowS
$cshowList :: [Typename] -> ShowS
show :: Typename -> String
$cshow :: Typename -> String
showsPrec :: Int -> Typename -> ShowS
$cshowsPrec :: Int -> Typename -> ShowS
Show, (forall x. Typename -> Rep Typename x)
-> (forall x. Rep Typename x -> Typename) -> Generic Typename
forall x. Rep Typename x -> Typename
forall x. Typename -> Rep Typename x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Typename x -> Typename
$cfrom :: forall x. Typename -> Rep Typename x
Generic, Typename -> Typename -> Bool
(Typename -> Typename -> Bool)
-> (Typename -> Typename -> Bool) -> Eq Typename
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Typename -> Typename -> Bool
$c/= :: Typename -> Typename -> Bool
== :: Typename -> Typename -> Bool
$c== :: Typename -> Typename -> Bool
Eq, Eq Typename
Eq Typename
-> (Typename -> Typename -> Ordering)
-> (Typename -> Typename -> Bool)
-> (Typename -> Typename -> Bool)
-> (Typename -> Typename -> Bool)
-> (Typename -> Typename -> Bool)
-> (Typename -> Typename -> Typename)
-> (Typename -> Typename -> Typename)
-> Ord Typename
Typename -> Typename -> Bool
Typename -> Typename -> Ordering
Typename -> Typename -> Typename
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Typename -> Typename -> Typename
$cmin :: Typename -> Typename -> Typename
max :: Typename -> Typename -> Typename
$cmax :: Typename -> Typename -> Typename
>= :: Typename -> Typename -> Bool
$c>= :: Typename -> Typename -> Bool
> :: Typename -> Typename -> Bool
$c> :: Typename -> Typename -> Bool
<= :: Typename -> Typename -> Bool
$c<= :: Typename -> Typename -> Bool
< :: Typename -> Typename -> Bool
$c< :: Typename -> Typename -> Bool
compare :: Typename -> Typename -> Ordering
$ccompare :: Typename -> Typename -> Ordering
$cp1Ord :: Eq Typename
Ord)

-- |
-- ==== References
-- @
-- Part of the Typename specification responsible for the choice between the following:
--   | opt_array_bounds
--   | ARRAY '[' Iconst ']'
--   | ARRAY
-- @
data TypenameArrayDimensions
  = BoundsTypenameArrayDimensions ArrayBounds
  | ExplicitTypenameArrayDimensions (Maybe Iconst)
  deriving (Int -> TypenameArrayDimensions -> ShowS
[TypenameArrayDimensions] -> ShowS
TypenameArrayDimensions -> String
(Int -> TypenameArrayDimensions -> ShowS)
-> (TypenameArrayDimensions -> String)
-> ([TypenameArrayDimensions] -> ShowS)
-> Show TypenameArrayDimensions
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TypenameArrayDimensions] -> ShowS
$cshowList :: [TypenameArrayDimensions] -> ShowS
show :: TypenameArrayDimensions -> String
$cshow :: TypenameArrayDimensions -> String
showsPrec :: Int -> TypenameArrayDimensions -> ShowS
$cshowsPrec :: Int -> TypenameArrayDimensions -> ShowS
Show, (forall x.
 TypenameArrayDimensions -> Rep TypenameArrayDimensions x)
-> (forall x.
    Rep TypenameArrayDimensions x -> TypenameArrayDimensions)
-> Generic TypenameArrayDimensions
forall x. Rep TypenameArrayDimensions x -> TypenameArrayDimensions
forall x. TypenameArrayDimensions -> Rep TypenameArrayDimensions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TypenameArrayDimensions x -> TypenameArrayDimensions
$cfrom :: forall x. TypenameArrayDimensions -> Rep TypenameArrayDimensions x
Generic, TypenameArrayDimensions -> TypenameArrayDimensions -> Bool
(TypenameArrayDimensions -> TypenameArrayDimensions -> Bool)
-> (TypenameArrayDimensions -> TypenameArrayDimensions -> Bool)
-> Eq TypenameArrayDimensions
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TypenameArrayDimensions -> TypenameArrayDimensions -> Bool
$c/= :: TypenameArrayDimensions -> TypenameArrayDimensions -> Bool
== :: TypenameArrayDimensions -> TypenameArrayDimensions -> Bool
$c== :: TypenameArrayDimensions -> TypenameArrayDimensions -> Bool
Eq, Eq TypenameArrayDimensions
Eq TypenameArrayDimensions
-> (TypenameArrayDimensions -> TypenameArrayDimensions -> Ordering)
-> (TypenameArrayDimensions -> TypenameArrayDimensions -> Bool)
-> (TypenameArrayDimensions -> TypenameArrayDimensions -> Bool)
-> (TypenameArrayDimensions -> TypenameArrayDimensions -> Bool)
-> (TypenameArrayDimensions -> TypenameArrayDimensions -> Bool)
-> (TypenameArrayDimensions
    -> TypenameArrayDimensions -> TypenameArrayDimensions)
-> (TypenameArrayDimensions
    -> TypenameArrayDimensions -> TypenameArrayDimensions)
-> Ord TypenameArrayDimensions
TypenameArrayDimensions -> TypenameArrayDimensions -> Bool
TypenameArrayDimensions -> TypenameArrayDimensions -> Ordering
TypenameArrayDimensions
-> TypenameArrayDimensions -> TypenameArrayDimensions
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: TypenameArrayDimensions
-> TypenameArrayDimensions -> TypenameArrayDimensions
$cmin :: TypenameArrayDimensions
-> TypenameArrayDimensions -> TypenameArrayDimensions
max :: TypenameArrayDimensions
-> TypenameArrayDimensions -> TypenameArrayDimensions
$cmax :: TypenameArrayDimensions
-> TypenameArrayDimensions -> TypenameArrayDimensions
>= :: TypenameArrayDimensions -> TypenameArrayDimensions -> Bool
$c>= :: TypenameArrayDimensions -> TypenameArrayDimensions -> Bool
> :: TypenameArrayDimensions -> TypenameArrayDimensions -> Bool
$c> :: TypenameArrayDimensions -> TypenameArrayDimensions -> Bool
<= :: TypenameArrayDimensions -> TypenameArrayDimensions -> Bool
$c<= :: TypenameArrayDimensions -> TypenameArrayDimensions -> Bool
< :: TypenameArrayDimensions -> TypenameArrayDimensions -> Bool
$c< :: TypenameArrayDimensions -> TypenameArrayDimensions -> Bool
compare :: TypenameArrayDimensions -> TypenameArrayDimensions -> Ordering
$ccompare :: TypenameArrayDimensions -> TypenameArrayDimensions -> Ordering
$cp1Ord :: Eq TypenameArrayDimensions
Ord)

-- |
-- ==== References
-- @
-- opt_array_bounds:
--   | opt_array_bounds '[' ']'
--   | opt_array_bounds '[' Iconst ']'
--   | EMPTY
-- @
type ArrayBounds = NonEmpty (Maybe Iconst)

-- |
-- ==== References
-- @
-- SimpleTypename:
--   | GenericType
--   | Numeric
--   | Bit
--   | Character
--   | ConstDatetime
--   | ConstInterval opt_interval
--   | ConstInterval '(' Iconst ')'
-- ConstInterval:
--   | INTERVAL
-- @
data SimpleTypename
  = GenericTypeSimpleTypename GenericType
  | NumericSimpleTypename Numeric
  | BitSimpleTypename Bit
  | CharacterSimpleTypename Character
  | ConstDatetimeSimpleTypename ConstDatetime
  | ConstIntervalSimpleTypename (Either (Maybe Interval) Iconst)
  deriving (Int -> SimpleTypename -> ShowS
[SimpleTypename] -> ShowS
SimpleTypename -> String
(Int -> SimpleTypename -> ShowS)
-> (SimpleTypename -> String)
-> ([SimpleTypename] -> ShowS)
-> Show SimpleTypename
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SimpleTypename] -> ShowS
$cshowList :: [SimpleTypename] -> ShowS
show :: SimpleTypename -> String
$cshow :: SimpleTypename -> String
showsPrec :: Int -> SimpleTypename -> ShowS
$cshowsPrec :: Int -> SimpleTypename -> ShowS
Show, (forall x. SimpleTypename -> Rep SimpleTypename x)
-> (forall x. Rep SimpleTypename x -> SimpleTypename)
-> Generic SimpleTypename
forall x. Rep SimpleTypename x -> SimpleTypename
forall x. SimpleTypename -> Rep SimpleTypename x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SimpleTypename x -> SimpleTypename
$cfrom :: forall x. SimpleTypename -> Rep SimpleTypename x
Generic, SimpleTypename -> SimpleTypename -> Bool
(SimpleTypename -> SimpleTypename -> Bool)
-> (SimpleTypename -> SimpleTypename -> Bool) -> Eq SimpleTypename
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SimpleTypename -> SimpleTypename -> Bool
$c/= :: SimpleTypename -> SimpleTypename -> Bool
== :: SimpleTypename -> SimpleTypename -> Bool
$c== :: SimpleTypename -> SimpleTypename -> Bool
Eq, Eq SimpleTypename
Eq SimpleTypename
-> (SimpleTypename -> SimpleTypename -> Ordering)
-> (SimpleTypename -> SimpleTypename -> Bool)
-> (SimpleTypename -> SimpleTypename -> Bool)
-> (SimpleTypename -> SimpleTypename -> Bool)
-> (SimpleTypename -> SimpleTypename -> Bool)
-> (SimpleTypename -> SimpleTypename -> SimpleTypename)
-> (SimpleTypename -> SimpleTypename -> SimpleTypename)
-> Ord SimpleTypename
SimpleTypename -> SimpleTypename -> Bool
SimpleTypename -> SimpleTypename -> Ordering
SimpleTypename -> SimpleTypename -> SimpleTypename
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: SimpleTypename -> SimpleTypename -> SimpleTypename
$cmin :: SimpleTypename -> SimpleTypename -> SimpleTypename
max :: SimpleTypename -> SimpleTypename -> SimpleTypename
$cmax :: SimpleTypename -> SimpleTypename -> SimpleTypename
>= :: SimpleTypename -> SimpleTypename -> Bool
$c>= :: SimpleTypename -> SimpleTypename -> Bool
> :: SimpleTypename -> SimpleTypename -> Bool
$c> :: SimpleTypename -> SimpleTypename -> Bool
<= :: SimpleTypename -> SimpleTypename -> Bool
$c<= :: SimpleTypename -> SimpleTypename -> Bool
< :: SimpleTypename -> SimpleTypename -> Bool
$c< :: SimpleTypename -> SimpleTypename -> Bool
compare :: SimpleTypename -> SimpleTypename -> Ordering
$ccompare :: SimpleTypename -> SimpleTypename -> Ordering
$cp1Ord :: Eq SimpleTypename
Ord)

-- |
-- ==== References
-- @
-- GenericType:
--   | type_function_name opt_type_modifiers
--   | type_function_name attrs opt_type_modifiers
-- @
data GenericType = GenericType TypeFunctionName (Maybe Attrs) (Maybe TypeModifiers)
  deriving (Int -> GenericType -> ShowS
[GenericType] -> ShowS
GenericType -> String
(Int -> GenericType -> ShowS)
-> (GenericType -> String)
-> ([GenericType] -> ShowS)
-> Show GenericType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GenericType] -> ShowS
$cshowList :: [GenericType] -> ShowS
show :: GenericType -> String
$cshow :: GenericType -> String
showsPrec :: Int -> GenericType -> ShowS
$cshowsPrec :: Int -> GenericType -> ShowS
Show, (forall x. GenericType -> Rep GenericType x)
-> (forall x. Rep GenericType x -> GenericType)
-> Generic GenericType
forall x. Rep GenericType x -> GenericType
forall x. GenericType -> Rep GenericType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GenericType x -> GenericType
$cfrom :: forall x. GenericType -> Rep GenericType x
Generic, GenericType -> GenericType -> Bool
(GenericType -> GenericType -> Bool)
-> (GenericType -> GenericType -> Bool) -> Eq GenericType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GenericType -> GenericType -> Bool
$c/= :: GenericType -> GenericType -> Bool
== :: GenericType -> GenericType -> Bool
$c== :: GenericType -> GenericType -> Bool
Eq, Eq GenericType
Eq GenericType
-> (GenericType -> GenericType -> Ordering)
-> (GenericType -> GenericType -> Bool)
-> (GenericType -> GenericType -> Bool)
-> (GenericType -> GenericType -> Bool)
-> (GenericType -> GenericType -> Bool)
-> (GenericType -> GenericType -> GenericType)
-> (GenericType -> GenericType -> GenericType)
-> Ord GenericType
GenericType -> GenericType -> Bool
GenericType -> GenericType -> Ordering
GenericType -> GenericType -> GenericType
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: GenericType -> GenericType -> GenericType
$cmin :: GenericType -> GenericType -> GenericType
max :: GenericType -> GenericType -> GenericType
$cmax :: GenericType -> GenericType -> GenericType
>= :: GenericType -> GenericType -> Bool
$c>= :: GenericType -> GenericType -> Bool
> :: GenericType -> GenericType -> Bool
$c> :: GenericType -> GenericType -> Bool
<= :: GenericType -> GenericType -> Bool
$c<= :: GenericType -> GenericType -> Bool
< :: GenericType -> GenericType -> Bool
$c< :: GenericType -> GenericType -> Bool
compare :: GenericType -> GenericType -> Ordering
$ccompare :: GenericType -> GenericType -> Ordering
$cp1Ord :: Eq GenericType
Ord)

-- |
-- ==== References
-- @
-- attrs:
--   | '.' attr_name
--   | attrs '.' attr_name
-- @
type Attrs = NonEmpty AttrName

-- |
-- ==== References
-- @
-- attr_name:
--   | ColLabel
-- @
type AttrName = ColLabel

-- |
-- ==== References
-- @
-- opt_type_modifiers:
--   | '(' expr_list ')'
--   | EMPTY
-- @
type TypeModifiers = ExprList

-- |
-- ==== References
-- @
-- type_list:
--   | Typename
--   | type_list ',' Typename
-- @
type TypeList = NonEmpty Typename

-- * Operators

-- |
-- ==== References
-- @
-- qual_Op:
--   | Op
--   | OPERATOR '(' any_operator ')'
-- @
data QualOp
  = OpQualOp Op
  | OperatorQualOp AnyOperator
  deriving (Int -> QualOp -> ShowS
[QualOp] -> ShowS
QualOp -> String
(Int -> QualOp -> ShowS)
-> (QualOp -> String) -> ([QualOp] -> ShowS) -> Show QualOp
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [QualOp] -> ShowS
$cshowList :: [QualOp] -> ShowS
show :: QualOp -> String
$cshow :: QualOp -> String
showsPrec :: Int -> QualOp -> ShowS
$cshowsPrec :: Int -> QualOp -> ShowS
Show, (forall x. QualOp -> Rep QualOp x)
-> (forall x. Rep QualOp x -> QualOp) -> Generic QualOp
forall x. Rep QualOp x -> QualOp
forall x. QualOp -> Rep QualOp x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep QualOp x -> QualOp
$cfrom :: forall x. QualOp -> Rep QualOp x
Generic, QualOp -> QualOp -> Bool
(QualOp -> QualOp -> Bool)
-> (QualOp -> QualOp -> Bool) -> Eq QualOp
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: QualOp -> QualOp -> Bool
$c/= :: QualOp -> QualOp -> Bool
== :: QualOp -> QualOp -> Bool
$c== :: QualOp -> QualOp -> Bool
Eq, Eq QualOp
Eq QualOp
-> (QualOp -> QualOp -> Ordering)
-> (QualOp -> QualOp -> Bool)
-> (QualOp -> QualOp -> Bool)
-> (QualOp -> QualOp -> Bool)
-> (QualOp -> QualOp -> Bool)
-> (QualOp -> QualOp -> QualOp)
-> (QualOp -> QualOp -> QualOp)
-> Ord QualOp
QualOp -> QualOp -> Bool
QualOp -> QualOp -> Ordering
QualOp -> QualOp -> QualOp
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: QualOp -> QualOp -> QualOp
$cmin :: QualOp -> QualOp -> QualOp
max :: QualOp -> QualOp -> QualOp
$cmax :: QualOp -> QualOp -> QualOp
>= :: QualOp -> QualOp -> Bool
$c>= :: QualOp -> QualOp -> Bool
> :: QualOp -> QualOp -> Bool
$c> :: QualOp -> QualOp -> Bool
<= :: QualOp -> QualOp -> Bool
$c<= :: QualOp -> QualOp -> Bool
< :: QualOp -> QualOp -> Bool
$c< :: QualOp -> QualOp -> Bool
compare :: QualOp -> QualOp -> Ordering
$ccompare :: QualOp -> QualOp -> Ordering
$cp1Ord :: Eq QualOp
Ord)

-- |
-- ==== References
-- @
-- qual_all_Op:
--   | all_Op
--   | OPERATOR '(' any_operator ')'
-- @
data QualAllOp
  = AllQualAllOp AllOp
  | AnyQualAllOp AnyOperator
  deriving (Int -> QualAllOp -> ShowS
[QualAllOp] -> ShowS
QualAllOp -> String
(Int -> QualAllOp -> ShowS)
-> (QualAllOp -> String)
-> ([QualAllOp] -> ShowS)
-> Show QualAllOp
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [QualAllOp] -> ShowS
$cshowList :: [QualAllOp] -> ShowS
show :: QualAllOp -> String
$cshow :: QualAllOp -> String
showsPrec :: Int -> QualAllOp -> ShowS
$cshowsPrec :: Int -> QualAllOp -> ShowS
Show, (forall x. QualAllOp -> Rep QualAllOp x)
-> (forall x. Rep QualAllOp x -> QualAllOp) -> Generic QualAllOp
forall x. Rep QualAllOp x -> QualAllOp
forall x. QualAllOp -> Rep QualAllOp x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep QualAllOp x -> QualAllOp
$cfrom :: forall x. QualAllOp -> Rep QualAllOp x
Generic, QualAllOp -> QualAllOp -> Bool
(QualAllOp -> QualAllOp -> Bool)
-> (QualAllOp -> QualAllOp -> Bool) -> Eq QualAllOp
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: QualAllOp -> QualAllOp -> Bool
$c/= :: QualAllOp -> QualAllOp -> Bool
== :: QualAllOp -> QualAllOp -> Bool
$c== :: QualAllOp -> QualAllOp -> Bool
Eq, Eq QualAllOp
Eq QualAllOp
-> (QualAllOp -> QualAllOp -> Ordering)
-> (QualAllOp -> QualAllOp -> Bool)
-> (QualAllOp -> QualAllOp -> Bool)
-> (QualAllOp -> QualAllOp -> Bool)
-> (QualAllOp -> QualAllOp -> Bool)
-> (QualAllOp -> QualAllOp -> QualAllOp)
-> (QualAllOp -> QualAllOp -> QualAllOp)
-> Ord QualAllOp
QualAllOp -> QualAllOp -> Bool
QualAllOp -> QualAllOp -> Ordering
QualAllOp -> QualAllOp -> QualAllOp
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: QualAllOp -> QualAllOp -> QualAllOp
$cmin :: QualAllOp -> QualAllOp -> QualAllOp
max :: QualAllOp -> QualAllOp -> QualAllOp
$cmax :: QualAllOp -> QualAllOp -> QualAllOp
>= :: QualAllOp -> QualAllOp -> Bool
$c>= :: QualAllOp -> QualAllOp -> Bool
> :: QualAllOp -> QualAllOp -> Bool
$c> :: QualAllOp -> QualAllOp -> Bool
<= :: QualAllOp -> QualAllOp -> Bool
$c<= :: QualAllOp -> QualAllOp -> Bool
< :: QualAllOp -> QualAllOp -> Bool
$c< :: QualAllOp -> QualAllOp -> Bool
compare :: QualAllOp -> QualAllOp -> Ordering
$ccompare :: QualAllOp -> QualAllOp -> Ordering
$cp1Ord :: Eq QualAllOp
Ord)

-- |
-- ==== References
-- @
-- The operator name is a sequence of up to NAMEDATALEN-1 (63 by default)
-- characters from the following list:
--
-- + - * / < > = ~ ! @ # % ^ & | ` ?
--
-- There are a few restrictions on your choice of name:
-- -- and /* cannot appear anywhere in an operator name,
-- since they will be taken as the start of a comment.
--
-- A multicharacter operator name cannot end in + or -,
-- unless the name also contains at least one of these characters:
--
-- ~ ! @ # % ^ & | ` ?
--
-- For example, @- is an allowed operator name, but *- is not.
-- This restriction allows PostgreSQL to parse SQL-compliant
-- commands without requiring spaces between tokens.
-- The use of => as an operator name is deprecated.
-- It may be disallowed altogether in a future release.
--
-- The operator != is mapped to <> on input,
-- so these two names are always equivalent.
-- @
type Op = Text

-- |
-- ==== References
-- @
-- any_operator:
--   | all_Op
--   | ColId '.' any_operator
-- @
data AnyOperator
  = AllOpAnyOperator AllOp
  | QualifiedAnyOperator ColId AnyOperator
  deriving (Int -> AnyOperator -> ShowS
[AnyOperator] -> ShowS
AnyOperator -> String
(Int -> AnyOperator -> ShowS)
-> (AnyOperator -> String)
-> ([AnyOperator] -> ShowS)
-> Show AnyOperator
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AnyOperator] -> ShowS
$cshowList :: [AnyOperator] -> ShowS
show :: AnyOperator -> String
$cshow :: AnyOperator -> String
showsPrec :: Int -> AnyOperator -> ShowS
$cshowsPrec :: Int -> AnyOperator -> ShowS
Show, (forall x. AnyOperator -> Rep AnyOperator x)
-> (forall x. Rep AnyOperator x -> AnyOperator)
-> Generic AnyOperator
forall x. Rep AnyOperator x -> AnyOperator
forall x. AnyOperator -> Rep AnyOperator x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AnyOperator x -> AnyOperator
$cfrom :: forall x. AnyOperator -> Rep AnyOperator x
Generic, AnyOperator -> AnyOperator -> Bool
(AnyOperator -> AnyOperator -> Bool)
-> (AnyOperator -> AnyOperator -> Bool) -> Eq AnyOperator
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AnyOperator -> AnyOperator -> Bool
$c/= :: AnyOperator -> AnyOperator -> Bool
== :: AnyOperator -> AnyOperator -> Bool
$c== :: AnyOperator -> AnyOperator -> Bool
Eq, Eq AnyOperator
Eq AnyOperator
-> (AnyOperator -> AnyOperator -> Ordering)
-> (AnyOperator -> AnyOperator -> Bool)
-> (AnyOperator -> AnyOperator -> Bool)
-> (AnyOperator -> AnyOperator -> Bool)
-> (AnyOperator -> AnyOperator -> Bool)
-> (AnyOperator -> AnyOperator -> AnyOperator)
-> (AnyOperator -> AnyOperator -> AnyOperator)
-> Ord AnyOperator
AnyOperator -> AnyOperator -> Bool
AnyOperator -> AnyOperator -> Ordering
AnyOperator -> AnyOperator -> AnyOperator
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: AnyOperator -> AnyOperator -> AnyOperator
$cmin :: AnyOperator -> AnyOperator -> AnyOperator
max :: AnyOperator -> AnyOperator -> AnyOperator
$cmax :: AnyOperator -> AnyOperator -> AnyOperator
>= :: AnyOperator -> AnyOperator -> Bool
$c>= :: AnyOperator -> AnyOperator -> Bool
> :: AnyOperator -> AnyOperator -> Bool
$c> :: AnyOperator -> AnyOperator -> Bool
<= :: AnyOperator -> AnyOperator -> Bool
$c<= :: AnyOperator -> AnyOperator -> Bool
< :: AnyOperator -> AnyOperator -> Bool
$c< :: AnyOperator -> AnyOperator -> Bool
compare :: AnyOperator -> AnyOperator -> Ordering
$ccompare :: AnyOperator -> AnyOperator -> Ordering
$cp1Ord :: Eq AnyOperator
Ord)

-- |
-- ==== References
-- @
-- all_Op:
--   | Op
--   | MathOp
-- @
data AllOp
  = OpAllOp Op
  | MathAllOp MathOp
  deriving (Int -> AllOp -> ShowS
[AllOp] -> ShowS
AllOp -> String
(Int -> AllOp -> ShowS)
-> (AllOp -> String) -> ([AllOp] -> ShowS) -> Show AllOp
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AllOp] -> ShowS
$cshowList :: [AllOp] -> ShowS
show :: AllOp -> String
$cshow :: AllOp -> String
showsPrec :: Int -> AllOp -> ShowS
$cshowsPrec :: Int -> AllOp -> ShowS
Show, (forall x. AllOp -> Rep AllOp x)
-> (forall x. Rep AllOp x -> AllOp) -> Generic AllOp
forall x. Rep AllOp x -> AllOp
forall x. AllOp -> Rep AllOp x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AllOp x -> AllOp
$cfrom :: forall x. AllOp -> Rep AllOp x
Generic, AllOp -> AllOp -> Bool
(AllOp -> AllOp -> Bool) -> (AllOp -> AllOp -> Bool) -> Eq AllOp
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AllOp -> AllOp -> Bool
$c/= :: AllOp -> AllOp -> Bool
== :: AllOp -> AllOp -> Bool
$c== :: AllOp -> AllOp -> Bool
Eq, Eq AllOp
Eq AllOp
-> (AllOp -> AllOp -> Ordering)
-> (AllOp -> AllOp -> Bool)
-> (AllOp -> AllOp -> Bool)
-> (AllOp -> AllOp -> Bool)
-> (AllOp -> AllOp -> Bool)
-> (AllOp -> AllOp -> AllOp)
-> (AllOp -> AllOp -> AllOp)
-> Ord AllOp
AllOp -> AllOp -> Bool
AllOp -> AllOp -> Ordering
AllOp -> AllOp -> AllOp
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: AllOp -> AllOp -> AllOp
$cmin :: AllOp -> AllOp -> AllOp
max :: AllOp -> AllOp -> AllOp
$cmax :: AllOp -> AllOp -> AllOp
>= :: AllOp -> AllOp -> Bool
$c>= :: AllOp -> AllOp -> Bool
> :: AllOp -> AllOp -> Bool
$c> :: AllOp -> AllOp -> Bool
<= :: AllOp -> AllOp -> Bool
$c<= :: AllOp -> AllOp -> Bool
< :: AllOp -> AllOp -> Bool
$c< :: AllOp -> AllOp -> Bool
compare :: AllOp -> AllOp -> Ordering
$ccompare :: AllOp -> AllOp -> Ordering
$cp1Ord :: Eq AllOp
Ord)

-- |
-- ==== References
-- @
-- MathOp:
--   | '+'
--   | '-'
--   | '*'
--   | '/'
--   | '%'
--   | '^'
--   | '<'
--   | '>'
--   | '='
--   | LESS_EQUALS
--   | GREATER_EQUALS
--   | NOT_EQUALS
-- @
data MathOp
  = PlusMathOp
  | MinusMathOp
  | AsteriskMathOp
  | SlashMathOp
  | PercentMathOp
  | ArrowUpMathOp
  | ArrowLeftMathOp
  | ArrowRightMathOp
  | EqualsMathOp
  | LessEqualsMathOp
  | GreaterEqualsMathOp
  | ArrowLeftArrowRightMathOp
  | ExclamationEqualsMathOp
  deriving (Int -> MathOp -> ShowS
[MathOp] -> ShowS
MathOp -> String
(Int -> MathOp -> ShowS)
-> (MathOp -> String) -> ([MathOp] -> ShowS) -> Show MathOp
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MathOp] -> ShowS
$cshowList :: [MathOp] -> ShowS
show :: MathOp -> String
$cshow :: MathOp -> String
showsPrec :: Int -> MathOp -> ShowS
$cshowsPrec :: Int -> MathOp -> ShowS
Show, (forall x. MathOp -> Rep MathOp x)
-> (forall x. Rep MathOp x -> MathOp) -> Generic MathOp
forall x. Rep MathOp x -> MathOp
forall x. MathOp -> Rep MathOp x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep MathOp x -> MathOp
$cfrom :: forall x. MathOp -> Rep MathOp x
Generic, MathOp -> MathOp -> Bool
(MathOp -> MathOp -> Bool)
-> (MathOp -> MathOp -> Bool) -> Eq MathOp
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MathOp -> MathOp -> Bool
$c/= :: MathOp -> MathOp -> Bool
== :: MathOp -> MathOp -> Bool
$c== :: MathOp -> MathOp -> Bool
Eq, Eq MathOp
Eq MathOp
-> (MathOp -> MathOp -> Ordering)
-> (MathOp -> MathOp -> Bool)
-> (MathOp -> MathOp -> Bool)
-> (MathOp -> MathOp -> Bool)
-> (MathOp -> MathOp -> Bool)
-> (MathOp -> MathOp -> MathOp)
-> (MathOp -> MathOp -> MathOp)
-> Ord MathOp
MathOp -> MathOp -> Bool
MathOp -> MathOp -> Ordering
MathOp -> MathOp -> MathOp
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: MathOp -> MathOp -> MathOp
$cmin :: MathOp -> MathOp -> MathOp
max :: MathOp -> MathOp -> MathOp
$cmax :: MathOp -> MathOp -> MathOp
>= :: MathOp -> MathOp -> Bool
$c>= :: MathOp -> MathOp -> Bool
> :: MathOp -> MathOp -> Bool
$c> :: MathOp -> MathOp -> Bool
<= :: MathOp -> MathOp -> Bool
$c<= :: MathOp -> MathOp -> Bool
< :: MathOp -> MathOp -> Bool
$c< :: MathOp -> MathOp -> Bool
compare :: MathOp -> MathOp -> Ordering
$ccompare :: MathOp -> MathOp -> Ordering
$cp1Ord :: Eq MathOp
Ord, Int -> MathOp
MathOp -> Int
MathOp -> [MathOp]
MathOp -> MathOp
MathOp -> MathOp -> [MathOp]
MathOp -> MathOp -> MathOp -> [MathOp]
(MathOp -> MathOp)
-> (MathOp -> MathOp)
-> (Int -> MathOp)
-> (MathOp -> Int)
-> (MathOp -> [MathOp])
-> (MathOp -> MathOp -> [MathOp])
-> (MathOp -> MathOp -> [MathOp])
-> (MathOp -> MathOp -> MathOp -> [MathOp])
-> Enum MathOp
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: MathOp -> MathOp -> MathOp -> [MathOp]
$cenumFromThenTo :: MathOp -> MathOp -> MathOp -> [MathOp]
enumFromTo :: MathOp -> MathOp -> [MathOp]
$cenumFromTo :: MathOp -> MathOp -> [MathOp]
enumFromThen :: MathOp -> MathOp -> [MathOp]
$cenumFromThen :: MathOp -> MathOp -> [MathOp]
enumFrom :: MathOp -> [MathOp]
$cenumFrom :: MathOp -> [MathOp]
fromEnum :: MathOp -> Int
$cfromEnum :: MathOp -> Int
toEnum :: Int -> MathOp
$ctoEnum :: Int -> MathOp
pred :: MathOp -> MathOp
$cpred :: MathOp -> MathOp
succ :: MathOp -> MathOp
$csucc :: MathOp -> MathOp
Enum, MathOp
MathOp -> MathOp -> Bounded MathOp
forall a. a -> a -> Bounded a
maxBound :: MathOp
$cmaxBound :: MathOp
minBound :: MathOp
$cminBound :: MathOp
Bounded)

data SymbolicExprBinOp
  = MathSymbolicExprBinOp MathOp
  | QualSymbolicExprBinOp QualOp
  deriving (Int -> SymbolicExprBinOp -> ShowS
[SymbolicExprBinOp] -> ShowS
SymbolicExprBinOp -> String
(Int -> SymbolicExprBinOp -> ShowS)
-> (SymbolicExprBinOp -> String)
-> ([SymbolicExprBinOp] -> ShowS)
-> Show SymbolicExprBinOp
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SymbolicExprBinOp] -> ShowS
$cshowList :: [SymbolicExprBinOp] -> ShowS
show :: SymbolicExprBinOp -> String
$cshow :: SymbolicExprBinOp -> String
showsPrec :: Int -> SymbolicExprBinOp -> ShowS
$cshowsPrec :: Int -> SymbolicExprBinOp -> ShowS
Show, (forall x. SymbolicExprBinOp -> Rep SymbolicExprBinOp x)
-> (forall x. Rep SymbolicExprBinOp x -> SymbolicExprBinOp)
-> Generic SymbolicExprBinOp
forall x. Rep SymbolicExprBinOp x -> SymbolicExprBinOp
forall x. SymbolicExprBinOp -> Rep SymbolicExprBinOp x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SymbolicExprBinOp x -> SymbolicExprBinOp
$cfrom :: forall x. SymbolicExprBinOp -> Rep SymbolicExprBinOp x
Generic, SymbolicExprBinOp -> SymbolicExprBinOp -> Bool
(SymbolicExprBinOp -> SymbolicExprBinOp -> Bool)
-> (SymbolicExprBinOp -> SymbolicExprBinOp -> Bool)
-> Eq SymbolicExprBinOp
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SymbolicExprBinOp -> SymbolicExprBinOp -> Bool
$c/= :: SymbolicExprBinOp -> SymbolicExprBinOp -> Bool
== :: SymbolicExprBinOp -> SymbolicExprBinOp -> Bool
$c== :: SymbolicExprBinOp -> SymbolicExprBinOp -> Bool
Eq, Eq SymbolicExprBinOp
Eq SymbolicExprBinOp
-> (SymbolicExprBinOp -> SymbolicExprBinOp -> Ordering)
-> (SymbolicExprBinOp -> SymbolicExprBinOp -> Bool)
-> (SymbolicExprBinOp -> SymbolicExprBinOp -> Bool)
-> (SymbolicExprBinOp -> SymbolicExprBinOp -> Bool)
-> (SymbolicExprBinOp -> SymbolicExprBinOp -> Bool)
-> (SymbolicExprBinOp -> SymbolicExprBinOp -> SymbolicExprBinOp)
-> (SymbolicExprBinOp -> SymbolicExprBinOp -> SymbolicExprBinOp)
-> Ord SymbolicExprBinOp
SymbolicExprBinOp -> SymbolicExprBinOp -> Bool
SymbolicExprBinOp -> SymbolicExprBinOp -> Ordering
SymbolicExprBinOp -> SymbolicExprBinOp -> SymbolicExprBinOp
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: SymbolicExprBinOp -> SymbolicExprBinOp -> SymbolicExprBinOp
$cmin :: SymbolicExprBinOp -> SymbolicExprBinOp -> SymbolicExprBinOp
max :: SymbolicExprBinOp -> SymbolicExprBinOp -> SymbolicExprBinOp
$cmax :: SymbolicExprBinOp -> SymbolicExprBinOp -> SymbolicExprBinOp
>= :: SymbolicExprBinOp -> SymbolicExprBinOp -> Bool
$c>= :: SymbolicExprBinOp -> SymbolicExprBinOp -> Bool
> :: SymbolicExprBinOp -> SymbolicExprBinOp -> Bool
$c> :: SymbolicExprBinOp -> SymbolicExprBinOp -> Bool
<= :: SymbolicExprBinOp -> SymbolicExprBinOp -> Bool
$c<= :: SymbolicExprBinOp -> SymbolicExprBinOp -> Bool
< :: SymbolicExprBinOp -> SymbolicExprBinOp -> Bool
$c< :: SymbolicExprBinOp -> SymbolicExprBinOp -> Bool
compare :: SymbolicExprBinOp -> SymbolicExprBinOp -> Ordering
$ccompare :: SymbolicExprBinOp -> SymbolicExprBinOp -> Ordering
$cp1Ord :: Eq SymbolicExprBinOp
Ord)

data VerbalExprBinOp
  = LikeVerbalExprBinOp
  | IlikeVerbalExprBinOp
  | SimilarToVerbalExprBinOp
  deriving (Int -> VerbalExprBinOp -> ShowS
[VerbalExprBinOp] -> ShowS
VerbalExprBinOp -> String
(Int -> VerbalExprBinOp -> ShowS)
-> (VerbalExprBinOp -> String)
-> ([VerbalExprBinOp] -> ShowS)
-> Show VerbalExprBinOp
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VerbalExprBinOp] -> ShowS
$cshowList :: [VerbalExprBinOp] -> ShowS
show :: VerbalExprBinOp -> String
$cshow :: VerbalExprBinOp -> String
showsPrec :: Int -> VerbalExprBinOp -> ShowS
$cshowsPrec :: Int -> VerbalExprBinOp -> ShowS
Show, (forall x. VerbalExprBinOp -> Rep VerbalExprBinOp x)
-> (forall x. Rep VerbalExprBinOp x -> VerbalExprBinOp)
-> Generic VerbalExprBinOp
forall x. Rep VerbalExprBinOp x -> VerbalExprBinOp
forall x. VerbalExprBinOp -> Rep VerbalExprBinOp x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep VerbalExprBinOp x -> VerbalExprBinOp
$cfrom :: forall x. VerbalExprBinOp -> Rep VerbalExprBinOp x
Generic, VerbalExprBinOp -> VerbalExprBinOp -> Bool
(VerbalExprBinOp -> VerbalExprBinOp -> Bool)
-> (VerbalExprBinOp -> VerbalExprBinOp -> Bool)
-> Eq VerbalExprBinOp
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VerbalExprBinOp -> VerbalExprBinOp -> Bool
$c/= :: VerbalExprBinOp -> VerbalExprBinOp -> Bool
== :: VerbalExprBinOp -> VerbalExprBinOp -> Bool
$c== :: VerbalExprBinOp -> VerbalExprBinOp -> Bool
Eq, Eq VerbalExprBinOp
Eq VerbalExprBinOp
-> (VerbalExprBinOp -> VerbalExprBinOp -> Ordering)
-> (VerbalExprBinOp -> VerbalExprBinOp -> Bool)
-> (VerbalExprBinOp -> VerbalExprBinOp -> Bool)
-> (VerbalExprBinOp -> VerbalExprBinOp -> Bool)
-> (VerbalExprBinOp -> VerbalExprBinOp -> Bool)
-> (VerbalExprBinOp -> VerbalExprBinOp -> VerbalExprBinOp)
-> (VerbalExprBinOp -> VerbalExprBinOp -> VerbalExprBinOp)
-> Ord VerbalExprBinOp
VerbalExprBinOp -> VerbalExprBinOp -> Bool
VerbalExprBinOp -> VerbalExprBinOp -> Ordering
VerbalExprBinOp -> VerbalExprBinOp -> VerbalExprBinOp
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: VerbalExprBinOp -> VerbalExprBinOp -> VerbalExprBinOp
$cmin :: VerbalExprBinOp -> VerbalExprBinOp -> VerbalExprBinOp
max :: VerbalExprBinOp -> VerbalExprBinOp -> VerbalExprBinOp
$cmax :: VerbalExprBinOp -> VerbalExprBinOp -> VerbalExprBinOp
>= :: VerbalExprBinOp -> VerbalExprBinOp -> Bool
$c>= :: VerbalExprBinOp -> VerbalExprBinOp -> Bool
> :: VerbalExprBinOp -> VerbalExprBinOp -> Bool
$c> :: VerbalExprBinOp -> VerbalExprBinOp -> Bool
<= :: VerbalExprBinOp -> VerbalExprBinOp -> Bool
$c<= :: VerbalExprBinOp -> VerbalExprBinOp -> Bool
< :: VerbalExprBinOp -> VerbalExprBinOp -> Bool
$c< :: VerbalExprBinOp -> VerbalExprBinOp -> Bool
compare :: VerbalExprBinOp -> VerbalExprBinOp -> Ordering
$ccompare :: VerbalExprBinOp -> VerbalExprBinOp -> Ordering
$cp1Ord :: Eq VerbalExprBinOp
Ord, Int -> VerbalExprBinOp
VerbalExprBinOp -> Int
VerbalExprBinOp -> [VerbalExprBinOp]
VerbalExprBinOp -> VerbalExprBinOp
VerbalExprBinOp -> VerbalExprBinOp -> [VerbalExprBinOp]
VerbalExprBinOp
-> VerbalExprBinOp -> VerbalExprBinOp -> [VerbalExprBinOp]
(VerbalExprBinOp -> VerbalExprBinOp)
-> (VerbalExprBinOp -> VerbalExprBinOp)
-> (Int -> VerbalExprBinOp)
-> (VerbalExprBinOp -> Int)
-> (VerbalExprBinOp -> [VerbalExprBinOp])
-> (VerbalExprBinOp -> VerbalExprBinOp -> [VerbalExprBinOp])
-> (VerbalExprBinOp -> VerbalExprBinOp -> [VerbalExprBinOp])
-> (VerbalExprBinOp
    -> VerbalExprBinOp -> VerbalExprBinOp -> [VerbalExprBinOp])
-> Enum VerbalExprBinOp
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: VerbalExprBinOp
-> VerbalExprBinOp -> VerbalExprBinOp -> [VerbalExprBinOp]
$cenumFromThenTo :: VerbalExprBinOp
-> VerbalExprBinOp -> VerbalExprBinOp -> [VerbalExprBinOp]
enumFromTo :: VerbalExprBinOp -> VerbalExprBinOp -> [VerbalExprBinOp]
$cenumFromTo :: VerbalExprBinOp -> VerbalExprBinOp -> [VerbalExprBinOp]
enumFromThen :: VerbalExprBinOp -> VerbalExprBinOp -> [VerbalExprBinOp]
$cenumFromThen :: VerbalExprBinOp -> VerbalExprBinOp -> [VerbalExprBinOp]
enumFrom :: VerbalExprBinOp -> [VerbalExprBinOp]
$cenumFrom :: VerbalExprBinOp -> [VerbalExprBinOp]
fromEnum :: VerbalExprBinOp -> Int
$cfromEnum :: VerbalExprBinOp -> Int
toEnum :: Int -> VerbalExprBinOp
$ctoEnum :: Int -> VerbalExprBinOp
pred :: VerbalExprBinOp -> VerbalExprBinOp
$cpred :: VerbalExprBinOp -> VerbalExprBinOp
succ :: VerbalExprBinOp -> VerbalExprBinOp
$csucc :: VerbalExprBinOp -> VerbalExprBinOp
Enum, VerbalExprBinOp
VerbalExprBinOp -> VerbalExprBinOp -> Bounded VerbalExprBinOp
forall a. a -> a -> Bounded a
maxBound :: VerbalExprBinOp
$cmaxBound :: VerbalExprBinOp
minBound :: VerbalExprBinOp
$cminBound :: VerbalExprBinOp
Bounded)

-- |
-- ==== References
-- @
--   | a_expr IS NULL_P
--   | a_expr IS TRUE_P
--   | a_expr IS FALSE_P
--   | a_expr IS UNKNOWN
--   | a_expr IS DISTINCT FROM a_expr
--   | a_expr IS OF '(' type_list ')'
--   | a_expr BETWEEN opt_asymmetric b_expr AND a_expr
--   | a_expr BETWEEN SYMMETRIC b_expr AND a_expr
--   | a_expr IN_P in_expr
--   | a_expr IS DOCUMENT_P
-- @
data AExprReversableOp
  = NullAExprReversableOp
  | TrueAExprReversableOp
  | FalseAExprReversableOp
  | UnknownAExprReversableOp
  | DistinctFromAExprReversableOp AExpr
  | OfAExprReversableOp TypeList
  | BetweenAExprReversableOp Bool BExpr AExpr
  | BetweenSymmetricAExprReversableOp BExpr AExpr
  | InAExprReversableOp InExpr
  | DocumentAExprReversableOp
  deriving (Int -> AExprReversableOp -> ShowS
[AExprReversableOp] -> ShowS
AExprReversableOp -> String
(Int -> AExprReversableOp -> ShowS)
-> (AExprReversableOp -> String)
-> ([AExprReversableOp] -> ShowS)
-> Show AExprReversableOp
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AExprReversableOp] -> ShowS
$cshowList :: [AExprReversableOp] -> ShowS
show :: AExprReversableOp -> String
$cshow :: AExprReversableOp -> String
showsPrec :: Int -> AExprReversableOp -> ShowS
$cshowsPrec :: Int -> AExprReversableOp -> ShowS
Show, (forall x. AExprReversableOp -> Rep AExprReversableOp x)
-> (forall x. Rep AExprReversableOp x -> AExprReversableOp)
-> Generic AExprReversableOp
forall x. Rep AExprReversableOp x -> AExprReversableOp
forall x. AExprReversableOp -> Rep AExprReversableOp x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AExprReversableOp x -> AExprReversableOp
$cfrom :: forall x. AExprReversableOp -> Rep AExprReversableOp x
Generic, AExprReversableOp -> AExprReversableOp -> Bool
(AExprReversableOp -> AExprReversableOp -> Bool)
-> (AExprReversableOp -> AExprReversableOp -> Bool)
-> Eq AExprReversableOp
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AExprReversableOp -> AExprReversableOp -> Bool
$c/= :: AExprReversableOp -> AExprReversableOp -> Bool
== :: AExprReversableOp -> AExprReversableOp -> Bool
$c== :: AExprReversableOp -> AExprReversableOp -> Bool
Eq, Eq AExprReversableOp
Eq AExprReversableOp
-> (AExprReversableOp -> AExprReversableOp -> Ordering)
-> (AExprReversableOp -> AExprReversableOp -> Bool)
-> (AExprReversableOp -> AExprReversableOp -> Bool)
-> (AExprReversableOp -> AExprReversableOp -> Bool)
-> (AExprReversableOp -> AExprReversableOp -> Bool)
-> (AExprReversableOp -> AExprReversableOp -> AExprReversableOp)
-> (AExprReversableOp -> AExprReversableOp -> AExprReversableOp)
-> Ord AExprReversableOp
AExprReversableOp -> AExprReversableOp -> Bool
AExprReversableOp -> AExprReversableOp -> Ordering
AExprReversableOp -> AExprReversableOp -> AExprReversableOp
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: AExprReversableOp -> AExprReversableOp -> AExprReversableOp
$cmin :: AExprReversableOp -> AExprReversableOp -> AExprReversableOp
max :: AExprReversableOp -> AExprReversableOp -> AExprReversableOp
$cmax :: AExprReversableOp -> AExprReversableOp -> AExprReversableOp
>= :: AExprReversableOp -> AExprReversableOp -> Bool
$c>= :: AExprReversableOp -> AExprReversableOp -> Bool
> :: AExprReversableOp -> AExprReversableOp -> Bool
$c> :: AExprReversableOp -> AExprReversableOp -> Bool
<= :: AExprReversableOp -> AExprReversableOp -> Bool
$c<= :: AExprReversableOp -> AExprReversableOp -> Bool
< :: AExprReversableOp -> AExprReversableOp -> Bool
$c< :: AExprReversableOp -> AExprReversableOp -> Bool
compare :: AExprReversableOp -> AExprReversableOp -> Ordering
$ccompare :: AExprReversableOp -> AExprReversableOp -> Ordering
$cp1Ord :: Eq AExprReversableOp
Ord)

-- |
-- ==== References
-- @
--   | b_expr IS DISTINCT FROM b_expr
--   | b_expr IS NOT DISTINCT FROM b_expr
--   | b_expr IS OF '(' type_list ')'
--   | b_expr IS NOT OF '(' type_list ')'
--   | b_expr IS DOCUMENT_P
--   | b_expr IS NOT DOCUMENT_P
-- @
data BExprIsOp
  = DistinctFromBExprIsOp BExpr
  | OfBExprIsOp TypeList
  | DocumentBExprIsOp
  deriving (Int -> BExprIsOp -> ShowS
[BExprIsOp] -> ShowS
BExprIsOp -> String
(Int -> BExprIsOp -> ShowS)
-> (BExprIsOp -> String)
-> ([BExprIsOp] -> ShowS)
-> Show BExprIsOp
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BExprIsOp] -> ShowS
$cshowList :: [BExprIsOp] -> ShowS
show :: BExprIsOp -> String
$cshow :: BExprIsOp -> String
showsPrec :: Int -> BExprIsOp -> ShowS
$cshowsPrec :: Int -> BExprIsOp -> ShowS
Show, (forall x. BExprIsOp -> Rep BExprIsOp x)
-> (forall x. Rep BExprIsOp x -> BExprIsOp) -> Generic BExprIsOp
forall x. Rep BExprIsOp x -> BExprIsOp
forall x. BExprIsOp -> Rep BExprIsOp x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep BExprIsOp x -> BExprIsOp
$cfrom :: forall x. BExprIsOp -> Rep BExprIsOp x
Generic, BExprIsOp -> BExprIsOp -> Bool
(BExprIsOp -> BExprIsOp -> Bool)
-> (BExprIsOp -> BExprIsOp -> Bool) -> Eq BExprIsOp
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BExprIsOp -> BExprIsOp -> Bool
$c/= :: BExprIsOp -> BExprIsOp -> Bool
== :: BExprIsOp -> BExprIsOp -> Bool
$c== :: BExprIsOp -> BExprIsOp -> Bool
Eq, Eq BExprIsOp
Eq BExprIsOp
-> (BExprIsOp -> BExprIsOp -> Ordering)
-> (BExprIsOp -> BExprIsOp -> Bool)
-> (BExprIsOp -> BExprIsOp -> Bool)
-> (BExprIsOp -> BExprIsOp -> Bool)
-> (BExprIsOp -> BExprIsOp -> Bool)
-> (BExprIsOp -> BExprIsOp -> BExprIsOp)
-> (BExprIsOp -> BExprIsOp -> BExprIsOp)
-> Ord BExprIsOp
BExprIsOp -> BExprIsOp -> Bool
BExprIsOp -> BExprIsOp -> Ordering
BExprIsOp -> BExprIsOp -> BExprIsOp
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: BExprIsOp -> BExprIsOp -> BExprIsOp
$cmin :: BExprIsOp -> BExprIsOp -> BExprIsOp
max :: BExprIsOp -> BExprIsOp -> BExprIsOp
$cmax :: BExprIsOp -> BExprIsOp -> BExprIsOp
>= :: BExprIsOp -> BExprIsOp -> Bool
$c>= :: BExprIsOp -> BExprIsOp -> Bool
> :: BExprIsOp -> BExprIsOp -> Bool
$c> :: BExprIsOp -> BExprIsOp -> Bool
<= :: BExprIsOp -> BExprIsOp -> Bool
$c<= :: BExprIsOp -> BExprIsOp -> Bool
< :: BExprIsOp -> BExprIsOp -> Bool
$c< :: BExprIsOp -> BExprIsOp -> Bool
compare :: BExprIsOp -> BExprIsOp -> Ordering
$ccompare :: BExprIsOp -> BExprIsOp -> Ordering
$cp1Ord :: Eq BExprIsOp
Ord)

-- |
-- ==== References
-- @
-- subquery_Op:
--   | all_Op
--   | OPERATOR '(' any_operator ')'
--   | LIKE
--   | NOT_LA LIKE
--   | ILIKE
--   | NOT_LA ILIKE
-- @
data SubqueryOp
  = AllSubqueryOp AllOp
  | AnySubqueryOp AnyOperator
  | LikeSubqueryOp Bool
  | IlikeSubqueryOp Bool
  deriving (Int -> SubqueryOp -> ShowS
[SubqueryOp] -> ShowS
SubqueryOp -> String
(Int -> SubqueryOp -> ShowS)
-> (SubqueryOp -> String)
-> ([SubqueryOp] -> ShowS)
-> Show SubqueryOp
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SubqueryOp] -> ShowS
$cshowList :: [SubqueryOp] -> ShowS
show :: SubqueryOp -> String
$cshow :: SubqueryOp -> String
showsPrec :: Int -> SubqueryOp -> ShowS
$cshowsPrec :: Int -> SubqueryOp -> ShowS
Show, (forall x. SubqueryOp -> Rep SubqueryOp x)
-> (forall x. Rep SubqueryOp x -> SubqueryOp) -> Generic SubqueryOp
forall x. Rep SubqueryOp x -> SubqueryOp
forall x. SubqueryOp -> Rep SubqueryOp x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SubqueryOp x -> SubqueryOp
$cfrom :: forall x. SubqueryOp -> Rep SubqueryOp x
Generic, SubqueryOp -> SubqueryOp -> Bool
(SubqueryOp -> SubqueryOp -> Bool)
-> (SubqueryOp -> SubqueryOp -> Bool) -> Eq SubqueryOp
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SubqueryOp -> SubqueryOp -> Bool
$c/= :: SubqueryOp -> SubqueryOp -> Bool
== :: SubqueryOp -> SubqueryOp -> Bool
$c== :: SubqueryOp -> SubqueryOp -> Bool
Eq, Eq SubqueryOp
Eq SubqueryOp
-> (SubqueryOp -> SubqueryOp -> Ordering)
-> (SubqueryOp -> SubqueryOp -> Bool)
-> (SubqueryOp -> SubqueryOp -> Bool)
-> (SubqueryOp -> SubqueryOp -> Bool)
-> (SubqueryOp -> SubqueryOp -> Bool)
-> (SubqueryOp -> SubqueryOp -> SubqueryOp)
-> (SubqueryOp -> SubqueryOp -> SubqueryOp)
-> Ord SubqueryOp
SubqueryOp -> SubqueryOp -> Bool
SubqueryOp -> SubqueryOp -> Ordering
SubqueryOp -> SubqueryOp -> SubqueryOp
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: SubqueryOp -> SubqueryOp -> SubqueryOp
$cmin :: SubqueryOp -> SubqueryOp -> SubqueryOp
max :: SubqueryOp -> SubqueryOp -> SubqueryOp
$cmax :: SubqueryOp -> SubqueryOp -> SubqueryOp
>= :: SubqueryOp -> SubqueryOp -> Bool
$c>= :: SubqueryOp -> SubqueryOp -> Bool
> :: SubqueryOp -> SubqueryOp -> Bool
$c> :: SubqueryOp -> SubqueryOp -> Bool
<= :: SubqueryOp -> SubqueryOp -> Bool
$c<= :: SubqueryOp -> SubqueryOp -> Bool
< :: SubqueryOp -> SubqueryOp -> Bool
$c< :: SubqueryOp -> SubqueryOp -> Bool
compare :: SubqueryOp -> SubqueryOp -> Ordering
$ccompare :: SubqueryOp -> SubqueryOp -> Ordering
$cp1Ord :: Eq SubqueryOp
Ord)

-- * Indexes

-- |
-- ==== References
-- @
-- index_params:
--   | index_elem
--   | index_params ',' index_elem
-- @
type IndexParams = NonEmpty IndexElem

-- |
-- ==== References
-- @
-- index_elem:
--   | ColId opt_collate opt_class opt_asc_desc opt_nulls_order
--   | func_expr_windowless opt_collate opt_class opt_asc_desc opt_nulls_order
--   | '(' a_expr ')' opt_collate opt_class opt_asc_desc opt_nulls_order
-- @
data IndexElem = IndexElem IndexElemDef (Maybe Collate) (Maybe Class) (Maybe AscDesc) (Maybe NullsOrder)
  deriving (Int -> IndexElem -> ShowS
[IndexElem] -> ShowS
IndexElem -> String
(Int -> IndexElem -> ShowS)
-> (IndexElem -> String)
-> ([IndexElem] -> ShowS)
-> Show IndexElem
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [IndexElem] -> ShowS
$cshowList :: [IndexElem] -> ShowS
show :: IndexElem -> String
$cshow :: IndexElem -> String
showsPrec :: Int -> IndexElem -> ShowS
$cshowsPrec :: Int -> IndexElem -> ShowS
Show, (forall x. IndexElem -> Rep IndexElem x)
-> (forall x. Rep IndexElem x -> IndexElem) -> Generic IndexElem
forall x. Rep IndexElem x -> IndexElem
forall x. IndexElem -> Rep IndexElem x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep IndexElem x -> IndexElem
$cfrom :: forall x. IndexElem -> Rep IndexElem x
Generic, IndexElem -> IndexElem -> Bool
(IndexElem -> IndexElem -> Bool)
-> (IndexElem -> IndexElem -> Bool) -> Eq IndexElem
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IndexElem -> IndexElem -> Bool
$c/= :: IndexElem -> IndexElem -> Bool
== :: IndexElem -> IndexElem -> Bool
$c== :: IndexElem -> IndexElem -> Bool
Eq, Eq IndexElem
Eq IndexElem
-> (IndexElem -> IndexElem -> Ordering)
-> (IndexElem -> IndexElem -> Bool)
-> (IndexElem -> IndexElem -> Bool)
-> (IndexElem -> IndexElem -> Bool)
-> (IndexElem -> IndexElem -> Bool)
-> (IndexElem -> IndexElem -> IndexElem)
-> (IndexElem -> IndexElem -> IndexElem)
-> Ord IndexElem
IndexElem -> IndexElem -> Bool
IndexElem -> IndexElem -> Ordering
IndexElem -> IndexElem -> IndexElem
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: IndexElem -> IndexElem -> IndexElem
$cmin :: IndexElem -> IndexElem -> IndexElem
max :: IndexElem -> IndexElem -> IndexElem
$cmax :: IndexElem -> IndexElem -> IndexElem
>= :: IndexElem -> IndexElem -> Bool
$c>= :: IndexElem -> IndexElem -> Bool
> :: IndexElem -> IndexElem -> Bool
$c> :: IndexElem -> IndexElem -> Bool
<= :: IndexElem -> IndexElem -> Bool
$c<= :: IndexElem -> IndexElem -> Bool
< :: IndexElem -> IndexElem -> Bool
$c< :: IndexElem -> IndexElem -> Bool
compare :: IndexElem -> IndexElem -> Ordering
$ccompare :: IndexElem -> IndexElem -> Ordering
$cp1Ord :: Eq IndexElem
Ord)

-- |
-- ==== References
-- @
--   | ColId opt_collate opt_class opt_asc_desc opt_nulls_order
--   | func_expr_windowless opt_collate opt_class opt_asc_desc opt_nulls_order
--   | '(' a_expr ')' opt_collate opt_class opt_asc_desc opt_nulls_order
-- @
data IndexElemDef
  = IdIndexElemDef ColId
  | FuncIndexElemDef FuncExprWindowless
  | ExprIndexElemDef AExpr
  deriving (Int -> IndexElemDef -> ShowS
[IndexElemDef] -> ShowS
IndexElemDef -> String
(Int -> IndexElemDef -> ShowS)
-> (IndexElemDef -> String)
-> ([IndexElemDef] -> ShowS)
-> Show IndexElemDef
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [IndexElemDef] -> ShowS
$cshowList :: [IndexElemDef] -> ShowS
show :: IndexElemDef -> String
$cshow :: IndexElemDef -> String
showsPrec :: Int -> IndexElemDef -> ShowS
$cshowsPrec :: Int -> IndexElemDef -> ShowS
Show, (forall x. IndexElemDef -> Rep IndexElemDef x)
-> (forall x. Rep IndexElemDef x -> IndexElemDef)
-> Generic IndexElemDef
forall x. Rep IndexElemDef x -> IndexElemDef
forall x. IndexElemDef -> Rep IndexElemDef x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep IndexElemDef x -> IndexElemDef
$cfrom :: forall x. IndexElemDef -> Rep IndexElemDef x
Generic, IndexElemDef -> IndexElemDef -> Bool
(IndexElemDef -> IndexElemDef -> Bool)
-> (IndexElemDef -> IndexElemDef -> Bool) -> Eq IndexElemDef
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IndexElemDef -> IndexElemDef -> Bool
$c/= :: IndexElemDef -> IndexElemDef -> Bool
== :: IndexElemDef -> IndexElemDef -> Bool
$c== :: IndexElemDef -> IndexElemDef -> Bool
Eq, Eq IndexElemDef
Eq IndexElemDef
-> (IndexElemDef -> IndexElemDef -> Ordering)
-> (IndexElemDef -> IndexElemDef -> Bool)
-> (IndexElemDef -> IndexElemDef -> Bool)
-> (IndexElemDef -> IndexElemDef -> Bool)
-> (IndexElemDef -> IndexElemDef -> Bool)
-> (IndexElemDef -> IndexElemDef -> IndexElemDef)
-> (IndexElemDef -> IndexElemDef -> IndexElemDef)
-> Ord IndexElemDef
IndexElemDef -> IndexElemDef -> Bool
IndexElemDef -> IndexElemDef -> Ordering
IndexElemDef -> IndexElemDef -> IndexElemDef
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: IndexElemDef -> IndexElemDef -> IndexElemDef
$cmin :: IndexElemDef -> IndexElemDef -> IndexElemDef
max :: IndexElemDef -> IndexElemDef -> IndexElemDef
$cmax :: IndexElemDef -> IndexElemDef -> IndexElemDef
>= :: IndexElemDef -> IndexElemDef -> Bool
$c>= :: IndexElemDef -> IndexElemDef -> Bool
> :: IndexElemDef -> IndexElemDef -> Bool
$c> :: IndexElemDef -> IndexElemDef -> Bool
<= :: IndexElemDef -> IndexElemDef -> Bool
$c<= :: IndexElemDef -> IndexElemDef -> Bool
< :: IndexElemDef -> IndexElemDef -> Bool
$c< :: IndexElemDef -> IndexElemDef -> Bool
compare :: IndexElemDef -> IndexElemDef -> Ordering
$ccompare :: IndexElemDef -> IndexElemDef -> Ordering
$cp1Ord :: Eq IndexElemDef
Ord)

-- |
-- ==== References
-- @
-- opt_collate:
--   | COLLATE any_name
--   | EMPTY
-- @
type Collate = AnyName

-- |
-- ==== References
-- @
-- opt_class:
--   | any_name
--   | EMPTY
-- @
type Class = AnyName

-- |
-- ==== References
-- @
-- opt_asc_desc:
--   | ASC
--   | DESC
--   | EMPTY
-- @
data AscDesc = AscAscDesc | DescAscDesc
  deriving (Int -> AscDesc -> ShowS
[AscDesc] -> ShowS
AscDesc -> String
(Int -> AscDesc -> ShowS)
-> (AscDesc -> String) -> ([AscDesc] -> ShowS) -> Show AscDesc
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AscDesc] -> ShowS
$cshowList :: [AscDesc] -> ShowS
show :: AscDesc -> String
$cshow :: AscDesc -> String
showsPrec :: Int -> AscDesc -> ShowS
$cshowsPrec :: Int -> AscDesc -> ShowS
Show, (forall x. AscDesc -> Rep AscDesc x)
-> (forall x. Rep AscDesc x -> AscDesc) -> Generic AscDesc
forall x. Rep AscDesc x -> AscDesc
forall x. AscDesc -> Rep AscDesc x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AscDesc x -> AscDesc
$cfrom :: forall x. AscDesc -> Rep AscDesc x
Generic, AscDesc -> AscDesc -> Bool
(AscDesc -> AscDesc -> Bool)
-> (AscDesc -> AscDesc -> Bool) -> Eq AscDesc
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AscDesc -> AscDesc -> Bool
$c/= :: AscDesc -> AscDesc -> Bool
== :: AscDesc -> AscDesc -> Bool
$c== :: AscDesc -> AscDesc -> Bool
Eq, Eq AscDesc
Eq AscDesc
-> (AscDesc -> AscDesc -> Ordering)
-> (AscDesc -> AscDesc -> Bool)
-> (AscDesc -> AscDesc -> Bool)
-> (AscDesc -> AscDesc -> Bool)
-> (AscDesc -> AscDesc -> Bool)
-> (AscDesc -> AscDesc -> AscDesc)
-> (AscDesc -> AscDesc -> AscDesc)
-> Ord AscDesc
AscDesc -> AscDesc -> Bool
AscDesc -> AscDesc -> Ordering
AscDesc -> AscDesc -> AscDesc
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: AscDesc -> AscDesc -> AscDesc
$cmin :: AscDesc -> AscDesc -> AscDesc
max :: AscDesc -> AscDesc -> AscDesc
$cmax :: AscDesc -> AscDesc -> AscDesc
>= :: AscDesc -> AscDesc -> Bool
$c>= :: AscDesc -> AscDesc -> Bool
> :: AscDesc -> AscDesc -> Bool
$c> :: AscDesc -> AscDesc -> Bool
<= :: AscDesc -> AscDesc -> Bool
$c<= :: AscDesc -> AscDesc -> Bool
< :: AscDesc -> AscDesc -> Bool
$c< :: AscDesc -> AscDesc -> Bool
compare :: AscDesc -> AscDesc -> Ordering
$ccompare :: AscDesc -> AscDesc -> Ordering
$cp1Ord :: Eq AscDesc
Ord, Int -> AscDesc
AscDesc -> Int
AscDesc -> [AscDesc]
AscDesc -> AscDesc
AscDesc -> AscDesc -> [AscDesc]
AscDesc -> AscDesc -> AscDesc -> [AscDesc]
(AscDesc -> AscDesc)
-> (AscDesc -> AscDesc)
-> (Int -> AscDesc)
-> (AscDesc -> Int)
-> (AscDesc -> [AscDesc])
-> (AscDesc -> AscDesc -> [AscDesc])
-> (AscDesc -> AscDesc -> [AscDesc])
-> (AscDesc -> AscDesc -> AscDesc -> [AscDesc])
-> Enum AscDesc
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: AscDesc -> AscDesc -> AscDesc -> [AscDesc]
$cenumFromThenTo :: AscDesc -> AscDesc -> AscDesc -> [AscDesc]
enumFromTo :: AscDesc -> AscDesc -> [AscDesc]
$cenumFromTo :: AscDesc -> AscDesc -> [AscDesc]
enumFromThen :: AscDesc -> AscDesc -> [AscDesc]
$cenumFromThen :: AscDesc -> AscDesc -> [AscDesc]
enumFrom :: AscDesc -> [AscDesc]
$cenumFrom :: AscDesc -> [AscDesc]
fromEnum :: AscDesc -> Int
$cfromEnum :: AscDesc -> Int
toEnum :: Int -> AscDesc
$ctoEnum :: Int -> AscDesc
pred :: AscDesc -> AscDesc
$cpred :: AscDesc -> AscDesc
succ :: AscDesc -> AscDesc
$csucc :: AscDesc -> AscDesc
Enum, AscDesc
AscDesc -> AscDesc -> Bounded AscDesc
forall a. a -> a -> Bounded a
maxBound :: AscDesc
$cmaxBound :: AscDesc
minBound :: AscDesc
$cminBound :: AscDesc
Bounded)

-- |
-- ==== References
-- @
-- opt_nulls_order:
--   | NULLS_LA FIRST_P
--   | NULLS_LA LAST_P
--   | EMPTY
-- @
data NullsOrder = FirstNullsOrder | LastNullsOrder
  deriving (Int -> NullsOrder -> ShowS
[NullsOrder] -> ShowS
NullsOrder -> String
(Int -> NullsOrder -> ShowS)
-> (NullsOrder -> String)
-> ([NullsOrder] -> ShowS)
-> Show NullsOrder
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NullsOrder] -> ShowS
$cshowList :: [NullsOrder] -> ShowS
show :: NullsOrder -> String
$cshow :: NullsOrder -> String
showsPrec :: Int -> NullsOrder -> ShowS
$cshowsPrec :: Int -> NullsOrder -> ShowS
Show, (forall x. NullsOrder -> Rep NullsOrder x)
-> (forall x. Rep NullsOrder x -> NullsOrder) -> Generic NullsOrder
forall x. Rep NullsOrder x -> NullsOrder
forall x. NullsOrder -> Rep NullsOrder x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep NullsOrder x -> NullsOrder
$cfrom :: forall x. NullsOrder -> Rep NullsOrder x
Generic, NullsOrder -> NullsOrder -> Bool
(NullsOrder -> NullsOrder -> Bool)
-> (NullsOrder -> NullsOrder -> Bool) -> Eq NullsOrder
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NullsOrder -> NullsOrder -> Bool
$c/= :: NullsOrder -> NullsOrder -> Bool
== :: NullsOrder -> NullsOrder -> Bool
$c== :: NullsOrder -> NullsOrder -> Bool
Eq, Eq NullsOrder
Eq NullsOrder
-> (NullsOrder -> NullsOrder -> Ordering)
-> (NullsOrder -> NullsOrder -> Bool)
-> (NullsOrder -> NullsOrder -> Bool)
-> (NullsOrder -> NullsOrder -> Bool)
-> (NullsOrder -> NullsOrder -> Bool)
-> (NullsOrder -> NullsOrder -> NullsOrder)
-> (NullsOrder -> NullsOrder -> NullsOrder)
-> Ord NullsOrder
NullsOrder -> NullsOrder -> Bool
NullsOrder -> NullsOrder -> Ordering
NullsOrder -> NullsOrder -> NullsOrder
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: NullsOrder -> NullsOrder -> NullsOrder
$cmin :: NullsOrder -> NullsOrder -> NullsOrder
max :: NullsOrder -> NullsOrder -> NullsOrder
$cmax :: NullsOrder -> NullsOrder -> NullsOrder
>= :: NullsOrder -> NullsOrder -> Bool
$c>= :: NullsOrder -> NullsOrder -> Bool
> :: NullsOrder -> NullsOrder -> Bool
$c> :: NullsOrder -> NullsOrder -> Bool
<= :: NullsOrder -> NullsOrder -> Bool
$c<= :: NullsOrder -> NullsOrder -> Bool
< :: NullsOrder -> NullsOrder -> Bool
$c< :: NullsOrder -> NullsOrder -> Bool
compare :: NullsOrder -> NullsOrder -> Ordering
$ccompare :: NullsOrder -> NullsOrder -> Ordering
$cp1Ord :: Eq NullsOrder
Ord, Int -> NullsOrder
NullsOrder -> Int
NullsOrder -> [NullsOrder]
NullsOrder -> NullsOrder
NullsOrder -> NullsOrder -> [NullsOrder]
NullsOrder -> NullsOrder -> NullsOrder -> [NullsOrder]
(NullsOrder -> NullsOrder)
-> (NullsOrder -> NullsOrder)
-> (Int -> NullsOrder)
-> (NullsOrder -> Int)
-> (NullsOrder -> [NullsOrder])
-> (NullsOrder -> NullsOrder -> [NullsOrder])
-> (NullsOrder -> NullsOrder -> [NullsOrder])
-> (NullsOrder -> NullsOrder -> NullsOrder -> [NullsOrder])
-> Enum NullsOrder
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: NullsOrder -> NullsOrder -> NullsOrder -> [NullsOrder]
$cenumFromThenTo :: NullsOrder -> NullsOrder -> NullsOrder -> [NullsOrder]
enumFromTo :: NullsOrder -> NullsOrder -> [NullsOrder]
$cenumFromTo :: NullsOrder -> NullsOrder -> [NullsOrder]
enumFromThen :: NullsOrder -> NullsOrder -> [NullsOrder]
$cenumFromThen :: NullsOrder -> NullsOrder -> [NullsOrder]
enumFrom :: NullsOrder -> [NullsOrder]
$cenumFrom :: NullsOrder -> [NullsOrder]
fromEnum :: NullsOrder -> Int
$cfromEnum :: NullsOrder -> Int
toEnum :: Int -> NullsOrder
$ctoEnum :: Int -> NullsOrder
pred :: NullsOrder -> NullsOrder
$cpred :: NullsOrder -> NullsOrder
succ :: NullsOrder -> NullsOrder
$csucc :: NullsOrder -> NullsOrder
Enum, NullsOrder
NullsOrder -> NullsOrder -> Bounded NullsOrder
forall a. a -> a -> Bounded a
maxBound :: NullsOrder
$cmaxBound :: NullsOrder
minBound :: NullsOrder
$cminBound :: NullsOrder
Bounded)