Skip to content

Commit

Permalink
Fixing algorithm Upath when p = p1*
Browse files Browse the repository at this point in the history
  • Loading branch information
sqmedeiros committed May 31, 2019
1 parent adcfb53 commit 20e31eb
Show file tree
Hide file tree
Showing 3 changed files with 203 additions and 2 deletions.
7 changes: 5 additions & 2 deletions recovery.lua
Original file line number Diff line number Diff line change
Expand Up @@ -218,8 +218,11 @@ local function annotateUPathAux (g, p, seq, afterU, flw)
else
return newNode(p, p1, p2)
end
elseif (p.tag == 'star' or p.tag == 'opt' or p.tag == 'plus') and disjoint(calcfirst(g, p.p1), flw) then
local newp = annotateUPathAux(g, p.p1, false, afterU, flw)
--elseif (p.tag == 'star' or p.tag == 'opt' or p.tag == 'plus') and disjoint(calcfirst(g, p.p1), flw) then
--local newp = annotateUPathAux(g, p.p1, false, afterU, flw)
elseif (p.tag == 'star' or p.tag == 'opt' or p.tag == 'plus') then
local flagDisjoint = disjoint(calcfirst(g, p.p1), flw)
local newp = annotateUPathAux(g, p.p1, false, flagDisjoint and afterU, flw)
if p.tag == 'star' or p.tag == 'opt' then
return newNode(p, newp)
else --plus
Expand Down
198 changes: 198 additions & 0 deletions test/java18/generatedJavaUPath2.lua
Original file line number Diff line number Diff line change
@@ -0,0 +1,198 @@
local m = require 'init'
local errinfo = require 'syntax_errors'
local pretty = require 'pretty'
local coder = require 'coder'
local first = require 'first'
local recovery = require 'recovery'
local lfs = require'lfs'
local re = require'relabel'
local util = require'util'

-- Added 68 labels
-- Did not have to remove rules manually

