Skip to content

Commit 9d42028

Browse files
committed
Correctly handle leading whitespace on a line
1 parent b6ac898 commit 9d42028

File tree

3 files changed

+76
-22
lines changed

3 files changed

+76
-22
lines changed

RetailCoder.VBE/Navigation/CodeMetrics/CodeMetricsAnalyst.cs

Lines changed: 25 additions & 22 deletions
Original file line numberDiff line numberDiff line change
@@ -23,6 +23,7 @@ public IEnumerable<ModuleMetricsResult> ModuleMetrics(RubberduckParserState stat
2323
{
2424
if (state == null || !state.AllUserDeclarations.Any())
2525
{
26+
// must not return Enumerable.Empty
2627
yield break;
2728
}
2829

@@ -68,24 +69,31 @@ public CodeMetricsListener(DeclarationFinder finder, IIndenterSettings indenterS
6869

6970
public override void EnterEndOfLine([NotNull] VBAParser.EndOfLineContext context)
7071
{
71-
(currentMember == null ? moduleResults : results).Add(new CodeMetricsResult(1, 0, 0));
72+
int followingIndentationLevel = 0;
73+
// we have a proper newline
74+
if (context.NEWLINE() != null)
75+
{
76+
// the last whitespace, which is the one in front of the next line's contents
77+
var followingWhitespace = context.whiteSpace().LastOrDefault();
78+
followingIndentationLevel = IndentationLevelFromWhitespace(followingWhitespace);
79+
}
80+
(currentMember == null ? moduleResults : results).Add(new CodeMetricsResult(1, 0, followingIndentationLevel));
7281
}
7382

7483
public override void EnterIfStmt([NotNull] VBAParser.IfStmtContext context)
7584
{
76-
// one additional path beside the default
7785
results.Add(new CodeMetricsResult(0, 1, 0));
7886
}
7987

8088
public override void EnterElseIfBlock([NotNull] VBAParser.ElseIfBlockContext context)
8189
{
82-
// one additonal path beside the default
8390
results.Add(new CodeMetricsResult(0, 1, 0));
8491
}
8592

93+
// notably: NO additional complexity for an Else-Block
94+
8695
public override void EnterForEachStmt([NotNull] VBAParser.ForEachStmtContext context)
8796
{
88-
// one additional path
8997
results.Add(new CodeMetricsResult(0, 1, 0));
9098
}
9199

@@ -101,78 +109,73 @@ public override void EnterCaseClause([NotNull] VBAParser.CaseClauseContext conte
101109

102110
public override void EnterSubStmt([NotNull] VBAParser.SubStmtContext context)
103111
{
104-
// this is the default path through the sub
105112
results.Add(new CodeMetricsResult(0, 1, 0));
106-
107-
// if First borks, we got a bigger problems
108113
currentMember = _finder.DeclarationsWithType(DeclarationType.Procedure).Where(d => d.Context == context).First();
109114
}
110115

111116
public override void ExitSubStmt([NotNull] VBAParser.SubStmtContext context)
112117
{
113-
// well, we're done here
114118
ExitMeasurableMember();
115119
}
116120

117121
public override void EnterFunctionStmt([NotNull] VBAParser.FunctionStmtContext context)
118122
{
119-
// this is the default path through the function
120123
results.Add(new CodeMetricsResult(0, 1, 0));
121-
122-
// if First borks, we got bigger problems
123124
currentMember = _finder.DeclarationsWithType(DeclarationType.Function).Where(d => d.Context == context).First();
124125
}
125126

126127
public override void ExitFunctionStmt([NotNull] VBAParser.FunctionStmtContext context)
127128
{
128-
// well, we're done here
129129
ExitMeasurableMember();
130130
}
131131

132132
public override void EnterPropertyGetStmt([NotNull] VBAParser.PropertyGetStmtContext context)
133133
{
134134
results.Add(new CodeMetricsResult(0, 1, 0));
135-
136135
currentMember = _finder.DeclarationsWithType(DeclarationType.PropertyGet).Where(d => d.Context == context).First();
137136
}
138137

139138
public override void ExitPropertyGetStmt([NotNull] VBAParser.PropertyGetStmtContext context)
140139
{
141-
// well, we're done here
142140
ExitMeasurableMember();
143141
}
144142

145143
public override void EnterPropertyLetStmt([NotNull] VBAParser.PropertyLetStmtContext context)
146144
{
147145
results.Add(new CodeMetricsResult(0, 1, 0));
148-
149146
currentMember = _finder.DeclarationsWithType(DeclarationType.PropertyLet).Where(d => d.Context == context).First();
150147
}
151148

152149
public override void ExitPropertyLetStmt([NotNull] VBAParser.PropertyLetStmtContext context)
153150
{
154-
// well, we're done here
155151
ExitMeasurableMember();
156152
}
157153

158154
public override void EnterPropertySetStmt([NotNull] VBAParser.PropertySetStmtContext context)
159155
{
160156
results.Add(new CodeMetricsResult(0, 1, 0));
161-
162157
currentMember = _finder.DeclarationsWithType(DeclarationType.PropertySet).Where(d => d.Context == context).First();
163158
}
164159

165160
public override void ExitPropertySetStmt([NotNull] VBAParser.PropertySetStmtContext context)
166-
{
167-
// well, we're done here
161+
{
168162
ExitMeasurableMember();
169163
}
170164

171165
public override void EnterBlockStmt([NotNull] VBAParser.BlockStmtContext context)
172166
{
173-
var ws = context.whiteSpace();
174-
// FIXME only take the last contiguous non-linebreak into account
175-
results.Add(new CodeMetricsResult(0, 0, (ws?.ChildCount ?? 0) / _indenterSettings.IndentSpaces));
167+
// there is a whitespace context here after the option of a statementLabel.
168+
// we need to account for that
169+
results.Add(new CodeMetricsResult(0, 0, IndentationLevelFromWhitespace(context.whiteSpace())));
170+
}
171+
172+
private int IndentationLevelFromWhitespace(VBAParser.WhiteSpaceContext wsContext)
173+
{
174+
if (wsContext == null) return 0;
175+
// the only thing that contains underscores is the line-continuation at this point
176+
var lineContinuation = wsContext.children.LastOrDefault((tree) => tree.GetText().Contains("_"));
177+
var index = lineContinuation != null ? wsContext.children.IndexOf(lineContinuation) : 0;
178+
return (wsContext?.ChildCount ?? 0 - index) / _indenterSettings.IndentSpaces;
176179
}
177180

178181
private void ExitMeasurableMember()

RetailCoder.VBE/UI/RubberduckUI.Designer.cs

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

RubberduckTests/Stats/ParseTreeMetricsAnalystTests.cs

Lines changed: 42 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -278,5 +278,47 @@ End Property
278278
var metrics = cut.ModuleMetrics(state).First();
279279
Assert.AreEqual(1, metrics.Result.CyclomaticComplexity);
280280
}
281+
282+
[TestMethod]
283+
[TestCategory("Code Metrics")]
284+
public void SimpleSub_HasNestingLevel_One()
285+
{
286+
var code = @"
287+
Option Explicit
288+
289+
Public Sub SimpleSub()
290+
'preceding comment just to check
291+
Debug.Print ""this is a test""
292+
End Sub
293+
";
294+
295+
var state = MockParser.ParseString(code, out var _);
296+
var metrics = cut.ModuleMetrics(state).First();
297+
Assert.AreEqual(1, metrics.Result.MaximumNesting);
298+
}
299+
300+
[TestMethod]
301+
[TestCategory("Code Metrics")]
302+
public void WeirdSub_HasNestingLevel_One()
303+
{
304+
var code = @"
305+
Option Explicit
306+
307+
Public Sub WeirdSub()
308+
' some comments
309+
Debug.Print ""An expression, that "" & _
310+
""extends across multiple lines, with "" _
311+
& ""Line continuations that do weird stuff "" & _
312+
""but shouldn't account for nesting""
313+
Debug.Print ""Just to confuse you""
314+
End Sub
315+
";
316+
using (var state = MockParser.ParseString(code, out var _))
317+
{
318+
var metrics = cut.ModuleMetrics(state).First();
319+
Assert.AreEqual(1, metrics.Result.MaximumNesting);
320+
}
321+
}
322+
281323
}
282324
}

0 commit comments

Comments
 (0)