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

Safe HaskellNone
LanguageHaskell2010

ADP.Fusion.TH.Backtrack

Contents

Description

Backtracking which uses lists internally. The basic idea is to convert each Stream into a list. The consumer consumes the stream lazily, but allows for fusion to happen. The hope is that this improves total performance in those cases, where backtracking has significant costs.

Synopsis

Documentation

class ProductBacktracking sigF sigB where Source

Backtracking products of f and b. Choice in f needs to be reduced to a scalar value. It is then compared to the fst values in b. From those, choice b selects.

Associated Types

type SigBacktracking sigF sigB :: * Source

Methods

(<||) :: sigF -> sigB -> SigBacktracking sigF sigB Source

class ProductCombining sigF sigB where Source

The ADP-established product operation. Returns a vector of results, along the lines of what the ADP f *** b provides.

Associated Types

type SigCombining sigF sigB :: * Source

Methods

(***) :: sigF -> sigB -> SigCombining sigF sigB Source

makeProductInstances :: Name -> Q [Dec] Source

Creates instances for all products given a signature data type.

getMonadName :: [TyVarBndr] -> Maybe Name Source

Returns the Name of the monad variable.

getObjectiveNames :: [VarStrictType] -> Maybe (Name, Name, Name, Name) Source

Returns the Names of the objective function variables, as well as the name of the objective function itself.

Constructions for the different algebra types.

buildLeftType :: Name -> (Name, Name, Name) -> (Name, Name) -> [TyVarBndr] -> Type Source

The left algebra type. Assumes that in choice :: Stream m x -> m r we have that x ~ r.

buildRightType :: Name -> (Name, Name, Name) -> (Name, Name, Name) -> [TyVarBndr] -> Type Source

Here, we do not set any restrictions on the types m and r.

buildSigBacktrackingType :: Name -> (Name, Name, Name) -> Name -> (Name, Name, Name) -> [TyVarBndr] -> Type Source

Build up the type for backtracking. We want laziness in the right return type. Hence, we have AppT ListT (VarT xR) ; i.e. we want to return results in a list.

buildSigCombiningType :: Name -> Name -> (Name, Name, Name) -> (Name, Name, Name) -> (Name, Name, Name) -> [TyVarBndr] -> TypeQ Source

Build up the type for backtracking. We want laziness in the right return type. Hence, we have AppT ListT (VarT xR).

genAlgProdFunctions :: Choice -> Name -> [VarStrictType] -> [VarStrictType] -> [VarStrictType] -> Q Clause Source

Build up attribute and choice function. Here, we actually bind the left and right algebra to l and r.

genChoiceFunction :: Choice -> Name -> Name -> VarStrictType -> Q (Name, Exp) Source

Simple wrapper for creating the choice fun expression.

genAttributeFunction :: [Name] -> Name -> Name -> VarStrictType -> Q (Name, Exp) Source

We take the left and right function name for one attribute and build up the combined attribute function. Mostly a wrapper around recBuildLampat which does the main work.

TODO need fun names from l and r

recBuildLamPat Source

Arguments

:: [Name]

all non-terminal names

-> Name

left attribute function

-> Name

right attribute function

-> [ArgTy Name]

all arguments to the attribute function

-> Q ([Pat], Exp, Exp) 

Now things become trickly. We are given all non-terminal names (to differentiate between a terminal (stack) and a syntactic variable; the left and right function; and the arguments to this attribute function (except the result parameter). We are given the latter as a result to an earlier call to getRuleSynVarNames.

We now look at each argument and determine wether it is a syntactic variable. If so, then we actually have a tuple arguments (x,ys) where x has to optimized value and ys the backtracking list. The left function receives just x in this case. For the right function, things are more complicated, since we have to flatten lists. See buildRns.

Terminals are always given "as is" since we do not have a need for tupled-up information as we have for syntactic variables.

argTyArgs :: ArgTy Name -> Q (ArgTy Pat) Source

Look at the argument type and build the capturing variables. In particular captures synvar arguments with a 2-tuple (x,ys).

buildRns :: Exp -> [ArgTy Pat] -> ExpQ Source

NOTE

[ f x | x <- xs ]
CompE [BindS (VarP x) (VarE xs), NoBindS (AppE (VarE f) (VarE x))]

type Choice = Name -> Name -> Q Exp Source

Type for backtracking functions.

Not too interesting, mostly to keep track of choice.

buildBacktrackingChoice :: Choice Source

Build up the backtracking choice function. This choice function will backtrack based on the first result, then return only the second.

TODO it should be (only?) this function we will need to modify to build all algebra products.

ysM can't be unboxed, as snd of each element is a list, lazily consumed. We build up ysM as this makes fusion happen. Of course, this is a boxed vector and not as efficient, but we gain the ability to have lazily created backtracking from this!

This means strict optimization AND lazy backtracking

streamToVector :: Monad m => Stream m x -> m (Vector x) Source

Transform a monadic stream monadically into a vector.

TODO Improve code!

vectorToStream :: Monad m => Vector x -> Stream m x Source

Transform a vector into a monadic stream.

TODO improve code!

getRuleSynVarNames :: [Name] -> Type -> [ArgTy Name] Source

Gets the names used in the evaluation function. This returns one Name for each variable.

In case of TupleT 0 the type is () and there isn't a name to go with it. We just mkName "()" a name, but this might be slightly dangerous? (Not really sure if it indeed is)

With AppT _ _ we have a multidim terminal and produce another hackish name to be consumed above.

AppT (AppT ArrowT (AppT (AppT (ConT Data.Array.Repa.Index.:.) (AppT (AppT (ConT Data.Array.Repa.Index.:.) (ConT Data.Array.Repa.Index.Z)) (VarT c_1627675270))) (VarT c_1627675270))) (VarT x_1627675265)

data ArgTy x Source

Constructors

SynVar

This SynVar spans the full column of tapes; i.e. it is a normal syntactic variable.

Fields

synVarName :: x
 
Term

We have just a single-tape grammar and as such just a single-dimensional terminal. We call this term, because StackedTerms will be rewritten to just Term!

Fields

termName :: x
 
StackedTerms

We have a multi-tape grammar with a stack of just terminals. We normally can ignore the contents in the functions above, but keep them anyway.

Fields

stackedTerms :: [ArgTy x]
 
StackedVars

We have a multi-tape grammar, but the stack contains a mixture of ArgTys.

Fields

stackedVars :: [ArgTy x]
 
NilVar

A single-dim () case

Result

The result type name

Fields

result :: x
 

Instances

Eq x => Eq (ArgTy x) 
Show x => Show (ArgTy x) 

unpackArgTy :: Show x => ArgTy x -> x Source

flattenSynVars :: ArgTy x -> [x] Source

Get all synvars, even if deep in a stack