Language.SQL.SQLite
Contents
- lexModuleArgument :: String -> Parse (Token, String)
- data ParseError
- readType :: String -> Either ParseError Type
- readMaybeType :: String -> Either ParseError MaybeType
- readMaybeTypeName :: String -> Either ParseError MaybeTypeName
- readMaybeTypeSize :: String -> Either ParseError MaybeTypeSize
- readTypeSizeField :: String -> Either ParseError TypeSizeField
- readLikeType :: String -> Either ParseError LikeType
- readMaybeSwitchExpression :: String -> Either ParseError MaybeSwitchExpression
- readCasePair :: String -> Either ParseError CasePair
- readEscape :: String -> Either ParseError Escape
- readElse :: String -> Either ParseError Else
- readExpression :: String -> Either ParseError Expression
- readMaybeUnique :: String -> Either ParseError MaybeUnique
- readMaybeIfNotExists :: String -> Either ParseError MaybeIfNotExists
- readMaybeIfExists :: String -> Either ParseError MaybeIfExists
- readMaybeForEachRow :: String -> Either ParseError MaybeForEachRow
- readMaybeTemporary :: String -> Either ParseError MaybeTemporary
- readMaybeCollation :: String -> Either ParseError MaybeCollation
- readMaybeAscDesc :: String -> Either ParseError MaybeAscDesc
- readMaybeAutoincrement :: String -> Either ParseError MaybeAutoincrement
- readMaybeSign :: String -> Either ParseError MaybeSign
- readMaybeColumn :: String -> Either ParseError MaybeColumn
- readAlterTableBody :: String -> Either ParseError AlterTableBody
- readColumnDefinition :: String -> Either ParseError ColumnDefinition
- readDefaultValue :: String -> Either ParseError DefaultValue
- readIndexedColumn :: String -> Either ParseError IndexedColumn
- readColumnConstraint :: String -> Either ParseError ColumnConstraint
- readTableConstraint :: String -> Either ParseError TableConstraint
- readMaybeConstraintName :: String -> Either ParseError MaybeConstraintName
- readTriggerTime :: String -> Either ParseError TriggerTime
- readTriggerCondition :: String -> Either ParseError TriggerCondition
- readModuleArgument :: String -> Either ParseError ModuleArgument
- readTriggerStatement :: String -> Either ParseError TriggerStatement
- readQualifiedTableName :: String -> Either ParseError QualifiedTableName
- readOrderingTerm :: String -> Either ParseError OrderingTerm
- readPragmaBody :: String -> Either ParseError PragmaBody
- readPragmaValue :: String -> Either ParseError PragmaValue
- readCreateTableBody :: String -> Either ParseError CreateTableBody
- readInsertHead :: String -> Either ParseError InsertHead
- readInsertBody :: String -> Either ParseError InsertBody
- readUpdateHead :: String -> Either ParseError UpdateHead
- readDistinctness :: String -> Either ParseError Distinctness
- readMaybeHaving :: String -> Either ParseError MaybeHaving
- readMaybeAs :: String -> Either ParseError MaybeAs
- readCompoundOperator :: String -> Either ParseError CompoundOperator
- readSelectCore :: String -> Either ParseError SelectCore
- readResultColumn :: String -> Either ParseError ResultColumn
- readJoinSource :: String -> Either ParseError JoinSource
- readSingleSource :: String -> Either ParseError SingleSource
- readJoinOperation :: String -> Either ParseError JoinOperation
- readJoinConstraint :: String -> Either ParseError JoinConstraint
- readMaybeIndexedBy :: String -> Either ParseError MaybeIndexedBy
- readFromClause :: String -> Either ParseError FromClause
- readWhereClause :: String -> Either ParseError WhereClause
- readGroupClause :: String -> Either ParseError GroupClause
- readOrderClause :: String -> Either ParseError OrderClause
- readLimitClause :: String -> Either ParseError LimitClause
- readWhenClause :: String -> Either ParseError WhenClause
- readConflictClause :: String -> Either ParseError ConflictClause
- readForeignKeyClause :: String -> Either ParseError ForeignKeyClause
- readForeignKeyClauseActionOrMatchPart :: String -> Either ParseError ForeignKeyClauseActionOrMatchPart
- readForeignKeyClauseActionPart :: String -> Either ParseError ForeignKeyClauseActionPart
- readMaybeForeignKeyClauseDeferrablePart :: String -> Either ParseError MaybeForeignKeyClauseDeferrablePart
- readMaybeInitialDeferralStatus :: String -> Either ParseError MaybeInitialDeferralStatus
- readCommitHead :: String -> Either ParseError CommitHead
- readMaybeTransaction :: String -> Either ParseError MaybeTransaction
- readMaybeTransactionType :: String -> Either ParseError MaybeTransactionType
- readMaybeDatabase :: String -> Either ParseError MaybeDatabase
- readMaybeSavepoint :: String -> Either ParseError MaybeSavepoint
- readMaybeReleaseSavepoint :: String -> Either ParseError MaybeReleaseSavepoint
- readStatementList :: String -> Either ParseError StatementList
- readAnyStatement :: String -> Either ParseError AnyStatement
- readExplainableStatement :: String -> Either ParseError ExplainableStatement
- readExplain :: String -> Either ParseError Explain
- readExplainQueryPlan :: String -> Either ParseError ExplainQueryPlan
- readAlterTable :: String -> Either ParseError AlterTable
- readAnalyze :: String -> Either ParseError Analyze
- readAttach :: String -> Either ParseError Attach
- readBegin :: String -> Either ParseError Begin
- readCommit :: String -> Either ParseError Commit
- readCreateIndex :: String -> Either ParseError CreateIndex
- readCreateTable :: String -> Either ParseError CreateTable
- readCreateTrigger :: String -> Either ParseError CreateTrigger
- readCreateView :: String -> Either ParseError CreateView
- readCreateVirtualTable :: String -> Either ParseError CreateVirtualTable
- readDelete :: String -> Either ParseError Delete
- readDeleteLimited :: String -> Either ParseError DeleteLimited
- readDeleteOrDeleteLimited :: String -> Either ParseError AnyStatement
- readDetach :: String -> Either ParseError Detach
- readDropIndex :: String -> Either ParseError DropIndex
- readDropTable :: String -> Either ParseError DropTable
- readDropTrigger :: String -> Either ParseError DropTrigger
- readDropView :: String -> Either ParseError DropView
- readInsert :: String -> Either ParseError Insert
- readPragma :: String -> Either ParseError Pragma
- readReindex :: String -> Either ParseError Reindex
- readRelease :: String -> Either ParseError Release
- readRollback :: String -> Either ParseError Rollback
- readSavepoint :: String -> Either ParseError Savepoint
- readSelect :: String -> Either ParseError Select
- readUpdate :: String -> Either ParseError Update
- readUpdateLimited :: String -> Either ParseError UpdateLimited
- readUpdateOrUpdateLimited :: String -> Either ParseError AnyStatement
- readVacuum :: String -> Either ParseError Vacuum
- readUnqualifiedIdentifier :: String -> Either ParseError UnqualifiedIdentifier
- readSinglyQualifiedIdentifier :: String -> Either ParseError SinglyQualifiedIdentifier
- readDoublyQualifiedIdentifier :: String -> Either ParseError DoublyQualifiedIdentifier
- class  ShowTokens a  where- showTokens :: a -> [Token]
 
