Skip to content

Commit f5360fc

Browse files
committed
Fix a couple things
1 parent 6cc9290 commit f5360fc

File tree

7 files changed

+29
-32
lines changed

7 files changed

+29
-32
lines changed

RetailCoder.VBE/Root/RubberduckModule.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -66,6 +66,7 @@ public override void Load()
6666
Bind<IVBE>().ToConstant(_vbe);
6767
Bind<IAddIn>().ToConstant(_addin);
6868
Bind<App>().ToSelf().InSingletonScope();
69+
Bind<ParserStateChangeCallbackManager>().ToSelf().InSingletonScope();
6970
Bind<RubberduckParserState>().ToSelf().InSingletonScope();
7071
Bind<ISelectionChangeService>().To<SelectionChangeService>().InSingletonScope();
7172
Bind<ISourceControlProvider>().To<GitProvider>();
@@ -101,7 +102,6 @@ public override void Load()
101102
Bind<Func<IIndenterSettings>>().ToMethod(t => () => KernelInstance.Get<IGeneralConfigService>().LoadConfiguration().UserSettings.IndenterSettings);
102103

103104
BindCustomDeclarationLoadersToParser();
104-
Rebind<IParserStateChangeCallbackManager>().To<ParserStateChangeCallbackManager>().InSingletonScope();
105105
Rebind<IParseCoordinator>().To<ParseCoordinator>().InSingletonScope().WithConstructorArgument("serializedDeclarationsPath", (string)null);
106106
Bind<Func<IVBAPreprocessor>>().ToMethod(p => () => new VBAPreprocessor(double.Parse(_vbe.Version, CultureInfo.InvariantCulture)));
107107

Rubberduck.Parsing/Rubberduck.Parsing.csproj

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -335,7 +335,6 @@
335335
<Compile Include="VBA\EnumerableExtensions.cs" />
336336
<Compile Include="VBA\IAttributeParser.cs" />
337337
<Compile Include="VBA\IModuleExporter.cs" />
338-
<Compile Include="VBA\IParserStateChangeCallbackManager.cs" />
339338
<Compile Include="VBA\ParserStateChangeCallbackManager.cs" />
340339
<Compile Include="VBA\ModuleState.cs" />
341340
<Compile Include="VBA\ParseErrorEventArgs.cs" />

Rubberduck.Parsing/VBA/IParserStateChangeCallbackManager.cs

Lines changed: 0 additions & 12 deletions
This file was deleted.

Rubberduck.Parsing/VBA/ParseCoordinator.cs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -40,7 +40,7 @@ private readonly IDictionary<IVBComponent, IDictionary<Tuple<string, Declaration
4040
private readonly IAttributeParser _attributeParser;
4141
private readonly Func<IVBAPreprocessor> _preprocessorFactory;
4242
private readonly IEnumerable<ICustomDeclarationLoader> _customDeclarationLoaders;
43-
private readonly IParserStateChangeCallbackManager _callbackManager;
43+
private readonly ParserStateChangeCallbackManager _callbackManager;
4444
private static readonly Logger Logger = LogManager.GetCurrentClassLogger();
4545

