Skip to content

Commit 8011485

Browse files
authored
Merge pull request #5526 from MDoerner/AdjustAttributeFromAnnotateDeclaration
Adjust attribute from annotate declaration
2 parents 669c4d8 + 66d00b0 commit 8011485

File tree

41 files changed

+1354
-168
lines changed

Some content is hidden

Large Commits have some content hidden by default. Use the searchbox below for content that may be hidden.

41 files changed

+1354
-168
lines changed

Rubberduck.Core/UI/CodeExplorer/Commands/AnnotateDeclarationCommand.cs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -133,7 +133,8 @@ protected override void OnExecute(object parameter)
133133
{
134134
var model = ModelFromParameter(annotation, target);
135135
if (!annotation.AllowedArguments.HasValue
136-
|| annotation.AllowedArguments.Value > 0)
136+
|| annotation.AllowedArguments.Value > 0
137+
|| annotation is IAttributeAnnotation)
137138
{
138139
model = _userInteraction.UserModifiedModel(model);
139140
}

Rubberduck.Core/UI/Converters/BoolToVisibleVisibilityConverter.cs

Lines changed: 4 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -7,16 +7,18 @@ namespace Rubberduck.UI.Converters
77
{
88
public class BoolToVisibleVisibilityConverter : IValueConverter
99
{
10+
public Visibility FalseVisibility { get; set; } = Visibility.Collapsed;
11+
1012
public object Convert(object value, Type targetType, object parameter, CultureInfo culture)
1113
{
1214
var typedValue = (bool)value;
13-
return typedValue ? Visibility.Visible : Visibility.Collapsed;
15+
return typedValue ? Visibility.Visible : FalseVisibility;
1416
}
1517

1618
public object ConvertBack(object value, Type targetType, object parameter, CultureInfo culture)
1719
{
1820
var typedValue = (Visibility)value;
19-
return typedValue != Visibility.Collapsed;
21+
return typedValue != FalseVisibility;
2022
}
2123
}
2224
}

Rubberduck.Core/UI/Refactorings/AnnotateDeclaration/AnnotateDeclarationView.xaml

Lines changed: 10 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -18,6 +18,7 @@
1818
<converters:InspectionToLocalizedNameConverter x:Key="InspectionToLocalizedNameConverter"/>
1919
<converters:DeclarationToQualifiedNameConverter x:Key="DeclarationToQualifiedNameConverter"/>
2020
<converters:AnnotationToCodeStringConverter x:Key="AnnotationToCodeStringConverter"/>
21+
<converters:BoolToVisibleVisibilityConverter FalseVisibility="Hidden" x:Key="AdjustAttributeVisibilityConverter"/>
2122

2223
</ResourceDictionary>
2324
</UserControl.Resources>
@@ -102,6 +103,15 @@
102103
</DataTemplate>
103104
</ComboBox.ItemTemplate>
104105
</ComboBox>
106+
<CheckBox Content="{Resx ResxName=Rubberduck.Resources.RubberduckUI, Key=AnnotateDeclarationDialog_AdjustAttributeLabel}"
107+
IsChecked="{Binding AdjustAttribute}"
108+
Visibility="{Binding ShowAdjustAttributeOption, Converter={StaticResource AdjustAttributeVisibilityConverter}}"
109+
Margin="10,0,10,-5"
110+
VerticalContentAlignment="Center">
111+
<CheckBox.LayoutTransform>
112+
<ScaleTransform ScaleX="0.9" ScaleY="0.9"/>
113+
</CheckBox.LayoutTransform>
114+
</CheckBox>
105115
</StackPanel>
106116
<Grid Grid.Row="2">
107117
<Grid.ColumnDefinitions>

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

Lines changed: 19 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -80,11 +80,30 @@ public IAnnotation Annotation
8080

8181
OnPropertyChanged();
8282
OnPropertyChanged(nameof(IsValidAnnotation));
83+
OnPropertyChanged(nameof(ShowAdjustAttributeOption));
8384
}
8485
}
8586

8687
public ObservableViewModelCollection<IAnnotationArgumentViewModel> AnnotationArguments { get; }
8788

