Skip to content

Commit 9be7204

Browse files
committed
Cleanup around the ImportCommand based on review comments to PR #5274
1 parent 8c84bb0 commit 9be7204

File tree

5 files changed

+27
-18
lines changed

5 files changed

+27
-18
lines changed

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

Lines changed: 20 additions & 15 deletions
Original file line numberDiff line numberDiff line change
@@ -35,7 +35,7 @@ public class ImportCommand : CodeExplorerCommandBase
3535
private readonly IParseManager _parseManager;
3636
private readonly IProjectsProvider _projectsProvider;
3737
private readonly IModuleNameFromFileExtractor _moduleNameFromFileExtractor;
38-
private readonly IDictionary<ComponentType, IRequiredBinaryFilesFromFileNameExtractor> _binaryFileExtractors;
38+
private readonly IDictionary<ComponentType, List<IRequiredBinaryFilesFromFileNameExtractor>> _binaryFileExtractors;
3939
private readonly IFileExistenceChecker _fileExistenceChecker;
4040

4141
protected readonly IDeclarationFinderProvider DeclarationFinderProvider;
@@ -58,13 +58,13 @@ public ImportCommand(
5858
_dialogFactory = dialogFactory;
5959
_parseManager = parseManager;
6060
_projectsProvider = projectsProvider;
61-
DeclarationFinderProvider = declarationFinderProvider;
6261
_moduleNameFromFileExtractor = moduleNameFromFileExtractor;
6362
_fileExistenceChecker = fileExistenceChecker;
6463

6564
_binaryFileExtractors = BinaryFileExtractors(binaryFileExtractors);
6665

6766
MessageBox = messageBox;
67+
DeclarationFinderProvider = declarationFinderProvider;
6868

6969
AddToCanExecuteEvaluation(SpecialEvaluateCanExecute);
7070

@@ -123,19 +123,19 @@ private IVBProject TargetProjectFromVbe()
123123
: null;
124124
}
125125

