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

Safe HaskellNone
LanguageHaskell2010

ADP.Fusion.SynVar.Fill

Contents

Synopsis

Specialized table-filling wrapper for MTbls

runFreezeMTbls :: ((~#) * * (TableFun t1) ((:.) tail (MutArr m (arr sh elm), t)), ExposeTables t1, PrimMonad m, IndexStream sh, FreezeTables m (OnlyTables t1), MPrimArrayOps arr sh elm, WriteCell m ((:.) tail (MutArr m (arr sh elm), t)) sh) => 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.

Minimal complete definition

expose, onlyTables

Associated Types

type TableFun t :: * Source #

type OnlyTables t :: * Source #

Methods

expose :: t -> TableFun t Source #

onlyTables :: t -> OnlyTables t Source #

Instances

ExposeTables Z Source # 

Associated Types

type TableFun Z :: * Source #

type OnlyTables Z :: * Source #

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) => MutateCell CFG ((:.) ts (TwITbl im arr c i x)) im om i Source # 

Methods

mutateCell :: Proxy * CFG -> Int -> Int -> (forall a. im a -> om a) -> (ts :. TwITbl im arr c i x) -> i -> i -> om () Source #

(MutateCell CFG ts im om i, PrimMonad om) => MutateCell CFG ((:.) ts (TwIRec im c i x)) im om i Source # 

Methods

mutateCell :: Proxy * CFG -> Int -> Int -> (forall a. im a -> om a) -> (ts :. TwIRec im c i x) -> i -> i -> om () 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 om ZS2, PrimMonad om) => MutateCell MonotoneMCFG ((:.) ts (TwITbl im arr c ZS2 x)) im om ZS2 Source # 

Methods

mutateCell :: Proxy * MonotoneMCFG -> Int -> Int -> (forall a. im a -> om a) -> (ts :. TwITbl im arr c ZS2 x) -> ZS2 -> ZS2 -> om () Source #

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)

Minimal complete definition

mutateCell

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 Source # 

Methods

mutateCell :: Proxy * p -> Int -> Int -> (forall a. im a -> om a) -> Z -> i -> i -> om () Source #

(PrimArrayOps arr ZS2 x, MPrimArrayOps arr ZS2 x, MutateCell MonotoneMCFG ts im om ZS2, PrimMonad om) => MutateCell MonotoneMCFG ((:.) ts (TwITbl im arr c ZS2 x)) im om ZS2 Source # 

Methods

mutateCell :: Proxy * MonotoneMCFG -> Int -> Int -> (forall a. im a -> om a) -> (ts :. TwITbl im arr c ZS2 x) -> ZS2 -> ZS2 -> om () Source #

(PrimArrayOps arr i x, MPrimArrayOps arr i x, MutateCell CFG ts im om i, PrimMonad om) => MutateCell CFG ((:.) ts (TwITbl im arr c i x)) im om i Source # 

Methods

mutateCell :: Proxy * CFG -> Int -> Int -> (forall a. im a -> om a) -> (ts :. TwITbl im arr c i x) -> i -> i -> om () Source #

(MutateCell CFG ts im om i, PrimMonad om) => MutateCell CFG ((:.) ts (TwIRec im c i x)) im om i Source # 

Methods

mutateCell :: Proxy * CFG -> Int -> Int -> (forall a. im a -> om a) -> (ts :. TwIRec im c i x) -> i -> i -> om () Source #

(PrimArrayOps arr (Subword I) x, MPrimArrayOps arr (Subword I) x, MutateCell h ts im om ((:.) ((:.) Z (Subword I)) (Subword I)), PrimMonad om) => MutateCell h ((:.) ts (TwITbl im arr c (Subword I) x)) im om ((:.) ((:.) Z (Subword I)) (Subword I)) Source # 

Methods

mutateCell :: Proxy * h -> Int -> Int -> (forall a. im a -> om a) -> (ts :. TwITbl im arr c (Subword I) x) -> ((Z :. Subword I) :. Subword I) -> ((Z :. Subword I) :. Subword I) -> om () Source #

class MutateTables h s im om where Source #

Minimal complete definition

mutateTables

Methods

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

Instances

(Monad om, MutateCell h ((:.) ts (TwITbl im arr c i x)) im om 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 om Source # 

Methods

mutateTables :: Proxy * h -> (forall a. im a -> om a) -> (ts :. TwITbl im arr c i x) -> om (ts :. TwITbl im arr c i x) Source #

class TableOrder s where Source #

Minimal complete definition

tableLittleOrder, tableBigOrder

Methods

tableLittleOrder :: s -> [Int] Source #

tableBigOrder :: s -> [Int] Source #

Instances

TableOrder Z Source # 
TableOrder ts => TableOrder ((:.) ts (TwIRec im c i x)) Source #

IRecs do not need an order, given that they do not memoize.

Methods

tableLittleOrder :: (ts :. TwIRec im c i x) -> [Int] Source #

tableBigOrder :: (ts :. TwIRec im c i x) -> [Int] Source #

TableOrder ts => TableOrder ((:.) ts (TwITbl im arr c i x)) Source # 

Methods

tableLittleOrder :: (ts :. TwITbl im arr c i x) -> [Int] Source #

tableBigOrder :: (ts :. TwITbl im arr c i x) -> [Int] Source #

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.