Skip to content

Commit 40edf8e

Browse files
committed
split ComplexType resolution into scenarios. this needs to be refactored, badly. and it's apparently still not working.
1 parent bc28c87 commit 40edf8e

File tree

1 file changed

+140
-24
lines changed

1 file changed

+140
-24
lines changed

Rubberduck.Parsing/Symbols/IdentifierReferenceResolver.cs

Lines changed: 140 additions & 24 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,7 @@
11
using System;
22
using System.CodeDom.Compiler;
33
using System.Collections.Generic;
4+
using System.Configuration;
45
using System.Linq;
56
using Antlr4.Runtime;
67
using Rubberduck.Parsing.Grammar;
@@ -176,38 +177,153 @@ private Declaration ResolveType(VBAParser.ComplexTypeContext context)
176177
return null;
177178
}
178179

179-
var identifiers = context.ambiguousIdentifier();
180+
var identifiers = context.ambiguousIdentifier()
181+
.Select(identifier => identifier)
182+
.ToList();
180183

181-
// VBA doesn't support namespaces.
182-
// A "ComplexType" is therefore only ever as "complex" as [Library].[Type].
183-
var identifier = identifiers.Last();
184-
var library = identifiers.Count > 1
185-
? identifiers[0]
184+
// if there's only 1 identifier, resolve to the tightest-scope match:
185+
if (identifiers.Count == 1)
186+
{
187+
return ResolveInScopeType(identifiers.Single().GetText(), _currentScope);
188+
}
189+
190+
// if there's 2 or more identifiers, resolve to the deepest path:
191+
var first = identifiers[0].GetText();
192+
var projectMatch = _currentScope.ProjectName == first
193+
? _declarations.SingleOrDefault(declaration =>
194+
declaration.DeclarationType == DeclarationType.Project
195+
&& declaration.Project == _currentScope.Project // todo: account for project references!
196+
&& declaration.IdentifierName == first)
186197
: null;
187198

