Safe Haskell | None |
---|---|
Language | Haskell2010 |
ADP.Fusion.SynVar.Fill
Contents
- runFreezeMTbls :: (WriteCell m ((:.) tail (MutArr m (arr sh elm), t)) sh, MPrimArrayOps arr sh elm, FreezeTables m (OnlyTables t1), IndexStream sh, PrimMonad m, ExposeTables t1, (~) * (TableFun t1) ((:.) tail (MutArr m (arr sh elm), t))) => t1 -> m (Frozen (OnlyTables t1))
- class ExposeTables t where
- type TableFun t :: *
- type OnlyTables t :: *
- expose :: t -> TableFun t
- onlyTables :: t -> OnlyTables t
- data CFG
- data MonotoneMCFG
- class MutateCell h s im om i where
- mutateCell :: Proxy h -> Int -> Int -> (forall a. im a -> om a) -> s -> i -> i -> om ()
- class MutateTables h s im om where
- mutateTables :: Proxy h -> (forall a. im a -> om a) -> s -> om s
- class TableOrder s where
- tableLittleOrder :: s -> [Int]
- tableBigOrder :: s -> [Int]
- type ZS2 = (Z :. Subword I) :. Subword I
- mutateTablesDefault :: MutateTables CFG t Id IO => t -> t
- mutateTablesWithHints :: MutateTables h t Id IO => Proxy h -> t -> t
Specialized table-filling wrapper for MTbl
s
runFreezeMTbls :: (WriteCell m ((:.) tail (MutArr m (arr sh elm), t)) sh, MPrimArrayOps arr sh elm, FreezeTables m (OnlyTables t1), IndexStream sh, PrimMonad m, ExposeTables t1, (~) * (TableFun t1) ((:.) tail (MutArr m (arr sh elm), t))) => t1 -> m (Frozen (OnlyTables t1)) Source
Run and freeze MTbl
s. 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 MTbl
s get a more thorough treatment for auto-filling.
Instances
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 (ITbl im arr c i x)) im om i Source | |
(MutateCell CFG ts im om i, PrimMonad om) => MutateCell CFG ((:.) ts (IRec im c i x)) im om 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 om ZS2, PrimMonad om) => MutateCell MonotoneMCFG ((:.) ts (ITbl im arr c ZS2 x)) im om ZS2 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)
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 | |
(PrimArrayOps arr ZS2 x, MPrimArrayOps arr ZS2 x, MutateCell MonotoneMCFG ts im om ZS2, PrimMonad om) => MutateCell MonotoneMCFG ((:.) ts (ITbl im arr c ZS2 x)) im om ZS2 Source | |
(PrimArrayOps arr i x, MPrimArrayOps arr i x, MutateCell CFG ts im om i, PrimMonad om) => MutateCell CFG ((:.) ts (ITbl im arr c i x)) im om i Source | |
(MutateCell CFG ts im om i, PrimMonad om) => MutateCell CFG ((:.) ts (IRec im c i x)) im om i 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 (ITbl im arr c (Subword I) x)) im om ((:.) ((:.) Z (Subword I)) (Subword I)) Source |
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 c i x)) im om i, PrimArrayOps arr i x, Show i, IndexStream i, TableOrder ((:.) ts (ITbl im arr c i x))) => MutateTables h ((:.) ts (ITbl im arr c i x)) im om Source |
class TableOrder s where Source
Instances
TableOrder Z Source | |
TableOrder ts => TableOrder ((:.) ts (IRec im c i x)) Source |
|
TableOrder ts => TableOrder ((:.) ts (ITbl 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 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.