Skip to content

Commit

Permalink
Add inital ReferenceSettings support.
Browse files Browse the repository at this point in the history
  • Loading branch information
comintern committed Dec 9, 2018
1 parent c92d7f5 commit 9bc9d80
Show file tree
Hide file tree
Showing 17 changed files with 730 additions and 173 deletions.
67 changes: 51 additions & 16 deletions Rubberduck.Core/AddRemoveReferences/ReferenceModel.cs
Expand Up @@ -15,19 +15,35 @@ namespace Rubberduck.AddRemoveReferences
public class ReferenceModel : INotifyPropertyChanged
{
public event PropertyChangedEventHandler PropertyChanged;

private ReferenceModel()
{
_info = new Lazy<ReferenceInfo>(GenerateInfo);
}

public ReferenceModel(IVBProject project, int priority)
public ReferenceModel(ReferenceInfo info, bool recent = false, bool pinned = false) : this()
{
Guid = info.Guid;
Name = info.Name;
FullPath = info.FullPath;
Major = info.Major;
Minor = info.Minor;
IsRecent = recent;
IsPinned = pinned;
}

public ReferenceModel(IVBProject project, int priority) : this()
{
Name = project.Name ?? string.Empty;
Priority = priority;
Guid = Guid.Empty;
Description = project.Description ?? string.Empty;
FullPath = project.FileName ?? string.Empty;
IsBuiltIn = false;
Type = ReferenceKind.Project;
Type = ReferenceKind.Project;
}

public ReferenceModel(RegisteredLibraryInfo info)
public ReferenceModel(RegisteredLibraryInfo info) : this()
{
Name = info.Name ?? string.Empty;
Guid = info.Guid;
Expand All @@ -50,11 +66,11 @@ public ReferenceModel(RegisteredLibraryInfo info, IReference reference, int prio
IsReferenced = true;
}

public ReferenceModel(IReference reference, int priority)
public ReferenceModel(IReference reference, int priority) : this()
{
Priority = priority;
Name = reference.Name;
Guid = new Guid(reference.Guid);
Guid = Guid.TryParse(reference.Guid, out var guid) ? guid : Guid.Empty;
Description = string.IsNullOrEmpty(reference.Description) ? Path.GetFileNameWithoutExtension(reference.FullPath) : reference.Description;
Major = reference.Major;
Minor = reference.Minor;
Expand All @@ -65,7 +81,7 @@ public ReferenceModel(IReference reference, int priority)
Type = reference.Type;
}

public ReferenceModel(ITypeLib reference)
public ReferenceModel(ITypeLib reference) : this()
{
var documentation = new ComDocumentation(reference, -1);
Name = documentation.Name;
Expand All @@ -83,10 +99,21 @@ public ReferenceModel(ITypeLib reference)
}
}

public ReferenceModel(string path)
public ReferenceModel(string path, bool broken = false) : this()
{
FullPath = path;
Name = Path.GetFileName(path);
try
{
Name = Path.GetFileName(path);
Description = Name;
}
catch
{
// Yeah, that's probably busted.
IsBroken = true;
}

IsBroken = broken;
}

private bool _pinned;
Expand All @@ -106,19 +133,19 @@ public bool IsPinned

public int? Priority { get; set; }

public string Name { get; }
public string Name { get; } = string.Empty;
public Guid Guid { get; }
public string Description { get; }
public string FullPath { get; }
public string LocaleName { get; }
public string Description { get; } = string.Empty;
public string FullPath { get; } = string.Empty;
public string LocaleName { get; } = string.Empty;

public bool IsBuiltIn { get; }
public bool IsBroken { get; }
public TypeLibTypeFlags Flags { get; set; }
public ReferenceKind Type { get; }

private string FullPath32 { get; }
private string FullPath64 { get; }
private string FullPath32 { get; } = string.Empty;
private string FullPath64 { get; } = string.Empty;
public int Major { get; set; }
public int Minor { get; set; }
public string Version => $"{Major}.{Minor}";
Expand Down Expand Up @@ -147,9 +174,17 @@ public ReferenceStatus Status
}
}

public ReferenceInfo ToReferenceInfo()
private readonly Lazy<ReferenceInfo> _info;
private ReferenceInfo GenerateInfo() => new ReferenceInfo(Guid, Name, FullPath, Major, Minor);
public ReferenceInfo ToReferenceInfo() => _info.Value;

public bool Matches(ReferenceInfo info)
{
return new ReferenceInfo(Guid, Name, FullPath, Major, Minor);
return Major == info.Major && Minor == info.Minor &&
FullPath.Equals(info.FullPath, StringComparison.OrdinalIgnoreCase) ||
FullPath32.Equals(info.FullPath, StringComparison.OrdinalIgnoreCase) ||
FullPath64.Equals(info.FullPath, StringComparison.OrdinalIgnoreCase) ||
Guid.Equals(info.Guid);
}

