Skip to content

Commit 9bb3dca

Browse files
committed
upgrade MIP to 0.2.*
1 parent 82362f5 commit 9bb3dca

15 files changed

+62
-94
lines changed

Diff for: app/toysat/toysat.hs

+3-2
Original file line numberDiff line numberDiff line change
@@ -43,6 +43,7 @@ import qualified Data.Vector.Unboxed as V
4343
import Data.Version
4444
import Data.Ratio
4545
import Data.Scientific as Scientific
46+
import Data.String
4647
import Data.Time
4748
import Options.Applicative hiding (info)
4849
import qualified Options.Applicative
@@ -1068,7 +1069,7 @@ solveMIP opt solver mip = do
10681069
printModel :: Map MIP.Var Rational -> IO ()
10691070
printModel m = do
10701071
forM_ (Map.toList m) $ \(v, val) -> do
1071-
printf "v %s = %d\n" (MIP.fromVar v) (asInteger val)
1072+
printf "v %s = %d\n" (MIP.varName v) (asInteger val)
10721073
hFlush stdout
10731074

10741075
writeSol :: Map MIP.Var Rational -> Rational -> IO ()
@@ -1121,7 +1122,7 @@ writeSOLFile opt m obj nbvar = do
11211122
let sol = MIP.Solution
11221123
{ MIP.solStatus = MIP.StatusUnknown
11231124
, MIP.solObjectiveValue = fmap fromIntegral obj
1124-
, MIP.solVariables = Map.fromList [(MIP.toVar ("x" ++ show x), if b then 1.0 else 0.0) | (x,b) <- assocs m, x <= nbvar]
1125+
, MIP.solVariables = Map.fromList [(fromString ("x" ++ show x), if b then 1.0 else 0.0) | (x,b) <- assocs m, x <= nbvar]
11251126
}
11261127
GurobiSol.writeFile fname sol
11271128

Diff for: samples/programs/svm2lp/svm2lp.hs

+10-11
Original file line numberDiff line numberDiff line change
@@ -10,6 +10,7 @@ import Data.IntMap (IntMap)
1010
import qualified Data.IntMap as IntMap
1111
import qualified Data.Map as Map
1212
import Data.Scientific
13+
import Data.String
1314
import qualified Data.Text.Lazy.IO as TLIO
1415
import System.Console.GetOpt
1516
import System.Environment
@@ -49,20 +50,19 @@ primal c prob
4950
.>=. 1 - (if isJust c then MIP.varExpr xi_i else 0)
5051
| ((y_i, xs_i), xi_i) <- zip prob xi
5152
]
52-
, MIP.varType = Map.fromList [(x, MIP.ContinuousVariable) | x <- b : [w_j | w_j <- IntMap.elems w] ++ [xi_i | isJust c, xi_i <- xi]]
53-
, MIP.varBounds =
53+
, MIP.varDomains =
5454
Map.unions
55-
[ Map.singleton b (MIP.NegInf, MIP.PosInf)
56-
, Map.fromList [(w_j, (MIP.NegInf, MIP.PosInf)) | w_j <- IntMap.elems w]
57-
, Map.fromList [(xi_i, (0, MIP.PosInf)) | isJust c, xi_i <- xi]
55+
[ Map.singleton b (MIP.ContinuousVariable, (MIP.NegInf, MIP.PosInf))
56+
, Map.fromList [(w_j, (MIP.ContinuousVariable, (MIP.NegInf, MIP.PosInf))) | w_j <- IntMap.elems w]
57+
, Map.fromList [(xi_i, (MIP.ContinuousVariable, (0, MIP.PosInf))) | isJust c, xi_i <- xi]
5858
]
5959
}
6060
where
6161
m = length prob
6262
n = fst $ IntMap.findMax $ IntMap.unions (map snd prob)
63-
w = IntMap.fromList [(j, MIP.toVar ("w_" ++ show j)) | j <- [1..n]]
64-
b = MIP.toVar "b"
65-
xi = [MIP.toVar ("xi_" ++ show i) | i <- [1..m]]
63+
w = IntMap.fromList [(j, fromString ("w_" ++ show j)) | j <- [1..n]]
64+
b = fromString "b"
65+
xi = [fromString ("xi_" ++ show i) | i <- [1..m]]
6666

