mirror of
https://github.com/github/semantic.git
synced 2024-12-26 08:25:19 +03:00
Merge branch 'master' into fix-stomping-json-key-term
This commit is contained in:
commit
61e5a61b95
@ -65,7 +65,6 @@ handleError = flip Assignment.catchError (\ err -> makeTerm <$> Assignment.locat
|
||||
parseError :: (HasCallStack, Error :< syntaxes, Bounded grammar, Enum grammar, Ix grammar, Apply Foldable syntaxes) => Assignment.Assignment ast grammar (Term (Sum syntaxes) (Record Location))
|
||||
parseError = makeTerm <$> Assignment.token maxBound <*> pure (Error (ErrorStack $ errorSite <$> getCallStack (freezeCallStack callStack)) [] (Just "ParseError") [])
|
||||
|
||||
|
||||
-- | Match context terms before a subject term, wrapping both up in a Context term if any context terms matched, or otherwise returning the subject term.
|
||||
contextualize :: (HasCallStack, Context :< syntaxes, Alternative m, Semigroup ann, Apply Foldable syntaxes)
|
||||
=> m (Term (Sum syntaxes) ann)
|
||||
|
@ -121,7 +121,8 @@ instance Declarations a => Declarations (VariableDeclaration a) where
|
||||
|
||||
|
||||
-- | A TypeScript/Java style interface declaration to implement.
|
||||
data InterfaceDeclaration a = InterfaceDeclaration { interfaceDeclarationContext :: ![a], interfaceDeclarationIdentifier :: !a, interfaceDeclarationBody :: !a }
|
||||
|
||||
data InterfaceDeclaration a = InterfaceDeclaration { interfaceDeclarationContext :: ![a], interfaceDeclarationIdentifier :: !a, interfaceDeclarationSuperInterfaces :: ![a], interfaceDeclarationBody :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1)
|
||||
|
||||
instance Eq1 InterfaceDeclaration where liftEq = genericLiftEq
|
||||
|
@ -14,7 +14,7 @@ import Data.Record
|
||||
import Data.Syntax (contextualize, emptyTerm, handleError, infixContext, makeTerm, makeTerm', makeTerm'', makeTerm1, parseError, postContextualize)
|
||||
import Data.Sum
|
||||
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 Data.Syntax as Syntax
|
||||
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.Term as Term
|
||||
import Prelude hiding (break)
|
||||
import Prologue hiding (for, try, This)
|
||||
import Prologue hiding (for, try, This, catches, finally)
|
||||
|
||||
type Syntax =
|
||||
'[ Comment.Comment
|
||||
@ -66,18 +66,33 @@ type Syntax =
|
||||
, Expression.Member
|
||||
, Expression.Super
|
||||
, Expression.This
|
||||
, Java.Syntax.AnnotatedType
|
||||
, Java.Syntax.Annotation
|
||||
, Java.Syntax.AnnotationField
|
||||
, Java.Syntax.AnnotationTypeElement
|
||||
, Java.Syntax.ArrayCreationExpression
|
||||
, Java.Syntax.AssertStatement
|
||||
, Java.Syntax.Asterisk
|
||||
, Java.Syntax.CatchType
|
||||
, Java.Syntax.Constructor
|
||||
, Java.Syntax.ClassBody
|
||||
, Java.Syntax.ClassLiteral
|
||||
, Java.Syntax.DefaultValue
|
||||
, Java.Syntax.DimsExpr
|
||||
, Java.Syntax.EnumDeclaration
|
||||
, Java.Syntax.GenericType
|
||||
, Java.Syntax.Import
|
||||
, Java.Syntax.Lambda
|
||||
, Java.Syntax.LambdaBody
|
||||
, Java.Syntax.MethodReference
|
||||
, Java.Syntax.Module
|
||||
, Java.Syntax.New
|
||||
, Java.Syntax.NewKeyword
|
||||
, Java.Syntax.Package
|
||||
, Java.Syntax.SpreadParameter
|
||||
, Java.Syntax.StaticInitializer
|
||||
, Java.Syntax.Synchronized
|
||||
, Java.Syntax.TryWithResources
|
||||
, Java.Syntax.TypeParameter
|
||||
, Java.Syntax.TypeWithModifiers
|
||||
, Java.Syntax.Variable
|
||||
@ -125,41 +140,43 @@ type Syntax =
|
||||
]
|
||||
|
||||
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 :: Assignment
|
||||
assignment :: Assignment Term
|
||||
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.
|
||||
manyTerm :: Assignment -> Assignment.Assignment [] Grammar [Term]
|
||||
manyTerm :: Assignment Term -> Assignment [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 :: Assignment Term
|
||||
-> Assignment b
|
||||
-> Assignment [Term]
|
||||
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))
|
||||
|
||||
-- | Match comments before and after the node.
|
||||
term :: Assignment -> Assignment
|
||||
term :: Assignment Term -> Assignment Term
|
||||
term term = contextualize comment (postContextualize comment term)
|
||||
|
||||
-- | Match
|
||||
expression :: Assignment
|
||||
expression :: Assignment Term
|
||||
expression = handleError (choice expressionChoices)
|
||||
|
||||
expressions :: Assignment
|
||||
expressions :: Assignment Term
|
||||
expressions = makeTerm'' <$> location <*> many expression
|
||||
|
||||
expressionChoices :: [Assignment.Assignment [] Grammar Term]
|
||||
expressionChoices :: [Assignment Term]
|
||||
expressionChoices =
|
||||
[
|
||||
arrayInitializer
|
||||
, arrayAccess
|
||||
arrayAccess
|
||||
, arrayCreationExpression
|
||||
, arrayInitializer
|
||||
, assert
|
||||
, assignment'
|
||||
, block
|
||||
, binary
|
||||
@ -168,11 +185,13 @@ expressionChoices =
|
||||
, castExpression
|
||||
, char
|
||||
, class'
|
||||
, classBody
|
||||
, classInstance
|
||||
, classLiteral
|
||||
, continue
|
||||
, constructorDeclaration
|
||||
, dimsExpr
|
||||
, explicitConstructorInvocation
|
||||
-- , TODO: constantDeclaration
|
||||
, doWhile
|
||||
, fieldAccess
|
||||
, fieldDeclaration
|
||||
@ -184,8 +203,10 @@ expressionChoices =
|
||||
, identifier
|
||||
, import'
|
||||
, integer
|
||||
, lambda
|
||||
, method
|
||||
, methodInvocation
|
||||
, methodReference
|
||||
, module'
|
||||
, null'
|
||||
, package
|
||||
@ -194,6 +215,7 @@ expressionChoices =
|
||||
, string
|
||||
, super
|
||||
, switch
|
||||
, staticInitializer
|
||||
, synchronized
|
||||
, ternary
|
||||
, this
|
||||
@ -206,22 +228,22 @@ expressionChoices =
|
||||
, while
|
||||
]
|
||||
|
||||
modifier :: Assignment
|
||||
modifier :: Assignment Term
|
||||
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 :: Assignment Term
|
||||
arrayInitializer = makeTerm <$> symbol ArrayInitializer <*> (Literal.Array <$> many expression)
|
||||
|
||||
comment :: Assignment
|
||||
comment :: Assignment Term
|
||||
comment = makeTerm <$> symbol Comment <*> (Comment.Comment <$> source)
|
||||
|
||||
localVariableDeclaration :: Assignment
|
||||
localVariableDeclaration :: Assignment Term
|
||||
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)
|
||||
where
|
||||
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, 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
|
||||
|
||||
variableDeclaratorId :: Assignment
|
||||
variableDeclaratorId :: Assignment Term
|
||||
variableDeclaratorId = symbol VariableDeclaratorId *> children identifier
|
||||
|
||||
-- Literals
|
||||
boolean :: Assignment
|
||||
boolean = toTerm (branchNode BooleanLiteral
|
||||
( leafNode Grammar.True $> Literal.true
|
||||
<|> leafNode Grammar.False $> Literal.false))
|
||||
boolean :: Assignment Term
|
||||
boolean = makeTerm <$> symbol BooleanLiteral <*> children
|
||||
(token Grammar.True $> Literal.true
|
||||
<|> token Grammar.False $> Literal.false)
|
||||
|
||||
null' :: Assignment
|
||||
null' :: Assignment Term
|
||||
null' = makeTerm <$> symbol NullLiteral <*> (Literal.Null <$ source)
|
||||
|
||||
-- Integer supports all integer and floating point literals (hex, octal, binary)
|
||||
integer :: Assignment
|
||||
integer :: Assignment Term
|
||||
integer = makeTerm <$> symbol IntegerLiteral <*> children (Literal.Integer <$> source)
|
||||
|
||||
float :: Assignment
|
||||
float :: Assignment Term
|
||||
float = makeTerm <$> symbol FloatingPointLiteral <*> children (Literal.Float <$> source)
|
||||
|
||||
string :: Assignment
|
||||
string :: Assignment Term
|
||||
string = makeTerm <$> symbol StringLiteral <*> (Literal.TextElement <$> source)
|
||||
|
||||
char :: Assignment
|
||||
char :: Assignment Term
|
||||
char = makeTerm <$> symbol CharacterLiteral <*> (Literal.TextElement <$> source)
|
||||
|
||||
-- Identifiers
|
||||
identifier :: Assignment
|
||||
identifier = makeTerm <$> (symbol Identifier <|> symbol TypeIdentifier) <*> (Syntax.Identifier . name <$> source)
|
||||
identifier :: Assignment Term
|
||||
identifier = makeTerm <$> symbol Identifier <*> (Syntax.Identifier . name <$> source)
|
||||
|
||||
identifier' :: Assignment.Assignment [] Grammar Name
|
||||
identifier' = (symbol Identifier <|> symbol TypeIdentifier) *> (name <$> source)
|
||||
typeIdentifier :: Assignment Term
|
||||
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')
|
||||
|
||||
superInterfaces :: Assignment.Assignment [] Grammar [Term]
|
||||
superInterfaces :: Assignment [Term]
|
||||
superInterfaces = symbol SuperInterfaces *> children (symbol InterfaceTypeList *> children(manyTerm type'))
|
||||
|
||||
-- Declarations
|
||||
class' :: Assignment
|
||||
class' :: Assignment Term
|
||||
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)
|
||||
makeClass modifiers identifier typeParams superClass superInterfaces = Declaration.Class (modifiers <> typeParams) identifier (maybeToList superClass <> superInterfaces)
|
||||
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)
|
||||
|
||||
method :: Assignment
|
||||
method :: Assignment Term
|
||||
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
|
||||
-- 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')
|
||||
|
||||
methodInvocation :: Assignment
|
||||
methodInvocation = makeTerm <$> symbol MethodInvocation <*> children (uncurry Expression.Call <$> (callFunction <$> expression <*> optional ((,) <$ token AnonDot <*> manyTerm typeArgument <*> identifier')) <*> (argumentList <|> pure []) <*> emptyTerm)
|
||||
methodInvocation :: Assignment Term
|
||||
methodInvocation = makeTerm <$> symbol MethodInvocation <*> children (uncurry Expression.Call <$> (callFunction <$> expression <*> optional ((,) <$ optional (token AnonRParen) <* token AnonDot <*> manyTerm typeArgument <*> identifier')) <*> (argumentList <|> pure []) <*> emptyTerm)
|
||||
where
|
||||
callFunction a (Just (typeArguments, b)) = (typeArguments, makeTerm1 (Expression.MemberAccess a b))
|
||||
callFunction a Nothing = ([], a)
|
||||
|
||||
explicitConstructorInvocation :: Assignment
|
||||
explicitConstructorInvocation = makeTerm <$> symbol ExplicitConstructorInvocation <*> children (uncurry Expression.Call <$> (callFunction <$> term expression <*> optional ((,) <$ token AnonDot <*> manyTerm type' <*> identifier')) <*> argumentList <*> emptyTerm)
|
||||
methodReference :: Assignment Term
|
||||
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
|
||||
callFunction a (Just (typeArguments, b)) = (typeArguments, makeTerm1 (Expression.MemberAccess a b))
|
||||
callFunction a Nothing = ([], a)
|
||||
|
||||
module' :: Assignment
|
||||
module' = toTerm (branchNode ModuleDeclaration (Java.Syntax.Module <$> expression <*> many expression))
|
||||
module' :: Assignment Term
|
||||
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))
|
||||
where asterisk = makeTerm <$> token Grammar.Asterisk <*> pure Java.Syntax.Asterisk
|
||||
|
||||
interface :: Assignment
|
||||
interface :: Assignment Term
|
||||
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)
|
||||
normal = symbol NormalInterfaceDeclaration *> children (makeInterface <$> manyTerm modifier <*> identifier <*> (typeParameters <|> pure []) <*> (extends <|> 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)
|
||||
annotationType = symbol AnnotationTypeDeclaration *> children (Declaration.InterfaceDeclaration [] <$> identifier <*> pure [] <*> annotationTypeBody)
|
||||
annotationTypeBody = makeTerm <$> symbol AnnotationTypeBody <*> children (manyTerm annotationTypeMember)
|
||||
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)
|
||||
|
||||
enum :: Assignment
|
||||
enum :: Assignment Term
|
||||
enum = makeTerm <$> symbol Grammar.EnumDeclaration <*> children (Java.Syntax.EnumDeclaration <$> manyTerm modifier <*> term identifier <*> (superInterfaces <|> pure []) <*> manyTerm enumConstant <*> (enumBodyDeclarations <|> pure []))
|
||||
where
|
||||
enumConstant = symbol EnumConstant *> children (term identifier)
|
||||
enumBodyDeclarations = symbol EnumBodyDeclarations *> children (manyTerm expression)
|
||||
|
||||
return' :: Assignment
|
||||
return' :: Assignment Term
|
||||
return' = makeTerm <$> symbol ReturnStatement <*> (Statement.Return <$> children (expression <|> emptyTerm))
|
||||
|
||||
-- method expressions
|
||||
dims :: Assignment.Assignment [] Grammar [Term]
|
||||
dims :: Assignment [Term]
|
||||
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 [
|
||||
makeTerm <$> token VoidType <*> pure Type.Void
|
||||
, makeTerm <$> token IntegralType <*> pure Type.Int
|
||||
, makeTerm <$> token FloatingPointType <*> pure Type.Float
|
||||
, makeTerm <$> token BooleanType <*> pure Type.Bool
|
||||
makeTerm <$> symbol VoidType <*> children (pure Type.Void)
|
||||
, makeTerm <$> symbol IntegralType <*> children (pure Type.Int)
|
||||
, makeTerm <$> symbol FloatingPointType <*> children (pure Type.Float)
|
||||
, makeTerm <$> symbol BooleanType <*> children (pure Type.Bool)
|
||||
, symbol ArrayType *> children (array <$> type' <*> dims) -- type rule recurs into itself
|
||||
, symbol CatchType *> children (term type')
|
||||
, symbol ExceptionType *> children (term type')
|
||||
, makeTerm <$> symbol ScopedTypeIdentifier <*> children (Expression.MemberAccess <$> term type' <*> identifier')
|
||||
, wildcard
|
||||
, identifier
|
||||
, typeIdentifier
|
||||
, generic
|
||||
, typeArgument
|
||||
, annotatedType
|
||||
]
|
||||
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')
|
||||
|
||||
wildcard :: Assignment
|
||||
wildcard :: Assignment Term
|
||||
wildcard = makeTerm <$> symbol Grammar.Wildcard <*> children (Java.Syntax.Wildcard <$> manyTerm annotation <*> optional (super <|> extends))
|
||||
where
|
||||
super = makeTerm <$> token Super <*> (Java.Syntax.WildcardBoundSuper <$> 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))
|
||||
|
||||
block :: Assignment
|
||||
block :: Assignment Term
|
||||
block = makeTerm <$> symbol Block <*> children (manyTerm expression)
|
||||
|
||||
while :: Assignment
|
||||
while :: Assignment Term
|
||||
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)
|
||||
|
||||
switch :: Assignment
|
||||
switch :: Assignment Term
|
||||
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 :: Assignment Term
|
||||
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))
|
||||
|
||||
throw :: Assignment
|
||||
throw :: Assignment Term
|
||||
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]
|
||||
try :: Assignment Term
|
||||
try = symbol TryStatement *> children tryWithResources <|> makeTerm <$> symbol TryStatement <*> children (Statement.Try <$> term expression <*> (append <$> optional catches <*> optional finally))
|
||||
|
||||
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)
|
||||
|
||||
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)
|
||||
where
|
||||
forInit = symbol ForInit *> children (term expression)
|
||||
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)
|
||||
where variable modifiers type' variableDeclaratorId = makeTerm1 (Java.Syntax.Variable modifiers type' variableDeclaratorId)
|
||||
|
||||
-- TODO: instanceOf
|
||||
binary :: Assignment
|
||||
binary = makeTerm' <$> symbol BinaryExpression <*> children (infixTerm expression expression
|
||||
assert :: Assignment Term
|
||||
assert = makeTerm <$> symbol Grammar.AssertStatement <*> children (Java.Syntax.AssertStatement <$> term expression <*> optional (term expression))
|
||||
|
||||
binary :: Assignment Term
|
||||
binary = makeTerm' <$> symbol BinaryExpression <*> children (infixTerm expressionAndParens expressionAndParens
|
||||
[ (inject .) . Expression.LessThan <$ symbol AnonLAngle
|
||||
, (inject .) . Expression.GreaterThan <$ symbol AnonRAngle
|
||||
, (inject .) . Expression.Equal <$ symbol AnonEqualEqual
|
||||
@ -444,16 +509,20 @@ binary = makeTerm' <$> symbol BinaryExpression <*> children (infixTerm expressio
|
||||
, (inject .) . Expression.DividedBy <$ symbol AnonSlash
|
||||
, (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.
|
||||
infixTerm :: Assignment
|
||||
-> Assignment
|
||||
-> [Assignment.Assignment [] Grammar (Term -> Term -> Sum Syntax Term)]
|
||||
-> Assignment.Assignment [] Grammar (Sum Syntax Term)
|
||||
infixTerm :: Assignment Term
|
||||
-> Assignment Term
|
||||
-> [Assignment (Term -> Term -> Sum Syntax Term)]
|
||||
-> Assignment (Sum Syntax Term)
|
||||
infixTerm = infixContext comment
|
||||
|
||||
assignment' :: Assignment
|
||||
assignment' :: Assignment Term
|
||||
assignment' = makeTerm' <$> symbol AssignmentExpression <*> children (infixTerm lhs expression
|
||||
[ (inject .) . Statement.Assignment [] <$ symbol AnonEqual
|
||||
, assign Expression.Plus <$ symbol AnonPlusEqual
|
||||
@ -479,7 +548,7 @@ data UnaryType
|
||||
| UBang
|
||||
| UTilde
|
||||
|
||||
unary :: Assignment
|
||||
unary :: Assignment Term
|
||||
unary = make <$> symbol UnaryExpression <*> children ((,) <$> operator <*> term expression)
|
||||
where
|
||||
make _ (UPlus, operand) = operand
|
||||
@ -491,36 +560,37 @@ unary = make <$> symbol UnaryExpression <*> children ((,) <$> operator <*> term
|
||||
<|> token AnonBang $> UBang
|
||||
<|> token AnonTilde $> UTilde
|
||||
|
||||
update :: Assignment
|
||||
update :: Assignment Term
|
||||
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 :: Assignment Term
|
||||
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)
|
||||
|
||||
classInstance :: Assignment
|
||||
classInstance :: Assignment Term
|
||||
classInstance = makeTerm <$> symbol ClassInstanceCreationExpression <*> children unqualified
|
||||
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)
|
||||
|
||||
super :: Assignment
|
||||
super :: Assignment Term
|
||||
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
|
||||
|
||||
constructorDeclaration :: Assignment
|
||||
constructorDeclaration :: Assignment Term
|
||||
constructorDeclaration = makeTerm <$> symbol ConstructorDeclaration <*> children (
|
||||
constructor <$> manyTerm modifier <*> constructorDeclarator <*> (throws <|> pure []) <*> constructorBody)
|
||||
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
|
||||
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)
|
||||
where
|
||||
typeParam = makeTerm <$> symbol Grammar.TypeParameter <*> children (Java.Syntax.TypeParameter <$> manyTerm annotation <*> term identifier <*> (typeBound <|> pure []))
|
||||
typeBound = symbol TypeBound *> children (manyTerm type')
|
||||
|
||||
annotation :: Assignment
|
||||
|
||||
annotation :: Assignment Term
|
||||
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))
|
||||
@ -543,28 +614,33 @@ annotation = makeTerm <$> symbol NormalAnnotation <*> children (Java.Syntax.Anno
|
||||
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'))
|
||||
throws :: Assignment [Term]
|
||||
throws = symbol Throws *> children (symbol ExceptionTypeList *> children (manyTerm type'))
|
||||
|
||||
formalParameters :: Assignment.Assignment [] Grammar [Term]
|
||||
formalParameters :: Assignment [Term]
|
||||
formalParameters = manyTerm (parameter <|> spreadParameter)
|
||||
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'))
|
||||
|
||||
castExpression :: Assignment
|
||||
castExpression :: Assignment Term
|
||||
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')
|
||||
|
||||
spreadParameter :: Assignment
|
||||
spreadParameter :: Assignment Term
|
||||
spreadParameter = makeTerm <$> symbol Grammar.SpreadParameter <*> children (Java.Syntax.SpreadParameter <$> (makeSingleDecl <$> manyTerm modifier <*> type' <*> variableDeclarator))
|
||||
where
|
||||
variableDeclarator = symbol VariableDeclarator *> children ((,) <$> variableDeclaratorId <*> optional expression)
|
||||
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)
|
||||
|
||||
arrayAccess :: Assignment
|
||||
arrayAccess :: Assignment Term
|
||||
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)
|
||||
|
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE DeriveAnyClass #-}
|
||||
{-# LANGUAGE DeriveAnyClass, DuplicateRecordFields #-}
|
||||
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
|
||||
module Language.Java.Syntax where
|
||||
|
||||
@ -68,7 +68,7 @@ instance Show1 Synchronized where liftShowsPrec = genericLiftShowsPrec
|
||||
-- TODO: Implement Eval instance for Synchronized
|
||||
instance Evaluatable Synchronized
|
||||
|
||||
data New a = New { newType :: !a, newArgs :: ![a] }
|
||||
data New a = New { newType :: !a, newArgs :: ![a], newClassBody :: Maybe a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 New where liftEq = genericLiftEq
|
||||
@ -139,6 +139,26 @@ instance Show1 GenericType where liftShowsPrec = genericLiftShowsPrec
|
||||
-- TODO: Implement Eval instance for GenericType
|
||||
instance Evaluatable GenericType
|
||||
|
||||
data AnnotatedType a = AnnotatedType { annotationes :: [a], annotatedType :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 AnnotatedType where liftEq = genericLiftEq
|
||||
instance Ord1 AnnotatedType where liftCompare = genericLiftCompare
|
||||
instance Show1 AnnotatedType where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for AnnotatedType
|
||||
instance Evaluatable AnnotatedType
|
||||
|
||||
newtype CatchType a = CatchType { types :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 CatchType where liftEq = genericLiftEq
|
||||
instance Ord1 CatchType where liftCompare = genericLiftCompare
|
||||
instance Show1 CatchType where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for CatchType
|
||||
instance Evaluatable CatchType
|
||||
|
||||
data TypeWithModifiers a = TypeWithModifiers [a] a
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
@ -178,3 +198,126 @@ instance Show1 SpreadParameter where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for SpreadParameter
|
||||
instance Evaluatable SpreadParameter
|
||||
|
||||
newtype StaticInitializer a = StaticInitializer { staticInitializerBlock :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
|
||||
instance Eq1 StaticInitializer where liftEq = genericLiftEq
|
||||
instance Ord1 StaticInitializer where liftCompare = genericLiftCompare
|
||||
instance Show1 StaticInitializer where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable StaticInitializer
|
||||
|
||||
data MethodReference a = MethodReference { methodReferenceType :: !a, methodReferenceTypeArgs :: ![a], methodReferenceIdentifier :: !a}
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 MethodReference where liftEq = genericLiftEq
|
||||
instance Ord1 MethodReference where liftCompare = genericLiftCompare
|
||||
instance Show1 MethodReference where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for TypeWithModifiers
|
||||
instance Evaluatable MethodReference
|
||||
|
||||
data NewKeyword a = NewKeyword
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 NewKeyword where liftEq = genericLiftEq
|
||||
instance Ord1 NewKeyword where liftCompare = genericLiftCompare
|
||||
instance Show1 NewKeyword where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for TypeWithModifiers
|
||||
instance Evaluatable NewKeyword
|
||||
|
||||
data Lambda a = Lambda { lambdaParams :: ![a], lambdaBody :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 Lambda where liftEq = genericLiftEq
|
||||
instance Ord1 Lambda where liftCompare = genericLiftCompare
|
||||
instance Show1 Lambda where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable Lambda
|
||||
|
||||
newtype LambdaBody a = LambdaBody { lambdaBodyExpression :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 LambdaBody where liftEq = genericLiftEq
|
||||
instance Ord1 LambdaBody where liftCompare = genericLiftCompare
|
||||
instance Show1 LambdaBody where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable LambdaBody
|
||||
|
||||
data ArrayCreationExpression a = ArrayCreationExpression { arrayCreationExpressionType :: !a, arrayCreationExpressionDims :: ![a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 ArrayCreationExpression where liftEq = genericLiftEq
|
||||
instance Ord1 ArrayCreationExpression where liftCompare = genericLiftCompare
|
||||
instance Show1 ArrayCreationExpression where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable ArrayCreationExpression
|
||||
|
||||
data DimsExpr a = DimsExpr { dimsExprAnnotation :: ![a], dimsExprExpression :: ![a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 DimsExpr where liftEq = genericLiftEq
|
||||
instance Ord1 DimsExpr where liftCompare = genericLiftCompare
|
||||
instance Show1 DimsExpr where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable DimsExpr
|
||||
|
||||
newtype ClassBody a = ClassBody { classBodyExpression :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 ClassBody where liftEq = genericLiftEq
|
||||
instance Ord1 ClassBody where liftCompare = genericLiftCompare
|
||||
instance Show1 ClassBody where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable ClassBody
|
||||
|
||||
newtype ClassLiteral a = ClassLiteral { classLiteralType :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 ClassLiteral where liftEq = genericLiftEq
|
||||
instance Ord1 ClassLiteral where liftCompare = genericLiftCompare
|
||||
instance Show1 ClassLiteral where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable ClassLiteral
|
||||
|
||||
data TryWithResources a = TryWithResources { tryResources :: ![a], tryBody :: !a, tryCatch :: ![a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 TryWithResources where liftEq = genericLiftEq
|
||||
instance Ord1 TryWithResources where liftCompare = genericLiftCompare
|
||||
instance Show1 TryWithResources where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for TryWithResources
|
||||
instance Evaluatable TryWithResources
|
||||
|
||||
data AssertStatement a = AssertStatement { assertLHS :: !a, assertRHS :: !(Maybe a) }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 AssertStatement where liftEq = genericLiftEq
|
||||
instance Ord1 AssertStatement where liftCompare = genericLiftCompare
|
||||
instance Show1 AssertStatement where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for AssertStatement
|
||||
instance Evaluatable AssertStatement
|
||||
|
||||
newtype DefaultValue a = DefaultValue { defaultValueElement :: a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 DefaultValue where liftEq = genericLiftEq
|
||||
instance Ord1 DefaultValue where liftCompare = genericLiftCompare
|
||||
instance Show1 DefaultValue where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable DefaultValue
|
||||
|
||||
data AnnotationTypeElement a = AnnotationTypeElement { modifiers :: ![a], annotationType :: a, identifier :: !a, dims :: ![a], defaultValue :: !a }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable)
|
||||
|
||||
instance Eq1 AnnotationTypeElement where liftEq = genericLiftEq
|
||||
instance Ord1 AnnotationTypeElement where liftCompare = genericLiftCompare
|
||||
instance Show1 AnnotationTypeElement where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Implement Eval instance for AnnotationTypeElement
|
||||
instance Evaluatable AnnotationTypeElement
|
||||
|
@ -753,8 +753,8 @@ enumAssignment :: Assignment Term
|
||||
enumAssignment = makeTerm <$> symbol Grammar.EnumAssignment <*> children (Statement.Assignment [] <$> term propertyName <*> term expression)
|
||||
|
||||
interfaceDeclaration :: Assignment Term
|
||||
interfaceDeclaration = makeInterfaceDecl <$> symbol Grammar.InterfaceDeclaration <*> children ((,,,) <$> term identifier <*> (term typeParameters <|> emptyTerm) <*> (term extendsClause <|> emptyTerm) <*> term objectType)
|
||||
where makeInterfaceDecl loc (identifier, typeParams, clause, objectType) = makeTerm loc (Declaration.InterfaceDeclaration [typeParams, clause] identifier objectType)
|
||||
interfaceDeclaration = makeInterfaceDecl <$> symbol Grammar.InterfaceDeclaration <*> children ((,,,) <$> term identifier <*> (term typeParameters <|> emptyTerm) <*> optional (term extendsClause) <*> term objectType)
|
||||
where makeInterfaceDecl loc (identifier, typeParams, clause, objectType) = makeTerm loc (Declaration.InterfaceDeclaration [typeParams] identifier (toList clause) objectType)
|
||||
|
||||
ambientDeclaration :: Assignment Term
|
||||
ambientDeclaration = makeTerm <$> symbol Grammar.AmbientDeclaration <*> children (TypeScript.Syntax.AmbientDeclaration <$> term (choice [declaration, statementBlock]))
|
||||
|
5
test/fixtures/java/classLiteral.java
vendored
Normal file
5
test/fixtures/java/classLiteral.java
vendored
Normal file
@ -0,0 +1,5 @@
|
||||
class Dino {
|
||||
void normalError() {
|
||||
error(TestException.class);
|
||||
}
|
||||
}
|
7
test/fixtures/java/corpus/assertStatement.java
vendored
Normal file
7
test/fixtures/java/corpus/assertStatement.java
vendored
Normal file
@ -0,0 +1,7 @@
|
||||
class Dino {
|
||||
void fn() {
|
||||
for (File file : snap.index()) {
|
||||
assert oldFile == null;
|
||||
}
|
||||
}
|
||||
}
|
5
test/fixtures/java/corpus/assertStringLiteral.java
vendored
Normal file
5
test/fixtures/java/corpus/assertStringLiteral.java
vendored
Normal file
@ -0,0 +1,5 @@
|
||||
class Dino {
|
||||
void hi() {
|
||||
assert failure : "expecting non null";
|
||||
}
|
||||
}
|
6
test/fixtures/java/corpus/classBody.java
vendored
Normal file
6
test/fixtures/java/corpus/classBody.java
vendored
Normal file
@ -0,0 +1,6 @@
|
||||
class Dino {
|
||||
public void dispose() {
|
||||
Test.flat(new Function<Integer>() {
|
||||
});
|
||||
}
|
||||
}
|
5
test/fixtures/java/corpus/lambda.java
vendored
Normal file
5
test/fixtures/java/corpus/lambda.java
vendored
Normal file
@ -0,0 +1,5 @@
|
||||
class LambdaTest {
|
||||
void singleton() {
|
||||
version -> create;
|
||||
}
|
||||
}
|
5
test/fixtures/java/corpus/member-access.java
vendored
Normal file
5
test/fixtures/java/corpus/member-access.java
vendored
Normal file
@ -0,0 +1,5 @@
|
||||
class Natural {
|
||||
int compare(Object a, Object b) {
|
||||
(a).compareTo(b);
|
||||
}
|
||||
}
|
11
test/fixtures/java/corpus/methodReference.java
vendored
Normal file
11
test/fixtures/java/corpus/methodReference.java
vendored
Normal file
@ -0,0 +1,11 @@
|
||||
class TermsSetQueryBuilder {
|
||||
void Terms() {
|
||||
min = read(Script::new);
|
||||
}
|
||||
}
|
||||
|
||||
class TermsSetQueryBuilder {
|
||||
void Terms() {
|
||||
min = read(Script::yodawg);
|
||||
}
|
||||
}
|
3
test/fixtures/java/corpus/normalInterfaceDeclaration.java
vendored
Normal file
3
test/fixtures/java/corpus/normalInterfaceDeclaration.java
vendored
Normal file
@ -0,0 +1,3 @@
|
||||
@interface TerminationHandle {
|
||||
Bar foo = 1;
|
||||
}
|
3
test/fixtures/java/corpus/scoped-identifier.java
vendored
Normal file
3
test/fixtures/java/corpus/scoped-identifier.java
vendored
Normal file
@ -0,0 +1,3 @@
|
||||
static final class EventLoopWorker extends Scheduler.Worker {
|
||||
|
||||
}
|
6
test/fixtures/java/corpus/tryWithResourcesStatement.java
vendored
Normal file
6
test/fixtures/java/corpus/tryWithResourcesStatement.java
vendored
Normal file
@ -0,0 +1,6 @@
|
||||
class Dino {
|
||||
void hi() {
|
||||
try (CustomAnalyzer analyzer = new CustomAnalyzer()){
|
||||
}
|
||||
}
|
||||
}
|
5
test/fixtures/java/corpus/type-argument.java
vendored
Normal file
5
test/fixtures/java/corpus/type-argument.java
vendored
Normal file
@ -0,0 +1,5 @@
|
||||
class Dinosaur {
|
||||
void apply() {
|
||||
(T1)a[0];
|
||||
}
|
||||
}
|
@ -22,7 +22,6 @@
|
||||
{-(Identifier)-}
|
||||
{-(Empty)-})-})
|
||||
->(InterfaceDeclaration
|
||||
{+(Empty)+}
|
||||
{+(Empty)+}
|
||||
{+(Identifier)+}
|
||||
{+(ObjectType)+}) })
|
||||
@ -63,7 +62,6 @@
|
||||
{-(Identifier)-}
|
||||
{-(Empty)-})-})-}
|
||||
{-(InterfaceDeclaration
|
||||
{-(Empty)-}
|
||||
{-(Empty)-}
|
||||
{-(Identifier)-}
|
||||
{-(ObjectType
|
||||
@ -74,7 +72,6 @@
|
||||
{-(PredefinedType)-})-}
|
||||
{-(Identifier)-})-})-})-}
|
||||
{-(InterfaceDeclaration
|
||||
{-(Empty)-}
|
||||
{-(Empty)-}
|
||||
{-(Identifier)-}
|
||||
{-(ObjectType
|
||||
|
@ -53,7 +53,6 @@
|
||||
{+(Identifier)+}
|
||||
{+(Empty)+})+})+}
|
||||
{+(InterfaceDeclaration
|
||||
{+(Empty)+}
|
||||
{+(Empty)+}
|
||||
{+(Identifier)+}
|
||||
{+(ObjectType
|
||||
@ -64,7 +63,6 @@
|
||||
{+(PredefinedType)+})+}
|
||||
{+(Identifier)+})+})+})+}
|
||||
{+(InterfaceDeclaration
|
||||
{+(Empty)+}
|
||||
{+(Empty)+}
|
||||
{+(Identifier)+}
|
||||
{+(ObjectType
|
||||
@ -95,7 +93,6 @@
|
||||
{-(Statements)-})-})-}
|
||||
{-(AmbientDeclaration
|
||||
{-(InterfaceDeclaration
|
||||
{-(Empty)-}
|
||||
{-(Empty)-}
|
||||
{-(Identifier)-}
|
||||
{-(ObjectType)-})-})-}
|
||||
|
@ -53,7 +53,6 @@
|
||||
(Identifier)
|
||||
(Empty)))
|
||||
(InterfaceDeclaration
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(ObjectType
|
||||
@ -64,7 +63,6 @@
|
||||
(PredefinedType))
|
||||
(Identifier))))
|
||||
(InterfaceDeclaration
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(ObjectType
|
||||
|
@ -8,7 +8,6 @@
|
||||
(Statements)))
|
||||
(AmbientDeclaration
|
||||
(InterfaceDeclaration
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(ObjectType)))
|
||||
|
@ -1,12 +1,11 @@
|
||||
(Statements
|
||||
(InterfaceDeclaration
|
||||
{+(Empty)+}
|
||||
{-(TypeParameters
|
||||
{-(TypeParameter
|
||||
{-(Identifier)-}
|
||||
{-(Empty)-}
|
||||
{-(Empty)-})-})-}
|
||||
(Empty)
|
||||
{+(Empty)+}
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(ObjectType
|
||||
|
@ -5,7 +5,6 @@
|
||||
{+(Identifier)+}
|
||||
{+(Empty)+}
|
||||
{+(Empty)+})+})+}
|
||||
(Empty)
|
||||
{-(Empty)-}
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
|
@ -5,7 +5,6 @@
|
||||
(Identifier)
|
||||
(Empty)
|
||||
(Empty)))
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(ObjectType
|
||||
(PropertySignature
|
||||
|
@ -1,6 +1,5 @@
|
||||
(Statements
|
||||
(InterfaceDeclaration
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(ObjectType
|
||||
|
2
vendor/haskell-tree-sitter
vendored
2
vendor/haskell-tree-sitter
vendored
@ -1 +1 @@
|
||||
Subproject commit 9ada8cc48be1a25b971aca1a49c0963897c09d7c
|
||||
Subproject commit 4a3e8b8bc08a10a0ec5b5d503a92757970672b2a
|
Loading…
Reference in New Issue
Block a user