Skip to content

Commit f4d9943

Browse files
committed
2 parents 33a3bd0 + 6a84c09 commit f4d9943

12 files changed

+101
-35
lines changed

RetailCoder.VBE/Inspections/ImplicitByRefParameterInspection.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -23,7 +23,7 @@ public ImplicitByRefParameterInspection(RubberduckParserState state)
2323
public override IEnumerable<InspectionResultBase> GetInspectionResults()
2424
{
2525
var interfaceMembers = UserDeclarations.FindInterfaceImplementationMembers();
26-
var builtinEventHandlers = State.DeclarationFinder.FindBuiltinEventHandlers();
26+
var builtinEventHandlers = State.DeclarationFinder.FindEventHandlers();
2727

2828
var issues = State.DeclarationFinder
2929
.UserDeclarations(DeclarationType.Parameter)

RetailCoder.VBE/Inspections/ParameterCanBeByValInspection.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -33,7 +33,7 @@ public override IEnumerable<InspectionResultBase> GetInspectionResults()
3333

3434
var eventMembers = declarations.Where(item => !item.IsBuiltIn && item.DeclarationType == DeclarationType.Event).ToList();
3535
var formEventHandlerScopes = State.FindFormEventHandlers().Select(handler => handler.Scope);
36-
var eventHandlerScopes = State.DeclarationFinder.FindBuiltinEventHandlers().Concat(declarations.FindUserEventHandlers()).Select(e => e.Scope);
36+
var eventHandlerScopes = State.DeclarationFinder.FindEventHandlers().Concat(declarations.FindUserEventHandlers()).Select(e => e.Scope);
3737
var eventScopes = eventMembers.Select(s => s.Scope)
3838
.Concat(formEventHandlerScopes)
3939
.Concat(eventHandlerScopes);

RetailCoder.VBE/Inspections/ParameterNotUsedInspection.cs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -28,7 +28,7 @@ public override IEnumerable<InspectionResultBase> GetInspectionResults()
2828
var interfaceMembers = State.DeclarationFinder.FindAllInterfaceMembers();
2929
var interfaceImplementationMembers = State.DeclarationFinder.FindAllInterfaceImplementingMembers();
3030

31-
var builtInHandlers = State.DeclarationFinder.FindBuiltinEventHandlers();
31+
var handlers = State.DeclarationFinder.FindEventHandlers();
3232

3333
var parameters = State.DeclarationFinder
3434
.UserDeclarations(DeclarationType.Parameter)
@@ -38,7 +38,7 @@ public override IEnumerable<InspectionResultBase> GetInspectionResults()
3838
&& parameter.ParentDeclaration.DeclarationType != DeclarationType.LibraryFunction
3939
&& parameter.ParentDeclaration.DeclarationType != DeclarationType.LibraryProcedure
4040
&& !interfaceMembers.Contains(parameter.ParentDeclaration)
41-
&& !builtInHandlers.Contains(parameter.ParentDeclaration))
41+
&& !handlers.Contains(parameter.ParentDeclaration))
4242
.ToList();
4343

4444
var issues = from issue in parameters

RetailCoder.VBE/Inspections/ProcedureCanBeWrittenAsFunctionInspection.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -43,7 +43,7 @@ public override IEnumerable<InspectionResultBase> GetInspectionResults()
4343
}
4444

4545
var userDeclarations = UserDeclarations.ToList();
46-
var builtinHandlers = State.DeclarationFinder.FindBuiltinEventHandlers().ToList();
46+
var builtinHandlers = State.DeclarationFinder.FindEventHandlers().ToList();
4747

4848
var contextLookup = userDeclarations.Where(decl => decl.Context != null).ToDictionary(decl => decl.Context);
4949

RetailCoder.VBE/Inspections/ProcedureNotUsedInspection.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -45,7 +45,7 @@ public override IEnumerable<InspectionResultBase> GetInspectionResults()
4545
var handlers = State.DeclarationFinder.UserDeclarations(DeclarationType.Control)
4646
.SelectMany(control => declarations.FindEventHandlers(control)).ToList();
4747

48-
var builtInHandlers = State.DeclarationFinder.FindBuiltinEventHandlers();
48+
var builtInHandlers = State.DeclarationFinder.FindEventHandlers();
4949
handlers.AddRange(builtInHandlers);
5050

5151
var withEventFields = State.DeclarationFinder.UserDeclarations(DeclarationType.Variable).Where(item => item.IsWithEvents).ToList();

