Skip to content

Commit 5edf6cc

Browse files
authored
Linear \and simplification (#2107)
* Export Kore.Internal.Pattern.syncSort * simplifyConjunctionByAssumption: Use clearer terminology
1 parent babf985 commit 5edf6cc

File tree

16 files changed

+347
-383
lines changed

16 files changed

+347
-383
lines changed

kore/src/Kore/Internal/MultiAnd.hs

Lines changed: 43 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -16,6 +16,8 @@ module Kore.Internal.MultiAnd
1616
, extractPatterns
1717
, make
1818
, toPredicate
19+
, fromPredicate
20+
, fromTermLike
1921
, singleton
2022
, toPattern
2123
, map
@@ -28,6 +30,7 @@ import Prelude.Kore hiding
2830
import Control.DeepSeq
2931
( NFData
3032
)
33+
import qualified Data.Functor.Foldable as Recursive
3134
import qualified Data.Set as Set
3235
import qualified Generics.SOP as SOP
3336
import qualified GHC.Exts as GHC
@@ -40,11 +43,14 @@ import Kore.Internal.Pattern
4043
import qualified Kore.Internal.Pattern as Pattern
4144
import Kore.Internal.Predicate
4245
( Predicate
46+
, getMultiAndPredicate
4347
, makeAndPredicate
4448
, makeTruePredicate_
4549
)
4650
import Kore.Internal.TermLike
47-
( mkAnd
51+
( TermLike
52+
, TermLikeF (..)
53+
, mkAnd
4854
)
4955
import Kore.Internal.Variable
5056
import Kore.TopBottom
@@ -88,6 +94,27 @@ instance Debug child => Debug (MultiAnd child)
8894

8995
instance (Debug child, Diff child) => Diff (MultiAnd child)
9096

97+
instance
98+
InternalVariable variable
99+
=> From (MultiAnd (Predicate variable)) (Predicate variable)
100+
where
101+
from = toPredicate
102+
{-# INLINE from #-}
103+
104+
instance
105+
InternalVariable variable
106+
=> From (Predicate variable) (MultiAnd (Predicate variable))
107+
where
108+
from = fromPredicate
109+
{-# INLINE from #-}
110+
111+
instance
112+
InternalVariable variable
113+
=> From (TermLike variable) (MultiAnd (TermLike variable))
114+
where
115+
from = fromTermLike
116+
{-# INLINE from #-}
117+
91118
{-| 'AndBool' is an some sort of Bool data type used when evaluating things
92119
inside a 'MultiAnd'.
93120
-}
@@ -184,6 +211,21 @@ toPredicate (MultiAnd predicates) =
184211
[] -> makeTruePredicate_
185212
_ -> foldr1 makeAndPredicate predicates
186213

214+
fromPredicate
215+
:: InternalVariable variable
216+
=> Predicate variable
217+
-> MultiAnd (Predicate variable)
218+
fromPredicate = make . getMultiAndPredicate
219+
220+
fromTermLike
221+
:: InternalVariable variable
222+
=> TermLike variable
223+
-> MultiAnd (TermLike variable)
224+
fromTermLike termLike =
225+
case Recursive.project termLike of
226+
_ :< AndF andF -> foldMap fromTermLike andF
227+
_ -> make [termLike]
228+
187229
toPattern
188230
:: InternalVariable variable
189231
=> MultiAnd (Pattern variable)

kore/src/Kore/Internal/Pattern.hs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -7,6 +7,7 @@ Representation of program configurations as conditional patterns.
77
module Kore.Internal.Pattern
88
( Pattern
99
, coerceSort
10+
, syncSort
1011
, patternSort
1112
, fromCondition
1213
, fromCondition_

0 commit comments

Comments
 (0)