selda-0.4.0.0: Multi-backend, high-level EDSL for interacting with SQL databases.

Safe HaskellNone
LanguageHaskell2010

Database.Selda.Backend

Description

API for building Selda backends and adding support for more types in queries.

Synopsis

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

withConnection

Associated Types

type Backend m Source #

Type of database backend used by m.

Methods

withConnection :: (SeldaConnection (Backend m) -> m a) -> m a Source #

Pass a Selda connection to the given computation and execute it. After the computation finishes, withConnection is free to do anything it likes to the connection, including closing it or giving it to another Selda computation. Thus, the computation must take care never to return or otherwise access the connection after returning.

transact :: m a -> m a Source #

Perform the given computation as a transaction. Implementations must ensure that subsequent calls to withConnection within the same transaction always passes the same connection to its argument.

Instances
(MonadIO m, MonadMask m) => MonadSelda (SeldaT b m) Source # 
Instance details

Defined in Database.Selda.Backend.Internal

Associated Types

type Backend (SeldaT b m) :: Type Source #

Methods

withConnection :: (SeldaConnection (Backend (SeldaT b m)) -> SeldaT b m a) -> SeldaT b m a Source #

transact :: SeldaT b m a -> SeldaT b m a Source #

data SeldaT b m a Source #

Monad transformer adding Selda SQL capabilities.

Instances
Monad m => Monad (SeldaT b m) Source # 
Instance details

Defined in Database.Selda.Backend.Internal

Methods

(>>=) :: SeldaT b m a -> (a -> SeldaT b m b0) -> SeldaT b m b0 #

(>>) :: SeldaT b m a -> SeldaT b m b0 -> SeldaT b m b0 #

return :: a -> SeldaT b m a #

fail :: String -> SeldaT b m a #

Functor m => Functor (SeldaT b m) Source # 
Instance details

Defined in Database.Selda.Backend.Internal

Methods

fmap :: (a -> b0) -> SeldaT b m a -> SeldaT b m b0 #

(<$) :: a -> SeldaT b m b0 -> SeldaT b m a #

MonadFail m => MonadFail (SeldaT b m) Source # 
Instance details

Defined in Database.Selda.Backend.Internal

Methods

fail :: String -> SeldaT b m a #

Monad m => Applicative (SeldaT b m) Source # 
Instance details

Defined in Database.Selda.Backend.Internal

Methods

pure :: a -> SeldaT b m a #

(<*>) :: SeldaT b m (a -> b0) -> SeldaT b m a -> SeldaT b m b0 #

liftA2 :: (a -> b0 -> c) -> SeldaT b m a -> SeldaT b m b0 -> SeldaT b m c #

(*>) :: SeldaT b m a -> SeldaT b m b0 -> SeldaT b m b0 #

(<*) :: SeldaT b m a -> SeldaT b m b0 -> SeldaT b m a #

MonadIO m => MonadIO (SeldaT b m) Source # 
Instance details

Defined in Database.Selda.Backend.Internal

Methods

liftIO :: IO a -> SeldaT b m a #

MonadThrow m => MonadThrow (SeldaT b m) Source # 
Instance details

Defined in Database.Selda.Backend.Internal

Methods

throwM :: Exception e => e -> SeldaT b m a #

MonadCatch m => MonadCatch (SeldaT b m) Source # 
Instance details

Defined in Database.Selda.Backend.Internal

Methods

catch :: Exception e => SeldaT b m a -> (e -> SeldaT b m a) -> SeldaT b m a #

MonadMask m => MonadMask (SeldaT b m) Source # 
Instance details

Defined in Database.Selda.Backend.Internal

Methods

mask :: ((forall a. SeldaT b m a -> SeldaT b m a) -> SeldaT b m b0) -> SeldaT b m b0 #

uninterruptibleMask :: ((forall a. SeldaT b m a -> SeldaT b m a) -> SeldaT b m b0) -> SeldaT b m b0 #

generalBracket :: SeldaT b m a -> (a -> ExitCase b0 -> SeldaT b m c) -> (a -> SeldaT b m b0) -> SeldaT b m (b0, c) #

(MonadIO m, MonadMask m) => MonadSelda (SeldaT b m) Source # 
Instance details

Defined in Database.Selda.Backend.Internal

Associated Types

type Backend (SeldaT b m) :: Type Source #

Methods

withConnection :: (SeldaConnection (Backend (SeldaT b m)) -> SeldaT b m a) -> SeldaT b m a Source #

transact :: SeldaT b m a -> SeldaT b m a Source #

type Backend (SeldaT b m) Source # 
Instance details

Defined in Database.Selda.Backend.Internal

type Backend (SeldaT b m) = b

type SeldaM b = SeldaT b IO Source #

The simplest form of Selda computation; SeldaT specialized to IO.

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.

data StmtID Source #

A prepared statement identifier. Guaranteed to be unique per application.

Instances
Eq StmtID Source # 
Instance details

Defined in Database.Selda.Backend.Internal

Methods

(==) :: StmtID -> StmtID -> Bool #

(/=) :: StmtID -> StmtID -> Bool #

