Skip to content

Commit 2f07e94

Browse files
committed
Merge branch 'rubberduck-vba/next' into 4349_RenameClash
2 parents 8a38df7 + 89f2cb8 commit 2f07e94

File tree

97 files changed

+2242
-1348
lines changed

Some content is hidden

Large Commits have some content hidden by default. Use the searchbox below for content that may be hidden.

97 files changed

+2242
-1348
lines changed
Lines changed: 84 additions & 146 deletions
Original file line numberDiff line numberDiff line change
@@ -1,175 +1,113 @@
1-
using System;
21
using System.Collections.Generic;
3-
using System.Diagnostics;
42
using System.Linq;
5-
using Antlr4.Runtime;
63
using Rubberduck.Inspections.Abstract;
74
using Rubberduck.Inspections.Results;
85
using Rubberduck.Parsing;
96
using Rubberduck.Parsing.Annotations;
10-
using Rubberduck.Parsing.Grammar;
117
using Rubberduck.Parsing.Inspections.Abstract;
12-
using Rubberduck.Resources.Inspections;
138
using Rubberduck.Parsing.Symbols;
9+
using Rubberduck.Resources.Inspections;
1410
using Rubberduck.Parsing.VBA;
15-
using Rubberduck.VBEditor;
11+
using Rubberduck.Parsing.VBA.Extensions;
1612

