Skip to content

Commit

Permalink
Merge pull request #4752 from rubberduck-vba/next
Browse files Browse the repository at this point in the history
Release 2.4.0
  • Loading branch information
retailcoder authored Jan 28, 2019
2 parents 7e17257 + 6ce3d6d commit 5d0eeb4
Show file tree
Hide file tree
Showing 362 changed files with 27,806 additions and 7,327 deletions.
39 changes: 39 additions & 0 deletions .github/ISSUE_TEMPLATE/bug_report.md
Original file line number Diff line number Diff line change
@@ -0,0 +1,39 @@
---
name: Bug report
about: Rubberduck does not work as expected
title: ''
labels: bug
assignees: ''

---
**Rubberduck version information**
The info below can be copy-paste-completed from the first lines of Rubberduck's Log or the About box:

Rubberduck version [...]
Operating System: [...]
Host Product: [...]
Host Version: [...]
Host Executable: [...]


**Description**
A clear and concise description of what the bug is.

**To Reproduce**
Steps to reproduce the behavior:
1. Go to '...'
2. Click on '....'
3. Scroll down to '....'
4. See error

**Expected behavior**
A clear and concise description of what you expected to happen.

**Screenshots**
If applicable, add screenshots to help explain your problem.

**Logfile**
Rubberduck generates extensive logging in TRACE-Level. If no log was created at `%APP_DATA%\Rubberduck\Logs`, check your settings. Include this Log for bugreports about the behavior of Rubbberduck

