toysolver-0.0.5: Assorted decision procedures for SAT, Max-SAT, PB, MIP, etc

Portabilitynon-portable (BangPatterns, DoRec, ScopedTypeVariables, CPP, DeriveDataTypeable)
Stabilityprovisional
Maintainermasahiro.sakai@gmail.com
Safe HaskellNone

SAT

Contents

Description

A CDCL SAT solver.

It follows the design of MiniSat and SAT4J.

See also:

Synopsis

The Solver type

data Solver Source

Solver instance

newSolver :: IO SolverSource

Create a new Solver instance.

Basic data structures

type Var = IntSource

Variable is represented as positive integers (DIMACS format).

type Lit = IntSource

Positive (resp. negative) literals are represented as positive (resp. negative) integers. (DIMACS format).

literalSource

Arguments

:: Var

variable

-> Bool

polarity

-> Lit 

Construct a literal from a variable and its polarity. True (resp False) means positive (resp. negative) literal.

litNot :: Lit -> LitSource

Negation of the Lit.

litVar :: Lit -> VarSource

Underlying variable of the Lit

litPolarity :: Lit -> BoolSource

Polarity of the Lit. True means positive literal and False means negative literal.

type Clause = [Lit]Source

Disjunction of Lit.

Problem specification

newVar :: Solver -> IO VarSource

Add a new variable

newVars :: Solver -> Int -> IO [Var]Source

Add variables. newVars solver n = replicateM n (newVar solver)

newVars_ :: Solver -> Int -> IO ()Source

Add variables. newVars_ solver n >> return () = newVars_ solver n

addClause :: Solver -> Clause -> IO ()Source

Add a clause to the solver.

addAtLeastSource

Arguments

:: Solver

The Solver argument.

-> [Lit]

set of literals {l1,l2,..} (duplicated elements are ignored)

-> Int

n.

-> IO () 

Add a cardinality constraints atleast({l1,l2,..},n).

addAtMostSource

Arguments

:: Solver

The Solver argument

-> [Lit]

set of literals {l1,l2,..} (duplicated elements are ignored)

-> Int

n

-> IO () 

Add a cardinality constraints atmost({l1,l2,..},n).

addExactlySource

Arguments

:: Solver

The Solver argument

-> [Lit]

set of literals {l1,l2,..} (duplicated elements are ignored)

-> Int

n

-> IO () 

Add a cardinality constraints exactly({l1,l2,..},n).

addPBAtLeastSource

Arguments

:: Solver

The Solver argument.

-> [(Integer, Lit)]

set of terms [(c1,l1),(c2,l2),…]

-> Integer

n

-> IO () 

Add a pseudo boolean constraints c1*l1 + c2*l2 + … ≥ n.

addPBAtMostSource

Arguments

:: Solver

The Solver argument.

-> [(Integer, Lit)]

list of [(c1,l1),(c2,l2),…]

-> Integer

n

-> IO () 

Add a pseudo boolean constraints c1*l1 + c2*l2 + … ≤ n.

addPBExactlySource

Arguments

:: Solver

The Solver argument.

-> [(Integer, Lit)]

list of terms [(c1,l1),(c2,l2),…]

-> Integer

n

-> IO () 

Add a pseudo boolean constraints c1*l1 + c2*l2 + … = n.

addPBAtLeastSoftSource

Arguments

:: Solver

The Solver argument.

-> Lit

indicator lit

-> [(Integer, Lit)]

set of terms [(c1,l1),(c2,l2),…]

-> Integer

n

-> IO () 

Add a soft pseudo boolean constraints lit ⇒ c1*l1 + c2*l2 + … ≥ n.

addPBAtMostSoftSource

Arguments

:: Solver

The Solver argument.

-> Lit

indicator lit

-> [(Integer, Lit)]

set of terms [(c1,l1),(c2,l2),…]

-> Integer

n

-> IO () 

Add a soft pseudo boolean constraints lit ⇒ c1*l1 + c2*l2 + … ≤ n.

addPBExactlySoftSource

Arguments

:: Solver

The Solver argument.

-> Lit

indicator lit

-> [(Integer, Lit)]

set of terms [(c1,l1),(c2,l2),…]

-> Integer

n

-> IO () 

Add a soft pseudo boolean constraints lit ⇒ c1*l1 + c2*l2 + … = n.

Solving

solve :: Solver -> IO BoolSource

Solve constraints. Returns True if the problem is SATISFIABLE. Returns False if the problem is UNSATISFIABLE.

solveWithSource

Arguments

:: Solver 
-> [Lit]

Assumptions

-> IO Bool 

Solve constraints under assuptions. Returns True if the problem is SATISFIABLE. Returns False if the problem is UNSATISFIABLE.

Extract results

type Model = UArray Var BoolSource

A model is represented as a mapping from variables to its values.

model :: Solver -> IO ModelSource

After solve returns True, it returns the model.

failedAssumptions :: Solver -> IO [Lit]Source

After solveWith returns False, it returns a set of assumptions that leads to contradiction. In particular, if it returns an empty set, the problem is unsatisiable without any assumptions.

Solver configulation

defaultRestartStrategy :: RestartStrategySource

default value for RestartStrategy.

setRestartFirst :: Solver -> Int -> IO ()Source

The initial restart limit. (default 100) Negative value is used to disable restart.

defaultRestartFirst :: IntSource

default value for RestartFirst.

setRestartInc :: Solver -> Double -> IO ()Source

The factor with which the restart limit is multiplied in each restart. (default 1.5)

defaultRestartInc :: DoubleSource

default value for RestartInc.

setLearntSizeFirst :: Solver -> Int -> IO ()Source

The initial limit for learnt clauses.

defaultLearntSizeFirst :: IntSource

default value for LearntSizeFirst.

setLearntSizeInc :: Solver -> Double -> IO ()Source

The limit for learnt clauses is multiplied with this factor each restart. (default 1.1)

defaultLearntSizeInc :: DoubleSource

default value for LearntSizeInc.

setCCMin :: Solver -> Int -> IO ()Source

The limit for learnt clauses is multiplied with this factor each restart. (default 1.1)

defaultCCMin :: IntSource

default value for CCMin.

setVarPolarity :: Solver -> Var -> Bool -> IO ()Source

The default polarity of a variable.

setLogger :: Solver -> (String -> IO ()) -> IO ()Source

set callback function for receiving messages.

setRandomFreq :: Solver -> Double -> IO ()Source

The frequency with which the decision heuristic tries to choose a random variable

setRandomSeed :: Solver -> Int -> IO ()Source

Used by the random variable selection

Read state

nVars :: Solver -> IO IntSource

number of variables of the problem.

nAssigns :: Solver -> IO IntSource

number of assigned variables.

nClauses :: Solver -> IO IntSource

number of clauses.

nLearnt :: Solver -> IO IntSource

number of learnt constrints.

Internal API