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

Safe HaskellNone
LanguageHaskell2010

ADP.Fusion.SynVar.Indices.Classes

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

Minimal complete definition

addIndexDenseGo

Methods

addIndexDenseGo :: Monad m => c -> Context i -> u -> u -> i -> i -> Stream m (SvState s a Z Z) -> Stream m (SvState s a u i) Source #

Instances

AddIndexDense a Z Z Z Source # 

Methods

addIndexDenseGo :: Monad m => Z -> Context Z -> Z -> Z -> Z -> Z -> Stream m (SvState a a Z Z) -> Stream m (SvState a a Z Z) Source #

data SvState s a u i 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 :: !s

    state coming in from the left , sIx :: !(RunningIndex a) -- I/C index from sS

  • tx :: !u

    I/C building up state to index the table.

  • iIx :: !(RunningIndex i)

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

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.

newtype SynVar1 s Source #

Constructors

SynVar1 s 

Instances

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

Associated Types

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

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

type Arg (SynVar1 s) :: * 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 #

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

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

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.