Skip to content

Commit 024eecd

Browse files
authored
Merge pull request #4015 from mansellan/3994
VB6 - rewrite files in-place
2 parents 85d7534 + 1f3c364 commit 024eecd

File tree

12 files changed

+52
-282
lines changed

12 files changed

+52
-282
lines changed

Rubberduck.Parsing/Rewriter/MemberAttributesRewriter.cs

Lines changed: 10 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -32,16 +32,25 @@ public override void Rewrite()
3232
if(!IsDirty) { return; }
3333

3434
var component = Module.Parent;
35+
var vbeKind = component.VBE.Kind;
3536
if (component.Type == ComponentType.Document)
3637
{
3738
// can't re-import a document module
3839
return;
3940
}
4041

41-
var file = _exporter.Export(component);
42+
var file = vbeKind == VBEKind.Embedded
43+
? _exporter.Export(component)
44+
: component.GetFileName(1);
45+
4246
var content = Rewriter.GetText();
4347
File.WriteAllText(file, content);
4448

49+
if (vbeKind == VBEKind.Standalone)
50+
{
51+
return;
52+
}
53+
4554
var components = component.Collection;
4655
components.Remove(component);
4756
components.ImportSourceFile(file);

Rubberduck.Parsing/VBA/AttributeParser.cs

