Skip to content

Commit

Permalink
Final updates per PR comments
Browse files Browse the repository at this point in the history
  • Loading branch information
BZngr committed Feb 28, 2017
1 parent 6871731 commit 8e4a56b
Show file tree
Hide file tree
Showing 7 changed files with 79 additions and 108 deletions.
Expand Up @@ -26,8 +26,8 @@ public AssignedByValParameterMakeLocalCopyQuickFix(Declaration target, Qualified
{
_target = target;
_dialogFactory = dialogFactory;
_localCopyVariableName = "x" + _target.IdentifierName.CapitalizeFirstLetter();
_variableNamesAccessibleToProcedureContext = GetVariableNamesAccessibleToProcedureContext(_target.Context.Parent.Parent);
SetValidLocalCopyVariableNameSuggestion();
}

public override bool CanFixInModule { get { return false; } }
Expand All @@ -37,7 +37,7 @@ public override void Fix()
{
RequestLocalCopyVariableName();

if (!ProposedLocalVariableNameIsValid() || IsCancelled)
if (!VariableNameIsValid(_localCopyVariableName) || IsCancelled)
{
return;
}
Expand All @@ -62,12 +62,31 @@ private void RequestLocalCopyVariableName()
}
}

private bool ProposedLocalVariableNameIsValid()
private void SetValidLocalCopyVariableNameSuggestion()
{
_localCopyVariableName = "x" + _target.IdentifierName.CapitalizeFirstLetter();
if (VariableNameIsValid(_localCopyVariableName)) { return; }

//If the initial suggestion is not valid, keep pre-pending x's until it is
for ( int attempt = 2; attempt < 10; attempt++)
{
_localCopyVariableName = "x" + _localCopyVariableName;
if (VariableNameIsValid(_localCopyVariableName))
{
return;
}
}
//if "xxFoo" to "xxxxxxxxxxFoo" isn't unique, give up and go with the original suggestion.
//The QuickFix will leave the code as-is unless it receives a name that is free of conflicts
_localCopyVariableName = "x" + _target.IdentifierName.CapitalizeFirstLetter();
}

private bool VariableNameIsValid(string variableName)
{
var validator = new VariableNameValidator(_localCopyVariableName);
return validator.IsValidName()
&& !_variableNamesAccessibleToProcedureContext
.Any(name => name.ToUpper().Equals(_localCopyVariableName.ToUpper()));
.Any(name => name.Equals(_localCopyVariableName, System.StringComparison.InvariantCultureIgnoreCase));
}

private void ReplaceAssignedByValParameterReferences()
Expand All @@ -92,6 +111,7 @@ private string BuildLocalCopyDeclaration()
return Tokens.Dim + " " + _localCopyVariableName + " " + Tokens.As
+ " " + _target.AsTypeName;
}

private string BuildLocalCopyAssignment()
{
return (SymbolList.ValueTypes.Contains(_target.AsTypeName) ? string.Empty : Tokens.Set + " ")
Expand All @@ -112,7 +132,7 @@ private string[] GetVariableNamesAccessibleToProcedureContext(RuleContext ruleCo
var potentiallyUnreferencedParameters = GetIdentifierNames(args);
allIdentifiers.UnionWith(potentiallyUnreferencedParameters);

//TODO: add module and global scope variableNames.
//TODO: add module and global scope variableNames to the list.

return allIdentifiers.ToArray();
}
Expand Down
2 changes: 0 additions & 2 deletions RetailCoder.VBE/Rubberduck.csproj
Expand Up @@ -473,10 +473,8 @@
<Compile Include="UI\EnvironmentProvider.cs" />
<Compile Include="UI\ModernFolderBrowser.cs" />
<Compile Include="UI\Refactorings\AssignedByValParameterQuickFixDialogFactory.cs" />
<Compile Include="UI\Refactorings\AssignedByValParameterQuickFixMockDialogFactory.cs" />
<Compile Include="UI\Refactorings\IAssignedByValParameterQuickFixDialog.cs" />
<Compile Include="UI\Refactorings\IAssignedByValParameterQuickFixDialogFactory.cs" />
<Compile Include="UI\Refactorings\AssignedByValParameterQuickFixMockDialog.cs" />
<Compile Include="UI\SelectionChangeService.cs" />
<Compile Include="VersionCheck\IVersionCheck.cs" />
<Compile Include="UI\Command\MenuItems\CommandBars\AppCommandBarBase.cs" />
Expand Down

This file was deleted.

This file was deleted.

Expand Up @@ -118,7 +118,7 @@ End Sub
.AddComponent("Module1", ComponentType.StandardModule, caller)
.MockVbeBuilder()
.Build();
var results = GetInspectionResults(vbe);
var results = GetInspectionResults(vbe.Object);
Assert.AreEqual(0, results.Count());
}

