Safe Haskell | None |
---|
Data.Store.Internal.Type
- moduleName :: String
- data M
- data O
- data Z = Z
- data S n = S n
- type N0 = Z
- type N1 = S N0
- type N2 = S N1
- type N3 = S N2
- type N4 = S N3
- type N5 = S N4
- type N6 = S N5
- type N7 = S N6
- type N8 = S N7
- type N9 = S N8
- type N10 = S N9
- n0 :: N0
- n1 :: N1
- n2 :: N2
- n3 :: N3
- n4 :: N4
- n5 :: N5
- n6 :: N6
- n7 :: N7
- n8 :: N8
- n9 :: N9
- n10 :: N10
- type family DimensionRelation n rs ts :: *
- type family DimensionType n rs ts :: *
- type family RawDimensionType n a :: *
- type family RawKey kspec tspec :: *
- class (Ord k, Enum k, Bounded k) => Auto k
- data Store tag krs irs ts v = Store {}
- data GenericKey dim rs ts where
- KN :: !(dim r t) -> !(GenericKey dim rt tt) -> GenericKey dim (r :. rt) (t :. tt)
- K1 :: !(dim r t) -> GenericKey dim r t
- type Key = GenericKey KeyDimension
- type IKey = GenericKey IKeyDimension
- data Index rs ts where
- data KeyDimension r t where
- KeyDimensionO :: Ord t => t -> KeyDimension O t
- KeyDimensionM :: Ord t => [t] -> KeyDimension M t
- KeyDimensionA :: Auto t => KeyDimension O t
- data IKeyDimension r t where
- IKeyDimensionO :: Ord t => t -> IKeyDimension O t
- IKeyDimensionM :: Ord t => [t] -> IKeyDimension M t
- data IndexDimension r t where
- IndexDimensionO :: Ord t => !(Map t Int) -> IndexDimension O t
- IndexDimensionM :: Ord t => !(Map t IntSet) -> IndexDimension M t
- class GetDimension n a where
- getDimension :: n -> a -> RawDimensionType n a
- data TT
- data FF
- type family EmptyProxyIsSpecial t :: *
- class Empty a where
- empty :: a
- class EmptyProxy flag a where
- emptyProxy :: flag -> a
- data h :. t = h :. t
Documentation
This is type-level tag for tagging dimensions of key and the index of a store.
You can think of
as an abbreviation for
many.
M
- When
dimension is tagged withKey
, it means that a single element can be indexed under multiple key dimension values. Example:M
Content
(element) has many tags. - When
dimension is tagged withIndex
, it means that a multiple elements can be indexed under a single key dimension values. Example: One rating can be shared by manyM
Content
s (elements).
See also:
Instances
GetDimension Z (Index M t) | |
Show t => Show (Index M t) | |
Show t => Show (IKey M t) | |
Show t => Show (Key M t) | |
(Ord t, Serialize t) => Serialize (IndexDimension M t) | |
(Ord t, Serialize t) => Serialize (IKeyDimension M t) | |
(Ord t, Serialize t, Serialize (Index rt tt)) => Serialize (Index (:. M rt) (:. t tt)) | |
(Ord t, Serialize t) => Serialize (Index M t) | |
NFData t => NFData (Index M t) | |
NFData t => NFData (IKey M t) | |
(Ord t, SafeCopy t) => SafeCopy (IndexDimension M t) | |
(Ord t, SafeCopy t) => SafeCopy (IKeyDimension M t) | |
(Ord t, SafeCopy t, SafeCopy (Index rt tt)) => SafeCopy (Index (:. M rt) (:. t tt)) | |
(Ord t, SafeCopy t) => SafeCopy (Index M t) | |
(Ord t, Empty (Index rt tt)) => Empty (Index (:. M rt) (:. t tt)) | |
Ord t => Empty (Index M t) | |
Serialize (dim M t) => Serialize (GenericKey dim M t) | |
SafeCopy (dim M t) => SafeCopy (GenericKey dim M t) |
This is type-level tag for tagging dimensions of key and the index of a store.
You can think of
as an abbreviation for
one.
O
- When
dimension is tagged withKey
, it means that a single element is indexed under exactly one key dimension value. Example:O
Content
(element) has exactly one title. - When
dimension is tagged withIndex
, it means that at most one element can be indexed under one key dimension value. Example: OneO
ContentID
corresponds to at most oneContent
(element).
See also:
Instances
GetDimension Z (Index O t) | |
Show t => Show (Index O t) | |
Show t => Show (IKey O t) | |
Show t => Show (Key O t) | |
(Ord t, Serialize t) => Serialize (IndexDimension O t) | |
(Ord t, Serialize t) => Serialize (IKeyDimension O t) | |
(Ord t, Serialize t, Serialize (Index rt tt)) => Serialize (Index (:. O rt) (:. t tt)) | |
(Ord t, Serialize t) => Serialize (Index O t) | |
NFData t => NFData (Index O t) | |
NFData t => NFData (IKey O t) | |
(Ord t, SafeCopy t) => SafeCopy (IndexDimension O t) | |
(Ord t, SafeCopy t) => SafeCopy (IKeyDimension O t) | |
(Ord t, SafeCopy t, SafeCopy (Index rt tt)) => SafeCopy (Index (:. O rt) (:. t tt)) | |
(Ord t, SafeCopy t) => SafeCopy (Index O t) | |
(Ord t, Empty (Index rt tt)) => Empty (Index (:. O rt) (:. t tt)) | |
Ord t => Empty (Index O t) | |
Serialize (dim O t) => Serialize (GenericKey dim O t) | |
SafeCopy (dim O t) => SafeCopy (GenericKey dim O t) |
Type-level zero.
Constructors
Z |
Instances
GetDimension Z (Index (:. r rt) (:. t tt)) | |
GetDimension Z (Index O t) | |
GetDimension Z (Index M t) |
Type-level successor of a number.
Constructors
S n |
Instances
GetDimension n (Index rt tt) => GetDimension (S n) (Index (:. r rt) (:. t tt)) |
type family DimensionRelation n rs ts :: *Source
type family DimensionType n rs ts :: *Source
type family RawDimensionType n a :: *Source
data Store tag krs irs ts v Source
The store data type has four type arguments that define what and how things are stored.
The krs
(key relation specification) and irs
(index relation
specification) define the relations between the dimensions of the key
and the elements. To that end, we use
and
O
type-level tags and
M
'Data.Store.Type.Internal.(:.)'
data type to create tuple of these
tags (to describe all the dimensions).
The possible relations are as follows:
- One-one: Every intem is indexed under exactly one key dimension value. One key dimension value corresponds to at most one elements.
- One-many: Every element is indexed under exactly one key dimension value. One key dimension value can correspond to many elements.
- Many-one: Every element can be indexed under multiple (zero or more) key dimension values. One key dimension value corresponds to at most one elements.
- Many-many: Every element cab be indexed under multiple (zero or more) key dimension value. One key dimension value can correspond to many elements.
The ts
(type specification) defines the type of the key's dimensions
and finally v
is the type of the elements stored.
In our example with Content
, we have five dimensions: ID, name, body,
tags and rating. We would like our store to have these properties:
-
Content
has one ID, only one content can have a given ID. -
Content
has one name, only one content can have a given name. -
Content
has one body, many contents can have the same content. -
Content
has many tags, many contents can have tte same tag. -
Content
has one rating, many contents can have the same rating.
So in our case, we define:
type ContentStoreKRS = O :. O :. O :. M :. O type ContentStoreIRS = O :. O :. M :. M :. M type ContentStoreTS = ContentID :. String :. String :. String :. Double type ContentStore = Store ContentStoreKRS ContentStoreIRS ContentStoreTS Content
See also:
Constructors
Store | |
Instances
Typeable5 Store | |
Functor (Store tag krs irs ts) | |
(Show (IKey krs ts), Show v) => Show (Store tag krs irs ts v) | |
Empty (Index irs ts) => Monoid (Store tag krs irs ts v) | |
(Serialize (IKey krs ts), Serialize (Index irs ts), Serialize v) => Serialize (Store tag krs irs ts v) | |
(NFData e, NFData (IKey krs ts), NFData (Index irs ts)) => NFData (Store tag krs irs ts e) | |
(SafeCopy (IKey krs ts), SafeCopy (Index irs ts), SafeCopy v) => SafeCopy (Store tag krs irs ts v) | |
Empty (Index irs ts) => Empty (Store tag krs irs ts e) |
data GenericKey dim rs ts whereSource
Constructors
KN :: !(dim r t) -> !(GenericKey dim rt tt) -> GenericKey dim (r :. rt) (t :. tt) | |
K1 :: !(dim r t) -> GenericKey dim r t |
Instances
Typeable2 (GenericKey dim) | |
(Show t, Show (IKey rt tt)) => Show (IKey (:. r rt) (:. t tt)) | |
Show t => Show (IKey O t) | |
Show t => Show (IKey M t) | |
(Show t, Show (Key rt tt)) => Show (Key (:. r rt) (:. t tt)) | |
Show t => Show (Key O t) | |
Show t => Show (Key M t) | |
(NFData t, NFData (IKey rt tt)) => NFData (IKey (:. r rt) (:. t tt)) | |
NFData t => NFData (IKey O t) | |
NFData t => NFData (IKey M t) | |
Eq (GenericKey IKeyDimension rs ts) | |
(Serialize (GenericKey dim rt tt), Serialize (dim r t)) => Serialize (GenericKey dim (:. r rt) (:. t tt)) | |
Serialize (dim M t) => Serialize (GenericKey dim M t) | |
Serialize (dim O t) => Serialize (GenericKey dim O t) | |
(SafeCopy (GenericKey dim rt tt), SafeCopy (dim r t)) => SafeCopy (GenericKey dim (:. r rt) (:. t tt)) | |
SafeCopy (dim M t) => SafeCopy (GenericKey dim M t) | |
SafeCopy (dim O t) => SafeCopy (GenericKey dim O t) |
type Key = GenericKey KeyDimensionSource
type IKey = GenericKey IKeyDimensionSource
Constructors
IN :: Ord t => !(IndexDimension r t) -> !(Index rt tt) -> Index (r :. rt) (t :. tt) | |
I1 :: Ord t => !(IndexDimension r t) -> Index r t |
Instances
data KeyDimension r t whereSource
Constructors
KeyDimensionO :: Ord t => t -> KeyDimension O t | |
KeyDimensionM :: Ord t => [t] -> KeyDimension M t | |
KeyDimensionA :: Auto t => KeyDimension O t |
data IKeyDimension r t whereSource
Constructors
IKeyDimensionO :: Ord t => t -> IKeyDimension O t | |
IKeyDimensionM :: Ord t => [t] -> IKeyDimension M t |
Instances
Typeable2 IKeyDimension | |
Eq (IKeyDimension r t) | |
Show t => Show (IKeyDimension r t) | |
(Show t, Show (IKey rt tt)) => Show (IKey (:. r rt) (:. t tt)) | |
Show t => Show (IKey O t) | |
Show t => Show (IKey M t) | |
(Ord t, Serialize t) => Serialize (IKeyDimension O t) | |
(Ord t, Serialize t) => Serialize (IKeyDimension M t) | |
NFData t => NFData (IKeyDimension r t) | |
(NFData t, NFData (IKey rt tt)) => NFData (IKey (:. r rt) (:. t tt)) | |
NFData t => NFData (IKey O t) | |
NFData t => NFData (IKey M t) | |
(Ord t, SafeCopy t) => SafeCopy (IKeyDimension O t) | |
(Ord t, SafeCopy t) => SafeCopy (IKeyDimension M t) | |
Eq (GenericKey IKeyDimension rs ts) |
data IndexDimension r t whereSource
Constructors
IndexDimensionO :: Ord t => !(Map t Int) -> IndexDimension O t | |
IndexDimensionM :: Ord t => !(Map t IntSet) -> IndexDimension M t |
Instances
Show t => Show (IndexDimension r t) | |
(Ord t, Serialize t) => Serialize (IndexDimension O t) | |
(Ord t, Serialize t) => Serialize (IndexDimension M t) | |
NFData t => NFData (IndexDimension r t) | |
(Ord t, SafeCopy t) => SafeCopy (IndexDimension O t) | |
(Ord t, SafeCopy t) => SafeCopy (IndexDimension M t) |
class GetDimension n a whereSource
Methods
getDimension :: n -> a -> RawDimensionType n aSource
Instances
GetDimension Z (Index (:. r rt) (:. t tt)) | |
GetDimension Z (Index O t) | |
GetDimension Z (Index M t) | |
GetDimension n (Index rt tt) => GetDimension (S n) (Index (:. r rt) (:. t tt)) |
type family EmptyProxyIsSpecial t :: *Source
class EmptyProxy flag a whereSource
Methods
emptyProxy :: flag -> aSource
Data type for creating tuples, it is used to:
- Create type-level tuples of relation tags for relation specification of the key and the index of the store.
M :. O :. O :. M
- Create type-level tuples of types for type specification of the key and index of the store.
Int :. Double :. String :. String
- Create value-level tuples to return raw key (with resolved auto-increment dimensions).
[1, 2, 3] :. 3.5 :. "Foo" :. ["Bar1", "Bar2"]
Constructors
h :. t |
Instances
GetDimension Z (Index (:. r rt) (:. t tt)) | |
GetDimension n (Index rt tt) => GetDimension (S n) (Index (:. r rt) (:. t tt)) | |
(Show h, Show t) => Show (:. h t) | |
(Show t, Show (Index rt tt)) => Show (Index (:. r rt) (:. t tt)) | |
(Show t, Show (IKey rt tt)) => Show (IKey (:. r rt) (:. t tt)) | |
(Show t, Show (Key rt tt)) => Show (Key (:. r rt) (:. t tt)) | |
(Ord t, Serialize t, Serialize (Index rt tt)) => Serialize (Index (:. O rt) (:. t tt)) | |
(Ord t, Serialize t, Serialize (Index rt tt)) => Serialize (Index (:. M rt) (:. t tt)) | |
(NFData a, NFData b) => NFData (:. a b) | |
(NFData t, NFData (Index rt tt)) => NFData (Index (:. r rt) (:. t tt)) | |
(NFData t, NFData (IKey rt tt)) => NFData (IKey (:. r rt) (:. t tt)) | |
(Ord t, SafeCopy t, SafeCopy (Index rt tt)) => SafeCopy (Index (:. O rt) (:. t tt)) | |
(Ord t, SafeCopy t, SafeCopy (Index rt tt)) => SafeCopy (Index (:. M rt) (:. t tt)) | |
(Ord t, Empty (Index rt tt)) => Empty (Index (:. O rt) (:. t tt)) | |
(Ord t, Empty (Index rt tt)) => Empty (Index (:. M rt) (:. t tt)) | |
(Serialize (GenericKey dim rt tt), Serialize (dim r t)) => Serialize (GenericKey dim (:. r rt) (:. t tt)) | |
(SafeCopy (GenericKey dim rt tt), SafeCopy (dim r t)) => SafeCopy (GenericKey dim (:. r rt) (:. t tt)) |