1- import { AmbiguousIdentifierContext , EnumDeclarationContext , EnumMemberContext , FunctionDeclarationContext , ProcedureDeclarationContext , PropertyGetDeclarationContext , PropertySetDeclarationContext , SubroutineDeclarationContext } from '../../antlr/out/vbaParser' ;
1+ import { AmbiguousIdentifierContext , EnumDeclarationContext , EnumMemberContext , FunctionDeclarationContext , ProcedureDeclarationContext , PropertyGetDeclarationContext , PropertySetDeclarationContext , PublicTypeDeclarationContext , SubroutineDeclarationContext , UdtDeclarationContext , UntypedNameContext } from '../../antlr/out/vbaParser' ;
22
33import { TextDocument } from 'vscode-languageserver-textdocument' ;
44
5- import { BaseContextSyntaxElement , HasSemanticToken , HasSymbolInformation , IdentifiableSyntaxElement } from './base' ;
5+ import { BaseContextSyntaxElement , HasSemanticToken , HasSymbolInformation , IdentifiableSyntaxElement , NamedSyntaxElement } from './base' ;
66import { SemanticTokenModifiers , SemanticTokenTypes , SymbolInformation , SymbolKind } from 'vscode-languageserver' ;
77import { ScopeElement } from './special' ;
88import { SymbolInformationFactory } from '../../capabilities/symbolInformation' ;
@@ -11,7 +11,7 @@ import { VbaClassDocument, VbaModuleDocument } from '../document';
1111
1212
1313export class IdentifierElement extends BaseContextSyntaxElement {
14- constructor ( ctx : AmbiguousIdentifierContext , doc : TextDocument ) {
14+ constructor ( ctx : UntypedNameContext | AmbiguousIdentifierContext , doc : TextDocument ) {
1515 super ( ctx , doc ) ;
1616 }
1717}
@@ -58,8 +58,8 @@ export class SubDeclarationElement extends DeclarationElement implements HasSymb
5858 constructor ( context : ProcedureDeclarationContext , document : TextDocument , methodContext : SubroutineDeclarationContext ) {
5959 super ( context , document ) ;
6060
61- const identifierContext = methodContext . subroutineName ( ) ! . ambiguousIdentifier ( ) ! ;
62- this . identifier = new IdentifierElement ( identifierContext , document ) ;
61+ const identifierContext = methodContext . subroutineName ( ) ? .ambiguousIdentifier ( ) ;
62+ this . identifier = new IdentifierElement ( identifierContext ! , document ) ;
6363 this . symbolInformation = SymbolInformation . create (
6464 this . identifier . text ,
6565 SymbolKind . Method ,
@@ -207,84 +207,6 @@ class EnumMemberDeclarationElement extends BaseEnumDeclarationElement {
207207 }
208208}
209209
210-
211- // abstract class BaseEnumElement extends FoldableElement implements HasSemanticToken, HasSymbolInformation {
212- // identifier: IdentifierElement;
213- // tokenModifiers: SemanticTokenModifiers[] = [];
214- // abstract tokenType: SemanticTokenTypes;
215- // abstract symbolKind: SymbolKind;
216-
217- // constructor(context: EnumerationStmtContext | EnumerationStmt_ConstantContext, document: TextDocument) {
218- // super(context, document);
219- // this.identifier = new IdentifierElement(context.ambiguousIdentifier(), document);
220- // }
221-
222- // get name(): string { return this.identifier.text; }
223- // get symbolInformation(): SymbolInformation {
224- // return SymbolInformationFactory.create(
225- // this, this.symbolKind
226- // );
227- // }
228-
229- // }
230-
231-
232- // export class EnumBlockDeclarationElement extends BaseEnumElement {
233- // tokenType: SemanticTokenTypes;
234- // tokenModifiers: SemanticTokenModifiers[] = [];
235- // symbolKind: SymbolKind;
236-
237- // constructor(context: EnumerationStmtContext, document: TextDocument) {
238- // super(context, document);
239- // this.tokenType = SemanticTokenTypes.enum;
240- // this.symbolKind = SymbolKind.Enum;
241- // }
242- // }
243-
244-
245- // export class EnumMemberDeclarationElement extends BaseEnumElement {
246- // tokenType: SemanticTokenTypes;
247- // tokenModifiers: SemanticTokenModifiers[] = [];
248- // symbolKind: SymbolKind;
249-
250- // constructor(context: EnumerationStmt_ConstantContext, document: TextDocument) {
251- // super(context, document);
252- // this.tokenType = SemanticTokenTypes.enumMember;
253- // this.symbolKind = SymbolKind.EnumMember;
254- // }
255- // }
256-
257- // abstract class BaseMethodElement extends FoldableElement implements HasSemanticToken, HasSymbolInformation {
258- // identifier: IdentifierElement;
259- // tokenModifiers: SemanticTokenModifiers[] = [];
260- // abstract tokenType: SemanticTokenTypes;
261- // abstract symbolKind: SymbolKind;
262-
263- // constructor(context: MethodStmtContext, document: TextDocument) {
264- // super(context, document);
265- // this.identifier = new IdentifierElement(context.methodSignatureStmt().ambiguousIdentifier(), document);
266- // }
267-
268- // get name(): string { return this.identifier.text; }
269- // get symbolInformation(): SymbolInformation {
270- // return SymbolInformationFactory.create(
271- // this, this.symbolKind
272- // );
273- // }
274- // }
275-
276- // export class MethodBlockDeclarationElement extends BaseMethodElement {
277- // tokenType: SemanticTokenTypes;
278- // tokenModifiers: SemanticTokenModifiers[] = [];
279- // symbolKind: SymbolKind;
280-
281- // constructor(context: MethodStmtContext, document: TextDocument) {
282- // super(context, document);
283- // this.tokenType = SemanticTokenTypes.method;
284- // this.symbolKind = SymbolKind.Method;
285- // }
286- // }
287-
288210// abstract class BaseVariableDeclarationStatementElement extends BaseContextSyntaxElement {
289211// abstract declarations: VariableDeclarationElement[];
290212
@@ -306,25 +228,27 @@ class EnumMemberDeclarationElement extends BaseEnumDeclarationElement {
306228// }
307229// }
308230
309- // export class TypeDeclarationElement extends FoldableElement implements HasSemanticToken, HasSymbolInformation {
310- // tokenType: SemanticTokenTypes;
311- // tokenModifiers: SemanticTokenModifiers[] = [];
312- // identifier: IdentifierElement;
313- // symbolKind: SymbolKind;
231+ export class TypeDeclarationElement extends ScopeElement implements HasSemanticToken , HasSymbolInformation , NamedSyntaxElement {
232+ tokenType : SemanticTokenTypes ;
233+ tokenModifiers : SemanticTokenModifiers [ ] = [ ] ;
234+ identifier : IdentifierElement ;
235+ symbolKind : SymbolKind ;
236+ declaredNames : Map < string , IdentifiableSyntaxElement [ ] > = new Map ( ) ; // Get variable declarations going
314237
315- // constructor(context: TypeStmtContext , document: TextDocument) {
316- // super(context, document);
317- // this.symbolKind = SymbolKind.Struct;
318- // this.tokenType = SemanticTokenTypes.struct;
319- // this.identifier = new IdentifierElement(context.ambiguousIdentifier (), document);
320- // }
238+ constructor ( context : UdtDeclarationContext , document : TextDocument ) {
239+ super ( context , document ) ;
240+ this . symbolKind = SymbolKind . Struct ;
241+ this . tokenType = SemanticTokenTypes . struct ;
242+ this . identifier = new IdentifierElement ( context . untypedName ( ) , document ) ;
243+ }
321244
322- // get name(): string { return this.identifier.text; }
323- // get symbolInformation(): SymbolInformation {
324- // return SymbolInformationFactory.create(
325- // this, this.symbolKind
326- // );
327- // }
245+ get name ( ) : string { return this . identifier . text ; }
246+ get symbolInformation ( ) : SymbolInformation {
247+ return SymbolInformationFactory . create (
248+ this as NamedSyntaxElement , this . symbolKind
249+ ) ;
250+ }
251+ }
328252
329253// }
330254
0 commit comments