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

The state (S) is a board, modeled as an array of occupied rows. The integer in each row indicates the column occupied by the queen. Since there can be only one queen by row, a single Int is enough for each row, and the whole board rows is just an Array[Int]. Only the occupied rows are stored, thus the length of rows indicates the number of occupied rows, the remaining virtual rows are considered free.

An action (A) is the column where to put a queen in the first free row, so modeled as an Int. Actions are applied until all rows are occupied by a queen.

Introduced properties

fun print_state(rows: Array[Int])

ai :: QueenProblem :: print_state

Draw a nice board
fun size: Int

ai :: QueenProblem :: size

The board size.
protected fun size=(size: Int)

ai :: QueenProblem :: size=

The board size.

Redefined properties

redef type SELF: QueenProblem

ai $ QueenProblem :: SELF

Type of this instance, automatically specialized in every class
redef fun actions(rows: Array[Int], node: BacktrackNode[Int]): nullable Collection[Int]

ai $ QueenProblem :: actions

What are the available columns for a queen in the first free row?
redef fun apply_action(rows: Array[Int], column: Int)

ai $ QueenProblem :: apply_action

The first free row become occupied with a queen placed where indicated.
redef fun backtrack(rows: Array[Int], column: Int)

ai $ QueenProblem :: backtrack

Just free the last occupied row.
redef fun initial_state: Array[Int]

ai $ QueenProblem :: initial_state

The initial state has no queens; so, no occupied rows.
redef fun is_goal(rows: Array[Int]): Bool

ai $ QueenProblem :: is_goal

Are all rows are occupied?

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 print_state(rows: Array[Int])

ai :: QueenProblem :: print_state

Draw a nice board
fun serialization_hash: Int

core :: Object :: serialization_hash

Hash value use for serialization
fun size: Int

ai :: QueenProblem :: size

The board size.
protected fun size=(size: Int)

ai :: QueenProblem :: size=

The board size.
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::QueenProblem QueenProblem ai::BacktrackProblem BacktrackProblem ai::QueenProblem->ai::BacktrackProblem core::Object Object ai::BacktrackProblem->core::Object ...core::Object ... ...core::Object->core::Object

Ancestors

interface Object

core :: Object

The root of the class hierarchy.

Parents

abstract class BacktrackProblem[S: Object, A: nullable Object]

ai :: BacktrackProblem

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

Class definitions

ai $ QueenProblem
# The (eight-)queens problem, modeled naively as a `BacktrackProblem`.
#
# The state (`S`) is a board, modeled as an array of occupied rows.
# The integer in each row indicates the column occupied by the queen.
# Since there can be only one queen by row, a single `Int` is
# enough for each row, and the whole board `rows` is just an `Array[Int]`.
# Only the occupied rows are stored, thus the length of `rows` indicates
# the number of occupied rows, the remaining virtual rows are considered free.
#
# An action (`A`) is the column where to put a queen in the first free row,
# so modeled as an Int.
# Actions are applied until all rows are occupied by a queen.
class QueenProblem
	super BacktrackProblem[Array[Int], Int]

	# The initial state has no queens; so, no occupied rows.
	redef fun initial_state do return new Array[Int]

	# The board size.
	# Hint: use 8 to be traditional.
	var size: Int

	# What are the available columns for a queen in the first free row?
	# Just look at occupied rows above and cancel the possible columns one by one.
	redef fun actions(rows, node)
	do
		# No more than 8 rows
		if rows.length >= size then return null

		# Available columns. At first, all are available.
		var columns = new Array[Bool].filled_with(true, size)

		# Look at each occupied row and cancel columns
		var i = rows.length # delta for each diagonal
		for r in rows do
			columns[r] = false # no queen under `r`
			var d = r - i
			if d >= 0 then columns[d] = false # no queen on the first diagonal
			d = r + i
			if d < size then columns[d] = false # no queen on the second diagonal
			i -= 1
		end

		# Collect the remaining columns, those that were not cancelled.
		var res = new Array[Int]
		for c in [0..size[ do if columns[c] then res.add(c)

		return res
	end

	# The first free row become occupied with a queen placed where indicated.
	redef fun apply_action(rows, column)
	do
		rows.add column
	end

	# Just `free` the last occupied row.
	redef fun backtrack(rows, column)
	do
		rows.pop
	end

	# Are all rows are occupied?
	redef fun is_goal(rows) do return rows.length >= size

	# Draw a nice board
	fun print_state(rows: Array[Int])
	do
		printn "+"
		for i in [0..size[ do printn "-"
		print "+"
		for r in rows do
			printn "|"
			for i in [0..r[ do printn "."
			printn "Q"
			for i in [r+1..size[ do printn "."
			print  "|"
		end
		for r in [rows.length..size[ do
			printn "|"
			for i in [0..size[ do printn "."
			print  "|"
		end
		printn "+"
		for i in [0..size[ do printn "-"
		print "+"
	end
end
lib/ai/examples/queens.nit:35,1--122,3