Skip to content

Commit 5f06ac2

Browse files
committed
Allow ignoring Hungarian notation, do not report for library procedures. Closes #3932
1 parent 91cf0d8 commit 5f06ac2

File tree

2 files changed

+78
-6
lines changed

2 files changed

+78
-6
lines changed

Rubberduck.CodeAnalysis/Inspections/Concrete/HungarianNotationInspection.cs

Lines changed: 11 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -94,8 +94,14 @@ public sealed class HungarianNotationInspection : InspectionBase
9494
DeclarationType.Variable
9595
};
9696

97+
private static readonly List<DeclarationType> IgnoredProcedureTypes = new List<DeclarationType>
98+
{
99+
DeclarationType.LibraryFunction,
100+
DeclarationType.LibraryProcedure
101+
};
102+
97103
#endregion
98-
104+
99105
private readonly IPersistanceService<CodeInspectionSettings> _settings;
100106

101107
public HungarianNotationInspection(RubberduckParserState state, IPersistanceService<CodeInspectionSettings> settings)
@@ -112,7 +118,10 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
112118
var hungarians = UserDeclarations
113119
.Where(declaration => !whitelistedNames.Contains(declaration.IdentifierName) &&
114120
TargetDeclarationTypes.Contains(declaration.DeclarationType) &&
115-
HungarianIdentifierRegex.IsMatch(declaration.IdentifierName))
121+
!IgnoredProcedureTypes.Contains(declaration.DeclarationType) &&
122+
!IgnoredProcedureTypes.Contains(declaration.ParentDeclaration.DeclarationType) &&
123+
HungarianIdentifierRegex.IsMatch(declaration.IdentifierName) &&
124+
!IsIgnoringInspectionResultFor(declaration, AnnotationName))
116125
.Select(issue => new DeclarationInspectionResult(this,
117126
string.Format(Resources.Inspections.InspectionResults.IdentifierNameInspection,
118127
RubberduckUI.ResourceManager.GetString($"DeclarationType_{issue.DeclarationType}", CultureInfo.CurrentUICulture),

RubberduckTests/Inspections/HungarianNotationInspectionTests.cs

Lines changed: 67 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -200,12 +200,75 @@ Dim oRange As Object
200200

201201
[Test]
202202
[Category("Inspections")]
203-
public void InspectionName()
203+
public void HungarianNotation_DoesNotReturnResult_Ignored()
204204
{
205-
const string inspectionName = "UseMeaningfulNameInspection";
206-
var inspection = new UseMeaningfulNameInspection(null, null);
205+
const string inputCode =
206+
@"Sub Hungarian()
207+
'@Ignore HungarianNotation
208+
Dim oFoo As Object
209+
End Sub";
210+
211+
var builder = new MockVbeBuilder();
212+
var project = builder.ProjectBuilder("VBAProject", ProjectProtection.Unprotected)
213+
.AddComponent("MyClass", ComponentType.ClassModule, inputCode)
214+
.Build();
215+
var vbe = builder.AddProject(project).Build();
216+
217+
using (var state = MockParser.CreateAndParse(vbe.Object))
218+
{
219+
var inspection = new HungarianNotationInspection(state, UseMeaningfulNameInspectionTests.GetInspectionSettings().Object);
220+
var inspectionResults = inspection.GetInspectionResults(CancellationToken.None);
221+
222+
Assert.AreEqual(0, inspectionResults.Count());
223+
}
224+
}
225+
226+
[Test]
227+
[Category("Inspections")]
228+
public void HungarianNotation_DoesNotReturnResult_LibraryFunctionParameters()
229+
{
230+
const string inputCode =
231+
@"
232+
Private Declare Function GetUserName Lib ""advapi32.dll"" Alias ""GetUserNameA"" (ByVal lpBuffer As String, nSize As Long) As Long
233+
";
234+
235+
var builder = new MockVbeBuilder();
236+
var project = builder.ProjectBuilder("VBAProject", ProjectProtection.Unprotected)
237+
.AddComponent("MyClass", ComponentType.ClassModule, inputCode)
238+
.Build();
239+
var vbe = builder.AddProject(project).Build();
240+
241+
using (var state = MockParser.CreateAndParse(vbe.Object))
242+
{
243+
var inspection = new HungarianNotationInspection(state, UseMeaningfulNameInspectionTests.GetInspectionSettings().Object);
244+
var inspectionResults = inspection.GetInspectionResults(CancellationToken.None);
207245

208-
Assert.AreEqual(inspectionName, inspection.Name);
246+
Assert.AreEqual(0, inspectionResults.Count());
247+
}
248+
}
249+
250+
[Test]
251+
[Category("Inspections")]
252+
public void HungarianNotation_DoesNotReturnResult_LibraryFunction()
253+
{
254+
const string inputCode =
255+
@"
256+
Private Declare Sub chkVoid Lib ""somelib.dll"" Alias ""chkVoidA"" (number As Long)
257+
";
258+
259+
var builder = new MockVbeBuilder();
260+
var project = builder.ProjectBuilder("VBAProject", ProjectProtection.Unprotected)
261+
.AddComponent("MyClass", ComponentType.ClassModule, inputCode)
262+
.Build();
263+
var vbe = builder.AddProject(project).Build();
264+
265+
using (var state = MockParser.CreateAndParse(vbe.Object))
266+
{
267+
var inspection = new HungarianNotationInspection(state, UseMeaningfulNameInspectionTests.GetInspectionSettings().Object);
268+
var inspectionResults = inspection.GetInspectionResults(CancellationToken.None);
269+
270+
Assert.AreEqual(0, inspectionResults.Count());
271+
}
209272
}
210273
}
211274
}

0 commit comments

Comments
 (0)