- data OneOrMore a
- mkOneOrMore :: [a] -> Maybe (OneOrMore a)
- fromOneOrMore :: OneOrMore a -> [a]
- data NonnegativeDouble
- mkNonnegativeDouble :: Double -> Maybe NonnegativeDouble
- fromNonnegativeDouble :: NonnegativeDouble -> Double
- computeTypeNameAffinity :: MaybeTypeName -> TypeAffinity
- computeAffinityTypeName :: TypeAffinity -> MaybeTypeName
- class  Identifier a  where- identifierProperName :: a -> String
- identifierParentName :: a -> Maybe String
- identifierGrandparentName :: a -> Maybe String
 
- toDoublyQualifiedIdentifier :: Identifier a => a -> DoublyQualifiedIdentifier
- data UnqualifiedIdentifier = UnqualifiedIdentifier String
- data SinglyQualifiedIdentifier = SinglyQualifiedIdentifier (Maybe String) String
- data DoublyQualifiedIdentifier = DoublyQualifiedIdentifier (Maybe (String, Maybe String)) String
- data  Token - = 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
 
- data AlterTableBody
- data CasePair = WhenThen Expression Expression
- data  ColumnConstraint - = ColumnPrimaryKey MaybeConstraintName MaybeAscDesc (Maybe ConflictClause) MaybeAutoincrement
- | ColumnNotNull MaybeConstraintName (Maybe ConflictClause)
- | ColumnUnique MaybeConstraintName (Maybe ConflictClause)
- | ColumnCheck MaybeConstraintName Expression
- | ColumnDefault MaybeConstraintName DefaultValue
- | ColumnCollate MaybeConstraintName UnqualifiedIdentifier
- | ColumnForeignKey MaybeConstraintName ForeignKeyClause
 
