diff options
| author | Justin Bedo <cu@cua0.org> | 2014-10-23 13:47:53 +1100 | 
|---|---|---|
| committer | Justin Bedo <cu@cua0.org> | 2014-10-23 13:49:09 +1100 | 
| commit | 2b2c0bfe78740fe4e228958054729e791e3733dd (patch) | |
| tree | 1717077486406f76aec71acb2bc4eb6f802a2d9a /Math/LinProg/Types.hs | |
| parent | 365afb5dca44d1ce19b30921aa9032e41d9c8e06 (diff) | |
Added documentation.
Diffstat (limited to 'Math/LinProg/Types.hs')
| -rw-r--r-- | Math/LinProg/Types.hs | 58 | 
1 files changed, 42 insertions, 16 deletions
| diff --git a/Math/LinProg/Types.hs b/Math/LinProg/Types.hs index 69da6bf..6fbad93 100644 --- a/Math/LinProg/Types.hs +++ b/Math/LinProg/Types.hs @@ -1,7 +1,20 @@  {-# LANGUAGE DeriveFunctor, FlexibleInstances, FlexibleContexts, UndecidableInstances #-} - +{-| +Module      : Math.LinProg.Types +Description : Base types for equations and optimisation monad +Copyright   : (c) Justin Bedő, 2014 +License     : BSD +Maintainer  : cu@cua0.org +Stability   : experimental + +This module defines the base types for representing equations and linear +programs.  The linear program is created as a free monad, and equations as an +AST.  Note that expressions are assumed to be linear expressions and hence +there is no explicit checking for higher order terms. +-}  module Math.LinProg.Types (    LinExpr +  ,LinExpr'(..)    ,var    ,vars    ,varTerms @@ -13,14 +26,13 @@ module Math.LinProg.Types (    ,(<:)    ,(=:)    ,(>:) -  ,eq -  ,leq -  ,geq  ) where  import Data.Functor.Foldable  import Control.Monad.Free +-- | Base AST for expressions.  Expressions have factors or type t and +-- variables referenced by ids of type v.  data LinExpr' t v a =    Lit t    | Var v @@ -31,12 +43,12 @@ data LinExpr' t v a =  type LinExpr t v = Fix (LinExpr' t v) +-- | Creates a new variable for reference in equations  var = Fix . Var -instance Fractional t => Fractional (LinExpr t v) where -  a / b = Fix (Mul a (1/b)) -  fromRational a = Fix (Lit (fromRational a)) - +-- | For convient notation, expressions are declared as instances of num. +-- However, linear expressions cannot implement absolute value or sign +-- functions, hence these two remain undefined.  instance Num t => Num (LinExpr t v) where    a * b = Fix (Mul a b)    a + b = Fix (Add a b) @@ -45,6 +57,12 @@ instance Num t => Num (LinExpr t v) where    abs = undefined    signum = undefined +-- | Linear expressions can also be instances of fractional. +instance Fractional t => Fractional (LinExpr t v) where +  a / b = Fix (Mul a (1/b)) +  fromRational a = Fix (Lit (fromRational a)) + +-- | Reduce a linear expression down to the constant factor.  consts :: Num t => LinExpr t v -> t  consts = cata consts' where    consts' (Negate a) = negate a @@ -53,6 +71,7 @@ consts = cata consts' where    consts' (Add a b) = a + b    consts' (Mul a b) = a * b +-- | Gets the multiplier for a particular variable.  getVar :: (Num t, Eq v) => v -> LinExpr t v -> t  getVar id x = cata getVar' x - consts x where    getVar' (Var x) | x == id = 1 @@ -62,6 +81,7 @@ getVar id x = cata getVar' x - consts x where    getVar' (Mul a b) = a * b    getVar' (Negate a) = negate a +-- | Gets all variables used in an equation.  vars :: LinExpr t v -> [v]  vars = cata vars' where    vars' (Var x) = [x] @@ -70,6 +90,7 @@ vars = cata vars' where    vars' (Negate a) = a    vars' _ = [] +-- | Reduces an expression to the variable terms  varTerms eq = go eq' where    go [t] = t    go (t:ts) = Fix (Add t (go ts)) @@ -79,6 +100,7 @@ varTerms eq = go eq' where    vs = vars eq    ws = map (`getVar` eq) vs +-- | Splits an expression into the variables and the constant term  split :: (Num t, Eq v) => LinExpr t v -> (LinExpr t v, t)  split eq = (varTerms eq, consts eq) @@ -89,8 +111,9 @@ prettyPrint = cata prettyPrint' where    prettyPrint' (Add a b) = concat ["(", a, "+", b, ")"]    prettyPrint' (Var x) = show x --- Monad for linear programs - +-- | Free monad for linear programs.  The monad allows definition of the +-- objective function, equality constraints, and inequality constraints (≤ only +-- in the data type).  data LinProg' t v a =    Objective (LinExpr t v) a    | EqConstraint (LinExpr t v) (LinExpr t v) a @@ -99,14 +122,17 @@ data LinProg' t v a =  type LinProg t v = Free (LinProg' t v) +-- | Define a term in the objective function  obj a = liftF (Objective a ()) -eq a b = liftF (EqConstraint a b ()) -leq a b = liftF (LeqConstraint a b ()) -geq b a = liftF (LeqConstraint a b ()) -a =: b = eq a b -a <: b = leq a b -a >: b = geq a b +-- | Define an equality constraint +a =: b = liftF (EqConstraint a b ()) + +-- | Define an inequality (less than equal) contraint +a <: b = liftF (LeqConstraint a b ()) +-- +-- | Define an inequality (greater than equal) contraint +b >: a = liftF (LeqConstraint a b ())  infix 4 =:  infix 4 <: | 
