Skip to content

Commit bcba323

Browse files
committed
Merge branch 'next' of git://github.com/rubberduck-vba/Rubberduck into scp-bugfix
2 parents d51c2a5 + 4bfdbbb commit bcba323

File tree

145 files changed

+12097
-4995
lines changed

Some content is hidden

Large Commits have some content hidden by default. Use the searchbox below for content that may be hidden.

145 files changed

+12097
-4995
lines changed

.github/ISSUE_TEMPLATE/bug_report.md

Lines changed: 39 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,39 @@
1+
---
2+
name: Bug report
3+
about: Rubberduck does not work as expected
4+
title: ''
5+
labels: bug
6+
assignees: ''
7+
8+
---
9+
**Rubberduck version information**
10+
The info below can be copy-paste-completed from the first lines of Rubberduck's Log or the About box:
11+
12+
Rubberduck version [...]
13+
Operating System: [...]
14+
Host Product: [...]
15+
Host Version: [...]
16+
Host Executable: [...]
17+
18+
19+
**Description**
20+
A clear and concise description of what the bug is.
21+
22+
**To Reproduce**
23+
Steps to reproduce the behavior:
24+
1. Go to '...'
25+
2. Click on '....'
26+
3. Scroll down to '....'
27+
4. See error
28+
29+
**Expected behavior**
30+
A clear and concise description of what you expected to happen.
31+
32+
**Screenshots**
33+
If applicable, add screenshots to help explain your problem.
34+
35+
**Logfile**
36+
Rubberduck generates extensive logging in TRACE-Level. If no log was created at `%APP_DATA%\Rubberduck\Logs`, check your settings. Include this Log for bugreports about the behavior of Rubbberduck
37+
38+
**Additional context**
39+
Add any other context about the problem here.

Rubberduck.CodeAnalysis/Inspections/Abstract/InspectionBase.cs

Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -166,5 +166,10 @@ public IEnumerable<IInspectionResult> GetInspectionResults(CancellationToken tok
166166
_logger.Trace("Intercepted invocation of '{0}.{1}' ran for {2}ms", GetType().Name, nameof(DoGetInspectionResults), _stopwatch.ElapsedMilliseconds);
167167
return result;
168168
}
169+
170+
public virtual bool ChangesInvalidateResult(IInspectionResult result, ICollection<QualifiedModuleName> modifiedModules)
171+
{
172+
return true;
173+
}
169174
}
170175
}

Rubberduck.CodeAnalysis/Inspections/Abstract/InspectionResultBase.cs

