Skip to content

Commit 4ded649

Browse files
committed
Merge branch 'next' of https://github.com/rubberduck-vba/Rubberduck into ComSafeCleanupLeaks
# Conflicts: # Rubberduck.Core/Properties/Settings.Designer.cs
2 parents eaa57ef + ca8beff commit 4ded649

File tree

81 files changed

+2938
-1954
lines changed

Some content is hidden

Large Commits have some content hidden by default. Use the searchbox below for content that may be hidden.

81 files changed

+2938
-1954
lines changed

.gitignore

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -7,6 +7,7 @@
77
*.sln.docstates
88
*.csproj.user
99
*.csproj.DotSettings
10+
launchSettings.json
1011

1112
# External NuGet Packages
1213
[Pp]ackages/
@@ -178,4 +179,5 @@ $RECYCLE.BIN/
178179
Installers/
179180
*.xlsx
180181

181-
CodeGraphData/
182+
CodeGraphData/
183+
/Rubberduck.Deployment/Properties/launchSettings.json

Rubberduck.CodeAnalysis/Inspections/Concrete/HungarianNotationInspection.cs

Lines changed: 11 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -94,8 +94,14 @@ public sealed class HungarianNotationInspection : InspectionBase
9494
DeclarationType.Variable
9595
};
9696

97+
private static readonly List<DeclarationType> IgnoredProcedureTypes = new List<DeclarationType>
98+
{
99+
DeclarationType.LibraryFunction,
100+
DeclarationType.LibraryProcedure
101+
};
102+
97103
#endregion
98-
104+
99105
private readonly IPersistanceService<CodeInspectionSettings> _settings;
100106

101107
public HungarianNotationInspection(RubberduckParserState state, IPersistanceService<CodeInspectionSettings> settings)
@@ -112,7 +118,10 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
112118
var hungarians = UserDeclarations
113119
.Where(declaration => !whitelistedNames.Contains(declaration.IdentifierName) &&
114120
TargetDeclarationTypes.Contains(declaration.DeclarationType) &&
115-
HungarianIdentifierRegex.IsMatch(declaration.IdentifierName))
121+
!IgnoredProcedureTypes.Contains(declaration.DeclarationType) &&
122+
!IgnoredProcedureTypes.Contains(declaration.ParentDeclaration.DeclarationType) &&
123+
HungarianIdentifierRegex.IsMatch(declaration.IdentifierName) &&
124+
!IsIgnoringInspectionResultFor(declaration, AnnotationName))
116125
.Select(issue => new DeclarationInspectionResult(this,
117126
string.Format(Resources.Inspections.InspectionResults.IdentifierNameInspection,
118127
RubberduckUI.ResourceManager.GetString($"DeclarationType_{issue.DeclarationType}", CultureInfo.CurrentUICulture),

Rubberduck.CodeAnalysis/Inspections/Concrete/MemberNotOnInterfaceInspection.cs

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -21,7 +21,7 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
2121

2222
var targets = Declarations.Where(decl => decl.AsTypeDeclaration != null &&
2323
!decl.AsTypeDeclaration.IsUserDefined &&
24-
decl.AsTypeDeclaration.DeclarationType.HasFlag(DeclarationType.ClassModule) &&
24+
decl.AsTypeDeclaration.DeclarationType.HasFlag(DeclarationType.ClassModule) &&
2525
((ClassModuleDeclaration)decl.AsTypeDeclaration).IsExtensible)
2626
.SelectMany(decl => decl.References).ToList();
2727
return unresolved
@@ -33,7 +33,8 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
3333
usage.Context.Parent.Parent.Equals(access.CallingContext))
3434
)
3535
})
36-
.Where(memberAccess => memberAccess.callingContext != null)
36+
.Where(memberAccess => memberAccess.callingContext != null &&
37+
memberAccess.callingContext.Declaration.DeclarationType != DeclarationType.Control) //TODO - remove this exception after resolving #2592)
3738
.Select(memberAccess => new DeclarationInspectionResult(this,
3839
string.Format(InspectionResults.MemberNotOnInterfaceInspection, memberAccess.access.IdentifierName,
3940
memberAccess.callingContext.Declaration.AsTypeDeclaration.IdentifierName), memberAccess.access));

