Skip to content

Commit 4b185ee

Browse files
Andrin Meierretailcoder
authored andcommitted
fix built-in enums/udts can't be resolved because of missing parent (#1631)
1 parent bd1fae3 commit 4b185ee

File tree

7 files changed

+35
-125
lines changed

7 files changed

+35
-125
lines changed

Rubberduck.Parsing/Symbols/AccessibilityCheck.cs

Lines changed: 3 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -23,12 +23,12 @@ public static bool IsModuleAccessible(Declaration callingProject, Declaration ca
2323
{
2424
return true;
2525
}
26-
bool sameProject = calleeModule != null && callingModule.ParentScopeDeclaration.Equals(calleeModule.ParentScopeDeclaration);
26+
bool sameProject = callingModule.ParentScopeDeclaration.Equals(calleeModule.ParentScopeDeclaration);
2727
if (sameProject)
2828
{
2929
return validAccessibility;
3030
}
31-
if (calleeModule != null && calleeModule.DeclarationType.HasFlag(DeclarationType.ProceduralModule))
31+
if (calleeModule.DeclarationType.HasFlag(DeclarationType.ProceduralModule))
3232
{
3333
bool isPrivate = ((ProceduralModuleDeclaration)calleeModule).IsPrivateModule;
3434
return validAccessibility && !isPrivate;
@@ -64,13 +64,7 @@ public static bool IsMemberAccessible(Declaration callingProject, Declaration ca
6464
return calleeHasSameParent;
6565
}
6666
var memberModule = Declaration.GetModuleParent(calleeMember);
67-
// TODO: Fix this?
68-
// Assume null = built in declaration which is always accessible.
69-
if (memberModule == null)
70-
{
71-
return true;
72-
}
73-
if (IsModuleAccessible(callingProject, callingModule, memberModule) && calleeMember.ParentScopeDeclaration.DeclarationType.HasFlag(DeclarationType.Module))
67+
if (IsModuleAccessible(callingProject, callingModule, memberModule))
7468
{
7569
if (calleeMember.DeclarationType.HasFlag(DeclarationType.EnumerationMember) || calleeMember.DeclarationType.HasFlag(DeclarationType.UserDefinedTypeMember))
7670
{

Rubberduck.Parsing/Symbols/Declaration.cs

Lines changed: 6 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -438,11 +438,15 @@ public string ProjectName
438438
/// </remarks>
439439
public string AsTypeName { get { return _asTypeName; } }
440440

441-
public virtual string AsTypeNameWithoutArrayDesignator
441+
public string AsTypeNameWithoutArrayDesignator
442442
{
443443
get
444444
{
445-
return AsTypeName;
445+
if (string.IsNullOrWhiteSpace(AsTypeName))
446+
{
447+
return AsTypeName;
448+
}
449+
return AsTypeName.Replace("(", "").Replace(")", "").Trim();
446450
}
447451
}
448452

Rubberduck.Parsing/Symbols/DeclarationFinder.cs

Lines changed: 1 addition & 75 deletions
Original file line numberDiff line numberDiff line change
@@ -63,17 +63,6 @@ public IEnumerable<Declaration> FindProjects()
6363
return _declarations.Where(d => d.DeclarationType == DeclarationType.Project).ToList();
6464
}
6565

66-
public IEnumerable<CommentNode> ModuleComments(QualifiedModuleName module)
67-
{
68-
CommentNode[] result;
69-
if (_comments.TryGetValue(module, out result))
70-
{
71-
return result;
72-
}
73-
74-
return new List<CommentNode>();
75-
}
76-
7766
public Declaration FindParameter(Declaration procedure, string parameterName)
7867
{
7968
var matches = MatchName(parameterName);
@@ -90,14 +79,6 @@ public IEnumerable<IAnnotation> FindAnnotations(QualifiedModuleName module)
9079
return new List<IAnnotation>();
9180
}
9281

93-
public IEnumerable<Declaration> MatchTypeName(string name)
94-
{
95-
return MatchName(name).Where(declaration =>
96-
declaration.DeclarationType.HasFlag(DeclarationType.ClassModule) ||
97-
declaration.DeclarationType.HasFlag(DeclarationType.UserDefinedType) ||
98-
declaration.DeclarationType.HasFlag(DeclarationType.Enumeration));
99-
}
100-
10182
public bool IsMatch(string declarationName, string potentialMatchName)
10283
{
10384
return string.Equals(declarationName, potentialMatchName, StringComparison.OrdinalIgnoreCase);
@@ -160,59 +141,6 @@ public Declaration FindStdModule(string name, Declaration parent = null, bool in
160141
return result;
161142
}
162143

163-
public Declaration FindUserDefinedType(string name, Declaration parent = null, bool includeBuiltIn = false)
164-
{
165-
Declaration result = null;
166-
try
167-
{
168-
var matches = MatchName(name);
169-
result = matches.SingleOrDefault(declaration => declaration.DeclarationType.HasFlag(DeclarationType.UserDefinedType)
170-
&& (parent == null || parent.Equals(declaration.ParentDeclaration))
171-
&& (includeBuiltIn || !declaration.IsBuiltIn));
172-
}
173-
catch (Exception exception)
174-
{
175-
_logger.Error(exception, "Multiple matches found for user-defined type '{0}'.", name);
176-
}
177-
178-
return result;
179-
}
180-
181-
public Declaration FindEnum(string name, Declaration parent = null, bool includeBuiltIn = false)
182-
{
183-
Declaration result = null;
184-
try
185-
{
186-
var matches = MatchName(name);
187-
result = matches.SingleOrDefault(declaration => declaration.DeclarationType.HasFlag(DeclarationType.Enumeration)
188-
&& (parent == null || parent.Equals(declaration.ParentDeclaration))
189-
&& (includeBuiltIn || !declaration.IsBuiltIn));
190-
}
191-
catch (Exception exception)
192-
{
193-
_logger.Error(exception, "Multiple matches found for enum type '{0}'.", name);
194-
}
195-
196-
return result;
197-
}
198-
199-
public Declaration FindClass(Declaration parent, string name, bool includeBuiltIn = false)
200-
{
201-
Declaration result = null;
202-
try
203-
{
204-
result = MatchName(name).SingleOrDefault(declaration => declaration.DeclarationType.HasFlag(DeclarationType.ClassModule)
205-
&& (parent == null || parent.Equals(declaration.ParentDeclaration))
206-
&& (includeBuiltIn || !declaration.IsBuiltIn));
207-
}
208-
catch (InvalidOperationException exception)
209-
{
210-
_logger.Error(exception, "Multiple matches found for class '{0}'.", name);
211-
}
212-
213-
return result;
214-
}
215-
216144
public Declaration FindReferencedProject(Declaration callingProject, string referencedProjectName)
217145
{
218146
return FindInReferencedProjectByPriority(callingProject, referencedProjectName, p => p.DeclarationType.HasFlag(DeclarationType.Project));
@@ -353,9 +281,7 @@ public Declaration FindMemberEnclosedProjectWithoutEnclosingModule(Declaration c
353281
var allMatches = MatchName(memberName);
354282
var memberMatches = allMatches.Where(m =>
355283
m.DeclarationType.HasFlag(memberType)
356-
// TODO: Fix this?
357-
// Assume no module = built-in, not checkable thus we conservatively include it in the matches.
358-
&& (Declaration.GetModuleParent(m) == null || Declaration.GetModuleParent(m).DeclarationType == DeclarationType.ProceduralModule)
284+
&& Declaration.GetModuleParent(m).DeclarationType == DeclarationType.ProceduralModule
359285
&& Declaration.GetProjectParent(m).Equals(callingProject)
360286
&& !callingModule.Equals(Declaration.GetModuleParent(m)));
361287
var accessibleMembers = memberMatches.Where(m => AccessibilityCheck.IsMemberAccessible(callingProject, callingModule, callingParent, m));

Rubberduck.Parsing/Symbols/FunctionDeclaration.cs

Lines changed: 0 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -78,21 +78,5 @@ public bool IsDefaultMember
7878
return false;
7979
}
8080
}
81-
82-
public override string AsTypeNameWithoutArrayDesignator
83-
{
84-
get
85-
{
86-
if (string.IsNullOrWhiteSpace(AsTypeName))
87-
{
88-
return AsTypeName;
89-
}
90-
if (!IsArray)
91-
{
92-
return AsTypeName;
93-
}
94-
return AsTypeName.Substring(0, AsTypeName.IndexOf("("));
95-
}
96-
}
9781
}
9882
}

Rubberduck.Parsing/Symbols/PropertyGetDeclaration.cs

Lines changed: 0 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -78,21 +78,5 @@ public bool IsDefaultMember
7878
return false;
7979
}
8080
}
81-
82-
public override string AsTypeNameWithoutArrayDesignator
83-
{
84-
get
85-
{
86-
if (string.IsNullOrWhiteSpace(AsTypeName))
87-
{
88-
return AsTypeName;
89-
}
90-
if (!IsArray)
91-
{
92-
return AsTypeName;
93-
}
94-
return AsTypeName.Substring(0, AsTypeName.IndexOf("("));
95-
}
96-
}
9781
}
9882
}