g = [[
compilation <- SKIP compilationUnit !.
basicType <- 'byte' / 'short' / 'int' / 'long' / 'char' / 'float' / 'double' / 'boolean'
primitiveType <- annotation* basicType
referenceType <- primitiveType dim+ / classType dim*
classType <- annotation* Identifier typeArguments? ('.' annotation* Identifier typeArguments?)*
type <- primitiveType / classType
arrayType <- primitiveType dim+ / classType dim+
typeVariable <- annotation* Identifier
dim <- annotation* '[' ']'
typeParameter <- typeParameterModifier* Identifier typeBound?
typeParameterModifier <- annotation
typeBound <- 'extends' (classType additionalBound* / typeVariable)
additionalBound <- 'and' classType^Err_001
typeArguments <- '<' typeArgumentList '>'
typeArgumentList <- typeArgument (',' typeArgument)*
typeArgument <- referenceType / wildcard
wildcard <- annotation* '?' wildcardBounds?
wildcardBounds <- 'extends' referenceType^Err_002 / 'super' referenceType^Err_003
qualIdent <- Identifier ('.' Identifier)*
compilationUnit <- packageDeclaration? importDeclaration* typeDeclaration*
packageDeclaration <- packageModifier* 'package' Identifier^Err_004 ('.' Identifier^Err_005)* ';'^Err_006
packageModifier <- annotation
importDeclaration <- 'import' 'static'? qualIdent^Err_007 ('.' '*'^Err_008)? ';'^Err_009 / ';'
typeDeclaration <- classDeclaration / interfaceDeclaration / ';'
classDeclaration <- normalClassDeclaration / enumDeclaration
normalClassDeclaration <- classModifier* 'class' Identifier typeParameters? superclass? superinterfaces? classBody
classModifier <- annotation / 'public' / 'protected' / 'private' / 'abstract' / 'static' / 'final' / 'strictfp'
typeParameters <- '<' typeParameterList '>'
typeParameterList <- typeParameter (',' typeParameter)*
superclass <- 'extends' classType
superinterfaces <- 'implements' interfaceTypeList^Err_010
interfaceTypeList <- classType (',' classType)*
classBody <- '{' classBodyDeclaration* '}'
classBodyDeclaration <- classMemberDeclaration / instanceInitializer / staticInitializer / constructorDeclaration
classMemberDeclaration <- fieldDeclaration / methodDeclaration / classDeclaration / interfaceDeclaration / ';'
fieldDeclaration <- fieldModifier* unannType variableDeclaratorList ';'
variableDeclaratorList <- variableDeclarator (',' variableDeclarator)*
variableDeclarator <- variableDeclaratorId ('=' !'=' variableInitializer)?
variableDeclaratorId <- Identifier dim*
variableInitializer <- expression / arrayInitializer
unannClassType <- Identifier typeArguments? ('.' annotation* Identifier typeArguments?)*
unannType <- basicType dim* / unannClassType dim*
fieldModifier <- annotation / 'public' / 'protected' / 'private' / 'static' / 'final' / 'transient' / 'volatile'
methodDeclaration <- methodModifier* methodHeader methodBody
methodHeader <- result methodDeclarator throws? / typeParameters annotation* result methodDeclarator throws?
methodDeclarator <- Identifier '(' formalParameterList? ')' dim*
formalParameterList <- (receiverParameter / formalParameter) (',' formalParameter)*
formalParameter <- variableModifier* unannType variableDeclaratorId / variableModifier* unannType annotation* '...' variableDeclaratorId^Err_011 !','
variableModifier <- annotation / 'final'
receiverParameter <- variableModifier* unannType (Identifier '.')? 'this'
result <- unannType / 'void'
methodModifier <- annotation / 'public' / 'protected' / 'private' / 'abstract' / 'static' / 'final' / 'synchronized' / 'native' / 'stictfp'
throws <- 'throws' exceptionTypeList^Err_012
exceptionTypeList <- exceptionType^Err_013 (',' exceptionType^Err_014)*
exceptionType <- (classType / typeVariable)^Err_015
methodBody <- block / ';'
instanceInitializer <- block
staticInitializer <- 'static' block
constructorDeclaration <- constructorModifier* constructorDeclarator throws? constructorBody
constructorDeclarator <- typeParameters? Identifier '(' formalParameterList? ')'
constructorModifier <- annotation / 'public' / 'protected' / 'private'
constructorBody <- '{' explicitConstructorInvocation? blockStatements? '}'
explicitConstructorInvocation <- typeArguments? 'this' arguments ';' / typeArguments? 'super' arguments ';' / primary '.' typeArguments? 'super' arguments ';' / qualIdent '.' typeArguments? 'super' arguments ';'
enumDeclaration <- classModifier* 'enum' Identifier^Err_016 superinterfaces? enumBody^Err_017
enumBody <- '{'^Err_018 enumConstantList? ','? enumBodyDeclarations? '}'^Err_019
enumConstantList <- enumConstant (',' enumConstant)*
enumConstant <- enumConstantModifier* Identifier arguments? classBody?
enumConstantModifier <- annotation
enumBodyDeclarations <- ';' classBodyDeclaration*
interfaceDeclaration <- normalInterfaceDeclaration / annotationTypeDeclaration
normalInterfaceDeclaration <- interfaceModifier* 'interface' Identifier typeParameters? extendsInterfaces? interfaceBody
interfaceModifier <- annotation / 'public' / 'protected' / 'private' / 'abstract' / 'static' / 'strictfp'
extendsInterfaces <- 'extends' interfaceTypeList
interfaceBody <- '{' interfaceMemberDeclaration* '}'
interfaceMemberDeclaration <- constantDeclaration / interfaceMethodDeclaration / classDeclaration / interfaceDeclaration / ';'
constantDeclaration <- constantModifier* unannType variableDeclaratorList ';'
constantModifier <- annotation / 'public' / 'static' / 'final'
interfaceMethodDeclaration <- interfaceMethodModifier* methodHeader methodBody
interfaceMethodModifier <- annotation / 'public' / 'abstract' / 'default' / 'static' / 'strictfp'
annotationTypeDeclaration <- interfaceModifier* '@' 'interface' Identifier annotationTypeBody
annotationTypeBody <- '{' annotationTypeMemberDeclaration* '}'
annotationTypeMemberDeclaration <- annotationTypeElementDeclaration / constantDeclaration / classDeclaration / interfaceDeclaration / ';'
annotationTypeElementDeclaration <- annotationTypeElementModifier* unannType Identifier '(' ')' dim* defaultValue? ';'
annotationTypeElementModifier <- annotation / 'public' / 'abstract'
defaultValue <- 'default' elementValue
annotation <- '@' (normalAnnotation / singleElementAnnotation / markerAnnotation)
normalAnnotation <- qualIdent '(' elementValuePairList* ')'
elementValuePairList <- elementValuePair (',' elementValuePair)*
elementValuePair <- Identifier '=' !'=' elementValue
elementValue <- conditionalExpression / elementValueArrayInitializer / annotation
elementValueArrayInitializer <- '{' elementValueList? ','? '}'
elementValueList <- elementValue (',' elementValue)*
markerAnnotation <- qualIdent
singleElementAnnotation <- qualIdent '(' elementValue ')'
arrayInitializer <- '{' variableInitializerList? ','? '}'
variableInitializerList <- variableInitializer (',' variableInitializer)*
block <- '{' blockStatements? '}'
blockStatements <- blockStatement blockStatement*
blockStatement <- localVariableDeclarationStatement / classDeclaration / statement
localVariableDeclarationStatement <- localVariableDeclaration ';'
localVariableDeclaration <- variableModifier* unannType variableDeclaratorList
statement <- block / 'if' parExpression^Err_020 statement^Err_021 ('else' statement^Err_022)? / basicForStatement / enhancedForStatement / 'while' parExpression statement / 'do' statement^Err_023 'while'^Err_024 parExpression^Err_025 ';'^Err_026 / tryStatement / 'switch' parExpression^Err_027 switchBlock^Err_028 / 'synchronized' parExpression block / 'return' expression? ';'^Err_029 / 'throw' expression^Err_030 ';'^Err_031 / 'break' Identifier? ';'^Err_032 / 'continue' Identifier? ';'^Err_033 / 'assert' expression^Err_034 (':' expression^Err_035)? ';'^Err_036 / ';' / statementExpression ';' / Identifier ':' statement
statementExpression <- assignment / ('++' / '--') (primary / qualIdent) / (primary / qualIdent) ('++' / '--') / primary
switchBlock <- '{'^Err_037 switchBlockStatementGroup* switchLabel* '}'^Err_038
switchBlockStatementGroup <- switchLabels blockStatements
switchLabels <- switchLabel switchLabel*
switchLabel <- 'case' (constantExpression / enumConstantName)^Err_039 ':'^Err_040 / 'default' ':'
enumConstantName <- Identifier^Err_041
basicForStatement <- 'for' '(' forInit? ';' expression? ';' forUpdate? ')' statement
forInit <- localVariableDeclaration / statementExpressionList
forUpdate <- statementExpressionList
statementExpressionList <- statementExpression (',' statementExpression)*
enhancedForStatement <- 'for' '(' variableModifier* unannType variableDeclaratorId ':' expression ')' statement
tryStatement <- 'try' (block (catchClause* finally / catchClause+)^Err_042 / resourceSpecification block^Err_043 catchClause* finally?)^Err_044
catchClause <- 'catch' '('^Err_045 catchFormalParameter^Err_046 ')'^Err_047 block^Err_048
catchFormalParameter <- variableModifier* catchType^Err_049 variableDeclaratorId^Err_050
catchType <- unannClassType^Err_051 ('|' ![=|] classType^Err_052)*
finally <- 'finally' block^Err_053
resourceSpecification <- '('^Err_054 resourceList^Err_055 ';'? ')'^Err_056
resourceList <- resource^Err_057 (',' resource^Err_058)*
resource <- variableModifier* unannType^Err_059 variableDeclaratorId^Err_060 '='^Err_061 !'=' expression^Err_062
expression <- lambdaExpression / assignmentExpression
primary <- primaryBase primaryRest*
primaryBase <- 'this' / Literal / parExpression / 'super' ('.' typeArguments? Identifier arguments / '.' Identifier / '::' typeArguments? Identifier) / 'new' (classCreator / arrayCreator) / qualIdent ('[' expression ']' / arguments / '.' ('this' / 'new' classCreator / typeArguments Identifier arguments / 'super' '.' typeArguments? Identifier arguments / 'super' '.' Identifier / 'super' '::' typeArguments? Identifier arguments) / ('[' ']')* '.' 'class' / '::' typeArguments? Identifier) / 'void' '.' 'class' / basicType ('[' ']')* '.' 'class' / referenceType '::' typeArguments? 'new' / arrayType '::' 'new'
primaryRest <- '.' (typeArguments? Identifier arguments / Identifier / 'new' classCreator) / '[' expression ']' / '::' typeArguments? Identifier
parExpression <- '(' expression ')'
classCreator <- typeArguments? annotation* classTypeWithDiamond arguments classBody?
classTypeWithDiamond <- annotation* Identifier typeArgumentsOrDiamond? ('.' annotation* Identifier typeArgumentsOrDiamond?)*
typeArgumentsOrDiamond <- typeArguments / '<' '>' !'.'
arrayCreator <- type dimExpr+ dim* / type dim+ arrayInitializer
dimExpr <- annotation* '[' expression ']'
arguments <- '(' argumentList? ')'
argumentList <- expression (',' expression)*
unaryExpression <- ('++' / '--') (primary / qualIdent) / '+' ![=+] unaryExpression^Err_063 / '-' ![-=>] unaryExpression^Err_064 / unaryExpressionNotPlusMinus
unaryExpressionNotPlusMinus <- '~' unaryExpression^Err_065 / '!' ![=&] unaryExpression^Err_066 / castExpression / (primary / qualIdent) ('++' / '--')?
castExpression <- '(' primitiveType ')' unaryExpression / '(' referenceType additionalBound* ')' lambdaExpression / '(' referenceType additionalBound* ')' unaryExpressionNotPlusMinus
infixExpression <- unaryExpression (InfixOperator unaryExpression^Err_067 / 'instanceof' referenceType^Err_068)*
InfixOperator <- '||' / '&&' / '|' ![=|] / '^' ![=] / '&' ![=&] / '==' / '!=' / '<' ![=<] / '>' ![=>] / '<=' / '>=' / '<<' ![=] / '>>' ![=>] / '>>>' ![=] / '+' ![=+] / '-' ![-=>] / '*' ![=] / '/' ![=] / '%' ![=]
conditionalExpression <- infixExpression ('query' expression^Err_069 ':'^Err_070 expression^Err_071)*
assignmentExpression <- assignment / conditionalExpression
assignment <- leftHandSide AssignmentOperator expression^Err_072
leftHandSide <- primary / qualIdent
AssignmentOperator <- '=' ![=] / '*=' / '/=' / '%=' / '+=' / '-=' / '<<=' / '>>=' / '>>>=' / '&=' / '^=' / '|='
lambdaExpression <- lambdaParameters '->' lambdaBody^Err_073
lambdaParameters <- Identifier / '(' formalParameterList? ')' / '(' inferredFormalParameterList ')'
inferredFormalParameterList <- Identifier (',' Identifier)*
lambdaBody <- (expression / block)^Err_074
constantExpression <- expression
Identifier <- !Keywords [a-zA-Z_] [a-zA-Z_$0-9]*
Keywords <- ('abstract' / 'assert' / 'boolean' / 'break' / 'byte' / 'case' / 'catch' / 'char' / 'class' / 'const' / 'continue' / 'default' / 'double' / 'do' / 'else' / 'enum' / 'extends' / 'false' / 'finally' / 'final' / 'float' / 'for' / 'goto' / 'if' / 'implements' / 'import' / 'interface' / 'int' / 'instanceof' / 'long' / 'native' / 'new' / 'null' / 'package' / 'private' / 'protected' / 'public' / 'return' / 'short' / 'static' / 'strictfp' / 'super' / 'switch' / 'synchronized' / 'this' / 'throws' / 'throw' / 'transient' / 'true' / 'try' / 'void' / 'volatile' / 'while') ![a-zA-Z_$0-9]
Literal <- FloatLiteral / IntegerLiteral / BooleanLiteral / CharLiteral / StringLiteral / NullLiteral
IntegerLiteral <- (HexNumeral / BinaryNumeral / OctalNumeral / DecimalNumeral) [lL]?
DecimalNumeral <- '0' / [1-9] ([_]* [0-9])*
HexNumeral <- ('0x' / '0X') HexDigits
OctalNumeral <- '0' ([_]* [0-7])+
BinaryNumeral <- ('0b' / '0B') [01] ([_]* [01])*
FloatLiteral <- HexaDecimalFloatingPointLiteral / DecimalFloatingPointLiteral
DecimalFloatingPointLiteral <- Digits '.' Digits? Exponent? [fFdD]? / '.' Digits Exponent? [fFdD]? / Digits Exponent [fFdD]? / Digits Exponent? [fFdD]
Exponent <- [eE] [-+]? Digits
HexaDecimalFloatingPointLiteral <- HexSignificand BinaryExponent [fFdD]?
HexSignificand <- ('0x' / '0X') HexDigits? '.' HexDigits / HexNumeral '.'?
HexDigits <- HexDigit ([_]* HexDigit)*
HexDigit <- [a-f] / [A-F] / [0-9]
BinaryExponent <- [pP] [-+]? Digits
Digits <- [0-9] ([_]* [0-9])*
BooleanLiteral <- 'true' / 'false'
CharLiteral <- "'" (%nl / !"'" .) "'"
StringLiteral <- '"' (%nl / !'"' .)* '"'
NullLiteral <- 'null'
COMMENT <- '//' (!%nl .)* / '/*' (!'*/' .)* '*/'
SPACE <- [
] / COMMENT
SKIP <- ([
] / COMMENT)*
]]

local g = m.match(g)
local p = coder.makeg(g, 'ast')

local dir = lfs.currentdir() .. '/test/java18/test/yes/'
util.testYes(dir, 'java', p)

local dir = lfs.currentdir() .. '/test/java18/test/no/'
util.testNo(dir, 'java', p)
Expand Down
Binary file modified test/titan/analysisRecovery.ods
Binary file not shown.

0 comments on commit 20e31eb

Please sign in to comment.