LogicGrowsOnTrees-1.0.0.0.1: a parallel implementation of logic programming using distributed tree exploration

Safe HaskellNone

LogicGrowsOnTrees.Examples.Queens.Advanced

Contents

Description

This module contains a heavily optimized solver for the n-queens problems. Specifically, it uses the following tricks:

  • symmetry breaking to prune redundant solutions
  • unpacked datatypes instead of multiple arguments
  • optimized getOpenings
  • C code for the inner-most loop
  • INLINEs in many places in order to create optimized specializations of the generic functions

Benchmarks were used to determine that all of these tricks resulted in performance improvements using GHC 7.4.3.

Synopsis

Types

data NQueensSymmetry Source

The possible board symmetries.

Constructors

NoSymmetries

the board has no symmetries at all

Rotate180Only

the board is symmetric under 180 degree rotations

AllRotations

the board is symmetric under all rotations

AllSymmetries

the board is symmetric under all rotations and reflections

type NQueensSolution = [(Word, Word)]Source

Type alias for a solution, which takes the form of a list of coordinates.

type NQueensSolutions = [NQueensSolution]Source

Type alias for a list of solutions.

data PositionAndBit Source

Represents a position and bit at that position.

data PositionAndBitWithReflection Source

Like PositionAndBit, but also including the same for the reflection of the position (i.e., one less than the board size minus the position).

Main algorithm

nqueensGenericSource

Arguments

:: (MonadPlus m, Typeable α, Typeable β) 
=> ([(Word, Word)] -> α -> α)

function that adds a list of coordinates to the partial solution

-> (Word -> NQueensSymmetry -> α -> m β)

function that finalizes a partial solution with the given board size and symmetry

-> α

initial partial solution

-> Word

board size

-> m β

the final result

Interface to the main algorithm; note that α and β need to be Typeable because of an optimization used in the C part of the code. This function takes functions for its first two operators that operate on partial solutions so that the same algorithm can be used both for generating solutions and counting them; the advantage of this approach is that it is much easier to find problems in the generated solution than it is in their count, so we can test it by looking for problems in the generated solutions, and when we are assured that it works we can trust it to obtain the correct counts.

Symmetry breaking

A performance gain can be obtained by factoring out symmetries because if, say, a solution has rotational symmetry, then that means that there are four configurations that are equivalent, and so we would ideally like to prune three of these four equivalent solutions.

I call the approach used here symmetry breaking. The idea is we start with a perfectly symmetrical board (as it has nothing on it) and then we work our way from the outside in. We shall use the term layer to refer to a set of board positions that form a centered (hollow) square on the board, so the outermost layer is the set of all positions at the boundary of the board, the next layer in is the square just nested in the outermost layer, and so in. At each step we either preserve a given symmetry for the current layer or we break it; in the former case we stay within the current routine to try to break it in the next layer in, in the latter case we jump to a routine designed to break the new symmetry in the next layer in. When all symmetries have been broken, we jump to the brute-force search code. If we place all of the queens while having preserved one or more symmetries, then either we apply the rotations and reflections of the symmetry to generate all of the solutions or we multiply the solution count by the number of equivalent solutions.

This code is unforunately quite complicated because there are many possibilities for how to break or not break the symmetries and at each step it has to place between 0 and 4 queens in such a way as to not conflict with any queen that has already been placed.

Each function takes callbacks for each symmetry rather than directly calling nqueensBreak90, etc. in order to ease testing.

nqueensStartSource

Arguments

:: MonadPlus m 
=> ([(Word, Word)] -> α -> α)

function that adds a list of coordinates to the partial solutions

-> (α -> NQueensBreak90State -> m β)

function to break the rotational symmetry for the next inner layer

-> (α -> NQueensBreak180State -> m β)

function to break the 180-degree rotational symmetry for the next inner layer

-> (α -> Int -> NQueensSearchState -> m β)

function to apply a brute-force search

-> α

partial solution

-> Word

board size

-> m β

the final result

Break the reflection symmetry.

nqueensBreak90Source

Arguments

:: MonadPlus m 
=> ([(Word, Word)] -> α -> α)