1713
namespace Rubberduck.Inspections.Concrete
1814
{
19-
public sealed class IllegalAnnotationInspection : ParseTreeInspectionBase
15+
public sealed class IllegalAnnotationInspection : InspectionBase
2016
{
2117
public IllegalAnnotationInspection(RubberduckParserState state)
2218
: base(state)
23-
{
24-
Listener = new IllegalAttributeAnnotationsListener(state);
25-
}
26-
27-
public override IInspectionListener Listener { get; }
19+
{}
2820

2921
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
3022
{
31-
return Listener.Contexts.Select(context =>
32-
new QualifiedContextInspectionResult(this,
33-
string.Format(InspectionResults.IllegalAnnotationInspection, ((VBAParser.AnnotationContext)context.Context).annotationName().GetText()), context));
23+
var illegalAnnotations = new List<IAnnotation>();
24+
25+
var userDeclarations = State.DeclarationFinder.AllUserDeclarations.ToList();
26+
var identifierReferences = State.DeclarationFinder.AllIdentifierReferences().ToList();
27+
var annotations = State.AllAnnotations;
28+
29+
illegalAnnotations.AddRange(UnboundAnnotations(annotations, userDeclarations, identifierReferences));
30+
illegalAnnotations.AddRange(NonIdentifierAnnotationsOnIdentifiers(identifierReferences));
31+
illegalAnnotations.AddRange(NonModuleAnnotationsOnModules(userDeclarations));
32+
illegalAnnotations.AddRange(NonMemberAnnotationsOnMembers(userDeclarations));
33+
illegalAnnotations.AddRange(NonVariableAnnotationsOnVariables(userDeclarations));
34+
illegalAnnotations.AddRange(NonGeneralAnnotationsWhereOnlyGeneralAnnotationsBelong(userDeclarations));
35+
36+
return illegalAnnotations.Select(annotation =>
37+
new QualifiedContextInspectionResult(
38+
this,
39+
string.Format(InspectionResults.IllegalAnnotationInspection, annotation.Context.annotationName().GetText()),
40+
new QualifiedContext(annotation.QualifiedSelection.QualifiedName, annotation.Context)));
3441
}
3542

36-
public class IllegalAttributeAnnotationsListener : VBAParserBaseListener, IInspectionListener
43+
private static ICollection<IAnnotation> UnboundAnnotations(IEnumerable<IAnnotation> annotations, IEnumerable<Declaration> userDeclarations, IEnumerable<IdentifierReference> identifierReferences)
3744
{
38-
private readonly RubberduckParserState _state;
39-
40-
private Lazy<Declaration> _module;
41-
private Lazy<IDictionary<string, Declaration>> _members;
42-
43-
public IllegalAttributeAnnotationsListener(RubberduckParserState state)
44-
{
45-
_state = state;
46-
}
47-
48-
private readonly List<QualifiedContext<ParserRuleContext>> _contexts =
49-
new List<QualifiedContext<ParserRuleContext>>();
50-
51-
public IReadOnlyList<QualifiedContext<ParserRuleContext>> Contexts => _contexts;
52-
53-
public QualifiedModuleName CurrentModuleName { get; set; }
54-
55-
private bool _isFirstMemberProcessed;
56-
57-
public void ClearContexts()
58-
{
59-
_contexts.Clear();
60-
_isFirstMemberProcessed = false;
61-
}
62-
63-
#region scoping
64-
private Declaration _currentScopeDeclaration;
65-
private bool _hasMembers;
66-
67-
private void SetCurrentScope(string memberName = null)
68-
{
69-
_hasMembers = !string.IsNullOrEmpty(memberName);
70-
// this is a one-time toggle until contexts are reset
71-
_isFirstMemberProcessed |= _hasMembers;
72-
_currentScopeDeclaration = _hasMembers ? _members.Value[memberName] : _module.Value;
73-
}
74-
75-
public override void EnterModuleBody(VBAParser.ModuleBodyContext context)
76-
{
77-
_currentScopeDeclaration = _state.DeclarationFinder
78-
.UserDeclarations(DeclarationType.Procedure)
79-
.Where(declaration => declaration.QualifiedName.QualifiedModuleName.Equals(CurrentModuleName))
80-
.OrderBy(declaration => declaration.Selection)
81-
.FirstOrDefault();
82-
}
83-
84-
public override void EnterModule(VBAParser.ModuleContext context)
85-
{
86-
_module = new Lazy<Declaration>(() => _state.DeclarationFinder
87-
.UserDeclarations(DeclarationType.Module)
88-
.SingleOrDefault(m => m.QualifiedName.QualifiedModuleName.Equals(CurrentModuleName)));
89-
90-
_members = new Lazy<IDictionary<string, Declaration>>(() => _state.DeclarationFinder
91-
.Members(CurrentModuleName)
92-
.GroupBy(m => m.IdentifierName)
93-
.ToDictionary(m => m.Key, m => m.First()));
94-
95-
// we did not process the first member of the module we just entered, so reset here
96-
_isFirstMemberProcessed = false;
97-
}
98-
99-
public override void ExitModule(VBAParser.ModuleContext context)
100-
{
101-
_currentScopeDeclaration = null;
102-
}
103-
104-
public override void EnterModuleAttributes(VBAParser.ModuleAttributesContext context)
105-
{
106-
// note: using ModuleAttributesContext for module-scope
107-
108-
if(_currentScopeDeclaration == null)
109-
{
110-
// we're at the top of the module.
111-
// everything we pick up between here and the module body, is module-scoped:
112-
_currentScopeDeclaration = _state.DeclarationFinder.UserDeclarations(DeclarationType.Module)
113-
.SingleOrDefault(d => d.QualifiedName.QualifiedModuleName.Equals(CurrentModuleName));
114-
}
115-
else
116-
{
117-
// DO NOT re-assign _currentScope here.
118-
// we're at the end of the module and that attribute is actually scoped to the last procedure.
119-
Debug.Assert(_currentScopeDeclaration != null); // deliberate no-op
120-
}
121-
}
122-
123-
public override void EnterSubStmt(VBAParser.SubStmtContext context)
124-
{
125-
SetCurrentScope(Identifier.GetName(context.subroutineName()));
126-
}
127-
128-
public override void EnterFunctionStmt(VBAParser.FunctionStmtContext context)
129-
{
130-
SetCurrentScope(Identifier.GetName(context.functionName()));
131-
}
132-
133-
public override void EnterPropertyGetStmt(VBAParser.PropertyGetStmtContext context)
134-
{
135-
SetCurrentScope(Identifier.GetName(context.functionName()));
136-
}
137-
138-
public override void EnterPropertyLetStmt(VBAParser.PropertyLetStmtContext context)
139-
{
140-
SetCurrentScope(Identifier.GetName(context.subroutineName()));
141-
}
142-
143-
public override void EnterPropertySetStmt(VBAParser.PropertySetStmtContext context)
144-
{
145-
SetCurrentScope(Identifier.GetName(context.subroutineName()));
146-
}
147-
#endregion
148-
149-
public override void ExitAnnotation(VBAParser.AnnotationContext context)
150-
{
151-
var name = Identifier.GetName(context.annotationName().unrestrictedIdentifier());
152-
var annotationType = (AnnotationType) Enum.Parse(typeof (AnnotationType), name, true);
153-
154-
var moduleHasMembers = _members.Value.Any();
45+
var boundAnnotationsSelections = userDeclarations
46+
.SelectMany(declaration => declaration.Annotations)
47+
.Concat(identifierReferences.SelectMany(reference => reference.Annotations))
48+
.Select(annotation => annotation.QualifiedSelection)
49+
.ToHashSet();
50+
51+
return annotations.Where(annotation => !boundAnnotationsSelections.Contains(annotation.QualifiedSelection)).ToList();
52+
}
15553

156-
var isMemberAnnotation = annotationType.HasFlag(AnnotationType.MemberAnnotation);
157-
var isModuleAnnotation = annotationType.HasFlag(AnnotationType.ModuleAnnotation);
54+
private static ICollection<IAnnotation> NonIdentifierAnnotationsOnIdentifiers(IEnumerable<IdentifierReference> identifierReferences)
55+
{
56+
return identifierReferences
57+
.SelectMany(reference => reference.Annotations)
58+
.Where(annotation => !annotation.AnnotationType.HasFlag(AnnotationType.IdentifierAnnotation))
59+
.ToList();
60+
}
15861

159-
var isModuleAnnotatedForMemberAnnotation = isMemberAnnotation
160-
&& (_currentScopeDeclaration?.DeclarationType.HasFlag(DeclarationType.Module) ?? false);
62+
private static ICollection<IAnnotation> NonModuleAnnotationsOnModules(IEnumerable<Declaration> userDeclarations)
63+
{
64+
return userDeclarations
65+
.Where(declaration => declaration.DeclarationType.HasFlag(DeclarationType.Module))
66+
.SelectMany(moduleDeclaration => moduleDeclaration.Annotations)
67+
.Where(annotation => !annotation.AnnotationType.HasFlag(AnnotationType.ModuleAnnotation))
68+
.ToList();
69+
}
16170

162-
var isMemberAnnotatedForModuleAnnotation = isModuleAnnotation
163-
&& (_currentScopeDeclaration?.DeclarationType.HasFlag(DeclarationType.Member) ?? false);
71+
private static ICollection<IAnnotation> NonMemberAnnotationsOnMembers(IEnumerable<Declaration> userDeclarations)
72+
{
73+
return userDeclarations
74+
.Where(declaration => declaration.DeclarationType.HasFlag(DeclarationType.Member))
75+
.SelectMany(member => member.Annotations)
76+
.Where(annotation => !annotation.AnnotationType.HasFlag(AnnotationType.MemberAnnotation))
77+
.ToList();
78+
}
16479

165-
var isIllegal = !(isMemberAnnotation && moduleHasMembers && !_isFirstMemberProcessed) &&
166-
(isMemberAnnotatedForModuleAnnotation || isModuleAnnotatedForMemberAnnotation);
80+
private static ICollection<IAnnotation> NonVariableAnnotationsOnVariables(IEnumerable<Declaration> userDeclarations)
81+
{
82+
return userDeclarations
83+
.Where(declaration => VariableAnnotationDeclarationTypes.Contains(declaration.DeclarationType))
84+
.SelectMany(declaration => declaration.Annotations)
85+
.Where(annotation => !annotation.AnnotationType.HasFlag(AnnotationType.VariableAnnotation))
86+
.ToList();
87+
}
16788

168-
if (isIllegal)
169-
{
170-
_contexts.Add(new QualifiedContext<ParserRuleContext>(CurrentModuleName, context));
171-
}
172-
}
89+
private static readonly HashSet<DeclarationType> VariableAnnotationDeclarationTypes = new HashSet<DeclarationType>()
90+
{
91+
DeclarationType.Variable,
92+
DeclarationType.Control,
93+
DeclarationType.Constant,
94+
DeclarationType.Enumeration,
95+
DeclarationType.EnumerationMember,
96+
DeclarationType.UserDefinedType,
97+
DeclarationType.UserDefinedType,
98+
DeclarationType.UserDefinedTypeMember
99+
};
100+
101+
private static ICollection<IAnnotation> NonGeneralAnnotationsWhereOnlyGeneralAnnotationsBelong(IEnumerable<Declaration> userDeclarations)
102+
{
103+
return userDeclarations
104+
.Where(declaration => !declaration.DeclarationType.HasFlag(DeclarationType.Module)
105+
&& !declaration.DeclarationType.HasFlag(DeclarationType.Member)
106+
&& !VariableAnnotationDeclarationTypes.Contains(declaration.DeclarationType)
107+
&& declaration.DeclarationType != DeclarationType.Project)
108+
.SelectMany(member => member.Annotations)
109+
.Where(annotation => !annotation.AnnotationType.HasFlag(AnnotationType.GeneralAnnotation))
110+
.ToList();
173111
}
174112
}
175113
}

