Skip to content

Commit c427819

Browse files
authored
Keep table of term replacements in SideCondition, use in term simplifier (#2315)
1 parent 6bb84ec commit c427819

File tree

19 files changed

+615
-376
lines changed

19 files changed

+615
-376
lines changed

kore/src/Debug.hs

Lines changed: 21 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,10 +1,10 @@
1-
{-# LANGUAGE UndecidableInstances #-}
2-
31
{- |
42
Copyright : (c) Runtime Verification, 2019
53
License : NCSA
64
75
-}
6+
{-# LANGUAGE Strict #-}
7+
{-# LANGUAGE UndecidableInstances #-}
88

99
module Debug
1010
(
@@ -37,6 +37,10 @@ import Data.Hashable
3737
( Hashed
3838
, unhashed
3939
)
40+
import Data.HashMap.Strict
41+
( HashMap
42+
)
43+
import qualified Data.HashMap.Strict as HashMap
4044
import Data.Int
4145
import Data.Map.Strict
4246
( Map
@@ -332,6 +336,11 @@ instance (Debug k, Debug a) => Debug (Map.Map k a) where
332336
(parens (precOut >= 10) . Pretty.sep)
333337
["Data.Map.Strict.fromList", debug (Map.toList as)]
334338

339+
instance (Debug k, Debug a) => Debug (HashMap k a) where
340+
debugPrec as precOut =
341+
(parens (precOut >= 10) . Pretty.sep)
342+
["Data.HashMap.Strict.fromList", debug (HashMap.toList as)]
343+
335344
instance Debug a => Debug (Set a) where
336345
debugPrec as precOut =
337346
(parens (precOut >= 10) . Pretty.sep)
@@ -592,6 +601,16 @@ instance
592601
wrapFromList diff' precOut =
593602
parens (precOut >= 10) $ "Data.Map.Strict.fromList" <+> diff' 10
594603

604+
instance
605+
( Debug key, Debug value, Diff key, Diff value )
606+
=> Diff (HashMap key value)
607+
where
608+
diffPrec as bs =
609+
fmap wrapFromList $ diffPrec (HashMap.toList as) (HashMap.toList bs)
610+
where
611+
wrapFromList diff' precOut =
612+
parens (precOut >= 10) $ "Data.HashMap.Strict.fromList" <+> diff' 10
613+
595614
instance (Debug a, Debug b, Diff a, Diff b) => Diff (a, b)
596615

597616
instance (Debug a, Diff a) => Diff (Set a) where

kore/src/Kore/Debug.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,3 @@
1-
{-# OPTIONS_GHC -Wno-unused-top-binds #-}
2-
31
{- |
42
Copyright : (c) Runtime Verification, 2018
53
License : NCSA
@@ -41,6 +39,8 @@ It also works for test error messages:
4139
4240
Enjoy.
4341
-}
42+
{-# OPTIONS_GHC -Wno-unused-top-binds #-}
43+
{-# LANGUAGE Strict #-}
4444

4545
module Kore.Debug
4646
(

kore/src/Kore/Equation/Simplification.hs

Lines changed: 2 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -37,9 +37,6 @@ import Kore.Internal.Pattern
3737
)
3838
import qualified Kore.Internal.Pattern as Pattern
3939
import qualified Kore.Internal.Predicate as Predicate
40-
import qualified Kore.Internal.SideCondition as SideCondition
41-
( top
42-
)
4340
import qualified Kore.Internal.Substitution as Substitution
4441
import qualified Kore.Internal.TermLike as TermLike
4542
import qualified Kore.Step.Simplification.Pattern as Pattern
@@ -132,6 +129,6 @@ simplifyPattern
132129
:: (InternalVariable variable, MonadSimplify simplifier)
133130
=> Pattern variable
134131
-> simplifier (OrPattern variable)
135-
simplifyPattern patt =
132+
simplifyPattern =
136133
Simplifier.localSimplifierAxioms (const mempty)
137-
$ Pattern.simplify SideCondition.top patt
134+
. Pattern.simplify

kore/src/Kore/Exec.hs

Lines changed: 5 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -8,6 +8,8 @@ Portability : portable
88
99
Expose concrete execution as a library
1010
-}
11+
{-# LANGUAGE Strict #-}
12+
1113
module Kore.Exec
1214
( exec
1315
, mergeAllRules
@@ -92,8 +94,7 @@ import Kore.Internal.Predicate
9294
, makeMultipleOrPredicate
9395
)
9496
import qualified Kore.Internal.SideCondition as SideCondition
95-
( top
96-
, topTODO
97+
( topTODO
9798
)
9899
import Kore.Internal.TermLike
99100
import Kore.Log.ErrorRewriteLoop
@@ -224,7 +225,7 @@ exec depthLimit breadthLimit verifiedModule strategy initialTerm =
224225
finals <-
225226
getFinalConfigsOf $ do
226227
initialConfig <-
227-
Pattern.simplify SideCondition.top
228+
Pattern.simplify
228229
(Pattern.fromTermLike initialTerm)
229230
>>= Logic.scatter
230231
let
@@ -372,7 +373,7 @@ search depthLimit breadthLimit verifiedModule termLike searchPattern searchConfi
372373
initialized <- initializeAndSimplify verifiedModule
373374
let Initialized { rewriteRules } = initialized
374375
simplifiedPatterns <-
375-
Pattern.simplify SideCondition.top
376+
Pattern.simplify
376377
$ Pattern.fromTermLike termLike
377378
let
378379
initialPattern =

0 commit comments

Comments
 (0)