Skip to content

Commit

Permalink
Merge branch 'next' into CacheUserComProjects
Browse files Browse the repository at this point in the history
  • Loading branch information
MDoerner committed Mar 31, 2019
2 parents e5029be + 2925035 commit 7687755
Show file tree
Hide file tree
Showing 673 changed files with 40,777 additions and 16,832 deletions.
39 changes: 39 additions & 0 deletions .github/ISSUE_TEMPLATE/bug_report.md
@@ -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 `%APPDATA%\Rubberduck\Logs`, check your settings. Include this log for bug reports about the behavior of Rubberduck.

**Additional context**
Add any other context about the problem here.
3 changes: 3 additions & 0 deletions .gitignore
Expand Up @@ -183,3 +183,6 @@ CodeGraphData/
/Rubberduck.Deployment/Properties/launchSettings.json
/Rubberduck.Deployment/Rubberduck.API.idl
/Rubberduck.Deployment/Rubberduck.idl

#Gradle
/.gradle/
4 changes: 3 additions & 1 deletion README.md
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/)
> devs@rubberduckvba.com
Expand All @@ -36,7 +38,7 @@ If you like this project and would like to thank its contributors, you are welco

Rubberduck is a COM add-in for the VBA IDE (VBE).

Copyright (C) 2014-2018 Rubberduck project contributors
Copyright (C) 2014-2019 Rubberduck project contributors

This program is free software: you can redistribute it and/or modify
it under the terms of the GNU General Public License as published by
Expand Down
1 change: 0 additions & 1 deletion Rubberduck.CodeAnalysis/CodePathAnalysis/Walker.cs
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
Expand Up @@ -166,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;
}
}
}
@@ -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 @@ public abstract class InspectionResultBase : IInspectionResult, INavigateSource,
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
Expand Up @@ -7,7 +7,6 @@
using Rubberduck.Inspections.CodePathAnalysis.Extensions;
using System.Linq;
using Rubberduck.Inspections.Results;
using Rubberduck.Parsing;
using Rubberduck.Parsing.Grammar;

namespace Rubberduck.Inspections.Concrete
Expand All @@ -30,9 +29,20 @@ 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;

nodes.AddRange(tree.GetIdentifierReferences());
if (parentScopeDeclaration.DeclarationType.HasFlag(DeclarationType.Module))
{
continue;
}

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

var references = tree.GetIdentifierReferences();
// ignore set-assignments to 'Nothing'
nodes.AddRange(references.Where(r =>
!(r.Context.Parent is VBAParser.SetStmtContext setStmtContext &&
setStmtContext.expression().GetText().Equals(Tokens.Nothing))));
}

return nodes
Expand Down
Expand Up @@ -75,13 +75,14 @@ private bool IsRecursive(Declaration function)

private bool IsReturnValueUsed(Declaration function)
{
// TODO: This is O(MG) at work here. Need to refactor the whole shebang.
return (from usage in function.References
where !IsAddressOfCall(usage)
where !IsTypeOfExpression(usage)
where !IsCallStmt(usage)
where !IsLet(usage)
where !IsSet(usage)
select usage).Any(usage => !IsReturnStatement(function, usage));
where !IsLet(usage)
where !IsSet(usage)
where !IsCallStmt(usage)
where !IsTypeOfExpression(usage)
where !IsAddressOfCall(usage)
select usage).Any(usage => !IsReturnStatement(function, usage));
}

private bool IsAddressOfCall(IdentifierReference usage)
Expand All @@ -93,7 +94,7 @@ private bool IsTypeOfExpression(IdentifierReference usage)
{
return usage.Context.IsDescendentOf<VBAParser.TypeofexprContext>();
}

