Skip to content

Commit

Permalink
Implement ThunderCode inspections
Browse files Browse the repository at this point in the history
  • Loading branch information
bclothier committed Feb 23, 2019
1 parent 56662a5 commit 1545d44
Show file tree
Hide file tree
Showing 12 changed files with 675 additions and 36 deletions.
@@ -0,0 +1,159 @@
using System.Collections.Generic;
using System.Linq;
using Rubberduck.Inspections.Abstract;
using Rubberduck.Inspections.Results;
using Rubberduck.Parsing.Grammar;
using Rubberduck.Parsing.Inspections.Abstract;
using Rubberduck.Parsing.Symbols;
using Rubberduck.Parsing.VBA;
using Rubberduck.Resources.Inspections;

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

protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
{
return State.DeclarationFinder.UserDeclarations(DeclarationType.UserDefinedTypeMember)
.Concat(State.DeclarationFinder.UserDeclarations(DeclarationType.EnumerationMember))
.Where(m => ReservedKeywords.Any(k =>
k.ToLowerInvariant().Equals(
m.IdentifierName.Trim().TrimStart('[').TrimEnd(']').ToLowerInvariant())))
.Select(m => new DeclarationInspectionResult(
this,
InspectionResults.KeywordsUsedAsMemberInspection.
ThunderCodeFormat(m.IdentifierName),
m
));
}

// MS-VBAL 3.3.5.2 Reserved Identifiers and IDENTIFIER
private static IEnumerable<string> ReservedKeywords = new []
{
/*
Statement-keyword = "Call" / "Case" /"Close" / "Const"/ "Declare" / "DefBool" / "DefByte" /
"DefCur" / "DefDate" / "DefDbl" / "DefInt" / "DefLng" / "DefLngLng" /
"DefLngPtr" / "DefObj" / "DefSng" / "DefStr" / "DefVar" / "Dim" / "Do" /
"Else" / "ElseIf" / "End" / "EndIf" / "Enum" / "Erase" / "Event" /
"Exit" / "For" / "Friend" / "Function" / "Get" / "Global" / "GoSub" /
"GoTo" / "If" / "Implements"/ "Input" / "Let" / "Lock" / "Loop" /
"LSet"/ "Next" / "On" / "Open" / "Option" / "Print" / "Private" /
"Public" / "Put" / "RaiseEvent" / "ReDim" / "Resume" / "Return" /
"RSet" / "Seek" / "Select" / "Set" / "Static" / "Stop" / "Sub" /
"Type" / "Unlock" / "Wend" / "While" / "With" / "Write"
*/

Tokens.Call,
Tokens.Case,
Tokens.Close,
Tokens.Const,
Tokens.Declare,
"DefBool",
"DefByte",
"DefCur",
"DefDate",
"DefDbl",
"DefInt",
"DefLng",
"DefLngLng",
"DefLngPtr",
"DefObj",
"DefSng",
"DefStr",
"DefVar",
Tokens.Dim,
Tokens.Do,
Tokens.Else,
Tokens.ElseIf,
Tokens.End,
"EndIf",
Tokens.Enum,
"Erase",
"Event",
Tokens.Exit,
Tokens.For,
Tokens.Friend,
Tokens.Function,
Tokens.Get,
Tokens.Global,
Tokens.GoSub,
Tokens.GoTo,
Tokens.If,
Tokens.Implements,
Tokens.Input,
Tokens.Let,
"Lock",
Tokens.Loop,
"LSet",
Tokens.Next,
Tokens.On,
Tokens.Open,
Tokens.Option,
Tokens.Print,
Tokens.Private,
Tokens.Public,
Tokens.Put,
"RaiseEvent",
Tokens.ReDim,
Tokens.Resume,
Tokens.Return,
"RSet",
"Seek",
Tokens.Select,
Tokens.Set,
Tokens.Static,
Tokens.Stop,
Tokens.Sub,
Tokens.Type,
"Unlock",
Tokens.Wend,
Tokens.While,
Tokens.With,
Tokens.Write,

/*
rem-keyword = "Rem" marker-keyword = "Any" / "As"/ "ByRef" / "ByVal "/"Case" / "Each" /
"Else" /"In"/ "New" / "Shared" / "Until" / "WithEvents" / "Write" / "Optional" /
"ParamArray" / "Preserve" / "Spc" / "Tab" / "Then" / "To"
*/

Tokens.Any,
Tokens.As,
Tokens.ByRef,
Tokens.ByVal,
Tokens.Case,
Tokens.Each,
Tokens.In,
Tokens.New,
"Shared",
Tokens.Until,
"WithEvents",
Tokens.Optional,
Tokens.ParamArray,
Tokens.Preserve,
Tokens.Spc,
"Tab",
Tokens.Then,
Tokens.To,

/*
operator-identifier = "AddressOf" / "And" / "Eqv" / "Imp" / "Is" / "Like" / "New" / "Mod" /
"Not" / "Or" / "TypeOf" / "Xor"
*/

Tokens.AddressOf,
Tokens.And,
Tokens.Eqv,
Tokens.Imp,
Tokens.Is,
Tokens.Like,
Tokens.Mod,
Tokens.Not,
Tokens.Or,
Tokens.TypeOf,
Tokens.XOr
};
}
}
@@ -0,0 +1,161 @@
using System.Collections.Generic;
using System.Linq;
using Antlr4.Runtime;
using Antlr4.Runtime.Tree;
using Rubberduck.Inspections.Abstract;
using Rubberduck.Inspections.Results;
using Rubberduck.Parsing;
using Rubberduck.Parsing.Grammar;
using Rubberduck.Parsing.Inspections.Abstract;
using Rubberduck.Parsing.VBA;
using Rubberduck.Resources.Inspections;
using Rubberduck.VBEditor;

