Skip to content

Commit cf9d4de

Browse files
committed
adding DeclarationType.BracketedExpression; fixes #2548.
1 parent 24925aa commit cf9d4de

File tree

7 files changed

+60
-11
lines changed

7 files changed

+60
-11
lines changed

RetailCoder.VBE/UI/Command/MenuItems/CommandBars/IContextFormatter.cs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -45,13 +45,13 @@ private string Format(Declaration declaration)
4545

4646
typeName = "(" + declarationType + (string.IsNullOrEmpty(typeName) ? string.Empty : ":" + typeName) + ")";
4747

48-
if (declaration.DeclarationType.HasFlag(DeclarationType.Project))
48+
if (declaration.DeclarationType.HasFlag(DeclarationType.Project) || declaration.DeclarationType == DeclarationType.BracketedExpression)
4949
{
50-
formattedDeclaration = System.IO.Path.GetFileName(declaration.QualifiedName.QualifiedModuleName.ProjectPath) + ";" + declaration.IdentifierName;
50+
formattedDeclaration = System.IO.Path.GetFileName(declaration.QualifiedName.QualifiedModuleName.ProjectPath) + ";" + declaration.IdentifierName + " (" + declarationType + ")";
5151
}
5252
else if (declaration.DeclarationType.HasFlag(DeclarationType.Module))
5353
{
54-
formattedDeclaration = moduleName.ToString();
54+
formattedDeclaration = moduleName + " (" + declarationType + ")";
5555
}
5656

5757
if (declaration.DeclarationType.HasFlag(DeclarationType.Member))

RetailCoder.VBE/UI/RubberduckUI.Designer.cs

Lines changed: 9 additions & 0 deletions
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

RetailCoder.VBE/UI/RubberduckUI.resx

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1908,4 +1908,7 @@ Would you like to import them to Rubberduck?</value>
19081908
<data name="IndenterSettings_VerticalSpacingLabel" xml:space="preserve">
19091909
<value>Vertical Spacing</value>
19101910
</data>
1911+
<data name="DeclarationType_BracketedExpression" xml:space="preserve">
1912+
<value>runtime expression</value>
1913+
</data>
19111914
</root>

Rubberduck.Parsing/Binding/SimpleNameDefaultBinding.cs

Lines changed: 13 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,7 @@
11
using Antlr4.Runtime;
22
using Rubberduck.Parsing.Symbols;
33
using System.Linq;
4+
using Rubberduck.Parsing.Grammar;
45

56
namespace Rubberduck.Parsing.Binding
67
{
@@ -28,7 +29,8 @@ public SimpleNameDefaultBinding(
2829
_module = module;
2930
_parent = parent;
3031
_context = context;
31-
_name = name;
32+
// hack; SimpleNameContext.Identifier() excludes the square brackets
33+
_name = context.Start.Text == "[" && context.Stop.Text == "]" ? "[" + name + "]" : name;
3234
_propertySearchType = StatementContext.GetSearchDeclarationType(statementContext);
3335
}
3436

@@ -68,8 +70,16 @@ public IBoundExpression Resolve()
6870
return boundExpression;
6971
}
7072

71-
var undeclaredLocal = _declarationFinder.OnUndeclaredVariable(_parent, _name, _context);
72-
return new SimpleNameExpression(undeclaredLocal, ExpressionClassification.Variable, _context);
73+
if (_context.Start.Text == "[" && _context.Stop.Text == "]")
74+
{
75+
var bracketedExpression = _declarationFinder.OnBracketedExpression(_context.GetText(), _context);
76+
return new SimpleNameExpression(bracketedExpression, ExpressionClassification.Unbound, _context);
77+
}
78+
else
79+
{
80+
var undeclaredLocal = _declarationFinder.OnUndeclaredVariable(_parent, _name, _context);
81+
return new SimpleNameExpression(undeclaredLocal, ExpressionClassification.Variable, _context);
82+
}
7383
//return new ResolutionFailedExpression();
7484
}
7585

Rubberduck.Parsing/Symbols/DeclarationFinder.cs

Lines changed: 23 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -6,6 +6,8 @@
66
using System.Diagnostics;
77
using System.Linq;
88
using Antlr4.Runtime;
9+
using Rubberduck.Parsing.Grammar;
10+
using Rubberduck.VBEditor.Application;
911

