selda-0.1.5.0: Type-safe, high-level EDSL for interacting with relational databases.

Safe HaskellNone
LanguageHaskell2010

Database.Selda.Backend

Description

API for building Selda backends.

Synopsis

Documentation

class Monad m => MonadIO m where #

Monads in which IO computations may be embedded. Any monad built by applying a sequence of monad transformers to the IO monad will be an instance of this class.

Instances should satisfy the following laws, which state that liftIO is a transformer of monads:

Minimal complete definition

liftIO

Methods

liftIO :: IO a -> m a #

Lift a computation from the IO monad.

Instances

MonadIO IO 

Methods

liftIO :: IO a -> IO a #

MonadIO m => MonadIO (ListT m) 

Methods

liftIO :: IO a -> ListT m a #

MonadIO m => MonadIO (MaybeT m) 

Methods

liftIO :: IO a -> MaybeT m a #

MonadIO m => MonadIO (SeldaT m) # 

Methods

liftIO :: IO a -> SeldaT m a #

(Error e, MonadIO m) => MonadIO (ErrorT e m) 

Methods

liftIO :: IO a -> ErrorT e m a #

MonadIO m => MonadIO (ExceptT e m) 

Methods

liftIO :: IO a -> ExceptT e m a #

MonadIO m => MonadIO (StateT s m) 

Methods

liftIO :: IO a -> StateT s m a #

MonadIO m => MonadIO (StateT s m) 

Methods

liftIO :: IO a -> StateT s m a #

(Monoid w, MonadIO m) => MonadIO (WriterT w m) 

Methods

liftIO :: IO a -> WriterT w m a #

(Monoid w, MonadIO m) => MonadIO (WriterT w m) 

Methods

liftIO :: IO a -> WriterT w m a #

MonadIO m => MonadIO (IdentityT * m) 

Methods

liftIO :: IO a -> IdentityT * m a #

MonadIO m => MonadIO (ContT * r m) 

Methods

liftIO :: IO a -> ContT * r m a #

MonadIO m => MonadIO (ReaderT * r m) 

Methods

liftIO :: IO a -> ReaderT * r m a #

(Monoid w, MonadIO m) => MonadIO (RWST r w s m) 

Methods

liftIO :: IO a -> RWST r w s m a #

(Monoid w, MonadIO m) => MonadIO (RWST r w s m) 

Methods

liftIO :: IO a -> RWST r w s m a #

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

  • runStmt :: QueryRunner (Int, [[SqlValue]])

    Execute an SQL statement.

  • runStmtWithPK :: QueryRunner Int

    Execute an SQL statement and return the last inserted primary key, where the primary key is auto-incrementing. Backends must take special care to make this thread-safe.

  • customColType :: Text -> [ColAttr] -> Maybe Text

    Generate a custom column type for the column having the given Selda type and list of attributes.

  • defaultKeyword :: Text

    The keyword that represents the default value for auto-incrementing primary keys.

  • dbIdentifier :: Text

    A string uniquely identifying the database used by this invocation of the backend. This could be, for instance, a PostgreSQL connection string or the absolute path to an SQLite file.

class MonadIO m => MonadSelda m where Source #

Some monad with Selda SQL capabilitites.

Methods

seldaBackend :: m SeldaBackend Source #

Get the backend 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.

beginTransaction :: m () Source #

Indicates the start of a new transaction. Starts bookkeeping to invalidate all tables modified during the transaction at the next call to endTransaction.

endTransaction :: Bool -> m () Source #

Indicates the end of the current transaction. Invalidates all tables that were modified since the last call to beginTransaction, unless the transaction was rolled back.

newtype SeldaT m a Source #

Monad transformer adding Selda SQL capabilities.

Constructors

S 

Fields

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 => 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 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 :: !(Lit a) -> Lit (Maybe a) 
LNull :: Lit (Maybe a) 

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

Some value that is representable in SQL.

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.

compileColAttr :: ColAttr -> Text Source #

Compile a column attribute.

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.

runSeldaT :: MonadIO m => SeldaT m a -> SeldaBackend -> m a Source #

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