hmemdb-0.4.0.0: In-memory relational database

Safe HaskellSafe-Inferred

Data.HMemDb

Contents

Description

Tables of values and keys for that tables.

Each value in the table may be accompanied with references to other tables.

= Usage

Each table is just an unordered collection of values.

== Simple values

Suppose we want to keep a collection of values of some type T. We should use a very simple specification to create a table:

 createTable (Spec Refs Keys :: Spec Refs Keys T)

Here we have to specify the type T, as otherwise Haskell would have no way of knowing what type to use. Generally it's not really needed.

== Keys

Of course, just keeping a collection of values is not very useful. Let's say a company wants to keep a table of it's employees, looking for information about them by their id numbers or names. Id number is unique, while the names could probably coincide.

 data Employee = Employee {empId :: Int, empName :: String}
 cEmps <- createTable $ Spec Refs (Keys :+: K (single empId) :+: K (multiple empName))
 case cEmps of
   Created employees (Keys :+: K idKey :+: K nameKey) -> ...

Here employees would be the table of employees itself, idKey would be the key that can be used to look up an employee by the id, and nameKey would be the key that can be used to look up an employee by the name.

select function can do the looking up by id part.

 ceoVar <- select idKey 0
 ceo <- readVar employees ceoVar

For multiple values the function select_ should be used instead.

 workersNamedDaniel <- select_ nameKey "Daniel" (==)
 mapM (\workerVar -> runMaybeT $ readVar employees workerVar) workersNamedDaniel

We can also use other comparison operators, like

 workersFromZ <- select_ nameKey "Z" (<=)

for selecting all workers whose names satisfy the inequality "Z" <= name.

== References

Tables can reference other tables, created before. For example, assume that we have a set of departments and a set of employees, and each of employees can be in one of the departments. We shouldn't keep that information inside the Employee data type (as it is quite changeable); instead we keep a reference into the departments table along with the Employee value in the employees table

 cDepts <- createTable $ ...
 case cDepts of
   Created departments ... ->
     do cEmps <- case createTable $ Spec (Refs :&: R (only departments)) (Keys ...)
        case cEmps of
          Created employees (Keys ...) -> ...

Given the TableVar we can find out the references associated with it:

 Refs :&: R deptVar <- readRefs employees ceoVar
 dept <- readVar departments deptVar

References can also be used as keys, if they are unique:

 createTable $ Spec (...) (Keys :+: K (single_ (\_ (Refs :&: deptVar) -> deptVar)))

== Circular references

It's possible to have tables referencing each other, but that requires some finesse. Suppose that each department has a manager. Again, we don't keep that information in the Department data type itself, but we want to keep a reference along the value in the table.

First of all, we need to create a data type that keeps both tables inside.

 data Company where
   Company
     :: Table (Refs :&: Ref d Department Single) e Employee ->
        Table (Refs :&: Ref e Employee Single) d Department ->
        Company

