Skip to content

Commit 0fd436d

Browse files
committed
Merge branch 'next' of https://github.com/rubberduck-vba/Rubberduck into refactorInspections
2 parents be4f88a + 9a9c1d7 commit 0fd436d

File tree

56 files changed

+3069
-838
lines changed

Some content is hidden

Large Commits have some content hidden by default. Use the searchbox below for content that may be hidden.

56 files changed

+3069
-838
lines changed

RetailCoder.VBE/API/ParserState.cs

Lines changed: 43 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -67,15 +67,50 @@ public void Initialize(Microsoft.Vbe.Interop.VBE vbe)
6767

6868
Func<IVBAPreprocessor> preprocessorFactory = () => new VBAPreprocessor(double.Parse(_vbe.Version, CultureInfo.InvariantCulture));
6969
_attributeParser = new AttributeParser(new ModuleExporter(), preprocessorFactory);
70-
_parser = new ParseCoordinator(_vbe, _state, _attributeParser, preprocessorFactory,
70+
var projectManager = new ProjectManager(_state, _vbe);
71+
var moduleToModuleReferenceManager = new ModuleToModuleReferenceManager(_state);
72+
var parserStateManager = new ParserStateManager(_state);
73+
var referenceRemover = new ReferenceRemover(_state, moduleToModuleReferenceManager);
74+
var comSynchronizer = new COMReferenceSynchronizer(_state, parserStateManager);
75+
var builtInDeclarationLoader = new BuiltInDeclarationLoader(
76+
_state,
7177
new List<ICustomDeclarationLoader>
72-
{
73-
new DebugDeclarations(_state),
74-
new SpecialFormDeclarations(_state),
75-
new FormEventDeclarations(_state),
76-
new AliasDeclarations(_state),
77-
//new RubberduckApiDeclarations(_state)
78-
});
78+
{
79+
new DebugDeclarations(_state),
80+
new SpecialFormDeclarations(_state),
81+
new FormEventDeclarations(_state),
82+
new AliasDeclarations(_state),
83+
//new RubberduckApiDeclarations(_state)
84+
}
85+
);
86+
var parseRunner = new ParseRunner(
87+
_state,
88+
parserStateManager,
89+
preprocessorFactory,
90+
_attributeParser);
91+
var declarationResolveRunner = new DeclarationResolveRunner(
92+
_state,
93+
parserStateManager,
94+
comSynchronizer);
95+
var referenceResolveRunner = new ReferenceResolveRunner(
96+
_state,
97+
parserStateManager,
98+
moduleToModuleReferenceManager);
99+
var parsingStageService = new ParsingStageService(
100+
comSynchronizer,
101+
builtInDeclarationLoader,
102+
parseRunner,
103+
declarationResolveRunner,
104+
referenceResolveRunner
105+
);
106+
107+
_parser = new ParseCoordinator(
108+
_state,
109+
parsingStageService,
110+
projectManager,
111+
moduleToModuleReferenceManager,
112+
parserStateManager,
113+
referenceRemover);
79114
}
80115

81116
/// <summary>

RetailCoder.VBE/Root/RubberduckModule.cs

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -102,9 +102,10 @@ public override void Load()
102102
Bind<Func<IIndenterSettings>>().ToMethod(t => () => KernelInstance.Get<IGeneralConfigService>().LoadConfiguration().UserSettings.IndenterSettings);
103103

104104
BindCustomDeclarationLoadersToParser();
105-
Rebind<IParseCoordinator>().To<ParseCoordinator>().InSingletonScope().WithConstructorArgument("serializedDeclarationsPath", (string)null);
105+
Rebind<ICOMReferenceSynchronizer>().To<COMReferenceSynchronizer>().InSingletonScope().WithConstructorArgument("serializedDeclarationsPath", (string)null);
106+
Bind<IProjectReferencesProvider>().To<COMReferenceSynchronizer>().InSingletonScope().WithConstructorArgument("serializedDeclarationsPath", (string)null);
106107
Bind<Func<IVBAPreprocessor>>().ToMethod(p => () => new VBAPreprocessor(double.Parse(_vbe.Version, CultureInfo.InvariantCulture)));
107-
108+
108109
Rebind<ISearchResultsWindowViewModel>().To<SearchResultsWindowViewModel>().InSingletonScope();
109110

110111
Bind<SourceControlViewViewModel>().ToSelf().InSingletonScope();

RetailCoder.VBE/Rubberduck.csproj

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -422,7 +422,6 @@
422422
<Compile Include="UI\EnvironmentProvider.cs" />
423423
<Compile Include="UI\Inspections\AggregateInspectionResult.cs" />
424424
<Compile Include="UI\ModernFolderBrowser.cs" />
425-
<Compile Include="UI\Refactorings\AssignedByValParameterQuickFixDialogFactory.cs" />
426425
<Compile Include="UI\Refactorings\EncapsulateField\EncapsulateFieldView.xaml.cs">
427426
<DependentUpon>EncapsulateFieldView.xaml</DependentUpon>
428427
</Compile>

