language-sqlite-1.1: Full parser and generator for SQL as implemented by SQLite3

Language.SQL.SQLite

Contents

Synopsis

Parsing

Building blocks

class ShowTokens a whereSource

A class implemented by every node of the AST; converts the node and its children into a list of tokens which correspond to the SQL representation of the node.

Methods

showTokens :: a -> [Token]Source

Instances

ShowTokens DoublyQualifiedIdentifier 
ShowTokens SinglyQualifiedIdentifier 
ShowTokens UnqualifiedIdentifier 
ShowTokens TriggerStatement 
ShowTokens ExplainableStatement 
ShowTokens AnyStatement 
ShowTokens StatementList 
ShowTokens MaybeReleaseSavepoint 
ShowTokens MaybeSavepoint 
ShowTokens MaybeDatabase 
ShowTokens MaybeTransactionType 
ShowTokens MaybeTransaction 
ShowTokens CommitHead 
ShowTokens MaybeInitialDeferralStatus 
ShowTokens MaybeForeignKeyClauseDeferrablePart 
ShowTokens ForeignKeyClauseActionPart 
ShowTokens ForeignKeyClauseActionOrMatchPart 
ShowTokens ForeignKeyClause 
ShowTokens ConflictClause 
ShowTokens WhenClause 
ShowTokens LimitClause 
ShowTokens OrderClause 
ShowTokens GroupClause 
ShowTokens WhereClause 
ShowTokens FromClause 
ShowTokens MaybeIndexedBy 
ShowTokens JoinConstraint 
ShowTokens JoinOperation 
ShowTokens SingleSource 
ShowTokens JoinSource 
ShowTokens ResultColumn 
ShowTokens SelectCore 
ShowTokens CompoundOperator 
ShowTokens MaybeAs 
ShowTokens MaybeHaving 
ShowTokens Distinctness 
ShowTokens UpdateHead 
ShowTokens InsertBody 
ShowTokens InsertHead 
ShowTokens CreateTableBody 
ShowTokens PragmaValue 
ShowTokens PragmaBody 
ShowTokens OrderingTerm 
ShowTokens QualifiedTableName 
ShowTokens ModuleArgument 
ShowTokens TriggerCondition 
ShowTokens TriggerTime 
ShowTokens MaybeConstraintName 
ShowTokens TableConstraint 
ShowTokens ColumnConstraint 
ShowTokens IndexedColumn 
ShowTokens DefaultValue 
ShowTokens ColumnDefinition 
ShowTokens AlterTableBody 
ShowTokens MaybeColumn 
ShowTokens MaybeSign 
ShowTokens MaybeAutoincrement 
ShowTokens MaybeAscDesc 
ShowTokens MaybeCollation 
ShowTokens MaybeTemporary 
ShowTokens MaybeForEachRow 
ShowTokens MaybeIfExists 
ShowTokens MaybeIfNotExists 
ShowTokens MaybeUnique 
ShowTokens Expression 
ShowTokens Else 
ShowTokens CasePair 
ShowTokens MaybeSwitchExpression 
ShowTokens Escape 
ShowTokens LikeType 
ShowTokens TypeSizeField 
ShowTokens MaybeTypeSize 
ShowTokens MaybeType 
ShowTokens MaybeTypeName 
ShowTokens TypeAffinity 
ShowTokens Type 
ShowTokens (Statement l t v w) 

data OneOrMore a Source

A class with hidden implementation so as to enforce the constraint that it is a nonempty homogeneous list of items.

Instances

Eq a => Eq (OneOrMore a) 
Show a => Show (OneOrMore a) 

mkOneOrMore :: [a] -> Maybe (OneOrMore a)Source

The constructor for OneOrMore a. Returns Nothing if the list it's given is empty, or Just OneOrMore a if it is not.

fromOneOrMore :: OneOrMore a -> [a]Source

The accessor for OneOrMore a. Returns [a].

data NonnegativeDouble Source

A class with hidden implementation so as to enforce the constraint that it is a nonnegative double.

mkNonnegativeDouble :: Double -> Maybe NonnegativeDoubleSource

The constructor for NonnegativeDouble. Returns Nothing if the double it's given is negative, or Just NonnegativeDouble if it is not.

fromNonnegativeDouble :: NonnegativeDouble -> DoubleSource

The accessor for NonnegativeDouble. Returns a double.

class Identifier a whereSource

A class implemented by all identifiers regardless of how many levels of qualification they allow.

