Copyright | (C) 2012-2013 Edward Kmett, |
---|---|
License | BSD-style (see the file LICENSE) |
Maintainer | Edward Kmett <[email protected]> |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell98 |
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.
- 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)
- makeTabular :: Name -> [(Name, Name)] -> Q [Dec]
- empty :: Table t
- singleton :: Tabular t => t -> Table t
- table :: Tabular t => Iso' [t] (Table t)
- fromList :: Tabular t => [t] -> Table t
- unsafeFromList :: Tabular t => [t] -> Table t
- union :: Table t -> Table t -> Table t
- difference :: (Tabular t1, Tabular t2, PKT t1 ~ PKT t2) => Table t1 -> Table t2 -> Table t1
- intersection :: (Tabular t1, Tabular t2, PKT t1 ~ PKT t2) => Table t1 -> Table t2 -> Table t1
- 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)
- unsafeInsert :: Tabular t => t -> Table t -> Table t
- delete :: t -> Table t -> Table t
- rows :: (Tabular t, PKT s ~ PKT t) => IndexedTraversal (PKT s) (Table s) (Table t) s t
- data Primary
- data Candidate
- data CandidateInt
- data CandidateHash
- data Supplemental
- data SupplementalInt
- data SupplementalHash
- data Inverted
- data InvertedInt
- data InvertedHash
- 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 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
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 | |
Typeable (* -> *) Table | |
type Index (Table t) = PKT t | |
type IxValue (Table t) = t |
class Ord (PKT t) => Tabular t where Source
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 -> a Source
Extract the value of a Key
primary :: Key Primary t (PKT t) Source
primarily :: Key Primary t a -> ((a ~ PKT t) => r) -> r Source
... 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 a Source
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.
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
unsafeFromList :: Tabular t => [t] -> Table t Source
Build up a table from a list, without checking for collisions
Combining Tables
union :: Table t -> Table t -> Table t Source
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 t1 Source
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 t1 Source
Return the elements of the first table that share a key with an element of the second table
Reading and Writing
class With q t | q -> t where Source
Minimal complete definition
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 t Source
Delete selected rows from a table
deleteWith
p cmp a t ≡set
(with
p cmp a)empty
t
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 where Source
Search inverted indices
class Group f q t i | q -> t i where Source
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, Contravariant f) => Group f (Key InvertedHash t (HashSet a)) t a | |
(Applicative f, Contravariant f, (~) * a Int) => Group f (Key InvertedInt t IntSet) t a | |
(Applicative f, Contravariant 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 t Source
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 t Source
Insert a row into a relation, ignoring collisions.
delete :: t -> Table t -> Table t Source
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 t Source
Traverse all of the rows in a table, potentially changing table types completely.
Key Types
Primary Keys
The key type for the canonical, unique identifier attached to
every row. There should only be one Primary
key.
Candidate Keys
A key type for values unique to each row, but that are
not Primary
.
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 Int
s.
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
.
Instances
(Eq a, Hashable a) => IsKeyType CandidateHash a | |
Applicative f => Group f (Key CandidateHash t a) t a | |
With (Key CandidateHash t) t | |
(NFData t, NFData a, NFData (PKT t)) => NFData (AnIndex t CandidateHash a) |
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
Ord a => IsKeyType Supplemental a | |
Applicative f => Group f (Key Supplemental t a) t a | |
With (Key Supplemental t) t | |
(NFData t, NFData a, NFData (PKT t)) => NFData (AnIndex t Supplemental a) |
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 Int
s.
Instances
(~) * a Int => IsKeyType SupplementalInt a | |
(Applicative f, (~) * a Int) => Group f (Key SupplementalInt t a) t a | |
With (Key SupplementalInt t) t | |
(NFData t, NFData (PKT t)) => NFData (AnIndex t SupplementalInt Int) |
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
.
Instances
(Eq a, Hashable a) => IsKeyType SupplementalHash a | |
Applicative f => Group f (Key SupplementalHash t a) t a | |
With (Key SupplementalHash t) t | |
(NFData t, NFData a, NFData (PKT t)) => NFData (AnIndex t SupplementalHash a) |
Inverted Keys
A key type for inverse keys.
data InvertedInt Source
Instances
IsKeyType InvertedInt IntSet | |
(Applicative f, Contravariant f, (~) * a Int) => Group f (Key InvertedInt t IntSet) t a | |
(NFData t, NFData (PKT t)) => NFData (AnIndex t InvertedInt IntSet) | |
Withal (Key InvertedInt t IntSet) [Int] t |
data InvertedHash Source
Instances
((~) (* -> *) t HashSet, Eq a, Hashable a) => IsKeyType InvertedHash (t a) | |
(Applicative f, Contravariant 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
Instances
Functor Auto | |
Foldable Auto | |
Traversable Auto | |
Comonad Auto | |
FunctorWithIndex Int Auto | |
FoldableWithIndex Int Auto | |
TraversableWithIndex Int Auto | |
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) | |
Binary a => Binary (Auto a) | |
Serialize a => Serialize (Auto a) | |
SafeCopy a => SafeCopy (Auto a) | |
Tabular (Auto a) | |
((~) * a Int, (~) * b Int) => Each (Auto a) (Auto b) a b | |
Field1 (Auto a) (Auto a) Int Int | |
Field2 (Auto a) (Auto b) a b | |
Typeable (* -> *) Auto | |
data Key p (Auto a) where | |
type Index (Auto a) = Int | |
type PKT (Auto a) = Int | |
data Tab (Auto a) = AutoTab (i Primary Int) |
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 where Source
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) |
data AnIndex t k a where Source
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 |
Instances
(NFData t, NFData a, NFData (PKT t)) => NFData (AnIndex t InvertedHash (HashSet a)) | |
(NFData t, NFData a, NFData (PKT t)) => NFData (AnIndex t Inverted (Set a)) | |
(NFData t, NFData (PKT t)) => NFData (AnIndex t InvertedInt IntSet) | |
(NFData t, NFData a, NFData (PKT t)) => NFData (AnIndex t CandidateHash a) | |
(NFData t, NFData (PKT t)) => NFData (AnIndex t CandidateInt Int) | |
(NFData t, NFData a, NFData (PKT t)) => NFData (AnIndex t Candidate a) | |
(NFData t, NFData a, NFData (PKT t)) => NFData (AnIndex t SupplementalHash a) | |
(NFData t, NFData (PKT t)) => NFData (AnIndex t SupplementalInt Int) | |
(NFData t, NFData a, NFData (PKT t)) => NFData (AnIndex t Supplemental a) | |
(NFData t, NFData a, NFData (PKT t)) => NFData (AnIndex t Primary a) |