Skip to content

Commit

Permalink
Make a clean separation of concerns among three issues --- caching of…
Browse files Browse the repository at this point in the history
… the types, querying service for the type library, and obtaining a type to mock. Introduce CachedTypeService to manage the cache of types created via reflection/type library APIs to ensure equivalence of types for a session lifetime. See the comments in the class for details.
  • Loading branch information
bclothier committed Jan 17, 2019
1 parent b152adb commit ba31c13
Show file tree
Hide file tree
Showing 5 changed files with 214 additions and 87 deletions.
51 changes: 11 additions & 40 deletions Rubberduck.Main/ComClientLibrary/UnitTesting/Mocks/MockProvider.cs
Original file line number Diff line number Diff line change
@@ -1,5 +1,4 @@
using System;
using System.Collections.Concurrent;
using System.Linq;
using System.Runtime.InteropServices;
using System.Runtime.InteropServices.ComTypes;
Expand Down Expand Up @@ -40,7 +39,7 @@ public interface IMockProvider
]
public class MockProvider : IMockProvider
{
private static readonly ConcurrentDictionary<string, Type> typeCache = new ConcurrentDictionary<string, Type>();
private static readonly ICachedTypeService TypeCache = CachedTypeService.Instance;

public MockProvider()
{
Expand All @@ -49,8 +48,7 @@ public MockProvider()

public IComMock Mock(string ProgId, string ProjectName = null)
{
var key = string.Concat(ProjectName?.ToLowerInvariant(), "::", ProgId.ToLowerInvariant());
if (!typeCache.TryGetValue(key, out var classType))
if (!TypeCache.TryGetCachedType(ProgId, ProjectName, out var classType))
{
// In order to mock a COM type, we must acquire a Type. However,
// ProgId will only return the coclass, which itself is a collection
Expand All @@ -63,26 +61,7 @@ public IComMock Mock(string ProgId, string ProjectName = null)
if (classType == null)
{
throw new ArgumentOutOfRangeException(nameof(ProgId),
$"The supplied {ProgId} was not found. The class may not be registered.");
}

if (classType.Name == "__ComObject")
{
var service = TypeLibQueryService.Instance;
if (service.TryGetTypeInfoFromProgId(ProgId, out classType))
{
if (classType == null)
{
throw new ArgumentOutOfRangeException(nameof(ProgId),
$"The supplied {ProgId} was found, but we could not acquire the required metadata on the type to mock it. The class may not support early-binding.");
}
}
}

typeCache.TryAdd(key, classType);
foreach (var face in classType.GetInterfaces())
{
typeCache.TryAdd(ProjectName + "::" + face.FullName, face);
$"The supplied {ProgId} was not found. The class may not be registered or could not be located with the available metadata.");
}
}

Expand Down Expand Up @@ -155,36 +134,28 @@ private static Type GetComDefaultInterface(Type classType)
return targetType;
}

private static Type GetVbaType(string ProgId, string ProjectName)
private static Type GetVbaType(string progId, string projectName)
{
Type classType = null;

if (!TryGetVbeProject(ProjectName, out var project))
if (!TryGetVbeProject(projectName, out var project))
{
return null;
}

var lib = TypeLibWrapper.FromVBProject(project);

foreach (var info in lib.TypeInfos)
foreach (var typeInfo in lib.TypeInfos)
{
if (info.Name != ProgId)
if (typeInfo.Name != progId)
{
continue;
}

var typeInfo = (ITypeInfo) info;
var pTypeInfo = Marshal.GetComInterfaceForObject(typeInfo, typeof(ITypeInfo));

// TODO: find out why this crashes with NRE; the pointer seems to be valid, but
// the exception comes from deep within the mscorlib assembly. It might not
// be liking some of funkiness that the VBA class typeinfo generates.
//
// Note: Tried both TypeLibConverter class and TypeToTypeInfoMarshaler class;
// all go into the same code path that throws NRE.
classType = Marshal.GetTypeForITypeInfo(pTypeInfo);
Marshal.Release(pTypeInfo);
break;
if (TypeCache.TryGetCachedType(typeInfo, projectName, out classType))
{
break;
}
}

return classType;
Expand Down
3 changes: 3 additions & 0 deletions Rubberduck.Main/Root/RubberduckIoCInstaller.cs
Original file line number Diff line number Diff line change
Expand Up @@ -43,6 +43,7 @@
using Rubberduck.AutoComplete;
using Rubberduck.AutoComplete.Service;
using Rubberduck.CodeAnalysis.CodeMetrics;
using Rubberduck.Parsing.ComReflection.TypeLibReflection;
using Rubberduck.Parsing.Rewriter;
using Rubberduck.Parsing.VBA.ComReferenceLoading;
using Rubberduck.Parsing.VBA.DeclarationResolving;
Expand Down Expand Up @@ -859,6 +860,8 @@ private void RegisterConstantVbeAndAddIn(IWindsorContainer container)
container.Register(Component.For<IUiContextProvider>().Instance(UiContextProvider.Instance()).LifestyleSingleton());
container.Register(Component.For<IVBEEvents>().Instance(VBEEvents.Initialize(_vbe)).LifestyleSingleton());
container.Register(Component.For<ITempSourceFileHandler>().Instance(_vbe.TempSourceFileHandler));
container.Register(Component.For<ICachedTypeService>().Instance(CachedTypeService.Instance).LifestyleSingleton());
container.Register(Component.For<ITypeLibQueryService>().Instance(TypeLibQueryService.Instance).LifestyleSingleton());
}
}
}
Original file line number Diff line number Diff line change
@@ -0,0 +1,180 @@
using System;
using System.Collections.Concurrent;
using System.Linq;
using System.Runtime.InteropServices;
using System.Runtime.InteropServices.ComTypes;
using Rubberduck.VBEditor.Utility;
using TYPEATTR = System.Runtime.InteropServices.ComTypes.TYPEATTR;

