1
1
mirror of https://github.com/github/semantic.git synced 2025-01-06 23:46:21 +03:00

Merge branch 'second-wait' of https://github.com/github/semantic into second-wait

This commit is contained in:
Rick Winfrey 2019-02-05 10:43:54 -08:00
commit 9f2820feaa
18 changed files with 118 additions and 116 deletions

View File

@ -15,8 +15,9 @@ import qualified Semantic.AST as AST
import Semantic.Config import Semantic.Config
import qualified Semantic.Graph as Graph import qualified Semantic.Graph as Graph
import qualified Semantic.Task as Task import qualified Semantic.Task as Task
import Semantic.Task.Files
import qualified Semantic.Telemetry.Log as Log import qualified Semantic.Telemetry.Log as Log
import Semantic.Task.Files
import Semantic.Telemetry
import Semantic.Version import Semantic.Version
import System.Exit (die) import System.Exit (die)
import System.FilePath import System.FilePath
@ -26,8 +27,9 @@ import Text.Read
main :: IO () main :: IO ()
main = do main = do
(options, task) <- customExecParser (prefs showHelpOnEmpty) arguments (options, task) <- customExecParser (prefs showHelpOnEmpty) arguments
res <- Task.withOptions options $ \ config logger statter -> config <- defaultConfig options
Task.runTaskWithConfig config { configSHA = Just buildSHA } logger statter task res <- withTelemetry config $ \ (TelemetryQueues logger statter _) ->
Task.runTask (Task.TaskSession config "-" logger statter) task
either (die . displayException) pure res either (die . displayException) pure res
-- | A parser for the application's command-line arguments. -- | A parser for the application's command-line arguments.
@ -46,7 +48,7 @@ optionsParser = do
(long "log-level" <> value (Just Log.Warning) <> help "Log messages at or above this level, or disable logging entirely.") (long "log-level" <> value (Just Log.Warning) <> help "Log messages at or above this level, or disable logging entirely.")
failOnWarning <- switch (long "fail-on-warning" <> help "Fail on assignment warnings.") failOnWarning <- switch (long "fail-on-warning" <> help "Fail on assignment warnings.")
failOnParseError <- switch (long "fail-on-parse-error" <> help "Fail on tree-sitter parse errors.") failOnParseError <- switch (long "fail-on-parse-error" <> help "Fail on tree-sitter parse errors.")
pure $ Options logLevel Nothing failOnWarning failOnParseError pure $ Options logLevel failOnWarning failOnParseError
argumentsParser :: Parser (Task.TaskEff ()) argumentsParser :: Parser (Task.TaskEff ())
argumentsParser = do argumentsParser = do

View File

@ -52,16 +52,15 @@ data Config
data Options data Options
= Options = Options
{ optionsLogLevel :: Maybe Level -- ^ What level of messages to log. 'Nothing' disables logging. { optionsLogLevel :: Maybe Level -- ^ What level of messages to log. 'Nothing' disables logging.
, optionsRequestID :: Maybe String -- ^ Optional request id for tracing across systems.
, optionsFailOnWarning :: Bool -- ^ Should semantic fail fast on assignment warnings (for testing) , optionsFailOnWarning :: Bool -- ^ Should semantic fail fast on assignment warnings (for testing)
, optionsFailOnParseError :: Bool -- ^ Should semantic fail fast on tree-sitter parser errors (for testing) , optionsFailOnParseError :: Bool -- ^ Should semantic fail fast on tree-sitter parser errors (for testing)
} }
defaultOptions :: Options defaultOptions :: Options
defaultOptions = Options (Just Warning) Nothing False False defaultOptions = Options (Just Warning) False False
debugOptions :: Options debugOptions :: Options
debugOptions = Options (Just Debug) Nothing False False debugOptions = Options (Just Debug) False False
defaultConfig :: Options -> IO Config defaultConfig :: Options -> IO Config
defaultConfig options@Options{..} = do defaultConfig options@Options{..} = do
@ -111,8 +110,7 @@ logOptionsFromConfig Config{..} = LogOptions
, ("hostname", configHostName) , ("hostname", configHostName)
, ("sha", fromMaybe "development" configSHA) , ("sha", fromMaybe "development" configSHA)
] ]
<> [("request_id", x) | x <- toList (optionsRequestID configOptions) ] _ -> []
_ -> []
withLoggerFromConfig :: Config -> (LogQueue -> IO c) -> IO c withLoggerFromConfig :: Config -> (LogQueue -> IO c) -> IO c

View File

