module Numeric.Limp.Canon.Simplify.Subst where
import Numeric.Limp.Canon.Constraint
import Numeric.Limp.Canon.Linear
import Numeric.Limp.Canon.Program
import Numeric.Limp.Rep
import qualified Data.Map as M
substLinear :: (Ord z, Ord r, Rep c) => Assignment z r c -> Linear z r c -> (Linear z r c, R c)
substLinear (Assignment mz mr) (Linear mf)
= ( Linear $ M.fromList $ concatMap update mf'
, sum $ map getC mf' )
where
mf' = M.toList mf
get (v,co)
| Left z <- v
, Just zv <- M.lookup z mz
= Just $ fromZ zv * co
| Right r <- v
, Just rv <- M.lookup r mr
= Just $ rv * co
| otherwise
= Nothing
update vc
| Just _ <- get vc
= []
| otherwise
= [vc]
getC vc
| Just n <- get vc
= n
| otherwise
= 0
substConstraint1 :: (Ord z, Ord r, Rep c) => Assignment z r c -> Constraint1 z r c -> Constraint1 z r c
substConstraint1 ass (C1 low lin upp)
= let (lin', const') = substLinear ass lin
fixup bound = bound - const'
in C1 (fmap fixup low) lin' (fmap fixup upp)
substConstraint :: (Ord z, Ord r, Rep c) => Assignment z r c -> Constraint z r c -> Constraint z r c
substConstraint ass (Constraint cs)
= Constraint
$ map (substConstraint1 ass) cs
substProgram :: (Ord z, Ord r, Rep c) => Assignment z r c -> Program z r c -> Program z r c
substProgram ass@(Assignment mz mr) p
= p
{ _objective = fst $ substLinear ass $ _objective p
, _constraints = substConstraint ass $ _constraints p
, _bounds = cullBounds $ _bounds p
}
where
cullBounds
= M.mapMaybeWithKey cullB
cullB k v
| Left z <- k
, Just _ <- M.lookup z mz
= Nothing
| Right r <- k
, Just _ <- M.lookup r mr
= Nothing
| otherwise
= Just v