Skip to content

Commit

Permalink
Merge pull request #5526 from MDoerner/AdjustAttributeFromAnnotateDec…
Browse files Browse the repository at this point in the history
…laration

Adjust attribute from annotate declaration
  • Loading branch information
retailcoder committed Jul 4, 2020
2 parents 669c4d8 + 66d00b0 commit 8011485
Show file tree
Hide file tree
Showing 41 changed files with 1,354 additions and 168 deletions.
Expand Up @@ -133,7 +133,8 @@ protected override void OnExecute(object parameter)
{
var model = ModelFromParameter(annotation, target);
if (!annotation.AllowedArguments.HasValue
|| annotation.AllowedArguments.Value > 0)
|| annotation.AllowedArguments.Value > 0
|| annotation is IAttributeAnnotation)
{
model = _userInteraction.UserModifiedModel(model);
}
Expand Down
Expand Up @@ -7,16 +7,18 @@ namespace Rubberduck.UI.Converters
{
public class BoolToVisibleVisibilityConverter : IValueConverter
{
public Visibility FalseVisibility { get; set; } = Visibility.Collapsed;

public object Convert(object value, Type targetType, object parameter, CultureInfo culture)
{
var typedValue = (bool)value;
return typedValue ? Visibility.Visible : Visibility.Collapsed;
return typedValue ? Visibility.Visible : FalseVisibility;
}

public object ConvertBack(object value, Type targetType, object parameter, CultureInfo culture)
{
var typedValue = (Visibility)value;
return typedValue != Visibility.Collapsed;
return typedValue != FalseVisibility;
}
}
}
Expand Up @@ -18,6 +18,7 @@
<converters:InspectionToLocalizedNameConverter x:Key="InspectionToLocalizedNameConverter"/>
<converters:DeclarationToQualifiedNameConverter x:Key="DeclarationToQualifiedNameConverter"/>
<converters:AnnotationToCodeStringConverter x:Key="AnnotationToCodeStringConverter"/>
<converters:BoolToVisibleVisibilityConverter FalseVisibility="Hidden" x:Key="AdjustAttributeVisibilityConverter"/>

</ResourceDictionary>
</UserControl.Resources>
Expand Down Expand Up @@ -102,6 +103,15 @@
</DataTemplate>
</ComboBox.ItemTemplate>
</ComboBox>
<CheckBox Content="{Resx ResxName=Rubberduck.Resources.RubberduckUI, Key=AnnotateDeclarationDialog_AdjustAttributeLabel}"
IsChecked="{Binding AdjustAttribute}"
Visibility="{Binding ShowAdjustAttributeOption, Converter={StaticResource AdjustAttributeVisibilityConverter}}"
Margin="10,0,10,-5"
VerticalContentAlignment="Center">
<CheckBox.LayoutTransform>
<ScaleTransform ScaleX="0.9" ScaleY="0.9"/>
</CheckBox.LayoutTransform>
</CheckBox>
</StackPanel>
<Grid Grid.Row="2">
<Grid.ColumnDefinitions>
Expand Down
Expand Up @@ -80,11 +80,30 @@ public IAnnotation Annotation

OnPropertyChanged();
OnPropertyChanged(nameof(IsValidAnnotation));
OnPropertyChanged(nameof(ShowAdjustAttributeOption));
}
}

public ObservableViewModelCollection<IAnnotationArgumentViewModel> AnnotationArguments { get; }

public bool AdjustAttribute
{
get => Model.AdjustAttribute;
set
{
if (value == Model.AdjustAttribute)
{
return;
}

Model.AdjustAttribute = value;

OnPropertyChanged();
}
}

public bool ShowAdjustAttributeOption => Model?.Annotation is IAttributeAnnotation;

