module Interfaces.MZinHaskell (
module Interfaces.MZAST,
module Interfaces.FZSolutionParser,
module Interfaces.MZPrinter,
iTestModel,
testModel,
testModelWithData,
writeData
) where
import Data.List
import System.Process
import System.FilePath
import Interfaces.MZAuxiliary
import Interfaces.MZAST hiding (UserD, PrefBop)
import Interfaces.MZPrinter
import Interfaces.FZSolutionParser
import Text.Parsec.Error
testModelWithData
:: MZModel
-> MZModel
-> FilePath
-> Int
-> Int
-> IO (Either ParseError [Solution])
testModelWithData model mdata path solver num =
let fdata = [Comment "Model\'s data"] ++ mdata ++ [Empty]
in testModel (fdata ++ model) path solver num
iTestModel :: MZModel -> IO (Either ParseError [Solution])
iTestModel 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\nInteger value associated with the solver: "
str_solver <- getLine
putStr "Number of solutions to be returned: "
str_ns <- getLine
let solver = read str_solver
ns = read str_ns
path = joinPath [dirpath, name]
testModel m path solver ns
testModel :: MZModel
-> FilePath
-> Int
-> Int
-> IO (Either ParseError [Solution])
testModel m mpath s n = do
configuration <- parseConfig
let mz_dir = case minizinc configuration of
"" -> addTrailingPathSeparator "."
str -> addTrailingPathSeparator str
let mfzn = (spaceFix $ mz_dir ++ "mzn2fzn") ++ " -O- - -o " ++ (spaceFix (mpath ++ ".fzn"))
let flatzinc = spaceFix $ mz_dir ++ "flatzinc"
readCreateProcess (shell mfzn) (Prelude.show $ printModel m)
res <- case s of
1 -> readCreateProcess (shell $ flatzinc ++ " -a -b fd " ++ mpath ++ ".fzn") ""
2 -> let antlr = antlr_path configuration
chocoParser = chocoparser configuration
chocoSolver = chocosolver configuration
in readCreateProcess (shell $ "java -cp ." ++ (intercalate [searchPathSeparator] [chocoSolver, chocoParser, antlr]) ++ " org.chocosolver.parser.flatzinc.ChocoFZN -a " ++ mpath ++ ".fzn") ""
return $ getSolution n res
writeData :: MZModel -> IO ()
writeData m = do
putStrLn "Enter datafile's filepath:"
datapath <- getLine
writeFile datapath (Prelude.show $ printModel m)