module ToySolver.SAT.Printer
( satPrintModel
, maxsatPrintModel
, pbPrintModel
, musPrintSol
) where
import Control.Monad
import Data.Array.IArray
import Data.List
import System.IO
import ToySolver.SAT.Types
satPrintModel :: Handle -> Model -> Int -> IO ()
satPrintModel h m n = do
let as = if n > 0
then takeWhile (\(v,_) -> v <= n) $ assocs m
else assocs m
forM_ (split 10 as) $ \xs -> do
hPutStr h "v"
forM_ xs $ \(var,val) -> hPutStr h (' ': show (literal var val))
hPutStrLn h ""
hPutStrLn h "v 0"
hFlush h
maxsatPrintModel :: Handle -> Model -> Int -> IO ()
maxsatPrintModel h m n = do
let as = if n > 0
then takeWhile (\(v,_) -> v <= n) $ assocs m
else assocs m
forM_ (split 10 as) $ \xs -> do
hPutStr h "v"
forM_ xs $ \(var,val) -> hPutStr h (' ' : show (literal var val))
hPutStrLn h ""
hFlush stdout
pbPrintModel :: Handle -> Model -> Int -> IO ()
pbPrintModel h m n = do
let as = if n > 0
then takeWhile (\(v,_) -> v <= n) $ assocs m
else assocs m
forM_ (split 10 as) $ \xs -> do
hPutStr h "v"
forM_ xs $ \(var,val) -> hPutStr h (" " ++ (if val then "" else "-") ++ "x" ++ show var)
hPutStrLn h ""
hFlush stdout
musPrintSol :: Handle -> [Int] -> IO ()
musPrintSol h is = do
forM_ (split 10 is) $ \xs -> do
hPutStr h "v"
forM_ xs $ \i -> hPutStr h (' ': show i)
hPutStrLn h ""
hPutStrLn h "v 0"
hFlush h
split :: Int -> [a] -> [[a]]
split n = go
where
go [] = []
go xs =
case splitAt n xs of
(ys, zs) -> ys : go zs