Skip to content

Commit 6c1136c

Browse files
committed
Merge pull request #47 from rubberduck-vba/CodeExplorer
Code explorer
2 parents b8196d4 + 76c8731 commit 6c1136c

File tree

84 files changed

+28765
-29483
lines changed

Some content is hidden

Large Commits have some content hidden by default. Use the searchbox below for content that may be hidden.

84 files changed

+28765
-29483
lines changed

RetailCoder.VBE/App.cs

Lines changed: 0 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -24,9 +24,7 @@ public class App : IDisposable
2424
{
2525
private readonly VBE _vbe;
2626
private readonly IMessageBox _messageBox;
27-
private readonly IParserErrorsPresenterFactory _parserErrorsPresenterFactory;
2827
private readonly IRubberduckParser _parser;
29-
private readonly IInspectorFactory _inspectorFactory;
3028
private readonly AutoSave.AutoSave _autoSave;
3129
private readonly IGeneralConfigService _configService;
3230
private readonly IAppMenu _appMenus;
@@ -39,9 +37,7 @@ public class App : IDisposable
3937
private Configuration _config;
4038

4139
public App(VBE vbe, IMessageBox messageBox,
42-
IParserErrorsPresenterFactory parserErrorsPresenterFactory,
4340
IRubberduckParser parser,
44-
IInspectorFactory inspectorFactory,
4541
IGeneralConfigService configService,
4642
IAppMenu appMenus,
4743
RubberduckCommandBar stateBar,
@@ -50,9 +46,7 @@ public App(VBE vbe, IMessageBox messageBox,
5046
{
5147
_vbe = vbe;
5248
_messageBox = messageBox;
53-
_parserErrorsPresenterFactory = parserErrorsPresenterFactory;
5449
_parser = parser;
55-
_inspectorFactory = inspectorFactory;
5650
_configService = configService;
5751
_autoSave = new AutoSave.AutoSave(_vbe, _configService);
5852
_appMenus = appMenus;
@@ -174,7 +168,6 @@ public void Startup()
174168
private void CleanReloadConfig()
175169
{
176170
LoadConfig();
177-
Setup();
178171
}
179172

180173
private void ConfigServiceLanguageChanged(object sender, EventArgs e)
@@ -202,12 +195,6 @@ private void LoadConfig()
202195
}
203196
}
204197

205-
private void Setup()
206-
{
207-
_inspectorFactory.Create();
208-
_parserErrorsPresenterFactory.Create();
209-
}
210-
211198
public void Dispose()
212199
{
213200
//_hooks.MessageReceived -= hooks_MessageReceived;

RetailCoder.VBE/AutoSave/AutoSave.cs

Lines changed: 7 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -24,10 +24,14 @@ public AutoSave(VBE vbe, IGeneralConfigService configService)
2424

2525
_configService.SettingsChanged += ConfigServiceSettingsChanged;
2626

27-
_timer.Enabled = _config.UserSettings.GeneralSettings.AutoSaveEnabled;
28-
_timer.Interval = _config.UserSettings.GeneralSettings.AutoSavePeriod * 1000;
27+
_timer.Enabled = _config.UserSettings.GeneralSettings.AutoSaveEnabled
28+
&& _config.UserSettings.GeneralSettings.AutoSavePeriod != 0;
2929

30-
_timer.Elapsed += _timer_Elapsed;
30+
if (_config.UserSettings.GeneralSettings.AutoSavePeriod != 0)
31+
{
32+
_timer.Interval = _config.UserSettings.GeneralSettings.AutoSavePeriod * 1000;
33+
_timer.Elapsed += _timer_Elapsed;
34+
}
3135
}
3236

3337
void ConfigServiceSettingsChanged(object sender, EventArgs e)

RetailCoder.VBE/Inspections/AssignedByValParameterInspection.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -26,7 +26,7 @@ public override IEnumerable<InspectionResultBase> GetInspectionResults()
2626
&& declaration.References.Any(reference => reference.IsAssignment));
2727

2828
var issues = assignedByValParameters
29-
.Select(param => new AssignedByValParameterInspectionResult(this, param.Context, param.QualifiedName));
29+
.Select(param => new AssignedByValParameterInspectionResult(this, param));
3030

3131
return issues;
3232
}

