Navigation Menu

Skip to content

Commit

Permalink
Merge branch 'rubberduck-vba/next' into ConflictDetectionSession
Browse files Browse the repository at this point in the history
  • Loading branch information
BZngr committed Aug 6, 2020
2 parents 8db77b7 + 9ed85e0 commit c525a8d
Show file tree
Hide file tree
Showing 216 changed files with 1,736 additions and 810 deletions.
1 change: 1 addition & 0 deletions .gitignore
Expand Up @@ -190,3 +190,4 @@ Rubberduck.CodeAnalysis.xml
#Gradle
/.gradle/
/Rubberduck.CodeAnalysis/Rubberduck.CodeAnalysis.xml
/Rubberduck.Parsing/Rubberduck.Parsing.xml
Expand Up @@ -8,7 +8,7 @@
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Resources.Inspections;

namespace Rubberduck.CodeAnalysis.Inspections.Concrete.Excel
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
/// <summary>
/// Warns about late-bound WorksheetFunction calls made against the extended interface of the Application object.
Expand Down
Expand Up @@ -5,7 +5,7 @@
using Rubberduck.Parsing.VBA;
using Rubberduck.Resources.Inspections;

namespace Rubberduck.CodeAnalysis.Inspections.Concrete.EmptyBlock
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
/// <summary>
/// Identifies empty 'Case' blocks that can be safely removed.
Expand Down
Expand Up @@ -5,7 +5,7 @@
using Rubberduck.Parsing.VBA;
using Rubberduck.Resources.Inspections;

namespace Rubberduck.CodeAnalysis.Inspections.Concrete.EmptyBlock
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
/// <summary>
/// Identifies empty 'Do...Loop While' blocks that can be safely removed.
Expand Down
Expand Up @@ -5,7 +5,7 @@
using Rubberduck.Parsing.VBA;
using Rubberduck.Resources.Inspections;

namespace Rubberduck.CodeAnalysis.Inspections.Concrete.EmptyBlock
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
/// <summary>
/// Identifies empty 'Else' blocks that can be safely removed.
Expand Down
Expand Up @@ -5,7 +5,7 @@
using Rubberduck.Parsing.VBA;
using Rubberduck.Resources.Inspections;

namespace Rubberduck.CodeAnalysis.Inspections.Concrete.EmptyBlock
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
/// <summary>
/// Identifies empty 'For Each...Next' blocks that can be safely removed.
Expand Down
Expand Up @@ -5,7 +5,7 @@
using Rubberduck.Parsing.VBA;
using Rubberduck.Resources.Inspections;

namespace Rubberduck.CodeAnalysis.Inspections.Concrete.EmptyBlock
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
/// <summary>
/// Identifies empty 'For...Next' blocks that can be safely removed.
Expand Down
Expand Up @@ -6,7 +6,7 @@
using Rubberduck.Parsing.VBA;
using Rubberduck.Resources.Inspections;

namespace Rubberduck.CodeAnalysis.Inspections.Concrete.EmptyBlock
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
/// <summary>
/// Identifies empty 'If' blocks.
Expand Down
Expand Up @@ -5,7 +5,7 @@
using Rubberduck.Parsing.VBA;
using Rubberduck.Resources.Inspections;

namespace Rubberduck.CodeAnalysis.Inspections.Concrete.EmptyBlock
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
/// <summary>
/// Identifies empty 'While...Wend' blocks that can be safely removed.
Expand Down
Expand Up @@ -7,7 +7,7 @@
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Resources.Inspections;

namespace Rubberduck.CodeAnalysis.Inspections.Concrete.Excel
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
/// <summary>Locates instances of member calls made against the result of a Range.Find/FindNext/FindPrevious method, without prior validation.</summary>
/// <reference name="Excel" />
Expand Down
Expand Up @@ -11,7 +11,7 @@
using Rubberduck.VBEditor;
using Rubberduck.VBEditor.SafeComWrappers;

namespace Rubberduck.CodeAnalysis.Inspections.Concrete.Excel
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
/// <summary>
/// Locates public User-Defined Function procedures accidentally named after a cell reference.
Expand Down
Expand Up @@ -2,7 +2,7 @@
using Rubberduck.CodeAnalysis.Inspections.Abstract;
using Rubberduck.CodeAnalysis.Inspections.Extensions;
using Rubberduck.Common;
using Rubberduck.Parsing.Annotations;
using Rubberduck.Parsing.Annotations.Concrete;
using Rubberduck.Parsing.Symbols;
using Rubberduck.Parsing.VBA;
using Rubberduck.Parsing.VBA.DeclarationCaching;
Expand Down
Expand Up @@ -7,7 +7,7 @@
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Resources.Inspections;

