Skip to content

Commit 1bd3bc3

Browse files
committed
Merge branch 'next' of https://github.com/rubberduck-vba/Rubberduck into ComDisconnect
# Conflicts: # Rubberduck.CodeAnalysis/Rubberduck.CodeAnalysis.xml # Rubberduck.Core/UI/Command/ComCommands/ReparseCommand.cs
2 parents 13eb65a + 65aac29 commit 1bd3bc3

File tree

196 files changed

+15411
-6216
lines changed

Some content is hidden

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

196 files changed

+15411
-6216
lines changed

.gitignore

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -189,3 +189,4 @@ Rubberduck.CodeAnalysis.xml
189189

190190
#Gradle
191191
/.gradle/
192+
/Rubberduck.CodeAnalysis/Rubberduck.CodeAnalysis.xml
Lines changed: 58 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,58 @@
1+
using Rubberduck.Inspections.Abstract;
2+
using Rubberduck.Inspections.Results;
3+
using Rubberduck.Parsing.Inspections.Abstract;
4+
using Rubberduck.Resources.Inspections;
5+
using Rubberduck.Parsing.VBA;
6+
using System.Collections.Generic;
7+
using System.Linq;
8+
using Rubberduck.Parsing.Symbols;
9+
using Rubberduck.Inspections.Inspections.Extensions;
10+
using Rubberduck.Common;
11+
12+
namespace Rubberduck.Inspections.Concrete
13+
{
14+
/// <summary>
15+
/// Identifies empty module member blocks.
16+
/// </summary>
17+
/// <why>
18+
/// Methods containing no executable statements are misleading as they appear to be doing something which they actually don't.
19+
/// This might be the result of delaying the actual implementation for a later stage of development, and then forgetting all about that.
20+
/// </why>
21+
/// <example hasResults="true">
22+
/// <![CDATA[
23+
/// Sub Foo()
24+
/// ' ...
25+
/// End Sub
26+
/// ]]>
27+
/// </example>
28+
/// <example hasResults="false">
29+
/// <![CDATA[
30+
/// Sub Foo()
31+
/// MsgBox "?"
32+
/// End Sub
33+
/// ]]>
34+
/// </example>
35+
internal class EmptyMethodInspection : InspectionBase
36+
{
37+
public EmptyMethodInspection(RubberduckParserState state)
38+
: base(state) { }
39+
40+
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
41+
{
42+
var allInterfaces = new HashSet<ClassModuleDeclaration>(State.DeclarationFinder.FindAllUserInterfaces());
43+
44+
return State.DeclarationFinder.UserDeclarations(DeclarationType.Member)
45+
.Where(member => !allInterfaces.Any(userInterface => userInterface.QualifiedModuleName == member.QualifiedModuleName)
46+
&& !member.IsIgnoringInspectionResultFor(AnnotationName)
47+
&& !((ModuleBodyElementDeclaration)member).Block.ContainsExecutableStatements())
48+
49+
.Select(result => new DeclarationInspectionResult(this,
50+
string.Format(InspectionResults.EmptyMethodInspection,
51+
Resources.RubberduckUI.ResourceManager
52+
.GetString("DeclarationType_" + result.DeclarationType)
53+
.Capitalize(),
54+
result.IdentifierName),
55+
result));
56+
}
57+
}
58+
}
Lines changed: 53 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,53 @@
1+
using Rubberduck.Inspections.Abstract;
2+
using Rubberduck.Inspections.Results;
3+
using Rubberduck.Parsing.Inspections.Abstract;
4+
using Rubberduck.Resources.Inspections;
5+
using System.Collections.Generic;
6+
using System.Linq;
7+
using Rubberduck.Parsing.Symbols;
8+
using Rubberduck.Inspections.Inspections.Extensions;
9+
using Rubberduck.Common;
10+
11+
namespace Rubberduck.Inspections.Concrete
12+
{
13+
/// <summary>
14+
/// Identifies implemented members of class modules that are used as interfaces.
15+
/// </summary>
16+
/// <why>
17+
/// Interfaces provide a unified programmatic access to different objects, and therefore are rarely instantiated as concrete objects.
18+
/// </why>
19+
/// <example hasResults="false">
20+
/// <![CDATA[
21+
/// Sub Foo()
22+
/// ' ...
23+
/// End Sub
24+
/// ]]>
25+
/// </example>
26+
/// <example hasResults="true">
27+
/// <![CDATA[
28+
/// Sub Foo()
29+
/// MsgBox "?"
30+
/// End Sub
31+
/// ]]>
32+
/// </example>
33+
internal class ImplementedInterfaceMemberInspection : InspectionBase
34+
{
35+
public ImplementedInterfaceMemberInspection(Parsing.VBA.RubberduckParserState state)
36+
: base(state) { }
37+
38+
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
39+
{
40+
return State.DeclarationFinder.FindAllUserInterfaces()
41+
.SelectMany(interfaceModule => interfaceModule.Members
42+
.Where(member => ((ModuleBodyElementDeclaration)member).Block.ContainsExecutableStatements(true)
43+
&& !member.IsIgnoringInspectionResultFor(AnnotationName)))
44+
.Select(result => new DeclarationInspectionResult(this,
45+
string.Format(InspectionResults.ImplementedInterfaceMemberInspection,
46+
Resources.RubberduckUI.ResourceManager
47+
.GetString("DeclarationType_" + result.DeclarationType)
48+
.Capitalize(),
49+
result.IdentifierName),
50+
result));
51+
}
52+
}
53+
}

