Skip to content

Commit ad75cc2

Browse files
committed
Improve performance by 66%
1 parent d468fbc commit ad75cc2

File tree

4 files changed

+9
-138
lines changed

4 files changed

+9
-138
lines changed

RetailCoder.VBE/Inspections/InspectionResultBase.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -121,7 +121,7 @@ public int CompareTo(object obj)
121121
public object[] ToArray()
122122
{
123123
var module = QualifiedSelection.QualifiedName;
124-
return new object[] { Inspection.Severity.ToString(), module.ProjectTitle, module.ComponentTitle, Description, QualifiedSelection.Selection.StartLine, QualifiedSelection.Selection.StartColumn };
124+
return new object[] { Inspection.Severity.ToString(), module.ProjectTitle, module.ComponentName, Description, QualifiedSelection.Selection.StartLine, QualifiedSelection.Selection.StartColumn };
125125
}
126126

127127
public string ToCsvString()

RetailCoder.VBE/Inspections/SelfAssignedDeclarationInspection.cs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -39,7 +39,8 @@ public override IEnumerable<InspectionResultBase> GetInspectionResults()
3939
&& declaration.IsTypeSpecified
4040
&& !ValueTypes.Contains(declaration.AsTypeName)
4141
&& declaration.DeclarationType == DeclarationType.Variable
42-
&& declaration.AsTypeDeclaration.DeclarationType != DeclarationType.UserDefinedType
42+
&& (declaration.AsTypeDeclaration == null
43+
|| declaration.AsTypeDeclaration.DeclarationType != DeclarationType.UserDefinedType)
4344
&& declaration.ParentScopeDeclaration != null
4445
&& declaration.ParentScopeDeclaration.DeclarationType.HasFlag(DeclarationType.Member))
4546
.Select(issue => new SelfAssignedDeclarationInspectionResult(this, issue));

RetailCoder.VBE/UnitTesting/TestMethod.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -109,7 +109,7 @@ public NavigateCodeEventArgs GetNavigationArgs()
109109

