Skip to content

Commit cfa0ab5

Browse files
committed
Merge pull request #1054 from retailcoder/CodeExplorer
Grammar & Resolver fixes
2 parents 0588974 + c29f99e commit cfa0ab5

File tree

8 files changed

+3086
-2914
lines changed

8 files changed

+3086
-2914
lines changed

RetailCoder.VBE/Inspections/UntypedFunctionUsageInspection.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -12,7 +12,7 @@ public sealed class UntypedFunctionUsageInspection : InspectionBase
1212
public UntypedFunctionUsageInspection(RubberduckParserState state)
1313
: base(state)
1414
{
15-
Severity = CodeInspectionSeverity.Hint;
15+
Severity = CodeInspectionSeverity.Warning;
1616
}
1717

1818
public override string Description { get { return RubberduckUI.UntypedFunctionUsage_; } }

RetailCoder.VBE/Root/RubberduckModule.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -132,7 +132,7 @@ private void ApplyAbstractFactoryConvention(IEnumerable<Assembly> assemblies)
132132
.Configure(binding => binding.InSingletonScope()));
133133
}
134134

135-
// note: IInspection implementations are discovered in the Rubberduck assembly via reflection.
135+
// note: InspectionBase implementations are discovered in the Rubberduck assembly via reflection.
136136
private void BindCodeInspectionTypes()
137137
{
138138
var inspections = Assembly.GetExecutingAssembly()

Rubberduck.Parsing/Grammar/VBA.g4

Lines changed: 13 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -310,7 +310,7 @@ functionStmt :
310310
END_FUNCTION
311311
;
312312

313-
getStmt : GET WS valueStmt WS? ',' WS? valueStmt? WS? ',' WS? valueStmt;
313+
getStmt : GET WS fileNumber WS? ',' WS? valueStmt? WS? ',' WS? valueStmt;
314314

315315
goSubStmt : GOSUB WS valueStmt;
316316

@@ -359,18 +359,18 @@ macroConstStmt : MACRO_CONST WS? ambiguousIdentifier WS? EQ WS? valueStmt;
359359
macroIfThenElseStmt : macroIfBlockStmt macroElseIfBlockStmt* macroElseBlockStmt? MACRO_END_IF;
360360

361361
macroIfBlockStmt :
362-
MACRO_IF WS? ifConditionStmt WS THEN NEWLINE+
363-
(moduleBody NEWLINE+)?
362+
MACRO_IF WS? ifConditionStmt WS THEN NEWLINE*
363+
((moduleDeclarationsElement | moduleBody | block) NEWLINE*)*
364364
;
365365

366366
macroElseIfBlockStmt :
367-
MACRO_ELSEIF WS? ifConditionStmt WS THEN NEWLINE+
368-
(moduleBody NEWLINE+)?
367+
MACRO_ELSEIF WS? ifConditionStmt WS THEN NEWLINE*
368+
((moduleDeclarationsElement | moduleBody | block) NEWLINE*)*
369369
;
370370

371371
macroElseBlockStmt :
372-
MACRO_ELSE NEWLINE+
373-
(moduleBody NEWLINE+)?
372+
MACRO_ELSE NEWLINE*
373+
((moduleDeclarationsElement | moduleBody | block) NEWLINE*)*
374374
;
375375

376376
midStmt : MID WS? LPAREN WS? argsCall WS? RPAREN;
@@ -447,7 +447,7 @@ savepictureStmt : SAVEPICTURE WS valueStmt WS? ',' WS? valueStmt;
447447

448448
saveSettingStmt : SAVESETTING WS valueStmt WS? ',' WS? valueStmt WS? ',' WS? valueStmt WS? ',' WS? valueStmt;
449449

450-
seekStmt : SEEK WS valueStmt WS? ',' WS? valueStmt;
450+
seekStmt : SEEK WS fileNumber WS? ',' WS? valueStmt;
451451

452452
selectCaseStmt :
453453
SELECT WS CASE WS valueStmt NEWLINE+
@@ -500,7 +500,7 @@ typeOfStmt : TYPEOF WS valueStmt (WS IS WS type)?;
500500

501501
unloadStmt : UNLOAD WS valueStmt;
502502

503-
unlockStmt : UNLOCK WS valueStmt (WS? ',' WS? valueStmt (WS TO WS valueStmt)?)?;
503+
unlockStmt : UNLOCK WS fileNumber (WS? ',' WS? valueStmt (WS TO WS valueStmt)?)?;
504504

505505
// operator precedence is represented by rule order
506506
valueStmt :
@@ -552,7 +552,7 @@ whileWendStmt :
552552
WEND
553553
;
554554

555-
widthStmt : WIDTH WS valueStmt WS? ',' WS? valueStmt;
555+
widthStmt : WIDTH WS fileNumber WS? ',' WS? valueStmt;
556556

557557
withStmt :
558558
WITH WS (implicitCallStmt_InStmt | (NEW WS type)) NEWLINE+
@@ -797,8 +797,8 @@ LSET : L S E T;
797797
MACRO_CONST : '#' C O N S T WS;
798798
MACRO_IF : '#' I F WS;
799799
MACRO_ELSEIF : '#' E L S E I F WS;
800-
MACRO_ELSE : '#' E L S E WS;
801-
MACRO_END_IF : '#' E N D WS I F;
800+
MACRO_ELSE : '#' E L S E NEWLINE;
801+
MACRO_END_IF : '#' E N D WS I F NEWLINE;
802802
ME : M E;
803803
MID : M I D;
804804
MKDIR : M K D I R;
@@ -909,7 +909,7 @@ INTEGERLITERAL : (PLUS|MINUS)? ('0'..'9')+ ( ('e' | 'E') INTEGERLITERAL)* ('#' |
909909
DOUBLELITERAL : (PLUS|MINUS)? ('0'..'9')* '.' ('0'..'9')+ ( ('e' | 'E') (PLUS|MINUS)? ('0'..'9')+)* ('#' | '&')?;
910910
BYTELITERAL : ('0'..'9')+;
911911
// identifier
912-
IDENTIFIER : LETTER (LETTERORDIGIT)* | L_SQUARE_BRACKET ((~[!\]\r\n])+ R_SQUARE_BRACKET;
912+
IDENTIFIER : (~[!\]\(\)\r\n\t ])+ | L_SQUARE_BRACKET (~[!\]\r\n])+ R_SQUARE_BRACKET;
913913
// whitespace, line breaks, comments, ...
914914
LINE_CONTINUATION : [ \t]+ '_' '\r'? '\n' -> skip;
915915
NEWLINE : (':' WS?) | (WS? ('\r'? '\n') WS?);

