Skip to content

Commit

Permalink
fixed bug with defaultMember logic
Browse files Browse the repository at this point in the history
  • Loading branch information
retailcoder committed Jan 22, 2018
1 parent 1a13a0d commit 97c224d
Show file tree
Hide file tree
Showing 4 changed files with 7 additions and 7 deletions.
Expand Up @@ -5,7 +5,6 @@
using System.Collections.Generic;
using System.Diagnostics;
using System.Linq;
using System.Windows.Forms;

namespace Rubberduck.Inspections
{
Expand Down
3 changes: 2 additions & 1 deletion Rubberduck.Parsing/Symbols/Declaration.cs
Expand Up @@ -342,7 +342,8 @@ private static string CorrectlyFormatedDescription(string literalDescription)
public virtual bool IsObject()
{
return AsTypeName == Tokens.Object
|| (AsTypeDeclaration?.DeclarationType.HasFlag(DeclarationType.ClassModule) ?? false);
|| (AsTypeDeclaration?.DeclarationType.HasFlag(DeclarationType.ClassModule) ?? false)
|| (!AsTypeIsBaseType && !IsArray && !DeclarationType.HasFlag(DeclarationType.UserDefinedType));
}

public void AddReference(
Expand Down
2 changes: 1 addition & 1 deletion Rubberduck.Parsing/Symbols/IdentifierReferenceResolver.cs
Expand Up @@ -194,7 +194,7 @@ private void ResolveLabel(ParserRuleContext context, string label)
{
var module = boundExpression.ReferencedDeclaration.AsTypeDeclaration;
var members = _declarationFinder.Members(module);
defaultMember = (IParameterizedDeclaration)members.SingleOrDefault(m => m is IParameterizedDeclaration && m.Attributes.HasDefaultMemberAttribute());
defaultMember = (IParameterizedDeclaration)members.FirstOrDefault(m => m is IParameterizedDeclaration && m.Attributes.HasDefaultMemberAttribute() && (isAssignmentTarget ? m.DeclarationType.HasFlag(DeclarationType.Procedure) : m.DeclarationType.HasFlag(DeclarationType.Function)));
}
_boundExpressionVisitor.AddIdentifierReferences(boundExpression, _qualifiedModuleName, _currentScope, _currentParent, isAssignmentTarget && (defaultMember == null || (!defaultMember.Parameters.Any() || defaultMember.Parameters.All(p => p.IsOptional)) || isSetAssignment), hasExplicitLetStatement);
}
Expand Down
Expand Up @@ -57,16 +57,16 @@ public void ObjectVariableNotSet_ForPropertyGetAssignment_ReturnsResults()
{
var expectedResultCount = 1;
var input = @"
Private example As MyObject
Private m_example As MyObject
Public Property Get Example() As MyObject
Example = example
Example = m_example
End Property
";
var expectedCode =
@"
Private example As MyObject
Private m_example As MyObject
Public Property Get Example() As MyObject
Set Example = example
Set Example = m_example
End Property
";

Expand Down

0 comments on commit 97c224d

Please sign in to comment.