@ -32,6 +32,7 @@ module Semantic.Task
, distributeFoldMap , distributeFoldMap
-- * Configuration -- * Configuration
, debugOptions , debugOptions
, defaultOptions
, defaultConfig , defaultConfig
, terminalFormatter , terminalFormatter
, logfmtFormatter , logfmtFormatter
@ -39,7 +40,7 @@ module Semantic.Task
, runTask , runTask
, runTaskWithOptions , runTaskWithOptions
, withOptions , withOptions
, runTaskWithConfig , TaskSession(..)
, runTraceInTelemetry , runTraceInTelemetry
, runTaskF , runTaskF
-- * Exceptions -- * Exceptions
@ -91,7 +92,6 @@ import Semantic.Timeout
import Semantic.Resolution import Semantic.Resolution
import Semantic.Telemetry import Semantic.Telemetry
import Serializing.Format hiding (Options) import Serializing.Format hiding (Options)
import System.Exit (die)
-- | A high-level task producing some result, e.g. parsing, diffing, rendering. 'Task's can also specify explicit concurrency via 'distribute', 'distributeFor', and 'distributeFoldMap' -- | A high-level task producing some result, e.g. parsing, diffing, rendering. 'Task's can also specify explicit concurrency via 'distribute', 'distributeFor', and 'distributeFoldMap'
type TaskEff type TaskEff
@ -150,33 +150,17 @@ serialize :: (Member Task sig, Carrier sig m)
-> m Builder -> m Builder
serialize format input = send (Serialize format input ret) serialize format input = send (Serialize format input ret)
-- | Execute a 'Task' with the 'defaultOptions', yielding its result value in 'IO'. data TaskSession
-- = TaskSession
-- > runTask = runTaskWithOptions defaultOptions { config :: Config
runTask :: TaskEff a , requestID :: String
-> IO a , logger :: LogQueue
runTask = runTaskWithOptions defaultOptions , statter :: StatQueue
}
-- | Execute a 'TaskEff' with the passed 'Options', yielding its result value in 'IO'.
runTaskWithOptions :: Options
-> TaskEff a
-> IO a
runTaskWithOptions opts task = withOptions opts (\ config logger statter -> runTaskWithConfig config logger statter task) >>= either (die . displayException) pure
withOptions :: Options
-> (Config -> LogQueue -> StatQueue -> IO a)
-> IO a
withOptions options with = do
config <- defaultConfig options
withTelemetry config (\ (TelemetryQueues logger statter _) -> with config logger statter)
-- | Execute a 'TaskEff' yielding its result value in 'IO'. -- | Execute a 'TaskEff' yielding its result value in 'IO'.
runTaskWithConfig :: Config runTask :: TaskSession -> TaskEff a -> IO (Either SomeException a)
-> LogQueue runTask TaskSession{..} task = do
-> StatQueue
-> TaskEff a
-> IO (Either SomeException a)
runTaskWithConfig options logger statter task = do
(result, stat) <- withTiming "run" [] $ do (result, stat) <- withTiming "run" [] $ do
let run :: TaskEff a -> IO (Either SomeException a) let run :: TaskEff a -> IO (Either SomeException a)
run run
@ -187,7 +171,7 @@ runTaskWithConfig options logger statter task = do
. runError . runError
. runTelemetry logger statter . runTelemetry logger statter
. runTraceInTelemetry . runTraceInTelemetry
. runReader options . runReader config
. Files.runFiles . Files.runFiles
. runResolution . runResolution
. runTaskF . runTaskF
@ -195,6 +179,17 @@ runTaskWithConfig options logger statter task = do
queueStat statter stat queueStat statter stat
pure result pure result
-- | Execute a 'TaskEff' yielding its result value in 'IO' using all default options and configuration.
runTaskWithOptions :: Options -> TaskEff a -> IO (Either SomeException a)
runTaskWithOptions options task = withOptions options $ \ config logger statter ->
runTask (TaskSession config "-" logger statter) task
-- | Yield config and telemetry queues for options.
withOptions :: Options -> (Config -> LogQueue -> StatQueue -> IO a) -> IO a
withOptions options with = do
config <- defaultConfig options
withTelemetry config (\ (TelemetryQueues logger statter _) -> with config logger statter)
runTraceInTelemetry :: (Member Telemetry sig, Carrier sig m, Monad m) runTraceInTelemetry :: (Member Telemetry sig, Carrier sig m, Monad m)
=> Eff (TraceInTelemetryC m) a => Eff (TraceInTelemetryC m) a
-> m a -> m a

View File

@ -33,7 +33,6 @@ import Semantic.Analysis
import Semantic.Config import Semantic.Config
import Semantic.Graph import Semantic.Graph
import Semantic.Task import Semantic.Task
import Semantic.Telemetry (LogQueue, StatQueue)
import System.Exit (die) import System.Exit (die)
import System.FilePath.Posix (takeDirectory) import System.FilePath.Posix (takeDirectory)
@ -83,7 +82,7 @@ evalTypeScriptProject = justEvaluating <=< evaluateProject (Proxy :: Proxy 'Lang
typecheckGoFile = checking <=< evaluateProjectWithCaching (Proxy :: Proxy 'Language.Go) goParser typecheckGoFile = checking <=< evaluateProjectWithCaching (Proxy :: Proxy 'Language.Go) goParser
typecheckRubyFile = checking <=< evaluateProjectWithCaching (Proxy :: Proxy 'Language.Ruby) rubyParser typecheckRubyFile = checking <=< evaluateProjectWithCaching (Proxy :: Proxy 'Language.Ruby) rubyParser
callGraphProject parser proxy opts paths = runTaskWithOptions opts $ do callGraphProject parser proxy paths = runTask' $ do
blobs <- catMaybes <$> traverse readBlobFromFile (flip File (Language.reflect proxy) <$> paths) blobs <- catMaybes <$> traverse readBlobFromFile (flip File (Language.reflect proxy) <$> paths)
package <- fmap snd <$> parsePackage parser (Project (takeDirectory (maybe "/" fst (uncons paths))) blobs (Language.reflect proxy) []) package <- fmap snd <$> parsePackage parser (Project (takeDirectory (maybe "/" fst (uncons paths))) blobs (Language.reflect proxy) [])
modules <- topologicalSort <$> runImportGraphToModules proxy package modules <- topologicalSort <$> runImportGraphToModules proxy package
@ -92,28 +91,29 @@ callGraphProject parser proxy opts paths = runTaskWithOptions opts $ do
evaluatePythonProject = justEvaluating <=< evaluatePythonProjects (Proxy @'Language.Python) pythonParser Language.Python evaluatePythonProject = justEvaluating <=< evaluatePythonProjects (Proxy @'Language.Python) pythonParser Language.Python
callGraphRubyProject = callGraphProject rubyParser (Proxy @'Language.Ruby) debugOptions callGraphRubyProject = callGraphProject rubyParser (Proxy @'Language.Ruby)
evaluateProject proxy parser paths = withOptions debugOptions $ \ config logger statter ->
evaluateProject' (TaskSession config "-" logger statter) proxy parser paths
-- Evaluate a project consisting of the listed paths. -- Evaluate a project consisting of the listed paths.
evaluateProject proxy parser paths = withOptions debugOptions $ \ config logger statter -> -- TODO: This is used by our specs and should be moved into SpecHelpers.hs
evaluateProject' (TaskConfig config logger statter) proxy parser paths evaluateProject' session proxy parser paths = do
res <- runTask session $ do
blobs <- catMaybes <$> traverse readBlobFromFile (flip File (Language.reflect proxy) <$> paths)
package <- fmap (quieterm . snd) <$> parsePackage parser (Project (takeDirectory (maybe "/" fst (uncons paths))) blobs (Language.reflect proxy) [])
modules <- topologicalSort <$> runImportGraphToModules proxy package
trace $ "evaluating with load order: " <> show (map (modulePath . moduleInfo) modules)
pure (id @(Evaluator _ Precise (Value _ Precise) _ _)
(runModuleTable
(runModules (ModuleTable.modulePaths (packageModules package))
(raiseHandler (runReader (packageInfo package))
(raiseHandler (evalState (lowerBound @Span))
(raiseHandler (runReader (lowerBound @Span))
(evaluate proxy (runDomainEffects (evalTerm withTermSpans)) modules)))))))
either (die . displayException) pure res
data TaskConfig = TaskConfig Config LogQueue StatQueue evaluatePythonProjects proxy parser lang path = runTask' $ do
evaluateProject' (TaskConfig config logger statter) proxy parser paths = either (die . displayException) pure <=< runTaskWithConfig config logger statter $ do
blobs <- catMaybes <$> traverse readBlobFromFile (flip File (Language.reflect proxy) <$> paths)
package <- fmap (quieterm . snd) <$> parsePackage parser (Project (takeDirectory (maybe "/" fst (uncons paths))) blobs (Language.reflect proxy) [])
modules <- topologicalSort <$> runImportGraphToModules proxy package
trace $ "evaluating with load order: " <> show (map (modulePath . moduleInfo) modules)
pure (id @(Evaluator _ Precise (Value _ Precise) _ _)
(runModuleTable
(runModules (ModuleTable.modulePaths (packageModules package))
(raiseHandler (runReader (packageInfo package))
(raiseHandler (evalState (lowerBound @Span))
(raiseHandler (runReader (lowerBound @Span))
(evaluate proxy (runDomainEffects (evalTerm withTermSpans)) modules)))))))
evaluatePythonProjects proxy parser lang path = runTaskWithOptions debugOptions $ do
project <- readProject Nothing path lang [] project <- readProject Nothing path lang []
package <- fmap quieterm <$> parsePythonPackage parser project package <- fmap quieterm <$> parsePythonPackage parser project
modules <- topologicalSort <$> runImportGraphToModules proxy package modules <- topologicalSort <$> runImportGraphToModules proxy package
@ -127,7 +127,7 @@ evaluatePythonProjects proxy parser lang path = runTaskWithOptions debugOptions
(evaluate proxy (runDomainEffects (evalTerm withTermSpans)) modules))))))) (evaluate proxy (runDomainEffects (evalTerm withTermSpans)) modules)))))))
evaluateProjectWithCaching proxy parser path = runTaskWithOptions debugOptions $ do evaluateProjectWithCaching proxy parser path = runTask' $ do
project <- readProject Nothing path (Language.reflect proxy) [] project <- readProject Nothing path (Language.reflect proxy) []
package <- fmap (quieterm . snd) <$> parsePackage parser project package <- fmap (quieterm . snd) <$> parsePackage parser project
modules <- topologicalSort <$> runImportGraphToModules proxy package modules <- topologicalSort <$> runImportGraphToModules proxy package
@ -141,10 +141,13 @@ evaluateProjectWithCaching proxy parser path = runTaskWithOptions debugOptions $
parseFile :: Parser term -> FilePath -> IO term parseFile :: Parser term -> FilePath -> IO term
parseFile parser = runTask . (parse parser <=< readBlob . file) parseFile parser = runTask' . (parse parser <=< readBlob . file)
blob :: FilePath -> IO Blob blob :: FilePath -> IO Blob
blob = runTask . readBlob . file blob = runTask' . readBlob . file
runTask' :: TaskEff a -> IO a
runTask' task = runTaskWithOptions debugOptions task >>= either (die . displayException) pure
mergeErrors :: Either (SomeError (Sum errs)) (Either (SomeError err) result) -> Either (SomeError (Sum (err ': errs))) result mergeErrors :: Either (SomeError (Sum errs)) (Either (SomeError err) result) -> Either (SomeError (Sum (err ': errs))) result
mergeErrors = either (\ (SomeError sum) -> Left (SomeError (weaken sum))) (either (\ (SomeError err) -> Left (SomeError (inject err))) Right) mergeErrors = either (\ (SomeError sum) -> Left (SomeError (weaken sum))) (either (\ (SomeError err) -> Left (SomeError (inject err))) Right)