Expand Down Expand Up @@ -168,29 +168,29 @@ private void AssertVbaFragmentYieldsExpectedInspectionResultCount(string inputCo
private string ApplyIgnoreOnceQuickFixToCodeFragment(string inputCode)
{
var vbe = BuildMockVBEStandardModuleForVBAFragment(inputCode);
var inspectionResults = GetInspectionResults(vbe);
var inspectionResults = GetInspectionResults(vbe.Object);

inspectionResults.First().QuickFixes.Single(s => s is IgnoreOnceQuickFix).Fix();

return GetModuleContent(vbe);
return GetModuleContent(vbe.Object);
}

private string GetModuleContent(Mock<IVBE> vbe)
private string GetModuleContent(IVBE vbe)
{
var project = vbe.Object.VBProjects[0];
var project = vbe.VBProjects[0];
var module = project.VBComponents[0].CodeModule;
return module.Content();
}

private IEnumerable<Rubberduck.Inspections.Abstract.InspectionResultBase> GetInspectionResults(string inputCode)
{
var vbe = BuildMockVBEStandardModuleForVBAFragment(inputCode);
return GetInspectionResults(vbe);
return GetInspectionResults(vbe.Object);
}

private IEnumerable<Rubberduck.Inspections.Abstract.InspectionResultBase> GetInspectionResults(Mock<IVBE> vbe)
private IEnumerable<Rubberduck.Inspections.Abstract.InspectionResultBase> GetInspectionResults(IVBE vbe)
{
var parser = MockParser.Create(vbe.Object, new RubberduckParserState(vbe.Object));
var parser = MockParser.Create(vbe, new RubberduckParserState(vbe));
parser.Parse(new CancellationTokenSource());
if (parser.State.Status >= ParserState.Error) { Assert.Inconclusive("Parser Error"); }

Expand Down
Expand Up @@ -10,7 +10,7 @@
using RubberduckTests.Mocks;
using System.Threading;
using Rubberduck.UI.Refactorings;

using System.Windows.Forms;

namespace RubberduckTests.Inspections
{
Expand Down Expand Up @@ -55,8 +55,10 @@ public void AssignedByValParameter_LocalVariableAssignment_NameInUse()
string expectedCode =
@"
Public Sub Foo(ByVal arg1 As String)
Dim xxArg1 As String
xxArg1 = arg1
xArg1 = 6
Let arg1 = ""test""
Let xxArg1 = ""test""
End Sub"
;

Expand All @@ -75,8 +77,10 @@ public void AssignedByValParameter_LocalVariableAssignment_NameInUse()
expectedCode =
@"
Public Sub Foo(ByVal arg1 As String)
Dim xxArg1 As String
xxArg1 = arg1
Dim fooVar, xArg1 As Long
Let arg1 = ""test""
Let xxArg1 = ""test""
End Sub"
;

Expand All @@ -96,9 +100,11 @@ public void AssignedByValParameter_LocalVariableAssignment_NameInUse()
expectedCode =
@"
Public Sub Foo(ByVal arg1 As String)
Dim xxArg1 As String
xxArg1 = arg1
Dim fooVar, _
xArg1 As Long
Let arg1 = ""test""
Let xxArg1 = ""test""
End Sub"
;
quickFixResult = ApplyLocalVariableQuickFixToVBAFragment(inputCode);
Expand Down Expand Up @@ -137,7 +143,7 @@ End Sub
Assert.AreEqual(expectedCode, quickFixResult);

//Punt if the user-defined or auto-generated name is already present as an parameter name
userEnteredName = "theSecondArg";
userEnteredName = "moduleScopeName";

inputCode =
@"
Expand Down Expand Up @@ -306,7 +312,6 @@ End Sub

quickFixResult = ApplyLocalVariableQuickFixToVBAFragment(inputCode);
Assert.AreEqual(expectedCode, quickFixResult);

}

[TestMethod]
Expand Down Expand Up @@ -368,6 +373,7 @@ End Sub
var quickFixResult = ApplyLocalVariableQuickFixToVBAFragment(inputCode);
Assert.AreEqual(expectedCode, quickFixResult);
}

[TestMethod]
[TestCategory("Inspections")]
public void AssignedByValParameter_ProperPlacementOfDeclaration()
Expand Down Expand Up @@ -433,7 +439,6 @@ End Function
Assert.AreEqual(expectedCode, quickFixResult);
}


[TestMethod]
[TestCategory("Inspections")]
public void InspectionType()
Expand All @@ -455,11 +460,13 @@ public void InspectionName()
private string ApplyLocalVariableQuickFixToVBAFragment(string inputCode, string userEnteredName = "")
{
var vbe = BuildMockVBEStandardModuleForVBAFragment(inputCode);
var inspectionResults = GetInspectionResults(vbe, userEnteredName);

var mockDialogFactory = BuildMockDialogFactory(userEnteredName);

var inspectionResults = GetInspectionResults(vbe.Object, mockDialogFactory.Object);
inspectionResults.First().QuickFixes.Single(s => s is AssignedByValParameterMakeLocalCopyQuickFix).Fix();

return GetModuleContent(vbe);
return GetModuleContent(vbe.Object);
}

