mios-1.6.0: A Minisat-based CDCL SAT solver in Haskell

Safe HaskellSafe
LanguageHaskell2010

SAT.Mios.Types

Contents

Description

(This is a part of MIOS.) Basic data types used throughout mios.

Synopsis

Interface to caller

type SolverResult = Either SolverException Certificate Source #

the type that Mios returns This captures the following three cases: * solved with a satisfiable assigment, * proved that it's an unsatisfiable problem, and * aborted due to Mios specification or an internal error

Solver Configuration

defaultConfiguration :: MiosConfiguration Source #

dafault configuration

  • Minisat-1.14 uses (0.95, 0.999, 0.2 = 20 / 1000).
  • Minisat-2.20 uses (0.95, 0.999, 0).
  • Gulcose-4.0 uses (0.8 , 0.999, 0).
  • Mios-1.2 uses (0.95, 0.999, 0).

internal structure

Variable

type Var = Int Source #

represents Var.

bottomVar :: Var Source #

Special constant in Var (p.7)

int2var :: Int -> Int Source #

converts a usual Int as literal to an internal Var presentation.

>>> int2var 1
1  -- the first literal is the first variable
>>> int2var 2
2  -- literal @2@ is variable 2
>>> int2var (-2)
2 -- literal @-2@ is corresponding to variable 2

Internal encoded Literal

type Lit = Int Source #

The literal data has an index method which converts the literal to a "small" integer suitable for array indexing. The var method returns the underlying variable of the literal, and the sign method if the literal is signed (False for x and True for -x).

lit2int :: Lit -> Int Source #

converts Lit into Int as int2lit . lit2int == id.

>>> lit2int 2
1
>>> lit2int 3
-1
>>> lit2int 4
2
>>> lit2int 5
-2

int2lit :: Int -> Lit Source #

converts Int into Lit as lit2int . int2lit == id.

>>> int2lit 1
2
>>> int2lit (-1)
3
>>> int2lit 2
4
>>> int2lit (-2)
5

bottomLit :: Lit Source #

Special constant in Lit (p.7)

positiveLit :: Lit -> Bool Source #

returns True if the literal is positive

lit2var :: Lit -> Var Source #

converts Lit into Var.

>>> lit2var 2
1
>>> lit2var 3
1
>>> lit2var 4
2
>>> lit2var 5
2

var2lit :: Var -> Bool -> Lit Source #

converts a Var to the corresponing literal.

>>> var2lit 1 True
2
>>> var2lit 1 False
3
>>> var2lit 2 True
4
>>> var2lit 2 False
5

negateLit :: Lit -> Lit Source #

negates literal

>>> negateLit 2
3
>>> negateLit 3
2
>>> negateLit 4
5
>>> negateLit 5
4

Assignment on the lifted Bool domain

type LiftedBool = Int Source #

Lifted Boolean domain (p.7) that extends Bool with "⊥" means undefined design note: _|_ should be null = 0; True literals are coded to even numbers. So it should be 2.

lit2lbool :: Lit -> LiftedBool Source #

returns the value of a literal as a LiftedBool

data Int :: * where #

A fixed-precision integer type with at least the range [-2^29 .. 2^29-1]. The exact range for a given implementation can be determined by using minBound and maxBound from the Bounded class.

Bundled Patterns

pattern LiftedF :: Int

FALSE on the Lifted Bool domain

pattern LiftedT :: Int

TRUE on the Lifted Bool domain

pattern LBottom :: Int

UNDEFINED on the Lifted Bool domain

pattern Conflict :: Int

CONFLICT on the Lifted Bool domain

Instances

Bounded Int

Since: 2.1

Methods

minBound :: Int #

maxBound :: Int #

Enum Int

Since: 2.1

Methods

succ :: Int -> Int #

pred :: Int -> Int #

toEnum :: Int -> Int #

fromEnum :: Int -> Int #

enumFrom :: Int -> [Int] #

enumFromThen :: Int -> Int -> [Int] #

enumFromTo :: Int -> Int -> [Int] #

enumFromThenTo :: Int -> Int -> Int -> [Int] #

Eq Int 

Methods

(==) :: Int -> Int -> Bool #

(/=) :: Int -> Int -> Bool #

Integral Int

Since: 2.0.1

Methods

quot :: Int -> Int -> Int #

rem :: Int -> Int -> Int #

div :: Int -> Int -> Int #

mod :: Int -> Int -> Int #

quotRem :: Int -> Int -> (Int, Int) #

divMod :: Int -> Int -> (Int, Int) #

toInteger :: Int -> Integer #

Num Int

Since: 2.1

Methods

(+) :: Int -> Int -> Int #

(-) :: Int -> Int -> Int #

