tables-0.4: 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 
Eq t => Eq (Table t) 
(Tabular t, Data t) => Data (Table t) 
Ord t => Ord (Table t) 
(Tabular t, Read t) => Read (Table t) 
Show t => Show (Table t) 
Monoid (Table t) 
(Tabular t, Binary t) => Binary (Table t) 
(Tabular t, Serialize t) => Serialize (Table t) 
(Tabular a, NFData a, NFData (Tab a (AnIndex a))) => NFData (Table a) 
Ixed (Table t) 
Tabular t => At (Table t) 
(Typeable t, Tabular t, SafeCopy t) => SafeCopy (Table t) 
(Tabular b, ~ * (PKT a) (PKT b)) => Each (Table a) (Table b) a b 

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 a => Tabular (Identity a) 
Tabular (Auto a) 
Ord k => Tabular (k, v)

Simple (key, value) pairs

Template Haskell helpers

makeTabular :: Name -> [(Name, Name)] -> Q [Dec]Source

Generate a Tabular instance for a data type. Currently, this only works for types which have no type variables, and won't generate autoTab.

 data Foo = Foo { fooId :: Int, fooBar :: String, fooBaz :: Double }

makeTabular 'fooId [(''Candidate, 'fooBaz), (''Supplemental, 'fooBar)]

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

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

Build up a table from a list, without checking for collisions

Combining Tables

union :: Table t -> Table t -> Table tSource

Left-biased union of the two tables

This is a synonym for mappend

difference :: (Tabular t1, Tabular t2, PKT t1 ~ PKT t2) => Table t1 -> Table t2 -> Table t1Source

Return the elements of the first table that do not share a key with an element of the second table

intersection :: (Tabular t1, Tabular t2, PKT t1 ~ PKT t2) => Table t1 -> Table t2 -> Table t1Source

Return the elements of the first table that share a key with an element of the second table

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.

insert' :: Tabular t => t -> Table t -> (t, Table t)Source

Insert a row into a relation, removing collisions.

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

Insert a row into a relation, ignoring 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, PKT s ~ PKT t) => IndexedTraversal (PKT s) (Table s) (Table t) s tSource

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

Key Types

Primary Keys

data Primary Source

The key type for the canonical, unique identifier attached to every row. There should only be one Primary key.

Instances

Ord a => IsKeyType Primary a 
Applicative f => Group f (Key Primary t a) t a 
With (Key Primary t) t 
(NFData t, NFData a, NFData (PKT t)) => NFData (AnIndex t Primary a) 

Candidate Keys

data Candidate Source

A key type for values unique to each row, but that are not Primary.

Instances

Ord a => IsKeyType Candidate a 
Applicative f => Group f (Key Candidate t a) t a 
With (Key Candidate t) t 
(NFData t, NFData a, NFData (PKT t)) => NFData (AnIndex t Candidate a) 

data CandidateInt Source

CandidateInt keys are like Candidate keys but are backed by an IntMap rather than a Map. This makes them more performant, but values at CandidateInt keys may only be Ints.

Instances

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

data CandidateHash Source

CandidateHash keys are like Candidate keys but are backed by a HashMap rather than a Map. This makes them more performant on (==) and (/=) lookups, but values at CandidateHash keys must be instances of Hashable and Eq.

Supplemental Keys

data Supplemental Source

A key type for supplemental data attached to each row that we still may want to index by. Values need not be unique.

Instances

data SupplementalInt Source

SupplementalInt keys are like Supplemental keys but are backed by an IntMap rather than a Map. This makes them more performant, but values at SupplementalInt keys may only be Ints.

Instances

data SupplementalHash Source

SupplementalHash keys are like Supplemental keys but are backed by a HashMap rather than a Map. This makes them more performant on (==) and (/=) lookups, but values at SupplementalHash keys must be instances of Hashable and Eq.

Inverted Keys

data Inverted Source

A key type for inverse keys.

Instances

(~ (* -> *) t Set, Ord a) => IsKeyType Inverted (t a) 
(Applicative f, Gettable f) => Group f (Key Inverted t (Set a)) t a 
(NFData t, NFData a, NFData (PKT t)) => NFData (AnIndex t Inverted (Set a)) 
Ord a => Withal (Key Inverted t (Set a)) [a] t 

data InvertedHash Source

Instances

(~ (* -> *) t HashSet, Eq a, Hashable a) => IsKeyType InvertedHash (t a) 
(Applicative f, Gettable f) => Group f (Key InvertedHash t (HashSet a)) t a 
(NFData t, NFData a, NFData (PKT t)) => NFData (AnIndex t InvertedHash (HashSet a)) 
(Eq a, Hashable a) => Withal (Key InvertedHash t (HashSet a)) [a] t 

Esoterica

data Auto a Source

Constructors

Auto !Int a 

Instances

auto :: a -> Auto aSource

Generate a row with an auto-incremented key

autoIncrement :: (Tabular t, Num (PKT t)) => ALens' t (PKT t) -> 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:

autoTab = autoIncrement primaryKeyField

Implementation Details

class IsKeyType k a whereSource

Methods

keyType :: Key k t a -> KeyType k aSource

data AnIndex t k a whereSource

This is used to store a single index.