glpk-hs-0.3.2: Comprehensive GLPK linear programming bindings

Safe HaskellSafe-Infered

Data.Algebra

Contents

Description

Common library for algebraic structures. Has the advantage of automatically inferring lots of useful structure, especially in the writing of linear programs. For example, here are several ways of writing 3 x - 4 y + z:

 gsum [3 *& x, (-4) *^ var y, var z]
 linCombination [(3, x), (-4, y), (1, z)]
 3 *& x ^-^ 4 *& y ^+^ var z

In addition, if we have two functions f and g, we can construct linear combinations of those functions, using exactly the same syntax. Moreover, we can multiply functions with Double coefficients by Rational values successfully. This module is intended to offer as much generality as possible without getting in your way.

Synopsis

Algebraic structures

class Group g whereSource

The algebraic structure of a group. Written additively. Required functions: zero and (^-^ or (^+^ and neg)).

Methods

zero :: gSource

(^+^) :: g -> g -> gSource

(^-^) :: g -> g -> gSource

neg :: g -> gSource

Instances

Group Bool 
Group Double 
Group Int 
Group Integer 
Integral a => Group (Ratio a) 
Group g => Group (IntMap g) 
Group g => Group (Poly g) 
Group g => Group (a -> g) 
(Group g1, Group g2) => Group (g1, g2) 
(Ord k, Group g) => Group (Map k g) 
(Ord v, Group c) => Group (LinExpr v c) 
(Group g1, Group g2, Group g3) => Group (g1, g2, g3) 
(Group g1, Group g2, Group g3, Group g4) => Group (g1, g2, g3, g4) 

class Group r => Ring r whereSource

The algebraic structure of a unital ring. Assumes that the additive operation forms an abelian group, that the multiplication operation forms a group, and that multiplication distributes.

Methods

one :: rSource

(*#) :: r -> r -> rSource

Instances

Ring Bool 
Ring Double 
Ring Int 
Ring Integer 
Integral a => Ring (Ratio a) 
Ring r => Ring (Poly r)

The polynomial ring.

Ring r => Ring (a -> r)

The function ring.

(Ord g, Group g, Ring r) => Ring (GroupRing r g)

The group ring.

class Ring f => Field f whereSource

Methods

inv :: f -> fSource

(/#) :: f -> f -> fSource

Instances

class (Ring r, Group m) => Module r m whereSource

The algebraic structure of a module. A vector space is a module with coefficients in a field.

Methods

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

Instances

Module Double Double 
Module Int Double 
Module Int Int 
Module Int Integer 
Module Integer Double 
Module Integer Integer 
Integral a => Module Int (Ratio a) 
Integral a => Module Integer (Ratio a) 
Module r m => Module r (IntMap m) 
(Module r m1, Module r m2) => Module r (m1, m2) 
(Ord k, Module r m) => Module r (Map k m) 
Module r m => Module r (a -> m) 
(Ord v, Module r c) => Module r (LinExpr v c) 
(Module r m1, Module r m2, Module r m3) => Module r (m1, m2, m3) 
(Module r m1, Module r m2, Module r m3, Module r m4) => Module r (m1, m2, m3, m4) 
Integral a => Module (Ratio a) Double 
Integral a => Module (Ratio a) (Ratio a) 
(Ord g, Group g, Ring r) => Module (GroupRing r g) (GroupRing r g) 

class (Module f v, Field f) => VectorSpace f v Source

Instances

(Module f v, Field f) => VectorSpace f v 

type Poly = []Source

varPoly :: Ring r => Poly rSource

Returns the polynomial p(x) = x.

type GroupRing r g = Map g rSource

A way of forming a ring from functions. See http://en.wikipedia.org/wiki/Group_ring.

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.

Algebraic functions

gsum :: Group g => [g] -> gSource

Does a summation over the elements of a group.

combination :: Module r m => [(r, m)] -> mSource

Given a collection of vectors and scaling coefficients, returns this linear combination.

evalPoly :: (Module r m, Ring m) => Poly r -> m -> mSource

Substitution into a polynomial.

Specialized methods on linear functions

var :: (Ord v, Ring c) => v -> LinFunc v cSource

Given a variable v, returns the function equivalent to v.

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

Equivalent to vsum . map var.

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

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

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.