Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
Show all changes
30 commits
Select commit Hold shift + click to select a range
16ef91d
Add module and datatype ClaimPattern
ana-pantilie Jul 24, 2020
19c1a8b
ClaimPattern: onePathRuleToTerm
ana-pantilie Jul 24, 2020
0d9cf80
ClaimPattern: allPathRuleToTerm
ana-pantilie Jul 24, 2020
6cf54fe
ClaimPattern: add missing instances
ana-pantilie Jul 24, 2020
6bfe65d
ClaimPattern: ReachabilityRule
ana-pantilie Jul 24, 2020
3fac67a
ClaimPattern: FreeVariables
ana-pantilie Jul 27, 2020
9be3816
Merge remote-tracking branch 'upstream/master' into change-representa…
ana-pantilie Jul 27, 2020
5faacd3
Rule.Expand: update to ClaimPattern
ana-pantilie Jul 27, 2020
256c30f
Rule.Simplify: add functionality for ClaimPattern
ana-pantilie Jul 27, 2020
058f1ab
Step.Rule: parse reachability claims to ClaimPattern
ana-pantilie Jul 27, 2020
12b61ca
Integrate old claim representation back
ana-pantilie Jul 27, 2020
6f9880d
Step.Rule.Expand: refactor instance for ClaimPattern
ana-pantilie Jul 28, 2020
52d5380
Step.Rule.Simplify: refactor instance for ClaimPattern
ana-pantilie Jul 28, 2020
be962b3
ClaimPattern: functions to construct ClaimPatterns
ana-pantilie Jul 28, 2020
cd886e3
Test.Step.Rule.Expand: add tests for ClaimPattern
ana-pantilie Jul 28, 2020
17c94ec
Test.Step.Rule: add Common.hs + add tests for ClaimPattern in Simplif…
ana-pantilie Jul 28, 2020
81cd449
Test.Step.Rule: fix sort issues
ana-pantilie Jul 28, 2020
f25410b
Test.Step.Rule: remove class specific to old OnePathRule
ana-pantilie Jul 28, 2020
4e27c08
Test.Step.Rule.Simplify: hlint workaround
ana-pantilie Jul 28, 2020
c263eee
Test.Step.Rule.Simplify: hlint workaround
ana-pantilie Jul 28, 2020
cdfd7ee
Test.Step.Rule.Simplify: fix unit test
ana-pantilie Jul 28, 2020
49d435c
HLint
ana-pantilie Jul 28, 2020
82c6c6c
Clean-up
ana-pantilie Jul 28, 2020
854f338
Merge branch 'master' into change-representation-of-claims
ana-pantilie Jul 29, 2020
89d4a32
Fix ClaimPattern right hand side free variables bug
ana-pantilie Jul 29, 2020
6eaf5c1
Fix ClaimPattern unparsing bug
ana-pantilie Jul 29, 2020
deb9abd
Kore.Step.Rule.Expand: Remove redundant State field
ttuegel Jul 29, 2020
5f866d4
Test.Kore.Step.Rule.Expand: Separate old and new tests
ttuegel Jul 29, 2020
03f9f85
Address review comments
ana-pantilie Jul 30, 2020
dcff39c
Merge branch 'master' into change-representation-of-claims
ana-pantilie Jul 30, 2020
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
13 changes: 13 additions & 0 deletions kore/src/Kore/Internal/Conditional.hs
Original file line number Diff line number Diff line change
Expand Up @@ -32,6 +32,9 @@ import Prelude.Kore
import Control.DeepSeq
( NFData
)
import Data.Map.Strict
( Map
)
import qualified Generics.SOP as SOP
import qualified GHC.Generics as GHC

Expand Down Expand Up @@ -245,6 +248,16 @@ instance
where
from = pure

instance
InternalVariable variable
=> From (Map (SomeVariable variable) (TermLike variable)) (Conditional variable ())
Copy link
Contributor

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Why not From (Substitution variable) (Conditional variable ())? Or at least, there should be a direct instance.

where
from =
from @(Substitution variable) @(Conditional variable ())
. from
@(Map (SomeVariable variable) (TermLike variable))
@(Substitution variable)

unparseConditional
:: Sort
-> Doc ann -- ^ term
Expand Down
22 changes: 22 additions & 0 deletions kore/src/Kore/Internal/OrPattern.hs
Original file line number Diff line number Diff line change
Expand Up @@ -20,6 +20,8 @@ module Kore.Internal.OrPattern
, toPattern
, toTermLike
, targetBinder
, substitute
, parseFromTermLike
, MultiOr.flatten
, MultiOr.filterOr
, MultiOr.gather
Expand All @@ -29,6 +31,9 @@ module Kore.Internal.OrPattern
import Prelude.Kore

import qualified Data.Foldable as Foldable
import Data.Map.Strict
( Map
)

