Skip to content

Commit ebe40b9

Browse files
committed
Allow to annotate declarations in attributes code
This only applies to components and declarations with attributes contexts.
1 parent 811448b commit ebe40b9

23 files changed

+188
-68
lines changed

Rubberduck.Parsing/VBA/AnnotationUpdater.cs

Lines changed: 76 additions & 26 deletions
Original file line numberDiff line numberDiff line change
@@ -10,13 +10,21 @@
1010
using Rubberduck.Parsing.Rewriter;
1111
using Rubberduck.Parsing.Symbols;
1212
using Rubberduck.Parsing.VBA.Parsing;
13+
using Rubberduck.VBEditor;
1314

1415
namespace Rubberduck.Parsing.VBA
1516
{
1617
public class AnnotationUpdater : IAnnotationUpdater
1718
{
19+
private readonly IParseTreeProvider _parseTreeProvider;
20+
1821
private readonly Logger _logger = LogManager.GetCurrentClassLogger();
1922

23+
public AnnotationUpdater(IParseTreeProvider parseTreeProvider)
24+
{
25+
_parseTreeProvider = parseTreeProvider;
26+
}
27+
2028
public void AddAnnotation(IRewriteSession rewriteSession, QualifiedContext context, IAnnotation annotationInfo, IReadOnlyList<string> values = null)
2129
{
2230
var annotationValues = values ?? new List<string>();
@@ -30,41 +38,55 @@ public void AddAnnotation(IRewriteSession rewriteSession, QualifiedContext conte
3038

3139
if (rewriteSession.TargetCodeKind != CodeKind.CodePaneCode)
3240
{
33-
_logger.Warn($"Tried to add an annotation with a rewriter not suitable for annotationss. (target code kind = {rewriteSession.TargetCodeKind})");
41+
_logger.Warn($"Tried to add an annotation with a rewriter not suitable to annotate contexts. (target code kind = {rewriteSession.TargetCodeKind})");
3442
_logger.Trace($"Tried to add annotation {annotationInfo.Name} with values {AnnotationValuesText(annotationValues)} to {context.Context.GetText()} at {context.Context.GetSelection()} in module {context.ModuleName} using a rewriter not suitable for annotations.");
3543
return;
3644
}
3745

46+
AddAnnotation(rewriteSession, context.ModuleName, context.Context, annotationInfo, annotationValues);
47+
}
48+
49+
private void AddAnnotation(IRewriteSession rewriteSession, QualifiedModuleName moduleName, ParserRuleContext context, IAnnotation annotationInfo, IReadOnlyList<string> values = null)
50+
{
51+
var annotationValues = values ?? new List<string>();
52+
53+
if (context == null)
54+
{
55+
_logger.Warn("Tried to add an annotation to a context that is null.");
56+
_logger.Trace($"Tried to add annotation {annotationInfo.Name} with values {AnnotationValuesText(annotationValues)} to a context that is null.");
57+
return;
58+
}
59+
3860
var annotationText = AnnotationText(annotationInfo.Name, annotationValues);
3961

4062
string codeToAdd;
4163
IModuleRewriter rewriter;
42-
if (context.Context.start.Line == 1)
64+
if (context.start.Line == 1)
4365
{
4466
codeToAdd = $"{annotationText}{Environment.NewLine}";
45-
rewriter = rewriteSession.CheckOutModuleRewriter(context.ModuleName);
67+
rewriter = rewriteSession.CheckOutModuleRewriter(moduleName);
4668
rewriter.InsertBefore(0, codeToAdd);
4769
return;
4870
}
4971

50-
var previousEndOfLine = PreviousEndOfLine(context.Context);
72+
var previousEndOfLine = PreviousEndOfLine(context);
5173
if (previousEndOfLine == null)
5274
{
5375
//We are on the first logical line, but not the first physical line.
5476
return;
5577
}
5678

57-
if (context.Context.start.Line > previousEndOfLine.stop.Line + 1)
79+
if (context.start.Line > previousEndOfLine.stop.Line + 1)
5880
{
5981
_logger.Warn("Tried to add an annotation to a context not on the first physical line of a logical line.");
60-
_logger.Trace($"Tried to add annotation {annotationInfo.Name} with values {AnnotationValuesText(annotationValues)} to a the context with text '{context.Context.GetText()}' at {context.Context.GetSelection()} in module {context.ModuleName}.");
82+
_logger.Trace($"Tried to add annotation {annotationInfo.Name} with values {AnnotationValuesText(annotationValues)} to a the context with text '{context.GetText()}' at {context.GetSelection()} in module {moduleName}.");
6183
return;
6284
}
63-
64-
codeToAdd = previousEndOfLine.TryGetFollowingContext(out VBAParser.WhiteSpaceContext whitespaceAtStartOfLine)
65-
? $"{whitespaceAtStartOfLine.GetText()}{annotationText}{Environment.NewLine}"
85+
86+
codeToAdd = previousEndOfLine.TryGetFollowingContext(out VBAParser.WhiteSpaceContext whitespaceAtStartOfLine)
87+
? $"{whitespaceAtStartOfLine.GetText()}{annotationText}{Environment.NewLine}"
6688
: $"{annotationText}{Environment.NewLine}";
67-
rewriter = rewriteSession.CheckOutModuleRewriter(context.ModuleName);
89+
rewriter = rewriteSession.CheckOutModuleRewriter(moduleName);
6890
rewriter.InsertAfter(previousEndOfLine.stop.TokenIndex, codeToAdd);
6991
}
7092

@@ -133,17 +155,47 @@ private void AddModuleAnnotation(IRewriteSession rewriteSession, Declaration dec
133155
return;
134156
}
135157

136-
if (rewriteSession.TargetCodeKind != CodeKind.CodePaneCode)
158+
if (rewriteSession.TargetCodeKind != CodeKind.CodePaneCode && rewriteSession.TargetCodeKind != CodeKind.AttributesCode)
137159
{
138-
_logger.Warn($"Tried to add an annotation to a module with a rewriter not suitable for annotationss. (target code kind = {rewriteSession.TargetCodeKind})");
160+
_logger.Warn($"Tried to add an annotation to a module with a rewriter not suitable for annotations. (target code kind = {rewriteSession.TargetCodeKind})");
139161
_logger.Trace($"Tried to add annotation {annotationInfo.Name} with values {AnnotationValuesText(annotationValues)} to the module {declaration.QualifiedModuleName} using a rewriter not suitable for annotations.");
140162
return;
141163
}
142164

143-
var codeToAdd = $"{AnnotationText(annotationInfo, annotationValues)}{Environment.NewLine}";
165+
var codeToAdd = AnnotationText(annotationInfo, annotationValues);
144166

145167
var rewriter = rewriteSession.CheckOutModuleRewriter(declaration.QualifiedModuleName);
146-
rewriter.InsertBefore(0, codeToAdd);
168+
169+
if (rewriteSession.TargetCodeKind == CodeKind.AttributesCode)
170+
{
171+
InsertAfterLastModuleAttribute(rewriter, declaration.QualifiedModuleName, codeToAdd);
172+
}
173+
else
174+
{
175+
var codeToInsert = codeToAdd + Environment.NewLine;
176+
rewriter.InsertBefore(0, codeToInsert);
177+
}
178+
}
179+
180+
private void InsertAfterLastModuleAttribute(IModuleRewriter rewriter, QualifiedModuleName module, string codeToAdd)
181+
{
182+
var moduleParseTree = (ParserRuleContext)_parseTreeProvider.GetParseTree(module, CodeKind.AttributesCode);
183+
var lastModuleAttribute = moduleParseTree.GetDescendents<VBAParser.ModuleAttributesContext>()
184+
.Where(moduleAttributes => moduleAttributes.attributeStmt() != null)
185+
.SelectMany(moduleAttributes => moduleAttributes.attributeStmt())
186+
.OrderBy(moduleAttribute => moduleAttribute.stop.TokenIndex)
187+
.LastOrDefault();
188+
if (lastModuleAttribute == null)
189+
{
190+
//This should never happen for a real module.
191+
var codeToInsert = codeToAdd + Environment.NewLine;
192+
rewriter.InsertBefore(0, codeToInsert);
193+
}
194+
else
195+
{
196+
var codeToInsert = Environment.NewLine + codeToAdd;
197+
rewriter.InsertAfter(lastModuleAttribute.stop.TokenIndex, codeToInsert);
198+
}
147199
}
148200

149201
private void AddVariableAnnotation(IRewriteSession rewriteSession, Declaration declaration, IAnnotation annotationInfo, IReadOnlyList<string> annotationValues)
@@ -155,14 +207,14 @@ private void AddVariableAnnotation(IRewriteSession rewriteSession, Declaration d
155207
return;
156208
}
157209

158-
if (rewriteSession.TargetCodeKind != CodeKind.CodePaneCode)
210+
if (rewriteSession.TargetCodeKind != CodeKind.CodePaneCode && (rewriteSession.TargetCodeKind != CodeKind.AttributesCode || declaration.AttributesPassContext == null))
159211
{
160-
_logger.Warn($"Tried to add an annotation to a variable with a rewriter not suitable for annotationss. (target code kind = {rewriteSession.TargetCodeKind})");
212+
_logger.Warn($"Tried to add an annotation to a variable with a rewriter not suitable for annotations to the variable. (target code kind = {rewriteSession.TargetCodeKind})");
161213
_logger.Trace($"Tried to add annotation {annotationInfo.Name} with values {AnnotationValuesText(annotationValues)} to the the variable {declaration.IdentifierName} at {declaration.Selection} in module {declaration.QualifiedModuleName} using a rewriter not suitable for annotations.");
162214
return;
163215
}
164216

165-
AddAnnotation(rewriteSession, new QualifiedContext(declaration.QualifiedName, declaration.Context), annotationInfo, annotationValues);
217+
AddAnnotation(rewriteSession, declaration.QualifiedModuleName, declaration.Context, annotationInfo, annotationValues);
166218
}
167219

168220
private void AddMemberAnnotation(IRewriteSession rewriteSession, Declaration declaration, IAnnotation annotationInfo, IReadOnlyList<string> annotationValues)
@@ -174,19 +226,17 @@ private void AddMemberAnnotation(IRewriteSession rewriteSession, Declaration dec
174226
return;
175227
}
176228

177-
if (rewriteSession.TargetCodeKind != CodeKind.CodePaneCode)
229+
if (rewriteSession.TargetCodeKind != CodeKind.CodePaneCode && (rewriteSession.TargetCodeKind != CodeKind.AttributesCode || declaration.AttributesPassContext == null))
178230
{
179-
_logger.Warn($"Tried to add an annotation to a member with a rewriter not suitable for annotationss. (target code kind = {rewriteSession.TargetCodeKind})");
231+
_logger.Warn($"Tried to add an annotation to a member with a rewriter not suitable for annotations to the member. (target code kind = {rewriteSession.TargetCodeKind})");
180232
_logger.Trace($"Tried to add annotation {annotationInfo.Name} with values {AnnotationValuesText(annotationValues)} to the the member {declaration.IdentifierName} at {declaration.Selection} in module {declaration.QualifiedModuleName} using a rewriter not suitable for annotations.");
181233
return;
182234
}
183235

184-
AddAnnotation(rewriteSession, new QualifiedContext(declaration.QualifiedName, declaration.Context), annotationInfo, annotationValues);
236+
AddAnnotation(rewriteSession, declaration.QualifiedModuleName, declaration.Context, annotationInfo, annotationValues);
185237
}
186238