private bool IsReturnStatement(Declaration function, IdentifierReference assignment)
{
return assignment.ParentScoping.Equals(function) && assignment.Declaration.Equals(function);
Expand All @@ -111,6 +112,19 @@ private bool IsCallStmt(IdentifierReference usage)
{
return false;
}

var indexExpr = usage.Context.GetAncestor<VBAParser.IndexExprContext>();
if (indexExpr != null)
{
var memberAccessStmt = usage.Context.GetAncestor<VBAParser.MemberAccessExprContext>();
if (memberAccessStmt != null &&
callStmt.SourceInterval.ProperlyContains(memberAccessStmt.SourceInterval) &&
memberAccessStmt.SourceInterval.ProperlyContains(indexExpr.SourceInterval))
{
return false;
}
}

var argumentList = CallStatement.GetArgumentList(callStmt);
if (argumentList == null)
{
Expand Down
Expand Up @@ -85,6 +85,7 @@ public sealed class HungarianNotationInspection : InspectionBase
DeclarationType.Constant,
DeclarationType.Control,
DeclarationType.ClassModule,
DeclarationType.Document,
DeclarationType.Member,
DeclarationType.Module,
DeclarationType.ProceduralModule,
Expand Down
Expand Up @@ -77,10 +77,7 @@ private static bool MissesCorrespondingMemberAnnotation(Declaration declaration,

private static string AttributeBaseName(Declaration declaration, AttributeNode attribute)
{
var attributeName = attribute.Name;
return attributeName.StartsWith($"{declaration.IdentifierName}.")
? attributeName.Substring(declaration.IdentifierName.Length + 1)
: attributeName;
return Attributes.AttributeBaseName(attribute.Name, declaration.IdentifierName);
}
}
}
Expand Up @@ -61,27 +61,7 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()

private static bool IsDefaultAttribute(Declaration declaration, AttributeNode attribute)
{
switch (attribute.Name)
{
case "VB_Name":
return true;
case "VB_GlobalNameSpace":
return declaration.DeclarationType.HasFlag(DeclarationType.ClassModule)
&& attribute.Values[0].Equals(Tokens.False);
case "VB_Exposed":
return declaration.DeclarationType.HasFlag(DeclarationType.ClassModule)
&& attribute.Values[0].Equals(Tokens.False);
case "VB_Creatable":
return declaration.DeclarationType.HasFlag(DeclarationType.ClassModule)
&& attribute.Values[0].Equals(Tokens.False);
case "VB_PredeclaredId":
return (declaration.QualifiedModuleName.ComponentType == ComponentType.ClassModule
&& attribute.Values[0].Equals(Tokens.False))
|| (declaration.QualifiedModuleName.ComponentType == ComponentType.UserForm
&& attribute.Values[0].Equals(Tokens.True));
default:
return false;
}
return Attributes.IsDefaultAttribute(declaration.QualifiedModuleName.ComponentType, attribute.Name, attribute.Values);
}

private static bool MissesCorrespondingModuleAnnotation(Declaration declaration, AttributeNode attribute)
Expand Down
Expand Up @@ -13,16 +13,17 @@ public sealed class ModuleWithoutFolderInspection : InspectionBase
{
public ModuleWithoutFolderInspection(RubberduckParserState state)
: base(state)
{
}
{}

protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
{
var modulesWithoutFolderAnnotation = State.DeclarationFinder.UserDeclarations(Parsing.Symbols.DeclarationType.Module)
.Where(w => w.Annotations.All(a => a.AnnotationType != AnnotationType.Folder))
.ToList();

return modulesWithoutFolderAnnotation.Select(declaration =>
return modulesWithoutFolderAnnotation
.Where(declaration => !IsIgnoringInspectionResultFor(declaration, AnnotationName))
.Select(declaration =>
new DeclarationInspectionResult(this, string.Format(InspectionResults.ModuleWithoutFolderInspection, declaration.IdentifierName), declaration));
}
}
Expand Down
Expand Up @@ -20,7 +20,7 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
.Where(declaration =>
{
if (declaration.IsWithEvents
|| !new[] {DeclarationType.ClassModule, DeclarationType.ProceduralModule}.Contains(declaration.ParentDeclaration.DeclarationType)
|| !new[] {DeclarationType.ClassModule, DeclarationType.Document, DeclarationType.ProceduralModule}.Contains(declaration.ParentDeclaration.DeclarationType)
|| IsIgnoringInspectionResultFor(declaration, AnnotationName))
{
return false;
Expand Down
Expand Up @@ -51,7 +51,7 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
private bool IsAssignedByRefArgument(Declaration enclosingProcedure, IdentifierReference reference)
{
var argExpression = reference.Context.GetAncestor<VBAParser.ArgumentExpressionContext>();
var parameter = State.DeclarationFinder.FindParameterFromArgument(argExpression, enclosingProcedure);
var parameter = State.DeclarationFinder.FindParameterOfNonDefaultMemberFromSimpleArgumentNotPassedByValExplicitly(argExpression, enclosingProcedure);

// note: not recursive, by design.
return parameter != null
Expand Down

0 comments on commit 7687755

Please sign in to comment.