mirror of
https://github.com/github/semantic.git
synced 2025-01-02 04:10:29 +03:00
Provide LoadError with an Erroring analysis.
This commit is contained in:
parent
c94a6467ce
commit
fa34e9e499
@ -5,7 +5,6 @@ module Analysis.Abstract.Evaluating
|
||||
|
||||
import Control.Abstract.Analysis hiding (lower)
|
||||
import Control.Monad.Effect.Exception as Exc
|
||||
import Control.Monad.Effect.Resumable as Res
|
||||
import Data.Abstract.Environment
|
||||
import Data.Abstract.Evaluatable hiding (lower)
|
||||
import Data.Abstract.Module
|
||||
@ -24,7 +23,6 @@ deriving instance Member NonDet effects => Alternative (Evaluating location term
|
||||
type EvaluatingEffects location term value
|
||||
= '[ Exc (ReturnThrow value)
|
||||
, Exc (LoopThrow value)
|
||||
, Resumable (LoadError term value)
|
||||
, Fail -- Failure with an error message
|
||||
, Fresh -- For allocating new addresses and/or type variables.
|
||||
, Reader (SomeOrigin term) -- The current term’s origin.
|
||||
@ -56,10 +54,9 @@ instance ( Corecursive term
|
||||
instance Interpreter (EvaluatingEffects location term value) (Evaluating location term value) where
|
||||
type Result (EvaluatingEffects location term value) (Evaluating location term value) result
|
||||
= ( Either String
|
||||
( Either (SomeExc (LoadError term value))
|
||||
( Either (LoopThrow value)
|
||||
( Either (ReturnThrow value)
|
||||
result)))
|
||||
result))
|
||||
, EvaluatorState location term value)
|
||||
interpret
|
||||
= interpret
|
||||
@ -71,6 +68,6 @@ instance Interpreter (EvaluatingEffects location term value) (Evaluating locatio
|
||||
. flip runReader lower -- Reader (SomeOrigin term)
|
||||
. flip runFresh' 0
|
||||
. runFail
|
||||
. Res.runError
|
||||
. Exc.runError
|
||||
. Exc.runError)
|
||||
|
||||
|
@ -2,6 +2,7 @@
|
||||
module Semantic.Graph where
|
||||
|
||||
import Analysis.Abstract.ImportGraph
|
||||
import Analysis.Abstract.Erroring
|
||||
import qualified Data.Abstract.Evaluatable as Analysis
|
||||
import Data.Abstract.FreeVariables
|
||||
import Data.Abstract.Package as Package
|
||||
@ -68,10 +69,11 @@ type ImportGraphAnalysis term
|
||||
( BadVariables
|
||||
( BadValues
|
||||
( BadSyntax
|
||||
( Erroring (Analysis.LoadError term (Value (Located Precise term)))
|
||||
( Evaluating
|
||||
(Located Precise term)
|
||||
term
|
||||
(Value (Located Precise term))))))))
|
||||
(Value (Located Precise term)))))))))
|
||||
|
||||
-- | Render the import graph for a given 'Package'.
|
||||
graphImports :: ( Show ann
|
||||
|
@ -53,9 +53,20 @@ type JustEvaluating term
|
||||
( Erroring (ResolutionError (Value (Located Precise term)))
|
||||
( Erroring (Unspecialized (Value (Located Precise term)))
|
||||
( Erroring (ValueError (Located Precise term) (Value (Located Precise term)))
|
||||
( Evaluating (Located Precise term) term (Value (Located Precise term)))))))
|
||||
type EvaluatingWithHoles term = BadAddresses (BadModuleResolutions (BadVariables (BadValues (BadSyntax (Evaluating (Located Precise term) term (Value (Located Precise term)))))))
|
||||
( Erroring (LoadError term (Value (Located Precise term)))
|
||||
( Evaluating (Located Precise term) term (Value (Located Precise term))))))))
|
||||
|
||||
type EvaluatingWithHoles term
|
||||
= BadAddresses
|
||||
( BadModuleResolutions
|
||||
( BadVariables
|
||||
( BadValues
|
||||
( BadSyntax
|
||||
( Erroring (LoadError term (Value (Located Precise term)))
|
||||
( Evaluating (Located Precise term) term (Value (Located Precise term))))))))
|
||||
|
||||
type ImportGraphingWithHoles term = ImportGraphing (EvaluatingWithHoles term)
|
||||
|
||||
-- The order is significant here: Caching has to come on the outside, or its Interpreter instance
|
||||
-- will expect the TypeError exception type to have an Ord instance, which is wrong.
|
||||
type Checking term
|
||||
@ -65,8 +76,9 @@ type Checking term
|
||||
( Erroring (EvalError Type)
|
||||
( Erroring (ResolutionError Type)
|
||||
( Erroring (Unspecialized Type)
|
||||
( Erroring (LoadError term Type)
|
||||
( Retaining
|
||||
( Evaluating Monovariant term Type)))))))
|
||||
( Evaluating Monovariant term Type))))))))
|
||||
|
||||
evalGoProject path = runAnalysis @(JustEvaluating Go.Term) <$> evaluateProject goParser Language.Go Nothing path
|
||||
evalRubyProject path = runAnalysis @(JustEvaluating Ruby.Term) <$> evaluateProject rubyParser Language.Ruby rubyPrelude path
|
||||
|
Loading…
Reference in New Issue
Block a user