• Home
  • Features
  • Pricing
  • Docs
  • Announcements
  • Sign In

msakai / haskell-MIP / 351

04 Jan 2026 10:32PM UTC coverage: 77.291% (+0.005%) from 77.286%
351

push

github

msakai
update ChangeLog for v0.2.0.1

1518 of 1964 relevant lines covered (77.29%)

0.77 hits per line

Source File
Press 'n' to go to next uncovered line, 'b' for previous

89.71
/MIP/src/Numeric/Optimization/MIP/MPSFile.hs
1
{-# OPTIONS_GHC -Wall -fno-warn-unused-do-bind #-}
2
{-# OPTIONS_HADDOCK show-extensions #-}
3
{-# LANGUAGE ConstraintKinds #-}
4
{-# LANGUAGE FlexibleContexts #-}
5
{-# LANGUAGE OverloadedStrings #-}
6
{-# LANGUAGE ScopedTypeVariables #-}
7
{-# LANGUAGE TypeFamilies #-}
8
{-# LANGUAGE TypeOperators #-}
9
-----------------------------------------------------------------------------
10
-- |
11
-- Module      :  Numeric.Optimization.MIP.MPSFile
12
-- Copyright   :  (c) Masahiro Sakai 2012-2014
13
-- License     :  BSD-style
14
--
15
-- Maintainer  :  masahiro.sakai@gmail.com
16
-- Stability   :  provisional
17
-- Portability :  non-portable
18
--
19
-- A @.mps@ format parser library.
20
--
21
-- References:
22
--
23
-- * <http://pic.dhe.ibm.com/infocenter/cosinfoc/v12r4/topic/ilog.odms.cplex.help/CPLEX/File_formats_reference/topics/MPS_synopsis.html>
24
--
25
-- * <http://pic.dhe.ibm.com/infocenter/cosinfoc/v12r4/topic/ilog.odms.cplex.help/CPLEX/File_formats_reference/topics/MPS_ext_synopsis.html>
26
--
27
-- * <http://www.gurobi.com/documentation/5.0/reference-manual/node744>
28
--
29
-- * <http://en.wikipedia.org/wiki/MPS_(format)>
30
--
31
-----------------------------------------------------------------------------
32
module Numeric.Optimization.MIP.MPSFile
33
  ( parseString
34
  , parseFile
35
  , ParseError
36
  , parser
37
  , render
38
  ) where
39

40
import Control.Exception (throwIO)
41
import Control.Monad
42
import Control.Monad.Writer
43
import Data.Default.Class
44
import Data.Maybe
45
import Data.Set (Set)
46
import qualified Data.Set as Set
47
import Data.Map (Map)
48
import qualified Data.Map as Map
49
import Data.Scientific
50
import Data.Interned
51
import Data.Interned.Text
52
import Data.String
53
import qualified Data.Text as T
54
import qualified Data.Text.Lazy as TL
55
import Data.Text.Lazy.Builder (Builder)
56
import qualified Data.Text.Lazy.Builder as B
57
import qualified Data.Text.Lazy.IO as TLIO
58
import System.IO
59
import Text.Megaparsec hiding  (ParseError)
60
import Text.Megaparsec.Char hiding (string', eol)
61
import qualified Text.Megaparsec.Char as P
62
import qualified Text.Megaparsec.Char.Lexer as Lexer
63

64
import Data.OptDir
65
import qualified Numeric.Optimization.MIP.Base as MIP
66
import Numeric.Optimization.MIP.FileUtils (ParseError)
67

68
type Column = MIP.Var
69
type Row = InternedText
70

71
data BoundType
72
  = LO  -- lower bound
73
  | UP  -- upper bound
74
  | FX  -- variable is fixed at the specified value
75
  | FR  -- free variable (no lower or upper bound)
76
  | MI  -- infinite lower bound
77
  | PL  -- infinite upper bound
78
  | BV  -- variable is binary (equal 0 or 1)
79
  | LI  -- lower bound for integer variable
80
  | UI  -- upper bound for integer variable
81
  | SC  -- upper bound for semi-continuous variable
82
  | SI  -- upper bound for semi-integer variable
83
  deriving (Eq, Ord, Show, Read, Enum, Bounded)
×
84

85
-- ---------------------------------------------------------------------------
86

87
type C e s m = (MonadParsec e s m, Token s ~ Char, IsString (Tokens s))
88

89
-- | Parse a string containing MPS file data.
90
-- The source name is only used in error messages and may be the empty string.
91
parseString :: (Stream s, Token s ~ Char, IsString (Tokens s)) => MIP.FileOptions -> String -> s -> Either (ParseError s) (MIP.Problem Scientific)
92
parseString _ = parse (parser <* eof)
1✔
93

94
-- | Parse a file containing MPS file data.
95
parseFile :: MIP.FileOptions -> FilePath -> IO (MIP.Problem Scientific)
96
parseFile opt fname = do
1✔
97
  h <- openFile fname ReadMode
1✔
98
  case MIP.optFileEncoding opt of
1✔
99
    Nothing -> return ()
×
100
    Just enc -> hSetEncoding h enc
×
101
  ret <- parse (parser <* eof) fname <$> TLIO.hGetContents h
×
102
  case ret of
1✔
103
    Left e -> throwIO (e :: ParseError TL.Text)
×
104
    Right a -> return a
1✔
105

106
-- ---------------------------------------------------------------------------
107

108

109
anyChar :: C e s m => m Char
110
anyChar = anySingle
1✔
111

112
space' :: C e s m => m Char
113
space' = oneOf [' ', '\t']
1✔
114

115
spaces' :: C e s m => m ()
116
spaces' = skipMany space'
1✔
117

118
spaces1' :: C e s m => m ()
119
spaces1' = skipSome space'
1✔
120

121
commentline :: C e s m => m ()
122
commentline = do
1✔
123
  _ <- char '*'
1✔
124
  _ <- manyTill anyChar P.eol
1✔
125
  return ()
×
126

127
eol' :: C e s m => m ()
128
eol' = do
1✔
129
  spaces'
1✔
130
  _ <- P.eol
1✔
131
  skipMany commentline
1✔
132
  return ()
×
133

134
tok :: C e s m => m a -> m a
135
tok p = do
1✔
136
  x <- p
1✔
137
  msum [eof, lookAhead (P.eol >> return ()), spaces1']
×
138
  return x
1✔
139

140
row :: C e s m => m Row
141
row = liftM intern ident
1✔
142

143
column :: C e s m => m Column
144
column = liftM MIP.Var $ ident
1✔
145

146
ident :: C e s m => m T.Text
147
ident = liftM fromString $ tok $ some $ noneOf [' ', '\t', '\r', '\n']
1✔
148

149
stringLn :: C e s m => String -> m ()
150
stringLn s = string (fromString s) >> eol'
1✔
151

152
number :: forall e s m. C e s m => m Scientific
153
number = tok $ Lexer.signed (return ()) Lexer.scientific
×
154

155
-- ---------------------------------------------------------------------------
156

157
-- | MPS file parser
158
parser :: (MonadParsec e s m, Token s ~ Char, IsString (Tokens s)) => m (MIP.Problem Scientific)
159
parser = do
1✔
160
  many commentline
1✔
161

162
  name <- nameSection
1✔
163

164
  -- http://pic.dhe.ibm.com/infocenter/cosinfoc/v12r4/topic/ilog.odms.cplex.help/CPLEX/File_formats_reference/topics/MPS_ext_objsen.html
165
  -- CPLEX extends the MPS standard by allowing two additional sections: OBJSEN and OBJNAME.
166
  -- If these options are used, they must appear in order and as the first and second sections after the NAME section.
167
  objsense <- optional $ objSenseSection
1✔
168
  objname  <- optional $ objNameSection
1✔
169

170
  rows <- rowsSection
1✔
171

172
  -- http://pic.dhe.ibm.com/infocenter/cosinfoc/v12r4/topic/ilog.odms.cplex.help/CPLEX/File_formats_reference/topics/MPS_ext_usercuts.html
173
  -- The order of sections must be ROWS USERCUTS.
174
  usercuts <- option [] userCutsSection
1✔
175

176
  -- http://pic.dhe.ibm.com/infocenter/cosinfoc/v12r4/topic/ilog.odms.cplex.help/CPLEX/File_formats_reference/topics/MPS_ext_lazycons.html
177
  -- The order of sections must be ROWS USERCUTS LAZYCONS.
178
  lazycons <- option [] lazyConsSection
1✔
179

180
  (cols, intvs1) <- colsSection
1✔
181
  rhss <- rhsSection
1✔
182
  rngs <- option Map.empty rangesSection
1✔
183
  bnds <- option [] boundsSection
1✔
184

185
  -- http://pic.dhe.ibm.com/infocenter/cosinfoc/v12r4/topic/ilog.odms.cplex.help/CPLEX/File_formats_reference/topics/MPS_ext_quadobj.html
186
  -- Following the BOUNDS section, a QMATRIX section may be specified.
187
  qobj <- msum [quadObjSection, qMatrixSection, return []]
1✔
188

189
  -- http://pic.dhe.ibm.com/infocenter/cosinfoc/v12r4/topic/ilog.odms.cplex.help/CPLEX/File_formats_reference/topics/MPS_ext_sos.html
190
  -- Note that in an MPS file, the SOS section must follow the BOUNDS section.
191
  sos <- option [] sosSection
1✔
192

193
  -- http://pic.dhe.ibm.com/infocenter/cosinfoc/v12r4/topic/ilog.odms.cplex.help/CPLEX/File_formats_reference/topics/MPS_ext_qcmatrix.html
194
  -- QCMATRIX sections appear after the optional SOS section.
195
  qterms <- liftM Map.fromList $ many qcMatrixSection
1✔
196

197
  -- http://pic.dhe.ibm.com/infocenter/cosinfoc/v12r4/topic/ilog.odms.cplex.help/CPLEX/File_formats_reference/topics/MPS_ext_indicators.html
198
  -- The INDICATORS section follows any quadratic constraint section and any quadratic objective section.
199
  inds <- option Map.empty indicatorsSection
1✔
200

201
  string "ENDATA"
1✔
202
  P.space
1✔
203

204
  let objrow =
1✔
205
        case objname of
1✔
206
          Nothing -> head [r | (Nothing, r) <- rows] -- XXX
1✔
207
          Just r  -> intern r
1✔
208
      objdir =
1✔
209
        case objsense of
1✔
210
          Nothing -> OptMin
1✔
211
          Just d  -> d
1✔
212
      vs     = Map.keysSet cols `Set.union` Set.fromList [col | (_,col,_) <- bnds]
1✔
213
      intvs2 = Set.fromList [col | (t,col,_) <- bnds, t `elem` [BV,LI,UI]]
1✔
214
      scvs   = Set.fromList [col | (SC,col,_) <- bnds]
1✔
215
      sivs   = Set.fromList [col | (SI,col,_) <- bnds]
1✔
216

217
  let explicitBounds = Map.fromListWith f
1✔
218
        [ case typ of
1✔
219
            LO -> (col, (Just (MIP.Finite val), Nothing))
1✔
220
            UP -> (col, (Nothing, Just (MIP.Finite val)))
1✔
221
            FX -> (col, (Just (MIP.Finite val), Just (MIP.Finite val)))
1✔
222
            FR -> (col, (Just MIP.NegInf, Just MIP.PosInf))
1✔
223
            MI -> (col, (Just MIP.NegInf, Nothing))
1✔
224
            PL -> (col, (Nothing, Just MIP.PosInf))
1✔
225
            BV -> (col, (Just (MIP.Finite 0), Just (MIP.Finite 1)))
1✔
226
            LI -> (col, (Just (MIP.Finite val), Nothing))
1✔
227
            UI -> (col, (Nothing, Just (MIP.Finite val)))
1✔
228
            SC -> (col, (Nothing, Just (MIP.Finite val)))
1✔
229
            SI -> (col, (Nothing, Just (MIP.Finite val)))
×
230
        | (typ,col,val) <- bnds ]
1✔
231
        where
232
          f (a1,b1) (a2,b2) = (g a1 a2, g b1 b2)
×
233
          g _ (Just x) = Just x
1✔
234
          g x Nothing  = x
1✔
235

236
  let bounds = Map.fromList
1✔
237
        [ case Map.lookup v explicitBounds of
1✔
238
            Nothing ->
239
              if v `Set.member` intvs1
1✔
240
              then
241
                -- http://eaton.math.rpi.edu/cplex90html/reffileformatscplex/reffileformatscplex9.html
242
                -- If no bounds are specified for the variables within markers, bounds of 0 (zero) and 1 (one) are assumed.
243
                (v, (MIP.Finite 0, MIP.Finite 1))
1✔
244
              else
245
                (v, (MIP.Finite 0, MIP.PosInf))
1✔
246
            Just (Nothing, Just (MIP.Finite ub)) | ub < 0 ->
1✔
247
              {-
248
                http://pic.dhe.ibm.com/infocenter/cosinfoc/v12r4/topic/ilog.odms.cplex.help/CPLEX/File_formats_reference/topics/MPS_records.html
249
                If no bounds are specified, CPLEX assumes a lower
250
                bound of 0 (zero) and an upper bound of +∞. If only a
251
                single bound is specified, the unspecified bound
252
                remains at 0 or +∞, whichever applies, with one
253
                exception. If an upper bound of less than 0 is
254
                specified and no other bound is specified, the lower
255
                bound is automatically set to -∞. CPLEX deviates
256
                slightly from a convention used by some MPS readers
257
                when it encounters an upper bound of 0 (zero). Rather
258
                than automatically set this variable’s lower bound to
259
                -∞, CPLEX accepts both a lower and upper bound of 0,
260
                effectively fixing that variable at 0. CPLEX resets
261
                the lower bound to -∞ only if the upper bound is less
262
                than 0. A warning message is issued when this
263
                exception is encountered.
264
              -}
265
              (v, (MIP.NegInf, MIP.Finite ub))
1✔
266
            {-
267
              lp_solve uses 1 as default lower bound for semi-continuous variable.
268
              <http://lpsolve.sourceforge.net/5.5/mps-format.htm>
269
              But Gurobi Optimizer uses 0 as default lower bound for semi-continuous variable.
270
              Here we adopt Gurobi's way.
271
            -}
272
{-
273
            Just (Nothing, ub) | v `Set.member` scvs ->
274
              (v, (MIP.Finite 1, fromMaybe MIP.PosInf ub))
275
-}
276
            Just (lb,ub) ->
277
              (v, (fromMaybe (MIP.Finite 0) lb, fromMaybe MIP.PosInf ub))
1✔
278
        | v <- Set.toList vs ]
1✔
279

280
  let rowCoeffs :: Map Row (Map Column Scientific)
281
      rowCoeffs = Map.fromListWith Map.union [(r, Map.singleton col coeff) | (col,m) <- Map.toList cols, (r,coeff) <- Map.toList m]
1✔
282

283
  let f :: Bool -> (Maybe MIP.RelOp, Row) -> [MIP.Constraint Scientific]
284
      f _isLazy (Nothing, _row) = []
1✔
285
      f isLazy (Just op, r) = do
1✔
286
        let lhs = [MIP.Term c [col] | (col,c) <- Map.toList (Map.findWithDefault Map.empty r rowCoeffs)]
×
287
                  ++ Map.findWithDefault [] r qterms
1✔
288
        let rhs = Map.findWithDefault 0 r rhss
1✔
289
            (lb,ub) =
290
              case Map.lookup r rngs of
1✔
291
                Nothing  ->
292
                  case op of
1✔
293
                    MIP.Ge  -> (MIP.Finite rhs, MIP.PosInf)
1✔
294
                    MIP.Le  -> (MIP.NegInf, MIP.Finite rhs)
1✔
295
                    MIP.Eql -> (MIP.Finite rhs, MIP.Finite rhs)
1✔
296
                Just rng ->
297
                  case op of
1✔
298
                    MIP.Ge  -> (MIP.Finite rhs, MIP.Finite (rhs + abs rng))
1✔
299
                    MIP.Le  -> (MIP.Finite (rhs - abs rng), MIP.Finite rhs)
1✔
300
                    MIP.Eql ->
301
                      if rng < 0
1✔
302
                      then (MIP.Finite (rhs + rng), MIP.Finite rhs)
1✔
303
                      else (MIP.Finite rhs, MIP.Finite (rhs + rng))
1✔
304
        return $
1✔
305
          MIP.Constraint
1✔
306
          { MIP.constrLabel     = Just $ unintern r
1✔
307
          , MIP.constrIndicator = Map.lookup r inds
1✔
308
          , MIP.constrIsLazy    = isLazy
1✔
309
          , MIP.constrExpr      = MIP.Expr lhs
1✔
310
          , MIP.constrLB        = lb
1✔
311
          , MIP.constrUB        = ub
1✔
312
          }
313

314
  let mip =
1✔
315
        MIP.Problem
1✔
316
        { MIP.name                  = name
1✔
317
        , MIP.objectiveFunction     = def
1✔
318
            { MIP.objDir = objdir
1✔
319
            , MIP.objLabel = Just (unintern objrow)
1✔
320
            , MIP.objExpr = MIP.Expr $ [MIP.Term c [col] | (col,m) <- Map.toList cols, c <- maybeToList (Map.lookup objrow m)] ++ qobj
1✔
321
            }
322
        , MIP.constraints           = concatMap (f False) rows ++ concatMap (f True) lazycons
1✔
323
        , MIP.sosConstraints        = sos
1✔
324
        , MIP.userCuts              = concatMap (f False) usercuts
×
325
        , MIP.varDomains            = Map.fromAscList
1✔
326
            [ (v, (t, bs))
1✔
327
            | v <- Set.toAscList vs
1✔
328
            , let t =
1✔
329
                    if v `Set.member` sivs then
1✔
330
                      MIP.SemiIntegerVariable
1✔
331
                    else if v `Set.member` intvs1 && v `Set.member` scvs then
1✔
332
                      MIP.SemiIntegerVariable
1✔
333
                    else if v `Set.member` intvs1 || v `Set.member` intvs2 then
1✔
334
                      MIP.IntegerVariable
1✔
335
                    else if v `Set.member` scvs then
1✔
336
                      MIP.SemiContinuousVariable
1✔
337
                    else
338
                      MIP.ContinuousVariable
1✔
339
            , let bs = Map.findWithDefault MIP.defaultBounds v bounds
×
340
            ]
341
        }
342

343
  return mip
1✔
344

345
nameSection :: C e s m => m (Maybe T.Text)
346
nameSection = do
1✔
347
  string "NAME"
1✔
348
  n <- optional $ try $ do
1✔
349
    spaces1'
1✔
350
    ident
1✔
351
  eol'
1✔
352
  return n
1✔
353

354
objSenseSection :: C e s m => m OptDir
355
objSenseSection = do
1✔
356
  try $ stringLn "OBJSENSE"
1✔
357
  spaces1'
1✔
358
  d <-  (try (stringLn "MAX") >> return OptMax)
1✔
359
    <|> (stringLn "MIN" >> return OptMin)
×
360
  return d
1✔
361

362
objNameSection :: C e s m => m T.Text
363
objNameSection = do
1✔
364
  try $ stringLn "OBJNAME"
1✔
365
  spaces1'
1✔
366
  name <- ident
1✔
367
  eol'
1✔
368
  return name
1✔
369

370
rowsSection :: C e s m => m [(Maybe MIP.RelOp, Row)]
371
rowsSection = do
1✔
372
  try $ stringLn "ROWS"
1✔
373
  rowsBody
1✔
374

375
userCutsSection :: C e s m => m [(Maybe MIP.RelOp, Row)]
376
userCutsSection = do
1✔
377
  try $ stringLn "USERCUTS"
1✔
378
  rowsBody
1✔
379

380
lazyConsSection :: C e s m => m [(Maybe MIP.RelOp, Row)]
381
lazyConsSection = do
1✔
382
  try $ stringLn "LAZYCONS"
1✔
383
  rowsBody
1✔
384

385
rowsBody :: C e s m => m [(Maybe MIP.RelOp, Row)]
386
rowsBody = many $ do
1✔
387
  spaces1'
1✔
388
  op <- msum
1✔
389
        [ char 'N' >> return Nothing
1✔
390
        , char 'G' >> return (Just MIP.Ge)
1✔
391
        , char 'L' >> return (Just MIP.Le)
1✔
392
        , char 'E' >> return (Just MIP.Eql)
1✔
393
        ]
394
  spaces1'
1✔
395
  name <- row
1✔
396
  eol'
1✔
397
  return (op, name)
1✔
398

399
colsSection :: forall e s m. C e s m => m (Map Column (Map Row Scientific), Set Column)
400
colsSection = do
1✔
401
  try $ stringLn "COLUMNS"
1✔
402
  body False Map.empty Set.empty
1✔
403
  where
404
    body :: Bool -> Map Column (Map Row Scientific) -> Set Column -> m (Map Column (Map Row Scientific), Set Column)
405
    body isInt rs ivs = msum
1✔
406
      [ do _ <- spaces1'
1✔
407
           x <- ident
1✔
408
           msum
1✔
409
             [ do isInt' <- try intMarker
1✔
410
                  body isInt' rs ivs
1✔
411
             , do (k,v) <- entry x
1✔
412
                  let rs'  = Map.insertWith Map.union k v rs
1✔
413
                      ivs' = if isInt then Set.insert k ivs else ivs
1✔
414
                  seq rs' $ seq ivs' $ body isInt rs' ivs'
1✔
415
             ]
416
      , return (rs, ivs)
1✔
417
      ]
418

419
    intMarker :: m Bool
420
    intMarker = do
1✔
421
      string "'MARKER'"
1✔
422
      spaces1'
1✔
423
      b <-  (try (string "'INTORG'") >> return True)
1✔
424
        <|> (string "'INTEND'" >> return False)
×
425
      eol'
1✔
426
      return b
1✔
427

428
    entry :: T.Text -> m (Column, Map Row Scientific)
429
    entry x = do
1✔
430
      let col = MIP.Var x
1✔
431
      rv1 <- rowAndVal
1✔
432
      opt <- optional rowAndVal
1✔
433
      eol'
1✔
434
      case opt of
1✔
435
        Nothing -> return (col, rv1)
1✔
436
        Just rv2 ->  return (col, Map.union rv1 rv2)
1✔
437

438
rowAndVal :: C e s m => m (Map Row Scientific)
439
rowAndVal = do
1✔
440
  r <- row
1✔
441
  val <- number
1✔
442
  return $ Map.singleton r val
1✔
443

444
rhsSection :: C e s m => m (Map Row Scientific)
445
rhsSection = do
1✔
446
  try $ stringLn "RHS"
1✔
447
  liftM Map.unions $ many entry
1✔
448
  where
449
    entry = do
1✔
450
      spaces1'
1✔
451
      _name <- ident
1✔
452
      rv1 <- rowAndVal
1✔
453
      opt <- optional rowAndVal
1✔
454
      eol'
1✔
455
      case opt of
1✔
456
        Nothing  -> return rv1
1✔
457
        Just rv2 -> return $ Map.union rv1 rv2
1✔
458

459
rangesSection :: C e s m => m (Map Row Scientific)
460
rangesSection = do
1✔
461
  try $ stringLn "RANGES"
1✔
462
  liftM Map.unions $ many entry
1✔
463
  where
464
    entry = do
1✔
465
      spaces1'
1✔
466
      _name <- ident
1✔
467
      rv1 <- rowAndVal
1✔
468
      opt <- optional rowAndVal
1✔
469
      eol'
1✔
470
      case opt of
1✔
471
        Nothing  -> return rv1
1✔
472
        Just rv2 -> return $ Map.union rv1 rv2
×
473

474
boundsSection :: C e s m => m [(BoundType, Column, Scientific)]
475
boundsSection = do
1✔
476
  try $ stringLn "BOUNDS"
1✔
477
  many entry
1✔
478
  where
479
    entry = do
1✔
480
      spaces1'
1✔
481
      typ   <- boundType
1✔
482
      _name <- ident
1✔
483
      col   <- column
1✔
484
      val   <- if typ `elem` [FR, BV, MI, PL]
1✔
485
               then return 0
×
486
               else number
1✔
487
      eol'
1✔
488
      return (typ, col, val)
1✔
489

490
boundType :: C e s m => m BoundType
491
boundType = tok $ do
1✔
492
  msum [try (string (fromString (show k))) >> return k | k <- [minBound..maxBound]]
1✔
493

494
sosSection :: forall e s m. C e s m => m [MIP.SOSConstraint Scientific]
495
sosSection = do
1✔
496
  try $ stringLn "SOS"
1✔
497
  many entry
1✔
498
  where
499
    entry = do
1✔
500
      spaces1'
1✔
501
      typ <-  (try (string "S1") >> return MIP.S1)
1✔
502
          <|> (string "S2" >> return MIP.S2)
1✔
503
      spaces1'
1✔
504
      name <- ident
1✔
505
      eol'
1✔
506
      xs <- many (try identAndVal)
1✔
507
      return $ MIP.SOSConstraint{ MIP.sosLabel = Just name, MIP.sosType = typ, MIP.sosBody = xs }
1✔
508

509
    identAndVal :: m (Column, Scientific)
510
    identAndVal = do
1✔
511
      spaces1'
1✔
512
      col <- column
1✔
513
      val <- number
1✔
514
      eol'
1✔
515
      return (col, val)
1✔
516

517
quadObjSection :: C e s m => m [MIP.Term Scientific]
518
quadObjSection = do
1✔
519
  try $ stringLn "QUADOBJ"
1✔
520
  many entry
1✔
521
  where
522
    entry = do
1✔
523
      spaces1'
1✔
524
      col1 <- column
1✔
525
      col2 <- column
1✔
526
      val  <- number
1✔
527
      eol'
1✔
528
      return $ MIP.Term (if col1 /= col2 then val else val / 2) [col1, col2]
1✔
529

530
qMatrixSection :: C e s m => m [MIP.Term Scientific]
531
qMatrixSection = do
1✔
532
  try $ stringLn "QMATRIX"
1✔
533
  many entry
1✔
534
  where
535
    entry = do
1✔
536
      spaces1'
1✔
537
      col1 <- column
1✔
538
      col2 <- column
1✔
539
      val  <- number
1✔
540
      eol'
1✔
541
      return $ MIP.Term (val / 2) [col1, col2]
1✔
542

543
qcMatrixSection :: C e s m => m (Row, [MIP.Term Scientific])
544
qcMatrixSection = do
1✔
545
  try $ string "QCMATRIX"
1✔
546
  spaces1'
1✔
547
  r <- row
1✔
548
  eol'
1✔
549
  xs <- many entry
1✔
550
  return (r, xs)
1✔
551
  where
552
    entry = do
1✔
553
      spaces1'
1✔
554
      col1 <- column
1✔
555
      col2 <- column
1✔
556
      val  <- number
1✔
557
      eol'
1✔
558
      return $ MIP.Term val [col1, col2]
1✔
559

560
indicatorsSection :: C e s m => m (Map Row (Column, Scientific))
561
indicatorsSection = do
1✔
562
  try $ stringLn "INDICATORS"
1✔
563
  liftM Map.fromList $ many entry
1✔
564
  where
565
    entry = do
1✔
566
      spaces1'
1✔
567
      string "IF"
1✔
568
      spaces1'
1✔
569
      r <- row
1✔
570
      var <- column
1✔
571
      val <- number
1✔
572
      eol'
1✔
573
      return (r, (var, val))
1✔
574

575
-- ---------------------------------------------------------------------------
576

577
type M a = Writer Builder a
578

579
execM :: M a -> TL.Text
580
execM m = B.toLazyText $ execWriter m
1✔
581

582
writeText :: T.Text -> M ()
583
writeText s = tell $ B.fromText s
1✔
584

585
writeChar :: Char -> M ()
586
writeChar c = tell $ B.singleton c
1✔
587

588
-- ---------------------------------------------------------------------------
589

590
-- | Render a problem into a 'TL.Text' containing MPS file data.
591
render :: MIP.FileOptions -> MIP.Problem Scientific -> Either String TL.Text
592
render _ mip | not (checkAtMostQuadratic mip) = Left "Expression must be atmost quadratic"
×
593
render opt mip = Right $ execM $ render' opt $ nameRows mip
1✔
594

595
render' :: MIP.FileOptions -> MIP.Problem Scientific -> M ()
596
render' opt mip = do
1✔
597
  let probName = fromMaybe "" (MIP.name mip)
1✔
598

599
  -- NAME section
600
  -- The name starts in column 15 in fixed formats.
601
  writeSectionHeader $ "NAME" <> T.replicate 10 " " <> probName
1✔
602

603
  let MIP.ObjectiveFunction
604
       { MIP.objLabel = Just objName
605
       , MIP.objDir = dir
606
       , MIP.objExpr = obj
607
       } = MIP.objectiveFunction mip
1✔
608

609
  -- OBJSENSE section
610
  when (MIP.optMPSWriteObjSense opt == MIP.WriteAlways ||
1✔
611
        MIP.optMPSWriteObjSense opt == MIP.WriteIfNotDefault && dir /= OptMin) $ do
1✔
612
    writeSectionHeader "OBJSENSE"
1✔
613
    case dir of
1✔
614
      OptMin -> writeFields ["MIN"]
×
615
      OptMax -> writeFields ["MAX"]
1✔
616

617
  -- OBJNAME section
618
  -- Note: GLPK-4.48 does not support this section.
619
  when (MIP.optMPSWriteObjName opt) $ do
1✔
620
    writeSectionHeader "OBJNAME"
1✔
621
    writeFields [objName]
1✔
622

623
  let splitRange c =
1✔
624
        case (MIP.constrLB c, MIP.constrUB c) of
1✔
625
          (MIP.Finite x, MIP.PosInf) -> ((MIP.Ge, x), Nothing)
1✔
626
          (MIP.NegInf, MIP.Finite x) -> ((MIP.Le, x), Nothing)
1✔
627
          (MIP.Finite x1, MIP.Finite x2)
628
            | x1 == x2 -> ((MIP.Eql, x1), Nothing)
1✔
629
            | x1 < x2  -> ((MIP.Eql, x1), Just (x2 - x1))
×
630
          _ -> error "invalid constraint bound"
×
631

632
  let renderRows cs = do
1✔
633
        forM_ cs $ \c -> do
1✔
634
          let ((op,_), _) = splitRange c
1✔
635
          let s = case op of
1✔
636
                    MIP.Le  -> "L"
1✔
637
                    MIP.Ge  -> "G"
1✔
638
                    MIP.Eql -> "E"
1✔
639
          writeFields [s, fromJust $ MIP.constrLabel c]
1✔
640

641
  -- ROWS section
642
  writeSectionHeader "ROWS"
1✔
643
  writeFields ["N", objName]
1✔
644
  renderRows [c | c <- MIP.constraints mip, not (MIP.constrIsLazy c)]
1✔
645

646
  -- USERCUTS section
647
  unless (null (MIP.userCuts mip)) $ do
1✔
648
    writeSectionHeader "USERCUTS"
1✔
649
    renderRows (MIP.userCuts mip)
1✔
650

651
  -- LAZYCONS section
652
  let lcs = [c | c <- MIP.constraints mip, MIP.constrIsLazy c]
1✔
653
  unless (null lcs) $ do
1✔
654
    writeSectionHeader "LAZYCONS"
1✔
655
    renderRows lcs
1✔
656

657
  -- COLUMNS section
658
  writeSectionHeader "COLUMNS"
1✔
659
  let cols :: Map Column (Map T.Text Scientific)
660
      cols = Map.fromListWith Map.union
1✔
661
             [ (v, Map.singleton l d)
1✔
662
             | (Just l, xs) <-
663
                 (Just objName, obj) :
1✔
664
                 [(MIP.constrLabel c, lhs) | c <- MIP.constraints mip ++ MIP.userCuts mip, let lhs = MIP.constrExpr c]
1✔
665
             , MIP.Term d [v] <- MIP.terms xs
1✔
666
             ]
667
      f col xs =
1✔
668
        forM_ (Map.toList xs) $ \(r, d) -> do
1✔
669
          writeFields ["", MIP.varName col, r, showValue d]
1✔
670
      ivs = MIP.integerVariables mip `Set.union` MIP.semiIntegerVariables mip
1✔
671
  forM_ (Map.toList (Map.filterWithKey (\col _ -> col `Set.notMember` ivs) cols)) $ \(col, xs) -> f col xs
1✔
672
  unless (Set.null ivs) $ do
1✔
673
    writeFields ["", "MARK0000", "'MARKER'", "", "'INTORG'"]
1✔
674
    forM_ (Map.toList (Map.filterWithKey (\col _ -> col `Set.member` ivs) cols)) $ \(col, xs) -> f col xs
1✔
675
    writeFields ["", "MARK0001", "'MARKER'", "", "'INTEND'"]
1✔
676

677
  -- RHS section
678
  let rs = [(fromJust $ MIP.constrLabel c, rhs) | c <- MIP.constraints mip ++ MIP.userCuts mip, let ((_,rhs),_) = splitRange c, rhs /= 0]
1✔
679
  writeSectionHeader "RHS"
1✔
680
  forM_ rs $ \(name, val) -> do
1✔
681
    writeFields ["", "rhs", name, showValue val]
1✔
682

683
  -- RANGES section
684
  let rngs = [(fromJust $ MIP.constrLabel c, fromJust rng) | c <- MIP.constraints mip ++ MIP.userCuts mip, let ((_,_), rng) = splitRange c, isJust rng]
1✔
685
  unless (null rngs) $ do
1✔
686
    writeSectionHeader "RANGES"
1✔
687
    forM_ rngs $ \(name, val) -> do
1✔
688
      writeFields ["", "rhs", name, showValue val]
1✔
689

690
  -- BOUNDS section
691
  writeSectionHeader "BOUNDS"
1✔
692
  forM_ (Map.toList (MIP.varDomains mip)) $ \(col, (vt, _)) -> do
1✔
693
    let (lb,ub) = MIP.getBounds mip col
1✔
694
    case (lb,ub)  of
1✔
695
      (MIP.NegInf, MIP.PosInf) -> do
1✔
696
        -- free variable (no lower or upper bound)
697
        writeFields ["FR", "bound", MIP.varName col]
1✔
698

699
      (MIP.Finite 0, MIP.Finite 1) | vt == MIP.IntegerVariable -> do
1✔
700
        -- variable is binary (equal 0 or 1)
701
        writeFields ["BV", "bound", MIP.varName col]
1✔
702

703
      (MIP.Finite a, MIP.Finite b) | a == b -> do
1✔
704
        -- variable is fixed at the specified value
705
        writeFields ["FX", "bound", MIP.varName col, showValue a]
1✔
706

707
      _ -> do
1✔
708
        case lb of
1✔
709
          MIP.PosInf -> error "should not happen"
×
710
          MIP.NegInf -> do
1✔
711
            -- Minus infinity
712
            writeFields ["MI", "bound", MIP.varName col]
1✔
713
          MIP.Finite 0 | vt == MIP.ContinuousVariable -> return ()
×
714
          MIP.Finite a -> do
1✔
715
            let t = case vt of
1✔
716
                      MIP.IntegerVariable -> "LI" -- lower bound for integer variable
1✔
717
                      _ -> "LO" -- Lower bound
1✔
718
            writeFields [t, "bound", MIP.varName col, showValue a]
1✔
719

720
        case ub of
1✔
721
          MIP.NegInf -> error "should not happen"
×
722
          MIP.PosInf | vt == MIP.ContinuousVariable -> return ()
×
723
          MIP.PosInf -> do
1✔
724
            when (vt == MIP.SemiContinuousVariable || vt == MIP.SemiIntegerVariable) $
1✔
725
              error "cannot express +inf upper bound of semi-continuous or semi-integer variable"
×
726
            writeFields ["PL", "bound", MIP.varName col] -- Plus infinity
1✔
727
          MIP.Finite a -> do
1✔
728
            let t = case vt of
1✔
729
                      MIP.SemiContinuousVariable -> "SC" -- Upper bound for semi-continuous variable
1✔
730
                      MIP.SemiIntegerVariable ->
731
                        -- Gurobi uses "SC" while lpsolve uses "SI" for upper bound of semi-integer variable
732
                        "SC"
1✔
733
                      MIP.IntegerVariable -> "UI" -- Upper bound for integer variable
1✔
734
                      _ -> "UP" -- Upper bound
1✔
735
            writeFields [t, "bound", MIP.varName col, showValue a]
1✔
736

737
  -- QMATRIX section
738
  -- Gurobiは対称行列になっていないと "qmatrix isn't symmetric" というエラーを発生させる
739
  do let qm = Map.map (2*) $ quadMatrix obj
1✔
740
     unless (Map.null qm) $ do
1✔
741
       writeSectionHeader "QMATRIX"
1✔
742
       forM_ (Map.toList qm) $ \(((v1,v2), val)) -> do
1✔
743
         writeFields ["", MIP.varName v1, MIP.varName v2, showValue val]
1✔
744

745
  -- SOS section
746
  unless (null (MIP.sosConstraints mip)) $ do
1✔
747
    writeSectionHeader "SOS"
1✔
748
    forM_ (MIP.sosConstraints mip) $ \sos -> do
1✔
749
      let t = case MIP.sosType sos of
1✔
750
                MIP.S1 -> "S1"
1✔
751
                MIP.S2 -> "S2"
1✔
752
      writeFields $ t : maybeToList (MIP.sosLabel sos)
1✔
753
      forM_ (MIP.sosBody sos) $ \(var,val) -> do
1✔
754
        writeFields ["", MIP.varName var, showValue val]
1✔
755

756
  -- QCMATRIX section
757
  let xs = [ (fromJust $ MIP.constrLabel c, qm)
1✔
758
           | c <- MIP.constraints mip ++ MIP.userCuts mip
1✔
759
           , let lhs = MIP.constrExpr c
1✔
760
           , let qm = quadMatrix lhs
1✔
761
           , not (Map.null qm) ]
1✔
762
  unless (null xs) $ do
1✔
763
    forM_ xs $ \(r, qm) -> do
1✔
764
      -- The name starts in column 12 in fixed formats.
765
      writeSectionHeader $ "QCMATRIX" <> T.replicate 3 " " <> r
1✔
766
      forM_ (Map.toList qm) $ \((v1,v2), val) -> do
1✔
767
        writeFields ["", MIP.varName v1, MIP.varName v2, showValue val]
1✔
768

769
  -- INDICATORS section
770
  -- Note: Gurobi-5.6.3 does not support this section.
771
  let ics = [c | c <- MIP.constraints mip, isJust $ MIP.constrIndicator c]
1✔
772
  unless (null ics) $ do
1✔
773
    writeSectionHeader "INDICATORS"
1✔
774
    forM_ ics $ \c -> do
1✔
775
      let Just (var,val) = MIP.constrIndicator c
1✔
776
      writeFields ["IF", fromJust (MIP.constrLabel c), MIP.varName var, showValue val]
1✔
777

778
  -- ENDATA section
779
  writeSectionHeader "ENDATA"
1✔
780

781
writeSectionHeader :: T.Text -> M ()
782
writeSectionHeader s = writeText s >> writeChar '\n'
1✔
783

784
-- Fields start in column 2, 5, 15, 25, 40 and 50
785
writeFields :: [T.Text] -> M ()
786
writeFields xs0 = f1 xs0 >> writeChar '\n'
1✔
787
  where
788
    -- columns 1-4
789
    f1 [] = return ()
×
790
    f1 [x] = writeChar ' ' >> writeText x
1✔
791
    f1 (x:xs) = do
1✔
792
      writeChar ' '
1✔
793
      writeText x
1✔
794
      let len = T.length x
1✔
795
      when (len < 2) $ writeText $ T.replicate (2 - len) " "
1✔
796
      writeChar ' '
1✔
797
      f2 xs
1✔
798

799
    -- columns 5-14
800
    f2 [] = return ()
×
801
    f2 [x] = writeText x
1✔
802
    f2 (x:xs) = do
1✔
803
      writeText x
1✔
804
      let len = T.length x
1✔
805
      when (len < 9) $ writeText $ T.replicate (9 - len) " "
1✔
806
      writeChar ' '
1✔
807
      f3 xs
1✔
808

809
    -- columns 15-24
810
    f3 [] = return ()
×
811
    f3 [x] = writeText x
1✔
812
    f3 (x:xs) = do
1✔
813
      writeText x
1✔
814
      let len = T.length x
1✔
815
      when (len < 9) $ writeText $ T.replicate (9 - len) " "
1✔
816
      writeChar ' '
1✔
817
      f4 xs
1✔
818

819
    -- columns 25-39
820
    f4 [] = return ()
×
821
    f4 [x] = writeText x
1✔
822
    f4 (x:xs) = do
1✔
823
      writeText x
1✔
824
      let len = T.length x
1✔
825
      when (len < 14) $ writeText $ T.replicate (14 - len) " "
1✔
826
      writeChar ' '
1✔
827
      f5 xs
1✔
828

829
    -- columns 40-49
830
    f5 [] = return ()
×
831
    f5 [x] = writeText x
1✔
832
    f5 (x:xs) = do
×
833
      writeText x
×
834
      let len = T.length x
×
835
      when (len < 19) $ writeText $ T.replicate (19 - len) " "
×
836
      writeChar ' '
×
837
      f6 xs
×
838

839
    -- columns 50-
840
    f6 [] = return ()
×
841
    f6 [x] = writeText x
×
842
    f6 _ = error "MPSFile: >6 fields (this should not happen)"
×
843

844
showValue :: Scientific -> T.Text
845
showValue = fromString . show
1✔
846

847
nameRows :: MIP.Problem r -> MIP.Problem r
848
nameRows mip
1✔
849
  = mip
1✔
850
  { MIP.objectiveFunction = (MIP.objectiveFunction mip){ MIP.objLabel = Just objName' }
1✔
851
  , MIP.constraints = f (MIP.constraints mip) [T.pack $ "row" ++ show n | n <- [(1::Int)..]]
1✔
852
  , MIP.userCuts = f (MIP.userCuts mip) [T.pack $ "usercut" ++ show n | n <- [(1::Int)..]]
×
853
  , MIP.sosConstraints = g (MIP.sosConstraints mip) [T.pack $ "sos" ++ show n | n <- [(1::Int)..]]
×
854
  }
855
  where
856
    objName = MIP.objLabel $ MIP.objectiveFunction mip
1✔
857
    used = Set.fromList $ catMaybes $ objName : [MIP.constrLabel c | c <- MIP.constraints mip ++ MIP.userCuts mip] ++ [MIP.sosLabel c | c <- MIP.sosConstraints mip]
×
858
    objName' = fromMaybe (head [name | n <- [(1::Int)..], let name = T.pack ("obj" ++ show n), name `Set.notMember` used]) objName
×
859

860
    f [] _ = []
1✔
861
    f (c:cs) (name:names)
862
      | isJust (MIP.constrLabel c) = c : f cs (name:names)
×
863
      | name `Set.notMember` used = c{ MIP.constrLabel = Just name } : f cs names
×
864
      | otherwise = f (c:cs) names
×
865
    f _ [] = error "should not happen"
×
866

867
    g [] _ = []
1✔
868
    g (c:cs) (name:names)
869
      | isJust (MIP.sosLabel c) = c : g cs (name:names)
×
870
      | name `Set.notMember` used = c{ MIP.sosLabel = Just name } : g cs names
×
871
      | otherwise = g (c:cs) names
×
872
    g _ [] = error "should not happen"
×
873

874
quadMatrix :: Fractional r => MIP.Expr r -> Map (MIP.Var, MIP.Var) r
875
quadMatrix e = Map.fromList $ do
1✔
876
  let m = Map.fromListWith (+) [(if v1<=v2 then (v1,v2) else (v2,v1), c) | MIP.Term c [v1,v2] <- MIP.terms e]
1✔
877
  ((v1,v2),c) <- Map.toList m
1✔
878
  if v1==v2 then
1✔
879
    [((v1,v2), c)]
1✔
880
  else
881
    [((v1,v2), c/2), ((v2,v1), c/2)]
1✔
882

883
checkAtMostQuadratic :: forall r. MIP.Problem r -> Bool
884
checkAtMostQuadratic mip =  all (all f . MIP.terms) es
1✔
885
  where
886
    es = MIP.objExpr (MIP.objectiveFunction mip) :
1✔
887
         [lhs | c <- MIP.constraints mip ++ MIP.userCuts mip, let lhs = MIP.constrExpr c]
1✔
888
    f :: MIP.Term r -> Bool
889
    f (MIP.Term _ [_]) = True
1✔
890
    f (MIP.Term _ [_,_]) = True
1✔
891
    f _ = False
×
892

893
-- ---------------------------------------------------------------------------
STATUS · Troubleshooting · Open an Issue · Sales · Support · CAREERS · ENTERPRISE · START FREE · SCHEDULE DEMO
ANNOUNCEMENTS · TWITTER · TOS & SLA · Supported CI Services · What's a CI service? · Automated Testing

© 2026 Coveralls, Inc