Lines changed: 8 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,5 @@
1-
using System.IO;
1+
using System.Collections.Generic;
2+
using System.IO;
23
using Antlr4.Runtime;
34
using Rubberduck.Common;
45
using Rubberduck.Parsing.Inspections;
@@ -39,6 +40,12 @@ protected InspectionResultBase(IInspection inspection,
3940
public Declaration Target { get; }
4041
public dynamic Properties { get; }
4142

43+
public virtual bool ChangesInvalidateResult(ICollection<QualifiedModuleName> modifiedModules)
44+
{
45+
return modifiedModules.Contains(QualifiedName)
46+
|| Inspection.ChangesInvalidateResult(this, modifiedModules);
47+
}
48+
4249
/// <summary>
4350
/// Gets the information needed to select the target instruction in the VBE.
4451
/// </summary>

Rubberduck.CodeAnalysis/Inspections/Concrete/ProcedureCanBeWrittenAsFunctionInspection.cs

Lines changed: 25 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -26,6 +26,11 @@ public ProcedureCanBeWrittenAsFunctionInspection(RubberduckParserState state)
2626

2727
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
2828
{
29+
if (!Listener.Contexts.Any())
30+
{
31+
return Enumerable.Empty<IInspectionResult>();
32+
}
33+
2934
var userDeclarations = UserDeclarations.ToList();
3035
var builtinHandlers = State.DeclarationFinder.FindEventHandlers().ToList();
3136

@@ -38,17 +43,31 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
3843

3944
return Listener.Contexts
4045
.Where(context => context.Context.Parent is VBAParser.SubStmtContext
41-
&& contextLookup[context.Context.GetChild<VBAParser.ArgContext>()].References
42-
.Any(reference => reference.IsAssignment))
43-
.Select(context => contextLookup[(VBAParser.SubStmtContext)context.Context.Parent])
44-
.Where(decl => !IsIgnoringInspectionResultFor(decl, AnnotationName) &&
45-
!ignored.Contains(decl) &&
46-
userDeclarations.Where(item => item.IsWithEvents)
46+
&& HasArgumentReferencesWithIsAssignmentFlagged(context))
47+
.Select(context => GetSubStmtParentDeclaration(context))
48+
.Where(decl => decl != null &&
49+
!IsIgnoringInspectionResultFor(decl, AnnotationName) &&
50+
!ignored.Contains(decl) &&
51+
userDeclarations.Where(item => item.IsWithEvents)
4752
.All(withEvents => userDeclarations.FindEventProcedures(withEvents) == null) &&
4853
!builtinHandlers.Contains(decl))
4954
.Select(result => new DeclarationInspectionResult(this,
5055
string.Format(InspectionResults.ProcedureCanBeWrittenAsFunctionInspection, result.IdentifierName),
5156
result));
57+
58+
bool HasArgumentReferencesWithIsAssignmentFlagged(QualifiedContext<ParserRuleContext> context)
59+
{
60+
return contextLookup.TryGetValue(context.Context.GetChild<VBAParser.ArgContext>(), out Declaration decl)
61+
? decl.References.Any(rf => rf.IsAssignment)
62+
: false;
63+
}
64+
65+
Declaration GetSubStmtParentDeclaration(QualifiedContext<ParserRuleContext> context)
66+
{
67+
return contextLookup.TryGetValue(context.Context.Parent as VBAParser.SubStmtContext, out Declaration decl)
68+
? decl
69+
: null;
70+
}
5271
}
5372

5473
public class SingleByRefParamArgListListener : VBAParserBaseListener, IInspectionListener

Rubberduck.CodeAnalysis/Inspections/Results/DeclarationInspectionResult.cs

Lines changed: 9 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,12 +1,13 @@
1-
using Rubberduck.Inspections.Abstract;
1+
using System.Collections.Generic;
2+
using Rubberduck.Inspections.Abstract;
23
using Rubberduck.Parsing;
34
using Rubberduck.Parsing.Inspections.Abstract;
45
using Rubberduck.Parsing.Symbols;
56
using Rubberduck.VBEditor;
67

78
namespace Rubberduck.Inspections.Results
89
{
9-
internal class DeclarationInspectionResult : InspectionResultBase
10+
public class DeclarationInspectionResult : InspectionResultBase
1011
{
1112
public DeclarationInspectionResult(IInspection inspection, string description, Declaration target, QualifiedContext context = null, dynamic properties = null) :
1213
base(inspection,
@@ -31,5 +32,11 @@ public DeclarationInspectionResult(IInspection inspection, string description, D
3132
? target.QualifiedName
3233
: GetQualifiedMemberName(target.ParentDeclaration);
3334
}
35+
36+
public override bool ChangesInvalidateResult(ICollection<QualifiedModuleName> modifiedModules)
37+
{
38+
return modifiedModules.Contains(Target.QualifiedModuleName)
39+
|| base.ChangesInvalidateResult(modifiedModules);
40+
}
3441
}
3542
}
Lines changed: 13 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,5 @@
1-
using System.Linq;
1+
using System.Collections.Generic;
2+
using System.Linq;
23
using Rubberduck.Inspections.Abstract;
34
using Rubberduck.Parsing;
45
using Rubberduck.Parsing.Inspections.Abstract;
@@ -8,24 +9,30 @@
89

910
namespace Rubberduck.Inspections.Results
1011
{
11-
internal class IdentifierReferenceInspectionResult : InspectionResultBase
12+
public class IdentifierReferenceInspectionResult : InspectionResultBase
1213
{
13-
public IdentifierReferenceInspectionResult(IInspection inspection, string description, RubberduckParserState state, IdentifierReference reference, dynamic properties = null) :
14+
public IdentifierReferenceInspectionResult(IInspection inspection, string description, IDeclarationFinderProvider declarationFinderProvider, IdentifierReference reference, dynamic properties = null) :
1415
base(inspection,
1516
description,
1617
reference.QualifiedModuleName,
1718
reference.Context,
1819
reference.Declaration,
1920
new QualifiedSelection(reference.QualifiedModuleName, reference.Context.GetSelection()),
20-
GetQualifiedMemberName(state, reference),
21+
GetQualifiedMemberName(declarationFinderProvider, reference),
2122
(object)properties)
2223
{
2324
}
2425

25-
private static QualifiedMemberName? GetQualifiedMemberName(RubberduckParserState state, IdentifierReference reference)
26+
private static QualifiedMemberName? GetQualifiedMemberName(IDeclarationFinderProvider declarationFinderProvider, IdentifierReference reference)
2627
{
27-
var members = state.DeclarationFinder.Members(reference.QualifiedModuleName);
28+
var members = declarationFinderProvider.DeclarationFinder.Members(reference.QualifiedModuleName);
2829
return members.SingleOrDefault(m => reference.Context.IsDescendentOf(m.Context))?.QualifiedName;
2930
}
31+
32+
public override bool ChangesInvalidateResult(ICollection<QualifiedModuleName> modifiedModules)
33+
{
34+
return modifiedModules.Contains(Target.QualifiedModuleName)
35+
|| base.ChangesInvalidateResult(modifiedModules);
36+
}
3037
}
3138
}

Rubberduck.CodeAnalysis/Inspections/Results/QualifiedContextInspectionResult.cs

Lines changed: 2 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -5,7 +5,7 @@
55

66
namespace Rubberduck.Inspections.Results
77
{
8-
internal class QualifiedContextInspectionResult : InspectionResultBase
8+
public class QualifiedContextInspectionResult : InspectionResultBase
99
{
1010
public QualifiedContextInspectionResult(IInspection inspection, string description, QualifiedContext context, dynamic properties = null) :
1111
base(inspection,
@@ -16,7 +16,6 @@ public QualifiedContextInspectionResult(IInspection inspection, string descripti
1616
new QualifiedSelection(context.ModuleName, context.Context.GetSelection()),
1717
context.MemberName,
1818
(object)properties)
19-
{
20-
}
19+
{}
2120
}
2221
}
Lines changed: 9 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,9 @@
1+
using Rubberduck.Parsing.Rewriter;
2+
3+
namespace Rubberduck.Inspections.QuickFixes
4+
{
5+
public interface IQuickFixFailureNotifier
6+
{
7+
void NotifyQuickFixExecutionFailure(RewriteSessionState sessionState);
8+
}
9+
}
Lines changed: 45 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,45 @@
1+
using System;
2+
using Rubberduck.Interaction;
3+
using Rubberduck.Parsing.Rewriter;
4+
5+
namespace Rubberduck.Inspections.QuickFixes
6+
{
7+
public class QuickFixFailureNotifier : IQuickFixFailureNotifier
8+
{
9+
private readonly IMessageBox _messageBox;
10+
11+
public QuickFixFailureNotifier(IMessageBox messageBox)
12+
{
13+
_messageBox = messageBox;
14+
}
15+
16+
public void NotifyQuickFixExecutionFailure(RewriteSessionState sessionState)
17+
{
18+
var message = FailureMessage(sessionState);
19+
var caption = Resources.Inspections.QuickFixes.ApplyQuickFixFailedCaption;
20+
21+
_messageBox.NotifyWarn(message, caption);
22+
}
23+
24+
private static string FailureMessage(RewriteSessionState sessionState)
25+
{
26+
var baseFailureMessage = Resources.Inspections.QuickFixes.ApplyQuickFixesFailedMessage;
27+
var failureReasonMessage = FailureReasonMessage(sessionState);
28+
var message = string.IsNullOrEmpty(failureReasonMessage)
29+
? baseFailureMessage
30+
: $"{baseFailureMessage}{Environment.NewLine}{Environment.NewLine}{failureReasonMessage}";
31+
return message;
32+
}
33+
34+
private static string FailureReasonMessage(RewriteSessionState sessionState)
35+
{
36+
switch (sessionState)
37+
{
38+
case RewriteSessionState.StaleParseTree:
39+
return Resources.Inspections.QuickFixes.StaleModuleFailureReason;
40+
default:
41+
return string.Empty;
42+
}
43+
}
44+
}
45+
}

Rubberduck.CodeAnalysis/QuickFixes/QuickFixProvider.cs

Lines changed: 16 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -5,7 +5,6 @@
55
using Microsoft.CSharp.RuntimeBinder;
66
using Rubberduck.Parsing.Inspections.Abstract;
77
using Rubberduck.Parsing.Rewriter;
8-
using Rubberduck.Parsing.VBA;
98
using Rubberduck.Parsing.VBA.Parsing;
109
using Rubberduck.VBEditor;
1110

@@ -14,11 +13,13 @@ namespace Rubberduck.Inspections.QuickFixes
1413
public class QuickFixProvider : IQuickFixProvider
1514
{
1615
private readonly IRewritingManager _rewritingManager;
16+
private readonly IQuickFixFailureNotifier _failureNotifier;
1717
private readonly Dictionary<Type, HashSet<IQuickFix>> _quickFixes = new Dictionary<Type, HashSet<IQuickFix>>();
1818

19-
public QuickFixProvider(IRewritingManager rewritingManager, IEnumerable<IQuickFix> quickFixes)
19+
public QuickFixProvider(IRewritingManager rewritingManager, IQuickFixFailureNotifier failureNotifier, IEnumerable<IQuickFix> quickFixes)
2020
{
2121
_rewritingManager = rewritingManager;
22+
_failureNotifier = failureNotifier;
2223
foreach (var quickFix in quickFixes)
2324
{
2425
foreach (var supportedInspection in quickFix.SupportedInspections)
@@ -78,7 +79,15 @@ public void Fix(IQuickFix fix, IInspectionResult result)
7879

7980
var rewriteSession = RewriteSession(fix.TargetCodeKind);
8081
fix.Fix(result, rewriteSession);
81-
rewriteSession.TryRewrite();
82+
Apply(rewriteSession);
83+
}
84+
85+
private void Apply(IRewriteSession rewriteSession)
86+
{
87+
if (!rewriteSession.TryRewrite())
88+
{
89+
_failureNotifier.NotifyQuickFixExecutionFailure(rewriteSession.Status);
90+
}
8291
}
8392

8493
private IRewriteSession RewriteSession(CodeKind targetCodeKind)
@@ -115,7 +124,7 @@ public void FixInProcedure(IQuickFix fix, QualifiedMemberName? qualifiedMember,
115124

116125
fix.Fix(result, rewriteSession);
117126
}
118-
rewriteSession.TryRewrite();
127+
Apply(rewriteSession);
119128
}
120129

121130
public void FixInModule(IQuickFix fix, QualifiedSelection selection, Type inspectionType, IEnumerable<IInspectionResult> results)
@@ -137,7 +146,7 @@ public void FixInModule(IQuickFix fix, QualifiedSelection selection, Type inspec
137146

138147
fix.Fix(result, rewriteSession);
139148
}
140-
rewriteSession.TryRewrite();
149+
Apply(rewriteSession);
141150
}
142151

143152
public void FixInProject(IQuickFix fix, QualifiedSelection selection, Type inspectionType, IEnumerable<IInspectionResult> results)
@@ -159,7 +168,7 @@ public void FixInProject(IQuickFix fix, QualifiedSelection selection, Type inspe
159168

160169
fix.Fix(result, rewriteSession);
161170
}
162-
rewriteSession.TryRewrite();
171+
Apply(rewriteSession);
163172
}
164173

165174
public void FixAll(IQuickFix fix, Type inspectionType, IEnumerable<IInspectionResult> results)
@@ -181,7 +190,7 @@ public void FixAll(IQuickFix fix, Type inspectionType, IEnumerable<IInspectionRe
181190

182191
fix.Fix(result, rewriteSession);
183192
}
184-
rewriteSession.TryRewrite();
193+
Apply(rewriteSession);
185194
}
186195

187196
public bool HasQuickFixes(IInspectionResult inspectionResult)

0 commit comments

Comments
 (0)