Skip to content

Commit

Permalink
Browse files Browse the repository at this point in the history
  • Loading branch information
rubberduck203 committed Nov 30, 2014
2 parents 171becf + 7149649 commit e300691
Show file tree
Hide file tree
Showing 17 changed files with 147 additions and 47 deletions.
4 changes: 3 additions & 1 deletion RetailCoder.VBE/App.cs
Original file line number Diff line number Diff line change
Expand Up @@ -30,17 +30,19 @@ public App(VBE vbe, AddIn addIn)
var constructorInfo = type.GetConstructor(Type.EmptyTypes);
return constructorInfo != null ? constructorInfo.Invoke(Type.EmptyTypes) : null;
})
.Where(syntax => syntax != null)
.Cast<ISyntax>()
.ToList();

_inspections = Assembly.GetExecutingAssembly()
.GetTypes()
.Where(type => type.GetInterfaces().Contains(typeof(IInspection)))
.Where(type => type.BaseType == typeof(CodeInspection))
.Select(type =>
{
var constructor = type.GetConstructor(Type.EmptyTypes);
return constructor != null ? constructor.Invoke(Type.EmptyTypes) : null;
})
.Where(inspection => inspection != null)
.Cast<IInspection>()
.ToList();

Expand Down
37 changes: 37 additions & 0 deletions RetailCoder.VBE/Inspections/CodeInspection.cs
Original file line number Diff line number Diff line change
@@ -0,0 +1,37 @@
using System.Collections.Generic;
using System.Runtime.InteropServices;
using Rubberduck.VBA.Parser;