function that adds a list of coordinates to the partial solutions

-> (α -> m β)

function that finalizes the partial solution

-> (α -> NQueensBreak90State -> m β)

function to break the rotational symmetry for the next inner layer

-> (α -> NQueensBreak180State -> m β)

function to break the 180-degree rotational symmetry for the next inner layer

-> (α -> Int -> NQueensSearchState -> m β)

function to apply a brute-force search

-> α

partial solution

-> NQueensBreak90State

current state

-> m β

the final result

Break the 90-degree rotational symmetry at the current layer.

nqueensBreak180Source

Arguments

:: MonadPlus m 
=> ([(Word, Word)] -> α -> α)

function that adds a list of coordinates to the partial solutions

-> (α -> m β)

function that finalizes the partial solution

-> (α -> NQueensBreak180State -> m β)

function to break the 180-degree rotational symmetry for the next inner layer

-> (α -> Int -> NQueensSearchState -> m β)

function to apply a brute-force search

-> α

partial solution

-> NQueensBreak180State

current state

-> m β

the final result

Break the 180-degree rotational symmetry at the current layer.

Brute-force search

After the symmetry has been fully broken, the brute-force approach attempts to place queens in the remaining inner sub-board. When the number of queens falls to 10 or less, it farms the rest of the search out to a routine written in C.

nqueensSearchSource

Arguments

:: (MonadPlus m, Typeable α, Typeable β) 
=> ([(Word, Word)] -> α -> α)

function that adds a list of coordinates to the partial solutions

-> (α -> m β)

function that finalizes the partial solution

-> α

partial solution

-> Int

board size

-> NQueensSearchState

current state

-> m β

the final result

Using brute-force to find placements for all of the remaining queens.

nqueensBruteForceGenericSource

Arguments

:: (MonadPlus m, Typeable α, Typeable β) 
=> ([(Word, Word)] -> α -> α)

function that adds a list of coordinates to the partial solutions

-> (α -> m β)

function that finalizes the partial solution

-> α

initial solution

-> Word

board size

-> m β

the final result

Interface for directly using the brute-force search approach

nqueensBruteForceSolutions :: MonadPlus m => Word -> m NQueensSolutionSource

Generates the solutions to the n-queens problem with the given board size.

nqueensBruteForceCount :: MonadPlus m => Word -> m WordSumSource

Generates the solution count to the n-queens problem with the given board size.

C inner-loop

c_LogicGrowsOnTrees_Queens_count_solutionsSource

Arguments

:: CUInt

board size

-> CUInt

number of queens remaining

-> CUInt

row number

-> Word64

occupied rows

-> Word64

occupied columns

-> Word64

occupied negative diagonals

-> Word64

occupied positive diagonals

-> FunPtr (CUInt -> CUInt -> IO ())

function to push a coordinate on the partial solution; may be NULL ^

-> FunPtr (IO ())

function to pop a coordinate from partial solution; may be NULL ^

-> FunPtr (IO ())

function to finalize a solution; may be NULL ^

-> IO CUInt 

C code that performs a brute-force search for the remaining queens. The last three arguments are allowed to be NULL, in which case they are ignored and only the count is returned.

mkPushValue :: (CUInt -> CUInt -> IO ()) -> IO (FunPtr (CUInt -> CUInt -> IO ()))Source

wrapper stub for the push value function pointer

mkPopValue :: IO () -> IO (FunPtr (IO ()))Source

wrapper stub for the pop value function pointer

mkFinalizeValue :: IO () -> IO (FunPtr (IO ()))Source

wrapper stub for the finalize value function pointer

nqueensCSearchSource

Arguments

:: forall α m β . (MonadPlus m, Typeable α, Typeable β) 
=> ([(Word, Word)] -> α -> α)

function that adds a list of coordinates to the partial solutions

-> (α -> m β)

function that finalizes the partial solution

-> α

partial solution

-> Int

board size

-> Int

window start

-> NQueensSearchState

current state

-> m β

the final result

Calls C code to perform a brute-force search for the remaining queens. The types α and β must be Typeable because this function actually optimizes for the case where only counting is being done by providing null values for the function pointer inputs.

