Skip to content

Commit 823562b

Browse files
committed
Use correct context when adding annotations via attributes code
This is hard to test since the bug fixed here only materializes when the attributes are removed in the code pane version of the code.
1 parent 1a2cef2 commit 823562b

File tree

2 files changed

+84
-2
lines changed

2 files changed

+84
-2
lines changed

Rubberduck.Parsing/VBA/AnnotationUpdater.cs

Lines changed: 10 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -214,7 +214,11 @@ private void AddVariableAnnotation(IRewriteSession rewriteSession, Declaration d
214214
return;
215215
}
216216

217-
AddAnnotation(rewriteSession, declaration.QualifiedModuleName, declaration.Context, annotationInfo, annotationValues);
217+
var context = rewriteSession.TargetCodeKind == CodeKind.CodePaneCode
218+
? declaration.Context
219+
: declaration.AttributesPassContext;
220+
221+
AddAnnotation(rewriteSession, declaration.QualifiedModuleName, context, annotationInfo, annotationValues);
218222
}
219223

220224
private void AddMemberAnnotation(IRewriteSession rewriteSession, Declaration declaration, IAnnotation annotationInfo, IReadOnlyList<string> annotationValues)
@@ -233,7 +237,11 @@ private void AddMemberAnnotation(IRewriteSession rewriteSession, Declaration dec
233237
return;
234238
}
235239

236-
AddAnnotation(rewriteSession, declaration.QualifiedModuleName, declaration.Context, annotationInfo, annotationValues);
240+
var context = rewriteSession.TargetCodeKind == CodeKind.CodePaneCode
241+
? declaration.Context
242+
: declaration.AttributesPassContext;
243+
244+
AddAnnotation(rewriteSession, declaration.QualifiedModuleName, context, annotationInfo, annotationValues);
237245
}
238246

239247
public void AddAnnotation(IRewriteSession rewriteSession, IdentifierReference reference, IAnnotation annotationInfo, IReadOnlyList<string> values = null)

RubberduckTests/Refactoring/AnnotateDeclaration/AnnotateDeclarationRefactoringActionTests.cs

Lines changed: 74 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -616,6 +616,80 @@ End Sub
616616
Assert.AreEqual(expectedCode, refactoredCode);
617617
}
618618

619+
[Test]
620+
[Category("Refactorings")]
621+
public void AnnotateDeclarationRefactoringAction_AdjustAttributeSet_WorksWithExistingAnnotation_Module()
622+
{
623+
const string code = @"Attribute VB_Exposed = False
624+
'@Folder ""MyFolder""
625+
'@DefaultMember
626+
Public Sub Foo()
627+
End Sub
628+
";
629+
const string expectedCode = @"Attribute VB_Exposed = False
630+
Attribute VB_Description = ""MyDesc""
631+
'@ModuleDescription ""MyDesc""
632+
'@Folder ""MyFolder""
633+
'@DefaultMember
634+
Public Sub Foo()
635+
End Sub
636+
";
637+
Func<RubberduckParserState, AnnotateDeclarationModel> modelBuilder = (state) =>
638+
{
639+
var declaration = state.DeclarationFinder
640+
.UserDeclarations(DeclarationType.Module)
641+
.Single();
642+
var annotation = new ModuleDescriptionAnnotation();
643+
var arguments = new List<TypedAnnotationArgument>
644+
{
645+
new TypedAnnotationArgument(AnnotationArgumentType.Text, "MyDesc")
646+
};
647+
648+
return new AnnotateDeclarationModel(declaration, annotation, arguments, true);
649+
};
650+
651+
var refactoredCode = RefactoredCode(code, modelBuilder);
652+
653+
Assert.AreEqual(expectedCode, refactoredCode);
654+
}
655+
656+
[Test]
657+
[Category("Refactorings")]
658+
public void AnnotateDeclarationRefactoringAction_WorksWithExistingAnnotation_Member()
659+
{
660+
const string code = @"Attribute VB_Exposed = False
661+
'@Folder ""MyFolder""
662+
'@DefaultMember
663+
Public Sub Foo()
664+
End Sub
665+
";
666+
const string expectedCode = @"Attribute VB_Exposed = False
667+
'@Folder ""MyFolder""
668+
'@DefaultMember
669+
'@Description ""MyDesc""
670+
Public Sub Foo()
671+
Attribute Foo.VB_Description = ""MyDesc""
672+
End Sub
673+
";
674+
Func<RubberduckParserState, AnnotateDeclarationModel> modelBuilder = (state) =>
675+
{
676+
var declaration = state.DeclarationFinder
677+
.UserDeclarations(DeclarationType.Procedure)
678+
.Single();
679+
var annotation = new DescriptionAnnotation();
680+
var arguments = new List<TypedAnnotationArgument>
681+
{
682+
new TypedAnnotationArgument(AnnotationArgumentType.Text, "MyDesc")
683+
};
684+
685+
return new AnnotateDeclarationModel(declaration, annotation, arguments, true);
686+
};
687+
688+
var refactoredCode = RefactoredCode(code, modelBuilder);
689+
690+
Assert.AreEqual(expectedCode, refactoredCode);
691+
}
692+
619693
protected override IRefactoringAction<AnnotateDeclarationModel> TestBaseRefactoring(RubberduckParserState state, IRewritingManager rewritingManager)
620694
{
621695
var annotationUpdater = new AnnotationUpdater(state);

0 commit comments

Comments
 (0)