| Copyright | (c) Junaid Rasheed 2020-2023 |
|---|---|
| License | BSD-3 |
| Maintainer | jrasheed178@gmail.com |
| Stability | experimental |
| Safe Haskell | Safe-Inferred |
| Language | Haskell2010 |
Linear.Simplex.Types
Description
Synopsis
- type Var = Int
- type SimplexNum = Rational
- type SystemRow = PolyConstraint
- type System = [SystemRow]
- data SystemWithSlackVarRow = SystemInStandardFormRow {
- mSlackVar :: Maybe Var
- row :: TableauRow
- type SystemWithSlackVars = [SystemWithSlackVarRow]
- data FeasibleSystem = FeasibleSystem {
- dict :: Dict
- slackVars :: [Var]
- artificialVars :: [Var]
- objectiveVar :: Var
- data Result = Result {}
- data SimplexMeta = SimplexMeta {}
- type VarLitMap = Map Var SimplexNum
- type VarLitMapSum = VarLitMap
- data PolyConstraint
- = LEQ {
- lhs :: VarLitMapSum
- rhs :: SimplexNum
- | GEQ {
- lhs :: VarLitMapSum
- rhs :: SimplexNum
- | EQ {
- lhs :: VarLitMapSum
- rhs :: SimplexNum
- = LEQ {
- data ObjectiveFunction
- data Equation = Equation {
- lhs :: VarLitMapSum
- rhs :: SimplexNum
- data TableauRow = TableauRow {
- lhs :: VarLitMapSum
- rhs :: SimplexNum
- type Tableau = Map Var TableauRow
- data DictValue = DictValue {}
- type Dict = Map Var DictValue
- data PivotObjective = PivotObjective {}
Documentation
type SimplexNum = Rational Source #
type SystemRow = PolyConstraint Source #
data SystemWithSlackVarRow Source #
Constructors
| SystemInStandardFormRow | |
Fields
| |
type SystemWithSlackVars = [SystemWithSlackVarRow] Source #
data FeasibleSystem Source #
Constructors
| FeasibleSystem | |
Fields
| |
Instances
Constructors
| Result | |
Fields
| |
Instances
| Generic Result Source # | |
| Read Result Source # | |
| Show Result Source # | |
| Eq Result Source # | |
| type Rep Result Source # | |
Defined in Linear.Simplex.Types type Rep Result = D1 ('MetaData "Result" "Linear.Simplex.Types" "simplex-method-0.2.0.0-DL5Tbu7QSIMBYoeQDIkkgN" 'False) (C1 ('MetaCons "Result" 'PrefixI 'True) (S1 ('MetaSel ('Just "objectiveVar") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Var) :*: S1 ('MetaSel ('Just "varValMap") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 VarLitMap))) | |
data SimplexMeta Source #
Constructors
| SimplexMeta | |
Fields | |
type VarLitMapSum = VarLitMap Source #
List of variables with their SimplexNum coefficients.
There is an implicit addition between elements in this list.
Example: [Var "x" 3, Var "y" -1, Var "z" 1] is equivalent to 3x + (-y) + z.
data PolyConstraint Source #
For specifying constraints in a system.
The LHS is a Vars, and the RHS, is a SimplexNum number.
LEQ [(1, 2), (2, 1)] 3.5 is equivalent to 2x1 + x2 <= 3.5.
Users must only provide positive integer variables.
Example: LEQ [Var "x" 3, Var "y" -1, Var "x" 1] 12.3 is equivalent to 3x + (-y) + x <= 12.3.
Constructors
| LEQ | |
Fields
| |
| GEQ | |
Fields
| |
| EQ | |
Fields
| |
Instances
data ObjectiveFunction Source #
Instances
TODO: Maybe we want this type TODO: A better/alternative name
Constructors
| Equation | |
Fields
| |
data TableauRow Source #
Value for Tableau. lhs = rhs.
Constructors
| TableauRow | |
Fields
| |
Instances
| Generic TableauRow Source # | |
Defined in Linear.Simplex.Types Associated Types type Rep TableauRow :: Type -> Type # | |
| Read TableauRow Source # | |
Defined in Linear.Simplex.Types Methods readsPrec :: Int -> ReadS TableauRow # readList :: ReadS [TableauRow] # readPrec :: ReadPrec TableauRow # readListPrec :: ReadPrec [TableauRow] # | |
| Show TableauRow Source # | |
Defined in Linear.Simplex.Types Methods showsPrec :: Int -> TableauRow -> ShowS # show :: TableauRow -> String # showList :: [TableauRow] -> ShowS # | |
| Eq TableauRow Source # | |
Defined in Linear.Simplex.Types | |
| type Rep TableauRow Source # | |
Defined in Linear.Simplex.Types type Rep TableauRow = D1 ('MetaData "TableauRow" "Linear.Simplex.Types" "simplex-method-0.2.0.0-DL5Tbu7QSIMBYoeQDIkkgN" 'False) (C1 ('MetaCons "TableauRow" 'PrefixI 'True) (S1 ('MetaSel ('Just "lhs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 VarLitMapSum) :*: S1 ('MetaSel ('Just "rhs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SimplexNum))) | |
type Tableau = Map Var TableauRow Source #
A simplex Tableu of equations.
Each entry in the map is a row.
Values for a Dict.
Constructors
| DictValue | |
Fields | |
Instances
| Generic DictValue Source # | |
| Read DictValue Source # | |
| Show DictValue Source # | |
| Eq DictValue Source # | |
| type Rep DictValue Source # | |
Defined in Linear.Simplex.Types type Rep DictValue = D1 ('MetaData "DictValue" "Linear.Simplex.Types" "simplex-method-0.2.0.0-DL5Tbu7QSIMBYoeQDIkkgN" 'False) (C1 ('MetaCons "DictValue" 'PrefixI 'True) (S1 ('MetaSel ('Just "varMapSum") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 VarLitMapSum) :*: S1 ('MetaSel ('Just "constant") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SimplexNum))) | |
type Dict = Map Var DictValue Source #
A simplex Dict
One quation represents the objective function.
Each pair in the list is one equation in the system we're working with.
data Dict = Dict
{ objective :: DictObjective
, entries :: DictEntries
}
deriving (Show, Read, Eq, Generic)
data PivotObjective Source #
Constructors
| PivotObjective | |
Fields
| |