Skip to content

Commit 6d4a334

Browse files
committed
Add more safety around adding annotations
1 parent 77d09fb commit 6d4a334

File tree

1 file changed

+65
-9
lines changed

1 file changed

+65
-9
lines changed

Rubberduck.Parsing/VBA/AnnotationUpdater.cs

Lines changed: 65 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -9,6 +9,7 @@
99
using Rubberduck.Parsing.Grammar;
1010
using Rubberduck.Parsing.Rewriter;
1111
using Rubberduck.Parsing.Symbols;
12+
using Rubberduck.Parsing.VBA.Parsing;
1213

1314
namespace Rubberduck.Parsing.VBA
1415
{
@@ -27,6 +28,13 @@ public void AddAnnotation(IRewriteSession rewriteSession, QualifiedContext conte
2728
return;
2829
}
2930

31+
if (rewriteSession.TargetCodeKind != CodeKind.CodePaneCode)
32+
{
33+
_logger.Warn($"Tried to add an annotation with a rewriter not suitable for annotationss. (target code kind = {rewriteSession.TargetCodeKind})");
34+
_logger.Trace($"Tried to add annotation {annotationType} with values {AnnotationValuesText(annotationValues)} to {context.Context.GetText()} at {context.Context.GetSelection()} in module {context.ModuleName} using a rewriter not suitable for annotations.");
35+
return;
36+
}
37+
3038
var annotationText = AnnotationText(annotationType, annotationValues);
3139

3240
string codeToAdd;
@@ -111,43 +119,64 @@ public void AddAnnotation(IRewriteSession rewriteSession, Declaration declaratio
111119
}
112120
}
113121

114-
private void AddModuleAnnotation(IRewriteSession rewriteSession, Declaration declaration, AnnotationType annotationType, IReadOnlyList<string> values)
122+
private void AddModuleAnnotation(IRewriteSession rewriteSession, Declaration declaration, AnnotationType annotationType, IReadOnlyList<string> annotationValues)
115123
{
116124
if (!annotationType.HasFlag(AnnotationType.ModuleAnnotation))
117125
{
118126
_logger.Warn("Tried to add an annotation without the module annotation flag to a module.");
119-
_logger.Trace($"Tried to add the annotation {annotationType} with values {AnnotationValuesText(values)} to the module {declaration.QualifiedModuleName}.");
127+
_logger.Trace($"Tried to add the annotation {annotationType} with values {AnnotationValuesText(annotationValues)} to the module {declaration.QualifiedModuleName}.");
128+
return;
129+
}
130+
131+
if (rewriteSession.TargetCodeKind != CodeKind.CodePaneCode)
132+
{
133+
_logger.Warn($"Tried to add an annotation to a module with a rewriter not suitable for annotationss. (target code kind = {rewriteSession.TargetCodeKind})");
134+
_logger.Trace($"Tried to add annotation {annotationType} with values {AnnotationValuesText(annotationValues)} to the module {declaration.QualifiedModuleName} using a rewriter not suitable for annotations.");
120135
return;
121136
}
122137

123-
var codeToAdd = $"{AnnotationText(annotationType, values)}{Environment.NewLine}";
138+
var codeToAdd = $"{AnnotationText(annotationType, annotationValues)}{Environment.NewLine}";
124139

125140
var rewriter = rewriteSession.CheckOutModuleRewriter(declaration.QualifiedModuleName);
126141
rewriter.InsertBefore(0, codeToAdd);
127142
}
128143

129-
private void AddVariableAnnotation(IRewriteSession rewriteSession, Declaration declaration, AnnotationType annotationType, IReadOnlyList<string> values)
144+
private void AddVariableAnnotation(IRewriteSession rewriteSession, Declaration declaration, AnnotationType annotationType, IReadOnlyList<string> annotationValues)
130145
{
131146
if (!annotationType.HasFlag(AnnotationType.VariableAnnotation))
132147
{
133148
_logger.Warn("Tried to add an annotation without the variable annotation flag to a variable declaration.");
134-
_logger.Trace($"Tried to add the annotation {annotationType} with values {AnnotationValuesText(values)} to the variable declaration for {declaration.QualifiedName}.");
149+
_logger.Trace($"Tried to add the annotation {annotationType} with values {AnnotationValuesText(annotationValues)} to the variable declaration for {declaration.QualifiedName}.");
135150
return;
136151
}
137152

138-
AddAnnotation(rewriteSession, new QualifiedContext(declaration.QualifiedName, declaration.Context), annotationType, values);
153+
if (rewriteSession.TargetCodeKind != CodeKind.CodePaneCode)
154+
{
155+
_logger.Warn($"Tried to add an annotation to a variable with a rewriter not suitable for annotationss. (target code kind = {rewriteSession.TargetCodeKind})");
156+
_logger.Trace($"Tried to add annotation {annotationType} with values {AnnotationValuesText(annotationValues)} to the the variable {declaration.IdentifierName} at {declaration.Selection} in module {declaration.QualifiedModuleName} using a rewriter not suitable for annotations.");
157+
return;
158+
}
159+
160+
AddAnnotation(rewriteSession, new QualifiedContext(declaration.QualifiedName, declaration.Context), annotationType, annotationValues);
139161
}
140162

