ADPfusion-0.6.0.0: Efficient, high-level dynamic programming.

Safe HaskellNone
LanguageHaskell2010

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

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

addIndexDenseGo Source #

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 X -> X X, we don't want to have one of the X's on the r.h.s. be of size 0.

-> 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 Zero indices.

-> Stream m (SvState elm tableIx ix)

The type of the full stream.

Instances
AddIndexDense (pos :: k) elm Z Z Z Source # 
Instance details

Defined in ADP.Fusion.Core.SynVar.Indices

Methods

addIndexDenseGo :: Monad m => Proxy pos -> Z -> LimitType Z -> LimitType Z -> Z -> Stream m (SvState elm Z Z) -> Stream m (SvState elm Z Z) Source #

AddIndexDenseContext ps elm x0 i0 cs c us (PointL O) is (PointL C) => AddIndexDense (ps :. Complement :: Type) elm (cs :. c) (us :. PointL O) (is :. PointL C) Source # 
Instance details

Defined in ADP.Fusion.PointL.SynVar.Indices

Methods

addIndexDenseGo :: Monad m => Proxy (ps :. Complement) -> (cs :. c) -> LimitType (us :. PointL O) -> LimitType (is :. PointL C) -> (is :. PointL C) -> Stream m (SvState elm Z Z) -> Stream m (SvState elm (us :. PointL O) (is :. PointL C)) Source #

AddIndexDenseContext ps elm x0 i0 cs c us (PointL I) is (PointL C) => AddIndexDense (ps :. Complement :: Type) elm (cs :. c) (us :. PointL I) (is :. PointL C) Source # 
Instance details

Defined in ADP.Fusion.PointL.SynVar.Indices

Methods

addIndexDenseGo :: Monad m => Proxy (ps :. Complement) -> (cs :. c) -> LimitType (us :. PointL I) -> LimitType (is :. PointL C) -> (is :. PointL C) -> Stream m (SvState elm Z Z) -> Stream m (SvState elm (us :. PointL I) (is :. PointL C)) Source #

(AddIndexDenseContext ps elm x0 i0 cs c us (PointL O) is (PointL O), MinSize c) => AddIndexDense (ps :. ORightOf d :: Type) elm (cs :. c) (us :. PointL O) (is :. PointL O) Source # 
Instance details

Defined in ADP.Fusion.PointL.SynVar.Indices

Methods

addIndexDenseGo :: Monad m => Proxy (ps :. ORightOf d) -> (cs :. c) -> LimitType (us :. PointL O) -> LimitType (is :. PointL O) -> (is :. PointL O) -> Stream m (SvState elm Z Z) -> Stream m (SvState elm (us :. PointL O) (is :. PointL O)) Source #

(AddIndexDenseContext ps elm x0 i0 cs c us (PointL O) is (PointL O), MinSize c) => AddIndexDense (ps :. OStatic d :: Type) elm (cs :. c) (us :. PointL O) (is :. PointL O) Source # 
Instance details

Defined in ADP.Fusion.PointL.SynVar.Indices

Methods

addIndexDenseGo :: Monad m => Proxy (ps :. OStatic d) -> (cs :. c) -> LimitType (us :. PointL O) -> LimitType (is :. PointL O) -> (is :. PointL O) -> Stream m (SvState elm Z Z) -> Stream m (SvState elm (us :. PointL O) (is :. PointL O)) Source #

(AddIndexDenseContext ps elm x0 i0 cs c us (PointL I) is (PointL I), MinSize c) => AddIndexDense (ps :. IVariable d :: Type) elm (cs :. c) (us :. PointL I) (is :. PointL I) Source # 
Instance details

Defined in ADP.Fusion.PointL.SynVar.Indices

Methods

addIndexDenseGo :: Monad m => Proxy (ps :. IVariable d) -> (cs :. c) -> LimitType (us :. PointL I) -> LimitType (is :. PointL I) -> (is :. PointL I) -> Stream m (SvState elm Z Z) -> Stream m (SvState elm (us :. PointL I) (is :. PointL I)) Source #

(AddIndexDenseContext ps elm x0 i0 cs c us (PointL I) is (PointL I), MinSize c) => AddIndexDense (ps :. IStatic d :: Type) elm (cs :. c) (us :. PointL I) (is :. PointL I) Source # 
Instance details

Defined in ADP.Fusion.PointL.SynVar.Indices

Methods

addIndexDenseGo :: Monad m => Proxy (ps :. IStatic d) -> (cs :. c) -> LimitType (us :. PointL I) -> LimitType (is :. PointL I) -> (is :. PointL I) -> Stream m (SvState elm Z Z) -> Stream m (SvState elm (us :. PointL I) (is :. PointL I)) Source #

