mirror of
https://github.com/github/semantic.git
synced 2024-11-24 17:04:47 +03:00
Merge remote-tracking branch 'origin/master' into entry-points
This commit is contained in:
commit
967803aae3
2
.gitignore
vendored
2
.gitignore
vendored
@ -13,6 +13,8 @@ dist-newstyle
|
||||
tmp/
|
||||
bin/
|
||||
|
||||
/semanticd/test/current
|
||||
/semanticd/test/rover-example-config/semantic.log
|
||||
/test/fixtures/*/examples
|
||||
|
||||
*.hp
|
||||
|
@ -85,6 +85,7 @@ library
|
||||
, Data.Map.Monoidal
|
||||
, Data.Patch
|
||||
, Data.Project
|
||||
, Data.Quieterm
|
||||
, Data.Range
|
||||
, Data.Record
|
||||
, Data.Semigroup.App
|
||||
|
@ -1,6 +1,7 @@
|
||||
{-# LANGUAGE DeriveAnyClass, DeriveGeneric, LambdaCase #-}
|
||||
{-# LANGUAGE DeriveAnyClass, DeriveGeneric, KindSignatures, LambdaCase #-}
|
||||
module Data.Language
|
||||
( Language (..)
|
||||
, SLanguage (..)
|
||||
, ensureLanguage
|
||||
, extensionsForLanguage
|
||||
, knownLanguage
|
||||
@ -34,6 +35,46 @@ data Language
|
||||
| PHP
|
||||
deriving (Eq, Generic, Ord, Read, Show, Bounded, Hashable, ToJSON, Named, Enum, MessageField)
|
||||
|
||||
class SLanguage (lang :: Language) where
|
||||
reflect :: proxy lang -> Language
|
||||
|
||||
instance SLanguage 'Unknown where
|
||||
reflect _ = Unknown
|
||||
|
||||
instance SLanguage 'Go where
|
||||
reflect _ = Go
|
||||
|
||||
instance SLanguage 'Haskell where
|
||||
reflect _ = Haskell
|
||||
|
||||
instance SLanguage 'Java where
|
||||
reflect _ = Java
|
||||
|
||||
instance SLanguage 'JavaScript where
|
||||
reflect _ = JavaScript
|
||||
|
||||
instance SLanguage 'JSON where
|
||||
reflect _ = JSON
|
||||
|
||||
instance SLanguage 'JSX where
|
||||
reflect _ = JSX
|
||||
|
||||
instance SLanguage 'Markdown where
|
||||
reflect _ = Markdown
|
||||
|
||||
instance SLanguage 'Python where
|
||||
reflect _ = Python
|
||||
|
||||
instance SLanguage 'Ruby where
|
||||
reflect _ = Ruby
|
||||
|
||||
instance SLanguage 'TypeScript where
|
||||
reflect _ = TypeScript
|
||||
|
||||
instance SLanguage 'PHP where
|
||||
reflect _ = PHP
|
||||
|
||||
|
||||
-- This ensures that the protobuf file is generated with ALL_CAPS_NAMES.
|
||||
instance Finite Language where
|
||||
enumerate _ = fmap go [Unknown ..] where
|
||||
|
40
src/Data/Quieterm.hs
Normal file
40
src/Data/Quieterm.hs
Normal file
@ -0,0 +1,40 @@
|
||||
{-# LANGUAGE GeneralizedNewtypeDeriving, TypeFamilies #-}
|
||||
module Data.Quieterm
|
||||
( Quieterm(..)
|
||||
, quieterm
|
||||
) where
|
||||
|
||||
import Data.Abstract.Declarations (Declarations)
|
||||
import Data.Abstract.FreeVariables (FreeVariables)
|
||||
import Data.Functor.Classes
|
||||
import Data.Functor.Foldable
|
||||
import Data.Term
|
||||
import Text.Show (showListWith)
|
||||
|
||||
newtype Quieterm syntax ann = Quieterm { unQuieterm :: TermF syntax ann (Quieterm syntax ann) }
|
||||
deriving (Declarations, FreeVariables)
|
||||
|
||||
type instance Base (Quieterm syntax ann) = TermF syntax ann
|
||||
instance Functor syntax => Recursive (Quieterm syntax ann) where project = unQuieterm
|
||||
instance Functor syntax => Corecursive (Quieterm syntax ann) where embed = Quieterm
|
||||
|
||||
instance Eq1 syntax => Eq1 (Quieterm syntax) where
|
||||
liftEq eqA = go where go t1 t2 = liftEq2 eqA go (unQuieterm t1) (unQuieterm t2)
|
||||
|
||||
instance (Eq1 syntax, Eq ann) => Eq (Quieterm syntax ann) where
|
||||
(==) = eq1
|
||||
|
||||
instance Ord1 syntax => Ord1 (Quieterm syntax) where
|
||||
liftCompare comp = go where go t1 t2 = liftCompare2 comp go (unQuieterm t1) (unQuieterm t2)
|
||||
|
||||
instance (Ord1 syntax, Ord ann) => Ord (Quieterm syntax ann) where
|
||||
compare = compare1
|
||||
|
||||
instance Show1 syntax => Show1 (Quieterm syntax) where
|
||||
liftShowsPrec _ _ = go where go d = liftShowsPrec go (showListWith (go 0)) d . termFOut . unQuieterm
|
||||
|
||||
instance Show1 syntax => Show (Quieterm syntax ann) where
|
||||
showsPrec = liftShowsPrec (const (const id)) (const id)
|
||||
|
||||
quieterm :: (Recursive term, Base term ~ TermF syntax ann) => term -> Quieterm syntax ann
|
||||
quieterm = cata Quieterm
|
@ -4,7 +4,7 @@ module Rendering.Graph
|
||||
, termStyle
|
||||
, diffStyle
|
||||
, ToTreeGraph(..)
|
||||
, Vertex(..)
|
||||
, TaggedVertex(..)
|
||||
, DiffTag(..)
|
||||
) where
|
||||
|
||||
@ -16,7 +16,6 @@ import Control.Monad.Effect.Reader
|
||||
import Data.Diff
|
||||
import Data.Graph
|
||||
import Data.Patch
|
||||
import Data.Semigroup.App
|
||||
import Data.String (IsString(..))
|
||||
import Data.Term
|
||||
import Prologue
|
||||
@ -24,53 +23,59 @@ import Prologue
|
||||
renderTreeGraph :: (Ord vertex, Recursive t, ToTreeGraph vertex (Base t)) => t -> Graph vertex
|
||||
renderTreeGraph = simplify . runGraph . cata toTreeGraph
|
||||
|
||||
runGraph :: Eff '[Fresh, Reader (Graph vertex)] (Graph vertex) -> Graph vertex
|
||||
runGraph = run . runReader mempty . runFresh 0
|
||||
runGraph :: Eff '[Reader (Graph vertex), Fresh] (Graph vertex) -> Graph vertex
|
||||
runGraph = run . runFresh 0 . runReader mempty
|
||||
|
||||
|
||||
termAlgebra :: (ConstructorName syntax, Foldable syntax, Member Fresh effs, Member (Reader (Graph (Vertex tag))) effs)
|
||||
termAlgebra :: (ConstructorName syntax, Foldable syntax, Member Fresh effs, Member (Reader (Graph (TaggedVertex tag))) effs)
|
||||
=> tag
|
||||
-> TermF syntax ann (Eff effs (Graph (Vertex tag)))
|
||||
-> Eff effs (Graph (Vertex tag))
|
||||
termAlgebra tag (In _ syntax) = do
|
||||
-> TermF syntax ann (Eff effs (Graph (TaggedVertex tag)))
|
||||
-> Eff effs (Graph (TaggedVertex tag))
|
||||
termAlgebra t (In _ syntax) = do
|
||||
i <- fresh
|
||||
let root = vertex (Vertex i tag (constructorName syntax))
|
||||
parent <- ask
|
||||
(parent `connect` root <>) <$> local (const root) (runAppMerge (foldMap AppMerge syntax))
|
||||
let root = vertex (TaggedVertex i t (constructorName syntax))
|
||||
subGraph <- foldl' (\acc x -> overlay <$> acc <*> local (const root) x) (pure mempty) syntax
|
||||
pure (parent `connect` root `overlay` subGraph)
|
||||
|
||||
|
||||
style :: (IsString string, Monoid string) => String -> (tag -> [Attribute string]) -> Style (Vertex tag) string
|
||||
style :: (IsString string, Monoid string) => String -> (tag -> [Attribute string]) -> Style (TaggedVertex tag) string
|
||||
style name tagAttributes = (defaultStyle (fromString . show . vertexId))
|
||||
{ graphName = fromString (quote name)
|
||||
, vertexAttributes = vertexAttributes }
|
||||
where quote a = "\"" <> a <> "\""
|
||||
vertexAttributes Vertex{..} = "label" := fromString vertexName : tagAttributes vertexTag
|
||||
vertexAttributes TaggedVertex{..} = "label" := fromString vertexName : tagAttributes vertexTag
|
||||
|
||||
termStyle :: (IsString string, Monoid string) => String -> Style (Vertex ()) string
|
||||
termStyle :: (IsString string, Monoid string) => String -> Style (TaggedVertex ()) string
|
||||
termStyle name = style name (const [])
|
||||
|
||||
diffStyle :: (IsString string, Monoid string) => String -> Style (Vertex DiffTag) string
|
||||
diffStyle :: (IsString string, Monoid string) => String -> Style (TaggedVertex DiffTag) string
|
||||
diffStyle name = style name diffTagAttributes
|
||||
where diffTagAttributes Deleted = ["color" := "red"]
|
||||
diffTagAttributes Inserted = ["color" := "green"]
|
||||
diffTagAttributes Replaced = ["color" := "orange", "style" := "dashed"]
|
||||
diffTagAttributes _ = []
|
||||
|
||||
data Vertex tag = Vertex { vertexId :: Int, vertexTag :: tag, vertexName :: String }
|
||||
data TaggedVertex tag = TaggedVertex { vertexId :: Int, vertexTag :: tag, vertexName :: String }
|
||||
deriving (Eq, Ord, Show)
|
||||
|
||||
data DiffTag = Deleted | Inserted | Merged
|
||||
data DiffTag = Deleted | Inserted | Replaced | Merged
|
||||
deriving (Eq, Ord, Show)
|
||||
|
||||
|
||||
class ToTreeGraph vertex t | t -> vertex where
|
||||
toTreeGraph :: (Member Fresh effs, Member (Reader (Graph vertex)) effs) => t (Eff effs (Graph vertex)) -> Eff effs (Graph vertex)
|
||||
|
||||
instance (ConstructorName syntax, Foldable syntax) => ToTreeGraph (Vertex ()) (TermF syntax ann) where
|
||||
instance (ConstructorName syntax, Foldable syntax) => ToTreeGraph (TaggedVertex ()) (TermF syntax ann) where
|
||||
toTreeGraph = termAlgebra ()
|
||||
|
||||
instance (ConstructorName syntax, Foldable syntax) => ToTreeGraph (Vertex DiffTag) (DiffF syntax ann1 ann2) where
|
||||
instance (ConstructorName syntax, Foldable syntax) => ToTreeGraph (TaggedVertex DiffTag) (DiffF syntax ann1 ann2) where
|
||||
toTreeGraph d = case d of
|
||||
Merge t -> termAlgebra Merged t
|
||||
Patch (Delete t1) -> termAlgebra Deleted t1
|
||||
Patch (Insert t2) -> termAlgebra Inserted t2
|
||||
Patch (Replace t1 t2) -> (<>) <$> termAlgebra Deleted t1 <*> termAlgebra Inserted t2
|
||||
Patch (Replace t1 t2) -> do
|
||||
i <- fresh
|
||||
parent <- ask
|
||||
let replace = vertex (TaggedVertex i Replaced "Replacement")
|
||||
graph <- local (const replace) (overlay <$> termAlgebra Deleted t1 <*> termAlgebra Inserted t2)
|
||||
pure (parent `connect` replace `overlay` graph)
|
||||
|
@ -34,7 +34,7 @@ data DiffRenderer output where
|
||||
-- | Render to a 'ByteString' formatted as nested s-expressions with patches indicated.
|
||||
SExpressionDiffRenderer :: DiffRenderer Builder
|
||||
-- | Render to a 'ByteString' formatted as a DOT description of the diff.
|
||||
DOTDiffRenderer :: DiffRenderer (Graph (Vertex DiffTag))
|
||||
DOTDiffRenderer :: DiffRenderer (Graph (TaggedVertex DiffTag))
|
||||
-- | Render to a 'ByteString' formatted using the 'Show' instance.
|
||||
ShowDiffRenderer :: DiffRenderer Builder
|
||||
|
||||
@ -50,7 +50,7 @@ data TermRenderer output where
|
||||
-- | Render to a list of symbols.
|
||||
SymbolsTermRenderer :: SymbolFields -> TermRenderer (JSON "files" SomeJSON)
|
||||
-- | Render to a 'ByteString' formatted as a DOT description of the term.
|
||||
DOTTermRenderer :: TermRenderer (Graph (Vertex ()))
|
||||
DOTTermRenderer :: TermRenderer (Graph (TaggedVertex ()))
|
||||
-- | Render to a 'ByteString' formatted using the 'Show' instance.
|
||||
ShowTermRenderer :: TermRenderer Builder
|
||||
|
||||
|
@ -6,8 +6,9 @@ module Semantic.CLI
|
||||
, Parse.runParse
|
||||
) where
|
||||
|
||||
import Control.Monad.IO.Class
|
||||
import Data.Language (ensureLanguage)
|
||||
import Data.List (intercalate)
|
||||
import Data.List (intercalate, uncons)
|
||||
import Data.List.Split (splitWhen)
|
||||
import Data.Project
|
||||
import Options.Applicative hiding (style)
|
||||
@ -22,6 +23,7 @@ import qualified Semantic.Parse as Parse
|
||||
import qualified Semantic.Task as Task
|
||||
import qualified Semantic.Telemetry.Log as Log
|
||||
import Semantic.Version
|
||||
import System.FilePath
|
||||
import Serializing.Format hiding (Options)
|
||||
import Text.Read
|
||||
|
||||
@ -36,21 +38,25 @@ arguments = info (version <*> helper <*> ((,) <$> optionsParser <*> argumentsPar
|
||||
where
|
||||
version = infoOption versionString (long "version" <> short 'v' <> help "Output the version of the program")
|
||||
versionString = "semantic version " <> buildVersion <> " (" <> buildSHA <> ")"
|
||||
description = fullDesc <> header "semantic -- Parse and diff semantically"
|
||||
description = fullDesc <> header "semantic -- Semantic (syntax-aware) diffs, program analysis toolkit"
|
||||
|
||||
optionsParser = do
|
||||
logLevel <- options [ ("error", Just Log.Error) , ("warning", Just Log.Warning) , ("info", Just Log.Info) , ("debug", Just Log.Debug) , ("none", Nothing)]
|
||||
(long "log-level" <> value (Just Log.Warning) <> help "Log messages at or above this level, or disable logging entirely.")
|
||||
requestId <- optional (strOption $ long "request-id" <> help "A string to use as the request identifier for any logged messages." <> metavar "id")
|
||||
failOnWarning <- switch (long "fail-on-warning" <> help "Fail on assignment warnings.")
|
||||
pure $ Options logLevel requestId failOnWarning
|
||||
optionsParser :: Parser Options
|
||||
optionsParser = do
|
||||
logLevel <- options [ ("error", Just Log.Error) , ("warning", Just Log.Warning) , ("info", Just Log.Info) , ("debug", Just Log.Debug) , ("none", Nothing)]
|
||||
(long "log-level" <> value (Just Log.Warning) <> help "Log messages at or above this level, or disable logging entirely.")
|
||||
requestId <- optional (strOption $ long "request-id" <> help "A string to use as the request identifier for any logged messages." <> metavar "id")
|
||||
failOnWarning <- switch (long "fail-on-warning" <> help "Fail on assignment warnings.")
|
||||
pure $ Options logLevel requestId failOnWarning
|
||||
|
||||
argumentsParser = do
|
||||
subparser <- hsubparser (diffCommand <> parseCommand <> tsParseCommand <> graphCommand)
|
||||
output <- ToPath <$> strOption (long "output" <> short 'o' <> help "Output path, defaults to stdout") <|> pure (ToHandle stdout)
|
||||
pure $ subparser >>= Task.write output
|
||||
argumentsParser :: Parser (Task.TaskEff ())
|
||||
argumentsParser = do
|
||||
subparser <- hsubparser (diffCommand <> parseCommand <> tsParseCommand <> graphCommand)
|
||||
output <- ToPath <$> strOption (long "output" <> short 'o' <> help "Output path, defaults to stdout") <|> pure (ToHandle stdout)
|
||||
pure $ subparser >>= Task.write output
|
||||
|
||||
diffCommand = command "diff" (info diffArgumentsParser (progDesc "Compute changes between paths"))
|
||||
diffCommand :: Mod CommandFields (Task.TaskEff Builder)
|
||||
diffCommand = command "diff" (info diffArgumentsParser (progDesc "Compute changes between paths"))
|
||||
where
|
||||
diffArgumentsParser = do
|
||||
renderer <- flag (Diff.runDiff SExpressionDiffRenderer) (Diff.runDiff SExpressionDiffRenderer) (long "sexpression" <> help "Output s-expression diff tree (default)")
|
||||
<|> flag' (Diff.runDiff JSONDiffRenderer) (long "json" <> help "Output JSON diff trees")
|
||||
@ -60,7 +66,9 @@ arguments = info (version <*> helper <*> ((,) <$> optionsParser <*> argumentsPar
|
||||
filesOrStdin <- Right <$> some (both <$> argument filePathReader (metavar "FILE_A") <*> argument filePathReader (metavar "FILE_B")) <|> pure (Left stdin)
|
||||
pure $ Task.readBlobPairs filesOrStdin >>= renderer
|
||||
|
||||
parseCommand = command "parse" (info parseArgumentsParser (progDesc "Generate parse trees for path(s)"))
|
||||
parseCommand :: Mod CommandFields (Task.TaskEff Builder)
|
||||
parseCommand = command "parse" (info parseArgumentsParser (progDesc "Generate parse trees for path(s)"))
|
||||
where
|
||||
parseArgumentsParser = do
|
||||
renderer <- flag (Parse.runParse SExpressionTermRenderer) (Parse.runParse SExpressionTermRenderer) (long "sexpression" <> help "Output s-expression parse trees (default)")
|
||||
<|> flag' (Parse.runParse JSONTermRenderer) (long "json" <> help "Output JSON parse trees")
|
||||
@ -74,7 +82,12 @@ arguments = info (version <*> helper <*> ((,) <$> optionsParser <*> argumentsPar
|
||||
filesOrStdin <- Right <$> some (argument filePathReader (metavar "FILES...")) <|> pure (Left stdin)
|
||||
pure $ Task.readBlobs filesOrStdin >>= renderer
|
||||
|
||||
tsParseCommand = command "ts-parse" (info tsParseArgumentsParser (progDesc "Print specialized tree-sitter ASTs for path(s)"))
|
||||
-- Example: semantic parse --symbols --fields=symbol,path,language,kind,line,span
|
||||
symbolFieldsReader = eitherReader (Right . parseSymbolFields)
|
||||
|
||||
tsParseCommand :: Mod CommandFields (Task.TaskEff Builder)
|
||||
tsParseCommand = command "ts-parse" (info tsParseArgumentsParser (progDesc "Print specialized tree-sitter ASTs for path(s)"))
|
||||
where
|
||||
tsParseArgumentsParser = do
|
||||
format <- flag AST.SExpression AST.SExpression (long "sexpression" <> help "Output s-expression ASTs (default)")
|
||||
<|> flag' AST.JSON (long "json" <> help "Output JSON ASTs")
|
||||
@ -82,32 +95,45 @@ arguments = info (version <*> helper <*> ((,) <$> optionsParser <*> argumentsPar
|
||||
filesOrStdin <- Right <$> some (argument filePathReader (metavar "FILES...")) <|> pure (Left stdin)
|
||||
pure $ Task.readBlobs filesOrStdin >>= AST.runASTParse format
|
||||
|
||||
graphCommand = command "graph" (info graphArgumentsParser (progDesc "Compute a graph for a directory or from a top-level entry point module"))
|
||||
graphArgumentsParser = do
|
||||
graphType <- flag Graph.ImportGraph Graph.ImportGraph (long "imports" <> help "Compute an import graph (default)")
|
||||
<|> flag' Graph.CallGraph (long "calls" <> help "Compute a call graph")
|
||||
let style = Graph.style
|
||||
includePackages <- switch (long "packages" <> help "Include a vertex for the package, with edges from it to each module")
|
||||
serializer <- flag (Task.serialize (DOT style)) (Task.serialize (DOT style)) (long "dot" <> help "Output in DOT graph format (default)")
|
||||
<|> flag' (Task.serialize JSON) (long "json" <> help "Output JSON graph")
|
||||
<|> flag' (Task.serialize Show) (long "show" <> help "Output using the Show instance (debug only, format subject to change without notice)")
|
||||
rootDir <- rootDirectoryOption
|
||||
excludeDirs <- excludeDirsOption
|
||||
File{..} <- argument filePathReader (metavar "DIR:LANGUAGE | FILE")
|
||||
pure $ Task.readProject rootDir filePath fileLanguage excludeDirs >>= Graph.runGraph graphType includePackages >>= serializer
|
||||
graphCommand :: Mod CommandFields (Task.TaskEff Builder)
|
||||
graphCommand = command "graph" (info graphArgumentsParser (progDesc "Compute a graph for a directory or from a top-level entry point module"))
|
||||
where
|
||||
graphArgumentsParser = makeGraphTask
|
||||
<$> graphType
|
||||
<*> switch (long "packages" <> help "Include a vertex for the package, with edges from it to each module")
|
||||
<*> serializer
|
||||
<*> (readProjectFromPaths <|> readProjectRecursively)
|
||||
graphType = flag Graph.ImportGraph Graph.ImportGraph (long "imports" <> help "Compute an import graph (default)")
|
||||
<|> flag' Graph.CallGraph (long "calls" <> help "Compute a call graph")
|
||||
serializer = flag (Task.serialize (DOT Graph.style)) (Task.serialize (DOT Graph.style)) (long "dot" <> help "Output in DOT graph format (default)")
|
||||
<|> flag' (Task.serialize JSON) (long "json" <> help "Output JSON graph")
|
||||
<|> flag' (Task.serialize Show) (long "show" <> help "Output using the Show instance (debug only, format subject to change without notice)")
|
||||
readProjectFromPaths = makeReadProjectFromPathsTask
|
||||
<$> option auto (long "language" <> help "The language for the analysis.")
|
||||
<*> ( Just <$> some (strArgument (metavar "FILES..."))
|
||||
<|> flag' Nothing (long "stdin" <> help "Read a list of newline-separated paths to analyze from stdin."))
|
||||
makeReadProjectFromPathsTask language maybePaths = do
|
||||
paths <- maybeM (liftIO (many getLine)) maybePaths
|
||||
blobs <- traverse IO.readBlob (flip File language <$> paths)
|
||||
pure $! Project (takeDirectory (maybe "/" fst (uncons paths))) blobs language []
|
||||
readProjectRecursively = makeReadProjectRecursivelyTask
|
||||
<$> optional (strOption (long "root" <> help "Root directory of project. Optional, defaults to entry file/directory." <> metavar "DIR"))
|
||||
<*> many (strOption (long "exclude-dir" <> help "Exclude a directory (e.g. vendor)" <> metavar "DIR"))
|
||||
<*> argument filePathReader (metavar "DIR:LANGUAGE | FILE")
|
||||
makeReadProjectRecursivelyTask rootDir excludeDirs File{..} = Task.readProject rootDir filePath fileLanguage excludeDirs
|
||||
makeGraphTask graphType includePackages serializer projectTask = projectTask >>= Graph.runGraph graphType includePackages >>= serializer
|
||||
|
||||
rootDirectoryOption = optional (strOption (long "root" <> help "Root directory of project. Optional, defaults to entry file/directory." <> metavar "DIR"))
|
||||
excludeDirsOption = many (strOption (long "exclude-dir" <> help "Exclude a directory (e.g. vendor)" <> metavar "DIR"))
|
||||
filePathReader = eitherReader parseFilePath
|
||||
filePathReader :: ReadM File
|
||||
filePathReader = eitherReader parseFilePath
|
||||
where
|
||||
parseFilePath arg = case splitWhen (== ':') arg of
|
||||
[a, b] | (Just lang) <- readMaybe b >>= ensureLanguage -> Right (File a lang)
|
||||
| (Just lang) <- readMaybe a >>= ensureLanguage -> Right (File b lang)
|
||||
[a, b] | Just lang <- readMaybe b >>= ensureLanguage -> Right (File a lang)
|
||||
| Just lang <- readMaybe a >>= ensureLanguage -> Right (File b lang)
|
||||
[path] -> maybe (Left $ "Cannot identify language for path: " <> path) (Right . File path) (ensureLanguage (languageForFilePath path))
|
||||
args -> Left ("cannot parse `" <> join args <> "`\nexpecting FILE:LANGUAGE or just FILE")
|
||||
|
||||
options :: Eq a => [(String, a)] -> Mod OptionFields a -> Parser a
|
||||
options options fields = option (optionsReader options) (fields <> showDefaultWith (findOption options) <> metavar (intercalate "|" (fmap fst options)))
|
||||
where
|
||||
optionsReader options = eitherReader $ \ str -> maybe (Left ("expected one of: " <> intercalate ", " (fmap fst options))) (Right . snd) (find ((== str) . fst) options)
|
||||
options options fields = option (optionsReader options) (fields <> showDefaultWith (findOption options) <> metavar (intercalate "|" (fmap fst options)))
|
||||
findOption options value = maybe "" fst (find ((== value) . snd) options)
|
||||
|
||||
-- Example: semantic parse --symbols --fields=symbol,path,language,kind,line,span
|
||||
symbolFieldsReader = eitherReader (Right . parseSymbolFields)
|
||||
|
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE GeneralizedNewtypeDeriving, TypeFamilies, TypeOperators, PartialTypeSignatures #-}
|
||||
{-# LANGUAGE TypeFamilies, TypeOperators #-}
|
||||
{-# OPTIONS_GHC -Wno-missing-signatures -Wno-missing-export-lists #-}
|
||||
module Semantic.Util where
|
||||
|
||||
@ -18,13 +18,12 @@ import Data.Abstract.Value.Concrete as Concrete
|
||||
import Data.Abstract.Value.Type as Type
|
||||
import Data.Blob
|
||||
import Data.Coerce
|
||||
import Data.Functor.Foldable
|
||||
import Data.Graph (topologicalSort)
|
||||
import qualified Data.Language as Language
|
||||
import Data.List (uncons)
|
||||
import Data.Project hiding (readFile)
|
||||
import Data.Quieterm (quieterm)
|
||||
import Data.Sum (weaken)
|
||||
import Data.Term
|
||||
import Language.Haskell.HsColour
|
||||
import Language.Haskell.HsColour.Colourise
|
||||
import Parsing.Parser
|
||||
@ -36,7 +35,6 @@ import Semantic.Task
|
||||
import Semantic.Telemetry (LogQueue, StatQueue)
|
||||
import System.Exit (die)
|
||||
import System.FilePath.Posix (takeDirectory)
|
||||
import Text.Show (showListWith)
|
||||
import Text.Show.Pretty (ppShow)
|
||||
|
||||
justEvaluating
|
||||
@ -53,28 +51,28 @@ justEvaluating
|
||||
. runAddressError
|
||||
. runValueError
|
||||
|
||||
newtype UtilEff address a = UtilEff
|
||||
{ runUtilEff :: Eff '[ Function address (Value address (UtilEff address))
|
||||
, Exc (LoopControl address)
|
||||
, Exc (Return address)
|
||||
, Env address
|
||||
, Deref address (Value address (UtilEff address))
|
||||
, Allocator address (Value address (UtilEff address))
|
||||
newtype UtilEff a = UtilEff
|
||||
{ runUtilEff :: Eff '[ Function Precise (Value Precise UtilEff)
|
||||
, Exc (LoopControl Precise)
|
||||
, Exc (Return Precise)
|
||||
, Env Precise
|
||||
, Deref Precise (Value Precise UtilEff)
|
||||
, Allocator Precise (Value Precise UtilEff)
|
||||
, Reader ModuleInfo
|
||||
, Modules address
|
||||
, Reader (ModuleTable (NonEmpty (Module (ModuleResult address))))
|
||||
, Modules Precise
|
||||
, Reader (ModuleTable (NonEmpty (Module (ModuleResult Precise))))
|
||||
, Reader Span
|
||||
, Reader PackageInfo
|
||||
, Resumable (ValueError address (UtilEff address))
|
||||
, Resumable (AddressError address (Value address (UtilEff address)))
|
||||
, Resumable (ValueError Precise UtilEff)
|
||||
, Resumable (AddressError Precise (Value Precise UtilEff))
|
||||
, Resumable ResolutionError
|
||||
, Resumable EvalError
|
||||
, Resumable (EnvironmentError address)
|
||||
, Resumable (Unspecialized (Value address (UtilEff address)))
|
||||
, Resumable (LoadError address)
|
||||
, Resumable (EnvironmentError Precise)
|
||||
, Resumable (Unspecialized (Value Precise UtilEff))
|
||||
, Resumable (LoadError Precise)
|
||||
, Trace
|
||||
, Fresh
|
||||
, State (Heap address Latest (Value address (UtilEff address)))
|
||||
, State (Heap Precise Latest (Value Precise UtilEff))
|
||||
, Lift IO
|
||||
] a
|
||||
}
|
||||
@ -96,38 +94,38 @@ checking
|
||||
. runAddressError
|
||||
. runTypes
|
||||
|
||||
evalGoProject = justEvaluating <=< evaluateProject (Proxy :: Proxy 'Language.Go) goParser Language.Go
|
||||
evalRubyProject = justEvaluating <=< evaluateProject (Proxy :: Proxy 'Language.Ruby) rubyParser Language.Ruby
|
||||
evalPHPProject = justEvaluating <=< evaluateProject (Proxy :: Proxy 'Language.PHP) phpParser Language.PHP
|
||||
evalPythonProject = justEvaluating <=< evaluateProject (Proxy :: Proxy 'Language.Python) pythonParser Language.Python
|
||||
evalJavaScriptProject = justEvaluating <=< evaluateProject (Proxy :: Proxy 'Language.JavaScript) typescriptParser Language.JavaScript
|
||||
evalTypeScriptProject = justEvaluating <=< evaluateProject (Proxy :: Proxy 'Language.TypeScript) typescriptParser Language.TypeScript
|
||||
evalGoProject = justEvaluating <=< evaluateProject (Proxy :: Proxy 'Language.Go) goParser
|
||||
evalRubyProject = justEvaluating <=< evaluateProject (Proxy :: Proxy 'Language.Ruby) rubyParser
|
||||
evalPHPProject = justEvaluating <=< evaluateProject (Proxy :: Proxy 'Language.PHP) phpParser
|
||||
evalPythonProject = justEvaluating <=< evaluateProject (Proxy :: Proxy 'Language.Python) pythonParser
|
||||
evalJavaScriptProject = justEvaluating <=< evaluateProject (Proxy :: Proxy 'Language.JavaScript) typescriptParser
|
||||
evalTypeScriptProject = justEvaluating <=< evaluateProject (Proxy :: Proxy 'Language.TypeScript) typescriptParser
|
||||
|
||||
typecheckGoFile = checking <=< evaluateProjectWithCaching (Proxy :: Proxy 'Language.Go) goParser Language.Go
|
||||
typecheckGoFile = checking <=< evaluateProjectWithCaching (Proxy :: Proxy 'Language.Go) goParser
|
||||
|
||||
callGraphProject parser proxy lang opts paths = runTaskWithOptions opts $ do
|
||||
blobs <- catMaybes <$> traverse readFile (flip File lang <$> paths)
|
||||
package <- parsePackage parser (Project (takeDirectory (maybe "/" fst (uncons paths))) blobs lang [])
|
||||
callGraphProject parser proxy opts paths = runTaskWithOptions opts $ do
|
||||
blobs <- catMaybes <$> traverse readFile (flip File (Language.reflect proxy) <$> paths)
|
||||
package <- parsePackage parser (Project (takeDirectory (maybe "/" fst (uncons paths))) blobs (Language.reflect proxy) [])
|
||||
modules <- topologicalSort <$> runImportGraphToModules proxy package
|
||||
x <- runCallGraph proxy False modules package
|
||||
pure (x, (() <$) <$> modules)
|
||||
|
||||
evaluatePythonProject = evaluatePythonProjects (Proxy @'Language.Python) pythonParser Language.Python
|
||||
|
||||
callGraphRubyProject = callGraphProject rubyParser (Proxy @'Language.Ruby) Language.Ruby debugOptions
|
||||
callGraphRubyProject = callGraphProject rubyParser (Proxy @'Language.Ruby) debugOptions
|
||||
|
||||
-- Evaluate a project consisting of the listed paths.
|
||||
evaluateProject proxy parser lang paths = withOptions debugOptions $ \ config logger statter ->
|
||||
evaluateProject' (TaskConfig config logger statter) proxy parser lang paths
|
||||
evaluateProject proxy parser paths = withOptions debugOptions $ \ config logger statter ->
|
||||
evaluateProject' (TaskConfig config logger statter) proxy parser paths
|
||||
|
||||
data TaskConfig = TaskConfig Config LogQueue StatQueue
|
||||
|
||||
evaluateProject' (TaskConfig config logger statter) proxy parser lang paths = either (die . displayException) pure <=< runTaskWithConfig config logger statter $ do
|
||||
blobs <- catMaybes <$> traverse readFile (flip File lang <$> paths)
|
||||
package <- fmap quieterm <$> parsePackage parser (Project (takeDirectory (maybe "/" fst (uncons paths))) blobs lang [])
|
||||
evaluateProject' (TaskConfig config logger statter) proxy parser paths = either (die . displayException) pure <=< runTaskWithConfig config logger statter $ do
|
||||
blobs <- catMaybes <$> traverse readFile (flip File (Language.reflect proxy) <$> paths)
|
||||
package <- fmap quieterm <$> 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 (runTermEvaluator @_ @_ @(Value Precise (UtilEff Precise))
|
||||
pure (runTermEvaluator @_ @_ @(Value Precise UtilEff)
|
||||
(runReader (packageInfo package)
|
||||
(runReader (lowerBound @Span)
|
||||
(runReader (lowerBound @(ModuleTable (NonEmpty (Module (ModuleResult Precise)))))
|
||||
@ -148,8 +146,8 @@ evaluatePythonProjects proxy parser lang path = runTaskWithOptions debugOptions
|
||||
(evaluate proxy id withTermSpans (Concrete.runFunction coerce coerce) modules))))))
|
||||
|
||||
|
||||
evaluateProjectWithCaching proxy parser lang path = runTaskWithOptions debugOptions $ do
|
||||
project <- readProject Nothing path lang []
|
||||
evaluateProjectWithCaching proxy parser path = runTaskWithOptions debugOptions $ do
|
||||
project <- readProject Nothing path (Language.reflect proxy) []
|
||||
package <- fmap quieterm <$> parsePackage parser project
|
||||
modules <- topologicalSort <$> runImportGraphToModules proxy package
|
||||
pure (runReader (packageInfo package)
|
||||
@ -173,34 +171,5 @@ reassociate :: Either (SomeExc exc1) (Either (SomeExc exc2) (Either (SomeExc exc
|
||||
reassociate = mergeExcs . mergeExcs . mergeExcs . mergeExcs . mergeExcs . mergeExcs . mergeExcs . Right
|
||||
|
||||
|
||||
newtype Quieterm syntax ann = Quieterm { unQuieterm :: TermF syntax ann (Quieterm syntax ann) }
|
||||
deriving (Declarations, FreeVariables)
|
||||
|
||||
type instance Base (Quieterm syntax ann) = TermF syntax ann
|
||||
instance Functor syntax => Recursive (Quieterm syntax ann) where project = unQuieterm
|
||||
instance Functor syntax => Corecursive (Quieterm syntax ann) where embed = Quieterm
|
||||
|
||||
instance Eq1 syntax => Eq1 (Quieterm syntax) where
|
||||
liftEq eqA = go where go t1 t2 = liftEq2 eqA go (unQuieterm t1) (unQuieterm t2)
|
||||
|
||||
instance (Eq1 syntax, Eq ann) => Eq (Quieterm syntax ann) where
|
||||
(==) = eq1
|
||||
|
||||
instance Ord1 syntax => Ord1 (Quieterm syntax) where
|
||||
liftCompare comp = go where go t1 t2 = liftCompare2 comp go (unQuieterm t1) (unQuieterm t2)
|
||||
|
||||
instance (Ord1 syntax, Ord ann) => Ord (Quieterm syntax ann) where
|
||||
compare = compare1
|
||||
|
||||
instance Show1 syntax => Show1 (Quieterm syntax) where
|
||||
liftShowsPrec _ _ = go where go d = liftShowsPrec go (showListWith (go 0)) d . termFOut . unQuieterm
|
||||
|
||||
instance Show1 syntax => Show (Quieterm syntax ann) where
|
||||
showsPrec = liftShowsPrec (const (const id)) (const id)
|
||||
|
||||
quieterm :: (Recursive term, Base term ~ TermF syntax ann) => term -> Quieterm syntax ann
|
||||
quieterm = cata Quieterm
|
||||
|
||||
|
||||
prettyShow :: Show a => a -> IO ()
|
||||
prettyShow = putStrLn . hscolour TTY defaultColourPrefs False False "" False . ppShow
|
||||
|
@ -30,4 +30,4 @@ spec config = parallel $ do
|
||||
where
|
||||
fixtures = "test/fixtures/go/analysis/"
|
||||
evaluate = evalGoProject . map (fixtures <>)
|
||||
evalGoProject = testEvaluating <=< evaluateProject' config (Proxy :: Proxy 'Language.Go) goParser Language.Go
|
||||
evalGoProject = testEvaluating <=< evaluateProject' config (Proxy :: Proxy 'Language.Go) goParser
|
||||
|
@ -42,4 +42,4 @@ spec config = parallel $ do
|
||||
where
|
||||
fixtures = "test/fixtures/php/analysis/"
|
||||
evaluate = evalPHPProject . map (fixtures <>)
|
||||
evalPHPProject = testEvaluating <=< evaluateProject' config (Proxy :: Proxy 'Language.PHP) phpParser Language.PHP
|
||||
evalPHPProject = testEvaluating <=< evaluateProject' config (Proxy :: Proxy 'Language.PHP) phpParser
|
||||
|
@ -60,4 +60,4 @@ spec config = parallel $ do
|
||||
ns n = Just . Latest . Last . Just . Namespace n
|
||||
fixtures = "test/fixtures/python/analysis/"
|
||||
evaluate = evalPythonProject . map (fixtures <>)
|
||||
evalPythonProject = testEvaluating <=< evaluateProject' config (Proxy :: Proxy 'Language.Python) pythonParser Language.Python
|
||||
evalPythonProject = testEvaluating <=< evaluateProject' config (Proxy :: Proxy 'Language.Python) pythonParser
|
||||
|
@ -104,4 +104,4 @@ spec config = parallel $ do
|
||||
ns n = Just . Latest . Last . Just . Namespace n
|
||||
fixtures = "test/fixtures/ruby/analysis/"
|
||||
evaluate = evalRubyProject . map (fixtures <>)
|
||||
evalRubyProject = testEvaluating <=< evaluateProject' config (Proxy :: Proxy 'Language.Ruby) rubyParser Language.Ruby
|
||||
evalRubyProject = testEvaluating <=< evaluateProject' config (Proxy :: Proxy 'Language.Ruby) rubyParser
|
||||
|
@ -49,4 +49,4 @@ spec config = parallel $ do
|
||||
where
|
||||
fixtures = "test/fixtures/typescript/analysis/"
|
||||
evaluate = evalTypeScriptProject . map (fixtures <>)
|
||||
evalTypeScriptProject = testEvaluating <=< evaluateProject' config (Proxy :: Proxy 'Language.TypeScript) typescriptParser Language.TypeScript
|
||||
evalTypeScriptProject = testEvaluating <=< evaluateProject' config (Proxy :: Proxy 'Language.TypeScript) typescriptParser
|
||||
|
@ -96,7 +96,7 @@ readFilePair :: Both FilePath -> IO BlobPair
|
||||
readFilePair paths = let paths' = fmap file paths in
|
||||
runBothWith IO.readFilePair paths'
|
||||
|
||||
type TestEvaluatingEffects = '[ Resumable (ValueError Precise (UtilEff Precise))
|
||||
type TestEvaluatingEffects = '[ Resumable (ValueError Precise UtilEff)
|
||||
, Resumable (AddressError Precise Val)
|
||||
, Resumable ResolutionError
|
||||
, Resumable EvalError
|
||||
@ -108,7 +108,7 @@ type TestEvaluatingEffects = '[ Resumable (ValueError Precise (UtilEff Precise))
|
||||
, State (Heap Precise Latest Val)
|
||||
, Lift IO
|
||||
]
|
||||
type TestEvaluatingErrors = '[ ValueError Precise (UtilEff Precise)
|
||||
type TestEvaluatingErrors = '[ ValueError Precise UtilEff
|
||||
, AddressError Precise Val
|
||||
, ResolutionError
|
||||
, EvalError
|
||||
@ -137,9 +137,9 @@ testEvaluating
|
||||
. runEvalError
|
||||
. runResolutionError
|
||||
. runAddressError
|
||||
. runValueError @_ @Precise @(UtilEff Precise)
|
||||
. runValueError @_ @Precise @UtilEff
|
||||
|
||||
type Val = Value Precise (UtilEff Precise)
|
||||
type Val = Value Precise UtilEff
|
||||
|
||||
|
||||
deNamespace :: Heap Precise (Cell Precise) (Value Precise term)
|
||||
|
5
test/fixtures/java/corpus/ClassLiteral.B.java
vendored
Normal file
5
test/fixtures/java/corpus/ClassLiteral.B.java
vendored
Normal file
@ -0,0 +1,5 @@
|
||||
class Dino {
|
||||
public static void normalError() {
|
||||
Class<String> c = String.class;
|
||||
}
|
||||
}
|
24
test/fixtures/java/corpus/ClassLiteral.diffA-B.txt
vendored
Normal file
24
test/fixtures/java/corpus/ClassLiteral.diffA-B.txt
vendored
Normal file
@ -0,0 +1,24 @@
|
||||
(Statements
|
||||
(Class
|
||||
(Identifier)
|
||||
(Statements
|
||||
(Method
|
||||
(Void)
|
||||
{+(AccessibilityModifier)+}
|
||||
{+(AccessibilityModifier)+}
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Statements
|
||||
{+(GreaterThan
|
||||
{+(LessThan
|
||||
{+(Identifier)+}
|
||||
{+(Identifier)+})+}
|
||||
{+(Assignment
|
||||
{+(Identifier)+}
|
||||
{+(ClassLiteral
|
||||
{+(Identifier)+})+})+})+}
|
||||
{-(Call
|
||||
{-(Identifier)-}
|
||||
{-(ClassLiteral
|
||||
{-(Identifier)-})-}
|
||||
{-(Empty)-})-})))))
|
24
test/fixtures/java/corpus/ClassLiteral.diffB-A.txt
vendored
Normal file
24
test/fixtures/java/corpus/ClassLiteral.diffB-A.txt
vendored
Normal file
@ -0,0 +1,24 @@
|
||||
(Statements
|
||||
(Class
|
||||
(Identifier)
|
||||
(Statements
|
||||
(Method
|
||||
(Void)
|
||||
{-(AccessibilityModifier)-}
|
||||
{-(AccessibilityModifier)-}
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Statements
|
||||
{+(Call
|
||||
{+(Identifier)+}
|
||||
{+(ClassLiteral
|
||||
{+(Identifier)+})+}
|
||||
{+(Empty)+})+}
|
||||
{-(GreaterThan
|
||||
{-(LessThan
|
||||
{-(Identifier)-}
|
||||
{-(Identifier)-})-}
|
||||
{-(Assignment
|
||||
{-(Identifier)-}
|
||||
{-(ClassLiteral
|
||||
{-(Identifier)-})-})-})-})))))
|
14
test/fixtures/java/corpus/ClassLiteral.parseA.txt
vendored
Normal file
14
test/fixtures/java/corpus/ClassLiteral.parseA.txt
vendored
Normal file
@ -0,0 +1,14 @@
|
||||
(Statements
|
||||
(Class
|
||||
(Identifier)
|
||||
(Statements
|
||||
(Method
|
||||
(Void)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Statements
|
||||
(Call
|
||||
(Identifier)
|
||||
(ClassLiteral
|
||||
(Identifier))
|
||||
(Empty)))))))
|
19
test/fixtures/java/corpus/ClassLiteral.parseB.txt
vendored
Normal file
19
test/fixtures/java/corpus/ClassLiteral.parseB.txt
vendored
Normal file
@ -0,0 +1,19 @@
|
||||
(Statements
|
||||
(Class
|
||||
(Identifier)
|
||||
(Statements
|
||||
(Method
|
||||
(Void)
|
||||
(AccessibilityModifier)
|
||||
(AccessibilityModifier)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Statements
|
||||
(GreaterThan
|
||||
(LessThan
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Assignment
|
||||
(Identifier)
|
||||
(ClassLiteral
|
||||
(Identifier)))))))))
|
7
test/fixtures/java/corpus/Continue.B.java
vendored
Normal file
7
test/fixtures/java/corpus/Continue.B.java
vendored
Normal file
@ -0,0 +1,7 @@
|
||||
class Test {
|
||||
public static void main(String[] args) {
|
||||
if (i > 4 && i < 9) {
|
||||
continue;
|
||||
}
|
||||
}
|
||||
}
|
30
test/fixtures/java/corpus/Continue.diffA-B.txt
vendored
Normal file
30
test/fixtures/java/corpus/Continue.diffA-B.txt
vendored
Normal file
@ -0,0 +1,30 @@
|
||||
(Statements
|
||||
(Class
|
||||
{-(AccessibilityModifier)-}
|
||||
(Identifier)
|
||||
(Statements
|
||||
{+(Method
|
||||
{+(Void)+}
|
||||
{+(AccessibilityModifier)+}
|
||||
{+(AccessibilityModifier)+}
|
||||
{+(Empty)+}
|
||||
{+(Identifier)+}
|
||||
{+(Annotation
|
||||
{+(Identifier)+}
|
||||
{+(Array
|
||||
{+(Empty)+}
|
||||
{+(Identifier)+})+})+}
|
||||
{+(Statements
|
||||
{+(If
|
||||
{+(And
|
||||
{+(GreaterThan
|
||||
{+(Identifier)+}
|
||||
{+(Integer)+})+}
|
||||
{+(LessThan
|
||||
{+(Identifier)+}
|
||||
{+(Integer)+})+})+}
|
||||
{+(Statements
|
||||
{+(Continue
|
||||
{+(Empty)+})+})+}
|
||||
{+(Empty)+})+})+})+}
|
||||
{-(Error)-})))
|
30
test/fixtures/java/corpus/Continue.diffB-A.txt
vendored
Normal file
30
test/fixtures/java/corpus/Continue.diffB-A.txt
vendored
Normal file
@ -0,0 +1,30 @@
|
||||
(Statements
|
||||
(Class
|
||||
{+(AccessibilityModifier)+}
|
||||
(Identifier)
|
||||
(Statements
|
||||
{+(Error)+}
|
||||
{-(Method
|
||||
{-(Void)-}
|
||||
{-(AccessibilityModifier)-}
|
||||
{-(AccessibilityModifier)-}
|
||||
{-(Empty)-}
|
||||
{-(Identifier)-}
|
||||
{-(Annotation
|
||||
{-(Identifier)-}
|
||||
{-(Array
|
||||
{-(Empty)-}
|
||||
{-(Identifier)-})-})-}
|
||||
{-(Statements
|
||||
{-(If
|
||||
{-(And
|
||||
{-(GreaterThan
|
||||
{-(Identifier)-}
|
||||
{-(Integer)-})-}
|
||||
{-(LessThan
|
||||
{-(Identifier)-}
|
||||
{-(Integer)-})-})-}
|
||||
{-(Statements
|
||||
{-(Continue
|
||||
{-(Empty)-})-})-}
|
||||
{-(Empty)-})-})-})-})))
|
6
test/fixtures/java/corpus/Continue.parseA.txt
vendored
Normal file
6
test/fixtures/java/corpus/Continue.parseA.txt
vendored
Normal file
@ -0,0 +1,6 @@
|
||||
(Statements
|
||||
(Class
|
||||
(AccessibilityModifier)
|
||||
(Identifier)
|
||||
(Statements
|
||||
(Error))))
|
28
test/fixtures/java/corpus/Continue.parseB.txt
vendored
Normal file
28
test/fixtures/java/corpus/Continue.parseB.txt
vendored
Normal file
@ -0,0 +1,28 @@
|
||||
(Statements
|
||||
(Class
|
||||
(Identifier)
|
||||
(Statements
|
||||
(Method
|
||||
(Void)
|
||||
(AccessibilityModifier)
|
||||
(AccessibilityModifier)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Annotation
|
||||
(Identifier)
|
||||
(Array
|
||||
(Empty)
|
||||
(Identifier)))
|
||||
(Statements
|
||||
(If
|
||||
(And
|
||||
(GreaterThan
|
||||
(Identifier)
|
||||
(Integer))
|
||||
(LessThan
|
||||
(Identifier)
|
||||
(Integer)))
|
||||
(Statements
|
||||
(Continue
|
||||
(Empty)))
|
||||
(Empty)))))))
|
14
test/fixtures/java/corpus/Continue0.A.java
vendored
Normal file
14
test/fixtures/java/corpus/Continue0.A.java
vendored
Normal file
@ -0,0 +1,14 @@
|
||||
public class Test {
|
||||
|
||||
public static void main(String args[]) {
|
||||
int [] numbers = {10, 20, 30, 40, 50};
|
||||
|
||||
for(int x : numbers ) {
|
||||
if( x == 30 ) {
|
||||
continue;
|
||||
}
|
||||
System.out.print( x );
|
||||
System.out.print("\n");
|
||||
}
|
||||
}
|
||||
}
|
14
test/fixtures/java/corpus/Continue1.A.java
vendored
Normal file
14
test/fixtures/java/corpus/Continue1.A.java
vendored
Normal file
@ -0,0 +1,14 @@
|
||||
public class Test {
|
||||
|
||||
public static void main(String args[]) {
|
||||
int [] numbers = {10, 20, 30, 40, 50};
|
||||
|
||||
for(int x : numbers ) {
|
||||
if( x == 30 ) {
|
||||
continue;
|
||||
}
|
||||
System.out.print( x );
|
||||
System.out.print("\n");
|
||||
}
|
||||
}
|
||||
}
|
1
test/fixtures/java/corpus/Dims.A.java
vendored
Normal file
1
test/fixtures/java/corpus/Dims.A.java
vendored
Normal file
@ -0,0 +1 @@
|
||||
class ForDemo { int[] metrics; }
|
20
test/fixtures/java/corpus/Dims.diffA-B.txt
vendored
Normal file
20
test/fixtures/java/corpus/Dims.diffA-B.txt
vendored
Normal file
@ -0,0 +1,20 @@
|
||||
(Statements
|
||||
(Class
|
||||
(Identifier)
|
||||
(Statements
|
||||
{+(Method
|
||||
{+(Void)+}
|
||||
{+(Empty)+}
|
||||
{+(Identifier)+}
|
||||
{+(Annotation
|
||||
{+(Identifier)+}
|
||||
{+(Array
|
||||
{+(Empty)+}
|
||||
{+(Identifier)+})+})+}
|
||||
{+(Statements)+})+}
|
||||
{-(Statements
|
||||
{-(Variable
|
||||
{-(Array
|
||||
{-(Empty)-}
|
||||
{-(Int)-})-}
|
||||
{-(Identifier)-})-})-})))
|
20
test/fixtures/java/corpus/Dims.diffB-A.txt
vendored
Normal file
20
test/fixtures/java/corpus/Dims.diffB-A.txt
vendored
Normal file
@ -0,0 +1,20 @@
|
||||
(Statements
|
||||
(Class
|
||||
(Identifier)
|
||||
(Statements
|
||||
{+(Statements
|
||||
{+(Variable
|
||||
{+(Array
|
||||
{+(Empty)+}
|
||||
{+(Int)+})+}
|
||||
{+(Identifier)+})+})+}
|
||||
{-(Method
|
||||
{-(Void)-}
|
||||
{-(Empty)-}
|
||||
{-(Identifier)-}
|
||||
{-(Annotation
|
||||
{-(Identifier)-}
|
||||
{-(Array
|
||||
{-(Empty)-}
|
||||
{-(Identifier)-})-})-}
|
||||
{-(Statements)-})-})))
|
10
test/fixtures/java/corpus/Dims.parseA.txt
vendored
Normal file
10
test/fixtures/java/corpus/Dims.parseA.txt
vendored
Normal file
@ -0,0 +1,10 @@
|
||||
(Statements
|
||||
(Class
|
||||
(Identifier)
|
||||
(Statements
|
||||
(Statements
|
||||
(Variable
|
||||
(Array
|
||||
(Empty)
|
||||
(Int))
|
||||
(Identifier))))))
|
14
test/fixtures/java/corpus/Dims.parseB.txt
vendored
Normal file
14
test/fixtures/java/corpus/Dims.parseB.txt
vendored
Normal file
@ -0,0 +1,14 @@
|
||||
(Statements
|
||||
(Class
|
||||
(Identifier)
|
||||
(Statements
|
||||
(Method
|
||||
(Void)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Annotation
|
||||
(Identifier)
|
||||
(Array
|
||||
(Empty)
|
||||
(Identifier)))
|
||||
(Statements)))))
|
9
test/fixtures/java/corpus/DoWhile.B.java
vendored
Normal file
9
test/fixtures/java/corpus/DoWhile.B.java
vendored
Normal file
@ -0,0 +1,9 @@
|
||||
class WhileDemo {
|
||||
public static void main(String[] args) {
|
||||
int i = 5;
|
||||
do {
|
||||
System.out.println(i);
|
||||
i++;
|
||||
} while (i <= 10);
|
||||
}
|
||||
}
|
51
test/fixtures/java/corpus/DoWhile.diffA-B.txt
vendored
Normal file
51
test/fixtures/java/corpus/DoWhile.diffA-B.txt
vendored
Normal file
@ -0,0 +1,51 @@
|
||||
(Statements
|
||||
(Class
|
||||
(Identifier)
|
||||
(Statements
|
||||
(Method
|
||||
(Void)
|
||||
(AccessibilityModifier)
|
||||
(AccessibilityModifier)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Annotation
|
||||
(Identifier)
|
||||
(Array
|
||||
(Empty)
|
||||
(Identifier)))
|
||||
(Statements
|
||||
{+(Statements
|
||||
{+(Assignment
|
||||
{+(Variable
|
||||
{+(Int)+}
|
||||
{+(Identifier)+})+}
|
||||
{+(Integer)+})+})+}
|
||||
(DoWhile
|
||||
{ (Not
|
||||
{-(Call
|
||||
{-(MemberAccess
|
||||
{-(TextElement)-})-}
|
||||
{-(Identifier)-}
|
||||
{-(Empty)-})-})
|
||||
->(LessThanEqual
|
||||
{+(Identifier)+}
|
||||
{+(Integer)+}) }
|
||||
(Statements
|
||||
(Call
|
||||
{ (MemberAccess
|
||||
{-(MemberAccess
|
||||
{-(Identifier)-})-})
|
||||
->(MemberAccess
|
||||
{+(MemberAccess
|
||||
{+(Identifier)+})+}) }
|
||||
{+(Identifier)+}
|
||||
{-(TextElement)-}
|
||||
(Empty))
|
||||
{+(PostIncrement
|
||||
{+(Identifier)+})+}
|
||||
{-(Assignment
|
||||
{-(Identifier)-}
|
||||
{-(Call
|
||||
{-(MemberAccess
|
||||
{-(Identifier)-})-}
|
||||
{-(Empty)-})-})-})))))))
|
55
test/fixtures/java/corpus/DoWhile.diffB-A.txt
vendored
Normal file
55
test/fixtures/java/corpus/DoWhile.diffB-A.txt
vendored
Normal file
@ -0,0 +1,55 @@
|
||||
(Statements
|
||||
(Class
|
||||
(Identifier)
|
||||
(Statements
|
||||
(Method
|
||||
(Void)
|
||||
(AccessibilityModifier)
|
||||
(AccessibilityModifier)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Annotation
|
||||
(Identifier)
|
||||
(Array
|
||||
(Empty)
|
||||
(Identifier)))
|
||||
(Statements
|
||||
{+(DoWhile
|
||||
{+(Not
|
||||
{+(Call
|
||||
{+(MemberAccess
|
||||
{+(TextElement)+})+}
|
||||
{+(Identifier)+}
|
||||
{+(Empty)+})+})+}
|
||||
{+(Statements
|
||||
{+(Call
|
||||
{+(MemberAccess
|
||||
{+(MemberAccess
|
||||
{+(Identifier)+})+})+}
|
||||
{+(TextElement)+}
|
||||
{+(Empty)+})+}
|
||||
{+(Assignment
|
||||
{+(Identifier)+}
|
||||
{+(Call
|
||||
{+(MemberAccess
|
||||
{+(Identifier)+})+}
|
||||
{+(Empty)+})+})+})+})+}
|
||||
{-(Statements
|
||||
{-(Assignment
|
||||
{-(Variable
|
||||
{-(Int)-}
|
||||
{-(Identifier)-})-}
|
||||
{-(Integer)-})-})-}
|
||||
{-(DoWhile
|
||||
{-(LessThanEqual
|
||||
{-(Identifier)-}
|
||||
{-(Integer)-})-}
|
||||
{-(Statements
|
||||
{-(Call
|
||||
{-(MemberAccess
|
||||
{-(MemberAccess
|
||||
{-(Identifier)-})-})-}
|
||||
{-(Identifier)-}
|
||||
{-(Empty)-})-}
|
||||
{-(PostIncrement
|
||||
{-(Identifier)-})-})-})-})))))
|
36
test/fixtures/java/corpus/DoWhile.parseA.txt
vendored
Normal file
36
test/fixtures/java/corpus/DoWhile.parseA.txt
vendored
Normal file
@ -0,0 +1,36 @@
|
||||
(Statements
|
||||
(Class
|
||||
(Identifier)
|
||||
(Statements
|
||||
(Method
|
||||
(Void)
|
||||
(AccessibilityModifier)
|
||||
(AccessibilityModifier)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Annotation
|
||||
(Identifier)
|
||||
(Array
|
||||
(Empty)
|
||||
(Identifier)))
|
||||
(Statements
|
||||
(DoWhile
|
||||
(Not
|
||||
(Call
|
||||
(MemberAccess
|
||||
(TextElement))
|
||||
(Identifier)
|
||||
(Empty)))
|
||||
(Statements
|
||||
(Call
|
||||
(MemberAccess
|
||||
(MemberAccess
|
||||
(Identifier)))
|
||||
(TextElement)
|
||||
(Empty))
|
||||
(Assignment
|
||||
(Identifier)
|
||||
(Call
|
||||
(MemberAccess
|
||||
(Identifier))
|
||||
(Empty))))))))))
|
35
test/fixtures/java/corpus/DoWhile.parseB.txt
vendored
Normal file
35
test/fixtures/java/corpus/DoWhile.parseB.txt
vendored
Normal file
@ -0,0 +1,35 @@
|
||||
(Statements
|
||||
(Class
|
||||
(Identifier)
|
||||
(Statements
|
||||
(Method
|
||||
(Void)
|
||||
(AccessibilityModifier)
|
||||
(AccessibilityModifier)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Annotation
|
||||
(Identifier)
|
||||
(Array
|
||||
(Empty)
|
||||
(Identifier)))
|
||||
(Statements
|
||||
(Statements
|
||||
(Assignment
|
||||
(Variable
|
||||
(Int)
|
||||
(Identifier))
|
||||
(Integer)))
|
||||
(DoWhile
|
||||
(LessThanEqual
|
||||
(Identifier)
|
||||
(Integer))
|
||||
(Statements
|
||||
(Call
|
||||
(MemberAccess
|
||||
(MemberAccess
|
||||
(Identifier)))
|
||||
(Identifier)
|
||||
(Empty))
|
||||
(PostIncrement
|
||||
(Identifier)))))))))
|
3
test/fixtures/java/corpus/EnumDeclaration.A.java
vendored
Normal file
3
test/fixtures/java/corpus/EnumDeclaration.A.java
vendored
Normal file
@ -0,0 +1,3 @@
|
||||
public enum Colour {
|
||||
|
||||
}
|
4
test/fixtures/java/corpus/EnumDeclaration.B.java
vendored
Normal file
4
test/fixtures/java/corpus/EnumDeclaration.B.java
vendored
Normal file
@ -0,0 +1,4 @@
|
||||
enum Colour
|
||||
{
|
||||
RED, GREEN, BLUE;
|
||||
}
|
7
test/fixtures/java/corpus/EnumDeclaration.diffA-B.txt
vendored
Normal file
7
test/fixtures/java/corpus/EnumDeclaration.diffA-B.txt
vendored
Normal file
@ -0,0 +1,7 @@
|
||||
(Statements
|
||||
(EnumDeclaration
|
||||
{-(AccessibilityModifier)-}
|
||||
(Identifier)
|
||||
{+(Identifier)+}
|
||||
{+(Identifier)+}
|
||||
{+(Identifier)+}))
|
7
test/fixtures/java/corpus/EnumDeclaration.diffB-A.txt
vendored
Normal file
7
test/fixtures/java/corpus/EnumDeclaration.diffB-A.txt
vendored
Normal file
@ -0,0 +1,7 @@
|
||||
(Statements
|
||||
(EnumDeclaration
|
||||
{+(AccessibilityModifier)+}
|
||||
(Identifier)
|
||||
{-(Identifier)-}
|
||||
{-(Identifier)-}
|
||||
{-(Identifier)-}))
|
4
test/fixtures/java/corpus/EnumDeclaration.parseA.txt
vendored
Normal file
4
test/fixtures/java/corpus/EnumDeclaration.parseA.txt
vendored
Normal file
@ -0,0 +1,4 @@
|
||||
(Statements
|
||||
(EnumDeclaration
|
||||
(AccessibilityModifier)
|
||||
(Identifier)))
|
6
test/fixtures/java/corpus/EnumDeclaration.parseB.txt
vendored
Normal file
6
test/fixtures/java/corpus/EnumDeclaration.parseB.txt
vendored
Normal file
@ -0,0 +1,6 @@
|
||||
(Statements
|
||||
(EnumDeclaration
|
||||
(Identifier)
|
||||
(Identifier)
|
||||
(Identifier)
|
||||
(Identifier)))
|
5
test/fixtures/java/corpus/FieldAccess.B.java
vendored
Normal file
5
test/fixtures/java/corpus/FieldAccess.B.java
vendored
Normal file
@ -0,0 +1,5 @@
|
||||
class Grouped {
|
||||
Flowable(K key) {
|
||||
System.out.println(favorite().mountain);
|
||||
}
|
||||
}
|
23
test/fixtures/java/corpus/FieldAccess.diffA-B.txt
vendored
Normal file
23
test/fixtures/java/corpus/FieldAccess.diffA-B.txt
vendored
Normal file
@ -0,0 +1,23 @@
|
||||
(Statements
|
||||
(Class
|
||||
(Identifier)
|
||||
(Statements
|
||||
(Constructor
|
||||
(Identifier)
|
||||
(Annotation
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Statements
|
||||
{+(Call
|
||||
{+(MemberAccess
|
||||
{+(MemberAccess
|
||||
{+(Identifier)+})+})+}
|
||||
{+(MemberAccess
|
||||
{+(Call
|
||||
{+(Identifier)+}
|
||||
{+(Empty)+})+})+}
|
||||
{+(Empty)+})+}
|
||||
{-(Assignment
|
||||
{-(MemberAccess
|
||||
{-(This)-})-}
|
||||
{-(Identifier)-})-})))))
|
23
test/fixtures/java/corpus/FieldAccess.diffB-A.txt
vendored
Normal file
23
test/fixtures/java/corpus/FieldAccess.diffB-A.txt
vendored
Normal file
@ -0,0 +1,23 @@
|
||||
(Statements
|
||||
(Class
|
||||
(Identifier)
|
||||
(Statements
|
||||
(Constructor
|
||||
(Identifier)
|
||||
(Annotation
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Statements
|
||||
{+(Assignment
|
||||
{+(MemberAccess
|
||||
{+(This)+})+}
|
||||
{+(Identifier)+})+}
|
||||
{-(Call
|
||||
{-(MemberAccess
|
||||
{-(MemberAccess
|
||||
{-(Identifier)-})-})-}
|
||||
{-(MemberAccess
|
||||
{-(Call
|
||||
{-(Identifier)-}
|
||||
{-(Empty)-})-})-}
|
||||
{-(Empty)-})-})))))
|
14
test/fixtures/java/corpus/FieldAccess.parseA.txt
vendored
Normal file
14
test/fixtures/java/corpus/FieldAccess.parseA.txt
vendored
Normal file
@ -0,0 +1,14 @@
|
||||
(Statements
|
||||
(Class
|
||||
(Identifier)
|
||||
(Statements
|
||||
(Constructor
|
||||
(Identifier)
|
||||
(Annotation
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Statements
|
||||
(Assignment
|
||||
(MemberAccess
|
||||
(This))
|
||||
(Identifier)))))))
|
19
test/fixtures/java/corpus/FieldAccess.parseB.txt
vendored
Normal file
19
test/fixtures/java/corpus/FieldAccess.parseB.txt
vendored
Normal file
@ -0,0 +1,19 @@
|
||||
(Statements
|
||||
(Class
|
||||
(Identifier)
|
||||
(Statements
|
||||
(Constructor
|
||||
(Identifier)
|
||||
(Annotation
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Statements
|
||||
(Call
|
||||
(MemberAccess
|
||||
(MemberAccess
|
||||
(Identifier)))
|
||||
(MemberAccess
|
||||
(Call
|
||||
(Identifier)
|
||||
(Empty)))
|
||||
(Empty)))))))
|
7
test/fixtures/java/corpus/Float.B.java
vendored
Normal file
7
test/fixtures/java/corpus/Float.B.java
vendored
Normal file
@ -0,0 +1,7 @@
|
||||
public class Point {
|
||||
void dinosaur() {
|
||||
Float x = 10.0;
|
||||
Float y = 20.0;
|
||||
System.out.print(x + y);
|
||||
}
|
||||
}
|
30
test/fixtures/java/corpus/Float.diffA-B.txt
vendored
Normal file
30
test/fixtures/java/corpus/Float.diffA-B.txt
vendored
Normal file
@ -0,0 +1,30 @@
|
||||
(Statements
|
||||
(Class
|
||||
(AccessibilityModifier)
|
||||
(Identifier)
|
||||
(Statements
|
||||
(Method
|
||||
(Void)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Statements
|
||||
(Statements
|
||||
(Assignment
|
||||
(Variable
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Float)))
|
||||
{+(Statements
|
||||
{+(Assignment
|
||||
{+(Variable
|
||||
{+(Identifier)+}
|
||||
{+(Identifier)+})+}
|
||||
{+(Float)+})+})+}
|
||||
{+(Call
|
||||
{+(MemberAccess
|
||||
{+(MemberAccess
|
||||
{+(Identifier)+})+})+}
|
||||
{+(Plus
|
||||
{+(Identifier)+}
|
||||
{+(Identifier)+})+}
|
||||
{+(Empty)+})+})))))
|
30
test/fixtures/java/corpus/Float.diffB-A.txt
vendored
Normal file
30
test/fixtures/java/corpus/Float.diffB-A.txt
vendored
Normal file
@ -0,0 +1,30 @@
|
||||
(Statements
|
||||
(Class
|
||||
(AccessibilityModifier)
|
||||
(Identifier)
|
||||
(Statements
|
||||
(Method
|
||||
(Void)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Statements
|
||||
(Statements
|
||||
(Assignment
|
||||
(Variable
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Float)))
|
||||
{-(Statements
|
||||
{-(Assignment
|
||||
{-(Variable
|
||||
{-(Identifier)-}
|
||||
{-(Identifier)-})-}
|
||||
{-(Float)-})-})-}
|
||||
{-(Call
|
||||
{-(MemberAccess
|
||||
{-(MemberAccess
|
||||
{-(Identifier)-})-})-}
|
||||
{-(Plus
|
||||
{-(Identifier)-}
|
||||
{-(Identifier)-})-}
|
||||
{-(Empty)-})-})))))
|
16
test/fixtures/java/corpus/Float.parseA.txt
vendored
Normal file
16
test/fixtures/java/corpus/Float.parseA.txt
vendored
Normal file
@ -0,0 +1,16 @@
|
||||
(Statements
|
||||
(Class
|
||||
(AccessibilityModifier)
|
||||
(Identifier)
|
||||
(Statements
|
||||
(Method
|
||||
(Void)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Statements
|
||||
(Statements
|
||||
(Assignment
|
||||
(Variable
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Float))))))))
|
30
test/fixtures/java/corpus/Float.parseB.txt
vendored
Normal file
30
test/fixtures/java/corpus/Float.parseB.txt
vendored
Normal file
@ -0,0 +1,30 @@
|
||||
(Statements
|
||||
(Class
|
||||
(AccessibilityModifier)
|
||||
(Identifier)
|
||||
(Statements
|
||||
(Method
|
||||
(Void)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Statements
|
||||
(Statements
|
||||
(Assignment
|
||||
(Variable
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Float)))
|
||||
(Statements
|
||||
(Assignment
|
||||
(Variable
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Float)))
|
||||
(Call
|
||||
(MemberAccess
|
||||
(MemberAccess
|
||||
(Identifier)))
|
||||
(Plus
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Empty)))))))
|
7
test/fixtures/java/corpus/For.B.java
vendored
Normal file
7
test/fixtures/java/corpus/For.B.java
vendored
Normal file
@ -0,0 +1,7 @@
|
||||
class ForDemo {
|
||||
public static void main(String[] args){
|
||||
for(int i: list){
|
||||
System.out.println("Count is: " + i);
|
||||
}
|
||||
}
|
||||
}
|
52
test/fixtures/java/corpus/For.diffA-B.txt
vendored
Normal file
52
test/fixtures/java/corpus/For.diffA-B.txt
vendored
Normal file
@ -0,0 +1,52 @@
|
||||
(Statements
|
||||
(Class
|
||||
(Identifier)
|
||||
(Statements
|
||||
(Method
|
||||
(Void)
|
||||
(AccessibilityModifier)
|
||||
(AccessibilityModifier)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Annotation
|
||||
(Identifier)
|
||||
(Array
|
||||
(Empty)
|
||||
(Identifier)))
|
||||
(Statements
|
||||
{+(ForEach
|
||||
{+(Variable
|
||||
{+(Int)+}
|
||||
{+(Identifier)+})+}
|
||||
{+(Identifier)+}
|
||||
{+(Statements
|
||||
{+(Call
|
||||
{+(MemberAccess
|
||||
{+(MemberAccess
|
||||
{+(Identifier)+})+})+}
|
||||
{+(Plus
|
||||
{+(TextElement)+}
|
||||
{+(Identifier)+})+}
|
||||
{+(Empty)+})+})+})+}
|
||||
{-(For
|
||||
{-(Statements
|
||||
{-(Assignment
|
||||
{-(Variable
|
||||
{-(Int)-}
|
||||
{-(Identifier)-})-}
|
||||
{-(Integer)-})-})-}
|
||||
{-(LessThan
|
||||
{-(Identifier)-}
|
||||
{-(Integer)-})-}
|
||||
{-(Statements
|
||||
{-(PostIncrement
|
||||
{-(Identifier)-})-})-}
|
||||
{-(Statements
|
||||
{-(Call
|
||||
{-(MemberAccess
|
||||
{-(MemberAccess
|
||||
{-(Identifier)-})-})-}
|
||||
{-(Plus
|
||||
{-(TextElement)-}
|
||||
{-(Identifier)-})-}
|
||||
{-(Empty)-})-})-})-})))))
|
52
test/fixtures/java/corpus/For.diffB-A.txt
vendored
Normal file
52
test/fixtures/java/corpus/For.diffB-A.txt
vendored
Normal file
@ -0,0 +1,52 @@
|
||||
(Statements
|
||||
(Class
|
||||
(Identifier)
|
||||
(Statements
|
||||
(Method
|
||||
(Void)
|
||||
(AccessibilityModifier)
|
||||
(AccessibilityModifier)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Annotation
|
||||
(Identifier)
|
||||
(Array
|
||||
(Empty)
|
||||
(Identifier)))
|
||||
(Statements
|
||||
{+(For
|
||||
{+(Statements
|
||||
{+(Assignment
|
||||
{+(Variable
|
||||
{+(Int)+}
|
||||
{+(Identifier)+})+}
|
||||
{+(Integer)+})+})+}
|
||||
{+(LessThan
|
||||
{+(Identifier)+}
|
||||
{+(Integer)+})+}
|
||||
{+(Statements
|
||||
{+(PostIncrement
|
||||
{+(Identifier)+})+})+}
|
||||
{+(Statements
|
||||
{+(Call
|
||||
{+(MemberAccess
|
||||
{+(MemberAccess
|
||||
{+(Identifier)+})+})+}
|
||||
{+(Plus
|
||||
{+(TextElement)+}
|
||||
{+(Identifier)+})+}
|
||||
{+(Empty)+})+})+})+}
|
||||
{-(ForEach
|
||||
{-(Variable
|
||||
{-(Int)-}
|
||||
{-(Identifier)-})-}
|
||||
{-(Identifier)-}
|
||||
{-(Statements
|
||||
{-(Call
|
||||
{-(MemberAccess
|
||||
{-(MemberAccess
|
||||
{-(Identifier)-})-})-}
|
||||
{-(Plus
|
||||
{-(TextElement)-}
|
||||
{-(Identifier)-})-}
|
||||
{-(Empty)-})-})-})-})))))
|
38
test/fixtures/java/corpus/For.parseA.txt
vendored
Normal file
38
test/fixtures/java/corpus/For.parseA.txt
vendored
Normal file
@ -0,0 +1,38 @@
|
||||
(Statements
|
||||
(Class
|
||||
(Identifier)
|
||||
(Statements
|
||||
(Method
|
||||
(Void)
|
||||
(AccessibilityModifier)
|
||||
(AccessibilityModifier)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Annotation
|
||||
(Identifier)
|
||||
(Array
|
||||
(Empty)
|
||||
(Identifier)))
|
||||
(Statements
|
||||
(For
|
||||
(Statements
|
||||
(Assignment
|
||||
(Variable
|
||||
(Int)
|
||||
(Identifier))
|
||||
(Integer)))
|
||||
(LessThan
|
||||
(Identifier)
|
||||
(Integer))
|
||||
(Statements
|
||||
(PostIncrement
|
||||
(Identifier)))
|
||||
(Statements
|
||||
(Call
|
||||
(MemberAccess
|
||||
(MemberAccess
|
||||
(Identifier)))
|
||||
(Plus
|
||||
(TextElement)
|
||||
(Identifier))
|
||||
(Empty)))))))))
|
30
test/fixtures/java/corpus/For.parseB.txt
vendored
Normal file
30
test/fixtures/java/corpus/For.parseB.txt
vendored
Normal file
@ -0,0 +1,30 @@
|
||||
(Statements
|
||||
(Class
|
||||
(Identifier)
|
||||
(Statements
|
||||
(Method
|
||||
(Void)
|
||||
(AccessibilityModifier)
|
||||
(AccessibilityModifier)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Annotation
|
||||
(Identifier)
|
||||
(Array
|
||||
(Empty)
|
||||
(Identifier)))
|
||||
(Statements
|
||||
(ForEach
|
||||
(Variable
|
||||
(Int)
|
||||
(Identifier))
|
||||
(Identifier)
|
||||
(Statements
|
||||
(Call
|
||||
(MemberAccess
|
||||
(MemberAccess
|
||||
(Identifier)))
|
||||
(Plus
|
||||
(TextElement)
|
||||
(Identifier))
|
||||
(Empty)))))))))
|
2
test/fixtures/java/corpus/If.B.java
vendored
Normal file
2
test/fixtures/java/corpus/If.B.java
vendored
Normal file
@ -0,0 +1,2 @@
|
||||
if (x=1)
|
||||
System.out.print(x);
|
14
test/fixtures/java/corpus/If.diffA-B.txt
vendored
Normal file
14
test/fixtures/java/corpus/If.diffA-B.txt
vendored
Normal file
@ -0,0 +1,14 @@
|
||||
(Statements
|
||||
(If
|
||||
{ (Identifier)
|
||||
->(Assignment
|
||||
{+(Identifier)+}
|
||||
{+(Integer)+}) }
|
||||
{ (Identifier)
|
||||
->(Call
|
||||
{+(MemberAccess
|
||||
{+(MemberAccess
|
||||
{+(Identifier)+})+})+}
|
||||
{+(Identifier)+}
|
||||
{+(Empty)+}) }
|
||||
(Empty)))
|
14
test/fixtures/java/corpus/If.diffB-A.txt
vendored
Normal file
14
test/fixtures/java/corpus/If.diffB-A.txt
vendored
Normal file
@ -0,0 +1,14 @@
|
||||
(Statements
|
||||
(If
|
||||
{ (Assignment
|
||||
{-(Identifier)-}
|
||||
{-(Integer)-})
|
||||
->(Identifier) }
|
||||
{ (Call
|
||||
{-(MemberAccess
|
||||
{-(MemberAccess
|
||||
{-(Identifier)-})-})-}
|
||||
{-(Identifier)-}
|
||||
{-(Empty)-})
|
||||
->(Identifier) }
|
||||
(Empty)))
|
5
test/fixtures/java/corpus/If.parseA.txt
vendored
Normal file
5
test/fixtures/java/corpus/If.parseA.txt
vendored
Normal file
@ -0,0 +1,5 @@
|
||||
(Statements
|
||||
(If
|
||||
(Identifier)
|
||||
(Identifier)
|
||||
(Empty)))
|
12
test/fixtures/java/corpus/If.parseB.txt
vendored
Normal file
12
test/fixtures/java/corpus/If.parseB.txt
vendored
Normal file
@ -0,0 +1,12 @@
|
||||
(Statements
|
||||
(If
|
||||
(Assignment
|
||||
(Identifier)
|
||||
(Integer))
|
||||
(Call
|
||||
(MemberAccess
|
||||
(MemberAccess
|
||||
(Identifier)))
|
||||
(Identifier)
|
||||
(Empty))
|
||||
(Empty)))
|
1
test/fixtures/java/corpus/Import.B.java
vendored
Normal file
1
test/fixtures/java/corpus/Import.B.java
vendored
Normal file
@ -0,0 +1 @@
|
||||
import java.until.*;
|
8
test/fixtures/java/corpus/Import.diffA-B.txt
vendored
Normal file
8
test/fixtures/java/corpus/Import.diffA-B.txt
vendored
Normal file
@ -0,0 +1,8 @@
|
||||
(Statements
|
||||
(Import
|
||||
{+(Identifier)+}
|
||||
{+(Identifier)+}
|
||||
{+(Asterisk)+}
|
||||
{-(Identifier)-}
|
||||
{-(Identifier)-}
|
||||
{-(Identifier)-}))
|
8
test/fixtures/java/corpus/Import.diffB-A.txt
vendored
Normal file
8
test/fixtures/java/corpus/Import.diffB-A.txt
vendored
Normal file
@ -0,0 +1,8 @@
|
||||
(Statements
|
||||
(Import
|
||||
{+(Identifier)+}
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
{-(Asterisk)-}))
|
5
test/fixtures/java/corpus/Import.parseA.txt
vendored
Normal file
5
test/fixtures/java/corpus/Import.parseA.txt
vendored
Normal file
@ -0,0 +1,5 @@
|
||||
(Statements
|
||||
(Import
|
||||
(Identifier)
|
||||
(Identifier)
|
||||
(Identifier)))
|
5
test/fixtures/java/corpus/Import.parseB.txt
vendored
Normal file
5
test/fixtures/java/corpus/Import.parseB.txt
vendored
Normal file
@ -0,0 +1,5 @@
|
||||
(Statements
|
||||
(Import
|
||||
(Identifier)
|
||||
(Identifier)
|
||||
(Asterisk)))
|
7
test/fixtures/java/corpus/Int.B.java
vendored
Normal file
7
test/fixtures/java/corpus/Int.B.java
vendored
Normal file
@ -0,0 +1,7 @@
|
||||
public class Point {
|
||||
void dinosaur() {
|
||||
Int A = 123;
|
||||
Int B = 10;
|
||||
System.out.print(A + B);
|
||||
}
|
||||
}
|
32
test/fixtures/java/corpus/Int.diffA-B.txt
vendored
Normal file
32
test/fixtures/java/corpus/Int.diffA-B.txt
vendored
Normal file
@ -0,0 +1,32 @@
|
||||
(Statements
|
||||
(Class
|
||||
(AccessibilityModifier)
|
||||
(Identifier)
|
||||
(Statements
|
||||
(Method
|
||||
(Void)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Statements
|
||||
(Statements
|
||||
(Assignment
|
||||
(Variable
|
||||
(Identifier)
|
||||
{ (Identifier)
|
||||
->(Identifier) })
|
||||
{ (Integer)
|
||||
->(Integer) }))
|
||||
{+(Statements
|
||||
{+(Assignment
|
||||
{+(Variable
|
||||
{+(Identifier)+}
|
||||
{+(Identifier)+})+}
|
||||
{+(Integer)+})+})+}
|
||||
{+(Call
|
||||
{+(MemberAccess
|
||||
{+(MemberAccess
|
||||
{+(Identifier)+})+})+}
|
||||
{+(Plus
|
||||
{+(Identifier)+}
|
||||
{+(Identifier)+})+}
|
||||
{+(Empty)+})+})))))
|
32
test/fixtures/java/corpus/Int.diffB-A.txt
vendored
Normal file
32
test/fixtures/java/corpus/Int.diffB-A.txt
vendored
Normal file
@ -0,0 +1,32 @@
|
||||
(Statements
|
||||
(Class
|
||||
(AccessibilityModifier)
|
||||
(Identifier)
|
||||
(Statements
|
||||
(Method
|
||||
(Void)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Statements
|
||||
(Statements
|
||||
(Assignment
|
||||
(Variable
|
||||
(Identifier)
|
||||
{ (Identifier)
|
||||
->(Identifier) })
|
||||
{ (Integer)
|
||||
->(Integer) }))
|
||||
{-(Statements
|
||||
{-(Assignment
|
||||
{-(Variable
|
||||
{-(Identifier)-}
|
||||
{-(Identifier)-})-}
|
||||
{-(Integer)-})-})-}
|
||||
{-(Call
|
||||
{-(MemberAccess
|
||||
{-(MemberAccess
|
||||
{-(Identifier)-})-})-}
|
||||
{-(Plus
|
||||
{-(Identifier)-}
|
||||
{-(Identifier)-})-}
|
||||
{-(Empty)-})-})))))
|
16
test/fixtures/java/corpus/Int.parseA.txt
vendored
Normal file
16
test/fixtures/java/corpus/Int.parseA.txt
vendored
Normal file
@ -0,0 +1,16 @@
|
||||
(Statements
|
||||
(Class
|
||||
(AccessibilityModifier)
|
||||
(Identifier)
|
||||
(Statements
|
||||
(Method
|
||||
(Void)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Statements
|
||||
(Statements
|
||||
(Assignment
|
||||
(Variable
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Integer))))))))
|
30
test/fixtures/java/corpus/Int.parseB.txt
vendored
Normal file
30
test/fixtures/java/corpus/Int.parseB.txt
vendored
Normal file
@ -0,0 +1,30 @@
|
||||
(Statements
|
||||
(Class
|
||||
(AccessibilityModifier)
|
||||
(Identifier)
|
||||
(Statements
|
||||
(Method
|
||||
(Void)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Statements
|
||||
(Statements
|
||||
(Assignment
|
||||
(Variable
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Integer)))
|
||||
(Statements
|
||||
(Assignment
|
||||
(Variable
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Integer)))
|
||||
(Call
|
||||
(MemberAccess
|
||||
(MemberAccess
|
||||
(Identifier)))
|
||||
(Plus
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Empty)))))))
|
3
test/fixtures/java/corpus/Interface.A.java
vendored
Normal file
3
test/fixtures/java/corpus/Interface.A.java
vendored
Normal file
@ -0,0 +1,3 @@
|
||||
interface Top {
|
||||
}
|
||||
// normal declaration
|
@ -1,3 +1,4 @@
|
||||
@interface TerminationHandle {
|
||||
Bar foo = 1;
|
||||
}
|
||||
// annotation type declaration
|
15
test/fixtures/java/corpus/Interface.diffA-B.txt
vendored
Normal file
15
test/fixtures/java/corpus/Interface.diffA-B.txt
vendored
Normal file
@ -0,0 +1,15 @@
|
||||
(Statements
|
||||
(InterfaceDeclaration
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Statements
|
||||
{+(Statements
|
||||
{+(Assignment
|
||||
{+(Variable
|
||||
{+(Identifier)+}
|
||||
{+(Identifier)+})+}
|
||||
{+(Integer)+})+})+}))
|
||||
(Context
|
||||
{ (Comment)
|
||||
->(Comment) }
|
||||
(Empty)))
|
15
test/fixtures/java/corpus/Interface.diffB-A.txt
vendored
Normal file
15
test/fixtures/java/corpus/Interface.diffB-A.txt
vendored
Normal file
@ -0,0 +1,15 @@
|
||||
(Statements
|
||||
(InterfaceDeclaration
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Statements
|
||||
{-(Statements
|
||||
{-(Assignment
|
||||
{-(Variable
|
||||
{-(Identifier)-}
|
||||
{-(Identifier)-})-}
|
||||
{-(Integer)-})-})-}))
|
||||
(Context
|
||||
{ (Comment)
|
||||
->(Comment) }
|
||||
(Empty)))
|
7
test/fixtures/java/corpus/Interface.parseA.txt
vendored
Normal file
7
test/fixtures/java/corpus/Interface.parseA.txt
vendored
Normal file
@ -0,0 +1,7 @@
|
||||
(Statements
|
||||
(InterfaceDeclaration
|
||||
(Identifier)
|
||||
(Statements))
|
||||
(Context
|
||||
(Comment)
|
||||
(Empty)))
|
13
test/fixtures/java/corpus/Interface.parseB.txt
vendored
Normal file
13
test/fixtures/java/corpus/Interface.parseB.txt
vendored
Normal file
@ -0,0 +1,13 @@
|
||||
(Statements
|
||||
(InterfaceDeclaration
|
||||
(Identifier)
|
||||
(Statements
|
||||
(Statements
|
||||
(Assignment
|
||||
(Variable
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Integer)))))
|
||||
(Context
|
||||
(Comment)
|
||||
(Empty)))
|
5
test/fixtures/java/corpus/Lambda.B.java
vendored
Normal file
5
test/fixtures/java/corpus/Lambda.B.java
vendored
Normal file
@ -0,0 +1,5 @@
|
||||
class LambdaTest {
|
||||
void singleton() {
|
||||
stateOwner.add(x -> System.out.println("State changed"));
|
||||
}
|
||||
}
|
26
test/fixtures/java/corpus/Lambda.diffA-B.txt
vendored
Normal file
26
test/fixtures/java/corpus/Lambda.diffA-B.txt
vendored
Normal file
@ -0,0 +1,26 @@
|
||||
(Statements
|
||||
(Class
|
||||
(Identifier)
|
||||
(Statements
|
||||
(Method
|
||||
(Void)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Statements
|
||||
{+(Call
|
||||
{+(MemberAccess
|
||||
{+(Identifier)+})+}
|
||||
{+(Lambda
|
||||
{+(Identifier)+}
|
||||
{+(LambdaBody
|
||||
{+(Call
|
||||
{+(MemberAccess
|
||||
{+(MemberAccess
|
||||
{+(Identifier)+})+})+}
|
||||
{+(TextElement)+}
|
||||
{+(Empty)+})+})+})+}
|
||||
{+(Empty)+})+}
|
||||
{-(Lambda
|
||||
{-(Identifier)-}
|
||||
{-(LambdaBody
|
||||
{-(Identifier)-})-})-})))))
|
26
test/fixtures/java/corpus/Lambda.diffB-A.txt
vendored
Normal file
26
test/fixtures/java/corpus/Lambda.diffB-A.txt
vendored
Normal file
@ -0,0 +1,26 @@
|
||||
(Statements
|
||||
(Class
|
||||
(Identifier)
|
||||
(Statements
|
||||
(Method
|
||||
(Void)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Statements
|
||||
{+(Lambda
|
||||
{+(Identifier)+}
|
||||
{+(LambdaBody
|
||||
{+(Identifier)+})+})+}
|
||||
{-(Call
|
||||
{-(MemberAccess
|
||||
{-(Identifier)-})-}
|
||||
{-(Lambda
|
||||
{-(Identifier)-}
|
||||
{-(LambdaBody
|
||||
{-(Call
|
||||
{-(MemberAccess
|
||||
{-(MemberAccess
|
||||
{-(Identifier)-})-})-}
|
||||
{-(TextElement)-}
|
||||
{-(Empty)-})-})-})-}
|
||||
{-(Empty)-})-})))))
|
13
test/fixtures/java/corpus/Lambda.parseA.txt
vendored
Normal file
13
test/fixtures/java/corpus/Lambda.parseA.txt
vendored
Normal file
@ -0,0 +1,13 @@
|
||||
(Statements
|
||||
(Class
|
||||
(Identifier)
|
||||
(Statements
|
||||
(Method
|
||||
(Void)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Statements
|
||||
(Lambda
|
||||
(Identifier)
|
||||
(LambdaBody
|
||||
(Identifier))))))))
|
22
test/fixtures/java/corpus/Lambda.parseB.txt
vendored
Normal file
22
test/fixtures/java/corpus/Lambda.parseB.txt
vendored
Normal file
@ -0,0 +1,22 @@
|
||||
(Statements
|
||||
(Class
|
||||
(Identifier)
|
||||
(Statements
|
||||
(Method
|
||||
(Void)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Statements
|
||||
(Call
|
||||
(MemberAccess
|
||||
(Identifier))
|
||||
(Lambda
|
||||
(Identifier)
|
||||
(LambdaBody
|
||||
(Call
|
||||
(MemberAccess
|
||||
(MemberAccess
|
||||
(Identifier)))
|
||||
(TextElement)
|
||||
(Empty))))
|
||||
(Empty)))))))
|
25
test/fixtures/java/corpus/ScopedIdentifier.diffA-B.txt
vendored
Normal file
25
test/fixtures/java/corpus/ScopedIdentifier.diffA-B.txt
vendored
Normal file
@ -0,0 +1,25 @@
|
||||
(Statements
|
||||
(Class
|
||||
{+(AccessibilityModifier)+}
|
||||
{+(AccessibilityModifier)+}
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
{+(MemberAccess
|
||||
{+(Identifier)+})+}
|
||||
(Statements
|
||||
{-(Method
|
||||
{-(Int)-}
|
||||
{-(Empty)-}
|
||||
{-(Identifier)-}
|
||||
{-(Annotation
|
||||
{-(Identifier)-}
|
||||
{-(Identifier)-})-}
|
||||
{-(Annotation
|
||||
{-(Identifier)-}
|
||||
{-(Identifier)-})-}
|
||||
{-(Statements
|
||||
{-(Call
|
||||
{-(MemberAccess
|
||||
{-(Identifier)-})-}
|
||||
{-(Identifier)-}
|
||||
{-(Empty)-})-})-})-})))
|
25
test/fixtures/java/corpus/ScopedIdentifier.diffB-A.txt
vendored
Normal file
25
test/fixtures/java/corpus/ScopedIdentifier.diffB-A.txt
vendored
Normal file
@ -0,0 +1,25 @@
|
||||
(Statements
|
||||
(Class
|
||||
{-(AccessibilityModifier)-}
|
||||
{-(AccessibilityModifier)-}
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
{-(MemberAccess
|
||||
{-(Identifier)-})-}
|
||||
(Statements
|
||||
{+(Method
|
||||
{+(Int)+}
|
||||
{+(Empty)+}
|
||||
{+(Identifier)+}
|
||||
{+(Annotation
|
||||
{+(Identifier)+}
|
||||
{+(Identifier)+})+}
|
||||
{+(Annotation
|
||||
{+(Identifier)+}
|
||||
{+(Identifier)+})+}
|
||||
{+(Statements
|
||||
{+(Call
|
||||
{+(MemberAccess
|
||||
{+(Identifier)+})+}
|
||||
{+(Identifier)+}
|
||||
{+(Empty)+})+})+})+})))
|
20
test/fixtures/java/corpus/ScopedIdentifier.parseA.txt
vendored
Normal file
20
test/fixtures/java/corpus/ScopedIdentifier.parseA.txt
vendored
Normal file
@ -0,0 +1,20 @@
|
||||
(Statements
|
||||
(Class
|
||||
(Identifier)
|
||||
(Statements
|
||||
(Method
|
||||
(Int)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Annotation
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Annotation
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Statements
|
||||
(Call
|
||||
(MemberAccess
|
||||
(Identifier))
|
||||
(Identifier)
|
||||
(Empty)))))))
|
8
test/fixtures/java/corpus/ScopedIdentifier.parseB.txt
vendored
Normal file
8
test/fixtures/java/corpus/ScopedIdentifier.parseB.txt
vendored
Normal file
@ -0,0 +1,8 @@
|
||||
(Statements
|
||||
(Class
|
||||
(AccessibilityModifier)
|
||||
(AccessibilityModifier)
|
||||
(Identifier)
|
||||
(MemberAccess
|
||||
(Identifier))
|
||||
(Statements)))
|
Some files were not shown because too many files have changed in this diff Show More
Loading…
Reference in New Issue
Block a user