- data ColumnDefinition = ColumnDefinition UnqualifiedIdentifier MaybeType [ColumnConstraint]
- data CommitHead
- data CompoundOperator
- data ConflictClause
- data  DefaultValue - = DefaultValueSignedInteger MaybeSign Word64
- | DefaultValueSignedFloat MaybeSign NonnegativeDouble
- | DefaultValueLiteralString String
- | DefaultValueLiteralBlob ByteString
- | DefaultValueLiteralNull
- | DefaultValueLiteralCurrentTime
- | DefaultValueLiteralCurrentDate
- | DefaultValueLiteralCurrentTimestamp
- | DefaultValueExpression Expression
 
- data  Distinctness - = NoDistinctness
- | Distinct
- | All
 
- data CreateTableBody
- data  Else - = NoElse
- | Else Expression
 
- data  Escape - = NoEscape
- | Escape Expression
 
- data ForeignKeyClause = References UnqualifiedIdentifier [UnqualifiedIdentifier] [ForeignKeyClauseActionOrMatchPart] MaybeForeignKeyClauseDeferrablePart
- data ForeignKeyClauseActionOrMatchPart
- data  ForeignKeyClauseActionPart - = SetNull
- | SetDefault
- | Cascade
- | Restrict
- | NoAction
 
- data FromClause = From JoinSource
- data GroupClause = GroupBy (OneOrMore OrderingTerm) MaybeHaving
- data IndexedColumn = IndexedColumn UnqualifiedIdentifier MaybeCollation MaybeAscDesc
- data InsertBody
- data InsertHead
- data JoinConstraint
- data  JoinOperation - = Comma
- | Join
- | OuterJoin
- | LeftJoin
- | LeftOuterJoin
- | InnerJoin
- | CrossJoin
- | NaturalJoin
- | NaturalOuterJoin
- | NaturalLeftJoin
- | NaturalLeftOuterJoin
- | NaturalInnerJoin
- | NaturalCrossJoin
 
- data JoinSource = JoinSource SingleSource [(JoinOperation, SingleSource, JoinConstraint)]
- data LikeType
- data LimitClause
- data MaybeAs
- data MaybeAscDesc
- data MaybeAutoincrement
- data MaybeCollation
- data  MaybeColumn - = ElidedColumn
- | Column
 
- data MaybeConstraintName
- data MaybeDatabase
- data MaybeForEachRow
- data MaybeForeignKeyClauseDeferrablePart
- data  MaybeHaving - = NoHaving
- | Having Expression
 
- data  MaybeIfExists - = NoIfExists
- | IfExists
 
- data MaybeIfNotExists
- data MaybeIndexedBy
- data MaybeInitialDeferralStatus
- data MaybeReleaseSavepoint
- data MaybeSavepoint
- data  MaybeSign - = NoSign
- | PositiveSign
- | NegativeSign
 
- data  MaybeSwitchExpression - = NoSwitch
- | Switch Expression
 
- data  MaybeTemporary - = NoTemporary
- | Temp
- | Temporary
 
- data MaybeTransaction
- data  MaybeTransactionType - = NoTransactionType
- | Deferred
- | Immediate
- | Exclusive
 
- data MaybeType
- data MaybeTypeName
- data MaybeTypeSize
- data MaybeUnique
- data ModuleArgument = ModuleArgument String
- data OrderClause = OrderBy (OneOrMore OrderingTerm)
- data OrderingTerm = OrderingTerm Expression MaybeCollation MaybeAscDesc
- data PragmaBody
- data PragmaValue
- data QualifiedTableName
- data ResultColumn
- data SelectCore = SelectCore Distinctness (OneOrMore ResultColumn) (Maybe FromClause) (Maybe WhereClause) (Maybe GroupClause)
- data SingleSource
- data StatementList = StatementList [AnyStatement]
- data  TableConstraint - = TablePrimaryKey MaybeConstraintName (OneOrMore IndexedColumn) (Maybe ConflictClause)
- | TableUnique MaybeConstraintName (OneOrMore IndexedColumn) (Maybe ConflictClause)
- | TableCheck MaybeConstraintName Expression
- | TableForeignKey MaybeConstraintName (OneOrMore UnqualifiedIdentifier) ForeignKeyClause
 
