Skip to content

Commit

Permalink
removed more static classes / moved extension methods to appropriate …
Browse files Browse the repository at this point in the history
…wrapper types
  • Loading branch information
retailcoder committed Oct 5, 2016
1 parent 8d50e17 commit 3ec6220
Show file tree
Hide file tree
Showing 16 changed files with 263 additions and 353 deletions.
Original file line number Diff line number Diff line change
Expand Up @@ -104,7 +104,7 @@ private void SetSelection(RegexSearchResult item)
project = proj;
break;
}
_vbe.SetSelection(project, item.Selection, item.Module.Name);
VBE.SetSelection(project, item.Selection, item.Module.Name);
}

private List<RegexSearchResult> SearchSelection(string searchPattern)
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -25,7 +25,7 @@ private void BindTarget(Declaration target)

public static void OnNavigateIdentifierReference(VBE vbe, IdentifierReference reference)
{
vbe.SetSelection(reference.QualifiedModuleName.Project, reference.Selection, reference.QualifiedModuleName.Component.Name);
VBE.SetSelection(reference.QualifiedModuleName.Project, reference.Selection, reference.QualifiedModuleName.Component.Name);
}

private void ControlNavigate(object sender, ListItemActionEventArgs e)
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -26,7 +26,7 @@ private void BindTarget(IEnumerable<Declaration> implementations)

public static void OnNavigateImplementation(VBE vbe, Declaration implementation)
{
vbe.SetSelection(implementation.QualifiedName.QualifiedModuleName.Project, implementation.Selection, implementation.QualifiedName.QualifiedModuleName.Component.Name);
VBE.SetSelection(implementation.QualifiedName.QualifiedModuleName.Project, implementation.Selection, implementation.QualifiedName.QualifiedModuleName.Component.Name);
}

private void ControlNavigate(object sender, ListItemActionEventArgs e)
Expand Down
4 changes: 2 additions & 2 deletions Rubberduck.SourceControl/SourceControlProviderBase.cs
Original file line number Diff line number Diff line change
Expand Up @@ -185,7 +185,7 @@ public void ReloadComponent(string filePath)
directory += directory.EndsWith("\\") ? string.Empty : "\\";
components.Import(directory + filePath);

vbe.SetSelection(selection.QualifiedName.Project, selection.Selection, name);
VBE.SetSelection(selection.QualifiedName.Project, selection.Selection, name);
}
}
else
Expand Down Expand Up @@ -233,7 +233,7 @@ private void Refresh()
throw new SourceControlException("Unknown exception.", ex);
}

vbe.SetSelection(selection.QualifiedName.Project, selection.Selection, name);
VBE.SetSelection(selection.QualifiedName.Project, selection.Selection, name);
}
}
else
Expand Down
70 changes: 70 additions & 0 deletions Rubberduck.VBEEditor/DisposableWrappers/VBA/VBComponent.cs
Original file line number Diff line number Diff line change
@@ -1,6 +1,8 @@
using System;
using System.Collections.Generic;
using System.IO;
using System.Linq;
using Rubberduck.VBEditor.Extensions;

namespace Rubberduck.VBEditor.DisposableWrappers.VBA
{
Expand Down Expand Up @@ -97,6 +99,74 @@ public void Export(string path)
Invoke(() => ComObject.Export(path));
}

/// <summary>
/// Exports the component to the folder. The file is name matches the component name and file extension is based on the component's type.
/// </summary>
/// <param name="folder">Destination folder for the resulting source file.</param>
public string ExportAsSourceFile(string folder)
{
var fullPath = Path.Combine(folder, Name + Type.FileExtension());
switch (Type)
{
case ComponentType.UserForm:
ExportUserFormModule(fullPath);
break;
case ComponentType.Document:
ExportDocumentModule(fullPath);
break;
default:
Export(fullPath);
break;
}

return fullPath;
}

