Skip to content

Commit 190dca9

Browse files
committed
Remove DerivePar and DeriveSeq
1 parent 9ff0685 commit 190dca9

File tree

6 files changed

+37
-143
lines changed

6 files changed

+37
-143
lines changed

kore/src/Kore/Log/DebugProofState.hs

Lines changed: 2 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -9,10 +9,8 @@ module Kore.Log.DebugProofState
99

1010
import Prelude.Kore
1111

12-
import Kore.Rewriting.RewritingVariable
1312
import Kore.Step.RulePattern
1413
( ReachabilityRule (..)
15-
, RewriteRule (..)
1614
)
1715
import Kore.Strategies.ProofState
1816
( Prim (..)
@@ -27,7 +25,7 @@ import qualified Pretty
2725
data DebugProofState =
2826
DebugProofState
2927
{ proofState :: ProofState ReachabilityRule
30-
, transition :: Prim (RewriteRule RewritingVariableName)
28+
, transition :: Prim
3129
, result :: Maybe (ProofState ReachabilityRule)
3230
}
3331
deriving (Show)
@@ -44,14 +42,10 @@ instance Pretty DebugProofState where
4442
[ "Reached proof state with the following configuration:"
4543
, Pretty.indent 4 (pretty proofState)
4644
, "On which the following transition applies:"
47-
, Pretty.indent 4 (prettyTransition transition)
45+
, Pretty.indent 4 (pretty transition)
4846
, "Resulting in:"
4947
, Pretty.indent 4 (maybe "Terminal state." pretty result)
5048
]
51-
where
52-
prettyTransition (DeriveSeq _) = "Transition DeriveSeq."
53-
prettyTransition (DerivePar _) = "Transition DerivePar."
54-
prettyTransition prim = Pretty.pretty prim
5549

5650
instance Entry DebugProofState where
5751
entrySeverity _ = Debug

kore/src/Kore/Strategies/Goal.hs

Lines changed: 22 additions & 62 deletions
Original file line numberDiff line numberDiff line change
@@ -150,8 +150,7 @@ import Kore.Step.Transition
150150
)
151151
import qualified Kore.Step.Transition as Transition
152152
import Kore.Strategies.ProofState hiding
153-
( Prim
154-
, proofState
153+
( proofState
155154
)
156155
import qualified Kore.Strategies.ProofState as ProofState
157156
import Kore.Strategies.Rule
@@ -190,8 +189,6 @@ proven
190189
-> Bool
191190
proven = Foldable.null . unprovenNodes
192191

193-
type Prim goal = ProofState.Prim (Rule goal)
194-
195192
class Goal goal where
196193
goalToRule :: goal -> Rule goal
197194
default goalToRule
@@ -203,7 +200,7 @@ class Goal goal where
203200
:: goal
204201
-> [goal]
205202
-> [Rule goal]
206-
-> Stream (Strategy (Prim goal))
203+
-> Stream (Strategy Prim)
207204

208205
isTriviallyValid :: goal -> Bool
209206

@@ -468,18 +465,16 @@ instance Goal ReachabilityRule where
468465
:: ReachabilityRule
469466
-> [ReachabilityRule]
470467
-> [Rule ReachabilityRule]
471-
-> Stream (Strategy (Prim ReachabilityRule))
468+
-> Stream (Strategy Prim)
472469
strategy goal claims axioms =
473470
case goal of
474471
OnePath rule ->
475-
reachabilityOnePathStrategy
476-
$ strategy
472+
strategy
477473
rule
478474
(mapMaybe maybeOnePath claims)
479475
(fmap ruleReachabilityToRuleOnePath axioms)
480476
AllPath rule ->
481-
reachabilityAllPathStrategy
482-
$ strategy
477+
strategy
483478
rule
484479
(mapMaybe maybeAllPath claims)
485480
(fmap ruleReachabilityToRuleAllPath axioms)
@@ -511,24 +506,6 @@ maybeAllPath :: ReachabilityRule -> Maybe AllPathRule
511506
maybeAllPath (AllPath rule) = Just rule
512507
maybeAllPath _ = Nothing
513508

514-
reachabilityOnePathStrategy
515-
:: Functor t
516-
=> t (Strategy (Prim OnePathRule))
517-
-> t (Strategy (Prim ReachabilityRule))
518-
reachabilityOnePathStrategy strategy' =
519-
(fmap . fmap . fmap)
520-
ruleOnePathToRuleReachability
521-
strategy'
522-
523-
reachabilityAllPathStrategy
524-
:: Functor t
525-
=> t (Strategy (Prim AllPathRule))
526-
-> t (Strategy (Prim ReachabilityRule))
527-
reachabilityAllPathStrategy strategy' =
528-
(fmap . fmap . fmap)
529-
ruleAllPathToRuleReachability
530-
strategy'
531-
532509
-- The functions below are easier to read coercions between
533510
-- the newtypes over 'RewriteRule VariableName' defined in the
534511
-- instances of 'Goal' as 'Rule's.
@@ -553,7 +530,7 @@ ruleOnePathToRuleReachability
553530
ruleOnePathToRuleReachability = coerce
554531

555532
type TransitionRule m goal =
556-
Prim goal
533+
Prim
557534
-> ProofState goal
558535
-> Strategy.TransitionT (Rule goal) m (ProofState goal)
559536

@@ -567,7 +544,7 @@ transitionRule
567544
transitionRule claims axiomGroups = transitionRuleWorker
568545
where
569546
transitionRuleWorker
570-
:: Prim goal
547+
:: Prim
571548
-> ProofState goal
572549
-> Strategy.TransitionT (Rule goal) m (ProofState goal)
573550
transitionRuleWorker CheckProven Proven = empty
@@ -614,6 +591,17 @@ transitionRule claims axiomGroups = transitionRuleWorker
614591
| isTriviallyValid goal =
615592
return Proven
616593

594+
-- TODO (virgil): Wrap the results in GoalRemainder/GoalRewritten here.
595+
--
596+
-- thomas.tuegel: "Here" is in ApplyClaims and ApplyAxioms.
597+
--
598+
-- Note that in most transitions it is obvious what is being transformed
599+
-- into what, e.g. that a `ResetGoal` transition transforms
600+
-- `GoalRewritten` into `Goal`. However, here we're taking a `Goal`
601+
-- and transforming it into `GoalRewritten` and `GoalRemainder` in an
602+
-- opaque way. I think that there's no good reason for wrapping the
603+
-- results in `derivePar` as opposed to here.
604+
617605
transitionRuleWorker ApplyClaims (Goal goal) =
618606
Profile.timeStrategy "applyClaims"
619607
$ applyClaims claims goal
@@ -630,37 +618,9 @@ transitionRule claims axiomGroups = transitionRuleWorker
630618
Profile.timeStrategy "applyAxioms"
631619
$ applyAxioms axiomGroups goal
632620

633-
transitionRuleWorker (DerivePar rules) (Goal goal) =
634-
-- TODO (virgil): Wrap the results in GoalRemainder/GoalRewritten here.
635-
--
636-
-- Note that in most transitions it is obvious what is being transformed
637-
-- into what, e.g. that a `ResetGoal` transition transforms
638-
-- `GoalRewritten` into `Goal`. However, here we're taking a `Goal`
639-
-- and transforming it into `GoalRewritten` and `GoalRemainder` in an
640-
-- opaque way. I think that there's no good reason for wrapping the
641-
-- results in `derivePar` as opposed to here.
642-
Profile.timeStrategy "Goal.DerivePar"
643-
$ derivePar rules goal
644-
transitionRuleWorker (DerivePar rules) (GoalRemainder goal) =
645-
-- TODO (virgil): Wrap the results in GoalRemainder/GoalRewritten here.
646-
-- See above for an explanation.
647-
Profile.timeStrategy "Goal.DeriveParRemainder"
648-
$ derivePar rules goal
649-
650-
transitionRuleWorker (DeriveSeq rules) (Goal goal) =
651-
-- TODO (virgil): Wrap the results in GoalRemainder/GoalRewritten here.
652-
-- See above for an explanation.
653-
Profile.timeStrategy "Goal.DeriveSeq"
654-
$ deriveSeq rules goal
655-
transitionRuleWorker (DeriveSeq rules) (GoalRemainder goal) =
656-
-- TODO (virgil): Wrap the results in GoalRemainder/GoalRewritten here.
657-
-- See above for an explanation.
658-
Profile.timeStrategy "Goal.DeriveSeqRemainder"
659-
$ deriveSeq rules goal
660-
661621
transitionRuleWorker _ state = return state
662622

663-
onePathFirstStep :: Strategy (Prim goal)
623+
onePathFirstStep :: Strategy Prim
664624
onePathFirstStep =
665625
(Strategy.sequence . map Strategy.apply)
666626
[ CheckProven
@@ -675,7 +635,7 @@ onePathFirstStep =
675635
, TriviallyValid
676636
]
677637

678-
onePathFollowupStep :: Strategy (Prim goal)
638+
onePathFollowupStep :: Strategy Prim
679639
onePathFollowupStep =
680640
(Strategy.sequence . map Strategy.apply)
681641
[ CheckProven
@@ -691,7 +651,7 @@ onePathFollowupStep =
691651
, TriviallyValid
692652
]
693653

694-
allPathFirstStep :: Strategy (Prim AllPathRule)
654+
allPathFirstStep :: Strategy Prim
695655
allPathFirstStep =
696656
(Strategy.sequence . map Strategy.apply)
697657
[ CheckProven
@@ -706,7 +666,7 @@ allPathFirstStep =
706666
, TriviallyValid
707667
]
708668

709-
allPathFollowupStep :: Strategy (Prim AllPathRule)
669+
allPathFollowupStep :: Strategy Prim
710670
allPathFollowupStep =
711671
(Strategy.sequence . map Strategy.apply)
712672
[ CheckProven

kore/src/Kore/Strategies/ProofState.hs

Lines changed: 4 additions & 27 deletions
Original file line numberDiff line numberDiff line change
@@ -27,7 +27,7 @@ import qualified Pretty
2727

2828
{- | The primitive transitions of the reachability proof strategy.
2929
-}
30-
data Prim rule
30+
data Prim
3131
= CheckProven
3232
-- ^ End execution on this branch if the state is 'Proven'.
3333
| CheckGoalRemainder
@@ -39,26 +39,11 @@ data Prim rule
3939
| Simplify
4040
| CheckImplication
4141
| TriviallyValid
42-
| DerivePar [rule]
43-
| DeriveSeq [rule]
4442
| ApplyClaims
4543
| ApplyAxioms
46-
deriving (Show, Functor)
47-
48-
instance Filterable Prim where
49-
mapMaybe _ CheckProven = CheckProven
50-
mapMaybe _ CheckGoalRemainder = CheckGoalRemainder
51-
mapMaybe _ CheckGoalStuck = CheckGoalStuck
52-
mapMaybe _ ResetGoal = ResetGoal
53-
mapMaybe _ Simplify = Simplify
54-
mapMaybe _ CheckImplication = CheckImplication
55-
mapMaybe _ TriviallyValid = TriviallyValid
56-
mapMaybe _ ApplyClaims = ApplyClaims
57-
mapMaybe _ ApplyAxioms = ApplyAxioms
58-
mapMaybe f (DerivePar rules) = DerivePar (mapMaybe f rules)
59-
mapMaybe f (DeriveSeq rules) = DeriveSeq (mapMaybe f rules)
60-
61-
instance Unparse goal => Pretty (Prim goal) where
44+
deriving (Show)
45+
46+
instance Pretty Prim where
6247
pretty CheckProven = "Transition CheckProven."
6348
pretty CheckGoalRemainder = "Transition CheckGoalRemainder."
6449
pretty CheckGoalStuck = "Transition CheckGoalStuck."
@@ -68,14 +53,6 @@ instance Unparse goal => Pretty (Prim goal) where
6853
pretty TriviallyValid = "Transition TriviallyValid."
6954
pretty ApplyClaims = "apply claims"
7055
pretty ApplyAxioms = "apply axioms"
71-
pretty (DerivePar rules) =
72-
Pretty.vsep
73-
$ ["Transition DerivePar with rules:"]
74-
<> fmap (Pretty.indent 4 . unparse) rules
75-
pretty (DeriveSeq rules) =
76-
Pretty.vsep
77-
$ ["Transition DeriveSeq with rules:"]
78-
<> fmap (Pretty.indent 4 . unparse) rules
7956

8057
{- | The state of the reachability proof strategy for @goal@.
8158
-}

kore/src/Kore/Strategies/Verification.hs

Lines changed: 7 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -295,7 +295,7 @@ verifyClaim
295295
& lift
296296

297297
modifiedTransitionRule
298-
:: Prim ReachabilityRule
298+
:: Prim
299299
-> CommonProofState
300300
-> TransitionT (Rule ReachabilityRule) (Verifier simplifier)
301301
CommonProofState
@@ -338,15 +338,15 @@ verifyClaimStep target claims axioms executionGraph node =
338338
destination = getDestination target
339339
axiomGroups = groupSortOn Attribute.Axiom.getPriorityOfAxiom axioms
340340

341-
strategy' :: Strategy (Prim ReachabilityRule)
341+
strategy' :: Strategy Prim
342342
strategy'
343343
| isRoot = firstStep
344344
| otherwise = followupStep
345345

346-
firstStep :: Strategy (Prim ReachabilityRule)
346+
firstStep :: Strategy Prim
347347
firstStep = strategy target claims axioms Stream.!! 0
348348

349-
followupStep :: Strategy (Prim ReachabilityRule)
349+
followupStep :: Strategy Prim
350350
followupStep = strategy target claims axioms Stream.!! 1
351351

352352
ExecutionGraph { root } = executionGraph
@@ -361,7 +361,7 @@ transitionRule'
361361
-> [[Rule ReachabilityRule]]
362362
-> ReachabilityRule
363363
-> RHS VariableName
364-
-> Prim ReachabilityRule
364+
-> Prim
365365
-> CommonProofState
366366
-> TransitionT (Rule ReachabilityRule) simplifier CommonProofState
367367
transitionRule' claims axiomGroups goal _ prim state = do
@@ -405,10 +405,6 @@ logTransitionRule rule prim proofState =
405405
whileSimplify goal $ rule prim proofState
406406
Prim.CheckImplication ->
407407
whileCheckImplication goal $ rule prim proofState
408-
(Prim.DeriveSeq rules) ->
409-
whileDeriveSeq rules goal $ rule prim proofState
410-
(Prim.DerivePar rules) ->
411-
whileDerivePar rules goal $ rule prim proofState
412408
_ ->
413409
rule prim proofState
414410

@@ -417,7 +413,7 @@ debugProofStateBracket
417413
. MonadLog monad
418414
=> ProofState ReachabilityRule
419415
-- ^ current proof state
420-
-> Prim ReachabilityRule
416+
-> Prim
421417
-- ^ transition
422418
-> monad (ProofState ReachabilityRule)
423419
-- ^ action to be computed
@@ -441,7 +437,7 @@ debugProofStateFinal
441437
=> MonadLog monad
442438
=> ProofState ReachabilityRule
443439
-- ^ current proof state
444-
-> Prim ReachabilityRule
440+
-> Prim
445441
-- ^ transition
446442
-> monad (ProofState ReachabilityRule)
447443
debugProofStateFinal proofState (coerce -> transition) = do

kore/test/Test/Kore/Strategies/AllPath/AllPath.hs

Lines changed: 1 addition & 30 deletions
Original file line numberDiff line numberDiff line change
@@ -4,7 +4,6 @@ module Test.Kore.Strategies.AllPath.AllPath
44
, test_transitionRule_CheckGoalRem
55
, test_transitionRule_CheckImplication
66
, test_transitionRule_TriviallyValid
7-
, test_transitionRule_DerivePar
87
, test_transitionRule_ApplyClaims
98
, test_transitionRule_ApplyAxioms
109
, test_runStrategy
@@ -175,34 +174,6 @@ test_transitionRule_TriviallyValid =
175174
becomesProven :: HasCallStack => ProofState -> TestTree
176175
becomesProven state = run state `equals_` [(ProofState.Proven, mempty)]
177176

178-
test_transitionRule_DerivePar :: [TestTree]
179-
test_transitionRule_DerivePar =
180-
[ unmodified ProofState.Proven
181-
, unmodified (ProofState.GoalRewritten (A, B))
182-
, [Rule (A, C)]
183-
`derives`
184-
[ (ProofState.Goal (C, C), Seq.singleton $ Rule (A, C))
185-
, (ProofState.GoalRemainder (Bot, C), mempty)
186-
]
187-
, fmap Rule [(A, B), (B, C)]
188-
`derives`
189-
[ (ProofState.Goal (B , C), Seq.singleton $ Rule (A, B))
190-
, (ProofState.GoalRemainder (Bot, C), mempty)
191-
]
192-
]
193-
where
194-
run rules = runTransitionRule [] [] (ProofState.DerivePar rules)
195-
unmodified :: HasCallStack => ProofState -> TestTree
196-
unmodified state = run [Rule (A, B)] state `equals_` [(state, mempty)]
197-
derives
198-
:: HasCallStack
199-
=> [Goal.Rule Goal]
200-
-- ^ rules to apply in parallel
201-
-> [(ProofState, Seq (Goal.Rule Goal))]
202-
-- ^ transitions
203-
-> TestTree
204-
derives rules = equals_ (run rules $ ProofState.GoalRemainder (A, C))
205-
206177
test_transitionRule_ApplyClaims :: [TestTree]
207178
test_transitionRule_ApplyClaims =
208179
[ unmodified ProofState.Proven
@@ -369,7 +340,7 @@ type Goal = (K, K)
369340

370341
type ProofState = ProofState.ProofState Goal
371342

372-
type Prim = Goal.Prim Goal
343+
type Prim = Goal.Prim
373344

374345
newtype instance Goal.Rule Goal =
375346
Rule { unRule :: (K, K) }

0 commit comments

Comments
 (0)