Skip to content

Commit b8118f9

Browse files
authored
Merge pull request #2412 from retailcoder/next
French translations
2 parents 12f4d4a + 952f769 commit b8118f9

22 files changed

+559
-58
lines changed

RetailCoder.VBE/Inspections/InspectionsUI.de.resx

Lines changed: 30 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 id="root" xmlns="" xmlns:xsd="http://www.w3.org/2001/XMLSchema" xmlns:msdata="urn:schemas-microsoft-com:xml-msdata">
62+
<xsd:schema xmlns:xsd="http://www.w3.org/2001/XMLSchema" xmlns:msdata="urn:schemas-microsoft-com:xml-msdata" id="root">
6363
<xsd:import namespace="http://www.w3.org/XML/1998/namespace" />
6464
<xsd:element name="root" msdata:IsDataSet="true">
6565
<xsd:complexType>
@@ -564,4 +564,31 @@ Falls der Parameter 'null' sein kann, bitte dieses Auftreten ignorieren. 'null'
564564
<data name="MalformedAnnotationInspectionMeta" xml:space="preserve">
565565
<value>Eine Annotation in einem Kommentar konnte nicht gelesen werden.</value>
566566
</data>
567-
</root>
567+
<data name="IntroduceLocalVariableQuickFix">
568+
<value>Introduce local variable</value>
569+
</data>
570+
<data name="UndeclaredVariableInspectionMeta">
571+
<value>Code that uses undeclared variables does not compile when Option Explicit is specified. Undeclared variables are always Variant, a data type that incurs unnecessary overhead and storage.</value>
572+
</data>
573+
<data name="WriteOnlyPropertyQuickFix">
574+
<value>Add property get</value>
575+
</data>
576+
<data name="ModuleScopeDimKeywordInspectionMeta">
577+
<value>The 'Public' keyword can only be used at module level; its counterpart 'Private' can also only be used at module level. 'Dim' however, can be used to declare both procedure and module scope variables. For consistency, it would be preferable to reserve 'Dim' for locals, and thus to use 'Private' instead of 'Dim' at module level.</value>
578+
</data>
579+
<data name="ChangeDimToPrivateQuickFix">
580+
<value>Replace 'Dim' with 'Private'</value>
581+
</data>
582+
<data name="UndeclaredVariableInspectionName">
583+
<value>Undeclared variable</value>
584+
</data>
585+
<data name="ModuleScopeDimKeywordInspectionName">
586+
<value>Use of 'Dim' keyword at module level</value>
587+
</data>
588+
<data name="UndeclaredVariableInspectionResultFormat">
589+
<value>Local variable '{0}' is not declared</value>
590+
</data>
591+
<data name="ModuleScopeDimKeywordInspectionResultFormat">
592+
<value>Module-level variable '{0}' is declared with the 'Dim' keyword.</value>
593+
</data>
594+
</root>

RetailCoder.VBE/Inspections/InspectionsUI.fr.resx

Lines changed: 17 additions & 4 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 id="root" xmlns="" xmlns:xsd="http://www.w3.org/2001/XMLSchema" xmlns:msdata="urn:schemas-microsoft-com:xml-msdata">
62+
<xsd:schema xmlns:xsd="http://www.w3.org/2001/XMLSchema" xmlns:msdata="urn:schemas-microsoft-com:xml-msdata" id="root">
6363
<xsd:import namespace="http://www.w3.org/XML/1998/namespace" />
6464
<xsd:element name="root" msdata:IsDataSet="true">
6565
<xsd:complexType>
@@ -552,7 +552,8 @@
552552
<value>Remplacer la fonction '{0}' par la fonction typée équivalente</value>
553553
</data>
554554
<data name="UntypedFunctionUsageInspectionMeta" xml:space="preserve">
555-
<value />
555+
<value>Une fonction équivalente retourne une valeur 'String' et devrait préférablement être utilisée afin d'éviter les conversions implicites.
556+
Si le paramètre peut être nul, ignorer ce résultat; passer une valeur nulle à cette fonction causerait une erreur d'exécution 'type mismatch'.</value>
556557
</data>
557558
<data name="ChangeDimToPrivateQuickFix" xml:space="preserve">
558559
<value>Remplacer 'Dim' par 'Private'</value>
@@ -579,4 +580,16 @@
579580
<value>La variable locale '{0}' n'est pas déclarée</value>
580581
<comment>{0} variable name</comment>
581582
</data>
582-
</root>
583+
<data name="WriteOnlyPropertyQuickFix">
584+
<value>Ajouter un accesseur 'Property Get'</value>
585+
</data>
586+
<data name="MalformedAnnotationInspectionName">
587+
<value>Annotation incorrecte</value>
588+
</data>
589+
<data name="MalformedAnnotationInspectionResultFormat">
590+
<value>Annotation '{0}' incorrecte.</value>
591+
</data>
592+
<data name="MalformedAnnotationInspectionMeta">
593+
<value>Un commentaire contient une annotation spécifiée incorrectement.</value>
594+
</data>
595+
</root>