Rubberduck.CodeAnalysis/Inspections/Concrete/UnassignedVariableUsageInspection.cs

Lines changed: 22 additions & 21 deletions
Original file line numberDiff line numberDiff line change
@@ -18,6 +18,15 @@ public sealed class UnassignedVariableUsageInspection : InspectionBase
1818
public UnassignedVariableUsageInspection(RubberduckParserState state)
1919
: base(state) { }
2020

21+
//See https://github.com/rubberduck-vba/Rubberduck/issues/2010 for why these are being excluded.
22+
private static readonly List<string> IgnoredFunctions = new List<string>
23+
{
24+
"VBE7.DLL;VBA.Strings.Len",
25+
"VBE7.DLL;VBA.Strings.LenB",
26+
"VBA6.DLL;VBA.Strings.Len",
27+
"VBA6.DLL;VBA.Strings.LenB"
28+
};
29+
2130
protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
2231
{
2332
var declarations = State.DeclarationFinder.UserDeclarations(DeclarationType.Variable)
@@ -27,41 +36,33 @@ protected override IEnumerable<IInspectionResult> DoGetInspectionResults()
2736
&& !declaration.IsSelfAssigned
2837
&& !declaration.References.Any(reference => reference.IsAssignment));
2938

30-
//See https://github.com/rubberduck-vba/Rubberduck/issues/2010 for why these are being excluded.
31-
//TODO: These need to be modified to correctly work in VB6.
32-
var lenFunction = BuiltInDeclarations.SingleOrDefault(s => s.DeclarationType == DeclarationType.Function && s.Scope.Equals("VBE7.DLL;VBA.Strings.Len"));
33-
var lenbFunction = BuiltInDeclarations.SingleOrDefault(s => s.DeclarationType == DeclarationType.Function && s.Scope.Equals("VBE7.DLL;VBA.Strings.LenB"));
39+
var excludedDeclarations = BuiltInDeclarations.Where(decl => IgnoredFunctions.Contains(decl.QualifiedName.ToString())).ToList();
3440

35-
return declarations.Where(d => d.References.Any() &&
36-
!DeclarationReferencesContainsReference(lenFunction, d) &&
37-
!DeclarationReferencesContainsReference(lenbFunction, d))
38-
.SelectMany(d => d.References)
39-
.Where(r => !r.IsIgnoringInspectionResultFor(AnnotationName))
40-
.Select(r => new IdentifierReferenceInspectionResult(this,
41-
string.Format(InspectionResults.UnassignedVariableUsageInspection, r.IdentifierName),
42-
State,
43-
r)).ToList();
41+
return declarations
42+
.Where(d => d.References.Any() && !excludedDeclarations.Any(excl => DeclarationReferencesContainsReference(excl, d)))
43+
.SelectMany(d => d.References)
44+
.Distinct()
45+
.Where(r => !r.IsIgnoringInspectionResultFor(AnnotationName))
46+
.Select(r => new IdentifierReferenceInspectionResult(this,
47+
string.Format(InspectionResults.UnassignedVariableUsageInspection, r.IdentifierName),
48+
State,
49+
r)).ToList();
4450
}
4551

46-
private bool DeclarationReferencesContainsReference(Declaration parentDeclaration, Declaration target)
52+
private static bool DeclarationReferencesContainsReference(Declaration parentDeclaration, Declaration target)
4753
{
48-
if (parentDeclaration == null)
49-
{
50-
return false;
51-
}
52-
5354
foreach (var targetReference in target.References)
5455
{
5556
foreach (var reference in parentDeclaration.References)
5657
{
57-
var context = (ParserRuleContext) reference.Context.Parent;
58+
var context = (ParserRuleContext)reference.Context.Parent;
5859
if (context.GetSelection().Contains(targetReference.Selection))
5960
{
6061
return true;
6162
}
6263
}
6364
}
64-
65+
6566
return false;
6667
}
6768
}

Rubberduck.CodeAnalysis/QuickFixes/AccessSheetUsingCodeNameQuickFix.cs

