Skip to content

Commit 88a8413

Browse files
authored
Merge pull request #234 from rubberduck-vba/next
sync with main repo
2 parents b6e18de + cd8202f commit 88a8413

File tree

12 files changed

+227
-77
lines changed

12 files changed

+227
-77
lines changed

RetailCoder.VBE/App.cs

Lines changed: 21 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -81,6 +81,26 @@ private static void EnsureLogFolderPathExists()
8181
}
8282
}
8383

84+
private static void EnsureTempPathExists()
85+
{
86+
// This is required by the parser - allow this to throw.
87+
if (!Directory.Exists(ApplicationConstants.RUBBERDUCK_TEMP_PATH))
88+
{
89+
Directory.CreateDirectory(ApplicationConstants.RUBBERDUCK_TEMP_PATH);
90+
}
91+
// The parser swallows the error if deletions fail - clean up any temp files on startup
92+
foreach (var file in new DirectoryInfo(ApplicationConstants.RUBBERDUCK_TEMP_PATH).GetFiles())
93+
{ try
94+
{
95+
file.Delete();
96+
}
97+
catch
98+
{
99+
// Yeah, don't care here either.
100+
}
101+
}
102+
}
103+
84104
private void UpdateLoggingLevel()
85105
{
86106
LogLevelHelper.SetMinimumLogLevel(LogLevel.FromOrdinal(_config.UserSettings.GeneralSettings.MinimumLogLevel));
@@ -89,6 +109,7 @@ private void UpdateLoggingLevel()
89109
public void Startup()
90110
{
91111
EnsureLogFolderPathExists();
112+
EnsureTempPathExists();
92113
LogRubberduckSart();
93114
LoadConfig();
94115
CheckForLegacyIndenterSettings();

RetailCoder.VBE/Common/ApplicationConstants.cs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -7,5 +7,6 @@ public static class ApplicationConstants
77
{
88
public static readonly string RUBBERDUCK_FOLDER_PATH = Path.Combine(Environment.GetFolderPath(Environment.SpecialFolder.ApplicationData), "Rubberduck");
99
public static readonly string LOG_FOLDER_PATH = Path.Combine(RUBBERDUCK_FOLDER_PATH, "Logs");
10+
public static readonly string RUBBERDUCK_TEMP_PATH = Path.Combine(Path.GetTempPath(), "Rubberduck");
1011
}
1112
}
Lines changed: 10 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,5 @@
1-
using System.IO;
1+
using System;
2+
using System.IO;
23
using System.Reflection;
34
using Rubberduck.Parsing.VBA;
45
using Rubberduck.VBEditor.SafeComWrappers.Abstract;
@@ -7,18 +8,22 @@ namespace Rubberduck.Common
78
{
89
public class ModuleExporter : IModuleExporter
910
{
11+
public bool TempFile { get; private set; }
12+
1013
public string ExportPath
1114
{
1215
get
1316
{
14-
var assemblyLocation = Assembly.GetAssembly(typeof(App)).Location;
15-
return Path.GetDirectoryName(assemblyLocation);
17+
return TempFile
18+
? ApplicationConstants.RUBBERDUCK_TEMP_PATH
19+
: Path.GetDirectoryName(Assembly.GetAssembly(typeof(App)).Location);
1620
}
1721
}
1822

19-
public string Export(IVBComponent component)
23+
public string Export(IVBComponent component, bool tempFile = false)
2024
{
21-
return component.ExportAsSourceFile(ExportPath);
25+
TempFile = tempFile;
26+
return component.ExportAsSourceFile(ExportPath, tempFile);
2227
}
2328
}
2429
}

RetailCoder.VBE/Refactorings/Rename/RenameRefactoring.cs

Lines changed: 3 additions & 63 deletions
Original file line numberDiff line numberDiff line change
@@ -14,6 +14,7 @@
1414
using Rubberduck.VBEditor;
1515
using Rubberduck.VBEditor.SafeComWrappers;
1616
using Rubberduck.VBEditor.SafeComWrappers.Abstract;
17+
using System;
1718

1819
namespace Rubberduck.Refactorings.Rename
1920
{
@@ -92,68 +93,6 @@ public void Refactor(Declaration target)
9293
pane.Selection = oldSelection;
9394
}
9495
}
95-
96-
private Declaration FindDeclarationForIdentifier()
97-
{
98-
var values = _model.Declarations.Where(item =>
99-
_model.NewName == item.IdentifierName
100-
&& ((item.Scope.Contains(_model.Target.Scope)
101-
|| (item.ParentScope == null && string.IsNullOrEmpty(_model.Target.ParentScope))
102-
|| (item.ParentScope != null && _model.Target.ParentScope.Contains(item.ParentScope))))
103-
).ToList();
104-
105-
if (values.Any())
106-
{
107-
return values.FirstOrDefault();
108-
}
109-
110-
foreach (var reference in _model.Target.References)
111-
{
112-
var targetReference = reference;
113-
var potentialDeclarations = _model.Declarations.Where(item => !item.IsBuiltIn
114-
&& item.ProjectId == targetReference.Declaration.ProjectId
115-
&& ((item.Context != null
116-
&& item.Context.Start.Line <= targetReference.Selection.StartLine
117-
&& item.Context.Stop.Line >= targetReference.Selection.EndLine)
118-
|| (item.Selection.StartLine <= targetReference.Selection.StartLine
119-
&& item.Selection.EndLine >= targetReference.Selection.EndLine))
120-
&& item.QualifiedName.QualifiedModuleName.ComponentName == targetReference.QualifiedModuleName.ComponentName);
121-
122-
var currentSelection = new Selection(0, 0, int.MaxValue, int.MaxValue);
123-
124-
Declaration target = null;
125-
foreach (var item in potentialDeclarations)
126-
{
127-
var startLine = item.Context == null ? item.Selection.StartLine : item.Context.Start.Line;
128-
var endLine = item.Context == null ? item.Selection.EndLine : item.Context.Stop.Column;
129-
var startColumn = item.Context == null ? item.Selection.StartColumn : item.Context.Start.Column;
130-
var endColumn = item.Context == null ? item.Selection.EndColumn : item.Context.Stop.Column;
131-
132-
var selection = new Selection(startLine, startColumn, endLine, endColumn);
133-
134-
if (currentSelection.Contains(selection))
135-
{
136-
currentSelection = selection;
137-
target = item;
138-
}
139-
}
140-
141-
if (target == null) { continue; }
142-
143-
values = _model.Declarations.Where(item => (item.Scope.Contains(target.Scope)
144-
|| (item.ParentScope == null && string.IsNullOrEmpty(target.ParentScope))
145-
|| (item.ParentScope != null && target.ParentScope.Contains(item.ParentScope)))
146-
&& _model.NewName == item.IdentifierName).ToList();
147-
148-
if (values.Any())
149-
{
150-
return values.FirstOrDefault();
151-
}
152-
}
153-
154-
return null;
155-
}
156-
15796
private static readonly DeclarationType[] ModuleDeclarationTypes =
15897
{
15998
DeclarationType.ClassModule,
@@ -162,7 +101,8 @@ private Declaration FindDeclarationForIdentifier()
162101

163102
private void Rename()
164103
{
165-
var declaration = FindDeclarationForIdentifier();
104+
var declaration = _state.DeclarationFinder.GetDeclarationsAccessibleToScope(_model.Target, _model.Declarations)
105+
.Where(d => d.IdentifierName.Equals(_model.NewName, StringComparison.InvariantCultureIgnoreCase)).FirstOrDefault();
166106
if (declaration != null)
167107
{
168108
var message = string.Format(RubberduckUI.RenameDialog_ConflictingNames, _model.NewName,

Rubberduck.Parsing/Symbols/DeclarationFinder.cs

Lines changed: 54 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -747,5 +747,59 @@ private ConcurrentBag<Declaration> FindEventHandlers(IEnumerable<Declaration> de
747747

748748
return new ConcurrentBag<Declaration>(handlers);
749749
}
750+
751+
public IEnumerable<Declaration> GetDeclarationsAccessibleToScope(Declaration target, IEnumerable<Declaration> declarations)
752+
{
753+
if (target == null) { return Enumerable.Empty<Declaration>(); }
754+
755+
return declarations
756+
.Where(candidateDeclaration =>
757+
(
758+
IsDeclarationInTheSameProcedure(candidateDeclaration, target)
759+
|| IsDeclarationChildOfTheScope(candidateDeclaration, target)
760+
|| IsModuleLevelDeclarationOfTheScope(candidateDeclaration, target)
761+
|| IsProjectGlobalDeclaration(candidateDeclaration, target)
762+
)).Distinct();
763+
}
764+
765+
private bool IsDeclarationInTheSameProcedure(Declaration candidateDeclaration, Declaration scopingDeclaration)
766+
{
767+
return candidateDeclaration.ParentScope == scopingDeclaration.ParentScope;
768+
}
769+
770+
private bool IsDeclarationChildOfTheScope(Declaration candidateDeclaration, Declaration scopingDeclaration)
771+
{
772+
return scopingDeclaration == candidateDeclaration.ParentDeclaration;
773+
}
774+
775+
private bool IsModuleLevelDeclarationOfTheScope(Declaration candidateDeclaration, Declaration scopingDeclaration)
776+
{
777+
if (candidateDeclaration.ParentDeclaration == null)
778+
{
779+
return false;
780+
}
781+
return candidateDeclaration.ComponentName == scopingDeclaration.ComponentName
782+
&& !IsDeclaredWithinMethodOrProperty(candidateDeclaration.ParentDeclaration.Context);
783+
}
784+
785+
private bool IsProjectGlobalDeclaration(Declaration candidateDeclaration, Declaration scopingDeclaration)
786+
{
787+
return candidateDeclaration.ProjectName == scopingDeclaration.ProjectName
788+
&& !(candidateDeclaration.ParentScopeDeclaration is ClassModuleDeclaration)
789+
&& (candidateDeclaration.Accessibility == Accessibility.Public
790+
|| ((candidateDeclaration.Accessibility == Accessibility.Implicit)
791+
&& (candidateDeclaration.ParentScopeDeclaration is ProceduralModuleDeclaration)));
792+
}
793+
794+
private bool IsDeclaredWithinMethodOrProperty(RuleContext procedureContextCandidate)
795+
{
796+
if (procedureContextCandidate == null) { return false; }
797+
798+
return (procedureContextCandidate is VBAParser.SubStmtContext)
799+
|| (procedureContextCandidate is VBAParser.FunctionStmtContext)
800+
|| (procedureContextCandidate is VBAParser.PropertyLetStmtContext)
801+
|| (procedureContextCandidate is VBAParser.PropertyGetStmtContext)
802+
|| (procedureContextCandidate is VBAParser.PropertySetStmtContext);
803+
}
750804
}
751805
}

Rubberduck.Parsing/VBA/AttributeParser.cs

Lines changed: 10 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -32,14 +32,22 @@ public AttributeParser(IModuleExporter exporter, Func<IVBAPreprocessor> preproce
3232
public IDictionary<Tuple<string, DeclarationType>, Attributes> Parse(IVBComponent component, CancellationToken token)
3333
{
3434
token.ThrowIfCancellationRequested();
35-
var path = _exporter.Export(component);
35+
var path = _exporter.Export(component, true);
3636
if (!File.Exists(path))
3737
{
3838
// a document component without any code wouldn't be exported (file would be empty anyway).
3939
return new Dictionary<Tuple<string, DeclarationType>, Attributes>();
4040
}
4141
var code = File.ReadAllText(path);
42-
File.Delete(path);
42+
try
43+
{
44+
File.Delete(path);
45+
}
46+
catch
47+
{
48+
// Meh.
49+
}
50+
4351
token.ThrowIfCancellationRequested();
4452

4553
var type = component.Type == ComponentType.StandardModule

Rubberduck.Parsing/VBA/IModuleExporter.cs

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -5,12 +5,14 @@ namespace Rubberduck.Parsing.VBA
55
public interface IModuleExporter
66
{
77
string ExportPath { get; }
8+
bool TempFile { get; }
89

910
/// <summary>
1011
/// Exports the specified component and returns the path to the created file.
1112
/// </summary>
1213
/// <param name="component">The module to export.</param>
14+
/// <param name="tempFile">True if a unique temp file name should be generated.</param>
1315
/// <returns>Returns a string containing the path and filename of the created file.</returns>
14-
string Export(IVBComponent component);
16+
string Export(IVBComponent component, bool tempFile = false);
1517
}
1618
}

Rubberduck.VBEEditor/SafeComWrappers/Abstract/IVBComponent.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -20,7 +20,7 @@ public interface IVBComponent : ISafeComWrapper, IEquatable<IVBComponent>
2020
IWindow DesignerWindow();
2121
void Activate();
2222
void Export(string path);
23-
string ExportAsSourceFile(string folder);
23+
string ExportAsSourceFile(string folder, bool tempFile = false);
2424

2525
IVBProject ParentProject { get; }
2626
}

Rubberduck.VBEEditor/SafeComWrappers/VB6/VBComponent.cs

Lines changed: 5 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -128,9 +128,12 @@ public void Export(string path)
128128
/// Exports the component to the folder. The file name matches the component name and file extension is based on the component's type.
129129
/// </summary>
130130
/// <param name="folder">Destination folder for the resulting source file.</param>
131-
public string ExportAsSourceFile(string folder)
131+
/// <param name="tempFile">True if a unique temp file name should be generated. WARNING: filenames generated with this flag are not persisted.</param>
132+
public string ExportAsSourceFile(string folder, bool tempFile = false)
132133
{
133-
var fullPath = Path.Combine(folder, Name + Type.FileExtension());
134+
var fullPath = tempFile
135+
? Path.Combine(folder, Path.GetRandomFileName())
136+
: Path.Combine(folder, Name + Type.FileExtension());
134137
switch (Type)
135138
{
136139
case ComponentType.UserForm:

Rubberduck.VBEEditor/SafeComWrappers/VBA/VBComponent.cs

Lines changed: 5 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -124,9 +124,12 @@ public void Export(string path)
124124
/// Exports the component to the folder. The file is name matches the component name and file extension is based on the component's type.
125125
/// </summary>
126126
/// <param name="folder">Destination folder for the resulting source file.</param>
127-
public string ExportAsSourceFile(string folder)
127+
/// <param name="tempFile">True if a unique temp file name should be generated. WARNING: filenames generated with this flag are not persisted.</param>
128+
public string ExportAsSourceFile(string folder, bool tempFile = false)
128129
{
129-
var fullPath = Path.Combine(folder, SafeName + Type.FileExtension());
130+
var fullPath = tempFile
131+
? Path.Combine(folder, Path.GetRandomFileName())
132+
: Path.Combine(folder, SafeName + Type.FileExtension());
130133
switch (Type)
131134
{
132135
case ComponentType.UserForm:

0 commit comments

Comments
 (0)