Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
Show all changes
16 commits
Select commit Hold shift + click to select a range
baad9b8
Split the ReferencedDeclarationsCollector into a SerializedReferenced…
MDoerner Aug 5, 2018
8ed868d
Removed the unused RubberduckParserState.CoClasses member.
MDoerner Aug 9, 2018
b187103
Introduced the SerializedProjectBuilder and made the SerializeDeclara…
MDoerner Aug 13, 2018
77db2a9
Removed generating serialized projects from the com collector.
MDoerner Aug 13, 2018
75242e9
Fixed error identifying QMNs belonging to modules of a project in the…
MDoerner Aug 13, 2018
c6a600a
Merge branch 'next' into SomeRefactoringOfTheComCollector
MDoerner Aug 13, 2018
48f3b25
Made the SerializableProjectBuilder build the trees with the children…
MDoerner Aug 14, 2018
411ce4c
Sort children of serializable declarations at a better place.
MDoerner Aug 14, 2018
ef6ea2c
Made the string Scope distinct between property get, let and set for …
MDoerner Aug 15, 2018
72d8a23
Fixed introduce and remove parameter refactoring relying on the scope…
MDoerner Aug 15, 2018
5d2093d
Fixed stupid oversight when changing the scope strings.
MDoerner Aug 15, 2018
8957688
Introduced ReferenceInfo and refactored the ComReferenceSynchonizerBa…
MDoerner Aug 16, 2018
adea46d
Merge branch 'next' into SomeRefactoringOfTheComCollector
MDoerner Aug 16, 2018
2d11cb0
Introduced static caching of library declaration in tests.
MDoerner Aug 17, 2018
acf4f2f
Make projectIds for referenced libraries distinct from those for user…
MDoerner Aug 18, 2018
750a766
Merge branch 'next' into SomeRefactoringOfTheComCollector
MDoerner Aug 23, 2018
File filter

Filter by extension

