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

Orville.PostgreSQL

Description

Orville.PostgreSQL is the module you will most often want to import for using Orville. It re-exports most of the functions you need for everyday basic operations on table entities. If you cannot find the function you need exported here, you may be able to find it in one of the modules that re-exports more functions for a specific area:

Of course, you can always use the table of contents for the package to see all the exports Orville offers.

Since: 1.0.0.0

Synopsis

Basic operations on entities in tables

insertEntity :: MonadOrville m => TableDefinition key writeEntity readEntity -> writeEntity -> m () Source #

Inserts an entity into the specified table.

Since: 1.0.0.0

insertEntityAndReturnRowCount :: MonadOrville m => TableDefinition key writeEntity readEntity -> writeEntity -> m Int Source #

Inserts an entity into the specified table. Returns the number of rows affected by the query.

Since: 1.0.0.0

insertAndReturnEntity :: MonadOrville m => TableDefinition key writeEntity readEntity -> writeEntity -> m readEntity Source #

Inserts an entity into the specified table, returning the data inserted into the database.

You can use this function to obtain any column values filled in by the database, such as auto-incrementing ids.

Since: 1.0.0.0

insertEntities :: MonadOrville m => TableDefinition key writeEntity readEntity -> NonEmpty writeEntity -> m () Source #

Inserts a non-empty list of entities into the specified table.

Since: 1.0.0.0

insertEntitiesAndReturnRowCount :: MonadOrville m => TableDefinition key writeEntity readEntity -> NonEmpty writeEntity -> m Int Source #

Inserts a non-empty list of entities into the specified table. Returns the number of rows affected by the query.

Since: 1.0.0.0

insertAndReturnEntities :: MonadOrville m => TableDefinition key writeEntity readEntity -> NonEmpty writeEntity -> m [readEntity] Source #

Inserts a non-empty list of entities into the specified table, returning the data that was inserted into the database.

You can use this function to obtain any column values filled in by the database, such as auto-incrementing ids.

Since: 1.0.0.0

updateEntity :: MonadOrville m => TableDefinition (HasKey key) writeEntity readEntity -> key -> writeEntity -> m () Source #

Updates the row with the given key with the data given by writeEntity.

Since: 1.0.0.0

updateEntityAndReturnRowCount :: MonadOrville m => TableDefinition (HasKey key) writeEntity readEntity -> key -> writeEntity -> m Int Source #

Updates the row with the given key with the data given by writeEntity. Returns the number of rows affected by the query.

Since: 1.0.0.0

updateAndReturnEntity :: MonadOrville m => TableDefinition (HasKey key) writeEntity readEntity -> key -> writeEntity -> m (Maybe readEntity) Source #

Updates the row with the given key with the data given by writeEntity, returning the updated row from the database. If no row matches the given key, Nothing will be returned.

You can use this function to obtain any column values computed by the database during the update, including columns with triggers attached to them.

Since: 1.0.0.0

updateFields :: MonadOrville m => TableDefinition (HasKey key) writeEntity readEntity -> NonEmpty SetClause -> Maybe BooleanExpr -> m () Source #

Applies the given SetClauses to the rows in the table that match the given where condition. The easiest way to construct a SetClause is via the setField function (also exported as .:=).

Since: 1.0.0.0

updateFieldsAndReturnEntities :: MonadOrville m => TableDefinition (HasKey key) writeEntity readEntity -> NonEmpty SetClause -> Maybe BooleanExpr -> m [readEntity] Source #

Like updateFields, but uses a RETURNING clause to return the updated version of any rows that were affected by the update.

Since: 1.0.0.0

updateFieldsAndReturnRowCount :: MonadOrville m => TableDefinition (HasKey key) writeEntity readEntity -> NonEmpty SetClause -> Maybe BooleanExpr -> m Int Source #

Applies the given SetClauses to the rows in the table that match the given where condition. The easiest way to construct a SetClause is via the setField function (also exported as .:=). Returns the number of rows affected by the query.

Since: 1.0.0.0

deleteEntity :: MonadOrville m => TableDefinition (HasKey key) writeEntity readEntity -> key -> m () Source #

Deletes the row with the given key.

Since: 1.0.0.0

deleteEntityAndReturnRowCount :: MonadOrville m => TableDefinition (HasKey key) writeEntity readEntity -> key -> m Int Source #

Deletes the row with the given key. Returns the number of rows affected by the query.

Since: 1.0.0.0

deleteAndReturnEntity :: MonadOrville m => TableDefinition (HasKey key) writeEntity readEntity -> key -> m (Maybe readEntity) Source #

Deletes the row with the given key, returning the row that was deleted. If no row matches the given key, Nothing is returned.

Since: 1.0.0.0

deleteEntities :: MonadOrville m => TableDefinition key writeEntity readEntity -> Maybe BooleanExpr -> m () Source #

Deletes all rows in the given table that match the where condition.

Since: 1.0.0.0

deleteEntitiesAndReturnRowCount :: MonadOrville m => TableDefinition key writeEntity readEntity -> Maybe BooleanExpr -> m Int Source #

Deletes all rows in the given table that match the where condition. Returns the number of rows affected by the query.

Since: 1.0.0.0

deleteAndReturnEntities :: MonadOrville m => TableDefinition key writeEntity readEntity -> Maybe BooleanExpr -> m [readEntity] Source #

Deletes all rows in the given table that match the where condition, returning the rows that were deleted.

Since: 1.0.0.0

findEntitiesBy :: MonadOrville m => TableDefinition key writeEntity readEntity -> SelectOptions -> m [readEntity] Source #

Finds all the entities in the given table according to the specified SelectOptions, which may include where conditions to match, ordering specifications, etc.

Since: 1.0.0.0

findFirstEntityBy :: MonadOrville m => TableDefinition key writeEntity readEntity -> SelectOptions -> m (Maybe readEntity) Source #

Like findEntitiesBy, but adds a 'LIMIT 1' to the query and then returns the first item from the list. Usually when you use this you will want to provide an order by clause in the SelectOptions because the database will not guarantee ordering.

Since: 1.0.0.0

findEntity :: MonadOrville m => TableDefinition (HasKey key) writeEntity readEntity -> key -> m (Maybe readEntity) Source #

Finds a single entity by the table's primary key value.

Since: 1.0.0.0

findEntities :: MonadOrville m => TableDefinition (HasKey key) writeEntity readEntity -> NonEmpty key -> m [readEntity] Source #

Finds multiple entities by the table's primary key.

Since: 1.0.0.0

A simple starter monad for running Orville operations

data Orville a Source #

The Orville Monad provides an easy starter implementation of MonadOrville when you don't have a monad specific to your application that you need to use.

If you want to add Orville capabilities to your own monad, take a look at MonadOrville to learn what needs to be done.

Since: 1.0.0.0

Instances

Instances details
MonadIO Orville Source # 
Instance details

Defined in Orville.PostgreSQL.Monad.Orville

Methods

liftIO :: IO a -> Orville a #

Applicative Orville Source # 
Instance details

Defined in Orville.PostgreSQL.Monad.Orville

Methods

pure :: a -> Orville a #

(<*>) :: Orville (a -> b) -> Orville a -> Orville b #

liftA2 :: (a -> b -> c) -> Orville a -> Orville b -> Orville c #

(*>) :: Orville a -> Orville b -> Orville b #

(<*) :: Orville a -> Orville b -> Orville a #

Functor Orville Source # 
Instance details

Defined in Orville.PostgreSQL.Monad.Orville

Methods

fmap :: (a -> b) -> Orville a -> Orville b #

(<$) :: a -> Orville b -> Orville a #

Monad Orville Source # 
Instance details

Defined in Orville.PostgreSQL.Monad.Orville

Methods

(>>=) :: Orville a -> (a -> Orville b) -> Orville b #

(>>) :: Orville a -> Orville b -> Orville b #

return :: a -> Orville a #

MonadCatch Orville Source # 
Instance details

Defined in Orville.PostgreSQL.Monad.Orville

Methods

catch :: Exception e => Orville a -> (e -> Orville a) -> Orville a #

MonadThrow Orville Source # 
Instance details

Defined in Orville.PostgreSQL.Monad.Orville

Methods

throwM :: Exception e => e -> Orville a #

MonadOrville Orville Source # 
Instance details

Defined in Orville.PostgreSQL.Monad.Orville

MonadOrvilleControl Orville Source # 
Instance details

Defined in Orville.PostgreSQL.Monad.Orville

Methods

liftWithConnection :: (forall a. (Connection -> IO a) -> IO a) -> (Connection -> Orville b) -> Orville b Source #

liftCatch :: Exception e => (forall a. IO a -> (e -> IO a) -> IO a) -> Orville b -> (e -> Orville b) -> Orville b Source #

liftMask :: (forall b. ((forall a. IO a -> IO a) -> IO b) -> IO b) -> ((forall a. Orville a -> Orville a) -> Orville c) -> Orville c Source #

HasOrvilleState Orville Source # 
Instance details

Defined in Orville.PostgreSQL.Monad.Orville

runOrville :: ConnectionPool -> Orville a -> IO a Source #

Runs an Orville operation in the IO monad using the given connection pool.

This will run the Orville operation with the ErrorDetailLevel set to the default. If you want to run with a different detail level, you can use newOrvilleState to create a state with the desired detail level and then use runOrvilleWithState.

Since: 1.0.0.0

runOrvilleWithState :: OrvilleState -> Orville a -> IO a Source #

Runs an Orville operation in the IO monad, starting from the provided OrvilleState.

Caution: If you harvest an OrvilleState from inside a MonadOrville monad using askOrvilleState, you may pick up connection tracking state that you didn't intend to. You may want to use resetOrvilleState in this situation to get a new initial state before passing it to runOrvilleWithState.

On the other hand, if you know that you want to pass the existing connection state from another monad into the Orville monad, this is how you do it.

Since: 1.0.0.0

Creating a connection pool

data ConnectionOptions Source #

Configuration options to pass to createConnectionPool to specify the parameters for the pool and the connections that it creates.

Since: 1.0.0.0

Constructors

ConnectionOptions 

Fields

createConnectionPool :: ConnectionOptions -> IO ConnectionPool Source #

createConnectionPool allocates a pool of connections to a PostgreSQL server.

Since: 1.0.0.0

data NoticeReporting Source #

An option for createConnectionPool that indicates whether LibPQ should print notice reports for warnings to the console.

Since: 1.0.0.0

data MaxConnections Source #

Values for the connectionMaxConnections field of ConnectionOptions.

Since: 1.0.0.0

Constructors

MaxConnectionsTotal Int

MaxConnectionsTotal creates a connection pool that will never allocate more than the specified number of connections. The total count of connections will be spread evenly across the all the stripes in the pool. If the number of stripes does not divide the total count evenly, any remainder will be unused.

MaxConnectionsPerStripe Int

MaxConnectionsPerStripe creates a connection pool that will allocate up to the specified number of connections in each stripe. In this case the total possible number of simultaneous connections will be this value multiplied by the number of stripes.

