Skip to content

Commit d927937

Browse files
committed
Merge remote-tracking branch 'upstream/next' into rkapka-master
# Conflicts: # RubberduckTests/RubberduckTests.csproj
2 parents e11b25b + 358c3c3 commit d927937

File tree

7 files changed

+263
-4
lines changed

7 files changed

+263
-4
lines changed

RetailCoder.VBE/UI/Inspections/InspectionResultsControl.xaml

Lines changed: 0 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -5,8 +5,6 @@
55
xmlns:d="http://schemas.microsoft.com/expression/blend/2008"
66
xmlns:codeInspections="clr-namespace:Rubberduck.UI.Inspections"
77
xmlns:controls="clr-namespace:Rubberduck.UI.Controls"
8-
xmlns:themes="clr-namespace:Microsoft.Windows.Themes;assembly=PresentationFramework.Aero"
9-
xmlns:converters="clr-namespace:Rubberduck.UI.Converters"
108
xmlns:abstract1="clr-namespace:Rubberduck.Parsing.Inspections.Abstract;assembly=Rubberduck.Parsing"
119
ResxExtension.DefaultResxName="Rubberduck.UI.RubberduckUI"
1210
Language="{UICulture}"
@@ -19,8 +17,6 @@
1917
<ResourceDictionary Source="../Controls/ToolBar.xaml"/>
2018
</ResourceDictionary.MergedDictionaries>
2119

22-
<converters:InvertBoolValueConverter x:Key="InvertBoolValue" />
23-
2420
<BooleanToVisibilityConverter x:Key="BoolToVisibility"/>
2521

2622
<codeInspections:InspectionSeverityImageSourceConverter x:Key="SeverityIconConverter" />
Lines changed: 77 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,77 @@
1+
using System.Collections.Generic;
2+
using System.Linq;
3+
using Rubberduck.Inspections.Abstract;
4+
using Rubberduck.Parsing.VBA;
5+
using Rubberduck.Parsing.Inspections.Resources;
6+
using Rubberduck.Parsing.Inspections.Abstract;
7+
using Rubberduck.Parsing.Grammar;
8+
using Antlr4.Runtime;
9+
using Rubberduck.Parsing;
10+
using Rubberduck.VBEditor;
11+
using Antlr4.Runtime.Misc;
12+
using Rubberduck.Inspections.Results;
13+
14+
namespace Rubberduck.Inspections.Concrete
15+
{
16+
public sealed class DefTypeStatementInspection : ParseTreeInspectionBase
17+
{
18+
public DefTypeStatementInspection(RubberduckParserState state)
19+
: base(state, CodeInspectionSeverity.Suggestion)
20+
{
21+
Listener = new DefTypeStatementInspectionListener();
22+
}
23+
24+
public override CodeInspectionType InspectionType => CodeInspectionType.LanguageOpportunities;
25+
public override IInspectionListener Listener { get; }
26+
27+
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
28+
{
29+
var results = Listener.Contexts.Where(context => !IsIgnoringInspectionResultFor(context.ModuleName, context.Context.Start.Line))
30+
.Select(context => new QualifiedContextInspectionResult(this,
31+
string.Format(InspectionsUI.DefTypeStatementInspectionResultFormat,
32+
GetTypeOfDefType(context.Context.start.Text),
33+
context.Context.start.Text),
34+
context));
35+
return results;
36+
}
37+
38+
public class DefTypeStatementInspectionListener : VBAParserBaseListener, IInspectionListener
39+
{
40+
private readonly List<QualifiedContext<ParserRuleContext>> _contexts = new List<QualifiedContext<ParserRuleContext>>();
41+
public IReadOnlyList<QualifiedContext<ParserRuleContext>> Contexts => _contexts;
42+
43+
public QualifiedModuleName CurrentModuleName { get; set; }
44+
45+
public void ClearContexts()
46+
{
47+
_contexts.Clear();
48+
}
49+
50+
public override void ExitDefType([NotNull] VBAParser.DefTypeContext context)
51+
{
52+
_contexts.Add(new QualifiedContext<ParserRuleContext>(CurrentModuleName, context));
53+
}
54+
}
55+
56+
private string GetTypeOfDefType(string defType)
57+
{
58+
_defTypes.TryGetValue(defType, out var value);
59+
return value;
60+
}
61+
62+
private readonly Dictionary<string, string> _defTypes = new Dictionary<string, string>
63+
{
64+
{ "DefBool", "Boolean" },
65+
{ "DefByte", "Byte" },
66+
{ "DefInt", "Integer" },
67+
{ "DefLng", "Long" },
68+
{ "DefCur", "Currency" },
69+
{ "DefSng", "Single" },
70+
{ "DefDbl", "Double" },
71+
{ "DefDate", "Date" },
72+
{ "DefStr", "String" },
73+
{ "DefObj", "Object" },
74+
{ "DefVar", "Variant" }
75+
};
76+
}
77+
}