Methods

identifierProperName :: a -> StringSource

Returns the final, proper name component of an identifier. In an identifier which names a column, this is the column name. In an identifier which names a table, this is the table name. All identifiers have this component, so it is a String and not a Maybe.

identifierParentName :: a -> Maybe StringSource

Returns the parent name component of an identifier, if it exists. In an identifier which names a column, this is the table name. In an identifier which names a table or other database-level object, this is the database name.

identifierGrandparentName :: a -> Maybe StringSource

Returns the grandparent name component of an identifier, if it exists. In an identifier which names a column, this is the database name.

toDoublyQualifiedIdentifier :: Identifier a => a -> DoublyQualifiedIdentifierSource

Converts an identifier to be doubly-qualified. This does not actually synthesize any missing components, merely provides Nothing for them.

data UnqualifiedIdentifier Source

An identifier which does not allow any levels of qualification. This is typically a database name.

data SinglyQualifiedIdentifier Source

An identifier which allows a single level of qualification. This is typically the name of a table or other database-level object.

data Token Source

Not an AST node but a token which corresponds to a primitive of SQL syntax. Has an instance of Show which prints a list of them as syntactically-valid SQL with no line wrapping.

Constructors

EndOfInputToken 
Identifier String 
LiteralInteger Word64 
LiteralFloat NonnegativeDouble 
LiteralString String 
LiteralBlob ByteString 
Variable 
VariableN Word64 
VariableNamed String 
ModuleArgumentToken String 
PunctuationBarBar 
PunctuationStar 
PunctuationSlash 
PunctuationPercent 
PunctuationPlus 
PunctuationMinus 
PunctuationLessLess 
PunctuationGreaterGreater 
PunctuationAmpersand 
PunctuationBar 
PunctuationLess 
PunctuationLessEquals 
PunctuationGreater 
PunctuationGreaterEquals 
PunctuationEquals 
PunctuationEqualsEquals 
PunctuationBangEquals 
PunctuationLessGreater 
PunctuationTilde 
PunctuationLeftParenthesis 
PunctuationRightParenthesis 
PunctuationComma 
PunctuationDot 
PunctuationSemicolon 
KeywordAbort 
KeywordAction 
KeywordAdd 
KeywordAfter 
KeywordAll 
KeywordAlter 
KeywordAnalyze 
KeywordAnd 
KeywordAs 
KeywordAsc 
KeywordAttach 
KeywordAutoincrement 
KeywordBefore 
KeywordBegin 
KeywordBetween 
KeywordBy 
KeywordCascade 
KeywordCase 
KeywordCast 
KeywordCheck 
KeywordCollate 
KeywordColumn 
KeywordCommit 
KeywordConflict 
KeywordConstraint 
KeywordCreate 
KeywordCross 
KeywordCurrentDate 
KeywordCurrentTime 
KeywordCurrentTimestamp 
KeywordDatabase 
KeywordDefault 
KeywordDeferrable 
KeywordDeferred 
KeywordDelete 
KeywordDesc 
KeywordDetach 
KeywordDistinct 
KeywordDrop 
KeywordEach 
KeywordElse 
KeywordEnd 
KeywordEscape 
KeywordExcept 
KeywordExclusive 
KeywordExists 
KeywordExplain 
KeywordFail 
KeywordFor 
KeywordForeign 
KeywordFrom 
KeywordFull 
KeywordGlob 
KeywordGroup 
KeywordHaving 
KeywordIf 
KeywordIgnore 
KeywordImmediate 
KeywordIn 
KeywordIndex 
KeywordIndexed 
KeywordInitially 
KeywordInner 
KeywordInsert 
KeywordInstead 
KeywordIntersect 
KeywordInto 
KeywordIs 
KeywordIsnull 
KeywordJoin 
KeywordKey 
KeywordLeft 
KeywordLike 
KeywordLimit 
KeywordMatch 
KeywordNatural 
KeywordNo 
KeywordNot 
KeywordNotnull 
KeywordNull 
KeywordOf 
KeywordOffset 
KeywordOn 
KeywordOr 
KeywordOrder 
KeywordOuter 
KeywordPlan 
KeywordPragma 
KeywordPrimary 
KeywordQuery 
KeywordRaise 
KeywordReferences 
KeywordRegexp 
KeywordReindex 
KeywordRelease 
KeywordRename 
KeywordReplace 
KeywordRestrict 
KeywordRight 
KeywordRollback 
KeywordRow 
KeywordSavepoint 
KeywordSelect 
KeywordSet 
KeywordTable 
KeywordTemp 
KeywordTemporary 
KeywordThen 
KeywordTo 
KeywordTransaction 
KeywordTrigger 
KeywordUnion 
KeywordUnique 
KeywordUpdate 
KeywordUsing 
KeywordVacuum 
KeywordValues 
KeywordView 
KeywordVirtual 
KeywordWhen 
KeywordWhere 

