| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Database.Selda.Backend
Description
API for building Selda backends and adding support for more types in queries.
Synopsis
- class MonadIO m => MonadSelda m where
- data SeldaT m a
- type SeldaM = SeldaT IO
- data SeldaError
- data StmtID
- data BackendID
- = SQLite
- | PostgreSQL
- | Other Text
- type QueryRunner a = Text -> [Param] -> IO a
- data SeldaBackend = SeldaBackend {
- runStmt :: Text -> [Param] -> IO (Int, [[SqlValue]])
- runStmtWithPK :: Text -> [Param] -> IO Int
- prepareStmt :: StmtID -> [SqlTypeRep] -> Text -> IO Dynamic
- runPrepared :: Dynamic -> [Param] -> IO (Int, [[SqlValue]])
- getTableInfo :: TableName -> IO [ColumnInfo]
- ppConfig :: PPConfig
- closeConnection :: SeldaConnection -> IO ()
- backendId :: BackendID
- disableForeignKeys :: Bool -> IO ()
- data SeldaConnection
- data SqlValue where
- data IndexMethod
- data Param where
- data ColAttr
- data PPConfig = PPConfig {
- ppType :: SqlTypeRep -> Text
- ppTypeHook :: SqlTypeRep -> [ColAttr] -> (SqlTypeRep -> Text) -> Text
- ppTypePK :: SqlTypeRep -> Text
- ppPlaceholder :: Int -> Text
- ppColAttrs :: [ColAttr] -> Text
- ppColAttrsHook :: SqlTypeRep -> [ColAttr] -> ([ColAttr] -> Text) -> Text
- ppAutoIncInsert :: Text
- ppMaxInsertParams :: Maybe Int
- ppIndexMethodHook :: IndexMethod -> Text
- defPPConfig :: PPConfig
- data TableName
- data ColName
- data ColumnInfo = ColumnInfo {
- colName :: ColName
- colType :: Either Text SqlTypeRep
- colIsPK :: Bool
- colIsAutoIncrement :: Bool
- colIsUnique :: Bool
- colIsNullable :: Bool
- colHasIndex :: Bool
- colFKs :: [(TableName, ColName)]
- columnInfo :: Table a -> [ColumnInfo]
- fromColInfo :: ColInfo -> ColumnInfo
- mkTableName :: Text -> TableName
- mkColName :: Text -> ColName
- fromTableName :: TableName -> Text
- fromColName :: ColName -> Text
- rawTableName :: TableName -> Text
- newConnection :: MonadIO m => SeldaBackend -> Text -> m SeldaConnection
- allStmts :: SeldaConnection -> IO [(StmtID, Dynamic)]
- seldaBackend :: MonadSelda m => m SeldaBackend
- runSeldaT :: (MonadIO m, MonadMask m) => SeldaT m a -> SeldaConnection -> m a
- seldaClose :: MonadIO m => SeldaConnection -> m ()
- module Database.Selda.SqlType
Documentation
class MonadIO m => MonadSelda m where Source #
Some monad with Selda SQL capabilitites.
Note that the default implementations of invalidateTable and
wrapTransaction flush the entire cache and disable caching when
invoked. If you want to use Selda's built-in caching mechanism, you will
need to implement these operations yourself.
Minimal complete definition
Methods
seldaConnection :: m SeldaConnection Source #
Get the connection in use by the computation.
invalidateTable :: Table a -> m () Source #
Invalidate the given table as soon as the current transaction finishes. Invalidate the table immediately if no transaction is ongoing.
Arguments
| :: m () | Signal transaction commit to SQL backend. |
| -> m () | Signal transaction rollback to SQL backend. |
| -> m a | Transaction to perform. |
| -> m a |
Safely wrap a transaction. To ensure consistency of the in-process cache, it is important that any cached tables modified during a transaction are invalidated ONLY if that transaction succeeds, AFTER the changes become visible in the database.
In order to be thread-safe in the presence of asynchronous exceptions, instances should:
- Mask async exceptions.
- Start bookkeeping of tables invalidated during the transaction.
- Perform the transaction, with async exceptions restored.
- Commit transaction, invalidate tables, and disable bookkeeping; OR
- If an exception was raised, rollback transaction, disable bookkeeping, and re-throw the exception.
Arguments
| :: MonadMask m | |
| => m () | Signal transaction commit to SQL backend. |
| -> m () | Signal transaction rollback to SQL backend. |
| -> m a | Transaction to perform. |
| -> m a |
Safely wrap a transaction. To ensure consistency of the in-process cache, it is important that any cached tables modified during a transaction are invalidated ONLY if that transaction succeeds, AFTER the changes become visible in the database.
In order to be thread-safe in the presence of asynchronous exceptions, instances should:
- Mask async exceptions.
- Start bookkeeping of tables invalidated during the transaction.
- Perform the transaction, with async exceptions restored.
- Commit transaction, invalidate tables, and disable bookkeeping; OR
- If an exception was raised, rollback transaction, disable bookkeeping, and re-throw the exception.
Instances
| (MonadIO m, MonadMask m) => MonadSelda (SeldaT m) Source # | |
Defined in Database.Selda.Backend.Internal Methods seldaConnection :: SeldaT m SeldaConnection Source # invalidateTable :: Table a -> SeldaT m () Source # wrapTransaction :: SeldaT m () -> SeldaT m () -> SeldaT m a -> SeldaT m a Source # | |
Monad transformer adding Selda SQL capabilities.
Instances
| MonadTrans SeldaT Source # | |
Defined in Database.Selda.Backend.Internal | |
| Monad m => Monad (SeldaT m) Source # | |
| Functor m => Functor (SeldaT m) Source # | |
| Monad m => Applicative (SeldaT m) Source # | |
| MonadIO m => MonadIO (SeldaT m) Source # | |
Defined in Database.Selda.Backend.Internal | |
| MonadThrow m => MonadThrow (SeldaT m) Source # | |
Defined in Database.Selda.Backend.Internal | |
| MonadCatch m => MonadCatch (SeldaT m) Source # | |
| MonadMask m => MonadMask (SeldaT m) Source # | |
Defined in Database.Selda.Backend.Internal | |
| (MonadIO m, MonadMask m) => MonadSelda (SeldaT m) Source # | |
Defined in Database.Selda.Backend.Internal Methods seldaConnection :: SeldaT m SeldaConnection Source # invalidateTable :: Table a -> SeldaT m () Source # wrapTransaction :: SeldaT m () -> SeldaT m () -> SeldaT m a -> SeldaT m a Source # | |
data SeldaError Source #
Thrown by any function in SeldaT if an error occurs.
Constructors
| DbError String | Unable to open or connect to database. |
| SqlError String | An error occurred while executing query. |
Instances
| Eq SeldaError Source # | |
Defined in Database.Selda.Backend.Internal | |
| Show SeldaError Source # | |
Defined in Database.Selda.Backend.Internal Methods showsPrec :: Int -> SeldaError -> ShowS # show :: SeldaError -> String # showList :: [SeldaError] -> ShowS # | |
| Exception SeldaError Source # | |
Defined in Database.Selda.Backend.Internal Methods toException :: SeldaError -> SomeException # fromException :: SomeException -> Maybe SeldaError # displayException :: SeldaError -> String # | |
A prepared statement identifier. Guaranteed to be unique per application.
Uniquely identifies some particular backend.
When publishing a new backend, consider submitting a pull request with a
constructor for your backend instead of using the Other constructor.
Constructors
| SQLite | |
| PostgreSQL | |
| Other Text |
Instances
| Eq BackendID Source # | |
| Ord BackendID Source # | |
| Show BackendID Source # | |
type QueryRunner a = Text -> [Param] -> IO a Source #
A function which executes a query and gives back a list of extensible tuples; one tuple per result row, and one tuple element per column.
data SeldaBackend Source #
A collection of functions making up a Selda backend.
Constructors
| SeldaBackend | |
Fields
| |
data SeldaConnection Source #
Some value that is representable in SQL.
data IndexMethod Source #
Method to use for indexing with indexedUsing.
Index methods are ignored by the SQLite backend, as SQLite doesn't support
different index methods.
Constructors
| BTreeIndex | |
| HashIndex |
Instances
| Eq IndexMethod Source # | |
Defined in Database.Selda.Table.Type | |
| Ord IndexMethod Source # | |
Defined in Database.Selda.Table.Type Methods compare :: IndexMethod -> IndexMethod -> Ordering # (<) :: IndexMethod -> IndexMethod -> Bool # (<=) :: IndexMethod -> IndexMethod -> Bool # (>) :: IndexMethod -> IndexMethod -> Bool # (>=) :: IndexMethod -> IndexMethod -> Bool # max :: IndexMethod -> IndexMethod -> IndexMethod # min :: IndexMethod -> IndexMethod -> IndexMethod # | |
| Show IndexMethod Source # | |
Defined in Database.Selda.Table.Type Methods showsPrec :: Int -> IndexMethod -> ShowS # show :: IndexMethod -> String # showList :: [IndexMethod] -> ShowS # | |
A parameter to a prepared SQL statement.
Column attributes such as nullability, auto increment, etc. When adding elements, make sure that they are added in the order required by SQL syntax, as this list is only sorted before being pretty-printed.
Constructors
| Primary | |
| AutoIncrement | |
| Required | |
| Optional | |
| Unique | |
| Indexed (Maybe IndexMethod) |
Backend-specific configuration for the SQL pretty-printer.
Constructors
| PPConfig | |
Fields
| |
defPPConfig :: PPConfig Source #
Default settings for pretty-printing. Geared towards SQLite.
The default definition of ppTypePK is 'defType, so that you don’t have to do anything
special if you don’t use special types for primary keys.
Name of a database table.
Instances
| Eq TableName Source # | |
| Ord TableName Source # | |
| Show TableName Source # | |
| IsString TableName Source # | |
Defined in Database.Selda.Types Methods fromString :: String -> TableName # | |
| Hashable TableName Source # | |
Defined in Database.Selda.Types | |
Name of a database column.
data ColumnInfo Source #
Comprehensive information about a column.
Constructors
| ColumnInfo | |
Fields
| |
Instances
| Eq ColumnInfo Source # | |
Defined in Database.Selda.Backend.Internal | |
| Show ColumnInfo Source # | |
Defined in Database.Selda.Backend.Internal Methods showsPrec :: Int -> ColumnInfo -> ShowS # show :: ColumnInfo -> String # showList :: [ColumnInfo] -> ShowS # | |
columnInfo :: Table a -> [ColumnInfo] Source #
Get the column information for each column in the given table.
fromColInfo :: ColInfo -> ColumnInfo Source #
Convert a ColInfo into a ColumnInfo.
mkTableName :: Text -> TableName Source #
Create a column name.
fromTableName :: TableName -> Text Source #
Convert a table name into a string, with quotes.
fromColName :: ColName -> Text Source #
Convert a column name into a string, with quotes.
rawTableName :: TableName -> Text Source #
Convert a table name into a string, without quotes.
newConnection :: MonadIO m => SeldaBackend -> Text -> m SeldaConnection Source #
Create a new Selda connection for the given backend and database identifier string.
allStmts :: SeldaConnection -> IO [(StmtID, Dynamic)] Source #
Get all statements and their corresponding identifiers for the current connection.
seldaBackend :: MonadSelda m => m SeldaBackend Source #
Get the backend in use by the computation.
runSeldaT :: (MonadIO m, MonadMask m) => SeldaT m a -> SeldaConnection -> m a Source #
Run a Selda transformer. Backends should use this to implement their
withX functions.
seldaClose :: MonadIO m => SeldaConnection -> m () Source #
Close a reusable Selda connection.
Closing a connection while in use is undefined.
Passing a closed connection to runSeldaT results in a SeldaError
being thrown. Closing a connection more than once is a no-op.
module Database.Selda.SqlType