Rubberduck.Inspections/Rubberduck.Inspections.csproj

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -61,6 +61,7 @@
6161
<Compile Include="Abstract\ParseTreeInspectionBase.cs" />
6262
<Compile Include="Concrete\ApplicationWorksheetFunctionInspection.cs" />
6363
<Compile Include="Concrete\AssignedByValParameterInspection.cs" />
64+
<Compile Include="Concrete\DefTypeStatementInspection.cs" />
6465
<Compile Include="Concrete\EmptyModuleInspection.cs" />
6566
<Compile Include="Concrete\EmptyBlockInspectionListenerBase.cs" />
6667
<Compile Include="Concrete\EmptyCaseBlockInspection.cs" />

Rubberduck.Parsing/Inspections/Resources/InspectionsUI.Designer.cs

Lines changed: 27 additions & 0 deletions
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

Rubberduck.Parsing/Inspections/Resources/InspectionsUI.resx

Lines changed: 9 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -902,4 +902,13 @@ If the parameter can be null, ignore this inspection result; passing a null valu
902902
<data name="UnhandledOnErrorResumeNextInspectionResultFormat" xml:space="preserve">
903903
<value>Errors are ignored but never handled again</value>
904904
</data>
905+
<data name="DefTypeStatementInspectionMeta" xml:space="preserve">
906+
<value>Using the 'Def[Type]' statement leads to specifying types by using a prefix. This style of naming is heavily discouraged and should be avoided.</value>
907+
</data>
908+
<data name="DefTypeStatementInspectionName" xml:space="preserve">
909+
<value>Usage of 'Def[Type]' statement</value>
910+
</data>
911+
<data name="DefTypeStatementInspectionResultFormat" xml:space="preserve">
912+
<value>Consider the explicit use of 'as {0}' instead of '{1}'</value>
913+
</data>
905914
</root>
Lines changed: 148 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,148 @@
1+
using NUnit.Framework;
2+
using Rubberduck.Parsing.Inspections.Resources;
3+
using Rubberduck.Inspections.Concrete;
4+
using RubberduckTests.Mocks;
5+
using System.Threading;
6+
using System.Linq;
7+
8+
namespace RubberduckTests.Inspections
9+
{
10+
[TestFixture]
11+
public class DefTypeStatementInspectionTests
12+
{
13+
[Test]
14+
[Category("Inspections")]
15+
public void DefType_InspectionType()
16+
{
17+
var inspection = new DefTypeStatementInspection(null);
18+
const CodeInspectionType expectedInspection = CodeInspectionType.LanguageOpportunities;
19+
20+
Assert.AreEqual(expectedInspection, inspection.InspectionType);
21+
}
22+
23+
[Test]
24+
[TestCase("Bool")]
25+
[TestCase("Byte")]
26+
[TestCase("Int")]
27+
[TestCase("Lng")]
28+
[TestCase("Cur")]
29+
[TestCase("Sng")]
30+
[TestCase("Dbl")]
31+
[TestCase("Date")]
32+
[TestCase("Str")]
33+
[TestCase("Obj")]
34+
[TestCase("Var")]
35+
[Category("Inspections")]
36+
public void DefType_SingleResultFound(string type)
37+
{
38+
const string inputCode =
39+
@"Def{0} A
40+
Public Function aFoo()
41+
End Function";
42+
43+
var vbe = MockVbeBuilder.BuildFromSingleStandardModule(string.Format(inputCode, type), out _);
44+
using (var state = MockParser.CreateAndParse(vbe.Object))
45+
{
46+
var inspection = new DefTypeStatementInspection(state);
47+
var inspector = InspectionsHelper.GetInspector(inspection);
48+
var inspectionResults = inspector.FindIssuesAsync(state, CancellationToken.None).Result;
49+
50+
Assert.AreEqual(1, inspectionResults.Count());
51+
}
52+
}
53+
54+
[Test]
55+
[TestCase("Bool")]
56+
[TestCase("Byte")]
57+
[TestCase("Int")]
58+
[TestCase("Lng")]
59+
[TestCase("Cur")]
60+
[TestCase("Sng")]
61+
[TestCase("Dbl")]
62+
[TestCase("Date")]
63+
[TestCase("Str")]
64+
[TestCase("Obj")]
65+
[TestCase("Var")]
66+
[Category("Inspections")]
67+
public void DefType_SingleResultIgnored(string type)
68+
{
69+
const string inputCode =
70+
@"'@Ignore DefTypeStatement
71+
Def{0} F
72+
Public Function FunctionWontBeFoundInResult()
73+
End Function";
74+
75+
var vbe = MockVbeBuilder.BuildFromSingleStandardModule(string.Format(inputCode, type), out _);
76+
using (var state = MockParser.CreateAndParse(vbe.Object))
77+
{
78+
var inspection = new DefTypeStatementInspection(state);
79+
var inspector = InspectionsHelper.GetInspector(inspection);
80+
var inspectionResults = inspector.FindIssuesAsync(state, CancellationToken.None).Result;
81+
82+
Assert.AreEqual(0, inspectionResults.Count());
83+
}
84+
}
85+
86+
[Test]
87+
[Category("Inspections")]
88+
public void DefType_AllDefTypeAreFound()
89+
{
90+
const string inputCode =
91+
@"DefBool A
92+
DefByte B
93+
DefInt C
94+
DefLng D
95+
DefCur E
96+
DefSng F
97+
DefDbl G
98+
DefDate H
99+
DefStr I
100+
DefObj J
101+
DefVar K
102+
Public Function Zoo()
103+
End Function";
104+
105+
var vbe = MockVbeBuilder.BuildFromSingleStandardModule(inputCode, out _);
106+
using (var state = MockParser.CreateAndParse(vbe.Object))
107+
{
108+
var inspection = new DefTypeStatementInspection(state);
109+
var inspector = InspectionsHelper.GetInspector(inspection);
110+
var inspectionResults = inspector.FindIssuesAsync(state, CancellationToken.None).Result;
111+
112+
Assert.AreEqual(11, inspectionResults.Count());
113+
}
114+
}
115+
116+
[Test]
117+
[Category("Inspections")]
118+
public void DefType_AllDefTypeAreIgnored()
119+
{
120+
const string inputCode =
121+
@"'@Ignore DefTypeStatement
122+
DefBool A
123+
DefByte B
124+
DefInt C
125+
DefLng D
126+
DefCur E
127+
DefSng F
128+
DefDbl G
129+
DefDate H
130+
DefStr I
131+
DefObj J
132+
DefVar K
133+
Public Function Zoo()
134+
End Function";
135+
136+
var vbe = MockVbeBuilder.BuildFromSingleStandardModule(inputCode, out _);
137+
using (var state = MockParser.CreateAndParse(vbe.Object))
138+
{
139+
var inspection = new DefTypeStatementInspection(state);
140+
var inspector = InspectionsHelper.GetInspector(inspection);
141+
var inspectionResults = inspector.FindIssuesAsync(state, CancellationToken.None).Result;
142+
143+
Assert.AreEqual(0, inspectionResults.Count());
144+
}
145+
}
146+
147+
}
148+
}

RubberduckTests/RubberduckTests.csproj

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -105,6 +105,7 @@
105105
<Compile Include="Binding\SimpleNameTypeBindingTests.cs" />
106106
<Compile Include="CodeExplorer\CodeExplorerTests.cs" />
107107
<Compile Include="Settings\CodeInspectionConfigProviderTests.cs" />
108+
<Compile Include="Inspections\DefTypeStatementInspectionTests.cs" />
108109
<Compile Include="VBEditor\ComSafeManagerTests.cs" />
109110
<Compile Include="VBEditor\ReferenceEqualityComparerTests.cs" />
110111
<Compile Include="VBEditor\ComSafeTests.cs" />

0 commit comments

Comments
 (0)