| Copyright | (c) Sebastian Graf 2018 |
|---|---|
| License | ISC |
| Maintainer | sgraf1337@gmail.com |
| Portability | portable |
| Safe Haskell | None |
| Language | Haskell2010 |
Datafix.Worklist
Description
This module provides the solveProblem function, which solves the description of a
DataFlowProblem by employing a worklist algorithm.
- data DependencyM graph domain a
- type Datafixable m = (Currying (ParamTypes (Domain m)) (ReturnType (Domain m)), Currying (ParamTypes (Domain m)) (m (ReturnType (Domain m))), Currying (ParamTypes (Domain m)) (ReturnType (Domain m) -> ReturnType (Domain m) -> Bool), Currying (ParamTypes (Domain m)) (ReturnType (Domain m) -> ReturnType (Domain m)), MonoMapKey (Products (ParamTypes (Domain m))), BoundedJoinSemiLattice (ReturnType (Domain m)))
- data Density graph where
- data IterationBound domain
- = NeverAbort
- | AbortAfter Int (AbortionFunction domain)
- solveProblem :: forall domain graph. GraphRef graph => Datafixable (DependencyM graph domain) => DataFlowProblem (DependencyM graph domain) -> Density graph -> IterationBound domain -> Node -> domain
- evalDenotation :: forall domain. Datafixable (DependencyM Ref domain) => ProblemBuilder (DependencyM Ref domain) (LiftedFunc domain (DependencyM Ref domain)) -> IterationBound domain -> domain
Documentation
data DependencyM graph domain a Source #
The concrete MonadDependency for this worklist-based solver.
This essentially tracks the current approximation of the solution to the
DataFlowProblem as mutable state while solveProblem makes sure we will eventually
halt with a conservative approximation.
Instances
| Monad (DependencyM graph domain) Source # | |
| Functor (DependencyM graph domain) Source # | |
| Applicative (DependencyM graph domain) Source # | |
| (Datafixable (DependencyM graph domain), GraphRef graph) => MonadDependency (DependencyM graph domain) Source # | This allows us to solve |
| type Domain (DependencyM graph domain) Source # | |
type Datafixable m = (Currying (ParamTypes (Domain m)) (ReturnType (Domain m)), Currying (ParamTypes (Domain m)) (m (ReturnType (Domain m))), Currying (ParamTypes (Domain m)) (ReturnType (Domain m) -> ReturnType (Domain m) -> Bool), Currying (ParamTypes (Domain m)) (ReturnType (Domain m) -> ReturnType (Domain m)), MonoMapKey (Products (ParamTypes (Domain m))), BoundedJoinSemiLattice (ReturnType (Domain m))) Source #
A constraint synonym for the constraints m and its associated
Domain have to suffice.
This is actually a lot less scary than you might think.
Assuming we got quantified class constraints,
Datafixable is a specialized version of this:
type Datafixable m = ( forall r. Currying (ParamTypes (Domain m)) r , MonoMapKey (Products (ParamTypes (Domain m))) , BoundedJoinSemiLattice (ReturnType (Domain m)) )
Now, let's assume a concrete Domain m ~ String -> Bool -> Int, so that
expands to the type-level list ParamTypes (String -> Bool -> Int)'[String, Bool]
and reduces to Products '[String, Bool](String, Bool).
Then this constraint makes sure we are able to
Curry the domain of
String -> Bool -> rfor allrto e.g.(String, Bool) -> r. SeeCurrying. This constraint should always be discharged automatically by the type-checker as soon asParamTypesandReturnTypesreduce for theDomainargument, which happens when the concreteis known.MonadDependencym(Actually, we do this for multiple concrete
rbecause of the missing support for quantified class constraints)We want to use a monotone map of
(String, Bool)toInt(theReturnType (Domain m)). This is ensured by theconstraint.MonoMapKey(String, Bool)This constraint has to be discharged manually, but should amount to a single line of boiler-plate in most cases, see
MonoMapKey.Note that the monotonicity requirement means we have to pull non-monotone arguments in
Domain minto theNodeportion of theDataFlowProblem.- For fixed-point iteration to work at all, the values which we iterate
naturally have to be instances of
BoundedJoinSemiLattice. That type-class allows us to start iteration from a most-optimisticbottomvalue and successively iterate towards a conservative approximation using the '(/)' operator.
data Density graph where Source #
Specifies the density of the problem, e.g. whether the domain of
Nodes can be confined to a finite range, in which case solveProblem
tries to use a Data.Vector based graph representation rather than
one based on Data.IntMap.
data IterationBound domain Source #
Expresses that iteration should or shouldn't stop after a point has been iterated a finite number of times.
Constructors
| NeverAbort | Will keep on iterating until a precise, yet conservative approximation
has been reached. Make sure that your |
| AbortAfter Int (AbortionFunction domain) | For when your The When your |
Arguments
| :: GraphRef graph | |
| => Datafixable (DependencyM graph domain) | |
| => DataFlowProblem (DependencyM graph domain) | The description of the |
| -> Density graph | Describes if the algorithm is free to use a |
| -> IterationBound domain | Whether the solution algorithm should respect a maximum bound on the
number of iterations per point. Pass |
| -> Node | The |
| -> domain |
Computes a solution to the described DataFlowProblem by iterating
transfer functions until a fixed-point is reached.
It does do by employing a worklist algorithm, iterating unstable Nodes
only.
Nodes become unstable when the point of another Node their transfer function
dependOned changed.
The sole initially unstable Node is the last parameter, and if your
domain is function-valued (so the returned Arrows expands to a function),
then any further parameters specify the exact point in the Nodes transfer
function you are interested in.
If your problem only has finitely many different Nodes , consider using
the ProblemBuilder API (e.g. datafix + evalDenotation) for a higher-level API
that let's you forget about Nodes and instead let's you focus on building
more complex data-flow frameworks.
Arguments
| :: Datafixable (DependencyM Ref domain) | |
| => ProblemBuilder (DependencyM Ref domain) (LiftedFunc domain (DependencyM Ref domain)) | A build plan for computing the denotation, possibly involving
fixed-point iteration factored through calls to |
| -> IterationBound domain | Whether the solution algorithm should respect a maximum bound on the
number of iterations per point. Pass |
| -> domain |
evalDenotation denot ib returns a value in domain that is described by
the denotation denot.
It does so by building up the DataFlowProblem corresponding to denot
and solving the resulting problem with solveProblem, the documentation of
which describes in detail how to arrive at a stable denotation and what
the IterationBound ib is for.