Skip to content

Commit

Permalink
Merge pull request #205 from rubberduck-vba/next
Browse files Browse the repository at this point in the history
sync with main repo
  • Loading branch information
retailcoder committed Jan 23, 2017
2 parents 2f021db + 18568e5 commit 61d3952
Show file tree
Hide file tree
Showing 39 changed files with 231 additions and 114 deletions.
1 change: 1 addition & 0 deletions RetailCoder.VBE/Root/RubberduckModule.cs
Original file line number Diff line number Diff line change
Expand Up @@ -7,6 +7,7 @@
using Ninject.Modules;
using Rubberduck.Common;
using Rubberduck.Parsing;
using Rubberduck.Parsing.ComReflection;
using Rubberduck.Parsing.Symbols.DeclarationLoaders;
using Rubberduck.Parsing.VBA;
using Rubberduck.Settings;
Expand Down
Original file line number Diff line number Diff line change
@@ -1,6 +1,7 @@
using System;
using System.IO;
using NLog;
using Rubberduck.Parsing.ComReflection;
using Rubberduck.Parsing.Symbols;
using Rubberduck.Parsing.VBA;
using Rubberduck.SettingsProvider;
Expand Down
5 changes: 5 additions & 0 deletions Rubberduck.Parsing/ComReflection/ComCoClass.cs
Original file line number Diff line number Diff line change
Expand Up @@ -41,6 +41,11 @@ public IEnumerable<ComMember> Members
get { return ImplementedInterfaces.Where(x => !_events.Contains(x)).SelectMany(i => i.Members); }
}

public ComMember DefaultMember
{
get { return DefaultInterface.DefaultMember; }
}

public IEnumerable<ComMember> SourceMembers
{
get { return _events.SelectMany(i => i.Members); }
Expand Down
1 change: 0 additions & 1 deletion Rubberduck.Parsing/ComReflection/ComField.cs
Original file line number Diff line number Diff line change
@@ -1,7 +1,6 @@
using System.Diagnostics;
using System.Runtime.InteropServices;
using System.Runtime.InteropServices.ComTypes;
using System.Xml.Schema;
using Rubberduck.Parsing.Symbols;
using VARDESC = System.Runtime.InteropServices.ComTypes.VARDESC;
using VARFLAGS = System.Runtime.InteropServices.ComTypes.VARFLAGS;
Expand Down
13 changes: 12 additions & 1 deletion Rubberduck.Parsing/ComReflection/ComInterface.cs
Original file line number Diff line number Diff line change
Expand Up @@ -16,6 +16,7 @@ public class ComInterface : ComType, IComTypeWithMembers
{
private readonly List<ComInterface> _inherited = new List<ComInterface>();
private readonly List<ComMember> _members = new List<ComMember>();
private ComMember _defaultMember;

public bool IsExtensible { get; private set; }

Expand All @@ -29,6 +30,11 @@ public IEnumerable<ComMember> Members
get { return _members; }
}

public ComMember DefaultMember
{
get { return _defaultMember; }
}

public ComInterface(ITypeInfo info, TYPEATTR attrib) : base(info, attrib)
{
GetImplementedInterfaces(info, attrib);
Expand Down Expand Up @@ -78,7 +84,12 @@ private void GetComMembers(ITypeInfo info, TYPEATTR attrib)
{
continue;
}
_members.Add(new ComMember(info, member));
var comMember = new ComMember(info, member);
_members.Add(comMember);
if (comMember.IsDefault)
{
_defaultMember = comMember;
}
info.ReleaseFuncDesc(memberPtr);
}
}
Expand Down
19 changes: 17 additions & 2 deletions Rubberduck.Parsing/ComReflection/ComMember.cs
Original file line number Diff line number Diff line change
Expand Up @@ -12,6 +12,18 @@

