1
1
mirror of https://github.com/github/semantic.git synced 2024-11-24 08:54:07 +03:00

Merge pull request #1577 from github/java-assignment

Java assignment WIP
This commit is contained in:
Ayman Nadeem 2018-06-01 12:57:08 -07:00 committed by GitHub
commit 437b59bc15
46 changed files with 1009 additions and 15 deletions

2
.ghci
View File

@ -24,6 +24,8 @@ assignmentExample lang = case lang of
"Haskell" -> mk "hs" "haskell"
"Markdown" -> mk "md" "markdown"
"JSON" -> mk "json" "json"
"Java" -> mk "java" "java"
"PHP" -> mk "php" "php"
_ -> mk "" ""
where mk fileExtension parser = putStrLn ("example: fmap (() <$) . runTask . parse " ++ parser ++ "Parser =<< Semantic.Util.blob \"example." ++ fileExtension ++ "\"") >> return ("import Parsing.Parser\nimport Semantic.Task\nimport Semantic.Util")
:}

View File

@ -133,6 +133,9 @@ library
, Language.Python.Assignment
, Language.Python.Grammar
, Language.Python.Syntax
, Language.Java.Assignment
, Language.Java.Grammar
, Language.Java.Syntax
-- Parser glue
, Parsing.CMark
, Parsing.Parser
@ -220,6 +223,7 @@ library
, tree-sitter-python
, tree-sitter-ruby
, tree-sitter-typescript
, tree-sitter-java
default-language: Haskell2010
default-extensions: DataKinds
, DeriveFoldable

View File

@ -9,6 +9,7 @@ import Proto3.Suite
data Language
= Go
| Haskell
| Java
| JavaScript
| JSON
| JSX
@ -22,6 +23,7 @@ data Language
-- | Returns a Language based on the file extension (including the ".").
languageForType :: String -> Maybe Language
languageForType mediaType = case mediaType of
".java" -> Just Java
".json" -> Just JSON
".hs" -> Just Haskell
".md" -> Just Markdown

View File

@ -330,7 +330,6 @@ instance ToJSONFields1 New
-- TODO: Implement Eval instance for New
instance Evaluatable New
-- | A cast expression to a specified type.
data Cast a = Cast { castSubject :: !a, castType :: !a }
deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1)
@ -343,3 +342,19 @@ instance ToJSONFields1 Cast
-- TODO: Implement Eval instance for Cast
instance Evaluatable Cast
data Super a = Super
deriving (Diffable, Eq, Foldable, Functor, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Hashable1)
instance Eq1 Super where liftEq = genericLiftEq
instance Ord1 Super where liftCompare = genericLiftCompare
instance Show1 Super where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Super
data This a = This
deriving (Diffable, Eq, Foldable, Functor, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Hashable1)
instance Eq1 This where liftEq = genericLiftEq
instance Ord1 This where liftCompare = genericLiftCompare
instance Show1 This where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable This

View File

@ -51,9 +51,7 @@ instance Evaluatable Data.Syntax.Literal.Integer where
instance ToJSONFields1 Data.Syntax.Literal.Integer where
toJSONFields1 (Integer i) = noChildren ["asString" .= unpack i]
-- TODO: Should IntegerLiteral hold an Integer instead of a ByteString?
-- TODO: Do we care about differentiating between hex/octal/decimal/binary integer literals?
-- TODO: Consider a Numeric datatype with FloatingPoint/Integral/etc constructors.
-- | A literal float of unspecified width.

View File

@ -155,6 +155,29 @@ instance ToJSONFields1 PostDecrement
-- TODO: Implement Eval instance for PostDecrement
instance Evaluatable PostDecrement
-- | Pre increment operator (e.g. ++1 in C or Java).
newtype PreIncrement a = PreIncrement a
deriving (Diffable, Eq, Foldable, Functor, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Hashable1)
instance Eq1 PreIncrement where liftEq = genericLiftEq
instance Ord1 PreIncrement where liftCompare = genericLiftCompare
instance Show1 PreIncrement where liftShowsPrec = genericLiftShowsPrec
-- TODO: Implement Eval instance for PreIncrement
instance Evaluatable PreIncrement
-- | Pre decrement operator (e.g. --1 in C or Java).
newtype PreDecrement a = PreDecrement a
deriving (Diffable, Eq, Foldable, Functor, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Hashable1)
instance Eq1 PreDecrement where liftEq = genericLiftEq
instance Ord1 PreDecrement where liftCompare = genericLiftCompare
instance Show1 PreDecrement where liftShowsPrec = genericLiftShowsPrec
-- TODO: Implement Eval instance for PreDecrement
instance Evaluatable PreDecrement
-- Returns

View File

@ -4,6 +4,7 @@ module Data.Syntax.Type where
import Data.Abstract.Evaluatable
import Data.JSON.Fields
import Diffing.Algorithm
import Prelude hiding (Int, Float, Bool)
import Prologue hiding (Map)
data Array a = Array { arraySize :: !(Maybe a), arrayElementType :: !a }
@ -149,3 +150,45 @@ instance ToJSONFields1 TypeParameters
-- TODO: Implement Eval instance for TypeParameters
instance Evaluatable TypeParameters
-- data instead of newtype because no payload
data Void a = Void
deriving (Diffable, Eq, Foldable, Functor, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Hashable1)
instance Eq1 Void where liftEq = genericLiftEq
instance Ord1 Void where liftCompare = genericLiftCompare
instance Show1 Void where liftShowsPrec = genericLiftShowsPrec
-- TODO: Implement Eval instance for Void
instance Evaluatable Void
-- data instead of newtype because no payload
data Int a = Int
deriving (Diffable, Eq, Foldable, Functor, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Hashable1)
instance Eq1 Int where liftEq = genericLiftEq
instance Ord1 Int where liftCompare = genericLiftCompare
instance Show1 Int where liftShowsPrec = genericLiftShowsPrec
-- TODO: Implement Eval instance for Int
instance Evaluatable Int
data Float a = Float | Double
deriving (Diffable, Eq, Foldable, Functor, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Hashable1)
instance Eq1 Float where liftEq = genericLiftEq
instance Ord1 Float where liftCompare = genericLiftCompare
instance Show1 Float where liftShowsPrec = genericLiftShowsPrec
-- TODO: Implement Eval instance for Float
instance Evaluatable Float
data Bool a = Bool
deriving (Diffable, Eq, Foldable, Functor, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Hashable1)
instance Eq1 Bool where liftEq = genericLiftEq
instance Ord1 Bool where liftCompare = genericLiftCompare
instance Show1 Bool where liftShowsPrec = genericLiftShowsPrec
-- TODO: Implement Eval instance for Float
instance Evaluatable Bool

