Skip to content

Commit afbac3d

Browse files
committed
Abort update of components from file if one component type does not match
1 parent 75b9939 commit afbac3d

File tree

3 files changed

+196
-5
lines changed

3 files changed

+196
-5
lines changed

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

Lines changed: 26 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -41,11 +41,11 @@ public ImportCommand(
4141

4242
AddToCanExecuteEvaluation(SpecialEvaluateCanExecute);
4343

44-
_importableExtensions =
45-
vbe.Kind == VBEKind.Hosted
46-
? new List<string> {".bas", ".cls", ".frm", ".doccls"} // VBA
47-
: new List<string> {".bas", ".cls", ".frm", ".ctl", ".pag", ".dob"}; // VB6
44+
ComponentTypeForExtension = vbe.Kind == VBEKind.Hosted
45+
? VBAComponentTypeForExtension
46+
: VB6ComponentTypeForExtension;
4847

48+
_importableExtensions = ComponentTypeForExtension.Keys.ToList();
4949
_filterExtensions = string.Join("; ", _importableExtensions.Select(ext => $"*{ext}"));
5050

5151
AddToCanExecuteEvaluation(SpecialEvaluateCanExecute);
@@ -179,5 +179,27 @@ protected override void OnExecute(object parameter)
179179
targetProject.Dispose();
180180
}
181181
}
182+
183+
protected IDictionary<string, ComponentType> ComponentTypeForExtension { get; }
184+
185+
private static IDictionary<string, ComponentType> VBAComponentTypeForExtension = new Dictionary<string, ComponentType>
186+
{
187+
[".bas"] = ComponentType.StandardModule,
188+
[".cls"] = ComponentType.ClassModule,
189+
[".frm"] = ComponentType.UserForm
190+
//TODO: find out what ".doccls" corresponds to.
191+
//[".doccls"] = ???
192+
};
193+
194+
private static IDictionary<string, ComponentType> VB6ComponentTypeForExtension = new Dictionary<string, ComponentType>
195+
{
196+
[".bas"] = ComponentType.StandardModule,
197+
[".cls"] = ComponentType.ClassModule,
198+
[".frm"] = ComponentType.VBForm,
199+
//TODO: double check whether the guesses below are correct.
200+
[".ctl"] = ComponentType.UserControl,
201+
[".pag"] = ComponentType.PropPage,
202+
[".dob"] = ComponentType.DocObject,
203+
};
182204
}
183205
}

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

Lines changed: 13 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -47,7 +47,11 @@ protected override void ImportFiles(ICollection<string> filesToImport, IVBProjec
4747

4848
var modules = Modules(moduleNames, targetProject.ProjectId, finder);
4949

50-
//TODO: abort if the component type of the to be removed component does not match the file extension.
50+
if(!modules.All(kvp => HasMatchingFileExtension(kvp.Key, kvp.Value)))
51+
{
52+
//TODO: report this to the user.
53+
return;
54+
}
5155

5256
using (var components = targetProject.VBComponents)
5357
{
@@ -125,6 +129,14 @@ private bool ValuesAreUnique(Dictionary<string, string> moduleNames)
125129

126130
return null;
127131
}
132+
133+
private bool HasMatchingFileExtension(string filename, QualifiedModuleName module)
134+
{
135+
var fileExtension = Path.GetExtension(filename);
136+
return ComponentTypeForExtension.TryGetValue(fileExtension, out var componentType)
137+
? module.ComponentType.Equals(componentType)
138+
: false;
139+
}
128140
}
129141

130142
public interface IModuleNameFromFileExtractor

RubberduckTests/CodeExplorer/CodeExplorerViewModelTests.cs

Lines changed: 157 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -429,6 +429,163 @@ public void UpdateFromFile_ModuleThere_RemovesMatchingComponent()
429429
}
430430
}
431431