Filter by extension


Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
5 changes: 4 additions & 1 deletion Rubberduck.API/VBA/Parser.cs
Original file line number Diff line number Diff line change
Expand Up @@ -6,6 +6,7 @@
using System.Runtime.InteropServices;
using System.Threading;
using Rubberduck.Common;
using Rubberduck.Parsing.ComReflection;
using Rubberduck.Parsing.PreProcessing;
using Rubberduck.Parsing.Rewriter;
using Rubberduck.Parsing.Symbols.DeclarationLoaders;
Expand Down Expand Up @@ -116,7 +117,9 @@ internal Parser(object vbe) : this()
var parserStateManager = new ParserStateManager(_state);
var referenceRemover = new ReferenceRemover(_state, moduleToModuleReferenceManager);
var supertypeClearer = new SupertypeClearer(_state);
var comSynchronizer = new COMReferenceSynchronizer(_state, parserStateManager);
var comLibraryProvider = new ComLibraryProvider();
var referencedDeclarationsCollector = new LibraryReferencedDeclarationsCollector(comLibraryProvider);
var comSynchronizer = new COMReferenceSynchronizer(_state, parserStateManager, projectRepository, referencedDeclarationsCollector);
var builtInDeclarationLoader = new BuiltInDeclarationLoader(
_state,
new List<ICustomDeclarationLoader>
Expand Down
Original file line number Diff line number Diff line change
@@ -1,5 +1,6 @@
using System;
using System.IO;
using System.Linq;
using NLog;
using Rubberduck.Parsing.ComReflection;
using Rubberduck.Parsing.Symbols;
Expand All @@ -22,12 +23,14 @@ public class SerializeDeclarationsCommand : CommandBase
{
private readonly RubberduckParserState _state;
private readonly IPersistable<SerializableProject> _service;
private readonly ISerializableProjectBuilder _serializableProjectBuilder;

public SerializeDeclarationsCommand(RubberduckParserState state, IPersistable<SerializableProject> service)
public SerializeDeclarationsCommand(RubberduckParserState state, IPersistable<SerializableProject> service, ISerializableProjectBuilder serializableProjectBuilder)
: base(LogManager.GetCurrentClassLogger())
{
_state = state;
_service = service;
_serializableProjectBuilder = serializableProjectBuilder;
}

protected override bool EvaluateCanExecute(object parameter)
Expand All @@ -43,15 +46,14 @@ protected override void OnExecute(object parameter)
var path = Path.Combine(BasePath, "Declarations");
if (!Directory.Exists(path)) { Directory.CreateDirectory(path); }

foreach (var tree in _state.BuiltInDeclarationTrees)
foreach (var project in _state.DeclarationFinder.BuiltInDeclarations(DeclarationType.Project).OfType<ProjectDeclaration>())
{
System.Diagnostics.Debug.Assert(path != null, "project path isn't supposed to be null");

var filename = string.Format("{0}.{1}.{2}.xml",
tree.Node.QualifiedMemberName.QualifiedModuleName.ProjectName,
tree.MajorVersion,
tree.MinorVersion);
_service.Persist(Path.Combine(path, filename), tree);
var tree = _serializableProjectBuilder.SerializableProject(project);
var filename = $"{tree.Node.QualifiedMemberName.QualifiedModuleName.ProjectName}.{tree.MajorVersion}.{tree.MinorVersion}.xml";
var fullFilename = Path.Combine(path, filename);
_service.Persist(fullFilename, tree);
}
}
}
Expand Down
6 changes: 6 additions & 0 deletions Rubberduck.Main/Root/RubberduckIoCInstaller.cs
Original file line number Diff line number Diff line change
Expand Up @@ -818,6 +818,12 @@ private void RegisterParsingEngine(IWindsorContainer container)
container.Register(Component.For<IParseCoordinator>()
.ImplementedBy<ParseCoordinator>()
.LifestyleSingleton());
container.Register(Component.For<IComLibraryProvider>()
.ImplementedBy<ComLibraryProvider>()
.LifestyleSingleton());
container.Register(Component.For<IReferencedDeclarationsCollector>()
.ImplementedBy<LibraryReferencedDeclarationsCollector>()
.LifestyleSingleton());
container.Register(Component.For<ITokenStreamPreprocessor>()
.ImplementedBy<VBAPreprocessor>()
.DependsOn(Dependency.OnComponent<ITokenStreamParser, VBAPreprocessorParser>())
Expand Down
44 changes: 44 additions & 0 deletions Rubberduck.Parsing/ComReflection/ComLibraryProvider.cs
Original file line number Diff line number Diff line change
@@ -0,0 +1,44 @@
using System.Runtime.InteropServices;
using System.Runtime.InteropServices.ComTypes;

namespace Rubberduck.Parsing.ComReflection
{
public class ComLibraryProvider : IComLibraryProvider
{
#region Native Stuff
// ReSharper disable InconsistentNaming
// ReSharper disable UnusedMember.Local
/// <summary>
/// Controls how a type library is registered.
/// </summary>
private enum REGKIND
{
/// <summary>
/// Use default register behavior.
/// </summary>


REGKIND_DEFAULT = 0,
/// <summary>
/// Register this type library.
/// </summary>
REGKIND_REGISTER = 1,
/// <summary>
/// Do not register this type library.
/// </summary>
REGKIND_NONE = 2
}
// ReSharper restore UnusedMember.Local

[DllImport("oleaut32.dll", CharSet = CharSet.Unicode)]
private static extern int LoadTypeLibEx(string strTypeLibName, REGKIND regKind, out ITypeLib TypeLib);
// ReSharper restore InconsistentNaming
#endregion

public ITypeLib LoadTypeLibrary(string libraryPath)
{
LoadTypeLibEx(libraryPath, REGKIND.REGKIND_NONE, out var typeLibrary);
return typeLibrary;
}
}
}
9 changes: 9 additions & 0 deletions Rubberduck.Parsing/ComReflection/IComLibraryProvider.cs
Original file line number Diff line number Diff line change
@@ -0,0 +1,9 @@
using System.Runtime.InteropServices.ComTypes;

namespace Rubberduck.Parsing.ComReflection
{
public interface IComLibraryProvider
{
ITypeLib LoadTypeLibrary(string libraryPath);
}
}
Original file line number Diff line number Diff line change
@@ -0,0 +1,11 @@
using System.Collections.Generic;
using Rubberduck.Parsing.Symbols;
using Rubberduck.VBEditor;

namespace Rubberduck.Parsing.ComReflection
{
public interface IReferencedDeclarationsCollector
{
IReadOnlyCollection<Declaration> CollectedDeclarations(ReferenceInfo reference);
}
}
Original file line number Diff line number Diff line change
@@ -0,0 +1,9 @@
using Rubberduck.Parsing.Symbols;

namespace Rubberduck.Parsing.ComReflection
{
public interface ISerializableProjectBuilder
{
SerializableProject SerializableProject(ProjectDeclaration projectDeclaration);
}
}
Loading