Skip to content

Commit

Permalink
Merge pull request #4568 from MDoerner/FixIllegalAnnotationInspection
Browse files Browse the repository at this point in the history
Fix illegal annotation inspection
  • Loading branch information
retailcoder committed Nov 29, 2018
2 parents 3a6aee5 + fbbe89e commit 0bda237
Show file tree
Hide file tree
Showing 11 changed files with 478 additions and 197 deletions.
Original file line number Diff line number Diff line change
Expand Up @@ -20,18 +20,11 @@ public IllegalAnnotationInspection(RubberduckParserState state)

protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
{
var illegalAnnotations = new List<IAnnotation>();

var userDeclarations = State.DeclarationFinder.AllUserDeclarations.ToList();
var identifierReferences = State.DeclarationFinder.AllIdentifierReferences().ToList();
var annotations = State.AllAnnotations;

illegalAnnotations.AddRange(UnboundAnnotations(annotations, userDeclarations, identifierReferences));
illegalAnnotations.AddRange(NonIdentifierAnnotationsOnIdentifiers(identifierReferences));
illegalAnnotations.AddRange(NonModuleAnnotationsOnModules(userDeclarations));
illegalAnnotations.AddRange(NonMemberAnnotationsOnMembers(userDeclarations));
illegalAnnotations.AddRange(NonVariableAnnotationsOnVariables(userDeclarations));
illegalAnnotations.AddRange(NonGeneralAnnotationsWhereOnlyGeneralAnnotationsBelong(userDeclarations));
var illegalAnnotations = UnboundAnnotations(annotations, userDeclarations, identifierReferences);

return illegalAnnotations.Select(annotation =>
new QualifiedContextInspectionResult(
Expand All @@ -50,64 +43,5 @@ private static ICollection<IAnnotation> UnboundAnnotations(IEnumerable<IAnnotati

return annotations.Where(annotation => !boundAnnotationsSelections.Contains(annotation.QualifiedSelection)).ToList();
}

private static ICollection<IAnnotation> NonIdentifierAnnotationsOnIdentifiers(IEnumerable<IdentifierReference> identifierReferences)
{
return identifierReferences
.SelectMany(reference => reference.Annotations)
.Where(annotation => !annotation.AnnotationType.HasFlag(AnnotationType.IdentifierAnnotation))
.ToList();
}

private static ICollection<IAnnotation> NonModuleAnnotationsOnModules(IEnumerable<Declaration> userDeclarations)
{
return userDeclarations
.Where(declaration => declaration.DeclarationType.HasFlag(DeclarationType.Module))
.SelectMany(moduleDeclaration => moduleDeclaration.Annotations)
.Where(annotation => !annotation.AnnotationType.HasFlag(AnnotationType.ModuleAnnotation))
.ToList();
}

private static ICollection<IAnnotation> NonMemberAnnotationsOnMembers(IEnumerable<Declaration> userDeclarations)
{
return userDeclarations
.Where(declaration => declaration.DeclarationType.HasFlag(DeclarationType.Member))
.SelectMany(member => member.Annotations)
.Where(annotation => !annotation.AnnotationType.HasFlag(AnnotationType.MemberAnnotation))
.ToList();
}

private static ICollection<IAnnotation> NonVariableAnnotationsOnVariables(IEnumerable<Declaration> userDeclarations)
{
return userDeclarations
.Where(declaration => VariableAnnotationDeclarationTypes.Contains(declaration.DeclarationType))
.SelectMany(declaration => declaration.Annotations)
.Where(annotation => !annotation.AnnotationType.HasFlag(AnnotationType.VariableAnnotation))
.ToList();
}

private static readonly HashSet<DeclarationType> VariableAnnotationDeclarationTypes = new HashSet<DeclarationType>()
{
DeclarationType.Variable,
DeclarationType.Control,
DeclarationType.Constant,
DeclarationType.Enumeration,
DeclarationType.EnumerationMember,
DeclarationType.UserDefinedType,
DeclarationType.UserDefinedType,
DeclarationType.UserDefinedTypeMember
};

private static ICollection<IAnnotation> NonGeneralAnnotationsWhereOnlyGeneralAnnotationsBelong(IEnumerable<Declaration> userDeclarations)
{
return userDeclarations
.Where(declaration => !declaration.DeclarationType.HasFlag(DeclarationType.Module)
&& !declaration.DeclarationType.HasFlag(DeclarationType.Member)
&& !VariableAnnotationDeclarationTypes.Contains(declaration.DeclarationType)
&& declaration.DeclarationType != DeclarationType.Project)
.SelectMany(member => member.Annotations)
.Where(annotation => !annotation.AnnotationType.HasFlag(AnnotationType.GeneralAnnotation))
.ToList();
}
}
}
Original file line number Diff line number Diff line change
@@ -1,16 +1,15 @@
using Rubberduck.Parsing.Symbols;
using Rubberduck.VBEditor;
using Rubberduck.VBEditor;
using System.Collections.Generic;
using System.Linq;
using Rubberduck.Parsing.VBA.DeclarationCaching;

namespace Rubberduck.Parsing.Annotations
{
public sealed class AnnotationService
public sealed class IdentifierAnnotationService
{
private readonly DeclarationFinder _declarationFinder;

public AnnotationService(DeclarationFinder declarationFinder)
public IdentifierAnnotationService(DeclarationFinder declarationFinder)
{
_declarationFinder = declarationFinder;
}
Expand All @@ -22,13 +21,15 @@ public IEnumerable<IAnnotation> FindAnnotations(QualifiedModuleName module, int
// VBE 1-based indexing
for (var currentLine = line - 1; currentLine >= 1; currentLine--)
{
//Identifier annotation sections end at the first line above without an identifier annotation.
if (!moduleAnnotations.Any(annotation => annotation.QualifiedSelection.Selection.StartLine <= currentLine
&& annotation.QualifiedSelection.Selection.EndLine >= currentLine))
&& annotation.QualifiedSelection.Selection.EndLine >= currentLine
&& annotation.AnnotationType.HasFlag(AnnotationType.IdentifierAnnotation)))
{
break;
}

var annotationsStartingOnCurrentLine = moduleAnnotations.Where(a => a.QualifiedSelection.Selection.StartLine == currentLine);
var annotationsStartingOnCurrentLine = moduleAnnotations.Where(a => a.QualifiedSelection.Selection.StartLine == currentLine && a.AnnotationType.HasFlag(AnnotationType.IdentifierAnnotation));

annotations.AddRange(annotationsStartingOnCurrentLine);
}
Expand Down
14 changes: 7 additions & 7 deletions Rubberduck.Parsing/Symbols/IdentifierReferenceResolver.cs
Original file line number Diff line number Diff line change
Expand Up @@ -23,7 +23,7 @@ public sealed class IdentifierReferenceResolver
private Declaration _currentParent;
private readonly BindingService _bindingService;
private readonly BoundExpressionVisitor _boundExpressionVisitor;
private readonly AnnotationService _annotationService;
private readonly IdentifierAnnotationService _identifierAnnotationService;
private static readonly Logger Logger = LogManager.GetCurrentClassLogger();

public IdentifierReferenceResolver(QualifiedModuleName qualifiedModuleName, DeclarationFinder finder)
Expand All @@ -44,8 +44,8 @@ public IdentifierReferenceResolver(QualifiedModuleName qualifiedModuleName, Decl
new DefaultBindingContext(_declarationFinder, typeBindingContext, procedurePointerBindingContext),
typeBindingContext,
procedurePointerBindingContext);
_annotationService = new AnnotationService(_declarationFinder);
_boundExpressionVisitor = new BoundExpressionVisitor(_annotationService);
_identifierAnnotationService = new IdentifierAnnotationService(_declarationFinder);
_boundExpressionVisitor = new BoundExpressionVisitor(_identifierAnnotationService);
}

public void SetCurrentScope()
Expand Down Expand Up @@ -153,7 +153,7 @@ private void ResolveLabel(ParserRuleContext context, string label)
identifier,
callee,
callSiteContext.GetSelection(),
_annotationService.FindAnnotations(_qualifiedModuleName, callSiteContext.GetSelection().StartLine));
_identifierAnnotationService.FindAnnotations(_qualifiedModuleName, callSiteContext.GetSelection().StartLine));
}
}

