Skip to content

Commit

Permalink
Added ForbiddenAttribute to mark keywords, reserved identifier names,…
Browse files Browse the repository at this point in the history
… and other forbidden names; adjusted name validator accordingly.
  • Loading branch information
retailcoder committed Apr 23, 2021
1 parent 46452a1 commit 3b0d094
Show file tree
Hide file tree
Showing 11 changed files with 425 additions and 21 deletions.
Original file line number Diff line number Diff line change
@@ -1,5 +1,6 @@
using Rubberduck.Parsing.Grammar;
using Rubberduck.Resources;
using Tokens = Rubberduck.Resources.Tokens;

namespace Rubberduck.Refactorings.ExtractMethod
{
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -42,7 +42,13 @@ public string Format(ICodePane activeCodePane, Declaration declaration)

public string Format(Declaration declaration, bool multipleControls)
{
return declaration == null ? string.Empty : FormatDeclaration(declaration, multipleControls);
if (declaration == null)
{
return string.Empty;
}

// designer, there is no code pane selection
return FormatDeclaration(declaration, multipleControls);
}

private string FormatDeclaration(Declaration declaration, bool multipleControls = false)
Expand Down Expand Up @@ -72,18 +78,18 @@ private string FormatDeclaration(Declaration declaration, bool multipleControls
if (declaration.ParentDeclaration.DeclarationType.HasFlag(DeclarationType.Module))
{
// fields
var withEvents = declaration.IsWithEvents ? "(WithEvents) " : string.Empty;
var withEvents = declaration.IsWithEvents ? $"({Tokens.WithEvents}) " : string.Empty;
return $"{withEvents}{moduleName}.{declaration.IdentifierName} {typeName}";
}
}

if (declaration.DeclarationType.HasFlag(DeclarationType.Member))
{
var formattedDeclaration = declaration.QualifiedName.ToString();
var formattedDeclaration = $"{declaration.QualifiedName}";
if (declaration.DeclarationType == DeclarationType.Function
|| declaration.DeclarationType == DeclarationType.PropertyGet)
{
formattedDeclaration += typeName;
formattedDeclaration += $" {typeName}";
}

return formattedDeclaration;
Expand All @@ -103,16 +109,16 @@ private string FormatDeclaration(Declaration declaration, bool multipleControls
case DeclarationType.Enumeration:
case DeclarationType.UserDefinedType:
return !declaration.IsUserDefined
// built-in enums & UDT's don't have a module
? $"{Path.GetFileName(moduleName.ProjectPath)};{moduleName.ProjectName}.{declaration.IdentifierName}"
// built-in enums & UDTs don't have a module
? $"{Path.GetFileName(moduleName.ProjectPath)};{declaration.IdentifierName}"
: moduleName.ToString();
case DeclarationType.EnumerationMember:
case DeclarationType.UserDefinedTypeMember:
return declaration.IsUserDefined
? $"{moduleName}.{declaration.ParentDeclaration.IdentifierName}.{declaration.IdentifierName} {typeName}"
: $"{Path.GetFileName(moduleName.ProjectPath)};{moduleName.ProjectName}.{declaration.ParentDeclaration.IdentifierName}.{declaration.IdentifierName} {typeName}";
: $"{Path.GetFileName(moduleName.ProjectPath)};{declaration.ParentDeclaration.IdentifierName}.{declaration.IdentifierName} {typeName}";
case DeclarationType.ComAlias:
return $"{Path.GetFileName(moduleName.ProjectPath)};{moduleName.ProjectName}.{declaration.IdentifierName} (alias:{declaration.AsTypeName})";
return $"{Path.GetFileName(moduleName.ProjectPath)};{declaration.IdentifierName} (alias:{declaration.AsTypeName})";
}

return string.Empty;
Expand All @@ -125,22 +131,20 @@ private static string TypeName(Declaration declaration, bool multipleControls, s
return RubberduckUI.ContextMultipleControlsSelection;
}

var friendlyTypeName = "IDispatch".Equals(declaration.AsTypeName, System.StringComparison.InvariantCultureIgnoreCase)
? "Object"
var typeName = Tokens.IDispatch.Equals(declaration.AsTypeName, System.StringComparison.InvariantCultureIgnoreCase)
? Tokens.Object
: declaration.AsTypeName ?? string.Empty;

var typeName = declaration.IsArray
? $"{friendlyTypeName}()"
: friendlyTypeName;
var friendlyTypeName = declaration.IsArray ? $"{typeName}()" : typeName;

switch (declaration)
{
case ValuedDeclaration valued:
return $"({declarationType}{(string.IsNullOrEmpty(typeName) ? string.Empty : ":" + typeName)}{(string.IsNullOrEmpty(valued.Expression) ? string.Empty : $" = {valued.Expression}")})";
return $"({declarationType}{(string.IsNullOrEmpty(friendlyTypeName) ? string.Empty : ":" + friendlyTypeName)}{(string.IsNullOrEmpty(valued.Expression) ? string.Empty : $" = {valued.Expression}")})";
case ParameterDeclaration parameter:
return $"({declarationType}{(string.IsNullOrEmpty(typeName) ? string.Empty : ":" + typeName)}{(string.IsNullOrEmpty(parameter.DefaultValue) ? string.Empty : $" = {parameter.DefaultValue}")})";
return $"({declarationType}{(string.IsNullOrEmpty(friendlyTypeName) ? string.Empty : ":" + friendlyTypeName)}{(string.IsNullOrEmpty(parameter.DefaultValue) ? string.Empty : $" = {parameter.DefaultValue}")})";
default:
return $"({declarationType}{(string.IsNullOrEmpty(typeName) ? string.Empty : ":" + typeName)})";
return $"({declarationType}{(string.IsNullOrEmpty(friendlyTypeName) ? string.Empty : ":" + friendlyTypeName)})";
}
}
}
Expand Down
2 changes: 1 addition & 1 deletion Rubberduck.Core/UI/FindSymbol/FindSymbolControl.xaml
Original file line number Diff line number Diff line change
Expand Up @@ -25,7 +25,7 @@
<ColumnDefinition Width="32" />
</Grid.ColumnDefinitions>

