Copyright | (c) Masahiro Sakai 2011-2014 |
---|---|
License | BSD-style |
Maintainer | masahiro.sakai@gmail.com |
Stability | provisional |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
Mixed-Integer Programming Problems with some commmonly used extensions
- data Problem = Problem {}
- type Expr = [Term]
- data Term = Term Rational [Var]
- data OptDir :: *
- type ObjectiveFunction = (Maybe Label, Expr)
- data Constraint = Constraint {
- constrLabel :: Maybe Label
- constrIndicator :: Maybe (Var, Rational)
- constrBody :: (Expr, RelOp, Rational)
- constrIsLazy :: Bool
- type Bounds = (BoundExpr, BoundExpr)
- type Label = String
- type Var = InternedString
- data VarType
- data VarInfo = VarInfo {}
- type BoundExpr = Extended Rational
- data Extended r :: * -> *
- data RelOp
- data SOSType
- data SOSConstraint = SOSConstraint {}
- defaultBounds :: Bounds
- defaultLB :: BoundExpr
- defaultUB :: BoundExpr
- toVar :: String -> Var
- fromVar :: Var -> String
- getVarInfo :: Problem -> Var -> VarInfo
- getVarType :: Problem -> Var -> VarType
- getBounds :: Problem -> Var -> Bounds
- variables :: Problem -> Set Var
- integerVariables :: Problem -> Set Var
- semiContinuousVariables :: Problem -> Set Var
- semiIntegerVariables :: Problem -> Set Var
- class Variables a where
- intersectBounds :: Bounds -> Bounds -> Bounds
Documentation
Problem
Problem | |
|
type ObjectiveFunction = (Maybe Label, Expr) Source
objective function
data Constraint Source
constraint
Constraint | |
|
type Var = InternedString Source
variable
data Extended r :: * -> *
Extended r
is an extension of r with positive/negative infinity (±∞).
Functor Extended | |
Bounded (Extended r) | |
Eq r => Eq (Extended r) | |
(Fractional r, Ord r) => Fractional (Extended r) | Note that |
Data r => Data (Extended r) | |
(Num r, Ord r) => Num (Extended r) | Note that
|
Ord r => Ord (Extended r) | |
Read r => Read (Extended r) | |
Show r => Show (Extended r) | |
NFData r => NFData (Extended r) | |
Hashable r => Hashable (Extended r) | |
Typeable (* -> *) Extended |
types of SOS (special ordered sets) constraints
data SOSConstraint Source
SOS (special ordered sets) constraints
defaultBounds :: Bounds Source
default bounds
getVarInfo :: Problem -> Var -> VarInfo Source
looking up attributes for a variable
getVarType :: Problem -> Var -> VarType Source
looking up bounds for a variable
integerVariables :: Problem -> Set Var Source
semiIntegerVariables :: Problem -> Set Var Source
Utilities
intersectBounds :: Bounds -> Bounds -> Bounds Source