Skip to content

Commit 5237703

Browse files
committed
Exclude attribute annotations from AnnotateDeclaration if not applicable
If there is no attributes context, the annotation does not make sanse. This is primarily a concern regarding variables, since module variables can have attributes, but local variables cannot. Accordingly, the annotation target enum is not sufficiently granular to provide all information.
1 parent 3bbacdb commit 5237703

File tree

3 files changed

+62
-10
lines changed

3 files changed

+62
-10
lines changed

Rubberduck.Core/UI/Converters/AnnotateDeclarationCommandCEVisibilityConverter.cs

Lines changed: 8 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -32,6 +32,13 @@ private bool ShouldBeVisible(IAnnotation annotation, ICodeExplorerNode node)
3232
return false;
3333
}
3434

35+
if (!target.DeclarationType.HasFlag(DeclarationType.Module)
36+
&& target.AttributesPassContext == null
37+
&& annotation is IAttributeAnnotation)
38+
{
39+
return false;
40+
}
41+
3542
var targetType = target.DeclarationType;
3643

3744
switch (annotation.Target)
@@ -46,7 +53,7 @@ private bool ShouldBeVisible(IAnnotation annotation, ICodeExplorerNode node)
4653
return targetType.HasFlag(DeclarationType.Variable)
4754
|| targetType.HasFlag(DeclarationType.Constant);
4855
case AnnotationTarget.General:
49-
return true;
56+
return !targetType.HasFlag(DeclarationType.Module);
5057
case AnnotationTarget.Identifier:
5158
return false;
5259
default:

Rubberduck.Core/UI/Refactorings/AnnotateDeclaration/AnnotateDeclarationViewModel.cs

Lines changed: 5 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -35,8 +35,11 @@ IAnnotationArgumentViewModelFactory argumentFactory
3535
private static IReadOnlyList<IAnnotation> AnnotationsForDeclaration(Declaration declaration, IEnumerable<IAnnotation> annotations)
3636
{
3737
return AnnotationsForDeclarationType(declaration.DeclarationType, annotations)
38-
.Where(annotation => annotation.AllowMultiple
39-
|| !declaration.Annotations.Any(pta => annotation.Equals(pta.Annotation)))
38+
.Where(annotation => (annotation.AllowMultiple
39+
|| !declaration.Annotations.Any(pta => annotation.Equals(pta.Annotation)))
40+
&& (declaration.DeclarationType.HasFlag(DeclarationType.Module)
41+
|| declaration.AttributesPassContext != null
42+
|| !(annotation is IAttributeAnnotation)))
4043
.ToList();
4144
}
4245

RubberduckTests/Refactoring/AnnotateDeclaration/AnnotateDeclarationViewModelTests.cs

Lines changed: 49 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -53,7 +53,40 @@ public void AnnotationAlreadyPresent_AllowsMultiple_InApplicableAnnotations()
5353

5454
Assert.True(applicableAnnotationNames.Contains("Ignore"));
5555
}
56-
56+
57+
[Test]
58+
public void AttributeAnnotation_NoAttributesContext_NoModule_NotInApplicableAnnotations()
59+
{
60+
var viewModel = TestViewModel(DeclarationType.Variable, localScope: true);
61+
var applicableAnnotationNames = viewModel.ApplicableAnnotations
62+
.Select(annotation => annotation.Name)
63+
.ToList();
64+
65+
Assert.False(applicableAnnotationNames.Contains("VariableDescription"));
66+
}
67+
68+
[Test]
69+
public void AttributeAnnotation_NoAttributesContext_IsModule_InApplicableAnnotations()
70+
{
71+
var viewModel = TestViewModel(DeclarationType.Module);
72+
var applicableAnnotationNames = viewModel.ApplicableAnnotations
73+
.Select(annotation => annotation.Name)
74+
.ToList();
75+
76+
Assert.True(applicableAnnotationNames.Contains("Exposed"));
77+
}
78+
79+
[Test]
80+
public void AttributeAnnotation_HasAttributesContext_NotInApplicableAnnotations()
81+
{
82+
var viewModel = TestViewModel(DeclarationType.Variable, localScope: false);
83+
var applicableAnnotationNames = viewModel.ApplicableAnnotations
84+
.Select(annotation => annotation.Name)
85+
.ToList();
86+
87+
Assert.True(applicableAnnotationNames.Contains("VariableDescription"));
88+
}
89+
5790
[Test]
5891
public void AnnotationNull_Invalid()
5992
{
@@ -264,10 +297,10 @@ public void DialogOK_SetsArguments()
264297
}
265298

