Skip to content

Commit f153743

Browse files
committed
Merge branch 'pull101' into next
2 parents 1a387f8 + 0d241d4 commit f153743

File tree

8 files changed

+277
-37
lines changed

8 files changed

+277
-37
lines changed

RetailCoder.VBE/Inspections/ObjectVariableNotSetInspection.cs

Lines changed: 18 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -47,7 +47,7 @@ public SetObjectVariableQuickFix(IdentifierReference reference)
4747
public override void Fix()
4848
{
4949
var codeModule = Selection.QualifiedName.Component.CodeModule;
50-
var codeLine = codeModule.get_Lines(Selection.Selection.StartLine, 1);
50+
var codeLine = codeModule.Lines[Selection.Selection.StartLine, 1];
5151

5252
var letStatementLeftSide = Context.GetText();
5353
var setStatementLeftSide = Tokens.Set + ' ' + letStatementLeftSide;
@@ -86,21 +86,26 @@ public ObjectVariableNotSetInspection(RubberduckParserState state)
8686

8787
public override IEnumerable<InspectionResultBase> GetInspectionResults()
8888
{
89-
return State.AllUserDeclarations
90-
.Where(item => !ValueTypes.Contains(item.AsTypeName)
91-
&& (item.AsTypeDeclaration != null && item.AsTypeDeclaration.DeclarationType != DeclarationType.UserDefinedType)
92-
&& !item.IsSelfAssigned
93-
&& (item.DeclarationType == DeclarationType.Variable
94-
|| item.DeclarationType == DeclarationType.Parameter))
89+
var interestingDeclarations =
90+
State.AllUserDeclarations.Where(item =>
91+
!item.IsSelfAssigned &&
92+
!ValueTypes.Contains(item.AsTypeName) &&
93+
(item.AsTypeDeclaration == null ||
94+
item.AsTypeDeclaration.DeclarationType != DeclarationType.Enumeration &&
95+
item.AsTypeDeclaration.DeclarationType != DeclarationType.UserDefinedType) &&
96+
(item.DeclarationType == DeclarationType.Variable ||
97+
item.DeclarationType == DeclarationType.Parameter));
98+
99+
var interestingReferences = interestingDeclarations
95100
.SelectMany(declaration =>
96101
declaration.References.Where(reference =>
97102
{
98-
var k = reference.Context.parent.GetType();
99-
var setStmtContext =
100-
ParserRuleContextHelper.GetParent<VBAParser.LetStmtContext>(reference.Context);
101-
return setStmtContext != null && setStmtContext.LET() == null;
102-
}))
103-
.Select(reference => new ObjectVariableNotSetInspectionResult(this, reference));
103+
var setStmtContext = ParserRuleContextHelper.GetParent<VBAParser.LetStmtContext>(reference.Context);
104+
return reference.IsAssignment && setStmtContext != null && setStmtContext.LET() == null;
105+
}));
106+
107+
108+
return interestingReferences.Select(reference => new ObjectVariableNotSetInspectionResult(this, reference));
104109
}
105110
}
106111
}

RetailCoder.VBE/Inspections/ObsoleteTypeHintInspection.cs

Lines changed: 12 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -22,12 +22,20 @@ public override IEnumerable<InspectionResultBase> GetInspectionResults()
2222

2323
var declarations = from item in results
2424
where item.HasTypeHint()
25-
// bug: this inspection result only has one value. Why are we passing two in?
26-
select new ObsoleteTypeHintInspectionResult(this, string.Format(InspectionsUI.ObsoleteTypeHintInspectionResultFormat, InspectionsUI.Inspections_Declaration, item.DeclarationType.ToString().ToLower(), item.IdentifierName), new QualifiedContext(item.QualifiedName, item.Context), item);
27-
// todo: localize this InspectionResultFormat properly
25+
select
26+
new ObsoleteTypeHintInspectionResult(this,
27+
string.Format(InspectionsUI.ObsoleteTypeHintInspectionResultFormat,
28+
InspectionsUI.Inspections_Declaration, item.DeclarationType.ToString().ToLower(),
29+
item.IdentifierName), new QualifiedContext(item.QualifiedName, item.Context), item);
30+
2831
var references = from item in results.SelectMany(d => d.References)
2932
where item.HasTypeHint()
30-
select new ObsoleteTypeHintInspectionResult(this, string.Format(InspectionsUI.ObsoleteTypeHintInspectionResultFormat, InspectionsUI.Inspections_Usage, item.Declaration.DeclarationType.ToString().ToLower(), item.IdentifierName), new QualifiedContext(item.QualifiedModuleName, item.Context), item.Declaration);
33+
select
34+
new ObsoleteTypeHintInspectionResult(this,
35+
string.Format(InspectionsUI.ObsoleteTypeHintInspectionResultFormat,
36+
InspectionsUI.Inspections_Usage, item.Declaration.DeclarationType.ToString().ToLower(),
37+
item.IdentifierName), new QualifiedContext(item.QualifiedModuleName, item.Context),
38+
item.Declaration);
3139

