Skip to content

Commit 89ade92

Browse files
committed
Merge branch 'Issue1826' of https://github.com/Hosch250/Rubberduck
2 parents 6a6720f + 56c4b55 commit 89ade92

File tree

9 files changed

+62
-119
lines changed

9 files changed

+62
-119
lines changed

RetailCoder.VBE/Inspections/ProcedureCanBeWrittenAsFunctionInspection.cs

Lines changed: 2 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -40,9 +40,7 @@ public override IEnumerable<InspectionResultBase> GetInspectionResults()
4040
.Where(c =>
4141
{
4242
var declaration =
43-
UserDeclarations.SingleOrDefault(d => d.DeclarationType == DeclarationType.Procedure &&
44-
d.IdentifierName == c.subroutineName().GetText() &&
45-
d.Context.GetSelection().Equals(c.GetSelection()));
43+
UserDeclarations.SingleOrDefault(d => d.Context == c);
4644

4745
if (UserDeclarations.FindInterfaceMembers().Contains(declaration))
4846
{
@@ -63,9 +61,7 @@ public override IEnumerable<InspectionResultBase> GetInspectionResults()
6361
var subStmtsNotImplementingEvents = subStmts
6462
.Where(c =>
6563
{
66-
var declaration = UserDeclarations.SingleOrDefault(d => d.DeclarationType == DeclarationType.Procedure &&
67-
d.IdentifierName == c.subroutineName().GetText() &&
68-
d.Context.GetSelection().Equals(c.GetSelection()));
64+
var declaration = UserDeclarations.SingleOrDefault(d => d.Context == c);
6965

7066
if (declaration == null) { return false; } // rather be safe than sorry
7167

Lines changed: 3 additions & 30 deletions
Original file line numberDiff line numberDiff line change
@@ -1,9 +1,5 @@
1-
using System.Linq;
2-
using System.Runtime.InteropServices;
1+
using System.Runtime.InteropServices;
32
using Microsoft.Vbe.Interop;
4-
using Rubberduck.Parsing.Annotations;
5-
using Rubberduck.Parsing.Symbols;
6-
using Rubberduck.Parsing.VBA;
73
using Rubberduck.Settings;
84
using Rubberduck.SmartIndenter;
95

@@ -13,22 +9,17 @@ namespace Rubberduck.UI.Command
139
public class IndentCurrentModuleCommand : CommandBase
1410
{
1511
private readonly VBE _vbe;
16-
private readonly RubberduckParserState _state;
1712
private readonly IIndenter _indenter;
1813

19-
public IndentCurrentModuleCommand(VBE vbe, RubberduckParserState state, IIndenter indenter)
14+
public IndentCurrentModuleCommand(VBE vbe, IIndenter indenter)
2015
{
2116
_vbe = vbe;
22-
_state = state;
2317
_indenter = indenter;
2418
}
2519

2620
public override bool CanExecute(object parameter)
2721
{
28-
var target = FindTarget(parameter);
29-
30-
return _vbe.ActiveCodePane != null && target != null &&
31-
target.Annotations.All(a => a.AnnotationType != AnnotationType.NoIndent);
22+
return _vbe.ActiveCodePane != null;
3223
}
3324

3425
public override void Execute(object parameter)
@@ -37,23 +28,5 @@ public override void Execute(object parameter)
3728
}
3829

3930
public RubberduckHotkey Hotkey { get { return RubberduckHotkey.IndentModule; } }
40-
41-
private Declaration FindTarget(object parameter)
42-
{
43-
var declaration = parameter as Declaration;
44-
if (declaration != null)
45-
{
46-
return declaration;
47-
}
48-
49-
var selectedDeclaration = _state.FindSelectedDeclaration(_vbe.ActiveCodePane);
50-
51-
while (selectedDeclaration != null && selectedDeclaration.DeclarationType.HasFlag(DeclarationType.Module))
52-
{
53-
selectedDeclaration = selectedDeclaration.ParentDeclaration;
54-
}
55-
56-
return selectedDeclaration;
57-
}
5831
}
5932
}

RetailCoder.VBE/UI/Command/IndentCurrentProcedureCommand.cs

Lines changed: 2 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,5 @@
11
using System.Runtime.InteropServices;
22
using Microsoft.Vbe.Interop;
3-
using Rubberduck.Parsing.VBA;
43
using Rubberduck.Settings;
54
using Rubberduck.SmartIndenter;
65

@@ -10,19 +9,17 @@ namespace Rubberduck.UI.Command
109
public class IndentCurrentProcedureCommand : CommandBase
1110
{
1211
private readonly VBE _vbe;
13-
private readonly RubberduckParserState _state;
1412
private readonly IIndenter _indenter;
1513

16-
public IndentCurrentProcedureCommand(VBE vbe, RubberduckParserState state, IIndenter indenter)
14+
public IndentCurrentProcedureCommand(VBE vbe, IIndenter indenter)
1715
{
1816
_vbe = vbe;
19-
_state = state;
2017
_indenter = indenter;
2118
}
2219

2320
public override bool CanExecute(object parameter)
2421
{
25-
return _state.FindSelectedDeclaration(_vbe.ActiveCodePane, true) != null;
22+
return _vbe.ActiveCodePane != null;
2623
}
2724

2825
public override void Execute(object parameter)

RetailCoder.VBE/UI/RubberduckUI.Designer.cs

Lines changed: 18 additions & 0 deletions
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

RetailCoder.VBE/UI/RubberduckUI.resx

Lines changed: 6 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1647,4 +1647,10 @@ All our stargazers, likers &amp; followers, for the warm fuzzies
16471647
<data name="SourceControl_OpenCommandPromptFailureTitle" xml:space="preserve">
16481648
<value>Failure opening command prompt</value>
16491649
</data>
1650+
<data name="SourceControl_ActivateProject" xml:space="preserve">
1651+
<value>Please open or activate a project and try again.</value>
1652+
</data>
1653+
<data name="SourceControl_NoActiveProject" xml:space="preserve">
1654+
<value>No active VBProject</value>
1655+
</data>
16501656
</root>

RetailCoder.VBE/UI/SourceControl/SourceControlViewViewModel.cs

Lines changed: 11 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -818,11 +818,18 @@ private bool ValidRepoExists()
818818
return false;
819819
}
820820

821-
var possibleRepos = _config.Repositories.Where(repo => repo.Id == _vbe.ActiveVBProject.HelpFile);
822-
var possibleCount = possibleRepos.Count();
821+
var project = _vbe.ActiveVBProject ?? (_vbe.VBProjects.Count == 1 ? _vbe.VBProjects.Item(1) : null);
823822

824-
//todo: if none are found, prompt user to create one
825-
return possibleCount == 1;
823+
if (project != null)
824+
{
825+
var possibleRepos = _config.Repositories.Where(repo => repo.Id == _vbe.ActiveVBProject.HelpFile);
826+
return possibleRepos.Count() == 1;
827+
}
828+
829+
ViewModel_ErrorThrown(this,
830+
new ErrorEventArgs(RubberduckUI.SourceControl_NoActiveProject,
831+
RubberduckUI.SourceControl_ActivateProject, NotificationType.Error));
832+
return false;
826833
}
827834

828835
private void ShowFilePicker()

Rubberduck.Parsing/ParserRuleContextExtensions.cs

Lines changed: 0 additions & 69 deletions
Original file line numberDiff line numberDiff line change
@@ -29,74 +29,5 @@ public static Selection GetSelection(this ParserRuleContext context)
2929
endCol
3030
);
3131
}
32-
33-
public static Accessibility GetAccessibility(this VBAParser.VisibilityContext context)
34-
{
35-
if (context == null)
36-
return Accessibility.Implicit;
37-
38-
return (Accessibility) Enum.Parse(typeof (Accessibility), context.GetText());
39-
}
40-
41-
public static string Signature(this VBAParser.FunctionStmtContext context)
42-
{
43-
var visibility = context.visibility();
44-
var visibilityText = visibility == null ? string.Empty : visibility.GetText();
45-
46-
var identifierText = context.functionName().identifier().GetText();
47-
var argsText = context.argList().GetText();
48-
49-
var asType = context.asTypeClause();
50-
var asTypeText = asType == null ? string.Empty : asType.GetText();
51-
52-
return (visibilityText + ' ' + Tokens.Function + ' ' + identifierText + argsText + ' ' + asTypeText).Trim();
53-
}
54-
55-
public static string Signature(this VBAParser.SubStmtContext context)
56-
{
57-
var visibility = context.visibility();
58-
var visibilityText = visibility == null ? string.Empty : visibility.GetText();
59-
60-
var identifierText = context.subroutineName().GetText();
61-
var argsText = context.argList().GetText();
62-
63-
return (visibilityText + ' ' + Tokens.Sub + ' ' + identifierText + argsText).Trim();
64-
}
65-
66-
public static string Signature(this VBAParser.PropertyGetStmtContext context)
67-
{
68-
var visibility = context.visibility();
69-
var visibilityText = visibility == null ? string.Empty : visibility.GetText();
70-
71-
var identifierText = context.functionName().identifier().GetText();
72-
var argsText = context.argList().GetText();
73-
74-
var asType = context.asTypeClause();
75-
var asTypeText = asType == null ? string.Empty : asType.GetText();
76-
77-
return (visibilityText + ' ' + Tokens.Property + ' ' + Tokens.Get + ' ' + identifierText + argsText + ' ' + asTypeText).Trim();
78-
}
79-
80-
public static string Signature(this VBAParser.PropertyLetStmtContext context)
81-
{
82-
var visibility = context.visibility();
83-
var visibilityText = visibility == null ? string.Empty : visibility.GetText();
84-
85-
var identifierText = context.subroutineName().GetText();
86-
var argsText = context.argList().GetText();
87-
88-
return (visibilityText + ' ' + Tokens.Property + ' ' + Tokens.Let + ' ' + identifierText + argsText).Trim();
89-
}
90-
91-
public static string Signature(this VBAParser.PropertySetStmtContext context)
92-
{
93-
var visibility = context.visibility();
94-
var visibilityText = visibility == null ? string.Empty : visibility.GetText();
95-
96-
var identifierText = context.subroutineName().GetText();
97-
var argsText = context.argList().GetText();
98-
99-
return (visibilityText + ' ' + Tokens.Property + ' ' + Tokens.Set + ' ' + identifierText + argsText).Trim();
100-
}
10132
}
10233
}

