orville-postgresql-1.0.0.0: A Haskell library for PostgreSQL
CopyrightFlipstone Technology Partners 2023
LicenseMIT
StabilityStable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Orville.PostgreSQL.Raw.RawSql

Description

The functions in this module are named with the intent that it is imported qualified as RawSql.

Since: 1.0.0.0

Synopsis

Documentation

data RawSql Source #

RawSql provides a type for efficiently constructing raw SQL statements from smaller parts and then executing them. It also supports using placeholder values to pass parameters with a query without having to interpolate them as part of the actual SQL state and being exposed to SQL injection.

Since: 1.0.0.0

Instances

Instances details
Monoid RawSql Source # 
Instance details

Defined in Orville.PostgreSQL.Raw.RawSql

Semigroup RawSql Source # 
Instance details

Defined in Orville.PostgreSQL.Raw.RawSql

SqlExpression RawSql Source # 
Instance details

Defined in Orville.PostgreSQL.Raw.RawSql

parameter :: SqlValue -> RawSql Source #

Includes an input parameter in the RawSql statement that will be passed using placeholders (e.g. '$1') rather than being included directly in the SQL statement. This is the correct way to include input from untrusted sources as part of a RawSql query. The parameter must be formatted in a textual representation, which the database will interpret. The database type for the value will be inferred by the database based on its usage in the query.

Since: 1.0.0.0

fromString :: String -> RawSql Source #

Constructs a RawSql from a String value using UTF-8 encoding.

Note that because the string is treated as raw SQL, it is completely up to the caller to protected againt SQL-injection attacks when using this function. Never use this function with input read from an untrusted source.

Since: 1.0.0.0

fromText :: Text -> RawSql Source #

Constructs a RawSql from a Text value using UTF-8 encoding.

Note that because the text is treated as raw SQL, it is completely up to the caller to protected againt SQL-injection attacks when using this function. Never use this function with input read from an untrusted source.

Since: 1.0.0.0

fromBytes :: ByteString -> RawSql Source #

Constructs a RawSql from a ByteString value, which is assumed to be encoded sensibly for the database to handle.

Note that because the string is treated as raw SQL, it is completely up to the caller to protected againt SQL-injection attacks when using this function. Never use this function with input read from an untrusted source.

Since: 1.0.0.0

intercalate :: (SqlExpression sql, Foldable f) => RawSql -> f sql -> RawSql Source #

Concatenates a list of RawSql values using another RawSql value as the separator between the items.

Since: 1.0.0.0

execute :: SqlExpression sql => Connection -> sql -> IO Result Source #

Executes a RawSql value using the executeRaw function. Make sure to read the documentation of executeRaw for caveats and warnings. Use with caution.

Note that because this is done in IO, no callback functions are available to be called.

Since: 1.0.0.0

executeVoid :: SqlExpression sql => Connection -> sql -> IO () Source #

Executes a RawSql value using the executeRawVoid function. Make sure to read the documentation of executeRawVoid for caveats and warnings. Use with caution.

Note that because this is done in IO, no callback functions are available to be called.

Since: 1.0.0.0

connectionQuoting :: Connection -> Quoting IO Source #

Quoting done in IO using the quoting functions provided by the connection, which can apply quoting based on the specific connection properties.

If you don't have a connection available and are only planning on using the SQL for explanatory or example purposes, see exampleQuoting.

Since: 1.0.0.0

Fragments provided for convenience

space :: RawSql Source #

Just a plain old space, provided for convenience.

comma :: RawSql Source #

Just a plain old comma, provided for convenience.

commaSpace :: RawSql Source #

Comma space separator, provided for convenience.

leftParen :: RawSql Source #

Just a plain old left paren, provided for convenience.

rightParen :: RawSql Source #

Just a plain old right paren, provided for convenience.

dot :: RawSql Source #

Just a plain period, provided for convenience.

doubleQuote :: RawSql Source #

Just a plain double quote, provided for convenience.

doubleColon :: RawSql Source #

Just two colons, provided for convenience.

stringLiteral :: ByteString -> RawSql Source #