namespace Rubberduck.CodeAnalysis.Inspections.Concrete.Excel
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
/// <summary>
/// Locates unqualified Worksheet.Range/Cells/Columns/Rows member calls that implicitly refer to ActiveSheet.
Expand Down
Expand Up @@ -7,7 +7,7 @@
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.Resources.Inspections;

namespace Rubberduck.CodeAnalysis.Inspections.Concrete.Excel
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
/// <summary>
/// Locates unqualified Workbook.Worksheets/Sheets/Names member calls that implicitly refer to ActiveWorkbook.
Expand Down
@@ -1,6 +1,6 @@
using System.Linq;
using Rubberduck.CodeAnalysis.Inspections.Abstract;
using Rubberduck.Parsing.Annotations;
using Rubberduck.Parsing.Annotations.Concrete;
using Rubberduck.Parsing.Symbols;
using Rubberduck.Parsing.VBA;
using Rubberduck.Parsing.VBA.DeclarationCaching;
Expand Down
18 changes: 18 additions & 0 deletions Rubberduck.CodeAnalysis/Inspections/Concrete/README.md
@@ -0,0 +1,18 @@
## Rubberduck.CodeAnalysis.Inspections.Concrete

All concrete code inspection implementations (classes) must be in their own .cs source file **in a namespace that corresponds to its folder location**, under this namespace.

The xml-doc content in this namespace is automatically downloaded, processed, and ultimately served on the rubberduckvba.com website feature pages.

Each inspection can have as many examples using as many modules of as many types as necessary. The following string values are recognized as module types:

- "Standard Module"
- "Class Module"
- "Predeclared Class"
- "Interface Module"
- "UserForm Module"
- "Document Module"

The "edit this page" link on each page generated from xml-doc content in this namespace, links to `https://github.com/rubberduck-vba/Rubberduck/edit/next/{namespace}/{inspection-name}.cs`; it is imperative that the files' folder location corresponds to their namespace, lest we generate broken links on the website.

The content generated from xml-doc in this namespace (and any concrete inspections in a namespace under it) is accessible at `https://rubberduckvba.com/inspections/details/{inspection-name}`.
Expand Up @@ -12,7 +12,7 @@
using Rubberduck.VBEditor.SafeComWrappers;
using Rubberduck.VBEditor.SafeComWrappers.Abstract;

