xref: /aoo41x/main/sc/source/ui/vba/vbaeventshelper.cxx (revision cdf0e10c)
1 /*************************************************************************
2  *
3  * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
4  *
5  * Copyright 2000, 2010 Oracle and/or its affiliates.
6  *
7  * OpenOffice.org - a multi-platform office productivity suite
8  *
9  * This file is part of OpenOffice.org.
10  *
11  * OpenOffice.org is free software: you can redistribute it and/or modify
12  * it under the terms of the GNU Lesser General Public License version 3
13  * only, as published by the Free Software Foundation.
14  *
15  * OpenOffice.org is distributed in the hope that it will be useful,
16  * but WITHOUT ANY WARRANTY; without even the implied warranty of
17  * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
18  * GNU Lesser General Public License version 3 for more details
19  * (a copy is included in the LICENSE file that accompanied this code).
20  *
21  * You should have received a copy of the GNU Lesser General Public License
22  * version 3 along with OpenOffice.org.  If not, see
23  * <http://www.openoffice.org/license.html>
24  * for a copy of the LGPLv3 License.
25  *
26  ************************************************************************/
27 
28 #include "vbaeventshelper.hxx"
29 
30 #include <com/sun/star/awt/XTopWindow.hpp>
31 #include <com/sun/star/awt/XTopWindowListener.hpp>
32 #include <com/sun/star/awt/XWindowListener.hpp>
33 #include <com/sun/star/frame/XBorderResizeListener.hpp>
34 #include <com/sun/star/frame/XControllerBorder.hpp>
35 #include <com/sun/star/script/ModuleType.hpp>
36 #include <com/sun/star/script/vba/VBAEventId.hpp>
37 #include <com/sun/star/sheet/XCellRangeAddressable.hpp>
38 #include <com/sun/star/sheet/XSheetCellRangeContainer.hpp>
39 #include <com/sun/star/table/XCellRange.hpp>
40 #include <com/sun/star/util/XChangesListener.hpp>
41 #include <com/sun/star/util/XChangesNotifier.hpp>
42 
43 #include <cppuhelper/implbase4.hxx>
44 #include <toolkit/unohlp.hxx>
45 #include <unotools/eventcfg.hxx>
46 #include <vbahelper/helperdecl.hxx>
47 #include <vcl/svapp.hxx>
48 #include <vcl/window.hxx>
49 
50 #include "cellsuno.hxx"
51 #include "convuno.hxx"
52 #include "vbaapplication.hxx"
53 
54 using namespace ::com::sun::star;
55 using namespace ::com::sun::star::script::vba::VBAEventId;
56 using namespace ::ooo::vba;
57 
58 using ::rtl::OUString;
59 
60 // ============================================================================
61 
62 namespace {
63 
64 /** Extracts a sheet index from the specified element of the passed sequence.
65     The element may be an integer, a Calc range or ranges object, or a VBA Range object. */
66 SCTAB lclGetTabFromArgs( const uno::Sequence< uno::Any >& rArgs, sal_Int32 nIndex ) throw (lang::IllegalArgumentException)
67 {
68     VbaEventsHelperBase::checkArgument( rArgs, nIndex );
69 
70     // first try to extract a sheet index
71     sal_Int32 nTab = -1;
72     if( rArgs[ nIndex ] >>= nTab )
73     {
74         if( (nTab < 0) || (nTab > MAXTAB) )
75             throw lang::IllegalArgumentException();
76         return static_cast< SCTAB >( nTab );
77     }
78 
79     // try VBA Range object
80     uno::Reference< excel::XRange > xVbaRange = getXSomethingFromArgs< excel::XRange >( rArgs, nIndex );
81     if( xVbaRange.is() )
82     {
83         uno::Reference< XHelperInterface > xVbaHelper( xVbaRange, uno::UNO_QUERY_THROW );
84         // TODO: in the future, the parent may be an excel::XChart (chart sheet) -> will there be a common base interface?
85         uno::Reference< excel::XWorksheet > xVbaSheet( xVbaHelper->getParent(), uno::UNO_QUERY_THROW );
86         // VBA sheet index is 1-based
87         return static_cast< SCTAB >( xVbaSheet->getIndex() - 1 );
88     }
89 
90     // try single UNO range object
91     uno::Reference< sheet::XCellRangeAddressable > xCellRangeAddressable = getXSomethingFromArgs< sheet::XCellRangeAddressable >( rArgs, nIndex );
92     if( xCellRangeAddressable.is() )
93         return xCellRangeAddressable->getRangeAddress().Sheet;
94 
95     // at last, try UNO range list
96     uno::Reference< sheet::XSheetCellRangeContainer > xRanges = getXSomethingFromArgs< sheet::XSheetCellRangeContainer >( rArgs, nIndex );
97     if( xRanges.is() )
98     {
99         uno::Sequence< table::CellRangeAddress > aRangeAddresses = xRanges->getRangeAddresses();
100         if( aRangeAddresses.getLength() > 0 )
101             return aRangeAddresses[ 0 ].Sheet;
102     }
103 
104     throw lang::IllegalArgumentException();
105 }
106 
107 /** Returns the AWT container window of the passed controller. */
108 uno::Reference< awt::XWindow > lclGetWindowForController( const uno::Reference< frame::XController >& rxController )
109 {
110     if( rxController.is() ) try
111     {
112         uno::Reference< frame::XFrame > xFrame( rxController->getFrame(), uno::UNO_SET_THROW );
113         return xFrame->getContainerWindow();
114     }
115     catch( uno::Exception& )
116     {
117     }
118     return 0;
119 }
120 
121 } // namespace
122 
123 // ============================================================================
124 
125 typedef ::cppu::WeakImplHelper4< awt::XTopWindowListener, awt::XWindowListener, frame::XBorderResizeListener, util::XChangesListener > ScVbaEventListener_BASE;
126 
127 // This class is to process Workbook window related event
128 class ScVbaEventListener : public ScVbaEventListener_BASE
129 {
130 public :
131     ScVbaEventListener( ScVbaEventsHelper& rVbaEvents, const uno::Reference< frame::XModel >& rxModel, ScDocShell* pDocShell );
132     virtual ~ScVbaEventListener();
133 
134     /** Starts listening to the passed document controller. */
135     void startControllerListening( const uno::Reference< frame::XController >& rxController );
136     /** Stops listening to the passed document controller. */
137     void stopControllerListening( const uno::Reference< frame::XController >& rxController );
138 
139     // XTopWindowListener
140     virtual void SAL_CALL windowOpened( const lang::EventObject& rEvent ) throw (uno::RuntimeException);
141     virtual void SAL_CALL windowClosing( const lang::EventObject& rEvent ) throw (uno::RuntimeException);
142     virtual void SAL_CALL windowClosed( const lang::EventObject& rEvent ) throw (uno::RuntimeException);
143     virtual void SAL_CALL windowMinimized( const lang::EventObject& rEvent ) throw (uno::RuntimeException);
144     virtual void SAL_CALL windowNormalized( const lang::EventObject& rEvent ) throw (uno::RuntimeException);
145     virtual void SAL_CALL windowActivated( const lang::EventObject& rEvent ) throw (uno::RuntimeException);
146     virtual void SAL_CALL windowDeactivated( const lang::EventObject& rEvent ) throw (uno::RuntimeException);
147 
148     // XWindowListener
149     virtual void SAL_CALL windowResized( const awt::WindowEvent& rEvent ) throw (uno::RuntimeException);
150     virtual void SAL_CALL windowMoved( const awt::WindowEvent& rEvent ) throw (uno::RuntimeException);
151     virtual void SAL_CALL windowShown( const lang::EventObject& rEvent ) throw (uno::RuntimeException);
152     virtual void SAL_CALL windowHidden( const lang::EventObject& rEvent ) throw (uno::RuntimeException);
153 
154     // XBorderResizeListener
155     virtual void SAL_CALL borderWidthsChanged( const uno::Reference< uno::XInterface >& rSource, const frame::BorderWidths& aNewSize ) throw (uno::RuntimeException);
156 
157     // XChangesListener
158     virtual void SAL_CALL changesOccurred( const util::ChangesEvent& rEvent ) throw (uno::RuntimeException);
159 
160     // XEventListener
161     virtual void SAL_CALL disposing( const lang::EventObject& rEvent ) throw (uno::RuntimeException);
162 
163 private:
164     /** Starts listening to the document model. */
165     void startModelListening();
166     /** Stops listening to the document model. */
167     void stopModelListening();
168 
169     /** Returns the controller for the passed VCL window. */
170     uno::Reference< frame::XController > getControllerForWindow( Window* pWindow ) const;
171 
172     /** Calls the Workbook_Window[Activate|Deactivate] event handler. */
173     void processWindowActivateEvent( Window* pWindow, bool bActivate );
174     /** Posts a Workbook_WindowResize user event. */
175     void postWindowResizeEvent( Window* pWindow );
176     /** Callback link for Application::PostUserEvent(). */
177     DECL_LINK( processWindowResizeEvent, Window* );
178 
179 private:
180     typedef ::std::map< Window*, uno::Reference< frame::XController > > WindowControllerMap;
181 
182     ::osl::Mutex        maMutex;
183     ScVbaEventsHelper&  mrVbaEvents;
184     uno::Reference< frame::XModel > mxModel;
185     ScDocShell*         mpDocShell;
186     WindowControllerMap maControllers;          /// Maps VCL top windows to their controllers.
187     Window*             mpActiveWindow;         /// Currently activated window, to prevent multiple (de)activation.
188     bool                mbWindowResized;        /// True = window resize system event processed.
189     bool                mbBorderChanged;        /// True = borders changed system event processed.
190     bool                mbDisposed;
191 };
192 
193 // ----------------------------------------------------------------------------
194 
195 ScVbaEventListener::ScVbaEventListener( ScVbaEventsHelper& rVbaEvents, const uno::Reference< frame::XModel >& rxModel, ScDocShell* pDocShell ) :
196     mrVbaEvents( rVbaEvents ),
197     mxModel( rxModel ),
198     mpDocShell( pDocShell ),
199     mpActiveWindow( 0 ),
200     mbWindowResized( false ),
201     mbBorderChanged( false ),
202     mbDisposed( !rxModel.is() )
203 {
204     if( !mxModel.is() )
205         return;
206 
207     startModelListening();
208     try
209     {
210         uno::Reference< frame::XController > xController( mxModel->getCurrentController(), uno::UNO_QUERY_THROW );
211         startControllerListening( xController );
212     }
213     catch( uno::Exception& )
214     {
215     }
216 }
217 
218 ScVbaEventListener::~ScVbaEventListener()
219 {
220 }
221 
222 void ScVbaEventListener::startControllerListening( const uno::Reference< frame::XController >& rxController )
223 {
224     ::osl::MutexGuard aGuard( maMutex );
225 
226     uno::Reference< awt::XWindow > xWindow = lclGetWindowForController( rxController );
227     if( xWindow.is() )
228         try { xWindow->addWindowListener( this ); } catch( uno::Exception& ) {}
229 
230     uno::Reference< awt::XTopWindow > xTopWindow( xWindow, uno::UNO_QUERY );
231     if( xTopWindow.is() )
232         try { xTopWindow->addTopWindowListener( this ); } catch( uno::Exception& ) {}
233 
234     uno::Reference< frame::XControllerBorder > xControllerBorder( rxController, uno::UNO_QUERY );
235     if( xControllerBorder.is() )
236         try { xControllerBorder->addBorderResizeListener( this ); } catch( uno::Exception& ) {}
237 
238     if( Window* pWindow = VCLUnoHelper::GetWindow( xWindow ) )
239         maControllers[ pWindow ] = rxController;
240 }
241 
242 void ScVbaEventListener::stopControllerListening( const uno::Reference< frame::XController >& rxController )
243 {
244     ::osl::MutexGuard aGuard( maMutex );
245 
246     uno::Reference< awt::XWindow > xWindow = lclGetWindowForController( rxController );
247     if( xWindow.is() )
248         try { xWindow->removeWindowListener( this ); } catch( uno::Exception& ) {}
249 
250     uno::Reference< awt::XTopWindow > xTopWindow( xWindow, uno::UNO_QUERY );
251     if( xTopWindow.is() )
252         try { xTopWindow->removeTopWindowListener( this ); } catch( uno::Exception& ) {}
253 
254     uno::Reference< frame::XControllerBorder > xControllerBorder( rxController, uno::UNO_QUERY );
255     if( xControllerBorder.is() )
256         try { xControllerBorder->removeBorderResizeListener( this ); } catch( uno::Exception& ) {}
257 
258     if( Window* pWindow = VCLUnoHelper::GetWindow( xWindow ) )
259     {
260         maControllers.erase( pWindow );
261         if( pWindow == mpActiveWindow )
262             mpActiveWindow = 0;
263     }
264 }
265 
266 void SAL_CALL ScVbaEventListener::windowOpened( const lang::EventObject& /*rEvent*/ ) throw (uno::RuntimeException)
267 {
268 }
269 
270 void SAL_CALL ScVbaEventListener::windowClosing( const lang::EventObject& /*rEvent*/ ) throw (uno::RuntimeException)
271 {
272 }
273 
274 void SAL_CALL ScVbaEventListener::windowClosed( const lang::EventObject& /*rEvent*/ ) throw (uno::RuntimeException)
275 {
276 }
277 
278 void SAL_CALL ScVbaEventListener::windowMinimized( const lang::EventObject& /*rEvent*/ ) throw (uno::RuntimeException)
279 {
280 }
281 
282 void SAL_CALL ScVbaEventListener::windowNormalized( const lang::EventObject& /*rEvent*/ ) throw (uno::RuntimeException)
283 {
284 }
285 
286 void SAL_CALL ScVbaEventListener::windowActivated( const lang::EventObject& rEvent ) throw (uno::RuntimeException)
287 {
288     ::osl::MutexGuard aGuard( maMutex );
289 
290     if( !mbDisposed )
291     {
292         uno::Reference< awt::XWindow > xWindow( rEvent.Source, uno::UNO_QUERY );
293         Window* pWindow = VCLUnoHelper::GetWindow( xWindow );
294         OSL_TRACE( "ScVbaEventListener::windowActivated - pWindow = 0x%x, mpActiveWindow = 0x%x", pWindow, mpActiveWindow );
295         // do not fire activation event multiple time for the same window
296         if( pWindow && (pWindow != mpActiveWindow) )
297         {
298             // if another window is active, fire deactivation event first
299             if( mpActiveWindow )
300                 processWindowActivateEvent( mpActiveWindow, false );
301             // fire activation event for the new window
302             processWindowActivateEvent( pWindow, true );
303             mpActiveWindow = pWindow;
304         }
305     }
306 }
307 
308 void SAL_CALL ScVbaEventListener::windowDeactivated( const lang::EventObject& rEvent ) throw (uno::RuntimeException)
309 {
310     ::osl::MutexGuard aGuard( maMutex );
311 
312     if( !mbDisposed )
313     {
314         uno::Reference< awt::XWindow > xWindow( rEvent.Source, uno::UNO_QUERY );
315         Window* pWindow = VCLUnoHelper::GetWindow( xWindow );
316         OSL_TRACE( "ScVbaEventListener::windowDeactivated - pWindow = 0x%x, mpActiveWindow = 0x%x", pWindow, mpActiveWindow );
317         // do not fire the deactivation event, if the window is not active (prevent multiple deactivation)
318         if( pWindow && (pWindow == mpActiveWindow) )
319             processWindowActivateEvent( pWindow, false );
320         // forget pointer to the active window
321         mpActiveWindow = 0;
322     }
323 }
324 
325 void SAL_CALL ScVbaEventListener::windowResized( const awt::WindowEvent& rEvent ) throw (uno::RuntimeException)
326 {
327     ::osl::MutexGuard aGuard( maMutex );
328 
329     mbWindowResized = true;
330     if( !mbDisposed && mbBorderChanged )
331     {
332         uno::Reference< awt::XWindow > xWindow( rEvent.Source, uno::UNO_QUERY );
333         postWindowResizeEvent( VCLUnoHelper::GetWindow( xWindow ) );
334     }
335 }
336 
337 void SAL_CALL ScVbaEventListener::windowMoved( const awt::WindowEvent& /*rEvent*/ ) throw (uno::RuntimeException)
338 {
339 }
340 
341 void SAL_CALL ScVbaEventListener::windowShown( const lang::EventObject& /*rEvent*/ ) throw (uno::RuntimeException)
342 {
343 }
344 
345 void SAL_CALL ScVbaEventListener::windowHidden( const lang::EventObject& /*rEvent*/ ) throw (uno::RuntimeException)
346 {
347 }
348 
349 void SAL_CALL ScVbaEventListener::borderWidthsChanged( const uno::Reference< uno::XInterface >& rSource, const frame::BorderWidths& /*aNewSize*/ ) throw (uno::RuntimeException)
350 {
351     ::osl::MutexGuard aGuard( maMutex );
352 
353     mbBorderChanged = true;
354     if( !mbDisposed && mbWindowResized )
355     {
356         uno::Reference< frame::XController > xController( rSource, uno::UNO_QUERY );
357         uno::Reference< awt::XWindow > xWindow = lclGetWindowForController( xController );
358         postWindowResizeEvent( VCLUnoHelper::GetWindow( xWindow ) );
359     }
360 }
361 
362 void SAL_CALL ScVbaEventListener::changesOccurred( const util::ChangesEvent& rEvent ) throw (uno::RuntimeException)
363 {
364     ::osl::MutexGuard aGuard( maMutex );
365 
366     sal_Int32 nCount = rEvent.Changes.getLength();
367     if( mbDisposed || !mpDocShell || (nCount == 0) )
368         return;
369 
370     util::ElementChange aChange = rEvent.Changes[ 0 ];
371     OUString sOperation;
372     aChange.Accessor >>= sOperation;
373     if( !sOperation.equalsIgnoreAsciiCaseAscii("cell-change") )
374         return;
375 
376     if( nCount == 1 )
377     {
378         uno::Reference< table::XCellRange > xRangeObj;
379         aChange.ReplacedElement >>= xRangeObj;
380         if( xRangeObj.is() )
381         {
382             uno::Sequence< uno::Any > aArgs( 1 );
383             aArgs[0] <<= xRangeObj;
384             mrVbaEvents.processVbaEventNoThrow( WORKSHEET_CHANGE, aArgs );
385         }
386         return;
387     }
388 
389     ScRangeList aRangeList;
390     for( sal_Int32 nIndex = 0; nIndex < nCount; ++nIndex )
391     {
392         aChange = rEvent.Changes[ nIndex ];
393         aChange.Accessor >>= sOperation;
394         uno::Reference< table::XCellRange > xRangeObj;
395         aChange.ReplacedElement >>= xRangeObj;
396         if( xRangeObj.is() && sOperation.equalsIgnoreAsciiCaseAscii("cell-change") )
397         {
398             uno::Reference< sheet::XCellRangeAddressable > xCellRangeAddressable( xRangeObj, uno::UNO_QUERY );
399             if( xCellRangeAddressable.is() )
400             {
401                 ScRange aRange;
402                 ScUnoConversion::FillScRange( aRange, xCellRangeAddressable->getRangeAddress() );
403                 aRangeList.Append( aRange );
404             }
405         }
406     }
407 
408     if( aRangeList.Count() > 0 )
409     {
410         uno::Reference< sheet::XSheetCellRangeContainer > xRanges( new ScCellRangesObj( mpDocShell, aRangeList ) );
411         uno::Sequence< uno::Any > aArgs(1);
412         aArgs[0] <<= xRanges;
413         mrVbaEvents.processVbaEventNoThrow( WORKSHEET_CHANGE, aArgs );
414     }
415 }
416 
417 void SAL_CALL ScVbaEventListener::disposing( const lang::EventObject& rEvent ) throw (uno::RuntimeException)
418 {
419     ::osl::MutexGuard aGuard( maMutex );
420 
421     uno::Reference< frame::XModel > xModel( rEvent.Source, uno::UNO_QUERY );
422     if( xModel.is() )
423     {
424         OSL_ENSURE( xModel.get() == mxModel.get(), "ScVbaEventListener::disposing - disposing from unknown model" );
425         stopModelListening();
426         mbDisposed = true;
427         return;
428     }
429 
430     uno::Reference< frame::XController > xController( rEvent.Source, uno::UNO_QUERY );
431     if( xController.is() )
432     {
433         stopControllerListening( xController );
434         return;
435     }
436 }
437 
438 // private --------------------------------------------------------------------
439 
440 void ScVbaEventListener::startModelListening()
441 {
442     try
443     {
444         uno::Reference< util::XChangesNotifier > xChangesNotifier( mxModel, uno::UNO_QUERY_THROW );
445         xChangesNotifier->addChangesListener( this );
446     }
447     catch( uno::Exception& )
448     {
449     }
450 }
451 
452 void ScVbaEventListener::stopModelListening()
453 {
454     try
455     {
456         uno::Reference< util::XChangesNotifier > xChangesNotifier( mxModel, uno::UNO_QUERY_THROW );
457         xChangesNotifier->removeChangesListener( this );
458     }
459     catch( uno::Exception& )
460     {
461     }
462 }
463 
464 uno::Reference< frame::XController > ScVbaEventListener::getControllerForWindow( Window* pWindow ) const
465 {
466     WindowControllerMap::const_iterator aIt = maControllers.find( pWindow );
467     return (aIt == maControllers.end()) ? uno::Reference< frame::XController >() : aIt->second;
468 }
469 
470 void ScVbaEventListener::processWindowActivateEvent( Window* pWindow, bool bActivate )
471 {
472     uno::Reference< frame::XController > xController = getControllerForWindow( pWindow );
473     if( xController.is() )
474     {
475         uno::Sequence< uno::Any > aArgs( 1 );
476         aArgs[ 0 ] <<= xController;
477         mrVbaEvents.processVbaEventNoThrow( bActivate ? WORKBOOK_WINDOWACTIVATE : WORKBOOK_WINDOWDEACTIVATE, aArgs );
478     }
479 }
480 
481 void ScVbaEventListener::postWindowResizeEvent( Window* pWindow )
482 {
483     // check that the passed window is still alive (it must be registered in maControllers)
484     if( pWindow && (maControllers.count( pWindow ) > 0) )
485     {
486         mbWindowResized = mbBorderChanged = false;
487         acquire();  // ensure we don't get deleted before the timer fires
488         Application::PostUserEvent( LINK( this, ScVbaEventListener, processWindowResizeEvent ), pWindow );
489     }
490 }
491 
492 IMPL_LINK( ScVbaEventListener, processWindowResizeEvent, Window*, EMPTYARG pWindow )
493 {
494     ::osl::MutexGuard aGuard( maMutex );
495 
496     /*  Check that the passed window is still alive (it must be registered in
497         maControllers). While closing a document, postWindowResizeEvent() may
498         be called on the last window which posts a user event via
499         Application::PostUserEvent to call this event handler. VCL will trigger
500         the handler some time later. Sometimes, the window gets deleted before.
501         This is handled via the disposing() function which removes the window
502         pointer from the member maControllers. Thus, checking whether
503         maControllers contains pWindow ensures that the window is still alive. */
504     if( !mbDisposed && pWindow && (maControllers.count( pWindow ) > 0) )
505     {
506         // do not fire event unless all mouse buttons have been released
507         Window::PointerState aPointerState = pWindow->GetPointerState();
508         if( (aPointerState.mnState & (MOUSE_LEFT | MOUSE_MIDDLE | MOUSE_RIGHT)) == 0 )
509         {
510             uno::Reference< frame::XController > xController = getControllerForWindow( pWindow );
511             if( xController.is() )
512             {
513                 uno::Sequence< uno::Any > aArgs( 1 );
514                 aArgs[ 0 ] <<= xController;
515                 // #163419# do not throw exceptions into application core
516                 mrVbaEvents.processVbaEventNoThrow( WORKBOOK_WINDOWRESIZE, aArgs );
517             }
518         }
519     }
520     release();
521     return 0;
522 }
523 
524 // ============================================================================
525 
526 ScVbaEventsHelper::ScVbaEventsHelper( const uno::Sequence< uno::Any >& rArgs, const uno::Reference< uno::XComponentContext >& xContext ) :
527     VbaEventsHelperBase( rArgs, xContext ),
528     mbOpened( false )
529 {
530     mpDocShell = dynamic_cast< ScDocShell* >( mpShell ); // mpShell from base class
531     mpDoc = mpDocShell ? mpDocShell->GetDocument() : 0;
532 
533     if( !mxModel.is() || !mpDocShell || !mpDoc )
534         return;
535 
536 #define REGISTER_EVENT( eventid, moduletype, classname, eventname, cancelindex, worksheet ) \
537     registerEventHandler( eventid, moduletype, classname "_" eventname, cancelindex, uno::Any( worksheet ) )
538 #define REGISTER_AUTO_EVENT( eventid, eventname ) \
539     REGISTER_EVENT( AUTO_##eventid, script::ModuleType::NORMAL, "Auto", eventname, -1, false )
540 #define REGISTER_WORKBOOK_EVENT( eventid, eventname, cancelindex ) \
541     REGISTER_EVENT( WORKBOOK_##eventid, script::ModuleType::DOCUMENT, "Workbook", eventname, cancelindex, false )
542 #define REGISTER_WORKSHEET_EVENT( eventid, eventname, cancelindex ) \
543     REGISTER_EVENT( WORKSHEET_##eventid, script::ModuleType::DOCUMENT, "Worksheet", eventname, cancelindex, true ); \
544     REGISTER_EVENT( (USERDEFINED_START + WORKSHEET_##eventid), script::ModuleType::DOCUMENT, "Workbook", "Sheet" eventname, (((cancelindex) >= 0) ? ((cancelindex) + 1) : -1), false )
545 
546     // global
547     REGISTER_AUTO_EVENT( OPEN,  "Open" );
548     REGISTER_AUTO_EVENT( CLOSE, "Close" );
549 
550     // Workbook
551     REGISTER_WORKBOOK_EVENT( ACTIVATE,            "Activate",           -1 );
552     REGISTER_WORKBOOK_EVENT( DEACTIVATE,          "Deactivate",         -1 );
553     REGISTER_WORKBOOK_EVENT( OPEN,                "Open",               -1 );
554     REGISTER_WORKBOOK_EVENT( BEFORECLOSE,         "BeforeClose",        0 );
555     REGISTER_WORKBOOK_EVENT( BEFOREPRINT,         "BeforePrint",        0 );
556     REGISTER_WORKBOOK_EVENT( BEFORESAVE,          "BeforeSave",         1 );
557     REGISTER_WORKBOOK_EVENT( AFTERSAVE,           "AfterSave",          -1 );
558     REGISTER_WORKBOOK_EVENT( NEWSHEET,            "NewSheet",           -1 );
559     REGISTER_WORKBOOK_EVENT( WINDOWACTIVATE,      "WindowActivate",     -1 );
560     REGISTER_WORKBOOK_EVENT( WINDOWDEACTIVATE,    "WindowDeactivate",   -1 );
561     REGISTER_WORKBOOK_EVENT( WINDOWRESIZE,        "WindowResize",       -1 );
562 
563     // Worksheet events. All events have a corresponding workbook event.
564     REGISTER_WORKSHEET_EVENT( ACTIVATE,           "Activate",           -1 );
565     REGISTER_WORKSHEET_EVENT( DEACTIVATE,         "Deactivate",         -1 );
566     REGISTER_WORKSHEET_EVENT( BEFOREDOUBLECLICK,  "BeforeDoubleClick",  1 );
567     REGISTER_WORKSHEET_EVENT( BEFORERIGHTCLICK,   "BeforeRightClick",   1 );
568     REGISTER_WORKSHEET_EVENT( CALCULATE,          "Calculate",          -1 );
569     REGISTER_WORKSHEET_EVENT( CHANGE,             "Change",             -1 );
570     REGISTER_WORKSHEET_EVENT( SELECTIONCHANGE,    "SelectionChange",    -1 );
571     REGISTER_WORKSHEET_EVENT( FOLLOWHYPERLINK,    "FollowHyperlink",    -1 );
572 
573 #undef REGISTER_WORKSHEET_EVENT
574 #undef REGISTER_WORKBOOK_EVENT
575 #undef REGISTER_AUTO_EVENT
576 #undef REGISTER_EVENT
577 }
578 
579 ScVbaEventsHelper::~ScVbaEventsHelper()
580 {
581 }
582 
583 void SAL_CALL ScVbaEventsHelper::notifyEvent( const css::document::EventObject& rEvent ) throw (css::uno::RuntimeException)
584 {
585     static const uno::Sequence< uno::Any > saEmptyArgs;
586     if( (rEvent.EventName == GlobalEventConfig::GetEventName( STR_EVENT_OPENDOC )) ||
587         (rEvent.EventName == GlobalEventConfig::GetEventName( STR_EVENT_CREATEDOC )) )  // CREATEDOC triggered e.g. during VBA Workbooks.Add
588     {
589         processVbaEventNoThrow( WORKBOOK_OPEN, saEmptyArgs );
590     }
591     else if( rEvent.EventName == GlobalEventConfig::GetEventName( STR_EVENT_ACTIVATEDOC ) )
592     {
593         processVbaEventNoThrow( WORKBOOK_ACTIVATE, saEmptyArgs );
594     }
595     else if( rEvent.EventName == GlobalEventConfig::GetEventName( STR_EVENT_DEACTIVATEDOC ) )
596     {
597         processVbaEventNoThrow( WORKBOOK_DEACTIVATE, saEmptyArgs );
598     }
599     else if( (rEvent.EventName == GlobalEventConfig::GetEventName( STR_EVENT_SAVEDOCDONE )) ||
600              (rEvent.EventName == GlobalEventConfig::GetEventName( STR_EVENT_SAVEASDOCDONE )) ||
601              (rEvent.EventName == GlobalEventConfig::GetEventName( STR_EVENT_SAVETODOCDONE )) )
602     {
603         uno::Sequence< uno::Any > aArgs( 1 );
604         aArgs[ 0 ] <<= true;
605         processVbaEventNoThrow( WORKBOOK_AFTERSAVE, aArgs );
606     }
607     else if( (rEvent.EventName == GlobalEventConfig::GetEventName( STR_EVENT_SAVEDOCFAILED )) ||
608              (rEvent.EventName == GlobalEventConfig::GetEventName( STR_EVENT_SAVEASDOCFAILED )) ||
609              (rEvent.EventName == GlobalEventConfig::GetEventName( STR_EVENT_SAVETODOCFAILED )) )
610     {
611         uno::Sequence< uno::Any > aArgs( 1 );
612         aArgs[ 0 ] <<= false;
613         processVbaEventNoThrow( WORKBOOK_AFTERSAVE, aArgs );
614     }
615     else if( rEvent.EventName == GlobalEventConfig::GetEventName( STR_EVENT_CLOSEDOC ) )
616     {
617         /*  Trigger the WORKBOOK_WINDOWDEACTIVATE and WORKBOOK_DEACTIVATE
618             events and stop listening to the model (done in base class). */
619         uno::Reference< frame::XController > xController( mxModel->getCurrentController() );
620         if( xController.is() )
621         {
622             uno::Sequence< uno::Any > aArgs( 1 );
623             aArgs[ 0 ] <<= xController;
624             processVbaEventNoThrow( WORKBOOK_WINDOWDEACTIVATE, aArgs );
625         }
626         processVbaEventNoThrow( WORKBOOK_DEACTIVATE, saEmptyArgs );
627     }
628     else if( rEvent.EventName == GlobalEventConfig::GetEventName( STR_EVENT_VIEWCREATED ) )
629     {
630         uno::Reference< frame::XController > xController( mxModel->getCurrentController() );
631         if( mxListener.get() && xController.is() )
632             mxListener->startControllerListening( xController );
633     }
634     VbaEventsHelperBase::notifyEvent( rEvent );
635 }
636 
637 // protected ------------------------------------------------------------------
638 
639 bool ScVbaEventsHelper::implPrepareEvent( EventQueue& rEventQueue,
640         const EventHandlerInfo& rInfo, const uno::Sequence< uno::Any >& rArgs ) throw (uno::RuntimeException)
641 {
642     // document and document shell are needed during event processing
643     if( !mpShell || !mpDoc )
644         throw uno::RuntimeException();
645 
646     /*  For document events: check if events are enabled via the
647         Application.EnableEvents symbol (this is an Excel-only attribute).
648         Check this again for every event, as the event handler may change the
649         state of the EnableEvents symbol. Global events such as AUTO_OPEN and
650         AUTO_CLOSE are always enabled. */
651     bool bExecuteEvent = (rInfo.mnModuleType != script::ModuleType::DOCUMENT) || ScVbaApplication::getDocumentEventsEnabled();
652 
653     // framework and Calc fire a few events before 'OnLoad', ignore them
654     if( bExecuteEvent )
655         bExecuteEvent = (rInfo.mnEventId == WORKBOOK_OPEN) ? !mbOpened : mbOpened;
656 
657     // special handling for some events
658     if( bExecuteEvent ) switch( rInfo.mnEventId )
659     {
660         case WORKBOOK_OPEN:
661         {
662             // execute delayed Activate event too (see above)
663             rEventQueue.push_back( WORKBOOK_ACTIVATE );
664             uno::Sequence< uno::Any > aArgs( 1 );
665             aArgs[ 0 ] <<= mxModel->getCurrentController();
666             rEventQueue.push_back( EventQueueEntry( WORKBOOK_WINDOWACTIVATE, aArgs ) );
667             rEventQueue.push_back( AUTO_OPEN );
668             // remember initial selection
669             maOldSelection <<= mxModel->getCurrentSelection();
670         }
671         break;
672         case WORKSHEET_SELECTIONCHANGE:
673             // if selection is not changed, then do not fire the event
674             bExecuteEvent = isSelectionChanged( rArgs, 0 );
675         break;
676     }
677 
678     if( bExecuteEvent )
679     {
680         // add workbook event associated to a sheet event
681         bool bSheetEvent = false;
682         if( (rInfo.maUserData >>= bSheetEvent) && bSheetEvent )
683             rEventQueue.push_back( EventQueueEntry( rInfo.mnEventId + USERDEFINED_START, rArgs ) );
684     }
685 
686     return bExecuteEvent;
687 }
688 
689 uno::Sequence< uno::Any > ScVbaEventsHelper::implBuildArgumentList( const EventHandlerInfo& rInfo,
690         const uno::Sequence< uno::Any >& rArgs ) throw (lang::IllegalArgumentException)
691 {
692     // fill arguments for workbook events associated to sheet events according to sheet events, sheet will be added below
693     bool bSheetEventAsBookEvent = rInfo.mnEventId > USERDEFINED_START;
694     sal_Int32 nEventId = bSheetEventAsBookEvent ? (rInfo.mnEventId - USERDEFINED_START) : rInfo.mnEventId;
695 
696     uno::Sequence< uno::Any > aVbaArgs;
697     switch( nEventId )
698     {
699         // *** Workbook ***
700 
701         // no arguments
702         case WORKBOOK_ACTIVATE:
703         case WORKBOOK_DEACTIVATE:
704         case WORKBOOK_OPEN:
705         break;
706         // 1 arg: cancel
707         case WORKBOOK_BEFORECLOSE:
708         case WORKBOOK_BEFOREPRINT:
709             aVbaArgs.realloc( 1 );
710             // current cancel state will be inserted by caller
711         break;
712         // 2 args: saveAs, cancel
713         case WORKBOOK_BEFORESAVE:
714             aVbaArgs.realloc( 2 );
715             checkArgumentType< bool >( rArgs, 0 );
716             aVbaArgs[ 0 ] = rArgs[ 0 ];
717             // current cancel state will be inserted by caller
718         break;
719         // 1 arg: success
720         case WORKBOOK_AFTERSAVE:
721             aVbaArgs.realloc( 1 );
722             checkArgumentType< bool >( rArgs, 0 );
723             aVbaArgs[ 0 ] = rArgs[ 0 ];
724         break;
725         // 1 arg: window
726         case WORKBOOK_WINDOWACTIVATE:
727         case WORKBOOK_WINDOWDEACTIVATE:
728         case WORKBOOK_WINDOWRESIZE:
729             aVbaArgs.realloc( 1 );
730             aVbaArgs[ 0 ] = createWindow( rArgs, 0 );
731         break;
732         // 1 arg: worksheet
733         case WORKBOOK_NEWSHEET:
734             aVbaArgs.realloc( 1 );
735             aVbaArgs[ 0 ] = createWorksheet( rArgs, 0 );
736         break;
737 
738         // *** Worksheet ***
739 
740         // no arguments
741         case WORKSHEET_ACTIVATE:
742         case WORKSHEET_CALCULATE:
743         case WORKSHEET_DEACTIVATE:
744         break;
745         // 1 arg: range
746         case WORKSHEET_CHANGE:
747         case WORKSHEET_SELECTIONCHANGE:
748             aVbaArgs.realloc( 1 );
749             aVbaArgs[ 0 ] = createRange( rArgs, 0 );
750         break;
751         // 2 args: range, cancel
752         case WORKSHEET_BEFOREDOUBLECLICK:
753         case WORKSHEET_BEFORERIGHTCLICK:
754             aVbaArgs.realloc( 2 );
755             aVbaArgs[ 0 ] = createRange( rArgs, 0 );
756             // current cancel state will be inserted by caller
757         break;
758         // 1 arg: hyperlink
759         case WORKSHEET_FOLLOWHYPERLINK:
760             aVbaArgs.realloc( 1 );
761             aVbaArgs[ 0 ] = createHyperlink( rArgs, 0 );
762         break;
763     }
764 
765     /*  For workbook events associated to sheet events, the workbook event gets
766         the same arguments but with a Worksheet object in front of them. */
767     if( bSheetEventAsBookEvent )
768     {
769         sal_Int32 nLength = aVbaArgs.getLength();
770         uno::Sequence< uno::Any > aVbaArgs2( nLength + 1 );
771         aVbaArgs2[ 0 ] = createWorksheet( rArgs, 0 );
772         for( sal_Int32 nIndex = 0; nIndex < nLength; ++nIndex )
773             aVbaArgs2[ nIndex + 1 ] = aVbaArgs[ nIndex ];
774         aVbaArgs = aVbaArgs2;
775     }
776 
777     return aVbaArgs;
778 }
779 
780 void ScVbaEventsHelper::implPostProcessEvent( EventQueue& rEventQueue,
781         const EventHandlerInfo& rInfo, bool bCancel ) throw (uno::RuntimeException)
782 {
783     switch( rInfo.mnEventId )
784     {
785         case WORKBOOK_OPEN:
786             mbOpened = true;
787             // register the listeners
788             if( !mxListener.is() )
789                 mxListener = new ScVbaEventListener( *this, mxModel, mpDocShell );
790         break;
791         case WORKBOOK_BEFORECLOSE:
792             /*  Execute Auto_Close only if not cancelled by event handler, but
793                 before UI asks user whether to cancel closing the document. */
794             if( !bCancel )
795                 rEventQueue.push_back( AUTO_CLOSE );
796         break;
797     }
798 }
799 
800 OUString ScVbaEventsHelper::implGetDocumentModuleName( const EventHandlerInfo& rInfo,
801         const uno::Sequence< uno::Any >& rArgs ) const throw (lang::IllegalArgumentException)
802 {
803     bool bSheetEvent = false;
804     rInfo.maUserData >>= bSheetEvent;
805     SCTAB nTab = bSheetEvent ? lclGetTabFromArgs( rArgs, 0 ) : -1;
806     if( bSheetEvent && (nTab < 0) )
807         throw lang::IllegalArgumentException();
808 
809     String aCodeName;
810     if( bSheetEvent )
811         mpDoc->GetCodeName( nTab, aCodeName );
812     else
813         aCodeName = mpDoc->GetCodeName();
814     return aCodeName;
815 }
816 
817 // private --------------------------------------------------------------------
818 
819 namespace {
820 
821 /** Compares the passed range lists representing sheet selections. Ignores
822     selections that refer to different sheets (returns false in this case). */
823 bool lclSelectionChanged( const ScRangeList& rLeft, const ScRangeList& rRight )
824 {
825     // one of the range lists empty? -> return false, if both lists empty
826     bool bLeftEmpty = rLeft.Count() == 0;
827     bool bRightEmpty = rRight.Count() == 0;
828     if( bLeftEmpty || bRightEmpty )
829         return !(bLeftEmpty && bRightEmpty);
830 
831     // check sheet indexes of the range lists (assuming that all ranges in a list are on the same sheet)
832     if( rLeft.GetObject( 0 )->aStart.Tab() != rRight.GetObject( 0 )->aStart.Tab() )
833         return false;
834 
835     // compare all ranges
836     return rLeft != rRight;
837 }
838 
839 } // namespace
840 
841 bool ScVbaEventsHelper::isSelectionChanged( const uno::Sequence< uno::Any >& rArgs, sal_Int32 nIndex ) throw (lang::IllegalArgumentException, uno::RuntimeException)
842 {
843     uno::Reference< uno::XInterface > xOldSelection( maOldSelection, uno::UNO_QUERY );
844     uno::Reference< uno::XInterface > xNewSelection = getXSomethingFromArgs< uno::XInterface >( rArgs, nIndex, false );
845     ScCellRangesBase* pOldCellRanges = ScCellRangesBase::getImplementation( xOldSelection );
846     ScCellRangesBase* pNewCellRanges = ScCellRangesBase::getImplementation( xNewSelection );
847     bool bChanged = !pOldCellRanges || !pNewCellRanges || lclSelectionChanged( pOldCellRanges->GetRangeList(), pNewCellRanges->GetRangeList() );
848     maOldSelection <<= xNewSelection;
849     return bChanged;
850 }
851 
852 uno::Any ScVbaEventsHelper::createWorksheet( const uno::Sequence< uno::Any >& rArgs, sal_Int32 nIndex ) const
853         throw (lang::IllegalArgumentException, uno::RuntimeException)
854 {
855     // extract sheet index, will throw, if parameter is invalid
856     SCTAB nTab = lclGetTabFromArgs( rArgs, nIndex );
857     return uno::Any( excel::getUnoSheetModuleObj( mxModel, nTab ) );
858 }
859 
860 uno::Any ScVbaEventsHelper::createRange( const uno::Sequence< uno::Any >& rArgs, sal_Int32 nIndex ) const
861         throw (lang::IllegalArgumentException, uno::RuntimeException)
862 {
863     // it is possible to pass an existing VBA Range object
864     uno::Reference< excel::XRange > xVbaRange = getXSomethingFromArgs< excel::XRange >( rArgs, nIndex );
865     if( !xVbaRange.is() )
866     {
867         uno::Reference< sheet::XSheetCellRangeContainer > xRanges = getXSomethingFromArgs< sheet::XSheetCellRangeContainer >( rArgs, nIndex );
868         uno::Reference< table::XCellRange > xRange = getXSomethingFromArgs< table::XCellRange >( rArgs, nIndex );
869         if ( !xRanges.is() && !xRange.is() )
870             throw lang::IllegalArgumentException();
871 
872         uno::Sequence< uno::Any > aArgs( 2 );
873         if ( xRanges.is() )
874         {
875             aArgs[ 0 ] <<= excel::getUnoSheetModuleObj( xRanges );
876             aArgs[ 1 ] <<= xRanges;
877         }
878         else
879         {
880             aArgs[ 0 ] <<= excel::getUnoSheetModuleObj( xRange );
881             aArgs[ 1 ] <<= xRange;
882         }
883         xVbaRange.set( createVBAUnoAPIServiceWithArgs( mpShell, "ooo.vba.excel.Range", aArgs ), uno::UNO_QUERY_THROW );
884     }
885     return uno::Any( xVbaRange );
886 }
887 
888 uno::Any ScVbaEventsHelper::createHyperlink( const uno::Sequence< uno::Any >& rArgs, sal_Int32 nIndex ) const
889         throw (lang::IllegalArgumentException, uno::RuntimeException)
890 {
891     uno::Reference< table::XCell > xCell = getXSomethingFromArgs< table::XCell >( rArgs, nIndex, false );
892     uno::Sequence< uno::Any > aArgs( 2 );
893     aArgs[ 0 ] <<= excel::getUnoSheetModuleObj( xCell );
894     aArgs[ 1 ] <<= xCell;
895     uno::Reference< uno::XInterface > xHyperlink( createVBAUnoAPIServiceWithArgs( mpShell, "ooo.vba.excel.Hyperlink", aArgs ), uno::UNO_SET_THROW );
896     return uno::Any( xHyperlink );
897 }
898 
899 uno::Any ScVbaEventsHelper::createWindow( const uno::Sequence< uno::Any >& rArgs, sal_Int32 nIndex ) const
900         throw (lang::IllegalArgumentException, uno::RuntimeException)
901 {
902     uno::Sequence< uno::Any > aArgs( 3 );
903     aArgs[ 0 ] <<= getVBADocument( mxModel );
904     aArgs[ 1 ] <<= mxModel;
905     aArgs[ 2 ] <<= getXSomethingFromArgs< frame::XController >( rArgs, nIndex, false );
906     uno::Reference< uno::XInterface > xWindow( createVBAUnoAPIServiceWithArgs( mpShell, "ooo.vba.excel.Window", aArgs ), uno::UNO_SET_THROW );
907     return uno::Any( xWindow );
908 }
909 
910 // ============================================================================
911 
912 namespace vbaeventshelper
913 {
914 namespace sdecl = comphelper::service_decl;
915 sdecl::class_<ScVbaEventsHelper, sdecl::with_args<true> > serviceImpl;
916 extern sdecl::ServiceDecl const serviceDecl(
917     serviceImpl,
918     "ScVbaEventsHelper",
919     "com.sun.star.script.vba.VBASpreadsheetEventProcessor" );
920 }
921 
922 // ============================================================================
923