Skip to content

Commit 5d5a355

Browse files
authored
Merge pull request #4199 from comintern/next
Pick some low hanging fruit in open issues.
2 parents e5e7728 + c7cecf6 commit 5d5a355

19 files changed

+69
-24
lines changed

Rubberduck.CodeAnalysis/Inspections/Concrete/IllegalAnnotationInspection.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -167,7 +167,7 @@ public override void EnterPropertySetStmt(VBAParser.PropertySetStmtContext conte
167167
public override void ExitAnnotation(VBAParser.AnnotationContext context)
168168
{
169169
var name = Identifier.GetName(context.annotationName().unrestrictedIdentifier());
170-
var annotationType = (AnnotationType) Enum.Parse(typeof (AnnotationType), name);
170+
var annotationType = (AnnotationType) Enum.Parse(typeof (AnnotationType), name, true);
171171
var key = Tuple.Create(_currentModuleName, annotationType);
172172
_annotationCounts[key]++;
173173

Rubberduck.CodeAnalysis/Inspections/Concrete/VariableTypeNotDeclaredInspection.cs

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -17,7 +17,6 @@ public VariableTypeNotDeclaredInspection(RubberduckParserState state)
1717
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
1818
{
1919
var issues = from item in State.DeclarationFinder.UserDeclarations(DeclarationType.Variable)
20-
.Union(State.DeclarationFinder.UserDeclarations(DeclarationType.Constant))
2120
.Union(State.DeclarationFinder.UserDeclarations(DeclarationType.Parameter))
2221
where (item.DeclarationType != DeclarationType.Parameter || (item.DeclarationType == DeclarationType.Parameter && !item.IsArray))
2322
&& item.DeclarationType != DeclarationType.Control

Rubberduck.VBEditor.VBA/SourceCodeHandler.cs

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -10,6 +10,10 @@ public class SourceCodeHandler : ISourceCodeHandler
1010
{
1111
public string Export(IVBComponent component)
1212
{
13+
if (!Directory.Exists(ApplicationConstants.RUBBERDUCK_TEMP_PATH))
14+
{
15+
Directory.CreateDirectory(ApplicationConstants.RUBBERDUCK_TEMP_PATH);
16+
}
1317
var fileName = component.ExportAsSourceFile(ApplicationConstants.RUBBERDUCK_TEMP_PATH);
1418

1519
return File.Exists(fileName)

RubberduckTests/Inspections/IllegalAnnotationsInspectionTests.cs

Lines changed: 22 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -301,5 +301,27 @@ public void InspectionName()
301301

302302
Assert.AreEqual(inspectionName, inspection.Name);
303303
}
304+
305+
[Test]
306+
[Category("Inspections")]
307+
public void AnnotationIsCaseInsensitive()
308+
{
309+
const string inputCode =
310+
@"'@folder ""Foo""
311+
Public Sub Foo()
312+
Const const1 As Integer = 9
313+
End Sub";
314+
315+
var vbe = MockVbeBuilder.BuildFromSingleStandardModule(inputCode, out _);
316+
using (var state = MockParser.CreateAndParse(vbe.Object))
317+
{
318+
319+
var inspection = new IllegalAnnotationInspection(state);
320+
var inspector = InspectionsHelper.GetInspector(inspection);
321+
var inspectionResults = inspector.FindIssuesAsync(state, CancellationToken.None).Result;
322+
323+
Assert.IsFalse(inspectionResults.Any());
324+
}
325+
}
304326
}
305327
}

RubberduckTests/Inspections/VariableTypeNotDeclaredInspectionTests.cs

Lines changed: 19 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -178,6 +178,25 @@ Sub Foo(arg1)
178178
}
179179
}
180180

181+
[Test]
182+
[Category("Inspections")]
183+
public void VariableTypeNotDeclared_Const_DoesNotReturnResult()
184+
{
185+
const string inputCode =
186+
@"Sub Foo()
187+
Const bar = 42
188+
End Sub";
189+
var vbe = MockVbeBuilder.BuildFromSingleStandardModule(inputCode, out _);
190+
using (var state = MockParser.CreateAndParse(vbe.Object))
191+
{
192+
193+
var inspection = new VariableTypeNotDeclaredInspection(state);
194+
var inspectionResults = inspection.GetInspectionResults(CancellationToken.None);
195+
196+
Assert.IsFalse(inspectionResults.Any());
197+
}
198+
}
199+
181200
[Test]
182201
[Category("Inspections")]
183202
public void InspectionName()

