HaskRel-0.1.0.0: HaskRel, Haskell as a DBMS with support for the relational algebra

Copyright© Thor Michael Støre, 2015
LicenseGPL v2 without "any later version" clause
Maintainerthormichael át gmail døt com
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Database.HaskRel.Relational.Unicode

Contents

Description

Functions pertaining to relational theory or set theory named with non-ASCII unicode characters, primarily infix operators. Each of these is a synonym for an alphabetically named prefix function.

See also: http://hackage.haskell.org/package/base-unicode-symbols

TODO: Fix operator precedence, right now one may need to apply more parenthesis than should be necessary.

Synopsis

Relational algebra operators

(⋈) :: (Eq (HList l), Ord (HList (HAppendListR * t1 t2)), HLabelSet [*] (LabelsOf l), HLabelSet [*] (LabelsOf t2), HLabelSet [*] (LabelsOf r), HLabelSet [*] (LabelsOf (HAppendListR * t1 t2)), H2ProjectByLabels (LabelsOf t1) t l t2, H2ProjectByLabels (LabelsOf t) t1 r b1, HRearrange3 (LabelsOf l) r l, HAppendList t1 t2, SameLength' * * l r, SameLength' * * r l, SameLength' * * r (LabelsOf l), SameLength' * * (LabelsOf l) r, HAllTaggedLV t2, HAllTaggedLV l, HAllTaggedLV r, HAllTaggedLV (HAppendListR * t1 t2), DyaOp a b, (~) * (DyaOpRight b) (Set (RTuple t)), (~) * (DyaOpLeft a) (Set (RTuple t1))) => a -> b -> DyaOpRes a b (Relation (HAppendListR * t1 t2)) Source

Natural join.

>>> rPrint$ sp ⋈ s
...

As naturalJoin.

(⋉) :: (Eq (HList l), Ord (HList t), HLabelSet [*] (LabelsOf l), HLabelSet [*] (LabelsOf r), H2ProjectByLabels (LabelsOf t) l1 l b1, H2ProjectByLabels (LabelsOf l1) t r b2, HRearrange3 (LabelsOf l) r l, SameLength' * * l r, SameLength' * * r l, SameLength' * * r (LabelsOf l), SameLength' * * (LabelsOf l) r, HAllTaggedLV l, HAllTaggedLV r, DyaOp a b, (~) * (DyaOpRight b) (Set (RTuple l1)), (~) * (DyaOpLeft a) (Set (RTuple t))) => a -> b -> DyaOpRes a b (Relation t) Source

Semijoin.

>>> rPrint$ s ⋉ sp
...

As matching.

(⋊) :: (Eq (HList l), Ord (HList t), HLabelSet [*] (LabelsOf l), HLabelSet [*] (LabelsOf r), H2ProjectByLabels (LabelsOf t) l1 l b1, H2ProjectByLabels (LabelsOf l1) t r b2, HRearrange3 (LabelsOf l) r l, SameLength' * * l r, SameLength' * * r l, SameLength' * * r (LabelsOf l), SameLength' * * (LabelsOf l) r, HAllTaggedLV l, HAllTaggedLV r, DyaOp a b, (~) * (DyaOpRight b) (Set (RTuple l1)), (~) * (DyaOpLeft a) (Set (RTuple t))) => b -> a -> DyaOpRes a b (Relation t) Source

Left semijoin. As (flip matching).

(◅) :: (Eq (HList l), Ord (HList t), HLabelSet [*] (LabelsOf l), HLabelSet [*] (LabelsOf r), H2ProjectByLabels (LabelsOf t) l1 l b1, H2ProjectByLabels (LabelsOf l1) t r b2, HRearrange3 (LabelsOf l) r l, SameLength' * * l r, SameLength' * * r l, SameLength' * * r (LabelsOf l), SameLength' * * (LabelsOf l) r, HAllTaggedLV l, HAllTaggedLV r, DyaOp a b, (~) * (DyaOpRight b) (Set (RTuple l1)), (~) * (DyaOpLeft a) (Set (RTuple t))) => a -> b -> DyaOpRes a b (Relation t) Source

Semidifference.

