tables-0.1: In-memory storage with multiple keys using lenses and traversals

Portabilitynon-portable
Stabilityexperimental
MaintainerEdward Kmett <ekmett@gmail.com>
Safe HaskellNone

Data.Table

Contents

Description

This module provides tables with multiple indices that support a simple API based on the lenses and traversals from the lens package.

Synopsis

Tables

data Table t whereSource

Every Table has a Primary key and may have Candidate, Supplemental or Inverted keys, plus their variants.

Constructors

EmptyTable :: Table t 
Table :: Tabular t => Tab t (AnIndex t) -> Table t 

Instances

Typeable1 Table 
Foldable Table 
(Functor f, Gettable f) => Contains f (Table t) 
(Functor f, Contains (Accessor (IxValue (Table t))) (Table t), Applicative f) => Ixed f (Table t) 
(Functor f, ~ * (Index (Table a)) (Index (Table b)), Tabular b, Applicative f, ~ * (PKT a) (PKT b)) => Each f (Table a) (Table b) a b 
Eq t => Eq (Table t) 
(Typeable (Table t), Tabular t, Data t) => Data (Table t) 
(Eq (Table t), Ord t) => Ord (Table t) 
(Tabular t, Read t) => Read (Table t) 
Show t => Show (Table t) 
Monoid (Table t) 
Tabular t => At (Table t) 

class Ord (PKT t) => Tabular t whereSource

This class describes how to index a user-defined data type.

Associated Types

type PKT t Source

The primary key type

data Tab t m Source

Used to store indices

data Key k t :: * -> *Source

The type used internally for columns

Methods

fetch :: Key k t a -> t -> aSource

Extract the value of a Key

primary :: Key Primary t (PKT t)Source

Every Table has one Primary Key

primarily :: Key Primary t a -> (a ~ PKT t => r) -> rSource

... and so if you find one, it had better be that one!

mkTab :: Applicative h => (forall k a. IsKeyType k a => Key k t a -> h (i k a)) -> h (Tab t i)Source

Construct a Tab given a function from key to index.

ixTab :: Tab t i -> Key k t a -> i k aSource

Lookup an index in a Tab

forTab :: Applicative h => Tab t i -> (forall k a. IsKeyType k a => Key k t a -> i k a -> h (j k a)) -> h (Tab t j)Source

Loop over each index in a Tab

autoTab :: t -> Maybe (Tab t (AnIndex t) -> t)Source

Adjust a record using meta-information about the table allowing for auto-increments.

Instances

(Ord (PKT (Identity a)), Ord a) => Tabular (Identity a) 
(Ord (PKT (Value a)), Ord a) => Tabular (Value a) 
Ord (PKT (Auto a)) => Tabular (Auto a) 
(Ord (PKT (k, v)), Ord k) => Tabular (k, v)

Simple (key, value) pairs

Table Construction

empty :: Table tSource

Construct an empty relation

singleton :: Tabular t => t -> Table tSource

Construct a relation with a single row

table :: Tabular t => Iso' [t] (Table t)Source

Convert a list to and from a Table.

The real isomorphism laws hold if the original list makes no use of the auto-increment functionality of the table, has no duplicates and is sorted according to the primary key.

However,

from table . tableid

always holds.

fromList :: Tabular t => [t] -> Table tSource

Build up a table from a list

Reading and Writing

null :: Table t -> BoolSource

Check to see if the relation is empty

count :: Table t -> IntSource

Retrieve a row count.

class With q t | q -> t whereSource

Methods

with :: Ord a => q a -> (forall x. Ord x => x -> x -> Bool) -> a -> Lens' (Table t) (Table t)Source

Select a smaller, updateable subset of the rows of a table using an index or an arbitrary function.

deleteWith :: Ord a => q a -> (forall x. Ord x => x -> x -> Bool) -> a -> Table t -> Table tSource

Delete selected rows from a table

deleteWith p cmp a t ≡ set (with p cmp a) empty t

Instances

class Withal q s t | q -> s t whereSource

Search inverted indices

Methods

withAny :: q -> s -> Lens' (Table t) (Table t)Source

withAll :: q -> s -> Lens' (Table t) (Table t)Source

deleteWithAny :: q -> s -> Table t -> Table tSource

deleteWithAll :: q -> s -> Table t -> Table tSource

Instances

