diff --git a/src/Semantic/Graph.hs b/src/Semantic/Graph.hs index ea7453815..055f34090 100644 --- a/src/Semantic/Graph.hs +++ b/src/Semantic/Graph.hs @@ -1,7 +1,6 @@ {-# LANGUAGE GADTs, ScopedTypeVariables, TypeOperators #-} module Semantic.Graph where -import Analysis.Abstract.BadValues import Analysis.Abstract.Evaluating import Analysis.Abstract.ImportGraph import qualified Control.Exception as Exc @@ -10,7 +9,8 @@ import Data.Abstract.Evaluatable import Data.Abstract.Located import Data.Abstract.Module import Data.Abstract.Package as Package -import Data.Abstract.Value (Value, ValueError) +import Data.Abstract.Value (Value, ValueError(..), runValueErrorWith) +import Data.ByteString.Char8 (pack) import Data.File import Data.Output import Data.Semilattice.Lower @@ -87,7 +87,7 @@ importGraphAnalysis . evaluating . runLoadError . resumingUnspecialized - . resumingBadValues + . resumingValueError . resumingEvalError . resumingResolutionError . resumingAddressError @@ -119,6 +119,22 @@ resumingAddressError = runAddressErrorWith (\ err -> traceM ("AddressError:" <> UnallocatedAddress _ -> pure lowerBound UninitializedAddress _ -> pure hole) +resumingValueError :: (AbstractHole value, Member (State (Environment location value)) effects, Show value) => Evaluator location term value (Resumable (ValueError location value) ': effects) a -> Evaluator location term value effects a +resumingValueError = runValueErrorWith (\ err -> traceM ("ValueError" <> show err) *> case err of + CallError val -> pure val + StringError val -> pure (pack (show val)) + BoolError{} -> pure True + BoundsError{} -> pure hole + IndexError{} -> pure hole + NumericError{} -> pure hole + Numeric2Error{} -> pure hole + ComparisonError{} -> pure hole + NamespaceError{} -> getEnv + BitwiseError{} -> pure hole + Bitwise2Error{} -> pure hole + KeyValueError{} -> pure (hole, hole) + ArithmeticError{} -> pure hole) + -- | Render the import graph for a given 'Package'. graphImports :: ( Show ann , Apply Declarations1 syntax diff --git a/src/Semantic/Util.hs b/src/Semantic/Util.hs index e2a1a900f..da3ac67bb 100644 --- a/src/Semantic/Util.hs +++ b/src/Semantic/Util.hs @@ -2,7 +2,6 @@ {-# OPTIONS_GHC -Wno-missing-signatures #-} module Semantic.Util where -import Analysis.Abstract.BadValues import Analysis.Abstract.Caching import Analysis.Abstract.Collecting import Analysis.Abstract.Evaluating as X @@ -40,10 +39,10 @@ evaluatingWithHoles . evaluating . runLoadError . resumingUnspecialized - . resumingBadValues @(Value Precise) + . resumingValueError . resumingEvalError . resumingResolutionError - . resumingAddressError + . resumingAddressError @(Value Precise) -- The order is significant here: caching has to run before typeChecking, or else we’ll nondeterministically produce TypeErrors as part of the result set. While this is probably actually correct, it will require us to have an Ord instance for TypeError, which we don’t have yet. checking