Skip to content

Commit 1545d44

Browse files
committed
Implement ThunderCode inspections
1 parent 56662a5 commit 1545d44

File tree

12 files changed

+675
-36
lines changed

12 files changed

+675
-36
lines changed
Lines changed: 159 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,159 @@
1+
using System.Collections.Generic;
2+
using System.Linq;
3+
using Rubberduck.Inspections.Abstract;
4+
using Rubberduck.Inspections.Results;
5+
using Rubberduck.Parsing.Grammar;
6+
using Rubberduck.Parsing.Inspections.Abstract;
7+
using Rubberduck.Parsing.Symbols;
8+
using Rubberduck.Parsing.VBA;
9+
using Rubberduck.Resources.Inspections;
10+
11+
namespace Rubberduck.Inspections.Inspections.Concrete.ThunderCode
12+
{
13+
public class KeywordsUsedAsMemberInspection : InspectionBase
14+
{
15+
public KeywordsUsedAsMemberInspection(RubberduckParserState state) : base(state) { }
16+
17+
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
18+
{
19+
return State.DeclarationFinder.UserDeclarations(DeclarationType.UserDefinedTypeMember)
20+
.Concat(State.DeclarationFinder.UserDeclarations(DeclarationType.EnumerationMember))
21+
.Where(m => ReservedKeywords.Any(k =>
22+
k.ToLowerInvariant().Equals(
23+
m.IdentifierName.Trim().TrimStart('[').TrimEnd(']').ToLowerInvariant())))
24+
.Select(m => new DeclarationInspectionResult(
25+
this,
26+
InspectionResults.KeywordsUsedAsMemberInspection.
27+
ThunderCodeFormat(m.IdentifierName),
28+
m
29+
));
30+
}
31+
32+
// MS-VBAL 3.3.5.2 Reserved Identifiers and IDENTIFIER
33+
private static IEnumerable<string> ReservedKeywords = new []
34+
{
35+
/*
36+
Statement-keyword = "Call" / "Case" /"Close" / "Const"/ "Declare" / "DefBool" / "DefByte" /
37+
"DefCur" / "DefDate" / "DefDbl" / "DefInt" / "DefLng" / "DefLngLng" /
38+
"DefLngPtr" / "DefObj" / "DefSng" / "DefStr" / "DefVar" / "Dim" / "Do" /
39+
"Else" / "ElseIf" / "End" / "EndIf" / "Enum" / "Erase" / "Event" /
40+
"Exit" / "For" / "Friend" / "Function" / "Get" / "Global" / "GoSub" /
41+
"GoTo" / "If" / "Implements"/ "Input" / "Let" / "Lock" / "Loop" /
42+
"LSet"/ "Next" / "On" / "Open" / "Option" / "Print" / "Private" /
43+
"Public" / "Put" / "RaiseEvent" / "ReDim" / "Resume" / "Return" /
44+
"RSet" / "Seek" / "Select" / "Set" / "Static" / "Stop" / "Sub" /
45+
"Type" / "Unlock" / "Wend" / "While" / "With" / "Write"
46+
*/
47+
48+
Tokens.Call,
49+
Tokens.Case,
50+
Tokens.Close,
51+
Tokens.Const,
52+
Tokens.Declare,
53+
"DefBool",
54+
"DefByte",
55+
"DefCur",
56+
"DefDate",
57+
"DefDbl",
58+
"DefInt",
59+
"DefLng",
60+
"DefLngLng",
61+
"DefLngPtr",
62+
"DefObj",
63+
"DefSng",
64+
"DefStr",
65+
"DefVar",
66+
Tokens.Dim,
67+
Tokens.Do,
68+
Tokens.Else,
69+
Tokens.ElseIf,
70+
Tokens.End,
71+
"EndIf",
72+
Tokens.Enum,
73+
"Erase",
74+
"Event",
75+
Tokens.Exit,
76+
Tokens.For,
77+
Tokens.Friend,
78+
Tokens.Function,
79+
Tokens.Get,
80+
Tokens.Global,
81+
Tokens.GoSub,
82+
Tokens.GoTo,
83+
Tokens.If,
84+
Tokens.Implements,
85+
Tokens.Input,
86+
Tokens.Let,
87+
"Lock",
88+
Tokens.Loop,
89+
"LSet",
90+
Tokens.Next,
91+
Tokens.On,
92+
Tokens.Open,
93+
Tokens.Option,
94+
Tokens.Print,
95+
Tokens.Private,
96+
Tokens.Public,
97+
Tokens.Put,
98+
"RaiseEvent",
99+
Tokens.ReDim,
100+
Tokens.Resume,
101+
Tokens.Return,
102+
"RSet",
103+
"Seek",
104+
Tokens.Select,
105+
Tokens.Set,
106+
Tokens.Static,
107+
Tokens.Stop,
108+
Tokens.Sub,
109+
Tokens.Type,
110+
"Unlock",
111+
Tokens.Wend,
112+
Tokens.While,
113+
Tokens.With,
114+
Tokens.Write,
115+
116+
/*
117+
rem-keyword = "Rem" marker-keyword = "Any" / "As"/ "ByRef" / "ByVal "/"Case" / "Each" /
118+
"Else" /"In"/ "New" / "Shared" / "Until" / "WithEvents" / "Write" / "Optional" /
119+
"ParamArray" / "Preserve" / "Spc" / "Tab" / "Then" / "To"
120+
*/
121+
122+
Tokens.Any,
123+
Tokens.As,
124+
Tokens.ByRef,
125+
Tokens.ByVal,
126+
Tokens.Case,
127+
Tokens.Each,
128+
Tokens.In,
129+
Tokens.New,
130+
"Shared",
131+
Tokens.Until,
132+
"WithEvents",
133+
Tokens.Optional,
134+
Tokens.ParamArray,
135+
Tokens.Preserve,
136+
Tokens.Spc,
137+
"Tab",
138+
Tokens.Then,
139+
Tokens.To,
140+
141+
/*
142+
operator-identifier = "AddressOf" / "And" / "Eqv" / "Imp" / "Is" / "Like" / "New" / "Mod" /
143+
"Not" / "Or" / "TypeOf" / "Xor"
144+
*/
145+
146+
Tokens.AddressOf,
147+
Tokens.And,
148+
Tokens.Eqv,
149+
Tokens.Imp,
150+
Tokens.Is,
151+
Tokens.Like,
152+
Tokens.Mod,
153+
Tokens.Not,
154+
Tokens.Or,
155+
Tokens.TypeOf,
156+
Tokens.XOr
157+
};
158+
}
159+
}
Lines changed: 161 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,161 @@
1+
using System.Collections.Generic;
2+
using System.Linq;
3+
using Antlr4.Runtime;
4+
using Antlr4.Runtime.Tree;
5+
using Rubberduck.Inspections.Abstract;
6+
using Rubberduck.Inspections.Results;
7+
using Rubberduck.Parsing;
8+
using Rubberduck.Parsing.Grammar;
9+
using Rubberduck.Parsing.Inspections.Abstract;
10+
using Rubberduck.Parsing.VBA;
11+
using Rubberduck.Resources.Inspections;
12+
using Rubberduck.VBEditor;
13+
14+
namespace Rubberduck.Inspections.Inspections.Concrete.ThunderCode
15+
{
16+
/// <summary>
17+
/// Note that the inspection only checks a subset of possible "evil" line continatuions
18+
/// for both simplicity and performance reasons. Exahustive inspection would likely take
19+
/// too much effort.
20+
/// </summary>
21+
public class LineContinuationBetweenKeywordsInspection : ParseTreeInspectionBase
22+
{
23+
public LineContinuationBetweenKeywordsInspection(RubberduckParserState state) : base(state)
24+
{
25+
Listener = new LineContinuationBetweenKeywordsListener();
26+
}
27+
28+
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
29+
{
30+
return Listener.Contexts.Select(c => new QualifiedContextInspectionResult(
31+
this,
32+
InspectionResults.LineContinuationBetweenKeywordsInspection.
33+
ThunderCodeFormat(),
34+
c));
35+
}
36+
37+
public override IInspectionListener Listener { get; }
38+
39+
public class LineContinuationBetweenKeywordsListener : VBAParserBaseListener, IInspectionListener
40+
{
41+
private readonly List<QualifiedContext<ParserRuleContext>> _contexts = new List<QualifiedContext<ParserRuleContext>>();
42+
43+
public IReadOnlyList<QualifiedContext<ParserRuleContext>> Contexts => _contexts;
44+
45+
public void ClearContexts()
46+
{
47+
_contexts.Clear();
48+
}
49+
50+
public QualifiedModuleName CurrentModuleName { get; set; }
51+
52+
public override void EnterSubStmt(VBAParser.SubStmtContext context)
53+
{
54+
CheckContext(context, context.END_SUB());
55+
base.EnterSubStmt(context);
56+
}
57+
58+
public override void EnterFunctionStmt(VBAParser.FunctionStmtContext context)
59+
{
60+
CheckContext(context, context.END_FUNCTION());
61+
base.EnterFunctionStmt(context);
62+
}
63+
64+
public override void EnterPropertyGetStmt(VBAParser.PropertyGetStmtContext context)
65+
{
66+
CheckContext(context, context.PROPERTY_GET());
67+
CheckContext(context, context.END_PROPERTY());
68+
base.EnterPropertyGetStmt(context);
69+
}
70+
71+
public override void EnterPropertyLetStmt(VBAParser.PropertyLetStmtContext context)
72+
{
73+
CheckContext(context, context.PROPERTY_LET());
74+
CheckContext(context, context.END_PROPERTY());
75+
base.EnterPropertyLetStmt(context);
76+
}
77+
78+
public override void EnterPropertySetStmt(VBAParser.PropertySetStmtContext context)
79+
{
80+
CheckContext(context, context.PROPERTY_SET());
81+
CheckContext(context, context.END_PROPERTY());
82+
base.EnterPropertySetStmt(context);
83+
}
84+
85+
public override void EnterSelectCaseStmt(VBAParser.SelectCaseStmtContext context)
86+
{
87+
CheckContext(context, context.END_SELECT());
88+
base.EnterSelectCaseStmt(context);
89+
}
90+
91+
public override void EnterWithStmt(VBAParser.WithStmtContext context)
92+
{
93+
CheckContext(context, context.END_WITH());
94+
base.EnterWithStmt(context);
95+
}
96+
97+
public override void EnterExitStmt(VBAParser.ExitStmtContext context)
98+
{
99+
CheckContext(context, context.EXIT_DO());
100+
CheckContext(context, context.EXIT_FOR());
101+
CheckContext(context, context.EXIT_FUNCTION());
102+
CheckContext(context, context.EXIT_PROPERTY());
103+
CheckContext(context, context.EXIT_SUB());
104+
base.EnterExitStmt(context);
105+
}
106+
107+
public override void EnterOnErrorStmt(VBAParser.OnErrorStmtContext context)
108+
{
109+
CheckContext(context, context.ON_ERROR());
110+
CheckContext(context, context.ON_LOCAL_ERROR());
111+
base.EnterOnErrorStmt(context);
112+
}
113+
114+
public override void EnterOptionBaseStmt(VBAParser.OptionBaseStmtContext context)
115+
{
116+
CheckContext(context, context.OPTION_BASE());
117+
base.EnterOptionBaseStmt(context);
118+
}
119+
120+
public override void EnterOptionCompareStmt(VBAParser.OptionCompareStmtContext context)
121+
{
122+
CheckContext(context, context.OPTION_COMPARE());
123+
base.EnterOptionCompareStmt(context);
124+
}
125+
126+
public override void EnterOptionExplicitStmt(VBAParser.OptionExplicitStmtContext context)
127+
{
128+
CheckContext(context, context.OPTION_EXPLICIT());
129+
base.EnterOptionExplicitStmt(context);
130+
}
131+
132+
public override void EnterOptionPrivateModuleStmt(VBAParser.OptionPrivateModuleStmtContext context)
133+
{
134+
CheckContext(context, context.OPTION_PRIVATE_MODULE());
135+
base.EnterOptionPrivateModuleStmt(context);
136+
}
137+
138+
public override void EnterEnumerationStmt(VBAParser.EnumerationStmtContext context)
139+
{
140+
CheckContext(context, context.END_ENUM());
141+
base.EnterEnumerationStmt(context);
142+
}
143+
144+
public override void EnterUdtDeclaration(VBAParser.UdtDeclarationContext context)
145+
{
146+
CheckContext(context, context.END_TYPE());
147+
base.EnterUdtDeclaration(context);
148+
}
149+
150+
151+
152+
private void CheckContext(ParserRuleContext context, IParseTree subTreeToExamine)
153+
{
154+
if (subTreeToExamine?.GetText().Contains("_") ?? false)
155+
{
156+
_contexts.Add(new QualifiedContext<ParserRuleContext>(CurrentModuleName, context));
157+
}
158+
}
159+
}
160+
}
161+
}
Lines changed: 28 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,28 @@
1+
using System.Collections.Generic;
2+
using System.Linq;
3+
using Rubberduck.Inspections.Abstract;
4+
using Rubberduck.Inspections.Results;
5+
using Rubberduck.Parsing.Inspections.Abstract;
6+
using Rubberduck.Parsing.VBA;
7+
using Rubberduck.Resources.Inspections;
8+
9+
namespace Rubberduck.Inspections.Inspections.Concrete.ThunderCode
10+
{
11+
public class NonBreakingSpaceIdentifierInspection : InspectionBase
12+
{
13+
private const string Nbsp = "\u00A0";
14+
15+
public NonBreakingSpaceIdentifierInspection(RubberduckParserState state) : base(state) { }
16+
17+
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
18+
{
19+
return State.DeclarationFinder.AllUserDeclarations
20+
.Where(d => d.IdentifierName.Contains(Nbsp))
21+
.Select(d => new DeclarationInspectionResult(
22+
this,
23+
InspectionResults.NonBreakingSpaceIdentifierInspection.
24+
ThunderCodeFormat(d.IdentifierName),
25+
d));
26+
}
27+
}
28+
}
Lines changed: 12 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,12 @@
1+
using Rubberduck.Resources.Inspections;
2+
3+
namespace Rubberduck.Inspections.Inspections.Concrete.ThunderCode
4+
{
5+
public static class ThunderCodeFormatExtension
6+
{
7+
public static string ThunderCodeFormat(this string inspectionBase, params object[] args)
8+
{
9+
return string.Format(InspectionResults.ThunderCode_Base, string.Format(inspectionBase, args));
10+
}
11+
}
12+
}