RetailCoder.VBE/Inspections/InspectionsUI.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 id="root" xmlns="" xmlns:xsd="http://www.w3.org/2001/XMLSchema" xmlns:msdata="urn:schemas-microsoft-com:xml-msdata">
62+
<xsd:schema xmlns:xsd="http://www.w3.org/2001/XMLSchema" xmlns:msdata="urn:schemas-microsoft-com:xml-msdata" id="root">
6363
<xsd:import namespace="http://www.w3.org/XML/1998/namespace" />
6464
<xsd:element name="root" msdata:IsDataSet="true">
6565
<xsd:complexType>
@@ -557,16 +557,16 @@ If the parameter can be null, ignore this inspection result; passing a null valu
557557
<value>{0} '{1}' is implicitly 'Variant'</value>
558558
</data>
559559
<data name="MalformedAnnotationInspectionMeta" xml:space="preserve">
560-
<value>An annotation comment is malformed.</value>
560+
<value>An annotation comment is incorrectly specified.</value>
561561
</data>
562562
<data name="MalformedAnnotationInspectionName" xml:space="preserve">
563-
<value>Malformed annotation</value>
563+
<value>Incorrect annotation</value>
564564
</data>
565565
<data name="MalformedAnnotationInspectionResultFormat" xml:space="preserve">
566-
<value>Malformed '{0}' annotation.</value>
566+
<value>Incorrect '{0}' annotation.</value>
567567
</data>
568568
<data name="WriteOnlyPropertyQuickFix" xml:space="preserve">
569-
<value>Add property get</value>
569+
<value>Add property get accessor</value>
570570
</data>
571571
<data name="ChangeDimToPrivateQuickFix" xml:space="preserve">
572572
<value>Replace 'Dim' with 'Private'</value>
@@ -593,4 +593,4 @@ If the parameter can be null, ignore this inspection result; passing a null valu
593593
<data name="IntroduceLocalVariableQuickFix" xml:space="preserve">
594594
<value>Introduce local variable</value>
595595
</data>
596-
</root>
596+
</root>

RetailCoder.VBE/Root/RubberduckModule.cs

Lines changed: 6 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -187,6 +187,8 @@ private void ApplyConfigurationConvention(IEnumerable<Assembly> assemblies)
187187
.BindAllInterfaces()
188188
.Configure(binding => binding.InSingletonScope()));
189189

