|
|
@ -14,7 +14,7 @@ import Data.Record
|
|
|
|
import Data.Syntax (contextualize, emptyTerm, handleError, infixContext, makeTerm, makeTerm', makeTerm'', makeTerm1, parseError, postContextualize)
|
|
|
|
import Data.Syntax (contextualize, emptyTerm, handleError, infixContext, makeTerm, makeTerm', makeTerm'', makeTerm1, parseError, postContextualize)
|
|
|
|
import Data.Sum
|
|
|
|
import Data.Sum
|
|
|
|
import Language.Java.Grammar as Grammar
|
|
|
|
import Language.Java.Grammar as Grammar
|
|
|
|
import Language.Java.Syntax as Java.Syntax
|
|
|
|
import qualified Language.Java.Syntax as Java.Syntax
|
|
|
|
import qualified Assigning.Assignment as Assignment
|
|
|
|
import qualified Assigning.Assignment as Assignment
|
|
|
|
import qualified Data.Syntax as Syntax
|
|
|
|
import qualified Data.Syntax as Syntax
|
|
|
|
import qualified Data.Syntax.Comment as Comment
|
|
|
|
import qualified Data.Syntax.Comment as Comment
|
|
|
@ -25,7 +25,7 @@ import qualified Data.Syntax.Statement as Statement
|
|
|
|
import qualified Data.Syntax.Type as Type
|
|
|
|
import qualified Data.Syntax.Type as Type
|
|
|
|
import qualified Data.Term as Term
|
|
|
|
import qualified Data.Term as Term
|
|
|
|
import Prelude hiding (break)
|
|
|
|
import Prelude hiding (break)
|
|
|
|
import Prologue hiding (for, try, This)
|
|
|
|
import Prologue hiding (for, try, This, catches, finally)
|
|
|
|
|
|
|
|
|
|
|
|
type Syntax =
|
|
|
|
type Syntax =
|
|
|
|
'[ Comment.Comment
|
|
|
|
'[ Comment.Comment
|
|
|
@ -66,18 +66,33 @@ type Syntax =
|
|
|
|
, Expression.Member
|
|
|
|
, Expression.Member
|
|
|
|
, Expression.Super
|
|
|
|
, Expression.Super
|
|
|
|
, Expression.This
|
|
|
|
, Expression.This
|
|
|
|
|
|
|
|
, Java.Syntax.AnnotatedType
|
|
|
|
, Java.Syntax.Annotation
|
|
|
|
, Java.Syntax.Annotation
|
|
|
|
, Java.Syntax.AnnotationField
|
|
|
|
, Java.Syntax.AnnotationField
|
|
|
|
|
|
|
|
, Java.Syntax.AnnotationTypeElement
|
|
|
|
|
|
|
|
, Java.Syntax.ArrayCreationExpression
|
|
|
|
|
|
|
|
, Java.Syntax.AssertStatement
|
|
|
|
, Java.Syntax.Asterisk
|
|
|
|
, Java.Syntax.Asterisk
|
|
|
|
|
|
|
|
, Java.Syntax.CatchType
|
|
|
|
, Java.Syntax.Constructor
|
|
|
|
, Java.Syntax.Constructor
|
|
|
|
|
|
|
|
, Java.Syntax.ClassBody
|
|
|
|
|
|
|
|
, Java.Syntax.ClassLiteral
|
|
|
|
|
|
|
|
, Java.Syntax.DefaultValue
|
|
|
|
|
|
|
|
, Java.Syntax.DimsExpr
|
|
|
|
, Java.Syntax.EnumDeclaration
|
|
|
|
, Java.Syntax.EnumDeclaration
|
|
|
|
, Java.Syntax.GenericType
|
|
|
|
, Java.Syntax.GenericType
|
|
|
|
, Java.Syntax.Import
|
|
|
|
, Java.Syntax.Import
|
|
|
|
|
|
|
|
, Java.Syntax.Lambda
|
|
|
|
|
|
|
|
, Java.Syntax.LambdaBody
|
|
|
|
|
|
|
|
, Java.Syntax.MethodReference
|
|
|
|
, Java.Syntax.Module
|
|
|
|
, Java.Syntax.Module
|
|
|
|
, Java.Syntax.New
|
|
|
|
, Java.Syntax.New
|
|
|
|
|
|
|
|
, Java.Syntax.NewKeyword
|
|
|
|
, Java.Syntax.Package
|
|
|
|
, Java.Syntax.Package
|
|
|
|
, Java.Syntax.SpreadParameter
|
|
|
|
, Java.Syntax.SpreadParameter
|
|
|
|
|
|
|
|
, Java.Syntax.StaticInitializer
|
|
|
|
, Java.Syntax.Synchronized
|
|
|
|
, Java.Syntax.Synchronized
|
|
|
|
|
|
|
|
, Java.Syntax.TryWithResources
|
|
|
|
, Java.Syntax.TypeParameter
|
|
|
|
, Java.Syntax.TypeParameter
|
|
|
|
, Java.Syntax.TypeWithModifiers
|
|
|
|
, Java.Syntax.TypeWithModifiers
|
|
|
|
, Java.Syntax.Variable
|
|
|
|
, Java.Syntax.Variable
|
|
|
@ -125,41 +140,43 @@ type Syntax =
|
|
|
|
]
|
|
|
|
]
|
|
|
|
|
|
|
|
|
|
|
|
type Term = Term.Term (Sum Syntax) (Record Location)
|
|
|
|
type Term = Term.Term (Sum Syntax) (Record Location)
|
|
|
|
type Assignment = Assignment.Assignment [] Grammar Term
|
|
|
|
type Assignment = Assignment.Assignment [] Grammar
|
|
|
|
|
|
|
|
|
|
|
|
-- | Assignment from AST in Java's grammar onto a program in Java's syntax.
|
|
|
|
-- | Assignment from AST in Java's grammar onto a program in Java's syntax.
|
|
|
|
assignment :: Assignment
|
|
|
|
assignment :: Assignment Term
|
|
|
|
assignment = handleError $ makeTerm <$> symbol Grammar.Program <*> children (Statement.Statements <$> manyTerm expression) <|> parseError
|
|
|
|
assignment = handleError $ makeTerm <$> symbol Grammar.Program <*> children (Statement.Statements <$> manyTerm expression) <|> parseError
|
|
|
|
|
|
|
|
|
|
|
|
-- | Match a term optionally preceded by comment(s), or a sequence of comments if the term is not present.
|
|
|
|
-- | 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 :: Assignment Term -> Assignment [Term]
|
|
|
|
manyTerm term = many (contextualize comment term <|> makeTerm1 <$> (Syntax.Context <$> some1 comment <*> emptyTerm))
|
|
|
|
manyTerm term = many (contextualize comment term <|> makeTerm1 <$> (Syntax.Context <$> some1 comment <*> emptyTerm))
|
|
|
|
|
|
|
|
|
|
|
|
-- | Match a series of terms or comments until a delimiter is matched.
|
|
|
|
-- | Match a series of terms or comments until a delimiter is matched.
|
|
|
|
manyTermsTill :: Assignment.Assignment [] Grammar Term
|
|
|
|
manyTermsTill :: Assignment Term
|
|
|
|
-> Assignment.Assignment [] Grammar b
|
|
|
|
-> Assignment b
|
|
|
|
-> Assignment.Assignment [] Grammar [Term]
|
|
|
|
-> Assignment [Term]
|
|
|
|
manyTermsTill step = manyTill (step <|> comment)
|
|
|
|
manyTermsTill step = manyTill (step <|> comment)
|
|
|
|
|
|
|
|
|
|
|
|
someTerm :: Assignment -> Assignment.Assignment [] Grammar [Term]
|
|
|
|
someTerm :: Assignment Term -> Assignment [Term]
|
|
|
|
someTerm term = some (contextualize comment term <|> makeTerm1 <$> (Syntax.Context <$> some1 comment <*> emptyTerm))
|
|
|
|
someTerm term = some (contextualize comment term <|> makeTerm1 <$> (Syntax.Context <$> some1 comment <*> emptyTerm))
|
|
|
|
|
|
|
|
|
|
|
|
-- | Match comments before and after the node.
|
|
|
|
-- | Match comments before and after the node.
|
|
|
|
term :: Assignment -> Assignment
|
|
|
|
term :: Assignment Term -> Assignment Term
|
|
|
|
term term = contextualize comment (postContextualize comment term)
|
|
|
|
term term = contextualize comment (postContextualize comment term)
|
|
|
|
|
|
|
|
|
|
|
|
-- | Match
|
|
|
|
-- | Match
|
|
|
|
expression :: Assignment
|
|
|
|
expression :: Assignment Term
|
|
|
|
expression = handleError (choice expressionChoices)
|
|
|
|
expression = handleError (choice expressionChoices)
|
|
|
|
|
|
|
|
|
|
|
|
expressions :: Assignment
|
|
|
|
expressions :: Assignment Term
|
|
|
|
expressions = makeTerm'' <$> location <*> many expression
|
|
|
|
expressions = makeTerm'' <$> location <*> many expression
|
|
|
|
|
|
|
|
|
|
|
|
expressionChoices :: [Assignment.Assignment [] Grammar Term]
|
|
|
|
expressionChoices :: [Assignment Term]
|
|
|
|
expressionChoices =
|
|
|
|
expressionChoices =
|
|
|
|
[
|
|
|
|
[
|
|
|
|
arrayInitializer
|
|
|
|
arrayAccess
|
|
|
|
, arrayAccess
|
|
|
|
, arrayCreationExpression
|
|
|
|
|
|
|
|
, arrayInitializer
|
|
|
|
|
|
|
|
, assert
|
|
|
|
, assignment'
|
|
|
|
, assignment'
|
|
|
|
, block
|
|
|
|
, block
|
|
|
|
, binary
|
|
|
|
, binary
|
|
|
@ -168,11 +185,13 @@ expressionChoices =
|
|
|
|
, castExpression
|
|
|
|
, castExpression
|
|
|
|
, char
|
|
|
|
, char
|
|
|
|
, class'
|
|
|
|
, class'
|
|
|
|
|
|
|
|
, classBody
|
|
|
|
, classInstance
|
|
|
|
, classInstance
|
|
|
|
|
|
|
|
, classLiteral
|
|
|
|
, continue
|
|
|
|
, continue
|
|
|
|
, constructorDeclaration
|
|
|
|
, constructorDeclaration
|
|
|
|
|
|
|
|
, dimsExpr
|
|
|
|
, explicitConstructorInvocation
|
|
|
|
, explicitConstructorInvocation
|
|
|
|
-- , TODO: constantDeclaration
|
|
|
|
|
|
|
|
, doWhile
|
|
|
|
, doWhile
|
|
|
|
, fieldAccess
|
|
|
|
, fieldAccess
|
|
|
|
, fieldDeclaration
|
|
|
|
, fieldDeclaration
|
|
|
@ -184,8 +203,10 @@ expressionChoices =
|
|
|
|
, identifier
|
|
|
|
, identifier
|
|
|
|
, import'
|
|
|
|
, import'
|
|
|
|
, integer
|
|
|
|
, integer
|
|
|
|
|
|
|
|
, lambda
|
|
|
|
, method
|
|
|
|
, method
|
|
|
|
, methodInvocation
|
|
|
|
, methodInvocation
|
|
|
|
|
|
|
|
, methodReference
|
|
|
|
, module'
|
|
|
|
, module'
|
|
|
|
, null'
|
|
|
|
, null'
|
|
|
|
, package
|
|
|
|
, package
|
|
|
@ -194,6 +215,7 @@ expressionChoices =
|
|
|
|
, string
|
|
|
|
, string
|
|
|
|
, super
|
|
|
|
, super
|
|
|
|
, switch
|
|
|
|
, switch
|
|
|
|
|
|
|
|
, staticInitializer
|
|
|
|
, synchronized
|
|
|
|
, synchronized
|
|
|
|
, ternary
|
|
|
|
, ternary
|
|
|
|
, this
|
|
|
|
, this
|
|
|
@ -206,22 +228,22 @@ expressionChoices =
|
|
|
|
, while
|
|
|
|
, while
|
|
|
|
]
|
|
|
|
]
|
|
|
|
|
|
|
|
|
|
|
|
modifier :: Assignment
|
|
|
|
modifier :: Assignment Term
|
|
|
|
modifier = make <$> symbol Modifier <*> children(Left <$> annotation <|> Right . Syntax.AccessibilityModifier <$> source)
|
|
|
|
modifier = make <$> symbol Modifier <*> children(Left <$> annotation <|> Right . Syntax.AccessibilityModifier <$> source)
|
|
|
|
where
|
|
|
|
where
|
|
|
|
make loc (Right modifier) = makeTerm loc modifier
|
|
|
|
make loc (Right modifier) = makeTerm loc modifier
|
|
|
|
make _ (Left annotation) = annotation
|
|
|
|
make _ (Left annotation) = annotation
|
|
|
|
|
|
|
|
|
|
|
|
arrayInitializer :: Assignment
|
|
|
|
arrayInitializer :: Assignment Term
|
|
|
|
arrayInitializer = makeTerm <$> symbol ArrayInitializer <*> (Literal.Array <$> many expression)
|
|
|
|
arrayInitializer = makeTerm <$> symbol ArrayInitializer <*> (Literal.Array <$> many expression)
|
|
|
|
|
|
|
|
|
|
|
|
comment :: Assignment
|
|
|
|
comment :: Assignment Term
|
|
|
|
comment = makeTerm <$> symbol Comment <*> (Comment.Comment <$> source)
|
|
|
|
comment = makeTerm <$> symbol Comment <*> (Comment.Comment <$> source)
|
|
|
|
|
|
|
|
|
|
|
|
localVariableDeclaration :: Assignment
|
|
|
|
localVariableDeclaration :: Assignment Term
|
|
|
|
localVariableDeclaration = makeTerm <$> symbol LocalVariableDeclaration <*> children ((,) <$> manyTerm modifier <*> type' <**> variableDeclaratorList)
|
|
|
|
localVariableDeclaration = makeTerm <$> symbol LocalVariableDeclaration <*> children ((,) <$> manyTerm modifier <*> type' <**> variableDeclaratorList)
|
|
|
|
|
|
|
|
|
|
|
|
variableDeclaratorList :: Assignment.Assignment [] Grammar (([Term], Term) -> [Term])
|
|
|
|
variableDeclaratorList :: Assignment (([Term], Term) -> [Term])
|
|
|
|
variableDeclaratorList = symbol VariableDeclaratorList *> children (makeDecl <$> some variableDeclarator)
|
|
|
|
variableDeclaratorList = symbol VariableDeclaratorList *> children (makeDecl <$> some variableDeclarator)
|
|
|
|
where
|
|
|
|
where
|
|
|
|
variableDeclarator = symbol VariableDeclarator *> children ((,) <$> variableDeclaratorId <*> optional expression)
|
|
|
|
variableDeclarator = symbol VariableDeclarator *> children ((,) <$> variableDeclaratorId <*> optional expression)
|
|
|
@ -229,200 +251,243 @@ variableDeclaratorList = symbol VariableDeclaratorList *> children (makeDecl <$>
|
|
|
|
makeSingleDecl modifiers type' (target, Nothing) = makeTerm1 (Java.Syntax.Variable modifiers type' target)
|
|
|
|
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)
|
|
|
|
makeSingleDecl modifiers type' (target, Just value) = makeTerm1 (Statement.Assignment [] (makeTerm1 (Java.Syntax.Variable modifiers type' target)) value)
|
|
|
|
|
|
|
|
|
|
|
|
localVariableDeclarationStatement :: Assignment
|
|
|
|
arrayCreationExpression :: Assignment Term
|
|
|
|
|
|
|
|
arrayCreationExpression = makeTerm <$> symbol Grammar.ArrayCreationExpression <*> children (Java.Syntax.ArrayCreationExpression <$> (new *> type') <*> many dimsExpr)
|
|
|
|
|
|
|
|
where new = token AnonNew $> Java.Syntax.NewKeyword
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
localVariableDeclarationStatement :: Assignment Term
|
|
|
|
localVariableDeclarationStatement = symbol LocalVariableDeclarationStatement *> children localVariableDeclaration
|
|
|
|
localVariableDeclarationStatement = symbol LocalVariableDeclarationStatement *> children localVariableDeclaration
|
|
|
|
|
|
|
|
|
|
|
|
variableDeclaratorId :: Assignment
|
|
|
|
variableDeclaratorId :: Assignment Term
|
|
|
|
variableDeclaratorId = symbol VariableDeclaratorId *> children identifier
|
|
|
|
variableDeclaratorId = symbol VariableDeclaratorId *> children identifier
|
|
|
|
|
|
|
|
|
|
|
|
-- Literals
|
|
|
|
-- Literals
|
|
|
|
boolean :: Assignment
|
|
|
|
boolean :: Assignment Term
|
|
|
|
boolean = toTerm (branchNode BooleanLiteral
|
|
|
|
boolean = makeTerm <$> symbol BooleanLiteral <*> children
|
|
|
|
( leafNode Grammar.True $> Literal.true
|
|
|
|
(token Grammar.True $> Literal.true
|
|
|
|
<|> leafNode Grammar.False $> Literal.false))
|
|
|
|
<|> token Grammar.False $> Literal.false)
|
|
|
|
|
|
|
|
|
|
|
|
null' :: Assignment
|
|
|
|
null' :: Assignment Term
|
|
|
|
null' = makeTerm <$> symbol NullLiteral <*> (Literal.Null <$ source)
|
|
|
|
null' = makeTerm <$> symbol NullLiteral <*> (Literal.Null <$ source)
|
|
|
|
|
|
|
|
|
|
|
|
-- Integer supports all integer and floating point literals (hex, octal, binary)
|
|
|
|
-- Integer supports all integer and floating point literals (hex, octal, binary)
|
|
|
|
integer :: Assignment
|
|
|
|
integer :: Assignment Term
|
|
|
|
integer = makeTerm <$> symbol IntegerLiteral <*> children (Literal.Integer <$> source)
|
|
|
|
integer = makeTerm <$> symbol IntegerLiteral <*> children (Literal.Integer <$> source)
|
|
|
|
|
|
|
|
|
|
|
|
float :: Assignment
|
|
|
|
float :: Assignment Term
|
|
|
|
float = makeTerm <$> symbol FloatingPointLiteral <*> children (Literal.Float <$> source)
|
|
|
|
float = makeTerm <$> symbol FloatingPointLiteral <*> children (Literal.Float <$> source)
|
|
|
|
|
|
|
|
|
|
|
|
string :: Assignment
|
|
|
|
string :: Assignment Term
|
|
|
|
string = makeTerm <$> symbol StringLiteral <*> (Literal.TextElement <$> source)
|
|
|
|
string = makeTerm <$> symbol StringLiteral <*> (Literal.TextElement <$> source)
|
|
|
|
|
|
|
|
|
|
|
|
char :: Assignment
|
|
|
|
char :: Assignment Term
|
|
|
|
char = makeTerm <$> symbol CharacterLiteral <*> (Literal.TextElement <$> source)
|
|
|
|
char = makeTerm <$> symbol CharacterLiteral <*> (Literal.TextElement <$> source)
|
|
|
|
|
|
|
|
|
|
|
|
-- Identifiers
|
|
|
|
-- Identifiers
|
|
|
|
identifier :: Assignment
|
|
|
|
identifier :: Assignment Term
|
|
|
|
identifier = makeTerm <$> (symbol Identifier <|> symbol TypeIdentifier) <*> (Syntax.Identifier . name <$> source)
|
|
|
|
identifier = makeTerm <$> symbol Identifier <*> (Syntax.Identifier . name <$> source)
|
|
|
|
|
|
|
|
|
|
|
|
identifier' :: Assignment.Assignment [] Grammar Name
|
|
|
|
typeIdentifier :: Assignment Term
|
|
|
|
identifier' = (symbol Identifier <|> symbol TypeIdentifier) *> (name <$> source)
|
|
|
|
typeIdentifier = makeTerm <$> symbol TypeIdentifier <*> (Syntax.Identifier . name <$> source)
|
|
|
|
|
|
|
|
|
|
|
|
scopedIdentifier :: Assignment
|
|
|
|
identifier' :: Assignment Name
|
|
|
|
|
|
|
|
identifier' = (symbol Identifier <|> symbol TypeIdentifier <|> symbol Identifier') *> (name <$> source)
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
scopedIdentifier :: Assignment Term
|
|
|
|
scopedIdentifier = makeTerm <$> symbol ScopedIdentifier <*> children (Expression.MemberAccess <$> term expression <*> identifier')
|
|
|
|
scopedIdentifier = makeTerm <$> symbol ScopedIdentifier <*> children (Expression.MemberAccess <$> term expression <*> identifier')
|
|
|
|
|
|
|
|
|
|
|
|
superInterfaces :: Assignment.Assignment [] Grammar [Term]
|
|
|
|
superInterfaces :: Assignment [Term]
|
|
|
|
superInterfaces = symbol SuperInterfaces *> children (symbol InterfaceTypeList *> children(manyTerm type'))
|
|
|
|
superInterfaces = symbol SuperInterfaces *> children (symbol InterfaceTypeList *> children(manyTerm type'))
|
|
|
|
|
|
|
|
|
|
|
|
-- Declarations
|
|
|
|
-- Declarations
|
|
|
|
class' :: Assignment
|
|
|
|
class' :: Assignment Term
|
|
|
|
class' = makeTerm <$> symbol ClassDeclaration <*> children (makeClass <$> many modifier <*> term identifier <*> (typeParameters <|> pure []) <*> optional superClass <*> (superInterfaces <|> pure []) <*> classBody)
|
|
|
|
class' = makeTerm <$> symbol ClassDeclaration <*> children (makeClass <$> many modifier <*> term identifier <*> (typeParameters <|> pure []) <*> optional superClass <*> (superInterfaces <|> pure []) <*> classBody)
|
|
|
|
where
|
|
|
|
where
|
|
|
|
makeClass modifiers identifier typeParams superClass superInterfaces = Declaration.Class (modifiers <> typeParams) identifier (maybeToList superClass <> superInterfaces) -- not doing an assignment, just straight up function
|
|
|
|
makeClass modifiers identifier typeParams superClass superInterfaces = Declaration.Class (modifiers <> typeParams) identifier (maybeToList superClass <> superInterfaces)
|
|
|
|
classBody = makeTerm <$> symbol ClassBody <*> children (manyTerm expression)
|
|
|
|
|
|
|
|
superClass = symbol Superclass *> children type'
|
|
|
|
superClass = symbol Superclass *> children type'
|
|
|
|
-- 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
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
fieldDeclaration :: Assignment
|
|
|
|
classBody :: Assignment Term
|
|
|
|
|
|
|
|
classBody = makeTerm <$> symbol Grammar.ClassBody <*> children (manyTerm expression)
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
staticInitializer :: Assignment Term
|
|
|
|
|
|
|
|
staticInitializer = makeTerm <$> symbol Grammar.StaticInitializer <*> children (Java.Syntax.StaticInitializer <$> block)
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
fieldDeclaration :: Assignment Term
|
|
|
|
fieldDeclaration = makeTerm <$> symbol FieldDeclaration <*> children ((,) <$> manyTerm modifier <*> type' <**> variableDeclaratorList)
|
|
|
|
fieldDeclaration = makeTerm <$> symbol FieldDeclaration <*> children ((,) <$> manyTerm modifier <*> type' <**> variableDeclaratorList)
|
|
|
|
|
|
|
|
|
|
|
|
method :: Assignment
|
|
|
|
method :: Assignment Term
|
|
|
|
method = makeTerm <$> symbol MethodDeclaration <*> children (makeMethod <$> many modifier <*> emptyTerm <*> methodHeader <*> methodBody)
|
|
|
|
method = makeTerm <$> symbol MethodDeclaration <*> children (makeMethod <$> many modifier <*> emptyTerm <*> methodHeader <*> methodBody)
|
|
|
|
where
|
|
|
|
where
|
|
|
|
methodBody = symbol MethodBody *> children (term expression <|> emptyTerm)
|
|
|
|
methodBody = symbol MethodBody *> children (term expression <|> emptyTerm)
|
|
|
|
methodDeclarator = symbol MethodDeclarator *> children ( (,) <$> identifier <*> formalParameters)
|
|
|
|
methodDeclarator = symbol MethodDeclarator *> children ( (,) <$> identifier <*> formalParameters)
|
|
|
|
methodHeader = symbol MethodHeader *> children ((,,,,) <$> (typeParameters <|> pure []) <*> manyTerm annotation <*> type' <*> methodDeclarator <*> (throws <|> pure []))
|
|
|
|
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
|
|
|
|
makeMethod modifiers receiver (typeParams, annotations, returnType, (name, params), throws) = Declaration.Method (returnType : modifiers <> typeParams <> annotations <> throws) receiver name params
|
|
|
|
-- methodHeader needs to include typeParameters (it does)
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
generic :: Assignment
|
|
|
|
generic :: Assignment Term
|
|
|
|
generic = makeTerm <$> symbol Grammar.GenericType <*> children(Java.Syntax.GenericType <$> term type' <*> manyTerm type')
|
|
|
|
generic = makeTerm <$> symbol Grammar.GenericType <*> children(Java.Syntax.GenericType <$> term type' <*> manyTerm type')
|
|
|
|
|
|
|
|
|
|
|
|
methodInvocation :: Assignment
|
|
|
|
methodInvocation :: Assignment Term
|
|
|
|
methodInvocation = makeTerm <$> symbol MethodInvocation <*> children (uncurry Expression.Call <$> (callFunction <$> expression <*> optional ((,) <$ token AnonDot <*> manyTerm typeArgument <*> identifier')) <*> (argumentList <|> pure []) <*> emptyTerm)
|
|
|
|
methodInvocation = makeTerm <$> symbol MethodInvocation <*> children (uncurry Expression.Call <$> (callFunction <$> expression <*> optional ((,) <$ optional (token AnonRParen) <* token AnonDot <*> manyTerm typeArgument <*> identifier')) <*> (argumentList <|> pure []) <*> emptyTerm)
|
|
|
|
where
|
|
|
|
where
|
|
|
|
callFunction a (Just (typeArguments, b)) = (typeArguments, makeTerm1 (Expression.MemberAccess a b))
|
|
|
|
callFunction a (Just (typeArguments, b)) = (typeArguments, makeTerm1 (Expression.MemberAccess a b))
|
|
|
|
callFunction a Nothing = ([], a)
|
|
|
|
callFunction a Nothing = ([], a)
|
|
|
|
|
|
|
|
|
|
|
|
explicitConstructorInvocation :: Assignment
|
|
|
|
methodReference :: Assignment Term
|
|
|
|
explicitConstructorInvocation = makeTerm <$> symbol ExplicitConstructorInvocation <*> children (uncurry Expression.Call <$> (callFunction <$> term expression <*> optional ((,) <$ token AnonDot <*> manyTerm type' <*> identifier')) <*> argumentList <*> emptyTerm)
|
|
|
|
methodReference = makeTerm <$> symbol Grammar.MethodReference <*> children (Java.Syntax.MethodReference <$> term type' <*> manyTerm typeArgument <*> (new <|> term identifier))
|
|
|
|
|
|
|
|
where new = makeTerm <$> token AnonNew <*> pure Java.Syntax.NewKeyword
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
explicitConstructorInvocation :: Assignment Term
|
|
|
|
|
|
|
|
explicitConstructorInvocation = makeTerm <$> symbol ExplicitConstructorInvocation <*> children (uncurry Expression.Call <$> (callFunction <$> term expression <*> optional ((,) <$ optional (token AnonRParen) <* token AnonDot <*> manyTerm type' <*> identifier')) <*> argumentList <*> emptyTerm)
|
|
|
|
where
|
|
|
|
where
|
|
|
|
callFunction a (Just (typeArguments, b)) = (typeArguments, makeTerm1 (Expression.MemberAccess a b))
|
|
|
|
callFunction a (Just (typeArguments, b)) = (typeArguments, makeTerm1 (Expression.MemberAccess a b))
|
|
|
|
callFunction a Nothing = ([], a)
|
|
|
|
callFunction a Nothing = ([], a)
|
|
|
|
|
|
|
|
|
|
|
|
module' :: Assignment
|
|
|
|
module' :: Assignment Term
|
|
|
|
module' = toTerm (branchNode ModuleDeclaration (Java.Syntax.Module <$> expression <*> many expression))
|
|
|
|
module' = makeTerm <$> symbol ModuleDeclaration <*> children (Java.Syntax.Module <$> expression <*> many expression)
|
|
|
|
|
|
|
|
|
|
|
|
import' :: Assignment
|
|
|
|
import' :: Assignment Term
|
|
|
|
import' = makeTerm <$> symbol ImportDeclaration <*> children (Java.Syntax.Import <$> someTerm (expression <|> asterisk))
|
|
|
|
import' = makeTerm <$> symbol ImportDeclaration <*> children (Java.Syntax.Import <$> someTerm (expression <|> asterisk))
|
|
|
|
where asterisk = makeTerm <$> token Grammar.Asterisk <*> pure Java.Syntax.Asterisk
|
|
|
|
where asterisk = makeTerm <$> token Grammar.Asterisk <*> pure Java.Syntax.Asterisk
|
|
|
|
|
|
|
|
|
|
|
|
interface :: Assignment
|
|
|
|
interface :: Assignment Term
|
|
|
|
interface = makeTerm <$> symbol InterfaceDeclaration <*> children (normal <|> annotationType)
|
|
|
|
interface = makeTerm <$> symbol InterfaceDeclaration <*> children (normal <|> annotationType)
|
|
|
|
where
|
|
|
|
where
|
|
|
|
interfaceBody = makeTerm <$> symbol InterfaceBody <*> children (manyTerm interfaceMemberDeclaration)
|
|
|
|
interfaceBody = makeTerm <$> symbol InterfaceBody <*> children (manyTerm interfaceMemberDeclaration)
|
|
|
|
normal = symbol NormalInterfaceDeclaration *> children (makeInterface <$> manyTerm modifier <*> identifier <*> (typeParameters <|> pure []) <*> interfaceBody)
|
|
|
|
normal = symbol NormalInterfaceDeclaration *> children (makeInterface <$> manyTerm modifier <*> identifier <*> (typeParameters <|> pure []) <*> (extends <|> pure []) <*> interfaceBody)
|
|
|
|
makeInterface modifiers identifier typeParams = Declaration.InterfaceDeclaration (modifiers <> typeParams) identifier
|
|
|
|
makeInterface modifiers identifier typeParams = Declaration.InterfaceDeclaration (modifiers <> typeParams) identifier
|
|
|
|
annotationType = symbol AnnotationTypeDeclaration *> children (Declaration.InterfaceDeclaration [] <$> identifier <*> annotationTypeBody)
|
|
|
|
annotationType = symbol AnnotationTypeDeclaration *> children (Declaration.InterfaceDeclaration [] <$> identifier <*> pure [] <*> annotationTypeBody)
|
|
|
|
annotationTypeBody = makeTerm <$> symbol AnnotationTypeBody <*> children (many expression)
|
|
|
|
annotationTypeBody = makeTerm <$> symbol AnnotationTypeBody <*> children (manyTerm annotationTypeMember)
|
|
|
|
interfaceMemberDeclaration = symbol InterfaceMemberDeclaration *> children (term expression)
|
|
|
|
annotationTypeMember = symbol AnnotationTypeMemberDeclaration *> children (class' <|> interface <|> constant <|> annotationTypeElement)
|
|
|
|
|
|
|
|
annotationTypeElement = makeTerm <$> symbol AnnotationTypeElementDeclaration <*> children (Java.Syntax.AnnotationTypeElement <$> many modifier <*> type' <*> identifier <*> (dims <|> pure []) <*> (defaultValue <|> emptyTerm))
|
|
|
|
|
|
|
|
defaultValue = makeTerm <$> symbol DefaultValue <*> children (Java.Syntax.DefaultValue <$> elementValue)
|
|
|
|
|
|
|
|
elementValue = symbol ElementValue *> children (term expression)
|
|
|
|
|
|
|
|
interfaceMemberDeclaration = symbol InterfaceMemberDeclaration *> children (constant <|> method <|> class' <|> interface)
|
|
|
|
|
|
|
|
extends = symbol ExtendsInterfaces *> children (symbol InterfaceTypeList *> children (manyTerm type'))
|
|
|
|
|
|
|
|
|
|
|
|
package :: Assignment
|
|
|
|
constant :: Assignment Term
|
|
|
|
|
|
|
|
constant = makeTerm <$> symbol ConstantDeclaration <*> children ((,) [] <$> type' <**> variableDeclaratorList)
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
package :: Assignment Term
|
|
|
|
package = makeTerm <$> symbol PackageDeclaration <*> children (Java.Syntax.Package <$> someTerm expression)
|
|
|
|
package = makeTerm <$> symbol PackageDeclaration <*> children (Java.Syntax.Package <$> someTerm expression)
|
|
|
|
|
|
|
|
|
|
|
|
enum :: Assignment
|
|
|
|
enum :: Assignment Term
|
|
|
|
enum = makeTerm <$> symbol Grammar.EnumDeclaration <*> children (Java.Syntax.EnumDeclaration <$> manyTerm modifier <*> term identifier <*> (superInterfaces <|> pure []) <*> manyTerm enumConstant <*> (enumBodyDeclarations <|> pure []))
|
|
|
|
enum = makeTerm <$> symbol Grammar.EnumDeclaration <*> children (Java.Syntax.EnumDeclaration <$> manyTerm modifier <*> term identifier <*> (superInterfaces <|> pure []) <*> manyTerm enumConstant <*> (enumBodyDeclarations <|> pure []))
|
|
|
|
where
|
|
|
|
where
|
|
|
|
enumConstant = symbol EnumConstant *> children (term identifier)
|
|
|
|
enumConstant = symbol EnumConstant *> children (term identifier)
|
|
|
|
enumBodyDeclarations = symbol EnumBodyDeclarations *> children (manyTerm expression)
|
|
|
|
enumBodyDeclarations = symbol EnumBodyDeclarations *> children (manyTerm expression)
|
|
|
|
|
|
|
|
|
|
|
|
return' :: Assignment
|
|
|
|
return' :: Assignment Term
|
|
|
|
return' = makeTerm <$> symbol ReturnStatement <*> (Statement.Return <$> children (expression <|> emptyTerm))
|
|
|
|
return' = makeTerm <$> symbol ReturnStatement <*> (Statement.Return <$> children (expression <|> emptyTerm))
|
|
|
|
|
|
|
|
|
|
|
|
-- method expressions
|
|
|
|
dims :: Assignment [Term]
|
|
|
|
dims :: Assignment.Assignment [] Grammar [Term]
|
|
|
|
|
|
|
|
dims = symbol Dims *> children (many (emptyTerm <* token AnonLBracket <* token AnonRBracket))
|
|
|
|
dims = symbol Dims *> children (many (emptyTerm <* token AnonLBracket <* token AnonRBracket))
|
|
|
|
|
|
|
|
|
|
|
|
type' :: Assignment
|
|
|
|
dimsExpr :: Assignment Term
|
|
|
|
|
|
|
|
dimsExpr = makeTerm <$> symbol Grammar.DimsExpr <*> children (Java.Syntax.DimsExpr <$> manyTerm annotation <*> manyTerm expression)
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
type' :: Assignment Term
|
|
|
|
type' = choice [
|
|
|
|
type' = choice [
|
|
|
|
makeTerm <$> token VoidType <*> pure Type.Void
|
|
|
|
makeTerm <$> symbol VoidType <*> children (pure Type.Void)
|
|
|
|
, makeTerm <$> token IntegralType <*> pure Type.Int
|
|
|
|
, makeTerm <$> symbol IntegralType <*> children (pure Type.Int)
|
|
|
|
, makeTerm <$> token FloatingPointType <*> pure Type.Float
|
|
|
|
, makeTerm <$> symbol FloatingPointType <*> children (pure Type.Float)
|
|
|
|
, makeTerm <$> token BooleanType <*> pure Type.Bool
|
|
|
|
, makeTerm <$> symbol BooleanType <*> children (pure Type.Bool)
|
|
|
|
, symbol ArrayType *> children (array <$> type' <*> dims) -- type rule recurs into itself
|
|
|
|
, symbol ArrayType *> children (array <$> type' <*> dims) -- type rule recurs into itself
|
|
|
|
, symbol CatchType *> children (term type')
|
|
|
|
, makeTerm <$> symbol ScopedTypeIdentifier <*> children (Expression.MemberAccess <$> term type' <*> identifier')
|
|
|
|
, symbol ExceptionType *> children (term type')
|
|
|
|
|
|
|
|
, wildcard
|
|
|
|
, wildcard
|
|
|
|
, identifier
|
|
|
|
, identifier
|
|
|
|
|
|
|
|
, typeIdentifier
|
|
|
|
, generic
|
|
|
|
, generic
|
|
|
|
, typeArgument
|
|
|
|
, typeArgument
|
|
|
|
|
|
|
|
, annotatedType
|
|
|
|
]
|
|
|
|
]
|
|
|
|
where array = foldl (\into each -> makeTerm1 (Type.Array (Just each) into))
|
|
|
|
where array = foldl (\into each -> makeTerm1 (Type.Array (Just each) into))
|
|
|
|
|
|
|
|
|
|
|
|
typeArgument :: Assignment
|
|
|
|
annotatedType :: Assignment Term
|
|
|
|
|
|
|
|
annotatedType = makeTerm <$> symbol AnnotatedType <*> children (Java.Syntax.AnnotatedType <$> many annotation <*> type')
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
typeArgument :: Assignment Term
|
|
|
|
typeArgument = symbol TypeArgument *> children (term type')
|
|
|
|
typeArgument = symbol TypeArgument *> children (term type')
|
|
|
|
|
|
|
|
|
|
|
|
wildcard :: Assignment
|
|
|
|
wildcard :: Assignment Term
|
|
|
|
wildcard = makeTerm <$> symbol Grammar.Wildcard <*> children (Java.Syntax.Wildcard <$> manyTerm annotation <*> optional (super <|> extends))
|
|
|
|
wildcard = makeTerm <$> symbol Grammar.Wildcard <*> children (Java.Syntax.Wildcard <$> manyTerm annotation <*> optional (super <|> extends))
|
|
|
|
where
|
|
|
|
where
|
|
|
|
super = makeTerm <$> token Super <*> (Java.Syntax.WildcardBoundSuper <$> type')
|
|
|
|
super = makeTerm <$> token Super <*> (Java.Syntax.WildcardBoundSuper <$> type')
|
|
|
|
extends = makeTerm1 <$> (Java.Syntax.WildcardBoundExtends <$> type')
|
|
|
|
extends = makeTerm1 <$> (Java.Syntax.WildcardBoundExtends <$> type')
|
|
|
|
|
|
|
|
|
|
|
|
if' :: Assignment
|
|
|
|
if' :: Assignment Term
|
|
|
|
if' = makeTerm <$> symbol IfThenElseStatement <*> children (Statement.If <$> term expression <*> term expression <*> (term expression <|> emptyTerm))
|
|
|
|
if' = makeTerm <$> symbol IfThenElseStatement <*> children (Statement.If <$> term expression <*> term expression <*> (term expression <|> emptyTerm))
|
|
|
|
|
|
|
|
|
|
|
|
block :: Assignment
|
|
|
|
block :: Assignment Term
|
|
|
|
block = makeTerm <$> symbol Block <*> children (manyTerm expression)
|
|
|
|
block = makeTerm <$> symbol Block <*> children (manyTerm expression)
|
|
|
|
|
|
|
|
|
|
|
|
while :: Assignment
|
|
|
|
while :: Assignment Term
|
|
|
|
while = makeTerm <$> symbol WhileStatement <*> children (Statement.While <$> term expression <*> term expression)
|
|
|
|
while = makeTerm <$> symbol WhileStatement <*> children (Statement.While <$> term expression <*> term expression)
|
|
|
|
|
|
|
|
|
|
|
|
doWhile :: Assignment
|
|
|
|
doWhile :: Assignment Term
|
|
|
|
doWhile = makeTerm <$> symbol DoStatement <*> children (flip Statement.DoWhile <$> term expression <*> term expression)
|
|
|
|
doWhile = makeTerm <$> symbol DoStatement <*> children (flip Statement.DoWhile <$> term expression <*> term expression)
|
|
|
|
|
|
|
|
|
|
|
|
switch :: Assignment
|
|
|
|
switch :: Assignment Term
|
|
|
|
switch = makeTerm <$> symbol SwitchStatement <*> children (Statement.Match <$> term expression <*> switchBlock)
|
|
|
|
switch = makeTerm <$> symbol SwitchStatement <*> children (Statement.Match <$> term expression <*> switchBlock)
|
|
|
|
where
|
|
|
|
where
|
|
|
|
switchBlock = makeTerm <$> symbol SwitchBlock <*> children (manyTerm switchLabel)
|
|
|
|
switchBlock = makeTerm <$> symbol SwitchBlock <*> children (manyTerm switchLabel)
|
|
|
|
switchLabel = makeTerm <$> symbol SwitchLabel <*> (Statement.Pattern <$> children (term expression <|> emptyTerm) <*> expressions)
|
|
|
|
switchLabel = makeTerm <$> symbol SwitchLabel <*> (Statement.Pattern <$> children (term expression <|> emptyTerm) <*> expressions)
|
|
|
|
|
|
|
|
|
|
|
|
break :: Assignment
|
|
|
|
break :: Assignment Term
|
|
|
|
break = makeTerm <$> symbol BreakStatement <*> children (Statement.Break <$> (term expression <|> emptyTerm))
|
|
|
|
break = makeTerm <$> symbol BreakStatement <*> children (Statement.Break <$> (term expression <|> emptyTerm))
|
|
|
|
|
|
|
|
|
|
|
|
continue :: Assignment
|
|
|
|
continue :: Assignment Term
|
|
|
|
continue = makeTerm <$> symbol ContinueStatement <*> children (Statement.Continue <$> (term expression <|> emptyTerm))
|
|
|
|
continue = makeTerm <$> symbol ContinueStatement <*> children (Statement.Continue <$> (term expression <|> emptyTerm))
|
|
|
|
|
|
|
|
|
|
|
|
throw :: Assignment
|
|
|
|
throw :: Assignment Term
|
|
|
|
throw = makeTerm <$> symbol ThrowStatement <*> children (Statement.Throw <$> term expression)
|
|
|
|
throw = makeTerm <$> symbol ThrowStatement <*> children (Statement.Throw <$> term expression)
|
|
|
|
|
|
|
|
|
|
|
|
try :: Assignment
|
|
|
|
try :: Assignment Term
|
|
|
|
try = makeTerm <$> symbol TryStatement <*> children (Statement.Try <$> term expression <*> (append <$> optional catches <*> optional finally))
|
|
|
|
try = symbol TryStatement *> children tryWithResources <|> 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
|
|
|
|
catches :: Assignment [Term]
|
|
|
|
|
|
|
|
catches = symbol Catches *> children (manyTerm catch)
|
|
|
|
|
|
|
|
where
|
|
|
|
|
|
|
|
catch = makeTerm <$> symbol CatchClause <*> children (Statement.Catch <$> catchFormalParameter <*> term expression)
|
|
|
|
|
|
|
|
catchFormalParameter = makeTerm <$> symbol CatchFormalParameter <*> children (flip Type.Annotation <$> catchType <* symbol VariableDeclaratorId <*> children identifier)
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
catchType :: Assignment Term
|
|
|
|
|
|
|
|
catchType = makeTerm <$> symbol CatchType <*> (Java.Syntax.CatchType <$> many type')
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
finally :: Assignment Term
|
|
|
|
|
|
|
|
finally = makeTerm <$> symbol Finally <*> children (Statement.Finally <$> term expression)
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
append :: Maybe [a] -> Maybe a -> [a]
|
|
|
|
|
|
|
|
append Nothing Nothing = []
|
|
|
|
|
|
|
|
append Nothing (Just a) = [a]
|
|
|
|
|
|
|
|
append (Just a) Nothing = a
|
|
|
|
|
|
|
|
append (Just a) (Just b) = a <> [b]
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
tryWithResources :: Assignment Term
|
|
|
|
|
|
|
|
tryWithResources = makeTerm <$> symbol TryWithResourcesStatement <*> children (Java.Syntax.TryWithResources <$> resourceSpecification <*> block <*> (append <$> optional catches <*> optional finally))
|
|
|
|
|
|
|
|
where
|
|
|
|
|
|
|
|
resourceSpecification = symbol ResourceSpecification *> children (manyTerm resource)
|
|
|
|
|
|
|
|
resource = symbol Resource *> children variableAccess <|> makeTerm <$> symbol Resource <*> children (makeSingleDecl <$> many modifier <*> type' <*> variableDeclaratorId <*> term expression)
|
|
|
|
|
|
|
|
variableAccess = symbol VariableAccess *> children (identifier <|> fieldAccess)
|
|
|
|
|
|
|
|
makeSingleDecl modifiers type' target = Statement.Assignment [] (makeTerm1 (Java.Syntax.Variable modifiers type' target))
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
for :: Assignment Term
|
|
|
|
for = symbol ForStatement *> children (basicFor <|> enhancedFor)
|
|
|
|
for = symbol ForStatement *> children (basicFor <|> enhancedFor)
|
|
|
|
|
|
|
|
|
|
|
|
basicFor :: Assignment
|
|
|
|
basicFor :: Assignment Term
|
|
|
|
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)
|
|
|
|
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
|
|
|
|
where
|
|
|
|
forInit = symbol ForInit *> children (term expression)
|
|
|
|
forInit = symbol ForInit *> children (term expression)
|
|
|
|
forStep = makeTerm <$> location <*> manyTermsTill expression (token AnonRParen)
|
|
|
|
forStep = makeTerm <$> location <*> manyTermsTill expression (token AnonRParen)
|
|
|
|
|
|
|
|
|
|
|
|
enhancedFor :: Assignment
|
|
|
|
enhancedFor :: Assignment Term
|
|
|
|
enhancedFor = makeTerm <$> symbol EnhancedForStatement <*> children (Statement.ForEach <$> (variable <$> manyTerm modifier <*> type' <*> variableDeclaratorId) <*> term expression <*> term expression)
|
|
|
|
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)
|
|
|
|
where variable modifiers type' variableDeclaratorId = makeTerm1 (Java.Syntax.Variable modifiers type' variableDeclaratorId)
|
|
|
|
|
|
|
|
|
|
|
|
-- TODO: instanceOf
|
|
|
|
assert :: Assignment Term
|
|
|
|
binary :: Assignment
|
|
|
|
assert = makeTerm <$> symbol Grammar.AssertStatement <*> children (Java.Syntax.AssertStatement <$> term expression <*> optional (term expression))
|
|
|
|
binary = makeTerm' <$> symbol BinaryExpression <*> children (infixTerm expression expression
|
|
|
|
|
|
|
|
|
|
|
|
binary :: Assignment Term
|
|
|
|
|
|
|
|
binary = makeTerm' <$> symbol BinaryExpression <*> children (infixTerm expressionAndParens expressionAndParens
|
|
|
|
[ (inject .) . Expression.LessThan <$ symbol AnonLAngle
|
|
|
|
[ (inject .) . Expression.LessThan <$ symbol AnonLAngle
|
|
|
|
, (inject .) . Expression.GreaterThan <$ symbol AnonRAngle
|
|
|
|
, (inject .) . Expression.GreaterThan <$ symbol AnonRAngle
|
|
|
|
, (inject .) . Expression.Equal <$ symbol AnonEqualEqual
|
|
|
|
, (inject .) . Expression.Equal <$ symbol AnonEqualEqual
|
|
|
@ -444,16 +509,20 @@ binary = makeTerm' <$> symbol BinaryExpression <*> children (infixTerm expressio
|
|
|
|
, (inject .) . Expression.DividedBy <$ symbol AnonSlash
|
|
|
|
, (inject .) . Expression.DividedBy <$ symbol AnonSlash
|
|
|
|
, (inject .) . Expression.InstanceOf <$ symbol AnonInstanceof
|
|
|
|
, (inject .) . Expression.InstanceOf <$ symbol AnonInstanceof
|
|
|
|
])
|
|
|
|
])
|
|
|
|
where invert cons a b = Expression.Not (makeTerm1 (cons a b))
|
|
|
|
where
|
|
|
|
|
|
|
|
invert cons a b = Expression.Not (makeTerm1 (cons a b))
|
|
|
|
|
|
|
|
expressionAndParens = token AnonLParen *> expressionAndParens <* token AnonRParen <|> expression
|
|
|
|
|
|
|
|
-- TODO: expressionAndParens is a hack that accommodates Java's nested parens
|
|
|
|
|
|
|
|
-- but altering the TreeSitter Java grammar is a better longer term goal.
|
|
|
|
|
|
|
|
|
|
|
|
-- | Match infix terms separated by any of a list of operators, assigning any comments following each operand.
|
|
|
|
-- | Match infix terms separated by any of a list of operators, assigning any comments following each operand.
|
|
|
|
infixTerm :: Assignment
|
|
|
|
infixTerm :: Assignment Term
|
|
|
|
-> Assignment
|
|
|
|
-> Assignment Term
|
|
|
|
-> [Assignment.Assignment [] Grammar (Term -> Term -> Sum Syntax Term)]
|
|
|
|
-> [Assignment (Term -> Term -> Sum Syntax Term)]
|
|
|
|
-> Assignment.Assignment [] Grammar (Sum Syntax Term)
|
|
|
|
-> Assignment (Sum Syntax Term)
|
|
|
|
infixTerm = infixContext comment
|
|
|
|
infixTerm = infixContext comment
|
|
|
|
|
|
|
|
|
|
|
|
assignment' :: Assignment
|
|
|
|
assignment' :: Assignment Term
|
|
|
|
assignment' = makeTerm' <$> symbol AssignmentExpression <*> children (infixTerm lhs expression
|
|
|
|
assignment' = makeTerm' <$> symbol AssignmentExpression <*> children (infixTerm lhs expression
|
|
|
|
[ (inject .) . Statement.Assignment [] <$ symbol AnonEqual
|
|
|
|
[ (inject .) . Statement.Assignment [] <$ symbol AnonEqual
|
|
|
|
, assign Expression.Plus <$ symbol AnonPlusEqual
|
|
|
|
, assign Expression.Plus <$ symbol AnonPlusEqual
|
|
|
@ -479,7 +548,7 @@ data UnaryType
|
|
|
|
| UBang
|
|
|
|
| UBang
|
|
|
|
| UTilde
|
|
|
|
| UTilde
|
|
|
|
|
|
|
|
|
|
|
|
unary :: Assignment
|
|
|
|
unary :: Assignment Term
|
|
|
|
unary = make <$> symbol UnaryExpression <*> children ((,) <$> operator <*> term expression)
|
|
|
|
unary = make <$> symbol UnaryExpression <*> children ((,) <$> operator <*> term expression)
|
|
|
|
where
|
|
|
|
where
|
|
|
|
make _ (UPlus, operand) = operand
|
|
|
|
make _ (UPlus, operand) = operand
|
|
|
@ -491,36 +560,37 @@ unary = make <$> symbol UnaryExpression <*> children ((,) <$> operator <*> term
|
|
|
|
<|> token AnonBang $> UBang
|
|
|
|
<|> token AnonBang $> UBang
|
|
|
|
<|> token AnonTilde $> UTilde
|
|
|
|
<|> token AnonTilde $> UTilde
|
|
|
|
|
|
|
|
|
|
|
|
update :: Assignment
|
|
|
|
update :: Assignment Term
|
|
|
|
update = makeTerm' <$> symbol UpdateExpression <*> children (
|
|
|
|
update = makeTerm' <$> symbol UpdateExpression <*> children (
|
|
|
|
inject . Statement.PreIncrement <$ token AnonPlusPlus <*> term expression
|
|
|
|
inject . Statement.PreIncrement <$ token AnonPlusPlus <*> term expression
|
|
|
|
<|> inject . Statement.PreDecrement <$ token AnonMinusMinus <*> term expression
|
|
|
|
<|> inject . Statement.PreDecrement <$ token AnonMinusMinus <*> term expression
|
|
|
|
<|> inject . Statement.PostIncrement <$> term expression <* token AnonPlusPlus
|
|
|
|
<|> inject . Statement.PostIncrement <$> term expression <* token AnonPlusPlus
|
|
|
|
<|> inject . Statement.PostDecrement <$> term expression <* token AnonMinusMinus)
|
|
|
|
<|> inject . Statement.PostDecrement <$> term expression <* token AnonMinusMinus)
|
|
|
|
|
|
|
|
|
|
|
|
ternary :: Assignment
|
|
|
|
ternary :: Assignment Term
|
|
|
|
ternary = makeTerm <$> symbol TernaryExpression <*> children (Statement.If <$> term expression <*> term expression <*> term expression)
|
|
|
|
ternary = makeTerm <$> symbol TernaryExpression <*> children (Statement.If <$> term expression <*> term expression <*> term expression)
|
|
|
|
|
|
|
|
|
|
|
|
synchronized :: Assignment
|
|
|
|
synchronized :: Assignment Term
|
|
|
|
synchronized = makeTerm <$> symbol SynchronizedStatement <*> children (Java.Syntax.Synchronized <$> term expression <*> term expression)
|
|
|
|
synchronized = makeTerm <$> symbol SynchronizedStatement <*> children (Java.Syntax.Synchronized <$> term expression <*> term expression)
|
|
|
|
|
|
|
|
|
|
|
|
classInstance :: Assignment
|
|
|
|
classInstance :: Assignment Term
|
|
|
|
classInstance = makeTerm <$> symbol ClassInstanceCreationExpression <*> children unqualified
|
|
|
|
classInstance = makeTerm <$> symbol ClassInstanceCreationExpression <*> children unqualified
|
|
|
|
where
|
|
|
|
where
|
|
|
|
unqualified = symbol UnqualifiedClassInstanceCreationExpression *> children (Java.Syntax.New <$> type' <*> (argumentList <|> pure []))
|
|
|
|
unqualified = symbol UnqualifiedClassInstanceCreationExpression *> children (Java.Syntax.New <$> type' <*> (argumentList <|> pure []) <*> optional classBody)
|
|
|
|
|
|
|
|
|
|
|
|
argumentList :: Assignment.Assignment [] Grammar [Term]
|
|
|
|
classLiteral :: Assignment Term
|
|
|
|
|
|
|
|
classLiteral = makeTerm <$> symbol Grammar.ClassLiteral <*> children (Java.Syntax.ClassLiteral <$> type')
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
argumentList :: Assignment [Term]
|
|
|
|
argumentList = symbol ArgumentList *> children (manyTerm expression)
|
|
|
|
argumentList = symbol ArgumentList *> children (manyTerm expression)
|
|
|
|
|
|
|
|
|
|
|
|
super :: Assignment
|
|
|
|
super :: Assignment Term
|
|
|
|
super = makeTerm <$> token Super <*> pure Expression.Super
|
|
|
|
super = makeTerm <$> token Super <*> pure Expression.Super
|
|
|
|
-- INCORRECT: super = makeTerm <$> token Super $> Expression.Super
|
|
|
|
|
|
|
|
-- Take partially applied function and replace it instead of applying
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
this :: Assignment
|
|
|
|
this :: Assignment Term
|
|
|
|
this = makeTerm <$> token This <*> pure Expression.This
|
|
|
|
this = makeTerm <$> token This <*> pure Expression.This
|
|
|
|
|
|
|
|
|
|
|
|
constructorDeclaration :: Assignment
|
|
|
|
constructorDeclaration :: Assignment Term
|
|
|
|
constructorDeclaration = makeTerm <$> symbol ConstructorDeclaration <*> children (
|
|
|
|
constructorDeclaration = makeTerm <$> symbol ConstructorDeclaration <*> children (
|
|
|
|
constructor <$> manyTerm modifier <*> constructorDeclarator <*> (throws <|> pure []) <*> constructorBody)
|
|
|
|
constructor <$> manyTerm modifier <*> constructorDeclarator <*> (throws <|> pure []) <*> constructorBody)
|
|
|
|
where
|
|
|
|
where
|
|
|
@ -528,13 +598,14 @@ constructorDeclaration = makeTerm <$> symbol ConstructorDeclaration <*> children
|
|
|
|
constructorBody = makeTerm <$> symbol ConstructorBody <*> children (manyTerm expression) -- wrapping list of terms up in single node
|
|
|
|
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
|
|
|
|
constructor modifiers (typeParameters, identifier, formalParameters) = Java.Syntax.Constructor modifiers typeParameters identifier formalParameters -- let partial application do its thing
|
|
|
|
|
|
|
|
|
|
|
|
typeParameters :: Assignment.Assignment [] Grammar [Term]
|
|
|
|
typeParameters :: Assignment [Term]
|
|
|
|
typeParameters = symbol TypeParameters *> children (manyTerm typeParam)
|
|
|
|
typeParameters = symbol TypeParameters *> children (manyTerm typeParam)
|
|
|
|
where
|
|
|
|
where
|
|
|
|
typeParam = makeTerm <$> symbol Grammar.TypeParameter <*> children (Java.Syntax.TypeParameter <$> manyTerm annotation <*> term identifier <*> (typeBound <|> pure []))
|
|
|
|
typeParam = makeTerm <$> symbol Grammar.TypeParameter <*> children (Java.Syntax.TypeParameter <$> manyTerm annotation <*> term identifier <*> (typeBound <|> pure []))
|
|
|
|
typeBound = symbol TypeBound *> children (manyTerm type')
|
|
|
|
typeBound = symbol TypeBound *> children (manyTerm type')
|
|
|
|
|
|
|
|
|
|
|
|
annotation :: Assignment
|
|
|
|
|
|
|
|
|
|
|
|
annotation :: Assignment Term
|
|
|
|
annotation = makeTerm <$> symbol NormalAnnotation <*> children (Java.Syntax.Annotation <$> term expression <*> (elementValuePairList <|> pure []))
|
|
|
|
annotation = makeTerm <$> symbol NormalAnnotation <*> children (Java.Syntax.Annotation <$> term expression <*> (elementValuePairList <|> pure []))
|
|
|
|
<|> makeTerm <$> symbol MarkerAnnotation <*> children (Java.Syntax.Annotation <$> term expression <*> pure [])
|
|
|
|
<|> makeTerm <$> symbol MarkerAnnotation <*> children (Java.Syntax.Annotation <$> term expression <*> pure [])
|
|
|
|
<|> makeTerm <$> symbol SingleElementAnnotation <*> children (Java.Syntax.Annotation <$> term expression <*> (pure <$> term elementValue))
|
|
|
|
<|> makeTerm <$> symbol SingleElementAnnotation <*> children (Java.Syntax.Annotation <$> term expression <*> (pure <$> term elementValue))
|
|
|
@ -543,28 +614,33 @@ annotation = makeTerm <$> symbol NormalAnnotation <*> children (Java.Syntax.Anno
|
|
|
|
elementValuePair = makeTerm <$> symbol ElementValuePair <*> children (Java.Syntax.AnnotationField <$> term expression <*> term elementValue)
|
|
|
|
elementValuePair = makeTerm <$> symbol ElementValuePair <*> children (Java.Syntax.AnnotationField <$> term expression <*> term elementValue)
|
|
|
|
elementValue = symbol ElementValue *> children (term expression)
|
|
|
|
elementValue = symbol ElementValue *> children (term expression)
|
|
|
|
|
|
|
|
|
|
|
|
throws :: Assignment.Assignment [] Grammar [Term]
|
|
|
|
throws :: Assignment [Term]
|
|
|
|
throws = symbol Throws *> children (symbol ExceptionTypeList *> children(manyTerm type'))
|
|
|
|
throws = symbol Throws *> children (symbol ExceptionTypeList *> children (manyTerm type'))
|
|
|
|
|
|
|
|
|
|
|
|
formalParameters :: Assignment.Assignment [] Grammar [Term]
|
|
|
|
formalParameters :: Assignment [Term]
|
|
|
|
formalParameters = manyTerm (parameter <|> spreadParameter)
|
|
|
|
formalParameters = manyTerm (parameter <|> spreadParameter)
|
|
|
|
where
|
|
|
|
where
|
|
|
|
parameter = makeTerm <$> symbol FormalParameter <*> children (makeAnnotation <$> manyTerm modifier <*> type' <* symbol VariableDeclaratorId <*> children identifier)
|
|
|
|
parameter = makeTerm <$> symbol FormalParameter <*> children (makeAnnotation <$> manyTerm modifier <*> type' <* symbol VariableDeclaratorId <*> children identifier)
|
|
|
|
makeAnnotation [] type' variableName = Type.Annotation variableName type'
|
|
|
|
makeAnnotation [] type' variableName = Type.Annotation variableName type'
|
|
|
|
makeAnnotation modifiers type' variableName = Type.Annotation variableName (makeTerm1 (Java.Syntax.TypeWithModifiers modifiers type'))
|
|
|
|
makeAnnotation modifiers type' variableName = Type.Annotation variableName (makeTerm1 (Java.Syntax.TypeWithModifiers modifiers type'))
|
|
|
|
|
|
|
|
|
|
|
|
castExpression :: Assignment
|
|
|
|
castExpression :: Assignment Term
|
|
|
|
castExpression = makeTerm <$> symbol CastExpression <*> children (flip Type.Annotation <$> type' <*> term expression)
|
|
|
|
castExpression = makeTerm <$> symbol CastExpression <*> children (flip Type.Annotation <$> type' <*> term expression)
|
|
|
|
|
|
|
|
|
|
|
|
fieldAccess :: Assignment
|
|
|
|
fieldAccess :: Assignment Term
|
|
|
|
fieldAccess = makeTerm <$> symbol FieldAccess <*> children (Expression.MemberAccess <$> term expression <*> identifier')
|
|
|
|
fieldAccess = makeTerm <$> symbol FieldAccess <*> children (Expression.MemberAccess <$> term expression <*> identifier')
|
|
|
|
|
|
|
|
|
|
|
|
spreadParameter :: Assignment
|
|
|
|
spreadParameter :: Assignment Term
|
|
|
|
spreadParameter = makeTerm <$> symbol Grammar.SpreadParameter <*> children (Java.Syntax.SpreadParameter <$> (makeSingleDecl <$> manyTerm modifier <*> type' <*> variableDeclarator))
|
|
|
|
spreadParameter = makeTerm <$> symbol Grammar.SpreadParameter <*> children (Java.Syntax.SpreadParameter <$> (makeSingleDecl <$> manyTerm modifier <*> type' <*> variableDeclarator))
|
|
|
|
where
|
|
|
|
where
|
|
|
|
variableDeclarator = symbol VariableDeclarator *> children ((,) <$> variableDeclaratorId <*> optional expression)
|
|
|
|
variableDeclarator = symbol VariableDeclarator *> children ((,) <$> variableDeclaratorId <*> optional expression)
|
|
|
|
makeSingleDecl modifiers type' (target, Nothing) = makeTerm1 (Java.Syntax.Variable modifiers type' target)
|
|
|
|
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)
|
|
|
|
makeSingleDecl modifiers type' (target, Just value) = makeTerm1 (Statement.Assignment [] (makeTerm1 (Java.Syntax.Variable modifiers type' target)) value)
|
|
|
|
|
|
|
|
|
|
|
|
arrayAccess :: Assignment
|
|
|
|
arrayAccess :: Assignment Term
|
|
|
|
arrayAccess = makeTerm <$> symbol ArrayAccess <*> children (Expression.Subscript <$> term expression <*> manyTerm expression)
|
|
|
|
arrayAccess = makeTerm <$> symbol ArrayAccess <*> children (Expression.Subscript <$> term expression <*> manyTerm expression)
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
lambda :: Assignment Term
|
|
|
|
|
|
|
|
lambda = makeTerm <$> symbol LambdaExpression <*> children (Java.Syntax.Lambda <$> manyTerm expression <*> lambdaBody)
|
|
|
|
|
|
|
|
where
|
|
|
|
|
|
|
|
lambdaBody = makeTerm <$> symbol Grammar.LambdaBody <*> children (Java.Syntax.LambdaBody <$> manyTerm expression)
|
|
|
|