glpk-hs-0.5: Comprehensive GLPK linear programming bindings

Safe HaskellNone
LanguageHaskell98

Data.LinearProgram.Common

Description

Contains sufficient tools to represent linear programming problems in Haskell. In the future, if linkings to other linear programming libraries are made, this will be common to them all.

Synopsis

Documentation

data Constraint v c Source #

Representation of a linear constraint on the variables, possibly labeled. The function may be bounded both above and below.

Constructors

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

Instances

Functor (Constraint v) Source # 

Methods

fmap :: (a -> b) -> Constraint v a -> Constraint v b #

(<$) :: a -> Constraint v b -> Constraint v a #

(Read v, Ord v, Read c, Ord c, Num c, Group c) => Read (Constraint v c) Source # 
(Show v, Ord c, Show c, Num c, Group c) => Show (Constraint v c) Source # 

Methods

showsPrec :: Int -> Constraint v c -> ShowS #

show :: Constraint v c -> String #

showList :: [Constraint v c] -> ShowS #

(NFData v, NFData c) => NFData (Constraint v c) Source # 

Methods

rnf :: Constraint v c -> () #

type VarTypes v = Map v VarKind Source #

A mapping from variables to their types. Variables not mentioned are assumed to be continuous,

type ObjectiveFunc = LinFunc Source #

An objective function for a linear program.

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

A mapping from variables to their boundaries. Variables not mentioned are assumed to be free.

data LP v c Source #

The specification of a linear programming problem with variables in v and coefficients/constants in c. Note: the Read and Show implementations do not correspond to any particular linear program specification format.

Constructors

LP 

Instances

Functor (LP v) Source # 

Methods

fmap :: (a -> b) -> LP v a -> LP v b #

(<$) :: a -> LP v b -> LP v a #

(Num c, Ord v, Ord c, Read v, Read c, Group c) => Read (LP v c) Source # 

Methods

readsPrec :: Int -> ReadS (LP v c) #

readList :: ReadS [LP v c] #

readPrec :: ReadPrec (LP v c) #

readListPrec :: ReadPrec [LP v c] #

(Num c, Ord c, Show v, Show c, Group c) => Show (LP v c) Source # 

Methods

showsPrec :: Int -> LP v c -> ShowS #

show :: LP v c -> String #

showList :: [LP v c] -> ShowS #

(NFData v, NFData c) => NFData (LP v c) Source # 

Methods

rnf :: LP v c -> () #

mapVars :: (Ord v', Ord c, Group c) => (v -> v') -> LP v c -> LP v' c Source #

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 :: (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.

allVars :: Ord v => LP v c -> Map v () Source #

linCombination :: (Ord v, Additive r) => [(r, v)] -> LinFunc v r Source #

data VarKind Source #

Constructors

ContVar 
IntVar 
BinVar 

Instances

Enum VarKind Source # 
Eq VarKind Source # 

Methods

(==) :: VarKind -> VarKind -> Bool #

(/=) :: VarKind -> VarKind -> Bool #

Ord VarKind Source # 
Read VarKind Source # 
Show VarKind Source # 
Generic VarKind Source # 

Associated Types

type Rep VarKind :: * -> * #

Methods

from :: VarKind -> Rep VarKind x #

to :: Rep VarKind x -> VarKind #

Monoid VarKind Source # 
NFData VarKind Source # 

Methods

rnf :: VarKind -> () #

type Rep VarKind Source # 
type Rep VarKind = D1 (MetaData "VarKind" "Data.LinearProgram.Types" "glpk-hs-0.5-9j4ql4mYOsHKQbbrngCmSv" False) ((:+:) (C1 (MetaCons "ContVar" PrefixI False) U1) ((:+:) (C1 (MetaCons "IntVar" PrefixI False) U1) (C1 (MetaCons "BinVar" PrefixI False) U1)))

data Direction Source #

Constructors

Min 
Max 

Instances

Enum Direction Source # 
Eq Direction Source # 
Ord Direction Source # 
Read Direction Source # 
Show Direction Source # 
Generic Direction Source # 

Associated Types

type Rep Direction :: * -> * #

NFData Direction Source # 

Methods

rnf :: Direction -> () #

type Rep Direction Source # 
type Rep Direction = D1 (MetaData "Direction" "Data.LinearProgram.Types" "glpk-hs-0.5-9j4ql4mYOsHKQbbrngCmSv" False) ((:+:) (C1 (MetaCons "Min" PrefixI False) U1) (C1 (MetaCons "Max" PrefixI False) U1))

data Bounds a Source #

Constructors

Free 
LBound !a 
UBound !a 
Equ !a 
Bound !a !a 

Instances

Functor Bounds Source # 

Methods

fmap :: (a -> b) -> Bounds a -> Bounds b #

(<$) :: a -> Bounds b -> Bounds a #

Eq a => Eq (Bounds a) Source # 

Methods

(==) :: Bounds a -> Bounds a -> Bool #

(/=) :: Bounds a -> Bounds a -> Bool #

Read a => Read (Bounds a) Source # 
Show a => Show (Bounds a) Source # 

Methods

showsPrec :: Int -> Bounds a -> ShowS #

show :: Bounds a -> String #

showList :: [Bounds a] -> ShowS #

Ord a => Monoid (Bounds a) Source # 

Methods

mempty :: Bounds a #

mappend :: Bounds a -> Bounds a -> Bounds a #

mconcat :: [Bounds a] -> Bounds a #

NFData c => NFData (Bounds c) Source # 

Methods

rnf :: Bounds c -> () #