188-
var libraryName = library == null
189-
? _qualifiedModuleName.ProjectName
190-
: library.GetText();
191-
192-
// note: inter-project references won't work, but we can qualify VbaStandardLib types:
193-
if (libraryName == _qualifiedModuleName.ProjectName || libraryName == "VBA")
194-
{
195-
var matches = _declarations.Where(d => d.IdentifierName == identifier.GetText());
196-
var results = matches.Where(item =>
197-
item.ProjectName == libraryName
198-
&& _projectScopePublicModifiers.Contains(item.Accessibility)
199-
&& _moduleTypes.Contains(item.DeclarationType)
200-
|| (_currentScope != null && _memberTypes.Contains(_currentScope.DeclarationType)
201-
&& item.DeclarationType == DeclarationType.UserDefinedType
202-
&& item.ComponentName == _currentScope.ComponentName))
203-
.ToList();
199+
if (projectMatch != null)
200+
{
201+
var projectReference = CreateReference(identifiers[0], projectMatch);
204202

205-
return results.Count != 1 ? null : results.SingleOrDefault();
203+
// matches current project. 2nd identifier could be:
204+
// - standard module (only if there's a 3rd identifier)
205+
// - class module
206+
// - UDT
207+
if (identifiers.Count == 3)
208+
{
209+
var moduleMatch = _declarations.SingleOrDefault(declaration =>
210+
!declaration.IsBuiltIn && declaration.ParentDeclaration != null
211+
&& declaration.ParentDeclaration.Equals(projectMatch)
212+
&& declaration.DeclarationType == DeclarationType.Module
213+
&& declaration.IdentifierName == identifiers[1].GetText());
214+
215+
if (moduleMatch != null)
216+
{
217+
var moduleReference = CreateReference(identifiers[1], moduleMatch);
218+
219+
// 3rd identifier can only be a UDT
220+
var udtMatch = _declarations.SingleOrDefault(declaration =>
221+
!declaration.IsBuiltIn && declaration.ParentDeclaration != null
222+
&& declaration.ParentDeclaration.Equals(moduleMatch)
223+
&& declaration.DeclarationType == DeclarationType.UserDefinedType
224+
&& declaration.IdentifierName == identifiers[2].GetText());
225+
if (udtMatch != null)
226+
{
227+
var udtReference = CreateReference(identifiers[2], udtMatch);
228+
projectMatch.AddReference(projectReference);
229+
moduleMatch.AddReference(moduleReference);
230+
udtMatch.AddReference(udtReference);
231+
return udtMatch;
232+
}
233+
}
234+
}
235+
else
236+
{
237+
var match = _declarations.SingleOrDefault(declaration =>
238+
!declaration.IsBuiltIn && declaration.ParentDeclaration != null
239+
&& declaration.ParentDeclaration.Equals(projectMatch)
240+
&& declaration.IdentifierName == identifiers[1].GetText()
241+
&& (declaration.DeclarationType == DeclarationType.Class ||
242+
declaration.DeclarationType == DeclarationType.UserDefinedType));
243+
if (match != null)
244+
{
245+
var reference = CreateReference(identifiers[1], match);
246+
match.AddReference(reference);
247+
return match;
248+
}
249+
}
250+
}
251+
252+
// first identifier didn't match current project.
253+
// if there are 3 identifiers, type isn't in current project.
254+
if (identifiers.Count == 3)
255+
{
256+
return null;
206257
}
258+
else
259+
{
260+
var moduleMatch = _declarations.SingleOrDefault(declaration =>
261+
!declaration.IsBuiltIn && declaration.ParentDeclaration != null
262+
&& declaration.ParentDeclaration.Equals(projectMatch)
263+
&& declaration.DeclarationType == DeclarationType.Module
264+
&& declaration.IdentifierName == identifiers[0].GetText());
207265

266+
if (moduleMatch != null)
267+
{
268+
var moduleReference = CreateReference(identifiers[0], moduleMatch);
269+
270+
// 2nd identifier can only be a UDT
271+
var udtMatch = _declarations.SingleOrDefault(declaration =>
272+
!declaration.IsBuiltIn && declaration.ParentDeclaration != null
273+
&& declaration.ParentDeclaration.Equals(moduleMatch)
274+
&& declaration.DeclarationType == DeclarationType.UserDefinedType
275+
&& declaration.IdentifierName == identifiers[1].GetText());
276+
if (udtMatch != null)
277+
{
278+
var udtReference = CreateReference(identifiers[1], udtMatch);
279+
moduleMatch.AddReference(moduleReference);
280+
udtMatch.AddReference(udtReference);
281+
return udtMatch;
282+
}
283+
}
284+
}
285+
208286
return null;
209287
}
210288

289+
private IEnumerable<Declaration> FindMatchingTypes(string identifier)
290+
{
291+
return _declarations.Where(declaration =>
292+
declaration.IdentifierName == identifier
293+
&& (declaration.DeclarationType == DeclarationType.Class
294+
|| declaration.DeclarationType == DeclarationType.UserDefinedType))
295+
.ToList();
296+
}
297+
298+
private Declaration ResolveInScopeType(string identifier, Declaration scope)
299+
{
300+
var matches = FindMatchingTypes(identifier).ToList();
301+
if (matches.Count == 1)
302+
{
303+
return matches.Single();
304+
}
305+
306+
// more than one matching identifiers found.
307+
// if it matches a UDT in the current scope, resolve to that type.
308+
var sameScopeUdt = matches.Where(declaration =>
309+
declaration.Project == scope.Project
310+
&& declaration.DeclarationType == DeclarationType.UserDefinedType
311+
&& declaration.ParentDeclaration.Equals(scope))
312+
.ToList();
313+
314+
if (sameScopeUdt.Count == 1)
315+
{
316+
return sameScopeUdt.Single();
317+
}
318+
319+
// todo: try to resolve identifier using referenced projects
320+
321+
return null; // match is ambiguous or unknown, return null
322+
}
323+
324+
325+
326+
211327
private Declaration ResolveType(Declaration parent)
212328
{
213329
if (parent != null && parent.DeclarationType == DeclarationType.UserDefinedType)
@@ -221,7 +337,7 @@ private Declaration ResolveType(Declaration parent)
221337
}
222338

223339
var identifier = parent.AsTypeName.Contains(".")
224-
? parent.AsTypeName.Split('.').Last()
340+
? parent.AsTypeName.Split('.').Last() // bug: this can't be right
225341
: parent.AsTypeName;
226342

227343
var matches = _declarations.Where(d => d.IdentifierName == identifier).ToList();

0 commit comments

Comments
 (0)