Rubberduck.Parsing/VBA/RubberduckParser.cs

Lines changed: 4 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -84,11 +84,10 @@ private void ReparseRequested(object sender, ParseRequestEventArgs e)
8484
_state.SetModuleState(e.Component, ParserState.Resolving);
8585
ResolveDeclarations(qualifiedName.Component,
8686
_state.ParseTrees.Find(s => s.Key == qualifiedName).Value);
87-
88-
_state.SetStatusAndFireStateChanged(ParserState.ResolvedDeclarations);
89-
87+
9088
if (_state.Status < ParserState.Error)
9189
{
90+
_state.SetStatusAndFireStateChanged(ParserState.ResolvedDeclarations);
9291
ResolveReferencesAsync();
9392
}
9493
});
@@ -170,10 +169,10 @@ public void Parse()
170169
}
171170

172171
Task.WaitAll(parseTasks);
173-
_state.SetStatusAndFireStateChanged(ParserState.ResolvedDeclarations);
174172

175173
if (_state.Status < ParserState.Error)
176174
{
175+
_state.SetStatusAndFireStateChanged(ParserState.ResolvedDeclarations);
177176
Task.WaitAll(ResolveReferencesAsync());
178177
}
179178
}
@@ -277,10 +276,10 @@ private void ParseAll()
277276
}
278277

