Skip to content

Commit

Permalink
Browse files Browse the repository at this point in the history
Fix array identifier validation bug
  • Loading branch information
BZngr committed Sep 21, 2020
1 parent 3a74f8d commit b227806
Show file tree
Hide file tree
Showing 3 changed files with 14 additions and 3 deletions.
Expand Up @@ -85,8 +85,14 @@ public EncapsulateFieldConflictFinder(IDeclarationFinderProvider declarationFind
&& rf.Context.TryGetAncestor<VBAParser.RedimVariableDeclarationContext>(out _)))
{
errorMessage = string.Format(RubberduckUI.EncapsulateField_ArrayHasExternalRedimFormat, field.IdentifierName);
return (false, errorMessage);
}

if (field is IEncapsulateFieldAsUDTMemberCandidate udtMember
&& VBAIdentifierValidator.TryMatchInvalidIdentifierCriteria(udtMember.UserDefinedTypeMemberIdentifier, declarationType, out errorMessage, true))
{
return (false, errorMessage);
}
return (!string.IsNullOrEmpty(errorMessage), errorMessage);
}

var hasConflictFreeValidIdentifiers =
Expand Down
Expand Up @@ -203,11 +203,12 @@ End Sub

var field = model[fieldUT];

field.TryValidateEncapsulationAttributes(out var errorMessage);
var result = field.TryValidateEncapsulationAttributes(out var errorMessage);

var expectedError = string.Format(RubberduckUI.EncapsulateField_ArrayHasExternalRedimFormat, field.IdentifierName);

StringAssert.AreEqualIgnoringCase(expectedError, errorMessage);
Assert.IsFalse(result);
}

protected override IRefactoring TestRefactoring(
Expand Down
Expand Up @@ -8,6 +8,7 @@
using Rubberduck.Parsing.Symbols;
using Rubberduck.VBEditor.SafeComWrappers;
using System.Linq;
using Rubberduck.Resources;

namespace RubberduckTests.Refactoring.EncapsulateField
{
Expand Down Expand Up @@ -502,7 +503,10 @@ public void UDTReservedMemberArrayIdentifier()

var model = Support.RetrieveUserModifiedModelPriorToRefactoring(vbe, fieldName, DeclarationType.Variable, presenterAction);

Assert.AreEqual(false, model[fieldName].TryValidateEncapsulationAttributes(out var message), message);
Assert.AreEqual(false, model[fieldName].TryValidateEncapsulationAttributes(out var errorMessage), errorMessage);

var expectedMessage = string.Format(RubberduckUI.InvalidNameCriteria_IsReservedKeywordFormat, fieldName);
Assert.AreEqual(expectedMessage, errorMessage);
}

[Test]
Expand Down

0 comments on commit b227806

Please sign in to comment.