{-# OPTIONS_GHC -Wall #-}
{-# OPTIONS_HADDOCK show-extensions #-}
{-# LANGUAGE MultiParamTypeClasses #-}
module Numeric.Optimization.MIP.Solver.CPLEX
( CPLEX (..)
, cplex
) where
import Control.Monad
import Data.Default.Class
import Data.IORef
import qualified Data.Text.Lazy.IO as TLIO
import System.Exit
import System.IO
import System.IO.Temp
import qualified Numeric.Optimization.MIP.Base as MIP
import qualified Numeric.Optimization.MIP.LPFile as LPFile
import Numeric.Optimization.MIP.Solver.Base
import qualified Numeric.Optimization.MIP.Solution.CPLEX as CPLEXSol
import Numeric.Optimization.MIP.Internal.ProcessUtil (runProcessWithOutputCallback)
data CPLEX
= CPLEX
{ CPLEX -> String
cplexPath :: String
, CPLEX -> [String]
cplexArgs :: [String]
, CPLEX -> [String]
cplexCommands :: [String]
}
instance Default CPLEX where
def :: CPLEX
def = CPLEX
cplex
cplex :: CPLEX
cplex :: CPLEX
cplex = String -> [String] -> [String] -> CPLEX
CPLEX String
"cplex" [] []
instance IsSolver CPLEX IO where
solve' :: CPLEX
-> SolveOptions -> Problem Scientific -> IO (Solution Scientific)
solve' CPLEX
solver SolveOptions
opt Problem Scientific
prob = do
case FileOptions -> Problem Scientific -> Either String Text
LPFile.render FileOptions
forall a. Default a => a
def Problem Scientific
prob of
Left String
err -> IOError -> IO (Solution Scientific)
forall a. IOError -> IO a
ioError (IOError -> IO (Solution Scientific))
-> IOError -> IO (Solution Scientific)
forall a b. (a -> b) -> a -> b
$ String -> IOError
userError String
err
Right Text
lp -> do
String
-> (String -> Handle -> IO (Solution Scientific))
-> IO (Solution Scientific)
forall (m :: * -> *) a.
(MonadIO m, MonadMask m) =>
String -> (String -> Handle -> m a) -> m a
withSystemTempFile String
"cplex.lp" ((String -> Handle -> IO (Solution Scientific))
-> IO (Solution Scientific))
-> (String -> Handle -> IO (Solution Scientific))
-> IO (Solution Scientific)
forall a b. (a -> b) -> a -> b
$ \String
fname1 Handle
h1 -> do
Handle -> Text -> IO ()
TLIO.hPutStr Handle
h1 Text
lp
Handle -> IO ()
hClose Handle
h1
String
-> (String -> Handle -> IO (Solution Scientific))
-> IO (Solution Scientific)
forall (m :: * -> *) a.
(MonadIO m, MonadMask m) =>
String -> (String -> Handle -> m a) -> m a
withSystemTempFile String
"cplex.sol" ((String -> Handle -> IO (Solution Scientific))
-> IO (Solution Scientific))
-> (String -> Handle -> IO (Solution Scientific))
-> IO (Solution Scientific)
forall a b. (a -> b) -> a -> b
$ \String
fname2 Handle
h2 -> do
Handle -> IO ()
hClose Handle
h2
IORef Bool
isInfeasibleRef <- Bool -> IO (IORef Bool)
forall a. a -> IO (IORef a)
newIORef Bool
False
let input :: String
input = [String] -> String
unlines ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$
(case SolveOptions -> Maybe Double
solveTimeLimit SolveOptions
opt of
Maybe Double
Nothing -> []
Just Double
sec -> [String
"set timelimit " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Double -> String
forall a. Show a => a -> String
show Double
sec]) [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++
(case SolveOptions -> Maybe (Tol Scientific)
solveTol SolveOptions
opt of
Maybe (Tol Scientific)
Nothing -> []
Just Tol Scientific
tol ->
[ String
"set mip tolerances integrality " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Scientific -> String
forall a. Show a => a -> String
show (Tol Scientific -> Scientific
forall r. Tol r -> r
MIP.integralityTol Tol Scientific
tol)
, String
"set simplex tolerances feasibility " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Scientific -> String
forall a. Show a => a -> String
show (Tol Scientific -> Scientific
forall r. Tol r -> r
MIP.feasibilityTol Tol Scientific
tol)
, String
"set simplex tolerances optimality " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Scientific -> String
forall a. Show a => a -> String
show (Tol Scientific -> Scientific
forall r. Tol r -> r
MIP.optimalityTol Tol Scientific
tol)
]
) [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++
[ String
"read " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> String
forall a. Show a => a -> String
show String
fname1 ] [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++
CPLEX -> [String]
cplexCommands CPLEX
solver [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++
[ String
"optimize"
, String
"write " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> String
forall a. Show a => a -> String
show String
fname2
, String
"y"
, String
"quit"
]
onGetLine :: String -> IO ()
onGetLine String
s = do
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (String
s String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"MIP - Integer infeasible.") (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
IORef Bool -> Bool -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef IORef Bool
isInfeasibleRef Bool
True
SolveOptions -> String -> IO ()
solveLogger SolveOptions
opt String
s
onGetErrorLine :: String -> IO ()
onGetErrorLine = SolveOptions -> String -> IO ()
solveErrorLogger SolveOptions
opt
ExitCode
exitcode <- String
-> [String]
-> Maybe String
-> String
-> (String -> IO ())
-> (String -> IO ())
-> IO ExitCode
runProcessWithOutputCallback (CPLEX -> String
cplexPath CPLEX
solver) (CPLEX -> [String]
cplexArgs CPLEX
solver) Maybe String
forall a. Maybe a
Nothing String
input String -> IO ()
onGetLine String -> IO ()
onGetErrorLine
case ExitCode
exitcode of
ExitFailure Int
n -> IOError -> IO (Solution Scientific)
forall a. IOError -> IO a
ioError (IOError -> IO (Solution Scientific))
-> IOError -> IO (Solution Scientific)
forall a b. (a -> b) -> a -> b
$ String -> IOError
userError (String -> IOError) -> String -> IOError
forall a b. (a -> b) -> a -> b
$ String
"exit with " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
n
ExitCode
ExitSuccess -> do
Integer
size <- String -> IOMode -> (Handle -> IO Integer) -> IO Integer
forall r. String -> IOMode -> (Handle -> IO r) -> IO r
withFile String
fname2 IOMode
ReadMode ((Handle -> IO Integer) -> IO Integer)
-> (Handle -> IO Integer) -> IO Integer
forall a b. (a -> b) -> a -> b
$ Handle -> IO Integer
hFileSize
if Integer
size Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
== Integer
0 then do
Bool
isInfeasible <- IORef Bool -> IO Bool
forall a. IORef a -> IO a
readIORef IORef Bool
isInfeasibleRef
if Bool
isInfeasible then
Solution Scientific -> IO (Solution Scientific)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Solution Scientific
forall a. Default a => a
def{ MIP.solStatus = MIP.StatusInfeasible }
else
Solution Scientific -> IO (Solution Scientific)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Solution Scientific
forall a. Default a => a
def
else
String -> IO (Solution Scientific)
CPLEXSol.readFile String
fname2