Rubberduck.CodeAnalysis/Inspections/Concrete/ImplicitActiveWorkbookReferenceInspection.cs

Lines changed: 18 additions & 17 deletions
Original file line numberDiff line numberDiff line change
@@ -4,6 +4,7 @@
44
using Rubberduck.Inspections.Results;
55
using Rubberduck.Parsing.Inspections;
66
using Rubberduck.Parsing.Inspections.Abstract;
7+
using Rubberduck.Parsing.Symbols;
78
using Rubberduck.Resources.Inspections;
89
using Rubberduck.Parsing.VBA;
910

@@ -15,32 +16,32 @@ public sealed class ImplicitActiveWorkbookReferenceInspection : InspectionBase
1516
public ImplicitActiveWorkbookReferenceInspection(RubberduckParserState state)
1617
: base(state) { }
1718

18-
private static readonly string[] Targets =
19+
private static readonly string[] InterestingMembers =
1920
{
20-
"Worksheets", "Sheets", "Names", "_Default"
21+
"Worksheets", "Sheets", "Names"
22+
};
23+
24+
private static readonly string[] InterestingClasses =
25+
{
26+
"_Global", "_Application", "Global", "Application"
2127
};
2228

2329
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
2430
{
2531
var excel = State.DeclarationFinder.Projects.SingleOrDefault(item => !item.IsUserDefined && item.IdentifierName == "Excel");
26-
if (excel == null) { return Enumerable.Empty<IInspectionResult>(); }
27-
28-
var modules = new[]
32+
if (excel == null)
2933
{
30-
State.DeclarationFinder.FindClassModule("_Global", excel, true),
31-
State.DeclarationFinder.FindClassModule("_Application", excel, true),
32-
State.DeclarationFinder.FindClassModule("Global", excel, true),
33-
State.DeclarationFinder.FindClassModule("Application", excel, true),
34-
State.DeclarationFinder.FindClassModule("Sheets", excel, true),
35-
};
34+
return Enumerable.Empty<IInspectionResult>();
35+
}
3636

