Skip to content

Commit d1f740f

Browse files
authored
Merge branch 'master' into unification-refactor2
2 parents 6b938e2 + e6bda1b commit d1f740f

Some content is hidden

Large Commits have some content hidden by default. Use the searchbox below for content that may be hidden.

57 files changed

+1768
-1030
lines changed

deps/k_release

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1 +1 @@
1-
v5.1.14
1+
v5.1.25

docs/hooks.md

Lines changed: 29 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -401,20 +401,29 @@ Convert an integer value to its base10 string representation.
401401

402402
~~~
403403
hooked-symbol int2string{}(Int{}) : String{}
404-
[hook{}("STRING.string2int")]
404+
[hook{}("STRING.int2string")]
405405
~~~
406406

407407
### STRING.string2base
408408

409409
Takes a string and a base and converts the string from `base` to its integer
410410
value.
411-
Currently only works for base 8, 10, and 16.
411+
Supports bases 2 to 36 inclusive.
412412

413413
~~~
414414
hooked-symbol string2base{}(String{}, Int{}) : Int{}
415415
[hook{}("STRING.string2base")]
416416
~~~
417417

418+
### STRING.base2string
419+
420+
Convert an integer value to its base string representation.
421+
422+
~~~
423+
hooked-symbol base2string{}(/* value */ Int{}, /* base */ Int{}) : String{}
424+
[hook{}("STRING.base2string")]
425+
~~~
426+
418427
### STRING.substr
419428

420429
Substr takes a string and two indices (start and end) and returns the substring
@@ -989,3 +998,21 @@ using the provided value.
989998
hooked-symbol bytes2int{}(Bytes{}, Endianness{}, Signedness{}) : Int{}
990999
[hook{}("BYTES.bytes2int")]
9911000
~~~
1001+
1002+
### BYTES.decodeBytes
1003+
1004+
`BYTES.decodeBytes` supports `"UTF-8"`, `"UTF-16LE"`, `"UTF-16BE"`, `"UTF-32LE"`, and `"UTF-32BE"` as the first argument. If decoding UTF-8 and the input contains any invalid data then `bottom` is returned. If decoding UTF-16 or UTF-32 and the input contains any invalid data then an exception will be thrown.
1005+
1006+
~~~
1007+
hooked-symbol decodeBytes{}(/* decoding */ String{}, /* contents */ Bytes{}) : String{}
1008+
[hook{}("BYTES.decodeBytes")]
1009+
~~~
1010+
1011+
### BYTES.encodeBytes
1012+
1013+
`BYTES.encodeBytes` supports `"UTF-8"`, `"UTF-16LE"`, `"UTF-16BE"`, `"UTF-32LE"`, and `"UTF-32BE"` as the first argument.
1014+
1015+
~~~
1016+
hooked-symbol encodeBytes{}(/* encoding */ String{}, /* contents */ String{}) : Bytes{}
1017+
[hook{}("BYTES.encodeBytes")]
1018+
~~~

kore/app/exec/Main.hs

Lines changed: 49 additions & 26 deletions
Original file line numberDiff line numberDiff line change
@@ -37,6 +37,9 @@ import qualified Data.Text.IO as Text (
3737
)
3838
import qualified GHC.Generics as GHC
3939
import GlobalMain
40+
import Kore.Attribute.Definition (
41+
KFileLocations (..),
42+
)
4043
import Kore.Attribute.Symbol as Attribute
4144
import Kore.BugReport
4245
import Kore.Exec
@@ -584,7 +587,7 @@ mainWithOptions execOptions = do
584587
}
585588
writeOptionsAndKoreFiles tmpDir execOptions'
586589
e <-
587-
mainDispatch execOptions' <* warnIfLowProductivity
590+
mainDispatch execOptions'
588591
& handle handleWithConfiguration
589592
& handle handleSomeException
590593
& runKoreLog tmpDir koreLogOptions
@@ -618,23 +621,34 @@ mainWithOptions execOptions = do
618621