Includes a bytestring value as a string literal in the SQL statement. The string literal will be quoted and escaped for you; the value provided should not include surrounding quotes or quote special characters.

Note: It's better to use the parameter function where possible to pass values to be used as input to a SQL statement. There are some situations where PostgreSQL does not allow this, however (for instance, in some DDL statements). This function is provided for those situations.

Since: 1.0.0.0

identifier :: ByteString -> RawSql Source #

Includes a bytestring value as an identifier in the SQL statement. The identifier will be quoted and escaped for you; the value provided should not include surrounding quotes or quote special characters.

Since: 1.0.0.0

parenthesized :: SqlExpression sql => sql -> RawSql Source #

Constructs a RawSql by putting parentheses around an arbitrary expression. The result is returned as a RawSql. It is up to the caller to decide whether it should be wrapped in a more-specific expression type.

Since: 1.0.0.0

Integer values as literals

intDecLiteral :: Int -> RawSql Source #

Constructs a RawSql from an Int value. The integral value is included directly in the SQL string, not passed as a parameter. When dealing with user input, it is better to use parameter whenever possible.

Since: 1.0.0.0

int8DecLiteral :: Int8 -> RawSql Source #

Constructs a RawSql from an Int8 value. The integral value is included directly in the SQL string, not passed as a parameter. When dealing with user input, it is better to use parameter whenever possible.

Since: 1.0.0.0

int16DecLiteral :: Int16 -> RawSql Source #

Constructs a RawSql from an Int16 value. The integral value is included directly in the SQL string, not passed as a parameter. When dealing with user input, it is better to use parameter whenever possible.

Since: 1.0.0.0

int32DecLiteral :: Int32 -> RawSql Source #

Constructs a RawSql from an Int32 value. The integral value is included directly in the SQL string, not passed as a parameter. When dealing with user input, it is better to use parameter whenever possible.

Since: 1.0.0.0

int64DecLiteral :: Int64 -> RawSql Source #

Constructs a RawSql from an Int64 value. The integral value is included directly in the SQL string, not passed as a parameter. When dealing with user input, it is better to use parameter whenever possible.

Since: 1.0.0.0

Generic interface for generating SQL

class SqlExpression a where Source #

SqlExpression provides a common interface for converting types to and from RawSql, either via toRawSql and unsafeFromRawSql, or the convenience function unsafeSqlExpression. Orville defines a large number of types that represent various fragments of SQL statements as well as functions to help construct them safely. These functions can be found in Expr. These types all provide SqlExpression instances as an escape hatch to allow you to pass any SQL you wish in place of what Orville directly supports. This should be used with great care as Orville cannot guarantee that the SQL you pass can be used to generate valid SQL in conjunction with the rest of the Expr API.

Since: 1.0.0.0

Instances

Instances details
SqlExpression MigrationStep Source #

Since: 1.0.0.0

Instance details

Defined in Orville.PostgreSQL.AutoMigration

SqlExpression BinaryOperator Source #

Since: 1.0.0.0

Instance details

Defined in Orville.PostgreSQL.Expr.BinaryOperator

SqlExpression ColumnConstraint Source #

Since: 1.0.0.0

Instance details

Defined in Orville.PostgreSQL.Expr.ColumnDefinition

SqlExpression ColumnDefault Source #

Since: 1.0.0.0

Instance details

Defined in Orville.PostgreSQL.Expr.ColumnDefinition

SqlExpression ColumnDefinition Source #

Since: 1.0.0.0

Instance details

Defined in Orville.PostgreSQL.Expr.ColumnDefinition

SqlExpression AllCursors Source #

Since: 1.0.0.0

Instance details

Defined in Orville.PostgreSQL.Expr.Cursor

SqlExpression CloseExpr Source #

Since: 1.0.0.0

Instance details

Defined in Orville.PostgreSQL.Expr.Cursor

SqlExpression CursorDirection Source #

Since: 1.0.0.0

Instance details

Defined in Orville.PostgreSQL.Expr.Cursor

SqlExpression DeclareExpr Source #

Since: 1.0.0.0

Instance details

Defined in Orville.PostgreSQL.Expr.Cursor