View File

@ -7,8 +7,8 @@ import qualified Language.Go.Assignment as Go
import SpecHelpers import SpecHelpers
spec :: TaskConfig -> Spec spec :: TaskSession -> Spec
spec config = parallel $ do spec session = parallel $ do
describe "Go" $ do describe "Go" $ do
it "imports and wildcard imports" $ do it "imports and wildcard imports" $ do
(scopeGraph, (heap, res)) <- evaluate ["main.go", "foo/foo.go", "bar/bar.go", "bar/rab.go"] (scopeGraph, (heap, res)) <- evaluate ["main.go", "foo/foo.go", "bar/bar.go", "bar/rab.go"]
@ -33,4 +33,4 @@ spec config = parallel $ do
where where
fixtures = "test/fixtures/go/analysis/" fixtures = "test/fixtures/go/analysis/"
evaluate = evalGoProject . map (fixtures <>) evaluate = evalGoProject . map (fixtures <>)
evalGoProject = testEvaluating <=< evaluateProject' config (Proxy :: Proxy 'Language.Go) goParser evalGoProject = testEvaluating <=< evaluateProject' session (Proxy :: Proxy 'Language.Go) goParser

View File

@ -9,8 +9,8 @@ import qualified Language.PHP.Assignment as PHP
import SpecHelpers import SpecHelpers
spec :: TaskConfig -> Spec spec :: TaskSession -> Spec
spec config = parallel $ do spec session = parallel $ do
describe "PHP" $ do describe "PHP" $ do
xit "evaluates include and require" $ do xit "evaluates include and require" $ do
(scopeGraph, (heap, res)) <- evaluate ["main.php", "foo.php", "bar.php"] (scopeGraph, (heap, res)) <- evaluate ["main.php", "foo.php", "bar.php"]
@ -46,4 +46,4 @@ spec config = parallel $ do
where where
fixtures = "test/fixtures/php/analysis/" fixtures = "test/fixtures/php/analysis/"
evaluate = evalPHPProject . map (fixtures <>) evaluate = evalPHPProject . map (fixtures <>)
evalPHPProject = testEvaluating <=< evaluateProject' config (Proxy :: Proxy 'Language.PHP) phpParser evalPHPProject = testEvaluating <=< evaluateProject' session (Proxy :: Proxy 'Language.PHP) phpParser

View File

