Skip to content

Commit effd3f0

Browse files
committed
parser state fixes
1 parent 32715a5 commit effd3f0

File tree

14 files changed

+155
-150
lines changed

14 files changed

+155
-150
lines changed

RetailCoder.VBE/App.cs

Lines changed: 4 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -138,7 +138,7 @@ private async void hooks_MessageReceived(object sender, HookEventArgs e)
138138

139139
private void _stateBar_Refresh(object sender, EventArgs e)
140140
{
141-
_parser.State.RequestParse();
141+
_parser.State.OnParseRequested();
142142
}
143143

144144
private void Parser_StateChanged(object sender, EventArgs e)
@@ -153,10 +153,11 @@ public void Startup()
153153
_appMenus.Initialize();
154154
_appMenus.Localize();
155155

156-
Task.Delay(1000).ContinueWith(t =>
156+
// delay to allow the VBE to properly load. HostApplication is null until then.
157+
Task.Delay(2000).ContinueWith(t =>
157158
{
158159
_parser.State.AddBuiltInDeclarations(_vbe.HostApplication());
159-
_parser.State.RequestParse();
160+
_parser.State.OnParseRequested();
160161
});
161162

162163
//_hooks.AddHook(new LowLevelKeyboardHook(_vbe));

RetailCoder.VBE/Extension.cs

Lines changed: 2 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,5 @@
11
using System;
22
using System.ComponentModel;
3-
using System.Diagnostics;
43
using System.Runtime.InteropServices;
54
using System.Windows.Forms;
65
using Extensibility;
@@ -40,10 +39,6 @@ public void OnConnection(object Application, ext_ConnectMode ConnectMode, object
4039
_kernel.Load(new RubberduckModule(_kernel, (VBE)Application, (AddIn)AddInInst));
4140
_kernel.Load(new UI.SourceControl.SourceControlBindings());
4241
_kernel.Load(new CommandBarsModule(_kernel));
43-
44-
Debug.Print("in OnConnection, ready.");
45-
var app = _kernel.Get<App>();
46-
app.Startup();
4742
}
4843
catch (Exception exception)
4944
{
@@ -53,7 +48,8 @@ public void OnConnection(object Application, ext_ConnectMode ConnectMode, object
5348

5449
public void OnStartupComplete(ref Array custom)
5550
{
56-
51+
var app = _kernel.Get<App>();
52+
app.Startup();
5753
}
5854

5955
public void OnDisconnection(ext_DisconnectMode RemoveMode, ref Array custom)
Lines changed: 31 additions & 48 deletions
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,5 @@
11
using System.Collections.Generic;
2-
using System.Collections.ObjectModel;
32
using System.Linq;
4-
using Rubberduck.Parsing.Grammar;
53
using Rubberduck.Parsing.Symbols;
64
using Rubberduck.Parsing.VBA;
75
using Rubberduck.VBEditor;
@@ -10,71 +8,56 @@ namespace Rubberduck.Refactorings.ExtractInterface
108
{
119
public class ExtractInterfaceModel
1210
{
13-
private readonly RubberduckParserState _parseResult;
14-
public RubberduckParserState ParseResult { get { return _parseResult; } }
15-
16-
private readonly IEnumerable<Declaration> _declarations;
17-
public IEnumerable<Declaration> Declarations { get { return _declarations; } }
18-
19-
private readonly QualifiedSelection _selection;
20-
public QualifiedSelection Selection { get { return _selection; } }
21-
2211
private readonly Declaration _targetDeclaration;
2312
public Declaration TargetDeclaration { get { return _targetDeclaration; } }
2413

2514
public string InterfaceName { get; set; }
26-
public List<InterfaceMember> Members { get; set; }
2715

28-
private static readonly DeclarationType[] _declarationTypes =
16+
private IEnumerable<InterfaceMember> _members = new List<InterfaceMember>();
17+
public IEnumerable<InterfaceMember> Members { get { return _members; } set { _members = value; } }
18+
19+
private static readonly DeclarationType[] ModuleTypes =
2920
{
3021
DeclarationType.Class,
3122
DeclarationType.Document,
3223
DeclarationType.UserForm
3324
};
34-
public ReadOnlyCollection<DeclarationType> DeclarationTypes = new ReadOnlyCollection<DeclarationType>(_declarationTypes);
3525

36-
private static readonly string[] _primitiveTypes =
26+
private static readonly DeclarationType[] MemberTypes =
3727
{
38-
Tokens.Boolean,
39-
Tokens.Byte,
40-
Tokens.Date,
41-
Tokens.Decimal,
42-
Tokens.Double,
43-
Tokens.Long,
44-
Tokens.LongLong,
45-
Tokens.LongPtr,
46-
Tokens.Integer,
47-
Tokens.Single,
48-
Tokens.String,
49-
Tokens.StrPtr
28+
DeclarationType.Procedure,
29+
DeclarationType.Function,
30+
DeclarationType.PropertyGet,
31+
DeclarationType.PropertyLet,
32+
DeclarationType.PropertySet,
5033
};
51-
public ReadOnlyCollection<string> PrimitiveTypes = new ReadOnlyCollection<string>(_primitiveTypes);
5234

53-
public ExtractInterfaceModel(RubberduckParserState parseResult, QualifiedSelection selection)
35+
public ExtractInterfaceModel(RubberduckParserState state, QualifiedSelection selection)
5436
{
55-
_parseResult = parseResult;
56-
_selection = selection;
57-
_declarations = parseResult.AllDeclarations.ToList();
37+
var declarations = state.AllDeclarations.ToList();
38+
var candidates = declarations.Where(item => !item.IsBuiltIn && ModuleTypes.Contains(item.DeclarationType)).ToList();
39+
40+
_targetDeclaration = candidates.SingleOrDefault(item =>
41+
item.Project == selection.QualifiedName.Project
42+
&& item.QualifiedSelection.QualifiedName.ComponentName == selection.QualifiedName.ComponentName);
5843

59-
_targetDeclaration =
60-
_declarations.SingleOrDefault(
61-
item =>
62-
!item.IsBuiltIn && DeclarationTypes.Contains(item.DeclarationType)
63-
&& item.Project == selection.QualifiedName.Project
64-
&& item.QualifiedSelection.QualifiedName == selection.QualifiedName);
44+
if (_targetDeclaration == null)
45+
{
46+
//throw new InvalidOperationException();
47+
return;
48+
}
6549

6650
InterfaceName = "I" + TargetDeclaration.IdentifierName;
6751

68-
Members = _declarations.Where(item => !item.IsBuiltIn &&
69-
item.Project == _targetDeclaration.Project &&
70-
item.ComponentName == _targetDeclaration.ComponentName &&
71-
item.Accessibility == Accessibility.Public &&
72-
item.DeclarationType != DeclarationType.Variable &&
73-
item.DeclarationType != DeclarationType.Event)
74-
.OrderBy(o => o.Selection.StartLine)
75-
.ThenBy(t => t.Selection.StartColumn)
76-
.Select(d => new InterfaceMember(d, _declarations))
77-
.ToList();
52+
_members = declarations.Where(item => !item.IsBuiltIn
53+
&& item.Project == _targetDeclaration.Project
54+
&& item.ComponentName == _targetDeclaration.ComponentName
55+
&& (item.Accessibility == Accessibility.Public || item.Accessibility == Accessibility.Implicit)
56+
&& MemberTypes.Contains(item.DeclarationType))
57+
.OrderBy(o => o.Selection.StartLine)
58+
.ThenBy(t => t.Selection.StartColumn)
59+
.Select(d => new InterfaceMember(d, declarations))
60+
.ToList();
7861
}
7962
}
8063
}

RetailCoder.VBE/Refactorings/ExtractInterface/ExtractInterfacePresenterFactory.cs

Lines changed: 12 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,5 @@
1-
using Rubberduck.Parsing.VBA;
1+
using System.Linq;
2+
using Rubberduck.Parsing.VBA;
23
using Rubberduck.VBEditor;
34

45
namespace Rubberduck.Refactorings.ExtractInterface
@@ -7,13 +8,13 @@ public class ExtractInterfacePresenterFactory : IRefactoringPresenterFactory<Ext
78
{
89
private readonly IActiveCodePaneEditor _editor;
910
private readonly IExtractInterfaceView _view;
10-
private readonly RubberduckParserState _parseResult;
11+
private readonly RubberduckParserState _state;
1112

12-
public ExtractInterfacePresenterFactory(RubberduckParserState parseResult, IActiveCodePaneEditor editor, IExtractInterfaceView view)
13+
public ExtractInterfacePresenterFactory(RubberduckParserState state, IActiveCodePaneEditor editor, IExtractInterfaceView view)
1314
{
1415
_editor = editor;
1516
_view = view;
16-
_parseResult = parseResult;
17+
_state = state;
1718
}
1819

1920
public ExtractInterfacePresenter Create()
@@ -24,7 +25,13 @@ public ExtractInterfacePresenter Create()
2425
return null;
2526
}
2627

27-
var model = new ExtractInterfaceModel(_parseResult, selection.Value);
28+
var model = new ExtractInterfaceModel(_state, selection.Value);
29+
if (!model.Members.Any())
30+
{
31+
// don't show the UI if there's no member to extract
32+
return null;
33+
}
34+
2835
return new ExtractInterfacePresenter(_view, model);
2936
}
3037
}

RetailCoder.VBE/Refactorings/ExtractInterface/ExtractInterfaceRefactoring.cs

Lines changed: 31 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,7 @@
11
using System;
22
using System.Linq;
33
using Microsoft.Vbe.Interop;
4+
using Rubberduck.Parsing.Grammar;
45
using Rubberduck.Parsing.Symbols;
56
using Rubberduck.Parsing.VBA;
67
using Rubberduck.Refactorings.ImplementInterface;
@@ -12,14 +13,16 @@ namespace Rubberduck.Refactorings.ExtractInterface
1213
public class ExtractInterfaceRefactoring : IRefactoring
1314
{
1415
private readonly RubberduckParserState _state;
16+
private readonly IMessageBox _messageBox;
1517
private readonly IRefactoringPresenterFactory<ExtractInterfacePresenter> _factory;
1618
private readonly IActiveCodePaneEditor _editor;
1719
private ExtractInterfaceModel _model;
1820

19-
public ExtractInterfaceRefactoring(RubberduckParserState state, IRefactoringPresenterFactory<ExtractInterfacePresenter> factory,
21+
public ExtractInterfaceRefactoring(RubberduckParserState state, IMessageBox messageBox, IRefactoringPresenterFactory<ExtractInterfacePresenter> factory,
2022
IActiveCodePaneEditor editor)
2123
{
2224
_state = state;
25+
_messageBox = messageBox;
2326
_factory = factory;
2427
_editor = editor;
2528
}
@@ -34,7 +37,10 @@ public void Refactor()
3437

3538
_model = presenter.Show();
3639

37-
if (_model == null) { return; }
40+
if (_model == null)
41+
{
42+
return;
43+
}
3844

3945
AddInterface();
4046
}
@@ -56,24 +62,38 @@ private void AddInterface()
5662
var interfaceComponent = _model.TargetDeclaration.Project.VBComponents.Add(vbext_ComponentType.vbext_ct_ClassModule);
5763
interfaceComponent.Name = _model.InterfaceName;
5864

59-
_editor.InsertLines(1, GetInterface());
65+
_editor.InsertLines(1, Tokens.Option + ' ' + Tokens.Explicit + Environment.NewLine + Environment.NewLine);
66+
_editor.InsertLines(3, GetInterfaceModuleBody());
6067

6168
var module = _model.TargetDeclaration.QualifiedSelection.QualifiedName.Component.CodeModule;
6269

63-
var implementsLine = module.CountOfDeclarationLines + 1;
64-
module.InsertLines(implementsLine, "Implements " + _model.InterfaceName);
70+
_insertionLine = module.CountOfDeclarationLines + 1;
71+
module.InsertLines(_insertionLine, Tokens.Implements + ' ' + _model.InterfaceName + Environment.NewLine);
6572

66-
_state.RequestParse(ParserState.Ready);
67-
var qualifiedSelection = new QualifiedSelection(_model.TargetDeclaration.QualifiedSelection.QualifiedName,
68-
new Selection(implementsLine, 1, implementsLine, 1));
73+
_state.StateChanged += _state_StateChanged;
74+
_state.OnParseRequested();
75+
}
6976

70-
var implementInterfaceRefactoring = new ImplementInterfaceRefactoring(_state, _editor, new MessageBox());
77+
private int _insertionLine;
78+
private void _state_StateChanged(object sender, EventArgs e)
79+
{
80+
if (_state.Status != ParserState.Ready)
81+
{
82+
return;
83+
}
84+
85+
var qualifiedSelection = new QualifiedSelection(_model.TargetDeclaration.QualifiedSelection.QualifiedName, new Selection(_insertionLine, 1, _insertionLine, 1));
86+
_editor.SetSelection(qualifiedSelection);
87+
88+
var implementInterfaceRefactoring = new ImplementInterfaceRefactoring(_state, _editor, _messageBox);
7189
implementInterfaceRefactoring.Refactor(qualifiedSelection);
90+
91+
_state.StateChanged -= _state_StateChanged;
7292
}
7393

74-
private string GetInterface()
94+
private string GetInterfaceModuleBody()
7595
{
76-
return "Option Explicit" + Environment.NewLine + string.Join(Environment.NewLine, _model.Members.Where(m => m.IsSelected));
96+
return string.Join(Environment.NewLine, _model.Members.Where(m => m.IsSelected).Select(m => m.Body));
7797
}
7898
}
7999
}