Ord StmtID Source # 
Instance details

Defined in Database.Selda.Backend.Internal

Show StmtID Source # 
Instance details

Defined in Database.Selda.Backend.Internal

data BackendID Source #

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 

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 b Source #

A collection of functions making up a Selda backend.

Constructors

SeldaBackend 

Fields

data SqlValue where Source #

Some value that is representable in SQL.

Instances
Show SqlValue Source # 
Instance details

Defined in Database.Selda.SqlType

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 

data Param where Source #

A parameter to a prepared SQL statement.

Constructors

Param :: !(Lit a) -> Param 
Instances
Eq Param Source # 
Instance details

Defined in Database.Selda.SQL

Methods

(==) :: Param -> Param -> Bool #

(/=) :: Param -> Param -> Bool #

Ord Param Source # 
Instance details

Defined in Database.Selda.SQL

Methods

compare :: Param -> Param -> Ordering #

(<) :: Param -> Param -> Bool #

(<=) :: Param -> Param -> Bool #

(>) :: Param -> Param -> Bool #

(>=) :: Param -> Param -> Bool #

max :: Param -> Param -> Param #

min :: Param -> Param -> Param #

Show Param Source # 
Instance details

Defined in Database.Selda.SQL

Methods

showsPrec :: Int -> Param -> ShowS #

show :: Param -> String #

showList :: [Param] -> ShowS #

data ColAttr Source #

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.

Instances
Eq ColAttr Source # 
Instance details

Defined in Database.Selda.Table.Type

Methods

(==) :: ColAttr -> ColAttr -> Bool #

(/=) :: ColAttr -> ColAttr -> Bool #

Ord ColAttr Source # 
Instance details

Defined in Database.Selda.Table.Type

Show ColAttr Source # 
Instance details

Defined in Database.Selda.Table.Type

data PPConfig Source #

Backend-specific configuration for the SQL pretty-printer.

Constructors

PPConfig 

Fields

  • ppType :: SqlTypeRep -> Text

    The SQL type name of the given type.

    This function should be used everywhere a type is needed to be printed but in primary keys position. This is due to the fact that some backends might have a special representation of primary keys (using sequences are such). If you have such a need, please use the ppTypePK record instead.

  • ppTypeHook :: SqlTypeRep -> [ColAttr] -> (SqlTypeRep -> Text) -> Text

    Hook that allows you to modify ppType output.

  • ppTypePK :: SqlTypeRep -> Text

    The SQL type name of the given type for primary keys uses.

  • ppPlaceholder :: Int -> Text

    Parameter placeholder for the nth parameter.

  • ppColAttrs :: [ColAttr] -> Text

    List of column attributes.

  • ppColAttrsHook :: SqlTypeRep -> [ColAttr] -> ([ColAttr] -> Text) -> Text

    Hook that allows you to modify ppColAttrs output.

  • ppAutoIncInsert :: Text

    The value used for the next value for an auto-incrementing column. For instance, DEFAULT for PostgreSQL, and NULL for SQLite.

  • ppMaxInsertParams :: Maybe Int

    Insert queries may have at most this many parameters; if an insertion has more parameters than this, it will be chunked.

    Note that only insertions of multiple rows are chunked. If your table has more than this many columns, you should really rethink your database design.

  • ppIndexMethodHook :: IndexMethod -> Text

    CREATE INDEX suffix to indicate that the index should use the given index method.

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.

data TableName Source #

Name of a database table.

data ColName Source #

Name of a database column.

Instances
Eq ColName Source # 
Instance details

Defined in Database.Selda.Types

Methods

(==) :: ColName -> ColName -> Bool #

(/=) :: ColName -> ColName -> Bool #

Ord ColName Source # 
Instance details

Defined in Database.Selda.Types

Show ColName Source # 
Instance details

Defined in Database.Selda.Types

IsString ColName Source # 
Instance details

Defined in Database.Selda.Types

Methods

fromString :: String -> ColName #

data TableInfo Source #

Comprehensive information about a table.

Constructors

TableInfo 

Fields

Instances
Eq TableInfo Source # 
Instance details

Defined in Database.Selda.Backend.Internal

Show TableInfo Source # 
Instance details

Defined in Database.Selda.Backend.Internal

data ColumnInfo Source #

Comprehensive information about a column.

Constructors

ColumnInfo 

Fields

tableInfo :: Table a -> TableInfo 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.

mkColName :: Text -> ColName 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 b -> Text -> m (SeldaConnection b) Source #

Create a new Selda connection for the given backend and database identifier string.

allStmts :: SeldaConnection b -> IO [(StmtID, Dynamic)] Source #

Get all statements and their corresponding identifiers for the current connection.

withBackend :: MonadSelda m => (SeldaBackend (Backend m) -> m a) -> m a Source #

Get the backend in use by the computation.

runSeldaT :: (MonadIO m, MonadMask m) => SeldaT b m a -> SeldaConnection b -> m a Source #

Run a Selda transformer. Backends should use this to implement their withX functions.

seldaClose :: MonadIO m => SeldaConnection b -> 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.