Skip to content

Commit f64ba33

Browse files
committed
COM return types resolved; added global "Err As ErrObject" variable in VBA scope; added "Debug As DebugClass" variable in VBA scope, but it doesn't seem to resolve. Parse timing issue still unresolved.
1 parent 41defa5 commit f64ba33

File tree

7 files changed

+120
-24
lines changed

7 files changed

+120
-24
lines changed

Rubberduck.Parsing/Symbols/DeclarationFinder.cs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -92,10 +92,11 @@ public IEnumerable<Declaration> MatchName(string name)
9292
{
9393
return result;
9494
}
95+
9596
return new List<Declaration>();
9697
}
9798

98-
public Declaration FindProject(Declaration currentScope, string name)
99+
public Declaration FindProject(string name, Declaration currentScope = null)
99100
{
100101
Declaration result = null;
101102
try

Rubberduck.Parsing/Symbols/IdentifierReferenceResolver.cs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -204,7 +204,7 @@ private Declaration ResolveType(VBAParser.ComplexTypeContext context)
204204
private Declaration ResolveType(IList<VBAParser.AmbiguousIdentifierContext> identifiers)
205205
{
206206
var first = identifiers[0].GetText();
207-
var projectMatch = _declarationFinder.FindProject(_currentScope, first);
207+
var projectMatch = _declarationFinder.FindProject(first, _currentScope);
208208

209209
if (projectMatch != null)
210210
{
@@ -1109,7 +1109,7 @@ private Declaration FindModuleScopeDeclaration(string identifierName, Declaratio
11091109
.ToList();
11101110
}
11111111

1112-
return result.Count == 1 ? result.SingleOrDefault() : null;
1112+
return result.Count == 1 ? result.SingleOrDefault() : null; // return null for multiple matches
11131113
}
11141114

11151115
private bool IsLocalEvent(Declaration item, Declaration localScope)

Rubberduck.Parsing/Symbols/ReferencedDeclarationsCollector.cs

Lines changed: 51 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,7 @@
11
using System;
22
using System.Collections.Generic;
33
using System.Diagnostics;
4+
using System.Diagnostics.Eventing.Reader;
45
using System.Runtime.InteropServices;
56
using System.Runtime.InteropServices.ComTypes;
67
using Microsoft.Vbe.Interop;
@@ -75,6 +76,39 @@ private enum REGKIND
7576
{VarEnum.VT_R8, "Double"},
7677
};
7778

79+
private string GetTypeName(TYPEDESC desc, ITypeInfo info)
80+
{
81+
var vt = (VarEnum)desc.vt;
82+
TYPEDESC tdesc;
83+
84+
switch (vt)
85+
{
86+
case VarEnum.VT_PTR:
87+
tdesc = (TYPEDESC) Marshal.PtrToStructure(desc.lpValue, typeof (TYPEDESC));
88+
return GetTypeName(tdesc, info);
89+
case VarEnum.VT_USERDEFINED:
90+
unchecked
91+
{
92+
var href = desc.lpValue.ToInt32();
93+
ITypeInfo refTypeInfo;
94+
info.GetRefTypeInfo(href, out refTypeInfo);
95+
return GetTypeName(refTypeInfo);
96+
}
97+
case VarEnum.VT_CARRAY:
98+
tdesc = (TYPEDESC) Marshal.PtrToStructure(desc.lpValue, typeof (TYPEDESC));
99+
return GetTypeName(tdesc, info) + "()";
100+
default:
101+
string result;
102+
if (TypeNames.TryGetValue(vt, out result))
103+
{
104+
return result;
105+
}
106+
break;
107+
}
108+
109+
return "UNKNOWN";
110+
}
111+
78112
private string GetTypeName(ITypeInfo info)
79113
{
80114
string typeName;
@@ -203,7 +237,22 @@ private Declaration CreateMemberDeclaration(out FUNCDESC memberDescriptor, TYPEK
203237
var asTypeName = string.Empty;
204238
if (memberDeclarationType != DeclarationType.Procedure && !TypeNames.TryGetValue(funcValueType, out asTypeName))
205239
{
206-
asTypeName = funcValueType.ToString(); //TypeNames[VarEnum.VT_VARIANT];
240+
if (funcValueType == VarEnum.VT_PTR)
241+
{
242+
try
243+
{
244+
var asTypeDesc = (TYPEDESC) Marshal.PtrToStructure(memberDescriptor.elemdescFunc.tdesc.lpValue, typeof (TYPEDESC));
245+
asTypeName = GetTypeName(asTypeDesc, info);
246+
}
247+
catch
248+
{
249+
asTypeName = funcValueType.ToString(); //TypeNames[VarEnum.VT_VARIANT];
250+
}
251+
}
252+
else
253+
{
254+
asTypeName = funcValueType.ToString(); //TypeNames[VarEnum.VT_VARIANT];
255+
}
207256
}
208257

209258
var attributes = new Attributes();
@@ -214,7 +263,7 @@ private Declaration CreateMemberDeclaration(out FUNCDESC memberDescriptor, TYPEK
214263
else if (memberDescriptor.memid == 0)
215264
{
216265
attributes.AddDefaultMemberAttribute(memberName);
217-
Debug.WriteLine("Default member found: {0}.{1} ({2} / {3})", moduleDeclaration.IdentifierName, memberName, memberDeclarationType, (VarEnum)memberDescriptor.elemdescFunc.tdesc.vt);
266+
//Debug.WriteLine("Default member found: {0}.{1} ({2} / {3})", moduleDeclaration.IdentifierName, memberName, memberDeclarationType, (VarEnum)memberDescriptor.elemdescFunc.tdesc.vt);
218267
}
219268
else if (((FUNCFLAGS)memberDescriptor.wFuncFlags).HasFlag(FUNCFLAGS.FUNCFLAG_FHIDDEN))
220269
{

Rubberduck.Parsing/Symbols/SyntaxErrorException.cs

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,5 @@
11
using System;
2+
using System.Diagnostics;
23
using Antlr4.Runtime;
34

45
namespace Rubberduck.Parsing.Symbols
@@ -16,6 +17,8 @@ public SyntaxErrorException(string message, RecognitionException innerException,
1617
_token = offendingSymbol;
1718
_line = line;
1819
_position = position;
20+
Debug.WriteLine(innerException.ToString());
21+
Debug.WriteLine("Token: {0} (L{1}C{2})", offendingSymbol.Text, line, position);
1922
}
2023

2124
private readonly IToken _token;

Rubberduck.Parsing/VBA/RubberduckParser.cs

Lines changed: 51 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -12,6 +12,7 @@
1212
using System.Globalization;
1313
using Rubberduck.Parsing.Preprocessing;
1414
using System.Diagnostics;
15+
using Rubberduck.Parsing.Annotations;
1516
using Rubberduck.Parsing.Grammar;
1617
using Rubberduck.Parsing.Nodes;
1718
using Rubberduck.VBEditor.Extensions;
@@ -33,10 +34,6 @@ public RubberduckParserState State
3334
private readonly ConcurrentDictionary<VBComponent, Tuple<Task, CancellationTokenSource>> _currentTasks =
3435
new ConcurrentDictionary<VBComponent, Tuple<Task, CancellationTokenSource>>();
3536

36-
private readonly Dictionary<VBComponent, IParseTree> _parseTrees = new Dictionary<VBComponent, IParseTree>();
37-
private readonly Dictionary<QualifiedModuleName, Dictionary<Declaration, byte>> _declarations = new Dictionary<QualifiedModuleName, Dictionary<Declaration, byte>>();
38-
private readonly Dictionary<VBComponent, ITokenStream> _tokenStreams = new Dictionary<VBComponent, ITokenStream>();
39-
private readonly Dictionary<VBComponent, IList<CommentNode>> _comments = new Dictionary<VBComponent, IList<CommentNode>>();
4037
private readonly IDictionary<VBComponent, IDictionary<Tuple<string, DeclarationType>, Attributes>> _componentAttributes
4138
= new Dictionary<VBComponent, IDictionary<Tuple<string, DeclarationType>, Attributes>>();
4239

@@ -134,25 +131,26 @@ private void ParseAll()
134131
}
135132

136133
var projects = _state.Projects.ToList();
137-
138134
var components = projects.SelectMany(p => p.VBComponents.Cast<VBComponent>()).ToList();
139-
var modified = components.Where(c => _state.IsNewOrModified(c)).ToList();
135+
136+
var toParse = components.Where(c => _state.IsNewOrModified(c)).ToList();
140137
var unchanged = components.Where(c => !_state.IsNewOrModified(c)).ToList();
141138

142-
SyncComReferences(projects);
139+
AddBuiltInDeclarations(projects);
143140

144-
if (!modified.Any())
141+
if (!toParse.Any())
145142
{
146143
return;
147144
}
148145

149-
foreach (var component in modified)
146+
foreach (var component in toParse)
150147
{
151148
_state.SetModuleState(component, ParserState.Pending);
152149
}
153150
foreach (var component in unchanged)
154151
{
155-
_state.SetModuleState(component, ParserState.Parsed);
152+
// note: seting to 'Parsed' would include them in the resolver walk. 'Ready' excludes them.
153+
_state.SetModuleState(component, ParserState.Ready);
156154
}
157155

158156
// invalidation cleanup should go into ParseAsync?
@@ -161,19 +159,55 @@ private void ParseAll()
161159
_componentAttributes.Remove(invalidated);
162160
}
163161

164-
foreach (var vbComponent in modified)
162+
foreach (var vbComponent in toParse)
165163
{
166164
ParseAsync(vbComponent, CancellationToken.None);
167165
}
168166
}
169167

168+
private void AddBuiltInDeclarations(IReadOnlyList<VBProject> projects)
169+
{
170+
SyncComReferences(projects);
171+
172+
var finder = new DeclarationFinder(_state.AllDeclarations, new CommentNode[]{}, new IAnnotation[]{});
173+
if (finder.MatchName(Tokens.Err).Any(item => item.IsBuiltIn
174+
&& item.DeclarationType == DeclarationType.Variable
175+
&& item.Accessibility == Accessibility.Global))
176+
{
177+
return;
178+
}
179+
180+
var vba = finder.FindProject("VBA");
181+
Debug.Assert(vba != null);
182+
183+
var errObject = finder.FindClass(vba, "ErrObject", true);
184+
Debug.Assert(errObject != null);
185+
186+
var qualifiedName = new QualifiedModuleName(vba.IdentifierName, vba.IdentifierName, errObject.IdentifierName);
187+
var err = new Declaration(new QualifiedMemberName(qualifiedName, Tokens.Err), vba, "Global", errObject.IdentifierName, true, false, Accessibility.Global, DeclarationType.Variable);
188+
_state.AddDeclaration(err);
189+
190+
var debugClassName = new QualifiedModuleName(vba.IdentifierName, vba.IdentifierName, "DebugClass");
191+
var debugClass = new Declaration(new QualifiedMemberName(debugClassName, "DebugClass"), vba, "Global", "DebugClass", false, false, Accessibility.Global, DeclarationType.Class);
192+
var debugObject = new Declaration(new QualifiedMemberName(debugClassName, "Debug"), vba, "Global", "DebugClass", true, false, Accessibility.Global, DeclarationType.Variable);
193+
var debugAssert = new Declaration(new QualifiedMemberName(debugClassName, "Assert"), debugObject, debugObject.Scope, null, false, false, Accessibility.Global, DeclarationType.Procedure);
194+
var debugPrint = new Declaration(new QualifiedMemberName(debugClassName, "Print"), debugObject, debugObject.Scope, null, false, false, Accessibility.Global, DeclarationType.Procedure);
195+
196+
_state.AddDeclaration(debugClass);
197+
_state.AddDeclaration(debugObject);
198+
_state.AddDeclaration(debugAssert);
199+
_state.AddDeclaration(debugPrint);
200+
}
201+
170202
private readonly HashSet<ReferencePriorityMap> _references = new HashSet<ReferencePriorityMap>();
171203

172204
private void SyncComReferences(IReadOnlyList<VBProject> projects)
173205
{
174206
foreach (var vbProject in projects)
175207
{
176208
var projectId = QualifiedModuleName.GetProjectId(vbProject);
209+
// use a 'for' loop to store the order of references as a 'priority'.
210+
// reference resolver needs this to know which declaration to prioritize when a global identifier exists in multiple libraries.
177211
for (var priority = 1; priority <= vbProject.References.Count; priority++)
178212
{
179213
var reference = vbProject.References.Item(priority);
@@ -368,7 +402,7 @@ private void ResolveDeclarations(VBComponent component, IParseTree tree)
368402
emptyStringLiteralListener,
369403
argListWithOneByRefParamListener,
370404
}), tree);
371-
// TODO: these are actually (almost) isnpection results.. we should handle them as such
405+
// TODO: these are actually (almost) inspection results.. we should handle them as such
372406
_state.ArgListsWithOneByRefParam = argListWithOneByRefParamListener.Contexts.Select(context => new QualifiedContext(qualifiedModuleName, context));
373407
_state.EmptyStringLiterals = emptyStringLiteralListener.Contexts.Select(context => new QualifiedContext(qualifiedModuleName, context));
374408
_state.ObsoleteLetContexts = obsoleteLetStatementListener.Contexts.Select(context => new QualifiedContext(qualifiedModuleName, context));
@@ -382,10 +416,13 @@ private void ResolveDeclarations(VBComponent component, IParseTree tree)
382416
declarationsListener.NewDeclaration += (sender, e) => _state.AddDeclaration(e.Declaration);
383417
declarationsListener.CreateModuleDeclarations();
384418
// rewalk parse tree for second declaration level
419+
420+
Debug.WriteLine("Walking parse tree for '{0}'... (acquiring declarations)", qualifiedModuleName.Name);
385421
ParseTreeWalker.Default.Walk(declarationsListener, tree);
422+
386423
} catch (Exception exception)
387424
{
388-
Debug.Print("Exception thrown resolving '{0}' (thread {2}): {1}", component.Name, exception, Thread.CurrentThread.ManagedThreadId);
425+
Debug.Print("Exception thrown acquiring declarations for '{0}' (thread {2}): {1}", component.Name, exception, Thread.CurrentThread.ManagedThreadId);
389426
_state.SetModuleState(component, ParserState.ResolverError);
390427
}
391428

@@ -399,8 +436,8 @@ private void ResolveReferences(DeclarationFinder finder, VBComponent component,
399436
return;
400437
}
401438

402-
Debug.WriteLine("Resolving '{0}'... (thread {1})", component.Name, Thread.CurrentThread.ManagedThreadId);
403439
var qualifiedName = new QualifiedModuleName(component);
440+
Debug.WriteLine("Resolving identifier references in '{0}'... (thread {1})", qualifiedName.Name, Thread.CurrentThread.ManagedThreadId);
404441
var resolver = new IdentifierReferenceResolver(qualifiedName, finder);
405442
var listener = new IdentifierReferenceListener(resolver);
406443
if (!string.IsNullOrWhiteSpace(tree.GetText().Trim()))

Rubberduck.Parsing/VBA/RubberduckParserState.cs

Lines changed: 10 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -235,8 +235,7 @@ private ParserState EvaluateParserState()
235235
if (moduleStates.Any(module => module != ParserState.Ready))
236236
{
237237
// now any module not ready means at least one of them has work in progress;
238-
// report the least advanced of them, except if that's 'Pending':
239-
return moduleStates.Except(new[]{ParserState.Pending}).Min();
238+
return moduleStates.Min();
240239
}
241240

242241
return default(ParserState); // default value is 'Pending'.
@@ -560,7 +559,7 @@ public bool IsNewOrModified(QualifiedModuleName key)
560559
private QualifiedSelection _lastSelection;
561560
private Declaration _selectedDeclaration;
562561

563-
public Declaration FindSelectedDeclaration(CodePane activeCodePane)
562+
public Declaration FindSelectedDeclaration(CodePane activeCodePane, bool procedureLevelOnly = false)
564563
{
565564
var selection = activeCodePane.GetSelection();
566565
if (selection.Equals(_lastSelection))
@@ -588,10 +587,17 @@ public Declaration FindSelectedDeclaration(CodePane activeCodePane)
588587
}
589588
else
590589
{
590+
Declaration match = null;
591+
if (procedureLevelOnly)
592+
{
593+
match = matches.SingleOrDefault(item => item.DeclarationType.HasFlag(DeclarationType.Member));
594+
}
595+
591596
// ambiguous (?), or no match - make the module be the current selection
592-
var match = AllUserDeclarations.SingleOrDefault(item =>
597+
match = match ?? AllUserDeclarations.SingleOrDefault(item =>
593598
(item.DeclarationType == DeclarationType.Class || item.DeclarationType == DeclarationType.Module)
594599
&& item.QualifiedName.QualifiedModuleName.Equals(selection.QualifiedName));
600+
595601
_selectedDeclaration = match;
596602
}
597603
}

Rubberduck.VBEEditor/QualifiedModuleName.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -103,7 +103,7 @@ public override string ToString()
103103
{
104104
return _component == null && string.IsNullOrEmpty(_projectName)
105105
? string.Empty
106-
: (string.IsNullOrEmpty(_projectPath) ? string.Empty : _projectPath + ";")
106+
: (string.IsNullOrEmpty(_projectPath) ? string.Empty : System.IO.Path.GetFileName(_projectPath) + ";")
107107
+ _projectName + "." + _componentName;
108108
}
109109

0 commit comments

Comments
 (0)