| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
ADP.Fusion.SynVar.TableWrap
Description
Wrap the underlying table and the rules. Isomorphic to (,).
Documentation
Wrap tables of type t. The tables are strict, the functions f can
 not be strict, because we need to build grammars recursively.
Constructors
| TW !t f | 
Instances
| SplitIxCol uId (SameSid uId (Elm ls i)) (Elm ls i) => SplitIxCol uId True (Elm ((:!:) ls (Split sId splitType (TwITblBt arr c j x mF mB r))) i) Source # | |
| SplitIxCol uId (SameSid uId (Elm ls i)) (Elm ls i) => SplitIxCol uId True (Elm ((:!:) ls (Split sId splitType (TwITbl m arr c j x))) i) Source # | |
| (MutateCell h ((:.) ts (TwITbl im arr c i x)) im i, PrimArrayOps arr i x, Show i, IndexStream i, TableOrder ((:.) ts (TwITbl im arr c i x))) => MutateTables h ((:.) ts (TwITbl im arr c i x)) im Source # | |
| (PrimArrayOps arr ZS2 x, MPrimArrayOps arr ZS2 x, MutateCell MonotoneMCFG ts im ZS2) => MutateCell MonotoneMCFG ((:.) ts (TwITbl im arr c ZS2 x)) im ZS2 Source # | |
| (PrimArrayOps arr i x, MPrimArrayOps arr i x, MutateCell CFG ts im i) => MutateCell CFG ((:.) ts (TwITbl im arr c i x)) im i Source # | |
| MutateCell CFG ts im i => MutateCell CFG ((:.) ts (TwIRec im c i x)) im i Source # | |
| (PrimArrayOps arr (Subword I) x, MPrimArrayOps arr (Subword I) x, MutateCell h ts im ((:.) ((:.) Z (Subword I)) (Subword I))) => MutateCell h ((:.) ts (TwITbl im arr c (Subword I) x)) im ((:.) ((:.) Z (Subword I)) (Subword I)) Source # | |
| (Monad mB, Element ls ((:.) is i), TableStaticVar ((:.) us u) ((:.) cs c) ((:.) is i), AddIndexDense (Elm ls ((:.) is i)) ((:.) us u) ((:.) cs c) ((:.) is i), MkStream mB ls ((:.) is i), PrimArrayOps arr ((:.) us u) x) => MkStream mB ((:!:) ls (TwITblBt arr ((:.) cs c) ((:.) us u) x mF mB r)) ((:.) is i) Source # | |
| (Monad m, Element ls ((:.) is i), TableStaticVar ((:.) us u) ((:.) cs c) ((:.) is i), AddIndexDense (Elm ls ((:.) is i)) ((:.) us u) ((:.) cs c) ((:.) is i), MkStream m ls ((:.) is i), PrimArrayOps arr ((:.) us u) x) => MkStream m ((:!:) ls (TwITbl m arr ((:.) cs c) ((:.) us u) x)) ((:.) is i) Source # | |
| (Applicative mB, Monad mB, Element ls ((:.) is i), TableStaticVar ((:.) us u) ((:.) cs c) ((:.) is i), AddIndexDense (Elm ls ((:.) is i)) ((:.) us u) ((:.) cs c) ((:.) is i), MkStream mB ls ((:.) is i)) => MkStream mB ((:!:) ls (TwIRecBt ((:.) cs c) ((:.) us u) x mF mB r)) ((:.) is i) Source # | |
| (Functor m, Monad m, Element ls ((:.) is i), TableStaticVar ((:.) us u) ((:.) cs c) ((:.) is i), AddIndexDense (Elm ls ((:.) is i)) ((:.) us u) ((:.) cs c) ((:.) is i), MkStream m ls ((:.) is i)) => MkStream m ((:!:) ls (TwIRec m ((:.) cs c) ((:.) us u) x)) ((:.) is i) Source # | |
| (Show x, Show i, Show (RunningIndex i), Show (Elm ls i)) => Show (Elm ((:!:) ls (TwITblBt arr c i x mF mB r)) i) # | |
| (Show i, Show (RunningIndex i), Show (Elm ls i), Show x) => Show (Elm ((:!:) ls (TwITbl m arr c j x)) i) # | |
| (Monad mB, PrimArrayOps arr i x, IndexStream i, (~) * j i, (~) (* -> *) m mB) => Axiom (TW (Backtrack (TwITbl mF arr c i x) mF mB) (j -> j -> m [r])) Source # | We need this somewhat annoying instance construction ( | 
| (Monad mB, IndexStream i, (~) * i j, (~) (* -> *) m mB) => Axiom (TW (Backtrack (TwIRec mF c i x) mF mB) (j -> j -> m [r])) Source # | |
| TSBO ts => TSBO ((:.) ts (TwIRec Id c i x)) Source # | |
| (TSBO ts, Typeable (* -> * -> *) arr, Typeable * c, Typeable * i, Typeable * x, PrimArrayOps arr i x, MPrimArrayOps arr i x, IndexStream i) => TSBO ((:.) ts (TwITbl Id arr c i x)) Source # | |
| TableOrder ts => TableOrder ((:.) ts (TwIRec im c i x)) Source # | 
 | 
