- data Constraint v c = Constr (Maybe String) (LinFunc v c) (Bounds c)
- type VarTypes v = Map v VarKind
- type ObjectiveFunc = LinFunc
- type VarBounds v c = Map v (Bounds c)
- data LP v c = LP {
- direction :: Direction
- objective :: ObjectiveFunc v c
- constraints :: [Constraint v c]
- varBounds :: VarBounds v c
- varTypes :: VarTypes v
- type LinFunc = Map
- class Module r m | m -> r where
- var :: (Ord v, Num c) => v -> LinFunc v c
- varSum :: (Ord v, Num c) => [v] -> LinFunc v c
- (*&) :: (Ord v, Num c) => c -> v -> LinFunc v c
- vsum :: Module r v => [v] -> v
- combination :: Module r m => [(r, m)] -> m
- linCombination :: (Ord v, Num r) => [(r, v)] -> LinFunc v r
- data VarKind
- data Direction
- data Bounds a
Documentation
data Constraint v c Source
(Ord v, Read v, Read c) => Read (Constraint v c) | |
(Show v, Show c) => Show (Constraint v c) |
type ObjectiveFunc = LinFuncSource
LP | |
|
is a linear combination of variables of type LinFunc
v cv
with coefficients
from c
. Formally, this is the free c
-module on v
.
class Module r m | m -> r whereSource
In algebra, if r
is a ring, an r
-module is an additive group with a scalar multiplication
operation. When r
is a field, this is equivalent to a vector space.
Module Double Double | |
Module Int Int | |
Module Integer Integer | |
Module r m => Module r (IntMap m) | |
(IArray UArray m, Module r m) => Module r (UArray Int m) | |
Module r m => Module r (Array Int m) | |
(Ord k, Module r m) => Module r (Map k m) | |
Module r m => Module r (a -> m) | |
Integral a => Module (Ratio a) (Ratio a) |
var :: (Ord v, Num c) => v -> LinFunc v cSource
Given a variable v
, returns the function equivalent to v
.
combination :: Module r m => [(r, m)] -> mSource
Given a collection of vectors and scaling coefficients, returns this linear combination.
linCombination :: (Ord v, Num r) => [(r, v)] -> LinFunc v rSource
Given a set of basic variables and coefficients, returns the linear combination obtained by summing.