Skip to content

Commit 817509e

Browse files
authored
Merge branch 'rd-next' into next
2 parents 280f29f + 2ba960b commit 817509e

File tree

7 files changed

+212
-56
lines changed

7 files changed

+212
-56
lines changed

RetailCoder.VBE/Inspections/ParameterCanBeByValInspection.cs

Lines changed: 37 additions & 30 deletions
Original file line numberDiff line numberDiff line change
@@ -23,53 +23,61 @@ public ParameterCanBeByValInspection(RubberduckParserState state)
2323

2424
public override IEnumerable<InspectionResultBase> GetInspectionResults()
2525
{
26-
var declarations = UserDeclarations.ToList();
26+
var declarations = UserDeclarations.ToArray();
2727
var issues = new List<ParameterCanBeByValInspectionResult>();
2828

29-
var interfaceDeclarationMembers = declarations.FindInterfaceMembers().ToList();
30-
var interfaceScopes = declarations.FindInterfaceImplementationMembers().Concat(interfaceDeclarationMembers).Select(s => s.Scope);
29+
var interfaceDeclarationMembers = declarations.FindInterfaceMembers().ToArray();
30+
var interfaceScopes = declarations.FindInterfaceImplementationMembers().Concat(interfaceDeclarationMembers).Select(s => s.Scope).ToArray();
3131

3232
issues.AddRange(GetResults(declarations, interfaceDeclarationMembers));
3333

34-
var eventMembers = declarations.Where(item => !item.IsBuiltIn && item.DeclarationType == DeclarationType.Event).ToList();
35-
var formEventHandlerScopes = State.FindFormEventHandlers().Select(handler => handler.Scope);
36-
var eventHandlerScopes = State.DeclarationFinder.FindEventHandlers().Concat(declarations.FindUserEventHandlers()).Select(e => e.Scope);
34+
var eventMembers = declarations.Where(item => !item.IsBuiltIn && item.DeclarationType == DeclarationType.Event).ToArray();
35+
var formEventHandlerScopes = State.FindFormEventHandlers().Select(handler => handler.Scope).ToArray();
36+
var eventHandlerScopes = State.DeclarationFinder.FindEventHandlers().Concat(declarations.FindUserEventHandlers()).Select(e => e.Scope).ToArray();
3737
var eventScopes = eventMembers.Select(s => s.Scope)
3838
.Concat(formEventHandlerScopes)
39-
.Concat(eventHandlerScopes);
39+
.Concat(eventHandlerScopes)
40+
.ToArray();
4041

4142
issues.AddRange(GetResults(declarations, eventMembers));
4243

4344
var declareScopes = declarations.Where(item =>
4445
item.DeclarationType == DeclarationType.LibraryFunction
4546
|| item.DeclarationType == DeclarationType.LibraryProcedure)
46-
.Select(e => e.Scope);
47+
.Select(e => e.Scope)
48+
.ToArray();
4749

48-
issues.AddRange(declarations.Where(declaration =>
50+
issues.AddRange(declarations.OfType<ParameterDeclaration>()
51+
.Where(declaration => IsIssue(declaration, declarations, declareScopes, eventScopes, interfaceScopes))
52+
.Select(issue => new ParameterCanBeByValInspectionResult(this, State, issue, issue.Context, issue.QualifiedName)));
53+
54+
return issues;
55+
}
56+
57+
private bool IsIssue(ParameterDeclaration declaration, Declaration[] userDeclarations, string[] declareScopes, string[] eventScopes, string[] interfaceScopes)
58+
{
59+
var isIssue =
4960
!declaration.IsArray
50-
&& (declaration.AsTypeDeclaration == null || declaration.AsTypeDeclaration.DeclarationType != DeclarationType.UserDefinedType)
61+
&& !declaration.IsParamArray
62+
&& (declaration.IsByRef || declaration.IsImplicitByRef)
63+
&& (declaration.AsTypeDeclaration == null || declaration.AsTypeDeclaration.DeclarationType != DeclarationType.ClassModule && declaration.AsTypeDeclaration.DeclarationType != DeclarationType.UserDefinedType && declaration.AsTypeDeclaration.DeclarationType != DeclarationType.Enumeration)
5164
&& !declareScopes.Contains(declaration.ParentScope)
5265
&& !eventScopes.Contains(declaration.ParentScope)
5366
&& !interfaceScopes.Contains(declaration.ParentScope)
54-
&& declaration.DeclarationType == DeclarationType.Parameter
55-
&& ((VBAParser.ArgContext)declaration.Context).BYVAL() == null
56-
&& !IsUsedAsByRefParam(declarations, declaration)
57-
&& !declaration.References.Any(reference => reference.IsAssignment))
58-
.Select(issue => new ParameterCanBeByValInspectionResult(this, State, issue, issue.Context, issue.QualifiedName)));
59-
60-
return issues;
67+
&& !IsUsedAsByRefParam(userDeclarations, declaration)
68+
&& (!declaration.References.Any() || !declaration.References.Any(reference => reference.IsAssignment));
69+
return isIssue;
6170
}
6271