- data TriggerCondition
- data TriggerTime
- data Type = Type TypeAffinity MaybeTypeName MaybeTypeSize
- data TypeAffinity
- data TypeSizeField
- data UpdateHead
- data WhenClause = When Expression
- data WhereClause = Where Expression
- data  Expression - = ExpressionLiteralInteger Word64
- | ExpressionLiteralFloat NonnegativeDouble
- | ExpressionLiteralString String
- | ExpressionLiteralBlob ByteString
- | ExpressionLiteralNull
- | ExpressionLiteralCurrentTime
- | ExpressionLiteralCurrentDate
- | ExpressionLiteralCurrentTimestamp
- | ExpressionVariable
- | ExpressionVariableN Word64
- | ExpressionVariableNamed String
- | ExpressionIdentifier DoublyQualifiedIdentifier
- | ExpressionUnaryNegative Expression
- | ExpressionUnaryPositive Expression
- | ExpressionUnaryBitwiseNot Expression
- | ExpressionUnaryLogicalNot Expression
- | ExpressionBinaryConcatenate Expression Expression
- | ExpressionBinaryMultiply Expression Expression
- | ExpressionBinaryDivide Expression Expression
- | ExpressionBinaryModulus Expression Expression
- | ExpressionBinaryAdd Expression Expression
- | ExpressionBinarySubtract Expression Expression
- | ExpressionBinaryLeftShift Expression Expression
- | ExpressionBinaryRightShift Expression Expression
- | ExpressionBinaryBitwiseAnd Expression Expression
- | ExpressionBinaryBitwiseOr Expression Expression
- | ExpressionBinaryLess Expression Expression
- | ExpressionBinaryLessEquals Expression Expression
- | ExpressionBinaryGreater Expression Expression
- | ExpressionBinaryGreaterEquals Expression Expression
- | ExpressionBinaryEquals Expression Expression
- | ExpressionBinaryEqualsEquals Expression Expression
- | ExpressionBinaryNotEquals Expression Expression
- | ExpressionBinaryLessGreater Expression Expression
- | ExpressionBinaryLogicalAnd Expression Expression
- | ExpressionBinaryLogicalOr Expression Expression
- | ExpressionFunctionCall UnqualifiedIdentifier [Expression]
- | ExpressionFunctionCallDistinct UnqualifiedIdentifier (OneOrMore Expression)
- | ExpressionFunctionCallStar UnqualifiedIdentifier
- | ExpressionCast Expression Type
- | ExpressionCollate Expression UnqualifiedIdentifier
- | ExpressionLike Expression LikeType Expression Escape
- | ExpressionIsnull Expression
- | ExpressionNotnull Expression
- | ExpressionNotNull Expression
- | ExpressionIs Expression Expression
- | ExpressionIsNot Expression Expression
- | ExpressionBetween Expression Expression Expression
- | ExpressionNotBetween Expression Expression Expression
- | ExpressionInSelect Expression Select
- | ExpressionNotInSelect Expression Select
- | ExpressionInList Expression [Expression]
- | ExpressionNotInList Expression [Expression]
- | ExpressionInTable Expression SinglyQualifiedIdentifier
- | ExpressionNotInTable Expression SinglyQualifiedIdentifier
- | ExpressionSubquery Select
- | ExpressionExistsSubquery Select
- | ExpressionNotExistsSubquery Select
- | ExpressionCase MaybeSwitchExpression (OneOrMore CasePair) Else
- | ExpressionRaiseIgnore
- | ExpressionRaiseRollback String
- | ExpressionRaiseAbort String
- | ExpressionRaiseFail String
- | ExpressionParenthesized Expression
 
- data AnyStatement = forall l t v w . Statement (Statement l t v w)
- fromAnyStatement :: StatementClass a => AnyStatement -> a
- data ExplainableStatement = forall t v w . ExplainableStatement (Statement L0 t v w)
- fromExplainableStatement :: StatementClass a => ExplainableStatement -> a
- data TriggerStatement = forall l v w . TriggerStatement (Statement l T v w)
- fromTriggerStatement :: StatementClass a => TriggerStatement -> a
- data  Statement level triggerable valueReturning which where- 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'
 