Instances

Abstract syntax tree nodes

There are a great many types of nodes in the abstract syntax tree. They are loosely divided into statements (commands to possibly be executed), expressions (algebraic expressions to possibly be evaluated), clauses (major portions of a statement or expression which have very complicated grammatical structure), subclauses (portions of clauses which still have some grammatical structure), qualifiers (things which have minimal grammatical structure of their own, but can be present and cause some change in semantics if they are), keywords (things which have minimal grammatical structure of their own, and no semantic meaning either, but can be present), heads (within a statement, groups of multiple clauses which include the verb of the statement), and bodies (within a statement, groups of multiple clauses which do not include the verb of the statement).

The guiding principle behind the selection of which things to give their own node-types to is that it should be possible to parse SQL and print it back out identically except for whitespace. This means for example that != and are distinct in the AST, as are NOT NULL and NOTNULL, and is the rationale behind the inclusion of the keywords category which has no semantic meaning. A likely use of this library is to implement a system which allows the same queries to be edited both as plaintext SQL and as some graphical form, and if a user edits as SQL, he expects these things to be preserved, as they can be important to readability.

When a qualifier is omitted, it's prefixed with No as in NoIfNotExists. When a keyword is omitted, it's prefixed with Elided as in ElidedTransaction. This is to remind you that an omitted qualifier has some sensible default semantic, whereas an omitted keyword has the same semantics as if it were present.

There is a great deal of sharing of structure, so I have made no attempt in this documentation to organize the exports by category, except to give expressions and statements their own sections; instead, please enjoy this alphabetical index!

data AlterTableBody Source

The AST node corresponding to the body of an AlterTable statement. Used by AlterTable.

data CasePair Source

The AST node corresponding to each WHEN-THEN pair of subexpressions in a CASE expression. Used by ExpressionCase.

data ColumnDefinition Source

The AST node corresponding to a column-definition subclause. Used by AlterTableBody and CreateTableBody.

data CommitHead Source

The AST node corresponding to the head of a COMMIT statement. Used by Commit.

Constructors

CommitCommit 
CommitEnd 

data CompoundOperator Source

The AST node corresponding to a compound operator in a SELECT statement. Used by Select.

Constructors

Union 
UnionAll 
Intersect 
Except 

data Distinctness Source

The AST node corresponding to an optional DISTINCT or ALL qualifier. Used by SelectCore.

Constructors

NoDistinctness 
Distinct 
All 

data Else Source

The AST node corresponding to the optional ELSE subclause in a CASE expression. Used by ExpressionCase.

Constructors

NoElse 
Else Expression 

data Escape Source

The AST node corresponding to the ESCAPE subclause of a textual comparison expression. Used by ExpressionLike.

Constructors

NoEscape 
Escape Expression 

data ForeignKeyClauseActionPart Source

The AST node corresponding to an action subclause in the first partial body of a FOREIGN KEY clause. Used by ForeignKeyClauseActionOrMatchPart.

data FromClause Source

The AST node corresponding to a FROM clause. Used by SelectCore.

Constructors

From JoinSource 

data GroupClause Source

The AST node corresponding to a GROUP BY clause. Used by SelectCore.

data IndexedColumn Source

The AST node corresponding to an indexed-column subclause. Used by TableConstraint and CreateIndex.

data JoinConstraint Source

The AST node corresponding to a join constraint, a qualifier in the FROM clause of a SELECT statement. Used by JoinSource.

data JoinOperation Source

The AST node corresponding to a join operation, a conjunction in the FROM clause of a SELECT statement. Used by JoinSource.

data JoinSource Source

The AST node corresponding to a source from which to join columns in a SELECT statement, which may be the head of the statement's FROM clause, or, in the case of a subjoin, only part of it. Used by FromClause and SingleSource.

data LikeType Source

The AST node corresponding to a textual comparison operator in an expression. Used by ExpressionLike.

data LimitClause Source