@ -9,8 +9,8 @@ import qualified Data.Language as Language
import SpecHelpers import SpecHelpers
spec :: TaskConfig -> Spec spec :: TaskSession -> Spec
spec config = parallel $ do spec session = parallel $ do
describe "Python" $ do describe "Python" $ do
it "imports" $ do it "imports" $ do
(scopeGraph, (heap, res)) <- evaluate ["main.py", "a.py", "b/__init__.py", "b/c.py"] (scopeGraph, (heap, res)) <- evaluate ["main.py", "a.py", "b/__init__.py", "b/c.py"]
@ -72,4 +72,4 @@ spec config = parallel $ do
where where
fixtures = "test/fixtures/python/analysis/" fixtures = "test/fixtures/python/analysis/"
evaluate = evalPythonProject . map (fixtures <>) evaluate = evalPythonProject . map (fixtures <>)
evalPythonProject = testEvaluating <=< evaluateProject' config (Proxy :: Proxy 'Language.Python) pythonParser evalPythonProject = testEvaluating <=< evaluateProject' session (Proxy :: Proxy 'Language.Python) pythonParser

View File

@ -14,8 +14,8 @@ import Data.Sum
import SpecHelpers import SpecHelpers
spec :: TaskConfig -> Spec spec :: TaskSession -> Spec
spec config = parallel $ do spec session = parallel $ do
describe "Ruby" $ do describe "Ruby" $ do
it "evaluates require_relative" $ do it "evaluates require_relative" $ do
(scopeGraph, (heap, res)) <- evaluate ["main.rb", "foo.rb"] (scopeGraph, (heap, res)) <- evaluate ["main.rb", "foo.rb"]
@ -101,4 +101,4 @@ spec config = parallel $ do
where where
fixtures = "test/fixtures/ruby/analysis/" fixtures = "test/fixtures/ruby/analysis/"
evaluate = evalRubyProject . map (fixtures <>) evaluate = evalRubyProject . map (fixtures <>)
evalRubyProject = testEvaluating <=< evaluateProject' config (Proxy :: Proxy 'Language.Ruby) rubyParser evalRubyProject = testEvaluating <=< evaluateProject' session (Proxy :: Proxy 'Language.Ruby) rubyParser

View File

@ -24,8 +24,8 @@ import Data.Text (pack)
import qualified Language.TypeScript.Assignment as TypeScript import qualified Language.TypeScript.Assignment as TypeScript
import SpecHelpers import SpecHelpers
spec :: TaskConfig -> Spec spec :: TaskSession -> Spec
spec config = parallel $ do spec session = parallel $ do
describe "TypeScript" $ do describe "TypeScript" $ do
it "qualified export from" $ do it "qualified export from" $ do
(scopeGraph, (heap, res)) <- evaluate ["main6.ts", "baz.ts", "foo.ts"] (scopeGraph, (heap, res)) <- evaluate ["main6.ts", "baz.ts", "foo.ts"]
@ -184,7 +184,7 @@ spec config = parallel $ do
where where
fixtures = "test/fixtures/typescript/analysis/" fixtures = "test/fixtures/typescript/analysis/"
evaluate = evalTypeScriptProject . map (fixtures <>) evaluate = evalTypeScriptProject . map (fixtures <>)
evalTypeScriptProject = testEvaluating <=< (evaluateProject' config (Proxy :: Proxy 'Language.TypeScript) typescriptParser) evalTypeScriptProject = testEvaluating <=< (evaluateProject' session (Proxy :: Proxy 'Language.TypeScript) typescriptParser)
type TypeScriptTerm = Quieterm (Sum TypeScript.Syntax) Location type TypeScriptTerm = Quieterm (Sum TypeScript.Syntax) Location
type TypeScriptEvalError = BaseError (EvalError TypeScriptTerm Precise (Concrete.Value TypeScriptTerm Precise)) type TypeScriptEvalError = BaseError (EvalError TypeScriptTerm Precise (Concrete.Value TypeScriptTerm Precise))

View File

@ -22,7 +22,6 @@ import Semantic.Config (Config (..), Options (..), defaultOptions)
import qualified Semantic.IO as IO import qualified Semantic.IO as IO
import Semantic.Task import Semantic.Task
import Semantic.Task.Files import Semantic.Task.Files
import Semantic.Util (TaskConfig (..))
import System.Directory import System.Directory
import System.Exit (die) import System.Exit (die)
import System.FilePath.Glob import System.FilePath.Glob
@ -33,7 +32,7 @@ import Test.Hspec
main :: IO () main :: IO ()
main = withOptions opts $ \ config logger statter -> hspec . parallel $ do main = withOptions opts $ \ config logger statter -> hspec . parallel $ do
let args = TaskConfig config logger statter let args = TaskSession config "-" logger statter
runIO setupExampleRepos runIO setupExampleRepos
@ -42,11 +41,11 @@ main = withOptions opts $ \ config logger statter -> hspec . parallel $ do
parallel . describe languageName $ parseExamples args lang tsDir parallel . describe languageName $ parseExamples args lang tsDir
where where
parseExamples (TaskConfig config logger statter) LanguageExample{..} tsDir = do parseExamples session LanguageExample{..} tsDir = do
knownFailures <- runIO $ knownFailuresForPath tsDir languageKnownFailuresTxt knownFailures <- runIO $ knownFailuresForPath tsDir languageKnownFailuresTxt
files <- runIO $ globDir1 (compile ("**/*" <> languageExtension)) (tsDir </> languageExampleDir) files <- runIO $ globDir1 (compile ("**/*" <> languageExtension)) (tsDir </> languageExampleDir)
for_ files $ \file -> it file $ do for_ files $ \file -> it file $ do
res <- runTaskWithConfig config logger statter (parseFilePath file) res <- runTask session (parseFilePath file)
case res of case res of
Left (SomeException e) -> case cast e of Left (SomeException e) -> case cast e of
-- We have a number of known assignment timeouts, consider these pending specs instead of failing the build. -- We have a number of known assignment timeouts, consider these pending specs instead of failing the build.

View File

@ -18,7 +18,7 @@ import Semantic.Config (defaultOptions)
import Semantic.Graph import Semantic.Graph
import Semantic.IO import Semantic.IO
callGraphPythonProject paths = runTask $ do callGraphPythonProject paths = runTaskOrDie $ do
let proxy = Proxy @'Language.Python let proxy = Proxy @'Language.Python
let lang = Language.Python let lang = Language.Python
blobs <- catMaybes <$> traverse readBlobFromFile (flip File lang <$> paths) blobs <- catMaybes <$> traverse readBlobFromFile (flip File lang <$> paths)

View File

