Skip to content

Commit 06982ea

Browse files
committed
Merge pull request #715 from Hosch250/next
Inspection tests
2 parents 59ab422 + 13c09e1 commit 06982ea

36 files changed

+3634
-96
lines changed

RetailCoder.VBE/Inspections/AssignedByValParameterInspection.cs

Lines changed: 4 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -7,14 +7,15 @@
77

88
namespace Rubberduck.Inspections
99
{
10-
public class AssignedByValParameterInspection //: IInspection /* note: deferred to v1.4 */
10+
public class AssignedByValParameterInspection : IInspection
1111
{
1212
public AssignedByValParameterInspection()
1313
{
1414
Severity = CodeInspectionSeverity.Warning;
1515
}
1616

17-
public string Name { get { return RubberduckUI.ByValParameterIsAssigned_; } }
17+
public string Name { get { return "AssignedByValParameterInspection"; } }
18+
public string Description { get { return RubberduckUI.ByValParameterIsAssigned_; } }
1819
public CodeInspectionType InspectionType { get { return CodeInspectionType.CodeQualityIssues; } }
1920
public CodeInspectionSeverity Severity { get; set; }
2021

@@ -27,7 +28,7 @@ public IEnumerable<CodeInspectionResultBase> GetInspectionResults(VBProjectParse
2728
&& declaration.References.Any(reference => reference.IsAssignment));
2829

2930
var issues = assignedByValParameters
30-
.Select(param => new AssignedByValParameterInspectionResult(string.Format(Name, param.IdentifierName), Severity, param.Context, param.QualifiedName));
31+
.Select(param => new AssignedByValParameterInspectionResult(string.Format(Description, param.IdentifierName), Severity, param.Context, param.QualifiedName));
3132

3233
return issues;
3334
}

RetailCoder.VBE/Inspections/CodeInspectionResultBase.cs

Lines changed: 1 addition & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -5,19 +5,15 @@
55
using Rubberduck.Parsing.Nodes;
66
using Rubberduck.Parsing.Symbols;
77
using Rubberduck.VBEditor;
8-
using Rubberduck.VBEditor.VBEInterfaces.RubberduckCodePane;
98

109
namespace Rubberduck.Inspections
1110
{
1211
public abstract class CodeInspectionResultBase : ICodeInspectionResult
1312
{
14-
private readonly IRubberduckCodePaneFactory _factory;
15-
16-
protected CodeInspectionResultBase(string inspection, CodeInspectionSeverity type, Declaration target, IRubberduckCodePaneFactory factory)
13+
protected CodeInspectionResultBase(string inspection, CodeInspectionSeverity type, Declaration target)
1714
: this(inspection, type, target.QualifiedName.QualifiedModuleName, null)
1815
{
1916
_target = target;
20-
_factory = factory;
2117
}
2218

2319
/// <summary>

RetailCoder.VBE/Inspections/DefaultProjectNameInspection.cs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -7,17 +7,17 @@
77

88
namespace Rubberduck.Inspections
99
{
10-
class GenericProjectNameInspection : IInspection
10+
public class DefaultProjectNameInspection : IInspection
1111
{
1212
private readonly IRubberduckCodePaneFactory _factory;
1313

14-
public GenericProjectNameInspection()
14+
public DefaultProjectNameInspection()
1515
{
1616
_factory = new RubberduckCodePaneFactory();
1717
Severity = CodeInspectionSeverity.Suggestion;
1818
}
1919

20-
public string Name { get { return "GenericProjectNameInspection"; } }
20+
public string Name { get { return "DefaultProjectNameInspection"; } }
2121
public string Description { get { return RubberduckUI.GenericProjectName_; } }
2222
public CodeInspectionType InspectionType { get { return CodeInspectionType.MaintainabilityAndReadabilityIssues; } }
2323
public CodeInspectionSeverity Severity { get; set; }
@@ -28,7 +28,7 @@ public IEnumerable<CodeInspectionResultBase> GetInspectionResults(VBProjectParse
2828
.Where(declaration => !declaration.IsBuiltIn
2929
&& declaration.DeclarationType == DeclarationType.Project
3030
&& declaration.IdentifierName.StartsWith("VBAProject"))
31-
.Select(issue => new GenericProjectNameInspectionResult(string.Format(Description, issue.IdentifierName), Severity, issue, parseResult, _factory))
31+
.Select(issue => new DefaultProjectNameInspectionResult(string.Format(Description, issue.IdentifierName), Severity, issue, parseResult, _factory))
3232
.ToList();
3333

3434
return issues;

RetailCoder.VBE/Inspections/DefaultProjectNameInspectionResult.cs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -10,13 +10,13 @@
1010

1111
namespace Rubberduck.Inspections
1212
{
13-
public class GenericProjectNameInspectionResult : CodeInspectionResultBase
13+
public class DefaultProjectNameInspectionResult : CodeInspectionResultBase
1414
{
1515
private readonly VBProjectParseResult _parseResult;
1616
private readonly IRubberduckCodePaneFactory _factory;
1717

18-
public GenericProjectNameInspectionResult(string inspection, CodeInspectionSeverity type, Declaration target, VBProjectParseResult parseResult, IRubberduckCodePaneFactory factory)
19-
: base(inspection, type, target, factory)
18+
public DefaultProjectNameInspectionResult(string inspection, CodeInspectionSeverity type, Declaration target, VBProjectParseResult parseResult, IRubberduckCodePaneFactory factory)
19+
: base(inspection, type, target)
2020
{
2121
_parseResult = parseResult;
2222
_factory = factory;

RetailCoder.VBE/Inspections/ImplicitByRefParameterInspection.cs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -22,11 +22,12 @@ public ImplicitByRefParameterInspection()
2222
public IEnumerable<CodeInspectionResultBase> GetInspectionResults(VBProjectParseResult parseResult)
2323
{
2424
var interfaceMembers = parseResult.Declarations.FindInterfaceImplementationMembers();
25+
2526
var issues = (from item in parseResult.Declarations.Items
2627
where item.DeclarationType == DeclarationType.Parameter
2728
&& !item.IsBuiltIn
2829
&& !interfaceMembers.Select(m => m.Scope).Contains(item.ParentScope)
29-
let arg = item.Context.Parent as VBAParser.ArgContext
30+
let arg = item.Context as VBAParser.ArgContext
3031
where arg != null && arg.BYREF() == null && arg.BYVAL() == null
3132
select new QualifiedContext<VBAParser.ArgContext>(item.QualifiedName, arg))
3233
.Select(issue => new ImplicitByRefParameterInspectionResult(string.Format(Description, issue.Context.ambiguousIdentifier().GetText()), Severity, issue));
Lines changed: 0 additions & 33 deletions
Original file line numberDiff line numberDiff line change
@@ -1,9 +1,7 @@
1-
using System;
21
using System.Collections.Generic;
32
using System.Linq;
43
using Antlr4.Runtime;
54
using Rubberduck.Parsing;
6-
using Rubberduck.Parsing.Grammar;
75
using Rubberduck.Parsing.Symbols;
86
using Rubberduck.UI;
97

@@ -38,36 +36,5 @@ public IEnumerable<CodeInspectionResultBase> GetInspectionResults(VBProjectParse
3836
select new ImplicitVariantReturnTypeInspectionResult(string.Format(Description, issue.Declaration.IdentifierName), Severity, issue.QualifiedContext);
3937
return issues;
4038
}
41-
42-
private static readonly IEnumerable<Func<ParserRuleContext, VBAParser.AsTypeClauseContext>> Converters =
43-
new List<Func<ParserRuleContext, VBAParser.AsTypeClauseContext>>
44-
{
45-
GetFunctionReturnType,
46-
GetPropertyGetReturnType
47-
};
48-
49-
private VBAParser.AsTypeClauseContext GetAsTypeClause(ParserRuleContext procedureContext)
50-
{
51-
return Converters.Select(converter => converter(procedureContext)).FirstOrDefault(args => args != null);
52-
}
53-
54-
private static bool HasExpectedReturnType(QualifiedContext<ParserRuleContext> procedureContext)
55-
{
56-
var function = procedureContext.Context as VBAParser.FunctionStmtContext;
57-
var getter = procedureContext.Context as VBAParser.PropertyGetStmtContext;
58-
return function != null || getter != null;
59-
}
60-
61-
private static VBAParser.AsTypeClauseContext GetFunctionReturnType(ParserRuleContext procedureContext)
62-
{
63-
var context = procedureContext as VBAParser.FunctionStmtContext;
64-
return context == null ? null : context.asTypeClause();
65-
}
66-
67-
private static VBAParser.AsTypeClauseContext GetPropertyGetReturnType(ParserRuleContext procedureContext)
68-
{
69-
var context = procedureContext as VBAParser.PropertyGetStmtContext;
70-
return context == null ? null : context.asTypeClause();
71-
}
7239
}
7340
}

RetailCoder.VBE/Inspections/MultilineParameterInspection.cs

Lines changed: 0 additions & 18 deletions
Original file line numberDiff line numberDiff line change
@@ -1,11 +1,8 @@
1-
using System;
21
using System.Collections.Generic;
32
using System.Linq;
4-
using Antlr4.Runtime;
53
using Rubberduck.Parsing;
64
using Rubberduck.Parsing.Symbols;
75
using Rubberduck.UI;
8-
using Rubberduck.VBEditor;
96

107
namespace Rubberduck.Inspections
118
{
@@ -33,20 +30,5 @@ where p.Context.GetSelection().LineCount > 1
3330

3431
return issues;
3532
}
36-
37-
public class MultilineParameterInspectionResult : CodeInspectionResultBase
38-
{
39-
public MultilineParameterInspectionResult(string inspection, CodeInspectionSeverity severity, ParserRuleContext context, QualifiedMemberName qualifiedName)
40-
: base(inspection, severity, qualifiedName.QualifiedModuleName, context)
41-
{
42-
43-
}
44-
45-
public override IDictionary<string, Action> GetQuickFixes()
46-
{
47-
// todo: implement a quickfix to rewrite the signature on 1 line
48-
return new Dictionary<string, Action>();
49-
}
50-
}
5133
}
5234
}
Lines changed: 51 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,51 @@
1+
using System;
2+
using System.Collections.Generic;
3+
using Antlr4.Runtime;
4+
using Rubberduck.UI;
5+
using Rubberduck.VBA;
6+
using Rubberduck.VBEditor;
7+
8+
namespace Rubberduck.Inspections
9+
{
10+
public class MultilineParameterInspectionResult : CodeInspectionResultBase
11+
{
12+
public MultilineParameterInspectionResult(string inspection, CodeInspectionSeverity severity, ParserRuleContext context, QualifiedMemberName qualifiedName)
13+
: base(inspection, severity, qualifiedName.QualifiedModuleName, context)
14+
{
15+
16+
}
17+
18+
public override IDictionary<string, Action> GetQuickFixes()
19+
{
20+
return new Dictionary<string, Action>
21+
{
22+
{RubberduckUI.Inspections_MultilineParameter, WriteParamOnOneLine}
23+
};
24+
}
25+
26+
private void WriteParamOnOneLine()
27+
{
28+
var module = QualifiedName.Component.CodeModule;
29+
var selection = QualifiedSelection.Selection;
30+
31+
var lines = module.Lines[selection.StartLine, selection.EndLine - selection.StartLine + 1];
32+
33+
var startLine = module.Lines[selection.StartLine, 1];
34+
var endLine = module.Lines[selection.EndLine, 1];
35+
36+
var adjustedStartColumn = selection.StartColumn - 1;
37+
var adjustedEndColumn = lines.Length - (endLine.Length - (selection.EndColumn > endLine.Length ? endLine.Length : selection.EndColumn - 1));
38+
39+
var parameter = lines.Substring(adjustedStartColumn,
40+
adjustedEndColumn - adjustedStartColumn)
41+
.Replace("_", "")
42+
.RemoveExtraSpaces();
43+
44+
var start = startLine.Remove(adjustedStartColumn);
45+
var end = lines.Remove(0, adjustedEndColumn);
46+
47+
module.ReplaceLine(selection.StartLine, start + parameter + end);
48+
module.DeleteLines(selection.StartLine + 1, selection.EndLine - selection.StartLine);
49+
}
50+
}
51+
}

RetailCoder.VBE/Inspections/MultipleDeclarationsInspection.cs

Lines changed: 1 addition & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -4,17 +4,14 @@
44
using Rubberduck.Parsing;
55
using Rubberduck.Parsing.Symbols;
66
using Rubberduck.UI;
7-
using Rubberduck.VBEditor.VBEInterfaces.RubberduckCodePane;
87

98
namespace Rubberduck.Inspections
109
{
1110
public class MultipleDeclarationsInspection : IInspection
1211
{
13-
private readonly IRubberduckCodePaneFactory _factory;
1412

1513
public MultipleDeclarationsInspection()
1614
{
17-
_factory = new RubberduckCodePaneFactory();
1815
Severity = CodeInspectionSeverity.Warning;
1916
}
2017

@@ -31,7 +28,7 @@ public IEnumerable<CodeInspectionResultBase> GetInspectionResults(VBProjectParse
3128
|| item.DeclarationType == DeclarationType.Constant)
3229
.GroupBy(variable => variable.Context.Parent as ParserRuleContext)
3330
.Where(grouping => grouping.Count() > 1)
34-
.Select(grouping => new MultipleDeclarationsInspectionResult(Description, Severity, new QualifiedContext<ParserRuleContext>(grouping.First().QualifiedName.QualifiedModuleName, grouping.Key), _factory));
31+
.Select(grouping => new MultipleDeclarationsInspectionResult(Description, Severity, new QualifiedContext<ParserRuleContext>(grouping.First().QualifiedName.QualifiedModuleName, grouping.Key)));
3532

3633
return issues;
3734
}

RetailCoder.VBE/Inspections/MultipleDeclarationsInspectionResult.cs

Lines changed: 1 addition & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -6,19 +6,15 @@
66
using Rubberduck.Parsing.Grammar;
77
using Rubberduck.UI;
88
using Rubberduck.VBEditor;
9-
using Rubberduck.VBEditor.VBEInterfaces.RubberduckCodePane;
109

1110
namespace Rubberduck.Inspections
1211
{
1312
public class MultipleDeclarationsInspectionResult : CodeInspectionResultBase
1413
{
15-
private readonly IRubberduckCodePaneFactory _factory;
16-
1714
public MultipleDeclarationsInspectionResult(string inspection, CodeInspectionSeverity type,
18-
QualifiedContext<ParserRuleContext> qualifiedContext, IRubberduckCodePaneFactory factory)
15+
QualifiedContext<ParserRuleContext> qualifiedContext)
1916
: base(inspection, type, qualifiedContext.ModuleName, qualifiedContext.Context)
2017
{
21-
_factory = factory;
2218
}
2319

2420
public override IDictionary<string, Action> GetQuickFixes()

0 commit comments

Comments
 (0)