SqlExpression FetchExpr Source #

Since: 1.0.0.0

Instance details

Defined in Orville.PostgreSQL.Expr.Cursor

SqlExpression HoldExpr Source #

Since: 1.0.0.0

Instance details

Defined in Orville.PostgreSQL.Expr.Cursor

SqlExpression MoveExpr Source #

Since: 1.0.0.0

Instance details

Defined in Orville.PostgreSQL.Expr.Cursor

SqlExpression ScrollExpr Source #

Since: 1.0.0.0

Instance details

Defined in Orville.PostgreSQL.Expr.Cursor

SqlExpression DataType Source #

Since: 1.0.0.0

Instance details

Defined in Orville.PostgreSQL.Expr.DataType

SqlExpression DeleteExpr Source #

Since: 1.0.0.0

Instance details

Defined in Orville.PostgreSQL.Expr.Delete

SqlExpression GroupByClause Source #

Since: 1.0.0.0

Instance details

Defined in Orville.PostgreSQL.Expr.GroupBy

SqlExpression GroupByExpr Source #

Since: 1.0.0.0

Instance details

Defined in Orville.PostgreSQL.Expr.GroupBy

SqlExpression IfExists Source #

Since: 1.0.0.0

Instance details

Defined in Orville.PostgreSQL.Expr.IfExists

SqlExpression ConcurrentlyExpr Source #

Since: 1.0.0.0

Instance details

Defined in Orville.PostgreSQL.Expr.Index

SqlExpression CreateIndexExpr Source #

Since: 1.0.0.0

Instance details

Defined in Orville.PostgreSQL.Expr.Index

SqlExpression DropIndexExpr Source #

Since: 1.0.0.0

Instance details

Defined in Orville.PostgreSQL.Expr.Index

SqlExpression IndexBodyExpr Source #

Since: 1.0.0.0

Instance details

Defined in Orville.PostgreSQL.Expr.Index

SqlExpression InsertColumnList Source #

Since: 1.0.0.0

Instance details

Defined in Orville.PostgreSQL.Expr.Insert

SqlExpression InsertExpr Source #

Since: 1.0.0.0

Instance details

Defined in Orville.PostgreSQL.Expr.Insert

SqlExpression InsertSource Source #

Since: 1.0.0.0

Instance details

Defined in Orville.PostgreSQL.Expr.Insert

SqlExpression RowValues Source #

Since: 1.0.0.0

Instance details

Defined in Orville.PostgreSQL.Expr.Insert

SqlExpression ColumnName Source #

Since: 1.0.0.0

Instance details

Defined in Orville.PostgreSQL.Expr.Internal.Name.ColumnName

SqlExpression ConstraintName Source #

Since: 1.0.0.0

Instance details

Defined in Orville.PostgreSQL.Expr.Internal.Name.ConstraintName

SqlExpression CursorName Source #

Since: 1.0.0.0

Instance details

Defined in Orville.PostgreSQL.Expr.Internal.Name.CursorName

SqlExpression FunctionName Source #

Since: 1.0.0.0

Instance details

Defined in Orville.PostgreSQL.Expr.Internal.Name.FunctionName

SqlExpression Identifier Source #

Since: 1.0.0.0

Instance details

Defined in Orville.PostgreSQL.Expr.Internal.Name.Identifier

SqlExpression IndexName Source #

Since: 1.0.0.0

Instance details

Defined in Orville.PostgreSQL.Expr.Internal.Name.IndexName

SqlExpression SavepointName Source #

Since: 1.0.0.0

Instance details

Defined in Orville.PostgreSQL.Expr.Internal.Name.SavepointName

SqlExpression SchemaName Source #

Since: 1.0.0.0

Instance details

Defined in Orville.PostgreSQL.Expr.Internal.Name.SchemaName

SqlExpression SequenceName Source #

Since: 1.0.0.0

Instance details

Defined in Orville.PostgreSQL.Expr.Internal.Name.SequenceName

SqlExpression TableName Source #

Since: 1.0.0.0

Instance details

Defined in Orville.PostgreSQL.Expr.Internal.Name.TableName

