module Ersatz.Solver.Common
( withTempFiles
, resultOf
, trySolvers
, NoSolvers(..)
, parseSolution5
) where
import Control.Exception (Exception(..), throwIO)
import Control.Monad.IO.Class
import Ersatz.Solution
import System.Exit (ExitCode(..))
import System.IO.Error (tryIOError)
import System.IO.Temp (withSystemTempDirectory)
import Data.IntMap (IntMap)
import qualified Data.IntMap.Strict as IntMap
withTempFiles :: MonadIO m
=> FilePath
-> FilePath
-> (FilePath -> FilePath -> IO a) -> m a
withTempFiles :: forall (m :: * -> *) a.
MonadIO m =>
FilePath -> FilePath -> (FilePath -> FilePath -> IO a) -> m a
withTempFiles FilePath
problemExt FilePath
solutionExt FilePath -> FilePath -> IO a
f = IO a -> m a
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO a -> m a) -> IO a -> m a
forall a b. (a -> b) -> a -> b
$
FilePath -> (FilePath -> IO a) -> IO a
forall (m :: * -> *) a.
(MonadIO m, MonadMask m) =>
FilePath -> (FilePath -> m a) -> m a
withSystemTempDirectory FilePath
"ersatz" ((FilePath -> IO a) -> IO a) -> (FilePath -> IO a) -> IO a
forall a b. (a -> b) -> a -> b
$ \FilePath
dir -> do
let problemPath :: FilePath
problemPath = FilePath
dir FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"/problem" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
problemExt
solutionPath :: FilePath
solutionPath = FilePath
dir FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"/solution" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
solutionExt
FilePath -> FilePath -> IO a
f FilePath
problemPath FilePath
solutionPath
resultOf :: ExitCode -> Result
resultOf :: ExitCode -> Result
resultOf (ExitFailure Key
10) = Result
Satisfied
resultOf (ExitFailure Key
20) = Result
Unsatisfied
resultOf ExitCode
_ = Result
Unsolved
newtype NoSolvers = NoSolvers [IOError] deriving Key -> NoSolvers -> FilePath -> FilePath
[NoSolvers] -> FilePath -> FilePath
NoSolvers -> FilePath
(Key -> NoSolvers -> FilePath -> FilePath)
-> (NoSolvers -> FilePath)
-> ([NoSolvers] -> FilePath -> FilePath)
-> Show NoSolvers
forall a.
(Key -> a -> FilePath -> FilePath)
-> (a -> FilePath) -> ([a] -> FilePath -> FilePath) -> Show a
$cshowsPrec :: Key -> NoSolvers -> FilePath -> FilePath
showsPrec :: Key -> NoSolvers -> FilePath -> FilePath
$cshow :: NoSolvers -> FilePath
show :: NoSolvers -> FilePath
$cshowList :: [NoSolvers] -> FilePath -> FilePath
showList :: [NoSolvers] -> FilePath -> FilePath
Show
instance Exception NoSolvers where
displayException :: NoSolvers -> FilePath
displayException NoSolvers
_ = FilePath
"no ersatz solvers were found"
trySolvers :: [Solver s IO] -> Solver s IO
trySolvers :: forall s. [Solver s IO] -> Solver s IO
trySolvers [Solver s IO]
solvers s
problem = (Solver s IO
-> ([IOError] -> IO (Result, IntMap Bool))
-> [IOError]
-> IO (Result, IntMap Bool))
-> ([IOError] -> IO (Result, IntMap Bool))
-> [Solver s IO]
-> [IOError]
-> IO (Result, IntMap Bool)
forall a b. (a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr Solver s IO
-> ([IOError] -> IO (Result, IntMap Bool))
-> [IOError]
-> IO (Result, IntMap Bool)
forall {b}. (s -> IO b) -> ([IOError] -> IO b) -> [IOError] -> IO b
runSolver [IOError] -> IO (Result, IntMap Bool)
forall {a}. [IOError] -> IO a
noSolvers [Solver s IO]
solvers []
where
noSolvers :: [IOError] -> IO a
noSolvers = NoSolvers -> IO a
forall e a. Exception e => e -> IO a
throwIO (NoSolvers -> IO a)
-> ([IOError] -> NoSolvers) -> [IOError] -> IO a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [IOError] -> NoSolvers
NoSolvers ([IOError] -> NoSolvers)
-> ([IOError] -> [IOError]) -> [IOError] -> NoSolvers
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [IOError] -> [IOError]
forall a. [a] -> [a]
reverse
runSolver :: (s -> IO b) -> ([IOError] -> IO b) -> [IOError] -> IO b
runSolver s -> IO b
solver [IOError] -> IO b
next [IOError]
es =
do Either IOError b
res <- IO b -> IO (Either IOError b)
forall a. IO a -> IO (Either IOError a)
tryIOError (s -> IO b
solver s
problem)
case Either IOError b
res of
Left IOError
e -> [IOError] -> IO b
next (IOError
eIOError -> [IOError] -> [IOError]
forall a. a -> [a] -> [a]
:[IOError]
es)
Right b
x -> b -> IO b
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return b
x
parseSolution5 :: String -> IntMap Bool
parseSolution5 :: FilePath -> IntMap Bool
parseSolution5 FilePath
txt = [(Key, Bool)] -> IntMap Bool
forall a. [(Key, a)] -> IntMap a
IntMap.fromList [(Key -> Key
forall a. Num a => a -> a
abs Key
v, Key
v Key -> Key -> Bool
forall a. Ord a => a -> a -> Bool
> Key
0) | Key
v <- [Key]
vars, Key
v Key -> Key -> Bool
forall a. Eq a => a -> a -> Bool
/= Key
0]
where
vlines :: [FilePath]
vlines = [FilePath
l | (Char
'v':FilePath
l) <- FilePath -> [FilePath]
lines FilePath
txt]
vars :: [Key]
vars = (FilePath -> Key) -> [FilePath] -> [Key]
forall a b. (a -> b) -> [a] -> [b]
map FilePath -> Key
forall a. Read a => FilePath -> a
read ((FilePath -> [FilePath]) -> [FilePath] -> [FilePath]
forall m a. Monoid m => (a -> m) -> [a] -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap FilePath -> [FilePath]
words [FilePath]
vlines)