summaryrefslogtreecommitdiff
path: root/patches/vba/vba-userform.diff
diff options
context:
space:
mode:
Diffstat (limited to 'patches/vba/vba-userform.diff')
-rw-r--r--patches/vba/vba-userform.diff395
1 files changed, 0 insertions, 395 deletions
diff --git a/patches/vba/vba-userform.diff b/patches/vba/vba-userform.diff
deleted file mode 100644
index 3e853a389..000000000
--- a/patches/vba/vba-userform.diff
+++ /dev/null
@@ -1,395 +0,0 @@
-diff --git basic/inc/basic/sbmod.hxx basic/inc/basic/sbmod.hxx
-index e676a49..ab496bc 100644
---- basic/inc/basic/sbmod.hxx
-+++ basic/inc/basic/sbmod.hxx
-@@ -59,6 +59,8 @@ class SbModule : public SbxObject
- friend class SbClassModuleObject;
-
- SbModuleImpl* mpSbModuleImpl; // Impl data
-+ SbModule();
-+ SbModule(const SbModule&);
-
- protected:
- ::rtl::OUString aOUSource;
-diff --git basic/inc/basic/sbobjmod.hxx basic/inc/basic/sbobjmod.hxx
-index cb581c1..96cbe9b 100644
---- basic/inc/basic/sbobjmod.hxx
-+++ basic/inc/basic/sbobjmod.hxx
-@@ -41,6 +41,7 @@
- #include <com/sun/star/script/ModuleInfo.hpp>
- #include <com/sun/star/lang/XEventListener.hpp>
- #include <com/sun/star/awt/XDialog.hpp>
-+#include <com/sun/star/frame/XModel.hpp>
-
- namespace css = ::com::sun::star;
-
-@@ -48,6 +49,8 @@ namespace css = ::com::sun::star;
-
- class SbObjModule : public SbModule
- {
-+ SbObjModule( const SbObjModule& );
-+ SbObjModule();
- public:
- TYPEINFO();
- SbObjModule( const com::sun::star::script::ModuleInfo& mInfo, bool bIsVbaCompatible );
-@@ -56,6 +59,32 @@ public:
- void SetUnoObject( const com::sun::star::uno::Any& aObj )throw ( com::sun::star::uno::RuntimeException ) ;
- };
-
-+class SbUserFormModule : public SbObjModule
-+{
-+ css::uno::Reference<css::lang::XEventListener> m_DialogListener;
-+ css::uno::Reference<css::awt::XDialog> m_xDialog;
-+ css::uno::Reference<css::frame::XModel> m_xModel;
-+ String sFormName;
-+ bool mbInit;
-+ SbUserFormModule( const SbUserFormModule& );
-+ SbUserFormModule();
-+
-+protected:
-+ virtual void InitObject();
-+public:
-+ TYPEINFO();
-+ SbUserFormModule( const com::sun::star::script::ModuleInfo& mInfo, bool bIsVBACompat );
-+ virtual SbxVariable* Find( const XubString& rName, SbxClassType t );
-+ void ResetApiObj();
-+ void Unload();
-+ void load();
-+ void triggerMethod( const String& );
-+ void triggerActivateEvent();
-+ void triggerDeActivateEvent();
-+ void triggerInitializeEvent();
-+ void triggerTerminateEvent();
-+};
-+
- #ifndef __SB_SBOBJMODULEREF_HXX
- #define __SB_SBOBJMODULEREF_HXX
-
---- basic/source/classes/sb.cxx
-+++ basic/source/classes/sb.cxx
-@@ -715,6 +715,9 @@ SbModule* StarBASIC::MakeModule32( const
- p = new SbModule( mInfo.ModuleName, isVBAEnabled() );
- p->SetModuleType( com::sun::star::script::ModuleType::Class );
- break;
-+ case ModuleType::Form:
-+ p = new SbUserFormModule( mInfo, isVBAEnabled() );
-+ break;
- default:
- p = new SbModule( mInfo.ModuleName, isVBAEnabled() );
-
-@@ -900,9 +903,8 @@ SbxVariable* StarBASIC::Find( const Stri
- // Only variables qualified by the Module Name e.g. Sheet1.foo
- // should work for Documant && Class type Modules
- INT32 nType = p->GetModuleType();
-- //if ( nType == com::sun::star::script::ModuleType::Class || nType == com::sun::star::script::ModuleType::Document )
-- if ( nType == com::sun::star::script::ModuleType::Document )
-- continue;
-+ if ( nType == com::sun::star::script::ModuleType::Document || nType == com::sun::star::script::ModuleType::Form )
-+ continue;
- // otherwise check if the element is available
- // unset GBLSEARCH-Flag (due to Rekursion)
- USHORT nGblFlag = p->GetFlags() & SBX_GBLSEARCH;
-diff --git basic/source/classes/sbxmod.cxx basic/source/classes/sbxmod.cxx
-index 8ea4b64..d3dd8d5 100644
---- basic/source/classes/sbxmod.cxx
-+++ basic/source/classes/sbxmod.cxx
-@@ -73,7 +73,6 @@
- #include <com/sun/star/awt/XDialogProvider.hpp>
- #include <com/sun/star/awt/XTopWindow.hpp>
- #include <com/sun/star/awt/XControl.hpp>
--#include <com/sun/star/frame/XModel.hpp>
- #include <cppuhelper/implbase1.hxx>
- #include <comphelper/anytostring.hxx>
-
-@@ -86,6 +85,7 @@ TYPEINIT1(SbProcedureProperty,SbxPropert
- TYPEINIT1(SbJScriptModule,SbModule)
- TYPEINIT1(SbJScriptMethod,SbMethod)
- TYPEINIT1(SbObjModule,SbModule)
-+TYPEINIT1(SbUserFormModule,SbObjModule)
-
- SV_DECL_VARARR(SbiBreakpoints,USHORT,4,4)
- SV_IMPL_VARARR(SbiBreakpoints,USHORT)
-@@ -2272,6 +2272,242 @@ SbObjModule::Find( const XubString& rNam
- pVar = SbModule::Find( rName, t );
- return pVar;
- }
-+
-+typedef ::cppu::WeakImplHelper1< awt::XTopWindowListener > EventListener_BASE;
-+
-+class FormObjEventListenerImpl : public EventListener_BASE
-+{
-+ SbUserFormModule* mpUserForm;
-+ uno::Reference< lang::XComponent > mxComponent;
-+ bool mbDisposed;
-+ sal_Bool mbOpened;
-+ sal_Bool mbActivated;
-+ sal_Bool mbShowing;
-+ FormObjEventListenerImpl(); // not defined
-+ FormObjEventListenerImpl(const FormObjEventListenerImpl&); // not defined
-+public:
-+ FormObjEventListenerImpl( SbUserFormModule* pUserForm, const uno::Reference< lang::XComponent >& xComponent ) : mpUserForm( pUserForm ), mxComponent( xComponent) , mbDisposed( false ), mbOpened( sal_False ), mbActivated( sal_False ), mbShowing( sal_False )
-+ {
-+ if ( mxComponent.is() );
-+ {
-+ uno::Reference< awt::XTopWindow > xList( mxComponent, uno::UNO_QUERY_THROW );;
-+ //uno::Reference< awt::XWindow > xList( mxComponent, uno::UNO_QUERY_THROW );;
-+ OSL_TRACE("*********** Registering the listener");
-+ xList->addTopWindowListener( this );
-+ }
-+ }
-+
-+ ~FormObjEventListenerImpl()
-+ {
-+ removeListener();
-+ }
-+ sal_Bool isShowing() { return mbShowing; }
-+ void removeListener()
-+ {
-+ try
-+ {
-+ if ( mxComponent.is() && !mbDisposed )
-+ {
-+ uno::Reference< awt::XTopWindow > xList( mxComponent, uno::UNO_QUERY_THROW );;
-+ OSL_TRACE("*********** Removing the listener");
-+ xList->removeTopWindowListener( this );
-+ mxComponent = NULL;
-+ }
-+ }
-+ catch( uno::Exception& ) {}
-+ }
-+ virtual void SAL_CALL windowOpened( const lang::EventObject& /*e*/ ) throw (uno::RuntimeException)
-+ {
-+ if ( mpUserForm )
-+ {
-+ mbOpened = sal_True;
-+ mbShowing = sal_True;
-+ if ( mbActivated )
-+ {
-+ mbOpened = mbActivated = sal_False;
-+ mpUserForm->triggerActivateEvent();
-+ }
-+ }
-+ }
-+ virtual void SAL_CALL windowClosing( const lang::EventObject& /*e*/ ) throw (uno::RuntimeException) {}
-+ virtual void SAL_CALL windowClosed( const lang::EventObject& /*e*/ ) throw (uno::RuntimeException) { mbOpened = sal_False; mbShowing = sal_False; }
-+ virtual void SAL_CALL windowMinimized( const lang::EventObject& /*e*/ ) throw (uno::RuntimeException) {}
-+ virtual void SAL_CALL windowNormalized( const lang::EventObject& /*e*/ ) throw (uno::RuntimeException){}
-+ virtual void SAL_CALL windowActivated( const lang::EventObject& /*e*/ ) throw (uno::RuntimeException)
-+ {
-+ if ( mpUserForm )
-+ {
-+ mbActivated = sal_True;
-+ if ( mbOpened )
-+ {
-+ mbOpened = mbActivated = sal_False;
-+ mpUserForm->triggerActivateEvent();
-+ }
-+ }
-+ }
-+
-+ virtual void SAL_CALL windowDeactivated( const lang::EventObject& /*e*/ ) throw (uno::RuntimeException)
-+ {
-+ if ( mpUserForm )
-+ mpUserForm->triggerDeActivateEvent();
-+ }
-+
-+
-+ virtual void SAL_CALL disposing( const lang::EventObject& Source ) throw (uno::RuntimeException)
-+ {
-+ OSL_TRACE("** Userform/Dialog disposing");
-+ mbDisposed = true;
-+ uno::Any aSource;
-+ aSource <<= Source;
-+ mxComponent = NULL;
-+ if ( mpUserForm )
-+ mpUserForm->ResetApiObj();
-+ }
-+};
-+
-+SbUserFormModule::SbUserFormModule( const com::sun::star::script::ModuleInfo& mInfo, bool bIsCompat )
-+ :SbObjModule( mInfo, bIsCompat ), mbInit( false )
-+{
-+ m_xModel.set( mInfo.ModuleObject, uno::UNO_QUERY_THROW );
-+}
-+
-+void SbUserFormModule::ResetApiObj()
-+{
-+ if ( m_xDialog.is() ) // probably someone close the dialog window
-+ {
-+ triggerTerminateEvent();
-+ }
-+ pDocObject = NULL;
-+ m_xDialog = NULL;
-+}
-+
-+void SbUserFormModule::triggerMethod( const String& aMethodToRun )
-+{
-+ OSL_TRACE("*** trigger %s ***", rtl::OUStringToOString( aMethodToRun, RTL_TEXTENCODING_UTF8 ).getStr() );
-+ // Search method
-+ SbxVariable* pMeth = SbObjModule::Find( aMethodToRun, SbxCLASS_METHOD );
-+ if( pMeth )
-+ {
-+ SbxValues aVals;
-+ pMeth->Get( aVals );
-+ }
-+}
-+
-+void SbUserFormModule::triggerActivateEvent( void )
-+{
-+ OSL_TRACE("**** entering SbUserFormModule::triggerActivate");
-+ triggerMethod( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("UserForm_activate") ) );
-+ OSL_TRACE("**** leaving SbUserFormModule::triggerActivate");
-+}
-+
-+void SbUserFormModule::triggerDeActivateEvent( void )
-+{
-+ OSL_TRACE("**** SbUserFormModule::triggerDeActivate");
-+ triggerMethod( rtl::OUString(RTL_CONSTASCII_USTRINGPARAM("Userform_DeActivate") ) );
-+}
-+
-+void SbUserFormModule::triggerInitializeEvent( void )
-+
-+{
-+ if ( mbInit )
-+ return;
-+ OSL_TRACE("**** SbUserFormModule::triggerInitializeEvent");
-+ static String aInitMethodName( RTL_CONSTASCII_USTRINGPARAM("Userform_Initialize") );
-+ triggerMethod( aInitMethodName );
-+ mbInit = true;
-+}
-+
-+void SbUserFormModule::triggerTerminateEvent( void )
-+{
-+ OSL_TRACE("**** SbUserFormModule::triggerTerminateEvent");
-+ static String aTermMethodName( RTL_CONSTASCII_USTRINGPARAM("Userform_Terminate") );
-+ triggerMethod( aTermMethodName );
-+ mbInit=false;
-+}
-+
-+void SbUserFormModule::load()
-+{
-+ OSL_TRACE("** load() ");
-+ // forces a load
-+ if ( !pDocObject )
-+ InitObject();
-+}
-+void SbUserFormModule::Unload()
-+{
-+ OSL_TRACE("** Unload() ");
-+ if ( m_xDialog.is() )
-+ {
-+ triggerTerminateEvent();
-+ }
-+ // Search method
-+ SbxVariable* pMeth = SbObjModule::Find( String( RTL_CONSTASCII_USTRINGPARAM( "UnloadObject" ) ), SbxCLASS_METHOD );
-+ if( pMeth )
-+ {
-+ OSL_TRACE("Attempting too run the UnloadObjectMethod");
-+ m_xDialog = NULL; //release ref to the uno object
-+ SbxValues aVals;
-+ FormObjEventListenerImpl* pFormListener = dynamic_cast< FormObjEventListenerImpl* >( m_DialogListener.get() );
-+ bool bWaitForDispose = true; // assume dialog is showing
-+ if ( pFormListener )
-+ {
-+ bWaitForDispose = pFormListener->isShowing();
-+ OSL_TRACE("Showing %d", bWaitForDispose );
-+ }
-+ pMeth->Get( aVals);
-+ if ( !bWaitForDispose )
-+ {
-+ // we've either already got a dispose or we'er never going to get one
-+ ResetApiObj();
-+ } // else wait for dispose
-+ OSL_TRACE("UnloadObject completed ( we hope )");
-+ }
-+}
-+
-+void SbUserFormModule::InitObject()
-+{
-+ try
-+ {
-+
-+ if ( m_xModel.is() )
-+ {
-+ uno::Reference< lang::XMultiServiceFactory > xFactory = comphelper::getProcessServiceFactory();
-+ uno::Sequence< uno::Any > aArgs(1);
-+ aArgs[ 0 ] <<= m_xModel;
-+ rtl::OUString sDialogUrl( RTL_CONSTASCII_USTRINGPARAM("vnd.sun.star.script:" ) );
-+ sDialogUrl = sDialogUrl.concat( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("Standard") ) ).concat( rtl::OUString( '.') ).concat( GetName() ).concat( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("?location=document") ) );
-+
-+ uno::Reference< awt::XDialogProvider > xProvider( xFactory->createInstanceWithArguments( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("com.sun.star.awt.DialogProvider")), aArgs ), uno::UNO_QUERY_THROW );
-+ m_xDialog = xProvider->createDialog( sDialogUrl );
-+
-+ // create vba api object
-+ aArgs.realloc( 3 );
-+ aArgs[ 0 ] = uno::Any();
-+ aArgs[ 1 ] <<= m_xDialog;
-+ aArgs[ 2 ] <<= m_xModel;
-+ pDocObject = new SbUnoObject( GetName(), uno::makeAny( xFactory->createInstanceWithArguments( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.excel.UserForm")), aArgs ) ) );
-+ uno::Reference< lang::XComponent > xComponent( aArgs[ 1 ], uno::UNO_QUERY_THROW );
-+ // remove old listener if it exists
-+ FormObjEventListenerImpl* pFormListener = dynamic_cast< FormObjEventListenerImpl* >( m_DialogListener.get() );
-+ if ( pFormListener )
-+ pFormListener->removeListener();
-+ m_DialogListener = new FormObjEventListenerImpl( this, xComponent );
-+
-+ triggerInitializeEvent();
-+ }
-+ }
-+ catch( uno::Exception& e )
-+ {
-+ }
-+
-+}
-+
-+SbxVariable*
-+SbUserFormModule::Find( const XubString& rName, SbxClassType t )
-+{
-+ if ( !pDocObject && !GetSbData()->bRunInit )
-+ InitObject();
-+ return SbObjModule::Find( rName, t );
-+}
- /////////////////////////////////////////////////////////////////////////
-
- SbProperty::SbProperty( const String& r, SbxDataType t, SbModule* p )
-diff --git basic/source/runtime/methods.cxx basic/source/runtime/methods.cxx
-index 792bce2..a0c3cad 100644
---- basic/source/runtime/methods.cxx
-+++ basic/source/runtime/methods.cxx
-@@ -126,6 +126,8 @@ using namespace com::sun::star::io;
-
- using namespace rtl;
-
-+#include <basic/sbobjmod.hxx>
-+
- static void FilterWhiteSpace( String& rStr )
- {
- rStr.EraseAllChars( ' ' );
-@@ -4135,7 +4137,12 @@ RTLFUNC(Load)
-
- // Diesen Call einfach an das Object weiterreichen
- SbxBase* pObj = (SbxObject*)rPar.Get(1)->GetObject();
-- if( pObj && pObj->IsA( TYPE( SbxObject ) ) )
-+ if( pObj && pObj->IsA( TYPE( SbUserFormModule ) ) )
-+ {
-+ SbUserFormModule* pFormModule = ( SbUserFormModule* )pObj;
-+ pFormModule->load();
-+ }
-+ else if( pObj && pObj->IsA( TYPE( SbxObject ) ) )
- {
- SbxVariable* pVar = ((SbxObject*)pObj)->
- Find( String( RTL_CONSTASCII_USTRINGPARAM("Load") ), SbxCLASS_METHOD );
-@@ -4158,7 +4165,12 @@ RTLFUNC(Unload)
-
- // Diesen Call einfach an das Object weitereichen
- SbxBase* pObj = (SbxObject*)rPar.Get(1)->GetObject();
-- if( pObj && pObj->IsA( TYPE( SbxObject ) ) )
-+ if( pObj && pObj->IsA( TYPE( SbUserFormModule ) ) )
-+ {
-+ SbUserFormModule* pFormModule = ( SbUserFormModule* )pObj;
-+ pFormModule->Unload();
-+ }
-+ else if( pObj && pObj->IsA( TYPE( SbxObject ) ) )
- {
- SbxVariable* pVar = ((SbxObject*)pObj)->
- Find( String( RTL_CONSTASCII_USTRINGPARAM("Unload") ), SbxCLASS_METHOD );