fast-downward-0.2.2.0: Solve classical planning problems (STRIPS/SAS+) using Haskell & Fast Downward.
Safe HaskellNone
LanguageHaskell2010

FastDownward

Description

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 Effects (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

Defining Problems

data Problem a Source #

The Problem monad is used to build a computation that describes a particular planning problem. In this monad you can declare state variables - Vars - using newVar, and you can solve planning problems using solve.

Instances

Instances details
Monad Problem Source # 
Instance details

Defined in FastDownward

Methods

(>>=) :: Problem a -> (a -> Problem b) -> Problem b #

(>>) :: Problem a -> Problem b -> Problem b #

return :: a -> Problem a #

Functor Problem Source # 
Instance details

Defined in FastDownward

Methods

fmap :: (a -> b) -> Problem a -> Problem b #

(<$) :: a -> Problem b -> Problem a #

Applicative Problem Source # 
Instance details

Defined in FastDownward

Methods

pure :: a -> Problem a #

(<*>) :: Problem (a -> b) -> Problem a -> Problem b #

liftA2 :: (a -> b -> c) -> Problem a -> Problem b -> Problem c #

(*>) :: Problem a -> Problem b -> Problem b #

(<*) :: Problem a -> Problem b -> Problem a #

MonadIO Problem Source # 
Instance details

Defined in FastDownward

Methods

liftIO :: IO a -> Problem a #

Variables

data Var a Source #

A Var is a state variable - a variable who's contents may change over the execution of a plan. Effects 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.

readVar :: Ord a => Var a -> Effect a Source #

Read the value of a Var at the point the Effect is invoked by the solver.

writeVar :: Ord a => Var a -> a -> Effect () Source #

Write a value into Var. If the solver choses to use this particular Effect, then the Var will begin take this new 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).

Effects

data Effect a Source #

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.

Instances

Instances details
Monad Effect Source # 
Instance details

Defined in FastDownward

Methods

(>>=) :: Effect a -> (a -> Effect b) -> Effect b #

(>>) :: Effect a -> Effect b -> Effect b #

return :: a -> Effect a #

Functor Effect Source # 
Instance details

Defined in FastDownward

Methods

fmap :: (a -> b) -> Effect a -> Effect b #

(<$) :: a -> Effect b -> Effect a #

MonadFail Effect Source # 
Instance details

Defined in FastDownward

Methods

fail :: String -> Effect a #

Applicative Effect Source # 
Instance details

Defined in FastDownward

Methods

pure :: a -> Effect a #

(<*>) :: Effect (a -> b) -> Effect a -> Effect b #

liftA2 :: (a -> b -> c) -> Effect a -> Effect b -> Effect c #

(*>) :: Effect a -> Effect b -> Effect b #

(<*) :: Effect a -> Effect b -> Effect a #

Alternative Effect Source # 
Instance details

Defined in FastDownward

Methods

empty :: Effect a #

(<|>) :: Effect a -> Effect a -> Effect a #

some :: Effect a -> Effect [a] #

many :: Effect a -> Effect [a] #

Tests

data Test Source #

Tests are use to drive the solver in order to find a plan to the goal.

(?=) :: Ord a => Var a -> a -> Test Source #

Test that a Var is set to a particular value.

any :: [Test] -> Test Source #

Take the disjunction (or) of a list of Tests 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

solve Source #

Arguments

:: Show a 
=> SearchConfiguration 
-> [Effect a]

The set of effects available to the planner. Each effect can return some domain-specific information of type a which you can use to interpret the plan. This will usually be some kind of Action 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.

Constructors

Unsolvable

The problem was proven to be unsolvable.

UnsolvableIncomplete

The problem was determined to be unsolvable, but the entire search space was not explored.

OutOfMemory

The downward executable ran out of memory.

OutOfTime

The downward executable ran out of time.

CriticalError

The downward executable encountered a critical error.

InputError

The downward executable encountered an error parsing input.

Unsupported

The downward executable was called with a search engine that is incompatible with the problem definition.

Crashed String String ExitCode

Fast Downward crashed (or otherwise rejected) the given problem.

Solved (Solution a)

A solution was found.

Instances

Instances details
Functor SolveResult Source # 
Instance details

Defined in FastDownward

Methods

fmap :: (a -> b) -> SolveResult a -> SolveResult b #

(<$) :: a -> SolveResult b -> SolveResult a #

Show a => Show (SolveResult a) Source # 
Instance details

Defined in FastDownward

data Solution a Source #

A successful solution to a planning problem. You can unpack a Solution into a plan by using totallyOrderedPlan and partiallyOrderedPlan.

Instances

Instances details
Functor Solution Source # 
Instance details

Defined in FastDownward

Methods

fmap :: (a -> b) -> Solution a -> Solution b #

(<$) :: a -> Solution b -> Solution a #

Show a => Show (Solution a) Source # 
Instance details

Defined in FastDownward

Methods

showsPrec :: Int -> Solution a -> ShowS #

show :: Solution a -> String #

showList :: [Solution a] -> ShowS #

runProblem :: MonadIO m => Problem a -> m a Source #

Leave the Problem monad by running the given computation to IO.

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.