Skip to content

Commit

Permalink
Merge pull request #155 from rubberduck-vba/next
Browse files Browse the repository at this point in the history
sync with main repo
  • Loading branch information
retailcoder committed Aug 31, 2016
2 parents fa86c17 + 750bfcd commit ccf003c
Show file tree
Hide file tree
Showing 8 changed files with 194 additions and 9 deletions.
30 changes: 21 additions & 9 deletions RetailCoder.VBE/Inspections/ObjectVariableNotSetInspection.cs
Original file line number Diff line number Diff line change
Expand Up @@ -14,12 +14,12 @@ public sealed class ObjectVariableNotSetInspectionResult : InspectionResultBase
private readonly IEnumerable<CodeInspectionQuickFix> _quickFixes;

public ObjectVariableNotSetInspectionResult(IInspection inspection, IdentifierReference reference)
:base(inspection, reference.QualifiedModuleName, reference.Context)
: base(inspection, reference.QualifiedModuleName, reference.Context)
{
_reference = reference;
_quickFixes = new CodeInspectionQuickFix[]
{
new SetObjectVariableQuickFix(_reference),
new SetObjectVariableQuickFix(_reference),
new IgnoreOnceQuickFix(Context, QualifiedSelection, Inspection.AnnotationName),
};
}
Expand All @@ -36,7 +36,7 @@ public sealed class SetObjectVariableQuickFix : CodeInspectionQuickFix
{
public SetObjectVariableQuickFix(IdentifierReference reference)
: base(context: reference.Context.Parent.Parent as ParserRuleContext, // ImplicitCallStmt_InStmtContext
selection: new QualifiedSelection(reference.QualifiedModuleName, reference.Selection),
selection: new QualifiedSelection(reference.QualifiedModuleName, reference.Selection),
description: InspectionsUI.SetObjectVariableQuickFix)
{
}
Expand Down Expand Up @@ -96,13 +96,25 @@ public override IEnumerable<InspectionResultBase> GetInspectionResults()
(item.DeclarationType == DeclarationType.Variable ||
item.DeclarationType == DeclarationType.Parameter));

var interestingMembers =
State.AllUserDeclarations.Where(item =>
(item.DeclarationType == DeclarationType.Function || item.DeclarationType == DeclarationType.PropertyGet)
&& item.IsTypeSpecified
&& !ValueTypes.Contains(item.AsTypeName));

var interestingReferences = interestingDeclarations
.SelectMany(declaration =>
declaration.References.Where(reference =>
{
var setStmtContext = ParserRuleContextHelper.GetParent<VBAParser.LetStmtContext>(reference.Context);
return reference.IsAssignment && setStmtContext != null && setStmtContext.LET() == null;
}));
.Union(interestingMembers.SelectMany(item =>
item.References.Where(reference =>
reference.ParentScoping == item && reference.IsAssignment
).Select(reference => reference.Declaration))
)
.SelectMany(declaration =>
declaration.References.Where(reference =>
{
var setStmtContext = ParserRuleContextHelper.GetParent<VBAParser.LetStmtContext>(reference.Context);
return reference.IsAssignment && setStmtContext != null && setStmtContext.LET() == null;
})
);


return interestingReferences.Select(reference => new ObjectVariableNotSetInspectionResult(this, reference));
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -18,6 +18,7 @@ public abstract class ParentMenuItemBase : IParentMenuItem
private readonly int? _beforeIndex;
private readonly IDictionary<IMenuItem, CommandBarControl> _items;
private static readonly Logger Logger = LogManager.GetCurrentClassLogger();
private static bool? _useClipboardForMenuIcons;