The AST node corresponding to a LIMIT clause. Used by Select, DeleteLimited, and UpdateLimited.

data MaybeAs Source

The AST node corresponding to an optional AS subclause, possibly with the actual keyword elided. Used by ResultColumn and SingleSource.

data MaybeAscDesc Source

The AST node corresponding to an optional ASC or DESC qualifier. Used by IndexedColumn, ColumnConstraint, and OrderingTerm.

Constructors

NoAscDesc 
Asc 
Desc 

data MaybeAutoincrement Source

The AST node corresponding to an optional AUTOINCREMENT qualifier. Used by ColumnConstraint.

data MaybeCollation Source

The AST node corresponding to an optional COLLATE subclause. Used by IndexedColumn and OrderingTerm.

data MaybeColumn Source

The AST node corresponding to an optional COLUMN keyword. Used by AlterTableBody.

Constructors

ElidedColumn 
Column 

data MaybeConstraintName Source

The AST node corresponding to an optional constraint name subclause. Used by ColumnConstraint and 'Table Constraint'.

data MaybeDatabase Source

The AST node corresponding to an optional DATABASE keyword. Used by Attach and Detach.

Constructors

ElidedDatabase 
Database 

data MaybeForEachRow Source

The AST node corresponding to an optional FOR EACH ROW qualifier. Used by CreateTrigger.

Constructors

NoForEachRow 
ForEachRow 

data MaybeHaving Source

The AST node corresponding to an optional HAVING subclause. Used by GroupClause.

Constructors

NoHaving 
Having Expression 

data MaybeIfExists Source

The AST node corresponding to an optional IF EXISTS qualifier. Used by DropIndex, DropTable, DropTrigger, and DropView.

Constructors

NoIfExists 
IfExists 

data MaybeIfNotExists Source

The AST node corresponding to an optional IF NOT EXISTS qualifier. Used by CreateIndex, CreateTable, CreateTrigger, and CreateView.

Constructors

NoIfNotExists 
IfNotExists 

data MaybeIndexedBy Source

The AST node corresponding to an optional INDEXED BY or NOT INDEXED qualifier. Used by SingleSource.

data MaybeInitialDeferralStatus Source

The AST node corresponding to an optional INITIALLY DEFERRED or INITIALLY IMMEDIATE qualifier in a FOREIGN KEY clause. Used by MaybeForeignKeyClauseDeferrablePart.

data MaybeSavepoint Source

The AST node corresponding to an optional TO SAVEPOINT qualifier. Used by Rollback.

data MaybeSign Source

The AST node corresponding to an optional + or - sign. Used by TypeSizeField, DefaultValue, and PragmaValue.

data MaybeSwitchExpression Source

The AST node corresponding to the optional first subexpression in a CASE expression. Used by ExpressionCase.

Constructors

NoSwitch 
Switch Expression 

data MaybeTemporary Source

The AST node corresponding to an optional TEMP or TEMPORARY qualifier. Used by CreateTable, CreateTrigger, and CreateView.

Constructors

NoTemporary 
Temp 
Temporary 

data MaybeTransaction Source

The AST node corresponding to an optional TRASACTION keyword. Used by Begin, Commit, and Rollback.

data MaybeTransactionType Source

The AST node corresponding to an optional transaction-type qualifier. Used by Begin.

data MaybeType Source

The AST node corresponding to an optional column type. Used by ColumnDefinition.

Constructors

NoType 
JustType Type 

data MaybeTypeSize Source

The AST node corresponding to an optional size annotation on a column or value type. Used by Type.

data MaybeUnique Source

The AST node corresponding to an optional UNIQUE qualifier. Used by CreateIndex.

Constructors

NoUnique 
Unique 

data ModuleArgument Source

The AST node corresponding to a module argument. Used by CreateVirtualTable.

Constructors

ModuleArgument String 

data OrderClause Source

The AST node corresponding to an ORDER BY clause. Used by Select, DeleteLimited, and UpdateLimited.

data OrderingTerm Source

The AST node corresponding to an ordering term subclause. Used by GroupClause and OrderClause.

data PragmaBody Source

The AST node corresponding to a pragma body. Used by Pragma.

data ResultColumn Source

The AST node corresponding to a result column in a SELECT statement. Used by SelectCore.

data SelectCore Source

The AST node corresponding to the core part of a SELECT statement, which may be the head of the overall statement, or, in the case of a compound SELECT, only part of it. Used by Select.

data SingleSource Source