187-
188-
public void AddAnnotation(IRewriteSession rewriteSession, IdentifierReference reference, IAnnotation annotationInfo,
189-
IReadOnlyList<string> values = null)
239+
public void AddAnnotation(IRewriteSession rewriteSession, IdentifierReference reference, IAnnotation annotationInfo, IReadOnlyList<string> values = null)
190240
{
191241
var annotationValues = values ?? new List<string>();
192242

@@ -206,7 +256,7 @@ public void AddAnnotation(IRewriteSession rewriteSession, IdentifierReference re
206256

207257
if (rewriteSession.TargetCodeKind != CodeKind.CodePaneCode)
208258
{
209-
_logger.Warn($"Tried to add an annotation to an identifier reference with a rewriter not suitable for annotationss. (target code kind = {rewriteSession.TargetCodeKind})");
259+
_logger.Warn($"Tried to add an annotation to an identifier reference with a rewriter not suitable for annotations to references. (target code kind = {rewriteSession.TargetCodeKind})");
210260
_logger.Trace($"Tried to add annotation {annotationInfo.Name} with values {AnnotationValuesText(annotationValues)} to the the identifier reference {reference.IdentifierName} at {reference.Selection} in module {reference.QualifiedModuleName} using a rewriter not suitable for annotations.");
211261
return;
212262
}
@@ -294,7 +344,7 @@ public void RemoveAnnotations(IRewriteSession rewriteSession, IEnumerable<IParse
294344
return;
295345
}
296346

297-
if (rewriteSession.TargetCodeKind != CodeKind.CodePaneCode)
347+
if (rewriteSession.TargetCodeKind != CodeKind.CodePaneCode && rewriteSession.TargetCodeKind != CodeKind.AttributesCode)
298348
{
299349
_logger.Warn($"Tried to remove multiple annotations with a rewriter not suitable for annotations. (target code kind = {rewriteSession.TargetCodeKind})");
300350
return;
@@ -341,7 +391,7 @@ public void UpdateAnnotation(IRewriteSession rewriteSession, IParseTreeAnnotatio
341391
return;
342392
}
343393

344-
if (rewriteSession.TargetCodeKind != CodeKind.CodePaneCode)
394+
if (rewriteSession.TargetCodeKind != CodeKind.CodePaneCode && rewriteSession.TargetCodeKind != CodeKind.AttributesCode)
345395
{
346396
_logger.Warn($"Tried to update an annotation with a rewriter not suitable for annotationss. (target code kind = {rewriteSession.TargetCodeKind})");
347397
_logger.Trace($"Tried to update annotation {annotation.Annotation.Name} at {annotation.QualifiedSelection.Selection} in module {annotation.QualifiedSelection.QualifiedName} with annotation {annotationInfo.Name} with values {AnnotationValuesText(newAnnotationValues)} using a rewriter not suitable for annotations.");

RubberduckTests/Commands/MockIndenter.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -43,7 +43,7 @@ internal static NoIndentAnnotationCommand ArrangeNoIndentAnnotationCommand(Mock<
4343
{
4444
var selectionService = new SelectionService(vbe.Object, state.ProjectsProvider);
4545
var selectedDeclarationService = new SelectedDeclarationProvider(selectionService, state);
46-
return new NoIndentAnnotationCommand(selectedDeclarationService, rewritingManager, new AnnotationUpdater(), vbeEvents.Object);
46+
return new NoIndentAnnotationCommand(selectedDeclarationService, rewritingManager, new AnnotationUpdater(state), vbeEvents.Object);
4747
}
4848

4949
internal static IndentCurrentProcedureCommand ArrangeIndentCurrentProcedureCommand(Mock<IVBE> vbe,

RubberduckTests/Commands/RefactorCommands/AnnotateSelectedDeclarationCommandTests.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -44,7 +44,7 @@ protected override CommandBase TestCommand(
4444
.Callback((Action action) => action.Invoke());
4545
var userInteraction = new RefactoringUserInteraction<IAnnotateDeclarationPresenter, AnnotateDeclarationModel>(factory, uiDispatcherMock.Object);
4646

47-
var annotationUpdater = new AnnotationUpdater();
47+
var annotationUpdater = new AnnotationUpdater(state);
4848
var annotateDeclarationAction = new AnnotateDeclarationRefactoringAction(rewritingManager, annotationUpdater);
4949

5050
var selectedDeclarationProvider = new SelectedDeclarationProvider(selectionService, state);

RubberduckTests/Commands/RefactorCommands/AnnotateSelectedMemberCommandTests.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -44,7 +44,7 @@ protected override CommandBase TestCommand(
4444
.Callback((Action action) => action.Invoke());
4545
var userInteraction = new RefactoringUserInteraction<IAnnotateDeclarationPresenter, AnnotateDeclarationModel>(factory, uiDispatcherMock.Object);
4646

47-
var annotationUpdater = new AnnotationUpdater();
47+
var annotationUpdater = new AnnotationUpdater(state);
4848
var annotateDeclarationAction = new AnnotateDeclarationRefactoringAction(rewritingManager, annotationUpdater);
4949

5050
var selectedDeclarationProvider = new SelectedDeclarationProvider(selectionService, state);

RubberduckTests/Commands/RefactorCommands/AnnotateSelectedModuleCommandTests.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -44,7 +44,7 @@ protected override CommandBase TestCommand(
4444
.Callback((Action action) => action.Invoke());
4545
var userInteraction = new RefactoringUserInteraction<IAnnotateDeclarationPresenter, AnnotateDeclarationModel>(factory, uiDispatcherMock.Object);
4646

47-
var annotationUpdater = new AnnotationUpdater();
47+
var annotationUpdater = new AnnotationUpdater(state);
4848
var annotateDeclarationAction = new AnnotateDeclarationRefactoringAction(rewritingManager, annotationUpdater);
4949

5050
var selectedDeclarationProvider = new SelectedDeclarationProvider(selectionService, state);

RubberduckTests/Commands/RefactorCommands/CodePaneMoveContainingFolderCommandTests.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -39,7 +39,7 @@ protected override CommandBase TestCommand(
3939
.Callback((Action action) => action.Invoke());
4040
var userInteraction = new RefactoringUserInteraction<IMoveMultipleFoldersPresenter, MoveMultipleFoldersModel>(factory, uiDispatcherMock.Object);
4141

42-
var annotationUpdater = new AnnotationUpdater();
42+
var annotationUpdater = new AnnotationUpdater(state);
4343
var moveToFolderAction = new MoveToFolderRefactoringAction(rewritingManager, annotationUpdater);
4444
var changeFolderAction = new ChangeFolderRefactoringAction(rewritingManager, moveToFolderAction);
4545
var moveFolderAction = new MoveFolderRefactoringAction(rewritingManager, changeFolderAction);

RubberduckTests/Commands/RefactorCommands/CodePaneMoveToFolderCommandTests.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -37,7 +37,7 @@ protected override CommandBase TestCommand(
3737
.Callback((Action action) => action.Invoke());
3838
var userInteraction = new RefactoringUserInteraction<IMoveMultipleToFolderPresenter, MoveMultipleToFolderModel>(factory, uiDispatcherMock.Object);
3939

40-
var annotationUpdater = new AnnotationUpdater();
40+
var annotationUpdater = new AnnotationUpdater(state);
4141
var moveToFolderAction = new MoveToFolderRefactoringAction(rewritingManager, annotationUpdater);
4242
var moveMultipleToFolderAction = new MoveMultipleToFolderRefactoringAction(rewritingManager, moveToFolderAction);
4343

0 commit comments

Comments
 (0)