module ToySolver.SAT.MUS.QuickXplain
( module ToySolver.SAT.MUS.Types
, Options (..)
, defaultOptions
, findMUSAssumptions
) where
import Control.Monad
import Data.Default.Class
import Data.List
import qualified Data.IntSet as IS
import qualified ToySolver.SAT as SAT
import ToySolver.SAT.Types
import ToySolver.SAT.MUS.Types
import ToySolver.SAT.MUS hiding (findMUSAssumptions)
findMUSAssumptions
:: SAT.Solver
-> Options
-> IO MUS
findMUSAssumptions solver opt = do
log "computing a minimal unsatisfiable core"
core <- liftM IS.fromList $ SAT.getFailedAssumptions solver
update $ IS.toList core
log $ "core = " ++ showLits core
if IS.null core then
return core
else
liftM fst $ f IS.empty False core
where
log :: String -> IO ()
log = optLogger opt
update :: [Lit] -> IO ()
update = optUpdateBest opt
showLit :: Lit -> String
showLit = optLitPrinter opt
showLits :: IS.IntSet -> String
showLits ls = "{" ++ intercalate ", " (map showLit (IS.toList ls)) ++ "}"
split :: IS.IntSet -> (IS.IntSet, IS.IntSet)
split cs = (cs1, cs2)
where
s = IS.size cs
cs' = IS.toAscList cs
cs1 = IS.fromAscList $ take (s `div` 2) cs'
cs2 = IS.fromAscList $ drop (s `div` 2) cs'
f :: IS.IntSet -> Bool -> IS.IntSet -> IO (IS.IntSet, IS.IntSet)
f bs hasDelta cs = do
log $ "checking satisfiability of " ++ showLits bs
ret <- if not hasDelta then do
return True
else
SAT.solveWith solver (IS.toList bs)
if not ret then do
log $ showLits bs ++ " is unsatisfiable"
bs' <- liftM IS.fromList $ SAT.getFailedAssumptions solver
log $ "new core = " ++ showLits bs'
update $ IS.toList bs'
return (IS.empty, bs')
else do
log $ showLits bs ++ " is satisfiable"
if IS.size cs == 1 then do
return (cs, bs)
else do
let (cs1,cs2) = split cs
log $ "splitting " ++ showLits cs ++ " into " ++ showLits cs1 ++ " and " ++ showLits cs2
(ds2, es2) <- f (bs `IS.union` cs1) (not (IS.null cs1)) cs2
let bs' = bs `IS.intersection` es2
cs1' = cs1 `IS.intersection` es2
(ds1, es1) <- f (bs' `IS.union` ds2) (not (IS.null ds2)) cs1'
return (ds1 `IS.union` ds2, bs `IS.intersection` (es1 `IS.union` es2))