Rubberduck.CodeAnalysis/Inspections/Concrete/ImplicitDefaultMemberAssignmentInspection.cs

Lines changed: 34 additions & 23 deletions
Original file line numberDiff line numberDiff line change
@@ -1,10 +1,7 @@
11
using System.Collections.Generic;
2-
using System.Diagnostics;
32
using System.Linq;
43
using Rubberduck.Inspections.Abstract;
54
using Rubberduck.Inspections.Results;
6-
using Rubberduck.Parsing;
7-
using Rubberduck.Parsing.Grammar;
85
using Rubberduck.Parsing.Inspections.Abstract;
96
using Rubberduck.Resources.Inspections;
107
using Rubberduck.Parsing.Symbols;
@@ -40,28 +37,42 @@ public ImplicitDefaultMemberAssignmentInspection(RubberduckParserState state)
4037

4138
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
4239
{
43-
var interestingDeclarations =
44-
State.AllDeclarations.Where(item =>
45-
item.AsTypeDeclaration != null
46-
&& ClassModuleDeclaration.HasDefaultMember(item.AsTypeDeclaration));
40+
var boundDefaultMemberAssignments = State.DeclarationFinder
41+
.AllIdentifierReferences()
42+
.Where(IsRelevantReference);
4743

48-
var interestingReferences = interestingDeclarations
49-
.SelectMany(declaration => declaration.References)
50-
.Where(reference =>
51-
{
52-
var letStmtContext = reference.Context.GetAncestor<VBAParser.LetStmtContext>();
53-
return reference.IsAssignment
54-
&& letStmtContext != null
55-
&& letStmtContext.LET() == null
56-
&& !reference.IsIgnoringInspectionResultFor(AnnotationName);
57-
});
44+
var boundIssues = boundDefaultMemberAssignments
45+
.Select(reference => new IdentifierReferenceInspectionResult(
46+
this,
47+
string.Format(
48+
InspectionResults.ImplicitDefaultMemberAssignmentInspection,
49+
reference.Context.GetText(),
50+
reference.Declaration.IdentifierName,
51+
reference.Declaration.QualifiedModuleName.ToString()),
52+
State,
53+
reference));
5854

59-
return interestingReferences.Select(reference => new IdentifierReferenceInspectionResult(this,
60-
string.Format(InspectionResults.ImplicitDefaultMemberAssignmentInspection,
61-
reference.Declaration.IdentifierName,
62-
reference.Declaration.AsTypeDeclaration.IdentifierName),
63-
State,
64-
reference));
55+
var unboundDefaultMemberAssignments = State.DeclarationFinder
56+
.AllUnboundDefaultMemberAccesses()
57+
.Where(IsRelevantReference);
58+
59+
var unboundIssues = unboundDefaultMemberAssignments
60+
.Select(reference => new IdentifierReferenceInspectionResult(
61+
this,
62+
string.Format(
63+
InspectionResults.ImplicitDefaultMemberAssignmentInspection_Unbound,
64+
reference.Context.GetText()),
65+
State,
66+
reference));
67+
68+
return boundIssues.Concat(unboundIssues);
69+
}
70+
71+
private bool IsRelevantReference(IdentifierReference reference)
72+
{
73+
return reference.IsAssignment
74+
&& reference.IsNonIndexedDefaultMemberAccess
75+
&& !reference.IsIgnoringInspectionResultFor(AnnotationName);
6576
}
6677
}
6778
}

