Skip to content

Commit 4f07e75

Browse files
committed
Merge branch 'next' of https://github.com/rubberduck-vba/Rubberduck into InvestigatingPermissiveAssertClass
2 parents d4e2276 + debf4a6 commit 4f07e75

File tree

5 files changed

+52
-4
lines changed

5 files changed

+52
-4
lines changed

Rubberduck.CodeAnalysis/Inspections/Concrete/IllegalAnnotationInspection.cs

Lines changed: 5 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -85,7 +85,8 @@ public void ClearContexts()
8585
private void SetCurrentScope(string memberName = null)
8686
{
8787
_hasMembers = !string.IsNullOrEmpty(memberName);
88-
_isFirstMemberProcessed = _hasMembers;
88+
// this is a one-time toggle until contexts are reset
89+
_isFirstMemberProcessed |= _hasMembers;
8990
_currentScopeDeclaration = _hasMembers ? _members.Value[memberName] : _module.Value;
9091
}
9192

@@ -108,6 +109,9 @@ public override void EnterModule(VBAParser.ModuleContext context)
108109
.Members(CurrentModuleName)
109110
.GroupBy(m => m.IdentifierName)
110111
.ToDictionary(m => m.Key, m => m.First()));
112+
113+
// we did not process the first member of the module we just entered, so reset here
114+
_isFirstMemberProcessed = false;
111115
}
112116

113117
public override void ExitModule(VBAParser.ModuleContext context)

Rubberduck.Core/AutoComplete/AutoCompleteService.cs

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -59,7 +59,7 @@ private void HandleKeyDown(object sender, AutoCompleteEventArgs e)
5959
var qualifiedSelection = module.GetQualifiedSelection();
6060
var pSelection = qualifiedSelection.Value.Selection;
6161

62-
if (_popupShown || (e.Keys != Keys.None && pSelection.LineCount > 1))
62+
if (_popupShown || (e.Keys != Keys.None && pSelection.LineCount > 1) || e.Keys == Keys.Delete)
6363
{
6464
return;
6565
}
@@ -78,7 +78,6 @@ private void HandleKeyDown(object sender, AutoCompleteEventArgs e)
7878
}
7979
}
8080

81-
var handleDelete = e.Keys == Keys.Delete && pSelection.EndColumn <= currentContent.Length;
8281
var handleBackspace = e.Keys == Keys.Back && pSelection.StartColumn > 1;
8382
var handleTab = e.Keys == Keys.Tab && !pSelection.IsSingleCharacter;
8483
var handleEnter = e.Keys == Keys.Enter && !pSelection.IsSingleCharacter;

Rubberduck.Parsing/Grammar/VBAParser.g4

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -561,7 +561,7 @@ withStmt :
561561
;
562562

563563
// Special forms with special syntax, only available in VBA reports or VB6 forms and pictureboxes.
564-
lineSpecialForm : expression whiteSpace (STEP whiteSpace?)? tuple MINUS (STEP whiteSpace?)? tuple whiteSpace? (COMMA whiteSpace? expression)? whiteSpace? (COMMA whiteSpace? lineSpecialFormOption)?;
564+
lineSpecialForm : expression whiteSpace ((STEP whiteSpace?)? tuple)? MINUS (STEP whiteSpace?)? tuple whiteSpace? (COMMA whiteSpace? expression)? whiteSpace? (COMMA whiteSpace? lineSpecialFormOption)?;
565565
circleSpecialForm : (expression whiteSpace? DOT whiteSpace?)? CIRCLE whiteSpace (STEP whiteSpace?)? tuple (whiteSpace? COMMA whiteSpace? expression)+;
566566
scaleSpecialForm : (expression whiteSpace? DOT whiteSpace?)? SCALE whiteSpace tuple whiteSpace? MINUS whiteSpace? tuple;
567567
pSetSpecialForm : (expression whiteSpace? DOT whiteSpace?)? PSET (whiteSpace STEP)? whiteSpace? tuple whiteSpace? (COMMA whiteSpace? expression)?;

RubberduckTests/Grammar/VBAParserTests.cs

Lines changed: 12 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -2486,6 +2486,18 @@ Sub Test()
24862486
AssertTree(parseResult.Item1, parseResult.Item2, "//lineSpecialForm");
24872487
}
24882488

2489+
[Category("Parser")]
2490+
[Test]
2491+
public void TestLineAccessReport_WithoutStartingTuple()
2492+
{
2493+
string code = @"
2494+
Sub Test()
2495+
Me.Line -(2, 2)
2496+
End Sub";
2497+
var parseResult = Parse(code);
2498+
AssertTree(parseResult.Item1, parseResult.Item2, "//lineSpecialForm");
2499+
}
2500+
24892501
[Category("Parser")]
24902502
[Test]
24912503
public void TestLineAccessReport_WithoutStep()

RubberduckTests/Inspections/IllegalAnnotationsInspectionTests.cs

Lines changed: 33 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -30,6 +30,39 @@ public void NoAnnotation_NoResult()
3030
}
3131
}
3232

33+
[Test]
34+
[Category("Inspections")]
35+
public void FirstMemberAnnotation_IsNotIllegal_InMultipleModules()
36+
{
37+
const string inputCode1 =
38+
@"'@TestModule
39+
'@Folder(""Test"")
40+
Option Explicit
41+
42+
'@ModuleInitialize
43+
Public Sub ModuleInitializeLegal()
44+
End Sub";
45+
const string inputCode2 =
46+
@"'@TestModule
47+
'@Folder(""Test"")
48+
Option Explicit
49+
50+
'@ModuleInitialize
51+
Public Sub ModuleInitializeAlsoLegal()
52+
End Sub";
53+
54+
var vbe = MockVbeBuilder.BuildFromStdModules(("Module1", inputCode1), ("Module2", inputCode2));
55+
using (var state = MockParser.CreateAndParse(vbe.Object))
56+
{
57+
58+
var inspection = new IllegalAnnotationInspection(state);
59+
var inspector = InspectionsHelper.GetInspector(inspection);
60+
var inspectionResults = inspector.FindIssuesAsync(state, CancellationToken.None).Result;
61+
62+
Assert.IsFalse(inspectionResults.Any());
63+
}
64+
}
65+
3366
[Test]
3467
[Category("Inspections")]
3568
public void GivenLegalModuleAnnotation_NoResult()

0 commit comments

Comments
 (0)