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

Safe HaskellNone
LanguageHaskell2010

ADP.Fusion.SynVar.Fill

Contents

Synopsis

Specialized table-filling wrapper for MTbls

runFreezeMTbls :: (ExposeTables t1, PrimMonad m, IndexStream sh, FreezeTables m (OnlyTables t1), MPrimArrayOps arr sh elm, WriteCell m ((:.) tail (MutArr m (arr sh elm), t)) sh, (~) * (TableFun t1) ((:.) tail (MutArr m (arr sh elm), t))) => t1 -> m (Frozen (OnlyTables t1)) Source

Run and freeze MTbls. Since actually running the table-filling part is usually the last thing to do, we can freeze as well.

Expose inner mutable tables

class ExposeTables t where Source

Expose the actual mutable table with an MTbl. (Should be temporary until MTbls get a more thorough treatment for auto-filling.

Associated Types

type TableFun t :: * Source

type OnlyTables t :: * Source

Methods

expose :: t -> TableFun t Source

onlyTables :: t -> OnlyTables t Source

Instances

data CFG Source

A vanilla context-free grammar

Instances

(PrimArrayOps arr i x, MPrimArrayOps arr i x, MutateCell CFG ts im om i, PrimMonad om, Show x, Show i) => MutateCell CFG ((:.) ts (ITbl im arr i x)) im om i 

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 om ZS2, PrimMonad om) => MutateCell MonotoneMCFG ((:.) ts (ITbl im arr ZS2 x)) im om ZS2 

Unsafely mutate ITbls and similar tables in the forward phase.

class MutateCell h s im om 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)

Methods

mutateCell :: Proxy h -> Int -> Int -> (forall a. im a -> om a) -> s -> i -> i -> om () Source

Instances

Monad om => MutateCell p Z im om i 
(PrimArrayOps arr ZS2 x, MPrimArrayOps arr ZS2 x, MutateCell MonotoneMCFG ts im om ZS2, PrimMonad om) => MutateCell MonotoneMCFG ((:.) ts (ITbl im arr ZS2 x)) im om ZS2 
(PrimArrayOps arr i x, MPrimArrayOps arr i x, MutateCell CFG ts im om i, PrimMonad om, Show x, Show i) => MutateCell CFG ((:.) ts (ITbl im arr i x)) im om i 
(PrimArrayOps arr Subword x, MPrimArrayOps arr Subword x, MutateCell h ts im om ((:.) ((:.) Z Subword) Subword), PrimMonad om) => MutateCell h ((:.) ts (ITbl im arr Subword x)) im om ((:.) ((:.) Z Subword) Subword) 

class MutateTables h s im om where Source

Methods

mutateTables :: Proxy h -> (forall a. im a -> om a) -> s -> om s Source

Instances

(Monad om, MutateCell h ((:.) ts (ITbl im arr i x)) im om i, PrimArrayOps arr i x, Show i, IndexStream i, TableOrder ((:.) ts (ITbl im arr i x))) => MutateTables h ((:.) ts (ITbl im arr i x)) im om 

class TableOrder s where Source

Instances

TableOrder Z 
TableOrder ts => TableOrder ((:.) ts (ITbl im arr i x)) 

individual instances for filling a *single cell*

individual instances for filling a complete table and extracting the

mutateTablesDefault :: MutateTables CFG t Id IO => 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 IO => Proxy h -> t -> t Source

Mutate tables, but observe certain hints. We use this for monotone mcfgs for now.