RetailCoder.VBE/UI/Refactorings/AssignedByValParameterQuickFixDialog.cs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -10,10 +10,10 @@ public partial class AssignedByValParameterQuickFixDialog : Form, IAssignedByVal
1010
{
1111
private readonly IEnumerable<string> _forbiddenNames;
1212

13-
internal AssignedByValParameterQuickFixDialog(string identifierName, string declarationType, IEnumerable<string> forbiddenNames)
13+
public AssignedByValParameterQuickFixDialog(string identifier, string identifierType, IEnumerable<string> forbiddenNames)
1414
{
1515
InitializeComponent();
16-
InitializeCaptions(identifierName, declarationType);
16+
InitializeCaptions(identifier, identifierType);
1717
_forbiddenNames = forbiddenNames;
1818
}
1919

RetailCoder.VBE/UI/Refactorings/AssignedByValParameterQuickFixDialogFactory.cs

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

Rubberduck.Parsing/Rubberduck.Parsing.csproj

Lines changed: 35 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -334,11 +334,46 @@
334334
<Compile Include="Syntax\TextSpan.cs" />
335335
<Compile Include="VBA\AttributeParser.cs" />
336336
<Compile Include="VBA\Attributes.cs" />
337+
<Compile Include="VBA\BuiltInDeclarationLoader.cs" />
338+
<Compile Include="VBA\ParsingStageService.cs" />
339+
<Compile Include="VBA\CollectionExtensions.cs" />
340+
<Compile Include="VBA\IParsingStageService.cs" />
341+
<Compile Include="VBA\IProjectReferencesProvider.cs" />
342+
<Compile Include="VBA\SynchronousReferenceRemover.cs" />
343+
<Compile Include="VBA\ReferenceRemover.cs" />
344+
<Compile Include="VBA\ReferenceRemoverBase.cs" />
345+
<Compile Include="VBA\ProjectManager.cs" />
346+
<Compile Include="VBA\SynchronousReferenceResolveRunner.cs" />
347+
<Compile Include="VBA\ReferenceResolveRunner.cs" />
348+
<Compile Include="VBA\ReferenceResolveRunnerBase.cs" />
349+
<Compile Include="VBA\IReferenceRemover.cs" />
350+
<Compile Include="VBA\SynchronousDeclarationResolveRunner.cs" />
351+
<Compile Include="VBA\DeclarationResolveRunner.cs" />
352+
<Compile Include="VBA\DeclarationResolveRunnerBase.cs" />
353+
<Compile Include="VBA\SynchronousParseRunner.cs" />
354+
<Compile Include="VBA\ParseRunner.cs" />
355+
<Compile Include="VBA\ParseRunnerBase.cs" />
356+
<Compile Include="VBA\IBuiltInDeclarationLoader.cs" />
357+
<Compile Include="VBA\SynchronousCOMReferenceSynchronizer.cs" />
358+
<Compile Include="VBA\COMReferenceSynchronizer.cs" />
359+
<Compile Include="VBA\COMReferenceSynchronizerBase.cs" />
360+
<Compile Include="VBA\ParserStateManagerBase.cs" />
361+
<Compile Include="VBA\SynchronousParserStateManager.cs" />
362+
<Compile Include="VBA\ParserStateManager.cs" />
363+
<Compile Include="VBA\ModuleToModuleReferenceManagerBase.cs" />
364+
<Compile Include="VBA\ModuleToModuleReferenceManager.cs" />
337365
<Compile Include="VBA\CombinedParseTreeListener.cs" />
338366
<Compile Include="VBA\ComponentParseTask.cs" />
339367
<Compile Include="VBA\EnumerableExtensions.cs" />
340368
<Compile Include="VBA\IAttributeParser.cs" />
341369
<Compile Include="VBA\IModuleExporter.cs" />
370+
<Compile Include="VBA\IModuleToModuleReferenceManager.cs" />
371+
<Compile Include="VBA\IDeclarationResolveRunner.cs" />
372+
<Compile Include="VBA\ICOMReferenceSynchronizer.cs" />
373+
<Compile Include="VBA\IProjectManager.cs" />
374+
<Compile Include="VBA\IParserStateManager.cs" />
375+
<Compile Include="VBA\IReferenceResolveRunner.cs" />
376+
<Compile Include="VBA\IParseRunner.cs" />
342377
<Compile Include="VBA\ModuleState.cs" />
343378
<Compile Include="VBA\ParseErrorEventArgs.cs" />
344379
<Compile Include="VBA\ParserState.cs" />

Rubberduck.Parsing/Symbols/Declaration.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -564,7 +564,7 @@ public void ClearReferences()
564564
_references = new ConcurrentBag<IdentifierReference>();
565565
}
566566

