Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module exposes a small DSL for building and solving planning problems using Fast Downward - an open source solver for classical planning problems.
Using this module, you model problems with a finite-domain representation
through state variables (see, Var
, newVar
), and model their changes through
Effect
s (see readVar
, and writeVar
). If you're familiar with software
transactional memory, an effect is like a transaction, except the process of
solving will choose the appropriate sequence for you.
Synopsis
- data Problem a
- data Var a
- newVar :: Ord a => a -> Problem (Var a)
- readVar :: Ord a => Var a -> Effect a
- writeVar :: Ord a => Var a -> a -> Effect ()
- modifyVar :: Ord a => Var a -> (a -> a) -> Effect ()
- resetInitial :: Ord a => Var a -> a -> Problem ()
- data Effect a
- data Test
- (?=) :: Ord a => Var a -> a -> Test
- any :: [Test] -> Test
- solve :: Show a => SearchEngine -> [Effect a] -> [Test] -> Problem (SolveResult a)
- data SolveResult a
- data Solution a
- runProblem :: MonadIO m => Problem a -> m a
- totallyOrderedPlan :: Solution a -> [a]
- partiallyOrderedPlan :: Ord a => Solution a -> (Graph, Vertex -> (a, Key, [Key]), Key -> Maybe Vertex)
Defining Problems
The Problem
monad is used to build a computation that describes a
particular planning problem. In this monad you can declare state variables
- Var
s - using newVar
, and you can solve planning problems using solve
.
Var
iables
A Var
is a state variable - a variable who's contents may change over
the execution of a plan. Effect
s can read and write from variables in
order to change their state.
newVar :: Ord a => a -> Problem (Var a) Source #
Introduce a new state variable into a problem, and set it to an initial starting value.
modifyVar :: Ord a => Var a -> (a -> a) -> Effect () Source #
Modify the contents of a Var
by using a function.
modifyVar v f = readVar v >>= writeVar v . f
resetInitial :: Ord a => Var a -> a -> Problem () Source #
Reset the initial state of a variable (the value that the solver will begin with).
Effect
s
An Effect
is a transition in a planning problem - a point where variables
can be inspected for their current values, and where they can take on new
values. For example, there might be an Effect
to instruct the robot to
move to a particular target location, if its current location is adjacent.
The Effect
monad supports failure, so you can guard
an Effect
to only
be applicable under particular circumstances. Continuing the above example,
we loosely mentioned the constraint that the robot must be adjacent to a
target location - something that could be modelled by using readVar
to
read the current location, and guard
to guard that this location is
adjacent to our goal.
Test
s
any :: [Test] -> Test Source #
Take the disjunction (or) of a list of Test
s to a form new a Test
that
succeeds when at least one of the given tests is true.
Caution! The use of any
introduces axioms into the problem definition,
which is not compatible with many search engines.
Solving Problems
:: Show a | |
=> SearchEngine | |
-> [Effect a] | The set of effects available to the planner. Each effect can return
some domain-specific information of type |
-> [Test] | A conjunction of tests that must true for a solution to be considered acceptable. |
-> Problem (SolveResult a) | The list of steps that will converge the initial state to a state that satisfies the given goal predicates. |
Given a particular SearchEngine
, attempt to solve a planning
problem.
data SolveResult a Source #
The result from the solver on a call to solve
.
A successful solution to a planning problem. You can unpack a Solution
into a plan by using totallyOrderedPlan
and partiallyOrderedPlan
.
runProblem :: MonadIO m => Problem a -> m a Source #
Extracting Plans
totallyOrderedPlan :: Solution a -> [a] Source #
Extract a totally ordered plan from a solution.
partiallyOrderedPlan :: Ord a => Solution a -> (Graph, Vertex -> (a, Key, [Key]), Key -> Maybe Vertex) Source #
Deorder a plan into a partially ordered plan. This attempts to recover some
concurrency when adjacent plan steps do not need to be totally ordered. The
result of this function is the same as the result of
graphFromEdges
.