6767
dual
6868
:: Maybe Double
@@ -82,12 +82,11 @@ dual c kernel prob
8282
}
8383
, MIP.constraints =
8484
[ MIP.Expr [ MIP.Term (fromIntegral y_i) [a_i] | ((y_i, _xs_i), a_i) <- zip prob a ] .==. 0 ]
85-
, MIP.varType = Map.fromList [(a_i, MIP.ContinuousVariable) | a_i <- a]
86-
, MIP.varBounds = Map.fromList [(a_i, (0, if isJust c then MIP.Finite (realToFrac (fromJust c)) else MIP.PosInf)) | a_i <- a]
85+
, MIP.varDomains = Map.fromList [(a_i, (MIP.ContinuousVariable, (0, if isJust c then MIP.Finite (realToFrac (fromJust c)) else MIP.PosInf))) | a_i <- a]
8786
}
8887
where
8988
m = length prob
90-
a = [MIP.toVar ("a_" ++ show i) | i <- [1..m]]
89+
a = [fromString ("a_" ++ show i) | i <- [1..m]]
9190

9291
dot :: Num a => IntMap a -> IntMap a -> a
9392
dot a b = sum $ IntMap.elems $ IntMap.intersectionWith (*) a b

Diff for: src/ToySolver/Converter/MIP.hs

