Safe Haskell | Safe-Inferred |
---|
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.
- type MS = MaybeT STM
- class Binary u => Multitude u
- data Single
- data Multiple
- data Table r t a
- data Key t a i u
- data TableVarU t a u
- type TableVar t a = TableVarU t a Single
- type TableVars t a = TableVarU t a Multiple
- fromList :: [TableVar t a] -> TableVars t a
- toList :: TableVars t a -> [TableVar t a]
- readVar :: Table r t a -> TableVar t a -> MS a
- readRefs :: Table r t a -> TableVar t a -> MS (r TableVarU)
- data Spec r k a = Spec {}
- data TableRef t a u
- class ToRefBase tbl => ToRef tbl where
- class RefsC r
- data Refs f = Refs
- class RefsComponent r
- newtype Ref t a u f = R (f t a u)
- data (rs :&: r) f = (rs f) :&: (r f)
- splitRef :: (rs :&: Ref t a u) f -> (rs f, f t a u)
- data KeySpec r a i u
- single :: (a -> i) -> KeySpec r a i Single
- multiple :: (a -> i) -> KeySpec r a i Multiple
- single_ :: (a -> r TableVarU -> i) -> KeySpec r a i Single
- multiple_ :: (a -> r TableVarU -> i) -> KeySpec r a i Multiple
- class KeysC k
- data Keys f = Keys
- class KeysComponent k
- newtype KeyRef i u f = K (f i u)
- data (ks :+: k) f = (ks f) :+: (k f)
- splitKey :: (ks :+: KeyRef i u) f -> (ks f, f i u)
- data Created r k a where
- createTable :: (KeysC k, RefsC r) => Spec r k a -> STM (Created r k a)
- select :: Ord i => Key t a i Single -> i -> MS (TableVar t a)
- select_ :: (Multitude u, Ord i) => Key t a i u -> i -> (forall o. Ord o => o -> o -> Bool) -> STM [TableVar t a]
- selectBetween :: (Multitude u, Ord i) => Key t a i u -> i -> Bool -> i -> Bool -> STM [TableVar t a]
- nullVar :: TableVar t a
- insert :: Table r t a -> a -> r TableVarU -> MS (TableVar t a)
- update :: Table r t a -> TableVar t a -> a -> MS ()
- update_ :: Table r t a -> TableVar t a -> a -> r TableVarU -> MS ()
- delete :: Table r t a -> TableVar t a -> MS ()
- getTable :: Binary a => Table t r a -> Get (STM ())
- getTable_ :: Get a -> Table t r a -> Get (STM ())
- getTable__ :: (Monad m, MonadSTM m) => Get (m a) -> Table t r a -> Get (m ())
- putTable :: Binary a => Table t r a -> STM Put
- putTable_ :: (a -> Put) -> Table t r a -> STM Put
- putTable__ :: (Monad m, MonadSTM m) => (a -> m Put) -> Table t r a -> m Put
- data Token t a = Token
- data Tokens = Tokens
- data tps :*: tp = tps :*: tp
- class TokensC toks
- class IsToken t
- data Specs toks tbls where
- data Tables = Tables
- class TablesC tbls
- data TableData r k t a = T (Table r t a) (k (Key t a))
- class IsTableData tbl
- class CreateTables crts
- data Exists toks z where
- newtype (crts :**: a) toks z = C (forall t. crts (toks :*: Token t a) z)
- createTables :: CreateTables crts => crts Tokens z -> STM z
Documentation
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.
This type specifies that we want a single value.
This type specifies that we want multiple values.
Main structures
Abstract type, which represents a collection of values of type a
,
possibly accompanied with some references to other Table
s.
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.
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
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
.
readRefs :: Table r t a -> TableVar t a -> MS (r TableVarU)Source
Function that reads all references accompanying the value.
Specifications
Type of table specifications.
Foreign table references
Type that is a template for references to another table. Used only in Spec
s.
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.
Empty reference specification. It doesn't specify any reference whatsoever.
class RefsComponent r Source
Class of the part of reference specification, corresponding to one reference.
Multitude u => RefsComponent (Ref t a u) |
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.
R (f t a u) |
Multitude u => RefsComponent (Ref t a u) |
Combining operator for reference specifications.
(rs f) :&: (r f) |
(RefsC rs, RefsComponent r) => RefsC (:&: rs r) |
Keys
Type that is a template for the key. Used only in Spec
s.
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 KeysComponent k Source
Class of the part of key specification, corresponding to one key.
(Multitude u, Ord i) => KeysComponent (KeyRef i u) |
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.
K (f i u) |
(Multitude u, Ord i) => KeysComponent (KeyRef i u) |
Combining operator for key specifications.
(ks f) :+: (k f) |
(KeysC ks, KeysComponent k) => KeysC (:+: ks k) |
Table manipulation
data Created r k a whereSource
Output of the createTable
function. Contains the created table and the keys to it.
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_ :: (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]
:: (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.
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 -> 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.
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.
Recursive tables
Combining operator for tokens or tables sets.
tps :*: tp |
Class of token sets, used primarily in the argument of createTables
function.
Class of tables sets, used primarily in the argument of createTables
function.
Table, paired with keys to it
IsTableData (TableData r k t a) |
class CreateTables crts Source
Class of the data used to generate Spec
s
for tables that need to reference each other.
CreateTables Exists | |
CreateTables crts => CreateTables (:**: crts a) |
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.
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.