- type AlterTable = Statement L0 NT NS AlterTable'
- type Analyze = Statement L0 NT NS Analyze'
- type Attach = Statement L0 NT NS Attach'
- type Begin = Statement L0 NT NS Begin'
- type Commit = Statement L0 NT NS Commit'
- type CreateIndex = Statement L0 NT NS CreateIndex'
- type CreateTable = Statement L0 NT NS CreateTable'
- type CreateTrigger = Statement L0 NT NS CreateTrigger'
- type CreateView = Statement L0 NT NS CreateView'
- type CreateVirtualTable = Statement L0 NT NS CreateVirtualTable'
- type Delete = Statement L0 T NS Delete'
- type DeleteLimited = Statement L0 NT NS DeleteLimited'
- type Detach = Statement L0 NT NS Detach'
- type DropIndex = Statement L0 NT NS DropIndex'
- type DropTable = Statement L0 NT NS DropTable'
- type DropTrigger = Statement L0 NT NS DropTrigger'
- type DropView = Statement L0 NT NS DropView'
- type Explain = Statement L1 NT NS Explain'
- type ExplainQueryPlan = Statement L1 NT NS ExplainQueryPlan'
- type Insert = Statement L0 T NS Insert'
- type Pragma = Statement L0 NT NS Pragma'
- type Reindex = Statement L0 NT NS Reindex'
- type Release = Statement L0 NT NS Release'
- type Rollback = Statement L0 NT NS Rollback'
- type Savepoint = Statement L0 NT NS Savepoint'
- type Select = Statement L0 T S Select'
- type Update = Statement L0 T NS Update'
- type UpdateLimited = Statement L0 NT NS UpdateLimited'
- type Vacuum = Statement L0 NT NS Vacuum'
Parsing
lexModuleArgument :: String -> Parse (Token, String)Source
data ParseError Source
Instances
readForeignKeyClauseActionOrMatchPart :: String -> Either ParseError ForeignKeyClauseActionOrMatchPartSource
readMaybeForeignKeyClauseDeferrablePart :: String -> Either ParseError MaybeForeignKeyClauseDeferrablePartSource
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
A class with hidden implementation so as to enforce the constraint that it is a nonempty homogeneous list of items.
mkOneOrMore :: [a] -> Maybe (OneOrMore a)Source
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.
Instances
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.
computeTypeNameAffinity :: MaybeTypeName -> TypeAffinitySource
Computes a TypeAffinity from a MaybeTypeName, as used in
   Type.
computeAffinityTypeName :: TypeAffinity -> MaybeTypeNameSource
Computes a MaybeTypeName from a TypeAffinity, as used in
   Type.
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.
Constructors
| UnqualifiedIdentifier String | 
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.
Constructors
| SinglyQualifiedIdentifier (Maybe String) String | 
data DoublyQualifiedIdentifier Source
An identifier which allows two levels of qualification. This is typically a column name.
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
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.
The AST node corresponding to each WHEN-THEN pair of subexpressions in a
   CASE expression.  Used by ExpressionCase.
Constructors
| WhenThen Expression Expression | 
data ColumnConstraint Source
The AST node corresponding to a column constraint subclause.  Used by
   ColumnDefinition.
Constructors
data ColumnDefinition Source
The AST node corresponding to a column-definition subclause.  Used by
   AlterTableBody and CreateTableBody.
Constructors
| ColumnDefinition UnqualifiedIdentifier MaybeType [ColumnConstraint] | 
data CommitHead Source
The AST node corresponding to the head of a COMMIT statement.  Used by
   Commit.
Constructors
| CommitCommit | |
| CommitEnd | 
Instances
data CompoundOperator Source
The AST node corresponding to a compound operator in a SELECT statement.
   Used by Select.
data ConflictClause Source
The AST node corresponding to an ON CONFLICT clause.  Used by
   ColumnConstraint and TableConstraint.
data DefaultValue Source
The AST node corresponding to a default-value subclause.  Used by
   ColumnConstraint.
Constructors
Instances
data Distinctness Source
The AST node corresponding to an optional DISTINCT or ALL qualifier.
   Used by SelectCore.
