Skip to content

Commit 6cbdb1c

Browse files
committed
Merge branch 'next' of https://github.com/rubberduck-vba/rubberduck into Issue3872
2 parents 5d8fee8 + 0fdf379 commit 6cbdb1c

File tree

208 files changed

+10169
-1666
lines changed

Some content is hidden

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

208 files changed

+10169
-1666
lines changed

Rubberduck.API/VBA/Parser.cs

Lines changed: 4 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -6,6 +6,7 @@
66
using System.Runtime.InteropServices;
77
using System.Threading;
88
using Rubberduck.Common;
9+
using Rubberduck.Parsing.ComReflection;
910
using Rubberduck.Parsing.PreProcessing;
1011
using Rubberduck.Parsing.Rewriter;
1112
using Rubberduck.Parsing.Symbols.DeclarationLoaders;
@@ -116,7 +117,9 @@ internal Parser(object vbe) : this()
116117
var parserStateManager = new ParserStateManager(_state);
117118
var referenceRemover = new ReferenceRemover(_state, moduleToModuleReferenceManager);
118119
var supertypeClearer = new SupertypeClearer(_state);
119-
var comSynchronizer = new COMReferenceSynchronizer(_state, parserStateManager);
120+
var comLibraryProvider = new ComLibraryProvider();
121+
var referencedDeclarationsCollector = new LibraryReferencedDeclarationsCollector(comLibraryProvider);
122+
var comSynchronizer = new COMReferenceSynchronizer(_state, parserStateManager, projectRepository, referencedDeclarationsCollector);
120123
var builtInDeclarationLoader = new BuiltInDeclarationLoader(
121124
_state,
122125
new List<ICustomDeclarationLoader>

Rubberduck.CodeAnalysis/Inspections/Concrete/EmptyModuleInspection.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -87,7 +87,7 @@ public override bool VisitModuleDeclarations(VBAParser.ModuleDeclarationsContext
8787

8888
public override bool VisitModuleDeclarationsElement(VBAParser.ModuleDeclarationsElementContext context)
8989
{
90-
return context.variableStmt() == null
90+
return context.moduleVariableStmt() == null
9191
&& context.constStmt() == null
9292
&& context.enumerationStmt() == null
9393
&& context.udtDeclaration() == null

Rubberduck.CodeAnalysis/Inspections/Concrete/ModuleScopeDimKeywordInspection.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -45,7 +45,7 @@ public void ClearContexts()
4545

4646
public override void ExitVariableStmt([NotNull] VBAParser.VariableStmtContext context)
4747
{
48-
if (context.DIM() != null && context.Parent is VBAParser.ModuleDeclarationsElementContext)
48+
if (context.DIM() != null && context.TryGetAncestor<VBAParser.ModuleDeclarationsElementContext>(out _))
4949
{
5050
_contexts.Add(new QualifiedContext<ParserRuleContext>(CurrentModuleName, context));
5151
}

Rubberduck.CodeAnalysis/Inspections/Concrete/ProcedureCanBeWrittenAsFunctionInspection.cs

Lines changed: 13 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -36,16 +36,19 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
3636
.Concat(builtinHandlers)
3737
.Concat(userDeclarations.Where(item => item.IsWithEvents)));
3838

39-
return Listener.Contexts.Where(context => context.Context.Parent is VBAParser.SubStmtContext)
40-
.Select(context => contextLookup[(VBAParser.SubStmtContext)context.Context.Parent])
41-
.Where(decl => !IsIgnoringInspectionResultFor(decl, AnnotationName) &&
42-
!ignored.Contains(decl) &&
43-
userDeclarations.Where(item => item.IsWithEvents)
44-
.All(withEvents => userDeclarations.FindEventProcedures(withEvents) == null) &&
45-
!builtinHandlers.Contains(decl))
46-
.Select(result => new DeclarationInspectionResult(this,
47-
string.Format(InspectionResults.ProcedureCanBeWrittenAsFunctionInspection, result.IdentifierName),
48-
result));
39+
return Listener.Contexts
40+
.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)
47+
.All(withEvents => userDeclarations.FindEventProcedures(withEvents) == null) &&
48+
!builtinHandlers.Contains(decl))
49+
.Select(result => new DeclarationInspectionResult(this,
50+
string.Format(InspectionResults.ProcedureCanBeWrittenAsFunctionInspection, result.IdentifierName),
51+
result));
4952
}
5053