432+
[Category("Code Explorer")]
433+
[Test]
434+
public void UpdateFromFile_MultipleImports_DifferentNames()
435+
{
436+
const string path1 = @"C:\Users\Rubberduck\Desktop\StdModule1.bas";
437+
const string path2 = @"C:\Users\Rubberduck\Desktop\Class1.cls";
438+
const string path3 = @"C:\Users\Rubberduck\Desktop\StdModule2.bas";
439+
const string path4 = @"C:\Users\Rubberduck\Desktop\Class2.cls";
440+
441+
using (var explorer = new MockedCodeExplorer(
442+
ProjectType.HostProject,
443+
("TestModule", ComponentType.StandardModule, string.Empty),
444+
("OtherTestModule", ComponentType.StandardModule, string.Empty),
445+
("TestClass", ComponentType.ClassModule, string.Empty))
446+
.ConfigureOpenDialog(new[] { path1, path2, path3, path4 }, DialogResult.OK)
447+
.SelectFirstProject())
448+
{
449+
explorer.ExecuteUpdateFromFileCommand(filename =>
450+
{
451+
switch (filename)
452+
{
453+
case path1:
454+
return "TestModule";
455+
case path2:
456+
return "TestClass";
457+
case path3:
458+
return "NewModule";
459+
case path4:
460+
return "NewClass";
461+
default:
462+
return "YetAnotherModule";
463+
}
464+
});
465+
466+
var modulesNames = explorer
467+
.VbComponents
468+
.Object
469+
.Select(component => component.Name)
470+
.ToList();
471+
472+
explorer.VbComponents.Verify(c => c.Remove(It.IsAny<IVBComponent>()), Times.Exactly(2));
473+
explorer.VbComponents.Verify(c => c.Import(path1), Times.Once);
474+
explorer.VbComponents.Verify(c => c.Import(path2), Times.Once);
475+
explorer.VbComponents.Verify(c => c.Import(path3), Times.Once);
476+
explorer.VbComponents.Verify(c => c.Import(path4), Times.Once);
477+
478+
Assert.IsTrue(modulesNames.Contains("OtherTestModule"));
479+
//This depends on the setup of Import on the VBComponents mock, which determines the component name from the filename.
480+
Assert.IsTrue(modulesNames.Contains("StdModule1"));
481+
Assert.IsTrue(modulesNames.Contains("Class1"));
482+
Assert.IsTrue(modulesNames.Contains("StdModule2"));
483+
Assert.IsTrue(modulesNames.Contains("Class2"));
484+
Assert.IsFalse(modulesNames.Contains("TestModule"));
485+
Assert.IsFalse(modulesNames.Contains("TestClass"));
486+
}
487+
}
488+
489+
[Category("Code Explorer")]
490+
[Test]
491+
public void UpdateFromFile_MultipleImports_RepeatedModeuleName_Aborts()
492+
{
493+
const string path1 = @"C:\Users\Rubberduck\Desktop\StdModule1.bas";
494+
const string path2 = @"C:\Users\Rubberduck\Desktop\Class1.cls";
495+
const string path3 = @"C:\Users\Rubberduck\Desktop\StdModule2.bas";
496+
const string path4 = @"C:\Users\Rubberduck\Desktop\Class2.cls";
497+
498+
using (var explorer = new MockedCodeExplorer(
499+
ProjectType.HostProject,
500+
("TestModule", ComponentType.StandardModule, string.Empty),
501+
("OtherTestModule", ComponentType.StandardModule, string.Empty),
502+
("TestClass", ComponentType.ClassModule, string.Empty))
503+
.ConfigureOpenDialog(new[] { path1, path2, path3, path4 }, DialogResult.OK)
504+
.SelectFirstProject())
505+
{
506+
explorer.ExecuteUpdateFromFileCommand(filename =>
507+
{
508+
switch (filename)
509+
{
510+
case path1:
511+
return "TestModule";
512+
case path2:
513+
return "TestClass";
514+
case path3:
515+
return "TestModule";
516+
case path4:
517+
return "NewClass";
518+
default:
519+
return "YetAnotherModule";
520+
}
521+
});
522+
523+
var modulesNames = explorer
524+
.VbComponents
525+
.Object
526+
.Select(component => component.Name)
527+
.ToList();
528+
529+
explorer.VbComponents.Verify(c => c.Remove(It.IsAny<IVBComponent>()), Times.Never);
530+
explorer.VbComponents.Verify(c => c.Import(It.IsAny <string>()), Times.Never);
531+
532+
Assert.IsTrue(modulesNames.Contains("OtherTestModule"));
533+
Assert.IsTrue(modulesNames.Contains("TestModule"));
534+
Assert.IsTrue(modulesNames.Contains("TestClass"));
535+
Assert.AreEqual(3, modulesNames.Count);
536+
}
537+
}
538+
539+
[Category("Code Explorer")]
540+
[Test]
541+
public void UpdateFromFile_NonMatchingComponentType_Aborts()
542+
{
543+
const string path1 = @"C:\Users\Rubberduck\Desktop\StdModule1.cls";
544+
const string path2 = @"C:\Users\Rubberduck\Desktop\Class1.cls";
545+
const string path3 = @"C:\Users\Rubberduck\Desktop\StdModule2.bas";
546+
const string path4 = @"C:\Users\Rubberduck\Desktop\Class2.cls";
547+
548+
using (var explorer = new MockedCodeExplorer(
549+
ProjectType.HostProject,
550+
("TestModule", ComponentType.StandardModule, string.Empty),
551+
("OtherTestModule", ComponentType.StandardModule, string.Empty),
552+
("TestClass", ComponentType.ClassModule, string.Empty))
553+
.ConfigureOpenDialog(new[] { path1, path2, path3, path4 }, DialogResult.OK)
554+
.SelectFirstProject())
555+
{
556+
explorer.ExecuteUpdateFromFileCommand(filename =>
557+
{
558+
switch (filename)
559+
{
560+
case path1:
561+
return "TestModule";
562+
case path2:
563+
return "TestClass";
564+
case path3:
565+
return "NewModule";
566+
case path4:
567+
return "NewClass";
568+
default:
569+
return "YetAnotherModule";
570+
}
571+
});
572+
573+
var modulesNames = explorer
574+
.VbComponents
575+
.Object
576+
.Select(component => component.Name)
577+
.ToList();
578+
579+
explorer.VbComponents.Verify(c => c.Remove(It.IsAny<IVBComponent>()), Times.Never);
580+
explorer.VbComponents.Verify(c => c.Import(It.IsAny<string>()), Times.Never);
581+
582+
Assert.IsTrue(modulesNames.Contains("OtherTestModule"));
583+
Assert.IsTrue(modulesNames.Contains("TestModule"));
584+
Assert.IsTrue(modulesNames.Contains("TestClass"));
585+
Assert.AreEqual(3, modulesNames.Count);
586+
}
587+
}
588+
432589
[Category("Code Explorer")]
433590
[Test]
434591
public void UpdateFromFile_Cancel()

0 commit comments

Comments
 (0)