namespace Rubberduck.Inspections
{
[ComVisible(false)]
public abstract class CodeInspection : IInspection
{
protected CodeInspection(string name, string message, CodeInspectionType type, CodeInspectionSeverity severity)
{
_name = name;
_message = message;
_inspectionType = type;
Severity = severity;
}

private readonly string _name;
public string Name { get { return _name; } }

private readonly string _message;
public string QuickFixMessage { get { return _message; } }

private readonly CodeInspectionType _inspectionType;
public CodeInspectionType InspectionType { get { return _inspectionType; } }

public CodeInspectionSeverity Severity { get; set; }
public bool IsEnabled { get; set; }

/// <summary>
/// Inspects specified tree node, searching for code issues.
/// </summary>
/// <param name="node"></param>
/// <returns></returns>
public abstract IEnumerable<CodeInspectionResultBase> Inspect(SyntaxTreeNode node);
}
}
9 changes: 8 additions & 1 deletion RetailCoder.VBE/Inspections/CodeInspectionResultBase.cs
Original file line number Diff line number Diff line change
Expand Up @@ -7,13 +7,20 @@ namespace Rubberduck.Inspections
[ComVisible(false)]
public abstract class CodeInspectionResultBase
{
public CodeInspectionResultBase(Instruction instruction, CodeInspectionSeverity type, string message)
public CodeInspectionResultBase(string inspection, Instruction instruction, CodeInspectionSeverity type, string message)
{
_name = inspection;
_instruction = instruction;
_type = type;
_message = message;
}

private readonly string _name;
/// <summary>
/// Gets a string containing the name of the code inspection.
/// </summary>
public string Name { get { return _name; } }

private readonly Instruction _instruction;
/// <summary>
/// Gets the <see cref="Instruction"/> containing a code issue.
Expand Down
5 changes: 4 additions & 1 deletion RetailCoder.VBE/Inspections/CodeInspectionSeverity.cs
Original file line number Diff line number Diff line change
Expand Up @@ -5,7 +5,10 @@ namespace Rubberduck.Inspections
[ComVisible(false)]
public enum CodeInspectionSeverity
{
DoNotShow,
Hint,
Suggestion,
Warning
Warning,
Error
}
}
32 changes: 9 additions & 23 deletions RetailCoder.VBE/Inspections/ObsoleteCommentSyntaxInspection.cs
Original file line number Diff line number Diff line change
Expand Up @@ -7,38 +7,24 @@
namespace Rubberduck.Inspections
{
[ComVisible(false)]
public class ObsoleteCommentSyntaxInspection : IInspection
public class ObsoleteCommentSyntaxInspection : CodeInspection
{
/// <summary>
/// Parameterless constructor required for discovery of implemented code inspections.
/// </summary>
public ObsoleteCommentSyntaxInspection()
: base("Use of obsolete Rem comment syntax",
"Replace Rem reserved keyword with single quote.",
CodeInspectionType.MaintainabilityAndReadabilityIssues,
CodeInspectionSeverity.Suggestion)
{
_name = "Use of obsolete Rem comment syntax";
_quickFixMessage = "Replace Rem reserved keyword with single quote.";
_inspectionType = CodeInspectionType.MaintainabilityAndReadabilityIssues;
_severity = CodeInspectionSeverity.Suggestion;
}

private readonly string _name;
public string Name { get { return _name; } }

private readonly string _quickFixMessage;
public string QuickFixMessage { get { return _quickFixMessage; } }

private readonly CodeInspectionType _inspectionType;
public CodeInspectionType InspectionType { get { return _inspectionType; } }

private readonly CodeInspectionSeverity _severity;
public CodeInspectionSeverity Severity { get { return _severity; } }

public bool IsEnabled { get; set; }

public IEnumerable<CodeInspectionResultBase> Inspect(SyntaxTreeNode node)
public override IEnumerable<CodeInspectionResultBase> Inspect(SyntaxTreeNode node)
{
return node.FindAllComments()
.Where(instruction => instruction.Value == ReservedKeywords.Rem)
.Select(instruction => new ObsoleteCommentSyntaxInspectionResult(instruction, _severity, _quickFixMessage));
var comments = node.FindAllComments();
var remComments = comments.Where(instruction => instruction.Value.Trim().StartsWith(ReservedKeywords.Rem));
return remComments.Select(instruction => new ObsoleteCommentSyntaxInspectionResult(Name, instruction, Severity, QuickFixMessage));
}
}
}
Original file line number Diff line number Diff line change
Expand Up @@ -6,8 +6,8 @@ namespace Rubberduck.Inspections
{
public class ObsoleteCommentSyntaxInspectionResult : CodeInspectionResultBase
{
public ObsoleteCommentSyntaxInspectionResult(Instruction instruction, CodeInspectionSeverity type, string message)
: base(instruction, type, message)
public ObsoleteCommentSyntaxInspectionResult(string inspection, Instruction instruction, CodeInspectionSeverity type, string message)
: base(inspection, instruction, type, message)
{
}

Expand Down
20 changes: 20 additions & 0 deletions RetailCoder.VBE/Properties/Resources.Designer.cs

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

6 changes: 6 additions & 0 deletions RetailCoder.VBE/Properties/Resources.resx
Original file line number Diff line number Diff line change
Expand Up @@ -166,4 +166,10 @@
<data name="TestManager_8590_32" type="System.Resources.ResXFileRef, System.Windows.Forms">
<value>..\Resources\Microsoft\TestManager_8590_32.bmp;System.Drawing.Bitmap, System.Drawing, Version=4.0.0.0, Culture=neutral, PublicKeyToken=b03f5f7f11d50a3a</value>
</data>
<data name="ListsofTests_8643_24" type="System.Resources.ResXFileRef, System.Windows.Forms">
<value>..\Resources\ListsofTests_8643_24.bmp;System.Drawing.Bitmap, System.Drawing, Version=4.0.0.0, Culture=neutral, PublicKeyToken=b03f5f7f11d50a3a</value>
</data>
<data name="Step_RunTest_8814_32" type="System.Resources.ResXFileRef, System.Windows.Forms">
<value>..\Resources\Step-RunTest_8814_32.bmp;System.Drawing.Bitmap, System.Drawing, Version=4.0.0.0, Culture=neutral, PublicKeyToken=b03f5f7f11d50a3a</value>
</data>
</root>
Binary file added RetailCoder.VBE/Resources/ListsofTests_8643_24.bmp
Binary file not shown.
Binary file added RetailCoder.VBE/Resources/Step-RunTest_8814_32.bmp
Binary file not shown.
3 changes: 3 additions & 0 deletions RetailCoder.VBE/Rubberduck.csproj
Original file line number Diff line number Diff line change
Expand Up @@ -52,6 +52,7 @@
<Compile Include="Extensions\CodeModuleSelection.cs" />
<Compile Include="Extensions\Selection.cs" />
<Compile Include="Extensions\VbeExtensions.cs" />
<Compile Include="Inspections\CodeInspection.cs" />
<Compile Include="Inspections\CodeInspectionResultBase.cs" />
<Compile Include="Inspections\CodeInspectionSeverity.cs" />
<Compile Include="Inspections\CodeInspectionType.cs" />
Expand Down Expand Up @@ -321,11 +322,13 @@
<None Include="Resources\plus-circle.png" />
</ItemGroup>
<ItemGroup>
<None Include="Resources\Step-RunTest_8814_32.bmp" />
<None Include="Resources\Warning.bmp" />
<None Include="Resources\Serious.bmp" />
<None Include="Resources\OK.bmp" />
<None Include="Resources\GoLtrHS.bmp" />
<None Include="Resources\Critical.bmp" />
<None Include="Resources\ListsofTests_8643_24.bmp" />
<Content Include="Resources\Microsoft\AddClass_5561_32.bmp" />
<Content Include="Resources\Microsoft\AddEvent_5539_32.bmp" />
<Content Include="Resources\Microsoft\AddForm_369_32.bmp" />
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -4,6 +4,7 @@
using System.Runtime.InteropServices;
using System.Text;
using System.Threading.Tasks;
using System.Windows.Forms;
using Microsoft.Vbe.Interop;
using Rubberduck.Inspections;
using Rubberduck.VBA.Parser;
Expand Down Expand Up @@ -33,7 +34,11 @@ private void OnRefreshCodeInspections(object sender, EventArgs e)
var results = new List<CodeInspectionResultBase>();
foreach (var inspection in _inspections.Where(inspection => inspection.IsEnabled))
{
results.AddRange(inspection.Inspect(code));
var result = inspection.Inspect(code).ToArray();
if (result.Length != 0)
{
results.AddRange(result);
}
}

DrawResultTree(results);
Expand All @@ -44,8 +49,10 @@ private void DrawResultTree(IEnumerable<CodeInspectionResultBase> results)
var tree = Control.CodeInspectionResultsTree;
tree.Nodes.Clear();

foreach (var result in results)
foreach (var result in results.OrderBy(r => r.Severity))
{
var node = new TreeNode(result.Message);

tree.Nodes.Add(result.Message);
}
}
Expand Down
15 changes: 13 additions & 2 deletions RetailCoder.VBE/UI/CodeInspections/CodeInspectionsWindow.cs
Original file line number Diff line number Diff line change
Expand Up @@ -22,6 +22,19 @@ public CodeInspectionsWindow()
{
InitializeComponent();
RefreshButton.Click += RefreshButtonClicked;
CodeInspectionResultsTree.NodeMouseDoubleClick += TreeNodeMouseDoubleClicked;
}

public event EventHandler NavigateCodeIssue;
private void TreeNodeMouseDoubleClicked(object sender, TreeNodeMouseClickEventArgs e)
{
var handler = NavigateCodeIssue;
if (handler == null)
{
return;
}

handler(this, EventArgs.Empty);
}

public event EventHandler RefreshCodeInspections;
Expand All @@ -35,7 +48,5 @@ private void RefreshButtonClicked(object sender, EventArgs e)

handler(this, EventArgs.Empty);
}