37-
var members = Targets
38-
.SelectMany(target => modules.SelectMany(module =>
39-
State.DeclarationFinder.FindMemberMatches(module, target)))
40-
.Where(item => item.References.Any())
41-
.SelectMany(item => item.References.Where(reference => !IsIgnoringInspectionResultFor(reference, AnnotationName)))
37+
var targetProperties = BuiltInDeclarations
38+
.OfType<PropertyGetDeclaration>()
39+
.Where(x => InterestingMembers.Contains(x.IdentifierName) && InterestingClasses.Contains(x.ParentDeclaration?.IdentifierName))
4240
.ToList();
43-
41+
42+
var members = targetProperties.SelectMany(item =>
43+
item.References.Where(reference => !IsIgnoringInspectionResultFor(reference, AnnotationName)));
44+
4445
return members.Select(issue => new IdentifierReferenceInspectionResult(this,
4546
string.Format(InspectionResults.ImplicitActiveWorkbookReferenceInspection, issue.Context.GetText()),
4647
State,
Lines changed: 54 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,54 @@
1+
using System.Collections.Generic;
2+
using System.Linq;
3+
using Antlr4.Runtime;
4+
using Rubberduck.Inspections.Abstract;
5+
using Rubberduck.Inspections.Results;
6+
using Rubberduck.Parsing;
7+
using Rubberduck.Parsing.Grammar;
8+
using Rubberduck.Parsing.Inspections.Abstract;
9+
using Rubberduck.Resources.Inspections;
10+
using Rubberduck.Parsing.VBA;
11+
using Rubberduck.VBEditor;
12+
using Antlr4.Runtime.Misc;
13+
14+
namespace Rubberduck.Inspections.Concrete
15+
{
16+
public sealed class OnLocalErrorInspection : ParseTreeInspectionBase
17+
{
18+
public OnLocalErrorInspection(RubberduckParserState state)
19+
: base(state) { }
20+
21+
public override IInspectionListener Listener { get; } =
22+
new OnLocalErrorListener();
23+
24+
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
25+
{
26+
return Listener.Contexts
27+
.Where(result => !IsIgnoringInspectionResultFor(result.ModuleName, result.Context.Start.Line))
28+
.Select(result => new QualifiedContextInspectionResult(this,
29+
InspectionResults.OnLocalErrorInspection,
30+
result));
31+
}
32+
33+
public class OnLocalErrorListener : VBAParserBaseListener, IInspectionListener
34+
{
35+
private readonly List<QualifiedContext<ParserRuleContext>> _contexts = new List<QualifiedContext<ParserRuleContext>>();
36+
public IReadOnlyList<QualifiedContext<ParserRuleContext>> Contexts => _contexts;
37+
38+
public QualifiedModuleName CurrentModuleName { get; set; }
39+
40+
public void ClearContexts()
41+
{
42+
_contexts.Clear();
43+
}
44+
45+
public override void ExitOnErrorStmt([NotNull] VBAParser.OnErrorStmtContext context)
46+
{
47+
if (context.ON_LOCAL_ERROR() != null)
48+
{
49+
_contexts.Add(new QualifiedContext<ParserRuleContext>(CurrentModuleName, context));
50+
}
51+
}
52+
}
53+
}
54+
}

0 commit comments

Comments
 (0)