Lines changed: 6 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -35,7 +35,12 @@ public AttributeParser(IModuleExporter exporter, Func<IVBAPreprocessor> preproce
3535
public (IParseTree tree, ITokenStream tokenStream, IDictionary<Tuple<string, DeclarationType>, Attributes> attributes) Parse(QualifiedModuleName module, CancellationToken cancellationToken)
3636
{
3737
cancellationToken.ThrowIfCancellationRequested();
38-
var path = _exporter.Export(_projectsProvider.Component(module));
38+
var component = _projectsProvider.Component(module);
39+
40+
var path = component.VBE.Kind == VBEKind.Embedded
41+
? _exporter.Export(component)
42+
: component.GetFileName(1);
43+
3944
if (!File.Exists(path))
4045
{
4146
// a document component without any code wouldn't be exported (file would be empty anyway).

Rubberduck.VBEEditor/Extensions/IDEExtensions.cs

Lines changed: 0 additions & 107 deletions
This file was deleted.

Rubberduck.VBEEditor/Rubberduck.VBEditor.csproj

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -69,6 +69,7 @@
6969
<Compile Include="SafeComWrappers\SafeComWrapper.cs" />
7070
<Compile Include="SafeComWrappers\SafeRedirectedEventedComWrapper.cs" />
7171
<Compile Include="SafeComWrappers\VB\Abstract\IHostApplication.cs" />
72+
<Compile Include="SafeComWrappers\VB\Enums\VBEKind.cs" />
7273
<Compile Include="Utility\UiContext.cs" />
7374
<Compile Include="VBERuntime\IVBERuntime.cs" />
7475
<Compile Include="VBERuntime\Settings\IVBESettings.cs" />
@@ -168,7 +169,6 @@
168169
<Compile Include="Extensions\StringExtensions.cs" />
169170
<Compile Include="SubClassingWindowEventArgs.cs" />
170171
<Compile Include="Extensions\ComponentTypeExtensions.cs" />
171-
<Compile Include="Extensions\IDEExtensions.cs" />
172172
<Compile Include="VBEEditorText.Designer.cs">
173173
<AutoGen>True</AutoGen>
174174
<DesignTime>True</DesignTime>

Rubberduck.VBEEditor/SafeComWrappers/VB/Abstract/IVBComponent.cs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -20,7 +20,8 @@ public interface IVBComponent : ISafeComWrapper, IEquatable<IVBComponent>
2020
void Activate();
2121
void Export(string path);
2222
string ExportAsSourceFile(string folder, bool tempFile = false);
23-
23+
int FileCount { get; }
24+
string GetFileName(short index);
2425
IVBProject ParentProject { get; }
2526

2627
QualifiedModuleName QualifiedModuleName { get; }

Rubberduck.VBEEditor/SafeComWrappers/VB/Abstract/IVBE.cs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -5,6 +5,7 @@ namespace Rubberduck.VBEditor.SafeComWrappers.Abstract
55
// ReSharper disable once InconsistentNaming
66
public interface IVBE : ISafeComWrapper, IEquatable<IVBE>
77
{
8+
VBEKind Kind { get; }
89
string Version { get; }
910
object HardReference { get; }
1011
IWindow ActiveWindow { get; }
Lines changed: 17 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,17 @@
1+
using System;
2+
using System.Collections.Generic;
3+
using System.Linq;
4+
using System.Text;
5+
using System.Threading.Tasks;
6+
7+
namespace Rubberduck.VBEditor.SafeComWrappers
8+
{
9+
public enum VBEKind
10+
{
11+
/// <summary>Embedded VB editor (Visual Basic for Applications).</summary>
12+
Embedded,
13+
14+
/// <summary>Standalone VB editor (Visual Basic).</summary>
15+
Standalone
16+
}
17+
}

Rubberduck.VBEditor.VB6/SafeComWrappers/VB/VBComponent.cs

Lines changed: 9 additions & 94 deletions
Original file line numberDiff line numberDiff line change
@@ -96,109 +96,24 @@ public bool HasDesigner
9696
/// <param name="tempFile">True if a unique temp file name should be generated. WARNING: filenames generated with this flag are not persisted.</param>
9797
public string ExportAsSourceFile(string folder, bool tempFile = false)
9898
{
99-
var fullPath = tempFile
100-
? Path.Combine(folder, Path.GetRandomFileName())
101-
: Path.Combine(folder, SafeName + Type.FileExtension());
102-
switch (Type)
103-
{
104-
case ComponentType.UserForm:
105-
ExportUserFormModule(fullPath);
106-
break;
107-
case ComponentType.Document:
108-
ExportDocumentModule(fullPath);
109-
break;
110-
default:
111-
Export(fullPath);
112-
break;
113-
}
114-
115-
return fullPath;
99+
throw new NotSupportedException("Export as source file is not supported in VB6");
116100
}
117101

118102
public IVBProject ParentProject => Collection.Parent;
119103

120-
private void ExportUserFormModule(string path)
121-
{
122-
// VBIDE API inserts an extra newline when exporting a UserForm module.
123-
// this issue causes forms to always be treated as "modified" in source control, which causes conflicts.
124-
// we need to remove the extra newline before the file gets written to its output location.
125-
126-
int legitEmptyLineCount;
127-
using (var codeModule = CodeModule)
128-
{
129-
var visibleCode = codeModule.Content().Split(new[] { Environment.NewLine }, StringSplitOptions.None);
130-
legitEmptyLineCount = visibleCode.TakeWhile(string.IsNullOrWhiteSpace).Count();
131-
}
132-
133-
var tempFile = ExportToTempFile();
134-
var tempFilePath = Directory.GetParent(tempFile).FullName;
135-
var fileEncoding = System.Text.Encoding.Default; //We use the current ANSI codepage because that is what the VBE does.
136-
var contents = File.ReadAllLines(tempFile, fileEncoding);
137-
var nonAttributeLines = contents.TakeWhile(line => !line.StartsWith("Attribute")).Count();
138-
var attributeLines = contents.Skip(nonAttributeLines).TakeWhile(line => line.StartsWith("Attribute")).Count();
139-
var declarationsStartLine = nonAttributeLines + attributeLines + 1;
140-
141-
var emptyLineCount = contents.Skip(declarationsStartLine - 1)
142-
.TakeWhile(string.IsNullOrWhiteSpace)
143-
.Count();
144-
145-
var code = contents;
146-
if (emptyLineCount > legitEmptyLineCount)
147-
{
148-
code = contents.Take(declarationsStartLine).Union(
149-
contents.Skip(declarationsStartLine + emptyLineCount - legitEmptyLineCount))
150-
.ToArray();
151-
}
152-
File.WriteAllLines(path, code, fileEncoding);
104+
public int FileCount => IsWrappingNullReference ? 0 : Target.FileCount;
153105

154-
// LINQ hates this search, therefore, iterate the long way
155-
foreach (string line in contents)
106+
public string GetFileName(short index)
107+
{
108+
if (IsWrappingNullReference)
156109
{
157-
if (line.Contains("OleObjectBlob"))
158-
{
159-
var binaryFileName = line.Trim().Split('"')[1];
160-
var destPath = Directory.GetParent(path).FullName;
161-
if (File.Exists(Path.Combine(tempFilePath, binaryFileName)) && !destPath.Equals(tempFilePath))
162-
{
163-
System.Diagnostics.Debug.WriteLine(Path.Combine(destPath, binaryFileName));
164-
if (File.Exists(Path.Combine(destPath, binaryFileName)))
165-
{
166-
try
167-
{
168-
File.Delete(Path.Combine(destPath, binaryFileName));
169-
}
170-
catch (Exception)
171-
{
172-
// Meh?
173-
}
174-
}
175-
File.Copy(Path.Combine(tempFilePath, binaryFileName), Path.Combine(destPath, binaryFileName));
176-
}
177-
break;
178-
}
110+
return null;
179111
}
180-
}
181-
182-
private void ExportDocumentModule(string path)
183-
{
184-
using (var codeModule = CodeModule)
112+
if (index < 1 || index > FileCount) // 1-based indexing from VB
185113
{
186-
var lineCount = codeModule.CountOfLines;
187-
if (lineCount > 0)
188-
{
189-
//One cannot reimport document modules as such in the VBE; so we simply export and import the contents of the code pane.
190-
//Because of this, it is OK, and actually preferable, to use the default UTF8 encoding.
191-
var text = codeModule.GetLines(1, lineCount);
192-
File.WriteAllText(path, text, Encoding.UTF8);
193-
}
114+
throw new ArgumentOutOfRangeException(nameof(index));
194115
}
195-
}
196-
197-
private string ExportToTempFile()
198-
{
199-
var path = Path.Combine(Path.GetTempPath(), SafeName + Type.FileExtension());
200-
Export(path);
201-
return path;
116+
return Target.FileNames[index];
202117
}
203118

204119
public override bool Equals(ISafeComWrapper<VB.VBComponent> other)

0 commit comments

Comments
 (0)