RubberduckTests/Mocks/MockVbeBuilder.cs

Lines changed: 10 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -20,20 +20,20 @@ public class MockVbeBuilder
2020
private readonly Mock<IVBEEvents> _vbeEvents;
2121

2222
#region standard library paths (referenced in all VBA projects hosted in Microsoft Excel)
23-
public static readonly string LibraryPathVBA = @"C:\PROGRA~2\COMMON~1\MICROS~1\VBA\VBA7.1\VBE7.DLL"; // standard library, priority locked
24-
public static readonly string LibraryPathMsExcel = @"C:\Program Files (x86)\Microsoft Office\Office15\EXCEL.EXE"; // mock host application, priority locked
25-
public static readonly string LibraryPathMsOffice = @"C:\Program Files (x86)\Common Files\Microsoft Shared\OFFICE15\MSO.DLL";
26-
public static readonly string LibraryPathStdOle = @"C:\Windows\SysWOW64\stdole2.tlb";
27-
public static readonly string LibraryPathMsForms = @"C:\Windows\SysWOW64\FM20.DLL"; // standard in projects with a UserForm module
23+
public static readonly string LibraryPathVBA = @"C:\PROGRA~1\COMMON~1\MICROS~1\VBA\VBA7.1\VBE7.DLL"; // standard library, priority locked
24+
public static readonly string LibraryPathMsExcel = @"C:\Program Files\Microsoft Office\Office15\EXCEL.EXE"; // mock host application, priority locked
25+
public static readonly string LibraryPathMsOffice = @"C:\Program Files\Common Files\Microsoft Shared\OFFICE15\MSO.DLL";
26+
public static readonly string LibraryPathStdOle = @"C:\Windows\System32\stdole2.tlb";
27+
public static readonly string LibraryPathMsForms = @"C:\Windows\system32\FM20.DLL"; // standard in projects with a UserForm module
2828
#endregion
2929

3030
public static readonly string LibraryPathVBIDE = @"C:\Program Files (x86)\Common Files\Microsoft Shared\VBA\VBA6\VBE6EXT.OLB";
31-
public static readonly string LibraryPathScripting = @"C:\Windows\SysWOW64\scrrun.dll";
32-
public static readonly string LibraryPathRegex = @"C:\Windows\SysWOW64\vbscript.dll\3";
31+
public static readonly string LibraryPathScripting = @"C:\Windows\System32\scrrun.dll";
32+
public static readonly string LibraryPathRegex = @"C:\Windows\System32\vbscript.dll\3";
3333
public static readonly string LibraryPathMsXml = @"C:\Windows\System32\msxml6.dll";
34-
public static readonly string LibraryPathShDoc = @"C:\Windows\SysWOW64\ieframe.dll";
35-
public static readonly string LibraryPathAdoDb = @"C:\Program Files (x86)\Common Files\System\ado\msado15.dll";
36-
public static readonly string LibraryPathAdoRecordset = @"C:\Program Files (x86)\Common Files\System\ado\msador15.dll";
34+
public static readonly string LibraryPathShDoc = @"C:\Windows\System32\ieframe.dll";
35+
public static readonly string LibraryPathAdoDb = @"C:\Program Files\Common Files\System\ado\msado15.dll";
36+
public static readonly string LibraryPathAdoRecordset = @"C:\Program Files\Common Files\System\ado\msador15.dll";
3737

3838
//private Mock<IWindows> _vbWindows;
3939
private readonly Windows _windows = new Windows();

RubberduckTests/Symbols/DeclarationFinderTests.cs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1213,6 +1213,7 @@ Dim Item As String
12131213

12141214
[Category("Resolver")]
12151215
[Test]
1216+
[Ignore("Temporarily ignored, the mock or serialization appears to be broken (works in release as of 7/16/2018); see issue #4191 for background")]
12161217
public void Identify_NamedParameter_Parameter_FromExcel()
12171218
{
12181219
const string code = @"

RubberduckTests/Testfiles/Resolver/ADODB.6.1.xml

Lines changed: 1 addition & 1 deletion
Large diffs are not rendered by default.

RubberduckTests/Testfiles/Resolver/ADOR.6.0.xml

Lines changed: 1 addition & 1 deletion
Large diffs are not rendered by default.

RubberduckTests/Testfiles/Resolver/Excel.1.8.xml

Lines changed: 1 addition & 1 deletion
Large diffs are not rendered by default.

0 commit comments

Comments
 (0)