619622
-- | Dispatch the requested command, for example 'koreProve' or 'koreRun'.
620623
mainDispatch :: KoreExecOptions -> Main ExitCode
621-
mainDispatch execOptions
622-
| Just proveOptions@KoreProveOptions{bmc} <- koreProveOptions =
623-
if bmc
624-
then koreBmc execOptions proveOptions
625-
else koreProve execOptions proveOptions
626-
| Just searchOptions <- koreSearchOptions =
627-
koreSearch execOptions searchOptions
628-
| Just mergeOptions <- koreMergeOptions =
629-
koreMerge execOptions mergeOptions
630-
| otherwise =
631-
koreRun execOptions
624+
mainDispatch = warnProductivity . mainDispatchWorker
632625
where
633-
KoreExecOptions{koreProveOptions} = execOptions
634-
KoreExecOptions{koreSearchOptions} = execOptions
635-
KoreExecOptions{koreMergeOptions} = execOptions
626+
warnProductivity :: Main (KFileLocations, ExitCode) -> Main ExitCode
627+
warnProductivity action = do
628+
(kFileLocations, exitCode) <- action
629+
warnIfLowProductivity kFileLocations
630+
return exitCode
631+
mainDispatchWorker :: KoreExecOptions -> Main (KFileLocations, ExitCode)
632+
mainDispatchWorker execOptions
633+
| Just proveOptions@KoreProveOptions{bmc} <- koreProveOptions =
634+
if bmc
635+
then koreBmc execOptions proveOptions
636+
else koreProve execOptions proveOptions
637+
| Just searchOptions <- koreSearchOptions =
638+
koreSearch execOptions searchOptions
639+
| Just mergeOptions <- koreMergeOptions =
640+
koreMerge execOptions mergeOptions
641+
| otherwise =
642+
koreRun execOptions
643+
where
644+
KoreExecOptions{koreProveOptions} = execOptions
645+
KoreExecOptions{koreSearchOptions} = execOptions
646+
KoreExecOptions{koreMergeOptions} = execOptions
636647

637-
koreSearch :: KoreExecOptions -> KoreSearchOptions -> Main ExitCode
648+
koreSearch ::
649+
KoreExecOptions ->
650+
KoreSearchOptions ->
651+
Main (KFileLocations, ExitCode)
638652
koreSearch execOptions searchOptions = do
639653
let KoreExecOptions{definitionFileName} = execOptions
640654
definition <- loadDefinitions [definitionFileName]
@@ -648,13 +662,13 @@ koreSearch execOptions searchOptions = do
648662
execute execOptions mainModule $
649663
search depthLimit breadthLimit mainModule initial target config
650664
lift $ renderResult execOptions (unparse final)
651-
return ExitSuccess
665+
return (kFileLocations definition, ExitSuccess)
652666
where
653667
KoreSearchOptions{bound, searchType} = searchOptions
654668
config = Search.Config{bound, searchType}
655669
KoreExecOptions{breadthLimit, depthLimit} = execOptions
656670

657-
koreRun :: KoreExecOptions -> Main ExitCode
671+
koreRun :: KoreExecOptions -> Main (KFileLocations, ExitCode)
658672
koreRun execOptions = do
659673
let KoreExecOptions{definitionFileName} = execOptions
660674
definition <- loadDefinitions [definitionFileName]
@@ -666,11 +680,14 @@ koreRun execOptions = do
666680
execute execOptions mainModule $
667681
exec depthLimit breadthLimit mainModule strategy initial
668682
lift $ renderResult execOptions (unparse final)
669-
return exitCode
683+
return (kFileLocations definition, exitCode)
670684
where
671685
KoreExecOptions{breadthLimit, depthLimit, strategy} = execOptions
672686

673-
koreProve :: KoreExecOptions -> KoreProveOptions -> Main ExitCode
687+
koreProve ::
688+
KoreExecOptions ->
689+
KoreProveOptions ->
690+
Main (KFileLocations, ExitCode)
674691
koreProve execOptions proveOptions = do
675692
let KoreExecOptions{definitionFileName} = execOptions
676693
KoreProveOptions{specFileName} = proveOptions
@@ -707,7 +724,7 @@ koreProve execOptions proveOptions = do
707724
getRewritingPattern . getConfiguration . getStuckClaim
708725
lift $ for_ saveProofs $ saveProven specModule provenClaims
709726
lift $ renderResult execOptions (unparse final)
710-
return exitCode
727+
return (kFileLocations definition, exitCode)
711728
where
712729
failure pat = (ExitFailure 1, pat)
713730
success :: (ExitCode, TermLike VariableName)
@@ -768,7 +785,10 @@ koreProve execOptions proveOptions = do
768785
, definitionModules = [provenModule]
769786
}
770787

771-
koreBmc :: KoreExecOptions -> KoreProveOptions -> Main ExitCode
788+
koreBmc ::
789+
KoreExecOptions ->
790+
KoreProveOptions ->
791+
Main (KFileLocations, ExitCode)
772792
koreBmc execOptions proveOptions = do
773793
let KoreExecOptions{definitionFileName} = execOptions
774794
KoreProveOptions{specFileName} = proveOptions
@@ -794,12 +814,15 @@ koreBmc execOptions proveOptions = do
794814
return success
795815
Bounded.Failed final -> return (failure final)
796816
lift $ renderResult execOptions (unparse final)
797-
return exitCode
817+
return (kFileLocations definition, exitCode)
798818
where
799819
failure pat = (ExitFailure 1, pat)
800820
success = (ExitSuccess, mkTop $ mkSortVariable "R")
801821