The AST node corresponding to a primitive source from which to join columns in a SELECT statement, which is a body of the statement's FROM clause. Used by JoinSource.

data StatementList Source

The AST node corresponding to a semicolon-separated list of statements. Used at the top level of an SQL file.

Constructors

StatementList [AnyStatement] 

data TriggerCondition Source

The AST node corresponding to a trigger-condition subclause. Used by CreateTrigger.

data TriggerTime Source

The AST node corresponding to a trigger-time qualifier. Used by CreateTrigger.

Constructors

Before 
After 
InsteadOf 

data Type Source

The AST node corresponding to a column or value type. Used by MaybeType which is used by ColumnDefinition, and by ExpressionCast.

data TypeAffinity Source

The AST node corresponding to the affinity of a column or value type. Used by Type.

data TypeSizeField Source

The AST node corresponding to one of zero to two fields annotating a column or value type with size limits. Used by MaybeTypeSize.

data WhenClause Source

The AST node corresponding to a WHEN clause. Used by CreateTrigger.

Constructors

When Expression 

data WhereClause Source

The AST node corresponding to a WHERE clause. Used by SelectCore, Delete, DeleteLimited, Update, and UpdateLimited.

Constructors

Where Expression 

Abstract syntax tree nodes - Expressions

data Expression Source

The AST node corresponding to an expression. Used by DefaultValue, ColumnConstraint, TableConstraint, OrderingTerm, InsertBody, MaybeHaving, ResultColumn, JoinConstraint, WhereClause, WhenClause, Update, and UpdateLimited. Also useful at top level.

Constructors

ExpressionLiteralInteger Word64

Represents a literal integer expression.

ExpressionLiteralFloat NonnegativeDouble

Represents a literal floating-point expression.

ExpressionLiteralString String

Represents a literal string expression.

ExpressionLiteralBlob ByteString

Represents a literal blob (binary large object) expression.

ExpressionLiteralNull

Represents a literal NULL expression.

ExpressionLiteralCurrentTime

Represents a literal current_time expression.

ExpressionLiteralCurrentDate

Represents a literal current_date expression.

ExpressionLiteralCurrentTimestamp

Represents a literal current_timestamp expression.

ExpressionVariable

Represents a positional-variable expression, written in SQL as ?.

ExpressionVariableN Word64

Represents a numbered positional variable expression, written in SQL as ?nnn.

ExpressionVariableNamed String

Represents a named positional variable expression, written in SQL as :aaaa.

ExpressionIdentifier DoublyQualifiedIdentifier

Represents a column-name expression, optionally qualified by a table name and further by a database name.

ExpressionUnaryNegative Expression

Represents a unary negation expression.

ExpressionUnaryPositive Expression

Represents a unary positive-sign expression. Yes, this is an nop.

ExpressionUnaryBitwiseNot Expression

Represents a unary bitwise negation expression.

ExpressionUnaryLogicalNot Expression

Represents a unary logical negation expression.

ExpressionBinaryConcatenate Expression Expression

Represents a binary string-concatenation expression.

ExpressionBinaryMultiply Expression Expression

Represents a binary multiplication expression.

ExpressionBinaryDivide Expression Expression

Represents a binary division expression.

ExpressionBinaryModulus Expression Expression

Represents a binary modulus expression.

ExpressionBinaryAdd Expression Expression

Represents a binary addition expression.

ExpressionBinarySubtract Expression Expression

Represents a binary subtraction expression.

ExpressionBinaryLeftShift Expression Expression

Represents a binary left-shift expression.

ExpressionBinaryRightShift Expression Expression

Represents a binary right-shift expression.

ExpressionBinaryBitwiseAnd Expression Expression

Represents a binary bitwise-and expression.

ExpressionBinaryBitwiseOr Expression Expression

Represents a binary bitwise-or expression.

ExpressionBinaryLess Expression Expression

Represents a binary less-than comparison expression.

ExpressionBinaryLessEquals Expression Expression

Represents a binary less-than-or-equal-to comparison expression.

ExpressionBinaryGreater Expression Expression

Represents a binary greater-than comparison expression.

ExpressionBinaryGreaterEquals Expression Expression

Represents a binary greater-than-or-equal-to comparison expression.

ExpressionBinaryEquals Expression Expression

Represents a binary equal-to comparison expression, written in SQL as =.

ExpressionBinaryEqualsEquals Expression Expression

Represents a binary equal-to comparison expression, written in SQL as ==.

