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

PostgresqlSyntax.Parsing

Description

Our parsing strategy is to port the original Postgres parser as closely as possible.

We're using the gram.y Postgres source file, which is the closest thing we have to a Postgres syntax spec. Here's a link to it: https://github.com/postgres/postgres/blob/master/src/backend/parser/gram.y.

Here's the essence of how the original parser is implemented, citing from PostgreSQL Wiki:

scan.l defines the lexer, i.e. the algorithm that splits a string (containing an SQL statement) into a stream of tokens. A token is usually a single word (i.e., doesn't contain spaces but is delimited by spaces), but can also be a whole single or double-quoted string for example. The lexer is basically defined in terms of regular expressions which describe the different token types.

gram.y defines the grammar (the syntactical structure) of SQL statements, using the tokens generated by the lexer as basic building blocks. The grammar is defined in BNF notation. BNF resembles regular expressions but works on the level of tokens, not characters. Also, patterns (called rules or productions in BNF) are named, and may be recursive, i.e. use themselves as sub-patterns.

Synopsis

Documentation

>>> testParser parser = either putStr print . run parser

Executors

Helpers

inParensWithLabel :: (label -> content -> result) -> Parser label -> Parser content -> Parser result Source #

inParensWithClause :: Parser clause -> Parser content -> Parser content Source #

quotedString :: Char -> Parser Text Source #

>>> testParser (quotedString '\'') "'abc''d'"
"abc'd"

PreparableStmt

Call

Insert

Update

Delete

Select

selectStmt :: HeadedParsec Void Text SelectStmt Source #

>>> test = testParser selectStmt
>>> test "select id from as"
...
  |
1 | select id from as
  |                  ^
Reserved keyword "as" used as an identifier. If that's what you intend, you have to wrap it in double quotes.

simpleSelectNoParens :: HeadedParsec Void Text SelectNoParens Source #

The one that doesn't start with "WITH".

References

  | 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

targetEl :: HeadedParsec Void Text TargetEl Source #

>>> testParser targetEl "a.b as c"
AliasedExprTargetEl (CExprAExpr (ColumnrefCExpr (Columnref (UnquotedIdent "a") (Just (AttrNameIndirectionEl (UnquotedIdent "b") :| []))))) (UnquotedIdent "c")

Into clause details

optTempTableName :: HeadedParsec Void Text IntoClause Source #

References

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

Group by details

Window clause details

windowSpecification :: HeadedParsec Void Text WindowSpecification Source #

References

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

frameClause :: HeadedParsec Void Text FrameClause Source #

References

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

frameBound :: HeadedParsec Void Text FrameBound Source #

References

  |  UNBOUNDED PRECEDING
  |  UNBOUNDED FOLLOWING
  |  CURRENT_P ROW
  |  a_expr PRECEDING
  |  a_expr FOLLOWING

Table refs

tableRef :: HeadedParsec Void Text TableRef Source #

>>> testParser tableRef "a left join b on (a.i = b.i)"
JoinTableRef (MethJoinedTable (QualJoinMeth...

inParensJoinedTable :: HeadedParsec Void Text JoinedTable Source #

References

  | '(' joined_table ')'

trailingJoinedTable :: TableRef -> HeadedParsec Void Text JoinedTable Source #

References

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

Where

Sorting

Expressions

aExpr :: Parser AExpr Source #

Notice that the tree constructed by this parser does not reflect the precedence order of Postgres. For the purposes of this library it simply doesn't matter, so we're not bothering with that.

Composite on the right:

>>> testParser aExpr "a = b :: int4"
SymbolicBinOpAExpr (CExprAExpr (ColumnrefCExpr (Columnref (UnquotedIdent "a") Nothing))) (MathSymbolicExprBinOp EqualsMathOp) (TypecastAExpr (CExprAExpr (ColumnrefCExpr (Columnref (UnquotedIdent "b") Nothing))) (Typename False (GenericTypeSimpleTypename (GenericType (UnquotedIdent "int4") Nothing Nothing)) False Nothing))

Composite on the left:

>>> testParser aExpr "a = b :: int4 and c"
SymbolicBinOpAExpr (CExprAExpr (ColumnrefCExpr (Columnref (UnquotedIdent "a") Nothing))) (MathSymbolicExprBinOp EqualsMathOp) (AndAExpr (TypecastAExpr (CExprAExpr (ColumnrefCExpr (Columnref (UnquotedIdent "b") Nothing))) (Typename False (GenericTypeSimpleTypename (GenericType (UnquotedIdent "int4") Nothing Nothing)) False Nothing)) (CExprAExpr (ColumnrefCExpr (Columnref (UnquotedIdent "c") Nothing))))

plusedExpr :: (Token strm ~ Char, Stream strm, Ord err) => HeadedParsec err strm b -> HeadedParsec err strm b Source #

minusedExpr :: (Token strm ~ Char, Stream strm, Ord err) => HeadedParsec err strm b -> HeadedParsec err strm b Source #

funcArgExpr :: HeadedParsec Void Text FuncArgExpr Source #

References

func_arg_expr:
  | a_expr
  | param_name COLON_EQUALS a_expr
  | param_name EQUALS_GREATER a_expr
param_name:
  | type_function_name

Ops

op :: (Tokens strm ~ Text, Token strm ~ Char, Ord err, Stream strm) => HeadedParsec err strm Text Source #

allOp :: (Tokens strm ~ Text, Token strm ~ Char, Ord err, Stream strm, FoldCase (Tokens strm), IsString (Tokens strm)) => HeadedParsec err strm AllOp Source #

mathOp :: (Token strm ~ Char, Stream strm, FoldCase (Tokens strm), IsString (Tokens strm), Ord err) => HeadedParsec err strm MathOp Source #

Constants

aexprConst :: HeadedParsec Void Text AexprConst Source #

>>> testParser aexprConst "32948023849023"
IAexprConst 32948023849023
>>> testParser aexprConst "'abc''de'"
SAexprConst "abc'de"
>>> testParser aexprConst "23.43234"
FAexprConst 23.43234
>>> testParser aexprConst "32423423.324324872"
FAexprConst 3.2423423324324872e7
>>> testParser aexprConst "NULL"
NullAexprConst

References

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

iconstOrFconst :: (Token strm ~ Char, Stream strm, RealFloat a, Integral a, Ord err) => HeadedParsec err strm (Either a a) Source #

iconst :: (Token strm ~ Char, Stream strm, Integral decimal, Ord err) => HeadedParsec err strm decimal Source #

fconst :: (Token strm ~ Char, Stream strm, RealFloat float, Ord err) => HeadedParsec err strm float Source #

constDatetime :: HeadedParsec Void Text ConstDatetime Source #

References

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

Clauses

selectLimit :: HeadedParsec Void Text SelectLimit Source #

References

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

limitClause :: HeadedParsec Void Text LimitClause Source #

References

limit_clause:
  | LIMIT select_limit_value
  | LIMIT select_limit_value ',' select_offset_value
  | FETCH first_or_next select_fetch_first_value row_or_rows ONLY
  | FETCH first_or_next row_or_rows ONLY

selectLimitValue :: HeadedParsec Void Text SelectLimitValue Source #

References

select_limit_value:
  | a_expr
  | ALL

plusOrMinus :: (Token strm ~ Char, Stream strm, Ord err) => HeadedParsec err strm Bool Source #

For Locking

forLockingClause :: HeadedParsec Void Text ForLockingClause Source #

References

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

forLockingItem :: HeadedParsec Void Text ForLockingItem Source #

References

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

forLockingStrength :: (Token s ~ Char, Tokens s ~ Text, Ord e, Stream s, FoldCase (Tokens s)) => HeadedParsec e s ForLockingStrength Source #

References

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

References & Names

ident :: HeadedParsec Void Text Ident Source #

References

ident_start   [A-Za-z200-377_]
ident_cont    [A-Za-z200-377_0-9$]
identifier    {ident_start}{ident_cont}*

colId :: HeadedParsec Void Text Ident Source #

References

ColId:
  |  IDENT
  |  unreserved_keyword
  |  col_name_keyword

colLabel :: HeadedParsec Void Text Ident Source #

References

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

qualifiedName :: HeadedParsec Void Text QualifiedName Source #

>>> testParser qualifiedName "a.b"
IndirectedQualifiedName (UnquotedIdent "a") (AttrNameIndirectionEl (UnquotedIdent "b") :| [])
>>> testParser qualifiedName "a.-"
...
expecting '*', column label, or white space

References

qualified_name:
  | ColId
  | ColId indirection

funcName :: Parser FuncName Source #

References

func_name:
  | type_function_name
  | ColId indirection

typeFunctionName :: HeadedParsec Void Text Ident Source #

References

type_function_name:
  | IDENT
  | unreserved_keyword
  | type_func_name_keyword

indirection :: HeadedParsec Void Text Indirection Source #

References

indirection:
  | indirection_el
  | indirection indirection_el

indirectionEl :: HeadedParsec Void Text IndirectionEl Source #

References

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

attrName :: HeadedParsec Void Text Ident Source #

References

attr_name:
  | ColLabel

keywordNameFromSet :: (Tokens strm ~ Text, Token strm ~ Char, Stream strm, Ord err) => HashSet Text -> HeadedParsec err strm Ident Source #

keywordNameByPredicate :: (Tokens strm ~ Text, Token strm ~ Char, Stream strm, Ord err) => (Text -> Bool) -> HeadedParsec err strm Ident Source #

keyword :: (Tokens s ~ Text, Token s ~ Char, Ord e, Stream s) => Text -> HeadedParsec e s Text Source #

Expected keyword

keyphrase :: (Token s ~ Char, Tokens s ~ Text, Ord e, Stream s, FoldCase (Tokens s)) => Text -> HeadedParsec e s Text Source #

Consume a keyphrase, ignoring case and types of spaces between words.

Typename

Indexes