module ToySolver.Data.MIP
( Problem (..)
, Expr
, Term (..)
, OptDir (..)
, ObjectiveFunction
, Constraint (..)
, Bounds
, Label
, Var
, VarType (..)
, VarInfo (..)
, BoundExpr (..)
, RelOp (..)
, SOSType (..)
, SOSConstraint (..)
, defaultBounds
, defaultLB
, defaultUB
, toVar
, fromVar
, getVarInfo
, getVarType
, getBounds
, variables
, integerVariables
, semiContinuousVariables
, semiIntegerVariables
, Variables (..)
, intersectBounds
) where
import Data.Map (Map)
import qualified Data.Map as Map
import Data.Set (Set)
import qualified Data.Set as Set
import Data.Interned (intern, unintern)
import Data.Interned.String
import Data.OptDir
data Problem
= Problem
{ dir :: OptDir
, objectiveFunction :: ObjectiveFunction
, constraints :: [Constraint]
, sosConstraints :: [SOSConstraint]
, userCuts :: [Constraint]
, varInfo :: Map Var VarInfo
}
deriving (Show, Eq, Ord)
type Expr = [Term]
data Term = Term Rational [Var]
deriving (Eq, Ord, Show)
type ObjectiveFunction = (Maybe Label, Expr)
data Constraint
= Constraint
{ constrLabel :: Maybe Label
, constrIndicator :: Maybe (Var, Rational)
, constrBody :: (Expr, RelOp, Rational)
, constrIsLazy :: Bool
}
deriving (Eq, Ord, Show)
data VarType
= ContinuousVariable
| IntegerVariable
| SemiContinuousVariable
| SemiIntegerVariable
deriving (Eq, Ord, Show)
data VarInfo
= VarInfo
{ varType :: VarType
, varBounds :: Bounds
}
deriving (Eq, Ord, Show)
defaultVarInfo :: VarInfo
defaultVarInfo
= VarInfo
{ varType = ContinuousVariable
, varBounds = defaultBounds
}
type Bounds = (BoundExpr, BoundExpr)
type Label = String
type Var = InternedString
data BoundExpr = NegInf | Finite Rational | PosInf
deriving (Eq, Ord, Show)
data RelOp = Le | Ge | Eql
deriving (Eq, Ord, Enum, Show)
data SOSType
= S1
| S2
deriving (Eq, Ord, Enum, Show, Read)
data SOSConstraint
= SOSConstraint
{ sosLabel :: Maybe Label
, sosType :: SOSType
, sosBody :: [(Var, Rational)]
}
deriving (Eq, Ord, Show)
class Variables a where
vars :: a -> Set Var
instance Variables a => Variables [a] where
vars = Set.unions . map vars
instance (Variables a, Variables b) => Variables (Either a b) where
vars (Left a) = vars a
vars (Right b) = vars b
instance Variables Problem where
vars = variables
instance Variables Term where
vars (Term _ xs) = Set.fromList xs
instance Variables Constraint where
vars Constraint{ constrIndicator = ind, constrBody = (lhs, _, _) } =
vars lhs `Set.union` vs2
where
vs2 = maybe Set.empty (Set.singleton . fst) ind
instance Variables SOSConstraint where
vars SOSConstraint{ sosBody = xs } = Set.fromList (map fst xs)
defaultBounds :: Bounds
defaultBounds = (defaultLB, defaultUB)
defaultLB :: BoundExpr
defaultLB = Finite 0
defaultUB :: BoundExpr
defaultUB = PosInf
toVar :: String -> Var
toVar = intern
fromVar :: Var -> String
fromVar = unintern
getVarInfo :: Problem -> Var -> VarInfo
getVarInfo lp v = Map.findWithDefault defaultVarInfo v (varInfo lp)
getVarType :: Problem -> Var -> VarType
getVarType lp v = varType $ getVarInfo lp v
getBounds :: Problem -> Var -> Bounds
getBounds lp v = varBounds $ getVarInfo lp v
intersectBounds :: Bounds -> Bounds -> Bounds
intersectBounds (lb1,ub1) (lb2,ub2) = (max lb1 lb2, min ub1 ub2)
variables :: Problem -> Set Var
variables lp = Map.keysSet $ varInfo lp
integerVariables :: Problem -> Set Var
integerVariables lp = Map.keysSet $ Map.filter p (varInfo lp)
where
p VarInfo{ varType = vt } = vt == IntegerVariable
semiContinuousVariables :: Problem -> Set Var
semiContinuousVariables lp = Map.keysSet $ Map.filter p (varInfo lp)
where
p VarInfo{ varType = vt } = vt == SemiContinuousVariable
semiIntegerVariables :: Problem -> Set Var
semiIntegerVariables lp = Map.keysSet $ Map.filter p (varInfo lp)
where
p VarInfo{ varType = vt } = vt == SemiIntegerVariable