Skip to content

Commit a795538

Browse files
authored
Merge pull request #1916 from rubberduck-vba/next
Release 2.0.3b
2 parents 7e9cc59 + 593d34e commit a795538

File tree

66 files changed

+6201
-5022
lines changed

Some content is hidden

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

66 files changed

+6201
-5022
lines changed

RetailCoder.VBE/App.cs

Lines changed: 70 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,5 @@
1-
using Infralution.Localization.Wpf;
1+
using System.IO;
2+
using Infralution.Localization.Wpf;
23
using Microsoft.Vbe.Interop;
34
using NLog;
45
using Rubberduck.Common;
@@ -18,6 +19,7 @@
1819
using System.Threading.Tasks;
1920
using System.Windows.Forms;
2021
using Rubberduck.UI.SourceControl;
22+
using Rubberduck.VBEditor.Extensions;
2123

2224
namespace Rubberduck
2325
{
@@ -169,13 +171,29 @@ private void _configService_SettingsChanged(object sender, ConfigurationChangedE
169171
}
170172
}
171173

174+
private void EnsureDirectoriesExist()
175+
{
176+
try
177+
{
178+
if (!Directory.Exists(ApplicationConstants.LOG_FOLDER_PATH))
179+
{
180+
Directory.CreateDirectory(ApplicationConstants.LOG_FOLDER_PATH);
181+
}
182+
}
183+
catch
184+
{
185+
//Does this need to display some sort of dialog?
186+
}
187+
}
188+
172189
private void UpdateLoggingLevel()
173190
{
174191
LogLevelHelper.SetMinimumLogLevel(LogLevel.FromOrdinal(_config.UserSettings.GeneralSettings.MinimumLogLevel));
175192
}
176193

