In this post I’ll demonstrate my new fast-downward
library and show how it can be used to solve planning problems. The name comes from the use of the backend solver - Fast Downward. But what’s a planning problem?
Roughly speaking, planning problems are a subclass of AI problems where we need to work out a plan that moves us from an initial state to some goal state. Typically, we have:
With this, we need to find a plan:
Planning problems are essentially state space search problems, and crop up in all sorts of places. The common examples are that of moving a robot around, planning logistics problems, and so on, but they can be used for plenty more! For example, the Beam library uses state space search to work out how to converge a database from one state to another (automatic migrations) by adding/removing columns.
State space search is an intuitive approach - simply build a graph where nodes are states and edges are state transitions (effects), and find a path (possibly shortest) that gets you from the starting state to a state that satisfies some predicates. However, naive enumeration of all states rapidly grinds to a halt. Forming optimal plans (least cost, least steps, etc) is an extremely difficult problem, and there is a lot of literature on the topic (see ICAPS - the International Conference on Automated Planning and Scheduling and recent International Planning Competitions for an idea of the state of the art). The fast-downward
library uses the state of the art Fast Downward solver and provides a small DSL to interface to it with Haskell.
In this post, we’ll look at using fast-downward
in the context of solving a small planning problem - moving balls between rooms via a robot. This post is literate Haskell, here’s the context we’ll be working in:
{-# language DisambiguateRecordFields #-}
module FastDownward.Examples.Gripper where
import Control.Monad
import qualified FastDownward.Exec as Exec
import FastDownward.Problem
If you’d rather see the Haskell in it’s entirety without comments, simply head to the end of this post.
As mentioned, in this example, we’ll consider the problem of transporting balls between rooms via a robot. The robot has two grippers and can move between rooms. Each gripper can hold zero or one balls. Our initial state is that everything is in room A, and our goal is to move all balls to room B.
First, we’ll introduce some domain specific types and functions to help model the problem. The fast-downward
DSL can work with any type that is an instance of Ord
.
data Room = RoomA | RoomB
deriving (Eq, Ord, Show)
adjacent :: Room -> Room
RoomA = RoomB
adjacent RoomB = RoomA
adjacent
data BallLocation = InRoom Room | InGripper
deriving (Eq, Ord, Show)
data GripperState = Empty | HoldingBall
deriving (Eq, Ord, Show)
A ball in our model is modelled by its current location. As this changes over time, it is a Var
- a state variable.
type Ball = Var BallLocation
A gripper in our model is modelled by its state - whether or not it’s holding a ball.
type Gripper = Var GripperState
Finally, we’ll introduce a type of all possible actions that can be taken:
data Action = PickUpBall | SwitchRooms | DropBall
deriving (Show)
With this, we can now begin modelling the specific instance of the problem. We do this by working in the Problem
monad, which lets us introduce variables (Var
s) and specify their initial state.
problem :: Problem (SolveResult Action)
= do problem
First, we introduce a state variable for each of the 4 balls. As in the problem description, all balls are initially in room A.
<- replicateM 4 (newVar (InRoom RoomA)) balls
Next, introduce a variable for the room the robot is in - which also begins in room A.
<- newVar RoomA robotLocation
We also introduce variables to track the state of each gripper.
<- replicateM 2 (newVar Empty) grippers
This is sufficient to model our problem. Next, we’ll define some effects to change the state of the world.
Effects are computations in the Effect
monad - a monad that allows us to read and write to variables, and also fail (via MonadPlus
). We could define these effects as top-level definitions (which might be better if we were writing a library), but here I’ll just define them inline so they can easily access the above state variables.
Effects may be used at any time by the solver. Indeed, that’s what solving planning problems is all about! The hard part is choosing effects intelligently, rather than blindly trying everything. Fortunately, you don’t need to worry about that - Fast Downward will take care of that for you!
let
The first effect takes a ball and a gripper, and attempts to pick up that ball with that gripper.
pickUpBallWithGripper :: Ball -> Gripper -> Effect Action
= do
pickUpBallWithGripper b gripper Empty <- readVar gripper -- (1)
<- readVar robotLocation -- (2)
robotRoom <- readVar b
ballLocation == InRoom robotRoom) -- (3)
guard (ballLocation
InGripper -- (4)
writeVar b HoldingBall
writeVar gripper
return PickUpBall -- (5)
First we check that the gripper is empty. This can be done concisely by using an incomplete pattern match. do
notation desugars incomplete pattern matches to a call to fail
, which in the Effect
monad simply means “this effect can’t currently be used”.
Next, we check where the ball and robot are, and make sure they are both in the same room.
Here we couldn’t choose a particular pattern match to use, because picking up a ball should be possible in either room. Instead, we simply observe the location of both the ball and the robot, and use an equality test with guard
to make sure they match.
If we got this far then we can pick up the ball. The act of picking up the ball is to say that the ball is now in a gripper, and that the gripper is now holding a ball.
Finally, we return some domain specific information to use if the solver chooses this effect. This has no impact on the final plan, but it’s information we can use to execute the plan in the real world (e.g., sending actual commands to the robot).
This effect moves the robot to the room adjacent to its current location.
moveRobotToAdjacentRoom :: Effect Action
= do
moveRobotToAdjacentRoom
modifyVar robotLocation adjacent
return SwitchRooms
This is an “unconditional” effect as we don’t have any explicit guards or pattern matches. We simply flip the current location by an adjacency function.
Again, we finish by returning some information to use when this effect is chosen.
Finally, we have an effect to drop a ball from a gripper.
dropBall :: Ball -> Gripper -> Effect Action
= do
dropBall b gripper HoldingBall <- readVar gripper -- (1)
InGripper <- readVar b
<- readVar robotLocation -- (2)
robotRoom Empty -- (3)
writeVar gripper InRoom robotRoom) -- (4)
writeVar b (
return DropBall -- (5)
First we check that the given gripper is holding a ball, and the given ball is in a gripper.
If we got here then those assumptions hold. We’ll update the location of the ball to be the location of the robot, so first read out the robot’s location.
Empty the gripper
Move the ball.
And we’re done! We’ll just return a tag to indicate that this effect was chosen.
With our problem modelled, we can now attempt to solve it. We invoke solve
with a particular search engine (in this case A* with landmark counting heuristics). We give the solver two bits of information:
InRoom RoomB
.
solve
cfg| b <- balls, g <- grippers ]
( [ pickUpBallWithGripper b g ++ [ dropBall b g | b <- balls, g <- grippers ]
++ [ moveRobotToAdjacentRoom ]
)?= InRoom RoomB | b <- balls ] [ b
So far we’ve been working in the Problem
monad. We can escape this monad by using runProblem :: Problem a -> IO a
. In our case, a
is SolveResult Action
, so running the problem might give us a plan (courtesy of solve
). If it did, we’ll print the plan.
main :: IO ()
= do
main <- runProblem problem
res case res of
Solved plan -> do
putStrLn "Found a plan!"
zipWithM_ -> putStrLn ( show i ++ ": " ++ show step ) )
( \i step 1::Int .. ]
[
( totallyOrderedPlan plan )
->
_ putStrLn "Couldn't find a plan!"
fast-downward
allows you to extract a totally ordered plan from a solution, but can also provide a partiallyOrderedPlan
. This type of plan is a graph (partial order) rather than a list (total order), and attempts to recover some concurrency. For example, if two effects do not interact with each other, they will be scheduled in parallel.
All that’s left is to run the problem!
> main
Found a plan!
1: PickUpBall
2: PickUpBall
3: SwitchRooms
4: DropBall
5: DropBall
6: SwitchRooms
7: PickUpBall
8: PickUpBall
9: SwitchRooms
10: DropBall
11: DropBall
Woohoo! Not bad for 0.02 secs, too :)
It might be interesting to some readers to understand what’s going on behind the scenes. Fast Downward is a C++ program, yet somehow it seems to be running Haskell code with nothing but an Ord
instance - there are no marshalling types involved!
First, let’s understand the input to Fast Downward. Fast Downward requires an encoding in its own SAS format. This format has a list of variables, where each variable contains a list of values. The contents of the values aren’t actually used by the solver, rather it just works with indices into the list of values for a variable. This observations means we can just invent values on the Haskell side and careful manage mapping indices back and forward.
Next, Fast Downward needs a list of operators which are ground instantiations of our effects above. Ground instantiations of operators mention exact values of variables. Recounting our gripper example, pickUpBallWithGripper b gripper
actually produces 2 operators - one for each room. However, we didn’t have to be this specific in the Haskell code, so how are we going to recover this information?
fast-downward
actually performs expansion on the given effects to find out all possible ways they could be called, by non-deterministically evaluating them to find a fixed point.
A small example can be seen in the moveRobotToAdjacentRoom
Effect
. This will actually produce two operators - one to move from room A to room B, and one to move from room B to room A. The body of this Effect
is (once we inline the definition of modifyVar
)
>>= writeVar robotLocation . adjacent readVar robotLocation
Initially, we only know that robotLocation
can take the value RoomA
, as that is what the variable was initialised with. So we pass this in, and see what the rest of the computation produces. This means we evaluate adjacent RoomA
to yield RoomB
, and write RoomB
into robotLocation
. We’re done for the first pass through this effect, but we gained new information - namely that robotLocation
might at some point contain RoomB
. Knowing this, we then rerun the effect, but the first readVar
gives us two paths:
readVar robotLocation >>= \RoomA -> writeVar robotLocation RoomB -- If we read RoomA
>>= \RoomB -> writeVar robotLocation (adjacent RoomB -> RoomA) -- If we read RoomB
This shows us that robotLocation
might also be set to RoomA
. However, we already knew this, so at this point we’ve reached a fixed point.
In practice, this process is ran over all Effect
s at the same time because they may interact - a change in one Effect
might cause new paths to be found in another Effect
. However, because fast-downward
only works with finite domain representations, this algorithm always terminates. Unfortunately, I have no way of enforcing this that I can see, which means a user could infinitely loop this normalisation process by writing modifyVar v succ
, which would produce an infinite number of variable assignments.
CircuitHub are using this in production (and I mean real, physical production!) to coordinate activities in its factories. By using AI, we have a declarative interface to the production process – rather than saying what steps are to be performed, we can instead say what state we want to end up in and we can trust the planner to find a suitable way to make it so.
Haskell really shines here, giving a very powerful way to present problems to the solver. The industry standard is PDDL, a Lisp-like language that I’ve found in practice is less than ideal to actually encode problems. By using Haskell, we:
fast-downward
is available on Hackage now, and I’d like to express a huge thank you to CircuitHub for giving me the time to explore this large space and to refine my work into the best solution I could think of. This work is the result of numerous iterations, but I think it was worth the wait!
Here is the complete example, as a single Haskell block:
{-# language DisambiguateRecordFields #-}
module FastDownward.Examples.Gripper where
import Control.Monad
import qualified FastDownward.Exec as Exec
import FastDownward.Problem
data Room = RoomA | RoomB
deriving (Eq, Ord, Show)
adjacent :: Room -> Room
RoomA = RoomB
adjacent RoomB = RoomA
adjacent
data BallLocation = InRoom Room | InGripper
deriving (Eq, Ord, Show)
data GripperState = Empty | HoldingBall
deriving (Eq, Ord, Show)
type Ball = Var BallLocation
type Gripper = Var GripperState
data Action = PickUpBall | SwitchRooms | DropBall
deriving (Show)
problem :: Problem (Maybe [Action])
= do
problem <- replicateM 4 (newVar (InRoom RoomA))
balls <- newVar RoomA
robotLocation <- replicateM 2 (newVar Empty)
grippers
let
pickUpBallWithGripper :: Ball -> Gripper -> Effect Action
= do
pickUpBallWithGripper b gripper Empty <- readVar gripper
<- readVar robotLocation
robotRoom <- readVar b
ballLocation == InRoom robotRoom)
guard (ballLocation
InGripper
writeVar b HoldingBall
writeVar gripper
return PickUpBall
moveRobotToAdjacentRoom :: Effect Action
= do
moveRobotToAdjacentRoom
modifyVar robotLocation adjacentreturn SwitchRooms
dropBall :: Ball -> Gripper -> Effect Action
= do
dropBall b gripper HoldingBall <- readVar gripper
InGripper <- readVar b
<- readVar robotLocation
robotRoom InRoom robotRoom)
writeVar b (
Empty
writeVar gripper
return DropBall
solve
cfg| b <- balls, g <- grippers ]
( [ pickUpBallWithGripper b g ++ [ dropBall b g | b <- balls, g <- grippers ]
++ [ moveRobotToAdjacentRoom ]
)?= InRoom RoomB | b <- balls ]
[ b
main :: IO ()
= do
main <- runProblem problem
plan case plan of
Nothing ->
putStrLn "Couldn't find a plan!"
Just steps -> do
putStrLn "Found a plan!"
-> putStrLn $ show i ++ ": " ++ show step) [1::Int ..] steps
zipWithM_ (\i step
cfg :: Exec.SearchEngine
=
cfg Exec.AStar Exec.AStarConfiguration
=
{ evaluator Exec.LMCount Exec.LMCountConfiguration
=
{ lmFactory Exec.LMExhaust Exec.LMExhaustConfiguration
= False
{ reasonableOrders = False
, onlyCausalLandmarks = True
, disjunctiveLandmarks = True
, conjunctiveLandmarks = False
, noOrders
}= False
, admissible = False
, optimal = True
, pref = True
, alm = Exec.CPLEX
, lpSolver = Exec.NoTransform
, transform = True
, cacheEstimates
}= Nothing
, lazyEvaluator = Exec.Null
, pruning = Exec.Normal
, costType = Nothing
, bound = Nothing
, maxTime }
You can contact me via email at ollie@ocharles.org.uk or tweet to me @acid2. I share almost all of my work at GitHub. This post is licensed under a Creative Commons Attribution-NonCommercial-NoDerivs 3.0 Unported License.