module Numeric.Limp.Canon.Simplify.Crunch where
import Numeric.Limp.Canon.Constraint
import Numeric.Limp.Canon.Program
import Numeric.Limp.Rep
import Data.List
import Data.Function
import Data.Maybe
crunchProgram :: (Ord z, Ord r, Rep c) => Program z r c -> Program z r c
crunchProgram p
= p { _constraints = crunchConstraint $ _constraints p }
crunchConstraint :: (Ord z, Ord r, Rep c) => Constraint z r c -> Constraint z r c
crunchConstraint (Constraint cs)
= Constraint
$ map crunchC
$ groupBy ((==) `on` getLin) cs
where
getLin (C1 _ lin _ ) = lin
getLow (C1 low _ _ ) = low
getUpp (C1 _ _ upp) = upp
crunchC grp@(c:_)
= let low = compareMaybes maximum $ map getLow grp
upp = compareMaybes minimum $ map getUpp grp
in C1 low (getLin c) upp
crunchC []
= error "Impossible - groupBy should not produce empty lists"
compareMaybes f ms
= case catMaybes ms of
ms'@(_:_) -> Just $ f ms'
[] -> Nothing