@@ -28,6 +28,7 @@ public RubberduckParserState State
28
28
}
29
29
30
30
private readonly CancellationTokenSource _central = new CancellationTokenSource ( ) ;
31
+ private readonly CancellationTokenSource _resolverTokenSource ; // linked to _central later
31
32
private readonly Dictionary < VBComponent , Tuple < Task , CancellationTokenSource > > _currentTasks = new Dictionary < VBComponent , Tuple < Task , CancellationTokenSource > > ( ) ;
32
33
33
34
private readonly Dictionary < VBComponent , IParseTree > _parseTrees = new Dictionary < VBComponent , IParseTree > ( ) ;
@@ -46,6 +47,7 @@ private readonly IDictionary<VBComponent, IDictionary<Tuple<string, DeclarationT
46
47
47
48
public RubberduckParserReimpl ( VBE vbe , RubberduckParserState state , IAttributeParser attributeParser )
48
49
{
50
+ _resolverTokenSource = CancellationTokenSource . CreateLinkedTokenSource ( _central . Token ) ;
49
51
_vbe = vbe ;
50
52
_state = state ;
51
53
_attributeParser = attributeParser ;
@@ -135,12 +137,11 @@ public void Cancel(VBComponent component = null)
135
137
}
136
138
else
137
139
{
140
+ _resolverTokenSource . Cancel ( false ) ;
138
141
Tuple < Task , CancellationTokenSource > result ;
139
142
if ( _currentTasks . TryGetValue ( component , out result ) )
140
143
{
141
144
result . Item2 . Cancel ( false ) ;
142
- // should we do this??
143
- //result.Item1.Wait();
144
145
}
145
146
}
146
147
}
@@ -171,7 +172,8 @@ public void ParseComponent(VBComponent component, TokenStreamRewriter rewriter =
171
172
172
173
public void Resolve ( CancellationToken token )
173
174
{
174
- Task . Run ( ( ) => ResolveInternal ( token ) ) ;
175
+ var sharedTokenSource = CancellationTokenSource . CreateLinkedTokenSource ( _resolverTokenSource . Token , token ) ;
176
+ Task . Run ( ( ) => ResolveInternal ( sharedTokenSource . Token ) ) ;
175
177
}
176
178
177
179
private void ResolveInternal ( CancellationToken token )
@@ -197,6 +199,7 @@ private void ResolveDeclarations(VBComponent component, IParseTree tree)
197
199
var declarations = new List < Declaration > ( ) ;
198
200
var qualifiedModuleName = new QualifiedModuleName ( component ) ;
199
201
DeclarationSymbolsListener declarationsListener = new DeclarationSymbolsListener ( qualifiedModuleName , Accessibility . Implicit , component . Type , _state . GetModuleComments ( component ) , _state . getModuleAttributes ( component ) ) ;
202
+ // TODO: should we unify the API? consider working like the other listeners instead of event-based
200
203
declarationsListener . NewDeclaration += ( sender , e ) => _state . AddDeclaration ( e . Declaration ) ;
201
204
declarationsListener . CreateModuleDeclarations ( ) ;
202
205
@@ -211,16 +214,14 @@ private void ResolveDeclarations(VBComponent component, IParseTree tree)
211
214
obsoleteLetStatementListener ,
212
215
emptyStringLiteralListener ,
213
216
argListWithOneByRefParamListener ,
214
-
215
217
declarationsListener ,
216
218
} ) , tree ) ;
217
219
218
220
// FIXME this are actually (almost) isnpection results.. we should handle them as such
219
221
_state . ArgListsWithOneByRefParam = argListWithOneByRefParamListener . Contexts . Select ( context => new QualifiedContext ( qualifiedModuleName , context ) ) ;
220
222
_state . EmptyStringLiterals = emptyStringLiteralListener . Contexts . Select ( context => new QualifiedContext ( qualifiedModuleName , context ) ) ;
221
223
_state . ObsoleteLetContexts = obsoleteLetStatementListener . Contexts . Select ( context => new QualifiedContext ( qualifiedModuleName , context ) ) ;
222
- _state . ObsoleteCallContexts = obsoleteCallStatementListener . Contexts . Select ( context => new QualifiedContext ( qualifiedModuleName , context ) ) ;
223
-
224
+ _state . ObsoleteCallContexts = obsoleteCallStatementListener . Contexts . Select ( context => new QualifiedContext ( qualifiedModuleName , context ) )
224
225
}
225
226
226
227
private void ResolveReferences ( DeclarationFinder finder , VBComponent component , IParseTree tree )
0 commit comments