Skip to content

Commit

Permalink
include whitespace in argument selection
Browse files Browse the repository at this point in the history
  • Loading branch information
retailcoder committed Apr 21, 2021
1 parent 743c3e6 commit ef55b69
Show file tree
Hide file tree
Showing 8 changed files with 81 additions and 33 deletions.
Expand Up @@ -71,7 +71,8 @@ private bool IsAssignedByRefArgument(Declaration enclosingProcedure, IdentifierR
return false;
}

var parameter = finder.FindParameterOfNonDefaultMemberFromSimpleArgumentNotPassedByValExplicitly(argExpression, enclosingProcedure);
var argument = argExpression.GetAncestor<VBAParser.ArgumentContext>();
var parameter = finder.FindParameterOfNonDefaultMemberFromSimpleArgumentNotPassedByValExplicitly(argument, enclosingProcedure);

// note: not recursive, by design.
return parameter != null
Expand Down
Expand Up @@ -142,7 +142,8 @@ private static bool IsPotentiallyAssignedByRefArgument(QualifiedModuleName modul
return false;
}

var parameter = finder.FindParameterOfNonDefaultMemberFromSimpleArgumentNotPassedByValExplicitly(argExpression, module);
var argument = argExpression.GetAncestor<VBAParser.ArgumentContext>();
var parameter = finder.FindParameterOfNonDefaultMemberFromSimpleArgumentNotPassedByValExplicitly(argument, module);

