Skip to content

Commit 39402e8

Browse files
committed
Reorder alternatives in annotationArgList in grammar
Previously the options without explicit parentheses were preferred and matched to expressions with parentheses consuming them as part or the argument.
1 parent 6348fff commit 39402e8

File tree

2 files changed

+51
-4
lines changed

2 files changed

+51
-4
lines changed

Rubberduck.Parsing/Grammar/VBAParser.g4

Lines changed: 5 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -955,11 +955,12 @@ annotationList : SINGLEQUOTE (AT annotation)+ (COLON commentBody)?;
955955
annotation : annotationName annotationArgList? whiteSpace?;
956956
annotationName : unrestrictedIdentifier;
957957
annotationArgList :
958-
whiteSpace annotationArg
959-
| whiteSpace annotationArg (whiteSpace? COMMA whiteSpace? annotationArg)+
958+
whiteSpace? LPAREN whiteSpace? annotationArg whiteSpace? RPAREN
960959
| whiteSpace? LPAREN whiteSpace? RPAREN
961-
| whiteSpace? LPAREN whiteSpace? annotationArg whiteSpace? RPAREN
962-
| whiteSpace? LPAREN annotationArg (whiteSpace? COMMA whiteSpace? annotationArg)+ whiteSpace? RPAREN;
960+
| whiteSpace? LPAREN annotationArg (whiteSpace? COMMA whiteSpace? annotationArg)+ whiteSpace? RPAREN
961+
| whiteSpace annotationArg
962+
| whiteSpace annotationArg (whiteSpace? COMMA whiteSpace? annotationArg)+
963+
;
963964
annotationArg : expression;
964965

965966
mandatoryLineContinuation : LINE_CONTINUATION WS*;

RubberduckTests/Annotations/AnnotationResolutionTests.cs

Lines changed: 46 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,6 @@
11
using System.Linq;
22
using NUnit.Framework;
3+
using Rubberduck.Parsing.Annotations;
34
using Rubberduck.Parsing.Symbols;
45
using RubberduckTests.Mocks;
56

@@ -556,5 +557,50 @@ Public Function Bar() As Variant '@Ignore MissingAttribute
556557
Assert.AreEqual(expectedAnnotationCount, actualAnnotationCount);
557558
}
558559
}
560+
561+
[Test]
562+
//Cf. issue #5071 at https://github.com/rubberduck-vba/Rubberduck/issues/5071
563+
public void AnnotationArgumentIsRecognisedWithWhiteSpaceInBetween()
564+
{
565+
const string inputCode =
566+
@"
567+
'@description (""Function description"")
568+
Public Function Bar() As Variant
569+
End Function";
570+
var vbe = MockVbeBuilder.BuildFromSingleStandardModule(inputCode, out _);
571+
using (var state = MockParser.CreateAndParse(vbe.Object))
572+
{
573+
var declaration = state.DeclarationFinder.UserDeclarations(DeclarationType.Function).Single();
574+
var annotation = declaration.Annotations.OfType<DescriptionAnnotation>().Single();
575+
576+
var expectedAnnotationArgument = "Function description";
577+
var actualAnnotationArgument = annotation.Description;
578+
579+
Assert.AreEqual(expectedAnnotationArgument, actualAnnotationArgument);
580+
}
581+
}
582+
583+
[Test]
584+
public void AnnotationArgumentIsRecognisedWithLineContinuationsInBetween()
585+
{
586+
const string inputCode =
587+
@"
588+
'@description _
589+
_
590+
(""Function description"")
591+
Public Function Bar() As Variant
592+
End Function";
593+
var vbe = MockVbeBuilder.BuildFromSingleStandardModule(inputCode, out _);
594+
using (var state = MockParser.CreateAndParse(vbe.Object))
595+
{
596+
var declaration = state.DeclarationFinder.UserDeclarations(DeclarationType.Function).Single();
597+
var annotation = declaration.Annotations.OfType<DescriptionAnnotation>().Single();
598+
599+
var expectedAnnotationArgument = "Function description";
600+
var actualAnnotationArgument = annotation.Description;
601+
602+
Assert.AreEqual(expectedAnnotationArgument, actualAnnotationArgument);
603+
}
604+
}
559605
}
560606
}

0 commit comments

Comments
 (0)