{-# OPTIONS_GHC -Wall #-}
{-# OPTIONS_HADDOCK show-extensions #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
module Numeric.Optimization.MIP
(
Problem (..)
, variables
, continuousVariables
, integerVariables
, binaryVariables
, semiContinuousVariables
, semiIntegerVariables
, varTypes
, varType
, getVarType
, varBounds
, getBounds
, Var (Var)
, varName
, toVar
, fromVar
, VarType (..)
, BoundExpr
, Extended (..)
, Bounds
, defaultBounds
, defaultLB
, defaultUB
, Label
, Expr (Expr)
, varExpr
, constExpr
, terms
, Term (..)
, OptDir (..)
, ObjectiveFunction (..)
, Constraint (..)
, (.==.)
, (.<=.)
, (.>=.)
, RelOp (..)
, SOSType (..)
, SOSConstraint (..)
, Solution (..)
, Status (..)
, meetStatus
, Tol (..)
, zeroTol
, Eval (..)
, FileOptions (..)
, WriteSetting (..)
, readFile
, readLPFile
, readMPSFile
, parseLPString
, parseMPSString
, ParseError
, writeFile
, writeLPFile
, writeMPSFile
, toLPString
, toMPSString
, Default (..)
, Variables (..)
, intersectBounds
) where
import Prelude hiding (readFile, writeFile)
import Control.Exception
import Data.Char
import Data.Scientific (Scientific)
import Data.String
import qualified Data.Text.Lazy as TL
import qualified Data.Text.Lazy.IO as TLIO
import System.FilePath (takeExtension, splitExtension)
import System.IO hiding (readFile, writeFile)
import Text.Megaparsec (Stream (..))
import Numeric.Optimization.MIP.Base
import Numeric.Optimization.MIP.FileUtils (ParseError)
import qualified Numeric.Optimization.MIP.LPFile as LPFile
import qualified Numeric.Optimization.MIP.MPSFile as MPSFile
#ifdef WITH_ZLIB
import qualified Codec.Compression.GZip as GZip
import qualified Data.ByteString.Lazy as BL
import Data.ByteString.Lazy.Encoding (encode, decode)
import qualified Data.CaseInsensitive as CI
import GHC.IO.Encoding (getLocaleEncoding)
#endif
readFile :: FileOptions -> FilePath -> IO (Problem Scientific)
readFile :: FileOptions -> String -> IO (Problem Scientific)
readFile FileOptions
opt String
fname =
case String -> String
getExt String
fname of
String
".lp" -> FileOptions -> String -> IO (Problem Scientific)
readLPFile FileOptions
opt String
fname
String
".mps" -> FileOptions -> String -> IO (Problem Scientific)
readMPSFile FileOptions
opt String
fname
String
ext -> IOError -> IO (Problem Scientific)
forall a. IOError -> IO a
ioError (IOError -> IO (Problem Scientific))
-> IOError -> IO (Problem Scientific)
forall a b. (a -> b) -> a -> b
$ String -> IOError
userError (String -> IOError) -> String -> IOError
forall a b. (a -> b) -> a -> b
$ String
"unknown extension: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
ext
readLPFile :: FileOptions -> FilePath -> IO (Problem Scientific)
#ifndef WITH_ZLIB
readLPFile = LPFile.parseFile
#else
readLPFile :: FileOptions -> String -> IO (Problem Scientific)
readLPFile FileOptions
opt String
fname = do
Text
s <- FileOptions -> String -> IO Text
readTextFile FileOptions
opt String
fname
let ret :: Either (ParseError Text) (Problem Scientific)
ret = FileOptions
-> String -> Text -> Either (ParseError Text) (Problem Scientific)
forall s.
(Stream s, Token s ~ Char, IsString (Tokens s)) =>
FileOptions
-> String -> s -> Either (ParseError s) (Problem Scientific)
LPFile.parseString FileOptions
opt String
fname Text
s
case Either (ParseError Text) (Problem Scientific)
ret of
Left ParseError Text
e -> ParseError Text -> IO (Problem Scientific)
forall a e. Exception e => e -> a
throw ParseError Text
e
Right Problem Scientific
a -> Problem Scientific -> IO (Problem Scientific)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Problem Scientific
a
#endif
readMPSFile :: FileOptions -> FilePath -> IO (Problem Scientific)
#ifndef WITH_ZLIB
readMPSFile = MPSFile.parseFile
#else
readMPSFile :: FileOptions -> String -> IO (Problem Scientific)
readMPSFile FileOptions
opt String
fname = do
Text
s <- FileOptions -> String -> IO Text
readTextFile FileOptions
opt String
fname
let ret :: Either (ParseError Text) (Problem Scientific)
ret = FileOptions
-> String -> Text -> Either (ParseError Text) (Problem Scientific)
forall s.
(Stream s, Token s ~ Char, IsString (Tokens s)) =>
FileOptions
-> String -> s -> Either (ParseError s) (Problem Scientific)
MPSFile.parseString FileOptions
opt String
fname Text
s
case Either (ParseError Text) (Problem Scientific)
ret of
Left ParseError Text
e -> ParseError Text -> IO (Problem Scientific)
forall a e. Exception e => e -> a
throw ParseError Text
e
Right Problem Scientific
a -> Problem Scientific -> IO (Problem Scientific)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Problem Scientific
a
#endif
readTextFile :: FileOptions -> FilePath -> IO TL.Text
#ifndef WITH_ZLIB
readTextFile opt fname = do
h <- openFile fname ReadMode
case optFileEncoding opt of
Nothing -> return ()
Just enc -> hSetEncoding h enc
TLIO.hGetContents h
#else
readTextFile :: FileOptions -> String -> IO Text
readTextFile FileOptions
opt String
fname = do
TextEncoding
enc <- case FileOptions -> Maybe TextEncoding
optFileEncoding FileOptions
opt of
Maybe TextEncoding
Nothing -> IO TextEncoding
getLocaleEncoding
Just TextEncoding
enc -> TextEncoding -> IO TextEncoding
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return TextEncoding
enc
let f :: ByteString -> ByteString
f = if String -> CI String
forall s. FoldCase s => s -> CI s
CI.mk (String -> String
takeExtension String
fname) CI String -> CI String -> Bool
forall a. Eq a => a -> a -> Bool
== CI String
".gz" then ByteString -> ByteString
GZip.decompress else ByteString -> ByteString
forall a. a -> a
id
ByteString
s <- String -> IO ByteString
BL.readFile String
fname
Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> IO Text) -> Text -> IO Text
forall a b. (a -> b) -> a -> b
$ TextEncoding -> ByteString -> Text
decode TextEncoding
enc (ByteString -> Text) -> ByteString -> Text
forall a b. (a -> b) -> a -> b
$ ByteString -> ByteString
f ByteString
s
#endif
parseLPString :: (Stream s, Token s ~ Char, IsString (Tokens s)) => FileOptions -> String -> s -> Either (ParseError s) (Problem Scientific)
parseLPString :: forall s.
(Stream s, Token s ~ Char, IsString (Tokens s)) =>
FileOptions
-> String -> s -> Either (ParseError s) (Problem Scientific)
parseLPString = FileOptions
-> String -> s -> Either (ParseError s) (Problem Scientific)
forall s.
(Stream s, Token s ~ Char, IsString (Tokens s)) =>
FileOptions
-> String -> s -> Either (ParseError s) (Problem Scientific)
LPFile.parseString
parseMPSString :: (Stream s, Token s ~ Char, IsString (Tokens s)) => FileOptions -> String -> s -> Either (ParseError s) (Problem Scientific)
parseMPSString :: forall s.
(Stream s, Token s ~ Char, IsString (Tokens s)) =>
FileOptions
-> String -> s -> Either (ParseError s) (Problem Scientific)
parseMPSString = FileOptions
-> String -> s -> Either (ParseError s) (Problem Scientific)
forall s.
(Stream s, Token s ~ Char, IsString (Tokens s)) =>
FileOptions
-> String -> s -> Either (ParseError s) (Problem Scientific)
MPSFile.parseString
writeFile :: FileOptions -> FilePath -> Problem Scientific -> IO ()
writeFile :: FileOptions -> String -> Problem Scientific -> IO ()
writeFile FileOptions
opt String
fname Problem Scientific
prob =
case String -> String
getExt String
fname of
String
".lp" -> FileOptions -> String -> Problem Scientific -> IO ()
writeLPFile FileOptions
opt String
fname Problem Scientific
prob
String
".mps" -> FileOptions -> String -> Problem Scientific -> IO ()
writeMPSFile FileOptions
opt String
fname Problem Scientific
prob
String
ext -> IOError -> IO ()
forall a. IOError -> IO a
ioError (IOError -> IO ()) -> IOError -> IO ()
forall a b. (a -> b) -> a -> b
$ String -> IOError
userError (String -> IOError) -> String -> IOError
forall a b. (a -> b) -> a -> b
$ String
"unknown extension: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
ext
getExt :: String -> String
getExt :: String -> String
getExt String
fname | (String
base, String
ext) <- String -> (String, String)
splitExtension String
fname =
case (Char -> Char) -> String -> String
forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
toLower String
ext of
#ifdef WITH_ZLIB
String
".gz" -> String -> String
getExt String
base
#endif
String
s -> String
s
writeLPFile :: FileOptions -> FilePath -> Problem Scientific -> IO ()
writeLPFile :: FileOptions -> String -> Problem Scientific -> IO ()
writeLPFile FileOptions
opt String
fname Problem Scientific
prob =
case FileOptions -> Problem Scientific -> Either String Text
LPFile.render FileOptions
opt Problem Scientific
prob of
Left String
err -> IOError -> IO ()
forall a. IOError -> IO a
ioError (IOError -> IO ()) -> IOError -> IO ()
forall a b. (a -> b) -> a -> b
$ String -> IOError
userError String
err
Right Text
s -> FileOptions -> String -> Text -> IO ()
writeTextFile FileOptions
opt String
fname Text
s
writeMPSFile :: FileOptions -> FilePath -> Problem Scientific -> IO ()
writeMPSFile :: FileOptions -> String -> Problem Scientific -> IO ()
writeMPSFile FileOptions
opt String
fname Problem Scientific
prob =
case FileOptions -> Problem Scientific -> Either String Text
MPSFile.render FileOptions
opt Problem Scientific
prob of
Left String
err -> IOError -> IO ()
forall a. IOError -> IO a
ioError (IOError -> IO ()) -> IOError -> IO ()
forall a b. (a -> b) -> a -> b
$ String -> IOError
userError String
err
Right Text
s -> FileOptions -> String -> Text -> IO ()
writeTextFile FileOptions
opt String
fname Text
s
writeTextFile :: FileOptions -> FilePath -> TL.Text -> IO ()
writeTextFile :: FileOptions -> String -> Text -> IO ()
writeTextFile FileOptions
opt String
fname Text
s = do
let writeSimple :: IO ()
writeSimple = do
String -> IOMode -> (Handle -> IO ()) -> IO ()
forall r. String -> IOMode -> (Handle -> IO r) -> IO r
withFile String
fname IOMode
WriteMode ((Handle -> IO ()) -> IO ()) -> (Handle -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Handle
h -> do
case FileOptions -> Maybe TextEncoding
optFileEncoding FileOptions
opt of
Maybe TextEncoding
Nothing -> () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
Just TextEncoding
enc -> Handle -> TextEncoding -> IO ()
hSetEncoding Handle
h TextEncoding
enc
Handle -> Text -> IO ()
TLIO.hPutStr Handle
h Text
s
#ifdef WITH_ZLIB
if String -> CI String
forall s. FoldCase s => s -> CI s
CI.mk (String -> String
takeExtension String
fname) CI String -> CI String -> Bool
forall a. Eq a => a -> a -> Bool
/= CI String
".gz" then do
IO ()
writeSimple
else do
TextEncoding
enc <- case FileOptions -> Maybe TextEncoding
optFileEncoding FileOptions
opt of
Maybe TextEncoding
Nothing -> IO TextEncoding
getLocaleEncoding
Just TextEncoding
enc -> TextEncoding -> IO TextEncoding
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return TextEncoding
enc
String -> ByteString -> IO ()
BL.writeFile String
fname (ByteString -> IO ()) -> ByteString -> IO ()
forall a b. (a -> b) -> a -> b
$ ByteString -> ByteString
GZip.compress (ByteString -> ByteString) -> ByteString -> ByteString
forall a b. (a -> b) -> a -> b
$ TextEncoding -> Text -> ByteString
encode TextEncoding
enc Text
s
#else
writeSimple
#endif
toLPString :: FileOptions -> Problem Scientific -> Either String TL.Text
toLPString :: FileOptions -> Problem Scientific -> Either String Text
toLPString = FileOptions -> Problem Scientific -> Either String Text
LPFile.render
toMPSString :: FileOptions -> Problem Scientific -> Either String TL.Text
toMPSString :: FileOptions -> Problem Scientific -> Either String Text
toMPSString = FileOptions -> Problem Scientific -> Either String Text
MPSFile.render