{-# LANGUAGE OverloadedStrings #-}
module Hydra.Sources.Tier4.Langs.RelationalModel where
import Hydra.Sources.Tier3.All
import Hydra.Dsl.Annotations
import Hydra.Dsl.Bootstrap
import Hydra.Dsl.Types as Types
relationalModelModule :: Module
relationalModelModule :: Module
relationalModelModule = Namespace
-> [Element] -> [Module] -> [Module] -> Maybe [Char] -> Module
Module Namespace
ns [Element]
elements [Module
hydraCoreModule] [Module]
tier0Modules (Maybe [Char] -> Module) -> Maybe [Char] -> Module
forall a b. (a -> b) -> a -> b
$
[Char] -> Maybe [Char]
forall a. a -> Maybe a
Just ([Char]
"An interpretation of Codd's Relational Model, " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++
[Char]
"as described in 'A Relational Model of Data for Large Shared Data Banks' (1970). " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++
[Char]
"Types ('domains') and values are parameterized so as to allow for application-specific implementations. " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++
[Char]
"No special support is provided for 'nonsimple' domains; i.e. relations are assumed to be normalized.")
where
ns :: Namespace
ns = [Char] -> Namespace
Namespace [Char]
"hydra/langs/relationalModel"
def :: [Char] -> Type -> Element
def = Namespace -> [Char] -> Type -> Element
datatype Namespace
ns
rm :: [Char] -> Type
rm = Namespace -> [Char] -> Type
typeref Namespace
ns
elements :: [Element]
elements = [
[Char] -> Type -> Element
def [Char]
"ColumnName" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
[Char] -> Type -> Type
doc [Char]
"A name for a domain which serves to identify the role played by that domain in the given relation; a 'role name' in Codd"
Type
string,
[Char] -> Type -> Element
def [Char]
"ColumnSchema" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
[Char] -> Type -> Type
doc [Char]
"An abstract specification of the domain represented by a column in a relation; a role" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[Char] -> Type -> Type
lambda [Char]
"t" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ [FieldType] -> Type
record [
[Char]
"name"[Char] -> Type -> FieldType
>:
[Char] -> Type -> Type
doc [Char]
"A unique name for the column" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[Char] -> Type
rm [Char]
"ColumnName",
[Char]
"domain"[Char] -> Type -> FieldType
>:
[Char] -> Type -> Type
doc [Char]
"The domain (type) of the column" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
Type
"t",
[Char]
"isPrimaryKey"[Char] -> Type -> FieldType
>:
[Char] -> Type -> Type
doc [Char]
"Whether this column represents the primary key of its relation"
Type
boolean],
[Char] -> Type -> Element
def [Char]
"ForeignKey" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
[Char] -> Type -> Type
doc [Char]
"A mapping from certain columns of a source relation to primary key columns of a target relation" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[FieldType] -> Type
record [
[Char]
"foreignRelation"[Char] -> Type -> FieldType
>:
[Char] -> Type -> Type
doc [Char]
"The name of the target relation" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[Char] -> Type
rm [Char]
"RelationName",
[Char]
"keys"[Char] -> Type -> FieldType
>:
Type -> Type -> Type
Types.map ([Char] -> Type
rm [Char]
"ColumnName") ([Char] -> Type
rm [Char]
"ColumnName")],
[Char] -> Type -> Element
def [Char]
"PrimaryKey" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
[Char] -> Type -> Type
doc [Char]
"A primary key of a relation, specified either as a single column, or as a list of columns" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
Type -> Type
list (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ [Char] -> Type
rm [Char]
"ColumnName",
[Char] -> Type -> Element
def [Char]
"Relation" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
[Char] -> Type -> Type
doc [Char]
"A set of distinct n-tuples; a table" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[Char] -> Type -> Type
lambda [Char]
"v" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ Type -> Type
set (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ Type -> Type
list Type
"v",
[Char] -> Type -> Element
def [Char]
"RelationName" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
[Char] -> Type -> Type
doc [Char]
"A unique relation (table) name"
Type
string,
[Char] -> Type -> Element
def [Char]
"RelationSchema" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
[Char] -> Type -> Type
doc [Char]
"An abstract relation; the name and columns of a relation without its actual data" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[Char] -> Type -> Type
lambda [Char]
"t" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ [FieldType] -> Type
record [
[Char]
"name"[Char] -> Type -> FieldType
>:
[Char] -> Type -> Type
doc [Char]
"A unique name for the relation" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[Char] -> Type
rm [Char]
"RelationName",
[Char]
"columns"[Char] -> Type -> FieldType
>:
[Char] -> Type -> Type
doc [Char]
"A list of column specifications" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
Type -> Type
list (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ [Char] -> Type
rm [Char]
"ColumnSchema" Type -> Type -> Type
@@ Type
"t",
[Char]
"primaryKeys"[Char] -> Type -> FieldType
>:
[Char] -> Type -> Type
doc [Char]
"Any number of primary keys for the relation, each of which must be valid for this relation" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
Type -> Type
list (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ [Char] -> Type
rm [Char]
"PrimaryKey",
[Char]
"foreignKeys"[Char] -> Type -> FieldType
>:
[Char] -> Type -> Type
doc [Char]
"Any number of foreign keys, each of which must be valid for both this relation and the target relation" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
Type -> Type
list (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ [Char] -> Type
rm [Char]
"ForeignKey"],
[Char] -> Type -> Element
def [Char]
"Relationship" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
[Char] -> Type -> Type
doc [Char]
"A domain-unordered (string-indexed, rather than position-indexed) relation" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[Char] -> Type -> Type
lambda [Char]
"v" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ Type -> Type
set (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ Type -> Type -> Type
Types.map ([Char] -> Type
rm [Char]
"ColumnName") Type
"v",
[Char] -> Type -> Element
def [Char]
"Row" (Type -> Element) -> Type -> Element
forall a b. (a -> b) -> a -> b
$
[Char] -> Type -> Type
doc [Char]
"An n-tuple which is an element of a given relation" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
[Char] -> Type -> Type
lambda [Char]
"v" (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ Type -> Type
list Type
"v"]