@@ -169,6 +169,7 @@ builtinFunctions =
169169
170170data UnifyBool = UnifyBool
171171 { bool1 , bool2 :: ! InternalBool
172+ , term1 , term2 :: ! (TermLike RewritingVariableName )
172173 }
173174
174175{- | Matches
@@ -187,31 +188,34 @@ matchBools ::
187188 TermLike RewritingVariableName ->
188189 TermLike RewritingVariableName ->
189190 Maybe UnifyBool
190- matchBools first second
191- | InternalBool_ bool1 <- first
192- , InternalBool_ bool2 <- second =
193- Just UnifyBool {bool1, bool2}
191+ matchBools term1 term2
192+ | InternalBool_ bool1 <- term2
193+ , InternalBool_ bool2 <- term1 =
194+ Just UnifyBool {bool1, bool2, term1, term2 }
194195 | otherwise = Nothing
195196{-# INLINE matchBools #-}
196197
197198-- | When bool values are equal, returns first term; otherwise returns bottom.
198199unifyBool ::
199200 forall unifier .
200201 MonadUnify unifier =>
201- TermLike RewritingVariableName ->
202- TermLike RewritingVariableName ->
203202 UnifyBool ->
204203 unifier (Pattern RewritingVariableName )
205- unifyBool termLike1 termLike2 unifyData
204+ unifyBool unifyData
206205 | bool1 == bool2 =
207- return (Pattern. fromTermLike termLike1 )
206+ return (Pattern. fromTermLike term1 )
208207 | otherwise =
209208 debugUnifyBottomAndReturnBottom
210209 " different Bool domain values"
211- termLike1
212- termLike2
210+ term1
211+ term2
213212 where
214- UnifyBool {bool1, bool2} = unifyData
213+ UnifyBool {bool1, bool2, term1, term2} = unifyData
214+
215+ data UnifyBoolAnd = UnifyBoolAnd
216+ { term :: ! (TermLike RewritingVariableName )
217+ , boolAnd :: ! BoolAnd
218+ }
215219
216220{- | Matches
217221
@@ -222,18 +226,24 @@ unifyBool termLike1 termLike2 unifyData
222226and
223227
224228@
225- \\and{_}(\\dv{Bool}("true"), andBool(_,_))
229+ \\and{_}(\\dv{Bool}("true"), andBool(_,_)),
226230@
231+
232+ symmetric in the two arguments.
227233-}
228234matchUnifyBoolAnd ::
229235 TermLike RewritingVariableName ->
230236 TermLike RewritingVariableName ->
231- Maybe BoolAnd
237+ Maybe UnifyBoolAnd
232238matchUnifyBoolAnd first second
233239 | Just True <- matchBool first
234240 , Just boolAnd <- matchBoolAnd second
235241 , isFunctionPattern second =
236- Just boolAnd
242+ Just $ UnifyBoolAnd {term = first, boolAnd}
243+ | Just True <- matchBool second
244+ , Just boolAnd <- matchBoolAnd first
245+ , isFunctionPattern first =
246+ Just $ UnifyBoolAnd {term = second, boolAnd}
237247 | otherwise =
238248 Nothing
239249{-# INLINE matchUnifyBoolAnd #-}
@@ -242,12 +252,12 @@ unifyBoolAnd ::
242252 forall unifier .
243253 MonadUnify unifier =>
244254 TermSimplifier RewritingVariableName unifier ->
245- TermLike RewritingVariableName ->
246- BoolAnd ->
255+ UnifyBoolAnd ->
247256 unifier (Pattern RewritingVariableName )
248- unifyBoolAnd unifyChildren term boolAnd =
257+ unifyBoolAnd unifyChildren unifyData =
249258 unifyBothWith unifyChildren term operand1 operand2
250259 where
260+ UnifyBoolAnd {term, boolAnd} = unifyData
251261 BoolAnd {operand1, operand2} = boolAnd
252262
253263{- | Takes a (function-like) pattern and unifies it against two other patterns.
@@ -275,6 +285,11 @@ unifyBothWith unify termLike1 operand1 operand2 = do
275285 unify' term1 term2 =
276286 Pattern. withoutTerm <$> unify term1 term2
277287
288+ data UnifyBoolOr = UnifyBoolOr
289+ { term :: ! (TermLike RewritingVariableName )
290+ , boolOr :: ! BoolOr
291+ }
292+
278293{- | Matches
279294
280295@
@@ -284,36 +299,42 @@ unifyBothWith unify termLike1 operand1 operand2 = do
284299and
285300
286301@
287- \\and{_}(\\dv{Bool}("false"), boolOr(_,_))
302+ \\and{_}(\\dv{Bool}("false"), boolOr(_,_)),
288303@
304+
305+ symmetric in the two arguments.
289306-}
290307matchUnifyBoolOr ::
291308 TermLike RewritingVariableName ->
292309 TermLike RewritingVariableName ->
293- Maybe BoolOr
310+ Maybe UnifyBoolOr
294311matchUnifyBoolOr first second
295312 | Just False <- matchBool first
296313 , Just boolOr <- matchBoolOr second
297314 , isFunctionPattern second =
298- Just boolOr
315+ Just UnifyBoolOr {term = first, boolOr}
316+ | Just False <- matchBool second
317+ , Just boolOr <- matchBoolOr first
318+ , isFunctionPattern first =
319+ Just UnifyBoolOr {term = second, boolOr}
299320 | otherwise = Nothing
300321{-# INLINE matchUnifyBoolOr #-}
301322
302323unifyBoolOr ::
303324 forall unifier .
304325 MonadUnify unifier =>
305326 TermSimplifier RewritingVariableName unifier ->
306- TermLike RewritingVariableName ->
307- BoolOr ->
327+ UnifyBoolOr ->
308328 unifier (Pattern RewritingVariableName )
309- unifyBoolOr unifyChildren termLike boolOr =
310- unifyBothWith unifyChildren termLike operand1 operand2
329+ unifyBoolOr unifyChildren unifyData =
330+ unifyBothWith unifyChildren term operand1 operand2
311331 where
332+ UnifyBoolOr {term, boolOr} = unifyData
312333 BoolOr {operand1, operand2} = boolOr
313334
314335data UnifyBoolNot = UnifyBoolNot
315- { boolNot :: BoolNot
316- , value :: Bool
336+ { boolNot :: ! BoolNot
337+ , value :: ! InternalBool
317338 }
318339
319340{- | Matches
@@ -325,8 +346,10 @@ data UnifyBoolNot = UnifyBoolNot
325346and
326347
327348@
328- \\and{_}(notBool(_), \\dv{Bool}(_))
349+ \\and{_}(notBool(_), \\dv{Bool}(_)),
329350@
351+
352+ symmetric in the two arguments.
330353-}
331354matchUnifyBoolNot ::
332355 TermLike RewritingVariableName ->
@@ -335,24 +358,33 @@ matchUnifyBoolNot ::
335358matchUnifyBoolNot first second
336359 | Just boolNot <- matchBoolNot first
337360 , isFunctionPattern first
338- , Just value <- matchBool second =
339- Just $ UnifyBoolNot boolNot value
361+ , Just value <- matchInternalBool second =
362+ Just UnifyBoolNot {boolNot, value}
363+ | Just boolNot <- matchBoolNot second
364+ , isFunctionPattern second
365+ , Just value <- matchInternalBool first =
366+ Just UnifyBoolNot {boolNot, value}
340367 | otherwise = Nothing
341368{-# INLINE matchUnifyBoolNot #-}
342369
343370unifyBoolNot ::
344371 forall unifier .
345372 TermSimplifier RewritingVariableName unifier ->
346- TermLike RewritingVariableName ->
347373 UnifyBoolNot ->
348374 unifier (Pattern RewritingVariableName )
349- unifyBoolNot unifyChildren term unifyData =
350- let notValue = asInternal (termLikeSort term) (not value )
375+ unifyBoolNot unifyChildren unifyData =
376+ let notValue = asInternal internalBoolSort (not internalBoolValue )
351377 in unifyChildren notValue operand
352378 where
353379 UnifyBoolNot {boolNot, value} = unifyData
380+ InternalBool {internalBoolValue, internalBoolSort} = value
354381 BoolNot {operand} = boolNot
355382
383+ matchInternalBool :: TermLike variable -> Maybe InternalBool
384+ matchInternalBool (InternalBool_ internalBool) =
385+ Just internalBool
386+ matchInternalBool _ = Nothing
387+
356388-- | Match a @BOOL.Bool@ builtin value.
357389matchBool :: TermLike variable -> Maybe Bool
358390matchBool (InternalBool_ InternalBool {internalBoolValue}) =
0 commit comments