namespace Rubberduck.Inspections.Inspections.Concrete.ThunderCode
{
/// <summary>
/// Note that the inspection only checks a subset of possible "evil" line continatuions
/// for both simplicity and performance reasons. Exahustive inspection would likely take
/// too much effort.
/// </summary>
public class LineContinuationBetweenKeywordsInspection : ParseTreeInspectionBase
{
public LineContinuationBetweenKeywordsInspection(RubberduckParserState state) : base(state)
{
Listener = new LineContinuationBetweenKeywordsListener();
}

protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
{
return Listener.Contexts.Select(c => new QualifiedContextInspectionResult(
this,
InspectionResults.LineContinuationBetweenKeywordsInspection.
ThunderCodeFormat(),
c));
}

public override IInspectionListener Listener { get; }

public class LineContinuationBetweenKeywordsListener : VBAParserBaseListener, IInspectionListener
{
private readonly List<QualifiedContext<ParserRuleContext>> _contexts = new List<QualifiedContext<ParserRuleContext>>();

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

public void ClearContexts()
{
_contexts.Clear();
}

public QualifiedModuleName CurrentModuleName { get; set; }

public override void EnterSubStmt(VBAParser.SubStmtContext context)
{
CheckContext(context, context.END_SUB());
base.EnterSubStmt(context);
}

public override void EnterFunctionStmt(VBAParser.FunctionStmtContext context)
{
CheckContext(context, context.END_FUNCTION());
base.EnterFunctionStmt(context);
}

public override void EnterPropertyGetStmt(VBAParser.PropertyGetStmtContext context)
{
CheckContext(context, context.PROPERTY_GET());
CheckContext(context, context.END_PROPERTY());
base.EnterPropertyGetStmt(context);
}

public override void EnterPropertyLetStmt(VBAParser.PropertyLetStmtContext context)
{
CheckContext(context, context.PROPERTY_LET());
CheckContext(context, context.END_PROPERTY());
base.EnterPropertyLetStmt(context);
}

public override void EnterPropertySetStmt(VBAParser.PropertySetStmtContext context)
{
CheckContext(context, context.PROPERTY_SET());
CheckContext(context, context.END_PROPERTY());
base.EnterPropertySetStmt(context);
}

public override void EnterSelectCaseStmt(VBAParser.SelectCaseStmtContext context)
{
CheckContext(context, context.END_SELECT());
base.EnterSelectCaseStmt(context);
}

public override void EnterWithStmt(VBAParser.WithStmtContext context)
{
CheckContext(context, context.END_WITH());
base.EnterWithStmt(context);
}

public override void EnterExitStmt(VBAParser.ExitStmtContext context)
{
CheckContext(context, context.EXIT_DO());
CheckContext(context, context.EXIT_FOR());
CheckContext(context, context.EXIT_FUNCTION());
CheckContext(context, context.EXIT_PROPERTY());
CheckContext(context, context.EXIT_SUB());
base.EnterExitStmt(context);
}

public override void EnterOnErrorStmt(VBAParser.OnErrorStmtContext context)
{
CheckContext(context, context.ON_ERROR());
CheckContext(context, context.ON_LOCAL_ERROR());
base.EnterOnErrorStmt(context);
}

public override void EnterOptionBaseStmt(VBAParser.OptionBaseStmtContext context)
{
CheckContext(context, context.OPTION_BASE());
base.EnterOptionBaseStmt(context);
}

public override void EnterOptionCompareStmt(VBAParser.OptionCompareStmtContext context)
{
CheckContext(context, context.OPTION_COMPARE());
base.EnterOptionCompareStmt(context);
}

public override void EnterOptionExplicitStmt(VBAParser.OptionExplicitStmtContext context)
{
CheckContext(context, context.OPTION_EXPLICIT());
base.EnterOptionExplicitStmt(context);
}

public override void EnterOptionPrivateModuleStmt(VBAParser.OptionPrivateModuleStmtContext context)
{
CheckContext(context, context.OPTION_PRIVATE_MODULE());
base.EnterOptionPrivateModuleStmt(context);
}

public override void EnterEnumerationStmt(VBAParser.EnumerationStmtContext context)
{
CheckContext(context, context.END_ENUM());
base.EnterEnumerationStmt(context);
}

public override void EnterUdtDeclaration(VBAParser.UdtDeclarationContext context)
{
CheckContext(context, context.END_TYPE());
base.EnterUdtDeclaration(context);
}



private void CheckContext(ParserRuleContext context, IParseTree subTreeToExamine)
{
if (subTreeToExamine?.GetText().Contains("_") ?? false)
{
_contexts.Add(new QualifiedContext<ParserRuleContext>(CurrentModuleName, context));
}
}
}
}
}
@@ -0,0 +1,28 @@
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.Inspections.Concrete.ThunderCode
{
public class NonBreakingSpaceIdentifierInspection : InspectionBase
{
private const string Nbsp = "\u00A0";

public NonBreakingSpaceIdentifierInspection(RubberduckParserState state) : base(state) { }

protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
{
return State.DeclarationFinder.AllUserDeclarations
.Where(d => d.IdentifierName.Contains(Nbsp))
.Select(d => new DeclarationInspectionResult(
this,
InspectionResults.NonBreakingSpaceIdentifierInspection.
ThunderCodeFormat(d.IdentifierName),
d));
}
}
}
@@ -0,0 +1,12 @@
using Rubberduck.Resources.Inspections;

