Skip to content

Commit a15e2b6

Browse files
committed
Remove debugStmt from grammar
Since be now have the objectPrintExpr to support VB6's print member syntax, having a separate debug statement is no longer necessary. This also allows to remove the static DebugPrint declaration.
1 parent 630fc50 commit a15e2b6

File tree

7 files changed

+15
-71
lines changed

7 files changed

+15
-71
lines changed

Rubberduck.Parsing/Grammar/VBAParser.g4

Lines changed: 0 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -186,7 +186,6 @@ fileStmt :
186186
| unlockStmt
187187
| lineInputStmt
188188
| widthStmt
189-
| debugPrintStmt
190189
| printStmt
191190
| writeStmt
192191
| inputStmt
@@ -258,13 +257,6 @@ lineWidth : expression;
258257

259258

260259
// 5.4.5.8 Print Statement
261-
// Debug.Print is special because it seems to take an output list as argument.
262-
// To shield the rest of the parsing/binding from this peculiarity, we treat it as a statement
263-
// and let the resolver handle it.
264-
debugPrintStmt : debugPrint (whiteSpace outputList)?;
265-
// We split it up into separate rules so that we have context classes generated that can be used in declarations/references.
266-
debugPrint : debugModule whiteSpace? DOT whiteSpace? printMethod;
267-
debugModule : DEBUG;
268260
printMethod : PRINT;
269261
printStmt : PRINT whiteSpace markedFileNumber whiteSpace? COMMA (whiteSpace? outputList)?;
270262

Rubberduck.Parsing/Symbols/DeclarationLoaders/DebugDeclarations.cs

Lines changed: 0 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -9,7 +9,6 @@ namespace Rubberduck.Parsing.Symbols.DeclarationLoaders
99
{
1010
public class DebugDeclarations : ICustomDeclarationLoader
1111
{
12-
public static Declaration DebugPrint;
1312
private readonly IDeclarationFinderProvider _finderProvider;
1413

1514
public DebugDeclarations(IDeclarationFinderProvider finderProvider)
@@ -58,12 +57,6 @@ private List<Declaration> LoadDebugDeclarations(Declaration parentProject)
5857
var debugAssert = DebugAssertDeclaration(debugClass);
5958
var debugPrint = DebugPrintDeclaration(debugClass);
6059

61-
// Debug.Print has the same special syntax as the print and write statement.
62-
// Because of that it is treated specially in the grammar and normally wouldn't be resolved.
63-
// Since we still want it to be resolved we make it easier for the resolver to access the debug print
64-
// declaration by exposing it in this way.
65-
DebugPrint = debugPrint;
66-
6760
return new List<Declaration> {
6861
debugModule,
6962
debugClass,

Rubberduck.Parsing/VBA/ReferenceManagement/IdentifierReferenceListener.cs

Lines changed: 0 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -331,10 +331,5 @@ public override void EnterPSetSpecialForm(VBAParser.PSetSpecialFormContext conte
331331
{
332332
_resolver.Resolve(context);
333333
}
334-
335-
public override void EnterDebugPrintStmt([NotNull] VBAParser.DebugPrintStmtContext context)
336-
{
337-
_resolver.Resolve(context);
338-
}
339334
}
340335
}

Rubberduck.Parsing/VBA/ReferenceManagement/IdentifierReferenceResolver.cs

Lines changed: 0 additions & 42 deletions
Original file line numberDiff line numberDiff line change
@@ -797,47 +797,5 @@ public void Resolve(VBAParser.EnumerationStmtContext context)
797797
}
798798
}
799799
}
800-
801-
public void Resolve(VBAParser.DebugPrintStmtContext context)
802-
{
803-
if (DebugDeclarations.DebugPrint != null)
804-
{
805-
// Because Debug.Print has a special argument (an output list) instead
806-
// of normal arguments we can't treat it as a function call.
807-
var debugPrint = DebugDeclarations.DebugPrint;
808-
var debugModule = debugPrint.ParentDeclaration;
809-
debugModule.AddReference(
810-
_qualifiedModuleName,
811-
_currentScope,
812-
_currentParent,
813-
context.debugPrint().debugModule(),
814-
context.debugPrint().debugModule().GetText(),
815-
debugModule,
816-
context.debugPrint().debugModule().GetSelection(),
817-
FindIdentifierAnnotations(_qualifiedModuleName,
818-
context.debugPrint().debugModule().GetSelection().StartLine));
819-
debugPrint.AddReference(
820-
_qualifiedModuleName,
821-
_currentScope,
822-
_currentParent,
823-
context.debugPrint().printMethod(),
824-
context.debugPrint().printMethod().GetText(),
825-
debugPrint,
826-
context.debugPrint().printMethod().GetSelection(),
827-
FindIdentifierAnnotations(_qualifiedModuleName,
828-
context.debugPrint().printMethod().GetSelection().StartLine));
829-
}
830-
else
831-
{
832-
Logger.Warn("Debug.Print (custom declaration) has not been loaded, skipping resolving Debug.Print call.");
833-
}
834-
835-
//The output list should be resolved no matter whether we have a declaration for Debug.Print or not.
836-
var outputList = context.outputList();
837-
if (outputList != null)
838-
{
839-
ResolveOutputList(outputList);
840-
}
841-
}
842800
}
843801
}

