Skip to content

Commit f2aad03

Browse files
authored
#3143 rewrite graph traversal + output unexplored leaves (#3168)
* Rewrite of graph traversal used by Kore.Exec and Kore.Reachability.Prove New traversal models required functionality in data types rather than using exceptions and monad stack layers to add functionality. The `graphTraversal` function operates with a list of "steps" (sequences of "instructions") that take a configuration to a result containing new configurations. The traversal is parameterised with a specific transition function `([Step instr],config) -> m (TransitionResult ([Step instr],config))` which interprets step results. `TransitionResult` can indicate to continue with one (`Continuing`) or more (`Branch`) new configurations, or that the configuration is final, stuck, or should be stopped. One reason to stop is when the list of steps runs empty, other reasons could be to stop execuction on the application of certain rules. The transition function can be constructed from one that operates on the primitive instructions, together with an interpretation function that differs depending on the use case (proving or executing). * Introduce named type for ([Step instr], config) (TState), document behaviour better * refactor Kore.Exec.exec for readability * update ghc923 nix configuration Command > nix run .#update-cabal-ghc9 * Overall documentation attached to graphTraversal * adapt Simplifier imports
1 parent 3c37aab commit f2aad03

File tree

11 files changed

+752
-435
lines changed

11 files changed

+752
-435
lines changed

flake.lock

Lines changed: 67 additions & 0 deletions
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

kore/kore.cabal

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -313,6 +313,7 @@ library
313313
Kore.Equation.Validate
314314
Kore.Error
315315
Kore.Exec
316+
Kore.Exec.GraphTraversal
316317
Kore.IndexedModule.Error
317318
Kore.IndexedModule.IndexedModule
318319
Kore.IndexedModule.MetadataTools

kore/src/Kore/Exec.hs

