| Portability | non-portable |
|---|---|
| Stability | experimental |
| Maintainer | Edward Kmett <ekmett@gmail.com> |
| Safe Haskell | None |
Data.Table
Description
This module provides tables with multiple indices that support a simple
API based on the lenses and traversals from the lens package.
- data Table t where
- class Ord (PKT t) => Tabular t where
- type PKT t
- data Tab t m
- data Key k t :: * -> *
- fetch :: Key k t a -> t -> a
- primary :: Key Primary t (PKT t)
- primarily :: Key Primary t a -> (a ~ PKT t => r) -> r
- mkTab :: Applicative h => (forall k a. IsKeyType k a => Key k t a -> h (i k a)) -> h (Tab t i)
- ixTab :: Tab t i -> Key k t a -> i k a
- 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)
- autoTab :: t -> Maybe (Tab t (AnIndex t) -> t)
- empty :: Table t
- singleton :: Tabular t => t -> Table t
- table :: Tabular t => Iso' [t] (Table t)
- fromList :: Tabular t => [t] -> Table t
- null :: Table t -> Bool
- count :: Table t -> Int
- class With q t | q -> t where
- class Withal q s t | q -> s t where
- class Group f q t i | q -> t i where
- group :: Ord i => q -> IndexedLensLike' i f (Table t) (Table t)
- insert :: Tabular t => t -> Table t -> Table t
- insert' :: Tabular t => t -> Table t -> (t, Table t)
- delete :: t -> Table t -> Table t
- rows :: Tabular t => Traversal (Table s) (Table t) s t
- rows' :: Traversal' (Table t) t
- data Auto a = Auto !Int a
- autoKey :: Lens' (Auto a) Int
- auto :: a -> Auto a
- autoIncrement :: (Tabular t, Num (PKT t)) => ALens' t (PKT t) -> t -> Maybe (Tab t (AnIndex t) -> t)
- class IsKeyType k a where
- data KeyType t a where
- Primary :: Ord a => KeyType Primary a
- Candidate :: Ord a => KeyType Candidate a
- CandidateInt :: KeyType CandidateInt Int
- CandidateHash :: (Eq a, Hashable a) => KeyType CandidateHash a
- Supplemental :: Ord a => KeyType Supplemental a
- SupplementalInt :: KeyType SupplementalInt Int
- SupplementalHash :: (Eq a, Hashable a) => KeyType SupplementalHash a
- Inverted :: Ord a => KeyType Inverted (Set a)
- InvertedInt :: KeyType InvertedInt IntSet
- InvertedHash :: (Eq a, Hashable a) => KeyType InvertedHash (HashSet a)
- data Primary
- data Candidate
- data CandidateInt
- data CandidateHash
- data Supplemental
- data SupplementalInt
- data SupplementalHash
- data Inverted
- data InvertedInt
- data InvertedHash
- data AnIndex t k a where
- PrimaryMap :: Map (PKT t) t -> AnIndex t Primary a
- CandidateIntMap :: IntMap t -> AnIndex t CandidateInt Int
- CandidateHashMap :: (Eq a, Hashable a) => HashMap a t -> AnIndex t CandidateHash a
- CandidateMap :: Ord a => Map a t -> AnIndex t Candidate a
- InvertedIntMap :: IntMap [t] -> AnIndex t InvertedInt IntSet
- InvertedHashMap :: (Eq a, Hashable a) => HashMap a [t] -> AnIndex t InvertedHash (HashSet a)
- InvertedMap :: Ord a => Map a [t] -> AnIndex t Inverted (Set a)
- SupplementalIntMap :: IntMap [t] -> AnIndex t SupplementalInt Int
- SupplementalHashMap :: (Eq a, Hashable a) => HashMap a [t] -> AnIndex t SupplementalHash a
- SupplementalMap :: Ord a => Map a [t] -> AnIndex t Supplemental a
Tables
Every Table has a Primary key and may have Candidate,
Supplemental or Inverted keys, plus their variants.
Instances
| Typeable1 Table | |
| Foldable Table | |
| Gettable f => Contains f (Table t) | |
| Applicative f => Ixed f (Table t) | |
| (Tabular b, Applicative f, ~ * (PKT a) (PKT b)) => Each f (Table a) (Table b) a b | |
| 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 t => At (Table t) | |
| (Typeable t, Tabular t, SafeCopy t) => SafeCopy (Table t) |
class Ord (PKT t) => Tabular t whereSource
This class describes how to index a user-defined data type.
Associated Types
The primary key type
Used to store indices
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
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.
Table Construction
Reading and Writing
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
deleteWithp cmp a t ≡set(withp cmp a)emptyt
Instances
| With ((->) t) t | |
| With (Key SupplementalHash t) t | |
| With (Key SupplementalInt t) t | |
| With (Key Supplemental t) t | |
| With (Key CandidateHash t) t | |
| With (Key CandidateInt t) t | |
| With (Key Candidate t) t | |
| With (Key Primary t) t |
class Withal q s t | q -> s t whereSource
Search inverted indices
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.
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
Instances
| Functor Auto | |
| Typeable1 Auto | |
| Foldable Auto | |
| Traversable Auto | |
| Comonad Auto | |
| FunctorWithIndex Int Auto | |
| FoldableWithIndex Int Auto | |
| TraversableWithIndex Int Auto | |
| (~ * a Int, ~ * b Int, Applicative f) => Each f (Auto a) (Auto b) a b | |
| Eq a => Eq (Auto a) | |
| Data a => Data (Auto a) | |
| Ord a => Ord (Auto a) | |
| Read a => Read (Auto a) | |
| Show a => Show (Auto a) | |
| Tabular (Auto a) | |
| Field1 (Auto a) (Auto a) Int Int | |
| Field2 (Auto a) (Auto b) a b |
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:
autoKey=autoIncrementprimaryKeyField
Implementation Details
class IsKeyType k a whereSource
Instances
| IsKeyType InvertedInt IntSet | |
| (Eq a, Hashable a) => IsKeyType SupplementalHash a | |
| ~ * a Int => IsKeyType SupplementalInt a | |
| Ord a => IsKeyType Supplemental a | |
| (Eq a, Hashable a) => IsKeyType CandidateHash a | |
| ~ * a Int => IsKeyType CandidateInt a | |
| Ord a => IsKeyType Candidate a | |
| Ord a => IsKeyType Primary a | |
| (~ (* -> *) t HashSet, Eq a, Hashable a) => IsKeyType InvertedHash (t a) | |
| (~ (* -> *) t Set, Ord a) => IsKeyType Inverted (t a) |
Value-level key types
Constructors
| Primary :: Ord a => KeyType Primary a | |
| Candidate :: Ord a => KeyType Candidate a | |
| CandidateInt :: KeyType CandidateInt Int | |
| CandidateHash :: (Eq a, Hashable a) => KeyType CandidateHash a | |
| Supplemental :: Ord a => KeyType Supplemental a | |
| SupplementalInt :: KeyType SupplementalInt Int | |
| SupplementalHash :: (Eq a, Hashable a) => KeyType SupplementalHash a | |
| Inverted :: Ord a => KeyType Inverted (Set a) | |
| InvertedInt :: KeyType InvertedInt IntSet | |
| InvertedHash :: (Eq a, Hashable a) => KeyType InvertedHash (HashSet a) |
Type level key types
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 CandidateHash Source
Instances
| (Eq a, Hashable a) => IsKeyType CandidateHash a | |
| Applicative f => Group f (Key CandidateHash t a) t a | |
| With (Key CandidateHash t) t |
data Supplemental Source
Instances
| Ord a => IsKeyType Supplemental a | |
| Applicative f => Group f (Key Supplemental t a) t a | |
| With (Key Supplemental t) t |
data SupplementalInt Source
Instances
| ~ * a Int => IsKeyType SupplementalInt a | |
| (Applicative f, ~ * a Int) => Group f (Key SupplementalInt t a) t a | |
| With (Key SupplementalInt t) t |
data SupplementalHash Source
Instances
| (Eq a, Hashable a) => IsKeyType SupplementalHash a | |
| Applicative f => Group f (Key SupplementalHash t a) t a | |
| With (Key SupplementalHash t) t |
data InvertedInt Source
Instances
| IsKeyType InvertedInt IntSet | |
| (Applicative f, Gettable f, ~ * a Int) => Group f (Key InvertedInt t IntSet) t a | |
| Withal (Key InvertedInt t IntSet) [Int] 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 | |
| (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.
Constructors
| PrimaryMap :: Map (PKT t) t -> AnIndex t Primary a | |
| CandidateIntMap :: IntMap t -> AnIndex t CandidateInt Int | |
| CandidateHashMap :: (Eq a, Hashable a) => HashMap a t -> AnIndex t CandidateHash a | |
| CandidateMap :: Ord a => Map a t -> AnIndex t Candidate a | |
| InvertedIntMap :: IntMap [t] -> AnIndex t InvertedInt IntSet | |
| InvertedHashMap :: (Eq a, Hashable a) => HashMap a [t] -> AnIndex t InvertedHash (HashSet a) | |
| InvertedMap :: Ord a => Map a [t] -> AnIndex t Inverted (Set a) | |
| SupplementalIntMap :: IntMap [t] -> AnIndex t SupplementalInt Int | |
| SupplementalHashMap :: (Eq a, Hashable a) => HashMap a [t] -> AnIndex t SupplementalHash a | |
| SupplementalMap :: Ord a => Map a [t] -> AnIndex t Supplemental a |