Safe Haskell | None |
---|---|
Language | Haskell2010 |
Functions for performing SQL style table joins on
Frame
objects. Uses Data.Discrimination under the hood
for O(n) joins. These have behaviour equivalent to
INNER JOIN
, FULL JOIN
, LEFT JOIN
, and RIGHT JOIN
from
SQL.
Synopsis
- innerJoin :: forall fs rs rs2 rs2'. (fs ⊆ rs, fs ⊆ rs2, rs ⊆ (rs ++ rs2'), rs2' ⊆ rs2, rs2' ~ RDeleteAll fs rs2, Grouping (Record fs), RecVec rs, RecVec rs2', RecVec (rs ++ rs2')) => Frame (Record rs) -> Frame (Record rs2) -> Frame (Record (rs ++ rs2'))
- outerJoin :: forall fs rs rs' rs2 rs2' ors. (fs ⊆ rs, fs ⊆ rs2, rs ⊆ (rs ++ rs2'), rs' ⊆ rs, rs' ~ RDeleteAll fs rs, rs2' ⊆ rs2, rs2' ~ RDeleteAll fs rs2, ors ~ (rs ++ rs2'), ors :~: (rs' ++ rs2), RecApplicative rs2', RecApplicative rs, RecApplicative rs', Grouping (Record fs), RMap rs, RMap rs2, RMap ors, RecVec rs, RecVec rs2', RecVec ors) => Frame (Record rs) -> Frame (Record rs2) -> [Rec (Maybe :. ElField) ors]
- leftJoin :: forall fs rs rs2 rs2'. (fs ⊆ rs, fs ⊆ rs2, rs ⊆ (rs ++ rs2'), rs2' ⊆ rs2, rs2' ~ RDeleteAll fs rs2, RMap rs, RMap (rs ++ rs2'), RecApplicative rs2', Grouping (Record fs), RecVec rs, RecVec rs2', RecVec (rs ++ rs2')) => Frame (Record rs) -> Frame (Record rs2) -> [Rec (Maybe :. ElField) (rs ++ rs2')]
- rightJoin :: forall fs rs rs' rs2 rs2' ors. (fs ⊆ rs, fs ⊆ rs2, rs ⊆ (rs ++ rs2'), rs' ⊆ rs, rs' ~ RDeleteAll fs rs, rs2' ⊆ rs2, rs2' ~ RDeleteAll fs rs2, ors ~ (rs ++ rs2'), ors :~: (rs' ++ rs2), RecApplicative rs2', RecApplicative rs, RecApplicative rs', Grouping (Record fs), RMap rs2, RMap ors, RecVec rs, RecVec rs2', RecVec ors) => Frame (Record rs) -> Frame (Record rs2) -> [Rec (Maybe :. ElField) ors]
Documentation
:: forall fs rs rs2 rs2'. (fs ⊆ rs, fs ⊆ rs2, rs ⊆ (rs ++ rs2'), rs2' ⊆ rs2, rs2' ~ RDeleteAll fs rs2, Grouping (Record fs), RecVec rs, RecVec rs2', RecVec (rs ++ rs2')) | |
=> Frame (Record rs) | The left frame |
-> Frame (Record rs2) | The right frame |
-> Frame (Record (rs ++ rs2')) | The joined frame |
Perform an inner join operation on two frames.
Requires the language extension TypeApplications
for specifying the columns to
join on.
Joins can be done on on one or more columns provided the matched
columns have a Grouping
instance, most simple types do.
Presently join columns must be present and named identically in both left and right frames.
Basic usage: innerJoin @'[JoinCol1, ..., JoinColN] leftFrame rightFrame
:: forall fs rs rs' rs2 rs2' ors. (fs ⊆ rs, fs ⊆ rs2, rs ⊆ (rs ++ rs2'), rs' ⊆ rs, rs' ~ RDeleteAll fs rs, rs2' ⊆ rs2, rs2' ~ RDeleteAll fs rs2, ors ~ (rs ++ rs2'), ors :~: (rs' ++ rs2), RecApplicative rs2', RecApplicative rs, RecApplicative rs', Grouping (Record fs), RMap rs, RMap rs2, RMap ors, RecVec rs, RecVec rs2', RecVec ors) | |
=> Frame (Record rs) | The left frame |
-> Frame (Record rs2) | The right frame |
-> [Rec (Maybe :. ElField) ors] | A list of the merged records, now in the Maybe functor |
Perform an outer join (FULL JOIN
) operation on two frames.
Requires the use the language extension TypeApplications
for specifying the
columns to join on.
Joins can be done on on one or more columns provided the
columns have a Grouping
instance, most simple types do.
Presently join columns must be present and named identically in both left and right frames.
Returns a list of Records in the Maybe interpretation functor.
If a key in the left table is missing from the right table, non-key
columns from the right table are filled with Nothing
.
If a key in the right table is missing from the left table, non-key
columns from the right table are filled with Nothing
.
Basic usage: outerJoin @'[JoinCol1, ..., JoinColN] leftFrame rightFrame
:: forall fs rs rs2 rs2'. (fs ⊆ rs, fs ⊆ rs2, rs ⊆ (rs ++ rs2'), rs2' ⊆ rs2, rs2' ~ RDeleteAll fs rs2, RMap rs, RMap (rs ++ rs2'), RecApplicative rs2', Grouping (Record fs), RecVec rs, RecVec rs2', RecVec (rs ++ rs2')) | |
=> Frame (Record rs) | The left frame |
-> Frame (Record rs2) | The right frame |
-> [Rec (Maybe :. ElField) (rs ++ rs2')] | A list of the merged records, now in the Maybe functor |
Perform an left join operation on two frames.
Requires the language extension TypeApplications
for specifying the
columns to join on.
Joins can be done on on one or more columns provided the
columns have a Grouping
instance, most simple types do.
Presently join columns must be present and named identically in both left and right frames.
Returns a list of Records in the Maybe interpretation functor.
If a key in the left table is missing from the right table, non-key
columns from the right table are filled with Nothing
.
Basic usage: leftJoin @'[JoinCol1, ..., JoinColN] leftFrame rightFrame
:: forall fs rs rs' rs2 rs2' ors. (fs ⊆ rs, fs ⊆ rs2, rs ⊆ (rs ++ rs2'), rs' ⊆ rs, rs' ~ RDeleteAll fs rs, rs2' ⊆ rs2, rs2' ~ RDeleteAll fs rs2, ors ~ (rs ++ rs2'), ors :~: (rs' ++ rs2), RecApplicative rs2', RecApplicative rs, RecApplicative rs', Grouping (Record fs), RMap rs2, RMap ors, RecVec rs, RecVec rs2', RecVec ors) | |
=> Frame (Record rs) | The left frame |
-> Frame (Record rs2) | The right frame |
-> [Rec (Maybe :. ElField) ors] | A list of the merged records, now in the Maybe functor |
Perform an right join operation on two frames.
Requires the language extension TypeApplications
for specifying the
columns to join on.
Joins can be done on on one or more columns provided the
columns have a Grouping
instance, most simple types do.
Presently join columns must be present and named identically in both left and right frames.
Returns a list of Records in the Maybe interpretation functor.
If a key in the right table is missing from the left table, non-key
columns from the right table are filled with Nothing
.
Basic usage: rightJoin @'[JoinCol1, ..., JoinColN] leftFrame rightFrame