glpk-hs-0.1.0: Comprehensive GLPK linear programming bindings

Data.LinearProgram.Common

Synopsis

Documentation

data Constraint v c Source

Constructors

Constr (Maybe String) (LinFunc v c) (Bounds c) 

Instances

Functor (Constraint v) 
(Read v, Ord v, Read c, Ord c, Num c) => Read (Constraint v c) 
(Show v, Num c, Ord c) => Show (Constraint v c) 

type VarBounds v c = Map v (Bounds c)Source

data LP v c Source

Constructors

LP 

Instances

Functor (LP v) 
(Num c, Ord v, Ord c, Read v, Read c) => Read (LP v c) 
(Num c, Ord c, Show v) => Show (LP v c) 

mapVars :: (Ord v', Ord c, Module r c) => (v -> v') -> LP v c -> LP v' cSource

Applies the specified function to the variables in the linear program. If multiple variables in the original program are mapped to the same variable in the new program, in general, we set those variables to all be equal, as follows. * In linear functions, including the objective function and the constraints, coefficients will be added together. For instance, if v1,v2 are mapped to the same variable v', then a linear function of the form c1 *& v1 ^+^ c2 *& v2 will be mapped to (c1 ^+^ c2) *& v'. * In variable bounds, bounds will be combined. An error will be thrown if the bounds are mutually contradictory. * In variable kinds, the most restrictive kind will be retained.

mapVals :: (Ord c', Module r c') => (c -> c') -> LP v c -> LP v c'Source

Applies the specified function to the constants in the linear program. This is only safe for a monotonic function.

type LinFunc = MapSource

LinFunc v c is a linear combination of variables of type v 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.

Methods

(*^) :: r -> m -> mSource

zero :: mSource

(^+^) :: m -> m -> mSource

(^-^) :: m -> m -> mSource

neg :: m -> mSource

Instances

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.

varSum :: (Ord v, Num c) => [v] -> LinFunc v cSource

Equivalent to vsum . map var.

(*&) :: (Ord v, Num c) => c -> v -> LinFunc v cSource

c *& v is equivalent to c *^ var v.

vsum :: Module r v => [v] -> vSource

Returns a vector sum.

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.

data Bounds a Source

Constructors

Free 
LBound a 
UBound a 
Equ a 
Bound a a 

Instances

Functor Bounds 
Eq a => Eq (Bounds a) 
Read a => Read (Bounds a) 
Show a => Show (Bounds a) 
Ord a => Monoid (Bounds a)