opaleye-trans-0.3.5: A monad transformer for Opaleye

Safe HaskellNone
LanguageHaskell2010

Opaleye.Trans

Contents

Synopsis

Documentation

newtype OpaleyeT m a Source #

The Opaleye monad transformer

Constructors

OpaleyeT 

Instances

MonadTrans OpaleyeT Source # 

Methods

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

Monad m => MonadReader Connection (OpaleyeT m) Source # 

Methods

ask :: OpaleyeT m Connection #

local :: (Connection -> Connection) -> OpaleyeT m a -> OpaleyeT m a #

reader :: (Connection -> a) -> OpaleyeT m a #

MonadBase b m => MonadBase b (OpaleyeT m) Source # 

Methods

liftBase :: b α -> OpaleyeT m α #

Monad m => Monad (OpaleyeT m) Source # 

Methods

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

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

return :: a -> OpaleyeT m a #

fail :: String -> OpaleyeT m a #

Functor m => Functor (OpaleyeT m) Source # 

Methods

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

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

Applicative m => Applicative (OpaleyeT m) Source # 

Methods

pure :: a -> OpaleyeT m a #

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

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

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

MonadIO m => MonadIO (OpaleyeT m) Source # 

Methods

liftIO :: IO a -> OpaleyeT m a #

runOpaleyeT :: Connection -> OpaleyeT m a -> m a Source #

Given a Connection, run an OpaleyeT

Transactions

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 #

Execute a Query. See runQuery.

queryFirst :: Default QueryRunner a b => Query a -> Transaction (Maybe b) Source #

Retrieve the first result from a Query. Similar to listToMaybe $ runQuery.

Inserts

insert :: Table w r -> w -> Transaction Int64 Source #

Insert into a Table. See runInsert.

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

update :: Table w r -> (r -> w) -> (r -> Column PGBool) -> Transaction Int64 Source #

Update items in a Table where the predicate is true. See runUpdate.

updateReturning :: Default QueryRunner returned haskells => Table w r -> (r -> w) -> (r -> Column PGBool) -> (r -> returned) -> Transaction [haskells] Source #

Update items in a Table with a return value. See runUpdateReturning.

updateReturningFirst :: Default QueryRunner returned haskells => Table w r -> (r -> w) -> (r -> Column PGBool) -> (r -> returned) -> Transaction (Maybe haskells) Source #

Update items in a Table with a return value. Similar to listToMaybe <$> updateReturning.

Deletes

delete :: Table a columnsR -> (columnsR -> Column PGBool) -> Transaction Int64 Source #

Utilities

withConn :: MonadIO m => (Connection -> IO a) -> OpaleyeT m a Source #

Reexports

liftBase :: MonadBase b m => forall α. b α -> m α #

Lift a computation from the base monad

class (Applicative b, Applicative m, Monad b, Monad m) => MonadBase b m | m -> b where #

Minimal complete definition

liftBase

Methods

liftBase :: b α -> m α #

Lift a computation from the base monad

Instances

MonadBase [] [] 

Methods

liftBase :: [α] -> [α] #

MonadBase Maybe Maybe 

Methods

liftBase :: Maybe α -> Maybe α #

MonadBase IO IO 

Methods

liftBase :: IO α -> IO α #

MonadBase Identity Identity 

Methods

liftBase :: Identity α -> Identity α #

MonadBase STM STM 

Methods

liftBase :: STM α -> STM α #

MonadBase b m => MonadBase b (MaybeT m) 

Methods

liftBase :: b α -> MaybeT m α #

MonadBase b m => MonadBase b (ListT m) 

Methods

liftBase :: b α -> ListT m α #

MonadBase b m => MonadBase b (OpaleyeT m) # 

Methods

liftBase :: b α -> OpaleyeT m α #

(Monoid w, MonadBase b m) => MonadBase b (WriterT w m) 

Methods

liftBase :: b α -> WriterT w m α #

(Monoid w, MonadBase b m) => MonadBase b (WriterT w m) 

Methods

liftBase :: b α -> WriterT w m α #

MonadBase b m => MonadBase b (StateT s m) 

Methods

liftBase :: b α -> StateT s m α #

MonadBase b m => MonadBase b (StateT s m) 

Methods

liftBase :: b α -> StateT s m α #

MonadBase b m => MonadBase b (IdentityT * m) 

Methods

liftBase :: b α -> IdentityT * m α #

MonadBase b m => MonadBase b (ExceptT e m) 

Methods

liftBase :: b α -> ExceptT e m α #

(Error e, MonadBase b m) => MonadBase b (ErrorT e m) 

Methods

liftBase :: b α -> ErrorT e m α #

MonadBase b m => MonadBase b (ReaderT * r m) 

Methods

liftBase :: b α -> ReaderT * r m α #

MonadBase b m => MonadBase b (ContT * r m) 

Methods

liftBase :: b α -> ContT * r m α #

(Monoid w, MonadBase b m) => MonadBase b (RWST r w s m) 

Methods

liftBase :: b α -> RWST r w s m α #

(Monoid w, MonadBase b m) => MonadBase b (RWST r w s m) 

Methods

liftBase :: b α -> RWST r w s m α #

MonadBase ((->) r) ((->) r) 

Methods

liftBase :: (r -> α) -> r -> α #

MonadBase (Either e) (Either e) 

Methods

liftBase :: Either e α -> Either e α #

MonadBase (ST s) (ST s) 

Methods

liftBase :: ST s α -> ST s α #

MonadBase (ST s) (ST s) 

Methods

liftBase :: ST s α -> ST s α #

liftIO :: MonadIO m => forall a. IO a -> m a #

Lift a computation from the IO monad.

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 (OpaleyeT m) # 

Methods

liftIO :: IO a -> OpaleyeT m a #

MonadIO m => MonadIO (IdentityT * m) 

Methods

liftIO :: IO a -> IdentityT * 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 (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 #

ask :: MonadReader r m => m r #

Retrieves the monad environment.

data Int64 :: * #

64-bit signed integer type

Instances

Bounded Int64 
Enum Int64 
Eq Int64 

Methods

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

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

Integral Int64 
Num Int64 
Ord Int64 

Methods

compare :: Int64 -> Int64 -> Ordering #

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

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

(>) :: Int64 -> Int64 -> Bool #

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

max :: Int64 -> Int64 -> Int64 #

min :: Int64 -> Int64 -> Int64 #

Read Int64 
Real Int64 

Methods

toRational :: Int64 -> Rational #

Show Int64 

Methods

showsPrec :: Int -> Int64 -> ShowS #

show :: Int64 -> String #

showList :: [Int64] -> ShowS #

Ix Int64 
Bits Int64 
FiniteBits Int64 
Unbox Int64 
QueryRunnerColumnDefault PGInt8 Int64 
Vector Vector Int64 
MVector MVector Int64 
data Vector Int64 
data MVector s Int64