@ -11,7 +11,7 @@ import SpecHelpers
languages :: [FilePath] languages :: [FilePath]
languages = ["go", "javascript", "json", "python", "ruby", "typescript"] languages = ["go", "javascript", "json", "python", "ruby", "typescript"]
spec :: TaskConfig -> Spec spec :: TaskSession -> Spec
spec config = parallel $ do spec config = parallel $ do
for_ languages $ \language -> do for_ languages $ \language -> do
let dir = "test/fixtures" </> language </> "corpus" let dir = "test/fixtures" </> language </> "corpus"
@ -81,13 +81,13 @@ examples directory = do
normalizeName :: FilePath -> FilePath normalizeName :: FilePath -> FilePath
normalizeName path = dropExtension $ dropExtension path normalizeName path = dropExtension $ dropExtension path
testParse :: TaskConfig -> FilePath -> FilePath -> Expectation testParse :: TaskSession -> FilePath -> FilePath -> Expectation
testParse config path expectedOutput = do testParse session path expectedOutput = do
actual <- verbatim <$> parseFilePath config path actual <- verbatim <$> parseFilePath session path
expected <- verbatim <$> B.readFile expectedOutput expected <- verbatim <$> B.readFile expectedOutput
actual `shouldBe` expected actual `shouldBe` expected
testDiff :: TaskConfig -> Both FilePath -> FilePath -> Expectation testDiff :: TaskSession -> Both FilePath -> FilePath -> Expectation
testDiff config paths expectedOutput = do testDiff config paths expectedOutput = do
actual <- verbatim <$> diffFilePaths config paths actual <- verbatim <$> diffFilePaths config paths
expected <- verbatim <$> B.readFile expectedOutput expected <- verbatim <$> B.readFile expectedOutput

View File

