Safe Haskell | None |
---|---|
Language | Haskell2010 |
The simplest, stupidest possible simplex algorithm. The idea here is to be slow, but "obviously correct" so other algorithms can be verified against it.
That's the plan, at least. For now this is just a first cut of trying to implement simplex.
Synopsis
- data IterateResult z r c
- simplex1 :: (Ord z, Ord r, Rep c) => Standard z r c -> IterateResult z r c
- pivotRowForCol :: (Ord z, Ord r, Rep c) => Standard z r c -> StandardVar z r -> Maybe (StandardVar z r)
- minBy' :: (a -> a -> Ordering) -> [a] -> Maybe a
- pivot :: (Ord z, Ord r, Rep c) => Standard z r c -> (StandardVar z r, StandardVar z r) -> Standard z r c
- single_simplex :: (Ord z, Ord r, Rep c) => Standard z r c -> Maybe (Standard z r c)
- simplex :: (Ord z, Ord r, Rep c) => Standard z r c -> Maybe (Standard z r c)
- find_initial_sat :: (Ord z, Ord r, Rep c) => Standard z r c -> Maybe (Standard z r c)
- assignmentAll :: Rep c => Standard z r c -> (Map (StandardVar z r) (R c), R c)
- assignment :: (Ord z, Ord r, Rep c) => Standard z r c -> (Assignment () (Either z r) c, R c)
- minimise_basics :: (Ord z, Ord r, Rep c) => Standard z r c -> Standard z r c
- pricing_out :: (Ord z, Ord r, Rep c) => Standard z r c -> Standard z r c
- drop_fake_objective :: (Ord z, Ord r, Rep c) => Standard z r c -> Standard z r c
Documentation
data IterateResult z r c Source #
Result of a single pivot attempt
Done | Maximum reached! |
Progress (Standard z r c) | Pivot was made |
Stuck | No progress can be made: unbounded along the objective |
Instances
(Show z, Show r, Show (R c)) => Show (IterateResult z r c) Source # | |
Defined in Numeric.Limp.Solve.Simplex.Maps showsPrec :: Int -> IterateResult z r c -> ShowS # show :: IterateResult z r c -> String # showList :: [IterateResult z r c] -> ShowS # |
simplex1 :: (Ord z, Ord r, Rep c) => Standard z r c -> IterateResult z r c Source #
Try to find a pivot and then perform it. We're assuming, at this stage, that the existing solution is feasible.
pivotRowForCol :: (Ord z, Ord r, Rep c) => Standard z r c -> StandardVar z r -> Maybe (StandardVar z r) Source #
Find pivot row for given column. We're trying to find a way to increase the value of column from zero, and the returned row will be decreased to zero. Since all variables are >= 0, we cannot return a row that would set the column to negative.
pivot :: (Ord z, Ord r, Rep c) => Standard z r c -> (StandardVar z r, StandardVar z r) -> Standard z r c Source #
Perform pivot for given row and column. We normalise row so that row.column = 1
norm = row / row[column]
Then, for all other rows including the objective, we want to make sure its column entry is zero:
row' = row - row[column]*norm
In the end, this means "column" will be an identity column, or a basis column.
single_simplex :: (Ord z, Ord r, Rep c) => Standard z r c -> Maybe (Standard z r c) Source #
Single phase of simplex. Keep repeating until no progress can be made.
simplex :: (Ord z, Ord r, Rep c) => Standard z r c -> Maybe (Standard z r c) Source #
Two phase: first, find a satisfying solution. then, solve simplex as normal.
find_initial_sat :: (Ord z, Ord r, Rep c) => Standard z r c -> Maybe (Standard z r c) Source #
Find a satisfying solution. if there are any rows with negative values, this means their basic values are negative (which is not satisfying the x >= 0 constraint) these negative-valued rows must be pivoted around using modified pivot criteria
assignmentAll :: Rep c => Standard z r c -> (Map (StandardVar z r) (R c), R c) Source #
assignment :: (Ord z, Ord r, Rep c) => Standard z r c -> (Assignment () (Either z r) c, R c) Source #
minimise_basics :: (Ord z, Ord r, Rep c) => Standard z r c -> Standard z r c Source #
Minimise whatever variables are basic
in given standard
input must not already have an objective row SVO,
because the existing objective is added as a new row with that name