namespace Rubberduck.Inspections.Inspections.Concrete.ThunderCode
{
public static class ThunderCodeFormatExtension
{
public static string ThunderCodeFormat(this string inspectionBase, params object[] args)
{
return string.Format(InspectionResults.ThunderCode_Base, string.Format(inspectionBase, args));
}
}
}
4 changes: 2 additions & 2 deletions Rubberduck.Parsing/Grammar/VBALexer.g4
Expand Up @@ -111,7 +111,7 @@ EACH : E A C H;
ELSE : E L S E;
ELSEIF : E L S E I F;
EMPTY : E M P T Y;
// Apparently END_ENUM and END_TYPE don't allow line continuations (in the VB editor)
// Apparently END_ENUM don't allow line continuations (in the VB editor)
END_ENUM : E N D WS+ E N U M;
END_FUNCTION : E N D (WS | LINE_CONTINUATION)+ F U N C T I O N;
// We allow "EndIf" without the whitespace as well for the preprocessor.
Expand All @@ -120,7 +120,7 @@ ENDPROPERTY : E N D P R O P E R T Y; //Used in module configurations.
END_PROPERTY : E N D (WS | LINE_CONTINUATION)+ P R O P E R T Y;
END_SELECT : E N D (WS | LINE_CONTINUATION)+ S E L E C T;
END_SUB : E N D (WS | LINE_CONTINUATION)+ S U B;
END_TYPE : E N D WS+ T Y P E;
END_TYPE : E N D (WS | LINE_CONTINUATION)+ T Y P E;
END_WITH : E N D (WS | LINE_CONTINUATION)+ W I T H;
END : E N D;
ENUM : E N U M;
Expand Down
9 changes: 9 additions & 0 deletions Rubberduck.Resources/Inspections/InspectionInfo.resx
Expand Up @@ -364,4 +364,13 @@ If the parameter can be null, ignore this inspection result; passing a null valu
<data name="MissingModuleAnnotationInspection" xml:space="preserve">
<value>Module attributes are not displayed in the VBE. By adding an annotation, you make these attributes more explicit, and Rubberduck can keep annotations and attributes synchronized.</value>
</data>
<data name="KeywordsUsedAsMemberInspection" xml:space="preserve">
<value>A keyword is being used as a member in either an enumeration or an user defined type. That can lead to ambiguous resolution. Condier renaming.</value>
</data>
<data name="LineContinuationBetweenKeywordsInspection" xml:space="preserve">
<value>There are line continuations between keywords. There is no good reason to put it there; consider removing them altogether</value>
</data>
<data name="NonBreakingSpaceIdentifierInspection" xml:space="preserve">
<value>The identiifer contains a non-breaking space which looks very much like just an ordinary space, which obfsucates the code and makes for a confusing experience. Consider using only latin characters for the identifiers.</value>
</data>
</root>

0 comments on commit 1545d44

Please sign in to comment.