Skip to content

Commit fbb5582

Browse files
ExecuteCode can now also call Private scoped procedures
added TypeInfoWrapper.Funcs.Find method removed use of reflection to invoke procedures on IDispatch to avoid access violation when debugging and VBE ends execution abruptly
1 parent 4af33c3 commit fbb5582

File tree

3 files changed

+149
-14
lines changed

3 files changed

+149
-14
lines changed

Rubberduck.VBEEditor/ComManagement/TypeLibs/TypeLibs.cs

Lines changed: 34 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -90,11 +90,6 @@ public static T ReadStructureSafe<T>(IntPtr memAddress)
9090
}
9191
}
9292

93-
public static class ComHelper
94-
{
95-
public static bool HRESULT_FAILED(int hr) => hr < 0;
96-
}
97-
9893
// RestrictComInterfaceByAggregation is used to ensure that a wrapped COM object only responds to a specific interface
9994
// In particular, we don't want them to respond to IProvideClassInfo, which is broken in the VBE for some ITypeInfo implementations
10095
public class RestrictComInterfaceByAggregation<T> : ICustomQueryInterface, IDisposable
@@ -498,6 +493,15 @@ public class FuncsCollection : IIndexedCollection<TypeInfoFunc>
498493
public FuncsCollection(TypeInfoWrapper parent) => _parent = parent;
499494
override public int Count { get => _parent.Attributes.cFuncs; }
500495
override public TypeInfoFunc GetItemByIndex(int index) => new TypeInfoFunc(_parent, index);
496+
497+
public TypeInfoFunc Find(string name, TypeInfoFunc.PROCKIND procKind)
498+
{
499+
foreach (var func in this)
500+
{
501+
if ((func.Name == name) && (func.ProcKind == procKind)) return func;
502+
}
503+
return null;
504+
}
501505
}
502506
public FuncsCollection Funcs;
503507