data StripeOption Source #

Values for the connectionPoolStripes field of ConnectionOptions.

Since: 1.0.0.0

Constructors

OneStripePerCapability

OneStripePerCapability will cause the connection pool to be set up with one stripe for each capability (processor thread) available to the runtime. This is the best option for multi-threaded connection pool performance.

StripeCount Int

StripeCount will cause the connection pool to be set up with the specified number of stripes, regardless of how many capabilities the runtime has.

data Connection Source #

An Orville handler for a LibPQ connection.

Since: 1.0.0.0

data ConnectionPool Source #

Orville always uses a connection pool to manage the number of open connections to the database. See ConnectionConfig and createConnectionPool to find how to create a ConnectionPool.

Since: 1.0.0.0

Opening transactions and savepoints

withTransaction :: MonadOrville m => m a -> m a Source #

Performs an action in an Orville monad within a database transaction. The transaction is begun before the action is called. If the action completes without raising an exception, the transaction will be committed. If the action raises an exception, the transaction will rollback.

This function is safe to call from within another transaction. When called this way, the transaction will establish a new savepoint at the beginning of the nested transaction and either release the savepoint or rollback to it as appropriate.

Note: Exceptions are handled using the implementations of catch and mask provided by the MonadOrvilleControl instance for m.

Since: 1.0.0.0

Types for incorporating Orville into other Monads

class (HasOrvilleState m, MonadOrvilleControl m, MonadIO m) => MonadOrville m Source #

MonadOrville is the typeclass that most Orville operations require to do anything that connects to the database. MonadOrville itself is empty, but it lists all the required typeclasses as superclass constraints so that it can be used instead of listing all the constraints on every function.

If you want to be able to run Orville operations directly in your own application's Monad stack, a good starting place is to add

   instance MonadOrville MyApplicationMonad
 

to your module and then let the compiler tell you what instances you are missing from the superclasses.

Since: 1.0.0.0

Instances

Instances details
MonadOrville Orville Source # 
Instance details

Defined in Orville.PostgreSQL.Monad.Orville

(MonadOrvilleControl m, MonadIO m) => MonadOrville (ReaderT OrvilleState m) Source # 
Instance details

Defined in Orville.PostgreSQL.Internal.MonadOrville

withConnection_ :: MonadOrville m => m a -> m a Source #

withConnection_ is a convenience version of withConnection for those that don't need the actual connection handle. You might want to use this function even without using the handle because it ensures that all the Orville operations performed by the action passed to it occur on the same connection. Orville uses connection pooling, so unless you use either withConnection or withTransaction, each database operation may be performed on a different connection.

Since: 1.0.0.0

withConnection :: MonadOrville m => (Connection -> m a) -> m a Source #

withConnection should be used to receive a Connection handle for executing queries against the database from within an application monad using Orville. For the "outermost" call of withConnection, a connection will be acquired from the resource pool. Additional calls to withConnection that happen inside the 'm a' that uses the connection will return the same Connection. When the 'm a' finishes, the connection will be returned to the pool. If 'm a' throws an exception, the pool's exception handling will take effect, generally destroying the connection in case it was the source of the error.

Since: 1.0.0.0

class MonadOrvilleControl m where Source #

MonadOrvilleControl presents the interface that Orville will use to lift low-level IO operations that cannot be lifted via liftIO (i.e. those where the IO parameter is contravariant rather than covariant).

For application monads built using only ReaderT and IO, this can be trivially implemented (or derived), using the ReaderT instance that is provided here. If your monad stack is sufficiently complicated, you may need to use the unliftio package as a stepping stone to implementing MonadOrvilleControl. If your monad uses features that unliftio cannot support (e.g. the State monad or continuations), then you may need to use monad-control instead.

See UnliftIO for functions that can be used as the implementation of the methods below for monads that implement MonadUnliftIO.

Since: 1.0.0.0

Methods

liftWithConnection :: (forall a. (Connection -> IO a) -> IO a) -> (Connection -> m b) -> m b Source #

Orville will use this function to lift the acquisition of connections from the resource pool into the application monad.

Since: 1.0.0.0

liftCatch :: Exception e => (forall a. IO a -> (e -> IO a) -> IO a) -> m b -> (e -> m b) -> m b Source #

Orville will use this function to lift exception catches into the application monad.

Since: 1.0.0.0

liftMask :: (forall b. ((forall a. IO a -> IO a) -> IO b) -> IO b) -> ((forall a. m a -> m a) -> m c) -> m c Source #

Orville will use this function to lift mask calls into the application monad to guarantee resource cleanup is executed even when asynchronous exceptions are thrown.

Since: 1.0.0.0

Instances

Instances details
MonadOrvilleControl IO Source # 
Instance details

Defined in Orville.PostgreSQL.Internal.MonadOrville

Methods

liftWithConnection :: (forall a. (Connection -> IO a) -> IO a) -> (Connection -> IO b) -> IO b Source #

liftCatch :: Exception e => (forall a. IO a -> (e -> IO a) -> IO a) -> IO b -> (e -> IO b) -> IO b Source #

liftMask :: (forall b. ((forall a. IO a -> IO a) -> IO b) -> IO b) -> ((forall a. IO a -> IO a) -> IO c) -> IO c Source #

MonadOrvilleControl Orville Source # 
Instance details

Defined in Orville.PostgreSQL.Monad.Orville

Methods

liftWithConnection :: (forall a. (Connection -> IO a) -> IO a) -> (Connection -> Orville b) -> Orville b Source #

liftCatch :: Exception e => (forall a. IO a -> (e -> IO a) -> IO a) -> Orville b -> (e -> Orville b) -> Orville b Source #

liftMask :: (forall b. ((forall a. IO a -> IO a) -> IO b) -> IO b) -> ((forall a. Orville a -> Orville a) -> Orville c) -> Orville c Source #

MonadOrvilleControl m => MonadOrvilleControl (ReaderT state m) Source # 
Instance details

Defined in Orville.PostgreSQL.Internal.MonadOrville

Methods

liftWithConnection :: (forall a. (Connection -> IO a) -> IO a) -> (Connection -> ReaderT state m b) -> ReaderT state m b Source #

liftCatch :: Exception e => (forall a. IO a -> (e -> IO a) -> IO a) -> ReaderT state m b -> (e -> ReaderT state m b) -> ReaderT state m b Source #

liftMask :: (forall b. ((forall a. IO a -> IO a) -> IO b) -> IO b) -> ((forall a. ReaderT state m a -> ReaderT state m a) -> ReaderT state m c) -> ReaderT state m c Source #

class HasOrvilleState m where Source #

