Skip to content

Commit 9047b3b

Browse files
committed
Added DeclarationFinder test class. Moved tests from AssignedByValParameter..QuickFixTests and RenameTests to new test class.
1 parent 2c274f2 commit 9047b3b

File tree

6 files changed

+334
-423
lines changed

6 files changed

+334
-423
lines changed

RetailCoder.VBE/Inspections/QuickFixes/AssignedByValParameterMakeLocalCopyQuickFix.cs

Lines changed: 3 additions & 58 deletions
Original file line numberDiff line numberDiff line change
@@ -27,8 +27,9 @@ public AssignedByValParameterMakeLocalCopyQuickFix(Declaration target, Qualified
2727
_target = target;
2828
_dialogFactory = dialogFactory;
2929
_parserState = parserState;
30-
_forbiddenNames = GetIdentifierNamesAccessibleToProcedureContext();
31-
_localCopyVariableName = ComputeSuggestedName();
30+
_forbiddenNames = parserState.DeclarationFinder.GetDeclarationsAccessibleToScope(target, parserState.AllUserDeclarations).Select(n => n.IdentifierName);
31+
//_forbiddenNames = GetIdentifierNamesAccessibleToProcedureContext();
32+
_localCopyVariableName = ComputeSuggestedName();
3233
}
3334

3435
public override bool CanFixInModule { get { return false; } }
@@ -113,61 +114,5 @@ private string BuildLocalCopyAssignment()
113114
return (_target.AsTypeDeclaration is ClassModuleDeclaration ? Tokens.Set + " " : string.Empty)
114115
+ _localCopyVariableName + " = " + _target.IdentifierName;
115116
}
116-
117-
private IEnumerable<string> GetIdentifierNamesAccessibleToProcedureContext()
118-
{
119-
return _parserState.AllUserDeclarations
120-
.Where(candidateDeclaration =>
121-
(
122-
IsDeclarationInTheSameProcedure(candidateDeclaration, _target)
123-
|| IsDeclarationInTheSameModule(candidateDeclaration, _target)
124-
|| IsProjectGlobalDeclaration(candidateDeclaration, _target))
125-
).Select(declaration => declaration.IdentifierName).Distinct();
126-
}
127-
128-
private bool IsDeclarationInTheSameProcedure(Declaration candidateDeclaration, Declaration scopingDeclaration)
129-
{
130-
return candidateDeclaration.ParentScope == scopingDeclaration.ParentScope;
131-
}
132-
133-
private bool IsDeclarationInTheSameModule(Declaration candidateDeclaration, Declaration scopingDeclaration)
134-
{
135-
return candidateDeclaration.ComponentName == scopingDeclaration.ComponentName
136-
&& !IsDeclaredInMethodOrProperty(candidateDeclaration.ParentDeclaration.Context);
137-
}
138-
139-
private bool IsProjectGlobalDeclaration(Declaration candidateDeclaration, Declaration scopingDeclaration)
140-
{
141-
return candidateDeclaration.ProjectName == scopingDeclaration.ProjectName
142-
&& !(candidateDeclaration.ParentScopeDeclaration is ClassModuleDeclaration)
143-
&& (candidateDeclaration.Accessibility == Accessibility.Public
144-
|| ((candidateDeclaration.Accessibility == Accessibility.Implicit)
145-
&& (candidateDeclaration.ParentScopeDeclaration is ProceduralModuleDeclaration)));
146-
}
147-
148-
private bool IsDeclaredInMethodOrProperty(RuleContext procedureContext)
149-
{
150-
if (procedureContext is VBAParser.SubStmtContext)
151-
{
152-
return true;
153-
}
154-
else if (procedureContext is VBAParser.FunctionStmtContext)
155-
{
156-
return true;
157-
}
158-
else if (procedureContext is VBAParser.PropertyLetStmtContext)
159-
{
160-
return true;
161-
}
162-
else if (procedureContext is VBAParser.PropertyGetStmtContext)
163-
{
164-
return true;
165-
}
166-
else if (procedureContext is VBAParser.PropertySetStmtContext)
167-
{
168-
return true;
169-
}
170-
return false;
171-
}
172117
}
173118
}

Rubberduck.Parsing/Symbols/DeclarationFinder.cs