>>> rPrint$ s ◅ sp
...

As notMatching.

(▻) :: (Eq (HList l), Ord (HList t), HLabelSet [*] (LabelsOf l), HLabelSet [*] (LabelsOf r), H2ProjectByLabels (LabelsOf t) l1 l b1, H2ProjectByLabels (LabelsOf l1) t r b2, HRearrange3 (LabelsOf l) r l, SameLength' * * l r, SameLength' * * r l, SameLength' * * r (LabelsOf l), SameLength' * * (LabelsOf l) r, HAllTaggedLV l, HAllTaggedLV r, DyaOp a b, (~) * (DyaOpRight b) (Set (RTuple l1)), (~) * (DyaOpLeft a) (Set (RTuple t))) => b -> a -> DyaOpRes a b (Relation t) Source

Left semidifference. As (flip notMatching).

(×) :: (Eq (HList l), Ord (HList (HAppendListR * t1 t2)), HLabelSet [*] (LabelsOf (HAppendListR * t r)), HLabelSet [*] (LabelsOf l), HLabelSet [*] (LabelsOf t2), HLabelSet [*] (LabelsOf r), HLabelSet [*] (LabelsOf (HAppendListR * t1 t2)), H2ProjectByLabels (LabelsOf t1) t l t2, H2ProjectByLabels (LabelsOf t) t1 r b1, HRearrange3 (LabelsOf l) r l, HAppendList t1 t2, SameLength' * * r l, SameLength' * * r (LabelsOf l), SameLength' * * l r, SameLength' * * (LabelsOf l) r, HAllTaggedLV t2, HAllTaggedLV r, HAllTaggedLV l, HAllTaggedLV (HAppendListR * t1 t2), HAllTaggedLV (HAppendListR * t r), DyaOp a b, (~) * (DyaOpRight b) (Set (RTuple t)), (~) * (DyaOpLeft a) (Set (RTuple t1))) => a -> b -> DyaOpRes a b (Relation (HAppendListR * t1 t2)) Source

Times. The special case of natural join where the headings of the relations are disjoint.

>>> rPrint$ ( sp `projectAllBut` (rHdr (sno)) ) × ( s `projectAllBut` (rHdr (sno)) )
...

As times.

(∣) :: (MonOp a, (~) * (MonOpArg a) (Set a1)) => a -> (a1 -> Bool) -> MonOpRes a (Set a1) Source

Restriction.

Note that the symbol used here is the divisor symbol, which looks the same but is distinct from the vertical bar, or pipe. However, since the vertical bar is used in Haskell for different purposes and is for that reason not a valid infix operator symbol, this is used instead.

>>> rPrint$ p ∣ (\[pun|weight|] -> weight < 17.5)
...

As restrict.

(∪) :: (Ord (HList l), HLabelSet [*] (LabelsOf l), HRearrange3 (LabelsOf l) r l, SameLength' * * l r, SameLength' * * r l, SameLength' * * r (LabelsOf l), SameLength' * * (LabelsOf l) r, DyaOp a b, (~) * (DyaOpRight b) (Set (RTuple r)), (~) * (DyaOpLeft a) (Set (RTuple l))) => a -> b -> DyaOpRes a b (Relation l) Source

Union.

>>> rPrint$ s ∪ ( relation [rTuple (sno .=. "S6", sName .=. "Nena", status .=. 40, city .=. "Berlin")] )
...

As union.

(∩) :: (Ord (HList l), HLabelSet [*] (LabelsOf l), HRearrange3 (LabelsOf l) r l, SameLength' * * l r, SameLength' * * r l, SameLength' * * r (LabelsOf l), SameLength' * * (LabelsOf l) r, DyaOp a b, (~) * (DyaOpRight b) (Set (RTuple r)), (~) * (DyaOpLeft a) (Set (RTuple l))) => a -> b -> DyaOpRes a b (Relation l) Source

Intersection.

>>> let sX = ( relation [rTuple (sno .=. "S2", sName .=. "Jones", status .=. 10, city .=. "Paris"), rTuple (sno .=. "S6", sName .=. "Nena", status .=. 40, city .=. "Berlin")] )
>>> rPrint$ s ∩ sX
...