1012
namespace Rubberduck.Parsing.Symbols
1113
{
@@ -26,6 +28,7 @@ public static IEnumerable<TValue> AllValues<TKey, TValue>(
2628

2729
public class DeclarationFinder
2830
{
31+
private readonly IHostApplication _hostApp;
2932
private readonly IDictionary<QualifiedModuleName, IAnnotation[]> _annotations;
3033
private readonly IDictionary<QualifiedMemberName, IList<Declaration>> _undeclared;
3134
private readonly AnnotationService _annotationService;
@@ -34,10 +37,9 @@ public class DeclarationFinder
3437
private readonly IDictionary<string, Declaration[]> _declarationsByName;
3538
private static readonly Logger Logger = LogManager.GetCurrentClassLogger();
3639

37-
public DeclarationFinder(
38-
IReadOnlyList<Declaration> declarations,
39-
IEnumerable<IAnnotation> annotations)
40+
public DeclarationFinder(IReadOnlyList<Declaration> declarations, IEnumerable<IAnnotation> annotations, IHostApplication hostApp = null)
4041
{
42+
_hostApp = hostApp;
4143
_annotations = annotations.GroupBy(node => node.QualifiedSelection.QualifiedName)
4244
.ToDictionary(grouping => grouping.Key, grouping => grouping.ToArray());
4345
_declarations = declarations.GroupBy(item => item.QualifiedName.QualifiedModuleName)
@@ -343,6 +345,24 @@ public Declaration OnUndeclaredVariable(Declaration enclosingProcedure, string i
343345
return undeclaredLocal;
344346
}
345347

348+
public Declaration OnBracketedExpression(string expression, ParserRuleContext context)
349+
{
350+
var hostApp = FindProject(_hostApp == null ? "VBA" : _hostApp.ApplicationName);
351+
var qualifiedName = hostApp.QualifiedName.QualifiedModuleName.QualifyMemberName(expression);
352+
353+
var exists = _undeclared.ContainsKey(qualifiedName);
354+
if (exists)
355+
{
356+
return _undeclared[qualifiedName][0];
357+
}
358+
else
359+
{
360+
var item = new Declaration(qualifiedName, hostApp, hostApp, Tokens.Variant, string.Empty, false, false, Accessibility.Global, DeclarationType.BracketedExpression, context, context.GetSelection(), false, null);
361+
_undeclared.Add(qualifiedName, new List<Declaration> { item });
362+
return item;
363+
}
364+
}
365+
346366
public Declaration FindMemberEnclosedProjectWithoutEnclosingModule(Declaration callingProject, Declaration callingModule, Declaration callingParent, string memberName, DeclarationType memberType)
347367
{
348368
var allMatches = MatchName(memberName);

Rubberduck.Parsing/Symbols/DeclarationType.cs

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -60,7 +60,9 @@ public enum DeclarationType
6060
[DebuggerDisplay("LineLabel")]
6161
LineLabel = 1 << 25,
6262
[DebuggerDisplay("UnresolvedMember")]
63-
UnresolvedMember = 1 << 26
63+
UnresolvedMember = 1 << 26,
64+
[DebuggerDisplay("BracketedExpression")]
65+
BracketedExpression = 1 << 27,
6466
}
6567

6668
public interface IIdentifier { IdentifierNode Identifier { get; } }

Rubberduck.Parsing/VBA/ParseCoordinator.cs

Lines changed: 6 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -14,6 +14,9 @@
1414
using NLog;
1515
using Rubberduck.VBEditor.SafeComWrappers.Abstract;
1616
using System.Runtime.InteropServices;
17+
using Rubberduck.VBEditor.Application;
18+
using Rubberduck.VBEditor.Extensions;
19+
1720
// ReSharper disable LoopCanBeConvertedToQuery
1821

1922
namespace Rubberduck.Parsing.VBA
@@ -36,6 +39,7 @@ private readonly IDictionary<IVBComponent, IDictionary<Tuple<string, Declaration
3639
private static readonly Logger Logger = LogManager.GetCurrentClassLogger();
3740

3841
private readonly bool _isTestScope;
42+
private readonly IHostApplication _hostApp;
3943

4044
public ParseCoordinator(
4145
IVBE vbe,
@@ -51,6 +55,7 @@ public ParseCoordinator(
5155
_preprocessorFactory = preprocessorFactory;
5256
_customDeclarationLoaders = customDeclarationLoaders;
5357
_isTestScope = isTestScope;
58+
_hostApp = _vbe.HostApplication();
5459

5560
state.ParseRequest += ReparseRequested;
5661
}
@@ -291,7 +296,7 @@ private Task[] ResolveReferencesAsync(CancellationToken token)
291296
State.SetModuleState(kvp.Key.Component, ParserState.ResolvingReferences);
292297
}
293298

294-
var finder = new DeclarationFinder(State.AllDeclarations, State.AllAnnotations);
299+
var finder = new DeclarationFinder(State.AllDeclarations, State.AllAnnotations, _hostApp);
295300
var passes = new List<ICompilationPass>
296301
{
297302
// This pass has to come first because the type binding resolution depends on it.

0 commit comments

Comments
 (0)