• 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

85.82
/MIP/src/Numeric/Optimization/MIP/LPFile.hs
1
{-# OPTIONS_GHC -Wall -fno-warn-unused-do-bind #-}
2
{-# OPTIONS_HADDOCK show-extensions #-}
3
{-# LANGUAGE BangPatterns #-}
4
{-# LANGUAGE ConstraintKinds #-}
5
{-# LANGUAGE FlexibleContexts #-}
6
{-# LANGUAGE OverloadedStrings #-}
7
{-# LANGUAGE ScopedTypeVariables #-}
8
{-# LANGUAGE TypeFamilies #-}
9
{-# LANGUAGE TypeOperators #-}
10
-----------------------------------------------------------------------------
11
-- |
12
-- Module      :  Numeric.Optimization.MIP.LPFile
13
-- Copyright   :  (c) Masahiro Sakai 2011-2014
14
-- License     :  BSD-style
15
--
16
-- Maintainer  :  masahiro.sakai@gmail.com
17
-- Stability   :  provisional
18
-- Portability :  non-portable
19
--
20
-- A CPLEX @.lp@ format parser library.
21
--
22
-- References:
23
--
24
-- * <http://publib.boulder.ibm.com/infocenter/cosinfoc/v12r2/index.jsp?topic=/ilog.odms.cplex.help/Content/Optimization/Documentation/CPLEX/_pubskel/CPLEX880.html>
25
--
26
-- * <http://www.gurobi.com/doc/45/refman/node589.html>
27
--
28
-- * <http://lpsolve.sourceforge.net/5.5/CPLEX-format.htm>
29
--
30
-----------------------------------------------------------------------------
31
module Numeric.Optimization.MIP.LPFile
32
  ( parseString
33
  , parseFile
34
  , ParseError
35
  , parser
36
  , render
37
  ) where
38

39
import Control.Applicative hiding (many)
40
import Control.Exception (throwIO)
41
import Control.Monad
42
import Control.Monad.Writer
43
import Control.Monad.ST
44
import Data.Char
45
import Data.Default.Class
46
import Data.List
47
import Data.Maybe
48
import Data.Scientific (Scientific, floatingOrInteger)
49
import Data.Map (Map)
50
import qualified Data.Map as Map
51
import Data.Set (Set)
52
import qualified Data.Set as Set
53
import Data.STRef
54
import Data.String
55
import qualified Data.Text as T
56
import qualified Data.Text.Lazy as TL
57
import Data.Text.Lazy.Builder (Builder)
58
import qualified Data.Text.Lazy.Builder as B
59
import qualified Data.Text.Lazy.Builder.Int as B
60
import qualified Data.Text.Lazy.Builder.Scientific as B
61
import qualified Data.Text.Lazy.IO as TLIO
62
import Data.OptDir
63
import System.IO
64
import Text.Megaparsec hiding (label, skipManyTill, ParseError)
65
import Text.Megaparsec.Char hiding (string', char')
66
import qualified Text.Megaparsec.Char.Lexer as P
67

68
import qualified Numeric.Optimization.MIP.Base as MIP
69
import Numeric.Optimization.MIP.FileUtils (ParseError)
70
import Numeric.Optimization.MIP.Internal.Util (combineMaybe)
71

72
-- ---------------------------------------------------------------------------
73

74
type C e s m = (MonadParsec e s m, Token s ~ Char, IsString (Tokens s))
75

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

81
-- | Parse a file containing LP file data.
82
parseFile :: MIP.FileOptions -> FilePath -> IO (MIP.Problem Scientific)
83
parseFile opt fname = do
1✔
84
  h <- openFile fname ReadMode
1✔
85
  case MIP.optFileEncoding opt of
1✔
86
    Nothing -> return ()
×
87
    Just enc -> hSetEncoding h enc
×
88
  ret <- parse (parser <* eof) fname <$> TLIO.hGetContents h
×
89
  case ret of
1✔
90
    Left e -> throwIO (e :: ParseError TL.Text)
×
91
    Right a -> return a
1✔
92

93
-- ---------------------------------------------------------------------------
94

95
anyChar :: C e s m => m Char
96
anyChar = anySingle
1✔
97

98
char' :: C e s m => Char -> m Char
99
char' c = (char c <|> char (toUpper c)) <?> show c
1✔
100

101
string' :: C e s m => String -> m ()
102
string' s = mapM_ char' s <?> show s
×
103

104
sep :: C e s m => m ()
105
sep = skipMany ((comment >> return ()) <|> (spaceChar >> return ()))
×
106

107
comment :: C e s m => m ()
108
comment = do
1✔
109
  char '\\'
1✔
110
  skipManyTill anyChar (try eol)
1✔
111

112
tok :: C e s m => m a -> m a
113
tok p = do
1✔
114
  x <- p
1✔
115
  sep
1✔
116
  return x
1✔
117

118
ident :: C e s m => m String
119
ident = tok $ do
1✔
120
  x <- letterChar <|> oneOf syms1
1✔
121
  xs <- many (alphaNumChar <|> oneOf syms2)
1✔
122
  let s = x:xs
1✔
123
  guard $ map toLower s `Set.notMember` reserved
1✔
124
  return s
1✔
125
  where
126
    syms1 = "!\"#$%&()/,;?@_`'{}|~"
1✔
127
    syms2 = '.' : syms1
1✔
128

129
variable :: C e s m => m MIP.Var
130
variable = liftM fromString ident
1✔
131

132
label :: C e s m => m MIP.Label
133
label = do
1✔
134
  name <- ident
1✔
135
  tok $ char ':'
1✔
136
  return $! T.pack name
1✔
137

138
reserved :: Set String
139
reserved = Set.fromList
1✔
140
  [ "bound", "bounds"
1✔
141
  , "gen", "general", "generals"
1✔
142
  , "bin", "binary", "binaries"
1✔
143
  , "semi", "semi-continuous", "semis"
1✔
144
  , "sos"
1✔
145
  , "end"
1✔
146
  , "subject"
1✔
147
  ]
148

149
-- ---------------------------------------------------------------------------
150

151
-- | LP file parser
152
parser :: (MonadParsec e s m, Token s ~ Char, IsString (Tokens s)) => m (MIP.Problem Scientific)
153
parser = do
1✔
154
  name <- optional $ try $ do
1✔
155
    space
1✔
156
    string' "\\* Problem: "
1✔
157
    liftM fromString $ manyTill anyChar (try (string " *\\" >> eol))
1✔
158
  sep
1✔
159
  obj <- problem
1✔
160

161
  cs <- liftM concat $ many $ msum $
1✔
162
    [ liftM (map Left) constraintSection
1✔
163
    , liftM (map Left) lazyConstraintsSection
1✔
164
    , liftM (map Right) userCutsSection
1✔
165
    ]
166

167
  bnds <- option Map.empty (try boundsSection)
1✔
168
  exvs <- many (liftM Left generalSection <|> liftM Right binarySection)
1✔
169
  let ints = Set.fromList $ concat [x | Left  x <- exvs]
1✔
170
      bins = Set.fromList $ concat [x | Right x <- exvs]
1✔
171
  bnds2 <- return $ Map.unionWith MIP.intersectBounds
×
172
            bnds (Map.fromAscList [(v, (MIP.Finite 0, MIP.Finite 1)) | v <- Set.toAscList bins])
1✔
173
  scs <- liftM Set.fromList $ option [] (try semiSection)
1✔
174

175
  ss <- option [] (try sosSection)
1✔
176
  end
1✔
177
  let vs = Set.unions $ map MIP.vars cs ++
1✔
178
           [ Map.keysSet bnds2
1✔
179
           , ints
1✔
180
           , bins
1✔
181
           , scs
1✔
182
           , MIP.vars obj
1✔
183
           , MIP.vars ss
1✔
184
           ]
185
      isInt v  = v `Set.member` ints || v `Set.member` bins
1✔
186
      isSemi v = v `Set.member` scs
1✔
187
  return $
1✔
188
    MIP.Problem
1✔
189
    { MIP.name              = name
1✔
190
    , MIP.objectiveFunction = obj
1✔
191
    , MIP.constraints       = [c | Left c <- cs]
1✔
192
    , MIP.userCuts          = [c | Right c <- cs]
1✔
193
    , MIP.sosConstraints    = ss
1✔
194
    , MIP.varDomains        = Map.fromAscList
1✔
195
       [ (v, (t, bs))
1✔
196
       | v <- Set.toAscList vs
1✔
197
       , let t =
1✔
198
               if isInt v then
1✔
199
                 if isSemi v then MIP.SemiIntegerVariable
1✔
200
                 else MIP.IntegerVariable
1✔
201
               else
202
                 if isSemi v then MIP.SemiContinuousVariable
1✔
203
                 else MIP.ContinuousVariable
1✔
204
       , let bs = Map.findWithDefault MIP.defaultBounds v bnds2
1✔
205
       ]
206
    }
207

208
problem :: C e s m => m (MIP.ObjectiveFunction Scientific)
209
problem = do
1✔
210
  flag <-  (try minimize >> return OptMin)
1✔
211
       <|> (try maximize >> return OptMax)
1✔
212
  name <- optional (try label)
1✔
213
  obj <- expr
1✔
214
  return def{ MIP.objLabel = name, MIP.objDir = flag, MIP.objExpr = obj }
1✔
215

216
minimize, maximize :: C e s m => m ()
217
minimize = tok $ string' "min" >> optional (string' "imize") >> return ()
×
218
maximize = tok $ string' "max" >> optional (string' "imize") >> return ()
×
219

220
end :: C e s m => m ()
221
end = tok $ string' "end"
1✔
222

223
-- ---------------------------------------------------------------------------
224

225
constraintSection :: C e s m => m [MIP.Constraint Scientific]
226
constraintSection = subjectTo >> many (try (constraint False))
1✔
227

228
subjectTo :: C e s m => m ()
229
subjectTo = msum
1✔
230
  [ try $ tok (string' "subject") >> tok (string' "to")
1✔
231
  , try $ tok (string' "such") >> tok (string' "that")
×
232
  , try $ tok (string' "st")
1✔
233
  , try $ tok (string' "s") >> optional (tok (char '.')) >> tok (string' "t")
×
234
        >> tok (char '.') >> return ()
×
235
  ]
236

237
constraint :: C e s m => Bool -> m (MIP.Constraint Scientific)
238
constraint isLazy = do
1✔
239
  name <- optional (try label)
1✔
240
  g <- optional $ try indicator
1✔
241

242
  -- It seems that CPLEX allows empty lhs, but GLPK rejects it.
243
  e <- expr
1✔
244
  op <- relOp
1✔
245
  s <- option 1 sign
1✔
246
  rhs <- liftM (s*) number
1✔
247

248
  let (lb,ub) =
249
        case op of
1✔
250
          MIP.Le -> (MIP.NegInf, MIP.Finite rhs)
1✔
251
          MIP.Ge -> (MIP.Finite rhs, MIP.PosInf)
1✔
252
          MIP.Eql -> (MIP.Finite rhs, MIP.Finite rhs)
1✔
253

254
  return $ MIP.Constraint
1✔
255
    { MIP.constrLabel     = name
1✔
256
    , MIP.constrIndicator = g
1✔
257
    , MIP.constrExpr      = e
1✔
258
    , MIP.constrLB        = lb
1✔
259
    , MIP.constrUB        = ub
1✔
260
    , MIP.constrIsLazy    = isLazy
1✔
261
    }
262

263
relOp :: C e s m => m MIP.RelOp
264
relOp = tok $ msum
1✔
265
  [ char '<' >> optional (char '=') >> return MIP.Le
1✔
266
  , char '>' >> optional (char '=') >> return MIP.Ge
1✔
267
  , char '=' >> msum [ char '<' >> return MIP.Le
×
268
                     , char '>' >> return MIP.Ge
×
269
                     , return MIP.Eql
1✔
270
                     ]
271
  ]
272

273
indicator :: C e s m => m (MIP.Var, Scientific)
274
indicator = do
1✔
275
  var <- variable
1✔
276
  tok (char '=')
1✔
277
  val <- number  -- numbers other than 0 or 1 should be error?
1✔
278
  tok $ string "->"
1✔
279
  return (var, val)
1✔
280

281
lazyConstraintsSection :: C e s m => m [MIP.Constraint Scientific]
282
lazyConstraintsSection = do
1✔
283
  tok $ string' "lazy"
1✔
284
  tok $ string' "constraints"
1✔
285
  many $ try $ constraint True
1✔
286

287
userCutsSection :: C e s m => m [MIP.Constraint Scientific]
288
userCutsSection = do
1✔
289
  tok $ string' "user"
1✔
290
  tok $ string' "cuts"
1✔
291
  many $ try $ constraint False
×
292

293
type Bounds2 c = (Maybe (MIP.BoundExpr c), Maybe (MIP.BoundExpr c))
294

295
boundsSection :: C e s m => m (Map MIP.Var (MIP.Bounds Scientific))
296
boundsSection = do
1✔
297
  tok $ string' "bound" >> optional (char' 's')
1✔
298
  liftM (Map.map g . Map.fromListWith f) $ many (try bound)
1✔
299
  where
300
    f (lb1,ub1) (lb2,ub2) = (combineMaybe max lb1 lb2, combineMaybe min ub1 ub2)
×
301
    g (lb, ub) = ( fromMaybe MIP.defaultLB lb
×
302
                 , fromMaybe MIP.defaultUB ub
1✔
303
                 )
304

305
bound :: C e s m => m (MIP.Var, Bounds2 Scientific)
306
bound = msum
1✔
307
  [ try $ do
1✔
308
      v <- try variable
1✔
309
      msum
1✔
310
        [ do
1✔
311
            op <- relOp
1✔
312
            b <- boundExpr
1✔
313
            return
1✔
314
              ( v
1✔
315
              , case op of
1✔
316
                  MIP.Le -> (Nothing, Just b)
1✔
317
                  MIP.Ge -> (Just b, Nothing)
1✔
318
                  MIP.Eql -> (Just b, Just b)
1✔
319
              )
320
        , do
1✔
321
            tok $ string' "free"
1✔
322
            return (v, (Just MIP.NegInf, Just MIP.PosInf))
1✔
323
        ]
324
  , do
1✔
325
      b1 <- liftM Just boundExpr
1✔
326
      op1 <- relOp
1✔
327
      guard $ op1 == MIP.Le
1✔
328
      v <- variable
1✔
329
      b2 <- option Nothing $ do
1✔
330
        op2 <- relOp
1✔
331
        guard $ op2 == MIP.Le
1✔
332
        liftM Just boundExpr
1✔
333
      return (v, (b1, b2))
1✔
334
  ]
335

336
boundExpr :: C e s m => m (MIP.BoundExpr Scientific)
337
boundExpr = msum
1✔
338
  [ try (tok (char '+') >> inf >> return MIP.PosInf)
1✔
339
  , try (tok (char '-') >> inf >> return MIP.NegInf)
1✔
340
  , do
1✔
341
      s <- option 1 sign
1✔
342
      x <- number
1✔
343
      return $ MIP.Finite (s*x)
1✔
344
  ]
345

346
inf :: C e s m => m ()
347
inf = tok (string "inf" >> optional (string "inity")) >> return ()
×
348

349
-- ---------------------------------------------------------------------------
350

351
generalSection :: C e s m => m [MIP.Var]
352
generalSection = do
1✔
353
  tok $ string' "gen" >> optional (string' "eral" >> optional (string' "s"))
1✔
354
  many (try variable)
1✔
355

356
binarySection :: C e s m => m [MIP.Var]
357
binarySection = do
1✔
358
  tok $ string' "bin" >> optional (string' "ar" >> (string' "y" <|> string' "ies"))
1✔
359
  many (try variable)
1✔
360

361
semiSection :: C e s m => m [MIP.Var]
362
semiSection = do
1✔
363
  tok $ string' "semi" >> optional (string' "-continuous" <|> string' "s")
×
364
  many (try variable)
1✔
365

366
sosSection :: C e s m => m [MIP.SOSConstraint Scientific]
367
sosSection = do
1✔
368
  tok $ string' "sos"
1✔
369
  many $ try $ do
1✔
370
    (l,t) <- try (do{ l <- label; t <- typ; return (Just l, t) })
1✔
371
          <|> (do{ t <- typ; return (Nothing, t) })
×
372
    xs <- many $ try $ do
1✔
373
      v <- variable
1✔
374
      tok $ char ':'
1✔
375
      w <- number
1✔
376
      return (v,w)
1✔
377
    return $ MIP.SOSConstraint l t xs
1✔
378
  where
379
    typ = do
1✔
380
      t <- tok $ (char' 's' >> ((char '1' >> return MIP.S1) <|> (char '2' >> return MIP.S2)))
1✔
381
      tok (string "::")
1✔
382
      return t
1✔
383

384
-- ---------------------------------------------------------------------------
385

386
expr :: forall e s m. C e s m => m (MIP.Expr Scientific)
387
expr = try expr1 <|> return 0
1✔
388
  where
389
    expr1 :: m (MIP.Expr Scientific)
390
    expr1 = do
1✔
391
      t <- term True
1✔
392
      ts <- many (term False)
1✔
393
      return $ foldr (+) 0 (t : ts)
1✔
394

395
sign :: (C e s m, Num a) => m a
396
sign = tok ((char '+' >> return 1) <|> (char '-' >> return (-1)))
1✔
397

398
term :: C e s m => Bool -> m (MIP.Expr Scientific)
399
term flag = do
1✔
400
  s <- if flag then optional sign else liftM Just sign
1✔
401
  c <- optional number
1✔
402
  e <- liftM MIP.varExpr variable <|> qexpr
1✔
403
  return $ case combineMaybe (*) s c of
1✔
404
    Nothing -> e
1✔
405
    Just d -> MIP.constExpr d * e
1✔
406

407
qexpr :: C e s m => m (MIP.Expr Scientific)
408
qexpr = do
1✔
409
  tok (char '[')
1✔
410
  t <- qterm True
1✔
411
  ts <- many (qterm False)
1✔
412
  let e = MIP.Expr (t:ts)
1✔
413
  tok (char ']')
1✔
414
  -- Gurobi allows ommiting "/2"
415
  (do mapM_ (tok . char) ("/2" :: String) -- Explicit type signature is necessary because the type of mapM_ in GHC-7.10 is generalized for arbitrary Foldable
1✔
416
      return $ MIP.constExpr (1/2) * e)
1✔
417
   <|> return e
1✔
418

419
qterm :: C e s m => Bool -> m (MIP.Term Scientific)
420
qterm flag = do
1✔
421
  s <- if flag then optional sign else liftM Just sign
1✔
422
  c <- optional number
1✔
423
  es <- do
1✔
424
    e <- qfactor
1✔
425
    es <- many (tok (char '*') >> qfactor)
1✔
426
    return $ e ++ concat es
1✔
427
  return $ case combineMaybe (*) s c of
1✔
428
    Nothing -> MIP.Term 1 es
1✔
429
    Just d -> MIP.Term d es
1✔
430

431
qfactor :: C e s m => m [MIP.Var]
432
qfactor = do
1✔
433
  v <- variable
1✔
434
  msum [ tok (char '^') >> tok (char '2') >> return [v,v]
1✔
435
       , return [v]
1✔
436
       ]
437

438
number :: forall e s m. C e s m => m Scientific
439
number = tok $ P.signed sep P.scientific
×
440

441
skipManyTill :: Alternative m => m a -> m end -> m ()
442
skipManyTill p end' = scan
1✔
443
  where
444
    scan = (end' *> pure ()) <|> (p *> scan)
×
445

446
-- ---------------------------------------------------------------------------
447

448
type M a = Writer Builder a
449

450
execM :: M a -> TL.Text
451
execM m = B.toLazyText $ execWriter m
1✔
452

453
writeString :: T.Text -> M ()
454
writeString s = tell $ B.fromText s
1✔
455

456
writeChar :: Char -> M ()
457
writeChar c = tell $ B.singleton c
1✔
458

459
-- ---------------------------------------------------------------------------
460

461
-- | Render a problem into a 'TL.Text' containing LP file data.
462
render :: MIP.FileOptions -> MIP.Problem Scientific -> Either String TL.Text
463
render _ mip = Right $ execM $ render' $ normalize mip
1✔
464

465
writeVar :: MIP.Var -> M ()
466
writeVar (MIP.Var v) = writeString v
1✔
467

468
render' :: MIP.Problem Scientific -> M ()
469
render' mip = do
1✔
470
  case MIP.name mip of
1✔
471
    Just name -> writeString $ "\\* Problem: " <> name <> " *\\\n"
1✔
472
    Nothing -> return ()
×
473

474
  let obj = MIP.objectiveFunction mip
1✔
475

476
  writeString $
1✔
477
    case MIP.objDir obj of
1✔
478
      OptMin -> "MINIMIZE"
1✔
479
      OptMax -> "MAXIMIZE"
1✔
480
  writeChar '\n'
1✔
481

482
  renderLabel (MIP.objLabel obj)
1✔
483
  renderExpr True (MIP.objExpr obj)
1✔
484
  writeChar '\n'
1✔
485

486
  writeString "SUBJECT TO\n"
1✔
487
  forM_ (MIP.constraints mip) $ \c -> do
1✔
488
    unless (MIP.constrIsLazy c) $ do
1✔
489
      renderConstraint c
1✔
490
      writeChar '\n'
1✔
491

492
  let lcs = [c | c <- MIP.constraints mip, MIP.constrIsLazy c]
1✔
493
  unless (null lcs) $ do
1✔
494
    writeString "LAZY CONSTRAINTS\n"
1✔
495
    forM_ lcs $ \c -> do
1✔
496
      renderConstraint c
1✔
497
      writeChar '\n'
1✔
498

499
  let cuts = [c | c <- MIP.userCuts mip]
1✔
500
  unless (null cuts) $ do
1✔
501
    writeString "USER CUTS\n"
1✔
502
    forM_ cuts $ \c -> do
1✔
503
      renderConstraint c
1✔
504
      writeChar '\n'
1✔
505

506
  let ivs = MIP.integerVariables mip `Set.union` MIP.semiIntegerVariables mip
1✔
507
      (bins,gens) = Set.partition (\v -> MIP.getBounds mip v == (MIP.Finite 0, MIP.Finite 1)) ivs
1✔
508
      scs = MIP.semiContinuousVariables mip `Set.union` MIP.semiIntegerVariables mip
1✔
509

510
  writeString "BOUNDS\n"
1✔
511
  forM_ (Map.toAscList (MIP.varBounds mip)) $ \(v, (lb,ub)) -> do
1✔
512
    unless (v `Set.member` bins) $ do
1✔
513
      renderBoundExpr lb
1✔
514
      writeString " <= "
1✔
515
      writeVar v
1✔
516
      writeString " <= "
1✔
517
      renderBoundExpr ub
1✔
518
      writeChar '\n'
1✔
519

520
  unless (Set.null gens) $ do
1✔
521
    writeString "GENERALS\n"
1✔
522
    renderVariableList $ Set.toList gens
1✔
523

524
  unless (Set.null bins) $ do
1✔
525
    writeString "BINARIES\n"
1✔
526
    renderVariableList $ Set.toList bins
1✔
527

528
  unless (Set.null scs) $ do
1✔
529
    writeString "SEMI-CONTINUOUS\n"
1✔
530
    renderVariableList $ Set.toList scs
1✔
531

532
  unless (null (MIP.sosConstraints mip)) $ do
1✔
533
    writeString "SOS\n"
1✔
534
    forM_ (MIP.sosConstraints mip) $ \(MIP.SOSConstraint l typ xs) -> do
1✔
535
      renderLabel l
1✔
536
      writeString $ fromString $ show typ
1✔
537
      writeString " ::"
1✔
538
      forM_ xs $ \(v, r) -> do
1✔
539
        writeString "  "
1✔
540
        writeVar v
1✔
541
        writeString " : "
1✔
542
        tell $ B.scientificBuilder r
1✔
543
      writeChar '\n'
1✔
544

545
  writeString "END\n"
1✔
546

547
-- FIXME: Gurobi は quadratic term が最後に一つある形式でないとダメっぽい
548
renderExpr :: Bool -> MIP.Expr Scientific -> M ()
549
renderExpr isObj e = fill 80 (ts1 ++ ts2)
1✔
550
  where
551
    (ts,qts) = partition isLin (MIP.terms e)
1✔
552
    isLin (MIP.Term _ [])  = True
×
553
    isLin (MIP.Term _ [_]) = True
1✔
554
    isLin _ = False
1✔
555

556
    ts1 = map f ts
1✔
557
    ts2
1✔
558
      | null qts  = []
1✔
559
      | otherwise =
×
560
        -- マイナスで始めるとSCIP 2.1.1 は「cannot have '-' in front of quadratic part ('[')」というエラーを出す
561
        -- SCIP-3.1.0 does not allow spaces between '/' and '2'.
562
        ["+ ["] ++ map g qts ++ [if isObj then "] /2" else "]"]
1✔
563

564
    f :: MIP.Term Scientific -> T.Text
565
    f (MIP.Term c [])  = showConstTerm c
×
566
    f (MIP.Term c [v]) = showCoeff c <> MIP.varName v
1✔
567
    f _ = error "should not happen"
×
568

569
    g :: MIP.Term Scientific -> T.Text
570
    g (MIP.Term c vs) =
1✔
571
      (if isObj then showCoeff (2*c) else showCoeff c) <>
1✔
572
      mconcat (intersperse " * " (map MIP.varName vs))
1✔
573

574
showValue :: Scientific -> T.Text
575
showValue = fromString . show
1✔
576

577
showCoeff :: Scientific -> T.Text
578
showCoeff c =
1✔
579
  if c' == 1
1✔
580
    then s
1✔
581
    else s <> showValue c' <> " "
1✔
582
  where
583
    c' = abs c
1✔
584
    s = if c >= 0 then "+ " else "- "
1✔
585

586
showConstTerm :: Scientific -> T.Text
587
showConstTerm c = s <> showValue (abs c)
×
588
  where
589
    s = if c >= 0 then "+ " else "- "
×
590

591
renderLabel :: Maybe MIP.Label -> M ()
592
renderLabel l =
1✔
593
  case l of
1✔
594
    Nothing -> return ()
×
595
    Just s -> writeString s >> writeString ": "
1✔
596

597
renderOp :: MIP.RelOp -> M ()
598
renderOp MIP.Le = writeString "<="
1✔
599
renderOp MIP.Ge = writeString ">="
1✔
600
renderOp MIP.Eql = writeString "="
1✔
601

602
renderConstraint :: MIP.Constraint Scientific -> M ()
603
renderConstraint c@MIP.Constraint{ MIP.constrExpr = e, MIP.constrLB = lb, MIP.constrUB = ub } = do
1✔
604
  renderLabel (MIP.constrLabel c)
1✔
605
  case MIP.constrIndicator c of
1✔
606
    Nothing -> return ()
×
607
    Just (v,vval) -> do
1✔
608
      writeVar v
1✔
609
      writeString " = "
1✔
610
      tell $
1✔
611
        case floatingOrInteger vval of
1✔
612
          Right (i :: Integer) -> B.decimal i
1✔
613
          Left (_ :: Double) -> B.scientificBuilder vval  -- should be error?
×
614
      writeString " -> "
1✔
615

616
  renderExpr False e
1✔
617
  writeChar ' '
1✔
618
  let (op, val) =
619
        case (lb, ub) of
1✔
620
          (MIP.NegInf, MIP.Finite x) -> (MIP.Le, x)
1✔
621
          (MIP.Finite x, MIP.PosInf) -> (MIP.Ge, x)
1✔
622
          (MIP.Finite x1, MIP.Finite x2) | x1==x2 -> (MIP.Eql, x1)
×
623
          _ -> error "Numeric.Optimization.MIP.LPFile.renderConstraint: should not happen"
×
624
  renderOp op
1✔
625
  writeChar ' '
1✔
626
  tell $ B.scientificBuilder val
1✔
627

628
renderBoundExpr :: MIP.BoundExpr Scientific -> M ()
629
renderBoundExpr (MIP.Finite r) = tell $ B.scientificBuilder r
1✔
630
renderBoundExpr MIP.NegInf = writeString "-inf"
1✔
631
renderBoundExpr MIP.PosInf = writeString "+inf"
1✔
632

633
renderVariableList :: [MIP.Var] -> M ()
634
renderVariableList vs = fill 80 (map MIP.varName vs) >> writeChar '\n'
1✔
635

636
fill :: Int -> [T.Text] -> M ()
637
fill width str = go str 0
1✔
638
  where
639
    go [] _ = return ()
×
640
    go (x:xs) 0 = writeString x >> go xs (T.length x)
1✔
641
    go (x:xs) w =
642
      if w + 1 + T.length x <= width
×
643
        then writeChar ' ' >> writeString x >> go xs (w + 1 + T.length x)
1✔
644
        else writeChar '\n' >> go (x:xs) 0
×
645

646
-- ---------------------------------------------------------------------------
647

648
{-
649
compileExpr :: Expr -> Maybe (Map Var Scientific)
650
compileExpr e = do
651
  xs <- forM e $ \(Term c vs) ->
652
    case vs of
653
      [v] -> return (v, c)
654
      _ -> mzero
655
  return (Map.fromList xs)
656
-}
657

658
-- ---------------------------------------------------------------------------
659

660
normalize :: (Eq r, Num r) => MIP.Problem r -> MIP.Problem r
661
normalize = removeEmptyExpr . removeRangeConstraints
1✔
662

663
removeRangeConstraints :: (Eq r, Num r) => MIP.Problem r -> MIP.Problem r
664
removeRangeConstraints prob = runST $ do
1✔
665
  vsRef <- newSTRef $ MIP.variables prob
×
666
  cntRef <- newSTRef (0::Int)
×
667
  newvsRef <- newSTRef []
1✔
668

669
  let gensym = do
×
670
        vs <- readSTRef vsRef
×
671
        let loop !c = do
×
672
              let v = fromString ("~r_" ++ show c)
×
673
              if v `Set.member` vs then
×
674
                loop (c+1)
×
675
              else do
×
676
                writeSTRef cntRef $! c+1
×
677
                modifySTRef vsRef (Set.insert v)
×
678
                return v
×
679
        loop =<< readSTRef cntRef
×
680

681
  cs2 <- forM (MIP.constraints prob) $ \c -> do
1✔
682
    case (MIP.constrLB c, MIP.constrUB c) of
1✔
683
      (MIP.NegInf, MIP.Finite _) -> return c
1✔
684
      (MIP.Finite _, MIP.PosInf) -> return c
1✔
685
      (MIP.Finite x1, MIP.Finite x2) | x1 == x2 -> return c
×
686
      (lb, ub) -> do
×
687
        v <- gensym
×
688
        modifySTRef newvsRef ((v, (lb,ub)) :)
×
689
        return $
×
690
          c
×
691
          { MIP.constrExpr = MIP.constrExpr c - MIP.varExpr v
×
692
          , MIP.constrLB = MIP.Finite 0
×
693
          , MIP.constrUB = MIP.Finite 0
×
694
          }
695

696
  newvs <- liftM reverse $ readSTRef newvsRef
1✔
697
  return $
1✔
698
    prob
1✔
699
    { MIP.constraints = cs2
1✔
700
    , MIP.varDomains = MIP.varDomains prob `Map.union` Map.fromList [(v, (MIP.ContinuousVariable, bs)) | (v,bs) <- newvs]
×
701
    }
702

703
removeEmptyExpr :: Num r => MIP.Problem r -> MIP.Problem r
704
removeEmptyExpr prob =
1✔
705
  prob
1✔
706
  { MIP.objectiveFunction = obj{ MIP.objExpr = convertExpr (MIP.objExpr obj) }
1✔
707
  , MIP.constraints = map convertConstr $ MIP.constraints prob
1✔
708
  , MIP.userCuts    = map convertConstr $ MIP.userCuts prob
1✔
709
  }
710
  where
711
    obj = MIP.objectiveFunction prob
1✔
712

713
    convertExpr (MIP.Expr []) = MIP.Expr [MIP.Term 0 [fromString "x0"]]
1✔
714
    convertExpr e = e
1✔
715

716
    convertConstr constr =
1✔
717
      constr
1✔
718
      { MIP.constrExpr = convertExpr $ MIP.constrExpr constr
1✔
719
      }
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