190+
Bind<IPersistable<SerializableDeclaration>>().To<XmlPersistableDeclarations>().InCallScope();
191+
190192
Bind<IPersistanceService<CodeInspectionSettings>>().To<XmlPersistanceService<CodeInspectionSettings>>().InCallScope();
191193
Bind<IPersistanceService<GeneralSettings>>().To<XmlPersistanceService<GeneralSettings>>().InCallScope();
192194
Bind<IPersistanceService<HotkeySettings>>().To<XmlPersistanceService<HotkeySettings>>().InCallScope();
@@ -409,7 +411,10 @@ private IEnumerable<ICommandMenuItem> GetRubberduckCommandBarItems()
409411
{
410412
KernelInstance.Get<ReparseCommandMenuItem>(),
411413
KernelInstance.Get<ShowParserErrorsCommandMenuItem>(),
412-
KernelInstance.Get<ContextSelectionLabelMenuItem>()
414+
KernelInstance.Get<ContextSelectionLabelMenuItem>(),
415+
//#if DEBUG
416+
// KernelInstance.Get<SerializeDeclarationsCommandMenuItem>()
417+
//#endif
413418
};
414419
}
415420

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\Command\MenuItems\CommandBars\ContextSelectionLabelMenuItem.cs" />
452452
<Compile Include="UI\Command\MenuItems\CommandBars\ReparseCommandMenuItem.cs" />
453453
<Compile Include="UI\Command\MenuItems\CommandBars\RubberduckCommandBar.cs" />
454+
<Compile Include="UI\Command\MenuItems\CommandBars\SerializeDeclarationsCommandMenuItem.cs" />
454455
<Compile Include="UI\Command\MenuItems\CommandBars\ShowParserErrorsCommandMenuItem.cs" />
455456
<Compile Include="UI\Command\MenuItems\ParentMenus\CommandBarButtonFactory.cs" />
456457
<Compile Include="UI\Command\MenuItems\ParentMenus\CommandBarPopupFactory.cs" />
Lines changed: 88 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,88 @@
1+
using System;
2+
using System.Collections.Generic;
3+
using System.IO;
4+
using System.Linq;
5+
using System.Printing;
6+
using System.Text;
7+
using System.Xml;
8+
using System.Xml.Serialization;
9+
using NLog;
10+
using Rubberduck.Parsing.Symbols;
11+
using Rubberduck.Parsing.VBA;
12+
using Rubberduck.SettingsProvider;
13+
14+
namespace Rubberduck.UI.Command.MenuItems.CommandBars
15+
{
16+
public class SerializeDeclarationsCommandMenuItem : CommandMenuItemBase
17+
{
18+
public SerializeDeclarationsCommandMenuItem(CommandBase command) : base(command)
19+
{
20+
}
21+
22+
public override Func<string> Caption { get { return () => "Serialize"; } }
23+
public override string Key { get { return "SerializeDeclarations"; } }
24+
}
25+
26+
public class SerializeDeclarationsCommand : CommandBase
27+
{
28+
private readonly RubberduckParserState _state;
29+
private readonly IPersistable<SerializableDeclaration> _service;
30+
31+
public SerializeDeclarationsCommand(RubberduckParserState state, IPersistable<SerializableDeclaration> service)
32+
: base(LogManager.GetCurrentClassLogger())
33+
{
34+
_state = state;
35+
_service = service;
36+
}
37+
38+
protected override bool CanExecuteImpl(object parameter)
39+
{
40+
return _state.Status == ParserState.Ready;
41+
}
42+
43+
private static readonly string BasePath =
44+
Path.Combine(Environment.GetFolderPath(Environment.SpecialFolder.ApplicationData), "Rubberduck");
45+
46+
protected override void ExecuteImpl(object parameter)
47+
{
48+
var path = Path.Combine(BasePath, "declarations");
49+
if (!Directory.Exists(path)) { Directory.CreateDirectory(path); }
50+
51+
var declarations = _state.AllDeclarations
52+
.Where(declaration => declaration.IsBuiltIn)
53+
.Select(declaration => new SerializableDeclaration(declaration))
54+
.GroupBy(declaration => declaration.QualifiedMemberName.QualifiedModuleName.ProjectPath);
55+
foreach (var project in declarations)
56+
{
57+
System.Diagnostics.Debug.Assert(path != null, "project path isn't supposed to be null");
58+
59+
var filename = Path.GetFileNameWithoutExtension(project.Key) + ".xml";
60+
_service.Persist(Path.Combine(path, filename), project);
61+
}
62+
}
63+
}
64+
65+
public class XmlPersistableDeclarations : IPersistable<SerializableDeclaration>
66+
{
67+
public void Persist(string path, IEnumerable<SerializableDeclaration> items)
68+
{
69+
if (string.IsNullOrEmpty(path)) { throw new InvalidOperationException(); }
70+
71+
var emptyNamespace = new XmlSerializerNamespaces(new[] { XmlQualifiedName.Empty });
72+
using (var writer = new StreamWriter(path, false))
73+
{
74+
var serializer = new XmlSerializer(typeof(SerializableDeclaration));
75+
foreach (var item in items)
76+
{
77+
serializer.Serialize(writer, item, emptyNamespace);
78+
}
79+
}
80+
}
81+
82+
public IEnumerable<SerializableDeclaration> Load(string path)
83+
{
84+
if (string.IsNullOrEmpty(path)) { throw new InvalidOperationException(); }
85+
throw new NotImplementedException();
86+
}
87+
}
88+
}

RetailCoder.VBE/UI/RubberduckUI.de.resx

Lines changed: 48 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1774,4 +1774,51 @@ Allen Sternguckern, Likern &amp; Followern, für das warme Kribbeln
17741774
<data name="RubberduckReloadFailure_Message">
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-
</root>
1777+
<data name="IndenterSettings_PreviewCode">
1778+
<value>Public Enum ExampleEnum
1779+
' Enum comment.
1780+
Foo
1781+
Bar ' Member comment.
1782+
End Enum
1783+
1784+
' Example Procedure
1785+
Sub ExampleProc()
1786+
1787+
' SMART INDENTER
1788+
' Original VB6 code graciously offered to Rubberduck by Stephen Bullen &amp; Rob Bovey
1789+
' © 2016 by Rubberduck VBA.
1790+
1791+
Dim count As Integer
1792+
Static name As String
1793+
1794+
If YouLikeRubberduck Then
1795+
' Star us on GitHub http://github.com/rubberduck-vba/Rubberduck
1796+
' Follow us on Twitter @rubberduckvba
1797+
' Visit http://rubberduckvba.com for news and updates
1798+
1799+
Select Case X
1800+
Case "A"
1801+
' If you have any comments or suggestions, _
1802+
or find valid VBA code that isn't indented correctly,
1803+
1804+
#If VBA6 Then
1805+
MsgBox "Contact contact@rubberduck-vba.com"
1806+
#End If
1807+
1808+
Case "Continued strings and parameters can be" _
1809+
&amp; "lined up for easier reading, optionally ignoring" _
1810+
&amp; "any operators (&amp;+, etc) at the start of the line."
1811+
1812+
Debug.Print "X&lt;&gt;1"
1813+
End Select 'Case X
1814+
End If 'More Tools? Suggestions http://github.com/rubberduck-vba/Rubberduck/Issues/New
1815+
1816+
End Sub</value>
1817+
</data>
1818+
<data name="ParserErrorToolTipText">
1819+
<value>{0} module(s) failed to parse; click for details.</value>
1820+
</data>
1821+
<data name="ReparseToolTipText">
1822+
<value>{0}. Click to refresh.</value>
1823+
</data>
1824+
</root>

0 commit comments

Comments
 (0)