141-
private void AddMemberAnnotation(IRewriteSession rewriteSession, Declaration declaration, AnnotationType annotationType, IReadOnlyList<string> values)
163+
private void AddMemberAnnotation(IRewriteSession rewriteSession, Declaration declaration, AnnotationType annotationType, IReadOnlyList<string> annotationValues)
142164
{
143165
if (!annotationType.HasFlag(AnnotationType.MemberAnnotation))
144166
{
145167
_logger.Warn("Tried to add an annotation without the member annotation flag to a member declaration.");
146-
_logger.Trace($"Tried to add the annotation {annotationType} with values {AnnotationValuesText(values)} to the member declaration for {declaration.QualifiedName}.");
168+
_logger.Trace($"Tried to add the annotation {annotationType} with values {AnnotationValuesText(annotationValues)} to the member declaration for {declaration.QualifiedName}.");
169+
return;
170+
}
171+
172+
if (rewriteSession.TargetCodeKind != CodeKind.CodePaneCode)
173+
{
174+
_logger.Warn($"Tried to add an annotation to a member with a rewriter not suitable for annotationss. (target code kind = {rewriteSession.TargetCodeKind})");
175+
_logger.Trace($"Tried to add annotation {annotationType} with values {AnnotationValuesText(annotationValues)} to the the member {declaration.IdentifierName} at {declaration.Selection} in module {declaration.QualifiedModuleName} using a rewriter not suitable for annotations.");
147176
return;
148177
}
149178

150-
AddAnnotation(rewriteSession, new QualifiedContext(declaration.QualifiedName, declaration.Context), annotationType, values);
179+
AddAnnotation(rewriteSession, new QualifiedContext(declaration.QualifiedName, declaration.Context), annotationType, annotationValues);
151180
}
152181

153182

@@ -170,6 +199,13 @@ public void AddAnnotation(IRewriteSession rewriteSession, IdentifierReference re
170199
return;
171200
}
172201

202+
if (rewriteSession.TargetCodeKind != CodeKind.CodePaneCode)
203+
{
204+
_logger.Warn($"Tried to add an annotation to an identifier reference with a rewriter not suitable for annotationss. (target code kind = {rewriteSession.TargetCodeKind})");
205+
_logger.Trace($"Tried to add annotation {annotationType} 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.");
206+
return;
207+
}
208+
173209
AddAnnotation(rewriteSession, new QualifiedContext(reference.QualifiedModuleName, reference.Context), annotationType, annotationValues);
174210
}
175211

@@ -181,6 +217,13 @@ public void RemoveAnnotation(IRewriteSession rewriteSession, IAnnotation annotat
181217
return;
182218
}
183219

220+
if (rewriteSession.TargetCodeKind != CodeKind.CodePaneCode)
221+
{
222+
_logger.Warn($"Tried to remove an annotation with a rewriter not suitable for annotationss. (target code kind = {rewriteSession.TargetCodeKind})");
223+
_logger.Trace($"Tried to remove annotation {annotation.AnnotationType} at {annotation.QualifiedSelection.Selection} in module {annotation.QualifiedSelection.QualifiedName} using a rewriter not suitable for annotations.");
224+
return;
225+
}
226+
184227
var annotationContext = annotation.Context;
185228
var annotationList = (VBAParser.AnnotationListContext)annotationContext.Parent;
186229

@@ -246,6 +289,12 @@ public void RemoveAnnotations(IRewriteSession rewriteSession, IEnumerable<IAnnot
246289
return;
247290
}
248291

292+
if (rewriteSession.TargetCodeKind != CodeKind.CodePaneCode)
293+
{
294+
_logger.Warn($"Tried to remove multiple annotations with a rewriter not suitable for annotations. (target code kind = {rewriteSession.TargetCodeKind})");
295+
return;
296+
}
297+
249298
var annotationsByAnnotationList = annotations.Distinct()
250299
.GroupBy(annotation => new QualifiedContext(annotation.QualifiedSelection.QualifiedName, (ParserRuleContext)annotation.Context.Parent))
251300
.ToDictionary(grouping => grouping.Key, grouping => grouping.ToList());
@@ -287,6 +336,13 @@ public void UpdateAnnotation(IRewriteSession rewriteSession, IAnnotation annotat
287336
return;
288337
}
289338

339+
if (rewriteSession.TargetCodeKind != CodeKind.CodePaneCode)
340+
{
341+
_logger.Warn($"Tried to update an annotation with a rewriter not suitable for annotationss. (target code kind = {rewriteSession.TargetCodeKind})");
342+
_logger.Trace($"Tried to update annotation {annotation.AnnotationType} at {annotation.QualifiedSelection.Selection} in module {annotation.QualifiedSelection.QualifiedName} with annotation {newAnnotationType} with values {AnnotationValuesText(newAnnotationValues)} using a rewriter not suitable for annotations.");
343+
return;
344+
}
345+
290346
//If there are no common flags, the annotations cannot apply to the same target.
291347
if ((annotation.AnnotationType & newAnnotationType) == 0)
292348
{

0 commit comments

Comments
 (0)