| TableOrder ts => TableOrder ((:.) ts (TwITbl im arr c i x)) Source # | |
| Element ls i => Element ((:!:) ls (TwITblBt arr c j x mF mB r)) i Source # | |
| Element ls i => Element ((:!:) ls (TwITbl m arr c j x)) i Source # | |
| Element ls i => Element ((:!:) ls (TwIRecBt c u x mF mB r)) i Source # | |
| Element ls i => Element ((:!:) ls (TwIRec m c u x)) i Source # | |
| Element ls i => Element ((:!:) ls (Split uId splitType (TwITblBt arr c j x mF mB r))) i Source # | |
| Element ls i => Element ((:!:) ls (Split uId splitType (TwITbl m arr c j x))) i Source # | |
| (Monad m, IndexStream i) => Axiom (TwIRec m c i x) Source # | |
| Build (TwIRec m c i x) Source # | |
| GenBacktrackTable (TwIRec mF c i x) mF mB Source # | |
| (Monad m, PrimArrayOps arr i x, IndexStream i) => Axiom (TwITbl m arr c i x) Source # | |
| Build (TwITbl m arr c i x) Source # | |
| GenBacktrackTable (TwITbl mF arr c i x) mF mB Source # | |
| Build (TwIRecBt c i x mF mB r) Source # | |
| Build (TwITblBt arr c i x mF mB r) Source # | |
| type SplitIxTy uId True (Elm ((:!:) ls (Split sId splitType (TwITblBt arr c j x mF mB r))) i) Source # | |
| type SplitIxTy uId True (Elm ((:!:) ls (Split sId splitType (TwITbl m arr c j x))) i) Source # | |
| type AxiomStream (TW (Backtrack (TwITbl mF arr c i x) mF mB) (j -> j -> m [r])) Source # | |
| type AxiomStream (TW (Backtrack (TwIRec mF c i x) mF mB) (j -> j -> m [r])) Source # | |
| data Elm ((:!:) ls (TwITblBt arr c j x mF mB r)) Source # | |
| data Elm ((:!:) ls (TwITbl m arr c j x)) Source # | |
| data Elm ((:!:) ls (TwIRecBt c u x mF mB r)) Source # | |
| data Elm ((:!:) ls (TwIRec m c u x)) Source # | |
| data Elm ((:!:) ls (Split uId splitType (TwITblBt arr c j x mF mB r))) Source # | |
| data Elm ((:!:) ls (Split uId splitType (TwITbl m arr c j x))) Source # | |
| type Arg ((:!:) ls (TwITblBt arr c j x mF mB r)) Source # | |
| type Arg ((:!:) ls (TwITbl m arr c j x)) Source # | |
| type Arg ((:!:) ls (TwIRecBt c u x mF mB r)) Source # | |
| type Arg ((:!:) ls (TwIRec m c u x)) Source # | |
| type Arg ((:!:) ls (Split uId splitType (TwITblBt arr c j x mF mB r))) Source # | |
| type Arg ((:!:) ls (Split uId splitType (TwITbl m arr c j x))) Source # | |
| type RecElm ((:!:) ls (TwITblBt arr c j x mF mB r)) i Source # | |
| type RecElm ((:!:) ls (TwITbl m arr c j x)) i Source # | |
| type RecElm ((:!:) ls (Split uId splitType (TwITblBt arr c j x mF mB r))) i Source # | |
| type RecElm ((:!:) ls (Split uId splitType (TwITbl m arr c j x))) i Source # | |
| type BacktrackIndex (TwIRec mF c i x) Source # | |
| type AxiomStream (TwIRec m c i x) Source # | |
| type Stack (TwIRec m c i x) Source # | |
| type TermArg (TwIRec m c i x) Source # | |
| data Backtrack (TwIRec mF c i x) mF Source # | |
| type BacktrackIndex (TwITbl mF arr c i x) Source # | |
| type AxiomStream (TwITbl m arr c i x) Source # | |
| type TNE (TwITbl m arr EmptyOk i x) Source # | |
| type TE (TwITbl m arr EmptyOk i x) Source # | |
| type Stack (TwITbl m arr c i x) Source # | |
| type TermArg (TwITbl m arr c i x) Source # | |
| data Backtrack (TwITbl mF arr c i x) mF Source # | |
| type Stack (TwIRecBt c i x mF mB r) Source # | |
| type TNE (TwITblBt arr EmptyOk i x mF mB r) Source # | |
| type TE (TwITblBt arr EmptyOk i x mF mB r) Source # | |
| type Stack (TwITblBt arr c i x mF mB r) Source # | |
| type TermArg (TwITblBt arr c i x mF mB r) Source # | |