| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Opaleye.Join
Contents
Description
Left, right, and full outer joins.
Synopsis
- optionalRestrict :: Default Unpackspec a a => Select a -> SelectArr (a -> Field SqlBool) (MaybeFields a)
- optional :: Default Unpackspec a a => SelectArr i a -> SelectArr i (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)
- leftJoinInferrable :: (Default Unpackspec fieldsL fieldsL, Default Unpackspec fieldsR fieldsR, Default NullMaker fieldsR nullableFieldsR, Map Nulled fieldsR ~ nullableFieldsR) => Select fieldsL -> Select fieldsR -> ((fieldsL, fieldsR) -> Field SqlBool) -> Select (fieldsL, nullableFieldsR)
- rightJoinInferrable :: (Default Unpackspec fieldsL fieldsL, Default Unpackspec fieldsR fieldsR, Default NullMaker fieldsL nullableFieldsL, Map Nulled fieldsL ~ nullableFieldsL) => Select fieldsL -> Select fieldsR -> ((fieldsL, fieldsR) -> Field SqlBool) -> Select (nullableFieldsL, fieldsR)
- fullJoinInferrable :: (Default Unpackspec fieldsL fieldsL, Default Unpackspec fieldsR fieldsR, Default NullMaker fieldsL nullableFieldsL, Default NullMaker fieldsR nullableFieldsR, Map Nulled fieldsL ~ nullableFieldsL, Map Nulled fieldsR ~ nullableFieldsR) => Select fieldsL -> Select fieldsR -> ((fieldsL, fieldsR) -> Field SqlBool) -> Select (nullableFieldsL, nullableFieldsR)
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 restrictdirectly (along with<*>or arrow notation)
- Left/right joins: use optionalRestrict
- Lateral left/right joins: use optional
- Full outer joins: use fullJoinF(If you have a real-world use case for full outer joins then we'd love to hear about it. Please open a new issue on the Opaleye project and tell us about it.)
Arguments
| :: 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] >runSelectconn (proc () -> optionalRestrict (valuesSafel) -< (.> 100000)) :: IO [Maybe Int] [Nothing] >runSelectconn (proc () -> optionalRestrict (valuesSafel) -< (.> 15)) :: IO [Maybe Int] [Just 100,Just 1000]
See the documentation of leftJoin for how to use
 optionalRestrict to replace leftJoin (and by symmetry,
 rightJoin).
Arguments
| :: 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" | 
NB Opaleye exports Opaleye.Table. from
 the top level.  If you want this optionaloptional you will have to import
 it from this module.
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 aoptional q
 :: SelectArr i (MaybeFields a)optional qq
 wrapped in "Just".  For example,
> let l1 = ["one", "two", "three"] :: [Field SqlText] >runSelectconn (optional(valuesSafel1)) :: IO [Maybe String] [Just "one", Just "two", Just "three"] > let l2 = [] :: [Field SqlText] >runSelectconn (optional(valuesSafel2)) :: IO [Maybe String] [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
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 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))
Arguments
| :: (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
 "leftJoin qL qR cond
proc () -> do fieldsL <- qL -< () maybeFieldsR <-optionalRestrictqR -<currycond fieldsLreturnA-< (fieldsL, maybeFieldsR)
Typically everything except the optionalRestrict line can be
 inlined in surrounding arrow notation.  In such cases, readability
 and maintainibility increase dramatically.
Arguments
| :: (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.
Arguments
| :: (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.
Arguments
| :: (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 #
Inferrable versions (deprecated)
Arguments
| :: (Default Unpackspec fieldsL fieldsL, Default Unpackspec fieldsR fieldsR, Default NullMaker fieldsR nullableFieldsR, Map Nulled fieldsR ~ nullableFieldsR) | |
| => Select fieldsL | Left query | 
| -> Select fieldsR | Right query | 
| -> ((fieldsL, fieldsR) -> Field SqlBool) | Condition on which to join | 
| -> Select (fieldsL, nullableFieldsR) | Left join | 
Deprecated: Use optionalRestrict instead.
Arguments
| :: (Default Unpackspec fieldsL fieldsL, Default Unpackspec fieldsR fieldsR, Default NullMaker fieldsL nullableFieldsL, Map Nulled fieldsL ~ nullableFieldsL) | |
| => Select fieldsL | Left query | 
| -> Select fieldsR | Right query | 
| -> ((fieldsL, fieldsR) -> Field SqlBool) | Condition on which to join | 
| -> Select (nullableFieldsL, fieldsR) | Right join | 
Deprecated: Use optionalRestrict instead.
Arguments
| :: (Default Unpackspec fieldsL fieldsL, Default Unpackspec fieldsR fieldsR, Default NullMaker fieldsL nullableFieldsL, Default NullMaker fieldsR nullableFieldsR, Map Nulled fieldsL ~ nullableFieldsL, Map Nulled 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 | 
Deprecated: Use rightJoinF instead.