| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Opaleye.Trans
Synopsis
- newtype OpaleyeT m a = OpaleyeT {
- unOpaleyeT :: ReaderT Connection m a
- runOpaleyeT :: Connection -> OpaleyeT m a -> m a
- data Transaction a
- transaction :: MonadIO m => Transaction a -> OpaleyeT m a
- run :: MonadIO m => Transaction a -> OpaleyeT m a
- query :: Default QueryRunner a b => Query a -> Transaction [b]
- queryFirst :: Default QueryRunner a b => Query a -> Transaction (Maybe b)
- insert :: Table w r -> w -> Transaction Int64
- insertMany :: Table w r -> [w] -> Transaction Int64
- insertReturning :: Default QueryRunner a b => Table w r -> (r -> a) -> w -> Transaction [b]
- insertReturningFirst :: Default QueryRunner a b => Table w r -> (r -> a) -> w -> Transaction (Maybe b)
- insertManyReturning :: Default QueryRunner a b => Table w r -> [w] -> (r -> a) -> Transaction [b]
- update :: Table w r -> (r -> w) -> (r -> Column PGBool) -> Transaction Int64
- updateReturning :: Default QueryRunner a b => Table w r -> (r -> w) -> (r -> Column PGBool) -> (r -> a) -> Transaction [b]
- updateReturningFirst :: Default QueryRunner a b => Table w r -> (r -> w) -> (r -> Column PGBool) -> (r -> a) -> Transaction (Maybe b)
- delete :: Table a b -> (b -> Column PGBool) -> Transaction Int64
- withConn :: MonadIO m => (Connection -> IO a) -> OpaleyeT m a
- liftIO :: MonadIO m => IO a -> m a
- class Monad m => MonadIO (m :: Type -> Type)
- ask :: MonadReader r m => m r
- data Int64
Documentation
The Opaleye monad transformer
Constructors
| OpaleyeT | |
Fields
| |
Instances
| MonadTrans OpaleyeT Source # | |
Defined in Opaleye.Trans | |
| Monad m => MonadReader Connection (OpaleyeT m) Source # | |
Defined in Opaleye.Trans Methods ask :: OpaleyeT m Connection # local :: (Connection -> Connection) -> OpaleyeT m a -> OpaleyeT m a # reader :: (Connection -> a) -> OpaleyeT m a # | |
| Monad m => Monad (OpaleyeT m) Source # | |
| Functor m => Functor (OpaleyeT m) Source # | |
| Applicative m => Applicative (OpaleyeT m) Source # | |
Defined in Opaleye.Trans | |
| MonadIO m => MonadIO (OpaleyeT m) Source # | |
Defined in Opaleye.Trans | |
| MonadThrow m => MonadThrow (OpaleyeT m) Source # | |
Defined in Opaleye.Trans | |
| MonadCatch m => MonadCatch (OpaleyeT m) Source # | |
runOpaleyeT :: Connection -> OpaleyeT m a -> m a Source #
Given a Connection, run an OpaleyeT
Transactions
data Transaction a Source #
Instances
| Monad Transaction Source # | |
Defined in Opaleye.Trans Methods (>>=) :: Transaction a -> (a -> Transaction b) -> Transaction b # (>>) :: Transaction a -> Transaction b -> Transaction b # return :: a -> Transaction a # | |
| Functor Transaction Source # | |
Defined in Opaleye.Trans Methods fmap :: (a -> b) -> Transaction a -> Transaction b # (<$) :: a -> Transaction b -> Transaction a # | |
| Applicative Transaction Source # | |
Defined in Opaleye.Trans Methods pure :: a -> Transaction a # (<*>) :: Transaction (a -> b) -> Transaction a -> Transaction b # liftA2 :: (a -> b -> c) -> Transaction a -> Transaction b -> Transaction c # (*>) :: Transaction a -> Transaction b -> Transaction b # (<*) :: Transaction a -> Transaction b -> Transaction a # | |
| MonadReader Connection Transaction Source # | |
Defined in Opaleye.Trans Methods ask :: Transaction Connection # local :: (Connection -> Connection) -> Transaction a -> Transaction a # reader :: (Connection -> a) -> Transaction a # | |
transaction :: MonadIO m => Transaction a -> OpaleyeT m a Source #
Run a postgresql transaction in the OpaleyeT monad
run :: MonadIO m => Transaction a -> OpaleyeT m a Source #
Execute a query without a literal transaction
Queries
query :: Default QueryRunner a b => Query a -> Transaction [b] Source #
queryFirst :: Default QueryRunner a b => Query a -> Transaction (Maybe b) Source #
Inserts
insertMany :: Table w r -> [w] -> Transaction Int64 Source #
Insert many records into a Table. See runInsertMany.
insertReturning :: Default QueryRunner a b => Table w r -> (r -> a) -> w -> Transaction [b] Source #
Insert a record into a Table with a return value. See runInsertReturning.
insertReturningFirst :: Default QueryRunner a b => Table w r -> (r -> a) -> w -> Transaction (Maybe b) Source #
Insert a record into a Table with a return value. Retrieve only the first result.
Similar to listToMaybe <$> insertReturning
insertManyReturning :: Default QueryRunner a b => Table w r -> [w] -> (r -> a) -> Transaction [b] Source #
Insert many records into a Table with a return value for each record.
Maybe not worth defining. This almost certainly does the wrong thing.
Updates
updateReturning :: Default QueryRunner a b => Table w r -> (r -> w) -> (r -> Column PGBool) -> (r -> a) -> Transaction [b] Source #
Update items in a Table with a return value. See runUpdateReturning.
updateReturningFirst :: Default QueryRunner a b => Table w r -> (r -> w) -> (r -> Column PGBool) -> (r -> a) -> Transaction (Maybe b) Source #
Update items in a Table with a return value. Similar to .listToMaybe <$> updateReturning
Deletes
Utilities
Reexports
class Monad m => MonadIO (m :: Type -> Type) #
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
Instances
ask :: MonadReader r m => m r #
Retrieves the monad environment.
64-bit signed integer type