89+
public bool AdjustAttribute
90+
{
91+
get => Model.AdjustAttribute;
92+
set
93+
{
94+
if (value == Model.AdjustAttribute)
95+
{
96+
return;
97+
}
98+
99+
Model.AdjustAttribute = value;
100+
101+
OnPropertyChanged();
102+
}
103+
}
104+
105+
public bool ShowAdjustAttributeOption => Model?.Annotation is IAttributeAnnotation;
106+
88107
private void RefreshAnnotationArguments(IAnnotation annotation)
89108
{
90109
AnnotationArguments.Clear();

Rubberduck.Parsing/Symbols/Declaration.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -289,7 +289,7 @@ public string DescriptionString
289289
{
290290
string literalDescription;
291291

292-
var memberAttribute = Attributes.SingleOrDefault(a => a.Name == $"{IdentifierName}.VB_Description");
292+
var memberAttribute = Attributes.SingleOrDefault(a => a.Name == Attributes.MemberAttributeName("VB_Description", IdentifierName));
293293
if (memberAttribute != null)
294294
{
295295
literalDescription = memberAttribute.Values.SingleOrDefault() ?? string.Empty;

Rubberduck.Parsing/VBA/AnnotationUpdater.cs

Lines changed: 84 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,18 @@ 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+
var context = rewriteSession.TargetCodeKind == CodeKind.CodePaneCode
218+
? declaration.Context
219+
: declaration.AttributesPassContext;
220+
221+
AddAnnotation(rewriteSession, declaration.QualifiedModuleName, context, annotationInfo, annotationValues);
166222
}
167223

168224
private void AddMemberAnnotation(IRewriteSession rewriteSession, Declaration declaration, IAnnotation annotationInfo, IReadOnlyList<string> annotationValues)
@@ -174,19 +230,21 @@ private void AddMemberAnnotation(IRewriteSession rewriteSession, Declaration dec
174230
return;
175231
}
176232

177-
if (rewriteSession.TargetCodeKind != CodeKind.CodePaneCode)
233+
if (rewriteSession.TargetCodeKind != CodeKind.CodePaneCode && (rewriteSession.TargetCodeKind != CodeKind.AttributesCode || declaration.AttributesPassContext == null))
178234
{
179-
_logger.Warn($"Tried to add an annotation to a member with a rewriter not suitable for annotationss. (target code kind = {rewriteSession.TargetCodeKind})");
235+
_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})");
180236
_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.");
181237
return;
182238
}
183239

184-
AddAnnotation(rewriteSession, new QualifiedContext(declaration.QualifiedName, declaration.Context), annotationInfo, annotationValues);
185-
}
240+
var context = rewriteSession.TargetCodeKind == CodeKind.CodePaneCode
241+
? declaration.Context
242+
: declaration.AttributesPassContext;
186243

244+
AddAnnotation(rewriteSession, declaration.QualifiedModuleName, context, annotationInfo, annotationValues);
245+
}
187246

188-
public void AddAnnotation(IRewriteSession rewriteSession, IdentifierReference reference, IAnnotation annotationInfo,
189-
IReadOnlyList<string> values = null)
247+
public void AddAnnotation(IRewriteSession rewriteSession, IdentifierReference reference, IAnnotation annotationInfo, IReadOnlyList<string> values = null)
190248
{
191249
var annotationValues = values ?? new List<string>();
192250

@@ -206,7 +264,7 @@ public void AddAnnotation(IRewriteSession rewriteSession, IdentifierReference re
206264

207265
if (rewriteSession.TargetCodeKind != CodeKind.CodePaneCode)
208266
{
209-
_logger.Warn($"Tried to add an annotation to an identifier reference with a rewriter not suitable for annotationss. (target code kind = {rewriteSession.TargetCodeKind})");
267+
_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})");
210268
_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.");
211269
return;
212270
}
@@ -294,7 +352,7 @@ public void RemoveAnnotations(IRewriteSession rewriteSession, IEnumerable<IParse
294352
return;
295353
}
296354

297-
if (rewriteSession.TargetCodeKind != CodeKind.CodePaneCode)
355+
if (rewriteSession.TargetCodeKind != CodeKind.CodePaneCode && rewriteSession.TargetCodeKind != CodeKind.AttributesCode)
298356
{
299357
_logger.Warn($"Tried to remove multiple annotations with a rewriter not suitable for annotations. (target code kind = {rewriteSession.TargetCodeKind})");
300358
return;
@@ -341,7 +399,7 @@ public void UpdateAnnotation(IRewriteSession rewriteSession, IParseTreeAnnotatio
341399
return;
342400
}
343401

344-
if (rewriteSession.TargetCodeKind != CodeKind.CodePaneCode)
402+
if (rewriteSession.TargetCodeKind != CodeKind.CodePaneCode && rewriteSession.TargetCodeKind != CodeKind.AttributesCode)
345403
{
346404
_logger.Warn($"Tried to update an annotation with a rewriter not suitable for annotationss. (target code kind = {rewriteSession.TargetCodeKind})");
347405
_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.");

0 commit comments

Comments
 (0)