huff: A fast-foward-based planner

[ ai, bsd3, library, program ] [ Propose Tags ]

An implementation of the fast-forward planner, as a quasi-quoter.


[Skip to Readme]

Modules

[Index]

Flags

Automatic Flags
NameDescriptionDefault
examples

Build the examples

Disabled

Use -f <flag> to enable a flag, or -f -<flag> to disable that flag. More info

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

  • No Candidates
Versions [RSS] 0.1.0.0, 0.1.0.1
Change log CHANGELOG.md
Dependencies alex-tools, array, base (>=4.9 && <5), containers, hashable, heaps, huff, template-haskell, text, unordered-containers [details]
License BSD-3-Clause
Author Trevor Elliott
Maintainer awesomelyawesome@gmail.com
Category AI
Home page https://github.com/elliottt/huff
Bug tracker https://github.com/elliottt/huff/issues
Source repo head: git clone git://github.com/elliottt/huff.git -b master
Uploaded by TrevorElliott at 2016-09-09T06:26:52Z
Distributions
Executables blocksWorld
Downloads 1412 total (6 in the last 30 days)
Rating (no votes yet) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs uploaded by user
Build status unknown [no reports yet]

Readme for huff-0.1.0.1

[back to package description]

Huff

Huff is an implementation of the fast-forward forward-chaining planner in Haskell. The main interface is the quasi-quoter huff, which allows the user to define re-usable domains that can be used with the planner to solve different problems.

Example

Consider the blocks world planning domain from Chapter 11 of "Artificial Intelligence: A Modern Approach". The domain includes two actions, Move and MoveToTable, four objects, A, B, C, Table, and two predicates, On and Clear. Embedding the domain in Haskell using huff looks like this:

module Main where

import Huff

[huff|

  domain BlocksWorld {
    object Obj = A | B | C | Table

    predicate on(Obj,Obj), clear(Obj)

    operator Move(b: Obj, x: Obj, y: Obj) {
      requires: on(b,x), clear(b), clear(y)
      effect:   on(b,y), clear(x), !clear(y)
    }

    operator MoveToTable(b: Obj, x: Obj) {
      requires: on(b,x), clear(b)
      effect:   on(b,Table), clear(x)
    }
  }

|]

The quasi-quoter will introduce the following declarations:

  • A data declaration for the Obj object
  • A data declaration for the BlocksWorld domain, that will consist of two constructors Move :: Obj -> Obj -> Obj -> BlocksWorld and MoveToTable :: Obj -> Obj -> BlocksWorld
  • Two classes called Has_on and Has_clear, that define the on and clear functions, respectively
  • Instances of the two Has classes for Literal and Term
  • The blocksWorld function of the type [Literal] -> [Term] -> Spec BlocksWorld

The blocksWorld function accepts the initial state and goal, and produces a Spec BlocksWorld value that can be used in conjunction with the findPlan function to attempt to find a plan. For example, the problem specified in chapter 11 Russel and Norvig can be solved as follows:

main =
  do mb <- findPlan $ blocksWorld [ on A Table, on B Table, on C Table, clear A
                                  , clear B, clear C ]
                                  [on A B, n B C]
     print mb

Running the example will produce the output:

$ find dist-newstyle -name blocksWorld -type f -exec {} \;
Just [MoveTo B Table C, MoveTo A Table B]