Rubberduck.Parsing/Grammar/VBALexer.g4

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -111,7 +111,7 @@ EACH : E A C H;
111111
ELSE : E L S E;
112112
ELSEIF : E L S E I F;
113113
EMPTY : E M P T Y;
114-
// Apparently END_ENUM and END_TYPE don't allow line continuations (in the VB editor)
114+
// Apparently END_ENUM don't allow line continuations (in the VB editor)
115115
END_ENUM : E N D WS+ E N U M;
116116
END_FUNCTION : E N D (WS | LINE_CONTINUATION)+ F U N C T I O N;
117117
// We allow "EndIf" without the whitespace as well for the preprocessor.
@@ -120,7 +120,7 @@ ENDPROPERTY : E N D P R O P E R T Y; //Used in module configurations.
120120
END_PROPERTY : E N D (WS | LINE_CONTINUATION)+ P R O P E R T Y;
121121
END_SELECT : E N D (WS | LINE_CONTINUATION)+ S E L E C T;
122122
END_SUB : E N D (WS | LINE_CONTINUATION)+ S U B;
123-
END_TYPE : E N D WS+ T Y P E;
123+
END_TYPE : E N D (WS | LINE_CONTINUATION)+ T Y P E;
124124
END_WITH : E N D (WS | LINE_CONTINUATION)+ W I T H;
125125
END : E N D;
126126
ENUM : E N U M;

Rubberduck.Resources/Inspections/InspectionInfo.resx

Lines changed: 9 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -364,4 +364,13 @@ If the parameter can be null, ignore this inspection result; passing a null valu
364364
<data name="MissingModuleAnnotationInspection" xml:space="preserve">
365365
<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>
366366
</data>
367+
<data name="KeywordsUsedAsMemberInspection" xml:space="preserve">
368+
<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>
369+
</data>
370+
<data name="LineContinuationBetweenKeywordsInspection" xml:space="preserve">
371+
<value>There are line continuations between keywords. There is no good reason to put it there; consider removing them altogether</value>
372+
</data>
373+
<data name="NonBreakingSpaceIdentifierInspection" xml:space="preserve">
374+
<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>
375+
</data>
367376
</root>

0 commit comments

Comments
 (0)