SqlExpression LimitExpr Source #

Since: 1.0.0.0

Instance details

Defined in Orville.PostgreSQL.Expr.LimitExpr

SqlExpression OffsetExpr Source #

Since: 1.0.0.0

Instance details

Defined in Orville.PostgreSQL.Expr.OffsetExpr

SqlExpression OrderByClause Source # 
Instance details

Defined in Orville.PostgreSQL.Expr.OrderBy

SqlExpression OrderByDirection Source # 
Instance details

Defined in Orville.PostgreSQL.Expr.OrderBy

SqlExpression OrderByExpr Source #

Since: 1.0.0.0

Instance details

Defined in Orville.PostgreSQL.Expr.OrderBy

SqlExpression DerivedColumn Source # 
Instance details

Defined in Orville.PostgreSQL.Expr.Query

SqlExpression QueryExpr Source # 
Instance details

Defined in Orville.PostgreSQL.Expr.Query

SqlExpression SelectList Source # 
Instance details

Defined in Orville.PostgreSQL.Expr.Query

SqlExpression TableExpr Source # 
Instance details

Defined in Orville.PostgreSQL.Expr.Query

SqlExpression ReturningExpr Source # 
Instance details

Defined in Orville.PostgreSQL.Expr.ReturningExpr

SqlExpression SelectClause Source # 
Instance details

Defined in Orville.PostgreSQL.Expr.Select

SqlExpression SelectExpr Source # 
Instance details

Defined in Orville.PostgreSQL.Expr.Select

SqlExpression AlterSequenceExpr Source # 
Instance details

Defined in Orville.PostgreSQL.Expr.SequenceDefinition

SqlExpression CacheExpr Source # 
Instance details

Defined in Orville.PostgreSQL.Expr.SequenceDefinition

SqlExpression CreateSequenceExpr Source # 
Instance details

Defined in Orville.PostgreSQL.Expr.SequenceDefinition

SqlExpression CycleExpr Source # 
Instance details

Defined in Orville.PostgreSQL.Expr.SequenceDefinition

SqlExpression DropSequenceExpr Source # 
Instance details

Defined in Orville.PostgreSQL.Expr.SequenceDefinition

SqlExpression IncrementByExpr Source # 
Instance details

Defined in Orville.PostgreSQL.Expr.SequenceDefinition

SqlExpression MaxValueExpr Source # 
Instance details

Defined in Orville.PostgreSQL.Expr.SequenceDefinition

SqlExpression MinValueExpr Source # 
Instance details

Defined in Orville.PostgreSQL.Expr.SequenceDefinition

SqlExpression StartWithExpr Source # 
Instance details

Defined in Orville.PostgreSQL.Expr.SequenceDefinition

SqlExpression ForeignKeyActionExpr Source # 
Instance details

Defined in Orville.PostgreSQL.Expr.TableConstraint

SqlExpression ForeignKeyDeleteActionExpr Source # 
Instance details

Defined in Orville.PostgreSQL.Expr.TableConstraint

SqlExpression ForeignKeyUpdateActionExpr Source # 
Instance details

Defined in Orville.PostgreSQL.Expr.TableConstraint

SqlExpression TableConstraint Source # 
Instance details

Defined in Orville.PostgreSQL.Expr.TableConstraint

SqlExpression AlterNotNull Source # 
Instance details

Defined in Orville.PostgreSQL.Expr.TableDefinition

SqlExpression AlterTableAction Source # 
Instance details

Defined in Orville.PostgreSQL.Expr.TableDefinition

SqlExpression AlterTableExpr Source # 
Instance details

Defined in Orville.PostgreSQL.Expr.TableDefinition

SqlExpression CreateTableExpr Source # 
Instance details

Defined in Orville.PostgreSQL.Expr.TableDefinition

SqlExpression DropTableExpr Source # 
Instance details

Defined in Orville.PostgreSQL.Expr.TableDefinition

SqlExpression PrimaryKeyExpr Source # 
Instance details

Defined in Orville.PostgreSQL.Expr.TableDefinition

SqlExpression UsingClause Source # 
Instance details

Defined in Orville.PostgreSQL.Expr.TableDefinition

