Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Left, right, and full outer joins.
Synopsis
- optional :: Default Unpackspec a a => SelectArr i a -> SelectArr i (MaybeFields a)
- optionalRestrict :: Default Unpackspec a a => Select a -> SelectArr (a -> Field SqlBool) (MaybeFields a)
- leftJoin :: (Default Unpackspec fieldsL fieldsL, Default Unpackspec fieldsR fieldsR, Default NullMaker fieldsR nullableFieldsR) => Select fieldsL -> Select fieldsR -> ((fieldsL, fieldsR) -> Field SqlBool) -> Select (fieldsL, nullableFieldsR)
- leftJoinA :: (Default Unpackspec fieldsR fieldsR, Default NullMaker fieldsR nullableFieldsR) => Select fieldsR -> SelectArr (fieldsR -> Field SqlBool) nullableFieldsR
- rightJoin :: (Default Unpackspec fieldsL fieldsL, Default Unpackspec fieldsR fieldsR, Default NullMaker fieldsL nullableFieldsL) => Select fieldsL -> Select fieldsR -> ((fieldsL, fieldsR) -> Field SqlBool) -> Select (nullableFieldsL, fieldsR)
- fullJoin :: (Default Unpackspec fieldsL fieldsL, Default Unpackspec fieldsR fieldsR, Default NullMaker fieldsL nullableFieldsL, Default NullMaker fieldsR nullableFieldsR) => Select fieldsL -> Select fieldsR -> ((fieldsL, fieldsR) -> Field SqlBool) -> Select (nullableFieldsL, nullableFieldsR)
- leftJoinExplicit :: Unpackspec fieldsL fieldsL -> Unpackspec fieldsR fieldsR -> NullMaker fieldsR nullableFieldsR -> Select fieldsL -> Select fieldsR -> ((fieldsL, fieldsR) -> Field SqlBool) -> Select (fieldsL, nullableFieldsR)
- leftJoinAExplict :: Unpackspec fieldsR fieldsR -> NullMaker fieldsR nullableFieldsR -> Select fieldsR -> SelectArr (fieldsR -> Field SqlBool) nullableFieldsR
- rightJoinExplicit :: Unpackspec fieldsL fieldsL -> Unpackspec fieldsR fieldsR -> NullMaker fieldsL nullableFieldsL -> Select fieldsL -> Select fieldsR -> ((fieldsL, fieldsR) -> Field SqlBool) -> Select (nullableFieldsL, fieldsR)
- fullJoinExplicit :: Unpackspec fieldsL fieldsL -> Unpackspec fieldsR fieldsR -> NullMaker fieldsL nullableFieldsL -> NullMaker fieldsR nullableFieldsR -> Select fieldsL -> Select fieldsR -> ((fieldsL, fieldsR) -> Field SqlBool) -> Select (nullableFieldsL, nullableFieldsR)
- optionalRestrictExplicit :: Unpackspec a a -> Select a -> SelectArr (a -> Field SqlBool) (MaybeFields a)
- optionalExplicit :: Unpackspec a a -> SelectArr i a -> SelectArr i (MaybeFields a)
The recommended way of performing joins in Opaleye
Opaleye supports inner joins, left/right joins and full outer joins. Instead of using them directly we recommend the following, which provide APIs that are more familiar to a Haskell programmer and more composable:
- Inner joins: use
where_
directly, along withdo
notation (or userestrict
directly, along with arrow notation) - Left/right joins: use
optional
We suspect the following do not have real world use cases. If you have one then we'd love to hear about it. Please open a new issue on the Opaleye project and tell us about it.
- Left/right joins which really must not use
LATERAL
: useoptionalRestrict
- Full outer joins: use
fullJoinF
:: Default Unpackspec a a | |
=> SelectArr i a | Input query |
-> SelectArr i (MaybeFields a) | The rows of the input query wrapped in "Just", unless the input query has no rows in which case a single row of "Nothing" |
Convenient access to lateral left/right join
functionality. Performs a LATERAL LEFT JOIN
under the hood and
has behaviour equivalent to the following Haskell function:
optional :: [a] -> [Maybe a] optional q = case q of [] -> [Nothing] xs -> map Just xs
That is, if q ::
returns no rows, SelectArr
i a
returns exactly one "Nothing"
row. Otherwise, optional
q
:: SelectArr
i (MaybeFields
a)
returns exactly the rows of optional
qq
wrapped in "Just". For example,
> let l1 = ["one", "two", "three"] :: [Field SqlText] >runSelectI
conn (optional
(values
l1)) [Just "one", Just "two", Just "three"] > let l2 = [] :: [Field SqlText] >runSelectI
conn (optional
(values
l2)) [Nothing]
optionalRestrict
is a special case of optional
and could be
written in terms of optional
as follows (except that
optionalRestrict
doesn't use LATERAL
under the hood and
optional
does).
optionalRestrict q = optional $ proc cond -> do a <- q -< () restrict -< cond a returnA -< a
:: Default Unpackspec a a | |
=> Select a | Input query |
-> SelectArr (a -> Field SqlBool) (MaybeFields a) | If any rows of the input query satisfy the condition then return them (wrapped in "Just"). If none of them satisfy the condition then return a single row of "Nothing" |
Convenient access to left/right join functionality. Performs a
LEFT JOIN
under the hood and has behaviour equivalent to the
following Haskell function:
optionalRestrict :: [a] -> (a -> Bool) -> [Maybe a] optionalRestrict xs p = case filter p xs of [] -> [Nothing] xs' -> map Just xs'
For example,
> let l = [1, 10, 100, 1000] :: [Field SqlInt4] >runSelectI
conn (proc () -> optionalRestrict (values
l) -< (.> 100000)) [Nothing] >runSelectI
conn (proc () -> optionalRestrict (values
l) -< (.> 15)) [Just 100,Just 1000]
See the documentation of leftJoin
for how to use
optionalRestrict
to replace leftJoin
(and by symmetry,
rightJoin
).
Direct access to joins (not recommended)
You probably want use the alternatives listed at the top of this
module instead of these.
The use of the
typeclass means that the compiler will
have trouble inferring types. It is strongly recommended that you
provide full type signatures when using the join functions.
Example specialization:Default
NullMaker
leftJoin :: Select (Field a, Field b)
-> Select (Field c, FieldNullable d)
-> (((Field a, Field b), (Field c, FieldNullable d)) -> Field SqlBool
)
-> Select ((Field a, Field b), (FieldNullable c, FieldNullable d))
:: (Default Unpackspec fieldsL fieldsL, Default Unpackspec fieldsR fieldsR, Default NullMaker fieldsR nullableFieldsR) | |
=> Select fieldsL | Left query |
-> Select fieldsR | Right query |
-> ((fieldsL, fieldsR) -> Field SqlBool) | Condition on which to join |
-> Select (fieldsL, nullableFieldsR) | Left join |
We suggest you use optionalRestrict
instead. Instead of writing
"
" you can writeleftJoin
qL qR cond
proc () -> do fieldsL <- qL -< () maybeFieldsR <-optionalRestrict
qR -<curry
cond fieldsLreturnA
-< (fieldsL, maybeFieldsR)
Typically everything except the optionalRestrict
line can be
inlined in surrounding arrow notation. In such cases, readability
and maintainability increase dramatically.
:: (Default Unpackspec fieldsR fieldsR, Default NullMaker fieldsR nullableFieldsR) | |
=> Select fieldsR | Right query |
-> SelectArr (fieldsR -> Field SqlBool) nullableFieldsR | Condition on which to join goes in, left join result comes out |
We suggest you don't use this. optionalRestrict
is probably
better for your use case. leftJoinA
is the same as
optionalRestrict
except without the return type wrapped in
MaybeFields
.
:: (Default Unpackspec fieldsL fieldsL, Default Unpackspec fieldsR fieldsR, Default NullMaker fieldsL nullableFieldsL) | |
=> Select fieldsL | Left query |
-> Select fieldsR | Right query |
-> ((fieldsL, fieldsR) -> Field SqlBool) | Condition on which to join |
-> Select (nullableFieldsL, fieldsR) | Right join |
We suggest you use optionalRestrict
instead. See leftJoin
for more details.
:: (Default Unpackspec fieldsL fieldsL, Default Unpackspec fieldsR fieldsR, Default NullMaker fieldsL nullableFieldsL, Default NullMaker fieldsR nullableFieldsR) | |
=> Select fieldsL | Left query |
-> Select fieldsR | Right query |
-> ((fieldsL, fieldsR) -> Field SqlBool) | Condition on which to join |
-> Select (nullableFieldsL, nullableFieldsR) | Full outer join |
Explicit versions
leftJoinExplicit :: Unpackspec fieldsL fieldsL -> Unpackspec fieldsR fieldsR -> NullMaker fieldsR nullableFieldsR -> Select fieldsL -> Select fieldsR -> ((fieldsL, fieldsR) -> Field SqlBool) -> Select (fieldsL, nullableFieldsR) Source #
leftJoinAExplict :: Unpackspec fieldsR fieldsR -> NullMaker fieldsR nullableFieldsR -> Select fieldsR -> SelectArr (fieldsR -> Field SqlBool) nullableFieldsR Source #
rightJoinExplicit :: Unpackspec fieldsL fieldsL -> Unpackspec fieldsR fieldsR -> NullMaker fieldsL nullableFieldsL -> Select fieldsL -> Select fieldsR -> ((fieldsL, fieldsR) -> Field SqlBool) -> Select (nullableFieldsL, fieldsR) Source #
fullJoinExplicit :: Unpackspec fieldsL fieldsL -> Unpackspec fieldsR fieldsR -> NullMaker fieldsL nullableFieldsL -> NullMaker fieldsR nullableFieldsR -> Select fieldsL -> Select fieldsR -> ((fieldsL, fieldsR) -> Field SqlBool) -> Select (nullableFieldsL, nullableFieldsR) Source #
optionalRestrictExplicit :: Unpackspec a a -> Select a -> SelectArr (a -> Field SqlBool) (MaybeFields a) Source #
optionalExplicit :: Unpackspec a a -> SelectArr i a -> SelectArr i (MaybeFields a) Source #