4646
private readonly bool _isTestScope;
@@ -53,7 +53,7 @@ public ParseCoordinator(
5353
IAttributeParser attributeParser,
5454
Func<IVBAPreprocessor> preprocessorFactory,
5555
IEnumerable<ICustomDeclarationLoader> customDeclarationLoaders,
56-
IParserStateChangeCallbackManager callbackManager,
56+
ParserStateChangeCallbackManager callbackManager,
5757
bool isTestScope = false,
5858
string serializedDeclarationsPath = null)
5959
{

Rubberduck.Parsing/VBA/ParserState.cs

Lines changed: 11 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -9,46 +9,46 @@ public enum ParserState
99
/// <summary>
1010
/// Parse was requested but hasn't started yet.
1111
/// </summary>
12-
Pending = 0,
12+
Pending = 1,
1313
/// <summary>
1414
/// Project references are being loaded into parser state.
1515
/// </summary>
16-
LoadingReference = 1,
16+
LoadingReference = 2,
1717
/// <summary>
1818
/// Code from modified modules is being parsed.
1919
/// </summary>
20-
Parsing = 2,
20+
Parsing = 4,
2121
/// <summary>
2222
/// Parse tree is waiting to be walked for identifier resolution.
2323
/// </summary>
24-
Parsed = 4,
24+
Parsed = 8,
2525
/// <summary>
2626
/// Resolving declarations.
2727
/// </summary>
28-
ResolvingDeclarations = 8,
28+
ResolvingDeclarations = 16,
2929
/// <summary>
3030
/// Resolved declarations.
3131
/// </summary>
32-
ResolvedDeclarations = 16,
32+
ResolvedDeclarations = 32,
3333
/// <summary>
3434
/// Resolving identifier references.
3535
/// </summary>
36-
ResolvingReferences = 32,
36+
ResolvingReferences = 64,
3737
/// <summary>
3838
/// Parser state is in sync with the actual code in the VBE.
3939
/// </summary>
40-
Ready = 64,
40+
Ready = 128,
4141
/// <summary>
4242
/// Parsing could not be completed for one or more modules.
4343
/// </summary>
44-
Error = 128,
44+
Error = 256,
4545
/// <summary>
4646
/// Parsing completed, but identifier references could not be resolved for one or more modules.
4747
/// </summary>
48-
ResolverError = 256,
48+
ResolverError = 512,
4949
/// <summary>
5050
/// This component doesn't need a state. Use for built-in declarations.
5151
/// </summary>
52-
None = 512,
52+
None = 1024,
5353
}
5454
}

Rubberduck.Parsing/VBA/ParserStateChangeCallbackManager.cs

Lines changed: 13 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -6,13 +6,16 @@
66

77
namespace Rubberduck.Parsing.VBA
88
{
9-
public class ParserStateChangeCallbackManager : IParserStateChangeCallbackManager
9+
public class ParserStateChangeCallbackManager
1010
{
11+
private readonly bool _runAsync;
12+
1113
private readonly Dictionary<ParserState, ConcurrentDictionary<Action<CancellationToken>, byte>> _callbacks =
1214
new Dictionary<ParserState, ConcurrentDictionary<Action<CancellationToken>, byte>>();
1315

14-
public ParserStateChangeCallbackManager()
16+
public ParserStateChangeCallbackManager(bool runAsync = true)
1517
{
18+
_runAsync = runAsync;
1619
foreach (ParserState value in Enum.GetValues(typeof(ParserState)))
1720
{
1821
_callbacks.Add(value, new ConcurrentDictionary<Action<CancellationToken>, byte>());
@@ -61,7 +64,14 @@ public void RunCallbacks(ParserState state, CancellationToken token)
6164
{
6265
if (token.IsCancellationRequested) { break; }
6366

64-
Task.Run(() => callback(token), token);
67+
if (_runAsync)
68+
{
69+
Task.Run(() => callback(token), token);
70+
}
71+
else
72+
{
73+
callback(token);
74+
}
6575
}
6676
}
6777
}

Rubberduck.Parsing/VBA/RubberduckParserState.cs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -69,9 +69,9 @@ public void UnregisterCallback(Action<CancellationToken> callback)
6969
}
7070

7171
private readonly IVBE _vbe;
72-
private readonly IParserStateChangeCallbackManager _callbackManager;
72+
private readonly ParserStateChangeCallbackManager _callbackManager;
7373

74-
public RubberduckParserState(IVBE vbe, IParserStateChangeCallbackManager callbackManager)
74+
public RubberduckParserState(IVBE vbe, ParserStateChangeCallbackManager callbackManager)
7575
{
7676
var values = Enum.GetValues(typeof(ParserState));
7777
foreach (var value in values)

0 commit comments

Comments
 (0)