module Interfaces.MZinHaskell (
iRunModel,
runModel,
Interfaces.MZPrinter.layout,
writeData
) where
import Data.List
import Data.Char
import System.Process
import System.FilePath
import System.Directory
import Interfaces.MZAuxiliary
import Interfaces.MZASTBase (MZModel, Item(Comment))
import Interfaces.MZAST (GItem(..))
import Interfaces.MZPrinter
import Interfaces.FZSolutionParser (Solution, trySolutionsDefault, getAllSolutions)
import Text.Parsec.Error
import Text.Parsec.String (Parser)
iRunModel :: [GItem a] -> IO (Either ParseError [Solution])
iRunModel m = do
putStrLn "Enter working directory:"
dirpath <- getLine
putStr "Enter model\'s name: "
name <- getLine
putStr "Choose a solver from the list below:\r\n\t1. G12/FD\r\n\t2. choco3\r\n\r\nEnter the number associated with the solver: "
str_solver <- getLine
putStr $ if (str_solver /= "2")
then "Number of solutions to be returned: "
else "Return all solutions? Y/N: "
str_ns <- getLine;
let solver = read str_solver
ns = if (solver == 2)
then if (read ("\"" ++ str_ns ++ "\"") == "Y")
then 0
else 1
else read str_ns
path = joinPath [dirpath, name]
runModel m path solver ns
runModel :: [GItem a]
-> FilePath
-> Int
-> Int
-> IO (Either ParseError [Solution])
runModel = testModelWithParser trySolutionsDefault
testModelWithParser :: Parser [Solution]
-> [GItem a]
-> FilePath
-> Int
-> Int
-> IO (Either ParseError [Solution])
testModelWithParser p m mpath s n = do
configuration <- parseConfig
let mz_dir = addTrailingPathSeparator $ case minizinc configuration of
"" -> "."
str -> str
let mzn_fp = spaceFix $ mpath ++ ".mzn"
let fzn_fp = spaceFix $ mpath ++ ".fzn"
let res_fp = spaceFix $ mpath ++ ".res"
writeFile mzn_fp (layout m)
let mzn2fzn = proc (mz_dir ++ "mzn2fzn") ["-O-"
,"-o", fzn_fp
, mzn_fp]
(ec1, out1, err1) <- readCreateProcessWithExitCode mzn2fzn ""
res <- case err1 of
"" -> case s of
1 -> do
let fz_options = ["-b", "fd"]
++ case (n > 0) of
True -> ["-n", show n]
_ -> []
++ [fzn_fp]
let flatzinc = proc (mz_dir ++ "flatzinc") fz_options
(ec2, out2, err2) <- readCreateProcessWithExitCode flatzinc ""
return $ case err2 of
"" -> out2
_ -> "flatzinc error: " ++ err2 ++ "."
2 -> let antlr = antlr_path configuration
chocoParser = chocoparser configuration
chocoSolver = chocosolver configuration
all_or_first = if (n == 0) then "-a " else ""
in readCreateProcess (shell $ "java -cp ." ++ (intercalate [searchPathSeparator] [chocoSolver, chocoParser, antlr]) ++ " org.chocosolver.parser.flatzinc.ChocoFZN " ++ all_or_first ++ mpath ++ ".fzn") ""
_ -> readIO ("mzn2fzn error: " ++ err1 ++ ".")
writeFile res_fp res
removeFile res_fp
removeFile mzn_fp
removeFile fzn_fp
return $ getAllSolutions p res
writeData :: MZModel -> IO ()
writeData m = do
putStrLn "Enter datafile's filepath:"
datapath <- getLine
writeFile datapath (Prelude.show $ printModel m)