Property definitions

ai $ SearchSolver :: defaultinit
# A running solver for a given problem, to configure and control.
#
# For a given problem, a lot of variation of search algorithms can be made.
# Thus this class permit the user to control the parameters of the search algorithm.
#
# Note that this class is not meant to be specialized, and usually not instantiated directly.
#
#
# # Basic run and result.
#
# 1. Instantiate it with the method `breadth_first`, `depth_first`, or `astar` from `SearchProblem`.
# 2. Apply the method `run`, that will search and return a solution.
# 3. Retrieve information from the solution.
#
# ~~~~nitish
# var p: SearchProblem = new MyProblem
# var res = p.astar.run
# if res != null then print "Found plan with {res.depth} actions, that cost {res.cost}: {res.plan.join(", ")}"
# ~~~~
#
#
# # Step-by-step runs and multiple runs
#
# The `run_steps` method (see also `steps`, and `steps_limit`) can be used to run only a maximum number of steps.
# This method can be used as a *co-routine* and run them periodically for a small amount of time.
#
# `run` and `run_steps` return the next solution.
# A subsequent call to `run` returns the following solution and so on.
#
# When there is no more solutions available, `is_running` become false.
#
#
# # Search-trees
#
# Internally, solvers use a search-tree where nodes are labeled with states, and edges are labeled with actions.
# See `SearchNode` for details.
#
# The `run` method return a `SearchNode` that can be used to retrieve a lot of useful information,
# like the full `path` or the `plan`.
#
#
# # Configuration
#
# The solver provide some *knobs* to control how the search-tree is visited.
#
# * `memorize` (see also `memorize_late`)
# * `do_revisit` (see also `revisits`)
# * `depth_limit` (see also `iterative_deepening` and `depth_limit_reached`)
class SearchSolver[S: Object, A]
	# The problem currently solved
	var problem: SearchProblem[S, A]

	# The currently open nodes to process.
	# They are the open nodes.
	#
	# It is the nature of the queue that control how the solver works.
	# However, the methods `SearchProblem::breadth_first`, `SearchProblem::depth_first`,
	# and `SearchProblem::astar` takes care of its correct initialization.
	private var todo: Queue[SearchNode[S, A]]

	# Is the solver still running?
	# A running solver has not yet exhausted all the possible solutions.
	var is_running: Bool = true

	# Does the solver need to memorize visited states?
	# When activated, there is an increased memory consumption since
	# all visited states must be kept in memory,
	# However, there is real a gain, since visited nodes are not
	# revisited (unless needed by `do_revisit`)
	#
	# Default: `true`
	#
	# Note: If the graph of states has circuits, then a memory-less search may not terminate.
	var memorize: Bool = true is writable

	# Use memory only on visited (closed) state.
	# Less memory operations, but two big drawbacks:
	# * duplicated nodes can fill the `todo` queue (and the memory)
	# * duplicated nodes require more invocation of `SearchProblem::heuristic`
	#
	# Note: if `memorize` is false, then this has no effect.
	#
	# Default: `false`
	var memorize_late: Bool = false is writable

	# Storage of nodes when `memorize` is activated
	# Each state is associated with a node.
	# This permit:
	#   * to avoid to revisit visited nodes (see `do_revisit`)
	#   * to avoid to reinvoke `heuristic` on known states (unless `memorize_late` is set)
	private var memory: Map[S, SearchNode[S, A]] = new HashMap[S, SearchNode[S, A]]

	# Total number of time an already memorized node is seen again.
	# If `memorize_late` is set, then only visited nodes are counted.
	# Otherwise, nodes in the todo-list are also considered.
	var memorized = 0

	# Revisit states when a better path to them is found.
	# Such revisits generally triggers more revisits because they yield
	# better path to their neighbors.
	#
	# If `false`, visited states are never revisited.
	#
	# With astar and an admissible heuristic, no visited node should be revisited.
	# If the heuristic is not admissible, one may consider set this to `true`.
	#
	# Obviously, if `memorize` is false, then the value has no specific effect
	# since all states are considered unvisited.
	#
	# Default: `false`.
	#
	# See also `revisits` and `SearchNode::revisits`.
	var do_revisit: Bool = false is writable

	# Total number of states (potentially) revisited.
	#
	# It is the number of time that a better path to a visited state is found.
	# With astar and a really admissible heuristic, this number should stay 0.
	# So check this value if you are not sure of the heuristic.
	#
	# Note that states are effectively revisited if `do_revisit` is activated.
	var revisits = 0

	# The solution found by the last `run`.
	#
	# ensure `solution != null implies problem.is_goal(solution.state)`
	var solution: nullable SearchNode[S,A] = null

	# Nearest solution found (up to date).
	# The nearest solution is the one with the smallest heuristic value.
	# The cost is not considered.
	var nearest_solution: nullable SearchNode[S,A] = null

	# Limit in the depth search.
	#
	# States found above this limit are not considered.
	#
	# Use 0 for no limit.
	# Default: 0
	# See also: `iterative_deepening`
	var depth_limit: Int = 0 is writable

	# How much time a `depth_limit` was reached?
	#
	# This can be used to query if some solutions may have been
	# ignored because of a `depth_limit`.
	#
	# This is also used automatically if `iterative_deepening` is activated.
	var depth_limit_reached: Int = 0

	# Increase amount for an iterative deepening search.
	# It =0, then the iterative deepening search is disabled.
	# If >0, then `depth_limit` is automatically increased when the todo
	# queue is empty but the `depth_limit` was reached in the previous iteration.
	# Default: 0
	var iterative_deepening: Int = 0

	# The total steps executed since the beginning
	# A step is the visit of a node in the `todo`-list
	var steps: Int = 0

	# The total number of nodes created
	var nodes = 0

	# Limit in the number of steps for a `run`.
	#
	# One can modify this value then `run` or just call `run_steps`.
	#
	# Use 0 for no limit.
	# Default: 0
	var steps_limit: Int = 0 is writable

	# Total number of neighbors considered.
	var neighbors = 0

	# The average number of neighbors by nodes.
	fun branching_factor: Float do return neighbors.to_f / steps.to_f

	# Update `steps_limit` then just run some additional steps
	# Return the best solution so far (if any)
	fun run_steps(steps: Int): nullable SearchNode[S,A]
	do
		assert steps > 0
		self.steps_limit = self.steps + steps
		return run
	end

	# Reset the search from the initial state.
	# Is used at the beginning and with `iterative_deepening`.
	private fun start
	do
		assert todo.is_empty
		depth_limit_reached = 0
		var initial_node = problem.initial_node
		if memorize and not memorize_late then memory[initial_node.state] = initial_node
		initial_node.id = nodes
		nodes += 1
		todo.add initial_node
	end

	# Run the solver and return the next solution (if any)
	# Return null is one of these is true:
	# * `steps_limit` is reached
	# * the `todo` queue is empty (eg. no reachable solution)
	fun run: nullable SearchNode[S,A]
	do
		if steps == 0 then start

		var nearest = nearest_solution
		loop
			# Enough work
			if steps_limit > 0 and steps >= steps_limit then break

			#print "todo={todo.length}"
			#print "  {todo.join("\n  ")}"

			# Next node, please
			if todo.is_empty then
				# iterative depth search?
				if depth_limit <= 0 or iterative_deepening <= 0 or depth_limit_reached == 0 then
					is_running = false
					break
				end

				depth_limit += iterative_deepening
				start
			end
			var node = todo.take

			# Skip `old` stuff
			# Because `Queue` has no remove :(
			if node.drop then continue

			var state = node.state

			if memorize and memorize_late then
				# Is the state already visited?
				var old = memory.get_or_null(state)
				if old != null then
					memorized += 1
					if old.cost - node.cost < problem.epsilon then continue
					revisits += 1
					if not do_revisit then
						old.revisits += 1
						continue
					end
					node.revisits = old.revisits + 1
				end
				memory[state] = node
			end

			steps += 1
			assert node.steps == 0
			node.steps = steps
			self.node = node

			# Keep trace to the nearest
			if nearest == null or node.heuristic < nearest.heuristic then
				nearest = node
				nearest_solution = node
			end

			#print "try {node}"
			#print "try {node}; todo={todo.length}"

			# Won?
			if problem.is_goal(state) then
				solution = node
				return node
			end

			# Ignore successors states if the depth limit is reached
			if depth_limit > 0 and node.depth >= depth_limit then
				depth_limit_reached += 1
				continue
			end

			# Now, expand!
			var actions = problem.actions(state)
			if actions == null then continue
			for action in actions do
				neighbors += 1

				# Fast track if no memory or late memory
				if not memorize or memorize_late then
					var new_node = node.apply_action(action)
					new_node.id = nodes
					nodes += 1
					todo.add(new_node)
					continue
				end

				# Get the state and the cost. Do not create the node yet.
				var new_state = problem.apply_action(state, action)
				var new_cost = node.cost + problem.cost(state, action, new_state)

				# So check if the state was already seen
				var old = memory.get_or_null(new_state)
				if old != null then
					memorized += 1
					# If not better, then skip
					if old.cost - new_cost < problem.epsilon then continue
					# If visited and do not revisit, then skip
					if old.steps > 0 and not do_revisit then
						old.revisits += 1
						revisits += 1
						continue
					end
					# Even if `==`, reuse the same state object so
					# * it may helps the GC
					# * user-cached things in the previous state can be reused
					new_state = old.state
				end

				# Finally, create the node
				var new_node = new SearchNode[S, A](problem, new_state, node, action, new_cost, node.depth+1)
				new_node.id = nodes
				nodes += 1

				if old == null then
					# Compute heuristic and cost
					new_node.compute_heuristic
				else
					# Reuse heuristic and update the cost
					var h = old.heuristic
					new_node.heuristic = h
					new_node.score = new_cost + h

					# Is `old` a visited node?
					if old.steps == 0 then
						# Old is still in the todo list, so drop it
						old.drop = true
					else
						# Old was visited, so revisit it
						new_node.revisits = old.revisits + 1
						revisits += 1
						#print "found {old.cost}>{new_cost}:{old.cost>new_cost} d={old.cost-new_cost}\n\t{old}\nthat is worse than\n\t{new_node}"
					end
				end
				memory[new_state] = new_node

				todo.add(new_node)
			end
		end
		return null
	end

	# The last visited node.
	# Unless when debugging, the last visited node is not really meaningful.
	var node: nullable SearchNode[S, A] = null

	redef fun to_s
	do
		var res ="steps={steps} nodes={nodes} todo={todo.length}"
		if neighbors > 0 then res += " n={neighbors} (bf={branching_factor})"
		if revisits > 0 then res += " re={revisits}"
		if memorized > 0 then res += " mem={memorized}"
		var n = solution
		if n != null then
			res += " last={n}"
		else
			n = nearest_solution
			if n != null then res += " near={n}"
		end
		return res
	end

	# Run the configuration number `i`, for `steps` number of steps.
	# The message `msg` suffixed by the name of the configuration is printed followed by the result
	#
	# This method is used by `SearchProblem::run_configs`
	fun run_config(steps: Int, i: Int, msg: String): Bool
	do
		do
			if i == 0 then
				msg += " -mem"
				memorize = false
				break
			end
			i -= 1

			var mems = problem.make_memory
			memory = mems[i % mems.length]
			msg += " {memory.class_name}"
			i = i / mems.length

			if i % 2 == 0 then
				msg += " +mem"
				memorize = true
				memorize_late = false
			else
				msg += " +mem_late"
				memorize = true
				memorize_late = true
			end
			i = i / 2

			if i % 2 == 0 then
				msg += " +revisit"
				do_revisit = true
			else
				msg += " -revisit"
				do_revisit = false
			end
			i = i / 2

			if i >= 1 then return true

		end
		print msg

		var t = new Clock
		run_steps(steps)
		print "\t{self}"
		var l = t.lapse
		print "\ttime={l}"
		return false
	end
end
lib/ai/search.nit:186,1--604,3