postgresql-syntax-0.3.0.2: PostgreSQL AST parsing and rendering

Safe HaskellNone
LanguageHaskell2010

PostgresqlSyntax.Parsing

Contents

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.compostgrespostgresblobmastersrcbackendparser/gram.y.

Here's the essence of how the original parser is implemented, citing from [PostgreSQL Wiki](https:/wiki.postgresql.orgwiki/Developer_FAQ):

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

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".

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

Group by details

Window clause details

Table refs

tableRef :: HeadedParsec Void Text TableRef Source #

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

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 :: (Stream strm, Ord err, Token strm ~# Char) => HeadedParsec err strm b -> HeadedParsec err strm b Source #

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

Ops

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

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

mathOp :: (Stream strm, FoldCase (Tokens strm), IsString (Tokens strm), Ord err, Token strm ~# Char) => 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

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

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

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

Clauses

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

For Locking

References & Names

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

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

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

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

Expected keyword

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

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

Typename

Indexes