| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Database.Beam.Sqlite.Syntax
Description
SQLite implementations of the Beam SQL syntax classes
The SQLite command syntax is implemented by SQLiteCommandSyntax.
Synopsis
- data SqliteSyntax = SqliteSyntax ((SQLData -> Builder) -> Builder) (DList SQLData)
 - data SqliteCommandSyntax
 - newtype SqliteSelectSyntax = SqliteSelectSyntax {}
 - data SqliteInsertSyntax = SqliteInsertSyntax {}
 - newtype SqliteUpdateSyntax = SqliteUpdateSyntax {}
 - newtype SqliteDeleteSyntax = SqliteDeleteSyntax {}
 - data SqliteInsertValuesSyntax
 - data SqliteColumnSchemaSyntax = SqliteColumnSchemaSyntax {}
 - data SqliteExpressionSyntax
 - newtype SqliteValueSyntax = SqliteValueSyntax {}
 - data SqliteDataTypeSyntax = SqliteDataTypeSyntax {}
 - sqliteTextType :: SqliteDataTypeSyntax
 - sqliteBlobType :: SqliteDataTypeSyntax
 - sqliteBigIntType :: SqliteDataTypeSyntax
 - sqliteSerialType :: SqliteDataTypeSyntax
 - fromSqliteCommand :: SqliteCommandSyntax -> SqliteSyntax
 - formatSqliteInsert :: Text -> [Text] -> SqliteInsertValuesSyntax -> SqliteSyntax
 - emit :: ByteString -> SqliteSyntax
 - emitValue :: SQLData -> SqliteSyntax
 - sqliteEscape :: Text -> Text
 - withPlaceholders :: ((SQLData -> Builder) -> Builder) -> Builder
 - sqliteRenderSyntaxScript :: SqliteSyntax -> ByteString
 
SQLite syntaxes
data SqliteSyntax Source #
The syntax for SQLite is stored as a Builder along with a list of data
 that hasn't been serialized yet.
The first argument is a function that receives a builder for SQLData and
 returns the concrete syntax to embed into the query. For queries sent to the
 backend, this is simply a function that returns "?". Thus, the syntax sent
 to the backend includes proper placeholders. The list of data is sent to the
 SQLite library for proper escaping.
When the syntax is being serialized for display (for use in beam migrate for example), the data builder attempts to properly format and escape the data. This returns syntax suitable for inclusion in scripts. In this case, the value list is ignored.
Instances
| Eq SqliteSyntax Source # | |
Defined in Database.Beam.Sqlite.Syntax  | |
| Show SqliteSyntax Source # | |
Defined in Database.Beam.Sqlite.Syntax Methods showsPrec :: Int -> SqliteSyntax -> ShowS # show :: SqliteSyntax -> String # showList :: [SqliteSyntax] -> ShowS #  | |
| Semigroup SqliteSyntax Source # | |
Defined in Database.Beam.Sqlite.Syntax Methods (<>) :: SqliteSyntax -> SqliteSyntax -> SqliteSyntax # sconcat :: NonEmpty SqliteSyntax -> SqliteSyntax # stimes :: Integral b => b -> SqliteSyntax -> SqliteSyntax #  | |
| Monoid SqliteSyntax Source # | |
Defined in Database.Beam.Sqlite.Syntax Methods mempty :: SqliteSyntax # mappend :: SqliteSyntax -> SqliteSyntax -> SqliteSyntax # mconcat :: [SqliteSyntax] -> SqliteSyntax #  | |
| Hashable SqliteSyntax Source # | |
Defined in Database.Beam.Sqlite.Syntax  | |
| Sql92DisplaySyntax SqliteSyntax Source # | |
Defined in Database.Beam.Sqlite.Syntax Methods displaySyntax :: SqliteSyntax -> String #  | |
data SqliteCommandSyntax Source #
A SQLite command. INSERT is special cased to handle AUTO INCREMENT
 columns. The fromSqliteCommand function will take an SqliteCommandSyntax
 and convert it into the correct SqliteSyntax.
Instances
newtype SqliteSelectSyntax Source #
SQLite SELECT syntax
Constructors
| SqliteSelectSyntax | |
Fields  | |
Instances
| HasQBuilder SqliteSelectSyntax Source # | |
Defined in Database.Beam.Sqlite.Syntax Methods buildSqlQuery :: Projectible (Sql92SelectExpressionSyntax SqliteSelectSyntax) a => TablePrefix -> Q SqliteSelectSyntax db s a -> SqliteSelectSyntax #  | |
| IsSql92SelectSyntax SqliteSelectSyntax Source # | |
Defined in Database.Beam.Sqlite.Syntax Associated Types  | |
| type Sql92SelectOrderingSyntax SqliteSelectSyntax Source # | |
Defined in Database.Beam.Sqlite.Syntax  | |
| type Sql92SelectSelectTableSyntax SqliteSelectSyntax Source # | |
data SqliteInsertSyntax Source #
SQLite INSERT syntax. This doesn't directly wrap SqliteSyntax because
 we need to do some processing on INSERT statements to deal with AUTO
 INCREMENT columns. Use formatSqliteInsert to turn SqliteInsertSyntax
 into SqliteSyntax.