RetailCoder.VBE/Refactorings/ExtractInterface/IExtractInterfaceView.cs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -6,7 +6,7 @@ namespace Rubberduck.Refactorings.ExtractInterface
66
public interface IExtractInterfaceView : IDialogView
77
{
88
string InterfaceName { get; set; }
9-
List<InterfaceMember> Members { get; set; }
9+
IEnumerable<InterfaceMember> Members { get; set; }
1010
List<string> ComponentNames { get; set; }
1111
}
1212
}

RetailCoder.VBE/Refactorings/ExtractInterface/InterfaceMember.cs

Lines changed: 9 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -20,23 +20,13 @@ public override string ToString()
2020

2121
public class InterfaceMember
2222
{
23-
public Declaration Member { get; set; }
24-
public IEnumerable<Parameter> MemberParams { get; set; }
25-
public string Type { get; set; }
23+
private Declaration Member { get; set; }
24+
private IEnumerable<Parameter> MemberParams { get; set; }
25+
private string Type { get; set; }
2626

27-
public string MemberType { get; set; }
27+
private string MemberType { get; set; }
2828

2929
public bool IsSelected { get; set; }
30-
public string MemberSignature
31-
{
32-
get
33-
{
34-
var signature = MemberType + " " + Member.IdentifierName + "(" +
35-
string.Join(", ", MemberParams.Select(m => m.ParamType)) + ")";
36-
37-
return Type == null ? signature : signature + " As " + Type;
38-
}
39-
}
4030

4131
public string FullMemberSignature
4232
{
@@ -111,10 +101,13 @@ private void GetMethodType()
111101
}
112102
}
113103

