set-cover-0.0.9: Solve exact set cover problems like Sudoku, 8 Queens, Soma Cube, Tetris Cube

Safe HaskellSafe
LanguageHaskell98

Math.SetCover.Exact

Description

This module provides a solver for exact set cover problems. http://en.wikipedia.org/wiki/Exact_cover

Synopsis

Documentation

data Assign label set Source #

Assign allows to associate a set with a label. If a particular set is chosen for a set cover, then its label is included in the output of partitions.

I have decided to separate sets and labels this way, since it is the easiest way to assign a meaning to a set. If you really want to know the sets in a partition, then you can fill the label field with the set.

Constructors

Assign 

Fields

Instances

Functor (Assign label) Source # 

Methods

fmap :: (a -> b) -> Assign label a -> Assign label b #

(<$) :: a -> Assign label b -> Assign label a #

assign :: label -> set -> Assign label set Source #

Construction of a labeled set.

bitVectorFromSetAssigns :: Ord a => [Assign label (Set a)] -> [Assign label (Set Integer)] Source #

You may use this to post-process a set of Assigns in order to speedup the solver considerably. You must process the whole set of Assigns at once, i.e. do not process only parts of the assignment list. The output of bitVectorFromSetAssigns should go into the solver as is.

partitions :: Set set => [Assign label set] -> [[label]] Source #

partitions [assign '0' set0, assign '1' set1, assign '2' set2] computes unions [set0, set1, set2] and tries to partition the union set using the sets set0, set1, set2. partitions returns all such partitions. If a set is chosen for a partition, then its label is included in the output. E.g. set0 = Set.fromList [0,1], set1 = Set.fromList [2], set2 = Set.fromList [0,1,2], then partitions returns ["01", "2"].

The order of partitions and the order of labels depends on the implementation and you must not rely on them.

You may use listToMaybe in order to select only the first solution.

search :: Set set => State label set -> [[label]] Source #

Start the search for partitions on a certain search state. This can be an initState or the result of performing some search steps. In the examples we use this for parallelization: We perform some steps manually and then run search on the results in parallel.

step :: Set set => State label set -> [State label set] Source #

This is the key of the search algorithm. The search algorithm tries to build partitions by adding sets to a partition list successively. A step starts on a partial partition and looks for new sets that could be added. The goal is to avoid to check a set again down in a search branch and to quickly determine search directions that lead to a dead end. To this end a search step selects a certain set element and tries all sets that contain that element and that do not overlap with the partial partition. Practically, step selects an element with the minimal number of non-overlapping sets it is contained in. If this number is zero, then the search can be aborted in this branch.

Most oftenly the power of the algorithm originates from the formulation of a problem as a set-cover problem and from the equal treatment of all elements. E.g. in the Soma cube example the algorithm chooses whether to do a case analysis on all bricks that cover a certain position, or to do a case analysis on all positions that are possible for a certain brick.

The algorithm might not be extraordinarily fast, but in all cases it consumes only little memory since it only has to maintain the current state of search.

data State label set Source #

The state of the search. usedSubsets contains the partial partition built up so far. availableSubsets is the list of sets we can still try to put into a partition. The lists usedSubsets and availableSubsets are disjoint, but their union is not necessarily equal to the list of initially given sets. There are sets not contained in the partial partition that overlap with the partial partition. Those sets are not available for extending the partition.

freeElements contains the elements that are not covered by the partial partition in usedSubsets. unions usedSubset and freeElements are disjoint and their union is the set of all elements.

Constructors

State 

Fields

Instances

Functor (State label) Source # 

Methods

fmap :: (a -> b) -> State label a -> State label b #

(<$) :: a -> State label b -> State label a #

initState :: Set set => [Assign label set] -> State label set Source #

updateState :: Set set => Assign label set -> State label set -> State label set Source #

class Set set where Source #

This class provides all operations needed for the set cover algorithm. It allows to use the same algorithm both for containers' Set and for sets represented by bit vectors.

Minimal complete definition

null, disjoint, unions, difference, minimize

Methods

null :: set -> Bool Source #

disjoint :: set -> set -> Bool Source #

unions :: [set] -> set Source #

difference :: set -> set -> set Source #

minimize :: set -> [Assign label set] -> [Assign label set] Source #

Unchecked preconditions: set must be a superset of all sets in the assign list. set must be non-empty. The list of assignments must be non-empty. The output of assigns must be a subsequence of the input assigns, that is, it must be a subset of the input and it must be in the same order. This requirement was originally needed by minimize for Map, but currently it is not utilized anywhere.

Instances

Set IntSet Source # 
Ord a => Set (Set a) Source # 

Methods

null :: Set a -> Bool Source #

disjoint :: Set a -> Set a -> Bool Source #

unions :: [Set a] -> Set a Source #

difference :: Set a -> Set a -> Set a Source #

minimize :: Set a -> [Assign label (Set a)] -> [Assign label (Set a)] Source #

C a => Set (Set a) Source # 

Methods

null :: Set a -> Bool Source #

disjoint :: Set a -> Set a -> Bool Source #

unions :: [Set a] -> Set a Source #

difference :: Set a -> Set a -> Set a Source #

minimize :: Set a -> [Assign label (Set a)] -> [Assign label (Set a)] Source #

(Ord k, Set a) => Set (Map k a) Source #

This instance supports Maps of Sets. This way you can structure your sets hierarchically. You may also use it to combine several low-level bitsets. A Map must not contain empty subsets.

Methods

null :: Map k a -> Bool Source #

disjoint :: Map k a -> Map k a -> Bool Source #

unions :: [Map k a] -> Map k a Source #

difference :: Map k a -> Map k a -> Map k a Source #

minimize :: Map k a -> [Assign label (Map k a)] -> [Assign label (Map k a)] Source #