@@ -597,7 +601,7 @@ public TypeInfoWrapper Get(string searchTypeName)
597601
}
598602
}
599603
public ImplementedInterfacesCollection ImplementedInterfaces;
600-
604+
601605
private void InitCommon()
602606
{
603607
Funcs = new FuncsCollection(this);
@@ -767,15 +771,33 @@ public IDispatch GetStdModAccessor()
767771
throw new ArgumentException("This ITypeInfo is not hosted by the VBE, so does not support GetStdModAccessor");
768772
}
769773
}
770-
771-
public object StdModExecute(string name, Reflection.BindingFlags invokeAttr, object[] args = null)
774+
775+
public object StdModExecute(string name, object[] args = null)
772776
{
773777
if (HasVBEExtensions)
774778
{
775-
var StaticModule = GetStdModAccessor();
776-
var retVal = StaticModule.GetType().InvokeMember(name, invokeAttr, null, StaticModule, args);
777-
Marshal.ReleaseComObject(StaticModule);
778-
return retVal;
779+
// We search for the dispId using the real type info rather than using staticModule.GetIdsOfNames,
780+
// as we can then also include PRIVATE scoped procedures.
781+
var func = Funcs.Find(name, TypeInfoFunc.PROCKIND.PROCKIND_PROC);
782+
if (func == null)
783+
{
784+
throw new ArgumentException($"StdModExecute failed. Couldn't find procedure named '{name}'");
785+
}
786+
787+
var staticModule = GetStdModAccessor();
788+
789+
try
790+
{
791+
return IDispatchHelper.Invoke(staticModule, func.FuncDesc.memid, IDispatchHelper.InvokeKind.DISPATCH_METHOD, args);
792+
}
793+
catch (Exception)
794+
{
795+
throw;
796+
}
797+
finally
798+
{
799+
Marshal.ReleaseComObject(staticModule);
800+
}
779801
}
780802
else
781803
{

Rubberduck.VBEEditor/ComManagement/TypeLibs/TypeLibsAPI.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -221,7 +221,7 @@ public static object ExecuteCode(IVBComponent component, string procName, object
221221
/// <returns>object representing the VBA return value, if one was provided, or null otherwise.</returns>
222222
public static object ExecuteCode(TypeInfoWrapper standardModuleTypeInfo, string procName, object[] args = null)
223223
{
224-
return standardModuleTypeInfo.StdModExecute(procName, Reflection.BindingFlags.InvokeMethod, args);
224+
return standardModuleTypeInfo.StdModExecute(procName, args);
225225
}
226226

227227
/// <summary>

Rubberduck.VBEEditor/ComManagement/TypeLibs/TypeLibsAbstract.cs

Lines changed: 114 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -5,9 +5,121 @@
55
namespace Rubberduck.VBEditor.ComManagement.TypeLibsAbstract
66
{
77
[ComImport(), Guid("00020400-0000-0000-C000-000000000046")]
8-
[InterfaceType(ComInterfaceType.InterfaceIsIDispatch)]
8+
[InterfaceType(ComInterfaceType.InterfaceIsIUnknown)]
99
public interface IDispatch
1010
{
11+
[PreserveSig] int GetTypeInfoCount([Out] out uint pctinfo);
12+
[PreserveSig] int GetTypeInfo([In] uint iTInfo, [In] uint lcid, [Out] out ComTypes.ITypeInfo pTypeInfo);
13+
[PreserveSig] int GetIDsOfNames([In] ref Guid riid, [In] string[] rgszNames, [In] uint cNames, [In] uint lcid, [Out] out int[] rgDispId);
14+
15+
[PreserveSig]
16+
int Invoke([In] int dispIdMember,
17+
[In] ref Guid riid,
18+
[In] uint lcid,
19+
[In] uint dwFlags,
20+
[In, Out] ref ComTypes.DISPPARAMS pDispParams,
21+
[Out] out Object pVarResult,
22+
[In, Out] ref ComTypes.EXCEPINFO pExcepInfo,
23+
[Out] out uint pArgErr);
24+
}
25+
26+
public static class ComHelper
27+
{
28+
public static bool HRESULT_FAILED(int hr) => hr < 0;
29+
}
30+
31+
public static class IDispatchHelper
32+
{
33+
static Guid GUID_NULL = new Guid();
34+
35+
public enum InvokeKind : int
36+
{
37+
DISPATCH_METHOD = 1,
38+
DISPATCH_PROPERTYGET = 2,
39+
DISPATCH_PROPERTYPUT = 4,
40+
DISPATCH_PROPERTYPUTREF = 8,
41+
}
42+
43+
[StructLayout(LayoutKind.Sequential)]
44+
public struct VARIANT
45+
{
46+
short vt;
47+
short reserved1;
48+
short reserved2;
49+
short reserved3;
50+
IntPtr data1;
51+
IntPtr data2;
52+
}
53+
54+
// Convert input args into a contigious array of real COM VARIANTs for the DISPPARAMS struct
55+
private static ComTypes.DISPPARAMS PrepareDispatchArgs(object[] args)
56+
{
57+
var pDispParams = new ComTypes.DISPPARAMS();
58+
59+
if ((args != null) && (args.Length != 0))
60+
{
61+
var variantStructSize = Marshal.SizeOf(typeof(VARIANT));
62+
pDispParams.cArgs = args.Length;
63+
64+
var argsVariantLength = variantStructSize * pDispParams.cArgs;
65+
var variantArgsArray = Marshal.AllocHGlobal(argsVariantLength);
66+
67+
// In IDispatch::Invoke, arguments are passed in reverse order
68+
IntPtr variantArgsArrayOffset = variantArgsArray + argsVariantLength;
69+
foreach (var arg in args)
70+
{
71+
variantArgsArrayOffset -= variantStructSize;
72+
Marshal.GetNativeVariantForObject(arg, variantArgsArrayOffset);
73+
}
74+
pDispParams.rgvarg = variantArgsArray;
75+
}
76+
return pDispParams;
77+
}
78+
79+
[DllImport("oleaut32.dll", SetLastError = true, CallingConvention = CallingConvention.StdCall)]
80+
static extern Int32 VariantClear(IntPtr pvarg);
81+
82+
// frees all unmanaged memory assoicated with the DISPPARAMS
83+
private static void UnprepareDispatchArgs(ComTypes.DISPPARAMS pDispParams)
84+
{
85+
if (pDispParams.rgvarg != IntPtr.Zero)
86+
{
87+
// free the array of COM VARIANTs
88+
var variantStructSize = Marshal.SizeOf(typeof(VARIANT));
89+
var variantArgsArrayOffset = pDispParams.rgvarg;
90+
int argIndex = 0;
91+
while (argIndex < pDispParams.cArgs)
92+
{
93+
VariantClear(variantArgsArrayOffset);
94+
variantArgsArrayOffset += variantStructSize;
95+
argIndex++;
96+
}
97+
Marshal.FreeHGlobal(pDispParams.rgvarg);
98+
}
99+
}
100+
101+
// TODO support DISPATCH_PROPERTYPUTREF (property-set) which requires special handling
102+
public static object Invoke(IDispatch obj, int memberId, InvokeKind invokeKind, object[] args = null)
103+
{
104+
var pDispParams = PrepareDispatchArgs(args);
105+
var pExcepInfo = new ComTypes.EXCEPINFO();
106+
107+
int hr = obj.Invoke(memberId, ref GUID_NULL, 0, (uint)invokeKind,
108+
ref pDispParams, out object pVarResult, ref pExcepInfo, out uint pErrArg);
109+
110+
UnprepareDispatchArgs(pDispParams);
111+
112+
if (ComHelper.HRESULT_FAILED(hr))
113+
{
114+
if ((hr == (int)KnownComHResults.DISP_E_EXCEPTION) && (ComHelper.HRESULT_FAILED(pExcepInfo.scode)))
115+
{
116+
throw Marshal.GetExceptionForHR(pExcepInfo.scode);
117+
}
118+
throw Marshal.GetExceptionForHR(hr);
119+
}
120+
121+
return pVarResult;
122+
}
11123
}
12124

13125
// A compatible version of ITypeInfo, where COM objects are outputted as IntPtrs instead of objects
@@ -215,5 +327,6 @@ public enum KnownComHResults : int
215327
{
216328
E_VBA_COMPILEERROR = unchecked((int)0x800A9C64),
217329
E_NOTIMPL = unchecked((int)0x80004001),
330+
DISP_E_EXCEPTION = unchecked((int)0x80020009),
218331
}
219332
}

0 commit comments

Comments
 (0)