<ComboBox x:Name="searchComboBox"
<ComboBox x:Name="SearchComboBox"
IsEditable="True"
ItemsSource="{Binding MatchResults}"
SelectedItem="{Binding SelectedItem, Mode=TwoWay, UpdateSourceTrigger=PropertyChanged}"
Expand Down
2 changes: 1 addition & 1 deletion Rubberduck.Core/UI/FindSymbol/FindSymbolControl.xaml.cs
Original file line number Diff line number Diff line change
Expand Up @@ -46,7 +46,7 @@ private void UIElement_OnPreviewKeyDown(object sender, KeyEventArgs e)

private void FindSymbolControl_Loaded(object sender, System.Windows.RoutedEventArgs e)
{
searchComboBox.Focus();
SearchComboBox.Focus();
}
}
}
6 changes: 5 additions & 1 deletion Rubberduck.Core/UI/Refactorings/ExtractMethodDialog.cs
Original file line number Diff line number Diff line change
Expand Up @@ -3,11 +3,13 @@
using System.ComponentModel;
using System.Drawing;
using System.Linq;
using System.Reflection;
using System.Windows.Forms;
using Rubberduck.Parsing.Grammar;
using Rubberduck.Parsing.Symbols;
using Rubberduck.Refactorings.ExtractMethod;
using Rubberduck.Resources;
using Tokens = Rubberduck.Resources.Tokens;

namespace Rubberduck.UI.Refactorings
{
Expand Down Expand Up @@ -193,7 +195,9 @@ public string MethodName

private void ValidateName()
{
var tokenValues = typeof(Tokens).GetFields().Select(item => item.GetValue(null)).Cast<string>().Select(item => item);
var tokenValues = typeof(Tokens).GetFields()
.Where(item => !item.GetCustomAttributes<NotReservedAttribute>().Any())
.Select(item => item.GetValue(null)).Cast<string>().Select(item => item);

OkButton.Enabled = MethodName != OldMethodName
&& char.IsLetter(MethodName.FirstOrDefault())
Expand Down
1 change: 1 addition & 0 deletions Rubberduck.Refactorings/Common/CodeBuilder.cs
Original file line number Diff line number Diff line change
Expand Up @@ -6,6 +6,7 @@
using System;
using System.Collections.Generic;
using System.Linq;
using Tokens = Rubberduck.Resources.Tokens;

namespace Rubberduck.Refactorings
{
Expand Down
10 changes: 8 additions & 2 deletions Rubberduck.Refactorings/Common/VBAIdentifierValidator.cs
Original file line number Diff line number Diff line change
Expand Up @@ -5,13 +5,19 @@
using System.Collections.Generic;
using System.Globalization;
using System.Linq;
using System.Reflection;
using Tokens = Rubberduck.Resources.Tokens;

namespace Rubberduck.Refactorings.Common
{
public static class VBAIdentifierValidator
{
private static IEnumerable<string> ReservedIdentifiers =
typeof(Tokens).GetFields().Select(item => item.GetValue(null).ToString()).ToArray();
// NOTE: ForbiddenAttribute marks the tokens that don't compile as identifier names. Includes "bad but legal" names.
// TODO: Compare with the unfiltered tokens if a client needs to tell "bad but legal" from "bad and illegal" names.
private static readonly IEnumerable<string> ReservedIdentifiers =
typeof(Tokens).GetFields()
.Where(item => item.GetType().GetCustomAttributes<ForbiddenAttribute>().Any())
.Select(item => item.GetValue(null).ToString()).ToArray();

/// <summary>
/// Predicate function determining if an identifier string's content will trigger a result for the UseMeaningfulNames inspection.
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -15,6 +15,7 @@
using Rubberduck.VBEditor.ComManagement;
using Rubberduck.VBEditor.SafeComWrappers;
using Rubberduck.VBEditor.Utility;
using Tokens = Rubberduck.Resources.Tokens;

namespace Rubberduck.Refactorings.ExtractInterface
{
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -5,6 +5,7 @@
using Rubberduck.Parsing.Rewriter;
using Rubberduck.Parsing.Symbols;
using Rubberduck.Resources;
using Tokens = Rubberduck.Resources.Tokens;

namespace Rubberduck.Refactorings.AddInterfaceImplementations
{
Expand Down

0 comments on commit 3b0d094

Please sign in to comment.