(*) :: Int -> Int -> Int #

negate :: Int -> Int #

abs :: Int -> Int #

signum :: Int -> Int #

fromInteger :: Integer -> Int #

Ord Int 

Methods

compare :: Int -> Int -> Ordering #

(<) :: Int -> Int -> Bool #

(<=) :: Int -> Int -> Bool #

(>) :: Int -> Int -> Bool #

(>=) :: Int -> Int -> Bool #

max :: Int -> Int -> Int #

min :: Int -> Int -> Int #

Read Int

Since: 2.1

Real Int

Since: 2.0.1

Methods

toRational :: Int -> Rational #

Show Int

Since: 2.1

Methods

showsPrec :: Int -> Int -> ShowS #

show :: Int -> String #

showList :: [Int] -> ShowS #

Ix Int

Since: 2.1

Methods

range :: (Int, Int) -> [Int] #

index :: (Int, Int) -> Int -> Int #

unsafeIndex :: (Int, Int) -> Int -> Int

inRange :: (Int, Int) -> Int -> Bool #

rangeSize :: (Int, Int) -> Int #

unsafeRangeSize :: (Int, Int) -> Int

Bits Int

Since: 2.1

Methods

(.&.) :: Int -> Int -> Int #

(.|.) :: Int -> Int -> Int #

xor :: Int -> Int -> Int #

complement :: Int -> Int #

shift :: Int -> Int -> Int #

rotate :: Int -> Int -> Int #

zeroBits :: Int #

bit :: Int -> Int #

setBit :: Int -> Int -> Int #

clearBit :: Int -> Int -> Int #

complementBit :: Int -> Int -> Int #

testBit :: Int -> Int -> Bool #

bitSizeMaybe :: Int -> Maybe Int #

bitSize :: Int -> Int #

isSigned :: Int -> Bool #

shiftL :: Int -> Int -> Int #

unsafeShiftL :: Int -> Int -> Int #

shiftR :: Int -> Int -> Int #

unsafeShiftR :: Int -> Int -> Int #

rotateL :: Int -> Int -> Int #

rotateR :: Int -> Int -> Int #

popCount :: Int -> Int #

FiniteBits Int

Since: 4.6.0.0

Prim Int 
Unbox Int 
BoolComponent Int Source # 

Methods

toBF :: Int -> BoolForm Source #

Vector Vector Int 
MVector MVector Int 
StackFamily Clause Lit Source #

Clause is a Stackfamilyon literals since literals in it will be discared if satisifed at level = 0.

SingleStorage Clause Int Source #

Clause is a SingleStorage on the number of literals in it.

Methods

new' :: Int -> IO Clause Source #

get' :: Clause -> IO Int Source #

set' :: Clause -> Int -> IO () Source #

modify' :: Clause -> (Int -> Int) -> IO () Source #

SingleStorage ClauseExtManager Int Source #

ClauseExtManager is a SingleStorage on the number of clauses in it.

SingleStorage ClauseSimpleManager Int Source #

ClauseSimpleManager is a SingleStorage on the number of clauses in it.

VecFamily Clause Lit Source #

Clause is a VecFamily of Lit.

Methods

getNth :: Clause -> Int -> IO Lit Source #

setNth :: Clause -> Int -> Lit -> IO () Source #

reset :: Clause -> IO () Source #

swapBetween :: Clause -> Int -> Int -> IO () Source #

modifyNth :: Clause -> (Lit -> Lit) -> Int -> IO () Source #

newVec :: Int -> Lit -> IO Clause Source #

setAll :: Clause -> Lit -> IO () Source #

growBy :: Clause -> Int -> IO Clause Source #

asList :: Clause -> IO [Lit] Source #

Generic1 k (URec k Int) 

Associated Types

type Rep1 (URec k Int) (f :: URec k Int -> *) :: k -> * #

Methods

from1 :: f a -> Rep1 (URec k Int) f a #

to1 :: Rep1 (URec k Int) f a -> f a #

VecFamily (Vec [Int]) Int Source # 

Methods

getNth :: Vec [Int] -> Int -> IO Int Source #

setNth :: Vec [Int] -> Int -> Int -> IO () Source #

reset :: Vec [Int] -> IO () Source #

swapBetween :: Vec [Int] -> Int -> Int -> IO () Source #

modifyNth :: Vec [Int] -> (Int -> Int) -> Int -> IO () Source #

newVec :: Int -> Int -> IO (Vec [Int]) Source #

setAll :: Vec [Int] -> Int -> IO () Source #

growBy :: Vec [Int] -> Int -> IO (Vec [Int]) Source #

asList :: Vec [Int] -> IO [Int] Source #

Functor (URec * Int) 

Methods