114-
public override string ToString()
104+
public string Body
115105
{
116-
return "Public " + FullMemberSignature + Environment.NewLine +
106+
get
107+
{
108+
return "Public " + FullMemberSignature + Environment.NewLine +
117109
"End " + MemberType.Split(' ').First() + Environment.NewLine;
110+
}
118111
}
119112
}
120113
}

RetailCoder.VBE/Refactorings/ImplementInterface/ImplementInterfaceRefactoring.cs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -18,7 +18,7 @@ public class ImplementInterfaceRefactoring : IRefactoring
1818
private Declaration _targetClass;
1919
private readonly IMessageBox _messageBox;
2020

21-
const string MemberBody = " Err.Raise 5";
21+
private const string MemberBody = " Err.Raise 5 'TODO: implement interface member";
2222

2323
public ImplementInterfaceRefactoring(RubberduckParserState state, IActiveCodePaneEditor editor, IMessageBox messageBox)
2424
{
@@ -182,9 +182,9 @@ private List<Parameter> GetParameters(Declaration member)
182182
.ThenBy(t => t.Selection.StartColumn)
183183
.Select(p => new Parameter
184184
{
185-
ParamAccessibility = ((VBAParser.ArgContext)p.Context).BYREF() == null ? Tokens.ByVal : Tokens.ByRef,
186-
ParamName = p.IdentifierName,
187-
ParamType = p.AsTypeName
185+
Accessibility = ((VBAParser.ArgContext)p.Context).BYREF() == null ? Tokens.ByVal : Tokens.ByRef,
186+
Name = p.IdentifierName,
187+
AsTypeName = p.AsTypeName
188188
})
189189
.ToList();
190190

RetailCoder.VBE/Refactorings/ImplementInterface/Parameter.cs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -2,13 +2,13 @@
22
{
33
public class Parameter
44
{
5-
public string ParamAccessibility { get; set; }
6-
public string ParamName { get; set; }
7-
public string ParamType { get; set; }
5+
public string Accessibility { get; set; }
6+
public string Name { get; set; }
7+
public string AsTypeName { get; set; }
88

99
public override string ToString()
1010
{
11-
return ParamAccessibility + " " + ParamName + " As " + ParamType;
11+
return Accessibility + " " + Name + " As " + AsTypeName;
1212
}
1313
}
1414
}

0 commit comments

Comments
 (0)