| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
ADP.Fusion.Core.SynVar.Indices
Description
Classes that enumerate the index structure necessary for actually performing the indexing.
TODO Currently, we only provide dense index generation.
Synopsis
- class AddIndexDense pos elm minSize tableIx ix where
- data SvState elm tableIx ix = SvS {
- sS :: !elm
- tx :: !tableIx
- iIx :: !(RunningIndex ix)
- addIndexDense :: (Monad m, AddIndexDense pos elm minSize tableIx ix, elm ~ Elm x0 i0, Element x0 i0) => Proxy pos -> minSize -> LimitType tableIx -> LimitType ix -> ix -> Stream m elm -> Stream m (elm, tableIx, RunningIndex ix)
- addIndexDense1 :: forall m pos x0 a ix minSize tableIx elm. (Monad m, AddIndexDense (Z :. pos) (Elm (SynVar1 (Elm x0 a)) (Z :. ix)) (Z :. minSize) (Z :. tableIx) (Z :. ix), GetIndex (Z :. a) (Z :. ix), elm ~ Elm x0 a, Element x0 a) => Proxy pos -> minSize -> LimitType tableIx -> LimitType ix -> ix -> Stream m elm -> Stream m (elm, tableIx, RunningIndex ix)
- newtype SynVar1 s = SynVar1 s
- elmSynVar1 :: s -> i -> Elm (SynVar1 s) (Z :. i)
- type AddIndexDenseContext pos elm x0 i0 minSizes minSize tableIxs tableIx ixs ix = (AddIndexDense pos elm minSizes tableIxs ixs, GetIndex (RunningIndex i0) (RunningIndex (ixs :. ix)), GetIx (RunningIndex i0) (RunningIndex (ixs :. ix)) ~ RunningIndex ix, Element x0 i0, elm ~ Elm x0 i0)
Documentation
class AddIndexDense pos elm minSize tableIx ix 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.
pos is the positional information,
s is the element type over the index ix,
minSize the minimal size or width to request from the syntactic variable,
tableIx the index type of the table to walk over,
and ix the actual index.
Methods
Arguments
| :: Monad m | |
| => Proxy pos | Positional information in the rule (staticvariableetc) |
| -> minSize | Minimal size of the structure under consideration. We might want to
constrain enumeration over syntactic variables to only consider at least
"size>=1" cases. Normally, a syntactic variable may be of size 0 as
well, but with rules like |
| -> LimitType tableIx | The upper limit imposed by the structure to traverse over. |
| -> LimitType ix | The upper limit imposed by the rule that traverses. |
| -> ix | The current index for the full rule. |
| -> Stream m (SvState elm Z Z) | Initial stream state with |
| -> Stream m (SvState elm tableIx ix) | The type of the full stream. |
Instances
data SvState elm tableIx ix Source #
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.
Constructors
| SvS | |
Fields
| |
addIndexDense :: (Monad m, AddIndexDense pos elm minSize tableIx ix, elm ~ Elm x0 i0, Element x0 i0) => Proxy pos -> minSize -> LimitType tableIx -> LimitType ix -> ix -> Stream m elm -> Stream m (elm, tableIx, RunningIndex ix) Source #
Given an incoming stream with indices, this adds indices for the current syntactic variable / symbol.
addIndexDense1 :: forall m pos x0 a ix minSize tableIx elm. (Monad m, AddIndexDense (Z :. pos) (Elm (SynVar1 (Elm x0 a)) (Z :. ix)) (Z :. minSize) (Z :. tableIx) (Z :. ix), GetIndex (Z :. a) (Z :. ix), elm ~ Elm x0 a, Element x0 a) => Proxy pos -> minSize -> LimitType tableIx -> LimitType ix -> ix -> Stream m elm -> Stream m (elm, tableIx, RunningIndex ix) 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.
Constructors
| SynVar1 s |
Instances
| (s ~ Elm x0 i, Element x0 i) => Element (SynVar1 s) (Z :. i) Source # | |
| newtype Elm (SynVar1 s) (Z :. i) Source # | |
Defined in ADP.Fusion.Core.SynVar.Indices | |
type AddIndexDenseContext pos elm x0 i0 minSizes minSize tableIxs tableIx ixs ix = (AddIndexDense pos elm minSizes tableIxs ixs, GetIndex (RunningIndex i0) (RunningIndex (ixs :. ix)), GetIx (RunningIndex i0) (RunningIndex (ixs :. ix)) ~ RunningIndex ix, Element x0 i0, elm ~ Elm x0 i0) Source #
Instance headers, we typically need.