RetailCoder.VBE/Inspections/UseMeaningfulNameInspection.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -42,7 +42,7 @@ public override IEnumerable<InspectionResultBase> GetInspectionResults()
4242
var settings = _settings.Load(new CodeInspectionSettings()) ?? new CodeInspectionSettings();
4343
var whitelistedNames = settings.WhitelistedIdentifiers.Select(s => s.Identifier).ToArray();
4444

45-
var handlers = State.DeclarationFinder.FindBuiltinEventHandlers();
45+
var handlers = State.DeclarationFinder.FindEventHandlers();
4646

4747
var issues = UserDeclarations
4848
.Where(declaration => !string.IsNullOrEmpty(declaration.IdentifierName) &&
Lines changed: 4 additions & 21 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,4 @@
1-
using System;
2-
using System.Diagnostics;
3-
using System.Runtime.InteropServices;
1+
using System.Diagnostics;
42
using System.Runtime.InteropServices.ComTypes;
53
using TYPEATTR = System.Runtime.InteropServices.ComTypes.TYPEATTR;
64
using TYPEFLAGS = System.Runtime.InteropServices.ComTypes.TYPEFLAGS;
@@ -10,7 +8,6 @@ namespace Rubberduck.Parsing.ComReflection
108
[DebuggerDisplay("{Name} As {TypeName}")]
119
public class ComAlias : ComBase
1210
{
13-
public VarEnum VarType { get; private set; }
1411
public string TypeName { get; private set; }
1512
public bool IsHidden { get; private set; }
1613
public bool IsRestricted { get; private set; }
@@ -20,7 +17,6 @@ public ComAlias(ITypeLib typeLib, ITypeInfo info, int index, TYPEATTR attributes
2017
Index = index;
2118
Documentation = new ComDocumentation(typeLib, index);
2219
Guid = attributes.guid;
23-
VarType = (VarEnum)attributes.tdescAlias.vt;
2420
IsHidden = attributes.wTypeFlags.HasFlag(TYPEFLAGS.TYPEFLAG_FHIDDEN);
2521
IsRestricted = attributes.wTypeFlags.HasFlag(TYPEFLAGS.TYPEFLAG_FRESTRICTED);
2622

@@ -29,22 +25,9 @@ public ComAlias(ITypeLib typeLib, ITypeInfo info, int index, TYPEATTR attributes
2925
TypeName = "LongPtr";
3026
return;
3127
}
32-
33-
if (ComVariant.TypeNames.ContainsKey(VarType))
34-
{
35-
TypeName = ComVariant.TypeNames[VarType];
36-
}
37-
else if (VarType == VarEnum.VT_USERDEFINED)
38-
{
39-
ITypeInfo refType;
40-
info.GetRefTypeInfo((int)attributes.tdescAlias.lpValue, out refType);
41-
var doc = new ComDocumentation(refType, -1);
42-
TypeName = doc.Name;
43-
}
44-
else
45-
{
46-
throw new NotImplementedException(string.Format("Didn't expect an alias with a type of {0}.", VarType));
47-
}
28+
29+
var aliased = new ComParameter(attributes, info);
30+
TypeName = aliased.TypeName;
4831
}
4932
}
5033
}

Rubberduck.Parsing/ComReflection/ComParameter.cs

Lines changed: 6 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -37,7 +37,6 @@ public string DeclarationName
3737
public bool IsOptional { get; private set; }
3838
public bool IsParamArray { get; set; }
3939

40-
4140
private Guid _enumGuid = Guid.Empty;
4241
public bool IsEnumMember
4342
{
@@ -81,6 +80,12 @@ public ComParameter(ELEMDESC elemDesc, ITypeInfo info, string name)
8180
DefaultAsEnum = member != null ? member.Name : string.Empty;
8281
}
8382