**Additional context**
Add any other context about the problem here.
2 changes: 2 additions & 0 deletions README.md
Original file line number Diff line number Diff line change
Expand Up @@ -17,6 +17,8 @@ If you like this project and would like to thank its contributors, you are welco
[masterBuildStatus]:https://ci.appveyor.com/api/projects/status/we3pdnkeebo4nlck/branch/master?svg=true
[![Average time to resolve an issue](http://isitmaintained.com/badge/resolution/Rubberduck-vba/rubberduck.svg)](http://isitmaintained.com/project/Rubberduck-vba/rubberduck "Average time to resolve an issue")
[![Percentage of issues still open](http://isitmaintained.com/badge/open/Rubberduck-vba/rubberduck.svg)](http://isitmaintained.com/project/Rubberduck-vba/rubberduck "Percentage of issues still open")
[![Chat on stackexchange](https://img.shields.io/badge/chat-on%20stackexchange-blue.svg)](https://chat.stackexchange.com/rooms/14929/vba-rubberducking)
[![License](https://img.shields.io/github/license/rubberduck-vba/Rubberduck.svg)](https://github.com/rubberduck-vba/Rubberduck/blob/next/LICENSE)

> **[rubberduckvba.com](http://rubberduckvba.com)** [Wiki](https://github.com/rubberduck-vba/Rubberduck/wiki) [Rubberduck News](https://rubberduckvba.wordpress.com/)
> [email protected]
Expand Down
1 change: 0 additions & 1 deletion Rubberduck.CodeAnalysis/CodePathAnalysis/Walker.cs
Original file line number Diff line number Diff line change
Expand Up @@ -5,7 +5,6 @@
using System.Collections.Generic;
using System.Collections.Immutable;
using System.Linq;
using Antlr4.Runtime;

namespace Rubberduck.Inspections.CodePathAnalysis
{
Expand Down
38 changes: 20 additions & 18 deletions Rubberduck.CodeAnalysis/Inspections/Abstract/InspectionBase.cs
Original file line number Diff line number Diff line change
Expand Up @@ -86,28 +86,22 @@ protected virtual IEnumerable<Declaration> BuiltInDeclarations

protected bool IsIgnoringInspectionResultFor(QualifiedModuleName module, int line)
{
var annotations = State.GetModuleAnnotations(module).ToList();

if (State.GetModuleAnnotations(module) == null)
{
return false;
}

// VBE 1-based indexing
for (var i = line; i >= 1; i--)
var lineScopedAnnotations = State.DeclarationFinder.FindAnnotations(module, line);
foreach (var ignoreAnnotation in lineScopedAnnotations.OfType<IgnoreAnnotation>())
{
var annotation = annotations.SingleOrDefault(a => a.QualifiedSelection.Selection.StartLine == i);
var ignoreAnnotation = annotation as IgnoreAnnotation;
var ignoreModuleAnnotation = annotation as IgnoreModuleAnnotation;

if (ignoreAnnotation?.InspectionNames.Contains(AnnotationName) == true)
if (ignoreAnnotation.InspectionNames.Contains(AnnotationName))
{
return true;
}
}

var moduleDeclaration = State.DeclarationFinder.Members(module)
.First(decl => decl.DeclarationType.HasFlag(DeclarationType.Module));

if (ignoreModuleAnnotation != null
&& (ignoreModuleAnnotation.InspectionNames.Contains(AnnotationName)
|| !ignoreModuleAnnotation.InspectionNames.Any()))
foreach (var ignoreModuleAnnotation in moduleDeclaration.Annotations.OfType<IgnoreModuleAnnotation>())
{
if (ignoreModuleAnnotation.InspectionNames.Contains(AnnotationName)
|| !ignoreModuleAnnotation.InspectionNames.Any())
{
return true;
}
Expand All @@ -119,7 +113,10 @@ protected bool IsIgnoringInspectionResultFor(QualifiedModuleName module, int lin
protected bool IsIgnoringInspectionResultFor(Declaration declaration, string inspectionName)
{
var module = Declaration.GetModuleParent(declaration);
if (module == null) { return false; }
if (module == null)
{
return false;
}

var isIgnoredAtModuleLevel = module.Annotations
.Any(annotation => annotation.AnnotationType == AnnotationType.IgnoreModule
Expand Down Expand Up @@ -169,5 +166,10 @@ public IEnumerable<IInspectionResult> GetInspectionResults(CancellationToken tok
_logger.Trace("Intercepted invocation of '{0}.{1}' ran for {2}ms", GetType().Name, nameof(DoGetInspectionResults), _stopwatch.ElapsedMilliseconds);
return result;
}

public virtual bool ChangesInvalidateResult(IInspectionResult result, ICollection<QualifiedModuleName> modifiedModules)
{
return true;
}
}
}
Original file line number Diff line number Diff line change
@@ -1,4 +1,5 @@
using System.IO;
using System.Collections.Generic;
using System.IO;
using Antlr4.Runtime;
using Rubberduck.Common;
using Rubberduck.Parsing.Inspections;
Expand Down Expand Up @@ -39,6 +40,12 @@ protected InspectionResultBase(IInspection inspection,
public Declaration Target { get; }
public dynamic Properties { get; }

public virtual bool ChangesInvalidateResult(ICollection<QualifiedModuleName> modifiedModules)
{
return modifiedModules.Contains(QualifiedName)
|| Inspection.ChangesInvalidateResult(this, modifiedModules);
}

/// <summary>
/// Gets the information needed to select the target instruction in the VBE.
/// </summary>
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -6,6 +6,7 @@
using Rubberduck.Parsing.Symbols;
using Rubberduck.Inspections.CodePathAnalysis.Extensions;
using System.Linq;
using Rubberduck.Inspections.CodePathAnalysis.Nodes;
using Rubberduck.Inspections.Results;
using Rubberduck.Parsing;
using Rubberduck.Parsing.Grammar;
Expand All @@ -30,7 +31,15 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
var nodes = new List<IdentifierReference>();
foreach (var variable in variables)
{
var tree = _walker.GenerateTree(variable.ParentScopeDeclaration.Context, variable);
var parentScopeDeclaration = variable.ParentScopeDeclaration;

if (parentScopeDeclaration.DeclarationType.HasFlag(DeclarationType.Module))
{
continue;
}

var tree = _walker.GenerateTree(parentScopeDeclaration.Context, variable);


nodes.AddRange(tree.GetIdentifierReferences());
}
Expand Down
Original file line number Diff line number Diff line change
@@ -0,0 +1,73 @@
using System.Collections.Generic;
using System.Linq;
using Rubberduck.Inspections.Abstract;
using Rubberduck.Inspections.Results;
using Rubberduck.Parsing;
using Rubberduck.Parsing.Annotations;
using Rubberduck.Parsing.Inspections;
using Rubberduck.Parsing.Inspections.Abstract;
using Rubberduck.Parsing.Symbols;
using Rubberduck.Parsing.VBA;
using Rubberduck.Resources.Inspections;
using Rubberduck.VBEditor.SafeComWrappers;

namespace Rubberduck.Inspections.Concrete
{
[CannotAnnotate]
public sealed class AttributeValueOutOfSyncInspection : InspectionBase
{
public AttributeValueOutOfSyncInspection(RubberduckParserState state)
:base(state)
{
}

protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
{
var declarationsWithAttributeAnnotations = State.DeclarationFinder.AllUserDeclarations
.Where(declaration => declaration.Annotations.Any(annotation => annotation.AnnotationType.HasFlag(AnnotationType.Attribute)));
var results = new List<DeclarationInspectionResult>();
foreach (var declaration in declarationsWithAttributeAnnotations.Where(decl => decl.QualifiedModuleName.ComponentType != ComponentType.Document))
{
foreach (var annotation in declaration.Annotations.OfType<IAttributeAnnotation>())
{
if (HasDifferingAttributeValues(declaration, annotation, out var attributeValues))
{
var description = string.Format(InspectionResults.AttributeValueOutOfSyncInspection,
annotation.Attribute,
string.Join(", ", attributeValues),
annotation.AnnotationType);

var result = new DeclarationInspectionResult(this, description, declaration,
new QualifiedContext(declaration.QualifiedModuleName, annotation.Context));
result.Properties.Annotation = annotation;
result.Properties.AttributeName = annotation.Attribute;
result.Properties.AttributeValues = attributeValues;

results.Add(result);
}
}
}

return results;
}

private static bool HasDifferingAttributeValues(Declaration declaration, IAttributeAnnotation annotation, out IReadOnlyList<string> attributeValues)
{
var attributeNodes = declaration.DeclarationType.HasFlag(DeclarationType.Module)
? declaration.Attributes.AttributeNodesFor(annotation)
: declaration.Attributes.AttributeNodesFor(annotation, declaration.IdentifierName);

foreach (var attributeNode in attributeNodes)
{
var values = attributeNode.Values;
if (!annotation.AttributeValues.SequenceEqual(values))
{
attributeValues = values;
return true;
}
}
attributeValues = new List<string>();
return false;
}
}
}
Original file line number Diff line number Diff line change
Expand Up @@ -8,7 +8,9 @@
using Rubberduck.Parsing.Symbols;
using Rubberduck.Resources.Inspections;
using Rubberduck.Parsing.VBA;
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Parsing.VBA.Extensions;
using Rubberduck.VBEditor.SafeComWrappers;

namespace Rubberduck.Inspections.Concrete
{
Expand All @@ -24,8 +26,12 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
var identifierReferences = State.DeclarationFinder.AllIdentifierReferences().ToList();
var annotations = State.AllAnnotations;

var illegalAnnotations = UnboundAnnotations(annotations, userDeclarations, identifierReferences)
.Where(annotation => !annotation.AnnotationType.HasFlag(AnnotationType.GeneralAnnotation));
var unboundAnnotations = UnboundAnnotations(annotations, userDeclarations, identifierReferences)
.Where(annotation => !annotation.AnnotationType.HasFlag(AnnotationType.GeneralAnnotation)
|| annotation.AnnotatedLine == null);
var attributeAnnotationsInDocuments = AttributeAnnotationsInDocuments(userDeclarations);

var illegalAnnotations = unboundAnnotations.Concat(attributeAnnotationsInDocuments).ToHashSet();

return illegalAnnotations.Select(annotation =>
new QualifiedContextInspectionResult(
Expand All @@ -34,7 +40,7 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
new QualifiedContext(annotation.QualifiedSelection.QualifiedName, annotation.Context)));
}

private static ICollection<IAnnotation> UnboundAnnotations(IEnumerable<IAnnotation> annotations, IEnumerable<Declaration> userDeclarations, IEnumerable<IdentifierReference> identifierReferences)
private static IEnumerable<IAnnotation> UnboundAnnotations(IEnumerable<IAnnotation> annotations, IEnumerable<Declaration> userDeclarations, IEnumerable<IdentifierReference> identifierReferences)
{
var boundAnnotationsSelections = userDeclarations
.SelectMany(declaration => declaration.Annotations)
Expand All @@ -44,5 +50,12 @@ private static ICollection<IAnnotation> UnboundAnnotations(IEnumerable<IAnnotati

return annotations.Where(annotation => !boundAnnotationsSelections.Contains(annotation.QualifiedSelection)).ToList();
}

private static IEnumerable<IAnnotation> AttributeAnnotationsInDocuments(IEnumerable<Declaration> userDeclarations)
{
var declarationsInDocuments = userDeclarations
.Where(declaration => declaration.QualifiedModuleName.ComponentType == ComponentType.Document);
return declarationsInDocuments.SelectMany(doc => doc.Annotations).OfType<IAttributeAnnotation>();
}
}
}
Loading

0 comments on commit 5d0eeb4

Please sign in to comment.