private void NotifyPropertyChanged([CallerMemberName] string propertyName = "")
Expand Down
70 changes: 57 additions & 13 deletions Rubberduck.Core/AddRemoveReferences/ReferenceReconciler.cs
@@ -1,18 +1,14 @@
using System;
using System.Collections.Generic;
using System.Collections.Generic;
using System.IO;
using System.Linq;
using System.Runtime.InteropServices;
using System.Text;
using System.Threading.Tasks;
using Rubberduck.Interaction;
using Rubberduck.Parsing.ComReflection;
using Rubberduck.Parsing.Symbols;
using Rubberduck.Resources;
using Rubberduck.Settings;
using Rubberduck.SettingsProvider;
using Rubberduck.UI.AddRemoveReferences;
using Rubberduck.VBEditor.SafeComWrappers.Abstract;
using Rubberduck.VBEditor.Utility;

namespace Rubberduck.AddRemoveReferences
{
Expand All @@ -23,15 +19,16 @@ public interface IReferenceReconciler
ReferenceModel TryAddReference(IVBProject project, string path);
ReferenceModel TryAddReference(IVBProject project, ReferenceModel reference);
ReferenceModel GetLibraryInfoFromPath(string path);
void UpdateSettings(IAddRemoveReferencesModel model, bool recent = false);
}

public class ReferenceReconciler : IReferenceReconciler
{
private readonly IMessageBox _messageBox;
private readonly IConfigProvider<GeneralSettings> _settings;
private readonly IConfigProvider<ReferenceSettings> _settings;
private readonly IComLibraryProvider _tlbProvider;

public ReferenceReconciler(IMessageBox messageBox, IConfigProvider<GeneralSettings> settings, IComLibraryProvider tlbProvider)
public ReferenceReconciler(IMessageBox messageBox, IConfigProvider<ReferenceSettings> settings, IComLibraryProvider tlbProvider)
{
_messageBox = messageBox;
_settings = settings;
Expand All @@ -40,11 +37,22 @@ public ReferenceReconciler(IMessageBox messageBox, IConfigProvider<GeneralSettin

public void ReconcileReferences(IAddRemoveReferencesModel model)
{
if (model?.NewReferences is null || !model.NewReferences.Any())
{
return;
}

ReconcileReferences(model, model.NewReferences.ToList());
}

//TODO test for simple adds.
public List<ReferenceModel> ReconcileReferences(IAddRemoveReferencesModel model, List<ReferenceModel> allReferences)
{
if (model is null || allReferences is null || !allReferences.Any())
{
return new List<ReferenceModel>();
}

var selected = allReferences.Where(reference => !reference.IsBuiltIn && reference.Priority.HasValue)
.ToDictionary(reference => reference.FullPath);

Expand All @@ -67,25 +75,38 @@ public List<ReferenceModel> ReconcileReferences(IAddRemoveReferencesModel model,
reference.Dispose();
}
}

output.AddRange(selected.Values.OrderBy(selection => selection.Priority)
.Select(reference => TryAddReference(project, reference)).Where(added => added != null));
}

UpdateSettings(model, true);
return output;
}

private static readonly List<string> InterestingExtensions = new List<string> { ".olb", ".tlb", ".dll", ".ocx", ".exe" };

public ReferenceModel GetLibraryInfoFromPath(string path)
{
try
{
return new ReferenceModel(_tlbProvider.LoadTypeLibrary(path));
var extension = Path.GetExtension(path)?.ToLowerInvariant() ?? string.Empty;
if (string.IsNullOrEmpty(extension))
{
return null;
}

// LoadTypeLibrary will attempt to open files in the host, so only attempt on possible COM servers.
if (InterestingExtensions.Contains(extension))
{
return new ReferenceModel(_tlbProvider.LoadTypeLibrary(path));
}
return new ReferenceModel(path);
}
catch
{
// Most likely this is a project. If not, it we can't fail here because it could have come from the Apply
// Most likely this is unloadable. If not, it we can't fail here because it could have come from the Apply
// button in the AddRemoveReferencesDialog. Wait for it... :-P
return new ReferenceModel(path);
return new ReferenceModel(path, true);
}
}

Expand All @@ -97,7 +118,7 @@ public ReferenceModel TryAddReference(IVBProject project, string path)
{
using (var reference = references.AddFromFile(path))
{
return reference is null ? null : new ReferenceModel(reference, references.Count);
return reference is null ? null : new ReferenceModel(reference, references.Count) { IsRecent = true };
}
}
catch (COMException ex)
Expand All @@ -117,6 +138,7 @@ public ReferenceModel TryAddReference(IVBProject project, ReferenceModel referen
using (references.AddFromFile(reference.FullPath))
{
reference.Priority = references.Count;
reference.IsRecent = true;
return reference;
}
}
Expand All @@ -127,5 +149,27 @@ public ReferenceModel TryAddReference(IVBProject project, ReferenceModel referen
return null;
}
}