83+
//This overload should only be used for retrieving the TypeName from a random TYPEATTR. TODO: Should be a base class of ComParameter instead.
84+
public ComParameter(TYPEATTR attributes, ITypeInfo info)
85+
{
86+
GetParameterType(attributes.tdescAlias, info);
87+
}
88+
8489
private void GetParameterType(TYPEDESC desc, ITypeInfo info)
8590
{
8691
var vt = (VarEnum)desc.vt;

Rubberduck.Parsing/Symbols/BoundExpressionVisitor.cs

Lines changed: 8 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,6 @@
11
using Rubberduck.Parsing.Annotations;
22
using Rubberduck.Parsing.Binding;
3+
using Rubberduck.Parsing.Grammar;
34
using Rubberduck.VBEditor;
45

56
namespace Rubberduck.Parsing.Symbols
@@ -47,6 +48,13 @@ private void Visit(
4748
bool isAssignmentTarget,
4849
bool hasExplicitLetStatement)
4950
{
51+
if (isAssignmentTarget && expression.Context.Parent is VBAParser.IndexExprContext && !expression.ReferencedDeclaration.IsArray)
52+
{
53+
// 'SomeDictionary' is not the assignment target in 'SomeDictionary("key") = 42'
54+
// ..but we want to treat array index assignment as assignment to the array itself.
55+
isAssignmentTarget = false;
56+
}
57+
5058
var callSiteContext = expression.Context;
5159
var identifier = expression.Context.GetText();
5260
var callee = expression.ReferencedDeclaration;

Rubberduck.Parsing/Symbols/DeclarationFinder.cs

Lines changed: 24 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -64,7 +64,7 @@ public DeclarationFinder(IReadOnlyList<Declaration> declarations, IEnumerable<IA
6464
_parametersByParent = declarations.Where(declaration => declaration.DeclarationType == DeclarationType.Parameter)
6565
.GroupBy(declaration => declaration.ParentDeclaration).ToConcurrentDictionary();
6666
_userDeclarationsByType = declarations.Where(declaration => !declaration.IsBuiltIn).GroupBy(declaration => declaration.DeclarationType).ToConcurrentDictionary();
67-
_builtinEvents = new Lazy<ConcurrentBag<Declaration>>(() => FindBuiltInEventHandlers(declarations), true);
67+
_eventHandlers = new Lazy<ConcurrentBag<Declaration>>(() => FindEventHandlers(declarations), true);
6868

6969
_projects = _projects = new Lazy<ConcurrentBag<Declaration>>(() => new ConcurrentBag<Declaration>(declarations.Where(d => d.DeclarationType == DeclarationType.Project)), true);
7070
_classes = new Lazy<ConcurrentBag<Declaration>>(() => new ConcurrentBag<Declaration>(declarations.Where(d => d.DeclarationType == DeclarationType.ClassModule)), true);
@@ -165,12 +165,12 @@ public IEnumerable<Declaration> FindDeclarationsWithNonBaseAsType()
165165
}
166166
}
167167

168-
private readonly Lazy<ConcurrentBag<Declaration>> _builtinEvents;
169-
public IEnumerable<Declaration> FindBuiltinEventHandlers()
168+
private readonly Lazy<ConcurrentBag<Declaration>> _eventHandlers;
169+
public IEnumerable<Declaration> FindEventHandlers()
170170
{
171171
lock (ThreadLock)
172172
{
173-
return _builtinEvents.Value;
173+
return _eventHandlers.Value;
174174
}
175175
}
176176

@@ -695,7 +695,23 @@ private IEnumerable<Declaration> FindAllInReferencedProjectByPriority(Declaratio
695695
}
696696
}
697697

698-
public ConcurrentBag<Declaration> FindBuiltInEventHandlers(IEnumerable<Declaration> declarations)
698+
private IEnumerable<Declaration> FindFormControlHandlers(IReadOnlyList<Declaration> declarations)
699+
{
700+
var controls = declarations
701+
.Where(declaration => declaration.DeclarationType == DeclarationType.Control);
702+
var handlerNames = declarations
703+
.Where(declaration => declaration.IsBuiltIn && declaration.DeclarationType == DeclarationType.Event)
704+
.SelectMany(e => controls.Select(c => c.IdentifierName + "_" + e.IdentifierName));
705+
if (!_userDeclarationsByType.ContainsKey(DeclarationType.Procedure))
706+
{
707+
return Enumerable.Empty<Declaration>();
708+
}
709+
var handlers = _userDeclarationsByType[DeclarationType.Procedure]
710+
.Where(procedure => handlerNames.Contains(procedure.IdentifierName));
711+
return handlers;
712+
}
713+
714+
private ConcurrentBag<Declaration> FindEventHandlers(IEnumerable<Declaration> declarations)
699715
{
700716
var declarationList = declarations.ToList();
701717

@@ -725,7 +741,9 @@ public ConcurrentBag<Declaration> FindBuiltInEventHandlers(IEnumerable<Declarati
725741
(!item.IsBuiltIn &&
726742
item.DeclarationType == DeclarationType.Procedure &&
727743
handlerNames.Contains(item.IdentifierName))
728-
);
744+
)
745+
.Concat(_handlersByWithEventsField.Value.SelectMany(kvp => kvp.Value))
746+
.Concat(FindFormControlHandlers(declarationList));
729747

730748
return new ConcurrentBag<Declaration>(handlers);
731749
}

0 commit comments

Comments
 (0)