private Mock<IVBE> BuildMockVBEStandardModuleForVBAFragment(string inputCode)
Expand All @@ -468,19 +475,38 @@ private Mock<IVBE> BuildMockVBEStandardModuleForVBAFragment(string inputCode)
IVBComponent component;
return builder.BuildFromSingleStandardModule(inputCode, out component);
}
private IEnumerable<Rubberduck.Inspections.Abstract.InspectionResultBase> GetInspectionResults(Mock<IVBE> vbe, string userEnteredName)

private IEnumerable<Rubberduck.Inspections.Abstract.InspectionResultBase> GetInspectionResults(IVBE vbe, IAssignedByValParameterQuickFixDialogFactory mockDialogFactory)
{
var parser = MockParser.Create(vbe.Object, new RubberduckParserState(vbe.Object));
var parser = MockParser.Create(vbe, new RubberduckParserState(vbe));
parser.Parse(new CancellationTokenSource());
if (parser.State.Status >= ParserState.Error) { Assert.Inconclusive("Parser Error"); }

var inspection = new AssignedByValParameterInspection(parser.State,new AssignedByValParameterQuickFixMockDialogFactory(userEnteredName));
var inspection = new AssignedByValParameterInspection(parser.State, mockDialogFactory);
return inspection.GetInspectionResults();
}

private string GetModuleContent(Mock<IVBE> vbe)
private Mock<IAssignedByValParameterQuickFixDialogFactory> BuildMockDialogFactory(string userEnteredName)
{
var mockDialog = new Mock<IAssignedByValParameterQuickFixDialog>();

mockDialog.SetupAllProperties();

if (userEnteredName.Length > 0)
{
mockDialog.SetupGet(m => m.NewName).Returns(() => userEnteredName);
}
mockDialog.SetupGet(m => m.DialogResult).Returns(() => DialogResult.OK);

var mockDialogFactory = new Mock<IAssignedByValParameterQuickFixDialogFactory>();
mockDialogFactory.Setup(f => f.Create(It.IsAny<string>(), It.IsAny<string>())).Returns(mockDialog.Object);

return mockDialogFactory;
}

private string GetModuleContent(IVBE vbe)
{
var project = vbe.Object.VBProjects[0];
var project = vbe.VBProjects[0];
var module = project.VBComponents[0].CodeModule;
return module.Content();
}
Expand Down
Expand Up @@ -162,44 +162,27 @@ End Sub
quickFixResult = ApplyPassParameterByReferenceQuickFixToVBAFragment(inputCode);
Assert.AreEqual(expectedCode, quickFixResult);
}
[TestMethod]
[TestCategory("Inspections")]
public void InspectionType()
{
var inspection = new AssignedByValParameterInspection(null,null);
Assert.AreEqual(CodeInspectionType.CodeQualityIssues, inspection.InspectionType);
}

[TestMethod]
[TestCategory("Inspections")]
public void InspectionName()
{
const string inspectionName = "AssignedByValParameterInspection";
var inspection = new AssignedByValParameterInspection(null,null);

Assert.AreEqual(inspectionName, inspection.Name);
}

private string ApplyPassParameterByReferenceQuickFixToVBAFragment(string inputCode)
{
var vbe = BuildMockVBEStandardModuleForVBAFragment(inputCode);
var inspectionResults = GetInspectionResults(vbe);
var inspectionResults = GetAssignedByValParameterInspectionResults(vbe.Object);

inspectionResults.First().QuickFixes.Single(s => s is PassParameterByReferenceQuickFix).Fix();

return GetModuleContent(vbe);
return GetModuleContent(vbe.Object);
}

private string GetModuleContent(Mock<IVBE> vbe)
private string GetModuleContent(IVBE vbe)
{
var project = vbe.Object.VBProjects[0];
var project = vbe.VBProjects[0];
var module = project.VBComponents[0].CodeModule;
return module.Content();
}

private IEnumerable<Rubberduck.Inspections.Abstract.InspectionResultBase> GetInspectionResults(Mock<IVBE> vbe)
private IEnumerable<Rubberduck.Inspections.Abstract.InspectionResultBase> GetAssignedByValParameterInspectionResults(IVBE vbe)
{
var parser = MockParser.Create(vbe.Object, new RubberduckParserState(vbe.Object));
var parser = MockParser.Create(vbe, new RubberduckParserState(vbe));
parser.Parse(new CancellationTokenSource());
if (parser.State.Status >= ParserState.Error) { Assert.Inconclusive("Parser Error"); }

Expand Down

0 comments on commit 8e4a56b

Please sign in to comment.