namespace Rubberduck.Parsing.ComReflection.TypeLibReflection
{
/// <summary>
/// Provide caching service for types that should be considered equivalent.
/// </summary>
/// <remarks>
/// The provider aims to work around a deficiency in the <see cref="Type.IsEquivalentTo"/>, particularly for
/// COM interop types. The issue is that when we create a <see cref="Type"/> derived from methods such as
/// <see cref="Marshal.GetTypeForITypeInfo"/> or <see cref="Type.GetTypeFromProgID(string)"/>, new types are
/// returned for each invocation, even for the same ProgID or ITypeInfo. That will cause problems later such
/// as being unable to cast an instance from one type to another, even though they are based on exactly the
/// same ProgID/ITypeInfo/etc.. In those cases, the <see cref="Type.IsEquivalentTo"/> incorrectly returns
/// false. Thus, those methods should be wrapped in the <see cref="TryCacheType"/> methods to ensure that
/// the repeated invocation will continue to return exactly same <see cref="Type"/>.
///
/// For details on the issue with the <see cref="Type.IsEquivalentTo"/>, refer to:
/// https://developercommunity.visualstudio.com/content/problem/422208/typeisequivalent-does-not-behave-according-to-the.html
/// </remarks>
public interface ICachedTypeService
{
bool TryGetCachedType(string progId, out Type type);
bool TryGetCachedType(string progId, string project, out Type type);
bool TryGetCachedType(ITypeInfo typeInfo, out Type type);
bool TryGetCachedType(ITypeInfo typeInfo, string project, out Type type);
}

public class CachedTypeService : ICachedTypeService
{
private static readonly ConcurrentDictionary<string, Type> TypeCache;
private static readonly Lazy<CachedTypeService> LazyInstance;
private static readonly ITypeLibQueryService QueryService;

static CachedTypeService()
{
TypeCache = new ConcurrentDictionary<string, Type>();
LazyInstance = new Lazy<CachedTypeService>(() => new CachedTypeService());
QueryService = TypeLibQueryService.Instance;
}

/// <summary>
/// Provided primarily for uses outside the CW's DI, mainly within Rubberduck.Main.
/// </summary>
public static ICachedTypeService Instance => LazyInstance.Value;

public bool TryGetCachedType(string progId, out Type type)
{
return TryGetCachedType(progId, null, out type);
}

public bool TryGetCachedType(string progId, string project, out Type type)
{
var key = CreateQualifiedIdentifier(progId, project);
if (!TypeCache.TryGetValue(key, out type))
{
type = Type.GetTypeFromProgID(progId);
if (type != null)
{
if (!TryAddTypeInternal(progId, project, ref type))
{
type = null;
}
}
}

return type != null;
}

public bool TryGetCachedType(ITypeInfo typeInfo, out Type type)
{
return TryGetCachedType(typeInfo, null, out type);
}

public bool TryGetCachedType(ITypeInfo typeInfo, string project, out Type type)
{
typeInfo.GetTypeAttr(out var pAttr);
if (pAttr != IntPtr.Zero)
{
using (DisposalActionContainer.Create(pAttr, typeInfo.ReleaseTypeAttr))
{
var attr = Marshal.PtrToStructure<TYPEATTR>(pAttr);
var clsid = attr.guid;
if (QueryService.TryGetProgIdFromClsid(clsid, out var progId))
{
return TryGetCachedType(typeInfo, progId, project, out type);
}
}
}

var typeName = Marshal.GetTypeInfoName(typeInfo);
typeInfo.GetContainingTypeLib(out var typeLib, out _);
var libName = Marshal.GetTypeLibName(typeLib);

return TryGetCachedType(typeInfo, string.Concat(libName, ".", typeName), project, out type);
}

private bool TryGetCachedType(ITypeInfo typeInfo, string progId, string project, out Type type)
{
var key = CreateQualifiedIdentifier(progId, project);
if (TypeCache.TryGetValue(key, out type))
{
return type != null;
}

var ptr = Marshal.GetComInterfaceForObject(typeInfo, typeof(ITypeInfo));
if (ptr == IntPtr.Zero)
{
return false;
}

using (DisposalActionContainer.Create(ptr, x => Marshal.Release(x)))
{
type = Marshal.GetTypeForITypeInfo(ptr);
if (type == null)
{
return false;
}

if (!TryAddTypeInternal(progId, project, ref type))
{
return false;
}
}

return type != null;
}

/// <summary>
/// Because a <see cref="Type"/> can have several interfaces and those may be further used in
/// downstream operations, it's important to also cache those interfaces to ensure we do not
/// return a different type for a given interface that's implemented by the cached type.
///
/// Additionally, we ensure that we do not cache any <see cref="System.__ComObject"/> types
/// as those are not useful in production. In that case, we must discover the type library
/// using the <see cref="TypeLibQueryService"/> and call <see cref="Marshal.GetTypeForITypeInfo"/>.
/// </summary>
/// <returns>True if the type and all its interface were added. False otherwise</returns>
private bool TryAddTypeInternal(string progId, string project, ref Type type)
{
// Ensure we do not cache the generic System.__ComObject, which is useless.
if (type.Name == "__ComObject")
{
return QueryService.TryGetTypeInfoFromProgId(progId, out var typeInfo)
&& TryGetCachedType(typeInfo, progId, project, out type);
}

if (!TypeCache.TryAdd(CreateQualifiedIdentifier(progId, project), type))
{
return false;
}

return type.GetInterfaces()
.Where(face => face.FullName != null)
.All(face => TypeCache.TryAdd(CreateQualifiedIdentifier(face.FullName, project), face));
}

/// <summary>
/// Creates a qualified identifier to uniquely identify a cached type, with optional scoping. Case insensitive.
/// </summary>
/// <remarks>
/// A typical use is to distinguish the types by its ProgID / <see cref="Type.FullName"/>. However,
/// if a type comes from a private project there is a potential for a collision. In that case, the
/// optional project should be filled in.
/// </remarks>
/// <param name="progId">Unique name for the type.</param>
/// <param name="project">Indicates whether the type belongs to a privately scoped project. Leave null to indicate it's global</param>
/// <returns>A fully qualified identifier</returns>
private static string CreateQualifiedIdentifier(string progId, string project)
{
return string.Concat(project?.ToLowerInvariant(), "::", progId.ToLowerInvariant());
}
}
}
Original file line number Diff line number Diff line change
@@ -1,42 +1,44 @@
using System;
using System.Collections.Concurrent;
using System.IO;
using System.Runtime.InteropServices;
using System.Runtime.InteropServices.ComTypes;
using Microsoft.Win32;