Constructors
| NoDistinctness | |
| Distinct | |
| All | 
Instances
data CreateTableBody Source
The AST node corresponding to a create-table body.  Used by CreateTable.
Constructors
| ColumnsAndConstraints (OneOrMore ColumnDefinition) [TableConstraint] | |
| AsSelect Select | 
The AST node corresponding to the optional ELSE subclause in a CASE expression.
   Used by ExpressionCase.
Constructors
| NoElse | |
| Else Expression | 
The AST node corresponding to the ESCAPE subclause of a textual comparison
   expression.  Used by ExpressionLike.
Constructors
| NoEscape | |
| Escape Expression | 
data ForeignKeyClause Source
The AST node corresponding to a FOREIGN KEY clause.  Used by
   ColumnConstraint and TableConstraint.
data ForeignKeyClauseActionOrMatchPart Source
The AST node corresponding to the first partial body of a FOREIGN KEY clause.
   Used by ForeignKeyClause.
data ForeignKeyClauseActionPart Source
The AST node corresponding to an action subclause in the first partial body of
   a FOREIGN KEY clause.  Used by ForeignKeyClauseActionOrMatchPart.
Constructors
| SetNull | |
| SetDefault | |
| Cascade | |
| Restrict | |
| NoAction | 
data FromClause Source
The AST node corresponding to a FROM clause.  Used by SelectCore.
Constructors
| From JoinSource | 
Instances
data GroupClause Source
The AST node corresponding to a GROUP BY clause.  Used by SelectCore.
Constructors
| GroupBy (OneOrMore OrderingTerm) MaybeHaving | 
Instances
data IndexedColumn Source
The AST node corresponding to an indexed-column subclause.  Used by
   TableConstraint and CreateIndex.
Constructors
| IndexedColumn UnqualifiedIdentifier MaybeCollation MaybeAscDesc | 
Instances
data InsertBody Source
The AST node corresponding to an insert body.  Used by Insert.
Constructors
| InsertValues [UnqualifiedIdentifier] (OneOrMore Expression) | |
| InsertSelect [UnqualifiedIdentifier] Select | |
| InsertDefaultValues | 
Instances
data InsertHead Source
The AST node corresponding to an insert head.  Used by Insert.
Constructors
| InsertNoAlternative | |
| InsertOrRollback | |
| InsertOrAbort | |
| InsertOrReplace | |
| InsertOrFail | |
| InsertOrIgnore | |
| Replace | 
Instances
data JoinConstraint Source
The AST node corresponding to a join constraint, a qualifier in the FROM
   clause of a SELECT statement.  Used by JoinSource.
Constructors
| NoConstraint | |
| On Expression | |
| Using (OneOrMore UnqualifiedIdentifier) | 
data JoinOperation Source
The AST node corresponding to a join operation, a conjunction in the FROM
   clause of a SELECT statement.  Used by JoinSource.
Constructors
| Comma | |
| Join | |
| OuterJoin | |
| LeftJoin | |
| LeftOuterJoin | |
| InnerJoin | |
| CrossJoin | |
| NaturalJoin | |
| NaturalOuterJoin | |
| NaturalLeftJoin | |
| NaturalLeftOuterJoin | |
| NaturalInnerJoin | |
| NaturalCrossJoin | 
Instances
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.
Constructors
| JoinSource SingleSource [(JoinOperation, SingleSource, JoinConstraint)] | 
Instances
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.
Constructors
| Limit Word64 | |
| LimitOffset Word64 Word64 | |
| LimitComma Word64 Word64 | 
Instances
The AST node corresponding to an optional AS subclause, possibly with the
   actual keyword elided.  Used by ResultColumn and SingleSource.
Constructors
| NoAs | |
| As UnqualifiedIdentifier | |
| ElidedAs UnqualifiedIdentifier | 
data MaybeAscDesc Source
The AST node corresponding to an optional ASC or DESC qualifier.  Used by
   IndexedColumn, ColumnConstraint, and OrderingTerm.
Instances
data MaybeAutoincrement Source
The AST node corresponding to an optional AUTOINCREMENT qualifier.  Used by
   ColumnConstraint.
Constructors
| NoAutoincrement | |
| Autoincrement | 
data MaybeCollation Source
The AST node corresponding to an optional COLLATE subclause.  Used by
   IndexedColumn and OrderingTerm.
Constructors
| NoCollation | |
| Collation UnqualifiedIdentifier | 
data MaybeColumn Source
The AST node corresponding to an optional COLUMN keyword.
   Used by AlterTableBody.