SqlExpression TableReferenceList Source # 
Instance details

Defined in Orville.PostgreSQL.Expr.TableReferenceList

SqlExpression IntervalArgument Source # 
Instance details

Defined in Orville.PostgreSQL.Expr.Time

SqlExpression BeginTransactionExpr Source # 
Instance details

Defined in Orville.PostgreSQL.Expr.Transaction

SqlExpression CommitExpr Source # 
Instance details

Defined in Orville.PostgreSQL.Expr.Transaction

SqlExpression IsolationLevel Source # 
Instance details

Defined in Orville.PostgreSQL.Expr.Transaction

SqlExpression ReleaseSavepointExpr Source # 
Instance details

Defined in Orville.PostgreSQL.Expr.Transaction

SqlExpression RollbackExpr Source # 
Instance details

Defined in Orville.PostgreSQL.Expr.Transaction

SqlExpression SavepointExpr Source # 
Instance details

Defined in Orville.PostgreSQL.Expr.Transaction

SqlExpression TransactionMode Source # 
Instance details

Defined in Orville.PostgreSQL.Expr.Transaction

SqlExpression SetClause Source # 
Instance details

Defined in Orville.PostgreSQL.Expr.Update

SqlExpression SetClauseList Source # 
Instance details

Defined in Orville.PostgreSQL.Expr.Update

SqlExpression UpdateExpr Source # 
Instance details

Defined in Orville.PostgreSQL.Expr.Update

SqlExpression ParameterName Source # 
Instance details

Defined in Orville.PostgreSQL.Expr.ValueExpression

SqlExpression ValueExpression Source # 
Instance details

Defined in Orville.PostgreSQL.Expr.ValueExpression

SqlExpression BooleanExpr Source # 
Instance details

Defined in Orville.PostgreSQL.Expr.WhereClause

SqlExpression InValuePredicate Source # 
Instance details

Defined in Orville.PostgreSQL.Expr.WhereClause

SqlExpression WhereClause Source # 
Instance details

Defined in Orville.PostgreSQL.Expr.WhereClause

SqlExpression RawSql Source # 
Instance details

Defined in Orville.PostgreSQL.Raw.RawSql

SqlExpression (Qualified name) Source #

Since: 1.0.0.0

Instance details

Defined in Orville.PostgreSQL.Expr.Internal.Name.Qualified

unsafeSqlExpression :: SqlExpression a => String -> a Source #

A convenience function for creating an arbitrary SqlExpression from a String. Great care should be exercised when using this function as it cannot provide any sort of guarantee that the string passed is usable to generate valid SQL via the rest of Orville's Expr API.

For example, if one wanted build a boolean expression not supported by Orville, you can do it like so:

import qualified Orville.PostgreSQL.Expr as Expr

a :: Expr.BooleanExpr
a RawSql.unsafeSqlExpression "foo BETWEEN 1 AND 3"

Since: 1.0.0.0

toBytesAndParams :: (SqlExpression sql, Monad m) => Quoting m -> sql -> m (ByteString, [Maybe PgTextFormatValue]) Source #

Constructs the actual SQL bytestring and parameter values that will be passed to the database to execute a RawSql query. Any string literals that are included in the SQL expression will be quoted using the given quoting directive.

Since: 1.0.0.0

toExampleBytes :: SqlExpression sql => sql -> ByteString Source #

Builds the bytes that represent the raw SQL. These bytes may not be executable on their own, because they may contain placeholders that must be filled in, but can be useful for inspecting SQL queries.

Since: 1.0.0.0

data Quoting m Source #

Provides procedures for quoting parts of a raw SQL query so that they can be safely executed. Quoting may be done in some Monad m, allowing for the use of quoting operations provided by Connection, which operates in the IO monad.

See connectionQuoting and exampleQuoting.

Since: 1.0.0.0

exampleQuoting :: Quoting Identity Source #

Quoting done in pure Haskell that is suitable for showing SQL examples, but is not guaranteed to be sufficient for all database connections. For quoting that is based on the actual connection to the database, see connectionQuoting.

Since: 1.0.0.0