HasOrvilleState is the typeclass that Orville uses to access and manange the connection pool and state tracking when it is being executed inside an unknown Monad. It is a specialized version of the Reader interface so that it can be easily implemented by application Monads that already have a Reader context and want to simply add OrvilleState as an attribute to that context, like so

   data MyApplicationState =
     MyApplicationState
       { appConfig :: MyAppConfig
       , appOrvilleState :: OrvilleState
       }

   newtype MyApplicationMonad a =
     MyApplicationMonad (ReaderT MyApplicationState IO) a

   instance HasOrvilleState MyApplicationMonad where
     askOrvilleState =
       MyApplicationMonad (asks appOrvilleState)

     localOrvilleState f (MyApplicationMonad reader) =
       MyApplicationMonad $
         local
           (\state -> state { appOrvilleState = f (appOrvilleState state))
           reader
 

An instance for 'ReaderT OrvilleState m' is provided as a convenience in the case that your application has no extra context to track.

Since: 1.0.0.0

Methods

askOrvilleState :: m OrvilleState Source #

Fetches the current OrvilleState from the host Monad context. The equivalent of ask for 'ReaderT OrvilleState'.

Since: 1.0.0.0

localOrvilleState Source #

Arguments

:: (OrvilleState -> OrvilleState)

The function to modify the OrvilleState.

-> m a

The monad operation to execute with the modified state.

-> m a 

Applies a modification to the OrvilleState that is local to the given monad operation. Calls to askOrvilleState made within the 'm a' provided must return the modified state. The modified state must only apply to the given 'm a' and not be persisted beyond it. The equivalent of local for 'ReaderT OrvilleState'.

Since: 1.0.0.0

data OrvilleState Source #

OrvilleState is used to manage opening connections to the database, transactions, etc. newOrvilleState should be used to create an appopriate initial state for your monad's context.

Since: 1.0.0.0

newOrvilleState :: ErrorDetailLevel -> ConnectionPool -> OrvilleState Source #

Creates an appropriate initial OrvilleState that will use the connection pool given to initiate connections to the database.

Since: 1.0.0.0

resetOrvilleState :: OrvilleState -> OrvilleState Source #

Creates a new initial OrvilleState using the connection pool from the provided state. You might need to use this if you are spawning one Orville monad from another and they should not share the same connection and transaction state.

Since: 1.0.0.0

addTransactionCallback :: (TransactionEvent -> IO ()) -> OrvilleState -> OrvilleState Source #

Registers a callback to be invoked during transactions.

The callback given will be called after the SQL statement corresponding to the given event has finished executing. Callbacks will be called in the order they are added.

Note: There is no specialized error handling for these callbacks. This means that if a callback raises an exception, no further callbacks will be called and the exception will propagate up until it is caught elsewhere. In particular, if an exception is raised by a callback upon opening the transaction, it will cause the transaction to be rolled-back the same as any other exception that might happen during the transaction. In general, we recommend only using callbacks that either raise no exceptions or can handle their own exceptions cleanly.

Since: 1.0.0.0

data TransactionEvent Source #

Describes an event in the lifecycle of a database transaction. You can use addTransactionCallback to register a callback to respond to these events. The callback will be called after the event in question has been successfully executed.

Since: 1.0.0.0

Constructors

BeginTransaction

Indicates a new transaction has been started.

NewSavepoint Savepoint

Indicates that a new savepoint has been saved within a transaction.

ReleaseSavepoint Savepoint

Indicates that a previous savepoint has been released. It can no longer be rolled back to.

RollbackToSavepoint Savepoint

Indicates that rollback was performed to a prior savepoint.

Note: It is possible to rollback to a savepoint prior to the most recent one without releasing or rolling back to intermediate savepoints. Doing so destroys any savepoints created after the given savepoint. Although Orville currently always matches NewSavepoint with either ReleaseSavepoint or RollbackToSavepoint, it is recommended that you do not rely on this behavior.

CommitTransaction

Indicates that the transaction has been committed.

RollbackTransaction

Indicates that the transaction has been rolled back.

data Savepoint Source #

An internal Orville identifier for a savepoint in a PostgreSQL transaction.

Since: 1.0.0.0

Instances

Instances details
Show Savepoint Source # 
Instance details

Defined in Orville.PostgreSQL.Internal.OrvilleState

Eq Savepoint Source # 
Instance details

Defined in Orville.PostgreSQL.Internal.OrvilleState

addSqlExecutionCallback :: (forall a. QueryType -> RawSql -> IO a -> IO a) -> OrvilleState -> OrvilleState Source #

Adds a callback to be called when an Orville operation executes a SQL statement. The callback is given the IO action that will perform the query execution and must call that action for the query to be run. In particular, you can use this to time queries and log any that are slow.

Calls to any previously added callbacks will also be executed as part of the IO action passed to the new callback. Thus the newly added callback happens "around" the previously added callback.

There is no special exception handling done for these callbacks beyond what they implement themselves. Any callbacks should allow for the possibility that the IO action they are given may raise an exception.

Since: 1.0.0.0

setBeginTransactionExpr :: BeginTransactionExpr -> OrvilleState -> OrvilleState Source #

Sets the SQL expression that Orville will use to begin transactions. You can control the transaction isolation level by building your own BeginTransactionExpr with the desired isolation level.

Since: 1.0.0.0

setSqlCommenterAttributes :: SqlCommenterAttributes -> OrvilleState -> OrvilleState Source #

Sets the SqlCommenterAttributes that Orville will then add to any following statement executions.

Since: 1.0.0.0

addSqlCommenterAttributes :: SqlCommenterAttributes -> OrvilleState -> OrvilleState Source #

Adds the SqlCommenterAttributes to the already existing attributes that Orville will then add to any following statement executions.

Since: 1.0.0.0

data ErrorDetailLevel Source #

ErrorDetailLevel provides a means to configure what elements of information are included in error messages that originate from decoding rows queried from the database. This can be specified either by manually rendering the error message and providing the desired configuration, or by setting the desired detail level in the OrvilleState as a default.

Information will be redacted from error messages for any of the fields that are set to False.

Since: 1.0.0.0

Instances

Instances details
Show ErrorDetailLevel Source #

Since: 1.0.0.0

Instance details

Defined in Orville.PostgreSQL.ErrorDetailLevel

defaultErrorDetailLevel :: ErrorDetailLevel Source #

A default ErrorDetailLevel that strikes a balance of including all Generic information such as the error message, schema names and row identifiers, but avoids unintentionally leaking non-identifier values from the database by redacting them.

Since: 1.0.0.0

minimalErrorDetailLevel :: ErrorDetailLevel Source #

A minimal ErrorDetailLevel where all information (including any situationally-specific error messages!) is redacted from error messages.

Since: 1.0.0.0

maximalErrorDetailLevel :: ErrorDetailLevel Source #

A maximal ErrorDetailLevel that redacts no information from the error messages. Error messages will include values from the database for any columns that are involved in a decoding failure, including some which you may not have intended to expose through error messages. Use with caution.

Since: 1.0.0.0

Functions for defining a database schema

data TableDefinition key writeEntity readEntity Source #

Contains the definition of a SQL table for Orville to use for generating queries and marshalling Haskell values to and from the database.

  • key is a Haskell type used to indicate whether the table has a primary key and what the type of the key is if so. See HasKey and NoKey for values to be used in this parameter.
  • writeEntity is the Haskell type for values that Orville will write to the database for you (i.e. both inserts and updates).
  • readEntity is the Haskell type for values that Orville will decode from the result set when entities are queried from this table.

Since: 1.0.0.0

mkTableDefinition Source #

Arguments

:: String

The name of the table

-> PrimaryKey key

Definition of the table's primary key

-> SqlMarshaller writeEntity readEntity

A SqlMarshaller to marshall table entities to and from the database

-> TableDefinition (HasKey key) writeEntity readEntity 

Constructs a new TableDefinition with the basic fields required for operation. For convenience, this function accepts a PrimaryKey even though this is not required for all Orville operations to work. If you need to create a table without any primary key, see mkTableDefinitionWithoutKey.

Since: 1.0.0.0

mkTableDefinitionWithoutKey Source #

Arguments

:: String

The name of the table

-> SqlMarshaller writeEntity readEntity

A SqlMarshaller to marshall table entities to and from the database

-> TableDefinition NoKey writeEntity readEntity 

Constructs a new TableDefinition with the minimal fields required for operation. Note: tables created via this function will not have a primary key. Certain Orville functions require a primary key. Attempting to call functions requiring a primary key will fail to compile when using a table that has no key.

Since: 1.0.0.0

setTableSchema :: String -> TableDefinition key writeEntity readEntity -> TableDefinition key writeEntity readEntity Source #

Sets the table's schema to the name in the given String, which will be treated as a SQL identifier. If a table has a schema name set, it will be included as a qualifier on the table name for all queries involving the table.

Since: 1.0.0.0

tableConstraints :: TableDefinition key writeEntity readEntity -> TableConstraints Source #

Retrieves all the table constraints that have been added to the table either via addTableConstraints or that are found on FieldDefinitions included with this table's SqlMarshaller.

Since: 1.0.0.0

addTableConstraints :: [ConstraintDefinition] -> TableDefinition key writeEntity readEntity -> TableDefinition key writeEntity readEntity Source #

Adds the given table constraints to the table definition. It's also possible to add constraints that apply to only one column, adding them to the FieldDefinitions that are included in the table's SqlMarshaller.

If you wish to constrain multiple columns with a single constraint (e.g. a multi-column unique constraint), you must use addTableConstraints.

Note: If multiple constraints are added with the same ConstraintMigrationKey, only the last one that is added will be part of the TableDefinition. Any previously-added constraint with the same key is replaced by the new one.

Since: 1.0.0.0

tableIndexes :: TableDefinition key writeEntity readEntity -> Map IndexMigrationKey IndexDefinition Source #

Retrieves all the table indexes that have been added to the table via addTableIndexes.

Since: 1.0.0.0

addTableIndexes :: [IndexDefinition] -> TableDefinition key writeEntity readEntity -> TableDefinition key writeEntity readEntity Source #

Adds the given table indexes to the table definition.

Note: If multiple indexes are added with the same IndexMigrationKey, only the last one that is added will be part of the TableDefinition. Any previously-added index with the same key is replaced by the new one.

Since: 1.0.0.0

dropColumns Source #

Arguments

:: [String]

Columns that should be dropped from the table

-> TableDefinition key writeEntity readEntity 
-> TableDefinition key writeEntity readEntity 

Annotates a TableDefinition with a direction to drop columns if they are found in the database. Orville does not drop columns during auto-migration unless they are explicitly requested to be dropped via dropColumns.

If you remove a reference to a column from the table's SqlMarshaller without adding the column's name to dropColumns, Orville will operate as if the column does not exist without actually dropping the column. This is often useful if you're not sure you want to lose the data in the column, or if you have zero down-time deployments, which requires the column not be referenced by deployed code before it can be dropped.

Since: 1.0.0.0

columnsToDrop :: TableDefinition key writeEntity readEntity -> Set String Source #

Returns the set of columns that have been marked as dropped by dropColumns.

Since: 1.0.0.0

tableIdentifier :: TableDefinition key writeEntity readEntity -> TableIdentifier Source #

Returns the table's TableIdentifier.

Since: 1.0.0.0

tableName :: TableDefinition key writeEntity readEntity -> Qualified TableName Source #

Returns the table's name as an expression that can be used to build SQL statements. If the table has a schema name set, the name will be qualified with it.

Since: 1.0.0.0

mkCreateTableExpr :: TableDefinition key writeEntity readEntity -> CreateTableExpr Source #

Builds a CreateTableExpr that will create a SQL table matching the given TableDefinition when it is executed.

Since: 1.0.0.0

mkTableColumnDefinitions :: TableDefinition key writeEntity readEntity -> [ColumnDefinition] Source #

Builds the ColumnDefinitions for all the fields described by the table definition's SqlMarshaller.

Since: 1.0.0.0

mkTablePrimaryKeyExpr :: TableDefinition key writeEntity readEntity -> Maybe PrimaryKeyExpr Source #

Builds the PrimaryKeyExpr for this table, or none if this table has no primary key.

Since: 1.0.0.0

tablePrimaryKey :: TableDefinition (HasKey key) writeEntity readEntity -> PrimaryKey key Source #

Returns the primary key for the table, as defined at construction via mkTableDefinition.

Since: 1.0.0.0

tableMarshaller :: TableDefinition key writeEntity readEntity -> AnnotatedSqlMarshaller writeEntity readEntity Source #

Returns the marshaller for the table, as defined at construction via mkTableDefinition.

Since: 1.0.0.0

data HasKey key Source #

HasKey is a type with no constructors. It is used only at the type level as the key parameter to the TableDefinition type to indicate that the table has a primary key and what the Haskell type of the primary key is.

Since: 1.0.0.0

data NoKey Source #

NoKey is a type with no constructors. It is used only at the type level as the key parameter to the TableDefinition type to indicate that the table does not have a primary key.

Since: 1.0.0.0

unqualifiedNameToTableId :: String -> TableIdentifier Source #

Constructs a TableIdentifier where the table's name will not be qualified by a particular schema.

Since: 1.0.0.0

tableIdUnqualifiedNameString :: TableIdentifier -> String Source #

Retrieves the unqualified name of the table as a String.

Since: 1.0.0.0

tableIdQualifiedName :: TableIdentifier -> Qualified TableName Source #

Returns the 'Expr.Qualified Expr.TableName' that should be used to refer to the table in SQL queries.

Since: 1.0.0.0

setTableIdSchema :: String -> TableIdentifier -> TableIdentifier Source #

Sets the schema of the TableIdentifier. Wherever applicable, references to the table will be qualified by the given schema name.

Since: 1.0.0.0

tableIdSchemaNameString :: TableIdentifier -> Maybe String Source #

Retrieves the schema name of the table as a String.

Since: 1.0.0.0

tableIdToString :: TableIdentifier -> String Source #

Converts a TableIdentifier to a String for descriptive purposes. The name will be qualified if a schema name has been set for the identifier.

Note: You should not use this function for building SQL expressions. Use tableIdQualifiedName instead for that.

Since: 1.0.0.0

data ConstraintDefinition Source #

Defines a constraint that can be added to a TableDefinition. Use one of the constructor functions below (such as uniqueConstraint) to construct the constraint definition you wish to have and then use addTableConstraints to add them to your table definition. Orville will then add the constraint next time you run auto-migrations.

Since: 1.0.0.0

uniqueConstraint :: NonEmpty FieldName -> ConstraintDefinition Source #

Constructs a ConstraintDefinition for a UNIQUE constraint on the given columns.

Since: 1.0.0.0

foreignKeyConstraint Source #

Arguments

:: TableIdentifier

Identifier of the table referenced by the foreign key.

-> NonEmpty ForeignReference

The columns constrained by the foreign key and those that they reference in the foreign table.

-> ConstraintDefinition 

Builds a ConstraintDefinition for a FOREIGN KEY constraint.

Since: 1.0.0.0

foreignKeyConstraintWithOptions Source #

Arguments

:: TableIdentifier

Identifier of the table referenced by the foreign key.

-> NonEmpty ForeignReference

The columns constrained by the foreign key and those that they reference in the foreign table.

-> ForeignKeyOptions 
-> ConstraintDefinition 

Builds a ConstraintDefinition for a FOREIGN KEY constraint, with ON UPDATE and ON DELETE actions.

Since: 1.0.0.0

data ForeignKeyOptions Source #

Defines the options for a foreign key constraint. To construct ForeignKeyOptions, perform a record update on defaultForeignKeyOptions.

Since: 1.0.0.0

foreignKeyOptionsOnDelete :: ForeignKeyOptions -> ForeignKeyAction Source #

The ON DELETE action for the foreign key.

foreignKeyOptionsOnUpdate :: ForeignKeyOptions -> ForeignKeyAction Source #

The ON UPDATE action for the foreign key.

data ForeignReference Source #

A ForeignReference represents one part of a foreign key. The entire foreign key may comprise multiple columns. The ForeignReference defines a single column in the key and which column it references in the foreign table.

Since: 1.0.0.0

foreignReference Source #

Arguments

:: FieldName

The name of the field in the table with the constraint.

-> FieldName

The name of the field in the foreign table that the local field references.

-> ForeignReference 

Constructs a ForeignReference.

Since: 1.0.0.0

data ConstraintMigrationKey Source #

The key used by Orville to determine whether a constraint should be added to a table when performing auto-migrations. For most use cases, the constructor functions that build a ConstraintDefinition will create this automatically for you.

Since: 1.0.0.0

constraintSqlExpr :: ConstraintDefinition -> TableConstraint Source #

Gets the SQL expression that will be used to add the constraint to the table.

Since: 1.0.0.0

data IndexDefinition Source #

Defines an index that can be added to a TableDefinition. Use one of the constructor functions below (such as uniqueIndex) to construct the index definition you wish to have and then use addTableIndexes to add them to your table definition. Orville will then add the index next time you run auto-migrations.

Since: 1.0.0.0

uniqueIndex :: NonEmpty FieldName -> IndexDefinition Source #

Constructs an IndexDefinition for a UNIQUE index on the given columns.

Since: 1.0.0.0

nonUniqueIndex :: NonEmpty FieldName -> IndexDefinition Source #

Constructs an IndexDefinition for a non-unique index on the given columns.

Since: 1.0.0.0

mkIndexDefinition :: IndexUniqueness -> NonEmpty FieldName -> IndexDefinition Source #

Constructs an IndexDefinition for an index on the given columns with the given uniqueness.

Since: 1.0.0.0

mkNamedIndexDefinition :: IndexUniqueness -> String -> IndexBodyExpr -> IndexDefinition Source #

Constructs an IndexDefinition for an index with the given uniqueness, given name, and given SQL.

Since: 1.0.0.0

indexCreateExpr :: IndexDefinition -> Qualified TableName -> CreateIndexExpr Source #

Gets the SQL expression that will be used to add the index to the specified table.

Since: 1.0.0.0

data IndexCreationStrategy Source #

Defines how an IndexDefinition will be executed to add an index to a table. By default, all indexes are created using the Transactional strategy.

Since: 1.0.0.0

Constructors

Transactional

The default strategy. The index will be added as part of a database transaction along with all the other DDL being executed to migrate the database schema. If any migration should fail, the index creation will be rolled back as part of the transaction. This is how schema migrations work in general in Orville.

Concurrent

Creates the index using the CONCURRENTLY keyword in PostgreSQL. Index creation will not lock the table during creation, allowing the application to access the table normally while the index is created. Concurrent index creation cannot be done in a transaction, so indexes created using CONCURRENTLY are created outside the normal schema transaction. Index creation may fail when using the Concurrent strategy. Orville has no special provision to detect or recover from this failure currently. You should manually check that index creation has succeeded. If necessary, you can manually drop the index to cause Orville to recreate it the next time migrations are run. Note that while the table will not be locked, index migration will still block application startup by default. See the information about schema migration options in Orville.PostgreSQL.AutoMigration for details about how to work around this if it is a problem for you. Also, it a good idea to read the PostgreSQL docs about creating indexes concurrently before you use this strategy. See https://www.postgresql.org/docs/current/sql-createindex.html#SQL-CREATEINDEX-CONCURRENTLY.

setIndexCreationStrategy :: IndexCreationStrategy -> IndexDefinition -> IndexDefinition Source #

Sets the IndexCreationStrategy to be used when creating the index described by the IndexDefinition. By default, all indexes are created using the Transactional strategy, but some tables are too large for this to be feasible. See the Concurrent creation strategy for how to work around this.

Since: 1.0.0.0

indexCreationStrategy :: IndexDefinition -> IndexCreationStrategy Source #

Gets the IndexCreationStrategy to be used when creating the index described by the IndexDefinition. By default, all indexes are created using the Transactional strategy.

Since: 1.0.0.0

data PrimaryKey key Source #

A Haskell description of the FieldDefinitions that make up the primary key of a SQL table. This type supports composite primary keys as well as singular ones.

Since: 1.0.0.0

primaryKey :: FieldDefinition NotNull key -> PrimaryKey key Source #

primaryKey constructs a single-field primary key from the FieldDefinition that corresponds to the primary key's column. This is generally used while building a TableDefinition.

Since: 1.0.0.0

compositePrimaryKey :: PrimaryKeyPart key -> [PrimaryKeyPart key] -> PrimaryKey key Source #

compositePrimaryKey constructs a multi-field primary key from the given parts, each of which corresponds to one field in the primary key. You should use this while building a TableDefinition for a table that you want to have a multi-column primary key. See primaryKeyPart for how to build the parts to be passed as parameters. Note: there is no special significance to the first argument other than requiring that there is at least one field in the primary key.

Since: 1.0.0.0

primaryKeyPart :: (key -> part) -> FieldDefinition NotNull part -> PrimaryKeyPart key Source #

primaryKeyPart constructs a building block for a composite primary key based on a FieldDefinition and an accessor function to extract the value for that field from the Haskell key type that represents the overall composite key. PrimaryKeyPart values built using this function are usually then passed in a list to compositePrimaryKey to build a PrimaryKey.

Since: 1.0.0.0

data SqlMarshaller a b Source #

SqlMarshaller is how we group the lowest-level translation of single fields into a higher-level marshalling of full SQL records into Haskell records. This is a flexible abstraction that allows us to ultimately model SQL tables and work with them as potentially nested Haskell records. We can then "marshall" the data as we want to model it in SQL and Haskell.

Since: 1.0.0.0

Instances

Instances details
Applicative (SqlMarshaller a) Source # 
Instance details

Defined in Orville.PostgreSQL.Marshall.SqlMarshaller

Methods

pure :: a0 -> SqlMarshaller a a0 #

(<*>) :: SqlMarshaller a (a0 -> b) -> SqlMarshaller a a0 -> SqlMarshaller a b #

liftA2 :: (a0 -> b -> c) -> SqlMarshaller a a0 -> SqlMarshaller a b -> SqlMarshaller a c #

(*>) :: SqlMarshaller a a0 -> SqlMarshaller a b -> SqlMarshaller a b #

(<*) :: SqlMarshaller a a0 -> SqlMarshaller a b -> SqlMarshaller a a0 #

Functor (SqlMarshaller a) Source # 
Instance details

Defined in Orville.PostgreSQL.Marshall.SqlMarshaller

Methods

fmap :: (a0 -> b) -> SqlMarshaller a a0 -> SqlMarshaller a b #

(<$) :: a0 -> SqlMarshaller a b -> SqlMarshaller a a0 #

data AnnotatedSqlMarshaller writeEntity readEntity Source #

An AnnotatedSqlMarshaller is a SqlMarshaller that contains extra annotations which cannot necessarily be determined from the data in the marshaller itself. In particular, it includes the names of fields that can be used to identify a row in the database when an error is encountered during decoding.

Normally you will not need to interact with this type directly -- the TableDefinition type creates it for you using the information it has about the primary key of the table to identify rows in decoding errors. If you are executing custom queries directly, you may need to annotate a raw SqlMarshaller yourself so that rows can be identified. See annotateSqlMarshaller and annotateSqlMarshallerEmptyAnnotation.

Since: 1.0.0.0

annotateSqlMarshaller :: [FieldName] -> SqlMarshaller writeEntity readEntity -> AnnotatedSqlMarshaller writeEntity readEntity Source #

Creates an AnnotatedSqlMarshaller that will use the given column names to identify rows in error messages when decoding fails. Any column names in the list that are not present in the result set will simply be omitted from the error message.

Since: 1.0.0.0

annotateSqlMarshallerEmptyAnnotation :: SqlMarshaller writeEntity readEntity -> AnnotatedSqlMarshaller writeEntity readEntity Source #

Creates an AnnotatedSqlMarshaller that will identify rows in decoding errors by any columns. This is the equivalent of annotateSqlMarshaller [].

Since: 1.0.0.0

unannotatedSqlMarshaller :: AnnotatedSqlMarshaller writeEntity readEntity -> SqlMarshaller writeEntity readEntity Source #

mapSqlMarshaller :: (SqlMarshaller readEntityA writeEntityA -> SqlMarshaller readEntityB writeEntityB) -> AnnotatedSqlMarshaller readEntityA writeEntityA -> AnnotatedSqlMarshaller readEntityB writeEntityB Source #

Applies the provided function to a SqlMarshaller that has been annotated, preserving the annotations.

Since: 1.0.0.0

marshallField :: (writeEntity -> fieldValue) -> FieldDefinition nullability fieldValue -> SqlMarshaller writeEntity fieldValue Source #

Builds a SqlMarshaller that maps a single field of a Haskell entity to a single column in the database. That value to store in the database will be retrieved from the entity using a provided accessor function. This function is intended to be used inside of a stanza of Applicative syntax that will pass values read from the database to a constructor function to rebuild the entity containing the field, like so:

 data Foo = Foo { bar :: Int32, baz :: Text }

 fooMarshaller :: SqlMarshaller Foo Foo
 fooMarshaller =
   Foo
     <$> marshallField bar (integerField "bar")
     <*> marshallField baz (unboundedTextField "baz")

 

Since: 1.0.0.0

marshallNested :: (parentEntity -> nestedWriteEntity) -> SqlMarshaller nestedWriteEntity nestedReadEntity -> SqlMarshaller parentEntity nestedReadEntity Source #

Nests a SqlMarshaller inside another, using the given accessor to retrieve values to be marshalled. The resulting marshaller can then be used in the same way as marshallField within the applicative syntax of a larger marshaller.

For Example:

 data Person =
   Person
     { personId :: PersonId
     , personName :: Name
     }

 data Name =
   Name
     { firstName :: Text
     , lastName :: Text
     }

 personMarshaller :: SqlMarshaller Person Person
 personMarshaller =
   Person
     <$> marshallField personId personIdField
     <*> marshallNested personName nameMarshaller

 nameMarshaller :: SqlMarshaller Name Name
 nameMarshaller =
   Name
     <$> marshallField firstName firstNameField
     <*> marshallField lastName lastNameField
 

Since: 1.0.0.0

marshallSyntheticField :: SyntheticField fieldValue -> SqlMarshaller writeEntity fieldValue Source #

Builds a SqlMarshaller that will include a SQL expression in select statements to calculate a value using the columns of the table being selected from. The columns being used in the calculation do not themselves need to be selected, though they must be present in the table so they can be referenced.

 data AgeCheck
   { atLeast21 :: Bool
   }

 fooMarshaller :: SqlMarshaller Void AgeCheck
 fooMarshaller =
   AgeCheck
     <*> Orville.marshallSyntheticField atLeast21Field

 atLeast21Field :: SyntheticField Bool
 atLeast21Field =
   SyntheticField
     { syntheticFieldExpression = RawSql.unsafeSqlExpression "age >= 21"
     , syntheticFieldAlias = Orville.stringToFieldName "over21"
     , syntheticFieldValueFromSqlValue = SqlValue.toBool
     }
 

Since: 1.0.0.0

marshallReadOnly :: SqlMarshaller a b -> SqlMarshaller c b Source #

Marks a SqlMarshaller as read-only so that it will not attempt to read any values from the writeEntity. You should use this if you have a group of fields which are populated by database rather than the application.

Since: 1.0.0.0

marshallReadOnlyField :: FieldDefinition nullability fieldValue -> SqlMarshaller writeEntity fieldValue Source #

A version of marshallField that uses marshallReadOnly to make a single read-only field. You will usually use this in conjunction with a FieldDefinition like serialField where the value is populated by the database.

Since: 1.0.0.0

marshallPartial :: SqlMarshaller a (Either String b) -> SqlMarshaller a b Source #

Builds a SqlMarshaller that will raise a decoding error when the value produced is a Left.

Since: 1.0.0.0

marshallMaybe :: SqlMarshaller a b -> SqlMarshaller (Maybe a) (Maybe b) Source #

Lifts a SqlMarshaller to have both read/write entities be Maybe, and applies a tag to avoid double mapping.

Since: 1.0.0.0

prefixMarshaller :: String -> SqlMarshaller readEntity writeEntity -> SqlMarshaller readEntity writeEntity Source #

Adds a prefix, followed by an underscore, to the names of all of the fields and synthetic fields in a SqlMarshaller.

Since: 1.0.0.0

foldMarshallerFields :: SqlMarshaller writeEntity readEntity -> result -> (MarshallerField writeEntity -> result -> result) -> result Source #

foldMarshallerFields allows you to consume the FieldDefinitions that are contained within the SqlMarshaller to process them however is required. This can be used to collect the names of all the fields, encode them to SqlValue, etc.

Since: 1.0.0.0

collectFromField :: ReadOnlyColumnOption -> (forall nullability a. FieldDefinition nullability a -> result) -> MarshallerField entity -> [result] -> [result] Source #

A fold function that can be used with foldMarshallerFields to collect a value calculated from a FieldDefinition via the given function. The calculated value is added to the list of values being built.

Note: Folds executed with collectFromField ignore Synthetic entries in the marshaller. You should only use collectFromField in situations where you only care about the actual columns referenced by the marshaller.

Since: 1.0.0.0

data ReadOnlyColumnOption Source #

Specifies whether read-only fields should be included when using functions such as collectFromField.

Since: 1.0.0.0

data SyntheticField a Source #

A SyntheticField can be used to evaluate a SQL expression based on the columns of a table when records are selected from the database. Synthetic fields are inherently read-only.

Since: 1.0.0.0

syntheticFieldExpression :: SyntheticField a -> ValueExpression Source #

Returns the SQL expression that should be used in select statements to calculate the synthetic field.

Since: 1.0.0.0

syntheticFieldAlias :: SyntheticField a -> FieldName Source #

Returns the alias that should be used in select statements to name the synthetic field.

Since: 1.0.0.0

syntheticFieldValueFromSqlValue :: SyntheticField a -> SqlValue -> Either String a Source #

Decodes a calculated value selected from the database to its expected Haskell type. Returns a Left with an error message if the decoding fails.

Since: 1.0.0.0

syntheticField Source #

Arguments

:: ValueExpression

The SQL expression to be selected.

-> String

The alias to be used to name the calculation in SQL expressions.

-> (SqlValue -> Either String a)

A function to decode the expression result from a SqlValue.

-> SyntheticField a 

Constructs a SyntheticField that will select a SQL expression using the given alias.

Since: 1.0.0.0

nullableSyntheticField :: SyntheticField a -> SyntheticField (Maybe a) Source #

Modifies a SyntheticField to allow it to decode NULL values.

Since: 1.0.0.0

prefixSyntheticField :: String -> SyntheticField a -> SyntheticField a Source #

Adds a prefix, followed by an underscore, to the alias used to name the synthetic field.

Since: 1.0.0.0

data FieldDefinition nullability a Source #

FieldDefinition determines the SQL construction of a column in the database, comprising the name, SQL type and whether the field is nullable. A FieldDefinition is matched to a particular Haskell type, which it knows how to marshall to and from the database representation of SQL type for the field.

Since: 1.0.0.0

data NotNull Source #

NotNull is a valueless type used to track that a FieldDefinition represents a field that is marked not-null in the database schema. See the FieldNullability type for the value-level representation of field nullability.

Since: 1.0.0.0

data Nullable Source #

Nullable is a valueless type used to track that a FieldDefinition represents a field that is marked nullable in the database schema. See the FieldNullability type for the value-level representation of field nullability.

Since: 1.0.0.0

nullableField :: FieldDefinition NotNull a -> FieldDefinition Nullable (Maybe a) Source #

Makes a NotNull field Nullable by wrapping the Haskell type of the field in Maybe. The field will be marked as NULL in the database schema and the value Nothing will be used to represent NULL values when converting to and from SQL.

Since: 1.0.0.0

asymmetricNullableField :: FieldDefinition Nullable a -> FieldDefinition Nullable (Maybe a) Source #

Adds a Maybe wrapper to a field that is already nullable. (If your field is NotNull, you wanted nullableField instead of this function). Note that fields created using this function have asymmetric encoding and decoding of NULL values. Because the provided field is Nullable, NULL values decoded from the database already have a representation in the a type, so NULL will be decoded as 'Just of type a for NULL'. This means if you insert a Nothing value using the field, it will be read back as Just value. This is useful for building high level combinators that might need to make fields Nullable but need the value to be decoded in its underlying type when reading back (e.g. maybeMapper from Orville.PostgreSQL.Marshall.SqlMarshaller).

Since: 1.0.0.0

convertField :: (SqlType a -> SqlType b) -> FieldDefinition nullability a -> FieldDefinition nullability b Source #

Applies a SqlType conversion to a FieldDefinition. You can use this function to create FieldDefinitions based on the primitive ones provided, but with more specific Haskell types.

See convertSqlType and tryConvertSqlType for functions to create the conversion needed as the first argument to convertField.

Since: 1.0.0.0

coerceField :: (Coercible a b, Coercible b a) => FieldDefinition nullability a -> FieldDefinition nullability b Source #

A specialization of convertField that can be used with types that implement Coercible. This is particularly useful for newtype wrappers around primitive types.

Since: 1.0.0.0

setDefaultValue :: DefaultValue a -> FieldDefinition nullability a -> FieldDefinition nullability a Source #

Sets a default value for the field. The default value will be added as part of the column definition in the database. Because the default value is ultimately provided by the database, this can be used to add a not-null column safely to an existing table as long as a reasonable default value is available to use.

Since: 1.0.0.0

removeDefaultValue :: FieldDefinition nullability a -> FieldDefinition nullability a Source #

Removes any default value that may have been set on a field via setDefaultValue.

Since: 1.0.0.0

prefixField :: String -> FieldDefinition nullability a -> FieldDefinition nullability a Source #

Adds a prefix, followed by an underscore, to a field's name.

Since: 1.0.0.0

integerField Source #

Arguments

:: String

Name of the field in the database.

-> FieldDefinition NotNull Int32 

Builds a FieldDefinition that stores Haskell Int32 values as the PostgreSQL INT type.

Since: 1.0.0.0

serialField Source #

Arguments

:: String

Name of the field in the database.

-> FieldDefinition NotNull Int32 

Builds a FieldDefinition that stores an Int32 value as the SERIAL type. This can be used to create auto-incrementing columns.

Since: 1.0.0.0

smallIntegerField Source #

Arguments

:: String

Name of the field in the database.

-> FieldDefinition NotNull Int16 

Builds a FieldDefinition that stores Haskell Int16 values as the PostgreSQL SMALLINT type.

Since: 1.0.0.0

uuidField Source #

Arguments

:: String

Name of the field in the database.

-> FieldDefinition NotNull UUID 

Builds a FieldDefinition that stores Haskell UUID values as the PostgreSQL UUID type.

Since: 1.0.0.0

bigIntegerField Source #

Arguments

:: String

Name of the field in the database.

-> FieldDefinition NotNull Int64 

Builds a FieldDefinition that stores Haskell Int64 values as the PostgreSQL BIGINT type.

Since: 1.0.0.0

bigSerialField Source #

Arguments

:: String

Name of the field in the database.

-> FieldDefinition NotNull Int64 

Builds a FieldDefinition that stores an Int64 value as the BIGSERIAL type. This can be used to create auto-incrementing columns.

Since: 1.0.0.0

doubleField Source #

Arguments

:: String

Name of the field in the database.

-> FieldDefinition NotNull Double 

Builds a FieldDefinition that stores a Double value as the "DOUBLE PRECISION" type. Note: PostgreSQL's "DOUBLE PRECISION" type only allows for up to 15 digits of precision, so some rounding may occur when values are stored in the database.

Since: 1.0.0.0

booleanField Source #

Arguments

:: String

Name of the field in the database.

-> FieldDefinition NotNull Bool 

Builds a FieldDefinition that stores Haskell Bool values as the PostgreSQL BOOLEAN type.

Since: 1.0.0.0

unboundedTextField Source #

Arguments

:: String

Name of the field in the database.

-> FieldDefinition NotNull Text 

Builds a FieldDefinition that stores Haskell Text values as the PostgreSQL TEXT type. Note that this PostgreSQL has no particular limit on the length of text stored.

Since: 1.0.0.0

boundedTextField Source #

Arguments

:: String

Name of the field in the database.

-> Int32

Maximum length of text in the field.

-> FieldDefinition NotNull Text 

Builds a FieldDefinition that stores Haskell Text values as the PostgreSQL VARCHAR type. Attempting to store a value beyond the length specified will cause an error.

Since: 1.0.0.0

fixedTextField Source #

Arguments

:: String

Name of the field in the database.

-> Int32

Maximum length of text in the field.

-> FieldDefinition NotNull Text 

Builds a FieldDefinition that stores Haskell Text values as the PostgreSQL CHAR type. Attempting to store a value beyond the length specified will cause an error. Storing a value that is not the full length of the field will result in padding by the database.

Since: 1.0.0.0

textSearchVectorField :: String -> FieldDefinition NotNull Text Source #

Builds a FieldDefinition that stores PostgreSQL text search vector values. The values are represented as Haskell Text values, but are interpreted as text search vector values by PostgreSQL when passed to it.

See https://www.postgresql.org/docs/current/datatype-textsearch.html for information about how PostgreSQL creates tsvector values from strings.

Since: 1.0.0.0

dateField Source #

Arguments

:: String

Name of the field in the database.

-> FieldDefinition NotNull Day 

Builds a FieldDefinition that stores Haskell Day values as the PostgreSQL DATE type.

Since: 1.0.0.0

utcTimestampField Source #

Arguments

:: String

Name of the field in the database.

-> FieldDefinition NotNull UTCTime 

Builds a FieldDefinition that stores Haskell UTCTime values as the PostgreSQL "TIMESTAMP with time zone" type.

Since: 1.0.0.0

localTimestampField Source #

Arguments

:: String

Name of the field in the database.

-> FieldDefinition NotNull LocalTime 

Builds a FieldDefinition that stores Haskell UTCTime values as the PostgreSQL "TIMESTAMP without time zone" type.

Since: 1.0.0.0

jsonbField :: String -> FieldDefinition NotNull Text Source #

Builds a FieldDefinition that stores Haskell Text values as the PostgreSQL JSONB type.

Since: 1.0.0.0

fieldOfType Source #

Arguments

:: SqlType a

SqlType that represents the PostgreSQL data type for the field.

-> String

Name of the field in the database.

-> FieldDefinition NotNull a 

Builds a FieldDefinition that will use the given SqlType to determine the database representation of the field. If you have created a custom SqlType, you can use this function to construct a helper like the other functions in this module for creating FieldDefinitions for your custom type.

Since: 1.0.0.0

fieldColumnName :: FieldDefinition nullability a -> ColumnName Source #

Constructs the ColumnName for a field for use in SQL expressions from the Orville.PostgreSQL.Expr module.

Since: 1.0.0.0

fieldColumnReference :: FieldDefinition nullability a -> ValueExpression Source #

Constructs the ValueExpression for a field for use in SQL expressions from the Orville.PostgreSQL.Expr module.

Since: 1.0.0.0

fieldName :: FieldDefinition nullability a -> FieldName Source #

The name used in database queries to reference the field.

Since: 1.0.0.0

setFieldName :: FieldName -> FieldDefinition nullability a -> FieldDefinition nullability a Source #

Sets the name used in database queries to reference the field.

Since: 1.0.0.0

fieldDescription :: FieldDefinition nullability a -> Maybe String Source #

Returns the description that was passed to setFieldDescription, if any.

Since: 1.0.0.0

setFieldDescription :: String -> FieldDefinition nullability a -> FieldDefinition nullability a Source #

Sets the description for the field. This description is not currently used anywhere by Orville itself, but users can retrieve the description via fieldDescription for their own purposes (e.g. generating documentation).

Since: 1.0.0.0

addUniqueConstraint :: FieldDefinition nullability a -> FieldDefinition nullability a Source #

Adds a UNIQUE constraint to the FieldDefinition. This constraint will be included on any table that uses the field definition.

Since: 1.0.0.0

addForeignKeyConstraint Source #

Arguments

:: TableIdentifier

Identifier of the table referenced by the foreign key.

-> FieldName

The field name that this field definition references in the foreign table.

-> FieldDefinition nullability a 
-> FieldDefinition nullability a 

Adds a FOREIGN KEY constraint to the FieldDefinition (using addFieldTableConstraints). This constraint will be included on any table that uses the field definition.

Since: 1.0.0.0

data FieldName Source #

A simple type to represent the name of a field.

Since: 1.0.0.0

stringToFieldName :: String -> FieldName Source #

Constructs a FieldName from a String.

Since: 1.0.0.0

fieldNameToString :: FieldName -> String Source #

Converts a FieldName back to a String.

Since: 1.0.0.0

fieldNameToColumnName :: FieldName -> ColumnName Source #

Convert a field name to a ColumnName for usage in SQL expressions. The field name will be properly quoted and escaped.

Since: 1.0.0.0

fieldNameToByteString :: FieldName -> ByteString Source #

Converts a FieldName back to a ByteString.

Since: 1.0.0.0

fieldType :: FieldDefinition nullability a -> SqlType a Source #

The SqlType for the FieldDefinition determines the PostgreSQL data type used to define the field as well as how to marshall Haskell values to and from the database.

Since: 1.0.0.0

fieldDefaultValue :: FieldDefinition nullability a -> Maybe (DefaultValue a) Source #

Returns the default value definition for the field, if any has been set.

Since: 1.0.0.0

fieldColumnDefinition :: FieldDefinition nullability a -> ColumnDefinition Source #

Constructs the equivalent FieldDefinition as a SQL expression, generally for use in DDL for creating columns in a table.

Since: 1.0.0.0

fieldIsNotNullable :: FieldDefinition nullability a -> Bool Source #

Indicates whether a field is not nullable.

Since: 1.0.0.0

fieldNullability :: FieldDefinition nullability a -> FieldNullability a Source #

Resolves the nullability of a field to a concrete type, which is returned via the FieldNullability type. You can pattern match on this type to then extract the either Nullable or NotNull field for cases where you may require different logic based on the nullability of a field.

Since: 1.0.0.0

setField :: FieldDefinition nullability a -> a -> SetClause Source #

Constructs a SetClause that will set the column named in the field definition to the given value. The value is converted to a SQL value using fieldValueToSqlValue.

Since: 1.0.0.0

(.:=) :: FieldDefinition nullability a -> a -> SetClause Source #

Operator alias for setField.

Since: 1.0.0.0

data FieldNullability a Source #

A FieldNullability is returned by the fieldNullability function, which can be used when a function works on both Nullable and NotNull functions but needs to deal with each type of field separately. It adds wrapper constructors around the FieldDefinition that you can pattern match on to then work with a concrete Nullable or NotNull field.

Since: 1.0.0.0

data DefaultValue a Source #

A DefaultValue is a SQL expression that can be attached to a field definition to give a default value for a column at the database level. The default value will be used if an insert is done and the column is not provided.

This is useful if you want to add a new column to a table that is already in production without breaking a previous version of your application that is running (e.g. during a zero-down-time deployment) and without needing to make the new column nullable. Default values can also be used to create database-assigned values such as using now() to set a created_at column on a row automatically in the database.

Since: 1.0.0.0

integerDefault :: Int32 -> DefaultValue Int32 Source #

Builds a default value from an Int32 for use with integer fields.

This is a specialization of integerDefault.

Since: 1.0.0.0

smallIntegerDefault :: Int16 -> DefaultValue Int16 Source #

Builds a default value from an Int16 for use with small integer fields.

This is a specialization of integerDefault.

Since: 1.0.0.0

bigIntegerDefault :: Int64 -> DefaultValue Int64 Source #

Builds a default value from an Int16 for use with big integer fields.

This is a specialization of integerDefault.

Since: 1.0.0.0

integralDefault :: Integral n => n -> DefaultValue n Source #

Builds a default value for any Integral type n by converting it to an Integer.

Since: 1.0.0.0

doubleDefault :: Double -> DefaultValue Double Source #

Builds a default value from a Double field for use with double fields.

Since: 1.0.0.0

booleanDefault :: Bool -> DefaultValue Bool Source #

Builds a default value from a Bool, for use with boolean fields.

Since: 1.0.0.0

textDefault :: Text -> DefaultValue Text Source #

Builds a default value from a Text, for use with unbounded, bounded and fixed-length text fields.

Since: 1.0.0.0

dateDefault :: Day -> DefaultValue Day Source #

Builds a default value from a Day for use with date fields.

Since: 1.0.0.0

currentDateDefault :: DefaultValue Day Source #

Builds a default value that will default to the current date (i.e. the date at which the database populates the default value on a given row).

For use with date fields.

Since: 1.0.0.0

utcTimestampDefault :: UTCTime -> DefaultValue UTCTime Source #

Builds a default value from a UTCTime for use with UTC timestamp fields.

Since: 1.0.0.0

currentUTCTimestampDefault :: DefaultValue UTCTime Source #

Builds a default value that will default to the current UTC time (i.e. the time at which the database populates the default value on a given row).

For use with UTC timestamp fields.

Since: 1.0.0.0

localTimestampDefault :: LocalTime -> DefaultValue LocalTime Source #

Builds a default value from a LocalTime for use with local timestamp fields.

Since: 1.0.0.0

currentLocalTimestampDefault :: DefaultValue LocalTime Source #

Builds a default value that will default to the current local time (i.e. the time at which the database populates the default value on a given row).

Note: "local" time here will be determined by the database itself, subject to whatever timezone offset has been configured in its settings.

For use with local timestamp fields.

Since: 1.0.0.0

coerceDefaultValue :: DefaultValue a -> DefaultValue b Source #

Coerces a DefaultValue so that it can be used with field definitions of a different Haskell type. The coercion will always succeed, and is safe as far as Haskell itself is concerned. As long as the DefaultValue is used with a column whose database type is the same as the one the DefaultValue was originally intended for, everything will work as expected.

Since: 1.0.0.0

defaultValueExpression :: DefaultValue a -> ValueExpression Source #

Returns a database value expression for the default value.

Since: 1.0.0.0

rawSqlDefault :: ValueExpression -> DefaultValue a Source #

Constructs a default value from a ValueExpression. You can use this to construct default values for any SQL expression that Orville does not support directly.

Note: If you are using auto-migrations, the ValueExpression that you pass here must match what is returned by the PostgreSQL pg_get_expr function. pg_get_expr decompiles the compiled version of the default experssion back to source text, sometimes in non-obvious ways. Orville's auto-migration compares the expression given in the field definition with the decompiled expression from the database to determine whether the default value needs to be updated in the schema or not. If the expression given by a DefaultValue is logically equivalent but does not match the decompiled form, auto-migration will continue to execute SQL statements to update the schema even when it does not need to.

Since: 1.0.0.0

Functions and operators for putting where clauses, order by clauses

data SelectOptions Source #

A SelectOptions is a set of options that can be used to change the way a basic query function works by adding WHERE, ORDER BY, GROUP BY, etc. Functions are provided to construct SelectOptions for individual options, which may then be combined via <> (also exposed as appendSelectOptions).

Since: 1.0.0.0

distinct :: SelectOptions Source #

Constructs a SelectOptions with just distinct set to True.

Since: 1.0.0.0

groupBy :: GroupByExpr -> SelectOptions Source #

Constructs a SelectOptions with just the given GroupByClause.

Since: 1.0.0.0

limit :: Int -> SelectOptions Source #

Constructs a SelectOptions that will apply the given limit.

Since: 1.0.0.0

offset :: Int -> SelectOptions Source #

Constructs a SelectOptions that will apply the given offset.

Since: 1.0.0.0

orderBy :: OrderByExpr -> SelectOptions Source #

Constructs a SelectOptions with just the given OrderByExpr.

Since: 1.0.0.0

where_ :: BooleanExpr -> SelectOptions Source #

Constructs a SelectOptions with just the given BooleanExpr.

Since: 1.0.0.0

emptySelectOptions :: SelectOptions Source #

A set of empty SelectOptions that will not change how a query is run.

Since: 1.0.0.0

appendSelectOptions :: SelectOptions -> SelectOptions -> SelectOptions Source #

Combines multple select options together, unioning the options together where possible. For options where this is not possible (e.g. LIMIT), the one on the left is preferred.

Since: 1.0.0.0

fieldEquals :: FieldDefinition nullability a -> a -> BooleanExpr Source #

Checks that the value in a field equals a particular value.

Since: 1.0.0.0

(.==) :: FieldDefinition nullability a -> a -> BooleanExpr infixl 9 Source #

Operator alias for fieldEquals.

Since: 1.0.0.0

fieldNotEquals :: FieldDefinition nullability a -> a -> BooleanExpr Source #

Checks that the value in a field does not equal a particular value.

Since: 1.0.0.0

(./=) :: FieldDefinition nullability a -> a -> BooleanExpr infixl 9 Source #

Operator alias for fieldNotEquals.

Since: 1.0.0.0

fieldGreaterThan :: FieldDefinition nullability a -> a -> BooleanExpr Source #

Checks that the value in a field is greater than a particular value.

Since: 1.0.0.0

(.>) :: FieldDefinition nullability a -> a -> BooleanExpr infixl 9 Source #

Operator alias for fieldGreaterThan.

Since: 1.0.0.0

fieldLessThan :: FieldDefinition nullability a -> a -> BooleanExpr Source #

Checks that the value in a field is less than a particular value.

Since: 1.0.0.0

(.<) :: FieldDefinition nullability a -> a -> BooleanExpr infixl 9 Source #

Operator alias for fieldLessThan.

Since: 1.0.0.0

fieldGreaterThanOrEqualTo :: FieldDefinition nullability a -> a -> BooleanExpr Source #

Checks that the value in a field is greater than or equal to a particular value.

Since: 1.0.0.0

(.>=) :: FieldDefinition nullability a -> a -> BooleanExpr infixl 9 Source #

Operator alias for fieldGreaterThanOrEqualTo.

Since: 1.0.0.0

fieldLessThanOrEqualTo :: FieldDefinition nullability a -> a -> BooleanExpr Source #

Checks that the value in a field is less than or equal to a particular value.

Since: 1.0.0.0

(.<=) :: FieldDefinition nullability a -> a -> BooleanExpr infixl 9 Source #

Operator alias for fieldLessThanOrEqualTo.

Since: 1.0.0.0

fieldLike :: FieldDefinition nullability a -> Text -> BooleanExpr Source #

Checks that the value in a field matches a like pattern.

Since: 1.0.0.0

fieldLikeInsensitive :: FieldDefinition nullability a -> Text -> BooleanExpr Source #

Checks that the value in a field matches a like pattern case insensitively.

Since: 1.0.0.0

fieldIsNull :: FieldDefinition Nullable a -> BooleanExpr Source #

Checks that the value in a field is null.

Since: 1.0.0.0

fieldIsNotNull :: FieldDefinition Nullable a -> BooleanExpr Source #

Checks that the value in a field is not null.

Since: 1.0.0.0

fieldIn :: FieldDefinition nullability a -> NonEmpty a -> BooleanExpr Source #

Checks that a field matches a list of values.

Since: 1.0.0.0

(.<-) :: FieldDefinition nullability a -> NonEmpty a -> BooleanExpr infixl 9 Source #

Operator alias for fieldIn.

Since: 1.0.0.0

fieldNotIn :: FieldDefinition nullability a -> NonEmpty a -> BooleanExpr Source #

Checks that a field does not match a list of values.

Since: 1.0.0.0

(.</-) :: FieldDefinition nullability a -> NonEmpty a -> BooleanExpr infixl 9 Source #

Operator alias for fieldNotIn.

Since: 1.0.0.0

fieldTupleIn :: FieldDefinition nullabilityA a -> FieldDefinition nullabilityB b -> NonEmpty (a, b) -> BooleanExpr Source #

Checks that a tuple of two fields is in the list of specified tuples.

Since: 1.0.0.0

fieldTupleNotIn :: FieldDefinition nullabilityA a -> FieldDefinition nullabilityB b -> NonEmpty (a, b) -> BooleanExpr Source #

Checks that a tuple of two fields is not in the list of specified tuples.

Since: 1.0.0.0

data OrderByDirection Source #

Type to represent a SQL order by direction expression. E.G.

ASC

OrderByDirection provides a SqlExpression instance. See unsafeSqlExpression for how to construct a value with your own custom SQL.

Since: 1.0.0.0

data NullsOrder Source #

Type to represent the ordering of Null, intended to be used with OrderByDirection.

Since: 1.0.0.0

Constructors

NullsFirst 
NullsLast 

ascendingOrder :: OrderByDirection Source #

The SQL ASC order direction.

Since: 1.0.0.0

ascendingOrderWith :: NullsOrder -> OrderByDirection Source #

The SQL ASC order direction with NULLs ordered as given.

Since: 1.0.0.0

descendingOrder :: OrderByDirection Source #

The SQL DESC order direction.

Since: 1.0.0.0

descendingOrderWith :: NullsOrder -> OrderByDirection Source #

The SQL DESC order direction with NULLs ordered as given.

Since: 1.0.0.0

andExpr :: BooleanExpr -> BooleanExpr -> BooleanExpr Source #

The SQL AND operator. The arguments will be surrounded with parentheses to ensure that the associativity of expression in the resulting SQL matches the associativity implied by this Haskell function.

Since: 1.0.0.0

orExpr :: BooleanExpr -> BooleanExpr -> BooleanExpr Source #

The SQL OR operator. The arguments will be surrounded with parentheses to ensure that the associativity of expression in the resulting SQL matches the associativity implied by this Haskell function.

Since: 1.0.0.0

(.&&) :: BooleanExpr -> BooleanExpr -> BooleanExpr infixr 8 Source #

The SQL AND operator (alias for andExpr).

Since: 1.0.0.0

(.||) :: BooleanExpr -> BooleanExpr -> BooleanExpr infixr 8 Source #

The SQL OR operator (alias for orExpr).

Since: 1.0.0.0

selectGroupByClause :: SelectOptions -> Maybe GroupByClause Source #

Builds the GroupByClause that should be used to include the GroupByClauses from the SelectOptions on a query. This will be Nothing when no GroupByClauses have been specified.

Since: 1.0.0.0

selectOrderByClause :: SelectOptions -> Maybe OrderByClause Source #

Builds the OrderByClause that should be used to include the OrderByClauses from the SelectOptions on a query. This will be Nothing when no OrderByClauses have been specified.

Since: 1.0.0.0

selectWhereClause :: SelectOptions -> Maybe WhereClause Source #

Builds the WhereClause that should be used to include the BooleanExprs from the SelectOptions on a query. This will be Nothing when no BooleanExprs have been specified.

Since: 1.0.0.0

selectDistinct :: SelectOptions -> SelectClause Source #

Builds the SelectClause that should be used to include the distincts from the SelectOptions on a query.

Since: 1.0.0.0

Functions for defining and working with sequences

sequenceNextValue :: MonadOrville m => SequenceDefinition -> m Int64 Source #

Fetches the next value from a sequence via the PostgreSQL nextval function.

Since: 1.0.0.0

sequenceCurrentValue :: MonadOrville m => SequenceDefinition -> m Int64 Source #

Fetches the current value from a sequence via the PostgreSQL currval function.

Since: 1.0.0.0

sequenceSetValue :: MonadOrville m => SequenceDefinition -> Int64 -> m Int64 Source #

Sets the current value from a sequence via the PostgreSQL setval function.

Since: 1.0.0.0

data SequenceDefinition Source #

Contains the definition of a SQL sequence for Orville to use when creating the sequence and fetching values from it. You can create a SequenceDefinition with default values via mkSequenceDefinition and then use the various set functions that are provided if you need to set specific attributes on the sequence.

Since: 1.0.0.0

mkSequenceDefinition :: String -> SequenceDefinition Source #

Constructs an ascending SequenceDefinition with increment 1 and cache 1 that does not cycle. The sequence will start at 1 and count to the largest Int64 value.

Since: 1.0.0.0

setSequenceSchema :: String -> SequenceDefinition -> SequenceDefinition Source #

Sets the sequence's schema to the name in the given String, which will be treated as a SQL identifier. If a sequence has a schema name set, it will be included as a qualifier on the sequence name for all queries involving the sequence.

Since: 1.0.0.0

sequenceIdentifier :: SequenceDefinition -> SequenceIdentifier Source #

Retrieves the SequenceIdentifier for this sequence, which is set by the name provided to mkSequenceDefinition and any calls made to setSequenceSchema thereafter.

Since: 1.0.0.0

sequenceName :: SequenceDefinition -> Qualified SequenceName Source #

Retrieves the Qualified SequenceName for the sequence that should be used to build SQL expressions involving it.

Since: 1.0.0.0

sequenceIncrement :: SequenceDefinition -> Int64 Source #

Retrieves the increment value for the sequence.

Since: 1.0.0.0

setSequenceIncrement :: Int64 -> SequenceDefinition -> SequenceDefinition Source #

Sets the increment value for the sequence. The increment cannot be set to 0 (PostgreSQL will raise an error when trying to create or modify the sequence in this case).

If the increment is negative, the sequence will be descending. When no explicit start is set, a descending sequence begins at the max value.

Since: 1.0.0.0

sequenceMinValue :: SequenceDefinition -> Int64 Source #

Retrieves the min value of the sequence. If no explicit minimum has been set, this returns 1 for ascending sequences and minBound for Int64 for descending sequences.

Since: 1.0.0.0

setSequenceMinValue :: Int64 -> SequenceDefinition -> SequenceDefinition Source #

Sets the min value for the sequence.

Since: 1.0.0.0

sequenceMaxValue :: SequenceDefinition -> Int64 Source #

Retrieves the max value of the sequence. If no explicit maximum has been set, this returns maxBound for Int64 for ascending sequences and -1 for descending sequences.

Since: 1.0.0.0

setSequenceMaxValue :: Int64 -> SequenceDefinition -> SequenceDefinition Source #

Sets the max value for the sequence.

Since: 1.0.0.0

sequenceStart :: SequenceDefinition -> Int64 Source #

Retrieves the start value for the sequence. If no explicit start value has been set, this returns sequenceMinValue for ascending sequences and sequenceMaxValue for descending sequences.

Since: 1.0.0.0

setSequenceStart :: Int64 -> SequenceDefinition -> SequenceDefinition Source #

Sets the sequence start value. The start value must be at least the minimum value and no greater than the maximum value.

Since: 1.0.0.0

sequenceCache :: SequenceDefinition -> Int64 Source #

Retrieves the number of sequence values that will be pre-allocated by PostgreSQL.

Since: 1.0.0.0

setSequenceCache :: Int64 -> SequenceDefinition -> SequenceDefinition Source #

Sets the number of sequence values that will be pre-allocated by PostgreSQL.

Since: 1.0.0.0

sequenceCycle :: SequenceDefinition -> Bool Source #

Indicates whether the sequence will wrap around when it reaches the maximum value (for ascending sequences) or minimum value (for descending sequences). When False, any attempts to get the next value of the sequence while at the limit will result in an error.

Since: 1.0.0.0

setSequenceCycle :: Bool -> SequenceDefinition -> SequenceDefinition Source #

Sets the sequenceCycle value for the sequence. True indicates that the sequence will cycle. False will cause an error to be raised if the next sequence value is requested while already at the limit.

Since: 1.0.0.0

mkCreateSequenceExpr :: SequenceDefinition -> CreateSequenceExpr Source #

Builds a CreateSequenceExpr that will create a SQL sequence matching the given SequenceDefinition when it is executed.

Since: 1.0.0.0

unqualifiedNameToSequenceId :: String -> SequenceIdentifier Source #

Constructs a SequenceIdentifier where the sequence's name will not be qualified by a particular schema.

Since: 1.0.0.0

sequenceIdUnqualifiedNameString :: SequenceIdentifier -> String Source #

Retrieves the unqualified name of the sequence as a String.

Since: 1.0.0.0

sequenceIdQualifiedName :: SequenceIdentifier -> Qualified SequenceName Source #

Returns the 'Expr.Qualified Expr.SequenceName' that should be used to refer to the sequence in SQL queries.

Since: 1.0.0.0

setSequenceIdSchema :: String -> SequenceIdentifier -> SequenceIdentifier Source #

Sets the schema of the SequenceIdentifier. Wherever applicable, references to the sequence will be qualified by the given schema name.

Since: 1.0.0.0

sequenceIdSchemaNameString :: SequenceIdentifier -> Maybe String Source #

Retrieves the schema name of the sequence as a String.

Since: 1.0.0.0

sequenceIdToString :: SequenceIdentifier -> String Source #

Converts a SequenceIdentifier for a String for descriptive purposes. The name will be qualified if a schema name has been set for the identifier.

Note: You should not use this function for building SQL expressions. Use sequenceIdQualifiedName instead for that.

Since: 1.0.0.0

Numeric types

integer :: SqlType Int32 Source #

integer defines a 32-bit integer type. This corresponds to the INTEGER type in SQL.

Since: 1.0.0.0

serial :: SqlType Int32 Source #

serial defines a 32-bit auto-incrementing column type. This corresponds to the SERIAL type in PostgreSQL.

Since: 1.0.0.0

bigInteger :: SqlType Int64 Source #

bigInteger defines a 64-bit integer type. This corresponds to the BIGINT type in SQL.

Since: 1.0.0.0

bigSerial :: SqlType Int64 Source #

bigSerial defines a 64-bit auto-incrementing column type. This corresponds to the BIGSERIAL type in PostgresSQL.

Since: 1.0.0.0

double :: SqlType Double Source #

double defines a floating point numeric type. This corresponds to the "DOUBLE PRECISION" type in SQL.

Since: 1.0.0.0

Textual-ish types

boolean :: SqlType Bool Source #

boolean defines a True/False boolean type. This corresponds to the BOOLEAN type in SQL.

Since: 1.0.0.0

unboundedText :: SqlType Text Source #

unboundedText defines an unbounded length text field type. This corresponds to a TEXT type in PostgreSQL.

Since: 1.0.0.0

fixedText :: Int32 -> SqlType Text Source #

fixedText defines a fixed length text field type. This corresponds to a "CHAR(len)" type in PostgreSQL.

Since: 1.0.0.0

boundedText :: Int32 -> SqlType Text Source #

boundedText defines a variable length text field type. This corresponds to a "VARCHAR(len)" type in PostgreSQL.

Since: 1.0.0.0

textSearchVector :: SqlType Text Source #

textSearchVector defines a type for indexed text searching. It corresponds to the TSVECTOR type in PostgreSQL.

Since: 1.0.0.0

uuid :: SqlType UUID Source #

uuid defines a UUID type. It corresponds to the UUID type in PostgreSQL.

Since: 1.0.0.0

Date types

date :: SqlType Day Source #

date defines a type representing a calendar date (without time zone). It corresponds to the DATE type in SQL.

Since: 1.0.0.0

timestamp :: SqlType UTCTime Source #

timestamp defines a type representing a particular point in time without time zone information, but can be constructed with a time zone offset. It corresponds to the "TIMESTAMP with time zone" type in SQL.

Note: This is NOT a typo. The "TIMESTAMP with time zone" type in SQL does not include any actual time zone information. For an excellent explanation of the complexities involving this type, please see Chris Clark's blog post about it: http://blog.untrod.com/2016/08/actually-understanding-timezones-in-postgresql.html

Since: 1.0.0.0

Json type

jsonb :: SqlType Text Source #

jsonb represents any type that can be converted To and From JSON. This corresponds to the JSONB type in PostgreSQL.

Since: 1.0.0.0

Type conversions

foreignRefType :: SqlType a -> SqlType a Source #

foreignRefType creates a SqlType suitable for columns that will be foreign keys referencing a column of the given SqlType. For most types, the underlying SQL type will be identical, but for special types (such as auto-incrementing primary keys), the type constructed by foreignRefType will have a regular underlying SQL type. Each SqlType definition must specify any special handling required when creating foreign reference types by setting the sqlTypeReferenceExpr field to an appropriate value.

Since: 1.0.0.0

convertSqlType :: (b -> a) -> (a -> b) -> SqlType a -> SqlType b Source #

convertSqlType changes the Haskell type used by a SqlType in the same manner as tryConvertSqlType in cases where an a can always be converted to a b.

Since: 1.0.0.0

tryConvertSqlType :: (b -> a) -> (a -> Either String b) -> SqlType a -> SqlType b Source #

tryConvertSqlType changes the Haskell type used by a SqlType which changes the column type that will be used in the database schema. The functions given will be used to convert the now Haskell type to and from the original type when reading and writing values from the database. When reading an a value from the database, the conversion function should produce Left with an error message if the value cannot be successfully converted to a b.

Since: 1.0.0.0

data SqlType a Source #

SqlType defines the mapping of a Haskell type (a) to a SQL column type in the database. This includes both how to convert the type to and from the raw values read from the database as well as the schema information required to create and migrate columns using the type.

Since: 1.0.0.0

Constructors

SqlType 

Fields

  • sqlTypeExpr :: DataType

    The SQL data type expression to use when creating/migrating columns of this type.

  • sqlTypeReferenceExpr :: Maybe DataType

    The SQL data type expression to use when creating/migrating columns with foreign keys to this type. This is used by foreignRefType to build a new SqlType when making foreign key fields.

  • sqlTypeOid :: Oid

    The Oid for the type in PostgreSQL. This will be used during migrations to determine whether the column type needs to be altered.

  • sqlTypeMaximumLength :: Maybe Int32

    The maximum length for types that take a type parameter (such as char and varchar). This will be used during migration to determine whether the column type needs to be altered.

  • sqlTypeToSql :: a -> SqlValue

    A function for converting Haskell values of this type into values to be stored in the database.

  • sqlTypeFromSql :: SqlValue -> Either String a

    A function for converting values of this type stored in the database into Haskell values. This function should return Left to indicate an error if the conversion is impossible. Otherwise it should return a Right of the corresponding a value.

  • sqlTypeDontDropImplicitDefaultDuringMigrate :: Bool

    The SERIAL and BIGSERIAL PostgreSQL types are really pseudo-types that create an implicit default value. This flag tells Orville's auto-migration logic to ignore the default value rather than drop it as it normally would.

data QueryExpr Source #

Type to represent a SQL query, E.G.

SELECT id FROM some_table

QueryExpr provides a SqlExpression instance. See unsafeSqlExpression for how to construct a value with your own custom SQL.

Since: 1.0.0.0

Instances

Instances details
SqlExpression QueryExpr Source # 
Instance details

Defined in Orville.PostgreSQL.Expr.Query

executeAndDecode :: (MonadOrville m, SqlExpression sql) => QueryType -> sql -> AnnotatedSqlMarshaller writeEntity readEntity -> m [readEntity] Source #

Executes a SQL query and decodes the result set using the provided marshaller. Any SQL Execution callbacks that have been added to the OrvilleState will be called.

If the query fails or if any row is unable to be decoded by the marshaller, an exception will be raised.

Since: 1.0.0.0

executeAndReturnAffectedRows :: (MonadOrville m, SqlExpression sql) => QueryType -> sql -> m Int Source #

Executes a SQL query and returns the number of rows affected by the query. Any SQL Execution callbacks that have been added to the OrvilleState will be called.

This function can only be used for the execution of a SELECT, CREATE TABLE AS, INSERT, UPDATE, DELETE, MOVE, FETCH, or COPY statement, or an EXECUTE of a prepared query that contains an INSERT, UPDATE, or DELETE statement. If the query is anything else, an AffectedRowsDecodingError wil be raised after the query is executed when the result is read.

If the query fails, an exception will be raised.

Since: 1.0.0.0

executeVoid :: (MonadOrville m, SqlExpression sql) => QueryType -> sql -> m () Source #

Executes a SQL query and ignores the result. Any SQL Execution callbacks that have been added to the OrvilleState will be called.

If the query fails an exception will be raised.

Since: 1.0.0.0

data QueryType Source #

A simple categorization of SQL queries that is used to provide a hint to user callbacks about what kind of query is being run.

See addSqlExecutionCallback

Since: 1.0.0.0

Instances

Instances details
Bounded QueryType Source #

Since: 1.0.0.0

Instance details

Defined in Orville.PostgreSQL.Execution.QueryType

Enum QueryType Source #

Since: 1.0.0.0

Instance details

Defined in Orville.PostgreSQL.Execution.QueryType

Read QueryType Source #

Since: 1.0.0.0

Instance details

Defined in Orville.PostgreSQL.Execution.QueryType

Show QueryType Source #

Since: 1.0.0.0

Instance details

Defined in Orville.PostgreSQL.Execution.QueryType

Eq QueryType Source #

Since: 1.0.0.0

Instance details

Defined in Orville.PostgreSQL.Execution.QueryType

Ord QueryType Source #

Since: 1.0.0.0

Instance details

Defined in Orville.PostgreSQL.Execution.QueryType

SqlCommenter support

type SqlCommenterAttributes = Map Text Text Source #

The representation of Text key/value pairs for supporting the sqlcommenter specification. This allows you to attach key/values of Text that supporting systems can use for advanced metrics. See sqlcommenter for details of the specification.

Since: 1.0.0.0