63-
private IEnumerable<ParameterCanBeByValInspectionResult> GetResults(List<Declaration> declarations, List<Declaration> declarationMembers)
72+
private IEnumerable<ParameterCanBeByValInspectionResult> GetResults(Declaration[] declarations, Declaration[] declarationMembers)
6473
{
6574
foreach (var declaration in declarationMembers)
6675
{
67-
var declarationParameters =
68-
declarations.Where(d => d.DeclarationType == DeclarationType.Parameter &&
69-
Equals(d.ParentDeclaration, declaration))
70-
.OrderBy(o => o.Selection.StartLine)
71-
.ThenBy(t => t.Selection.StartColumn)
72-
.ToList();
76+
var declarationParameters = declarations.OfType<ParameterDeclaration>()
77+
.Where(d => Equals(d.ParentDeclaration, declaration))
78+
.OrderBy(o => o.Selection.StartLine)
79+
.ThenBy(t => t.Selection.StartColumn)
80+
.ToList();
7381

7482
if (!declarationParameters.Any()) { continue; }
7583
var parametersAreByRef = declarationParameters.Select(s => true).ToList();
@@ -80,12 +88,11 @@ private IEnumerable<ParameterCanBeByValInspectionResult> GetResults(List<Declara
8088

8189
foreach (var member in members)
8290
{
83-
var parameters =
84-
declarations.Where(d => d.DeclarationType == DeclarationType.Parameter &&
85-
Equals(d.ParentDeclaration, member))
86-
.OrderBy(o => o.Selection.StartLine)
87-
.ThenBy(t => t.Selection.StartColumn)
88-
.ToList();
91+
var parameters = declarations.OfType<ParameterDeclaration>()
92+
.Where(d => Equals(d.ParentDeclaration, member))
93+
.OrderBy(o => o.Selection.StartLine)
94+
.ThenBy(t => t.Selection.StartColumn)
95+
.ToList();
8996

9097
for (var i = 0; i < parameters.Count; i++)
9198
{

Rubberduck.Parsing/Symbols/DeclarationFinder.cs

Lines changed: 4 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -242,7 +242,10 @@ public IEnumerable<Declaration> FindAllInterfaceImplementingMembers()
242242

243243
public Declaration FindParameter(Declaration procedure, string parameterName)
244244
{
245-
return _parametersByParent[procedure].SingleOrDefault(parameter => parameter.IdentifierName == parameterName);
245+
ConcurrentBag<Declaration> parameters;
246+
return _parametersByParent.TryGetValue(procedure, out parameters)
247+
? parameters.SingleOrDefault(parameter => parameter.IdentifierName == parameterName)
248+
: null;
246249
}
247250

248251
public IEnumerable<Declaration> FindMemberMatches(Declaration parent, string memberName)

Rubberduck.Parsing/VBA/ComponentParseTask.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -92,7 +92,7 @@ public void Start(CancellationToken token)
9292
}
9393
catch (SyntaxErrorException exception)
9494
{
95-
//System.Diagnostics.Debug.Assert(false, "A RecognitionException should be notified of, not thrown as a SyntaxErrorException. This lets the parser recover from parse errors.");
95+
Logger.Warn("Syntax error; offending token '{0}' at line {1}, column {2} in module {3}.", exception.OffendingSymbol.Text, exception.LineNumber, exception.Position, _qualifiedName);
9696
Logger.Error(exception, "Exception thrown in thread {0}, ParseTaskID {1}.", Thread.CurrentThread.ManagedThreadId, _taskId);
9797
var failedHandler = ParseFailure;
9898
if (failedHandler != null)

Rubberduck.Parsing/VBA/ParseCoordinator.cs

Lines changed: 20 additions & 18 deletions
Original file line numberDiff line numberDiff line change
@@ -17,7 +17,6 @@
1717
using Rubberduck.VBEditor.SafeComWrappers.Abstract;
1818
using System.Runtime.InteropServices;
1919
using Rubberduck.VBEditor.Application;
20-
using Rubberduck.VBEditor.Extensions;
2120

2221
// ReSharper disable LoopCanBeConvertedToQuery
2322

@@ -75,8 +74,8 @@ public ParseCoordinator(
7574
// but the cancelees need to use their own token.
7675
private readonly List<CancellationTokenSource> _cancellationTokens = new List<CancellationTokenSource> { new CancellationTokenSource() };
7776

78-
private readonly Object _cancellationSyncObject = new Object();
79-
private readonly Object _parsingRunSyncObject = new Object();
77+
private readonly object _cancellationSyncObject = new object();
78+
private readonly object _parsingRunSyncObject = new object();
8079

8180
private void ReparseRequested(object sender, EventArgs e)
8281
{
@@ -89,7 +88,7 @@ private void ReparseRequested(object sender, EventArgs e)
8988

9089
if (!_isTestScope)
9190
{
92-
Task.Run(() => ParseAll(sender, token));
91+
Task.Run(() => ParseAll(sender, token), token);
9392
}
9493
else
9594
{
@@ -295,7 +294,7 @@ private void ClearModuleToModuleReferences(ICollection<QualifiedModuleName> toCl
295294
}
296295
}
297296

298-
//This doesn not live on the RubberduckParserState to keep concurrency haanlding out of it.
297+
//This does not live on the RubberduckParserState to keep concurrency haanlding out of it.
299298
public void RemoveAllReferencesBy(ICollection<QualifiedModuleName> referencesFromToRemove, ICollection<QualifiedModuleName> modulesNotNeedingReferenceRemoval, DeclarationFinder finder, CancellationToken token)
300299
{
301300
var referencedModulesNeedingReferenceRemoval = State.ModulesReferencedBy(referencesFromToRemove).Where(qmn => !modulesNotNeedingReferenceRemoval.Contains(qmn));
@@ -343,7 +342,7 @@ private void ParseComponents(ICollection<IVBComponent> components, CancellationT
343342
{
344343
if (exception.Flatten().InnerExceptions.All(ex => ex is OperationCanceledException))
345344
{
346-
throw exception.InnerException; //This eliminates the stack trace, but for the cancellation, this is irrelevant.
345+
throw exception.InnerException ?? exception; //This eliminates the stack trace, but for the cancellation, this is irrelevant.
347346
}
348347
State.SetStatusAndFireStateChanged(this, ParserState.Error);
349348
throw;
@@ -438,7 +437,7 @@ private void ResolveAllDeclarations(ICollection<IVBComponent> components, Cancel
438437
{
439438
if (exception.Flatten().InnerExceptions.All(ex => ex is OperationCanceledException))
440439
{
441-
throw exception.InnerException; //This eliminates the stack trace, but for the cancellation, this is irrelevant.
440+
throw exception.InnerException ?? exception; //This eliminates the stack trace, but for the cancellation, this is irrelevant.
442441
}
443442
State.SetStatusAndFireStateChanged(this, ParserState.ResolverError);
444443
throw;
@@ -537,7 +536,7 @@ private void ResolveAllReferences(ICollection<QualifiedModuleName> toResolve, Ca
537536
{
538537
if (exception.Flatten().InnerExceptions.All(ex => ex is OperationCanceledException))
539538
{
540-
throw exception.InnerException; //This eliminates the stack trace, but for the cancellation, this is irrelevant.
539+
throw exception.InnerException ?? exception; //This eliminates the stack trace, but for the cancellation, this is irrelevant.
541540
}
542541
State.SetStatusAndFireStateChanged(this, ParserState.ResolverError);
543542
throw;
@@ -611,9 +610,12 @@ private void ResolveReferences(DeclarationFinder finder, QualifiedModuleName qua
611610

612611
private void AddModuleToModuleReferences(DeclarationFinder finder, CancellationToken token)
613612
{
614-
var options = new ParallelOptions();
615-
options.CancellationToken = token;
616-
options.MaxDegreeOfParallelism = _maxDegreeOfReferenceResolverParallelism;
613+
var options = new ParallelOptions
614+
{
615+
CancellationToken = token,
616+
MaxDegreeOfParallelism = _maxDegreeOfReferenceResolverParallelism
617+
};
618+
617619
try
618620
{
619621
Parallel.For(0, State.ParseTrees.Count, options,
@@ -624,7 +626,7 @@ private void AddModuleToModuleReferences(DeclarationFinder finder, CancellationT
624626
{
625627
if (exception.Flatten().InnerExceptions.All(ex => ex is OperationCanceledException))
626628
{
627-
throw exception.InnerException; //This eliminates the stack trace, but for the cancellation, this is irrelevant.
629+
throw exception.InnerException ?? exception; //This eliminates the stack trace, but for the cancellation, this is irrelevant.
628630
}
629631
State.SetStatusAndFireStateChanged(this, ParserState.ResolverError);
630632
throw;
@@ -749,9 +751,9 @@ private void ParseAllInternal(object requestor, CancellationToken token)
749751
/// </summary>
750752
private bool CleanUpRemovedComponents(ICollection<IVBComponent> components, CancellationToken token)
751753
{
752-
var removedModuledecalrations = RemovedModuleDeclarations(components);
753-
var componentRemoved = removedModuledecalrations.Any();
754-
var removedModules = removedModuledecalrations.Select(declaration => declaration.QualifiedName.QualifiedModuleName).ToHashSet();
754+
var removedModuleDeclarations = RemovedModuleDeclarations(components).ToArray();
755+
var componentRemoved = removedModuleDeclarations.Any();
756+
var removedModules = removedModuleDeclarations.Select(declaration => declaration.QualifiedName.QualifiedModuleName).ToHashSet();
755757
if (removedModules.Any())
756758
{
757759
RemoveAllReferencesBy(removedModules, removedModules, State.DeclarationFinder, token);
@@ -865,7 +867,7 @@ private void SyncComReferences(IReadOnlyList<IVBProject> projects, CancellationT
865867
{
866868
if (exception.Flatten().InnerExceptions.All(ex => ex is OperationCanceledException))
867869
{
868-
throw exception.InnerException; //This eliminates the stack trace, but for the cancellation, this is irrelevant.
870+
throw exception.InnerException ?? exception; //This eliminates the stack trace, but for the cancellation, this is irrelevant.
869871
}
870872
State.SetStatusAndFireStateChanged(this, ParserState.Error);
871873
throw;
@@ -952,7 +954,7 @@ private void LoadReference(IReference localReference, ConcurrentBag<IReference>
952954
}
953955
else
954956
{
955-
LoadReferenceByCOMReflection(localReference, comReflector);
957+
LoadReferenceFromTypeLibrary(localReference, comReflector);
956958
}
957959
}
958960
catch (Exception exception)
@@ -973,7 +975,7 @@ private void LoadReferenceByDeserialization(IReference localReference, Reference
973975
}
974976
}
975977

976-
private void LoadReferenceByCOMReflection(IReference localReference, ReferencedDeclarationsCollector comReflector)
978+
private void LoadReferenceFromTypeLibrary(IReference localReference, ReferencedDeclarationsCollector comReflector)
977979
{
978980
Logger.Trace(string.Format("COM reflecting reference '{0}'.", localReference.Name));
979981
var declarations = comReflector.LoadDeclarationsFromLibrary();

Rubberduck.Parsing/VBA/RubberduckParserState.cs

Lines changed: 26 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1069,7 +1069,31 @@ public Declaration FindSelectedDeclaration(ICodePane activeCodePane, bool proced
10691069
item.DeclarationType == DeclarationType.ProceduralModule) &&
10701070
item.QualifiedName.QualifiedModuleName.Equals(selection.Value.QualifiedName))
10711071
{
1072+
// var line = selection.Value.Selection.StartLine;
1073+
// var procType = activeCodePane.CodeModule.GetProcKindOfLine(line);
1074+
// var procName = activeCodePane.CodeModule.GetProcOfLine(line);
1075+
// if (!string.IsNullOrEmpty(procName))
1076+
// {
1077+
// switch (procType)
1078+
// {
1079+
// case ProcKind.PropertyGet:
1080+
// match = DeclarationFinder.Members(item).SingleOrDefault(m => m.IdentifierName == procName && m.DeclarationType == DeclarationType.PropertyGet);
1081+
// break;
1082+
// case ProcKind.PropertyLet:
1083+
// match = DeclarationFinder.Members(item).SingleOrDefault(m => m.IdentifierName == procName && m.DeclarationType == DeclarationType.PropertyLet);
1084+
// break;
1085+
// case ProcKind.PropertySet:
1086+
// match = DeclarationFinder.Members(item).SingleOrDefault(m => m.IdentifierName == procName && m.DeclarationType == DeclarationType.PropertySet);
1087+
// break;
1088+
// default:
1089+
// match = DeclarationFinder.Members(item).SingleOrDefault(m => m.IdentifierName == procName);
1090+
// break;
1091+
// }
1092+
// }
1093+
// else
1094+
// {
10721095
match = match != null ? null : item;
1096+
// }
10731097
}
10741098
}
10751099
}
@@ -1159,9 +1183,9 @@ public void ClearModuleToModuleReferencesFromModule(QualifiedModuleName referenc
11591183
return;
11601184
}
11611185

1162-
ModuleState referencedModuleState;
11631186
foreach (var referencedModule in referencingModuleState.HasReferenceToModule.Keys)
11641187
{
1188+
ModuleState referencedModuleState;
11651189
if (!_moduleStates.TryGetValue(referencedModule,out referencedModuleState))
11661190
{
11671191
continue;
@@ -1184,6 +1208,7 @@ public HashSet<QualifiedModuleName> ModulesReferencedBy(QualifiedModuleName refe
11841208
public HashSet<QualifiedModuleName> ModulesReferencedBy(IEnumerable<QualifiedModuleName> referencingModules)
11851209
{
11861210
var toModules = new HashSet<QualifiedModuleName>();
1211+
11871212
foreach (var referencingModule in referencingModules)
11881213
{
11891214
toModules.UnionWith(ModulesReferencedBy(referencingModule));

Rubberduck.VBEEditor/SafeComWrappers/VBA/Controls.cs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -42,10 +42,10 @@ public override void Release(bool final = false)
4242
{
4343
if (!IsWrappingNullReference)
4444
{
45-
for (var i = 1; i <= Count; i++)
46-
{
47-
this[i].Release();
48-
}
45+
//for (var i = 1; i <= Count; i++)
46+
//{
47+
// this[i].Release();
48+
//}
4949
base.Release(final);
5050
}
5151
}

0 commit comments

Comments
 (0)