@@ -4,13 +4,23 @@ module Test.Kore.Exec
44 , test_searchPriority
55 , test_searchExceedingBreadthLimit
66 , test_execGetExitCode
7+ , test_execDepthLimitExceeded
78 ) where
89
910import Prelude.Kore
1011
1112import Test.Tasty
1213
1314import Control.Exception as Exception
15+ import Control.Monad.Catch
16+ ( MonadCatch
17+ , MonadMask
18+ , MonadThrow
19+ )
20+ import Control.Monad.State.Strict
21+ ( StateT (.. )
22+ )
23+ import qualified Control.Monad.State.Strict as State
1424import Data.Default
1525 ( def
1626 )
@@ -27,6 +37,7 @@ import System.Exit
2737 ( ExitCode (.. )
2838 )
2939
40+ import qualified Data.Bifunctor as Bifunctor
3041import Data.Limit
3142 ( Limit (.. )
3243 )
@@ -51,6 +62,7 @@ import Kore.Internal.Predicate
5162 )
5263import Kore.Internal.TermLike
5364import qualified Kore.Internal.TermLike as TermLike
65+ import Kore.Log.WarnDepthLimitExceeded
5466import Kore.Step
5567 ( ExecutionMode (.. )
5668 )
@@ -69,6 +81,9 @@ import Kore.Step.Search
6981 ( SearchType (.. )
7082 )
7183import qualified Kore.Step.Search as Search
84+ import Kore.Step.Simplification.Data
85+ ( MonadProf
86+ )
7287import Kore.Step.Strategy
7388 ( LimitExceeded (.. )
7489 )
@@ -78,6 +93,12 @@ import Kore.Syntax.Definition hiding
7893 )
7994import qualified Kore.Syntax.Definition as Syntax
8095import qualified Kore.Verified as Verified
96+ import Log
97+ ( Entry (.. )
98+ , MonadLog (.. )
99+ , SomeEntry
100+ )
101+ import qualified SMT
81102
82103import Test.Kore
83104import qualified Test.Kore.IndexedModule.MockMetadataTools as Mock
@@ -123,6 +144,53 @@ test_execPriority = testCase "execPriority" $ actual >>= assertEqual "" expected
123144 inputPattern = applyToNoArgs mySort " a"
124145 expected = (ExitSuccess , applyToNoArgs mySort " d" )
125146
147+ newtype TestLog a = TestLog ( StateT [SomeEntry ] SMT. NoSMT a )
148+ deriving newtype (Functor , Applicative , Monad )
149+ deriving newtype (State.MonadState [SomeEntry ], MonadIO , SMT.MonadSMT )
150+ deriving newtype (MonadThrow , MonadCatch , MonadMask , MonadProf )
151+
152+ instance MonadLog TestLog where
153+ logEntry entry = State. modify (toEntry entry : )
154+ logWhile entry (TestLog state) =
155+ TestLog $ State. mapStateT addEntry state
156+ where
157+ addEntry :: SMT. NoSMT (a , [SomeEntry ]) -> SMT. NoSMT (a , [SomeEntry ])
158+ addEntry = fmap $ Bifunctor. second (toEntry entry : )
159+
160+ runTestLog :: TestLog a -> IO [SomeEntry ]
161+ runTestLog (TestLog state) = runNoSMT $ State. execStateT state []
162+
163+ test_execDepthLimitExceeded :: TestTree
164+ test_execDepthLimitExceeded = testCase " exec exceeds depth limit"
165+ $ do
166+ entries <- actual
167+ let actualDepthWarnings =
168+ catMaybes $ fromEntry @ WarnDepthLimitExceeded <$> entries
169+ expectedWarning = WarnDepthLimitExceeded 1
170+ assertEqual " " [expectedWarning] actualDepthWarnings
171+ where
172+ actual =
173+ exec
174+ (Limit 1 )
175+ Unlimited
176+ verifiedModule
177+ Any
178+ inputPattern
179+ & runTestLog
180+ verifiedModule = verifiedMyModule Module
181+ { moduleName = ModuleName " MY-MODULE"
182+ , moduleSentences =
183+ [ asSentence mySortDecl
184+ , asSentence $ constructorDecl " a"
185+ , asSentence $ constructorDecl " b"
186+ , functionalAxiom " a"
187+ , functionalAxiom " b"
188+ , simpleRewriteAxiom " a" " b"
189+ ]
190+ , moduleAttributes = Attributes []
191+ }
192+ inputPattern = applyToNoArgs mySort " a"
193+
126194test_exec :: TestTree
127195test_exec = testCase " exec" $ actual >>= assertEqual " " expected
128196 where
0 commit comments