Lines changed: 17 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -751,11 +751,10 @@ private ConcurrentBag<Declaration> FindEventHandlers(IEnumerable<Declaration> de
751751
public IEnumerable<Declaration> GetDeclarationsAccessibleToScope(Declaration target, IEnumerable<Declaration> declarations)
752752
{
753753
if (target == null) { return Enumerable.Empty<Declaration>(); }
754-
755754
return declarations
756755
.Where(candidateDeclaration =>
757756
(
758-
IsDeclarationInTheSameProcedure(candidateDeclaration, target)
757+
IsDeclarationInTheSameProcedure(candidateDeclaration, target)
759758
|| IsDeclarationChildOfTheScope(candidateDeclaration, target)
760759
|| IsModuleLevelDeclarationOfTheScope(candidateDeclaration, target)
761760
|| IsProjectGlobalDeclaration(candidateDeclaration, target)
@@ -786,9 +785,22 @@ private bool IsProjectGlobalDeclaration(Declaration candidateDeclaration, Declar
786785
{
787786
return candidateDeclaration.ProjectName == scopingDeclaration.ProjectName
788787
&& !(candidateDeclaration.ParentScopeDeclaration is ClassModuleDeclaration)
789-
&& (candidateDeclaration.Accessibility == Accessibility.Public
790-
|| ((candidateDeclaration.Accessibility == Accessibility.Implicit)
791-
&& (candidateDeclaration.ParentScopeDeclaration is ProceduralModuleDeclaration)));
788+
&& (IsExplicitPublicInOtherModule(candidateDeclaration, scopingDeclaration)
789+
|| IsImplicitPublicInOtherModule(candidateDeclaration, scopingDeclaration));
790+
}
791+
792+
private bool IsExplicitPublicInOtherModule(Declaration candidateDeclaration, Declaration scopingDeclaration)
793+
{
794+
return candidateDeclaration.ComponentName != scopingDeclaration.ComponentName
795+
&& candidateDeclaration.Accessibility == Accessibility.Public;
796+
}
797+
798+
private bool IsImplicitPublicInOtherModule(Declaration candidateDeclaration, Declaration scopingDeclaration)
799+
{
800+
return candidateDeclaration.ComponentName != scopingDeclaration.ComponentName
801+
&& candidateDeclaration.Accessibility == Accessibility.Implicit
802+
&& (candidateDeclaration.ParentScopeDeclaration is ProceduralModuleDeclaration)
803+
&& !candidateDeclaration.IdentifierName.StartsWith("Option ");
792804
}
793805

794806
private bool IsDeclaredWithinMethodOrProperty(RuleContext procedureContextCandidate)

RubberduckTests/Inspections/AssignedByValParameterMakeLocalCopyQuickFixTests.cs

Lines changed: 0 additions & 246 deletions
Original file line numberDiff line numberDiff line change
@@ -10,7 +10,6 @@
1010
using System.Threading;
1111
using Rubberduck.UI.Refactorings;
1212
using System.Windows.Forms;
13-
using Rubberduck.VBEditor.SafeComWrappers;
1413

1514
namespace RubberduckTests.Inspections
1615
{
@@ -172,74 +171,6 @@ End Function
172171

173172
}
174173

175-
[TestMethod]
176-
[TestCategory("Inspections")]
177-
public void AssignedByValParameter_LocalVariableAssignment_RespectsAccessibleDeclarations_InProcedure()
178-
{
179-
string[] accessibleWithinParentProcedure = { "localVar" };
180-
RespectsDeclarationAccessibilityRules(accessibleWithinParentProcedure, "Procedure Scope", true, false);
181-
}
182-
183-
[TestMethod]
184-
[TestCategory("Inspections")]
185-
public void AssignedByValParameter_LocalVariableAssignment_RespectsAccessibleDeclarations_ModuleScope()
186-
{
187-
string[] accessibleModuleScope = { "memberString", "KungFooFighting", "FooFight" };
188-
RespectsDeclarationAccessibilityRules(accessibleModuleScope, "ModuleScope", true, false);
189-
}
190-
191-
[TestMethod]
192-
[TestCategory("Inspections")]
193-
public void AssignedByValParameter_LocalVariableAssignment_RespectsAccessibleDeclarations_GlobalScope()
194-
{
195-
string[] accessibleGlobalScope = { "CantTouchThis", "BigNumber", "DoSomething", "SetFilename" };
196-
RespectsDeclarationAccessibilityRules(accessibleGlobalScope, "GlobalScope", true, true);
197-
}
198-
199-
[TestMethod]
200-
[TestCategory("Inspections")]
201-
public void AssignedByValParameter_LocalVariableAssignment_RespectsAccessibleDeclarations_PublicClassElements()
202-
{
203-
string[] allowsNamesThatArePublicDeclarationsWithinAnotherClassModule = { "mySecondEggo", "Bar" };
204-
RespectsDeclarationAccessibilityRules(allowsNamesThatArePublicDeclarationsWithinAnotherClassModule, "Different Class, Public Member", false, false);
205-
}
206-
207-
private void RespectsDeclarationAccessibilityRules(string[] namesToTest, string scope, bool expectedEqualsInput, bool includeModuleNames)
208-
{
209-
var firstClassBody = GetRespectsDeclarationsAccessibilityRules_FirstClassBody();
210-
var secondClassBody = GetRespectsDeclarationsAccessibilityRules_SecondClassBody();
211-
var firstModuleBody = GetRespectsDeclarationsAccessibilityRules_FirstModuleBody();
212-
var secondModuleBody = GetRespectsDeclarationsAccessibilityRules_SecondModuleBody();
213-
214-
var firstClass = new TestComponentSpecification("CFirstClass", firstClassBody, ComponentType.ClassModule);
215-
var secondClass = new TestComponentSpecification("CSecondClass", secondClassBody, ComponentType.ClassModule);
216-
var firstModule = new TestComponentSpecification("modFirst", firstModuleBody, ComponentType.StandardModule);
217-
var secondModule = new TestComponentSpecification("modSecond", secondModuleBody, ComponentType.StandardModule);
218-
219-
220-
var expectedCode = firstClass.Content;
221-
TestComponentSpecification[] testComponents = { firstClass, secondClass, firstModule, secondModule };
222-
var allTestNames = namesToTest.ToList();
223-
if (includeModuleNames)
224-
{
225-
allTestNames.AddRange(testComponents.Select(n => n.Name));
226-
}
227-
228-
var messagePreface = "Test failed for " + scope + " identifier: ";
229-
foreach (var nameToTest in allTestNames)
230-
{
231-
var quickFixResult = GetQuickFixResult(nameToTest, firstClass, testComponents);
232-
if (expectedEqualsInput)
233-
{
234-
Assert.AreEqual(expectedCode, quickFixResult, messagePreface + nameToTest);
235-
}
236-
else
237-
{
238-
Assert.AreNotEqual(expectedCode, quickFixResult, messagePreface + nameToTest);
239-
}
240-
}
241-
}
242-
243174
private string ApplyLocalVariableQuickFixToCodeFragment(string inputCode, string userEnteredName = "")
244175
{
245176
var vbe = BuildMockVBEStandardModuleForCodeFragment(inputCode);
@@ -300,182 +231,5 @@ private string GetModuleContent(IVBE vbe, string componentName = "")
300231
? project.VBComponents[componentName].CodeModule : project.VBComponents[0].CodeModule;
301232
return module.Content();
302233
}
303-
304-
internal class TestComponentSpecification
305-
{
306-
private string _name;
307-
private string _content;
308-
private ComponentType _componentType;
309-
public TestComponentSpecification(string componentName, string componentContent, ComponentType componentType)
310-
{
311-
_name = componentName;
312-
_content = componentContent;
313-
_componentType = componentType;
314-
}
315-
316-
public string Name { get { return _name; } }
317-
public string Content { get { return _content; } }
318-
public ComponentType ModuleType { get { return _componentType; } }
319-
}
320-
321-
private string GetQuickFixResult(string userEnteredNames, TestComponentSpecification resultsComponent, TestComponentSpecification[] testComponents)
322-
{
323-
var vbe = BuildProject("TestProject", testComponents.ToList());
324-
var parser = MockParser.Create(vbe.Object, new RubberduckParserState(vbe.Object));
325-
parser.Parse(new CancellationTokenSource());
326-
if (parser.State.Status >= ParserState.Error) { Assert.Inconclusive("Parser Error"); }
327-
328-
var mockDialogFactory = BuildMockDialogFactory(userEnteredNames);
329-
var inspection = new AssignedByValParameterInspection(parser.State, mockDialogFactory.Object);
330-
var inspectionResults = inspection.GetInspectionResults();
331-
332-
inspectionResults.First().QuickFixes.Single(s => s is AssignedByValParameterMakeLocalCopyQuickFix).Fix();
333-
334-
return GetModuleContent(vbe.Object, resultsComponent.Name);
335-
}
336-
337-
private Mock<IVBE> BuildProject(string projectName, List<TestComponentSpecification> testComponents)
338-
{
339-
var builder = new MockVbeBuilder();
340-
var enclosingProjectBuilder = builder.ProjectBuilder(projectName, ProjectProtection.Unprotected);
341-
342-
testComponents.ForEach(c => enclosingProjectBuilder.AddComponent(c.Name, c.ModuleType, c.Content));
343-
var enclosingProject = enclosingProjectBuilder.Build();
344-
builder.AddProject(enclosingProject);
345-
return builder.Build();
346-
}
347-
348-
private string GetNameAlreadyAccessibleWithinClass_FirstClassBody()
349-
{
350-
return
351-
@"
352-
Private memberString As String
353-
Private memberLong As Long
354-
355-
Private Sub Class_Initialize()
356-
memberLong = 6
357-
memberString = ""No Value""
358-
End Sub
359-
360-
Public Sub Foo(ByVal arg1 As String, theSecondArg As Long)
361-
Let arg1 = ""test""
362-
End Sub
363-
364-
Private Sub FooFight(ByRef arg1 As String)
365-
xArg1 = 6
366-
Let arg1 = ""test""
367-
End Sub
368-
";
369-
370-
}
371-
private string GetRespectsDeclarationsAccessibilityRules_FirstClassBody()
372-
{
373-
return
374-
@"
375-
Private memberString As String
376-
Private memberLong As Long
377-
Private myEggo as String
378-
379-
Public Sub Foo(ByVal arg1 As String)
380-
Dim localVar as Long
381-
localVar = 7
382-
Let arg1 = ""test""
383-
memberString = arg1 & ""Foo""
384-
End Sub
385-
386-
Public Function KungFooFighting(ByRef arg1 As String, theSecondArg As Long) As String
387-
Let arg1 = ""test""
388-
Dim result As String
389-
result = arg1 & theSecondArg
390-
KungFooFighting = result
391-
End Function
392-
393-
Property Let GoMyEggo(newValue As String)
394-
myEggo = newValue
395-
End Property
396-
397-
Property Get GoMyEggo()
398-
GoMyEggo = myEggo
399-
End Property
400-
401-
Private Sub FooFight(ByRef arg1 As String)
402-
xArg1 = 6
403-
Let arg1 = ""test""
404-
End Sub
405-
";
406-
}
407-
private string GetRespectsDeclarationsAccessibilityRules_SecondClassBody()
408-
{
409-
return
410-
@"
411-
Private memberString As String
412-
Private memberLong As Long
413-
Public mySecondEggo as String
414-
415-
416-
Public Sub Foo2( arg1 As String, theSecondArg As Long)
417-
Let arg1 = ""test""
418-
memberString = arg1 & ""Foo""
419-
End Sub
420-
421-
Public Function KungFooFighting(ByRef arg1 As String, theSecondArg As Long) As String
422-
Let arg1 = ""test""
423-
Dim result As String
424-
result = arg1 & theSecondArg
425-
KungFooFighting = result
426-
End Function
427-
428-
Property Let GoMyOtherEggo(newValue As String)
429-
mySecondEggo = newValue
430-
End Property
431-
432-
Property Get GoMyOtherEggo()
433-
GoMyOtherEggo = mySecondEggo
434-
End Property
435-
436-
Private Sub FooFighters(ByRef arg1 As String)
437-
xArg1 = 6
438-
Let arg1 = ""test""
439-
End Sub
440-
441-
Sub Bar()
442-
Dim st As String
443-
st = ""Test""
444-
Dim v As Long
445-
v = 5
446-
result = KungFooFighting(st, v)
447-
End Sub
448-
";
449-
}
450-
private string GetRespectsDeclarationsAccessibilityRules_FirstModuleBody()
451-
{
452-
return
453-
@"
454-
Option Explicit
455-
456-
457-
Public Const CantTouchThis As String = ""Can't Touch this""
458-
Public THE_FILENAME As String
459-
460-
Sub SetFilename(filename As String)
461-
THE_FILENAME = filename
462-
End Sub
463-
";
464-
}
465-
private string GetRespectsDeclarationsAccessibilityRules_SecondModuleBody()
466-
{
467-
return
468-
@"
469-
Option Explicit
470-
471-
472-
Public BigNumber as Long
473-
Public ShortStory As String
474-
475-
Public Sub DoSomething(filename As String)
476-
ShortStory = filename
477-
End Sub
478-
";
479-
}
480234
}
481235
}

0 commit comments

Comments
 (0)