protected ParentMenuItemBase(string key, IEnumerable<IMenuItem> items, int? beforeIndex = null)
{
Expand Down Expand Up @@ -178,6 +179,20 @@ public static void SetButtonImage(CommandBarButton button, Image image, Image ma
return;
}

if (!_useClipboardForMenuIcons.HasValue)
{
_useClipboardForMenuIcons = !HasPictureProperty(button);
}

if ((bool)_useClipboardForMenuIcons)
{
Bitmap bitMask = MaskedImage(image, mask);
Clipboard.SetImage(bitMask);
button.PasteFace();
Clipboard.Clear();
return;
}

try
{
button.Picture = AxHostConverter.ImageToPictureDisp(image);
Expand All @@ -189,6 +204,41 @@ public static void SetButtonImage(CommandBarButton button, Image image, Image ma
}
}

private static Bitmap MaskedImage(Image image, Image mask)
{
//HACK - just blend image with buttonface color (mask is ignored)
//TODO - a real solution would use clipboard formats "Toolbar Button Face" AND "Toolbar Button Mask"
//because PasteFace apparently needs both to be present on the clipboard
//However, the clipboard formats are apparently only accessible in English versions of Office
//https://social.msdn.microsoft.com/Forums/office/en-US/33e97c32-9fc2-4531-b208-67c39ccfb048/question-about-toolbar-button-face-in-pasteface-?forum=vsto

Bitmap output = new Bitmap(image.Width, image.Height, System.Drawing.Imaging.PixelFormat.Format32bppArgb);

using (Graphics g = Graphics.FromImage(output))
{
g.Clear(SystemColors.ButtonFace);
g.DrawImage(image, 0, 0);
}
return output;
}

private static bool HasPictureProperty(CommandBarButton button)
{
try
{
dynamic control = button;
object picture = control.Picture;
return true;
}

catch (Microsoft.CSharp.RuntimeBinder.RuntimeBinderException exception)
{
Logger.Debug("Button image cannot be set for button [" + button.Caption + "], because Host VBE CommandBars are too old.\n" + exception);
}

return false;
}

private class AxHostConverter : AxHost
{
private AxHostConverter() : base(string.Empty) { }
Expand Down
6 changes: 6 additions & 0 deletions Rubberduck.VBEEditor/Extensions/VbeExtensions.cs
Original file line number Diff line number Diff line change
Expand Up @@ -81,6 +81,8 @@ public static IHostApplication HostApplication(this VBE vbe)
return new AutoCADApp();
case "CorelDRAW":
return new CorelDRAWApp();
case "SolidWorks":
return new SolidWorksApp(vbe);
}
}
return null;
Expand Down Expand Up @@ -111,6 +113,8 @@ public static IHostApplication HostApplication(this VBE vbe)
return new AutoCADApp();
case "CorelDRAW":
return new CorelDRAWApp(vbe);
case "SolidWorks":
return new SolidWorksApp(vbe);
}
}

Expand Down Expand Up @@ -143,6 +147,7 @@ public static bool HostSupportsUnitTests(this VBE vbe)
case "Microsoft Visio":
case "AutoCAD":
case "CorelDRAW":
case "SolidWorks":
return true;
default:
return false;
Expand All @@ -164,6 +169,7 @@ public static bool HostSupportsUnitTests(this VBE vbe)
case "Visio":
case "AutoCAD":
case "CorelDRAW":
case "SolidWorks":
return true;
}
}
Expand Down
9 changes: 9 additions & 0 deletions Rubberduck.VBEEditor/Rubberduck.VBEditor.csproj
Original file line number Diff line number Diff line change
Expand Up @@ -31,6 +31,14 @@
<WarningLevel>4</WarningLevel>
</PropertyGroup>
<ItemGroup>
<Reference Include="Interop.SldWorks.Extensibility">
<HintPath>..\libs\Interop.SldWorks.Extensibility.dll</HintPath>
<EmbedInteropTypes>True</EmbedInteropTypes>
</Reference>
<Reference Include="Interop.SldWorks.Types">
<HintPath>..\libs\Interop.SldWorks.Types.dll</HintPath>
<EmbedInteropTypes>True</EmbedInteropTypes>
</Reference>
<Reference Include="Microsoft.CSharp" />
<Reference Include="Microsoft.Office.Interop.Access, Version=12.0.0.0, Culture=neutral, PublicKeyToken=71e9bce111e9429c">
<SpecificVersion>False</SpecificVersion>
Expand Down Expand Up @@ -127,6 +135,7 @@
<Compile Include="VBEHost\OutlookApp.cs" />
<Compile Include="VBEHost\PowerPointApp.cs" />
<Compile Include="VBEHost\PublisherApp.cs" />
<Compile Include="VBEHost\SolidWorksApp.cs" />
<Compile Include="VBEHost\Visio.cs" />
<Compile Include="VBEHost\WordApp.cs" />
<Compile Include="VBEHost\AutoCADApp.cs" />
Expand Down
24 changes: 24 additions & 0 deletions Rubberduck.VBEEditor/VBEHost/SolidWorksApp.cs
Original file line number Diff line number Diff line change
@@ -0,0 +1,24 @@
using Interop.SldWorks.Types;
using Microsoft.Vbe.Interop;