802-
koreMerge :: KoreExecOptions -> KoreMergeOptions -> Main ExitCode
822+
koreMerge ::
823+
KoreExecOptions ->
824+
KoreMergeOptions ->
825+
Main (KFileLocations, ExitCode)
803826
koreMerge execOptions mergeOptions = do
804827
let KoreExecOptions{definitionFileName} = execOptions
805828
definition <- loadDefinitions [definitionFileName]
@@ -816,12 +839,12 @@ koreMerge execOptions mergeOptions = do
816839
case eitherMergedRule of
817840
(Left err) -> do
818841
lift $ Text.hPutStrLn stderr err
819-
return (ExitFailure 1)
842+
return (kFileLocations definition, ExitFailure 1)
820843
(Right mergedRule) -> do
821844
let mergedRule' =
822845
mergedRule <&> mapRuleVariables getRewritingVariable
823846
lift $ renderResult execOptions (vsep (map unparse mergedRule'))
824-
return ExitSuccess
847+
return (kFileLocations definition, ExitSuccess)
825848

826849
loadRuleIds :: FilePath -> IO [Text]
827850
loadRuleIds fileName = do

kore/app/repl/Main.hs

Lines changed: 4 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -215,7 +215,8 @@ mainWithOptions
215215
let swapLogAction = swappableLogger mvarLogAction
216216
flip runLoggerT swapLogAction $
217217
runExceptionHandlers $ do
218-
definition <- loadDefinitions [definitionFileName, specFile]
218+
definition <-
219+
loadDefinitions [definitionFileName, specFile]
219220
indexedModule <- loadModule mainModuleName definition
220221
specDefIndexedModule <- loadModule specModule definition
221222

@@ -265,8 +266,10 @@ mainWithOptions
265266
outputFile
266267
mainModuleName
267268
koreLogOptions
269+
(GlobalMain.kFileLocations definition)
268270

269271
warnIfLowProductivity
272+
(GlobalMain.kFileLocations definition)
270273
pure ExitSuccess
271274
exitWith exitCode
272275
where

kore/app/share/GlobalMain.hs

Lines changed: 33 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -18,7 +18,7 @@ module GlobalMain (
1818
verifyDefinitionWithBase,
1919
mainParse,
2020
lookupMainModule,
21-
LoadedDefinition,
21+
LoadedDefinition (..),
2222
LoadedModule,
2323
loadDefinitions,
2424
loadModule,
@@ -34,6 +34,7 @@ import qualified Control.Lens as Lens
3434
import qualified Control.Monad as Monad
3535
import Data.List (
3636
intercalate,
37+
nub,
3738
)
3839
import Data.Map.Strict (
3940
Map,
@@ -55,6 +56,13 @@ import Kore.ASTVerifier.DefinitionVerifier (
5556
verifyAndIndexDefinitionWithBase,
5657
)
5758
import Kore.ASTVerifier.PatternVerifier as PatternVerifier
59+
import Kore.Attribute.Definition (
60+
KFileLocations (..),
61+
parseKFileAttributes,
62+
)
63+
import Kore.Attribute.SourceLocation (
64+
notDefault,
65+
)
5866
import qualified Kore.Attribute.Symbol as Attribute (
5967
Symbol,
6068
)
@@ -84,6 +92,7 @@ import Kore.Syntax
8492
import Kore.Syntax.Definition (
8593
ModuleName (..),
8694
ParsedDefinition,
95+
definitionAttributes,
8796
getModuleNameForError,
8897
)
8998
import qualified Kore.Verified as Verified
@@ -473,18 +482,34 @@ mainParse parser fileName = do
473482

474483
type LoadedModule = VerifiedModule Attribute.Symbol
475484

476-
type LoadedDefinition = (Map ModuleName LoadedModule, Map Text AstLocation)
485+
data LoadedDefinition = LoadedDefinition
486+
{ indexedModules :: Map ModuleName LoadedModule
487+
, definedNames :: Map Text AstLocation
488+
, kFileLocations :: KFileLocations
489+
}
477490

478491
loadDefinitions :: [FilePath] -> Main LoadedDefinition
479492
loadDefinitions filePaths =
480-
loadedDefinitions <&> sortClaims
493+
do
494+
loadedDefinitions & fmap sortClaims
481495
where
482-
loadedDefinitions =
483-
Monad.foldM verifyDefinitionWithBase mempty
484-
=<< traverse parseDefinition filePaths
496+
loadedDefinitions = do
497+
parsedDefinitions <- traverse parseDefinition filePaths
498+
let attributes = fmap definitionAttributes parsedDefinitions
499+
sources <- traverse parseKFileAttributes attributes
500+
let sources' = filter notDefault (nub sources)
501+
(indexedModules, definedNames) <-
502+
Monad.foldM verifyDefinitionWithBase mempty parsedDefinitions
503+
return $
504+
LoadedDefinition
505+
indexedModules
506+
definedNames
507+
(KFileLocations sources')
485508

486509
sortClaims :: LoadedDefinition -> LoadedDefinition
487-
sortClaims = Lens._1 . Lens.traversed %~ sortModuleClaims
510+
sortClaims def@LoadedDefinition{indexedModules} =
511+
let indexedModules' = indexedModules & Lens.traversed %~ sortModuleClaims
512+
in def{indexedModules = indexedModules'}
488513

489514
loadModule :: ModuleName -> LoadedDefinition -> Main LoadedModule
490-
loadModule moduleName = lookupMainModule moduleName . fst
515+
loadModule moduleName = lookupMainModule moduleName . indexedModules

kore/kore.cabal

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -198,6 +198,7 @@ library
198198
Kore.Attribute.Axiom.Unit
199199
Kore.Attribute.Comm
200200
Kore.Attribute.Constructor
201+
Kore.Attribute.Definition
201202
Kore.Attribute.Function
202203
Kore.Attribute.Functional
203204
Kore.Attribute.Hook
@@ -209,7 +210,6 @@ library
209210
Kore.Attribute.Overload
210211
Kore.Attribute.Owise
211212
Kore.Attribute.Parser
212-
Kore.Attribute.Pattern
213213
Kore.Attribute.Pattern.ConstructorLike
214214
Kore.Attribute.Pattern.Created
215215
Kore.Attribute.Pattern.Defined
@@ -302,6 +302,7 @@ library
302302
Kore.Internal.ApplicationSorts
303303
Kore.Internal.Condition
304304
Kore.Internal.Conditional
305+
Kore.Internal.From
305306
Kore.Internal.Inj
306307
Kore.Internal.InternalBool
307308
Kore.Internal.InternalBytes
@@ -676,6 +677,7 @@ test-suite kore-test
676677
Test.Kore.IndexedModule.SortGraph
677678
Test.Kore.Internal.ApplicationSorts
678679
Test.Kore.Internal.Condition
680+
Test.Kore.Internal.From
679681
Test.Kore.Internal.Key
680682
Test.Kore.Internal.MultiAnd
681683
Test.Kore.Internal.OrCondition

kore/src/Kore/ASTVerifier/DefinitionVerifier.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -100,7 +100,7 @@ verifyAndIndexDefinition builtinVerifiers definition = do
100100
{- |Verifies a `ParsedDefinition` against a preverified definition, consisting of
101101
map of indexed modules and a map of defined names.
102102
103-
If verification is successfull, it returns the updated maps op indexed modules
103+
If verification is successfull, it returns the updated maps of indexed modules
104104
and defined names.
105105
-}
106106
verifyAndIndexDefinitionWithBase ::
Lines changed: 36 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,36 @@
1+
{- |
2+
Copyright : (c) Runtime Verification, 2021
3+
License : NCSA
4+
-}
5+
module Kore.Attribute.Definition (
6+
parseKFileAttributes,
7+
KFileLocations (..),
8+
) where
9+
10+
import Control.Monad.Catch (MonadThrow)
11+
import qualified Data.Default as Default
12+
import Data.Generics.Product (typed)
13+
import Kore.Attribute.Attributes (Attributes (..))
14+
import Kore.Attribute.Parser (ParseAttributes (..))
15+
import Kore.Attribute.SourceLocation (SourceLocation)
16+
import Kore.Error (printError)
17+
import Kore.Log.ErrorParse
18+
import Prelude.Kore
19+
20+
{- | Location attribute for some of the K files used during execution, displayed
21+
by the 'WarnIfLowProductivity' warning.
22+
-}
23+
newtype KFileLocations = KFileLocations
24+
{locations :: [SourceLocation]}
25+
deriving stock (Show)
26+
27+
parseKFileAttributes :: MonadThrow m => Attributes -> m SourceLocation
28+
parseKFileAttributes (Attributes attrs) =
29+
case parser of
30+
Left err -> errorParse $ printError err
31+
Right sourceLocation ->
32+
return sourceLocation
33+
where
34+
parser = foldlM (flip parseDefinitionLocation) Default.def attrs
35+
parseDefinitionLocation source =
36+
typed @SourceLocation (parseAttribute source)

0 commit comments

Comments
 (0)