Skip to content

Commit

Permalink
Keep upper and lower bounds together.
Browse files Browse the repository at this point in the history
This should make it easier to extract models
  • Loading branch information
yav committed Oct 29, 2013
1 parent 7fcd2ba commit 05015ef
Showing 1 changed file with 27 additions and 24 deletions.
51 changes: 27 additions & 24 deletions src/Data/Integer/Presburger/Omega.hs
Expand Up @@ -79,12 +79,15 @@ ctGt t1 t2 = ctLt t2 t1
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- Inert set -- Inert set



type Bound = (Integer,Term)

-- | The inert contains the solver state on one possible path. -- | The inert contains the solver state on one possible path.
data Inerts = Inerts data Inerts = Inerts
{ bounds :: IntMap ([(Integer,Term)], [(Integer,Term)]) { bounds :: IntMap ([Bound],[Bound])
-- ^ Known lower and upper bounds for variables. -- ^ Known lower and upper bounds for variables.
-- Each entry @(c,t)@ in the first list asserts @t < c * x@ -- Each bound @(c,t)@ in the first list asserts that @t < c * x@
-- Each entry @(c,t)@ in the second list asserts @c * x < t@ -- Each bound @(c,t)@ in the second list asserts that @c * x < t@


, solved :: IntMap Term , solved :: IntMap Term
-- ^ Definitions for resolved variabless. -- ^ Definitions for resolved variabless.
Expand Down Expand Up @@ -122,34 +125,32 @@ iSolved x t i =
where where
(kickedOut, otherBounds) = (kickedOut, otherBounds) =


-- First, we eliminate all entries for `x`
let (mb, mp1) = Map.updateLookupWithKey (\_ _ -> Nothing) x (bounds i) let (mb, mp1) = Map.updateLookupWithKey (\_ _ -> Nothing) x (bounds i)


check (c,t1) if tHasVar x t1 then Right -- Next, we elminate all constraints that mentiond `x` in bounds

mp2 = Map.mapWithKey extractBounds mp1
upd y (lbs,ubs) = let (lbsStay, lbsKick) = partition stay lbs
(ubsStay, ubsKick) = partition stay ubs
in ( (lbsStay,ubsStay)
, [

-- xy * y < t(x)
mp2 = fmap (partition (tHasVar x . snd)) mp1


in ( [ ct | (lbs,ubs) <- maybeToList mb in ( [ ct | (lbs,ubs) <- maybeToList mb
, ct <- [ ctLt lb (c |*| t) | (c,lb) <- lbs ] ++ , ct <- [ ctLt lb (c |*| t) | (c,lb) <- lbs ] ++
[ ctLt (c |*| t) ub | (c,ub) <- ubs ] [ ctLt (c |*| t) ub | (c,ub) <- ubs ]
] ++ ] ++
[ ct | (_,cts) <- Map.elems mp2, ct <- cts ]


[ (y, (lbs,ubs)) <- Map.toList mp1 , fmap fst mp2
, )


] extractBounds y (lbs,ubs) =
let (lbsStay, lbsKick) = partition stay lbs
(ubsStay, ubsKick) = partition stay ubs
in ( (lbsStay,ubsStay)
, [ ctLt (tLet x t lb) (c |*| tVar y) | (c,lb) <- lbsKick ] ++
[ ctLt (c |*| tVar y) (tLet x t ub) | (c,ub) <- ubsKick ]
)


stay (_,bnd) = not (tHasVar x bnd)




++ [ f (yc |*| tVar y) (tLet x t t1) | (y,(vs,_)) <- Map.toList mp2,
(yc,t1) <- vs ]
, Map.filter (not . null) (fmap snd mp2)
)




-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
Expand Down Expand Up @@ -212,13 +213,13 @@ solveIsNeg t
do ctrs <- if xc < 0 do ctrs <- if xc < 0
-- -XC*x + S < 0 -- -XC*x + S < 0
-- S < XC*x -- S < XC*x
then do ubs <- getBounds (snd . bounds) x then do ubs <- getBounds snd x
let b = negate xc let b = negate xc
beta = s beta = s
return [ (a,alpha,b,beta) | (a,alpha) <- ubs ] return [ (a,alpha,b,beta) | (a,alpha) <- ubs ]
-- XC*x + S < 0 -- XC*x + S < 0
-- XC*x < -S -- XC*x < -S
else do lbs <- getBounds (fst . bounds) x else do lbs <- getBounds fst x
let a = xc let a = xc
alpha = negate s alpha = negate s
return [ (a,alpha,b,beta) | (b,beta) <- lbs ] return [ (a,alpha,b,beta) | (b,beta) <- lbs ]
Expand Down Expand Up @@ -343,9 +344,11 @@ addWork (getF,setF) t = updS_ $ \rw ->
let work = todo rw let work = todo rw
in rw { todo = setF (t : getF work) work } in rw { todo = setF (t : getF work) work }


-- | Get upper or lower bounds for a variable. -- | Get lower ('fst'), or upper ('snd') bounds for a variable.
getBounds :: (Inerts -> IntMap [a]) -> Name -> S [a] getBounds :: (([Bound],[Bound]) -> [Bound]) -> Name -> S [Bound]
getBounds f x = get $ Map.findWithDefault [] x . f . inerts getBounds f x = get $ \rw -> case Map.lookup x $ bounds $ inerts rw of
Nothing -> []
Just bs -> f bs


-- | Add a new definition. -- | Add a new definition.
-- Assumes substitution has already been applied -- Assumes substitution has already been applied
Expand Down

0 comments on commit 05015ef

Please sign in to comment.