opaleye-trans-0.5.2: A monad transformer for Opaleye
Safe HaskellNone
LanguageHaskell2010

Opaleye.Trans

Synopsis

Documentation

newtype OpaleyeT m a Source #

The Opaleye monad transformer

Constructors

OpaleyeT 

Instances

Instances details
MonadTrans OpaleyeT Source # 
Instance details

Defined in Opaleye.Trans

Methods

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

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

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 # 
Instance details

Defined in Opaleye.Trans

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 #

Functor m => Functor (OpaleyeT m) Source # 
Instance details

Defined in Opaleye.Trans

Methods

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

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

Applicative m => Applicative (OpaleyeT m) Source # 
Instance details

Defined in Opaleye.Trans

Methods

pure :: a -> OpaleyeT m a #

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

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

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

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

MonadIO m => MonadIO (OpaleyeT m) Source # 
Instance details

Defined in Opaleye.Trans

Methods

liftIO :: IO a -> OpaleyeT m a #

MonadThrow m => MonadThrow (OpaleyeT m) Source # 
Instance details

Defined in Opaleye.Trans

Methods

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

MonadCatch m => MonadCatch (OpaleyeT m) Source # 
Instance details

Defined in Opaleye.Trans

Methods

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

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

Given a Connection, run an OpaleyeT

Transactions

data Transaction a Source #

Instances

Instances details
Monad Transaction Source # 
Instance details

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 # 
Instance details

Defined in Opaleye.Trans

Methods

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

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

Applicative Transaction Source # 
Instance details

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 # 
Instance details

Defined in Opaleye.Trans

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 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

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

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

Utilities

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

Reexports

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

Lift a computation from the IO monad.

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

liftIO

Instances

Instances details
MonadIO IO

Since: base-4.9.0.0

Instance details

Defined in Control.Monad.IO.Class

Methods

liftIO :: IO a -> IO a #

MonadIO Q 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

liftIO :: IO a -> Q a #

MonadIO m => MonadIO (MaybeT m) 
Instance details

Defined in Control.Monad.Trans.Maybe

Methods

liftIO :: IO a -> MaybeT m a #

MonadIO m => MonadIO (ListT m) 
Instance details

Defined in Control.Monad.Trans.List

Methods

liftIO :: IO a -> ListT m a #

MonadIO m => MonadIO (OpaleyeT m) Source # 
Instance details

Defined in Opaleye.Trans

Methods

liftIO :: IO a -> OpaleyeT m a #

MonadIO m => MonadIO (IdentityT m) 
Instance details

Defined in Control.Monad.Trans.Identity

Methods

liftIO :: IO a -> IdentityT m a #

MonadIO m => MonadIO (ExceptT e m) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

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

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

Defined in Control.Monad.Trans.Error

Methods

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

MonadIO m => MonadIO (ReaderT r m) 
Instance details

Defined in Control.Monad.Trans.Reader

Methods

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

MonadIO m => MonadIO (StateT s m) 
Instance details

Defined in Control.Monad.Trans.State.Lazy

Methods

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

MonadIO m => MonadIO (StateT s m) 
Instance details

Defined in Control.Monad.Trans.State.Strict

Methods

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

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

Defined in Control.Monad.Trans.Writer.Lazy

Methods

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

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

Defined in Control.Monad.Trans.Writer.Strict

Methods

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

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

Defined in Opaleye.Trans.Exception

Methods

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

MonadIO m => MonadIO (ContT r m) 
Instance details

Defined in Control.Monad.Trans.Cont

Methods

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

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

Defined in Control.Monad.Trans.RWS.Lazy

Methods

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

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

Defined in Control.Monad.Trans.RWS.Strict

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

Instances details
Bounded Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Enum Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Eq Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

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

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

Integral Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Num Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Ord Int64

Since: base-2.1

Instance details

Defined in GHC.Int

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

Since: base-2.1

Instance details

Defined in GHC.Int

Real Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

toRational :: Int64 -> Rational #

Show Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

showsPrec :: Int -> Int64 -> ShowS #

show :: Int64 -> String #

showList :: [Int64] -> ShowS #

Ix Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Bits Int64

Since: base-2.1

Instance details

Defined in GHC.Int

FiniteBits Int64

Since: base-4.6.0.0

Instance details

Defined in GHC.Int

Lift Int64 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Int64 -> Q Exp #

liftTyped :: Int64 -> Q (TExp Int64) #

DefaultFromField SqlInt8 Int64 
Instance details

Defined in Opaleye.Internal.RunQuery

Default ToFields Int64 (Column SqlInt8) 
Instance details

Defined in Opaleye.Internal.Constant

Default ToFields (PGRange Int64) (Column (SqlRange SqlInt8)) 
Instance details

Defined in Opaleye.Internal.Constant