Skip to content

Commit

Permalink
Merge branch 'next' into 5719_RemoveUnusedDeclarationQF_Formatting
Browse files Browse the repository at this point in the history
  • Loading branch information
BZngr committed Apr 16, 2021
2 parents b79a497 + 51f2d13 commit 6842721
Show file tree
Hide file tree
Showing 13 changed files with 96 additions and 52 deletions.
Expand Up @@ -26,6 +26,7 @@ protected override IEnumerable<Declaration> ObjectionableDeclarations(Declaratio
.Select(className => finder.FindClassModule(className, excel, true))
.OfType<ModuleDeclaration>();


return globalModules
.SelectMany(moduleClass => moduleClass.Members)
.Where(declaration => TargetMemberNames.Contains(declaration.IdentifierName)
Expand All @@ -35,7 +36,8 @@ protected override IEnumerable<Declaration> ObjectionableDeclarations(Declaratio

private static readonly string[] GlobalObjectClassNames =
{
"Global", "_Global"
"Global", "_Global",
"Worksheet", "_Worksheet"
};

private static readonly string[] TargetMemberNames =
Expand Down
Expand Up @@ -24,9 +24,7 @@ internal ImplicitWorkbookReferenceInspectionBase(IDeclarationFinderProvider decl

protected override IEnumerable<Declaration> ObjectionableDeclarations(DeclarationFinder finder)
{
var excel = finder.Projects
.SingleOrDefault(project => project.IdentifierName == "Excel" && !project.IsUserDefined);
if (excel == null)
if (!finder.TryFindProjectDeclaration("Excel", out var excel))
{
return Enumerable.Empty<Declaration>();
}
Expand Down
Expand Up @@ -131,20 +131,19 @@ private static IEnumerable<AssignmentNode> FindUnusedAssignmentNodes(INode node,
.Contains(refNode));

var assignmentsPrecedingReference = assignmentExprNodesWithReference.Any()
? assignmentExprNodes.TakeWhile(n => n != assignmentExprNodesWithReference.Last())
.Last()
.Nodes(new[] { typeof(AssignmentNode) })
? assignmentExprNodes.TakeWhile(n => n != assignmentExprNodesWithReference.LastOrDefault())
?.LastOrDefault()
?.Nodes(new[] { typeof(AssignmentNode) })
: allAssignmentsAndReferences.TakeWhile(n => n != refNode)
.OfType<AssignmentNode>();

if (assignmentsPrecedingReference.Any())
if (assignmentsPrecedingReference?.Any() ?? false)
{
usedAssignments.Add(assignmentsPrecedingReference.Last() as AssignmentNode);
usedAssignments.Add(assignmentsPrecedingReference.LastOrDefault() as AssignmentNode);
}
}

return allAssignmentsAndReferences.OfType<AssignmentNode>()
.Except(usedAssignments);
return allAssignmentsAndReferences.OfType<AssignmentNode>().Except(usedAssignments);
}

private static bool IsDescendentOfNeverFlagNode(AssignmentNode assignment)
Expand Down
Expand Up @@ -19,6 +19,7 @@ namespace Rubberduck.CodeAnalysis.Inspections.Concrete
/// a parameter that is passed by reference (implicitly, or explicitly ByRef) makes it ambiguous from the calling code's standpoint, whether the
/// procedure might re-assign these ByRef values and introduce a bug.
/// </why>
/// <remarks>For performance reasons, this inspection will not flag a parameter that is passed as an argument to a procedure that also accepts it ByRef.</remarks>
/// <example hasResult="true">
/// <module name="MyModule" type="Standard Module">
/// <![CDATA[
Expand All @@ -39,6 +40,21 @@ namespace Rubberduck.CodeAnalysis.Inspections.Concrete
/// ]]>
/// </module>
/// </example>
/// <example hasResult="false">
/// <module name="MyModule" type="Standard Module">
/// <![CDATA[
/// Option Explicit
/// Public Sub DoSomething(ByVal foo As long, ByRef bar As Long)
/// DoSomethingElse bar ' ByRef argument will not be flagged
/// Debug.Print foo, bar
/// End Sub
///
/// Private Sub DoSomethingElse(ByRef wouldNeedRecursiveLogic As Long)
/// Debug.Print wouldNeedRecursiveLogic
/// End Sub
/// ]]>
/// </module>
/// </example>
internal sealed class ParameterCanBeByValInspection : DeclarationInspectionBase
{
public ParameterCanBeByValInspection(IDeclarationFinderProvider declarationFinderProvider)
Expand Down
Expand Up @@ -61,19 +61,19 @@ public SheetAccessedUsingStringInspection(IDeclarationFinderProvider declaration

private static readonly string[] InterestingMembers =
{
"Worksheets", "Sheets"
"Worksheets", // gets a Sheets object containing Worksheet objects.
"Sheets", // gets a Sheets object containing all sheets (not just Worksheet sheets) in the qualifying workbook.
};

private static readonly string[] InterestingClasses =
{
"Workbook"
"Workbook", // unqualified member call
"_Workbook", // qualified member call
};

protected override IEnumerable<Declaration> ObjectionableDeclarations(DeclarationFinder finder)
{
var excel = finder.Projects
.SingleOrDefault(project => project.IdentifierName == "Excel" && !project.IsUserDefined);
if (excel == null)
if (!finder.TryFindProjectDeclaration("Excel", out var excel))
{
return Enumerable.Empty<Declaration>();
}
Expand Down
Expand Up @@ -16,7 +16,6 @@ namespace Rubberduck.Parsing.Annotations.Concrete
/// </remarks>
/// <example>
/// <module name="Module1" type="Standard Module">
/// </module>
/// <![CDATA[
/// Option Explicit
/// Option Private Module
Expand All @@ -31,6 +30,7 @@ namespace Rubberduck.Parsing.Annotations.Concrete
/// '...
/// End Sub
/// ]]>
/// </module>
/// </example>
public sealed class EntryPointAnnotation : AnnotationBase
{
Expand Down Expand Up @@ -69,4 +69,4 @@ public override IReadOnlyList<string> ProcessAnnotationArguments(IEnumerable<str
return base.ProcessAnnotationArguments(args);
}
}
}
}
Expand Up @@ -187,7 +187,7 @@ private IBoundExpression ResolveEnclosingProjectNamespace()
var defaultInstanceVariableClass = _declarationFinder.FindDefaultInstanceVariableClassEnclosingProject(_project, _module, _name);
if (defaultInstanceVariableClass != null)
{
return new SimpleNameExpression(defaultInstanceVariableClass, ExpressionClassification.Type, _context);
return new SimpleNameExpression(defaultInstanceVariableClass, ExpressionClassification.Variable, _context);
}
return null;
}
Expand Down
5 changes: 3 additions & 2 deletions Rubberduck.Parsing/Symbols/VariableDeclaration.cs
Expand Up @@ -23,7 +23,8 @@ public sealed class VariableDeclaration : Declaration, IInterfaceExposable
bool isArray,
VBAParser.AsTypeClauseContext asTypeContext,
IEnumerable<IParseTreeAnnotation> annotations = null,
Attributes attributes = null)
Attributes attributes = null,
bool isUserDefined = true)
: base(
qualifiedName,
parentDeclaration,
Expand All @@ -39,7 +40,7 @@ public sealed class VariableDeclaration : Declaration, IInterfaceExposable
selection,
isArray,
asTypeContext,
true,
isUserDefined,
annotations,
attributes)
{
Expand Down
41 changes: 28 additions & 13 deletions Rubberduck.Parsing/VBA/DeclarationCaching/DeclarationFinder.cs
Expand Up @@ -333,7 +333,7 @@ public IEnumerable<ModuleBodyElementDeclaration> FindEventHandlers(Declaration e
{
var withEventsDeclarations = FindWithEventFields(eventDeclaration);
return withEventsDeclarations
.Select(withEventsField => FindHandlersForWithEventsField(withEventsField).Single(handler =>
.Select(withEventsField => FindHandlersForWithEventsField(withEventsField).SingleOrDefault(handler =>
handler.IdentifierName.Equals($"{withEventsField.IdentifierName}_{eventDeclaration.IdentifierName}", StringComparison.InvariantCultureIgnoreCase)));
}

Expand All @@ -357,6 +357,18 @@ public ICollection<Declaration> FindFormEventHandlers()
public IEnumerable<Declaration> Classes => _classes.Value;
public IEnumerable<Declaration> Projects => _projects.Value;

/// <summary>
/// Gets the <see cref="ProjectDeclaration"/> object for specified referenced project/library.
/// </summary>
/// <param name="name">The identifier name of the project declaration to find.</param>
/// <param name="result">The <see cref="ProjectDeclaration"/> result, if found; null otherwise.</param>
/// <param name="includeUserDefined">True to include user-defined projects in the search; false by default.</param>
public bool TryFindProjectDeclaration(string name, out Declaration result, bool includeUserDefined = false)
{
result = _projects.Value.FirstOrDefault(project => project.IdentifierName.Equals(name, StringComparison.InvariantCultureIgnoreCase) && project.IsUserDefined == includeUserDefined);
return result != null;
}

public IEnumerable<Declaration> UserDeclarations(DeclarationType type)
{
return _userDeclarationsByType.TryGetValue(type, out var result)
Expand Down Expand Up @@ -898,9 +910,10 @@ public Declaration FindDefaultInstanceVariableClassReferencedProject(Declaration
string memberName, DeclarationType memberType)
{
var allMatches = MatchName(memberName);
var parentClass = parent as ClassModuleDeclaration;
var memberMatches = allMatches
.Where(m => m.DeclarationType.HasFlag(memberType)
&& parent.Equals(m.ParentDeclaration))
&& (parent.Equals(m.ParentDeclaration) || (parentClass?.Supertypes.Any(t => t.Equals(m.ParentDeclaration)) ?? false)))
.ToList();
var accessibleMembers = memberMatches.Where(m => AccessibilityCheck.IsMemberAccessible(callingProject, callingModule, callingParent, m));
var match = accessibleMembers.FirstOrDefault();
Expand Down Expand Up @@ -934,21 +947,23 @@ public Declaration FindMemberEnclosingModule(Declaration callingModule, Declarat
}
// Classes such as Worksheet have properties such as Range that can be access in a user defined class such as Sheet1,
// that's why we have to walk the type hierarchy and find these implementations.
foreach (var supertype in ClassModuleDeclaration.GetSupertypes(callingModule))
if (callingModule is ClassModuleDeclaration callingClass)
{
// Only built-in classes such as Worksheet can be considered "real base classes".
// User created interfaces work differently and don't allow accessing accessing implementations.
if (supertype.IsUserDefined)
foreach (var supertype in callingClass.Supertypes)
{
continue;
}
var supertypeMatch = FindMemberEnclosingModule(supertype, callingParent, memberName, memberType);
if (supertypeMatch != null)
{
return supertypeMatch;
// Only built-in classes such as Worksheet can be considered "real base classes".
// User created interfaces work differently and don't allow accessing accessing implementations.
if (supertype.IsUserDefined)
{
continue;
}
var supertypeMatch = FindMemberEnclosingModule(supertype, callingParent, memberName, memberType);
if (supertypeMatch != null)
{
return supertypeMatch;
}
}
}

return null;
}

Expand Down
9 changes: 9 additions & 0 deletions Rubberduck.Resources/RubberduckUI.Designer.cs

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

3 changes: 3 additions & 0 deletions Rubberduck.Resources/RubberduckUI.resx
Expand Up @@ -1892,4 +1892,7 @@ Do you want to proceed?</value>
<data name="IndenterSettings_GroupRelatedProperties" xml:space="preserve">
<value>Remove vertical space between related property members</value>
</data>
<data name="DeclarationType_Document" xml:space="preserve">
<value>document</value>
</data>
</root>
35 changes: 18 additions & 17 deletions Rubberduck.VBEEditor/ComManagement/TypeLibs/TypeLibVBEExtensions.cs
Expand Up @@ -89,23 +89,24 @@ public bool CompileProject()
{
try
{
// Prevent a potential access violation by first calling the Placeholder3().
// Under certain conditions where the VBA project is fully compiled, clicking parse
// as soon as Rubberduck has loaded into VBIDE can cause an access violation when
// accessing CompileProject(). We've tried using ComMessagePumper and
// UiDispatcher.FlushMessageQueue but neither helped in preventing the
// access violation. We at least know that Placeholder3() does not save the unsaved
// change so hopefully there should be no permanent side effects from invoking the
// Placeholder3().
try
{
_target_IVBEProject.Placeholder3();
}
catch(Exception ex)
{
Logger.Info(ex, $"Cannot compile the VBA project '{_name}' because there may be a potential access violation.");
return false;
}
// FIXME: Prevent an access violation when calling CompileProject(). A easy way to reproduce
// this AV is to parse an Access project, then do a Compact & Repair, then try to shut down
// Access. There was an attempt to avoid the AV by calling PlaceHolder3 which did seem to prevent
// the AV but somehow alters the VBA project in such way that _sometimes_ the user is shown a message
// that the project has changed and whether the user wants to proceeds. That is a slightly worse fix
// than the AV prevention, so we had to remove the fix. Reference:
// https://github.com/rubberduck-vba/Rubberduck/issues/5722
// https://github.com/rubberduck-vba/Rubberduck/pull/5675

//try
//{
// _target_IVBEProject.Placeholder3();
//}
//catch(Exception ex)
//{
// Logger.Info(ex, $"Cannot compile the VBA project '{_name}' because there may be a potential access violation.");
// return false;
//}

_target_IVBEProject.CompileProject();
return true;
Expand Down
Expand Up @@ -527,7 +527,7 @@ public void Identify_NamedParameter_Parameter_FromExcel()
.AddProjectToVbeBuilder()
.Build();

var (expected, actual) = DeclarationsFromParse(vbe.Object, DeclarationType.Parameter, "Link", "EXCEL.EXE;Excel.Worksheet.Paste");
var (expected, actual) = DeclarationsFromParse(vbe.Object, DeclarationType.Parameter, "Link", "EXCEL.EXE;Excel._Worksheet.Paste");

Assert.AreEqual(expected, actual);
}
Expand Down

0 comments on commit 6842721

Please sign in to comment.