Skip to content

Commit fb76c97

Browse files
authored
Merge pull request #2401 from retailcoder/next
Click double-handling fix
2 parents df4ccec + a65e520 commit fb76c97

File tree

14 files changed

+100
-46
lines changed

14 files changed

+100
-46
lines changed

RetailCoder.VBE/Inspections/InspectionsUI.Designer.cs

Lines changed: 2 additions & 2 deletions
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

RetailCoder.VBE/Inspections/InspectionsUI.de.resx

Lines changed: 7 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,4 @@
1-
<?xml version="1.0" encoding="UTF-8"?>
1+
<?xml version="1.0" encoding="utf-8"?>
22
<root>
33
<!--
44
Microsoft ResX Schema
@@ -59,7 +59,7 @@
5959
: using a System.ComponentModel.TypeConverter
6060
: and then encoded with base64 encoding.
6161
-->
62-
<xsd:schema xmlns:xsd="http://www.w3.org/2001/XMLSchema" xmlns:msdata="urn:schemas-microsoft-com:xml-msdata" id="root">
62+
<xsd:schema id="root" xmlns="" xmlns:xsd="http://www.w3.org/2001/XMLSchema" xmlns:msdata="urn:schemas-microsoft-com:xml-msdata">
6363
<xsd:import namespace="http://www.w3.org/XML/1998/namespace" />
6464
<xsd:element name="root" msdata:IsDataSet="true">
6565
<xsd:complexType>
@@ -274,7 +274,7 @@
274274
<value>'Option Base 1' ist angegeben.</value>
275275
</data>
276276
<data name="OptionExplicitInspectionMeta" xml:space="preserve">
277-
<value>Rubberduck kann keine Variablen auswerten, die nicht deklariert wurden. Nutze am besten 'Option Explicit' um fehleranfällige Programme zu erstellen.</value>
277+
<value>Nutze am besten 'Option Explicit' um fehleranfällige Programme zu erstellen.</value>
278278
</data>
279279
<data name="OptionExplicitInspectionName" xml:space="preserve">
280280
<value>'Option Explicit' ist nicht angegeben.</value>
@@ -555,13 +555,13 @@ Falls der Parameter 'null' sein kann, bitte dieses Auftreten ignorieren. 'null'
555555
<data name="MultipleDeclarationsInspectionResultFormat" xml:space="preserve">
556556
<value>Instruktion enthält Mehrfachdeklaration</value>
557557
</data>
558-
<data name="MalformedAnnotationInspectionName">
558+
<data name="MalformedAnnotationInspectionName" xml:space="preserve">
559559
<value>Unlesbare Annotation</value>
560560
</data>
561-
<data name="MalformedAnnotationInspectionResultFormat">
561+
<data name="MalformedAnnotationInspectionResultFormat" xml:space="preserve">
562562
<value>Annotation '{0}' ist nicht lesbar</value>
563563
</data>
564-
<data name="MalformedAnnotationInspectionMeta">
564+
<data name="MalformedAnnotationInspectionMeta" xml:space="preserve">
565565
<value>Eine Annotation in einem Kommentar konnte nicht gelesen werden.</value>
566566
</data>
567-
</root>
567+
</root>

RetailCoder.VBE/Inspections/InspectionsUI.fr.resx

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -274,7 +274,7 @@
274274
<value>'Option Base 1' est spécifié</value>
275275
</data>
276276
<data name="OptionExplicitInspectionMeta" xml:space="preserve">
277-
<value>Rubberduck ne peut pas voir les variables qui ne sont pas déclarées, et VBA n'aura aucun problème à compiler une erreur typographique: utilisez 'Option Explicit' pour prévenir la compilation d'un programme erroné.</value>
277+
<value>VBA n'aura aucun problème à compiler une erreur typographique: utilisez 'Option Explicit' pour prévenir la compilation d'un programme erroné.</value>
278278
</data>
279279
<data name="OptionExplicitInspectionName" xml:space="preserve">
280280
<value>'Option Explicit' n'est pas spécifiée.</value>

RetailCoder.VBE/Inspections/InspectionsUI.resx

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -274,7 +274,7 @@
274274
<value>'Option Base 1' is specified</value>
275275
</data>
276276
<data name="OptionExplicitInspectionMeta" xml:space="preserve">
277-
<value>Rubberduck cannot see variables that aren't declared. VBA will happily compile a typo: use 'Option Explicit' to prevent successfully compiling an erroneous program.</value>
277+
<value>VBA will happily compile a typo: use 'Option Explicit' to prevent successfully compiling an erroneous program.</value>
278278
</data>
279279
<data name="OptionExplicitInspectionName" xml:space="preserve">
280280
<value>'Option Explicit' is not specified</value>

RetailCoder.VBE/Inspections/Inspector.cs