Constructors
| ElidedColumn | |
| Column | 
Instances
data MaybeConstraintName Source
The AST node corresponding to an optional constraint name subclause.  Used by
   ColumnConstraint and 'Table Constraint'.
Constructors
| NoConstraintName | |
| ConstraintName UnqualifiedIdentifier | 
data MaybeForEachRow Source
The AST node corresponding to an optional FOR EACH ROW qualifier.  Used by
   CreateTrigger.
Constructors
| NoForEachRow | |
| ForEachRow | 
data MaybeForeignKeyClauseDeferrablePart Source
The AST node corresponding to the second partial body of a FOREIGN KEY clause.
   Used by ForeignKeyClause.
data MaybeHaving Source
The AST node corresponding to an optional HAVING subclause.  Used by
   GroupClause.
Constructors
| NoHaving | |
| Having Expression | 
Instances
data MaybeIfExists Source
The AST node corresponding to an optional IF EXISTS qualifier.  Used by
   DropIndex, DropTable, DropTrigger, and DropView.
Constructors
| NoIfExists | |
| IfExists | 
Instances
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.
Constructors
| NoIndexedBy | |
| IndexedBy UnqualifiedIdentifier | |
| NotIndexed | 
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 MaybeReleaseSavepoint Source
The AST node corresponding to an optional RELEASE SAVEPOINT qualifier.
   Used by Release.
data MaybeSavepoint Source
The AST node corresponding to an optional TO SAVEPOINT qualifier.  Used by
   Rollback.
The AST node corresponding to an optional + or - sign.  Used by
   TypeSizeField, DefaultValue, and PragmaValue.
Constructors
| NoSign | |
| PositiveSign | |
| NegativeSign | 
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
Constructors
| ElidedTransaction | |
| Transaction | 
data MaybeTransactionType Source
The AST node corresponding to an optional transaction-type qualifier.  Used
   by Begin.
Constructors
| NoTransactionType | |
| Deferred | |
| Immediate | |
| Exclusive | 
The AST node corresponding to an optional column type.  Used by ColumnDefinition.
data MaybeTypeName Source
Constructors
| NoTypeName | |
| TypeName (OneOrMore UnqualifiedIdentifier) | 
Instances
data MaybeTypeSize Source
The AST node corresponding to an optional size annotation on a column or value
   type.  Used by Type.
Instances
data MaybeUnique Source
The AST node corresponding to an optional UNIQUE qualifier.  Used by
   CreateIndex.
Instances
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.
Constructors
| OrderBy (OneOrMore OrderingTerm) | 
Instances
data OrderingTerm Source
The AST node corresponding to an ordering term subclause.  Used by
   GroupClause and OrderClause.
Constructors
| OrderingTerm Expression MaybeCollation MaybeAscDesc | 
Instances
data PragmaValue Source
The AST node corresponding to a pragma value subclause.  Used by PragmaBody.
Constructors
| SignedIntegerPragmaValue MaybeSign Word64 | |
| SignedFloatPragmaValue MaybeSign NonnegativeDouble | |
| NamePragmaValue UnqualifiedIdentifier | |
| StringPragmaValue String | 
Instances
data QualifiedTableName Source
The AST node corresponding to a qualified table name subclause.  Used by
   Delete, DeleteLimited, Update, and UpdateLimited.
data ResultColumn Source
The AST node corresponding to a result column in a SELECT statement.  Used by
   SelectCore.
Constructors
| Star | |
| TableStar UnqualifiedIdentifier | |
| Result Expression MaybeAs | 
Instances
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.
Constructors
| SelectCore Distinctness (OneOrMore ResultColumn) (Maybe FromClause) (Maybe WhereClause) (Maybe GroupClause) | 
Instances
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.
Constructors
| TableSource SinglyQualifiedIdentifier MaybeAs MaybeIndexedBy | |
| SelectSource Select MaybeAs | |
| SubjoinSource JoinSource | 
Instances
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] | 
Instances
data TableConstraint Source
The AST node corresponding to a table-constraint subclause.  Used by
   CreateTableBody.
Constructors
data TriggerCondition Source
The AST node corresponding to a trigger-condition subclause.  Used by
   CreateTrigger.