nqueensCGenericSource

Arguments

:: (MonadPlus m, Typeable α, Typeable β) 
=> ([(Word, Word)] -> α -> α)

function that adds a list of coordinates to the partial solutions

-> (α -> m β)

function that finalizes the partial solution

-> α

initial value

-> Word

the board size

-> m β

the final result

Interface for directly using the C search approach

nqueensCSolutions :: MonadPlus m => Word -> m NQueensSolutionSource

Generates the solutions to the n-queens problem with the given board size.

nqueensCCount :: MonadPlus m => Word -> m WordSumSource

Generates the solution count to the n-queens problem with the given board size.

Helper functions

allRotationsAndReflectionsOfSource

Arguments

:: Word

board size

-> NQueensSolution

given solution

-> NQueensSolutions

all rotations and reflections of the given solution

Computes all rotations and reflections of the given solution.

allRotationsOfSource

Arguments

:: Word

board size

-> NQueensSolution

given solution

-> NQueensSolutions

all rotations of the given solution

Computes all rotations of the given solution.

convertSolutionToWord :: [(Int, Int)] -> [(Word, Word)]Source

Converts coordinates of type Int to type Word.

extractExteriorFromSolutionSource

Arguments

:: Word

board size

-> Word

number of outer layers to extract

-> NQueensSolution

given solution

-> NQueensSolution

the outermost layers of the solution

Extracts the outermost layers of a solution.

getOpeningsSource

Arguments

:: MonadPlus m 
=> Int

board size

-> Word64

occupied positions

-> m PositionAndBit

open positions and their corresponding bits

Get the openings for a queen

getSymmetricOpeningsSource

Arguments

:: MonadPlus m 
=> Int

board size

-> Word64

occupied positions

-> m PositionAndBitWithReflection

open positions and their corresponding bits and reflections

Get the symmetric openings for a queen

hasReflectionSymmetrySource

Arguments

:: Word

board size

-> NQueensSolution

given solution

-> Bool

true if the given solution has reflection symmetry

Checks if a solution has reflection symmetry.

hasRotate90SymmetrySource

Arguments

:: Word

board size

-> NQueensSolution

given solution

-> Bool

true if the given solution has 90-degree rotation symmetry

Checks if a solution has 90-degree rotation symmetry.

hasRotate180SymmetrySource

Arguments

:: Word

board size

-> NQueensSolution

given solution

-> Bool

true if the given solution has 180-degree rotation symmetry

Checks if a solution has 180-degree rotation symmetry.

multiplicityForSymmetry :: NQueensSymmetry -> WordSource

Returns the number of equivalent solutions for a solution with a given symmetry.

multiplySolutionSource

Arguments

:: MonadPlus m 
=> Word

board size

-> NQueensSymmetry

the symmetry of the solution

-> NQueensSolution

a solution with the given symmetry

-> m NQueensSolution

the equivalent solutions of the given solution

Gets all of the equivalent solutions with an equivalent symmetry.

reflectBits :: Word64 -> Word64Source

Reflects the bits in a number so that each bit at position i is moved to position -i (i.e., what you get when you take a bit at position 0 and rotate it i positions to the right)

reflectSolutionSource

Arguments

:: Word

board size

-> NQueensSolution

given solution

-> NQueensSolution

the solution with its columns reflected

Reflects the columns of a solution

rotate180Source

Arguments

:: Word

board size

-> NQueensSolution

given solution

-> NQueensSolution

the given solution rotated by 180 degrees

Rotate a solution left by 180 degrees.

rotateLeftSource

Arguments

:: Word

board size

-> NQueensSolution

given solution

-> NQueensSolution

the given solution rotated left by 90 degrees

Rotate a solution left by 90 degrees.

rotateRightSource

Arguments

:: Word

board size

-> NQueensSolution

given solution

-> NQueensSolution

the given solution rotated right by 90 degrees

Rotate a solution right by 90 degrees.

symmetryOfSource

Arguments

:: Word

board size

-> NQueensSolution

given solution

-> NQueensSymmetry

the symmetry of the given solution

Computes the symmetry class of the given solution