| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Database.PostgreSQL.Query.Types
Contents
- class MonadBase IO m => HasPostgres m where
- type MonadPostgres m = (HasPostgres m, MonadLogger m)
- class TransactionSafe m
- newtype PgMonadT m a = PgMonadT {
- unPgMonadT :: ReaderT Connection m a
- runPgMonadT :: Connection -> PgMonadT m a -> m a
- launchPG :: HasPostgres m => PgMonadT m a -> m a
- data Qp = ToRow row => Qp Query row
- newtype InetText = InetText {
- unInetText :: Text
- newtype FN = FN [Text]
- textFN :: Text -> FN
- newtype MarkedRow = MR {
- unMR :: [(FN, SqlBuilder)]
- mrToBuilder :: SqlBuilder -> MarkedRow -> SqlBuilder
- class ToMarkedRow a where
Query execution
class MonadBase IO m => HasPostgres m where Source #
Instances of this typeclass can acquire connection and pass it to computation. It can be reader of pool of connections or just reader of connection
Minimal complete definition
Methods
withPGConnection :: (Connection -> m a) -> m a Source #
Instances
| HasPostgres m => HasPostgres (MaybeT m) Source # | |
| MonadBase IO m => HasPostgres (PgMonadT m) Source # | |
| HasPostgres m => HasPostgres (IdentityT * m) Source # | |
| (HasPostgres m, Monoid w) => HasPostgres (WriterT w m) Source # | |
| (HasPostgres m, Monoid w) => HasPostgres (WriterT w m) Source # | |
| HasPostgres m => HasPostgres (StateT s m) Source # | |
| HasPostgres m => HasPostgres (StateT s m) Source # | |
| HasPostgres m => HasPostgres (EitherT e m) Source # | |
| (MonadBase IO m, MonadBaseControl IO m, HGettable els (Pool Connection)) => HasPostgres (HReaderT els m) Source # | |
| HasPostgres m => HasPostgres (ExceptT e m) Source # | |
| HasPostgres m => HasPostgres (ReaderT * r m) Source # | |
| HasPostgres m => HasPostgres (ContT * r m) Source # | |
type MonadPostgres m = (HasPostgres m, MonadLogger m) Source #
class TransactionSafe m Source #
Empty typeclass signing monad in which transaction is
safe. i.e. PgMonadT have this instance, but some other monad giving
connection from e.g. connection pool is not.
Instances
| TransactionSafe m => TransactionSafe (MaybeT m) Source # | |
| TransactionSafe (PgMonadT m) Source # | |
| TransactionSafe m => TransactionSafe (IdentityT * m) Source # | |
| (TransactionSafe m, Monoid w) => TransactionSafe (WriterT w m) Source # | |
| (TransactionSafe m, Monoid w) => TransactionSafe (WriterT w m) Source # | |
| TransactionSafe m => TransactionSafe (StateT s m) Source # | |
| TransactionSafe m => TransactionSafe (StateT s m) Source # | |
| TransactionSafe m => TransactionSafe (EitherT e m) Source # | |
| TransactionSafe m => TransactionSafe (ExceptT e m) Source # | |
| TransactionSafe m => TransactionSafe (ReaderT * r m) Source # | |
| TransactionSafe m => TransactionSafe (ContT * r m) Source # | |
Reader of connection. Has instance of HasPostgres. So if you have a
connection you can run queries in this monad using runPgMonadT. Or you
can use this transformer to run sequence of queries using same
connection with launchPG.
Constructors
| PgMonadT | |
Fields
| |
Instances
runPgMonadT :: Connection -> PgMonadT m a -> m a Source #
launchPG :: HasPostgres m => PgMonadT m a -> m a Source #
If your monad have instance of HasPostgres you maybe dont need this
function, unless your instance use withPGPool which acquires connection
from pool for each query. If you want to run sequence of queries using same
connection you need this function
Auxiliary types
Special constructor to perform old-style query interpolation
Instances
type to put and get from db inet and cidr typed postgresql
fields. This should be in postgresql-simple in fact.
Constructors
| InetText | |
Fields
| |
Dot-separated field name. Each element in nested list will be
properly quoted and separated by dot. It also have instance of
ToSqlBuilder and IsString so you can:
>>>let a = "hello" :: FN>>>aFN ["hello"]
>>>let b = "user.name" :: FN>>>bFN ["user","name"]
>>>let n = "u.name" :: FN>>>runSqlBuilder c $ toSqlBuilder n"\"u\".\"name\""
>>>("user" <> "name") :: FNFN ["user","name"]
>>>let a = "name" :: FN>>>let b = "email" :: FN>>>runSqlBuilder c [sqlExp|^{"u" <> a} = 'name', ^{"e" <> b} = 'email'|]"\"u\".\"name\" = 'name', \"e\".\"email\" = 'email'"
Marked row is list of pairs of field name and some sql expression. Used to generate queries like:
name = name AND size = 10 AND length = 20
or
UPDATE tbl SET name = name, size = 10, lenght = 20
Constructors
| MR | |
Fields
| |
Arguments
| :: SqlBuilder | Builder to intercalate with |
| -> MarkedRow | |
| -> SqlBuilder |
Turns marked row to query intercalating it with other builder
>>>runSqlBuilder c $ mrToBuilder "AND" $ MR [("name", mkValue "petr"), ("email", mkValue "foo@bar.com")]" \"name\" = 'petr' AND \"email\" = 'foo@bar.com' "