Rubberduck.CodeAnalysis/Inspections/Concrete/MissingAttributeInspection.cs

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,7 @@
11
using System.Collections.Generic;
22
using System.Linq;
33
using Rubberduck.Inspections.Abstract;
4+
using Rubberduck.Inspections.Inspections.Extensions;
45
using Rubberduck.Inspections.Results;
56
using Rubberduck.Parsing;
67
using Rubberduck.Parsing.Annotations;
@@ -49,7 +50,8 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
4950
var declarationsWithAttributeAnnotations = State.DeclarationFinder.AllUserDeclarations
5051
.Where(declaration => declaration.Annotations.Any(annotation => annotation.AnnotationType.HasFlag(AnnotationType.Attribute)));
5152
var results = new List<DeclarationInspectionResult>();
52-
foreach (var declaration in declarationsWithAttributeAnnotations.Where(decl => decl.QualifiedModuleName.ComponentType != ComponentType.Document))
53+
foreach (var declaration in declarationsWithAttributeAnnotations.Where(decl => decl.QualifiedModuleName.ComponentType != ComponentType.Document
54+
&& !decl.IsIgnoringInspectionResultFor(AnnotationName)))
5355
{
5456
foreach(var annotation in declaration.Annotations.OfType<IAttributeAnnotation>())
5557
{

Rubberduck.CodeAnalysis/Inspections/Concrete/NonReturningFunctionInspection.cs

Lines changed: 18 additions & 15 deletions
Original file line numberDiff line numberDiff line change
@@ -1,13 +1,15 @@
11
using System.Collections.Generic;
22
using System.Linq;
33
using Rubberduck.Inspections.Abstract;
4+
using Rubberduck.Inspections.Inspections.Extensions;
45
using Rubberduck.Inspections.Results;
56
using Rubberduck.Parsing;
67
using Rubberduck.Parsing.Grammar;
78
using Rubberduck.Parsing.Inspections.Abstract;
89
using Rubberduck.Resources.Inspections;
910
using Rubberduck.Parsing.Symbols;
1011
using Rubberduck.Parsing.VBA;
12+
using Rubberduck.Parsing.VBA.Extensions;
1113

1214
namespace Rubberduck.Inspections.Concrete
1315
{
@@ -48,30 +50,31 @@ public NonReturningFunctionInspection(RubberduckParserState state)
4850

4951
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
5052
{
51-
var declarations = UserDeclarations.ToList();
53+
var interfaceMembers = State.DeclarationFinder.FindAllInterfaceMembers().ToHashSet();
5254

53-
var interfaceMembers = State.DeclarationFinder.FindAllInterfaceMembers();
55+
var functions = State.DeclarationFinder.UserDeclarations(DeclarationType.Function)
56+
.Where(declaration => !interfaceMembers.Contains(declaration));
5457

55-
var functions = declarations
56-
.Where(declaration => ReturningMemberTypes.Contains(declaration.DeclarationType)
57-
&& !interfaceMembers.Contains(declaration)).ToList();
58-
59-
var unassigned = (from function in functions
60-
let isUdt = IsReturningUserDefinedType(function)
61-
let inScopeRefs = function.References.Where(r => r.ParentScoping.Equals(function))
62-
where (!isUdt && (!inScopeRefs.Any(r => r.IsAssignment) &&
63-
!inScopeRefs.Any(reference => IsAssignedByRefArgument(function, reference))))
64-
|| (isUdt && !IsUserDefinedTypeAssigned(function))
65-
select function)
66-
.ToList();
58+
var unassigned = functions.Where(function => IsReturningUserDefinedType(function)
59+
&& !IsUserDefinedTypeAssigned(function)
60+
|| !IsReturningUserDefinedType(function)
61+
&& !IsAssigned(function));
6762

6863
return unassigned
64+
.Where(declaration => !declaration.IsIgnoringInspectionResultFor(AnnotationName))
6965
.Select(issue =>
7066
new DeclarationInspectionResult(this,
7167
string.Format(InspectionResults.NonReturningFunctionInspection, issue.IdentifierName),
7268
issue));
7369
}
7470

71+
private bool IsAssigned(Declaration function)
72+
{
73+
var inScopeIdentifierReferences = function.References.Where(r => r.ParentScoping.Equals(function));
74+
return inScopeIdentifierReferences.Any(reference => reference.IsAssignment
75+
|| IsAssignedByRefArgument(function, reference));
76+
}
77+
7578
private bool IsAssignedByRefArgument(Declaration enclosingProcedure, IdentifierReference reference)
7679
{
7780
var argExpression = reference.Context.GetAncestor<VBAParser.ArgumentExpressionContext>();
@@ -83,7 +86,7 @@ private bool IsAssignedByRefArgument(Declaration enclosingProcedure, IdentifierR
8386
&& parameter.References.Any(r => r.IsAssignment);
8487
}
8588

86-
private bool IsReturningUserDefinedType(Declaration member)
89+
private static bool IsReturningUserDefinedType(Declaration member)
8790
{
8891
return member.AsTypeDeclaration != null &&
8992
member.AsTypeDeclaration.DeclarationType == DeclarationType.UserDefinedType;

0 commit comments

Comments
 (0)