Skip to content

Commit 67f4810

Browse files
author
Andrin Meier
committed
Merge branch 'next' of https://github.com/rubberduck-vba/Rubberduck into interpreter
2 parents 609f8f8 + 640644a commit 67f4810

20 files changed

+149
-132
lines changed

RetailCoder.VBE/App.cs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -15,7 +15,6 @@
1515
using Rubberduck.SmartIndenter;
1616
using Rubberduck.UI;
1717
using Rubberduck.UI.Command.MenuItems;
18-
using Rubberduck.VBEditor.Extensions;
1918
using Infralution.Localization.Wpf;
2019
using Rubberduck.Common.Dispatch;
2120

@@ -99,7 +98,7 @@ async void sink_ProjectAdded(object sender, DispatcherEventArgs<VBProject> e)
9998
{
10099
Debug.WriteLine(string.Format("Project '{0}' was added.", e.Item.Name));
101100
var connectionPointContainer = (IConnectionPointContainer)e.Item.VBComponents;
102-
Guid interfaceId = typeof(_dispVBComponentsEvents).GUID;
101+
var interfaceId = typeof(_dispVBComponentsEvents).GUID;
103102

104103
IConnectionPoint connectionPoint;
105104
connectionPointContainer.FindConnectionPoint(ref interfaceId, out connectionPoint);
@@ -128,6 +127,7 @@ async void sink_ComponentSelected(object sender, DispatcherEventArgs<VBComponent
128127
async void sink_ComponentRenamed(object sender, DispatcherRenamedEventArgs<VBComponent> e)
129128
{
130129
Debug.WriteLine(string.Format("Component '{0}' was renamed.", e.Item.Name));
130+
131131
_parser.State.ClearDeclarations(e.Item);
132132
_parser.State.OnParseRequested(e.Item);
133133
}

RetailCoder.VBE/Inspections/ImplicitActiveSheetReferenceInspection.cs

Lines changed: 5 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -37,10 +37,11 @@ public override IEnumerable<InspectionResultBase> GetInspectionResults()
3737
// if host isn't Excel, the ExcelObjectModel declarations shouldn't be loaded anyway.
3838
}
3939

40-
var issues = Declarations.Where(item => item.IsBuiltIn
41-
&& item.ParentScope == "Excel.Global"
42-
&& Targets.Contains(item.IdentifierName)
43-
&& item.References.Any())
40+
var matches = BuiltInDeclarations.Where(item =>
41+
(item.ParentScope == "Excel.Global" || item.ParentScope == "Excel.Application")
42+
&& Targets.Contains(item.IdentifierName)).ToList();
43+
44+
var issues = matches.Where(item => item.References.Any())
4445
.SelectMany(declaration => declaration.References);
4546

4647
return issues.Select(issue =>

RetailCoder.VBE/Inspections/InspectionBase.cs

Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -74,6 +74,11 @@ protected virtual IEnumerable<Declaration> Declarations
7474
get { return State.AllDeclarations.Where(declaration => !declaration.IsInspectionDisabled(AnnotationName)); }
7575
}
7676

77+
protected virtual IEnumerable<Declaration> BuiltInDeclarations
78+
{
79+
get { return State.AllDeclarations.Where(declaration => declaration.IsBuiltIn); }
80+
}
81+
7782
/// <summary>
7883
/// Gets all user declarations in the parser state without an @Ignore annotation for this inspection.
7984
/// </summary>

RetailCoder.VBE/Inspections/InspectionsUI.Designer.cs

Lines changed: 12 additions & 3 deletions
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

RetailCoder.VBE/Inspections/InspectionsUI.resx

Lines changed: 6 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -166,13 +166,13 @@
166166
<value>Ignore once</value>
167167
</data>
168168
<data name="ImplicitActiveSheetReferenceInspectionMeta" xml:space="preserve">
169-
<value>Implicit references to the active sheet make the code frail and harder to debug. Consider making these references explicit when they're intended, and prefer working off object references.</value>
169+
<value>Implicit references to the active sheet make the code frail and harder to debug. Consider making these references explicit when they're intended, and prefer working off object references. Ignore if the member call is referring to a type Rubberduck can't resolve.</value>
170170
</data>
171171
<data name="ImplicitActiveSheetReferenceInspectionName" xml:space="preserve">
172172
<value>Implicit reference to ActiveSheet</value>
173173
</data>
174174
<data name="ImplicitActiveWorkbookReferenceInspectionMeta" xml:space="preserve">
175-
<value>Implicit references to the active workbook make the code frail and harder to debug. Consider making these references explicit when they're intended, and prefer working off object references.</value>
175+
<value>Implicit references to the active workbook make the code frail and harder to debug. Consider making these references explicit when they're intended, and prefer working off object references. Ignore if the member call is referring to a type Rubberduck can't resolve.</value>
176176
</data>
177177
<data name="ImplicitActiveWorkbookReferenceInspectionName" xml:space="preserve">
178178
<value>Implicit reference to ActiveWorkbook</value>
@@ -274,7 +274,7 @@
274274
<value>'Option Base 1' is specified</value>
275275
</data>
276276
<data name="OptionExplicitInspectionMeta" xml:space="preserve">
277-
<value>Rubberduck cannot see variables that aren't declared. VBA will happily compile a typo and you'll soon be asking an embarassing question on Stack Overflow. Avoid problems, use 'Option Explicit'. </value>
277+
<value>Rubberduck cannot see variables that aren't declared. VBA will happily compile a typo: use 'Option Explicit' to prevent successfully compiling an erroneous program.</value>
278278
</data>
279279
<data name="OptionExplicitInspectionName" xml:space="preserve">
280280
<value>'Option Explicit' is not specified</value>
@@ -497,4 +497,7 @@
497497
<data name="VariableNotAssignedInspectionResultFormat" xml:space="preserve">
498498
<value>Variable '{0}' is never assigned</value>
499499
</data>
500+
<data name="DisableThisInspection" xml:space="preserve">
501+
<value>Disable this inspection</value>
502+
</data>
500503
</root>

RetailCoder.VBE/Inspections/MultilineParameterInspection.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -25,7 +25,7 @@ where p.Context.GetSelection().LineCount > 1
2525
select p;
2626

2727
var issues = multilineParameters
28-
.Select(param => new MultilineParameterInspectionResult(this, param.Context, param.QualifiedName));
28+
.Select(param => new MultilineParameterInspectionResult(this, param));
2929

3030
return issues;
3131
}

