A node in the search-tree visited by a SearchSolver.

In search-trees, nodes are labeled with states (S), and edges by actions (A).

The root node is labeled by the initial state of the problem.

This class is exposed to allow queries on the solution provided by the solver.

Introduced properties

fun action: nullable A

ai :: SearchNode :: action

The action used to go from parent to self (if not root)
protected fun action=(action: nullable A)

ai :: SearchNode :: action=

The action used to go from parent to self (if not root)
fun apply_action(action: A): SearchNode[S, A]

ai :: SearchNode :: apply_action

Create a new child node for the next state, according to problem.
fun cost: Float

ai :: SearchNode :: cost

The past cost (g) from the root node to self.
protected fun cost=(cost: Float)

ai :: SearchNode :: cost=

The past cost (g) from the root node to self.
init defaultinit(problem: SearchProblem[S, A], state: S, parent: nullable SearchNode[S, A], action: nullable A, cost: Float, depth: Int)

ai :: SearchNode :: defaultinit

fun depth: Int

ai :: SearchNode :: depth

The depth of self in the search tree
protected fun depth=(depth: Int)

ai :: SearchNode :: depth=

The depth of self in the search tree
fun dump

ai :: SearchNode :: dump

Just print a detailed path on the screen
fun heuristic: Float

ai :: SearchNode :: heuristic