fmap :: (a -> b) -> URec * Int a -> URec * Int b #

(<$) :: a -> URec * Int b -> URec * Int a #

Foldable (URec * Int) 

Methods

fold :: Monoid m => URec * Int m -> m #

foldMap :: Monoid m => (a -> m) -> URec * Int a -> m #

foldr :: (a -> b -> b) -> b -> URec * Int a -> b #

foldr' :: (a -> b -> b) -> b -> URec * Int a -> b #

foldl :: (b -> a -> b) -> b -> URec * Int a -> b #

foldl' :: (b -> a -> b) -> b -> URec * Int a -> b #

foldr1 :: (a -> a -> a) -> URec * Int a -> a #

foldl1 :: (a -> a -> a) -> URec * Int a -> a #

toList :: URec * Int a -> [a] #

null :: URec * Int a -> Bool #

length :: URec * Int a -> Int #

elem :: Eq a => a -> URec * Int a -> Bool #

maximum :: Ord a => URec * Int a -> a #

minimum :: Ord a => URec * Int a -> a #

sum :: Num a => URec * Int a -> a #

product :: Num a => URec * Int a -> a #

Traversable (URec * Int) 

Methods

traverse :: Applicative f => (a -> f b) -> URec * Int a -> f (URec * Int b) #

sequenceA :: Applicative f => URec * Int (f a) -> f (URec * Int a) #

mapM :: Monad m => (a -> m b) -> URec * Int a -> m (URec * Int b) #

sequence :: Monad m => URec * Int (m a) -> m (URec * Int a) #

Eq (URec k Int p) 

Methods

(==) :: URec k Int p -> URec k Int p -> Bool #

(/=) :: URec k Int p -> URec k Int p -> Bool #

Ord (URec k Int p) 

Methods

compare :: URec k Int p -> URec k Int p -> Ordering #

(<) :: URec k Int p -> URec k Int p -> Bool #

(<=) :: URec k Int p -> URec k Int p -> Bool #

(>) :: URec k Int p -> URec k Int p -> Bool #

(>=) :: URec k Int p -> URec k Int p -> Bool #

max :: URec k Int p -> URec k Int p -> URec k Int p #

min :: URec k Int p -> URec k Int p -> URec k Int p #

Show (URec k Int p) 

Methods

showsPrec :: Int -> URec k Int p -> ShowS #

show :: URec k Int p -> String #

showList :: [URec k Int p] -> ShowS #

Generic (URec k Int p) 

Associated Types

type Rep (URec k Int p) :: * -> * #

Methods

from :: URec k Int p -> Rep (URec k Int p) x #

to :: Rep (URec k Int p) x -> URec k Int p #

data Vector Int 
data Vec Int Source # 
data URec k Int

Used for marking occurrences of Int#

Since: 4.9.0.0

data URec k Int = UInt {}
data MVector s Int 
type Rep1 k (URec k Int) 
type Rep1 k (URec k Int) = D1 k (MetaData "URec" "GHC.Generics" "base" False) (C1 k (MetaCons "UInt" PrefixI True) (S1 k (MetaSel (Just Symbol "uInt#") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (UInt k)))
data Vec [Int] Source # 
data Vec [Int] = Vec (UVector Int)
type Rep (URec k Int p) 
type Rep (URec k Int p) = D1 * (MetaData "URec" "GHC.Generics" "base" False) (C1 * (MetaCons "UInt" PrefixI True) (S1 * (MetaSel (Just Symbol "uInt#") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (UInt *)))

class VarOrder o where Source #

Assisting ADT for the dynamic variable ordering of the solver. The constructor takes references to the assignment vector and the activity vector of the solver. The method select will return the unassigned variable with the highest activity.

Methods

update :: o -> Var -> IO () Source #

should be called when a variable has increased in activity.

undo :: o -> Var -> IO () Source #

should be called when a variable becomes unbound (may be selected again).

select :: o -> IO Var Source #

returns a new, unassigned var as the next decision.

Instances

VarOrder Solver Source #

Interfate to select a decision var based on variable activity.

Methods

update :: Solver -> Var -> IO () Source #

undo :: Solver -> Var -> IO () Source #

select :: Solver -> IO Var Source #

statistics

data StatIndex Source #

stat index

Constructors

NumOfBackjump

the number of backjump

NumOfRestart

the number of restart

NumOfBlockRestart

the number of blacking start

NumOfGeometricRestart

the number of classic restart

NumOfPropagation

the number of propagation

NumOfReduction

the number of reduction

NumOfClause

the number of alive given clauses

NumOfLearnt

the number of alive learnt clauses

NumOfVariable

the number of alive variables

NumOfAssigned

the number of assigned variables

EndOfStatIndex

Don't use this dummy.