5154
public class SingleByRefParamArgListListener : VBAParserBaseListener, IInspectionListener

Rubberduck.Core/App.cs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -116,13 +116,13 @@ public void Startup()
116116

117117
CheckForLegacyIndenterSettings();
118118
_appMenus.Initialize();
119-
_hooks.HookHotkeys(); // need to hook hotkeys before we localize menus, to correctly display ShortcutTexts
119+
_hooks.HookHotkeys(); // need to hook hotkeys before we localize menus, to correctly display ShortcutTexts
120120
_appMenus.Localize();
121121

122122
if (_config.UserSettings.GeneralSettings.CanCheckVersion)
123123
{
124124
_checkVersionCommand.Execute(null);
125-
}
125+
}
126126
}
127127

128128
public void Shutdown()

Rubberduck.Core/AppMenu.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,6 @@
11
using System;
22
using System.Collections.Generic;
33
using System.Linq;
4-
using System.Threading;
54
using NLog;
65
using Rubberduck.Parsing;
76
using Rubberduck.Parsing.VBA;
@@ -63,6 +62,7 @@ public void Localize()
6362
{
6463
_stateBar.Localize();
6564
_stateBar.SetStatusLabelCaption(_parser.State.Status);
65+
6666
foreach (var menu in _menus)
6767
{
6868
menu.Localize();

Rubberduck.Core/AutoComplete/AutoCompleteBase.cs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -9,6 +9,7 @@
99

1010
namespace Rubberduck.AutoComplete
1111
{
12+
1213
public abstract class AutoCompleteBase : IAutoComplete
1314
{
1415
protected AutoCompleteBase(string inputToken, string outputToken)
@@ -67,7 +68,7 @@ public virtual bool Execute(AutoCompleteEventArgs e, AutoCompleteSettings settin
6768
else if (input == OutputToken && nextChar == OutputToken)
6869
{
6970
// just move caret one character to the right & suppress the keypress
70-
pane.Selection = new Selection(pSelection.StartLine, pSelection.StartColumn + 2);
71+
pane.Selection = new Selection(pSelection.StartLine, GetPrettifiedCaretPosition(pSelection, original, original) + 1);
7172
e.Handled = true;
7273
return true;
7374
}

Rubberduck.Core/AutoComplete/AutoCompleteBlockBase.cs

Lines changed: 39 additions & 34 deletions
Original file line numberDiff line numberDiff line change
@@ -13,6 +13,7 @@
1313

1414
namespace Rubberduck.AutoComplete
1515
{
16+
1617
public abstract class AutoCompleteBlockBase : AutoCompleteBase
1718
{
1819
/// <param name="indenterSettings">Used for auto-indenting blocks as per indenter settings.</param>
@@ -24,6 +25,8 @@ protected AutoCompleteBlockBase(IConfigProvider<IndenterSettings> indenterSettin
2425
IndenterSettings = indenterSettings;
2526
}
2627

28+
public bool IsCapturing { get; set; }
29+
2730
protected virtual bool FindInputTokenAtBeginningOfCurrentLine => false;
2831
protected virtual bool SkipPreCompilerDirective => true;
2932

@@ -42,43 +45,45 @@ public override bool Execute(AutoCompleteEventArgs e, AutoCompleteSettings setti
4245
{
4346
return false;
4447
}
45-
46-
var module = e.CodeModule;
47-
using (var pane = module.CodePane)
48-
{
49-
var selection = pane.Selection;
50-
var originalCode = module.GetLines(selection);
51-
var code = originalCode.Trim().StripStringLiterals();
52-
var hasComment = code.HasComment(out int commentStart);
53-
54-
var isDeclareStatement = Regex.IsMatch(code, $"\\b{Tokens.Declare}\\b", RegexOptions.IgnoreCase);
55-
var isExitStatement = Regex.IsMatch(code, $"\\b{Tokens.Exit}\\b", RegexOptions.IgnoreCase);
56-
var isNamedArg = Regex.IsMatch(code, $"\\b{InputToken}\\:\\=", RegexOptions.IgnoreCase);
5748

58-
if ((SkipPreCompilerDirective && code.StartsWith("#"))
59-
|| isDeclareStatement || isExitStatement || isNamedArg)
49+
{
50+
var module = e.CodeModule;
51+
using (var pane = module.CodePane)
6052
{
53+
var selection = pane.Selection;
54+
var originalCode = module.GetLines(selection);
55+
var code = originalCode.Trim().StripStringLiterals();
56+
var hasComment = code.HasComment(out int commentStart);
57+
58+
var isDeclareStatement = Regex.IsMatch(code, $"\\b{Tokens.Declare}\\b", RegexOptions.IgnoreCase);
59+
var isExitStatement = Regex.IsMatch(code, $"\\b{Tokens.Exit}\\b", RegexOptions.IgnoreCase);
60+
var isNamedArg = Regex.IsMatch(code, $"\\b{InputToken}\\:\\=", RegexOptions.IgnoreCase);
61+
62+
if ((SkipPreCompilerDirective && code.StartsWith("#"))
63+
|| isDeclareStatement || isExitStatement || isNamedArg)
64+
{
65+
return false;
66+
}
67+
68+
if (IsMatch(code) && !IsBlockCompleted(module, selection))
69+
{
70+
var indent = originalCode.TakeWhile(c => char.IsWhiteSpace(c)).Count();
71+
var newCode = OutputToken.PadLeft(OutputToken.Length + indent, ' ');
72+
73+
var stdIndent = IndentBody
74+
? IndenterSettings.Create().IndentSpaces
75+
: 0;
76+
77+
module.InsertLines(selection.NextLine.StartLine, "\n" + newCode);
78+
79+
module.ReplaceLine(selection.NextLine.StartLine, new string(' ', indent + stdIndent));
80+
pane.Selection = new Selection(selection.NextLine.StartLine, indent + stdIndent + 1);
81+
82+
e.Handled = true;
83+
return true;
84+
}
6185
return false;
6286
}
63-
64-
if (IsMatch(code) && !IsBlockCompleted(module, selection))
65-
{
66-
var indent = originalCode.TakeWhile(c => char.IsWhiteSpace(c)).Count();
67-
var newCode = OutputToken.PadLeft(OutputToken.Length + indent, ' ');
68-
69-
var stdIndent = IndentBody
70-
? IndenterSettings.Create().IndentSpaces
71-
: 0;
72-
73-
module.InsertLines(selection.NextLine.StartLine, "\n" + newCode);
74-
75-
module.ReplaceLine(selection.NextLine.StartLine, new string(' ', indent + stdIndent));
76-
pane.Selection = new Selection(selection.NextLine.StartLine, indent + stdIndent + 1);
77-
78-
e.Handled = true;
79-
return true;
80-
}
81-
return false;
8287
}
8388
}
8489

@@ -104,7 +109,7 @@ public override bool IsMatch(string code)
104109
return regexOk && (!hasComment || code.IndexOf(InputToken) < commentIndex);
105110
}
106111

107-
private bool IsBlockCompleted(ICodeModule module, Selection selection)
112+
protected bool IsBlockCompleted(ICodeModule module, Selection selection)
108113
{
109114
string content;
110115
var proc = module.GetProcOfLine(selection.StartLine);

Rubberduck.Core/AutoComplete/AutoCompleteIfBlock.cs

Lines changed: 8 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,13 +1,20 @@
11
using Rubberduck.Parsing.Grammar;
2+
using Rubberduck.Parsing.VBA;
3+
using Rubberduck.Settings;
24
using Rubberduck.SettingsProvider;
35
using Rubberduck.SmartIndenter;
6+
using Rubberduck.VBEditor;
7+
using Rubberduck.VBEditor.Events;
8+
using System.Linq;
9+
using System.Text.RegularExpressions;
10+
using System.Windows.Forms;
411

512
namespace Rubberduck.AutoComplete
613
{
714
public class AutoCompleteIfBlock : AutoCompleteBlockBase
815
{
916
public AutoCompleteIfBlock(IConfigProvider<IndenterSettings> indenterSettings)
10-
: base(indenterSettings, $"{Tokens.Then}", $"{Tokens.End} {Tokens.If}") { }
17+
: base(indenterSettings, $"{Tokens.If}", $"{Tokens.End} {Tokens.If}") { }
1118

1219
// matching "If" would trigger erroneous block completion on inline if..then..else syntax.
1320
protected override bool MatchInputTokenAtEndOfLineOnly => true;

0 commit comments

Comments
 (0)