opaleye-0.6.7005.0: An SQL-generating DSL targeting PostgreSQL

Safe HaskellNone
LanguageHaskell2010

Opaleye.Adaptors

Contents

Synopsis

Binaryspec

data Binaryspec columns columns' Source #

Instances
Profunctor Binaryspec Source # 
Instance details

Defined in Opaleye.Internal.Binary

Methods

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

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

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

(#.) :: Coercible c b => q b c -> Binaryspec a b -> Binaryspec a c #

(.#) :: Coercible b a => Binaryspec b c -> q a b -> Binaryspec a c #

ProductProfunctor Binaryspec Source # 
Instance details

Defined in Opaleye.Internal.Binary

Methods

purePP :: b -> Binaryspec a b #

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

empty :: Binaryspec () () #

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

Default Binaryspec (Column a) (Column a) Source # 
Instance details

Defined in Opaleye.Internal.Binary

Methods

def :: Binaryspec (Column a) (Column a) #

Default (WithNulls Binaryspec) a b => Default Binaryspec (MaybeFields a) (MaybeFields b) Source # 
Instance details

Defined in Opaleye.Internal.MaybeFields

Functor (Binaryspec a) Source # 
Instance details

Defined in Opaleye.Internal.Binary

Methods

fmap :: (a0 -> b) -> Binaryspec a a0 -> Binaryspec a b #

(<$) :: a0 -> Binaryspec a b -> Binaryspec a a0 #

Applicative (Binaryspec a) Source # 
Instance details

Defined in Opaleye.Internal.Binary

Methods

pure :: a0 -> Binaryspec a a0 #

(<*>) :: Binaryspec a (a0 -> b) -> Binaryspec a a0 -> Binaryspec a b #

liftA2 :: (a0 -> b -> c) -> Binaryspec a a0 -> Binaryspec a b -> Binaryspec a c #

(*>) :: Binaryspec a a0 -> Binaryspec a b -> Binaryspec a b #

(<*) :: Binaryspec a a0 -> Binaryspec a b -> Binaryspec a a0 #

Distinctspec

data Distinctspec a b Source #

Instances
Profunctor Distinctspec Source # 
Instance details

Defined in Opaleye.Internal.Distinct

Methods

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

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

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

(#.) :: Coercible c b => q b c -> Distinctspec a b -> Distinctspec a c #

(.#) :: Coercible b a => Distinctspec b c -> q a b -> Distinctspec a c #

ProductProfunctor Distinctspec Source # 
Instance details

Defined in Opaleye.Internal.Distinct

Methods

purePP :: b -> Distinctspec a b #

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

empty :: Distinctspec () () #

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

SumProfunctor Distinctspec Source # 
Instance details

Defined in Opaleye.Internal.Distinct

Methods

(+++!) :: Distinctspec a b -> Distinctspec a' b' -> Distinctspec (Either a a') (Either b b') #

Default Distinctspec (Column a) (Column a) Source # 
Instance details

Defined in Opaleye.Internal.Distinct

Methods

def :: Distinctspec (Column a) (Column a) #

Default (WithNulls Distinctspec) a b => Default Distinctspec (MaybeFields a) (MaybeFields b) Source # 
Instance details

Defined in Opaleye.Internal.Distinct

Functor (Distinctspec a) Source # 
Instance details

Defined in Opaleye.Internal.Distinct

Methods

fmap :: (a0 -> b) -> Distinctspec a a0 -> Distinctspec a b #

(<$) :: a0 -> Distinctspec a b -> Distinctspec a a0 #

Applicative (Distinctspec a) Source # 
Instance details

Defined in Opaleye.Internal.Distinct

Methods

pure :: a0 -> Distinctspec a a0 #

(<*>) :: Distinctspec a (a0 -> b) -> Distinctspec a a0 -> Distinctspec a b #

liftA2 :: (a0 -> b -> c) -> Distinctspec a a0 -> Distinctspec a b -> Distinctspec a c #

(*>) :: Distinctspec a a0 -> Distinctspec a b -> Distinctspec a b #

(<*) :: Distinctspec a a0 -> Distinctspec a b -> Distinctspec a a0 #

EqPP

data EqPP a b Source #

Instances
Profunctor EqPP Source # 
Instance details

Defined in Opaleye.Internal.Operators

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 => q b c -> EqPP a b -> EqPP a c #

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

ProductProfunctor EqPP Source # 
Instance details

Defined in Opaleye.Internal.Operators

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') #

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

Defined in Opaleye.Internal.Operators

Methods

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

Default EqPP a b => Default EqPP (MaybeFields a) (MaybeFields b) Source # 
Instance details

Defined in Opaleye.Internal.MaybeFields

Methods

def :: EqPP (MaybeFields a) (MaybeFields b) #

eqPPField :: EqPP (Column a) ignored Source #

IfPP

data IfPP a b Source #

Instances
Profunctor IfPP Source # 
Instance details

Defined in Opaleye.Internal.Operators

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 => q b c -> IfPP a b -> IfPP a c #

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

ProductProfunctor IfPP Source # 
Instance details

Defined in Opaleye.Internal.Operators

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') #

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

Defined in Opaleye.Internal.Operators

Methods

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

Default IfPP a b => Default IfPP (MaybeFields a) (MaybeFields b) Source # 
Instance details

Defined in Opaleye.Internal.MaybeFields

Methods

def :: IfPP (MaybeFields a) (MaybeFields b) #

FromFields

fromFieldsMaybeFields :: FromFields fields haskells -> FromFields (MaybeFields fields) (Maybe haskells) Source #

Nullspec

data Nullspec fields fields' Source #

Instances
Profunctor Nullspec Source # 
Instance details

Defined in Opaleye.Internal.Values

Methods

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

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

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

(#.) :: Coercible c b => q b c -> Nullspec a b -> Nullspec a c #

(.#) :: Coercible b a => Nullspec b c -> q a b -> Nullspec a c #

ProductProfunctor Nullspec Source # 
Instance details

Defined in Opaleye.Internal.Values

Methods

purePP :: b -> Nullspec a b #

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

empty :: Nullspec () () #

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

IsSqlType b => Default Nullspec a (Column b) Source # 
Instance details

Defined in Opaleye.Internal.Values

Methods

def :: Nullspec a (Column b) #

Functor (Nullspec a) Source # 
Instance details

Defined in Opaleye.Internal.Values

Methods

fmap :: (a0 -> b) -> Nullspec a a0 -> Nullspec a b #

(<$) :: a0 -> Nullspec a b -> Nullspec a a0 #

Applicative (Nullspec a) Source # 
Instance details

Defined in Opaleye.Internal.Values

Methods

pure :: a0 -> Nullspec a a0 #

(<*>) :: Nullspec a (a0 -> b) -> Nullspec a a0 -> Nullspec a b #

liftA2 :: (a0 -> b -> c) -> Nullspec a a0 -> Nullspec a b -> Nullspec a c #

(*>) :: Nullspec a a0 -> Nullspec a b -> Nullspec a b #

(<*) :: Nullspec a a0 -> Nullspec a b -> Nullspec a a0 #

ToFields

Unpackspec

data Unpackspec columns columns' Source #

Instances
Profunctor Unpackspec Source # 
Instance details

Defined in Opaleye.Internal.Unpackspec

Methods

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

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

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

(#.) :: Coercible c b => q b c -> Unpackspec a b -> Unpackspec a c #

(.#) :: Coercible b a => Unpackspec b c -> q a b -> Unpackspec a c #

ProductProfunctor Unpackspec Source # 
Instance details

Defined in Opaleye.Internal.Unpackspec

Methods

purePP :: b -> Unpackspec a b #

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

empty :: Unpackspec () () #

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

SumProfunctor Unpackspec Source # 
Instance details

Defined in Opaleye.Internal.Unpackspec

Methods

(+++!) :: Unpackspec a b -> Unpackspec a' b' -> Unpackspec (Either a a') (Either b b') #

Default Unpackspec (Column a) (Column a) Source # 
Instance details

Defined in Opaleye.Internal.Unpackspec

Methods

def :: Unpackspec (Column a) (Column a) #

Default Unpackspec a b => Default Unpackspec (MaybeFields a) (MaybeFields b) Source # 
Instance details

Defined in Opaleye.Internal.MaybeFields

Functor (Unpackspec a) Source # 
Instance details

Defined in Opaleye.Internal.Unpackspec

Methods

fmap :: (a0 -> b) -> Unpackspec a a0 -> Unpackspec a b #

(<$) :: a0 -> Unpackspec a b -> Unpackspec a a0 #

Applicative (Unpackspec a) Source # 
Instance details

Defined in Opaleye.Internal.Unpackspec

Methods

pure :: a0 -> Unpackspec a a0 #

(<*>) :: Unpackspec a (a0 -> b) -> Unpackspec a a0 -> Unpackspec a b #

liftA2 :: (a0 -> b -> c) -> Unpackspec a a0 -> Unpackspec a b -> Unpackspec a c #

(*>) :: Unpackspec a a0 -> Unpackspec a b -> Unpackspec a b #

(<*) :: Unpackspec a a0 -> Unpackspec a b -> Unpackspec a a0 #

unpackspecField :: Unpackspec (Column a) (Column a) Source #

Target the single PrimExpr inside a Column

Updater

data Updater a b Source #

Instances
Profunctor Updater Source # 
Instance details

Defined in Opaleye.Internal.Manipulation

Methods

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

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

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

(#.) :: Coercible c b => q b c -> Updater a b -> Updater a c #

(.#) :: Coercible b a => Updater b c -> q a b -> Updater a c #

ProductProfunctor Updater Source # 
Instance details

Defined in Opaleye.Internal.Manipulation

Methods

purePP :: b -> Updater a b #

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

empty :: Updater () () #

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

Default Updater (Column a) (Maybe (Column a)) Source # 
Instance details

Defined in Opaleye.Internal.Manipulation

Methods

def :: Updater (Column a) (Maybe (Column a)) #

Default Updater (Column a) (Column a) Source # 
Instance details

Defined in Opaleye.Internal.Manipulation

Methods

def :: Updater (Column a) (Column a) #

Functor (Updater a) Source # 
Instance details

Defined in Opaleye.Internal.Manipulation

Methods

fmap :: (a0 -> b) -> Updater a a0 -> Updater a b #

(<$) :: a0 -> Updater a b -> Updater a a0 #

Applicative (Updater a) Source # 
Instance details

Defined in Opaleye.Internal.Manipulation

Methods

pure :: a0 -> Updater a a0 #

(<*>) :: Updater a (a0 -> b) -> Updater a a0 -> Updater a b #

liftA2 :: (a0 -> b -> c) -> Updater a a0 -> Updater a b -> Updater a c #

(*>) :: Updater a a0 -> Updater a b -> Updater a b #

(<*) :: Updater a a0 -> Updater a b -> Updater a a0 #

Valuesspec

data ValuesspecSafe columns columns' Source #

Instances
Profunctor ValuesspecSafe Source # 
Instance details

Defined in Opaleye.Internal.Values

Methods

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

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

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

(#.) :: Coercible c b => q b c -> ValuesspecSafe a b -> ValuesspecSafe a c #

(.#) :: Coercible b a => ValuesspecSafe b c -> q a b -> ValuesspecSafe a c #

ProductProfunctor ValuesspecSafe Source # 
Instance details

Defined in Opaleye.Internal.Values

Methods

purePP :: b -> ValuesspecSafe a b #

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

empty :: ValuesspecSafe () () #

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

IsSqlType a => Default ValuesspecSafe (Column a) (Column a) Source # 
Instance details

Defined in Opaleye.Internal.Values

Methods

def :: ValuesspecSafe (Column a) (Column a) #

Default ValuesspecSafe a b => Default ValuesspecSafe (MaybeFields a) (MaybeFields b) Source # 
Instance details

Defined in Opaleye.Internal.MaybeFields

Functor (ValuesspecSafe a) Source # 
Instance details

Defined in Opaleye.Internal.Values

Methods

fmap :: (a0 -> b) -> ValuesspecSafe a a0 -> ValuesspecSafe a b #

(<$) :: a0 -> ValuesspecSafe a b -> ValuesspecSafe a a0 #

Applicative (ValuesspecSafe a) Source # 
Instance details

Defined in Opaleye.Internal.Values

Methods

pure :: a0 -> ValuesspecSafe a a0 #

(<*>) :: ValuesspecSafe a (a0 -> b) -> ValuesspecSafe a a0 -> ValuesspecSafe a b #

liftA2 :: (a0 -> b -> c) -> ValuesspecSafe a a0 -> ValuesspecSafe a b -> ValuesspecSafe a c #

(*>) :: ValuesspecSafe a a0 -> ValuesspecSafe a b -> ValuesspecSafe a b #

(<*) :: ValuesspecSafe a a0 -> ValuesspecSafe a b -> ValuesspecSafe a a0 #

WithNulls

data WithNulls p a b Source #

Instances
Profunctor p => Profunctor (WithNulls p) Source # 
Instance details

Defined in Opaleye.Internal.MaybeFields

Methods

dimap :: (a -> b) -> (c -> d) -> WithNulls p b c -> WithNulls p a d #

lmap :: (a -> b) -> WithNulls p b c -> WithNulls p a c #

rmap :: (b -> c) -> WithNulls p a b -> WithNulls p a c #

(#.) :: Coercible c b => q b c -> WithNulls p a b -> WithNulls p a c #

(.#) :: Coercible b a => WithNulls p b c -> q a b -> WithNulls p a c #

ProductProfunctor p => ProductProfunctor (WithNulls p) Source # 
Instance details

Defined in Opaleye.Internal.MaybeFields

Methods

purePP :: b -> WithNulls p a b #

(****) :: WithNulls p a (b -> c) -> WithNulls p a b -> WithNulls p a c #

empty :: WithNulls p () () #

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

SumProfunctor p => SumProfunctor (WithNulls p) Source # 
Instance details

Defined in Opaleye.Internal.MaybeFields

Methods

(+++!) :: WithNulls p a b -> WithNulls p a' b' -> WithNulls p (Either a a') (Either b b') #

(Profunctor p, IsSqlType a, Default p (Column a) (Column a)) => Default (WithNulls p) (Column a) (Column a) Source # 
Instance details

Defined in Opaleye.Internal.MaybeFields

Methods

def :: WithNulls p (Column a) (Column a) #

Profunctor p => Functor (WithNulls p a) Source # 
Instance details

Defined in Opaleye.Internal.MaybeFields

Methods

fmap :: (a0 -> b) -> WithNulls p a a0 -> WithNulls p a b #

(<$) :: a0 -> WithNulls p a b -> WithNulls p a a0 #

ProductProfunctor p => Applicative (WithNulls p a) Source # 
Instance details

Defined in Opaleye.Internal.MaybeFields

Methods

pure :: a0 -> WithNulls p a a0 #

(<*>) :: WithNulls p a (a0 -> b) -> WithNulls p a a0 -> WithNulls p a b #

liftA2 :: (a0 -> b -> c) -> WithNulls p a a0 -> WithNulls p a b -> WithNulls p a c #

(*>) :: WithNulls p a a0 -> WithNulls p a b -> WithNulls p a b #

(<*) :: WithNulls p a a0 -> WithNulls p a b -> WithNulls p a a0 #