Skip to content

Commit 8edc94e

Browse files
Remove MultiAnd's Functor instance (#2139)
* Remove Functor instance from MultiAnd * Remove MultiAnd.extractPatterns * MultiAnd: define Semigroup and Monoid instances Co-authored-by: Thomas Tuegel <[email protected]>
1 parent 3fb0874 commit 8edc94e

File tree

12 files changed

+67
-39
lines changed

12 files changed

+67
-39
lines changed

kore/src/Kore/Exec.hs

Lines changed: 1 addition & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -80,9 +80,6 @@ import Kore.IndexedModule.Resolvers
8080
( resolveInternalSymbol
8181
)
8282
import qualified Kore.Internal.Condition as Condition
83-
import qualified Kore.Internal.MultiAnd as MultiAnd
84-
( extractPatterns
85-
)
8683
import Kore.Internal.Pattern
8784
( Pattern
8885
)
@@ -712,7 +709,7 @@ initializeProver definitionModule specModule maybeTrustedModule = do
712709
simplifyToList :: SomeClaim -> simplifier [SomeClaim]
713710
simplifyToList rule = do
714711
simplified <- simplifyRuleLhs rule
715-
let result = MultiAnd.extractPatterns simplified
712+
let result = Foldable.toList simplified
716713
when (null result) $ warnTrivialClaimRemoved rule
717714
return result
718715

kore/src/Kore/Internal/MultiAnd.hs

Lines changed: 25 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -14,25 +14,28 @@ Portability : portable
1414
module Kore.Internal.MultiAnd
1515
( MultiAnd
1616
, top
17-
, extractPatterns
1817
, make
1918
, toPredicate
2019
, fromPredicate
2120
, fromTermLike
2221
, singleton
2322
, toPattern
2423
, map
24+
, traverse
2525
) where
2626

2727
import Prelude.Kore hiding
2828
( map
29+
, traverse
2930
)
3031

3132
import Control.DeepSeq
3233
( NFData
3334
)
35+
import qualified Data.Foldable as Foldable
3436
import qualified Data.Functor.Foldable as Recursive
3537
import qualified Data.Set as Set
38+
import qualified Data.Traversable as Traversable
3639
import qualified Generics.SOP as SOP
3740
import qualified GHC.Exts as GHC
3841
import qualified GHC.Generics as GHC
@@ -72,9 +75,7 @@ A non-empty 'MultiAnd' would also have a nice symmetry between 'Top' and
7275
-}
7376
newtype MultiAnd child = MultiAnd { getMultiAnd :: [child] }
7477
deriving (Eq, Ord, Show)
75-
deriving (Semigroup, Monoid)
76-
deriving (Functor, Applicative, Monad, Alternative)
77-
deriving (Foldable, Traversable)
78+
deriving (Foldable)
7879
deriving (GHC.Generic, GHC.IsList)
7980

8081
instance SOP.Generic (MultiAnd child)
@@ -95,6 +96,14 @@ instance Debug child => Debug (MultiAnd child)
9596

9697
instance (Debug child, Diff child) => Diff (MultiAnd child)
9798

99+
instance (Ord child, TopBottom child) => Semigroup (MultiAnd child) where
100+
(MultiAnd []) <> b = b
101+
a <> (MultiAnd []) = a
102+
(MultiAnd a) <> (MultiAnd b) = make (a <> b)
103+
104+
instance (Ord child, TopBottom child) => Monoid (MultiAnd child) where
105+
mempty = make []
106+
98107
instance
99108
InternalVariable variable
100109
=> From (MultiAnd (Predicate variable)) (Predicate variable)
@@ -148,12 +157,6 @@ make patts = filterAnd (MultiAnd patts)
148157
singleton :: (Ord term, TopBottom term) => term -> MultiAnd term
149158
singleton term = make [term]
150159