(AddIndexDenseContext ps elm x0 i0 cs c us (PointR I) is (PointR I), MinSize c) => AddIndexDense (ps :. IStatic d :: Type) elm (cs :. c) (us :. PointR I) (is :. PointR I) Source # 
Instance details

Defined in ADP.Fusion.PointR.SynVar.Indices

Methods

addIndexDenseGo :: Monad m => Proxy (ps :. IStatic d) -> (cs :. c) -> LimitType (us :. PointR I) -> LimitType (is :. PointR I) -> (is :. PointR I) -> Stream m (SvState elm Z Z) -> Stream m (SvState elm (us :. PointR I) (is :. PointR I)) Source #

(AddIndexDenseContext ps elm x0 i0 cs c us (Unit O) is (Unit C), MinSize c) => AddIndexDense (ps :. Unit d :: Type) elm (cs :. c) (us :. Unit O) (is :. Unit C) Source # 
Instance details

Defined in ADP.Fusion.Unit.SynVar.Indices

Methods

addIndexDenseGo :: Monad m => Proxy (ps :. Unit d) -> (cs :. c) -> LimitType (us :. Unit O) -> LimitType (is :. Unit C) -> (is :. Unit C) -> Stream m (SvState elm Z Z) -> Stream m (SvState elm (us :. Unit O) (is :. Unit C)) Source #

(AddIndexDenseContext ps elm x0 i0 cs c us (Unit I) is (Unit C), MinSize c) => AddIndexDense (ps :. Unit d :: Type) elm (cs :. c) (us :. Unit I) (is :. Unit C) Source # 
Instance details

Defined in ADP.Fusion.Unit.SynVar.Indices

Methods

addIndexDenseGo :: Monad m => Proxy (ps :. Unit d) -> (cs :. c) -> LimitType (us :. Unit I) -> LimitType (is :. Unit C) -> (is :. Unit C) -> Stream m (SvState elm Z Z) -> Stream m (SvState elm (us :. Unit I) (is :. Unit C)) Source #

(AddIndexDenseContext ps elm x0 i0 cs c us (Unit O) is (Unit O), MinSize c) => AddIndexDense (ps :. Unit d :: Type) elm (cs :. c) (us :. Unit O) (is :. Unit O) Source # 
Instance details

Defined in ADP.Fusion.Unit.SynVar.Indices

Methods

addIndexDenseGo :: Monad m => Proxy (ps :. Unit d) -> (cs :. c) -> LimitType (us :. Unit O) -> LimitType (is :. Unit O) -> (is :. Unit O) -> Stream m (SvState elm Z Z) -> Stream m (SvState elm (us :. Unit O) (is :. Unit O)) Source #

(AddIndexDenseContext ps elm x0 i0 cs c us (Unit I) is (Unit I), MinSize c) => AddIndexDense (ps :. Unit d :: Type) elm (cs :. c) (us :. Unit I) (is :. Unit I) Source # 
Instance details

Defined in ADP.Fusion.Unit.SynVar.Indices

Methods

addIndexDenseGo :: Monad m => Proxy (ps :. Unit d) -> (cs :. c) -> LimitType (us :. Unit I) -> LimitType (is :. Unit I) -> (is :. Unit I) -> Stream m (SvState elm Z Z) -> Stream m (SvState elm (us :. Unit I) (is :. Unit I)) Source #

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

  • sS :: !elm

    state coming in from the left

  • tx :: !tableIx

    I/C building up state to index the table.

  • iIx :: !(RunningIndex ix)

    I/C building up state to hand over to next symbol

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.

newtype SynVar1 s Source #

Constructors

SynVar1 s 
Instances
(s ~ Elm x0 i, Element x0 i) => Element (SynVar1 s) (Z :. i) Source # 
Instance details

Defined in ADP.Fusion.Core.SynVar.Indices

Associated Types

data Elm (SynVar1 s) (Z :. i) :: Type Source #

type RecElm (SynVar1 s) (Z :. i) :: Type Source #

type Arg (SynVar1 s) :: Type Source #

Methods

getArg :: Elm (SynVar1 s) (Z :. i) -> Arg (SynVar1 s) Source #

getIdx :: Elm (SynVar1 s) (Z :. i) -> RunningIndex (Z :. i) Source #

getElm :: Elm (SynVar1 s) (Z :. i) -> RecElm (SynVar1 s) (Z :. i) Source #

newtype Elm (SynVar1 s) (Z :. i) Source # 
Instance details

Defined in ADP.Fusion.Core.SynVar.Indices

newtype Elm (SynVar1 s) (Z :. i) = ElmSynVar1 s

elmSynVar1 :: s -> i -> Elm (SynVar1 s) (Z :. i) Source #

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.