simplex-method-0.2.0.0: Implementation of the two-phase simplex method in exact rational arithmetic
Copyright(c) Junaid Rasheed 2020-2023
LicenseBSD-3
Maintainerjrasheed178@gmail.com
Stabilityexperimental
Safe HaskellSafe-Inferred
LanguageHaskell2010

Linear.Simplex.Types

Description

 
Synopsis

Documentation

type Var = Int Source #

data SystemWithSlackVarRow Source #

Constructors

SystemInStandardFormRow 

Fields

data FeasibleSystem Source #

Constructors

FeasibleSystem 

Instances

Instances details
Generic FeasibleSystem Source # 
Instance details

Defined in Linear.Simplex.Types

Associated Types

type Rep FeasibleSystem :: Type -> Type #

Read FeasibleSystem Source # 
Instance details

Defined in Linear.Simplex.Types

Show FeasibleSystem Source # 
Instance details

Defined in Linear.Simplex.Types

Eq FeasibleSystem Source # 
Instance details

Defined in Linear.Simplex.Types

type Rep FeasibleSystem Source # 
Instance details

Defined in Linear.Simplex.Types

type Rep FeasibleSystem = D1 ('MetaData "FeasibleSystem" "Linear.Simplex.Types" "simplex-method-0.2.0.0-DL5Tbu7QSIMBYoeQDIkkgN" 'False) (C1 ('MetaCons "FeasibleSystem" 'PrefixI 'True) ((S1 ('MetaSel ('Just "dict") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Dict) :*: S1 ('MetaSel ('Just "slackVars") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Var])) :*: (S1 ('MetaSel ('Just "artificialVars") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Var]) :*: S1 ('MetaSel ('Just "objectiveVar") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Var))))

data Result Source #

Constructors

Result 

Instances

Instances details
Generic Result Source # 
Instance details

Defined in Linear.Simplex.Types

Associated Types

type Rep Result :: Type -> Type #

Methods

from :: Result -> Rep Result x #

to :: Rep Result x -> Result #

Read Result Source # 
Instance details

Defined in Linear.Simplex.Types

Show Result Source # 
Instance details

Defined in Linear.Simplex.Types

Eq Result Source # 
Instance details

Defined in Linear.Simplex.Types

Methods

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

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

type Rep Result Source # 
Instance details

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)))

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 
GEQ 
EQ 

Instances

Instances details
Generic PolyConstraint Source # 
Instance details

Defined in Linear.Simplex.Types

Associated Types

type Rep PolyConstraint :: Type -> Type #

Read PolyConstraint Source # 
Instance details

Defined in Linear.Simplex.Types

Show PolyConstraint Source # 
Instance details

Defined in Linear.Simplex.Types

Eq PolyConstraint Source # 
Instance details

Defined in Linear.Simplex.Types

type Rep PolyConstraint Source # 
Instance details

Defined in Linear.Simplex.Types

data ObjectiveFunction Source #

Create an objective function. We can either Maximize or Minimize a VarTermSum.

Constructors

Max 
Min 

data Equation Source #

TODO: Maybe we want this type TODO: A better/alternative name

Constructors

Equation 

data TableauRow Source #

Value for Tableau. lhs = rhs.

Constructors

TableauRow 

Instances

Instances details
Generic TableauRow Source # 
Instance details

Defined in Linear.Simplex.Types

Associated Types

type Rep TableauRow :: Type -> Type #

Read TableauRow Source # 
Instance details

Defined in Linear.Simplex.Types

Show TableauRow Source # 
Instance details

Defined in Linear.Simplex.Types

Eq TableauRow Source # 
Instance details

Defined in Linear.Simplex.Types

type Rep TableauRow Source # 
Instance details

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.

data DictValue Source #

Values for a Dict.

Constructors

DictValue 

Instances

Instances details
Generic DictValue Source # 
Instance details

Defined in Linear.Simplex.Types

Associated Types

type Rep DictValue :: Type -> Type #

Read DictValue Source # 
Instance details

Defined in Linear.Simplex.Types

Show DictValue Source # 
Instance details

Defined in Linear.Simplex.Types

Eq DictValue Source # 
Instance details

Defined in Linear.Simplex.Types

type Rep DictValue Source # 
Instance details

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 #

Instances

Instances details
Generic PivotObjective Source # 
Instance details

Defined in Linear.Simplex.Types

Associated Types

type Rep PivotObjective :: Type -> Type #

Read PivotObjective Source # 
Instance details

Defined in Linear.Simplex.Types

Show PivotObjective Source # 
Instance details

Defined in Linear.Simplex.Types

Eq PivotObjective Source # 
Instance details

Defined in Linear.Simplex.Types

type Rep PivotObjective Source # 
Instance details

Defined in Linear.Simplex.Types

type Rep PivotObjective = D1 ('MetaData "PivotObjective" "Linear.Simplex.Types" "simplex-method-0.2.0.0-DL5Tbu7QSIMBYoeQDIkkgN" 'False) (C1 ('MetaCons "PivotObjective" 'PrefixI 'True) (S1 ('MetaSel ('Just "variable") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Var) :*: (S1 ('MetaSel ('Just "function") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 VarLitMapSum) :*: S1 ('MetaSel ('Just "constant") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SimplexNum))))