567-
public void RemoveReferencesFrom(ICollection<QualifiedModuleName> modulesByWhichToRemoveReferences)
567+
public void RemoveReferencesFrom(IReadOnlyCollection<QualifiedModuleName> modulesByWhichToRemoveReferences)
568568
{
569569
//This gets replaced with a new ConcurrentBag because one cannot remove specific items from a ConcurrentBag.
570570
//Moreover, changing to a ConcurrentDictionary<IdentifierReference,byte> breaks all sorts of tests, for some obscure reason.
Lines changed: 60 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,60 @@
1+
using System;
2+
using System.Collections.Generic;
3+
using System.Linq;
4+
using NLog;
5+
using Rubberduck.Parsing.Symbols.DeclarationLoaders;
6+
using System.Threading;
7+
8+
namespace Rubberduck.Parsing.VBA
9+
{
10+
public class BuiltInDeclarationLoader : IBuiltInDeclarationLoader
11+
{
12+
private readonly IEnumerable<ICustomDeclarationLoader> _customDeclarationLoaders;
13+
private RubberduckParserState _state;
14+
15+
private static readonly Logger Logger = LogManager.GetCurrentClassLogger();
16+
17+
public BuiltInDeclarationLoader(RubberduckParserState state, IEnumerable<ICustomDeclarationLoader> customDeclarationLoaders)
18+
{
19+
if (state == null)
20+
{
21+
throw new ArgumentNullException(nameof(state));
22+
}
23+
if (customDeclarationLoaders == null)
24+
{
25+
throw new ArgumentNullException(nameof(customDeclarationLoaders));
26+
}
27+
28+
_state = state;
29+
_customDeclarationLoaders = customDeclarationLoaders;
30+
}
31+
32+
33+
public bool LastLoadOfBuiltInDeclarationsLoadedDeclarations { get; private set; }
34+
35+
36+
public void LoadBuitInDeclarations()
37+
{
38+
LastLoadOfBuiltInDeclarationsLoadedDeclarations = false;
39+
foreach (var customDeclarationLoader in _customDeclarationLoaders)
40+
{
41+
try
42+
{
43+
var customDeclarations = customDeclarationLoader.Load();
44+
if (customDeclarations.Any())
45+
{
46+
LastLoadOfBuiltInDeclarationsLoadedDeclarations = true;
47+
foreach (var declaration in customDeclarationLoader.Load())
48+
{
49+
_state.AddDeclaration(declaration);
50+
}
51+
}
52+
}
53+
catch (Exception exception)
54+
{
55+
Logger.Error(exception, "Exception thrown loading built-in declarations. (thread {0}).", Thread.CurrentThread.ManagedThreadId);
56+
}
57+
}
58+
}
59+
}
60+
}
Lines changed: 71 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,71 @@
1+
using System;
2+
using System.Collections.Generic;
3+
using System.Linq;
4+
using System.Threading;
5+
using System.Threading.Tasks;
6+
using Rubberduck.VBEditor.SafeComWrappers.Abstract;
7+
using System.Collections.Concurrent;
8+
9+
namespace Rubberduck.Parsing.VBA
10+
{
11+
public class COMReferenceSynchronizer : COMReferenceSynchronizerBase
12+
{
13+
private const int _maxReferenceLoadingConcurrency = -1;
14+
15+
public COMReferenceSynchronizer(
16+
RubberduckParserState state,
17+
IParserStateManager parserStateManager,
18+
string serializedDeclarationsPath = null)
19+
:base(
20+
state,
21+
parserStateManager,
22+
serializedDeclarationsPath)
23+
{ }
24+
25+
26+
protected override void LoadReferences(IEnumerable<IReference> referencesToLoad, ConcurrentBag<IReference> unmapped, CancellationToken token)
27+
{
28+
var referenceLoadingTaskScheduler = ThrottledTaskScheduler(_maxReferenceLoadingConcurrency);
29+
30+
//Parallel.ForEach is not used because loading the references can contain IO-bound operations.
31+
var loadTasks = new List<Task>();
32+
foreach (var reference in referencesToLoad)
33+
{
34+
loadTasks.Add(Task.Factory.StartNew(
35+
() => LoadReference(reference, unmapped),
36+
token,
37+
TaskCreationOptions.None,
38+
referenceLoadingTaskScheduler
39+
));
40+
}
41+
42+
try
43+
{
44+
Task.WaitAll(loadTasks.ToArray(), token);
45+
}
46+
catch (AggregateException exception)
47+
{
48+
if (exception.Flatten().InnerExceptions.All(ex => ex is OperationCanceledException))
49+
{
50+
throw exception.InnerException ?? exception; //This eliminates the stack trace, but for the cancellation, this is irrelevant.
51+
}
52+
_parserStateManager.SetStatusAndFireStateChanged(this, ParserState.Error, token);
53+
throw;
54+
}
55+
token.ThrowIfCancellationRequested();
56+
}
57+
58+
private TaskScheduler ThrottledTaskScheduler(int maxLevelOfConcurrency)
59+
{
60+
if (maxLevelOfConcurrency <= 0)
61+
{
62+
return TaskScheduler.Default;
63+
}
64+
else
65+
{
66+
var taskSchedulerPair = new ConcurrentExclusiveSchedulerPair(TaskScheduler.Default, maxLevelOfConcurrency);
67+
return taskSchedulerPair.ConcurrentScheduler;
68+
}
69+
}
70+
}
71+
}

0 commit comments

Comments
 (0)