@ -57,7 +57,7 @@ spec = parallel $ do
it "summarizes changed methods" $ do it "summarizes changed methods" $ do
sourceBlobs <- blobsForPaths (Both "ruby/toc/methods.A.rb" "ruby/toc/methods.B.rb") sourceBlobs <- blobsForPaths (Both "ruby/toc/methods.A.rb" "ruby/toc/methods.B.rb")
diff <- runTask $ diffWithParser rubyParser sourceBlobs diff <- runTaskOrDie $ diffWithParser rubyParser sourceBlobs
diffTOC diff `shouldBe` diffTOC diff `shouldBe`
[ TOCSummary "Method" "self.foo" (Span (Pos 1 1) (Pos 2 4)) "added" [ TOCSummary "Method" "self.foo" (Span (Pos 1 1) (Pos 2 4)) "added"
, TOCSummary "Method" "bar" (Span (Pos 4 1) (Pos 6 4)) "modified" , TOCSummary "Method" "bar" (Span (Pos 4 1) (Pos 6 4)) "modified"
@ -66,7 +66,7 @@ spec = parallel $ do
xit "summarizes changed classes" $ do xit "summarizes changed classes" $ do
sourceBlobs <- blobsForPaths (Both "ruby/toc/classes.A.rb" "ruby/toc/classes.B.rb") sourceBlobs <- blobsForPaths (Both "ruby/toc/classes.A.rb" "ruby/toc/classes.B.rb")
diff <- runTask $ diffWithParser rubyParser sourceBlobs diff <- runTaskOrDie $ diffWithParser rubyParser sourceBlobs
diffTOC diff `shouldBe` diffTOC diff `shouldBe`
[ TOCSummary "Class" "Baz" (Span (Pos 1 1) (Pos 2 4)) "removed" [ TOCSummary "Class" "Baz" (Span (Pos 1 1) (Pos 2 4)) "removed"
, TOCSummary "Class" "Foo" (Span (Pos 1 1) (Pos 3 4)) "modified" , TOCSummary "Class" "Foo" (Span (Pos 1 1) (Pos 3 4)) "modified"
@ -75,37 +75,37 @@ spec = parallel $ do
it "dedupes changes in same parent method" $ do it "dedupes changes in same parent method" $ do
sourceBlobs <- blobsForPaths (Both "javascript/toc/duplicate-parent.A.js" "javascript/toc/duplicate-parent.B.js") sourceBlobs <- blobsForPaths (Both "javascript/toc/duplicate-parent.A.js" "javascript/toc/duplicate-parent.B.js")
diff <- runTask $ diffWithParser typescriptParser sourceBlobs diff <- runTaskOrDie $ diffWithParser typescriptParser sourceBlobs
diffTOC diff `shouldBe` diffTOC diff `shouldBe`
[ TOCSummary "Function" "myFunction" (Span (Pos 1 1) (Pos 6 2)) "modified" ] [ TOCSummary "Function" "myFunction" (Span (Pos 1 1) (Pos 6 2)) "modified" ]
it "dedupes similar methods" $ do it "dedupes similar methods" $ do
sourceBlobs <- blobsForPaths (Both "javascript/toc/erroneous-duplicate-method.A.js" "javascript/toc/erroneous-duplicate-method.B.js") sourceBlobs <- blobsForPaths (Both "javascript/toc/erroneous-duplicate-method.A.js" "javascript/toc/erroneous-duplicate-method.B.js")
diff <- runTask $ diffWithParser typescriptParser sourceBlobs diff <- runTaskOrDie $ diffWithParser typescriptParser sourceBlobs
diffTOC diff `shouldBe` diffTOC diff `shouldBe`
[ TOCSummary "Function" "performHealthCheck" (Span (Pos 8 1) (Pos 29 2)) "modified" ] [ TOCSummary "Function" "performHealthCheck" (Span (Pos 8 1) (Pos 29 2)) "modified" ]
it "summarizes Go methods with receivers with special formatting" $ do it "summarizes Go methods with receivers with special formatting" $ do
sourceBlobs <- blobsForPaths (Both "go/toc/method-with-receiver.A.go" "go/toc/method-with-receiver.B.go") sourceBlobs <- blobsForPaths (Both "go/toc/method-with-receiver.A.go" "go/toc/method-with-receiver.B.go")
diff <- runTask $ diffWithParser goParser sourceBlobs diff <- runTaskOrDie $ diffWithParser goParser sourceBlobs
diffTOC diff `shouldBe` diffTOC diff `shouldBe`
[ TOCSummary "Method" "(*apiClient) CheckAuth" (Span (Pos 3 1) (Pos 3 101)) "added" ] [ TOCSummary "Method" "(*apiClient) CheckAuth" (Span (Pos 3 1) (Pos 3 101)) "added" ]
it "summarizes Ruby methods that start with two identifiers" $ do it "summarizes Ruby methods that start with two identifiers" $ do
sourceBlobs <- blobsForPaths (Both "ruby/toc/method-starts-with-two-identifiers.A.rb" "ruby/toc/method-starts-with-two-identifiers.B.rb") sourceBlobs <- blobsForPaths (Both "ruby/toc/method-starts-with-two-identifiers.A.rb" "ruby/toc/method-starts-with-two-identifiers.B.rb")
diff <- runTask $ diffWithParser rubyParser sourceBlobs diff <- runTaskOrDie $ diffWithParser rubyParser sourceBlobs
diffTOC diff `shouldBe` diffTOC diff `shouldBe`
[ TOCSummary "Method" "foo" (Span (Pos 1 1) (Pos 4 4)) "modified" ] [ TOCSummary "Method" "foo" (Span (Pos 1 1) (Pos 4 4)) "modified" ]
it "handles unicode characters in file" $ do it "handles unicode characters in file" $ do
sourceBlobs <- blobsForPaths (Both "ruby/toc/unicode.A.rb" "ruby/toc/unicode.B.rb") sourceBlobs <- blobsForPaths (Both "ruby/toc/unicode.A.rb" "ruby/toc/unicode.B.rb")
diff <- runTask $ diffWithParser rubyParser sourceBlobs diff <- runTaskOrDie $ diffWithParser rubyParser sourceBlobs
diffTOC diff `shouldBe` diffTOC diff `shouldBe`
[ TOCSummary "Method" "foo" (Span (Pos 6 1) (Pos 7 4)) "added" ] [ TOCSummary "Method" "foo" (Span (Pos 6 1) (Pos 7 4)) "added" ]
it "properly slices source blob that starts with a newline and has multi-byte chars" $ do it "properly slices source blob that starts with a newline and has multi-byte chars" $ do
sourceBlobs <- blobsForPaths (Both "javascript/toc/starts-with-newline.js" "javascript/toc/starts-with-newline.js") sourceBlobs <- blobsForPaths (Both "javascript/toc/starts-with-newline.js" "javascript/toc/starts-with-newline.js")
diff <- runTaskWithOptions (defaultOptions { optionsLogLevel = Nothing }) $ diffWithParser typescriptParser sourceBlobs diff <- runTaskOrDie $ diffWithParser typescriptParser sourceBlobs
diffTOC diff `shouldBe` [] diffTOC diff `shouldBe` []
prop "inserts of methods and functions are summarized" . forAll ((not . isMethodOrFunction . Prelude.snd) `filterT` tiers) $ prop "inserts of methods and functions are summarized" . forAll ((not . isMethodOrFunction . Prelude.snd) `filterT` tiers) $
@ -148,22 +148,22 @@ spec = parallel $ do
describe "diff with ToCDiffRenderer'" $ do describe "diff with ToCDiffRenderer'" $ do
it "produces JSON output" $ do it "produces JSON output" $ do
blobs <- blobsForPaths (Both "ruby/toc/methods.A.rb" "ruby/toc/methods.B.rb") blobs <- blobsForPaths (Both "ruby/toc/methods.A.rb" "ruby/toc/methods.B.rb")
output <- runTask (diffSummaryBuilder Format.JSON [blobs]) output <- runTaskOrDie (diffSummaryBuilder Format.JSON [blobs])
runBuilder output `shouldBe` ("{\"changes\":{\"test/fixtures/ruby/toc/methods.A.rb -> test/fixtures/ruby/toc/methods.B.rb\":[{\"span\":{\"start\":[1,1],\"end\":[2,4]},\"category\":\"Method\",\"term\":\"self.foo\",\"changeType\":\"added\"},{\"span\":{\"start\":[4,1],\"end\":[6,4]},\"category\":\"Method\",\"term\":\"bar\",\"changeType\":\"modified\"},{\"span\":{\"start\":[4,1],\"end\":[5,4]},\"category\":\"Method\",\"term\":\"baz\",\"changeType\":\"removed\"}]},\"errors\":{}}\n" :: ByteString) runBuilder output `shouldBe` ("{\"changes\":{\"test/fixtures/ruby/toc/methods.A.rb -> test/fixtures/ruby/toc/methods.B.rb\":[{\"span\":{\"start\":[1,1],\"end\":[2,4]},\"category\":\"Method\",\"term\":\"self.foo\",\"changeType\":\"added\"},{\"span\":{\"start\":[4,1],\"end\":[6,4]},\"category\":\"Method\",\"term\":\"bar\",\"changeType\":\"modified\"},{\"span\":{\"start\":[4,1],\"end\":[5,4]},\"category\":\"Method\",\"term\":\"baz\",\"changeType\":\"removed\"}]},\"errors\":{}}\n" :: ByteString)
it "produces JSON output if there are parse errors" $ do it "produces JSON output if there are parse errors" $ do
blobs <- blobsForPaths (Both "ruby/toc/methods.A.rb" "ruby/toc/methods.X.rb") blobs <- blobsForPaths (Both "ruby/toc/methods.A.rb" "ruby/toc/methods.X.rb")
output <- runTaskWithOptions (defaultOptions { optionsLogLevel = Nothing }) (diffSummaryBuilder Format.JSON [blobs]) output <- runTaskOrDie (diffSummaryBuilder Format.JSON [blobs])
runBuilder output `shouldBe` ("{\"changes\":{\"test/fixtures/ruby/toc/methods.A.rb -> test/fixtures/ruby/toc/methods.X.rb\":[{\"span\":{\"start\":[1,1],\"end\":[2,4]},\"category\":\"Method\",\"term\":\"bar\",\"changeType\":\"removed\"},{\"span\":{\"start\":[4,1],\"end\":[5,4]},\"category\":\"Method\",\"term\":\"baz\",\"changeType\":\"removed\"}]},\"errors\":{\"test/fixtures/ruby/toc/methods.A.rb -> test/fixtures/ruby/toc/methods.X.rb\":[{\"span\":{\"start\":[1,1],\"end\":[2,3]},\"error\":\"expected end of input nodes, but got ParseError\",\"language\":\"Ruby\"}]}}\n" :: ByteString) runBuilder output `shouldBe` ("{\"changes\":{\"test/fixtures/ruby/toc/methods.A.rb -> test/fixtures/ruby/toc/methods.X.rb\":[{\"span\":{\"start\":[1,1],\"end\":[2,4]},\"category\":\"Method\",\"term\":\"bar\",\"changeType\":\"removed\"},{\"span\":{\"start\":[4,1],\"end\":[5,4]},\"category\":\"Method\",\"term\":\"baz\",\"changeType\":\"removed\"}]},\"errors\":{\"test/fixtures/ruby/toc/methods.A.rb -> test/fixtures/ruby/toc/methods.X.rb\":[{\"span\":{\"start\":[1,1],\"end\":[2,3]},\"error\":\"expected end of input nodes, but got ParseError\",\"language\":\"Ruby\"}]}}\n" :: ByteString)
it "ignores anonymous functions" $ do it "ignores anonymous functions" $ do
blobs <- blobsForPaths (Both "ruby/toc/lambda.A.rb" "ruby/toc/lambda.B.rb") blobs <- blobsForPaths (Both "ruby/toc/lambda.A.rb" "ruby/toc/lambda.B.rb")
output <- runTask (diffSummaryBuilder Format.JSON [blobs]) output <- runTaskOrDie (diffSummaryBuilder Format.JSON [blobs])
runBuilder output `shouldBe` ("{\"changes\":{},\"errors\":{}}\n" :: ByteString) runBuilder output `shouldBe` ("{\"changes\":{},\"errors\":{}}\n" :: ByteString)
it "summarizes Markdown headings" $ do it "summarizes Markdown headings" $ do
blobs <- blobsForPaths (Both "markdown/toc/headings.A.md" "markdown/toc/headings.B.md") blobs <- blobsForPaths (Both "markdown/toc/headings.A.md" "markdown/toc/headings.B.md")
output <- runTask (diffSummaryBuilder Format.JSON [blobs]) output <- runTaskOrDie (diffSummaryBuilder Format.JSON [blobs])
runBuilder output `shouldBe` ("{\"changes\":{\"test/fixtures/markdown/toc/headings.A.md -> test/fixtures/markdown/toc/headings.B.md\":[{\"span\":{\"start\":[1,1],\"end\":[3,16]},\"category\":\"Heading 1\",\"term\":\"Introduction\",\"changeType\":\"removed\"},{\"span\":{\"start\":[5,1],\"end\":[7,4]},\"category\":\"Heading 2\",\"term\":\"Two\",\"changeType\":\"modified\"},{\"span\":{\"start\":[9,1],\"end\":[11,10]},\"category\":\"Heading 3\",\"term\":\"This heading is new\",\"changeType\":\"added\"},{\"span\":{\"start\":[13,1],\"end\":[14,4]},\"category\":\"Heading 1\",\"term\":\"Final\",\"changeType\":\"added\"}]},\"errors\":{}}\n" :: ByteString) runBuilder output `shouldBe` ("{\"changes\":{\"test/fixtures/markdown/toc/headings.A.md -> test/fixtures/markdown/toc/headings.B.md\":[{\"span\":{\"start\":[1,1],\"end\":[3,16]},\"category\":\"Heading 1\",\"term\":\"Introduction\",\"changeType\":\"removed\"},{\"span\":{\"start\":[5,1],\"end\":[7,4]},\"category\":\"Heading 2\",\"term\":\"Two\",\"changeType\":\"modified\"},{\"span\":{\"start\":[9,1],\"end\":[11,10]},\"category\":\"Heading 3\",\"term\":\"This heading is new\",\"changeType\":\"added\"},{\"span\":{\"start\":[13,1],\"end\":[14,4]},\"category\":\"Heading 1\",\"term\":\"Final\",\"changeType\":\"added\"}]},\"errors\":{}}\n" :: ByteString)

View File

@ -65,7 +65,7 @@ spec = describe "reprinting" $ do
printed `shouldBe` Right src printed `shouldBe` Right src
it "should be able to parse the output of a refactor" $ do it "should be able to parse the output of a refactor" $ do
let (Just tagged) = rewrite (mark Unmodified tree) (topDownAny increaseNumbers) let (Just tagged) = rewrite (mark Unmodified tree) (topDownAny increaseNumbers)
let (Right printed) = runReprinter src defaultJSONPipeline tagged let (Right printed) = runReprinter src defaultJSONPipeline tagged
tree' <- runTask (parse jsonParser (Blob printed path Language.JSON)) tree' <- runTaskOrDie (parse jsonParser (Blob printed path Language.JSON))
length tree' `shouldSatisfy` (/= 0) length tree' `shouldSatisfy` (/= 0)

View File

@ -18,13 +18,13 @@ spec = parallel $ do
describe "parseDiffBuilder" $ describe "parseDiffBuilder" $
for_ diffFixtures $ \ (diffRenderer, runDiff, files, expected) -> for_ diffFixtures $ \ (diffRenderer, runDiff, files, expected) ->
it ("renders to " <> diffRenderer <> " with files " <> show files) $ do it ("renders to " <> diffRenderer <> " with files " <> show files) $ do
output <- runTask $ readBlobPairs (Right files) >>= runDiff output <- runTaskOrDie $ readBlobPairs (Right files) >>= runDiff
runBuilder output `shouldBe'` expected runBuilder output `shouldBe'` expected
describe "parseTermBuilder" $ describe "parseTermBuilder" $
for_ parseFixtures $ \ (format, runParse, files, expected) -> for_ parseFixtures $ \ (format, runParse, files, expected) ->
it ("renders to " <> format <> " with files " <> show files) $ do it ("renders to " <> format <> " with files " <> show files) $ do
output <- runTask $ readBlobs (Right files) >>= runParse output <- runTaskOrDie $ readBlobs (Right files) >>= runParse
runBuilder output `shouldBe'` expected runBuilder output `shouldBe'` expected
where where
shouldBe' actual' expectedFile = do shouldBe' actual' expectedFile = do

View File

@ -12,14 +12,14 @@ spec :: Spec
spec = parallel $ do spec = parallel $ do
describe "parseBlob" $ do describe "parseBlob" $ do
it "returns error if given an unknown language (json)" $ do it "returns error if given an unknown language (json)" $ do
output <- fmap runBuilder . runTask $ parseTermBuilder TermJSONTree [ methodsBlob { blobLanguage = Unknown } ] output <- fmap runBuilder . runTaskOrDie $ parseTermBuilder TermJSONTree [ methodsBlob { blobLanguage = Unknown } ]
output `shouldBe` "{\"trees\":[{\"path\":\"methods.rb\",\"error\":\"NoLanguageForBlob \\\"methods.rb\\\"\",\"language\":\"Unknown\"}]}\n" output `shouldBe` "{\"trees\":[{\"path\":\"methods.rb\",\"error\":\"NoLanguageForBlob \\\"methods.rb\\\"\",\"language\":\"Unknown\"}]}\n"
it "throws if given an unknown language for sexpression output" $ do it "throws if given an unknown language for sexpression output" $ do
runTask (parseTermBuilder TermSExpression [methodsBlob { blobLanguage = Unknown }]) `shouldThrow` (== ExitFailure 1) runTaskOrDie (parseTermBuilder TermSExpression [methodsBlob { blobLanguage = Unknown }]) `shouldThrow` (== ExitFailure 1)
it "renders with the specified renderer" $ do it "renders with the specified renderer" $ do
output <- fmap runBuilder . runTask $ parseTermBuilder TermSExpression [methodsBlob] output <- fmap runBuilder . runTaskOrDie $ parseTermBuilder TermSExpression [methodsBlob]
output `shouldBe` "(Statements\n (Method\n (Empty)\n (Identifier)\n (Statements)))\n" output `shouldBe` "(Statements\n (Method\n (Empty)\n (Identifier)\n (Statements)))\n"
where where
methodsBlob = Blob "def foo\nend\n" "methods.rb" Ruby methodsBlob = Blob "def foo\nend\n" "methods.rb" Ruby

View File

@ -33,16 +33,15 @@ import qualified Semantic.Spec
import qualified Semantic.CLI.Spec import qualified Semantic.CLI.Spec
import qualified Semantic.IO.Spec import qualified Semantic.IO.Spec
import qualified Semantic.Stat.Spec import qualified Semantic.Stat.Spec
import Semantic.Config (defaultOptions) import Semantic.Config (defaultOptions, optionsLogLevel)
import Semantic.Task (withOptions) import Semantic.Task (withOptions, TaskSession(..))
import Semantic.Util (TaskConfig(..))
import qualified Proto3.Roundtrip import qualified Proto3.Roundtrip
import Test.Hspec import Test.Hspec
main :: IO () main :: IO ()
main = do main = do
withOptions defaultOptions $ \ config logger statter -> hspec $ do withOptions defaultOptions { optionsLogLevel = Nothing } $ \ config logger statter -> hspec $ do
let args = TaskConfig config logger statter let args = TaskSession config "-" logger statter
describe "Semantic.Stat" Semantic.Stat.Spec.spec describe "Semantic.Stat" Semantic.Stat.Spec.spec
parallel $ do parallel $ do
describe "Analysis.Go" (Analysis.Go.Spec.spec args) describe "Analysis.Go" (Analysis.Go.Spec.spec args)

View File

@ -7,6 +7,8 @@ module SpecHelpers
, parseFilePath , parseFilePath
, parseTestFile , parseTestFile
, readFilePair , readFilePair
, runTaskOrDie
, TaskSession(..)
, testEvaluating , testEvaluating
, verbatim , verbatim
, Verbatim(..) , Verbatim(..)
@ -78,7 +80,7 @@ import qualified Data.ByteString as B
import qualified Data.Set as Set import qualified Data.Set as Set
import Data.Set (Set) import Data.Set (Set)
import qualified Semantic.IO as IO import qualified Semantic.IO as IO
import Semantic.Config (Config) import Semantic.Config (Config(..), optionsLogLevel)
import Semantic.Telemetry (LogQueue, StatQueue) import Semantic.Telemetry (LogQueue, StatQueue)
import Semantic.API hiding (File, Blob, BlobPair) import Semantic.API hiding (File, Blob, BlobPair)
import System.Exit (die) import System.Exit (die)
@ -92,12 +94,12 @@ instance IsString Name where
fromString = X.name . fromString fromString = X.name . fromString
-- | Returns an s-expression formatted diff for the specified FilePath pair. -- | Returns an s-expression formatted diff for the specified FilePath pair.
diffFilePaths :: TaskConfig -> Both FilePath -> IO ByteString diffFilePaths :: TaskSession -> Both FilePath -> IO ByteString
diffFilePaths (TaskConfig config logger statter) paths = readFilePair paths >>= runTaskWithConfig config logger statter . parseDiffBuilder @[] DiffSExpression . pure >>= either (die . displayException) (pure . runBuilder) diffFilePaths session paths = readFilePair paths >>= runTask session . parseDiffBuilder @[] DiffSExpression . pure >>= either (die . displayException) (pure . runBuilder)
-- | Returns an s-expression parse tree for the specified FilePath. -- | Returns an s-expression parse tree for the specified FilePath.
parseFilePath :: TaskConfig -> FilePath -> IO ByteString parseFilePath :: TaskSession -> FilePath -> IO ByteString
parseFilePath (TaskConfig config logger statter) path = (fromJust <$> readBlobFromFile (file path)) >>= runTaskWithConfig config logger statter . parseTermBuilder @[] TermSExpression . pure >>= either (die . displayException) (pure . runBuilder) parseFilePath session path = (fromJust <$> readBlobFromFile (file path)) >>= runTask session . parseTermBuilder @[] TermSExpression . pure >>= either (die . displayException) (pure . runBuilder)
-- | Read two files to a BlobPair. -- | Read two files to a BlobPair.
readFilePair :: Both FilePath -> IO BlobPair readFilePair :: Both FilePath -> IO BlobPair
@ -105,11 +107,15 @@ readFilePair paths = let paths' = fmap file paths in
runBothWith F.readFilePair paths' runBothWith F.readFilePair paths'
parseTestFile :: Parser term -> FilePath -> IO (Blob, term) parseTestFile :: Parser term -> FilePath -> IO (Blob, term)
parseTestFile parser path = runTask $ do parseTestFile parser path = runTaskOrDie $ do
blob <- readBlob (file path) blob <- readBlob (file path)
term <- parse parser blob term <- parse parser blob
pure (blob, term) pure (blob, term)
-- Run a Task and call `die` if it returns an Exception.
runTaskOrDie :: TaskEff a -> IO a
runTaskOrDie task = runTaskWithOptions defaultOptions { optionsLogLevel = Nothing } task >>= either (die . displayException) pure
type TestEvaluatingC term type TestEvaluatingC term
= ResumableC (BaseError (AddressError Precise (Val term))) (Eff = ResumableC (BaseError (AddressError Precise (Val term))) (Eff
( ResumableC (BaseError (ValueError term Precise)) (Eff ( ResumableC (BaseError (ValueError term Precise)) (Eff