Rubberduck.Parsing/Symbols/ReferencedDeclarationsCollector.cs

Lines changed: 20 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -20,6 +20,7 @@
2020
using VARDESC = System.Runtime.InteropServices.ComTypes.VARDESC;
2121
using Rubberduck.Parsing.Annotations;
2222
using System.Linq;
23+
using Rubberduck.Parsing.Grammar;
2324

2425
namespace Rubberduck.Parsing.Symbols
2526
{
@@ -206,10 +207,25 @@ public IEnumerable<Declaration> GetDeclarationsForReference(Reference reference)
206207
moduleDeclaration = module;
207208
break;
208209
default:
210+
string pseudoModuleName = string.Format("_{0}", typeName);
211+
var pseudoParentModule = new ProceduralModuleDeclaration(
212+
new QualifiedMemberName(projectQualifiedModuleName, pseudoModuleName),
213+
projectDeclaration,
214+
pseudoModuleName,
215+
true,
216+
new List<IAnnotation>(),
217+
new Attributes());
218+
// Enums don't define their own type but have a declared type of "Long".
219+
if (typeDeclarationType == DeclarationType.Enumeration)
220+
{
221+
typeName = Tokens.Long;
222+
}
223+
// UDTs and ENUMs don't seem to have a module parent that's why we add a "fake" module
224+
// so that the rest of the application can treat it normally.
209225
moduleDeclaration = new Declaration(
210-
typeQualifiedMemberName,
211-
projectDeclaration,
212-
projectDeclaration,
226+
typeQualifiedMemberName,
227+
pseudoParentModule,
228+
pseudoParentModule,
213229
typeName,
214230
null,
215231
false,
@@ -409,7 +425,7 @@ private Declaration CreateFieldDeclaration(ITypeInfo info, int fieldIndex, Decla
409425
var fieldName = names[0];
410426
var memberType = GetDeclarationType(varDesc, typeDeclarationType);
411427

412-
var asTypeName = GetTypeName(varDesc.elemdescVar.tdesc, info);
428+
var asTypeName = GetTypeName(varDesc.elemdescVar.tdesc, info);
413429

414430
return new Declaration(new QualifiedMemberName(typeQualifiedModuleName, fieldName),
415431
moduleDeclaration, moduleDeclaration, asTypeName, null, false, false, Accessibility.Global, memberType, null,

Rubberduck.Parsing/Symbols/TypeAnnotationPass.cs

Lines changed: 5 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -64,7 +64,6 @@ private void AnnotateType(Declaration declaration)
6464
var module = Declaration.GetModuleParent(declaration);
6565
if (module == null)
6666
{
67-
// TODO: Reference Collector does not add module, find workaround?
6867
_logger.Warn("Type annotation failed for {0} because module parent is missing.", typeExpression);
6968
return;
7069
}
@@ -76,8 +75,11 @@ private void AnnotateType(Declaration declaration)
7675
}
7776
else
7877
{
79-
// Commented out due to a massive amount of VT_HRESULT messages.
80-
//Debug.WriteLine(string.Format("{0}: Failed to resolve type {1}.", GetType().Name, typeExpression));
78+
const string IGNORE_THIS = "DISPATCH";
79+
if (typeExpression != IGNORE_THIS)
80+
{
81+
_logger.Warn("Failed to resolve type {0}", typeExpression);
82+
}
8183
}
8284
}
8385
}

0 commit comments

Comments
 (0)