glpk-hs-0.3.5: Comprehensive GLPK linear programming bindings

Safe HaskellNone
LanguageHaskell98

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 where Source

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

Minimal complete definition

zero

Methods

zero :: g Source

(^+^) :: g -> g -> g infixr 4 Source

(^-^) :: g -> g -> g infixr 4 Source

neg :: g -> g Source

Instances

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

class Group r => Ring r where Source

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 :: r Source

(*#) :: r -> r -> r infixr 6 Source

Instances

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

The polynomial ring.

Ring r => Ring (a -> r) Source

The function ring.

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

The group ring.

class Ring f => Field f where Source

Minimal complete definition

Nothing

Methods

inv :: f -> f Source

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

class (Ring r, Group m) => Module r m where Source

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

Methods

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

Instances

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

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

Instances

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

type Poly = [] Source

varPoly :: Ring r => Poly r Source

Returns the polynomial p(x) = x.

type GroupRing r g = Map g r Source

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

type LinFunc = Map Source

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] -> g Source

Does a summation over the elements of a group.

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

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

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

Substitution into a polynomial.

Specialized methods on linear functions

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

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

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

Equivalent to vsum . map var.

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

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

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

Given a set of basic variables and coefficients, returns the linear combination obtained by summing.