Skip to content

Commit

Permalink
Resolve merge conflict
Browse files Browse the repository at this point in the history
  • Loading branch information
IvenBach committed Sep 20, 2018
2 parents 770bd4e + 6d4087b commit 3b94644
Show file tree
Hide file tree
Showing 342 changed files with 7,593 additions and 4,505 deletions.
Expand Up @@ -5,9 +5,8 @@
using Rubberduck.Parsing.Inspections.Abstract;
using Rubberduck.Resources.Inspections;
using Rubberduck.Parsing.Symbols;
using Rubberduck.UI;
using Rubberduck.UI.Controls;
using Rubberduck.VBEditor;
using Rubberduck.Interaction.Navigation;

namespace Rubberduck.Inspections.Abstract
{
Expand Down
@@ -0,0 +1,43 @@
using System.Collections.Generic;
using System.Linq;
using Rubberduck.Inspections.Abstract;
using Rubberduck.Inspections.Results;
using Rubberduck.Parsing.Inspections.Abstract;
using Rubberduck.Parsing.VBA;
using Rubberduck.Resources.Inspections;

namespace Rubberduck.Inspections.Concrete
{
public sealed class DuplicatedAnnotationInspection : InspectionBase
{
public DuplicatedAnnotationInspection(RubberduckParserState state) : base(state)
{
}

protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
{
var issues = new List<DeclarationInspectionResult>();

foreach (var declaration in State.AllUserDeclarations)
{
var duplicateAnnotations = declaration.Annotations
.GroupBy(annotation => annotation.AnnotationType)
.Where(group => !group.First().AllowMultiple && group.Count() > 1);

issues.AddRange(duplicateAnnotations.Select(duplicate =>
{
var result = new DeclarationInspectionResult(
this,
string.Format(InspectionResults.DuplicatedAnnotationInspection, duplicate.Key.ToString()),
declaration);
result.Properties.AnnotationType = duplicate.Key;
return result;
}));
}

return issues;
}
}
}
@@ -1,7 +1,6 @@
using System;
using System.Collections.Generic;
using System.Linq;
using Rubberduck.Common;
using Rubberduck.Inspections.Abstract;
using Rubberduck.Inspections.Results;
using Rubberduck.Parsing;
Expand All @@ -25,8 +24,8 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
{
// Note: This inspection does not find dictionary calls (e.g. foo!bar) since we do not know what the
// default member is of a class.
var interfaceMembers = UserDeclarations.FindInterfaceMembers().ToList();
var interfaceImplementationMembers = UserDeclarations.FindInterfaceImplementationMembers();
var interfaceMembers = State.DeclarationFinder.FindAllInterfaceMembers().ToList();
var interfaceImplementationMembers = State.DeclarationFinder.FindAllInterfaceImplementingMembers();
var functions = State.DeclarationFinder
.UserDeclarations(DeclarationType.Function)
.Where(item => !IsIgnoringInspectionResultFor(item, AnnotationName))
Expand All @@ -41,7 +40,7 @@ private IEnumerable<IInspectionResult> GetInterfaceMemberIssues(IEnumerable<Decl
{
return from interfaceMember in interfaceMembers
let implementationMembers =
UserDeclarations.FindInterfaceImplementationMembers(interfaceMember.IdentifierName).ToList()
State.DeclarationFinder.FindInterfaceImplementationMembers(interfaceMember).ToList()
where interfaceMember.DeclarationType == DeclarationType.Function &&
!IsReturnValueUsed(interfaceMember) &&
implementationMembers.All(member => !IsReturnValueUsed(member))
Expand Down
Expand Up @@ -35,11 +35,6 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()

public class IllegalAttributeAnnotationsListener : VBAParserBaseListener, IInspectionListener
{
private static readonly AnnotationType[] AnnotationTypes = Enum.GetValues(typeof(AnnotationType)).Cast<AnnotationType>().ToArray();

private IDictionary<Tuple<QualifiedModuleName, AnnotationType>, int> _annotationCounts =
new Dictionary<Tuple<QualifiedModuleName, AnnotationType>, int>();

private readonly RubberduckParserState _state;

private Lazy<Declaration> _module;
Expand All @@ -55,32 +50,19 @@ public IllegalAttributeAnnotationsListener(RubberduckParserState state)

public IReadOnlyList<QualifiedContext<ParserRuleContext>> Contexts => _contexts;

public QualifiedModuleName CurrentModuleName
{
get => _currentModuleName;
set
{
_currentModuleName = value;
foreach (var type in AnnotationTypes)
{
_annotationCounts.Add(Tuple.Create(value, type), 0);
}
}
}
public QualifiedModuleName CurrentModuleName { get; set; }

private bool _isFirstMemberProcessed;

public void ClearContexts()
{
_annotationCounts = new Dictionary<Tuple<QualifiedModuleName, AnnotationType>, int>();
_contexts.Clear();
_isFirstMemberProcessed = false;
}

#region scoping
private Declaration _currentScopeDeclaration;
private bool _hasMembers;
private QualifiedModuleName _currentModuleName;

private void SetCurrentScope(string memberName = null)
{
Expand Down Expand Up @@ -168,8 +150,6 @@ public override void ExitAnnotation(VBAParser.AnnotationContext context)
{
var name = Identifier.GetName(context.annotationName().unrestrictedIdentifier());
var annotationType = (AnnotationType) Enum.Parse(typeof (AnnotationType), name, true);
var key = Tuple.Create(_currentModuleName, annotationType);
_annotationCounts[key]++;

var moduleHasMembers = _members.Value.Any();

Expand All @@ -183,9 +163,7 @@ public override void ExitAnnotation(VBAParser.AnnotationContext context)
&& (_currentScopeDeclaration?.DeclarationType.HasFlag(DeclarationType.Member) ?? false);

var isIllegal = !(isMemberAnnotation && moduleHasMembers && !_isFirstMemberProcessed) &&
(isModuleAnnotation && _annotationCounts[key] > 1
|| isMemberAnnotatedForModuleAnnotation
|| isModuleAnnotatedForMemberAnnotation);
(isMemberAnnotatedForModuleAnnotation || isModuleAnnotatedForMemberAnnotation);

if (isIllegal)
{
Expand Down
@@ -1,7 +1,6 @@
using System.Collections.Generic;
using System.Linq;
using Antlr4.Runtime;
using Rubberduck.Common;
using Rubberduck.Inspections.Abstract;
using Rubberduck.Inspections.Results;
using Rubberduck.Parsing;
Expand All @@ -26,7 +25,7 @@ public ImplicitByRefModifierInspection(RubberduckParserState state)
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
{
var builtInEventHandlerContexts = State.DeclarationFinder.FindEventHandlers().Select(handler => handler.Context).ToHashSet();
var interfaceImplementationMemberContexts = UserDeclarations.FindInterfaceImplementationMembers().Select(member => member.Context).ToHashSet();
var interfaceImplementationMemberContexts = State.DeclarationFinder.FindAllInterfaceImplementingMembers().Select(member => member.Context).ToHashSet();

var issues = Listener.Contexts.Where(context =>
!IsIgnoringInspectionResultFor(context.ModuleName, context.Context.Start.Line) &&
Expand Down
@@ -1,7 +1,6 @@
using System.Collections.Generic;
using System.Globalization;
using System.Linq;
using Rubberduck.Common;
using Rubberduck.Inspections.Abstract;
using Rubberduck.Inspections.Results;
using Rubberduck.Parsing.Grammar;
Expand All @@ -21,7 +20,7 @@ public IntegerDataTypeInspection(RubberduckParserState state) : base(state)

protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
{
var interfaceImplementationMembers = UserDeclarations.FindInterfaceImplementationMembers().ToHashSet();
var interfaceImplementationMembers = State.DeclarationFinder.FindAllInterfaceImplementingMembers().ToHashSet();

var excludeParameterMembers = State.DeclarationFinder.FindEventHandlers().ToHashSet();
excludeParameterMembers.UnionWith(interfaceImplementationMembers);
Expand Down
@@ -1,6 +1,5 @@
using System.Collections.Generic;
using System.Linq;
using Rubberduck.Common;
using Rubberduck.Inspections.Abstract;
using Rubberduck.Inspections.Results;
using Rubberduck.Parsing.Grammar;
Expand All @@ -26,7 +25,7 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
{
var declarations = UserDeclarations.ToList();

var interfaceMembers = declarations.FindInterfaceMembers();
var interfaceMembers = State.DeclarationFinder.FindAllInterfaceMembers();

var functions = declarations
.Where(declaration => ReturningMemberTypes.Contains(declaration.DeclarationType)
Expand Down
Expand Up @@ -6,14 +6,13 @@
using Rubberduck.Resources.Inspections;
using Rubberduck.Parsing.Symbols;
using Rubberduck.Parsing.VBA;
using Rubberduck.VBEditor.SafeComWrappers;

namespace Rubberduck.Inspections.Concrete
{
public sealed class ObjectVariableNotSetInspection : InspectionBase
{
public ObjectVariableNotSetInspection(RubberduckParserState state)
: base(state) { }
: base(state) { }

protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
{
Expand All @@ -36,17 +35,11 @@ private IEnumerable<IdentifierReference> InterestingReferences()
continue;
}

foreach (var reference in moduleReferences.Value)
{
if (!IsIgnoringInspectionResultFor(reference, AnnotationName)
&& VariableRequiresSetAssignmentEvaluator.NeedsSetKeywordAdded(reference, State))
{
result.Add(reference);
}
}
result.AddRange(moduleReferences.Value.Where(reference => !reference.IsSetAssignment
&& VariableRequiresSetAssignmentEvaluator.RequiresSetAssignment(reference, State)));
}

return result;
return result.Where(reference => !IsIgnoringInspectionResultFor(reference, AnnotationName));
}
}
}
Expand Up @@ -25,9 +25,11 @@ public OptionExplicitInspection(RubberduckParserState state)

protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
{
return Listener.Contexts.Select(context => new QualifiedContextInspectionResult(this,
string.Format(InspectionResults.OptionExplicitInspection, context.ModuleName.ComponentName),
context));
return Listener.Contexts
.Where(context => !IsIgnoringInspectionResultFor(context.ModuleName, context.Context.Start.Line))
.Select(context => new QualifiedContextInspectionResult(this,
string.Format(InspectionResults.OptionExplicitInspection, context.ModuleName.ComponentName),
context));
}

public class MissingOptionExplicitListener : VBAParserBaseListener, IInspectionListener
Expand Down
Expand Up @@ -22,8 +22,8 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
var declarations = UserDeclarations.ToArray();
var issues = new List<IInspectionResult>();

var interfaceDeclarationMembers = declarations.FindInterfaceMembers().ToArray();
var interfaceScopes = declarations.FindInterfaceImplementationMembers().Concat(interfaceDeclarationMembers).Select(s => s.Scope).ToArray();
var interfaceDeclarationMembers = State.DeclarationFinder.FindAllInterfaceMembers().ToArray();
var interfaceScopes = State.DeclarationFinder.FindAllInterfaceImplementingMembers().Concat(interfaceDeclarationMembers).Select(s => s.Scope).ToArray();

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

Expand Down Expand Up @@ -80,7 +80,7 @@ private IEnumerable<IInspectionResult> GetResults(Declaration[] declarations, De

var members = declarationMembers.Any(a => a.DeclarationType == DeclarationType.Event)
? declarations.FindHandlersForEvent(declaration).Select(s => s.Item2).ToList()
: declarations.FindInterfaceImplementationMembers(declaration).ToList();
: State.DeclarationFinder.FindInterfaceImplementationMembers(declaration).Cast<Declaration>().ToList();

foreach (var member in members)
{
Expand Down
@@ -1,7 +1,6 @@
using System.Collections.Generic;
using System.Linq;
using Antlr4.Runtime;
using Rubberduck.Common;
using Rubberduck.Inspections.Abstract;
using Rubberduck.Inspections.Results;
using Rubberduck.Parsing;
Expand All @@ -26,7 +25,7 @@ public RedundantByRefModifierInspection(RubberduckParserState state)
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
{
var builtInEventHandlerContexts = State.DeclarationFinder.FindEventHandlers().Select(handler => handler.Context).ToHashSet();
var interfaceImplementationMemberContexts = UserDeclarations.FindInterfaceImplementationMembers().Select(member => member.Context).ToHashSet();
var interfaceImplementationMemberContexts = State.DeclarationFinder.FindAllInterfaceImplementingMembers().Select(member => member.Context).ToHashSet();

var issues = Listener.Contexts.Where(context =>
!IsIgnoringInspectionResultFor(context.ModuleName, context.Context.Start.Line) &&
Expand Down

0 comments on commit 3b94644

Please sign in to comment.