As intersect.

(∖) :: (Ord (HList l), HLabelSet [*] (LabelsOf l), HRearrange3 (LabelsOf l) r l, SameLength' * * l r, SameLength' * * r l, SameLength' * * r (LabelsOf l), SameLength' * * (LabelsOf l) r, DyaOp a b, (~) * (DyaOpRight b) (Set (RTuple r)), (~) * (DyaOpLeft a) (Set (RTuple l))) => a -> b -> DyaOpRes a b (Relation l) Source

Minus.

Note that this is the difference symbol, not a backslash.

>>> rPrint$ s ∖ sX
...

As minus.

π :: (Ord (HList a1), HLabelSet [*] (LabelsOf a1), H2ProjectByLabels ls t a1 b, HAllTaggedLV a1, MonOp a, (~) * (MonOpArg a) (Set (RTuple t))) => proxy ls -> a -> MonOpRes a (Relation a1) Source

Projection.

Note that no matter how greek it is π is still a character, and Haskell therefore treats it as a prefix operator, which is in line with how it is employed.

>>> rPrint$ π (rHdr (color,city)) p
...

As project, but note how the operands are reversed.

(⊂) :: (Ord (HList l), HLabelSet [*] (LabelsOf l), HRearrange3 (LabelsOf l) r l, SameLength' * * l r, SameLength' * * r l, SameLength' * * r (LabelsOf l), SameLength' * * (LabelsOf l) r, DyaOp a b, (~) * (DyaOpRight b) (Set (RTuple r)), (~) * (DyaOpLeft a) (Set (RTuple l))) => a -> b -> DyaOpRes a b Bool Source

Is proper subset.

>>> let spX = relation [rTuple (sno .=. "S1", pno .=. "P4", qty .=. 200), rTuple (sno .=. "S2", pno .=. "P2", qty .=. 400)]
>>> spX ⊂ sp
True

As isProperSubsetOf.

(⊆) :: (Ord (HList l), HLabelSet [*] (LabelsOf l), HRearrange3 (LabelsOf l) r l, SameLength' * * l r, SameLength' * * r l, SameLength' * * r (LabelsOf l), SameLength' * * (LabelsOf l) r, DyaOp a b, (~) * (DyaOpRight b) (Set (RTuple r)), (~) * (DyaOpLeft a) (Set (RTuple l))) => a -> b -> DyaOpRes a b Bool Source

Is subset of.

>>> spX ⊆ sp
True

As isSubsetOf.

(⊃) :: (Ord (HList l), HLabelSet [*] (LabelsOf l), HRearrange3 (LabelsOf l) r l, SameLength' * * l r, SameLength' * * r l, SameLength' * * r (LabelsOf l), SameLength' * * (LabelsOf l) r, DyaOp a b, (~) * (DyaOpRight b) (Set (RTuple r)), (~) * (DyaOpLeft a) (Set (RTuple l))) => b -> a -> DyaOpRes a b Bool Source

Left is proper subset of. As (flip isProperSubsetOf).

(⊇) :: (Ord (HList l), HLabelSet [*] (LabelsOf l), HRearrange3 (LabelsOf l) r l, SameLength' * * l r, SameLength' * * r l, SameLength' * * r (LabelsOf l), SameLength' * * (LabelsOf l) r, DyaOp a b, (~) * (DyaOpRight b) (Set (RTuple r)), (~) * (DyaOpLeft a) (Set (RTuple l))) => b -> a -> DyaOpRes a b Bool Source

Left is subset of. As (flip isSubsetOf).

Relational assignment operators

(≔) :: (Ord (HList a1), Show (HList (RecordValuesR a1)), HLabelSet [*] (LabelsOf a1), RecordValues a1, HRearrange3 (LabelsOf a1) r a1, SameLength' * * a1 r, SameLength' * * r a1, SameLength' * * r (LabelsOf a1), SameLength' * * (LabelsOf a1) r, RelAssign a, (~) * (RelAssignArg a) (Set (RTuple r))) => Relvar a1 -> a -> IO () infix 1 Source

Relational assignment operator.