namespace Rubberduck.Parsing.ComReflection
{
internal enum DispId
{
Collect = -8, //The method you are calling through Invoke is an accessor function.
Destructor = -7, //The C++ destructor function for the object.
Construtor = -6, //The C++ constructor function for the object.
Evaluate = -5, //This method is implicitly invoked when the ActiveX client encloses the arguments in square brackets.
NewEnum = -4, //It returns an enumerator object that supports IEnumVARIANT.
PropertyPut = -3, //The parameter that receives the value of an assignment in a PROPERTYPUT.
Unknown = -1, //The value returned by IDispatch::GetIDsOfNames to indicate that a member or parameter name was not found.
Value = 0 //The default member for the object.
}

[DebuggerDisplay("{MemberDeclaration}")]
public class ComMember : ComBase
{
Expand All @@ -20,6 +32,8 @@ public class ComMember : ComBase
public bool ReturnsWithEventsObject { get; private set; }
public bool IsDefault { get; private set; }
public bool IsEnumerator { get; private set; }
//This member is called on an interface when a bracketed expression is dereferenced.
public bool IsEvaluateFunction { get; private set; }
public ComParameter ReturnType { get; private set; }
public List<ComParameter> Parameters { get; set; }

Expand All @@ -30,8 +44,9 @@ public ComMember(ITypeInfo info, FUNCDESC funcDesc) : base(info, funcDesc)
IsHidden = flags.HasFlag(FUNCFLAGS.FUNCFLAG_FHIDDEN);
IsRestricted = flags.HasFlag(FUNCFLAGS.FUNCFLAG_FRESTRICTED);
ReturnsWithEventsObject = flags.HasFlag(FUNCFLAGS.FUNCFLAG_FSOURCE);
IsDefault = flags.HasFlag(FUNCFLAGS.FUNCFLAG_FUIDEFAULT);
IsEnumerator = flags.HasFlag(FUNCFLAGS.FUNCFLAG_FNONBROWSABLE) && Name.Equals("_NewEnum");
IsDefault = Index == (int)DispId.Value;
IsEnumerator = Index == (int)DispId.NewEnum;
IsEvaluateFunction = Index == (int)DispId.Evaluate;
SetDeclarationType(funcDesc, info);
}

Expand Down
6 changes: 5 additions & 1 deletion Rubberduck.Parsing/ComReflection/ComModule.cs
Original file line number Diff line number Diff line change
@@ -1,7 +1,6 @@
using System;
using System.Collections.Generic;
using System.Diagnostics;
using System.Linq;
using System.Runtime.InteropServices;
using System.Runtime.InteropServices.ComTypes;
using Rubberduck.Parsing.Symbols;
Expand All @@ -20,6 +19,11 @@ public IEnumerable<ComMember> Members
get { return _members; }
}

public ComMember DefaultMember
{
get { return null; }
}

private readonly List<ComField> _fields = new List<ComField>();
public IEnumerable<ComField> Fields
{
Expand Down
5 changes: 3 additions & 2 deletions Rubberduck.Parsing/ComReflection/ComProject.cs
Original file line number Diff line number Diff line change
Expand Up @@ -120,8 +120,6 @@ private void LoadModules(ITypeLib typeLibrary)
if (type != null) KnownTypes.TryAdd(typeAttributes.guid, coclass);
break;
case TYPEKIND.TKIND_ALIAS:
case TYPEKIND.TKIND_UNION:

//The current handling of this is wrong - these don't have to be classes or interfaces. In the VBE module for example,
//"LongPtr" is defined as an alias to "Long" (at least on a 32 bit system) - RD is currently treating is like a class.
//Unclear if these can *also* define alternative names for interfaces as well, but all the ones I've seen have been basically
Expand All @@ -141,6 +139,9 @@ private void LoadModules(ITypeLib typeLibrary)
_modules.Add(module as ComModule);
if (type != null) KnownTypes.TryAdd(typeAttributes.guid, module);
break;
case TYPEKIND.TKIND_UNION:
//TKIND_UNION is not a supported member type in VBA.
break;
default:
throw new NotImplementedException(string.Format("Didn't expect a TYPEATTR with multiple typekind flags set in {0}.", Path));
}
Expand Down
3 changes: 2 additions & 1 deletion Rubberduck.Parsing/ComReflection/ComType.cs
Original file line number Diff line number Diff line change
Expand Up @@ -9,12 +9,13 @@ public interface IComType : IComBase
bool IsAppObject { get; }
bool IsPreDeclared { get; }
bool IsHidden { get; }
bool IsRestricted { get; }
bool IsRestricted { get; }
}

public interface IComTypeWithMembers : IComType
{
IEnumerable<ComMember> Members { get; }
ComMember DefaultMember { get; }
}

public interface IComTypeWithFields : IComType
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -2,15 +2,15 @@
using System.Collections.Generic;
using System.ComponentModel;
using System.IO;
using System.Linq;
using System.Runtime.InteropServices;
using System.Runtime.InteropServices.ComTypes;
using Rubberduck.Parsing.ComReflection;
using Rubberduck.Parsing.Symbols;
using Rubberduck.Parsing.VBA;
using Rubberduck.VBEditor;
using System.Linq;
using Rubberduck.VBEditor.SafeComWrappers.Abstract;