177194
public void Startup()
178195
{
196+
EnsureDirectoriesExist();
179197
LoadConfig();
180198
_appMenus.Initialize();
181199
_hooks.HookHotkeys(); // need to hook hotkeys before we localize menus, to correctly display ShortcutTexts
@@ -199,7 +217,7 @@ public void Shutdown()
199217
#region sink handlers. todo: move to another class
200218
async void sink_ProjectRemoved(object sender, DispatcherEventArgs<VBProject> e)
201219
{
202-
if (!_handleSinkEvents) { return; }
220+
if (!_handleSinkEvents || !_vbe.IsInDesignMode()) { return; }
203221

204222
if (e.Item.Protection == vbext_ProjectProtection.vbext_pp_locked)
205223
{
@@ -213,6 +231,7 @@ async void sink_ProjectRemoved(object sender, DispatcherEventArgs<VBProject> e)
213231
_componentsEventsSinks.Remove(projectId);
214232
_referencesEventsSinks.Remove(projectId);
215233
_parser.State.RemoveProject(e.Item);
234+
_parser.State.OnParseRequested(this);
216235

217236
_logger.Debug("Project '{0}' was removed.", e.Item.Name);
218237
Tuple<IConnectionPoint, int> componentsTuple;
@@ -238,7 +257,7 @@ async void sink_ProjectRemoved(object sender, DispatcherEventArgs<VBProject> e)
238257

239258
async void sink_ProjectAdded(object sender, DispatcherEventArgs<VBProject> e)
240259
{
241-
if (!_handleSinkEvents) { return; }
260+
if (!_handleSinkEvents || !_vbe.IsInDesignMode()) { return; }
242261

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

296315
async void sink_ComponentSelected(object sender, DispatcherEventArgs<VBComponent> e)
297316
{
298-
if (!_handleSinkEvents) { return; }
317+
if (!_handleSinkEvents || !_vbe.IsInDesignMode()) { return; }
299318

300319
if (!_parser.State.AllDeclarations.Any())
301320
{
@@ -308,7 +327,7 @@ async void sink_ComponentSelected(object sender, DispatcherEventArgs<VBComponent
308327

309328
async void sink_ComponentRenamed(object sender, DispatcherRenamedEventArgs<VBComponent> e)
310329
{
311-
if (!_handleSinkEvents) { return; }
330+
if (!_handleSinkEvents || !_vbe.IsInDesignMode()) { return; }
312331

313332
if (!_parser.State.AllDeclarations.Any())
314333
{
@@ -318,13 +337,52 @@ async void sink_ComponentRenamed(object sender, DispatcherRenamedEventArgs<VBCom
318337
_sourceControlPanelVM.HandleRenamedComponent(e.Item, e.OldName);
319338

320339
_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);
321346

322-
_parser.State.RemoveRenamedComponent(e.Item, e.OldName);
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+
}
372+
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);
323381
}
324382

325383
async void sink_ComponentRemoved(object sender, DispatcherEventArgs<VBComponent> e)
326384
{
327-
if (!_handleSinkEvents) { return; }
385+
if (!_handleSinkEvents || !_vbe.IsInDesignMode()) { return; }
328386

329387
if (!_parser.State.AllDeclarations.Any())
330388
{
@@ -339,7 +397,7 @@ async void sink_ComponentRemoved(object sender, DispatcherEventArgs<VBComponent>
339397

340398
async void sink_ComponentReloaded(object sender, DispatcherEventArgs<VBComponent> e)
341399
{
342-
if (!_handleSinkEvents) { return; }
400+
if (!_handleSinkEvents || !_vbe.IsInDesignMode()) { return; }
343401

344402
if (!_parser.State.AllDeclarations.Any())
345403
{
@@ -352,7 +410,7 @@ async void sink_ComponentReloaded(object sender, DispatcherEventArgs<VBComponent
352410

353411
async void sink_ComponentAdded(object sender, DispatcherEventArgs<VBComponent> e)
354412
{
355-
if (!_handleSinkEvents) { return; }
413+
if (!_handleSinkEvents || !_vbe.IsInDesignMode()) { return; }
356414

357415
if (!_parser.State.AllDeclarations.Any())
358416
{
@@ -367,7 +425,7 @@ async void sink_ComponentAdded(object sender, DispatcherEventArgs<VBComponent> e
367425

368426
async void sink_ComponentActivated(object sender, DispatcherEventArgs<VBComponent> e)
369427
{
370-
if (!_handleSinkEvents) { return; }
428+
if (!_handleSinkEvents || !_vbe.IsInDesignMode()) { return; }
371429

372430
if (!_parser.State.AllDeclarations.Any())
373431
{
@@ -380,7 +438,7 @@ async void sink_ComponentActivated(object sender, DispatcherEventArgs<VBComponen
380438

381439
async void sink_ProjectRenamed(object sender, DispatcherRenamedEventArgs<VBProject> e)
382440
{
383-
if (!_handleSinkEvents) { return; }
441+
if (!_handleSinkEvents || !_vbe.IsInDesignMode()) { return; }
384442

385443
if (!_parser.State.AllDeclarations.Any())
386444
{
@@ -397,7 +455,7 @@ async void sink_ProjectRenamed(object sender, DispatcherRenamedEventArgs<VBProje
397455

398456
async void sink_ProjectActivated(object sender, DispatcherEventArgs<VBProject> e)
399457
{
400-
if (!_handleSinkEvents) { return; }
458+
if (!_handleSinkEvents || !_vbe.IsInDesignMode()) { return; }
401459

402460
if (!_parser.State.AllDeclarations.Any())
403461
{

RetailCoder.VBE/Common/ApplicationConstants.cs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -5,6 +5,7 @@ namespace Rubberduck.Common
55
{
66
public static class ApplicationConstants
77
{
8-
public static readonly string LOG_FOLDER_PATH = Path.Combine(Environment.GetFolderPath(Environment.SpecialFolder.ApplicationData), "Rubberduck", "Logs");
8+
public static readonly string RUBBERDUCK_FOLDER_PATH = Path.Combine(Environment.GetFolderPath(Environment.SpecialFolder.ApplicationData), "Rubberduck");
9+
public static readonly string LOG_FOLDER_PATH = Path.Combine(RUBBERDUCK_FOLDER_PATH, "Logs");
910
}
1011
}

RetailCoder.VBE/Common/WindowsOperatingSystem.cs

Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,11 +1,16 @@
11
using System.Diagnostics;
2+
using System.IO;
23

34
namespace Rubberduck.Common
45
{
56
public sealed class WindowsOperatingSystem : IOperatingSystem
67
{
78
public void ShowFolder(string folderPath)
89
{
10+
if (!Directory.Exists(folderPath))
11+
{
12+
Directory.CreateDirectory(folderPath);
13+
}
914
Process.Start(folderPath);
1015
}
1116
}

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/Inspections/ParameterCanBeByValInspection.cs

Lines changed: 0 additions & 17 deletions
Original file line numberDiff line numberDiff line change
@@ -18,23 +18,6 @@ public ParameterCanBeByValInspection(RubberduckParserState state)
1818
public override string Description { get { return InspectionsUI.ParameterCanBeByValInspectionName; } }
1919
public override CodeInspectionType InspectionType { get { return CodeInspectionType.CodeQualityIssues; } }
2020

21-
// if we don't want to suggest passing non-primitive types ByRef (i.e. object types and Variant), then we need this:
22-
private static readonly string[] PrimitiveTypes =
23-
{
24-
Tokens.Boolean,
25-
Tokens.Byte,
26-
Tokens.Date,
27-
Tokens.Decimal,
28-
Tokens.Double,
29-
Tokens.Long,
30-
Tokens.LongLong,
31-
Tokens.LongPtr,
32-
Tokens.Integer,
33-
Tokens.Single,
34-
Tokens.String,
35-
Tokens.StrPtr
36-
};
37-
3821
public override IEnumerable<InspectionResultBase> GetInspectionResults()
3922
{
4023
var declarations = UserDeclarations.ToList();

RetailCoder.VBE/Inspections/VariableTypeNotDeclaredInspectionResult.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -52,7 +52,7 @@ public override void Fix()
5252

5353
if (string.IsNullOrEmpty(originalInstruction))
5454
{
55-
fix = DeclareExplicitVariant(Context.Parent as VBAParser.ConstSubStmtContext, out originalInstruction);
55+
fix = DeclareExplicitVariant(Context as VBAParser.ConstSubStmtContext, out originalInstruction);
5656
}
5757

5858
if (string.IsNullOrEmpty(originalInstruction))

RetailCoder.VBE/Navigation/CodeExplorer/CodeExplorerViewModel.cs

Lines changed: 8 additions & 18 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

@@ -244,23 +245,6 @@ public ObservableCollection<CodeExplorerItemViewModel> Projects
244245
}
245246
}
246247

247-
private Declaration FindNewProjectDeclaration(string id)
248-
{
249-
return _state.AllUserDeclarations.SingleOrDefault(item =>
250-
item.ProjectId == id &&
251-
item.DeclarationType == DeclarationType.Project);
252-
}
253-
254-
private Declaration FindNewDeclaration(Declaration declaration)
255-
{
256-
return _state.AllUserDeclarations.SingleOrDefault(item =>
257-
item.ProjectId == declaration.ProjectId &&
258-
item.ComponentName == declaration.ComponentName &&
259-
item.ParentScope == declaration.ParentScope &&
260-
item.IdentifierName == declaration.IdentifierName &&
261-
item.DeclarationType == declaration.DeclarationType);
262-
}
263-
264248
private void ParserState_StateChanged(object sender, ParserStateEventArgs e)
265249
{
266250
if (Projects == null)
@@ -332,7 +316,10 @@ private void UpdateNodes(IEnumerable<CodeExplorerItemViewModel> oldList,
332316

333317
private void ParserState_ModuleStateChanged(object sender, Parsing.ParseProgressEventArgs e)
334318
{
335-
if (e.State != ParserState.Error)
319+
// if we are resolving references, we already have the declarations and don't need to display error
320+
if (!(e.State == ParserState.Error ||
321+
(e.State == ParserState.ResolverError &&
322+
e.OldState == ParserState.ResolvingDeclarations)))
336323
{
337324
return;
338325
}
@@ -456,6 +443,9 @@ private void SetErrorState(CodeExplorerItemViewModel itemNode, VBComponent compo
456443
private readonly ICommand _openDesignerCommand;
457444
public ICommand OpenDesignerCommand { get { return _openDesignerCommand; } }
458445

446+
private readonly ICommand _openProjectPropertiesCommand;
447+
public ICommand OpenProjectPropertiesCommand { get { return _openProjectPropertiesCommand; } }
448+
459449
private readonly ICommand _renameCommand;
460450
public ICommand RenameCommand { get { return _renameCommand; } }
461451

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.0.*")]
35-
[assembly: AssemblyFileVersion("2.0.0.0")]
34+
[assembly: AssemblyVersion("2.0.2.*")]
35+
[assembly: AssemblyFileVersion("2.0.2.0")]

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}"

0 commit comments

Comments
 (0)