simple-sql-parser-0.4.0: A parser for SQL queries

Safe HaskellSafe-Inferred

Language.SQL.SimpleSQL.Syntax

Contents

Description

The AST for SQL queries.

Synopsis

Value expressions

data ValueExpr Source

Represents a value expression. This is used for the expressions in select lists. It is also used for expressions in where, group by, having, order by and so on.

Constructors

NumLit String

a numeric literal optional decimal point, e+- integral exponent, e.g

  • 10
  • 10.
  • .1
  • 10.1
  • 1e5
  • 12.34e-6
StringLit String

string literal, currently only basic strings between single quotes with a single quote escaped using ''

IntervalLit

text of interval literal, units of interval precision, e.g. interval 3 days (3)

Fields

ilSign :: Maybe Bool

true if + used, false if - used

ilLiteral :: String

literal text

ilFrom :: IntervalTypeField
 
ilTo :: Maybe IntervalTypeField
 
Iden [Name]

identifier with parts separated by dots

Star

star, as in select *, t.*, count(*)

App [Name] [ValueExpr]

function application (anything that looks like c style function application syntactically)

AggregateApp

aggregate application, which adds distinct or all, and order by, to regular function application

Fields

aggName :: [Name]

aggregate function name

aggregate function name

aggDistinct :: SetQuantifier

distinct

aggArgs :: [ValueExpr]

args

args

aggOrderBy :: [SortSpec]

order by

aggFilter :: Maybe ValueExpr

filter

AggregateAppGroup

aggregates with within group

Fields

aggName :: [Name]

aggregate function name

aggregate function name

aggArgs :: [ValueExpr]

args

args

aggGroup :: [SortSpec]

within group

WindowApp

window application, which adds over (partition by a order by b) to regular function application. Explicit frames are not currently supported

Fields

wnName :: [Name]

window function name

wnArgs :: [ValueExpr]

args

wnPartition :: [ValueExpr]

partition by

wnOrderBy :: [SortSpec]

order by

wnFrame :: Maybe Frame

frame clause

BinOp ValueExpr [Name] ValueExpr

Infix binary operators. This is used for symbol operators (a + b), keyword operators (a and b) and multiple keyword operators (a is similar to b)

PrefixOp [Name] ValueExpr

Prefix unary operators. This is used for symbol operators, keyword operators and multiple keyword operators.

PostfixOp [Name] ValueExpr

Postfix unary operators. This is used for symbol operators, keyword operators and multiple keyword operators.

SpecialOp [Name] [ValueExpr]

Used for ternary, mixfix and other non orthodox operators. Currently used for row constructors, and for between.

SpecialOpK [Name] (Maybe ValueExpr) [(String, ValueExpr)]

Used for the operators which look like functions except the arguments are separated by keywords instead of commas. The maybe is for the first unnamed argument if it is present, and the list is for the keyword argument pairs.

Case

case expression. both flavours supported

Fields

caseTest :: Maybe ValueExpr

test value

caseWhens :: [([ValueExpr], ValueExpr)]

when branches

caseElse :: Maybe ValueExpr

else value

Parens ValueExpr 
Cast ValueExpr TypeName

cast(a as typename)

TypedLit TypeName String

prefix 'typed literal', e.g. int '42'

SubQueryExpr SubQueryExprType QueryExpr

exists, all, any, some subqueries

In Bool ValueExpr InPredValue

in list literal and in subquery, if the bool is false it means not in was used ('a not in (1,2)')

Parameter

Represents a ? in a parameterized query

HostParameter String (Maybe String)

represents a host parameter, e.g. :a. The Maybe String is for the indicator, e.g. :var indicator :nl

QuantifiedComparison ValueExpr [Name] CompPredQuantifier QueryExpr 
Match ValueExpr Bool QueryExpr 
Array ValueExpr [ValueExpr]

represents an array access expression, or an array ctor e.g. a[3]. The first valueExpr is the array, the second is the subscripts/ctor args

ArrayCtor QueryExpr

this is used for the query expression version of array constructors, e.g. array(select * from t)

CSStringLit String String 
Escape ValueExpr Char 
UEscape ValueExpr Char 
Collate ValueExpr [Name] 
MultisetBinOp ValueExpr CombineOp SetQuantifier ValueExpr 
MultisetCtor [ValueExpr] 
MultisetQueryCtor QueryExpr 
NextValueFor [Name] 

data Name Source

Represents an identifier name, which can be quoted or unquoted.

data SetQuantifier Source

Represents the Distinct or All keywords, which can be used before a select list, in an aggregate/window function application, or in a query expression set operator.

Constructors

SQDefault 
Distinct 
All 

data SortSpec Source

Represents one field in an order by list.

data Direction Source

The direction for a column in order by.

Constructors

DirDefault 
Asc 
Desc 

data NullsOrder Source

Represents 'nulls first' or 'nulls last' in an order by clause.

data InPredValue Source

Used for 'expr in (value expression list)', and 'expr in (subquery)' syntax.

data SubQueryExprType Source

A subquery in a value expression.

Constructors

SqExists

exists (query expr)

SqUnique

unique (query expr)

SqSq

a scalar subquery

data Frame Source

Represents the frame clause of a window this can be [range | rows] frame_start or [range | rows] between frame_start and frame_end

data FrameRows Source

Represents whether a window frame clause is over rows or ranges.

Constructors

FrameRows 
FrameRange 

Query expressions

data QueryExpr Source

Represents a query expression, which can be:

  • a regular select;
  • a set operator (union, except, intersect);
  • a common table expression (with);
  • a table value constructor (values (1,2),(3,4)); or
  • an explicit table (table t).

makeSelect :: QueryExprSource

Helper/'default' value for query exprs to make creating query expr values a little easier. It is defined like this:

 makeSelect :: QueryExpr
 makeSelect = Select {qeSetQuantifier = SQDefault
                     ,qeSelectList = []
                     ,qeFrom = []
                     ,qeWhere = Nothing
                     ,qeGroupBy = []
                     ,qeHaving = Nothing
                     ,qeOrderBy = []
                     ,qeOffset = Nothing
                     ,qeFetchFirst = Nothing}

data CombineOp Source

Query expression set operators.

Constructors

Union 
Except 
Intersect 

data Corresponding Source

Corresponding, an option for the set operators.

data Alias Source

Represents an alias for a table valued expression, used in with queries and in from alias, e.g. select a from t u, select a from t u(b), with a(c) as select 1, select * from a.

Constructors

Alias Name (Maybe [Name]) 

From

data TableRef Source

Represents a entry in the csv of tables in the from clause.

Constructors

TRSimple [Name]

from t / from s.t

TRJoin TableRef Bool JoinType TableRef (Maybe JoinCondition)

from a join b, the bool is true if natural was used

TRParens TableRef

from (a)

TRAlias TableRef Alias

from a as b(c,d)

TRQueryExpr QueryExpr

from (query expr)

TRFunction [Name] [ValueExpr]

from function(args)

TRLateral TableRef

from lateral t

data JoinType Source

The type of a join.

Constructors

JInner 
JLeft 
JRight 
JFull 
JCross 

data JoinCondition Source

The join condition.

Constructors

JoinOn ValueExpr

on expr

JoinUsing [Name]

using (column list)