Skip to content

Commit

Permalink
Merge remote-tracking branch 'upstream/next' into rkapka-master
Browse files Browse the repository at this point in the history
  • Loading branch information
rkapka committed Jul 20, 2018
2 parents 65b96df + 9d5f49a commit 82daf5a
Show file tree
Hide file tree
Showing 74 changed files with 1,231 additions and 546 deletions.
Expand Up @@ -167,7 +167,7 @@ public override void EnterPropertySetStmt(VBAParser.PropertySetStmtContext conte
public override void ExitAnnotation(VBAParser.AnnotationContext context)
{
var name = Identifier.GetName(context.annotationName().unrestrictedIdentifier());
var annotationType = (AnnotationType) Enum.Parse(typeof (AnnotationType), name);
var annotationType = (AnnotationType) Enum.Parse(typeof (AnnotationType), name, true);
var key = Tuple.Create(_currentModuleName, annotationType);
_annotationCounts[key]++;

Expand Down
Expand Up @@ -2,6 +2,7 @@
using System.Linq;
using Rubberduck.Inspections.Abstract;
using Rubberduck.Inspections.Results;
using Rubberduck.Parsing.Grammar;
using Rubberduck.Parsing.Inspections.Abstract;
using Rubberduck.Resources.Inspections;
using Rubberduck.Parsing.Symbols;
Expand All @@ -23,12 +24,19 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
decl.AsTypeDeclaration.DeclarationType.HasFlag(DeclarationType.ClassModule) &&
((ClassModuleDeclaration)decl.AsTypeDeclaration).IsExtensible)
.SelectMany(decl => decl.References).ToList();
return from access in unresolved
let callingContext = targets.FirstOrDefault(usage => usage.Context.Equals(access.CallingContext))
where callingContext != null
select new DeclarationInspectionResult(this,
string.Format(InspectionResults.MemberNotOnInterfaceInspection, access.IdentifierName, callingContext.Declaration.AsTypeDeclaration.IdentifierName),
access);
return unresolved
.Select(access => new
{
access,
callingContext = targets.FirstOrDefault(usage => usage.Context.Equals(access.CallingContext)
|| (access.CallingContext is VBAParser.NewExprContext &&
usage.Context.Parent.Parent.Equals(access.CallingContext))
)
})
.Where(memberAccess => memberAccess.callingContext != null)
.Select(memberAccess => new DeclarationInspectionResult(this,
string.Format(InspectionResults.MemberNotOnInterfaceInspection, memberAccess.access.IdentifierName,
memberAccess.callingContext.Declaration.AsTypeDeclaration.IdentifierName), memberAccess.access));
}
}
}
@@ -1,4 +1,5 @@
using System.Collections.Generic;
using System.Diagnostics;
using System.Linq;
using Rubberduck.Common;
using Rubberduck.Inspections.Abstract;
Expand Down Expand Up @@ -91,6 +92,9 @@ private IEnumerable<IInspectionResult> GetResults(Declaration[] declarations, De

for (var i = 0; i < parameters.Count; i++)
{
//If you hit this assert, congratulations! you've found a test case for https://github.com/rubberduck-vba/Rubberduck/issues/3906
//Please examine the code, and if possible, either fix the indexing on this or upload your failing code to the GitHub issue.
Debug.Assert(parametersAreByRef.Count == parameters.Count);
parametersAreByRef[i] = parametersAreByRef[i] &&
!IsUsedAsByRefParam(declarations, parameters[i]) &&
((VBAParser.ArgContext) parameters[i].Context).BYVAL() == null &&
Expand Down
Expand Up @@ -17,7 +17,6 @@ public VariableTypeNotDeclaredInspection(RubberduckParserState state)
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
{
var issues = from item in State.DeclarationFinder.UserDeclarations(DeclarationType.Variable)
.Union(State.DeclarationFinder.UserDeclarations(DeclarationType.Constant))
.Union(State.DeclarationFinder.UserDeclarations(DeclarationType.Parameter))
where (item.DeclarationType != DeclarationType.Parameter || (item.DeclarationType == DeclarationType.Parameter && !item.IsArray))
&& item.DeclarationType != DeclarationType.Control
Expand Down
13 changes: 9 additions & 4 deletions Rubberduck.Core/UI/CodeExplorer/Commands/AddComponentCommand.cs
Expand Up @@ -9,7 +9,6 @@ namespace Rubberduck.UI.CodeExplorer.Commands
public class AddComponentCommand
{
private readonly IVBE _vbe;
private const string DefaultFolder = "VBAProject";

public AddComponentCommand(IVBE vbe)
{
Expand Down Expand Up @@ -69,16 +68,22 @@ private Declaration GetDeclaration(CodeExplorerItemViewModel node)

return (node as ICodeExplorerDeclarationViewModel)?.Declaration;
}

private string GetActiveProjectName()
{
using (var activeProject = _vbe.ActiveVBProject)
{
return activeProject.Name;
}
}
private string GetFolder(CodeExplorerItemViewModel node)
{
switch (node)
{
case null:
return DefaultFolder;
return GetActiveProjectName();
case ICodeExplorerDeclarationViewModel declarationNode:
return string.IsNullOrEmpty(declarationNode.Declaration.CustomFolder)
? DefaultFolder
? GetActiveProjectName()
: declarationNode.Declaration.CustomFolder.Replace("\"", string.Empty);
default:
return ((CodeExplorerCustomFolderViewModel)node).FullPath;
Expand Down
53 changes: 49 additions & 4 deletions Rubberduck.Deployment/BuildRegistryScript.ps1
Expand Up @@ -69,12 +69,32 @@ function Restore-Environment {
foreach-object { set-item Env:$($_.Name) $_.Value }
}

# Remove older imported registry scripts for debug builds.
function Clean-OldImports
{
param(
[String] $dir
)
$i = 0;
Get-ChildItem $dir -Filter DebugRegistryEntries.reg.imported_*.txt |
Sort-Object Name -Descending |
Foreach-Object {
if($i -ge 10) {
$_.Delete();
}
$i++;
}
}

Set-StrictMode -Version latest;
$ErrorActionPreference = "Stop";
$DebugUnregisterRun = $false;

try
{
# Clean imports older than 10 builds
Clean-OldImports ((Get-ScriptDirectory) + "\LocalRegistryEntries");;

# Allow multiple DLL files to be registered if necessary
$separator = "|";
$option = [System.StringSplitOptions]::RemoveEmptyEntries;
Expand Down Expand Up @@ -137,6 +157,22 @@ try
$dllXml = $targetDll + ".xml";
$tlbXml = $targetTlb32 + ".xml";

# Write-Host "Variable printout:"
# Write-Host "dllFile = $dllFile";
# Write-Host "idlFile = $idlFile";
# Write-Host "tlb32File = $tlb32File";
# Write-Host "tlb64File = $tlb64File";
# Write-Host "sourceDll = $sourceDll";
# Write-Host "targetDll = $targetDll";
# Write-Host "sourceTlb32 = $sourceTlb32";
# Write-Host "targetTlb32 = $targetTlb32";
# Write-Host "sourceTlb64 = $sourceTlb64";
# Write-Host "targetTlb64 = $targetTlb64";
# Write-Host "dllXml = $dllXml";
# Write-Host "tlbXml = $tlbXml";
# Write-Host "targetDir = $targetDir";
# Write-Host "";

# Use for debugging issues with passing parameters to the external programs
# Note that it is not legal to have syntax like `& $cmdIncludingArguments` or `& $cmd $args`
# For simplicity, the arguments are pass in literally.
Expand All @@ -151,12 +187,21 @@ try
$encoding = New-Object System.Text.UTF8Encoding $true;
[System.IO.File]::WriteAllLines($idlFile, $idl, $encoding);

$origEnv = Get-Environment
$origEnv = Get-Environment;
try {
Invoke-CmdScript "$devPath";

& "midl.exe" ""$idlFile"" /win32 /out ""$targetDir"" /tlb ""$tlb32File"";
& "midl.exe" ""$idlFile"" /amd64 /out ""$targetDir"" /tlb ""$tlb64File"";

if($targetDir.EndsWith("\"))
{
$targetDirWithoutSlash = $targetDir.Substring(0,$targetDir.Length-1);
}
else
{
$targetDirWithoutSlash = $targetDir;
}

& midl.exe /win32 /tlb ""$tlb32File"" ""$idlFile"" /out ""$targetDirWithoutSlash"";
& midl.exe /amd64 /tlb ""$tlb64File"" ""$idlFile"" /out ""$targetDirWithoutSlash"";
} catch {
throw;
} finally {
Expand Down
4 changes: 2 additions & 2 deletions Rubberduck.Deployment/Rubberduck.Deployment.csproj
Expand Up @@ -116,9 +116,9 @@
</ItemGroup>
<Import Project="$(MSBuildToolsPath)\Microsoft.CSharp.targets" />
<PropertyGroup>
<PostBuildEvent>C:\Windows\System32\WindowsPowerShell\v1.0\powershell.exe -ExecutionPolicy Bypass -command "$(ProjectDir)BuildRegistryScript.ps1 -config '$(ConfigurationName)' -builderAssemblyPath '$(TargetPath)' -netToolsDir '$(FrameworkSDKDir)bin\NETFX 4.6.1 Tools\' -wixToolsDir '$(ProjectDir)WixToolset\' -sourceDir '$(TargetDir)' -targetDir '$(TargetDir)' -projectDir '$(ProjectDir)' -includeDir '$(ProjectDir)InnoSetup\Includes\' -filesToExtract 'Rubberduck.dll|Rubberduck.API.dll'"</PostBuildEvent>
<PostBuildEvent>C:\Windows\System32\WindowsPowerShell\v1.0\powershell.exe -ExecutionPolicy Bypass -command "&amp; '$(ProjectDir)BuildRegistryScript.ps1' -config '$(ConfigurationName)' -builderAssemblyPath '$(TargetPath)' -netToolsDir '$(FrameworkSDKDir)bin\NETFX 4.6.1 Tools\' -wixToolsDir '$(ProjectDir)WixToolset\' -sourceDir '$(TargetDir)' -targetDir '$(TargetDir)' -projectDir '$(ProjectDir)' -includeDir '$(ProjectDir)InnoSetup\Includes\' -filesToExtract 'Rubberduck.dll|Rubberduck.API.dll'"</PostBuildEvent>
</PropertyGroup>
<PropertyGroup>
<PreBuildEvent>C:\Windows\System32\WindowsPowerShell\v1.0\powershell.exe -ExecutionPolicy Bypass -command "$(ProjectDir)PreInnoSetupConfiguration.ps1 -WorkingDir $(ProjectDir)</PreBuildEvent>
<PreBuildEvent>C:\Windows\System32\WindowsPowerShell\v1.0\powershell.exe -ExecutionPolicy Bypass -command "&amp; '$(ProjectDir)PreInnoSetupConfiguration.ps1' -WorkingDir '$(ProjectDir)'"</PreBuildEvent>
</PropertyGroup>
</Project>
3 changes: 3 additions & 0 deletions Rubberduck.Interaction/Rubberduck.Interaction.csproj
Expand Up @@ -46,5 +46,8 @@
<Compile Include="IMessageBox.cs" />
<Compile Include="Properties\AssemblyInfo.cs" />
</ItemGroup>
<ItemGroup>
<Analyzer Include="..\RubberduckCodeAnalysis\bin\Release\RubberduckCodeAnalysis.dll" />
</ItemGroup>
<Import Project="$(MSBuildToolsPath)\Microsoft.CSharp.targets" />
</Project>
6 changes: 3 additions & 3 deletions Rubberduck.Parsing/ComReflection/ComAlias.cs
Expand Up @@ -8,9 +8,9 @@ namespace Rubberduck.Parsing.ComReflection
[DebuggerDisplay("{Name} As {TypeName}")]
public class ComAlias : ComBase
{
public string TypeName { get; private set; }
public bool IsHidden { get; private set; }
public bool IsRestricted { get; private set; }
public string TypeName { get; }
public bool IsHidden { get; }
public bool IsRestricted { get; }

public ComAlias(ITypeLib typeLib, ITypeInfo info, int index, TYPEATTR attributes) : base(typeLib, index)
{
Expand Down
9 changes: 2 additions & 7 deletions Rubberduck.Parsing/ComReflection/ComBase.cs
Expand Up @@ -20,10 +20,7 @@ public abstract class ComBase : IComBase
public Guid Guid { get; protected set; }
public int Index { get; protected set; }
public ComDocumentation Documentation { get; protected set; }
public string Name
{
get { return Documentation == null ? string.Empty : Documentation.Name; }
}
public string Name => Documentation == null ? string.Empty : Documentation.Name;

public DeclarationType Type { get; protected set; }

Expand All @@ -35,9 +32,7 @@ protected ComBase(ITypeLib typeLib, int index)

protected ComBase(ITypeInfo info)
{
ITypeLib typeLib;
int index;
info.GetContainingTypeLib(out typeLib, out index);
info.GetContainingTypeLib(out ITypeLib typeLib, out int index);
Index = index;
Debug.Assert(typeLib != null);
Documentation = new ComDocumentation(typeLib, index);
Expand Down
103 changes: 41 additions & 62 deletions Rubberduck.Parsing/ComReflection/ComCoClass.cs
Expand Up @@ -5,6 +5,7 @@
using System.Runtime.InteropServices;
using System.Runtime.InteropServices.ComTypes;
using Rubberduck.Parsing.Symbols;
using Rubberduck.VBEditor.Utility;
using TYPEATTR = System.Runtime.InteropServices.ComTypes.TYPEATTR;
using IMPLTYPEFLAGS = System.Runtime.InteropServices.ComTypes.IMPLTYPEFLAGS;
using TYPEFLAGS = System.Runtime.InteropServices.ComTypes.TYPEFLAGS;
Expand All @@ -16,51 +17,31 @@ public class ComCoClass : ComType, IComTypeWithMembers
private readonly Dictionary<ComInterface, bool> _interfaces = new Dictionary<ComInterface, bool>();
private readonly List<ComInterface> _events = new List<ComInterface>();

public bool IsControl { get; private set; }
public bool IsControl { get; }

public bool IsExtensible
{
get { return _interfaces.Keys.Any(i => i.IsExtensible); }
}
public bool IsExtensible => _interfaces.Keys.Any(i => i.IsExtensible);

public ComInterface DefaultInterface { get; private set; }

public IEnumerable<ComInterface> EventInterfaces
{
get { return _events; }
}
public IEnumerable<ComInterface> ImplementedInterfaces
{
get { return _interfaces.Keys; }
}
public IEnumerable<ComInterface> EventInterfaces => _events;

public IEnumerable<ComInterface> VisibleInterfaces
{
get { return _interfaces.Where(i => !i.Value).Select(i => i.Key); }
}
public IEnumerable<ComInterface> ImplementedInterfaces => _interfaces.Keys;

public IEnumerable<ComMember> Members
{
get { return ImplementedInterfaces.Where(x => !_events.Contains(x)).SelectMany(i => i.Members); }
}
public IEnumerable<ComField> Properties => ImplementedInterfaces.Where(x => !_events.Contains(x)).SelectMany(i => i.Properties);

public ComMember DefaultMember
{
get { return DefaultInterface.DefaultMember; }
}
public IEnumerable<ComInterface> VisibleInterfaces => _interfaces.Where(i => !i.Value).Select(i => i.Key);

public IEnumerable<ComMember> SourceMembers
{
get { return _events.SelectMany(i => i.Members); }
}
public IEnumerable<ComMember> Members => ImplementedInterfaces.Where(x => !_events.Contains(x)).SelectMany(i => i.Members);

public bool WithEvents
{
get { return _events.Count > 0; }
}
public ComMember DefaultMember => DefaultInterface.DefaultMember;

public IEnumerable<ComMember> SourceMembers => _events.SelectMany(i => i.Members);

public bool WithEvents => _events.Count > 0;

public void AddInterface(ComInterface intrface, bool restricted = false)
{
Debug.Assert(intrface != null);
if (!_interfaces.ContainsKey(intrface))
{
_interfaces.Add(intrface, restricted);
Expand All @@ -79,38 +60,36 @@ private void GetImplementedInterfaces(ITypeInfo info, TYPEATTR typeAttr)
{
for (var implIndex = 0; implIndex < typeAttr.cImplTypes; implIndex++)
{
int href;
info.GetRefTypeOfImplType(implIndex, out href);

ITypeInfo implemented;
info.GetRefTypeInfo(href, out implemented);

IntPtr attribPtr;
implemented.GetTypeAttr(out attribPtr);
var attribs = (TYPEATTR)Marshal.PtrToStructure(attribPtr, typeof(TYPEATTR));
info.GetRefTypeOfImplType(implIndex, out int href);
info.GetRefTypeInfo(href, out ITypeInfo implemented);

ComType inherited;
ComProject.KnownTypes.TryGetValue(attribs.guid, out inherited);
var intface = inherited as ComInterface ?? new ComInterface(implemented, attribs);
ComProject.KnownTypes.TryAdd(attribs.guid, intface);

IMPLTYPEFLAGS flags = 0;
try
{
info.GetImplTypeFlags(implIndex, out flags);
}
catch (COMException) { }

if (flags.HasFlag(IMPLTYPEFLAGS.IMPLTYPEFLAG_FSOURCE))
{
_events.Add(intface);
}
else
implemented.GetTypeAttr(out IntPtr attribPtr);
using (DisposalActionContainer.Create(attribPtr, info.ReleaseTypeAttr))
{
DefaultInterface = flags.HasFlag(IMPLTYPEFLAGS.IMPLTYPEFLAG_FDEFAULT) ? intface : DefaultInterface;
var attribs = Marshal.PtrToStructure<TYPEATTR>(attribPtr);

ComProject.KnownTypes.TryGetValue(attribs.guid, out ComType inherited);
var intface = inherited as ComInterface ?? new ComInterface(implemented, attribs);

ComProject.KnownTypes.TryAdd(attribs.guid, intface);

IMPLTYPEFLAGS flags = 0;
try
{
info.GetImplTypeFlags(implIndex, out flags);
}
catch (COMException) { }

if (flags.HasFlag(IMPLTYPEFLAGS.IMPLTYPEFLAG_FSOURCE))
{
_events.Add(intface);
}
else
{
DefaultInterface = flags.HasFlag(IMPLTYPEFLAGS.IMPLTYPEFLAG_FDEFAULT) ? intface : DefaultInterface;
}
_interfaces.Add(intface, flags.HasFlag(IMPLTYPEFLAGS.IMPLTYPEFLAG_FRESTRICTED));
}
_interfaces.Add(intface, flags.HasFlag(IMPLTYPEFLAGS.IMPLTYPEFLAG_FRESTRICTED));
info.ReleaseTypeAttr(attribPtr);
}
}
}
Expand Down

0 comments on commit 82daf5a

Please sign in to comment.