Skip to content

Commit 94bac46

Browse files
authored
Merge pull request #2488 from MDoerner/CustomDeclarationLoading
Custom declaration loading and some fixes from retailcoder
2 parents f572046 + 7ca2d78 commit 94bac46

File tree

7 files changed

+205
-59
lines changed

7 files changed

+205
-59
lines changed

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

Lines changed: 10 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -45,11 +45,15 @@ private string Format(Declaration declaration)
4545

4646
typeName = "(" + declarationType + (string.IsNullOrEmpty(typeName) ? string.Empty : ":" + typeName) + ")";
4747

48-
if (declaration.DeclarationType.HasFlag(DeclarationType.Module))
48+
if (declaration.DeclarationType.HasFlag(DeclarationType.Project))
49+
{
50+
formattedDeclaration = System.IO.Path.GetFileName(declaration.QualifiedName.QualifiedModuleName.ProjectPath) + ";" + declaration.IdentifierName;
51+
}
52+
else if (declaration.DeclarationType.HasFlag(DeclarationType.Module))
4953
{
5054
formattedDeclaration = moduleName.ToString();
5155
}
52-
56+
5357
if (declaration.DeclarationType.HasFlag(DeclarationType.Member))
5458
{
5559
formattedDeclaration = declaration.QualifiedName.ToString();
@@ -59,7 +63,7 @@ private string Format(Declaration declaration)
5963
formattedDeclaration += typeName;
6064
}
6165
}
62-
66+
6367
if (declaration.DeclarationType == DeclarationType.Enumeration
6468
|| declaration.DeclarationType == DeclarationType.UserDefinedType)
6569
{
@@ -68,8 +72,7 @@ private string Format(Declaration declaration)
6872
? System.IO.Path.GetFileName(moduleName.ProjectPath) + ";" + moduleName.ProjectName + "." + declaration.IdentifierName
6973
: moduleName.ToString();
7074
}
71-
72-
if (declaration.DeclarationType == DeclarationType.EnumerationMember
75+
else if (declaration.DeclarationType == DeclarationType.EnumerationMember
7376
|| declaration.DeclarationType == DeclarationType.UserDefinedTypeMember)
7477
{
7578
formattedDeclaration = string.Format("{0}.{1}.{2}",
@@ -81,13 +84,13 @@ private string Format(Declaration declaration)
8184
}
8285

8386
var subscripts = declaration.IsArray ? "()" : string.Empty;
84-
if (declaration.ParentDeclaration.DeclarationType.HasFlag(DeclarationType.Member))
87+
if (declaration.ParentDeclaration != null && declaration.ParentDeclaration.DeclarationType.HasFlag(DeclarationType.Member))
8588
{
8689
// locals, parameters
8790
formattedDeclaration = string.Format("{0}:{1}{2} {3}", declaration.ParentDeclaration.QualifiedName, declaration.IdentifierName, subscripts, typeName);
8891
}
8992

90-
if (declaration.ParentDeclaration.DeclarationType.HasFlag(DeclarationType.Module))
93+
if (declaration.ParentDeclaration != null && declaration.ParentDeclaration.DeclarationType.HasFlag(DeclarationType.Module))
9194
{
9295
// fields
9396
var withEvents = declaration.IsWithEvents ? "(WithEvents) " : string.Empty;

Rubberduck.Parsing/Symbols/AliasDeclarations.cs

Lines changed: 73 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -14,6 +14,7 @@ public class AliasDeclarations : ICustomDeclarationLoader
1414
private Declaration _fileSystemModule;
1515
private Declaration _interactionModule;
1616
private Declaration _stringsModule;
17+
private Declaration _dateTimeModule;
1718

1819
public AliasDeclarations(RubberduckParserState state)
1920
{
@@ -48,12 +49,21 @@ public IReadOnlyList<Declaration> Load()
4849
Grammar.Tokens.RightB,
4950
Grammar.Tokens.RTrim,
5051
Grammar.Tokens.String,
51-
Grammar.Tokens.UCase
52+
Grammar.Tokens.UCase,
53+
Grammar.Tokens.Date,
54+
Grammar.Tokens.Time,
5255
};
5356

5457
private IReadOnlyList<Declaration> AddAliasDeclarations()
5558
{
56-
UpdateAliasFunctionModulesFromReferencedProjects(_state);
59+
var finder = new DeclarationFinder(_state.AllDeclarations, new CommentNode[] { }, new IAnnotation[] { });
60+
61+
if (WeHaveAlreadyLoadedTheDeclarationsBefore(finder))
62+
{
63+
return new List<Declaration>();
64+
}
65+
66+
UpdateAliasFunctionModulesFromReferencedProjects(finder);
5767

5868
if (NoReferenceToProjectContainingTheFunctionAliases())
5969
{
@@ -64,13 +74,11 @@ private IReadOnlyList<Declaration> AddAliasDeclarations()
6474
var functionAliases = FunctionAliasesWithoutParameters();
6575
AddParametersToAliasesFromReferencedFunctions(functionAliases, possiblyAliasedFunctions);
6676

67-
return functionAliases;
77+
return functionAliases.Concat<Declaration>(PropertyGetDeclarations()).ToList();
6878
}
6979

70-
private void UpdateAliasFunctionModulesFromReferencedProjects(RubberduckParserState state)
80+
private void UpdateAliasFunctionModulesFromReferencedProjects(DeclarationFinder finder)
7181
{
72-
var finder = new DeclarationFinder(state.AllDeclarations, new CommentNode[] {}, new IAnnotation[] {});
73-
7482
var vba = finder.FindProject("VBA");
7583
if (vba == null)
7684
{
@@ -83,6 +91,20 @@ private void UpdateAliasFunctionModulesFromReferencedProjects(RubberduckParserSt
8391
_fileSystemModule = finder.FindStdModule("FileSystem", vba, true);
8492
_interactionModule = finder.FindStdModule("Interaction", vba, true);
8593
_stringsModule = finder.FindStdModule("Strings", vba, true);
94+
_dateTimeModule = finder.FindStdModule("DateTime", vba, true);
95+
}
96+
97+
98+
private static bool WeHaveAlreadyLoadedTheDeclarationsBefore(DeclarationFinder finder)
99+
{
100+
return ThereIsAGlobalBuiltInErrVariableDeclaration(finder);
101+
}
102+
103+
private static bool ThereIsAGlobalBuiltInErrVariableDeclaration(DeclarationFinder finder)
104+
{
105+
return finder.MatchName(Grammar.Tokens.Err).Any(declaration => declaration.IsBuiltIn
106+
&& declaration.DeclarationType == DeclarationType.Variable
107+
&& declaration.Accessibility == Accessibility.Global);
86108
}
87109

88110

@@ -102,6 +124,50 @@ private List<Declaration> ReferencedBuiltInFunctionsThatMightHaveAnAlias(Rubberd
102124
return functions.ToList();
103125
}
104126

127+
private List<PropertyGetDeclaration> PropertyGetDeclarations()
128+
{
129+
return new List<PropertyGetDeclaration>
130+
{
131+
DatePropertyGet(),
132+
TimePropertyGet(),
133+
};
134+
}
135+
136+
private PropertyGetDeclaration DatePropertyGet()
137+
{
138+
return new PropertyGetDeclaration(
139+
new QualifiedMemberName(_dateTimeModule.QualifiedName.QualifiedModuleName, "Date"),
140+
_dateTimeModule,
141+
_dateTimeModule,
142+
"Variant",
143+
null,
144+
string.Empty,
145+
Accessibility.Global,
146+
null,
147+
new Selection(),
148+
false,
149+
true,
150+
new List<IAnnotation>(),
151+
new Attributes());
152+
}
153+
154+
private PropertyGetDeclaration TimePropertyGet()
155+
{
156+
return new PropertyGetDeclaration(
157+
new QualifiedMemberName(_dateTimeModule.QualifiedName.QualifiedModuleName, "Time"),
158+
_dateTimeModule,
159+
_dateTimeModule,
160+
"Variant",
161+
null,
162+
string.Empty,
163+
Accessibility.Global,
164+
null,
165+
new Selection(),
166+
false,
167+
true,
168+
new List<IAnnotation>(),
169+
new Attributes());
170+
}
105171

106172
private List<FunctionDeclaration> FunctionAliasesWithoutParameters()
107173
{
@@ -128,7 +194,7 @@ private List<FunctionDeclaration> FunctionAliasesWithoutParameters()
128194
RightBFunction(),
129195
RTrimFunction(),
130196
StringFunction(),
131-
UCaseFunction()
197+
UCaseFunction(),
132198
};
133199
}
134200

Rubberduck.Parsing/Symbols/DebugDeclarations.cs

Lines changed: 7 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -21,7 +21,7 @@ public IReadOnlyList<Declaration> Load()
2121
{
2222
var finder = new DeclarationFinder(_state.AllDeclarations, new CommentNode[] { }, new IAnnotation[] { });
2323

24-
if (ThereIsAGlobalBuiltInErrVariableDeclaration(finder))
24+
if (WeHaveAlreadyLoadedTheDeclarationsBefore(finder))
2525
{
2626
return new List<Declaration>();
2727
}
@@ -37,9 +37,14 @@ public IReadOnlyList<Declaration> Load()
3737
return LoadDebugDeclarations(vba);
3838
}
3939

40+
private static bool WeHaveAlreadyLoadedTheDeclarationsBefore(DeclarationFinder finder)
41+
{
42+
return ThereIsAGlobalBuiltInErrVariableDeclaration(finder);
43+
}
44+
4045
private static bool ThereIsAGlobalBuiltInErrVariableDeclaration(DeclarationFinder finder)
4146
{
42-
return finder.MatchName(Tokens.Err).Any(declaration => declaration.IsBuiltIn
47+
return finder.MatchName(Grammar.Tokens.Err).Any(declaration => declaration.IsBuiltIn
4348
&& declaration.DeclarationType == DeclarationType.Variable
4449
&& declaration.Accessibility == Accessibility.Global);
4550
}

Rubberduck.Parsing/Symbols/DeclarationFinder.cs

Lines changed: 18 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -140,6 +140,24 @@ public Declaration FindStdModule(string name, Declaration parent = null, bool in
140140
return result;
141141
}
142142

143+
public Declaration FindClassModule(string name, Declaration parent = null, bool includeBuiltIn = false)
144+
{
145+
Declaration result = null;
146+
try
147+
{
148+
var matches = MatchName(name);
149+
result = matches.SingleOrDefault(declaration => declaration.DeclarationType.HasFlag(DeclarationType.ClassModule)
150+
&& (parent == null || parent.Equals(declaration.ParentDeclaration))
151+
&& (includeBuiltIn || !declaration.IsBuiltIn));
152+
}
153+
catch (InvalidOperationException exception)
154+
{
155+
Logger.Error(exception, "Multiple matches found for class module '{0}'.", name);
156+
}
157+
158+
return result;
159+
}
160+
143161
public Declaration FindReferencedProject(Declaration callingProject, string referencedProjectName)
144162
{
145163
return FindInReferencedProjectByPriority(callingProject, referencedProjectName, p => p.DeclarationType.HasFlag(DeclarationType.Project));

Rubberduck.Parsing/Symbols/FormEventDeclarations.cs

Lines changed: 2 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -33,12 +33,11 @@ private static Declaration FormsClassModuleFromParserState(RubberduckParserState
3333
var msForms = finder.FindProject("MSForms");
3434
if (msForms == null)
3535
{
36-
// If the VBA project is null, we haven't loaded any COM references;
37-
// we're in a unit test and the mock project didn't setup any references.
36+
//The corresponding COM reference has not been loaded.
3837
return null;
3938
}
4039

41-
return finder.FindStdModule("FormEvents", msForms, true);
40+
return finder.FindClassModule("FormEvents", msForms, true);
4241
}
4342

4443

Rubberduck.Parsing/Symbols/SpecialFormDeclarations.cs

Lines changed: 20 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -10,38 +10,51 @@ namespace Rubberduck.Parsing.Symbols
1010
{
1111
public class SpecialFormDeclarations : ICustomDeclarationLoader
1212
{
13-
private readonly DeclarationFinder _finder;
13+
private readonly RubberduckParserState _state;
1414

1515
public SpecialFormDeclarations(RubberduckParserState state)
1616
{
17-
_finder = new DeclarationFinder(state.AllDeclarations, new CommentNode[] { }, new IAnnotation[] { });
17+
_state = state;
1818
}
1919

2020

2121
public IReadOnlyList<Declaration> Load()
2222
{
23-
if (ThereIsAGlobalBuiltInErrVariableDeclaration(_finder))
23+
var finder = new DeclarationFinder(_state.AllDeclarations, new CommentNode[] { }, new IAnnotation[] { });
24+
25+
if (WeHaveAlreadyLoadedTheDeclarationsBefore(finder))
2426
{
2527
return new List<Declaration>();
2628
}
2729

28-
var vba = _finder.FindProject("VBA");
30+
var vba = finder.FindProject("VBA");
2931
if (vba == null)
3032
{
3133
// If the VBA project is null, we haven't loaded any COM references;
3234
// we're in a unit test and the mock project didn't setup any references.
3335
return new List<Declaration>();
3436
}
3537

36-
var informationModule = _finder.FindStdModule("Information", vba, true);
37-
Debug.Assert(informationModule != null, "We expect the information module to exist in the VBA project.");
38+
var informationModule = finder.FindStdModule("Information", vba, true);
39+
if (informationModule == null)
40+
{
41+
//This should not happen under normal circumstances.
42+
//Most probably, we are in a test that only addded parts of the VBA project.
43+
return new List<Declaration>();
44+
}
3845

3946
return LoadSpecialFormDeclarations(informationModule);
4047
}
4148

49+
50+
private static bool WeHaveAlreadyLoadedTheDeclarationsBefore(DeclarationFinder finder)
51+
{
52+
return ThereIsAGlobalBuiltInErrVariableDeclaration(finder);
53+
}
54+
4255
private static bool ThereIsAGlobalBuiltInErrVariableDeclaration(DeclarationFinder finder)
4356
{
44-
return finder.MatchName(Tokens.Err).Any(declaration => declaration.IsBuiltIn
57+
return finder.MatchName(Grammar.Tokens.Err).Any(declaration => declaration.IsBuiltIn
4558
&& declaration.DeclarationType == DeclarationType.Variable
4659
&& declaration.Accessibility == Accessibility.Global);
4760
}

0 commit comments

Comments
 (0)