126-
private IDictionary<ComponentType, IRequiredBinaryFilesFromFileNameExtractor> BinaryFileExtractors(IEnumerable<IRequiredBinaryFilesFromFileNameExtractor> extractors)
126+
private IDictionary<ComponentType, List<IRequiredBinaryFilesFromFileNameExtractor>> BinaryFileExtractors(IEnumerable<IRequiredBinaryFilesFromFileNameExtractor> extractors)
127127
{
128-
var dict = new Dictionary<ComponentType, IRequiredBinaryFilesFromFileNameExtractor>();
128+
var dict = new Dictionary<ComponentType, List<IRequiredBinaryFilesFromFileNameExtractor>>();
129129
foreach (var extractor in extractors)
130130
{
131131
foreach (var componentType in extractor.SupportedComponentTypes)
132-
{
133-
if (dict.ContainsKey(componentType))
132+
{
133+
if (!dict.ContainsKey(componentType))
134134
{
135-
continue;
135+
dict.Add(componentType, new List<IRequiredBinaryFilesFromFileNameExtractor>());
136136
}
137137

138-
dict.Add(componentType, extractor);
138+
dict[componentType].Add(extractor);
139139
}
140140
}
141141

@@ -164,8 +164,7 @@ protected virtual ICollection<string> FilesToImport(object parameter)
164164

165165
var fileNames = dialog.FileNames;
166166
var fileExtensions = fileNames.Select(Path.GetExtension);
167-
var importableExtensions = ImportableExtensions;
168-
if (fileExtensions.Any(fileExt => !importableExtensions.Contains(fileExt)))
167+
if (fileExtensions.Any(fileExt => !ImportableExtensions.Contains(fileExt)))
169168
{
170169
NotifyUserAboutAbortDueToUnsupportedFileExtensions(fileNames);
171170
return new List<string>();
@@ -177,6 +176,7 @@ protected virtual ICollection<string> FilesToImport(object parameter)
177176

178177
protected virtual string DialogsTitle => RubberduckUI.ImportCommand_OpenDialog_Title;
179178

179+
//TODO: Gather all conflicts and report them in one error dialog instead of reporting them one at a time.
180180
private void NotifyUserAboutAbortDueToUnsupportedFileExtensions(IEnumerable<string> fileNames)
181181
{
182182
var firstUnsupportedFile = fileNames.First(filename => !ImportableExtensions.Contains(Path.GetExtension(filename)));
@@ -193,6 +193,7 @@ private void ImportFilesWithSuspension(ICollection<string> filesToImport, IVBPro
193193
{
194194
if (suspendOutcome == SuspensionOutcome.UnexpectedError || suspendOutcome == SuspensionOutcome.Canceled)
195195
{
196+
//This rethrows the exception with the original stack trace.
196197
ExceptionDispatchInfo.Capture(suspendResult.EncounteredException).Throw();
197198
return;
198199
}
@@ -382,16 +383,19 @@ private Dictionary<string, ICollection<string>> RequiredBinaryFiles(ICollection<
382383
private ICollection<string> RequiredBinaryFiles(string filename)
383384
{
384385
var extension = Path.GetExtension(filename);
385-
if (!ComponentTypesForExtension.TryGetValue(extension, out var componentTypes))
386+
if (extension == null || !ComponentTypesForExtension.TryGetValue(extension, out var componentTypes))
386387
{
387388
return new List<string>();
388389
}
389390

390391
foreach (var componentType in componentTypes)
391392
{
392-
if (_binaryFileExtractors.TryGetValue(componentType, out var binaryExtractor))
393+
if (_binaryFileExtractors.TryGetValue(componentType, out var binaryExtractors))
393394
{
394-
return binaryExtractor.RequiredBinaryFiles(filename, componentType);
395+
return binaryExtractors
396+
.SelectMany(binaryExtractor => binaryExtractor
397+
.RequiredBinaryFiles(filename, componentType))
398+
.ToHashSet();
395399
}
396400
}
397401

@@ -523,8 +527,8 @@ protected override void OnExecute(object parameter)
523527
}
524528

525529

526-
//We only allow extensions to be imported for which we might be able to determine that the conditions are met to actually import the file.
527-
//The exception are specif exceptions to the rule.
530+
//We usually only allow extensions to be imported for which we might be able to determine that the conditions are met to actually import the file.
531+
//However, we ignore this cautionary rule for the extensions specified in AlwaysImportableExtensions;
528532
protected ICollection<string> ImportableExtensions =>
529533
ComponentTypesForExtension.Keys
530534
.Where(fileExtension => ComponentTypesForExtension.TryGetValue(fileExtension, out var componentTypes)
@@ -534,6 +538,7 @@ protected override void OnExecute(object parameter)
534538
.Concat(AlwaysImportableExtensions)
535539
.ToHashSet();
536540

541+
//TODO: Implement the binary extractors necessary to allow us to remove this member.
537542
protected virtual IEnumerable<string> AlwaysImportableExtensions => _vbe.Kind == VBEKind.Standalone
538543
? ComponentTypesForExtension.Keys
539544
: Enumerable.Empty<string>();

Rubberduck.Parsing/VBA/DeclarationResolving/DeclarationResolveRunner.cs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -56,6 +56,7 @@ protected override void ResolveDeclarations(IReadOnlyCollection<QualifiedModuleN
5656
{
5757
if (exception.Flatten().InnerExceptions.All(ex => ex is OperationCanceledException))
5858
{
59+
//This rethrows the exception with the original stack trace.
5960
ExceptionDispatchInfo.Capture(exception.InnerException ?? exception).Throw();
6061
}
6162
_parserStateManager.SetStatusAndFireStateChanged(this, ParserState.ResolverError, token);

Rubberduck.Parsing/VBA/Parsing/ParseRunner.cs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -62,6 +62,7 @@ public ParseRunner(
6262
{
6363
if (exception.Flatten().InnerExceptions.All(ex => ex is OperationCanceledException))
6464
{
65+
//This rethrows the exception with the original stack trace.
6566
ExceptionDispatchInfo.Capture(exception.InnerException ?? exception).Throw();
6667
}
6768
StateManager.SetStatusAndFireStateChanged(this, ParserState.Error, token);

Rubberduck.Parsing/VBA/ReferenceManagement/ReferenceResolveRunner.cs

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -42,6 +42,7 @@ protected override void ResolveReferences(ICollection<KeyValuePair<QualifiedModu
4242
{
4343
if (exception.Flatten().InnerExceptions.All(ex => ex is OperationCanceledException))
4444
{
45+
//This rethrows the exception with the original stack trace.
4546
ExceptionDispatchInfo.Capture(exception.InnerException ?? exception).Throw();
4647
}
4748

@@ -70,7 +71,8 @@ protected override void AddModuleToModuleReferences(DeclarationFinder finder, Ca
7071
{
7172
if (exception.Flatten().InnerExceptions.All(ex => ex is OperationCanceledException))
7273
{
73-
throw exception.InnerException ?? exception; //This eliminates the stack trace, but for the cancellation, this is irrelevant.
74+
//This rethrows the exception with the original stack trace.
75+
ExceptionDispatchInfo.Capture(exception.InnerException ?? exception).Throw();
7476
}
7577

7678
_parserStateManager.SetStatusAndFireStateChanged(this, ParserState.ResolverError, token);

Rubberduck.Resources/RubberduckUI.de.resx

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1538,12 +1538,12 @@ Import abgebrochen.</value>
15381538
Import abgebrochen.</value>
15391539
</data>
15401540
<data name="ImportCommand_BinaryAndComponentDoNotExist" xml:space="preserve">
1541-
<value>Für die Datei '{0}' fehlen die benötigte(n) Binary-Datei(en) '{1}' und die Zielkomponente '{2}'existiert noch nicht.
1541+
<value>Für die Datei '{0}' fehlen die benötigte(n) Binärdatei(en) '{1}' und die Zielkomponente '{2}' existiert noch nicht.
15421542

15431543
Import abgebrochen.</value>
15441544
</data>
15451545
<data name="ImportCommand_BinaryDoesNotExist" xml:space="preserve">
1546-
<value>Für die Datei '{0}' fehlen die benötigte(n) Binary-Datei(en) '{1}'.
1546+
<value>Für die Datei '{0}' fehlen die benötigte(n) Binärdatei(en) '{1}'.
15471547

15481548
Import abgebrochen.</value>
15491549
</data>

0 commit comments

Comments
 (0)