RetailCoder.VBE/Inspections/MultilineParameterInspectionResult.cs

Lines changed: 3 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -1,17 +1,16 @@
11
using System.Collections.Generic;
2-
using Antlr4.Runtime;
32
using Rubberduck.Parsing;
3+
using Rubberduck.Parsing.Symbols;
44
using Rubberduck.UI;
5-
using Rubberduck.VBEditor;
65

76
namespace Rubberduck.Inspections
87
{
98
public class MultilineParameterInspectionResult : InspectionResultBase
109
{
1110
private readonly IEnumerable<CodeInspectionQuickFix> _quickFixes;
1211

13-
public MultilineParameterInspectionResult(IInspection inspection, ParserRuleContext context, QualifiedMemberName qualifiedName)
14-
: base(inspection, qualifiedName.QualifiedModuleName, context)
12+
public MultilineParameterInspectionResult(IInspection inspection, Declaration target)
13+
: base(inspection, target)
1514
{
1615
_quickFixes = new[]
1716
{

RetailCoder.VBE/Inspections/ProcedureNotUsedInspection.cs

Lines changed: 4 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -42,9 +42,10 @@ public override IEnumerable<InspectionResultBase> GetInspectionResults()
4242
handlers.AddRange(forms.SelectMany(form => declarations.FindFormEventHandlers(form)));
4343
}
4444

45-
var issues = declarations
46-
.Where(item => !IsIgnoredDeclaration(declarations, item, handlers, classes, modules))
47-
.Select(issue => new IdentifierNotUsedInspectionResult(this, issue, issue.Context, issue.QualifiedName.QualifiedModuleName));
45+
var items = declarations
46+
.Where(item => !IsIgnoredDeclaration(declarations, item, handlers, classes, modules)
47+
&& !item.IsInspectionDisabled(AnnotationName)).ToList();
48+
var issues = items.Select(issue => new IdentifierNotUsedInspectionResult(this, issue, issue.Context, issue.QualifiedName.QualifiedModuleName));
4849

4950
issues = DocumentNames.DocumentEventHandlerPrefixes.Aggregate(issues, (current, item) => current.Where(issue => !issue.Description.Contains("'" + item)));
5051

RetailCoder.VBE/Navigation/CodeExplorer/CodeExplorerViewModel.cs

Lines changed: 1 addition & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -2,10 +2,8 @@
22
using System.Diagnostics;
33
using System.Linq;
44
using System.Windows.Input;
5-
using System.Windows.Media.Imaging;
65
using Rubberduck.Parsing.Symbols;
76
using Rubberduck.Parsing.VBA;
8-
using Rubberduck.Properties;
97
using Rubberduck.UI;
108
using Rubberduck.UI.Command;
119

@@ -80,7 +78,7 @@ public ObservableCollection<CodeExplorerProjectViewModel> Projects
8078
private void ParserState_StateChanged(object sender, ParserStateEventArgs e)
8179
{
8280
IsBusy = e.State == ParserState.Parsing;
83-
if (e.State != ParserState.Parsed)
81+
if (e.State < ParserState.Parsed)
8482
{
8583
return;
8684
}

RetailCoder.VBE/UI/CodeExplorer/CodeExplorerControl.xaml

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

121121
<Style x:Key="CodeExplorerTreeViewStyle" TargetType="TreeView">
122122
<Setter Property="ItemTemplate" Value="{StaticResource CodeExplorerTemplate}" />
123-
<Setter Property="ItemsSource" Value="{Binding Projects}" />
123+
<Setter Property="ItemsSource" Value="{Binding Projects, UpdateSourceTrigger=PropertyChanged}" />
124124
</Style>
125125

126126
</UserControl.Resources>

0 commit comments

Comments
 (0)