Skip to content

Commit 2e5f26c

Browse files
authored
Merge pull request #4264 from comintern/parser
Make parser aware of CDecl, add inspection for its use
2 parents 5d6357c + e7e8838 commit 2e5f26c

File tree

15 files changed

+223
-4
lines changed

15 files changed

+223
-4
lines changed
Lines changed: 54 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,54 @@
1+
using System.Collections.Generic;
2+
using System.Linq;
3+
using Antlr4.Runtime;
4+
using Rubberduck.Inspections.Abstract;
5+
using Rubberduck.Inspections.Results;
6+
using Rubberduck.Parsing;
7+
using Rubberduck.Parsing.Grammar;
8+
using Rubberduck.Parsing.Inspections.Abstract;
9+
using Rubberduck.Parsing.VBA;
10+
using Rubberduck.Resources.Inspections;
11+
using Rubberduck.VBEditor;
12+
13+
namespace Rubberduck.Inspections.Inspections.Concrete
14+
{
15+
public sealed class ObsoleteCallingConventionInspection : ParseTreeInspectionBase
16+
{
17+
public ObsoleteCallingConventionInspection(RubberduckParserState state)
18+
: base(state)
19+
{
20+
Listener = new ObsoleteCallingConventionListener();
21+
}
22+
23+
public override IInspectionListener Listener { get; }
24+
25+
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
26+
{
27+
return Listener.Contexts
28+
.Where(context => ((VBAParser.DeclareStmtContext) context.Context).CDECL() != null &&
29+
!IsIgnoringInspectionResultFor(context.ModuleName, context.Context.Start.Line))
30+
.Select(context => new QualifiedContextInspectionResult(this,
31+
string.Format(InspectionResults.ObsoleteCallingConventionInspection,
32+
((VBAParser.DeclareStmtContext) context.Context).identifier().GetText()), context));
33+
}
34+
35+
public class ObsoleteCallingConventionListener : VBAParserBaseListener, IInspectionListener
36+
{
37+
private readonly List<QualifiedContext<ParserRuleContext>> _contexts = new List<QualifiedContext<ParserRuleContext>>();
38+
public IReadOnlyList<QualifiedContext<ParserRuleContext>> Contexts => _contexts;
39+
40+
public QualifiedModuleName CurrentModuleName { get; set; }
41+
42+
public void ClearContexts()
43+
{
44+
_contexts.Clear();
45+
}
46+
47+
public override void ExitDeclareStmt(VBAParser.DeclareStmtContext context)
48+
{
49+
_contexts.Add(new QualifiedContext<ParserRuleContext>(CurrentModuleName, context));
50+
base.ExitDeclareStmt(context);
51+
}
52+
}
53+
}
54+
}

Rubberduck.CodeAnalysis/Rubberduck.CodeAnalysis.csproj

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -79,6 +79,7 @@
7979
<Compile Include="Inspections\Concrete\EmptyForLoopBlockInspection.cs" />
8080
<Compile Include="Inspections\Concrete\BooleanAssignedInIfElseInspection.cs" />
8181
<Compile Include="Inspections\Concrete\EmptyWhileWendBlockInspection.cs" />
82+
<Compile Include="Inspections\Concrete\ObsoleteCallingConventionInspection.cs" />
8283
<Compile Include="Inspections\Concrete\ObsoleteErrorSyntaxInspection.cs" />
8384
<Compile Include="Inspections\Concrete\ObsoleteMemberUsageInspection.cs" />
8485
<Compile Include="Inspections\Concrete\SheetAccessedUsingStringInspection.cs" />

Rubberduck.Core/Properties/Settings.Designer.cs

Lines changed: 5 additions & 3 deletions
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

