Skip to content

Commit 75b9939

Browse files
committed
Introduce UpdateFromFilesCommand
It removes existing modules with the module name of a file to be imported before importing from file. Failure reporting to the user is still missing.
1 parent 5d20c1a commit 75b9939

File tree

6 files changed

+308
-11
lines changed

6 files changed

+308
-11
lines changed

Rubberduck.Core/Navigation/CodeExplorer/CodeExplorerViewModel.cs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -385,6 +385,7 @@ private void ExecuteRemoveCommand(object param)
385385
public CopyResultsCommand CopyResultsCommand { get; set; }
386386
public CommandBase ExpandAllSubnodesCommand { get; }
387387
public ImportCommand ImportCommand { get; set; }
388+
public UpdateFromFilesCommand UpdateFromFilesCommand { get; set; }
388389
public ExportCommand ExportCommand { get; set; }
389390
public ExportAllCommand ExportAllCommand { get; set; }
390391
public DeleteCommand DeleteCommand { get; set; }

Rubberduck.Core/UI/CodeExplorer/Commands/ImportCommand.cs

Lines changed: 5 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -43,10 +43,10 @@ public ImportCommand(
4343

4444
_importableExtensions =
4545
vbe.Kind == VBEKind.Hosted
46-
? new List<string> {"bas", "cls", "frm", "doccls"} // VBA
47-
: new List<string> {"bas", "cls", "frm", "ctl", "pag", "dob"}; // VB6
46+
? new List<string> {".bas", ".cls", ".frm", ".doccls"} // VBA
47+
: new List<string> {".bas", ".cls", ".frm", ".ctl", ".pag", ".dob"}; // VB6
4848

49-
_filterExtensions = string.Join("; ", _importableExtensions.Select(ext => $"*.{ext}"));
49+
_filterExtensions = string.Join("; ", _importableExtensions.Select(ext => $"*{ext}"));
5050

5151
AddToCanExecuteEvaluation(SpecialEvaluateCanExecute);
5252
AddToOnExecuteEvaluation(SpecialEvaluateCanExecute);
@@ -125,6 +125,7 @@ protected virtual ICollection<string> FilesToImport(object parameter)
125125
var fileExtensions = fileNames.Select(Path.GetExtension);
126126
if (fileExtensions.Any(fileExt => !_importableExtensions.Contains(fileExt)))
127127
{
128+
//TODO: report this to the user.
128129
return new List<string>();
129130
}
130131

@@ -134,7 +135,7 @@ protected virtual ICollection<string> FilesToImport(object parameter)
134135

135136
protected virtual string FileDialogTitle => RubberduckUI.ImportCommand_OpenDialog_Title;
136137

137-
private void ImportFilesWithSuspension(IEnumerable<string> filesToImport, IVBProject targetProject)
138+
private void ImportFilesWithSuspension(ICollection<string> filesToImport, IVBProject targetProject)
138139
{
139140
var suspensionResult = _parseManager.OnSuspendParser(this, new[] {ParserState.Ready}, () => ImportFiles(filesToImport, targetProject));
140141
if (suspensionResult != SuspensionResult.Completed)
Lines changed: 155 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,155 @@
1+
using System.Collections.Generic;
2+
using System.IO;
3+
using System.Linq;
4+
using System.Text;
5+
using Rubberduck.Parsing.VBA;
6+
using Rubberduck.Parsing.VBA.DeclarationCaching;
7+
using Rubberduck.VBEditor;
8+
using Rubberduck.VBEditor.Events;
9+
using Rubberduck.VBEditor.ComManagement;
10+
using Rubberduck.VBEditor.Extensions;
11+
using Rubberduck.VBEditor.SafeComWrappers.Abstract;
12+
13+
namespace Rubberduck.UI.CodeExplorer.Commands
14+
{
15+
public class UpdateFromFilesCommand : ImportCommand
16+
{
17+
private readonly IDeclarationFinderProvider _declarationFinderProvider;
18+
private readonly IProjectsProvider _projectsProvider;
19+
private readonly IModuleNameFromFileExtractor _moduleNameFromFileExtractor;
20+
21+
public UpdateFromFilesCommand(
22+
IVBE vbe,
23+
IFileSystemBrowserFactory dialogFactory,
24+
IVbeEvents vbeEvents,
25+
IParseManager parseManager,
26+
IDeclarationFinderProvider declarationFinderProvider,
27+
IProjectsProvider projectsProvider,
28+
IModuleNameFromFileExtractor moduleNameFromFileExtractor)
29+
: base(vbe, dialogFactory, vbeEvents, parseManager)
30+
{
31+
_projectsProvider = projectsProvider;
32+
_declarationFinderProvider = declarationFinderProvider;
33+
_moduleNameFromFileExtractor = moduleNameFromFileExtractor;
34+
}
35+
36+
protected override void ImportFiles(ICollection<string> filesToImport, IVBProject targetProject)
37+
{
38+
var finder = _declarationFinderProvider.DeclarationFinder;
39+
40+
var moduleNames = ModuleNames(filesToImport);
41+
42+
if (!ValuesAreUnique(moduleNames))
43+
{
44+
//TODO: report this to the user.
45+
return;
46+
}
47+
48+
var modules = Modules(moduleNames, targetProject.ProjectId, finder);
49+
50+
//TODO: abort if the component type of the to be removed component does not match the file extension.
51+
52+
using (var components = targetProject.VBComponents)
53+
{
54+
foreach (var filename in filesToImport)
55+
{
56+
if (modules.TryGetValue(filename, out var module))
57+
{
58+
var component = _projectsProvider.Component(module);
59+
components.Remove(component);
60+
}
61+
62+
//We have to dispose the return value.
63+
using (components.Import(filename)) { }
64+
}
65+
}
66+
}
67+
68+
private Dictionary<string, string> ModuleNames(ICollection<string> filenames)
69+
{
70+
var moduleNames = new Dictionary<string, string>();
71+
foreach(var filename in filenames)
72+
{
73+
if (moduleNames.ContainsKey(filename))
74+
{
75+
continue;
76+
}
77+
78+
var moduleName = ModuleName(filename);
79+
if(moduleName != null)
80+
{
81+
moduleNames.Add(filename, moduleName);
82+
}
83+
}
84+
85+
return moduleNames;
86+
}
87+
88+
private string ModuleName(string filename)
89+
{
90+
return _moduleNameFromFileExtractor.ModuleName(filename);
91+
}
92+
93+
private Dictionary<string, QualifiedModuleName> Modules(IDictionary<string, string> moduleNames, string projectId, DeclarationFinder finder)
94+
{
95+
var modules = new Dictionary<string, QualifiedModuleName>();
96+
foreach (var (fileName, moduleName) in moduleNames)
97+
{
98+
var module = Module(moduleName, projectId, finder);
99+
if (module.HasValue)
100+
{
101+
modules.Add(fileName, module.Value);
102+
}
103+
}
104+
105+
return modules;
106+
}
107+
108+
private bool ValuesAreUnique(Dictionary<string, string> moduleNames)
109+
{
110+
return moduleNames
111+
.GroupBy(kvp => kvp.Value)
112+
.All(moduleNameGroup => moduleNameGroup.Count() == 1);
113+
}
114+
115+
private QualifiedModuleName? Module(string moduleName, string projectId, DeclarationFinder finder)
116+
{
117+
foreach(var module in finder.AllModules)
118+
{
119+
if(module.ProjectId.Equals(projectId)
120+
&& module.ComponentName.Equals(moduleName))
121+
{
122+
return module;
123+
}
124+
}
125+
126+
return null;
127+
}
128+
}
129+
130+
public interface IModuleNameFromFileExtractor
131+
{
132+
string ModuleName(string filename);
133+
}
134+
135+
public class ModuleNameFromFileExtractor : IModuleNameFromFileExtractor
136+
{
137+
public string ModuleName(string filename)
138+
{
139+
if (!File.Exists(filename))
140+
{
141+
return null;
142+
}
143+
144+
var contents = File.ReadLines(filename, Encoding.Default);
145+
var nameLine = contents.FirstOrDefault(line => line.StartsWith("Attribute VB_Name = "));
146+
if (nameLine == null)
147+
{
148+
return Path.GetFileNameWithoutExtension(filename);
149+
}
150+
151+
//The format is Attribute VB_Name = "ModuleName"
152+
return nameLine.Substring("Attribute VB_Name = ".Length + 1, nameLine.Length - "Attribute VB_Name = ".Length - 2);
153+
}
154+
}
155+
}

RubberduckTests/CodeExplorer/CodeExplorerViewModelTests.cs

Lines changed: 99 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -13,6 +13,8 @@
1313
using Rubberduck.Parsing.VBA;
1414
using Rubberduck.UI.Command.ComCommands;
1515
using RubberduckTests.Mocks;
16+
using Rubberduck.VBEditor.SafeComWrappers.Abstract;
17+
using Rubberduck.Parsing.Symbols;
1618

1719
namespace RubberduckTests.CodeExplorer
1820
{
@@ -337,11 +339,107 @@ public void ImportModule_Cancel()
337339
{
338340
const string path = @"C:\Users\Rubberduck\Desktop\StdModule1.bas";
339341

342+
using (var explorer = new MockedCodeExplorer(ProjectType.HostProject)
343+
.ConfigureSaveDialog(path, DialogResult.Cancel)
344+
.SelectFirstModule())
345+
{
346+
explorer.ExecuteImportCommand();
347+
explorer.VbComponents.Verify(c => c.Import(path), Times.Never);
348+
}
349+
}
350+
351+
[Category("Code Explorer")]
352+
[Test]
353+
public void UpdateFromFile_ModuleNotThere_Imports()
354+
{
355+
const string path = @"C:\Users\Rubberduck\Desktop\StdModule1.bas";
356+
357+
using (var explorer = new MockedCodeExplorer(
358+
ProjectType.HostProject,
359+
("TestModule", ComponentType.StandardModule, string.Empty))
360+
.ConfigureOpenDialog(new[] { path }, DialogResult.OK)
361+
.SelectFirstProject())
362+
{
363+
explorer.ExecuteUpdateFromFileCommand(filename => "SomeOtherModule");
364+
explorer.VbComponents.Verify(c => c.Import(path), Times.Once);
365+
}
366+
}
367+
368+
[Category("Code Explorer")]
369+
[Test]
370+
public void UpdateFromFile_ModuleThere_Imports()
371+
{
372+
const string path = @"C:\Users\Rubberduck\Desktop\StdModule1.bas";
373+
374+
using (var explorer = new MockedCodeExplorer(
375+
ProjectType.HostProject,
376+
("TestModule", ComponentType.StandardModule, string.Empty))
377+
.ConfigureOpenDialog(new[] { path }, DialogResult.OK)
378+
.SelectFirstProject())
379+
{
380+
explorer.ExecuteUpdateFromFileCommand(filename => "TestModule");
381+
explorer.VbComponents.Verify(c => c.Import(path), Times.Once);
382+
}
383+
}
384+
385+
[Category("Code Explorer")]
386+
[Test]
387+
public void UpdateFromFile_ModuleNotThere_DoesNotRemove()
388+
{
389+
const string path = @"C:\Users\Rubberduck\Desktop\StdModule1.bas";
390+
391+
using (var explorer = new MockedCodeExplorer(
392+
ProjectType.HostProject,
393+
("TestModule", ComponentType.StandardModule, string.Empty))
394+
.ConfigureOpenDialog(new[] { path }, DialogResult.OK)
395+
.SelectFirstProject())
396+
{
397+
explorer.ExecuteUpdateFromFileCommand(filename => "SomeOtherModule");
398+
explorer.VbComponents.Verify(c => c.Remove(It.IsAny<IVBComponent>()), Times.Never);
399+
}
400+
}
401+
402+
[Category("Code Explorer")]
403+
[Test]
404+
public void UpdateFromFile_ModuleThere_RemovesMatchingComponent()
405+
{
406+
const string path = @"C:\Users\Rubberduck\Desktop\StdModule1.bas";
407+
408+
using (var explorer = new MockedCodeExplorer(
409+
ProjectType.HostProject,
410+
("TestModule", ComponentType.StandardModule, string.Empty),
411+
("OtherTestModule", ComponentType.StandardModule, string.Empty))
412+
.ConfigureOpenDialog(new[] { path }, DialogResult.OK)
413+
.SelectFirstProject())
414+
{
415+
explorer.ExecuteUpdateFromFileCommand(filename => filename == path ? "TestModule" : "YetAnotherModule");
416+
417+
var modulesNames = explorer
418+
.VbComponents
419+
.Object
420+
.Select(component => component.Name)
421+
.ToList();
422+
423+
explorer.VbComponents.Verify(c => c.Remove(It.IsAny<IVBComponent>()), Times.Once);
424+
425+
Assert.IsTrue(modulesNames.Contains("OtherTestModule"));
426+
//This depends on the setup of Import on the VBComponents mock, which determines the component name from the filename.
427+
Assert.IsTrue(modulesNames.Contains("StdModule1"));
428+
Assert.IsFalse(modulesNames.Contains("TestModule"));
429+
}
430+
}
431+
432+
[Category("Code Explorer")]
433+
[Test]
434+
public void UpdateFromFile_Cancel()
435+
{
436+
const string path = @"C:\Users\Rubberduck\Desktop\StdModule1.bas";
437+
340438
using (var explorer = new MockedCodeExplorer(ProjectType.HostProject)
341439
.ConfigureOpenDialog(new[] { path }, DialogResult.Cancel)
342440
.SelectFirstProject())
343441
{
344-
explorer.ExecuteImportCommand();
442+
explorer.ExecuteUpdateFromFileCommand(filename => filename);
345443
explorer.VbComponents.Verify(c => c.Import(path), Times.Never);
346444
}
347445
}

RubberduckTests/CodeExplorer/MockedCodeExplorer.cs

Lines changed: 41 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -136,6 +136,39 @@ public MockedCodeExplorer(ProjectType projectType,
136136
VbProject.SetupGet(m => m.VBComponents.Count).Returns(componentTypes.Count);
137137
}
138138

139+
public MockedCodeExplorer(
140+
ProjectType projectType,
141+
params (string componentName, ComponentType componentTypes, string code)[] modules)
142+
: this()
143+
{
144+
var builder = new MockVbeBuilder();
145+
var project = builder.ProjectBuilder("TestProject1", ProjectProtection.Unprotected, projectType);
146+
147+
for (var index = 0; index < modules.Length; index++)
148+
{
149+
var (name, componentType, code) = modules[index];
150+
if (componentType == ComponentType.UserForm)
151+
{
152+
project.MockUserFormBuilder(name, code).AddFormToProjectBuilder();
153+
}
154+
else
155+
{
156+
project.AddComponent(name, componentType, code);
157+
}
158+
}
159+
160+
VbComponents = project.MockVBComponents;
161+
VbComponent = project.MockComponents.First();
162+
VbProject = project.Build();
163+
Vbe = builder.AddProject(VbProject).Build();
164+
VbeEvents = MockVbeEvents.CreateMockVbeEvents(Vbe);
165+
ProjectsRepository = new Mock<IProjectsRepository>();
166+
ProjectsRepository.Setup(x => x.Project(It.IsAny<string>())).Returns(VbProject.Object);
167+
ProjectsRepository.Setup(x => x.Component(It.IsAny<QualifiedModuleName>())).Returns(VbComponent.Object);
168+
169+
SetupViewModelAndParse();
170+
}
171+
139172
private void SetupViewModelAndParse()
140173
{
141174
var vbeEvents = MockVbeEvents.CreateMockVbeEvents(Vbe);
@@ -343,6 +376,14 @@ public void ExecuteImportCommand()
343376
ViewModel.ImportCommand.Execute(ViewModel.SelectedItem);
344377
}
345378

379+
public void ExecuteUpdateFromFileCommand(Func<string, string> fileNameToModuleNameConverter)
380+
{
381+
var mockModuleNameExtractor = new Mock<IModuleNameFromFileExtractor>();
382+
mockModuleNameExtractor.Setup(m => m.ModuleName(It.IsAny<string>())).Returns((string filename) => fileNameToModuleNameConverter(filename));
383+
ViewModel.UpdateFromFilesCommand = new UpdateFromFilesCommand(Vbe.Object, BrowserFactory.Object, VbeEvents.Object, State, State, State.ProjectsProvider, mockModuleNameExtractor.Object);
384+
ViewModel.UpdateFromFilesCommand.Execute(ViewModel.SelectedItem);
385+
}
386+
346387
public void ExecuteExportAllCommand()
347388
{
348389
if (ViewModel.ExportAllCommand is null)

0 commit comments

Comments
 (0)