Skip to content

Commit 57bd697

Browse files
committed
Merge conflict with next
2 parents 6976d74 + 6d4087b commit 57bd697

File tree

342 files changed

+7593
-4501
lines changed

Some content is hidden

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

342 files changed

+7593
-4501
lines changed

Rubberduck.CodeAnalysis/Inspections/Abstract/InspectionResultBase.cs

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -5,9 +5,8 @@
55
using Rubberduck.Parsing.Inspections.Abstract;
66
using Rubberduck.Resources.Inspections;
77
using Rubberduck.Parsing.Symbols;
8-
using Rubberduck.UI;
9-
using Rubberduck.UI.Controls;
108
using Rubberduck.VBEditor;
9+
using Rubberduck.Interaction.Navigation;
1110

1211
namespace Rubberduck.Inspections.Abstract
1312
{
Lines changed: 43 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,43 @@
1+
using System.Collections.Generic;
2+
using System.Linq;
3+
using Rubberduck.Inspections.Abstract;
4+
using Rubberduck.Inspections.Results;
5+
using Rubberduck.Parsing.Inspections.Abstract;
6+
using Rubberduck.Parsing.VBA;
7+
using Rubberduck.Resources.Inspections;
8+
9+
namespace Rubberduck.Inspections.Concrete
10+
{
11+
public sealed class DuplicatedAnnotationInspection : InspectionBase
12+
{
13+
public DuplicatedAnnotationInspection(RubberduckParserState state) : base(state)
14+
{
15+
}
16+
17+
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
18+
{
19+
var issues = new List<DeclarationInspectionResult>();
20+
21+
foreach (var declaration in State.AllUserDeclarations)
22+
{
23+
var duplicateAnnotations = declaration.Annotations
24+
.GroupBy(annotation => annotation.AnnotationType)
25+
.Where(group => !group.First().AllowMultiple && group.Count() > 1);
26+
27+
issues.AddRange(duplicateAnnotations.Select(duplicate =>
28+
{
29+
var result = new DeclarationInspectionResult(
30+
this,
31+
string.Format(InspectionResults.DuplicatedAnnotationInspection, duplicate.Key.ToString()),
32+
declaration);
33+
34+
result.Properties.AnnotationType = duplicate.Key;
35+
36+
return result;
37+
}));
38+
}
39+
40+
return issues;
41+
}
42+
}
43+
}

Rubberduck.CodeAnalysis/Inspections/Concrete/FunctionReturnValueNotUsedInspection.cs

Lines changed: 3 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,6 @@
11
using System;
22
using System.Collections.Generic;
33
using System.Linq;
4-
using Rubberduck.Common;
54
using Rubberduck.Inspections.Abstract;
65
using Rubberduck.Inspections.Results;
76
using Rubberduck.Parsing;
@@ -25,8 +24,8 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
2524
{
2625
// Note: This inspection does not find dictionary calls (e.g. foo!bar) since we do not know what the
2726
// default member is of a class.
28-
var interfaceMembers = UserDeclarations.FindInterfaceMembers().ToList();
29-
var interfaceImplementationMembers = UserDeclarations.FindInterfaceImplementationMembers();
27+
var interfaceMembers = State.DeclarationFinder.FindAllInterfaceMembers().ToList();
28+
var interfaceImplementationMembers = State.DeclarationFinder.FindAllInterfaceImplementingMembers();
3029
var functions = State.DeclarationFinder
3130
.UserDeclarations(DeclarationType.Function)
3231
.Where(item => !IsIgnoringInspectionResultFor(item, AnnotationName))
@@ -41,7 +40,7 @@ private IEnumerable<IInspectionResult> GetInterfaceMemberIssues(IEnumerable<Decl
4140
{
4241
return from interfaceMember in interfaceMembers
4342
let implementationMembers =
44-
UserDeclarations.FindInterfaceImplementationMembers(interfaceMember.IdentifierName).ToList()
43+
State.DeclarationFinder.FindInterfaceImplementationMembers(interfaceMember).ToList()
4544
where interfaceMember.DeclarationType == DeclarationType.Function &&
4645
!IsReturnValueUsed(interfaceMember) &&
4746
implementationMembers.All(member => !IsReturnValueUsed(member))

Rubberduck.CodeAnalysis/Inspections/Concrete/IllegalAnnotationInspection.cs

Lines changed: 2 additions & 24 deletions
Original file line numberDiff line numberDiff line change
@@ -35,11 +35,6 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
3535

3636
public class IllegalAttributeAnnotationsListener : VBAParserBaseListener, IInspectionListener
3737
{
38-
private static readonly AnnotationType[] AnnotationTypes = Enum.GetValues(typeof(AnnotationType)).Cast<AnnotationType>().ToArray();
39-
40-
private IDictionary<Tuple<QualifiedModuleName, AnnotationType>, int> _annotationCounts =
41-
new Dictionary<Tuple<QualifiedModuleName, AnnotationType>, int>();
42-
4338
private readonly RubberduckParserState _state;
4439

4540
private Lazy<Declaration> _module;
@@ -55,32 +50,19 @@ public IllegalAttributeAnnotationsListener(RubberduckParserState state)
5550

5651
public IReadOnlyList<QualifiedContext<ParserRuleContext>> Contexts => _contexts;
5752

58-
public QualifiedModuleName CurrentModuleName
59-
{
60-
get => _currentModuleName;
61-
set
62-
{
63-
_currentModuleName = value;
64-
foreach (var type in AnnotationTypes)
65-
{
66-
_annotationCounts.Add(Tuple.Create(value, type), 0);
67-
}
68-
}
69-
}
53+
public QualifiedModuleName CurrentModuleName { get; set; }
7054

7155
private bool _isFirstMemberProcessed;
7256

7357
public void ClearContexts()
7458
{
75-
_annotationCounts = new Dictionary<Tuple<QualifiedModuleName, AnnotationType>, int>();
7659
_contexts.Clear();
7760
_isFirstMemberProcessed = false;
7861
}
7962

8063
#region scoping
8164
private Declaration _currentScopeDeclaration;
8265
private bool _hasMembers;
83-
private QualifiedModuleName _currentModuleName;
8466

8567
private void SetCurrentScope(string memberName = null)
8668
{
@@ -168,8 +150,6 @@ public override void ExitAnnotation(VBAParser.AnnotationContext context)
168150
{
169151
var name = Identifier.GetName(context.annotationName().unrestrictedIdentifier());
170152
var annotationType = (AnnotationType) Enum.Parse(typeof (AnnotationType), name, true);
171-
var key = Tuple.Create(_currentModuleName, annotationType);
172-
_annotationCounts[key]++;
173153

174154
var moduleHasMembers = _members.Value.Any();
175155

@@ -183,9 +163,7 @@ public override void ExitAnnotation(VBAParser.AnnotationContext context)
183163
&& (_currentScopeDeclaration?.DeclarationType.HasFlag(DeclarationType.Member) ?? false);
184164

185165
var isIllegal = !(isMemberAnnotation && moduleHasMembers && !_isFirstMemberProcessed) &&
186-
(isModuleAnnotation && _annotationCounts[key] > 1
187-
|| isMemberAnnotatedForModuleAnnotation
188-
|| isModuleAnnotatedForMemberAnnotation);
166+
(isMemberAnnotatedForModuleAnnotation || isModuleAnnotatedForMemberAnnotation);
189167

190168
if (isIllegal)
191169
{

Rubberduck.CodeAnalysis/Inspections/Concrete/ImplicitByRefModifierInspection.cs

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,6 @@
11
using System.Collections.Generic;
22
using System.Linq;
33
using Antlr4.Runtime;
4-
using Rubberduck.Common;
54
using Rubberduck.Inspections.Abstract;
65
using Rubberduck.Inspections.Results;
76
using Rubberduck.Parsing;
@@ -26,7 +25,7 @@ public ImplicitByRefModifierInspection(RubberduckParserState state)
2625
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
2726
{
2827
var builtInEventHandlerContexts = State.DeclarationFinder.FindEventHandlers().Select(handler => handler.Context).ToHashSet();
29-
var interfaceImplementationMemberContexts = UserDeclarations.FindInterfaceImplementationMembers().Select(member => member.Context).ToHashSet();
28+
var interfaceImplementationMemberContexts = State.DeclarationFinder.FindAllInterfaceImplementingMembers().Select(member => member.Context).ToHashSet();
3029

3130
var issues = Listener.Contexts.Where(context =>
3231
!IsIgnoringInspectionResultFor(context.ModuleName, context.Context.Start.Line) &&

Rubberduck.CodeAnalysis/Inspections/Concrete/IntegerDataTypeInspection.cs

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,6 @@
11
using System.Collections.Generic;
22
using System.Globalization;
33
using System.Linq;
4-
using Rubberduck.Common;
54
using Rubberduck.Inspections.Abstract;
65
using Rubberduck.Inspections.Results;
76
using Rubberduck.Parsing.Grammar;
@@ -21,7 +20,7 @@ public IntegerDataTypeInspection(RubberduckParserState state) : base(state)
2120

2221
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
2322
{
24-
var interfaceImplementationMembers = UserDeclarations.FindInterfaceImplementationMembers().ToHashSet();
23+
var interfaceImplementationMembers = State.DeclarationFinder.FindAllInterfaceImplementingMembers().ToHashSet();
2524

2625
var excludeParameterMembers = State.DeclarationFinder.FindEventHandlers().ToHashSet();
2726
excludeParameterMembers.UnionWith(interfaceImplementationMembers);

Rubberduck.CodeAnalysis/Inspections/Concrete/NonReturningFunctionInspection.cs

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,5 @@
11
using System.Collections.Generic;
22
using System.Linq;
3-
using Rubberduck.Common;
43
using Rubberduck.Inspections.Abstract;
54
using Rubberduck.Inspections.Results;
65
using Rubberduck.Parsing.Grammar;
@@ -26,7 +25,7 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
2625
{
2726
var declarations = UserDeclarations.ToList();
2827

29-
var interfaceMembers = declarations.FindInterfaceMembers();
28+
var interfaceMembers = State.DeclarationFinder.FindAllInterfaceMembers();
3029

3130
var functions = declarations
3231
.Where(declaration => ReturningMemberTypes.Contains(declaration.DeclarationType)

Rubberduck.CodeAnalysis/Inspections/Concrete/ObjectVariableNotSetInspection.cs

Lines changed: 4 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -6,14 +6,13 @@
66
using Rubberduck.Resources.Inspections;
77
using Rubberduck.Parsing.Symbols;
88
using Rubberduck.Parsing.VBA;
9-
using Rubberduck.VBEditor.SafeComWrappers;
109

1110
namespace Rubberduck.Inspections.Concrete
1211
{
1312
public sealed class ObjectVariableNotSetInspection : InspectionBase
1413
{
1514
public ObjectVariableNotSetInspection(RubberduckParserState state)
16-
: base(state) { }
15+
: base(state) { }
1716

1817
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
1918
{
@@ -36,17 +35,11 @@ private IEnumerable<IdentifierReference> InterestingReferences()
3635
continue;
3736
}
3837

39-
foreach (var reference in moduleReferences.Value)
40-
{
41-
if (!IsIgnoringInspectionResultFor(reference, AnnotationName)
42-
&& VariableRequiresSetAssignmentEvaluator.NeedsSetKeywordAdded(reference, State))
43-
{
44-
result.Add(reference);
45-
}
46-
}
38+
result.AddRange(moduleReferences.Value.Where(reference => !reference.IsSetAssignment
39+
&& VariableRequiresSetAssignmentEvaluator.RequiresSetAssignment(reference, State)));
4740
}
4841

49-
return result;
42+
return result.Where(reference => !IsIgnoringInspectionResultFor(reference, AnnotationName));
5043
}
5144
}
5245
}

Rubberduck.CodeAnalysis/Inspections/Concrete/OptionExplicitInspection.cs

Lines changed: 5 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -25,9 +25,11 @@ public OptionExplicitInspection(RubberduckParserState state)
2525

2626
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
2727
{
28-
return Listener.Contexts.Select(context => new QualifiedContextInspectionResult(this,
29-
string.Format(InspectionResults.OptionExplicitInspection, context.ModuleName.ComponentName),
30-
context));
28+
return Listener.Contexts
29+
.Where(context => !IsIgnoringInspectionResultFor(context.ModuleName, context.Context.Start.Line))
30+
.Select(context => new QualifiedContextInspectionResult(this,
31+
string.Format(InspectionResults.OptionExplicitInspection, context.ModuleName.ComponentName),
32+
context));
3133
}
3234

3335
public class MissingOptionExplicitListener : VBAParserBaseListener, IInspectionListener

Rubberduck.CodeAnalysis/Inspections/Concrete/ParameterCanBeByValInspection.cs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -22,8 +22,8 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
2222
var declarations = UserDeclarations.ToArray();
2323
var issues = new List<IInspectionResult>();
2424

25-
var interfaceDeclarationMembers = declarations.FindInterfaceMembers().ToArray();
26-
var interfaceScopes = declarations.FindInterfaceImplementationMembers().Concat(interfaceDeclarationMembers).Select(s => s.Scope).ToArray();
25+
var interfaceDeclarationMembers = State.DeclarationFinder.FindAllInterfaceMembers().ToArray();
26+
var interfaceScopes = State.DeclarationFinder.FindAllInterfaceImplementingMembers().Concat(interfaceDeclarationMembers).Select(s => s.Scope).ToArray();
2727

2828
issues.AddRange(GetResults(declarations, interfaceDeclarationMembers));
2929

@@ -80,7 +80,7 @@ private IEnumerable<IInspectionResult> GetResults(Declaration[] declarations, De
8080

8181
var members = declarationMembers.Any(a => a.DeclarationType == DeclarationType.Event)
8282
? declarations.FindHandlersForEvent(declaration).Select(s => s.Item2).ToList()
83-
: declarations.FindInterfaceImplementationMembers(declaration).ToList();
83+
: State.DeclarationFinder.FindInterfaceImplementationMembers(declaration).Cast<Declaration>().ToList();
8484

8585
foreach (var member in members)
8686
{

0 commit comments

Comments
 (0)