opaleye-trans-0.4.2: A monad transformer for Opaleye

Safe HaskellNone
LanguageHaskell2010

Opaleye.Trans.Exception

Contents

Synopsis

Documentation

newtype OpaleyeT e m a Source #

Constructors

OpaleyeT 

Fields

Instances

Monad m => MonadError e (OpaleyeT e m) Source # 

Methods

throwError :: e -> OpaleyeT e m a #

catchError :: OpaleyeT e m a -> (e -> OpaleyeT e m a) -> OpaleyeT e m a #

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

Methods

ask :: OpaleyeT e m Connection #

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

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

MonadTrans (OpaleyeT e) Source # 

Methods

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

Monad m => Monad (OpaleyeT e m) Source # 

Methods

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

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

return :: a -> OpaleyeT e m a #

fail :: String -> OpaleyeT e m a #

Functor m => Functor (OpaleyeT e m) Source # 

Methods

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

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

Monad m => Applicative (OpaleyeT e m) Source # 

Methods

pure :: a -> OpaleyeT e m a #

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

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

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

MonadIO m => MonadIO (OpaleyeT e m) Source # 

Methods

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

MonadThrow m => MonadThrow (OpaleyeT e m) Source # 

Methods

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

MonadCatch m => MonadCatch (OpaleyeT e m) Source # 

Methods

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

runOpaleyeT :: Connection -> OpaleyeT e m a -> m (Either e a) Source #

Given a Connection, run an OpaleyeT

Transactions

data Transaction e a Source #

Just like Transaction only with exception handling

Instances

MonadError e (Transaction e) Source # 

Methods

throwError :: e -> Transaction e a #

catchError :: Transaction e a -> (e -> Transaction e a) -> Transaction e a #

MonadReader Connection (Transaction e) Source # 
Monad (Transaction e) Source # 

Methods

(>>=) :: Transaction e a -> (a -> Transaction e b) -> Transaction e b #

(>>) :: Transaction e a -> Transaction e b -> Transaction e b #

return :: a -> Transaction e a #

fail :: String -> Transaction e a #

Functor (Transaction e) Source # 

Methods

fmap :: (a -> b) -> Transaction e a -> Transaction e b #

(<$) :: a -> Transaction e b -> Transaction e a #

Applicative (Transaction e) Source # 

Methods

pure :: a -> Transaction e a #

(<*>) :: Transaction e (a -> b) -> Transaction e a -> Transaction e b #

(*>) :: Transaction e a -> Transaction e b -> Transaction e b #

(<*) :: Transaction e a -> Transaction e b -> Transaction e a #

transaction :: MonadIO m => Transaction e a -> OpaleyeT e m a Source #

Run a postgresql transaction in the OpaleyeT monad

run :: MonadIO m => Transaction e a -> OpaleyeT e m a Source #

Execute a query without a literal transaction

Queries

query :: Default QueryRunner a b => Query a -> Transaction e [b] Source #

Execute a Query. See runQuery.

queryFirst :: Default QueryRunner a b => e -> Query a -> Transaction e b Source #

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

Inserts

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

Insert into a Table. See runInsert.

insertMany :: Table w r -> [w] -> Transaction e Int64 Source #

Insert many records into a Table. See runInsertMany.

insertReturning :: Default QueryRunner a b => Table w r -> (r -> a) -> w -> Transaction e [b] Source #

Insert a record into a Table with a return value. See runInsertReturning.

insertReturningFirst :: Default QueryRunner a b => e -> Table w r -> (r -> a) -> w -> Transaction e 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 e [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 e Int64 Source #

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

updateReturning :: Default QueryRunner a b => Table w r -> (r -> w) -> (r -> Column PGBool) -> (r -> a) -> Transaction e [b] Source #

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

updateReturningFirst :: Default QueryRunner a b => e -> Table w r -> (r -> w) -> (r -> Column PGBool) -> (r -> a) -> Transaction e b Source #

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

Deletes

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

Delete items in a Table that satisfy some boolean predicate. See runDelete.

Exceptions

withExceptOpaleye :: Functor m => (e -> e') -> OpaleyeT e m a -> OpaleyeT e' m a Source #

withExceptTrans :: (e -> e') -> Transaction e a -> Transaction e' a Source #

Utilities

withError :: Monad m => OpaleyeT m (Either e a) -> OpaleyeT e m a Source #

withoutError :: Monad m => OpaleyeT e m a -> OpaleyeT m (Either e a) Source #

liftError :: Monad m => (Transaction (Either e a) -> OpaleyeT m (Either r b)) -> Transaction e a -> OpaleyeT r m b Source #

Reexports

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

Methods

liftIO :: IO a -> OpaleyeT e 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 
Lift Int64 

Methods

lift :: Int64 -> Q Exp #

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

throwError :: MonadError e m => forall a. e -> m a #

Is used within a monadic computation to begin exception processing.

catchError :: MonadError e m => forall a. m a -> (e -> m a) -> m a #

A handler function to handle previous errors and return to normal execution. A common idiom is:

do { action1; action2; action3 } `catchError` handler

where the action functions can call throwError. Note that handler and the do-block must have the same return type.