Rubberduck.Parsing/Grammar/VBALexer.cs

Lines changed: 797 additions & 800 deletions
Large diffs are not rendered by default.

Rubberduck.Parsing/Grammar/VBAParser.cs

Lines changed: 2202 additions & 2067 deletions
Large diffs are not rendered by default.

Rubberduck.Parsing/Symbols/IdentifierReferenceResolver.cs

Lines changed: 44 additions & 24 deletions
Original file line numberDiff line numberDiff line change
@@ -168,11 +168,20 @@ private string FindAnnotations(int line)
168168
return null;
169169
}
170170

171-
private Declaration ResolveType(VBAParser.ComplexTypeContext context)
171+
private void ResolveType(VBAParser.ICS_S_MembersCallContext context)
172+
{
173+
var first = context.iCS_S_VariableOrProcedureCall().ambiguousIdentifier();
174+
var identifiers = new[] {first}.Concat(context.iCS_S_MemberCall()
175+
.Select(member => member.iCS_S_VariableOrProcedureCall().ambiguousIdentifier()))
176+
.ToList();
177+
ResolveType(identifiers);
178+
}
179+
180+
private void ResolveType(VBAParser.ComplexTypeContext context)
172181
{
173182
if (context == null)
174183
{
175-
return null;
184+
return;
176185
}
177186

178187
var identifiers = context.ambiguousIdentifier()
@@ -182,10 +191,16 @@ private Declaration ResolveType(VBAParser.ComplexTypeContext context)
182191
// if there's only 1 identifier, resolve to the tightest-scope match:
183192
if (identifiers.Count == 1)
184193
{
185-
return ResolveInScopeType(identifiers.Single().GetText(), _currentScope);
194+
ResolveInScopeType(identifiers.Single().GetText(), _currentScope);
195+
return;
186196
}
187197

188198
// if there's 2 or more identifiers, resolve to the deepest path:
199+
ResolveType(identifiers);
200+
}
201+
202+
private void ResolveType(IList<VBAParser.AmbiguousIdentifierContext> identifiers)
203+
{
189204
var first = identifiers[0].GetText();
190205
var projectMatch = _currentScope.ProjectName == first
191206
? _declarations.SingleOrDefault(declaration =>
@@ -223,22 +238,25 @@ private Declaration ResolveType(VBAParser.ComplexTypeContext context)
223238
if (udtMatch != null)
224239
{
225240
var udtReference = CreateReference(identifiers[2], udtMatch);
226-
241+
227242
projectMatch.AddReference(projectReference);
228243
_alreadyResolved.Add(projectReference.Context);
229244

230245
moduleMatch.AddReference(moduleReference);
231246
_alreadyResolved.Add(moduleReference.Context);
232-
247+
233248
udtMatch.AddReference(udtReference);
234249
_alreadyResolved.Add(udtReference.Context);
235-
236-
return udtMatch;
250+
251+
return;
237252
}
238253
}
239254
}
240255
else
241256
{
257+
projectMatch.AddReference(projectReference);
258+
_alreadyResolved.Add(projectReference.Context);
259+
242260
var match = _declarations.SingleOrDefault(declaration =>
243261
!declaration.IsBuiltIn && declaration.ParentDeclaration != null
244262
&& declaration.ParentDeclaration.Equals(projectMatch)
@@ -248,20 +266,19 @@ private Declaration ResolveType(VBAParser.ComplexTypeContext context)
248266
if (match != null)
249267
{
250268
var reference = CreateReference(identifiers[1], match);
251-
match.AddReference(reference);
252-
_alreadyResolved.Add(reference.Context);
253-
return match;
269+
if (reference != null)
270+
{
271+
match.AddReference(reference);
272+
_alreadyResolved.Add(reference.Context);
273+
return;
274+
}
254275
}
255276
}
256277
}
257278