279278
Task.WaitAll(parseTasks);
280-
_state.SetStatusAndFireStateChanged(ParserState.ResolvedDeclarations);
281279

282280
if (_state.Status < ParserState.Error)
283281
{
282+
_state.SetStatusAndFireStateChanged(ParserState.ResolvedDeclarations);
284283
ResolveReferencesAsync();
285284
}
286285
}

RubberduckTests/SourceControl/SourceControlViewModelTests.cs

Lines changed: 16 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -975,6 +975,22 @@ public void OnBrowseDefaultRepoLocation_WhenUserCancels_LocalDirectoryDoesNotCha
975975
Assert.AreEqual(originalPath, _vm.LocalDirectory);
976976
}
977977

978+
[TestMethod]
979+
public void NullProject_DisplaysError()
980+
{
981+
//arrange
982+
SetupValidVbProject();
983+
SetupVM();
984+
_vbe.Setup(v => v.ActiveVBProject).Returns((VBProject)null);
985+
_vbe.Setup(v => v.VBProjects).Returns(new Mock<VBProjects>().Object);
986+
987+
//act
988+
_vm.RefreshCommand.Execute(null);
989+
990+
//assert
991+
Assert.IsTrue(_vm.DisplayErrorMessageGrid, "Null ActiveProject did not raise error.");
992+
}
993+
978994
private const string DummyRepoId = "SourceControlTest";
979995

980996
private SourceControlSettings GetDummyConfig()

0 commit comments

Comments
 (0)