Lines changed: 11 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -5,6 +5,7 @@
55
using System.Threading;
66
using System.Threading.Tasks;
77
using Antlr4.Runtime.Tree;
8+
using NLog;
89
using Rubberduck.Parsing;
910
using Rubberduck.Parsing.Grammar;
1011
using Rubberduck.Parsing.VBA;
@@ -64,9 +65,9 @@ public async Task<IEnumerable<ICodeInspectionResult>> FindIssuesAsync(Rubberduck
6465

6566
// Prepare ParseTreeWalker based inspections
6667
var parseTreeWalkResults = GetParseTreeResults(config, state);
67-
foreach (var parseTreeInspection in _inspections.Where(inspection => inspection.Severity != CodeInspectionSeverity.DoNotShow && inspection is IParseTreeInspection))
68+
foreach (var parseTreeInspection in _inspections.OfType<IParseTreeInspection>().Where(inspection => inspection.Severity != CodeInspectionSeverity.DoNotShow))
6869
{
69-
(parseTreeInspection as IParseTreeInspection).ParseTreeResults = parseTreeWalkResults;
70+
parseTreeInspection.ParseTreeResults = parseTreeWalkResults;
7071
}
7172

7273
var inspections = _inspections.Where(inspection => inspection.Severity != CodeInspectionSeverity.DoNotShow)
@@ -82,7 +83,14 @@ public async Task<IEnumerable<ICodeInspectionResult>> FindIssuesAsync(Rubberduck
8283
}
8384
}, token)).ToList();
8485

85-
await Task.WhenAll(inspections);
86+
try
87+
{
88+
await Task.WhenAll(inspections);
89+
}
90+
catch (Exception e)
91+
{
92+
LogManager.GetCurrentClassLogger().Error(e);
93+
}
8694
state.OnStatusMessageUpdate(RubberduckUI.ResourceManager.GetString("ParserState_" + state.Status, UI.Settings.Settings.Culture)); // should be "Ready"
8795
return allIssues;
8896
}

RetailCoder.VBE/Inspections/ParameterCanBeByValInspection.cs

Lines changed: 8 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,4 @@
1+
using System;
12
using System.Collections.Generic;
23
using System.Linq;
34
using Rubberduck.Common;
@@ -63,11 +64,12 @@ private IEnumerable<ParameterCanBeByValInspectionResult> GetResults(List<Declara
6364
{
6465
var declarationParameters =
6566
declarations.Where(d => d.DeclarationType == DeclarationType.Parameter &&
66-
d.ParentDeclaration == declaration)
67+
Equals(d.ParentDeclaration, declaration))
6768
.OrderBy(o => o.Selection.StartLine)
6869
.ThenBy(t => t.Selection.StartColumn)
6970
.ToList();
7071

72+
if (!declarationParameters.Any()) { continue; }
7173
var parametersAreByRef = declarationParameters.Select(s => true).ToList();
7274

7375
var members = declarationMembers.Any(a => a.DeclarationType == DeclarationType.Event)
@@ -78,16 +80,17 @@ private IEnumerable<ParameterCanBeByValInspectionResult> GetResults(List<Declara
7880
{
7981
var parameters =
8082
declarations.Where(d => d.DeclarationType == DeclarationType.Parameter &&
81-
d.ParentDeclaration == member)
83+
Equals(d.ParentDeclaration, member))
8284
.OrderBy(o => o.Selection.StartLine)
8385
.ThenBy(t => t.Selection.StartColumn)
8486
.ToList();
8587

8688
for (var i = 0; i < parameters.Count; i++)
8789
{
88-
parametersAreByRef[i] = parametersAreByRef[i] && !IsUsedAsByRefParam(declarations, parameters[i]) &&
89-
((VBAParser.ArgContext)parameters[i].Context).BYVAL() == null &&
90-
!parameters[i].References.Any(reference => reference.IsAssignment);
90+
parametersAreByRef[i] = parametersAreByRef[i] &&
91+
!IsUsedAsByRefParam(declarations, parameters[i]) &&
92+
((VBAParser.ArgContext) parameters[i].Context).BYVAL() == null &&
93+
!parameters[i].References.Any(reference => reference.IsAssignment);
9194
}
9295
}
9396

RetailCoder.VBE/UI/Command/MenuItems/CodePaneRefactorRenameCommandMenuItem.cs

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,3 @@
1-
using System.Windows.Input;
21
using Rubberduck.Parsing.VBA;
32
using Rubberduck.UI.Command.MenuItems.ParentMenus;
43

RetailCoder.VBE/UI/Command/MenuItems/ParentMenus/ParentMenuItemBase.cs

Lines changed: 3 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -151,7 +151,7 @@ private ICommandBarControl InitializeChildControl(ICommandMenuItem item)
151151
child.ApplyIcon();
152152

153153
child.BeginsGroup = item.BeginGroup;
154-
child.Tag = item.GetType().FullName;
154+
child.Tag = Item.Parent.Name + "::" + Item.Tag + "::" + item.GetType().Name;
155155
child.Caption = item.Caption.Invoke();
156156
var command = item.Command; // todo: add 'ShortcutText' to a new 'interface CommandBase : System.Windows.Input.CommandBase'
157157
child.ShortcutText = command != null
@@ -162,21 +162,14 @@ private ICommandBarControl InitializeChildControl(ICommandMenuItem item)
162162
return child;
163163
}
164164