ExpressionBinaryNotEquals Expression Expression

Represents a binary not-equal-to comparison expression, written in SQL as !=.

ExpressionBinaryLessGreater Expression Expression

Represents a binary not-equal-to comparison expression, written in SQL as .

ExpressionBinaryLogicalAnd Expression Expression

Represents a binary logical-and expression.

ExpressionBinaryLogicalOr Expression Expression

Represents a binary logical-or expression.

ExpressionFunctionCall UnqualifiedIdentifier [Expression]

Represents a call to a built-in function.

ExpressionFunctionCallDistinct UnqualifiedIdentifier (OneOrMore Expression)

Represents a call to a built-in function, with the DISTINCT qualifier.

ExpressionFunctionCallStar UnqualifiedIdentifier

Represents a call to a built-in function, with * as parameter.

ExpressionCast Expression Type

Represents a type-cast expression.

ExpressionCollate Expression UnqualifiedIdentifier

Represents a COLLATE expression.

ExpressionLike Expression LikeType Expression Escape

Represents a textual comparison expression.

ExpressionIsnull Expression

Represents an ISNULL expression. Not to be confused with an IS expression with a literal NULL as its right side; the meaning is the same but the parsing is different.

ExpressionNotnull Expression

Represents a NOTNULL expression. Not to be confused with a NOT NULL expression; the meaning is the same but the parsing is different.

ExpressionNotNull Expression

Represents a NOT NULL expression. Not to be confused with a NOTNULL expression; the meaning is the same but the parsing is different.

ExpressionIs Expression Expression

Represents an IS expression.

ExpressionIsNot Expression Expression

Represents an IS NOT expression.

ExpressionBetween Expression Expression Expression

Represents a BETWEEN expression.

ExpressionNotBetween Expression Expression Expression

Represents a NOT BETWEEN expression.

ExpressionInSelect Expression Select

Represents an IN expression with the right-hand side being a SELECT statement.

ExpressionNotInSelect Expression Select

Represents a NOT IN expression with the right-hand side being a SELECT statement.

ExpressionInList Expression [Expression]

Represents an IN expression with the right-hand side being a list of subexpressions.

ExpressionNotInList Expression [Expression]

Represents a NOT IN expression with the right-hand side being a list of subexpressions.

ExpressionInTable Expression SinglyQualifiedIdentifier

Represents an IN expression with the right-hand side being a table name, optionally qualified by a database name.

ExpressionNotInTable Expression SinglyQualifiedIdentifier

Represents a NOT IN expression with the right-hand side being a table name, optionally qualified by a database name.

ExpressionSubquery Select

Represents a subquery SELECT expression.

ExpressionExistsSubquery Select

Represents a subquery SELECT expression with the EXISTS qualifier.

ExpressionNotExistsSubquery Select

Represents a subquery SELECT expression with the NOT EXISTS qualifier.

ExpressionCase MaybeSwitchExpression (OneOrMore CasePair) Else

Represents a CASE expression.

ExpressionRaiseIgnore

Represents a RAISE(IGNORE) expression.

ExpressionRaiseRollback String

Represents a RAISE(ROLLBACK, string) expression.

ExpressionRaiseAbort String

Represents a RAISE(ABORT, string) expression.

ExpressionRaiseFail String

Represents a RAISE(FAIL, string) expression.

ExpressionParenthesized Expression

Represents a parenthesized subexpression.

Abstract syntax tree nodes - Statements

data AnyStatement Source

The AST node corresponding to any statement. Used by StatementList. Also useful at top level.

Constructors

forall l t v w . Statement (Statement l t v w) 

fromAnyStatement :: StatementClass a => AnyStatement -> aSource

fromTriggerStatement :: StatementClass a => TriggerStatement -> aSource

data Statement level triggerable valueReturning which whereSource

The AST node which corresponds to a statement. Not directly useful at top level because it is a generalized algebraic datatype the type parameters to which are not exported; instead, see the existentially qualified types AnyStatement, ExplainableStatement, and TriggerStatement, and the type synonyms such as Select which correspond to individual statement types.

I apologize for the lack of documentation on these individual entries, but Haddock won't let me do it! At any rate, each of them is an AST node corresponding to an individual statement type.

Note the distinctions between Delete and DeleteLimited and Update and UpdateLimited: The Limited ones have LIMIT clauses and the others do not. Because SQL imposes stricter restrictions on where the ones with LIMIT clauses can occur, these are are separate types.

