Skip to content

Commit 89dc500

Browse files
authored
Merge pull request #2490 from retailcoder/next
2.0.11
2 parents 7ca9028 + 09957af commit 89dc500

File tree

12 files changed

+44
-60
lines changed

12 files changed

+44
-60
lines changed

RetailCoder.VBE/API/ParserState.cs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -49,7 +49,7 @@ public sealed class ParserState : IParserState, IDisposable
4949

5050
private RubberduckParserState _state;
5151
private AttributeParser _attributeParser;
52-
private RubberduckParser _parser;
52+
private ParseCoordinator _parser;
5353
private VBE _vbe;
5454

5555
public ParserState()
@@ -70,7 +70,7 @@ public void Initialize(VBE vbe)
7070

7171
Func<IVBAPreprocessor> preprocessorFactory = () => new VBAPreprocessor(double.Parse(vbe.Version, CultureInfo.InvariantCulture));
7272
_attributeParser = new AttributeParser(new ModuleExporter(), preprocessorFactory);
73-
_parser = new RubberduckParser(vbe, _state, _attributeParser, preprocessorFactory,
73+
_parser = new ParseCoordinator(vbe, _state, _attributeParser, preprocessorFactory,
7474
new List<ICustomDeclarationLoader> { new DebugDeclarations(_state), new SpecialFormDeclarations(_state), new FormEventDeclarations(_state), new AliasDeclarations(_state) });
7575
}
7676

