Skip to content

Commit d136446

Browse files
Fix Strict performance (#2447)
* WIP: make evaluation of side condition representation lazy * WIP fix: best results so far * Replace undefined * WIP fix: best performance yet * Remove useless lazy bindings * Remove useless lazy bindings * Update kore/src/Kore/Attribute/Pattern/Simplified.hs Co-authored-by: Thomas Tuegel <[email protected]> * TermLike.setSimplified: make attributes lazy * TermLike.TermLike: make call to Attribute.traverseVariables lazy * Review: make Representation lazy * Make Attribute.Simplified lazy * Review: remove redundant Co-authored-by: Thomas Tuegel <[email protected]> * Review: make TypeRep strict Co-authored-by: Thomas Tuegel <[email protected]> * Make Simplified and SideCondition.SideCondition NoStrict * Remove redundant lazy bindings Co-authored-by: Thomas Tuegel <[email protected]>
1 parent 0427fae commit d136446

File tree

4 files changed

+30
-10
lines changed

4 files changed

+30
-10
lines changed

kore/src/Kore/Attribute/Pattern/Simplified.hs

Lines changed: 5 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -4,7 +4,7 @@ License : NCSA
44
55
-}
66

7-
{-# LANGUAGE Strict #-}
7+
{-# LANGUAGE NoStrict #-}
88

99
module Kore.Attribute.Pattern.Simplified
1010
( Simplified (..)
@@ -100,7 +100,7 @@ data Condition
100100
= Any
101101
-- ^ The term and all its subterms are simplified the same regardless
102102
-- of the side condition.
103-
| Condition !SideCondition.Representation
103+
| Condition SideCondition.Representation
104104
-- ^ The term is in its current simplified state only when using the
105105
-- given side condition. When the side condition changes, e.g. by
106106
-- adding extra conditions, then we may be able to further simplify the
@@ -134,8 +134,8 @@ instance Monoid Condition where
134134

135135
data SimplifiedData =
136136
SimplifiedData
137-
{ sType :: !Type
138-
, condition :: !Condition
137+
{ sType :: Type
138+
, condition :: Condition
139139
}
140140
deriving (Eq, Ord, Show)
141141
deriving (GHC.Generic)
@@ -156,7 +156,7 @@ Most patterns are assumed un-simplified until marked otherwise, so the
156156
simplified status is reset by any substitution under the pattern.
157157
-}
158158
data Simplified
159-
= Simplified !SimplifiedData
159+
= Simplified SimplifiedData
160160
| NotSimplified
161161
deriving (Eq, Ord, Show)
162162
deriving (GHC.Generic)

kore/src/Kore/Internal/Predicate.hs

Lines changed: 18 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1045,8 +1045,24 @@ mapVariables
10451045
=> AdjSomeVariableName (variable1 -> variable2)
10461046
-> Predicate variable1
10471047
-> Predicate variable2
1048-
mapVariables adj =
1049-
either undefined id . makePredicate . TermLike.mapVariables adj . fromPredicate_
1048+
mapVariables adj predicate =
1049+
let termPredicate =
1050+
TermLike.mapVariables adj
1051+
. fromPredicate_
1052+
$ predicate
1053+
in
1054+
either
1055+
errorMappingVariables
1056+
id
1057+
(makePredicate termPredicate)
1058+
where
1059+
errorMappingVariables termPredicate =
1060+
error . show . Pretty.vsep $
1061+
[ "Error when mapping the variables of predicate:"
1062+
, Pretty.pretty predicate
1063+
, "The resulting term is not a predicate:"
1064+
, Pretty.pretty termPredicate
1065+
]
10501066

10511067
-- |Is the predicate free of the given variables?
10521068
isFreeOf

kore/src/Kore/Internal/SideCondition/SideCondition.hs

Lines changed: 5 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -3,6 +3,8 @@ Copyright : (c) Runtime Verification, 2020
33
License : NCSA
44
-}
55

6+
{-# LANGUAGE NoStrict #-}
7+
68
module Kore.Internal.SideCondition.SideCondition
79
( Representation
810
, mkRepresentation
@@ -34,7 +36,9 @@ import Type.Reflection
3436
)
3537

3638
data Representation where
37-
Representation :: (Ord a, Pretty a) => !(TypeRep a) -> !(Hashed a) -> Representation
39+
Representation
40+
:: (Ord a, Pretty a)
41+
=> !(TypeRep a) -> Hashed a -> Representation
3842

3943
instance Eq Representation where
4044
(==) (Representation typeRep1 hashed1) (Representation typeRep2 hashed2) =

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

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -909,8 +909,8 @@ traverseVariables adj termLike =
909909
(RenamingT variable1 variable2 m (TermLike variable2))
910910
-> RenamingT variable1 variable2 m (TermLike variable2)
911911
worker (attrs :< termLikeF) = do
912-
attrs' <- Attribute.traverseVariables askSomeVariableName attrs
913-
let avoiding = freeVariables attrs'
912+
~attrs' <- Attribute.traverseVariables askSomeVariableName attrs
913+
let ~avoiding = freeVariables attrs'
914914
termLikeF' <- case termLikeF of
915915
VariableF (Const unifiedVariable) -> do
916916
unifiedVariable' <- askSomeVariable unifiedVariable

0 commit comments

Comments
 (0)