Abstract backtrack problem of states (S) and actions (A).

This class serves to model search problems using a backtracking approach. A state, S, is a point in the search problem and fully model a given state of the world. An action, A, is an available mean of transition between two states. While there is a potential large number of distinct states and actions, there should be only a small number of possible actions from a specific state (thus, a small, or at least finite, branching factor).

The point this class is that the state is a mutable object, the roles of the actions is to modify the state.

This abstract class is generic and made to work with any kind of states and actions. Therefore, specific subclasses must be developed to implements the required services:

Basic search

The method solve returns a new solver for a backtrack search.

Introduced properties

abstract fun actions(state: S, node: BacktrackNode[A]): nullable Collection[A]

ai :: BacktrackProblem :: actions

The available and applicable actions for a given state
abstract fun apply_action(state: S, action: A)

ai :: BacktrackProblem :: apply_action

Modify state by applying action
abstract fun backtrack(state: S, action: A)

ai :: BacktrackProblem :: backtrack

Modify state by undoing action
abstract fun initial_state: S

ai :: BacktrackProblem :: initial_state

The starting state of the problem.
abstract fun is_goal(state: S): Bool

ai :: BacktrackProblem :: is_goal

Is the state a goal state?
fun solve: BacktrackSolver[S, A]

ai :: BacktrackProblem :: solve

Return a new solver

Redefined properties

redef type SELF: BacktrackProblem[S, A]

ai $ BacktrackProblem :: SELF

Type of this instance, automatically specialized in every class

All properties

fun !=(other: nullable Object): Bool

core :: Object :: !=

Have self and other different values?
fun ==(other: nullable Object): Bool

core :: Object :: ==

Have self and other the same value?
type CLASS: Class[SELF]

core :: Object :: CLASS

The type of the class of self.
type SELF: Object

core :: Object :: SELF

Type of this instance, automatically specialized in every class
abstract fun actions(state: S, node: BacktrackNode[A]): nullable Collection[A]

ai :: BacktrackProblem :: actions

The available and applicable actions for a given state
abstract fun apply_action(state: S, action: A)

ai :: BacktrackProblem :: apply_action

Modify state by applying action
abstract fun backtrack(state: S, action: A)

ai :: BacktrackProblem :: backtrack

Modify state by undoing action
protected fun class_factory(name: String): CLASS

core :: Object :: class_factory

Implementation used by get_class to create the specific class.
fun class_name: String

core :: Object :: class_name

The class name of the object.
fun get_class: CLASS

core :: Object :: get_class

The meta-object representing the dynamic type of self.
fun hash: Int

core :: Object :: hash

The hash code of the object.
init init

core :: Object :: init

abstract fun initial_state: S

ai :: BacktrackProblem :: initial_state

The starting state of the problem.
fun inspect: String

core :: Object :: inspect

Developer readable representation of self.
protected fun inspect_head: String

core :: Object :: inspect_head

Return "CLASSNAME:#OBJECTID".
abstract fun is_goal(state: S): Bool

ai :: BacktrackProblem :: is_goal

Is the state a goal state?
intern fun is_same_instance(other: nullable Object): Bool

core :: Object :: is_same_instance

Return true if self and other are the same instance (i.e. same identity).
fun is_same_serialized(other: nullable Object): Bool

core :: Object :: is_same_serialized

Is self the same as other in a serialization context?
intern fun is_same_type(other: Object): Bool

core :: Object :: is_same_type

Return true if self and other have the same dynamic type.
intern fun object_id: Int

core :: Object :: object_id

An internal hash code for the object based on its identity.
fun output

core :: Object :: output

Display self on stdout (debug only).
intern fun output_class_name

core :: Object :: output_class_name

Display class name on stdout (debug only).
fun serialization_hash: Int

core :: Object :: serialization_hash

Hash value use for serialization
fun solve: BacktrackSolver[S, A]

ai :: BacktrackProblem :: solve

Return a new solver
intern fun sys: Sys

core :: Object :: sys

Return the global sys object, the only instance of the Sys class.
abstract fun to_jvalue(env: JniEnv): JValue

core :: Object :: to_jvalue

fun to_s: String

core :: Object :: to_s

User readable representation of self.
package_diagram ai::BacktrackProblem BacktrackProblem core::Object Object ai::BacktrackProblem->core::Object ai::QueenProblem QueenProblem ai::QueenProblem->ai::BacktrackProblem

Parents

interface Object

core :: Object

The root of the class hierarchy.

Children

class QueenProblem

ai :: QueenProblem

The (eight-)queens problem, modeled naively as a BacktrackProblem.

Class definitions

ai $ BacktrackProblem
# Abstract backtrack problem of states (`S`) and actions (`A`).
#
# This class serves to model search problems using a backtracking approach.
# A state, `S`, is a point in the search problem and fully model a given state of the world.
# An action, `A`, is an available mean of transition between two states.
# While there is a potential large number of distinct states and actions, there should be only
# a small number of possible actions from a specific state (thus, a small, or at least finite, branching factor).
#
# The point this class is that the state is a mutable object, the roles of the actions is to modify
# the state.
#
# This abstract class is generic and made to work with any kind of states and actions.
# Therefore, specific subclasses must be developed to implements the required services:
#
# * `initial_state`
# * `actions`
# * `apply_action`
# * `backtrack`
# * `is_goal`
#
# # Basic search
#
# The method `solve` returns a new solver for a backtrack search.
abstract class BacktrackProblem[S: Object,A]
	# The starting state of the problem.
	# It is this object that will be modified by `apply_action` and `backtrack`.
	fun initial_state: S is abstract

	# The available and applicable actions for a given state
	# Because of `backtracking`, actions must also be reversible (see `backtrack`).
	#
	# If there is no available actions, null (or an empty collection) must be returned.
	#
	# In order to optimise the search time, it is sensible to return `null`
	# (or an empty collection) as early as possible.
	#
	# Node: to help some specific implementations, the current node is also available.
	# See `BacktrackNode` for details.
	fun actions(state: S, node: BacktrackNode[A]): nullable Collection[A] is abstract

	# Modify `state` by applying `action`
	# The `action` comes from an earlier invocation of `actions`.
	fun apply_action(state: S, action: A) is abstract

	# Modify `state` by undoing `action`
	# Because of this method, it is important that any action can be undone
	# knowing only the post-state and the action.
	fun backtrack(state: S, action: A) is abstract

	# Is the state a goal state?
	# Once a goal state is found, the solver is automatically stopped.
	# See `BacktrackSolver.run`.
	fun is_goal(state: S): Bool is abstract

	# Return a new solver
	fun solve: BacktrackSolver[S,A] do
		return new BacktrackSolver[S,A](self, initial_state)
	end
end
lib/ai/backtrack.nit:20,1--78,3