Skip to content

Commit 6e0c279

Browse files
committed
Merge branch 'next' into testsforsymbols
Merging recent changes prior to pull request.
2 parents 492cce6 + b8118f9 commit 6e0c279

Some content is hidden

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

42 files changed

+1395
-241
lines changed

RetailCoder.VBE/Inspections/ChangeParameterByRefByValQuickFix.cs

Lines changed: 32 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,6 @@
1+
using System;
12
using Antlr4.Runtime;
3+
using Rubberduck.Parsing.Grammar;
24
using Rubberduck.VBEditor;
35

46
namespace Rubberduck.Inspections
@@ -15,16 +17,38 @@ public ChangeParameterByRefByValQuickFix(ParserRuleContext context, QualifiedSel
1517

1618
public override void Fix()
1719
{
18-
var parameter = Context.GetText();
19-
var newContent = string.Concat(_newToken, " ", parameter);
20-
var selection = Selection.Selection;
21-
22-
var module = Selection.QualifiedName.Component.CodeModule;
20+
try
2321
{
24-
var lines = module.GetLines(selection.StartLine, selection.LineCount);
25-
var result = lines.Replace(parameter, newContent);
26-
module.ReplaceLine(selection.StartLine, result);
22+
dynamic context = Context;
23+
var parameter = Context.GetText();
24+
dynamic args = Context.parent;
25+
var argList = args.GetText();
26+
var module = Selection.QualifiedName.Component.CodeModule;
27+
{
28+
string result;
29+
if (context.OPTIONAL() != null)
30+
{
31+
result = parameter.Replace(Tokens.Optional, Tokens.Optional + ' ' + _newToken);
32+
}
33+
else
34+
{
35+
result = _newToken + ' ' + parameter;
36+
}
37+
38+
dynamic proc = args.parent;
39+
var startLine = proc.GetType().GetProperty("Start").GetValue(proc).Line;
40+
var stopLine = proc.GetType().GetProperty("Stop").GetValue(proc).Line;
41+
var code = module.GetLines(startLine, stopLine - startLine + 1);
42+
result = code.Replace(argList, argList.Replace(parameter, result));
43+
44+
foreach (var line in result.Split(new[] {"\r\n"}, StringSplitOptions.None))
45+
{
46+
module.ReplaceLine(startLine++, line);
47+
}
48+
}
2749
}
50+
// ReSharper disable once EmptyGeneralCatchClause
51+
catch { }
2852
}
2953
}
3054
}

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/Inspections/PassParameterByValueQuickFix.cs

Lines changed: 33 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,4 @@
1+
using System;
12
using System.Linq;
23
using Antlr4.Runtime;
34
using Rubberduck.Common;
@@ -73,14 +74,42 @@ private void FixMethods()
7374

7475
private void FixMethod(VBAParser.ArgContext context, QualifiedSelection qualifiedSelection)
7576
{
76-
var selectionLength = context.BYREF() == null ? 0 : 6;
77+
var parameter = context.GetText();
78+
var argList = context.parent.GetText();
7779

7880
var module = qualifiedSelection.QualifiedName.Component.CodeModule;
7981
{
80-
var lines = module.GetLines(context.Start.Line, 1);
82+
string result;
83+
if (context.BYREF() != null)
84+
{
85+
result = parameter.Replace(Tokens.ByRef, Tokens.ByVal);
86+
}
87+
else if (context.OPTIONAL() != null)
88+
{
89+
result = parameter.Replace(Tokens.Optional, Tokens.Optional + ' ' + Tokens.ByVal);
90+
}
91+
else
92+
{
93+
result = Tokens.ByVal + ' ' + parameter;
94+
}
8195

82-
var result = lines.Remove(context.Start.Column, selectionLength).Insert(context.Start.Column, Tokens.ByVal + ' ');
83-
module.ReplaceLine(context.Start.Line, result);
96+
var startLine = 0;
97+
var stopLine = 0;
98+
try
99+
{
100+
dynamic proc = context.parent.parent;
101+
startLine = proc.GetType().GetProperty("Start").GetValue(proc).Line;
102+
stopLine = proc.GetType().GetProperty("Stop").GetValue(proc).Line;
103+
}
104+
catch { return; }
105+
106+
var code = module.GetLines(startLine, stopLine - startLine + 1);
107+
result = code.Replace(argList, argList.Replace(parameter, result));
108+
109+
foreach (var line in result.Split(new[] { "\r\n" }, StringSplitOptions.None))
110+
{
111+
module.ReplaceLine(startLine++, line);
112+
}
84113
}
85114
}
86115
}

RetailCoder.VBE/Root/RubberduckModule.cs

Lines changed: 8 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -64,7 +64,8 @@ public override void Load()
6464
Bind<Sinks>().ToSelf().InSingletonScope();
6565
Bind<App>().ToSelf().InSingletonScope();
6666
Bind<RubberduckParserState>().ToSelf().InSingletonScope();
67-
Bind<GitProvider>().ToSelf().InSingletonScope();
67+
Bind<ISourceControlProvider>().To<GitProvider>();
68+
//Bind<GitProvider>().ToSelf().InSingletonScope();
6869
Bind<TestExplorerModel>().ToSelf().InSingletonScope();
6970
Bind<IOperatingSystem>().To<WindowsOperatingSystem>().InSingletonScope();
7071

@@ -186,6 +187,8 @@ private void ApplyConfigurationConvention(IEnumerable<Assembly> assemblies)
186187
.BindAllInterfaces()
187188
.Configure(binding => binding.InSingletonScope()));
188189

190+
Bind<IPersistable<SerializableDeclaration>>().To<XmlPersistableDeclarations>().InCallScope();
191+
189192
Bind<IPersistanceService<CodeInspectionSettings>>().To<XmlPersistanceService<CodeInspectionSettings>>().InCallScope();
190193
Bind<IPersistanceService<GeneralSettings>>().To<XmlPersistanceService<GeneralSettings>>().InCallScope();
191194
Bind<IPersistanceService<HotkeySettings>>().To<XmlPersistanceService<HotkeySettings>>().InCallScope();
@@ -408,7 +411,10 @@ private IEnumerable<ICommandMenuItem> GetRubberduckCommandBarItems()
408411
{
409412
KernelInstance.Get<ReparseCommandMenuItem>(),
410413
KernelInstance.Get<ShowParserErrorsCommandMenuItem>(),
411-
KernelInstance.Get<ContextSelectionLabelMenuItem>()
414+
KernelInstance.Get<ContextSelectionLabelMenuItem>(),
415+
//#if DEBUG
416+
// KernelInstance.Get<SerializeDeclarationsCommandMenuItem>()
417+
//#endif
412418
};
413419
}
414420

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+
}

0 commit comments

Comments
 (0)