@@ -5,19 +5,19 @@ import { SemanticTokenModifiers, SemanticTokenTypes, SymbolKind } from 'vscode-l
55// Antlr
66import { ParserRuleContext } from 'antlr4ng' ;
77import {
8+ ArrayDimContext ,
9+ AsClauseContext ,
10+ ConstDeclarationContext ,
811 ConstItemContext ,
912 EnumDeclarationContext ,
1013 EnumMemberContext ,
11- GlobalVariableDeclarationContext ,
12- PrivateConstDeclarationContext ,
13- PrivateVariableDeclarationContext ,
14- PublicConstDeclarationContext ,
1514 PublicEnumDeclarationContext ,
1615 PublicTypeDeclarationContext ,
17- PublicVariableDeclarationContext ,
1816 TypeSuffixContext ,
1917 UdtDeclarationContext ,
18+ UnrestrictedNameContext ,
2019 VariableDclContext ,
20+ VariableDeclarationContext ,
2121 WitheventsVariableDclContext
2222} from '../../antlr/out/vbaParser' ;
2323
@@ -107,35 +107,48 @@ export class TypeDeclarationElement extends BaseTypeDeclarationElement<UdtDeclar
107107}
108108
109109
110- type CombinedVariableContext =
111- PublicVariableDeclarationContext
112- | GlobalVariableDeclarationContext
113- | PrivateVariableDeclarationContext
114- | PublicConstDeclarationContext
115- | PrivateConstDeclarationContext
110+ // ToDo: When events are implemented, note that you cannot raise an event in the
111+ // constructor. It's legal but won't do anything since handlers aren't
112+ // attached until the object is constructed.
113+ // Also note that an event _can only be public_.
116114
117- export class DeclarationStatementElement < T extends CombinedVariableContext > extends BaseContextSyntaxElement < T > {
118- private _isPublic : boolean ;
119- private isConstant : boolean ;
115+ export class VariableDeclarationStatementElement extends BaseContextSyntaxElement < VariableDeclarationContext > {
116+
117+ get isPublic ( ) : boolean {
118+ const modifierCtx = this . context . rule . variableModifier ( ) ;
119+ return ! ! modifierCtx ?. GLOBAL ( ) || ! ! modifierCtx ?. PUBLIC ( ) ;
120+ }
120121
121- get isPublic ( ) : boolean { return this . _isPublic ; }
122122 get declarations ( ) {
123- return this . context . rule . declarationContexts ( ) . map ( x => new VariableDeclarationElement (
124- x , this . context . document , this . isPublic , this . isConstant
125- ) ) ;
123+ const doc = this . context . document ;
124+ const declarationList = this . context . rule . variableDeclarationList ( )
125+ ?? this . context . rule . moduleVariableDeclarationList ( ) ! ;
126+
127+ return declarationList . variableDcl ( ) . map ( ctx => new VariableDeclarationElement ( ctx , doc , this . isPublic , false ) ) ;
126128 }
127129
128- constructor ( ctx : T , doc : TextDocument , isConstant : boolean , isPublic : boolean ) {
130+ constructor ( ctx : VariableDeclarationContext , doc : TextDocument ) {
129131 super ( ctx , doc ) ;
130- this . _isPublic = isPublic ;
131- this . isConstant = isConstant ;
132132 this . scopeItemCapability = new ScopeItemCapability ( this , ItemType . VARIABLE ) ;
133133 }
134+ }
135+
136+ export class ConstDeclarationStatementElement extends BaseContextSyntaxElement < ConstDeclarationContext > {
137+
138+ get isPublic ( ) : boolean {
139+ const modifierCtx = this . context . rule . variableModifier ( ) ;
140+ return ! ! modifierCtx ?. GLOBAL ( ) || ! ! modifierCtx ?. PUBLIC ( ) ;
141+ }
134142
135- static create ( ctx : CombinedVariableContext , doc : TextDocument ) {
136- const isPublicOrGlobal = ( o : any ) : boolean => 'PUBLIC' in o || 'GLOBAL' in o ;
137- const isConstantContext = ( o : any ) : o is PublicConstDeclarationContext | PrivateConstDeclarationContext => 'moduleConstDeclaration' in o ;
138- return new DeclarationStatementElement ( ctx , doc , isConstantContext ( ctx ) , isPublicOrGlobal ( ctx ) ) ;
143+ get declarations ( ) {
144+ const doc = this . context . document ;
145+ const declarationList = this . context . rule . constItemList ( ) . constItem ( ) ;
146+ return declarationList . map ( ctx => new VariableDeclarationElement ( ctx , doc , this . isPublic , true ) ) ;
147+ }
148+
149+ constructor ( ctx : ConstDeclarationContext , doc : TextDocument ) {
150+ super ( ctx , doc ) ;
151+ this . scopeItemCapability = new ScopeItemCapability ( this , ItemType . VARIABLE ) ;
139152 }
140153}
141154
@@ -146,17 +159,134 @@ export class VariableDeclarationElement extends BaseContextSyntaxElement<Variabl
146159 symbolInformationCapability : SymbolInformationCapability ;
147160 // semanticTokenCapability: SemanticTokenCapability;
148161
149- private _isPublic : boolean ;
150- get isPublic ( ) : boolean { return this . _isPublic ; }
162+ private variableTypeInformation ?: VariableTypeInformation ;
151163
152- constructor ( ctx : VariableDclContext | WitheventsVariableDclContext | ConstItemContext , doc : TextDocument , isPublic : boolean , isConst : boolean ) {
164+ constructor ( ctx : VariableDclContext | WitheventsVariableDclContext | ConstItemContext , doc : TextDocument , readonly isPublic : boolean , readonly isConstant : boolean ) {
153165 super ( ctx , doc ) ;
154- this . _isPublic = isPublic ;
155166 this . diagnosticCapability = new DiagnosticCapability ( this ) ;
156167 this . symbolInformationCapability = new SymbolInformationCapability ( this , ctx . toSymbolKind ( ) ) ;
157168 // this.semanticTokenCapability = new SemanticTokenCapability(this, SemanticTokenTypes.variable, isConst ? [SemanticTokenModifiers.declaration, SemanticTokenModifiers.readonly] : [SemanticTokenModifiers.declaration]);
158169 this . identifierCapability = new IdentifierCapability ( { element : this , getNameContext : ( ) => ctx . ambiguousIdentifier ( ) } ) ;
170+
171+ // VariableDcl > TypedVariableDcl > TypedName > TypeSuffix
172+ // > UntypedVariableDcl > AsClause
173+
174+ // Always going to be an object.
175+ // WithEventsVariable > classTypeName > definedTypeExpression > simple/member
176+
177+ // Always going to be a primative.
178+ // ConstItemContext > TypeSuffix
179+ // ConstItemContext > constAsClause > builtInType
180+ if ( ctx instanceof VariableDclContext ) {
181+ const typeCtx = ctx . typedVariableDcl ( ) ?. typedName ( ) . typeSuffix ( )
182+ ?? ctx . untypedVariableDcl ( ) ?. asClause ( ) ;
183+ const arrayCtx = ctx . typedVariableDcl ( ) ?. arrayDim ( )
184+ ?? ctx . untypedVariableDcl ( ) ?. arrayClause ( ) ?. arrayDim ( ) ;
185+ if ( typeCtx ) {
186+ this . variableTypeInformation = new VariableTypeInformation ( typeCtx , doc , arrayCtx ) ;
187+ }
188+ }
159189 this . scopeItemCapability = new ScopeItemCapability ( this , ItemType . VARIABLE ) ;
190+ this . scopeItemCapability . assignmentType = AssignmentType . GET
191+ | ( this . hasLetAccessor ? AssignmentType . LET : AssignmentType . NONE )
192+ | ( this . hasSetAccessor ? AssignmentType . SET : AssignmentType . NONE ) ;
193+ }
194+
195+ get hasLetAccessor ( ) : boolean {
196+ if ( this . context . rule instanceof WitheventsVariableDclContext ) {
197+ return false ;
198+ }
199+ if ( this . context . rule instanceof ConstItemContext ) {
200+ return false ;
201+ }
202+ return this . variableTypeInformation ?. isPrimativeType ?? true ;
203+ }
204+
205+ get hasSetAccessor ( ) : boolean {
206+ if ( this . context . rule instanceof WitheventsVariableDclContext ) {
207+ return true ;
208+ }
209+ if ( this . context . rule instanceof ConstItemContext ) {
210+ return false ;
211+ }
212+ return this . variableTypeInformation ?. isObjectType ?? true ;
213+ }
214+
215+ getType ( ) {
216+ const ctx = this . context . rule ;
217+ if ( ctx instanceof VariableDclContext ) {
218+ // If we're null here, we're implicitly a variant.
219+ const typeCtx = ctx . typedVariableDcl ( ) ?. typedName ( ) . typeSuffix ( )
220+ ?? ctx . untypedVariableDcl ( ) ! . asClause ( ) ;
221+
222+ }
223+ }
224+ }
225+
226+ // ToDo: Needs to handle ClassTypeNameContext
227+ class VariableTypeInformation extends BaseContextSyntaxElement < TypeSuffixContext | AsClauseContext > {
228+ get isObjectType ( ) : boolean {
229+ // Type hints are never an object.
230+ const ctx = this . context . rule ;
231+ if ( ctx instanceof TypeSuffixContext ) {
232+ return false ;
233+ }
234+
235+ // Check builtins for variant type.
236+ const builtin = ctx . asType ( ) ?. typeSpec ( ) . typeExpression ( ) ?. builtinType ( ) ;
237+ if ( builtin ?. reservedTypeIdentifier ( ) ?. VARIANT ( ) || builtin ?. reservedTypeIdentifierB ( ) ?. VARIANT_B ( ) ) {
238+ return true ;
239+ }
240+
241+ // Don't trust anything else. Just check not a primative.
242+ return ! this . isPrimativeType ;
243+ }
244+
245+ get isPrimativeType ( ) : boolean {
246+ // Type hints are always primitive.
247+ const ctx = this . context . rule ;
248+ if ( ctx instanceof TypeSuffixContext ) {
249+ return true ;
250+ }
251+
252+ // A newed object is always an object.
253+ if ( ctx . asAutoObject ( ) ) {
254+ return false ;
255+ }
256+
257+ // Fixed length strings are primative.
258+ const typeSpec = ctx . asType ( ) ! . typeSpec ( ) ;
259+ if ( typeSpec . fixedLengthStringSpec ( ) ) {
260+ return true ;
261+ }
262+
263+ // Built ins are primative (or can be in Variant's case) unless object.
264+ const builtin = typeSpec . typeExpression ( ) ?. builtinType ( ) ;
265+ if ( builtin ?. reservedTypeIdentifier ( ) || builtin ?. reservedTypeIdentifierB ( ) ) {
266+ return true ;
267+ } else if ( builtin ?. OBJECT ( ) || builtin ?. OBJECT_B ( ) ) {
268+ return false ;
269+ }
270+
271+ // Defined names can be all sorts of things but if we got here, we're an object.
272+ const definedType = typeSpec . typeExpression ( ) ?. definedTypeExpression ( ) ;
273+ if ( definedType ?. simpleNameExpression ( ) ) {
274+ return false ;
275+ }
276+
277+ // If we have a member accessed type, we need to do more digging...
278+ const memberAccessed = definedType ?. memberAccessExpression ( ) ?. unrestrictedName ( ) ;
279+ const isPrimativeMember = ( ctx : UnrestrictedNameContext | undefined ) : boolean => ! ! memberAccessed ?. reservedIdentifier ( ) ?. reservedTypeIdentifier ( ) ;
280+ const isTypeSuffixMember = ( ctx : UnrestrictedNameContext | undefined ) : boolean => ! ! memberAccessed ?. name ( ) ?. typedName ( ) ;
281+ return isPrimativeMember ( memberAccessed ) || isTypeSuffixMember ( memberAccessed ) ;
282+ }
283+
284+ get isFixedArrayType ( ) : boolean {
285+ return ! this . arrayCtx ?. boundsList ( ) ;
286+ }
287+
288+ constructor ( ctx : TypeSuffixContext | AsClauseContext , doc : TextDocument , private readonly arrayCtx ?: ArrayDimContext ) {
289+ super ( ctx , doc ) ;
160290 }
161291}
162292
0 commit comments