Copyright | © Thor Michael Støre, 2015 |
---|---|
License | GPL v2 without "any later version" clause |
Maintainer | thormichael át gmail døt com |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
Definition and presentation of relational objects in terms of Haskell and HList records, and certain implementation level supporting functions.
Naming convention of the relational model is, to a degree, adopted to clarify how it is mirrored into Haskell. With these aliases in place the following are equivalent:
>>>
:t fromList [] :: Set (Record '[Tagged "sno" String, Tagged "status" Int])
>>>
:t relation [] :: Relation '[Attr "sno" String, Attr "status" Int]
- type Attr = Tagged
- type RTuple = Record
- type Relation a = Set (RTuple a)
- data Label l :: k -> * = Label
- type family Labels xs :: *
- rTuple :: (HLabelSet (LabelsOf r), HTuple r t, HAllTaggedLV r) => t -> RTuple r
- rTuple' :: (RecordValues b, HTuple (RecordValuesR b) t, HMapAux HList TaggedFn (RecordValuesR b) b) => t -> RTuple b
- relation :: (Ord a, a ~ Record b) => [a] -> Relation b
- relation' :: (Ord (HList b), RecordValues b, HTuple (RecordValuesR b) t, HMapAux HList TaggedFn (RecordValuesR b) b) => [t] -> Relation b
- rHdr :: HTuple v t => t -> HList v
- as :: Label l -> v -> Tagged l v
- nAs :: (HLabelSet (LabelsOf r), HTuple r t, HAllTaggedLV r) => t -> Record r
- tableDum :: Relation `[]`
- tableDee :: Relation `[]`
- empty :: Set a
- unordRecEq :: (Eq (HList l), HRearrange3 (LabelsOf l) r l, HLabelSet (LabelsOf l), SameLength' r l, SameLength' r (LabelsOf l), SameLength' l r, SameLength' (LabelsOf l) r) => RTuple l -> RTuple r -> Bool
- bodyAsList :: RecordValues r => Relation r -> [HList (RecordValuesR r)]
- relRearrange :: (Ord (HList l), HRearrange3 (LabelsOf l) r l, HLabelSet (LabelsOf l), SameLength' r l, SameLength' r (LabelsOf l), SameLength' l r, SameLength' (LabelsOf l) r) => Relation r -> Relation l
- relRearrange' :: (Ord (HList l), HRearrange3 (LabelsOf l) r l, HLabelSet (LabelsOf l), SameLength' r l, SameLength' r (LabelsOf l), SameLength' l r, SameLength' (LabelsOf l) r) => Relation r -> Relation l -> Relation l
- data HaskRelTS = HaskRelTS
- class HListTypeSynonym s
- rPrint :: HFWPresent r => r -> IO ()
- rPrintTyped :: HFWPresent r => r -> IO ()
- p :: HFWPresent r => r -> IO ()
- pt :: HFWPresent r => r -> IO ()
- rShowType :: TypeRep -> String
- showRelTab :: (Typeable a, RecordValues a, HFoldr (Mapcar HPresentRecAttr) [[String]] (RecordValuesR a) [[String]]) => Relation a -> String
Definition
A "tuple as defined by the relational model", synonym for Data.HList.Record
.
Labels
To be in line with the naming convention of the relational model, the Label
type could be referred to as an "attribute name", and the Labels
type as "attribute names", but since this would not clarify the matter significantly HaskRel re-exports them as-is.
It is important to note how labels may either be pre-defined, or used ad-hoc:
>>>
let qty = Label :: Label "qty"
>>>
sum $ agg qty sp'
3100>>>
sum $ agg ( Label :: Label "qty" ) sp'
3100
data Label l :: k -> *
A special Proxy
for record labels, polykinded
(~) * (Label k t) (Label Symbol t') => SameLabels * Symbol (Label k t) t' | |
(~) * (Label k t) (Label k1 t') => SameLabels * * (Label k t) (Label k1 t') | |
(~) * (Label k t) (Label k1 t') => SameLabels * * (Label k t) (Tagged k1 t' a) | |
(~) * (Label k t) (Label * (Lbl ix ns n)) => SameLabels * * (Label k t) (Lbl ix ns n) | |
Show desc => Show (Label * (Lbl x ns desc)) | |
HExtend (Label * (Lbl n ns desc)) (Proxy [*] ((:) * (Lbl n' ns' desc') xs)) | If possible, Label is left off:
|
HExtend (Label * (Lbl n ns desc)) (Proxy [Symbol] ((:) Symbol x xs)) | Mixing two label kinds means we have to include
|
HExtend (Label k x) (Proxy [*] ([] *)) | to keep types shorter, ghc-7.6 does not accept |
type UnLabel k proxy ((:) * (Label k x) xs) = (:) k x (UnLabel k proxy xs) | |
type ZipTagged * ((:) * (Label k t) ts) ((:) * v vs) = (:) * (Tagged k t v) (ZipTagged * ts vs) | |
type HExtendR (Label * (Lbl n ns desc)) (Proxy [Symbol] ((:) Symbol x xs)) = Proxy [*] ((:) * (Label * (Lbl n ns desc)) (MapLabel Symbol ((:) Symbol x xs))) | |
type HExtendR (Label * (Lbl n ns desc)) (Proxy [*] ((:) * (Lbl n' ns' desc') xs)) = Proxy [*] ((:) * (Lbl n ns desc) ((:) * (Lbl n' ns' desc') xs)) | |
type HExtendR (Label Nat y) (Proxy [Nat] ((:) Nat x xs)) = Proxy [Nat] ((:) Nat y ((:) Nat x xs)) | |
type HExtendR (Label Nat y) (Proxy [Symbol] ((:) Symbol x xs)) = Proxy [*] ((:) * (Label Nat y) (MapLabel Symbol ((:) Symbol x xs))) | |
type HExtendR (Label Nat y) (Proxy [*] ((:) * x xs)) = Proxy [*] ((:) * (Label Nat y) (MapLabel * ((:) * x xs))) | |
type HExtendR (Label Symbol y) (Proxy [Symbol] ((:) Symbol x xs)) = Proxy [Symbol] ((:) Symbol y ((:) Symbol x xs)) | |
type HExtendR (Label Symbol y) (Proxy [Nat] ((:) Nat x xs)) = Proxy [*] ((:) * (Label Symbol y) (MapLabel Nat ((:) Nat x xs))) | |
type HExtendR (Label Symbol y) (Proxy [*] ((:) * x xs)) = Proxy [*] ((:) * (Label Symbol y) (MapLabel * ((:) * x xs))) | |
type HExtendR (Label k x) (Proxy [*] ([] *)) = Proxy [k] ((:) k x ([] k)) | |
type LabelsOf ((:) * (Label k l) r) = (:) * (Label k l) (LabelsOf r) |
type family Labels xs :: *
A helper to make the Proxy needed by hProjectByLabels, and similar functions which accept a list of kind [*].
For example:
(rin,rout) = hProjectByLabels2
(Proxy :: Labels ["x","y"]) r
behaves like
rin = r .!. (Label :: Label "x") .*. r .!. (Label :: Label "y") .*. emptyRecord rout = r .-. (Label :: Label "x") .-. (Label :: Label "y")
Construction
These functions are based on common HList operations, and given aliases that are in line with relational theory. As mentioned for each function they only support 0 to 6-tuples, which is of course a drawback. For r-tuples of other degrees the basic HList approaches to record construction may be used:
>>>
let sno = Label :: Label "sno"
... etc ...>>>
pt$ sno .=. "S1" .*. sName .=. "Smith" .*. status .=. (20::Integer) .*. city .=. "London" .*. pName .=. "Ratchet" .*. color .=. "Mauve" .*. pno .=. "P9" .*. emptyRecord
...>>>
type SNO = Tagged "sno" String
... etc ...>>>
pt$ (hEndR $ hBuild "S1" "Smith" 20 "London" "Ratchet" "Mauve" "P9" :: Record '[SNO,SName,Status,City,PName,Color,PNO])
...
Same result.
rTuple :: (HLabelSet (LabelsOf r), HTuple r t, HAllTaggedLV r) => t -> RTuple r Source
Constructs an r-tuple from tagged values. Supports only 0 to 6-tuples.
>>>
pt$ rTuple (sno .=. "S1", sName .=. "Smith", status .=. (20::Integer), city .=. "London")
┌───────────────┬─────────────────┬───────────────────┬────────────────┐ │ sno :: String │ sName :: String │ status :: Integer │ city :: String │ ├───────────────┼─────────────────┼───────────────────┼────────────────┤ │ S1 │ Smith │ 20 │ London │ └───────────────┴─────────────────┴───────────────────┴────────────────┘
rTuple' :: (RecordValues b, HTuple (RecordValuesR b) t, HMapAux HList TaggedFn (RecordValuesR b) b) => t -> RTuple b Source
Constructs an r-tuple from a tuples of untagged values, where the labels and exact types are inferred from the context. Supports only 0 to 6-tuples.
>>>
pt$ ( rTuple' ("S1", "Smith", 20, "London") :: RTuple '[SNO, SName, Status, City] )
...
Result as for rTuple
.
relation :: (Ord a, a ~ Record b) => [a] -> Relation b Source
Construct a relation value from a list of r-tuples of tagged values. Alias of fromList
with a result restricted to Relation
, with a name from relational theory. Supports only 0 to 6-tuples.
>>>
:{
pt$ relation [rTuple (sno .=. "S1", sName .=. "Smith", status .=. (20::Integer), city .=. "London"), rTuple (sno .=. "S2", sName .=. "Jones", status .=. (10::Integer), city .=. "Paris")] :} ┌───────────────┬─────────────────┬───────────────────┬────────────────┐ │ sno :: String │ sName :: String │ status :: Integer │ city :: String │ ╞═══════════════╪═════════════════╪═══════════════════╪════════════════╡ │ S1 │ Smith │ 20 │ London │ │ S2 │ Jones │ 10 │ Paris │ └───────────────┴─────────────────┴───────────────────┴────────────────┘
relation' :: (Ord (HList b), RecordValues b, HTuple (RecordValuesR b) t, HMapAux HList TaggedFn (RecordValuesR b) b) => [t] -> Relation b Source
Construct a relation value from a list of tuples of untagged values, where the labels and exact types are inferred from the context. Supports only 0 to 6-tuples.
>>>
pt$ ( relation' [("S1", "Smith", 20, "London"), ("S2", "Jones", 10, "Paris")] :: Relation '[SNO, SName, Status, City] )
Result as for relation
.
rHdr :: HTuple v t => t -> HList v Source
Alias of Data.HList.HList.hFromTuple
with a name that is more descriptive for the purpose of constructing Labels, which are employed as relational headings, from Haskell tuples of label values. When labels have been defined it permits expressing:
>>>
pt$ p `project` (undefined :: Labels '["pno","pName","color"])
As:
>>>
pt$ p `project` (rHdr (pno,pName,color))
Supports 0 to 6-tuples.
nAs :: (HLabelSet (LabelsOf r), HTuple r t, HAllTaggedLV r) => t -> Record r Source
N-adic constructor of as
statements, using mkRecord . hFromTuple
. Only supports 0 to 6-tuples.
>>>
let pnu = Label :: Label "pnu"
>>>
let colour = Label :: Label "colour"
>>>
:t nAs (pno `as` pnu, color `as` colour)
nAs (pno `as` pnu, color `as` colour) :: Record '[Tagged "pno" (Label "pnu"), Tagged "color" (Label "colour")]
Constants
tableDum :: Relation `[]` Source
The nullary relation with an empty body
>>>
pt$ tableDum
┌──┐ │ │ ╞══╡ └──┘>>>
relation [] == tableDum
True
tableDee :: Relation `[]` Source
The nullary relation of cardinality one.
>>>
pt$ tableDee
┌──┐ │ │ ╞══╡ │ │ └──┘>>>
relation [rTuple ()] == tableDee
True>>>
relation' [()] == tableDee
True
Support
unordRecEq :: (Eq (HList l), HRearrange3 (LabelsOf l) r l, HLabelSet (LabelsOf l), SameLength' r l, SameLength' r (LabelsOf l), SameLength' l r, SameLength' (LabelsOf l) r) => RTuple l -> RTuple r -> Bool Source
Order-agnostic equality operation, which is neccessary for comparison correct for r-tuples.
bodyAsList :: RecordValues r => Relation r -> [HList (RecordValuesR r)] Source
Gives the body of a relation as a list. This will untag the values.
relRearrange :: (Ord (HList l), HRearrange3 (LabelsOf l) r l, HLabelSet (LabelsOf l), SameLength' r l, SameLength' r (LabelsOf l), SameLength' l r, SameLength' (LabelsOf l) r) => Relation r -> Relation l Source
Rearrange a set of HList records to context. From the perspective of relational theory this is a presentation function.
relRearrange' :: (Ord (HList l), HRearrange3 (LabelsOf l) r l, HLabelSet (LabelsOf l), SameLength' r l, SameLength' r (LabelsOf l), SameLength' l r, SameLength' (LabelsOf l) r) => Relation r -> Relation l -> Relation l Source
Rearrange a set of HList records to the order of a set given by an argument. The value of the second argument will be ignored. From the perspective of relational theory this is a presentation function.
Presentation
HaskRel type synonyms
HListTypeSynonym HaskRelTS Source | HaskRel type synonyms |
class HListTypeSynonym s Source
Type synoyms used when building the table header with type names
HListTypeSynonym HaskRelTS Source | HaskRel type synonyms |
rPrint :: HFWPresent r => r -> IO () Source
Prints a tabular representation of an r-tuple or relation.
rPrintTyped :: HFWPresent r => r -> IO () Source
Prints a tabular representation of an r-tuple or relation, with type information.
p :: HFWPresent r => r -> IO () Source
Synonym of rPrint
.
pt :: HFWPresent r => r -> IO () Source
Synonym of rPrintTyped
.
rShowType :: TypeRep -> String Source
Specialization of Database.HaskRel.HFWTabulation.showHTypeTS
that employs HaskRel specific type-synonyms.
showRelTab :: (Typeable a, RecordValues a, HFoldr (Mapcar HPresentRecAttr) [[String]] (RecordValuesR a) [[String]]) => Relation a -> String Source
Shows a tabular representation of a relation.