33using Microsoft . Vbe . Interop ;
44using NLog ;
55using Rubberduck . Common ;
6- using Rubberduck . Common . Dispatch ;
76using Rubberduck . Parsing ;
87using Rubberduck . Parsing . Symbols ;
98using Rubberduck . Parsing . VBA ;
109using Rubberduck . Settings ;
1110using Rubberduck . UI ;
1211using Rubberduck . UI . Command . MenuItems ;
1312using System ;
14- using System . Collections . Generic ;
15- using System . Diagnostics ;
1613using System . Globalization ;
17- using System . Linq ;
18- using System . Runtime . InteropServices . ComTypes ;
1914using System . Threading . Tasks ;
2015using System . Windows . Forms ;
21- using Rubberduck . UI . SourceControl ;
22- using Rubberduck . VBEditor . Extensions ;
2316
2417namespace Rubberduck
2518{
2619 public sealed class App : IDisposable
2720 {
28- private const string FILE_TARGET_NAME = "file" ;
2921 private readonly VBE _vbe ;
3022 private readonly IMessageBox _messageBox ;
31- private IRubberduckParser _parser ;
23+ private readonly IRubberduckParser _parser ;
3224 private AutoSave . AutoSave _autoSave ;
3325 private IGeneralConfigService _configService ;
3426 private readonly IAppMenu _appMenus ;
3527 private RubberduckCommandBar _stateBar ;
3628 private IRubberduckHooks _hooks ;
37- private bool _handleSinkEvents = true ;
38- private readonly BranchesViewViewModel _branchesVM ;
39- private readonly SourceControlViewViewModel _sourceControlPanelVM ;
4029 private readonly UI . Settings . Settings _settings ;
4130
4231 private static readonly Logger Logger = LogManager . GetCurrentClassLogger ( ) ;
43-
44- private VBProjectsEventsSink _sink ;
32+
4533 private Configuration _config ;
4634
47- private readonly IConnectionPoint _projectsEventsConnectionPoint ;
48- private readonly int _projectsEventsCookie ;
49-
50- private readonly IDictionary < string , Tuple < IConnectionPoint , int > > _componentsEventsConnectionPoints =
51- new Dictionary < string , Tuple < IConnectionPoint , int > > ( ) ;
52- private readonly IDictionary < string , Tuple < IConnectionPoint , int > > _referencesEventsConnectionPoints =
53- new Dictionary < string , Tuple < IConnectionPoint , int > > ( ) ;
54-
5535 public App ( VBE vbe , IMessageBox messageBox ,
5636 UI . Settings . Settings settings ,
5737 IRubberduckParser parser ,
5838 IGeneralConfigService configService ,
5939 IAppMenu appMenus ,
6040 RubberduckCommandBar stateBar ,
61- IRubberduckHooks hooks ,
62- SourceControlDockablePresenter sourceControlPresenter )
41+ IRubberduckHooks hooks )
6342 {
6443 _vbe = vbe ;
6544 _messageBox = messageBox ;
@@ -71,52 +50,14 @@ public App(VBE vbe, IMessageBox messageBox,
7150 _stateBar = stateBar ;
7251 _hooks = hooks ;
7352
74- var sourceControlPanel = ( SourceControlPanel ) sourceControlPresenter . Window ( ) ;
75- _sourceControlPanelVM = ( SourceControlViewViewModel ) sourceControlPanel . ViewModel ;
76- _branchesVM = ( BranchesViewViewModel ) _sourceControlPanelVM . TabItems . Single ( t => t . ViewModel . Tab == SourceControlTab . Branches ) . ViewModel ;
77-
78- _sourceControlPanelVM . OpenRepoStarted += DisableSinkEventHandlers ;
79- _sourceControlPanelVM . OpenRepoCompleted += EnableSinkEventHandlersAndUpdateCache ;
80-
81- _branchesVM . LoadingComponentsStarted += DisableSinkEventHandlers ;
82- _branchesVM . LoadingComponentsCompleted += EnableSinkEventHandlersAndUpdateCache ;
83-
8453 _hooks . MessageReceived += _hooks_MessageReceived ;
8554 _configService . SettingsChanged += _configService_SettingsChanged ;
8655 _parser . State . StateChanged += Parser_StateChanged ;
8756 _parser . State . StatusMessageUpdate += State_StatusMessageUpdate ;
8857 _stateBar . Refresh += _stateBar_Refresh ;
89-
90- _sink = new VBProjectsEventsSink ( ) ;
91- var connectionPointContainer = ( IConnectionPointContainer ) _vbe . VBProjects ;
92- var interfaceId = typeof ( _dispVBProjectsEvents ) . GUID ;
93- connectionPointContainer . FindConnectionPoint ( ref interfaceId , out _projectsEventsConnectionPoint ) ;
94-
95- _sink . ProjectAdded += sink_ProjectAdded ;
96- _sink . ProjectRemoved += sink_ProjectRemoved ;
97- _sink . ProjectActivated += sink_ProjectActivated ;
98- _sink . ProjectRenamed += sink_ProjectRenamed ;
99-
100- _projectsEventsConnectionPoint . Advise ( _sink , out _projectsEventsCookie ) ;
10158 UiDispatcher . Initialize ( ) ;
10259 }
10360
104- private void EnableSinkEventHandlersAndUpdateCache ( object sender , EventArgs e )
105- {
106- _handleSinkEvents = true ;
107-
108- // update cache
109- _parser . State . RemoveProject ( _vbe . ActiveVBProject . HelpFile ) ;
110- _parser . State . AddProject ( _vbe . ActiveVBProject ) ;
111-
112- _parser . State . OnParseRequested ( this ) ;
113- }
114-
115- private void DisableSinkEventHandlers ( object sender , EventArgs e )
116- {
117- _handleSinkEvents = false ;
118- }
119-
12061 private void State_StatusMessageUpdate ( object sender , RubberduckStatusMessageEventArgs e )
12162 {
12263 var message = e . Message ;
@@ -216,7 +157,7 @@ public void Shutdown()
216157 }
217158 }
218159
219- #region sink handlers. todo: move to another class
160+ /* #region sink handlers.
220161 async void sink_ProjectRemoved(object sender, DispatcherEventArgs<VBProject> e)
221162 {
222163 if (!_handleSinkEvents || !_vbe.IsInDesignMode()) { return; }
@@ -232,33 +173,10 @@ async void sink_ProjectRemoved(object sender, DispatcherEventArgs<VBProject> e)
232173 var projectId = e.Item.HelpFile;
233174 Debug.Assert(projectId != null);
234175
235- _componentsEventsSinks . Remove ( projectId ) ;
236- _referencesEventsSinks . Remove ( projectId ) ;
237176 _parser.State.RemoveProject(e.Item);
238177 _parser.State.OnParseRequested(this);
239-
240- Logger . Debug ( "Project '{0}' was removed." , e . Item . Name ) ;
241- Tuple < IConnectionPoint , int > componentsTuple ;
242- if ( _componentsEventsConnectionPoints . TryGetValue ( projectId , out componentsTuple ) )
243- {
244- componentsTuple . Item1 . Unadvise ( componentsTuple . Item2 ) ;
245- _componentsEventsConnectionPoints . Remove ( projectId ) ;
246- }
247-
248- Tuple < IConnectionPoint , int > referencesTuple ;
249- if ( _referencesEventsConnectionPoints . TryGetValue ( projectId , out referencesTuple ) )
250- {
251- referencesTuple . Item1 . Unadvise ( referencesTuple . Item2 ) ;
252- _referencesEventsConnectionPoints . Remove ( projectId ) ;
253- }
254178 }
255179
256- private readonly IDictionary < string , VBComponentsEventsSink > _componentsEventsSinks =
257- new Dictionary < string , VBComponentsEventsSink > ( ) ;
258-
259- private readonly IDictionary < string , ReferencesEventsSink > _referencesEventsSinks =
260- new Dictionary < string , ReferencesEventsSink > ( ) ;
261-
262180 async void sink_ProjectAdded(object sender, DispatcherEventArgs<VBProject> e)
263181 {
264182 if (!_handleSinkEvents || !_vbe.IsInDesignMode()) { return; }
@@ -285,37 +203,6 @@ async void sink_ProjectAdded(object sender, DispatcherEventArgs<VBProject> e)
285203 _parser.State.OnParseRequested(sender);
286204 }
287205
288- private void RegisterComponentsEventSink ( VBComponents components , string projectId )
289- {
290- if ( _componentsEventsSinks . ContainsKey ( projectId ) )
291- {
292- // already registered - this is caused by the initial load+rename of a project in the VBE
293- Logger . Debug ( "Components sink already registered." ) ;
294- return ;
295- }
296-
297- var connectionPointContainer = ( IConnectionPointContainer ) components ;
298- var interfaceId = typeof ( _dispVBComponentsEvents ) . GUID ;
299-
300- IConnectionPoint connectionPoint ;
301- connectionPointContainer . FindConnectionPoint ( ref interfaceId , out connectionPoint ) ;
302-
303- var componentsSink = new VBComponentsEventsSink ( ) ;
304- componentsSink . ComponentActivated += sink_ComponentActivated ;
305- componentsSink . ComponentAdded += sink_ComponentAdded ;
306- componentsSink . ComponentReloaded += sink_ComponentReloaded ;
307- componentsSink . ComponentRemoved += sink_ComponentRemoved ;
308- componentsSink . ComponentRenamed += sink_ComponentRenamed ;
309- componentsSink . ComponentSelected += sink_ComponentSelected ;
310- _componentsEventsSinks . Add ( projectId , componentsSink ) ;
311-
312- int cookie ;
313- connectionPoint . Advise ( componentsSink , out cookie ) ;
314-
315- _componentsEventsConnectionPoints . Add ( projectId , Tuple . Create ( connectionPoint , cookie ) ) ;
316- Logger . Debug ( "Components sink registered and advising." ) ;
317- }
318-
319206 async void sink_ComponentSelected(object sender, DispatcherEventArgs<VBComponent> e)
320207 {
321208 if (!_handleSinkEvents || !_vbe.IsInDesignMode()) { return; }
@@ -324,8 +211,6 @@ async void sink_ComponentSelected(object sender, DispatcherEventArgs<VBComponent
324211 {
325212 return;
326213 }
327-
328- // todo: keep Code Explorer in sync with Project Explorer
329214 }
330215
331216 async void sink_ComponentRenamed(object sender, DispatcherRenamedEventArgs<VBComponent> e)
@@ -356,25 +241,8 @@ async void sink_ComponentRenamed(object sender, DispatcherRenamedEventArgs<VBCom
356241 // with two Document-component types just skip the Worksheet component
357242 ((ClassModuleDeclaration) componentDeclaration).Supertypes.All(a => a.IdentifierName != "Worksheet"))
358243 {
359- _componentsEventsSinks . Remove ( projectId ) ;
360- _referencesEventsSinks . Remove ( projectId ) ;
361244 _parser.State.RemoveProject(projectId);
362245
363- Logger . Debug ( "Project '{0}' was removed." , e . Item . Name ) ;
364- Tuple < IConnectionPoint , int > componentsTuple ;
365- if ( _componentsEventsConnectionPoints . TryGetValue ( projectId , out componentsTuple ) )
366- {
367- componentsTuple . Item1 . Unadvise ( componentsTuple . Item2 ) ;
368- _componentsEventsConnectionPoints . Remove ( projectId ) ;
369- }
370-
371- Tuple < IConnectionPoint , int > referencesTuple ;
372- if ( _referencesEventsConnectionPoints . TryGetValue ( projectId , out referencesTuple ) )
373- {
374- referencesTuple . Item1 . Unadvise ( referencesTuple . Item2 ) ;
375- _referencesEventsConnectionPoints . Remove ( projectId ) ;
376- }
377-
378246 _parser.State.AddProject(e.Item.Collection.Parent);
379247 }
380248 else
@@ -431,18 +299,6 @@ async void sink_ComponentAdded(object sender, DispatcherEventArgs<VBComponent> e
431299 _parser.State.OnParseRequested(sender, e.Item);
432300 }
433301
434- async void sink_ComponentActivated ( object sender , DispatcherEventArgs < VBComponent > e )
435- {
436- if ( ! _handleSinkEvents || ! _vbe . IsInDesignMode ( ) ) { return ; }
437-
438- if ( ! _parser . State . AllDeclarations . Any ( ) )
439- {
440- return ;
441- }
442-
443- // do something?
444- }
445-
446302 async void sink_ProjectRenamed(object sender, DispatcherRenamedEventArgs<VBProject> e)
447303 {
448304 if (!_handleSinkEvents || !_vbe.IsInDesignMode()) { return; }
@@ -461,19 +317,7 @@ async void sink_ProjectRenamed(object sender, DispatcherRenamedEventArgs<VBProje
461317
462318 _parser.State.OnParseRequested(sender);
463319 }
464-
465- async void sink_ProjectActivated ( object sender , DispatcherEventArgs < VBProject > e )
466- {
467- if ( ! _handleSinkEvents || ! _vbe . IsInDesignMode ( ) ) { return ; }
468-
469- if ( ! _parser . State . AllDeclarations . Any ( ) )
470- {
471- return ;
472- }
473-
474- // todo: keep Code Explorer in sync with Project Explorer
475- }
476- #endregion
320+ #endregion*/
477321
478322 private void _stateBar_Refresh ( object sender , EventArgs e )
479323 {
@@ -509,28 +353,13 @@ private void LoadConfig()
509353 }
510354
511355 private bool _disposed ;
512-
513356 public void Dispose ( )
514357 {
515358 if ( _disposed )
516359 {
517360 return ;
518361 }
519362
520- if ( _sourceControlPanelVM != null )
521- {
522- _sourceControlPanelVM . OpenRepoStarted -= DisableSinkEventHandlers ;
523- _sourceControlPanelVM . OpenRepoCompleted -= EnableSinkEventHandlersAndUpdateCache ;
524- }
525-
526- if ( _branchesVM != null )
527- {
528- _branchesVM . LoadingComponentsStarted -= DisableSinkEventHandlers ;
529- _branchesVM . LoadingComponentsCompleted -= EnableSinkEventHandlersAndUpdateCache ;
530- }
531-
532- _handleSinkEvents = false ;
533-
534363 if ( _parser != null && _parser . State != null )
535364 {
536365 _parser . State . StateChanged -= Parser_StateChanged ;
@@ -564,41 +393,12 @@ public void Dispose()
564393 _stateBar = null ;
565394 }
566395
567- if ( _sink != null )
568- {
569- _sink . ProjectAdded -= sink_ProjectAdded ;
570- _sink . ProjectRemoved -= sink_ProjectRemoved ;
571- _sink . ProjectActivated -= sink_ProjectActivated ;
572- _sink . ProjectRenamed -= sink_ProjectRenamed ;
573- _sink = null ;
574- }
575-
576- foreach ( var item in _componentsEventsSinks )
577- {
578- item . Value . ComponentActivated -= sink_ComponentActivated ;
579- item . Value . ComponentAdded -= sink_ComponentAdded ;
580- item . Value . ComponentReloaded -= sink_ComponentReloaded ;
581- item . Value . ComponentRemoved -= sink_ComponentRemoved ;
582- item . Value . ComponentRenamed -= sink_ComponentRenamed ;
583- item . Value . ComponentSelected -= sink_ComponentSelected ;
584- }
585-
586396 if ( _autoSave != null )
587397 {
588398 _autoSave . Dispose ( ) ;
589399 _autoSave = null ;
590400 }
591401
592- _projectsEventsConnectionPoint . Unadvise ( _projectsEventsCookie ) ;
593- foreach ( var item in _componentsEventsConnectionPoints )
594- {
595- item . Value . Item1 . Unadvise ( item . Value . Item2 ) ;
596- }
597- foreach ( var item in _referencesEventsConnectionPoints )
598- {
599- item . Value . Item1 . Unadvise ( item . Value . Item2 ) ;
600- }
601-
602402 UiDispatcher . Shutdown ( ) ;
603403
604404 _disposed = true ;
0 commit comments