Constructors
| SqliteInsertSyntax | |
Fields  | |
Instances
| IsSql92InsertSyntax SqliteInsertSyntax Source # | |
Defined in Database.Beam.Sqlite.Syntax Associated Types type Sql92InsertValuesSyntax SqliteInsertSyntax :: * # Methods insertStmt :: Text -> [Text] -> Sql92InsertValuesSyntax SqliteInsertSyntax -> SqliteInsertSyntax #  | |
| type Sql92InsertValuesSyntax SqliteInsertSyntax Source # | |
newtype SqliteUpdateSyntax Source #
SQLite UPDATE syntax
Constructors
| SqliteUpdateSyntax | |
Fields  | |
Instances
| IsSql92UpdateSyntax SqliteUpdateSyntax Source # | |
Defined in Database.Beam.Sqlite.Syntax Associated Types  | |
| type Sql92UpdateExpressionSyntax SqliteUpdateSyntax Source # | |
| type Sql92UpdateFieldNameSyntax SqliteUpdateSyntax Source # | |
Defined in Database.Beam.Sqlite.Syntax  | |
newtype SqliteDeleteSyntax Source #
SQLite DELETE syntax
Constructors
| SqliteDeleteSyntax | |
Fields  | |
Instances
| IsSql92DeleteSyntax SqliteDeleteSyntax Source # | |
Defined in Database.Beam.Sqlite.Syntax Associated Types Methods deleteStmt :: Text -> Maybe Text -> Maybe (Sql92DeleteExpressionSyntax SqliteDeleteSyntax) -> SqliteDeleteSyntax #  | |
| type Sql92DeleteExpressionSyntax SqliteDeleteSyntax Source # | |
data SqliteInsertValuesSyntax Source #
SQLite VALUES clause in INSERT. Expressions need to be handled
 explicitly in order to deal with DEFAULT values and AUTO INCREMENT
 columns.
Constructors
| SqliteInsertExpressions [[SqliteExpressionSyntax]] | |
| SqliteInsertFromSql SqliteSelectSyntax | 
Instances
data SqliteColumnSchemaSyntax Source #
SQLite syntax for column schemas in CREATE TABLE or ALTER COLUMN ... ADD
 COLUMN statements
Constructors
| SqliteColumnSchemaSyntax | |
Fields  | |
Instances
data SqliteExpressionSyntax Source #
Implements beam SQL expression syntaxes
Instances
newtype SqliteValueSyntax Source #
SQLite syntax for values that can be embedded in SqliteSyntax
Constructors
| SqliteValueSyntax | |
Fields  | |
Instances
SQLite data type syntax
data SqliteDataTypeSyntax Source #
SQLite syntax that implements IsSql92DataTypeSyntax and a good portion of
 IsSql99DataTypeSyntax, except for array and row types.
Constructors
| SqliteDataTypeSyntax | |
Instances
Building and consuming SqliteSyntax
fromSqliteCommand :: SqliteCommandSyntax -> SqliteSyntax Source #
Convert a SqliteCommandSyntax into a renderable SqliteSyntax
formatSqliteInsert :: Text -> [Text] -> SqliteInsertValuesSyntax -> SqliteSyntax Source #
Format a SQLite INSERT expression for the given table name, fields, and values.
emit :: ByteString -> SqliteSyntax Source #
Embed a ByteString directly in the syntax
emitValue :: SQLData -> SqliteSyntax Source #
Emit a properly escaped value into the syntax
This causes a literal ? 3
sqliteEscape :: Text -> Text Source #
A best effort attempt to implement the escaping rules of SQLite. This is never used to escape data sent to the database; only for emitting scripts or displaying syntax to the user.
withPlaceholders :: ((SQLData -> Builder) -> Builder) -> Builder Source #
Convert the first argument of SQLiteSyntax to a ByteString Builder,
 where all the data has been replaced by "?" placeholders.
sqliteRenderSyntaxScript :: SqliteSyntax -> ByteString Source #
Render a SqliteSyntax as a lazy ByteString, for purposes of
 displaying to a user. Embedded SQLData is directly embedded into the
 concrete syntax, with a best effort made to escape strings.