private void RefreshAnnotationArguments(IAnnotation annotation)
{
AnnotationArguments.Clear();
Expand Down
2 changes: 1 addition & 1 deletion Rubberduck.Parsing/Symbols/Declaration.cs
Expand Up @@ -289,7 +289,7 @@ public string DescriptionString
{
string literalDescription;

var memberAttribute = Attributes.SingleOrDefault(a => a.Name == $"{IdentifierName}.VB_Description");
var memberAttribute = Attributes.SingleOrDefault(a => a.Name == Attributes.MemberAttributeName("VB_Description", IdentifierName));
if (memberAttribute != null)
{
literalDescription = memberAttribute.Values.SingleOrDefault() ?? string.Empty;
Expand Down
110 changes: 84 additions & 26 deletions Rubberduck.Parsing/VBA/AnnotationUpdater.cs
Expand Up @@ -10,13 +10,21 @@
using Rubberduck.Parsing.Rewriter;
using Rubberduck.Parsing.Symbols;
using Rubberduck.Parsing.VBA.Parsing;
using Rubberduck.VBEditor;

namespace Rubberduck.Parsing.VBA
{
public class AnnotationUpdater : IAnnotationUpdater
{
private readonly IParseTreeProvider _parseTreeProvider;

private readonly Logger _logger = LogManager.GetCurrentClassLogger();

public AnnotationUpdater(IParseTreeProvider parseTreeProvider)
{
_parseTreeProvider = parseTreeProvider;
}

public void AddAnnotation(IRewriteSession rewriteSession, QualifiedContext context, IAnnotation annotationInfo, IReadOnlyList<string> values = null)
{
var annotationValues = values ?? new List<string>();
Expand All @@ -30,41 +38,55 @@ public void AddAnnotation(IRewriteSession rewriteSession, QualifiedContext conte

if (rewriteSession.TargetCodeKind != CodeKind.CodePaneCode)
{
_logger.Warn($"Tried to add an annotation with a rewriter not suitable for annotationss. (target code kind = {rewriteSession.TargetCodeKind})");
_logger.Warn($"Tried to add an annotation with a rewriter not suitable to annotate contexts. (target code kind = {rewriteSession.TargetCodeKind})");
_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.");
return;
}

AddAnnotation(rewriteSession, context.ModuleName, context.Context, annotationInfo, annotationValues);
}

private void AddAnnotation(IRewriteSession rewriteSession, QualifiedModuleName moduleName, ParserRuleContext context, IAnnotation annotationInfo, IReadOnlyList<string> values = null)
{
var annotationValues = values ?? new List<string>();

if (context == null)
{
_logger.Warn("Tried to add an annotation to a context that is null.");
_logger.Trace($"Tried to add annotation {annotationInfo.Name} with values {AnnotationValuesText(annotationValues)} to a context that is null.");
return;
}

var annotationText = AnnotationText(annotationInfo.Name, annotationValues);

string codeToAdd;
IModuleRewriter rewriter;
if (context.Context.start.Line == 1)
if (context.start.Line == 1)
{
codeToAdd = $"{annotationText}{Environment.NewLine}";
rewriter = rewriteSession.CheckOutModuleRewriter(context.ModuleName);
rewriter = rewriteSession.CheckOutModuleRewriter(moduleName);
rewriter.InsertBefore(0, codeToAdd);
return;
}

var previousEndOfLine = PreviousEndOfLine(context.Context);
var previousEndOfLine = PreviousEndOfLine(context);
if (previousEndOfLine == null)
{
//We are on the first logical line, but not the first physical line.
return;
}

if (context.Context.start.Line > previousEndOfLine.stop.Line + 1)
if (context.start.Line > previousEndOfLine.stop.Line + 1)
{
_logger.Warn("Tried to add an annotation to a context not on the first physical line of a logical line.");
_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}.");
_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}.");
return;
}
codeToAdd = previousEndOfLine.TryGetFollowingContext(out VBAParser.WhiteSpaceContext whitespaceAtStartOfLine)
? $"{whitespaceAtStartOfLine.GetText()}{annotationText}{Environment.NewLine}"

codeToAdd = previousEndOfLine.TryGetFollowingContext(out VBAParser.WhiteSpaceContext whitespaceAtStartOfLine)
? $"{whitespaceAtStartOfLine.GetText()}{annotationText}{Environment.NewLine}"
: $"{annotationText}{Environment.NewLine}";
rewriter = rewriteSession.CheckOutModuleRewriter(context.ModuleName);
rewriter = rewriteSession.CheckOutModuleRewriter(moduleName);
rewriter.InsertAfter(previousEndOfLine.stop.TokenIndex, codeToAdd);
}

Expand Down Expand Up @@ -133,17 +155,47 @@ private void AddModuleAnnotation(IRewriteSession rewriteSession, Declaration dec
return;
}

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

var codeToAdd = $"{AnnotationText(annotationInfo, annotationValues)}{Environment.NewLine}";
var codeToAdd = AnnotationText(annotationInfo, annotationValues);

var rewriter = rewriteSession.CheckOutModuleRewriter(declaration.QualifiedModuleName);
rewriter.InsertBefore(0, codeToAdd);

if (rewriteSession.TargetCodeKind == CodeKind.AttributesCode)
{
InsertAfterLastModuleAttribute(rewriter, declaration.QualifiedModuleName, codeToAdd);
}
else
{
var codeToInsert = codeToAdd + Environment.NewLine;
rewriter.InsertBefore(0, codeToInsert);
}
}

private void InsertAfterLastModuleAttribute(IModuleRewriter rewriter, QualifiedModuleName module, string codeToAdd)
{
var moduleParseTree = (ParserRuleContext)_parseTreeProvider.GetParseTree(module, CodeKind.AttributesCode);
var lastModuleAttribute = moduleParseTree.GetDescendents<VBAParser.ModuleAttributesContext>()
.Where(moduleAttributes => moduleAttributes.attributeStmt() != null)
.SelectMany(moduleAttributes => moduleAttributes.attributeStmt())
.OrderBy(moduleAttribute => moduleAttribute.stop.TokenIndex)
.LastOrDefault();
if (lastModuleAttribute == null)
{
//This should never happen for a real module.
var codeToInsert = codeToAdd + Environment.NewLine;
rewriter.InsertBefore(0, codeToInsert);
}
else
{
var codeToInsert = Environment.NewLine + codeToAdd;
rewriter.InsertAfter(lastModuleAttribute.stop.TokenIndex, codeToInsert);
}
}

private void AddVariableAnnotation(IRewriteSession rewriteSession, Declaration declaration, IAnnotation annotationInfo, IReadOnlyList<string> annotationValues)
Expand All @@ -155,14 +207,18 @@ private void AddVariableAnnotation(IRewriteSession rewriteSession, Declaration d
return;
}

if (rewriteSession.TargetCodeKind != CodeKind.CodePaneCode)
if (rewriteSession.TargetCodeKind != CodeKind.CodePaneCode && (rewriteSession.TargetCodeKind != CodeKind.AttributesCode || declaration.AttributesPassContext == null))
{
_logger.Warn($"Tried to add an annotation to a variable with a rewriter not suitable for annotationss. (target code kind = {rewriteSession.TargetCodeKind})");
_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})");
_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.");
return;
}

AddAnnotation(rewriteSession, new QualifiedContext(declaration.QualifiedName, declaration.Context), annotationInfo, annotationValues);
var context = rewriteSession.TargetCodeKind == CodeKind.CodePaneCode
? declaration.Context
: declaration.AttributesPassContext;

AddAnnotation(rewriteSession, declaration.QualifiedModuleName, context, annotationInfo, annotationValues);
}

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

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

AddAnnotation(rewriteSession, new QualifiedContext(declaration.QualifiedName, declaration.Context), annotationInfo, annotationValues);
}
var context = rewriteSession.TargetCodeKind == CodeKind.CodePaneCode
? declaration.Context
: declaration.AttributesPassContext;

AddAnnotation(rewriteSession, declaration.QualifiedModuleName, context, annotationInfo, annotationValues);
}

public void AddAnnotation(IRewriteSession rewriteSession, IdentifierReference reference, IAnnotation annotationInfo,
IReadOnlyList<string> values = null)
public void AddAnnotation(IRewriteSession rewriteSession, IdentifierReference reference, IAnnotation annotationInfo, IReadOnlyList<string> values = null)
{
var annotationValues = values ?? new List<string>();

Expand All @@ -206,7 +264,7 @@ private void AddMemberAnnotation(IRewriteSession rewriteSession, Declaration dec

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

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

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

0 comments on commit 8011485

Please sign in to comment.