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

Safe HaskellNone

ADP.Fusion.Multi.Classes

Contents

Synopsis

Documentation

data TermBase Source

The zero-th dimension of every terminal parser.

Constructors

T 

data Term a b Source

Combine a terminal parser of dimension k in a with a new 1-dim parser b generating a parser of dimension k+1.

Constructors

a :! b 

Instances

(Monad m, Elms ls ix, MkStream m ls ix, TermElm m (Term a b) ix, TermValidIndex (Term a b) ix) => MkStream m (:!: ls (Term a b)) ix 
(Monad m, TermElm m ts is) => TermElm m (Term ts Empty) (:. is PointL) 
(Monad m, TermElm m ts is) => TermElm m (Term ts None) (:. is PointL) 
(Monad m, TermElm m ts is) => TermElm m (Term ts (GChr r xs)) (:. is PointL)

NOTE This instance is currently the only one using an inline outer check. If This behaves well, it could be possible to put checks for valid indices inside the outerCheck function. (Currently disabled, as the compiler chokes on four-way alignments).

(Monad m, TermElm m ts is) => TermElm m (Term ts (GChr r xs)) (:. is Subword) 
Build (Term a b) 
(ValidIndex ls ix, TermValidIndex (Term a b) ix, Show ix, Show (ParserRange ix)) => ValidIndex (:!: ls (Term a b)) ix 
Elms ls ix => Elms (:!: ls (Term a b)) ix 
TermValidIndex ts is => TermValidIndex (Term ts Empty) (:. is PointL) 
TermValidIndex ts is => TermValidIndex (Term ts None) (:. is PointL) 
TermValidIndex ts is => TermValidIndex (Term ts (GChr r xs)) (:. is PointL) 
TermValidIndex ts is => TermValidIndex (Term ts (GChr r xs)) (:. is Subword) 

class Monad m => TermElm m t ix whereSource

A termStream extracts all terminal elements from a multi-dimensional terminal symbol.

Methods

termStream :: t -> InOut ix -> ix -> Stream m ((ze :!: zix) :!: ix) -> Stream m (((ze :!: zix) :!: ix) :!: TermOf t)Source

Instances

Monad m => TermElm m TermBase Z 
(Monad m, TermElm m ts is) => TermElm m (Term ts Empty) (:. is PointL) 
(Monad m, TermElm m ts is) => TermElm m (Term ts None) (:. is PointL) 
(Monad m, TermElm m ts is) => TermElm m (Term ts (GChr r xs)) (:. is PointL)

NOTE This instance is currently the only one using an inline outer check. If This behaves well, it could be possible to put checks for valid indices inside the outerCheck function. (Currently disabled, as the compiler chokes on four-way alignments).

(Monad m, TermElm m ts is) => TermElm m (Term ts (GChr r xs)) (:. is Subword) 

type family TermOf t :: *Source

class TermValidIndex t i whereSource

To calculate parser ranges and index validity we need an additional type class that recurses over the individual Term elements.

The instance declarations for generic Term a b data ctors.

Terminal stream of TermBase with index Z