Safe Haskell | None |
---|---|
Language | Haskell2010 |
Classes that enumerate the index structure necessary for actually performing the indexing.
TODO Currently, we only provide dense index generation.
- class AddIndexDense s u c i where
- data SvState s a u i = SvS {
- sS :: !s
- tx :: !u
- iIx :: !(RunningIndex i)
- addIndexDense :: (Monad m, AddIndexDense s u c i, s ~ Elm x0 i0, Element x0 i0) => c -> Context i -> u -> u -> i -> i -> Stream m s -> Stream m (s, u, RunningIndex i)
- addIndexDense1 :: (Monad m, AddIndexDense (Elm (SynVar1 (Elm x0 a)) (Z :. i)) (Z :. u) (Z :. c) (Z :. i), GetIndex (Z :. a) (Z :. i), s ~ Elm x0 a, Element x0 a) => c -> Context i -> u -> u -> i -> i -> Stream m s -> Stream m (s, u, RunningIndex i)
- newtype SynVar1 s = SynVar1 s
- elmSynVar1 :: s -> i -> Elm (SynVar1 s) (Z :. i)
- type IndexHdr s x0 i0 us u cs c is i = (AddIndexDense s us cs is, GetIndex (RunningIndex i0) (RunningIndex (is :. i)), GetIx (RunningIndex i0) (RunningIndex (is :. i)) ~ RunningIndex i, Element x0 i0, s ~ Elm x0 i0)
Documentation
class AddIndexDense s u c i where Source #
This type classes enable enumeration both in single- and multi-dim
cases. The type a
is the type of the full stack of indices, i.e. the
full multi-tape problem.
SvState
holds the state that is currently being built up by
AddIndexDense
. We have both tIx
(and tOx
) and iIx
(and iOx
).
For most index structures, the indices will co-incide; however for some,
this will not be true -- herein for Set
index structures.
SvS | |
|
addIndexDense :: (Monad m, AddIndexDense s u c i, s ~ Elm x0 i0, Element x0 i0) => c -> Context i -> u -> u -> i -> i -> Stream m s -> Stream m (s, u, RunningIndex i) Source #
Given an incoming stream with indices, this adds indices for the current syntactic variable / symbol.
addIndexDense1 :: (Monad m, AddIndexDense (Elm (SynVar1 (Elm x0 a)) (Z :. i)) (Z :. u) (Z :. c) (Z :. i), GetIndex (Z :. a) (Z :. i), s ~ Elm x0 a, Element x0 a) => c -> Context i -> u -> u -> i -> i -> Stream m s -> Stream m (s, u, RunningIndex i) Source #
In case of 1-dim tables, we wrap the index creation in a multi-dim
system and remove the Z
later on. This allows us to have to write only
a single instance.
SynVar1 s |
type IndexHdr s x0 i0 us u cs c is i = (AddIndexDense s us cs is, GetIndex (RunningIndex i0) (RunningIndex (is :. i)), GetIx (RunningIndex i0) (RunningIndex (is :. i)) ~ RunningIndex i, Element x0 i0, s ~ Elm x0 i0) Source #
Instance headers, we typically need.