Lines changed: 71 additions & 41 deletions
Original file line numberDiff line numberDiff line change
@@ -40,8 +40,9 @@ import Control.Monad.Trans.Maybe (runMaybeT)
4040
import Data.Coerce (
4141
coerce,
4242
)
43-
import Data.Limit (
43+
import Data.Limit as Limit (
4444
Limit (..),
45+
takeWithin,
4546
)
4647
import Data.List (
4748
tails,
@@ -69,6 +70,7 @@ import Kore.Equation qualified as Equation (
6970
argument,
7071
requires,
7172
)
73+
import Kore.Exec.GraphTraversal qualified as GraphTraversal
7274
import Kore.IndexedModule.IndexedModule (
7375
IndexedModule (..),
7476
VerifiedModule,
@@ -168,7 +170,6 @@ import Kore.Rewrite.Search (
168170
searchGraph,
169171
)
170172
import Kore.Rewrite.Search qualified as Search
171-
import Kore.Rewrite.Strategy (FinalNodeType (Leaf))
172173
import Kore.Rewrite.Strategy qualified as Strategy
173174
import Kore.Rewrite.Transition (
174175
runTransitionT,
@@ -278,44 +279,30 @@ exec
278279
, overloadGraph
279280
, metadataTools
280281
, verifiedModule
281-
, rewrites
282+
, rewrites = Initialized{rewriteRules}
282283
, equations
283284
}
284-
strategy
285+
execMode
285286
(mkRewritingTerm -> initialTerm) =
286287
evalSimplifier simplifierx verifiedModule' sortGraph overloadGraph metadataTools equations $ do
287-
let Initialized{rewriteRules} = rewrites
288288
finals <-
289-
getFinalConfigsOf $ do
290-
initialConfig <-
291-
Pattern.simplify
292-
(Pattern.fromTermLike initialTerm)
293-
>>= Logic.scatter
294-
let updateQueue = \as ->
295-
Strategy.unfoldDepthFirst as
296-
>=> lift
297-
. Strategy.applyBreadthLimit
298-
breadthLimit
299-
dropStrategy
300-
rewriteGroups = groupRewritesByPriority rewriteRules
301-
transit instr config =
302-
Strategy.transitionRule
303-
( transitionRule rewriteGroups strategy
304-
& profTransitionRule
305-
& trackExecDepth
306-
)
307-
instr
308-
config
309-
& runTransitionT
310-
& fmap (map fst)
311-
& lift
312-
Strategy.leavesM
313-
Leaf
314-
updateQueue
315-
(unfoldTransition transit)
316-
( limitedExecutionStrategy depthLimit
317-
, (ExecDepth 0, Start initialConfig)
318-
)
289+
GraphTraversal.graphTraversal
290+
Strategy.Leaf
291+
Strategy.DepthFirst
292+
breadthLimit
293+
transit
294+
Limit.Unlimited
295+
execStrategy
296+
(ExecDepth 0, Start $ Pattern.fromTermLike initialTerm)
297+
>>= \case
298+
GraphTraversal.Ended results -> pure results
299+
GraphTraversal.GotStuck n results -> do
300+
when (n == 0 && any (notStuck . snd) results) $
301+
forM_ depthLimit warnDepthLimitExceeded
302+
pure results
303+
GraphTraversal.Aborted _ results -> do
304+
pure results
305+
319306
let (depths, finalConfigs) = unzip finals
320307
infoExecDepth (maximum (ExecDepth 0 : depths))
321308
let finalConfigs' =
@@ -328,17 +315,60 @@ exec
328315
& sameTermLikeSort initialSort
329316
return (exitCode, finalTerm)
330317
where
331-
dropStrategy = snd
332-
getFinalConfigsOf act = observeAllT $ fmap snd act
333318
verifiedModule' =
334319
IndexedModule.mapAliasPatterns
335320
-- TODO (thomas.tuegel): Move this into Kore.Builtin
336321
(Builtin.internalize metadataTools)
337322
verifiedModule
338323
initialSort = termLikeSort initialTerm
339-
unfoldTransition transit (instrs, config) = do
340-
when (null instrs) $ forM_ depthLimit warnDepthLimitExceeded
341-
Strategy.unfoldTransition transit (instrs, config)
324+
325+
execStrategy :: [GraphTraversal.Step Prim]
326+
execStrategy =
327+
Limit.takeWithin depthLimit $
328+
[Begin, Simplify, Rewrite, Simplify] :
329+
repeat [Begin, Rewrite, Simplify]
330+
331+
transit ::
332+
GraphTraversal.TState
333+
Prim
334+
(ExecDepth, ProgramState (Pattern RewritingVariableName)) ->
335+
Simplifier.Simplifier
336+
( GraphTraversal.TransitionResult
337+
( GraphTraversal.TState
338+
Prim
339+
(ExecDepth, ProgramState (Pattern RewritingVariableName))
340+
)
341+
)
342+
transit =
343+
GraphTraversal.simpleTransition
344+
( trackExecDepth . profTransitionRule $
345+
transitionRule (groupRewritesByPriority rewriteRules) execMode
346+
)
347+
toTransitionResult
348+
349+
toTransitionResult ::
350+
(ExecDepth, ProgramState p) ->
351+
[(ExecDepth, ProgramState p)] ->
352+
( GraphTraversal.TransitionResult
353+
(ExecDepth, ProgramState p)
354+
)
355+
toTransitionResult prior [] =
356+
case snd prior of
357+
Start _ -> GraphTraversal.Stopped [prior]
358+
Rewritten _ -> GraphTraversal.Stopped [prior]
359+
Remaining _ -> GraphTraversal.Stuck prior
360+
Kore.Rewrite.Bottom -> GraphTraversal.Stuck prior
361+
toTransitionResult _prior [next] =
362+
case snd next of
363+
Start _ -> GraphTraversal.Continuing next
364+
Rewritten _ -> GraphTraversal.Continuing next
365+
Remaining _ -> GraphTraversal.Stuck next
366+
Kore.Rewrite.Bottom -> GraphTraversal.Stuck next
367+
toTransitionResult prior (s : ss) =
368+
GraphTraversal.Branch prior (s :| ss)
369+
370+
notStuck :: ProgramState a -> Bool
371+
notStuck = isJust . extractProgramState
342372

343373
-- | Modify a 'TransitionRule' to track the depth of the execution graph.
344374
trackExecDepth ::
@@ -494,7 +524,7 @@ prove ::
494524
Limit Natural ->
495525
Limit Natural ->
496526
Natural ->
497-
FinalNodeType ->
527+
Strategy.FinalNodeType ->
498528
-- | The main module
499529
VerifiedModule StepperAttributes ->
500530
-- | The spec module

0 commit comments

Comments
 (0)