| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
ADP.Fusion.SynVar.Fill
Contents
- data CFG
- data MonotoneMCFG
- class MutateCell h s im i where
- class MutateTables h s im where
- class TableOrder s where
- type ZS2 = (Z :. Subword I) :. Subword I
- mutateTablesDefault :: MutateTables CFG t Id => t -> t
- mutateTablesWithHints :: MutateTables h t Id => Proxy h -> t -> t
- mutateTablesST :: (TableOrder t, TSBO t) => t -> t
- mutateTablesNew :: forall t m. (TableOrder t, TSBO t, Monad m, PrimMonad m) => t -> m t
- data Q = Q {}
- class TSBO t where
Documentation
A vanilla context-free grammar
Instances
| (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 # | |
data MonotoneMCFG Source #
This grammar is a multi-cfg in a monotone setting
Instances
| (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 # | |
Unsafely mutate ITbls and similar tables in the forward phase.
class MutateCell h s im i where Source #
Mutate a cell in a stack of syntactic variables.
TODO generalize to monad morphism via mmorph package. This will allow
 more interesting mrph functions that can, for example, track some
 state in the forward phase. (Note that this can be dangerous, we do
 not want to have this state influence forward results, unless that can
 be made deterministic, or we'll break Bellman)
Minimal complete definition
Methods
mutateCell :: (Monad om, PrimMonad om) => Proxy h -> Int -> Int -> (forall a. im a -> om a) -> s -> i -> i -> om () Source #
Instances
| MutateCell p Z im i 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 # | |
class MutateTables h s im where Source #
Minimal complete definition
Methods
mutateTables :: (Monad om, PrimMonad om) => Proxy h -> (forall a. im a -> om a) -> s -> om s Source #
Instances
| (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 # | |
class TableOrder s where Source #
Minimal complete definition
Instances
| TableOrder Z Source # | |
| TableOrder ts => TableOrder ((:.) ts (TwIRec im c i x)) Source # | 
 | 
| TableOrder ts => TableOrder ((:.) ts (TwITbl im arr c i x)) Source # | |
individual instances for filling a *single cell*
individual instances for filling a complete table and extracting the
mutateTablesDefault :: MutateTables CFG t Id => t -> t Source #
Default table filling, assuming that the forward monad is just IO.
TODO generalize to MonadIO or MonadPrim.
mutateTablesWithHints :: MutateTables h t Id => Proxy h -> t -> t Source #
Mutate tables, but observe certain hints. We use this for monotone mcfgs for now.
mutateTablesST :: (TableOrder t, TSBO t) => t -> t Source #
mutateTablesNew :: forall t m. (TableOrder t, TSBO t, Monad m, PrimMonad m) => t -> m t Source #
TODO new way how to do table filling. Because we now have heterogeneous
 tables (i) group tables by big order into different bins; (ii) check
 that each bin has the same bounds (needed? -- could we have
 smaller-sized tables once in a while); (iii) run each bin one after the
 other
TODO measure performance penalty, if any. We might need liberal INLINEABLE, and specialization. On the other hand, we can do the freeze/unfreeze outside of table filling.