import Kore.Internal.Condition
( Condition
Expand All @@ -52,6 +57,7 @@ import qualified Kore.Internal.SideCondition.SideCondition as SideCondition
)
import Kore.Internal.TermLike
( InternalVariable
, pattern Or_
, Sort
, TermLike
, mkBottom_
Expand Down Expand Up @@ -219,3 +225,19 @@ targetBinder Binder { binderVariable, binderChild } =
{ binderVariable = newVar
, binderChild = newChild
}

substitute
:: InternalVariable variable
=> Map (SomeVariableName variable) (TermLike variable)
-> OrPattern variable
-> OrPattern variable
substitute subst =
fromPatterns . fmap (Pattern.substitute subst) . toPatterns

parseFromTermLike
:: InternalVariable variable
=> TermLike variable
-> OrPattern variable
parseFromTermLike (Or_ _ term1 term2) =
parseFromTermLike term1 <> parseFromTermLike term2
parseFromTermLike term = fromTermLike term
13 changes: 13 additions & 0 deletions kore/src/Kore/Internal/Pattern.hs
Original file line number Diff line number Diff line change
Expand Up @@ -10,6 +10,7 @@ module Kore.Internal.Pattern
, patternSort
, fromCondition
, fromCondition_
, fromTermAndPredicate
, fromPredicateSorted
, bottom
, bottomOf
Expand Down Expand Up @@ -96,6 +97,18 @@ program configuration for Kore execution.
-}
type Pattern variable = Conditional variable (TermLike variable)

fromTermAndPredicate
:: InternalVariable variable
=> TermLike variable
-> Predicate variable
-> Pattern variable
fromTermAndPredicate term predicate =
Conditional
{ term
, predicate
, substitution = mempty
}

fromCondition_
:: InternalVariable variable
=> Condition variable
Expand Down
62 changes: 62 additions & 0 deletions kore/src/Kore/Internal/TermLike.hs
Original file line number Diff line number Diff line change
Expand Up @@ -45,6 +45,11 @@ module Kore.Internal.TermLike
-- * Utility functions for dealing with sorts
, forceSort
, fullyOverrideSort
-- * Reachability modalities and application
, Modality (..)
, weakExistsFinally
, weakAlwaysFinally
, applyModality
-- * Pure Kore pattern constructors
, mkAnd
, mkApplyAlias
Expand Down Expand Up @@ -2025,3 +2030,60 @@ refreshSetBinder
-> Binder (SetVariable variable) (TermLike variable)
-> Binder (SetVariable variable) (TermLike variable)
refreshSetBinder = refreshBinder refreshSetVariable

data Modality = WEF | WAF

-- | Weak exists finally modality symbol.
weakExistsFinally :: Text
weakExistsFinally = "weakExistsFinally"

-- | Weak always finally modality symbol.
weakAlwaysFinally :: Text
weakAlwaysFinally = "weakAlwaysFinally"

-- | 'Alias' construct for weak exist finally.
wEF :: Sort -> Alias (TermLike VariableName)
wEF sort = Alias
{ aliasConstructor = Id
{ getId = weakExistsFinally
, idLocation = AstLocationNone
}
, aliasParams = [sort]
, aliasSorts = ApplicationSorts
{ applicationSortsOperands = [sort]
, applicationSortsResult = sort
}
, aliasLeft = []
, aliasRight = mkTop sort
}

-- | 'Alias' construct for weak always finally.
wAF :: Sort -> Alias (TermLike VariableName)
wAF sort = Alias
{ aliasConstructor = Id
{ getId = weakAlwaysFinally
, idLocation = AstLocationNone
}
, aliasParams = [sort]
, aliasSorts = ApplicationSorts
{ applicationSortsOperands = [sort]
, applicationSortsResult = sort
}
, aliasLeft = []
, aliasRight = mkTop sort
}

-- | Apply one of the reachability modality aliases
-- to a term.
applyModality
:: Modality
-> TermLike VariableName
-> TermLike VariableName
applyModality modality term =
case modality of
WEF ->
mkApplyAlias (wEF sort) [term]
WAF ->
mkApplyAlias (wAF sort) [term]
where
sort = termLikeSort term
5 changes: 5 additions & 0 deletions kore/src/Kore/Rewriting/RewritingVariable.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,6 +6,7 @@ License : NCSA

module Kore.Rewriting.RewritingVariable
( RewritingVariableName
, RewritingVariable
, isConfigVariable
, isRuleVariable
, isSomeConfigVariable
Expand All @@ -26,6 +27,8 @@ module Kore.Rewriting.RewritingVariable
, getResultPattern
, getRemainderPredicate
, getRemainderPattern
-- * Exported for reachability rule unparsing
, getRewritingVariable
) where

import Prelude.Kore
Expand Down Expand Up @@ -118,6 +121,8 @@ instance From VariableName RewritingVariableName where

instance FreshName RewritingVariableName

type RewritingVariable = Variable RewritingVariableName

mkElementConfigVariable
:: ElementVariable VariableName
-> ElementVariable RewritingVariableName
Expand Down
Loading