opaleye-0.5.4.0: An SQL-generating DSL targeting PostgreSQL

Safe HaskellNone
LanguageHaskell2010

Opaleye.Internal.Operators

Synopsis

Documentation

(.==) :: forall columns. Default EqPP columns columns => columns -> columns -> Column PGBool infix 4 Source #

(.&&) :: Column PGBool -> Column PGBool -> Column PGBool infixr 3 Source #

Boolean and

data EqPP a b Source #

Constructors

EqPP (a -> a -> Column PGBool) 

Instances

ProductProfunctor EqPP Source # 

Methods

purePP :: b -> EqPP a b #

(****) :: EqPP a (b -> c) -> EqPP a b -> EqPP a c #

empty :: EqPP () () #

(***!) :: EqPP a b -> EqPP a' b' -> EqPP (a, a') (b, b') #

Profunctor EqPP Source # 

Methods

dimap :: (a -> b) -> (c -> d) -> EqPP b c -> EqPP a d #

lmap :: (a -> b) -> EqPP b c -> EqPP a c #

rmap :: (b -> c) -> EqPP a b -> EqPP a c #

(#.) :: Coercible * c b => (b -> c) -> EqPP a b -> EqPP a c #

(.#) :: Coercible * b a => EqPP b c -> (a -> b) -> EqPP a c #

Default EqPP (Column a) (Column a) Source # 

Methods

def :: EqPP (Column a) (Column a) #

eqExplicit :: EqPP columns a -> columns -> columns -> Column PGBool Source #

newtype IfPP a b Source #

Constructors

IfPP (Column PGBool -> a -> a -> b) 

Instances

ProductProfunctor IfPP Source # 

Methods

purePP :: b -> IfPP a b #

(****) :: IfPP a (b -> c) -> IfPP a b -> IfPP a c #

empty :: IfPP () () #

(***!) :: IfPP a b -> IfPP a' b' -> IfPP (a, a') (b, b') #

Profunctor IfPP Source # 

Methods

dimap :: (a -> b) -> (c -> d) -> IfPP b c -> IfPP a d #

lmap :: (a -> b) -> IfPP b c -> IfPP a c #

rmap :: (b -> c) -> IfPP a b -> IfPP a c #

(#.) :: Coercible * c b => (b -> c) -> IfPP a b -> IfPP a c #

(.#) :: Coercible * b a => IfPP b c -> (a -> b) -> IfPP a c #

Default IfPP (Column a) (Column a) Source # 

Methods

def :: IfPP (Column a) (Column a) #

ifExplict :: IfPP columns columns' -> Column PGBool -> columns -> columns -> columns' Source #

data RelExprMaker a b Source #

Constructors

RelExprMaker 

Instances

ProductProfunctor RelExprMaker Source # 

Methods

purePP :: b -> RelExprMaker a b #

(****) :: RelExprMaker a (b -> c) -> RelExprMaker a b -> RelExprMaker a c #

empty :: RelExprMaker () () #

(***!) :: RelExprMaker a b -> RelExprMaker a' b' -> RelExprMaker (a, a') (b, b') #

Profunctor RelExprMaker Source # 

Methods

dimap :: (a -> b) -> (c -> d) -> RelExprMaker b c -> RelExprMaker a d #

lmap :: (a -> b) -> RelExprMaker b c -> RelExprMaker a c #

rmap :: (b -> c) -> RelExprMaker a b -> RelExprMaker a c #

(#.) :: Coercible * c b => (b -> c) -> RelExprMaker a b -> RelExprMaker a c #

(.#) :: Coercible * b a => RelExprMaker b c -> (a -> b) -> RelExprMaker a c #

Default RelExprMaker String (Column a) Source # 

runRelExprMaker :: RelExprMaker strings columns -> Tag -> strings -> (columns, [(Symbol, PrimExpr)]) Source #

relationValuedExprExplicit :: RelExprMaker strings columns -> strings -> (a -> PrimExpr) -> QueryArr a columns Source #

relationValuedExpr :: Default RelExprMaker strings columns => strings -> (a -> PrimExpr) -> QueryArr a columns Source #