if (parameter == null)
{
Expand Down
Expand Up @@ -88,7 +88,8 @@ private static bool IsUsageAsAssignedToByRefArgument(IdentifierReference referen
return false;
}

var parameter = finder.FindParameterOfNonDefaultMemberFromSimpleArgumentNotPassedByValExplicitly(argExpression, reference.QualifiedModuleName);
var argument = argExpression.GetAncestor<VBAParser.ArgumentContext>();
var parameter = finder.FindParameterOfNonDefaultMemberFromSimpleArgumentNotPassedByValExplicitly(argument, reference.QualifiedModuleName);

if (parameter == null)
{
Expand Down
Expand Up @@ -155,7 +155,8 @@ private static bool IsAssignedByRefArgument(Declaration enclosingProcedure, Iden
return false;
}

var parameter = finder.FindParameterOfNonDefaultMemberFromSimpleArgumentNotPassedByValExplicitly(argExpression, enclosingProcedure);
var argument = argExpression.GetAncestor<VBAParser.ArgumentContext>();
var parameter = finder.FindParameterOfNonDefaultMemberFromSimpleArgumentNotPassedByValExplicitly(argument, enclosingProcedure);

// note: not recursive, by design.
return parameter != null
Expand Down
Expand Up @@ -69,7 +69,8 @@ private static bool IsAssignedByRefArgument(Declaration enclosingProcedure, Iden
return false;
}

var parameter = finder.FindParameterOfNonDefaultMemberFromSimpleArgumentNotPassedByValExplicitly(argExpression, enclosingProcedure);
var argument = argExpression.GetAncestor<VBAParser.ArgumentContext>();
var parameter = finder.FindParameterOfNonDefaultMemberFromSimpleArgumentNotPassedByValExplicitly(argument, enclosingProcedure);

// note: not recursive, by design.
return parameter != null
Expand Down
54 changes: 32 additions & 22 deletions Rubberduck.Parsing/VBA/DeclarationCaching/DeclarationFinder.cs
Expand Up @@ -602,31 +602,33 @@ public IEnumerable<Declaration> MatchName(string name)
: Enumerable.Empty<Declaration>();
}

public ParameterDeclaration FindParameterOfNonDefaultMemberFromSimpleArgumentNotPassedByValExplicitly(VBAParser.ArgumentExpressionContext argumentExpression, Declaration enclosingProcedure)
public ParameterDeclaration FindParameterOfNonDefaultMemberFromSimpleArgumentNotPassedByValExplicitly(VBAParser.ArgumentContext argument, Declaration enclosingProcedure)
{
return FindParameterOfNonDefaultMemberFromSimpleArgumentNotPassedByValExplicitly(argumentExpression, enclosingProcedure.QualifiedModuleName);
return FindParameterOfNonDefaultMemberFromSimpleArgumentNotPassedByValExplicitly(argument, enclosingProcedure.QualifiedModuleName);
}

public ParameterDeclaration FindParameterOfNonDefaultMemberFromSimpleArgumentNotPassedByValExplicitly(VBAParser.ArgumentExpressionContext argumentExpression, QualifiedModuleName module)
public ParameterDeclaration FindParameterOfNonDefaultMemberFromSimpleArgumentNotPassedByValExplicitly(VBAParser.ArgumentContext argument, QualifiedModuleName module)
{
//todo: Rename after making it work for more general cases.

if (argumentExpression == null
|| argumentExpression.GetDescendent<VBAParser.ParenthesizedExprContext>() != null
|| argumentExpression.BYVAL() != null)
var missingArgument = argument.missingArgument();
var argumentExpression = argument.GetDescendent<VBAParser.ArgumentExpressionContext>();
if ((missingArgument == null && argumentExpression == null)
|| argumentExpression?.GetDescendent<VBAParser.ParenthesizedExprContext>() != null
|| argumentExpression?.BYVAL() != null)
{
// not a simple argument, or argument is parenthesized and thus passed ByVal
return null;
}

var callingNonDefaultMember = CallingNonDefaultMember(argumentExpression, module);
var callingNonDefaultMember = CallingNonDefaultMember((ParserRuleContext)argumentExpression ?? missingArgument, module);
if (callingNonDefaultMember == null)
{
// Either we could not resolve the call or there is a default member call involved.
return null;
}

var parameters = Parameters(callingNonDefaultMember);
var hasNamedArgs = argumentExpression?.GetAncestor<VBAParser.ArgListContext>()?.TryGetChildContext<VBAParser.NamedArgumentContext>(out _) ?? false;

ParameterDeclaration parameter;
var namedArg = argumentExpression.GetAncestor<VBAParser.NamedArgumentContext>();
Expand All @@ -639,35 +641,44 @@ public ParameterDeclaration FindParameterOfNonDefaultMemberFromSimpleArgumentNot
else
{
// argument is positional: work out its index
var argumentList = argumentExpression.GetAncestor<VBAParser.ArgumentListContext>();
var arguments = argumentList.children.Where(t => (t is VBAParser.ArgumentContext)).ToArray();

var parameterIndex = arguments
.Select((arg, index) => (arg: arg as ParserRuleContext, index))
.SingleOrDefault(item => item.arg.ContainsTokenIndex(argumentExpression.Start.TokenIndex)).index;

var argumentList = ((ParserRuleContext)argumentExpression ?? missingArgument).GetAncestor<VBAParser.ArgumentListContext>();
var arguments = argumentList.children.Where(t => t is VBAParser.ArgumentContext).ToArray();
var selection = argumentExpression?.GetSelection() ?? missingArgument.GetSelection();

var indexedArgs = arguments.Select((arg, index) => (arg: arg as ParserRuleContext, index))
.Select(e => (arg: e.arg, e.index, selection:e.arg.GetSelection()))
.ToList();
var indexedArg = indexedArgs.SingleOrDefault(item => item.selection.Contains(selection));
if (indexedArg.arg == null)
{
return null;
}
parameter = parameters
.Select((param, index) => (param, index))
.SingleOrDefault(item => item.index == parameterIndex).param;
.Single(item => item.index == indexedArg.index).param;
}

return parameter;
}

public ModuleBodyElementDeclaration FindInvokedMemberFromArgumentExpressionContext(VBAParser.ArgumentExpressionContext argumentExpression, QualifiedModuleName module)
public ModuleBodyElementDeclaration FindInvokedMemberFromArgumentContext(VBAParser.ArgumentContext argument, QualifiedModuleName module)
{
return CallingNonDefaultMember(argumentExpression, module);
var expression = (ParserRuleContext)argument.GetDescendent<VBAParser.ArgumentExpressionContext>()
?? argument.GetDescendent<VBAParser.MissingArgumentContext>();
return expression != null
? CallingNonDefaultMember(expression, module)
: null;
}

private ModuleBodyElementDeclaration CallingNonDefaultMember(VBAParser.ArgumentExpressionContext argumentExpression, QualifiedModuleName module)
private ModuleBodyElementDeclaration CallingNonDefaultMember(ParserRuleContext argumentExpressionOrMissingArgument, QualifiedModuleName module)
{
//todo: Make this work for default member calls.

var argumentList = argumentExpression.GetAncestor<VBAParser.ArgumentListContext>();
var argumentList = argumentExpressionOrMissingArgument.GetAncestor<VBAParser.ArgumentListContext>();
var cannotHaveDefaultMemberCall = false;

ParserRuleContext callingExpression;
switch (argumentList.Parent)
switch (argumentList?.Parent)
{
case VBAParser.CallStmtContext callStmt:
cannotHaveDefaultMemberCall = true;
Expand All @@ -680,7 +691,6 @@ private ModuleBodyElementDeclaration CallingNonDefaultMember(VBAParser.ArgumentE
callingExpression = indexExpr.lExpression();
break;
default:
//This should never happen.
return null;
}

Expand Down
40 changes: 34 additions & 6 deletions Rubberduck.Parsing/VBA/SelectedDeclarationProvider.cs
Expand Up @@ -107,19 +107,47 @@ private static Declaration SelectedDeclarationViaArgument(QualifiedSelection qua
.Where(m => (m.DeclarationType.HasFlag(DeclarationType.Procedure) // includes PropertyLet and PropertySet and LibraryProcedure
|| m.DeclarationType.HasFlag(DeclarationType.Function)) // includes PropertyGet and LibraryFunction
&& !m.DeclarationType.HasFlag(DeclarationType.LibraryFunction)
&& !m.DeclarationType.HasFlag(DeclarationType.LibraryProcedure));
&& !m.DeclarationType.HasFlag(DeclarationType.LibraryProcedure));
var enclosingProcedure = members.SingleOrDefault(m => m.Context.GetSelection().Contains(qualifiedSelection.Selection));
if (enclosingProcedure == null)
{
return null;
}

var context = enclosingProcedure?.Context.GetDescendents<VBAParser.ArgumentExpressionContext>()
.FirstOrDefault(m => m.GetSelection().ContainsFirstCharacter(qualifiedSelection.Selection));
var allArguments = enclosingProcedure.Context.GetDescendents<VBAParser.ArgumentContext>();

var context = allArguments
.Where(arg => arg.missingArgument() == null)
.FirstOrDefault(m =>
{
var isOnWhitespace = false;
if (m.TryGetPrecedingContext<VBAParser.WhiteSpaceContext>(out var whitespace))
{
isOnWhitespace = whitespace.GetSelection().ContainsFirstCharacter(qualifiedSelection.Selection);
}
return isOnWhitespace || m.GetSelection().ContainsFirstCharacter(qualifiedSelection.Selection);
});

var skippedArg = allArguments
.Where(arg => arg.missingArgument() != null)
.FirstOrDefault(m =>
{
var isOnWhitespace = false;
if (m.TryGetPrecedingContext<VBAParser.WhiteSpaceContext>(out var whitespace))
{
isOnWhitespace = whitespace.GetSelection().ContainsFirstCharacter(qualifiedSelection.Selection);
}
return isOnWhitespace || m.GetSelection().ContainsFirstCharacter(qualifiedSelection.Selection);
});

context = context ?? skippedArg;
if (context != null)
{
return finder.FindParameterOfNonDefaultMemberFromSimpleArgumentNotPassedByValExplicitly(context, enclosingProcedure);
return (Declaration)finder.FindParameterOfNonDefaultMemberFromSimpleArgumentNotPassedByValExplicitly(context, enclosingProcedure)
?? finder.FindInvokedMemberFromArgumentContext(context, qualifiedSelection.QualifiedName); // fallback to the invoked procedure declaration
}

// fallback to the invoked procedure declaration
return finder.FindInvokedMemberFromArgumentExpressionContext(context, qualifiedSelection.QualifiedName);
return null;
}

private static Declaration SelectedDeclarationViaReference(QualifiedSelection qualifiedSelection, DeclarationFinder finder)
Expand Down
5 changes: 5 additions & 0 deletions Rubberduck.VBEEditor/Selection.cs
Expand Up @@ -46,6 +46,11 @@ public bool ContainsFirstCharacter(Selection selection)
return Contains(new Selection(selection.StartLine, selection.StartColumn, selection.StartLine, selection.StartColumn));
}

public Selection ExtendLeft(int positions = 1)
{
return new Selection(StartLine, Math.Max(StartColumn - positions, 1), EndLine, EndColumn);
}

public bool Contains(Selection selection)
{
// single line comparison
Expand Down

0 comments on commit ef55b69

Please sign in to comment.