The heuristic from self to the goal (according to problem.heuristic(state)
protected fun heuristic=(heuristic: Float)

ai :: SearchNode :: heuristic=

The heuristic from self to the goal (according to problem.heuristic(state)
fun id: Int

ai :: SearchNode :: id

The rank of creation of nodes by the solver.
protected fun id=(id: Int)

ai :: SearchNode :: id=

The rank of creation of nodes by the solver.
fun is_root: Bool

ai :: SearchNode :: is_root

Is self a root node of the search-tree?
fun parent: nullable SearchNode[S, A]

ai :: SearchNode :: parent

The previous node in the search-tree (if not root).
protected fun parent=(parent: nullable SearchNode[S, A])

ai :: SearchNode :: parent=

The previous node in the search-tree (if not root).
fun path: Sequence[SearchNode[S, A]]

ai :: SearchNode :: path

Build the sequence of nodes from the initial node to self
fun plan: Sequence[A]

ai :: SearchNode :: plan

Build a sequence of actions from the initial state to self
fun problem: SearchProblem[S, A]

ai :: SearchNode :: problem

The associated problem
protected fun problem=(problem: SearchProblem[S, A])

ai :: SearchNode :: problem=

The associated problem
fun revisits: Int

ai :: SearchNode :: revisits

The number of (potential) revisits of node.
protected fun revisits=(revisits: Int)

ai :: SearchNode :: revisits=

The number of (potential) revisits of node.
fun score: Float

ai :: SearchNode :: score

The sum of cost and heuristic
protected fun score=(score: Float)

ai :: SearchNode :: score=

The sum of cost and heuristic
fun state: S

ai :: SearchNode :: state

The state associated to self.
protected fun state=(state: S)

ai :: SearchNode :: state=

The state associated to self.
fun steps: Int

ai :: SearchNode :: steps

The number of steps needed by the solver to process self
protected fun steps=(steps: Int)

ai :: SearchNode :: steps=

The number of steps needed by the solver to process self

Redefined properties

redef type SELF: SearchNode[S, A]

ai $ SearchNode :: SELF

Type of this instance, automatically specialized in every class
redef fun to_s: String

ai $ SearchNode :: to_s

User readable representation of self.

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
fun action: nullable A

ai :: SearchNode :: action

The action used to go from parent to self (if not root)
protected fun action=(action: nullable A)

ai :: SearchNode :: action=

The action used to go from parent to self (if not root)
fun apply_action(action: A): SearchNode[S, A]

ai :: SearchNode :: apply_action

Create a new child node for the next state, according to problem.
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 cost: Float

ai :: SearchNode :: cost

The past cost (g) from the root node to self.
protected fun cost=(cost: Float)

ai :: SearchNode :: cost=

The past cost (g) from the root node to self.
init defaultinit(problem: SearchProblem[S, A], state: S, parent: nullable SearchNode[S, A], action: nullable A, cost: Float, depth: Int)

ai :: SearchNode :: defaultinit

fun depth: Int

ai :: SearchNode :: depth

The depth of self in the search tree
protected fun depth=(depth: Int)

ai :: SearchNode :: depth=

The depth of self in the search tree
fun dump

ai :: SearchNode :: dump

Just print a detailed path on the screen
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.
fun heuristic: Float

ai :: SearchNode :: heuristic

The heuristic from self to the goal (according to problem.heuristic(state)
protected fun heuristic=(heuristic: Float)

ai :: SearchNode :: heuristic=

The heuristic from self to the goal (according to problem.heuristic(state)
fun id: Int

ai :: SearchNode :: id

The rank of creation of nodes by the solver.
protected fun id=(id: Int)

ai :: SearchNode :: id=

The rank of creation of nodes by the solver.
init init

core :: Object :: init

fun inspect: String

core :: Object :: inspect

Developer readable representation of self.
protected fun inspect_head: String

core :: Object :: inspect_head

Return "CLASSNAME:#OBJECTID".
fun is_root: Bool

ai :: SearchNode :: is_root

Is self a root node of the search-tree?
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 parent: nullable SearchNode[S, A]

ai :: SearchNode :: parent

The previous node in the search-tree (if not root).
protected fun parent=(parent: nullable SearchNode[S, A])

ai :: SearchNode :: parent=

The previous node in the search-tree (if not root).
fun path: Sequence[SearchNode[S, A]]

ai :: SearchNode :: path

Build the sequence of nodes from the initial node to self
fun plan: Sequence[A]

ai :: SearchNode :: plan

Build a sequence of actions from the initial state to self
fun problem: SearchProblem[S, A]

ai :: SearchNode :: problem

The associated problem
protected fun problem=(problem: SearchProblem[S, A])

ai :: SearchNode :: problem=

The associated problem
fun revisits: Int

ai :: SearchNode :: revisits

The number of (potential) revisits of node.
protected fun revisits=(revisits: Int)

ai :: SearchNode :: revisits=

The number of (potential) revisits of node.
fun score: Float

ai :: SearchNode :: score

The sum of cost and heuristic
protected fun score=(score: Float)

ai :: SearchNode :: score=

The sum of cost and heuristic
fun serialization_hash: Int

core :: Object :: serialization_hash

Hash value use for serialization
fun state: S

ai :: SearchNode :: state

The state associated to self.
protected fun state=(state: S)

ai :: SearchNode :: state=

The state associated to self.
fun steps: Int

ai :: SearchNode :: steps

The number of steps needed by the solver to process self
protected fun steps=(steps: Int)

ai :: SearchNode :: steps=

The number of steps needed by the solver to process self
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::SearchNode SearchNode core::Object Object ai::SearchNode->core::Object

Parents

interface Object

core :: Object

The root of the class hierarchy.

Class definitions

ai $ SearchNode
# A node in the search-tree visited by a `SearchSolver`.
# In search-trees, nodes are labeled with states (`S`), and edges by actions (`A`).
#
# The root node is labeled by the initial state of the problem.
#
# This class is exposed to allow queries on the solution provided by the solver.
class SearchNode[S: Object, A]
	# A flag that indicate that `self` is virtually removed from the todo-list.
	# `self` was added to the todo-list but that a better node for the
	# same state was found latter.
	private var drop = false

	# The associated problem
	var problem: SearchProblem[S, A]

	# The state associated to `self`.
	# The state labels the node `self`.
	var state: S

	# Is `self` a root node of the search-tree?
	# ensure: `result` == `parent == null` and `result`== `action == null`
	fun is_root: Bool do return parent == null

	# The previous node in the search-tree (if not root).
	var parent: nullable SearchNode[S, A]

	# The action used to go from `parent` to `self` (if not root)
	# The action labels the edge from `parent` to `self`.
	var action: nullable A

	# The past cost (g) from the root node to `self`.
	var cost: Float

	# The heuristic from self to the goal (according to `problem.heuristic(state)`
	# It is the future cost (h)
	var heuristic: Float is noinit

	# The sum of `cost` and `heuristic`
	# It is the f function.
	var score: Float is noinit

	# Update `heuristic` and `score` according to `problem`.
	private fun compute_heuristic
	do
		var h = problem.heuristic(state)
		heuristic = h
		score = cost + h
	end

	# The depth of `self` in the search tree
	# It is the number of parents to the root node.
	var depth: Int

	# The number of steps needed by the solver to process `self`
	# It is just a useless generation number, but could be used to evaluate
	# the behavior of search algorithms.
	var steps: Int = 0

	# The rank of creation of nodes by the solver.
	# It is just a useless generation number, but could be used to evaluate
	# the behavior of search algorithms.
	var id: Int = 0

	# The number of (potential) revisits of `node`.
	# This information can be used to debug search algorithms.
	# And to detect when heuristics are not admissible.
	#
	# See `SearchSolver::revisits` and `SearchSolver::do_revisit`
	# for details.
	var revisits: Int = 0

	# Create a new child node for the next state, according to `problem`.
	# Used internally by the solvers but made public for those who want to replay a plan.
	#
	# ensure `result.parent == self`
	# ensure `result.action == action`
	fun apply_action(action: A): SearchNode[S, A]
	do
		var new_state = problem.apply_action(state, action)
		var new_cost = problem.cost(state, action, new_state)
		var new_node = new SearchNode[S, A](problem, new_state, self, action, cost + new_cost, depth+1)
		new_node.compute_heuristic
		return new_node
	end

	# Build the sequence of nodes from the initial node to `self`
	#
	# ensure `result.first.is_root and result.last == self`
	fun path: Sequence[SearchNode[S, A]]
	do
		var res = new List[SearchNode[S, A]]
		res.add(self)
		var node = parent
		while node != null do
			res.unshift(node)
			node = node.parent
		end
		return res
	end

	# Build a sequence of actions from the initial state to `self`
	# See `path` for a more detailed plan.
	fun plan: Sequence[A]
	do
		var res = new List[A]
		var node: nullable SearchNode[S, A] = self
		while node != null do
			var a = node.action
			if a != null then res.unshift(a)
			node = node.parent
		end
		return res
	end

	# Just print a detailed path on the screen
	fun dump
	do
		print "result:{state}"
		for n in path do
			var a = n.action
			if a != null then print "    + {a}"
			print "  {n.steps}: {n.state} ({n.cost}$)"
		end
	end

	redef fun to_s do return "#{steps}/{id} d={depth} f={cost+heuristic} g={cost} h={heuristic}: {state}"
	#redef fun to_s do return "#{steps} f={(cost+heuristic).to_i} g={cost.to_i} h={heuristic.to_i}"
end
lib/ai/search.nit:614,1--741,3