258279
// first identifier didn't match current project.
259280
// if there are 3 identifiers, type isn't in current project.
260-
if (identifiers.Count == 3)
261-
{
262-
return null;
263-
}
264-
else
281+
if (identifiers.Count != 3)
265282
{
266283
var moduleMatch = _declarations.SingleOrDefault(declaration =>
267284
!declaration.IsBuiltIn && declaration.ParentDeclaration != null
@@ -288,13 +305,9 @@ private Declaration ResolveType(VBAParser.ComplexTypeContext context)
288305

289306
udtMatch.AddReference(udtReference);
290307
_alreadyResolved.Add(udtReference.Context);
291-
292-
return udtMatch;
293308
}
294309
}
295310
}
296-
297-
return null;
298311
}
299312

300313
private IEnumerable<Declaration> FindMatchingTypes(string identifier)
@@ -306,12 +319,12 @@ private IEnumerable<Declaration> FindMatchingTypes(string identifier)
306319
.ToList();
307320
}
308321

309-
private Declaration ResolveInScopeType(string identifier, Declaration scope)
322+
private void ResolveInScopeType(string identifier, Declaration scope)
310323
{
311324
var matches = FindMatchingTypes(identifier).ToList();
312325
if (matches.Count == 1)
313326
{
314-
return matches.Single();
327+
return;
315328
}
316329

317330
// more than one matching identifiers found.
@@ -324,12 +337,12 @@ private Declaration ResolveInScopeType(string identifier, Declaration scope)
324337

325338
if (sameScopeUdt.Count == 1)
326339
{
327-
return sameScopeUdt.Single();
340+
return;
328341
}
329342

330343
// todo: try to resolve identifier using referenced projects
331344

332-
return null; // match is ambiguous or unknown, return null
345+
return;
333346
}
334347