165-
// note: HAAAAACK!!!
166-
private static int _lastHashCode;
167-
168165
private void child_Click(object sender, CommandBarButtonClickEventArgs e)
169166
{
170-
var item = _items.Select(kvp => kvp.Key).SingleOrDefault(menu => menu.GetType().FullName == e.Control.Tag) as ICommandMenuItem;
171-
if (item == null || e.Control.Target.GetHashCode() == _lastHashCode)
167+
var item = _items.Select(kvp => kvp.Key).SingleOrDefault(menu => e.Control.Tag.EndsWith(menu.GetType().Name)) as ICommandMenuItem;
168+
if (item == null)
172169
{
173170
return;
174171
}
175172

176-
// without this hack, handler runs once for each menu item that's hooked up to the command.
177-
// hash code is different on every frakkin' click. go figure. I've had it, this is the fix.
178-
_lastHashCode = e.Control.Target.GetHashCode();
179-
180173
Logger.Debug("({0}) Executing click handler for menu item '{1}', hash code {2}", GetHashCode(), e.Control.Caption, e.Control.Target.GetHashCode());
181174
item.Command.Execute(null);
182175
}

RetailCoder.VBE/UI/RubberduckUI.Designer.cs

Lines changed: 4 additions & 3 deletions
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

RetailCoder.VBE/UI/RubberduckUI.fr.resx

Lines changed: 44 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,4 @@
1-
<?xml version="1.0" encoding="UTF-8"?>
1+
<?xml version="1.0" encoding="utf-8"?>
22
<root>
33
<!--
44
Microsoft ResX Schema
@@ -59,7 +59,7 @@
5959
: using a System.ComponentModel.TypeConverter
6060
: and then encoded with base64 encoding.
6161
-->
62-
<xsd:schema xmlns:xsd="http://www.w3.org/2001/XMLSchema" xmlns:msdata="urn:schemas-microsoft-com:xml-msdata" id="root">
62+
<xsd:schema id="root" xmlns="" xmlns:xsd="http://www.w3.org/2001/XMLSchema" xmlns:msdata="urn:schemas-microsoft-com:xml-msdata">
6363
<xsd:import namespace="http://www.w3.org/XML/1998/namespace" />
6464
<xsd:element name="root" msdata:IsDataSet="true">
6565
<xsd:complexType>
@@ -1586,4 +1586,45 @@ Tous ceux qui nous ont donné une étoile ou un "like"
15861586
<data name="ReparseToolTipText" xml:space="preserve">
15871587
<value>{0}. Cliquez pour rafraîchir.</value>
15881588
</data>
1589-
</root>
1589+
<data name="IndenterSettings_PreviewCode" xml:space="preserve">
1590+
<value>Public Enum ExempleEnum
1591+
' commentaire enum.
1592+
Foo
1593+
Bar ' commentaire membre enum.
1594+
End Enum
1595+
1596+
' Procédure exemple
1597+
Sub ExampleProc()
1598+
1599+
' SMART INDENTER
1600+
' Code VB6 original gracieusement offert au projet Rubberduck par Stephen Bullen et Rob Bovey
1601+
' © 2016 Rubberduck VBA.
1602+
1603+
Dim count As Integer
1604+
Static name As String
1605+
1606+
If VousAimezRubberduck Then
1607+
' Donnez-nous une étoile sur GitHub http://github.com/rubberduck-vba/Rubberduck
1608+
' Suivez-nous sur Twitter @rubberduckvba
1609+
' Visitez http://rubberduckvba.com pour les nouvelles et mises à jour
1610+
1611+
Select Case X
1612+
Case "A"
1613+
' Si vous avez des commentaires ou suggestions, _
1614+
ou si vous trouvez du code VBA valide qui ne s'indente pas correctement,
1615+
1616+
#If VBA6 Then
1617+
MsgBox "Contactez contact@rubberduck-vba.com"
1618+
#End If
1619+
1620+
Case "Les chaînes de caractères et paramètres peuvent être" _
1621+
&amp; "alignés pour une lecture plus facile, en ignorant facultativement" _
1622+
&amp; "les opérateurs (&amp;+, etc) au début d'une ligne."
1623+
1624+
Debug.Print "X&lt;&gt;1"
1625+
End Select 'Case X
1626+
End If 'Plus d'outils? Suggestions http://github.com/rubberduck-vba/Rubberduck/Issues/New
1627+
1628+
End Sub</value>
1629+
</data>
1630+
</root>

0 commit comments

Comments
 (0)