Lines changed: 18 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -27,7 +27,8 @@ public override void Fix(IInspectionResult result)
2727
var rewriter = _state.GetRewriter(referenceResult.QualifiedName);
2828

2929
var setStatement = referenceResult.Context.GetAncestor<VBAParser.SetStmtContext>();
30-
if (setStatement == null)
30+
var isArgument = referenceResult.Context.GetAncestor<VBAParser.ArgumentContext>() != null;
31+
if (setStatement == null || isArgument)
3132
{
3233
// Sheet accessed inline
3334

@@ -49,20 +50,23 @@ public override void Fix(IInspectionResult result)
4950
return moduleBodyElement != null && moduleBodyElement == referenceResult.Context.GetAncestor<VBAParser.ModuleBodyElementContext>();
5051
});
5152

52-
var variableListContext = (VBAParser.VariableListStmtContext)sheetDeclaration.Context.Parent;
53-
if (variableListContext.variableSubStmt().Length == 1)
53+
if (!sheetDeclaration.IsUndeclared)
5454
{
55-
rewriter.Remove(variableListContext.Parent as ParserRuleContext);
56-
}
57-
else if (sheetDeclaration.Context == variableListContext.variableSubStmt().Last())
58-
{
59-
rewriter.Remove(variableListContext.COMMA().Last());
60-
rewriter.Remove(sheetDeclaration);
61-
}
62-
else
63-
{
64-
rewriter.Remove(variableListContext.COMMA().First(comma => comma.Symbol.StartIndex > sheetDeclaration.Context.Start.StartIndex));
65-
rewriter.Remove(sheetDeclaration);
55+
var variableListContext = (VBAParser.VariableListStmtContext)sheetDeclaration.Context.Parent;
56+
if (variableListContext.variableSubStmt().Length == 1)
57+
{
58+
rewriter.Remove(variableListContext.Parent as ParserRuleContext);
59+
}
60+
else if (sheetDeclaration.Context == variableListContext.variableSubStmt().Last())
61+
{
62+
rewriter.Remove(variableListContext.COMMA().Last());
63+
rewriter.Remove(sheetDeclaration);
64+
}
65+
else
66+
{
67+
rewriter.Remove(variableListContext.COMMA().First(comma => comma.Symbol.StartIndex > sheetDeclaration.Context.Start.StartIndex));
68+
rewriter.Remove(sheetDeclaration);
69+
}
6670
}
6771

6872
foreach (var reference in sheetDeclaration.References)

Rubberduck.Core/App.cs

Lines changed: 20 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -105,6 +105,24 @@ private void UpdateLoggingLevel()
105105
LogLevelHelper.SetMinimumLogLevel(LogLevel.FromOrdinal(_config.UserSettings.GeneralSettings.MinimumLogLevel));
106106
}
107107

108+
/// <summary>
109+
/// Ensure that log level is changed to "none" after a successful
110+
/// run of Rubberduck for first time. By default, we ship with
111+
/// log level set to Trace (0) but once it's installed and has
112+
/// ran without problem, it should be set to None (6)
113+
/// </summary>
114+
private void UpdateLoggingLevelOnShutdown()
115+
{
116+
if (_config.UserSettings.GeneralSettings.UserEditedLogLevel ||
117+
_config.UserSettings.GeneralSettings.MinimumLogLevel != LogLevel.Trace.Ordinal)
118+
{
119+
return;
120+
}
121+
122+
_config.UserSettings.GeneralSettings.MinimumLogLevel = LogLevel.Off.Ordinal;
123+
_configService.SaveConfiguration(_config);
124+
}
125+
108126
public void Startup()
109127
{
110128
EnsureLogFolderPathExists();
@@ -131,6 +149,8 @@ public void Shutdown()
131149
{
132150
Debug.WriteLine("App calling Hooks.Detach.");
133151
_hooks.Detach();
152+
153+
UpdateLoggingLevelOnShutdown();
134154
}
135155
catch
136156
{

Rubberduck.Core/AutoComplete/AutoCompleteBase.cs

Lines changed: 0 additions & 131 deletions
This file was deleted.

0 commit comments

Comments
 (0)