namespace Rubberduck.Parsing.Symbols
namespace Rubberduck.Parsing.ComReflection
{
public class ReferencedDeclarationsCollector
{
Expand Down Expand Up @@ -139,29 +139,19 @@ public List<Declaration> LoadDeclarationsFromLibrary()
? string.Format("_{0}", module.Name)
: module.Name);

var attributes = new Attributes();
if (module.IsPreDeclared)
{
attributes.AddPredeclaredIdTypeAttribute();
}
if (module.IsAppObject)
{
attributes.AddGlobalClassAttribute();
}

var declaration = CreateModuleDeclaration(module, moduleName, project, attributes);
var declaration = CreateModuleDeclaration(module, moduleName, project, GetModuleAttributes(module));
var moduleTree = new SerializableDeclarationTree(declaration);
_declarations.Add(declaration);
_serialized.AddDeclaration(moduleTree);

var membered = module as IComTypeWithMembers;
if (membered != null)
{
CreateMemberDeclarations(membered.Members, moduleName, declaration, moduleTree);
CreateMemberDeclarations(membered.Members, moduleName, declaration, moduleTree, membered.DefaultMember);
var coClass = membered as ComCoClass;
if (coClass != null)
{
CreateMemberDeclarations(coClass.SourceMembers, moduleName, declaration, moduleTree, true);
CreateMemberDeclarations(coClass.SourceMembers, moduleName, declaration, moduleTree, coClass.DefaultMember, true);
}
}

Expand Down Expand Up @@ -204,8 +194,26 @@ public List<Declaration> LoadDeclarationsFromLibrary()
return _declarations;
}

private static Attributes GetModuleAttributes(IComType module)
{
var attributes = new Attributes();
if (module.IsPreDeclared)
{
attributes.AddPredeclaredIdTypeAttribute();
}
if (module.IsAppObject)
{
attributes.AddGlobalClassAttribute();
}
if (module as ComInterface != null && ((ComInterface)module).IsExtensible)
{
attributes.AddExtensibledClassAttribute();
}
return attributes;
}

