selda-0.1.10.1: Type-safe, high-level EDSL for interacting with relational 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.

Minimal complete definition

seldaConnection, invalidateTable, wrapTransaction

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.

wrapTransaction :: m () -> m () -> m a -> m a Source #

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:

  1. Mask async exceptions.
  2. Start bookkeeping of tables invalidated during the transaction.
  3. Perform the transaction, with async exceptions restored.
  4. Commit transaction, invalidate tables, and disable bookkeeping; OR
  5. If an exception was raised, rollback transaction and disable bookkeeping.

See the instance for SeldaT for an example of how to do this safely.

data SeldaT m a Source #

Monad transformer adding Selda SQL capabilities.

Instances

MonadTrans SeldaT Source # 

Methods

lift :: Monad m => m a -> SeldaT m a #

Monad m => Monad (SeldaT m) Source # 

Methods

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

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

return :: a -> SeldaT m a #

fail :: String -> SeldaT m a #

Functor m => Functor (SeldaT m) Source # 

Methods

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

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

Monad m => Applicative (SeldaT m) Source # 

Methods

pure :: a -> SeldaT m a #

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

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

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

MonadIO m => MonadIO (SeldaT m) Source # 

Methods

liftIO :: IO a -> SeldaT m a #

MonadThrow m => MonadThrow (SeldaT m) Source # 

Methods

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

MonadCatch m => MonadCatch (SeldaT m) Source # 

Methods

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

MonadMask m => MonadMask (SeldaT m) Source # 

Methods

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

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

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

type SeldaM = SeldaT 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.

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

A collection of functions making up a Selda backend.

Constructors

SeldaBackend 

Fields

class Typeable a => SqlType a where Source #

Any datatype representable in (Selda's subset of) SQL.

Minimal complete definition

mkLit, fromSql, defaultValue

Methods

mkLit :: a -> Lit a Source #

Create a literal of this type.

sqlType :: Proxy a -> SqlTypeRep Source #

The SQL representation for this type.

fromSql :: SqlValue -> a Source #

Convert an SqlValue into this type.

defaultValue :: Lit a Source #

Default value when using def at this type.

Instances

SqlType Bool Source # 
SqlType Double Source # 
SqlType Int Source # 
SqlType ByteString Source # 
SqlType ByteString Source # 
SqlType Text Source # 
SqlType TimeOfDay Source # 
SqlType UTCTime Source # 
SqlType Day Source # 
SqlType RowID Source # 
SqlType a => SqlType (Maybe a) Source # 

data SqlValue where Source #

Some value that is representable in SQL.

data Param where Source #

A parameter to a prepared SQL statement.

Constructors

Param :: !(Lit a) -> Param 

Instances

Eq Param Source # 

Methods

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

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

Ord Param Source # 

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 # 

Methods

showsPrec :: Int -> Param -> ShowS #

show :: Param -> String #

showList :: [Param] -> ShowS #

data Lit a where Source #

An SQL literal.

Constructors

LText :: !Text -> Lit Text 
LInt :: !Int -> Lit Int 
LDouble :: !Double -> Lit Double 
LBool :: !Bool -> Lit Bool 
LDateTime :: !Text -> Lit UTCTime 
LDate :: !Text -> Lit Day 
LTime :: !Text -> Lit TimeOfDay 
LJust :: SqlType a => !(Lit a) -> Lit (Maybe a) 
LBlob :: !ByteString -> Lit ByteString 
LNull :: SqlType a => Lit (Maybe a) 
LCustom :: Lit a -> Lit b 

Instances

Eq (Lit a) Source # 

Methods

(==) :: Lit a -> Lit a -> Bool #

(/=) :: Lit a -> Lit a -> Bool #

Ord (Lit a) Source # 

Methods

compare :: Lit a -> Lit a -> Ordering #

(<) :: Lit a -> Lit a -> Bool #

(<=) :: Lit a -> Lit a -> Bool #

(>) :: Lit a -> Lit a -> Bool #

(>=) :: Lit a -> Lit a -> Bool #

max :: Lit a -> Lit a -> Lit a #

min :: Lit a -> Lit a -> Lit a #

Show (Lit a) Source # 

Methods

showsPrec :: Int -> Lit a -> ShowS #

show :: Lit a -> String #

showList :: [Lit a] -> 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.

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.

  • ppPlaceholder :: Int -> Text

    Parameter placeholder for the nth parameter.

  • ppColAttrs :: [ColAttr] -> Text

    List of column attributes, such as

  • 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.

defPPConfig :: PPConfig Source #

Default settings for pretty-printing. Geared towards SQLite.

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.

sqlDateTimeFormat :: String Source #

Format string used to represent date and time when talking to the database backend.

sqlDateFormat :: String Source #

Format string used to represent date when talking to the database backend.

sqlTimeFormat :: String Source #

Format string used to represent time of day when talking to the database backend.