1
- using System ;
2
- using System . Collections . Generic ;
3
- using System . IO ;
4
- using System . Linq ;
5
- using Antlr4 . Runtime ;
6
- using Antlr4 . Runtime . Misc ;
1
+ using Antlr4 . Runtime ;
7
2
using Antlr4 . Runtime . Tree ;
8
3
using Microsoft . Vbe . Interop ;
4
+ using NLog ;
9
5
using Rubberduck . Parsing . Grammar ;
6
+ using Rubberduck . Parsing . Preprocessing ;
10
7
using Rubberduck . Parsing . Symbols ;
8
+ using System ;
9
+ using System . Collections . Generic ;
10
+ using System . IO ;
11
+ using System . Linq ;
11
12
12
13
namespace Rubberduck . Parsing . VBA
13
14
{
14
15
public class AttributeParser : IAttributeParser
15
16
{
16
17
private readonly IModuleExporter _exporter ;
18
+ private readonly Func < IVBAPreprocessor > _preprocessorFactory ;
19
+ private static readonly Logger _logger = LogManager . GetCurrentClassLogger ( ) ;
17
20
18
- public AttributeParser ( IModuleExporter exporter )
21
+ public AttributeParser ( IModuleExporter exporter , Func < IVBAPreprocessor > preprocessorFactory )
19
22
{
20
23
_exporter = exporter ;
24
+ _preprocessorFactory = preprocessorFactory ;
21
25
}
22
26
23
27
/// <summary>
@@ -32,26 +36,28 @@ public IDictionary<Tuple<string, DeclarationType>, Attributes> Parse(VBComponent
32
36
// a document component without any code wouldn't be exported (file would be empty anyway).
33
37
return new Dictionary < Tuple < string , DeclarationType > , Attributes > ( ) ;
34
38
}
35
-
36
39
var code = File . ReadAllText ( path ) ;
37
40
File . Delete ( path ) ;
38
-
39
41
var type = component . Type == vbext_ComponentType . vbext_ct_StdModule
40
42
? DeclarationType . ProceduralModule
41
43
: DeclarationType . ClassModule ;
44
+ var preprocessor = _preprocessorFactory ( ) ;
45
+ string preprocessed ;
46
+ try
47
+ {
48
+ preprocessed = preprocessor . Execute ( component . Name , code ) ;
49
+ }
50
+ catch ( VBAPreprocessorException ex )
51
+ {
52
+ _logger . Error ( ex , "Preprocessing failed while preparing attribute parsing for module {0}. Trying without preprocessing." , component . Name ) ;
53
+ preprocessed = code ;
54
+ }
42
55
var listener = new AttributeListener ( Tuple . Create ( component . Name , type ) ) ;
43
-
44
- var stream = new AntlrInputStream ( code ) ;
45
- var lexer = new VBALexer ( stream ) ;
46
- var tokens = new CommonTokenStream ( lexer ) ;
47
- var parser = new VBAParser ( tokens ) ;
48
-
49
56
// parse tree isn't usable for declarations because
50
57
// line numbers are offset due to module header and attributes
51
58
// (these don't show up in the VBE, that's why we're parsing an exported file)
52
- var tree = parser . startRule ( ) ;
53
- ParseTreeWalker . Default . Walk ( listener , tree ) ;
54
-
59
+ ITokenStream tokenStream ;
60
+ new VBAModuleParser ( ) . Parse ( component . Name , preprocessed , new IParseTreeListener [ ] { listener } , out tokenStream ) ;
55
61
return listener . Attributes ;
56
62
}
57
63
@@ -76,56 +82,21 @@ public IDictionary<Tuple<string, DeclarationType>, Attributes> Attributes
76
82
77
83
public override void ExitModuleAttributes ( VBAParser . ModuleAttributesContext context )
78
84
{
79
- _attributes . Add ( _currentScope , _currentScopeAttributes ) ;
80
- }
81
-
82
- private static readonly IReadOnlyDictionary < Type , DeclarationType > ScopingContextTypes =
83
- new Dictionary < Type , DeclarationType >
84
- {
85
- { typeof ( VBAParser . SubStmtContext ) , DeclarationType . Procedure } ,
86
- { typeof ( VBAParser . FunctionStmtContext ) , DeclarationType . Function } ,
87
- { typeof ( VBAParser . PropertyGetStmtContext ) , DeclarationType . PropertyGet } ,
88
- { typeof ( VBAParser . PropertyLetStmtContext ) , DeclarationType . PropertyLet } ,
89
- { typeof ( VBAParser . PropertySetStmtContext ) , DeclarationType . PropertySet }
90
- } ;
91
-
92
- public override void EnterSubroutineName ( VBAParser . SubroutineNameContext context )
93
- {
94
- if ( ParserRuleContextHelper . HasParent < VBAParser . SubStmtContext > ( context ) )
85
+ if ( _currentScopeAttributes . Any ( ) )
95
86
{
96
- _currentScope = Tuple . Create ( context . GetText ( ) , DeclarationType . Procedure ) ;
97
- }
98
- else if ( ParserRuleContextHelper . HasParent < VBAParser . PropertyGetStmtContext > ( context ) )
99
- {
100
- _currentScope = Tuple . Create ( context . GetText ( ) , DeclarationType . PropertyGet ) ;
101
- }
102
- }
103
-
104
- public override void EnterFunctionName ( VBAParser . FunctionNameContext context )
105
- {
106
- if ( ParserRuleContextHelper . HasParent < VBAParser . FunctionStmtContext > ( context ) )
107
- {
108
- _currentScope = Tuple . Create ( context . identifier ( ) . GetText ( ) , DeclarationType . Function ) ;
109
- }
110
- else if ( ParserRuleContextHelper . HasParent < VBAParser . PropertyLetStmtContext > ( context ) )
111
- {
112
- _currentScope = Tuple . Create ( context . identifier ( ) . GetText ( ) , DeclarationType . PropertyLet ) ;
113
- }
114
- else if ( ParserRuleContextHelper . HasParent < VBAParser . PropertySetStmtContext > ( context ) )
115
- {
116
- _currentScope = Tuple . Create ( context . identifier ( ) . GetText ( ) , DeclarationType . PropertySet ) ;
87
+ _attributes . Add ( _currentScope , _currentScopeAttributes ) ;
117
88
}
118
89
}
119
90
120
91
public override void EnterSubStmt ( VBAParser . SubStmtContext context )
121
92
{
122
93
_currentScopeAttributes = new Attributes ( ) ;
123
- _currentScope = Tuple . Create ( context . subroutineName ( ) . GetText ( ) , DeclarationType . Procedure ) ;
94
+ _currentScope = Tuple . Create ( Identifier . GetName ( context . subroutineName ( ) ) , DeclarationType . Procedure ) ;
124
95
}
125
96
126
97
public override void ExitSubStmt ( VBAParser . SubStmtContext context )
127
98
{
128
- if ( ! string . IsNullOrEmpty ( _currentScope . Item1 ) && _currentScopeAttributes . Any ( ) )
99
+ if ( _currentScopeAttributes . Any ( ) )
129
100
{
130
101
_attributes . Add ( _currentScope , _currentScopeAttributes ) ;
131
102
}
@@ -134,12 +105,12 @@ public override void ExitSubStmt(VBAParser.SubStmtContext context)
134
105
public override void EnterFunctionStmt ( VBAParser . FunctionStmtContext context )
135
106
{
136
107
_currentScopeAttributes = new Attributes ( ) ;
137
- _currentScope = Tuple . Create ( context . functionName ( ) . identifier ( ) . GetText ( ) , DeclarationType . Function ) ;
108
+ _currentScope = Tuple . Create ( Identifier . GetName ( context . functionName ( ) ) , DeclarationType . Function ) ;
138
109
}
139
110
140
111
public override void ExitFunctionStmt ( VBAParser . FunctionStmtContext context )
141
112
{
142
- if ( ! string . IsNullOrEmpty ( _currentScope . Item1 ) && _currentScopeAttributes . Any ( ) )
113
+ if ( _currentScopeAttributes . Any ( ) )
143
114
{
144
115
_attributes . Add ( _currentScope , _currentScopeAttributes ) ;
145
116
}
@@ -148,12 +119,12 @@ public override void ExitFunctionStmt(VBAParser.FunctionStmtContext context)
148
119
public override void EnterPropertyGetStmt ( VBAParser . PropertyGetStmtContext context )
149
120
{
150
121
_currentScopeAttributes = new Attributes ( ) ;
151
- _currentScope = Tuple . Create ( context . functionName ( ) . identifier ( ) . GetText ( ) , DeclarationType . PropertyGet ) ;
122
+ _currentScope = Tuple . Create ( Identifier . GetName ( context . functionName ( ) ) , DeclarationType . PropertyGet ) ;
152
123
}
153
124
154
125
public override void ExitPropertyGetStmt ( VBAParser . PropertyGetStmtContext context )
155
126
{
156
- if ( ! string . IsNullOrEmpty ( _currentScope . Item1 ) && _currentScopeAttributes . Any ( ) )
127
+ if ( _currentScopeAttributes . Any ( ) )
157
128
{
158
129
_attributes . Add ( _currentScope , _currentScopeAttributes ) ;
159
130
}
@@ -162,12 +133,12 @@ public override void ExitPropertyGetStmt(VBAParser.PropertyGetStmtContext contex
162
133
public override void EnterPropertyLetStmt ( VBAParser . PropertyLetStmtContext context )
163
134
{
164
135
_currentScopeAttributes = new Attributes ( ) ;
165
- _currentScope = Tuple . Create ( context . subroutineName ( ) . GetText ( ) , DeclarationType . PropertyLet ) ;
136
+ _currentScope = Tuple . Create ( Identifier . GetName ( context . subroutineName ( ) ) , DeclarationType . PropertyLet ) ;
166
137
}
167
138
168
139
public override void ExitPropertyLetStmt ( VBAParser . PropertyLetStmtContext context )
169
140
{
170
- if ( ! string . IsNullOrEmpty ( _currentScope . Item1 ) && _currentScopeAttributes . Any ( ) )
141
+ if ( _currentScopeAttributes . Any ( ) )
171
142
{
172
143
_attributes . Add ( _currentScope , _currentScopeAttributes ) ;
173
144
}
@@ -176,24 +147,49 @@ public override void ExitPropertyLetStmt(VBAParser.PropertyLetStmtContext contex
176
147
public override void EnterPropertySetStmt ( VBAParser . PropertySetStmtContext context )
177
148
{
178
149
_currentScopeAttributes = new Attributes ( ) ;
179
- _currentScope = Tuple . Create ( context . subroutineName ( ) . GetText ( ) , DeclarationType . PropertySet ) ;
150
+ _currentScope = Tuple . Create ( Identifier . GetName ( context . subroutineName ( ) ) , DeclarationType . PropertySet ) ;
180
151
}
181
152
182
153
public override void ExitPropertySetStmt ( VBAParser . PropertySetStmtContext context )
183
154
{
184
- if ( ! string . IsNullOrEmpty ( _currentScope . Item1 ) && _currentScopeAttributes . Any ( ) )
155
+ if ( _currentScopeAttributes . Any ( ) )
185
156
{
186
157
_attributes . Add ( _currentScope , _currentScopeAttributes ) ;
187
158
}
188
159
}
189
160
190
161
public override void ExitAttributeStmt ( VBAParser . AttributeStmtContext context )
191
162
{
192
- var name = context . attributeName ( ) . GetText ( ) . Trim ( ) ;
163
+ // We assume attributes can either be simple names (VB_Name) or, if they are inside procedures, member access expressions
164
+ // (e.g. Foo.VB_UserMemId = 0)
165
+ var expr = context . attributeName ( ) . lExpression ( ) ;
166
+ string name ;
167
+ if ( expr is VBAParser . SimpleNameExprContext )
168
+ {
169
+ name = ( ( VBAParser . SimpleNameExprContext ) expr ) . identifier ( ) . GetText ( ) ;
170
+ }
171
+ else
172
+ {
173
+ // Turns "Foo.VB_ProcData.VB_Invoke_Func" into "VB_ProcData.VB_Invoke_Func",
174
+ // because we are not interested in the subroutine name Foo.
175
+ name = GetAttributeNameWithoutProcedureName ( ( VBAParser . MemberAccessExprContext ) expr ) ;
176
+ }
193
177
var values = context . attributeValue ( ) . Select ( e => e . GetText ( ) . Replace ( "\" " , string . Empty ) ) . ToList ( ) ;
194
178
_currentScopeAttributes . Add ( name , values ) ;
195
179
}
196
180
181
+ private string GetAttributeNameWithoutProcedureName ( VBAParser . MemberAccessExprContext expr )
182
+ {
183
+ string name = expr . unrestrictedIdentifier ( ) . GetText ( ) ;
184
+ // The simple name expression represents the procedure's name.
185
+ // We don't want that one though so we simply ignore it.
186
+ if ( expr . lExpression ( ) is VBAParser . SimpleNameExprContext )
187
+ {
188
+ return name ;
189
+ }
190
+ return string . Format ( "{0}.{1}" , GetAttributeNameWithoutProcedureName ( ( VBAParser . MemberAccessExprContext ) expr . lExpression ( ) ) , name ) ;
191
+ }
192
+
197
193
public override void ExitModuleConfigElement ( VBAParser . ModuleConfigElementContext context )
198
194
{
199
195
var name = context . unrestrictedIdentifier ( ) . GetText ( ) ;
0 commit comments