Expand Down Expand Up @@ -713,7 +713,7 @@ public void Resolve(VBAParser.RaiseEventStmtContext context)
identifier,
callee,
callSiteContext.GetSelection(),
_annotationService.FindAnnotations(_qualifiedModuleName, callSiteContext.GetSelection().StartLine));
_identifierAnnotationService.FindAnnotations(_qualifiedModuleName, callSiteContext.GetSelection().StartLine));
}
if (context.eventArgumentList() == null)
{
Expand Down Expand Up @@ -819,7 +819,7 @@ public void Resolve(VBAParser.DebugPrintStmtContext context)
context.debugPrint().debugModule().GetText(),
debugModule,
context.debugPrint().debugModule().GetSelection(),
_annotationService.FindAnnotations(_qualifiedModuleName, context.debugPrint().debugModule().GetSelection().StartLine));
_identifierAnnotationService.FindAnnotations(_qualifiedModuleName, context.debugPrint().debugModule().GetSelection().StartLine));
debugPrint.AddReference(
_qualifiedModuleName,
_currentScope,
Expand All @@ -828,7 +828,7 @@ public void Resolve(VBAParser.DebugPrintStmtContext context)
context.debugPrint().debugPrintSub().GetText(),
debugPrint,
context.debugPrint().debugPrintSub().GetSelection(),
_annotationService.FindAnnotations(_qualifiedModuleName, context.debugPrint().debugPrintSub().GetSelection().StartLine));
_identifierAnnotationService.FindAnnotations(_qualifiedModuleName, context.debugPrint().debugPrintSub().GetSelection().StartLine));
var outputList = context.outputList();
if (outputList != null)
{
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -22,7 +22,7 @@ public class DeclarationFinder
private static readonly Logger Logger = LogManager.GetCurrentClassLogger();

private readonly IHostApplication _hostApp;
private readonly AnnotationService _annotationService;
private readonly IdentifierAnnotationService _identifierAnnotationService;
private IDictionary<string, List<Declaration>> _declarationsByName;
private IDictionary<QualifiedModuleName, List<Declaration>> _declarations;
private readonly ConcurrentDictionary<QualifiedMemberName, ConcurrentBag<Declaration>> _newUndeclared;
Expand Down Expand Up @@ -68,7 +68,7 @@ private static QualifiedSelection GetGroupingKey(Declaration declaration)
_newUndeclared = new ConcurrentDictionary<QualifiedMemberName, ConcurrentBag<Declaration>>(new Dictionary<QualifiedMemberName, ConcurrentBag<Declaration>>());
_newUnresolved = new ConcurrentBag<UnboundMemberDeclaration>(new List<UnboundMemberDeclaration>());

_annotationService = new AnnotationService(this);
_identifierAnnotationService = new IdentifierAnnotationService(this);

var collectionConstructionActions = CollectionConstructionActions(declarations, annotations, unresolvedMemberDeclarations);
ExecuteCollectionConstructionActions(collectionConstructionActions);
Expand Down Expand Up @@ -804,7 +804,7 @@ public Declaration FindMemberEnclosingProcedure(Declaration enclosingProcedure,

public Declaration OnUndeclaredVariable(Declaration enclosingProcedure, string identifierName, ParserRuleContext context)
{
var annotations = _annotationService.FindAnnotations(enclosingProcedure.QualifiedName.QualifiedModuleName, context.Start.Line);
var annotations = _identifierAnnotationService.FindAnnotations(enclosingProcedure.QualifiedName.QualifiedModuleName, context.Start.Line);
var undeclaredLocal =
new Declaration(
new QualifiedMemberName(enclosingProcedure.QualifiedName.QualifiedModuleName, identifierName),
Expand Down Expand Up @@ -859,7 +859,7 @@ public void AddUnboundContext(Declaration parentDeclaration, VBAParser.LExpressi
}

var identifier = context.GetChild<VBAParser.UnrestrictedIdentifierContext>(0);
var annotations = _annotationService.FindAnnotations(parentDeclaration.QualifiedName.QualifiedModuleName, context.Start.Line);
var annotations = _identifierAnnotationService.FindAnnotations(parentDeclaration.QualifiedName.QualifiedModuleName, context.Start.Line);

var declaration = new UnboundMemberDeclaration(parentDeclaration, identifier,
(context is VBAParser.MemberAccessExprContext) ? (ParserRuleContext)context.children[0] : withExpression.Context,
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -159,12 +159,6 @@ protected void ResolveDeclarations(QualifiedModuleName module, IParseTree tree,
{
_state.AddDeclaration(createdDeclaration);
}

//This is a hack to deal with annotations on module level variables.
var memberAnnotations = declarationsListener.CreatedDeclarations
.SelectMany(declaration => declaration.Annotations)
.ToHashSet();
moduleDeclaration.RemoveAnnotations(memberAnnotations);
}
catch (Exception exception)
{
Expand Down Expand Up @@ -235,43 +229,25 @@ private static IEnumerable<IAnnotation> FindModuleAnnotations(IParseTree tree, I
return null;
}

var lastDeclarationsSectionLine = LastDeclarationsSectionLine(tree, annotations);
var potentialModuleAnnotations = annotations.Where(annotation =>
annotation.AnnotationType.HasFlag(AnnotationType.ModuleAnnotation));

var lastPossibleDeclarationsSectionLine = LastPossibleDeclarationsSectionLine(tree);

//There is no module body.
if (lastDeclarationsSectionLine == null)
if (lastPossibleDeclarationsSectionLine == null)
{
return annotations;
return potentialModuleAnnotations;
}

var lastPossibleModuleAnnotationLine = lastDeclarationsSectionLine.Value;
var moduleAnnotations = annotations.Where(annotation => annotation.QualifiedSelection.Selection.EndLine <= lastPossibleModuleAnnotationLine);
return moduleAnnotations.ToList();
var lastPossibleModuleAnnotationLine = lastPossibleDeclarationsSectionLine.Value;
var moduleAnnotations = potentialModuleAnnotations.Where(annotation => annotation.QualifiedSelection.Selection.EndLine <= lastPossibleModuleAnnotationLine);
return moduleAnnotations;
}

private static int? LastDeclarationsSectionLine(IParseTree tree, ICollection<IAnnotation> annotations)
private static int? LastPossibleDeclarationsSectionLine(IParseTree tree)
{
var firstModuleBodyElementLine = FirstModuleBodyElementLine(tree);

if (firstModuleBodyElementLine == null)
{
return null;
}

//The VBE uses 1-based lines.
for (var currentLine = firstModuleBodyElementLine.Value - 1; currentLine >= 1; currentLine--)
{
if (annotations.Any(annotation => annotation.QualifiedSelection.Selection.StartLine <= currentLine
&& annotation.QualifiedSelection.Selection.EndLine >=
currentLine))
{
continue;
}

return currentLine;
}

//There is no declaration section.
return 0;
return FirstModuleBodyElementLine(tree) - 1;
}

private static int? FirstModuleBodyElementLine(IParseTree tree)
Expand Down

0 comments on commit 0bda237

Please sign in to comment.