This uses the COLON EQUALS UTF-8 character (&#8788;), the ASCII variant := wouldn't be allowed in Haskell since it starts with a colon.

>>> s ≔ s'
>>> 

As assign.

Supplementary relational operators

Not part of relational theory

(⊠) :: (Eq (HList l), Ord (HList (HAppendListR * t1 t2)), HLabelSet [*] (LabelsOf r), HLabelSet [*] (LabelsOf l), HLabelSet [*] (LabelsOf t2), HLabelSet [*] (LabelsOf (HAppendListR * t1 t2)), H2ProjectByLabels (LabelsOf t) t1 r b1, H2ProjectByLabels (LabelsOf t1) t l t2, HRearrange3 (LabelsOf l) r l, HAppendList t1 t2, HTIntersect (LabelsOf r) (LabelsOf t) i, SameLength' * * r l, SameLength' * * r (LabelsOf l), SameLength' * * l r, SameLength' * * (LabelsOf l) r, HAllTaggedLV t2, HAllTaggedLV r, HAllTaggedLV l, HAllTaggedLV (HAppendListR * t1 t2), NotEmpty i, DyaOp a b, (~) * (DyaOpRight b) (Set (RTuple t)), (~) * (DyaOpLeft a) (Set (RTuple t1))) => a -> b -> DyaOpRes a b (Relation (HAppendListR * t1 t2)) Source

Attribute intersecting natural join. The special case of natural join where the headings of the relations are not disjoint.

Using the "box times" or "squared times" (U+22A0) symbol is my own solution. As with the name "(attribute) intersecting natural join" suggestions are welcome.

As mentioned in Database.HaskRel.Relational.Algebra, this operation doesn't have a single identity value, although it holds that for any given relation value r, r ⊠ r = r

>>> rPrint$ sp ⊠ s
...

As interJoin.

Set theoretic operators

(#) :: (MonOp a, (~) * (MonOpArg a) (Set a1)) => a -> MonOpRes a Int Source

Cardinality.

>>> (#) sp
12

As count.

(∈) :: (Ord (HList l), HLabelSet [*] (LabelsOf l), HRearrange3 (LabelsOf l) r l, SameLength' * * r l, SameLength' * * r (LabelsOf l), SameLength' * * l r, SameLength' * * (LabelsOf l) r, MonOp a, (~) * (MonOpArg a) (Set (Record l))) => Record r -> a -> MonOpRes a Bool Source

Is member of.

>>> let spX = rTuple(sno .=. "S3", qty .=. 200, pno .=. "P2")
>>> spX ∈ sp
True

As member.

(∉) :: (Ord (HList l), HLabelSet [*] (LabelsOf l), HRearrange3 (LabelsOf l) r l, SameLength' * * r l, SameLength' * * r (LabelsOf l), SameLength' * * l r, SameLength' * * (LabelsOf l) r, MonOp a, (~) * (MonOpArg a) (Set (Record l))) => Record r -> a -> MonOpRes a Bool Source

Is not member of.

>>> spX ∉ sp
False

As notMember.

(∋) :: (Ord (HList l), HLabelSet [*] (LabelsOf l), HRearrange3 (LabelsOf l) r l, SameLength' * * r l, SameLength' * * r (LabelsOf l), SameLength' * * l r, SameLength' * * (LabelsOf l) r, MonOp a, (~) * (MonOpArg a) (Set (Record l))) => a -> Record r -> MonOpRes a Bool Source

Is member of left. As (flip member).

(∌) :: (Ord (HList l), HLabelSet [*] (LabelsOf l), HRearrange3 (LabelsOf l) r l, SameLength' * * r l, SameLength' * * r (LabelsOf l), SameLength' * * l r, SameLength' * * (LabelsOf l) r, MonOp a, (~) * (MonOpArg a) (Set (Record l))) => a -> Record r -> MonOpRes a Bool Source

Is not member of left. As (flip notMember).

(∅) :: Set a Source

The empty set. Note that this is neither tableDum nor tableDee.

>>> (relation [] :: Relation '[]) == (∅)
True
>>> relation [rTuple (sno .=. "S1", status .=. 5)] == (∅)
False