View File

@ -0,0 +1,553 @@
{-# LANGUAGE DataKinds, RankNTypes, TypeOperators #-}
module Language.Java.Assignment
( assignment
, Syntax
, Grammar
, Term
) where
import Assigning.Assignment hiding (Assignment, Error, while, try)
import Data.Abstract.Name
import Data.Functor (($>))
import Data.List.NonEmpty (some1)
import Data.Record
import Data.Syntax (contextualize, emptyTerm, handleError, infixContext, makeTerm, makeTerm', makeTerm'', makeTerm1, parseError, postContextualize)
import Data.Sum
import GHC.Stack
import Language.Java.Grammar as Grammar
import Language.Java.Syntax as Java.Syntax
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.Expression as Expression
import qualified Data.Syntax.Literal as Literal
import qualified Data.Syntax.Statement as Statement
import qualified Data.Syntax.Type as Type
import qualified Data.Term as Term
import Prelude hiding (break)
import Prologue hiding (for, try, This)
type Syntax =
'[ Comment.Comment
, Declaration.Class
, Declaration.InterfaceDeclaration
, Declaration.Method
, Declaration.VariableDeclaration
, Expression.Arithmetic
, Expression.Call
, Expression.Comparison
, Expression.Bitwise
, Expression.Boolean
, Expression.InstanceOf
, Expression.MemberAccess
, Expression.Super
, Expression.This
, Java.Syntax.Annotation
, Java.Syntax.AnnotationField
, Java.Syntax.Asterisk
, Java.Syntax.Constructor
, Java.Syntax.EnumDeclaration
, Java.Syntax.GenericType
, Java.Syntax.Import
, Java.Syntax.Module
, Java.Syntax.New
, Java.Syntax.Package
, Java.Syntax.Synchronized
, Java.Syntax.TypeParameter
, Java.Syntax.TypeWithModifiers
, Java.Syntax.Variable
, Literal.Array
, Literal.Boolean
, Literal.Integer
, Literal.Float
, Literal.Null
, Literal.String
, Literal.TextElement
, Statement.Assignment
, Statement.Break
, Statement.Catch
, Statement.Continue
, Statement.DoWhile
, Statement.Finally
, Statement.For
, Statement.ForEach
, Statement.If
, Statement.Match
, Statement.Pattern
, Statement.PostIncrement
, Statement.PostDecrement
, Statement.PreIncrement
, Statement.PreDecrement
, Statement.While
, Statement.Throw
, Statement.Try
, Syntax.Context
, Syntax.Empty
, Syntax.Error
, Syntax.Identifier
, Syntax.AccessibilityModifier
, Syntax.Program
, Type.Array
, Type.Bool
, Type.Int
, Type.Void
, Type.Float
, Type.Annotation
, Statement.Return
, []
]
type Term = Term.Term (Sum Syntax) (Record Location)
type Assignment = HasCallStack => Assignment.Assignment [] Grammar Term
-- | Assignment from AST in Java's grammar onto a program in Java's syntax.
assignment :: Assignment
assignment = handleError $ makeTerm <$> symbol Grammar.Program <*> children (Syntax.Program <$> manyTerm expression) <|> parseError
-- | Match a term optionally preceded by comment(s), or a sequence of comments if the term is not present.
manyTerm :: Assignment -> Assignment.Assignment [] Grammar [Term]
manyTerm term = many (contextualize comment term <|> makeTerm1 <$> (Syntax.Context <$> some1 comment <*> emptyTerm))
-- | Match a series of terms or comments until a delimiter is matched.
manyTermsTill :: Assignment.Assignment [] Grammar Term
-> Assignment.Assignment [] Grammar b
-> Assignment.Assignment [] Grammar [Term]
manyTermsTill step = manyTill (step <|> comment)
someTerm :: Assignment -> Assignment.Assignment [] Grammar [Term]
someTerm term = some (contextualize comment term <|> makeTerm1 <$> (Syntax.Context <$> some1 comment <*> emptyTerm))
-- | Match comments before and after the node.
term :: Assignment -> Assignment
term term = contextualize comment (postContextualize comment term)
-- | Match
expression :: Assignment
expression = handleError (choice expressionChoices)
expressions :: Assignment
expressions = makeTerm'' <$> location <*> many expression
expressionChoices :: [Assignment.Assignment [] Grammar Term]
expressionChoices =
[
arrayInitializer
, assignment'
, block
, binary
, boolean
, break
, castExpression
, char
, class'
, classInstance
, continue
, constructorDeclaration
, explicitConstructorInvocation
-- , constantDeclaration
, doWhile
, fieldDeclaration
, float
, for
, enum
-- , hexadecimal
, if'
, interface
, identifier
, import'
, integer
, method
, methodInvocation
, module'
, null'
, package
, return'
, scopedIdentifier
, string
, super
, switch
, synchronized
, ternary
, this
, throw
, try
, unary
, update
, localVariableDeclaration
, localVariableDeclarationStatement
, while
]
modifier :: Assignment
modifier = make <$> symbol Modifier <*> children(Left <$> annotation <|> Right . Syntax.AccessibilityModifier <$> source)
where
make loc (Right modifier) = makeTerm loc modifier
make _ (Left annotation) = annotation
arrayInitializer :: Assignment
arrayInitializer = makeTerm <$> symbol ArrayInitializer <*> (Literal.Array <$> many expression)
comment :: Assignment
comment = makeTerm <$> symbol Comment <*> (Comment.Comment <$> source)
localVariableDeclaration :: Assignment
localVariableDeclaration = makeTerm <$> symbol LocalVariableDeclaration <*> children ((,) <$> manyTerm modifier <*> type' <**> variableDeclaratorList)
variableDeclaratorList :: Assignment.Assignment [] Grammar (([Term], Term) -> [Term])
variableDeclaratorList = symbol VariableDeclaratorList *> children (makeDecl <$> some variableDeclarator)
where
variableDeclarator = symbol VariableDeclarator *> children ((,) <$> variableDeclaratorId <*> optional expression)
makeDecl decls (modifiers, type') = map (makeSingleDecl modifiers type') decls
makeSingleDecl modifiers type' (target, Nothing) = makeTerm1 (Java.Syntax.Variable modifiers type' target)
makeSingleDecl modifiers type' (target, Just value) = makeTerm1 (Statement.Assignment [] (makeTerm1 (Java.Syntax.Variable modifiers type' target)) value)
localVariableDeclarationStatement :: Assignment
localVariableDeclarationStatement = symbol LocalVariableDeclarationStatement *> children localVariableDeclaration
variableDeclaratorId :: Assignment
variableDeclaratorId = symbol VariableDeclaratorId *> children identifier
-- Literals
boolean :: Assignment
boolean = makeTerm <$> symbol BooleanLiteral <*> children
(token Grammar.True $> Literal.true
<|> token Grammar.False $> Literal.false)
null' :: Assignment
null' = makeTerm <$> symbol NullLiteral <*> (Literal.Null <$ source)
-- Integer supports all integer and floating point literals (hex, octal, binary)
integer :: Assignment
integer = makeTerm <$> symbol IntegerLiteral <*> children (Literal.Integer <$> source)
float :: Assignment
float = makeTerm <$> symbol FloatingPointLiteral <*> children (Literal.Float <$> source)
string :: Assignment
string = makeTerm <$> symbol StringLiteral <*> (Literal.TextElement <$> source)
char :: Assignment
char = makeTerm <$> symbol CharacterLiteral <*> (Literal.TextElement <$> source)
-- Identifiers
identifier :: Assignment
identifier = makeTerm <$> (symbol Identifier <|> symbol TypeIdentifier) <*> (Syntax.Identifier . name <$> source)
scopedIdentifier :: Assignment
scopedIdentifier = makeTerm <$> symbol ScopedIdentifier <*> children (Expression.MemberAccess <$> term expression <*> term expression)
superInterfaces :: Assignment.Assignment [] Grammar [Term]
superInterfaces = symbol SuperInterfaces *> children (symbol InterfaceTypeList *> children(manyTerm type'))
-- a *> b
-- both of these are impure
-- getLine *> getLine
-- in half apply, they're both monadic impure actions
-- :t (<$)
-- :t (*>)
-- what does it mean to say monadic action? more precise term: sequence-able
-- a sequence of applicative actions can be executed left to right
-- applicative computations can't do branch and control flow; applicative computations can only compute in a direct line, monadic can compute arbitrary branches
-- Declarations
class' :: Assignment
class' = makeTerm <$> symbol ClassDeclaration <*> children (makeClass <$> many modifier <*> term identifier <*> (typeParameters <|> pure []) <*> optional superClass <*> (superInterfaces <|> pure []) <*> classBody)
where
makeClass modifiers identifier typeParams superClass superInterfaces = Declaration.Class (modifiers ++ typeParams) identifier (maybeToList superClass ++ superInterfaces) -- not doing an assignment, just straight up function
classBody = makeTerm <$> symbol ClassBody <*> children (manyTerm expression)
superClass = symbol Superclass *> children type'
-- matching term expression won't work since there is no node for that; it's AnonExtends
-- superClass = makeTerm <$> symbol SuperClass <*> children (Java.Syntax.SuperClass <$> term expression <*> type')
-- We'd still like to match the SuperClass node, but we don't need to create a syntax to make a term
-- Do you lose info by omitting the superclass term? No...
-- Don't need to make a term since we're not using syntax
-- what's the difference between using tokens: AnonExtends GenericType?
-- optional: when something can or can't exist and you want to produce a Maybe
-- TODO: superclass -- need to match the superclass node when it exists (which will be a rule, similar to how the type params rule matches the typeparams node when it exists)
-- optional, when we have a single term
-- superInterfaces is also optional but since it produces a list, lists already have an empty value so we don't need to wrap it up in a maybe to get an empty value
-- define this at the top level, we may change TS grammar so that if someone wants to write a Java snippet we could assign
-- it correctly; fieldDeclaration is standalone (compared to a type, which doesn't say anything by itself)
fieldDeclaration :: Assignment
fieldDeclaration = makeTerm <$> symbol FieldDeclaration <*> children ((,) <$> manyTerm modifier <*> type' <**> variableDeclaratorList)
method :: Assignment
method = makeTerm <$> symbol MethodDeclaration <*> children (makeMethod <$> many modifier <*> emptyTerm <*> methodHeader <*> methodBody)
where
methodBody = symbol MethodBody *> children (term expression <|> emptyTerm)
methodDeclarator = symbol MethodDeclarator *> children ( (,) <$> identifier <*> formalParameters)
methodHeader = symbol MethodHeader *> children ((,,,,) <$> (typeParameters <|> pure []) <*> manyTerm annotation <*> type' <*> methodDeclarator <*> (throws <|> pure []))
makeMethod modifiers receiver (typeParams, annotations, returnType, (name, params), throws) = Declaration.Method (returnType : modifiers ++ typeParams ++ annotations ++ throws) receiver name params
-- TODO: add genericType
-- Question: should this genericType be part of type or not? Its own type because it's different structurally
generic :: Assignment
generic = makeTerm <$> symbol Grammar.GenericType <*> children(Java.Syntax.GenericType <$> term type' <*> manyTerm type')
-- when do we make a term again? - if we want to wrap something in a syntax constructor, because each piece of syntax
-- will be populated by further terms inside it. in this case, we wrap two terms in a piece of syntax.
-- Q to help decide: do we lose anything by omitting the term?
methodInvocation :: Assignment
methodInvocation = makeTerm <$> symbol MethodInvocation <*> children (Expression.Call [] <$> (callFunction <$> expression <*> optional (token AnonDot *> expression)) <*> (argumentList <|> pure []) <*> emptyTerm)
where
callFunction a (Just b) = makeTerm1 (Expression.MemberAccess a b)
callFunction a Nothing = a
explicitConstructorInvocation :: Assignment
explicitConstructorInvocation = makeTerm <$> symbol ExplicitConstructorInvocation <*> children (Expression.Call [] <$> (callFunction <$> term expression <*> optional (token AnonDot *> term expression)) <*> argumentList <*> emptyTerm)
where
callFunction a (Just b) = makeTerm1 (Expression.MemberAccess a b)
callFunction a Nothing = a
module' :: Assignment
module' = makeTerm <$> symbol ModuleDeclaration <*> children (Java.Syntax.Module <$> expression <*> many expression)
import' :: Assignment
import' = makeTerm <$> symbol ImportDeclaration <*> children (Java.Syntax.Import <$> someTerm (expression <|> asterisk))
where asterisk = makeTerm <$> token Grammar.Asterisk <*> pure Java.Syntax.Asterisk
interface :: Assignment
interface = makeTerm <$> symbol InterfaceDeclaration <*> children (normal <|> annotationType)
where
interfaceBody = makeTerm <$> symbol InterfaceBody <*> children (manyTerm interfaceMemberDeclaration)
normal = symbol NormalInterfaceDeclaration *> children (makeInterface <$> manyTerm modifier <*> identifier <*> (typeParameters <|> pure []) <*> interfaceBody)
makeInterface modifiers identifier typeParams = Declaration.InterfaceDeclaration (modifiers ++ typeParams) identifier
annotationType = symbol AnnotationTypeDeclaration *> children (Declaration.InterfaceDeclaration [] <$> identifier <*> annotationTypeBody)
annotationTypeBody = makeTerm <$> symbol AnnotationTypeBody <*> children (many expression)
interfaceMemberDeclaration = symbol InterfaceMemberDeclaration *> children (term expression)
-- we won't make a term because we have a choice of a bunch of things
package :: Assignment
-- package = makeTerm <$> symbol PackageDeclaration <*> children (Java.Syntax.Package <$> someTerm expression)
package = do
loc <- symbol PackageDeclaration -- location which is calling the symbol API
c <- children $ do Java.Syntax.Package <$> someTerm expression
pure (makeTerm loc c) -- pure is re-wrapping it back into the outer context, which in this case is Assignment (ie., the return type of the function)
enum :: Assignment
enum = makeTerm <$> symbol Grammar.EnumDeclaration <*> children (Java.Syntax.EnumDeclaration <$> term identifier <*> manyTerm enumConstant)
where enumConstant = symbol EnumConstant *> children (term identifier)
return' :: Assignment
return' = makeTerm <$> symbol ReturnStatement <*> (Statement.Return <$> children expression)
-- method expressions
dims :: Assignment.Assignment [] Grammar [Term]
dims = symbol Dims *> children (many (emptyTerm <* token AnonLBracket <* token AnonRBracket))
type' :: Assignment
type' = choice [
makeTerm <$> token VoidType <*> pure Type.Void
, makeTerm <$> token IntegralType <*> pure Type.Int
, makeTerm <$> token FloatingPointType <*> pure Type.Float
, makeTerm <$> token BooleanType <*> pure Type.Bool
, symbol ArrayType *> children (array <$> type' <*> dims) -- type rule recurs into itself
, symbol CatchType *> children (term type')
, symbol ExceptionType *> children (term type')
, symbol TypeArgument *> children (term type')
-- , symbol WildCard *> children (term type')
, identifier
, generic
]
where array = foldl (\into each -> makeTerm1 (Type.Array (Just each) into))
if' :: Assignment
if' = makeTerm <$> symbol IfThenElseStatement <*> children (Statement.If <$> term expression <*> term expression <*> (term expression <|> emptyTerm))
block :: Assignment
block = makeTerm <$> symbol Block <*> children (manyTerm expression)
while :: Assignment
while = makeTerm <$> symbol WhileStatement <*> children (Statement.While <$> term expression <*> term expression)
doWhile :: Assignment
doWhile = makeTerm <$> symbol DoStatement <*> children (flip Statement.DoWhile <$> term expression <*> term expression)
switch :: Assignment
switch = makeTerm <$> symbol SwitchStatement <*> children (Statement.Match <$> term expression <*> switchBlock)
where
switchBlock = makeTerm <$> symbol SwitchBlock <*> children (manyTerm switchLabel)
switchLabel = makeTerm <$> symbol SwitchLabel <*> (Statement.Pattern <$> children (term expression <|> emptyTerm) <*> expressions)
break :: Assignment
break = makeTerm <$> symbol BreakStatement <*> children (Statement.Break <$> (term expression <|> emptyTerm))
continue :: Assignment
continue = makeTerm <$> symbol ContinueStatement <*> children (Statement.Continue <$> (term expression <|> emptyTerm))
throw :: Assignment
throw = makeTerm <$> symbol ThrowStatement <*> children (Statement.Throw <$> term expression)
try :: Assignment
try = makeTerm <$> symbol TryStatement <*> children (Statement.Try <$> term expression <*> (append <$> optional catches <*> optional finally))
where
catches = symbol Catches *> children (manyTerm catch)
catch = makeTerm <$> symbol CatchClause <*> children (Statement.Catch <$> catchFormalParameter <*> term expression)
catchFormalParameter = makeTerm <$> symbol CatchFormalParameter <*> children (flip Type.Annotation <$> type' <* symbol VariableDeclaratorId <*> children identifier)
finally = makeTerm <$> symbol Finally <*> children (Statement.Finally <$> term expression)
-- append catches finally =
append Nothing Nothing = []
append Nothing (Just a) = [a]
append (Just a) Nothing = a
append (Just a) (Just b) = a <> [b]
for :: Assignment
for = symbol ForStatement *> children (basicFor <|> enhancedFor)
basicFor :: Assignment
basicFor = makeTerm <$> symbol BasicForStatement <*> children (Statement.For <$ token AnonFor <* token AnonLParen <*> (token AnonSemicolon *> emptyTerm <|> forInit <* token AnonSemicolon) <*> (token AnonSemicolon *> emptyTerm <|> term expression <* token AnonSemicolon) <*> forStep <*> term expression)
where
forInit = symbol ForInit *> children (term expression)
forStep = makeTerm <$> location <*> manyTermsTill expression (token AnonRParen)
enhancedFor :: Assignment
enhancedFor = makeTerm <$> symbol EnhancedForStatement <*> children (Statement.ForEach <$> (variable <$> manyTerm modifier <*> type' <*> variableDeclaratorId) <*> term expression <*> term expression)
where variable modifiers type' variableDeclaratorId = makeTerm1 (Java.Syntax.Variable modifiers type' variableDeclaratorId)
-- TODO: instanceOf
binary :: Assignment
binary = makeTerm' <$> symbol BinaryExpression <*> children (infixTerm expression expression
[ (inject .) . Expression.LessThan <$ symbol AnonLAngle
, (inject .) . Expression.GreaterThan <$ symbol AnonRAngle
, (inject .) . Expression.Equal <$ symbol AnonEqualEqual
, (inject .) . Expression.GreaterThanEqual <$ symbol AnonRAngleEqual
, (inject .) . Expression.LessThanEqual <$ symbol AnonLAngleEqual
, (inject .) . invert Expression.Equal <$ symbol AnonBangEqual
, (inject .) . Expression.And <$ symbol AnonAmpersandAmpersand
, (inject .) . Expression.Or <$ symbol AnonPipePipe
, (inject .) . Expression.BAnd <$ symbol AnonAmpersand
, (inject .) . Expression.BOr <$ symbol AnonPipe
, (inject .) . Expression.BXOr <$ symbol AnonCaret
, (inject .) . Expression.Modulo <$ symbol AnonPercent
, (inject .) . Expression.LShift <$ symbol AnonLAngleLAngle
, (inject .) . Expression.RShift <$ symbol AnonRAngleRAngle
, (inject .) . Expression.UnsignedRShift <$ symbol AnonRAngleRAngleRAngle
, (inject .) . Expression.Plus <$ symbol AnonPlus
, (inject .) . Expression.Minus <$ symbol AnonMinus
, (inject .) . Expression.Times <$ symbol AnonStar
, (inject .) . Expression.DividedBy <$ symbol AnonSlash
, (inject .) . Expression.InstanceOf <$ symbol AnonInstanceof
])
where invert cons a b = Expression.Not (makeTerm1 (cons a b))
-- | Match infix terms separated by any of a list of operators, assigning any comments following each operand.
infixTerm :: HasCallStack
=> Assignment
-> Assignment
-> [Assignment.Assignment [] Grammar (Term -> Term -> Sum Syntax Term)]
-> Assignment.Assignment [] Grammar (Sum Syntax Term)
infixTerm = infixContext comment
assignment' :: Assignment
assignment' = makeTerm' <$> symbol AssignmentExpression <*> children (infixTerm lhs expression
[ (inject .) . Statement.Assignment [] <$ symbol AnonEqual
, assign Expression.Plus <$ symbol AnonPlusEqual
, assign Expression.Minus <$ symbol AnonMinusEqual
, assign Expression.Times <$ symbol AnonStarEqual
, assign Expression.DividedBy <$ symbol AnonSlashEqual
, assign Expression.BOr <$ symbol AnonPipeEqual
, assign Expression.BAnd <$ symbol AnonAmpersandEqual
, assign Expression.Modulo <$ symbol AnonPercentEqual
, assign Expression.RShift <$ symbol AnonRAngleRAngleEqual
, assign Expression.UnsignedRShift <$ symbol AnonRAngleRAngleRAngleEqual
, assign Expression.LShift <$ symbol AnonLAngleLAngleEqual
, assign Expression.BXOr <$ symbol AnonCaretEqual
])
where
assign :: (f :< Syntax) => (Term -> Term -> f Term) -> Term -> Term -> Sum Syntax Term
assign c l r = inject (Statement.Assignment [] l (makeTerm1 (c l r)))
lhs = symbol Lhs *> children (term expression)
data UnaryType
= UPlus
| UMinus
| UBang
| UTilde
unary :: Assignment
unary = make <$> symbol UnaryExpression <*> children ((,) <$> operator <*> term expression)
where
make _ (UPlus, operand) = operand
make loc (UMinus, operand) = makeTerm loc (Expression.Negate operand)
make loc (UBang, operand) = makeTerm loc (Expression.Not operand)
make loc (UTilde, operand) = makeTerm loc (Expression.Complement operand)
operator = token AnonPlus $> UPlus
<|> token AnonMinus $> UMinus
<|> token AnonBang $> UBang
<|> token AnonTilde $> UTilde
update :: Assignment
update = makeTerm' <$> symbol UpdateExpression <*> children (
inject . Statement.PreIncrement <$ token AnonPlusPlus <*> term expression
<|> inject . Statement.PreDecrement <$ token AnonMinusMinus <*> term expression
<|> inject . Statement.PostIncrement <$> term expression <* token AnonPlusPlus
<|> inject . Statement.PostDecrement <$> term expression <* token AnonMinusMinus)
ternary :: Assignment
ternary = makeTerm <$> symbol TernaryExpression <*> children (Statement.If <$> term expression <*> term expression <*> term expression)
synchronized :: Assignment
synchronized = makeTerm <$> symbol SynchronizedStatement <*> children (Java.Syntax.Synchronized <$> term expression <*> term expression)
classInstance :: Assignment
classInstance = makeTerm <$> symbol ClassInstanceCreationExpression <*> children unqualified
where
unqualified = symbol UnqualifiedClassInstanceCreationExpression *> children (Java.Syntax.New <$> type' <*> (argumentList <|> pure []))
argumentList :: Assignment.Assignment [] Grammar [Term]
argumentList = symbol ArgumentList *> children (manyTerm expression)
super :: Assignment
super = makeTerm <$> token Super <*> pure Expression.Super
this :: Assignment
this = makeTerm <$> token This <*> pure Expression.This
constructorDeclaration :: Assignment
constructorDeclaration = makeTerm <$> symbol ConstructorDeclaration <*> children (
constructor <$> manyTerm modifier <*> constructorDeclarator <*> (throws <|> pure []) <*> constructorBody)
where
constructorDeclarator = symbol ConstructorDeclarator *> children ((,,) <$> (typeParameters <|> pure []) <*> term identifier <*> formalParameters)
constructorBody = makeTerm <$> symbol ConstructorBody <*> children (manyTerm expression) -- wrapping list of terms up in single node
constructor modifiers (typeParameters, identifier, formalParameters) = Java.Syntax.Constructor modifiers typeParameters identifier formalParameters -- let partial application do its thing
typeParameters :: Assignment.Assignment [] Grammar [Term]
typeParameters = symbol TypeParameters *> children (manyTerm typeParam) -- this produces a list, which is what we need to return given by the type definition
where
typeParam = makeTerm <$> symbol Grammar.TypeParameter <*> children (Java.Syntax.TypeParameter <$> manyTerm annotation <*> term identifier <*> (typeBound <|> pure [])) -- wrapping up all three of those fields so we need to makeTerm (producing a term here)
typeBound = symbol TypeBound *> children (manyTerm type')
-- manyTerm typeParam made sense because each type Parameter was wrapped up into a Grammar.TypeParameter node, dissimilar
-- to superInterfaces
annotation :: Assignment
annotation = makeTerm <$> symbol NormalAnnotation <*> children (Java.Syntax.Annotation <$> term expression <*> (elementValuePairList <|> pure []))
<|> makeTerm <$> symbol MarkerAnnotation <*> children (Java.Syntax.Annotation <$> term expression <*> pure [])
<|> makeTerm <$> symbol SingleElementAnnotation <*> children (Java.Syntax.Annotation <$> term expression <*> (pure <$> term elementValue))
where
elementValuePairList = symbol ElementValuePairList *> children (manyTerm elementValuePair)
elementValuePair = makeTerm <$> symbol ElementValuePair <*> children (Java.Syntax.AnnotationField <$> term expression <*> term elementValue)
elementValue = symbol ElementValue *> children (term expression)
throws :: Assignment.Assignment [] Grammar [Term]
throws = symbol Throws *> children (symbol ExceptionTypeList *> children(manyTerm type'))
formalParameters :: Assignment.Assignment [] Grammar [Term]
formalParameters = manyTerm parameter
where
parameter = makeTerm <$> symbol FormalParameter <*> children (makeAnnotation <$> manyTerm modifier <*> type' <* symbol VariableDeclaratorId <*> children identifier)
makeAnnotation [] type' variableName = Type.Annotation variableName type'
makeAnnotation modifiers type' variableName = Type.Annotation variableName (makeTerm1 (Java.Syntax.TypeWithModifiers modifiers type'))
-- know when we are in a functor context and fmap is all gravy
-- we're just wrapping stuff up in data, we aren't building a pattern (assignment) so we aren't in an applicative context
-- when in an applicative context, we're also in a functor context (ie., defining how fmap will work over it)
-- sometimes it is nice to be able to say you're in an applicative context without refering to any particular applicative instance
-- constantDeclaration :: Assignment
-- constantDeclaration = makeTerm <$> symbol ConstantDeclaration <*>
castExpression :: Assignment
castExpression = makeTerm <$> symbol CastExpression <*> children (flip Type.Annotation <$> type' <*> term expression)
-- term expression, because we can deal with comments

View File

@ -0,0 +1,12 @@
{-# LANGUAGE TemplateHaskell #-}
module Language.Java.Grammar where
import Language.Haskell.TH
import TreeSitter.Language
import TreeSitter.Java
-- Regenerate template haskell code when these files change:
addDependentFileRelative "../../../vendor/haskell-tree-sitter/languages/java/vendor/tree-sitter-java/src/parser.c"
-- | Statically-known rules corresponding to symbols in the grammar.
mkSymbolDatatype (mkName "Grammar") tree_sitter_java

146
src/Language/Java/Syntax.hs Normal file
View File

@ -0,0 +1,146 @@
{-# LANGUAGE DeriveAnyClass #-}
module Language.Java.Syntax where
import Data.Abstract.Evaluatable
import Diffing.Algorithm
import Prologue hiding (Constructor)
import Data.JSON.Fields
newtype Import a = Import [a]
deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, Generic1, Mergeable, Ord, Show, Traversable, Declarations1, ToJSONFields1, Hashable1)
instance Eq1 Import where liftEq = genericLiftEq
instance Ord1 Import where liftCompare = genericLiftCompare
instance Show1 Import where liftShowsPrec = genericLiftShowsPrec
-- TODO: Implement Eval instance for ArrayType
instance Evaluatable Import
data Module a = Module { moduleIdentifier :: !a, moduleStatements :: ![a] }
deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, Generic1, Mergeable, Ord, Show, Traversable, Declarations1, ToJSONFields1, Hashable1)
instance Eq1 Module where liftEq = genericLiftEq
instance Ord1 Module where liftCompare = genericLiftCompare
instance Show1 Module where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable Module
newtype Package a = Package [a]
deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, Generic1, Mergeable, Ord, Show, Traversable, Declarations1, ToJSONFields1, Hashable1)
instance Eq1 Package where liftEq = genericLiftEq
instance Ord1 Package where liftCompare = genericLiftCompare
instance Show1 Package where liftShowsPrec = genericLiftShowsPrec
-- TODO: Implement Eval instance for ArrayType
instance Evaluatable Package
data EnumDeclaration a = EnumDeclaration { _enumDeclarationIdentifier :: !a, _enumDeclarationBody :: ![a] }
deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, Generic1, Mergeable, Ord, Show, Traversable, Declarations1, ToJSONFields1, Hashable1)
instance Eq1 EnumDeclaration where liftEq = genericLiftEq
instance Ord1 EnumDeclaration where liftCompare = genericLiftCompare
instance Show1 EnumDeclaration where liftShowsPrec = genericLiftShowsPrec
instance Evaluatable EnumDeclaration
data Variable a = Variable { variableModifiers :: ![a], variableType :: !a, variableName :: !a}
deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, Generic1, Mergeable, Ord, Show, Traversable, Declarations1, ToJSONFields1, Hashable1)
instance Eq1 Variable where liftEq = genericLiftEq
instance Ord1 Variable where liftCompare = genericLiftCompare
instance Show1 Variable where liftShowsPrec = genericLiftShowsPrec
-- TODO: Implement Eval instance for Variable
instance Evaluatable Variable
data Synchronized a = Synchronized { synchronizedSubject :: !a, synchronizedBody :: !a}
deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, Generic1, Mergeable, Ord, Show, Traversable, Declarations1, ToJSONFields1, Hashable1)
instance Eq1 Synchronized where liftEq = genericLiftEq
instance Ord1 Synchronized where liftCompare = genericLiftCompare
instance Show1 Synchronized where liftShowsPrec = genericLiftShowsPrec
-- TODO: Implement Eval instance for Synchronized
instance Evaluatable Synchronized
data New a = New { newType :: !a, newArgs :: ![a] }
deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, Generic1, Mergeable, Ord, Show, Traversable, Declarations1, ToJSONFields1, Hashable1)
instance Eq1 New where liftEq = genericLiftEq
instance Ord1 New where liftCompare = genericLiftCompare
instance Show1 New where liftShowsPrec = genericLiftShowsPrec
-- TODO: Implement Eval instance for New
instance Evaluatable New
data Asterisk a = Asterisk
deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, Generic1, Mergeable, Ord, Show, Traversable, Declarations1, ToJSONFields1, Hashable1)
instance Eq1 Asterisk where liftEq = genericLiftEq
instance Ord1 Asterisk where liftCompare = genericLiftCompare
instance Show1 Asterisk where liftShowsPrec = genericLiftShowsPrec
-- TODO: Implement Eval instance for New
instance Evaluatable Asterisk
data Constructor a = Constructor { constructorModifiers :: ![a], constructorTypeParams :: ![a], constructorIdentifier :: !a, constructorParams :: ![a], constructorThrows :: ![a], constructorBody :: a}
deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, Generic1, Mergeable, Ord, Show, Traversable, Declarations1, ToJSONFields1, Hashable1)
instance Eq1 Constructor where liftEq = genericLiftEq
instance Ord1 Constructor where liftCompare = genericLiftCompare
instance Show1 Constructor where liftShowsPrec = genericLiftShowsPrec
-- TODO: Implement Eval instance for Constructor
instance Evaluatable Constructor
data TypeParameter a = TypeParameter { typeParamAnnotation :: ![a], typeParamIdentifier :: !a, typeParamTypeBound :: ![a]}
deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, Generic1, Mergeable, Ord, Show, Traversable, Declarations1, ToJSONFields1, Hashable1)
instance Eq1 TypeParameter where liftEq = genericLiftEq
instance Ord1 TypeParameter where liftCompare = genericLiftCompare
instance Show1 TypeParameter where liftShowsPrec = genericLiftShowsPrec
-- TODO: Implement Eval instance for TypeParameter
instance Evaluatable TypeParameter
data Annotation a = Annotation { annotationName :: !a, annotationField :: [a]}
deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, Generic1, Mergeable, Ord, Show, Traversable, Declarations1, ToJSONFields1, Hashable1)
instance Eq1 Annotation where liftEq = genericLiftEq
instance Ord1 Annotation where liftCompare = genericLiftCompare
instance Show1 Annotation where liftShowsPrec = genericLiftShowsPrec
-- TODO: Implement Eval instance for Annotation
instance Evaluatable Annotation
data AnnotationField a = AnnotationField { annotationFieldName :: a, annotationFieldValue :: a }
deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, Generic1, Mergeable, Ord, Show, Traversable, Declarations1, ToJSONFields1, Hashable1)
instance Eq1 AnnotationField where liftEq = genericLiftEq
instance Ord1 AnnotationField where liftCompare = genericLiftCompare
instance Show1 AnnotationField where liftShowsPrec = genericLiftShowsPrec
-- TODO: Implement Eval instance for AnnotationField
instance Evaluatable AnnotationField
data GenericType a = GenericType { genericTypeIdentifier :: a, genericTypeArguments :: [a] }
deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, Generic1, Mergeable, Ord, Show, Traversable, Declarations1, ToJSONFields1, Hashable1)
instance Eq1 GenericType where liftEq = genericLiftEq
instance Ord1 GenericType where liftCompare = genericLiftCompare
instance Show1 GenericType where liftShowsPrec = genericLiftShowsPrec
-- TODO: Implement Eval instance for GenericType
instance Evaluatable GenericType
data TypeWithModifiers a = TypeWithModifiers [a] a
deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, Generic1, Mergeable, Ord, Show, Traversable, Declarations1, ToJSONFields1, Hashable1)
instance Eq1 TypeWithModifiers where liftEq = genericLiftEq
instance Ord1 TypeWithModifiers where liftCompare = genericLiftCompare
instance Show1 TypeWithModifiers where liftShowsPrec = genericLiftShowsPrec
-- TODO: Implement Eval instance for TypeWithModifiers
instance Evaluatable TypeWithModifiers

View File

@ -250,7 +250,7 @@ functionDefinition =
makeFunctionDeclaration loc (functionName', functionParameters, ty, functionBody) = makeTerm loc $ Type.Annotation (makeTerm loc $ Declaration.Function [] functionName' functionParameters functionBody) (fromMaybe (makeTerm loc Syntax.Empty) ty)
classDefinition :: Assignment
classDefinition = makeTerm <$> symbol ClassDefinition <*> children (Declaration.Class <$> pure [] <*> term expression <*> argumentList <*> expressions)
classDefinition = makeTerm <$> symbol ClassDefinition <*> children (Declaration.Class [] <$> term expression <*> argumentList <*> expressions)
where argumentList = symbol ArgumentList *> children (manyTerm expression)
<|> pure []

View File

@ -396,7 +396,7 @@ assignment' = makeTerm <$> symbol Assignment <*> children (Statement.As
, assign Expression.Times <$ symbol AnonStarEqual
, assign Expression.Power <$ symbol AnonStarStarEqual
, assign Expression.DividedBy <$ symbol AnonSlashEqual
, assign Expression.And <$ symbol AnonPipePipeEqual
, assign Expression.Or <$ symbol AnonPipePipeEqual
, assign Expression.BOr <$ symbol AnonPipeEqual
, assign Expression.And <$ symbol AnonAmpersandAmpersandEqual
, assign Expression.BAnd <$ symbol AnonAmpersandEqual

View File

@ -12,6 +12,7 @@ module Parsing.Parser
, ApplyAll'
-- À la carte parsers
, goParser
, javaParser
, jsonParser
, markdownParser
, pythonParser
@ -35,6 +36,7 @@ import Foreign.Ptr
import qualified GHC.TypeLits as TypeLevel
import qualified Language.Go.Assignment as Go
import qualified Language.Haskell.Assignment as Haskell
import qualified Language.Java.Assignment as Java
import qualified Language.JSON.Assignment as JSON
import qualified Language.Markdown.Assignment as Markdown
import qualified Language.PHP.Assignment as PHP
@ -46,6 +48,7 @@ import Prologue
import TreeSitter.Go
import TreeSitter.JSON
import qualified TreeSitter.Language as TS (Language, Symbol)
import TreeSitter.Java
import TreeSitter.PHP
import TreeSitter.Python
import TreeSitter.Ruby
@ -67,6 +70,7 @@ data SomeAnalysisParser typeclasses ann where
-- | A parser for some specific language, producing 'Term's whose syntax satisfies a list of typeclass constraints.
someAnalysisParser :: ( ApplyAll' typeclasses Go.Syntax
, ApplyAll' typeclasses Java.Syntax
, ApplyAll' typeclasses PHP.Syntax
, ApplyAll' typeclasses Python.Syntax
, ApplyAll' typeclasses Ruby.Syntax
@ -77,6 +81,7 @@ someAnalysisParser :: ( ApplyAll' typeclasses Go.Syntax
-> Language -- ^ The 'Language' to select.
-> SomeAnalysisParser typeclasses (Record Location) -- ^ A 'SomeAnalysisParser abstracting the syntax type to be produced.
someAnalysisParser _ Go = SomeAnalysisParser goParser Nothing
someAnalysisParser _ Java = SomeAnalysisParser javaParser Nothing
someAnalysisParser _ JavaScript = SomeAnalysisParser typescriptParser $ Just (File (TypeLevel.symbolVal (Proxy :: Proxy (PreludePath TypeScript.Term))) (Just JavaScript))
someAnalysisParser _ Haskell = SomeAnalysisParser haskellParser Nothing
someAnalysisParser _ PHP = SomeAnalysisParser phpParser Nothing
@ -112,6 +117,7 @@ type family ApplyAll (typeclasses :: [(* -> *) -> Constraint]) (syntax :: * -> *
-- > runTask (parse (someParser @'[Show1] language) blob) >>= putStrLn . withSomeTerm show
someParser :: ( ApplyAll typeclasses (Sum Go.Syntax)
, ApplyAll typeclasses (Sum Haskell.Syntax)
, ApplyAll typeclasses (Sum Java.Syntax)
, ApplyAll typeclasses (Sum JSON.Syntax)
, ApplyAll typeclasses (Sum Markdown.Syntax)
, ApplyAll typeclasses (Sum Python.Syntax)
@ -122,6 +128,7 @@ someParser :: ( ApplyAll typeclasses (Sum Go.Syntax)
=> Language   -- ^ The 'Language' to select.
-> Parser (SomeTerm typeclasses (Record Location)) -- ^ A 'SomeParser' abstracting the syntax type to be produced.
someParser Go = SomeParser goParser
someParser Java = SomeParser javaParser
someParser JavaScript = SomeParser typescriptParser
someParser JSON = SomeParser jsonParser
someParser Haskell = SomeParser haskellParser
@ -145,6 +152,9 @@ phpParser = AssignmentParser (ASTParser tree_sitter_php) PHP.assignment
pythonParser :: Parser Python.Term
pythonParser = AssignmentParser (ASTParser tree_sitter_python) Python.assignment
javaParser :: Parser Java.Term
javaParser = AssignmentParser (ASTParser tree_sitter_java) Java.assignment
jsonParser :: Parser JSON.Term
jsonParser = AssignmentParser (ASTParser tree_sitter_json) JSON.assignment

19
test/fixtures/java/binary.java vendored Normal file
View File

@ -0,0 +1,19 @@
a > b;
a < b;
a == b;
a >= b;
a <= b;
a != b;
a && b;
a || b;
a & b;
a | b;
a ^ b;
a % b;
a << b;
a >> b;
a >>> b;
3 + 2;
3 - 2;
3 * 2;
9 / 3;

5
test/fixtures/java/boolean.java vendored Normal file
View File

@ -0,0 +1,5 @@
public class Point {
void dinosaur() {
Boolean x = true;
}
}

5
test/fixtures/java/char.java vendored Normal file
View File

@ -0,0 +1,5 @@
public class Point {
void dinosaur() {
Char a = 'a';
}
}

5
test/fixtures/java/comment.java vendored Normal file
View File

@ -0,0 +1,5 @@
// This is a single-line comment.
/* This is
a multi-line
comment */

14
test/fixtures/java/continue.java vendored Normal file
View 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");
}
}
}

4
test/fixtures/java/dims.java vendored Normal file
View File

@ -0,0 +1,4 @@
class ForDemo {
void main(String[] args){
}
}

9
test/fixtures/java/do-while.java vendored Normal file
View File

@ -0,0 +1,9 @@
class WhileDemo {
public static void main(String[] args){
do {
System.out.print("Guess my name: ");
guess = scanner.nextLine();
}
while (!"Daffy Duck".equals(guess));
}
}

3
test/fixtures/java/enum.java vendored Normal file
View File

@ -0,0 +1,3 @@
enum HandSign {
SCISSOR, PAPER, STONE
}

5
test/fixtures/java/float.java vendored Normal file
View File

@ -0,0 +1,5 @@
public class Point {
void dinosaur() {
Float x = 10.0;
}
}

7
test/fixtures/java/for.java vendored Normal file
View File

@ -0,0 +1,7 @@
class ForDemo {
public static void main(String[] args){
for(int i=1; i<11; i++){
System.out.println("Count is: " + i);
}
}
}

2
test/fixtures/java/if.java vendored Normal file
View File

@ -0,0 +1,2 @@
if (x)
y;

1
test/fixtures/java/import.java vendored Normal file
View File

@ -0,0 +1 @@
import javax.swing.JOptionPane;

5
test/fixtures/java/int.java vendored Normal file
View File

@ -0,0 +1,5 @@
public class Point {
void dinosaur() {
Int x = 1;
}
}

2
test/fixtures/java/interface.java vendored Normal file
View File

@ -0,0 +1,2 @@
interface Top {
}

View File

@ -0,0 +1,3 @@
abstract class Point {
}

View File

@ -0,0 +1 @@

View File

@ -0,0 +1,3 @@
protected class Point {
}

View File

@ -0,0 +1,3 @@
public class Point {
}

View File

@ -0,0 +1,3 @@
public static class Point {
}

5
test/fixtures/java/null.java vendored Normal file
View File

@ -0,0 +1,5 @@
public class Point {
void dinosaur() {
String str = null;
}
}

1
test/fixtures/java/package.java vendored Normal file
View File

@ -0,0 +1 @@
package myVector;

5
test/fixtures/java/return.java vendored Normal file
View File

@ -0,0 +1,5 @@
public class Point {
void dinosaur() {
return x;
}
}

5
test/fixtures/java/string.java vendored Normal file
View File

@ -0,0 +1,5 @@
public class Point {
void dinosaur() {
String str = "yo wassup";
}
}

29
test/fixtures/java/switch.java vendored Normal file
View File

@ -0,0 +1,29 @@
public class Test
{
public static void main(String[] args)
{
int day = 5;
String dayString;
switch (day)
{
case 1: dayString = "Monday";
break;
case 2: dayString = "Tuesday";
break;
case 3: dayString = "Wednesday";
break;
case 4: dayString = "Thursday";
break;
case 5: dayString = "Friday";
break;
case 6: dayString = "Saturday";
break;
case 7: dayString = "Sunday";
break;
default: dayString = "Invalid day";
break;
}
System.out.println(dayString);
}
}

5
test/fixtures/java/throws.java vendored Normal file
View File

@ -0,0 +1,5 @@
class Beyonce {
BufferedReader newReader() throws FileNotFoundException {
new BufferedReader(new InputStreamReader(new FileInputStream(file), charset));
}
}

19
test/fixtures/java/try-catches.java vendored Normal file
View File

@ -0,0 +1,19 @@
class Example2{
public static void main(String args[]){
try{
int a[]=new int[7];
a[4]=30/0;
System.out.println("First print statement in try block");
}
catch(ArithmeticException e){
System.out.println("Warning: ArithmeticException");
}
catch(ArrayIndexOutOfBoundsException e){
System.out.println("Warning: ArrayIndexOutOfBoundsException");
}
catch(Exception e){
System.out.println("Warning: Some Other exception");
}
System.out.println("Out of try-catch block...");
}
}

4
test/fixtures/java/update.java vendored Normal file
View File

@ -0,0 +1,4 @@
foo++;
++bar;
baz--;
--boo;

View File

@ -0,0 +1 @@
int x = 3;

9
test/fixtures/java/while.java vendored Normal file
View File

@ -0,0 +1,9 @@
class WhileDemo {
public static void main(String[] args){
int count = 1;
while (count < 11) {
System.out.println("Count is: " + count);
count++;
}
}
}

View File

@ -1,7 +1,9 @@
(Program
(Assignment
(Identifier)
(And
(Identifier)
{ (Integer)
->(Integer) })))
{ (Or
{-(Identifier)-}
{-(Integer)-})
->(And
{+(Identifier)+}
{+(Integer)+}) }))

View File

@ -1,7 +1,9 @@
(Program
(Assignment
(Identifier)
(And
(Identifier)
{ (Integer)
->(Integer) })))
{ (And
{-(Identifier)-}
{-(Integer)-})
->(Or
{+(Identifier)+}
{+(Integer)+}) }))

View File

@ -1,6 +1,6 @@
(Program
(Assignment
(Identifier)
(And
(Or
(Identifier)
(Integer))))

@ -1 +1 @@
Subproject commit e5b4ad8f70454ba67edce974eb3b065ee9f51cb5
Subproject commit 2df318536681fcb4a3a6fb11b4bc03709bf80343