HaskRel-0.1.0.2: 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.RDBMS

Contents

Description

Exports the pertinent parts of HaskRel building on HList records. This gives most features of the relational algebra, relation variable support, HList CommonMain, as well as certain non-relational features such as ordering.

This section below belongs in the package description, but Hackage doesn't format the package description in a satisfactory manner.

Examples

The examples in this documentation are based on "the old warhorse" that is the suppliers-parts database (see [1] for more). This gives a body of relational expressions with known results to base examples upon. See also examples/SuppliersPartsExamples.hs (not visible from this documentation) for Haskell versions of a selection of the Tutorial D expressions given as examples in chapters 6 and 7 of [1]. These can be run by starting examples/suppliersPartsDB.sh and then running snrt2ndExamples. While most Tutorial D expressions translate fairly verbatim to Haskell there are a few where one must be a bit more explicit. While most Tutorial D expressions translate fairly verbatim to Haskell there are a few where Haskell is stricter than Tutorial D and one must be a bit more explicit.

$ is always used after p/rPrint or pt/rPrintTyped in the examples to keep them uniform (and so it kinda looks like a prompt), even when not required. The short forms p and pt are used whenever there isn't a conflict with other identifiers, whereas for the SuppliersPartsExample, which has a relvar "p", rPrint is used instead of p for presentation of relational objects without type information.

Terminology

Since this builds on both Haskell and relational theory this documentation uses terms as they have been established in material related to either. Several terms of Haskell and HList have been redefined in terms of relational theory in this library, mostly to illustrate how terms and concepts have been mapped from the latter to the former. (I'm trying to keep this open to change later if it turns out to be an unhelpful crutch.)

The following table gives a quick overview of either terms or concepts as found in Haskell, the relational model (as presented in [1]), HaskRel and SQL, and how they are mapped from the second to the first:

┌───────────────────────────┬────────────────────┬────────────┬────────────────────────────────────────────────┐
│ haskell                   │ relModel           │ haskRel    │ sql                                            │
╞═══════════════════════════╪════════════════════╪════════════╪════════════════════════════════════════════════╡
│ Data.Tagged.Tagged        │ attribute          │ Attr       │ field, column                                  │
│ Data.HList.Record.Record  │ tuple              │ RTuple     │ row                                            │
│ ( Set (Record a) )        │ relation           │ Relation a │ table                                          │
│ FilePath (Set (Record a)) │ relvar             │ Relvar a   │ table                                          │
│ Data.HList.Record.Label   │ attribute name     │ Label      │ field name, column name                        │
│ Data.HList.Record.Labels  │ attribute name set │ Labels     │ list of field/column names                     │
│ function, operator        │ operator           │ function   │ operator, function, procedure, routine, method │
└───────────────────────────┴────────────────────┴────────────┴────────────────────────────────────────────────┘

Found in "example/Terminology.hs". Note that this is just an overview, study of [1] or [2], Haskell itself, HList and HaskRel is required to see how terms and concepts correlate.

The term "RTuple", or "r-tuple", is chosen to simultaneously distinguish the concept from Haskell tuples while relating it to tuples of the relational model. For the type of either "Record a" or "Set ( Record a )" in Haskell the term "heading" is used in relational theory, and "row type" or "composite type" in SQL. In relational theory the term "scalar" is used to refer to data types that are neither tuples nor relations, which corresponds to everything but "Record a" or "Set ( Record a )" in Haskell. Note also that HaskRel does use the term "table", but then only in the sense of "presentation of a relation value" (see above).

1
SQL and Relational Theory, 2nd ed. (2011), C.J. Date
2
The Third Manifesto, C. J. Date and Hugh Darwen, February 7th, 2013

Synopsis

The relational model of database management: A subset thereof

data Relvar a Source

Relation variable reference. This type has a phantom type variable, which generally calls for the type to be explicity specified:

 s = Relvar "SuppliersPartsDB/S.rv" :: Relvar '[SNO, SName, Status, City]

Constructors

Relvar 

Fields

relvarPath :: FilePath
 

Instances

Typeable [*] a => Show (Relvar a) Source 
(Ord (HList b), Read (HList (RecordValuesR b)), Typeable [*] b, RecordValues b, HMapAux HList TaggedFn (RecordValuesR b) b, HFoldr (Mapcar HPresentTypedRecAttr) [[String]] (RecordValuesR b) [[String]], HFoldr (Mapcar HPresentRecAttr) [[String]] (RecordValuesR b) [[String]]) => HFWPresent (Relvar b) Source 
(Ord (HList b), Read (HList (RecordValuesR b)), RecordValues b, HMapAux HList TaggedFn (RecordValuesR b) b) => RelAssign (Relvar b) Source 
(Ord (HList b), Read (HList (RecordValuesR b)), RecordValues b, HMapAux HList TaggedFn (RecordValuesR b) b) => MonOp (Relvar b) Source 
(Ord (HList b), Read (HList (RecordValuesR b)), RecordValues b, HMapAux HList TaggedFn (RecordValuesR b) b) => DyaOp (IO (Relation a)) (Relvar b) Source 
(Ord (HList b), Read (HList (RecordValuesR b)), RecordValues b, HMapAux HList TaggedFn (RecordValuesR b) b) => DyaOp (Relation a) (Relvar b) Source 
(Ord (HList a), Ord (HList b), Read (HList (RecordValuesR a)), Read (HList (RecordValuesR b)), RecordValues a, RecordValues b, HMapAux HList TaggedFn (RecordValuesR a) a, HMapAux HList TaggedFn (RecordValuesR b) b) => DyaOp (Relvar a) (Relvar b) Source 
(Ord (HList a), Read (HList (RecordValuesR a)), RecordValues a, HMapAux HList TaggedFn (RecordValuesR a) a) => DyaOp (Relvar a) (IO (Relation b)) Source 
(Ord (HList a), Read (HList (RecordValuesR a)), RecordValues a, HMapAux HList TaggedFn (RecordValuesR a) a) => DyaOp (Relvar a) (Relation b) Source 
type RelAssignArg (Relvar b) = Relation b Source 
type DyaOpLeft (Relvar a) = Relation a Source 
type DyaOpLeft (Relvar a) = Relation a Source 
type DyaOpLeft (Relvar a) = Relation a Source 
type DyaOpRight (Relvar b) = Relation b Source 
type DyaOpRight (Relvar b) = Relation b Source 
type DyaOpRight (Relvar b) = Relation b Source 
type MonOpArg (Relvar b) = Relation b Source 
type MonOpRes (Relvar b) res = IO res 
type DyaOpRes (IO (Relation a)) (Relvar b) res = IO res 
type DyaOpRes (Relation a) (Relvar b) res = IO res 
type DyaOpRes (Relvar a) (Relvar b) res = IO res 
type DyaOpRes (Relvar a) (IO (Relation b)) res = IO res 
type DyaOpRes (Relvar a) (Relation b) res = IO res 

relvarType :: Relvar a -> Relation a Source

Gives the type a relvar results in. Note that the value this results in will always be undefined.

readRelvar :: (Ord (HList b), Read (HList (RecordValuesR b)), RecordValues b, HMapAux HList TaggedFn (RecordValuesR b) b) => Relvar b -> IO (Relation b) Source

Read a relation variable from the file referenced by the first argument

Non-relational features