Skip to content

Commit fcfc2d5

Browse files
MirceaSrv-jenkins
andauthored
Remove the EvaluatedF marker from TermLike (#2469)
* removed the EvaluatedF marker from TermLike * removed some redundant imports Co-authored-by: rv-jenkins <admin@runtimeverification.com>
1 parent 1f61e5a commit fcfc2d5

File tree

17 files changed

+6
-482
lines changed

17 files changed

+6
-482
lines changed

kore/src/Kore/Builtin/Builtin.hs

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -311,9 +311,8 @@ applicationEvaluator impl =
311311
(TermLike variable)
312312
-> simplifier (AttemptedAxiom variable)
313313
evaluator sideCondition (_ :< app) = do
314-
let app' = fmap TermLike.removeEvaluated app
315314
getAttemptedAxiom
316-
(impl sideCondition app' >>= appliedFunction)
315+
(impl sideCondition app >>= appliedFunction)
317316

318317
{- | Run a parser on a verified domain value.
319318

kore/src/Kore/Builtin/External.hs

Lines changed: 0 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -12,7 +12,6 @@ module Kore.Builtin.External
1212

1313
import Prelude.Kore
1414

15-
import qualified Control.Comonad.Trans.Cofree as Cofree
1615
import Data.Functor.Const
1716
( Const (..)
1817
)
@@ -123,10 +122,6 @@ externalize =
123122
TopF topF -> Syntax.TopF topF
124123
VariableF variableF -> Syntax.VariableF variableF
125124
InhabitantF inhabitantF -> Syntax.InhabitantF inhabitantF
126-
EvaluatedF evaluatedF ->
127-
Cofree.tailF
128-
$ worker
129-
$ getEvaluated evaluatedF
130125
EndiannessF endiannessF ->
131126
Syntax.ApplicationF
132127
$ mapHead Symbol.toSymbolOrAlias

kore/src/Kore/Internal/SideCondition.hs

Lines changed: 1 addition & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -449,10 +449,7 @@ simplifyConjunctionByAssumption (toList -> andPredicates) =
449449

450450
size :: TermLike variable -> Int
451451
size =
452-
Recursive.fold $ \(_ :< termLikeF) ->
453-
case termLikeF of
454-
TermLike.EvaluatedF evaluated -> TermLike.getEvaluated evaluated
455-
_ -> 1 + sum termLikeF
452+
Recursive.fold $ \(_ :< termLikeF) -> 1 + sum termLikeF
456453

457454
predSize :: Predicate variable -> Int
458455
predSize =

kore/src/Kore/Internal/TermLike.hs

Lines changed: 0 additions & 25 deletions
Original file line numberDiff line numberDiff line change
@@ -10,7 +10,6 @@ License : NCSA
1010
module Kore.Internal.TermLike
1111
( TermLikeF (..)
1212
, TermLike (..)
13-
, Evaluated (..)
1413
, extractAttributes
1514
, isSimplified
1615
, isSimplifiedSomeCondition
@@ -27,7 +26,6 @@ module Kore.Internal.TermLike
2726
, hasConstructorLikeTop
2827
, freeVariables
2928
, refreshVariables
30-
, removeEvaluated
3129
, termLikeSort
3230
, hasFreeVariable
3331
, withoutFreeVariable
@@ -89,7 +87,6 @@ module Kore.Internal.TermLike
8987
, mkSort
9088
, mkSortVariable
9189
, mkInhabitant
92-
, mkEvaluated
9390
, mkEndianness
9491
, mkSignedness
9592
-- * Predicate constructors
@@ -144,7 +141,6 @@ module Kore.Internal.TermLike
144141
, pattern ElemVar_
145142
, pattern SetVar_
146143
, pattern StringLiteral_
147-
, pattern Evaluated_
148144
, pattern Endianness_
149145
, pattern Signedness_
150146
, pattern Inj_
@@ -652,7 +648,6 @@ forceSortPredicate
652648
=
653649
case pattern' of
654650
-- Recurse
655-
EvaluatedF evaluated -> EvaluatedF (Right <$> evaluated)
656651
-- Predicates: Force sort and stop.
657652
BottomF bottom' -> BottomF bottom' { bottomSort = forcedSort }
658653
TopF top' -> TopF top' { topSort = forcedSort }
@@ -791,14 +786,6 @@ forceSorts operandSorts children =
791786
, Pretty.indent 4 (Unparser.arguments children)
792787
]
793788

794-
{- | Remove `Evaluated` if it appears on the top of the `TermLike`.
795-
-}
796-
removeEvaluated :: TermLike variable -> TermLike variable
797-
removeEvaluated termLike@(Recursive.project -> (_ :< termLikeF)) =
798-
case termLikeF of
799-
EvaluatedF (Evaluated e) -> removeEvaluated e
800-
_ -> termLike
801-
802789
{- | Construct an 'Application' pattern.
803790
804791
The result sort of the 'Alias' must be provided. The sorts of arguments
@@ -1460,13 +1447,6 @@ mkInhabitant
14601447
-> TermLike variable
14611448
mkInhabitant = updateCallStack . synthesize . InhabitantF . Inhabitant
14621449

1463-
mkEvaluated
1464-
:: HasCallStack
1465-
=> Ord variable
1466-
=> TermLike variable
1467-
-> TermLike variable
1468-
mkEvaluated = updateCallStack . synthesize . EvaluatedF . Evaluated
1469-
14701450
{- | Construct an 'Endianness' pattern.
14711451
-}
14721452
mkEndianness
@@ -1730,8 +1710,6 @@ pattern SetVar_ :: SetVariable variable -> TermLike variable
17301710

17311711
pattern StringLiteral_ :: Text -> TermLike variable
17321712

1733-
pattern Evaluated_ :: TermLike variable -> TermLike variable
1734-
17351713
pattern And_ andSort andFirst andSecond <-
17361714
(Recursive.project -> _ :< AndF And { andSort, andFirst, andSecond })
17371715

@@ -1880,9 +1858,6 @@ pattern ElemVar_ elemVariable <- Var_ (retract -> Just elemVariable)
18801858
pattern StringLiteral_ str <-
18811859
(Recursive.project -> _ :< StringLiteralF (Const (StringLiteral str)))
18821860

1883-
pattern Evaluated_ child <-
1884-
(Recursive.project -> _ :< EvaluatedF (Evaluated child))
1885-
18861861
pattern Endianness_ :: Endianness -> TermLike child
18871862
pattern Endianness_ endianness <-
18881863
(Recursive.project -> _ :< EndiannessF (Const endianness))

kore/src/Kore/Internal/TermLike/TermLike.hs

Lines changed: 1 addition & 41 deletions
Original file line numberDiff line numberDiff line change
@@ -8,8 +8,7 @@ License : NCSA
88
{-# LANGUAGE UndecidableInstances #-}
99

1010
module Kore.Internal.TermLike.TermLike
11-
( Evaluated (..)
12-
, TermLike (..)
11+
( TermLike (..)
1312
, TermLikeF (..)
1413
, retractKey
1514
, extractAttributes
@@ -120,34 +119,6 @@ import Kore.Variables.Binding
120119
import qualified Pretty
121120
import qualified SQL
122121

123-
{- | @Evaluated@ wraps patterns which are fully evaluated.
124-
125-
Fully-evaluated patterns will not be simplified further because no progress
126-
could be made.
127-
128-
-}
129-
newtype Evaluated child = Evaluated { getEvaluated :: child }
130-
deriving (Eq, Ord, Show)
131-
deriving (Foldable, Functor, Traversable)
132-
deriving (GHC.Generic)
133-
deriving anyclass (Hashable, NFData)
134-
deriving anyclass (SOP.Generic, SOP.HasDatatypeInfo)
135-
deriving anyclass (Debug, Diff)
136-
137-
instance Unparse child => Unparse (Evaluated child) where
138-
unparse evaluated =
139-
Pretty.vsep ["/* evaluated: */", Unparser.unparseGeneric evaluated]
140-
unparse2 evaluated =
141-
Pretty.vsep ["/* evaluated: */", Unparser.unparse2Generic evaluated]
142-
143-
instance Synthetic syn Evaluated where
144-
synthetic = getEvaluated
145-
{-# INLINE synthetic #-}
146-
147-
instance {-# OVERLAPS #-} Synthetic Pattern.Simplified Evaluated where
148-
synthetic = const Pattern.fullySimplified
149-
{-# INLINE synthetic #-}
150-
151122
{- | 'TermLikeF' is the 'Base' functor of internal term-like patterns.
152123
153124
-}
@@ -174,7 +145,6 @@ data TermLikeF variable child
174145
| RewritesF !(Rewrites Sort child)
175146
| TopF !(Top Sort child)
176147
| InhabitantF !(Inhabitant child)
177-
| EvaluatedF !(Evaluated child)
178148
| StringLiteralF !(Const StringLiteral child)
179149
| InternalBoolF !(Const InternalBool child)
180150
| InternalBytesF !(Const InternalBytes child)
@@ -226,7 +196,6 @@ instance
226196
RewritesF rewrites -> synthetic rewrites
227197
TopF top -> synthetic top
228198
InhabitantF inhabitant -> synthetic inhabitant
229-
EvaluatedF evaluated -> synthetic evaluated
230199
StringLiteralF stringLiteral -> synthetic stringLiteral
231200
InternalBoolF internalBool -> synthetic internalBool
232201
InternalBytesF internalBytes -> synthetic internalBytes
@@ -264,7 +233,6 @@ instance Synthetic Sort (TermLikeF variable) where
264233
RewritesF rewrites -> synthetic rewrites
265234
TopF top -> synthetic top
266235
InhabitantF inhabitant -> synthetic inhabitant
267-
EvaluatedF evaluated -> synthetic evaluated
268236
StringLiteralF stringLiteral -> synthetic stringLiteral
269237
InternalBoolF internalBool -> synthetic internalBool
270238
InternalBytesF internalBytes -> synthetic internalBytes
@@ -302,7 +270,6 @@ instance Synthetic Pattern.Functional (TermLikeF variable) where
302270
RewritesF rewrites -> synthetic rewrites
303271
TopF top -> synthetic top
304272
InhabitantF inhabitant -> synthetic inhabitant
305-
EvaluatedF evaluated -> synthetic evaluated
306273
StringLiteralF stringLiteral -> synthetic stringLiteral
307274
InternalBoolF internalBool -> synthetic internalBool
308275
InternalBytesF internalBytes -> synthetic internalBytes
@@ -340,7 +307,6 @@ instance Synthetic Pattern.Function (TermLikeF variable) where
340307
RewritesF rewrites -> synthetic rewrites
341308
TopF top -> synthetic top
342309
InhabitantF inhabitant -> synthetic inhabitant
343-
EvaluatedF evaluated -> synthetic evaluated
344310
StringLiteralF stringLiteral -> synthetic stringLiteral
345311
InternalBoolF internalBool -> synthetic internalBool
346312
InternalBytesF internalBytes -> synthetic internalBytes
@@ -378,7 +344,6 @@ instance Synthetic Pattern.Defined (TermLikeF variable) where
378344
RewritesF rewrites -> synthetic rewrites
379345
TopF top -> synthetic top
380346
InhabitantF inhabitant -> synthetic inhabitant
381-
EvaluatedF evaluated -> synthetic evaluated
382347
StringLiteralF stringLiteral -> synthetic stringLiteral
383348
InternalBoolF internalBool -> synthetic internalBool
384349
InternalBytesF internalBytes -> synthetic internalBytes
@@ -416,7 +381,6 @@ instance Synthetic Pattern.Simplified (TermLikeF variable) where
416381
RewritesF rewrites -> synthetic rewrites
417382
TopF top -> synthetic top
418383
InhabitantF inhabitant -> synthetic inhabitant
419-
EvaluatedF evaluated -> synthetic evaluated
420384
StringLiteralF stringLiteral -> synthetic stringLiteral
421385
InternalBoolF internalBool -> synthetic internalBool
422386
InternalBytesF internalBytes -> synthetic internalBytes
@@ -454,7 +418,6 @@ instance Synthetic Pattern.ConstructorLike (TermLikeF variable) where
454418
RewritesF rewrites -> synthetic rewrites
455419
TopF top -> synthetic top
456420
InhabitantF inhabitant -> synthetic inhabitant
457-
EvaluatedF evaluated -> synthetic evaluated
458421
StringLiteralF stringLiteral -> synthetic stringLiteral
459422
InternalBoolF internalBool -> synthetic internalBool
460423
InternalBytesF internalBytes -> synthetic internalBytes
@@ -752,8 +715,6 @@ instance
752715
TopF Top { topSort } -> locationFromAst topSort
753716
VariableF (Const variable) -> locationFromAst variable
754717
InhabitantF Inhabitant { inhSort } -> locationFromAst inhSort
755-
EvaluatedF Evaluated { getEvaluated } ->
756-
locationFromAst getEvaluated
757718
InjF Inj { injChild } -> locationFromAst injChild
758719
SignednessF (Const signedness) -> locationFromAst signedness
759720
EndiannessF (Const endianness) -> locationFromAst endianness
@@ -821,7 +782,6 @@ traverseVariablesF adj =
821782
InternalSetF setP -> pure (InternalSetF setP)
822783
TopF topP -> pure (TopF topP)
823784
InhabitantF s -> pure (InhabitantF s)
824-
EvaluatedF childP -> pure (EvaluatedF childP)
825785
EndiannessF endianness -> pure (EndiannessF endianness)
826786
SignednessF signedness -> pure (SignednessF signedness)
827787
InjF inj -> pure (InjF inj)

kore/src/Kore/Step/SMT/Translate.hs

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -153,7 +153,6 @@ translatePredicateWith sideCondition translateTerm predicate =
153153
translatePredicatePatternWorker :: p -> Translator variable m SExpr
154154
translatePredicatePatternWorker pat =
155155
case Cofree.tailF (Recursive.project pat) of
156-
EvaluatedF child -> translatePredicatePattern (getEvaluated child)
157156
-- Logical connectives: translate as connectives
158157
AndF and' -> translatePredicateAnd and'
159158
BottomF _ -> return (SMT.bool False)

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

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -390,7 +390,6 @@ makeSimplifiedCeil
390390
where
391391
needsChildCeils = case termLikeF of
392392
ApplyAliasF _ -> False
393-
EvaluatedF _ -> False
394393
EndiannessF _ -> True
395394
SignednessF _ -> True
396395
AndF _ -> True

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

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -369,7 +369,6 @@ simplify sideCondition = \termLike ->
369369
-- Unimplemented cases
370370
ApplyAliasF _ -> doNotSimplify
371371
-- Do not simplify non-simplifiable patterns.
372-
EvaluatedF _ -> doNotSimplify
373372
EndiannessF _ -> doNotSimplify
374373
SignednessF _ -> doNotSimplify
375374
--

kore/test/Test/ConsistentKore.hs

Lines changed: 0 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -90,7 +90,6 @@ import Kore.Internal.TermLike
9090
, mkCeil
9191
, mkElemVar
9292
, mkEquals
93-
, mkEvaluated
9493
, mkExists
9594
, mkFloor
9695
, mkForall
@@ -332,7 +331,6 @@ _checkTermImplemented term@(Recursive.project -> _ :< termF) =
332331
checkTermF (InternalListF _) = term
333332
checkTermF (InternalMapF _) = term
334333
checkTermF (InternalSetF _) = term
335-
checkTermF (EvaluatedF _) = term
336334
checkTermF (InhabitantF _) = term -- Not implemented.
337335
checkTermF (EndiannessF _) = term -- Not implemented.
338336
checkTermF (SignednessF _) = term -- Not implemented.
@@ -358,7 +356,6 @@ termGenerators = do
358356
, orGenerator
359357
, rewritesGenerator
360358
, topGenerator
361-
, evaluatedGenerator
362359
]
363360
literals <- filterGeneratorsAndGroup
364361
(catMaybes
@@ -587,9 +584,6 @@ rewritesGenerator = binaryOperatorGenerator mkRewrites
587584
topGenerator :: TermGenerator
588585
topGenerator = nullaryFreeSortOperatorGenerator mkTop
589586

590-
evaluatedGenerator :: TermGenerator
591-
evaluatedGenerator = unaryOperatorGenerator mkEvaluated
592-
593587
maybeStringLiteralGenerator :: Setup -> Maybe TermGenerator
594588
maybeStringLiteralGenerator Setup {maybeStringLiteralSort} =
595589
case maybeStringLiteralSort of

kore/test/Test/Kore/Builtin/Int.hs

Lines changed: 0 additions & 32 deletions
Original file line numberDiff line numberDiff line change
@@ -11,8 +11,6 @@ module Test.Kore.Builtin.Int
1111
, test_and, test_or, test_xor, test_not
1212
, test_shl, test_shr
1313
, test_pow, test_powmod, test_log2
14-
, test_tdiv_evaluated_arguments
15-
, test_ediv_evaluated_arguments
1614
, test_unifyEqual_NotEqual
1715
, test_unifyEqual_Equal
1816
, test_unifyAnd_NotEqual
@@ -57,9 +55,6 @@ import Data.Bits
5755
, (.&.)
5856
, (.|.)
5957
)
60-
import Data.Semigroup
61-
( Endo (..)
62-
)
6358
import qualified Data.Text as Text
6459

6560
import Kore.Builtin.Int
@@ -281,10 +276,6 @@ test_abs = testUnary absIntSymbol abs
281276
test_tdiv :: TestTree
282277
test_tdiv = testPartialBinary tdivIntSymbol tdiv
283278

284-
test_tdiv_evaluated_arguments :: TestTree
285-
test_tdiv_evaluated_arguments =
286-
testDivEvaluatedArguments tdivIntSymbol tdiv
287-
288279
test_tmod :: TestTree
289280
test_tmod = testPartialBinary tmodIntSymbol tmod
290281

@@ -297,10 +288,6 @@ test_tmodZero = testPartialBinaryZero tmodIntSymbol tmod
297288
test_ediv_property :: TestTree
298289
test_ediv_property = testPartialBinary edivIntSymbol ediv
299290

300-
test_ediv_evaluated_arguments :: TestTree
301-
test_ediv_evaluated_arguments =
302-
testDivEvaluatedArguments edivIntSymbol ediv
303-
304291
test_emod_property :: TestTree
305292
test_emod_property = testPartialBinary emodIntSymbol emod
306293

@@ -400,25 +387,6 @@ test_euclidian_division_theorem =
400387
internalIntValue
401388
_ -> error "Expecting builtin int."
402389

403-
testDivEvaluatedArguments
404-
:: Symbol
405-
-> (Integer -> Integer -> Maybe Integer)
406-
-> TestTree
407-
testDivEvaluatedArguments symbol expected =
408-
testPropertyWithSolver (Text.unpack name) $ do
409-
a <- forAll genInteger
410-
b <- forAll genInteger
411-
na <- forAll $ Gen.integral (Range.linear 0 5)
412-
nb <- forAll $ Gen.integral (Range.linear 0 5)
413-
let expect = asPartialPattern $ expected a b
414-
actual <- evaluateT
415-
$ mkApplySymbol symbol [evaluated na a, evaluated nb b]
416-
(===) expect actual
417-
where
418-
name = expectHook edivIntSymbol <> " with evaluated arguments"
419-
compose n f = appEndo $ stimes (n :: Integer) (Endo f)
420-
evaluated n x = compose n mkEvaluated $ asInternal x
421-
422390
-- Bitwise operations
423391
test_and :: TestTree
424392
test_and = testBinary andIntSymbol (.&.)

0 commit comments

Comments
 (0)