@@ -144,14 +144,18 @@ private void ParseAll()
144144 return ;
145145 }
146146
147- foreach ( var component in toParse )
148- {
149- _state . SetModuleState ( component , ParserState . Pending ) ;
150- }
151- foreach ( var component in unchanged )
147+
148+ lock ( _state )
152149 {
153- // note: seting to 'Parsed' would include them in the resolver walk. 'Ready' excludes them.
154- _state . SetModuleState ( component , ParserState . Ready ) ;
150+ foreach ( var component in toParse )
151+ {
152+ _state . SetModuleState ( component , ParserState . Pending ) ;
153+ }
154+ foreach ( var component in unchanged )
155+ {
156+ // note: seting to 'Parsed' would include them in the resolver walk. 'Ready' excludes them.
157+ _state . SetModuleState ( component , ParserState . Ready ) ;
158+ }
155159 }
156160
157161 // invalidation cleanup should go into ParseAsync?
@@ -186,18 +190,21 @@ private void AddBuiltInDeclarations(IReadOnlyList<VBProject> projects)
186190
187191 var qualifiedName = new QualifiedModuleName ( vba . IdentifierName , vba . IdentifierName , errObject . IdentifierName ) ;
188192 var err = new Declaration ( new QualifiedMemberName ( qualifiedName , Tokens . Err ) , vba , "Global" , errObject . IdentifierName , true , false , Accessibility . Global , DeclarationType . Variable ) ;
189- _state . AddDeclaration ( err ) ;
190-
191193 var debugClassName = new QualifiedModuleName ( vba . IdentifierName , vba . IdentifierName , "DebugClass" ) ;
192194 var debugClass = new Declaration ( new QualifiedMemberName ( debugClassName , "DebugClass" ) , vba , "Global" , "DebugClass" , false , false , Accessibility . Global , DeclarationType . ClassModule ) ;
193195 var debugObject = new Declaration ( new QualifiedMemberName ( debugClassName , "Debug" ) , vba , "Global" , "DebugClass" , true , false , Accessibility . Global , DeclarationType . Variable ) ;
194196 var debugAssert = new Declaration ( new QualifiedMemberName ( debugClassName , "Assert" ) , debugObject , debugObject . Scope , null , false , false , Accessibility . Global , DeclarationType . Procedure ) ;
195197 var debugPrint = new Declaration ( new QualifiedMemberName ( debugClassName , "Print" ) , debugObject , debugObject . Scope , null , false , false , Accessibility . Global , DeclarationType . Procedure ) ;
196198
197- _state . AddDeclaration ( debugClass ) ;
198- _state . AddDeclaration ( debugObject ) ;
199- _state . AddDeclaration ( debugAssert ) ;
200- _state . AddDeclaration ( debugPrint ) ;
199+
200+ lock ( _state )
201+ {
202+ _state . AddDeclaration ( err ) ;
203+ _state . AddDeclaration ( debugClass ) ;
204+ _state . AddDeclaration ( debugObject ) ;
205+ _state . AddDeclaration ( debugAssert ) ;
206+ _state . AddDeclaration ( debugPrint ) ;
207+ }
201208 }
202209
203210 private readonly HashSet < ReferencePriorityMap > _projectReferences = new HashSet < ReferencePriorityMap > ( ) ;
@@ -287,8 +294,12 @@ private void UnloadComReference(Reference reference, IReadOnlyList<VBProject> pr
287294
288295 public Task ParseAsync ( VBComponent component , CancellationToken token , TokenStreamRewriter rewriter = null )
289296 {
290- _state . ClearStateCache ( component ) ;
291- _state . SetModuleState ( component , ParserState . Pending ) ; // also clears module-exceptions
297+ lock ( _state )
298+ lock ( component )
299+ {
300+ _state . ClearStateCache ( component ) ;
301+ _state . SetModuleState ( component , ParserState . Pending ) ; // also clears module-exceptions
302+ }
292303
293304 var linkedTokenSource = CancellationTokenSource . CreateLinkedTokenSource ( _central . Token , token ) ;
294305
@@ -336,20 +347,34 @@ private void ParseAsyncInternal(VBComponent component, CancellationToken token,
336347 {
337348 var preprocessor = new VBAPreprocessor ( double . Parse ( _vbe . Version , CultureInfo . InvariantCulture ) ) ;
338349 var parser = new ComponentParseTask ( component , preprocessor , _attributeParser , rewriter ) ;
339- parser . ParseFailure += ( sender , e ) => _state . SetModuleState ( component , ParserState . Error , e . Cause as SyntaxErrorException ) ;
350+ parser . ParseFailure += ( sender , e ) =>
351+ {
352+ lock ( _state )
353+ lock ( component )
354+ {
355+ _state . SetModuleState ( component , ParserState . Error , e . Cause as SyntaxErrorException ) ;
356+ }
357+ } ;
340358 parser . ParseCompleted += ( sender , e ) =>
341359 {
342- // possibly lock _state
343- _state . SetModuleAttributes ( component , e . Attributes ) ;
344- _state . AddParseTree ( component , e . ParseTree ) ;
345- _state . AddTokenStream ( component , e . Tokens ) ;
346- _state . SetModuleComments ( component , e . Comments ) ;
347- _state . SetModuleAnnotations ( component , e . Annotations ) ;
348-
349- // This really needs to go last
350- _state . SetModuleState ( component , ParserState . Parsed ) ;
360+ lock ( _state )
361+ lock ( component )
362+ {
363+ _state . SetModuleAttributes ( component , e . Attributes ) ;
364+ _state . AddParseTree ( component , e . ParseTree ) ;
365+ _state . AddTokenStream ( component , e . Tokens ) ;
366+ _state . SetModuleComments ( component , e . Comments ) ;
367+ _state . SetModuleAnnotations ( component , e . Annotations ) ;
368+
369+ // This really needs to go last
370+ _state . SetModuleState ( component , ParserState . Parsed ) ;
371+ }
351372 } ;
352- _state . SetModuleState ( component , ParserState . Parsing ) ;
373+ lock ( _state )
374+ lock ( component )
375+ {
376+ _state . SetModuleState ( component , ParserState . Parsing ) ;
377+ }
353378 parser . Start ( token ) ;
354379 }
355380
@@ -426,18 +451,26 @@ private void ResolveDeclarations(VBComponent component, IParseTree tree)
426451 argListWithOneByRefParamListener ,
427452 } ) , tree ) ;
428453 // TODO: these are actually (almost) inspection results.. we should handle them as such
429- _state . ArgListsWithOneByRefParam = argListWithOneByRefParamListener . Contexts . Select ( context => new QualifiedContext ( qualifiedModuleName , context ) ) ;
430- _state . EmptyStringLiterals = emptyStringLiteralListener . Contexts . Select ( context => new QualifiedContext ( qualifiedModuleName , context ) ) ;
431- _state . ObsoleteLetContexts = obsoleteLetStatementListener . Contexts . Select ( context => new QualifiedContext ( qualifiedModuleName , context ) ) ;
432- _state . ObsoleteCallContexts = obsoleteCallStatementListener . Contexts . Select ( context => new QualifiedContext ( qualifiedModuleName , context ) ) ;
454+ lock ( _state )
455+ lock ( component )
456+ {
457+ _state . ArgListsWithOneByRefParam = argListWithOneByRefParamListener . Contexts . Select ( context => new QualifiedContext ( qualifiedModuleName , context ) ) ;
458+ _state . EmptyStringLiterals = emptyStringLiteralListener . Contexts . Select ( context => new QualifiedContext ( qualifiedModuleName , context ) ) ;
459+ _state . ObsoleteLetContexts = obsoleteLetStatementListener . Contexts . Select ( context => new QualifiedContext ( qualifiedModuleName , context ) ) ;
460+ _state . ObsoleteCallContexts = obsoleteCallStatementListener . Contexts . Select ( context => new QualifiedContext ( qualifiedModuleName , context ) ) ;
461+ }
462+
433463 var project = component . Collection . Parent ;
434464 var projectQualifiedName = new QualifiedModuleName ( project ) ;
435465 Declaration projectDeclaration ;
436466 if ( ! _projectDeclarations . TryGetValue ( projectQualifiedName . ProjectId , out projectDeclaration ) )
437467 {
438468 projectDeclaration = CreateProjectDeclaration ( projectQualifiedName , project ) ;
439469 _projectDeclarations . Add ( projectQualifiedName . ProjectId , projectDeclaration ) ;
440- _state . AddDeclaration ( projectDeclaration ) ;
470+ lock ( _state )
471+ {
472+ _state . AddDeclaration ( projectDeclaration ) ;
473+ }
441474 }
442475 var declarationsListener = new DeclarationSymbolsListener ( qualifiedModuleName , Accessibility . Implicit , component . Type , _state . GetModuleComments ( component ) , _state . GetModuleAnnotations ( component ) , _state . GetModuleAttributes ( component ) , _projectReferences , projectDeclaration ) ;
443476 // TODO: should we unify the API? consider working like the other listeners instead of event-based
@@ -451,7 +484,10 @@ private void ResolveDeclarations(VBComponent component, IParseTree tree)
451484 } catch ( Exception exception )
452485 {
453486 Debug . Print ( "Exception thrown acquiring declarations for '{0}' (thread {2}): {1}" , component . Name , exception , Thread . CurrentThread . ManagedThreadId ) ;
454- _state . SetModuleState ( component , ParserState . ResolverError ) ;
487+ lock ( _state )
488+ {
489+ _state . SetModuleState ( component , ParserState . ResolverError ) ;
490+ }
455491 }
456492 }
457493
0 commit comments