RetailCoder.VBE/App.cs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -23,7 +23,7 @@ public sealed class App : IDisposable
2323
{
2424
private readonly IVBE _vbe;
2525
private readonly IMessageBox _messageBox;
26-
private readonly IRubberduckParser _parser;
26+
private readonly IParseCoordinator _parser;
2727
private readonly AutoSave.AutoSave _autoSave;
2828
private readonly IGeneralConfigService _configService;
2929
private readonly IAppMenu _appMenus;
@@ -36,7 +36,7 @@ public sealed class App : IDisposable
3636

3737
public App(IVBE vbe,
3838
IMessageBox messageBox,
39-
IRubberduckParser parser,
39+
IParseCoordinator parser,
4040
IGeneralConfigService configService,
4141
IAppMenu appMenus,
4242
RubberduckCommandBar stateBar,

RetailCoder.VBE/Inspections/ImplicitActiveSheetReferenceInspection.cs

Lines changed: 6 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -4,20 +4,14 @@
44
using Rubberduck.Inspections.Resources;
55
using Rubberduck.Inspections.Results;
66
using Rubberduck.Parsing.VBA;
7-
using Rubberduck.VBEditor.Application;
8-
using Rubberduck.VBEditor.Extensions;
9-
using Rubberduck.VBEditor.SafeComWrappers.Abstract;
107

118
namespace Rubberduck.Inspections
129
{
1310
public sealed class ImplicitActiveSheetReferenceInspection : InspectionBase
1411
{
15-
private readonly IHostApplication _hostApp;
16-
17-
public ImplicitActiveSheetReferenceInspection(IVBE vbe, RubberduckParserState state)
12+
public ImplicitActiveSheetReferenceInspection(RubberduckParserState state)
1813
: base(state)
1914
{
20-
_hostApp = vbe.HostApplication();
2115
}
2216

2317
public override string Meta { get { return InspectionsUI.ImplicitActiveSheetReferenceInspectionMeta; } }
@@ -31,22 +25,18 @@ public ImplicitActiveSheetReferenceInspection(IVBE vbe, RubberduckParserState st
3125

3226
public override IEnumerable<InspectionResultBase> GetInspectionResults()
3327
{
34-
if (_hostApp == null || _hostApp.ApplicationName != "Excel")
35-
{
36-
return Enumerable.Empty<InspectionResultBase>();
37-
// if host isn't Excel, the ExcelObjectModel declarations shouldn't be loaded anyway.
38-
}
39-
4028
var matches = BuiltInDeclarations.Where(item =>
29+
item.ProjectName == "Excel" &&
4130
Targets.Contains(item.IdentifierName) &&
42-
item.ParentScope == "EXCEL.EXE;Excel._Global" &&
31+
item.ParentDeclaration.ComponentName == "_Global" &&
4332
item.AsTypeName == "Range").ToList();
4433

4534
var issues = matches.Where(item => item.References.Any())
4635
.SelectMany(declaration => declaration.References.Distinct());
4736

48-
return issues.Select(issue =>
49-
new ImplicitActiveSheetReferenceInspectionResult(this, issue));
37+
return issues
38+
.Where(issue => !issue.IsInspectionDisabled(AnnotationName))
39+
.Select(issue => new ImplicitActiveSheetReferenceInspectionResult(this, issue));
5040
}
5141
}
5242
}

RetailCoder.VBE/Inspections/ImplicitActiveWorkbookReferenceInspection.cs

Lines changed: 6 additions & 18 deletions
Original file line numberDiff line numberDiff line change
@@ -4,20 +4,14 @@
44
using Rubberduck.Inspections.Resources;
55
using Rubberduck.Inspections.Results;
66
using Rubberduck.Parsing.VBA;
7-
using Rubberduck.VBEditor.Application;
8-
using Rubberduck.VBEditor.Extensions;
9-
using Rubberduck.VBEditor.SafeComWrappers.Abstract;
107

118
namespace Rubberduck.Inspections
129
{
1310
public sealed class ImplicitActiveWorkbookReferenceInspection : InspectionBase
1411
{
15-
private readonly IHostApplication _hostApp;
16-
17-
public ImplicitActiveWorkbookReferenceInspection(IVBE vbe, RubberduckParserState state)
12+
public ImplicitActiveWorkbookReferenceInspection(RubberduckParserState state)
1813
: base(state)
1914
{
20-
_hostApp = vbe.HostApplication();
2115
}
2216

2317
public override string Meta { get { return InspectionsUI.ImplicitActiveWorkbookReferenceInspectionMeta; } }
@@ -31,22 +25,16 @@ public ImplicitActiveWorkbookReferenceInspection(IVBE vbe, RubberduckParserState
3125

3226
private static readonly string[] ParentScopes =
3327
{
34-
"EXCEL.EXE;Excel._Global",
35-
"EXCEL.EXE;Excel._Application",
36-
"EXCEL.EXE;Excel.Sheets",
37-
//"EXCEL.EXE;Excel.Worksheets",
28+
"_Global",
29+
"_Application",
30+
"Sheets",
31+
//"Worksheets",
3832
};
3933

4034
public override IEnumerable<InspectionResultBase> GetInspectionResults()
4135
{
42-
if (_hostApp == null || _hostApp.ApplicationName != "Excel")
43-
{
44-
return Enumerable.Empty<InspectionResultBase>();
45-
// if host isn't Excel, the ExcelObjectModel declarations shouldn't be loaded anyway.
46-
}
47-
4836
var issues = BuiltInDeclarations
49-
.Where(item => ParentScopes.Contains(item.ParentScope)
37+
.Where(item => item.ProjectName == "Excel" && ParentScopes.Contains(item.ComponentName)
5038
&& item.References.Any(r => Targets.Contains(r.IdentifierName)))
5139
.SelectMany(declaration => declaration.References.Distinct())
5240
.Where(item => Targets.Contains(item.IdentifierName))

RetailCoder.VBE/Navigation/RegexSearchReplace/RegexSearchReplace.cs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -14,9 +14,9 @@ namespace Rubberduck.Navigation.RegexSearchReplace
1414
public class RegexSearchReplace : IRegexSearchReplace
1515
{
1616
private readonly IVBE _vbe;
17-
private readonly IRubberduckParser _parser;
17+
private readonly IParseCoordinator _parser;
1818

19-
public RegexSearchReplace(IVBE vbe, IRubberduckParser parser)
19+
public RegexSearchReplace(IVBE vbe, IParseCoordinator parser)
2020
{
2121
_vbe = vbe;
2222
_parser = parser;

RetailCoder.VBE/Properties/AssemblyInfo.cs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -31,5 +31,5 @@
3131
// You can specify all the values or you can default the Build and Revision Numbers
3232
// by using the '*' as shown below:
3333
// [assembly: AssemblyVersion("1.0.*")]
34-
[assembly: AssemblyVersion("2.0.10.*")]
35-
[assembly: AssemblyFileVersion("2.0.10.0")]
34+
[assembly: AssemblyVersion("2.0.11.*")]
35+
[assembly: AssemblyFileVersion("2.0.11.0")]

RetailCoder.VBE/Root/RubberduckModule.cs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -75,7 +75,7 @@ public override void Load()
7575
{
7676
Assembly.GetExecutingAssembly(),
7777
Assembly.GetAssembly(typeof(IHostApplication)),
78-
Assembly.GetAssembly(typeof(IRubberduckParser)),
78+
Assembly.GetAssembly(typeof(IParseCoordinator)),
7979
Assembly.GetAssembly(typeof(IIndenter))
8080
};
8181

@@ -91,7 +91,7 @@ public override void Load()
9191
Bind<Func<IIndenterSettings>>().ToMethod(t => () => KernelInstance.Get<IGeneralConfigService>().LoadConfiguration().UserSettings.IndenterSettings);
9292

9393
BindCustomDeclarationLoadersToParser();
94-
Rebind<IRubberduckParser>().To<RubberduckParser>().InSingletonScope();
94+
Rebind<IParseCoordinator>().To<ParseCoordinator>().InSingletonScope();
9595
Bind<Func<IVBAPreprocessor>>().ToMethod(p => () => new VBAPreprocessor(double.Parse(_vbe.Version, CultureInfo.InvariantCulture)));
9696

9797
Rebind<ISearchResultsWindowViewModel>().To<SearchResultsWindowViewModel>().InSingletonScope();

Rubberduck.Parsing/IRubberduckParser.cs renamed to Rubberduck.Parsing/IParseCoordinator.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -3,7 +3,7 @@
33

44
namespace Rubberduck.Parsing
55
{
6-
public interface IRubberduckParser : IDisposable
6+
public interface IParseCoordinator : IDisposable
77
{
88
RubberduckParserState State { get; }
99
}

Rubberduck.Parsing/Rubberduck.Parsing.csproj

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -158,7 +158,7 @@
158158
<Compile Include="Binding\SimpleNameTypeBinding.cs" />
159159
<Compile Include="ComHelper.cs" />
160160
<Compile Include="IParseResultProvider.cs" />
161-
<Compile Include="IRubberduckParser.cs" />
161+
<Compile Include="IParseCoordinator.cs" />
162162
<Compile Include="ParsingText.Designer.cs">
163163
<AutoGen>True</AutoGen>
164164
<DesignTime>True</DesignTime>
@@ -296,7 +296,7 @@
296296
<Compile Include="VBA\ParseErrorEventArgs.cs" />
297297
<Compile Include="VBA\ParserState.cs" />
298298
<Compile Include="VBA\ReferencePriorityMap.cs" />
299-
<Compile Include="VBA\RubberduckParser.cs" />
299+
<Compile Include="VBA\ParseCoordinator.cs" />
300300
<Compile Include="VBA\RubberduckParserState.cs" />
301301
<Compile Include="VBA\StringExtensions.cs" />
302302
<Compile Include="VBA\VBALikePatternParser.cs" />

Rubberduck.Parsing/VBA/RubberduckParser.cs renamed to Rubberduck.Parsing/VBA/ParseCoordinator.cs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -18,7 +18,7 @@
1818

1919
namespace Rubberduck.Parsing.VBA
2020
{
21-
public class RubberduckParser : IRubberduckParser
21+
public class ParseCoordinator : IParseCoordinator
2222
{
2323
public RubberduckParserState State { get { return _state; } }
2424

@@ -37,7 +37,7 @@ private readonly IDictionary<IVBComponent, IDictionary<Tuple<string, Declaration
3737

3838
private readonly bool _isTestScope;
3939

40-
public RubberduckParser(
40+
public ParseCoordinator(
4141
IVBE vbe,
4242
RubberduckParserState state,
4343
IAttributeParser attributeParser,
@@ -654,7 +654,7 @@ private void ResolveReferences(DeclarationFinder finder, IVBComponent component,
654654
var watch = Stopwatch.StartNew();
655655
walker.Walk(listener, tree);
656656
watch.Stop();
657-
Logger.Debug("Binding Resolution done for component '{0}' in {1}ms (thread {2})", component.Name,
657+
Logger.Debug("Binding resolution done for component '{0}' in {1}ms (thread {2})", component.Name,
658658
watch.ElapsedMilliseconds, Thread.CurrentThread.ManagedThreadId);
659659

660660
State.SetModuleState(component, ParserState.Ready);

0 commit comments

Comments
 (0)