namespace Rubberduck.VBEditor.VBEHost
{
public class SolidWorksApp : HostApplicationBase<Interop.SldWorks.Extensibility.Application>
{
public SolidWorksApp() : base("SolidWorks") { }
public SolidWorksApp(VBE vbe) : base(vbe, "SolidWorks") { }

public override void Run(QualifiedMemberName qualifiedMemberName)
{
var projectFileName = qualifiedMemberName.QualifiedModuleName.Project.FileName;
var moduleName = qualifiedMemberName.QualifiedModuleName.ComponentName;
var memberName = qualifiedMemberName.MemberName;

if (Application != null)
{
SldWorks runner = (SldWorks)Application.SldWorks;
runner.RunMacro(projectFileName, moduleName, memberName);
}
}
}
}
84 changes: 84 additions & 0 deletions RubberduckTests/Inspections/ObjectVariableNotSetInpsectionTests.cs
Original file line number Diff line number Diff line change
Expand Up @@ -215,5 +215,89 @@ public void ObjectVariableNotSet_IgnoreQuickFixWorks()

Assert.AreEqual(expectedCode, module.Lines());
}

[TestMethod]
[TestCategory("Inspections")]
public void ObjectVariableNotSet_ForFunctionAssignment_ReturnsResult()
{
const string inputCode = @"
Private Function CombineRanges(ByVal source As Range, ByVal toCombine As Range) As Range
If source Is Nothing Then
CombineRanges = toCombine 'no inspection result (but there should be one!)
Else
CombineRanges = Union(source, toCombine) 'no inspection result (but there should be one!)
End If
End Function";

const string expectedCode = @"
Private Function CombineRanges(ByVal source As Range, ByVal toCombine As Range) As Range
If source Is Nothing Then
Set CombineRanges = toCombine 'no inspection result (but there should be one!)
Else
Set CombineRanges = Union(source, toCombine) 'no inspection result (but there should be one!)
End If
End Function";

//Arrange
var builder = new MockVbeBuilder();
VBComponent component;
var vbe = builder.BuildFromSingleStandardModule(inputCode, out component);
var module = vbe.Object.VBProjects.Item(0).VBComponents.Item(0).CodeModule;
var mockHost = new Mock<IHostApplication>();
mockHost.SetupAllProperties();
var parser = MockParser.Create(vbe.Object, new RubberduckParserState(new Mock<ISinks>().Object));

parser.Parse(new CancellationTokenSource());
if (parser.State.Status >= ParserState.Error) { Assert.Inconclusive("Parser Error"); }

var inspection = new ObjectVariableNotSetInspection(parser.State);
var inspectionResults = inspection.GetInspectionResults();

Assert.AreEqual(2, inspectionResults.Count());
foreach (var fix in inspectionResults.SelectMany(result => result.QuickFixes.Where(s => s is SetObjectVariableQuickFix)))
{
fix.Fix();
}
Assert.AreEqual(expectedCode, module.Lines());
}

[TestMethod]
[TestCategory("Inspections")]
public void ObjectVariableNotSet_ForPropertyGetAssignment_ReturnsResults()
{
const string inputCode = @"
Private example As MyObject
Public Property Get Example() As MyObject
Example = example
End Property
";
const string expectedCode = @"
Private example As MyObject
Public Property Get Example() As MyObject
Set Example = example
End Property
";
//Arrange
var builder = new MockVbeBuilder();
VBComponent component;
var vbe = builder.BuildFromSingleStandardModule(inputCode, out component);
var module = vbe.Object.VBProjects.Item(0).VBComponents.Item(0).CodeModule;
var mockHost = new Mock<IHostApplication>();
mockHost.SetupAllProperties();
var parser = MockParser.Create(vbe.Object, new RubberduckParserState(new Mock<ISinks>().Object));

parser.Parse(new CancellationTokenSource());
if (parser.State.Status >= ParserState.Error) { Assert.Inconclusive("Parser Error"); }

var inspection = new ObjectVariableNotSetInspection(parser.State);
var inspectionResults = inspection.GetInspectionResults();

Assert.AreEqual(1, inspectionResults.Count());
foreach (var fix in inspectionResults.SelectMany(result => result.QuickFixes.Where(s => s is SetObjectVariableQuickFix)))
{
fix.Fix();
}
Assert.AreEqual(expectedCode, module.Lines());
}
}
}
Binary file added libs/Interop.SldWorks.Extensibility.dll
Binary file not shown.
Binary file added libs/Interop.SldWorks.Types.dll
Binary file not shown.

0 comments on commit ccf003c

Please sign in to comment.