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

Safe HaskellNone
LanguageHaskell2010

ADP.Fusion.SynVar.Fill

Contents

Synopsis

Documentation

data CFG Source #

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 # 

Methods

mutateCell :: (Monad om, PrimMonad om) => 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 i => MutateCell CFG ((:.) ts (TwIRec im c i x)) im i Source # 

Methods

mutateCell :: (Monad om, PrimMonad om) => 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 ZS2) => MutateCell MonotoneMCFG ((:.) ts (TwITbl im arr c ZS2 x)) im ZS2 Source # 

Methods

mutateCell :: (Monad om, PrimMonad om) => 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 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 :: (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 # 

Methods

mutateCell :: (Monad om, PrimMonad om) => 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 ZS2) => MutateCell MonotoneMCFG ((:.) ts (TwITbl im arr c ZS2 x)) im ZS2 Source # 

Methods

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

Methods

mutateCell :: (Monad om, PrimMonad om) => 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 i => MutateCell CFG ((:.) ts (TwIRec im c i x)) im i Source # 

Methods

mutateCell :: (Monad om, PrimMonad om) => 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 ((:.) ((:.) Z (Subword I)) (Subword I))) => MutateCell h ((:.) ts (TwITbl im arr c (Subword I) x)) im ((:.) ((:.) Z (Subword I)) (Subword I)) Source # 

Methods

mutateCell :: (Monad om, PrimMonad om) => 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 where Source #

Minimal complete definition

mutateTables

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 # 

Methods

mutateTables :: (Monad om, PrimMonad om) => 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 => 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.

data Q Source #

Constructors

Q 

Instances

Eq Q Source # 

Methods

(==) :: Q -> Q -> Bool #

(/=) :: Q -> Q -> Bool #

Ord Q Source # 

Methods

compare :: Q -> Q -> Ordering #

(<) :: Q -> Q -> Bool #

(<=) :: Q -> Q -> Bool #

(>) :: Q -> Q -> Bool #

(>=) :: Q -> Q -> Bool #

max :: Q -> Q -> Q #

min :: Q -> Q -> Q #

Show Q Source # 

Methods

showsPrec :: Int -> Q -> ShowS #

show :: Q -> String #

showList :: [Q] -> ShowS #

class TSBO t where Source #

Find the outermost table that has a certain big order and then fill from there.

Minimal complete definition

asDyn, fillWithDyn

Methods

asDyn :: t -> [Q] Source #

fillWithDyn :: (Monad m, PrimMonad m) => [Q] -> t -> m [Q] Source #

Instances

TSBO Z Source # 

Methods

asDyn :: Z -> [Q] Source #

fillWithDyn :: (Monad m, PrimMonad m) => [Q] -> Z -> m [Q] Source #

TSBO ts => TSBO ((:.) ts (TwIRec Id c i x)) Source # 

Methods

asDyn :: (ts :. TwIRec Id c i x) -> [Q] Source #

fillWithDyn :: (Monad m, PrimMonad m) => [Q] -> (ts :. TwIRec Id c i x) -> m [Q] 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 # 

Methods

asDyn :: (ts :. TwITbl Id arr c i x) -> [Q] Source #

fillWithDyn :: (Monad m, PrimMonad m) => [Q] -> (ts :. TwITbl Id arr c i x) -> m [Q] Source #