Skip to content

Commit 23039cc

Browse files
authored
Merge pull request #4121 from MDoerner/FixingStuff
Fix for MoveCloserToUsage quickfix problem
2 parents b20482c + 9470515 commit 23039cc

File tree

7 files changed

+122
-19
lines changed

7 files changed

+122
-19
lines changed

Rubberduck.Parsing/ComReflection/ComProject.cs

Lines changed: 18 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -108,30 +108,37 @@ private void LoadModules(ITypeLib typeLibrary)
108108
{
109109
ITypeInfo info;
110110
typeLibrary.GetTypeInfo(index, out info);
111-
IntPtr typeAttributesPointer;
112-
info.GetTypeAttr(out typeAttributesPointer);
111+
info.GetTypeAttr(out var typeAttributesPointer);
113112
var typeAttributes = (TYPEATTR)Marshal.PtrToStructure(typeAttributesPointer, typeof(TYPEATTR));
114113

115-
ComType type;
116-
KnownTypes.TryGetValue(typeAttributes.guid, out type);
114+
KnownTypes.TryGetValue(typeAttributes.guid, out var type);
117115

118116
switch (typeAttributes.typekind)
119117
{
120118
case TYPEKIND.TKIND_ENUM:
121119
var enumeration = type ?? new ComEnumeration(typeLibrary, info, typeAttributes, index);
122120
_enumerations.Add(enumeration as ComEnumeration);
123-
if (type == null) KnownTypes.TryAdd(typeAttributes.guid, enumeration);
121+
if (type == null)
122+
{
123+
KnownTypes.TryAdd(typeAttributes.guid, enumeration);
124+
}
124125
break;
125126
case TYPEKIND.TKIND_COCLASS:
126127
var coclass = type ?? new ComCoClass(typeLibrary, info, typeAttributes, index);
127128
_classes.Add(coclass as ComCoClass);
128-
if (type == null) KnownTypes.TryAdd(typeAttributes.guid, coclass);
129+
if (type == null)
130+
{
131+
KnownTypes.TryAdd(typeAttributes.guid, coclass);
132+
}
129133
break;
130134
case TYPEKIND.TKIND_DISPATCH:
131135
case TYPEKIND.TKIND_INTERFACE:
132136
var intface = type ?? new ComInterface(typeLibrary, info, typeAttributes, index);
133137
_interfaces.Add(intface as ComInterface);
134-
if (type == null) KnownTypes.TryAdd(typeAttributes.guid, intface);
138+
if (type == null)
139+
{
140+
KnownTypes.TryAdd(typeAttributes.guid, intface);
141+
}
135142
break;
136143
case TYPEKIND.TKIND_RECORD:
137144
var structure = new ComStruct(typeLibrary, info, typeAttributes, index);
@@ -140,7 +147,10 @@ private void LoadModules(ITypeLib typeLibrary)
140147
case TYPEKIND.TKIND_MODULE:
141148
var module = type ?? new ComModule(typeLibrary, info, typeAttributes, index);
142149
_modules.Add(module as ComModule);
143-
if (type == null) KnownTypes.TryAdd(typeAttributes.guid, module);
150+
if (type == null)
151+
{
152+
KnownTypes.TryAdd(typeAttributes.guid, module);
153+
}
144154
break;
145155
case TYPEKIND.TKIND_ALIAS:
146156
var alias = new ComAlias(typeLibrary, info, index, typeAttributes);

Rubberduck.Parsing/Grammar/VBAParser.g4

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -410,7 +410,7 @@ listOrLabel :
410410
lineNumberLabel (whiteSpace? COLON whiteSpace? sameLineStatement?)*
411411
| (COLON whiteSpace?)? sameLineStatement (whiteSpace? COLON whiteSpace? sameLineStatement?)*
412412
;
413-
sameLineStatement : blockStmt;
413+
sameLineStatement : mainBlockStmt;
414414
booleanExpression : expression;
415415

416416
implementsStmt : IMPLEMENTS whiteSpace expression;

Rubberduck.Parsing/VBA/ParseCoordinator.cs

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -352,6 +352,9 @@ private void ParseAllInternal(object requestor, CancellationToken token)
352352
toParse.UnionWith(modules.Where(module => _parserStateManager.GetModuleState(module) != ParserState.Ready));
353353
token.ThrowIfCancellationRequested();
354354

355+
toParse = toParse.Where(module => module.IsParsable).ToHashSet();
356+
token.ThrowIfCancellationRequested();
357+
355358
var removedModules = RemovedModules(modules);
356359
token.ThrowIfCancellationRequested();
357360

Rubberduck.Parsing/VBA/ParseRunner.cs

Lines changed: 1 addition & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -42,13 +42,7 @@ public override void ParseModules(IReadOnlyCollection<QualifiedModuleName> modul
4242
{
4343
Parallel.ForEach(modules,
4444
options,
45-
module =>
46-
{
47-
if (module.IsParsable)
48-
{
49-
ParseModule(module, token);
50-
}
51-
}
45+
module => ParseModule(module, token)
5246
);
5347
}
5448
catch (AggregateException exception)

Rubberduck.Parsing/VBA/ParseRunnerBase.cs

Lines changed: 0 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -5,8 +5,6 @@
55
using System.Threading;
66
using Rubberduck.Parsing.PreProcessing;
77
using Antlr4.Runtime;
8-
using Rubberduck.Parsing.Inspections.Abstract;
9-
using Rubberduck.Parsing.Symbols;
108
using Rubberduck.Parsing.Symbols.ParsingExceptions;
119

1210
namespace Rubberduck.Parsing.VBA

Rubberduck.Parsing/VBA/ReferenceResolveRunnerBase.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -63,7 +63,7 @@ public void ResolveReferences(IReadOnlyCollection<QualifiedModuleName> toResolve
6363
{
6464
token.ThrowIfCancellationRequested();
6565

66-
_toResolve.UnionWith(toResolve.Where(qmn => qmn.IsParsable));
66+
_toResolve.UnionWith(toResolve);
6767
token.ThrowIfCancellationRequested();
6868

6969
if(!_toResolve.Any())

RubberduckTests/QuickFixes/MoveFieldCloserToUsageQuickFixTests.cs

Lines changed: 98 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -39,5 +39,103 @@ Dim bar As String
3939
Assert.AreEqual(expectedCode, component.CodeModule.Content());
4040
}
4141
}
42+
43+
[Test]
44+
[Category("QuickFixes")]
45+
public void MoveFieldCloserToUsage_QuickFixWorks_SingleLineIfStatemente()
46+
{
47+
const string inputCode =
48+
@"Private bar As String
49+
50+
Public Sub Foo()
51+
If bar = ""test"" Then Baz Else Foobar
52+
End Sub
53+
54+
Private Sub Baz()
55+
End Sub
56+
57+
Private Sub FooBar()
58+
End Sub
59+
";
60+
61+
const string expectedCode =
62+
@"Public Sub Foo()
63+
Dim bar As String
64+
If bar = ""test"" Then Baz Else Foobar
65+
End Sub
66+
67+
Private Sub Baz()
68+
End Sub
69+
70+
Private Sub FooBar()
71+
End Sub
72+
";
73+
74+
var vbe = MockVbeBuilder.BuildFromSingleStandardModule(inputCode, out var component);
75+
using (var state = MockParser.CreateAndParse(vbe.Object))
76+
{
77+
var inspection = new MoveFieldCloserToUsageInspection(state);
78+
var inspectionResults = inspection.GetInspectionResults(CancellationToken.None);
79+
80+
new MoveFieldCloserToUsageQuickFix(vbe.Object, state, new Mock<IMessageBox>().Object).Fix(inspectionResults.First());
81+
Assert.AreEqual(expectedCode, component.CodeModule.Content());
82+
}
83+
}
84+
85+
[Test]
86+
[Category("QuickFixes")]
87+
public void MoveFieldCloserToUsage_QuickFixWorks_SingleLineThenStatemente()
88+
{
89+
const string inputCode =
90+
@"Private bar As String
91+
92+
Public Sub Foo()
93+
If True Then bar = ""test""
94+
End Sub";
95+
96+
const string expectedCode =
97+
@"Public Sub Foo()
98+
Dim bar As String
99+
If True Then bar = ""test""
100+
End Sub";
101+
102+
var vbe = MockVbeBuilder.BuildFromSingleStandardModule(inputCode, out var component);
103+
using (var state = MockParser.CreateAndParse(vbe.Object))
104+
{
105+
var inspection = new MoveFieldCloserToUsageInspection(state);
106+
var inspectionResults = inspection.GetInspectionResults(CancellationToken.None);
107+
108+
new MoveFieldCloserToUsageQuickFix(vbe.Object, state, new Mock<IMessageBox>().Object).Fix(inspectionResults.First());
109+
Assert.AreEqual(expectedCode, component.CodeModule.Content());
110+
}
111+
}
112+
113+
[Test]
114+
[Category("QuickFixes")]
115+
public void MoveFieldCloserToUsage_QuickFixWorks_SingleLineElseStatemente()
116+
{
117+
const string inputCode =
118+
@"Private bar As String
119+
120+
Public Sub Foo()
121+
If True Then Else bar = ""test""
122+
End Sub";
123+
124+
const string expectedCode =
125+
@"Public Sub Foo()
126+
Dim bar As String
127+
If True Then Else bar = ""test""
128+
End Sub";
129+
130+
var vbe = MockVbeBuilder.BuildFromSingleStandardModule(inputCode, out var component);
131+
using (var state = MockParser.CreateAndParse(vbe.Object))
132+
{
133+
var inspection = new MoveFieldCloserToUsageInspection(state);
134+
var inspectionResults = inspection.GetInspectionResults(CancellationToken.None);
135+
136+
new MoveFieldCloserToUsageQuickFix(vbe.Object, state, new Mock<IMessageBox>().Object).Fix(inspectionResults.First());
137+
Assert.AreEqual(expectedCode, component.CodeModule.Content());
138+
}
139+
}
42140
}
43141
}

0 commit comments

Comments
 (0)