@@ -39,6 +39,7 @@ along with this program. If not, see <https://www.gnu.org/licenses/>.
39
39
40
40
module Language.CQL.Term where
41
41
42
+ import Control.Applicative ((<|>) )
42
43
import Control.DeepSeq
43
44
import Data.Map.Merge.Strict
44
45
import Data.Map.Strict as Map hiding (foldr , size )
@@ -267,27 +268,26 @@ occurs h x = case x of
267
268
Att h' a -> h == HAtt h' || occurs h a
268
269
Sym h' as -> h == HSym h' || any (occurs h) as
269
270
270
- -- | If there is one, finds an equation of the form empty |- @ gen/sk = term@,
271
+ -- | If there is one, finds an equation of the form @ empty |- gen/sk = term@,
271
272
-- where @gen@ does not occur in @term@.
272
- findSimplifiableEqs
273
+ findSimplifiableEq
273
274
:: (Eq ty , Eq sym , Eq en , Eq fk , Eq att , Eq gen , Eq sk )
274
275
=> Theory var ty sym en fk att gen sk
275
276
-> Maybe (Head ty sym en fk att gen sk , Term var ty sym en fk att gen sk )
276
- findSimplifiableEqs = procEqs . Set. toList
277
+ findSimplifiableEq = goEqs . Set. toList
277
278
where
279
+ goEqs [] = Nothing
280
+ goEqs ((ctx, _ ): ctxEqs) | not (Map. null ctx) = goEqs ctxEqs
281
+ goEqs ((_ , eq): ctxEqs) = goEq eq <|> goEqs ctxEqs
282
+
283
+ goEq (EQ (lhs, rhs)) = g lhs rhs <|> g rhs lhs
284
+
278
285
g (Var _) _ = Nothing
279
- g (Sk y) t = if occurs ( HSk y) t then Nothing else Just (HSk y, t)
280
- g (Gen y) t = if occurs ( HGen y) t then Nothing else Just (HGen y, t)
286
+ g (Sk y) t = if HSk y `occurs` t then Nothing else Just (HSk y, t)
287
+ g (Gen y) t = if HGen y `occurs` t then Nothing else Just (HGen y, t)
281
288
g (Sym _ [] ) _ = Nothing
282
- g _ _ = Nothing
289
+ g _ _ = Nothing
283
290
284
- procEqs [] = Nothing
285
- procEqs ((m, _): tl) | not (Map. null m) = procEqs tl
286
- procEqs ((_, EQ (lhs, rhs)): tl) = case g lhs rhs of
287
- Nothing -> case g rhs lhs of
288
- Nothing -> procEqs tl
289
- Just y -> Just y
290
- Just y -> Just y
291
291
292
292
-- | Replaces a symbol by a term in a term.
293
293
replace
@@ -331,7 +331,7 @@ simplifyTheoryStep
331
331
:: (MultiTyMap '[Ord ] '[var , ty , sym , en , fk , att , gen , sk ])
332
332
=> Theory var ty sym en fk att gen sk
333
333
-> Maybe (Theory var ty sym en fk att gen sk , (Head ty sym en fk att gen sk , Term var ty sym en fk att gen sk ))
334
- simplifyTheoryStep eqs = case findSimplifiableEqs eqs of
334
+ simplifyTheoryStep eqs = case findSimplifiableEq eqs of
335
335
Nothing -> Nothing
336
336
Just (toRemove, replacer) -> let
337
337
eqs2 = Set. map (\ (ctx, EQ (lhs, rhs)) -> (ctx, EQ (replace toRemove replacer lhs, replace toRemove replacer rhs))) eqs
0 commit comments