Constructors

Explain :: ExplainableStatement -> Statement L1 NT NS Explain' 
ExplainQueryPlan :: ExplainableStatement -> Statement L1 NT NS ExplainQueryPlan' 
AlterTable :: SinglyQualifiedIdentifier -> AlterTableBody -> Statement L0 NT NS AlterTable' 
Analyze :: SinglyQualifiedIdentifier -> Statement L0 NT NS Analyze' 
Attach :: MaybeDatabase -> String -> UnqualifiedIdentifier -> Statement L0 NT NS Attach' 
Begin :: MaybeTransactionType -> MaybeTransaction -> Statement L0 NT NS Begin' 
Commit :: CommitHead -> MaybeTransaction -> Statement L0 NT NS Commit' 
CreateIndex :: MaybeUnique -> MaybeIfNotExists -> SinglyQualifiedIdentifier -> UnqualifiedIdentifier -> OneOrMore IndexedColumn -> Statement L0 NT NS CreateIndex' 
CreateTable :: MaybeTemporary -> MaybeIfNotExists -> SinglyQualifiedIdentifier -> CreateTableBody -> Statement L0 NT NS CreateTable' 
CreateTrigger :: MaybeTemporary -> MaybeIfNotExists -> SinglyQualifiedIdentifier -> TriggerTime -> TriggerCondition -> UnqualifiedIdentifier -> MaybeForEachRow -> Maybe WhenClause -> OneOrMore TriggerStatement -> Statement L0 NT NS CreateTrigger' 
CreateView :: MaybeTemporary -> MaybeIfNotExists -> SinglyQualifiedIdentifier -> Statement L0 T S Select' -> Statement L0 NT NS CreateView' 
CreateVirtualTable :: SinglyQualifiedIdentifier -> UnqualifiedIdentifier -> [ModuleArgument] -> Statement L0 NT NS CreateVirtualTable' 
Delete :: QualifiedTableName -> Maybe WhereClause -> Statement L0 T NS Delete' 
DeleteLimited :: QualifiedTableName -> Maybe WhereClause -> Maybe OrderClause -> LimitClause -> Statement L0 NT NS DeleteLimited' 
Detach :: MaybeDatabase -> UnqualifiedIdentifier -> Statement L0 NT NS Detach' 
DropIndex :: MaybeIfExists -> SinglyQualifiedIdentifier -> Statement L0 NT NS DropIndex' 
DropTable :: MaybeIfExists -> SinglyQualifiedIdentifier -> Statement L0 NT NS DropTable' 
DropTrigger :: MaybeIfExists -> SinglyQualifiedIdentifier -> Statement L0 NT NS DropTrigger' 
DropView :: MaybeIfExists -> SinglyQualifiedIdentifier -> Statement L0 NT NS DropView' 
Insert :: InsertHead -> SinglyQualifiedIdentifier -> InsertBody -> Statement L0 T NS Insert' 
Pragma :: SinglyQualifiedIdentifier -> PragmaBody -> Statement L0 NT NS Pragma' 
Reindex :: SinglyQualifiedIdentifier -> Statement L0 NT NS Reindex' 
Release :: MaybeReleaseSavepoint -> UnqualifiedIdentifier -> Statement L0 NT NS Release' 
Rollback :: MaybeTransaction -> MaybeSavepoint -> Statement L0 NT NS Rollback' 
Savepoint :: UnqualifiedIdentifier -> Statement L0 NT NS Savepoint' 
Select :: SelectCore -> [(CompoundOperator, SelectCore)] -> Maybe OrderClause -> Maybe LimitClause -> Statement L0 T S Select' 
Update :: UpdateHead -> QualifiedTableName -> OneOrMore (UnqualifiedIdentifier, Expression) -> Maybe WhereClause -> Statement L0 T NS Update' 
UpdateLimited :: UpdateHead -> QualifiedTableName -> OneOrMore (UnqualifiedIdentifier, Expression) -> Maybe WhereClause -> Maybe OrderClause -> LimitClause -> Statement L0 NT NS UpdateLimited' 
Vacuum :: Statement L0 NT NS Vacuum' 

Instances

Eq (Statement l t v w) 
Show (Statement l t v w) 
ShowTokens (Statement l t v w) 

type AlterTable = Statement L0 NT NS AlterTable'Source

A type synonym which matches only the AST node corresponding to an ALTER TABLE statement. Useful at top level.