namespace Rubberduck.Parsing.ComReflection.TypeLibReflection
{
public class TypeLibQueryService
public interface ITypeLibQueryService
{
bool TryGetProgIdFromClsid(Guid clsid, out string progId);
bool TryGetTypeInfoFromProgId(string progId, out ITypeInfo typeInfo);
}

public class TypeLibQueryService : ITypeLibQueryService
{
[DllImport("ole32.dll", CharSet = CharSet.Unicode, ExactSpelling = true, PreserveSig = true)]
private static extern int CLSIDFromProgID(string lpszProgID, out Guid lpclsid);

[DllImport("ole32.dll", CharSet = CharSet.Unicode, ExactSpelling = true, PreserveSig = true)]
private static extern int ProgIDFromCLSID([In]ref Guid clsid, [MarshalAs(UnmanagedType.LPWStr)]out string lplpszProgID);

[DllImport("oleaut32.dll", CharSet = CharSet.Unicode, ExactSpelling = true, PreserveSig = true)]
private static extern int LoadTypeLib(string fileName, out ITypeLib typeLib);

private static readonly Lazy<TypeLibQueryService> LazyInstance = new Lazy<TypeLibQueryService>();
private static readonly RegisteredLibraryFinderService Finder = new RegisteredLibraryFinderService();

/// <summary>
/// The types returned by the <see cref="Marshal.GetTypeForITypeInfo"/> are not equivalent. For that reason
/// we must cache all types to ensure that any objects we create will be castable accordingly. We must also
/// collect all implementing interfaces for the same reasons.
/// </summary>
private static readonly ConcurrentDictionary<string, Type> TypeCache = new ConcurrentDictionary<string, Type>();

/// <summary>
/// Provided primarily for uses outside the CW's DI, mainly within Rubberduck.Main.
/// </summary>
public static TypeLibQueryService Instance => LazyInstance.Value;
public static ITypeLibQueryService Instance => LazyInstance.Value;

public bool TryGetTypeInfoFromProgId(string progId, out Type type)
public bool TryGetProgIdFromClsid(Guid clsid, out string progId)
{
if (TypeCache.TryGetValue(progId, out type))
{
return true;
}
return ProgIDFromCLSID(ref clsid, out progId) == 0;
}

public bool TryGetTypeInfoFromProgId(string progId, out ITypeInfo typeInfo)
{
typeInfo = null;
if (CLSIDFromProgID(progId, out var clsid) != 0)
{
return false;
Expand All @@ -47,37 +49,8 @@ public bool TryGetTypeInfoFromProgId(string progId, out Type type)
return false;
}

lib.GetTypeInfoOfGuid(ref clsid, out var typeInfo);
var pUnk = IntPtr.Zero;
try
{
pUnk = Marshal.GetIUnknownForObject(typeInfo);
type = Marshal.GetTypeForITypeInfo(pUnk);

if (type == null)
{
return false;
}

if (!TypeCache.TryAdd(progId, type))
{
return false;
}

foreach (var face in type.GetInterfaces())
{
if (face.FullName != null)
{
TypeCache.TryAdd(face.FullName, face);
}
}

return type != null;
}
finally
{
if(pUnk!=IntPtr.Zero) Marshal.Release(pUnk);
}
lib.GetTypeInfoOfGuid(ref clsid, out typeInfo);
return typeInfo != null;
}

private static bool TryGetTypeLibFromClsid(Guid clsid, out ITypeLib lib)
Expand Down

0 comments on commit ba31c13

Please sign in to comment.