private void CreateMemberDeclarations(IEnumerable<ComMember> members, QualifiedModuleName moduleName, Declaration declaration,
SerializableDeclarationTree moduleTree, bool eventHandlers = false)
SerializableDeclarationTree moduleTree, ComMember defaultMember, bool eventHandlers = false)
{
foreach (var item in members.Where(m => !m.IsRestricted && !IgnoredInterfaceMembers.Contains(m.Name)))
{
Expand All @@ -222,7 +230,7 @@ public List<Declaration> LoadDeclarationsFromLibrary()
memberTree.AddChildren(hasParams.Parameters);
}
var coClass = memberDeclaration as ClassModuleDeclaration;
if (coClass != null && item.IsDefault)
if (coClass != null && item == defaultMember)
{
coClass.DefaultMember = memberDeclaration;
}
Expand Down Expand Up @@ -262,20 +270,7 @@ private Declaration CreateModuleDeclaration(IComType module, QualifiedModuleName

private Declaration CreateMemberDeclaration(ComMember member, QualifiedModuleName module, Declaration parent, bool handler)
{
var attributes = new Attributes();
if (member.IsEnumerator)
{
attributes.AddEnumeratorMemberAttribute(member.Name);
}
else if (member.IsDefault)
{
attributes.AddDefaultMemberAttribute(member.Name);
}
else if (member.IsHidden)
{
attributes.AddHiddenMemberAttribute(member.Name);
}

var attributes = GetMemberAttibutes(member);
switch (member.Type)
{
case DeclarationType.Procedure:
Expand All @@ -292,5 +287,27 @@ private Declaration CreateMemberDeclaration(ComMember member, QualifiedModuleNam
throw new InvalidEnumArgumentException(string.Format("Unexpected DeclarationType {0} encountered.", member.Type));
}
}

private static Attributes GetMemberAttibutes(ComMember member)
{
var attributes = new Attributes();
if (member.IsEnumerator)
{
attributes.AddEnumeratorMemberAttribute(member.Name);
}
else if (member.IsDefault)
{
attributes.AddDefaultMemberAttribute(member.Name);
}
else if (member.IsHidden)
{
attributes.AddHiddenMemberAttribute(member.Name);
}
else if (member.IsEvaluateFunction)
{
attributes.AddEvaluateMemberAttribute(member.Name);
}
return attributes;
}
}
}
Original file line number Diff line number Diff line change
Expand Up @@ -2,10 +2,11 @@
using System.Linq;
using System.Runtime.Serialization;
using Rubberduck.Parsing.Annotations;
using Rubberduck.Parsing.Symbols;
using Rubberduck.Parsing.VBA;
using Rubberduck.VBEditor;

namespace Rubberduck.Parsing.Symbols
namespace Rubberduck.Parsing.ComReflection
{
public class SerializableDeclarationTree
{
Expand Down Expand Up @@ -176,12 +177,6 @@ public SerializableDeclaration(Declaration declaration)
IsByRefParam = param.IsByRef;
IsParamArray = param.IsParamArray;
}

var canExtend = declaration as ClassModuleDeclaration;
if (canExtend != null)
{
IsExtensible = canExtend.IsExtensible;
}
}

public List<SerializableMemberAttribute> Attributes { get; set; }
Expand Down Expand Up @@ -225,7 +220,7 @@ public Declaration Unwrap(Declaration parent)
case DeclarationType.Project:
return new ProjectDeclaration(QualifiedMemberName, IdentifierName, true, null);
case DeclarationType.ClassModule:
return new ClassModuleDeclaration(QualifiedMemberName, parent, IdentifierName, true, annotations, attributes) { IsExtensible = IsExtensible };
return new ClassModuleDeclaration(QualifiedMemberName, parent, IdentifierName, true, annotations, attributes);
case DeclarationType.ProceduralModule:
return new ProceduralModuleDeclaration(QualifiedMemberName, parent, IdentifierName, true, annotations, attributes);
case DeclarationType.Procedure:
Expand Down
Original file line number Diff line number Diff line change
@@ -1,12 +1,11 @@
using System;
using System.IO;
using System.Runtime.InteropServices.ComTypes;
using System.Runtime.Serialization;
using System.Text;
using System.Xml;
using Rubberduck.SettingsProvider;

namespace Rubberduck.Parsing.Symbols
namespace Rubberduck.Parsing.ComReflection
{
public class XmlPersistableDeclarations : IPersistable<SerializableProject>
{
Expand Down
6 changes: 3 additions & 3 deletions Rubberduck.Parsing/Rubberduck.Parsing.csproj
Original file line number Diff line number Diff line change
Expand Up @@ -258,7 +258,7 @@
<Compile Include="Symbols\PropertyGetDeclaration.cs" />
<Compile Include="Symbols\FunctionDeclaration.cs" />
<Compile Include="Symbols\DeclarationLoaders\RubberduckApiDeclarations.cs" />
<Compile Include="Symbols\SerializableDeclaration.cs" />
<Compile Include="ComReflection\SerializableDeclaration.cs" />
<Compile Include="Symbols\SquareBracketedNameComparer.cs" />
<Compile Include="Symbols\SubroutineDeclaration.cs" />
<Compile Include="Symbols\ProjectReferencePass.cs" />
Expand All @@ -272,7 +272,7 @@
<Compile Include="Symbols\ProceduralModuleDeclaration.cs" />
<Compile Include="Symbols\ProjectDeclaration.cs" />
<Compile Include="Symbols\ProjectReference.cs" />
<Compile Include="Symbols\ReferencedDeclarationsCollector.cs" />
<Compile Include="ComReflection\ReferencedDeclarationsCollector.cs" />
<Compile Include="Symbols\SyntaxErrorException.cs" />
<Compile Include="ParserRuleContextExtensions.cs" />
<Compile Include="Properties\AssemblyInfo.cs" />
Expand All @@ -284,7 +284,7 @@
<Compile Include="Symbols\IdentifierReference.cs" />
<Compile Include="Symbols\IdentifierReferenceListener.cs" />
<Compile Include="Symbols\ConstantDeclaration.cs" />
<Compile Include="Symbols\XmlPersistableDeclarations.cs" />
<Compile Include="ComReflection\XmlPersistableDeclarations.cs" />
<Compile Include="Syntax\SyntaxTree.cs" />
<Compile Include="Syntax\TextSpan.cs" />
<Compile Include="VBA\AttributeParser.cs" />
Expand Down

0 comments on commit 61d3952

Please sign in to comment.