110110
public object[] ToArray()
111111
{
112-
return new object[] { Declaration.QualifiedName.QualifiedModuleName.ProjectTitle, Declaration.QualifiedName.QualifiedModuleName.ComponentTitle, Declaration.IdentifierName,
112+
return new object[] { Declaration.QualifiedName.QualifiedModuleName.ProjectTitle, Declaration.QualifiedName.QualifiedModuleName.ComponentName, Declaration.IdentifierName,
113113
_result.Outcome.ToString(), _result.Output, _result.StartTime.ToString(CultureInfo.InvariantCulture), _result.EndTime.ToString(CultureInfo.InvariantCulture), _result.Duration };
114114
}
115115

Rubberduck.VBEEditor/QualifiedModuleName.cs

Lines changed: 5 additions & 135 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,5 @@
11
using System;
22
using Microsoft.Vbe.Interop;
3-
using System.IO;
43
using System.Linq;
54

65
namespace Rubberduck.VBEditor
@@ -12,94 +11,18 @@ public struct QualifiedModuleName
1211
{
1312
private static string GetDisplayName(VBProject project)
1413
{
15-
16-
if (project.Protection == vbext_ProjectProtection.vbext_pp_none)
17-
{
18-
//Try reading the top-most document-type component's Properties("Name") value
19-
//Eg. A Workbook's parent is the application, so read the workbook's name
20-
try
21-
{
22-
var component = project.VBComponents.Cast<VBComponent>()
23-
.FirstOrDefault(comp => comp.Type == vbext_ComponentType.vbext_ct_Document
24-
&& comp.Properties.Item("Name").Value != null
25-
&& comp.Properties.Item("Parent")
26-
.Object.Equals(comp.Properties.Item("Application").Object));
27-
28-
if (component == null) { return null; }
29-
30-
var nameProperty = component.Properties.Cast<Property>().FirstOrDefault(property => property.Name == "Name");
31-
return nameProperty == null
32-
? null
33-
: nameProperty.Value.ToString();
34-
}
35-
catch
36-
{
37-
//The Properties collection either wasn't available, or didn't have the expected properties
38-
}
39-
40-
//Try reading the top-most document-type component's parent's Properties("Name") value
41-
// Eg. A PowerPoint Slide is top level, but it's parent is a Presentation (that is NOT a vbComponent)
42-
try
43-
{
44-
var firstOrDefault = project.VBComponents.Cast<VBComponent>()
45-
.FirstOrDefault(comp => comp.Type == vbext_ComponentType.vbext_ct_Document
46-
&& comp.Properties.Item("Parent").Value != null);
47-
if (firstOrDefault != null)
48-
{
49-
var parentProp = firstOrDefault
50-
.Properties.Cast<Property>().FirstOrDefault(property => property.Name == "Parent");
51-
52-
Property nameProperty = null;
53-
if (parentProp != null && parentProp.Value is Properties)
54-
{
55-
var props = (Properties)parentProp.Value;
56-
nameProperty = props.Cast<Property>().FirstOrDefault(property => property.Name == "Name");
57-
}
58-
59-
return nameProperty == null
60-
? null
61-
: nameProperty.Value.ToString();
62-
}
63-
}
64-
catch
65-
{
66-
//The Properties collection either wasn't available, or didn't have the expected properties
67-
}
68-
}
69-
70-
//Try reading the filename
7114
try
7215
{
73-
if (!string.IsNullOrEmpty(Path.GetDirectoryName(project.BuildFileName)))
16+
if (project.HelpFile != project.VBE.ActiveVBProject.HelpFile)
7417
{
75-
return Path.GetFileName(project.FileName);
18+
project.VBE.ActiveVBProject = project;
7619
}
20+
return project.VBE.MainWindow.Caption.Split(' ').Last();
7721
}
7822
catch
79-
{ //The GetFileName getter probably threw
80-
}
81-
82-
return null;
83-
}
84-
85-
private static string GetDisplayName(VBComponent component)
86-
{
87-
if (component.Type == vbext_ComponentType.vbext_ct_Document)
8823
{
89-
//Check for a valid properties collection (some hosts don't validate the Properties method unless the component's designer is open in the host
90-
try
91-
{
92-
var nameProperty = component.Properties.Item("Name");
93-
return nameProperty == null
94-
? null
95-
: nameProperty.Value.ToString();
96-
}
97-
catch
98-
{
99-
//The component isn't open in the host, the Properties Collection is probably inaccessible
100-
}
24+
return string.Empty;
10125
}
102-
return null;
10326
}
10427

10528
public static string GetProjectId(VBProject project)
@@ -128,7 +51,6 @@ public QualifiedModuleName(VBProject project)
12851
{
12952
_component = null;
13053
_componentName = null;
131-
_componentDisplayName = null;
13254
_project = project;
13355
_projectName = project.Name;
13456
_projectPath = string.Empty;
@@ -143,7 +65,6 @@ public QualifiedModuleName(VBComponent component)
14365

14466
_component = component;
14567
_componentName = component == null ? string.Empty : component.Name;
146-
_componentDisplayName = GetDisplayName(component);
14768
_project = component == null ? null : component.Collection.Parent;
14869
_projectName = _project == null ? string.Empty : _project.Name;
14970
_projectDisplayName = GetDisplayName(_project);
@@ -163,26 +84,6 @@ public QualifiedModuleName(VBComponent component)
16384
: 0;
16485
}
16586

166-
/// <summary>
167-
/// Creates a QualifiedModuleName for removing renamed declarations.
168-
/// Do not use this overload.
169-
/// </summary>
170-
public QualifiedModuleName(VBComponent component, string oldComponentName)
171-
{
172-
_project = null; // field is only assigned when the instance refers to a VBProject.
173-
174-
_component = component;
175-
_componentName = oldComponentName;
176-
_componentDisplayName = GetDisplayName(component);
177-
_project = component == null ? null : component.Collection.Parent;
178-
_projectName = _project == null ? string.Empty : _project.Name;
179-
_projectDisplayName = GetDisplayName(_project);
180-
_projectPath = string.Empty;
181-
_projectId = GetProjectId(_project);
182-
183-
_contentHashCode = 0;
184-
}
185-
18687
/// <summary>
18788
/// Creates a QualifiedModuleName for a built-in declaration.
18889
/// Do not use this overload for user declarations.
@@ -196,7 +97,6 @@ public QualifiedModuleName(string projectName, string projectPath, string compon
19697
_projectId = (_projectName + ";" + _projectPath).GetHashCode().ToString();
19798
_componentName = componentName;
19899
_component = null;
199-
_componentDisplayName = null;
200100
_contentHashCode = 0;
201101
}
202102

@@ -222,39 +122,9 @@ public QualifiedMemberName QualifyMemberName(string member)
222122

223123
public string Name { get { return ToString(); } }
224124

225-
private readonly string _componentDisplayName;
226-
public string ComponentDisplayName { get {return _componentDisplayName; } }
227-
228125
private readonly string _projectDisplayName;
229126
public string ProjectDisplayName { get { return _projectDisplayName; } }
230-
231-
232-
/// <summary>
233-
/// returns: "ComponentName (DisplayName)" as typically displayed in VBE Project Explorer
234-
/// </summary>
235-
public string ComponentTitle {
236-
get {
237-
if (_project != null && _component == null)
238-
{
239-
//handle display of Project component
240-
return _projectName + (_projectDisplayName != null ? " (" + _projectDisplayName + ")" : string.Empty);
241-
}
242-
else
243-
{
244-
if (_componentDisplayName == _projectDisplayName)
245-
{
246-
//handle display of main documents, like ThisWorkbook and ThisDocument
247-
return _componentName;
248-
}
249-
else
250-
{
251-
//handle display of all other components
252-
return _componentName + (_componentDisplayName != null ? " (" + _componentDisplayName + ")" : string.Empty);
253-
}
254-
}
255-
}
256-
}
257-
127+
258128
/// <summary>
259129
/// returns: "ProjectName (DisplayName)" as typically displayed in VBE Project Explorer
260130
/// </summary>

0 commit comments

Comments
 (0)