3240
return declarations.Union(references);
3341
}

RetailCoder.VBE/Inspections/UntypedFunctionUsageInspectionResult.cs

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,6 @@
11
using System;
22
using System.Collections.Generic;
3+
using System.Diagnostics;
34
using System.Linq;
45
using Antlr4.Runtime;
56
using Rubberduck.Parsing.Grammar;
@@ -72,6 +73,8 @@ public override void Fix()
7273

7374
private static string GetNewSignature(ParserRuleContext context)
7475
{
76+
Debug.Assert(context != null);
77+
7578
return context.children.Aggregate(string.Empty, (current, member) =>
7679
{
7780
var isIdentifierNode = member is VBAParser.IdentifierContext;

RetailCoder.VBE/Navigation/CodeExplorer/CodeExplorerItemViewModel.cs

Lines changed: 24 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -28,6 +28,22 @@ public override int Compare(CodeExplorerItemViewModel x, CodeExplorerItemViewMod
2828

2929
public class CompareByType : Comparer<CodeExplorerItemViewModel>
3030
{
31+
private static readonly Dictionary<DeclarationType, int> SortOrder = new Dictionary<DeclarationType, int>
32+
{
33+
{DeclarationType.LibraryFunction, 0},
34+
{DeclarationType.LibraryProcedure, 1},
35+
{DeclarationType.UserDefinedType, 2},
36+
{DeclarationType.Enumeration, 3},
37+
{DeclarationType.Event, 4},
38+
{DeclarationType.Constant, 5},
39+
{DeclarationType.Variable, 6},
40+
{DeclarationType.PropertyGet, 7},
41+
{DeclarationType.PropertyLet, 8},
42+
{DeclarationType.PropertySet, 9},
43+
{DeclarationType.Function, 10},
44+
{DeclarationType.Procedure, 11}
45+
};
46+
3147
public override int Compare(CodeExplorerItemViewModel x, CodeExplorerItemViewModel y)
3248
{
3349
if (x == y)
@@ -54,6 +70,14 @@ public override int Compare(CodeExplorerItemViewModel x, CodeExplorerItemViewMod
5470
// keep separate types separate
5571
if (xNode.Declaration.DeclarationType != yNode.Declaration.DeclarationType)
5672
{
73+
int xValue, yValue;
74+
75+
if (SortOrder.TryGetValue(xNode.Declaration.DeclarationType, out xValue) &&
76+
SortOrder.TryGetValue(yNode.Declaration.DeclarationType, out yValue))
77+
{
78+
return xValue < yValue ? -1 : 1;
79+
}
80+
5781
return xNode.Declaration.DeclarationType < yNode.Declaration.DeclarationType ? -1 : 1;
5882
}
5983

RetailCoder.VBE/UI/Command/IndentCurrentProcedureCommand.cs

Lines changed: 12 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,6 @@
11
using System.Runtime.InteropServices;
2+
using Microsoft.Vbe.Interop;
3+
using Rubberduck.Parsing.VBA;
24
using Rubberduck.Settings;
35
using Rubberduck.SmartIndenter;
46

@@ -7,13 +9,22 @@ namespace Rubberduck.UI.Command
79
[ComVisible(false)]
810
public class IndentCurrentProcedureCommand : CommandBase
911
{
12+
private readonly VBE _vbe;
13+
private readonly RubberduckParserState _state;
1014
private readonly IIndenter _indenter;
1115

12-
public IndentCurrentProcedureCommand(IIndenter indenter)
16+
public IndentCurrentProcedureCommand(VBE vbe, RubberduckParserState state, IIndenter indenter)
1317
{
18+
_vbe = vbe;
19+
_state = state;
1420
_indenter = indenter;
1521
}
1622

23+
public override bool CanExecute(object parameter)
24+
{
25+
return _state.FindSelectedDeclaration(_vbe.ActiveCodePane, true) != null;
26+
}
27+
1728
public override void Execute(object parameter)
1829
{
1930
_indenter.IndentCurrentProcedure();

Rubberduck.Parsing/Symbols/ReferencedDeclarationsCollector.cs

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -174,6 +174,7 @@ public IEnumerable<Declaration> GetDeclarationsForReference(Reference reference)
174174
info.GetTypeAttr(out typeAttributesPointer);
175175

176176
var typeAttributes = (TYPEATTR)Marshal.PtrToStructure(typeAttributesPointer, typeof(TYPEATTR));
177+
info.ReleaseTypeAttr(typeAttributesPointer);
177178

178179
var attributes = new Attributes();
179180
if (typeAttributes.wTypeFlags.HasFlag(TYPEFLAGS.TYPEFLAG_FPREDECLID))
@@ -243,6 +244,7 @@ private Declaration CreateMemberDeclaration(out FUNCDESC memberDescriptor, TYPEK
243244
IntPtr memberDescriptorPointer;
244245
info.GetFuncDesc(memberIndex, out memberDescriptorPointer);
245246
memberDescriptor = (FUNCDESC)Marshal.PtrToStructure(memberDescriptorPointer, typeof(FUNCDESC));
247+
info.ReleaseFuncDesc(memberDescriptorPointer);
246248

247249
if (memberDescriptor.callconv != CALLCONV.CC_STDCALL)
248250
{
@@ -390,6 +392,7 @@ private Declaration CreateFieldDeclaration(ITypeInfo info, int fieldIndex, Decla
390392
info.GetVarDesc(fieldIndex, out ppVarDesc);
391393

392394
var varDesc = (VARDESC)Marshal.PtrToStructure(ppVarDesc, typeof(VARDESC));
395+
info.ReleaseVarDesc(ppVarDesc);
393396

394397
var names = new string[255];
395398
int namesArrayLength;

Rubberduck.SmartIndenter/Indenter.cs

Lines changed: 20 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -48,6 +48,11 @@ private void OnReportProgress(string moduleName, int progress, int max)
4848
public void IndentCurrentProcedure()
4949
{
5050
var pane = _vbe.ActiveCodePane;
51+
52+
if (pane == null)
53+
{
54+
return;
55+
}
5156
var module = pane.CodeModule;
5257
var selection = GetSelection(pane);
5358

@@ -69,6 +74,10 @@ public void IndentCurrentProcedure()
6974
public void IndentCurrentModule()
7075
{
7176
var pane = _vbe.ActiveCodePane;
77+
if (pane == null)
78+
{
79+
return;
80+
}
7281
Indent(pane.CodeModule.Parent);
7382
}
7483

@@ -288,12 +297,12 @@ public void Indent(string[] codeLines, string moduleName, bool reportProgress =
288297
break;
289298

290299
case ": ":
291-
// a multi-statement line separator => tidy up and continue
292-
if (!currentLine.Substring(0, scan + 1).EndsWith("Then:"))
300+
//a multi-statement line separator => tidy up and continue
301+
if (!currentLine.Substring(0, scan + 1).EndsWith(" Then:"))
293302
{
294-
currentLine = currentLine.Substring(0, scan + 1) + currentLine.Substring(scan + 2);
303+
currentLine = currentLine.Substring(0, scan + 2) + currentLine.Substring(scan + 2);
295304
// check the indenting for the line segment
296-
CheckLine(settings, currentLine, ref noIndent, out ins, out outs, ref atProcedureStart, ref atFirstProcLine, ref isInsideIfBlock);
305+
CheckLine(settings, currentLine.Substring(start - 1), ref noIndent, out ins, out outs, ref atProcedureStart, ref atFirstProcLine, ref isInsideIfBlock);
297306
if (atProcedureStart)
298307
{
299308
atFirstDim = true;
@@ -455,27 +464,23 @@ public void Indent(string[] codeLines, string moduleName, bool reportProgress =
455464
(settings.EndOfLineCommentStyle == EndOfLineCommentStyle.Absolute ||
456465
settings.EndOfLineCommentStyle == EndOfLineCommentStyle.AlignInColumn))
457466
{
458-
gap -= lineNumber.Length - indents*settings.IndentSpaces - 1;
459-
}
460-
if (gap < 2)
461-
{
462-
gap = settings.IndentSpaces;
467+
gap -= lineNumber.Length - indents * settings.IndentSpaces - 1;
463468
}
464469

465470
commentStart = currentLine.Length + gap;
466471
currentLine += new string(' ', gap) + right;
467472
}
468473

469474
// work out where the text of the comment starts, to align the next line
470-
if (currentLine.Substring(commentStart, 4) == "Rem ")
475+
if (commentStart < currentLine.Length - 4 && currentLine.Substring(commentStart, 4) == "Rem ")
471476
{
472477
commentStart += 3;
473478
}
474-
if (currentLine.Substring(commentStart, 1) == "'")
479+
if (commentStart < currentLine.Length && currentLine.Substring(commentStart, 1) == "'")
475480
{
476481
commentStart += 1;
477482
}
478-
while (currentLine.Substring(commentStart, 1) != " ")
483+
while (commentStart < currentLine.Length && currentLine.Substring(commentStart, 1) != " ")
479484
{
480485
commentStart += 1;
481486
}
@@ -528,7 +533,9 @@ public void Indent(string[] codeLines, string moduleName, bool reportProgress =
528533
atProcedureStart = false;
529534
}
530535

531-
CheckLine(settings, currentLine.Substring(start - 1, scan - 1), ref noIndent, out ins, out outs, ref atProcedureStart, ref atFirstProcLine, ref isInsideIfBlock);
536+
CheckLine(settings, currentLine.Substring(start - 1, Math.Min(scan - 1, currentLine.Length - start)),
537+
ref noIndent, out ins, out outs, ref atProcedureStart, ref atFirstProcLine,
538+
ref isInsideIfBlock);
532539
if (atProcedureStart)
533540
{
534541
atFirstDim = true;

0 commit comments

Comments
 (0)