Constructors
| DeleteOn | |
| InsertOn | |
| UpdateOn [UnqualifiedIdentifier] | 
data TriggerTime Source
The AST node corresponding to a trigger-time qualifier.  Used by CreateTrigger.
Instances
The AST node corresponding to a column or value type.  Used by
   MaybeType which is used by ColumnDefinition, and by ExpressionCast.
Constructors
| Type TypeAffinity MaybeTypeName MaybeTypeSize | 
data TypeAffinity Source
The AST node corresponding to the affinity of a column or value type.
   Used by Type.
Constructors
| TypeAffinityText | |
| TypeAffinityNumeric | |
| TypeAffinityInteger | |
| TypeAffinityReal | |
| TypeAffinityNone | 
Instances
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.
Constructors
| DoubleSize MaybeSign NonnegativeDouble | |
| IntegerSize MaybeSign Word64 | 
Instances
data UpdateHead Source
The AST node corresponding to an update head.  Used by Update and
   UpdateLimited.
Constructors
| UpdateNoAlternative | |
| UpdateOrRollback | |
| UpdateOrAbort | |
| UpdateOrReplace | |
| UpdateOrFail | |
| UpdateOrIgnore | 
Instances
data WhenClause Source
The AST node corresponding to a WHEN clause.  Used by CreateTrigger.
Constructors
| When Expression | 
Instances
data WhereClause Source
The AST node corresponding to a WHERE clause.  Used by SelectCore,
   Delete, DeleteLimited, Update, and UpdateLimited.
Constructors
| Where Expression | 
Instances
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  | 
| ExpressionLiteralCurrentTime | Represents a literal  | 
| ExpressionLiteralCurrentDate | Represents a literal  | 
| ExpressionLiteralCurrentTimestamp | Represents a literal  | 
| ExpressionVariable | Represents a positional-variable expression, written in SQL as  | 
| ExpressionVariableN Word64 | Represents a numbered positional variable expression, written in
   SQL as  | 
| ExpressionVariableNamed String | Represents a named positional variable expression, written in
   SQL as  | 
| 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  | 
| ExpressionFunctionCallStar UnqualifiedIdentifier | Represents a call to a built-in function, with  | 
| ExpressionCast Expression Type | Represents a type-cast expression. | 
| ExpressionCollate Expression UnqualifiedIdentifier | Represents a  | 
| ExpressionLike Expression LikeType Expression Escape | Represents a textual comparison expression. | 
| ExpressionIsnull Expression | Represents an  | 
| ExpressionNotnull Expression | Represents a  | 
| ExpressionNotNull Expression | Represents a  | 
| ExpressionIs Expression Expression | Represents an  | 
| ExpressionIsNot Expression Expression | Represents an  | 
| ExpressionBetween Expression Expression Expression | Represents a  | 
| ExpressionNotBetween Expression Expression Expression | Represents a  | 
| ExpressionInSelect Expression Select | Represents an  | 
| ExpressionNotInSelect Expression Select | Represents a  | 
| ExpressionInList Expression [Expression] | Represents an  | 
| ExpressionNotInList Expression [Expression] | Represents a  | 
| ExpressionInTable Expression SinglyQualifiedIdentifier | Represents an  | 
| ExpressionNotInTable Expression SinglyQualifiedIdentifier | Represents a  | 
| ExpressionSubquery Select | Represents a subquery  | 
| ExpressionExistsSubquery Select | Represents a subquery  | 
| ExpressionNotExistsSubquery Select | Represents a subquery  | 
| ExpressionCase MaybeSwitchExpression (OneOrMore CasePair) Else | Represents a  | 
| ExpressionRaiseIgnore | Represents a  | 
| ExpressionRaiseRollback String | Represents a  | 
| ExpressionRaiseAbort String | Represents a  | 
| ExpressionRaiseFail String | Represents a  | 
| ExpressionParenthesized Expression | Represents a parenthesized subexpression. | 
Instances
Abstract syntax tree nodes - Statements
data AnyStatement Source
The AST node corresponding to any statement.  Used by StatementList.
   Also useful at top level.
Instances
fromAnyStatement :: StatementClass a => AnyStatement -> aSource
data ExplainableStatement Source
Constructors
| forall t v w . ExplainableStatement (Statement L0 t v w) | 
fromExplainableStatement :: StatementClass a => ExplainableStatement -> aSource
data TriggerStatement Source
Constructors
| forall l v w . TriggerStatement (Statement l T v w) | 
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
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.