public event EventHandler NavigateCodeIssue;
}
}
28 changes: 26 additions & 2 deletions RetailCoder.VBE/UI/Menu.cs
Original file line number Diff line number Diff line change
@@ -1,8 +1,10 @@
using System;
using System.Drawing;
using System.Runtime.InteropServices;
using Microsoft.Office.Core;
using Microsoft.Vbe.Interop;
using System.Windows.Forms;
using Rubberduck.Properties;

namespace Rubberduck.UI
{
Expand All @@ -20,9 +22,31 @@ public Menu(VBE vbe, AddIn addInInstance)
this.addInInstance = addInInstance;
}

protected CommandBarButton AddMenuButton(CommandBarPopup menu)
protected CommandBarButton AddMenuButton(CommandBarPopup menu, string caption, Bitmap image)
{
return menu.Controls.Add(MsoControlType.msoControlButton, Temporary: true) as CommandBarButton;
var result = menu.Controls.Add(MsoControlType.msoControlButton, Temporary: true) as CommandBarButton;
if (result == null)
{
throw new InvalidOperationException("Failed to create menu control.");
}

result.Caption = caption;
SetButtonImage(result, image);

return result;
}



private static void SetButtonImage(CommandBarButton result, Bitmap image)
{
result.FaceId = 0;

if (image != null)
{
Clipboard.SetDataObject(image, true);
result.PasteFace();
}
}

