2010-07-06 19:34:53 +02:00
|
|
|
/*************************************************************************
|
|
|
|
*
|
|
|
|
* DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
|
|
|
|
*
|
|
|
|
* Copyright 2000, 2010 Oracle and/or its affiliates.
|
|
|
|
*
|
|
|
|
* OpenOffice.org - a multi-platform office productivity suite
|
|
|
|
*
|
|
|
|
* This file is part of OpenOffice.org.
|
|
|
|
*
|
|
|
|
* OpenOffice.org is free software: you can redistribute it and/or modify
|
|
|
|
* it under the terms of the GNU Lesser General Public License version 3
|
|
|
|
* only, as published by the Free Software Foundation.
|
|
|
|
*
|
|
|
|
* OpenOffice.org is distributed in the hope that it will be useful,
|
|
|
|
* but WITHOUT ANY WARRANTY; without even the implied warranty of
|
|
|
|
* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
|
|
|
|
* GNU Lesser General Public License version 3 for more details
|
|
|
|
* (a copy is included in the LICENSE file that accompanied this code).
|
|
|
|
*
|
|
|
|
* You should have received a copy of the GNU Lesser General Public License
|
|
|
|
* version 3 along with OpenOffice.org. If not, see
|
|
|
|
* <http://www.openoffice.org/license.html>
|
|
|
|
* for a copy of the LGPLv3 License.
|
|
|
|
*
|
|
|
|
************************************************************************/
|
|
|
|
|
|
|
|
#include "vbaeventshelper.hxx"
|
|
|
|
|
|
|
|
#include <com/sun/star/awt/XWindowListener.hpp>
|
|
|
|
#include <com/sun/star/frame/XBorderResizeListener.hpp>
|
|
|
|
#include <com/sun/star/frame/XControllerBorder.hpp>
|
2010-07-12 11:17:00 +02:00
|
|
|
#include <com/sun/star/script/vba/VBAEventId.hpp>
|
2010-07-06 19:34:53 +02:00
|
|
|
#include <com/sun/star/sheet/XCellRangeAddressable.hpp>
|
|
|
|
#include <com/sun/star/sheet/XSheetCellRangeContainer.hpp>
|
|
|
|
#include <com/sun/star/table/XCellRange.hpp>
|
|
|
|
#include <com/sun/star/util/XChangesListener.hpp>
|
|
|
|
#include <com/sun/star/util/XChangesNotifier.hpp>
|
|
|
|
#include <com/sun/star/util/XCloseListener.hpp>
|
|
|
|
|
|
|
|
#include <ooo/vba/excel/XApplication.hpp>
|
|
|
|
|
|
|
|
#include <cppuhelper/implbase1.hxx>
|
|
|
|
#include <cppuhelper/implbase3.hxx>
|
|
|
|
#include <toolkit/unohlp.hxx>
|
|
|
|
#include <vbahelper/helperdecl.hxx>
|
|
|
|
#include <vcl/svapp.hxx>
|
|
|
|
#include <vcl/window.hxx>
|
|
|
|
|
|
|
|
#include "cellsuno.hxx"
|
|
|
|
#include "convuno.hxx"
|
|
|
|
|
|
|
|
using namespace ::com::sun::star;
|
2010-07-12 11:17:00 +02:00
|
|
|
using namespace ::com::sun::star::script::vba::VBAEventId;
|
2010-07-06 19:34:53 +02:00
|
|
|
using namespace ::ooo::vba;
|
|
|
|
|
|
|
|
// ============================================================================
|
|
|
|
|
|
|
|
typedef ::cppu::WeakImplHelper1< util::XChangesListener > ScVbaChangesListener_BASE;
|
|
|
|
|
|
|
|
class ScVbaChangesListener : public ScVbaChangesListener_BASE
|
|
|
|
{
|
|
|
|
public:
|
|
|
|
ScVbaChangesListener( ScVbaEventsHelper* pHelper, ScDocShell* pDocShell );
|
|
|
|
|
|
|
|
virtual void SAL_CALL changesOccurred( const util::ChangesEvent& aEvent ) throw (uno::RuntimeException);
|
|
|
|
virtual void SAL_CALL disposing( const lang::EventObject& aSource ) throw (uno::RuntimeException);
|
|
|
|
|
|
|
|
private:
|
|
|
|
ScVbaEventsHelper* mpVbaEvents;
|
|
|
|
ScDocShell* mpDocShell;
|
|
|
|
};
|
|
|
|
|
|
|
|
// ----------------------------------------------------------------------------
|
|
|
|
|
|
|
|
ScVbaChangesListener::ScVbaChangesListener( ScVbaEventsHelper* pHelper, ScDocShell* pDocShell ) :
|
|
|
|
mpVbaEvents( pHelper ),
|
|
|
|
mpDocShell( pDocShell )
|
|
|
|
{
|
|
|
|
}
|
|
|
|
|
|
|
|
void SAL_CALL ScVbaChangesListener::changesOccurred( const util::ChangesEvent& aEvent ) throw (uno::RuntimeException)
|
|
|
|
{
|
|
|
|
sal_Int32 nCount = aEvent.Changes.getLength();
|
|
|
|
if( nCount == 0 )
|
|
|
|
return;
|
|
|
|
|
|
|
|
util::ElementChange aChange = aEvent.Changes[ 0 ];
|
|
|
|
rtl::OUString sOperation;
|
|
|
|
aChange.Accessor >>= sOperation;
|
|
|
|
if( !sOperation.equalsIgnoreAsciiCaseAscii("cell-change") )
|
|
|
|
return;
|
|
|
|
|
|
|
|
if( nCount == 1 )
|
|
|
|
{
|
|
|
|
uno::Reference< table::XCellRange > xRangeObj;
|
|
|
|
aChange.ReplacedElement >>= xRangeObj;
|
|
|
|
if( xRangeObj.is() )
|
|
|
|
{
|
|
|
|
uno::Sequence< uno::Any > aArgs(1);
|
|
|
|
aArgs[0] <<= xRangeObj;
|
|
|
|
mpVbaEvents->processVbaEvent( WORKSHEET_CHANGE, aArgs );
|
|
|
|
}
|
|
|
|
return;
|
|
|
|
}
|
|
|
|
|
|
|
|
ScRangeList aRangeList;
|
|
|
|
for( sal_Int32 nIndex = 0; nIndex < nCount; ++nIndex )
|
|
|
|
{
|
|
|
|
aChange = aEvent.Changes[ nIndex ];
|
|
|
|
aChange.Accessor >>= sOperation;
|
|
|
|
uno::Reference< table::XCellRange > xRangeObj;
|
|
|
|
aChange.ReplacedElement >>= xRangeObj;
|
|
|
|
if( xRangeObj.is() && sOperation.equalsIgnoreAsciiCaseAscii("cell-change") )
|
|
|
|
{
|
|
|
|
uno::Reference< sheet::XCellRangeAddressable > xCellRangeAddressable( xRangeObj, uno::UNO_QUERY );
|
|
|
|
if( xCellRangeAddressable.is() )
|
|
|
|
{
|
|
|
|
ScRange aRange;
|
|
|
|
ScUnoConversion::FillScRange( aRange, xCellRangeAddressable->getRangeAddress() );
|
|
|
|
aRangeList.Append( aRange );
|
|
|
|
}
|
|
|
|
}
|
|
|
|
}
|
|
|
|
|
|
|
|
if( (aRangeList.Count() > 0) && mpDocShell )
|
|
|
|
{
|
|
|
|
uno::Reference< sheet::XSheetCellRangeContainer > xRanges( new ScCellRangesObj( mpDocShell, aRangeList ) );
|
|
|
|
uno::Sequence< uno::Any > aArgs(1);
|
|
|
|
aArgs[0] <<= xRanges;
|
|
|
|
mpVbaEvents->processVbaEvent( WORKSHEET_CHANGE, aArgs );
|
|
|
|
}
|
|
|
|
}
|
|
|
|
|
|
|
|
void SAL_CALL ScVbaChangesListener::disposing( const lang::EventObject& /*aSource*/ ) throw(uno::RuntimeException)
|
|
|
|
{
|
|
|
|
}
|
|
|
|
|
|
|
|
// ============================================================================
|
|
|
|
|
|
|
|
typedef ::cppu::WeakImplHelper3<
|
|
|
|
awt::XWindowListener, util::XCloseListener, frame::XBorderResizeListener > ScVbaWindowListener_BASE;
|
|
|
|
|
|
|
|
// This class is to process Workbook window related event
|
|
|
|
class ScVbaWindowListener : public ScVbaWindowListener_BASE
|
|
|
|
{
|
|
|
|
public :
|
|
|
|
ScVbaWindowListener( ScVbaEventsHelper* pHelper, const uno::Reference< frame::XModel >& rxModel );
|
|
|
|
virtual ~ScVbaWindowListener();
|
|
|
|
|
|
|
|
void startListening();
|
|
|
|
void stopListening();
|
|
|
|
|
|
|
|
// XWindowListener
|
|
|
|
virtual void SAL_CALL windowResized( const awt::WindowEvent& aEvent ) throw (uno::RuntimeException);
|
|
|
|
virtual void SAL_CALL windowMoved( const awt::WindowEvent& aEvent ) throw (uno::RuntimeException);
|
|
|
|
virtual void SAL_CALL windowShown( const lang::EventObject& aEvent ) throw (uno::RuntimeException);
|
|
|
|
virtual void SAL_CALL windowHidden( const lang::EventObject& aEvent ) throw (uno::RuntimeException);
|
|
|
|
virtual void SAL_CALL disposing( const lang::EventObject& aEvent ) throw (uno::RuntimeException);
|
|
|
|
|
|
|
|
// XCloseListener
|
|
|
|
virtual void SAL_CALL queryClosing( const lang::EventObject& Source, ::sal_Bool GetsOwnership ) throw (util::CloseVetoException, uno::RuntimeException);
|
|
|
|
virtual void SAL_CALL notifyClosing( const lang::EventObject& Source ) throw (uno::RuntimeException);
|
|
|
|
|
|
|
|
// XBorderResizeListener
|
|
|
|
virtual void SAL_CALL borderWidthsChanged( const uno::Reference< uno::XInterface >& aObject, const frame::BorderWidths& aNewSize ) throw (uno::RuntimeException);
|
|
|
|
|
|
|
|
private:
|
|
|
|
uno::Reference< frame::XFrame > getFrame();
|
|
|
|
uno::Reference< awt::XWindow > getContainerWindow();
|
|
|
|
bool isMouseReleased();
|
|
|
|
DECL_LINK( fireResizeMacro, void* );
|
|
|
|
void processWindowResizeMacro();
|
|
|
|
|
|
|
|
private:
|
|
|
|
::osl::Mutex maMutex;
|
|
|
|
ScVbaEventsHelper* mpVbaEvents;
|
|
|
|
uno::Reference< frame::XModel > mxModel;
|
|
|
|
bool mbWindowResized;
|
|
|
|
bool mbBorderChanged;
|
|
|
|
};
|
|
|
|
|
|
|
|
// ----------------------------------------------------------------------------
|
|
|
|
|
|
|
|
ScVbaWindowListener::ScVbaWindowListener( ScVbaEventsHelper* pHelper, const uno::Reference< frame::XModel >& rxModel ) :
|
|
|
|
mpVbaEvents( pHelper ),
|
|
|
|
mxModel( rxModel ),
|
|
|
|
mbWindowResized( sal_False ),
|
|
|
|
mbBorderChanged( sal_False )
|
|
|
|
{
|
|
|
|
OSL_TRACE( "ScVbaWindowListener::ScVbaWindowListener( 0x%x ) - ctor ", this );
|
|
|
|
}
|
|
|
|
|
|
|
|
ScVbaWindowListener::~ScVbaWindowListener()
|
|
|
|
{
|
|
|
|
OSL_TRACE( "ScVbaWindowListener::~ScVbaWindowListener( 0x%x ) - dtor ", this );
|
|
|
|
}
|
|
|
|
|
|
|
|
void ScVbaWindowListener::startListening()
|
|
|
|
{
|
|
|
|
if( mxModel.is() )
|
|
|
|
{
|
|
|
|
// add window listener
|
|
|
|
try
|
|
|
|
{
|
|
|
|
uno::Reference< awt::XWindow > xWindow( getContainerWindow(), uno::UNO_QUERY_THROW );
|
|
|
|
xWindow->addWindowListener( this );
|
|
|
|
}
|
|
|
|
catch( uno::Exception& )
|
|
|
|
{
|
|
|
|
}
|
|
|
|
// add close listener
|
|
|
|
try
|
|
|
|
{
|
|
|
|
uno::Reference< util::XCloseBroadcaster > xCloseBroadcaster( mxModel, uno::UNO_QUERY_THROW );
|
|
|
|
xCloseBroadcaster->addCloseListener( this );
|
|
|
|
}
|
|
|
|
catch( uno::Exception& )
|
|
|
|
{
|
|
|
|
}
|
|
|
|
// add Border resize listener
|
|
|
|
try
|
|
|
|
{
|
|
|
|
uno::Reference< frame::XControllerBorder > xControllerBorder( mxModel->getCurrentController(), uno::UNO_QUERY_THROW );
|
|
|
|
xControllerBorder->addBorderResizeListener( this );
|
|
|
|
}
|
|
|
|
catch( uno::Exception& )
|
|
|
|
{
|
|
|
|
}
|
|
|
|
}
|
|
|
|
}
|
|
|
|
|
|
|
|
void ScVbaWindowListener::stopListening()
|
|
|
|
{
|
|
|
|
if( mxModel.is() )
|
|
|
|
{
|
|
|
|
try
|
|
|
|
{
|
|
|
|
uno::Reference< awt::XWindow > xWindow( getContainerWindow(), uno::UNO_QUERY_THROW );
|
|
|
|
xWindow->removeWindowListener( this );
|
|
|
|
}
|
|
|
|
catch( uno::Exception& )
|
|
|
|
{
|
|
|
|
}
|
|
|
|
try
|
|
|
|
{
|
|
|
|
uno::Reference< util::XCloseBroadcaster > xCloseBroadcaster( mxModel, uno::UNO_QUERY_THROW );
|
|
|
|
xCloseBroadcaster->removeCloseListener( this );
|
|
|
|
}
|
|
|
|
catch( uno::Exception& )
|
|
|
|
{
|
|
|
|
}
|
|
|
|
try
|
|
|
|
{
|
|
|
|
uno::Reference< frame::XControllerBorder > xControllerBorder( mxModel->getCurrentController(), uno::UNO_QUERY_THROW );
|
|
|
|
xControllerBorder->removeBorderResizeListener( this );
|
|
|
|
}
|
|
|
|
catch( uno::Exception& )
|
|
|
|
{
|
|
|
|
}
|
|
|
|
}
|
|
|
|
mpVbaEvents = 0;
|
|
|
|
}
|
|
|
|
|
|
|
|
void SAL_CALL ScVbaWindowListener::windowResized( const awt::WindowEvent& /*aEvent*/ ) throw ( uno::RuntimeException )
|
|
|
|
{
|
|
|
|
::osl::MutexGuard aGuard( maMutex );
|
|
|
|
// Workbook_window_resize event
|
|
|
|
mbWindowResized = true;
|
|
|
|
if( mbBorderChanged )
|
|
|
|
{
|
2010-07-09 16:46:39 +02:00
|
|
|
if( /*Window* pWindow =*/ VCLUnoHelper::GetWindow( getContainerWindow() ) )
|
2010-07-06 19:34:53 +02:00
|
|
|
{
|
|
|
|
mbBorderChanged = mbWindowResized = false;
|
|
|
|
acquire(); // ensure we don't get deleted before the event is handled
|
|
|
|
Application::PostUserEvent( LINK( this, ScVbaWindowListener, fireResizeMacro ), 0 );
|
|
|
|
}
|
|
|
|
}
|
|
|
|
}
|
|
|
|
|
|
|
|
void SAL_CALL ScVbaWindowListener::windowMoved( const awt::WindowEvent& /*aEvent*/ ) throw ( uno::RuntimeException )
|
|
|
|
{
|
|
|
|
// not interest this time
|
|
|
|
}
|
|
|
|
|
|
|
|
void SAL_CALL ScVbaWindowListener::windowShown( const lang::EventObject& /*aEvent*/ ) throw ( uno::RuntimeException )
|
|
|
|
{
|
|
|
|
// not interest this time
|
|
|
|
}
|
|
|
|
|
|
|
|
void SAL_CALL ScVbaWindowListener::windowHidden( const lang::EventObject& /*aEvent*/ ) throw ( uno::RuntimeException )
|
|
|
|
{
|
|
|
|
// not interest this time
|
|
|
|
}
|
|
|
|
|
|
|
|
void SAL_CALL ScVbaWindowListener::disposing( const lang::EventObject& /*aEvent*/ ) throw ( uno::RuntimeException )
|
|
|
|
{
|
|
|
|
::osl::MutexGuard aGuard( maMutex );
|
|
|
|
OSL_TRACE( "ScVbaWindowListener::disposing( 0x%x )", this );
|
|
|
|
mpVbaEvents = 0;
|
|
|
|
}
|
|
|
|
|
|
|
|
void SAL_CALL ScVbaWindowListener::queryClosing( const lang::EventObject& /*Source*/, sal_Bool /*GetsOwnership*/ ) throw (util::CloseVetoException, uno::RuntimeException)
|
|
|
|
{
|
|
|
|
// it can cancel the close, but need to throw a CloseVetoException, and it will be transmit to caller.
|
|
|
|
}
|
|
|
|
|
|
|
|
void SAL_CALL ScVbaWindowListener::notifyClosing( const lang::EventObject& /*Source*/ ) throw (uno::RuntimeException)
|
|
|
|
{
|
|
|
|
::osl::MutexGuard aGuard( maMutex );
|
|
|
|
stopListening();
|
|
|
|
}
|
|
|
|
|
|
|
|
void SAL_CALL ScVbaWindowListener::borderWidthsChanged( const uno::Reference< uno::XInterface >& /*aObject*/, const frame::BorderWidths& /*aNewSize*/ ) throw (uno::RuntimeException)
|
|
|
|
{
|
|
|
|
::osl::MutexGuard aGuard( maMutex );
|
|
|
|
// work with WindowResized event to guard Window Resize event.
|
|
|
|
mbBorderChanged = true;
|
|
|
|
if( mbWindowResized )
|
|
|
|
{
|
2010-07-09 16:46:39 +02:00
|
|
|
if( /*Window* pWindow =*/ VCLUnoHelper::GetWindow( getContainerWindow() ) )
|
2010-07-06 19:34:53 +02:00
|
|
|
{
|
|
|
|
mbWindowResized = mbBorderChanged = false;
|
|
|
|
acquire(); // ensure we don't get deleted before the timer fires.
|
|
|
|
Application::PostUserEvent( LINK( this, ScVbaWindowListener, fireResizeMacro ), 0 );
|
|
|
|
}
|
|
|
|
}
|
|
|
|
}
|
|
|
|
|
|
|
|
// ----------------------------------------------------------------------------
|
|
|
|
|
|
|
|
uno::Reference< frame::XFrame > ScVbaWindowListener::getFrame()
|
|
|
|
{
|
|
|
|
if( mpVbaEvents && mxModel.is() ) try
|
|
|
|
{
|
|
|
|
uno::Reference< frame::XController > xController( mxModel->getCurrentController(), uno::UNO_QUERY_THROW );
|
|
|
|
return xController->getFrame();
|
|
|
|
}
|
|
|
|
catch( uno::Exception& )
|
|
|
|
{
|
|
|
|
}
|
|
|
|
return uno::Reference< frame::XFrame >();
|
|
|
|
}
|
|
|
|
|
|
|
|
uno::Reference< awt::XWindow > ScVbaWindowListener::getContainerWindow()
|
|
|
|
{
|
|
|
|
try
|
|
|
|
{
|
|
|
|
uno::Reference< frame::XFrame > xFrame( getFrame(), uno::UNO_SET_THROW );
|
|
|
|
return xFrame->getContainerWindow();
|
|
|
|
}
|
|
|
|
catch( uno::Exception& )
|
|
|
|
{
|
|
|
|
}
|
|
|
|
return uno::Reference< awt::XWindow >();
|
|
|
|
}
|
|
|
|
|
|
|
|
bool ScVbaWindowListener::isMouseReleased()
|
|
|
|
{
|
|
|
|
if( Window* pWindow = VCLUnoHelper::GetWindow( getContainerWindow() ) )
|
|
|
|
{
|
|
|
|
Window::PointerState aPointerState = pWindow->GetPointerState();
|
|
|
|
return (aPointerState.mnState & ( MOUSE_LEFT | MOUSE_MIDDLE | MOUSE_RIGHT )) == 0;
|
|
|
|
}
|
|
|
|
return false;
|
|
|
|
}
|
|
|
|
|
2010-07-09 16:46:39 +02:00
|
|
|
IMPL_LINK( ScVbaWindowListener, fireResizeMacro, void*, EMPTYARG )
|
2010-07-06 19:34:53 +02:00
|
|
|
{
|
|
|
|
if( mpVbaEvents && isMouseReleased() )
|
|
|
|
processWindowResizeMacro();
|
|
|
|
release();
|
|
|
|
return 0;
|
|
|
|
}
|
|
|
|
|
|
|
|
void ScVbaWindowListener::processWindowResizeMacro()
|
|
|
|
{
|
|
|
|
OSL_TRACE( "**** Attempt to FIRE MACRO **** " );
|
|
|
|
if( mpVbaEvents )
|
|
|
|
mpVbaEvents->processVbaEvent( WORKBOOK_WINDOWRESIZE, uno::Sequence< uno::Any >() );
|
|
|
|
}
|
|
|
|
|
|
|
|
// ============================================================================
|
|
|
|
|
|
|
|
ScVbaEventsHelper::ScVbaEventsHelper( const uno::Sequence< uno::Any >& rArgs, const uno::Reference< uno::XComponentContext >& xContext ) :
|
|
|
|
VbaEventsHelperBase( rArgs, xContext ),
|
|
|
|
mbOpened( false ),
|
|
|
|
mbClosed( false )
|
|
|
|
{
|
|
|
|
mpDocShell = dynamic_cast< ScDocShell* >( mpShell ); // mpShell from base class
|
|
|
|
mpDoc = mpDocShell ? mpDocShell->GetDocument() : 0;
|
|
|
|
|
|
|
|
if( !mxModel.is() || !mpDocShell || !mpDoc )
|
|
|
|
return;
|
|
|
|
|
|
|
|
// add worksheet change listener
|
|
|
|
try
|
|
|
|
{
|
|
|
|
uno::Reference< util::XChangesNotifier > xChangesNotifier( mxModel, uno::UNO_QUERY_THROW );
|
|
|
|
uno::Reference< util::XChangesListener > xChangesListener( new ScVbaChangesListener( this, mpDocShell ) );
|
|
|
|
xChangesNotifier->addChangesListener( xChangesListener );
|
|
|
|
}
|
|
|
|
catch( uno::Exception& )
|
|
|
|
{
|
|
|
|
}
|
|
|
|
|
|
|
|
#define REGISTER_EVENT( eventid, eventname, type, cancelindex, worksheet ) \
|
|
|
|
registerEventHandler( eventid, eventname, type, cancelindex, uno::Any( worksheet ) )
|
|
|
|
|
|
|
|
#define REGISTER_WORKBOOK_EVENT( eventid, eventname, cancelindex ) \
|
|
|
|
REGISTER_EVENT( WORKBOOK_##eventid, "Workbook_" eventname, EVENTHANDLER_DOCUMENT, cancelindex, false )
|
|
|
|
|
|
|
|
#define REGISTER_WORKSHEET_EVENT( eventid, eventname, cancelindex ) \
|
|
|
|
REGISTER_EVENT( WORKSHEET_##eventid, "Worksheet_" eventname, EVENTHANDLER_DOCUMENT, cancelindex, true ); \
|
|
|
|
REGISTER_EVENT( (USERDEFINED_START + WORKSHEET_##eventid), "Workbook_Sheet" eventname, EVENTHANDLER_DOCUMENT, (((cancelindex) >= 0) ? ((cancelindex) + 1) : -1), false )
|
|
|
|
|
|
|
|
// global
|
|
|
|
REGISTER_EVENT( AUTO_OPEN, "Auto_Open", EVENTHANDLER_GLOBAL, -1, false );
|
|
|
|
REGISTER_EVENT( AUTO_CLOSE, "Auto_Close", EVENTHANDLER_GLOBAL, -1, false );
|
|
|
|
|
|
|
|
// Workbook
|
|
|
|
REGISTER_WORKBOOK_EVENT( ACTIVATE, "Activate", -1 );
|
|
|
|
REGISTER_WORKBOOK_EVENT( DEACTIVATE, "Deactivate", -1 );
|
|
|
|
REGISTER_WORKBOOK_EVENT( OPEN, "Open", -1 );
|
|
|
|
REGISTER_WORKBOOK_EVENT( BEFORECLOSE, "BeforeClose", 0 );
|
|
|
|
REGISTER_WORKBOOK_EVENT( BEFOREPRINT, "BeforePrint", 0 );
|
|
|
|
REGISTER_WORKBOOK_EVENT( BEFORESAVE, "BeforeSave", 1 );
|
|
|
|
REGISTER_WORKBOOK_EVENT( AFTERSAVE, "AfterSave", -1 );
|
|
|
|
REGISTER_WORKBOOK_EVENT( NEWSHEET, "NewSheet", -1 );
|
|
|
|
REGISTER_WORKBOOK_EVENT( WINDOWACTIVATE, "WindowActivate", -1 );
|
|
|
|
REGISTER_WORKBOOK_EVENT( WINDOWDEACTIVATE, "WindowDeactivate", -1 );
|
|
|
|
REGISTER_WORKBOOK_EVENT( WINDOWRESIZE, "WindowResize", -1 );
|
|
|
|
|
|
|
|
// Worksheet events. All events have a corresponding workbook event.
|
|
|
|
REGISTER_WORKSHEET_EVENT( ACTIVATE, "Activate", -1 );
|
|
|
|
REGISTER_WORKSHEET_EVENT( DEACTIVATE, "Deactivate", -1 );
|
|
|
|
REGISTER_WORKSHEET_EVENT( BEFOREDOUBLECLICK, "BeforeDoubleClick", 1 );
|
|
|
|
REGISTER_WORKSHEET_EVENT( BEFORERIGHTCLICK, "BeforeRightClick", 1 );
|
|
|
|
REGISTER_WORKSHEET_EVENT( CALCULATE, "Calculate", -1 );
|
|
|
|
REGISTER_WORKSHEET_EVENT( CHANGE, "Change", -1 );
|
|
|
|
REGISTER_WORKSHEET_EVENT( SELECTIONCHANGE, "SelectionChange", -1 );
|
|
|
|
REGISTER_WORKSHEET_EVENT( FOLLOWHYPERLINK, "FollowHyperlink", -1 );
|
|
|
|
|
|
|
|
#undef REGISTER_EVENT
|
|
|
|
#undef REGISTER_WORKBOOK_EVENT
|
|
|
|
#undef REGISTER_WORKSHEET_EVENT
|
|
|
|
}
|
|
|
|
|
|
|
|
ScVbaEventsHelper::~ScVbaEventsHelper()
|
|
|
|
{
|
|
|
|
}
|
|
|
|
|
|
|
|
// protected ------------------------------------------------------------------
|
|
|
|
|
|
|
|
bool ScVbaEventsHelper::implEventsEnabled() throw (uno::RuntimeException)
|
|
|
|
{
|
|
|
|
// document and document shell are needed during event processing
|
|
|
|
if( !mpDocShell || !mpDoc )
|
|
|
|
throw uno::RuntimeException();
|
|
|
|
|
|
|
|
// get Application object and check if events are enabled (this is an Excel-only attribute)
|
|
|
|
uno::Reference< excel::XApplication > xApplication( mxApplication.get(), uno::UNO_QUERY );
|
|
|
|
if( !xApplication.is() && mpShell )
|
|
|
|
{
|
|
|
|
uno::Any aVBAGlobals;
|
|
|
|
mpShell->GetBasicManager()->GetGlobalUNOConstant( "VBAGlobals", aVBAGlobals );
|
|
|
|
uno::Reference< XHelperInterface > xHelperInterface( aVBAGlobals, uno::UNO_QUERY );
|
|
|
|
if( xHelperInterface.is() )
|
|
|
|
{
|
|
|
|
xApplication.set( xHelperInterface->Application(), uno::UNO_QUERY );
|
|
|
|
mxApplication = xApplication;
|
|
|
|
}
|
|
|
|
}
|
|
|
|
if( !xApplication.is() )
|
|
|
|
throw uno::RuntimeException();
|
|
|
|
|
|
|
|
// return whether event processing is enabled
|
|
|
|
return xApplication->getEnableEvents();
|
|
|
|
}
|
|
|
|
|
|
|
|
bool ScVbaEventsHelper::implPrepareEvent( EventQueue& rEventQueue,
|
|
|
|
const EventHandlerInfo& rInfo, const uno::Sequence< uno::Any >& rArgs ) throw (uno::RuntimeException)
|
|
|
|
{
|
|
|
|
// check preconditions for some events, add more events if needed
|
|
|
|
bool bExecuteEvent = true;
|
|
|
|
switch( rInfo.mnEventId )
|
|
|
|
{
|
|
|
|
case WORKBOOK_ACTIVATE:
|
|
|
|
// while loading, framework fires this before 'opened' event, delay it
|
|
|
|
bExecuteEvent = mbOpened;
|
|
|
|
break;
|
|
|
|
case WORKBOOK_OPEN:
|
|
|
|
bExecuteEvent = !mbOpened;
|
|
|
|
if( bExecuteEvent )
|
|
|
|
{
|
|
|
|
// execute delayed Activate event too (see above)
|
|
|
|
rEventQueue.push_back( WORKBOOK_ACTIVATE );
|
|
|
|
rEventQueue.push_back( WORKBOOK_WINDOWACTIVATE );
|
|
|
|
rEventQueue.push_back( AUTO_OPEN );
|
|
|
|
}
|
|
|
|
break;
|
|
|
|
case WORKBOOK_DEACTIVATE:
|
|
|
|
if( mbClosed )
|
|
|
|
rEventQueue.push_back( WORKBOOK_WINDOWDEACTIVATE );
|
|
|
|
break;
|
|
|
|
case WORKSHEET_SELECTIONCHANGE:
|
|
|
|
// if selection is not changed, then do not fire the event
|
|
|
|
bExecuteEvent = mbOpened && !mbClosed && isSelectionChanged( rArgs, 0 );
|
|
|
|
break;
|
|
|
|
}
|
|
|
|
|
|
|
|
// add workbook event associated to a sheet event
|
|
|
|
bool bSheetEvent = false;
|
|
|
|
rInfo.maUserData >>= bSheetEvent;
|
|
|
|
if( bSheetEvent && bExecuteEvent )
|
|
|
|
rEventQueue.push_back( EventQueueEntry( rInfo.mnEventId + USERDEFINED_START, rArgs ) );
|
|
|
|
|
|
|
|
return bExecuteEvent;
|
|
|
|
}
|
|
|
|
|
|
|
|
uno::Sequence< uno::Any > ScVbaEventsHelper::implBuildArgumentList( const EventHandlerInfo& rInfo,
|
|
|
|
const uno::Sequence< uno::Any >& rArgs ) throw (lang::IllegalArgumentException)
|
|
|
|
{
|
|
|
|
// fill arguments for workbook events associated to sheet events according to sheet events, sheet will be added below
|
|
|
|
bool bSheetEventAsBookEvent = rInfo.mnEventId > USERDEFINED_START;
|
|
|
|
sal_Int32 nEventId = bSheetEventAsBookEvent ? (rInfo.mnEventId - USERDEFINED_START) : rInfo.mnEventId;
|
|
|
|
|
|
|
|
uno::Sequence< uno::Any > aVbaArgs;
|
|
|
|
switch( nEventId )
|
|
|
|
{
|
|
|
|
// *** Workbook ***
|
|
|
|
|
|
|
|
// no arguments
|
|
|
|
case WORKBOOK_ACTIVATE:
|
|
|
|
case WORKBOOK_DEACTIVATE:
|
|
|
|
case WORKBOOK_OPEN:
|
|
|
|
break;
|
|
|
|
// 1 arg: cancel
|
|
|
|
case WORKBOOK_BEFORECLOSE:
|
|
|
|
case WORKBOOK_BEFOREPRINT:
|
|
|
|
aVbaArgs.realloc( 1 );
|
|
|
|
// current cancel state will be inserted by caller
|
|
|
|
break;
|
|
|
|
// 2 args: saveAs, cancel
|
|
|
|
case WORKBOOK_BEFORESAVE:
|
|
|
|
aVbaArgs.realloc( 2 );
|
|
|
|
checkArgumentType< bool >( rArgs, 0 );
|
|
|
|
aVbaArgs[ 0 ] = rArgs[ 0 ];
|
|
|
|
// current cancel state will be inserted by caller
|
|
|
|
break;
|
|
|
|
// 1 arg: success
|
|
|
|
case WORKBOOK_AFTERSAVE:
|
|
|
|
aVbaArgs.realloc( 1 );
|
|
|
|
checkArgumentType< bool >( rArgs, 0 );
|
|
|
|
aVbaArgs[ 0 ] = rArgs[ 0 ];
|
|
|
|
break;
|
|
|
|
// 1 arg: window
|
|
|
|
case WORKBOOK_WINDOWACTIVATE:
|
|
|
|
case WORKBOOK_WINDOWDEACTIVATE:
|
|
|
|
case WORKBOOK_WINDOWRESIZE:
|
|
|
|
aVbaArgs.realloc( 1 );
|
|
|
|
aVbaArgs[ 0 ] = createWindow();
|
|
|
|
break;
|
|
|
|
// 1 arg: worksheet
|
|
|
|
case WORKBOOK_NEWSHEET:
|
|
|
|
aVbaArgs.realloc( 1 );
|
|
|
|
aVbaArgs[ 0 ] = createWorksheet( rArgs, 0 );
|
|
|
|
break;
|
|
|
|
|
|
|
|
// *** Worksheet ***
|
|
|
|
|
|
|
|
// no arguments
|
|
|
|
case WORKSHEET_ACTIVATE:
|
|
|
|
case WORKSHEET_CALCULATE:
|
|
|
|
case WORKSHEET_DEACTIVATE:
|
|
|
|
break;
|
|
|
|
// 1 arg: range
|
|
|
|
case WORKSHEET_CHANGE:
|
|
|
|
case WORKSHEET_SELECTIONCHANGE:
|
|
|
|
aVbaArgs.realloc( 1 );
|
|
|
|
aVbaArgs[ 0 ] = createRange( rArgs, 0 );
|
|
|
|
break;
|
|
|
|
// 2 args: range, cancel
|
|
|
|
case WORKSHEET_BEFOREDOUBLECLICK:
|
|
|
|
case WORKSHEET_BEFORERIGHTCLICK:
|
|
|
|
aVbaArgs.realloc( 2 );
|
|
|
|
aVbaArgs[ 0 ] = createRange( rArgs, 0 );
|
|
|
|
// current cancel state will be inserted by caller
|
|
|
|
break;
|
|
|
|
// 1 arg: hyperlink
|
|
|
|
case WORKSHEET_FOLLOWHYPERLINK:
|
|
|
|
aVbaArgs.realloc( 1 );
|
|
|
|
aVbaArgs[ 0 ] = createHyperlink( rArgs, 0 );
|
|
|
|
break;
|
|
|
|
}
|
|
|
|
|
|
|
|
/* For workbook events associated to sheet events, the workbook event gets
|
|
|
|
the same arguments but with a Worksheet object in front of them. */
|
|
|
|
if( bSheetEventAsBookEvent )
|
|
|
|
{
|
|
|
|
sal_Int32 nLength = aVbaArgs.getLength();
|
|
|
|
uno::Sequence< uno::Any > aVbaArgs2( nLength + 1 );
|
|
|
|
aVbaArgs2[ 0 ] = createWorksheet( rArgs, 0 );
|
|
|
|
for( sal_Int32 nIndex = 0; nIndex < nLength; ++nIndex )
|
|
|
|
aVbaArgs2[ nIndex + 1 ] = aVbaArgs[ nIndex ];
|
|
|
|
aVbaArgs = aVbaArgs2;
|
|
|
|
}
|
|
|
|
|
|
|
|
return aVbaArgs;
|
|
|
|
}
|
|
|
|
|
|
|
|
void ScVbaEventsHelper::implPostProcessEvent( EventQueue& rEventQueue,
|
|
|
|
const EventHandlerInfo& rInfo, bool /*bSuccess*/, bool bCancel ) throw (uno::RuntimeException)
|
|
|
|
{
|
|
|
|
switch( rInfo.mnEventId )
|
|
|
|
{
|
|
|
|
case WORKBOOK_OPEN:
|
|
|
|
mbOpened = true;
|
|
|
|
// register the window listener
|
|
|
|
if( !mxWindowListener.is() )
|
|
|
|
{
|
|
|
|
mxWindowListener = new ScVbaWindowListener( this, mxModel );
|
|
|
|
mxWindowListener->startListening();
|
|
|
|
}
|
|
|
|
break;
|
|
|
|
case WORKBOOK_BEFORECLOSE:
|
|
|
|
mbClosed = !bCancel;
|
|
|
|
if( mbClosed )
|
|
|
|
{
|
|
|
|
// execute Auto_Close if not cancelled
|
|
|
|
rEventQueue.push_back( AUTO_CLOSE );
|
|
|
|
if( mxWindowListener.is() )
|
|
|
|
{
|
|
|
|
mxWindowListener->stopListening();
|
|
|
|
mxWindowListener.clear();
|
|
|
|
}
|
|
|
|
}
|
|
|
|
break;
|
|
|
|
}
|
|
|
|
}
|
|
|
|
|
|
|
|
::rtl::OUString ScVbaEventsHelper::implGetDocumentModuleName( const EventHandlerInfo& rInfo,
|
|
|
|
const uno::Sequence< uno::Any >& rArgs ) const throw (lang::IllegalArgumentException)
|
|
|
|
{
|
|
|
|
bool bSheetEvent = false;
|
|
|
|
rInfo.maUserData >>= bSheetEvent;
|
|
|
|
SCTAB nTab = bSheetEvent ? getTabFromArgs( rArgs, 0 ) : -1;
|
|
|
|
if( bSheetEvent && (nTab < 0) )
|
|
|
|
throw lang::IllegalArgumentException();
|
|
|
|
|
|
|
|
String aCodeName;
|
|
|
|
if( bSheetEvent )
|
|
|
|
mpDoc->GetCodeName( nTab, aCodeName );
|
|
|
|
else
|
|
|
|
aCodeName = mpDoc->GetCodeName();
|
|
|
|
return aCodeName;
|
|
|
|
}
|
|
|
|
|
|
|
|
// private --------------------------------------------------------------------
|
|
|
|
|
|
|
|
SCTAB ScVbaEventsHelper::getTabFromArgs( const uno::Sequence< uno::Any >& rArgs, sal_Int32 nIndex ) throw (lang::IllegalArgumentException)
|
|
|
|
{
|
|
|
|
checkArgument( rArgs, nIndex );
|
|
|
|
|
|
|
|
// first try to extract a sheet index
|
|
|
|
SCTAB nTab = -1;
|
|
|
|
if( rArgs[ nIndex ] >>= nTab )
|
|
|
|
return nTab;
|
|
|
|
|
|
|
|
// next, try single range object
|
|
|
|
uno::Reference< sheet::XCellRangeAddressable > xCellRangeAddressable = getXSomethingFromArgs< sheet::XCellRangeAddressable >( rArgs, nIndex );
|
|
|
|
if( xCellRangeAddressable.is() )
|
|
|
|
return xCellRangeAddressable->getRangeAddress().Sheet;
|
|
|
|
|
|
|
|
// at last, try range list
|
|
|
|
uno::Reference< sheet::XSheetCellRangeContainer > xRanges = getXSomethingFromArgs< sheet::XSheetCellRangeContainer >( rArgs, nIndex );
|
|
|
|
if( xRanges.is() )
|
|
|
|
{
|
|
|
|
uno::Sequence< table::CellRangeAddress > aRangeAddresses = xRanges->getRangeAddresses();
|
|
|
|
if( aRangeAddresses.getLength() > 0 )
|
|
|
|
return aRangeAddresses[ 0 ].Sheet;
|
|
|
|
}
|
|
|
|
|
|
|
|
throw lang::IllegalArgumentException();
|
|
|
|
}
|
|
|
|
|
|
|
|
bool ScVbaEventsHelper::isSelectionChanged( const uno::Sequence< uno::Any >& rArgs, sal_Int32 nIndex ) throw (lang::IllegalArgumentException, uno::RuntimeException)
|
|
|
|
{
|
|
|
|
uno::Reference< uno::XInterface > xNewSelection = getXSomethingFromArgs< uno::XInterface >( rArgs, nIndex, false );
|
|
|
|
if( ScCellRangesBase* pNewCellRanges = ScCellRangesBase::getImplementation( xNewSelection ) )
|
|
|
|
{
|
|
|
|
bool bChanged = maOldSelection != pNewCellRanges->GetRangeList();
|
|
|
|
maOldSelection = pNewCellRanges->GetRangeList();
|
|
|
|
return bChanged;
|
|
|
|
}
|
|
|
|
maOldSelection.Clear();
|
|
|
|
return true;
|
|
|
|
}
|
|
|
|
|
|
|
|
uno::Any ScVbaEventsHelper::createWorksheet( const uno::Sequence< uno::Any >& rArgs, sal_Int32 nIndex ) const
|
|
|
|
throw (lang::IllegalArgumentException, uno::RuntimeException)
|
|
|
|
{
|
|
|
|
// Eventually we will be able to pull the Workbook/Worksheet objects
|
|
|
|
// directly from basic and register them as listeners
|
|
|
|
|
|
|
|
// extract sheet index, will throw, if parameter is invalid
|
|
|
|
SCTAB nTab = getTabFromArgs( rArgs, nIndex );
|
|
|
|
|
|
|
|
// create Workbook
|
|
|
|
uno::Sequence< uno::Any > aArgs( 2 );
|
|
|
|
aArgs[ 0 ] <<= uno::Reference< uno::XInterface >();
|
|
|
|
aArgs[ 1 ] <<= mxModel;
|
|
|
|
uno::Reference< uno::XInterface > xWorkbook( createVBAUnoAPIServiceWithArgs( mpShell, "ooo.vba.excel.Workbook", aArgs ), uno::UNO_SET_THROW );
|
|
|
|
|
|
|
|
// create WorkSheet
|
|
|
|
String aSheetName;
|
|
|
|
mpDoc->GetName( nTab, aSheetName );
|
|
|
|
aArgs = uno::Sequence< uno::Any >( 3 );
|
|
|
|
aArgs[ 0 ] <<= xWorkbook;
|
|
|
|
aArgs[ 1 ] <<= mxModel;
|
|
|
|
aArgs[ 2 ] <<= ::rtl::OUString( aSheetName );
|
|
|
|
uno::Reference< uno::XInterface > xWorksheet( createVBAUnoAPIServiceWithArgs( mpShell, "ooo.vba.excel.Worksheet", aArgs ), uno::UNO_SET_THROW );
|
|
|
|
return uno::Any( xWorksheet );
|
|
|
|
}
|
|
|
|
|
|
|
|
uno::Any ScVbaEventsHelper::createRange( const uno::Sequence< uno::Any >& rArgs, sal_Int32 nIndex ) const
|
|
|
|
throw (lang::IllegalArgumentException, uno::RuntimeException)
|
|
|
|
{
|
|
|
|
uno::Reference< sheet::XSheetCellRangeContainer > xRanges = getXSomethingFromArgs< sheet::XSheetCellRangeContainer >( rArgs, nIndex );
|
|
|
|
uno::Reference< table::XCellRange > xRange = getXSomethingFromArgs< table::XCellRange >( rArgs, nIndex );
|
|
|
|
if ( !xRanges.is() && !xRange.is() )
|
|
|
|
throw lang::IllegalArgumentException();
|
|
|
|
|
|
|
|
uno::Sequence< uno::Any > aArgs( 2 );
|
|
|
|
aArgs[ 0 ] <<= uno::Reference< uno::XInterface >(); // dummy parent
|
|
|
|
if ( xRanges.is() )
|
|
|
|
aArgs[ 1 ] <<= xRanges;
|
|
|
|
else
|
|
|
|
aArgs[ 1 ] <<= xRange;
|
|
|
|
uno::Reference< uno::XInterface > xVbaRange( createVBAUnoAPIServiceWithArgs( mpShell, "ooo.vba.excel.Range", aArgs ), uno::UNO_SET_THROW );
|
|
|
|
return uno::Any( xVbaRange );
|
|
|
|
}
|
|
|
|
|
|
|
|
uno::Any ScVbaEventsHelper::createHyperlink( const uno::Sequence< uno::Any >& rArgs, sal_Int32 nIndex ) const
|
|
|
|
throw (lang::IllegalArgumentException, uno::RuntimeException)
|
|
|
|
{
|
|
|
|
uno::Sequence< uno::Any > aArgs( 2 );
|
|
|
|
aArgs[ 0 ] <<= uno::Reference< uno::XInterface >(); // dummy parent
|
|
|
|
aArgs[ 1 ] <<= getXSomethingFromArgs< table::XCell >( rArgs, nIndex, false );
|
|
|
|
uno::Reference< uno::XInterface > xHyperlink( createVBAUnoAPIServiceWithArgs( mpShell, "ooo.vba.excel.Hyperlink", aArgs ), uno::UNO_SET_THROW );
|
|
|
|
return uno::Any( xHyperlink );
|
|
|
|
}
|
|
|
|
|
|
|
|
uno::Any ScVbaEventsHelper::createWindow() const throw (uno::RuntimeException)
|
|
|
|
{
|
|
|
|
uno::Sequence< uno::Any > aArgs( 2 );
|
|
|
|
aArgs[ 0 ] <<= createVBAUnoAPIService( mpShell, "ooo.vba.Application" );
|
|
|
|
aArgs[ 1 ] <<= mxModel;
|
|
|
|
uno::Reference< uno::XInterface > xWindow( createVBAUnoAPIServiceWithArgs( mpShell, "ooo.vba.excel.Window", aArgs ), uno::UNO_SET_THROW );
|
|
|
|
return uno::Any( xWindow );
|
|
|
|
}
|
|
|
|
|
|
|
|
// ============================================================================
|
|
|
|
|
|
|
|
namespace vbaeventshelper
|
|
|
|
{
|
|
|
|
namespace sdecl = comphelper::service_decl;
|
|
|
|
sdecl::class_<ScVbaEventsHelper, sdecl::with_args<true> > serviceImpl;
|
|
|
|
extern sdecl::ServiceDecl const serviceDecl(
|
|
|
|
serviceImpl,
|
|
|
|
"ScVbaEventsHelper",
|
2010-07-12 11:17:00 +02:00
|
|
|
"com.sun.star.script.vba.VBASpreadsheetEventProcessor" );
|
2010-07-06 19:34:53 +02:00
|
|
|
}
|
|
|
|
|
|
|
|
// ============================================================================
|