mirror of
https://github.com/github/semantic.git
synced 2024-12-01 09:15:01 +03:00
Merge remote-tracking branch 'origin/master' into ruby-self-class
This commit is contained in:
commit
dfd669a720
@ -94,6 +94,7 @@ library
|
||||
, Data.Syntax
|
||||
, Data.Syntax.Comment
|
||||
, Data.Syntax.Declaration
|
||||
, Data.Syntax.Directive
|
||||
, Data.Syntax.Expression
|
||||
, Data.Syntax.Literal
|
||||
, Data.Syntax.Statement
|
||||
|
@ -45,7 +45,7 @@ module Control.Abstract.Evaluator
|
||||
, throwResumable
|
||||
, throwException
|
||||
, catchException
|
||||
-- Origin
|
||||
-- | Origin
|
||||
, pushOrigin
|
||||
) where
|
||||
|
||||
|
@ -333,6 +333,8 @@ instance ( Monad (m effects)
|
||||
call op params = do
|
||||
case prjValue op of
|
||||
Just (Closure names label env) -> do
|
||||
-- Evaluate the bindings and the body within a `goto` in order to
|
||||
-- charge their origins to the closure's origin.
|
||||
goto label $ \body -> do
|
||||
bindings <- foldr (\ (name, param) rest -> do
|
||||
v <- param
|
||||
|
19
src/Data/Syntax/Directive.hs
Normal file
19
src/Data/Syntax/Directive.hs
Normal file
@ -0,0 +1,19 @@
|
||||
{-# LANGUAGE DeriveAnyClass, MultiParamTypeClasses, ScopedTypeVariables, UndecidableInstances #-}
|
||||
module Data.Syntax.Directive where
|
||||
|
||||
import Data.Abstract.Evaluatable
|
||||
import Data.Abstract.Module (ModuleInfo(..))
|
||||
import qualified Data.ByteString.Char8 as BC
|
||||
import Diffing.Algorithm
|
||||
import Prologue
|
||||
|
||||
-- A file directive like the Ruby constant `__FILE__`.
|
||||
data File a = File
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
|
||||
|
||||
instance Eq1 File where liftEq = genericLiftEq
|
||||
instance Ord1 File where liftCompare = genericLiftCompare
|
||||
instance Show1 File where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable File where
|
||||
eval File = currentModule >>= string . BC.pack . modulePath
|
@ -17,6 +17,7 @@ import qualified Assigning.Assignment as Assignment
|
||||
import qualified Data.Syntax as Syntax
|
||||
import qualified Data.Syntax.Comment as Comment
|
||||
import qualified Data.Syntax.Declaration as Declaration
|
||||
import qualified Data.Syntax.Directive as Directive
|
||||
import qualified Data.Syntax.Expression as Expression
|
||||
import qualified Data.Syntax.Literal as Literal
|
||||
import qualified Data.Syntax.Statement as Statement
|
||||
@ -28,6 +29,7 @@ type Syntax = '[
|
||||
Comment.Comment
|
||||
, Declaration.Function
|
||||
, Declaration.Method
|
||||
, Directive.File
|
||||
, Expression.Arithmetic
|
||||
, Expression.Bitwise
|
||||
, Expression.Boolean
|
||||
@ -73,12 +75,12 @@ type Syntax = '[
|
||||
, Syntax.Error
|
||||
, Syntax.Identifier
|
||||
, Syntax.Program
|
||||
, Ruby.Syntax.Send
|
||||
, Ruby.Syntax.Class
|
||||
, Ruby.Syntax.Load
|
||||
, Ruby.Syntax.LowPrecedenceBoolean
|
||||
, Ruby.Syntax.Module
|
||||
, Ruby.Syntax.Require
|
||||
, Ruby.Syntax.Send
|
||||
, []
|
||||
]
|
||||
|
||||
@ -177,10 +179,13 @@ identifier =
|
||||
mk s = makeTerm <$> symbol s <*> (Syntax.Identifier . name <$> source)
|
||||
vcallOrLocal = do
|
||||
(loc, ident, locals) <- identWithLocals
|
||||
let identTerm = makeTerm loc (Syntax.Identifier (name ident))
|
||||
if ident `elem` locals
|
||||
then pure identTerm
|
||||
else pure $ makeTerm loc (Ruby.Syntax.Send Nothing (Just identTerm) [] Nothing)
|
||||
case ident of
|
||||
"__FILE__" -> pure $ makeTerm loc Directive.File
|
||||
_ -> do
|
||||
let identTerm = makeTerm loc (Syntax.Identifier (name ident))
|
||||
if ident `elem` locals
|
||||
then pure identTerm
|
||||
else pure $ makeTerm loc (Ruby.Syntax.Send Nothing (Just identTerm) [] Nothing)
|
||||
|
||||
-- TODO: Handle interpolation in all literals that support it (strings, regexes, symbols, subshells, etc).
|
||||
literal :: Assignment
|
||||
|
@ -54,11 +54,11 @@ parsePackage parser preludeFile project@Project{..} = do
|
||||
parseModules :: Members '[Distribute WrappedTask, Files, Task] effs => Parser term -> Project -> Eff effs [Module term]
|
||||
parseModules parser Project{..} = distributeFor (projectEntryPoints <> projectFiles) (WrapTask . parseModule parser (Just projectRootDir))
|
||||
|
||||
-- | Parse a file into a 'Module'.
|
||||
parseModule :: Members '[Files, Task] effs => Parser term -> Maybe FilePath -> File -> Eff effs (Module term)
|
||||
parseModule parser rootDir file = do
|
||||
blob <- readBlob file
|
||||
moduleForBlob rootDir blob <$> parse parser blob
|
||||
-- | Parse a file into a 'Module'.
|
||||
parseModule :: Members '[Files, Task] effs => Parser term -> Maybe FilePath -> File -> Eff effs (Module term)
|
||||
parseModule parser rootDir file = do
|
||||
blob <- readBlob file
|
||||
moduleForBlob rootDir blob <$> parse parser blob
|
||||
|
||||
|
||||
type ImportGraphAnalysis term effects value =
|
||||
|
@ -157,13 +157,13 @@ runParser blob@Blob{..} parser = case parser of
|
||||
time "parse.tree_sitter_ast_parse" languageTag $
|
||||
IO.rethrowing (parseToAST language blob)
|
||||
AssignmentParser parser assignment -> do
|
||||
traceM ("Parsing" <> blobPath)
|
||||
traceM ("Parsing " <> blobPath)
|
||||
ast <- runParser blob parser `catchError` \ (SomeException err) -> do
|
||||
writeStat (Stat.increment "parse.parse_failures" languageTag)
|
||||
writeLog Error "failed parsing" (("task", "parse") : blobFields)
|
||||
throwError (toException err)
|
||||
options <- ask
|
||||
traceM ("Assigning" <> blobPath)
|
||||
traceM ("Assigning " <> blobPath)
|
||||
time "parse.assign" languageTag $
|
||||
case Assignment.assign blobSource assignment ast of
|
||||
Left err -> do
|
||||
|
@ -45,7 +45,6 @@ import qualified Language.Python.Assignment as Python
|
||||
import qualified Language.Ruby.Assignment as Ruby
|
||||
import qualified Language.TypeScript.Assignment as TypeScript
|
||||
|
||||
-- type TestEvaluating term = Evaluating Precise term (Value Precise)
|
||||
type JustEvaluating term
|
||||
= Erroring (AddressError (Located Precise term) (Value (Located Precise term)))
|
||||
( Erroring (EvalError (Value (Located Precise term)))
|
||||
@ -81,6 +80,10 @@ pythonPrelude = Just $ File (TypeLevel.symbolVal (Proxy :: Proxy (PreludePath Py
|
||||
-- Evaluate a project, starting at a single entrypoint.
|
||||
evaluateProject parser lang prelude path = evaluatePackage <$> runTask (readProject Nothing path lang [] >>= parsePackage parser prelude)
|
||||
|
||||
evalRubyFile path = runAnalysis @(JustEvaluating Ruby.Term) <$> evaluateFile rubyParser path
|
||||
evaluateFile parser path = evaluateModule <$> runTask (parseModule parser Nothing (file path))
|
||||
|
||||
|
||||
parseFile :: Parser term -> FilePath -> IO term
|
||||
parseFile parser = runTask . (parse parser <=< readBlob . file)
|
||||
|
||||
|
@ -1,6 +1,5 @@
|
||||
(Program
|
||||
(Send
|
||||
(Identifier))
|
||||
(File)
|
||||
(Send
|
||||
(Identifier))
|
||||
(Send
|
||||
|
Loading…
Reference in New Issue
Block a user