+31-15
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,6 @@
11
{-# OPTIONS_GHC -Wall #-}
22
{-# OPTIONS_HADDOCK show-extensions #-}
3+
{-# LANGUAGE CPP #-}
34
{-# LANGUAGE MultiParamTypeClasses #-}
45
{-# LANGUAGE OverloadedStrings #-}
56
{-# LANGUAGE ScopedTypeVariables #-}
@@ -42,6 +43,9 @@ import Control.Monad.Trans
4243
import Control.Monad.Trans.Except
4344
import qualified Data.Aeson as J
4445
import qualified Data.Aeson.Types as J
46+
#if MIN_VERSION_aeson(2,0,0)
47+
import qualified Data.Aeson.Key as Key
48+
#endif
4549
import Data.Aeson ((.=), (.:))
4650
import Data.Array.IArray
4751
import Data.Default.Class
@@ -55,6 +59,7 @@ import Data.Primitive.MutVar
5559
import Data.Ratio
5660
import qualified Data.Set as Set
5761
import Data.String
62+
import qualified Data.Text as T
5863
import Data.VectorSpace
5964

6065
import qualified Data.PseudoBoolean as PBFile
@@ -115,8 +120,7 @@ pb2ip formula = (mip, PB2IPInfo (PBFile.pbNumVars formula))
115120
mip = def
116121
{ MIP.objectiveFunction = obj2
117122
, MIP.constraints = cs2
118-
, MIP.varType = Map.fromList [(v, MIP.IntegerVariable) | v <- vs]
119-
, MIP.varBounds = Map.fromList [(v, (0,1)) | v <- vs]
123+
, MIP.varDomains = Map.fromList [(v, (MIP.IntegerVariable, (0,1))) | v <- vs]
120124
}
121125

122126
vs = [convVar v | v <- [1..PBFile.pbNumVars formula]]
@@ -144,7 +148,7 @@ convExpr s = sum [product (fromIntegral w : map f tm) | (w,tm) <- s]
144148
| otherwise = 1 - MIP.varExpr (convVar (abs x))
145149

146150
convVar :: PBFile.Var -> MIP.Var
147-
convVar x = MIP.toVar ("x" ++ show x)
151+
convVar x = fromString ("x" ++ show x)
148152

149153
-- -----------------------------------------------------------------------------
150154

@@ -180,10 +184,16 @@ instance J.ToJSON WBO2IPInfo where
180184
[ "type" .= ("WBO2IPInfo" :: J.Value)
181185
, "num_original_variables" .= nv
182186
, "relax_variables" .= J.object
183-
[ fromString (MIP.fromVar v) .= jPBConstraint constr
187+
[ toKey (MIP.varName v) .= jPBConstraint constr
184188
| (v, constr) <- relaxVariables
185189
]
186190
]
191+
where
192+
#if MIN_VERSION_aeson(2,0,0)
193+
toKey = Key.fromText
194+
#else
195+
toKey = id
196+
#endif
187197

188198
instance J.FromJSON WBO2IPInfo where
189199
parseJSON =
@@ -193,19 +203,18 @@ instance J.FromJSON WBO2IPInfo where
193203
<$> obj .: "num_original_variables"
194204
<*> mapM f (Map.toList xs)
195205
where
196-
f :: (String, J.Value) -> J.Parser (MIP.Var, PBFile.Constraint)
206+
f :: (T.Text, J.Value) -> J.Parser (MIP.Var, PBFile.Constraint)
197207
f (name, val) = do
198208
constr <- parsePBConstraint val
199-
pure (MIP.toVar name, constr)
209+
pure (MIP.Var name, constr)
200210

201211
wbo2ip :: Bool -> PBFile.SoftFormula -> (MIP.Problem Integer, WBO2IPInfo)
202212
wbo2ip useIndicator formula = (mip, WBO2IPInfo (PBFile.wboNumVars formula) [(r, c) | (r, (Just _, c)) <- relaxVariables])
203213
where
204214
mip = def
205215
{ MIP.objectiveFunction = obj2
206216
, MIP.constraints = topConstr ++ map snd cs2
207-
, MIP.varType = Map.fromList [(v, MIP.IntegerVariable) | v <- vs]
208-
, MIP.varBounds = Map.fromList [(v, (0,1)) | v <- vs]
217+
, MIP.varDomains = Map.fromList [(v, (MIP.IntegerVariable, (0,1))) | v <- vs]
209218
}
210219

211220
vs = [convVar v | v <- [1..PBFile.wboNumVars formula]] ++ [v | (ts, _) <- cs2, (_, v) <- ts]
@@ -223,7 +232,7 @@ wbo2ip useIndicator formula = (mip, WBO2IPInfo (PBFile.wboNumVars formula) [(r,
223232
[ def{ MIP.constrExpr = MIP.objExpr obj2, MIP.constrUB = MIP.Finite (fromInteger t - 1) } ]
224233

225234
relaxVariables :: [(MIP.Var, PBFile.SoftConstraint)]
226-
relaxVariables = [(MIP.toVar ("r" ++ show n), c) | (n, c) <- zip [(0::Int)..] (PBFile.wboConstraints formula)]
235+
relaxVariables = [(fromString ("r" ++ show n), c) | (n, c) <- zip [(0::Int)..] (PBFile.wboConstraints formula)]
227236

228237
cs2 :: [([(Integer, MIP.Var)], MIP.Constraint Integer)]
229238
cs2 = do
@@ -373,26 +382,33 @@ instance J.ToJSON MIP2PBInfo where
373382
J.object
374383
[ "type" .= ("MIP2PBInfo" :: J.Value)
375384
, "substitutions" .= J.object
376-
[ fromString (MIP.fromVar v) .= jPBSum s
385+
[ toKey (MIP.varName v) .= jPBSum s
377386
| (v, Integer.Expr s) <- Map.toList vmap
378387
]
379388
, "nonzero_indicators" .= J.object
380-
[ fromString (MIP.fromVar v) .= (jLitName lit :: J.Value)
389+
[ toKey (MIP.varName v) .= (jLitName lit :: J.Value)
381390
| (v, lit) <- Map.toList nonZeroTable
382391
]
383392
, "objective_function_scale_factor" .= d
384393
]
394+
where
395+
#if MIN_VERSION_aeson(2,0,0)
396+
toKey = Key.fromText
397+
#else
398+
toKey = id
399+
#endif
400+
385401

386402
instance J.FromJSON MIP2PBInfo where
387403
parseJSON = withTypedObject "MIP2PBInfo" $ \obj -> do
388404
tmp1 <- obj .: "substitutions"
389405
subst <- liftM Map.fromList $ forM (Map.toList tmp1) $ \(name, expr) -> do
390406
s <- parsePBSum expr
391-
return (MIP.toVar name, Integer.Expr s)
407+
return (MIP.Var name, Integer.Expr s)
392408
tmp2 <- obj .: "nonzero_indicators"
393409
nonZeroTable <- liftM Map.fromList $ forM (Map.toList tmp2) $ \(name, s) -> do
394410
lit <- parseLitName s
395-
return (MIP.toVar name, lit)
411+
return (MIP.Var name, lit)
396412
d <- obj .: "objective_function_scale_factor"
397413
pure $ MIP2PBInfo subst nonZeroTable d
398414

@@ -402,15 +418,15 @@ addMIP enc mip = runExceptT $ addMIP' enc mip
402418
addMIP' :: forall m enc. (SAT.AddPBNL m enc, PrimMonad m) => enc -> MIP.Problem Rational -> ExceptT String m (Integer.Expr, MIP2PBInfo)
403419
addMIP' enc mip = do
404420
if not (Set.null nivs) then do
405-
throwE $ "cannot handle non-integer variables: " ++ intercalate ", " (map MIP.fromVar (Set.toList nivs))
421+
throwE $ "cannot handle non-integer variables: " ++ intercalate ", " (map (T.unpack . MIP.varName) (Set.toList nivs))
406422
else do
407423
vmap <- liftM Map.fromList $ revForM (Set.toList ivs) $ \v -> do
408424
case MIP.getBounds mip v of
409425
(MIP.Finite lb, MIP.Finite ub) -> do
410426
v2 <- lift $ Integer.newVar enc (ceiling lb) (floor ub)
411427
return (v,v2)
412428
_ -> do
413-
throwE $ "cannot handle unbounded variable: " ++ MIP.fromVar v
429+
throwE $ "cannot handle unbounded variable: " ++ T.unpack (MIP.varName v)
414430
forM_ (MIP.constraints mip) $ \c -> do
415431
let lhs = MIP.constrExpr c
416432
let f op rhs = do

Diff for: src/ToySolver/Converter/MIP2SMT.hs

+3-4
Original file line numberDiff line numberDiff line change
@@ -21,7 +21,6 @@ module ToySolver.Converter.MIP2SMT
2121

2222
import Data.Char
2323
import Data.Default.Class
24-
import Data.Interned
2524
import Data.Ord
2625
import Data.List
2726
import Data.Ratio
@@ -335,10 +334,10 @@ mip2smt opt mip =
335334
YICES _ -> "int"
336335
ts = [(v, realType) | v <- Set.toList real_vs] ++ [(v, intType) | v <- Set.toList int_vs]
337336
obj = MIP.objectiveFunction mip
338-
env = Map.fromList [(v, encode opt (unintern v)) | v <- Set.toList vs]
337+
env = Map.fromList [(v, encode opt (MIP.varName v)) | v <- Set.toList vs]
339338
-- Note that identifiers of LPFile does not contain '-'.
340339
-- So that there are no name crash.
341-
env2 = Map.fromList [(v, encode opt (unintern v <> "-2")) | v <- Set.toList vs]
340+
env2 = Map.fromList [(v, encode opt (MIP.varName v <> "-2")) | v <- Set.toList vs]
342341

343342
options =
344343
[ case optLanguage opt of
@@ -358,7 +357,7 @@ mip2smt opt mip =
358357
return $
359358
case optLanguage opt of
360359
SMTLIB2 -> "(declare-fun " <> B.fromText v2 <> " () " <> B.fromString t <> ")"
361-
YICES _ -> "(define " <> B.fromText v2 <> "::" <> B.fromString t <> ") ; " <> B.fromString (MIP.fromVar v)
360+
YICES _ -> "(define " <> B.fromText v2 <> "::" <> B.fromString t <> ") ; " <> B.fromText (MIP.varName v)
362361

363362
optimality = list ["forall", decl, body]
364363
where

Diff for: stack-ghc-8.10.yaml

+1-1
Original file line numberDiff line numberDiff line change
@@ -48,7 +48,7 @@ extra-deps:
4848
- pseudo-boolean-0.1.10.0@sha256:c6a8b6c23c84cce8cecb37683755bde54db80b1ca817ce72de772c98d31dae44,2552
4949
- sign-0.4.4
5050
- bytestring-encoding-0.1.1.0
51-
- MIP-0.1.1.0
51+
- MIP-0.2.0.0@sha256:badc69dc1a72453af332175f998a6ba91f03844dea1fd2d4841852e8dcee6ca3,6363
5252
# Patched version of tasty-th for reading UTF-8 files on non UTF-8 environment.
5353
- git: https://github.com/msakai/tasty-th/
5454
commit: ebbe5a79b3c7a537ceafc6291744c4d531bef63c

Diff for: stack-ghc-8.8.yaml

+1-1
Original file line numberDiff line numberDiff line change
@@ -48,7 +48,7 @@ extra-deps:
4848
- pseudo-boolean-0.1.10.0@sha256:c6a8b6c23c84cce8cecb37683755bde54db80b1ca817ce72de772c98d31dae44,2552
4949
- sign-0.4.4
5050
- bytestring-encoding-0.1.1.0
51-
- MIP-0.1.1.0
51+
- MIP-0.2.0.0@sha256:badc69dc1a72453af332175f998a6ba91f03844dea1fd2d4841852e8dcee6ca3,6363
5252
# Patched version of tasty-th for reading UTF-8 files on non UTF-8 environment.
5353
- git: https://github.com/msakai/tasty-th/
5454
commit: ebbe5a79b3c7a537ceafc6291744c4d531bef63c

Diff for: stack-ghc-9.0.yaml

+1-1
Original file line numberDiff line numberDiff line change
@@ -48,7 +48,7 @@ extra-deps:
4848
- pseudo-boolean-0.1.10.0@sha256:c6a8b6c23c84cce8cecb37683755bde54db80b1ca817ce72de772c98d31dae44,2552
4949
- sign-0.4.4
5050
- bytestring-encoding-0.1.1.0
51-
- MIP-0.1.1.0
51+
- MIP-0.2.0.0@sha256:badc69dc1a72453af332175f998a6ba91f03844dea1fd2d4841852e8dcee6ca3,6363
5252
# Patched version of tasty-th for reading UTF-8 files on non UTF-8 environment.
5353
- git: https://github.com/msakai/tasty-th/
5454
commit: ebbe5a79b3c7a537ceafc6291744c4d531bef63c

Diff for: stack-ghc-9.2.yaml

+1-1
Original file line numberDiff line numberDiff line change
@@ -48,7 +48,7 @@ extra-deps:
4848
- pseudo-boolean-0.1.10.0@sha256:c6a8b6c23c84cce8cecb37683755bde54db80b1ca817ce72de772c98d31dae44,2552
4949
- sign-0.4.4
5050
- bytestring-encoding-0.1.1.0
51-
- MIP-0.1.1.0
51+
- MIP-0.2.0.0@sha256:badc69dc1a72453af332175f998a6ba91f03844dea1fd2d4841852e8dcee6ca3,6363
5252
# Patched version of tasty-th for reading UTF-8 files on non UTF-8 environment.
5353
- git: https://github.com/msakai/tasty-th/
5454
commit: ebbe5a79b3c7a537ceafc6291744c4d531bef63c

Diff for: stack-ghc-9.4.yaml

+1-1
Original file line numberDiff line numberDiff line change
@@ -48,7 +48,7 @@ extra-deps:
4848
- pseudo-boolean-0.1.10.0@sha256:50b8b5b4403c282d00d9951216106b64738767b154b43fa1633db58972dac732,2552
4949
- sign-0.4.4
5050
- bytestring-encoding-0.1.2.0
51-
- MIP-0.1.1.0
51+
- MIP-0.2.0.0@sha256:badc69dc1a72453af332175f998a6ba91f03844dea1fd2d4841852e8dcee6ca3,6363
5252
# Patched version of tasty-th for reading UTF-8 files on non UTF-8 environment.
5353
- git: https://github.com/msakai/tasty-th/
5454
commit: ebbe5a79b3c7a537ceafc6291744c4d531bef63c

Diff for: stack-ghc-9.6.yaml

+1-1
Original file line numberDiff line numberDiff line change
@@ -48,7 +48,7 @@ extra-deps:
4848
- pseudo-boolean-0.1.11.0@sha256:3e03a1fd845c70397d4e47c0da79a126c747bf4c3b0e4553eb4026297376dfd7
4949
- sign-0.4.4
5050
- bytestring-encoding-0.1.2.0
51-
- MIP-0.1.2.0
51+
- MIP-0.2.0.0@sha256:badc69dc1a72453af332175f998a6ba91f03844dea1fd2d4841852e8dcee6ca3,6363
5252
# Patched version of tasty-th for reading UTF-8 files on non UTF-8 environment.
5353
- git: https://github.com/msakai/tasty-th/
5454
commit: ebbe5a79b3c7a537ceafc6291744c4d531bef63c

Diff for: stack-ghc-9.8.yaml

+1-1
Original file line numberDiff line numberDiff line change
@@ -48,7 +48,7 @@ extra-deps:
4848
- pseudo-boolean-0.1.11.0
4949
- sign-0.4.4@sha256:e97cc7f11e67a99b1eeeefb9d7552ec867bf29d3c8ce11338850c31fc09637fb
5050
- bytestring-encoding-0.1.2.0
51-
- MIP-0.1.2.0
51+
- MIP-0.2.0.0@sha256:badc69dc1a72453af332175f998a6ba91f03844dea1fd2d4841852e8dcee6ca3,6363
5252
# Patched version of tasty-th for reading UTF-8 files on non UTF-8 environment.
5353
- git: https://github.com/msakai/tasty-th/
5454
commit: ebbe5a79b3c7a537ceafc6291744c4d531bef63c

Diff for: stack-windows-i386.yaml

+1-1
Original file line numberDiff line numberDiff line change
@@ -54,7 +54,7 @@ extra-deps:
5454
- pseudo-boolean-0.1.10.0@sha256:c6a8b6c23c84cce8cecb37683755bde54db80b1ca817ce72de772c98d31dae44,2552
5555
- sign-0.4.4
5656
- bytestring-encoding-0.1.1.0
57-
- MIP-0.1.1.0
57+
- MIP-0.2.0.0@sha256:badc69dc1a72453af332175f998a6ba91f03844dea1fd2d4841852e8dcee6ca3,6363
5858
# Patched version of tasty-th for reading UTF-8 files on non UTF-8 environment.
5959
- git: https://github.com/msakai/tasty-th/
6060
commit: ebbe5a79b3c7a537ceafc6291744c4d531bef63c

Diff for: stack.yaml

+1-1
Original file line numberDiff line numberDiff line change
@@ -48,7 +48,7 @@ extra-deps:
4848
- pseudo-boolean-0.1.11.0@sha256:3e03a1fd845c70397d4e47c0da79a126c747bf4c3b0e4553eb4026297376dfd7
4949
- sign-0.4.4
5050
- bytestring-encoding-0.1.2.0
51-
- MIP-0.1.2.0
51+
- MIP-0.2.0.0@sha256:badc69dc1a72453af332175f998a6ba91f03844dea1fd2d4841852e8dcee6ca3,6363
5252
# Patched version of tasty-th for reading UTF-8 files on non UTF-8 environment.
5353
- git: https://github.com/msakai/tasty-th/
5454
commit: ebbe5a79b3c7a537ceafc6291744c4d531bef63c

0 commit comments

Comments
 (0)