Skip to content

Commit d112a03

Browse files
committed
Merge branch 'Issue2069' of https://github.com/Hosch250/Rubberduck
2 parents 3976556 + 4385dfb commit d112a03

34 files changed

+2589
-1329
lines changed

Installer Build Script.iss

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -27,6 +27,7 @@ OutputDir={#OutputDirectory}
2727
OutputBaseFilename=Rubberduck.Setup.{#AppVersion}
2828
Compression=lzma
2929
SolidCompression=yes
30+
SignTool=RubberduckSignTool /d $qRubberduck Installer$q $f
3031

3132
ArchitecturesAllowed=x86 x64
3233
ArchitecturesInstallIn64BitMode=x64

RetailCoder.VBE/Inspections/ParameterCanBeByValInspection.cs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -44,6 +44,7 @@ public override IEnumerable<InspectionResultBase> GetInspectionResults()
4444

4545
issues.AddRange(declarations.Where(declaration =>
4646
!declaration.IsArray
47+
&& (declaration.AsTypeDeclaration == null || declaration.AsTypeDeclaration.DeclarationType != DeclarationType.UserDefinedType)
4748
&& !declareScopes.Contains(declaration.ParentScope)
4849
&& !eventScopes.Contains(declaration.ParentScope)
4950
&& !interfaceScopes.Contains(declaration.ParentScope)

RetailCoder.VBE/Inspections/UnassignedVariableUsageInspection.cs

Lines changed: 39 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,7 @@
11
using System.Collections.Generic;
22
using System.Linq;
3+
using Antlr4.Runtime;
4+
using Rubberduck.Parsing;
35
using Rubberduck.Parsing.Symbols;
46
using Rubberduck.Parsing.VBA;
57

@@ -27,10 +29,46 @@ public override IEnumerable<InspectionResultBase> GetInspectionResults()
2729
.SelectMany(declaration => declaration.References)
2830
.Where(usage => !usage.IsInspectionDisabled(AnnotationName));
2931

32+
var lenFunction = BuiltInDeclarations.SingleOrDefault(s => s.Scope == "VBE7.DLL;VBA.Strings.Len");
33+
var lenbFunction = BuiltInDeclarations.SingleOrDefault(s => s.Scope == "VBE7.DLL;VBA.Strings.LenB");
34+
3035
foreach (var issue in usages)
3136
{
32-
yield return new UnassignedVariableUsageInspectionResult(this, issue.Context, issue.QualifiedModuleName, issue.Declaration);
37+
if (DeclarationReferencesContainsReference(lenFunction, issue) ||
38+
DeclarationReferencesContainsReference(lenbFunction, issue))
39+
{
40+
continue;
41+
}
42+
43+
yield return
44+
new UnassignedVariableUsageInspectionResult(this, issue.Context, issue.QualifiedModuleName,
45+
issue.Declaration);
46+
}
47+
}
48+
49+
private bool DeclarationReferencesContainsReference(Declaration parentDeclaration, IdentifierReference issue)
50+
{
51+
if (parentDeclaration == null)
52+
{
53+
return false;
54+
}
55+
56+
var lenUsesIssue = false;
57+
foreach (var reference in parentDeclaration.References)
58+
{
59+
var context = (ParserRuleContext) reference.Context.Parent;
60+
if (context.GetSelection().Contains(issue.Selection))
61+
{
62+
lenUsesIssue = true;
63+
break;
64+
}
65+
}
66+
67+
if (lenUsesIssue)
68+
{
69+
return true;
3370
}
71+
return false;
3472
}
3573
}
3674
}

RetailCoder.VBE/Properties/AssemblyInfo.cs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -31,5 +31,5 @@
3131
// You can specify all the values or you can default the Build and Revision Numbers
3232
// by using the '*' as shown below:
3333
// [assembly: AssemblyVersion("1.0.*")]
34-
[assembly: AssemblyVersion("2.0.5.*")]
35-
[assembly: AssemblyFileVersion("2.0.5.0")]
34+
[assembly: AssemblyVersion("2.0.6.*")]
35+
[assembly: AssemblyFileVersion("2.0.6.0")]

RetailCoder.VBE/Refactorings/ExtractInterface/ExtractInterfaceModel.cs

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -42,7 +42,6 @@ public ExtractInterfaceModel(RubberduckParserState state, QualifiedSelection sel
4242

4343
if (_targetDeclaration == null)
4444
{
45-
//throw new InvalidOperationException();
4645
return;
4746
}
4847

RetailCoder.VBE/Refactorings/ExtractInterface/ExtractInterfacePresenter.cs

Lines changed: 4 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -22,7 +22,10 @@ public ExtractInterfacePresenter(IExtractInterfaceDialog view, ExtractInterfaceM
2222

2323
public ExtractInterfaceModel Show()
2424
{
25-
if (_model.TargetDeclaration == null) { return null; }
25+
if (_model.TargetDeclaration == null)
26+
{
27+
return null;
28+
}
2629

2730
_view.ComponentNames =
2831
_model.TargetDeclaration.Project.VBComponents.Cast<VBComponent>().Select(c => c.Name).ToList();

RetailCoder.VBE/Refactorings/ExtractInterface/ExtractInterfacePresenterFactory.cs

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,6 @@
11
using System.Linq;
22
using Microsoft.Vbe.Interop;
33
using Rubberduck.Parsing.VBA;
4-
using Rubberduck.VBEditor.Extensions;
54

65
namespace Rubberduck.Refactorings.ExtractInterface
76
{
@@ -20,7 +19,7 @@ public ExtractInterfacePresenterFactory(VBE vbe, RubberduckParserState state, IE
2019

2120
public ExtractInterfacePresenter Create()
2221
{
23-
var selection = _vbe.ActiveCodePane.CodeModule.GetSelection();
22+
var selection = _vbe.ActiveCodePane.GetQualifiedSelection();
2423
if (selection == null)
2524
{
2625
return null;

RetailCoder.VBE/Refactorings/ExtractInterface/ExtractInterfaceRefactoring.cs

Lines changed: 6 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -17,11 +17,11 @@ public class ExtractInterfaceRefactoring : IRefactoring
1717
private readonly VBE _vbe;
1818
private readonly RubberduckParserState _state;
1919
private readonly IMessageBox _messageBox;
20-
private readonly IRefactoringPresenterFactory<ExtractInterfacePresenter> _factory;
20+
private readonly IRefactoringPresenterFactory<IExtractInterfacePresenter> _factory;
2121
private ExtractInterfaceModel _model;
2222
private static readonly Logger Logger = LogManager.GetCurrentClassLogger();
2323

24-
public ExtractInterfaceRefactoring(VBE vbe, RubberduckParserState state, IMessageBox messageBox, IRefactoringPresenterFactory<ExtractInterfacePresenter> factory)
24+
public ExtractInterfaceRefactoring(VBE vbe, RubberduckParserState state, IMessageBox messageBox, IRefactoringPresenterFactory<IExtractInterfacePresenter> factory)
2525
{
2626
_vbe = vbe;
2727
_state = state;
@@ -38,7 +38,6 @@ public void Refactor()
3838
}
3939

4040
_model = presenter.Show();
41-
4241
if (_model == null)
4342
{
4443
return;
@@ -66,8 +65,8 @@ private void AddInterface()
6665
var interfaceComponent = _model.TargetDeclaration.Project.VBComponents.Add(vbext_ComponentType.vbext_ct_ClassModule);
6766
interfaceComponent.Name = _model.InterfaceName;
6867

69-
_vbe.ActiveCodePane.CodeModule.InsertLines(1, Tokens.Option + ' ' + Tokens.Explicit + Environment.NewLine);
70-
_vbe.ActiveCodePane.CodeModule.InsertLines(3, GetInterfaceModuleBody());
68+
interfaceComponent.CodeModule.InsertLines(1, Tokens.Option + ' ' + Tokens.Explicit + Environment.NewLine);
69+
interfaceComponent.CodeModule.InsertLines(3, GetInterfaceModuleBody());
7170

7271
var module = _model.TargetDeclaration.QualifiedSelection.QualifiedName.Component.CodeModule;
7372

@@ -85,14 +84,13 @@ private void _state_StateChanged(object sender, EventArgs e)
8584
{
8685
return;
8786
}
88-
87+
88+
_state.StateChanged -= _state_StateChanged;
8989
var qualifiedSelection = new QualifiedSelection(_model.TargetDeclaration.QualifiedSelection.QualifiedName, new Selection(_insertionLine, 1, _insertionLine, 1));
9090
_vbe.ActiveCodePane.CodeModule.SetSelection(qualifiedSelection);
9191

9292
var implementInterfaceRefactoring = new ImplementInterfaceRefactoring(_vbe, _state, _messageBox);
9393
implementInterfaceRefactoring.Refactor(qualifiedSelection);
94-
95-
_state.StateChanged -= _state_StateChanged;
9694
}
9795

9896
private string GetInterfaceModuleBody()

RetailCoder.VBE/Refactorings/ExtractInterface/InterfaceMember.cs

Lines changed: 19 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -46,17 +46,25 @@ public InterfaceMember(Declaration member, IEnumerable<Declaration> declarations
4646

4747
GetMethodType();
4848

49-
MemberParams = declarations.Where(item => item.DeclarationType == DeclarationType.Parameter &&
50-
item.ParentScope == Member.Scope)
51-
.OrderBy(o => o.Selection.StartLine)
52-
.ThenBy(t => t.Selection.StartColumn)
53-
.Select(p => new Parameter
54-
{
55-
ParamAccessibility = ((VBAParser.ArgContext)p.Context).BYREF() == null ? Tokens.ByVal : Tokens.ByRef,
56-
ParamName = p.IdentifierName,
57-
ParamType = p.AsTypeName
58-
})
59-
.ToList();
49+
var memberWithParams = member as IDeclarationWithParameter;
50+
if (memberWithParams != null)
51+
{
52+
MemberParams = memberWithParams.Parameters
53+
.OrderBy(o => o.Selection.StartLine)
54+
.ThenBy(t => t.Selection.StartColumn)
55+
.Select(p => new Parameter
56+
{
57+
ParamAccessibility =
58+
((VBAParser.ArgContext) p.Context).BYVAL() != null ? Tokens.ByVal : Tokens.ByRef,
59+
ParamName = p.IdentifierName,
60+
ParamType = p.AsTypeName
61+
})
62+
.ToList();
63+
}
64+
else
65+
{
66+
MemberParams = new List<Parameter>();
67+
}
6068

6169
if (MemberType == "Property Get")
6270
{

RetailCoder.VBE/Refactorings/ImplementInterface/ImplementInterfaceRefactoring.cs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -17,7 +17,7 @@ public class ImplementInterfaceRefactoring : IRefactoring
1717
private readonly RubberduckParserState _state;
1818
private readonly IMessageBox _messageBox;
1919

20-
private List<Declaration> _declarations;
20+
private readonly List<Declaration> _declarations;
2121
private Declaration _targetInterface;
2222
private Declaration _targetClass;
2323

@@ -91,7 +91,7 @@ private void AddItems(List<Declaration> members)
9191

9292
var missingMembersText = members.Aggregate(string.Empty, (current, member) => current + Environment.NewLine + GetInterfaceMember(member));
9393

94-
module.InsertLines(module.CountOfDeclarationLines + 2, missingMembersText);
94+
module.InsertLines(module.CountOfDeclarationLines + 1, missingMembersText);
9595
}
9696

9797
private string GetInterfaceMember(Declaration member)

0 commit comments

Comments
 (0)