/// <summary>
Expand Down
13 changes: 3 additions & 10 deletions RetailCoder.VBE/UI/UnitTesting/TestMenu.cs
Original file line number Diff line number Diff line change
@@ -1,4 +1,5 @@
using System.Diagnostics;
using System.Drawing;
using System.Runtime.InteropServices;
using System.Windows.Forms;
using Microsoft.Office.Core;
Expand Down Expand Up @@ -38,19 +39,11 @@ public void Initialize(CommandBarControls menuControls)

menu.Caption = "Te&st";

_windowsTestExplorerButton = AddMenuButton(menu);
_windowsTestExplorerButton.Caption = "&Test Explorer";
_windowsTestExplorerButton.FaceId = 0;

Clipboard.SetDataObject(Resources.TestManager_8590_32, true);
_windowsTestExplorerButton.PasteFace();

_windowsTestExplorerButton = AddMenuButton(menu, "&Test Explorer", Resources.TestManager_8590_32);
_windowsTestExplorerButton.Click += OnTestExplorerButtonClick;

_runAllTestsButton = AddMenuButton(menu);
_runAllTestsButton = AddMenuButton(menu, "&Run All Tests", Resources.AllLoadedTests_8644_24);
_runAllTestsButton.BeginGroup = true;
_runAllTestsButton.Caption = "&Run All Tests";
_runAllTestsButton.FaceId = 186; // a "play" icon
_runAllTestsButton.Click += OnRunAllTestsButtonClick;
}

Expand Down
5 changes: 3 additions & 2 deletions RetailCoder.VBE/VBA/Parser/Grammar/StringExtensions.cs
Original file line number Diff line number Diff line change
Expand Up @@ -37,12 +37,13 @@ public static bool HasComment(this string line, out int index)
index = -1;
var instruction = line.StripStringLiterals();

for (var cursor = 0; cursor < instruction.Length - 1; cursor++)
var firstIndex = instruction.TakeWhile(c => c == ' ').Count();
for (var cursor = firstIndex; cursor < instruction.Length - 1; cursor++)
{
if (!string.IsNullOrWhiteSpace(instruction.Trim())
&&(instruction[cursor] == CommentMarker
|| (cursor == ReservedKeywords.Rem.Length
&& instruction.TrimStart().Substring(0, ReservedKeywords.Rem.Length) == ReservedKeywords.Rem)))
&& instruction.Trim().Substring(0, ReservedKeywords.Rem.Length) == ReservedKeywords.Rem)))
{
index = cursor;
return true;
Expand Down
2 changes: 1 addition & 1 deletion RetailCoder.VBE/VBA/Parser/Instruction.cs
Original file line number Diff line number Diff line change
Expand Up @@ -21,7 +21,7 @@ public Instruction(LogicalCodeLine line, int startColumn, int endColumn, string
if (_content.HasComment(out index))
{
_comment = _content.Substring(index);
_instruction = _content.Substring(0, index);
_instruction = _content.Trim().Substring(0, index);
}
else
{
Expand Down

0 comments on commit e300691

Please sign in to comment.