Skip to content

Commit

Permalink
Merge pull request #2490 from retailcoder/next
Browse files Browse the repository at this point in the history
2.0.11
  • Loading branch information
retailcoder authored Jan 6, 2017
2 parents 7ca9028 + 09957af commit 89dc500
Show file tree
Hide file tree
Showing 12 changed files with 44 additions and 60 deletions.
4 changes: 2 additions & 2 deletions RetailCoder.VBE/API/ParserState.cs
Original file line number Diff line number Diff line change
Expand Up @@ -49,7 +49,7 @@ public sealed class ParserState : IParserState, IDisposable

private RubberduckParserState _state;
private AttributeParser _attributeParser;
private RubberduckParser _parser;
private ParseCoordinator _parser;
private VBE _vbe;

public ParserState()
Expand All @@ -70,7 +70,7 @@ public void Initialize(VBE vbe)

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

Expand Down
4 changes: 2 additions & 2 deletions RetailCoder.VBE/App.cs
Original file line number Diff line number Diff line change
Expand Up @@ -23,7 +23,7 @@ public sealed class App : IDisposable
{
private readonly IVBE _vbe;
private readonly IMessageBox _messageBox;
private readonly IRubberduckParser _parser;
private readonly IParseCoordinator _parser;
private readonly AutoSave.AutoSave _autoSave;
private readonly IGeneralConfigService _configService;
private readonly IAppMenu _appMenus;
Expand All @@ -36,7 +36,7 @@ public sealed class App : IDisposable

public App(IVBE vbe,
IMessageBox messageBox,
IRubberduckParser parser,
IParseCoordinator parser,
IGeneralConfigService configService,
IAppMenu appMenus,
RubberduckCommandBar stateBar,
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -4,20 +4,14 @@
using Rubberduck.Inspections.Resources;
using Rubberduck.Inspections.Results;
using Rubberduck.Parsing.VBA;
using Rubberduck.VBEditor.Application;
using Rubberduck.VBEditor.Extensions;
using Rubberduck.VBEditor.SafeComWrappers.Abstract;

namespace Rubberduck.Inspections
{
public sealed class ImplicitActiveSheetReferenceInspection : InspectionBase
{
private readonly IHostApplication _hostApp;

public ImplicitActiveSheetReferenceInspection(IVBE vbe, RubberduckParserState state)
public ImplicitActiveSheetReferenceInspection(RubberduckParserState state)
: base(state)
{
_hostApp = vbe.HostApplication();
}

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

public override IEnumerable<InspectionResultBase> GetInspectionResults()
{
if (_hostApp == null || _hostApp.ApplicationName != "Excel")
{
return Enumerable.Empty<InspectionResultBase>();
// if host isn't Excel, the ExcelObjectModel declarations shouldn't be loaded anyway.
}

var matches = BuiltInDeclarations.Where(item =>
item.ProjectName == "Excel" &&
Targets.Contains(item.IdentifierName) &&
item.ParentScope == "EXCEL.EXE;Excel._Global" &&
item.ParentDeclaration.ComponentName == "_Global" &&
item.AsTypeName == "Range").ToList();

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

return issues.Select(issue =>
new ImplicitActiveSheetReferenceInspectionResult(this, issue));
return issues
.Where(issue => !issue.IsInspectionDisabled(AnnotationName))
.Select(issue => new ImplicitActiveSheetReferenceInspectionResult(this, issue));
}
}
}
Original file line number Diff line number Diff line change
Expand Up @@ -4,20 +4,14 @@
using Rubberduck.Inspections.Resources;
using Rubberduck.Inspections.Results;
using Rubberduck.Parsing.VBA;
using Rubberduck.VBEditor.Application;
using Rubberduck.VBEditor.Extensions;
using Rubberduck.VBEditor.SafeComWrappers.Abstract;

namespace Rubberduck.Inspections
{
public sealed class ImplicitActiveWorkbookReferenceInspection : InspectionBase
{
private readonly IHostApplication _hostApp;

public ImplicitActiveWorkbookReferenceInspection(IVBE vbe, RubberduckParserState state)
public ImplicitActiveWorkbookReferenceInspection(RubberduckParserState state)
: base(state)
{
_hostApp = vbe.HostApplication();
}

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

private static readonly string[] ParentScopes =
{
"EXCEL.EXE;Excel._Global",
"EXCEL.EXE;Excel._Application",
"EXCEL.EXE;Excel.Sheets",
//"EXCEL.EXE;Excel.Worksheets",
"_Global",
"_Application",
"Sheets",
//"Worksheets",
};

public override IEnumerable<InspectionResultBase> GetInspectionResults()
{
if (_hostApp == null || _hostApp.ApplicationName != "Excel")
{
return Enumerable.Empty<InspectionResultBase>();
// if host isn't Excel, the ExcelObjectModel declarations shouldn't be loaded anyway.
}

var issues = BuiltInDeclarations
.Where(item => ParentScopes.Contains(item.ParentScope)
.Where(item => item.ProjectName == "Excel" && ParentScopes.Contains(item.ComponentName)
&& item.References.Any(r => Targets.Contains(r.IdentifierName)))
.SelectMany(declaration => declaration.References.Distinct())
.Where(item => Targets.Contains(item.IdentifierName))
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -14,9 +14,9 @@ namespace Rubberduck.Navigation.RegexSearchReplace
public class RegexSearchReplace : IRegexSearchReplace
{
private readonly IVBE _vbe;
private readonly IRubberduckParser _parser;
private readonly IParseCoordinator _parser;

public RegexSearchReplace(IVBE vbe, IRubberduckParser parser)
public RegexSearchReplace(IVBE vbe, IParseCoordinator parser)
{
_vbe = vbe;
_parser = parser;
Expand Down
4 changes: 2 additions & 2 deletions RetailCoder.VBE/Properties/AssemblyInfo.cs
Original file line number Diff line number Diff line change
Expand Up @@ -31,5 +31,5 @@
// You can specify all the values or you can default the Build and Revision Numbers
// by using the '*' as shown below:
// [assembly: AssemblyVersion("1.0.*")]
[assembly: AssemblyVersion("2.0.10.*")]
[assembly: AssemblyFileVersion("2.0.10.0")]
[assembly: AssemblyVersion("2.0.11.*")]
[assembly: AssemblyFileVersion("2.0.11.0")]
4 changes: 2 additions & 2 deletions RetailCoder.VBE/Root/RubberduckModule.cs
Original file line number Diff line number Diff line change
Expand Up @@ -75,7 +75,7 @@ public override void Load()
{
Assembly.GetExecutingAssembly(),
Assembly.GetAssembly(typeof(IHostApplication)),
Assembly.GetAssembly(typeof(IRubberduckParser)),
Assembly.GetAssembly(typeof(IParseCoordinator)),
Assembly.GetAssembly(typeof(IIndenter))
};

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

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

Rebind<ISearchResultsWindowViewModel>().To<SearchResultsWindowViewModel>().InSingletonScope();
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,7 @@

namespace Rubberduck.Parsing
{
public interface IRubberduckParser : IDisposable
public interface IParseCoordinator : IDisposable
{
RubberduckParserState State { get; }
}
Expand Down
4 changes: 2 additions & 2 deletions Rubberduck.Parsing/Rubberduck.Parsing.csproj
Original file line number Diff line number Diff line change
Expand Up @@ -158,7 +158,7 @@
<Compile Include="Binding\SimpleNameTypeBinding.cs" />
<Compile Include="ComHelper.cs" />
<Compile Include="IParseResultProvider.cs" />
<Compile Include="IRubberduckParser.cs" />
<Compile Include="IParseCoordinator.cs" />
<Compile Include="ParsingText.Designer.cs">
<AutoGen>True</AutoGen>
<DesignTime>True</DesignTime>
Expand Down Expand Up @@ -296,7 +296,7 @@
<Compile Include="VBA\ParseErrorEventArgs.cs" />
<Compile Include="VBA\ParserState.cs" />
<Compile Include="VBA\ReferencePriorityMap.cs" />
<Compile Include="VBA\RubberduckParser.cs" />
<Compile Include="VBA\ParseCoordinator.cs" />
<Compile Include="VBA\RubberduckParserState.cs" />
<Compile Include="VBA\StringExtensions.cs" />
<Compile Include="VBA\VBALikePatternParser.cs" />
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -18,7 +18,7 @@

namespace Rubberduck.Parsing.VBA
{
public class RubberduckParser : IRubberduckParser
public class ParseCoordinator : IParseCoordinator
{
public RubberduckParserState State { get { return _state; } }

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

private readonly bool _isTestScope;

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

State.SetModuleState(component, ParserState.Ready);
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -49,7 +49,7 @@ End Sub
parser.Parse(new CancellationTokenSource());
if (parser.State.Status >= ParserState.Error) { Assert.Inconclusive("Parser Error"); }

var inspection = new ImplicitActiveSheetReferenceInspection(vbe.Object, parser.State);
var inspection = new ImplicitActiveSheetReferenceInspection(parser.State);
var inspectionResults = inspection.GetInspectionResults();

Assert.AreEqual(1, inspectionResults.Count());
Expand Down Expand Up @@ -86,10 +86,10 @@ End Sub
parser.Parse(new CancellationTokenSource());
if (parser.State.Status >= ParserState.Error) { Assert.Inconclusive("Parser Error"); }

var inspection = new ImplicitActiveSheetReferenceInspection(vbe.Object, parser.State);
var inspection = new ImplicitActiveSheetReferenceInspection(parser.State);
var inspectionResults = inspection.GetInspectionResults();

Assert.AreEqual(1, inspectionResults.Count());
Assert.AreEqual(0, inspectionResults.Count());
}

[TestMethod]
Expand Down Expand Up @@ -127,7 +127,7 @@ Dim arr1() As Variant
parser.Parse(new CancellationTokenSource());
if (parser.State.Status >= ParserState.Error) { Assert.Inconclusive("Parser Error"); }

var inspection = new ImplicitActiveSheetReferenceInspection(vbe.Object, parser.State);
var inspection = new ImplicitActiveSheetReferenceInspection(parser.State);
var inspectionResults = inspection.GetInspectionResults();

inspectionResults.First().QuickFixes.Single(s => s is IgnoreOnceQuickFix).Fix();
Expand All @@ -146,7 +146,7 @@ public void InspectionType()
.Build();
var vbe = builder.AddProject(project).Build();

var inspection = new ImplicitActiveSheetReferenceInspection(vbe.Object, null);
var inspection = new ImplicitActiveSheetReferenceInspection(null);
Assert.AreEqual(CodeInspectionType.MaintainabilityAndReadabilityIssues, inspection.InspectionType);
}

Expand All @@ -162,7 +162,7 @@ public void InspectionName()
var vbe = builder.AddProject(project).Build();

const string inspectionName = "ImplicitActiveSheetReferenceInspection";
var inspection = new ImplicitActiveSheetReferenceInspection(vbe.Object, null);
var inspection = new ImplicitActiveSheetReferenceInspection(null);

Assert.AreEqual(inspectionName, inspection.Name);
}
Expand Down
14 changes: 10 additions & 4 deletions RubberduckTests/Mocks/MockParser.cs
Original file line number Diff line number Diff line change
Expand Up @@ -31,19 +31,25 @@ public static void ParseString(string inputCode, out QualifiedModuleName qualifi

}

public static RubberduckParser Create(IVBE vbe, RubberduckParserState state)
public static ParseCoordinator Create(IVBE vbe, RubberduckParserState state)
{
var attributeParser = new Mock<IAttributeParser>();
attributeParser.Setup(m => m.Parse(It.IsAny<IVBComponent>()))
.Returns(() => new Dictionary<Tuple<string, DeclarationType>, Attributes>());
return Create(vbe, state, attributeParser.Object);
}

public static RubberduckParser Create(IVBE vbe, RubberduckParserState state, IAttributeParser attributeParser)
public static ParseCoordinator Create(IVBE vbe, RubberduckParserState state, IAttributeParser attributeParser)
{
return new RubberduckParser(vbe, state, attributeParser,
return new ParseCoordinator(vbe, state, attributeParser,
() => new VBAPreprocessor(double.Parse(vbe.Version, CultureInfo.InvariantCulture)),
new List<ICustomDeclarationLoader> {new DebugDeclarations(state), new SpecialFormDeclarations(state), new FormEventDeclarations(state), new AliasDeclarations(state)}, true);
new List<ICustomDeclarationLoader>
{
new DebugDeclarations(state),
new SpecialFormDeclarations(state),
new FormEventDeclarations(state),
new AliasDeclarations(state),
}, true);
}
}
}

0 comments on commit 89dc500

Please sign in to comment.