RetailCoder.VBE/Inspections/AssignedByValParameterInspectionResult.cs

Lines changed: 4 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,7 @@
11
using System.Collections.Generic;
22
using Antlr4.Runtime;
33
using Rubberduck.Parsing.Grammar;
4+
using Rubberduck.Parsing.Symbols;
45
using Rubberduck.VBEditor;
56

67
namespace Rubberduck.Inspections
@@ -9,12 +10,12 @@ public class AssignedByValParameterInspectionResult : InspectionResultBase
910
{
1011
private readonly IEnumerable<CodeInspectionQuickFix> _quickFixes;
1112

12-
public AssignedByValParameterInspectionResult(IInspection inspection, ParserRuleContext context, QualifiedMemberName qualifiedName)
13-
: base(inspection, qualifiedName.QualifiedModuleName, context)
13+
public AssignedByValParameterInspectionResult(IInspection inspection, Declaration target)
14+
: base(inspection, target)
1415
{
1516
_quickFixes = new[]
1617
{
17-
new PassParameterByReferenceQuickFix(context, QualifiedSelection),
18+
new PassParameterByReferenceQuickFix(target.Context, QualifiedSelection),
1819
};
1920
}
2021

RetailCoder.VBE/Inspections/FunctionReturnValueNotUsedInspection.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -98,7 +98,7 @@ private bool IsAddressOfCall(IdentifierReference usage)
9898

9999
private bool IsReturnStatement(Declaration function, IdentifierReference assignment)
100100
{
101-
return assignment.ParentScope == function.Scope;
101+
return assignment.ParentScoping.Equals(function);
102102
}
103103

104104
private bool IsCallWithoutAssignment(IdentifierReference usage)

RetailCoder.VBE/Inspections/FunctionReturnValueNotUsedInspectionResult.cs

Lines changed: 4 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -9,12 +9,9 @@ namespace Rubberduck.Inspections
99
public class FunctionReturnValueNotUsedInspectionResult : InspectionResultBase
1010
{
1111
private readonly IEnumerable<CodeInspectionQuickFix> _quickFixes;
12+
private QualifiedMemberName _memberName;
1213

13-
public FunctionReturnValueNotUsedInspectionResult(
14-
IInspection inspection,
15-
ParserRuleContext context,
16-
QualifiedMemberName qualifiedName,
17-
IEnumerable<string> returnStatements)
14+
public FunctionReturnValueNotUsedInspectionResult(IInspection inspection, ParserRuleContext context, QualifiedMemberName qualifiedName, IEnumerable<string> returnStatements)
1815
: this(inspection, context, qualifiedName, returnStatements, new List<Tuple<ParserRuleContext, QualifiedSelection, IEnumerable<string>>>())
1916
{
2017
}
@@ -27,6 +24,7 @@ public FunctionReturnValueNotUsedInspectionResult(
2724
IEnumerable<Tuple<ParserRuleContext, QualifiedSelection, IEnumerable<string>>> children)
2825
: base(inspection, qualifiedName.QualifiedModuleName, context)
2926
{
27+
_memberName = qualifiedName;
3028
var root = new ConvertToProcedureQuickFix(context, QualifiedSelection, returnStatements);
3129
var compositeFix = new CompositeCodeInspectionFix(root);
3230
children.ToList().ForEach(child => compositeFix.AddChild(new ConvertToProcedureQuickFix(child.Item1, child.Item2, child.Item3)));
@@ -42,7 +40,7 @@ public override string Description
4240
{
4341
get
4442
{
45-
return string.Format(InspectionsUI.FunctionReturnValueNotUsedInspectionResultFormat, Target.IdentifierName);
43+
return string.Format(InspectionsUI.FunctionReturnValueNotUsedInspectionResultFormat, _memberName.MemberName);
4644
}
4745
}
4846
}

RetailCoder.VBE/Inspections/IdentifierNotAssignedInspectionResult.cs

Lines changed: 7 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -9,18 +9,25 @@ namespace Rubberduck.Inspections
99
public class IdentifierNotAssignedInspectionResult : IdentifierNotUsedInspectionResult
1010
{
1111
private readonly IEnumerable<CodeInspectionQuickFix> _quickFixes;
12+
private readonly Declaration _target;
1213

1314
public IdentifierNotAssignedInspectionResult(IInspection inspection, Declaration target,
1415
ParserRuleContext context, QualifiedModuleName qualifiedName)
1516
: base(inspection, target, context, qualifiedName)
1617
{
18+
_target = target;
1719
_quickFixes = new CodeInspectionQuickFix[]
1820
{
1921
new RemoveUnassignedIdentifierQuickFix(Context, QualifiedSelection),
2022
new IgnoreOnceQuickFix(context, QualifiedSelection, Inspection.AnnotationName),
2123
};
2224
}
2325

26+
public override string Description
27+
{
28+
get { return string.Format(InspectionsUI.VariableNotAssignedInspectionResultFormat, _target.IdentifierName); }
29+
}
30+
2431
public override IEnumerable<CodeInspectionQuickFix> QuickFixes { get { return _quickFixes; } }
2532
}
2633

RetailCoder.VBE/Inspections/IdentifierNotUsedInspectionResult.cs

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -24,8 +24,7 @@ public IdentifierNotUsedInspectionResult(IInspection inspection, Declaration tar
2424
}
2525

2626
public override IEnumerable<CodeInspectionQuickFix> QuickFixes { get { return _quickFixes; } }
27-
28-
public override string Description
27+
public override string Description
2928
{
3029
get
3130
{

RetailCoder.VBE/Inspections/ImplicitByRefParameterInspection.cs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -29,8 +29,8 @@ public override IEnumerable<InspectionResultBase> GetInspectionResults()
2929
&& !interfaceMembers.Select(m => m.Scope).Contains(item.ParentScope)
3030
let arg = item.Context as VBAParser.ArgContext
3131
where arg != null && arg.BYREF() == null && arg.BYVAL() == null
32-
select new QualifiedContext<VBAParser.ArgContext>(item.QualifiedName, arg))
33-
.Select(issue => new ImplicitByRefParameterInspectionResult(this, string.Format(Description, issue.Context.ambiguousIdentifier().GetText()), issue));
32+
select new {Declaration = item, Context = new QualifiedContext<VBAParser.ArgContext>(item.QualifiedName, arg) })
33+
.Select(issue => new ImplicitByRefParameterInspectionResult(this, issue.Context, issue.Declaration));
3434

3535

3636
return issues;

RetailCoder.VBE/Inspections/ImplicitByRefParameterInspectionResult.cs

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -2,6 +2,7 @@
22
using Antlr4.Runtime;
33
using Rubberduck.Parsing;
44
using Rubberduck.Parsing.Grammar;
5+
using Rubberduck.Parsing.Symbols;
56
using Rubberduck.VBEditor;
67

78
namespace Rubberduck.Inspections
@@ -10,8 +11,8 @@ public class ImplicitByRefParameterInspectionResult : InspectionResultBase
1011
{
1112
private readonly IEnumerable<CodeInspectionQuickFix> _quickFixes;
1213

13-
public ImplicitByRefParameterInspectionResult(IInspection inspection, string result, QualifiedContext<VBAParser.ArgContext> qualifiedContext)
14-
: base(inspection, qualifiedContext.ModuleName, qualifiedContext.Context)
14+
public ImplicitByRefParameterInspectionResult(IInspection inspection, QualifiedContext<VBAParser.ArgContext> qualifiedContext, Declaration declaration)
15+
: base(inspection, declaration)
1516
{
1617
_quickFixes = new CodeInspectionQuickFix[]
1718
{

0 commit comments

Comments
 (0)