Rubberduck.Core/Properties/Settings.settings

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -277,6 +277,7 @@
277277
&lt;CodeInspection Name="StepOneIsRedundantInspection" Severity="Hint" InspectionType="LanguageOpportunities" /&gt;
278278
&lt;CodeInspection Name="SheetAccessedUsingStringInspection" Severity="Suggestion" InspectionType="LanguageOpportunities" /&gt;
279279
&lt;CodeInspection Name="ObsoleteMemberUsageInspection" Severity="Warning" InspectionType="MaintainabilityAndReadabilityIssues" /&gt;
280+
&lt;CodeInspection Name="ObsoleteCallingConventionInspection" Severity="Warning" InspectionType="CodeQualityIssues" /&gt;
280281
&lt;/CodeInspections&gt;
281282
&lt;WhitelistedIdentifiers /&gt;
282283
&lt;RunInspectionsOnSuccessfulParse&gt;true&lt;/RunInspectionsOnSuccessfulParse&gt;

Rubberduck.Core/app.config

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -398,6 +398,8 @@
398398
InspectionType="LanguageOpportunities" />
399399
<CodeInspection Name="ObsoleteMemberUsageInspection" Severity="Warning"
400400
InspectionType="MaintainabilityAndReadabilityIssues" />
401+
<CodeInspection Name="ObsoleteCallingConventionInspection" Severity="Warning"
402+
InspectionType="CodeQualityIssues" />
401403
</CodeInspections>
402404
<WhitelistedIdentifiers />
403405
<RunInspectionsOnSuccessfulParse>true</RunInspectionsOnSuccessfulParse>

Rubberduck.Parsing/Grammar/VBALexer.g4

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -80,6 +80,7 @@ BYREF : B Y R E F;
8080
BYTE : B Y T E;
8181
CALL : C A L L;
8282
CASE : C A S E;
83+
CDECL : C D E C L;
8384
CLASS : C L A S S;
8485
CLOSE : C L O S E;
8586
CONST : C O N S T;

Rubberduck.Parsing/Grammar/VBAParser.g4

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -297,7 +297,7 @@ variable : expression;
297297
constStmt : (visibility whiteSpace)? CONST whiteSpace constSubStmt (whiteSpace? COMMA whiteSpace? constSubStmt)*;
298298
constSubStmt : identifier (whiteSpace asTypeClause)? whiteSpace? EQ whiteSpace? expression;
299299

300-
declareStmt : (visibility whiteSpace)? DECLARE whiteSpace (PTRSAFE whiteSpace)? (FUNCTION | SUB) whiteSpace identifier whiteSpace LIB whiteSpace STRINGLITERAL (whiteSpace ALIAS whiteSpace STRINGLITERAL)? (whiteSpace? argList)? (whiteSpace asTypeClause)?;
300+
declareStmt : (visibility whiteSpace)? DECLARE whiteSpace (PTRSAFE whiteSpace)? (FUNCTION | SUB) whiteSpace identifier whiteSpace (CDECL whiteSpace)? LIB whiteSpace STRINGLITERAL (whiteSpace ALIAS whiteSpace STRINGLITERAL)? (whiteSpace? argList)? (whiteSpace asTypeClause)?;
301301

302302
argList : LPAREN (whiteSpace? arg (whiteSpace? COMMA whiteSpace? arg)*)? whiteSpace? RPAREN;
303303

Rubberduck.Resources/Inspections/InspectionInfo.Designer.cs

Lines changed: 9 additions & 0 deletions
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

Rubberduck.Resources/Inspections/InspectionInfo.resx

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -331,4 +331,7 @@ If the parameter can be null, ignore this inspection result; passing a null valu
331331
<data name="ObsoleteMemberUsageInspection" xml:space="preserve">
332332
<value>This member is marked '@Obsolete'. It should no longer be used, there should be a better alternative.</value>
333333
</data>
334+
<data name="ObsoleteCallingConventionInspection" xml:space="preserve">
335+
<value>Windows implementations of Visual Basic only support the StdCall calling convention, and use of of the CDecl calling convention is only supported in Macintosh versions of VBA. Use of this keyword in Windows will result in runtime error 49 - 'Bad DLL calling convention'. If this procedure is only intended to be used on Macintosh hosts, it should be conditionally compiled.</value>
336+
</data>
334337
</root>

Rubberduck.Resources/Inspections/InspectionNames.Designer.cs

Lines changed: 9 additions & 0 deletions
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

0 commit comments

Comments
 (0)