335348

@@ -709,6 +722,13 @@ public void Resolve(VBAParser.ICS_S_MembersCallContext context)
709722
return;
710723
}
711724

725+
if (context.Parent.Parent.Parent is VBAParser.VsNewContext)
726+
{
727+
// if we're in a ValueStatement/New context, we're actually resolving for a type:
728+
ResolveType(context);
729+
return;
730+
}
731+
712732
Declaration parent;
713733
if (_withBlockQualifiers.Any())
714734
{
@@ -721,7 +741,7 @@ public void Resolve(VBAParser.ICS_S_MembersCallContext context)
721741
else
722742
{
723743
parent = ResolveInternal(context.iCS_S_ProcedureOrArrayCall(), _currentScope)
724-
?? ResolveInternal(context.iCS_S_VariableOrProcedureCall(), _currentScope);
744+
?? ResolveInternal(context.iCS_S_VariableOrProcedureCall(), _currentScope);
725745
parent = ResolveType(parent);
726746
}
727747

Rubberduck.Parsing/VBA/RubberduckParserState.cs

Lines changed: 22 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -28,9 +28,22 @@ public ParserStateEventArgs(ParserState state)
2828
public ParserState State { get {return _state; } }
2929
}
3030

31+
public class ParseRequestEventArgs : EventArgs
32+
{
33+
private readonly VBComponent _component;
34+
35+
public ParseRequestEventArgs(VBComponent component)
36+
{
37+
_component = component;
38+
}
39+
40+
public VBComponent Component { get { return _component; } }
41+
public bool IsFullReparseRequest { get { return _component == null; } }
42+
}
43+
3144
public sealed class RubberduckParserState
3245
{
33-
public event EventHandler ParseRequest;
46+
public event EventHandler<ParseRequestEventArgs> ParseRequest;
3447

3548
// keys are the declarations; values indicate whether a declaration is resolved.
3649
private readonly ConcurrentDictionary<Declaration, ResolutionState> _declarations =
@@ -291,12 +304,18 @@ public void AddBuiltInDeclarations(IHostApplication hostApplication)
291304
}
292305
}
293306

294-
public void OnParseRequested()
307+
/// <summary>
308+
/// Requests reparse for specified component.
309+
/// Omit parameter to request a full reparse.
310+
/// </summary>
311+
/// <param name="component">The component to reparse.</param>
312+
public void OnParseRequested(VBComponent component = null)
295313
{
296314
var handler = ParseRequest;
297315
if (handler != null)
298316
{
299-
handler.Invoke(this, EventArgs.Empty);
317+
var args = new ParseRequestEventArgs(component);
318+
handler.Invoke(this, args);
300319
}
301320
}
302321
}

RubberduckTests/SourceControl/SCPresenterTests.cs

Lines changed: 6 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -411,7 +411,8 @@ public void OpenWorkingDir_WhenUserConfirms_RepoIsAddedToConfig()
411411

412412
//assert
413413
_configService.Verify(c => c.SaveConfiguration(It.IsAny<SourceControlConfiguration>()), Times.Once);
414-
} [TestMethod]
414+
}
415+
[TestMethod]
415416
public void InitRepository_WhenUserConfirms_StatusIsOnline()
416417
{
417418
//arrange
@@ -706,12 +707,12 @@ public void UnsyncedPresenter_AfterLogin_NewPresenterIsCreatedWithCredentials()
706707
private SourceControlConfiguration GetDummyConfig()
707708
{
708709
return new SourceControlConfiguration()
709-
{
710-
Repositories = new List<Repository>()
710+
{
711+
Repositories = new List<Repository>()
711712
{
712713
(Repository)GetDummyRepo()
713714
}
714-
};
715+
};
715716
}
716717

717718
private static IRepository GetDummyRepo()
@@ -724,4 +725,4 @@ private static IRepository GetDummyRepo()
724725
);
725726
}
726727
}
727-
}
728+
}

0 commit comments

Comments
 (0)