| Copyright | (c) Masahiro Sakai 2011-2014 |
|---|---|
| License | BSD-style |
| Maintainer | masahiro.sakai@gmail.com |
| Stability | provisional |
| Portability | portable |
| Safe Haskell | None |
| Language | Haskell2010 |
ToySolver.Data.MIP.Base
Contents
Description
Mixed-Integer Programming Problems with some commmonly used extensions
- data Problem = Problem {
- name :: Maybe String
- objectiveFunction :: ObjectiveFunction
- constraints :: [Constraint]
- sosConstraints :: [SOSConstraint]
- userCuts :: [Constraint]
- varType :: Map Var VarType
- varBounds :: Map Var Bounds
- newtype Expr = Expr [Term]
- varExpr :: Var -> Expr
- constExpr :: Rational -> Expr
- terms :: Expr -> [Term]
- data Term = Term Rational [Var]
- data OptDir :: *
- data ObjectiveFunction = ObjectiveFunction {}
- data Constraint = Constraint {
- constrLabel :: Maybe Label
- constrIndicator :: Maybe (Var, Rational)
- constrExpr :: Expr
- constrLB :: BoundExpr
- constrUB :: BoundExpr
- constrIsLazy :: Bool
- (.==.) :: Expr -> Expr -> Constraint
- (.<=.) :: Expr -> Expr -> Constraint
- (.>=.) :: Expr -> Expr -> Constraint
- type Bounds = (BoundExpr, BoundExpr)
- type Label = String
- type Var = InternedString
- data VarType
- 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
- 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
Constructors
| Problem | |
Fields
| |
expressions
terms
The OptDir type represents optimization directions.
data ObjectiveFunction Source #
objective function
data Constraint Source #
constraint
Constructors
| Constraint | |
Fields
| |
Instances
type Var = InternedString Source #
variable
Extended r is an extension of r with positive/negative infinity (±∞).
Instances
| 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) | |
relational operators
types of SOS (special ordered sets) constraints
data SOSConstraint Source #
SOS (special ordered sets) constraints
Constructors
| SOSConstraint | |
Instances
defaultBounds :: Bounds Source #
default bounds