RubberduckTests/Grammar/VBAParserTests.cs

Lines changed: 7 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -2578,7 +2578,7 @@ Sub Test()
25782578
Debug.Print
25792579
End Sub";
25802580
var parseResult = Parse(code);
2581-
AssertTree(parseResult.Item1, parseResult.Item2, "//debugPrintStmt");
2581+
AssertTree(parseResult.Item1, parseResult.Item2, "//printMethod");
25822582
}
25832583

25842584

@@ -2590,7 +2590,7 @@ Sub Test()
25902590
Debug.Print ""Anything""
25912591
End Sub";
25922592
var parseResult = Parse(code);
2593-
AssertTree(parseResult.Item1, parseResult.Item2, "//debugPrintStmt/outputList");
2593+
AssertTree(parseResult.Item1, parseResult.Item2, "//lExpression/outputList");
25942594
}
25952595

25962596

@@ -2602,7 +2602,7 @@ Sub Test()
26022602
Debug.Print 1;
26032603
End Sub";
26042604
var parseResult = Parse(code);
2605-
AssertTree(parseResult.Item1, parseResult.Item2, "//debugPrintStmt/outputList");
2605+
AssertTree(parseResult.Item1, parseResult.Item2, "//lExpression/outputList");
26062606
}
26072607

26082608

@@ -2614,7 +2614,7 @@ Sub Test()
26142614
Debug.Print 1,
26152615
End Sub";
26162616
var parseResult = Parse(code);
2617-
AssertTree(parseResult.Item1, parseResult.Item2, "//debugPrintStmt/outputList");
2617+
AssertTree(parseResult.Item1, parseResult.Item2, "//lExpression/outputList");
26182618
}
26192619

26202620

@@ -2631,7 +2631,7 @@ Debug.Print GetDescrip(fld)
26312631
Next
26322632
End Sub";
26332633
var parseResult = Parse(code);
2634-
AssertTree(parseResult.Item1, parseResult.Item2, "//debugPrintStmt", matches => matches.Count == 4);
2634+
AssertTree(parseResult.Item1, parseResult.Item2, "//printMethod", matches => matches.Count == 4);
26352635
}
26362636

26372637

@@ -2646,7 +2646,7 @@ If Not pFault Then
26462646
End If
26472647
End Sub";
26482648
var parseResult = Parse(code, PredictionMode.Sll);
2649-
AssertTree(parseResult.Item1, parseResult.Item2, "//debugPrintStmt", matches => matches.Count == 2);
2649+
AssertTree(parseResult.Item1, parseResult.Item2, "//printMethod", matches => matches.Count == 2);
26502650
}
26512651

26522652

@@ -2660,7 +2660,7 @@ Sub Test()
26602660
Next i
26612661
End Sub";
26622662
var parseResult = Parse(code);
2663-
AssertTree(parseResult.Item1, parseResult.Item2, "//debugPrintStmt", matches => matches.Count == 1);
2663+
AssertTree(parseResult.Item1, parseResult.Item2, "//printMethod", matches => matches.Count == 1);
26642664
}
26652665

26662666