Ord a => Withal (t -> [a]) [a] t 
(Eq a, Hashable a) => Withal (Key InvertedHash t (HashSet a)) [a] t 
Withal (Key InvertedInt t IntSet) [Int] t 
Ord a => Withal (Key Inverted t (Set a)) [a] t 

class Group f q t i | q -> t i whereSource

Methods

group :: Ord i => q -> IndexedLensLike' i f (Table t) (Table t)Source

Group by a given key or arbitrary function.

Instances

Applicative f => Group f (t -> a) t a 
(Applicative f, Gettable f) => Group f (Key InvertedHash t (HashSet a)) t a 
(Applicative f, Gettable f, ~ * a Int) => Group f (Key InvertedInt t IntSet) t a 
(Applicative f, Gettable f) => Group f (Key Inverted t (Set a)) t a 
Applicative f => Group f (Key SupplementalHash t a) t a 
(Applicative f, ~ * a Int) => Group f (Key SupplementalInt t a) t a 
Applicative f => Group f (Key Supplemental t a) t a 
Applicative f => Group f (Key CandidateHash t a) t a 
(Applicative f, ~ * a Int) => Group f (Key CandidateInt t a) t a 
Applicative f => Group f (Key Candidate t a) t a 
Applicative f => Group f (Key Primary t a) t a 

insert :: Tabular t => t -> Table t -> Table tSource

Insert a row into a relation, removing collisions.

delete :: t -> Table t -> Table tSource

Delete this row from the database. This will remove any row that collides with the specified row on any primary or candidate key.

rows :: Tabular t => Traversal (Table s) (Table t) s tSource

Traverse all of the rows in a table, potentially changing table types completely.

rows' :: Traversal' (Table t) tSource

Traverse all of the rows in a table without changing any types

Esoterica

data Auto a Source

Constructors

Auto !Int a 

Instances

Functor Auto 
Typeable1 Auto 
Foldable Auto 
Traversable Auto 
Comonad Auto 
FunctorWithIndex Int Auto 
FoldableWithIndex Int Auto 
TraversableWithIndex Int Auto 
(Indexable Int p, ~ (* -> * -> *) q (->), Functor f) => HasValue p q f (Auto a) (Auto b) a b 
(Functor f, ~ * (Index (Auto a)) (Index (Auto b)), ~ * a Int, ~ * b Int, Applicative f) => Each f (Auto a) (Auto b) a b 
Eq a => Eq (Auto a) 
(Typeable (Auto a), Data a) => Data (Auto a) 
(Eq (Auto a), Ord a) => Ord (Auto a) 
Read a => Read (Auto a) 
Show a => Show (Auto a) 
Ord (PKT (Auto a)) => Tabular (Auto a) 
Field1 (Auto a) (Auto a) Int Int 
Field2 (Auto a) (Auto b) a b 

auto :: a -> Auto aSource

Generate a row with an auto-incremented key

autoIncrement :: (Tabular t, PKT t ~ Int) => ALens' t Int -> t -> Maybe (Tab t (AnIndex t) -> t)Source

This lets you define autoKey to increment to 1 greater than the existing maximum key in a table.

In order to support this you need a numeric primary key, and the ability to update the primary key in a record, indicated by a lens to the field.

To enable auto-increment for a table with primary key primaryKeyField, set:

autoKey = autoIncrement primaryKeyField

Implementation Details

data Primary Source

Type level key types

Instances

Ord a => IsKeyType Primary a 
Applicative f => Group f (Key Primary t a) t a 
With (Key Primary t) t 

data Candidate Source

Instances

data CandidateInt Source

Instances

~ * a Int => IsKeyType CandidateInt a 
(Applicative f, ~ * a Int) => Group f (Key CandidateInt t a) t a 
With (Key CandidateInt t) t 

data SupplementalInt Source

Instances

data Inverted Source

Instances

Ord a => IsKeyType Inverted (Set a) 
(Applicative f, Gettable f) => Group f (Key Inverted t (Set a)) t a 
Ord a => Withal (Key Inverted t (Set a)) [a] t 

data InvertedHash Source

Instances

(Eq a, Hashable a) => IsKeyType InvertedHash (HashSet a) 
(Applicative f, Gettable f) => Group f (Key InvertedHash t (HashSet a)) t a 
(Eq a, Hashable a) => Withal (Key InvertedHash t (HashSet a)) [a] t 

data AnIndex t k a whereSource

This is used to store a single index.