public void UpdateSettings(IAddRemoveReferencesModel model, bool recent = false)
{
if (model?.Settings is null || model.References is null)
{
return;
}

if (recent)
{
model.Settings.UpdateRecentReferencesForHost(model.HostApplication,
model.References.Where(reference => reference.IsReferenced && !reference.IsBuiltIn)
.Select(reference => reference.ToReferenceInfo()).ToList());

}

model.Settings.UpdatePinnedReferencesForHost(model.HostApplication,
model.References.Where(reference => reference.IsPinned).Select(reference => reference.ToReferenceInfo())
.ToList());

_settings.Save(model.Settings);
}
}
}
12 changes: 1 addition & 11 deletions Rubberduck.Core/Settings/GeneralSettings.cs
Expand Up @@ -20,9 +20,6 @@ public interface IGeneralSettings
int MinimumLogLevel { get; set; }
bool SetDpiUnaware { get; set; }
List<ExperimentalFeatures> EnableExperimentalFeatures { get; set; }
int RecentReferencesTracked { get; set; }
List<string> RecentReferences { get; set; }
List<string> PinnedReferences { get; set; }
}

[SettingsSerializeAs(SettingsSerializeAs.Xml)]
Expand Down Expand Up @@ -64,10 +61,6 @@ public int MinimumLogLevel

public List<ExperimentalFeatures> EnableExperimentalFeatures { get; set; } = new List<ExperimentalFeatures>();

public int RecentReferencesTracked { get; set; }
public List<string> RecentReferences { get; set; }
public List<string> PinnedReferences { get; set; }

public GeneralSettings()
{
//Enforce non-default default value for members
Expand All @@ -87,12 +80,9 @@ public bool Equals(GeneralSettings other)
IsAutoSaveEnabled == other.IsAutoSaveEnabled &&
AutoSavePeriod == other.AutoSavePeriod &&
UserEditedLogLevel == other.UserEditedLogLevel &&
MinimumLogLevel == other.MinimumLogLevel &&
RecentReferencesTracked == other.RecentReferencesTracked &&
MinimumLogLevel == other.MinimumLogLevel &&
EnableExperimentalFeatures.Count == other.EnableExperimentalFeatures.Count &&
EnableExperimentalFeatures.All(other.EnableExperimentalFeatures.Contains) &&
RecentReferences.SequenceEqual(other.RecentReferences, StringComparer.OrdinalIgnoreCase) &&
PinnedReferences.OrderBy(x => x).SequenceEqual(other.PinnedReferences.OrderBy(x => x), StringComparer.OrdinalIgnoreCase) &&
SetDpiUnaware == other.SetDpiUnaware;
}
}
Expand Down
43 changes: 43 additions & 0 deletions Rubberduck.Core/Settings/ReferenceConfigProvider.cs
@@ -0,0 +1,43 @@
using System;
using System.Reflection;
using Rubberduck.Resources.Registration;
using Rubberduck.SettingsProvider;
using Rubberduck.VBEditor;

namespace Rubberduck.Settings
{
public class ReferenceConfigProvider : IConfigProvider<ReferenceSettings>
{
private readonly IPersistanceService<ReferenceSettings> _persister;

public ReferenceConfigProvider(IPersistanceService<ReferenceSettings> persister)
{
_persister = persister;
}

public ReferenceSettings Create()
{
var defaults = CreateDefaults();
return _persister.Load(defaults) ?? defaults;
}

public ReferenceSettings CreateDefaults()
{
var defaults = new ReferenceSettings
{
RecentReferencesTracked = 20
};

var version = Assembly.GetEntryAssembly().GetName().Version;
defaults.PinReference(new ReferenceInfo(new Guid(RubberduckGuid.RubberduckTypeLibGuid), string.Empty, string.Empty, version.Major, version.Minor));
defaults.PinReference(new ReferenceInfo(new Guid(RubberduckGuid.RubberduckApiTypeLibGuid), string.Empty, string.Empty, version.Major, version.Minor));

return defaults;
}

public void Save(ReferenceSettings settings)
{
_persister.Save(settings);
}
}
}

0 comments on commit 9bc9d80

Please sign in to comment.