Skip to content

Commit 04140e2

Browse files
committed
2 parents 7fbc5d1 + 5827545 commit 04140e2

File tree

9 files changed

+220
-135
lines changed

9 files changed

+220
-135
lines changed

RetailCoder.VBE/App.cs

Lines changed: 2 additions & 50 deletions
Original file line numberDiff line numberDiff line change
@@ -84,7 +84,8 @@ private void RefreshSelection()
8484
if (!pane.IsWrappingNullReference)
8585
{
8686
selectedDeclaration = _parser.State.FindSelectedDeclaration(pane);
87-
_stateBar.SetContextSelectionCaption(GetSelectionText(selectedDeclaration));
87+
var caption = _stateBar.GetContextSelectionCaption(_vbe.ActiveCodePane, selectedDeclaration);
88+
_stateBar.SetContextSelectionCaption(caption);
8889
}
8990

9091
var currentStatus = _parser.State.Status;
@@ -99,55 +100,6 @@ private void RefreshSelection()
99100
}
100101
}
101102

102-
private string GetSelectionText(Declaration declaration)
103-
{
104-
if (declaration == null && _vbe.ActiveCodePane != null)
105-
{
106-
var selection = _vbe.ActiveCodePane.GetQualifiedSelection();
107-
if (selection.HasValue)
108-
{
109-
return selection.Value.ToString();
110-
}
111-
}
112-
else if (declaration == null && _vbe.ActiveCodePane == null)
113-
{
114-
return string.Empty;
115-
}
116-
else if (declaration != null && !declaration.IsBuiltIn && declaration.DeclarationType != DeclarationType.ClassModule && declaration.DeclarationType != DeclarationType.ProceduralModule)
117-
{
118-
var typeName = declaration.HasTypeHint
119-
? Declaration.TypeHintToTypeName[declaration.TypeHint]
120-
: declaration.AsTypeName;
121-
122-
return string.Format("{0}|{1}: {2} ({3}{4})",
123-
declaration.QualifiedSelection.Selection,
124-
declaration.QualifiedName.QualifiedModuleName,
125-
declaration.IdentifierName,
126-
RubberduckUI.ResourceManager.GetString("DeclarationType_" + declaration.DeclarationType, UI.Settings.Settings.Culture),
127-
string.IsNullOrEmpty(declaration.AsTypeName) ? string.Empty : ": " + typeName);
128-
}
129-
else if (declaration != null)
130-
{
131-
// todo: confirm this is what we want, and then refator
132-
var selection = _vbe.ActiveCodePane.GetQualifiedSelection();
133-
if (selection.HasValue)
134-
{
135-
var typeName = declaration.HasTypeHint
136-
? Declaration.TypeHintToTypeName[declaration.TypeHint]
137-
: declaration.AsTypeName;
138-
139-
return string.Format("{0}|{1}: {2} ({3}{4})",
140-
selection.Value.Selection,
141-
declaration.QualifiedName.QualifiedModuleName,
142-
declaration.IdentifierName,
143-
RubberduckUI.ResourceManager.GetString("DeclarationType_" + declaration.DeclarationType, UI.Settings.Settings.Culture),
144-
string.IsNullOrEmpty(declaration.AsTypeName) ? string.Empty : ": " + typeName);
145-
}
146-
}
147-
148-
return string.Empty;
149-
}
150-
151103
private bool ShouldEvaluateCanExecute(Declaration selectedDeclaration, ParserState currentStatus)
152104
{
153105
return _lastStatus != currentStatus ||

RetailCoder.VBE/Rubberduck.csproj

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -451,6 +451,7 @@
451451
<Compile Include="UI\CodeExplorer\Commands\AddTestModuleCommand.cs" />
452452
<Compile Include="UI\Command\MenuItems\CommandBars\AppCommandBarBase.cs" />
453453
<Compile Include="UI\Command\MenuItems\CommandBars\ContextSelectionLabelMenuItem.cs" />
454+
<Compile Include="UI\Command\MenuItems\CommandBars\IContextFormatter.cs" />
454455
<Compile Include="UI\Command\MenuItems\CommandBars\ReparseCommandMenuItem.cs" />
455456
<Compile Include="UI\Command\MenuItems\CommandBars\RubberduckCommandBar.cs" />
456457
<Compile Include="UI\Command\MenuItems\CommandBars\SerializeDeclarationsCommandMenuItem.cs" />
Lines changed: 101 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,101 @@
1+
using System;
2+
using System.Linq;
3+
using Rubberduck.Parsing.Symbols;
4+
using Rubberduck.VBEditor.SafeComWrappers.Abstract;
5+
6+
namespace Rubberduck.UI.Command.MenuItems.CommandBars
7+
{
8+
public interface IContextFormatter
9+
{
10+
/// <summary>
11+
/// Determines the formatting of the contextual selection caption.
12+
/// </summary>
13+
string Format(ICodePane activeCodePane, Declaration declaration);
14+
}
15+
16+
public class ContextFormatter : IContextFormatter
17+
{
18+
public string Format(ICodePane activeCodePane, Declaration declaration)
19+
{
20+
if (activeCodePane == null)
21+
{
22+
return string.Empty;
23+
}
24+
25+
var qualifiedSelection = activeCodePane.GetQualifiedSelection();
26+
if (declaration == null || !qualifiedSelection.HasValue)
27+
{
28+
return string.Empty;
29+
}
30+
31+
var selection = qualifiedSelection.Value;
32+
var codePaneSelectionText = selection.Selection.ToString();
33+
var contextSelectionText = Format(declaration);
34+
35+
return string.Format("{0} | {1}", codePaneSelectionText, contextSelectionText);
36+
}
37+
38+
private string Format(Declaration declaration)
39+
{
40+
var formattedDeclaration = string.Empty;
41+
var moduleName = declaration.QualifiedName.QualifiedModuleName;
42+
var typeName = declaration.HasTypeHint
43+
? Declaration.TypeHintToTypeName[declaration.TypeHint]
44+
: declaration.AsTypeName;
45+
var declarationType = RubberduckUI.ResourceManager.GetString("DeclarationType_" + declaration.DeclarationType, Settings.Settings.Culture);
46+
47+
typeName = "(" + declarationType + (string.IsNullOrEmpty(typeName) ? string.Empty : ":" + typeName) + ")";
48+
49+
if (declaration.DeclarationType.HasFlag(DeclarationType.Module))
50+
{
51+
formattedDeclaration = moduleName.ToString();
52+
}
53+
54+
if (declaration.DeclarationType.HasFlag(DeclarationType.Member))
55+
{
56+
formattedDeclaration = declaration.QualifiedName.ToString();
57+
if (declaration.DeclarationType == DeclarationType.Function
58+
|| declaration.DeclarationType == DeclarationType.PropertyGet)
59+
{
60+
formattedDeclaration += typeName;
61+
}
62+
}
63+
64+
if (declaration.DeclarationType == DeclarationType.Enumeration
65+
|| declaration.DeclarationType == DeclarationType.UserDefinedType)
66+
{
67+
formattedDeclaration = declaration.IsBuiltIn
68+
// built-in enums & UDT's don't have a module
69+
? System.IO.Path.GetFileName(moduleName.ProjectPath) + ";" + moduleName.ProjectName + "." + declaration.IdentifierName
70+
: moduleName.ToString();
71+
}
72+
73+
if (declaration.DeclarationType == DeclarationType.EnumerationMember
74+
|| declaration.DeclarationType == DeclarationType.UserDefinedTypeMember)
75+
{
76+
formattedDeclaration = string.Format("{0}.{1}.{2}",
77+
declaration.IsBuiltIn
78+
? System.IO.Path.GetFileName(moduleName.ProjectPath) + ";" + moduleName.ProjectName
79+
: moduleName.ToString(),
80+
declaration.ParentDeclaration.IdentifierName,
81+
declaration.IdentifierName);
82+
}
83+
84+
var subscripts = declaration.IsArray ? "()" : string.Empty;
85+
if (declaration.ParentDeclaration.DeclarationType.HasFlag(DeclarationType.Member))
86+
{
87+
// locals, parameters
88+
formattedDeclaration = string.Format("{0}:{1}{2} {3}", declaration.ParentDeclaration.QualifiedName, declaration.IdentifierName, subscripts, typeName);
89+
}
90+
91+
if (declaration.ParentDeclaration.DeclarationType.HasFlag(DeclarationType.Module))
92+
{
93+
// fields
94+
var withEvents = declaration.IsWithEvents ? "(WithEvents) " : string.Empty;
95+
formattedDeclaration = string.Format("{0}{1}.{2} {3}", withEvents, moduleName, declaration.IdentifierName, typeName);
96+
}
97+
98+
return string.Format("{0} | {1} {2}", formattedDeclaration.Trim(), declaration.References.Count(), RubberduckUI.ContextReferences);
99+
}
100+
}
101+
}

RetailCoder.VBE/UI/Command/MenuItems/CommandBars/RubberduckCommandBar.cs

Lines changed: 11 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,15 +1,20 @@
11
using System;
22
using System.Collections.Generic;
3+
using Rubberduck.Parsing.Symbols;
34
using Rubberduck.Parsing.VBA;
5+
using Rubberduck.VBEditor.SafeComWrappers.Abstract;
46
using Rubberduck.VBEditor.SafeComWrappers.Office.Core;
57

68
namespace Rubberduck.UI.Command.MenuItems.CommandBars
79
{
810
public class RubberduckCommandBar : AppCommandBarBase, IDisposable
911
{
10-
public RubberduckCommandBar(IEnumerable<ICommandMenuItem> items)
12+
private readonly IContextFormatter _formatter;
13+
14+
public RubberduckCommandBar(IEnumerable<ICommandMenuItem> items, IContextFormatter formatter)
1115
: base("Rubberduck", CommandBarPosition.Top, items)
1216
{
17+
_formatter = formatter;
1318
}
1419

1520
public void SetStatusLabelCaption(ParserState state, int? errorCount = null)
@@ -38,6 +43,11 @@ public void SetStatusLabelCaption(string caption, int? errorCount = null)
3843
Localize();
3944
}
4045

46+
public string GetContextSelectionCaption(ICodePane activeCodePane, Declaration declaration)
47+
{
48+
return _formatter.Format(activeCodePane, declaration);
49+
}
50+
4151
public void SetContextSelectionCaption(string caption)
4252
{
4353
var child = FindChildByTag(typeof(ContextSelectionLabelMenuItem).FullName) as ContextSelectionLabelMenuItem;

RetailCoder.VBE/UI/RubberduckUI.Designer.cs

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

RetailCoder.VBE/UI/RubberduckUI.de.resx

Lines changed: 17 additions & 14 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>
@@ -1750,31 +1750,31 @@ Allen Sternguckern, Likern &amp; Followern, für das warme Kribbeln
17501750
<data name="IndenterSettings_IndentEnumTypeAsProcedure" xml:space="preserve">
17511751
<value>Kommentare in Enums und Typen wie in Prozeduren einrücken</value>
17521752
</data>
1753-
<data name="CodeInspectionSettings_Misc_RunInspectionsOnSuccessfulParse">
1753+
<data name="CodeInspectionSettings_Misc_RunInspectionsOnSuccessfulParse" xml:space="preserve">
17541754
<value>Inspektionen nach erfolgreichem Parsen automatisch starten</value>
17551755
</data>
1756-
<data name="RubberduckReloadFailure_Title">
1756+
<data name="RubberduckReloadFailure_Title" xml:space="preserve">
17571757
<value>Rubberduck wird nicht neu geladen</value>
17581758
</data>
1759-
<data name="GeneralSettings_ShowSplash">
1759+
<data name="GeneralSettings_ShowSplash" xml:space="preserve">
17601760
<value>Ein Startlogo zu Beginn zeigen</value>
17611761
</data>
1762-
<data name="HotkeyDescription_RefactorEncapsulateField">
1762+
<data name="HotkeyDescription_RefactorEncapsulateField" xml:space="preserve">
17631763
<value>Refactor / Feld kapseln</value>
17641764
</data>
1765-
<data name="CodeExplorer_CollapseSubnodesToolTip">
1765+
<data name="CodeExplorer_CollapseSubnodesToolTip" xml:space="preserve">
17661766
<value>Knoten und alle Kindknoten einklappen</value>
17671767
</data>
1768-
<data name="CodeInspectionSettings_Misc">
1768+
<data name="CodeInspectionSettings_Misc" xml:space="preserve">
17691769
<value>Verschiedenes</value>
17701770
</data>
1771-
<data name="CodeExplorer_ExpandSubnodesToolTip">
1771+
<data name="CodeExplorer_ExpandSubnodesToolTip" xml:space="preserve">
17721772
<value>Expand node and all child nodes</value>
17731773
</data>
1774-
<data name="RubberduckReloadFailure_Message">
1774+
<data name="RubberduckReloadFailure_Message" xml:space="preserve">
17751775
<value>Werkzeugfenster wurden nicht korrekt entfernt und/oder konnten nicht wieder hergestellt werden; Die VBE könnte instabil sein. Rubberduck wird beim nächsten Start der VBE normal laden.</value>
17761776
</data>
1777-
<data name="IndenterSettings_PreviewCode">
1777+
<data name="IndenterSettings_PreviewCode" xml:space="preserve">
17781778
<value>Public Enum ExampleEnum
17791779
' Enum comment.
17801780
Foo
@@ -1815,10 +1815,13 @@ End If 'More Tools? Suggestions http://github.com/rubberduck-vba/Rubberduck
18151815

18161816
End Sub</value>
18171817
</data>
1818-
<data name="ParserErrorToolTipText">
1818+
<data name="ParserErrorToolTipText" xml:space="preserve">
18191819
<value>{0} module(s) failed to parse; click for details.</value>
18201820
</data>
1821-
<data name="ReparseToolTipText">
1821+
<data name="ReparseToolTipText" xml:space="preserve">
18221822
<value>{0}. Click to refresh.</value>
18231823
</data>
1824-
</root>
1824+
<data name="ContextReferences" xml:space="preserve">
1825+
<value>Referenzen</value>
1826+
</data>
1827+
</root>

0 commit comments

Comments
 (0)