Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- newtype NullMaker a b = NullMaker (a -> b)
- toNullable :: NullMaker a b -> a -> b
- joinExplicit :: Unpackspec columnsA columnsA -> Unpackspec columnsB columnsB -> (columnsA -> returnedColumnsA) -> (columnsB -> returnedColumnsB) -> JoinType -> Query columnsA -> Query columnsB -> ((columnsA, columnsB) -> Column PGBool) -> Query (returnedColumnsA, returnedColumnsB)
- leftJoinAExplicit :: Unpackspec a a -> NullMaker a nullableA -> Query a -> QueryArr (a -> Column PGBool) nullableA
- optionalRestrict :: Default Unpackspec a a => Select a -> SelectArr (a -> Field SqlBool) (MaybeFields a)
- optionalRestrictExplicit :: Unpackspec a a -> Select a -> SelectArr (a -> Field SqlBool) (MaybeFields a)
- leftJoinInTermsOfOptionalRestrict :: Default Unpackspec fieldsR fieldsR => Select fieldsL -> Select fieldsR -> ((fieldsL, fieldsR) -> Field SqlBool) -> Select (fieldsL, MaybeFields fieldsR)
- extractLeftJoinFields :: Int -> Tag -> PrimExpr -> PM [(Symbol, PrimExpr)] PrimExpr
- data Nulled
Documentation
newtype NullMaker a b Source #
NullMaker (a -> b) |
Instances
Profunctor NullMaker Source # | |
Defined in Opaleye.Internal.Join dimap :: (a -> b) -> (c -> d) -> NullMaker b c -> NullMaker a d # lmap :: (a -> b) -> NullMaker b c -> NullMaker a c # rmap :: (b -> c) -> NullMaker a b -> NullMaker a c # (#.) :: forall a b c q. Coercible c b => q b c -> NullMaker a b -> NullMaker a c # (.#) :: forall a b c q. Coercible b a => NullMaker b c -> q a b -> NullMaker a c # | |
ProductProfunctor NullMaker Source # | |
Default NullMaker (Column a) (Column (Nullable a)) Source # | |
Default NullMaker (Column (Nullable a)) (Column (Nullable a)) Source # | |
Functor (NullMaker a) Source # | |
Applicative (NullMaker a) Source # | |
Defined in Opaleye.Internal.Join |
toNullable :: NullMaker a b -> a -> b Source #
joinExplicit :: Unpackspec columnsA columnsA -> Unpackspec columnsB columnsB -> (columnsA -> returnedColumnsA) -> (columnsB -> returnedColumnsB) -> JoinType -> Query columnsA -> Query columnsB -> ((columnsA, columnsB) -> Column PGBool) -> Query (returnedColumnsA, returnedColumnsB) Source #
leftJoinAExplicit :: Unpackspec a a -> NullMaker a nullableA -> Query a -> QueryArr (a -> Column PGBool) nullableA Source #
optionalRestrict :: Default Unpackspec a a => Select a -> SelectArr (a -> Field SqlBool) (MaybeFields a) Source #
optionalRestrictExplicit :: Unpackspec a a -> Select a -> SelectArr (a -> Field SqlBool) (MaybeFields a) Source #
leftJoinInTermsOfOptionalRestrict :: Default Unpackspec fieldsR fieldsR => Select fieldsL -> Select fieldsR -> ((fieldsL, fieldsR) -> Field SqlBool) -> Select (fieldsL, MaybeFields fieldsR) Source #
An example to demonstrate how the functionality of LEFT JOIN
can be recovered using optionalRestrict
.
Deprecated: Will be removed in version 0.8
Instances
type IMap Nulled NullsT Source # | |
Defined in Opaleye.Internal.Join | |
type IMap Nulled OT Source # | |
Defined in Opaleye.Internal.Join | |
type Map Nulled (Column (Nullable a)) Source # | |
type Map Nulled (Column PGJsonb) Source # | |
type Map Nulled (Column PGJson) Source # | |
type Map Nulled (Column PGBytea) Source # | |
type Map Nulled (Column PGCitext) Source # | |
type Map Nulled (Column PGUuid) Source # | |
type Map Nulled (Column PGTimestamptz) Source # | |
Defined in Opaleye.Internal.Join | |
type Map Nulled (Column PGTimestamp) Source # | |
Defined in Opaleye.Internal.Join | |
type Map Nulled (Column PGTime) Source # | |
type Map Nulled (Column PGText) Source # | |
type Map Nulled (Column PGText) Source # | |
type Map Nulled (Column PGInt4) Source # | |
type Map Nulled (Column PGInt8) Source # | |
type Map Nulled (Column PGFloat8) Source # | |
type Map Nulled (Column PGDate) Source # | |
type Map Nulled (Column PGBool) Source # | |