private void ExportUserFormModule(string path)
{
// VBIDE API inserts an extra newline when exporting a UserForm module.
// this issue causes forms to always be treated as "modified" in source control, which causes conflicts.
// we need to remove the extra newline before the file gets written to its output location.

var visibleCode = CodeModule.Content().Split(new[] { Environment.NewLine }, StringSplitOptions.None);
var legitEmptyLineCount = visibleCode.TakeWhile(string.IsNullOrWhiteSpace).Count();

var tempFile = ExportToTempFile();
var contents = File.ReadAllLines(tempFile);
var nonAttributeLines = contents.TakeWhile(line => !line.StartsWith("Attribute")).Count();
var attributeLines = contents.Skip(nonAttributeLines).TakeWhile(line => line.StartsWith("Attribute")).Count();
var declarationsStartLine = nonAttributeLines + attributeLines + 1;

var emptyLineCount = contents.Skip(declarationsStartLine - 1)
.TakeWhile(string.IsNullOrWhiteSpace)
.Count();

var code = contents;
if (emptyLineCount > legitEmptyLineCount)
{
code = contents.Take(declarationsStartLine).Union(
contents.Skip(declarationsStartLine + emptyLineCount - legitEmptyLineCount))
.ToArray();
}
File.WriteAllLines(path, code);
}

private void ExportDocumentModule(string path)
{
var lineCount = CodeModule.CountOfLines;
if (lineCount > 0)
{
var text = CodeModule.GetLines(1, lineCount);
File.WriteAllText(path, text);
}
}

private string ExportToTempFile()
{
var path = Path.Combine(Path.GetTempPath(), Name + Type.FileExtension());
Export(path);
return path;
}
public override void Release()
{
if (!IsWrappingNullReference)
Expand Down
73 changes: 73 additions & 0 deletions Rubberduck.VBEEditor/DisposableWrappers/VBA/VBComponents.cs
Original file line number Diff line number Diff line change
@@ -1,8 +1,11 @@
using System;
using System.Collections;
using System.Collections.Generic;
using System.IO;
using System.Linq;
using System.Runtime.InteropServices;
using Microsoft.Vbe.Interop;
using Rubberduck.VBEditor.Extensions;

namespace Rubberduck.VBEditor.DisposableWrappers.VBA
{
Expand Down Expand Up @@ -94,5 +97,75 @@ public override int GetHashCode()
{
return IsWrappingNullReference ? 0 : ComObject.GetHashCode();
}

public void ImportSourceFile(string path)
{
var ext = Path.GetExtension(path);
var name = Path.GetFileNameWithoutExtension(path);
if (!File.Exists(path))
{
return;
}

var codeString = File.ReadAllText(path);
var codeLines = codeString.Split(new[] { Environment.NewLine }, StringSplitOptions.None);
if (ext == ComponentTypeExtensions.DocClassExtension)
{
var component = Item(name);
component.CodeModule.Clear();
component.CodeModule.AddFromString(codeString);
}
else if (ext == ComponentTypeExtensions.FormExtension)
{
VBComponent component;
try
{
component = Item(name);
}
catch (IndexOutOfRangeException)
{
component = Add(ComponentType.UserForm);
component.Properties.Item("Caption").Value = name;
component.Name = name;
}

var nonAttributeLines = codeLines.TakeWhile(line => !line.StartsWith("Attribute")).Count();
var attributeLines = codeLines.Skip(nonAttributeLines).TakeWhile(line => line.StartsWith("Attribute")).Count();
var declarationsStartLine = nonAttributeLines + attributeLines + 1;
var correctCodeString = string.Join(Environment.NewLine, codeLines.Skip(declarationsStartLine - 1).ToArray());

component.CodeModule.Clear();
component.CodeModule.AddFromString(correctCodeString);
}
else if (ext != ComponentTypeExtensions.FormBinaryExtension)
{
Import(path);
}
}

/// <summary>
/// Safely removes the specified VbComponent from the collection.
/// </summary>
/// <remarks>
/// UserForms, Class modules, and Standard modules are completely removed from the project.
/// Since Document type components can't be removed through the VBE, all code in its CodeModule are deleted instead.
/// </remarks>
public void RemoveSafely(VBComponent component)
{
switch (component.Type)
{
case ComponentType.ClassModule:
case ComponentType.StandardModule:
case ComponentType.UserForm:
Remove(component);
break;
case ComponentType.ActiveXDesigner:
case ComponentType.Document:
component.CodeModule.Clear();
break;
default:
break;
}
}
}
}
20 changes: 20 additions & 0 deletions Rubberduck.VBEEditor/DisposableWrappers/VBA/VBE.cs
Original file line number Diff line number Diff line change
@@ -1,4 +1,5 @@
using System;
using System.Linq;
using System.Runtime.InteropServices;
using Rubberduck.VBEditor.DisposableWrappers.Office.Core;