266299

267-
private AnnotateDeclarationViewModel TestViewModel(DeclarationType targetDeclarationType, IAnnotation initialAnnotation = null)
300+
private AnnotateDeclarationViewModel TestViewModel(DeclarationType targetDeclarationType, IAnnotation initialAnnotation = null, bool localScope = false)
268301
{
269302
var argumentFactory = MockArgumentFactory().Object;
270-
return TestViewModel(targetDeclarationType, argumentFactory, initialAnnotation);
303+
return TestViewModel(targetDeclarationType, argumentFactory, initialAnnotation, localScope);
271304
}
272305

273306
private Mock<IAnnotationArgumentViewModelFactory> MockArgumentFactory(IReadOnlyList<bool> hasErrorSpecifications = null)
@@ -296,20 +329,21 @@ private Mock<IAnnotationArgumentViewModel> MockArgument(AnnotationArgumentType a
296329
return mockArgument;
297330
}
298331

299-
private AnnotateDeclarationViewModel TestViewModel(DeclarationType targetDeclarationType, IAnnotationArgumentViewModelFactory argumentFactory, IAnnotation initialAnnotation = null)
332+
private AnnotateDeclarationViewModel TestViewModel(DeclarationType targetDeclarationType, IAnnotationArgumentViewModelFactory argumentFactory, IAnnotation initialAnnotation = null, bool localScope = false)
300333
{
301-
var targetDeclaration = TestDeclaration(targetDeclarationType);
334+
var targetDeclaration = TestDeclaration(targetDeclarationType, localScope);
302335
var model = new AnnotateDeclarationModel(targetDeclaration, initialAnnotation);
303336
return new AnnotateDeclarationViewModel(model, _testAnnotations, argumentFactory);
304337
}
305338

306-
private Declaration TestDeclaration(DeclarationType targetDeclarationType)
339+
private Declaration TestDeclaration(DeclarationType targetDeclarationType, bool localScope = false)
307340
{
308341
const string code = @"
309342
Public myVar As Variant
310343
311344
'@Ignore MissingMemberAnnotationInspection
312345
Public Sub Foo
346+
Dim bar As Variant
313347
End Sub
314348
315349
'@DefaultMember
@@ -319,7 +353,15 @@ End Function
319353
var vbe = MockVbeBuilder.BuildFromSingleModule(code, ComponentType.ClassModule, out _).Object;
320354
using (var state = MockParser.CreateAndParse(vbe))
321355
{
322-
return state.DeclarationFinder.UserDeclarations(targetDeclarationType).Single();
356+
if (localScope)
357+
{
358+
return state.DeclarationFinder.UserDeclarations(targetDeclarationType)
359+
.Single(declaration => declaration.ParentScopeDeclaration.DeclarationType.HasFlag(DeclarationType.Member));
360+
}
361+
362+
return state.DeclarationFinder.UserDeclarations(targetDeclarationType)
363+
.Single(declaration => declaration.DeclarationType.HasFlag(DeclarationType.Module)
364+
|| declaration.ParentScopeDeclaration.DeclarationType.HasFlag(DeclarationType.Module));
323365
}
324366
}
325367

0 commit comments

Comments
 (0)