RubberduckTests/Inspections/UndeclaredVariableInspectionTests.cs

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -23,6 +23,7 @@ Debug.Print a
2323
var builder = new MockVbeBuilder();
2424
var project = builder.ProjectBuilder("VBAProject", ProjectProtection.Unprotected)
2525
.AddComponent("MyClass", ComponentType.ClassModule, inputCode)
26+
.AddReference("VBA", MockVbeBuilder.LibraryPathVBA, 4, 2, true)
2627
.Build();
2728
var vbe = builder.AddProject(project).Build();
2829

@@ -49,6 +50,7 @@ Debug.Print a
4950
var builder = new MockVbeBuilder();
5051
var project = builder.ProjectBuilder("VBAProject", ProjectProtection.Unprotected)
5152
.AddComponent("MyClass", ComponentType.ClassModule, inputCode)
53+
.AddReference("VBA", MockVbeBuilder.LibraryPathVBA, 4, 2, true)
5254
.Build();
5355
var vbe = builder.AddProject(project).Build();
5456

@@ -76,6 +78,7 @@ Debug.Print a
7678
var builder = new MockVbeBuilder();
7779
var project = builder.ProjectBuilder("VBAProject", ProjectProtection.Unprotected)
7880
.AddComponent("MyClass", ComponentType.ClassModule, inputCode)
81+
.AddReference("VBA", MockVbeBuilder.LibraryPathVBA, 4, 2, true)
7982
.Build();
8083
var vbe = builder.AddProject(project).Build();
8184

@@ -132,6 +135,7 @@ Debug.Print a
132135
var builder = new MockVbeBuilder();
133136
var project = builder.ProjectBuilder("VBAProject", ProjectProtection.Unprotected)
134137
.AddComponent("MyClass", ComponentType.ClassModule, inputCode)
138+
.AddReference("VBA", MockVbeBuilder.LibraryPathVBA, 4, 2, true)
135139
.Build();
136140
var vbe = builder.AddProject(project).Build();
137141

RubberduckTests/Symbols/DeclarationFinderTests.cs

Lines changed: 4 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -630,13 +630,14 @@ End Sub
630630
var vbe = new MockVbeBuilder()
631631
.ProjectBuilder("foo", ProjectProtection.Unprotected)
632632
.AddComponent("foo", ComponentType.StandardModule, code, new Selection(6, 6))
633+
.AddReference("VBA", MockVbeBuilder.LibraryPathVBA, 4, 2, true)
633634
.AddProjectToVbeBuilder()
634635
.Build();
635636

636637
var parser = MockParser.Create(vbe.Object);
637638
parser.Parse(new CancellationTokenSource());
638639

639-
var expected = parser.State.DeclarationFinder.DeclarationsWithType(DeclarationType.Variable).Single();
640+
var expected = parser.State.DeclarationFinder.DeclarationsWithType(DeclarationType.Variable).Single(declaration => declaration.IdentifierName.Equals("foo"));
640641
var actual = parser.State.DeclarationFinder.FindSelectedDeclaration(vbe.Object.ActiveCodePane);
641642

642643
Assert.AreEqual(expected, actual, "Expected {0}, resolved to {1}", expected.DeclarationType, actual.DeclarationType);
@@ -659,13 +660,14 @@ End Sub
659660
var vbe = new MockVbeBuilder()
660661
.ProjectBuilder("TestProject", ProjectProtection.Unprotected)
661662
.AddComponent("TestModule", ComponentType.StandardModule, code, new Selection(6, 6))
663+
.AddReference("VBA", MockVbeBuilder.LibraryPathVBA, 4, 2, true)
662664
.AddProjectToVbeBuilder()
663665
.Build();
664666

665667
var parser = MockParser.Create(vbe.Object);
666668
parser.Parse(new CancellationTokenSource());
667669

668-
var expected = parser.State.DeclarationFinder.DeclarationsWithType(DeclarationType.Variable).Single();
670+
var expected = parser.State.DeclarationFinder.DeclarationsWithType(DeclarationType.Variable).Single(declaration => declaration.IdentifierName.Equals("foo"));
669671
var actual = parser.State.DeclarationFinder.FindSelectedDeclaration(vbe.Object.ActiveCodePane);
670672

671673
Assert.AreEqual(expected, actual, "Expected {0}, resolved to {1}", expected.DeclarationType, actual.DeclarationType);

0 commit comments

Comments
 (0)