namespace Rubberduck.CodeAnalysis.Inspections.Concrete.Excel
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
/// <summary>
/// Locates ThisWorkbook.Worksheets and ThisWorkbook.Sheets calls that appear to be dereferencing a worksheet that is already accessible at compile-time with a global-scope identifier.
Expand Down
Expand Up @@ -13,7 +13,7 @@ namespace Rubberduck.CodeAnalysis.Inspections.Concrete.ThunderCode
/// <why>
/// This inpection is flagging code we dubbed "ThunderCode",
/// code our friend Andrew Jackson would have written to confuse Rubberduck's parser and/or resolver.
/// 'On Error GoTo -1' is poorly documented and uselessly complicates error handling.
/// 'On Error GoTo -1' is poorly documented and uselessly complicates error handling. Consider using 'On Error GoTo 0' instead.
/// </why>
internal sealed class OnErrorGoToMinusOneInspection : ParseTreeInspectionBase<VBAParser.OnErrorStmtContext>
{
Expand Down
@@ -0,0 +1,5 @@
## Rubberduck.CodeAnalysis.Inspections.Concrete.ThunderCode

Inspections in this namespace should have a *hidden* attribute on the summary tag, e.g. `<summary hidden="true">`. When the xml-doc is processed, this attribute toggles this content to be displayed:

> *This feature is hidden. It could be an Easter egg, or a problematic feature that is likely (hopefully?) disabled by default.*
Expand Up @@ -5,7 +5,7 @@
using Antlr4.Runtime;
using Rubberduck.Parsing.PreProcessing;

namespace Rubberduck.CodeAnalysis.Inspections.Concrete.UnreachableCaseInspection
namespace Rubberduck.CodeAnalysis.Inspections.Concrete.UnreachableCaseEvaluation
{
internal class ComparableDateValue : IValue, IComparable<ComparableDateValue>
{
Expand Down
Expand Up @@ -5,7 +5,7 @@
using System.Text;
using Rubberduck.Parsing.Grammar;

namespace Rubberduck.CodeAnalysis.Inspections.Concrete.UnreachableCaseInspection
namespace Rubberduck.CodeAnalysis.Inspections.Concrete.UnreachableCaseEvaluation
{
internal enum VariableClauseTypes
{
Expand Down
@@ -1,6 +1,6 @@
using Rubberduck.Parsing.Grammar;

namespace Rubberduck.CodeAnalysis.Inspections.Concrete.UnreachableCaseInspection
namespace Rubberduck.CodeAnalysis.Inspections.Concrete.UnreachableCaseEvaluation
{
internal class ExpressionFilterBoolean : ExpressionFilter<bool>
{
Expand Down
Expand Up @@ -2,7 +2,7 @@
using System.Linq;
using Rubberduck.Parsing.Grammar;

namespace Rubberduck.CodeAnalysis.Inspections.Concrete.UnreachableCaseInspection
namespace Rubberduck.CodeAnalysis.Inspections.Concrete.UnreachableCaseEvaluation
{
internal class ExpressionFilterDate : ExpressionFilter<ComparableDateValue>
{
Expand Down
Expand Up @@ -3,8 +3,8 @@
using System.Linq;
using Rubberduck.Parsing.Grammar;

namespace Rubberduck.CodeAnalysis.Inspections.Concrete.UnreachableCaseInspection{

namespace Rubberduck.CodeAnalysis.Inspections.Concrete.UnreachableCaseEvaluation
{
internal static class ExpressionFilterFactory
{
private static readonly Dictionary<string, (long typeMin, long typeMax)> IntegralNumberExtents = new Dictionary<string, (long typeMin, long typeMax)>()
Expand Down
Expand Up @@ -2,7 +2,7 @@
using System.Collections.Generic;
using System.Linq;

namespace Rubberduck.CodeAnalysis.Inspections.Concrete.UnreachableCaseInspection
namespace Rubberduck.CodeAnalysis.Inspections.Concrete.UnreachableCaseEvaluation
{
internal class ExpressionFilterIntegral : ExpressionFilter<long>
{
Expand Down
@@ -1,6 +1,6 @@
using System;

namespace Rubberduck.CodeAnalysis.Inspections.Concrete.UnreachableCaseInspection
namespace Rubberduck.CodeAnalysis.Inspections.Concrete.UnreachableCaseEvaluation
{
internal struct Limit<T> where T : IComparable<T>
{
Expand Down
Expand Up @@ -4,7 +4,7 @@
using Rubberduck.Parsing.Grammar;
using Rubberduck.Parsing.PreProcessing;

namespace Rubberduck.CodeAnalysis.Inspections.Concrete.UnreachableCaseInspection
namespace Rubberduck.CodeAnalysis.Inspections.Concrete.UnreachableCaseEvaluation
{
internal struct VBACurrency
{
Expand Down
Expand Up @@ -3,7 +3,7 @@
using System.Linq;
using Rubberduck.Parsing.Grammar;

namespace Rubberduck.CodeAnalysis.Inspections.Concrete.UnreachableCaseInspection
namespace Rubberduck.CodeAnalysis.Inspections.Concrete.UnreachableCaseEvaluation
{
internal class OperatorTypesProvider
{
Expand Down
Expand Up @@ -6,7 +6,7 @@
using Rubberduck.Parsing.Grammar;
using Rubberduck.Parsing.PreProcessing;

namespace Rubberduck.CodeAnalysis.Inspections.Concrete.UnreachableCaseInspection
namespace Rubberduck.CodeAnalysis.Inspections.Concrete.UnreachableCaseEvaluation
{
internal interface IParseTreeExpressionEvaluator
{
Expand Down
Expand Up @@ -4,7 +4,7 @@
using Rubberduck.Parsing.Grammar;
using Rubberduck.Parsing.PreProcessing;

namespace Rubberduck.CodeAnalysis.Inspections.Concrete.UnreachableCaseInspection
namespace Rubberduck.CodeAnalysis.Inspections.Concrete.UnreachableCaseEvaluation
{
internal interface IParseTreeValue
{
Expand Down
Expand Up @@ -3,7 +3,7 @@
using Rubberduck.Parsing;
using Rubberduck.Parsing.Grammar;

namespace Rubberduck.CodeAnalysis.Inspections.Concrete.UnreachableCaseInspection
namespace Rubberduck.CodeAnalysis.Inspections.Concrete.UnreachableCaseEvaluation
{
internal interface IParseTreeValueFactory
{
Expand Down
Expand Up @@ -9,7 +9,7 @@
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.VBEditor;

namespace Rubberduck.CodeAnalysis.Inspections.Concrete.UnreachableCaseInspection
namespace Rubberduck.CodeAnalysis.Inspections.Concrete.UnreachableCaseEvaluation
{
internal interface IParseTreeValueVisitor
{
Expand Down
Expand Up @@ -4,7 +4,7 @@
using Antlr4.Runtime;
using Rubberduck.Parsing.Grammar;

namespace Rubberduck.CodeAnalysis.Inspections.Concrete.UnreachableCaseInspection
namespace Rubberduck.CodeAnalysis.Inspections.Concrete.UnreachableCaseEvaluation
{
internal interface IParseTreeVisitorResults
{
Expand Down
@@ -1,7 +1,7 @@
using System.Collections.Generic;
using Rubberduck.Parsing.Grammar;

namespace Rubberduck.CodeAnalysis.Inspections.Concrete.UnreachableCaseInspection
namespace Rubberduck.CodeAnalysis.Inspections.Concrete.UnreachableCaseEvaluation
{
internal interface IRangeClauseExpression
{
Expand Down
Expand Up @@ -4,7 +4,7 @@
using System.Linq;
using Rubberduck.Parsing.Grammar;

namespace Rubberduck.CodeAnalysis.Inspections.Concrete.UnreachableCaseInspection
namespace Rubberduck.CodeAnalysis.Inspections.Concrete.UnreachableCaseEvaluation
{
internal struct TypeTokenPair
{
Expand Down
Expand Up @@ -8,7 +8,7 @@
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.VBEditor;

namespace Rubberduck.CodeAnalysis.Inspections.Concrete.UnreachableCaseInspection
namespace Rubberduck.CodeAnalysis.Inspections.Concrete.UnreachableCaseEvaluation
{
internal interface IUnreachableCaseInspector
{
Expand Down
Expand Up @@ -14,8 +14,9 @@
using Rubberduck.Parsing.VBA.Parsing;
using Rubberduck.Resources.Inspections;
using Rubberduck.VBEditor;
using Rubberduck.CodeAnalysis.Inspections.Concrete.UnreachableCaseEvaluation;

namespace Rubberduck.CodeAnalysis.Inspections.Concrete.UnreachableCaseInspection
namespace Rubberduck.CodeAnalysis.Inspections.Concrete
{
/// <summary>
/// Flags 'Case' blocks that will never execute.
Expand Down Expand Up @@ -104,7 +105,7 @@ namespace Rubberduck.CodeAnalysis.Inspections.Concrete.UnreachableCaseInspection
/// <module name="MyModule" type="Standard Module">
/// <![CDATA[
///
/// 'The inspecion flags Range Clauses that are not of the required form:
/// 'The inspection flags Range Clauses that are not of the required form:
/// '[x] To [y] where [x] less than or equal to [y]
///
/// Private Sub ExampleInvalidRangeExpression(ByVal value As String)
Expand Down
@@ -1,7 +1,7 @@
using System.Linq;
using Rubberduck.CodeAnalysis.Inspections.Results;
using Rubberduck.Parsing;
using Rubberduck.Parsing.Annotations;
using Rubberduck.Parsing.Annotations.Concrete;
using Rubberduck.Parsing.Symbols;
using Rubberduck.Parsing.VBA.DeclarationCaching;
using Rubberduck.VBEditor;
Expand Down
@@ -1,7 +1,7 @@
using System.Linq;
using Antlr4.Runtime;
using Rubberduck.CodeAnalysis.Inspections;
using Rubberduck.CodeAnalysis.Inspections.Concrete.Excel;
using Rubberduck.CodeAnalysis.Inspections.Concrete;
using Rubberduck.CodeAnalysis.Inspections.Results;
using Rubberduck.CodeAnalysis.QuickFixes.Abstract;
using Rubberduck.Parsing;
Expand Down
@@ -1,5 +1,5 @@
using Rubberduck.CodeAnalysis.Inspections;
using Rubberduck.CodeAnalysis.Inspections.Concrete.Excel;
using Rubberduck.CodeAnalysis.Inspections.Concrete;
using Rubberduck.CodeAnalysis.QuickFixes.Abstract;
using Rubberduck.Parsing.Rewriter;

Expand Down
Expand Up @@ -3,6 +3,7 @@
using Rubberduck.CodeAnalysis.Inspections;
using Rubberduck.CodeAnalysis.Inspections.Attributes;
using Rubberduck.CodeAnalysis.QuickFixes.Abstract;
using Rubberduck.Parsing.Annotations.Concrete;
using Rubberduck.Parsing.Annotations;
using Rubberduck.Parsing.Rewriter;
using Rubberduck.Parsing.Symbols;
Expand Down
Expand Up @@ -4,7 +4,7 @@
using Rubberduck.CodeAnalysis.Inspections.Attributes;
using Rubberduck.CodeAnalysis.QuickFixes.Abstract;
using Rubberduck.Parsing;
using Rubberduck.Parsing.Annotations;
using Rubberduck.Parsing.Annotations.Concrete;
using Rubberduck.Parsing.Rewriter;
using Rubberduck.Parsing.Symbols;
using Rubberduck.Parsing.VBA;
Expand Down

0 comments on commit c525a8d

Please sign in to comment.