Then we make specifications from table tokens (tables aren't created yet):

 makeSpecs (Tokens :*: tE :*: tD) =
   Specs :&&: Spec (Refs :&: R (only tD)) Keys :&&: Spec (Refs :&: R (only tE)) Keys

and make the final result (the Company type) from the tables:

 generate (Tables :*: T employees Keys :*: T departments Keys) =
   return $ Company employees departments

All that should be launched by the createTables function:

 company <- createTables $ C $ C $ Exists makeSpecs generate
 case company of
   Company employees departments -> ...

Here we should use two C constructors to indicate that we are creating two tables.

Synopsis

Documentation

type MS = MaybeT STMSource

STM that can fail. Note that it doesn't revert the transaction on failure.

class Binary u => Multitude u Source

Closed class. It's instances allow us to choose whether we want to get a single value or multiple ones.

data Single Source

This type specifies that we want a single value.

data Multiple Source

This type specifies that we want multiple values.

Main structures

data Table r t a Source

Abstract type, which represents a collection of values of type a, possibly accompanied with some references to other Tables. The type t is an abstract type, used to ensure that we don't confuse different tables with values of the same type. r is a type of references accompanying each value.

Instances

ToRef (Table r) 

data Key t a i u Source

Abstract type, which allows us to select one or many values from the Table. Type t is an abstract type, same as in the Table. Type a is a type of values, also same as in the Table. Type i is a type of index values, used by this key. Type u is either Multiple or Single, depending on whether this key allows different values to have the same index, or not.

Value references

data TableVarU t a u Source

Base type for TableVar and TableVars Type t is an abstract type, same as in the Table. Type a is a type of value, which can be obtained with unVar, also same as in the Table.

Instances

Eq u => Eq (TableVarU t a u) 
Ord u => Ord (TableVarU t a u) 

type TableVar t a = TableVarU t a SingleSource

Reference to a single value in some table.

type TableVars t a = TableVarU t a MultipleSource

Reference to multiple values in a single table.

fromList :: [TableVar t a] -> TableVars t aSource

Function that converts a list of single-value references to a single multiple-value reference. Normally it should only be used in cInsert statments.

toList :: TableVars t a -> [TableVar t a]Source

Function that converts a multiple-value reference to a list of single-value references. Should be used with multiple-value references accompanying values in the Table.

readVar :: Table r t a -> TableVar t a -> MS aSource

Function that dereferences a value from table. Note that we have to provide the Table along with TableVar.

readRefs :: Table r t a -> TableVar t a -> MS (r TableVarU)Source

Function that reads all references accompanying the value.

Specifications

data Spec r k a Source

Type of table specifications.

Constructors

Spec 

Fields

sRefs :: r TableRef

Other tables that should be referenced by values of this one.

sKeys :: k (KeySpec r a)

Keys for the table-to-be

Foreign table references

data TableRef t a u Source

Type that is a template for references to another table. Used only in Specs. Type t is an abstract type, same as in the Table. Type a is a type of values in that Table. Type u is either Single or Multiple, depending on whether the reference, accompanying the value, should be single-value or multiple-value

class ToRefBase tbl => ToRef tbl whereSource

Class of things you can reference. Normally that would be only tables, but you can use tokens as substitutes.

Methods

only :: tbl t a -> TableRef t a SingleSource

Each value in the table-to-be should be accompanied with a single-value reference.

some :: tbl t a -> TableRef t a MultipleSource

Each value in the table-to-be should be accompanied with a multiple-value reference.

Instances

class RefsC r Source

Class of table reference specifications, used in the sRefs field of the Spec.

Instances

RefsC Refs 
(RefsC rs, RefsComponent r) => RefsC (:&: rs r) 

data Refs f Source

Empty reference specification. It doesn't specify any reference whatsoever.

Constructors

Refs 

Instances

class RefsComponent r Source

Class of the part of reference specification, corresponding to one reference.

Instances

Multitude u => RefsComponent (Ref t a u) 

newtype Ref t a u f Source

One table reference specification. Note that it can't be used in the sRefs field by itself, but rather should be combined with Refs with the :&: operator.

Constructors

R (f t a u) 

Instances

Multitude u => RefsComponent (Ref t a u) 

data (rs :&: r) f Source

Combining operator for reference specifications.

Constructors

(rs f) :&: (r f) 

Instances

(RefsC rs, RefsComponent r) => RefsC (:&: rs r) 

splitRef :: (rs :&: Ref t a u) f -> (rs f, f t a u)Source

Splitting references.

Keys

data KeySpec r a i u Source

Type that is a template for the key. Used only in Specs. Type t is an abstract type, same as in the Table. Type a is a type of values in that Table. Type i is a type of index values, used by this key. Type u is either Multiple or Single, depending on whether this key allows different values to have the same index, or not.

single :: (a -> i) -> KeySpec r a i SingleSource

This key will provide access to a single value within a Table. It's index will be calculated, based on this value alone.

multiple :: (a -> i) -> KeySpec r a i MultipleSource

This key will provide access to multiple values in the same Table. Their indices will be calculated based on the value alone.

single_ :: (a -> r TableVarU -> i) -> KeySpec r a i SingleSource

This is a more generic version of single. The difference is that value index will be calculated based on both the value and it's accompanying references.

multiple_ :: (a -> r TableVarU -> i) -> KeySpec r a i MultipleSource

This is a more generic version of multiple. The difference is that value index will be calculated based on both the value and it's accompanying references.

class KeysC k Source

Class of key specifications, used in the sKeys field of the Spec.

Instances

KeysC Keys 
(KeysC ks, KeysComponent k) => KeysC (:+: ks k) 

data Keys f Source

Empty key specification. It doesn't specify any key whatsoever.

Constructors

Keys 

Instances

class KeysComponent k Source

Class of the part of key specification, corresponding to one key.

Instances

(Multitude u, Ord i) => KeysComponent (KeyRef i u) 

newtype KeyRef i u f Source

One key specification. Note that it can't be used in the sKeys field by itself, but rather should be combined with Keys with the :+: operator.

Constructors

K (f i u) 

Instances

(Multitude u, Ord i) => KeysComponent (KeyRef i u) 

data (ks :+: k) f Source

Combining operator for key specifications.

Constructors

(ks f) :+: (k f) 

Instances

(KeysC ks, KeysComponent k) => KeysC (:+: ks k) 

splitKey :: (ks :+: KeyRef i u) f -> (ks f, f i u)Source

Splitting keys.

Table manipulation

data Created r k a whereSource

Output of the createTable function. Contains the created table and the keys to it.

Constructors

Created :: Table r t a -> k (Key t a) -> Created r k a 

createTable :: (KeysC k, RefsC r) => Spec r k a -> STM (Created r k a)Source

Function that creates the table (along with keys and everything) based on a Spec.

select :: Ord i => Key t a i Single -> i -> MS (TableVar t a)Source

Function that selects one value from a Key. Note that the value is not returned directly. Instead, a reference to it is returned, which allows to get other references, accompanying that value in the Table.

select_ :: (Multitude u, Ord i) => Key t a i u -> i -> (forall o. Ord o => o -> o -> Bool) -> STM [TableVar t a]Source

A more generic version of select. Instead of one value, it returns multiple ones. It can also select values with indices that are smaller or greater to the provided one, depending on the third argument, which could be anything like (>), (<=), (/=), or even return True.

 select_ k i (==) ~~ [select k i]

selectBetweenSource

Arguments

:: (Multitude u, Ord i) 
=> Key t a i u 
-> i

lower bound

-> Bool

including lower bound?

-> i

upper bound

-> Bool

including upper bound?

-> STM [TableVar t a] 

A variant of select_, which allows to choose two bounds for the index. Additional boolean arguments show whether to include bounds themselves or not.

nullVar :: TableVar t aSource

An invalid reference to any table. Dereferencing it always fails.

insert :: Table r t a -> a -> r TableVarU -> MS (TableVar t a)Source

Function that lets one to insert a new value to the Table. Of course, we have to provide accompanying references as well. This function can fail if some key clashes with an already existing one.

update :: Table r t a -> TableVar t a -> a -> MS ()Source

Function that writes another value to the referenced place in the Table. It doesn't change the accompanying references. In case that it fails due to some single-value key prohibiting the new value, nothing is changed, and the Table remains the same.

update_ :: Table r t a -> TableVar t a -> a -> r TableVarU -> MS ()Source

More generic version of update. It allows changing accompanying references as well as the value.

delete :: Table r t a -> TableVar t a -> MS ()Source

Function that removes the value (along with accompanying references) from the Table. It only fails if the value was already removed.

Persistence

getTable :: Binary a => Table t r a -> Get (STM ())Source

Function that makes it possible to read the table from the file or other source. Table should be created beforehand, as specifications are not serializable.

getTable_ :: Get a -> Table t r a -> Get (STM ())Source

More generic version of getTable that allows to change the way values are serialized.

getTable__ :: (Monad m, MonadSTM m) => Get (m a) -> Table t r a -> Get (m ())Source

The most generic version of getTable. Not only it allows to change the way values are serialized, it also permits side-effects during the deserialization. The table is still filled in one STM transaction, thus avoiding any difficulties with multithreading.

putTable :: Binary a => Table t r a -> STM PutSource

Function that makes it possible to write the table to the file or other storage.

putTable_ :: (a -> Put) -> Table t r a -> STM PutSource

More generic version of putTable that allows to change the way values are serialized.

putTable__ :: (Monad m, MonadSTM m) => (a -> m Put) -> Table t r a -> m PutSource

The most generic version of putTable. Not only it allows to change the way values are serialized, it also permits side-effects during the serialization. The table is still read in one STM transaction, thus avoiding any difficulties with multithreading.

Recursive tables

data Token t a Source

Type that can be used as a substitute for Table in only and some functions.

Constructors

Token 

Instances

data Tokens Source

Empty tokens set.

Constructors

Tokens 

Instances

data tps :*: tp Source

Combining operator for tokens or tables sets.

Constructors

tps :*: tp 

Instances

(IsTableData tbl, TablesC tbls) => TablesC (:*: tbls tbl) 
(IsToken t, TokensC toks) => TokensC (:*: toks t) 

class TokensC toks Source

Class of token sets, used primarily in the argument of createTables function.

Instances

TokensC Tokens 
(IsToken t, TokensC toks) => TokensC (:*: toks t) 

class IsToken t Source

Class of Tokens

Instances

IsToken (Token t a) 

data Specs toks tbls whereSource

Set of specs, of the same size as given sets of tokens and tables.

Constructors

Specs :: Specs Tokens Tables 
:&&: :: (KeysC k, RefsC r, TokensC toks) => Specs toks tbls -> Spec r k a -> Specs (toks :*: Token t a) (tbls :*: TableData r k t a) 

data Tables Source

Empty tables set.

Constructors

Tables 

Instances

class TablesC tbls Source

Class of tables sets, used primarily in the argument of createTables function.

Instances

TablesC Tables 
(IsTableData tbl, TablesC tbls) => TablesC (:*: tbls tbl) 

data TableData r k t a Source

Table, paired with keys to it

Constructors

T (Table r t a) (k (Key t a)) 

Instances

class IsTableData tbl Source

Class of all TableDatas

Instances

class CreateTables crts Source

Class of the data used to generate Specs for tables that need to reference each other.

Instances

data Exists toks z whereSource

Data type that hides references and keys specifications inside.

Constructors

Exists :: TablesC tbls => (toks -> Specs toks tbls) -> (tbls -> STM z) -> Exists toks z 

Instances

newtype (crts :**: a) toks z Source

Data type that quantifies universally over the table types. It should be applied as many times as there are tables being created.

Constructors

C (forall t. crts (toks :*: Token t a) z) 

Instances

CreateTables crts => CreateTables (:**: crts a) 

createTables :: CreateTables crts => crts Tokens z -> STM zSource

Function that actually creates multiple tables, possibly referencing each other, at once.