module Ersatz.Solver.Minisat
( minisat
, cryptominisat
, minisatPath
) where
import Blaze.ByteString.Builder
import Control.Applicative
import Control.Exception (IOException, handle)
import Control.Monad
import Control.Monad.IO.Class
import qualified Data.ByteString as BS
import Data.IntMap (IntMap)
import Ersatz.Internal.Parser
import Ersatz.Problem
import Ersatz.Solution
import Ersatz.Solver.Common
import qualified Data.IntMap as IntMap
import System.IO
import System.Process (readProcessWithExitCode)
minisat :: MonadIO m => Solver SAT m
minisat = minisatPath "minisat"
cryptominisat :: MonadIO m => Solver SAT m
cryptominisat = minisatPath "cryptominisat"
minisatPath :: MonadIO m => FilePath -> Solver SAT m
minisatPath path problem = liftIO $
withTempFiles ".cnf" "" $ \problemPath solutionPath -> do
withFile problemPath WriteMode $ \fh ->
toByteStringIO (BS.hPut fh) (dimacs problem)
(exit, _out, _err) <-
readProcessWithExitCode path [problemPath, solutionPath] []
sol <- parseSolutionFile solutionPath
return (resultOf exit, sol)
parseSolutionFile :: FilePath -> IO (IntMap Bool)
parseSolutionFile path = handle handler (parseSolution <$> readFile path)
where
handler :: IOException -> IO (IntMap Bool)
handler _ = return IntMap.empty
parseSolution :: String -> IntMap Bool
parseSolution input =
case runParser solution input of
s:_ -> s
_ -> IntMap.empty
solution :: Parser Char (IntMap Bool)
solution = do
_ <- string "SAT\n"
IntMap.fromList <$> values
values :: Parser Char [(Int, Bool)]
values = (value `sepBy` token ' ')
<* string " 0"
<* (() <$ token '\n' <|> eof)
value :: Parser Char (Int, Bool)
value = do
i <- integer
guard (i /= 0)
return (toPair i)
where
toPair n | n >= 0 = ( n, True)
| otherwise = (n, False)