Skip to content

Commit cfbf0d0

Browse files
authored
Merge pull request #133 from rubberduck-vba/next
sync with main repo
2 parents 1bba4b3 + 593d34e commit cfbf0d0

28 files changed

+561
-120
lines changed

RetailCoder.VBE/App.cs

Lines changed: 51 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -19,6 +19,7 @@
1919
using System.Threading.Tasks;
2020
using System.Windows.Forms;
2121
using Rubberduck.UI.SourceControl;
22+
using Rubberduck.VBEditor.Extensions;
2223

2324
namespace Rubberduck
2425
{
@@ -216,7 +217,7 @@ public void Shutdown()
216217
#region sink handlers. todo: move to another class
217218
async void sink_ProjectRemoved(object sender, DispatcherEventArgs<VBProject> e)
218219
{
219-
if (!_handleSinkEvents) { return; }
220+
if (!_handleSinkEvents || !_vbe.IsInDesignMode()) { return; }
220221

221222
if (e.Item.Protection == vbext_ProjectProtection.vbext_pp_locked)
222223
{
@@ -256,7 +257,7 @@ async void sink_ProjectRemoved(object sender, DispatcherEventArgs<VBProject> e)
256257

257258
async void sink_ProjectAdded(object sender, DispatcherEventArgs<VBProject> e)
258259
{
259-
if (!_handleSinkEvents) { return; }
260+
if (!_handleSinkEvents || !_vbe.IsInDesignMode()) { return; }
260261

261262
_logger.Debug("Project '{0}' was added.", e.Item.Name);
262263
if (e.Item.Protection == vbext_ProjectProtection.vbext_pp_locked)
@@ -313,7 +314,7 @@ private void RegisterComponentsEventSink(VBComponents components, string project
313314

314315
async void sink_ComponentSelected(object sender, DispatcherEventArgs<VBComponent> e)
315316
{
316-
if (!_handleSinkEvents) { return; }
317+
if (!_handleSinkEvents || !_vbe.IsInDesignMode()) { return; }
317318

318319
if (!_parser.State.AllDeclarations.Any())
319320
{
@@ -326,7 +327,7 @@ async void sink_ComponentSelected(object sender, DispatcherEventArgs<VBComponent
326327

327328
async void sink_ComponentRenamed(object sender, DispatcherRenamedEventArgs<VBComponent> e)
328329
{
329-
if (!_handleSinkEvents) { return; }
330+
if (!_handleSinkEvents || !_vbe.IsInDesignMode()) { return; }
330331

331332
if (!_parser.State.AllDeclarations.Any())
332333
{
@@ -336,13 +337,52 @@ async void sink_ComponentRenamed(object sender, DispatcherRenamedEventArgs<VBCom
336337
_sourceControlPanelVM.HandleRenamedComponent(e.Item, e.OldName);
337338

338339
_logger.Debug("Component '{0}' was renamed to '{1}'.", e.OldName, e.Item.Name);
340+
341+
var projectId = e.Item.Collection.Parent.HelpFile;
342+
var componentDeclaration = _parser.State.AllDeclarations.FirstOrDefault(f =>
343+
f.ProjectId == projectId &&
344+
f.DeclarationType == DeclarationType.ClassModule &&
345+
f.IdentifierName == e.OldName);
346+
347+
if (e.Item.Type == vbext_ComponentType.vbext_ct_Document &&
348+
componentDeclaration != null &&
349+
350+
// according to ThunderFrame, Excel is the only one we explicitly support
351+
// with two Document-component types just skip the Worksheet component
352+
((ClassModuleDeclaration) componentDeclaration).Supertypes.All(a => a.IdentifierName != "Worksheet"))
353+
{
354+
_componentsEventsSinks.Remove(projectId);
355+
_referencesEventsSinks.Remove(projectId);
356+
_parser.State.RemoveProject(projectId);
357+
358+
_logger.Debug("Project '{0}' was removed.", e.Item.Name);
359+
Tuple<IConnectionPoint, int> componentsTuple;
360+
if (_componentsEventsConnectionPoints.TryGetValue(projectId, out componentsTuple))
361+
{
362+
componentsTuple.Item1.Unadvise(componentsTuple.Item2);
363+
_componentsEventsConnectionPoints.Remove(projectId);
364+
}
365+
366+
Tuple<IConnectionPoint, int> referencesTuple;
367+
if (_referencesEventsConnectionPoints.TryGetValue(projectId, out referencesTuple))
368+
{
369+
referencesTuple.Item1.Unadvise(referencesTuple.Item2);
370+
_referencesEventsConnectionPoints.Remove(projectId);
371+
}
339372

340-
_parser.State.RemoveRenamedComponent(e.Item, e.OldName);
373+
_parser.State.AddProject(e.Item.Collection.Parent);
374+
}
375+
else
376+
{
377+
_parser.State.RemoveRenamedComponent(e.Item, e.OldName);
378+
}
379+
380+
_parser.State.OnParseRequested(this);
341381
}
342382

343383
async void sink_ComponentRemoved(object sender, DispatcherEventArgs<VBComponent> e)
344384
{
345-
if (!_handleSinkEvents) { return; }
385+
if (!_handleSinkEvents || !_vbe.IsInDesignMode()) { return; }
346386

347387
if (!_parser.State.AllDeclarations.Any())
348388
{
@@ -357,7 +397,7 @@ async void sink_ComponentRemoved(object sender, DispatcherEventArgs<VBComponent>
357397

358398
async void sink_ComponentReloaded(object sender, DispatcherEventArgs<VBComponent> e)
359399
{
360-
if (!_handleSinkEvents) { return; }
400+
if (!_handleSinkEvents || !_vbe.IsInDesignMode()) { return; }
361401

362402
if (!_parser.State.AllDeclarations.Any())
363403
{
@@ -370,7 +410,7 @@ async void sink_ComponentReloaded(object sender, DispatcherEventArgs<VBComponent
370410

371411
async void sink_ComponentAdded(object sender, DispatcherEventArgs<VBComponent> e)
372412
{
373-
if (!_handleSinkEvents) { return; }
413+
if (!_handleSinkEvents || !_vbe.IsInDesignMode()) { return; }
374414

375415
if (!_parser.State.AllDeclarations.Any())
376416
{
@@ -385,7 +425,7 @@ async void sink_ComponentAdded(object sender, DispatcherEventArgs<VBComponent> e
385425

386426
async void sink_ComponentActivated(object sender, DispatcherEventArgs<VBComponent> e)
387427
{
388-
if (!_handleSinkEvents) { return; }
428+
if (!_handleSinkEvents || !_vbe.IsInDesignMode()) { return; }
389429

390430
if (!_parser.State.AllDeclarations.Any())
391431
{
@@ -398,7 +438,7 @@ async void sink_ComponentActivated(object sender, DispatcherEventArgs<VBComponen
398438

399439
async void sink_ProjectRenamed(object sender, DispatcherRenamedEventArgs<VBProject> e)
400440
{
401-
if (!_handleSinkEvents) { return; }
441+
if (!_handleSinkEvents || !_vbe.IsInDesignMode()) { return; }
402442

403443
if (!_parser.State.AllDeclarations.Any())
404444
{
@@ -415,7 +455,7 @@ async void sink_ProjectRenamed(object sender, DispatcherRenamedEventArgs<VBProje
415455

416456
async void sink_ProjectActivated(object sender, DispatcherEventArgs<VBProject> e)
417457
{
418-
if (!_handleSinkEvents) { return; }
458+
if (!_handleSinkEvents || !_vbe.IsInDesignMode()) { return; }
419459

420460
if (!_parser.State.AllDeclarations.Any())
421461
{

RetailCoder.VBE/Inspections/ImplicitActiveWorkbookReferenceInspection.cs

Lines changed: 7 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -27,6 +27,12 @@ public ImplicitActiveWorkbookReferenceInspection(VBE vbe, RubberduckParserState
2727
"Worksheets", "Sheets", "Names",
2828
};
2929

30+
private static readonly string[] ParentScopes =
31+
{
32+
"EXCEL.EXE;Excel._Global",
33+
"EXCEL.EXE;Excel._Application"
34+
};
35+
3036
public override IEnumerable<InspectionResultBase> GetInspectionResults()
3137
{
3238
if (_hostApp == null || _hostApp.ApplicationName != "Excel")
@@ -35,7 +41,7 @@ public override IEnumerable<InspectionResultBase> GetInspectionResults()
3541
// if host isn't Excel, the ExcelObjectModel declarations shouldn't be loaded anyway.
3642
}
3743

38-
var issues = BuiltInDeclarations.Where(item => item.ParentScope.StartsWith("EXCEL.EXE;")
44+
var issues = BuiltInDeclarations.Where(item => ParentScopes.Contains(item.ParentScope)
3945
&& Targets.Contains(item.IdentifierName)
4046
&& item.References.Any())
4147
.SelectMany(declaration => declaration.References);

RetailCoder.VBE/Inspections/ObsoleteCallStatementInspection.cs

Lines changed: 24 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,4 @@
11
using System.Collections.Generic;
2-
using System.Linq;
32
using Rubberduck.Parsing;
43
using Rubberduck.Parsing.Grammar;
54
using Rubberduck.Parsing.VBA;
@@ -25,9 +24,30 @@ public override IEnumerable<InspectionResultBase> GetInspectionResults()
2524
return new InspectionResultBase[] { };
2625
}
2726

28-
return ParseTreeResults.ObsoleteCallContexts.Select(context =>
29-
new ObsoleteCallStatementUsageInspectionResult(this,
30-
new QualifiedContext<VBAParser.CallStmtContext>(context.ModuleName, context.Context as VBAParser.CallStmtContext)));
27+
var results = new List<ObsoleteCallStatementUsageInspectionResult>();
28+
29+
foreach (var context in ParseTreeResults.ObsoleteCallContexts)
30+
{
31+
var lines = context.ModuleName.Component.CodeModule.Lines[
32+
context.Context.Start.Line, context.Context.Stop.Line - context.Context.Start.Line + 1];
33+
34+
var stringStrippedLines = string.Join(string.Empty, lines).StripStringLiterals();
35+
36+
int commentIndex;
37+
if (stringStrippedLines.HasComment(out commentIndex))
38+
{
39+
stringStrippedLines = stringStrippedLines.Remove(commentIndex);
40+
}
41+
42+
if (!stringStrippedLines.Contains(":"))
43+
{
44+
results.Add(new ObsoleteCallStatementUsageInspectionResult(this,
45+
new QualifiedContext<VBAParser.CallStmtContext>(context.ModuleName,
46+
context.Context as VBAParser.CallStmtContext)));
47+
}
48+
}
49+
50+
return results;
3151
}
3252

3353
public class ObsoleteCallStatementListener : VBAParserBaseListener

RetailCoder.VBE/Navigation/CodeExplorer/CodeExplorerViewModel.cs

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -42,6 +42,7 @@ public CodeExplorerViewModel(FolderHelper folderHelper, RubberduckParserState st
4242
_addUserFormCommand = commands.OfType<CodeExplorer_AddUserFormCommand>().FirstOrDefault();
4343

4444
_openDesignerCommand = commands.OfType<CodeExplorer_OpenDesignerCommand>().FirstOrDefault();
45+
_openProjectPropertiesCommand = commands.OfType<CodeExplorer_OpenProjectPropertiesCommand>().FirstOrDefault();
4546
_renameCommand = commands.OfType<CodeExplorer_RenameCommand>().FirstOrDefault();
4647
_indenterCommand = commands.OfType<CodeExplorer_IndentCommand>().FirstOrDefault();
4748

@@ -442,6 +443,9 @@ private void SetErrorState(CodeExplorerItemViewModel itemNode, VBComponent compo
442443
private readonly ICommand _openDesignerCommand;
443444
public ICommand OpenDesignerCommand { get { return _openDesignerCommand; } }
444445

446+
private readonly ICommand _openProjectPropertiesCommand;
447+
public ICommand OpenProjectPropertiesCommand { get { return _openProjectPropertiesCommand; } }
448+
445449
private readonly ICommand _renameCommand;
446450
public ICommand RenameCommand { get { return _renameCommand; } }
447451

RetailCoder.VBE/Refactorings/Rename/RenameRefactoring.cs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -199,6 +199,7 @@ private void Rename()
199199
if (ModuleDeclarationTypes.Contains(_model.Target.DeclarationType))
200200
{
201201
RenameModule();
202+
return; // renaming a component automatically triggers a reparse
202203
}
203204
else if (_model.Target.DeclarationType == DeclarationType.Project)
204205
{

RetailCoder.VBE/Rubberduck.csproj

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -407,6 +407,7 @@
407407
<Compile Include="UI\CodeExplorer\Commands\CodeExplorer_CommitCommand.cs" />
408408
<Compile Include="UI\CodeExplorer\Commands\CodeExplorer_AddUserFormCommand.cs" />
409409
<Compile Include="UI\CodeExplorer\Commands\CodeExplorer_CopyResultsCommand.cs" />
410+
<Compile Include="UI\CodeExplorer\Commands\CodeExplorer_OpenProjectPropertiesCommand.cs" />
410411
<Compile Include="UI\CodeExplorer\Commands\CodeExplorer_RefreshComponentCommand.cs" />
411412
<Compile Include="UI\CodeExplorer\Commands\CodeExplorer_RenameCommand.cs" />
412413
<Compile Include="UI\CodeExplorer\Commands\CodeExplorer_FindAllReferencesCommand.cs" />

RetailCoder.VBE/UI/CodeExplorer/CodeExplorerControl.xaml

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -373,6 +373,9 @@
373373
Command="{Binding RenameCommand}"
374374
CommandParameter="{Binding SelectedItem}" />
375375
<Separator />
376+
<MenuItem Header="{Resx ResxName=Rubberduck.UI.RubberduckUI, Key=CodeExplorer_OpenProjectProperties}"
377+
Command="{Binding OpenProjectPropertiesCommand}" />
378+
<Separator />
376379
<MenuItem Header="{Resx ResxName=Rubberduck.UI.RubberduckUI, Key=Add}">
377380
<MenuItem Header="{Resx ResxName=Rubberduck.UI.RubberduckUI, Key=CodeExplorer_AddTestModuleText}"
378381
Command="{Binding AddTestModuleCommand}"
Lines changed: 22 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,22 @@
1+
using Microsoft.Vbe.Interop;
2+
using Rubberduck.UI.Command;
3+
4+
namespace Rubberduck.UI.CodeExplorer.Commands
5+
{
6+
public class CodeExplorer_OpenProjectPropertiesCommand : CommandBase
7+
{
8+
private readonly VBE _vbe;
9+
10+
public CodeExplorer_OpenProjectPropertiesCommand(VBE vbe)
11+
{
12+
_vbe = vbe;
13+
}
14+
15+
public override void Execute(object parameter)
16+
{
17+
const int openProjectPropertiesId = 2578;
18+
19+
_vbe.CommandBars.FindControl(Id: openProjectPropertiesId).Execute();
20+
}
21+
}
22+
}

RetailCoder.VBE/UI/Command/AddTestModuleCommand.cs

Lines changed: 1 addition & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -25,15 +25,7 @@ public AddTestModuleCommand(VBE vbe, RubberduckParserState state, NewUnitTestMod
2525

2626
public override bool CanExecute(object parameter)
2727
{
28-
var app = _vbe.HostApplication();
29-
if (app == null || _state.Status != ParserState.Ready)
30-
{
31-
return false;
32-
}
33-
34-
// Outlook requires test methods to be located in [ThisOutlookSession] class.
35-
//return app.ApplicationName != "Outlook";
36-
return true;
28+
return _vbe.HostSupportsUnitTests();
3729
}
3830

3931
public override void Execute(object parameter)

RetailCoder.VBE/UI/Command/RunAllTestsCommand.cs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -5,6 +5,7 @@
55
using Rubberduck.Parsing.VBA;
66
using Rubberduck.UI.UnitTesting;
77
using Rubberduck.UnitTesting;
8+
using Rubberduck.VBEditor.Extensions;
89

910
namespace Rubberduck.UI.Command
1011
{
@@ -28,7 +29,7 @@ public RunAllTestsCommand(VBE vbe, RubberduckParserState state, ITestEngine engi
2829

2930
public override bool CanExecute(object parameter)
3031
{
31-
return _vbe.VBProjects.Cast<VBProject>().All(project => project.Mode == vbext_VBAMode.vbext_vm_Design);
32+
return _vbe.IsInDesignMode();
3233
}
3334

3435
public override void Execute(object parameter)

0 commit comments

Comments
 (0)