Expand Down Expand Up @@ -95,5 +96,24 @@ public override int GetHashCode()
{
return IsWrappingNullReference ? 0 : ComObject.GetHashCode();
}

public bool IsInDesignMode()
{
return VBProjects.All(project => project.Mode == EnvironmentMode.Design);
}

public static void SetSelection(VBProject vbProject, Selection selection, string name)
{
var components = vbProject.VBComponents;
var component = components.SingleOrDefault(c => c.Name == name);
if (component == null || component.IsWrappingNullReference)
{
return;
}

var module = component.CodeModule;
var pane = module.CodePane;
pane.SetSelection(selection);
}
}
}
41 changes: 41 additions & 0 deletions Rubberduck.VBEEditor/DisposableWrappers/VBA/VBProject.cs
Original file line number Diff line number Diff line change
@@ -1,4 +1,6 @@
using System;
using System.Collections.Generic;
using System.Linq;
using System.Runtime.InteropServices;

namespace Rubberduck.VBEditor.DisposableWrappers.VBA
Expand Down Expand Up @@ -128,5 +130,44 @@ public override int GetHashCode()
{
return IsWrappingNullReference ? 0 : ComObject.GetHashCode();
}

public IEnumerable<string> ComponentNames()
{
return VBComponents.Select(component => component.Name);
}

public void AssignProjectId()
{
//assign a hashcode if no helpfile is present
if (string.IsNullOrEmpty(HelpFile))
{
HelpFile = GetHashCode().ToString();
}

//loop until the helpfile is unique for this host session
while (!IsProjectIdUnique())
{
HelpFile = (GetHashCode() ^ HelpFile.GetHashCode()).ToString();
}
}

private bool IsProjectIdUnique()
{
return VBE.VBProjects.Count(project => project.HelpFile == HelpFile) == 1;
}


/// <summary>
/// Exports all code modules in the VbProject to a destination directory. Files are given the same name as their parent code Module name and file extensions are based on what type of code Module it is.
/// </summary>
/// <param name="folder">The destination directory path.</param>
public void ExportSourceFiles(string folder)
{
foreach (var component in VBComponents)
{
component.ExportAsSourceFile(folder);
}
}

}
}
5 changes: 5 additions & 0 deletions Rubberduck.VBEEditor/DisposableWrappers/VBA/Window.cs
Original file line number Diff line number Diff line change
Expand Up @@ -16,6 +16,11 @@ public int HWnd
get { return IsWrappingNullReference ? 0 : InvokeResult(() => ComObject.HWnd); }
}

public IntPtr Handle()
{
return (IntPtr)HWnd;
}

public VBE VBE
{
get { return new VBE(IsWrappingNullReference ? null : InvokeResult(() => ComObject.VBE)); }
Expand Down
39 changes: 39 additions & 0 deletions Rubberduck.VBEEditor/Extensions/ComponentTypeExtensions.cs
Original file line number Diff line number Diff line change
@@ -0,0 +1,39 @@
using Rubberduck.VBEditor.DisposableWrappers.VBA;

namespace Rubberduck.VBEditor.Extensions
{
public static class ComponentTypeExtensions
{
internal const string ClassExtension = ".cls";
internal const string FormExtension = ".frm";
internal const string StandardExtension = ".bas";
internal const string FormBinaryExtension = ".frx";
internal const string DocClassExtension = ".doccls";

/// <summary>
/// Returns the proper file extension for the Component Type.
/// </summary>
/// <remarks>Document classes should properly have a ".cls" file extension.
/// However, because they cannot be removed and imported like other component types, we need to make a distinction.</remarks>
/// <param name="componentType"></param>
/// <returns>File extension that includes a preceeding "dot" (.) </returns>
public static string FileExtension(this ComponentType componentType)
{
switch (componentType)
{
case ComponentType.ClassModule:
return ClassExtension;
case ComponentType.UserForm:
return FormExtension;
case ComponentType.StandardModule:
return StandardExtension;
case ComponentType.Document:
// documents should technically be a ".cls", but we need to be able to tell them apart.
return DocClassExtension;
case ComponentType.ActiveXDesigner:
default:
return string.Empty;
}
}
}
}

0 comments on commit 3ec6220

Please sign in to comment.