151-
{-| Returns the patterns inside an @\and@.
152-
-}
153-
extractPatterns :: MultiAnd term -> [term]
154-
extractPatterns = getMultiAnd
155-
156-
157160
{- | Simplify the conjunction.
158161
159162
The arguments are simplified by filtering on @\\top@ and @\\bottom@. The
@@ -245,4 +248,15 @@ map
245248
=> (child1 -> child2)
246249
-> MultiAnd child1
247250
-> MultiAnd child2
248-
map f = make . fmap f . extractPatterns
251+
map f = make . fmap f . Foldable.toList
252+
{-# INLINE map #-}
253+
254+
traverse
255+
:: Ord child2
256+
=> TopBottom child2
257+
=> Applicative f
258+
=> (child1 -> f child2)
259+
-> MultiAnd child1
260+
-> f (MultiAnd child2)
261+
traverse f = fmap make . Traversable.traverse f . Foldable.toList
262+
{-# INLINE traverse #-}

kore/src/Kore/Internal/MultiOr.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -194,7 +194,7 @@ distributeAnd =
194194
foldr (crossProductGeneric and') (singleton MultiAnd.top)
195195
where
196196
and' term ma =
197-
term : MultiAnd.extractPatterns ma & MultiAnd.make
197+
MultiAnd.singleton term <> ma
198198

199199
distributeApplication
200200
:: Ord head

kore/src/Kore/Step/Axiom/Matcher.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -197,7 +197,7 @@ matchIncremental termLike1 termLike2 =
197197
MatcherState
198198
{ queued = Set.singleton (Constraint (Pair termLike1 termLike2))
199199
, deferred = empty
200-
, predicate = empty
200+
, predicate = mempty
201201
, substitution = mempty
202202
, bound = mempty
203203
, targets = free1
@@ -521,7 +521,7 @@ substitute eVariable termLike = do
521521
-- Apply the substitution to the accumulated matching solution.
522522
>>= (field @"substitution" . traverse) substitute1
523523
>>= Monad.State.put
524-
field @"predicate" . Lens.mapped %= Predicate.substitute subst
524+
field @"predicate" %= MultiAnd.map (Predicate.substitute subst)
525525

526526
return ()
527527
where
@@ -581,7 +581,7 @@ setSubstitute sVariable termLike = do
581581

582582
-- Apply the substitution to the accumulated matching solution.
583583
field @"substitution" . Lens.mapped %= substitute1
584-
field @"predicate" . Lens.mapped %= Predicate.substitute subst
584+
field @"predicate" %= MultiAnd.map (Predicate.substitute subst)
585585

586586
return ()
587587
where

kore/src/Kore/Step/Remainder.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -119,7 +119,7 @@ unificationConditions
119119
-- ^ Unification solution
120120
-> MultiAnd (Predicate RewritingVariableName)
121121
unificationConditions Conditional { predicate, substitution } =
122-
pure predicate <|> substitutionConditions substitution'
122+
MultiAnd.singleton predicate <> substitutionConditions substitution'
123123
where
124124
substitution' = Substitution.filter isSomeConfigVariable substitution
125125

kore/src/Kore/Step/Rule/Simplify.hs

Lines changed: 11 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -22,8 +22,6 @@ import Kore.Internal.MultiAnd
2222
( MultiAnd
2323
)
2424
import qualified Kore.Internal.MultiAnd as MultiAnd
25-
( make
26-
)
2725
import qualified Kore.Internal.OrPattern as OrPattern
2826
import Kore.Internal.Pattern
2927
( Pattern
@@ -144,21 +142,27 @@ instance SimplifyRuleLHS ClaimPattern
144142

145143
instance SimplifyRuleLHS (RewriteRule VariableName) where
146144
simplifyRuleLhs =
147-
fmap (fmap RewriteRule) . simplifyRuleLhs . getRewriteRule
145+
fmap (MultiAnd.map RewriteRule)
146+
. simplifyRuleLhs
147+
. getRewriteRule
148148

149149
instance SimplifyRuleLHS OnePathClaim where
150150
simplifyRuleLhs =
151-
fmap (fmap OnePathClaim) . simplifyClaimRule . getOnePathClaim
151+
fmap (MultiAnd.map OnePathClaim)
152+
. simplifyClaimRule
153+
. getOnePathClaim
152154

153155
instance SimplifyRuleLHS AllPathClaim where
154156
simplifyRuleLhs =
155-
fmap (fmap AllPathClaim) . simplifyClaimRule . getAllPathClaim
157+
fmap (MultiAnd.map AllPathClaim)
158+
. simplifyClaimRule
159+
. getAllPathClaim
156160

157161
instance SimplifyRuleLHS SomeClaim where
158162
simplifyRuleLhs (OnePath rule) =
159-
(fmap . fmap) OnePath $ simplifyRuleLhs rule
163+
(fmap . MultiAnd.map) OnePath $ simplifyRuleLhs rule
160164
simplifyRuleLhs (AllPath rule) =
161-
(fmap . fmap) AllPath $ simplifyRuleLhs rule
165+
(fmap . MultiAnd.map) AllPath $ simplifyRuleLhs rule
162166

163167
simplifyClaimRule
164168
:: forall simplifier

kore/src/Kore/Step/RulePattern.hs

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -551,6 +551,10 @@ instance From (RewriteRule variable) Attribute.PriorityAttributes where
551551
instance From (RewriteRule variable) Attribute.HeatCool where
552552
from = from @(RulePattern _) . getRewriteRule
553553

554+
instance TopBottom (RewriteRule variable) where
555+
isTop _ = False
556+
isBottom _ = False
557+
554558
{- | Implication-based pattern.
555559
-}
556560
newtype ImplicationRule variable =

kore/src/Kore/Step/Simplification/And.hs

Lines changed: 6 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -143,7 +143,7 @@ simplify
143143
-> simplifier (OrPattern variable)
144144
simplify notSimplifier sideCondition orPatterns =
145145
OrPattern.observeAllT $ do
146-
patterns <- traverse scatter orPatterns
146+
patterns <- MultiAnd.traverse scatter orPatterns
147147
makeEvaluate notSimplifier sideCondition patterns
148148

149149
{- | 'makeEvaluate' simplifies a 'MultiAnd' of 'Pattern's.
@@ -179,7 +179,11 @@ makeEvaluateNonBool notSimplifier sideCondition patterns = do
179179
let (term1, condition1) = Pattern.splitTerm pattern1
180180
unified <- termAnd notSimplifier term1 term2
181181
pure (Pattern.andCondition unified condition1)
182-
unified <- Foldable.foldlM unify Pattern.top (term <$> patterns)
182+
unified <-
183+
Foldable.foldlM
184+
unify
185+
Pattern.top
186+
(term <$> Foldable.toList patterns)
183187
let substitutions =
184188
Pattern.substitution unified
185189
<> foldMap Pattern.substitution patterns

kore/src/Kore/Step/Simplification/Not.hs

Lines changed: 7 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -111,7 +111,8 @@ simplifyEvaluated
111111
simplifyEvaluated sideCondition simplified =
112112
OrPattern.observeAllT $ do
113113
let not' = Not { notChild = simplified, notSort = () }
114-
andPattern <- scatterAnd (makeEvaluateNot <$> distributeNot not')
114+
andPattern <-
115+
scatterAnd (MultiAnd.map makeEvaluateNot (distributeNot not'))
115116
mkMultiAndPattern sideCondition andPattern
116117

117118
simplifyEvaluatedPredicate
@@ -122,7 +123,11 @@ simplifyEvaluatedPredicate notChild =
122123
OrCondition.observeAllT $ do
123124
let not' = Not { notChild = notChild, notSort = () }
124125
andPredicate <-
125-
scatterAnd (makeEvaluateNotPredicate <$> distributeNot not')
126+
scatterAnd
127+
( MultiAnd.map
128+
makeEvaluateNotPredicate
129+
(distributeNot not')
130+
)
126131
mkMultiAndPredicate andPredicate
127132

128133
{-|'makeEvaluate' simplifies a 'Not' pattern given its 'Pattern'

kore/src/Kore/Step/Simplification/TermLike.hs

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -340,7 +340,9 @@ simplify sideCondition = \termLike ->
340340
AndF andF -> do
341341
let conjuncts = foldMap MultiAnd.fromTermLike andF
342342
And.simplify Not.notSimplifier sideCondition
343-
=<< simplifyChildren conjuncts
343+
=<< MultiAnd.traverse
344+
(simplifyTermLike sideCondition)
345+
conjuncts
344346
ApplySymbolF applySymbolF ->
345347
Application.simplify sideCondition
346348
=<< simplifyChildren applySymbolF

kore/test/Test/Kore/Internal/MultiAnd.hs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -7,6 +7,7 @@ import Prelude.Kore
77

88
import Test.Tasty
99

10+
import qualified Data.Foldable as Foldable
1011
import qualified Generics.SOP as SOP
1112
import qualified GHC.Generics as GHC
1213

@@ -72,7 +73,7 @@ hasPatterns actual expected =
7273
testCase "hasPattern"
7374
(assertEqual ""
7475
expected
75-
(MultiAnd.extractPatterns actual)
76+
(Foldable.toList actual)
7677
)
7778

7879
assertIsTop :: Bool -> MultiAnd TestTopBottom -> TestTree

kore/test/Test/Kore/Step/Rule/Simplify.hs

Lines changed: 3 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -28,9 +28,6 @@ import Kore.Internal.Condition
2828
( Condition
2929
)
3030
import qualified Kore.Internal.Condition as Condition
31-
import qualified Kore.Internal.MultiAnd as MultiAnd
32-
( extractPatterns
33-
)
3431
import qualified Kore.Internal.OrPattern as OrPattern
3532
import qualified Kore.Internal.Pattern as Pattern
3633
import Kore.Internal.Predicate
@@ -339,7 +336,7 @@ runSimplifyRuleNoSMT
339336
=> rule
340337
-> IO [rule]
341338
runSimplifyRuleNoSMT rule =
342-
fmap MultiAnd.extractPatterns
339+
fmap Foldable.toList
343340
$ runNoSMT
344341
$ runSimplifier Mock.env $ do
345342
SMT.All.declare Mock.smtDeclarations
@@ -350,7 +347,7 @@ runSimplifyRule
350347
=> rule
351348
-> IO [rule]
352349
runSimplifyRule rule =
353-
fmap MultiAnd.extractPatterns
350+
fmap Foldable.toList
354351
$ runSMT (pure ())
355352
$ runSimplifier Mock.env $ do
356353
SMT.All.declare Mock.smtDeclarations
@@ -423,7 +420,7 @@ test_simplifyClaimRule =
423420
-- Test simplifyClaimRule through the OnePathClaim instance.
424421
testCase name $ do
425422
actual <- run $ simplifyRuleLhs input
426-
assertEqual "" expect (MultiAnd.extractPatterns actual)
423+
assertEqual "" expect (Foldable.toList actual)
427424
where
428425
run =
429426
runSMT (pure ())

0 commit comments

Comments
 (0)