type Analyze = Statement L0 NT NS Analyze'Source

A type synonym which matches only the AST node corresponding to an ANALYZE statement. Useful at top level.

type Attach = Statement L0 NT NS Attach'Source

A type synonym which matches only the AST node corresponding to an ATTACH statement. Useful at top level.

type Begin = Statement L0 NT NS Begin'Source

A type synonym which matches only the AST node corresponding to a BEGIN statement. Useful at top level.

type Commit = Statement L0 NT NS Commit'Source

A type synonym which matches only the AST node corresponding to a COMMIT statement. Useful at top level.

type CreateIndex = Statement L0 NT NS CreateIndex'Source

A type synonym which matches only the AST node corresponding to a CREATE INDEX statement. Useful at top level.

type CreateTable = Statement L0 NT NS CreateTable'Source

A type synonym which matches only the AST node corresponding to a CREATE TABLE statement. Useful at top level.

type CreateTrigger = Statement L0 NT NS CreateTrigger'Source

A type synonym which matches only the AST node corresponding to a CREATE TRIGGER statement. Useful at top level.

type CreateView = Statement L0 NT NS CreateView'Source

A type synonym which matches only the AST node corresponding to a CREATE VIEW statement. Useful at top level.

type CreateVirtualTable = Statement L0 NT NS CreateVirtualTable'Source

A type synonym which matches only the AST node corresponding to a CREATE VIRTUAL TABLE statement. Useful at top level.

type Delete = Statement L0 T NS Delete'Source

A type synonym which matches only the AST node corresponding to a DELETE statement without a LIMIT clause. Useful at top level.

type DeleteLimited = Statement L0 NT NS DeleteLimited'Source

A type synonym which matches only the AST node corresponding to a DELETE statement with a LIMIT clause. Useful at top level.

type Detach = Statement L0 NT NS Detach'Source

A type synonym which matches only the AST node corresponding to a DETACH statement. Useful at top level.

type DropIndex = Statement L0 NT NS DropIndex'Source

A type synonym which matches only the AST node corresponding to a DROP INDEX statement. Useful at top level.

type DropTable = Statement L0 NT NS DropTable'Source

A type synonym which matches only the AST node corresponding to a DROP TABLE statement. Useful at top level.

type DropTrigger = Statement L0 NT NS DropTrigger'Source

A type synonym which matches only the AST node corresponding to a DROP TRIGGER statement. Useful at top level.

type DropView = Statement L0 NT NS DropView'Source

A type synonym which matches only the AST node corresponding to a DROP VIEW statement. Useful at top level.

type Explain = Statement L1 NT NS Explain'Source

A type synonym which matches only the AST node corresponding to an EXPLAIN statement. Useful at top level.

type ExplainQueryPlan = Statement L1 NT NS ExplainQueryPlan'Source

A type synonym which matches only the AST node corresponding to an EXPLAIN QUERY PLAN statement. Useful at top level.

type Insert = Statement L0 T NS Insert'Source

A type synonym which matches only the AST node corresponding to an INSERT statement. Useful at top level.

type Pragma = Statement L0 NT NS Pragma'Source

A type synonym which matches only the AST node corresponding to a PRAGMA statement. Useful at top level.

type Reindex = Statement L0 NT NS Reindex'Source

A type synonym which matches only the AST node corresponding to a REINDEX statement. Useful at top level.

type Release = Statement L0 NT NS Release'Source

A type synonym which matches only the AST node corresponding to a RELEASE statement. Useful at top level.

type Rollback = Statement L0 NT NS Rollback'Source

A type synonym which matches only the AST node corresponding to a ROLLBACK statement. Useful at top level.

type Savepoint = Statement L0 NT NS Savepoint'Source

A type synonym which matches only the AST node corresponding to a SAVEPOINT statement. Useful at top level.

type Select = Statement L0 T S Select'Source

A type synonym which matches only the AST node corresponding to a SELECT statement. Useful at top level.

type Update = Statement L0 T NS Update'Source

A type synonym which matches only the AST node corresponding to an UPDATE statement without a LIMIT clause. Useful at top level.

type UpdateLimited = Statement L0 NT NS UpdateLimited'Source

A type synonym which matches only the AST node corresponding to an UPDATE statement with a LIMIT clause. Useful at top level.

type Vacuum = Statement L0 NT NS Vacuum'Source

A type synonym which matches only the AST node corresponding to a VACUUM statement. Useful at top level.