summaryrefslogtreecommitdiff
path: root/patches/vba/vba-word-support.diff
diff options
context:
space:
mode:
Diffstat (limited to 'patches/vba/vba-word-support.diff')
-rw-r--r--patches/vba/vba-word-support.diff30509
1 files changed, 0 insertions, 30509 deletions
diff --git a/patches/vba/vba-word-support.diff b/patches/vba/vba-word-support.diff
deleted file mode 100644
index 804915cce..000000000
--- a/patches/vba/vba-word-support.diff
+++ /dev/null
@@ -1,30509 +0,0 @@
---- basic/inc/basic/basmgr.hxx.old 2009-04-06 16:41:59.000000000 +0000
-+++ basic/inc/basic/basmgr.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -231,6 +231,8 @@ public:
- ::com::sun::star::uno::Any
- SetGlobalUNOConstant( const sal_Char* _pAsciiName, const ::com::sun::star::uno::Any& _rValue );
-
-+ /** retrieves a global constant in the basic library, referring to some UNO object, returns true if a value is found ( value is in aOut ) false otherwise. */
-+ bool GetGlobalUNOConstant( const sal_Char* _pAsciiName, ::com::sun::star::uno::Any& aOut );
- /** determines whether there are password-protected modules whose size exceedes the
- legacy module size
- @param _out_rModuleNames
---- basic/inc/basic/sbstar.hxx
-+++ basic/inc/basic/sbstar.hxx
-@@ -75,6 +75,10 @@ class StarBASIC : public SbxObject
- BOOL bVBAEnabled;
- BasicLibInfo* pLibInfo; // Info block for basic manager
- SbLanguageMode eLanguageMode; // LanguageMode of the basic object
-+
-+ SbxObjectRef pVBAGlobals;
-+ SbxObject* getVBAGlobals( );
-+
- protected:
- BOOL CError( SbError, const String&, xub_StrLen, xub_StrLen, xub_StrLen );
- private:
-@@ -199,6 +203,7 @@ public:
-
- SbxObjectRef getRTL( void ) { return pRtl; }
- BOOL IsDocBasic() { return bDocBasic; }
-+ SbxVariable* VBAFind( const String& rName, SbxClassType t );
- };
-
- #ifndef __SB_SBSTARBASICREF_HXX
---- basic/prj/d.lst.old 2009-04-02 10:49:18.000000000 +0000
-+++ basic/prj/d.lst 2009-04-06 16:42:01.000000000 +0000
-@@ -7,6 +7,8 @@ mkdir: %COMMON_DEST%\res%_EXT%
- ..\%__SRC%\lib\*.dylib %_DEST%\lib%_EXT%\*.dylib
- ..\%__SRC%\lib\*.a %_DEST%\lib%_EXT%\*.a
- ..\%__SRC%\slb\sb.lib %_DEST%\lib%_EXT%\xsb.lib
-+..\%__SRC%\lib\vbahelp*.* %_DEST%\lib%_EXT%\vba*.*
-+
- ..\%__SRC%\srs\classes.srs %_DEST%\res%_EXT%\basic.srs
- ..\%COMMON_OUTDIR%\srs\classes_srs.hid %COMMON_DEST%\res%_EXT%\basic_srs.hid
- ..\%__SRC%\bin\sb?????.dll %_DEST%\bin%_EXT%\sb?????.dll
-@@ -56,4 +58,8 @@ mkdir: %_DEST%\inc%_EXT%\basic
- ..\inc\basic\sbxmstrm.hxx %_DEST%\inc%_EXT%\basic\sbxmstrm.hxx
-
- ..\inc\basic\basicmanagerrepository.hxx %_DEST%\inc%_EXT%\basic\basicmanagerrepository.hxx
-+..\inc\basic\vbacollectionimpl.hxx %_DEST%\inc%_EXT%\basic\vbacollectionimpl.hxx
-+..\inc\basic\vbahelper.hxx %_DEST%\inc%_EXT%\basic\vbahelper.hxx
-+..\inc\basic\helperdecl.hxx %_DEST%\inc%_EXT%\basic\helperdecl.hxx
-+..\inc\basic\vbahelperinterface.hxx %_DEST%\inc%_EXT%\basic\vbahelperinterface.hxx
- ..\inc\modsizeexceeded.hxx %_DEST%\inc%_EXT%\basic\modsizeexceeded.hxx
---- basic/source/basmgr/basmgr.cxx.old 2009-04-06 16:41:59.000000000 +0000
-+++ basic/source/basmgr/basmgr.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -48,6 +48,7 @@
-
- #include <basic/sbuno.hxx>
- #include <basic/basmgr.hxx>
-+#include <sbunoobj.hxx>
- #include "basrid.hxx"
- #include "sbintern.hxx"
- #include <sb.hrc>
-@@ -1833,6 +1834,23 @@ BasicError* BasicManager::GetNextError()
- DBG_CHKTHIS( BasicManager, 0 );
- return pErrorMgr->GetNextError();
- }
-+bool BasicManager::GetGlobalUNOConstant( const sal_Char* _pAsciiName, ::com::sun::star::uno::Any& aOut )
-+{
-+ bool bRes = false;
-+ StarBASIC* pStandardLib = GetStdLib();
-+ OSL_PRECOND( pStandardLib, "BasicManager::SetGlobalUNOConstant: no lib to insert into!" );
-+ if ( pStandardLib )
-+ {
-+ ::rtl::OUString sVarName( ::rtl::OUString::createFromAscii( _pAsciiName ) );
-+ SbUnoObject* pGlobs = dynamic_cast<SbUnoObject*>( pStandardLib->Find( sVarName, SbxCLASS_DONTCARE ) );
-+ if ( pGlobs )
-+ {
-+ aOut = pGlobs->getUnoAny();
-+ bRes = true;
-+ }
-+ }
-+ return bRes;
-+}
-
- Any BasicManager::SetGlobalUNOConstant( const sal_Char* _pAsciiName, const Any& _rValue )
- {
---- basic/source/classes/sb.cxx
-+++ basic/source/classes/sb.cxx
-@@ -70,7 +70,29 @@ SV_IMPL_VARARR(SbTextPortions,SbTextPort
- TYPEINIT1(StarBASIC,SbxObject)
-
- #define RTLNAME "@SBRTL"
-+// i#i68894#
-
-+const static String aThisComponent( RTL_CONSTASCII_USTRINGPARAM("ThisComponent") );
-+const static String aVBAHook( RTL_CONSTASCII_USTRINGPARAM( "VBAGlobals" ) );
-+
-+SbxObject* StarBASIC::getVBAGlobals( )
-+{
-+ if ( !pVBAGlobals )
-+ pVBAGlobals = (SbUnoObject*)Find( aVBAHook , SbxCLASS_DONTCARE );
-+ return pVBAGlobals;
-+}
-+
-+// i#i68894#
-+SbxVariable* StarBASIC::VBAFind( const String& rName, SbxClassType t )
-+{
-+ if( rName == aThisComponent )
-+ return NULL;
-+ // rename to init globals
-+ if ( getVBAGlobals( ) )
-+ return pVBAGlobals->Find( rName, t );
-+ return NULL;
-+
-+}
- // Create array for conversion SFX <-> VB error code
- struct SFX_VB_ErrorItem
- {
-@@ -609,6 +631,7 @@ StarBASIC::StarBASIC( StarBASIC* p, BOOL
- pRtl = new SbiStdObject( String( RTL_CONSTASCII_USTRINGPARAM(RTLNAME) ), this );
- // Search via StarBasic is always global
- SetFlag( SBX_GBLSEARCH );
-+ pVBAGlobals = NULL;
- }
-
- // #51727 Override SetModified so that the modified state
---- basic/source/classes/sbxmod.cxx.old 2009-04-06 16:42:00.000000000 +0000
-+++ basic/source/classes/sbxmod.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -1781,13 +1781,20 @@ void SbUserFormModule::InitObject()
- try
- {
-
-- if ( m_xModel.is() )
-+ String aHook( RTL_CONSTASCII_USTRINGPARAM( "VBAGlobals" ) );
-+ SbUnoObject* pGlobs = (SbUnoObject*)GetParent()->Find( aHook, SbxCLASS_DONTCARE );
-+ if ( m_xModel.is() && pGlobs )
- {
-+
-+ uno::Reference< lang::XMultiServiceFactory > xVBAFactory( pGlobs->getUnoAny(), uno::UNO_QUERY_THROW );
- 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") ) );
-+ rtl::OUString sProjectName( RTL_CONSTASCII_USTRINGPARAM("Standard") );
-+ if ( this->GetParent()->GetName().Len() )
-+ sProjectName = this->GetParent()->GetName();
-+ sDialogUrl = sDialogUrl.concat( sProjectName ).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 );
-@@ -1797,7 +1804,7 @@ void SbUserFormModule::InitObject()
- 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 ) ) );
-+ pDocObject = new SbUnoObject( GetName(), uno::makeAny( xVBAFactory->createInstanceWithArguments( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.msforms.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() );
---- basic/source/inc/runtime.hxx.old 2009-04-06 16:42:00.000000000 +0000
-+++ basic/source/inc/runtime.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -206,7 +206,6 @@ class SbiInstance
- BOOL bCompatibility; // Flag: TRUE = VBA runtime compatibility mode
-
- ComponentVector_t ComponentVector;
--
- public:
- SbiRuntime* pRun; // Call-Stack
- SbiInstance* pNext; // Instanzen-Chain
---- basic/source/runtime/methods.cxx.old 2009-04-06 16:42:00.000000000 +0000
-+++ basic/source/runtime/methods.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -844,6 +844,15 @@ RTLFUNC(SendKeys) // JSM
- StarBASIC::Error(SbERR_NOT_IMPLEMENTED);
- }
-
-+// Stub, basic already yields by default
-+RTLFUNC(DoEvents)
-+{
-+ (void)pBasic;
-+ (void)bWrite;
-+
-+ rPar.Get(0)->PutInteger( 0 );
-+}
-+
- RTLFUNC(Exp)
- {
- (void)pBasic;
---- basic/source/runtime/rtlproto.hxx.old 2009-04-06 16:42:00.000000000 +0000
-+++ basic/source/runtime/rtlproto.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -167,6 +167,7 @@ extern RTLFUNC(Kill); // JSM
- extern RTLFUNC(MkDir); // JSM
- extern RTLFUNC(RmDir); // JSM
- extern RTLFUNC(SendKeys); // JSM
-+extern RTLFUNC(DoEvents);
- extern RTLFUNC(DimArray);
- extern RTLFUNC(Dir);
- extern RTLFUNC(Exp);
---- basic/source/runtime/stdobj.cxx.old 2009-04-06 16:42:00.000000000 +0000
-+++ basic/source/runtime/stdobj.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -478,6 +478,7 @@ static Methods aMethods[] = {
- { "SendKeys", SbxNULL, 2 | _FUNCTION, RTLNAME(SendKeys),0 },
- { "String", SbxSTRING, 0,NULL,0 },
- { "Wait", SbxBOOL, _OPT, NULL,0 },
-+{ "DoEvents", SbxINTEGER, 0 | _FUNCTION, RTLNAME(DoEvents),0 },
- { "SetAttr", SbxNULL, 2 | _FUNCTION, RTLNAME(SetAttr),0 },
- { "File" , SbxSTRING, 0,NULL,0 },
- { "Attributes", SbxINTEGER, 0,NULL,0 },
---- basic/source/runtime/step2.cxx.old 2009-04-02 10:49:15.000000000 +0000
-+++ basic/source/runtime/step2.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -56,57 +56,6 @@ using com::sun::star::uno::Reference;
-
- SbxVariable* getVBAConstant( const String& rName );
-
--const static String aThisComponent( RTL_CONSTASCII_USTRINGPARAM("ThisComponent") );
--const static String aVBAHook( RTL_CONSTASCII_USTRINGPARAM( "VBAGlobals" ) );
--// i#i68894#
--SbxArray* getVBAGlobals( )
--{
-- static SbxArrayRef pArray;
-- static bool isInitialised = false;
-- if ( isInitialised )
-- return pArray;
-- Reference < XComponentContext > xCtx;
-- Reference < XPropertySet > xProps(
-- ::comphelper::getProcessServiceFactory(), UNO_QUERY_THROW );
-- xCtx.set( xProps->getPropertyValue( rtl::OUString(
-- RTL_CONSTASCII_USTRINGPARAM( "DefaultContext" ))),
-- UNO_QUERY_THROW );
-- SbUnoObject dGlobs( String( RTL_CONSTASCII_USTRINGPARAM("ExcelGlobals") ), xCtx->getValueByName( ::rtl::OUString::createFromAscii( "/singletons/ooo.vba.theGlobals") ) );
--
-- SbxVariable *vba = dGlobs.Find( String( RTL_CONSTASCII_USTRINGPARAM("getGlobals") ) , SbxCLASS_DONTCARE );
--
-- if ( vba )
-- {
-- pArray = static_cast<SbxArray *>(vba->GetObject());
-- isInitialised = true;
-- return pArray;
-- }
-- return NULL;
--}
--
--// i#i68894#
--SbxVariable* VBAFind( const String& rName, SbxClassType t )
--{
-- if( rName == aThisComponent )
-- return NULL;
--
-- SbxArray *pVBAGlobals = getVBAGlobals( );
-- for (USHORT i = 0; pVBAGlobals && i < pVBAGlobals->Count(); i++)
-- {
-- SbxVariable *pElem = pVBAGlobals->Get( i );
-- if (!pElem || !pElem->IsObject())
-- continue;
-- SbxObject *pVba = static_cast<SbxObject *>(pElem->GetObject());
-- SbxVariable *pVbaVar = pVba ? pVba->Find( rName, t ) : NULL;
-- if( pVbaVar )
-- {
-- return pVbaVar;
-- }
-- }
-- return NULL;
--
--}
--
- // Suchen eines Elements
- // Die Bits im String-ID:
- // 0x8000 - Argv ist belegt
-@@ -191,7 +140,7 @@ SbxVariable* SbiRuntime::FindElement
- if ( bVBAEnabled )
- {
- // Try Find in VBA symbols space
-- pElem = VBAFind( aName, SbxCLASS_DONTCARE );
-+ pElem = rBasic.VBAFind( aName, SbxCLASS_DONTCARE );
- if ( pElem )
- bSetName = false; // don't overwrite uno name
- else
---- forms/source/misc/InterfaceContainer.cxx.old 2009-04-06 16:41:59.000000000 +0000
-+++ forms/source/misc/InterfaceContainer.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -132,9 +132,8 @@ OInterfaceContainer::fakeVbaEventsHack(
- // we'll ignore, we'll get called back here anyway )
- Reference< XChild > xChild( xForm->getParent(), UNO_QUERY_THROW );
- Reference< XModel > xDocOwner( xChild->getParent(), UNO_QUERY );
-- Reference< XCodeNameQuery > xNameQuery( xDocOwner, UNO_QUERY );
- OSL_TRACE(" Is DOC ????? %s", xDocOwner.is() ? "true" : "false" );
-- if ( xDocOwner.is() && xNameQuery.is() )
-+ if ( xDocOwner.is() )
- {
- bool hasVBABindings = lcl_hasVbaEvents( m_xEventAttacher->getScriptEvents( _nIndex ) );
- if ( hasVBABindings )
-@@ -143,12 +142,14 @@ OInterfaceContainer::fakeVbaEventsHack(
- return;
- }
- Reference< XMultiServiceFactory > xFac( comphelper::getProcessServiceFactory(), UNO_QUERY );
-- if ( xFac.is() )
-+ Reference< XMultiServiceFactory > xDocFac( xDocOwner, UNO_QUERY );
-+ if ( xFac.is() && xDocFac.is() )
- {
- try
- {
- Reference< ooo::vba::XVBAToOOEventDescGen > xDescSupplier( xFac->createInstance( rtl::OUString::createFromAscii( "ooo.vba.VBAToOOEventDesc" ) ), UNO_QUERY_THROW );
- Reference< XInterface > xIf( getByIndex( _nIndex ) , UNO_QUERY_THROW );
-+ Reference< XCodeNameQuery > xNameQuery( xDocFac->createInstance( rtl::OUString::createFromAscii( "ooo.vba.VBACodeNameProvider" ) ), UNO_QUERY_THROW );
- rtl::OUString sCodeName;
- sCodeName = xNameQuery->getCodeNameForObject( xIf );
- Reference< XPropertySet > xProps( xIf, UNO_QUERY );
---- offapi/com/sun/star/document/XCompatWriterDocProperties.idl.old 1970-01-01 00:00:00.000000000 +0000
-+++ offapi/com/sun/star/document/XCompatWriterDocProperties.idl 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,49 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile: XDocumentProperties.idl,v $
-+ * $Revision: 1.5 $
-+ *
-+ * 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.
-+ *
-+ ************************************************************************/
-+#ifndef __com_sun_star_document_XCompatWriterDocProperties_idl__
-+#define __com_sun_star_document_XCompatWriterDocProperties_idl__
-+
-+#ifndef __com_sun_star_document_XDocumentProperties_idl__
-+#include <com/sun/star/document/XDocumentProperties.idl>
-+#endif
-+//=============================================================================
-+
-+module com { module sun { module star { module document {
-+interface XCompatWriterDocProperties
-+{
-+// interface ::com::sun::star::document::XDocumentProperties;
-+ [attribute] string Manager;
-+ [attribute] string Category;
-+ [attribute] string Company;
-+
-+
-+}; }; }; };
-+};
-+#endif
---- offapi/com/sun/star/document/makefile.mk.old 2009-04-06 16:42:00.000000000 +0000
-+++ offapi/com/sun/star/document/makefile.mk 2009-04-06 16:42:01.000000000 +0000
-@@ -118,6 +118,7 @@ IDLFILES=\
- XDocumentLanguages.idl \
- XCodeNameQuery.idl \
- XDocumentEventCompatibleHelper.idl \
-+ XCompatWriterDocProperties.idl \
- VbaEventId.idl \
- XVbaEventsHelper.idl \
- VbaEventsHelper.idl \
---- oovbaapi/ooo/vba/ControlProvider.idl.old 1970-01-01 00:00:00.000000000 +0000
-+++ oovbaapi/ooo/vba/ControlProvider.idl 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,54 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile: XGlobals.idl,v $
-+ * $Revision: 1.4 $
-+ *
-+ * 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.
-+ *
-+ ************************************************************************/
-+#ifndef __ooo_vba_ControlProvider_idl__
-+#define __ooo_vba_ControlProvider_idl__
-+
-+#ifndef __com_sun_star_uno_XInterface_idl__
-+#include <com/sun/star/uno/XInterface.idl>
-+#endif
-+
-+#ifndef __com_sun_star_frame_XModel_idl__
-+#include <com/sun/star/frame/XModel.idl>
-+#endif
-+
-+
-+module ooo { module vba {
-+
-+interface XControlProvider;
-+
-+service ControlProvider
-+{
-+ interface ::ooo::vba::XControlProvider;
-+};
-+
-+}; };
-+
-+#endif
-+
---- oovbaapi/ooo/vba/Globals.idl.old 2009-04-02 10:36:29.000000000 +0000
-+++ oovbaapi/ooo/vba/Globals.idl 1970-01-01 00:00:00.000000000 +0000
-@@ -1,48 +0,0 @@
--/*************************************************************************
-- *
-- * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-- *
-- * Copyright 2008 by Sun Microsystems, Inc.
-- *
-- * OpenOffice.org - a multi-platform office productivity suite
-- *
-- * $RCSfile: Globals.idl,v $
-- * $Revision: 1.3 $
-- *
-- * 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.
-- *
-- ************************************************************************/
--
--#ifndef __ooo_vba_Globals_idl__
--#define __ooo_vba_Globals_idl__
--
--#ifndef __ooo_vba_XGlobals_idl__
--#include <ooo/vba/XGlobals.idl>
--#endif
--
--#include <com/sun/star/uno/XComponentContext.idl>
--#include <com/sun/star/table/XCellRange.idl>
--
--module ooo { module vba {
--service Globals : XGlobals
--{
--};
--
--}; };
--
--#endif
---- oovbaapi/ooo/vba/XApplicationBase.idl.old 1970-01-01 00:00:00.000000000 +0000
-+++ oovbaapi/ooo/vba/XApplicationBase.idl 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,61 @@
-+/*************************************************************************
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile$
-+ *
-+ * $Revision$
-+ *
-+ * last change: $Author$ $Date$
-+ *
-+ * The Contents of this file are made available subject to
-+ * the terms of GNU Lesser General Public License Version 2.1.
-+ *
-+ *
-+ * GNU Lesser General Public License Version 2.1
-+ * =============================================
-+ * Copyright 2005 by Sun Microsystems, Inc.
-+ * 901 San Antonio Road, Palo Alto, CA 94303, USA
-+ *
-+ * This library is free software; you can redistribute it and/or
-+ * modify it under the terms of the GNU Lesser General Public
-+ * License version 2.1, as published by the Free Software Foundation.
-+ *
-+ * This library 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 for more details.
-+ *
-+ * You should have received a copy of the GNU Lesser General Public
-+ * License along with this library; if not, write to the Free Software
-+ * Foundation, Inc., 59 Temple Place, Suite 330, Boston,
-+ * MA 02111-1307 USA
-+ *
-+ ************************************************************************/
-+#ifndef __ooo_vba_XApplicationBase_idl__
-+#define __ooo_vba_XApplicationBase_idl__
-+
-+#ifndef __com_sun_star_uno_XInterface_idl__
-+#include <com/sun/star/uno/XInterface.idl>
-+#endif
-+
-+#ifndef __ooo_vba_XHelperInterface_idl__
-+#include <ooo/vba/XHelperInterface.idl>
-+#endif
-+
-+module ooo { module vba {
-+//=============================================================================
-+
-+interface XApplicationBase
-+{
-+ interface ::ooo::vba::XHelperInterface;
-+
-+ [attribute] boolean ScreenUpdating;
-+ [attribute] boolean DisplayStatusBar;
-+
-+ any CommandBars( [in] any aIndex );
-+};
-+
-+}; };
-+
-+#endif
---- oovbaapi/ooo/vba/XControlProvider.idl.old 1970-01-01 00:00:00.000000000 +0000
-+++ oovbaapi/ooo/vba/XControlProvider.idl 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,64 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile: XGlobals.idl,v $
-+ * $Revision: 1.4 $
-+ *
-+ * 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.
-+ *
-+ ************************************************************************/
-+#ifndef __ooo_vba_XControlProvider_idl__
-+#define __ooo_vba_XControlProvider_idl__
-+
-+#ifndef __com_sun_star_uno_XInterface_idl__
-+#include <com/sun/star/uno/XInterface.idl>
-+#endif
-+
-+#ifndef __com_sun_star_frame_XModel_idl__
-+#include <com/sun/star/frame/XModel.idl>
-+#endif
-+
-+#ifndef __com_sun_star_awt_XControl_idl__
-+#include <com/sun/star/awt/XControl.idl>
-+#endif
-+
-+#ifndef __com_sun_star_drawing_XControlShape_idl__
-+#include <com/sun/star/drawing/XControlShape.idl>
-+#endif
-+#ifndef __ooo_vba_msforms_XControl_idl__
-+#include <ooo/vba/msforms/XControl.idl>
-+#endif
-+
-+module ooo { module vba {
-+
-+interface XControlProvider
-+{
-+ ::ooo::vba::msforms::XControl createControl( [in] ::com::sun::star::drawing::XControlShape xControl, [in] ::com::sun::star::frame::XModel xDocOwner );
-+ ::ooo::vba::msforms::XControl createUserformControl( [in] ::com::sun::star::awt::XControl xControl, [in] ::com::sun::star::awt::XControl xDialog, [in] ::com::sun::star::frame::XModel xDocOwner );
-+
-+};
-+
-+}; };
-+
-+#endif
-+
---- oovbaapi/ooo/vba/XDocumentBase.idl.old 1970-01-01 00:00:00.000000000 +0000
-+++ oovbaapi/ooo/vba/XDocumentBase.idl 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,67 @@
-+/*************************************************************************
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile$
-+ *
-+ * $Revision$
-+ *
-+ * last change: $Author$ $Date$
-+ *
-+ * The Contents of this file are made available subject to
-+ * the terms of GNU Lesser General Public License Version 2.1.
-+ *
-+ *
-+ * GNU Lesser General Public License Version 2.1
-+ * =============================================
-+ * Copyright 2005 by Sun Microsystems, Inc.
-+ * 901 San Antonio Road, Palo Alto, CA 94303, USA
-+ *
-+ * This library is free software; you can redistribute it and/or
-+ * modify it under the terms of the GNU Lesser General Public
-+ * License version 2.1, as published by the Free Software Foundation.
-+ *
-+ * This library 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 for more details.
-+ *
-+ * You should have received a copy of the GNU Lesser General Public
-+ * License along with this library; if not, write to the Free Software
-+ * Foundation, Inc., 59 Temple Place, Suite 330, Boston,
-+ * MA 02111-1307 USA
-+ *
-+ ************************************************************************/
-+#ifndef __ooo_vba_XDocumentBase_idl__
-+#define __ooo_vba_XDocumentBase_idl__
-+
-+#ifndef __com_sun_star_uno_XInterface_idl__
-+#include <com/sun/star/uno/XInterface.idl>
-+#endif
-+
-+#ifndef __ooo_vba_XHelperInterface_idl__
-+#include <ooo/vba/XHelperInterface.idl>
-+#endif
-+
-+module ooo { module vba {
-+//=============================================================================
-+
-+interface XDocumentBase
-+{
-+ interface ::ooo::vba::XHelperInterface;
-+
-+ [attribute, readonly] string Name;
-+ [attribute, readonly] string Path;
-+ [attribute, readonly] string FullName;
-+ [attribute] boolean Saved;
-+
-+ void Close([in] any SaveChanges, [in] any FileName, [in] any RouteWorkBook);
-+ void Save();
-+ void Activate();
-+ void Protect( [in] any Password );
-+ void Unprotect( [in] any Password );
-+};
-+
-+}; };
-+
-+#endif
---- oovbaapi/ooo/vba/XDocumentProperties.idl.old 1970-01-01 00:00:00.000000000 +0000
-+++ oovbaapi/ooo/vba/XDocumentProperties.idl 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,71 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile: XDocument.idl,v $
-+ * $Revision: 1.4 $
-+ *
-+ * 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.
-+ *
-+ ************************************************************************/
-+
-+#ifndef __ooo_vba_XDocumentProperties_idl__
-+#define __ooo_vba_XDocumentProperties_idl__
-+
-+#ifndef __com_sun_star_script_BasicErrorException_idl__
-+#include <com/sun/star/script/BasicErrorException.idl>
-+#endif
-+#ifndef __ooo_vba_XHelperInterface_idl__
-+#include <ooo/vba/XHelperInterface.idl>
-+#endif
-+#ifndef __ooo_vba_XCollection_idl__
-+#include <ooo/vba/XCollection.idl>
-+#endif
-+
-+module ooo { module vba {
-+interface XDocumentProperty;
-+interface XDocumentProperties
-+{
-+ interface XCollection;
-+ /** Creates a new custom document property.
-+ * You can only add a new document property to the custom DocumentProperties collection. Depending on value of
-+ * boolean LinkSource, either (False) Value or (True) LinkSource must be provided.
-+ * @param Name (Required String. The name of the property.
-+ * @param LinkToContent Specifies whether the property is linked to the contents of the container document. If this argument is True, the LinkSource argument is required; if it's False, the value argument is required.
-+ * @param Type The data type of the property. Can be one of the following MsoDocProperties constants:
-+ * msoPropertyTypeBoolean, msoPropertyTypeDate, msoPropertyTypeFloat, msoPropertyTypeNumber, or msoPropertyTypeString.
-+ * @param Value The value of the property, if it's not linked to the contents of the container document.
-+ * The value is converted to match the data type specified by the type argument, if it can't be converted, an error occurs.
-+ * If LinkToContent is True, the Value argument is ignored and the new document property is assigned a default value
-+ * until the linked property values are updated by the container application (usually when the document is saved).
-+ * @param LinkSource Ignored if LinkToContent is False. The source of the linked property. The container application determines
-+ * what types of source linking you can use.
-+ */
-+ XDocumentProperty Add([in] string Name, [in] boolean LinkToContent, [in] /* MsoDocProperties */ byte Type, [in] any Value,
-+ [in] /*optional*/ any LinkSource)
-+ raises (com::sun::star::script::BasicErrorException);
-+};
-+
-+}; };
-+
-+#endif
-+
---- oovbaapi/ooo/vba/XDocumentProperty.idl.old 1970-01-01 00:00:00.000000000 +0000
-+++ oovbaapi/ooo/vba/XDocumentProperty.idl 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,106 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile: XDocument.idl,v $
-+ * $Revision: 1.4 $
-+ *
-+ * 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.
-+ *
-+ ************************************************************************/
-+
-+#ifndef __ooo_vba_XDocumentProperty_idl__
-+#define __ooo_vba_XDocumentProperty_idl__
-+
-+#ifndef __com_sun_star_script_BasicErrorException_idl__
-+#include <com/sun/star/script/BasicErrorException.idl>
-+#endif
-+#ifndef __com_sun_star_script_XDefaultProperty_idl__
-+#include <com/sun/star/script/XDefaultProperty.idl>
-+#endif
-+#ifndef __ooo_vba_XHelperInterface_idl__
-+#include <ooo/vba/XHelperInterface.idl>
-+#endif
-+
-+module ooo { module vba {
-+
-+/**
-+ * Specific built-in document property. Use CustomDocumentProperties(index),
-+ * where index is the name or index number of the custom document property,
-+ * to return a DocumentProperty object that represents a specific custom document property.
-+ */
-+interface XDocumentProperty
-+{
-+
-+ interface com::sun::star::script::XDefaultProperty;
-+ interface ooo::vba::XHelperInterface;
-+
-+ void Delete()
-+ raises (com::sun::star::script::BasicErrorException);
-+
-+ /** Required String. The name of the property.
-+ */
-+ string getName()
-+ raises (com::sun::star::script::BasicErrorException);
-+
-+ void setName([in] string Name)
-+ raises (com::sun::star::script::BasicErrorException);
-+
-+ /** The data type of the property.
-+ * Can be one of the following MsoDocProperties constants:
-+ * msoPropertyTypeBoolean, msoPropertyTypeDate, msoPropertyTypeFloat,
-+ * msoPropertyTypeNumber, or msoPropertyTypeString.
-+ */
-+ byte getType()
-+ raises (com::sun::star::script::BasicErrorException);
-+
-+ void setType([in] byte Type)
-+ raises (com::sun::star::script::BasicErrorException);
-+
-+ /** If true, then LinkSource has a valid value. */
-+ boolean getLinkToContent()
-+ raises (com::sun::star::script::BasicErrorException);
-+
-+ void setLinkToContent([in] boolean LinkToContent)
-+ raises (com::sun::star::script::BasicErrorException);
-+
-+ /** If LinkToContent is false, then this contains the value of the property
-+ * The data type of the value will match the Type property.
-+ */
-+ any getValue()
-+ raises (com::sun::star::script::BasicErrorException);
-+
-+ void setValue([in] any Value)
-+ raises (com::sun::star::script::BasicErrorException);
-+
-+ /** If LinkToContent is false, then this contains the value of the property */
-+ string getLinkSource()
-+ raises (com::sun::star::script::BasicErrorException);
-+
-+ void setLinkSource([in] string LinkSource)
-+ raises (com::sun::star::script::BasicErrorException);
-+};
-+
-+}; };
-+
-+#endif
-+
---- oovbaapi/ooo/vba/XGlobals.idl.old 2009-04-02 10:36:29.000000000 +0000
-+++ oovbaapi/ooo/vba/XGlobals.idl 1970-01-01 00:00:00.000000000 +0000
-@@ -1,67 +0,0 @@
--/*************************************************************************
-- *
-- * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-- *
-- * Copyright 2008 by Sun Microsystems, Inc.
-- *
-- * OpenOffice.org - a multi-platform office productivity suite
-- *
-- * $RCSfile: XGlobals.idl,v $
-- * $Revision: 1.4 $
-- *
-- * 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.
-- *
-- ************************************************************************/
--#ifndef __ooo_vba_XGlobals_idl__
--#define __ooo_vba_XGlobals_idl__
--
--#ifndef __com_sun_star_uno_XInterface_idl__
--#include <com/sun/star/uno/XInterface.idl>
--#endif
--#ifndef __ooo_vba_excel_XApplication_idl__
--#include <ooo/vba/excel/XApplication.idl>
--#endif
--#ifndef __ooo_vba_excel_XWorkbook_idl__
--#include <ooo/vba/excel/XWorkbook.idl>
--#endif
--#ifndef __ooo_vba_excel_XWorksheet_idl__
--#include <ooo/vba/excel/XWorksheet.idl>
--#endif
--
--module ooo { module vba {
--
--interface XGlobals: com::sun::star::uno::XInterface
--{
-- // FIXME, need better way to expose globals
-- sequence< any > getGlobals();
--
-- [attribute, readonly] ooo::vba::excel::XApplication Application;
-- [attribute, readonly] ooo::vba::excel::XWorkbook ActiveWorkbook;
-- [attribute, readonly] ooo::vba::excel::XWorksheet ActiveSheet;
-- any WorkSheets( [in] any aIndex );
-- any WorkBooks( [in] any aIndex );
-- any Sheets( [in] any aIndex );
-- any Range( [in] any Cell1, [in] any Cell2 );
-- any Names( [in] any Index );
--};
--
--}; };
--
--#endif
--
--
---- oovbaapi/ooo/vba/XGlobalsBase.idl.old 1970-01-01 00:00:00.000000000 +0000
-+++ oovbaapi/ooo/vba/XGlobalsBase.idl 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,53 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile: XGlobals.idl,v $
-+ * $Revision: 1.4 $
-+ *
-+ * 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.
-+ *
-+ ************************************************************************/
-+#ifndef __ooo_vba_XGlobalsBase_idl__
-+#define __ooo_vba_XGlobalsBase_idl__
-+
-+#ifndef __com_sun_star_uno_XInterface_idl__
-+#include <com/sun/star/uno/XInterface.idl>
-+#endif
-+#ifndef __ooo_vba_XHelperInterface_idl__
-+#include <ooo/vba/XHelperInterface.idl>
-+#endif
-+#ifndef __com_sun_star_lang_XMultiServiceFactory
-+#include <com/sun/star/lang/XMultiServiceFactory.idl>
-+#endif
-+module ooo { module vba {
-+interface XGlobalsBase
-+{
-+ interface ::ooo::vba::XHelperInterface;
-+ interface ::com::sun::star::lang::XMultiServiceFactory;
-+};
-+
-+}; };
-+
-+#endif
-+
-+
---- oovbaapi/ooo/vba/XWindowBase.idl.old 1970-01-01 00:00:00.000000000 +0000
-+++ oovbaapi/ooo/vba/XWindowBase.idl 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,62 @@
-+/*************************************************************************
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile$
-+ *
-+ * $Revision$
-+ *
-+ * last change: $Author$ $Date$
-+ *
-+ * The Contents of this file are made available subject to
-+ * the terms of GNU Lesser General Public License Version 2.1.
-+ *
-+ *
-+ * GNU Lesser General Public License Version 2.1
-+ * =============================================
-+ * Copyright 2005 by Sun Microsystems, Inc.
-+ * 901 San Antonio Road, Palo Alto, CA 94303, USA
-+ *
-+ * This library is free software; you can redistribute it and/or
-+ * modify it under the terms of the GNU Lesser General Public
-+ * License version 2.1, as published by the Free Software Foundation.
-+ *
-+ * This library 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 for more details.
-+ *
-+ * You should have received a copy of the GNU Lesser General Public
-+ * License along with this library; if not, write to the Free Software
-+ * Foundation, Inc., 59 Temple Place, Suite 330, Boston,
-+ * MA 02111-1307 USA
-+ *
-+ ************************************************************************/
-+#ifndef __ooo_vba_XHelperWindow_idl__
-+#define __ooo_vba_XHelperWindow_idl__
-+
-+#ifndef __com_sun_star_uno_XInterface_idl__
-+#include <com/sun/star/uno/XInterface.idl>
-+#endif
-+
-+#ifndef __ooo_vba_XHelperInterface_idl__
-+#include <ooo/vba/XHelperInterface.idl>
-+#endif
-+
-+module ooo { module vba {
-+//=============================================================================
-+
-+interface XWindowBase
-+{
-+ interface ::ooo::vba::XHelperInterface;
-+
-+ [attribute] long Height;
-+ [attribute] long Left;
-+ [attribute] long Top;
-+ [attribute] boolean Visible;
-+ [attribute] long Width;
-+};
-+
-+}; };
-+
-+#endif
---- oovbaapi/ooo/vba/excel/Globals.idl.old 1970-01-01 00:00:00.000000000 +0000
-+++ oovbaapi/ooo/vba/excel/Globals.idl 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,48 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile: Globals.idl,v $
-+ * $Revision: 1.3 $
-+ *
-+ * 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.
-+ *
-+ ************************************************************************/
-+
-+#ifndef __ooo_vba_excel_Globals_idl__
-+#define __ooo_vba_excel_Globals_idl__
-+
-+#ifndef __ooo_vba_excel_XGlobals_idl__
-+#include <ooo/vba/excel/XGlobals.idl>
-+#endif
-+
-+#include <com/sun/star/uno/XComponentContext.idl>
-+#include <com/sun/star/table/XCellRange.idl>
-+
-+module ooo { module vba { module excel {
-+service Globals : XGlobals
-+{
-+};
-+
-+}; }; };
-+
-+#endif
---- oovbaapi/ooo/vba/excel/XApplication.idl.old 2009-04-06 16:41:59.000000000 +0000
-+++ oovbaapi/ooo/vba/excel/XApplication.idl 2009-04-06 16:42:01.000000000 +0000
-@@ -42,10 +42,6 @@
- #include <ooo/vba/XAssistant.idl>
- #endif
-
--#ifndef __ooo_vba_XCommandBars_idl__
--#include <ooo/vba/XCommandBars.idl>
--#endif
--
- module ooo { module vba { module excel {
-
- interface XRange;
-@@ -56,10 +52,10 @@ interface XWorksheetFunction;
- interface XWindow;
- interface XWorksheet;
-
--interface XApplication
-+interface XApplication : com::sun::star::uno::XInterface
- {
-
-- interface ::ooo::vba::XHelperInterface;
-+// interface ::ooo::vba::XHelperInterface;
-
- [attribute, readonly] any Selection;
- [attribute, readonly] XWorkbook ActiveWorkbook;
-@@ -74,8 +70,6 @@ interface XApplication
- // to determine this
- [attribute, readonly] XWorkbook ThisWorkbook;
- [attribute, readonly] string Name;
-- [attribute] boolean ScreenUpdating;
-- [attribute] boolean DisplayStatusBar;
- [attribute] boolean DisplayAlerts;
- [attribute] boolean DisplayFormulaBar;
- [attribute] any CutCopyMode;
-@@ -90,7 +84,7 @@ interface XApplication
- string LibraryPath() raises(com::sun::star::script::BasicErrorException);
- string TemplatesPath() raises(com::sun::star::script::BasicErrorException);
- string PathSeparator() raises(com::sun::star::script::BasicErrorException);
-- any CommandBars( [in] any aIndex );
-+ //any CommandBars( [in] any aIndex );
- any Workbooks( [in] any aIndex );
- any Worksheets( [in] any aIndex );
- any Windows( [in] any aIndex );
-@@ -109,7 +103,6 @@ interface XApplication
- XRange Union([in] XRange Arg1, [in] XRange Arg2, [in] /*Optional*/ any Arg3, [in] /*Optional*/ any Arg4, [in] /*Optional*/ any Arg5, [in] /*Optional*/ any Arg6, [in] /*Optional*/ any Arg7, [in] /*Optional*/ any Arg8, [in] /*Optional*/ any Arg9, [in] /*Optional*/ any Arg10, [in] /*Optional*/ any Arg11, [in] /*Optional*/ any Arg12, [in] /*Optional*/ any Arg13, [in] /*Optional*/ any Arg14, [in] /*Optional*/ any Arg15, [in] /*Optional*/ any Arg16, [in] /*Optional*/ any Arg17, [in] /*Optional*/ any Arg18, [in] /*Optional*/ any Arg19, [in] /*Optional*/ any Arg20, [in] /*Optional*/ any Arg21, [in] /*Optional*/ any Arg22, [in] /*Optional*/ any Arg23, [in] /*Optional*/ any Arg24, [in] /*Optional*/ any Arg25, [in] /*Optional*/ any Arg26, [in] /*Optional*/ any Arg27, [in] /*Optional*/ any Arg28, [in] /*Optional*/ any Arg29, [in] /*Optional*/ any Arg30)
- raises(com::sun::star::script::BasicErrorException);
- void Volatile([in] any Volatile);
-- void DoEvents();
- any Caller( [in] any aIndex );
- };
-
---- oovbaapi/ooo/vba/excel/XGlobals.idl.old 1970-01-01 00:00:00.000000000 +0000
-+++ oovbaapi/ooo/vba/excel/XGlobals.idl 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,86 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile: XGlobals.idl,v $
-+ * $Revision: 1.4 $
-+ *
-+ * 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.
-+ *
-+ ************************************************************************/
-+#ifndef __ooo_vba_excel_XGlobals_idl__
-+#define __ooo_vba_excel_XGlobals_idl__
-+
-+#ifndef __com_sun_star_uno_XInterface_idl__
-+#include <com/sun/star/uno/XInterface.idl>
-+#endif
-+#ifndef __com_sun_star_script_BasicErrorException_idl__
-+#include <com/sun/star/script/BasicErrorException.idl>
-+#endif
-+#ifndef __ooo_vba_excel_XWorkbook_idl__
-+#include <ooo/vba/excel/XWorkbook.idl>
-+#endif
-+#ifndef __ooo_vba_excel_XWorksheet_idl__
-+#include <ooo/vba/excel/XWorksheet.idl>
-+#endif
-+#ifndef __ooo_vba_XAssistant_idl__
-+#include <ooo/vba/XAssistant.idl>
-+#endif
-+
-+module ooo { module vba { module excel {
-+interface XRange;
-+interface XWindow;
-+interface XGlobals: com::sun::star::uno::XInterface
-+{
-+ [attribute, readonly] ooo::vba::excel::XWorkbook ActiveWorkbook;
-+ [attribute, readonly] ooo::vba::excel::XWorksheet ActiveSheet;
-+ [attribute, readonly] ooo::vba::excel::XWindow ActiveWindow;
-+ [attribute, readonly] ooo::vba::excel::XRange ActiveCell;
-+ [attribute, readonly] ooo::vba::XAssistant Assistant;
-+ [attribute, readonly] any Selection;
-+ [attribute, readonly] XWorkbook ThisWorkbook;
-+
-+ void Calculate() raises(com::sun::star::script::BasicErrorException);
-+ XRange Cells([in] any RowIndex, [in] any ColumnIndex);
-+ XRange Columns([in] any aIndex);
-+ any CommandBars( [in] any aIndex );
-+ any Evaluate( [in] string Name );
-+XRange Intersect([in] XRange Arg1, [in] XRange Arg2, [in] /*Optional*/ any Arg3, [in] /*Optional*/ any Arg4, [in] /*Optional*/ any Arg5, [in] /*Optional*/ any Arg6, [in] /*Optional*/ any Arg7, [in] /*Optional*/ any Arg8, [in] /*Optional*/ any Arg9, [in] /*Optional*/ any Arg10, [in] /*Optional*/ any Arg11, [in] /*Optional*/ any Arg12, [in] /*Optional*/ any Arg13, [in] /*Optional*/ any Arg14, [in] /*Optional*/ any Arg15, [in] /*Optional*/ any Arg16, [in] /*Optional*/ any Arg17, [in] /*Optional*/ any Arg18, [in] /*Optional*/ any Arg19, [in] /*Optional*/ any Arg20, [in] /*Optional*/ any Arg21, [in] /*Optional*/ any Arg22, [in] /*Optional*/ any Arg23, [in] /*Optional*/ any Arg24, [in] /*Optional*/ any Arg25, [in] /*Optional*/ any Arg26, [in] /*Optional*/ any Arg27, [in] /*Optional*/ any Arg28, [in] /*Optional*/ any Arg29, [in] /*Optional*/ any Arg30)
-+ raises(com::sun::star::script::BasicErrorException);
-+ any WorkSheets( [in] any aIndex );
-+ any WorkBooks( [in] any aIndex );
-+ any WorksheetFunction();
-+ any Windows( [in] any aIndex );
-+ any Sheets( [in] any aIndex );
-+ any Range( [in] any Cell1, [in] any Cell2 );
-+ XRange Rows([in] any aIndex);
-+ any Names( [in] any Index );
-+ XRange Union([in] XRange Arg1, [in] XRange Arg2, [in] /*Optional*/ any Arg3, [in] /*Optional*/ any Arg4, [in] /*Optional*/ any Arg5, [in] /*Optional*/ any Arg6, [in] /*Optional*/ any Arg7, [in] /*Optional*/ any Arg8, [in] /*Optional*/ any Arg9, [in] /*Optional*/ any Arg10, [in] /*Optional*/ any Arg11, [in] /*Optional*/ any Arg12, [in] /*Optional*/ any Arg13, [in] /*Optional*/ any Arg14, [in] /*Optional*/ any Arg15, [in] /*Optional*/ any Arg16, [in] /*Optional*/ any Arg17, [in] /*Optional*/ any Arg18, [in] /*Optional*/ any Arg19, [in] /*Optional*/ any Arg20, [in] /*Optional*/ any Arg21, [in] /*Optional*/ any Arg22, [in] /*Optional*/ any Arg23, [in] /*Optional*/ any Arg24, [in] /*Optional*/ any Arg25, [in] /*Optional*/ any Arg26, [in] /*Optional*/ any Arg27, [in] /*Optional*/ any Arg28, [in] /*Optional*/ any Arg29, [in] /*Optional*/ any Arg30)
-+ raises(com::sun::star::script::BasicErrorException);
-+
-+};
-+
-+}; }; };
-+
-+#endif
-+
-+
---- oovbaapi/ooo/vba/excel/XWindow.idl.old 2009-04-02 10:36:29.000000000 +0000
-+++ oovbaapi/ooo/vba/excel/XWindow.idl 2009-04-06 16:42:01.000000000 +0000
-@@ -46,10 +46,8 @@ module ooo { module vba { module excel
- interface XRange;
- interface XWorksheet;
- interface XPane;
--interface XWindow
-+interface XWindow : com::sun::star::uno::XInterface
- {
-- interface ::ooo::vba::XHelperInterface;
--
- [attribute] any Caption;
- [attribute] boolean DisplayGridlines;
- [attribute] boolean DisplayHeadings;
-@@ -58,8 +56,6 @@ interface XWindow
- [attribute] boolean DisplayVerticalScrollBar;
- [attribute] boolean DisplayWorkbookTabs;
- [attribute] boolean FreezePanes;
-- [attribute] long Height;
-- [attribute] long Left;
- [attribute] boolean Split;
- [attribute] long SplitColumn;
- [attribute] double SplitHorizontal;
-@@ -67,10 +63,7 @@ interface XWindow
- [attribute] double SplitVertical;
- [attribute] any ScrollColumn;
- [attribute] any ScrollRow;
-- [attribute] long Top;
- [attribute] any View;
-- [attribute] boolean Visible;
-- [attribute] long Width;
- [attribute] any WindowState;
- [attribute] any Zoom;
- any SelectedSheets( [in] any aIndex );
---- oovbaapi/ooo/vba/excel/XWorkbook.idl.old 2009-04-02 10:36:29.000000000 +0000
-+++ oovbaapi/ooo/vba/excel/XWorkbook.idl 2009-04-06 16:42:01.000000000 +0000
-@@ -48,31 +48,19 @@ interface XWorksheet;
- interface XWorksheets;
- interface XStyles;
-
--interface XWorkbook
-+interface XWorkbook : com::sun::star::uno::XInterface
- {
-- interface ::ooo::vba::XHelperInterface;
--
-- [attribute, readonly] string Name;
-- [attribute, readonly] string Path;
-- [attribute, readonly] string FullName;
- [attribute, readonly] boolean ProtectStructure;
- [attribute, readonly] XWorksheet ActiveSheet;
-- [attribute] boolean Saved;
- [attribute, readonly] string CodeName;
-
- any Worksheets([in] any sheet);
- any Styles([in] any Index );
- any Sheets([in] any sheet);
- any Windows([in] any index );
-- void Close([in] any SaveChanges, [in] any FileName, [in] any RouteWorkBook);
-- void Protect( [in] any Password );
-- void Unprotect( [in] any Password );
-- void Save();
-- void Activate();
- void ResetColors() raises (com::sun::star::script::BasicErrorException);
--
-+ void Activate();
- any Names( [in] any Index );
--
- any Colors([in] any Index) raises (com::sun::star::script::BasicErrorException);
- long FileFormat() raises (com::sun::star::script::BasicErrorException);
- void SaveCopyAs( [in] string Filename );
---- oovbaapi/ooo/vba/excel/makefile.mk.old 2009-04-06 16:41:59.000000000 +0000
-+++ oovbaapi/ooo/vba/excel/makefile.mk 2009-04-06 16:42:01.000000000 +0000
-@@ -41,7 +41,9 @@ PACKAGE=ooo$/vba$/Excel
- # ------------------------------------------------------------------------
-
-
--IDLFILES= XApplication.idl\
-+IDLFILES= XGlobals.idl\
-+ Globals.idl\
-+ XApplication.idl\
- XComment.idl\
- XComments.idl\
- XRange.idl\
---- oovbaapi/ooo/vba/makefile.mk.old 2009-04-06 16:42:00.000000000 +0000
-+++ oovbaapi/ooo/vba/makefile.mk 2009-04-06 16:42:01.000000000 +0000
-@@ -42,7 +42,6 @@ PACKAGE=ooo$/vba
-
- IDLFILES=\
- XErrObject.idl \
-- XGlobals.idl \
- XCollection.idl\
- XVBAToOOEventDescGen.idl\
- XPropValue.idl\
-@@ -54,7 +53,14 @@ IDLFILES=\
- XCommandBars.idl\
- XCommandBarPopup.idl\
- XCommandBarButton.idl\
-- Globals.idl\
-+ XControlProvider.idl\
-+ ControlProvider.idl\
-+ XApplicationBase.idl\
-+ XWindowBase.idl\
-+ XDocumentBase.idl\
-+ XGlobalsBase.idl\
-+ XDocumentProperty.idl\
-+ XDocumentProperties.idl\
-
- # ------------------------------------------------------------------
-
---- oovbaapi/ooo/vba/word/XApplication.idl.old 1970-01-01 00:00:00.000000000 +0000
-+++ oovbaapi/ooo/vba/word/XApplication.idl 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,63 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile: XApplication.idl,v $
-+ * $Revision: 1.4 $
-+ *
-+ * 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.
-+ *
-+ ************************************************************************/
-+#ifndef __ooo_vba_word_XApplication_idl__
-+#define __ooo_vba_word_XApplication_idl__
-+
-+#ifndef __com_sun_star_uno_XInterface_idl__
-+#include <com/sun/star/uno/XInterface.idl>
-+#endif
-+
-+#ifndef __ooo_vba_XHelperInterface_idl__
-+#include <ooo/vba/XHelperInterface.idl>
-+#endif
-+
-+module ooo { module vba { module word {
-+
-+interface XDocument;
-+interface XWindow;
-+interface XSystem;
-+interface XOptions;
-+interface XSelection;
-+interface XApplication : com::sun::star::uno::XInterface
-+{
-+ [attribute, readonly] XDocument ActiveDocument;
-+ [attribute, readonly] XWindow ActiveWindow;
-+ [attribute, readonly] string Name;
-+ [attribute, readonly] ooo::vba::word::XSystem System;
-+ [attribute, readonly] ooo::vba::word::XOptions Options;
-+ [attribute, readonly] ooo::vba::word::XSelection Selection;
-+ any CommandBars( [in] any aIndex );
-+};
-+
-+}; }; };
-+
-+#endif
-+
-+
---- oovbaapi/ooo/vba/word/XBookmark.idl.old 1970-01-01 00:00:00.000000000 +0000
-+++ oovbaapi/ooo/vba/word/XBookmark.idl 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,61 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile:
-+ * $Revision:
-+ *
-+ * 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.
-+ *
-+ ************************************************************************/
-+#ifndef __ooo_vba_word_XBookmark_idl__
-+#define __ooo_vba_word_XBookmark_idl__
-+
-+#ifndef __com_sun_star_uno_XInterface_idl__
-+#include <com/sun/star/uno/XInterface.idl>
-+#endif
-+
-+#ifndef __ooo_vba_XHelperInterface_idl__
-+#include <ooo/vba/XHelperInterface.idl>
-+#endif
-+
-+#ifndef __com_sun_star_container_XNamed_idl__
-+#include <com/sun/star/container/XNamed.idl>
-+#endif
-+
-+module ooo { module vba { module word {
-+
-+interface XBookmark
-+{
-+ interface ooo::vba::XHelperInterface;
-+ interface ::com::sun::star::container::XNamed;
-+
-+ void Delete();
-+ void Select();
-+ any Range();
-+};
-+
-+}; }; };
-+
-+#endif
-+
-+
---- oovbaapi/ooo/vba/word/XBookmarks.idl.old 1970-01-01 00:00:00.000000000 +0000
-+++ oovbaapi/ooo/vba/word/XBookmarks.idl 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,61 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile:
-+ * $Revision:
-+ *
-+ * 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.
-+ *
-+ ************************************************************************/
-+#ifndef __ooo_vba_word_XBookmarks_idl__
-+#define __ooo_vba_word_XBookmarks_idl__
-+
-+#ifndef __com_sun_star_uno_XInterface_idl__
-+#include <com/sun/star/uno/XInterface.idl>
-+#endif
-+
-+#ifndef __ooo_vba_XCollection_idl__
-+#include <ooo/vba/XCollection.idl>
-+#endif
-+
-+
-+//=============================================================================
-+
-+module ooo { module vba { module word {
-+
-+//=============================================================================
-+
-+interface XBookmarks
-+{
-+ interface ::ooo::vba::XCollection;
-+
-+ [attribute] long DefaultSorting;
-+ [attribute] boolean ShowHidden;
-+
-+ any Add( [in] string Name, [in] any Range );
-+ boolean Exists( [in] string Name );
-+};
-+
-+}; }; };
-+
-+#endif
---- oovbaapi/ooo/vba/word/XDocument.idl.old 1970-01-01 00:00:00.000000000 +0000
-+++ oovbaapi/ooo/vba/word/XDocument.idl 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,62 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile: XDocument.idl,v $
-+ * $Revision: 1.4 $
-+ *
-+ * 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.
-+ *
-+ ************************************************************************/
-+#ifndef __ooo_vba_word_XDocument_idl__
-+#define __ooo_vba_word_XDocument_idl__
-+
-+#ifndef __com_sun_star_uno_XInterface_idl__
-+#include <com/sun/star/uno/XInterface.idl>
-+#endif
-+
-+#ifndef __ooo_vba_XHelperInterface_idl__
-+#include <ooo/vba/XHelperInterface.idl>
-+#endif
-+
-+#ifndef __ooo_vba_word_XRange_idl__
-+#include <ooo/vba/word/XRange.idl>
-+#endif
-+
-+module ooo { module vba { module word {
-+
-+interface XDocument : com::sun::star::uno::XInterface
-+{
-+ [attribute, readonly] XRange Content;
-+
-+ XRange Range( [in] any Start, [in] any End );
-+ any BuiltInDocumentProperties( [in] any index );
-+ any CustomDocumentProperties( [in] any index );
-+ any Bookmarks( [in] any aIndex );
-+ any Variables( [in] any aIndex );
-+};
-+
-+}; }; };
-+
-+#endif
-+
-+
---- oovbaapi/ooo/vba/word/XGlobals.idl.old 1970-01-01 00:00:00.000000000 +0000
-+++ oovbaapi/ooo/vba/word/XGlobals.idl 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,58 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile: XGlobals.idl,v $
-+ * $Revision: 1.4 $
-+ *
-+ * 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.
-+ *
-+ ************************************************************************/
-+#ifndef __ooo_vba_word_XGlobals_idl__
-+#define __ooo_vba_word_XGlobals_idl__
-+
-+#ifndef __com_sun_star_uno_XInterface_idl__
-+#include <com/sun/star/uno/XInterface.idl>
-+#endif
-+
-+module ooo { module vba { module word {
-+interface XDocument;
-+interface XWindow;
-+interface XSystem;
-+interface XOptions;
-+interface XSelection;
-+interface XGlobals : com::sun::star::uno::XInterface
-+{
-+ [attribute, readonly] XDocument ActiveDocument;
-+ [attribute, readonly] XWindow ActiveWindow;
-+ [attribute, readonly] string Name;
-+ [attribute, readonly] ooo::vba::word::XSystem System;
-+ [attribute, readonly] ooo::vba::word::XOptions Options;
-+ [attribute, readonly] ooo::vba::word::XSelection Selection;
-+ any CommandBars( [in] any aIndex );
-+};
-+
-+}; }; };
-+
-+#endif
-+
-+
---- oovbaapi/ooo/vba/word/XOptions.idl.old 1970-01-01 00:00:00.000000000 +0000
-+++ oovbaapi/ooo/vba/word/XOptions.idl 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,54 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile:
-+ * $Revision:
-+ *
-+ * 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.
-+ *
-+ ************************************************************************/
-+#ifndef __ooo_vba_word_XOptions_idl__
-+#define __ooo_vba_word_XOptions_idl__
-+
-+#ifndef __com_sun_star_uno_XInterface_idl__
-+#include <com/sun/star/uno/XInterface.idl>
-+#endif
-+
-+#ifndef __ooo_vba_XHelperInterface_idl__
-+#include <ooo/vba/XHelperInterface.idl>
-+#endif
-+
-+module ooo { module vba { module word {
-+
-+interface XOptions
-+{
-+ interface ooo::vba::XHelperInterface;
-+
-+ any DefaultFilePath( [in] long Path );
-+};
-+
-+}; }; };
-+
-+#endif
-+
-+
---- oovbaapi/ooo/vba/word/XPane.idl.old 1970-01-01 00:00:00.000000000 +0000
-+++ oovbaapi/ooo/vba/word/XPane.idl 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,55 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile:
-+ * $Revision:
-+ *
-+ * 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.
-+ *
-+ ************************************************************************/
-+#ifndef __ooo_vba_word_XPane_idl__
-+#define __ooo_vba_word_XPane_idl__
-+
-+#ifndef __com_sun_star_uno_XInterface_idl__
-+#include <com/sun/star/uno/XInterface.idl>
-+#endif
-+
-+#ifndef __ooo_vba_XHelperInterface_idl__
-+#include <ooo/vba/XHelperInterface.idl>
-+#endif
-+
-+module ooo { module vba { module word {
-+
-+interface XPane
-+{
-+ interface ooo::vba::XHelperInterface;
-+
-+ any View();
-+ void Close();
-+};
-+
-+}; }; };
-+
-+#endif
-+
-+
---- oovbaapi/ooo/vba/word/XPanes.idl.old 1970-01-01 00:00:00.000000000 +0000
-+++ oovbaapi/ooo/vba/word/XPanes.idl 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,55 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile:
-+ * $Revision:
-+ *
-+ * 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.
-+ *
-+ ************************************************************************/
-+#ifndef __ooo_vba_word_XPanes_idl__
-+#define __ooo_vba_word_XPanes_idl__
-+
-+#ifndef __com_sun_star_uno_XInterface_idl__
-+#include <com/sun/star/uno/XInterface.idl>
-+#endif
-+
-+#ifndef __ooo_vba_XCollection_idl__
-+#include <ooo/vba/XCollection.idl>
-+#endif
-+
-+
-+//=============================================================================
-+
-+module ooo { module vba { module word {
-+
-+//=============================================================================
-+
-+interface XPanes
-+{
-+ interface ::ooo::vba::XCollection;
-+};
-+
-+}; }; };
-+
-+#endif
---- oovbaapi/ooo/vba/word/XRange.idl.old 1970-01-01 00:00:00.000000000 +0000
-+++ oovbaapi/ooo/vba/word/XRange.idl 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,57 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile:
-+ * $Revision:
-+ *
-+ * 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.
-+ *
-+ ************************************************************************/
-+#ifndef __ooo_vba_word_XRange_idl__
-+#define __ooo_vba_word_XRange_idl__
-+
-+#ifndef __com_sun_star_uno_XInterface_idl__
-+#include <com/sun/star/uno/XInterface.idl>
-+#endif
-+
-+#ifndef __ooo_vba_XHelperInterface_idl__
-+#include <ooo/vba/XHelperInterface.idl>
-+#endif
-+
-+
-+module ooo { module vba { module word {
-+
-+interface XRange
-+{
-+ interface ooo::vba::XHelperInterface;
-+
-+ [attribute] string Text;
-+
-+ void InsertBreak( [in] any Type );
-+};
-+
-+}; }; };
-+
-+#endif
-+
-+
---- oovbaapi/ooo/vba/word/XSelection.idl.old 1970-01-01 00:00:00.000000000 +0000
-+++ oovbaapi/ooo/vba/word/XSelection.idl 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,55 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile:
-+ * $Revision:
-+ *
-+ * 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.
-+ *
-+ ************************************************************************/
-+#ifndef __ooo_vba_word_XSelection_idl__
-+#define __ooo_vba_word_XSelection_idl__
-+
-+#ifndef __com_sun_star_uno_XInterface_idl__
-+#include <com/sun/star/uno/XInterface.idl>
-+#endif
-+
-+#ifndef __ooo_vba_XHelperInterface_idl__
-+#include <ooo/vba/XHelperInterface.idl>
-+#endif
-+
-+
-+module ooo { module vba { module word {
-+
-+interface XSelection
-+{
-+ interface ooo::vba::XHelperInterface;
-+
-+ [attribute] string Text;
-+};
-+
-+}; }; };
-+
-+#endif
-+
-+
---- oovbaapi/ooo/vba/word/XSystem.idl.old 1970-01-01 00:00:00.000000000 +0000
-+++ oovbaapi/ooo/vba/word/XSystem.idl 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,56 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile:
-+ * $Revision:
-+ *
-+ * 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.
-+ *
-+ ************************************************************************/
-+#ifndef __ooo_vba_word_XSystem_idl__
-+#define __ooo_vba_word_XSystem_idl__
-+
-+#ifndef __com_sun_star_uno_XInterface_idl__
-+#include <com/sun/star/uno/XInterface.idl>
-+#endif
-+
-+#ifndef __ooo_vba_XHelperInterface_idl__
-+#include <ooo/vba/XHelperInterface.idl>
-+#endif
-+
-+
-+module ooo { module vba { module word {
-+
-+interface XSystem
-+{
-+ interface ooo::vba::XHelperInterface;
-+
-+ [attribute] long Cursor;
-+ any PrivateProfileString( [in] string Filename, [in] string Section, [in] string Key );
-+};
-+
-+}; }; };
-+
-+#endif
-+
-+
---- oovbaapi/ooo/vba/word/XVariable.idl.old 1970-01-01 00:00:00.000000000 +0000
-+++ oovbaapi/ooo/vba/word/XVariable.idl 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,60 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile:
-+ * $Revision:
-+ *
-+ * 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.
-+ *
-+ ************************************************************************/
-+#ifndef __ooo_vba_word_XVariable_idl__
-+#define __ooo_vba_word_XVariable_idl__
-+
-+#ifndef __com_sun_star_uno_XInterface_idl__
-+#include <com/sun/star/uno/XInterface.idl>
-+#endif
-+
-+#ifndef __ooo_vba_XHelperInterface_idl__
-+#include <ooo/vba/XHelperInterface.idl>
-+#endif
-+
-+#ifndef __com_sun_star_container_XNamed_idl__
-+#include <com/sun/star/container/XNamed.idl>
-+#endif
-+
-+module ooo { module vba { module word {
-+
-+interface XVariable
-+{
-+ interface ooo::vba::XHelperInterface;
-+ interface ::com::sun::star::container::XNamed;
-+
-+ [attribute] any Value;
-+ [attribute, readonly] long Index;
-+};
-+
-+}; }; };
-+
-+#endif
-+
-+
---- oovbaapi/ooo/vba/word/XVariables.idl.old 1970-01-01 00:00:00.000000000 +0000
-+++ oovbaapi/ooo/vba/word/XVariables.idl 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,57 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile:
-+ * $Revision:
-+ *
-+ * 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.
-+ *
-+ ************************************************************************/
-+#ifndef __ooo_vba_word_XVariables_idl__
-+#define __ooo_vba_word_XVariables_idl__
-+
-+#ifndef __com_sun_star_uno_XInterface_idl__
-+#include <com/sun/star/uno/XInterface.idl>
-+#endif
-+
-+#ifndef __ooo_vba_XCollection_idl__
-+#include <ooo/vba/XCollection.idl>
-+#endif
-+
-+
-+//=============================================================================
-+
-+module ooo { module vba { module word {
-+
-+//=============================================================================
-+
-+interface XVariables
-+{
-+ interface ::ooo::vba::XCollection;
-+
-+ any Add( [in] string Name, [in] any Value );
-+};
-+
-+}; }; };
-+
-+#endif
---- oovbaapi/ooo/vba/word/XView.idl.old 1970-01-01 00:00:00.000000000 +0000
-+++ oovbaapi/ooo/vba/word/XView.idl 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,57 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile:
-+ * $Revision:
-+ *
-+ * 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.
-+ *
-+ ************************************************************************/
-+#ifndef __ooo_vba_word_XView_idl__
-+#define __ooo_vba_word_XView_idl__
-+
-+#ifndef __com_sun_star_uno_XInterface_idl__
-+#include <com/sun/star/uno/XInterface.idl>
-+#endif
-+
-+#ifndef __ooo_vba_XHelperInterface_idl__
-+#include <ooo/vba/XHelperInterface.idl>
-+#endif
-+
-+module ooo { module vba { module word {
-+
-+interface XView
-+{
-+ interface ooo::vba::XHelperInterface;
-+
-+ [attribute] long SeekView;
-+ [attribute] long SplitSpecial;
-+ [attribute] boolean TableGridLines;
-+ [attribute] long Type;
-+};
-+
-+}; }; };
-+
-+#endif
-+
-+
---- oovbaapi/ooo/vba/word/XWindow.idl.old 1970-01-01 00:00:00.000000000 +0000
-+++ oovbaapi/ooo/vba/word/XWindow.idl 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,62 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile: XWindow.idl,v $
-+ * $Revision: 1.4 $
-+ *
-+ * 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.
-+ *
-+ ************************************************************************/
-+#ifndef __ooo_vba_word_XWindow_idl__
-+#define __ooo_vba_word_XWindow_idl__
-+
-+#ifndef __com_sun_star_uno_XInterface_idl__
-+#include <com/sun/star/uno/XInterface.idl>
-+#endif
-+
-+#ifndef __ooo_vba_XHelperInterface_idl__
-+#include <ooo/vba/XHelperInterface.idl>
-+#endif
-+
-+//=============================================================================
-+
-+module ooo { module vba { module word {
-+
-+//=============================================================================
-+//interface XPane;
-+interface XWindow : com::sun::star::uno::XInterface
-+{
-+ [attribute] any View;
-+ void Activate();
-+ void Close([in] any SaveChanges, [in] any RouteDocument);
-+ any Panes( [in] any aIndex ); // this is a fake api for it seems not support in Write
-+ any ActivePane(); // this is a fake api for it seems not support in Write
-+};
-+
-+//=============================================================================
-+
-+}; }; };
-+
-+#endif
-+
-+
---- oovbaapi/ooo/vba/word/makefile.mk.old 1970-01-01 00:00:00.000000000 +0000
-+++ oovbaapi/ooo/vba/word/makefile.mk 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,63 @@
-+#*************************************************************************
-+#
-+# DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+#
-+# Copyright 2008 by Sun Microsystems, Inc.
-+#
-+# OpenOffice.org - a multi-platform office productivity suite
-+#
-+# $RCSfile: makefile.mk,v $
-+#
-+# $Revision: 1.4 $
-+#
-+# 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.
-+#
-+#*************************************************************************
-+PRJ=..$/..$/..
-+
-+PRJNAME=oovapi
-+
-+TARGET=word
-+PACKAGE=ooo$/vba$/Word
-+
-+# --- Settings -----------------------------------------------------
-+.INCLUDE : $(PRJ)$/util$/makefile.pmk
-+
-+# ------------------------------------------------------------------------
-+
-+
-+IDLFILES= XGlobals.idl\
-+ XApplication.idl \
-+ XDocument.idl \
-+ XWindow.idl \
-+ XSystem.idl \
-+ XRange.idl \
-+ XBookmark.idl \
-+ XBookmarks.idl \
-+ XVariable.idl \
-+ XVariables.idl \
-+ XView.idl \
-+ XPane.idl \
-+ XPanes.idl \
-+ XOptions.idl \
-+ XSelection.idl \
-+
-+# ------------------------------------------------------------------
-+
-+.INCLUDE : target.mk
-+
---- oovbaapi/prj/build.lst.old 2009-04-02 10:36:28.000000000 +0000
-+++ oovbaapi/prj/build.lst 2009-04-06 16:42:01.000000000 +0000
-@@ -4,5 +4,6 @@ ovba oovbaapi\genconstidl
- ovba oovbaapi\ooo\vba\constants nmake - all ovba_constants ovba_genconstidl NULL
- ovba oovbaapi\ooo\vba nmake - all ovba_vba NULL
- ovba oovbaapi\ooo\vba\excel nmake - all ovba_excel NULL
-+ovba oovbaapi\ooo\vba\word nmake - all ovba_word NULL
- ovba oovbaapi\ooo\vba\msforms nmake - all ovba_msforms NULL
--ovba oovbaapi\util nmake - all ovba_util ovba_vba ovba_excel ovba_msforms ovba_constants ovba_genconstidl NULL
-+ovba oovbaapi\util nmake - all ovba_util ovba_vba ovba_excel ovba_word ovba_msforms ovba_constants ovba_genconstidl NULL
---- oovbaapi/util/makefile.mk.old 2009-04-06 16:41:59.000000000 +0000
-+++ oovbaapi/util/makefile.mk 2009-04-06 16:42:01.000000000 +0000
-@@ -44,6 +44,7 @@ TARGET=oovbaapi_db
- UNOIDLDBFILES= \
- $(UCR)$/vba.db \
- $(UCR)$/excel.db \
-+ $(UCR)$/word.db \
- $(UCR)$/msforms.db \
- $(UCR)$/constants.db
-
---- sc/inc/docuno.hxx.old 2009-04-06 16:42:00.000000000 +0000
-+++ sc/inc/docuno.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -77,8 +77,6 @@ class SvxFmDrawPage;
- class SvxDrawPage;
- class ScRangeList;
-
--#include <com/sun/star/document/XCodeNameQuery.hpp>
--
- class SC_DLLPUBLIC ScModelObj : public SfxBaseModel,
- public com::sun::star::sheet::XSpreadsheetDocument,
- public com::sun::star::document::XActionLockable,
-@@ -92,7 +90,6 @@ class SC_DLLPUBLIC ScModelObj : public S
- public com::sun::star::view::XRenderable,
- public com::sun::star::document::XLinkTargetSupplier,
- public com::sun::star::beans::XPropertySet,
-- public com::sun::star::document::XCodeNameQuery,
- public com::sun::star::document::XDocumentEventCompatibleHelper,
- public SvxFmMSFactory, // derived from XMultiServiceFactory
- public com::sun::star::lang::XServiceInfo,
-@@ -320,8 +317,6 @@ public:
- virtual void SAL_CALL removeChangesListener( const ::com::sun::star::uno::Reference<
- ::com::sun::star::util::XChangesListener >& aListener )
- throw (::com::sun::star::uno::RuntimeException);
-- virtual rtl::OUString SAL_CALL getCodeNameForObject( const ::com::sun::star::uno::Reference< ::com::sun::star::uno::XInterface >& aObj )
-- throw(::com::sun::star::uno::RuntimeException);
- // XVbaEventHelper
- virtual sal_Bool SAL_CALL processCompatibleEvent( sal_Int16 nEventId ) throw (::com::sun::star::uno::RuntimeException);
- };
---- sc/inc/servuno.hxx.old 2009-04-06 16:41:59.000000000 +0000
-+++ sc/inc/servuno.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -94,7 +94,8 @@ class ScDocShell;
- #define SC_SERVICE_FORMULAPARS 38
- #define SC_SERVICE_OPCODEMAPPER 39
- #define SC_SERVICE_VBAOBJECTPROVIDER 40
--#define SC_SERVICE_COUNT 41
-+#define SC_SERVICE_VBACODENAMEPROVIDER 41
-+#define SC_SERVICE_COUNT 42
- #define SC_SERVICE_INVALID USHRT_MAX
-
-
---- sc/prj/build.lst
-+++ sc/prj/build.lst
-@@ -1,4 +1,4 @@
--sc sc : l10n oovbaapi svx stoc uui BOOST:boost formula oox NULL
-+sc sc : l10n vbahelper oovbaapi svx stoc uui BOOST:boost formula oox NULL
- sc sc usr1 - all sc_mkout NULL
- sc sc\inc nmake - all sc_inc NULL
- sc sc\prj get - all sc_prj NULL
---- sc/source/core/tool/interpr4.cxx.old 2009-04-06 16:41:58.000000000 +0000
-+++ sc/source/core/tool/interpr4.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -77,7 +77,8 @@
- #include <map>
- #include <algorithm>
- #include <functional>
- #include <memory>
-+#include <vbahelper/vbahelper.hxx>
-
- using namespace com::sun::star;
- using namespace formula;
-@@ -2513,18 +2514,11 @@ lcl_setVBARange( ScRange& aRange, ScDocu
- try
- {
- uno::Reference< uno::XInterface > xVBARange;
-- uno::Reference< lang::XMultiComponentFactory > xSMgr( ::comphelper::getProcessServiceFactory(), uno::UNO_QUERY_THROW );
-- uno::Reference< beans::XPropertySet > xProps( xSMgr, uno::UNO_QUERY_THROW );
-- uno::Reference< uno::XComponentContext > xCtx( xProps->getPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "DefaultContext" ))), uno::UNO_QUERY_THROW );
- uno::Reference<table::XCellRange> xCellRange = ScCellRangeObj::CreateRangeFromDoc( pDok, aRange );
-- // hmm probably better not to have to include the vba generated headers
-- // here, but... if they ever become always available certainly the
-- // line below is more coder friendly
-- //xRange = ooo::vba::excel::Range::createRangeFromXCellRange( xCtx , uno::Reference< ooo::vba::XHelperInterface >(), xCellRange );
- uno::Sequence< uno::Any > aArgs(2);
- aArgs[0] = uno::Any( uno::Reference< uno::XInterface >() ); // dummy parent
- aArgs[1] = uno::Any( xCellRange );
-- xVBARange = xSMgr->createInstanceWithArgumentsAndContext( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.excel.Range") ), aArgs, xCtx );
-+ xVBARange = ov::createVBAUnoAPIServiceWithArgs( pDok->GetDocumentShell(), "ooo.vba.excel.Range", aArgs );
- if ( xVBARange.is() )
- {
- String sDummy(RTL_CONSTASCII_USTRINGPARAM("A-Range") );
---- sc/source/filter/excel/excimp8.cxx.old 2009-04-06 16:41:59.000000000 +0000
-+++ sc/source/filter/excel/excimp8.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -103,8 +103,11 @@
- #include <com/sun/star/document/XDocumentProperties.hpp>
- #include <com/sun/star/document/XDocumentPropertiesSupplier.hpp>
- #include <com/sun/star/script/ModuleInfo.hpp>
-+#include <basic/basmgr.hxx>
-+#include <cppuhelper/component_context.hxx>
-
--
-+#include <com/sun/star/container/XNameContainer.hpp>
-+
- using namespace com::sun::star;
-
-
-@@ -255,16 +258,6 @@ void ImportExcel8::SheetProtection( void
- GetSheetProtectBuffer().ReadOptions( aIn, GetCurrScTab() );
- }
-
--bool lcl_hasVBAEnabled()
--{
-- uno::Reference< beans::XPropertySet > xProps( ::comphelper::getProcessServiceFactory(), uno::UNO_QUERY);
-- // test if vba service is present
-- uno::Reference< uno::XComponentContext > xCtx( xProps->getPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "DefaultContext" ))), uno::UNO_QUERY );
-- uno::Reference< uno::XInterface > xGlobals( xCtx->getValueByName( ::rtl::OUString::createFromAscii( "/singletons/ooo.vba.theGlobals") ), uno::UNO_QUERY );
--
-- return xGlobals.is();
--}
--
- void ImportExcel8::ReadBasic( void )
- {
- //bHasBasic = TRUE;
-@@ -280,8 +273,11 @@ void ImportExcel8::ReadBasic( void )
- bool bLoadStrg = pFilterOpt->IsLoadExcelBasicStorage();
- if( bLoadCode || bLoadStrg )
- {
-+ uno::Any aGlobs;
-+ aGlobs <<= ::comphelper::getProcessServiceFactory()->createInstance( ::rtl::OUString::createFromAscii( "ooo.vba.excel.Globals") );
-+ pShell->GetBasicManager()->SetGlobalUNOConstant( "VBAGlobals", aGlobs );
- SvxImportMSVBasic aBasicImport( *pShell, *xRootStrg, bLoadCode, bLoadStrg );
-- bool bAsComment = !bLoadExecutable || !lcl_hasVBAEnabled();
-+ bool bAsComment = !bLoadExecutable || !aGlobs.hasValue();
- aBasicImport.Import( EXC_STORAGE_VBA_PROJECT, EXC_STORAGE_VBA, bAsComment );
- GetObjectManager().SetOleNameOverrideInfo( aBasicImport.ControlNameForObjectId() );
- }
---- sc/source/filter/excel/xlescher.cxx.old 2009-04-06 16:41:59.000000000 +0000
-+++ sc/source/filter/excel/xlescher.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -44,6 +44,7 @@
- #include <basic/sbstar.hxx>
- #include <basic/sbmod.hxx>
- #include <basic/sbmeth.hxx>
-+#include <basic/basmgr.hxx>
-
- using ::rtl::OUString;
- using ::com::sun::star::uno::Reference;
-@@ -305,6 +306,7 @@ Reference< XControlModel > XclControlHel
- }
-
- #define EXC_MACRONAME_PRE "vnd.sun.star.script:Standard."
-+#define EXC_MACRO_SCHEME "vnd.sun.star.script:"
- #define EXC_MACRONAME_SUF "?language=Basic&location=document"
-
- OUString XclControlHelper::GetScMacroName( const String& rXclMacroName, SfxObjectShell* pDocShell )
-@@ -312,9 +314,14 @@ OUString XclControlHelper::GetScMacroNam
- String sTmp( rXclMacroName );
- if( rXclMacroName.Len() > 0 )
- {
-+ String sProjectName( RTL_CONSTASCII_USTRINGPARAM("Standard") );
-+
-+ if ( pDocShell && pDocShell->GetBasicManager()->GetName().Len() > 0 )
-+ sProjectName = pDocShell->GetBasicManager()->GetName();
-+
- if ( ( sTmp.Search( '.' ) == STRING_NOTFOUND) && pDocShell )
- {
-- if( StarBASIC* pBasic = pDocShell->GetBasic() )
-+ if( StarBASIC* pBasic = pDocShell->GetBasicManager()->GetLib( sProjectName ) )
- {
- if( SbMethod* pMethod = dynamic_cast< SbMethod* >( pBasic->Find( sTmp, SbxCLASS_METHOD ) ) )
- {
-@@ -325,7 +332,9 @@ OUString XclControlHelper::GetScMacroNam
- }
- }
- }
-- return CREATE_OUSTRING( EXC_MACRONAME_PRE ) + sTmp + CREATE_OUSTRING( EXC_MACRONAME_SUF );
-+ sProjectName.Append( '.' );
-+ sTmp.Insert( sProjectName, 0 );
-+ return CREATE_OUSTRING( EXC_MACRO_SCHEME ) + sTmp + CREATE_OUSTRING( EXC_MACRONAME_SUF );
- }
- return OUString();
- }
---- sc/source/ui/docshell/docsh.cxx.old 2009-04-06 16:42:00.000000000 +0000
-+++ sc/source/ui/docshell/docsh.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -131,7 +131,8 @@
- #include "cellsuno.hxx"
- #include <com/sun/star/document/XVbaEventsHelper.hpp>
- #include <com/sun/star/document/VbaEventId.hpp>
--
-+#include <basic/sbstar.hxx>
-+#include <basic/basmgr.hxx>
- using namespace com::sun::star;
- using namespace com::sun::star::document::VbaEventId;
-
-@@ -284,6 +285,7 @@ void ScDocShell::BeforeXMLLoading()
- if ( xEvt.is() )
- xEvt->setIgnoreEvents( sal_True );
-
-+// if VBA enabled then we need to
- // prevent unnecessary broadcasts and updates
- DBG_ASSERT(pModificator == NULL, "The Modificator should not exist");
- pModificator = new ScDocShellModificator( *this );
-@@ -367,7 +369,14 @@ void ScDocShell::AfterXMLLoading(sal_Boo
- }
- else
- aDocument.SetInsertingFromOtherDoc( FALSE );
--
-+ // add vba globals ( if they are availabl )
-+ SfxObjectShell* pShell = aDocument.GetDocumentShell();
-+ if ( pShell )
-+ {
-+ uno::Any aGlobs;
-+ aGlobs <<= ::comphelper::getProcessServiceFactory()->createInstance( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "ooo.vba.excel.Globals" ) ) );
-+ pShell->GetBasicManager()->SetGlobalUNOConstant( "VBAGlobals", aGlobs );
-+ }
- // suppress VBA events when loading the xml
- uno::Reference< document::XVbaEventsHelper > xEvt( aDocument.GetVbaEventsHelper() );
- if ( xEvt.is() )
---- sc/source/ui/unoobj/docuno.cxx
-+++ sc/source/ui/unoobj/docuno.cxx
-@@ -107,7 +107,6 @@ using namespace com::sun::star::document
- // alles ohne Which-ID, Map nur fuer PropertySetInfo
-
- //! umbenennen, sind nicht mehr nur Options
--#include <com/sun/star/script/ScriptEventDescriptor.hpp>
- const SfxItemPropertyMapEntry* lcl_GetDocOptPropertyMap()
- {
- static SfxItemPropertyMapEntry aDocOptPropertyMap_Impl[] =
-@@ -315,7 +314,6 @@ uno::Any SAL_CALL ScModelObj::queryInter
- SC_QUERYINTERFACE( view::XRenderable )
- SC_QUERYINTERFACE( document::XLinkTargetSupplier )
- SC_QUERYINTERFACE( beans::XPropertySet )
-- SC_QUERYINTERFACE( document::XCodeNameQuery )
- SC_QUERYINTERFACE( document::XDocumentEventCompatibleHelper)
- SC_QUERYINTERFACE( lang::XMultiServiceFactory )
- SC_QUERYINTERFACE( lang::XServiceInfo )
-@@ -1723,49 +1721,7 @@ uno::Sequence<rtl::OUString> SAL_CALL Sc
-
- return concatServiceNames( aMyServices, aDrawServices );
- }
--// XCodeNameQuery
--rtl::OUString SAL_CALL
--ScModelObj::getCodeNameForObject( const uno::Reference< uno::XInterface >& xIf ) throw( uno::RuntimeException )
--{
-- rtl::OUString sCodeName;
-- if ( pDocShell )
-- {
-- OSL_TRACE( "*** In ScModelObj::getCodeNameForObject");
-- // need to find the page ( and index ) for this control
-- uno::Reference< drawing::XDrawPagesSupplier > xSupplier( pDocShell->GetModel(), uno::UNO_QUERY_THROW );
-- uno::Reference< container::XIndexAccess > xIndex( xSupplier->getDrawPages(), uno::UNO_QUERY_THROW );
-- sal_Int32 nLen = xIndex->getCount();
-- bool bMatched = false;
-- uno::Sequence< script::ScriptEventDescriptor > aFakeEvents;
-- for ( sal_Int32 index = 0; index < nLen; ++index )
-- {
-- try
-- {
-- uno::Reference< form::XFormsSupplier > xFormSupplier( xIndex->getByIndex( index ), uno::UNO_QUERY_THROW );
-- uno::Reference< container::XIndexAccess > xFormIndex( xFormSupplier->getForms(), uno::UNO_QUERY_THROW );
-- // get the www-standard container
-- uno::Reference< container::XIndexAccess > xFormControls( xFormIndex->getByIndex(0), uno::UNO_QUERY_THROW );
-- sal_Int32 nCntrls = xFormControls->getCount();
-- for( sal_Int32 cIndex = 0; cIndex < nCntrls; ++cIndex )
-- {
-- uno::Reference< uno::XInterface > xControl( xFormControls->getByIndex( cIndex ), uno::UNO_QUERY_THROW );
-- bMatched = ( xControl == xIf );
-- if ( bMatched )
-- {
-- String sName;
-- pDocShell->GetDocument()->GetCodeName( index, sName );
-- sCodeName = sName;
-- }
-- }
-- }
-- catch( uno::Exception& ) {}
-- if ( bMatched )
-- break;
-- }
-- }
-- // Probably should throw here ( if !bMatched )
-- return sCodeName;
--}
-+
- // XVbaEventHelper
- // For Vba Event
- sal_Bool SAL_CALL
---- sc/source/ui/unoobj/servuno.cxx.old 2009-04-06 16:41:59.000000000 +0000
-+++ sc/source/ui/unoobj/servuno.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -63,31 +63,31 @@
- #include <svx/xmlgrhlp.hxx>
-
- #include <comphelper/processfactory.hxx>
--
-+#include <com/sun/star/document/XCodeNameQuery.hpp>
-+#include <com/sun/star/drawing/XDrawPagesSupplier.hpp>
-+#include <com/sun/star/form/XFormsSupplier.hpp>
-+#include <com/sun/star/script/ScriptEventDescriptor.hpp>
-+#include <comphelper/componentcontext.hxx>
-+#include <cppuhelper/component_context.hxx>
-+#include <vbahelper/vbahelper.hxx>
- using namespace ::com::sun::star;
-
- class ScVbaObjectForCodeNameProvider : public ::cppu::WeakImplHelper1< container::XNameAccess >
- {
- uno::Any maWorkbook;
- uno::Any maCachedObject;
-- uno::Reference<lang::XMultiServiceFactory> mxSF;
- ScDocShell* mpDocShell;
- public:
- ScVbaObjectForCodeNameProvider( ScDocShell* pDocShell ) : mpDocShell( pDocShell )
- {
-- mxSF.set(comphelper::getProcessServiceFactory());
-- uno::Reference<beans::XPropertySet> xProps(mxSF, uno::UNO_QUERY);
-- if( xProps.is() )
-- {
-- ScDocument* pDoc = mpDocShell->GetDocument();
-- if ( !pDoc )
-- throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("")), uno::Reference< uno::XInterface >() );
--
-- uno::Sequence< uno::Any > aArgs(2);
-- aArgs[0] = uno::Any( uno::Reference< uno::XInterface >() );
-- aArgs[1] = uno::Any( mpDocShell->GetModel() );
-- maWorkbook <<= mxSF->createInstanceWithArguments( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.excel.Workbook") ), aArgs );
-- }
-+ ScDocument* pDoc = mpDocShell->GetDocument();
-+ if ( !pDoc )
-+ throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("")), uno::Reference< uno::XInterface >() );
-+
-+ uno::Sequence< uno::Any > aArgs(2);
-+ aArgs[0] = uno::Any( uno::Reference< uno::XInterface >() );
-+ aArgs[1] = uno::Any( mpDocShell->GetModel() );
-+ maWorkbook <<= ov::createVBAUnoAPIServiceWithArgs( mpDocShell, "ooo.vba.excel.Workbook", aArgs );
- }
-
- virtual ::sal_Bool SAL_CALL hasByName( const ::rtl::OUString& aName ) throw (::com::sun::star::uno::RuntimeException )
-@@ -120,7 +120,7 @@ public:
- aArgs[0] = maWorkbook;
- aArgs[1] = uno::Any( xModel );
- aArgs[2] = uno::Any( rtl::OUString( sSheetName ) );
-- maCachedObject <<= mxSF->createInstanceWithArguments( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.excel.Worksheet") ), aArgs );
-+ maCachedObject <<= ov::createVBAUnoAPIServiceWithArgs( mpDocShell, "ooo.vba.excel.Worksheet", aArgs );
- break;
- }
- }
-@@ -160,6 +160,56 @@ public:
-
- };
-
-+class ScVbaCodeNameProvider : public ::cppu::WeakImplHelper1< document::XCodeNameQuery >
-+{
-+ScDocShell* mpDocShell;
-+public:
-+ ScVbaCodeNameProvider( ScDocShell* pDocShell ) : mpDocShell( pDocShell ) {}
-+ // XCodeNameQuery
-+ rtl::OUString SAL_CALL getCodeNameForObject( const uno::Reference< uno::XInterface >& xIf ) throw( uno::RuntimeException )
-+ {
-+ rtl::OUString sCodeName;
-+ if ( mpDocShell )
-+ {
-+ OSL_TRACE( "*** In ScVbaCodeNameProvider::getCodeNameForObject");
-+ // need to find the page ( and index ) for this control
-+ uno::Reference< drawing::XDrawPagesSupplier > xSupplier( mpDocShell->GetModel(), uno::UNO_QUERY_THROW );
-+ uno::Reference< container::XIndexAccess > xIndex( xSupplier->getDrawPages(), uno::UNO_QUERY_THROW );
-+ sal_Int32 nLen = xIndex->getCount();
-+ bool bMatched = false;
-+ uno::Sequence< script::ScriptEventDescriptor > aFakeEvents;
-+ for ( sal_Int32 index = 0; index < nLen; ++index )
-+ {
-+ try
-+ {
-+ uno::Reference< form::XFormsSupplier > xFormSupplier( xIndex->getByIndex( index ), uno::UNO_QUERY_THROW );
-+ uno::Reference< container::XIndexAccess > xFormIndex( xFormSupplier->getForms(), uno::UNO_QUERY_THROW );
-+ // get the www-standard container
-+ uno::Reference< container::XIndexAccess > xFormControls( xFormIndex->getByIndex(0), uno::UNO_QUERY_THROW );
-+ sal_Int32 nCntrls = xFormControls->getCount();
-+ for( sal_Int32 cIndex = 0; cIndex < nCntrls; ++cIndex )
-+ {
-+ uno::Reference< uno::XInterface > xControl( xFormControls->getByIndex( cIndex ), uno::UNO_QUERY_THROW );
-+ bMatched = ( xControl == xIf );
-+ if ( bMatched )
-+ {
-+ String sName;
-+ mpDocShell->GetDocument()->GetCodeName( index, sName );
-+ sCodeName = sName;
-+ }
-+ }
-+ }
-+ catch( uno::Exception& ) {}
-+ if ( bMatched )
-+ break;
-+ }
-+ }
-+ // Probably should throw here ( if !bMatched )
-+ return sCodeName;
-+ }
-+
-+};
-+
- //------------------------------------------------------------------------
-
- static const sal_Char* __FAR_DATA aProvNames[SC_SERVICE_COUNT] =
-@@ -210,6 +260,7 @@ static const sal_Char* __FAR_DATA aProvN
- SC_SERVICENAME_FORMULAPARS, // SC_SERVICE_FORMULAPARS
- SC_SERVICENAME_OPCODEMAPPER, // SC_SERVICE_OPCODEMAPPER
- "ooo.vba.VBAObjectModuleObjectProvider",// SC_SERVICE_VBAOBJECTPROVIDER
-+"ooo.vba.VBACodeNameProvider",// SC_SERVICE_VBACODENAMEPROVIDER
- };
-
- //
-@@ -263,6 +314,7 @@ static const sal_Char* __FAR_DATA aOldNa
- "", // SC_SERVICE_FORMULAPARS
- "", // SC_SERVICE_OPCODEMAPPER
- "", // SC_SERVICE_VBAOBJECTPROVIDER
-+ "", // SC_SERVICE_VBACODENAMEPROVIDER
- };
-
-
-@@ -464,6 +516,9 @@ uno::Reference<uno::XInterface> ScServic
- case SC_SERVICE_VBAOBJECTPROVIDER:
- xRet.set(static_cast<container::XNameAccess*>(new ScVbaObjectForCodeNameProvider( pDocShell )));
- break;
-+ case SC_SERVICE_VBACODENAMEPROVIDER:
-+ xRet.set(static_cast<document::XCodeNameQuery*>(new ScVbaCodeNameProvider( pDocShell )));
-+ break;
- }
- return xRet;
- }
---- sc/source/ui/vba/excelvbahelper.cxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ sc/source/ui/vba/excelvbahelper.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,218 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile: vbahelper.cxx,v $
-+ * $Revision: 1.5.32.1 $
-+ *
-+ * 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 <docuno.hxx>
-+#include "excelvbahelper.hxx"
-+#include "tabvwsh.hxx"
-+#include "transobj.hxx"
-+#include "scmod.hxx"
-+#include "cellsuno.hxx"
-+#include <comphelper/processfactory.hxx>
-+
-+using namespace ::com::sun::star;
-+using namespace ::ooo::vba;
-+
-+namespace ooo
-+{
-+namespace vba
-+{
-+namespace excel
-+{
-+bool isInPrintPreview( SfxViewFrame* pView )
-+{
-+ sal_uInt16 nViewNo = SID_VIEWSHELL1 - SID_VIEWSHELL0;
-+ if ( pView->GetObjectShell()->GetFactory().GetViewFactoryCount() >
-+nViewNo && !pView->GetObjectShell()->IsInPlaceActive() )
-+ {
-+ SfxViewFactory &rViewFactory =
-+ pView->GetObjectShell()->GetFactory().GetViewFactory(nViewNo);
-+ if ( pView->GetCurViewId() == rViewFactory.GetOrdinal() )
-+ return true;
-+ }
-+ return false;
-+}
-+
-+const ::rtl::OUString REPLACE_CELLS_WARNING( RTL_CONSTASCII_USTRINGPARAM( "ReplaceCellsWarning"));
-+
-+class PasteCellsWarningReseter
-+{
-+private:
-+ bool bInitialWarningState;
-+ static uno::Reference< beans::XPropertySet > getGlobalSheetSettings() throw ( uno::RuntimeException )
-+ {
-+ static uno::Reference< beans::XPropertySet > xTmpProps( ::comphelper::getProcessServiceFactory(), uno::UNO_QUERY_THROW );
-+ static uno::Reference<uno::XComponentContext > xContext( xTmpProps->getPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "DefaultContext" ))), uno::UNO_QUERY_THROW );
-+ static uno::Reference<lang::XMultiComponentFactory > xServiceManager(
-+ xContext->getServiceManager(), uno::UNO_QUERY_THROW );
-+ static uno::Reference< beans::XPropertySet > xProps( xServiceManager->createInstanceWithContext( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "com.sun.star.sheet.GlobalSheetSettings" ) ) ,xContext ), uno::UNO_QUERY_THROW );
-+ return xProps;
-+ }
-+
-+ bool getReplaceCellsWarning() throw ( uno::RuntimeException )
-+ {
-+ sal_Bool res = sal_False;
-+ getGlobalSheetSettings()->getPropertyValue( REPLACE_CELLS_WARNING ) >>= res;
-+ return ( res == sal_True );
-+ }
-+
-+ void setReplaceCellsWarning( bool bState ) throw ( uno::RuntimeException )
-+ {
-+ getGlobalSheetSettings()->setPropertyValue( REPLACE_CELLS_WARNING, uno::makeAny( bState ) );
-+ }
-+public:
-+ PasteCellsWarningReseter() throw ( uno::RuntimeException )
-+ {
-+ bInitialWarningState = getReplaceCellsWarning();
-+ if ( bInitialWarningState )
-+ setReplaceCellsWarning( false );
-+ }
-+ ~PasteCellsWarningReseter()
-+ {
-+ if ( bInitialWarningState )
-+ {
-+ // don't allow dtor to throw
-+ try
-+ {
-+ setReplaceCellsWarning( true );
-+ }
-+ catch ( uno::Exception& /*e*/ ){}
-+ }
-+ }
-+};
-+
-+void
-+implnPaste()
-+{
-+ PasteCellsWarningReseter resetWarningBox;
-+ ScTabViewShell* pViewShell = getCurrentBestViewShell();
-+ if ( pViewShell )
-+ {
-+ pViewShell->PasteFromSystem();
-+ pViewShell->CellContentChanged();
-+ }
-+}
-+
-+
-+void
-+implnCopy()
-+{
-+ ScTabViewShell* pViewShell = getCurrentBestViewShell();
-+ if ( pViewShell )
-+ pViewShell->CopyToClip(NULL,false,false,true);
-+}
-+
-+void
-+implnCut()
-+{
-+ ScTabViewShell* pViewShell = getCurrentBestViewShell();
-+ if ( pViewShell )
-+ pViewShell->CutToClip( NULL, TRUE );
-+}
-+
-+void implnPasteSpecial(USHORT nFlags,USHORT nFunction,sal_Bool bSkipEmpty, sal_Bool bTranspose)
-+{
-+ PasteCellsWarningReseter resetWarningBox;
-+ sal_Bool bAsLink(sal_False), bOtherDoc(sal_False);
-+ InsCellCmd eMoveMode = INS_NONE;
-+
-+ ScTabViewShell* pTabViewShell = ScTabViewShell::GetActiveViewShell();
-+ if ( !pTabViewShell )
-+ // none active, try next best
-+ pTabViewShell = getCurrentBestViewShell();
-+ if ( pTabViewShell )
-+ {
-+ ScViewData* pView = pTabViewShell->GetViewData();
-+ Window* pWin = ( pView != NULL ) ? pView->GetActiveWin() : NULL;
-+ if ( pView && pWin )
-+ {
-+ if ( bAsLink && bOtherDoc )
-+ pTabViewShell->PasteFromSystem(0);//SOT_FORMATSTR_ID_LINK
-+ else
-+ {
-+ ScTransferObj* pOwnClip = ScTransferObj::GetOwnClipboard( pWin );
-+ ScDocument* pDoc = NULL;
-+ if ( pOwnClip )
-+ pDoc = pOwnClip->GetDocument();
-+ pTabViewShell->PasteFromClip( nFlags, pDoc,
-+ nFunction, bSkipEmpty, bTranspose, bAsLink,
-+ eMoveMode, IDF_NONE, TRUE );
-+ pTabViewShell->CellContentChanged();
-+ }
-+ }
-+ }
-+
-+}
-+
-+ScDocShell*
-+getDocShell( css::uno::Reference< css::frame::XModel>& xModel )
-+{
-+ uno::Reference< uno::XInterface > xIf( xModel, uno::UNO_QUERY_THROW );
-+ ScModelObj* pModel = dynamic_cast< ScModelObj* >( xIf.get() );
-+ ScDocShell* pDocShell = NULL;
-+ if ( pModel )
-+ pDocShell = (ScDocShell*)pModel->GetEmbeddedObject();
-+ return pDocShell;
-+
-+}
-+
-+ScTabViewShell*
-+getBestViewShell( css::uno::Reference< css::frame::XModel>& xModel )
-+{
-+ ScDocShell* pDocShell = getDocShell( xModel );
-+ if ( pDocShell )
-+ return pDocShell->GetBestViewShell();
-+ return NULL;
-+}
-+
-+ScTabViewShell*
-+getCurrentBestViewShell()
-+{
-+ uno::Reference< frame::XModel > xModel = getCurrentDocument();
-+ return getBestViewShell( xModel );
-+}
-+
-+SfxViewFrame*
-+getCurrentViewFrame()
-+{
-+ ScTabViewShell* pViewShell = getCurrentBestViewShell();
-+ if ( pViewShell )
-+ return pViewShell->GetViewFrame();
-+ return NULL;
-+}
-+
-+SfxItemSet*
-+ScVbaCellRangeAccess::GetDataSet( ScCellRangeObj* pRangeObj )
-+{
-+ SfxItemSet* pDataSet = pRangeObj ? pRangeObj->GetCurrentDataSet( true ) : NULL ;
-+ return pDataSet;
-+
-+}
-+} //excel
-+} //vba
-+} //ooo
---- sc/source/ui/vba/excelvbahelper.hxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ sc/source/ui/vba/excelvbahelper.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,60 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile: vbahelper.hxx,v $
-+ * $Revision: 1.5.32.1 $
-+ *
-+ * 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.
-+ *
-+ ************************************************************************/
-+#ifndef SC_EXCEL_VBA_HELPER_HXX
-+#define SC_EXCEL_VBA_HELPER_HXX
-+
-+#include<vbahelper/vbahelper.hxx>
-+#include <docsh.hxx>
-+
-+class ScCellRangeObj;
-+
-+namespace ooo
-+{
-+ namespace vba
-+ {
-+ namespace excel
-+ {
-+ void implnCopy();
-+ void implnPaste();
-+ void implnCut();
-+ void implnPasteSpecial(sal_uInt16 nFlags,sal_uInt16 nFunction,sal_Bool bSkipEmpty, sal_Bool bTranspose);
-+ ScTabViewShell* getBestViewShell( css::uno::Reference< css::frame::XModel>& xModel ) ;
-+ ScDocShell* getDocShell( css::uno::Reference< css::frame::XModel>& xModel ) ;
-+ ScTabViewShell* getCurrentBestViewShell();
-+ SfxViewFrame* getCurrentViewFrame();
-+ class ScVbaCellRangeAccess
-+ {
-+ public:
-+ static SfxItemSet* GetDataSet( ScCellRangeObj* pRangeObj );
-+ };
-+};
-+};
-+};
-+#endif
---- sc/source/ui/vba/makefile.mk.old 2009-04-06 16:42:00.000000000 +0000
-+++ sc/source/ui/vba/makefile.mk 2009-04-06 16:42:01.000000000 +0000
-@@ -64,7 +64,7 @@ SLOFILES= \
- $(SLO)$/vbaworksheet.obj \
- $(SLO)$/vbaoutline.obj \
- $(SLO)$/vbafont.obj\
-- $(SLO)$/vbahelper.obj\
-+ $(SLO)$/excelvbahelper.obj\
- $(SLO)$/vbainterior.obj\
- $(SLO)$/vbawsfunction.obj\
- $(SLO)$/vbawindow.obj\
-@@ -81,20 +81,10 @@ SLOFILES= \
- $(SLO)$/vbapalette.obj \
- $(SLO)$/vbaborders.obj \
- $(SLO)$/vbacharacters.obj \
-- $(SLO)$/vbacombobox.obj \
- $(SLO)$/vbavalidation.obj \
-- $(SLO)$/vbacontrol.obj \
-- $(SLO)$/vbacontrols.obj \
- $(SLO)$/vbaoleobject.obj \
- $(SLO)$/vbaoleobjects.obj \
-- $(SLO)$/vbabutton.obj \
-- $(SLO)$/vbalabel.obj \
-- $(SLO)$/vbatextbox.obj \
- $(SLO)$/vbatextboxshape.obj \
-- $(SLO)$/vbaradiobutton.obj \
-- $(SLO)$/vbalistbox.obj \
-- $(SLO)$/vbalistcontrolhelper.obj \
-- $(SLO)$/vbapropvalue.obj \
- $(SLO)$/vbapane.obj \
- $(SLO)$/vbashape.obj \
- $(SLO)$/vbacolorformat.obj \
-@@ -116,24 +106,10 @@ SLOFILES= \
- $(SLO)$/vbastyle.obj \
- $(SLO)$/vbastyles.obj \
- $(SLO)$/vbaassistant.obj \
-- $(SLO)$/vbauserform.obj \
-- $(SLO)$/vbacheckbox.obj \
-- $(SLO)$/vbatogglebutton.obj \
-- $(SLO)$/vbaframe.obj \
-- $(SLO)$/vbascrollbar.obj \
-- $(SLO)$/vbaprogressbar.obj \
-- $(SLO)$/vbamultipage.obj \
-- $(SLO)$/vbapages.obj \
-- $(SLO)$/vbacommandbarcontrol.obj \
-- $(SLO)$/vbacommandbarcontrols.obj \
-- $(SLO)$/vbacommandbar.obj \
-- $(SLO)$/vbacommandbars.obj \
- $(SLO)$/vbahyperlink.obj \
- $(SLO)$/vbapagesetup.obj \
- $(SLO)$/vbapagebreak.obj \
- $(SLO)$/vbapagebreaks.obj \
-- $(SLO)$/vbaspinbutton.obj \
-- $(SLO)$/vbaimage.obj \
- $(SLO)$/service.obj \
- $(SLO)$/vbaeventshelper.obj
-
---- sc/source/ui/vba/service.cxx.old 2009-04-06 16:42:00.000000000 +0000
-+++ sc/source/ui/vba/service.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -61,11 +61,11 @@ namespace globals
- {
- extern sdecl::ServiceDecl const serviceDecl;
- }
--namespace userform
-+namespace hyperlink
- {
- extern sdecl::ServiceDecl const serviceDecl;
- }
--namespace hyperlink
-+namespace application
- {
- extern sdecl::ServiceDecl const serviceDecl;
- }
-@@ -87,10 +87,10 @@ extern "C"
- lang::XMultiServiceFactory * pServiceManager, registry::XRegistryKey * pRegistryKey )
- {
- OSL_TRACE("In component_writeInfo");
--
-+#if 0
- // Component registration
- if ( component_writeInfoHelper( pServiceManager, pRegistryKey,
-- range::serviceDecl, workbook::serviceDecl, worksheet::serviceDecl, globals::serviceDecl, userform::serviceDecl, window::serviceDecl, hyperlink::serviceDecl ) && component_writeInfoHelper( pServiceManager, pRegistryKey, vbaeventshelper::serviceDecl ) )
-+ range::serviceDecl, workbook::serviceDecl, worksheet::serviceDecl, globals::serviceDecl, window::serviceDecl, hyperlink::serviceDecl, application::serviceDecl ) && component_writeInfoHelper( pServiceManager, pRegistryKey, vbaeventshelper::serviceDecl ) )
- {
- // Singleton registration
- try
-@@ -110,6 +110,12 @@ extern "C"
- }
- }
- return sal_False;
-+#else
-+ // Component registration
-+ return component_writeInfoHelper( pServiceManager, pRegistryKey,
-+ range::serviceDecl, workbook::serviceDecl, worksheet::serviceDecl, globals::serviceDecl, window::serviceDecl, hyperlink::serviceDecl, application::serviceDecl ) && component_writeInfoHelper( pServiceManager, pRegistryKey, vbaeventshelper::serviceDecl );
-+#endif
-+
- }
-
- SAL_DLLPUBLIC_EXPORT void * SAL_CALL component_getFactory(
-@@ -118,7 +124,7 @@ extern "C"
- {
- OSL_TRACE("In component_getFactory for %s", pImplName );
- void* pRet = component_getFactoryHelper(
-- pImplName, pServiceManager, pRegistryKey, range::serviceDecl, workbook::serviceDecl, worksheet::serviceDecl, globals::serviceDecl, userform::serviceDecl, window::serviceDecl, hyperlink::serviceDecl );
-+ pImplName, pServiceManager, pRegistryKey, range::serviceDecl, workbook::serviceDecl, worksheet::serviceDecl, globals::serviceDecl, window::serviceDecl, hyperlink::serviceDecl, application::serviceDecl );
- if( !pRet )
- pRet = component_getFactoryHelper( pImplName, pServiceManager, pRegistryKey, vbaeventshelper::serviceDecl );
- OSL_TRACE("Ret is 0x%x", pRet);
---- sc/source/ui/vba/vbaapplication.cxx.old 2009-04-06 16:41:59.000000000 +0000
-+++ sc/source/ui/vba/vbaapplication.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -60,7 +60,6 @@
- #include "vbashape.hxx"
- #include "vbatextboxshape.hxx"
- #include "vbaassistant.hxx"
--#include "vbacommandbars.hxx"
- #include "sc.hrc"
-
- #include <osl/file.hxx>
-@@ -87,6 +86,7 @@
- #include "miscuno.hxx"
- #include "unonames.hxx"
- #include "docsh.hxx"
-+#include <vbahelper/helperdecl.hxx>
-
- using namespace ::ooo::vba;
- using namespace ::com::sun::star;
-@@ -123,7 +123,7 @@ public:
- ActiveWorkbook( const uno::Reference< XHelperInterface >& xParent, const uno::Reference< uno::XComponentContext >& xContext) : ScVbaWorkbook( xParent, xContext ){}
- };
-
--ScVbaApplication::ScVbaApplication( uno::Reference<uno::XComponentContext >& xContext ): ScVbaApplication_BASE( uno::Reference< XHelperInterface >(), xContext ), m_xCalculation( excel::XlCalculation::xlCalculationAutomatic )
-+ScVbaApplication::ScVbaApplication( const uno::Reference<uno::XComponentContext >& xContext ): ScVbaApplication_BASE( xContext ), m_xCalculation( excel::XlCalculation::xlCalculationAutomatic )
- {
- }
-
-@@ -151,15 +151,6 @@ ScVbaApplication::getAssistant() throw (
- }
-
- uno::Any SAL_CALL
--ScVbaApplication::CommandBars( const uno::Any& aIndex ) throw (uno::RuntimeException)
--{
-- uno::Reference< XCommandBars > xCommandBars( new ScVbaCommandBars( this, mxContext, uno::Reference< container::XIndexAccess >() ) );
-- if( aIndex.hasValue() )
-- return uno::makeAny( xCommandBars->Item( aIndex, uno::Any() ) );
-- return uno::makeAny( xCommandBars );
--}
--
--uno::Any SAL_CALL
- ScVbaApplication::getSelection() throw (uno::RuntimeException)
- {
- OSL_TRACE("** ScVbaApplication::getSelection() ** ");
-@@ -227,7 +218,7 @@ ScVbaApplication::getActiveCell() throw
- {
- uno::Reference< sheet::XSpreadsheetView > xView( getCurrentDocument()->getCurrentController(), uno::UNO_QUERY_THROW );
- uno::Reference< table::XCellRange > xRange( xView->getActiveSheet(), ::uno::UNO_QUERY_THROW);
-- ScTabViewShell* pViewShell = getCurrentBestViewShell();
-+ ScTabViewShell* pViewShell = excel::getCurrentBestViewShell();
- if ( !pViewShell )
- throw uno::RuntimeException( rtl::OUString::createFromAscii("No ViewShell available"), uno::Reference< uno::XInterface >() );
- ScViewData* pTabView = pViewShell->GetViewData();
-@@ -240,65 +231,6 @@ ScVbaApplication::getActiveCell() throw
- return new ScVbaRange( this, mxContext, xRange->getCellRangeByPosition( nCursorX, nCursorY, nCursorX, nCursorY ) );
- }
-
--sal_Bool
--ScVbaApplication::getScreenUpdating() throw (uno::RuntimeException)
--{
-- uno::Reference< frame::XModel > xModel( getCurrentDocument(), uno::UNO_QUERY_THROW );
-- return !xModel->hasControllersLocked();
--}
--
--void
--ScVbaApplication::setScreenUpdating(sal_Bool bUpdate) throw (uno::RuntimeException)
--{
-- uno::Reference< frame::XModel > xModel( getCurrentDocument(), uno::UNO_QUERY_THROW );
-- if (bUpdate)
-- xModel->unlockControllers();
-- else
-- xModel->lockControllers();
--}
--
--sal_Bool
--ScVbaApplication::getDisplayStatusBar() throw (uno::RuntimeException)
--{
-- uno::Reference< frame::XModel > xModel( getCurrentDocument(), uno::UNO_QUERY_THROW );
-- uno::Reference< frame::XFrame > xFrame( xModel->getCurrentController()->getFrame(), uno::UNO_QUERY_THROW );
-- uno::Reference< beans::XPropertySet > xProps( xFrame, uno::UNO_QUERY_THROW );
--
-- if( xProps.is() ){
-- uno::Reference< frame::XLayoutManager > xLayoutManager( xProps->getPropertyValue( rtl::OUString(RTL_CONSTASCII_USTRINGPARAM("LayoutManager")) ), uno::UNO_QUERY_THROW );
-- rtl::OUString url(RTL_CONSTASCII_USTRINGPARAM( "private:resource/statusbar/statusbar" ));
-- if( xLayoutManager.is() && xLayoutManager->isElementVisible( url ) ){
-- return sal_True;
-- }
-- }
-- return sal_False;
--}
--
--void
--ScVbaApplication::setDisplayStatusBar(sal_Bool bDisplayStatusBar) throw (uno::RuntimeException)
--{
-- uno::Reference< frame::XModel > xModel( getCurrentDocument(), uno::UNO_QUERY_THROW );
-- uno::Reference< frame::XFrame > xFrame( xModel->getCurrentController()->getFrame(), uno::UNO_QUERY_THROW );
-- uno::Reference< beans::XPropertySet > xProps( xFrame, uno::UNO_QUERY_THROW );
--
-- if( xProps.is() ){
-- uno::Reference< frame::XLayoutManager > xLayoutManager( xProps->getPropertyValue( rtl::OUString(RTL_CONSTASCII_USTRINGPARAM("LayoutManager")) ), uno::UNO_QUERY_THROW );
-- rtl::OUString url(RTL_CONSTASCII_USTRINGPARAM( "private:resource/statusbar/statusbar" ));
-- if( xLayoutManager.is() ){
-- if( bDisplayStatusBar && !xLayoutManager->isElementVisible( url ) ){
-- if( !xLayoutManager->showElement( url ) )
-- xLayoutManager->createElement( url );
-- return;
-- }
-- else if( !bDisplayStatusBar && xLayoutManager->isElementVisible( url ) ){
-- xLayoutManager->hideElement( url );
-- return;
-- }
-- }
-- }
-- return;
--}
--
- uno::Any SAL_CALL
- ScVbaApplication::Workbooks( const uno::Any& aIndex ) throw (uno::RuntimeException)
- {
-@@ -347,7 +279,7 @@ ScVbaApplication::Evaluate( const ::rtl:
- uno::Any
- ScVbaApplication::Dialogs( const uno::Any &aIndex ) throw (uno::RuntimeException)
- {
-- uno::Reference< excel::XDialogs > xDialogs( new ScVbaDialogs( uno::Reference< XHelperInterface >( ScVbaGlobals::getGlobalsImpl( mxContext )->getApplication(), uno::UNO_QUERY_THROW ), mxContext ) );
-+ uno::Reference< excel::XDialogs > xDialogs( new ScVbaDialogs( uno::Reference< XHelperInterface >( this ), mxContext ) );
- if( !aIndex.hasValue() )
- return uno::Any( xDialogs );
- return uno::Any( xDialogs->Item( aIndex ) );
-@@ -460,7 +392,7 @@ ScVbaApplication::setCalculation( ::sal_
- uno::Any SAL_CALL
- ScVbaApplication::Windows( const uno::Any& aIndex ) throw (uno::RuntimeException)
- {
-- uno::Reference< XCollection > xWindows = ScVbaWindows::Windows( mxContext );
-+ uno::Reference< excel::XWindows > xWindows( new ScVbaWindows( this, mxContext ) );
- if ( aIndex.getValueTypeClass() == uno::TypeClass_VOID )
- return uno::Any( xWindows );
- return uno::Any( xWindows->Item( aIndex, uno::Any() ) );
-@@ -571,11 +503,11 @@ ScVbaApplication::GoTo( const uno::Any&
- xModel->getCurrentController(), uno::UNO_QUERY_THROW );
- uno::Reference< sheet::XSpreadsheet > xDoc = xSpreadsheet->getActiveSheet();
-
-- ScTabViewShell* pShell = getCurrentBestViewShell();
-+ ScTabViewShell* pShell = excel::getCurrentBestViewShell();
- ScGridWindow* gridWindow = (ScGridWindow*)pShell->GetWindow();
- try
- {
-- uno::Reference< excel::XRange > xVbaSheetRange = ScVbaRange::getRangeObjectForName( mxContext, sRangeName, getDocShell( xModel ), formula::FormulaGrammar::CONV_XL_R1C1 );
-+ uno::Reference< excel::XRange > xVbaSheetRange = ScVbaRange::getRangeObjectForName( mxContext, sRangeName, excel::getDocShell( xModel ), formula::FormulaGrammar::CONV_XL_R1C1 );
- ;
- if( bScroll )
- {
-@@ -613,7 +545,7 @@ ScVbaApplication::GoTo( const uno::Any&
- if( Reference >>= xRange )
- {
- uno::Reference< excel::XRange > xVbaRange( Reference, uno::UNO_QUERY );
-- ScTabViewShell* pShell = getCurrentBestViewShell();
-+ ScTabViewShell* pShell = excel::getCurrentBestViewShell();
- ScGridWindow* gridWindow = (ScGridWindow*)pShell->GetWindow();
- if ( xVbaRange.is() )
- {
-@@ -643,38 +575,10 @@ ScVbaApplication::GoTo( const uno::Any&
- uno::Reference< uno::XInterface >() );
- }
-
--namespace
--{
-- static uno::Reference< frame::XController > lcl_getCurrentController()
-- {
-- const uno::Reference< frame::XModel > xWorkingDoc( SfxObjectShell::GetCurrentComponent(), uno::UNO_QUERY );
-- uno::Reference< frame::XController > xController;
-- if ( xWorkingDoc.is() )
-- xController.set( xWorkingDoc->getCurrentController(), uno::UNO_SET_THROW );
-- else
-- xController.set( SfxObjectShell::GetCurrentComponent(), uno::UNO_QUERY_THROW );
-- return xController;
-- }
--}
--
- sal_Int32 SAL_CALL
- ScVbaApplication::getCursor() throw (uno::RuntimeException)
- {
-- sal_Int32 nPointerStyle( POINTER_ARROW );
-- try
-- {
-- const uno::Reference< frame::XController > xController( lcl_getCurrentController(), uno::UNO_SET_THROW );
-- const uno::Reference< frame::XFrame > xFrame ( xController->getFrame(), uno::UNO_SET_THROW );
-- const uno::Reference< awt::XWindow > xWindow ( xFrame->getContainerWindow(), uno::UNO_SET_THROW );
-- // why the heck isn't there an XWindowPeer::getPointer, but a setPointer only?
-- const Window* pWindow = VCLUnoHelper::GetWindow( xWindow );
-- if ( pWindow )
-- nPointerStyle = pWindow->GetSystemWindow()->GetPointer().GetStyle();
-- }
-- catch( const uno::Exception& )
-- {
-- DBG_UNHANDLED_EXCEPTION();
-- }
-+ sal_Int32 nPointerStyle = getPointerStyle();
-
- switch( nPointerStyle )
- {
-@@ -696,82 +600,34 @@ ScVbaApplication::setCursor( sal_Int32 _
- {
- try
- {
-- ::std::vector< uno::Reference< frame::XController > > aControllers;
--
-- const uno::Reference< frame::XModel2 > xModel2( SfxObjectShell::GetCurrentComponent(), uno::UNO_QUERY );
-- if ( xModel2.is() )
-- {
-- const uno::Reference< container::XEnumeration > xEnumControllers( xModel2->getControllers(), uno::UNO_SET_THROW );
-- while ( xEnumControllers->hasMoreElements() )
-- {
-- const uno::Reference< frame::XController > xController( xEnumControllers->nextElement(), uno::UNO_QUERY_THROW );
-- aControllers.push_back( xController );
-- }
-- }
-- else
-+ switch( _cursor )
- {
-- const uno::Reference< frame::XModel > xModel( SfxObjectShell::GetCurrentComponent(), uno::UNO_QUERY );
-- if ( xModel.is() )
-+ case excel::XlMousePointer::xlNorthwestArrow:
- {
-- const uno::Reference< frame::XController > xController( xModel->getCurrentController(), uno::UNO_SET_THROW );
-- aControllers.push_back( xController );
-+ const Pointer& rPointer( POINTER_ARROW );
-+ setCursorHelper( rPointer, sal_False );
-+ break;
- }
-- else
-+ case excel::XlMousePointer::xlWait:
-+ case excel::XlMousePointer::xlIBeam:
- {
-- const uno::Reference< frame::XController > xController( SfxObjectShell::GetCurrentComponent(), uno::UNO_QUERY_THROW );
-- aControllers.push_back( xController );
-+ const Pointer& rPointer( static_cast< PointerStyle >( _cursor ) );
-+ //It will set the edit window, toobar and statusbar's mouse pointer.
-+ setCursorHelper( rPointer, sal_True );
-+ break;
- }
-- }
--
-- for ( ::std::vector< uno::Reference< frame::XController > >::const_iterator controller = aControllers.begin();
-- controller != aControllers.end();
-- ++controller
-- )
-- {
-- const uno::Reference< frame::XFrame > xFrame ( (*controller)->getFrame(), uno::UNO_SET_THROW );
-- const uno::Reference< awt::XWindow > xWindow ( xFrame->getContainerWindow(), uno::UNO_SET_THROW );
--
-- Window* pWindow = VCLUnoHelper::GetWindow( xWindow );
-- OSL_ENSURE( pWindow, "ScVbaApplication::setCursor: no window!" );
-- if ( !pWindow )
-- continue;
--
-- switch( _cursor )
-+ case excel::XlMousePointer::xlDefault:
- {
-- case excel::XlMousePointer::xlNorthwestArrow:
-- {
-- const Pointer& rPointer( POINTER_ARROW );
-- pWindow->GetSystemWindow()->SetPointer( rPointer );
-- pWindow->GetSystemWindow()->EnableChildPointerOverwrite( sal_False );
-- break;
-- }
-- case excel::XlMousePointer::xlWait:
-- case excel::XlMousePointer::xlIBeam:
-- {
-- const Pointer& rPointer( static_cast< PointerStyle >( _cursor ) );
-- //It will set the edit window, toobar and statusbar's mouse pointer.
-- pWindow->GetSystemWindow()->SetPointer( rPointer );
-- pWindow->GetSystemWindow()->EnableChildPointerOverwrite( sal_True );
-- //It only set the edit window's mouse pointer
-- //pWindow->.SetPointer( rPointer );
-- //pWindow->.EnableChildPointerOverwrite( sal_True );
-- //printf("\nset Cursor...%d\n", pWindow->.GetType());
-- break;
-- }
-- case excel::XlMousePointer::xlDefault:
-- {
-- const Pointer& rPointer( POINTER_NULL );
-- pWindow->GetSystemWindow()->SetPointer( rPointer );
-- pWindow->GetSystemWindow()->EnableChildPointerOverwrite( sal_False );
-- break;
-- }
-- default:
-- throw uno::RuntimeException( rtl::OUString(
-- RTL_CONSTASCII_USTRINGPARAM("Unknown value for Cursor pointer")), uno::Reference< uno::XInterface >() );
-- // TODO: isn't this a flaw in the API? It should be allowed to throw an
-- // IllegalArgumentException, or so
-+ const Pointer& rPointer( POINTER_NULL );
-+ setCursorHelper( rPointer, sal_False );
-+ break;
- }
-- }
-+ default:
-+ throw uno::RuntimeException( rtl::OUString(
-+ RTL_CONSTASCII_USTRINGPARAM("Unknown value for Cursor pointer")), uno::Reference< uno::XInterface >() );
-+ // TODO: isn't this a flaw in the API? It should be allowed to throw an
-+ // IllegalArgumentException, or so
-+ }
- }
- catch( const uno::Exception& )
- {
-@@ -1145,7 +1001,7 @@ ScVbaApplication::Intersect( const uno::
- }
-
- uno::Reference< frame::XModel > xModel( getCurrentDocument(), uno::UNO_QUERY_THROW );
-- ScDocShell* pDocShell = getDocShell( xModel );
-+ ScDocShell* pDocShell = excel::getDocShell( xModel );
- if ( aCellRanges.Count() == 1 )
- {
- xRefRange = new ScVbaRange( uno::Reference< XHelperInterface >(), mxContext, new ScCellRangeObj( pDocShell, *aCellRanges.First() ) );
-@@ -1234,7 +1090,7 @@ ScVbaApplication::Union( const uno::Refe
- aCellRanges.Append( *it );
-
- uno::Reference< frame::XModel > xModel( getCurrentDocument(), uno::UNO_QUERY_THROW );
-- ScDocShell* pDocShell = getDocShell( xModel );
-+ ScDocShell* pDocShell = excel::getDocShell( xModel );
- if ( aCellRanges.Count() == 1 )
- {
- // normal range
-@@ -1269,16 +1125,11 @@ ScVbaApplication::Volatile( const uno::A
- */
- }
-
--void SAL_CALL
--ScVbaApplication::DoEvents() throw ( uno::RuntimeException )
--{
--}
--
- ::sal_Bool SAL_CALL
- ScVbaApplication::getDisplayFormulaBar() throw ( css::uno::RuntimeException )
- {
- sal_Bool bRes = sal_False;
-- ScTabViewShell* pViewShell = getCurrentBestViewShell();
-+ ScTabViewShell* pViewShell = excel::getCurrentBestViewShell();
- if ( pViewShell )
- {
- SfxBoolItem sfxFormBar( FID_TOGGLEINPUTLINE);
-@@ -1296,7 +1147,7 @@ ScVbaApplication::getDisplayFormulaBar()
- void SAL_CALL
- ScVbaApplication::setDisplayFormulaBar( ::sal_Bool _displayformulabar ) throw ( css::uno::RuntimeException )
- {
-- ScTabViewShell* pViewShell = getCurrentBestViewShell();
-+ ScTabViewShell* pViewShell = excel::getCurrentBestViewShell();
- if ( pViewShell && ( _displayformulabar != getDisplayFormulaBar() ) )
- {
- SfxBoolItem sfxFormBar( FID_TOGGLEINPUTLINE, _displayformulabar);
-@@ -1343,3 +1194,13 @@ ScVbaApplication::getServiceNames()
- }
- return aServiceNames;
- }
-+
-+namespace application
-+{
-+namespace sdecl = comphelper::service_decl;
-+sdecl::vba_service_class_<ScVbaApplication, sdecl::with_args<false> > serviceImpl;
-+extern sdecl::ServiceDecl const serviceDecl(
-+ serviceImpl,
-+ "ScVbaApplication",
-+ "ooo.vba.excel.Application" );
-+}
---- sc/source/ui/vba/vbaapplication.hxx.old 2009-04-06 16:41:59.000000000 +0000
-+++ sc/source/ui/vba/vbaapplication.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -35,9 +35,12 @@
- #include <ooo/vba/excel/XApplication.hpp>
- #include <com/sun/star/uno/XComponentContext.hpp>
-
--#include "vbahelperinterface.hxx"
-+#include <vbahelper/vbahelperinterface.hxx>
-+#include <vbahelper/vbaapplicationbase.hxx>
-+#include <cppuhelper/implbase1.hxx>
-
--typedef InheritedHelperInterfaceImpl1< ov::excel::XApplication > ScVbaApplication_BASE;
-+//typedef InheritedHelperInterfaceImpl1< ov::excel::XApplication > ScVbaApplication_BASE;
-+typedef cppu::ImplInheritanceHelper1< VbaApplicationBase, ov::excel::XApplication > ScVbaApplication_BASE;
-
- class ScVbaApplication : public ScVbaApplication_BASE
- {
-@@ -45,12 +48,9 @@ private:
- sal_Int32 m_xCalculation;
- rtl::OUString getOfficePath( const rtl::OUString& sPath ) throw ( css::uno::RuntimeException );
- public:
-- ScVbaApplication( css::uno::Reference< css::uno::XComponentContext >& m_xContext );
-+ ScVbaApplication( const css::uno::Reference< css::uno::XComponentContext >& m_xContext );
- virtual ~ScVbaApplication();
-
-- // XHelperInterface ( parent is itself )
-- virtual css::uno::Reference< ov::XHelperInterface > SAL_CALL getParent( ) throw (css::script::BasicErrorException, css::uno::RuntimeException) { return this; }
--
- // XApplication
- virtual ::rtl::OUString SAL_CALL PathSeparator( ) throw (css::script::BasicErrorException, css::uno::RuntimeException);
- virtual void SAL_CALL setDefaultFilePath( const ::rtl::OUString& DefaultFilePath ) throw (css::script::BasicErrorException, css::uno::RuntimeException);
-@@ -68,15 +68,10 @@ public:
- virtual css::uno::Reference< ov::excel::XRange > SAL_CALL getActiveCell() throw ( css::uno::RuntimeException);
- virtual css::uno::Reference< ov::excel::XWindow > SAL_CALL getActiveWindow() throw (css::uno::RuntimeException);
- virtual css::uno::Reference< ov::excel::XWorksheet > SAL_CALL getActiveSheet() throw (css::uno::RuntimeException);
-- virtual sal_Bool SAL_CALL getScreenUpdating() throw (css::uno::RuntimeException);
-- virtual void SAL_CALL setScreenUpdating(sal_Bool bUpdate) throw (css::uno::RuntimeException);
-- virtual sal_Bool SAL_CALL getDisplayStatusBar() throw (css::uno::RuntimeException);
-- virtual void SAL_CALL setDisplayStatusBar(sal_Bool bDisplayStatusBar) throw (css::uno::RuntimeException);
- virtual ::sal_Bool SAL_CALL getDisplayFormulaBar() throw ( css::uno::RuntimeException );
- virtual void SAL_CALL setDisplayFormulaBar( ::sal_Bool _displayformulabar ) throw ( css::uno::RuntimeException );
-
- virtual css::uno::Reference< ov::XAssistant > SAL_CALL getAssistant() throw (css::uno::RuntimeException);
-- virtual css::uno::Any SAL_CALL CommandBars( const css::uno::Any& aIndex ) throw (css::uno::RuntimeException);
- virtual css::uno::Reference< ov::excel::XWorkbook > SAL_CALL getThisWorkbook() throw (css::uno::RuntimeException);
- virtual css::uno::Any SAL_CALL Workbooks( const css::uno::Any& aIndex ) throw (css::uno::RuntimeException);
- virtual css::uno::Any SAL_CALL Worksheets( const css::uno::Any& aIndex ) throw (css::uno::RuntimeException);
-@@ -102,7 +97,6 @@ public:
- virtual css::uno::Reference< ov::excel::XRange > SAL_CALL Intersect( const css::uno::Reference< ov::excel::XRange >& Arg1, const css::uno::Reference< ov::excel::XRange >& Arg2, const css::uno::Any& Arg3, const css::uno::Any& Arg4, const css::uno::Any& Arg5, const css::uno::Any& Arg6, const css::uno::Any& Arg7, const css::uno::Any& Arg8, const css::uno::Any& Arg9, const css::uno::Any& Arg10, const css::uno::Any& Arg11, const css::uno::Any& Arg12, const css::uno::Any& Arg13, const css::uno::Any& Arg14, const css::uno::Any& Arg15, const css::uno::Any& Arg16, const css::uno::Any& Arg17, const css::uno::Any& Arg18, const css::uno::Any& Arg19, const css::uno::Any& Arg20, const css::uno::Any& Arg21, const css::uno::Any& Arg22, const css::uno::Any& Arg23, const css::uno::Any& Arg24, const css::uno::Any& Arg25, const css::uno::Any& Arg26, const css::uno::Any& Arg27, const css::uno::Any& Arg28, const css::uno::Any& Arg29, const css::uno::Any& Arg30 ) throw (css::script::BasicErrorException, css::uno::RuntimeException);
- virtual css::uno::Reference< ov::excel::XRange > SAL_CALL Union( const css::uno::Reference< ov::excel::XRange >& Arg1, const css::uno::Reference< ov::excel::XRange >& Arg2, const css::uno::Any& Arg3, const css::uno::Any& Arg4, const css::uno::Any& Arg5, const css::uno::Any& Arg6, const css::uno::Any& Arg7, const css::uno::Any& Arg8, const css::uno::Any& Arg9, const css::uno::Any& Arg10, const css::uno::Any& Arg11, const css::uno::Any& Arg12, const css::uno::Any& Arg13, const css::uno::Any& Arg14, const css::uno::Any& Arg15, const css::uno::Any& Arg16, const css::uno::Any& Arg17, const css::uno::Any& Arg18, const css::uno::Any& Arg19, const css::uno::Any& Arg20, const css::uno::Any& Arg21, const css::uno::Any& Arg22, const css::uno::Any& Arg23, const css::uno::Any& Arg24, const css::uno::Any& Arg25, const css::uno::Any& Arg26, const css::uno::Any& Arg27, const css::uno::Any& Arg28, const css::uno::Any& Arg29, const css::uno::Any& Arg30 ) throw (css::script::BasicErrorException, css::uno::RuntimeException);
- virtual void SAL_CALL Volatile( const css::uno::Any& Volatile ) throw (css::uno::RuntimeException );
-- virtual void SAL_CALL DoEvents() throw (css::uno::RuntimeException);
- virtual css::uno::Any SAL_CALL Caller( const css::uno::Any& aIndex ) throw (css::uno::RuntimeException);
- // XHelperInterface
- virtual rtl::OUString& getServiceImplName();
---- sc/source/ui/vba/vbaassistant.hxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbaassistant.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -40,8 +40,8 @@
-
- #include <sfx2/sfxhelp.hxx>
-
--#include "vbahelper.hxx"
--#include "vbahelperinterface.hxx"
-+#include "excelvbahelper.hxx"
-+#include <vbahelper/vbahelperinterface.hxx>
-
- typedef ::cppu::WeakImplHelper1< ov::XAssistant > Assistant;
- typedef InheritedHelperInterfaceImpl< Assistant > ScVbaAssistantImpl_BASE;
---- sc/source/ui/vba/vbaaxes.hxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbaaxes.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -32,7 +32,7 @@
- #include <ooo/vba/excel/XAxes.hpp>
- #include <ooo/vba/excel/XAxis.hpp>
- #include <ooo/vba/excel/XChart.hpp>
--#include "vbacollectionimpl.hxx"
-+#include <vbahelper/vbacollectionimpl.hxx>
-
- typedef CollTestImplHelper< ov::excel::XAxes > ScVbaAxes_BASE;
- class ScVbaAxes : public ScVbaAxes_BASE
---- sc/source/ui/vba/vbaaxis.hxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbaaxis.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -32,8 +32,8 @@
- #include <com/sun/star/beans/XPropertySet.hpp>
- #include <ooo/vba/excel/XAxis.hpp>
- #include <ooo/vba/excel/XChart.hpp>
--#include "vbahelperinterface.hxx"
--
-+#include <vbahelper/vbahelperinterface.hxx>
-+#include <memory>
- typedef InheritedHelperInterfaceImpl1< ov::excel::XAxis > ScVbaAxis_BASE;
- class ScVbaChart;
- class ScVbaAxis : public ScVbaAxis_BASE
---- sc/source/ui/vba/vbaborders.hxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbaborders.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -38,7 +38,7 @@
- #include <com/sun/star/beans/XPropertySet.hpp>
-
-
--#include "vbacollectionimpl.hxx"
-+#include <vbahelper/vbacollectionimpl.hxx>
-
- typedef CollTestImplHelper< ov::excel::XBorders > ScVbaBorders_BASE;
- class ScVbaPalette;
---- sc/source/ui/vba/vbabutton.cxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbabutton.cxx 1970-01-01 00:00:00.000000000 +0000
-@@ -1,74 +0,0 @@
--/*************************************************************************
-- *
-- * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-- *
-- * Copyright 2008 by Sun Microsystems, Inc.
-- *
-- * OpenOffice.org - a multi-platform office productivity suite
-- *
-- * $RCSfile: vbabutton.cxx,v $
-- * $Revision: 1.3 $
-- *
-- * 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 "vbabutton.hxx"
--#include <vector>
--
--using namespace com::sun::star;
--using namespace ooo::vba;
--
--
--const static rtl::OUString LABEL( RTL_CONSTASCII_USTRINGPARAM("Label") );
--ScVbaButton::ScVbaButton( const uno::Reference< XHelperInterface >& xParent, const uno::Reference< uno::XComponentContext >& xContext, const uno::Reference< uno::XInterface >& xControl, const uno::Reference< frame::XModel >& xModel, AbstractGeometryAttributes* pGeomHelper ) : ButtonImpl_BASE( xParent, xContext, xControl, xModel, pGeomHelper )
--{
--}
--
--// Attributes
--rtl::OUString SAL_CALL
--ScVbaButton::getCaption() throw (css::uno::RuntimeException)
--{
-- rtl::OUString Label;
-- m_xProps->getPropertyValue( LABEL ) >>= Label;
-- return Label;
--}
--
--void SAL_CALL
--ScVbaButton::setCaption( const rtl::OUString& _caption ) throw (::com::sun::star::uno::RuntimeException)
--{
-- m_xProps->setPropertyValue( LABEL, uno::makeAny( _caption ) );
--}
--
--rtl::OUString&
--ScVbaButton::getServiceImplName()
--{
-- static rtl::OUString sImplName( RTL_CONSTASCII_USTRINGPARAM("ScVbaButton") );
-- return sImplName;
--}
--
--uno::Sequence< rtl::OUString >
--ScVbaButton::getServiceNames()
--{
-- static uno::Sequence< rtl::OUString > aServiceNames;
-- if ( aServiceNames.getLength() == 0 )
-- {
-- aServiceNames.realloc( 1 );
-- aServiceNames[ 0 ] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.msforms.Button" ) );
-- }
-- return aServiceNames;
--}
---- sc/source/ui/vba/vbabutton.hxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbabutton.hxx 1970-01-01 00:00:00.000000000 +0000
-@@ -1,51 +0,0 @@
--/*************************************************************************
-- *
-- * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-- *
-- * Copyright 2008 by Sun Microsystems, Inc.
-- *
-- * OpenOffice.org - a multi-platform office productivity suite
-- *
-- * $RCSfile: vbabutton.hxx,v $
-- * $Revision: 1.3 $
-- *
-- * 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.
-- *
-- ************************************************************************/
--#ifndef SC_VBA_BUTTON_HXX
--#define SC_VBA_BUTTON_HXX
--#include <cppuhelper/implbase1.hxx>
--#include <ooo/vba/msforms/XButton.hpp>
--
--#include "vbacontrol.hxx"
--#include "vbahelper.hxx"
--
--typedef cppu::ImplInheritanceHelper1< ScVbaControl, ov::msforms::XButton > ButtonImpl_BASE;
--
--class ScVbaButton : public ButtonImpl_BASE
--{
--public:
-- ScVbaButton( const css::uno::Reference< ov::XHelperInterface >& xParent, const css::uno::Reference< css::uno::XComponentContext >& xContext, const css::uno::Reference< css::uno::XInterface >& xControl, const css::uno::Reference< css::frame::XModel >& xModel, ov::AbstractGeometryAttributes* pGeomHelper );
-- // Attributes
-- virtual rtl::OUString SAL_CALL getCaption() throw (css::uno::RuntimeException);
-- virtual void SAL_CALL setCaption( const rtl::OUString& _caption ) throw (css::uno::RuntimeException);
-- //XHelperInterface
-- virtual rtl::OUString& getServiceImplName();
-- virtual css::uno::Sequence<rtl::OUString> getServiceNames();
--};
--#endif //SC_VBA_BUTTON_HXX
---- sc/source/ui/vba/vbacharacters.hxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbacharacters.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -36,7 +36,7 @@
- #include <com/sun/star/uno/XComponentContext.hpp>
- #include <com/sun/star/text/XSimpleText.hpp>
-
--#include "vbahelperinterface.hxx"
-+#include <vbahelper/vbahelperinterface.hxx>
- #include "vbapalette.hxx"
- typedef InheritedHelperInterfaceImpl1< ov::excel::XCharacters > ScVbaCharacters_BASE;
-
---- sc/source/ui/vba/vbachart.hxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbachart.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -41,7 +41,7 @@
- #include <ooo/vba/excel/XChart.hpp>
- #include <ooo/vba/excel/XDataLabels.hpp>
- #include <ooo/vba/excel/XSeries.hpp>
--#include "vbahelperinterface.hxx"
-+#include <vbahelper/vbahelperinterface.hxx>
-
- typedef InheritedHelperInterfaceImpl1<ov::excel::XChart > ChartImpl_BASE;
-
---- sc/source/ui/vba/vbachartobject.hxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbachartobject.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -36,7 +36,7 @@
- #include <com/sun/star/container/XNamed.hpp>
- #include <com/sun/star/document/XEmbeddedObjectSupplier.hpp>
- #include <ooo/vba/excel/XChartObject.hpp>
--#include "vbahelperinterface.hxx"
-+#include <vbahelper/vbahelperinterface.hxx>
- #include <memory>
-
- typedef InheritedHelperInterfaceImpl1<ov::excel::XChartObject > ChartObjectImpl_BASE;
---- sc/source/ui/vba/vbachartobjects.hxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbachartobjects.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -36,8 +36,8 @@
- #include <com/sun/star/table/XTableCharts.hpp>
- #include <com/sun/star/drawing/XDrawPageSupplier.hpp>
- #include <com/sun/star/container/XEnumerationAccess.hpp>
--#include"vbacollectionimpl.hxx"
--#include "vbahelper.hxx"
-+#include <vbahelper/vbacollectionimpl.hxx>
-+#include "excelvbahelper.hxx"
- #include <hash_map>
-
- typedef CollTestImplHelper< ov::excel::XChartObjects > ChartObjects_BASE;
---- sc/source/ui/vba/vbacharts.hxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbacharts.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -31,8 +31,8 @@
- #define SC_VBA_CHARTS_HXX
- #include <ooo/vba/excel/XCharts.hpp>
- #include <com/sun/star/sheet/XSpreadsheetDocument.hpp>
--#include"vbacollectionimpl.hxx"
--#include "vbahelper.hxx"
-+#include <vbahelper/vbacollectionimpl.hxx>
-+#include "excelvbahelper.hxx"
- #include <hash_map>
-
- typedef CollTestImplHelper< ov::excel::XCharts > Charts_BASE;
---- sc/source/ui/vba/vbacheckbox.cxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbacheckbox.cxx 1970-01-01 00:00:00.000000000 +0000
-@@ -1,110 +0,0 @@
--/*************************************************************************
-- *
-- * OpenOffice.org - a multi-platform office productivity suite
-- *
-- * $RCSfile$
-- *
-- * $Revision$
-- *
-- * last change: $Author$ $Date$
-- *
-- * The Contents of this file are made available subject to
-- * the terms of GNU Lesser General Public License Version 2.1.
-- *
-- *
-- * GNU Lesser General Public License Version 2.1
-- * =============================================
-- * Copyright 2005 by Sun Microsystems, Inc.
-- * 901 San Antonio Road, Palo Alto, CA 94303, USA
-- *
-- * This library is free software; you can redistribute it and/or
-- * modify it under the terms of the GNU Lesser General Public
-- * License version 2.1, as published by the Free Software Foundation.
-- *
-- * This library 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 for more details.
-- *
-- * You should have received a copy of the GNU Lesser General Public
-- * License along with this library; if not, write to the Free Software
-- * Foundation, Inc., 59 Temple Place, Suite 330, Boston,
-- * MA 02111-1307 USA
-- *
-- ************************************************************************/
--#include "vbacheckbox.hxx"
--#include <vector>
--
--using namespace com::sun::star;
--using namespace ooo::vba;
--
--
--const static rtl::OUString LABEL( RTL_CONSTASCII_USTRINGPARAM("Label") );
--const static rtl::OUString STATE( RTL_CONSTASCII_USTRINGPARAM("State") );
--ScVbaCheckbox::ScVbaCheckbox( const uno::Reference< ov::XHelperInterface >& xParent, const uno::Reference< uno::XComponentContext >& xContext, const uno::Reference< uno::XInterface >& xControl, const uno::Reference< frame::XModel >& xModel, ov::AbstractGeometryAttributes* pGeomHelper ) : CheckBoxImpl_BASE( xParent, xContext, xControl, xModel, pGeomHelper )
--{
--}
--
--// Attributes
--rtl::OUString SAL_CALL
--ScVbaCheckbox::getCaption() throw (css::uno::RuntimeException)
--{
-- rtl::OUString Label;
-- m_xProps->getPropertyValue( LABEL ) >>= Label;
-- return Label;
--}
--
--void SAL_CALL
--ScVbaCheckbox::setCaption( const rtl::OUString& _caption ) throw (::com::sun::star::uno::RuntimeException)
--{
-- m_xProps->setPropertyValue( LABEL, uno::makeAny( _caption ) );
--}
--
--uno::Any SAL_CALL
--ScVbaCheckbox::getValue() throw (css::uno::RuntimeException)
--{
-- sal_Int16 nValue = -1;
-- m_xProps->getPropertyValue( STATE ) >>= nValue;
-- if( nValue != 0 )
-- nValue = -1;
--// return uno::makeAny( nValue );
--// I must be missing something MSO says value should be -1 if selected, 0 if not
--// selected
-- return uno::makeAny( ( nValue == -1 ) ? sal_True : sal_False );
--}
--
--void SAL_CALL
--ScVbaCheckbox::setValue( const uno::Any& _value ) throw (css::uno::RuntimeException)
--{
-- sal_Int16 nValue = 0;
-- sal_Bool bValue = false;
-- if( _value >>= nValue )
-- {
-- if( nValue == -1)
-- nValue = 1;
-- }
-- else if ( _value >>= bValue )
-- {
-- if ( bValue )
-- nValue = 1;
-- }
-- m_xProps->setPropertyValue( STATE, uno::makeAny( nValue ) );
--}
--rtl::OUString&
--ScVbaCheckbox::getServiceImplName()
--{
-- static rtl::OUString sImplName( RTL_CONSTASCII_USTRINGPARAM("ScVbaCheckbox") );
-- return sImplName;
--}
--
--uno::Sequence< rtl::OUString >
--ScVbaCheckbox::getServiceNames()
--{
-- static uno::Sequence< rtl::OUString > aServiceNames;
-- if ( aServiceNames.getLength() == 0 )
-- {
-- aServiceNames.realloc( 1 );
-- aServiceNames[ 0 ] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.msforms.CheckBox" ) );
-- }
-- return aServiceNames;
--}
---- sc/source/ui/vba/vbacheckbox.hxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbacheckbox.hxx 1970-01-01 00:00:00.000000000 +0000
-@@ -1,60 +0,0 @@
--/*************************************************************************
-- *
-- * OpenOffice.org - a multi-platform office productivity suite
-- *
-- * $RCSfile$
-- *
-- * $Revision$
-- *
-- * last change: $Author$ $Date$
-- *
-- * The Contents of this file are made available subject to
-- * the terms of GNU Lesser General Public License Version 2.1.
-- *
-- *
-- * GNU Lesser General Public License Version 2.1
-- * =============================================
-- * Copyright 2005 by Sun Microsystems, Inc.
-- * 901 San Antonio Road, Palo Alto, CA 94303, USA
-- *
-- * This library is free software; you can redistribute it and/or
-- * modify it under the terms of the GNU Lesser General Public
-- * License version 2.1, as published by the Free Software Foundation.
-- *
-- * This library 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 for more details.
-- *
-- * You should have received a copy of the GNU Lesser General Public
-- * License along with this library; if not, write to the Free Software
-- * Foundation, Inc., 59 Temple Place, Suite 330, Boston,
-- * MA 02111-1307 USA
-- *
-- ************************************************************************/
--#ifndef SC_VBA_CHECKBOX_HXX
--#define SC_VBA_CHECKBOX_HXX
--#include <cppuhelper/implbase2.hxx>
--#include <ooo/vba/msforms/XRadioButton.hpp>
--
--#include "vbacontrol.hxx"
--#include "vbahelper.hxx"
--
--typedef cppu::ImplInheritanceHelper2< ScVbaControl, ov::msforms::XRadioButton, css::script::XDefaultProperty > CheckBoxImpl_BASE;
--
--class ScVbaCheckbox : public CheckBoxImpl_BASE
--{
--public:
-- ScVbaCheckbox( const css::uno::Reference< ov::XHelperInterface >& xParent, const css::uno::Reference< css::uno::XComponentContext >& xContext, const css::uno::Reference< css::uno::XInterface >& xControl, const css::uno::Reference< css::frame::XModel >& xModel, ov::AbstractGeometryAttributes* pGeomHelper );
-- // Attributes
-- virtual rtl::OUString SAL_CALL getCaption() throw (css::uno::RuntimeException);
-- virtual void SAL_CALL setCaption( const rtl::OUString& _caption ) throw (css::uno::RuntimeException);
-- virtual css::uno::Any SAL_CALL getValue() throw (css::uno::RuntimeException);
-- virtual void SAL_CALL setValue( const css::uno::Any& _value ) throw (css::uno::RuntimeException);
-- // XDefaultProperty
-- rtl::OUString SAL_CALL getDefaultPropertyName( ) throw (css::uno::RuntimeException) { return ::rtl::OUString::createFromAscii("Value"); }
-- //XHelperInterface
-- virtual rtl::OUString& getServiceImplName();
-- virtual css::uno::Sequence<rtl::OUString> getServiceNames();
--};
--#endif //SC_VBA_CHECKBOX_HXX
---- sc/source/ui/vba/vbacollectionimpl.cxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbacollectionimpl.cxx 1970-01-01 00:00:00.000000000 +0000
-@@ -1,136 +0,0 @@
--/*************************************************************************
-- *
-- * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-- *
-- * Copyright 2008 by Sun Microsystems, Inc.
-- *
-- * OpenOffice.org - a multi-platform office productivity suite
-- *
-- * $RCSfile: vbacollectionimpl.cxx,v $
-- * $Revision: 1.3 $
-- *
-- * 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 <vbacollectionimpl.hxx>
--#include "vbaglobals.hxx"
--using namespace ::com::sun::star;
--using namespace ::ooo::vba;
--
--
--ScVbaCollectionBaseImpl::ScVbaCollectionBaseImpl( const uno::Reference< uno::XComponentContext >& xContext, const uno::Reference< container::XIndexAccess >& xIndexAccess ) throw (uno::RuntimeException) : m_xContext( xContext ), m_xIndexAccess( xIndexAccess )
--{
-- m_xNameAccess.set( xIndexAccess, uno::UNO_QUERY );
--}
--
--uno::Any
--ScVbaCollectionBaseImpl::getItemByStringIndex( const rtl::OUString& sIndex ) throw (::uno::RuntimeException)
--{
-- if ( !m_xNameAccess.is() )
-- throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ScVbaCollectionBaseImpl string index access not supported by this object") ), uno::Reference< uno::XInterface >() );
--
-- return createCollectionObject( m_xNameAccess->getByName( sIndex ) );
--}
--
--uno::Any
--ScVbaCollectionBaseImpl::getItemByIntIndex( const sal_Int32 nIndex ) throw (uno::RuntimeException)
--{
-- if ( !m_xIndexAccess.is() )
-- throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ScVbaCollectionBaseImpl numeric index access not supported by this object") ), uno::Reference< uno::XInterface >() );
-- if ( nIndex <= 0 )
-- {
-- throw lang::IndexOutOfBoundsException(
-- ::rtl::OUString( RTL_CONSTASCII_USTRINGPARAM(
-- "index is 0 or negative" ) ),
-- uno::Reference< uno::XInterface >() );
-- }
-- // need to adjust for vba index ( for which first element is 1 )
-- return createCollectionObject( m_xIndexAccess->getByIndex( nIndex - 1 ) );
--}
--
--::sal_Int32 SAL_CALL
--ScVbaCollectionBaseImpl::getCount() throw (uno::RuntimeException)
--{
-- return m_xIndexAccess->getCount();
--}
--
--uno::Any SAL_CALL
--ScVbaCollectionBaseImpl::getParent() throw (uno::RuntimeException)
--{
-- // #TODO #FIXME investigate whether this makes sense
-- uno::Reference< excel::XApplication > xApplication =
-- ScVbaGlobals::getGlobalsImpl( m_xContext )->getApplication();
-- uno::Reference< excel::XWorkbook > xWorkbook;
-- if ( xApplication.is() )
-- {
-- xWorkbook = xApplication->getActiveWorkbook();
-- }
-- return uno::Any( xWorkbook );
--}
--
--::sal_Int32 SAL_CALL ScVbaCollectionBaseImpl::getCreator() throw (uno::RuntimeException)
--{
-- // #TODO #FIXE some sort of implementation
-- //SC_VBA_STUB();
-- return 0;
--}
--uno::Reference< excel::XApplication > SAL_CALL ScVbaCollectionBaseImpl::getApplication() throw (uno::RuntimeException)
--{
-- // #TODO #FIXME investigate whether this makes sense
-- uno::Reference< excel::XApplication > xApplication =
-- ScVbaGlobals::getGlobalsImpl( m_xContext )->getApplication();
-- return xApplication;
--}
--
--uno::Any SAL_CALL ScVbaCollectionBaseImpl::Item( const uno::Any& aIndex ) throw (uno::RuntimeException)
--{
-- if ( aIndex.getValueTypeClass() != uno::TypeClass_STRING )
-- {
-- sal_Int32 nIndex = 0;
--
-- if ( ( aIndex >>= nIndex ) != sal_True )
-- {
-- rtl::OUString message;
-- message = rtl::OUString::createFromAscii(
-- "Couldn't convert index to Int32");
-- throw lang::IndexOutOfBoundsException( message,
-- uno::Reference< uno::XInterface >() );
-- }
-- return getItemByIntIndex( nIndex );
-- }
-- rtl::OUString aStringSheet;
--
-- aIndex >>= aStringSheet;
-- return getItemByStringIndex( aStringSheet );
--}
--
--::rtl::OUString SAL_CALL
--ScVbaCollectionBaseImpl::getDefaultMethodName( ) throw (css::uno::RuntimeException)
--{
-- const static rtl::OUString sName( RTL_CONSTASCII_USTRINGPARAM("Item") );
-- return sName;
--}
--
-- // XElementAccess
--
--::sal_Bool SAL_CALL ScVbaCollectionBaseImpl::hasElements() throw (uno::RuntimeException)
--{
-- return ( m_xIndexAccess->getCount() > 0 );
--}
--
--
---- sc/source/ui/vba/vbacollectionimpl.hxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbacollectionimpl.hxx 1970-01-01 00:00:00.000000000 +0000
-@@ -1,259 +0,0 @@
--/*************************************************************************
-- *
-- * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-- *
-- * Copyright 2008 by Sun Microsystems, Inc.
-- *
-- * OpenOffice.org - a multi-platform office productivity suite
-- *
-- * $RCSfile: vbacollectionimpl.hxx,v $
-- * $Revision: 1.5 $
-- *
-- * 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.
-- *
-- ************************************************************************/
--#ifndef SC_VBA_COLLECTION_IMPL_HXX
--#define SC_VBA_COLLECTION_IMPL_HXX
--
--#include <ooo/vba/XCollection.hpp>
--//#include <ooo/vba/XCollectionTest.hpp>
--#include <com/sun/star/container/XEnumerationAccess.hpp>
--#include <com/sun/star/uno/XComponentContext.hpp>
--#include <com/sun/star/script/XDefaultMethod.hpp>
--#include <com/sun/star/container/XIndexAccess.hpp>
--#include <com/sun/star/container/XNameAccess.hpp>
--#include <com/sun/star/container/XNamed.hpp>
--
--#include <cppuhelper/implbase3.hxx>
--#include <cppuhelper/implbase2.hxx>
--#include <cppuhelper/implbase1.hxx>
--
--#include "vbahelper.hxx"
--#include "vbahelperinterface.hxx"
--#include "vbaglobals.hxx"
--
--#include <vector>
--
--typedef ::cppu::WeakImplHelper1< css::container::XEnumeration > EnumerationHelper_BASE;
--
--class EnumerationHelperImpl : public EnumerationHelper_BASE
--{
--protected:
-- css::uno::Reference< css::uno::XComponentContext > m_xContext;
-- css::uno::Reference< css::container::XEnumeration > m_xEnumeration;
--public:
--
-- EnumerationHelperImpl( const css::uno::Reference< css::uno::XComponentContext >& xContext, const css::uno::Reference< css::container::XEnumeration >& xEnumeration ) throw ( css::uno::RuntimeException ) : m_xContext( xContext ), m_xEnumeration( xEnumeration ) { }
-- virtual ::sal_Bool SAL_CALL hasMoreElements( ) throw (css::uno::RuntimeException) { return m_xEnumeration->hasMoreElements(); }
--};
--
--// a wrapper class for a providing a XIndexAccess, XNameAccess, XEnumerationAccess impl based on providing a vector of interfaces
--// only requirement is the object needs to implement XName
--
--
--
--typedef ::cppu::WeakImplHelper3< css::container::XNameAccess, css::container::XIndexAccess, css::container::XEnumerationAccess > XNamedCollectionHelper_BASE;
--
--template< typename Ifc1 >
--class XNamedObjectCollectionHelper : public XNamedCollectionHelper_BASE
--{
--public:
--typedef std::vector< css::uno::Reference< Ifc1 > > XNamedVec;
--private:
--
-- class XNamedEnumerationHelper : public EnumerationHelper_BASE
-- {
-- XNamedVec mXNamedVec;
-- typename XNamedVec::iterator mIt;
-- public:
-- XNamedEnumerationHelper( const XNamedVec& sMap ) : mXNamedVec( sMap ), mIt( mXNamedVec.begin() ) {}
--
-- virtual ::sal_Bool SAL_CALL hasMoreElements( ) throw (css::uno::RuntimeException)
-- {
-- return ( mIt != mXNamedVec.end() );
-- }
--
-- virtual css::uno::Any SAL_CALL nextElement( ) throw (css::container::NoSuchElementException, css::lang::WrappedTargetException, css::uno::RuntimeException)
-- {
-- if ( hasMoreElements() )
-- return css::uno::makeAny( *mIt++ );
-- throw css::container::NoSuchElementException();
-- }
-- };
--
--protected:
-- XNamedVec mXNamedVec;
-- typename XNamedVec::iterator cachePos;
--public:
-- XNamedObjectCollectionHelper( const XNamedVec& sMap ) : mXNamedVec( sMap ), cachePos(mXNamedVec.begin()) {}
-- // XElementAccess
-- virtual css::uno::Type SAL_CALL getElementType( ) throw (css::uno::RuntimeException) { return Ifc1::static_type(0); }
-- virtual ::sal_Bool SAL_CALL hasElements( ) throw (css::uno::RuntimeException) { return ( mXNamedVec.size() > 0 ); }
-- // XNameAcess
-- virtual css::uno::Any SAL_CALL getByName( const ::rtl::OUString& aName ) throw (css::container::NoSuchElementException, css::lang::WrappedTargetException, css::uno::RuntimeException)
-- {
-- if ( !hasByName(aName) )
-- throw css::container::NoSuchElementException();
-- return css::uno::makeAny( *cachePos );
-- }
-- virtual css::uno::Sequence< ::rtl::OUString > SAL_CALL getElementNames( ) throw (css::uno::RuntimeException)
-- {
-- css::uno::Sequence< rtl::OUString > sNames( mXNamedVec.size() );
-- rtl::OUString* pString = sNames.getArray();
-- typename XNamedVec::iterator it = mXNamedVec.begin();
-- typename XNamedVec::iterator it_end = mXNamedVec.end();
--
-- for ( ; it != it_end; ++it, ++pString )
-- {
-- css::uno::Reference< css::container::XNamed > xName( *it, css::uno::UNO_QUERY_THROW );
-- *pString = xName->getName();
-- }
-- return sNames;
-- }
-- virtual ::sal_Bool SAL_CALL hasByName( const ::rtl::OUString& aName ) throw (css::uno::RuntimeException)
-- {
-- cachePos = mXNamedVec.begin();
-- typename XNamedVec::iterator it_end = mXNamedVec.end();
-- for ( ; cachePos != it_end; ++cachePos )
-- {
-- css::uno::Reference< css::container::XNamed > xName( *cachePos, css::uno::UNO_QUERY_THROW );
-- if ( aName.equals( xName->getName() ) )
-- break;
-- }
-- return ( cachePos != it_end );
-- }
--
-- // XElementAccess
-- virtual ::sal_Int32 SAL_CALL getCount( ) throw (css::uno::RuntimeException) { return mXNamedVec.size(); }
-- virtual css::uno::Any SAL_CALL getByIndex( ::sal_Int32 Index ) throw (css::lang::IndexOutOfBoundsException, css::lang::WrappedTargetException, css::uno::RuntimeException )
-- {
-- if ( Index < 0 || Index >= getCount() )
-- throw css::lang::IndexOutOfBoundsException();
--
-- return css::uno::makeAny( mXNamedVec[ Index ] );
--
-- }
-- // XEnumerationAccess
-- virtual css::uno::Reference< css::container::XEnumeration > SAL_CALL createEnumeration( ) throw (css::uno::RuntimeException)
-- {
-- return new XNamedEnumerationHelper( mXNamedVec );
-- }
--};
--
--// including a HelperInterface implementation
--template< typename Ifc1 >
--class ScVbaCollectionBase : public InheritedHelperInterfaceImpl< Ifc1 >
--{
--typedef InheritedHelperInterfaceImpl< Ifc1 > BaseColBase;
--protected:
-- css::uno::Reference< css::container::XIndexAccess > m_xIndexAccess;
-- css::uno::Reference< css::container::XNameAccess > m_xNameAccess;
--
-- virtual css::uno::Any getItemByStringIndex( const rtl::OUString& sIndex ) throw (css::uno::RuntimeException)
-- {
-- if ( !m_xNameAccess.is() )
-- throw css::uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ScVbaCollectionBase string index access not supported by this object") ), css::uno::Reference< css::uno::XInterface >() );
--
-- return createCollectionObject( m_xNameAccess->getByName( sIndex ) );
-- }
--
-- virtual css::uno::Any getItemByIntIndex( const sal_Int32 nIndex ) throw (css::uno::RuntimeException)
-- {
-- if ( !m_xIndexAccess.is() )
-- throw css::uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ScVbaCollectionBase numeric index access not supported by this object") ), css::uno::Reference< css::uno::XInterface >() );
-- if ( nIndex <= 0 )
-- {
-- throw css::lang::IndexOutOfBoundsException(
-- ::rtl::OUString( RTL_CONSTASCII_USTRINGPARAM(
-- "index is 0 or negative" ) ),
-- css::uno::Reference< css::uno::XInterface >() );
-- }
-- // need to adjust for vba index ( for which first element is 1 )
-- return createCollectionObject( m_xIndexAccess->getByIndex( nIndex - 1 ) );
-- }
--public:
-- ScVbaCollectionBase( const css::uno::Reference< ov::XHelperInterface >& xParent, const css::uno::Reference< css::uno::XComponentContext >& xContext, const css::uno::Reference< css::container::XIndexAccess >& xIndexAccess ) : BaseColBase( xParent, xContext ), m_xIndexAccess( xIndexAccess ){ m_xNameAccess.set(m_xIndexAccess, css::uno::UNO_QUERY); }
-- //XCollection
-- virtual ::sal_Int32 SAL_CALL getCount() throw (css::uno::RuntimeException)
-- {
-- return m_xIndexAccess->getCount();
-- }
--
-- virtual css::uno::Any SAL_CALL Item( const css::uno::Any& Index1, const css::uno::Any& /*not processed in this base class*/ ) throw (css::uno::RuntimeException)
-- {
-- if ( Index1.getValueTypeClass() != css::uno::TypeClass_STRING )
-- {
-- sal_Int32 nIndex = 0;
--
-- if ( ( Index1 >>= nIndex ) != sal_True )
-- {
-- rtl::OUString message;
-- message = rtl::OUString::createFromAscii(
-- "Couldn't convert index to Int32");
-- throw css::lang::IndexOutOfBoundsException( message,
-- css::uno::Reference< css::uno::XInterface >() );
-- }
-- return getItemByIntIndex( nIndex );
-- }
-- rtl::OUString aStringSheet;
--
-- Index1 >>= aStringSheet;
-- return getItemByStringIndex( aStringSheet );
-- }
-- // XDefaultMethod
-- ::rtl::OUString SAL_CALL getDefaultMethodName( ) throw (css::uno::RuntimeException)
-- {
-- const static rtl::OUString sName( RTL_CONSTASCII_USTRINGPARAM("Item") );
-- return sName;
-- }
-- // XEnumerationAccess
-- virtual css::uno::Reference< css::container::XEnumeration > SAL_CALL createEnumeration() throw (css::uno::RuntimeException) = 0;
--
-- // XElementAccess
-- virtual css::uno::Type SAL_CALL getElementType() throw (css::uno::RuntimeException) = 0;
-- // XElementAccess
-- virtual ::sal_Bool SAL_CALL hasElements() throw (css::uno::RuntimeException)
-- {
-- return ( m_xIndexAccess->getCount() > 0 );
-- }
-- virtual css::uno::Any createCollectionObject( const css::uno::Any& aSource ) = 0;
--
--};
--
--typedef ::cppu::WeakImplHelper1<ov::XCollection> XCollection_InterfacesBASE;
--
--typedef ScVbaCollectionBase< XCollection_InterfacesBASE > CollImplBase1;
--// compatible with the old collections ( pre XHelperInterface base class ) ( some internal objects still use this )
--class ScVbaCollectionBaseImpl : public CollImplBase1
--{
--public:
-- ScVbaCollectionBaseImpl( const css::uno::Reference< ov::XHelperInterface > xParent, const css::uno::Reference< css::uno::XComponentContext >& xContext, const css::uno::Reference< css::container::XIndexAccess >& xIndexAccess ) throw( css::uno::RuntimeException ) : CollImplBase1( xParent, xContext, xIndexAccess){}
--
--};
--
--template <typename Ifc> // where Ifc must implement XCollectionTest
--class CollTestImplHelper : public ScVbaCollectionBase< ::cppu::WeakImplHelper1< Ifc > >
--{
--typedef ScVbaCollectionBase< ::cppu::WeakImplHelper1< Ifc > > ImplBase1;
--
--public:
-- CollTestImplHelper( const css::uno::Reference< ov::XHelperInterface >& xParent, const css::uno::Reference< css::uno::XComponentContext >& xContext, const css::uno::Reference< css::container::XIndexAccess >& xIndexAccess ) throw( css::uno::RuntimeException ) : ImplBase1( xParent, xContext, xIndexAccess ) {}
--};
--
--
--#endif //SC_VBA_COLLECTION_IMPL_HXX
---- sc/source/ui/vba/vbacolorformat.hxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbacolorformat.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -33,7 +33,7 @@
- #include <com/sun/star/drawing/XShape.hpp>
- #include <ooo/vba/msforms/XColorFormat.hpp>
- #include <ooo/vba/msforms/XFillFormat.hpp>
--#include "vbahelperinterface.hxx"
-+#include <vbahelper/vbahelperinterface.hxx>
- #include "vbafillformat.hxx"
-
- typedef InheritedHelperInterfaceImpl1< ov::msforms::XColorFormat > ScVbaColorFormat_BASE;
---- sc/source/ui/vba/vbacombobox.cxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbacombobox.cxx 1970-01-01 00:00:00.000000000 +0000
-@@ -1,175 +0,0 @@
--/*************************************************************************
-- *
-- * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-- *
-- * Copyright 2008 by Sun Microsystems, Inc.
-- *
-- * OpenOffice.org - a multi-platform office productivity suite
-- *
-- * $RCSfile: vbacombobox.cxx,v $
-- * $Revision: 1.4 $
-- *
-- * 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 "vbacombobox.hxx"
--#include <vector>
--
--using namespace com::sun::star;
--using namespace ooo::vba;
--
--
--//SelectedItems list of integer indexes
--//StringItemList list of items
--
--const static rtl::OUString TEXT( RTL_CONSTASCII_USTRINGPARAM("Text") );
--const static rtl::OUString SELECTEDITEMS( RTL_CONSTASCII_USTRINGPARAM("SelectedItems") );
--const static rtl::OUString ITEMS( RTL_CONSTASCII_USTRINGPARAM("StringItemList") );
--const static rtl::OUString CONTROLSOURCEPROP( RTL_CONSTASCII_USTRINGPARAM("DataFieldProperty") );
--
--ScVbaComboBox::ScVbaComboBox( const uno::Reference< XHelperInterface >& xParent, const uno::Reference< uno::XComponentContext >& xContext, const uno::Reference< uno::XInterface >& xControl, const uno::Reference< frame::XModel >& xModel, AbstractGeometryAttributes* pGeomHelper, bool bDialogType ) : ComboBoxImpl_BASE( xParent, xContext, xControl, xModel, pGeomHelper ), mbDialogType( bDialogType )
--{
-- mpListHelper.reset( new ListControlHelper( m_xProps ) );
-- // grab the default value property name
-- m_xProps->getPropertyValue( CONTROLSOURCEPROP ) >>= sSourceName;
--}
--
--// Attributes
--
--
--// Value, [read] e.g. getValue returns the value of ooo Text propery e.g. the value in
--// the drop down
--uno::Any SAL_CALL
--ScVbaComboBox::getValue() throw (uno::RuntimeException)
--{
-- return m_xProps->getPropertyValue( sSourceName );
--}
--
--void SAL_CALL
--ScVbaComboBox::setListIndex( const uno::Any& _value ) throw (uno::RuntimeException)
--{
-- uno::Sequence< sal_Int16 > sSelection(1);
-- _value >>= sSelection[ 0 ];
-- m_xProps->setPropertyValue( SELECTEDITEMS, uno::makeAny( sSelection ) );
--}
--
--uno::Any SAL_CALL
--ScVbaComboBox::getListIndex() throw (uno::RuntimeException)
--{
-- uno::Sequence< rtl::OUString > sItems;
-- m_xProps->getPropertyValue( ITEMS ) >>= sItems;
-- // should really return the item that has focus regardless of
-- // it been selected
-- if ( sItems.getLength() > 0 )
-- {
-- rtl::OUString sText = getText();
-- sal_Int32 nLen = sItems.getLength();
-- for ( sal_Int32 index = 0; sText.getLength() && index < nLen; ++index )
-- {
-- if ( sItems[ index ].equals( sText ) )
-- {
-- OSL_TRACE("getListIndex returning %d", index );
-- return uno::makeAny( index );
-- }
--
-- }
-- }
-- OSL_TRACE("getListIndex returning %d", -1 );
-- return uno::makeAny( sal_Int32( -1 ) );
--}
--
--// Value, [write]e.g. setValue sets the value in the drop down, and if the value is one
--// of the values in the list then the selection is also set
--void SAL_CALL
--ScVbaComboBox::setValue( const uno::Any& _value ) throw (uno::RuntimeException)
--{
-- m_xProps->setPropertyValue( sSourceName, _value );
--}
--
--// see Value
--
--::rtl::OUString SAL_CALL
--ScVbaComboBox::getText() throw (uno::RuntimeException)
--{
-- rtl::OUString result;
-- getValue() >>= result;
-- return result;
--}
--
--void SAL_CALL
--ScVbaComboBox::setText( const ::rtl::OUString& _text ) throw (uno::RuntimeException)
--{
-- setValue( uno::makeAny( _text ) ); // seems the same
--}
--
--// Methods
--void SAL_CALL
--ScVbaComboBox::AddItem( const uno::Any& pvargItem, const uno::Any& pvargIndex ) throw (uno::RuntimeException)
--{
-- mpListHelper->AddItem( pvargItem, pvargIndex );
--}
--
--void SAL_CALL
--ScVbaComboBox::removeItem( const uno::Any& index ) throw (uno::RuntimeException)
-- {
-- mpListHelper->removeItem( index );
--}
--
--void SAL_CALL
--ScVbaComboBox::Clear( ) throw (uno::RuntimeException)
-- {
-- mpListHelper->Clear();
-- }
--
--void SAL_CALL
--ScVbaComboBox::setRowSource( const rtl::OUString& _rowsource ) throw (css::uno::RuntimeException)
--{
-- ScVbaControl::setRowSource( _rowsource );
-- mpListHelper->setRowSource( _rowsource );
-- }
--
--sal_Int32 SAL_CALL
--ScVbaComboBox::getListCount() throw (uno::RuntimeException)
--{
-- return mpListHelper->getListCount();
--}
--
--uno::Any SAL_CALL
--ScVbaComboBox::List( const ::uno::Any& pvargIndex, const uno::Any& pvarColumn ) throw (uno::RuntimeException)
--{
-- return mpListHelper->List( pvargIndex, pvarColumn );
-- }
--
--rtl::OUString&
--ScVbaComboBox::getServiceImplName()
--{
-- static rtl::OUString sImplName( RTL_CONSTASCII_USTRINGPARAM("ScVbaComboBox") );
-- return sImplName;
--}
--
--uno::Sequence< rtl::OUString >
--ScVbaComboBox::getServiceNames()
--{
-- static uno::Sequence< rtl::OUString > aServiceNames;
-- if ( aServiceNames.getLength() == 0 )
-- {
-- aServiceNames.realloc( 1 );
-- aServiceNames[ 0 ] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.msforms.ComboBox" ) );
-- }
-- return aServiceNames;
--}
---- sc/source/ui/vba/vbacombobox.hxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbacombobox.hxx 1970-01-01 00:00:00.000000000 +0000
-@@ -1,80 +0,0 @@
--/*************************************************************************
-- *
-- * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-- *
-- * Copyright 2008 by Sun Microsystems, Inc.
-- *
-- * OpenOffice.org - a multi-platform office productivity suite
-- *
-- * $RCSfile: vbacombobox.hxx,v $
-- * $Revision: 1.4 $
-- *
-- * 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.
-- *
-- ************************************************************************/
--#ifndef SC_VBA_COMBOBOX_HXX
--#define SC_VBA_COMBOBOX_HXX
--#include <cppuhelper/implbase2.hxx>
--#include <com/sun/star/uno/XComponentContext.hpp>
--#include <com/sun/star/beans/XPropertySet.hpp>
--#include <com/sun/star/script/XDefaultProperty.hpp>
--#include <ooo/vba/msforms/XComboBox.hpp>
--#include <comphelper/proparrhlp.hxx>
--#include <comphelper/propertycontainer.hxx>
--#include <com/sun/star/beans/PropertyAttribute.hpp>
--
--#include "vbacontrol.hxx"
--#include "vbalistcontrolhelper.hxx"
--#include "vbahelper.hxx"
--
--typedef cppu::ImplInheritanceHelper2<ScVbaControl, ov::msforms::XComboBox, css::script::XDefaultProperty > ComboBoxImpl_BASE;
--class ScVbaComboBox : public ComboBoxImpl_BASE
--{
-- std::auto_ptr< ListControlHelper > mpListHelper;
-- rtl::OUString sSourceName;
-- rtl::OUString msDftPropName;
-- bool mbDialogType;
--
--public:
-- ScVbaComboBox( const css::uno::Reference< ov::XHelperInterface >& xParent, const css::uno::Reference< css::uno::XComponentContext >& xContext, const css::uno::Reference< css::uno::XInterface >& xControl, const css::uno::Reference< css::frame::XModel >& xModel, ov::AbstractGeometryAttributes* pGeomHelper, bool bDialogType = false );
--
-- // Attributes
-- virtual css::uno::Any SAL_CALL getListIndex() throw (css::uno::RuntimeException);
-- virtual ::sal_Int32 SAL_CALL getListCount() throw (css::uno::RuntimeException);
-- virtual void SAL_CALL setListIndex( const css::uno::Any& _value ) throw (css::uno::RuntimeException);
-- virtual css::uno::Any SAL_CALL getValue() throw (css::uno::RuntimeException);
-- virtual void SAL_CALL setValue( const css::uno::Any& _value ) throw (css::uno::RuntimeException);
-- virtual ::rtl::OUString SAL_CALL getText() throw (css::uno::RuntimeException);
-- virtual void SAL_CALL setText( const ::rtl::OUString& _text ) throw (css::uno::RuntimeException);
--
-- // Methods
-- virtual void SAL_CALL AddItem( const css::uno::Any& pvargItem, const css::uno::Any& pvargIndex ) throw (css::uno::RuntimeException);
-- virtual void SAL_CALL removeItem( const css::uno::Any& index ) throw (css::uno::RuntimeException);
-- virtual void SAL_CALL Clear( ) throw (css::uno::RuntimeException);
-- virtual css::uno::Any SAL_CALL List( const css::uno::Any& pvargIndex, const css::uno::Any& pvarColumn ) throw (css::uno::RuntimeException);
-- // XControl
-- virtual void SAL_CALL setRowSource( const rtl::OUString& _rowsource ) throw (css::uno::RuntimeException);
--
-- // XDefaultProperty
-- ::rtl::OUString SAL_CALL getDefaultPropertyName( ) throw (css::uno::RuntimeException) { return ::rtl::OUString::createFromAscii("Value"); }
-- //XHelperInterface
-- virtual rtl::OUString& getServiceImplName();
-- virtual css::uno::Sequence<rtl::OUString> getServiceNames();
--};
--
--#endif //
---- sc/source/ui/vba/vbacommandbar.cxx.old 2009-04-06 16:42:00.000000000 +0000
-+++ sc/source/ui/vba/vbacommandbar.cxx 1970-01-01 00:00:00.000000000 +0000
-@@ -1,347 +0,0 @@
--/*************************************************************************
-- *
-- * OpenOffice.org - a multi-platform office productivity suite
-- *
-- * $RCSfile$
-- *
-- * $Revision$
-- *
-- * last change: $Author$ $Date$
-- *
-- * The Contents of this file are made available subject to
-- * the terms of GNU Lesser General Public License Version 2.1.
-- *
-- *
-- * GNU Lesser General Public License Version 2.1
-- * =============================================
-- * Copyright 2005 by Sun Microsystems, Inc.
-- * 901 San Antonio Road, Palo Alto, CA 94303, USA
-- *
-- * This library is free software; you can redistribute it and/or
-- * modify it under the terms of the GNU Lesser General Public
-- * License version 2.1, as published by the Free Software Foundation.
-- *
-- * This library 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 for more details.
-- *
-- * You should have received a copy of the GNU Lesser General Public
-- * License along with this library; if not, write to the Free Software
-- * Foundation, Inc., 59 Temple Place, Suite 330, Boston,
-- * MA 02111-1307 USA
-- *
-- ************************************************************************/
--#include <com/sun/star/ui/XModuleUIConfigurationManagerSupplier.hpp>
--#include <com/sun/star/frame/XFrame.hpp>
--#include <com/sun/star/frame/XDesktop.hpp>
--#include <com/sun/star/frame/XLayoutManager.hpp>
--#include <com/sun/star/beans/XPropertySet.hpp>
--#include <ooo/vba/office/MsoBarType.hpp>
--
--#include "vbacommandbar.hxx"
--#include "vbacommandbarcontrols.hxx"
--#include "vbahelper.hxx"
--
--
--using namespace com::sun::star;
--using namespace ooo::vba;
--
--ScVbaCommandBar::ScVbaCommandBar( const uno::Reference< XHelperInterface > xParent, const uno::Reference< uno::XComponentContext > xContext, sal_Int32 nModuleType ) throw (uno::RuntimeException) : CommandBar_BASE( xParent, xContext )
--{
-- // it's a menu bar
-- // only supporting factory menus ( no custom menus )
-- m_xParentHardRef.set( xParent, uno::UNO_QUERY_THROW );
-- initCommandBar();
-- switch( nModuleType )
-- {
-- case 0:
-- m_sMenuModuleName = rtl::OUString::createFromAscii( "com.sun.star.sheet.SpreadsheetDocument" );
-- break;
-- case 1:
-- m_sMenuModuleName = rtl::OUString::createFromAscii( "com.sun.star.text.TextDocument" );
-- break;
-- default:
-- m_sMenuModuleName = rtl::OUString::createFromAscii( "com.sun.star.text.TextDocument" );
-- }
-- getMenuSettings();
-- m_bIsMenu = sal_True;
-- m_bCustom = sal_False;
--}
--ScVbaCommandBar::ScVbaCommandBar( const uno::Reference< XHelperInterface > xParent, const uno::Reference< uno::XComponentContext > xContext, rtl::OUString sToolBarName, sal_Bool bTemporary, sal_Bool bCreate ) throw (uno::RuntimeException) : CommandBar_BASE( xParent, xContext )
--{
-- // it's a tool bar
-- m_xParentHardRef.set( xParent, uno::UNO_QUERY_THROW );
-- initCommandBar();
-- m_bTemporary = bTemporary;
-- m_bCreate = bCreate;
-- // get OOo ToolBarName
-- CommandBarNameMap::const_iterator iter = mCommandBarNameMap.find( sToolBarName.toAsciiLowerCase() );
-- if( iter != mCommandBarNameMap.end() )
-- {
-- m_sToolBarName = iter->second;
-- }
-- else
-- {
-- m_sToolBarName = sToolBarName;
-- }
-- m_sUIName = m_sToolBarName;
-- m_bIsMenu = sal_False;
-- getToolBarSettings( m_sToolBarName );
--}
--void
--ScVbaCommandBar::initCommandBar() throw (uno::RuntimeException)
--{
-- m_pScVbaCommandBars = dynamic_cast< ScVbaCommandBars* >( m_xParentHardRef.get() );
-- if ( !m_pScVbaCommandBars )
-- throw uno::RuntimeException( rtl::OUString::createFromAscii( "Parent needs to be a ScVbaCommandBars"), uno::Reference< uno::XInterface >() );
-- m_bIsMenu = sal_False;
-- m_bCustom = sal_False;
-- m_bTemporary = sal_True;
-- m_sToolBarName = rtl::OUString::createFromAscii("");
-- m_sUIName = rtl::OUString::createFromAscii("");
-- m_sMenuModuleName = m_pScVbaCommandBars->GetModuleName();
--}
--void
--ScVbaCommandBar::getToolBarSettings( rtl::OUString sToolBarName ) throw( uno::RuntimeException )
--{
-- rtl::OUString sFactoryToolBar = rtl::OUString::createFromAscii("private:resource/toolbar/") + sToolBarName.toAsciiLowerCase();
-- rtl::OUString sCustomToolBar = rtl::OUString::createFromAscii("private:resource/toolbar/custom_toolbar_") + sToolBarName;
-- uno::Reference< lang::XMultiServiceFactory > xMSF( mxContext->getServiceManager(), uno::UNO_QUERY_THROW );
-- uno::Reference< ui::XModuleUIConfigurationManagerSupplier > xUICfgManagerSup( xMSF->createInstance(rtl::OUString::createFromAscii("com.sun.star.ui.ModuleUIConfigurationManagerSupplier") ), uno::UNO_QUERY_THROW );
-- m_xUICfgManager.set( xUICfgManagerSup->getUIConfigurationManager( m_pScVbaCommandBars->GetModuleName() ), uno::UNO_QUERY_THROW );
-- m_xUICfgPers.set( m_xUICfgManager, uno::UNO_QUERY_THROW );
-- if( m_xUICfgManager->hasSettings( sFactoryToolBar ) )
-- {
-- // exsiting standard ToolBar
-- m_xBarSettings.set( m_xUICfgManager->getSettings( sFactoryToolBar, sal_True ), uno::UNO_QUERY_THROW );
-- m_sToolBarName = sFactoryToolBar;
-- }
-- else if( m_xUICfgManager->hasSettings( sCustomToolBar ) )
-- {
-- // exisiting custom ToolBar
-- m_xBarSettings.set( m_xUICfgManager->getSettings( sCustomToolBar, sal_True ), uno::UNO_QUERY_THROW );
-- m_sToolBarName = sCustomToolBar;
-- m_bCustom = sal_True;
-- }
-- else if( m_bCreate )
-- {
-- // new custom ToolBar
-- m_xBarSettings.set( m_xUICfgManager->createSettings(), uno::UNO_QUERY_THROW );
-- m_sToolBarName = sCustomToolBar;
-- m_bCustom = sal_True;
-- addCustomBar();
-- }
-- else
-- throw uno::RuntimeException( rtl::OUString::createFromAscii("ToolBar do not exist"), uno::Reference< uno::XInterface >() );
-- if( m_pScVbaCommandBars->GetWindows()->hasByName( m_sToolBarName ) )
-- {
-- uno::Any aToolBar = m_pScVbaCommandBars->GetWindows()->getByName( m_sToolBarName );
-- aToolBar >>= m_aToolBar;
-- }
--}
--void
--ScVbaCommandBar::addCustomBar()
--{
-- uno::Reference< beans::XPropertySet > xPropertySet( m_xBarSettings, uno::UNO_QUERY_THROW );
-- xPropertySet->setPropertyValue(rtl::OUString::createFromAscii("UIName"), uno::makeAny( m_sUIName ));
--
-- if( m_xUICfgManager->hasSettings(m_sToolBarName) )
-- {
-- m_xUICfgManager->replaceSettings( m_sToolBarName, uno::Reference< container::XIndexAccess > (m_xBarSettings, uno::UNO_QUERY_THROW ) );
-- }
-- else
-- {
-- m_xUICfgManager->insertSettings( m_sToolBarName, uno::Reference< container::XIndexAccess > (m_xBarSettings, uno::UNO_QUERY_THROW ) );
-- }
-- if( !m_bTemporary )
-- {
-- m_xUICfgPers->store();
-- }
--}
--void
--ScVbaCommandBar::getMenuSettings()
--{
-- try
-- {
-- rtl::OUString sMenuBar = rtl::OUString::createFromAscii( "private:resource/menubar/menubar" );
-- uno::Reference< lang::XMultiServiceFactory > xMSF( mxContext->getServiceManager(), uno::UNO_QUERY_THROW );
-- uno::Reference< ui::XModuleUIConfigurationManagerSupplier > xUICfgManagerSup( xMSF->createInstance(rtl::OUString::createFromAscii("com.sun.star.ui.ModuleUIConfigurationManagerSupplier") ), uno::UNO_QUERY_THROW );
-- m_xUICfgManager.set( xUICfgManagerSup->getUIConfigurationManager( m_sMenuModuleName ), uno::UNO_QUERY_THROW );
-- m_xUICfgPers.set( m_xUICfgManager, uno::UNO_QUERY_THROW );
-- m_xBarSettings.set( m_xUICfgManager->getSettings( sMenuBar, sal_True ), uno::UNO_QUERY_THROW );
-- }
-- catch ( uno::Exception e)
-- {
-- OSL_TRACE( "getMenuSetting got a error\n" );
-- }
--}
--::rtl::OUString SAL_CALL
--ScVbaCommandBar::getName() throw ( uno::RuntimeException )
--{
-- // This will get a "NULL length string" when Name is not set.
-- uno::Reference< beans::XPropertySet > xPropertySet( m_xBarSettings, uno::UNO_QUERY_THROW );
-- uno::Any aName = xPropertySet->getPropertyValue( rtl::OUString::createFromAscii("UIName") );
-- rtl::OUString sName;
-- aName >>= sName;
-- if( sName.getLength() < 1 && !m_bIsMenu )
-- {
-- uno::Reference< container::XNameAccess > xNameAccess( m_pScVbaCommandBars->GetWindows(), uno::UNO_QUERY_THROW );
-- if( xNameAccess->hasByName( m_sToolBarName ) )
-- {
-- beans::PropertyValues aToolBar;
-- xNameAccess->getByName( m_sToolBarName ) >>= aToolBar;
-- sal_Int32 nCount = aToolBar.getLength();
-- beans::PropertyValue aPropertyValue;
-- for( sal_Int32 i = 0; i < nCount; i++ )
-- {
-- aPropertyValue = aToolBar[i];
-- if( aPropertyValue.Name.equals( rtl::OUString::createFromAscii("UIName") ) )
-- {
-- aPropertyValue.Value >>= sName;
-- return sName;
-- }
-- }
-- }
-- }
-- return sName;
--}
--void SAL_CALL
--ScVbaCommandBar::setName( const ::rtl::OUString& _name ) throw (uno::RuntimeException)
--{
-- uno::Reference< beans::XPropertySet > xPropertySet( m_xBarSettings, uno::UNO_QUERY_THROW );
-- xPropertySet->setPropertyValue( rtl::OUString::createFromAscii("UIName"), uno::makeAny( _name ) );
-- uno::Reference< container::XIndexAccess > xIndexAccess( m_xBarSettings, uno::UNO_QUERY_THROW );
--
-- if( m_xUICfgManager->hasSettings( m_sToolBarName ) )
-- {
-- m_xUICfgManager->replaceSettings( m_sToolBarName, xIndexAccess );
-- }
-- else
-- {
-- // toolbar not found
-- }
-- if( !m_bTemporary )
-- {
-- m_xUICfgPers->store();
-- }
--}
--::sal_Bool SAL_CALL
--ScVbaCommandBar::getVisible() throw (uno::RuntimeException)
--{
-- sal_Bool bVisible = sal_False;
-- try
-- {
-- sal_Int32 i = 0;
-- while( !m_aToolBar[i].Name.equals( rtl::OUString::createFromAscii( "Visible" ) ) )
-- {
-- i++;
-- }
-- m_aToolBar[i].Value >>= bVisible;
-- }
-- catch ( uno::Exception e )
-- {
-- }
-- return bVisible;
--}
--void SAL_CALL
--ScVbaCommandBar::setVisible( ::sal_Bool _visible ) throw (uno::RuntimeException)
--{
-- try
-- {
-- uno::Reference< frame::XFrame > xFrame( getCurrentDocument()->getCurrentController()->getFrame(), uno::UNO_QUERY_THROW );
-- uno::Reference< beans::XPropertySet > xPropertySet( xFrame, uno::UNO_QUERY_THROW );
-- uno::Reference< frame::XLayoutManager > xLayoutManager( xPropertySet->getPropertyValue( rtl::OUString::createFromAscii("LayoutManager") ), uno::UNO_QUERY_THROW );
-- if( _visible )
-- {
-- xLayoutManager->createElement( m_sToolBarName );
-- xLayoutManager->showElement( m_sToolBarName );
-- }
-- else
-- {
-- xLayoutManager->hideElement( m_sToolBarName );
-- xLayoutManager->destroyElement( m_sToolBarName );
-- }
-- }
-- catch( uno::Exception e )
-- {
-- OSL_TRACE( "SetVisible get an exception\n" );
-- }
--}
--void SAL_CALL
--ScVbaCommandBar::Delete( ) throw (css::script::BasicErrorException, css::uno::RuntimeException)
--{
-- if( m_bCustom )
-- {
-- if( m_xUICfgManager->hasSettings( m_sToolBarName ) )
-- {
-- m_xUICfgManager->removeSettings(m_sToolBarName);
-- // make it permanent
-- if( !m_bTemporary )
-- {
-- m_xUICfgPers->store();
-- }
-- }
-- else
-- {
-- // toolbar not found
-- // TODO throw Error
-- }
-- uno::Reference< container::XNameContainer > xNameContainer( m_pScVbaCommandBars->GetWindows(), uno::UNO_QUERY_THROW );
-- if( xNameContainer->hasByName( m_sToolBarName ) )
-- {
-- xNameContainer->removeByName( m_sToolBarName );
-- }
-- }
--}
--uno::Any SAL_CALL
--ScVbaCommandBar::Controls( const uno::Any& aIndex ) throw (script::BasicErrorException, uno::RuntimeException)
--{
-- sal_Int32 nIndex;
-- uno::Reference< XCommandBarControls > xCommandBarControls( new ScVbaCommandBarControls( this, mxContext, uno::Reference< container::XIndexAccess >() ) );
-- if( aIndex.hasValue() )
-- {
-- if( aIndex >>= nIndex )
-- {
-- uno::Reference< XCommandBarControl > xCommandBarControl( xCommandBarControls->Item( aIndex, uno::Any() ), uno::UNO_QUERY_THROW );
-- return uno::makeAny( xCommandBarControl );
-- }
-- else
-- throw uno::RuntimeException( rtl::OUString::createFromAscii( "invalid index" ), uno::Reference< uno::XInterface >() );
-- }
-- return uno::makeAny( xCommandBarControls );
--}
--
--sal_Int32 SAL_CALL
--ScVbaCommandBar::Type() throw (script::BasicErrorException, uno::RuntimeException)
--{
-- // #FIXME support msoBarTypePopup
-- sal_Int32 nType = office::MsoBarType::msoBarTypePopup;
-- nType = m_bIsMenu? office::MsoBarType::msoBarTypeNormal : office::MsoBarType::msoBarTypeMenuBar;
-- return nType;
--}
--
--uno::Any SAL_CALL
--ScVbaCommandBar::FindControl( const uno::Any& /*aType*/, const uno::Any& /*aId*/, const uno::Any& /*aTag*/, const uno::Any& /*aVisible*/, const uno::Any& /*aRecursive*/ ) throw (script::BasicErrorException, uno::RuntimeException)
--{
-- // alwayse fail to find control
-- return uno::makeAny( uno::Reference< XCommandBarControl > () );
--}
--
--rtl::OUString&
--ScVbaCommandBar::getServiceImplName()
--{
-- static rtl::OUString sImplName( RTL_CONSTASCII_USTRINGPARAM("ScVbaCommandBar") );
-- return sImplName;
--}
--uno::Sequence<rtl::OUString>
--ScVbaCommandBar::getServiceNames()
--{
-- static uno::Sequence< rtl::OUString > aServiceNames;
-- if ( aServiceNames.getLength() == 0 )
-- {
-- aServiceNames.realloc( 1 );
-- aServiceNames[ 0 ] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.CommandBar" ) );
-- }
-- return aServiceNames;
--}
---- sc/source/ui/vba/vbacommandbar.hxx.old 2009-04-06 16:42:00.000000000 +0000
-+++ sc/source/ui/vba/vbacommandbar.hxx 1970-01-01 00:00:00.000000000 +0000
-@@ -1,107 +0,0 @@
--/*************************************************************************
-- *
-- * OpenOffice.org - a multi-platform office productivity suite
-- *
-- * $RCSfile$
-- *
-- * $Revision$
-- *
-- * last change: $Author$ $Date$
-- *
-- * The Contents of this file are made available subject to
-- * the terms of GNU Lesser General Public License Version 2.1.
-- *
-- *
-- * GNU Lesser General Public License Version 2.1
-- * =============================================
-- * Copyright 2005 by Sun Microsystems, Inc.
-- * 901 San Antonio Road, Palo Alto, CA 94303, USA
-- *
-- * This library is free software; you can redistribute it and/or
-- * modify it under the terms of the GNU Lesser General Public
-- * License version 2.1, as published by the Free Software Foundation.
-- *
-- * This library 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 for more details.
-- *
-- * You should have received a copy of the GNU Lesser General Public
-- * License along with this library; if not, write to the Free Software
-- * Foundation, Inc., 59 Temple Place, Suite 330, Boston,
-- * MA 02111-1307 USA
-- *
-- ************************************************************************/
--#ifndef SC_VBA_COMMANDBAR_HXX
--#define SC_VBA_COMMANDBAR_HXX
--
--#include <ooo/vba/XCommandBar.hpp>
--#include <com/sun/star/ui/XUIConfigurationManager.hpp>
--#include <com/sun/star/ui/XUIConfigurationPersistence.hpp>
--#include <com/sun/star/container/XIndexContainer.hpp>
--#include <com/sun/star/beans/PropertyValues.hpp>
--
--#include "vbahelperinterface.hxx"
--#include "vbacommandbars.hxx"
--
--#include <map>
--typedef std::map< const rtl::OUString, rtl::OUString > CommandBarNameMap;
--typedef std::pair< const rtl::OUString, rtl::OUString > CommandBarNamePair;
--const CommandBarNamePair namePair[] = {
-- CommandBarNamePair( rtl::OUString::createFromAscii("standard"), rtl::OUString::createFromAscii("standardbar") ),
-- CommandBarNamePair( rtl::OUString::createFromAscii("formatting"), rtl::OUString::createFromAscii("formatobjectbar") ),
--};
--static const CommandBarNameMap mCommandBarNameMap( namePair, ( namePair + sizeof(namePair) / sizeof(namePair[0]) ) );
--
--
--typedef InheritedHelperInterfaceImpl1< ov::XCommandBar > CommandBar_BASE;
--
--class ScVbaCommandBar : public CommandBar_BASE
--{
--private:
-- rtl::OUString m_sToolBarName;
-- rtl::OUString m_sMenuModuleName;
-- rtl::OUString m_sUIName;
-- sal_Bool m_bTemporary;
-- sal_Bool m_bIsMenu;
-- sal_Bool m_bCustom;
-- sal_Bool m_bCreate;
-- ScVbaCommandBars* m_pScVbaCommandBars;
-- css::beans::PropertyValues m_aToolBar;
-- // hard reference for parent
-- css::uno::Reference< ov::XHelperInterface > m_xParentHardRef;
-- css::uno::Reference< css::ui::XUIConfigurationManager > m_xUICfgManager;
-- css::uno::Reference< css::ui::XUIConfigurationPersistence > m_xUICfgPers;
-- css::uno::Reference< css::container::XIndexContainer > m_xBarSettings;
-- void initCommandBar() throw( css::uno::RuntimeException );
--protected:
-- void getToolBarSettings( rtl::OUString sToolBarName ) throw( css::uno::RuntimeException );
-- void getMenuSettings();
-- void addCustomBar();
--public:
-- ScVbaCommandBar( const css::uno::Reference< ov::XHelperInterface > xParent, const css::uno::Reference< css::uno::XComponentContext > xContext, sal_Int32 nModuleType ) throw( css::uno::RuntimeException );
-- ScVbaCommandBar( const css::uno::Reference< ov::XHelperInterface > xParent, const css::uno::Reference< css::uno::XComponentContext > xContext, rtl::OUString sToolBarName, sal_Bool bTemporary, sal_Bool bCreate ) throw( css::uno::RuntimeException );
--
-- sal_Bool IsMenu() { return m_bIsMenu; };
-- css::uno::Reference< css::ui::XUIConfigurationManager > GetUICfgManager() { return m_xUICfgManager; };
-- css::uno::Reference< css::ui::XUIConfigurationPersistence > GetUICfgPers() { return m_xUICfgPers; };
-- css::uno::Reference< css::container::XIndexContainer > GetBarSettings() { return m_xBarSettings; };
-- rtl::OUString GetToolBarName() { return m_sToolBarName; };
--
-- // Attributes
-- virtual ::rtl::OUString SAL_CALL getName() throw (css::uno::RuntimeException);
-- virtual void SAL_CALL setName( const ::rtl::OUString& _name ) throw (css::uno::RuntimeException);
-- virtual ::sal_Bool SAL_CALL getVisible() throw (css::uno::RuntimeException);
-- virtual void SAL_CALL setVisible( ::sal_Bool _visible ) throw (css::uno::RuntimeException);
--
-- // Methods
-- virtual void SAL_CALL Delete( ) throw (css::script::BasicErrorException, css::uno::RuntimeException);
-- virtual css::uno::Any SAL_CALL Controls( const css::uno::Any& aIndex ) throw (css::script::BasicErrorException, css::uno::RuntimeException);
-- virtual sal_Int32 SAL_CALL Type( ) throw (css::script::BasicErrorException, css::uno::RuntimeException);
-- virtual css::uno::Any SAL_CALL FindControl( const css::uno::Any& aType, const css::uno::Any& aId, const css::uno::Any& aTag, const css::uno::Any& aVisible, const css::uno::Any& aRecursive ) throw (css::script::BasicErrorException, css::uno::RuntimeException);
--
-- // XHelperInterface
-- virtual rtl::OUString& getServiceImplName();
-- virtual css::uno::Sequence<rtl::OUString> getServiceNames();
--};
--#endif//SC_VBA_COMMANDBAR_HXX
---- sc/source/ui/vba/vbacommandbarcontrol.cxx.old 2009-04-06 16:42:00.000000000 +0000
-+++ sc/source/ui/vba/vbacommandbarcontrol.cxx 1970-01-01 00:00:00.000000000 +0000
-@@ -1,443 +0,0 @@
--/*************************************************************************
-- *
-- * OpenOffice.org - a multi-platform office productivity suite
-- *
-- * $RCSfile$
-- *
-- * $Revision$
-- *
-- * last change: $Author$ $Date$
-- *
-- * The Contents of this file are made available subject to
-- * the terms of GNU Lesser General Public License Version 2.1.
-- *
-- *
-- * GNU Lesser General Public License Version 2.1
-- * =============================================
-- * Copyright 2005 by Sun Microsystems, Inc.
-- * 901 San Antonio Road, Palo Alto, CA 94303, USA
-- *
-- * This library is free software; you can redistribute it and/or
-- * modify it under the terms of the GNU Lesser General Public
-- * License version 2.1, as published by the Free Software Foundation.
-- *
-- * This library 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 for more details.
-- *
-- * You should have received a copy of the GNU Lesser General Public
-- * License along with this library; if not, write to the Free Software
-- * Foundation, Inc., 59 Temple Place, Suite 330, Boston,
-- * MA 02111-1307 USA
-- *
-- ************************************************************************/
--#include "vbacommandbarcontrol.hxx"
--#include <basic/sbstar.hxx>
--#include <basic/sbmod.hxx>
--
--using namespace com::sun::star;
--using namespace ooo::vba;
--
--uno::Any lcl_getPropertyValue( beans::PropertyValues aPropertyValues, rtl::OUString sPropertyName )
--{
-- sal_Int32 nCount = aPropertyValues.getLength();
-- for( sal_Int32 i = 0; i < nCount; i++ )
-- {
-- if( aPropertyValues[i].Name.equalsIgnoreAsciiCase( sPropertyName ) )
-- {
-- return aPropertyValues[i].Value;
-- }
-- }
-- return uno::Any();
--}
--
--beans::PropertyValues lcl_repalcePropertyValue( beans::PropertyValues aPropertyValues, rtl::OUString sPropertyName, uno::Any aValue )
--{
-- sal_Int32 nCount = aPropertyValues.getLength();
-- for( sal_Int32 i = 0; i < nCount; i++ )
-- {
-- if( aPropertyValues[i].Name.equalsIgnoreAsciiCase( sPropertyName ) )
-- {
-- aPropertyValues[i].Value = aValue;
-- return aPropertyValues;
-- }
-- }
-- return aPropertyValues;
--}
--
--ScVbaCommandBarControl::ScVbaCommandBarControl( const uno::Reference< XHelperInterface > xParent, const uno::Reference< uno::XComponentContext > xContext, rtl::OUString sName, sal_Int32 nPosition, sal_Int32 nType ) throw (uno::RuntimeException) : CommandBarControl_BASE( xParent, xContext ), m_sName( sName ), m_nPosition( nPosition ), m_nType( nType )
--{
-- // exsiting CommandBarBarControl
-- m_xParentHardRef.set( xParent, uno::UNO_QUERY_THROW );
-- initObjects();
-- if( m_xBarSettings->hasElements() )
-- {
-- ScVbaCommandBarControl* pParentCommandBarControl = m_pCommandBarControls->GetParentCommandBarControl();
-- if( pParentCommandBarControl )
-- {
-- beans::PropertyValues aPropertyValues;
-- pParentCommandBarControl->GetCurrentSettings()->getByIndex( pParentCommandBarControl->GetPosition() ) >>= aPropertyValues;
-- pParentCommandBarControl->SetPropertyValues( aPropertyValues );
-- m_xCurrentSettings.set( lcl_getPropertyValue( pParentCommandBarControl->GetPropertyValues(), rtl::OUString::createFromAscii( "ItemDescriptorContainer" ) ), uno::UNO_QUERY_THROW );
-- }
-- if( !m_xCurrentSettings.is() )
-- {
-- m_xCurrentSettings.set( m_xUICfgManager->getSettings( m_pCommandBarControls->GetParentToolBarName(), sal_True ), uno::UNO_QUERY_THROW );
-- }
-- }
-- if( m_bIsMenu )
-- {
-- m_sBarName = rtl::OUString::createFromAscii("private:resource/menubar/menubar");
-- }
-- else
-- {
-- m_sBarName = m_pCommandBarControls->GetParentToolBarName();
-- }
-- m_bTemporary = sal_True;
--}
--ScVbaCommandBarControl::ScVbaCommandBarControl( const uno::Reference< XHelperInterface > xParent, const uno::Reference< uno::XComponentContext > xContext, rtl::OUString sName, sal_Int32 nPosition, sal_Bool bTemporary, sal_Int32 nType) throw (uno::RuntimeException) : CommandBarControl_BASE( xParent, xContext ), m_nPosition( nPosition ), m_bTemporary( bTemporary ), m_nType( nType )
--{
-- m_xParentHardRef.set( xParent, uno::UNO_QUERY_THROW );
-- initObjects();
-- if( sName.getLength() > 0 )
-- {
-- m_sName = sName;
-- }
-- m_sCommand = rtl::OUString::createFromAscii("vnd.openoffice.org:") + sName;
-- if( m_bIsMenu )
-- {
-- m_sBarName = rtl::OUString::createFromAscii("private:resource/menubar/menubar");
-- createNewMenuBarControl();
-- }
-- else
-- {
-- m_sBarName = m_pCommandBarControls->GetParentToolBarName();
-- createNewToolBarControl();
-- }
--}
--
--void
--ScVbaCommandBarControl::initObjects() throw (uno::RuntimeException)
--{
-- m_pCommandBarControls = dynamic_cast< ScVbaCommandBarControls* >( m_xParentHardRef.get() );
-- if( !m_pCommandBarControls )
-- throw uno::RuntimeException( rtl::OUString::createFromAscii( "Parent needs to be a ScVbaCommandBarControls"), uno::Reference< uno::XInterface >() );
-- m_xUICfgManager.set( m_pCommandBarControls->GetUICfgManager(), uno::UNO_QUERY_THROW );
-- m_xUICfgPers.set( m_pCommandBarControls->GetUICfgPers(), uno::UNO_QUERY_THROW );
-- m_xBarSettings.set( m_pCommandBarControls->GetBarSettings(), uno::UNO_QUERY_THROW );
-- m_bIsMenu = m_pCommandBarControls->IsMenu();
-- m_sName = rtl::OUString::createFromAscii( "Custom" );
--}
--
--void
--ScVbaCommandBarControl::createNewMenuBarControl()
--{
-- uno::Reference< lang::XSingleComponentFactory > xMenuMSF( m_xBarSettings, uno::UNO_QUERY_THROW );
--
-- uno::Sequence< beans::PropertyValue > aPropertys;
-- if( m_nType == office::MsoControlType::msoControlPopup )
-- aPropertys = uno::Sequence< beans::PropertyValue >( 4 );
-- else
-- aPropertys = uno::Sequence< beans::PropertyValue >( 3 );
--
-- aPropertys[0].Name = rtl::OUString::createFromAscii("CommandURL");
-- aPropertys[0].Value <<= m_sCommand;
-- aPropertys[1].Name = rtl::OUString::createFromAscii("Label");
-- aPropertys[1].Value <<= m_sName;
-- aPropertys[2].Name = rtl::OUString::createFromAscii("Type");
-- aPropertys[2].Value <<= sal_Int32(0);
--
-- if( m_nType == office::MsoControlType::msoControlPopup )
-- {
-- aPropertys[3].Name = rtl::OUString::createFromAscii("ItemDescriptorContainer");
-- aPropertys[3].Value <<= xMenuMSF->createInstanceWithContext( mxContext );
-- }
--
-- if( m_pCommandBarControls->GetParentCommandBar() != NULL )
-- {
-- // create a new menu
-- m_xBarSettings->insertByIndex( m_nPosition, uno::makeAny( aPropertys ) );
-- m_xCurrentSettings.set( m_xBarSettings, uno::UNO_QUERY_THROW );
-- }
-- else if( m_pCommandBarControls->GetParentCommandBarControl() != NULL )
-- {
-- // create a new menu entry
-- ScVbaCommandBarControl* pPc = m_pCommandBarControls->GetParentCommandBarControl();
-- beans::PropertyValues aPropertyValues;
-- pPc->GetCurrentSettings()->getByIndex( pPc->GetPosition() ) >>= aPropertyValues;
-- pPc->SetPropertyValues( aPropertyValues );
--
-- // has the property already been set?
-- if( lcl_getPropertyValue( pPc->GetPropertyValues(), rtl::OUString::createFromAscii("ItemDescriptorContainer") ).hasValue() )
-- {
-- lcl_repalcePropertyValue( pPc->GetPropertyValues(), rtl::OUString::createFromAscii("ItemDescriptorContainer"), uno::makeAny( xMenuMSF->createInstanceWithContext( mxContext ) ) );
-- pPc->GetCurrentSettings()->replaceByIndex( pPc->GetPosition(), uno::makeAny( pPc->GetPropertyValues() ) );
-- }
-- m_xCurrentSettings.set( lcl_getPropertyValue( pPc->GetPropertyValues(), rtl::OUString::createFromAscii("ItemDescriptorContainer") ), uno::UNO_QUERY_THROW );
-- m_xCurrentSettings->insertByIndex( m_nPosition, uno::makeAny( aPropertys ) );
-- }
-- if( m_xUICfgManager->hasSettings( m_sBarName ) )
-- {
-- m_xUICfgManager->replaceSettings( m_sBarName, uno::Reference< container::XIndexAccess > (m_xBarSettings, uno::UNO_QUERY_THROW ) );
-- }
-- else
-- {
-- m_xUICfgManager->insertSettings( m_sBarName, uno::Reference< container::XIndexAccess > (m_xBarSettings, uno::UNO_QUERY_THROW ) );
-- }
-- if( !m_bTemporary )
-- {
-- m_xUICfgPers->store();
-- }
--}
--
--void
--ScVbaCommandBarControl::createNewToolBarControl()
--{
-- uno::Sequence< beans::PropertyValue > aPropertys(4);
-- aPropertys[0].Name = rtl::OUString::createFromAscii("CommandURL");
-- aPropertys[0].Value <<= m_sCommand;
-- aPropertys[1].Name = rtl::OUString::createFromAscii("Label");
-- aPropertys[1].Value <<= m_sName;
-- aPropertys[2].Name = rtl::OUString::createFromAscii("Type");
-- aPropertys[2].Value <<= sal_Int32(0);
-- aPropertys[3].Name = rtl::OUString::createFromAscii("IsVisible");
-- aPropertys[3].Value <<= sal_True;
--
-- m_xBarSettings->insertByIndex( m_nPosition, uno::makeAny( aPropertys ) );
-- uno::Reference< beans::XPropertySet > xPropertySet( m_xBarSettings, uno::UNO_QUERY_THROW );
-- rtl::OUString sUIName;
-- xPropertySet->getPropertyValue( rtl::OUString::createFromAscii("UIName") ) >>= sUIName;
--
-- m_xCurrentSettings.set( m_xBarSettings, uno::UNO_QUERY_THROW );
-- if( m_xUICfgManager->hasSettings( m_sBarName ) )
-- {
-- m_xUICfgManager->replaceSettings( m_sBarName, uno::Reference< container::XIndexAccess > (m_xBarSettings, uno::UNO_QUERY_THROW ) );
-- }
-- else
-- {
-- m_xUICfgManager->insertSettings( m_sBarName, uno::Reference< container::XIndexAccess > (m_xBarSettings, uno::UNO_QUERY_THROW ) );
-- }
-- if( !m_bTemporary )
-- {
-- m_xUICfgPers->store();
-- }
--}
--
--::rtl::OUString SAL_CALL
--ScVbaCommandBarControl::getCaption() throw ( uno::RuntimeException )
--{
-- // "Label" always empty
-- rtl::OUString sCaption;
-- beans::PropertyValues aPropertyValues;
-- if( m_xCurrentSettings.is() )
-- {
-- m_xCurrentSettings->getByIndex( m_nPosition ) >>= aPropertyValues;
-- lcl_getPropertyValue( aPropertyValues, rtl::OUString::createFromAscii("Label") ) >>= sCaption;
-- }
-- else if( m_xBarSettings.is() )
-- {
-- m_xBarSettings->getByIndex( m_nPosition ) >>= aPropertyValues;
-- lcl_getPropertyValue( aPropertyValues, rtl::OUString::createFromAscii("Label") ) >>= sCaption;
-- }
-- return sCaption;
--}
--void SAL_CALL
--ScVbaCommandBarControl::setCaption( const ::rtl::OUString& _caption ) throw (uno::RuntimeException)
--{
-- if( m_xCurrentSettings.is() )
-- {
-- beans::PropertyValues aPropertyValues;
-- m_xCurrentSettings->getByIndex( m_nPosition ) >>= aPropertyValues;
-- beans::PropertyValues aNewPropertyValues;
-- aNewPropertyValues = lcl_repalcePropertyValue( aPropertyValues, rtl::OUString::createFromAscii("Label"), uno::makeAny( _caption ) );
-- m_xCurrentSettings->replaceByIndex( m_nPosition, uno::makeAny( aNewPropertyValues ) );
-- if( m_xUICfgManager->hasSettings( m_sBarName ) )
-- {
-- m_xUICfgManager->replaceSettings( m_sBarName, uno::Reference< container::XIndexAccess > (m_xBarSettings, uno::UNO_QUERY_THROW ) );
-- }
-- else
-- {
-- m_xUICfgManager->insertSettings( m_sBarName, uno::Reference< container::XIndexAccess > (m_xBarSettings, uno::UNO_QUERY_THROW ) );
-- }
-- // make it permanent
-- if( !m_bTemporary )
-- {
-- m_xUICfgPers->store();
-- }
-- }
--}
--::rtl::OUString SAL_CALL
--ScVbaCommandBarControl::getOnAction() throw (uno::RuntimeException)
--{
-- if( m_xCurrentSettings.is() )
-- {
-- beans::PropertyValues aPropertyValues;
-- m_xCurrentSettings->getByIndex( m_nPosition ) >>= aPropertyValues;
-- rtl::OUString sCommandURL;
-- lcl_getPropertyValue( aPropertyValues, rtl::OUString::createFromAscii( "CommandURL" ) ) >>= sCommandURL;
-- return sCommandURL;
-- }
-- return ::rtl::OUString();
--}
--void SAL_CALL
--ScVbaCommandBarControl::setOnAction( const ::rtl::OUString& _onaction ) throw (uno::RuntimeException)
--{
-- if( m_xCurrentSettings.is() )
-- {
-- // convert the comand url into something like vnd.sun.star.script:Standard.testMacro.Macro1?language=Basic&location=document
-- rtl::OUString aCommandURL;
-- rtl::OUString sUrlPart = rtl::OUString::createFromAscii( "vnd.sun.star.script:Standard.");
-- SbModule* pModule = StarBASIC::GetActiveModule();
-- if( pModule && ( _onaction.indexOf( sUrlPart ) == -1 ) )
-- {
-- rtl::OUString sUrlPart1 = rtl::OUString::createFromAscii( "?language=Basic&location=document");
-- aCommandURL = sUrlPart.concat( pModule->GetName() ).concat( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM(".") ) ).concat( _onaction ).concat( sUrlPart1 );
-- }
-- else
-- {
-- aCommandURL = _onaction;
-- }
-- OSL_TRACE(" ScVbaCommandBarControl::setOnAction: %s", rtl::OUStringToOString( aCommandURL, RTL_TEXTENCODING_UTF8 ).getStr() );
--
-- beans::PropertyValues aPropertyValues;
-- m_xCurrentSettings->getByIndex( m_nPosition ) >>= aPropertyValues;
-- beans::PropertyValues aNewPropertyValues;
-- aNewPropertyValues = lcl_repalcePropertyValue( aPropertyValues, rtl::OUString::createFromAscii("CommandURL"), uno::makeAny( aCommandURL ) );
-- m_xCurrentSettings->replaceByIndex( m_nPosition, uno::makeAny( aNewPropertyValues ) );
-- if( m_xUICfgManager->hasSettings( m_sBarName ) )
-- {
-- m_xUICfgManager->replaceSettings( m_sBarName, uno::Reference< container::XIndexAccess > (m_xBarSettings, uno::UNO_QUERY_THROW ) );
-- }
-- else
-- {
-- m_xUICfgManager->insertSettings( m_sBarName, uno::Reference< container::XIndexAccess > (m_xBarSettings, uno::UNO_QUERY_THROW ) );
-- }
-- // make it permanent
-- if( !m_bTemporary )
-- {
-- m_xUICfgPers->store();
-- }
-- }
--}
--::sal_Bool SAL_CALL
--ScVbaCommandBarControl::getVisible() throw (uno::RuntimeException)
--{
-- // not possible in UNO?
-- return sal_True;
--}
--void SAL_CALL
--ScVbaCommandBarControl::setVisible( ::sal_Bool /*_visible*/ ) throw (uno::RuntimeException)
--{
-- // "IsVisilbe"
--}
--void SAL_CALL
--ScVbaCommandBarControl::Delete( ) throw (css::script::BasicErrorException, css::uno::RuntimeException)
--{
-- if( m_xCurrentSettings.is() )
-- {
-- m_xCurrentSettings->removeByIndex( m_nPosition );
--
-- if( m_xUICfgManager->hasSettings( m_sBarName ) )
-- {
-- m_xUICfgManager->replaceSettings( m_sBarName, uno::Reference< container::XIndexAccess > (m_xBarSettings, uno::UNO_QUERY_THROW ) );
-- }
-- else
-- {
-- m_xUICfgManager->insertSettings( m_sBarName, uno::Reference< container::XIndexAccess > (m_xBarSettings, uno::UNO_QUERY_THROW ) );
-- }
-- // make it permanent
-- if( !m_bTemporary )
-- {
-- m_xUICfgPers->store();
-- }
-- }
--}
--uno::Any SAL_CALL
--ScVbaCommandBarControl::Controls( const uno::Any& aIndex ) throw (script::BasicErrorException, uno::RuntimeException)
--{
-- sal_Int32 nIndex;
-- uno::Reference< XCommandBarControls > xCommandBarControls( new ScVbaCommandBarControls( this, mxContext, uno::Reference< container::XIndexAccess >() ) );
-- if( aIndex.hasValue() )
-- {
-- if( aIndex >>= nIndex )
-- {
-- uno::Reference< XCommandBarControl > xCommandBarControl( xCommandBarControls->Item( aIndex, uno::Any() ), uno::UNO_QUERY_THROW );
-- return uno::makeAny( xCommandBarControl );
-- }
-- else
-- throw uno::RuntimeException( rtl::OUString::createFromAscii( "invalid index" ), uno::Reference< uno::XInterface >() );
-- }
-- return uno::makeAny( xCommandBarControls );
--}
--rtl::OUString&
--ScVbaCommandBarControl::getServiceImplName()
--{
-- static rtl::OUString sImplName( RTL_CONSTASCII_USTRINGPARAM("ScVbaCommandBarControl") );
-- return sImplName;
--}
--uno::Sequence<rtl::OUString>
--ScVbaCommandBarControl::getServiceNames()
--{
-- static uno::Sequence< rtl::OUString > aServiceNames;
-- if ( aServiceNames.getLength() == 0 )
-- {
-- aServiceNames.realloc( 1 );
-- aServiceNames[ 0 ] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.CommandBarControl" ) );
-- }
-- return aServiceNames;
--}
--
--//////////// ScVbaCommandBarPopup //////////////////////////////
--ScVbaCommandBarPopup::ScVbaCommandBarPopup( const uno::Reference< XHelperInterface > xParent, const uno::Reference< uno::XComponentContext > xContext, rtl::OUString sName, sal_Int32 nPosition ) throw (uno::RuntimeException) : CommandBarPopup_BASE( xParent, xContext, sName, nPosition, office::MsoControlType::msoControlPopup )
--{
--}
--
--ScVbaCommandBarPopup::ScVbaCommandBarPopup( const uno::Reference< XHelperInterface > xParent, const uno::Reference< uno::XComponentContext > xContext, rtl::OUString sName, sal_Int32 nPosition, sal_Bool bTemporary ) throw (uno::RuntimeException) : CommandBarPopup_BASE( xParent, xContext, sName, nPosition, bTemporary, office::MsoControlType::msoControlPopup)
--{
--}
--
--rtl::OUString&
--ScVbaCommandBarPopup::getServiceImplName()
--{
-- static rtl::OUString sImplName( RTL_CONSTASCII_USTRINGPARAM("ScVbaCommandBarPopup") );
-- return sImplName;
--}
--uno::Sequence<rtl::OUString>
--ScVbaCommandBarPopup::getServiceNames()
--{
-- static uno::Sequence< rtl::OUString > aServiceNames;
-- if ( aServiceNames.getLength() == 0 )
-- {
-- aServiceNames.realloc( 1 );
-- aServiceNames[ 0 ] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.CommandBarPopup" ) );
-- }
-- return aServiceNames;
--}
--
--//////////// ScVbaCommandBarButton //////////////////////////////
--ScVbaCommandBarButton::ScVbaCommandBarButton( const uno::Reference< XHelperInterface > xParent, const uno::Reference< uno::XComponentContext > xContext, rtl::OUString sName, sal_Int32 nPosition ) throw (uno::RuntimeException) : CommandBarButton_BASE( xParent, xContext, sName, nPosition, office::MsoControlType::msoControlButton )
--{
--}
--
--ScVbaCommandBarButton::ScVbaCommandBarButton( const uno::Reference< XHelperInterface > xParent, const uno::Reference< uno::XComponentContext > xContext, rtl::OUString sName, sal_Int32 nPosition, sal_Bool bTemporary ) throw (uno::RuntimeException) : CommandBarButton_BASE( xParent, xContext, sName, nPosition, bTemporary, office::MsoControlType::msoControlButton)
--{
--}
--
--rtl::OUString&
--ScVbaCommandBarButton::getServiceImplName()
--{
-- static rtl::OUString sImplName( RTL_CONSTASCII_USTRINGPARAM("ScVbaCommandBarButton") );
-- return sImplName;
--}
--uno::Sequence<rtl::OUString>
--ScVbaCommandBarButton::getServiceNames()
--{
-- static uno::Sequence< rtl::OUString > aServiceNames;
-- if ( aServiceNames.getLength() == 0 )
-- {
-- aServiceNames.realloc( 1 );
-- aServiceNames[ 0 ] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.CommandBarButton" ) );
-- }
-- return aServiceNames;
--}
---- sc/source/ui/vba/vbacommandbarcontrol.hxx.old 2009-04-06 16:42:00.000000000 +0000
-+++ sc/source/ui/vba/vbacommandbarcontrol.hxx 1970-01-01 00:00:00.000000000 +0000
-@@ -1,120 +0,0 @@
--/*************************************************************************
-- *
-- * OpenOffice.org - a multi-platform office productivity suite
-- *
-- * $RCSfile$
-- *
-- * $Revision$
-- *
-- * last change: $Author$ $Date$
-- *
-- * The Contents of this file are made available subject to
-- * the terms of GNU Lesser General Public License Version 2.1.
-- *
-- *
-- * GNU Lesser General Public License Version 2.1
-- * =============================================
-- * Copyright 2005 by Sun Microsystems, Inc.
-- * 901 San Antonio Road, Palo Alto, CA 94303, USA
-- *
-- * This library is free software; you can redistribute it and/or
-- * modify it under the terms of the GNU Lesser General Public
-- * License version 2.1, as published by the Free Software Foundation.
-- *
-- * This library 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 for more details.
-- *
-- * You should have received a copy of the GNU Lesser General Public
-- * License along with this library; if not, write to the Free Software
-- * Foundation, Inc., 59 Temple Place, Suite 330, Boston,
-- * MA 02111-1307 USA
-- *
-- ************************************************************************/
--#ifndef SC_VBA_COMMANDBARCONTROL_HXX
--#define SC_VBA_COMMANDBARCONTROL_HXX
--
--#include <ooo/vba/XCommandBarControl.hpp>
--#include <ooo/vba/XCommandBarPopup.hpp>
--#include <ooo/vba/XCommandBarButton.hpp>
--#include <ooo/vba/office/MsoControlType.hpp>
--
--#include "vbahelperinterface.hxx"
--#include "vbacommandbarcontrols.hxx"
--
--typedef InheritedHelperInterfaceImpl1< ov::XCommandBarControl > CommandBarControl_BASE;
--
--class ScVbaCommandBarControl : public CommandBarControl_BASE
--{
--private:
-- rtl::OUString m_sName;
-- rtl::OUString m_sBarName;
-- rtl::OUString m_sCommand;
-- sal_Int32 m_nType;
-- sal_Int32 m_nPosition;
-- sal_Bool m_bTemporary;
-- sal_Bool m_bIsMenu;
-- ScVbaCommandBarControls* m_pCommandBarControls;
-- css::uno::Reference< ov::XHelperInterface > m_xParentHardRef;
-- css::uno::Reference< css::ui::XUIConfigurationManager > m_xUICfgManager;
-- css::uno::Reference< css::ui::XUIConfigurationPersistence > m_xUICfgPers;
-- css::uno::Reference< css::container::XIndexContainer > m_xBarSettings;
-- css::uno::Reference< css::container::XIndexContainer > m_xCurrentSettings;
-- css::beans::PropertyValues m_aPropertyValues;
--
-- void initObjects() throw (css::uno::RuntimeException);
-- void createNewMenuBarControl();
-- void createNewToolBarControl();
--public:
-- ScVbaCommandBarControl( const css::uno::Reference< ov::XHelperInterface > xParent, const css::uno::Reference< css::uno::XComponentContext > xContext, rtl::OUString sName, sal_Int32 nPosition = 0, sal_Int32 nType = ov::office::MsoControlType::msoControlButton ) throw (css::uno::RuntimeException);
-- ScVbaCommandBarControl( const css::uno::Reference< ov::XHelperInterface > xParent, const css::uno::Reference< css::uno::XComponentContext > xContext, rtl::OUString sName, sal_Int32 nPosition, sal_Bool bTemporary, sal_Int32 nType = ov::office::MsoControlType::msoControlButton ) throw (css::uno::RuntimeException);
-- css::uno::Reference< css::ui::XUIConfigurationManager > GetUICfgManager() { return m_xUICfgManager; };
-- css::uno::Reference< css::ui::XUIConfigurationPersistence > GetUICfgPers() { return m_xUICfgPers; };
-- css::uno::Reference< css::container::XIndexContainer > GetBarSettings() { return m_xBarSettings; };
-- sal_Bool IsMenu() { return m_bIsMenu; };
-- sal_Int32 GetPosition() { return m_nPosition; };
-- css::uno::Reference< css::container::XIndexContainer > GetCurrentSettings() { return m_xCurrentSettings; };
-- css::beans::PropertyValues GetPropertyValues() { return m_aPropertyValues; };
-- void SetPropertyValues( css::beans::PropertyValues aPropertyValues ) { m_aPropertyValues = aPropertyValues; };
--
-- // Attributes
-- virtual ::rtl::OUString SAL_CALL getCaption() throw (css::uno::RuntimeException);
-- virtual void SAL_CALL setCaption( const ::rtl::OUString& _caption ) throw (css::uno::RuntimeException);
-- virtual ::rtl::OUString SAL_CALL getOnAction() throw (css::uno::RuntimeException);
-- virtual void SAL_CALL setOnAction( const ::rtl::OUString& _onaction ) throw (css::uno::RuntimeException);
-- virtual ::sal_Bool SAL_CALL getVisible() throw (css::uno::RuntimeException);
-- virtual void SAL_CALL setVisible( ::sal_Bool _visible ) throw (css::uno::RuntimeException);
--
-- // Methods
-- virtual void SAL_CALL Delete( ) throw (css::script::BasicErrorException, css::uno::RuntimeException);
-- virtual css::uno::Any SAL_CALL Controls( const css::uno::Any& aIndex ) throw (css::script::BasicErrorException, css::uno::RuntimeException);
--
-- // XHelperInterface
-- virtual rtl::OUString& getServiceImplName();
-- virtual css::uno::Sequence<rtl::OUString> getServiceNames();
--};
--
--typedef cppu::ImplInheritanceHelper1< ScVbaCommandBarControl, ov::XCommandBarPopup > CommandBarPopup_BASE;
--class ScVbaCommandBarPopup : public CommandBarPopup_BASE
--{
--public:
-- ScVbaCommandBarPopup( const css::uno::Reference< ov::XHelperInterface > xParent, const css::uno::Reference< css::uno::XComponentContext > xContext, rtl::OUString sName, sal_Int32 nPosition = 0 ) throw (css::uno::RuntimeException);
-- ScVbaCommandBarPopup( const css::uno::Reference< ov::XHelperInterface > xParent, const css::uno::Reference< css::uno::XComponentContext > xContext, rtl::OUString sName, sal_Int32 nPosition, sal_Bool bTemporary ) throw (css::uno::RuntimeException);
-- // XHelperInterface
-- virtual rtl::OUString& getServiceImplName();
-- virtual css::uno::Sequence<rtl::OUString> getServiceNames();
--};
--
--typedef cppu::ImplInheritanceHelper1< ScVbaCommandBarControl, ov::XCommandBarButton > CommandBarButton_BASE;
--class ScVbaCommandBarButton : public CommandBarButton_BASE
--{
--public:
-- ScVbaCommandBarButton( const css::uno::Reference< ov::XHelperInterface > xParent, const css::uno::Reference< css::uno::XComponentContext > xContext, rtl::OUString sName, sal_Int32 nPosition = 0 ) throw (css::uno::RuntimeException);
-- ScVbaCommandBarButton( const css::uno::Reference< ov::XHelperInterface > xParent, const css::uno::Reference< css::uno::XComponentContext > xContext, rtl::OUString sName, sal_Int32 nPosition, sal_Bool bTemporary ) throw (css::uno::RuntimeException);
-- // XHelperInterface
-- virtual rtl::OUString& getServiceImplName();
-- virtual css::uno::Sequence<rtl::OUString> getServiceNames();
--};
--
--#endif//SC_VBA_COMMANDBARCONTROL_HXX
---- sc/source/ui/vba/vbacommandbarcontrols.cxx.old 2009-04-06 16:42:00.000000000 +0000
-+++ sc/source/ui/vba/vbacommandbarcontrols.cxx 1970-01-01 00:00:00.000000000 +0000
-@@ -1,348 +0,0 @@
--/*************************************************************************
-- *
-- * OpenOffice.org - a multi-platform office productivity suite
-- *
-- * $RCSfile$
-- *
-- * $Revision$
-- *
-- * last change: $Author$ $Date$
-- *
-- * The Contents of this file are made available subject to
-- * the terms of GNU Lesser General Public License Version 2.1.
-- *
-- *
-- * GNU Lesser General Public License Version 2.1
-- * =============================================
-- * Copyright 2005 by Sun Microsystems, Inc.
-- * 901 San Antonio Road, Palo Alto, CA 94303, USA
-- *
-- * This library is free software; you can redistribute it and/or
-- * modify it under the terms of the GNU Lesser General Public
-- * License version 2.1, as published by the Free Software Foundation.
-- *
-- * This library 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 for more details.
-- *
-- * You should have received a copy of the GNU Lesser General Public
-- * License along with this library; if not, write to the Free Software
-- * Foundation, Inc., 59 Temple Place, Suite 330, Boston,
-- * MA 02111-1307 USA
-- *
-- ************************************************************************/
--#include "vbacommandbarcontrols.hxx"
--#include "vbacommandbarcontrol.hxx"
--
--using namespace com::sun::star;
--using namespace ooo::vba;
--
--uno::Any lcl_getPropertyValue( beans::PropertyValues aPropertyValues, rtl::OUString sPropertyName );
--
--typedef ::cppu::WeakImplHelper1< container::XEnumeration > CommandBarControlEnumeration_BASE;
--class CommandBarControlEnumeration : public CommandBarControlEnumeration_BASE
--{
-- //uno::Reference< uno::XComponentContext > m_xContext;
-- ScVbaCommandBarControls* m_pCommandBarControls;
-- sal_Int32 m_nCurrentPosition;
--public:
-- CommandBarControlEnumeration( ScVbaCommandBarControls* pCommandBarControls ) : m_pCommandBarControls( pCommandBarControls ), m_nCurrentPosition( 0 ) {}
-- virtual sal_Bool SAL_CALL hasMoreElements() throw ( uno::RuntimeException )
-- {
-- if( m_nCurrentPosition < m_pCommandBarControls->getCount() )
-- return sal_True;
-- return sal_False;
-- }
-- virtual uno::Any SAL_CALL nextElement() throw ( container::NoSuchElementException, lang::WrappedTargetException, uno::RuntimeException )
-- {
-- if( hasMoreElements() )
-- {
-- rtl::OUString sName = m_pCommandBarControls->GetControlNameByIndex( m_nCurrentPosition );
-- m_nCurrentPosition = m_nCurrentPosition + 1;
-- if( sName.getLength() > 0 )
-- return m_pCommandBarControls->createCollectionObject( uno::makeAny( sName ) );
-- else
-- return nextElement();
-- }
-- else
-- throw container::NoSuchElementException();
-- }
--};
--
--ScVbaCommandBarControls::ScVbaCommandBarControls( const uno::Reference< XHelperInterface > xParent, const uno::Reference< uno::XComponentContext > xContext, const uno::Reference< container::XIndexAccess> xIndexAccess ) throw (uno::RuntimeException) : CommandBarControls_BASE( xParent, xContext, xIndexAccess )
--{
-- m_bIsMenu = sal_False;
-- m_bHasElements = sal_False;
-- m_xParentHardRef.set( xParent, uno::UNO_QUERY_THROW );
-- m_pCommandBar = dynamic_cast< ScVbaCommandBar* >( m_xParentHardRef.get() );
-- m_pCommandBarControl = dynamic_cast< ScVbaCommandBarControl* >( m_xParentHardRef.get() );
-- if( m_pCommandBar )
-- {
-- m_xUICfgManager.set( m_pCommandBar->GetUICfgManager(), uno::UNO_QUERY_THROW );
-- m_xUICfgPers.set( m_pCommandBar->GetUICfgPers(), uno::UNO_QUERY_THROW );
-- m_xBarSettings.set( m_pCommandBar->GetBarSettings(), uno::UNO_QUERY_THROW );
-- m_bIsMenu = m_pCommandBar->IsMenu();
-- if( m_xBarSettings->hasElements() )
-- {
-- m_bHasElements = sal_True;
-- }
-- }
-- else if( m_pCommandBarControl )
-- {
-- m_xUICfgManager.set( m_pCommandBarControl->GetUICfgManager(), uno::UNO_QUERY_THROW );
-- m_xUICfgPers.set( m_pCommandBarControl->GetUICfgPers(), uno::UNO_QUERY_THROW );
-- beans::PropertyValues aPropertyValues;
-- m_pCommandBarControl->GetCurrentSettings()->getByIndex( m_pCommandBarControl->GetPosition() ) >>= aPropertyValues;
-- m_pCommandBarControl->SetPropertyValues( aPropertyValues );
-- m_xBarSettings.set( m_pCommandBarControl->GetCurrentSettings(), uno::UNO_QUERY_THROW );
--
-- uno::Any aValue = lcl_getPropertyValue( m_pCommandBarControl->GetPropertyValues(), rtl::OUString::createFromAscii("ItemDescriptorContainer") );
-- if( aValue.hasValue() )
-- {
-- m_xCurrentSettings = m_pCommandBarControl->GetCurrentSettings();
-- m_bHasElements = sal_True;
-- }
-- else
-- {
-- m_bHasElements = sal_False;
-- }
-- m_bIsMenu = m_pCommandBarControl->IsMenu();
-- }
-- else
-- {
-- throw uno::RuntimeException( rtl::OUString::createFromAscii("Parent needs to be a ScVbaCommandBar or a ScVbaCommandBarControl"), uno::Reference< uno::XInterface >() );
-- }
--}
--rtl::OUString
--ScVbaCommandBarControls::GetControlNameByIndex( const sal_Int32 nIndex ) throw ( uno::RuntimeException )
--{
-- sal_Int32 nCount = 0;
-- if( m_bHasElements )
-- {
-- sal_Int32 nBarSettingsCount = m_xBarSettings->getCount();
-- for( sal_Int32 i = 0; i < nBarSettingsCount; i++ )
-- {
-- beans::PropertyValues aMenuValues;
-- m_xBarSettings->getByIndex( i ) >>= aMenuValues;
-- for( sal_Int32 j = 0; j < aMenuValues.getLength(); j++ )
-- {
-- if( aMenuValues[j].Name.equalsIgnoreAsciiCase( rtl::OUString::createFromAscii( "CommandURL" ) ) )
-- {
-- nCount++;
-- if( nIndex == nCount )
-- {
-- rtl::OUString sCommandURL;
-- aMenuValues[j].Value >>= sCommandURL;
-- sal_Int32 nLastIndex = sCommandURL.lastIndexOf( rtl::OUString::createFromAscii(":") );
-- if( ( nLastIndex != -1 ) && ( ( nLastIndex +1 ) < sCommandURL.getLength() ) )
-- {
-- sCommandURL = sCommandURL.copy( nLastIndex + 1 );
-- return sCommandURL;
-- }
-- }
-- }
-- }
-- }
-- }
-- else
-- throw uno::RuntimeException( rtl::OUString::createFromAscii( "Out of bound" ), uno::Reference< uno::XInterface >() );
-- return rtl::OUString();
--}
--
--// Attributes
--sal_Int32 SAL_CALL
--ScVbaCommandBarControls::getCount() throw (uno::RuntimeException)
--{
-- sal_Int32 nCount = 0;
-- if( m_bHasElements )
-- {
-- sal_Int32 nBarSettingsCount = m_xBarSettings->getCount();
-- for( sal_Int32 i = 0; i < nBarSettingsCount; i++ )
-- {
-- beans::PropertyValues aMenuValues;
-- m_xBarSettings->getByIndex( i ) >>= aMenuValues;
-- for( sal_Int32 j = 0; j < aMenuValues.getLength(); j++ )
-- {
-- if( aMenuValues[j].Name.equalsIgnoreAsciiCase( rtl::OUString::createFromAscii( "CommandURL" ) ) )
-- {
-- nCount++;
-- }
-- }
-- }
-- }
-- return nCount;
--}
--// XEnumerationAccess
--uno::Type SAL_CALL
--ScVbaCommandBarControls::getElementType() throw ( uno::RuntimeException )
--{
-- return XCommandBarControls::static_type( 0 );
--}
--uno::Reference< container::XEnumeration >
--ScVbaCommandBarControls::createEnumeration() throw ( uno::RuntimeException )
--{
-- return uno::Reference< container::XEnumeration >( new CommandBarControlEnumeration( this ) );
--}
--uno::Any
--ScVbaCommandBarControls::createCollectionObject( const uno::Any& aSource )
--{
-- // only surport the aSource as a name string, because this class is a API wrapper
-- rtl::OUString sName;
-- if( aSource >>= sName )
-- {
-- uno::Reference< container::XIndexContainer > xCurrentSettings;
-- beans::PropertyValues aPropertyValues;
-- if( m_pCommandBarControl )
-- {
-- m_pCommandBarControl->GetCurrentSettings()->getByIndex( m_pCommandBarControl->GetPosition() ) >>= aPropertyValues;
-- xCurrentSettings.set( lcl_getPropertyValue( aPropertyValues, rtl::OUString::createFromAscii( "ItemDescriptorContainer" ) ), uno::UNO_QUERY );
-- if( !xCurrentSettings.is() )
-- {
-- xCurrentSettings.set( m_xUICfgManager->getSettings( GetParentToolBarName(), sal_True ), uno::UNO_QUERY );
-- }
-- }
--
-- sal_Int32 nPosition = -1;
-- for( sal_Int32 i = 0; i < xCurrentSettings->getCount(); i++ )
-- {
-- xCurrentSettings->getByIndex( i ) >>= aPropertyValues;
-- // Label always empty in OOo
-- rtl::OUString sLabel;
-- lcl_getPropertyValue( aPropertyValues, rtl::OUString::createFromAscii( "Label" ) ) >>= sLabel;
-- if( sLabel.equalsIgnoreAsciiCase( sName ) )
-- {
-- nPosition = i;
-- break;
-- }
-- // using CammandURL to find
-- rtl::OUString sCommandURL;
-- lcl_getPropertyValue( aPropertyValues, rtl::OUString::createFromAscii( "CommandURL" ) ) >>= sCommandURL;
-- sal_Int32 nLastIndex = sCommandURL.lastIndexOf( rtl::OUString::createFromAscii(":") );
-- if( ( nLastIndex != -1 ) && ( ( nLastIndex + 1 ) < sCommandURL.getLength() ) )
-- {
-- sCommandURL = sCommandURL.copy( nLastIndex + 1 );
-- }
-- if( sCommandURL.equalsIgnoreAsciiCase( sName ) )
-- {
-- nPosition = i;
-- break;
-- }
-- }
--
-- if( nPosition != -1 )
-- {
-- uno::Reference< container::XIndexContainer > xSubMenu;
-- lcl_getPropertyValue( aPropertyValues, rtl::OUString::createFromAscii( "ItemDescriptorContainer" ) ) >>= xSubMenu;
-- ScVbaCommandBarControl* pNewCommandBarControl = NULL;
-- if( xSubMenu.is() )
-- pNewCommandBarControl = new ScVbaCommandBarPopup( this, mxContext, sName, nPosition );
-- else
-- pNewCommandBarControl = new ScVbaCommandBarButton( this, mxContext, sName, nPosition );
--
-- return uno::makeAny( uno::Reference< XCommandBarControl > ( pNewCommandBarControl ) );
-- }
-- else
-- throw uno::RuntimeException( rtl::OUString::createFromAscii("The CommandBarControl do not exist"), uno::Reference< uno::XInterface >() );
--
-- }
-- return uno::Any();
--}
--
--// Methods
--uno::Any SAL_CALL
--ScVbaCommandBarControls::Item( const uno::Any& aIndex, const uno::Any& /*aIndex*/ ) throw (uno::RuntimeException)
--{
-- if( aIndex.getValueTypeClass() == uno::TypeClass_STRING )
-- {
-- return createCollectionObject( aIndex );
-- }
-- sal_Int32 nIndex = 0;
-- if( aIndex >>= nIndex )
-- {
-- return createCollectionObject( uno::makeAny( GetControlNameByIndex( nIndex ) ) );
-- }
--
-- return uno::Any();
--}
--uno::Reference< XCommandBarControl > SAL_CALL
--ScVbaCommandBarControls::Add( const uno::Any& Type, const uno::Any& Id, const uno::Any& /*Parameter*/, const uno::Any& Before, const uno::Any& Temporary ) throw (script::BasicErrorException, uno::RuntimeException)
--{
-- // Parameter is not supported
-- // the following name needs to be individually created;
-- rtl::OUString sCaption( rtl::OUString::createFromAscii("custom Control") );
-- rtl::OUString sCommand( rtl::OUString::createFromAscii("macro:///Standard.Module1.Test()") );
-- sal_Int32 nType =0;
-- sal_Int32 nPosition = 0;
-- sal_Int32 nId;
-- sal_Bool bTemporary = sal_True;
--
-- if( Type.hasValue() )
-- if( Type >>= nType )
-- {
-- // evalute the type of the new control
-- }
-- if( Id.hasValue() )
-- if( Id >>= nId )
-- {
-- // evalute the action of the new control
-- }
-- if( Before.hasValue() )
-- Before >>= nPosition;
-- else
-- {
-- // if Before is ignore, the new control should be placed at the end of the commandbars;
-- if( m_pCommandBar )
-- nPosition = getCount();
-- else if ( m_pCommandBarControl )
-- {
-- css::uno::Reference< css::container::XIndexContainer > xCurrentSettings;
-- xCurrentSettings.set( lcl_getPropertyValue( m_pCommandBarControl->GetPropertyValues(), rtl::OUString::createFromAscii("ItemDescriptorContainer") ), uno::UNO_QUERY );
-- if( xCurrentSettings.is() )
-- {
-- nPosition = xCurrentSettings->getCount();
-- }
-- }
-- }
-- if( Temporary.hasValue() )
-- if( Temporary >>= bTemporary )
-- {
-- // evalute the temporary of the new Control
-- }
--
-- ScVbaCommandBarControl* pNewCommandBarControl = NULL;
-- if( nType == office::MsoControlType::msoControlButton )
-- {
-- pNewCommandBarControl = new ScVbaCommandBarButton( this, mxContext, sCaption, nPosition, bTemporary );
-- }
-- else if ( nType == office::MsoControlType::msoControlPopup )
-- {
-- pNewCommandBarControl = new ScVbaCommandBarPopup( this, mxContext, sCaption, nPosition, bTemporary );
-- }
-- else
-- {
-- pNewCommandBarControl = new ScVbaCommandBarControl( this, mxContext, sCaption, nPosition, bTemporary );
-- }
--
-- return uno::Reference< XCommandBarControl >( pNewCommandBarControl );
--}
--
--// XHelperInterface
--rtl::OUString&
--ScVbaCommandBarControls::getServiceImplName()
--{
-- static rtl::OUString sImplName( RTL_CONSTASCII_USTRINGPARAM("ScVbaCommandBarControls") );
-- return sImplName;
--}
--uno::Sequence<rtl::OUString>
--ScVbaCommandBarControls::getServiceNames()
--{
-- static uno::Sequence< rtl::OUString > aServiceNames;
-- if ( aServiceNames.getLength() == 0 )
-- {
-- aServiceNames.realloc( 1 );
-- aServiceNames[ 0 ] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.CommandBarControls" ) );
-- }
-- return aServiceNames;
--}
--
---- sc/source/ui/vba/vbacommandbarcontrols.hxx.old 2009-04-06 16:42:00.000000000 +0000
-+++ sc/source/ui/vba/vbacommandbarcontrols.hxx 1970-01-01 00:00:00.000000000 +0000
-@@ -1,91 +0,0 @@
--/*************************************************************************
-- *
-- * OpenOffice.org - a multi-platform office productivity suite
-- *
-- * $RCSfile$
-- *
-- * $Revision$
-- *
-- * last change: $Author$ $Date$
-- *
-- * The Contents of this file are made available subject to
-- * the terms of GNU Lesser General Public License Version 2.1.
-- *
-- *
-- * GNU Lesser General Public License Version 2.1
-- * =============================================
-- * Copyright 2005 by Sun Microsystems, Inc.
-- * 901 San Antonio Road, Palo Alto, CA 94303, USA
-- *
-- * This library is free software; you can redistribute it and/or
-- * modify it under the terms of the GNU Lesser General Public
-- * License version 2.1, as published by the Free Software Foundation.
-- *
-- * This library 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 for more details.
-- *
-- * You should have received a copy of the GNU Lesser General Public
-- * License along with this library; if not, write to the Free Software
-- * Foundation, Inc., 59 Temple Place, Suite 330, Boston,
-- * MA 02111-1307 USA
-- *
-- ************************************************************************/
--#ifndef SC_VBA_COMMANDBARCONTROLS_HXX
--#define SC_VBA_COMMANDBARCONTROLS_HXX
--
--#include <ooo/vba/XCommandBarControls.hpp>
--
--#include "vbahelperinterface.hxx"
--#include "vbacommandbar.hxx"
--#include "vbacollectionimpl.hxx"
--
--class ScVbaCommandBarControl;
--
--typedef CollTestImplHelper< ov::XCommandBarControls > CommandBarControls_BASE;
--
--class ScVbaCommandBarControls : public CommandBarControls_BASE
--{
--private:
-- sal_Bool m_bIsMenu;
-- sal_Bool m_bHasElements;
-- ScVbaCommandBar* m_pCommandBar;
-- ScVbaCommandBarControl* m_pCommandBarControl;
-- css::uno::Reference< ov::XHelperInterface > m_xParentHardRef;
-- css::uno::Reference< css::ui::XUIConfigurationManager > m_xUICfgManager;
-- css::uno::Reference< css::ui::XUIConfigurationPersistence > m_xUICfgPers;
-- css::uno::Reference< css::container::XIndexContainer > m_xBarSettings;
-- css::uno::Reference< css::container::XIndexContainer > m_xCurrentSettings;
--
--public:
-- ScVbaCommandBarControls( const css::uno::Reference< ov::XHelperInterface > xParent, const css::uno::Reference< css::uno::XComponentContext > xContext, const css::uno::Reference< css::container::XIndexAccess > xIndexAccess ) throw( css::uno::RuntimeException );
-- css::uno::Reference< css::ui::XUIConfigurationManager > GetUICfgManager() { return m_xUICfgManager; };
-- css::uno::Reference< css::ui::XUIConfigurationPersistence > GetUICfgPers() { return m_xUICfgPers; };
-- css::uno::Reference< css::container::XIndexContainer > GetBarSettings() { return m_xBarSettings; };
-- sal_Bool IsMenu() { return m_bIsMenu; };
-- ScVbaCommandBar* GetParentCommandBar() { return m_pCommandBar; };
-- ScVbaCommandBarControl* GetParentCommandBarControl() { return m_pCommandBarControl; };
-- rtl::OUString GetParentToolBarName()
-- {
-- if( m_pCommandBar ) return m_pCommandBar->GetToolBarName();
-- else return rtl::OUString();
-- }
-- rtl::OUString GetControlNameByIndex( const sal_Int32 nIndex ) throw ( css::uno::RuntimeException );
--
-- // Attributes
-- virtual ::sal_Int32 SAL_CALL getCount() throw (css::uno::RuntimeException);
-- // XEnumerationAccess
-- virtual css::uno::Type SAL_CALL getElementType() throw (css::uno::RuntimeException);
-- virtual css::uno::Reference< css::container::XEnumeration > SAL_CALL createEnumeration() throw (css::uno::RuntimeException);
-- virtual css::uno::Any createCollectionObject( const css::uno::Any& aSource );
--
-- // Methods
-- virtual css::uno::Any SAL_CALL Item( const css::uno::Any& Index, const css::uno::Any& /*Index2*/ ) throw (css::uno::RuntimeException);
-- virtual css::uno::Reference< ov::XCommandBarControl > SAL_CALL Add( const css::uno::Any& Type, const css::uno::Any& Id, const css::uno::Any& Parameter, const css::uno::Any& Before, const css::uno::Any& Temporary ) throw (css::script::BasicErrorException, css::uno::RuntimeException);
-- // XHelperInterface
-- virtual rtl::OUString& getServiceImplName();
-- virtual css::uno::Sequence<rtl::OUString> getServiceNames();
--};
--
--#endif//SC_VBA_COMMANDBARCONTROLS_HXX
---- sc/source/ui/vba/vbacommandbars.cxx.old 2009-04-06 16:42:00.000000000 +0000
-+++ sc/source/ui/vba/vbacommandbars.cxx 1970-01-01 00:00:00.000000000 +0000
-@@ -1,261 +0,0 @@
--/*************************************************************************
-- *
-- * OpenOffice.org - a multi-platform office productivity suite
-- *
-- * $RCSfile$
-- *
-- * $Revision$
-- *
-- * last change: $Author$ $Date$
-- *
-- * The Contents of this file are made available subject to
-- * the terms of GNU Lesser General Public License Version 2.1.
-- *
-- *
-- * GNU Lesser General Public License Version 2.1
-- * =============================================
-- * Copyright 2005 by Sun Microsystems, Inc.
-- * 901 San Antonio Road, Palo Alto, CA 94303, USA
-- *
-- * This library is free software; you can redistribute it and/or
-- * modify it under the terms of the GNU Lesser General Public
-- * License version 2.1, as published by the Free Software Foundation.
-- *
-- * This library 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 for more details.
-- *
-- * You should have received a copy of the GNU Lesser General Public
-- * License along with this library; if not, write to the Free Software
-- * Foundation, Inc., 59 Temple Place, Suite 330, Boston,
-- * MA 02111-1307 USA
-- *
-- ************************************************************************/
--#include <com/sun/star/lang/XServiceInfo.hpp>
--#include <com/sun/star/frame/XDesktop.hpp>
--#include <com/sun/star/container/XNameAccess.hpp>
--
--#include "vbacommandbars.hxx"
--#include "vbacommandbar.hxx"
--
--using namespace com::sun::star;
--using namespace ooo::vba;
--
--typedef ::cppu::WeakImplHelper1< container::XEnumeration > CommandBarEnumeration_BASE;
--
--static rtl::OUString sSpreadsheetDocumentUrl( rtl::OUString::createFromAscii( "com.sun.star.sheet.SpreadsheetDocument" ) );
--static rtl::OUString sTextDocumentUrl( rtl::OUString::createFromAscii( "com.sun.star.text.TextDocument" ) );
--static rtl::OUString sWindowStateConfUrl( rtl::OUString::createFromAscii( "com.sun.star.ui.WindowStateConfiguration" ) );
--
--class CommandBarEnumeration : public CommandBarEnumeration_BASE
--{
-- uno::Reference< uno::XComponentContext > m_xContext;
-- uno::Reference< XCommandBars > m_xCommandBars;
-- uno::Sequence< rtl::OUString > m_sNames;
-- sal_Int32 m_nCurrentPosition;
--public:
-- CommandBarEnumeration( const uno::Reference< uno::XComponentContext > xContext, const uno::Reference< XCommandBars > xCommandBars, const uno::Sequence< rtl::OUString > sNames ) : m_xContext( xContext ), m_xCommandBars( xCommandBars ), m_sNames( sNames ), m_nCurrentPosition( 0 )
-- {
-- }
-- virtual sal_Bool SAL_CALL hasMoreElements() throw ( uno::RuntimeException )
-- {
-- if( m_nCurrentPosition < m_sNames.getLength() )
-- return sal_True;
-- return sal_False;
-- }
-- virtual uno::Any SAL_CALL nextElement() throw ( container::NoSuchElementException, lang::WrappedTargetException, uno::RuntimeException )
-- {
-- if( hasMoreElements() )
-- {
-- rtl::OUString sName( m_sNames[ m_nCurrentPosition ] );
-- m_nCurrentPosition = m_nCurrentPosition + 1;
-- if( sName.indexOf( rtl::OUString::createFromAscii("private:resource/toolbar/") ) != -1 )
-- {
-- sal_Int32 nLastIndex = sName.lastIndexOf( rtl::OUString::createFromAscii( "/" ) );
-- if( ( nLastIndex != -1 ) && ( ( nLastIndex + 1 ) < sName.getLength() ) )
-- {
-- sName = sName.copy( nLastIndex + 1);
-- if( sName.getLength() > 0 )
-- {
-- uno::Reference< XHelperInterface > xHelperInterface( m_xCommandBars, uno::UNO_QUERY_THROW );
-- uno::Reference< XCommandBar > xCommandBar( new ScVbaCommandBar( xHelperInterface, m_xContext, sName, sal_True, sal_False ) );
-- if( xCommandBar.is() )
-- return uno::makeAny( xCommandBar );
-- else
-- return nextElement();
-- }
-- else
-- return nextElement();
-- }
-- }
-- else
-- return nextElement();
-- }
-- else
-- throw container::NoSuchElementException();
-- return uno::Any();
-- }
--};
--
--
--ScVbaCommandBars::ScVbaCommandBars( const uno::Reference< XHelperInterface > xParent, const uno::Reference< uno::XComponentContext > xContext, const uno::Reference< container::XIndexAccess > xIndexAccess ) : CommandBars_BASE( xParent, xContext, xIndexAccess )
--{
-- retrieveObjects();
--}
--void
--ScVbaCommandBars::retrieveObjects() throw ( uno::RuntimeException )
--{
-- uno::Reference< lang::XServiceInfo > xServiceInfo( getCurrentDocument(), uno::UNO_QUERY_THROW );
-- if( xServiceInfo->supportsService( sSpreadsheetDocumentUrl ) )
-- {
-- m_sModuleName = sSpreadsheetDocumentUrl;
-- }
-- else if( xServiceInfo->supportsService( sTextDocumentUrl ) )
-- {
-- m_sModuleName = sTextDocumentUrl;
-- }
-- else
-- throw uno::RuntimeException( rtl::OUString::createFromAscii( "Unsupported Document" ), uno::Reference< uno::XInterface >() );
--
-- uno::Reference < lang::XMultiServiceFactory > xMSF( mxContext->getServiceManager(), uno::UNO_QUERY_THROW );
-- uno::Reference < container::XNameAccess > xNameAccess( xMSF->createInstance( sWindowStateConfUrl ), uno::UNO_QUERY_THROW );
-- m_xNameAccess.set( xNameAccess->getByName( m_sModuleName ), uno::UNO_QUERY_THROW );
--}
--
--// XEnumerationAccess
--uno::Type SAL_CALL
--ScVbaCommandBars::getElementType() throw ( uno::RuntimeException )
--{
-- return XCommandBars::static_type( 0 );
--}
--uno::Reference< container::XEnumeration >
--ScVbaCommandBars::createEnumeration() throw ( uno::RuntimeException )
--{
-- return uno::Reference< container::XEnumeration >( new CommandBarEnumeration( mxContext, this, m_xNameAccess->getElementNames() ) );
--}
--
--uno::Any
--ScVbaCommandBars::createCollectionObject( const uno::Any& aSource )
--{
-- // aSource should be a name at this time, because of the class is API wrapper.
-- rtl::OUString sToolBarName;
-- if( aSource >>= sToolBarName )
-- {
-- sToolBarName = sToolBarName.toAsciiLowerCase();
-- if( sToolBarName.equalsIgnoreAsciiCase( rtl::OUString::createFromAscii("Worksheet Menu Bar") ) )
-- {
-- return uno::makeAny( uno::Reference< XCommandBar > ( new ScVbaCommandBar( this, mxContext, 0 ) ) );
-- }
-- else if( sToolBarName.equalsIgnoreAsciiCase( rtl::OUString::createFromAscii("Menu Bar") ) )
-- {
-- return uno::makeAny( uno::Reference< XCommandBar > ( new ScVbaCommandBar( this, mxContext, 1 ) ) );
-- }
-- else if( checkToolBarExist( sToolBarName ) )
-- {
-- return uno::makeAny( uno::Reference< XCommandBar > (new ScVbaCommandBar( this, mxContext, sToolBarName, sal_True, sal_False ) ) );
-- }
-- }
-- return uno::Any();
--}
--
--// XCommandBars
--uno::Reference< XCommandBar > SAL_CALL
--ScVbaCommandBars::Add( const css::uno::Any& Name, const css::uno::Any& /*Position*/, const css::uno::Any& /*MenuBar*/, const css::uno::Any& Temporary ) throw (css::script::BasicErrorException, css::uno::RuntimeException)
--{
-- // Position - MsoBar MenuBar - sal_Bool
-- // Currently only the Name is supported.
-- rtl::OUString sName;
-- if( !( Name >>= sName ) )
-- {
-- sName = rtl::OUString::createFromAscii("Custom1");
-- }
-- sal_Bool bTemporary = false;
-- if( !( Temporary >>= bTemporary ) )
-- {
-- bTemporary = sal_True;
-- }
-- return uno::Reference< XCommandBar >( new ScVbaCommandBar( this, mxContext, sName.toAsciiLowerCase(), bTemporary, sal_True ) );
--}
--sal_Int32 SAL_CALL
--ScVbaCommandBars::getCount() throw(css::uno::RuntimeException)
--{
-- // Filter out all toolbars from the window collection
-- sal_Int32 nCount = 0;
-- uno::Sequence< ::rtl::OUString > allNames = m_xNameAccess->getElementNames();
-- for( sal_Int32 i = 0; i < allNames.getLength(); i++ )
-- {
-- if(allNames[i].indexOf( rtl::OUString::createFromAscii("private:resource/toolbar/") ) != -1 )
-- {
-- nCount++;
-- }
-- }
-- return nCount;
--}
--
--// ScVbaCollectionBaseImpl
--uno::Any SAL_CALL
--ScVbaCommandBars::Item( const uno::Any& aIndex, const uno::Any& /*aIndex2*/ ) throw( uno::RuntimeException )
--{
-- if( aIndex.getValueTypeClass() == uno::TypeClass_STRING )
-- {
-- return createCollectionObject( aIndex );
-- }
--
-- // hardcode if "aIndex = 1" that would return "main menu".
-- sal_Int16 nIndex = 0;
-- aIndex >>= nIndex;
-- if( nIndex == 1 )
-- {
-- uno::Any aSource;
-- if( m_sModuleName.equalsIgnoreAsciiCase( sSpreadsheetDocumentUrl ) )
-- aSource <<= rtl::OUString::createFromAscii( "Worksheet Menu Bar" );
-- else if( m_sModuleName.equalsIgnoreAsciiCase( sTextDocumentUrl ) )
-- aSource <<= rtl::OUString::createFromAscii( "Menu Bar" );
-- if( aSource.hasValue() )
-- return createCollectionObject( aSource );
-- }
-- return uno::Any();
--}
--
--sal_Bool
--ScVbaCommandBars::checkToolBarExist( rtl::OUString sToolBarName )
--{
-- CommandBarNameMap::const_iterator iter = mCommandBarNameMap.find( sToolBarName.toAsciiLowerCase() );
-- if( iter != mCommandBarNameMap.end() )
-- {
-- return sal_True;
-- }
-- uno::Sequence< ::rtl::OUString > allNames = m_xNameAccess->getElementNames();
-- for( sal_Int32 i = 0; i < allNames.getLength(); i++ )
-- {
-- if(allNames[i].indexOf( rtl::OUString::createFromAscii("private:resource/toolbar/") ) != -1 )
-- {
-- if( allNames[i].indexOf( sToolBarName ) != -1 )
-- {
-- return sal_True;
-- }
-- }
-- }
-- return sal_False;
--}
--
--// XHelperInterface
--rtl::OUString&
--ScVbaCommandBars::getServiceImplName()
--{
-- static rtl::OUString sImplName( RTL_CONSTASCII_USTRINGPARAM("ScVbaCommandBars") );
-- return sImplName;
--}
--uno::Sequence<rtl::OUString>
--ScVbaCommandBars::getServiceNames()
--{
-- static uno::Sequence< rtl::OUString > aServiceNames;
-- if ( aServiceNames.getLength() == 0 )
-- {
-- aServiceNames.realloc( 1 );
-- aServiceNames[ 0 ] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.CommandBars" ) );
-- }
-- return aServiceNames;
--}
--
---- sc/source/ui/vba/vbacommandbars.hxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbacommandbars.hxx 1970-01-01 00:00:00.000000000 +0000
-@@ -1,79 +0,0 @@
--/*************************************************************************
-- *
-- * OpenOffice.org - a multi-platform office productivity suite
-- *
-- * $RCSfile$
-- *
-- * $Revision$
-- *
-- * last change: $Author$ $Date$
-- *
-- * The Contents of this file are made available subject to
-- * the terms of GNU Lesser General Public License Version 2.1.
-- *
-- *
-- * GNU Lesser General Public License Version 2.1
-- * =============================================
-- * Copyright 2005 by Sun Microsystems, Inc.
-- * 901 San Antonio Road, Palo Alto, CA 94303, USA
-- *
-- * This library is free software; you can redistribute it and/or
-- * modify it under the terms of the GNU Lesser General Public
-- * License version 2.1, as published by the Free Software Foundation.
-- *
-- * This library 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 for more details.
-- *
-- * You should have received a copy of the GNU Lesser General Public
-- * License along with this library; if not, write to the Free Software
-- * Foundation, Inc., 59 Temple Place, Suite 330, Boston,
-- * MA 02111-1307 USA
-- *
-- ************************************************************************/
--#ifndef SC_VBA_COMMANDBARS_HXX
--#define SC_VBA_COMMANDBARS_HXX
--
--#include <ooo/vba/XCommandBar.hpp>
--#include <ooo/vba/XCommandBars.hpp>
--#include <com/sun/star/container/XNameAccess.hpp>
--
--#include <cppuhelper/implbase1.hxx>
--
--#include "vbahelperinterface.hxx"
--#include "vbacollectionimpl.hxx"
--
--typedef CollTestImplHelper< ov::XCommandBars > CommandBars_BASE;
--
--class ScVbaCommandBars : public CommandBars_BASE
--{
--private:
-- css::uno::Reference< css::container::XNameAccess > m_xNameAccess;
-- rtl::OUString m_sModuleName;
-- void retrieveObjects() throw( css::uno::RuntimeException );
--public:
-- ScVbaCommandBars( const css::uno::Reference< ov::XHelperInterface > xParent, const css::uno::Reference< css::uno::XComponentContext > xContext, const css::uno::Reference< css::container::XIndexAccess > xIndexAccess );
--
-- sal_Bool checkToolBarExist( rtl::OUString sToolBarName );
-- rtl::OUString GetModuleName(){ return m_sModuleName; };
-- css::uno::Reference< css::container::XNameAccess > GetWindows()
-- {
-- retrieveObjects();
-- return m_xNameAccess;
-- };
-- // XCommandBars
-- virtual css::uno::Reference< ov::XCommandBar > SAL_CALL Add( const css::uno::Any& Name, const css::uno::Any& Position, const css::uno::Any& MenuBar, const css::uno::Any& Temporary ) throw (css::script::BasicErrorException, css::uno::RuntimeException);
-- // XEnumerationAccess
-- virtual css::uno::Type SAL_CALL getElementType() throw (css::uno::RuntimeException);
-- virtual css::uno::Reference< css::container::XEnumeration > SAL_CALL createEnumeration() throw (css::uno::RuntimeException);
-- virtual css::uno::Any createCollectionObject( const css::uno::Any& aSource );
--
-- virtual sal_Int32 SAL_CALL getCount() throw(css::uno::RuntimeException);
-- virtual css::uno::Any SAL_CALL Item( const css::uno::Any& aIndex, const css::uno::Any& /*aIndex2*/ ) throw( css::uno::RuntimeException);
-- // XHelperInterface
-- virtual rtl::OUString& getServiceImplName();
-- virtual css::uno::Sequence<rtl::OUString> getServiceNames();
--};
--
--#endif//SC_VBA_COMMANDBARS_HXX
---- sc/source/ui/vba/vbacomment.hxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbacomment.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -39,7 +39,7 @@
- #include <com/sun/star/table/XCellRange.hpp>
- #include <com/sun/star/uno/XComponentContext.hpp>
-
--#include "vbahelperinterface.hxx"
-+#include <vbahelper/vbahelperinterface.hxx>
-
- typedef InheritedHelperInterfaceImpl1< ov::excel::XComment > ScVbaComment_BASE;
-
---- sc/source/ui/vba/vbacomments.hxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbacomments.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -34,8 +34,8 @@
-
- #include <ooo/vba/excel/XComments.hpp>
-
--#include "vbahelper.hxx"
--#include "vbacollectionimpl.hxx"
-+#include "excelvbahelper.hxx"
-+#include <vbahelper/vbacollectionimpl.hxx>
- #include "vbacomment.hxx"
-
- typedef CollTestImplHelper< ov::excel::XComments > ScVbaComments_BASE;
---- sc/source/ui/vba/vbacondition.hxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbacondition.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -31,7 +31,7 @@
- #define SC_VBA_CONDITION_HXX
- #include <com/sun/star/sheet/XSheetCondition.hpp>
- #include <com/sun/star/sheet/XCellRangeAddressable.hpp>
--#include "vbahelperinterface.hxx"
-+#include <vbahelper/vbahelperinterface.hxx>
- #include <com/sun/star/sheet/ConditionOperator.hpp>
-
- template< typename Ifc1 >
---- sc/source/ui/vba/vbacontrol.cxx
-+++ sc/source/ui/vba/vbacontrol.cxx
-@@ -1,468 +0,0 @@
--/*************************************************************************
-- *
-- * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-- *
-- * Copyright 2008 by Sun Microsystems, Inc.
-- *
-- * OpenOffice.org - a multi-platform office productivity suite
-- *
-- * $RCSfile: vbacontrol.cxx,v $
-- * $Revision: 1.3 $
-- *
-- * 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 <com/sun/star/form/FormComponentType.hpp>
--#include <com/sun/star/awt/XControlModel.hpp>
--#include <com/sun/star/awt/XControl.hpp>
--#include <com/sun/star/awt/XWindow2.hpp>
--#include <com/sun/star/lang/XEventListener.hpp>
--#include <com/sun/star/drawing/XShape.hpp>
--#include <com/sun/star/frame/XModel.hpp>
--#include <com/sun/star/view/XControlAccess.hpp>
--#include <com/sun/star/container/XChild.hpp>
--#include <com/sun/star/form/binding/XBindableValue.hpp>
--#include <com/sun/star/form/binding/XListEntrySink.hpp>
--#include <com/sun/star/table/CellAddress.hpp>
--#include <com/sun/star/table/CellRangeAddress.hpp>
--#ifdef VBA_OOBUILD_HACK
--#include <svtools/bindablecontrolhelper.hxx>
--#endif
--#include"vbacontrol.hxx"
--#include"vbacombobox.hxx"
--#include "vbabutton.hxx"
--#include "vbalabel.hxx"
--#include "vbatextbox.hxx"
--#include "vbaradiobutton.hxx"
--#include "vbalistbox.hxx"
--#include "vbatogglebutton.hxx"
--#include "vbacheckbox.hxx"
--#include "vbaframe.hxx"
--#include "vbascrollbar.hxx"
--#include "vbaprogressbar.hxx"
--#include "vbamultipage.hxx"
--#include "vbaspinbutton.hxx"
--#include "vbaimage.hxx"
--
--
--using namespace com::sun::star;
--using namespace ooo::vba;
--
--uno::Reference< css::awt::XWindowPeer >
--ScVbaControl::getWindowPeer() throw (uno::RuntimeException)
--{
-- uno::Reference< drawing::XControlShape > xControlShape( m_xControl, uno::UNO_QUERY );
--
-- uno::Reference< awt::XControlModel > xControlModel;
-- uno::Reference< css::awt::XWindowPeer > xWinPeer;
-- if ( !xControlShape.is() )
-- {
-- // would seem to be a Userform control
-- uno::Reference< awt::XControl > xControl( m_xControl, uno::UNO_QUERY_THROW );
-- xWinPeer = xControl->getPeer();
-- return xWinPeer;
-- }
-- // form control
-- xControlModel.set( xControlShape->getControl(), uno::UNO_QUERY_THROW );
--
-- uno::Reference< view::XControlAccess > xControlAccess( m_xModel->getCurrentController(), uno::UNO_QUERY_THROW );
-- try
-- {
-- uno::Reference< awt::XControl > xControl( xControlAccess->getControl( xControlModel ), uno::UNO_QUERY );
-- xWinPeer = xControl->getPeer();
-- }
-- catch( uno::Exception )
-- {
-- throw uno::RuntimeException( rtl::OUString::createFromAscii( "The Control does not exsit" ),
-- uno::Reference< uno::XInterface >() );
-- }
-- return xWinPeer;
--}
--
--//ScVbaControlListener
--class ScVbaControlListener: public cppu::WeakImplHelper1< lang::XEventListener >
--{
--private:
-- ScVbaControl *pControl;
--public:
-- ScVbaControlListener( ScVbaControl *pTmpControl );
-- virtual ~ScVbaControlListener();
-- virtual void SAL_CALL disposing( const lang::EventObject& rEventObject ) throw( uno::RuntimeException );
--};
--
--ScVbaControlListener::ScVbaControlListener( ScVbaControl *pTmpControl ): pControl( pTmpControl )
--{
--}
--
--ScVbaControlListener::~ScVbaControlListener()
--{
--}
--
--void SAL_CALL
--ScVbaControlListener::disposing( const lang::EventObject& ) throw( uno::RuntimeException )
--{
-- if( pControl )
-- {
-- pControl->removeResouce();
-- pControl = NULL;
-- }
--}
--
--//ScVbaControl
--
--ScVbaControl::ScVbaControl( const uno::Reference< XHelperInterface >& xParent, const uno::Reference< uno::XComponentContext >& xContext, const uno::Reference< ::uno::XInterface >& xControl, const css::uno::Reference< css::frame::XModel >& xModel, AbstractGeometryAttributes* pGeomHelper ) : ControlImpl_BASE( xParent, xContext ), m_xControl( xControl ), m_xModel( xModel )
--{
-- //add listener
-- m_xEventListener.set( new ScVbaControlListener( this ) );
-- setGeometryHelper( pGeomHelper );
-- uno::Reference< lang::XComponent > xComponent( m_xControl, uno::UNO_QUERY_THROW );
-- xComponent->addEventListener( m_xEventListener );
--
-- //init m_xProps
-- uno::Reference< drawing::XControlShape > xControlShape( m_xControl, uno::UNO_QUERY ) ;
-- uno::Reference< awt::XControl> xUserFormControl( m_xControl, uno::UNO_QUERY ) ;
-- if ( xControlShape.is() ) // form control
-- m_xProps.set( xControlShape->getControl(), uno::UNO_QUERY_THROW );
-- else if ( xUserFormControl.is() ) // userform control
-- m_xProps.set( xUserFormControl->getModel(), uno::UNO_QUERY_THROW );
--}
--
--ScVbaControl::~ScVbaControl()
--{
-- if( m_xControl.is() )
--{
-- uno::Reference< lang::XComponent > xComponent( m_xControl, uno::UNO_QUERY_THROW );
-- xComponent->removeEventListener( m_xEventListener );
--}
--}
--
--void
--ScVbaControl::setGeometryHelper( AbstractGeometryAttributes* pHelper )
--{
-- mpGeometryHelper.reset( pHelper );
--}
--
--void ScVbaControl::removeResouce() throw( uno::RuntimeException )
--{
-- uno::Reference< lang::XComponent > xComponent( m_xControl, uno::UNO_QUERY_THROW );
-- xComponent->removeEventListener( m_xEventListener );
-- m_xControl= NULL;
-- m_xProps = NULL;
--}
--
--//In design model has different behavior
--sal_Bool SAL_CALL ScVbaControl::getEnabled() throw (uno::RuntimeException)
--{
-- uno::Any aValue = m_xProps->getPropertyValue
-- (rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "Enabled" ) ) );
-- sal_Bool bRet = false;
-- aValue >>= bRet;
-- return bRet;
--}
--
--void SAL_CALL ScVbaControl::setEnabled( sal_Bool bVisible ) throw (uno::RuntimeException)
--{
-- uno::Any aValue( bVisible );
-- m_xProps->setPropertyValue
-- (rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "Enabled" ) ), aValue);
--
--}
--
--sal_Bool SAL_CALL ScVbaControl::getVisible() throw (uno::RuntimeException)
--{
-- sal_Bool bVisible = sal_False;
-- m_xProps->getPropertyValue(rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "EnableVisible" ) ) ) >>= bVisible;
-- return bVisible;
--}
--
--void SAL_CALL ScVbaControl::setVisible( sal_Bool bVisible ) throw (uno::RuntimeException)
--{
-- m_xProps->setPropertyValue
-- (rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "EnableVisible" ) ), uno::makeAny( bVisible ) );
--}
--double SAL_CALL ScVbaControl::getHeight() throw (uno::RuntimeException)
--{
-- return mpGeometryHelper->getHeight();
--}
--void SAL_CALL ScVbaControl::setHeight( double _height ) throw (uno::RuntimeException)
--{
-- mpGeometryHelper->setHeight( _height );
--}
--
--double SAL_CALL ScVbaControl::getWidth() throw (uno::RuntimeException)
--{
-- return mpGeometryHelper->getWidth();
--}
--void SAL_CALL ScVbaControl::setWidth( double _width ) throw (uno::RuntimeException)
--{
-- mpGeometryHelper->setWidth( _width );
--}
--
--double SAL_CALL
--ScVbaControl::getLeft() throw (uno::RuntimeException)
--{
-- return mpGeometryHelper->getLeft();
--}
--
--void SAL_CALL
--ScVbaControl::setLeft( double _left ) throw (uno::RuntimeException)
--{
-- mpGeometryHelper->setLeft( _left );
--
--}
--
--double SAL_CALL
--ScVbaControl::getTop() throw (uno::RuntimeException)
--{
-- return mpGeometryHelper->getTop();
--}
--
--void SAL_CALL
--ScVbaControl::setTop( double _top ) throw (uno::RuntimeException)
--{
-- mpGeometryHelper->setTop( _top );
--}
--
--uno::Reference< uno::XInterface > SAL_CALL
--ScVbaControl::getObject() throw (uno::RuntimeException)
--{
-- uno::Reference< msforms::XControl > xRet( this );
-- return xRet;
--}
--
--void SAL_CALL ScVbaControl::SetFocus() throw (uno::RuntimeException)
--{
-- uno::Reference< awt::XWindow > xWin( m_xControl, uno::UNO_QUERY_THROW );
-- xWin->setFocus();
--}
--
--rtl::OUString SAL_CALL
--ScVbaControl::getControlSource() throw (uno::RuntimeException)
--{
--// #FIXME I *hate* having these upstream differences
--// but this is necessary until I manage to upstream other
--// dependant parts
--#ifdef VBA_OOBUILD_HACK
-- rtl::OUString sControlSource;
-- uno::Reference< form::binding::XBindableValue > xBindable( m_xProps, uno::UNO_QUERY );
-- if ( xBindable.is() )
-- {
-- try
-- {
-- uno::Reference< lang::XMultiServiceFactory > xFac( m_xModel, uno::UNO_QUERY_THROW );
-- uno::Reference< beans::XPropertySet > xConvertor( xFac->createInstance( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "com.sun.star.table.CellAddressConversion" ))), uno::UNO_QUERY );
-- uno::Reference< beans::XPropertySet > xProps( xBindable->getValueBinding(), uno::UNO_QUERY_THROW );
-- table::CellAddress aAddress;
-- xProps->getPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("BoundCell") ) ) >>= aAddress;
-- xConvertor->setPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("Address") ), uno::makeAny( aAddress ) );
-- xConvertor->getPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("XL_A1_Representation") ) ) >>= sControlSource;
-- }
-- catch( uno::Exception& )
-- {
-- }
-- }
-- return sControlSource;
--#else
-- throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("getControlSource not supported") ), uno::Reference< uno::XInterface >()); // not supported
--#endif
--}
--
--void SAL_CALL
--ScVbaControl::setControlSource( const rtl::OUString& _controlsource ) throw (uno::RuntimeException)
--{
--#ifdef VBA_OOBUILD_HACK
-- rtl::OUString sEmpty;
-- svt::BindableControlHelper::ApplyListSourceAndBindableData( m_xModel, m_xProps, _controlsource, sEmpty );
--#else
-- throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("setControlSource not supported ") ).concat( _controlsource ), uno::Reference< uno::XInterface >()); // not supported
--#endif
--}
--
--rtl::OUString SAL_CALL
--ScVbaControl::getRowSource() throw (uno::RuntimeException)
--{
--#ifdef VBA_OOBUILD_HACK
-- rtl::OUString sRowSource;
-- uno::Reference< form::binding::XListEntrySink > xListSink( m_xProps, uno::UNO_QUERY );
-- if ( xListSink.is() )
-- {
-- try
-- {
-- uno::Reference< lang::XMultiServiceFactory > xFac( m_xModel, uno::UNO_QUERY_THROW );
-- uno::Reference< beans::XPropertySet > xConvertor( xFac->createInstance( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "com.sun.star.table.CellRangeAddressConversion" ))), uno::UNO_QUERY );
--
-- uno::Reference< beans::XPropertySet > xProps( xListSink->getListEntrySource(), uno::UNO_QUERY_THROW );
-- table::CellRangeAddress aAddress;
-- xProps->getPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("CellRange") ) ) >>= aAddress;
-- xConvertor->setPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("Address")), uno::makeAny( aAddress ) );
-- xConvertor->getPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("XL_A1_Representation") ) ) >>= sRowSource;
-- }
-- catch( uno::Exception& )
-- {
-- }
-- }
-- return sRowSource;
--#else
-- throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("getRowSource not supported") ), uno::Reference< uno::XInterface >()); // not supported
--#endif
--}
--
--void SAL_CALL
--ScVbaControl::setRowSource( const rtl::OUString& _rowsource ) throw (uno::RuntimeException)
--{
--#ifdef VBA_OOBUILD_HACK
-- rtl::OUString sEmpty;
-- svt::BindableControlHelper::ApplyListSourceAndBindableData( m_xModel, m_xProps, sEmpty, _rowsource );
--#else
-- throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("setRowSource not supported ") ).concat( _rowsource ), uno::Reference< uno::XInterface >()); // not supported
--#endif
--}
--
--rtl::OUString SAL_CALL
--ScVbaControl::getName() throw (uno::RuntimeException)
--{
-- rtl::OUString sName;
-- m_xProps->getPropertyValue
-- (rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "Name" ) ) ) >>= sName;
-- return sName;
--
--}
--
--void SAL_CALL
--ScVbaControl::setName( const rtl::OUString& _name ) throw (uno::RuntimeException)
--{
-- m_xProps->setPropertyValue
-- (rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "Name" ) ), uno::makeAny( _name ) );
-- }
--//ScVbaControlFactory
--
--ScVbaControlFactory::ScVbaControlFactory( const uno::Reference< uno::XComponentContext >& xContext, const uno::Reference< uno::XInterface >& xControl, const uno::Reference< frame::XModel >& xModel ): m_xContext( xContext ), m_xControl( xControl ), m_xModel( xModel )
--{
--}
--
--ScVbaControl* ScVbaControlFactory::createControl() throw (uno::RuntimeException)
--{
-- return createControl( m_xModel );
--}
--ScVbaControl* ScVbaControlFactory::createControl( const uno::Reference< uno::XInterface >& xParent ) throw (uno::RuntimeException)
--{
-- uno::Reference< drawing::XControlShape > xControlShape( m_xControl, uno::UNO_QUERY );
-- if ( xControlShape.is() ) // form controls
-- return createControl( xControlShape, xParent );
-- uno::Reference< awt::XControl > xControl( m_xControl, uno::UNO_QUERY );
-- if ( !xControl.is() )
-- throw uno::RuntimeException(); // really we should be more informative
-- return createControl( xControl, xParent );
--
--}
--
--ScVbaControl* ScVbaControlFactory::createControl(const uno::Reference< drawing::XControlShape >& xControlShape, const uno::Reference< uno::XInterface >& /*xParent*/ ) throw (uno::RuntimeException)
--{
-- uno::Reference< beans::XPropertySet > xProps( xControlShape->getControl(), uno::UNO_QUERY_THROW );
-- sal_Int32 nClassId = -1;
-- const static rtl::OUString sClassId( RTL_CONSTASCII_USTRINGPARAM("ClassId") );
-- xProps->getPropertyValue( sClassId ) >>= nClassId;
-- uno::Reference< XHelperInterface > xVbaParent; // #FIXME - should be worksheet I guess
-- switch( nClassId )
-- {
-- case form::FormComponentType::COMBOBOX:
-- return new ScVbaComboBox( xVbaParent, m_xContext, xControlShape, m_xModel, new ConcreteXShapeGeometryAttributes( m_xContext, uno::Reference< drawing::XShape >( xControlShape, uno::UNO_QUERY_THROW ) ) );
-- case form::FormComponentType::COMMANDBUTTON:
-- return new ScVbaButton( xVbaParent, m_xContext, xControlShape, m_xModel, new ConcreteXShapeGeometryAttributes( m_xContext, uno::Reference< drawing::XShape >( xControlShape, uno::UNO_QUERY_THROW ) ) );
-- case form::FormComponentType::FIXEDTEXT:
-- return new ScVbaLabel( xVbaParent, m_xContext, xControlShape, m_xModel, new ConcreteXShapeGeometryAttributes( m_xContext, uno::Reference< drawing::XShape >( xControlShape, uno::UNO_QUERY_THROW ) ) );
-- case form::FormComponentType::TEXTFIELD:
-- return new ScVbaTextBox( xVbaParent, m_xContext, xControlShape, m_xModel, new ConcreteXShapeGeometryAttributes( m_xContext, uno::Reference< drawing::XShape >( xControlShape, uno::UNO_QUERY_THROW ) ) );
-- case form::FormComponentType::RADIOBUTTON:
-- return new ScVbaRadioButton( xVbaParent, m_xContext, xControlShape, m_xModel, new ConcreteXShapeGeometryAttributes( m_xContext, uno::Reference< drawing::XShape >( xControlShape, uno::UNO_QUERY_THROW ) ) );
-- case form::FormComponentType::LISTBOX:
-- return new ScVbaListBox( xVbaParent, m_xContext, xControlShape, m_xModel, new ConcreteXShapeGeometryAttributes( m_xContext, uno::Reference< drawing::XShape >( xControlShape, uno::UNO_QUERY_THROW ) ) );
-- case form::FormComponentType::SPINBUTTON:
-- return new ScVbaSpinButton( xVbaParent, m_xContext, xControlShape, m_xModel, new ConcreteXShapeGeometryAttributes( m_xContext, uno::Reference< drawing::XShape >( xControlShape, uno::UNO_QUERY_THROW ) ) );
-- case form::FormComponentType::IMAGECONTROL:
-- return new ScVbaImage( xVbaParent, m_xContext, xControlShape, m_xModel, new ConcreteXShapeGeometryAttributes( m_xContext, uno::Reference< drawing::XShape >( xControlShape, uno::UNO_QUERY_THROW ) ) );
-- default:
-- throw uno::RuntimeException( rtl::OUString::createFromAscii(
-- "Donot support this Control Type." ), uno::Reference< uno::XInterface >() );
-- }
--}
--
--ScVbaControl* ScVbaControlFactory::createControl( const uno::Reference< awt::XControl >& xControl, const uno::Reference< uno::XInterface >& xParent ) throw (uno::RuntimeException)
--{
-- uno::Reference< beans::XPropertySet > xProps( xControl->getModel(), uno::UNO_QUERY_THROW );
-- uno::Reference< lang::XServiceInfo > xServiceInfo( xProps, uno::UNO_QUERY_THROW );
-- ScVbaControl* pControl = NULL;
-- uno::Reference< XHelperInterface > xVbaParent; // #FIXME - should be worksheet I guess
-- if ( xServiceInfo->supportsService( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("com.sun.star.awt.UnoControlCheckBoxModel") ) ) )
-- pControl = new ScVbaCheckbox( xVbaParent, m_xContext, xControl, m_xModel, new UserFormGeometryHelper( m_xContext, xControl ) );
-- else if ( xServiceInfo->supportsService( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("com.sun.star.awt.UnoControlRadioButtonModel") ) ) )
-- pControl = new ScVbaRadioButton( xVbaParent, m_xContext, xControl, m_xModel, new UserFormGeometryHelper( m_xContext, xControl ) );
-- else if ( xServiceInfo->supportsService( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("com.sun.star.awt.UnoControlEditModel") ) ) )
-- pControl = new ScVbaTextBox( xVbaParent, m_xContext, xControl, m_xModel, new UserFormGeometryHelper( m_xContext, xControl ), true );
-- else if ( xServiceInfo->supportsService( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("com.sun.star.awt.UnoControlButtonModel") ) ) )
-- {
-- sal_Bool bToggle = sal_False;
-- xProps->getPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("Toggle") ) ) >>= bToggle;
-- if ( bToggle )
-- pControl = new ScVbaToggleButton( xVbaParent, m_xContext, xControl, m_xModel, new UserFormGeometryHelper( m_xContext, xControl ) );
-- else
-- pControl = new ScVbaButton( xVbaParent, m_xContext, xControl, m_xModel, new UserFormGeometryHelper( m_xContext, xControl ) );
-- }
-- else if ( xServiceInfo->supportsService( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("com.sun.star.awt.UnoControlComboBoxModel") ) ) )
-- pControl = new ScVbaComboBox( xVbaParent, m_xContext, xControl, m_xModel, new UserFormGeometryHelper( m_xContext, xControl ), true );
-- else if ( xServiceInfo->supportsService( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("com.sun.star.awt.UnoControlListBoxModel") ) ) )
-- pControl = new ScVbaListBox( xVbaParent, m_xContext, xControl, m_xModel, new UserFormGeometryHelper( m_xContext, xControl ) );
-- else if ( xServiceInfo->supportsService( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("com.sun.star.awt.UnoControlFixedTextModel") ) ) )
-- pControl = new ScVbaLabel( xVbaParent, m_xContext, xControl, m_xModel, new UserFormGeometryHelper( m_xContext, xControl ) );
-- else if ( xServiceInfo->supportsService( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("com.sun.star.awt.UnoControlImageControlModel") ) ) )
-- pControl = new ScVbaImage( xVbaParent, m_xContext, xControl, m_xModel, new UserFormGeometryHelper( m_xContext, xControl ) );
-- else if ( xServiceInfo->supportsService( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("com.sun.star.awt.UnoControlProgressBarModel") ) ) )
-- pControl = new ScVbaProgressBar( xVbaParent, m_xContext, xControl, m_xModel, new UserFormGeometryHelper( m_xContext, xControl ) );
-- else if ( xServiceInfo->supportsService( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("com.sun.star.awt.UnoControlGroupBoxModel") ) ) )
-- pControl = new ScVbaFrame( xVbaParent, m_xContext, xControl, m_xModel, new UserFormGeometryHelper( m_xContext, xControl ) );
-- else if ( xServiceInfo->supportsService( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("com.sun.star.awt.UnoControlScrollBarModel") ) ) )
-- pControl = new ScVbaScrollBar( xVbaParent, m_xContext, xControl, m_xModel, new UserFormGeometryHelper( m_xContext, xControl ) );
-- else if ( xServiceInfo->supportsService( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("com.sun.star.awt.UnoMultiPageModel") ) ) )
-- pControl = new ScVbaMultiPage( xVbaParent, m_xContext, xControl, m_xModel, new UserFormGeometryHelper( m_xContext, xControl ), xParent );
-- else if ( xServiceInfo->supportsService( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("com.sun.star.awt.UnoControlSpinButtonModel") ) ) )
-- pControl = new ScVbaSpinButton( xVbaParent, m_xContext, xControl, m_xModel, new UserFormGeometryHelper( m_xContext, xControl ) );
-- else
-- throw uno::RuntimeException( rtl::OUString::createFromAscii("Unsupported control " ), uno::Reference< uno::XInterface >() );
-- return pControl;
--}
--
--rtl::OUString&
--ScVbaControl::getServiceImplName()
--{
-- static rtl::OUString sImplName( RTL_CONSTASCII_USTRINGPARAM("ScVbaControl") );
-- return sImplName;
--}
--
--uno::Sequence< rtl::OUString >
--ScVbaControl::getServiceNames()
--{
-- static uno::Sequence< rtl::OUString > aServiceNames;
-- if ( aServiceNames.getLength() == 0 )
-- {
-- aServiceNames.realloc( 1 );
-- aServiceNames[ 0 ] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.excel.Control" ) );
-- }
-- return aServiceNames;
--}
--
--
---- sc/source/ui/vba/vbacontrol.hxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbacontrol.hxx 1970-01-01 00:00:00.000000000 +0000
-@@ -1,111 +0,0 @@
--/*************************************************************************
-- *
-- * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-- *
-- * Copyright 2008 by Sun Microsystems, Inc.
-- *
-- * OpenOffice.org - a multi-platform office productivity suite
-- *
-- * $RCSfile: vbacontrol.hxx,v $
-- * $Revision: 1.3 $
-- *
-- * 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.
-- *
-- ************************************************************************/
--#ifndef SC_VBA_CONTROL_HXX
--#define SC_VBA_CONTROL_HXX
--
--#include <cppuhelper/implbase1.hxx>
--#include <com/sun/star/beans/XPropertySet.hpp>
--#include <com/sun/star/uno/XComponentContext.hpp>
--#include <com/sun/star/script/XDefaultProperty.hpp>
--#include <com/sun/star/drawing/XControlShape.hpp>
--#include <com/sun/star/awt/XControl.hpp>
--#include <com/sun/star/awt/XWindowPeer.hpp>
--#include <ooo/vba/msforms/XControl.hpp>
--
--#include "vbahelper.hxx"
--#include "vbahelperinterface.hxx"
--
--//typedef ::cppu::WeakImplHelper1< ov::msforms::XControl > ControlImpl_BASE;
--typedef InheritedHelperInterfaceImpl1< ov::msforms::XControl > ControlImpl_BASE;
--
--class ScVbaControl : public ControlImpl_BASE
--{
--private:
-- com::sun::star::uno::Reference< com::sun::star::lang::XEventListener > m_xEventListener;
--protected:
-- std::auto_ptr< ov::AbstractGeometryAttributes > mpGeometryHelper;
-- css::uno::Reference< css::beans::XPropertySet > m_xProps;
-- css::uno::Reference< css::uno::XInterface > m_xControl;
-- css::uno::Reference< css::frame::XModel > m_xModel;
--
-- virtual css::uno::Reference< css::awt::XWindowPeer > getWindowPeer() throw (css::uno::RuntimeException);
--public:
-- ScVbaControl( const css::uno::Reference< ov::XHelperInterface >& xParent, const css::uno::Reference< css::uno::XComponentContext >& xContext,
-- const css::uno::Reference< css::uno::XInterface >& xControl, const css::uno::Reference< css::frame::XModel >& xModel, ov::AbstractGeometryAttributes* pHelper );
-- virtual ~ScVbaControl();
-- // This class will own the helper, so make sure it is allocated from
-- // the heap
-- void setGeometryHelper( ov::AbstractGeometryAttributes* pHelper );
-- // XControl
-- virtual sal_Bool SAL_CALL getEnabled() throw (css::uno::RuntimeException);
-- virtual void SAL_CALL setEnabled( sal_Bool _enabled ) throw (css::uno::RuntimeException);
-- virtual sal_Bool SAL_CALL getVisible() throw (css::uno::RuntimeException);
-- virtual void SAL_CALL setVisible( sal_Bool _visible ) throw (css::uno::RuntimeException);
-- virtual double SAL_CALL getHeight() throw (css::uno::RuntimeException);
-- virtual void SAL_CALL setHeight( double _height ) throw (css::uno::RuntimeException);
-- virtual double SAL_CALL getWidth() throw (css::uno::RuntimeException);
-- virtual void SAL_CALL setWidth( double _width ) throw (css::uno::RuntimeException);
-- virtual double SAL_CALL getLeft() throw (css::uno::RuntimeException);
-- virtual void SAL_CALL setLeft( double _left ) throw (css::uno::RuntimeException);
-- virtual double SAL_CALL getTop() throw (css::uno::RuntimeException);
-- virtual void SAL_CALL setTop( double _top ) throw (css::uno::RuntimeException);
-- virtual void SAL_CALL SetFocus( ) throw (css::uno::RuntimeException);
--
-- virtual css::uno::Reference< css::uno::XInterface > SAL_CALL getObject() throw (css::uno::RuntimeException);
-- virtual rtl::OUString SAL_CALL getControlSource() throw (css::uno::RuntimeException);
-- virtual void SAL_CALL setControlSource( const rtl::OUString& _controlsource ) throw (css::uno::RuntimeException);
-- virtual rtl::OUString SAL_CALL getRowSource() throw (css::uno::RuntimeException);
-- virtual void SAL_CALL setRowSource( const rtl::OUString& _rowsource ) throw (css::uno::RuntimeException);
-- virtual rtl::OUString SAL_CALL getName() throw (css::uno::RuntimeException);
-- virtual void SAL_CALL setName( const rtl::OUString& _name ) throw (css::uno::RuntimeException);
-- //remove resouce because ooo.vba.excel.XControl is a wrapper of com.sun.star.drawing.XControlShape
-- virtual void removeResouce() throw( css::uno::RuntimeException );
-- //XHelperInterface
-- virtual rtl::OUString& getServiceImplName();
-- virtual css::uno::Sequence<rtl::OUString> getServiceNames();
--};
--
--
--class ScVbaControlFactory
--{
--public:
-- ScVbaControlFactory( const css::uno::Reference< css::uno::XComponentContext >& xContext,
-- const css::uno::Reference< css::uno::XInterface >& xControl, const css::uno::Reference< css::frame::XModel >& xModel );
-- ScVbaControl* createControl() throw ( css::uno::RuntimeException );
-- ScVbaControl* createControl( const css::uno::Reference< css::uno::XInterface >& xParent ) throw ( css::uno::RuntimeException );
--private:
-- ScVbaControl* createControl( const css::uno::Reference< css::awt::XControl >&, const css::uno::Reference< css::uno::XInterface >& ) throw ( css::uno::RuntimeException );
-- ScVbaControl* createControl( const css::uno::Reference< css::drawing::XControlShape >&, const css::uno::Reference< css::uno::XInterface >& ) throw ( css::uno::RuntimeException );
-- css::uno::Reference< css::uno::XComponentContext > m_xContext;
-- css::uno::Reference< css::uno::XInterface > m_xControl;
-- css::uno::Reference< css::frame::XModel > m_xModel;
--};
--
--#endif//SC_VBA_CONTROL_HXX
---- sc/source/ui/vba/vbacontrols.cxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbacontrols.cxx 1970-01-01 00:00:00.000000000 +0000
-@@ -1,227 +0,0 @@
--/*************************************************************************
-- *
-- * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-- *
-- * Copyright 2008 by Sun Microsystems, Inc.
-- *
-- * OpenOffice.org - a multi-platform office productivity suite
-- *
-- * $RCSfile$
-- * $Revision$
-- *
-- * 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 "vbacontrols.hxx"
--#include "vbacontrol.hxx"
--#include <cppuhelper/implbase2.hxx>
--#include <com/sun/star/awt/XControlContainer.hpp>
--#include <hash_map>
--
--using namespace com::sun::star;
--using namespace ooo::vba;
--
--
--typedef ::cppu::WeakImplHelper2< container::XNameAccess, container::XIndexAccess > ArrayWrapImpl;
--
--typedef std::hash_map< rtl::OUString, sal_Int32, ::rtl::OUStringHash,
-- ::std::equal_to< ::rtl::OUString > > ControlIndexMap;
--typedef std::vector< uno::Reference< awt::XControl > > ControlVec;
--
--class ControlArrayWrapper : public ArrayWrapImpl
--{
-- uno::Reference< awt::XControlContainer > mxDialog;
-- uno::Sequence< ::rtl::OUString > msNames;
-- ControlVec mControls;
-- ControlIndexMap mIndices;
--
-- rtl::OUString getControlName( const uno::Reference< awt::XControl >& xCtrl )
-- {
-- uno::Reference< beans::XPropertySet > xProp( xCtrl->getModel(), uno::UNO_QUERY );
-- rtl::OUString sName;
-- xProp->getPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "Name" ) ) ) >>= sName;
-- return sName;
-- }
--
--public:
--
-- ControlArrayWrapper( const uno::Reference< awt::XControl >& xDialog )
-- {
-- mxDialog.set( xDialog, uno::UNO_QUERY_THROW );
-- uno::Sequence< uno::Reference< awt::XControl > > sXControls = mxDialog->getControls();
--
-- msNames.realloc( sXControls.getLength() );
-- for ( sal_Int32 i = 0; i < sXControls.getLength(); ++i )
-- {
-- uno::Reference< awt::XControl > xCtrl = sXControls[ i ];
-- msNames[ i ] = getControlName( xCtrl );
-- mControls.push_back( xCtrl );
-- mIndices[ msNames[ i ] ] = i;
-- }
-- }
--
-- // XElementAccess
-- virtual uno::Type SAL_CALL getElementType( ) throw (uno::RuntimeException)
-- {
-- return awt::XControl::static_type(0);
-- }
--
-- virtual ::sal_Bool SAL_CALL hasElements( ) throw (uno::RuntimeException)
-- {
-- return ( mControls.size() > 0 );
-- }
--
-- // XNameAcess
-- virtual uno::Any SAL_CALL getByName( const ::rtl::OUString& aName ) throw (container::NoSuchElementException, lang::WrappedTargetException, uno::RuntimeException)
-- {
-- if ( !hasByName( aName ) )
-- throw container::NoSuchElementException();
-- return getByIndex( mIndices[ aName ] );
-- }
--
-- virtual uno::Sequence< ::rtl::OUString > SAL_CALL getElementNames( ) throw (uno::RuntimeException)
-- {
-- return msNames;
-- }
--
-- virtual ::sal_Bool SAL_CALL hasByName( const ::rtl::OUString& aName ) throw (css::uno::RuntimeException)
-- {
-- ControlIndexMap::iterator it = mIndices.find( aName );
-- return it != mIndices.end();
-- }
--
-- // XElementAccess
-- virtual ::sal_Int32 SAL_CALL getCount( ) throw (css::uno::RuntimeException)
-- {
-- return mControls.size();
-- }
--
-- virtual uno::Any SAL_CALL getByIndex( ::sal_Int32 Index ) throw (lang::IndexOutOfBoundsException, lang::WrappedTargetException, uno::RuntimeException )
-- {
-- if ( Index < 0 || Index >= static_cast< sal_Int32 >( mControls.size() ) )
-- throw lang::IndexOutOfBoundsException();
-- return uno::makeAny( mControls[ Index ] );
-- }
--};
--
--
--class ControlsEnumWrapper : public EnumerationHelper_BASE
--{
-- uno::Reference<XHelperInterface > m_xParent;
-- uno::Reference<uno::XComponentContext > m_xContext;
-- uno::Reference<container::XIndexAccess > m_xIndexAccess;
-- uno::Reference<awt::XControl > m_xDlg;
-- sal_Int32 nIndex;
--
--public:
--
-- ControlsEnumWrapper( const uno::Reference< XHelperInterface >& xParent, const uno::Reference< uno::XComponentContext >& xContext, const uno::Reference< container::XIndexAccess >& xIndexAccess, const uno::Reference< awt::XControl >& xDlg ) : m_xParent( xParent ), m_xContext( xContext), m_xIndexAccess( xIndexAccess ), m_xDlg( xDlg ), nIndex( 0 ) {}
--
-- virtual ::sal_Bool SAL_CALL hasMoreElements( ) throw (uno::RuntimeException)
-- {
-- return ( nIndex < m_xIndexAccess->getCount() );
-- }
--
-- virtual uno::Any SAL_CALL nextElement( ) throw (container::NoSuchElementException, lang::WrappedTargetException, uno::RuntimeException)
-- {
-- if ( nIndex < m_xIndexAccess->getCount() )
-- {
-- uno::Reference< frame::XModel > xModel;
-- uno::Reference< uno::XInterface > xControl;
-- m_xIndexAccess->getByIndex( nIndex++ ) >>= xControl;
-- // Create control from awt::XControl
-- ScVbaControlFactory aFac( m_xContext, xControl, xModel );
-- uno::Reference< msforms::XControl > xVBAControl( aFac.createControl( m_xDlg->getModel() ) );
-- return uno::makeAny( xVBAControl );
-- }
-- throw container::NoSuchElementException();
-- }
--
--};
--
--
--uno::Reference<container::XIndexAccess >
--lcl_controlsWrapper( const uno::Reference< awt::XControl >& xDlg )
--{
-- return new ControlArrayWrapper( xDlg );
--}
--
--ScVbaControls::ScVbaControls( const uno::Reference< XHelperInterface >& xParent, const uno::Reference< uno::XComponentContext >& xContext,
-- const css::uno::Reference< awt::XControl >& xDialog )
-- : ControlsImpl_BASE( xParent, xContext, lcl_controlsWrapper( xDialog ) )
--{
-- mxDialog.set( xDialog, uno::UNO_QUERY_THROW );
--}
--
--uno::Reference< container::XEnumeration >
--ScVbaControls::createEnumeration() throw (uno::RuntimeException)
--{
-- uno::Reference< container::XEnumeration > xEnum( new ControlsEnumWrapper( mxParent, mxContext, m_xIndexAccess, mxDialog ) );
-- if ( !xEnum.is() )
-- throw uno::RuntimeException();
-- return xEnum;
--}
--
--uno::Any
--ScVbaControls::createCollectionObject( const css::uno::Any& aSource )
--{
-- // Create control from awt::XControl
-- uno::Reference< awt::XControl > xControl;
-- aSource >>= xControl;
-- uno::Reference< frame::XModel > xModel;
-- ScVbaControlFactory aFac( mxContext, xControl, xModel );
-- uno::Reference< msforms::XControl > xVBAControl( aFac.createControl( mxDialog->getModel() ) );
-- return uno::makeAny( xVBAControl );
--}
--
--void SAL_CALL
--ScVbaControls::Move( double cx, double cy ) throw (uno::RuntimeException)
--{
-- uno::Reference< container::XEnumeration > xEnum( createEnumeration() );
-- while ( xEnum->hasMoreElements() )
-- {
-- uno::Reference< msforms::XControl > xControl( xEnum->nextElement(), uno::UNO_QUERY_THROW );
-- xControl->setLeft( xControl->getLeft() + cx );
-- xControl->setTop( xControl->getTop() + cy );
-- }
--}
--
--uno::Type
--ScVbaControls::getElementType() throw (uno::RuntimeException)
--{
-- return ooo::vba::msforms::XControl::static_type(0);
--}
--rtl::OUString&
--ScVbaControls::getServiceImplName()
--{
-- static rtl::OUString sImplName( RTL_CONSTASCII_USTRINGPARAM("ScVbaControls") );
-- return sImplName;
--}
--
--uno::Sequence< rtl::OUString >
--ScVbaControls::getServiceNames()
--{
-- static uno::Sequence< rtl::OUString > aServiceNames;
-- if ( aServiceNames.getLength() == 0 )
-- {
-- aServiceNames.realloc( 1 );
-- aServiceNames[ 0 ] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.excel.Controls" ) );
-- }
-- return aServiceNames;
--}
---- sc/source/ui/vba/vbacontrols.hxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbacontrols.hxx 1970-01-01 00:00:00.000000000 +0000
-@@ -1,62 +0,0 @@
--/*************************************************************************
-- *
-- * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-- *
-- * Copyright 2008 by Sun Microsystems, Inc.
-- *
-- * OpenOffice.org - a multi-platform office productivity suite
-- *
-- * $RCSfile$
-- * $Revision$
-- *
-- * 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.
-- *
-- ************************************************************************/
--#ifndef SC_VBA_CONTROLS_HXX
--#define SC_VBA_CONTROLS_HXX
--
--#include <cppuhelper/implbase1.hxx>
--#include <ooo/vba/msforms/XControls.hpp>
--#include <com/sun/star/awt/XControl.hpp>
--
--#include "vbacollectionimpl.hxx"
--#include "vbahelper.hxx"
--
--typedef CollTestImplHelper< ov::msforms::XControls > ControlsImpl_BASE;
--
--class ScVbaControls : public ControlsImpl_BASE
--{
-- css::uno::Reference< css::awt::XControl > mxDialog;
--protected:
-- virtual rtl::OUString& getServiceImplName();
-- virtual css::uno::Sequence<rtl::OUString> getServiceNames();
--public:
-- ScVbaControls( const css::uno::Reference< ov::XHelperInterface >& xParent, const css::uno::Reference< css::uno::XComponentContext >& xContext,
-- const css::uno::Reference< css::awt::XControl >& xDialog );
-- // XControls
-- virtual void SAL_CALL Move( double cx, double cy ) throw (css::uno::RuntimeException);
-- // XEnumerationAccess
-- virtual css::uno::Type SAL_CALL getElementType() throw (css::uno::RuntimeException);
-- virtual css::uno::Reference< css::container::XEnumeration > SAL_CALL createEnumeration() throw (css::uno::RuntimeException);
--
-- // ScVbaCollectionBaseImpl
-- virtual css::uno::Any createCollectionObject( const css::uno::Any& aSource );
--
--};
--#endif //SC_VBA_OLEOBJECTS_HXX
--
---- sc/source/ui/vba/vbadialog.cxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbadialog.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -35,7 +35,7 @@
-
- #include <tools/string.hxx>
-
--#include "vbahelper.hxx"
-+#include "excelvbahelper.hxx"
- #include "vbadialog.hxx"
- #include "vbaglobals.hxx"
-
---- sc/source/ui/vba/vbadialog.hxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbadialog.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -33,11 +33,10 @@
- #include <cppuhelper/implbase1.hxx>
-
- #include <com/sun/star/uno/XComponentContext.hpp>
--#include <ooo/vba/XGlobals.hpp>
- #include <ooo/vba/excel/XApplication.hpp>
- #include <ooo/vba/excel/XDialog.hpp>
-
--#include "vbahelperinterface.hxx"
-+#include <vbahelper/vbahelperinterface.hxx>
- #include "vbadialog.hxx"
-
- typedef InheritedHelperInterfaceImpl1< ov::excel::XDialog > ScVbaDialog_BASE;
---- sc/source/ui/vba/vbadialogs.cxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbadialogs.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -36,7 +36,7 @@
-
- #include <tools/string.hxx>
-
--#include "vbahelper.hxx"
-+#include "excelvbahelper.hxx"
- #include "vbadialogs.hxx"
- #include "vbaglobals.hxx"
- #include "vbadialog.hxx"
-@@ -62,7 +62,7 @@ ScVbaDialogs::Item( const uno::Any &aIte
- {
- sal_Int32 nIndex = 0;
- aItem >>= nIndex;
-- uno::Reference< excel::XDialog > aDialog( new ScVbaDialog( uno::Reference< XHelperInterface >( ScVbaGlobals::getGlobalsImpl( mxContext )->getApplication(), uno::UNO_QUERY_THROW ), nIndex, mxContext ) );
-+ uno::Reference< excel::XDialog > aDialog( new ScVbaDialog( uno::Reference< XHelperInterface >( Application(),uno::UNO_QUERY_THROW ), nIndex, mxContext ) );
- return uno::Any( aDialog );
- }
- rtl::OUString&
---- sc/source/ui/vba/vbadialogs.hxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbadialogs.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -35,7 +35,7 @@
- #include <com/sun/star/uno/XComponentContext.hpp>
- #include <ooo/vba/excel/XDialogs.hpp>
- #include <ooo/vba/XCollection.hpp>
--#include "vbahelperinterface.hxx"
-+#include <vbahelper/vbahelperinterface.hxx>
-
- class ScModelObj;
-
---- sc/source/ui/vba/vbaeventshelper.cxx.old 2009-04-06 16:42:00.000000000 +0000
-+++ sc/source/ui/vba/vbaeventshelper.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -33,12 +33,8 @@
- *
- ************************************************************************/
- #include "vbaeventshelper.hxx"
--#include "helperdecl.hxx"
-+#include <vbahelper/helperdecl.hxx>
- #include <sfx2/objsh.hxx>
--#include <basic/basmgr.hxx>
--#include <basic/sbmod.hxx>
--#include <basic/sbmeth.hxx>
--#include <basic/sbx.hxx>
- #include "scextopt.hxx"
- #include <sfx2/evntconf.hxx>
- #include <sfx2/event.hxx>
-@@ -69,8 +65,6 @@ using namespace com::sun::star;
- using namespace ooo::vba;
- using namespace com::sun::star::document::VbaEventId;
-
--const static String sLibrary( RTL_CONSTASCII_USTRINGPARAM("Standard"));
--
- const static rtl::OUString sUrlPart0 = rtl::OUString::createFromAscii( "vnd.sun.star.script:");
- const static rtl::OUString sUrlPart1 = rtl::OUString::createFromAscii( "vnd.sun.star.script:Standard.");
- const static rtl::OUString sUrlPart2 = rtl::OUString::createFromAscii( "?language=Basic&location=document");
-@@ -400,7 +394,7 @@ ScVbaEventsHelper::ScVbaEventsHelper( un
- : m_xContext( xContext ), mpVbaEventsListener( NULL ), mbOpened( sal_False ), mbIgnoreEvents( sal_False )
- {
- uno::Reference< frame::XModel > xModel ( getXSomethingFromArgs< frame::XModel >( aArgs, 0 ), uno::UNO_QUERY );
-- ScDocShell* pDocShell = getDocShell( xModel );
-+ ScDocShell* pDocShell = excel::getDocShell( xModel );
- pDoc = pDocShell->GetDocument();
- }
-
-@@ -452,55 +446,6 @@ sal_Bool ScVbaEventsHelper::executeMacro
- }
- return sal_True;
- }
--String ScVbaEventsHelper::workbookMacroExists( SfxObjectShell* pShell, const String& sMod, const String& sMacro )
--{
-- String sFullName;
-- // would use the script provider to see if the macro exists but
-- // called at this stage tdoc content handler stuff is not set up
-- // so it fails
--
-- BasicManager* pBasicMgr = pShell-> GetBasicManager();
-- if ( pBasicMgr )
-- {
-- StarBASIC* pBasic = pBasicMgr->GetLib( sLibrary );
-- if ( !pBasic )
-- {
-- USHORT nId = pBasicMgr->GetLibId( sLibrary );
-- pBasicMgr->LoadLib( nId );
-- pBasic = pBasicMgr->GetLib( sLibrary );
-- }
-- if ( pBasic )
-- {
-- if ( sMod.Len() ) // we wish to find the macro is a specific module
-- {
-- SbModule* pModule = pBasic->FindModule( sMod );
-- if ( pModule )
-- {
-- SbxArray* pMethods = pModule->GetMethods();
-- if ( pMethods )
-- {
-- SbMethod* pMethod = static_cast< SbMethod* >( pMethods->Find( sMacro, SbxCLASS_METHOD ) );
-- if ( pMethod )
-- {
-- sFullName = sMacro;
-- sFullName.Insert( '.', 0 ).Insert( sMod, 0 ).Insert( '.', 0 ).Insert( sLibrary, 0 );
-- }
-- }
-- }
-- }
-- else if( SbMethod* pMethod = dynamic_cast< SbMethod* >( pBasic->Find( sMacro, SbxCLASS_METHOD ) ) )
-- {
-- if( SbModule* pModule = pMethod->GetModule() )
-- {
-- sFullName = sMacro;
-- sFullName.Insert( '.', 0 ).Insert( pModule->GetName(), 0).Insert( '.', 0 ).Insert( sLibrary, 0 );
-- }
-- }
--
-- }
-- }
-- return sFullName;
--}
-
- uno::Any ScVbaEventsHelper::createWorkSheet( SfxObjectShell* pShell, SCTAB nTab )
- {
-@@ -517,7 +462,7 @@ uno::Any ScVbaEventsHelper::createWorkSh
- uno::Sequence< uno::Any > aArgs(2);
- aArgs[0] = uno::Any( uno::Reference< uno::XInterface >() );
- aArgs[1] = uno::Any( pShell->GetModel() );
-- uno::Reference< uno::XInterface > xWorkbook( xSMgr->createInstanceWithArgumentsAndContext( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.excel.Workbook") ), aArgs, xCtx ), uno::UNO_QUERY );
-+ uno::Reference< uno::XInterface > xWorkbook( ov::createVBAUnoAPIServiceWithArgs( pShell, "ooo.vba.excel.Workbook", aArgs ), uno::UNO_QUERY );
-
- // create WorkSheet
- String sSheetName;
-@@ -526,7 +471,7 @@ uno::Any ScVbaEventsHelper::createWorkSh
- aArgs[ 0 ] <<= xWorkbook;
- aArgs[ 1 ] <<= pShell->GetModel();
- aArgs[ 2 ] = uno::makeAny( rtl::OUString( sSheetName ) );
-- aRet <<= xSMgr->createInstanceWithArgumentsAndContext( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.excel.Worksheet") ), aArgs, xCtx );
-+ aRet <<= ov::createVBAUnoAPIServiceWithArgs( pShell, "ooo.vba.excel.Worksheet", aArgs );
- }
- catch( uno::Exception& e )
- {
-@@ -560,7 +505,7 @@ uno::Any ScVbaEventsHelper::createRange(
- {
- throw uno::RuntimeException(); //
- }
-- aRet <<= xSMgr->createInstanceWithArgumentsAndContext( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.excel.Range") ), aArgs, xCtx );
-+ aRet <<= ov::createVBAUnoAPIServiceWithArgs( pDoc->GetDocumentShell(), "ooo.vba.excel.Range", aArgs );
- }
- }
- catch( uno::Exception& e )
-@@ -584,7 +529,7 @@ uno::Any ScVbaEventsHelper::createHyperl
- aArgs[0] = uno::Any( uno::Reference< uno::XInterface >() ); // dummy parent
- aArgs[1] <<= rCell;
-
-- aRet <<= xSMgr->createInstanceWithArgumentsAndContext( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.excel.Hyperlink") ), aArgs, xCtx );
-+ aRet <<= ov::createVBAUnoAPIServiceWithArgs( pDoc->GetDocumentShell(), "ooo.vba.excel.Hyperlink", aArgs );
- }
- else
- {
-@@ -647,7 +592,7 @@ ScVbaEventsHelper::getMacroPath( const s
- case VBAEVENT_WORKSHEET_SELECTIONCHANGE :
- {
- rtl::OUString aSheetModuleName = getSheetModuleName( nTab );
-- sMacroPath = workbookMacroExists( pShell, aSheetModuleName, sMacroName );
-+ sMacroPath = docMacroExists( pShell, aSheetModuleName, sMacroName );
- break;
- }
- // Workbook
-@@ -681,7 +626,7 @@ ScVbaEventsHelper::getMacroPath( const s
- sWorkbookModuleName = aExtDocSettings.maGlobCodeName;
- }
-
-- sMacroPath = workbookMacroExists( pShell, sWorkbookModuleName, sMacroName );
-+ sMacroPath = docMacroExists( pShell, sWorkbookModuleName, sMacroName );
- break;
- }
- default:
---- sc/source/ui/vba/vbaeventshelper.hxx.old 2009-04-06 16:42:00.000000000 +0000
-+++ sc/source/ui/vba/vbaeventshelper.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -40,7 +40,7 @@
- #include <cppuhelper/implbase1.hxx>
- #include <com/sun/star/document/VbaEventId.hpp>
- #include <com/sun/star/document/XVbaEventsHelper.hpp>
--#include "vbahelper.hxx"
-+#include "excelvbahelper.hxx"
-
- #define INVALID_TAB -1
-
-@@ -57,7 +57,6 @@ private:
- sal_Bool mbIgnoreEvents;
-
- String getSheetModuleName( SCTAB nTab );
-- String workbookMacroExists( SfxObjectShell* pShell, const String& sMod, const String& sMacro );
- css::uno::Any createWorkSheet( SfxObjectShell* pShell, SCTAB nTab );
- css::uno::Any createRange( const css::uno::Any& aRange );
- css::uno::Any createHyperlink( const css::uno::Any& rCell );
---- sc/source/ui/vba/vbafillformat.hxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbafillformat.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -33,7 +33,7 @@
- #include <com/sun/star/drawing/XShape.hpp>
- #include <com/sun/star/drawing/FillStyle.hpp>
- #include <ooo/vba/msforms/XFillFormat.hpp>
--#include "vbahelperinterface.hxx"
-+#include <vbahelper/vbahelperinterface.hxx>
-
- typedef InheritedHelperInterfaceImpl1< ov::msforms::XFillFormat > ScVbaFillFormat_BASE;
-
---- sc/source/ui/vba/vbafont.hxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbafont.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -34,7 +34,7 @@
-
- #include <ooo/vba/excel/XFont.hpp>
- #include <com/sun/star/beans/XPropertySet.hpp>
--#include "vbahelperinterface.hxx"
-+#include <vbahelper/vbahelperinterface.hxx>
- #include "vbapalette.hxx"
-
- class ScTableSheetsObj;
---- sc/source/ui/vba/vbaformat.cxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbaformat.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -33,6 +33,7 @@
- #include <ooo/vba/excel/XlHAlign.hpp>
- #include <ooo/vba/excel/XlOrientation.hpp>
- #include <ooo/vba/excel/Constants.hpp>
-+#include <ooo/vba/excel/XRange.hpp>
- #include <com/sun/star/table/CellVertJustify.hpp>
- #include <com/sun/star/table/CellHoriJustify.hpp>
- #include <com/sun/star/table/CellOrientation.hpp>
-@@ -341,7 +342,7 @@ template< typename Ifc1 >
- uno::Any SAL_CALL
- ScVbaFormat<Ifc1>::Borders( const uno::Any& Index ) throw (script::BasicErrorException, uno::RuntimeException )
- {
-- ScVbaPalette aPalette( getDocShell( mxModel ) );
-+ ScVbaPalette aPalette( excel::getDocShell( mxModel ) );
- uno::Reference< XCollection > xColl = new ScVbaBorders( thisHelperIface(), ScVbaFormat_BASE::mxContext, uno::Reference< table::XCellRange >( mxPropertySet, uno::UNO_QUERY_THROW ), aPalette );
-
- if ( Index.hasValue() )
-@@ -355,7 +356,7 @@ template< typename Ifc1 >
- uno::Reference< excel::XFont > SAL_CALL
- ScVbaFormat<Ifc1>::Font( ) throw (script::BasicErrorException, uno::RuntimeException)
- {
-- ScVbaPalette aPalette( getDocShell( mxModel ) );
-+ ScVbaPalette aPalette( excel::getDocShell( mxModel ) );
- return new ScVbaFont( thisHelperIface(), ScVbaFormat_BASE::mxContext, aPalette, mxPropertySet );
- }
-
---- sc/source/ui/vba/vbaformat.hxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbaformat.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -39,7 +39,7 @@
- #include <com/sun/star/lang/XMultiServiceFactory.hpp>
- #include <com/sun/star/lang/Locale.hpp>
- #include <com/sun/star/beans/XPropertyState.hpp>
--#include "vbahelperinterface.hxx"
-+#include <vbahelper/vbahelperinterface.hxx>
-
- template< typename Ifc1 >
- class ScVbaFormat : public InheritedHelperInterfaceImpl1< Ifc1 >
---- sc/source/ui/vba/vbaformatconditions.cxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbaformatconditions.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -36,6 +36,7 @@
- #include "vbaformatcondition.hxx"
- #include "vbaworkbook.hxx"
- #include "vbastyles.hxx"
-+#include "vbaglobals.hxx"
- using namespace ::ooo::vba;
- using namespace ::com::sun::star;
-
-@@ -50,7 +51,7 @@ static rtl::OUString sStyleNamePrefix( R
- ScVbaFormatConditions::ScVbaFormatConditions( const uno::Reference< XHelperInterface >& xParent, const uno::Reference< uno::XComponentContext > & xContext, const uno::Reference< sheet::XSheetConditionalEntries >& _xSheetConditionalEntries, const uno::Reference< frame::XModel >& xModel ) : ScVbaFormatConditions_BASE( xParent, xContext, uno::Reference< container::XIndexAccess >( _xSheetConditionalEntries, uno::UNO_QUERY_THROW ) ), mxSheetConditionalEntries( _xSheetConditionalEntries )
- {
- mxRangeParent.set( xParent, uno::UNO_QUERY_THROW );
-- uno::Reference< excel::XWorkbook > xWorkbook = new ScVbaWorkbook( uno::Reference< XHelperInterface >( ScVbaGlobals::getGlobalsImpl( xContext )->getApplication(), uno::UNO_QUERY_THROW ), xContext, xModel );
-+ uno::Reference< excel::XWorkbook > xWorkbook = new ScVbaWorkbook( uno::Reference< XHelperInterface >( Application(), uno::UNO_QUERY_THROW ), xContext, xModel );
- mxStyles.set( xWorkbook->Styles( uno::Any() ), uno::UNO_QUERY_THROW );
- uno::Reference< sheet::XCellRangeAddressable > xCellRange( mxRangeParent->getCellRange(), uno::UNO_QUERY_THROW );
- mxParentRangePropertySet.set( xCellRange, uno::UNO_QUERY_THROW );
---- sc/source/ui/vba/vbaformatconditions.hxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbaformatconditions.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -35,7 +35,7 @@
- #include <com/sun/star/beans/XPropertySet.hpp>
- #include <com/sun/star/table/CellAddress.hpp>
- #include <com/sun/star/sheet/XSheetConditionalEntries.hpp>
--#include "vbacollectionimpl.hxx"
-+#include <vbahelper/vbacollectionimpl.hxx>
-
- typedef CollTestImplHelper< ov::excel::XFormatConditions > ScVbaFormatConditions_BASE;
- class ScVbaFormatConditions: public ScVbaFormatConditions_BASE
---- sc/source/ui/vba/vbaframe.cxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbaframe.cxx 1970-01-01 00:00:00.000000000 +0000
-@@ -1,93 +0,0 @@
--/*************************************************************************
-- *
-- * OpenOffice.org - a multi-platform office productivity suite
-- *
-- * $RCSfile$
-- *
-- * $Revision$
-- *
-- * last change: $Author$ $Date$
-- *
-- * The Contents of this file are made available subject to
-- * the terms of GNU Lesser General Public License Version 2.1.
-- *
-- *
-- * GNU Lesser General Public License Version 2.1
-- * =============================================
-- * Copyright 2005 by Sun Microsystems, Inc.
-- * 901 San Antonio Road, Palo Alto, CA 94303, USA
-- *
-- * This library is free software; you can redistribute it and/or
-- * modify it under the terms of the GNU Lesser General Public
-- * License version 2.1, as published by the Free Software Foundation.
-- *
-- * This library 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 for more details.
-- *
-- * You should have received a copy of the GNU Lesser General Public
-- * License along with this library; if not, write to the Free Software
-- * Foundation, Inc., 59 Temple Place, Suite 330, Boston,
-- * MA 02111-1307 USA
-- *
-- ************************************************************************/
--#include "vbaframe.hxx"
--#include <vector>
--
--using namespace com::sun::star;
--using namespace ooo::vba;
--
--
--const static rtl::OUString LABEL( RTL_CONSTASCII_USTRINGPARAM("Label") );
--ScVbaFrame::ScVbaFrame( const uno::Reference< XHelperInterface >& xParent, const uno::Reference< uno::XComponentContext >& xContext, const uno::Reference< uno::XInterface >& xControl, const uno::Reference< frame::XModel >& xModel, ov::AbstractGeometryAttributes* pGeomHelper ) : FrameImpl_BASE( xParent, xContext, xControl, xModel, pGeomHelper )
--{
--}
--
--// Attributes
--rtl::OUString SAL_CALL
--ScVbaFrame::getCaption() throw (css::uno::RuntimeException)
--{
-- rtl::OUString Label;
-- m_xProps->getPropertyValue( LABEL ) >>= Label;
-- return Label;
--}
--
--void SAL_CALL
--ScVbaFrame::setCaption( const rtl::OUString& _caption ) throw (::com::sun::star::uno::RuntimeException)
--{
-- m_xProps->setPropertyValue( LABEL, uno::makeAny( _caption ) );
--}
--
--uno::Any SAL_CALL
--ScVbaFrame::getValue() throw (css::uno::RuntimeException)
--{
-- return uno::makeAny( getCaption() );
--}
--
--void SAL_CALL
--ScVbaFrame::setValue( const uno::Any& _value ) throw (::com::sun::star::uno::RuntimeException)
--{
-- rtl::OUString sCaption;
-- _value >>= sCaption;
-- setCaption( sCaption );
--}
--
--rtl::OUString&
--ScVbaFrame::getServiceImplName()
--{
-- static rtl::OUString sImplName( RTL_CONSTASCII_USTRINGPARAM("ScVbaFrame") );
-- return sImplName;
--}
--
--uno::Sequence< rtl::OUString >
--ScVbaFrame::getServiceNames()
--{
-- static uno::Sequence< rtl::OUString > aServiceNames;
-- if ( aServiceNames.getLength() == 0 )
-- {
-- aServiceNames.realloc( 1 );
-- aServiceNames[ 0 ] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.msforms.Frame" ) );
-- }
-- return aServiceNames;
--}
---- sc/source/ui/vba/vbaframe.hxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbaframe.hxx 1970-01-01 00:00:00.000000000 +0000
-@@ -1,58 +0,0 @@
--/*************************************************************************
-- *
-- * OpenOffice.org - a multi-platform office productivity suite
-- *
-- * $RCSfile$
-- *
-- * $Revision$
-- *
-- * last change: $Author$ $Date$
-- *
-- * The Contents of this file are made available subject to
-- * the terms of GNU Lesser General Public License Version 2.1.
-- *
-- *
-- * GNU Lesser General Public License Version 2.1
-- * =============================================
-- * Copyright 2005 by Sun Microsystems, Inc.
-- * 901 San Antonio Road, Palo Alto, CA 94303, USA
-- *
-- * This library is free software; you can redistribute it and/or
-- * modify it under the terms of the GNU Lesser General Public
-- * License version 2.1, as published by the Free Software Foundation.
-- *
-- * This library 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 for more details.
-- *
-- * You should have received a copy of the GNU Lesser General Public
-- * License along with this library; if not, write to the Free Software
-- * Foundation, Inc., 59 Temple Place, Suite 330, Boston,
-- * MA 02111-1307 USA
-- *
-- ************************************************************************/
--#ifndef SC_VBA_FRAME_HXX
--#define SC_VBA_FRAME_HXX
--#include <cppuhelper/implbase1.hxx>
--#include <ooo/vba/msforms/XLabel.hpp>
--
--#include "vbacontrol.hxx"
--#include "vbahelper.hxx"
--
--typedef cppu::ImplInheritanceHelper1< ScVbaControl, ov::msforms::XLabel > FrameImpl_BASE;
--
--class ScVbaFrame : public FrameImpl_BASE
--{
--public:
-- ScVbaFrame( const css::uno::Reference< ov::XHelperInterface >& xParent, const css::uno::Reference< css::uno::XComponentContext >& xContext, const css::uno::Reference< css::uno::XInterface >& xControl, const css::uno::Reference< css::frame::XModel >& xModel, ov::AbstractGeometryAttributes* pGeomHelper );
-- // Attributes
-- virtual css::uno::Any SAL_CALL getValue() throw (css::uno::RuntimeException);
-- virtual void SAL_CALL setValue( const css::uno::Any& _value ) throw (css::uno::RuntimeException);
-- virtual rtl::OUString SAL_CALL getCaption() throw (css::uno::RuntimeException);
-- virtual void SAL_CALL setCaption( const rtl::OUString& _caption ) throw (css::uno::RuntimeException);
-- //XHelperInterface
-- virtual rtl::OUString& getServiceImplName();
-- virtual css::uno::Sequence<rtl::OUString> getServiceNames();
--};
--#endif //SC_VBA_LABEL_HXX
---- sc/source/ui/vba/vbaglobals.cxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbaglobals.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -27,13 +27,14 @@
- * for a copy of the LGPLv3 License.
- *
- ************************************************************************/
--#include "helperdecl.hxx"
-+#include <vbahelper/helperdecl.hxx>
- #include "vbaglobals.hxx"
-
- #include <comphelper/unwrapargs.hxx>
-
- #include <com/sun/star/lang/XMultiComponentFactory.hpp>
- #include <com/sun/star/beans/XPropertySet.hpp>
-+#include <cppuhelper/component_context.hxx>
-
- #include "vbaapplication.hxx"
- #include "vbaworksheet.hxx"
-@@ -49,11 +50,10 @@ using namespace ::ooo::vba;
- // ScVbaGlobals
- // =============================================================================
-
--ScVbaGlobals::ScVbaGlobals( css::uno::Reference< css::uno::XComponentContext >const& rxContext )
-- :m_xContext( rxContext )
-+ScVbaGlobals::ScVbaGlobals( css::uno::Reference< css::uno::XComponentContext >const& rxContext ) : ScVbaGlobals_BASE( uno::Reference< XHelperInterface >(), rxContext )
- {
- OSL_TRACE("ScVbaGlobals::ScVbaGlobals()");
-- mxApplication = uno::Reference< excel::XApplication > ( new ScVbaApplication( m_xContext) );
-+ init( rxContext, uno::Any( getApplication() ) );
- }
-
- ScVbaGlobals::~ScVbaGlobals()
-@@ -61,23 +61,6 @@ ScVbaGlobals::~ScVbaGlobals()
- OSL_TRACE("ScVbaGlobals::~ScVbaGlobals");
- }
-
--// Will throw if singleton can't be accessed
--uno::Reference< XGlobals >
--ScVbaGlobals::getGlobalsImpl( const uno::Reference< uno::XComponentContext >& xContext ) throw ( uno::RuntimeException )
--{
-- uno::Reference< XGlobals > xGlobals(
-- xContext->getValueByName( ::rtl::OUString::createFromAscii(
-- "/singletons/ooo.vba.theGlobals") ), uno::UNO_QUERY);
--
-- if ( !xGlobals.is() )
-- {
-- throw uno::RuntimeException(
-- ::rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( ": Couldn't access Globals" ) ),
-- uno::Reference< XInterface >() );
-- }
-- return xGlobals;
--}
--
- // =============================================================================
- // XGlobals
- // =============================================================================
-@@ -85,14 +68,15 @@ uno::Reference<excel::XApplication >
- ScVbaGlobals::getApplication() throw (uno::RuntimeException)
- {
- // OSL_TRACE("In ScVbaGlobals::getApplication");
-- return mxApplication;
-+ static uno::Reference< excel::XApplication > ExcelApplication( new ScVbaApplication( mxContext) );
-+ return ExcelApplication;
- }
-
- uno::Reference< excel::XWorkbook > SAL_CALL
- ScVbaGlobals::getActiveWorkbook() throw (uno::RuntimeException)
- {
- // OSL_TRACE("In ScVbaGlobals::getActiveWorkbook");
-- uno::Reference< excel::XWorkbook > xWorkbook( mxApplication->getActiveWorkbook(), uno::UNO_QUERY);
-+ uno::Reference< excel::XWorkbook > xWorkbook( getApplication()->getActiveWorkbook(), uno::UNO_QUERY);
- if ( xWorkbook.is() )
- {
- return xWorkbook;
-@@ -103,22 +87,28 @@ ScVbaGlobals::getActiveWorkbook() throw
- }
-
-
-+uno::Reference< excel::XWindow > SAL_CALL
-+ScVbaGlobals::getActiveWindow() throw (uno::RuntimeException)
-+{
-+ return getApplication()->getActiveWindow();
-+}
-+
- uno::Reference< excel::XWorksheet > SAL_CALL
- ScVbaGlobals::getActiveSheet() throw (uno::RuntimeException)
- {
-- return mxApplication->getActiveSheet();
-+ return getApplication()->getActiveSheet();
- }
-
- uno::Any SAL_CALL
- ScVbaGlobals::WorkBooks( const uno::Any& aIndex ) throw (uno::RuntimeException)
- {
-- return uno::Any( mxApplication->Workbooks(aIndex) );
-+ return uno::Any( getApplication()->Workbooks(aIndex) );
- }
-
- uno::Any SAL_CALL
- ScVbaGlobals::WorkSheets(const uno::Any& aIndex) throw (uno::RuntimeException)
- {
-- return mxApplication->Worksheets( aIndex );
-+ return getApplication()->Worksheets( aIndex );
- }
- uno::Any SAL_CALL
- ScVbaGlobals::Sheets( const uno::Any& aIndex ) throw (uno::RuntimeException)
-@@ -126,26 +116,6 @@ ScVbaGlobals::Sheets( const uno::Any& aI
- return WorkSheets( aIndex );
- }
-
--::uno::Sequence< ::uno::Any > SAL_CALL
--ScVbaGlobals::getGlobals( ) throw (::uno::RuntimeException)
--{
-- sal_uInt32 nMax = 0;
-- uno::Sequence< uno::Any > maGlobals(4);
-- maGlobals[ nMax++ ] <<= ScVbaGlobals::getGlobalsImpl(m_xContext);
-- maGlobals[ nMax++ ] <<= mxApplication;
--
-- uno::Reference< excel::XWorkbook > xWorkbook = mxApplication->getActiveWorkbook();
-- if( xWorkbook.is() )
-- {
-- maGlobals[ nMax++ ] <<= xWorkbook;
-- uno::Reference< excel::XWorksheet > xWorksheet = xWorkbook->getActiveSheet();
-- if( xWorksheet.is() )
-- maGlobals[ nMax++ ] <<= xWorksheet;
-- }
-- maGlobals.realloc( nMax );
-- return maGlobals;
--}
--
- uno::Any SAL_CALL
- ScVbaGlobals::Range( const uno::Any& Cell1, const uno::Any& Cell2 ) throw (uno::RuntimeException)
- {
-@@ -158,13 +128,140 @@ ScVbaGlobals::Names( const css::uno::Any
- return getApplication()->Names( aIndex );
- }
-
-+uno::Reference< excel::XRange > SAL_CALL
-+ScVbaGlobals::getActiveCell() throw (uno::RuntimeException)
-+{
-+ return getApplication()->getActiveCell();
-+}
-+
-+uno::Reference< XAssistant > SAL_CALL
-+ScVbaGlobals::getAssistant() throw (uno::RuntimeException)
-+{
-+ return getApplication()->getAssistant();
-+}
-+
-+uno::Any SAL_CALL
-+ScVbaGlobals::getSelection() throw (uno::RuntimeException)
-+{
-+ return getApplication()->getSelection();
-+}
-+
-+uno::Reference< excel::XWorkbook > SAL_CALL
-+ScVbaGlobals::getThisWorkbook() throw (uno::RuntimeException)
-+{
-+ return getApplication()->getThisWorkbook();
-+}
-+void SAL_CALL
-+ScVbaGlobals::Calculate() throw (::com::sun::star::script::BasicErrorException, ::com::sun::star::uno::RuntimeException)
-+{
-+ return getApplication()->Calculate();
-+}
-+
-+uno::Reference< excel::XRange > SAL_CALL
-+ScVbaGlobals::Cells( const uno::Any& RowIndex, const uno::Any& ColumnIndex ) throw (uno::RuntimeException)
-+{
-+ return getApplication()->getActiveSheet()->Cells( RowIndex, ColumnIndex );
-+}
-+uno::Reference< excel::XRange > SAL_CALL
-+ScVbaGlobals::Columns( const uno::Any& aIndex ) throw (uno::RuntimeException)
-+{
-+ return getApplication()->getActiveSheet()->Columns( aIndex );
-+}
-+
-+uno::Any SAL_CALL
-+ScVbaGlobals::CommandBars( const uno::Any& aIndex ) throw (uno::RuntimeException)
-+{
-+ uno::Reference< XApplicationBase > xBase( getApplication(), uno::UNO_QUERY_THROW );
-+ return xBase->CommandBars( aIndex );
-+}
-+
-+css::uno::Reference< ov::excel::XRange > SAL_CALL
-+ScVbaGlobals::Union( const css::uno::Reference< ov::excel::XRange >& Arg1, const css::uno::Reference< ov::excel::XRange >& Arg2, const css::uno::Any& Arg3, const css::uno::Any& Arg4, const css::uno::Any& Arg5, const css::uno::Any& Arg6, const css::uno::Any& Arg7, const css::uno::Any& Arg8, const css::uno::Any& Arg9, const css::uno::Any& Arg10, const css::uno::Any& Arg11, const css::uno::Any& Arg12, const css::uno::Any& Arg13, const css::uno::Any& Arg14, const css::uno::Any& Arg15, const css::uno::Any& Arg16, const css::uno::Any& Arg17, const css::uno::Any& Arg18, const css::uno::Any& Arg19, const css::uno::Any& Arg20, const css::uno::Any& Arg21, const css::uno::Any& Arg22, const css::uno::Any& Arg23, const css::uno::Any& Arg24, const css::uno::Any& Arg25, const css::uno::Any& Arg26, const css::uno::Any& Arg27, const css::uno::Any& Arg28, const css::uno::Any& Arg29, const css::uno::Any& Arg30 ) throw (css::script::BasicErrorException, css::uno::RuntimeException)
-+{
-+ return getApplication()->Union( Arg1, Arg2, Arg3, Arg4, Arg5, Arg6, Arg7, Arg8, Arg9, Arg10, Arg11, Arg12, Arg13, Arg14, Arg15, Arg16, Arg17, Arg18, Arg19, Arg20, Arg21, Arg22, Arg23, Arg24, Arg25, Arg26, Arg27, Arg28, Arg29, Arg30 );
-+}
-+css::uno::Reference< ov::excel::XRange > SAL_CALL
-+ScVbaGlobals::Intersect( const css::uno::Reference< ov::excel::XRange >& Arg1, const css::uno::Reference< ov::excel::XRange >& Arg2, const css::uno::Any& Arg3, const css::uno::Any& Arg4, const css::uno::Any& Arg5, const css::uno::Any& Arg6, const css::uno::Any& Arg7, const css::uno::Any& Arg8, const css::uno::Any& Arg9, const css::uno::Any& Arg10, const css::uno::Any& Arg11, const css::uno::Any& Arg12, const css::uno::Any& Arg13, const css::uno::Any& Arg14, const css::uno::Any& Arg15, const css::uno::Any& Arg16, const css::uno::Any& Arg17, const css::uno::Any& Arg18, const css::uno::Any& Arg19, const css::uno::Any& Arg20, const css::uno::Any& Arg21, const css::uno::Any& Arg22, const css::uno::Any& Arg23, const css::uno::Any& Arg24, const css::uno::Any& Arg25, const css::uno::Any& Arg26, const css::uno::Any& Arg27, const css::uno::Any& Arg28, const css::uno::Any& Arg29, const css::uno::Any& Arg30 ) throw (css::script::BasicErrorException, css::uno::RuntimeException)
-+{
-+ return getApplication()->Intersect( Arg1, Arg2, Arg3, Arg4, Arg5, Arg6, Arg7, Arg8, Arg9, Arg10, Arg11, Arg12, Arg13, Arg14, Arg15, Arg16, Arg17, Arg18, Arg19, Arg20, Arg21, Arg22, Arg23, Arg24, Arg25, Arg26, Arg27, Arg28, Arg29, Arg30 );
-+}
-+
-+uno::Any SAL_CALL
-+ScVbaGlobals::Evaluate( const ::rtl::OUString& Name ) throw (uno::RuntimeException)
-+{
-+ return getApplication()->Evaluate( Name );
-+}
-+
-+css::uno::Any SAL_CALL
-+ScVbaGlobals::WorksheetFunction( ) throw (css::uno::RuntimeException)
-+{
-+ return getApplication()->WorksheetFunction();
-+}
-+
-+uno::Any SAL_CALL
-+ScVbaGlobals::Windows( const uno::Any& aIndex ) throw (uno::RuntimeException)
-+{
-+ return getApplication()->Windows( aIndex );
-+}
-+
-+uno::Reference< excel::XRange > SAL_CALL
-+ScVbaGlobals::Rows( const uno::Any& aIndex ) throw (uno::RuntimeException)
-+{
-+ return getApplication()->getActiveSheet()->Rows( aIndex );
-+
-+}
-+
-+uno::Sequence< ::rtl::OUString > SAL_CALL
-+ScVbaGlobals::getAvailableServiceNames( ) throw (uno::RuntimeException)
-+{
-+ static bool bInit = false;
-+ static uno::Sequence< rtl::OUString > serviceNames( ScVbaGlobals_BASE::getAvailableServiceNames() );
-+ if ( !bInit )
-+ {
-+ rtl::OUString names[] = {
-+ ::rtl::OUString( RTL_CONSTASCII_USTRINGPARAM ( "ooo.vba.excel.Range" ) ),
-+ ::rtl::OUString( RTL_CONSTASCII_USTRINGPARAM ( "ooo.vba.excel.Workbook" ) ),
-+ ::rtl::OUString( RTL_CONSTASCII_USTRINGPARAM ( "ooo.vba.excel.Window" ) ),
-+ ::rtl::OUString( RTL_CONSTASCII_USTRINGPARAM ( "ooo.vba.excel.Worksheet" ) ),
-+ ::rtl::OUString( RTL_CONSTASCII_USTRINGPARAM ( "ooo.vba.excel.Application" ) ),
-+ ::rtl::OUString( RTL_CONSTASCII_USTRINGPARAM ( "ooo.vba.excel.Hyperlink" ) ),
-+ };
-+ sal_Int32 nExcelServices = ( sizeof( names )/ sizeof( names[0] ) );
-+ sal_Int32 startIndex = serviceNames.getLength();
-+ serviceNames.realloc( serviceNames.getLength() + nExcelServices );
-+ for ( sal_Int32 index = 0; index < nExcelServices; ++index )
-+ serviceNames[ startIndex + index ] = names[ index ];
-+ bInit = true;
-+ }
-+ return serviceNames;
-+}
-+
-+rtl::OUString&
-+ScVbaGlobals::getServiceImplName()
-+{
-+ static rtl::OUString sImplName( RTL_CONSTASCII_USTRINGPARAM("ScVbaGlobals") );
-+ return sImplName;
-+}
-+
-+uno::Sequence< rtl::OUString >
-+ScVbaGlobals::getServiceNames()
-+{
-+ static uno::Sequence< rtl::OUString > aServiceNames;
-+ if ( aServiceNames.getLength() == 0 )
-+ {
-+ aServiceNames.realloc( 1 );
-+ aServiceNames[ 0 ] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.excel.Globals" ) );
-+ }
-+ return aServiceNames;
-+}
-+
- namespace globals
- {
- namespace sdecl = comphelper::service_decl;
--sdecl::class_<ScVbaGlobals, sdecl::with_args<false> > serviceImpl;
-+sdecl::vba_service_class_<ScVbaGlobals, sdecl::with_args<false> > serviceImpl;
- extern sdecl::ServiceDecl const serviceDecl(
- serviceImpl,
- "ScVbaGlobals",
-- "ooo.vba.Globals" );
-+ "ooo.vba.excel.Globals" );
- }
-
---- sc/source/ui/vba/vbaglobals.hxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbaglobals.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -33,43 +33,62 @@
- #include <com/sun/star/lang/XServiceInfo.hpp>
- #include <com/sun/star/lang/XInitialization.hpp>
- #include <com/sun/star/uno/XComponentContext.hpp>
--#include <ooo/vba/XGlobals.hpp>
-+#include <ooo/vba/excel/XGlobals.hpp>
-+#include <ooo/vba/excel/XApplication.hpp>
-
- #include <cppuhelper/implbase1.hxx>
--#include "vbahelper.hxx"
-+#include "excelvbahelper.hxx"
-
-+#include <vbahelper/vbaglobalbase.hxx>
- // =============================================================================
- // class ScVbaGlobals
- // =============================================================================
-
-- typedef ::cppu::WeakImplHelper1<
-- ov::XGlobals > ScVbaGlobals_BASE;
--
-+typedef ::cppu::ImplInheritanceHelper1< VbaGlobalsBase, ov::excel::XGlobals > ScVbaGlobals_BASE;
-
- class ScVbaGlobals : public ScVbaGlobals_BASE
- {
-- private:
-- css::uno::Reference< css::uno::XComponentContext > m_xContext;
-- css::uno::Reference< ov::excel::XApplication > mxApplication;
-+ virtual css::uno::Reference<
-+ ov::excel::XApplication > SAL_CALL getApplication()
-+ throw (css::uno::RuntimeException);
- public:
-
- ScVbaGlobals(
- css::uno::Reference< css::uno::XComponentContext >const& rxContext );
- virtual ~ScVbaGlobals();
-
-- static css::uno::Reference< ov::XGlobals > getGlobalsImpl(const css::uno::Reference< css::uno::XComponentContext >& ) throw (css::uno::RuntimeException);
--
- // XGlobals
-- virtual css::uno::Reference<
-- ov::excel::XApplication > SAL_CALL getApplication()
-- throw (css::uno::RuntimeException);
- virtual css::uno::Reference< ov::excel::XWorkbook > SAL_CALL getActiveWorkbook() throw (css::uno::RuntimeException);
-+ virtual css::uno::Reference< ov::excel::XWindow > SAL_CALL getActiveWindow() throw (css::uno::RuntimeException);
- virtual css::uno::Reference< ov::excel::XWorksheet > SAL_CALL getActiveSheet() throw (css::uno::RuntimeException);
-+ virtual css::uno::Reference< ov::XAssistant > SAL_CALL getAssistant() throw (css::uno::RuntimeException);
-+ virtual void SAL_CALL Calculate( ) throw (::com::sun::star::script::BasicErrorException, ::com::sun::star::uno::RuntimeException);
-+
-+ virtual css::uno::Any SAL_CALL getSelection() throw (css::uno::RuntimeException);
-+ virtual css::uno::Reference< ov::excel::XRange > SAL_CALL getActiveCell() throw (css::uno::RuntimeException);
-+ virtual css::uno::Reference< ov::excel::XWorkbook > SAL_CALL getThisWorkbook() throw (css::uno::RuntimeException);
-+ virtual css::uno::Reference< ov::excel::XRange > SAL_CALL Cells( const css::uno::Any& RowIndex, const css::uno::Any& ColumnIndex ) throw (css::uno::RuntimeException);
-+ virtual css::uno::Reference< ov::excel::XRange > SAL_CALL Columns( const css::uno::Any& aIndex ) throw (css::uno::RuntimeException);
-+ virtual css::uno::Any SAL_CALL CommandBars( const css::uno::Any& aIndex ) throw (css::uno::RuntimeException);
-+ virtual css::uno::Any SAL_CALL Evaluate( const ::rtl::OUString& Name ) throw (css::uno::RuntimeException);
-+
- virtual css::uno::Any SAL_CALL WorkSheets(const css::uno::Any& aIndex ) throw (css::uno::RuntimeException);
- virtual css::uno::Any SAL_CALL WorkBooks(const css::uno::Any& aIndex ) throw (css::uno::RuntimeException);
-+ virtual css::uno::Any SAL_CALL WorksheetFunction( ) throw (css::uno::RuntimeException);
-+ virtual css::uno::Any SAL_CALL Windows( const css::uno::Any& aIndex ) throw (css::uno::RuntimeException);
- virtual css::uno::Any SAL_CALL Sheets( const css::uno::Any& aIndex ) throw (css::uno::RuntimeException);
-- virtual css::uno::Sequence< css::uno::Any > SAL_CALL getGlobals( ) throw (css::uno::RuntimeException);
- virtual css::uno::Any SAL_CALL Range( const css::uno::Any& Cell1, const css::uno::Any& Cell2 ) throw (css::uno::RuntimeException);
-+ virtual css::uno::Reference< ::ooo::vba::excel::XRange > SAL_CALL Rows( const css::uno::Any& aIndex ) throw (css::uno::RuntimeException);
- virtual css::uno::Any SAL_CALL Names( const css::uno::Any& aIndex ) throw ( css::uno::RuntimeException );
-+ virtual css::uno::Reference< ov::excel::XRange > SAL_CALL Intersect( const css::uno::Reference< ov::excel::XRange >& Arg1, const css::uno::Reference< ov::excel::XRange >& Arg2, const css::uno::Any& Arg3, const css::uno::Any& Arg4, const css::uno::Any& Arg5, const css::uno::Any& Arg6, const css::uno::Any& Arg7, const css::uno::Any& Arg8, const css::uno::Any& Arg9, const css::uno::Any& Arg10, const css::uno::Any& Arg11, const css::uno::Any& Arg12, const css::uno::Any& Arg13, const css::uno::Any& Arg14, const css::uno::Any& Arg15, const css::uno::Any& Arg16, const css::uno::Any& Arg17, const css::uno::Any& Arg18, const css::uno::Any& Arg19, const css::uno::Any& Arg20, const css::uno::Any& Arg21, const css::uno::Any& Arg22, const css::uno::Any& Arg23, const css::uno::Any& Arg24, const css::uno::Any& Arg25, const css::uno::Any& Arg26, const css::uno::Any& Arg27, const css::uno::Any& Arg28, const css::uno::Any& Arg29, const css::uno::Any& Arg30 ) throw (css::script::BasicErrorException, css::uno::RuntimeException);
-+ virtual css::uno::Reference< ov::excel::XRange > SAL_CALL Union( const css::uno::Reference< ov::excel::XRange >& Arg1, const css::uno::Reference< ov::excel::XRange >& Arg2, const css::uno::Any& Arg3, const css::uno::Any& Arg4, const css::uno::Any& Arg5, const css::uno::Any& Arg6, const css::uno::Any& Arg7, const css::uno::Any& Arg8, const css::uno::Any& Arg9, const css::uno::Any& Arg10, const css::uno::Any& Arg11, const css::uno::Any& Arg12, const css::uno::Any& Arg13, const css::uno::Any& Arg14, const css::uno::Any& Arg15, const css::uno::Any& Arg16, const css::uno::Any& Arg17, const css::uno::Any& Arg18, const css::uno::Any& Arg19, const css::uno::Any& Arg20, const css::uno::Any& Arg21, const css::uno::Any& Arg22, const css::uno::Any& Arg23, const css::uno::Any& Arg24, const css::uno::Any& Arg25, const css::uno::Any& Arg26, const css::uno::Any& Arg27, const css::uno::Any& Arg28, const css::uno::Any& Arg29, const css::uno::Any& Arg30 ) throw (css::script::BasicErrorException, css::uno::RuntimeException);
-+
-+
-+
-+ // XMultiServiceFactory
-+ virtual css::uno::Sequence< ::rtl::OUString > SAL_CALL getAvailableServiceNames( ) throw (css::uno::RuntimeException);
-+ // XHelperInterface
-+ virtual rtl::OUString& getServiceImplName();
-+ virtual css::uno::Sequence<rtl::OUString> getServiceNames();
- };
- #endif //
---- sc/source/ui/vba/vbahelper.cxx
-+++ sc/source/ui/vba/vbahelper.cxx
-@@ -1,828 +0,0 @@
--/*************************************************************************
-- *
-- * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-- *
-- * Copyright 2008 by Sun Microsystems, Inc.
-- *
-- * OpenOffice.org - a multi-platform office productivity suite
-- *
-- * $RCSfile: vbahelper.cxx,v $
-- * $Revision: 1.5.32.1 $
-- *
-- * 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 <cppuhelper/bootstrap.hxx>
--#include <com/sun/star/util/XURLTransformer.hpp>
--#include <com/sun/star/frame/XDispatchProvider.hpp>
--#include <com/sun/star/frame/XModel.hpp>
--#include <com/sun/star/frame/XFrame.hpp>
--#include <com/sun/star/frame/XDesktop.hpp>
--#include <com/sun/star/frame/XController.hpp>
--#include <com/sun/star/uno/XComponentContext.hpp>
--#include <com/sun/star/lang/XMultiComponentFactory.hpp>
--#include <com/sun/star/beans/XPropertySet.hpp>
--#include <com/sun/star/beans/XIntrospection.hpp>
--
--#include <comphelper/processfactory.hxx>
--
--#include <sfx2/objsh.hxx>
--#include <sfx2/viewfrm.hxx>
--#include <sfx2/dispatch.hxx>
--#include <sfx2/app.hxx>
--#include <svtools/stritem.hxx>
--
--#include <docuno.hxx>
--
--#include <basic/sbx.hxx>
--#include <basic/sbstar.hxx>
--#include <rtl/math.hxx>
--
--#include <math.h>
--#include "vbahelper.hxx"
--#include "tabvwsh.hxx"
--#include "transobj.hxx"
--#include "scmod.hxx"
--#include "vbashape.hxx"
--#include "unonames.hxx"
--#include "cellsuno.hxx"
--using namespace ::com::sun::star;
--using namespace ::ooo::vba;
--
--#define POINTTO100THMILLIMETERFACTOR 35.27778
--void unoToSbxValue( SbxVariable* pVar, const uno::Any& aValue );
--
--uno::Any sbxToUnoValue( SbxVariable* pVar );
--
--
--namespace ooo
--{
--namespace vba
--{
--
--const double Millimeter::factor = 35.27778;
--
--uno::Reference< beans::XIntrospectionAccess >
--getIntrospectionAccess( const uno::Any& aObject ) throw (uno::RuntimeException)
--{
-- static uno::Reference< beans::XIntrospection > xIntrospection;
-- if( !xIntrospection.is() )
-- {
-- uno::Reference< lang::XMultiServiceFactory > xFactory( comphelper::getProcessServiceFactory(), uno::UNO_QUERY_THROW );
-- xIntrospection.set( xFactory->createInstance( rtl::OUString::createFromAscii("com.sun.star.beans.Introspection") ), uno::UNO_QUERY_THROW );
-- }
-- return xIntrospection->inspect( aObject );
--}
--
--uno::Reference< script::XTypeConverter >
--getTypeConverter( const uno::Reference< uno::XComponentContext >& xContext ) throw (uno::RuntimeException)
--{
-- static uno::Reference< script::XTypeConverter > xTypeConv( xContext->getServiceManager()->createInstanceWithContext( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("com.sun.star.script.Converter") ), xContext ), uno::UNO_QUERY_THROW );
-- return xTypeConv;
--}
--// helper method to determine if the view ( calc ) is in print-preview mode
--bool isInPrintPreview( SfxViewFrame* pView )
--{
-- sal_uInt16 nViewNo = SID_VIEWSHELL1 - SID_VIEWSHELL0;
-- if ( pView->GetObjectShell()->GetFactory().GetViewFactoryCount() >
--nViewNo && !pView->GetObjectShell()->IsInPlaceActive() )
-- {
-- SfxViewFactory &rViewFactory =
-- pView->GetObjectShell()->GetFactory().GetViewFactory(nViewNo);
-- if ( pView->GetCurViewId() == rViewFactory.GetOrdinal() )
-- return true;
-- }
-- return false;
--}
--const ::rtl::OUString REPLACE_CELLS_WARNING( RTL_CONSTASCII_USTRINGPARAM( "ReplaceCellsWarning"));
--const uno::Any&
--aNULL()
--{
-- static uno::Any aNULLL = uno::makeAny( uno::Reference< uno::XInterface >() );
-- return aNULLL;
--}
--
--class PasteCellsWarningReseter
--{
--private:
-- bool bInitialWarningState;
-- static uno::Reference< beans::XPropertySet > getGlobalSheetSettings() throw ( uno::RuntimeException )
-- {
-- static uno::Reference< beans::XPropertySet > xTmpProps( ::comphelper::getProcessServiceFactory(), uno::UNO_QUERY_THROW );
-- static uno::Reference<uno::XComponentContext > xContext( xTmpProps->getPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "DefaultContext" ))), uno::UNO_QUERY_THROW );
-- static uno::Reference<lang::XMultiComponentFactory > xServiceManager(
-- xContext->getServiceManager(), uno::UNO_QUERY_THROW );
-- static uno::Reference< beans::XPropertySet > xProps( xServiceManager->createInstanceWithContext( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "com.sun.star.sheet.GlobalSheetSettings" ) ) ,xContext ), uno::UNO_QUERY_THROW );
-- return xProps;
-- }
--
-- bool getReplaceCellsWarning() throw ( uno::RuntimeException )
-- {
-- sal_Bool res = sal_False;
-- getGlobalSheetSettings()->getPropertyValue( REPLACE_CELLS_WARNING ) >>= res;
-- return ( res == sal_True );
-- }
--
-- void setReplaceCellsWarning( bool bState ) throw ( uno::RuntimeException )
-- {
-- getGlobalSheetSettings()->setPropertyValue( REPLACE_CELLS_WARNING, uno::makeAny( bState ) );
-- }
--public:
-- PasteCellsWarningReseter() throw ( uno::RuntimeException )
-- {
-- bInitialWarningState = getReplaceCellsWarning();
-- if ( bInitialWarningState )
-- setReplaceCellsWarning( false );
-- }
-- ~PasteCellsWarningReseter()
-- {
-- if ( bInitialWarningState )
-- {
-- // don't allow dtor to throw
-- try
-- {
-- setReplaceCellsWarning( true );
-- }
-- catch ( uno::Exception& /*e*/ ){}
-- }
-- }
--};
--
--void
--dispatchRequests (uno::Reference< frame::XModel>& xModel,rtl::OUString & aUrl, uno::Sequence< beans::PropertyValue >& sProps )
--{
--
-- util::URL url ;
-- url.Complete = aUrl;
-- rtl::OUString emptyString = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "" ));
-- uno::Reference<frame::XController> xController = xModel->getCurrentController();
-- uno::Reference<frame::XFrame> xFrame = xController->getFrame();
-- uno::Reference<frame::XDispatchProvider> xDispatchProvider (xFrame,uno::UNO_QUERY_THROW);
-- try
-- {
-- uno::Reference< beans::XPropertySet > xProps( ::comphelper::getProcessServiceFactory(), uno::UNO_QUERY_THROW );
-- uno::Reference<uno::XComponentContext > xContext( xProps->getPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "DefaultContext" ))), uno::UNO_QUERY_THROW );
-- if ( !xContext.is() )
-- {
-- return ;
-- }
--
-- uno::Reference<lang::XMultiComponentFactory > xServiceManager(
-- xContext->getServiceManager() );
-- if ( !xServiceManager.is() )
-- {
-- return ;
-- }
-- uno::Reference<util::XURLTransformer> xParser( xServiceManager->createInstanceWithContext( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "com.sun.star.util.URLTransformer" ) )
-- ,xContext), uno::UNO_QUERY_THROW );
-- if (!xParser.is())
-- return;
-- xParser->parseStrict (url);
-- }
-- catch ( uno::Exception & /*e*/ )
-- {
-- return ;
-- }
--
-- uno::Reference<frame::XDispatch> xDispatcher = xDispatchProvider->queryDispatch(url,emptyString,0);
--
-- uno::Sequence<beans::PropertyValue> dispatchProps(1);
--
-- sal_Int32 nProps = sProps.getLength();
-- beans::PropertyValue* pDest = dispatchProps.getArray();
-- if ( nProps )
-- {
-- dispatchProps.realloc( nProps + 1 );
-- // need to reaccquire pDest after realloc
-- pDest = dispatchProps.getArray();
-- beans::PropertyValue* pSrc = sProps.getArray();
-- for ( sal_Int32 index=0; index<nProps; ++index, ++pSrc, ++pDest )
-- *pDest = *pSrc;
-- }
--
-- (*pDest).Name = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "Silent" ));
-- (*pDest).Value <<= (sal_Bool)sal_True;
--
-- if (xDispatcher.is())
-- xDispatcher->dispatch( url, dispatchProps );
--}
--
--void
--dispatchRequests (uno::Reference< frame::XModel>& xModel,rtl::OUString & aUrl)
--{
-- uno::Sequence<beans::PropertyValue> dispatchProps;
-- dispatchRequests( xModel, aUrl, dispatchProps );
--}
--
--
--void dispatchExecute(css::uno::Reference< css::frame::XModel>& xModel, USHORT nSlot, SfxCallMode nCall)
--{
-- ScTabViewShell* pViewShell = getBestViewShell( xModel );
-- SfxViewFrame* pViewFrame = NULL;
-- if ( pViewShell )
-- pViewFrame = pViewShell->GetViewFrame();
-- if ( pViewFrame )
-- {
-- SfxDispatcher* pDispatcher = pViewFrame->GetDispatcher();
-- if( pDispatcher )
-- {
-- pDispatcher->Execute( nSlot , nCall );
-- }
-- }
--}
--
--void
--implnPaste()
--{
-- PasteCellsWarningReseter resetWarningBox;
-- ScTabViewShell* pViewShell = getCurrentBestViewShell();
-- if ( pViewShell )
-- {
-- pViewShell->PasteFromSystem();
-- pViewShell->CellContentChanged();
-- }
--}
--
--
--void
--implnCopy()
--{
-- ScTabViewShell* pViewShell = getCurrentBestViewShell();
-- if ( pViewShell )
-- pViewShell->CopyToClip(NULL,false,false,true);
--}
--
--void
--implnCut()
--{
-- ScTabViewShell* pViewShell = getCurrentBestViewShell();
-- if ( pViewShell )
-- pViewShell->CutToClip( NULL, TRUE );
--}
--
--void implnPasteSpecial(USHORT nFlags,USHORT nFunction,sal_Bool bSkipEmpty, sal_Bool bTranspose)
--{
-- PasteCellsWarningReseter resetWarningBox;
-- sal_Bool bAsLink(sal_False), bOtherDoc(sal_False);
-- InsCellCmd eMoveMode = INS_NONE;
--
-- ScTabViewShell* pTabViewShell = ScTabViewShell::GetActiveViewShell();
-- if ( !pTabViewShell )
-- // none active, try next best
-- pTabViewShell = getCurrentBestViewShell();
-- if ( pTabViewShell )
-- {
-- ScViewData* pView = pTabViewShell->GetViewData();
-- Window* pWin = ( pView != NULL ) ? pView->GetActiveWin() : NULL;
-- if ( pView && pWin )
-- {
-- if ( bAsLink && bOtherDoc )
-- pTabViewShell->PasteFromSystem(0);//SOT_FORMATSTR_ID_LINK
-- else
-- {
-- ScTransferObj* pOwnClip = ScTransferObj::GetOwnClipboard( pWin );
-- ScDocument* pDoc = NULL;
-- if ( pOwnClip )
-- pDoc = pOwnClip->GetDocument();
-- pTabViewShell->PasteFromClip( nFlags, pDoc,
-- nFunction, bSkipEmpty, bTranspose, bAsLink,
-- eMoveMode, IDF_NONE, TRUE );
-- pTabViewShell->CellContentChanged();
-- }
-- }
-- }
--
--}
--
-- uno::Reference< frame::XModel >
--getCurrentDocument() throw (uno::RuntimeException)
--{
-- uno::Reference< frame::XModel > xModel;
-- SbxObject* pBasic = dynamic_cast< SbxObject* > ( SFX_APP()->GetBasic() );
-- SbxObject* basicChosen = pBasic ;
-- if ( basicChosen == NULL)
-- {
-- OSL_TRACE("getModelFromBasic() StarBASIC* is NULL" );
-- return xModel;
-- }
-- SbxObject* p = pBasic;
-- SbxObject* pParent = p->GetParent();
-- SbxObject* pParentParent = pParent ? pParent->GetParent() : NULL;
--
-- if( pParentParent )
-- {
-- basicChosen = pParentParent;
-- }
-- else if( pParent )
-- {
-- basicChosen = pParent;
-- }
--
--
-- uno::Any aModel;
-- SbxVariable *pCompVar = basicChosen->Find( UniString(RTL_CONSTASCII_USTRINGPARAM("ThisComponent")), SbxCLASS_OBJECT );
--
-- if ( pCompVar )
-- {
-- aModel = sbxToUnoValue( pCompVar );
-- if ( sal_False == ( aModel >>= xModel ) ||
-- !xModel.is() )
-- {
-- // trying last gasp try the current component
-- uno::Reference< beans::XPropertySet > xProps( ::comphelper::getProcessServiceFactory(), uno::UNO_QUERY_THROW );
-- // test if vba service is present
-- uno::Reference< uno::XComponentContext > xCtx( xProps->getPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "DefaultContext" ))), uno::UNO_QUERY_THROW );
-- uno::Reference<lang::XMultiComponentFactory > xSMgr( xCtx->getServiceManager(), uno::UNO_QUERY_THROW );
-- uno::Reference< frame::XDesktop > xDesktop (xSMgr->createInstanceWithContext(::rtl::OUString::createFromAscii("com.sun.star.frame.Desktop"), xCtx), uno::UNO_QUERY_THROW );
-- xModel.set( xDesktop->getCurrentComponent(), uno::UNO_QUERY );
-- if ( !xModel.is() )
-- {
-- throw uno::RuntimeException(
-- rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "Can't extract model from basic ( its obviously not set yet ) therefore don't know the currently selected document") ), uno::Reference< uno::XInterface >() );
-- }
-- return xModel;
-- }
-- else
-- {
-- OSL_TRACE("Have model ThisComponent points to url %s",
-- ::rtl::OUStringToOString( xModel->getURL(),
-- RTL_TEXTENCODING_ASCII_US ).pData->buffer );
-- }
-- }
-- else
-- {
-- OSL_TRACE("Failed to get ThisComponent");
-- throw uno::RuntimeException(
-- rtl::OUString(
-- RTL_CONSTASCII_USTRINGPARAM(
-- "Can't determine the currently selected document") ),
-- uno::Reference< uno::XInterface >() );
-- }
-- return xModel;
--}
--
--ScDocShell*
--getDocShell( css::uno::Reference< css::frame::XModel>& xModel )
--{
-- uno::Reference< uno::XInterface > xIf( xModel, uno::UNO_QUERY_THROW );
-- ScModelObj* pModel = dynamic_cast< ScModelObj* >( xIf.get() );
-- ScDocShell* pDocShell = NULL;
-- if ( pModel )
-- pDocShell = (ScDocShell*)pModel->GetEmbeddedObject();
-- return pDocShell;
--
--}
--
--ScTabViewShell*
--getBestViewShell( css::uno::Reference< css::frame::XModel>& xModel )
--{
-- ScDocShell* pDocShell = getDocShell( xModel );
-- if ( pDocShell )
-- return pDocShell->GetBestViewShell();
-- return NULL;
--}
--
--ScTabViewShell*
--getCurrentBestViewShell()
--{
-- uno::Reference< frame::XModel > xModel = getCurrentDocument();
-- return getBestViewShell( xModel );
--}
--
--SfxViewFrame*
--getCurrentViewFrame()
--{
-- ScTabViewShell* pViewShell = getCurrentBestViewShell();
-- if ( pViewShell )
-- return pViewShell->GetViewFrame();
-- return NULL;
--}
--
--sal_Int32
--OORGBToXLRGB( sal_Int32 nCol )
--{
-- sal_Int32 nRed = nCol;
-- nRed &= 0x00FF0000;
-- nRed >>= 16;
-- sal_Int32 nGreen = nCol;
-- nGreen &= 0x0000FF00;
-- nGreen >>= 8;
-- sal_Int32 nBlue = nCol;
-- nBlue &= 0x000000FF;
-- sal_Int32 nRGB = ( (nBlue << 16) | (nGreen << 8) | nRed );
-- return nRGB;
--}
--sal_Int32
--XLRGBToOORGB( sal_Int32 nCol )
--{
-- sal_Int32 nBlue = nCol;
-- nBlue &= 0x00FF0000;
-- nBlue >>= 16;
-- sal_Int32 nGreen = nCol;
-- nGreen &= 0x0000FF00;
-- nGreen >>= 8;
-- sal_Int32 nRed = nCol;
-- nRed &= 0x000000FF;
-- sal_Int32 nRGB = ( (nRed << 16) | (nGreen << 8) | nBlue );
-- return nRGB;
--}
--uno::Any
--OORGBToXLRGB( const uno::Any& aCol )
--{
-- sal_Int32 nCol=0;
-- aCol >>= nCol;
-- nCol = OORGBToXLRGB( nCol );
-- return uno::makeAny( nCol );
--}
--uno::Any
--XLRGBToOORGB( const uno::Any& aCol )
--{
-- sal_Int32 nCol=0;
-- aCol >>= nCol;
-- nCol = XLRGBToOORGB( nCol );
-- return uno::makeAny( nCol );
--}
--
--void PrintOutHelper( const uno::Any& From, const uno::Any& To, const uno::Any& Copies, const uno::Any& Preview, const uno::Any& /*ActivePrinter*/, const uno::Any& /*PrintToFile*/, const uno::Any& Collate, const uno::Any& PrToFileName, css::uno::Reference< frame::XModel >& xModel, sal_Bool bUseSelection )
--{
-- sal_Int32 nTo = 0;
-- sal_Int32 nFrom = 0;
-- sal_Int16 nCopies = 1;
-- sal_Bool bPreview = sal_False;
-- sal_Bool bCollate = sal_False;
-- sal_Bool bSelection = bUseSelection;
-- From >>= nFrom;
-- To >>= nTo;
-- Copies >>= nCopies;
-- Preview >>= bPreview;
-- if ( nCopies > 1 ) // Collate only useful when more that 1 copy
-- Collate >>= bCollate;
--
-- rtl::OUString sRange( RTL_CONSTASCII_USTRINGPARAM( "-" ) );
-- rtl::OUString sFileName;
--
-- if (( nFrom || nTo ) )
-- {
-- if ( nFrom )
-- sRange = ( ::rtl::OUString::valueOf( nFrom ) + sRange );
-- if ( nTo )
-- sRange += ::rtl::OUString::valueOf( nTo );
-- }
--
-- if ( PrToFileName.getValue() )
-- {
-- PrToFileName >>= sFileName;
-- }
-- ScTabViewShell* pViewShell = getBestViewShell( xModel );
-- SfxViewFrame* pViewFrame = NULL;
-- if ( pViewShell )
-- pViewFrame = pViewShell->GetViewFrame();
-- if ( pViewFrame )
-- {
-- SfxAllItemSet aArgs( SFX_APP()->GetPool() );
--
-- SfxBoolItem sfxCollate( SID_PRINT_COLLATE, bCollate );
-- aArgs.Put( sfxCollate, sfxCollate.Which() );
-- SfxInt16Item sfxCopies( SID_PRINT_COPIES, nCopies );
-- aArgs.Put( sfxCopies, sfxCopies.Which() );
-- if ( sFileName.getLength() )
-- {
-- SfxStringItem sfxFileName( SID_FILE_NAME, sFileName);
-- aArgs.Put( sfxFileName, sfxFileName.Which() );
--
-- }
-- if ( sRange.getLength() )
-- {
-- SfxStringItem sfxRange( SID_PRINT_PAGES, sRange );
-- aArgs.Put( sfxRange, sfxRange.Which() );
-- }
-- SfxBoolItem sfxSelection( SID_SELECTION, bSelection );
-- aArgs.Put( sfxSelection, sfxSelection.Which() );
-- SfxBoolItem sfxAsync( SID_ASYNCHRON, sal_False );
-- aArgs.Put( sfxAsync, sfxAsync.Which() );
-- SfxDispatcher* pDispatcher = pViewFrame->GetDispatcher();
--
-- if ( pDispatcher )
-- {
-- if ( bPreview )
-- {
-- if ( !pViewFrame->GetFrame()->IsInPlace() )
-- {
-- SC_MOD()->InputEnterHandler();
-- pViewFrame->GetDispatcher()->Execute( SID_VIEWSHELL1, SFX_CALLMODE_SYNCHRON );
-- while ( isInPrintPreview( pViewFrame ) )
-- Application::Yield();
-- }
-- }
-- else
-- pDispatcher->Execute( (USHORT)SID_PRINTDOC, (SfxCallMode)SFX_CALLMODE_SYNCHRON, aArgs );
-- }
--
-- }
--
-- // #FIXME #TODO
-- // 1 ActivePrinter ( how/can we switch a printer via API? )
-- // 2 PrintToFile ( ms behaviour if this option is specified but no
-- // filename supplied 'PrToFileName' then the user will be prompted )
-- // 3 Need to check behaviour of Selected sheets with range ( e.g. From & To
-- // values ) in oOO these options are mutually exclusive
-- // 4 There is a pop up to do with transparent objects in the print source
-- // should be able to disable that via configuration for the duration
-- // of this method
--}
--
-- void PrintPreviewHelper( const css::uno::Any& /*EnableChanges*/, css::uno::Reference< css::frame::XModel >& xModel )
--{
-- dispatchExecute( xModel, SID_VIEWSHELL1 );
--}
--
--rtl::OUString getAnyAsString( const uno::Any& pvargItem ) throw ( uno::RuntimeException )
--{
-- uno::Type aType = pvargItem.getValueType();
-- uno::TypeClass eTypeClass = aType.getTypeClass();
-- rtl::OUString sString;
-- switch ( eTypeClass )
-- {
-- case uno::TypeClass_BOOLEAN:
-- {
-- sal_Bool bBool = sal_False;
-- pvargItem >>= bBool;
-- sString = rtl::OUString::valueOf( bBool );
-- break;
-- }
-- case uno::TypeClass_STRING:
-- pvargItem >>= sString;
-- break;
-- case uno::TypeClass_FLOAT:
-- {
-- float aFloat = 0;
-- pvargItem >>= aFloat;
-- sString = rtl::OUString::valueOf( aFloat );
-- break;
-- }
-- case uno::TypeClass_DOUBLE:
-- {
-- double aDouble = 0;
-- pvargItem >>= aDouble;
-- sString = rtl::OUString::valueOf( aDouble );
-- break;
-- }
-- case uno::TypeClass_SHORT:
-- case uno::TypeClass_LONG:
-- case uno::TypeClass_BYTE:
-- {
-- sal_Int32 aNum = 0;
-- pvargItem >>= aNum;
-- sString = rtl::OUString::valueOf( aNum );
-- break;
-- }
--
-- case uno::TypeClass_HYPER:
-- {
-- sal_Int64 aHyper = 0;
-- pvargItem >>= aHyper;
-- sString = rtl::OUString::valueOf( aHyper );
-- break;
-- }
-- default:
-- throw uno::RuntimeException( rtl::OUString::createFromAscii( "Invalid type, can't convert" ), uno::Reference< uno::XInterface >() );
-- }
-- return sString;
--}
--
--
--rtl::OUString
--ContainerUtilities::getUniqueName( const uno::Sequence< ::rtl::OUString >& _slist, const rtl::OUString& _sElementName, const ::rtl::OUString& _sSuffixSeparator)
--{
-- return getUniqueName(_slist, _sElementName, _sSuffixSeparator, sal_Int32(2));
--}
--
--rtl::OUString
--ContainerUtilities::getUniqueName( const uno::Sequence< rtl::OUString >& _slist, const rtl::OUString _sElementName, const rtl::OUString& _sSuffixSeparator, sal_Int32 _nStartSuffix)
--{
-- sal_Int32 a = _nStartSuffix;
-- rtl::OUString scompname = _sElementName;
-- bool bElementexists = true;
-- sal_Int32 nLen = _slist.getLength();
-- if ( nLen == 0 )
-- return _sElementName;
--
-- while (bElementexists == true)
-- {
-- for (sal_Int32 i = 0; i < nLen; i++)
-- {
-- if (FieldInList(_slist, scompname) == -1)
-- {
-- return scompname;
-- }
-- }
-- scompname = _sElementName + _sSuffixSeparator + rtl::OUString::valueOf( a++ );
-- }
-- return rtl::OUString();
--}
--
--sal_Int32
--ContainerUtilities::FieldInList( const uno::Sequence< rtl::OUString >& SearchList, const rtl::OUString& SearchString )
--{
-- sal_Int32 FieldLen = SearchList.getLength();
-- sal_Int32 retvalue = -1;
-- for (sal_Int32 i = 0; i < FieldLen; i++)
-- {
-- // I wonder why comparing lexicographically is done
-- // when its a match is whats interesting?
-- //if (SearchList[i].compareTo(SearchString) == 0)
-- if ( SearchList[i].equals( SearchString ) )
-- {
-- retvalue = i;
-- break;
-- }
-- }
-- return retvalue;
--
--}
--bool NeedEsc(sal_Unicode cCode)
--{
-- String sEsc(RTL_CONSTASCII_USTRINGPARAM(".^$+\\|{}()"));
-- return (STRING_NOTFOUND != sEsc.Search(cCode));
--}
--
--rtl::OUString VBAToRegexp(const rtl::OUString &rIn, bool bForLike )
--{
-- rtl::OUStringBuffer sResult;
-- const sal_Unicode *start = rIn.getStr();
-- const sal_Unicode *end = start + rIn.getLength();
--
-- int seenright = 0;
-- if ( bForLike )
-- sResult.append(static_cast<sal_Unicode>('^'));
--
-- while (start < end)
-- {
-- switch (*start)
-- {
-- case '?':
-- sResult.append(static_cast<sal_Unicode>('.'));
-- start++;
-- break;
-- case '*':
-- sResult.append(rtl::OUString(RTL_CONSTASCII_USTRINGPARAM(".*")));
-- start++;
-- break;
-- case '#':
-- sResult.append(rtl::OUString(RTL_CONSTASCII_USTRINGPARAM("[0-9]")));
-- start++;
-- break;
-- case '~':
-- sResult.append(static_cast<sal_Unicode>('\\'));
-- sResult.append(*(++start));
-- start++;
-- break;
-- // dump the ~ and escape the next characture
-- case ']':
-- sResult.append(static_cast<sal_Unicode>('\\'));
-- sResult.append(*start++);
-- break;
-- case '[':
-- sResult.append(*start++);
-- seenright = 0;
-- while (start < end && !seenright)
-- {
-- switch (*start)
-- {
-- case '[':
-- case '?':
-- case '*':
-- sResult.append(static_cast<sal_Unicode>('\\'));
-- sResult.append(*start);
-- break;
-- case ']':
-- sResult.append(*start);
-- seenright = 1;
-- break;
-- case '!':
-- sResult.append(static_cast<sal_Unicode>('^'));
-- break;
-- default:
-- if (NeedEsc(*start))
-- sResult.append(static_cast<sal_Unicode>('\\'));
-- sResult.append(*start);
-- break;
-- }
-- start++;
-- }
-- break;
-- default:
-- if (NeedEsc(*start))
-- sResult.append(static_cast<sal_Unicode>('\\'));
-- sResult.append(*start++);
-- }
-- }
--
-- if ( bForLike )
-- sResult.append(static_cast<sal_Unicode>('$'));
--
-- return sResult.makeStringAndClear( );
--}
--
--double getPixelTo100thMillimeterConversionFactor( css::uno::Reference< css::awt::XDevice >& xDevice, sal_Bool bVertical)
--{
-- double fConvertFactor = 1.0;
-- if( bVertical )
-- {
-- fConvertFactor = xDevice->getInfo().PixelPerMeterY/100000;
-- }
-- else
-- {
-- fConvertFactor = xDevice->getInfo().PixelPerMeterX/100000;
-- }
-- return fConvertFactor;
--}
--
--double PointsToPixels( css::uno::Reference< css::awt::XDevice >& xDevice, double fPoints, sal_Bool bVertical)
--{
-- double fConvertFactor = getPixelTo100thMillimeterConversionFactor( xDevice, bVertical );
-- return fPoints * POINTTO100THMILLIMETERFACTOR * fConvertFactor;
--}
--double PixelsToPoints( css::uno::Reference< css::awt::XDevice >& xDevice, double fPixels, sal_Bool bVertical)
--{
-- double fConvertFactor = getPixelTo100thMillimeterConversionFactor( xDevice, bVertical );
-- return (fPixels/fConvertFactor)/POINTTO100THMILLIMETERFACTOR;
--}
--
--ConcreteXShapeGeometryAttributes::ConcreteXShapeGeometryAttributes( const css::uno::Reference< css::uno::XComponentContext >& xContext, const css::uno::Reference< css::drawing::XShape >& xShape )
--{
-- m_xShape = new ScVbaShape( xContext, xShape );
--}
--
--#define VBA_LEFT "PositionX"
--#define VBA_TOP "PositionY"
--UserFormGeometryHelper::UserFormGeometryHelper( const uno::Reference< uno::XComponentContext >& /*xContext*/, const uno::Reference< awt::XControl >& xControl )
--{
-- mxModel.set( xControl->getModel(), uno::UNO_QUERY_THROW );
--}
-- double UserFormGeometryHelper::getLeft()
-- {
-- sal_Int32 nLeft = 0;
-- mxModel->getPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( VBA_LEFT ) ) ) >>= nLeft;
-- return Millimeter::getInPoints( nLeft );
-- }
-- void UserFormGeometryHelper::setLeft( double nLeft )
-- {
-- mxModel->setPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( VBA_LEFT ) ), uno::makeAny( Millimeter::getInHundredthsOfOneMillimeter( nLeft ) ) );
-- }
-- double UserFormGeometryHelper::getTop()
-- {
-- sal_Int32 nTop = 0;
-- mxModel->getPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( VBA_TOP ) ) ) >>= nTop;
-- return Millimeter::getInPoints( nTop );
-- }
-- void UserFormGeometryHelper::setTop( double nTop )
-- {
-- mxModel->setPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( VBA_TOP ) ), uno::makeAny( Millimeter::getInHundredthsOfOneMillimeter( nTop ) ) );
-- }
-- double UserFormGeometryHelper::getHeight()
-- {
-- sal_Int32 nHeight = 0;
-- mxModel->getPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( SC_UNONAME_CELLHGT ) ) ) >>= nHeight;
-- return Millimeter::getInPoints( nHeight );
-- }
-- void UserFormGeometryHelper::setHeight( double nHeight )
-- {
-- mxModel->setPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( SC_UNONAME_CELLHGT ) ), uno::makeAny( Millimeter::getInHundredthsOfOneMillimeter( nHeight ) ) );
-- }
-- double UserFormGeometryHelper::getWidth()
-- {
-- sal_Int32 nWidth = 0;
-- mxModel->getPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( SC_UNONAME_CELLWID ) ) ) >>= nWidth;
-- return Millimeter::getInPoints( nWidth );
-- }
-- void UserFormGeometryHelper::setWidth( double nWidth)
-- {
-- mxModel->setPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( SC_UNONAME_CELLWID ) ), uno::makeAny( Millimeter::getInHundredthsOfOneMillimeter( nWidth ) ) );
-- }
--
--SfxItemSet*
--ScVbaCellRangeAccess::GetDataSet( ScCellRangeObj* pRangeObj )
--{
-- SfxItemSet* pDataSet = pRangeObj ? pRangeObj->GetCurrentDataSet( true ) : NULL ;
-- return pDataSet;
--
--}
--
--} // openoffice
--} //org
---- sc/source/ui/vba/vbahelper.hxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbahelper.hxx 1970-01-01 00:00:00.000000000 +0000
-@@ -1,352 +0,0 @@
--/*************************************************************************
-- *
-- * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-- *
-- * Copyright 2008 by Sun Microsystems, Inc.
-- *
-- * OpenOffice.org - a multi-platform office productivity suite
-- *
-- * $RCSfile: vbahelper.hxx,v $
-- * $Revision: 1.5.32.1 $
-- *
-- * 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.
-- *
-- ************************************************************************/
--#ifndef SC_VBA_HELPER_HXX
--#define SC_VBA_HELPER_HXX
--
--#include <com/sun/star/drawing/XShape.hpp>
--#include <com/sun/star/beans/XIntrospectionAccess.hpp>
--#include <com/sun/star/script/BasicErrorException.hpp>
--#include <com/sun/star/script/XTypeConverter.hpp>
--#include <com/sun/star/lang/IllegalArgumentException.hpp>
--#include <com/sun/star/awt/XControl.hpp>
--#include <com/sun/star/awt/XDevice.hpp>
--#include <basic/sberrors.hxx>
--#include <cppuhelper/implbase1.hxx>
--#include <com/sun/star/frame/XModel.hpp>
--#include <docsh.hxx>
--#include <sfx2/dispatch.hxx>
--#include <ooo/vba/msforms/XShape.hpp>
--#include "cellsuno.hxx"
--
--namespace css = ::com::sun::star;
--
--namespace ooo
--{
-- namespace vba
-- {
-- template < class T >
-- css::uno::Reference< T > getXSomethingFromArgs( css::uno::Sequence< css::uno::Any > const & args, sal_Int32 nPos, bool bCanBeNull = true ) throw (css::lang::IllegalArgumentException)
-- {
-- if ( args.getLength() < ( nPos + 1) )
-- throw css::lang::IllegalArgumentException();
-- css::uno::Reference< T > aSomething( args[ nPos ], css::uno::UNO_QUERY );
-- if ( !bCanBeNull && !aSomething.is() )
-- throw css::lang::IllegalArgumentException();
-- return aSomething;
-- }
-- css::uno::Reference< css::beans::XIntrospectionAccess > getIntrospectionAccess( const css::uno::Any& aObject ) throw (css::uno::RuntimeException);
-- css::uno::Reference< css::script::XTypeConverter > getTypeConverter( const css::uno::Reference< css::uno::XComponentContext >& xContext ) throw (css::uno::RuntimeException);
--
-- void dispatchRequests (css::uno::Reference< css::frame::XModel>& xModel,rtl::OUString & aUrl) ;
-- void dispatchRequests (css::uno::Reference< css::frame::XModel>& xModel,rtl::OUString & aUrl, css::uno::Sequence< css::beans::PropertyValue >& sProps ) ;
-- void dispatchExecute(css::uno::Reference< css::frame::XModel>& xModel, USHORT nSlot, SfxCallMode nCall = SFX_CALLMODE_SYNCHRON );
-- void implnCopy();
-- void implnPaste();
-- void implnCut();
-- void implnPasteSpecial(sal_uInt16 nFlags,sal_uInt16 nFunction,sal_Bool bSkipEmpty, sal_Bool bTranspose);
-- css::uno::Reference< css::frame::XModel >
-- getCurrentDocument() throw (css::uno::RuntimeException);
-- ScTabViewShell* getBestViewShell( css::uno::Reference< css::frame::XModel>& xModel ) ;
-- ScDocShell* getDocShell( css::uno::Reference< css::frame::XModel>& xModel ) ;
-- ScTabViewShell* getCurrentBestViewShell();
-- SfxViewFrame* getCurrentViewFrame();
-- sal_Int32 OORGBToXLRGB( sal_Int32 );
-- sal_Int32 XLRGBToOORGB( sal_Int32 );
-- css::uno::Any OORGBToXLRGB( const css::uno::Any& );
-- css::uno::Any XLRGBToOORGB( const css::uno::Any& );
-- // provide a NULL object that can be passed as variant so that
-- // the object when passed to IsNull will return true. aNULL
-- // contains an empty object reference
-- const css::uno::Any& aNULL();
-- void PrintOutHelper( const css::uno::Any& From, const css::uno::Any& To, const css::uno::Any& Copies, const css::uno::Any& Preview, const css::uno::Any& ActivePrinter, const css::uno::Any& PrintToFile, const css::uno::Any& Collate, const css::uno::Any& PrToFileName, css::uno::Reference< css::frame::XModel >& xModel, sal_Bool bSelection );
-- void PrintPreviewHelper( const css::uno::Any& EnableChanges, css::uno::Reference< css::frame::XModel >& xModel );
--
-- rtl::OUString getAnyAsString( const css::uno::Any& pvargItem ) throw ( css::uno::RuntimeException );
-- rtl::OUString VBAToRegexp(const rtl::OUString &rIn, bool bForLike = false); // needs to be in an uno service ( already this code is duplicated in basic )
-- double getPixelTo100thMillimeterConversionFactor( css::uno::Reference< css::awt::XDevice >& xDevice, sal_Bool bVertical);
-- double PointsToPixels( css::uno::Reference< css::awt::XDevice >& xDevice, double fPoints, sal_Bool bVertical);
-- double PixelsToPoints( css::uno::Reference< css::awt::XDevice >& xDevice, double fPoints, sal_Bool bVertical);
--
--
--class ScVbaCellRangeAccess
--{
--public:
-- static SfxItemSet* GetDataSet( ScCellRangeObj* pRangeObj );
--};
--
--class Millimeter
--{
--//Factor to translate between points and hundredths of millimeters:
--private:
-- static const double factor;
--
-- double m_nMillimeter;
--
--public:
-- Millimeter():m_nMillimeter(0) {}
--
-- Millimeter(double mm):m_nMillimeter(mm) {}
--
-- void set(double mm) { m_nMillimeter = mm; }
-- void setInPoints(double points)
-- {
-- m_nMillimeter = points * 0.352777778;
-- // 25.4mm / 72
-- }
--
-- void setInHundredthsOfOneMillimeter(double hmm)
-- {
-- m_nMillimeter = hmm / 100;
-- }
--
-- double get()
-- {
-- return m_nMillimeter;
-- }
-- double getInHundredthsOfOneMillimeter()
-- {
-- return m_nMillimeter * 100;
-- }
-- double getInPoints()
-- {
-- return m_nMillimeter * 2.834645669; // 72 / 25.4mm
-- }
--
-- static sal_Int32 getInHundredthsOfOneMillimeter(double points)
-- {
-- sal_Int32 mm = static_cast<sal_Int32>(points * factor);
-- return mm;
-- }
--
-- static double getInPoints(int _hmm)
-- {
-- double points = double( static_cast<double>(_hmm) / factor);
-- return points;
-- }
--};
--
--class AbstractGeometryAttributes // probably should replace the ShapeHelper below
--{
--public:
-- virtual ~AbstractGeometryAttributes() {}
-- virtual double getLeft() = 0;
-- virtual void setLeft( double ) = 0;
-- virtual double getTop() = 0;
-- virtual void setTop( double ) = 0;
-- virtual double getHeight() = 0;
-- virtual void setHeight( double ) = 0;
-- virtual double getWidth() = 0;
-- virtual void setWidth( double ) = 0;
--};
--
--class ConcreteXShapeGeometryAttributes : public AbstractGeometryAttributes
--{
--public:
-- css::uno::Reference< ooo::vba::msforms::XShape > m_xShape;
-- ConcreteXShapeGeometryAttributes( const css::uno::Reference< css::uno::XComponentContext >& xContext, const css::uno::Reference< css::drawing::XShape >& xShape );
-- virtual double getLeft()
-- {
-- return m_xShape->getLeft();
-- }
-- virtual void setLeft( double nLeft )
-- {
-- m_xShape->setLeft( nLeft );
-- }
-- virtual double getTop()
-- {
-- return m_xShape->getTop();
-- }
-- virtual void setTop( double nTop )
-- {
-- m_xShape->setTop( nTop );
-- }
--
-- virtual double getHeight()
-- {
-- return m_xShape->getHeight();
-- }
-- virtual void setHeight( double nHeight )
-- {
-- m_xShape->setHeight( nHeight );
-- }
-- virtual double getWidth()
-- {
-- return m_xShape->getWidth();
-- }
-- virtual void setWidth( double nWidth)
-- {
-- m_xShape->setHeight( nWidth );
-- }
--
--
--};
--#define VBA_LEFT "PositionX"
--#define VBA_TOP "PositionY"
--class UserFormGeometryHelper : public AbstractGeometryAttributes
--{
--
-- css::uno::Reference< css::beans::XPropertySet > mxModel;
--public:
-- UserFormGeometryHelper( const css::uno::Reference< css::uno::XComponentContext >& xContext, const css::uno::Reference< css::awt::XControl >& xControl );
-- virtual double getLeft();
-- virtual void setLeft( double nLeft );
-- virtual double getTop();
-- virtual void setTop( double nTop );
-- virtual double getHeight();
-- virtual void setHeight( double nHeight );
-- virtual double getWidth();
-- virtual void setWidth( double nWidth);
--};
--
--class ShapeHelper
--{
--protected:
-- css::uno::Reference< css::drawing::XShape > xShape;
--public:
-- ShapeHelper( const css::uno::Reference< css::drawing::XShape >& _xShape) throw (css::script::BasicErrorException ) : xShape( _xShape )
-- {
-- if( !xShape.is() )
-- throw css::uno::RuntimeException( rtl::OUString::createFromAscii("No valid shape for helper"), css::uno::Reference< css::uno::XInterface >() );
-- }
--
-- double getHeight()
-- {
-- return Millimeter::getInPoints(xShape->getSize().Height);
-- }
--
--
-- void setHeight(double _fheight) throw ( css::script::BasicErrorException )
-- {
-- try
-- {
-- css::awt::Size aSize = xShape->getSize();
-- aSize.Height = Millimeter::getInHundredthsOfOneMillimeter(_fheight);
-- xShape->setSize(aSize);
-- }
-- catch ( css::uno::Exception& /*e*/)
-- {
-- throw css::script::BasicErrorException( rtl::OUString(), css::uno::Reference< css::uno::XInterface >(), SbERR_METHOD_FAILED, rtl::OUString() );
-- }
-- }
--
--
-- double getWidth()
-- {
-- return Millimeter::getInPoints(xShape->getSize().Width);
-- }
--
-- void setWidth(double _fWidth) throw ( css::script::BasicErrorException )
-- {
-- try
-- {
-- css::awt::Size aSize = xShape->getSize();
-- aSize.Width = Millimeter::getInHundredthsOfOneMillimeter(_fWidth);
-- xShape->setSize(aSize);
-- }
-- catch (css::uno::Exception& /*e*/)
-- {
-- throw css::script::BasicErrorException( rtl::OUString(), css::uno::Reference< css::uno::XInterface >(), SbERR_METHOD_FAILED, rtl::OUString() );
-- }
-- }
--
--
-- double getLeft()
-- {
-- return Millimeter::getInPoints(xShape->getPosition().X);
-- }
--
--
-- void setLeft(double _fLeft)
-- {
-- css::awt::Point aPoint = xShape->getPosition();
-- aPoint.X = Millimeter::getInHundredthsOfOneMillimeter(_fLeft);
-- xShape->setPosition(aPoint);
-- }
--
--
-- double getTop()
-- {
-- return Millimeter::getInPoints(xShape->getPosition().Y);
-- }
--
--
-- void setTop(double _fTop)
-- {
-- css::awt::Point aPoint = xShape->getPosition();
-- aPoint.Y = Millimeter::getInHundredthsOfOneMillimeter(_fTop);
-- xShape->setPosition(aPoint);
-- }
--
--};
--
--class ContainerUtilities
--{
--
--public:
-- static rtl::OUString getUniqueName( const css::uno::Sequence< ::rtl::OUString >& _slist, const rtl::OUString& _sElementName, const ::rtl::OUString& _sSuffixSeparator);
-- static rtl::OUString getUniqueName( const css::uno::Sequence< rtl::OUString >& _slist, const rtl::OUString _sElementName, const rtl::OUString& _sSuffixSeparator, sal_Int32 _nStartSuffix );
--
-- static sal_Int32 FieldInList( const css::uno::Sequence< rtl::OUString >& SearchList, const rtl::OUString& SearchString );
--};
--
--// really just a a place holder to ease the porting pain
--class DebugHelper
--{
--public:
-- static void exception( const rtl::OUString& DetailedMessage, const css::uno::Exception& ex, int err, const rtl::OUString& /*additionalArgument*/ ) throw( css::script::BasicErrorException )
-- {
-- // #TODO #FIXME ( do we want to support additionalArg here )
-- throw css::script::BasicErrorException( DetailedMessage.concat( rtl::OUString::createFromAscii(" ") ).concat( ex.Message ), css::uno::Reference< css::uno::XInterface >(), err, rtl::OUString() );
-- }
--
-- static void exception( int err, const rtl::OUString& additionalArgument ) throw( css::script::BasicErrorException )
-- {
-- exception( rtl::OUString(), css::uno::Exception(), err, additionalArgument );
-- }
--
-- static void exception( css::uno::Exception& ex ) throw( css::script::BasicErrorException )
-- {
-- exception( rtl::OUString(), ex, SbERR_INTERNAL_ERROR, rtl::OUString() );
-- }
--};
-- } // openoffice
--} // org
--
--namespace ov = ooo::vba;
--
--#ifdef DEBUG
--# define SC_VBA_FIXME(a) OSL_TRACE( a )
--# define SC_VBA_STUB() SC_VBA_FIXME(( "%s - stubbed\n", __FUNCTION__ ))
--#else
--# define SC_VBA_FIXME(a)
--# define SC_VBA_STUB()
--#endif
--
--#endif
---- sc/source/ui/vba/vbahelperinterface.hxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbahelperinterface.hxx 1970-01-01 00:00:00.000000000 +0000
-@@ -1,116 +0,0 @@
--/*************************************************************************
-- *
-- * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-- *
-- * Copyright 2008 by Sun Microsystems, Inc.
-- *
-- * OpenOffice.org - a multi-platform office productivity suite
-- *
-- * $RCSfile: vbahelperinterface.hxx,v $
-- * $Revision: 1.3 $
-- *
-- * 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.
-- *
-- ************************************************************************/
--#ifndef SC_VBA_HELPERINTERFACE_HXX
--#define SC_VBA_HELPERINTERFACE_HXX
--
--#include <cppuhelper/implbase1.hxx>
--#include <ooo/vba/XHelperInterface.hpp>
--#include "vbahelper.hxx"
--#include "vbaglobals.hxx"
--
--// use this class when you have an a object like
--// interface XAnInterface which contains XHelperInterface in its inheritance hierarchy
--// interface XAnInterface
--// {
--// interface XHelperInterface;
--// [attribute, string] name;
--// }
--// or
--// interface XAnInterface : XHelperInterface;
--// {
--// [attribute, string] name;
--// }
--//
--// then this class can provide a default implementation of XHelperInterface,
--// you can use it like this
--// typedef InheritedHelperInterfaceImpl< XAnInterface > > AnInterfaceImpl_BASE;
--// class AnInterfaceImpl : public AnInterfaceImpl_BASE
--// {
--// public:
--// AnInterface( const Reference< HelperInterface >& xParent ) : AnInterfaceImpl_BASE( xParent ) {}
--// // implement XAnInterface methods only, no need to implement the XHelperInterface
--// // methods
--// virtual void setName( const OUString& );
--// virtual OUString getName();
--// }
--//
--const ::rtl::OUString sHelperServiceName( RTL_CONSTASCII_USTRINGPARAM( "ooo.vba.HelperServiceBase" ) );
--
--template< typename Ifc1 >
--class InheritedHelperInterfaceImpl : public Ifc1
--{
--protected:
-- css::uno::WeakReference< ov::XHelperInterface > mxParent;
-- css::uno::Reference< css::uno::XComponentContext > mxContext;
--public:
-- InheritedHelperInterfaceImpl() {}
-- InheritedHelperInterfaceImpl( const css::uno::Reference< ov::XHelperInterface >& xParent, const css::uno::Reference< css::uno::XComponentContext >& xContext ) : mxParent( xParent ), mxContext( xContext ) {}
-- virtual rtl::OUString& getServiceImplName() = 0;
-- virtual css::uno::Sequence<rtl::OUString> getServiceNames() = 0;
--
-- // XHelperInterface Methods
-- virtual ::sal_Int32 SAL_CALL getCreator() throw (css::script::BasicErrorException, css::uno::RuntimeException)
-- {
-- return 0x53756E4F;
-- }
-- virtual css::uno::Reference< ov::XHelperInterface > SAL_CALL getParent( ) throw (css::script::BasicErrorException, css::uno::RuntimeException) { return mxParent; }
--
-- virtual css::uno::Any SAL_CALL Application( ) throw (css::script::BasicErrorException, css::uno::RuntimeException) { return css::uno::makeAny( ScVbaGlobals::getGlobalsImpl( mxContext )->getApplication() ); }
--
--
-- // XServiceInfo Methods
-- virtual ::rtl::OUString SAL_CALL getImplementationName( ) throw (css::uno::RuntimeException) { return getServiceImplName(); }
-- virtual ::sal_Bool SAL_CALL supportsService( const ::rtl::OUString& ServiceName ) throw (css::uno::RuntimeException)
-- {
-- css::uno::Sequence< rtl::OUString > sServices = getSupportedServiceNames();
-- const rtl::OUString* pStart = sServices.getConstArray();
-- const rtl::OUString* pEnd = pStart + sServices.getLength();
-- for ( ; pStart != pEnd ; ++pStart )
-- if ( (*pStart).equals( ServiceName ) )
-- return sal_True;
-- return sal_False;
-- }
-- virtual css::uno::Sequence< ::rtl::OUString > SAL_CALL getSupportedServiceNames( ) throw (css::uno::RuntimeException)
-- {
-- css::uno::Sequence< rtl::OUString > aNames = getServiceNames();;
-- return aNames;
-- }
-- };
--
--template< typename Ifc1 >
--class InheritedHelperInterfaceImpl1 : public InheritedHelperInterfaceImpl< ::cppu::WeakImplHelper1< Ifc1 > >
--
--{
--typedef InheritedHelperInterfaceImpl< ::cppu::WeakImplHelper1< Ifc1 > > Base;
--public:
-- InheritedHelperInterfaceImpl1< Ifc1 > ( const css::uno::Reference< ov::XHelperInterface >& xParent, const css::uno::Reference< css::uno::XComponentContext >& xContext ) : Base( xParent, xContext ) {}
--
--};
--#endif
---- sc/source/ui/vba/vbahyperlink.cxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbahyperlink.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -32,7 +32,7 @@
- * MA 02111-1307 USA
- *
- ************************************************************************/
--#include "helperdecl.hxx"
-+#include <vbahelper/helperdecl.hxx>
- #include "vbahyperlink.hxx"
- #include <com/sun/star/container/XIndexAccess.hpp>
- #include <com/sun/star/text/XTextFieldsSupplier.hpp>
---- sc/source/ui/vba/vbahyperlink.hxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbahyperlink.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -40,7 +40,7 @@
- #include <com/sun/star/beans/XPropertySet.hpp>
- #include <ooo/vba/excel/XRange.hpp>
-
--#include "vbahelperinterface.hxx"
-+#include <vbahelper/vbahelperinterface.hxx>
-
- typedef InheritedHelperInterfaceImpl1< ov::excel::XHyperlink > HyperlinkImpl_BASE;
-
---- sc/source/ui/vba/vbaimage.cxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbaimage.cxx 1970-01-01 00:00:00.000000000 +0000
-@@ -1,59 +0,0 @@
--/*************************************************************************
-- *
-- * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-- *
-- * Copyright 2008 by Sun Microsystems, Inc.
-- *
-- * OpenOffice.org - a multi-platform office productivity suite
-- *
-- * $RCSfile$
-- * $Revision$
-- *
-- * 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 "vbaimage.hxx"
--#include <vector>
--
--using namespace com::sun::star;
--using namespace ooo::vba;
--
--
--const static rtl::OUString LABEL( RTL_CONSTASCII_USTRINGPARAM("Label") );
--ScVbaImage::ScVbaImage( const uno::Reference< XHelperInterface >& xParent, const uno::Reference< uno::XComponentContext >& xContext, const uno::Reference< uno::XInterface >& xControl, const uno::Reference< frame::XModel >& xModel, AbstractGeometryAttributes* pGeomHelper ) : ImageImpl_BASE( xParent, xContext, xControl, xModel, pGeomHelper )
--{
--}
--
--rtl::OUString&
--ScVbaImage::getServiceImplName()
--{
-- static rtl::OUString sImplName( RTL_CONSTASCII_USTRINGPARAM("ScVbaImage") );
-- return sImplName;
--}
--
--uno::Sequence< rtl::OUString >
--ScVbaImage::getServiceNames()
--{
-- static uno::Sequence< rtl::OUString > aServiceNames;
-- if ( aServiceNames.getLength() == 0 )
-- {
-- aServiceNames.realloc( 1 );
-- aServiceNames[ 0 ] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.msforms.Image" ) );
-- }
-- return aServiceNames;
--}
---- sc/source/ui/vba/vbaimage.hxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbaimage.hxx 1970-01-01 00:00:00.000000000 +0000
-@@ -1,48 +0,0 @@
--/*************************************************************************
-- *
-- * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-- *
-- * Copyright 2008 by Sun Microsystems, Inc.
-- *
-- * OpenOffice.org - a multi-platform office productivity suite
-- *
-- * $RCSfile$
-- * $Revision$
-- *
-- * 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.
-- *
-- ************************************************************************/
--#ifndef SC_VBA_IMAGE_HXX
--#define SC_VBA_IMAGE_HXX
--#include <cppuhelper/implbase1.hxx>
--#include <ooo/vba/msforms/XImage.hpp>
--
--#include "vbacontrol.hxx"
--#include "vbahelper.hxx"
--
--typedef cppu::ImplInheritanceHelper1< ScVbaControl, ov::msforms::XImage > ImageImpl_BASE;
--
--class ScVbaImage : public ImageImpl_BASE
--{
--public:
-- ScVbaImage( const css::uno::Reference< ov::XHelperInterface >& xParent, const css::uno::Reference< css::uno::XComponentContext >& xContext, const css::uno::Reference< css::uno::XInterface >& xControl, const css::uno::Reference< css::frame::XModel >& xModel, ov::AbstractGeometryAttributes* pGeomHelper );
-- //XHelperInterface
-- virtual rtl::OUString& getServiceImplName();
-- virtual css::uno::Sequence<rtl::OUString> getServiceNames();
--};
--#endif //SC_VBA_IMAGE_HXX
---- sc/source/ui/vba/vbainterior.hxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbainterior.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -34,9 +34,10 @@
- #include <com/sun/star/uno/XComponentContext.hpp>
- #include <com/sun/star/beans/XPropertySet.hpp>
- #include <com/sun/star/container/XIndexAccess.hpp>
-+#include <com/sun/star/container/XNameContainer.hpp>
-
- #include <com/sun/star/script/XInvocation.hpp>
--#include "vbahelperinterface.hxx"
-+#include <vbahelper/vbahelperinterface.hxx>
-
- class ScDocument;
-
---- sc/source/ui/vba/vbalabel.cxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbalabel.cxx 1970-01-01 00:00:00.000000000 +0000
-@@ -1,88 +0,0 @@
--/*************************************************************************
-- *
-- * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-- *
-- * Copyright 2008 by Sun Microsystems, Inc.
-- *
-- * OpenOffice.org - a multi-platform office productivity suite
-- *
-- * $RCSfile: vbalabel.cxx,v $
-- * $Revision: 1.3 $
-- *
-- * 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 "vbalabel.hxx"
--#include <vector>
--
--using namespace com::sun::star;
--using namespace ooo::vba;
--
--
--const static rtl::OUString LABEL( RTL_CONSTASCII_USTRINGPARAM("Label") );
--ScVbaLabel::ScVbaLabel( const css::uno::Reference< XHelperInterface >& xParent, const uno::Reference< uno::XComponentContext >& xContext, const uno::Reference< uno::XInterface >& xControl, const uno::Reference< frame::XModel >& xModel, ov::AbstractGeometryAttributes* pGeomHelper ) : LabelImpl_BASE( xParent, xContext, xControl, xModel, pGeomHelper )
--{
--}
--
--// Attributes
--rtl::OUString SAL_CALL
--ScVbaLabel::getCaption() throw (css::uno::RuntimeException)
--{
-- rtl::OUString Label;
-- m_xProps->getPropertyValue( LABEL ) >>= Label;
-- return Label;
--}
--
--void SAL_CALL
--ScVbaLabel::setCaption( const rtl::OUString& _caption ) throw (::com::sun::star::uno::RuntimeException)
--{
-- m_xProps->setPropertyValue( LABEL, uno::makeAny( _caption ) );
--}
--uno::Any SAL_CALL
--ScVbaLabel::getValue() throw (css::uno::RuntimeException)
--{
-- return uno::makeAny( getCaption() );
--}
--
--void SAL_CALL
--ScVbaLabel::setValue( const uno::Any& _value ) throw (::com::sun::star::uno::RuntimeException)
--{
-- rtl::OUString sCaption;
-- _value >>= sCaption;
-- setCaption( sCaption );
--}
--
--
--rtl::OUString&
--ScVbaLabel::getServiceImplName()
--{
-- static rtl::OUString sImplName( RTL_CONSTASCII_USTRINGPARAM("ScVbaLabel") );
-- return sImplName;
--}
--
--uno::Sequence< rtl::OUString >
--ScVbaLabel::getServiceNames()
--{
-- static uno::Sequence< rtl::OUString > aServiceNames;
-- if ( aServiceNames.getLength() == 0 )
-- {
-- aServiceNames.realloc( 1 );
-- aServiceNames[ 0 ] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.msforms.Label" ) );
-- }
-- return aServiceNames;
--}
---- sc/source/ui/vba/vbalabel.hxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbalabel.hxx 1970-01-01 00:00:00.000000000 +0000
-@@ -1,56 +0,0 @@
--/*************************************************************************
-- *
-- * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-- *
-- * Copyright 2008 by Sun Microsystems, Inc.
-- *
-- * OpenOffice.org - a multi-platform office productivity suite
-- *
-- * $RCSfile: vbalabel.hxx,v $
-- * $Revision: 1.3 $
-- *
-- * 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.
-- *
-- ************************************************************************/
--#ifndef SC_VBA_LABEL_HXX
--#define SC_VBA_LABEL_HXX
--#include <cppuhelper/implbase1.hxx>
--#include <ooo/vba/msforms/XLabel.hpp>
--
--#include "vbacontrol.hxx"
--#include "vbahelper.hxx"
--#include <cppuhelper/implbase2.hxx>
--
--typedef cppu::ImplInheritanceHelper2< ScVbaControl, ov::msforms::XLabel, css::script::XDefaultProperty > LabelImpl_BASE;
--
--class ScVbaLabel : public LabelImpl_BASE
--{
--public:
-- ScVbaLabel( const css::uno::Reference< ov::XHelperInterface >& xParent, const css::uno::Reference< css::uno::XComponentContext >& xContext, const css::uno::Reference< css::uno::XInterface >& xControl, const css::uno::Reference< css::frame::XModel >& xModel, ov::AbstractGeometryAttributes* pGeomHelper );
-- // Attributes
-- virtual css::uno::Any SAL_CALL getValue() throw (css::uno::RuntimeException);
-- virtual void SAL_CALL setValue( const css::uno::Any& _value ) throw (css::uno::RuntimeException);
-- virtual rtl::OUString SAL_CALL getCaption() throw (css::uno::RuntimeException);
-- virtual void SAL_CALL setCaption( const rtl::OUString& _caption ) throw (css::uno::RuntimeException);
-- //XHelperInterface
-- virtual rtl::OUString& getServiceImplName();
-- virtual css::uno::Sequence<rtl::OUString> getServiceNames();
-- // XDefaultProperty
-- rtl::OUString SAL_CALL getDefaultPropertyName( ) throw (css::uno::RuntimeException) { return ::rtl::OUString::createFromAscii("Value"); }
--};
--#endif //SC_VBA_LABEL_HXX
---- sc/source/ui/vba/vbalineformat.hxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbalineformat.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -33,7 +33,7 @@
- #include <com/sun/star/drawing/XShape.hpp>
- #include <com/sun/star/beans/XPropertySet.hpp>
- #include <ooo/vba/msforms/XLineFormat.hpp>
--#include "vbahelperinterface.hxx"
-+#include <vbahelper/vbahelperinterface.hxx>
-
- typedef InheritedHelperInterfaceImpl1< ov::msforms::XLineFormat > ScVbaLineFormat_BASE;
-
---- sc/source/ui/vba/vbalistbox.cxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbalistbox.cxx 1970-01-01 00:00:00.000000000 +0000
-@@ -1,289 +0,0 @@
--/*************************************************************************
-- *
-- * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-- *
-- * Copyright 2008 by Sun Microsystems, Inc.
-- *
-- * OpenOffice.org - a multi-platform office productivity suite
-- *
-- * $RCSfile: vbalistbox.cxx,v $
-- * $Revision: 1.4 $
-- *
-- * 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 <com/sun/star/form/validation/XValidatableFormComponent.hpp>
--
--#include "vbalistbox.hxx"
--#include "vbapropvalue.hxx"
--#include <vector>
--#include <comphelper/anytostring.hxx>
--#include <com/sun/star/script/ArrayWrapper.hpp>
--
--using namespace com::sun::star;
--using namespace ooo::vba;
--
--const static rtl::OUString TEXT( RTL_CONSTASCII_USTRINGPARAM("Text") );
--const static rtl::OUString SELECTEDITEMS( RTL_CONSTASCII_USTRINGPARAM("SelectedItems") );
--const static rtl::OUString ITEMS( RTL_CONSTASCII_USTRINGPARAM("StringItemList") );
--
--
--ScVbaListBox::ScVbaListBox( const uno::Reference< XHelperInterface >& xParent, const uno::Reference< uno::XComponentContext >& xContext, const uno::Reference< css::uno::XInterface >& xControl, const uno::Reference< frame::XModel >& xModel, AbstractGeometryAttributes* pGeomHelper ) : ListBoxImpl_BASE( xParent, xContext, xControl, xModel, pGeomHelper )
--{
-- mpListHelper.reset( new ListControlHelper( m_xProps ) );
--}
--
--// Attributes
--void SAL_CALL
--ScVbaListBox::setListIndex( const uno::Any& _value ) throw (uno::RuntimeException)
--{
-- sal_Int32 nIndex = 0;
-- _value >>= nIndex;
-- Selected( nIndex );
--}
--
--uno::Any SAL_CALL
--ScVbaListBox::getListIndex() throw (uno::RuntimeException)
--{
-- uno::Sequence< sal_Int16 > sSelection;
-- m_xProps->getPropertyValue( SELECTEDITEMS ) >>= sSelection;
-- if ( sSelection.getLength() == 0 )
-- return uno::Any( sal_Int32( -1 ) );
-- return uno::Any( sSelection[ 0 ] );
--}
--
--uno::Any SAL_CALL
--ScVbaListBox::getValue() throw (uno::RuntimeException)
--{
-- uno::Sequence< sal_Int16 > sSelection;
-- uno::Sequence< rtl::OUString > sItems;
-- m_xProps->getPropertyValue( SELECTEDITEMS ) >>= sSelection;
-- m_xProps->getPropertyValue( ITEMS ) >>= sItems;
-- if( getMultiSelect() )
-- throw uno::RuntimeException( rtl::OUString::createFromAscii(
-- "Attribute use invalid." ), uno::Reference< uno::XInterface >() );
-- uno::Any aRet;
-- if ( sSelection.getLength() )
-- aRet = uno::makeAny( sItems[ sSelection[ 0 ] ] );
-- return aRet;
--}
--
--void SAL_CALL
--ScVbaListBox::setValue( const uno::Any& _value ) throw (uno::RuntimeException)
--{
-- if( getMultiSelect() )
-- {
-- throw uno::RuntimeException( rtl::OUString::createFromAscii(
-- "Attribute use invalid." ), uno::Reference< uno::XInterface >() );
-- }
-- rtl::OUString sValue = getAnyAsString( _value );
-- uno::Sequence< rtl::OUString > sList;
-- m_xProps->getPropertyValue( ITEMS ) >>= sList;
-- uno::Sequence< sal_Int16 > nList;
-- sal_Int16 nLength = static_cast<sal_Int16>( sList.getLength() );
-- sal_Int16 nValue = -1;
-- sal_Int16 i = 0;
-- for( i = 0; i < nLength; i++ )
-- {
-- if( sList[i].equals( sValue ) )
-- {
-- nValue = i;
-- break;
-- }
-- }
-- if( nValue == -1 )
-- throw uno::RuntimeException( rtl::OUString::createFromAscii(
-- "Attribute use invalid." ), uno::Reference< uno::XInterface >() );
--
-- uno::Sequence< sal_Int16 > nSelectedIndices(1);
-- nSelectedIndices[ 0 ] = nValue;
-- m_xProps->setPropertyValue( SELECTEDITEMS, uno::makeAny( nSelectedIndices ) );
-- m_xProps->setPropertyValue( TEXT, uno::makeAny( sValue ) );
--}
--
--::rtl::OUString SAL_CALL
--ScVbaListBox::getText() throw (uno::RuntimeException)
--{
-- rtl::OUString result;
-- getValue() >>= result;
-- return result;
--}
--
--void SAL_CALL
--ScVbaListBox::setText( const ::rtl::OUString& _text ) throw (uno::RuntimeException)
--{
-- setValue( uno::makeAny( _text ) ); // seems the same
--}
--
--sal_Bool SAL_CALL
--ScVbaListBox::getMultiSelect() throw (css::uno::RuntimeException)
--{
-- sal_Bool bMultiSelect = sal_False;
-- m_xProps->getPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "MultiSelection" ) ) ) >>= bMultiSelect;
-- return bMultiSelect;
--}
--
--void SAL_CALL
--ScVbaListBox::setMultiSelect( sal_Bool _multiselect ) throw (css::uno::RuntimeException)
--{
-- m_xProps->setPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "MultiSelection" ) ), uno::makeAny( _multiselect ) );
--}
--
--css::uno::Any SAL_CALL
--ScVbaListBox::Selected( sal_Int32 index ) throw (css::uno::RuntimeException)
--{
-- uno::Sequence< rtl::OUString > sList;
-- m_xProps->getPropertyValue( ITEMS ) >>= sList;
-- sal_Int16 nLength = static_cast< sal_Int16 >( sList.getLength() );
-- // no choice but to do a horror cast as internally
-- // the indices are but sal_Int16
-- sal_Int16 nIndex = static_cast< sal_Int16 >( index );
-- if( nIndex < 0 || nIndex >= nLength )
-- throw uno::RuntimeException( rtl::OUString::createFromAscii(
-- "Error Number." ), uno::Reference< uno::XInterface >() );
-- m_nIndex = nIndex;
-- return uno::makeAny( uno::Reference< XPropValue > ( new ScVbaPropValue( this ) ) );
--}
--
--// Methods
--void SAL_CALL
--ScVbaListBox::AddItem( const uno::Any& pvargItem, const uno::Any& pvargIndex ) throw (uno::RuntimeException)
--{
-- mpListHelper->AddItem( pvargItem, pvargIndex );
-- }
--
--void SAL_CALL
--ScVbaListBox::removeItem( const uno::Any& index ) throw (uno::RuntimeException)
--{
-- mpListHelper->removeItem( index );
--}
--
--void SAL_CALL
--ScVbaListBox::Clear( ) throw (uno::RuntimeException)
--{
-- mpListHelper->Clear();
--}
--
--// this is called when something like the following vba code is used
--// to set the selected state of particular entries in the Listbox
--// ListBox1.Selected( 3 ) = false
--//PropListener
--void
--ScVbaListBox::setValueEvent( const uno::Any& value )
--{
-- sal_Bool bValue = sal_False;
-- if( !(value >>= bValue) )
-- throw uno::RuntimeException( rtl::OUString::createFromAscii(
-- "Invalid type\n. need boolean." ), uno::Reference< uno::XInterface >() );
-- uno::Sequence< sal_Int16 > nList;
-- m_xProps->getPropertyValue( SELECTEDITEMS ) >>= nList;
-- sal_Int16 nLength = static_cast<sal_Int16>( nList.getLength() );
-- sal_Int16 nIndex = m_nIndex;
-- for( sal_Int16 i = 0; i < nLength; i++ )
-- {
-- if( nList[i] == nIndex )
-- {
-- if( bValue )
-- return;
-- else
-- {
-- for( ; i < nLength - 1; i++ )
-- {
-- nList[i] = nList[i + 1];
-- }
-- nList.realloc( nLength - 1 );
-- //m_xProps->setPropertyValue( sSourceName, uno::makeAny( nList ) );
-- m_xProps->setPropertyValue( SELECTEDITEMS, uno::makeAny( nList ) );
-- return;
-- }
-- }
-- }
-- if( bValue )
-- {
-- if( getMultiSelect() )
-- {
-- nList.realloc( nLength + 1 );
-- nList[nLength] = nIndex;
-- }
-- else
-- {
-- nList.realloc( 1 );
-- nList[0] = nIndex;
-- }
-- m_xProps->setPropertyValue( sSourceName, uno::makeAny( nList ) );
-- }
--}
--
--// this is called when something like the following vba code is used
--// to determine the selected state of particular entries in the Listbox
--// msgbox ListBox1.Selected( 3 )
--
--css::uno::Any
--ScVbaListBox::getValueEvent()
--{
-- uno::Sequence< sal_Int16 > nList;
-- m_xProps->getPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "SelectedItems" ) ) ) >>= nList;
-- sal_Int32 nLength = nList.getLength();
-- sal_Int32 nIndex = m_nIndex;
--
-- for( sal_Int32 i = 0; i < nLength; i++ )
-- {
-- if( nList[i] == nIndex )
-- return uno::makeAny( sal_True );
-- }
--
-- return uno::makeAny( sal_False );
--}
--
--void SAL_CALL
--ScVbaListBox::setRowSource( const rtl::OUString& _rowsource ) throw (uno::RuntimeException)
--{
-- ScVbaControl::setRowSource( _rowsource );
-- mpListHelper->setRowSource( _rowsource );
--}
--
--sal_Int32 SAL_CALL
--ScVbaListBox::getListCount() throw (uno::RuntimeException)
--{
-- return mpListHelper->getListCount();
--}
--
--uno::Any SAL_CALL
--ScVbaListBox::List( const ::uno::Any& pvargIndex, const uno::Any& pvarColumn ) throw (uno::RuntimeException)
--{
-- return mpListHelper->List( pvargIndex, pvarColumn );
--}
--
--rtl::OUString&
--ScVbaListBox::getServiceImplName()
--{
-- static rtl::OUString sImplName( RTL_CONSTASCII_USTRINGPARAM("ScVbaListBox") );
-- return sImplName;
--}
--
--uno::Sequence< rtl::OUString >
--ScVbaListBox::getServiceNames()
--{
-- static uno::Sequence< rtl::OUString > aServiceNames;
-- if ( aServiceNames.getLength() == 0 )
-- {
-- aServiceNames.realloc( 1 );
-- aServiceNames[ 0 ] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.msforms.ScVbaListBox" ) );
-- }
-- return aServiceNames;
--}
---- sc/source/ui/vba/vbalistbox.hxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbalistbox.hxx 1970-01-01 00:00:00.000000000 +0000
-@@ -1,90 +0,0 @@
--/*************************************************************************
-- *
-- * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-- *
-- * Copyright 2008 by Sun Microsystems, Inc.
-- *
-- * OpenOffice.org - a multi-platform office productivity suite
-- *
-- * $RCSfile: vbalistbox.hxx,v $
-- * $Revision: 1.3 $
-- *
-- * 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.
-- *
-- ************************************************************************/
--#ifndef SC_VBA_LISTBOX_HXX
--#define SC_VBA_LISTBOX_HXX
--#include <cppuhelper/implbase2.hxx>
--#include <com/sun/star/uno/XComponentContext.hpp>
--#include <com/sun/star/script/XDefaultProperty.hpp>
--#include <ooo/vba/msforms/XListBox.hpp>
--#include <com/sun/star/beans/PropertyAttribute.hpp>
--
--#include "vbacontrol.hxx"
--#include "vbapropvalue.hxx"
--#include "vbalistcontrolhelper.hxx"
--#include "vbahelper.hxx"
--
--typedef cppu::ImplInheritanceHelper2<ScVbaControl, ov::msforms::XListBox, css::script::XDefaultProperty > ListBoxImpl_BASE;
--class ScVbaListBox : public ListBoxImpl_BASE
-- ,public PropListener
--{
-- std::auto_ptr< ListControlHelper > mpListHelper;
-- rtl::OUString sSourceName;
-- rtl::OUString msDftPropName;
--
-- sal_Int16 m_nIndex;
--
--public:
-- ScVbaListBox( const css::uno::Reference< ov::XHelperInterface >& xParent, const css::uno::Reference< css::uno::XComponentContext >& xContext, const css::uno::Reference< css::uno::XInterface >& xControl, const css::uno::Reference< css::frame::XModel >& xModel, ov::AbstractGeometryAttributes* pGeomHelper );
--
-- // Attributes
-- virtual css::uno::Any SAL_CALL getListIndex() throw (css::uno::RuntimeException);
-- virtual void SAL_CALL setListIndex( const css::uno::Any& _value ) throw (css::uno::RuntimeException);
-- virtual ::sal_Int32 SAL_CALL getListCount() throw (css::uno::RuntimeException);
-- virtual css::uno::Any SAL_CALL getValue() throw (css::uno::RuntimeException);
-- virtual void SAL_CALL setValue( const css::uno::Any& _value ) throw (css::uno::RuntimeException);
-- virtual rtl::OUString SAL_CALL getText() throw (css::uno::RuntimeException);
-- virtual void SAL_CALL setText( const ::rtl::OUString& _text ) throw (css::uno::RuntimeException);
-- virtual sal_Bool SAL_CALL getMultiSelect() throw (css::uno::RuntimeException);
-- virtual void SAL_CALL setMultiSelect( sal_Bool _multiselect ) throw (css::uno::RuntimeException);
-- virtual css::uno::Any SAL_CALL Selected( ::sal_Int32 index ) throw (css::uno::RuntimeException);
--
-- // Methods
-- virtual void SAL_CALL AddItem( const css::uno::Any& pvargItem, const css::uno::Any& pvargIndex ) throw (css::uno::RuntimeException);
-- virtual void SAL_CALL removeItem( const css::uno::Any& index ) throw (css::uno::RuntimeException);
-- virtual void SAL_CALL Clear( ) throw (css::uno::RuntimeException);
-- virtual css::uno::Any SAL_CALL List( const css::uno::Any& pvargIndex, const css::uno::Any& pvarColumn ) throw (css::uno::RuntimeException);
-- // XControl
-- virtual void SAL_CALL setRowSource( const rtl::OUString& _rowsource ) throw (css::uno::RuntimeException);
--
-- // XDefaultProperty
-- rtl::OUString SAL_CALL getDefaultPropertyName( ) throw (css::uno::RuntimeException) { return ::rtl::OUString::createFromAscii("Value"); }
--
-- //XHelperInterface
-- virtual rtl::OUString& getServiceImplName();
-- virtual css::uno::Sequence<rtl::OUString> getServiceNames();
--
-- //PropListener
-- virtual void setValueEvent( const css::uno::Any& value );
-- virtual css::uno::Any getValueEvent();
--
--
--};
--
--#endif //
---- sc/source/ui/vba/vbalistcontrolhelper.cxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbalistcontrolhelper.cxx 1970-01-01 00:00:00.000000000 +0000
-@@ -1,145 +0,0 @@
--#include <vbalistcontrolhelper.hxx>
--
--using namespace com::sun::star;
--using namespace ooo::vba;
--
--const static rtl::OUString ITEMS( RTL_CONSTASCII_USTRINGPARAM("StringItemList") );
--
--void SAL_CALL
--ListControlHelper::AddItem( const uno::Any& pvargItem, const uno::Any& pvargIndex ) throw (uno::RuntimeException)
--{
-- if ( pvargItem.hasValue() )
-- {
-- uno::Sequence< rtl::OUString > sList;
-- m_xProps->getPropertyValue( ITEMS ) >>= sList;
--
-- sal_Int32 nIndex = sList.getLength();
--
-- if ( pvargIndex.hasValue() )
-- pvargIndex >>= nIndex;
--
-- rtl::OUString sString = getAnyAsString( pvargItem );
--
-- // if no index specified or item is to be appended to end of
-- // list just realloc the array and set the last item
-- if ( nIndex == sList.getLength() )
-- {
-- sal_Int32 nOldSize = sList.getLength();
-- sList.realloc( nOldSize + 1 );
-- sList[ nOldSize ] = sString;
-- }
-- else
-- {
-- // just copy those elements above the one to be inserted
-- std::vector< rtl::OUString > sVec;
-- // reserve just the amount we need to copy
-- sVec.reserve( sList.getLength() - nIndex );
--
-- // point at first element to copy
-- rtl::OUString* pString = sList.getArray() + nIndex;
-- const rtl::OUString* pEndString = sList.getArray() + sList.getLength();
-- // insert the new element
-- sVec.push_back( sString );
-- // copy elements
-- for ( ; pString != pEndString; ++pString )
-- sVec.push_back( *pString );
--
-- sList.realloc( sList.getLength() + 1 );
--
-- // point at first element to be overwritten
-- pString = sList.getArray() + nIndex;
-- pEndString = sList.getArray() + sList.getLength();
-- std::vector< rtl::OUString >::iterator it = sVec.begin();
-- for ( ; pString != pEndString; ++pString, ++it)
-- *pString = *it;
-- //
-- }
--
-- m_xProps->setPropertyValue( ITEMS, uno::makeAny( sList ) );
--
-- }
--}
--
--void SAL_CALL
--ListControlHelper::removeItem( const uno::Any& index ) throw (uno::RuntimeException)
--{
-- sal_Int32 nIndex = 0;
-- // for int index
-- if ( index >>= nIndex )
-- {
-- uno::Sequence< rtl::OUString > sList;
-- m_xProps->getPropertyValue( ITEMS ) >>= sList;
-- if( nIndex < 0 || nIndex > ( sList.getLength() - 1 ) )
-- throw uno::RuntimeException( rtl::OUString::createFromAscii( "Invalid index" ), uno::Reference< uno::XInterface > () );
-- if( sList.hasElements() )
-- {
-- if( sList.getLength() == 1 )
-- {
-- Clear();
-- return;
-- }
-- for( sal_Int32 i = nIndex; i < ( sList.getLength()-1 ); i++ )
-- {
-- sList[i] = sList[i+1];
-- }
-- sList.realloc( sList.getLength() - 1 );
-- }
--
-- m_xProps->setPropertyValue( ITEMS, uno::makeAny( sList ) );
-- }
--}
--
--void SAL_CALL
--ListControlHelper::Clear( ) throw (uno::RuntimeException)
--{
-- // urk, setValue doesn't seem to work !!
-- //setValue( uno::makeAny( sal_Int16() ) );
-- m_xProps->setPropertyValue( ITEMS, uno::makeAny( uno::Sequence< rtl::OUString >() ) );
--}
--
--void SAL_CALL
--ListControlHelper::setRowSource( const rtl::OUString& _rowsource ) throw (uno::RuntimeException)
--{
-- if ( _rowsource.getLength() == 0 )
-- Clear();
--}
--
--sal_Int32 SAL_CALL
--ListControlHelper::getListCount() throw (uno::RuntimeException)
--{
-- uno::Sequence< rtl::OUString > sList;
-- m_xProps->getPropertyValue( ITEMS ) >>= sList;
-- return sList.getLength();
--}
--
--uno::Any SAL_CALL
--ListControlHelper::List( const ::uno::Any& pvargIndex, const uno::Any& pvarColumn ) throw (uno::RuntimeException)
--{
-- uno::Sequence< rtl::OUString > sList;
-- m_xProps->getPropertyValue( ITEMS ) >>= sList;
-- sal_Int16 nLength = static_cast< sal_Int16 >( sList.getLength() );
-- uno::Any aRet;
-- if ( pvargIndex.hasValue() )
-- {
-- sal_Int16 nIndex = -1;
-- pvargIndex >>= nIndex;
-- if( nIndex < 0 || nIndex >= nLength )
-- throw uno::RuntimeException( rtl::OUString::createFromAscii(
-- "Bad row Index" ), uno::Reference< uno::XInterface >() );
-- aRet <<= sList[ nIndex ];
-- }
-- else if ( pvarColumn.hasValue() ) // pvarColumn on its own would be bad
-- throw uno::RuntimeException( rtl::OUString::createFromAscii(
-- "Bad column Index" ), uno::Reference< uno::XInterface >() );
-- else // List() ( e.g. no args )
-- {
-- uno::Sequence< uno::Sequence< rtl::OUString > > sReturnArray( nLength );
-- for ( sal_Int32 i = 0; i < nLength; ++i )
-- {
-- sReturnArray[ i ].realloc( 10 );
-- sReturnArray[ i ][ 0 ] = sList[ i ];
-- }
-- aRet = uno::makeAny( sReturnArray );
-- }
-- return aRet;
--}
---- sc/source/ui/vba/vbalistcontrolhelper.hxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbalistcontrolhelper.hxx 1970-01-01 00:00:00.000000000 +0000
-@@ -1,20 +0,0 @@
--#ifndef SC_VBA_LISTCONTROLHELPER
--#define SC_VBA_LISTCONTROLHELPER
--
--#include "vbahelper.hxx"
--
--class ListControlHelper
--{
-- css::uno::Reference< css::beans::XPropertySet > m_xProps;
--
--public:
-- ListControlHelper( const css::uno::Reference< css::beans::XPropertySet >& rxControl ) : m_xProps( rxControl ){}
-- virtual ~ListControlHelper() {}
-- virtual void SAL_CALL AddItem( const css::uno::Any& pvargItem, const css::uno::Any& pvargIndex ) throw (css::uno::RuntimeException);
-- virtual void SAL_CALL removeItem( const css::uno::Any& index ) throw (css::uno::RuntimeException);
-- virtual void SAL_CALL setRowSource( const rtl::OUString& _rowsource ) throw (css::uno::RuntimeException);
-- virtual ::sal_Int32 SAL_CALL getListCount() throw (css::uno::RuntimeException);
-- virtual css::uno::Any SAL_CALL List( const css::uno::Any& pvargIndex, const css::uno::Any& pvarColumn ) throw (css::uno::RuntimeException);
-- virtual void SAL_CALL Clear( ) throw (css::uno::RuntimeException);
--};
--#endif
---- sc/source/ui/vba/vbamultipage.cxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbamultipage.cxx 1970-01-01 00:00:00.000000000 +0000
-@@ -1,132 +0,0 @@
--/*************************************************************************
-- *
-- * OpenOffice.org - a multi-platform office productivity suite
-- *
-- * $RCSfile$
-- *
-- * $Revision$
-- *
-- * last change: $Author$ $Date$
-- *
-- * The Contents of this file are made available subject to
-- * the terms of GNU Lesser General Public License Version 2.1.
-- *
-- *
-- * GNU Lesser General Public License Version 2.1
-- * =============================================
-- * Copyright 2005 by Sun Microsystems, Inc.
-- * 901 San Antonio Road, Palo Alto, CA 94303, USA
-- *
-- * This library is free software; you can redistribute it and/or
-- * modify it under the terms of the GNU Lesser General Public
-- * License version 2.1, as published by the Free Software Foundation.
-- *
-- * This library 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 for more details.
-- *
-- * You should have received a copy of the GNU Lesser General Public
-- * License along with this library; if not, write to the Free Software
-- * Foundation, Inc., 59 Temple Place, Suite 330, Boston,
-- * MA 02111-1307 USA
-- *
-- ************************************************************************/
--#include "vbamultipage.hxx"
--#include <ooo/vba/XCollection.hpp>
--#include "vbapages.hxx"
--#include <vector>
--
--using namespace com::sun::star;
--using namespace ooo::vba;
--
--// uno servicename com.sun.star.awt.UnoControlProgressBarMode
--const rtl::OUString SVALUE( RTL_CONSTASCII_USTRINGPARAM("ProgressValue") );
--const rtl::OUString SVALUEMAX( RTL_CONSTASCII_USTRINGPARAM("ProgressValueMax") );
--const rtl::OUString SSTEP( RTL_CONSTASCII_USTRINGPARAM("Step") );
--
--typedef cppu::WeakImplHelper1< container::XIndexAccess > PagesImpl_Base;
--class PagesImpl : public PagesImpl_Base
--{
-- sal_Int32 mnPages;
--public:
-- PagesImpl( sal_Int32 nPages ) : mnPages( nPages ) {}
-- virtual ::sal_Int32 SAL_CALL getCount() throw (uno::RuntimeException) { return mnPages; }
-- virtual uno::Any SAL_CALL getByIndex( ::sal_Int32 Index ) throw (lang::IndexOutOfBoundsException, lang::WrappedTargetException, ::uno::RuntimeException)
-- {
-- if ( Index < 0 || Index > mnPages )
-- throw lang::IndexOutOfBoundsException();
-- return uno::makeAny( uno::Reference< uno::XInterface >() );
-- }
-- // XElementAccess
-- virtual uno::Type SAL_CALL getElementType() throw (uno::RuntimeException)
-- {
-- // no Pages object yet #FIXME
-- //return msforms::XPage::static_type(0);
-- return uno::XInterface::static_type(0);
-- }
-- virtual ::sal_Bool SAL_CALL hasElements( ) throw (uno::RuntimeException)
-- {
-- return ( mnPages > 0 );
-- }
--};
--uno::Reference< container::XIndexAccess >
--ScVbaMultiPage::getPages( sal_Int32 nPages )
--{
-- return new PagesImpl( nPages );
--}
--
--ScVbaMultiPage::ScVbaMultiPage( const uno::Reference< ov::XHelperInterface >& xParent, const uno::Reference< uno::XComponentContext >& xContext, const uno::Reference< uno::XInterface >& xControl, uno::Reference< frame::XModel >& xModel, AbstractGeometryAttributes* pGeomHelper, const uno::Reference< uno::XInterface >& xDialog ) : MultiPageImpl_BASE( xParent, xContext, xControl, xModel, pGeomHelper )
--{
-- mxDialogProps.set( xDialog, uno::UNO_QUERY_THROW );
-- // set dialog step to value of multipage pseudo model
-- setValue(getValue());
--}
--
--// Attributes
--sal_Int32 SAL_CALL
--ScVbaMultiPage::getValue() throw (css::uno::RuntimeException)
--{
-- sal_Int32 nValue = 0;
-- m_xProps->getPropertyValue( SVALUE ) >>= nValue;
-- return nValue;
--}
--
--void SAL_CALL
--ScVbaMultiPage::setValue( const sal_Int32 _value ) throw (::com::sun::star::uno::RuntimeException)
--{
-- // track change in dialog ( dialog value is 1 based, 0 is a special value )
-- m_xProps->setPropertyValue( SVALUE, uno::makeAny( _value ) );
-- mxDialogProps->setPropertyValue( SSTEP, uno::makeAny( _value + 1) );
--}
--
--
--rtl::OUString&
--ScVbaMultiPage::getServiceImplName()
--{
-- static rtl::OUString sImplName( RTL_CONSTASCII_USTRINGPARAM("ScVbaMultiPage") );
-- return sImplName;
--}
--
--uno::Any SAL_CALL
--ScVbaMultiPage::Pages( const uno::Any& index ) throw (uno::RuntimeException)
--{
-- sal_Int32 nValue = 0;
-- m_xProps->getPropertyValue( SVALUEMAX ) >>= nValue;
-- uno::Reference< XCollection > xColl( new ScVbaPages( this, mxContext, getPages( nValue ) ) );
-- if ( !index.hasValue() )
-- return uno::makeAny( xColl );
-- return xColl->Item( uno::makeAny( index ), uno::Any() );
--}
--
--uno::Sequence< rtl::OUString >
--ScVbaMultiPage::getServiceNames()
--{
-- static uno::Sequence< rtl::OUString > aServiceNames;
-- if ( aServiceNames.getLength() == 0 )
-- {
-- aServiceNames.realloc( 1 );
-- aServiceNames[ 0 ] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.msforms.MultiPage" ) );
-- }
-- return aServiceNames;
--}
---- sc/source/ui/vba/vbamultipage.hxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbamultipage.hxx 1970-01-01 00:00:00.000000000 +0000
-@@ -1,65 +0,0 @@
--/*************************************************************************
-- *
-- * OpenOffice.org - a multi-platform office productivity suite
-- *
-- * $RCSfile$
-- *
-- * $Revision$
-- *
-- * last change: $Author$ $Date$
-- *
-- * The Contents of this file are made available subject to
-- * the terms of GNU Lesser General Public License Version 2.1.
-- *
-- *
-- * GNU Lesser General Public License Version 2.1
-- * =============================================
-- * Copyright 2005 by Sun Microsystems, Inc.
-- * 901 San Antonio Road, Palo Alto, CA 94303, USA
-- *
-- * This library is free software; you can redistribute it and/or
-- * modify it under the terms of the GNU Lesser General Public
-- * License version 2.1, as published by the Free Software Foundation.
-- *
-- * This library 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 for more details.
-- *
-- * You should have received a copy of the GNU Lesser General Public
-- * License along with this library; if not, write to the Free Software
-- * Foundation, Inc., 59 Temple Place, Suite 330, Boston,
-- * MA 02111-1307 USA
-- *
-- ************************************************************************/
--#ifndef SC_VBA_MULTIPAGE_HXX
--#define SC_VBA_MULTIPAGE_HXX
--#include <cppuhelper/implbase1.hxx>
--#include <ooo/vba/msforms/XMultiPage.hpp>
--#include <com/sun/star/container/XIndexAccess.hpp>
--
--#include "vbacontrol.hxx"
--#include "vbahelper.hxx"
--//#include <cppuhelper/implbase2.hxx>
--#include <cppuhelper/implbase1.hxx>
--
--typedef cppu::ImplInheritanceHelper1< ScVbaControl, ov::msforms::XMultiPage > MultiPageImpl_BASE;
--
--class ScVbaMultiPage : public MultiPageImpl_BASE
--{
-- css::uno::Reference< css::container::XIndexAccess > getPages( sal_Int32 nPages );
-- css::uno::Reference< css::beans::XPropertySet > mxDialogProps;
--public:
-- ScVbaMultiPage( const css::uno::Reference< ov::XHelperInterface >& xParent, const css::uno::Reference< css::uno::XComponentContext >& xContext, const css::uno::Reference< css::uno::XInterface >& xControl, css::uno::Reference< css::frame::XModel >& xModel, ov::AbstractGeometryAttributes* pGeomHelper, const css::uno::Reference< css::uno::XInterface >& xDialog );
-- // Attributes
-- virtual sal_Int32 SAL_CALL getValue() throw (css::uno::RuntimeException);
-- virtual void SAL_CALL setValue( sal_Int32 _value ) throw (css::uno::RuntimeException);
-- virtual css::uno::Any SAL_CALL Pages( const css::uno::Any& index ) throw (css::uno::RuntimeException);
--
-- //XHelperInterface
-- virtual rtl::OUString& getServiceImplName();
-- virtual css::uno::Sequence<rtl::OUString> getServiceNames();
-- // XDefaultProperty
-- rtl::OUString SAL_CALL getDefaultPropertyName( ) throw (css::uno::RuntimeException) { return ::rtl::OUString::createFromAscii("Value"); }
--};
--#endif //SC_VBA_LABEL_HXX
---- sc/source/ui/vba/vbaname.cxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbaname.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -27,7 +27,7 @@
- * for a copy of the LGPLv3 License.
- *
- ************************************************************************/
--#include "helperdecl.hxx"
-+#include <vbahelper/helperdecl.hxx>
-
- #include <com/sun/star/table/XCellRange.hpp>
- #include <com/sun/star/sheet/XCellRangeAddressable.hpp>
-@@ -64,7 +64,8 @@ ScVbaName::~ScVbaName()
- css::uno::Reference< ov::excel::XWorksheet >
- ScVbaName::getWorkSheet() throw (css::uno::RuntimeException)
- {
-- return ScVbaGlobals::getGlobalsImpl( mxContext )->getActiveSheet();
-+ uno::Reference< excel::XApplication > xApplication( Application(), uno::UNO_QUERY_THROW );
-+ return xApplication->getActiveSheet();
- }
-
- ::rtl::OUString
-@@ -234,7 +235,7 @@ ScVbaName::setRefersToR1C1Local( const :
- css::uno::Reference< ov::excel::XRange >
- ScVbaName::getRefersToRange() throw (css::uno::RuntimeException)
- {
-- uno::Reference< ov::excel::XRange > xRange = ScVbaRange::getRangeObjectForName( mxContext, mxNamedRange->getName(), getDocShell( mxModel ), formula::FormulaGrammar::CONV_XL_R1C1 );
-+ uno::Reference< ov::excel::XRange > xRange = ScVbaRange::getRangeObjectForName( mxContext, mxNamedRange->getName(), excel::getDocShell( mxModel ), formula::FormulaGrammar::CONV_XL_R1C1 );
- return xRange;
- }
-
---- sc/source/ui/vba/vbaname.hxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbaname.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -34,7 +34,9 @@
- #include <com/sun/star/sheet/XNamedRange.hpp>
- #include <com/sun/star/sheet/XNamedRanges.hpp>
-
--#include "vbahelperinterface.hxx"
-+#include <vbahelper/vbahelperinterface.hxx>
-+
-+class ScDocument;
-
- typedef InheritedHelperInterfaceImpl1< ov::excel::XName > NameImpl_BASE;
-
---- sc/source/ui/vba/vbanames.cxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbanames.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -27,7 +27,7 @@
- * for a copy of the LGPLv3 License.
- *
- ************************************************************************/
--#include "helperdecl.hxx"
-+#include <vbahelper/helperdecl.hxx>
-
- #include <com/sun/star/table/XCellRange.hpp>
- #include <com/sun/star/sheet/XCellRangeAddressable.hpp>
-@@ -81,7 +81,7 @@ ScDocument *
- ScVbaNames::getScDocument()
- {
- uno::Reference< frame::XModel > xModel( getModel() , uno::UNO_QUERY_THROW );
-- ScTabViewShell * pTabViewShell = getBestViewShell( xModel );
-+ ScTabViewShell * pTabViewShell = excel::getBestViewShell( xModel );
- if ( !pTabViewShell )
- throw uno::RuntimeException( rtl::OUString::createFromAscii("No ViewShell available"), uno::Reference< uno::XInterface >() );
- ScViewData* pViewData = pTabViewShell->GetViewData();
---- sc/source/ui/vba/vbanames.hxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbanames.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -34,7 +34,10 @@
- #include <ooo/vba/XCollection.hpp>
- #include <com/sun/star/container/XEnumerationAccess.hpp>
- #include <com/sun/star/sheet/XNamedRanges.hpp>
--#include "vbacollectionimpl.hxx"
-+#include <vbahelper/vbacollectionimpl.hxx>
-+
-+class ScDocument;
-+class ScDocShell;
-
- typedef CollTestImplHelper< ov::excel::XNames > ScVbaNames_BASE;
-
---- sc/source/ui/vba/vbaoleobject.hxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbaoleobject.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -35,7 +35,7 @@
- #include <com/sun/star/awt/XWindowPeer.hpp>
- #include <ooo/vba/excel/XOLEObject.hpp>
-
--#include "vbahelperinterface.hxx"
-+#include <vbahelper/vbahelperinterface.hxx>
-
- typedef InheritedHelperInterfaceImpl1< ov::excel::XOLEObject > OLEObjectImpl_BASE;
-
---- sc/source/ui/vba/vbaoleobjects.hxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbaoleobjects.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -33,8 +33,8 @@
- #include <cppuhelper/implbase1.hxx>
- #include <ooo/vba/excel/XOLEObjects.hpp>
-
--#include "vbacollectionimpl.hxx"
--#include "vbahelper.hxx"
-+#include <vbahelper/vbacollectionimpl.hxx>
-+#include "excelvbahelper.hxx"
-
- typedef CollTestImplHelper< ov::excel::XOLEObjects > OLEObjectsImpl_BASE;
-
---- sc/source/ui/vba/vbaoutline.hxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbaoutline.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -34,7 +34,7 @@
- #include <cppuhelper/implbase1.hxx>
- #include <ooo/vba/excel/XOutline.hpp>
- #include <com/sun/star/uno/XComponentContext.hpp>
--#include "vbahelperinterface.hxx"
-+#include <vbahelper/vbahelperinterface.hxx>
-
- typedef InheritedHelperInterfaceImpl1< ov::excel::XOutline > ScVbaOutline_BASE;
-
---- sc/source/ui/vba/vbapagebreak.hxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbapagebreak.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -38,7 +38,7 @@
- #include <com/sun/star/script/BasicErrorException.hpp>
- #include <com/sun/star/sheet/TablePageBreakData.hpp>
- #include <com/sun/star/beans/XPropertySet.hpp>
--#include "vbahelperinterface.hxx"
-+#include <vbahelper/vbahelperinterface.hxx>
-
- template< typename Ifc1 >
- class ScVbaPageBreak : public InheritedHelperInterfaceImpl1< Ifc1 >
---- sc/source/ui/vba/vbapagebreaks.hxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbapagebreaks.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -41,8 +41,8 @@
- #include <com/sun/star/beans/XPropertySet.hpp>
- #include <com/sun/star/container/XIndexAccess.hpp>
- #include <com/sun/star/table/XColumnRowRange.hpp>
--#include "vbahelperinterface.hxx"
--#include "vbacollectionimpl.hxx"
-+#include <vbahelper/vbahelperinterface.hxx>
-+#include <vbahelper/vbacollectionimpl.hxx>
-
- typedef CollTestImplHelper< ov::excel::XHPageBreaks > ScVbaHPageBreaks_BASE;
-
---- sc/source/ui/vba/vbapages.cxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbapages.cxx 1970-01-01 00:00:00.000000000 +0000
-@@ -1,81 +0,0 @@
--/*************************************************************************
-- *
-- * OpenOffice.org - a multi-platform office productivity suite
-- *
-- * $RCSfile$
-- *
-- * $Revision$
-- *
-- * last change: $Author$ $Date$
-- *
-- * The Contents of this file are made available subject to
-- * the terms of GNU Lesser General Public License Version 2.1.
-- *
-- *
-- * GNU Lesser General Public License Version 2.1
-- * =============================================
-- * Copyright 2005 by Sun Microsystems, Inc.
-- * 901 San Antonio Road, Palo Alto, CA 94303, USA
-- *
-- * This library is free software; you can redistribute it and/or
-- * modify it under the terms of the GNU Lesser General Public
-- * License version 2.1, as published by the Free Software Foundation.
-- *
-- * This library 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 for more details.
-- *
-- * You should have received a copy of the GNU Lesser General Public
-- * License along with this library; if not, write to the Free Software
-- * Foundation, Inc., 59 Temple Place, Suite 330, Boston,
-- * MA 02111-1307 USA
-- *
-- ************************************************************************/
--#include "vbapages.hxx"
--
--using namespace ::ooo::vba;
--using namespace ::com::sun::star;
--using namespace ::vos;
--
--ScVbaPages::ScVbaPages( const uno::Reference< XHelperInterface >& xParent, const uno::Reference< uno::XComponentContext >& xContext, const uno::Reference< container::XIndexAccess >& xPages ) throw( lang::IllegalArgumentException ) : ScVbaPages_BASE( xParent, xContext, xPages )
--{
--}
--
--uno::Type SAL_CALL
--ScVbaPages::getElementType() throw (uno::RuntimeException)
--{
-- // return msforms::XPage::static_type(0);
-- return uno::XInterface::static_type(0);
--}
--
--uno::Any
--ScVbaPages::createCollectionObject( const css::uno::Any& aSource )
--{
-- return aSource;
--}
--
--rtl::OUString&
--ScVbaPages::getServiceImplName()
--{
-- static rtl::OUString sImplName( RTL_CONSTASCII_USTRINGPARAM("ScVbaPages") );
-- return sImplName;
--}
--
--uno::Reference< container::XEnumeration > SAL_CALL
--ScVbaPages::createEnumeration() throw (uno::RuntimeException)
--{
-- return uno::Reference< container::XEnumeration >();
--}
--
--uno::Sequence< rtl::OUString >
--ScVbaPages::getServiceNames()
--{
-- static uno::Sequence< rtl::OUString > aServiceNames;
-- if ( aServiceNames.getLength() == 0 )
-- {
-- aServiceNames.realloc( 1 );
-- aServiceNames[ 0 ] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.msform.Pages" ) );
-- }
-- return aServiceNames;
--}
---- sc/source/ui/vba/vbapages.hxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbapages.hxx 1970-01-01 00:00:00.000000000 +0000
-@@ -1,64 +0,0 @@
--/*************************************************************************
-- *
-- * OpenOffice.org - a multi-platform office productivity suite
-- *
-- * $RCSfile$
-- *
-- * $Revision$
-- *
-- * last change: $Author$ $Date$
-- *
-- * The Contents of this file are made available subject to
-- * the terms of GNU Lesser General Public License Version 2.1.
-- *
-- *
-- * GNU Lesser General Public License Version 2.1
-- * =============================================
-- * Copyright 2005 by Sun Microsystems, Inc.
-- * 901 San Antonio Road, Palo Alto, CA 94303, USA
-- *
-- * This library is free software; you can redistribute it and/or
-- * modify it under the terms of the GNU Lesser General Public
-- * License version 2.1, as published by the Free Software Foundation.
-- *
-- * This library 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 for more details.
-- *
-- * You should have received a copy of the GNU Lesser General Public
-- * License along with this library; if not, write to the Free Software
-- * Foundation, Inc., 59 Temple Place, Suite 330, Boston,
-- * MA 02111-1307 USA
-- *
-- ************************************************************************/
--#ifndef SC_VBA_PAGES_HXX
--#define SC_VBA_PAGES_HXX
--
--#include <ooo/vba/office/MsoShapeType.hpp>
--#include <com/sun/star/lang/XEventListener.hpp>
--#include <com/sun/star/beans/XPropertySet.hpp>
--#include <ooo/vba/msforms/XPages.hpp>
--#include <cppuhelper/implbase2.hxx>
--#include <cppuhelper/implbase1.hxx>
--
--#include "vbacollectionimpl.hxx"
--typedef CollTestImplHelper<
--ov::msforms::XPages > ScVbaPages_BASE;
--
--class ScVbaPages : public ScVbaPages_BASE
--{
--protected:
-- virtual rtl::OUString& getServiceImplName();
-- virtual css::uno::Sequence<rtl::OUString> getServiceNames();
--public:
-- ScVbaPages( const css::uno::Reference< ov::XHelperInterface >& xParent, const css::uno::Reference< css::uno::XComponentContext >& xContext, const css::uno::Reference< css::container::XIndexAccess >& xPages ) throw ( css::lang::IllegalArgumentException );
-- virtual ~ScVbaPages() {}
-- // XEnumerationAccess
-- virtual css::uno::Type SAL_CALL getElementType() throw (css::uno::RuntimeException);
-- virtual css::uno::Reference< css::container::XEnumeration > SAL_CALL createEnumeration() throw (css::uno::RuntimeException);
-- // ScVbaPages_BASE
-- virtual css::uno::Any createCollectionObject( const css::uno::Any& aSource );
--
--};
--#endif//SC_VBA_SHAPE_HXX
---- sc/source/ui/vba/vbapagesetup.cxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbapagesetup.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -31,6 +31,7 @@
- #include "cellsuno.hxx"
- #include "convuno.hxx"
- #include "rangelst.hxx"
-+#include "excelvbahelper.hxx"
- #include <com/sun/star/sheet/XPrintAreas.hpp>
- #include <com/sun/star/sheet/XHeaderFooterContent.hpp>
- #include <com/sun/star/text/XText.hpp>
-@@ -85,7 +86,7 @@ rtl::OUString SAL_CALL ScVbaPageSetup::g
- ScUnoConversion::FillScRange( aRange, aSeq[i] );
- aRangeList.Append( aRange );
- }
-- ScDocument* pDoc = getDocShell( mxModel )->GetDocument();
-+ ScDocument* pDoc = excel::getDocShell( mxModel )->GetDocument();
- aRangeList.Format( aPrintArea, nFlags, pDoc, formula::FormulaGrammar::CONV_XL_A1, ',' );
- }
-
-@@ -106,7 +107,7 @@ void SAL_CALL ScVbaPageSetup::setPrintAr
- {
- ScRangeList aCellRanges;
- ScRange aRange;
-- if( getScRangeListForAddress( rAreas, getDocShell( mxModel ) , aRange, aCellRanges ) )
-+ if( getScRangeListForAddress( rAreas, excel::getDocShell( mxModel ) , aRange, aCellRanges ) )
- {
- uno::Sequence< table::CellRangeAddress > aSeq( aCellRanges.Count() );
- USHORT i=0;
---- sc/source/ui/vba/vbapagesetup.hxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbapagesetup.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -35,7 +35,7 @@
- #include <com/sun/star/uno/XComponentContext.hpp>
- #include <com/sun/star/sheet/XSpreadsheet.hpp>
- #include <com/sun/star/beans/XPropertySet.hpp>
--#include "vbahelperinterface.hxx"
-+#include <vbahelper/vbahelperinterface.hxx>
-
- typedef InheritedHelperInterfaceImpl1< ov::excel::XPageSetup > ScVbaPageSetup_BASE;
-
---- sc/source/ui/vba/vbapalette.hxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbapalette.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -30,7 +30,7 @@
- #ifndef SC_VBAPALETTE_HXX
- #define SC_VBAPALETTE_HXX
-
--#include "vbahelper.hxx"
-+#include "excelvbahelper.hxx"
- #include <document.hxx>
- #include <com/sun/star/container/XIndexAccess.hpp>
-
---- sc/source/ui/vba/vbapane.hxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbapane.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -34,7 +34,7 @@
- #include<com/sun/star/sheet/XViewPane.hpp>
- #include<ooo/vba/excel/XPane.hpp>
-
--#include"vbahelper.hxx"
-+#include"excelvbahelper.hxx"
-
- typedef cppu::WeakImplHelper1< ov::excel::XPane > PaneImpl_Base;
-
---- sc/source/ui/vba/vbapictureformat.hxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbapictureformat.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -33,7 +33,7 @@
- #include <com/sun/star/drawing/XShape.hpp>
- #include <com/sun/star/beans/XPropertySet.hpp>
- #include <ooo/vba/msforms/XPictureFormat.hpp>
--#include "vbahelperinterface.hxx"
-+#include <vbahelper/vbahelperinterface.hxx>
-
- typedef InheritedHelperInterfaceImpl1< ov::msforms::XPictureFormat > ScVbaPictureFormat_BASE;
-
---- sc/source/ui/vba/vbapivotcache.hxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbapivotcache.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -34,7 +34,7 @@
- #include <com/sun/star/sheet/XDataPilotTable.hpp>
-
- #include <ooo/vba/excel/XPivotCache.hpp>
--#include "vbahelperinterface.hxx"
-+#include <vbahelper/vbahelperinterface.hxx>
-
- typedef InheritedHelperInterfaceImpl1<ov::excel::XPivotCache > PivotCacheImpl_BASE;
-
---- sc/source/ui/vba/vbapivottable.hxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbapivottable.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -33,8 +33,8 @@
- #include <com/sun/star/uno/XComponentContext.hpp>
- #include <com/sun/star/sheet/XDataPilotTable.hpp>
- #include <ooo/vba/excel/XPivotTable.hpp>
--#include "vbahelper.hxx"
--#include "vbahelperinterface.hxx"
-+#include "excelvbahelper.hxx"
-+#include <vbahelper/vbahelperinterface.hxx>
-
- typedef InheritedHelperInterfaceImpl1< ov::excel::XPivotTable > PivotTableImpl_BASE;
-
---- sc/source/ui/vba/vbapivottables.hxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbapivottables.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -36,9 +36,9 @@
- #include <com/sun/star/container/XEnumerationAccess.hpp>
- #include <com/sun/star/uno/XComponentContext.hpp>
-
--#include "vbahelper.hxx"
--#include "vbahelperinterface.hxx"
--#include "vbacollectionimpl.hxx"
-+#include "excelvbahelper.hxx"
-+#include <vbahelper/vbahelperinterface.hxx>
-+#include <vbahelper/vbacollectionimpl.hxx>
-
-
- typedef CollTestImplHelper< ov::excel::XPivotTables > ScVbaPivotTables_BASE;
---- sc/source/ui/vba/vbaprogressbar.cxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbaprogressbar.cxx 1970-01-01 00:00:00.000000000 +0000
-@@ -1,78 +0,0 @@
--/*************************************************************************
-- *
-- * OpenOffice.org - a multi-platform office productivity suite
-- *
-- * $RCSfile$
-- *
-- * $Revision$
-- *
-- * last change: $Author$ $Date$
-- *
-- * The Contents of this file are made available subject to
-- * the terms of GNU Lesser General Public License Version 2.1.
-- *
-- *
-- * GNU Lesser General Public License Version 2.1
-- * =============================================
-- * Copyright 2005 by Sun Microsystems, Inc.
-- * 901 San Antonio Road, Palo Alto, CA 94303, USA
-- *
-- * This library is free software; you can redistribute it and/or
-- * modify it under the terms of the GNU Lesser General Public
-- * License version 2.1, as published by the Free Software Foundation.
-- *
-- * This library 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 for more details.
-- *
-- * You should have received a copy of the GNU Lesser General Public
-- * License along with this library; if not, write to the Free Software
-- * Foundation, Inc., 59 Temple Place, Suite 330, Boston,
-- * MA 02111-1307 USA
-- *
-- ************************************************************************/
--#include "vbaprogressbar.hxx"
--#include <vector>
--
--using namespace com::sun::star;
--using namespace ooo::vba;
--
--// uno servicename com.sun.star.awt.UnoControlProgressBarMode
--const rtl::OUString SVALUE( RTL_CONSTASCII_USTRINGPARAM("ProgressValue") );
--
--ScVbaProgressBar::ScVbaProgressBar( const uno::Reference< ov::XHelperInterface >& xParent, const uno::Reference< uno::XComponentContext >& xContext, const uno::Reference< uno::XInterface >& xControl, const uno::Reference< frame::XModel >& xModel, AbstractGeometryAttributes* pGeomHelper ) : ProgressBarImpl_BASE( xParent, xContext, xControl, xModel, pGeomHelper )
--{
--}
--
--// Attributes
--uno::Any SAL_CALL
--ScVbaProgressBar::getValue() throw (css::uno::RuntimeException)
--{
-- return m_xProps->getPropertyValue( SVALUE );
--}
--
--void SAL_CALL
--ScVbaProgressBar::setValue( const uno::Any& _value ) throw (::com::sun::star::uno::RuntimeException)
--{
-- m_xProps->setPropertyValue( SVALUE, _value );
--}
--
--rtl::OUString&
--ScVbaProgressBar::getServiceImplName()
--{
-- static rtl::OUString sImplName( RTL_CONSTASCII_USTRINGPARAM("ScVbaProgressBar") );
-- return sImplName;
--}
--
--uno::Sequence< rtl::OUString >
--ScVbaProgressBar::getServiceNames()
--{
-- static uno::Sequence< rtl::OUString > aServiceNames;
-- if ( aServiceNames.getLength() == 0 )
-- {
-- aServiceNames.realloc( 1 );
-- aServiceNames[ 0 ] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.msforms.Label" ) );
-- }
-- return aServiceNames;
--}
---- sc/source/ui/vba/vbaprogressbar.hxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbaprogressbar.hxx 1970-01-01 00:00:00.000000000 +0000
-@@ -1,59 +0,0 @@
--/*************************************************************************
-- *
-- * OpenOffice.org - a multi-platform office productivity suite
-- *
-- * $RCSfile$
-- *
-- * $Revision$
-- *
-- * last change: $Author$ $Date$
-- *
-- * The Contents of this file are made available subject to
-- * the terms of GNU Lesser General Public License Version 2.1.
-- *
-- *
-- * GNU Lesser General Public License Version 2.1
-- * =============================================
-- * Copyright 2005 by Sun Microsystems, Inc.
-- * 901 San Antonio Road, Palo Alto, CA 94303, USA
-- *
-- * This library is free software; you can redistribute it and/or
-- * modify it under the terms of the GNU Lesser General Public
-- * License version 2.1, as published by the Free Software Foundation.
-- *
-- * This library 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 for more details.
-- *
-- * You should have received a copy of the GNU Lesser General Public
-- * License along with this library; if not, write to the Free Software
-- * Foundation, Inc., 59 Temple Place, Suite 330, Boston,
-- * MA 02111-1307 USA
-- *
-- ************************************************************************/
--#ifndef SC_VBA_PROGRESSBAR_HXX
--#define SC_VBA_PROGRESSBAR_HXX
--#include <cppuhelper/implbase1.hxx>
--#include <ooo/vba/msforms/XProgressBar.hpp>
--
--#include "vbacontrol.hxx"
--#include "vbahelper.hxx"
--#include <cppuhelper/implbase2.hxx>
--
--typedef cppu::ImplInheritanceHelper2< ScVbaControl, ov::msforms::XProgressBar, css::script::XDefaultProperty > ProgressBarImpl_BASE;
--
--class ScVbaProgressBar : public ProgressBarImpl_BASE
--{
--public:
-- ScVbaProgressBar( const css::uno::Reference< ov::XHelperInterface >& xParent, const css::uno::Reference< css::uno::XComponentContext >& xContext, const css::uno::Reference< css::uno::XInterface >& xControl, const css::uno::Reference< css::frame::XModel >& xModel, ov::AbstractGeometryAttributes* pGeomHelper );
-- // Attributes
-- virtual css::uno::Any SAL_CALL getValue() throw (css::uno::RuntimeException);
-- virtual void SAL_CALL setValue( const css::uno::Any& _value ) throw (css::uno::RuntimeException);
-- //XHelperInterface
-- virtual rtl::OUString& getServiceImplName();
-- virtual css::uno::Sequence<rtl::OUString> getServiceNames();
-- // XDefaultProperty
-- rtl::OUString SAL_CALL getDefaultPropertyName( ) throw (css::uno::RuntimeException) { return ::rtl::OUString::createFromAscii("Value"); }
--};
--#endif //SC_VBA_LABEL_HXX
---- sc/source/ui/vba/vbapropvalue.hxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbapropvalue.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -32,7 +32,7 @@
- #include <ooo/vba/XPropValue.hpp>
- #include <cppuhelper/implbase1.hxx>
-
--#include "vbahelper.hxx"
-+#include "excelvbahelper.hxx"
-
- typedef ::cppu::WeakImplHelper1< ov::XPropValue > PropValueImpl_BASE;
-
---- sc/source/ui/vba/vbaradiobutton.cxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbaradiobutton.cxx 1970-01-01 00:00:00.000000000 +0000
-@@ -1,107 +0,0 @@
--/*************************************************************************
-- *
-- * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-- *
-- * Copyright 2008 by Sun Microsystems, Inc.
-- *
-- * OpenOffice.org - a multi-platform office productivity suite
-- *
-- * $RCSfile: vbaradiobutton.cxx,v $
-- * $Revision: 1.3 $
-- *
-- * 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 "vbaradiobutton.hxx"
--#include <vector>
--
--using namespace com::sun::star;
--using namespace ooo::vba;
--
--
--const static rtl::OUString LABEL( RTL_CONSTASCII_USTRINGPARAM("Label") );
--const static rtl::OUString STATE( RTL_CONSTASCII_USTRINGPARAM("State") );
--ScVbaRadioButton::ScVbaRadioButton( const uno::Reference< XHelperInterface >& xParent, const uno::Reference< uno::XComponentContext >& xContext, const uno::Reference< uno::XInterface >& xControl, const uno::Reference< frame::XModel >& xModel, AbstractGeometryAttributes* pGeomHelper ) : RadioButtonImpl_BASE( xParent, xContext, xControl, xModel, pGeomHelper )
--{
--}
--
--// Attributes
--rtl::OUString SAL_CALL
--ScVbaRadioButton::getCaption() throw (css::uno::RuntimeException)
--{
-- rtl::OUString Label;
-- m_xProps->getPropertyValue( LABEL ) >>= Label;
-- return Label;
--}
--
--void SAL_CALL
--ScVbaRadioButton::setCaption( const rtl::OUString& _caption ) throw (::com::sun::star::uno::RuntimeException)
--{
-- m_xProps->setPropertyValue( LABEL, uno::makeAny( _caption ) );
--}
--
--uno::Any SAL_CALL
--ScVbaRadioButton::getValue() throw (css::uno::RuntimeException)
--{
-- sal_Int16 nValue = -1;
-- m_xProps->getPropertyValue( STATE ) >>= nValue;
-- if( nValue != 0 )
-- nValue = -1;
--// return uno::makeAny( nValue );
--// I must be missing something MSO says value should be -1 if selected, 0 if not
--// selected
-- return uno::makeAny( ( nValue == -1 ) ? sal_True : sal_False );
--
--}
--
--void SAL_CALL
--ScVbaRadioButton::setValue( const uno::Any& _value ) throw (uno::RuntimeException)
--{
-- sal_Int16 nValue = 0;
-- sal_Bool bValue = sal_False;
-- if( _value >>= nValue )
-- {
-- if( nValue == -1)
-- nValue = 1;
-- }
-- else if ( _value >>= bValue )
-- {
-- if ( bValue )
-- nValue = 1;
-- }
-- m_xProps->setPropertyValue( STATE, uno::makeAny( nValue ) );
--}
--
--rtl::OUString&
--ScVbaRadioButton::getServiceImplName()
--{
-- static rtl::OUString sImplName( RTL_CONSTASCII_USTRINGPARAM("ScVbaRadioButton") );
-- return sImplName;
--}
--
--uno::Sequence< rtl::OUString >
--ScVbaRadioButton::getServiceNames()
--{
-- static uno::Sequence< rtl::OUString > aServiceNames;
-- if ( aServiceNames.getLength() == 0 )
-- {
-- aServiceNames.realloc( 1 );
-- aServiceNames[ 0 ] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.msforms.RadioButton" ) );
-- }
-- return aServiceNames;
--}
---- sc/source/ui/vba/vbaradiobutton.hxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbaradiobutton.hxx 1970-01-01 00:00:00.000000000 +0000
-@@ -1,55 +0,0 @@
--/*************************************************************************
-- *
-- * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-- *
-- * Copyright 2008 by Sun Microsystems, Inc.
-- *
-- * OpenOffice.org - a multi-platform office productivity suite
-- *
-- * $RCSfile: vbaradiobutton.hxx,v $
-- * $Revision: 1.3 $
-- *
-- * 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.
-- *
-- ************************************************************************/
--#ifndef SC_VBA_RADIOBUTTON_HXX
--#define SC_VBA_RADIOBUTTON_HXX
--#include <ooo/vba/msforms/XRadioButton.hpp>
--#include "vbacontrol.hxx"
--#include "vbahelper.hxx"
--#include <cppuhelper/implbase2.hxx>
--
--typedef cppu::ImplInheritanceHelper2< ScVbaControl, ov::msforms::XRadioButton, css::script::XDefaultProperty > RadioButtonImpl_BASE;
--
--class ScVbaRadioButton : public RadioButtonImpl_BASE
--{
--public:
-- ScVbaRadioButton( const css::uno::Reference< ov::XHelperInterface >& xParent, const css::uno::Reference< css::uno::XComponentContext >& xContext, const css::uno::Reference< css::uno::XInterface >& xControl, const css::uno::Reference< css::frame::XModel >& xModel, ov::AbstractGeometryAttributes* pGeomHelper );
-- // Attributes
-- virtual rtl::OUString SAL_CALL getCaption() throw (css::uno::RuntimeException);
-- virtual void SAL_CALL setCaption( const rtl::OUString& _caption ) throw (css::uno::RuntimeException);
-- virtual css::uno::Any SAL_CALL getValue() throw (css::uno::RuntimeException);
-- virtual void SAL_CALL setValue(const com::sun::star::uno::Any&) throw (css::uno::RuntimeException);
-- //XHelperInterface
-- virtual rtl::OUString& getServiceImplName();
-- virtual css::uno::Sequence<rtl::OUString> getServiceNames();
-- // XDefaultProperty
-- rtl::OUString SAL_CALL getDefaultPropertyName( ) throw (css::uno::RuntimeException) { return ::rtl::OUString::createFromAscii("Value"); }
--
--};
--#endif //SC_VBA_RADIOBUTTON_HXX
---- sc/source/ui/vba/vbarange.cxx.old 2009-04-06 16:42:00.000000000 +0000
-+++ sc/source/ui/vba/vbarange.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -27,7 +27,7 @@
- * for a copy of the LGPLv3 License.
- *
- ************************************************************************/
--#include "helperdecl.hxx"
-+#include <vbahelper/helperdecl.hxx>
-
- #include <comphelper/unwrapargs.hxx>
- #include <comphelper/processfactory.hxx>
-@@ -146,7 +146,6 @@
- #include "rangelst.hxx"
- #include "convuno.hxx"
- #include "compiler.hxx"
--#include "formula/grammar.hxx"
- #include "attrib.hxx"
- #include "undodat.hxx"
- #include "dbdocfun.hxx"
-@@ -159,7 +158,7 @@
- #include "vbaglobals.hxx"
- #include "vbastyle.hxx"
- #include <vector>
--#include <vbacollectionimpl.hxx>
-+#include <vbahelper/vbacollectionimpl.hxx>
- // begin test includes
- #include <com/sun/star/sheet/FunctionArgument.hpp>
- // end test includes
-@@ -253,7 +252,7 @@ ScCellRangeObj* ScVbaRange::getCellRang
- SfxItemSet* ScVbaRange::getCurrentDataSet( ) throw ( uno::RuntimeException )
- {
- ScCellRangeObj* pUnoCellRange = getCellRangeObj();
-- SfxItemSet* pDataSet = ScVbaCellRangeAccess::GetDataSet( pUnoCellRange );
-+ SfxItemSet* pDataSet = excel::ScVbaCellRangeAccess::GetDataSet( pUnoCellRange );
- if ( !pDataSet )
- throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "Can't access Itemset for range" ) ), uno::Reference< uno::XInterface >() );
- return pDataSet;
-@@ -470,7 +469,7 @@ public:
- if ( pUnoCellRange )
- {
-
-- SfxItemSet* pDataSet = ScVbaCellRangeAccess::GetDataSet( pUnoCellRange );
-+ SfxItemSet* pDataSet = excel::ScVbaCellRangeAccess::GetDataSet( pUnoCellRange );
- SfxItemState eState = pDataSet->GetItemState( ATTR_VALUE_FORMAT, TRUE, NULL);
- // one of the cells in the range is not like the other ;-)
- // so return a zero length format to indicate that
-@@ -1999,7 +1998,7 @@ bool cellInRange( const table::CellRange
-
- void setCursor( const SCCOL& nCol, const SCROW& nRow, bool bInSel = true )
- {
-- ScTabViewShell* pShell = getCurrentBestViewShell();
-+ ScTabViewShell* pShell = excel::getCurrentBestViewShell();
- if ( pShell )
- {
- if ( bInSel )
-@@ -2210,7 +2209,7 @@ ScVbaRange::Copy(const ::uno::Any& Desti
- else
- {
- Select();
-- implnCopy();
-+ excel::implnCopy();
- }
- }
-
-@@ -2234,7 +2233,7 @@ ScVbaRange::Cut(const ::uno::Any& Destin
- }
- {
- Select();
-- implnCut();
-+ excel::implnCut();
- }
- }
-
-@@ -2564,7 +2563,7 @@ ScVbaRange::PasteSpecial( const uno::Any
-
- USHORT nFlags = getPasteFlags(nPaste);
- USHORT nFormulaBits = getPasteFormulaBits(nOperation);
-- implnPasteSpecial(nFlags,nFormulaBits,bSkipBlanks,bTranspose);
-+ excel::implnPasteSpecial(nFlags,nFormulaBits,bSkipBlanks,bTranspose);
- // restore selection
- xSelection->select( uno::makeAny( xSel ) );
- }
-@@ -3233,13 +3232,13 @@ ScVbaRange::End( ::sal_Int32 Direction )
-
- // Save ActiveCell pos ( to restore later )
- uno::Any aDft;
-- rtl::OUString sActiveCell = ScVbaGlobals::getGlobalsImpl(
-- mxContext )->getApplication()->getActiveCell()->Address(aDft, aDft, aDft, aDft, aDft );
-+ uno::Reference< excel::XApplication > xApplication( Application(), uno::UNO_QUERY_THROW );
-+ rtl::OUString sActiveCell = xApplication->getActiveCell()->Address(aDft, aDft, aDft, aDft, aDft );
-
- // position current cell upper left of this range
- Cells( uno::makeAny( (sal_Int32) 1 ), uno::makeAny( (sal_Int32) 1 ) )->Select();
-
-- SfxViewFrame* pViewFrame = getCurrentViewFrame();
-+ SfxViewFrame* pViewFrame = excel::getCurrentViewFrame();
- if ( pViewFrame )
- {
- SfxAllItemSet aArgs( SFX_APP()->GetPool() );
-@@ -3275,18 +3274,17 @@ ScVbaRange::End( ::sal_Int32 Direction )
- }
-
- // result is the ActiveCell
-- rtl::OUString sMoved = ScVbaGlobals::getGlobalsImpl(
-- mxContext )->getApplication()->getActiveCell()->Address(aDft, aDft, aDft, aDft, aDft );
-+ rtl::OUString sMoved = xApplication->getActiveCell()->Address(aDft, aDft, aDft, aDft, aDft );
-
- // restore old ActiveCell
- uno::Any aVoid;
-- uno::Reference< excel::XRange > xOldActiveCell( ScVbaGlobals::getGlobalsImpl(
-- mxContext )->getActiveSheet()->Range( uno::makeAny( sActiveCell ), aVoid ), uno::UNO_QUERY_THROW );
-+
-+ uno::Reference< excel::XRange > xOldActiveCell( xApplication->getActiveSheet()->Range( uno::makeAny( sActiveCell ), aVoid ), uno::UNO_QUERY_THROW );
- xOldActiveCell->Select();
-
- uno::Reference< excel::XRange > resultCell;
-- resultCell.set( ScVbaGlobals::getGlobalsImpl(
-- mxContext )->getActiveSheet()->Range( uno::makeAny( sMoved ), aVoid ), uno::UNO_QUERY_THROW );
-+
-+ resultCell.set( xApplication->getActiveSheet()->Range( uno::makeAny( sMoved ), aVoid ), uno::UNO_QUERY_THROW );
-
- // return result
-
-@@ -3749,7 +3747,7 @@ ScVbaRange::setPageBreak( const uno::Any
- uno::Reference< frame::XModel > xModel = pShell->GetModel();
- if ( xModel.is() )
- {
-- ScTabViewShell* pViewShell = getBestViewShell( xModel );
-+ ScTabViewShell* pViewShell = excel::getBestViewShell( xModel );
- if ( nPageBreak == excel::XlPageBreak::xlPageBreakManual )
- pViewShell->InsertPageBreak( bColumn, TRUE, &aAddr);
- else if ( nPageBreak == excel::XlPageBreak::xlPageBreakNone )
-@@ -4711,7 +4709,7 @@ ScVbaRange::PrintOut( const uno::Any& Fr
- {
- xPrintAreas->setPrintAreas( printAreas );
- uno::Reference< frame::XModel > xModel = pShell->GetModel();
-- PrintOutHelper( From, To, Copies, Preview, ActivePrinter, PrintToFile, Collate, PrToFileName, xModel, sal_True );
-+ PrintOutHelper( excel::getBestViewShell( xModel ), From, To, Copies, Preview, ActivePrinter, PrintToFile, Collate, PrToFileName, sal_True );
- }
- }
- }
-@@ -5362,7 +5360,8 @@ sal_Bool SAL_CALL
- ScVbaRange::hasError() throw (uno::RuntimeException)
- {
- double dResult = sal_False;
-- uno::Reference< script::XInvocation > xInvoc( ScVbaGlobals::getGlobalsImpl( mxContext )->getApplication()->WorksheetFunction(), uno::UNO_QUERY_THROW );
-+ uno::Reference< excel::XApplication > xApplication( Application(), uno::UNO_QUERY_THROW );
-+ uno::Reference< script::XInvocation > xInvoc( xApplication->WorksheetFunction(), uno::UNO_QUERY_THROW );
-
- static rtl::OUString FunctionName( RTL_CONSTASCII_USTRINGPARAM("IsError" ) );
- uno::Sequence< uno::Any > Params(1);
---- sc/source/ui/vba/vbarange.hxx.old 2009-04-06 16:42:00.000000000 +0000
-+++ sc/source/ui/vba/vbarange.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -53,12 +53,15 @@
- #include <com/sun/star/sheet/XSpreadsheet.hpp>
- #include <com/sun/star/sheet/XSheetCellRangeContainer.hpp>
-
--//#include "vbahelperinterface.hxx"
-+//#include <vbahelper/vbahelperinterface.hxx>
- #include "vbaformat.hxx"
-+#include <formula/grammar.hxx>
-
- class ScTableSheetsObj;
- class ScCellRangesBase;
- class ScCellRangeObj;
-+class ScDocShell;
-+class ScDocument;
-
- //typedef InheritedHelperInterfaceImpl1< ov::excel::XRange > ScVbaRange_BASE;
- typedef ScVbaFormat< ov::excel::XRange > ScVbaRange_BASE;
---- sc/source/ui/vba/vbascrollbar.cxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbascrollbar.cxx 1970-01-01 00:00:00.000000000 +0000
-@@ -1,139 +0,0 @@
--/*************************************************************************
-- *
-- * OpenOffice.org - a multi-platform office productivity suite
-- *
-- * $RCSfile$
-- *
-- * $Revision$
-- *
-- * last change: $Author$ $Date$
-- *
-- * The Contents of this file are made available subject to
-- * the terms of GNU Lesser General Public License Version 2.1.
-- *
-- *
-- * GNU Lesser General Public License Version 2.1
-- * =============================================
-- * Copyright 2005 by Sun Microsystems, Inc.
-- * 901 San Antonio Road, Palo Alto, CA 94303, USA
-- *
-- * This library is free software; you can redistribute it and/or
-- * modify it under the terms of the GNU Lesser General Public
-- * License version 2.1, as published by the Free Software Foundation.
-- *
-- * This library 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 for more details.
-- *
-- * You should have received a copy of the GNU Lesser General Public
-- * License along with this library; if not, write to the Free Software
-- * Foundation, Inc., 59 Temple Place, Suite 330, Boston,
-- * MA 02111-1307 USA
-- *
-- ************************************************************************/
--#include "vbascrollbar.hxx"
--#include <vector>
--
--using namespace com::sun::star;
--using namespace ooo::vba;
--
--
--const static rtl::OUString LARGECHANGE( RTL_CONSTASCII_USTRINGPARAM("BlockIncrement") );
--const static rtl::OUString SMALLCHANGE( RTL_CONSTASCII_USTRINGPARAM("LineIncrement") );
--const static rtl::OUString ORIENTATION( RTL_CONSTASCII_USTRINGPARAM("Orientation") );
--const static rtl::OUString SCROLLVALUE( RTL_CONSTASCII_USTRINGPARAM("ScrollValue") );
--const static rtl::OUString SCROLLMAX( RTL_CONSTASCII_USTRINGPARAM("ScrollValueMax") );
--const static rtl::OUString SCROLLMIN( RTL_CONSTASCII_USTRINGPARAM("ScrollValueMin") );
--
--ScVbaScrollBar::ScVbaScrollBar( const css::uno::Reference< ov::XHelperInterface >& xParent, const uno::Reference< uno::XComponentContext >& xContext, const uno::Reference< uno::XInterface >& xControl, const uno::Reference< frame::XModel >& xModel, AbstractGeometryAttributes* pGeomHelper ) : ScrollBarImpl_BASE( xParent, xContext, xControl, xModel, pGeomHelper )
--{
--}
--
--// Attributes
--uno::Any SAL_CALL
--ScVbaScrollBar::getValue() throw (css::uno::RuntimeException)
--{
-- return m_xProps->getPropertyValue( SCROLLVALUE );
--}
--
--void SAL_CALL
--ScVbaScrollBar::setValue( const uno::Any& _value ) throw (::com::sun::star::uno::RuntimeException)
--{
-- m_xProps->setPropertyValue( SCROLLVALUE, _value );
--}
--
--::sal_Int32 SAL_CALL
--ScVbaScrollBar::getMax() throw (uno::RuntimeException)
--{
-- sal_Int32 nMax = 0;
-- m_xProps->getPropertyValue( SCROLLMAX ) >>= nMax;
-- return nMax;
--}
--
--void SAL_CALL
--ScVbaScrollBar::setMax( sal_Int32 nVal ) throw (uno::RuntimeException)
--{
-- m_xProps->setPropertyValue( SCROLLMAX, uno::makeAny( nVal ) );
--}
--
--::sal_Int32 SAL_CALL
--ScVbaScrollBar::getMin() throw (uno::RuntimeException)
--{
-- sal_Int32 nVal = 0;
-- m_xProps->getPropertyValue( SCROLLMIN ) >>= nVal;
-- return nVal;
--}
--
--void SAL_CALL
--ScVbaScrollBar::setMin( sal_Int32 nVal ) throw (uno::RuntimeException)
--{
-- m_xProps->setPropertyValue( SCROLLMIN, uno::makeAny( nVal ) );
--}
--
--void SAL_CALL
--ScVbaScrollBar::setLargeChange( ::sal_Int32 _largechange ) throw (uno::RuntimeException)
--{
-- m_xProps->setPropertyValue( LARGECHANGE, uno::makeAny( _largechange ) );
--}
--
--::sal_Int32 SAL_CALL
--ScVbaScrollBar::getLargeChange() throw (uno::RuntimeException)
--{
-- sal_Int32 nVal = 0;
-- m_xProps->getPropertyValue( LARGECHANGE ) >>= nVal;
-- return nVal;
--}
--
--::sal_Int32 SAL_CALL
--ScVbaScrollBar::getSmallChange() throw (uno::RuntimeException)
--{
-- sal_Int32 nSmallChange = 0;
-- m_xProps->getPropertyValue( SMALLCHANGE ) >>= nSmallChange;
-- return nSmallChange;
--}
--
--void SAL_CALL
--ScVbaScrollBar::setSmallChange( ::sal_Int32 _smallchange ) throw (uno::RuntimeException)
--{
-- m_xProps->setPropertyValue( SMALLCHANGE, uno::makeAny( _smallchange ) );
--}
--
--rtl::OUString&
--ScVbaScrollBar::getServiceImplName()
--{
-- static rtl::OUString sImplName( RTL_CONSTASCII_USTRINGPARAM("ScVbaScrollBar") );
-- return sImplName;
--}
--
--uno::Sequence< rtl::OUString >
--ScVbaScrollBar::getServiceNames()
--{
-- static uno::Sequence< rtl::OUString > aServiceNames;
-- if ( aServiceNames.getLength() == 0 )
-- {
-- aServiceNames.realloc( 1 );
-- aServiceNames[ 0 ] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.msforms.Frame" ) );
-- }
-- return aServiceNames;
--}
---- sc/source/ui/vba/vbascrollbar.hxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbascrollbar.hxx 1970-01-01 00:00:00.000000000 +0000
-@@ -1,66 +0,0 @@
--/*************************************************************************
-- *
-- * OpenOffice.org - a multi-platform office productivity suite
-- *
-- * $RCSfile$
-- *
-- * $Revision$
-- *
-- * last change: $Author$ $Date$
-- *
-- * The Contents of this file are made available subject to
-- * the terms of GNU Lesser General Public License Version 2.1.
-- *
-- *
-- * GNU Lesser General Public License Version 2.1
-- * =============================================
-- * Copyright 2005 by Sun Microsystems, Inc.
-- * 901 San Antonio Road, Palo Alto, CA 94303, USA
-- *
-- * This library is free software; you can redistribute it and/or
-- * modify it under the terms of the GNU Lesser General Public
-- * License version 2.1, as published by the Free Software Foundation.
-- *
-- * This library 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 for more details.
-- *
-- * You should have received a copy of the GNU Lesser General Public
-- * License along with this library; if not, write to the Free Software
-- * Foundation, Inc., 59 Temple Place, Suite 330, Boston,
-- * MA 02111-1307 USA
-- *
-- ************************************************************************/
--#ifndef SC_VBA_SCROLLBAR_HXX
--#define SC_VBA_SCROLLBAR_HXX
--#include <cppuhelper/implbase1.hxx>
--#include <ooo/vba/msforms/XScrollBar.hpp>
--
--#include "vbacontrol.hxx"
--#include "vbahelper.hxx"
--
--typedef cppu::ImplInheritanceHelper1< ScVbaControl, ov::msforms::XScrollBar > ScrollBarImpl_BASE;
--
--class ScVbaScrollBar : public ScrollBarImpl_BASE
--{
--public:
-- ScVbaScrollBar( const css::uno::Reference< ov::XHelperInterface >& xParent, const css::uno::Reference< css::uno::XComponentContext >& xContext, const css::uno::Reference< css::uno::XInterface >& xControl, const css::uno::Reference< css::frame::XModel >& xModel, ov::AbstractGeometryAttributes* pGeomHelper );
-- // Attributes
-- virtual css::uno::Any SAL_CALL getValue() throw (css::uno::RuntimeException);
-- virtual void SAL_CALL setValue( const css::uno::Any& _value ) throw (css::uno::RuntimeException);
-- virtual ::sal_Int32 SAL_CALL getMax() throw (css::uno::RuntimeException);
-- virtual void SAL_CALL setMax( ::sal_Int32 _max ) throw (css::uno::RuntimeException);
-- virtual ::sal_Int32 SAL_CALL getMin() throw (css::uno::RuntimeException);
-- virtual void SAL_CALL setMin( ::sal_Int32 _min ) throw (css::uno::RuntimeException);
-- virtual ::sal_Int32 SAL_CALL getLargeChange() throw (css::uno::RuntimeException);
-- virtual void SAL_CALL setLargeChange( ::sal_Int32 _largechange ) throw (css::uno::RuntimeException);
-- virtual ::sal_Int32 SAL_CALL getSmallChange() throw (css::uno::RuntimeException);
-- virtual void SAL_CALL setSmallChange( ::sal_Int32 _smallchange ) throw (css::uno::RuntimeException);
--
--
-- //XHelperInterface
-- virtual rtl::OUString& getServiceImplName();
-- virtual css::uno::Sequence<rtl::OUString> getServiceNames();
--};
--#endif //SC_VBA_LABEL_HXX
---- sc/source/ui/vba/vbaseriescollection.hxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbaseriescollection.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -31,9 +31,9 @@
- #define SC_VBA_SERIESCOLLECTION_HXX
-
- #include <ooo/vba/excel/XSeriesCollection.hpp>
--#include "vbahelperinterface.hxx"
--#include "vbacollectionimpl.hxx"
--#include "vbahelper.hxx"
-+#include <vbahelper/vbahelperinterface.hxx>
-+#include <vbahelper/vbacollectionimpl.hxx>
-+#include "excelvbahelper.hxx"
-
-
- typedef CollTestImplHelper< ov::excel::XSeriesCollection > SeriesCollection_BASE;
---- sc/source/ui/vba/vbashape.hxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbashape.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -39,7 +39,7 @@
- #include <ooo/vba/msforms/XLineFormat.hpp>
- #include <cppuhelper/implbase2.hxx>
-
--#include "vbahelperinterface.hxx"
-+#include <vbahelper/vbahelperinterface.hxx>
-
- typedef ::cppu::WeakImplHelper2< ov::msforms::XShape, css::lang::XEventListener > ListeningShape;
-
---- sc/source/ui/vba/vbashaperange.cxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbashaperange.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -30,6 +30,7 @@
- #include <com/sun/star/drawing/XShapeGrouper.hpp>
- #include <com/sun/star/drawing/XDrawPage.hpp>
-
-+#include "excelvbahelper.hxx"
- #include "vbashaperange.hxx"
- #include "vbashape.hxx"
-
---- sc/source/ui/vba/vbashaperange.hxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbashaperange.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -33,7 +33,7 @@
- #include <com/sun/star/drawing/XShapes.hpp>
- #include <ooo/vba/msforms/XShapeRange.hpp>
-
--#include "vbacollectionimpl.hxx"
-+#include <vbahelper/vbacollectionimpl.hxx>
-
- typedef CollTestImplHelper< ov::msforms::XShapeRange > ScVbaShapeRange_BASE;
-
---- sc/source/ui/vba/vbashapes.cxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbashapes.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -33,6 +33,7 @@
- #include <ooo/vba/msforms/XShapeRange.hpp>
- #include <ooo/vba/office/MsoAutoShapeType.hpp>
-
-+#include "excelvbahelper.hxx"
- #include "vbashapes.hxx"
- #include "vbashape.hxx"
- #include "vbashaperange.hxx"
---- sc/source/ui/vba/vbashapes.hxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbashapes.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -35,9 +35,9 @@
- #include <com/sun/star/container/XIndexAccess.hpp>
- #include <ooo/vba/msforms/XShapes.hpp>
-
--#include "vbahelperinterface.hxx"
-+#include <vbahelper/vbahelperinterface.hxx>
-
--#include "vbacollectionimpl.hxx"
-+#include <vbahelper/vbacollectionimpl.hxx>
-
- typedef CollTestImplHelper< ov::msforms::XShapes > ScVbaShapes_BASE;
-
---- sc/source/ui/vba/vbaspinbutton.cxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbaspinbutton.cxx 1970-01-01 00:00:00.000000000 +0000
-@@ -1,109 +0,0 @@
--/*************************************************************************
-- *
-- * OpenOffice.org - a multi-platform office productivity suite
-- *
-- * $RCSfile$
-- *
-- * $Revision$
-- *
-- * last change: $Author$ $Date$
-- *
-- * The Contents of this file are made available subject to
-- * the terms of GNU Lesser General Public License Version 2.1.
-- *
-- *
-- * GNU Lesser General Public License Version 2.1
-- * =============================================
-- * Copyright 2005 by Sun Microsystems, Inc.
-- * 901 San Antonio Road, Palo Alto, CA 94303, USA
-- *
-- * This library is free software; you can redistribute it and/or
-- * modify it under the terms of the GNU Lesser General Public
-- * License version 2.1, as published by the Free Software Foundation.
-- *
-- * This library 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 for more details.
-- *
-- * You should have received a copy of the GNU Lesser General Public
-- * License along with this library; if not, write to the Free Software
-- * Foundation, Inc., 59 Temple Place, Suite 330, Boston,
-- * MA 02111-1307 USA
-- *
-- ************************************************************************/
--#include "vbaspinbutton.hxx"
--#include <vector>
--
--using namespace com::sun::star;
--using namespace ooo::vba;
--
--
--const static rtl::OUString ORIENTATION( RTL_CONSTASCII_USTRINGPARAM("Orientation") );
--const static rtl::OUString SPINVALUE( RTL_CONSTASCII_USTRINGPARAM("SpinValue") );
--const static rtl::OUString SPINMAX( RTL_CONSTASCII_USTRINGPARAM("SpinValueMax") );
--const static rtl::OUString SPINMIN( RTL_CONSTASCII_USTRINGPARAM("SpinValueMin") );
--
--ScVbaSpinButton::ScVbaSpinButton( const css::uno::Reference< ov::XHelperInterface >& xParent, const uno::Reference< uno::XComponentContext >& xContext, const uno::Reference< uno::XInterface >& xControl, const uno::Reference< frame::XModel >& xModel, AbstractGeometryAttributes* pGeomHelper ) : SpinButtonImpl_BASE( xParent, xContext, xControl, xModel, pGeomHelper )
--{
--}
--
--// Attributes
--uno::Any SAL_CALL
--ScVbaSpinButton::getValue() throw (css::uno::RuntimeException)
--{
-- return m_xProps->getPropertyValue( SPINVALUE );
--}
--
--void SAL_CALL
--ScVbaSpinButton::setValue( const uno::Any& _value ) throw (::com::sun::star::uno::RuntimeException)
--{
-- m_xProps->setPropertyValue( SPINVALUE, _value );
--}
--
--::sal_Int32 SAL_CALL
--ScVbaSpinButton::getMax() throw (uno::RuntimeException)
--{
-- sal_Int32 nMax = 0;
-- m_xProps->getPropertyValue( SPINMAX ) >>= nMax;
-- return nMax;
--}
--
--void SAL_CALL
--ScVbaSpinButton::setMax( sal_Int32 nVal ) throw (uno::RuntimeException)
--{
-- m_xProps->setPropertyValue( SPINMAX, uno::makeAny( nVal ) );
--}
--
--::sal_Int32 SAL_CALL
--ScVbaSpinButton::getMin() throw (uno::RuntimeException)
--{
-- sal_Int32 nVal = 0;
-- m_xProps->getPropertyValue( SPINMIN ) >>= nVal;
-- return nVal;
--}
--
--void SAL_CALL
--ScVbaSpinButton::setMin( sal_Int32 nVal ) throw (uno::RuntimeException)
--{
-- m_xProps->setPropertyValue( SPINMIN, uno::makeAny( nVal ) );
--}
--
--rtl::OUString&
--ScVbaSpinButton::getServiceImplName()
--{
-- static rtl::OUString sImplName( RTL_CONSTASCII_USTRINGPARAM("ScVbaSpinButton") );
-- return sImplName;
--}
--
--uno::Sequence< rtl::OUString >
--ScVbaSpinButton::getServiceNames()
--{
-- static uno::Sequence< rtl::OUString > aServiceNames;
-- if ( aServiceNames.getLength() == 0 )
-- {
-- aServiceNames.realloc( 1 );
-- aServiceNames[ 0 ] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.msforms.Frame" ) );
-- }
-- return aServiceNames;
--}
---- sc/source/ui/vba/vbaspinbutton.hxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbaspinbutton.hxx 1970-01-01 00:00:00.000000000 +0000
-@@ -1,61 +0,0 @@
--/*************************************************************************
-- *
-- * OpenOffice.org - a multi-platform office productivity suite
-- *
-- * $RCSfile$
-- *
-- * $Revision$
-- *
-- * last change: $Author$ $Date$
-- *
-- * The Contents of this file are made available subject to
-- * the terms of GNU Lesser General Public License Version 2.1.
-- *
-- *
-- * GNU Lesser General Public License Version 2.1
-- * =============================================
-- * Copyright 2005 by Sun Microsystems, Inc.
-- * 901 San Antonio Road, Palo Alto, CA 94303, USA
-- *
-- * This library is free software; you can redistribute it and/or
-- * modify it under the terms of the GNU Lesser General Public
-- * License version 2.1, as published by the Free Software Foundation.
-- *
-- * This library 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 for more details.
-- *
-- * You should have received a copy of the GNU Lesser General Public
-- * License along with this library; if not, write to the Free Software
-- * Foundation, Inc., 59 Temple Place, Suite 330, Boston,
-- * MA 02111-1307 USA
-- *
-- ************************************************************************/
--#ifndef SC_VBA_SPINBUTTON_HXX
--#define SC_VBA_SPINBUTTON_HXX
--#include <cppuhelper/implbase1.hxx>
--#include <ooo/vba/msforms/XSpinButton.hpp>
--
--#include "vbacontrol.hxx"
--#include "vbahelper.hxx"
--
--typedef cppu::ImplInheritanceHelper1< ScVbaControl, ov::msforms::XSpinButton > SpinButtonImpl_BASE;
--
--class ScVbaSpinButton : public SpinButtonImpl_BASE
--{
--public:
-- ScVbaSpinButton( const css::uno::Reference< ov::XHelperInterface >& xParent, const css::uno::Reference< css::uno::XComponentContext >& xContext, const css::uno::Reference< css::uno::XInterface >& xControl, const css::uno::Reference< css::frame::XModel >& xModel, ov::AbstractGeometryAttributes* pGeomHelper );
-- // Attributes
-- virtual css::uno::Any SAL_CALL getValue() throw (css::uno::RuntimeException);
-- virtual void SAL_CALL setValue( const css::uno::Any& _value ) throw (css::uno::RuntimeException);
-- virtual ::sal_Int32 SAL_CALL getMax() throw (css::uno::RuntimeException);
-- virtual void SAL_CALL setMax( ::sal_Int32 _max ) throw (css::uno::RuntimeException);
-- virtual ::sal_Int32 SAL_CALL getMin() throw (css::uno::RuntimeException);
-- virtual void SAL_CALL setMin( ::sal_Int32 _min ) throw (css::uno::RuntimeException);
--
-- //XHelperInterface
-- virtual rtl::OUString& getServiceImplName();
-- virtual css::uno::Sequence<rtl::OUString> getServiceNames();
--};
--#endif //SC_VBA_SPINBUTTON_HXX
---- sc/source/ui/vba/vbastyles.cxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbastyles.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -29,6 +29,7 @@
- ************************************************************************/
- #include "vbastyles.hxx"
- #include "vbastyle.hxx"
-+#include <ooo/vba/excel/XRange.hpp>
-
- using namespace ::ooo::vba;
- using namespace ::com::sun::star;
---- sc/source/ui/vba/vbastyles.hxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbastyles.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -31,7 +31,7 @@
- #define SC_VBA_STYLES_HXX
- #include <ooo/vba/excel/XStyles.hpp>
- #include <com/sun/star/container/XNameContainer.hpp>
--#include "vbacollectionimpl.hxx"
-+#include <vbahelper/vbacollectionimpl.hxx>
-
- typedef CollTestImplHelper< ov::excel::XStyles > ScVbaStyles_BASE;
- class ScVbaStyles: public ScVbaStyles_BASE
---- sc/source/ui/vba/vbatextbox.cxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbatextbox.cxx 1970-01-01 00:00:00.000000000 +0000
-@@ -1,137 +0,0 @@
--/*************************************************************************
-- *
-- * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-- *
-- * Copyright 2008 by Sun Microsystems, Inc.
-- *
-- * OpenOffice.org - a multi-platform office productivity suite
-- *
-- * $RCSfile: vbatextbox.cxx,v $
-- * $Revision: 1.3 $
-- *
-- * 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 <com/sun/star/text/XTextRange.hpp>
--
--#include "vbatextbox.hxx"
--#include <vector>
--
--using namespace com::sun::star;
--using namespace ooo::vba;
--
--
--
--ScVbaTextBox::ScVbaTextBox( const uno::Reference< ov::XHelperInterface >& xParent, const uno::Reference< uno::XComponentContext >& xContext, const uno::Reference< uno::XInterface >& xControl, const uno::Reference< frame::XModel >& xModel, AbstractGeometryAttributes* pGeomHelper, bool bDialog ) : TextBoxImpl_BASE( xParent, xContext, xControl, xModel, pGeomHelper ), mbDialog( bDialog )
--{
--}
--
--// Attributes
--uno::Any SAL_CALL
--ScVbaTextBox::getValue() throw (css::uno::RuntimeException)
--{
-- return uno::makeAny( getText() );
--}
--
--void SAL_CALL
--ScVbaTextBox::setValue( const uno::Any& _value ) throw (css::uno::RuntimeException)
--{
-- rtl::OUString sVal = getAnyAsString( _value );
-- setText( sVal );
--}
--
--//getString() will cause some imfo lose.
--rtl::OUString SAL_CALL
--ScVbaTextBox::getText() throw (css::uno::RuntimeException)
--{
-- uno::Any aValue;
-- aValue = m_xProps->getPropertyValue
-- (rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "Text" ) ) );
-- rtl::OUString sString;
-- aValue >>= sString;
-- return sString;
--}
--
--void SAL_CALL
--ScVbaTextBox::setText( const rtl::OUString& _text ) throw (css::uno::RuntimeException)
--{
-- if ( !mbDialog )
-- {
-- uno::Reference< text::XTextRange > xTextRange( m_xProps, uno::UNO_QUERY_THROW );
-- xTextRange->setString( _text );
--}
-- else
-- m_xProps->setPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("Text") ), uno::makeAny( _text ) );
--}
--
--sal_Int32 SAL_CALL
--ScVbaTextBox::getMaxLength() throw (css::uno::RuntimeException)
--{
-- uno::Any aValue;
-- aValue = m_xProps->getPropertyValue
-- (rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "MaxTextLen" ) ) );
-- sal_Int32 nMaxLength = 0;
-- aValue >>= nMaxLength;
-- return nMaxLength;
--}
--
--void SAL_CALL
--ScVbaTextBox::setMaxLength( sal_Int32 _maxlength ) throw (css::uno::RuntimeException)
--{
-- uno::Any aValue( _maxlength );
-- m_xProps->setPropertyValue
-- (rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "MaxTextLen" ) ), aValue);
--}
--
--sal_Bool SAL_CALL
--ScVbaTextBox::getMultiline() throw (css::uno::RuntimeException)
--{
-- uno::Any aValue;
-- aValue = m_xProps->getPropertyValue
-- (rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "MultiLine" ) ) );
-- sal_Bool bRet = false;
-- aValue >>= bRet;
-- return bRet;
--}
--
--void SAL_CALL
--ScVbaTextBox::setMultiline( sal_Bool _multiline ) throw (css::uno::RuntimeException)
--{
-- uno::Any aValue( _multiline );
-- m_xProps->setPropertyValue
-- (rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "MultiLine" ) ), aValue);
--}
--
--rtl::OUString&
--ScVbaTextBox::getServiceImplName()
--{
-- static rtl::OUString sImplName( RTL_CONSTASCII_USTRINGPARAM("ScVbaTextBox") );
-- return sImplName;
--}
--
--uno::Sequence< rtl::OUString >
--ScVbaTextBox::getServiceNames()
--{
-- static uno::Sequence< rtl::OUString > aServiceNames;
-- if ( aServiceNames.getLength() == 0 )
-- {
-- aServiceNames.realloc( 1 );
-- aServiceNames[ 0 ] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.msforms.TextBox" ) );
-- }
-- return aServiceNames;
--}
---- sc/source/ui/vba/vbatextbox.hxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbatextbox.hxx 1970-01-01 00:00:00.000000000 +0000
-@@ -1,57 +0,0 @@
--/*************************************************************************
-- *
-- * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-- *
-- * Copyright 2008 by Sun Microsystems, Inc.
-- *
-- * OpenOffice.org - a multi-platform office productivity suite
-- *
-- * $RCSfile: vbatextbox.hxx,v $
-- * $Revision: 1.3 $
-- *
-- * 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.
-- *
-- ************************************************************************/
--#ifndef SC_VBA_TEXTBOX_HXX
--#define SC_VBA_TEXTBOX_HXX
--#include <cppuhelper/implbase1.hxx>
--#include <ooo/vba/msforms/XTextBox.hpp>
--#include "vbacontrol.hxx"
--#include "vbahelper.hxx"
--
--typedef cppu::ImplInheritanceHelper1< ScVbaControl, ov::msforms::XTextBox > TextBoxImpl_BASE;
--
--class ScVbaTextBox : public TextBoxImpl_BASE
--{
-- bool mbDialog;
--public:
-- ScVbaTextBox( const css::uno::Reference< ov::XHelperInterface >& xParent, const css::uno::Reference< css::uno::XComponentContext >& xContext, const css::uno::Reference< css::uno::XInterface >& xControl, const css::uno::Reference< css::frame::XModel >& xModel, ov::AbstractGeometryAttributes* pGeomHelper, bool bDialog = false );
-- // Attributes
-- virtual css::uno::Any SAL_CALL getValue() throw (css::uno::RuntimeException);
-- virtual void SAL_CALL setValue( const css::uno::Any& _value ) throw (css::uno::RuntimeException);
-- virtual rtl::OUString SAL_CALL getText() throw (css::uno::RuntimeException);
-- virtual void SAL_CALL setText( const rtl::OUString& _text ) throw (css::uno::RuntimeException);
-- virtual sal_Int32 SAL_CALL getMaxLength() throw (css::uno::RuntimeException);
-- virtual void SAL_CALL setMaxLength( sal_Int32 _maxlength ) throw (css::uno::RuntimeException);
-- virtual sal_Bool SAL_CALL getMultiline() throw (css::uno::RuntimeException);
-- virtual void SAL_CALL setMultiline( sal_Bool _multiline ) throw (css::uno::RuntimeException);
-- //XHelperInterface
-- virtual rtl::OUString& getServiceImplName();
-- virtual css::uno::Sequence<rtl::OUString> getServiceNames();
--};
--#endif //SC_VBA_TEXTBOX_HXX
---- sc/source/ui/vba/vbatextboxshape.cxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbatextboxshape.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -62,7 +62,7 @@ ScVbaTextBoxShape::setText( const rtl::O
- uno::Reference< excel::XCharacters > SAL_CALL
- ScVbaTextBoxShape::characters( const uno::Any& Start, const uno::Any& Length ) throw (uno::RuntimeException)
- {
-- ScDocShell* pDocShell = getDocShell( m_xModel );
-+ ScDocShell* pDocShell = excel::getDocShell( m_xModel );
- ScDocument* pDoc = pDocShell ? pDocShell->GetDocument() : NULL;
-
- if ( !pDoc )
---- sc/source/ui/vba/vbatextboxshape.hxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbatextboxshape.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -38,7 +38,7 @@
- #include <com/sun/star/text/XTextRange.hpp>
- #include <ooo/vba/msforms/XTextBoxShape.hpp>
- #include "vbashape.hxx"
--#include "vbahelper.hxx"
-+#include "excelvbahelper.hxx"
- #include "vbacharacters.hxx"
-
- typedef cppu::ImplInheritanceHelper1< ScVbaShape, ov::msforms::XTextBoxShape > TextBoxShapeImpl_BASE;
---- sc/source/ui/vba/vbatextframe.hxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbatextframe.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -34,7 +34,7 @@
- #include <ooo/vba/excel/XCharacters.hpp>
- #include <ooo/vba/excel/XTextFrame.hpp>
-
--#include "vbahelperinterface.hxx"
-+#include <vbahelper/vbahelperinterface.hxx>
- #include "vbapalette.hxx"
-
- typedef InheritedHelperInterfaceImpl1< ov::excel::XTextFrame > ScVbaTextFrame_BASE;
---- sc/source/ui/vba/vbatitle.hxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbatitle.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -30,14 +30,15 @@
- #ifndef SC_VBA_TITLE_HXX
- #define SC_VBA_TITLE_HXX
-
--#include "vbahelperinterface.hxx"
--#include "vbahelper.hxx"
-+#include <vbahelper/vbahelperinterface.hxx>
-+#include "excelvbahelper.hxx"
- #include "vbainterior.hxx"
- #include "vbafont.hxx"
- #include "vbapalette.hxx"
- #include <com/sun/star/drawing/XShape.hpp>
- #include <com/sun/star/beans/XPropertySet.hpp>
- #include <ooo/vba/excel/XTitle.hpp>
-+#include <ooo/vba/excel/XCharacters.hpp>
- #include <basic/sberrors.hxx>
- #include <memory>
-
---- sc/source/ui/vba/vbatogglebutton.cxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbatogglebutton.cxx 1970-01-01 00:00:00.000000000 +0000
-@@ -1,108 +0,0 @@
--/*************************************************************************
-- *
-- * OpenOffice.org - a multi-platform office productivity suite
-- *
-- * $RCSfile$
-- *
-- * $Revision$
-- *
-- * last change: $Author$ $Date$
-- *
-- * The Contents of this file are made available subject to
-- * the terms of GNU Lesser General Public License Version 2.1.
-- *
-- *
-- * GNU Lesser General Public License Version 2.1
-- * =============================================
-- * Copyright 2005 by Sun Microsystems, Inc.
-- * 901 San Antonio Road, Palo Alto, CA 94303, USA
-- *
-- * This library is free software; you can redistribute it and/or
-- * modify it under the terms of the GNU Lesser General Public
-- * License version 2.1, as published by the Free Software Foundation.
-- *
-- * This library 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 for more details.
-- *
-- * You should have received a copy of the GNU Lesser General Public
-- * License along with this library; if not, write to the Free Software
-- * Foundation, Inc., 59 Temple Place, Suite 330, Boston,
-- * MA 02111-1307 USA
-- *
-- ************************************************************************/
--#include "vbatogglebutton.hxx"
--#include <vector>
--
--using namespace com::sun::star;
--using namespace ooo::vba;
--
--
--const static rtl::OUString LABEL( RTL_CONSTASCII_USTRINGPARAM("Label") );
--const static rtl::OUString TOGGLE( RTL_CONSTASCII_USTRINGPARAM("Toggle") );
--const static rtl::OUString STATE( RTL_CONSTASCII_USTRINGPARAM("State") );
--ScVbaToggleButton::ScVbaToggleButton( const css::uno::Reference< ov::XHelperInterface >& xParent, const uno::Reference< uno::XComponentContext >& xContext, const uno::Reference< uno::XInterface >& xControl, const uno::Reference< frame::XModel >& xModel, ov::AbstractGeometryAttributes* pGeomHelper ) : ToggleButtonImpl_BASE( xParent, xContext, xControl, xModel, pGeomHelper )
--{
-- OSL_TRACE("ScVbaToggleButton(ctor)");
-- m_xProps->setPropertyValue( TOGGLE, uno::makeAny( sal_True ) );
--}
--
--ScVbaToggleButton::~ScVbaToggleButton()
--{
-- OSL_TRACE("~ScVbaToggleButton(dtor)");
--}
--
--// Attributes
--rtl::OUString SAL_CALL
--ScVbaToggleButton::getCaption() throw (css::uno::RuntimeException)
--{
-- rtl::OUString Label;
-- m_xProps->getPropertyValue( LABEL ) >>= Label;
-- return Label;
--}
--
--void SAL_CALL
--ScVbaToggleButton::setCaption( const rtl::OUString& _caption ) throw (::com::sun::star::uno::RuntimeException)
--{
-- m_xProps->setPropertyValue( LABEL, uno::makeAny( _caption ) );
--}
--
--uno::Any SAL_CALL
--ScVbaToggleButton::getValue() throw (uno::RuntimeException)
--{
-- sal_Int16 nState = 0;
-- m_xProps->getPropertyValue( STATE ) >>= nState;
-- return uno::makeAny( nState ? sal_Int16( -1 ) : sal_Int16( 0 ) );
--}
--
--void SAL_CALL
--ScVbaToggleButton::setValue( const uno::Any& _value ) throw (uno::RuntimeException)
--{
-- sal_Int16 nState = 0;
-- _value >>= nState;
-- OSL_TRACE( "nState - %d", nState );
-- nState = ( nState == -1 ) ? 1 : 0;
-- OSL_TRACE( "nState - %d", nState );
-- m_xProps->setPropertyValue( STATE, uno::makeAny( nState ) );
--}
--
--rtl::OUString&
--ScVbaToggleButton::getServiceImplName()
--{
-- static rtl::OUString sImplName( RTL_CONSTASCII_USTRINGPARAM("ScVbaToggleButton") );
-- return sImplName;
--}
--
--uno::Sequence< rtl::OUString >
--ScVbaToggleButton::getServiceNames()
--{
-- static uno::Sequence< rtl::OUString > aServiceNames;
-- if ( aServiceNames.getLength() == 0 )
-- {
-- aServiceNames.realloc( 1 );
-- aServiceNames[ 0 ] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.msforms.ToggleButton" ) );
-- }
-- return aServiceNames;
--}
--
---- sc/source/ui/vba/vbatogglebutton.hxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbatogglebutton.hxx 1970-01-01 00:00:00.000000000 +0000
-@@ -1,63 +0,0 @@
--/*************************************************************************
-- *
-- * OpenOffice.org - a multi-platform office productivity suite
-- *
-- * $RCSfile$
-- *
-- * $Revision$
-- *
-- * last change: $Author$ $Date$
-- *
-- * The Contents of this file are made available subject to
-- * the terms of GNU Lesser General Public License Version 2.1.
-- *
-- *
-- * GNU Lesser General Public License Version 2.1
-- * =============================================
-- * Copyright 2005 by Sun Microsystems, Inc.
-- * 901 San Antonio Road, Palo Alto, CA 94303, USA
-- *
-- * This library is free software; you can redistribute it and/or
-- * modify it under the terms of the GNU Lesser General Public
-- * License version 2.1, as published by the Free Software Foundation.
-- *
-- * This library 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 for more details.
-- *
-- * You should have received a copy of the GNU Lesser General Public
-- * License along with this library; if not, write to the Free Software
-- * Foundation, Inc., 59 Temple Place, Suite 330, Boston,
-- * MA 02111-1307 USA
-- *
-- ************************************************************************/
--#ifndef SC_VBA_TOGGLEBUTTON_HXX
--#define SC_VBA_TOGGLEBUTTON_HXX
--#include <cppuhelper/implbase2.hxx>
--#include <ooo/vba/msforms/XToggleButton.hpp>
--
--#include "vbacontrol.hxx"
--#include "vbahelper.hxx"
--
--typedef cppu::ImplInheritanceHelper2< ScVbaControl, ov::msforms::XToggleButton, css::script::XDefaultProperty > ToggleButtonImpl_BASE;
--
--class ScVbaToggleButton : public ToggleButtonImpl_BASE
--{
-- rtl::OUString msDftPropName;
--public:
-- ScVbaToggleButton( const css::uno::Reference< ov::XHelperInterface >& xParent, const css::uno::Reference< css::uno::XComponentContext >& xContext, const css::uno::Reference< css::uno::XInterface >& xControl, const css::uno::Reference< css::frame::XModel >& xModel, ov::AbstractGeometryAttributes* pGeomHelper );
-- ~ScVbaToggleButton();
-- // Attributes
-- virtual css::uno::Any SAL_CALL getValue() throw (css::uno::RuntimeException);
-- virtual void SAL_CALL setValue( const css::uno::Any& _value ) throw (css::uno::RuntimeException);
--
-- virtual rtl::OUString SAL_CALL getCaption() throw (css::uno::RuntimeException);
-- virtual void SAL_CALL setCaption( const rtl::OUString& _caption ) throw (css::uno::RuntimeException);
-- //XHelperInterface
-- virtual rtl::OUString& getServiceImplName();
-- virtual css::uno::Sequence<rtl::OUString> getServiceNames();
-- // XDefaultProperty
-- rtl::OUString SAL_CALL getDefaultPropertyName( ) throw (css::uno::RuntimeException) { return ::rtl::OUString::createFromAscii("Value"); }
--};
--#endif //SC_VBA_TOGGLEBUTTON_HXX
---- sc/source/ui/vba/vbauserform.cxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbauserform.cxx 1970-01-01 00:00:00.000000000 +0000
-@@ -1,228 +0,0 @@
--/*************************************************************************
-- *
-- * OpenOffice.org - a multi-platform office productivity suite
-- *
-- * $RCSfile$
-- *
-- * $Revision$
-- *
-- * last change: $Author$ $Date$
-- *
-- * The Contents of this file are made available subject to
-- * the terms of GNU Lesser General Public License Version 2.1.
-- *
-- *
-- * GNU Lesser General Public License Version 2.1
-- * =============================================
-- * Copyright 2005 by Sun Microsystems, Inc.
-- * 901 San Antonio Road, Palo Alto, CA 94303, USA
-- *
-- * This library is free software; you can redistribute it and/or
-- * modify it under the terms of the GNU Lesser General Public
-- * License version 2.1, as published by the Free Software Foundation.
-- *
-- * This library 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 for more details.
-- *
-- * You should have received a copy of the GNU Lesser General Public
-- * License along with this library; if not, write to the Free Software
-- * Foundation, Inc., 59 Temple Place, Suite 330, Boston,
-- * MA 02111-1307 USA
-- *
-- ************************************************************************/
--#include "helperdecl.hxx"
--#include "vbauserform.hxx"
--#include <com/sun/star/awt/XControl.hpp>
--#include <com/sun/star/awt/XControlContainer.hpp>
--#include <com/sun/star/beans/PropertyConcept.hpp>
--#include <basic/sbx.hxx>
--#include <basic/sbstar.hxx>
--#include <basic/sbmeth.hxx>
--#include "unonames.hxx"
--#include "vbacontrols.hxx"
--
--using namespace ::ooo::vba;
--using namespace ::com::sun::star;
--
--// some little notes
--// XDialog implementation has the following interesting bits
--// a Controls property ( which is an array of the container controls )
--// each item in the controls array is a XControl, where the model is
--// basically a property bag
--// additionally the XDialog instance has itself a model
--// this model has a ControlModels ( array of models ) property
--// the models in ControlModels can be accessed by name
--// also the XDialog is a XControl ( to access the model above
--
--ScVbaUserForm::ScVbaUserForm( uno::Sequence< uno::Any > const& aArgs, uno::Reference< uno::XComponentContext >const& xContext ) throw ( lang::IllegalArgumentException ) : ScVbaUserForm_BASE( getXSomethingFromArgs< XHelperInterface >( aArgs, 0 ), xContext, getXSomethingFromArgs< uno::XInterface >( aArgs, 1 ), getXSomethingFromArgs< frame::XModel >( aArgs, 2 ), static_cast< ooo::vba::AbstractGeometryAttributes* >(0) ), m_pDocShell( 0 ), mbDispose( true )
--{
-- m_xDialog.set( m_xControl, uno::UNO_QUERY_THROW );
-- uno::Reference< awt::XControl > xControl( m_xDialog, uno::UNO_QUERY_THROW );
-- m_pDocShell = getDocShell( m_xModel );
-- m_xProps.set( xControl->getModel(), uno::UNO_QUERY_THROW );
-- setGeometryHelper( new UserFormGeometryHelper( xContext, xControl ) );
--}
--
--ScVbaUserForm::~ScVbaUserForm()
--{
--}
--
--void SAL_CALL
--ScVbaUserForm::Show( ) throw (uno::RuntimeException)
--{
-- OSL_TRACE("ScVbaUserForm::Show( )");
-- short aRet = 0;
-- if ( m_xDialog.is() )
-- aRet = m_xDialog->execute();
-- OSL_TRACE("ScVbaUserForm::Show() execute returned %d", aRet);
-- if ( mbDispose )
-- {
-- try
-- {
-- uno::Reference< lang::XComponent > xComp( m_xDialog, uno::UNO_QUERY_THROW );
-- m_xDialog = NULL;
-- xComp->dispose();
-- mbDispose = false;
-- }
-- catch( uno::Exception& )
-- {
-- }
-- }
--}
--
--rtl::OUString SAL_CALL
--ScVbaUserForm::getCaption() throw (::com::sun::star::uno::RuntimeException)
--{
-- rtl::OUString sCaption;
-- m_xProps->getPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("Title") ) ) >>= sCaption;
-- return sCaption;
--}
--void
--ScVbaUserForm::setCaption( const ::rtl::OUString& _caption ) throw (::com::sun::star::uno::RuntimeException)
--{
-- m_xProps->setPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("Title") ), uno::makeAny( _caption ) );
--}
--
--void SAL_CALL
--ScVbaUserForm::Hide( ) throw (uno::RuntimeException)
--{
-- mbDispose = false; // hide not dispose
-- if ( m_xDialog.is() )
-- m_xDialog->endExecute();
--}
--
--void SAL_CALL
--ScVbaUserForm::RePaint( ) throw (uno::RuntimeException)
--{
-- // do nothing
--}
--
--void SAL_CALL
--ScVbaUserForm::UnloadObject( ) throw (uno::RuntimeException)
--{
-- mbDispose = true;
-- if ( m_xDialog.is() )
-- m_xDialog->endExecute();
--}
--
--rtl::OUString&
--ScVbaUserForm::getServiceImplName()
--{
-- static rtl::OUString sImplName( RTL_CONSTASCII_USTRINGPARAM("ScVbaUserForm") );
-- return sImplName;
--}
--
--uno::Sequence< rtl::OUString >
--ScVbaUserForm::getServiceNames()
--{
-- static uno::Sequence< rtl::OUString > aServiceNames;
-- if ( aServiceNames.getLength() == 0 )
-- {
-- aServiceNames.realloc( 1 );
-- aServiceNames[ 0 ] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.excel.UserForm" ) );
-- }
-- return aServiceNames;
--}
--
--uno::Reference< beans::XIntrospectionAccess > SAL_CALL
--ScVbaUserForm::getIntrospection( ) throw (uno::RuntimeException)
--{
-- return uno::Reference< beans::XIntrospectionAccess >();
--}
--
--uno::Any SAL_CALL
--ScVbaUserForm::invoke( const ::rtl::OUString& /*aFunctionName*/, const uno::Sequence< uno::Any >& /*aParams*/, uno::Sequence< ::sal_Int16 >& /*aOutParamIndex*/, uno::Sequence< uno::Any >& /*aOutParam*/ ) throw (lang::IllegalArgumentException, script::CannotConvertException, reflection::InvocationTargetException, uno::RuntimeException)
--{
-- throw uno::RuntimeException(); // unsupported operation
--}
--
--void SAL_CALL
--ScVbaUserForm::setValue( const ::rtl::OUString& aPropertyName, const uno::Any& aValue ) throw (beans::UnknownPropertyException, script::CannotConvertException, reflection::InvocationTargetException, uno::RuntimeException)
--{
-- uno::Any aObject = getValue( aPropertyName );
-- // The Object *must* support XDefaultProperty here because getValue will
-- // only return properties that are Objects ( e.g. controls )
-- // e.g. Userform1.aControl = something
-- // 'aControl' has to support XDefaultProperty to make sense here
-- uno::Reference< script::XDefaultProperty > xDfltProp( aObject, uno::UNO_QUERY_THROW );
-- rtl::OUString aDfltPropName = xDfltProp->getDefaultPropertyName();
-- uno::Reference< beans::XIntrospectionAccess > xUnoAccess( getIntrospectionAccess( aObject ) );
-- uno::Reference< beans::XPropertySet > xPropSet( xUnoAccess->queryAdapter( ::getCppuType( (const uno::Reference< beans::XPropertySet > *)0 ) ), uno::UNO_QUERY_THROW );
-- xPropSet->setPropertyValue( aDfltPropName, aValue );
--}
--
--uno::Any SAL_CALL
--ScVbaUserForm::getValue( const ::rtl::OUString& aPropertyName ) throw (beans::UnknownPropertyException, uno::RuntimeException)
--{
-- uno::Reference< awt::XControl > xDialogControl( m_xDialog, uno::UNO_QUERY_THROW );
-- uno::Reference< awt::XControlContainer > xContainer( m_xDialog, uno::UNO_QUERY_THROW );
-- uno::Reference< awt::XControl > xControl = xContainer->getControl( aPropertyName );
-- ScVbaControlFactory aFac( mxContext, xControl, m_xModel );
-- uno::Reference< msforms::XControl > xVBAControl( aFac.createControl( xDialogControl->getModel() ) );
-- ScVbaControl* pControl = dynamic_cast< ScVbaControl* >( xVBAControl.get() );
-- pControl->setGeometryHelper( new UserFormGeometryHelper( mxContext, xControl ) );
-- return uno::makeAny( xVBAControl );
--}
--
--::sal_Bool SAL_CALL
--ScVbaUserForm::hasMethod( const ::rtl::OUString& /*aName*/ ) throw (uno::RuntimeException)
--{
-- return sal_False;
--}
--uno::Any SAL_CALL
--ScVbaUserForm::Controls( const uno::Any& index ) throw (uno::RuntimeException)
--{
-- uno::Reference< awt::XControl > xDialogControl( m_xDialog, uno::UNO_QUERY_THROW );
-- uno::Reference< XCollection > xControls( new ScVbaControls( this, mxContext, xDialogControl ) );
-- if ( index.hasValue() )
-- return uno::makeAny( xControls->Item( index, uno::Any() ) );
-- return uno::makeAny( xControls );
--}
--
--::sal_Bool SAL_CALL
--ScVbaUserForm::hasProperty( const ::rtl::OUString& aName ) throw (uno::RuntimeException)
--{
-- uno::Reference< awt::XControl > xControl( m_xDialog, uno::UNO_QUERY );
-- OSL_TRACE("ScVbaUserForm::hasProperty(%s) %d", rtl::OUStringToOString( aName, RTL_TEXTENCODING_UTF8 ).getStr(), xControl.is() );
-- if ( xControl.is() )
-- {
-- uno::Reference< container::XNameAccess > xNameAccess( xControl->getModel(), uno::UNO_QUERY_THROW );
-- sal_Bool bRes = xNameAccess->hasByName( aName );
-- OSL_TRACE("ScVbaUserForm::hasProperty(%s) %d ---> %d", rtl::OUStringToOString( aName, RTL_TEXTENCODING_UTF8 ).getStr(), xControl.is(), bRes );
-- return bRes;
-- }
-- return sal_False;
--}
--
--namespace userform
--{
--namespace sdecl = comphelper::service_decl;
--sdecl::vba_service_class_<ScVbaUserForm, sdecl::with_args<true> > serviceImpl;
--extern sdecl::ServiceDecl const serviceDecl(
-- serviceImpl,
-- "ScVbaUserForm",
-- "ooo.vba.excel.UserForm" );
--}
--
---- sc/source/ui/vba/vbauserform.hxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbauserform.hxx 1970-01-01 00:00:00.000000000 +0000
-@@ -1,78 +0,0 @@
--/*************************************************************************
-- *
-- * OpenOffice.org - a multi-platform office productivity suite
-- *
-- * $RCSfile$
-- *
-- * $Revision$
-- *
-- * last change: $Author$ $Date$
-- *
-- * The Contents of this file are made available subject to
-- * the terms of GNU Lesser General Public License Version 2.1.
-- *
-- *
-- * GNU Lesser General Public License Version 2.1
-- * =============================================
-- * Copyright 2005 by Sun Microsystems, Inc.
-- * 901 San Antonio Road, Palo Alto, CA 94303, USA
-- *
-- * This library is free software; you can redistribute it and/or
-- * modify it under the terms of the GNU Lesser General Public
-- * License version 2.1, as published by the Free Software Foundation.
-- *
-- * This library 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 for more details.
-- *
-- * You should have received a copy of the GNU Lesser General Public
-- * License along with this library; if not, write to the Free Software
-- * Foundation, Inc., 59 Temple Place, Suite 330, Boston,
-- * MA 02111-1307 USA
-- *
-- ************************************************************************/
--#ifndef SC_VBA_USERFORM_HXX
--#define SC_VBA_USERFORM_HXX
--
--#include <cppuhelper/implbase1.hxx>
--#include <ooo/vba/msforms/XUserForm.hpp>
--#include <com/sun/star/awt/XDialog.hpp>
--#include <com/sun/star/frame/XModel.hpp>
--
--#include "vbahelperinterface.hxx"
--#include "vbacontrol.hxx"
--
--//typedef InheritedHelperInterfaceImpl1< ov::msforms::XUserForm > ScVbaUserForm_BASE;
--typedef cppu::ImplInheritanceHelper1< ScVbaControl, ov::msforms::XUserForm > ScVbaUserForm_BASE;
--
--class ScVbaUserForm : public ScVbaUserForm_BASE
--{
--private:
-- css::uno::Reference< css::awt::XDialog > m_xDialog;
-- ScDocShell* m_pDocShell;
-- bool mbDispose;
--protected:
--public:
-- ScVbaUserForm( css::uno::Sequence< css::uno::Any > const& aArgs, css::uno::Reference< css::uno::XComponentContext >const& xContext ) throw ( css::lang::IllegalArgumentException );
-- virtual ~ScVbaUserForm();
-- // XUserForm
-- virtual void SAL_CALL RePaint( ) throw (css::uno::RuntimeException);
-- virtual void SAL_CALL Show( ) throw (css::uno::RuntimeException);
-- // XIntrospection
-- virtual css::uno::Reference< css::beans::XIntrospectionAccess > SAL_CALL getIntrospection( ) throw (css::uno::RuntimeException);
-- virtual css::uno::Any SAL_CALL invoke( const ::rtl::OUString& aFunctionName, const css::uno::Sequence< css::uno::Any >& aParams, css::uno::Sequence< ::sal_Int16 >& aOutParamIndex, css::uno::Sequence< css::uno::Any >& aOutParam ) throw (css::lang::IllegalArgumentException, css::script::CannotConvertException, css::reflection::InvocationTargetException, css::uno::RuntimeException);
-- virtual void SAL_CALL setValue( const ::rtl::OUString& aPropertyName, const css::uno::Any& aValue ) throw (css::beans::UnknownPropertyException, css::script::CannotConvertException, css::reflection::InvocationTargetException, css::uno::RuntimeException);
-- virtual css::uno::Any SAL_CALL getValue( const ::rtl::OUString& aPropertyName ) throw (css::beans::UnknownPropertyException, css::uno::RuntimeException);
-- virtual ::sal_Bool SAL_CALL hasMethod( const ::rtl::OUString& aName ) throw (css::uno::RuntimeException);
-- virtual ::sal_Bool SAL_CALL hasProperty( const ::rtl::OUString& aName ) throw (css::uno::RuntimeException);
-- virtual ::rtl::OUString SAL_CALL getCaption() throw (::com::sun::star::uno::RuntimeException);
-- virtual void SAL_CALL setCaption( const ::rtl::OUString& _caption ) throw (::com::sun::star::uno::RuntimeException);
-- virtual void SAL_CALL Hide( ) throw (css::uno::RuntimeException);
-- virtual void SAL_CALL UnloadObject( ) throw (css::uno::RuntimeException);
-- virtual css::uno::Any SAL_CALL Controls( const css::uno::Any& index ) throw (css::uno::RuntimeException);
-- //XHelperInterface
-- virtual rtl::OUString& getServiceImplName();
-- virtual css::uno::Sequence<rtl::OUString> getServiceNames();
--};
--#endif
---- sc/source/ui/vba/vbavalidation.hxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbavalidation.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -33,7 +33,7 @@
- #include <com/sun/star/uno/XComponentContext.hpp>
- #include <ooo/vba/excel/XValidation.hpp>
- #include <com/sun/star/table/XCellRange.hpp>
--#include "vbahelperinterface.hxx"
-+#include <vbahelper/vbahelperinterface.hxx>
-
- typedef InheritedHelperInterfaceImpl1<ov::excel::XValidation > ValidationImpl_BASE;
-
---- sc/source/ui/vba/vbawindow.cxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbawindow.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -27,10 +27,11 @@
- * for a copy of the LGPLv3 License.
- *
- ************************************************************************/
--#include "helperdecl.hxx"
-+#include <vbahelper/helperdecl.hxx>
- #include "vbawindow.hxx"
- #include "vbaworksheets.hxx"
- #include "vbaworksheet.hxx"
-+#include "vbaglobals.hxx"
- #include "vbapane.hxx"
- #include <com/sun/star/sheet/XSpreadsheetDocument.hpp>
- #include <com/sun/star/sheet/XSpreadsheet.hpp>
-@@ -118,7 +119,7 @@ public:
- ScDocShell* pDocShell = (ScDocShell*)pModel->GetEmbeddedObject();
- if ( !pDocShell )
- throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "Cannot obtain docshell" ) ), uno::Reference< uno::XInterface >() );
-- ScTabViewShell* pViewShell = getBestViewShell( m_xModel );
-+ ScTabViewShell* pViewShell = excel::getBestViewShell( m_xModel );
- if ( !pViewShell )
- throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "Cannot obtain view shell" ) ), uno::Reference< uno::XInterface >() );
-
-@@ -202,14 +203,13 @@ public:
-
- };
-
--ScVbaWindow::ScVbaWindow( const uno::Reference< XHelperInterface >& xParent, const uno::Reference< uno::XComponentContext >& xContext, const uno::Reference< frame::XModel >& xModel ) : WindowImpl_BASE( xParent, xContext ), m_xModel( xModel )
-+ScVbaWindow::ScVbaWindow( const uno::Reference< XHelperInterface >& xParent, const uno::Reference< uno::XComponentContext >& xContext, const uno::Reference< frame::XModel >& xModel ) : WindowImpl_BASE( xParent, xContext, xModel )
- {
- init();
- }
-
- ScVbaWindow::ScVbaWindow( uno::Sequence< uno::Any > const & args, uno::Reference< uno::XComponentContext > const & xContext )
-- : WindowImpl_BASE( getXSomethingFromArgs< XHelperInterface >( args, 0 ), xContext ),
-- m_xModel( getXSomethingFromArgs< frame::XModel >( args, 1 ) )
-+ : WindowImpl_BASE( args, xContext )
- {
- init();
- }
-@@ -306,8 +306,7 @@ ScVbaWindow::getCaption() throw (uno::Ru
- if ( ( nCrudLen + nCrudIndex ) == sTitle.getLength() )
- {
- sTitle = sTitle.copy( 0, nCrudIndex );
-- uno::Reference< ov::XGlobals > xTemp( ScVbaGlobals::getGlobalsImpl( mxContext )); // temporary needed for g++ 3.3.5
-- ScVbaWorkbook workbook( uno::Reference< XHelperInterface >( xTemp->getApplication(), uno::UNO_QUERY_THROW ), mxContext, m_xModel );
-+ ScVbaWorkbook workbook( uno::Reference< XHelperInterface >( Application(), uno::UNO_QUERY_THROW ), mxContext, m_xModel );
- rtl::OUString sName = workbook.getName();
- // rather bizare hack to make sure the name behavior
- // is like XL
-@@ -343,7 +342,7 @@ uno::Any SAL_CALL
- ScVbaWindow::getScrollRow() throw (uno::RuntimeException)
- {
- sal_Int32 nValue = 0;
-- ScTabViewShell* pViewShell = getBestViewShell( m_xModel );
-+ ScTabViewShell* pViewShell = excel::getBestViewShell( m_xModel );
- if ( pViewShell )
- {
- ScSplitPos eWhich = pViewShell->GetViewData()->GetActivePart();
-@@ -356,7 +355,7 @@ ScVbaWindow::getScrollRow() throw (uno::
- void SAL_CALL
- ScVbaWindow::setScrollRow( const uno::Any& _scrollrow ) throw (uno::RuntimeException)
- {
-- ScTabViewShell* pViewShell = getBestViewShell( m_xModel );
-+ ScTabViewShell* pViewShell = excel::getBestViewShell( m_xModel );
- if ( pViewShell )
- {
- sal_Int32 scrollRow = 0;
-@@ -371,7 +370,7 @@ uno::Any SAL_CALL
- ScVbaWindow::getScrollColumn() throw (uno::RuntimeException)
- {
- sal_Int32 nValue = 0;
-- ScTabViewShell* pViewShell = getBestViewShell( m_xModel );
-+ ScTabViewShell* pViewShell = excel::getBestViewShell( m_xModel );
- if ( pViewShell )
- {
- ScSplitPos eWhich = pViewShell->GetViewData()->GetActivePart();
-@@ -384,7 +383,7 @@ ScVbaWindow::getScrollColumn() throw (un
- void SAL_CALL
- ScVbaWindow::setScrollColumn( const uno::Any& _scrollcolumn ) throw (uno::RuntimeException)
- {
-- ScTabViewShell* pViewShell = getBestViewShell( m_xModel );
-+ ScTabViewShell* pViewShell = excel::getBestViewShell( m_xModel );
- if ( pViewShell )
- {
- sal_Int32 scrollColumn = 0;
-@@ -399,7 +398,7 @@ uno::Any SAL_CALL
- ScVbaWindow::getWindowState() throw (uno::RuntimeException)
- {
- sal_Int32 nwindowState = xlNormal;
-- ScTabViewShell* pViewShell = getBestViewShell( m_xModel );
-+ ScTabViewShell* pViewShell = excel::getBestViewShell( m_xModel );
- SfxViewFrame* pViewFrame = pViewShell -> GetViewFrame();
- SfxTopViewFrame *pTop= PTR_CAST( SfxTopViewFrame, pViewFrame -> GetTopViewFrame() );
- if ( pTop )
-@@ -421,7 +420,7 @@ ScVbaWindow::setWindowState( const uno::
- {
- sal_Int32 nwindowState = xlMaximized;
- _windowstate >>= nwindowState;
-- ScTabViewShell* pViewShell = getBestViewShell( m_xModel );
-+ ScTabViewShell* pViewShell = excel::getBestViewShell( m_xModel );
- SfxViewFrame* pViewFrame = pViewShell -> GetViewFrame();
- SfxTopViewFrame *pTop= PTR_CAST( SfxTopViewFrame, pViewFrame -> GetTopViewFrame() );
- if ( pTop )
-@@ -444,8 +443,7 @@ ScVbaWindow::setWindowState( const uno::
- void
- ScVbaWindow::Activate() throw (css::uno::RuntimeException)
- {
-- uno::Reference< ov::XGlobals > xTemp( ScVbaGlobals::getGlobalsImpl( mxContext )); // temporary needed for g++ 3.3.5
-- ScVbaWorkbook workbook( uno::Reference< XHelperInterface >( xTemp->getApplication(), uno::UNO_QUERY_THROW ), mxContext, m_xModel );
-+ ScVbaWorkbook workbook( uno::Reference< XHelperInterface >( Application(), uno::UNO_QUERY_THROW ), mxContext, m_xModel );
-
- workbook.Activate();
- }
-@@ -453,8 +451,7 @@ ScVbaWindow::Activate() throw (css::uno:
- void
- ScVbaWindow::Close( const uno::Any& SaveChanges, const uno::Any& FileName, const uno::Any& RouteWorkBook ) throw (uno::RuntimeException)
- {
-- uno::Reference< ov::XGlobals > xTemp( ScVbaGlobals::getGlobalsImpl( mxContext )); // temporary needed for g++ 3.3.5
-- ScVbaWorkbook workbook( uno::Reference< XHelperInterface >( xTemp->getApplication(), uno::UNO_QUERY_THROW ), mxContext, m_xModel );
-+ ScVbaWorkbook workbook( uno::Reference< XHelperInterface >( Application(), uno::UNO_QUERY_THROW ), mxContext, m_xModel );
- workbook.Close(SaveChanges, FileName, RouteWorkBook );
- }
-
-@@ -467,13 +464,15 @@ ScVbaWindow::ActivePane() throw (script:
- uno::Reference< excel::XRange > SAL_CALL
- ScVbaWindow::ActiveCell( ) throw (script::BasicErrorException, uno::RuntimeException)
- {
-- return ScVbaGlobals::getGlobalsImpl( mxContext )->getApplication()->getActiveCell();
-+ uno::Reference< excel::XApplication > xApplication( Application(), uno::UNO_QUERY_THROW );
-+ return xApplication->getActiveCell();
- }
-
- uno::Any SAL_CALL
- ScVbaWindow::Selection( ) throw (script::BasicErrorException, uno::RuntimeException)
- {
-- return ScVbaGlobals::getGlobalsImpl( mxContext )->getApplication()->getSelection();
-+ uno::Reference< excel::XApplication > xApplication( Application(), uno::UNO_QUERY_THROW );
-+ return xApplication->getSelection();
- }
-
- ::sal_Bool SAL_CALL
-@@ -759,7 +758,8 @@ ScVbaWindow::setZoom( const uno::Any& _z
- uno::Reference< excel::XWorksheet > SAL_CALL
- ScVbaWindow::ActiveSheet( ) throw (script::BasicErrorException, uno::RuntimeException)
- {
-- return ScVbaGlobals::getGlobalsImpl(mxContext)->getApplication()->getActiveSheet();
-+ uno::Reference< excel::XApplication > xApplication( Application(), uno::UNO_QUERY_THROW );
-+ return xApplication->getActiveSheet();
- }
-
- uno::Any SAL_CALL
-@@ -787,121 +787,9 @@ ScVbaWindow::setView( const uno::Any& _v
- default:
- DebugHelper::exception(SbERR_BAD_PARAMETER, rtl::OUString() );
- }
-- dispatchExecute( m_xModel, nSlot );
--}
--
--sal_Bool SAL_CALL
--ScVbaWindow::getVisible() throw (uno::RuntimeException)
--{
-- sal_Bool bVisible = sal_True;
-- uno::Reference< frame::XController > xController( m_xModel->getCurrentController(), uno::UNO_QUERY_THROW );
-- uno::Reference< css::awt::XWindow > xWindow (xController->getFrame()->getContainerWindow(), uno::UNO_QUERY_THROW );
-- uno::Reference< css::awt::XWindow2 > xWindow2 (xWindow, uno::UNO_QUERY_THROW );
-- if( xWindow2.is() )
-- {
-- bVisible = xWindow2->isVisible();
-- }
-- return bVisible;
--}
--
--void SAL_CALL
--ScVbaWindow::setVisible(sal_Bool _visible) throw (uno::RuntimeException)
--{
-- uno::Reference< frame::XController > xController( m_xModel->getCurrentController(), uno::UNO_QUERY_THROW );
-- uno::Reference< css::awt::XWindow > xWindow (xController->getFrame()->getContainerWindow(), uno::UNO_QUERY_THROW );
-- if( xWindow.is() )
-- {
-- xWindow->setVisible( _visible );
-- }
--}
--
--css::awt::Rectangle getPosSize( const uno::Reference< frame::XModel >& xModel )
--{
-- css::awt::Rectangle aRect;
-- uno::Reference< frame::XController > xController( xModel->getCurrentController(), uno::UNO_QUERY_THROW );
-- uno::Reference< css::awt::XWindow > xWindow (xController->getFrame()->getContainerWindow(), uno::UNO_QUERY_THROW );
-- if( xWindow.is() )
-- {
-- aRect = xWindow->getPosSize();
-- }
-- return aRect;
--}
--
--void setPosSize( const uno::Reference< frame::XModel >& xModel, sal_Int32 nValue, USHORT nFlag )
--{
-- uno::Reference< frame::XController > xController( xModel->getCurrentController(), uno::UNO_QUERY_THROW );
-- uno::Reference< css::awt::XWindow > xWindow (xController->getFrame()->getContainerWindow(), uno::UNO_QUERY_THROW );
-- if( xWindow.is() )
-- {
-- css::awt::Rectangle aRect = xWindow->getPosSize();
-- switch( nFlag )
-- {
-- case css::awt::PosSize::X:
-- xWindow->setPosSize( nValue, aRect.Y, 0, 0, css::awt::PosSize::X );
-- break;
-- case css::awt::PosSize::Y:
-- xWindow->setPosSize( aRect.X, nValue, 0, 0, css::awt::PosSize::Y );
-- break;
-- case css::awt::PosSize::WIDTH:
-- xWindow->setPosSize( 0, 0, nValue, aRect.Height, css::awt::PosSize::WIDTH );
-- break;
-- case css::awt::PosSize::HEIGHT:
-- xWindow->setPosSize( 0, 0, aRect.Width, nValue, css::awt::PosSize::HEIGHT );
-- break;
-- default:
-- break;
-- }
-- }
--}
--
--sal_Int32 SAL_CALL
--ScVbaWindow::getHeight() throw (uno::RuntimeException)
--{
-- css::awt::Rectangle aRect = getPosSize(m_xModel);
-- return aRect.Height;
--}
--
--void SAL_CALL
--ScVbaWindow::setHeight( sal_Int32 _height ) throw (uno::RuntimeException)
--{
-- setPosSize(m_xModel, _height, css::awt::PosSize::HEIGHT);
--}
--
--sal_Int32 SAL_CALL
--ScVbaWindow::getLeft() throw (uno::RuntimeException)
--{
-- css::awt::Rectangle aRect = getPosSize(m_xModel);
-- return aRect.X;
--}
--
--void SAL_CALL
--ScVbaWindow::setLeft( sal_Int32 _left ) throw (uno::RuntimeException)
--{
-- setPosSize(m_xModel, _left, css::awt::PosSize::X);
--}
--sal_Int32 SAL_CALL
--ScVbaWindow::getTop() throw (uno::RuntimeException)
--{
-- css::awt::Rectangle aRect = getPosSize(m_xModel);
-- return aRect.Y;
--}
--
--void SAL_CALL
--ScVbaWindow::setTop( sal_Int32 _top ) throw (uno::RuntimeException)
--{
-- setPosSize(m_xModel, _top, css::awt::PosSize::Y);
--}
--sal_Int32 SAL_CALL
--ScVbaWindow::getWidth() throw (uno::RuntimeException)
--{
-- css::awt::Rectangle aRect = getPosSize(m_xModel);
-- return aRect.Width;
--}
--
--void SAL_CALL
--ScVbaWindow::setWidth( sal_Int32 _width ) throw (uno::RuntimeException)
--{
-- setPosSize(m_xModel, _width, css::awt::PosSize::WIDTH);
-+ ScTabViewShell* pViewShell = excel::getBestViewShell( m_xModel );
-+ if ( pViewShell )
-+ dispatchExecute( pViewShell, nSlot );
- }
-
- sal_Int32 SAL_CALL
-@@ -924,14 +812,14 @@ void SAL_CALL
- ScVbaWindow::PrintOut( const css::uno::Any& From, const css::uno::Any&To, const css::uno::Any& Copies, const css::uno::Any& Preview, const css::uno::Any& ActivePrinter, const css::uno::Any& PrintToFile, const css::uno::Any& Collate, const css::uno::Any& PrToFileName ) throw (css::script::BasicErrorException, css::uno::RuntimeException)
- {
- // need test, print current active sheet
-- PrintOutHelper( From, To, Copies, Preview, ActivePrinter, PrintToFile, Collate, PrToFileName, m_xModel, sal_True );
-+ PrintOutHelper( excel::getBestViewShell( m_xModel ), From, To, Copies, Preview, ActivePrinter, PrintToFile, Collate, PrToFileName, sal_True );
- }
-
- void SAL_CALL
- ScVbaWindow::PrintPreview( const css::uno::Any& EnableChanges ) throw (css::script::BasicErrorException, css::uno::RuntimeException)
- {
- // need test, print preview current active sheet
-- PrintPreviewHelper( EnableChanges, m_xModel );
-+ PrintPreviewHelper( EnableChanges, excel::getBestViewShell( m_xModel ) );
- }
-
- rtl::OUString&
---- sc/source/ui/vba/vbawindow.hxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbawindow.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -39,15 +39,16 @@
- #include <ooo/vba/excel/XPane.hpp>
- #include <com/sun/star/awt/XDevice.hpp>
-
--#include "vbahelperinterface.hxx"
-+#include <vbahelper/vbahelperinterface.hxx>
-+#include <vbahelper/vbawindowbase.hxx>
- #include "vbaworkbook.hxx"
-
--typedef InheritedHelperInterfaceImpl1<ov::excel::XWindow > WindowImpl_BASE;
-+//typedef InheritedHelperInterfaceImpl1<ov::excel::XWindow > WindowImpl_BASE;
-+typedef cppu::ImplInheritanceHelper1< VbaWindowBase, ov::excel::XWindow > WindowImpl_BASE;
-
- class ScVbaWindow : public WindowImpl_BASE
- {
- private:
-- css::uno::Reference< css::frame::XModel > m_xModel;
- css::uno::Reference< css::sheet::XViewPane > m_xViewPane;
- css::uno::Reference< css::sheet::XViewFreezable > m_xViewFreezable;
- css::uno::Reference< css::sheet::XViewSplitable > m_xViewSplitable;
-@@ -82,10 +83,6 @@ public:
- virtual void SAL_CALL setDisplayWorkbookTabs( ::sal_Bool _bDisplayWorkbookTabs ) throw (css::uno::RuntimeException);
- virtual ::sal_Bool SAL_CALL getFreezePanes() throw (css::uno::RuntimeException);
- virtual void SAL_CALL setFreezePanes( ::sal_Bool _bFreezePanes ) throw (css::uno::RuntimeException);
-- virtual sal_Int32 SAL_CALL getHeight() throw (css::uno::RuntimeException) ;
-- virtual void SAL_CALL setHeight( sal_Int32 _height ) throw (css::uno::RuntimeException) ;
-- virtual sal_Int32 SAL_CALL getLeft() throw (css::uno::RuntimeException) ;
-- virtual void SAL_CALL setLeft( sal_Int32 _left ) throw (css::uno::RuntimeException) ;
- virtual ::sal_Bool SAL_CALL getSplit() throw (css::uno::RuntimeException);
- virtual void SAL_CALL setSplit( ::sal_Bool _bSplit ) throw (css::uno::RuntimeException);
- virtual sal_Int32 SAL_CALL getSplitColumn() throw (css::uno::RuntimeException) ;
-@@ -100,14 +97,8 @@ public:
- virtual void SAL_CALL setScrollRow( const css::uno::Any& _scrollrow ) throw (css::uno::RuntimeException) ;
- virtual css::uno::Any SAL_CALL getScrollColumn() throw (css::uno::RuntimeException) ;
- virtual void SAL_CALL setScrollColumn( const css::uno::Any& _scrollcolumn ) throw (css::uno::RuntimeException) ;
-- virtual sal_Int32 SAL_CALL getTop() throw (css::uno::RuntimeException) ;
-- virtual void SAL_CALL setTop( sal_Int32 _top ) throw (css::uno::RuntimeException) ;
- virtual css::uno::Any SAL_CALL getView() throw (css::uno::RuntimeException);
- virtual void SAL_CALL setView( const css::uno::Any& _view ) throw (css::uno::RuntimeException);
-- virtual sal_Bool SAL_CALL getVisible() throw (css::uno::RuntimeException);
-- virtual void SAL_CALL setVisible( sal_Bool _visible ) throw (css::uno::RuntimeException);
-- virtual sal_Int32 SAL_CALL getWidth() throw (css::uno::RuntimeException) ;
-- virtual void SAL_CALL setWidth( sal_Int32 _width ) throw (css::uno::RuntimeException) ;
- virtual css::uno::Any SAL_CALL getWindowState() throw (css::uno::RuntimeException);
- virtual void SAL_CALL setWindowState( const css::uno::Any& _windowstate ) throw (css::uno::RuntimeException);
- virtual css::uno::Any SAL_CALL getZoom() throw (css::uno::RuntimeException);
---- sc/source/ui/vba/vbawindows.cxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbawindows.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -37,6 +37,7 @@
-
- #include <tools/urlobj.hxx>
- #include "vbawindow.hxx"
-+#include "vbaglobals.hxx"
- //#include "vbaworkbook.hxx"
-
- using namespace ::com::sun::star;
-@@ -47,15 +48,15 @@ sal_Int32, ::rtl::OUStringHash,
- ::std::equal_to< ::rtl::OUString > > NameIndexHash;
-
-
--uno::Reference< XHelperInterface > lcl_createWorkbookHIParent( const uno::Reference< frame::XModel >& xModel, const uno::Reference< uno::XComponentContext >& xContext )
-+uno::Reference< XHelperInterface > lcl_createWorkbookHIParent( const uno::Reference< frame::XModel >& xModel, const uno::Reference< uno::XComponentContext >& xContext, const uno::Any& aApplication )
- {
-- return new ScVbaWorkbook( uno::Reference< XHelperInterface >( ScVbaGlobals::getGlobalsImpl( xContext )->getApplication(), uno::UNO_QUERY_THROW ), xContext, xModel );
-+ return new ScVbaWorkbook( uno::Reference< XHelperInterface >( aApplication, uno::UNO_QUERY_THROW ), xContext, xModel );
- }
-
--uno::Any ComponentToWindow( const uno::Any& aSource, uno::Reference< uno::XComponentContext > & xContext )
-+uno::Any ComponentToWindow( const uno::Any& aSource, uno::Reference< uno::XComponentContext > & xContext, const uno::Any& aApplication )
- {
- uno::Reference< frame::XModel > xModel( aSource, uno::UNO_QUERY_THROW );
-- uno::Reference< excel::XWindow > xWin( new ScVbaWindow( lcl_createWorkbookHIParent( xModel, xContext ), xContext,xModel ) );
-+ uno::Reference< excel::XWindow > xWin( new ScVbaWindow( lcl_createWorkbookHIParent( xModel, xContext, aApplication ), xContext,xModel ) );
- return uno::makeAny( xWin );
- }
-
-@@ -108,12 +109,13 @@ public:
-
- class WindowEnumImpl : public WindowComponentEnumImpl
- {
-+ uno::Any m_aApplication;
- public:
-- WindowEnumImpl(const uno::Reference< uno::XComponentContext >& xContext, const Components& components ):WindowComponentEnumImpl( xContext, components ) {}
-- WindowEnumImpl( const uno::Reference< uno::XComponentContext >& xContext ): WindowComponentEnumImpl( xContext ) {}
-+ WindowEnumImpl(const uno::Reference< uno::XComponentContext >& xContext, const Components& components, const uno::Any& aApplication ):WindowComponentEnumImpl( xContext, components ), m_aApplication( aApplication ){}
-+ WindowEnumImpl( const uno::Reference< uno::XComponentContext >& xContext, const uno::Any& aApplication ): WindowComponentEnumImpl( xContext ), m_aApplication( aApplication ) {}
- virtual uno::Any SAL_CALL nextElement( ) throw (container::NoSuchElementException, lang::WrappedTargetException, uno::RuntimeException)
- {
-- return ComponentToWindow( WindowComponentEnumImpl::nextElement(), m_xContext );
-+ return ComponentToWindow( WindowComponentEnumImpl::nextElement(), m_xContext, m_aApplication );
- }
- };
-
-@@ -212,16 +214,19 @@ ScVbaWindows::ScVbaWindows( const uno::R
- {
- }
-
-+ScVbaWindows::ScVbaWindows( const uno::Reference< ov::XHelperInterface >& xParent, const css::uno::Reference< css::uno::XComponentContext >& xContext ) : ScVbaWindows_BASE( xParent, xContext, uno::Reference< container::XIndexAccess > ( new WindowsAccessImpl( xContext ) ) )
-+{
-+}
- uno::Reference< container::XEnumeration >
- ScVbaWindows::createEnumeration() throw (uno::RuntimeException)
- {
-- return new WindowEnumImpl( mxContext );
-+ return new WindowEnumImpl( mxContext, Application() );
- }
-
- uno::Any
- ScVbaWindows::createCollectionObject( const css::uno::Any& aSource )
- {
-- return ComponentToWindow( aSource, mxContext );
-+ return ComponentToWindow( aSource, mxContext, Application() );
- }
-
- uno::Type
-@@ -230,12 +235,6 @@ ScVbaWindows::getElementType() throw (un
- return excel::XWindows::static_type(0);
- }
-
--uno::Reference< XCollection >
--ScVbaWindows::Windows( const css::uno::Reference< css::uno::XComponentContext >& xContext )
--{
-- uno::Reference< container::XIndexAccess > xIndex( new WindowsAccessImpl( xContext ) );
-- return new ScVbaWindows( uno::Reference< XHelperInterface >( ScVbaGlobals::getGlobalsImpl( xContext )->getApplication(), uno::UNO_QUERY_THROW ), xContext , xIndex );
--}
-
- void SAL_CALL
- ScVbaWindows::Arrange( ::sal_Int32 /*ArrangeStyle*/, const uno::Any& /*ActiveWorkbook*/, const uno::Any& /*SyncHorizontal*/, const uno::Any& /*SyncVertical*/ ) throw (uno::RuntimeException)
---- sc/source/ui/vba/vbawindows.hxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbawindows.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -35,8 +35,8 @@
-
- #include <com/sun/star/uno/XComponentContext.hpp>
-
--#include "vbahelper.hxx"
--#include "vbacollectionimpl.hxx"
-+#include "excelvbahelper.hxx"
-+#include <vbahelper/vbacollectionimpl.hxx>
-
-
- typedef CollTestImplHelper< ov::excel::XWindows > ScVbaWindows_BASE;
-@@ -45,6 +45,7 @@ class ScVbaWindows : public ScVbaWindows
- {
- public:
- ScVbaWindows( const css::uno::Reference< ov::XHelperInterface >& xParent, const css::uno::Reference< css::uno::XComponentContext > & xContext, const css::uno::Reference< css::container::XIndexAccess >& xIndexAccess );
-+ ScVbaWindows( const css::uno::Reference< ov::XHelperInterface >& xParent, const css::uno::Reference< css::uno::XComponentContext > & xContext );
- virtual ~ScVbaWindows() {}
-
- // XEnumerationAccess
-@@ -57,8 +58,6 @@ public:
- // ScVbaCollectionBaseImpl
- virtual css::uno::Any createCollectionObject( const css::uno::Any& aSource );
-
-- static css::uno::Reference< ov::XCollection > Windows( const css::uno::Reference< css::uno::XComponentContext >& xContext );
--
- // XHelperInterface
- virtual rtl::OUString& getServiceImplName();
- virtual css::uno::Sequence<rtl::OUString> getServiceNames();
---- sc/source/ui/vba/vbaworkbook.cxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbaworkbook.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -27,7 +27,7 @@
- * for a copy of the LGPLv3 License.
- *
- ************************************************************************/
--#include "helperdecl.hxx"
-+#include <vbahelper/helperdecl.hxx>
- #include <tools/urlobj.hxx>
- #include <comphelper/unwrapargs.hxx>
-
-@@ -46,7 +46,7 @@
- #include "vbaworkbook.hxx"
- #include "vbawindows.hxx"
- #include "vbastyles.hxx"
--#include "vbahelper.hxx"
-+#include "excelvbahelper.hxx"
- #include "vbapalette.hxx"
- #include <osl/file.hxx>
- #include <stdio.h>
-@@ -192,7 +192,7 @@ ScVbaWorkbook::init()
- if ( !ColorData.getLength() )
- ResetColors();
- }
--ScVbaWorkbook::ScVbaWorkbook( const css::uno::Reference< ov::XHelperInterface >& xParent, const css::uno::Reference< css::uno::XComponentContext >& xContext) :ScVbaWorkbook_BASE( xParent, xContext ), mxModel(NULL)
-+ScVbaWorkbook::ScVbaWorkbook( const css::uno::Reference< ov::XHelperInterface >& xParent, const css::uno::Reference< css::uno::XComponentContext >& xContext) :ScVbaWorkbook_BASE( xParent, xContext )
- {
- //#FIXME this persists the color data per office instance and
- // not per workbook instance, need to hook the data into XModel
-@@ -203,54 +203,18 @@ ScVbaWorkbook::ScVbaWorkbook( const css
- init();
- }
-
--ScVbaWorkbook::ScVbaWorkbook( const css::uno::Reference< ov::XHelperInterface >& xParent, const css::uno::Reference< css::uno::XComponentContext >& xContext, css::uno::Reference< css::frame::XModel > xModel ) : ScVbaWorkbook_BASE( xParent, xContext ), mxModel( xModel )
-+ScVbaWorkbook::ScVbaWorkbook( const css::uno::Reference< ov::XHelperInterface >& xParent, const css::uno::Reference< css::uno::XComponentContext >& xContext, css::uno::Reference< css::frame::XModel > xModel ) : ScVbaWorkbook_BASE( xParent, xContext, xModel )
- {
- init();
- }
-
- ScVbaWorkbook::ScVbaWorkbook( uno::Sequence< uno::Any> const & args,
-- uno::Reference< uno::XComponentContext> const & xContext ) : ScVbaWorkbook_BASE( getXSomethingFromArgs< XHelperInterface >( args, 0 ), xContext ), mxModel( getXSomethingFromArgs< frame::XModel >( args, 1 ) )
-+ uno::Reference< uno::XComponentContext> const & xContext ) : ScVbaWorkbook_BASE( args, xContext )
-
- {
- init();
- }
-
--::rtl::OUString
--ScVbaWorkbook::getName() throw (uno::RuntimeException)
--{
-- rtl::OUString sName = getModel()->getURL();
-- if ( sName.getLength() )
-- {
--
-- INetURLObject aURL( getModel()->getURL() );
-- ::osl::File::getSystemPathFromFileURL( aURL.GetLastName(), sName );
-- }
-- else
-- {
-- const static rtl::OUString sTitle( RTL_CONSTASCII_USTRINGPARAM("Title" ) );
-- // process "UntitledX - $(PRODUCTNAME)"
-- uno::Reference< frame::XFrame > xFrame( getModel()->getCurrentController()->getFrame(), uno::UNO_QUERY_THROW );
-- uno::Reference< beans::XPropertySet > xProps( xFrame, uno::UNO_QUERY_THROW );
-- xProps->getPropertyValue(sTitle ) >>= sName;
-- sal_Int32 pos = 0;
-- sName = sName.getToken(0,' ',pos);
-- }
-- return sName;
--}
--::rtl::OUString
--ScVbaWorkbook::getPath() throw (uno::RuntimeException)
--{
-- INetURLObject aURL( getModel()->getURL() );
-- aURL.CutLastName();
-- return aURL.GetURLPath();
--}
--
--::rtl::OUString
--ScVbaWorkbook::getFullName() throw (uno::RuntimeException)
--{
-- INetURLObject aURL( getModel()->getURL() );
-- return aURL.GetURLPath();
--}
- uno::Reference< excel::XWorksheet >
- ScVbaWorkbook::getActiveSheet() throw (uno::RuntimeException)
- {
-@@ -281,91 +245,19 @@ ScVbaWorkbook::Worksheets( const uno::An
- uno::Any SAL_CALL
- ScVbaWorkbook::Windows( const uno::Any& aIndex ) throw (uno::RuntimeException)
- {
-- uno::Reference< XCollection > xWindows = ScVbaWindows::Windows( mxContext );
-+
-+ uno::Reference< excel::XWindows > xWindows( new ScVbaWindows( getParent(), mxContext ) );
- if ( aIndex.getValueTypeClass() == uno::TypeClass_VOID )
- return uno::Any( xWindows );
- return uno::Any( xWindows->Item( aIndex, uno::Any() ) );
- }
--void
--ScVbaWorkbook::Close( const uno::Any &rSaveArg, const uno::Any &rFileArg,
-- const uno::Any &rRouteArg ) throw (uno::RuntimeException)
--{
-- sal_Bool bSaveChanges = sal_False;
-- rtl::OUString aFileName;
-- sal_Bool bRouteWorkbook = sal_True;
--
-- rSaveArg >>= bSaveChanges;
-- sal_Bool bFileName = ( rFileArg >>= aFileName );
-- rRouteArg >>= bRouteWorkbook;
-- uno::Reference< frame::XStorable > xStorable( getModel(), uno::UNO_QUERY_THROW );
-- uno::Reference< util::XModifiable > xModifiable( getModel(), uno::UNO_QUERY_THROW );
--
-- if( bSaveChanges )
-- {
-- if( xStorable->isReadonly() )
-- {
-- throw uno::RuntimeException(::rtl::OUString(
-- RTL_CONSTASCII_USTRINGPARAM( "Unable to save to a read only file ") ),
-- uno::Reference< XInterface >() );
-- }
-- if( bFileName )
-- xStorable->storeAsURL( aFileName, uno::Sequence< beans::PropertyValue >(0) );
-- else
-- xStorable->store();
-- }
-- else
-- xModifiable->setModified( false );
--
-- uno::Reference< util::XCloseable > xCloseable( getModel(), uno::UNO_QUERY );
-
-- if( xCloseable.is() )
-- // use close(boolean DeliverOwnership)
--
-- // The boolean parameter DeliverOwnership tells objects vetoing the close process that they may
-- // assume ownership if they object the closure by throwing a CloseVetoException
-- // Here we give up ownership. To be on the safe side, catch possible veto exception anyway.
-- xCloseable->close(sal_True);
-- // If close is not supported by this model - try to dispose it.
-- // But if the model disagree with a reset request for the modify state
-- // we shouldn't do so. Otherwhise some strange things can happen.
-- else
-- {
-- uno::Reference< lang::XComponent > xDisposable ( getCurrentDocument(), uno::UNO_QUERY );
-- if ( xDisposable.is() )
-- xDisposable->dispose();
-- }
--}
--
--void
--ScVbaWorkbook::Protect( const uno::Any &aPassword ) throw (uno::RuntimeException)
-+void SAL_CALL
-+ScVbaWorkbook::Activate() throw (uno::RuntimeException)
- {
-- rtl::OUString rPassword;
-- uno::Reference< util::XProtectable > xProt( getModel(), uno::UNO_QUERY_THROW );
-- SC_VBA_FIXME(("Workbook::Protect stub"));
-- if( aPassword >>= rPassword )
-- xProt->protect( rPassword );
-- else
-- xProt->protect( rtl::OUString() );
-+ VbaDocumentBase::Activate();
- }
-
--void
--ScVbaWorkbook::Unprotect( const uno::Any &aPassword ) throw (uno::RuntimeException)
--{
-- rtl::OUString rPassword;
-- uno::Reference< util::XProtectable > xProt( getModel(), uno::UNO_QUERY_THROW );
-- if( !getProtectStructure() )
-- throw uno::RuntimeException(::rtl::OUString(
-- RTL_CONSTASCII_USTRINGPARAM( "File is already unprotected" ) ),
-- uno::Reference< XInterface >() );
-- else
-- {
-- if( aPassword >>= rPassword )
-- xProt->unprotect( rPassword );
-- else
-- xProt->unprotect( rtl::OUString() );
-- }
--}
--
- ::sal_Bool
- ScVbaWorkbook::getProtectStructure() throw (uno::RuntimeException)
- {
-@@ -373,28 +265,6 @@ ScVbaWorkbook::getProtectStructure() thr
- return xProt->isProtected();
- }
-
--void
--ScVbaWorkbook::setSaved( sal_Bool bSave ) throw (uno::RuntimeException)
--{
-- uno::Reference< util::XModifiable > xModifiable( getModel(), uno::UNO_QUERY_THROW );
-- xModifiable->setModified( bSave );
--}
--
--sal_Bool
--ScVbaWorkbook::getSaved() throw (uno::RuntimeException)
--{
-- uno::Reference< util::XModifiable > xModifiable( getModel(), uno::UNO_QUERY_THROW );
-- return xModifiable->isModified();
--}
--
--void
--ScVbaWorkbook::Save() throw (uno::RuntimeException)
--{
-- rtl::OUString url = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM(".uno:Save"));
-- uno::Reference< frame::XModel > xModel = getModel();
-- dispatchRequests(xModel,url);
--}
--
- void
- ScVbaWorkbook::SaveCopyAs( const rtl::OUString& sFileName ) throw ( uno::RuntimeException)
- {
-@@ -407,13 +277,6 @@ ScVbaWorkbook::SaveCopyAs( const rtl::OU
- xStor->storeToURL( aURL, storeProps );
- }
-
--void
--ScVbaWorkbook::Activate() throw (uno::RuntimeException)
--{
-- uno::Reference< frame::XFrame > xFrame( getModel()->getCurrentController()->getFrame(), uno::UNO_QUERY_THROW );
-- xFrame->activate();
--}
--
- css::uno::Any SAL_CALL
- ScVbaWorkbook::Styles( const::uno::Any& Item ) throw (uno::RuntimeException)
- {
-@@ -465,7 +328,7 @@ ScVbaWorkbook::getCodeName() throw (css:
- {
- #ifdef VBA_OOBUILD_HACK
- uno::Reference< frame::XModel > xModel( getModel(), uno::UNO_QUERY_THROW );
-- ScDocument* pDoc = getDocShell( xModel )->GetDocument();
-+ ScDocument* pDoc = excel::getDocShell( xModel )->GetDocument();
- ScExtDocOptions* pExtOptions = pDoc->GetExtDocOptions();
- ScExtDocSettings pExtSettings = pExtOptions->GetDocSettings();
- ::rtl::OUString sGlobCodeName = pExtSettings.maGlobCodeName;
-@@ -479,7 +342,7 @@ void SAL_CALL
- ScVbaWorkbook::setCodeName( const ::rtl::OUString& sGlobCodeName ) throw (css::uno::RuntimeException)
- {
- uno::Reference< frame::XModel > xModel( getModel(), uno::UNO_QUERY_THROW );
-- ScDocument* pDoc = getDocShell( xModel )->GetDocument();
-+ ScDocument* pDoc = excel::getDocShell( xModel )->GetDocument();
- ScExtDocOptions* pExtOptions = pDoc->GetExtDocOptions();
- ScExtDocSettings pExtSettings = pExtOptions->GetDocSettings();
- pExtSettings.maGlobCodeName = sGlobCodeName;
---- sc/source/ui/vba/vbaworkbook.hxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbaworkbook.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -32,21 +32,20 @@
-
- #include <com/sun/star/frame/XModel.hpp>
- #include <ooo/vba/excel/XWorkbook.hpp>
--#include "vbahelperinterface.hxx"
-+#include <vbahelper/vbahelperinterface.hxx>
-+#include <vbahelper/vbadocumentbase.hxx>
-
- class ScModelObj;
-
--typedef InheritedHelperInterfaceImpl1< ov::excel::XWorkbook > ScVbaWorkbook_BASE;
-+typedef cppu::ImplInheritanceHelper1< VbaDocumentBase, ov::excel::XWorkbook > ScVbaWorkbook_BASE;
-
- class ScVbaWorkbook : public ScVbaWorkbook_BASE
- {
-- css::uno::Reference< css::frame::XModel > mxModel;
- static css::uno::Sequence< sal_Int32 > ColorData;
- void initColorData( const css::uno::Sequence< sal_Int32 >& sColors );
- void init();
- protected:
-
-- virtual css::uno::Reference< css::frame::XModel > getModel() { return mxModel; }
- ScVbaWorkbook( const css::uno::Reference< ov::XHelperInterface >& xParent, const css::uno::Reference< css::uno::XComponentContext >& xContext);
- public:
- ScVbaWorkbook( const css::uno::Reference< ov::XHelperInterface >& xParent, const css::uno::Reference< css::uno::XComponentContext >& xContext,
-@@ -55,25 +54,14 @@ public:
- virtual ~ScVbaWorkbook() {}
-
- // Attributes
-- virtual ::rtl::OUString SAL_CALL getName() throw (css::uno::RuntimeException);
-- virtual ::rtl::OUString SAL_CALL getPath() throw (css::uno::RuntimeException);
-- virtual ::rtl::OUString SAL_CALL getFullName() throw (css::uno::RuntimeException);
- virtual ::sal_Bool SAL_CALL getProtectStructure() throw (css::uno::RuntimeException);
- virtual css::uno::Reference< ov::excel::XWorksheet > SAL_CALL getActiveSheet() throw (css::uno::RuntimeException);
-- virtual sal_Bool SAL_CALL getSaved() throw (css::uno::RuntimeException);
-- virtual void SAL_CALL setSaved( sal_Bool bSave ) throw (css::uno::RuntimeException);
-
- // Methods
- virtual css::uno::Any SAL_CALL Worksheets( const css::uno::Any& aIndex ) throw (css::uno::RuntimeException);
- virtual css::uno::Any SAL_CALL Sheets( const css::uno::Any& aIndex ) throw (css::uno::RuntimeException);
- virtual css::uno::Any SAL_CALL Windows( const css::uno::Any& aIndex ) throw (css::uno::RuntimeException);
-- virtual void SAL_CALL Close( const css::uno::Any &bSaveChanges,
-- const css::uno::Any &aFileName,
-- const css::uno::Any &bRouteWorkbook ) throw (css::uno::RuntimeException);
-- virtual void SAL_CALL Protect( const css::uno::Any & aPassword ) throw (css::uno::RuntimeException);
-- virtual void SAL_CALL Unprotect( const css::uno::Any &aPassword ) throw (css::uno::RuntimeException);
-- virtual void SAL_CALL Save() throw (css::uno::RuntimeException);
-- virtual void SAL_CALL Activate() throw (css::uno::RuntimeException);
-+ virtual void SAL_CALL Activate() throw (css::uno::RuntimeException);
- // Amelia Wang
- virtual css::uno::Any SAL_CALL Names( const css::uno::Any& aIndex ) throw (css::uno::RuntimeException);
-
---- sc/source/ui/vba/vbaworkbooks.cxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbaworkbooks.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -56,7 +56,7 @@
- #include "vbaglobals.hxx"
- #include "vbaworkbook.hxx"
- #include "vbaworkbooks.hxx"
--#include "vbahelper.hxx"
-+#include <vbahelper/vbahelper.hxx>
-
- #include <hash_map>
- #include <osl/file.hxx>
-@@ -74,14 +74,14 @@ typedef std::vector < uno::Reference< sh
- typedef ::cppu::WeakImplHelper1< container::XEnumeration > SpreadSheetDocEnumImpl_BASE;
-
- static uno::Any
--getWorkbook( uno::Reference< uno::XComponentContext >& xContext, const uno::Reference< sheet::XSpreadsheetDocument > &xDoc )
-+getWorkbook( uno::Reference< uno::XComponentContext >& xContext, const uno::Reference< sheet::XSpreadsheetDocument > &xDoc, const uno::Any& aApplication )
- {
- // FIXME: fine as long as ScVbaWorkbook is stateless ...
- uno::Reference< frame::XModel > xModel( xDoc, uno::UNO_QUERY );
- if( !xModel.is() )
- return uno::Any();
-
-- ScVbaWorkbook *pWb = new ScVbaWorkbook( uno::Reference< XHelperInterface >( ScVbaGlobals::getGlobalsImpl( xContext )->getApplication(), uno::UNO_QUERY_THROW ), xContext, xModel );
-+ ScVbaWorkbook *pWb = new ScVbaWorkbook( uno::Reference< XHelperInterface >( aApplication, uno::UNO_QUERY_THROW ), xContext, xModel );
- return uno::Any( uno::Reference< excel::XWorkbook > (pWb) );
- }
-
-@@ -134,13 +134,14 @@ public:
-
- class WorkBookEnumImpl : public EnumerationHelperImpl
- {
-+ uno::Any m_aApplication;
- public:
-- WorkBookEnumImpl( const uno::Reference< uno::XComponentContext >& xContext, const uno::Reference< container::XEnumeration >& xEnumeration ) throw ( uno::RuntimeException ) : EnumerationHelperImpl( xContext, xEnumeration ){}
-+ WorkBookEnumImpl( const uno::Reference< uno::XComponentContext >& xContext, const uno::Reference< container::XEnumeration >& xEnumeration, const uno::Any& aApplication ) throw ( uno::RuntimeException ) : EnumerationHelperImpl( xContext, xEnumeration ), m_aApplication( aApplication ) {}
-
- virtual uno::Any SAL_CALL nextElement( ) throw (container::NoSuchElementException, lang::WrappedTargetException, uno::RuntimeException)
- {
- uno::Reference< sheet::XSpreadsheetDocument > xDoc( m_xEnumeration->nextElement(), uno::UNO_QUERY_THROW );
-- return getWorkbook( m_xContext, xDoc );
-+ return getWorkbook( m_xContext, xDoc, m_aApplication );
- }
-
- };
-@@ -254,14 +255,14 @@ ScVbaWorkbooks::createEnumeration() thro
- // the state of this object ( although it should ) would be
- // safer to create an enumeration based on this objects state
- // rather than one effectively based of the desktop component
-- return new WorkBookEnumImpl( mxContext, uno::Reference< container::XEnumeration >( new SpreadSheetDocEnumImpl(mxContext) ) );
-+ return new WorkBookEnumImpl( mxContext, uno::Reference< container::XEnumeration >( new SpreadSheetDocEnumImpl(mxContext) ), Application() );
- }
-
- uno::Any
- ScVbaWorkbooks::createCollectionObject( const css::uno::Any& aSource )
- {
- uno::Reference< sheet::XSpreadsheetDocument > xDoc( aSource, uno::UNO_QUERY );
-- return getWorkbook( mxContext, xDoc );
-+ return getWorkbook( mxContext, xDoc, Application() );
- }
-
-
-@@ -282,7 +283,7 @@ ScVbaWorkbooks::Add() throw (uno::Runtim
- uno::Reference <sheet::XSpreadsheetDocument> xSpreadDoc( xComponent, uno::UNO_QUERY_THROW );
-
- if( xSpreadDoc.is() )
-- return getWorkbook( mxContext, xSpreadDoc );
-+ return getWorkbook( mxContext, xSpreadDoc, Application() );
- return uno::Any();
- }
-
-@@ -438,7 +439,7 @@ ScVbaWorkbooks::Open( const rtl::OUStrin
- frame::FrameSearchFlag::CREATE,
- sProps);
- uno::Reference <sheet::XSpreadsheetDocument> xSpreadDoc( xComponent, uno::UNO_QUERY_THROW );
-- uno::Any aRet = getWorkbook( mxContext, xSpreadDoc );
-+ uno::Any aRet = getWorkbook( mxContext, xSpreadDoc, Application() );
- uno::Reference< excel::XWorkbook > xWBook( aRet, uno::UNO_QUERY );
- if ( xWBook.is() )
- xWBook->Activate();
---- sc/source/ui/vba/vbaworkbooks.hxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbaworkbooks.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -31,11 +31,10 @@
- #define SC_VBA_WORKBOOKS_HXX
-
-
--#include "vbacollectionimpl.hxx"
--#include <ooo/vba/XGlobals.hpp>
-+#include <vbahelper/vbacollectionimpl.hxx>
- #include <ooo/vba/excel/XWorkbooks.hpp>
- #include <com/sun/star/container/XEnumerationAccess.hpp>
--#include "vbahelper.hxx"
-+#include "excelvbahelper.hxx"
-
-
- class ScModelObj;
-@@ -45,7 +44,6 @@ typedef CollTestImplHelper< ov::excel::X
- class ScVbaWorkbooks : public ScVbaWorkbooks_BASE
- {
- private:
-- css::uno::Reference< ov::XGlobals > getGlobals() throw (css::uno::RuntimeException);
- rtl::OUString getFileFilterType( const rtl::OUString& rString );
- bool isTextFile( const rtl::OUString& rString );
- bool isSpreadSheetFile( const rtl::OUString& rString );
---- sc/source/ui/vba/vbaworksheet.cxx.old 2009-04-06 16:42:00.000000000 +0000
-+++ sc/source/ui/vba/vbaworksheet.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -27,7 +27,7 @@
- * for a copy of the LGPLv3 License.
- *
- ************************************************************************/
--#include "helperdecl.hxx"
-+#include <vbahelper/helperdecl.hxx>
- #include <cppuhelper/queryinterface.hxx>
-
- #include <com/sun/star/beans/XPropertySet.hpp>
-@@ -59,6 +59,7 @@
- #include <com/sun/star/form/FormComponentType.hpp>
- #include <com/sun/star/form/XFormsSupplier.hpp>
- #include <ooo/vba/excel/XlEnableSelection.hpp>
-+#include <ooo/vba/XControlProvider.hpp>
-
- #include <comphelper/processfactory.hxx>
-
-@@ -83,7 +84,6 @@
- #include "vbaworksheet.hxx"
- #include "vbachartobjects.hxx"
- #include "vbapivottables.hxx"
--#include "vbacombobox.hxx"
- #include "vbaoleobject.hxx"
- #include "vbaoleobjects.hxx"
- #include "vbashapes.hxx"
-@@ -268,7 +268,7 @@ ScVbaWorksheet::getEnableSelection() thr
- if ( bSheetExists )
- {
- uno::Reference< frame::XModel > xModel( getModel(), uno::UNO_QUERY_THROW );
-- ScDocument* pDoc = getDocShell( xModel )->GetDocument();
-+ ScDocument* pDoc = excel::getDocShell( xModel )->GetDocument();
- ScTableProtection* pProtect = pDoc->GetTabProtection(nTab);
- sal_Bool bLockedCells = sal_False;
- sal_Bool bUnlockedCells = sal_False;
-@@ -308,7 +308,7 @@ ScVbaWorksheet::setEnableSelection( sal_
- if ( bSheetExists )
- {
- uno::Reference< frame::XModel > xModel( getModel(), uno::UNO_QUERY_THROW );
-- ScDocument* pDoc = getDocShell( xModel )->GetDocument();
-+ ScDocument* pDoc = excel::getDocShell( xModel )->GetDocument();
- ScTableProtection* pProtect = pDoc->GetTabProtection(nTab);
- // default is xlNoSelection
- sal_Bool bLockedCells = sal_False;
-@@ -431,11 +431,11 @@ ScVbaWorksheet::Move( const uno::Any& Be
- uno::Reference<excel::XRange> xRange = new ScVbaRange( this, mxContext, xRange1);
- if (xRange.is())
- xRange->Select();
-- implnCopy();
-+ excel::implnCopy();
- uno::Reference<frame::XModel> xModel = openNewDoc(aCurrSheetName);
- if (xModel.is())
- {
-- implnPaste();
-+ excel::implnPaste();
- Delete();
- }
- return ;
-@@ -469,11 +469,11 @@ ScVbaWorksheet::Copy( const uno::Any& Be
- uno::Reference<excel::XRange> xRange = new ScVbaRange( this, mxContext, xRange1);
- if (xRange.is())
- xRange->Select();
-- implnCopy();
-+ excel::implnCopy();
- uno::Reference<frame::XModel> xModel = openNewDoc(aCurrSheetName);
- if (xModel.is())
- {
-- implnPaste();
-+ excel::implnPaste();
- }
- return;
- }
-@@ -502,7 +502,7 @@ ScVbaWorksheet::Paste( const uno::Any& D
- uno::Reference<excel::XRange> xRange( Destination, uno::UNO_QUERY );
- if ( xRange.is() )
- xRange->Select();
-- implnPaste();
-+ excel::implnPaste();
- }
-
- void
-@@ -713,7 +713,7 @@ ScVbaWorksheet::ShowDataForm( ) throw (u
- {
- #ifdef VBA_OOBUILD_HACK
- uno::Reference< frame::XModel > xModel( getModel(), uno::UNO_QUERY_THROW );
-- ScTabViewShell* pTabViewShell = getBestViewShell( xModel );
-+ ScTabViewShell* pTabViewShell = excel::getBestViewShell( xModel );
-
- ScAbstractDialogFactory* pFact = ScAbstractDialogFactory::Create();
- DBG_ASSERT(pFact, "ScAbstractFactory create fail!");//CHINA001
-@@ -762,9 +762,11 @@ uno::Any SAL_CALL
- ScVbaWorksheet::getValue( const ::rtl::OUString& aPropertyName ) throw (beans::UnknownPropertyException, uno::RuntimeException)
- {
- uno::Reference< drawing::XControlShape > xControlShape( getControlShape( aPropertyName ), uno::UNO_QUERY_THROW );
-- ScVbaControlFactory controlFactory( mxContext, xControlShape, getModel() );
-- uno::Reference< msforms::XControl > xControl( controlFactory.createControl( getModel() ) );
-- return uno::makeAny( xControl );
-+
-+ uno::Reference<lang::XMultiComponentFactory > xServiceManager( mxContext->getServiceManager(), uno::UNO_QUERY_THROW );
-+ uno::Reference< XControlProvider > xControlProvider( xServiceManager->createInstanceWithContext( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "ooo.vba.ControlProvider" ) ), mxContext ), uno::UNO_QUERY_THROW );
-+ uno::Reference< msforms::XControl > xControl( xControlProvider->createControl( xControlShape, getModel() ) );
-+ return uno::makeAny( xControl );
- }
-
- ::sal_Bool SAL_CALL
-@@ -947,10 +949,9 @@ ScVbaWorksheet::PrintOut( const uno::Any
- bSelection = sal_True;
-
- uno::Reference< frame::XModel > xModel( getModel(), uno::UNO_QUERY_THROW );
-- PrintOutHelper( From, To, Copies, Preview, ActivePrinter, PrintToFile, Collate, PrToFileName, xModel, bSelection );
-+ PrintOutHelper( excel::getBestViewShell( xModel ), From, To, Copies, Preview, ActivePrinter, PrintToFile, Collate, PrToFileName, bSelection );
- }
-
--
- namespace worksheet
- {
- namespace sdecl = comphelper::service_decl;
---- sc/source/ui/vba/vbaworksheet.hxx.old 2009-04-06 16:42:00.000000000 +0000
-+++ sc/source/ui/vba/vbaworksheet.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -47,7 +47,8 @@
- #include <ooo/vba/excel/XChartObjects.hpp>
- #include <com/sun/star/container/XNamed.hpp>
-
--#include "vbahelperinterface.hxx"
-+#include <vbahelper/vbahelperinterface.hxx>
-+#include "address.hxx"
-
- typedef InheritedHelperInterfaceImpl1< ov::excel::XWorksheet > WorksheetImpl_BASE;
-
---- sc/source/ui/vba/vbaworksheets.cxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbaworksheets.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -217,8 +217,8 @@ ScVbaWorksheets::Add( const uno::Any& Be
- }
- if (!aStringSheet.getLength())
- {
-- aStringSheet = ScVbaGlobals::getGlobalsImpl(
-- mxContext )->getApplication()->getActiveWorkbook()->getActiveSheet()->getName();
-+ uno::Reference< excel::XApplication > xApplication( Application(), uno::UNO_QUERY_THROW );
-+ aStringSheet = xApplication->getActiveWorkbook()->getActiveSheet()->getName();
- bBefore = sal_True;
- }
- nCount = static_cast< SCTAB >( m_xIndexAccess->getCount() );
-@@ -295,7 +295,7 @@ ScVbaWorksheets::PrintOut( const uno::An
- if ( isSelectedSheets() )
- bSelection = sal_True;
-
-- PrintOutHelper( From, To, Copies, Preview, ActivePrinter, PrintToFile, Collate, PrToFileName, mxModel, bSelection );
-+ PrintOutHelper( excel::getBestViewShell( mxModel ), From, To, Copies, Preview, ActivePrinter, PrintToFile, Collate, PrToFileName, bSelection );
- }
-
- uno::Any SAL_CALL
-@@ -336,7 +336,7 @@ ScVbaWorksheets::setVisible( const uno::
- void SAL_CALL
- ScVbaWorksheets::Select( const uno::Any& Replace ) throw (uno::RuntimeException)
- {
-- ScTabViewShell* pViewShell = getBestViewShell( mxModel );
-+ ScTabViewShell* pViewShell = excel::getBestViewShell( mxModel );
- if ( !pViewShell )
- throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "Cannot obtain view shell" ) ), uno::Reference< uno::XInterface >() );
-
---- sc/source/ui/vba/vbaworksheets.hxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbaworksheets.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -36,9 +36,8 @@
- #include <com/sun/star/sheet/XSpreadsheets.hpp>
- #include <com/sun/star/container/XEnumerationAccess.hpp>
- #include <com/sun/star/uno/XComponentContext.hpp>
--#include <ooo/vba/XGlobals.hpp>
-
--#include "vbacollectionimpl.hxx"
-+#include <vbahelper/vbacollectionimpl.hxx>
-
- class ScModelObj;
-
---- sc/util/makefile.mk.old 2009-04-06 16:41:56.000000000 +0000
-+++ sc/util/makefile.mk 2009-04-06 16:42:01.000000000 +0000
-@@ -78,6 +78,7 @@ SHL1IMPLIB= sci
-
- # dynamic libraries
- SHL1STDLIBS= \
-+ $(VBAHELPERLIB) \
- $(BASICLIB) \
- $(SFXLIB) \
- $(SVTOOLLIB) \
-@@ -299,6 +300,7 @@ SHL9RPATH=OOO
- .ENDIF
-
- SHL9STDLIBS= \
-+ $(VBAHELPERLIB) \
- $(CPPUHELPERLIB) \
- $(VCLLIB) \
- $(CPPULIB) \
---- scp2/source/ooo/file_library_ooo.scp.old 2009-04-06 16:41:58.000000000 +0000
-+++ scp2/source/ooo/file_library_ooo.scp 2009-04-06 16:42:01.000000000 +0000
-@@ -406,7 +406,42 @@ File gid_File_Lib_Vbaobj
- #endif
- End
-
-+File gid_File_Lib_Vbaswobj
-+ TXT_FILE_BODY;
-+ Styles = (PACKED,UNO_COMPONENT);
-+ RegistryID = gid_Starregistry_Services_Rdb;
-+ Dir = gid_Dir_Program;
-+ #ifdef UNX
-+ Name = STRING(CONCAT4(libvbaswobj,DLLPOSTFIX,.uno,UNXSUFFIX));
-+ #else
-+ Name = STRING(CONCAT4(vbaswobj,DLLPOSTFIX,.uno,.dll));
-+ #endif
-+End
-+
-+File gid_File_Lib_Vbamsforms
-+ TXT_FILE_BODY;
-+ Styles = (PACKED,UNO_COMPONENT);
-+ RegistryID = gid_Starregistry_Services_Rdb;
-+ Dir = gid_Dir_Program;
-+ #ifdef UNX
-+ Name = STRING(CONCAT4(libmsforms,DLLPOSTFIX,.uno,UNXSUFFIX));
-+ #else
-+ Name = STRING(CONCAT4(msforms,DLLPOSTFIX,.uno,.dll));
-+ #endif
-+End
-+
- #endif // VBA_EXTENSION
-+File gid_File_Lib_Vbahelper
-+ TXT_FILE_BODY;
-+ Styles = (PACKED);
-+ RegistryID = gid_Starregistry_Services_Rdb;
-+ Dir = SCP2_OOO_BIN_DIR;
-+ #ifdef UNX
-+ Name = STRING(CONCAT3(libvbahelper,DLLPOSTFIX,UNXSUFFIX));
-+ #else
-+ Name = STRING(CONCAT3(vbahelper,DLLPOSTFIX,.dll));
-+ #endif
-+End
- #endif // ENABLE_VBA
-
-
---- scripting/source/vbaevents/eventhelper.cxx.old 2009-04-06 16:42:00.000000000 +0000
-+++ scripting/source/vbaevents/eventhelper.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -768,10 +768,27 @@ EventListener::firing_Impl(const ScriptE
- std::list< TranslateInfo >::const_iterator txInfo =
- eventInfo_it->second.begin();
- std::list< TranslateInfo >::const_iterator txInfo_end = eventInfo_it->second.end();
-- rtl::OUString sMacroLoc = rtl::OUString::createFromAscii("Standard.").concat( evt.ScriptCode ).concat( rtl::OUString::createFromAscii(".") );
-
- StarBASIC* pBasic = mpShell->GetBasic();
-+ BasicManager* pBasicManager = mpShell->GetBasicManager();
-+ //'Project' is a better default but I want to force failures
-+ //rtl::OUString sMacroLoc = rtl::OUString::createFromAscii("Project");
-+ rtl::OUString sProject = rtl::OUString::createFromAscii("Standard");
-+
-+ if ( pBasicManager->GetName().Len() > 0 )
-+ sProject = pBasicManager->GetName();
-+
-+ rtl::OUString sMacroLoc = sProject;
-+ sMacroLoc = sMacroLoc.concat( rtl::OUString::createFromAscii(".") );
-+ sMacroLoc = sMacroLoc.concat( evt.ScriptCode ).concat( rtl::OUString::createFromAscii(".") );
-+
-+ OSL_TRACE("sMacroLoc is %s", rtl::OUStringToOString( sMacroLoc, RTL_TEXTENCODING_UTF8 ).getStr() );
-+
-+ // find library
-+ pBasic = pBasicManager->GetLib( sProject );
-+
- SbModule* pModule = pBasic->FindModule( evt.ScriptCode );
-+
- for ( ; pModule && txInfo != txInfo_end; ++txInfo )
- {
- // see if we have a match for the handlerextension
---- sfx2/inc/sfx2/sfx.hrc.old 2009-04-02 10:44:03.000000000 +0000
-+++ sfx2/inc/sfx2/sfx.hrc 2009-04-06 16:42:01.000000000 +0000
-@@ -402,8 +402,10 @@
- #define MID_DOCINFO_ENCRYPTED 0x2c
- #define MID_DOCINFO_STATISTIC 0x33
- #define MID_DOCINFO_CHARLOCALE 0x34
--
--#define MID_LAST_USED_PROPID MID_DOCINFO_CHARLOCALE
-+#define MID_CATEGORY 0x35
-+#define MID_COMPANY 0x36
-+#define MID_MANAGER 0x37
-+#define MID_LAST_USED_PROPID MID_MANAGER
-
- // Config-Ids -----------------------------------------------------------
-
---- sfx2/inc/sfx2/sfxbasemodel.hxx.old 2009-04-02 10:44:03.000000000 +0000
-+++ sfx2/inc/sfx2/sfxbasemodel.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -1379,6 +1379,7 @@ protected:
- /* returns true if the document signatures are valid, otherwise false */
- sal_Bool hasValidSignatures() const;
-
-+ void setDocumentProperties( const ::com::sun::star::uno::Reference< ::com::sun::star::document::XDocumentProperties >& );
- //________________________________________________________________________________________________________
- // private methods
- //________________________________________________________________________________________________________
---- sfx2/source/appl/appuno.cxx.old 2009-04-02 10:44:02.000000000 +0000
-+++ sfx2/source/appl/appuno.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -2283,6 +2283,16 @@ SFX2_DLLPUBLIC sal_Bool SAL_CALL compone
- xNewKey = xKey->createKey( aTempStr );
- xNewKey->createKey( ::rtl::OUString::createFromAscii("com.sun.star.document.DocumentProperties") );
-
-+
-+ // writer compatable document properties
-+ aImpl = ::rtl::OUString(RTL_CONSTASCII_USTRINGPARAM("/"));
-+ aImpl += comp_CompatWriterDocProps::_getImplementationName();
-+
-+ aTempStr = aImpl;
-+ aTempStr += ::rtl::OUString(RTL_CONSTASCII_USTRINGPARAM("/UNO/SERVICES"));
-+ xNewKey = xKey->createKey( aTempStr );
-+ xNewKey->createKey( ::rtl::OUString::createFromAscii("com.sun.star.writer.DocumentProperties") );
-+
- return sal_True;
- }
-
-@@ -2340,6 +2350,16 @@ SFX2_DLLPUBLIC void* SAL_CALL component_
- ::comp_SfxDocumentMetaData::_getImplementationName(),
- ::comp_SfxDocumentMetaData::_getSupportedServiceNames());
- }
-+ if ( ::comp_CompatWriterDocProps::_getImplementationName().equals(
-+ ::rtl::OUString::createFromAscii( pImplementationName ) ) )
-+ {
-+ xFactory = ::cppu::createSingleComponentFactory(
-+ ::comp_CompatWriterDocProps::_create,
-+ ::comp_CompatWriterDocProps::_getImplementationName(),
-+ ::comp_CompatWriterDocProps::_getSupportedServiceNames());
-+ }
-+
-+ // Factory is valid - service was found.
-
- // Factory is valid - service was found.
- if ( xFactory.is() )
---- sfx2/source/doc/SfxDocumentMetaData.cxx.old 2009-04-02 10:43:58.000000000 +0000
-+++ sfx2/source/doc/SfxDocumentMetaData.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -89,6 +89,10 @@
- #include <cstring>
- #include <limits>
-
-+
-+#include <cppuhelper/implbase1.hxx>
-+#include <com/sun/star/document/XCompatWriterDocProperties.hpp>
-+
- /**
- * This file contains the implementation of the service
- * com.sun.star.document.DocumentProperties.
-@@ -298,12 +302,12 @@ public:
- const css::uno::Sequence< css::beans::StringPair >& i_rNamespaces)
- throw (css::uno::RuntimeException, css::xml::sax::SAXException);
-
--private:
-+protected:
- SfxDocumentMetaData(SfxDocumentMetaData &); // not defined
- SfxDocumentMetaData& operator =(SfxDocumentMetaData &); // not defined
-
- virtual ~SfxDocumentMetaData() {}
--
-+ virtual SfxDocumentMetaData* createMe( css::uno::Reference< css::uno::XComponentContext > const & context ) { return new SfxDocumentMetaData( context ); };
- const css::uno::Reference< css::uno::XComponentContext > m_xContext;
-
- /// for notification
-@@ -377,6 +381,54 @@ private:
- // throw (css::uno::RuntimeException);
- };
-
-+typedef ::cppu::ImplInheritanceHelper1< SfxDocumentMetaData, css::document::XCompatWriterDocProperties > CompatWriterDocPropsImpl_BASE;
-+
-+class CompatWriterDocPropsImpl : public CompatWriterDocPropsImpl_BASE
-+{
-+ rtl::OUString msManager;
-+ rtl::OUString msCategory;
-+ rtl::OUString msCompany;
-+protected:
-+ virtual SfxDocumentMetaData* createMe( css::uno::Reference< css::uno::XComponentContext > const & context ) { return new CompatWriterDocPropsImpl( context ); };
-+public:
-+ CompatWriterDocPropsImpl( css::uno::Reference< css::uno::XComponentContext > const & context) : CompatWriterDocPropsImpl_BASE( context ) {}
-+// XCompatWriterDocPropsImpl
-+ virtual ::rtl::OUString SAL_CALL getManager() throw (::com::sun::star::uno::RuntimeException) { return msManager; }
-+ virtual void SAL_CALL setManager( const ::rtl::OUString& _manager ) throw (::com::sun::star::uno::RuntimeException) { msManager = _manager; }
-+ virtual ::rtl::OUString SAL_CALL getCategory() throw (::com::sun::star::uno::RuntimeException){ return msCategory; }
-+ virtual void SAL_CALL setCategory( const ::rtl::OUString& _category ) throw (::com::sun::star::uno::RuntimeException){ msCategory = _category; }
-+ virtual ::rtl::OUString SAL_CALL getCompany() throw (::com::sun::star::uno::RuntimeException){ return msCompany; }
-+ virtual void SAL_CALL setCompany( const ::rtl::OUString& _company ) throw (::com::sun::star::uno::RuntimeException){ msCompany = _company; }
-+
-+// XServiceInfo
-+ virtual ::rtl::OUString SAL_CALL getImplementationName( ) throw (::com::sun::star::uno::RuntimeException)
-+ {
-+ return comp_CompatWriterDocProps::_getImplementationName();
-+ }
-+
-+ virtual ::sal_Bool SAL_CALL supportsService( const ::rtl::OUString& ServiceName ) throw (::com::sun::star::uno::RuntimeException)
-+ {
-+ css::uno::Sequence< rtl::OUString > sServiceNames= getSupportedServiceNames();
-+ sal_Int32 nLen = sServiceNames.getLength();
-+ rtl::OUString* pIt = sServiceNames.getArray();
-+ rtl::OUString* pEnd = ( pIt + nLen );
-+ sal_Bool bRes = sal_False;
-+ for ( ; pIt != pEnd; ++pIt )
-+ {
-+ if ( pIt->equals( ServiceName ) )
-+ {
-+ bRes = sal_True;
-+ break;
-+ }
-+ }
-+ return bRes;
-+ }
-+
-+ virtual ::com::sun::star::uno::Sequence< ::rtl::OUString > SAL_CALL getSupportedServiceNames( ) throw (::com::sun::star::uno::RuntimeException)
-+ {
-+ return comp_CompatWriterDocProps::_getSupportedServiceNames();
-+ }
-+};
- ////////////////////////////////////////////////////////////////////////////
-
- bool operator== (const css::util::DateTime &i_rLeft,
-@@ -2149,7 +2201,7 @@ SfxDocumentMetaData::createClone()
- ::osl::MutexGuard g(m_aMutex);
- checkInit();
-
-- SfxDocumentMetaData *pNew = new SfxDocumentMetaData(m_xContext);
-+ SfxDocumentMetaData *pNew = createMe(m_xContext);
-
- // NB: do not copy the modification listeners, only DOM
- css::uno::Reference<css::xml::dom::XDocument> xDoc = createDOM();
-@@ -2266,6 +2318,32 @@ void SAL_CALL SfxDocumentMetaData::seria
-
-
- // component helper namespace
-+namespace comp_CompatWriterDocProps {
-+
-+ ::rtl::OUString SAL_CALL _getImplementationName() {
-+ return ::rtl::OUString(RTL_CONSTASCII_USTRINGPARAM(
-+ "CompatWriterDocPropsImpl"));
-+}
-+
-+ css::uno::Sequence< ::rtl::OUString > SAL_CALL _getSupportedServiceNames()
-+ {
-+ static css::uno::Sequence< rtl::OUString > aServiceNames;
-+ if ( aServiceNames.getLength() == 0 )
-+ {
-+ aServiceNames.realloc( 1 );
-+ aServiceNames[ 0 ] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("com.sun.star.writer.DocumentProperties" ) );
-+ }
-+ return aServiceNames;
-+ }
-+ css::uno::Reference< css::uno::XInterface > SAL_CALL _create(
-+ const css::uno::Reference< css::uno::XComponentContext > & context)
-+ SAL_THROW((css::uno::Exception))
-+ {
-+ return static_cast< ::cppu::OWeakObject * >
-+ (new CompatWriterDocPropsImpl(context));
-+ }
-+
-+}
- namespace comp_SfxDocumentMetaData {
-
- ::rtl::OUString SAL_CALL _getImplementationName() {
---- sfx2/source/doc/docinf.cxx.old 2009-04-02 10:43:58.000000000 +0000
-+++ sfx2/source/doc/docinf.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -37,6 +37,7 @@
- #include <com/sun/star/beans/XPropertySet.hpp>
- #include <com/sun/star/beans/XPropertyContainer.hpp>
- #include <com/sun/star/document/XDocumentProperties.hpp>
-+#include <com/sun/star/document/XCompatWriterDocProperties.hpp>
- #include <com/sun/star/uno/Exception.hpp>
-
- #include <rtl/ustring.hxx>
-@@ -46,7 +47,6 @@
- #include <vcl/gdimtf.hxx>
-
- #include "oleprops.hxx"
--
- // ============================================================================
-
- // stream names
-@@ -174,6 +174,28 @@ sal_uInt32 SFX2_DLLPUBLIC LoadOlePropert
- }
- }
- }
-+
-+ uno::Reference< document::XCompatWriterDocProperties > xWriterProps( i_xDocProps, uno::UNO_QUERY );
-+ if ( xWriterProps.is() )
-+ {
-+ SfxOleSectionRef xBuiltin = aDocSet.GetSection( SECTION_BUILTIN );
-+ if ( xBuiltin.get() )
-+ {
-+ try
-+ {
-+ String aStrValue;
-+ if ( xBuiltin->GetStringValue( aStrValue, PROPID_MANAGER ) )
-+ xWriterProps->setManager( aStrValue );
-+ if ( xBuiltin->GetStringValue( aStrValue, PROPID_CATEGORY ) )
-+ xWriterProps->setCategory( aStrValue );
-+ if ( xBuiltin->GetStringValue( aStrValue, PROPID_COMPANY ) )
-+ xWriterProps->setCompany( aStrValue );
-+ }
-+ catch ( uno::Exception& )
-+ {
-+ }
-+ }
-+ }
-
- // return code
- return (nGlobError != ERRCODE_NONE) ? nGlobError : nDocError;
---- sfx2/source/doc/objuno.cxx.old 2009-04-02 10:43:58.000000000 +0000
-+++ sfx2/source/doc/objuno.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -48,6 +48,7 @@
- #include <com/sun/star/lang/Locale.hpp>
- #include <com/sun/star/util/XModifiable.hpp>
- #include <com/sun/star/document/XDocumentProperties.hpp>
-+#include <com/sun/star/document/XCompatWriterDocProperties.hpp>
-
- #include <unotools/configmgr.hxx>
- #include <tools/inetdef.hxx>
-@@ -105,6 +106,9 @@ SfxItemPropertyMap aDocInfoPropertyMap_I
- { "AutoloadEnabled" , 15, MID_DOCINFO_AUTOLOADENABLED, &::getBooleanCppuType(), PROPERTY_UNBOUND, 0 },
- { "AutoloadSecs" , 12, MID_DOCINFO_AUTOLOADSECS, &::getCppuType((const sal_Int32*)0), PROPERTY_UNBOUND, 0 },
- { "AutoloadURL" , 11, MID_DOCINFO_AUTOLOADURL, &::getCppuType((const ::rtl::OUString*)0), PROPERTY_UNBOUND, 0 },
-+ { "Category" , 8 , MID_CATEGORY, &::getCppuType((const ::rtl::OUString*)0), PROPERTY_UNBOUND, 0 },
-+ { "Company" , 7 , MID_COMPANY, &::getCppuType((const ::rtl::OUString*)0), PROPERTY_UNBOUND, 0 },
-+ { "Manager" , 7 , MID_MANAGER, &::getCppuType((const ::rtl::OUString*)0), PROPERTY_UNBOUND, 0 },
- { "CreationDate" , 12, WID_DATE_CREATED, &::getCppuType((const ::com::sun::star::util::DateTime*)0),PROPERTY_MAYBEVOID, 0 },
- { "DefaultTarget" , 13, MID_DOCINFO_DEFAULTTARGET, &::getCppuType((const ::rtl::OUString*)0), PROPERTY_UNBOUND, 0 },
- { "Description" , 11, MID_DOCINFO_DESCRIPTION, &::getCppuType((const ::rtl::OUString*)0), PROPERTY_UNBOUND, 0 },
-@@ -824,6 +828,22 @@ void SAL_CALL SfxDocumentInfoObject::se
- _pImp->m_xDocProps->setDefaultTarget(sTemp);
- break;
- // case WID_CONTENT_TYPE : // this is readonly!
-+ case MID_CATEGORY:
-+ case MID_MANAGER:
-+ case MID_COMPANY:
-+ {
-+ uno::Reference< document::XCompatWriterDocProperties > xWriterProps( _pImp->m_xDocProps, uno::UNO_QUERY );
-+ if ( xWriterProps.is() )
-+ {
-+ if ( nHandle == MID_CATEGORY )
-+ xWriterProps->setCategory( sTemp );
-+ else if ( nHandle == MID_MANAGER )
-+ xWriterProps->setManager( sTemp );
-+ else
-+ xWriterProps->setCompany( sTemp );
-+ break;
-+ }
-+ }
- default:
- break;
- }
-@@ -1041,6 +1061,23 @@ void SAL_CALL SfxDocumentInfoObject::se
- case MID_DOCINFO_CHARLOCALE:
- aValue <<= _pImp->m_xDocProps->getLanguage();
- break;
-+ case MID_CATEGORY:
-+ case MID_MANAGER:
-+ case MID_COMPANY:
-+ {
-+ uno::Reference< document::XCompatWriterDocProperties > xWriterProps( _pImp->m_xDocProps, uno::UNO_QUERY );
-+ if ( xWriterProps.is() )
-+ {
-+ if ( nHandle == MID_CATEGORY )
-+ aValue <<= xWriterProps->getCategory();
-+ else if ( nHandle == MID_MANAGER )
-+ aValue <<= xWriterProps->getManager();
-+ else
-+ aValue <<= xWriterProps->getCompany();
-+ break;
-+ }
-+ }
-+
- default:
- aValue <<= ::rtl::OUString();
- break;
---- sfx2/source/doc/oleprops.hxx.old 2009-04-02 10:43:58.000000000 +0000
-+++ sfx2/source/doc/oleprops.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -83,6 +83,10 @@ const sal_Int32 PROPID_CREATED
- const sal_Int32 PROPID_LASTSAVED = 13;
- const sal_Int32 PROPID_THUMBNAIL = 17;
-
-+// some Builtin properties
-+const sal_Int32 PROPID_CATEGORY = 0x2;
-+const sal_Int32 PROPID_COMPANY = 0xf;
-+const sal_Int32 PROPID_MANAGER = 0xe;
- // predefined codepages
- const sal_uInt16 CODEPAGE_UNKNOWN = 0;
- const sal_uInt16 CODEPAGE_UNICODE = 1200;
---- sfx2/source/doc/sfxbasemodel.cxx.old 2009-04-02 10:43:58.000000000 +0000
-+++ sfx2/source/doc/sfxbasemodel.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -784,7 +784,15 @@ uno::Reference< document::XDocumentInfo
-
- return m_pData->m_xDocumentInfo;
- }
--
-+void
-+SfxBaseModel::setDocumentProperties( const uno::Reference< document::XDocumentProperties >& rxNewDocProps )
-+{
-+ // object already disposed?
-+ ::vos::OGuard aGuard( Application::GetSolarMutex() );
-+ if ( impl_isDisposed() )
-+ throw lang::DisposedException();
-+ m_pData->m_xDocumentProperties.set(rxNewDocProps, uno::UNO_QUERY_THROW);
-+}
- // document::XDocumentPropertiesSupplier:
- uno::Reference< document::XDocumentProperties > SAL_CALL
- SfxBaseModel::getDocumentProperties()
---- sfx2/source/inc/SfxDocumentMetaData.hxx.old 2009-04-02 10:43:59.000000000 +0000
-+++ sfx2/source/inc/SfxDocumentMetaData.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -48,5 +48,16 @@ css::uno::Reference< css::uno::XInterfac
-
- } // closing component helper namespace
-
-+namespace comp_CompatWriterDocProps {
-+
-+namespace css = ::com::sun::star;
-+
-+// component and service helper functions:
-+::rtl::OUString SAL_CALL _getImplementationName();
-+css::uno::Sequence< ::rtl::OUString > SAL_CALL _getSupportedServiceNames();
-+css::uno::Reference< css::uno::XInterface > SAL_CALL _create(
-+ css::uno::Reference< css::uno::XComponentContext > const & context );
-+
-+}
- #endif
-
---- solenv/inc/libs.mk.old 2009-04-02 10:53:10.000000000 +0000
-+++ solenv/inc/libs.mk 2009-04-06 16:42:01.000000000 +0000
-@@ -192,6 +192,7 @@ SAXLIB=-lsax$(DLLPOSTFIX)
- MAILLIB=-lmail
- DOCMGRLIB=-ldmg$(DLLPOSTFIX)
- BASICLIB=-lsb$(DLLPOSTFIX)
-+VBAHELPERLIB=-lvbahelper$(DLLPOSTFIX)
- DBTOOLSLIB=-ldbtools$(DLLPOSTFIX)
- HM2LIBSH=-lhmwrpdll
- HM2LIBST=-lhmwrap
-@@ -433,6 +434,7 @@ SAXLIB=isax.lib
- MAILLIB=mail.lib
- DOCMGRLIB=docmgr.lib
- BASICLIB=basic.lib
-+VBAHELPERLIB=vbahelper.lib
- TKTLIB=tkt.lib
- SJLIB=sj.lib
- SVXLIB=isvx.lib
---- svx/inc/svx/mstoolbar.hxx.old 2009-04-06 16:42:00.000000000 +0000
-+++ svx/inc/svx/mstoolbar.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -27,6 +27,7 @@ public:
- virtual rtl::OUString MSOTCIDToOOCommand( sal_Int16 msoTCID ) = 0;
- };
-
-+class SfxObjectShell;
-
- class SVX_DLLPUBLIC CustomToolBarImportHelper
- {
-@@ -39,16 +40,16 @@ class SVX_DLLPUBLIC CustomToolBarImportH
- std::auto_ptr< MSOCommandConvertor > pMSOCmdConvertor;
- css::uno::Reference< css::ui::XUIConfigurationManagerSupplier > m_xCfgSupp;
- css::uno::Reference< css::ui::XUIConfigurationManager > m_xAppCfgMgr;
--
-+ SfxObjectShell& mrDocSh;
- public:
-- CustomToolBarImportHelper( const css::uno::Reference< css::frame::XModel >& rxModel, const css::uno::Reference< css::ui::XUIConfigurationManager >& rxAppCfgMgr );
-+ CustomToolBarImportHelper( SfxObjectShell& rDocSh, const css::uno::Reference< css::ui::XUIConfigurationManager >& rxAppCfgMgr );
-
- void setMSOCommandMap( MSOCommandConvertor* pCnvtr ) { pMSOCmdConvertor.reset( pCnvtr ); }
- css::uno::Reference< css::ui::XUIConfigurationManager > getCfgManager();
- css::uno::Reference< css::ui::XUIConfigurationManager > getAppCfgManager();
-
-
-- static css::uno::Any createCommandFromMacro( const rtl::OUString& sCmd );
-+ css::uno::Any createCommandFromMacro( const rtl::OUString& sCmd );
-
- void addIcon( const css::uno::Reference< css::graphic::XGraphic >& xImage, const rtl::OUString& sString );
- void applyIcons();
-@@ -131,7 +132,7 @@ public:
- ~TBCGeneralInfo() {}
- bool Read(SvStream *pS);
- void Print( FILE* );
-- bool ImportToolBarControlData( std::vector< css::beans::PropertyValue >& );
-+ bool ImportToolBarControlData( CustomToolBarImportHelper&, std::vector< css::beans::PropertyValue >& );
- };
-
- class SVX_DLLPUBLIC TBCBitMap : public TBBase
---- svx/inc/svxmsbas.hxx.old 2009-04-06 16:42:00.000000000 +0000
-+++ svx/inc/svxmsbas.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -59,6 +59,8 @@ typedef std::hash_map< sal_Int32, String
-
- typedef std::map< String, ObjIdToName > ControlAttributeInfo;
-
-+class VBA_Impl;
-+
- class SVX_DLLPUBLIC SvxImportMSVBasic
- {
- ControlAttributeInfo m_ModuleNameToObjIdHash;
-@@ -102,6 +104,9 @@ private:
- const String &rSubStorageName, BOOL bVBAMode );
- SVX_DLLPRIVATE BOOL CopyStorage_Impl( const String& rStorageName,
- const String &rSubStorageName);
-+ rtl::OUString msProjectName;
-+ SVX_DLLPRIVATE BOOL ImportCode_Impl( VBA_Impl&, BOOL, BOOL );
-+ SVX_DLLPRIVATE bool ImportForms_Impl( VBA_Impl&, const String&, const String&, BOOL);
- };
-
- #endif
---- svx/source/msfilter/mstoolbar.cxx.old 2009-04-06 16:42:00.000000000 +0000
-+++ svx/source/msfilter/mstoolbar.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -8,6 +8,8 @@
- #include <vcl/graph.hxx>
- #include <vcl/bitmapex.hxx>
- #include <map>
-+#include <sfx2/objsh.hxx>
-+#include <basic/basmgr.hxx>
-
- int TBBase::nIndent = 0;
-
-@@ -36,9 +38,9 @@ void CustomToolBarImportHelper::addIcon(
- iconcommands.push_back( item );
- }
-
--CustomToolBarImportHelper::CustomToolBarImportHelper( const uno::Reference< frame::XModel >& rxModel, const css::uno::Reference< css::ui::XUIConfigurationManager>& rxAppCfgMgr )
-+CustomToolBarImportHelper::CustomToolBarImportHelper( SfxObjectShell& rDocShell, const css::uno::Reference< css::ui::XUIConfigurationManager>& rxAppCfgMgr ) : mrDocSh( rDocShell )
- {
-- m_xCfgSupp.set( rxModel, uno::UNO_QUERY_THROW );
-+ m_xCfgSupp.set( mrDocSh.GetModel(), uno::UNO_QUERY_THROW );
- m_xAppCfgMgr.set( rxAppCfgMgr, uno::UNO_QUERY_THROW );
- }
-
-@@ -58,10 +60,18 @@ uno::Any
- CustomToolBarImportHelper::createCommandFromMacro( const rtl::OUString& sCmd )
- {
- //"vnd.sun.star.script:Standard.Module1.Main?language=Basic&location=document"
-- static rtl::OUString part1 = rtl::OUString::createFromAscii( "vnd.sun.star.script:Standard.");
-+ static rtl::OUString scheme = rtl::OUString::createFromAscii( "vnd.sun.star.script:");
- static rtl::OUString part2 = rtl::OUString::createFromAscii("?language=Basic&location=document");
-+ rtl::OUString sProject( RTL_CONSTASCII_USTRINGPARAM("Standard") );
-+ if ( mrDocSh.GetBasicManager()->GetName().Len() )
-+ sProject = mrDocSh.GetBasicManager()->GetName();
-+ sProject += rtl::OUString( RTL_CONSTASCII_USTRINGPARAM(".") );
-+
-+ // #TODO #FIXME a script can also be loosly defined ( e.g. with no module
-+ // spec )
-+
- // create script url
-- rtl::OUString scriptURL = part1 + sCmd + part2;
-+ rtl::OUString scriptURL = scheme + sProject + sCmd + part2;
- return uno::makeAny( scriptURL );
- }
-
-@@ -197,7 +207,7 @@ bool TBCData::Read(SvStream *pS)
-
- bool TBCData::ImportToolBarControl( const css::uno::Reference< css::container::XIndexContainer >& /*toolbarcontainer*/, CustomToolBarImportHelper& helper, std::vector< css::beans::PropertyValue >& props )
- {
-- controlGeneralInfo.ImportToolBarControlData( props );
-+ controlGeneralInfo.ImportToolBarControlData( helper, props );
- beans::PropertyValue aProp;
- aProp.Name = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("Visible") ) ;
- aProp.Value = uno::makeAny( rHeader.isVisible() ); // where is the visible attribute stored
-@@ -356,7 +366,7 @@ TBCGeneralInfo::Print( FILE* fp )
- }
-
- bool
--TBCGeneralInfo::ImportToolBarControlData( std::vector< beans::PropertyValue >& sControlData )
-+TBCGeneralInfo::ImportToolBarControlData( CustomToolBarImportHelper& helper, std::vector< beans::PropertyValue >& sControlData )
- {
- if ( ( bFlags & 0x5 ) )
- {
-@@ -366,7 +376,7 @@ TBCGeneralInfo::ImportToolBarControlData
- if ( extraInfo.getOnAction().getLength() )
- {
- aProp.Name = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("CommandURL") );
-- aProp.Value = CustomToolBarImportHelper::createCommandFromMacro( extraInfo.getOnAction() );
-+ aProp.Value = helper.createCommandFromMacro( extraInfo.getOnAction() );
- sControlData.push_back( aProp );
- }
-
-@@ -379,7 +389,7 @@ TBCGeneralInfo::ImportToolBarControlData
- sControlData.push_back( aProp );
-
- aProp.Name = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("HelpURL") );
-- aProp.Value = uno::makeAny( CustomToolBarImportHelper::createCommandFromMacro( tooltip.getString() ) );
-+ aProp.Value = uno::makeAny( helper.createCommandFromMacro( tooltip.getString() ) );
- sControlData.push_back( aProp );
-
- // #TODO find out what is the property for tooltip?
---- svx/source/msfilter/msvbasic.cxx.old 2009-04-06 16:41:59.000000000 +0000
-+++ svx/source/msfilter/msvbasic.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -40,9 +40,929 @@
- #include <osl/endian.h>
- #include <rtl/tencinfo.h> //rtl_getTextEncodingFromWindowsCodePage
- #include "msvbasic.hxx"
-+#include <fstream>
-+#include <memory>
-+#include <rtl/ustrbuf.hxx>
-
- using namespace ::com::sun::star::script;
-
-+// #FIXME this routine is stolen from msocximex ( needs to be somewhere central )
-+
-+const sal_uInt32 SVX_MSOCX_SIZEMASK = 0x7FFFFFFF; /// Mask for character buffer size.
-+const sal_uInt32 SVX_MSOCX_COMPRESSED = 0x80000000;
-+
-+inline bool lclIsCompressed( sal_uInt32 nLenFld )
-+{
-+ return (nLenFld & SVX_MSOCX_COMPRESSED) != 0;
-+}
-+
-+
-+/** Extracts and returns the memory size of the character buffer.
-+ @return Character buffer size (may differ from resulting string length!).
-+ */
-+inline sal_uInt32 lclGetBufferSize( sal_uInt32 nLenFld )
-+{
-+ return nLenFld & SVX_MSOCX_SIZEMASK;
-+}
-+/** Creates an OUString from a character array created with lclReadCharArray().
-+
-+ The passed parameters must match, that means the length field must be the
-+ same used to create the passed character array.
-+
-+ @param pcCharArr
-+ The character array returned by lclReadCharArray(). May be compressed
-+ or uncompressed, next parameter nLenFld will specify this.
-+
-+ @param nLenFld
-+ MUST be the same string length field that has been passed to
-+ lclReadCharArray() to create the character array in previous parameter
-+ pcCharArr.
-+
-+ @return
-+ An OUString containing the decoded string data. Will be empty if
-+ pcCharArr is 0.
-+ */
-+rtl::OUString lclCreateOUString( const char* pcCharArr, sal_uInt32 nLenFld )
-+{
-+ rtl::OUStringBuffer aBuffer;
-+ sal_uInt32 nBufSize = lclGetBufferSize( nLenFld );
-+ if( lclIsCompressed( nLenFld ) )
-+ {
-+ // buffer contains compressed Unicode, not encoded bytestring
-+ sal_Int32 nStrLen = static_cast< sal_Int32 >( nBufSize );
-+ aBuffer.setLength( nStrLen );
-+ const char* pcCurrChar = pcCharArr;
-+ for( sal_Int32 nChar = 0; nChar < nStrLen; ++nChar, ++pcCurrChar )
-+ /* *pcCurrChar may contain negative values and therefore MUST be
-+ casted to unsigned char, before assigned to a sal_Unicode. */
-+ aBuffer.setCharAt( nChar, static_cast< unsigned char >( *pcCurrChar ) );
-+ }
-+ else
-+ {
-+ // buffer contains Little-Endian Unicode
-+ sal_Int32 nStrLen = static_cast< sal_Int32 >( nBufSize ) / 2;
-+ aBuffer.setLength( nStrLen );
-+ const char* pcCurrChar = pcCharArr;
-+ for( sal_Int32 nChar = 0; nChar < nStrLen; ++nChar )
-+ {
-+ /* *pcCurrChar may contain negative values and therefore MUST be
-+ casted to unsigned char, before assigned to a sal_Unicode. */
-+ sal_Unicode cChar = static_cast< unsigned char >( *pcCurrChar++ );
-+ cChar |= (static_cast< unsigned char >( *pcCurrChar++ ) << 8);
-+ aBuffer.setCharAt( nChar, cChar );
-+ }
-+ }
-+ return aBuffer.makeStringAndClear();
-+}
-+
-+
-+namespace MSLZSS {
-+
-+static unsigned int getShift( sal_uInt32 nPos )
-+{
-+ if (nPos <= 0x80) {
-+ if (nPos <= 0x20)
-+ return (nPos <= 0x10) ? 12 : 11;
-+ else
-+ return (nPos <= 0x40) ? 10 : 9;
-+ } else {
-+ if (nPos <= 0x200)
-+ return (nPos <= 0x100) ? 8 : 7;
-+ else if (nPos <= 0x800)
-+ return (nPos <= 0x400) ? 6 : 5;
-+ else
-+ return 4;
-+ }
-+}
-+
-+SvMemoryStream *decompressAsStream( SvStream *pStream, sal_uInt32 nOffset, sal_uInt32 *pCompressedLength = NULL, sal_uInt32 *pLength = NULL )
-+{
-+ SvMemoryStream *pResult;
-+ const sal_Int32 nWINDOWLEN = 4096;
-+ pResult = new SvMemoryStream();
-+
-+ sal_uInt8 nLeadbyte;
-+ unsigned int nPos = 0;
-+ int nLen, nDistance, nShift, nClean=1;
-+ sal_uInt8 aHistory[ nWINDOWLEN ];
-+
-+ pStream->Seek( nOffset + 3 );
-+
-+ while( pStream->Read( &nLeadbyte, 1 ) )
-+ {
-+ for(int nMask=0x01; nMask < 0x100; nMask = nMask<<1)
-+ {
-+ // we see if the leadbyte has flagged this location as a dataunit
-+ // which is actually a token which must be looked up in the history
-+ if( nLeadbyte & nMask )
-+ {
-+ sal_uInt16 nToken;
-+
-+ *pStream >> nToken;
-+
-+ if (nClean == 0)
-+ nClean=1;
-+
-+ //For some reason the division of the token into the length
-+ //field of the data to be inserted, and the distance back into
-+ //the history differs depending on how full the history is
-+ nShift = getShift( nPos % nWINDOWLEN );
-+
-+ nLen = (nToken & ((1<<nShift) - 1)) + 3;
-+ nDistance = nToken >> nShift;
-+
-+ //read the len of data from the history, wrapping around the
-+ //nWINDOWLEN boundary if necessary data read from the history
-+ //is also copied into the recent part of the history as well.
-+ for (int i = 0; i < nLen; i++)
-+ {
-+ unsigned char c;
-+ c = aHistory[(nPos-nDistance-1) % nWINDOWLEN];
-+ aHistory[nPos % nWINDOWLEN] = c;
-+ nPos++;
-+ }
-+ }
-+ else
-+ {
-+ // special boundary case code, not guarantueed to be correct
-+ // seems to work though, there is something wrong with the
-+ // compression scheme (or maybe a feature) where when the data
-+ // ends on a nWINDOWLEN boundary and the excess bytes in the 8
-+ // dataunit list are discarded, and not interpreted as tokens
-+ // or normal data.
-+ if ((nPos != 0) && ((nPos % nWINDOWLEN) == 0) && (nClean))
-+ {
-+ pStream->SeekRel(2);
-+ nClean=0;
-+ pResult->Write( aHistory, nWINDOWLEN );
-+ break;
-+ }
-+ //This is the normal case for when the data unit is not a
-+ //token to be looked up, but instead some normal data which
-+ //can be output, and placed in the history.
-+ if (pStream->Read(&aHistory[nPos % nWINDOWLEN],1))
-+ nPos++;
-+
-+ if (nClean == 0)
-+ nClean=1;
-+ }
-+ }
-+ }
-+ if (nPos % nWINDOWLEN)
-+ pResult->Write( aHistory, nPos % nWINDOWLEN );
-+ pResult->Flush();
-+
-+ if( pCompressedLength )
-+ *pCompressedLength = nPos;
-+
-+ if( pLength )
-+ *pLength = pResult->Tell();
-+
-+ pResult->Seek( 0 );
-+
-+ return pResult;
-+}
-+
-+} //MSZSS
-+
-+// also _VBA_PROJECT_VDPI can be used to create a usable
-+// ( and much smaller ) "_VBA_PROJECT" stream
-+
-+// _VBA_PROJECT Stream Version Dependant Project Information
-+// _VBA_PROJECT Stream Version Dependant Project Information
-+
-+class _VBA_PROJECT_VDPI
-+{
-+public:
-+sal_Int16 Reserved1;
-+sal_Int16 Version;
-+sal_Int8 Reserved2;
-+sal_Int16 Reserved3;
-+sal_uInt8* PerformanceCache;
-+sal_Int32 PerformanceCacheSize;
-+_VBA_PROJECT_VDPI(): Reserved1( 0x61CC), Version( 0xFFFF ), Reserved2(0x0), Reserved3(0x0), PerformanceCache(0), PerformanceCacheSize(0) {}
-+~_VBA_PROJECT_VDPI()
-+{
-+ if ( PerformanceCache )
-+ delete [] PerformanceCache;
-+ PerformanceCache = 0;
-+ PerformanceCacheSize = 0;
-+}
-+void read(){}
-+void write( SvStream* pStream )
-+{
-+ *pStream << Reserved1 << Version << Reserved2 << Reserved3;
-+ for( sal_Int32 i = 0; PerformanceCache && i < PerformanceCacheSize; ++i )
-+ {
-+ *pStream >> PerformanceCache[ i ];
-+ }
-+}
-+};
-+
-+class ProjectSysKindRecord
-+{
-+public:
-+sal_Int16 Id;
-+sal_Int32 Size;
-+sal_Int32 SysKind;
-+ProjectSysKindRecord(): Id(0x1), Size(0x4), SysKind( 0x1 ) {}
-+void read( SvStream* pStream )
-+{
-+ *pStream >> Id >> Size >> SysKind;
-+}
-+};
-+
-+class ProjectLcidRecord
-+{
-+public:
-+sal_Int16 Id;
-+sal_Int32 Size;
-+sal_Int32 Lcid;
-+
-+ProjectLcidRecord() : Id( 0x2 ), Size( 0x4 ), Lcid( 0x409 ) {}
-+void read( SvStream* pStream )
-+{
-+ OSL_TRACE("ProjectLcidRecord [0x%x]", pStream->Tell() );
-+ *pStream >> Id >> Size >> Lcid;
-+}
-+};
-+
-+class ProjectLcidInvokeRecord
-+{
-+sal_Int16 Id;
-+sal_Int32 Size;
-+sal_Int32 LcidInvoke;
-+public:
-+ProjectLcidInvokeRecord() : Id( 0x14 ), Size( 0x4 ), LcidInvoke( 0x409 ) {}
-+void read( SvStream* pStream )
-+{
-+ OSL_TRACE("ProjectLcidInvokeRecord [0x%x]", pStream->Tell() );
-+ *pStream >> Id >> Size >> LcidInvoke;
-+}
-+};
-+
-+class ProjectCodePageRecord
-+{
-+sal_Int16 Id;
-+sal_Int32 Size;
-+sal_Int16 CodePage;
-+public:
-+// #FIXME get a better default for the CodePage
-+ProjectCodePageRecord() : Id( 0x03 ), Size( 0x2 ), CodePage( 0x0 ) {}
-+void read( SvStream* pStream )
-+{
-+ OSL_TRACE("ProjectCodePageRecord [0x%x]", pStream->Tell() );
-+ *pStream >> Id >> Size >> CodePage;
-+}
-+};
-+class ProjectNameRecord
-+{
-+public:
-+sal_Int16 Id;
-+sal_Int32 SizeOfProjectName;
-+sal_uInt8* ProjectName;
-+rtl::OUString msProjectName;
-+ProjectNameRecord() : Id( 0x04 ), SizeOfProjectName( 0x0 ), ProjectName(0) {}
-+~ProjectNameRecord()
-+{
-+ delete [] ProjectName;
-+ ProjectName = 0;
-+}
-+void read( SvStream* pStream )
-+{
-+ OSL_TRACE("ProjectNameRecord [0x%x]", pStream->Tell() );
-+ *pStream >> Id >> SizeOfProjectName;
-+ if ( ProjectName )
-+ delete [] ProjectName;
-+
-+ if ( SizeOfProjectName )
-+ {
-+ ProjectName = new sal_uInt8[ SizeOfProjectName ];
-+ OSL_TRACE("ProjectNameRecord about to read name from [0x%x], size %d", pStream->Tell(), SizeOfProjectName );
-+ pStream->Read( ProjectName, SizeOfProjectName );
-+ msProjectName = lclCreateOUString( reinterpret_cast< const char* >( ProjectName ), ( SVX_MSOCX_COMPRESSED | SizeOfProjectName ) );
-+ }
-+}
-+};
-+
-+class ProjectDocStringRecord
-+{
-+public:
-+sal_Int16 Id;
-+sal_Int32 SizeOfDocString;
-+sal_uInt8* DocString;
-+sal_Int16 Reserved;
-+sal_Int32 SizeOfDocStringUnicode;
-+sal_uInt8* DocStringUnicode;
-+
-+ProjectDocStringRecord() : Id( 0x5 ), SizeOfDocString( 0x0 ), DocString( 0 ), Reserved( 0x0 ), SizeOfDocStringUnicode( 0 ), DocStringUnicode( 0 ) {}
-+
-+~ProjectDocStringRecord()
-+{
-+ delete [] DocString;
-+ delete [] DocStringUnicode;
-+ DocString = 0;
-+ DocStringUnicode = 0;
-+}
-+void read( SvStream* pStream )
-+{
-+ OSL_TRACE("ProjectDocStringRecord [0x%x]", pStream->Tell() );
-+ *pStream >> Id >> SizeOfDocString;
-+
-+ if ( DocString )
-+ delete [] DocString;
-+
-+ DocString = new sal_uInt8[ SizeOfDocString ];
-+ pStream->Read( DocString, SizeOfDocString );
-+
-+ if ( SizeOfDocStringUnicode )
-+ delete [] DocStringUnicode;
-+
-+ *pStream >> Reserved >> SizeOfDocStringUnicode;
-+
-+ if ( DocStringUnicode )
-+ delete [] DocStringUnicode;
-+
-+ DocStringUnicode = new sal_uInt8[ SizeOfDocStringUnicode ];
-+
-+ pStream->Read( DocStringUnicode, SizeOfDocStringUnicode );
-+}
-+
-+};
-+
-+class ProjectHelpFilePath
-+{
-+public:
-+sal_Int16 Id;
-+sal_Int32 SizeOfHelpFile1;
-+sal_uInt8* HelpFile1;
-+sal_Int16 Reserved;
-+sal_Int32 SizeOfHelpFile2;
-+sal_uInt8* HelpFile2;
-+
-+ProjectHelpFilePath() : Id( 0x06 ), SizeOfHelpFile1(0), HelpFile1(0), Reserved(0x0), SizeOfHelpFile2(0), HelpFile2(0) {}
-+~ProjectHelpFilePath()
-+{
-+ if ( HelpFile1 )
-+ delete [] HelpFile1;
-+ if ( HelpFile2 )
-+ delete [] HelpFile2;
-+ HelpFile1 = 0;
-+ HelpFile2 = 0;
-+}
-+void read( SvStream* pStream )
-+{
-+ OSL_TRACE("ProjectHelpFilePath [0x%x]", pStream->Tell() );
-+ *pStream >> Id >> SizeOfHelpFile1;
-+
-+ if ( HelpFile1 )
-+ delete HelpFile1;
-+
-+ HelpFile1 = new sal_uInt8[ SizeOfHelpFile1 ];
-+ pStream->Read( HelpFile1, SizeOfHelpFile1 );
-+
-+ *pStream >> Reserved >> SizeOfHelpFile2;
-+
-+ if ( HelpFile2 )
-+ delete HelpFile2;
-+
-+ HelpFile2 = new sal_uInt8[ SizeOfHelpFile2 ];
-+ pStream->Read( HelpFile2, SizeOfHelpFile2 );
-+
-+}
-+};
-+
-+class ProjectHelpContextRecord
-+{
-+public:
-+sal_Int16 Id;
-+sal_Int32 Size;
-+sal_Int32 HelpContext;
-+
-+ProjectHelpContextRecord() : Id( 0x7 ), Size( 0x4 ), HelpContext( 0 ) {}
-+void read( SvStream* pStream )
-+{
-+
-+ OSL_TRACE("ProjectHelpContextRecord [0x%x]", pStream->Tell() );
-+ *pStream >> Id >> Size >> HelpContext;
-+}
-+
-+};
-+
-+class ProjectLibFlagsRecord
-+{
-+sal_Int16 Id;
-+sal_Int32 Size;
-+sal_Int32 ProjectLibFlags;
-+
-+public:
-+ProjectLibFlagsRecord() : Id( 0x8 ), Size( 0x4 ), ProjectLibFlags( 0x0 ) {}
-+void read( SvStream* pStream )
-+{
-+ OSL_TRACE("ProjectLibFlagsRecord [0x%x]", pStream->Tell() );
-+ *pStream >> Id >> Size >> ProjectLibFlags;
-+}
-+};
-+
-+class ProjectVersionRecord
-+{
-+public:
-+sal_Int16 Id;
-+sal_Int32 Reserved;
-+sal_Int32 VersionMajor;
-+sal_Int16 VersionMinor;
-+ProjectVersionRecord() : Id( 0x9 ), Reserved( 0x4 ), VersionMajor( 0x1 ), VersionMinor( 0 ) {}
-+void read( SvStream* pStream )
-+{
-+ OSL_TRACE("ProjectVersionRecord [0x%x]", pStream->Tell() );
-+ *pStream >> Id >> Reserved >> VersionMajor >> VersionMinor;
-+}
-+};
-+
-+class ProjectConstantsRecord
-+{
-+sal_Int16 Id;
-+sal_Int32 SizeOfConstants;
-+sal_uInt8* Constants;
-+sal_Int16 Reserved;
-+sal_Int32 SizeOfConstantsUnicode;
-+sal_uInt8* ConstantsUnicode;
-+public:
-+ProjectConstantsRecord() : Id( 0xC ), SizeOfConstants( 0 ), Constants( 0 ), Reserved( 0x3C ), SizeOfConstantsUnicode( 0 ), ConstantsUnicode(0) {}
-+
-+~ProjectConstantsRecord()
-+{
-+ delete [] Constants;
-+ Constants = 0;
-+ delete [] ConstantsUnicode;
-+ ConstantsUnicode = 0;
-+}
-+
-+void read( SvStream* pStream )
-+{
-+ OSL_TRACE("ProjectConstantsRecord [0x%x]", pStream->Tell() );
-+ *pStream >> Id >> SizeOfConstants;
-+ if ( Constants )
-+ delete [] Constants;
-+ Constants = new sal_uInt8[ SizeOfConstants ];
-+
-+ pStream->Read( Constants, SizeOfConstants );
-+
-+ *pStream >> Reserved;
-+
-+ if ( ConstantsUnicode )
-+ delete [] ConstantsUnicode;
-+
-+ *pStream >> SizeOfConstantsUnicode;
-+
-+ ConstantsUnicode = new sal_uInt8[ SizeOfConstantsUnicode ];
-+ pStream->Read( ConstantsUnicode, SizeOfConstantsUnicode );
-+}
-+
-+};
-+
-+class ReferenceNameRecord
-+{
-+public:
-+sal_Int16 Id;
-+sal_Int32 SizeOfName;
-+sal_uInt8* Name;
-+sal_Int16 Reserved;
-+sal_Int32 SizeOfNameUnicode;
-+sal_uInt8* NameUnicode;
-+
-+ReferenceNameRecord() : Id( 0x16 ), SizeOfName( 0 ), Name( 0 ), Reserved( 0x3E ), SizeOfNameUnicode( 0 ), NameUnicode( 0 ) {}
-+~ReferenceNameRecord()
-+{
-+ delete [] Name;
-+ Name = 0;
-+ delete [] NameUnicode;
-+ NameUnicode = 0;
-+}
-+
-+void read( SvStream* pStream )
-+{
-+ OSL_TRACE("NameRecord [0x%x]", pStream->Tell() );
-+ *pStream >> Id >> SizeOfName;
-+
-+ if ( Name )
-+ delete [] Name;
-+
-+ Name = new sal_uInt8[ SizeOfName ];
-+
-+ pStream->Read( Name, SizeOfName );
-+
-+ *pStream >> Reserved >> SizeOfNameUnicode;
-+
-+ if ( NameUnicode )
-+ delete [] Name;
-+
-+ NameUnicode = new sal_uInt8[ SizeOfNameUnicode ];
-+ pStream->Read( NameUnicode, SizeOfNameUnicode );
-+}
-+
-+};
-+
-+// Baseclass for ReferenceControlRecord, ReferenceRegisteredRecord, ReferenceProjectRecord
-+class DirDumper;
-+
-+class BaseReferenceRecord
-+{
-+public:
-+virtual ~BaseReferenceRecord(){}
-+virtual bool read( SvStream* pStream ) = 0;
-+virtual void import( VBA_Impl& ){}
-+};
-+
-+
-+class ReferenceProjectRecord : public BaseReferenceRecord
-+{
-+public:
-+ sal_uInt16 Id;
-+ sal_uInt32 Size;
-+ sal_uInt32 SizeOfLibidAbsolute;
-+ sal_uInt8* pLibidAbsolute;
-+ sal_uInt32 SizeOfLibidRelative;
-+ sal_uInt8* pLibidRelative;
-+ sal_uInt32 MajorVersion;
-+ sal_uInt16 MinorVersion;
-+ rtl::OUString msAbsoluteLibid;
-+ rtl::OUString msRelativeLibid;
-+
-+ virtual bool read( SvStream* pStream );
-+ virtual void import( VBA_Impl& rDir );
-+ ReferenceProjectRecord();
-+ ~ReferenceProjectRecord();
-+};
-+
-+ReferenceProjectRecord::ReferenceProjectRecord() : Id( 0x000E ), Size( 0 ), SizeOfLibidAbsolute( 0 ), pLibidAbsolute( NULL ), SizeOfLibidRelative( 0 ), pLibidRelative( 0 ), MajorVersion( 0 ), MinorVersion( 0 )
-+{
-+}
-+
-+ReferenceProjectRecord::~ReferenceProjectRecord()
-+{
-+ if ( pLibidAbsolute )
-+ delete[] pLibidAbsolute;
-+ if ( pLibidRelative )
-+ delete[] pLibidRelative;
-+}
-+
-+bool ReferenceProjectRecord::read( SvStream* pStream )
-+{
-+ OSL_TRACE("ReferenceProjectRecord [0x%x]", pStream->Tell() );
-+ *pStream >> Id >> Size >> SizeOfLibidAbsolute;
-+
-+ if ( SizeOfLibidAbsolute )
-+ {
-+ pLibidAbsolute = new sal_uInt8[ SizeOfLibidAbsolute ];
-+ OSL_TRACE("ReferenceProjectRecord about to read LibidAbsolute at [0x%x]", pStream->Tell() );
-+ pStream->Read( pLibidAbsolute, SizeOfLibidAbsolute );
-+ }
-+
-+ *pStream >> SizeOfLibidRelative;
-+
-+ if ( SizeOfLibidRelative )
-+ {
-+ pLibidRelative = new sal_uInt8[ SizeOfLibidRelative ];
-+ OSL_TRACE("ReferenceProjectRecord about to read LibidRelative at [0x%x]", pStream->Tell() );
-+ pStream->Read( pLibidRelative, SizeOfLibidRelative );
-+ }
-+
-+ *pStream >> MajorVersion >> MinorVersion;
-+
-+ // array size is ORed with SVX_MSOCX_COMPRESSED to force processing of ascii bytes ( and not
-+ // 16 bit unicode )
-+ // the offset of 3 is needed to skip the ProjectReference "*\" and project kind ( 0x4[1-4] ) info.
-+
-+ msAbsoluteLibid = lclCreateOUString( reinterpret_cast< const char* >( pLibidAbsolute + 3 ), ( SVX_MSOCX_COMPRESSED | (SizeOfLibidAbsolute - 3 )));
-+ msRelativeLibid = lclCreateOUString( reinterpret_cast< const char* >( pLibidRelative + 3 ), ( SVX_MSOCX_COMPRESSED | ( SizeOfLibidRelative -3 )));
-+
-+ OSL_TRACE("ReferenceProjectRecord - absolute path %s", rtl::OUStringToOString( msAbsoluteLibid, RTL_TEXTENCODING_UTF8 ).getStr() );
-+ OSL_TRACE("ReferenceProjectRecord - relative path %s", rtl::OUStringToOString( msRelativeLibid, RTL_TEXTENCODING_UTF8 ).getStr() );
-+ return true;
-+}
-+
-+void ReferenceProjectRecord::import( VBA_Impl& rDir )
-+{
-+ rDir.AddProjectReference( msAbsoluteLibid );
-+}
-+
-+class ReferenceRegisteredRecord : public BaseReferenceRecord
-+{
-+public:
-+ sal_uInt16 Id;
-+ sal_uInt32 Size;
-+ sal_uInt32 SizeOfLibid;
-+ sal_uInt8* pLibid;
-+ sal_Int32 Reserved1;
-+ sal_Int16 Reserved2;
-+
-+ ReferenceRegisteredRecord();
-+ ~ReferenceRegisteredRecord();
-+ bool read( SvStream* pStream );
-+};
-+
-+ReferenceRegisteredRecord::ReferenceRegisteredRecord() : Id( 0x000D ), Size( 0 ), SizeOfLibid( 0 ), pLibid( NULL ), Reserved1( 0 ), Reserved2( 0 )
-+{
-+}
-+
-+ReferenceRegisteredRecord::~ReferenceRegisteredRecord()
-+{
-+ if ( pLibid )
-+ {
-+ delete[] pLibid;
-+ }
-+}
-+
-+bool
-+ReferenceRegisteredRecord::read( SvStream* pStream )
-+{
-+ OSL_TRACE("ReferenceRegisteredRecord [0x%x]", pStream->Tell() );
-+ *pStream >> Id >> Size >> SizeOfLibid;
-+ if ( SizeOfLibid )
-+ {
-+ pLibid = new sal_uInt8[ SizeOfLibid ];
-+ OSL_TRACE("ReferenceRegisteredRecord about to read Libid [0x%x]", pStream->Tell() );
-+ pStream->Read( pLibid, SizeOfLibid );
-+ }
-+ *pStream >> Reserved1 >> Reserved2;
-+ return true;
-+}
-+
-+class ReferenceOriginalRecord
-+{
-+public:
-+ sal_uInt16 Id;
-+ sal_uInt32 SizeOfLibOriginal;
-+ sal_uInt8* pLibidOriginal;
-+
-+
-+ReferenceOriginalRecord() : Id( 0x033 ), SizeOfLibOriginal( 0 ), pLibidOriginal( NULL )
-+{
-+}
-+
-+~ReferenceOriginalRecord()
-+{
-+ if ( pLibidOriginal )
-+ delete[] pLibidOriginal;
-+}
-+
-+void read( SvStream* pStream )
-+{
-+ *pStream >> Id >> SizeOfLibOriginal;
-+ if ( SizeOfLibOriginal )
-+ {
-+ pLibidOriginal = new sal_uInt8[ SizeOfLibOriginal ];
-+ pStream->Read( pLibidOriginal, SizeOfLibOriginal );
-+ }
-+}
-+
-+};
-+
-+class ReferenceControlRecord : public BaseReferenceRecord
-+{
-+public:
-+ReferenceOriginalRecord OriginalRecord;
-+sal_Int16 Id;
-+sal_uInt32 SizeTwiddled;
-+sal_uInt32 SizeOfLibidTwiddled;
-+sal_uInt8* LibidTwiddled;
-+sal_uInt32 Reserved1;
-+sal_uInt16 Reserved2;
-+ReferenceNameRecord* NameRecordExtended;// Optional
-+sal_uInt16 Reserved3;
-+sal_uInt32 SizeExtended;
-+sal_uInt32 SizeOfLibidExtended;
-+sal_uInt8* LibidExtended;
-+sal_uInt32 Reserved4;
-+sal_uInt16 Reserved5;
-+sal_uInt8 OriginalTypeLib[ 16 ];
-+sal_uInt32 Cookie;
-+
-+ReferenceControlRecord() : Id( 0x2F ), SizeTwiddled( 0 ), SizeOfLibidTwiddled( 0 ), LibidTwiddled( 0 ), Reserved1( 0 ), Reserved2( 0 ), NameRecordExtended( 0 ), Reserved3( 0x30 ), SizeExtended( 0 ), SizeOfLibidExtended( 0 ), LibidExtended( 0 ), Reserved4( 0 ), Reserved5( 0 ), Cookie( 0 )
-+{
-+ for( int i = 0; i < 16; ++i )
-+ OriginalTypeLib[ i ] = 0;
-+}
-+
-+~ReferenceControlRecord()
-+{
-+ delete LibidTwiddled;
-+ delete NameRecordExtended;
-+ delete [] LibidExtended;
-+ LibidTwiddled = 0;
-+ NameRecordExtended = 0;
-+ LibidExtended = 0;
-+}
-+
-+bool read( SvStream* pStream )
-+{
-+ OSL_TRACE("ReferenceControlRecord [0x%x]", pStream->Tell() );
-+ OriginalRecord.read( pStream );
-+ *pStream >> Id >> SizeTwiddled >> SizeOfLibidTwiddled;
-+
-+ if ( SizeOfLibidTwiddled )
-+ {
-+ LibidTwiddled = new sal_uInt8[ SizeOfLibidTwiddled ];
-+ pStream->Read( LibidTwiddled, SizeOfLibidTwiddled );
-+ }
-+
-+ *pStream >> Reserved1 >> Reserved2;
-+
-+ long nPos = pStream->Tell();
-+ // peek at the id for optional NameRecord
-+ sal_Int16 nTmpId;
-+ *pStream >> nTmpId;
-+ if ( nTmpId == 0x30 )
-+ {
-+ Reserved3 = 0x30;
-+ }
-+ else
-+ {
-+ pStream->Seek( nPos );
-+ NameRecordExtended = new ReferenceNameRecord();
-+ NameRecordExtended->read( pStream );
-+ *pStream >> Reserved3;
-+ }
-+ *pStream >> SizeExtended >> SizeOfLibidExtended;
-+
-+ if ( SizeExtended )
-+ {
-+ LibidExtended = new sal_uInt8[ SizeOfLibidExtended ];
-+ pStream->Read( LibidExtended, SizeOfLibidExtended );
-+ }
-+
-+ *pStream >> Reserved4;
-+ *pStream >> Reserved5;
-+
-+ pStream->Read( OriginalTypeLib, sizeof( OriginalTypeLib ) );
-+ *pStream >> Cookie;
-+ return true;
-+}
-+
-+};
-+
-+class ReferenceRecord : public BaseReferenceRecord
-+{
-+public:
-+// NameRecord is Optional
-+ReferenceNameRecord* NameRecord;
-+BaseReferenceRecord* aReferenceRecord;
-+ReferenceRecord(): NameRecord(0), aReferenceRecord(0) {}
-+~ReferenceRecord()
-+{
-+ if ( NameRecord )
-+ delete NameRecord;
-+ if ( aReferenceRecord )
-+ delete aReferenceRecord;
-+}
-+
-+// false return would mean failed to read Record e.g. end of array encountered
-+// Note: this read routine will make sure the stream is pointing to where it was the
-+// method was called )
-+
-+bool read( SvStream* pStream )
-+{
-+ OSL_TRACE("ReferenceRecord [0x%x]", pStream->Tell() );
-+ bool bRead = true;
-+ long nStart = pStream->Tell();
-+ long nPos = nStart;
-+ // Peek at the ID
-+ sal_Int16 Id;
-+ *pStream >> Id;
-+ pStream->Seek( nPos ); // place back before Id
-+ if ( Id == 0x16 ) // Optional NameRecord
-+ {
-+ NameRecord = new ReferenceNameRecord();
-+ NameRecord->read( pStream );
-+ }
-+ else if ( Id == 0x0f )
-+ {
-+ pStream->Seek( nStart );
-+ bRead = false;
-+ return bRead; // start of module, terminate read
-+ }
-+
-+ nPos = pStream->Tell(); // mark position, peek at next Id
-+ *pStream >> Id;
-+ pStream->Seek( nPos ); // place back before Id
-+
-+ switch( Id )
-+ {
-+ case 0x0D:
-+ aReferenceRecord = new ReferenceRegisteredRecord();
-+ break;
-+ case 0x0E:
-+ aReferenceRecord = new ReferenceProjectRecord();
-+ break;
-+ case 0x2F:
-+ case 0x33:
-+ aReferenceRecord = new ReferenceControlRecord();
-+ break;
-+ default:
-+ bRead = false;
-+ OSL_TRACE("Big fat error, unknown ID 0x%x", Id);
-+ break;
-+ }
-+ if ( bRead )
-+ aReferenceRecord->read( pStream );
-+ return bRead;
-+}
-+
-+void import( VBA_Impl& rVBA )
-+{
-+ if ( aReferenceRecord )
-+ aReferenceRecord->import( rVBA );
-+}
-+
-+};
-+
-+class DirDumper
-+{
-+public:
-+ProjectSysKindRecord mSysKindRec;
-+ProjectLcidRecord mLcidRec;
-+ProjectLcidInvokeRecord mLcidInvokeRec;
-+ProjectCodePageRecord mCodePageRec;
-+ProjectNameRecord mProjectNameRec;
-+ProjectDocStringRecord mDocStringRec;
-+ProjectHelpFilePath mHelpFileRec;
-+ProjectHelpContextRecord mHelpContextRec;
-+ProjectLibFlagsRecord mLibFlagsRec;
-+ProjectVersionRecord mVersionRec;
-+ProjectConstantsRecord mConstantsRecord;
-+std::vector< ReferenceRecord* > ReferenceArray;
-+
-+DirDumper() {}
-+~DirDumper()
-+{
-+ for ( std::vector< ReferenceRecord* >::iterator it = ReferenceArray.begin(); it != ReferenceArray.end(); ++it )
-+ delete *it;
-+
-+}
-+
-+void read( SvStream* pStream )
-+{
-+ sal_Int32 nPos = pStream->Tell();
-+ std::ofstream aDump("dir.dump");
-+ while ( !pStream->IsEof() )
-+ {
-+ sal_Int8 aByte;
-+ *pStream >> aByte;
-+ aDump << aByte;
-+ }
-+ aDump.flush();
-+ pStream->Seek( nPos );
-+ readProjectInformation( pStream );
-+ readProjectReferenceInformation( pStream );
-+}
-+
-+void readProjectReferenceInformation( SvStream* pStream )
-+{
-+ bool bKeepReading = true;
-+ while( bKeepReading )
-+ {
-+ ReferenceRecord* pRef = new ReferenceRecord();
-+ bKeepReading = pRef->read( pStream );
-+ if ( bKeepReading )
-+ ReferenceArray.push_back( pRef );
-+ }
-+}
-+
-+void readProjectInformation( SvStream* pStream )
-+{
-+ mSysKindRec.read( pStream );
-+ mLcidRec.read( pStream );
-+ mLcidInvokeRec.read( pStream );
-+ mCodePageRec.read( pStream );
-+ mProjectNameRec.read( pStream );
-+ mDocStringRec.read( pStream );
-+ mHelpFileRec.read( pStream );
-+ mHelpContextRec.read( pStream );
-+ mLibFlagsRec.read( pStream );
-+ mVersionRec.read( pStream );
-+ sal_Int32 nPos = pStream->Tell();
-+ sal_uInt16 nTmp;
-+ *pStream >> nTmp;
-+ if ( nTmp == 0x0C )
-+ {
-+ pStream->Seek( nPos );
-+ mConstantsRecord.read( pStream );
-+ }
-+ OSL_TRACE("After Information pos is 0x%x", pStream->Tell() );
-+}
-+
-+void import( VBA_Impl& rVBA )
-+{
-+ // get project references
-+ for ( std::vector< ReferenceRecord* >::iterator it = ReferenceArray.begin(); it != ReferenceArray.end(); ++it )
-+ (*it)->import( rVBA );
-+ rVBA.SetProjectName( mProjectNameRec.msProjectName );
-+
-+}
-+};
-+
-+
- /*
- A few urls which may in the future be of some use
- http://www.virusbtn.com/vb2000/Programme/papers/bontchev.pdf
-@@ -155,7 +1075,17 @@ int VBA_Impl::ReadVBAProject(const SvSto
- xVBAProject = rxVBAStorage->OpenSotStream(
- String( RTL_CONSTASCII_USTRINGPARAM( "_VBA_PROJECT" ) ),
- STREAM_STD_READ | STREAM_NOCREATE );
--
-+ // read Dir stream
-+ SvStorageStreamRef xDir = rxVBAStorage->OpenSotStream(
-+ String( RTL_CONSTASCII_USTRINGPARAM( "dir" ) ),
-+ STREAM_STD_READ | STREAM_NOCREATE );
-+ // decompress the stream
-+ std::auto_ptr< SvMemoryStream > xCmpDir;
-+ xCmpDir.reset( MSLZSS::decompressAsStream( xDir, 0 ) );
-+ // try to parse the dir stream
-+ DirDumper dDump;
-+ dDump.read( xCmpDir.get() );
-+ dDump.import( *this );
- if( !xVBAProject.Is() || SVSTREAM_OK != xVBAProject->GetError() )
- {
- DBG_WARNING("Not able to find vba project, cannot find macros");
-@@ -455,6 +1385,7 @@ bool VBA_Impl::Open( const String &rTopl
- if( !xMacros.Is() || SVSTREAM_OK != xMacros->GetError() )
- {
- DBG_WARNING("No Macros Storage");
-+ OSL_TRACE("No Macros Storage");
- }
- else
- {
-@@ -464,6 +1395,7 @@ bool VBA_Impl::Open( const String &rTopl
- if( !xVBA.Is() || SVSTREAM_OK != xVBA->GetError() )
- {
- DBG_WARNING("No Visual Basic in Storage");
-+ OSL_TRACE("No Visual Basic in Storage");
- }
- else
- {
-@@ -478,6 +1410,7 @@ bool VBA_Impl::Open( const String &rTopl
- * ( value ) is either a Class Module, Form Module or a plain VB Module. */
- SvStorageStreamRef xProject = xMacros->OpenSotStream(
- String( RTL_CONSTASCII_USTRINGPARAM( "PROJECT" ) ) );
-+
- SvStorageStream* pStp = xProject;
- UniString tmp;
- static const String sThisDoc( RTL_CONSTASCII_USTRINGPARAM( "ThisDocument" ) );
---- svx/source/msfilter/msvbasic.hxx.old 2009-04-06 16:41:59.000000000 +0000
-+++ svx/source/msfilter/msvbasic.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -97,9 +97,14 @@ public:
- //
- // #117718# member map of module names to types of module
- ModType GetModuleType( const UniString& rModuleName );
--
-- std::vector<String> maReferences;
-+ rtl::OUString& ProjectName() { return msProjectName; }
-+ void SetProjectName( const rtl::OUString& rPName ) { msProjectName = rPName; }
-+ const std::vector<rtl::OUString>& ProjectReferences() { return maPrjReferences; }
-+ void AddProjectReference( const rtl::OUString& rProject ) { maPrjReferences.push_back( rProject); }
-+ SvStorage* GetStorage() { return xStor; }
- private:
-+ std::vector<rtl::OUString> maReferences;
-+ std::vector<rtl::OUString> maPrjReferences;
- struct VBAOffset_Impl
- {
- String sName;
-@@ -125,6 +130,7 @@ private:
- int ReadVBAProject(const SvStorageRef &rxVBAStorage);
- int DecompressVBA(int index, SvStorageStreamRef &rxVBAStream);
- sal_uInt8 ReadPString(SvStorageStreamRef &xVBAProject, bool bIsUnicode);
-+ rtl::OUString msProjectName;
- };
-
- #endif
---- svx/source/msfilter/svxmsbas.cxx.old 2009-04-06 16:42:00.000000000 +0000
-+++ svx/source/msfilter/svxmsbas.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -83,6 +83,7 @@ int SvxImportMSVBasic::Import( const Str
- const String &rSubStorageName,
- BOOL bAsComment, BOOL bStripped )
- {
-+ msProjectName = rtl::OUString();
- int nRet = 0;
- if( bImport && ImportCode_Impl( rStorageName, rSubStorageName,
- bAsComment, bStripped ))
-@@ -100,7 +101,42 @@ int SvxImportMSVBasic::Import( const Str
- bool SvxImportMSVBasic::ImportForms_Impl(const String& rStorageName,
- const String& rSubStorageName, BOOL bVBAMode )
- {
-- SvStorageRef xVBAStg(xRoot->OpenSotStorage(rStorageName,
-+ BOOL bRet = FALSE;
-+ // #FIXME VBA_Impl ( or some other new class ) should handle both userforms
-+ // and code
-+ VBA_Impl aVBA( *xRoot, TRUE );
-+ // This call is a waste we read the source ( again ) only to get the refereneces
-+ // *AGAIN*, we really need to rewrite all of this
-+ aVBA.Open( rStorageName, rSubStorageName );
-+
-+ bRet = ImportForms_Impl( aVBA, rStorageName, rSubStorageName, bVBAMode );
-+ std::vector<rtl::OUString> sProjectRefs = aVBA.ProjectReferences();
-+
-+ for ( std::vector<rtl::OUString>::iterator it = sProjectRefs.begin(); it != sProjectRefs.end(); ++it )
-+ {
-+ rtl::OUString sFileName = *it;
-+#ifndef WIN
-+#ifdef DEBUG
-+ // hacky test code to read referenced projects on linux
-+ sal_Int32 nPos = (*it).lastIndexOf('\\');
-+ sFileName = (*it).copy( nPos + 1 );
-+ sFileName = rtl::OUString::createFromAscii("~/Documents/") + sFileName;
-+#endif
-+#endif
-+ SotStorageRef rRoot = new SotStorage( sFileName, STREAM_STD_READWRITE, STORAGE_TRANSACTED );
-+ VBA_Impl refVBA( *rRoot, TRUE );
-+ refVBA.Open( rStorageName, rSubStorageName );
-+ // The return from ImportForms doesn't indicate and error ( it could )
-+ // but also it just means no userforms were imported
-+ if ( ImportForms_Impl( refVBA, rStorageName, rSubStorageName, bVBAMode ) )
-+ bRet = true; // mark that at least on userform was imported
-+ }
-+ return bRet;
-+}
-+
-+bool SvxImportMSVBasic::ImportForms_Impl( VBA_Impl& rVBA, const String& rStorageName, const String& rSubStorageName, BOOL bVBAMode )
-+{
-+ SvStorageRef xVBAStg(rVBA.GetStorage()->OpenSotStorage(rStorageName,
- STREAM_READWRITE | STREAM_NOCREATE | STREAM_SHARE_DENYALL));
- if (!xVBAStg.Is() || xVBAStg->GetError())
- return false;
-@@ -133,6 +169,10 @@ bool SvxImportMSVBasic::ImportForms_Impl
- DBG_ASSERT( xLibContainer.is(), "No BasicContainer!" );
-
- String aLibName( RTL_CONSTASCII_USTRINGPARAM( "Standard" ) );
-+
-+ if (rVBA.ProjectName().getLength() )
-+ aLibName = rVBA.ProjectName();
-+ OSL_TRACE( "userformage lib name %s", rtl::OUStringToOString( aLibName, RTL_TEXTENCODING_UTF8 ).getStr() );
- Reference<XNameContainer> xLib;
- if (xLibContainer.is())
- {
-@@ -260,17 +300,55 @@ BOOL SvxImportMSVBasic::ImportCode_Impl(
- {
- BOOL bRet = FALSE;
- VBA_Impl aVBA( *xRoot, bAsComment );
-+
- if( aVBA.Open(rStorageName,rSubStorageName) )
- {
-+ msProjectName = aVBA.ProjectName();
-+
-+ if ( msProjectName.getLength() )
-+ rDocSh.GetBasicManager()->SetName( msProjectName ); // set name of Project
-+
-+ bRet = ImportCode_Impl( aVBA, bAsComment, bStripped );
-+ std::vector<rtl::OUString> sProjectRefs = aVBA.ProjectReferences();
-+
-+ for ( std::vector<rtl::OUString>::iterator it = sProjectRefs.begin(); it != sProjectRefs.end(); ++it )
-+ {
-+ rtl::OUString sFileName = *it;
-+#ifndef WIN
-+#ifdef DEBUG
-+ // hacky test code to read referenced projects on linux
-+ sal_Int32 nPos = (*it).lastIndexOf('\\');
-+ sFileName = (*it).copy( nPos + 1 );
-+ sFileName = rtl::OUString::createFromAscii("~/Documents/") + sFileName;
-+#endif
-+#endif
-+ OSL_TRACE("referenced project %s ", rtl::OUStringToOString( sFileName, RTL_TEXTENCODING_UTF8 ).getStr() );
-+ SotStorageRef rRoot = new SotStorage( sFileName, STREAM_STD_READWRITE, STORAGE_TRANSACTED );
-+ VBA_Impl refVBA( *rRoot, bAsComment );
-+ if( refVBA.Open(rStorageName,rSubStorageName) && ImportCode_Impl( refVBA, bAsComment, bStripped ) )
-+ bRet = TRUE; // mark that some code was imported
-+ }
-+ }
-+ return bRet;
-+}
-+
-+BOOL SvxImportMSVBasic::ImportCode_Impl( VBA_Impl& aVBA, BOOL bAsComment, BOOL bStripped )
-+{
-+ BOOL bRet = FALSE;
- SFX_APP()->EnterBasicCall();
- Reference<XLibraryContainer> xLibContainer = rDocSh.GetBasicContainer();
- DBG_ASSERT( xLibContainer.is(), "No BasicContainer!" );
-
- UINT16 nStreamCount = aVBA.GetNoStreams();
- Reference<XNameContainer> xLib;
-+
-+ String aLibName( RTL_CONSTASCII_USTRINGPARAM( "Standard" ) );
-+
- if( xLibContainer.is() && nStreamCount )
- {
-- String aLibName( RTL_CONSTASCII_USTRINGPARAM( "Standard" ) );
-+ if ( aVBA.ProjectName().getLength() )
-+ aLibName = aVBA.ProjectName();
-+
- if( !xLibContainer->hasByName( aLibName ) )
- xLibContainer->createLibrary( aLibName );
-
-@@ -282,7 +360,7 @@ BOOL SvxImportMSVBasic::ImportCode_Impl(
- Reference< container::XNameAccess > xVBAObjectForCodeName;
- if ( !bAsComment )
- {
-- rDocSh.GetBasic()->SetVBAEnabled( true );
-+ rDocSh.GetBasicManager()->GetLib( aLibName )->SetVBAEnabled( true );
- Reference< XMultiServiceFactory> xSF(rDocSh.GetModel(), UNO_QUERY);
- if ( xSF.is() )
- {
-@@ -483,7 +561,6 @@ BOOL SvxImportMSVBasic::ImportCode_Impl(
- }
- if( bRet )
- SFX_APP()->LeaveBasicCall();
-- }
- return bRet;
- }
-
---- sw/inc/unocoll.hxx.old 2009-04-02 10:50:57.000000000 +0000
-+++ sw/inc/unocoll.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -194,8 +194,10 @@ class SwUnoCollection
- #define SW_SERVICE_CHART2_DATA_PROVIDER 106
- #define SW_SERVICE_TYPE_FIELDMARK 107
- #define SW_SERVICE_TYPE_FORMFIELDMARK 108
-+#define SW_SERVICE_VBAOBJECTPROVIDER 109
-+#define SW_SERVICE_VBACODENAMEPROVIDER 110
-
--#define SW_SERVICE_LAST SW_SERVICE_TYPE_FORMFIELDMARK
-+#define SW_SERVICE_LAST SW_SERVICE_VBACODENAMEPROVIDER
-
- #define SW_SERVICE_INVALID USHRT_MAX
-
---- sw/prj/build.lst
-+++ sw/prj/build.lst
-@@ -1,4 +1,4 @@
--sw sw : l10n connectivity OOo:writerperfect OOo:lotuswordpro svx stoc uui writerfilter NULL
-+sw sw : l10n connectivity OOo:writerperfect OOo:lotuswordpro svx stoc uui writerfilter vbahelper NULL
- sw sw usr1 - all sw_mkout NULL
- sw sw\inc nmake - all sw_inc NULL
- sw sw\uiconfig\layout nmake - all sw_layout NULL
-@@ -33,6 +33,7 @@ sw sw\source\ui\smartmenu
- sw sw\source\ui\table nmake - all sw_table sw_inc NULL
- sw sw\source\ui\uiview nmake - all sw_uivw sw_sdi sw_inc NULL
- sw sw\source\ui\uno nmake - all sw_uiuno sw_sdi sw_inc NULL
-+sw sw\source\ui\vba nmake - all sw_vba sw_inc NULL
- sw sw\source\ui\utlui nmake - all sw_utlui sw_inc NULL
- sw sw\source\ui\web nmake - all sw_web sw_uinc sw_sdi sw_inc NULL
- sw sw\source\ui\wrtsh nmake - all sw_wrtsh sw_inc NULL
-@@ -69,7 +70,7 @@ sw sw\source\filter\writer
- sw sw\source\filter\ww1 nmake - all sw_ww1 sw_inc NULL
- sw sw\source\filter\ww8 nmake - all sw_ww8 sw_inc NULL
- sw sw\source\filter\xml nmake - all sw_xml sw_inc NULL
--sw sw\source\ui nmake - all sw_ui sw_app sw_cctrl sw_chrdl sw_conf sw_dbui sw_dchdl sw_dcvw sw_dlg sw_envlp sw_fldui sw_fmtui sw_frmdl sw_globd sw_index sw_ling sw_misc sw_rbbar sw_shell sw_table sw_uiuno sw_uivw sw_utlui sw_web sw_wrtsh sw_smartmenu NULL
-+sw sw\source\ui nmake - all sw_ui sw_app sw_cctrl sw_chrdl sw_conf sw_dbui sw_dchdl sw_dcvw sw_dlg sw_envlp sw_fldui sw_fmtui sw_frmdl sw_globd sw_index sw_ling sw_misc sw_rbbar sw_shell sw_table sw_uiuno sw_uivw sw_utlui sw_web sw_wrtsh sw_smartmenu sw_vba NULL
- sw sw\source\core nmake - all sw_core sw_attr sw_bast sw_crsr sw_dcnd sw_doc sw_draw sw_edit sw_excpt sw_fld sw_frmed sw_grph sw_layo sw_ole sw_para sw_sw3io sw_swg sw_text sw_tox sw_txtnd sw_uco sw_undo sw_view sw_acc sw_objpos sw_NumberTree sw_tablecore NULL
- sw sw\source\filter nmake - all sw_flt sw_ascii sw_bsflt sw_html sw_rtf sw_wrtr sw_ww1 sw_ww8 sw_xml NULL
- sw sw\util nmake - all sw_util sw_core sw_flt sw_sdi sw_ui NULL
---- sw/prj/d.lst.old 2009-04-02 10:50:58.000000000 +0000
-+++ sw/prj/d.lst 2009-04-06 16:42:01.000000000 +0000
-@@ -63,6 +63,7 @@ mkdir: %_DEST%\xml%_EXT%\uiconfig\module
- ..\%__SRC%\bin\swd?????.dll %_DEST%\bin%_EXT%\swd?????.dll
- ..\%__SRC%\bin\swui?????.dll %_DEST%\bin%_EXT%\swui?????.dll
- ..\%__SRC%\bin\msword?????.dll %_DEST%\bin%_EXT%\msword?????.dll
-+..\%__SRC%\bin\vbaswobj*.dll %_DEST%\bin%_EXT%\vbaswobj*.dll
- ..\%__SRC%\bin\sw*.res %_DEST%\bin%_EXT%\sw*.res
- ..\%__SRC%\lib\lib*.* %_DEST%\lib%_EXT%\lib*.*
-
---- sw/source/core/unocore/unocoll.cxx
-+++ sw/source/core/unocore/unocoll.cxx
-@@ -73,7 +73,14 @@
- #include <iterator>
-
- #include "docsh.hxx"
--
-+#include <com/sun/star/document/XCodeNameQuery.hpp>
-+#include <com/sun/star/drawing/XDrawPageSupplier.hpp>
-+#include <com/sun/star/form/XFormsSupplier.hpp>
-+#include <com/sun/star/script/ModuleInfo.hpp>
-+#include <com/sun/star/script/ModuleType.hpp>
-+#include <com/sun/star/script/ScriptEventDescriptor.hpp>
-+#include <vbahelper/vbahelper.hxx>
-+#include <basic/basmgr.hxx>
- using ::rtl::OUString;
- using namespace ::com::sun::star;
- using namespace ::com::sun::star::document;
-@@ -82,6 +89,119 @@ using namespace ::com::sun::star::text;
- using namespace ::com::sun::star::container;
- using namespace ::com::sun::star::lang;
-
-+class SwVbaCodeNameProvider : public ::cppu::WeakImplHelper1< document::XCodeNameQuery >
-+{
-+ SwDocShell* mpDocShell;
-+ rtl::OUString msThisDocumentCodeName;
-+public:
-+ SwVbaCodeNameProvider( SwDocShell* pDocShell ) : mpDocShell( pDocShell ) {}
-+ // XCodeNameQuery
-+ rtl::OUString SAL_CALL getCodeNameForObject( const uno::Reference< uno::XInterface >& xIf ) throw( uno::RuntimeException )
-+ {
-+ // Initialise the code name
-+ if ( msThisDocumentCodeName.getLength() == 0 )
-+ {
-+ try
-+ {
-+ uno::Reference< beans::XPropertySet > xProps( mpDocShell->GetModel(), uno::UNO_QUERY_THROW );
-+ uno::Reference< container::XNameAccess > xLibContainer( xProps->getPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("BasicLibraries") ) ), uno::UNO_QUERY_THROW );
-+ rtl::OUString sProjectName( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("Standard") ) );
-+ if ( mpDocShell->GetBasicManager()->GetName().Len() )
-+ sProjectName = mpDocShell->GetBasicManager()->GetName();
-+
-+ uno::Reference< container::XNameAccess > xStandard( xLibContainer->getByName( sProjectName ), uno::UNO_QUERY_THROW );
-+ uno::Sequence< rtl::OUString > sModuleNames = xStandard->getElementNames();
-+ for ( sal_Int32 i=0; i < sModuleNames.getLength(); ++i )
-+ {
-+ script::ModuleInfo mInfo;
-+ if ( xStandard->getByName( sModuleNames[ i ] ) >>= mInfo )
-+ {
-+ if ( mInfo.ModuleType == script::ModuleType::Document )
-+ {
-+ msThisDocumentCodeName = sModuleNames[ i ];
-+ break;
-+ }
-+ }
-+ }
-+ }
-+ catch( uno::Exception& )
-+ {
-+ }
-+ }
-+ rtl::OUString sCodeName;
-+ if ( mpDocShell )
-+ {
-+ OSL_TRACE( "*** In ScVbaCodeNameProvider::getCodeNameForObject");
-+ // need to find the page ( and index ) for this control
-+ uno::Reference< drawing::XDrawPageSupplier > xSupplier( mpDocShell->GetModel(), uno::UNO_QUERY_THROW );
-+ uno::Reference< container::XIndexAccess > xIndex( xSupplier->getDrawPage(), uno::UNO_QUERY_THROW );
-+ sal_Int32 nLen = xIndex->getCount();
-+ bool bMatched = false;
-+ uno::Sequence< script::ScriptEventDescriptor > aFakeEvents;
-+ try
-+ {
-+ uno::Reference< form::XFormsSupplier > xFormSupplier( xIndex, uno::UNO_QUERY_THROW );
-+ uno::Reference< container::XIndexAccess > xFormIndex( xFormSupplier->getForms(), uno::UNO_QUERY_THROW );
-+ // get the www-standard container
-+ uno::Reference< container::XIndexAccess > xFormControls( xFormIndex->getByIndex(0), uno::UNO_QUERY_THROW );
-+ sal_Int32 nCntrls = xFormControls->getCount();
-+ for( sal_Int32 cIndex = 0; cIndex < nCntrls; ++cIndex )
-+ {
-+ uno::Reference< uno::XInterface > xControl( xFormControls->getByIndex( cIndex ), uno::UNO_QUERY_THROW );
-+ bMatched = ( xControl == xIf );
-+ if ( bMatched )
-+ {
-+ sCodeName = msThisDocumentCodeName;
-+ break;
-+ }
-+ }
-+ }
-+ catch( uno::Exception& ) {}
-+ }
-+ // Probably should throw here ( if !bMatched )
-+ return sCodeName;
-+ }
-+};
-+
-+class SwVbaObjectForCodeNameProvider : public ::cppu::WeakImplHelper1< container::XNameAccess >
-+{
-+ SwDocShell* mpDocShell;
-+public:
-+ SwVbaObjectForCodeNameProvider( SwDocShell* pDocShell ) : mpDocShell( pDocShell )
-+ {
-+ // #FIXME #TODO is the code name for ThisDocument read anywhere?
-+ }
-+
-+ virtual ::sal_Bool SAL_CALL hasByName( const ::rtl::OUString& aName ) throw (::com::sun::star::uno::RuntimeException )
-+ {
-+ // #FIXME #TODO we really need to be checking against the codename for
-+ // ThisDocument
-+ if ( aName.equals( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ThisDocument" ) ) ) )
-+ return sal_True;
-+ return sal_False;
-+ }
-+ ::com::sun::star::uno::Any SAL_CALL getByName( const ::rtl::OUString& aName ) throw (::com::sun::star::container::NoSuchElementException, ::com::sun::star::lang::WrappedTargetException, ::com::sun::star::uno::RuntimeException)
-+ {
-+ if ( !hasByName( aName ) )
-+ throw container::NoSuchElementException();
-+ uno::Sequence< uno::Any > aArgs( 2 );
-+ aArgs[0] = uno::Any( uno::Reference< uno::XInterface >() );
-+ aArgs[1] = uno::Any( mpDocShell->GetModel() );
-+ uno::Reference< uno::XInterface > xDocObj = ov::createVBAUnoAPIServiceWithArgs( mpDocShell, "ooo.vba.word.Document" , aArgs );
-+ OSL_TRACE("Creating Object ( ooo.vba.word.Document ) 0x%x", xDocObj.get() );
-+ return uno::makeAny( xDocObj );
-+ }
-+ virtual ::com::sun::star::uno::Sequence< ::rtl::OUString > SAL_CALL getElementNames( ) throw (::com::sun::star::uno::RuntimeException)
-+ {
-+ uno::Sequence< rtl::OUString > aNames;
-+ return aNames;
-+ }
-+ // XElemenAccess
-+ virtual ::com::sun::star::uno::Type SAL_CALL getElementType( ) throw (::com::sun::star::uno::RuntimeException){ return uno::Type(); }
-+ virtual ::sal_Bool SAL_CALL hasElements( ) throw (::com::sun::star::uno::RuntimeException ) { return sal_True; }
-+
-+};
-+
- /******************************************************************************
- *
- ******************************************************************************/
-@@ -203,6 +323,8 @@ const ProvNamesId_Type __FAR_DATA aProvN
- { "com.sun.star.chart2.data.DataProvider", SW_SERVICE_CHART2_DATA_PROVIDER },
- { "com.sun.star.text.Fieldmark", SW_SERVICE_TYPE_FIELDMARK },
- { "com.sun.star.text.FormFieldmark", SW_SERVICE_TYPE_FORMFIELDMARK },
-+ { "ooo.vba.VBAObjectModuleObjectProvider", SW_SERVICE_VBAOBJECTPROVIDER },
-+ { "ooo.vba.VBACodeNameProvider", SW_SERVICE_VBACODENAMEPROVIDER },
-
- // case-correct versions of the service names (see #i67811)
- { CSS_TEXT_TEXTFIELD_DATE_TIME, SW_SERVICE_FIELDTYPE_DATETIME },
-@@ -383,6 +505,18 @@ uno::Reference< uno::XInterface > SwXS
- xRet = (cppu::OWeakObject*)pFieldmark;
- }
- break;
-+ case SW_SERVICE_VBAOBJECTPROVIDER :
-+ {
-+ SwVbaObjectForCodeNameProvider* pObjProv = new SwVbaObjectForCodeNameProvider( pDoc->GetDocShell() );
-+ xRet = (cppu::OWeakObject*)pObjProv;
-+ }
-+ break;
-+ case SW_SERVICE_VBACODENAMEPROVIDER :
-+ {
-+ SwVbaCodeNameProvider* pObjProv = new SwVbaCodeNameProvider( pDoc->GetDocShell() );
-+ xRet = (cppu::OWeakObject*)pObjProv;
-+ }
-+ break;
- case SW_SERVICE_TYPE_FOOTNOTE :
- xRet = (cppu::OWeakObject*)new SwXFootnote(sal_False);
- break;
---- sw/source/filter/ww8/ww8par.cxx.old 2009-04-06 16:42:00.000000000 +0000
-+++ sw/source/filter/ww8/ww8par.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -132,6 +132,9 @@
- #include <svtools/itemiter.hxx> //SfxItemIter
-
- #include <stdio.h>
-+#include <comphelper/processfactory.hxx>
-+#include <basic/basmgr.hxx>
-+
- #include "ww8toolbar.hxx"
- #ifdef DEBUG
- #include <iostream>
-@@ -146,6 +149,76 @@ using namespace sw::util;
- using namespace sw::types;
- using namespace nsHdFtFlags;
-
-+#include <vbahelper/vbahelper.hxx>
-+#include <com/sun/star/document/XEventsSupplier.hpp>
-+#include <com/sun/star/container/XNameReplace.hpp>
-+#include <com/sun/star/frame/XModel.hpp>
-+const static String sModule( RTL_CONSTASCII_USTRINGPARAM("ThisDocument"));
-+
-+const static rtl::OUString sUrlPart0 = rtl::OUString::createFromAscii( "vnd.sun.star.script:");
-+const static rtl::OUString sUrlPart1 = rtl::OUString::createFromAscii( "vnd.sun.star.script:Standard.");
-+const static rtl::OUString sUrlPart2 = rtl::OUString::createFromAscii( "?language=Basic&location=document");
-+
-+struct DocEventNameTable
-+{
-+ const sal_Char* sEventName;
-+ const sal_Char* sMacroName;
-+};
-+
-+const DocEventNameTable aEventNameTable[] =
-+{
-+ {"OnNew", "Document_New"},
-+ {"OnLoad", "Document_Open"},
-+ {"OnPrepareUnload", "Document_Close"},
-+ {NULL, NULL}
-+};
-+
-+bool registerDocEvent( SfxObjectShell* pShell )
-+{
-+ bool result = false;
-+ const static rtl::OUString sEvtType( RTL_CONSTASCII_USTRINGPARAM("EventType") );
-+ const static rtl::OUString sScript( RTL_CONSTASCII_USTRINGPARAM("Script") );
-+ uno::Reference< document::XEventsSupplier > xEvtSupplier( pShell->GetModel(), uno::UNO_QUERY );
-+ if( !xEvtSupplier.is() )
-+ return result;
-+ uno::Reference< container::XNameReplace > xEvts( xEvtSupplier->getEvents(), uno::UNO_QUERY );
-+ if ( xEvts.is() )
-+ {
-+ for( const DocEventNameTable* pTable = aEventNameTable; pTable->sEventName != NULL; pTable++ )
-+ {
-+ rtl::OUString sEvt = rtl::OUString::createFromAscii( pTable->sEventName );
-+ rtl::OUString sMacroName = rtl::OUString::createFromAscii( pTable->sMacroName );
-+ // fail to search the macro if the module is not specified.
-+ String sFullPath = ooo::vba::docMacroExists( pShell, sModule, sMacroName );
-+ if( sFullPath.Len() == 0 )
-+ continue;
-+
-+ uno::Sequence< beans::PropertyValue > aEvents;
-+ xEvts->getByName( sEvt ) >>= aEvents;
-+ uno::Sequence< beans::PropertyValue > aOpenEvt( 2 );
-+ aOpenEvt[ 0 ].Name = sEvtType;
-+ aOpenEvt[ 0 ].Value = uno::makeAny(sScript);
-+ aOpenEvt[ 1 ].Name = sScript;
-+ rtl::OUString sUrl = sUrlPart0.concat( sFullPath ).concat( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM(".") ) ).concat( sUrlPart2 );
-+ aOpenEvt[ 1 ].Value = uno::makeAny(sUrl);
-+ sal_Int32 nPos = aEvents.getLength();
-+
-+ sal_Int32 nNewSize = aEvents.getLength() + aOpenEvt.getLength();
-+ if ( nNewSize > aEvents.getLength() )
-+ aEvents.realloc( nNewSize );
-+
-+ for ( sal_Int32 nIndex = nPos, nCpyIndex = 0; nIndex<nNewSize; nIndex++, nCpyIndex++ )
-+ aEvents[ nIndex ] = aOpenEvt[ nCpyIndex ];
-+
-+ uno::Any aParam = uno::makeAny( aEvents );
-+
-+ xEvts->replaceByName( sEvt, aParam );
-+ result = true;
-+ }
-+ }
-+ return result;
-+}
-+
-
- SwMSDffManager::SwMSDffManager( SwWW8ImplReader& rRdr )
- : SvxMSDffManager(*rRdr.pTableStream, rRdr.GetBaseURL(), rRdr.pWwFib->fcDggInfo,
-@@ -3904,7 +3977,52 @@ ULONG SwWW8ImplReader::CoreLoad(WW8Gloss
- }
- else //ordinary case
- {
-+ if (mbNewDoc && pStg && !pGloss) /*meaningless for a glossary, cmc*/
-+ {
-+ const SvtFilterOptions* pVBAFlags = SvtFilterOptions::Get();
-+ maTracer.EnterEnvironment(sw::log::eMacros);
-+ // Create and insert Excel vba Globals
-+ uno::Any aGlobs;
-+ aGlobs <<= ::comphelper::getProcessServiceFactory()->createInstance( ::rtl::OUString::createFromAscii( "ooo.vba.word.Globals") );
-+ mpDocShell->GetBasicManager()->SetGlobalUNOConstant( "VBAGlobals", aGlobs );
-+
-+ SvxImportMSVBasic aVBasic(*mpDocShell, *pStg,
-+ pVBAFlags->IsLoadWordBasicCode(),
-+ pVBAFlags->IsLoadWordBasicStorage() );
-+ String s1(CREATE_CONST_ASC("Macros"));
-+ String s2(CREATE_CONST_ASC("VBA"));
-+ int nRet = aVBasic.Import( s1, s2, ! pVBAFlags->IsLoadWordBasicCode() );
-+ // Read custom toolbars
-+ if ( pWwFib->lcbCmds )
-+ {
-+ // there is a tgc255 structure
-+ long nCur = pTableStream->Tell();
-+ Tcg aTCG;
-+ pTableStream->Seek( pWwFib->fcCmds ); // point at tgc record
-+ if (!aTCG.Read( pTableStream ) )
-+ OSL_TRACE("** Read of Customization data failed!!!! ");
-+ pTableStream->Seek( nCur ); // return to previous position, is that necessary?
-+#if DEBUG
-+ aTCG.Print( stderr );
-+#endif
-+ aTCG.ImportCustomToolBar( *mpDocShell );
-+ }
-+ if( 2 & nRet )
-+ {
-+ maTracer.Log(sw::log::eContainsVisualBasic);
-+ rDoc.SetContainsMSVBasic(true);
-+ }
-+
-+ StoreMacroCmds();
-+
-+ // Hackly to register the document event.
-+ // should be find a better solution to share the codes with Excel Workbook event.
-+ registerDocEvent( mpDocShell );
-+
-+ maTracer.LeaveEnvironment(sw::log::eMacros);
-+ }
- ReadText(0, pWwFib->ccpText, MAN_MAINTEXT);
-+
- }
-
- ::SetProgressState(nProgress, mpDocShell); // Update
-@@ -3978,41 +4096,6 @@ ULONG SwWW8ImplReader::CoreLoad(WW8Gloss
- eMode |= nsRedlineMode_t::REDLINE_ON;
- if( pWDop->fRMView )
- eMode |= nsRedlineMode_t::REDLINE_SHOW_DELETE;
-- if (pStg && !pGloss) /*meaningless for a glossary, cmc*/
-- {
-- // Read custom toolbars
-- if ( pWwFib->lcbCmds )
-- {
-- // there is a tgc255 structure
-- long nCur = pTableStream->Tell();
-- Tcg aTCG;
-- pTableStream->Seek( pWwFib->fcCmds ); // point at tgc record
-- if (!aTCG.Read( pTableStream ) )
-- OSL_TRACE("** Read of Customization data failed!!!! ");
-- pTableStream->Seek( nCur ); // return to previous position, is that necessary?
--#if DEBUG
-- aTCG.Print( stderr );
--#endif
-- aTCG.ImportCustomToolBar( mpDocShell->GetModel() );
-- }
-- const SvtFilterOptions* pVBAFlags = SvtFilterOptions::Get();
-- maTracer.EnterEnvironment(sw::log::eMacros);
-- SvxImportMSVBasic aVBasic(*mpDocShell, *pStg,
-- pVBAFlags->IsLoadWordBasicCode(),
-- pVBAFlags->IsLoadWordBasicStorage() );
-- String s1(CREATE_CONST_ASC("Macros"));
-- String s2(CREATE_CONST_ASC("VBA"));
-- int nRet = aVBasic.Import( s1, s2 );
-- if( 2 & nRet )
-- {
-- maTracer.Log(sw::log::eContainsVisualBasic);
-- rDoc.SetContainsMSVBasic(true);
-- }
--
-- StoreMacroCmds();
--
-- maTracer.LeaveEnvironment(sw::log::eMacros);
-- }
- }
-
- maInsertedTables.DelAndMakeTblFrms();
---- sw/source/filter/ww8/ww8toolbar.cxx.old 2009-04-06 16:42:00.000000000 +0000
-+++ sw/source/filter/ww8/ww8toolbar.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -154,14 +154,14 @@ void CTBWrapper::Print( FILE* fp )
- }
- }
-
--bool CTBWrapper::ImportCustomToolBar( const uno::Reference< css::frame::XModel >& rxModel )
-+bool CTBWrapper::ImportCustomToolBar( SfxObjectShell& rDocSh )
- {
-
- for ( std::vector< Customization >::iterator it = rCustomizations.begin(); it != rCustomizations.end(); ++it )
- {
- uno::Reference< lang::XMultiServiceFactory > xMSF( ::comphelper::getProcessServiceFactory(), uno::UNO_QUERY_THROW );
- uno::Reference< ui::XModuleUIConfigurationManagerSupplier > xAppCfgSupp( xMSF->createInstance( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "com.sun.star.ui.ModuleUIConfigurationManagerSupplier" ) ) ), uno::UNO_QUERY_THROW );
-- CustomToolBarImportHelper helper( rxModel, xAppCfgSupp->getUIConfigurationManager( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("com.sun.star.text.TextDocument" ) ) ) );
-+ CustomToolBarImportHelper helper( rDocSh, xAppCfgSupp->getUIConfigurationManager( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("com.sun.star.text.TextDocument" ) ) ) );
- helper.setMSOCommandMap( new MSOWordCommandConvertor() );
- if ( !(*it).ImportCustomToolBar( helper ) )
- return false;
-@@ -538,9 +538,9 @@ void Tcg::Print( FILE* fp )
- tcg->Print( fp );
- }
-
--bool Tcg::ImportCustomToolBar( const uno::Reference< frame::XModel >& rxModel )
-+bool Tcg::ImportCustomToolBar( SfxObjectShell& rDocSh )
- {
-- return tcg->ImportCustomToolBar( rxModel );
-+ return tcg->ImportCustomToolBar( rDocSh );
- }
-
- Tcg255::Tcg255()
-@@ -601,7 +601,7 @@ bool Tcg255::processSubStruct( sal_uInt8
- return true;
- }
-
--bool Tcg255::ImportCustomToolBar( const uno::Reference< css::frame::XModel >& rxModel )
-+bool Tcg255::ImportCustomToolBar( SfxObjectShell& rDocSh )
- {
- // Find the CTBWrapper
- for ( std::vector< Tcg255SubStruct* >::const_iterator it = rgtcgData.begin(); it != rgtcgData.end(); ++it )
-@@ -612,7 +612,7 @@ bool Tcg255::ImportCustomToolBar( const
- CTBWrapper* pCTBWrapper = dynamic_cast< CTBWrapper* > ( *it );
- if ( pCTBWrapper )
- {
-- if ( !pCTBWrapper->ImportCustomToolBar( rxModel ) )
-+ if ( !pCTBWrapper->ImportCustomToolBar( rDocSh ) )
- return false;
- }
- }
---- sw/source/filter/ww8/ww8toolbar.hxx.old 2009-04-06 16:42:00.000000000 +0000
-+++ sw/source/filter/ww8/ww8toolbar.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -117,6 +117,8 @@ public:
- void Print( FILE* );
- };
-
-+class SfxObjectShell;
-+
- class CTBWrapper : public Tcg255SubStruct
- {
- // reserved1 is the ch field of Tcg255SubStruct
-@@ -139,7 +141,7 @@ public:
- CTBWrapper( bool bReadId = true );
- ~CTBWrapper();
- bool Read(SvStream *pS);
-- bool ImportCustomToolBar( const css::uno::Reference< css::frame::XModel >& rxModel );
-+ bool ImportCustomToolBar( SfxObjectShell& rDocSh );
- void Print( FILE* );
- };
-
-@@ -320,7 +322,7 @@ public:
- ~Tcg255();
- bool Read(SvStream *pS);
- void Print( FILE* );
-- bool ImportCustomToolBar( const css::uno::Reference< css::frame::XModel >& rxModel );
-+ bool ImportCustomToolBar( SfxObjectShell& rDocSh );
- };
-
- class Tcg: public TBBase
-@@ -333,7 +335,7 @@ public:
- Tcg();
- ~Tcg(){}
- bool Read(SvStream *pS);
-- bool ImportCustomToolBar( const css::uno::Reference< css::frame::XModel >& rxModel );
-+ bool ImportCustomToolBar( SfxObjectShell& rDocSh );
- void Print( FILE* );
- };
-
---- sw/source/ui/uno/unotxdoc.cxx.old 2009-04-02 10:50:38.000000000 +0000
-+++ sw/source/ui/uno/unotxdoc.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -170,6 +170,7 @@ using ::osl::FileBase;
- #define SW_CREATE_MARKER_TABLE 0x06
- #define SW_CREATE_DRAW_DEFAULTS 0x07
-
-+#include <comphelper/processfactory.hxx>
-
- /******************************************************************************
- *
-@@ -362,6 +363,9 @@ SwXTextDocument::SwXTextDocument(SwDocSh
- pxXRedlines(0),
- m_pHiddenViewFrame(0)
- {
-+ uno::Reference< document::XDocumentProperties > xWriterProps( ::comphelper::getProcessServiceFactory()->createInstance( DEFINE_CONST_UNICODE("com.sun.star.writer.DocumentProperties") ), uno::UNO_QUERY_THROW);
-+
-+ SfxBaseModel::setDocumentProperties( xWriterProps );
- }
- /*-- 18.12.98 11:53:00---------------------------------------------------
-
-@@ -2883,6 +2887,7 @@ uno::Sequence< lang::Locale > SAL_CALL S
- {
- ::vos::OGuard aGuard(Application::GetSolarMutex());
-
-+
- // possible canonical values for nScriptTypes
- // any bit wise combination is allowed
- const sal_Int16 nLatin = 0x001;
---- sw/source/ui/vba/makefile.mk.old 1970-01-01 00:00:00.000000000 +0000
-+++ sw/source/ui/vba/makefile.mk 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,85 @@
-+#*************************************************************************
-+#
-+# DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+#
-+# Copyright 2008 by Sun Microsystems, Inc.
-+#
-+# OpenOffice.org - a multi-platform office productivity suite
-+#
-+# $RCSfile: makefile.mk,v $
-+#
-+# $Revision: 1.6 $
-+#
-+# 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.
-+#
-+#*************************************************************************
-+
-+PRJ=..$/..$/..
-+
-+PRJNAME=sw
-+TARGET=vbaswobj
-+ENABLE_EXCEPTIONS=TRUE
-+
-+# --- Settings -----------------------------------------------------
-+
-+.INCLUDE : settings.mk
-+DLLPRE =
-+
-+.IF "$(ENABLE_VBA)"!="YES"
-+dummy:
-+ @echo "not building vba..."
-+.ENDIF
-+
-+INCPRE=$(INCCOM)$/$(TARGET)
-+CDEFS+=-DVBA_OOBUILD_HACK
-+# ------------------------------------------------------------------
-+
-+SLOFILES= \
-+ $(SLO)$/vbaglobals.obj \
-+ $(SLO)$/vbaapplication.obj \
-+ $(SLO)$/vbadocument.obj \
-+ $(SLO)$/vbawindow.obj \
-+ $(SLO)$/vbasystem.obj \
-+ $(SLO)$/vbarangehelper.obj \
-+ $(SLO)$/vbarange.obj \
-+ $(SLO)$/vbabookmark.obj \
-+ $(SLO)$/vbabookmarks.obj \
-+ $(SLO)$/vbavariable.obj \
-+ $(SLO)$/vbavariables.obj \
-+ $(SLO)$/vbaview.obj \
-+ $(SLO)$/wordvbahelper.obj \
-+ $(SLO)$/service.obj \
-+ $(SLO)$/vbadocumentproperties.obj \
-+ $(SLO)$/vbapane.obj \
-+ $(SLO)$/vbapanes.obj \
-+ $(SLO)$/vbaoptions.obj \
-+ $(SLO)$/vbaselection.obj \
-+
-+# --- Targets ------------------------------------------------------
-+
-+.INCLUDE : target.mk
-+
-+ALLTAR : \
-+ $(MISC)$/$(TARGET).don \
-+
-+$(SLOFILES) : $(MISC)$/$(TARGET).don
-+
-+$(MISC)$/$(TARGET).don : $(SOLARBINDIR)$/oovbaapi.rdb
-+ +$(CPPUMAKER) -O$(INCCOM)$/$(TARGET) -BUCR $(SOLARBINDIR)$/oovbaapi.rdb -X$(SOLARBINDIR)$/types.rdb && echo > $@
-+ echo $@
-+
---- sw/source/ui/vba/service.cxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ sw/source/ui/vba/service.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,82 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile: service.cxx,v $
-+ * $Revision: 1.4 $
-+ *
-+ * 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 "cppuhelper/implementationentry.hxx"
-+#include "com/sun/star/lang/XMultiServiceFactory.hpp"
-+#include "com/sun/star/registry/XRegistryKey.hpp"
-+#include "comphelper/servicedecl.hxx"
-+
-+// =============================================================================
-+// component exports
-+// =============================================================================
-+using namespace ::com::sun::star;
-+using namespace ::com::sun::star::uno;
-+
-+namespace sdecl = comphelper::service_decl;
-+
-+namespace globals
-+{
-+extern sdecl::ServiceDecl const serviceDecl;
-+}
-+
-+namespace document
-+{
-+extern sdecl::ServiceDecl const serviceDecl;
-+}
-+
-+extern "C"
-+{
-+ void SAL_CALL component_getImplementationEnvironment(
-+ const sal_Char ** ppEnvTypeName, uno_Environment ** /*ppEnv*/ )
-+ {
-+ OSL_TRACE("In component_getImplementationEnv");
-+ *ppEnvTypeName = CPPU_CURRENT_LANGUAGE_BINDING_NAME;
-+ }
-+
-+ sal_Bool SAL_CALL component_writeInfo(
-+ lang::XMultiServiceFactory * pServiceManager, registry::XRegistryKey * pRegistryKey )
-+ {
-+ OSL_TRACE("In component_writeInfo");
-+
-+ // Component registration
-+ return component_writeInfoHelper( pServiceManager, pRegistryKey,
-+ globals::serviceDecl, document::serviceDecl );
-+ }
-+
-+ void * SAL_CALL component_getFactory(
-+ const sal_Char * pImplName, lang::XMultiServiceFactory * pServiceManager,
-+ registry::XRegistryKey * pRegistryKey )
-+ {
-+ OSL_TRACE("In component_getFactory for %s", pImplName );
-+ void* pRet = component_getFactoryHelper(
-+ pImplName, pServiceManager, pRegistryKey, globals::serviceDecl, document::serviceDecl );
-+ OSL_TRACE("Ret is 0x%x", pRet);
-+ return pRet;
-+ }
-+}
---- sw/source/ui/vba/vbaapplication.cxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ sw/source/ui/vba/vbaapplication.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,135 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile: vbaapplication.cxx,v $
-+ * $Revision: 1.7 $
-+ *
-+ * 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 <stdio.h>
-+#include "vbaapplication.hxx"
-+#include "vbadocument.hxx"
-+#include <osl/file.hxx>
-+#include <vbahelper/vbahelper.hxx>
-+#include "vbawindow.hxx"
-+#include "vbasystem.hxx"
-+#include "vbaoptions.hxx"
-+#include "vbaselection.hxx"
-+
-+using namespace ::ooo;
-+using namespace ::ooo::vba;
-+using namespace ::com::sun::star;
-+
-+using ::com::sun::star::uno::Reference;
-+using ::com::sun::star::uno::UNO_QUERY_THROW;
-+using ::com::sun::star::uno::UNO_QUERY;
-+using ::rtl::OUString;
-+
-+// Enable our own join detection for Intersection and Union
-+// should be more efficient than using ScRangeList::Join ( because
-+// we already are testing the same things )
-+
-+#define OWN_JOIN 1
-+
-+// #TODO is this defined somewhere else?
-+#if ( defined UNX ) || ( defined OS2 ) //unix
-+#define FILE_PATH_SEPERATOR "/"
-+#else // windows
-+#define FILE_PATH_SEPERATOR "\\"
-+#endif
-+
-+#define EXCELVERSION "11.0"
-+
-+uno::Any sbxToUnoValue( SbxVariable* pVar );
-+
-+SwVbaApplication::SwVbaApplication( uno::Reference<uno::XComponentContext >& xContext ): SwVbaApplication_BASE( xContext )
-+{
-+}
-+
-+SwVbaApplication::~SwVbaApplication()
-+{
-+}
-+
-+rtl::OUString SAL_CALL
-+SwVbaApplication::getName() throw (uno::RuntimeException)
-+{
-+ static rtl::OUString appName( RTL_CONSTASCII_USTRINGPARAM("Microsoft Word" ) );
-+ return appName;
-+}
-+
-+uno::Reference< word::XDocument > SAL_CALL
-+SwVbaApplication::getActiveDocument() throw (uno::RuntimeException)
-+{
-+ return new SwVbaDocument( this, mxContext, getCurrentDocument() );
-+}
-+
-+uno::Reference< word::XWindow > SAL_CALL
-+SwVbaApplication::getActiveWindow() throw (uno::RuntimeException)
-+{
-+ // #FIXME sofar can't determine Parent
-+ return new SwVbaWindow( uno::Reference< XHelperInterface >(), mxContext, getCurrentDocument() );
-+}
-+
-+uno::Reference<word::XSystem > SAL_CALL
-+SwVbaApplication::getSystem() throw (uno::RuntimeException)
-+{
-+ return uno::Reference< word::XSystem >( new SwVbaSystem( mxContext ) );
-+}
-+
-+uno::Reference<word::XOptions > SAL_CALL
-+SwVbaApplication::getOptions() throw (uno::RuntimeException)
-+{
-+ return uno::Reference< word::XOptions >( new SwVbaOptions( mxContext ) );
-+}
-+
-+uno::Any SAL_CALL
-+SwVbaApplication::CommandBars( const uno::Any& aIndex ) throw (uno::RuntimeException)
-+{
-+ return VbaApplicationBase::CommandBars( aIndex );
-+}
-+
-+uno::Reference< word::XSelection > SAL_CALL
-+SwVbaApplication::getSelection() throw (uno::RuntimeException)
-+{
-+ return new SwVbaSelection( this, mxContext, getCurrentDocument() );
-+}
-+
-+rtl::OUString&
-+SwVbaApplication::getServiceImplName()
-+{
-+ static rtl::OUString sImplName( RTL_CONSTASCII_USTRINGPARAM("SwVbaApplication") );
-+ return sImplName;
-+}
-+
-+uno::Sequence< rtl::OUString >
-+SwVbaApplication::getServiceNames()
-+{
-+ static uno::Sequence< rtl::OUString > aServiceNames;
-+ if ( aServiceNames.getLength() == 0 )
-+ {
-+ aServiceNames.realloc( 1 );
-+ aServiceNames[ 0 ] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.word.Application" ) );
-+ }
-+ return aServiceNames;
-+}
---- sw/source/ui/vba/vbaapplication.hxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ sw/source/ui/vba/vbaapplication.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,64 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile: vbaapplication.hxx,v $
-+ * $Revision: 1.4 $
-+ *
-+ * 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.
-+ *
-+ ************************************************************************/
-+#ifndef SW_VBA_APPLICATION_HXX
-+#define SW_VBA_APPLICATION_HXX
-+
-+#include <ooo/vba/word/XApplication.hpp>
-+#include <ooo/vba/word/XDocument.hpp>
-+#include <ooo/vba/word/XWindow.hpp>
-+#include <ooo/vba/word/XSystem.hpp>
-+#include <ooo/vba/word/XOptions.hpp>
-+#include <ooo/vba/word/XSelection.hpp>
-+#include <vbahelper/vbahelperinterface.hxx>
-+#include <vbahelper/vbaapplicationbase.hxx>
-+#include <cppuhelper/implbase1.hxx>
-+
-+//typedef InheritedHelperInterfaceImpl1< ooo::vba::word::XApplication > SwVbaApplication_BASE;
-+typedef cppu::ImplInheritanceHelper1< VbaApplicationBase, ooo::vba::word::XApplication > SwVbaApplication_BASE;
-+
-+class SwVbaApplication : public SwVbaApplication_BASE
-+{
-+public:
-+ SwVbaApplication( css::uno::Reference< css::uno::XComponentContext >& m_xContext );
-+ virtual ~SwVbaApplication();
-+
-+ // XApplication
-+ virtual ::rtl::OUString SAL_CALL getName() throw (css::uno::RuntimeException);
-+ virtual css::uno::Reference< ooo::vba::word::XSystem > SAL_CALL getSystem() throw (css::uno::RuntimeException);
-+ virtual css::uno::Reference< ov::word::XDocument > SAL_CALL getActiveDocument() throw (css::uno::RuntimeException);
-+ virtual css::uno::Reference< ov::word::XWindow > SAL_CALL getActiveWindow() throw (css::uno::RuntimeException);
-+ virtual css::uno::Reference< ooo::vba::word::XOptions > SAL_CALL getOptions() throw (css::uno::RuntimeException);
-+ virtual css::uno::Reference< ooo::vba::word::XSelection > SAL_CALL getSelection() throw (css::uno::RuntimeException);
-+ virtual css::uno::Any SAL_CALL CommandBars( const css::uno::Any& aIndex ) throw (css::uno::RuntimeException);
-+ // XHelperInterface
-+ virtual rtl::OUString& getServiceImplName();
-+ virtual css::uno::Sequence<rtl::OUString> getServiceNames();
-+};
-+#endif /* SW_VBA_APPLICATION_HXX */
---- sw/source/ui/vba/vbabookmark.cxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ sw/source/ui/vba/vbabookmark.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,111 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile:
-+ * $Revision:
-+ *
-+ * 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 "vbabookmark.hxx"
-+#include <vbahelper/vbahelper.hxx>
-+#include <tools/diagnose_ex.h>
-+#include <com/sun/star/text/XTextDocument.hpp>
-+#include <com/sun/star/text/XTextContent.hpp>
-+#include <com/sun/star/text/XTextViewCursor.hpp>
-+#include <com/sun/star/text/XTextViewCursorSupplier.hpp>
-+#include "vbarange.hxx"
-+
-+using namespace ::ooo::vba;
-+using namespace ::com::sun::star;
-+
-+SwVbaBookmark::SwVbaBookmark( const uno::Reference< ooo::vba::XHelperInterface >& rParent, const uno::Reference< uno::XComponentContext >& rContext,
-+ const css::uno::Reference< frame::XModel >& rModel, const rtl::OUString& rName ) throw ( css::uno::RuntimeException ) :
-+ SwVbaBookmark_BASE( rParent, rContext ), mxModel( rModel ), maName( rName ), mbValid( sal_True )
-+{
-+ uno::Reference< text::XBookmarksSupplier > xBookmarksSupplier( mxModel, uno::UNO_QUERY_THROW );
-+ mxBookmark.set( xBookmarksSupplier->getBookmarks()->getByName( maName ), uno::UNO_QUERY_THROW );
-+}
-+
-+SwVbaBookmark::~SwVbaBookmark()
-+{
-+}
-+
-+void SwVbaBookmark::checkVality() throw ( uno::RuntimeException )
-+{
-+ if( !mbValid )
-+ throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("The bookmark is not valid" ) ), uno::Reference< uno::XInterface >() );
-+}
-+
-+void SAL_CALL SwVbaBookmark::Delete() throw ( uno::RuntimeException )
-+{
-+ checkVality();
-+ uno::Reference< text::XTextDocument > xTextDocument( mxModel, uno::UNO_QUERY_THROW );
-+ xTextDocument->getText()->removeTextContent( mxBookmark );
-+ mbValid = sal_False;
-+}
-+
-+void SAL_CALL SwVbaBookmark::Select() throw ( uno::RuntimeException )
-+{
-+ checkVality();
-+ uno::Reference< text::XTextViewCursorSupplier > xViewCursorSupplier( mxModel->getCurrentController(), uno::UNO_QUERY_THROW );
-+ xViewCursorSupplier->getViewCursor()->gotoRange( mxBookmark->getAnchor(),sal_False );
-+}
-+
-+rtl::OUString SAL_CALL SwVbaBookmark::getName() throw ( uno::RuntimeException )
-+{
-+ return maName;
-+}
-+
-+void SAL_CALL SwVbaBookmark::setName( const rtl::OUString& _name ) throw ( uno::RuntimeException )
-+{
-+ uno::Reference< container::XNamed > xNamed( mxBookmark, uno::UNO_QUERY_THROW );
-+ xNamed->setName( _name );
-+}
-+
-+uno::Any SAL_CALL SwVbaBookmark::Range() throw ( uno::RuntimeException )
-+{
-+ uno::Reference< text::XTextContent > xTextContent( mxBookmark, uno::UNO_QUERY_THROW );
-+ uno::Reference< text::XTextDocument > xTextDocument( mxModel, uno::UNO_QUERY_THROW );
-+ return uno::makeAny( uno::Reference< word::XRange>( new SwVbaRange( this, mxContext, xTextDocument, xTextContent->getAnchor()->getStart(), xTextContent->getAnchor()->getEnd() ) ) );
-+}
-+
-+rtl::OUString&
-+SwVbaBookmark::getServiceImplName()
-+{
-+ static rtl::OUString sImplName( RTL_CONSTASCII_USTRINGPARAM("SwVbaBookmark") );
-+ return sImplName;
-+}
-+
-+uno::Sequence< rtl::OUString >
-+SwVbaBookmark::getServiceNames()
-+{
-+ static uno::Sequence< rtl::OUString > aServiceNames;
-+ if ( aServiceNames.getLength() == 0 )
-+ {
-+ aServiceNames.realloc( 1 );
-+ aServiceNames[ 0 ] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.word.Bookmark" ) );
-+ }
-+ return aServiceNames;
-+}
-+
---- sw/source/ui/vba/vbabookmark.hxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ sw/source/ui/vba/vbabookmark.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,68 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile:
-+ * $Revision:
-+ *
-+ * 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.
-+ *
-+ ************************************************************************/
-+#ifndef SW_VBA_BOOKMARK_HXX
-+#define SW_VBA_BOOKMARK_HXX
-+
-+#include <ooo/vba/word/XBookmark.hpp>
-+#include <vbahelper/vbahelperinterface.hxx>
-+#include <cppuhelper/implbase1.hxx>
-+#include <com/sun/star/text/XBookmarksSupplier.hpp>
-+#include <com/sun/star/text/XTextContent.hpp>
-+
-+typedef InheritedHelperInterfaceImpl1< ooo::vba::word::XBookmark > SwVbaBookmark_BASE;
-+
-+class SwVbaBookmark : public SwVbaBookmark_BASE
-+{
-+private:
-+ css::uno::Reference< css::frame::XModel > mxModel;
-+ css::uno::Reference< css::text::XTextContent > mxBookmark;
-+ rtl::OUString maName;
-+ sal_Bool mbValid;
-+
-+private:
-+ void checkVality() throw ( css::uno::RuntimeException );
-+
-+public:
-+ SwVbaBookmark( const css::uno::Reference< ooo::vba::XHelperInterface >& rParent, const css::uno::Reference< css::uno::XComponentContext >& rContext,
-+ const css::uno::Reference< css::frame::XModel >& rModel, const rtl::OUString& rName ) throw ( css::uno::RuntimeException );
-+ virtual ~SwVbaBookmark();
-+
-+ // Methods
-+ virtual rtl::OUString SAL_CALL getName() throw ( css::uno::RuntimeException );
-+ virtual void SAL_CALL setName( const rtl::OUString& ) throw ( css::uno::RuntimeException );
-+ virtual void SAL_CALL Delete() throw ( css::uno::RuntimeException );
-+ virtual void SAL_CALL Select() throw ( css::uno::RuntimeException );
-+ virtual css::uno::Any SAL_CALL Range() throw ( css::uno::RuntimeException );
-+
-+ // XHelperInterface
-+ virtual rtl::OUString& getServiceImplName();
-+ virtual css::uno::Sequence<rtl::OUString> getServiceNames();
-+};
-+#endif /* SW_VBA_BOOKMARK_HXX */
---- sw/source/ui/vba/vbabookmarks.cxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ sw/source/ui/vba/vbabookmarks.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,193 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile:
-+ * $Revision:
-+ *
-+ * 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 "vbabookmarks.hxx"
-+#include "vbabookmark.hxx"
-+#include <com/sun/star/container/XNamed.hpp>
-+#include <com/sun/star/text/XTextDocument.hpp>
-+#include <com/sun/star/text/XTextViewCursor.hpp>
-+#include <com/sun/star/text/XTextViewCursorSupplier.hpp>
-+#include <ooo/vba/word/WdBookmarkSortBy.hpp>
-+#include "vbarange.hxx"
-+
-+using namespace ::ooo::vba;
-+using namespace ::com::sun::star;
-+
-+class BookmarksEnumeration : public EnumerationHelperImpl
-+{
-+ uno::Reference< frame::XModel > mxModel;
-+ uno::WeakReference< XHelperInterface > mxParent;
-+public:
-+ BookmarksEnumeration( const uno::Reference< XHelperInterface >& xParent, const uno::Reference< uno::XComponentContext >& xContext, const uno::Reference< container::XEnumeration >& xEnumeration, const uno::Reference< frame::XModel >& xModel ) throw ( uno::RuntimeException ) : EnumerationHelperImpl( xContext, xEnumeration ), mxModel( xModel ), mxParent( xParent ) {}
-+
-+ virtual uno::Any SAL_CALL nextElement( ) throw (container::NoSuchElementException, lang::WrappedTargetException, uno::RuntimeException)
-+ {
-+ uno::Reference< container::XNamed > xNamed( m_xEnumeration->nextElement(), uno::UNO_QUERY_THROW );
-+ rtl::OUString aName = xNamed->getName();
-+ return uno::makeAny( uno::Reference< word::XBookmark > ( new SwVbaBookmark( mxParent, m_xContext, mxModel, aName ) ) );
-+ }
-+
-+};
-+
-+SwVbaBookmarks::SwVbaBookmarks( const uno::Reference< XHelperInterface >& xParent, const uno::Reference< ::com::sun::star::uno::XComponentContext > & xContext, const uno::Reference< container::XIndexAccess >& xBookmarks, const uno::Reference< frame::XModel >& xModel ): SwVbaBookmarks_BASE( xParent, xContext, xBookmarks ), mxModel( xModel )
-+{
-+ mxBookmarksSupplier.set( mxModel, uno::UNO_QUERY_THROW );
-+ uno::Reference< text::XTextDocument > xDocument( mxModel, uno::UNO_QUERY_THROW );
-+ mxText = xDocument->getText();
-+
-+ // FIXME: fail to rename the bookmark
-+ // word doesn't distinguish cases, so set all bookmarknames to Lowercase
-+ //renameAllBookmarksToLowercase();
-+}
-+// XEnumerationAccess
-+uno::Type
-+SwVbaBookmarks::getElementType() throw (uno::RuntimeException)
-+{
-+ return word::XBookmark::static_type(0);
-+}
-+uno::Reference< container::XEnumeration >
-+SwVbaBookmarks::createEnumeration() throw (uno::RuntimeException)
-+{
-+ uno::Reference< container::XEnumerationAccess > xEnumAccess( m_xIndexAccess, uno::UNO_QUERY_THROW );
-+ return new BookmarksEnumeration( getParent(), mxContext,xEnumAccess->createEnumeration(), mxModel );
-+}
-+
-+uno::Any
-+SwVbaBookmarks::createCollectionObject( const css::uno::Any& aSource )
-+{
-+ uno::Reference< container::XNamed > xNamed( aSource, uno::UNO_QUERY_THROW );
-+ rtl::OUString aName = xNamed->getName();
-+ return uno::makeAny( uno::Reference< word::XBookmark > ( new SwVbaBookmark( getParent(), mxContext, mxModel, aName ) ) );
-+}
-+
-+void SwVbaBookmarks::removeBookmarkByName( const rtl::OUString& rName ) throw (uno::RuntimeException)
-+{
-+ uno::Reference< text::XTextContent > xBookmark( mxBookmarksSupplier->getBookmarks()->getByName( rName ), uno::UNO_QUERY_THROW );
-+ mxText->removeTextContent( xBookmark );
-+}
-+
-+void SwVbaBookmarks::addBookmarkByName( const rtl::OUString& rName, const uno::Reference< text::XTextRange >& rTextRange ) throw (uno::RuntimeException)
-+{
-+ uno::Reference< lang::XMultiServiceFactory > xDocMSF( mxModel, uno::UNO_QUERY_THROW );
-+ uno::Reference< text::XTextContent > xBookmark( xDocMSF->createInstance( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("com.sun.star.text.Bookmark")) ), uno::UNO_QUERY_THROW );
-+ uno::Reference< container::XNamed > xNamed( xBookmark, uno::UNO_QUERY_THROW );
-+ xNamed->setName( rName );
-+ mxText->insertTextContent( rTextRange, xBookmark, sal_False );
-+}
-+
-+void SwVbaBookmarks::renameAllBookmarksToLowercase() throw (uno::RuntimeException)
-+{
-+ uno::Reference< container::XIndexAccess > xBookmarks( mxBookmarksSupplier->getBookmarks(),uno::UNO_QUERY_THROW );
-+ for( sal_Int32 nIndex = 0; nIndex < xBookmarks->getCount(); nIndex++ )
-+ {
-+ uno::Reference< container::XNamed > xNamed( xBookmarks->getByIndex( nIndex ), uno::UNO_QUERY_THROW );
-+ rtl::OUString aName = xNamed->getName();
-+ rtl::OUString aNameLowerCase = aName.toAsciiLowerCase();
-+ if( !aName.equals( aNameLowerCase ) );
-+ xNamed->setName( aNameLowerCase );
-+ }
-+}
-+
-+uno::Any SAL_CALL
-+SwVbaBookmarks::Add( const rtl::OUString& rName, const uno::Any& rRange ) throw (uno::RuntimeException)
-+{
-+ uno::Reference< text::XTextRange > xTextRange;
-+ uno::Reference< word::XRange > xRange;
-+ if( rRange >>= xRange )
-+ {
-+ SwVbaRange* pRange = dynamic_cast< SwVbaRange* >( xRange.get() );
-+ if( pRange )
-+ xTextRange = pRange->getXTextRange();
-+ }
-+ else
-+ {
-+ // FIXME: insert the bookmark into current view cursor
-+ uno::Reference< text::XTextViewCursorSupplier > xViewCursorSupplier( mxModel->getCurrentController(), uno::UNO_QUERY_THROW );
-+ xTextRange.set( xViewCursorSupplier->getViewCursor(), uno::UNO_QUERY_THROW );
-+ }
-+
-+ // remove the exist bookmark
-+ rtl::OUString aName = rName.toAsciiLowerCase();
-+ if( mxBookmarksSupplier->getBookmarks()->hasByName( aName ) )
-+ removeBookmarkByName( aName );
-+
-+ addBookmarkByName( aName, xTextRange );
-+
-+ return uno::makeAny( uno::Reference< word::XBookmark >( new SwVbaBookmark( getParent(), mxContext, mxModel, aName ) ) );
-+}
-+
-+sal_Int32 SAL_CALL
-+SwVbaBookmarks::getDefaultSorting() throw (css::uno::RuntimeException)
-+{
-+ return word::WdBookmarkSortBy::wdSortByName;
-+}
-+
-+void SAL_CALL
-+SwVbaBookmarks::setDefaultSorting( sal_Int32/* _type*/ ) throw (css::uno::RuntimeException)
-+{
-+ // not support in Writer
-+}
-+
-+sal_Bool SAL_CALL
-+SwVbaBookmarks::getShowHidden() throw (css::uno::RuntimeException)
-+{
-+ return sal_True;
-+}
-+
-+void SAL_CALL
-+SwVbaBookmarks::setShowHidden( sal_Bool /*_hidden*/ ) throw (css::uno::RuntimeException)
-+{
-+ // not support in Writer
-+}
-+
-+sal_Bool SAL_CALL
-+SwVbaBookmarks::Exists( const rtl::OUString& rName ) throw (css::uno::RuntimeException)
-+{
-+ sal_Bool bExist = mxBookmarksSupplier->getBookmarks()->hasByName( rName.toAsciiLowerCase() );
-+ return bExist;
-+}
-+
-+rtl::OUString&
-+SwVbaBookmarks::getServiceImplName()
-+{
-+ static rtl::OUString sImplName( RTL_CONSTASCII_USTRINGPARAM("SwVbaBookmarks") );
-+ return sImplName;
-+}
-+
-+css::uno::Sequence<rtl::OUString>
-+SwVbaBookmarks::getServiceNames()
-+{
-+ static uno::Sequence< rtl::OUString > sNames;
-+ if ( sNames.getLength() == 0 )
-+ {
-+ sNames.realloc( 1 );
-+ sNames[0] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.word.Bookmarks") );
-+ }
-+ return sNames;
-+}
---- sw/source/ui/vba/vbabookmarks.hxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ sw/source/ui/vba/vbabookmarks.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,79 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile:
-+ * $Revision:
-+ *
-+ * 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.
-+ *
-+ ************************************************************************/
-+#ifndef SW_VBA_BOOKMARKS_HXX
-+#define SW_VBA_BOOKMARKS_HXX
-+
-+#include <vbahelper/vbacollectionimpl.hxx>
-+#include <ooo/vba/word/XBookmarks.hpp>
-+#include <com/sun/star/container/XEnumerationAccess.hpp>
-+#include <com/sun/star/container/XIndexAccess.hpp>
-+#include <vbahelper/vbahelperinterface.hxx>
-+#include <com/sun/star/text/XBookmarksSupplier.hpp>
-+#include <com/sun/star/text/XTextRange.hpp>
-+#include <com/sun/star/text/XText.hpp>
-+
-+typedef CollTestImplHelper< ooo::vba::word::XBookmarks > SwVbaBookmarks_BASE;
-+
-+class SwVbaBookmarks : public SwVbaBookmarks_BASE
-+{
-+private:
-+ css::uno::Reference< css::frame::XModel > mxModel;
-+ css::uno::Reference< css::text::XBookmarksSupplier > mxBookmarksSupplier;
-+ css::uno::Reference< css::text::XText > mxText;
-+
-+private:
-+ void removeBookmarkByName( const rtl::OUString& rName ) throw (css::uno::RuntimeException);
-+ void addBookmarkByName( const rtl::OUString& rName, const css::uno::Reference< css::text::XTextRange >& rTextRange ) throw (css::uno::RuntimeException);
-+ void renameAllBookmarksToLowercase() throw (css::uno::RuntimeException);
-+
-+public:
-+ SwVbaBookmarks( const css::uno::Reference< ov::XHelperInterface >& xParent, const css::uno::Reference< css::uno::XComponentContext > & xContext, const css::uno::Reference< css::container::XIndexAccess >& xBookmarks, const css::uno::Reference< css::frame::XModel >& xModel );
-+ virtual ~SwVbaBookmarks() {}
-+
-+ // XEnumerationAccess
-+ virtual css::uno::Type SAL_CALL getElementType() throw (css::uno::RuntimeException);
-+ virtual css::uno::Reference< css::container::XEnumeration > SAL_CALL createEnumeration() throw (css::uno::RuntimeException);
-+
-+ // SwVbaBookmarks_BASE
-+ virtual css::uno::Any createCollectionObject( const css::uno::Any& aSource );
-+ virtual rtl::OUString& getServiceImplName();
-+ virtual css::uno::Sequence<rtl::OUString> getServiceNames();
-+
-+ // XBookmarks
-+ virtual sal_Int32 SAL_CALL getDefaultSorting() throw (css::uno::RuntimeException);
-+ virtual void SAL_CALL setDefaultSorting( sal_Int32 _type ) throw (css::uno::RuntimeException);
-+ virtual sal_Bool SAL_CALL getShowHidden() throw (css::uno::RuntimeException);
-+ virtual void SAL_CALL setShowHidden( sal_Bool _hidden ) throw (css::uno::RuntimeException);
-+
-+ virtual css::uno::Any SAL_CALL Add( const rtl::OUString& rName, const css::uno::Any& rRange ) throw (css::uno::RuntimeException);
-+ virtual sal_Bool SAL_CALL Exists( const rtl::OUString& rName ) throw (css::uno::RuntimeException);
-+};
-+
-+#endif /* SW_VBA_BOOKMARKS_HXX */
---- sw/source/ui/vba/vbadocument.cxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ sw/source/ui/vba/vbadocument.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,186 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile: vbadocument.cxx,v $
-+ * $Revision: 1.7 $
-+ *
-+ * 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 "vbadocument.hxx"
-+#include "vbarange.hxx"
-+#include "vbarangehelper.hxx"
-+#include "vbadocumentproperties.hxx"
-+#include "vbabookmarks.hxx"
-+#include "vbavariables.hxx"
-+#include <com/sun/star/text/XBookmarksSupplier.hpp>
-+#include <com/sun/star/document/XDocumentPropertiesSupplier.hpp>
-+#include <com/sun/star/document/XDocumentProperties.hpp>
-+#include <vbahelper/helperdecl.hxx>
-+
-+using namespace ::ooo::vba;
-+using namespace ::com::sun::star;
-+
-+SwVbaDocument::SwVbaDocument( const uno::Reference< XHelperInterface >& xParent, const uno::Reference< uno::XComponentContext >& xContext, uno::Reference< frame::XModel > xModel ): SwVbaDocument_BASE( xParent, xContext, xModel )
-+{
-+ Initialize();
-+}
-+SwVbaDocument::SwVbaDocument( uno::Sequence< uno::Any > const& aArgs, uno::Reference< uno::XComponentContext >const& xContext ) : SwVbaDocument_BASE( aArgs, xContext )
-+{
-+ Initialize();
-+}
-+
-+SwVbaDocument::~SwVbaDocument()
-+{
-+}
-+
-+void SwVbaDocument::Initialize()
-+{
-+ mxTextDocument.set( getModel(), uno::UNO_QUERY_THROW );
-+}
-+
-+uno::Reference< word::XRange > SAL_CALL
-+SwVbaDocument::getContent() throw ( uno::RuntimeException )
-+{
-+ uno::Reference< text::XTextRange > xStart = mxTextDocument->getText()->getStart();
-+ uno::Reference< text::XTextRange > xEnd;
-+ return uno::Reference< word::XRange >( new SwVbaRange( this, mxContext, mxTextDocument, xStart, xEnd, sal_True ) );
-+}
-+
-+uno::Reference< word::XRange > SAL_CALL
-+SwVbaDocument::Range( const uno::Any& rStart, const uno::Any& rEnd ) throw ( uno::RuntimeException )
-+{
-+ if( !rStart.hasValue() && !rEnd.hasValue() )
-+ return getContent();
-+
-+ sal_Int32 nStart = 0;
-+ sal_Int32 nEnd = 0;
-+ rStart >>= nStart;
-+ rEnd >>= nEnd;
-+ nStart--;
-+ nEnd--;
-+
-+ uno::Reference< text::XTextRange > xStart;
-+ uno::Reference< text::XTextRange > xEnd;
-+ if( nStart != -1 || nEnd != -1 )
-+ {
-+ if( nStart == -1 )
-+ xStart = mxTextDocument->getText()->getStart();
-+ else
-+ xStart = SwVbaRangeHelper::getRangeByPosition( mxTextDocument->getText(), nStart );
-+
-+ if( nEnd == -1 )
-+ xEnd = mxTextDocument->getText()->getEnd();
-+ else
-+ xEnd = SwVbaRangeHelper::getRangeByPosition( mxTextDocument->getText(), nEnd );
-+ }
-+
-+ if( !xStart.is() && !xEnd.is() )
-+ {
-+ try
-+ {
-+ // FIXME
-+ xStart = mxTextDocument->getText()->getStart();
-+ xEnd = mxTextDocument->getText()->getEnd();
-+ }
-+ catch( uno::Exception )
-+ {
-+ DebugHelper::exception(SbERR_METHOD_FAILED, rtl::OUString());
-+ }
-+ }
-+ return uno::Reference< word::XRange >( new SwVbaRange( this, mxContext, mxTextDocument, xStart, xEnd ) );
-+}
-+
-+uno::Any SAL_CALL
-+SwVbaDocument::BuiltInDocumentProperties( const uno::Any& index ) throw (uno::RuntimeException)
-+{
-+ uno::Reference< XCollection > xCol( new SwVbaBuiltinDocumentProperties( mxParent, mxContext, getModel() ) );
-+ if ( index.hasValue() )
-+ return xCol->Item( index, uno::Any() );
-+ return uno::makeAny( xCol );
-+}
-+
-+uno::Any SAL_CALL
-+SwVbaDocument::CustomDocumentProperties( const uno::Any& index ) throw (uno::RuntimeException)
-+{
-+ uno::Reference< XCollection > xCol( new SwVbaCustomDocumentProperties( mxParent, mxContext, getModel() ) );
-+ if ( index.hasValue() )
-+ return xCol->Item( index, uno::Any() );
-+ return uno::makeAny( xCol );
-+}
-+
-+uno::Any SAL_CALL
-+SwVbaDocument::Bookmarks( const uno::Any& rIndex ) throw ( uno::RuntimeException )
-+{
-+ uno::Reference< text::XBookmarksSupplier > xBookmarksSupplier( getModel(),uno::UNO_QUERY_THROW );
-+ uno::Reference<container::XIndexAccess > xBookmarks( xBookmarksSupplier->getBookmarks(), uno::UNO_QUERY_THROW );
-+ uno::Reference< XCollection > xBookmarksVba( new SwVbaBookmarks( this, mxContext, xBookmarks, getModel() ) );
-+ if ( rIndex.getValueTypeClass() == uno::TypeClass_VOID )
-+ return uno::makeAny( xBookmarksVba );
-+
-+ return uno::Any( xBookmarksVba->Item( rIndex, uno::Any() ) );
-+}
-+
-+uno::Any SAL_CALL
-+SwVbaDocument::Variables( const uno::Any& rIndex ) throw ( uno::RuntimeException )
-+{
-+ uno::Reference< document::XDocumentPropertiesSupplier > xDocumentPropertiesSupplier( getModel(),uno::UNO_QUERY_THROW );
-+ uno::Reference< document::XDocumentProperties > xDocumentProperties = xDocumentPropertiesSupplier->getDocumentProperties();
-+ uno::Reference< beans::XPropertyAccess > xUserDefined( xDocumentProperties->getUserDefinedProperties(), uno::UNO_QUERY_THROW );
-+
-+ uno::Reference< XCollection > xVariables( new SwVbaVariables( this, mxContext, xUserDefined ) );
-+ if ( rIndex.getValueTypeClass() == uno::TypeClass_VOID )
-+ return uno::makeAny( xVariables );
-+
-+ return uno::Any( xVariables->Item( rIndex, uno::Any() ) );
-+}
-+
-+rtl::OUString&
-+SwVbaDocument::getServiceImplName()
-+{
-+ static rtl::OUString sImplName( RTL_CONSTASCII_USTRINGPARAM("SwVbaDocument") );
-+ return sImplName;
-+}
-+
-+uno::Sequence< rtl::OUString >
-+SwVbaDocument::getServiceNames()
-+{
-+ static uno::Sequence< rtl::OUString > aServiceNames;
-+ if ( aServiceNames.getLength() == 0 )
-+ {
-+ aServiceNames.realloc( 1 );
-+ aServiceNames[ 0 ] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.word.Document" ) );
-+ }
-+ return aServiceNames;
-+}
-+
-+namespace document
-+{
-+namespace sdecl = comphelper::service_decl;
-+sdecl::vba_service_class_<SwVbaDocument, sdecl::with_args<true> > serviceImpl;
-+extern sdecl::ServiceDecl const serviceDecl(
-+ serviceImpl,
-+ "SwVbaDocument",
-+ "ooo.vba.word.Document" );
-+}
-+
---- sw/source/ui/vba/vbadocument.hxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ sw/source/ui/vba/vbadocument.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,63 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile: vbadocument.hxx,v $
-+ * $Revision: 1.4 $
-+ *
-+ * 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.
-+ *
-+ ************************************************************************/
-+#ifndef SW_VBA_DOCUMENT_HXX
-+#define SW_VBA_DOCUMENT_HXX
-+
-+#include <ooo/vba/word/XDocument.hpp>
-+#include <vbahelper/vbahelperinterface.hxx>
-+#include <vbahelper/vbadocumentbase.hxx>
-+#include <com/sun/star/text/XTextDocument.hpp>
-+
-+typedef cppu::ImplInheritanceHelper1< VbaDocumentBase, ooo::vba::word::XDocument > SwVbaDocument_BASE;
-+
-+class SwVbaDocument : public SwVbaDocument_BASE
-+{
-+private:
-+ css::uno::Reference< css::text::XTextDocument > mxTextDocument;
-+
-+ void Initialize();
-+public:
-+ SwVbaDocument( const css::uno::Reference< ooo::vba::XHelperInterface >& xParent, const css::uno::Reference< css::uno::XComponentContext >& m_xContext, css::uno::Reference< css::frame::XModel > xModel );
-+ SwVbaDocument( css::uno::Sequence< css::uno::Any > const& aArgs, css::uno::Reference< css::uno::XComponentContext >const& xContext );
-+ virtual ~SwVbaDocument();
-+
-+ // XDocument
-+ virtual css::uno::Reference< ooo::vba::word::XRange > SAL_CALL getContent() throw ( css::uno::RuntimeException );
-+ virtual css::uno::Reference< ooo::vba::word::XRange > SAL_CALL Range( const css::uno::Any& rStart, const css::uno::Any& rEnd ) throw ( css::uno::RuntimeException );
-+ virtual css::uno::Any SAL_CALL BuiltInDocumentProperties( const css::uno::Any& index ) throw (css::uno::RuntimeException);
-+ virtual css::uno::Any SAL_CALL CustomDocumentProperties( const css::uno::Any& index ) throw (css::uno::RuntimeException);
-+ virtual css::uno::Any SAL_CALL Bookmarks( const css::uno::Any& rIndex ) throw ( css::uno::RuntimeException );
-+ virtual css::uno::Any SAL_CALL Variables( const css::uno::Any& rIndex ) throw ( css::uno::RuntimeException );
-+
-+ // XHelperInterface
-+ virtual rtl::OUString& getServiceImplName();
-+ virtual css::uno::Sequence<rtl::OUString> getServiceNames();
-+};
-+#endif /* SW_VBA_DOCUMENT_HXX */
---- sw/source/ui/vba/vbadocumentproperties.cxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ sw/source/ui/vba/vbadocumentproperties.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,798 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile: vbadocument.cxx,v $
-+ * $Revision: 1.7 $
-+ *
-+ * 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 "vbadocumentproperties.hxx"
-+#include <cppuhelper/implbase1.hxx>
-+#include <cppuhelper/implbase3.hxx>
-+#include <com/sun/star/document/XDocumentInfoSupplier.hpp>
-+#include <com/sun/star/document/XDocumentPropertiesSupplier.hpp>
-+#include <com/sun/star/beans/NamedValue.hpp>
-+#include <com/sun/star/beans/XPropertyContainer.hpp>
-+#include <ooo/vba/word/WdBuiltInProperty.hpp>
-+#include <ooo/vba/office/MsoDocProperties.hpp>
-+#include <memory>
-+#include <boost/shared_ptr.hpp>
-+#include "wordvbahelper.hxx"
-+#include "fesh.hxx"
-+#include "docsh.hxx"
-+using namespace ::ooo::vba;
-+using namespace css;
-+
-+sal_Int8 lcl_toMSOPropType( const uno::Type& aType ) throw ( lang::IllegalArgumentException )
-+{
-+ sal_Int16 msoType = office::MsoDocProperties::msoPropertyTypeString;
-+
-+ switch ( aType.getTypeClass() )
-+ {
-+ case uno::TypeClass_BOOLEAN:
-+ msoType = office::MsoDocProperties::msoPropertyTypeBoolean;
-+ break;
-+ case uno::TypeClass_FLOAT:
-+ msoType = office::MsoDocProperties::msoPropertyTypeFloat;
-+ break;
-+ case uno::TypeClass_STRUCT: // Assume date
-+ msoType = office::MsoDocProperties::msoPropertyTypeDate;
-+ break;
-+ case uno::TypeClass_BYTE:
-+ case uno::TypeClass_SHORT:
-+ case uno::TypeClass_LONG:
-+ case uno::TypeClass_HYPER:
-+ msoType = office::MsoDocProperties::msoPropertyTypeNumber;
-+ break;
-+ default:
-+ throw lang::IllegalArgumentException();
-+ }
-+ return msoType;
-+}
-+
-+class PropertGetSetHelper
-+{
-+protected:
-+ uno::Reference< frame::XModel > m_xModel;
-+ uno::Reference< beans::XPropertySet > mxProps;
-+public:
-+ PropertGetSetHelper( const uno::Reference< frame::XModel >& xModel ):m_xModel( xModel )
-+ {
-+ uno::Reference< document::XDocumentInfoSupplier > xDocInfoSupp( m_xModel, uno::UNO_QUERY_THROW );
-+ mxProps.set( xDocInfoSupp->getDocumentInfo(), uno::UNO_QUERY_THROW );
-+ }
-+ virtual ~PropertGetSetHelper() {}
-+ virtual uno::Any getPropertyValue( const rtl::OUString& rPropName ) = 0;
-+ virtual void setPropertyValue( const rtl::OUString& rPropName, const uno::Any& aValue ) = 0;
-+ virtual uno::Reference< beans::XPropertySet > getUnoProperties() { return mxProps; }
-+
-+};
-+
-+class BuiltinPropertyGetSetHelper : public PropertGetSetHelper
-+{
-+public:
-+ BuiltinPropertyGetSetHelper( const uno::Reference< frame::XModel >& xModel ) :PropertGetSetHelper( xModel )
-+ {
-+ }
-+ virtual uno::Any getPropertyValue( const rtl::OUString& rPropName )
-+ {
-+ if ( rPropName.equals( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("EditingDuration" ) ) ) )
-+ {
-+ sal_Int32 nSecs = 0;
-+ mxProps->getPropertyValue( rPropName ) >>= nSecs;
-+ return uno::makeAny( nSecs/60 ); // minutes
-+ }
-+ return mxProps->getPropertyValue( rPropName );
-+ }
-+ virtual void setPropertyValue( const rtl::OUString& rPropName, const uno::Any& aValue )
-+ {
-+ mxProps->setPropertyValue( rPropName, aValue );
-+ }
-+};
-+
-+class CustomPropertyGetSetHelper : public BuiltinPropertyGetSetHelper
-+{
-+public:
-+ CustomPropertyGetSetHelper( const uno::Reference< frame::XModel >& xModel ) :BuiltinPropertyGetSetHelper( xModel )
-+ {
-+ uno::Reference< document::XDocumentPropertiesSupplier > xDocPropSupp( mxProps, uno::UNO_QUERY_THROW );
-+ uno::Reference< document::XDocumentProperties > xDocProp( xDocPropSupp->getDocumentProperties(), uno::UNO_QUERY_THROW );
-+ mxProps.set( xDocProp->getUserDefinedProperties(), uno::UNO_QUERY_THROW );
-+ }
-+};
-+class StatisticPropertyGetSetHelper : public PropertGetSetHelper
-+{
-+ SwDocShell* mpDocShell;
-+ uno::Reference< beans::XPropertySet > mxModelProps;
-+public:
-+ StatisticPropertyGetSetHelper( const uno::Reference< frame::XModel >& xModel ) :PropertGetSetHelper( xModel ) , mpDocShell( NULL )
-+ {
-+ mxModelProps.set( m_xModel, uno::UNO_QUERY_THROW );
-+ mpDocShell = word::getDocShell( xModel );
-+ }
-+ virtual uno::Any getPropertyValue( const rtl::OUString& rPropName )
-+ {
-+ uno::Sequence< beans::NamedValue > stats;
-+ try
-+ {
-+ // Characters, ParagraphCount & WordCount are available from
-+ // the model ( and addtionally these also update the statics object )
-+ //return mxProps->getPropertyValue( rPropName );
-+ return mxModelProps->getPropertyValue( rPropName );
-+ }
-+ catch( uno::Exception& )
-+ {
-+ OSL_TRACE("Got exception");
-+ }
-+ uno::Any aReturn;
-+ if ( rPropName.equals( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("LineCount")) ) ) // special processing needed
-+ {
-+ if ( mpDocShell )
-+ {
-+ SwFEShell* pFEShell = mpDocShell->GetFEShell();
-+ if(pFEShell)
-+ {
-+ aReturn <<= pFEShell->GetLineCount(FALSE);
-+ }
-+ }
-+ }
-+ else
-+ {
-+ mxModelProps->getPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ParagraphCount") ) ) >>= stats;
-+ mxProps->getPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("DocumentStatistic") ) ) >>= stats;
-+
-+ sal_Int32 nLen = stats.getLength();
-+ bool bFound = false;
-+ for ( sal_Int32 index = 0; index < nLen && !bFound ; ++index )
-+ {
-+ if ( rPropName.equals( stats[ index ].Name ) )
-+ {
-+ aReturn = stats[ index ].Value;
-+ bFound = true;
-+ }
-+ }
-+ if ( !bFound )
-+ throw uno::RuntimeException(); // bad Property
-+ }
-+ return aReturn;
-+ }
-+
-+ virtual void setPropertyValue( const rtl::OUString& rPropName, const uno::Any& aValue )
-+ {
-+
-+ uno::Sequence< beans::NamedValue > stats;
-+ mxProps->getPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("DocumentStatistic") ) ) >>= stats;
-+
-+ sal_Int32 nLen = stats.getLength();
-+ for ( sal_Int32 index = 0; index < nLen; ++index )
-+ {
-+ if ( rPropName.equals( stats[ index ].Name ) )
-+ {
-+ stats[ index ].Value = aValue;
-+ mxProps->setPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("DocumentStatistic") ), uno::makeAny( stats ) );
-+ break;
-+ }
-+ }
-+ }
-+};
-+
-+class DocPropInfo
-+{
-+public:
-+ rtl::OUString msMSODesc;
-+ rtl::OUString msOOOPropName;
-+ boost::shared_ptr< PropertGetSetHelper > mpPropGetSetHelper;
-+
-+ static DocPropInfo createDocPropInfo( const rtl::OUString& sDesc, const rtl::OUString& sPropName, boost::shared_ptr< PropertGetSetHelper >& rHelper )
-+ {
-+ return createDocPropInfo( rtl::OUStringToOString( sDesc, RTL_TEXTENCODING_UTF8 ).getStr(), rtl::OUStringToOString( sPropName, RTL_TEXTENCODING_UTF8 ).getStr(), rHelper );
-+ }
-+
-+ static DocPropInfo createDocPropInfo( const sal_Char* sDesc, const sal_Char* sPropName, boost::shared_ptr< PropertGetSetHelper >& rHelper )
-+ {
-+ DocPropInfo aItem;
-+ aItem.msMSODesc = rtl::OUString::createFromAscii( sDesc );
-+ aItem.msOOOPropName = rtl::OUString::createFromAscii( sPropName );
-+ aItem.mpPropGetSetHelper = rHelper;
-+ return aItem;
-+ }
-+ uno::Any getValue()
-+ {
-+ if ( mpPropGetSetHelper.get() )
-+ return mpPropGetSetHelper->getPropertyValue( msOOOPropName );
-+ return uno::Any();
-+ }
-+ void setValue( const uno::Any& rValue )
-+ {
-+ if ( mpPropGetSetHelper.get() )
-+ mpPropGetSetHelper->setPropertyValue( msOOOPropName, rValue );
-+ }
-+ uno::Reference< beans::XPropertySet > getUnoProperties()
-+ {
-+
-+ uno::Reference< beans::XPropertySet > xProps;
-+ if ( mpPropGetSetHelper.get() )
-+ return mpPropGetSetHelper->getUnoProperties();
-+ return xProps;
-+ }
-+};
-+
-+
-+typedef std::hash_map< sal_Int32, DocPropInfo > MSOIndexToOODocPropInfo;
-+
-+class BuiltInIndexHelper
-+{
-+ MSOIndexToOODocPropInfo m_docPropInfoMap;
-+ BuiltInIndexHelper();
-+public:
-+ BuiltInIndexHelper( const uno::Reference< frame::XModel >& xModel )
-+ {
-+ boost::shared_ptr< PropertGetSetHelper > aStandardHelper( new BuiltinPropertyGetSetHelper( xModel ) );
-+ boost::shared_ptr< PropertGetSetHelper > aUsingStatsHelper( new StatisticPropertyGetSetHelper( xModel ) );
-+/*
-+ m_docPropInfoMap[ word::WdBuiltInProperty::wdPropertyTitle ] = DocPropInfo::createDocPropInfo( "Title", "Title", office::MsoDocProperties::msoPropertyTypeString, aStandardHelper );
-+ m_docPropInfoMap[ word::WdBuiltInProperty::wdPropertySubject ] = DocPropInfo::createDocPropInfo( "Subject", "Subject", office::MsoDocProperties::msoPropertyTypeString, aStandardHelper );
-+ m_docPropInfoMap[ word::WdBuiltInProperty::wdPropertyAuthor ] = DocPropInfo::createDocPropInfo( "Author", "Author", office::MsoDocProperties::msoPropertyTypeString, aStandardHelper );
-+ m_docPropInfoMap[ word::WdBuiltInProperty::wdPropertyKeywords ] = DocPropInfo::createDocPropInfo( "Keywords", "Keywords", office::MsoDocProperties::msoPropertyTypeString, aStandardHelper );
-+ m_docPropInfoMap[ word::WdBuiltInProperty::wdPropertyComments ] = DocPropInfo::createDocPropInfo( "Comments", "Description", office::MsoDocProperties::msoPropertyTypeString, aStandardHelper );
-+ m_docPropInfoMap[ word::WdBuiltInProperty::wdPropertyTemplate ] = DocPropInfo::createDocPropInfo( "Template", "Template", office::MsoDocProperties::msoPropertyTypeString, aStandardHelper );
-+ m_docPropInfoMap[ word::WdBuiltInProperty::wdPropertyLastAuthor ] = DocPropInfo::createDocPropInfo( "Last author", "", office::MsoDocProperties::msoPropertyTypeString, aStandardHelper ); // doesn't seem to exist - throw or return nothing ?
-+ m_docPropInfoMap[ word::WdBuiltInProperty::wdPropertyRevision ] = DocPropInfo::createDocPropInfo( "Revision number", "", office::MsoDocProperties::msoPropertyTypeString, aStandardHelper ); // doesn't seem to exist - throw or return nothing ?
-+ m_docPropInfoMap[ word::WdBuiltInProperty::wdPropertyAppName ] = DocPropInfo::createDocPropInfo( "Application name", "Generator", office::MsoDocProperties::msoPropertyTypeString, aStandardHelper ); // doesn't seem to exist - throw or return nothing ?
-+ m_docPropInfoMap[ word::WdBuiltInProperty::wdPropertyTimeLastPrinted ] = DocPropInfo::createDocPropInfo( "Last print date", "PrintDate", office::MsoDocProperties::msoPropertyTypeDate, aStandardHelper ); // doesn't seem to exist - throw or return nothing ?
-+ m_docPropInfoMap[ word::WdBuiltInProperty::wdPropertyTimeCreated ] = DocPropInfo::createDocPropInfo( "Creation date", "CreationDate", office::MsoDocProperties::msoPropertyTypeDate, aStandardHelper ); // doesn't seem to exist - throw or return nothing ?
-+ m_docPropInfoMap[ word::WdBuiltInProperty::wdPropertyTimeLastSaved ] = DocPropInfo::createDocPropInfo( "Last save time", "ModifyDate", office::MsoDocProperties::msoPropertyTypeDate, aStandardHelper ); // doesn't seem to exist - throw or return nothing ?
-+ m_docPropInfoMap[ word::WdBuiltInProperty::wdPropertyVBATotalEdit ] = DocPropInfo::createDocPropInfo( "Total editing time", "EditingDuration", office::MsoDocProperties::msoPropertyTypeNumber, aStandardHelper ); // Not sure if this is correct
-+ m_docPropInfoMap[ word::WdBuiltInProperty::wdPropertyPages ] = DocPropInfo::createDocPropInfo( "Number of pages", "PageCount", office::MsoDocProperties::msoPropertyTypeNumber, aUsingStatsHelper ); // special handling required
-+ m_docPropInfoMap[ word::WdBuiltInProperty::wdPropertyWords ] = DocPropInfo::createDocPropInfo( "Number of words", "WordCount", office::MsoDocProperties::msoPropertyTypeNumber, aUsingStatsHelper ); // special handling required
-+ m_docPropInfoMap[ word::WdBuiltInProperty::wdPropertyCharacters ] = DocPropInfo::createDocPropInfo( "Number of characters", "CharacterCount", office::MsoDocProperties::msoPropertyTypeNumber, aUsingStatsHelper ); // special handling required
-+ m_docPropInfoMap[ word::WdBuiltInProperty::wdPropertySecurity ] = DocPropInfo::createDocPropInfo( "Security", "", office::MsoDocProperties::msoPropertyTypeNumber, aStandardHelper ); // doesn't seem to exist
-+ m_docPropInfoMap[ word::WdBuiltInProperty::wdPropertyCategory ] = DocPropInfo::createDocPropInfo( "Category", "", office::MsoDocProperties::msoPropertyTypeString, aStandardHelper ); // doesn't seem to exist
-+ m_docPropInfoMap[ word::WdBuiltInProperty::wdPropertyFormat ] = DocPropInfo::createDocPropInfo( "Format", "", office::MsoDocProperties::msoPropertyTypeString, aStandardHelper ); // doesn't seem to exist
-+ m_docPropInfoMap[ word::WdBuiltInProperty::wdPropertyManager ] = DocPropInfo::createDocPropInfo( "Manager", "", office::MsoDocProperties::msoPropertyTypeString, aStandardHelper ); // doesn't seem to exist
-+ m_docPropInfoMap[ word::WdBuiltInProperty::wdPropertyCompany ] = DocPropInfo::createDocPropInfo( "Company", "", office::MsoDocProperties::msoPropertyTypeString, aStandardHelper ); // doesn't seem to exist
-+ m_docPropInfoMap[ word::WdBuiltInProperty::wdPropertyBytes ] = DocPropInfo::createDocPropInfo( "Number of bytes", "", office::MsoDocProperties::msoPropertyTypeNumber, aStandardHelper ); // doesn't seem to exist - size on disk exists ( for an already saved document ) perhaps it will do ( or we need something else )
-+ m_docPropInfoMap[ word::WdBuiltInProperty::wdPropertyLines ] = DocPropInfo::createDocPropInfo( "Number of lines", "LineCount", office::MsoDocProperties::msoPropertyTypeNumber, aUsingStatsHelper ); // special handling
-+ m_docPropInfoMap[ word::WdBuiltInProperty::wdPropertyParas ] = DocPropInfo::createDocPropInfo( "Number of paragraphs", "", office::MsoDocProperties::msoPropertyTypeNumber, aUsingStatsHelper ); // special handling
-+ m_docPropInfoMap[ word::WdBuiltInProperty::wdPropertySlides ] = DocPropInfo::createDocPropInfo( "Number of slides", "" , office::MsoDocProperties::msoPropertyTypeNumber, aStandardHelper ); // doesn't seem to exist
-+ m_docPropInfoMap[ word::WdBuiltInProperty::wdPropertyNotes ] = DocPropInfo::createDocPropInfo( "Number of notes", "", office::MsoDocProperties::msoPropertyTypeNumber, aStandardHelper ); // doesn't seem to exist
-+ m_docPropInfoMap[ word::WdBuiltInProperty::wdPropertyHiddenSlides ] = DocPropInfo::createDocPropInfo("Number of hidden Slides", "", office::MsoDocProperties::msoPropertyTypeNumber, aStandardHelper ); // doesn't seem to exist
-+ m_docPropInfoMap[ word::WdBuiltInProperty::wdPropertyMMClips ] = DocPropInfo::createDocPropInfo( "Number of multimedia clips", "", office::MsoDocProperties::msoPropertyTypeNumber, aStandardHelper ); // doesn't seem to exist
-+ m_docPropInfoMap[ word::WdBuiltInProperty::wdPropertyHyperlinkBase ] = DocPropInfo::createDocPropInfo( "Hyperlink base", "AutoloadURL", office::MsoDocProperties::msoPropertyTypeString, aStandardHelper );
-+ m_docPropInfoMap[ word::WdBuiltInProperty::wdPropertyCharsWSpaces ] = DocPropInfo::createDocPropInfo( "Number of characters (with spaces)", "", office::MsoDocProperties::msoPropertyTypeNumber, aStandardHelper ); // doesn't seem to be supported
-+*/
-+ m_docPropInfoMap[ word::WdBuiltInProperty::wdPropertyTitle ] = DocPropInfo::createDocPropInfo( "Title", "Title", aStandardHelper );
-+ m_docPropInfoMap[ word::WdBuiltInProperty::wdPropertySubject ] = DocPropInfo::createDocPropInfo( "Subject", "Subject", aStandardHelper );
-+ m_docPropInfoMap[ word::WdBuiltInProperty::wdPropertyAuthor ] = DocPropInfo::createDocPropInfo( "Author", "Author", aStandardHelper );
-+ m_docPropInfoMap[ word::WdBuiltInProperty::wdPropertyKeywords ] = DocPropInfo::createDocPropInfo( "Keywords", "Keywords", aStandardHelper );
-+ m_docPropInfoMap[ word::WdBuiltInProperty::wdPropertyComments ] = DocPropInfo::createDocPropInfo( "Comments", "Description", aStandardHelper );
-+ m_docPropInfoMap[ word::WdBuiltInProperty::wdPropertyTemplate ] = DocPropInfo::createDocPropInfo( "Template", "Template", aStandardHelper );
-+ m_docPropInfoMap[ word::WdBuiltInProperty::wdPropertyLastAuthor ] = DocPropInfo::createDocPropInfo( "Last author", "ModifiedBy", aStandardHelper ); // doesn't seem to exist - throw or return nothing ?
-+ m_docPropInfoMap[ word::WdBuiltInProperty::wdPropertyRevision ] = DocPropInfo::createDocPropInfo( "Revision number", "EditingCycles", aStandardHelper ); // doesn't seem to exist - throw or return nothing ?
-+ m_docPropInfoMap[ word::WdBuiltInProperty::wdPropertyAppName ] = DocPropInfo::createDocPropInfo( "Application name", "Generator", aStandardHelper ); // doesn't seem to exist - throw or return nothing ?
-+ m_docPropInfoMap[ word::WdBuiltInProperty::wdPropertyTimeLastPrinted ] = DocPropInfo::createDocPropInfo( "Last print date", "PrintDate", aStandardHelper ); // doesn't seem to exist - throw or return nothing ?
-+ m_docPropInfoMap[ word::WdBuiltInProperty::wdPropertyTimeCreated ] = DocPropInfo::createDocPropInfo( "Creation date", "CreationDate", aStandardHelper );
-+ m_docPropInfoMap[ word::WdBuiltInProperty::wdPropertyTimeLastSaved ] = DocPropInfo::createDocPropInfo( "Last save time", "ModifyDate", aStandardHelper );
-+ m_docPropInfoMap[ word::WdBuiltInProperty::wdPropertyVBATotalEdit ] = DocPropInfo::createDocPropInfo( "Total editing time", "EditingDuration", aStandardHelper ); // Not sure if this is correct
-+ m_docPropInfoMap[ word::WdBuiltInProperty::wdPropertyPages ] = DocPropInfo::createDocPropInfo( "Number of pages", "PageCount", aUsingStatsHelper ); // special handling required ?
-+ m_docPropInfoMap[ word::WdBuiltInProperty::wdPropertyWords ] = DocPropInfo::createDocPropInfo( "Number of words", "WordCount", aUsingStatsHelper ); // special handling require ?
-+ m_docPropInfoMap[ word::WdBuiltInProperty::wdPropertyCharacters ] = DocPropInfo::createDocPropInfo( "Number of characters", "CharacterCount", aUsingStatsHelper ); // special handling required ?
-+ m_docPropInfoMap[ word::WdBuiltInProperty::wdPropertySecurity ] = DocPropInfo::createDocPropInfo( "Security", "", aStandardHelper ); // doesn't seem to exist
-+ m_docPropInfoMap[ word::WdBuiltInProperty::wdPropertyCategory ] = DocPropInfo::createDocPropInfo( "Category", "Category", aStandardHelper ); // hacked in
-+ m_docPropInfoMap[ word::WdBuiltInProperty::wdPropertyFormat ] = DocPropInfo::createDocPropInfo( "Format", "", aStandardHelper ); // doesn't seem to exist
-+ m_docPropInfoMap[ word::WdBuiltInProperty::wdPropertyManager ] = DocPropInfo::createDocPropInfo( "Manager", "Manager", aStandardHelper ); // hacked in
-+ m_docPropInfoMap[ word::WdBuiltInProperty::wdPropertyCompany ] = DocPropInfo::createDocPropInfo( "Company", "Company", aStandardHelper ); // hacked in
-+ m_docPropInfoMap[ word::WdBuiltInProperty::wdPropertyBytes ] = DocPropInfo::createDocPropInfo( "Number of bytes", "", aStandardHelper ); // doesn't seem to exist - size on disk exists ( for an already saved document ) perhaps it will do ( or we need something else )
-+ m_docPropInfoMap[ word::WdBuiltInProperty::wdPropertyLines ] = DocPropInfo::createDocPropInfo( "Number of lines", "LineCount", aUsingStatsHelper ); // special handling
-+ m_docPropInfoMap[ word::WdBuiltInProperty::wdPropertyParas ] = DocPropInfo::createDocPropInfo( "Number of paragraphs", "ParagraphCount", aUsingStatsHelper ); // special handling
-+ m_docPropInfoMap[ word::WdBuiltInProperty::wdPropertySlides ] = DocPropInfo::createDocPropInfo( "Number of slides", "" , aStandardHelper ); // doesn't seem to exist
-+ m_docPropInfoMap[ word::WdBuiltInProperty::wdPropertyNotes ] = DocPropInfo::createDocPropInfo( "Number of notes", "", aStandardHelper ); // doesn't seem to exist
-+ m_docPropInfoMap[ word::WdBuiltInProperty::wdPropertyHiddenSlides ] = DocPropInfo::createDocPropInfo("Number of hidden Slides", "", aStandardHelper ); // doesn't seem to exist
-+ m_docPropInfoMap[ word::WdBuiltInProperty::wdPropertyMMClips ] = DocPropInfo::createDocPropInfo( "Number of multimedia clips", "", aStandardHelper ); // doesn't seem to exist
-+ m_docPropInfoMap[ word::WdBuiltInProperty::wdPropertyHyperlinkBase ] = DocPropInfo::createDocPropInfo( "Hyperlink base", "AutoloadURL", aStandardHelper );
-+ m_docPropInfoMap[ word::WdBuiltInProperty::wdPropertyCharsWSpaces ] = DocPropInfo::createDocPropInfo( "Number of characters (with spaces)", "", aStandardHelper ); // doesn't seem to be supported
-+ }
-+
-+ MSOIndexToOODocPropInfo& getDocPropInfoMap() { return m_docPropInfoMap; }
-+};
-+
-+
-+typedef InheritedHelperInterfaceImpl1< ooo::vba::XDocumentProperty > SwVbaDocumentProperty_BASE;
-+
-+class SwVbaBuiltInDocumentProperty : public SwVbaDocumentProperty_BASE
-+{
-+protected:
-+ DocPropInfo mPropInfo;
-+public:
-+ SwVbaBuiltInDocumentProperty( const uno::Reference< ov::XHelperInterface >& xParent, const uno::Reference< uno::XComponentContext >& xContext, const DocPropInfo& rInfo );
-+ // XDocumentProperty
-+ virtual void SAL_CALL Delete( ) throw (script::BasicErrorException, uno::RuntimeException);
-+ virtual ::rtl::OUString SAL_CALL getName( ) throw (script::BasicErrorException, uno::RuntimeException);
-+ virtual void SAL_CALL setName( const ::rtl::OUString& Name ) throw (script::BasicErrorException, uno::RuntimeException);
-+ virtual ::sal_Int8 SAL_CALL getType( ) throw (script::BasicErrorException, uno::RuntimeException);
-+ virtual void SAL_CALL setType( ::sal_Int8 Type ) throw (script::BasicErrorException, uno::RuntimeException);
-+ virtual ::sal_Bool SAL_CALL getLinkToContent( ) throw (script::BasicErrorException, uno::RuntimeException);
-+ virtual void SAL_CALL setLinkToContent( ::sal_Bool LinkToContent ) throw (script::BasicErrorException, uno::RuntimeException);
-+ virtual uno::Any SAL_CALL getValue( ) throw (script::BasicErrorException, uno::RuntimeException);
-+ virtual void SAL_CALL setValue( const uno::Any& Value ) throw (script::BasicErrorException, uno::RuntimeException);
-+ virtual rtl::OUString SAL_CALL getLinkSource( ) throw (script::BasicErrorException, uno::RuntimeException);
-+ virtual void SAL_CALL setLinkSource( const rtl::OUString& LinkSource ) throw (script::BasicErrorException, uno::RuntimeException);
-+ //XDefaultProperty
-+ virtual ::rtl::OUString SAL_CALL getDefaultPropertyName( ) throw (uno::RuntimeException) { return rtl::OUString::createFromAscii("Value"); }
-+ // XHelperInterface
-+ virtual rtl::OUString& getServiceImplName();
-+ virtual uno::Sequence<rtl::OUString> getServiceNames();
-+};
-+
-+class SwVbaCustomDocumentProperty : public SwVbaBuiltInDocumentProperty
-+{
-+public:
-+
-+ SwVbaCustomDocumentProperty( const uno::Reference< ov::XHelperInterface >& xParent, const uno::Reference< uno::XComponentContext >& xContext, const DocPropInfo& rInfo );
-+
-+ virtual ::sal_Bool SAL_CALL getLinkToContent( ) throw (script::BasicErrorException, uno::RuntimeException);
-+ virtual void SAL_CALL setLinkToContent( ::sal_Bool LinkToContent ) throw (script::BasicErrorException, uno::RuntimeException);
-+
-+ virtual rtl::OUString SAL_CALL getLinkSource( ) throw (script::BasicErrorException, uno::RuntimeException);
-+ virtual void SAL_CALL setLinkSource( const rtl::OUString& LinkSource ) throw (script::BasicErrorException, uno::RuntimeException);
-+ virtual void SAL_CALL Delete( ) throw (script::BasicErrorException, uno::RuntimeException);
-+ virtual void SAL_CALL setName( const ::rtl::OUString& Name ) throw (script::BasicErrorException, uno::RuntimeException);
-+ virtual void SAL_CALL setType( ::sal_Int8 Type ) throw (script::BasicErrorException, uno::RuntimeException);
-+
-+};
-+
-+
-+SwVbaCustomDocumentProperty::SwVbaCustomDocumentProperty( const uno::Reference< ov::XHelperInterface >& xParent, const uno::Reference< uno::XComponentContext >& xContext, const DocPropInfo& rInfo ) : SwVbaBuiltInDocumentProperty( xParent, xContext, rInfo )
-+{
-+}
-+
-+sal_Bool
-+SwVbaCustomDocumentProperty::getLinkToContent( ) throw (script::BasicErrorException, uno::RuntimeException)
-+{
-+ // #FIXME we need to store the link content somewhere
-+ return sal_False;
-+}
-+
-+void
-+SwVbaCustomDocumentProperty::setLinkToContent( sal_Bool /*bLinkContent*/ ) throw (script::BasicErrorException, uno::RuntimeException)
-+{
-+}
-+
-+rtl::OUString
-+SwVbaCustomDocumentProperty::getLinkSource( ) throw (script::BasicErrorException, uno::RuntimeException)
-+{
-+ // #FIXME we need to store the link content somewhere
-+ return rtl::OUString();;
-+}
-+
-+void
-+SwVbaCustomDocumentProperty::setLinkSource( const rtl::OUString& /*rsLinkContent*/ ) throw (script::BasicErrorException, uno::RuntimeException)
-+{
-+ // #FIXME we need to store the link source somewhere
-+}
-+
-+void SAL_CALL
-+SwVbaCustomDocumentProperty::setName( const ::rtl::OUString& Name ) throw (script::BasicErrorException, uno::RuntimeException)
-+{
-+ // setName on existing property ?
-+ // #FIXME
-+ // do we need to delete existing property and create a new one?
-+}
-+
-+void SAL_CALL
-+SwVbaCustomDocumentProperty::setType( ::sal_Int8 Type ) throw (script::BasicErrorException, uno::RuntimeException)
-+{
-+ // setType, do we need to do a conversion?
-+ // #FIXME the underlying value needs to be changed to the new type
-+}
-+
-+void SAL_CALL
-+SwVbaCustomDocumentProperty::Delete( ) throw (script::BasicErrorException, uno::RuntimeException)
-+{
-+ uno::Reference< beans::XPropertyContainer > xContainer( mPropInfo.getUnoProperties(), uno::UNO_QUERY_THROW );
-+ xContainer->removeProperty( getName() );
-+}
-+
-+SwVbaBuiltInDocumentProperty::SwVbaBuiltInDocumentProperty( const uno::Reference< ov::XHelperInterface >& xParent, const uno::Reference< uno::XComponentContext >& xContext, const DocPropInfo& rInfo ) : SwVbaDocumentProperty_BASE( xParent, xContext ), mPropInfo( rInfo )
-+{
-+}
-+
-+void SAL_CALL
-+SwVbaBuiltInDocumentProperty::Delete( ) throw (script::BasicErrorException, uno::RuntimeException)
-+{
-+ // not valid for Builtin
-+ throw uno::RuntimeException();
-+}
-+
-+::rtl::OUString SAL_CALL
-+SwVbaBuiltInDocumentProperty::getName( ) throw (script::BasicErrorException, uno::RuntimeException)
-+{
-+ return mPropInfo.msMSODesc;
-+}
-+
-+void SAL_CALL
-+SwVbaBuiltInDocumentProperty::setName( const rtl::OUString& ) throw (script::BasicErrorException, uno::RuntimeException)
-+{
-+ // not valid for Builtin
-+ throw uno::RuntimeException();
-+}
-+
-+::sal_Int8 SAL_CALL
-+SwVbaBuiltInDocumentProperty::getType( ) throw (script::BasicErrorException, uno::RuntimeException)
-+{
-+ return lcl_toMSOPropType( getValue().getValueType() );
-+}
-+
-+void SAL_CALL
-+SwVbaBuiltInDocumentProperty::setType( ::sal_Int8 /*Type*/ ) throw (script::BasicErrorException, uno::RuntimeException)
-+{
-+ // not valid for Builtin
-+ throw uno::RuntimeException();
-+}
-+
-+::sal_Bool SAL_CALL
-+SwVbaBuiltInDocumentProperty::getLinkToContent( ) throw (script::BasicErrorException, uno::RuntimeException)
-+{
-+ return sal_False; // built-in always false
-+}
-+
-+void SAL_CALL
-+SwVbaBuiltInDocumentProperty::setLinkToContent( ::sal_Bool /*LinkToContent*/ ) throw (script::BasicErrorException, uno::RuntimeException)
-+{
-+ // not valid for Builtin
-+ throw uno::RuntimeException();
-+}
-+
-+uno::Any SAL_CALL
-+SwVbaBuiltInDocumentProperty::getValue( ) throw (script::BasicErrorException, uno::RuntimeException)
-+{
-+ uno::Any aRet = mPropInfo.getValue();
-+ if ( !aRet.hasValue() )
-+ throw uno::RuntimeException();
-+ return aRet;
-+}
-+
-+void SAL_CALL
-+SwVbaBuiltInDocumentProperty::setValue( const uno::Any& Value ) throw (script::BasicErrorException, uno::RuntimeException)
-+{
-+ mPropInfo.setValue( Value );
-+}
-+
-+rtl::OUString SAL_CALL
-+SwVbaBuiltInDocumentProperty::getLinkSource( ) throw (script::BasicErrorException, uno::RuntimeException)
-+{
-+ // not valid for Builtin
-+ throw uno::RuntimeException();
-+}
-+
-+void SAL_CALL
-+SwVbaBuiltInDocumentProperty::setLinkSource( const rtl::OUString& /*LinkSource*/ ) throw (script::BasicErrorException, uno::RuntimeException)
-+{
-+ // not valid for Builtin
-+ throw uno::RuntimeException();
-+}
-+
-+rtl::OUString&
-+SwVbaBuiltInDocumentProperty::getServiceImplName()
-+{
-+ static rtl::OUString sImplName( RTL_CONSTASCII_USTRINGPARAM("SwVbaBuiltinDocumentProperty") );
-+ return sImplName;
-+}
-+
-+uno::Sequence<rtl::OUString>
-+SwVbaBuiltInDocumentProperty::getServiceNames()
-+{
-+ static uno::Sequence< rtl::OUString > aServiceNames;
-+ if ( aServiceNames.getLength() == 0 )
-+ {
-+ aServiceNames.realloc( 1 );
-+ aServiceNames[ 0 ] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.word.DocumentProperty" ) );
-+ }
-+ return aServiceNames;
-+}
-+typedef ::cppu::WeakImplHelper3< com::sun::star::container::XIndexAccess
-+ ,com::sun::star::container::XNameAccess
-+ ,com::sun::star::container::XEnumerationAccess
-+ > PropertiesImpl_BASE;
-+
-+typedef std::hash_map< sal_Int32, uno::Reference< XDocumentProperty > > DocProps;
-+
-+typedef ::cppu::WeakImplHelper1< com::sun::star::container::XEnumeration > DocPropEnumeration_BASE;
-+class DocPropEnumeration : public DocPropEnumeration_BASE
-+{
-+ DocProps mDocProps;
-+ DocProps::iterator mIt;
-+public:
-+
-+ DocPropEnumeration( const DocProps& rProps ) : mDocProps( rProps ), mIt( mDocProps.begin() ) {}
-+ virtual ::sal_Bool SAL_CALL hasMoreElements( ) throw (uno::RuntimeException)
-+ {
-+ return mIt != mDocProps.end();
-+ }
-+ virtual uno::Any SAL_CALL nextElement( ) throw (container::NoSuchElementException, lang::WrappedTargetException, uno::RuntimeException)
-+ {
-+ if ( !hasMoreElements() )
-+ throw container::NoSuchElementException();
-+ return uno::makeAny( mIt++->second );
-+ }
-+};
-+
-+typedef std::hash_map< rtl::OUString, uno::Reference< XDocumentProperty >, ::rtl::OUStringHash, ::std::equal_to< ::rtl::OUString > > DocPropsByName;
-+
-+class BuiltInPropertiesImpl : public PropertiesImpl_BASE
-+{
-+protected:
-+
-+ uno::Reference< XHelperInterface > m_xParent;
-+ uno::Reference< uno::XComponentContext > m_xContext;
-+ uno::Reference< frame::XModel > m_xModel;
-+ uno::Reference< document::XDocumentInfo > m_xOOOBuiltIns;
-+
-+ DocProps mDocProps;
-+ DocPropsByName mNamedDocProps;
-+
-+ public:
-+ BuiltInPropertiesImpl( const uno::Reference< XHelperInterface >& xParent, const uno::Reference< uno::XComponentContext >& xContext, const uno::Reference< frame::XModel >& xModel ) : m_xParent( xParent ), m_xContext( xContext ), m_xModel( xModel )
-+ {
-+ BuiltInIndexHelper builtIns( m_xModel );
-+ for ( sal_Int32 index = word::WdBuiltInProperty::wdPropertyTitle; index <= word::WdBuiltInProperty::wdPropertyCharsWSpaces; ++index )
-+ {
-+ mDocProps[ index ] = new SwVbaBuiltInDocumentProperty( xParent, xContext, builtIns.getDocPropInfoMap()[ index ] );
-+ mNamedDocProps[ mDocProps[ index ]->getName() ] = mDocProps[ index ];
-+ }
-+ }
-+// XIndexAccess
-+ virtual ::sal_Int32 SAL_CALL getCount( ) throw (uno::RuntimeException)
-+ {
-+ return mDocProps.size();
-+ }
-+ virtual uno::Any SAL_CALL getByIndex( ::sal_Int32 Index ) throw (lang::IndexOutOfBoundsException, lang::WrappedTargetException )
-+ {
-+ // correct the correct by the base class for 1 based indices
-+ DocProps::iterator it = mDocProps.find( ++Index );
-+ if ( it == mDocProps.end() )
-+ throw lang::IndexOutOfBoundsException();
-+ return uno::makeAny( it->second );
-+ }
-+ virtual uno::Any SAL_CALL getByName( const ::rtl::OUString& aName ) throw (container::NoSuchElementException, lang::WrappedTargetException, uno::RuntimeException)
-+ {
-+ if ( !hasByName( aName ) )
-+ throw container::NoSuchElementException();
-+ DocPropsByName::iterator it = mNamedDocProps.find( aName );
-+ return uno::Any( it->second );
-+
-+ }
-+ virtual uno::Sequence< ::rtl::OUString > SAL_CALL getElementNames( ) throw (uno::RuntimeException)
-+ {
-+ uno::Sequence< rtl::OUString > aNames( getCount() );
-+ rtl::OUString* pName = aNames.getArray();
-+ DocPropsByName::iterator it_end = mNamedDocProps.end();
-+ for( DocPropsByName::iterator it = mNamedDocProps.begin(); it != it_end; ++it, ++pName )
-+ *pName = it->first;
-+ return aNames;
-+ }
-+
-+ virtual ::sal_Bool SAL_CALL hasByName( const ::rtl::OUString& aName ) throw (uno::RuntimeException)
-+ {
-+ DocPropsByName::iterator it = mNamedDocProps.find( aName );
-+ if ( it == mNamedDocProps.end() )
-+ return sal_False;
-+ return sal_True;
-+ }
-+// XElementAccess
-+ virtual uno::Type SAL_CALL getElementType( ) throw (uno::RuntimeException)
-+ {
-+ return XDocumentProperty::static_type(0);
-+ }
-+ virtual ::sal_Bool SAL_CALL hasElements( ) throw (uno::RuntimeException)
-+ {
-+ return mDocProps.size() > 0;
-+ }
-+ virtual uno::Reference< container::XEnumeration > SAL_CALL createEnumeration( ) throw (uno::RuntimeException)
-+ {
-+ return new DocPropEnumeration( mDocProps );
-+ }
-+};
-+
-+SwVbaBuiltinDocumentProperties::SwVbaBuiltinDocumentProperties( const uno::Reference< XHelperInterface >& xParent, const uno::Reference< uno::XComponentContext >& xContext, const uno::Reference< frame::XModel >& xModel ) : SwVbaDocumentproperties_BASE( xParent, xContext, uno::Reference< container::XIndexAccess >( new BuiltInPropertiesImpl( xParent, xContext, xModel ) ) ), m_xModel( xModel )
-+{
-+}
-+
-+uno::Reference< XDocumentProperty > SAL_CALL
-+SwVbaBuiltinDocumentProperties::Add( const ::rtl::OUString& /*Name*/, ::sal_Bool /*LinkToContent*/, ::sal_Int8 /*Type*/, const uno::Any& value, const uno::Any& /*LinkSource*/ ) throw (script::BasicErrorException, uno::RuntimeException)
-+{
-+ throw uno::RuntimeException(
-+ rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("not supported for Builtin properties") ), uno::Reference< uno::XInterface >() );
-+}
-+
-+// XEnumerationAccess
-+uno::Type SAL_CALL
-+SwVbaBuiltinDocumentProperties::getElementType() throw (uno::RuntimeException)
-+{
-+ return XDocumentProperty::static_type(0);
-+}
-+
-+uno::Reference< container::XEnumeration > SAL_CALL
-+SwVbaBuiltinDocumentProperties::createEnumeration() throw (uno::RuntimeException)
-+{
-+ uno::Reference< container::XEnumerationAccess > xEnumAccess( m_xIndexAccess, uno::UNO_QUERY_THROW );
-+ return xEnumAccess->createEnumeration();
-+}
-+
-+// ScVbaCollectionBaseImpl
-+uno::Any
-+SwVbaBuiltinDocumentProperties::createCollectionObject( const uno::Any& aSource )
-+{
-+ // pass through
-+ return aSource;
-+}
-+
-+// XHelperInterface
-+rtl::OUString&
-+SwVbaBuiltinDocumentProperties::getServiceImplName()
-+{
-+ static rtl::OUString sImplName( RTL_CONSTASCII_USTRINGPARAM("SwVbaBuiltinDocumentProperties") );
-+ return sImplName;
-+}
-+
-+uno::Sequence<rtl::OUString>
-+SwVbaBuiltinDocumentProperties::getServiceNames()
-+{
-+ static uno::Sequence< rtl::OUString > aServiceNames;
-+ if ( aServiceNames.getLength() == 0 )
-+ {
-+ aServiceNames.realloc( 1 );
-+ aServiceNames[ 0 ] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.word.DocumentProperties" ) );
-+ }
-+ return aServiceNames;
-+}
-+
-+class CustomPropertiesImpl : public PropertiesImpl_BASE
-+{
-+ uno::Reference< XHelperInterface > m_xParent;
-+ uno::Reference< uno::XComponentContext > m_xContext;
-+ uno::Reference< frame::XModel > m_xModel;
-+ uno::Reference< beans::XPropertySet > mxUserDefinedProp;
-+ boost::shared_ptr< PropertGetSetHelper > mpPropGetSetHelper;
-+public:
-+ CustomPropertiesImpl( const uno::Reference< XHelperInterface >& xParent, const uno::Reference< uno::XComponentContext >& xContext, const uno::Reference< frame::XModel >& xModel ) : m_xParent( xParent ), m_xContext( xContext ), m_xModel( xModel )
-+ {
-+ // suck in the document( custom ) properties
-+ uno::Reference< document::XDocumentInfoSupplier > xDocInfoSupp( m_xModel, uno::UNO_QUERY_THROW );
-+ uno::Reference< document::XDocumentPropertiesSupplier > xDocPropSupp( xDocInfoSupp->getDocumentInfo(), uno::UNO_QUERY_THROW );
-+ uno::Reference< document::XDocumentProperties > xDocProp( xDocPropSupp->getDocumentProperties(), uno::UNO_QUERY_THROW );
-+ mxUserDefinedProp.set( xDocProp->getUserDefinedProperties(), uno::UNO_QUERY_THROW );
-+ mpPropGetSetHelper.reset( new CustomPropertyGetSetHelper( m_xModel ) );
-+ };
-+ // XIndexAccess
-+ virtual ::sal_Int32 SAL_CALL getCount( ) throw (uno::RuntimeException)
-+ {
-+ return mxUserDefinedProp->getPropertySetInfo()->getProperties().getLength();
-+ }
-+
-+ virtual uno::Any SAL_CALL getByIndex( ::sal_Int32 Index ) throw (lang::IndexOutOfBoundsException, lang::WrappedTargetException )
-+ {
-+ uno::Sequence< beans::Property > aProps = mxUserDefinedProp->getPropertySetInfo()->getProperties();
-+ if ( Index >= aProps.getLength() )
-+ throw lang::IndexOutOfBoundsException();
-+ // How to determine type e.g Date? ( com.sun.star.util.DateTime )
-+ DocPropInfo aPropInfo = DocPropInfo::createDocPropInfo( aProps[ Index ].Name, aProps[ Index ].Name, mpPropGetSetHelper );
-+ return uno::makeAny( uno::Reference< XDocumentProperty >( new SwVbaCustomDocumentProperty( m_xParent, m_xContext, aPropInfo ) ) );
-+ }
-+
-+ virtual uno::Any SAL_CALL getByName( const ::rtl::OUString& aName ) throw (container::NoSuchElementException, lang::WrappedTargetException, uno::RuntimeException)
-+ {
-+ if ( !hasByName( aName ) )
-+ throw container::NoSuchElementException();
-+
-+ DocPropInfo aPropInfo = DocPropInfo::createDocPropInfo( aName, aName, mpPropGetSetHelper );
-+ return uno::makeAny( uno::Reference< XDocumentProperty >( new SwVbaCustomDocumentProperty( m_xParent, m_xContext, aPropInfo ) ) );
-+ }
-+
-+ virtual uno::Sequence< ::rtl::OUString > SAL_CALL getElementNames( ) throw (uno::RuntimeException)
-+ {
-+ uno::Sequence< beans::Property > aProps = mxUserDefinedProp->getPropertySetInfo()->getProperties();
-+ uno::Sequence< rtl::OUString > aNames( aProps.getLength() );
-+ rtl::OUString* pString = aNames.getArray();
-+ rtl::OUString* pEnd = ( pString + aNames.getLength() );
-+ beans::Property* pProp = aProps.getArray();
-+ for ( ; pString != pEnd; ++pString, ++pProp )
-+ *pString = pProp->Name;
-+ return aNames;
-+ }
-+
-+ virtual ::sal_Bool SAL_CALL hasByName( const ::rtl::OUString& aName ) throw (uno::RuntimeException)
-+ {
-+ OSL_TRACE("hasByName(%s) returns %d", rtl::OUStringToOString( aName, RTL_TEXTENCODING_UTF8 ).getStr(), mxUserDefinedProp->getPropertySetInfo()->hasPropertyByName( aName ) );
-+ return mxUserDefinedProp->getPropertySetInfo()->hasPropertyByName( aName );
-+ }
-+
-+ // XElementAccess
-+ virtual uno::Type SAL_CALL getElementType( ) throw (uno::RuntimeException)
-+ {
-+ return XDocumentProperty::static_type(0);
-+ }
-+
-+ virtual ::sal_Bool SAL_CALL hasElements( ) throw (uno::RuntimeException)
-+ {
-+ return getCount() > 0;
-+ }
-+
-+ virtual uno::Reference< container::XEnumeration > SAL_CALL createEnumeration( ) throw (uno::RuntimeException)
-+ {
-+ // create a map of properties ( the key doesn't matter )
-+ OSL_TRACE("Creating an enumeration");
-+ sal_Int32 key = 0;
-+ sal_Int32 nElem = getCount();
-+ DocProps simpleDocPropSnapShot;
-+ for ( ; key < nElem; ++key )
-+ simpleDocPropSnapShot[ key ].set( getByIndex( key ), uno::UNO_QUERY_THROW );
-+ OSL_TRACE("After creating the enumeration");
-+ return new DocPropEnumeration( simpleDocPropSnapShot );
-+ }
-+
-+ void addProp( const ::rtl::OUString& Name, ::sal_Int8 Type, const uno::Any& Value )
-+ {
-+ sal_Int16 attributes = 128;
-+ uno::Reference< beans::XPropertyContainer > xContainer( mxUserDefinedProp, uno::UNO_QUERY_THROW );
-+ // TODO fixme, perform the necessary Type Value conversions
-+ xContainer->addProperty( Name, attributes, Value );
-+ }
-+
-+};
-+
-+
-+SwVbaCustomDocumentProperties::SwVbaCustomDocumentProperties( const uno::Reference< XHelperInterface >& xParent, const uno::Reference< uno::XComponentContext >& xContext, const uno::Reference< frame::XModel >& xModel ) : SwVbaBuiltinDocumentProperties( xParent, xContext, xModel )
-+{
-+ // replace the m_xIndexAccess implementation ( we need a virtual init )
-+ m_xIndexAccess.set( new CustomPropertiesImpl( xParent, xContext, xModel ) );
-+ m_xNameAccess.set( m_xIndexAccess, uno::UNO_QUERY_THROW );
-+}
-+
-+uno::Reference< XDocumentProperty > SAL_CALL
-+SwVbaCustomDocumentProperties::Add( const ::rtl::OUString& Name, ::sal_Bool LinkToContent, ::sal_Int8 Type, const uno::Any& Value, const uno::Any& LinkSource ) throw (script::BasicErrorException, uno::RuntimeException)
-+{
-+ CustomPropertiesImpl* pCustomProps = dynamic_cast< CustomPropertiesImpl* > ( m_xIndexAccess.get() );
-+ uno::Reference< XDocumentProperty > xDocProp;
-+ if ( pCustomProps )
-+ {
-+ rtl::OUString sLinkSource;
-+ pCustomProps->addProp( Name, Type, Value );
-+
-+ xDocProp.set( m_xNameAccess->getByName( Name ), uno::UNO_QUERY_THROW );
-+ xDocProp->setLinkToContent( LinkToContent );
-+
-+ if ( LinkSource >>= sLinkSource )
-+ xDocProp->setLinkSource( sLinkSource );
-+ }
-+ return xDocProp;
-+}
-+
-+// XHelperInterface
-+rtl::OUString&
-+SwVbaCustomDocumentProperties::getServiceImplName()
-+{
-+ static rtl::OUString sImplName( RTL_CONSTASCII_USTRINGPARAM("SwVbaCustomDocumentProperties") );
-+ return sImplName;
-+}
---- sw/source/ui/vba/vbadocumentproperties.hxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ sw/source/ui/vba/vbadocumentproperties.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,70 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile: vbadocument.hxx,v $
-+ * $Revision: 1.4 $
-+ *
-+ * 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.
-+ *
-+ ************************************************************************/
-+#ifndef SW_VBA_DOCUMENTPROPERTIES_HXX
-+#define SW_VBA_DOCUMENTPROPERTIES_HXX
-+
-+#include <ooo/vba/XDocumentProperties.hpp>
-+#include <com/sun/star/frame/XModel.hpp>
-+#include <vbahelper/vbacollectionimpl.hxx>
-+#include <hash_map>
-+
-+typedef CollTestImplHelper< ov::XDocumentProperties > SwVbaDocumentproperties_BASE;
-+
-+class SwVbaBuiltinDocumentProperties : public SwVbaDocumentproperties_BASE
-+{
-+protected:
-+ css::uno::Reference< css::frame::XModel > m_xModel;
-+public:
-+ SwVbaBuiltinDocumentProperties( const css::uno::Reference< ov::XHelperInterface >& xParent, const css::uno::Reference< css::uno::XComponentContext > & xContext, const css::uno::Reference< css::frame::XModel >& xDocument );
-+
-+ // XDocumentProperties
-+ virtual css::uno::Reference< ::ooo::vba::XDocumentProperty > SAL_CALL Add( const ::rtl::OUString& Name, ::sal_Bool LinkToContent, ::sal_Int8 Type, const css::uno::Any& Value, const css::uno::Any& LinkSource ) throw (css::script::BasicErrorException, css::uno::RuntimeException);
-+ // XEnumerationAccess
-+ virtual css::uno::Type SAL_CALL getElementType() throw (css::uno::RuntimeException);
-+ virtual css::uno::Reference< css::container::XEnumeration > SAL_CALL createEnumeration() throw (css::uno::RuntimeException);
-+ // ScVbaCollectionBaseImpl
-+ virtual css::uno::Any createCollectionObject( const css::uno::Any& aSource );
-+
-+ // XHelperInterface
-+ virtual rtl::OUString& getServiceImplName();
-+ virtual css::uno::Sequence<rtl::OUString> getServiceNames();
-+};
-+
-+class SwVbaCustomDocumentProperties : public SwVbaBuiltinDocumentProperties
-+{
-+public:
-+ SwVbaCustomDocumentProperties( const css::uno::Reference< ov::XHelperInterface >& xParent, const css::uno::Reference< css::uno::XComponentContext > & xContext, const css::uno::Reference< css::frame::XModel >& xDocument );
-+// XDocumentProperties
-+ virtual css::uno::Reference< ::ooo::vba::XDocumentProperty > SAL_CALL Add( const ::rtl::OUString& Name, ::sal_Bool LinkToContent, ::sal_Int8 Type, const css::uno::Any& Value, const css::uno::Any& LinkSource ) throw (css::script::BasicErrorException, css::uno::RuntimeException);
-+ // XHelperInterface
-+ virtual rtl::OUString& getServiceImplName();
-+};
-+
-+#endif /* SW_VBA_DOCUMENTPROPERTY_HXX */
---- sw/source/ui/vba/vbaglobals.cxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ sw/source/ui/vba/vbaglobals.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,164 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile: vbaglobals.cxx,v $
-+ * $Revision: 1.4 $
-+ *
-+ * 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 <vbahelper/helperdecl.hxx>
-+#include "vbaglobals.hxx"
-+
-+#include <comphelper/unwrapargs.hxx>
-+
-+#include <com/sun/star/lang/XMultiComponentFactory.hpp>
-+#include <com/sun/star/beans/XPropertySet.hpp>
-+#include <com/sun/star/container/XNameContainer.hpp>
-+#include <cppuhelper/bootstrap.hxx>
-+#include "vbaapplication.hxx"
-+using namespace ::com::sun::star;
-+using namespace ::com::sun::star::uno;
-+using namespace ::ooo::vba;
-+
-+
-+
-+// =============================================================================
-+// SwVbaGlobals
-+// =============================================================================
-+
-+SwVbaGlobals::SwVbaGlobals( css::uno::Reference< css::uno::XComponentContext >const& rxContext ) : SwVbaGlobals_BASE( uno::Reference< XHelperInterface >(), rxContext )
-+{
-+ OSL_TRACE("SwVbaGlobals::SwVbaGlobals()");
-+ init( rxContext, uno::makeAny( getApplication() ) );
-+}
-+
-+SwVbaGlobals::~SwVbaGlobals()
-+{
-+ OSL_TRACE("SwVbaGlobals::~SwVbaGlobals");
-+}
-+
-+// =============================================================================
-+// XGlobals
-+// =============================================================================
-+uno::Reference<word::XApplication >
-+SwVbaGlobals::getApplication() throw (uno::RuntimeException)
-+{
-+ OSL_TRACE("In SwVbaGlobals::getApplication");
-+ static uno::Reference< word::XApplication > WordApplication( new SwVbaApplication( mxContext) );
-+ return WordApplication;
-+}
-+
-+uno::Reference<word::XSystem > SAL_CALL
-+SwVbaGlobals::getSystem() throw (uno::RuntimeException)
-+{
-+ return getApplication()->getSystem();
-+}
-+
-+uno::Reference< word::XDocument > SAL_CALL
-+SwVbaGlobals::getActiveDocument() throw (uno::RuntimeException)
-+{
-+ return getApplication()->getActiveDocument();
-+}
-+
-+uno::Reference< word::XWindow > SAL_CALL
-+SwVbaGlobals::getActiveWindow() throw (uno::RuntimeException)
-+{
-+ return getApplication()->getActiveWindow();
-+}
-+
-+rtl::OUString SAL_CALL
-+SwVbaGlobals::getName() throw (uno::RuntimeException)
-+{
-+ return getApplication()->getName();
-+}
-+
-+uno::Reference<word::XOptions > SAL_CALL
-+SwVbaGlobals::getOptions() throw (uno::RuntimeException)
-+{
-+ return getApplication()->getOptions();
-+}
-+
-+uno::Any SAL_CALL
-+SwVbaGlobals::CommandBars( const uno::Any& aIndex ) throw (uno::RuntimeException)
-+{
-+ return getApplication()->CommandBars( aIndex );
-+}
-+
-+uno::Reference<word::XSelection > SAL_CALL
-+SwVbaGlobals::getSelection() throw (uno::RuntimeException)
-+{
-+ return getApplication()->getSelection();
-+}
-+
-+rtl::OUString&
-+SwVbaGlobals::getServiceImplName()
-+{
-+ static rtl::OUString sImplName( RTL_CONSTASCII_USTRINGPARAM("SwVbaGlobals") );
-+ return sImplName;
-+}
-+
-+uno::Sequence< rtl::OUString >
-+SwVbaGlobals::getServiceNames()
-+{
-+ static uno::Sequence< rtl::OUString > aServiceNames;
-+ if ( aServiceNames.getLength() == 0 )
-+ {
-+ aServiceNames.realloc( 1 );
-+ aServiceNames[ 0 ] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.word.Globals" ) );
-+ }
-+ return aServiceNames;
-+}
-+
-+uno::Sequence< rtl::OUString >
-+SwVbaGlobals::getAvailableServiceNames( ) throw (uno::RuntimeException)
-+{
-+ static bool bInit = false;
-+ static uno::Sequence< rtl::OUString > serviceNames( SwVbaGlobals_BASE::getAvailableServiceNames() );
-+ if ( !bInit )
-+ {
-+ rtl::OUString names[] = {
-+ ::rtl::OUString( RTL_CONSTASCII_USTRINGPARAM ( "ooo.vba.word.Document" ) ),
-+// #FIXME #TODO make Application a proper service
-+// ::rtl::OUString( RTL_CONSTASCII_USTRINGPARAM ( "ooo.vba.word.Application" ) ),
-+ };
-+ sal_Int32 nWordServices = ( sizeof( names )/ sizeof( names[0] ) );
-+ sal_Int32 startIndex = serviceNames.getLength();
-+ serviceNames.realloc( serviceNames.getLength() + nWordServices );
-+ for ( sal_Int32 index = 0; index < nWordServices; ++index )
-+ serviceNames[ startIndex + index ] = names[ index ];
-+ bInit = true;
-+ }
-+ return serviceNames;
-+}
-+
-+namespace globals
-+{
-+namespace sdecl = comphelper::service_decl;
-+sdecl::vba_service_class_<SwVbaGlobals, sdecl::with_args<false> > serviceImpl;
-+extern sdecl::ServiceDecl const serviceDecl(
-+ serviceImpl,
-+ "SwVbaGlobals",
-+ "ooo.vba.word.Globals" );
-+}
-+
---- sw/source/ui/vba/vbaglobals.hxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ sw/source/ui/vba/vbaglobals.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,80 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile: vbaglobals.hxx,v $
-+ * $Revision: 1.4 $
-+ *
-+ * 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.
-+ *
-+ ************************************************************************/
-+#ifndef SW_VBA_GLOBALS_HXX
-+#define SW_VBA_GLOBALS_HXX
-+
-+#include <com/sun/star/lang/XServiceInfo.hpp>
-+#include <com/sun/star/lang/XInitialization.hpp>
-+#include <com/sun/star/uno/XComponentContext.hpp>
-+#include <ooo/vba/word/XGlobals.hpp>
-+#include <ooo/vba/word/XApplication.hpp>
-+#include <ooo/vba/word/XSystem.hpp>
-+#include <ooo/vba/word/XOptions.hpp>
-+#include <ooo/vba/word/XSelection.hpp>
-+
-+#include <cppuhelper/implbase1.hxx>
-+#include <vbahelper/vbahelper.hxx>
-+#include <vbahelper/vbaglobalbase.hxx>
-+
-+// =============================================================================
-+// class SwVbaGlobals
-+// =============================================================================
-+
-+
-+typedef ::cppu::ImplInheritanceHelper1< VbaGlobalsBase, ov::word::XGlobals > SwVbaGlobals_BASE;
-+
-+class SwVbaGlobals : public SwVbaGlobals_BASE
-+{
-+private:
-+ css::uno::Reference< ooo::vba::word::XApplication > mxApplication;
-+
-+ virtual css::uno::Reference< ooo::vba::word::XApplication > getApplication() throw (css::uno::RuntimeException);
-+
-+public:
-+
-+ SwVbaGlobals( css::uno::Reference< css::uno::XComponentContext >const& rxContext );
-+ virtual ~SwVbaGlobals();
-+
-+ // XGlobals
-+ virtual ::rtl::OUString SAL_CALL getName() throw (css::uno::RuntimeException);
-+ virtual css::uno::Reference< ooo::vba::word::XSystem > SAL_CALL getSystem() throw (css::uno::RuntimeException);
-+ virtual css::uno::Reference< ov::word::XDocument > SAL_CALL getActiveDocument() throw (css::uno::RuntimeException);
-+ virtual css::uno::Reference< ov::word::XWindow > SAL_CALL getActiveWindow() throw (css::uno::RuntimeException);
-+ virtual css::uno::Reference< ooo::vba::word::XOptions > SAL_CALL getOptions() throw (css::uno::RuntimeException);
-+ virtual css::uno::Reference< ooo::vba::word::XSelection > SAL_CALL getSelection() throw (css::uno::RuntimeException);
-+ virtual css::uno::Any SAL_CALL CommandBars( const css::uno::Any& aIndex ) throw (css::uno::RuntimeException);
-+ // XMultiServiceFactory
-+ virtual css::uno::Sequence< ::rtl::OUString > SAL_CALL getAvailableServiceNames( ) throw (css::uno::RuntimeException);
-+
-+ // XHelperInterface
-+ virtual rtl::OUString& getServiceImplName();
-+ virtual css::uno::Sequence<rtl::OUString> getServiceNames();
-+};
-+#endif /* SW_VBA_GLOBALS_HXX */
---- sw/source/ui/vba/vbaoptions.cxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ sw/source/ui/vba/vbaoptions.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,148 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microoptionss, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile:
-+ * $Revision:
-+ *
-+ * 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 "vbaoptions.hxx"
-+#include <vbahelper/vbahelper.hxx>
-+#include <ooo/vba/word/WdDefaultFilePath.hpp>
-+#include <com/sun/star/util/XStringSubstitution.hpp>
-+#include <com/sun/star/beans/XPropertySet.hpp>
-+#include <osl/file.hxx>
-+
-+using namespace ::ooo::vba;
-+using namespace ::com::sun::star;
-+
-+SwVbaOptions::SwVbaOptions( uno::Reference<uno::XComponentContext >& xContext ) throw ( uno::RuntimeException ) : SwVbaOptions_BASE( uno::Reference< XHelperInterface >(), xContext )
-+{
-+ mxFactory.set( comphelper::getProcessServiceFactory(), uno::UNO_QUERY_THROW );
-+}
-+
-+SwVbaOptions::~SwVbaOptions()
-+{
-+}
-+
-+uno::Any SAL_CALL
-+SwVbaOptions::DefaultFilePath( sal_Int32 _path ) throw ( uno::RuntimeException )
-+{
-+ switch( _path )
-+ {
-+ case word::WdDefaultFilePath::wdDocumentsPath:
-+ {
-+ msDefaultFilePath = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("Work") );
-+ break;
-+ }
-+ case word::WdDefaultFilePath::wdPicturesPath:
-+ {
-+ msDefaultFilePath = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("Gallery") );
-+ break;
-+ }
-+ case word::WdDefaultFilePath::wdUserTemplatesPath:
-+ case word::WdDefaultFilePath::wdWorkgroupTemplatesPath:
-+ {
-+ msDefaultFilePath = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("Template") );
-+ break;
-+ }
-+ case word::WdDefaultFilePath::wdUserOptionsPath:
-+ {
-+ msDefaultFilePath = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("UserConfig") );
-+ break;
-+ }
-+ case word::WdDefaultFilePath::wdToolsPath:
-+ case word::WdDefaultFilePath::wdProgramPath:
-+ {
-+ msDefaultFilePath = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("Module") );
-+ break;
-+ }
-+ case word::WdDefaultFilePath::wdTempFilePath:
-+ {
-+ msDefaultFilePath = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("Temp") );
-+ break;
-+ }
-+ default:
-+ {
-+ DebugHelper::exception( SbERR_NOT_IMPLEMENTED, rtl::OUString() );
-+ break;
-+ }
-+ }
-+ return uno::makeAny( uno::Reference< XPropValue > ( new ScVbaPropValue( this ) ) );
-+}
-+
-+void SwVbaOptions::setValueEvent( const uno::Any& value )
-+{
-+ rtl::OUString sNewPath;
-+ value >>= sNewPath;
-+ rtl::OUString sNewPathUrl;
-+ ::osl::File::getFileURLFromSystemPath( sNewPath, sNewPathUrl );
-+ uno::Reference< beans::XPropertySet > xPathSettings( mxFactory->createInstance( rtl::OUString::createFromAscii("com.sun.star.util.PathSettings") ), uno::UNO_QUERY_THROW );
-+ rtl::OUString sOldPathUrl;
-+ xPathSettings->getPropertyValue( msDefaultFilePath ) >>= sOldPathUrl;
-+ // path could be a multipath, Microsoft doesn't support this feature in Word currently
-+ // only the last path is from interest.
-+ sal_Int32 nIndex = sOldPathUrl.lastIndexOf( sal_Unicode(';') );
-+ if( nIndex != -1 )
-+ {
-+ sNewPathUrl = sOldPathUrl.copy( 0, nIndex + 1 ).concat( sNewPathUrl );
-+ }
-+ xPathSettings->setPropertyValue( msDefaultFilePath, uno::makeAny( sNewPathUrl ) );
-+}
-+
-+uno::Any SwVbaOptions::getValueEvent()
-+{
-+ uno::Reference< beans::XPropertySet > xPathSettings( mxFactory->createInstance( rtl::OUString::createFromAscii("com.sun.star.util.PathSettings") ), uno::UNO_QUERY_THROW );
-+ rtl::OUString sPathUrl;
-+ xPathSettings->getPropertyValue( msDefaultFilePath ) >>= sPathUrl;
-+ // path could be a multipath, Microsoft doesn't support this feature in Word currently
-+ // only the last path is from interest.
-+ sal_Int32 nIndex = sPathUrl.lastIndexOf( sal_Unicode(';') );
-+ if( nIndex != -1 )
-+ {
-+ sPathUrl = sPathUrl.copy( nIndex + 1 );
-+ }
-+ rtl::OUString sPath;
-+ ::osl::File::getSystemPathFromFileURL( sPathUrl, sPath );
-+ return uno::makeAny( sPath );
-+}
-+
-+rtl::OUString&
-+SwVbaOptions::getServiceImplName()
-+{
-+ static rtl::OUString sImplName( RTL_CONSTASCII_USTRINGPARAM("SwVbaOptions") );
-+ return sImplName;
-+}
-+
-+uno::Sequence< rtl::OUString >
-+SwVbaOptions::getServiceNames()
-+{
-+ static uno::Sequence< rtl::OUString > aServiceNames;
-+ if ( aServiceNames.getLength() == 0 )
-+ {
-+ aServiceNames.realloc( 1 );
-+ aServiceNames[ 0 ] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.word.Options" ) );
-+ }
-+ return aServiceNames;
-+}
---- sw/source/ui/vba/vbaoptions.hxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ sw/source/ui/vba/vbaoptions.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,62 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile: vbasystem.hxx,v $
-+ * $Revision: 1.4 $
-+ *
-+ * 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.
-+ *
-+ ************************************************************************/
-+#ifndef SW_VBA_OPTIONS_HXX
-+#define SW_VBA_OPTIONS_HXX
-+
-+#include <ooo/vba/word/XOptions.hpp>
-+#include <vbahelper/vbahelperinterface.hxx>
-+#include <cppuhelper/implbase1.hxx>
-+#include <vbahelper/vbapropvalue.hxx>
-+#include <comphelper/processfactory.hxx>
-+
-+typedef InheritedHelperInterfaceImpl1< ooo::vba::word::XOptions > SwVbaOptions_BASE;
-+
-+class SwVbaOptions : public SwVbaOptions_BASE,
-+ public PropListener
-+{
-+private:
-+ rtl::OUString msDefaultFilePath;
-+ css::uno::Reference< css::lang::XMultiServiceFactory > mxFactory;
-+public:
-+ SwVbaOptions( css::uno::Reference< css::uno::XComponentContext >& m_xContext ) throw ( css::uno::RuntimeException );
-+ virtual ~SwVbaOptions();
-+
-+ // XOptions
-+ virtual css::uno::Any SAL_CALL DefaultFilePath( sal_Int32 _path ) throw ( css::uno::RuntimeException );
-+
-+ //PropListener
-+ virtual void setValueEvent( const css::uno::Any& value );
-+ virtual css::uno::Any getValueEvent();
-+
-+ // XHelperInterface
-+ virtual rtl::OUString& getServiceImplName();
-+ virtual css::uno::Sequence<rtl::OUString> getServiceNames();
-+};
-+#endif /* SW_VBA_OPTIONS_HXX */
---- sw/source/ui/vba/vbapane.cxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ sw/source/ui/vba/vbapane.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,79 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile:
-+ * $Revision:
-+ *
-+ * 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 "vbapane.hxx"
-+#include <vbahelper/vbahelper.hxx>
-+#include <tools/diagnose_ex.h>
-+#include "vbaview.hxx"
-+
-+using namespace ::ooo::vba;
-+using namespace ::com::sun::star;
-+
-+SwVbaPane::SwVbaPane( const uno::Reference< ooo::vba::XHelperInterface >& rParent, const uno::Reference< uno::XComponentContext >& rContext,
-+ const uno::Reference< frame::XModel >& xModel ) throw ( uno::RuntimeException ) :
-+ SwVbaPane_BASE( rParent, rContext ), mxModel( xModel )
-+{
-+}
-+
-+SwVbaPane::~SwVbaPane()
-+{
-+}
-+
-+uno::Any SAL_CALL
-+SwVbaPane::View() throw ( css::uno::RuntimeException )
-+{
-+ return uno::makeAny( uno::Reference< word::XView >( new SwVbaView( this, mxContext, mxModel ) ) );
-+}
-+
-+void SAL_CALL
-+SwVbaPane::Close( ) throw ( css::uno::RuntimeException )
-+{
-+ rtl::OUString url = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( ".uno:CloseWin"));
-+ dispatchRequests( mxModel,url );
-+}
-+
-+rtl::OUString&
-+SwVbaPane::getServiceImplName()
-+{
-+ static rtl::OUString sImplName( RTL_CONSTASCII_USTRINGPARAM("SwVbaPane") );
-+ return sImplName;
-+}
-+
-+uno::Sequence< rtl::OUString >
-+SwVbaPane::getServiceNames()
-+{
-+ static uno::Sequence< rtl::OUString > aServiceNames;
-+ if ( aServiceNames.getLength() == 0 )
-+ {
-+ aServiceNames.realloc( 1 );
-+ aServiceNames[ 0 ] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.word.Pane" ) );
-+ }
-+ return aServiceNames;
-+}
-+
---- sw/source/ui/vba/vbapane.hxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ sw/source/ui/vba/vbapane.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,57 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile:
-+ * $Revision:
-+ *
-+ * 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.
-+ *
-+ ************************************************************************/
-+#ifndef SW_VBA_PANE_HXX
-+#define SW_VBA_PANE_HXX
-+
-+#include <ooo/vba/word/XPane.hpp>
-+#include <vbahelper/vbahelperinterface.hxx>
-+#include <cppuhelper/implbase1.hxx>
-+
-+typedef InheritedHelperInterfaceImpl1< ooo::vba::word::XPane > SwVbaPane_BASE;
-+
-+class SwVbaPane : public SwVbaPane_BASE
-+{
-+private:
-+ css::uno::Reference< css::frame::XModel > mxModel;
-+
-+public:
-+ SwVbaPane( const css::uno::Reference< ooo::vba::XHelperInterface >& rParent, const css::uno::Reference< css::uno::XComponentContext >& rContext,
-+ const css::uno::Reference< css::frame::XModel >& xModel ) throw ( css::uno::RuntimeException );
-+ virtual ~SwVbaPane();
-+
-+ // Methods
-+ virtual css::uno::Any SAL_CALL View( ) throw (css::uno::RuntimeException);
-+ virtual void SAL_CALL Close( ) throw (css::uno::RuntimeException);
-+
-+ // XHelperInterface
-+ virtual rtl::OUString& getServiceImplName();
-+ virtual css::uno::Sequence<rtl::OUString> getServiceNames();
-+};
-+#endif /* SW_VBA_PANE_HXX */
---- sw/source/ui/vba/vbapanes.cxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ sw/source/ui/vba/vbapanes.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,127 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile:
-+ * $Revision:
-+ *
-+ * 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 "vbapanes.hxx"
-+#include "vbapane.hxx"
-+
-+using namespace ::ooo::vba;
-+using namespace ::com::sun::star;
-+
-+// I assume there is only one pane in Writer
-+typedef ::cppu::WeakImplHelper1<container::XIndexAccess > PanesIndexAccess_Base;
-+class PanesIndexAccess : public PanesIndexAccess_Base
-+{
-+private:
-+ uno::Reference< XHelperInterface > mxParent;
-+ uno::Reference< uno::XComponentContext > mxContext;
-+ uno::Reference< frame::XModel > mxModel;
-+
-+public:
-+ PanesIndexAccess( const uno::Reference< XHelperInterface >& xParent, const uno::Reference< uno::XComponentContext >& xContext, const uno::Reference< frame::XModel >& xModel ) : mxParent( xParent ), mxContext( xContext ), mxModel( xModel ) {}
-+ ~PanesIndexAccess(){}
-+
-+ // XIndexAccess
-+ virtual sal_Int32 SAL_CALL getCount( ) throw (uno::RuntimeException)
-+ {
-+ return 1;
-+ }
-+ virtual uno::Any SAL_CALL getByIndex( sal_Int32 Index ) throw (lang::IndexOutOfBoundsException, lang::WrappedTargetException, uno::RuntimeException)
-+ {
-+ if( Index != 1 )
-+ throw container::NoSuchElementException();
-+ return uno::makeAny( uno::Reference< word::XPane >( new SwVbaPane( mxParent, mxContext, mxModel ) ) );
-+ }
-+ virtual uno::Type SAL_CALL getElementType( ) throw (uno::RuntimeException)
-+ {
-+ return word::XPane::static_type(0);
-+ }
-+ virtual sal_Bool SAL_CALL hasElements( ) throw (uno::RuntimeException)
-+ {
-+ return sal_True;
-+ }
-+};
-+
-+class PanesEnumWrapper : public EnumerationHelper_BASE
-+{
-+ uno::Reference<container::XIndexAccess > m_xIndexAccess;
-+ sal_Int32 nIndex;
-+public:
-+ PanesEnumWrapper( const uno::Reference< container::XIndexAccess >& xIndexAccess ) : m_xIndexAccess( xIndexAccess ), nIndex( 0 ) {}
-+ virtual ::sal_Bool SAL_CALL hasMoreElements( ) throw (uno::RuntimeException)
-+ {
-+ return ( nIndex < m_xIndexAccess->getCount() );
-+ }
-+
-+ virtual uno::Any SAL_CALL nextElement( ) throw (container::NoSuchElementException, lang::WrappedTargetException, uno::RuntimeException)
-+ {
-+ if ( nIndex < m_xIndexAccess->getCount() )
-+ return m_xIndexAccess->getByIndex( nIndex++ );
-+ throw container::NoSuchElementException();
-+ }
-+};
-+
-+SwVbaPanes::SwVbaPanes( const uno::Reference< XHelperInterface >& xParent, const uno::Reference< uno::XComponentContext > & xContext, const uno::Reference< frame::XModel >& xModel ): SwVbaPanes_BASE( xParent, xContext, new PanesIndexAccess( xParent, xContext, xModel ) ), mxModel( xModel )
-+{
-+}
-+// XEnumerationAccess
-+uno::Type
-+SwVbaPanes::getElementType() throw (uno::RuntimeException)
-+{
-+ return word::XPane::static_type(0);
-+}
-+uno::Reference< container::XEnumeration >
-+SwVbaPanes::createEnumeration() throw (uno::RuntimeException)
-+{
-+ return new PanesEnumWrapper( m_xIndexAccess );
-+}
-+
-+uno::Any
-+SwVbaPanes::createCollectionObject( const css::uno::Any& aSource )
-+{
-+ return aSource;
-+}
-+
-+rtl::OUString&
-+SwVbaPanes::getServiceImplName()
-+{
-+ static rtl::OUString sImplName( RTL_CONSTASCII_USTRINGPARAM("SwVbaPanes") );
-+ return sImplName;
-+}
-+
-+css::uno::Sequence<rtl::OUString>
-+SwVbaPanes::getServiceNames()
-+{
-+ static uno::Sequence< rtl::OUString > sNames;
-+ if ( sNames.getLength() == 0 )
-+ {
-+ sNames.realloc( 1 );
-+ sNames[0] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.word.Panes") );
-+ }
-+ return sNames;
-+}
---- sw/source/ui/vba/vbapanes.hxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ sw/source/ui/vba/vbapanes.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,60 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile:
-+ * $Revision:
-+ *
-+ * 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.
-+ *
-+ ************************************************************************/
-+#ifndef SW_VBA_PANES_HXX
-+#define SW_VBA_PANES_HXX
-+
-+#include <vbahelper/vbacollectionimpl.hxx>
-+#include <ooo/vba/word/XPanes.hpp>
-+#include <com/sun/star/container/XEnumerationAccess.hpp>
-+#include <com/sun/star/container/XIndexAccess.hpp>
-+#include <vbahelper/vbahelperinterface.hxx>
-+
-+typedef CollTestImplHelper< ooo::vba::word::XPanes > SwVbaPanes_BASE;
-+
-+class SwVbaPanes : public SwVbaPanes_BASE
-+{
-+private:
-+ css::uno::Reference< css::frame::XModel > mxModel;
-+
-+public:
-+ SwVbaPanes( const css::uno::Reference< ov::XHelperInterface >& xParent, const css::uno::Reference< css::uno::XComponentContext > & xContext, const css::uno::Reference< css::frame::XModel >& xModel );
-+ virtual ~SwVbaPanes() {}
-+
-+ // XEnumerationAccess
-+ virtual css::uno::Type SAL_CALL getElementType() throw (css::uno::RuntimeException);
-+ virtual css::uno::Reference< css::container::XEnumeration > SAL_CALL createEnumeration() throw (css::uno::RuntimeException);
-+
-+ // SwVbaPanes_BASE
-+ virtual css::uno::Any createCollectionObject( const css::uno::Any& aSource );
-+ virtual rtl::OUString& getServiceImplName();
-+ virtual css::uno::Sequence<rtl::OUString> getServiceNames();
-+};
-+
-+#endif /* SW_VBA_PANES_HXX */
---- sw/source/ui/vba/vbarange.cxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ sw/source/ui/vba/vbarange.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,302 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile:
-+ * $Revision:
-+ *
-+ * 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 "vbarange.hxx"
-+#include <vbahelper/vbahelper.hxx>
-+#include <tools/diagnose_ex.h>
-+#include "vbarangehelper.hxx"
-+#include <com/sun/star/text/XTextDocument.hpp>
-+#include <ooo/vba/word/WdBreakType.hpp>
-+#include <com/sun/star/style/BreakType.hpp>
-+
-+using namespace ::ooo::vba;
-+using namespace ::com::sun::star;
-+
-+typedef InheritedHelperInterfaceImpl1< ooo::vba::word::XRange > SwVbaBaseRange_BASE;
-+
-+class SwVbaBaseRange : public SwVbaBaseRange_BASE
-+{
-+protected:
-+ uno::Reference< text::XTextDocument > mxTextDocument;
-+ uno::Reference< text::XTextCursor > mxTextCursor;
-+ uno::Reference< text::XText > mxText;
-+ sal_Bool mbMaySpanEndOfDocument;
-+
-+ SwVbaBaseRange( const uno::Reference< ooo::vba::XHelperInterface >& rParent, const uno::Reference< uno::XComponentContext >& rContext );
-+ virtual ~SwVbaBaseRange();
-+
-+public:
-+ uno::Reference< text::XTextRange > getXTextRange() throw (uno::RuntimeException);
-+
-+ // XRange
-+ virtual rtl::OUString SAL_CALL getText() throw (uno::RuntimeException);
-+ virtual void SAL_CALL setText( const rtl::OUString& rText ) throw (uno::RuntimeException);
-+
-+ // Methods
-+ virtual void SAL_CALL InsertBreak( const uno::Any& _breakType ) throw (uno::RuntimeException);
-+
-+ // XHelperInterface
-+ virtual rtl::OUString& getServiceImplName();
-+ virtual uno::Sequence<rtl::OUString> getServiceNames();
-+};
-+
-+
-+SwVbaBaseRange::SwVbaBaseRange( const uno::Reference< ooo::vba::XHelperInterface >& rParent, const uno::Reference< uno::XComponentContext >& rContext )
-+ : SwVbaBaseRange_BASE( rParent, rContext )
-+{
-+}
-+
-+SwVbaBaseRange::~SwVbaBaseRange()
-+{
-+}
-+
-+uno::Reference< text::XTextRange >
-+SwVbaBaseRange::getXTextRange() throw (uno::RuntimeException)
-+{
-+ uno::Reference< text::XTextRange > xTextRange( mxTextCursor, uno::UNO_QUERY_THROW );
-+ return xTextRange;
-+}
-+
-+/**
-+* The complexity in this method is because we need to workaround
-+* an issue that the last paragraph in a document does not have a trailing CRLF.
-+* @return
-+*/
-+rtl::OUString SAL_CALL
-+SwVbaBaseRange::getText() throw ( uno::RuntimeException )
-+{
-+ rtl::OUString aText = mxTextCursor->getString();
-+ sal_Int32 nLen = aText.getLength();
-+
-+ // FIXME: should add a line separator if the range includes the last paragraph
-+ if( nLen == 0 )
-+ {
-+ if( mxTextCursor->isCollapsed() )
-+ {
-+ mxTextCursor->goRight( 1, sal_True );
-+ aText = mxTextCursor->getString();
-+ mxTextCursor->collapseToStart();
-+ }
-+ else
-+ {
-+ uno::Reference< text::XTextRange > xStart = mxTextCursor->getStart();
-+ uno::Reference< text::XTextRange > xEnd = mxTextCursor->getEnd();
-+ mxTextCursor->collapseToEnd();
-+ mxTextCursor->goRight( 1, sal_True );
-+ mxTextCursor->gotoRange( xStart, sal_False );
-+ mxTextCursor->gotoRange( xEnd, sal_True );
-+ }
-+ }
-+
-+ return aText;
-+}
-+
-+void SAL_CALL
-+SwVbaBaseRange::setText( const rtl::OUString& rText ) throw ( uno::RuntimeException )
-+{
-+ if( rText.indexOf( '\n' ) != -1 )
-+ {
-+ mxTextCursor->setString( rtl::OUString() );
-+ // process CR in strings
-+ uno::Reference< text::XTextRange > xRange( mxTextCursor, uno::UNO_QUERY_THROW );
-+ SwVbaRangeHelper::insertString( xRange, mxText, rText, sal_True );
-+ }
-+ else
-+ {
-+ mxTextCursor->setString( rText );
-+ }
-+}
-+
-+// FIXME: test is not pass
-+void SAL_CALL SwVbaBaseRange::InsertBreak( const uno::Any& _breakType ) throw (uno::RuntimeException)
-+{
-+ // default type is wdPageBreak;
-+ sal_Int32 nBreakType = word::WdBreakType::wdPageBreak;
-+ if( _breakType.hasValue() )
-+ _breakType >>= nBreakType;
-+
-+ style::BreakType eBreakType = style::BreakType_NONE;
-+ switch( nBreakType )
-+ {
-+ case word::WdBreakType::wdPageBreak:
-+ eBreakType = style::BreakType_PAGE_AFTER;
-+ break;
-+ case word::WdBreakType::wdColumnBreak:
-+ eBreakType = style::BreakType_COLUMN_AFTER;
-+ break;
-+ case word::WdBreakType::wdLineBreak:
-+ case word::WdBreakType::wdLineBreakClearLeft:
-+ case word::WdBreakType::wdLineBreakClearRight:
-+ case word::WdBreakType::wdSectionBreakContinuous:
-+ case word::WdBreakType::wdSectionBreakEvenPage:
-+ case word::WdBreakType::wdSectionBreakNextPage:
-+ case word::WdBreakType::wdSectionBreakOddPage:
-+ case word::WdBreakType::wdTextWrappingBreak:
-+ DebugHelper::exception( SbERR_NOT_IMPLEMENTED, rtl::OUString() );
-+ break;
-+ default:
-+ DebugHelper::exception( SbERR_BAD_PARAMETER, rtl::OUString() );
-+ }
-+
-+ if( eBreakType != style::BreakType_NONE )
-+ {
-+ if( !mxTextCursor->isCollapsed() )
-+ {
-+ mxTextCursor->setString( rtl::OUString() );
-+ mxTextCursor->collapseToStart();
-+ }
-+
-+ uno::Reference< beans::XPropertySet > xProp( mxTextCursor, uno::UNO_QUERY_THROW );
-+ xProp->setPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("BreakType") ), uno::makeAny( eBreakType ) );
-+ }
-+}
-+
-+rtl::OUString&
-+SwVbaBaseRange::getServiceImplName()
-+{
-+ static rtl::OUString sImplName( RTL_CONSTASCII_USTRINGPARAM("SwVbaBaseRange") );
-+ return sImplName;
-+}
-+
-+uno::Sequence< rtl::OUString >
-+SwVbaBaseRange::getServiceNames()
-+{
-+ static uno::Sequence< rtl::OUString > aServiceNames;
-+ if ( aServiceNames.getLength() == 0 )
-+ {
-+ aServiceNames.realloc( 1 );
-+ aServiceNames[ 0 ] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.word.BaseRange" ) );
-+ }
-+ return aServiceNames;
-+}
-+
-+
-+/*
-+* class SwVbaDocRange
-+*/
-+class SwVbaDocRange : public SwVbaBaseRange
-+{
-+public:
-+ SwVbaDocRange( const uno::Reference< ooo::vba::XHelperInterface >& rParent, const uno::Reference< uno::XComponentContext >& rContext,
-+ const uno::Reference< text::XTextDocument >& rDocument, const uno::Reference< text::XTextRange >& rStart,
-+ const uno::Reference< text::XTextRange >& rEnd, const uno::Reference< text::XText >& rText, sal_Bool _bMaySpanEndOfDocument = sal_False )
-+ throw ( uno::RuntimeException );
-+ virtual ~SwVbaDocRange();
-+};
-+
-+SwVbaDocRange::SwVbaDocRange( const uno::Reference< ooo::vba::XHelperInterface >& rParent, const uno::Reference< uno::XComponentContext >& rContext,
-+ const uno::Reference< text::XTextDocument >& rDocument, const uno::Reference< text::XTextRange >& rStart,
-+ const uno::Reference< text::XTextRange >& rEnd, const uno::Reference< text::XText >& rText, sal_Bool _bMaySpanEndOfDocument ) throw ( uno::RuntimeException ) : SwVbaBaseRange( rParent, rContext )
-+{
-+ mxTextDocument = rDocument;
-+ mbMaySpanEndOfDocument = _bMaySpanEndOfDocument;
-+
-+ if( rText.is() )
-+ mxText = rText;
-+ else
-+ mxText = mxTextDocument->getText();
-+
-+ mxTextCursor = SwVbaRangeHelper::initCursor( rStart, mxText );
-+ mxTextCursor->collapseToStart();
-+
-+ if( rEnd.is() )
-+ mxTextCursor->gotoRange( rEnd, sal_True );
-+ else
-+ mxTextCursor->gotoEnd( sal_True );
-+}
-+
-+SwVbaDocRange::~SwVbaDocRange()
-+{
-+}
-+
-+/*
-+* class SwVbaRange
-+*/
-+SwVbaRange::SwVbaRange( const uno::Reference< ooo::vba::XHelperInterface >& rParent, const uno::Reference< uno::XComponentContext >& rContext,
-+ const uno::Reference< text::XTextDocument >& rTextDocument, const uno::Reference< text::XTextRange >& rStart, const uno::Reference< text::XTextRange >& rEnd, sal_Bool _bMaySpanEndOfDocument ) : SwVbaRange_BASE( rParent, rContext )
-+{
-+ uno::Reference< text::XText > xText;
-+ mxActualRange = uno::Reference< word::XRange > ( new SwVbaDocRange( rParent, rContext, rTextDocument, rStart, rEnd, xText, _bMaySpanEndOfDocument ) );
-+}
-+
-+SwVbaRange::~SwVbaRange()
-+{
-+}
-+
-+uno::Reference< text::XTextRange >
-+SwVbaRange::getXTextRange() throw (uno::RuntimeException)
-+{
-+ uno::Reference< text::XTextRange > xTextRange;
-+ SwVbaBaseRange* pBaseRange = dynamic_cast< SwVbaBaseRange* >( mxActualRange.get() );
-+ if( pBaseRange )
-+ xTextRange = pBaseRange->getXTextRange();
-+ return xTextRange;
-+}
-+
-+rtl::OUString SAL_CALL
-+SwVbaRange::getText() throw ( uno::RuntimeException )
-+{
-+ rtl::OUString aText;
-+ if( mxActualRange.is() )
-+ return mxActualRange->getText();
-+ return aText;
-+}
-+
-+void SAL_CALL
-+SwVbaRange::setText( const rtl::OUString& rText ) throw ( uno::RuntimeException )
-+{
-+ if( mxActualRange.is() )
-+ mxActualRange->setText( rText );
-+}
-+
-+void SAL_CALL SwVbaRange::InsertBreak( const uno::Any& _breakType ) throw (uno::RuntimeException)
-+{
-+ if( mxActualRange.is() )
-+ mxActualRange->InsertBreak( _breakType );
-+}
-+
-+rtl::OUString&
-+SwVbaRange::getServiceImplName()
-+{
-+ static rtl::OUString sImplName( RTL_CONSTASCII_USTRINGPARAM("SwVbaRange") );
-+ return sImplName;
-+}
-+
-+uno::Sequence< rtl::OUString >
-+SwVbaRange::getServiceNames()
-+{
-+ static uno::Sequence< rtl::OUString > aServiceNames;
-+ if ( aServiceNames.getLength() == 0 )
-+ {
-+ aServiceNames.realloc( 1 );
-+ aServiceNames[ 0 ] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.word.Range" ) );
-+ }
-+ return aServiceNames;
-+}
-+
---- sw/source/ui/vba/vbarange.hxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ sw/source/ui/vba/vbarange.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,65 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile:
-+ * $Revision:
-+ *
-+ * 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.
-+ *
-+ ************************************************************************/
-+#ifndef SW_VBA_RANGE_HXX
-+#define SW_VBA_RANGE_HXX
-+
-+#include <ooo/vba/word/XRange.hpp>
-+#include <vbahelper/vbahelperinterface.hxx>
-+#include <cppuhelper/implbase1.hxx>
-+#include <com/sun/star/text/XTextRange.hpp>
-+#include <com/sun/star/text/XTextDocument.hpp>
-+
-+typedef InheritedHelperInterfaceImpl1< ooo::vba::word::XRange > SwVbaRange_BASE;
-+
-+class SwVbaRange : public SwVbaRange_BASE
-+{
-+private:
-+ css::uno::Reference< ooo::vba::word::XRange > mxActualRange;
-+
-+public:
-+ SwVbaRange( const css::uno::Reference< ooo::vba::XHelperInterface >& rParent, const css::uno::Reference< css::uno::XComponentContext >& rContext,
-+ const css::uno::Reference< css::text::XTextDocument >& rTextDocument, const css::uno::Reference< css::text::XTextRange >& rStart, const css::uno::Reference< css::text::XTextRange >& rEnd, sal_Bool _bMaySpanEndOfDocument = sal_False );
-+ virtual ~SwVbaRange();
-+
-+ css::uno::Reference< css::text::XTextRange > getXTextRange() throw (css::uno::RuntimeException);
-+
-+ // Attribute
-+ virtual rtl::OUString SAL_CALL getText() throw (css::uno::RuntimeException);
-+ virtual void SAL_CALL setText( const rtl::OUString& rText ) throw (css::uno::RuntimeException);
-+
-+ // Methods
-+ virtual void SAL_CALL InsertBreak( const css::uno::Any& _breakType ) throw (css::uno::RuntimeException);
-+
-+
-+ // XHelperInterface
-+ virtual rtl::OUString& getServiceImplName();
-+ virtual css::uno::Sequence<rtl::OUString> getServiceNames();
-+};
-+#endif /* SW_VBA_RANGE_HXX */
---- sw/source/ui/vba/vbarangehelper.cxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ sw/source/ui/vba/vbarangehelper.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,143 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile:
-+ * $Revision:
-+ *
-+ * 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 "vbarangehelper.hxx"
-+#include <com/sun/star/text/ControlCharacter.hpp>
-+
-+using namespace ::ooo::vba;
-+using namespace ::com::sun::star;
-+
-+/**
-+ * get a range in a xText by creating
-+ * a cursor that iterates over the text. If the iterating cursor is
-+ * equal to the desired position, the range equivalent is returned.
-+ * Some special cases are tables that are inside of the text, because the
-+ * position has to be adjusted.
-+ * @param xText a text where a range position is searched
-+ * @param position a position inside o the text
-+ * @return a range for the postion; null is returned if no range can be
-+ * constructed.
-+ */
-+uno::Reference< text::XTextRange > SwVbaRangeHelper::getRangeByPosition( const uno::Reference< text::XText >& rText, sal_Int32 _position ) throw ( uno::RuntimeException )
-+{
-+ uno::Reference< text::XTextRange > xRange;
-+ if( rText.is() )
-+ {
-+ sal_Int32 nPos = 0;
-+ uno::Reference< text::XTextCursor > xCursor = rText->createTextCursor();
-+ xCursor->collapseToStart();
-+ sal_Bool bCanGo = sal_True;
-+ while( !xRange.is() && bCanGo )
-+ {
-+ if( _position == nPos )
-+ {
-+ xRange = xCursor->getStart();
-+ }
-+ else
-+ {
-+ bCanGo = xCursor->goRight( 1, sal_False );
-+ nPos++;
-+ }
-+ }
-+ }
-+ return xRange;
-+}
-+
-+
-+void SwVbaRangeHelper::insertString( uno::Reference< text::XTextRange >& rTextRange, uno::Reference< text::XText >& rText, const rtl::OUString& rStr, sal_Bool _bAbsorb ) throw ( uno::RuntimeException )
-+{
-+ sal_Int32 nlastIndex = 0;
-+ sal_Int32 nIndex = 0;
-+ uno::Reference< text::XTextRange > xRange = rTextRange;
-+
-+ while(( nIndex = rStr.indexOf('\n', nlastIndex)) >= 0 )
-+ {
-+ xRange = xRange->getEnd();
-+ if( nlastIndex < ( nIndex - 1 ) )
-+ {
-+ rText->insertString( xRange, rStr.copy( nlastIndex, ( nIndex - 1 - nlastIndex ) ), _bAbsorb );
-+ xRange = xRange->getEnd();
-+ }
-+
-+ rText->insertControlCharacter( xRange, text::ControlCharacter::PARAGRAPH_BREAK, _bAbsorb );
-+ nlastIndex = nIndex + 1;
-+ }
-+
-+ if( nlastIndex < rStr.getLength() )
-+ {
-+ xRange = xRange->getEnd();
-+
-+ rtl::OUString aWatt = rStr.copy( nlastIndex );
-+ rText->insertString( xRange, aWatt, _bAbsorb );
-+ }
-+}
-+
-+uno::Reference< text::XTextCursor > SwVbaRangeHelper::initCursor( const uno::Reference< text::XTextRange >& rTextRange, const uno::Reference< text::XText >& rText ) throw ( uno::RuntimeException )
-+{
-+ uno::Reference< text::XTextCursor > xTextCursor;
-+ sal_Bool bGotTextCursor = sal_False;
-+
-+ try
-+ {
-+ xTextCursor = rText->createTextCursorByRange( rTextRange );
-+ bGotTextCursor = sal_True;
-+ }
-+ catch (uno::Exception& e)
-+ {
-+ DebugHelper::exception(e);
-+ }
-+
-+ if( !bGotTextCursor )
-+ {
-+ try
-+ {
-+ uno::Reference< text::XText > xText = rTextRange->getText();
-+ xTextCursor = xText->createTextCursor();
-+ bGotTextCursor = sal_True;
-+ }
-+ catch( uno::Exception& e )
-+ {
-+ DebugHelper::exception(e);
-+ }
-+ }
-+
-+ if( !bGotTextCursor )
-+ {
-+ try
-+ {
-+ xTextCursor = rText->createTextCursor();
-+ bGotTextCursor = sal_True;
-+ }
-+ catch( uno::Exception& e )
-+ {
-+ DebugHelper::exception(e);
-+ }
-+ }
-+ return xTextCursor;
-+}
---- sw/source/ui/vba/vbarangehelper.hxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ sw/source/ui/vba/vbarangehelper.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,45 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile:
-+ * $Revision:
-+ *
-+ * 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.
-+ *
-+ ************************************************************************/
-+#ifndef SW_VBA_RANGEHELPER_HXX
-+#define SW_VBA_RANGEHELPER_HXX
-+
-+#include <vbahelper/vbahelperinterface.hxx>
-+#include <com/sun/star/text/XTextViewCursor.hpp>
-+#include <com/sun/star/text/XText.hpp>
-+
-+class SwVbaRangeHelper
-+{
-+public:
-+ static css::uno::Reference< css::text::XTextRange > getRangeByPosition( const css::uno::Reference< css::text::XText >& rText, sal_Int32 _position )throw ( css::uno::RuntimeException );
-+ static void insertString( css::uno::Reference< css::text::XTextRange >& rTextRange, css::uno::Reference< css::text::XText >& rText, const rtl::OUString& rStr, sal_Bool _bAbsorb ) throw ( css::uno::RuntimeException );
-+ static css::uno::Reference< css::text::XTextCursor > initCursor( const css::uno::Reference< css::text::XTextRange >& rTextRange, const css::uno::Reference< css::text::XText >& rText ) throw ( css::uno::RuntimeException );
-+
-+};
-+#endif /* SW_VBA_RANGEHELPER_HXX */
---- sw/source/ui/vba/vbaselection.cxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ sw/source/ui/vba/vbaselection.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,75 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile:
-+ * $Revision:
-+ *
-+ * 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 "vbaselection.hxx"
-+#include <vbahelper/vbahelper.hxx>
-+#include <tools/diagnose_ex.h>
-+
-+using namespace ::ooo::vba;
-+using namespace ::com::sun::star;
-+
-+SwVbaSelection::SwVbaSelection( const uno::Reference< ooo::vba::XHelperInterface >& rParent, const css::uno::Reference< css::uno::XComponentContext >& rContext, const css::uno::Reference< css::frame::XModel >& rModel ) throw ( css::uno::RuntimeException ) : SwVbaSelection_BASE( rParent, rContext ), mxModel( rModel )
-+{
-+}
-+
-+SwVbaSelection::~SwVbaSelection()
-+{
-+}
-+
-+rtl::OUString SAL_CALL
-+SwVbaSelection::getText() throw ( uno::RuntimeException )
-+{
-+ rtl::OUString aText;
-+ return aText;
-+}
-+
-+void SAL_CALL
-+SwVbaSelection::setText( const rtl::OUString& rText ) throw ( uno::RuntimeException )
-+{
-+}
-+
-+rtl::OUString&
-+SwVbaSelection::getServiceImplName()
-+{
-+ static rtl::OUString sImplName( RTL_CONSTASCII_USTRINGPARAM("SwVbaSelection") );
-+ return sImplName;
-+}
-+
-+uno::Sequence< rtl::OUString >
-+SwVbaSelection::getServiceNames()
-+{
-+ static uno::Sequence< rtl::OUString > aServiceNames;
-+ if ( aServiceNames.getLength() == 0 )
-+ {
-+ aServiceNames.realloc( 1 );
-+ aServiceNames[ 0 ] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.word.Selection" ) );
-+ }
-+ return aServiceNames;
-+}
-+
---- sw/source/ui/vba/vbaselection.hxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ sw/source/ui/vba/vbaselection.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,56 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile:
-+ * $Revision:
-+ *
-+ * 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.
-+ *
-+ ************************************************************************/
-+#ifndef SW_VBA_SELECTION_HXX
-+#define SW_VBA_SELECTION_HXX
-+
-+#include <ooo/vba/word/XSelection.hpp>
-+#include <vbahelper/vbahelperinterface.hxx>
-+
-+typedef InheritedHelperInterfaceImpl1< ooo::vba::word::XSelection > SwVbaSelection_BASE;
-+
-+class SwVbaSelection : public SwVbaSelection_BASE
-+{
-+private:
-+ css::uno::Reference< css::frame::XModel > mxModel;
-+
-+public:
-+ SwVbaSelection( const css::uno::Reference< ooo::vba::XHelperInterface >& rParent, const css::uno::Reference< css::uno::XComponentContext >& rContext, const css::uno::Reference< css::frame::XModel >& rModel ) throw ( css::uno::RuntimeException );
-+ virtual ~SwVbaSelection();
-+
-+ // Attribute
-+ virtual rtl::OUString SAL_CALL getText() throw (css::uno::RuntimeException);
-+ virtual void SAL_CALL setText( const rtl::OUString& rText ) throw (css::uno::RuntimeException);
-+
-+
-+ // XHelperInterface
-+ virtual rtl::OUString& getServiceImplName();
-+ virtual css::uno::Sequence<rtl::OUString> getServiceNames();
-+};
-+#endif /* SW_VBA_SELECTION_HXX */
---- sw/source/ui/vba/vbasystem.cxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ sw/source/ui/vba/vbasystem.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,195 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile:
-+ * $Revision:
-+ *
-+ * 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 "vbasystem.hxx"
-+#include <vbahelper/vbahelper.hxx>
-+#include <ooo/vba/word/WdCursorType.hpp>
-+#include <tools/diagnose_ex.h>
-+#include <tools/config.hxx>
-+#include <tools/string.hxx>
-+#include <osl/file.hxx>
-+#include <tools/urlobj.hxx>
-+#include <tools/string.hxx>
-+
-+using namespace ::ooo::vba;
-+using namespace ::com::sun::star;
-+
-+PrivateProfileStringListener::PrivateProfileStringListener( const rtl::OUString& rFileName, const ByteString& rGroupName, const ByteString& rKey )
-+ :maFileName( rFileName ), maGroupName( rGroupName ), maKey( rKey )
-+{
-+}
-+
-+PrivateProfileStringListener::~PrivateProfileStringListener()
-+{
-+}
-+
-+void PrivateProfileStringListener::Initialize( const rtl::OUString& rFileName, const ByteString& rGroupName, const ByteString& rKey )
-+{
-+ maFileName = rFileName;
-+ maGroupName = rGroupName;
-+ maKey = rKey;
-+}
-+
-+uno::Any PrivateProfileStringListener::getValueEvent()
-+{
-+ // get the private profile string
-+ Config aCfg( maFileName );
-+ aCfg.SetGroup( maGroupName );
-+ rtl::OUString sValue = rtl::OUString( String( aCfg.ReadKey( maKey ), RTL_TEXTENCODING_UTF8 ) );
-+
-+ return uno::makeAny( sValue );
-+}
-+
-+void PrivateProfileStringListener::setValueEvent( const css::uno::Any& value )
-+{
-+ // set the private profile string
-+ Config aCfg( maFileName );
-+ aCfg.SetGroup( maGroupName );
-+
-+ rtl::OUString aValue;
-+ value >>= aValue;
-+ aCfg.WriteKey( maKey, ByteString( aValue.getStr(), RTL_TEXTENCODING_UTF8 ) );
-+}
-+
-+SwVbaSystem::SwVbaSystem( uno::Reference<uno::XComponentContext >& xContext ): SwVbaSystem_BASE( uno::Reference< XHelperInterface >(), xContext )
-+{
-+}
-+
-+SwVbaSystem::~SwVbaSystem()
-+{
-+}
-+
-+sal_Int32 SAL_CALL
-+SwVbaSystem::getCursor() throw (uno::RuntimeException)
-+{
-+ sal_Int32 nPointerStyle = getPointerStyle();
-+
-+ switch( nPointerStyle )
-+ {
-+ case POINTER_ARROW:
-+ return word::WdCursorType::wdCursorNorthwestArrow;
-+ case POINTER_NULL:
-+ return word::WdCursorType::wdCursorNormal;
-+ case POINTER_WAIT:
-+ return word::WdCursorType::wdCursorWait;
-+ case POINTER_TEXT:
-+ return word::WdCursorType::wdCursorIBeam;
-+ default:
-+ return word::WdCursorType::wdCursorNormal;
-+ }
-+}
-+
-+void SAL_CALL
-+SwVbaSystem::setCursor( sal_Int32 _cursor ) throw (uno::RuntimeException)
-+{
-+ try
-+ {
-+ switch( _cursor )
-+ {
-+ case word::WdCursorType::wdCursorNorthwestArrow:
-+ {
-+ const Pointer& rPointer( POINTER_ARROW );
-+ setCursorHelper( rPointer, sal_False );
-+ break;
-+ }
-+ case word::WdCursorType::wdCursorWait:
-+ {
-+ const Pointer& rPointer( static_cast< PointerStyle >( POINTER_WAIT ) );
-+ //It will set the edit window, toobar and statusbar's mouse pointer.
-+ setCursorHelper( rPointer, sal_True );
-+ break;
-+ }
-+ case word::WdCursorType::wdCursorIBeam:
-+ {
-+ const Pointer& rPointer( static_cast< PointerStyle >( POINTER_TEXT ) );
-+ //It will set the edit window, toobar and statusbar's mouse pointer.
-+ setCursorHelper( rPointer, sal_True );
-+ break;
-+ }
-+ case word::WdCursorType::wdCursorNormal:
-+ {
-+ const Pointer& rPointer( POINTER_NULL );
-+ setCursorHelper( rPointer, sal_False );
-+ break;
-+ }
-+ default:
-+ throw uno::RuntimeException( rtl::OUString(
-+ RTL_CONSTASCII_USTRINGPARAM("Unknown value for Cursor pointer")), uno::Reference< uno::XInterface >() );
-+ // TODO: isn't this a flaw in the API? It should be allowed to throw an
-+ // IllegalArgumentException, or so
-+ }
-+ }
-+ catch( const uno::Exception& )
-+ {
-+ DBG_UNHANDLED_EXCEPTION();
-+ }
-+}
-+
-+uno::Any SAL_CALL
-+SwVbaSystem::PrivateProfileString( const rtl::OUString& rFilename, const rtl::OUString& rSection, const rtl::OUString& rKey ) throw ( uno::RuntimeException )
-+{
-+ if( rFilename.getLength() == 0 )
-+ throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "Failed to access document from shell" ) ), uno::Reference< uno::XInterface >() );
-+
-+ // FIXME: need to detect whether it is a relative file path
-+ // we need to detect if this is a URL, if not then assume its a file path
-+ rtl::OUString sFileUrl;
-+ INetURLObject aObj;
-+ aObj.SetURL( rFilename );
-+ bool bIsURL = aObj.GetProtocol() != INET_PROT_NOT_VALID;
-+ if ( bIsURL )
-+ sFileUrl = rFilename;
-+ else
-+ osl::FileBase::getFileURLFromSystemPath( rFilename, sFileUrl);
-+
-+ ByteString aGroupName = ByteString( rSection.getStr(), RTL_TEXTENCODING_UTF8);
-+ ByteString aKey = ByteString( rKey.getStr(), RTL_TEXTENCODING_UTF8);
-+ maPrivateProfileStringListener.Initialize( sFileUrl, aGroupName, aKey );
-+
-+ return uno::makeAny( uno::Reference< XPropValue > ( new ScVbaPropValue( &maPrivateProfileStringListener ) ) );
-+}
-+
-+rtl::OUString&
-+SwVbaSystem::getServiceImplName()
-+{
-+ static rtl::OUString sImplName( RTL_CONSTASCII_USTRINGPARAM("SwVbaSystem") );
-+ return sImplName;
-+}
-+
-+uno::Sequence< rtl::OUString >
-+SwVbaSystem::getServiceNames()
-+{
-+ static uno::Sequence< rtl::OUString > aServiceNames;
-+ if ( aServiceNames.getLength() == 0 )
-+ {
-+ aServiceNames.realloc( 1 );
-+ aServiceNames[ 0 ] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.word.System" ) );
-+ }
-+ return aServiceNames;
-+}
---- sw/source/ui/vba/vbasystem.hxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ sw/source/ui/vba/vbasystem.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,75 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile: vbasystem.hxx,v $
-+ * $Revision: 1.4 $
-+ *
-+ * 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.
-+ *
-+ ************************************************************************/
-+#ifndef SW_VBA_SYSTEM_HXX
-+#define SW_VBA_SYSTEM_HXX
-+
-+#include <ooo/vba/word/XSystem.hpp>
-+#include <vbahelper/vbahelperinterface.hxx>
-+#include <cppuhelper/implbase1.hxx>
-+#include <vbahelper/vbapropvalue.hxx>
-+
-+typedef InheritedHelperInterfaceImpl1< ooo::vba::word::XSystem > SwVbaSystem_BASE;
-+
-+class PrivateProfileStringListener : public PropListener
-+{
-+private:
-+ rtl::OUString maFileName;
-+ ByteString maGroupName;
-+ ByteString maKey;
-+public:
-+ PrivateProfileStringListener(){};
-+ PrivateProfileStringListener( const rtl::OUString& rFileName, const ByteString& rGroupName, const ByteString& rKey );
-+ virtual ~PrivateProfileStringListener();
-+ void Initialize( const rtl::OUString& rFileName, const ByteString& rGroupName, const ByteString& rKey );
-+
-+ //PropListener
-+ virtual void setValueEvent( const css::uno::Any& value );
-+ virtual css::uno::Any getValueEvent();
-+};
-+
-+class SwVbaSystem : public SwVbaSystem_BASE
-+{
-+private:
-+ PrivateProfileStringListener maPrivateProfileStringListener;
-+
-+public:
-+ SwVbaSystem( css::uno::Reference< css::uno::XComponentContext >& m_xContext );
-+ virtual ~SwVbaSystem();
-+
-+ // XSystem
-+ virtual sal_Int32 SAL_CALL getCursor() throw ( css::uno::RuntimeException );
-+ virtual void SAL_CALL setCursor( sal_Int32 _cursor ) throw ( css::uno::RuntimeException );
-+ virtual css::uno::Any SAL_CALL PrivateProfileString( const rtl::OUString& rFilename, const rtl::OUString& rSection, const rtl::OUString& rKey ) throw ( css::uno::RuntimeException );
-+
-+ // XHelperInterface
-+ virtual rtl::OUString& getServiceImplName();
-+ virtual css::uno::Sequence<rtl::OUString> getServiceNames();
-+};
-+#endif /* SW_VBA_SYSTEM_HXX */
---- sw/source/ui/vba/vbavariable.cxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ sw/source/ui/vba/vbavariable.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,108 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile:
-+ * $Revision:
-+ *
-+ * 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 "vbavariable.hxx"
-+#include <vbahelper/vbahelper.hxx>
-+#include <tools/diagnose_ex.h>
-+#include <com/sun/star/beans/XPropertySet.hpp>
-+#include <com/sun/star/beans/PropertyValue.hpp>
-+
-+using namespace ::ooo::vba;
-+using namespace ::com::sun::star;
-+
-+SwVbaVariable::SwVbaVariable( const uno::Reference< ooo::vba::XHelperInterface >& rParent, const uno::Reference< uno::XComponentContext >& rContext,
-+ const uno::Reference< beans::XPropertyAccess >& rUserDefined, const rtl::OUString& rName ) throw ( uno::RuntimeException ) :
-+ SwVbaVariable_BASE( rParent, rContext ), mxUserDefined( rUserDefined ), maName( rName )
-+{
-+}
-+
-+SwVbaVariable::~SwVbaVariable()
-+{
-+}
-+
-+rtl::OUString SAL_CALL
-+SwVbaVariable::getName() throw ( css::uno::RuntimeException )
-+{
-+ return maName;
-+}
-+
-+void SAL_CALL
-+SwVbaVariable::setName( const rtl::OUString& ) throw ( css::uno::RuntimeException )
-+{
-+ throw uno::RuntimeException( rtl::OUString(
-+ RTL_CONSTASCII_USTRINGPARAM(" Fail to set name")), uno::Reference< uno::XInterface >() );
-+}
-+
-+uno::Any SAL_CALL
-+SwVbaVariable::getValue() throw ( css::uno::RuntimeException )
-+{
-+ uno::Reference< beans::XPropertySet > xProp( mxUserDefined, uno::UNO_QUERY_THROW );
-+ return xProp->getPropertyValue( maName );
-+}
-+
-+void SAL_CALL
-+SwVbaVariable::setValue( const uno::Any& rValue ) throw ( css::uno::RuntimeException )
-+{
-+ // FIXME: fail to set the value if the new type of vaue is differenct from the original one.
-+ uno::Reference< beans::XPropertySet > xProp( mxUserDefined, uno::UNO_QUERY_THROW );
-+ xProp->setPropertyValue( maName, rValue );
-+}
-+
-+sal_Int32 SAL_CALL
-+SwVbaVariable::getIndex() throw ( css::uno::RuntimeException )
-+{
-+ const uno::Sequence< beans::PropertyValue > props = mxUserDefined->getPropertyValues();
-+ for (sal_Int32 i = 0; i < props.getLength(); ++i)
-+ {
-+ if( maName.equals( props[i].Name ) )
-+ return i+1;
-+ }
-+
-+ return 0;
-+}
-+
-+rtl::OUString&
-+SwVbaVariable::getServiceImplName()
-+{
-+ static rtl::OUString sImplName( RTL_CONSTASCII_USTRINGPARAM("SwVbaVariable") );
-+ return sImplName;
-+}
-+
-+uno::Sequence< rtl::OUString >
-+SwVbaVariable::getServiceNames()
-+{
-+ static uno::Sequence< rtl::OUString > aServiceNames;
-+ if ( aServiceNames.getLength() == 0 )
-+ {
-+ aServiceNames.realloc( 1 );
-+ aServiceNames[ 0 ] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.word.Variable" ) );
-+ }
-+ return aServiceNames;
-+}
-+
---- sw/source/ui/vba/vbavariable.hxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ sw/source/ui/vba/vbavariable.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,62 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile:
-+ * $Revision:
-+ *
-+ * 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.
-+ *
-+ ************************************************************************/
-+#ifndef SW_VBA_VARIABLE_HXX
-+#define SW_VBA_VARIABLE_HXX
-+
-+#include <ooo/vba/word/XVariable.hpp>
-+#include <vbahelper/vbahelperinterface.hxx>
-+#include <cppuhelper/implbase1.hxx>
-+#include <com/sun/star/beans/XPropertyAccess.hpp>
-+
-+typedef InheritedHelperInterfaceImpl1< ooo::vba::word::XVariable > SwVbaVariable_BASE;
-+
-+class SwVbaVariable : public SwVbaVariable_BASE
-+{
-+private:
-+ css::uno::Reference< css::beans::XPropertyAccess > mxUserDefined;
-+ rtl::OUString maName;
-+
-+public:
-+ SwVbaVariable( const css::uno::Reference< ooo::vba::XHelperInterface >& rParent, const css::uno::Reference< css::uno::XComponentContext >& rContext,
-+ const css::uno::Reference< css::beans::XPropertyAccess >& rUserDefined, const rtl::OUString& rName ) throw ( css::uno::RuntimeException );
-+ virtual ~SwVbaVariable();
-+
-+ // XVariable
-+ virtual rtl::OUString SAL_CALL getName() throw ( css::uno::RuntimeException );
-+ virtual void SAL_CALL setName( const rtl::OUString& ) throw ( css::uno::RuntimeException );
-+ virtual css::uno::Any SAL_CALL getValue() throw ( css::uno::RuntimeException );
-+ virtual void SAL_CALL setValue( const css::uno::Any& rValue ) throw ( css::uno::RuntimeException );
-+ virtual sal_Int32 SAL_CALL getIndex() throw ( css::uno::RuntimeException );
-+
-+ // XHelperInterface
-+ virtual rtl::OUString& getServiceImplName();
-+ virtual css::uno::Sequence<rtl::OUString> getServiceNames();
-+};
-+#endif /* SW_VBA_VARIABLE_HXX */
---- sw/source/ui/vba/vbavariables.cxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ sw/source/ui/vba/vbavariables.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,105 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile:
-+ * $Revision:
-+ *
-+ * 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 "vbavariables.hxx"
-+#include "vbavariable.hxx"
-+#include <com/sun/star/beans/XPropertyContainer.hpp>
-+#include <com/sun/star/beans/PropertyAttribute.hpp>
-+
-+using namespace ::ooo::vba;
-+using namespace ::com::sun::star;
-+
-+uno::Reference< container::XIndexAccess > createVariablesAccess( const uno::Reference< XHelperInterface >& xParent, const uno::Reference< uno::XComponentContext >& xContext, const uno::Reference< beans::XPropertyAccess >& xUserDefined ) throw ( uno::RuntimeException )
-+{
-+ // FIXME: the performance is poor?
-+ XNamedObjectCollectionHelper< word::XVariable >::XNamedVec mVariables;
-+ const uno::Sequence< beans::PropertyValue > props = xUserDefined->getPropertyValues();
-+ sal_Int32 nCount = props.getLength();
-+ mVariables.reserve( nCount );
-+ for( sal_Int32 i=0; i < nCount; i++ )
-+ mVariables.push_back( uno::Reference< word::XVariable > ( new SwVbaVariable( xParent, xContext, xUserDefined, props[i].Name ) ) );
-+
-+ uno::Reference< container::XIndexAccess > xVariables( new XNamedObjectCollectionHelper< word::XVariable >( mVariables ) );
-+ return xVariables;
-+}
-+
-+SwVbaVariables::SwVbaVariables( const uno::Reference< XHelperInterface >& xParent, const uno::Reference< ::com::sun::star::uno::XComponentContext > & xContext, const uno::Reference< beans::XPropertyAccess >& rUserDefined ): SwVbaVariables_BASE( xParent, xContext, createVariablesAccess( xParent, xContext, rUserDefined ) ), mxUserDefined( rUserDefined )
-+{
-+}
-+// XEnumerationAccess
-+uno::Type
-+SwVbaVariables::getElementType() throw (uno::RuntimeException)
-+{
-+ return word::XVariable::static_type(0);
-+}
-+uno::Reference< container::XEnumeration >
-+SwVbaVariables::createEnumeration() throw (uno::RuntimeException)
-+{
-+ uno::Reference< container::XEnumerationAccess > xEnumerationAccess( m_xIndexAccess, uno::UNO_QUERY_THROW );
-+ return xEnumerationAccess->createEnumeration();
-+}
-+
-+uno::Any
-+SwVbaVariables::createCollectionObject( const css::uno::Any& aSource )
-+{
-+ return aSource;
-+}
-+
-+uno::Any SAL_CALL
-+SwVbaVariables::Add( const rtl::OUString& rName, const uno::Any& rValue ) throw (uno::RuntimeException)
-+{
-+ uno::Any aValue;
-+ if( rValue.hasValue() )
-+ aValue = rValue;
-+ else
-+ aValue <<= rtl::OUString();
-+ uno::Reference< beans::XPropertyContainer > xPropertyContainer( mxUserDefined, uno::UNO_QUERY_THROW );
-+ xPropertyContainer->addProperty( rName, beans::PropertyAttribute::MAYBEVOID | beans::PropertyAttribute::REMOVEABLE, aValue );
-+
-+ return uno::makeAny( uno::Reference< word::XVariable >( new SwVbaVariable( getParent(), mxContext, mxUserDefined, rName ) ) );
-+}
-+
-+rtl::OUString&
-+SwVbaVariables::getServiceImplName()
-+{
-+ static rtl::OUString sImplName( RTL_CONSTASCII_USTRINGPARAM("SwVbaVariables") );
-+ return sImplName;
-+}
-+
-+css::uno::Sequence<rtl::OUString>
-+SwVbaVariables::getServiceNames()
-+{
-+ static uno::Sequence< rtl::OUString > sNames;
-+ if ( sNames.getLength() == 0 )
-+ {
-+ sNames.realloc( 1 );
-+ sNames[0] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.word.Variables") );
-+ }
-+ return sNames;
-+}
---- sw/source/ui/vba/vbavariables.hxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ sw/source/ui/vba/vbavariables.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,64 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile:
-+ * $Revision:
-+ *
-+ * 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.
-+ *
-+ ************************************************************************/
-+#ifndef SW_VBA_VARIABLES_HXX
-+#define SW_VBA_VARIABLES_HXX
-+
-+#include <vbahelper/vbacollectionimpl.hxx>
-+#include <ooo/vba/word/XVariables.hpp>
-+#include <com/sun/star/container/XEnumerationAccess.hpp>
-+#include <com/sun/star/container/XIndexAccess.hpp>
-+#include <vbahelper/vbahelperinterface.hxx>
-+#include <com/sun/star/beans/XPropertyAccess.hpp>
-+
-+typedef CollTestImplHelper< ooo::vba::word::XVariables > SwVbaVariables_BASE;
-+
-+class SwVbaVariables : public SwVbaVariables_BASE
-+{
-+private:
-+ css::uno::Reference< css::beans::XPropertyAccess > mxUserDefined;
-+
-+public:
-+ SwVbaVariables( const css::uno::Reference< ov::XHelperInterface >& xParent, const css::uno::Reference< css::uno::XComponentContext > & xContext, const css::uno::Reference< css::beans::XPropertyAccess >& rUserDefined );
-+ virtual ~SwVbaVariables() {}
-+
-+ // XEnumerationAccess
-+ virtual css::uno::Type SAL_CALL getElementType() throw (css::uno::RuntimeException);
-+ virtual css::uno::Reference< css::container::XEnumeration > SAL_CALL createEnumeration() throw (css::uno::RuntimeException);
-+
-+ // SwVbaVariables_BASE
-+ virtual css::uno::Any createCollectionObject( const css::uno::Any& aSource );
-+ virtual rtl::OUString& getServiceImplName();
-+ virtual css::uno::Sequence<rtl::OUString> getServiceNames();
-+
-+ // XVariables
-+ virtual css::uno::Any SAL_CALL Add( const rtl::OUString& rName, const css::uno::Any& rValue ) throw (css::uno::RuntimeException);
-+};
-+
-+#endif /* SW_VBA_VARIABLES_HXX */
---- sw/source/ui/vba/vbaview.cxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ sw/source/ui/vba/vbaview.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,384 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile:
-+ * $Revision:
-+ *
-+ * 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 "vbaview.hxx"
-+#include <vbahelper/vbahelper.hxx>
-+#include <tools/diagnose_ex.h>
-+#include <com/sun/star/beans/XPropertySet.hpp>
-+#include <com/sun/star/view/XViewSettingsSupplier.hpp>
-+#include <com/sun/star/text/XTextViewCursorSupplier.hpp>
-+#include <com/sun/star/text/XText.hpp>
-+#include <com/sun/star/text/XTextDocument.hpp>
-+#include <com/sun/star/text/XFootnotesSupplier.hpp>
-+#include <com/sun/star/text/XEndnotesSupplier.hpp>
-+#include <com/sun/star/container/XIndexAccess.hpp>
-+#include <com/sun/star/frame/XController.hpp>
-+#include <com/sun/star/lang/XServiceInfo.hpp>
-+#include <ooo/vba/word/WdSpecialPane.hpp>
-+#include <ooo/vba/word/WdViewType.hpp>
-+#include <ooo/vba/word/WdSeekView.hpp>
-+
-+#include "wordvbahelper.hxx"
-+#include <view.hxx>
-+
-+using namespace ::ooo::vba;
-+using namespace ::com::sun::star;
-+
-+const sal_Int32 DEFAULT_BODY_DISTANCE = 500;
-+
-+SwVbaView::SwVbaView( const uno::Reference< ooo::vba::XHelperInterface >& rParent, const uno::Reference< uno::XComponentContext >& rContext,
-+ const uno::Reference< frame::XModel >& rModel ) throw ( uno::RuntimeException ) :
-+ SwVbaView_BASE( rParent, rContext ), mxModel( rModel )
-+{
-+ uno::Reference< frame::XController > xController = mxModel->getCurrentController();
-+
-+ uno::Reference< text::XTextViewCursorSupplier > xTextViewCursorSupp( xController, uno::UNO_QUERY_THROW );
-+ mxViewCursor = xTextViewCursorSupp->getViewCursor();
-+
-+ uno::Reference< view::XViewSettingsSupplier > xViewSettingSupp( xController, uno::UNO_QUERY_THROW );
-+ mxViewSettings.set( xViewSettingSupp->getViewSettings(), uno::UNO_QUERY_THROW );
-+}
-+
-+SwVbaView::~SwVbaView()
-+{
-+}
-+
-+::sal_Int32 SAL_CALL
-+SwVbaView::getSeekView() throw (css::uno::RuntimeException)
-+{
-+ uno::Reference< text::XText > xCurrentText = mxViewCursor->getText();
-+ uno::Reference< lang::XServiceInfo > xServiceInfo( xCurrentText, uno::UNO_QUERY_THROW );
-+ rtl::OUString aImplName = xServiceInfo->getImplementationName();
-+ if( aImplName.equalsAscii("SwXBodyText") )
-+ {
-+ return word::WdSeekView::wdSeekMainDocument;
-+ }
-+ else if( aImplName.equalsAscii("SwXHeadFootText") )
-+ {
-+ if( word::HeaderFooterHelper::isHeader( mxModel, xCurrentText ) )
-+ {
-+ if( word::HeaderFooterHelper::isFirstPageHeader( mxModel, xCurrentText ) )
-+ return word::WdSeekView::wdSeekFirstPageHeader;
-+ else if( word::HeaderFooterHelper::isEvenPagesHeader( mxModel, xCurrentText ) )
-+ return word::WdSeekView::wdSeekEvenPagesHeader;
-+ else
-+ return word::WdSeekView::wdSeekPrimaryHeader;
-+ }
-+ else
-+ {
-+ if( word::HeaderFooterHelper::isFirstPageFooter( mxModel, xCurrentText ) )
-+ return word::WdSeekView::wdSeekFirstPageFooter;
-+ else if( word::HeaderFooterHelper::isEvenPagesFooter( mxModel, xCurrentText ) )
-+ return word::WdSeekView::wdSeekEvenPagesFooter;
-+ else
-+ return word::WdSeekView::wdSeekPrimaryFooter;
-+ }
-+ }
-+ else if( aImplName.equalsAscii("SwXFootnote") )
-+ {
-+ if( xServiceInfo->supportsService( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("com.sun.star.text.Endnote") ) ) )
-+ return word::WdSeekView::wdSeekEndnotes;
-+ else
-+ return word::WdSeekView::wdSeekFootnotes;
-+ }
-+
-+ return word::WdSeekView::wdSeekMainDocument;
-+}
-+
-+void SAL_CALL
-+SwVbaView::setSeekView( ::sal_Int32 _seekview ) throw (css::uno::RuntimeException)
-+{
-+ if( _seekview == getSeekView() )
-+ return;
-+
-+ switch( _seekview )
-+ {
-+ case word::WdSeekView::wdSeekFirstPageFooter:
-+ case word::WdSeekView::wdSeekFirstPageHeader:
-+ case word::WdSeekView::wdSeekCurrentPageFooter:
-+ case word::WdSeekView::wdSeekCurrentPageHeader:
-+ case word::WdSeekView::wdSeekPrimaryFooter:
-+ case word::WdSeekView::wdSeekPrimaryHeader:
-+ case word::WdSeekView::wdSeekEvenPagesFooter:
-+ case word::WdSeekView::wdSeekEvenPagesHeader:
-+ {
-+ // need to test
-+ mxViewCursor->gotoRange( getHFTextRange( _seekview ), sal_False );
-+ break;
-+ }
-+ case word::WdSeekView::wdSeekFootnotes:
-+ {
-+ uno::Reference< text::XFootnotesSupplier > xFootnotesSupp( mxModel, uno::UNO_QUERY_THROW );
-+ uno::Reference< container::XIndexAccess > xFootnotes( xFootnotesSupp->getFootnotes(), uno::UNO_QUERY_THROW );
-+ if( xFootnotes->getCount() > 0 )
-+ {
-+ uno::Reference< text::XText > xText( xFootnotes->getByIndex(0), uno::UNO_QUERY_THROW );
-+ mxViewCursor->gotoRange( xText->getStart(), sal_False );
-+ }
-+ else
-+ {
-+ DebugHelper::exception( SbERR_NO_ACTIVE_OBJECT, rtl::OUString() );
-+ }
-+ break;
-+ }
-+ case word::WdSeekView::wdSeekEndnotes:
-+ {
-+ uno::Reference< text::XEndnotesSupplier > xEndnotesSupp( mxModel, uno::UNO_QUERY_THROW );
-+ uno::Reference< container::XIndexAccess > xEndnotes( xEndnotesSupp->getEndnotes(), uno::UNO_QUERY_THROW );
-+ if( xEndnotes->getCount() > 0 )
-+ {
-+ uno::Reference< text::XText > xText( xEndnotes->getByIndex(0), uno::UNO_QUERY_THROW );
-+ mxViewCursor->gotoRange( xText->getStart(), sal_False );
-+ }
-+ else
-+ {
-+ DebugHelper::exception( SbERR_NO_ACTIVE_OBJECT, rtl::OUString() );
-+ }
-+ break;
-+ }
-+ case word::WdSeekView::wdSeekMainDocument:
-+ {
-+ uno::Reference< text::XTextDocument > xTextDocument( mxModel, uno::UNO_QUERY_THROW );
-+ uno::Reference< text::XText > xText = xTextDocument->getText();
-+ mxViewCursor->gotoRange( xText->getStart(), sal_False );
-+ break;
-+ }
-+ }
-+}
-+
-+::sal_Int32 SAL_CALL
-+SwVbaView::getSplitSpecial() throw (css::uno::RuntimeException)
-+{
-+ return word::WdSpecialPane::wdPaneNone;
-+}
-+
-+void SAL_CALL
-+SwVbaView::setSplitSpecial( ::sal_Int32/* _splitspecial */) throw (css::uno::RuntimeException)
-+{
-+ // not support in Writer
-+}
-+
-+::sal_Bool SAL_CALL
-+SwVbaView::getTableGridLines() throw (css::uno::RuntimeException)
-+{
-+ sal_Bool bShowTableGridLine = sal_False;
-+ mxViewSettings->getPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ShowTableBoundaries"))) >>= bShowTableGridLine;
-+ return bShowTableGridLine;
-+}
-+
-+void SAL_CALL
-+SwVbaView::setTableGridLines( ::sal_Bool _tablegridlines ) throw (css::uno::RuntimeException)
-+{
-+ mxViewSettings->setPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ShowTableBoundaries")), uno::makeAny( _tablegridlines ) );
-+}
-+
-+::sal_Int32 SAL_CALL
-+SwVbaView::getType() throw (css::uno::RuntimeException)
-+{
-+ // FIXME: handle wdPrintPreview type
-+ sal_Bool bOnlineLayout = sal_False;
-+ mxViewSettings->getPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ShowOnlineLayout"))) >>= bOnlineLayout;
-+ return bOnlineLayout ? word::WdViewType::wdWebView : word::WdViewType::wdPrintView;
-+}
-+
-+void SAL_CALL
-+SwVbaView::setType( ::sal_Int32 _type ) throw (css::uno::RuntimeException)
-+{
-+ // FIXME: handle wdPrintPreview type
-+ switch( _type )
-+ {
-+ case word::WdViewType::wdPrintView:
-+ {
-+ mxViewSettings->setPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ShowOnlineLayout")), uno::makeAny( sal_False ) );
-+ break;
-+ }
-+ case word::WdViewType::wdWebView:
-+ {
-+ mxViewSettings->setPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ShowOnlineLayout")), uno::makeAny( sal_True ) );
-+ break;
-+ }
-+ case word::WdViewType::wdPrintPreview:
-+ {
-+ PrintPreviewHelper( uno::Any(),word::getView( mxModel ) );
-+ break;
-+ }
-+ default:
-+ DebugHelper::exception( SbERR_NOT_IMPLEMENTED, rtl::OUString() );
-+
-+ }
-+}
-+
-+uno::Reference< text::XTextRange > SwVbaView::getHFTextRange( sal_Int32 nType ) throw (uno::RuntimeException)
-+{
-+ mxModel->lockControllers();
-+
-+ rtl::OUString aPropIsOn;
-+ rtl::OUString aPropIsShared;
-+ rtl::OUString aPropBodyDistance;
-+ rtl::OUString aPropText;
-+
-+ switch( nType )
-+ {
-+ case word::WdSeekView::wdSeekCurrentPageFooter:
-+ case word::WdSeekView::wdSeekFirstPageFooter:
-+ case word::WdSeekView::wdSeekPrimaryFooter:
-+ case word::WdSeekView::wdSeekEvenPagesFooter:
-+ {
-+ aPropIsOn = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("FooterIsOn") );
-+ aPropIsShared = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("FooterIsShared") );
-+ aPropBodyDistance = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("FooterBodyDistance") );
-+ aPropText = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("FooterText") );
-+ break;
-+ }
-+ case word::WdSeekView::wdSeekCurrentPageHeader:
-+ case word::WdSeekView::wdSeekFirstPageHeader:
-+ case word::WdSeekView::wdSeekPrimaryHeader:
-+ case word::WdSeekView::wdSeekEvenPagesHeader:
-+ {
-+ aPropIsOn = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("HeaderIsOn") );
-+ aPropIsShared = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("HeaderIsShared") );
-+ aPropBodyDistance = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("HeaderBodyDistance") );
-+ aPropText = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("HeaderText") );
-+ break;
-+ }
-+ }
-+
-+ uno::Reference< text::XPageCursor > xPageCursor( mxViewCursor, uno::UNO_QUERY_THROW );
-+
-+ if( nType == word::WdSeekView::wdSeekFirstPageFooter
-+ || nType == word::WdSeekView::wdSeekFirstPageHeader )
-+ {
-+ xPageCursor->jumpToFirstPage();
-+ }
-+
-+ uno::Reference< style::XStyle > xStyle;
-+ uno::Reference< text::XText > xText;
-+ switch( nType )
-+ {
-+ case word::WdSeekView::wdSeekPrimaryFooter:
-+ case word::WdSeekView::wdSeekPrimaryHeader:
-+ case word::WdSeekView::wdSeekEvenPagesFooter:
-+ case word::WdSeekView::wdSeekEvenPagesHeader:
-+ {
-+ // The primary header is the first header of the section.
-+ // If the header is not shared between odd and even pages
-+ // the odd page's header is the primary header. If the
-+ // first page's header is different from the rest of the
-+ // document, it is NOT the primary header ( the next primary
-+ // header would be on page 3 )
-+ // The even pages' header is only available if the header is
-+ // not shared and the current style is applied to a page with
-+ // an even page number
-+ uno::Reference< beans::XPropertySet > xCursorProps( mxViewCursor, uno::UNO_QUERY_THROW );
-+ rtl::OUString aPageStyleName;
-+ xCursorProps->getPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("PageStyleName"))) >>= aPageStyleName;
-+ if( aPageStyleName.equalsAscii("First Page") )
-+ {
-+ // go to the beginning of where the next style is used
-+ sal_Bool hasNextPage = sal_False;
-+ xStyle = word::getCurrentPageStyle( mxModel );
-+ do
-+ {
-+ hasNextPage = xPageCursor->jumpToNextPage();
-+ }
-+ while( hasNextPage && ( xStyle == word::getCurrentPageStyle( mxModel ) ) );
-+
-+ if( !hasNextPage )
-+ DebugHelper::exception( SbERR_BAD_ACTION, rtl::OUString() );
-+ }
-+ break;
-+ }
-+ default:
-+ {
-+ break;
-+ }
-+ }
-+
-+ xStyle = word::getCurrentPageStyle( mxModel );
-+ uno::Reference< beans::XPropertySet > xPageProps( xStyle, uno::UNO_QUERY_THROW );
-+ sal_Bool isOn = sal_False;
-+ xPageProps->getPropertyValue( aPropIsOn ) >>= isOn;
-+ sal_Bool isShared = sal_False;
-+ xPageProps->getPropertyValue( aPropIsShared ) >>= isShared;
-+ if( !isOn )
-+ {
-+ xPageProps->setPropertyValue( aPropIsOn, uno::makeAny( sal_True ) );
-+ xPageProps->setPropertyValue( aPropBodyDistance, uno::makeAny( DEFAULT_BODY_DISTANCE ) );
-+ }
-+ if( !isShared )
-+ {
-+ rtl::OUString aTempPropText = aPropText;
-+ if( nType == word::WdSeekView::wdSeekEvenPagesFooter
-+ || nType == word::WdSeekView::wdSeekEvenPagesHeader )
-+ {
-+ aTempPropText += rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("Left") );
-+ }
-+ else
-+ {
-+ aTempPropText += rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("Right") );
-+ }
-+ xText.set( xPageProps->getPropertyValue( aTempPropText), uno::UNO_QUERY_THROW );
-+ }
-+ else
-+ {
-+ if( nType == word::WdSeekView::wdSeekEvenPagesFooter
-+ || nType == word::WdSeekView::wdSeekEvenPagesHeader )
-+ {
-+ DebugHelper::exception( SbERR_BAD_ACTION, rtl::OUString() );
-+ }
-+ xText.set( xPageProps->getPropertyValue( aPropText ), uno::UNO_QUERY_THROW );
-+ }
-+
-+ mxModel->unlockControllers();
-+ if( !xText.is() )
-+ {
-+ DebugHelper::exception( SbERR_INTERNAL_ERROR, rtl::OUString() );
-+ }
-+ return xText->getStart();
-+}
-+
-+rtl::OUString&
-+SwVbaView::getServiceImplName()
-+{
-+ static rtl::OUString sImplName( RTL_CONSTASCII_USTRINGPARAM("SwVbaView") );
-+ return sImplName;
-+}
-+
-+uno::Sequence< rtl::OUString >
-+SwVbaView::getServiceNames()
-+{
-+ static uno::Sequence< rtl::OUString > aServiceNames;
-+ if ( aServiceNames.getLength() == 0 )
-+ {
-+ aServiceNames.realloc( 1 );
-+ aServiceNames[ 0 ] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.word.View" ) );
-+ }
-+ return aServiceNames;
-+}
-+
---- sw/source/ui/vba/vbaview.hxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ sw/source/ui/vba/vbaview.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,69 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile:
-+ * $Revision:
-+ *
-+ * 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.
-+ *
-+ ************************************************************************/
-+#ifndef SW_VBA_VIEW_HXX
-+#define SW_VBA_VIEW_HXX
-+
-+#include <ooo/vba/word/XView.hpp>
-+#include <vbahelper/vbahelperinterface.hxx>
-+#include <com/sun/star/text/XTextViewCursor.hpp>
-+#include <com/sun/star/text/XTextRange.hpp>
-+#include <com/sun/star/beans/XPropertySet.hpp>
-+
-+typedef InheritedHelperInterfaceImpl1< ooo::vba::word::XView > SwVbaView_BASE;
-+
-+class SwVbaView : public SwVbaView_BASE
-+{
-+private:
-+ css::uno::Reference< css::frame::XModel > mxModel;
-+ css::uno::Reference< css::text::XTextViewCursor > mxViewCursor;
-+ css::uno::Reference< css::beans::XPropertySet > mxViewSettings;
-+
-+ css::uno::Reference< css::text::XTextRange > getHFTextRange( sal_Int32 nType ) throw (css::uno::RuntimeException);
-+
-+public:
-+ SwVbaView( const css::uno::Reference< ooo::vba::XHelperInterface >& rParent, const css::uno::Reference< css::uno::XComponentContext >& rContext,
-+ const css::uno::Reference< css::frame::XModel >& rModel ) throw ( css::uno::RuntimeException );
-+ virtual ~SwVbaView();
-+
-+ // XView
-+ virtual ::sal_Int32 SAL_CALL getSeekView() throw (css::uno::RuntimeException);
-+ virtual void SAL_CALL setSeekView( ::sal_Int32 _seekview ) throw (css::uno::RuntimeException);
-+ virtual ::sal_Int32 SAL_CALL getSplitSpecial() throw (css::uno::RuntimeException);
-+ virtual void SAL_CALL setSplitSpecial( ::sal_Int32 _splitspecial ) throw (css::uno::RuntimeException);
-+ virtual ::sal_Bool SAL_CALL getTableGridLines() throw (css::uno::RuntimeException);
-+ virtual void SAL_CALL setTableGridLines( ::sal_Bool _tablegridlines ) throw (css::uno::RuntimeException);
-+ virtual ::sal_Int32 SAL_CALL getType() throw (css::uno::RuntimeException);
-+ virtual void SAL_CALL setType( ::sal_Int32 _type ) throw (css::uno::RuntimeException);
-+
-+ // XHelperInterface
-+ virtual rtl::OUString& getServiceImplName();
-+ virtual css::uno::Sequence<rtl::OUString> getServiceNames();
-+};
-+#endif /* SW_VBA_VIEW_HXX */
---- sw/source/ui/vba/vbawindow.cxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ sw/source/ui/vba/vbawindow.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,116 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile: vbawindow.cxx,v $
-+ * $Revision: 1.5 $
-+ *
-+ * 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 <vbahelper/helperdecl.hxx>
-+#include "vbawindow.hxx"
-+#include "vbaglobals.hxx"
-+#include "vbadocument.hxx"
-+#include "vbaview.hxx"
-+#include "vbapanes.hxx"
-+#include "vbapane.hxx"
-+
-+using namespace ::com::sun::star;
-+using namespace ::ooo::vba;
-+
-+SwVbaWindow::SwVbaWindow( const uno::Reference< XHelperInterface >& xParent, const uno::Reference< uno::XComponentContext >& xContext, const uno::Reference< frame::XModel >& xModel ) : WindowImpl_BASE( xParent, xContext, xModel )
-+{
-+}
-+
-+SwVbaWindow::SwVbaWindow( uno::Sequence< uno::Any > const & args, uno::Reference< uno::XComponentContext > const & xContext )
-+ : WindowImpl_BASE( args, xContext )
-+{
-+}
-+
-+void
-+SwVbaWindow::Activate() throw (css::uno::RuntimeException)
-+{
-+ SwVbaDocument document( uno::Reference< XHelperInterface >( Application(), uno::UNO_QUERY_THROW ), mxContext, m_xModel );
-+
-+ document.Activate();
-+}
-+
-+void
-+SwVbaWindow::Close( const uno::Any& SaveChanges, const uno::Any& RouteDocument ) throw (uno::RuntimeException)
-+{
-+ // FIXME: it is incorrect when there are more than 1 windows
-+ SwVbaDocument document( uno::Reference< XHelperInterface >( Application(), uno::UNO_QUERY_THROW ), mxContext, m_xModel );
-+ uno::Any FileName;
-+ document.Close(SaveChanges, FileName, RouteDocument );
-+}
-+
-+uno::Any SAL_CALL
-+SwVbaWindow::getView() throw (uno::RuntimeException)
-+{
-+ return uno::makeAny( uno::Reference< word::XView >( new SwVbaView( this, mxContext, m_xModel ) ) );
-+}
-+
-+void SAL_CALL SwVbaWindow::setView( const uno::Any& _view ) throw (uno::RuntimeException)
-+{
-+ sal_Int32 nType = 0;
-+ if( _view >>= nType )
-+ {
-+ SwVbaView view( this, mxContext, m_xModel );
-+ view.setType( nType );
-+ }
-+}
-+
-+uno::Any SAL_CALL
-+SwVbaWindow::Panes( const uno::Any& aIndex ) throw (uno::RuntimeException)
-+{
-+ uno::Reference< XCollection > xPanes( new SwVbaPanes( this, mxContext, m_xModel ) );
-+ if( aIndex.getValueTypeClass() == uno::TypeClass_VOID )
-+ return uno::makeAny( xPanes );
-+
-+ return uno::Any( xPanes->Item( aIndex, uno::Any() ) );
-+}
-+
-+uno::Any SAL_CALL
-+SwVbaWindow::ActivePane() throw (uno::RuntimeException)
-+{
-+ return uno::makeAny( uno::Reference< word::XPane >( new SwVbaPane( this, mxContext, m_xModel ) ) );
-+}
-+
-+rtl::OUString&
-+SwVbaWindow::getServiceImplName()
-+{
-+ static rtl::OUString sImplName( RTL_CONSTASCII_USTRINGPARAM("SwVbaWindow") );
-+ return sImplName;
-+}
-+
-+uno::Sequence< rtl::OUString >
-+SwVbaWindow::getServiceNames()
-+{
-+ static uno::Sequence< rtl::OUString > aServiceNames;
-+ if ( aServiceNames.getLength() == 0 )
-+ {
-+ aServiceNames.realloc( 1 );
-+ aServiceNames[ 0 ] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.word.Window" ) );
-+ }
-+ return aServiceNames;
-+}
---- sw/source/ui/vba/vbawindow.hxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ sw/source/ui/vba/vbawindow.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,61 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile: vbawindow.hxx,v $
-+ * $Revision: 1.4 $
-+ *
-+ * 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.
-+ *
-+ ************************************************************************/
-+#ifndef SW_VBA_WINDOW_HXX
-+#define SW_VBA_WINDOW_HXX
-+#include <cppuhelper/implbase1.hxx>
-+#include <ooo/vba/word/XWindow.hpp>
-+#include <com/sun/star/uno/XComponentContext.hpp>
-+
-+#include <vbahelper/vbahelperinterface.hxx>
-+#include <vbahelper/vbawindowbase.hxx>
-+
-+typedef cppu::ImplInheritanceHelper1< VbaWindowBase, ov::word::XWindow > WindowImpl_BASE;
-+
-+class SwVbaWindow : public WindowImpl_BASE
-+{
-+public:
-+ SwVbaWindow( const css::uno::Reference< ov::XHelperInterface >& xParent, const css::uno::Reference< css::uno::XComponentContext >& xContext, const css::uno::Reference< css::frame::XModel >& xModel );
-+ SwVbaWindow( css::uno::Sequence< css::uno::Any > const& aArgs, css::uno::Reference< css::uno::XComponentContext > const& xContext );
-+
-+
-+ // Attributes
-+ virtual css::uno::Any SAL_CALL getView() throw (css::uno::RuntimeException);
-+ virtual void SAL_CALL setView( const css::uno::Any& _view ) throw (css::uno::RuntimeException);
-+ // Methods
-+ virtual void SAL_CALL Activate( ) throw (css::uno::RuntimeException);
-+ virtual void SAL_CALL Close( const css::uno::Any& SaveChanges, const css::uno::Any& RouteDocument ) throw (css::uno::RuntimeException);
-+ virtual css::uno::Any SAL_CALL Panes( const css::uno::Any& aIndex ) throw (css::uno::RuntimeException);
-+ virtual css::uno::Any SAL_CALL ActivePane() throw (css::uno::RuntimeException);
-+ // XHelperInterface
-+ virtual rtl::OUString& getServiceImplName();
-+ virtual css::uno::Sequence<rtl::OUString> getServiceNames();
-+};
-+
-+#endif //SW_VBA_WINDOW_HXX
---- sw/source/ui/vba/wordvbahelper.cxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ sw/source/ui/vba/wordvbahelper.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,207 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile: vbahelper.cxx,v $
-+ * $Revision: 1.5.32.1 $
-+ *
-+ * 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 <docsh.hxx>
-+#include "wordvbahelper.hxx"
-+#include <comphelper/processfactory.hxx>
-+#include <com/sun/star/frame/XController.hpp>
-+#include <com/sun/star/text/XTextViewCursorSupplier.hpp>
-+#include <com/sun/star/style/XStyleFamiliesSupplier.hpp>
-+#include <com/sun/star/container/XNameAccess.hpp>
-+#include <com/sun/star/lang/XUnoTunnel.hpp>
-+#include <unotxdoc.hxx>
-+
-+using namespace ::com::sun::star;
-+using namespace ::ooo::vba;
-+
-+#define FIRST_PAGE 1;
-+
-+namespace ooo
-+{
-+namespace vba
-+{
-+namespace word
-+{
-+
-+SwDocShell* getDocShell( const uno::Reference< frame::XModel>& xModel )
-+{
-+ uno::Reference< lang::XUnoTunnel > xTunnel( xModel, uno::UNO_QUERY_THROW );
-+ SwXTextDocument* pXDoc = reinterpret_cast< SwXTextDocument * >( sal::static_int_cast< sal_IntPtr >(xTunnel->getSomething(SwXTextDocument::getUnoTunnelId())));
-+ return pXDoc ? pXDoc->GetDocShell() : 0;
-+}
-+
-+SwView* getView( const uno::Reference< frame::XModel>& xModel )
-+{
-+ SwDocShell* pDocShell = getDocShell( xModel );
-+ return pDocShell? pDocShell->GetView() : 0;
-+}
-+
-+uno::Reference< text::XTextViewCursor > getXTextViewCursor( const uno::Reference< frame::XModel >& xModel ) throw (uno::RuntimeException)
-+{
-+ uno::Reference< frame::XController > xController = xModel->getCurrentController();
-+ uno::Reference< text::XTextViewCursorSupplier > xTextViewCursorSupp( xController, uno::UNO_QUERY_THROW );
-+ uno::Reference< text::XTextViewCursor > xTextViewCursor = xTextViewCursorSupp->getViewCursor();
-+ return xTextViewCursor;
-+}
-+
-+uno::Reference< style::XStyle > getCurrentPageStyle( const uno::Reference< frame::XModel >& xModel ) throw (uno::RuntimeException)
-+{
-+ uno::Reference< beans::XPropertySet > xCursorProps( getXTextViewCursor( xModel ), uno::UNO_QUERY_THROW );
-+ rtl::OUString aPageStyleName;
-+ xCursorProps->getPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("PageStyleName"))) >>= aPageStyleName;
-+ uno::Reference< style::XStyleFamiliesSupplier > xSytleFamSupp( xModel, uno::UNO_QUERY_THROW );
-+ uno::Reference< container::XNameAccess > xSytleFamNames( xSytleFamSupp->getStyleFamilies(), uno::UNO_QUERY_THROW );
-+ uno::Reference< container::XNameAccess > xPageStyles( xSytleFamNames->getByName( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("PageStyles") ) ), uno::UNO_QUERY_THROW );
-+ uno::Reference< style::XStyle > xStyle( xPageStyles->getByName( aPageStyleName ), uno::UNO_QUERY_THROW );
-+
-+ return xStyle;
-+}
-+
-+// Class HeaderFooterHelper
-+
-+sal_Bool HeaderFooterHelper::isHeader( const uno::Reference< frame::XModel >& xModel, const uno::Reference< text::XText >& xCurrentText ) throw (uno::RuntimeException)
-+{
-+ uno::Reference< text::XPageCursor > xPageCursor( getXTextViewCursor( xModel ), uno::UNO_QUERY_THROW );
-+ uno::Reference< beans::XPropertySet > xStyleProps( getCurrentPageStyle( xModel ), uno::UNO_QUERY_THROW );
-+
-+ sal_Bool isOn = sal_False;
-+ xStyleProps->getPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("HeaderIsOn"))) >>= isOn;
-+ if( !isOn )
-+ return sal_False;
-+
-+ sal_Bool isShared = sal_False;
-+ xStyleProps->getPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("HeaderIsShared"))) >>= isShared;
-+
-+ rtl::OUString aPropText = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("HeaderText") );
-+ if( !isShared )
-+ {
-+ if( 0 == xPageCursor->getPage() % 2 )
-+ {
-+ aPropText = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("HeaderTextLeft") );
-+ }
-+ else
-+ {
-+ aPropText = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("HeaderTextRight") );
-+ }
-+ }
-+
-+ uno::Reference< text::XText > xText( xStyleProps->getPropertyValue( aPropText ), uno::UNO_QUERY_THROW );
-+ //FIXME: can not compare in this way?
-+ return ( xText == xCurrentText );
-+}
-+
-+sal_Bool HeaderFooterHelper::isFirstPageHeader( const uno::Reference< frame::XModel >& xModel, const uno::Reference< text::XText >& xCurrentText ) throw (uno::RuntimeException)
-+{
-+ if( isHeader( xModel, xCurrentText ) )
-+ {
-+ uno::Reference< text::XPageCursor > xPageCursor( getXTextViewCursor( xModel ), uno::UNO_QUERY_THROW );
-+ // FIXME: getPage allways returns 1
-+ sal_Int32 nPage = xPageCursor->getPage();
-+ return nPage == FIRST_PAGE;
-+ }
-+ return sal_False;
-+}
-+
-+sal_Bool HeaderFooterHelper::isEvenPagesHeader( const uno::Reference< frame::XModel >& xModel, const uno::Reference< text::XText >& xCurrentText ) throw (uno::RuntimeException)
-+{
-+ if( isHeader( xModel, xCurrentText ) )
-+ {
-+ uno::Reference< beans::XPropertySet > xStyleProps( getCurrentPageStyle( xModel ), uno::UNO_QUERY_THROW );
-+ sal_Bool isShared = sal_False;
-+ xStyleProps->getPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("HeaderIsShared"))) >>= isShared;
-+ if( !isShared )
-+ {
-+ uno::Reference< text::XPageCursor > xPageCursor( getXTextViewCursor( xModel ), uno::UNO_QUERY_THROW );
-+ return ( 0 == xPageCursor->getPage() % 2 );
-+ }
-+ }
-+ return sal_False;
-+}
-+
-+sal_Bool HeaderFooterHelper::isFooter( const uno::Reference< frame::XModel >& xModel, const uno::Reference< text::XText >& xCurrentText ) throw (uno::RuntimeException)
-+{
-+ uno::Reference< text::XPageCursor > xPageCursor( getXTextViewCursor( xModel ), uno::UNO_QUERY_THROW );
-+ uno::Reference< beans::XPropertySet > xStyleProps( getCurrentPageStyle( xModel ), uno::UNO_QUERY_THROW );
-+
-+ sal_Bool isOn = sal_False;
-+ xStyleProps->getPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("FooterIsOn"))) >>= isOn;
-+ if( !isOn )
-+ return sal_False;
-+
-+ sal_Bool isShared = sal_False;
-+ xStyleProps->getPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("FooterIsShared"))) >>= isShared;
-+
-+ rtl::OUString aPropText = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("FooterText") );
-+ if( !isShared )
-+ {
-+ if( 0 == xPageCursor->getPage() % 2 )
-+ {
-+ aPropText = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("FooterTextLeft") );
-+ }
-+ else
-+ {
-+ aPropText = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("FooterTextRight") );
-+ }
-+ }
-+
-+ uno::Reference< text::XText > xText( xStyleProps->getPropertyValue( aPropText ), uno::UNO_QUERY_THROW );
-+
-+ return ( xText == xCurrentText );
-+}
-+
-+sal_Bool HeaderFooterHelper::isFirstPageFooter( const uno::Reference< frame::XModel >& xModel, const uno::Reference< text::XText >& xCurrentText ) throw (uno::RuntimeException)
-+{
-+ if( isFooter( xModel, xCurrentText ) )
-+ {
-+ uno::Reference< text::XPageCursor > xPageCursor( getXTextViewCursor( xModel ), uno::UNO_QUERY_THROW );
-+ sal_Int32 nPage = xPageCursor->getPage();
-+ return nPage == FIRST_PAGE;
-+ }
-+ return sal_False;
-+}
-+
-+sal_Bool HeaderFooterHelper::isEvenPagesFooter( const uno::Reference< frame::XModel >& xModel, const uno::Reference< text::XText >& xCurrentText ) throw (uno::RuntimeException)
-+{
-+ if( isFooter( xModel, xCurrentText ) )
-+ {
-+ uno::Reference< beans::XPropertySet > xStyleProps( getCurrentPageStyle( xModel ), uno::UNO_QUERY_THROW );
-+ sal_Bool isShared = sal_False;
-+ xStyleProps->getPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("FooterIsShared"))) >>= isShared;
-+ if( !isShared )
-+ {
-+ uno::Reference< text::XPageCursor > xPageCursor( getXTextViewCursor( xModel ), uno::UNO_QUERY_THROW );
-+ return ( 0 == xPageCursor->getPage() % 2 );
-+ }
-+ }
-+ return sal_False;
-+}
-+
-+} // word
-+} //
-+} //
---- sw/source/ui/vba/wordvbahelper.hxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ sw/source/ui/vba/wordvbahelper.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,67 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile: vbahelper.hxx,v $
-+ * $Revision: 1.5.32.1 $
-+ *
-+ * 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.
-+ *
-+ ************************************************************************/
-+#ifndef SW_WORD_VBA_HELPER_HXX
-+#define SW_WORD_VBA_HELPER_HXX
-+
-+#include <vbahelper/vbahelper.hxx>
-+#include <com/sun/star/text/XText.hpp>
-+#include <com/sun/star/text/XTextViewCursor.hpp>
-+#include <com/sun/star/text/XPageCursor.hpp>
-+#include <com/sun/star/style/XStyle.hpp>
-+
-+class SwDocShell;
-+class SwView;
-+namespace ooo
-+{
-+ namespace vba
-+ {
-+ namespace word
-+ {
-+ //css::uno::Reference< css::frame::XModel > getCurrentDocument() throw (css::uno::RuntimeException);
-+ SwDocShell* getDocShell( const css::uno::Reference< css::frame::XModel>& xModel );
-+ SwView* getView( const css::uno::Reference< css::frame::XModel>& xModel );
-+ css::uno::Reference< css::text::XTextViewCursor > getXTextViewCursor( const css::uno::Reference< css::frame::XModel >& xModel ) throw (css::uno::RuntimeException);
-+ css::uno::Reference< css::style::XStyle > getCurrentPageStyle( const css::uno::Reference< css::frame::XModel >& xModel ) throw (css::uno::RuntimeException);
-+
-+class HeaderFooterHelper
-+{
-+public:
-+ static sal_Bool isHeader( const css::uno::Reference< css::frame::XModel >& xModel, const css::uno::Reference< css::text::XText >& xCurrentText ) throw (css::uno::RuntimeException);
-+ static sal_Bool isFirstPageHeader( const css::uno::Reference< css::frame::XModel >& xModel, const css::uno::Reference< css::text::XText >& xCurrentText ) throw (css::uno::RuntimeException);
-+ static sal_Bool isEvenPagesHeader( const css::uno::Reference< css::frame::XModel >& xModel, const css::uno::Reference< css::text::XText >& xCurrentText ) throw (css::uno::RuntimeException);
-+ static sal_Bool isFooter( const css::uno::Reference< css::frame::XModel >& xModel, const css::uno::Reference< css::text::XText >& xCurrentText ) throw (css::uno::RuntimeException);
-+ static sal_Bool isFirstPageFooter( const css::uno::Reference< css::frame::XModel >& xModel, const css::uno::Reference< css::text::XText >& xCurrentText ) throw (css::uno::RuntimeException);
-+ static sal_Bool isEvenPagesFooter( const css::uno::Reference< css::frame::XModel >& xModel, const css::uno::Reference< css::text::XText >& xCurrentText ) throw (css::uno::RuntimeException);
-+};
-+
-+}; // word
-+}; // vba
-+}; // ooo
-+#endif
---- sw/util/makefile.mk.old 2009-04-06 16:41:40.000000000 +0000
-+++ sw/util/makefile.mk 2009-04-06 16:42:01.000000000 +0000
-@@ -131,6 +131,7 @@ SHL1STDLIBS+= \
- $(SALHELPERLIB) \
- $(ICUUCLIB) \
- $(I18NUTILLIB) \
-+ $(VBAHELPERLIB) \
- $(AVMEDIALIB)
-
- .IF "$(GUI)"=="WNT"
-@@ -343,6 +344,41 @@ SHL4STDLIBS= \
- $(CPPUHELPERLIB) \
- $(SALLIB) \
- $(ICUUCLIB) \
-+ $(VBAHELPERLIB) \
-+ $(BASICLIB) \
- $(I18NUTILLIB)
-
-+#target vba
-+TARGET_VBA=vbaswobj
-+SHL5TARGET=$(TARGET_VBA)$(DLLPOSTFIX).uno
-+SHL5IMPLIB= i$(TARGET_VBA)
-+
-+SHL5VERSIONMAP=$(TARGET_VBA).map
-+SHL5DEF=$(MISC)$/$(SHL5TARGET).def
-+DEF5NAME=$(SHL5TARGET)
-+SHL5STDLIBS= \
-+ $(ISWLIB) \
-+ $(CPPUHELPERLIB) \
-+ $(VCLLIB) \
-+ $(CPPULIB) \
-+ $(COMPHELPERLIB) \
-+ $(SVLIB) \
-+ $(TOOLSLIB) \
-+ $(SALLIB)\
-+ $(VBAHELPERLIB) \
-+ $(BASICLIB) \
-+ $(SFXLIB) \
-+ $(SVXLIB) \
-+ $(SVTOOLLIB) \
-+ $(SVLLIB) \
-+ $(VCLLIB) \
-+ $(TKLIB) \
-+
-+.IF "$(GUI)"=="WNT"
-+SHL5STDLIBS+= $(ADVAPI32LIB)
-+.ENDIF # WNT
-+
-+SHL5DEPN=$(SHL1TARGETN)
-+SHL5LIBS=$(SLB)$/$(TARGET_VBA).lib
-+
- .INCLUDE : target.mk
---- sw/util/vbaswobj.map.old 1970-01-01 00:00:00.000000000 +0000
-+++ sw/util/vbaswobj.map 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,9 @@
-+OOO_1.1 {
-+ global:
-+ component_getImplementationEnvironment;
-+ component_getFactory;
-+ component_writeInfo;
-+
-+ local:
-+ *;
-+};
---- vbahelper/inc/vbahelper/helperdecl.hxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ vbahelper/inc/vbahelper/helperdecl.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,58 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile: helperdecl.hxx,v $
-+ * $Revision: 1.3 $
-+ *
-+ * 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.
-+ *
-+ ************************************************************************/
-+#ifndef OOVBAAPI_SERV_DECL
-+#define OOVBAAPI_SERV_DECL
-+#include <comphelper/servicedecl.hxx>
-+#include <ooo/vba/XHelperInterface.hpp>
-+
-+namespace comphelper {
-+namespace service_decl {
-+template <typename ImplT_, typename WithArgsT = with_args<false> >
-+struct vba_service_class_ : public serviceimpl_base< detail::OwnServiceImpl<ImplT_>, WithArgsT >
-+{
-+ typedef serviceimpl_base< detail::OwnServiceImpl<ImplT_>, WithArgsT > baseT;
-+ /** Default ctor. Implementation class without args, expecting
-+ component context as single argument.
-+ */
-+ vba_service_class_() : baseT() {}
-+ template <typename PostProcessFuncT>
-+ /** Ctor to pass a post processing function/functor.
-+
-+ @tpl PostProcessDefaultT let your compiler deduce this
-+ @param postProcessFunc function/functor that gets the yet unacquired
-+ ImplT_ pointer returning a
-+ uno::Reference<uno::XInterface>
-+ */
-+ explicit vba_service_class_( PostProcessFuncT const& postProcessFunc ) : baseT( postProcessFunc ) {}
-+};
-+
-+} // namespace service_decl
-+} // namespace comphelper
-+#endif
---- vbahelper/inc/vbahelper/vbaapplicationbase.hxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ vbahelper/inc/vbahelper/vbaapplicationbase.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,59 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile: vbaapplicationbase.hxx,v $
-+ * $Revision: 1.3 $
-+ *
-+ * 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.
-+ *
-+ ************************************************************************/
-+#ifndef VBA_APPLICATION_BASE_HXX
-+#define VBA_APPLICATION_BASE_HXX
-+
-+#include <ooo/vba/XHelperInterface.hpp>
-+#include <ooo/vba/XApplicationBase.hpp>
-+#include <vbahelper/vbahelperinterface.hxx>
-+
-+typedef InheritedHelperInterfaceImpl1< ov::XApplicationBase > ApplicationBase_BASE;
-+
-+class VbaApplicationBase : public ApplicationBase_BASE
-+{
-+protected:
-+ VbaApplicationBase( const css::uno::Reference< css::uno::XComponentContext >& xContext );
-+ virtual ~VbaApplicationBase();
-+
-+public:
-+ // XHelperInterface ( parent is itself )
-+ virtual css::uno::Reference< ov::XHelperInterface > SAL_CALL getParent( ) throw (css::script::BasicErrorException, css::uno::RuntimeException) { return this; }
-+
-+ virtual sal_Bool SAL_CALL getScreenUpdating() throw (css::uno::RuntimeException);
-+ virtual void SAL_CALL setScreenUpdating(sal_Bool bUpdate) throw (css::uno::RuntimeException);
-+ virtual sal_Bool SAL_CALL getDisplayStatusBar() throw (css::uno::RuntimeException);
-+ virtual void SAL_CALL setDisplayStatusBar(sal_Bool bDisplayStatusBar) throw (css::uno::RuntimeException);
-+ virtual css::uno::Any SAL_CALL CommandBars( const css::uno::Any& aIndex ) throw (css::uno::RuntimeException);
-+
-+ // XHelperInterface
-+ virtual rtl::OUString& getServiceImplName();
-+ virtual css::uno::Sequence<rtl::OUString> getServiceNames();
-+};
-+#endif
---- vbahelper/inc/vbahelper/vbacollectionimpl.hxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ vbahelper/inc/vbahelper/vbacollectionimpl.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,257 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile: vbacollectionimpl.hxx,v $
-+ * $Revision: 1.5 $
-+ *
-+ * 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.
-+ *
-+ ************************************************************************/
-+#ifndef OOVBAAPI_VBA_COLLECTION_IMPL_HXX
-+#define OOVBAAPI_VBA_COLLECTION_IMPL_HXX
-+
-+#include <ooo/vba/XCollection.hpp>
-+#include <com/sun/star/container/XEnumerationAccess.hpp>
-+#include <com/sun/star/uno/XComponentContext.hpp>
-+#include <com/sun/star/script/XDefaultMethod.hpp>
-+#include <com/sun/star/container/XIndexAccess.hpp>
-+#include <com/sun/star/container/XNameAccess.hpp>
-+#include <com/sun/star/container/XNamed.hpp>
-+
-+#include <cppuhelper/implbase3.hxx>
-+#include <cppuhelper/implbase2.hxx>
-+#include <cppuhelper/implbase1.hxx>
-+
-+#include "vbahelper/vbahelper.hxx"
-+#include "vbahelper/vbahelperinterface.hxx"
-+
-+#include <vector>
-+
-+typedef ::cppu::WeakImplHelper1< css::container::XEnumeration > EnumerationHelper_BASE;
-+
-+class EnumerationHelperImpl : public EnumerationHelper_BASE
-+{
-+protected:
-+ css::uno::Reference< css::uno::XComponentContext > m_xContext;
-+ css::uno::Reference< css::container::XEnumeration > m_xEnumeration;
-+public:
-+
-+ EnumerationHelperImpl( const css::uno::Reference< css::uno::XComponentContext >& xContext, const css::uno::Reference< css::container::XEnumeration >& xEnumeration ) throw ( css::uno::RuntimeException ) : m_xContext( xContext ), m_xEnumeration( xEnumeration ) { }
-+ virtual ::sal_Bool SAL_CALL hasMoreElements( ) throw (css::uno::RuntimeException) { return m_xEnumeration->hasMoreElements(); }
-+};
-+
-+// a wrapper class for a providing a XIndexAccess, XNameAccess, XEnumerationAccess impl based on providing a vector of interfaces
-+// only requirement is the object needs to implement XName
-+
-+
-+
-+typedef ::cppu::WeakImplHelper3< css::container::XNameAccess, css::container::XIndexAccess, css::container::XEnumerationAccess > XNamedCollectionHelper_BASE;
-+
-+template< typename Ifc1 >
-+class XNamedObjectCollectionHelper : public XNamedCollectionHelper_BASE
-+{
-+public:
-+typedef std::vector< css::uno::Reference< Ifc1 > > XNamedVec;
-+private:
-+
-+ class XNamedEnumerationHelper : public EnumerationHelper_BASE
-+ {
-+ XNamedVec mXNamedVec;
-+ typename XNamedVec::iterator mIt;
-+ public:
-+ XNamedEnumerationHelper( const XNamedVec& sMap ) : mXNamedVec( sMap ), mIt( mXNamedVec.begin() ) {}
-+
-+ virtual ::sal_Bool SAL_CALL hasMoreElements( ) throw (css::uno::RuntimeException)
-+ {
-+ return ( mIt != mXNamedVec.end() );
-+ }
-+
-+ virtual css::uno::Any SAL_CALL nextElement( ) throw (css::container::NoSuchElementException, css::lang::WrappedTargetException, css::uno::RuntimeException)
-+ {
-+ if ( hasMoreElements() )
-+ return css::uno::makeAny( *mIt++ );
-+ throw css::container::NoSuchElementException();
-+ }
-+ };
-+
-+protected:
-+ XNamedVec mXNamedVec;
-+ typename XNamedVec::iterator cachePos;
-+public:
-+ XNamedObjectCollectionHelper( const XNamedVec& sMap ) : mXNamedVec( sMap ), cachePos(mXNamedVec.begin()) {}
-+ // XElementAccess
-+ virtual css::uno::Type SAL_CALL getElementType( ) throw (css::uno::RuntimeException) { return Ifc1::static_type(0); }
-+ virtual ::sal_Bool SAL_CALL hasElements( ) throw (css::uno::RuntimeException) { return ( mXNamedVec.size() > 0 ); }
-+ // XNameAcess
-+ virtual css::uno::Any SAL_CALL getByName( const ::rtl::OUString& aName ) throw (css::container::NoSuchElementException, css::lang::WrappedTargetException, css::uno::RuntimeException)
-+ {
-+ if ( !hasByName(aName) )
-+ throw css::container::NoSuchElementException();
-+ return css::uno::makeAny( *cachePos );
-+ }
-+ virtual css::uno::Sequence< ::rtl::OUString > SAL_CALL getElementNames( ) throw (css::uno::RuntimeException)
-+ {
-+ css::uno::Sequence< rtl::OUString > sNames( mXNamedVec.size() );
-+ rtl::OUString* pString = sNames.getArray();
-+ typename XNamedVec::iterator it = mXNamedVec.begin();
-+ typename XNamedVec::iterator it_end = mXNamedVec.end();
-+
-+ for ( ; it != it_end; ++it, ++pString )
-+ {
-+ css::uno::Reference< css::container::XNamed > xName( *it, css::uno::UNO_QUERY_THROW );
-+ *pString = xName->getName();
-+ }
-+ return sNames;
-+ }
-+ virtual ::sal_Bool SAL_CALL hasByName( const ::rtl::OUString& aName ) throw (css::uno::RuntimeException)
-+ {
-+ cachePos = mXNamedVec.begin();
-+ typename XNamedVec::iterator it_end = mXNamedVec.end();
-+ for ( ; cachePos != it_end; ++cachePos )
-+ {
-+ css::uno::Reference< css::container::XNamed > xName( *cachePos, css::uno::UNO_QUERY_THROW );
-+ if ( aName.equals( xName->getName() ) )
-+ break;
-+ }
-+ return ( cachePos != it_end );
-+ }
-+
-+ // XElementAccess
-+ virtual ::sal_Int32 SAL_CALL getCount( ) throw (css::uno::RuntimeException) { return mXNamedVec.size(); }
-+ virtual css::uno::Any SAL_CALL getByIndex( ::sal_Int32 Index ) throw (css::lang::IndexOutOfBoundsException, css::lang::WrappedTargetException, css::uno::RuntimeException )
-+ {
-+ if ( Index < 0 || Index >= getCount() )
-+ throw css::lang::IndexOutOfBoundsException();
-+
-+ return css::uno::makeAny( mXNamedVec[ Index ] );
-+
-+ }
-+ // XEnumerationAccess
-+ virtual css::uno::Reference< css::container::XEnumeration > SAL_CALL createEnumeration( ) throw (css::uno::RuntimeException)
-+ {
-+ return new XNamedEnumerationHelper( mXNamedVec );
-+ }
-+};
-+
-+// including a HelperInterface implementation
-+template< typename Ifc1 >
-+class ScVbaCollectionBase : public InheritedHelperInterfaceImpl< Ifc1 >
-+{
-+typedef InheritedHelperInterfaceImpl< Ifc1 > BaseColBase;
-+protected:
-+ css::uno::Reference< css::container::XIndexAccess > m_xIndexAccess;
-+ css::uno::Reference< css::container::XNameAccess > m_xNameAccess;
-+
-+ virtual css::uno::Any getItemByStringIndex( const rtl::OUString& sIndex ) throw (css::uno::RuntimeException)
-+ {
-+ if ( !m_xNameAccess.is() )
-+ throw css::uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ScVbaCollectionBase string index access not supported by this object") ), css::uno::Reference< css::uno::XInterface >() );
-+
-+ return createCollectionObject( m_xNameAccess->getByName( sIndex ) );
-+ }
-+
-+ virtual css::uno::Any getItemByIntIndex( const sal_Int32 nIndex ) throw (css::uno::RuntimeException)
-+ {
-+ if ( !m_xIndexAccess.is() )
-+ throw css::uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ScVbaCollectionBase numeric index access not supported by this object") ), css::uno::Reference< css::uno::XInterface >() );
-+ if ( nIndex <= 0 )
-+ {
-+ throw css::lang::IndexOutOfBoundsException(
-+ ::rtl::OUString( RTL_CONSTASCII_USTRINGPARAM(
-+ "index is 0 or negative" ) ),
-+ css::uno::Reference< css::uno::XInterface >() );
-+ }
-+ // need to adjust for vba index ( for which first element is 1 )
-+ return createCollectionObject( m_xIndexAccess->getByIndex( nIndex - 1 ) );
-+ }
-+public:
-+ ScVbaCollectionBase( const css::uno::Reference< ov::XHelperInterface >& xParent, const css::uno::Reference< css::uno::XComponentContext >& xContext, const css::uno::Reference< css::container::XIndexAccess >& xIndexAccess ) : BaseColBase( xParent, xContext ), m_xIndexAccess( xIndexAccess ){ m_xNameAccess.set(m_xIndexAccess, css::uno::UNO_QUERY); }
-+ //XCollection
-+ virtual ::sal_Int32 SAL_CALL getCount() throw (css::uno::RuntimeException)
-+ {
-+ return m_xIndexAccess->getCount();
-+ }
-+
-+ virtual css::uno::Any SAL_CALL Item( const css::uno::Any& Index1, const css::uno::Any& /*not processed in this base class*/ ) throw (css::uno::RuntimeException)
-+ {
-+ if ( Index1.getValueTypeClass() != css::uno::TypeClass_STRING )
-+ {
-+ sal_Int32 nIndex = 0;
-+
-+ if ( ( Index1 >>= nIndex ) != sal_True )
-+ {
-+ rtl::OUString message;
-+ message = rtl::OUString::createFromAscii(
-+ "Couldn't convert index to Int32");
-+ throw css::lang::IndexOutOfBoundsException( message,
-+ css::uno::Reference< css::uno::XInterface >() );
-+ }
-+ return getItemByIntIndex( nIndex );
-+ }
-+ rtl::OUString aStringSheet;
-+
-+ Index1 >>= aStringSheet;
-+ return getItemByStringIndex( aStringSheet );
-+ }
-+ // XDefaultMethod
-+ ::rtl::OUString SAL_CALL getDefaultMethodName( ) throw (css::uno::RuntimeException)
-+ {
-+ const static rtl::OUString sName( RTL_CONSTASCII_USTRINGPARAM("Item") );
-+ return sName;
-+ }
-+ // XEnumerationAccess
-+ virtual css::uno::Reference< css::container::XEnumeration > SAL_CALL createEnumeration() throw (css::uno::RuntimeException) = 0;
-+
-+ // XElementAccess
-+ virtual css::uno::Type SAL_CALL getElementType() throw (css::uno::RuntimeException) = 0;
-+ // XElementAccess
-+ virtual ::sal_Bool SAL_CALL hasElements() throw (css::uno::RuntimeException)
-+ {
-+ return ( m_xIndexAccess->getCount() > 0 );
-+ }
-+ virtual css::uno::Any createCollectionObject( const css::uno::Any& aSource ) = 0;
-+
-+};
-+
-+typedef ::cppu::WeakImplHelper1<ov::XCollection> XCollection_InterfacesBASE;
-+
-+typedef ScVbaCollectionBase< XCollection_InterfacesBASE > CollImplBase1;
-+// compatible with the old collections ( pre XHelperInterface base class ) ( some internal objects still use this )
-+class ScVbaCollectionBaseImpl : public CollImplBase1
-+{
-+public:
-+ ScVbaCollectionBaseImpl( const css::uno::Reference< ov::XHelperInterface > xParent, const css::uno::Reference< css::uno::XComponentContext >& xContext, const css::uno::Reference< css::container::XIndexAccess >& xIndexAccess ) throw( css::uno::RuntimeException ) : CollImplBase1( xParent, xContext, xIndexAccess){}
-+
-+};
-+
-+template <typename Ifc> // where Ifc must implement XCollectionTest
-+class CollTestImplHelper : public ScVbaCollectionBase< ::cppu::WeakImplHelper1< Ifc > >
-+{
-+typedef ScVbaCollectionBase< ::cppu::WeakImplHelper1< Ifc > > ImplBase1;
-+
-+public:
-+ CollTestImplHelper( const css::uno::Reference< ov::XHelperInterface >& xParent, const css::uno::Reference< css::uno::XComponentContext >& xContext, const css::uno::Reference< css::container::XIndexAccess >& xIndexAccess ) throw( css::uno::RuntimeException ) : ImplBase1( xParent, xContext, xIndexAccess ) {}
-+};
-+
-+
-+#endif //SC_VBA_COLLECTION_IMPL_HXX
---- vbahelper/inc/vbahelper/vbadllapi.h.old 1970-01-01 00:00:00.000000000 +0000
-+++ vbahelper/inc/vbahelper/vbadllapi.h 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,44 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile: svldllapi.h,v $
-+ * $Revision: 1.4 $
-+ *
-+ * 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.
-+ *
-+ ************************************************************************/
-+
-+#ifndef INCLUDED_VBADLLAPI_H
-+#define INCLUDED_VBADLLAPI_H
-+
-+#include "sal/types.h"
-+
-+#if defined(VBAHELPER_DLLIMPLEMENTATION)
-+#define VBAHELPER_DLLPUBLIC SAL_DLLPUBLIC_EXPORT
-+#else
-+#define VBAHELPER_DLLPUBLIC SAL_DLLPUBLIC_IMPORT
-+#endif
-+#define VBAHELPER_DLLPRIVATE SAL_DLLPRIVATE
-+
-+#endif /* INCLUDED_SVLDLLAPI_H */
-+
---- vbahelper/inc/vbahelper/vbadocumentbase.hxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ vbahelper/inc/vbahelper/vbadocumentbase.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,73 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile:
-+ * $Revision:
-+ *
-+ * 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.
-+ *
-+ ************************************************************************/
-+#ifndef VBA_DOCUMENTBASE_HXX
-+#define VBA_DOCUMENTBASE_HXX
-+
-+#include <com/sun/star/frame/XModel.hpp>
-+#include <ooo/vba/XDocumentBase.hpp>
-+#include <vbahelper/vbahelperinterface.hxx>
-+
-+typedef InheritedHelperInterfaceImpl1< ooo::vba::XDocumentBase > VbaDocumentBase_BASE;
-+
-+class VbaDocumentBase : public VbaDocumentBase_BASE
-+{
-+protected:
-+ css::uno::Reference< css::frame::XModel > mxModel;
-+protected:
-+ virtual css::uno::Reference< css::frame::XModel > getModel() { return mxModel; }
-+ VbaDocumentBase( const css::uno::Reference< ov::XHelperInterface >& xParent, const css::uno::Reference< css::uno::XComponentContext >& xContext);
-+public:
-+ VbaDocumentBase( const css::uno::Reference< ov::XHelperInterface >& xParent, const css::uno::Reference< css::uno::XComponentContext >& xContext,
-+ css::uno::Reference< css::frame::XModel > xModel );
-+ VbaDocumentBase( css::uno::Sequence< css::uno::Any > const& aArgs, css::uno::Reference< css::uno::XComponentContext >const& xContext );
-+ virtual ~VbaDocumentBase() {}
-+
-+ // Attributes
-+ virtual ::rtl::OUString SAL_CALL getName() throw (css::uno::RuntimeException);
-+ virtual ::rtl::OUString SAL_CALL getPath() throw (css::uno::RuntimeException);
-+ virtual ::rtl::OUString SAL_CALL getFullName() throw (css::uno::RuntimeException);
-+ virtual sal_Bool SAL_CALL getSaved() throw (css::uno::RuntimeException);
-+ virtual void SAL_CALL setSaved( sal_Bool bSave ) throw (css::uno::RuntimeException);
-+
-+ // Methods
-+ virtual void SAL_CALL Close( const css::uno::Any &bSaveChanges,
-+ const css::uno::Any &aFileName,
-+ const css::uno::Any &bRouteWorkbook ) throw (css::uno::RuntimeException);
-+ virtual void SAL_CALL Protect( const css::uno::Any & aPassword ) throw (css::uno::RuntimeException);
-+ virtual void SAL_CALL Unprotect( const css::uno::Any &aPassword ) throw (css::uno::RuntimeException);
-+ virtual void SAL_CALL Save() throw (css::uno::RuntimeException);
-+ virtual void SAL_CALL Activate() throw (css::uno::RuntimeException);
-+
-+ // XHelperInterface
-+ virtual rtl::OUString& getServiceImplName();
-+ virtual css::uno::Sequence<rtl::OUString> getServiceNames();
-+};
-+
-+#endif /* VBA_DOCUMENTBASE_HXX */
---- vbahelper/inc/vbahelper/vbaglobalbase.hxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ vbahelper/inc/vbahelper/vbaglobalbase.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,53 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile: vbaapplicationbase.hxx,v $
-+ * $Revision: 1.3 $
-+ *
-+ * 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.
-+ *
-+ ************************************************************************/
-+#ifndef VBA_GLOBAL_BASE_HXX
-+#define VBA_GLOBAL_BASE_HXX
-+
-+#include "vbahelperinterface.hxx"
-+#include <ooo/vba/XGlobalsBase.hpp>
-+
-+typedef InheritedHelperInterfaceImpl1< ov::XGlobalsBase > Globals_BASE;
-+class VbaGlobalsBase : public Globals_BASE
-+
-+{
-+protected:
-+
-+ bool hasServiceName( const rtl::OUString& serviceName );
-+ void init( const css::uno::Reference< css::uno::XComponentContext >& xContext, const css::uno::Any& aApplication );
-+
-+public:
-+ VbaGlobalsBase( const css::uno::Reference< ov::XHelperInterface >& xParent, const css::uno::Reference< css::uno::XComponentContext >& xContext);
-+ virtual ~VbaGlobalsBase(){};
-+ // XMultiServiceFactory
-+ virtual css::uno::Reference< css::uno::XInterface > SAL_CALL createInstance( const ::rtl::OUString& aServiceSpecifier ) throw (css::uno::Exception, css::uno::RuntimeException);
-+ virtual css::uno::Reference< css::uno::XInterface > SAL_CALL createInstanceWithArguments( const ::rtl::OUString& ServiceSpecifier, const css::uno::Sequence< css::uno::Any >& Arguments ) throw (css::uno::Exception, css::uno::RuntimeException);
-+ virtual css::uno::Sequence< ::rtl::OUString > SAL_CALL getAvailableServiceNames( ) throw (css::uno::RuntimeException);
-+};
-+#endif
---- vbahelper/inc/vbahelper/vbahelper.hxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ vbahelper/inc/vbahelper/vbahelper.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,224 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile: vbahelper.hxx,v $
-+ * $Revision: 1.5.32.1 $
-+ *
-+ * 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.
-+ *
-+ ************************************************************************/
-+#ifndef OOVBAAPI_VBA_HELPER_HXX
-+#define OOVBAAPI_VBA_HELPER_HXX
-+
-+#include <com/sun/star/drawing/XShape.hpp>
-+#include <com/sun/star/beans/XIntrospectionAccess.hpp>
-+#include <com/sun/star/beans/XPropertySet.hpp>
-+#include <com/sun/star/script/BasicErrorException.hpp>
-+#include <com/sun/star/script/XTypeConverter.hpp>
-+#include <com/sun/star/lang/IllegalArgumentException.hpp>
-+#include <com/sun/star/awt/XControl.hpp>
-+#include <com/sun/star/awt/XDevice.hpp>
-+#include <basic/sberrors.hxx>
-+#include <cppuhelper/implbase1.hxx>
-+#include <com/sun/star/frame/XModel.hpp>
-+#include <sfx2/dispatch.hxx>
-+//#include <ooo/vba/msforms/XShape.hpp>
-+#include <vcl/pointr.hxx>
-+#define VBAHELPER_DLLIMPLEMENTATION
-+#include <vbahelper/vbadllapi.h>
-+namespace css = ::com::sun::star;
-+
-+namespace ooo
-+{
-+ namespace vba
-+ {
-+ template < class T >
-+ css::uno::Reference< T > getXSomethingFromArgs( css::uno::Sequence< css::uno::Any > const & args, sal_Int32 nPos, bool bCanBeNull = true ) throw (css::lang::IllegalArgumentException)
-+ {
-+ if ( args.getLength() < ( nPos + 1) )
-+ throw css::lang::IllegalArgumentException();
-+ css::uno::Reference< T > aSomething( args[ nPos ], css::uno::UNO_QUERY );
-+ if ( !bCanBeNull && !aSomething.is() )
-+ throw css::lang::IllegalArgumentException();
-+ return aSomething;
-+ }
-+ VBAHELPER_DLLPUBLIC css::uno::Reference< css::uno::XInterface > createVBAUnoAPIService( SfxObjectShell* pShell, const sal_Char* _pAsciiName ) throw (css::uno::RuntimeException);
-+ VBAHELPER_DLLPUBLIC css::uno::Reference< css::uno::XInterface > createVBAUnoAPIServiceWithArgs( SfxObjectShell* pShell, const sal_Char* _pAsciiName, const css::uno::Sequence< css::uno::Any >& aArgs ) throw (css::uno::RuntimeException);
-+ VBAHELPER_DLLPUBLIC css::uno::Reference< css::frame::XModel > getCurrentDocument() throw (css::uno::RuntimeException);
-+ VBAHELPER_DLLPUBLIC css::uno::Reference< css::beans::XIntrospectionAccess > getIntrospectionAccess( const css::uno::Any& aObject ) throw (css::uno::RuntimeException);
-+ VBAHELPER_DLLPUBLIC css::uno::Reference< css::script::XTypeConverter > getTypeConverter( const css::uno::Reference< css::uno::XComponentContext >& xContext ) throw (css::uno::RuntimeException);
-+
-+ VBAHELPER_DLLPUBLIC void dispatchRequests (css::uno::Reference< css::frame::XModel>& xModel,rtl::OUString & aUrl) ;
-+ VBAHELPER_DLLPUBLIC void dispatchRequests (css::uno::Reference< css::frame::XModel>& xModel,rtl::OUString & aUrl, css::uno::Sequence< css::beans::PropertyValue >& sProps ) ;
-+ VBAHELPER_DLLPUBLIC void dispatchExecute(SfxViewShell* pView, USHORT nSlot, SfxCallMode nCall = SFX_CALLMODE_SYNCHRON );
-+ VBAHELPER_DLLPUBLIC sal_Int32 OORGBToXLRGB( sal_Int32 );
-+ VBAHELPER_DLLPUBLIC sal_Int32 XLRGBToOORGB( sal_Int32 );
-+ VBAHELPER_DLLPUBLIC css::uno::Any OORGBToXLRGB( const css::uno::Any& );
-+ VBAHELPER_DLLPUBLIC css::uno::Any XLRGBToOORGB( const css::uno::Any& );
-+ // provide a NULL object that can be passed as variant so that
-+ // the object when passed to IsNull will return true. aNULL
-+ // contains an empty object reference
-+ VBAHELPER_DLLPUBLIC const css::uno::Any& aNULL();
-+ VBAHELPER_DLLPUBLIC void PrintOutHelper( SfxViewShell* pViewShell, const css::uno::Any& From, const css::uno::Any& To, const css::uno::Any& Copies, const css::uno::Any& Preview, const css::uno::Any& ActivePrinter, const css::uno::Any& PrintToFile, const css::uno::Any& Collate, const css::uno::Any& PrToFileName, sal_Bool bSelection );
-+ VBAHELPER_DLLPUBLIC void PrintPreviewHelper( const css::uno::Any& EnableChanges, SfxViewShell* );
-+
-+ VBAHELPER_DLLPUBLIC rtl::OUString getAnyAsString( const css::uno::Any& pvargItem ) throw ( css::uno::RuntimeException );
-+ VBAHELPER_DLLPUBLIC rtl::OUString VBAToRegexp(const rtl::OUString &rIn, bool bForLike = false); // needs to be in an uno service ( already this code is duplicated in basic )
-+ VBAHELPER_DLLPUBLIC double getPixelTo100thMillimeterConversionFactor( css::uno::Reference< css::awt::XDevice >& xDevice, sal_Bool bVertical);
-+ VBAHELPER_DLLPUBLIC double PointsToPixels( css::uno::Reference< css::awt::XDevice >& xDevice, double fPoints, sal_Bool bVertical);
-+ VBAHELPER_DLLPUBLIC double PixelsToPoints( css::uno::Reference< css::awt::XDevice >& xDevice, double fPoints, sal_Bool bVertical);
-+ VBAHELPER_DLLPUBLIC sal_Int32 getPointerStyle();
-+ VBAHELPER_DLLPUBLIC void setCursorHelper( const Pointer& rPointer, sal_Bool bOverWrite );
-+ VBAHELPER_DLLPUBLIC String docMacroExists( SfxObjectShell* pShell, const String& sMod, const String& sMacro );
-+
-+class VBAHELPER_DLLPUBLIC Millimeter
-+{
-+//Factor to translate between points and hundredths of millimeters:
-+private:
-+ static const double factor;
-+
-+ double m_nMillimeter;
-+
-+public:
-+ Millimeter();
-+
-+ Millimeter(double mm);
-+
-+ void set(double mm);
-+ void setInPoints(double points) ;
-+ void setInHundredthsOfOneMillimeter(double hmm);
-+ double get();
-+ double getInHundredthsOfOneMillimeter();
-+ double getInPoints();
-+ static sal_Int32 getInHundredthsOfOneMillimeter(double points);
-+ static double getInPoints(int _hmm);
-+};
-+
-+class VBAHELPER_DLLPUBLIC AbstractGeometryAttributes // probably should replace the ShapeHelper below
-+{
-+public:
-+ virtual ~AbstractGeometryAttributes() {}
-+ virtual double getLeft() = 0;
-+ virtual void setLeft( double ) = 0;
-+ virtual double getTop() = 0;
-+ virtual void setTop( double ) = 0;
-+ virtual double getHeight() = 0;
-+ virtual void setHeight( double ) = 0;
-+ virtual double getWidth() = 0;
-+ virtual void setWidth( double ) = 0;
-+};
-+
-+namespace msforms {
-+ class XShape;
-+}
-+
-+class VBAHELPER_DLLPUBLIC ConcreteXShapeGeometryAttributes : public AbstractGeometryAttributes
-+{
-+public:
-+ css::uno::Reference< ooo::vba::msforms::XShape > m_xShape;
-+ ConcreteXShapeGeometryAttributes( const css::uno::Reference< css::uno::XComponentContext >& xContext, const css::uno::Reference< css::drawing::XShape >& xShape );
-+ virtual double getLeft();
-+ virtual void setLeft( double nLeft );
-+ virtual double getTop();
-+ virtual void setTop( double nTop );
-+ virtual double getHeight();
-+ virtual void setHeight( double nHeight );
-+ virtual double getWidth();
-+ virtual void setWidth( double nWidth);
-+};
-+#define VBA_LEFT "PositionX"
-+#define VBA_TOP "PositionY"
-+class VBAHELPER_DLLPUBLIC UserFormGeometryHelper : public AbstractGeometryAttributes
-+{
-+
-+ css::uno::Reference< css::beans::XPropertySet > mxModel;
-+public:
-+ UserFormGeometryHelper( const css::uno::Reference< css::uno::XComponentContext >& xContext, const css::uno::Reference< css::awt::XControl >& xControl );
-+ virtual double getLeft();
-+ virtual void setLeft( double nLeft );
-+ virtual double getTop();
-+ virtual void setTop( double nTop );
-+ virtual double getHeight();
-+ virtual void setHeight( double nHeight );
-+ virtual double getWidth();
-+ virtual void setWidth( double nWidth);
-+};
-+
-+class VBAHELPER_DLLPUBLIC ShapeHelper
-+{
-+protected:
-+ css::uno::Reference< css::drawing::XShape > xShape;
-+public:
-+ ShapeHelper( const css::uno::Reference< css::drawing::XShape >& _xShape) throw (css::script::BasicErrorException );
-+
-+ double getHeight();
-+
-+ void setHeight(double _fheight) throw ( css::script::BasicErrorException );
-+
-+ double getWidth();
-+
-+ void setWidth(double _fWidth) throw ( css::script::BasicErrorException );
-+
-+ double getLeft();
-+
-+ void setLeft(double _fLeft);
-+
-+ double getTop();
-+
-+ void setTop(double _fTop);
-+};
-+
-+class VBAHELPER_DLLPUBLIC ContainerUtilities
-+{
-+
-+public:
-+ static rtl::OUString getUniqueName( const css::uno::Sequence< ::rtl::OUString >& _slist, const rtl::OUString& _sElementName, const ::rtl::OUString& _sSuffixSeparator);
-+ static rtl::OUString getUniqueName( const css::uno::Sequence< rtl::OUString >& _slist, const rtl::OUString _sElementName, const rtl::OUString& _sSuffixSeparator, sal_Int32 _nStartSuffix );
-+
-+ static sal_Int32 FieldInList( const css::uno::Sequence< rtl::OUString >& SearchList, const rtl::OUString& SearchString );
-+};
-+
-+// really just a a place holder to ease the porting pain
-+class VBAHELPER_DLLPUBLIC DebugHelper
-+{
-+public:
-+ static void exception( const rtl::OUString& DetailedMessage, const css::uno::Exception& ex, int err, const rtl::OUString& /*additionalArgument*/ ) throw( css::script::BasicErrorException );
-+
-+ static void exception( int err, const rtl::OUString& additionalArgument ) throw( css::script::BasicErrorException );
-+
-+ static void exception( css::uno::Exception& ex ) throw( css::script::BasicErrorException );
-+};
-+ } // openoffice
-+} // org
-+
-+namespace ov = ooo::vba;
-+
-+#ifdef DEBUG
-+# define SC_VBA_FIXME(a) OSL_TRACE( a )
-+# define SC_VBA_STUB() SC_VBA_FIXME(( "%s - stubbed\n", __FUNCTION__ ))
-+#else
-+# define SC_VBA_FIXME(a)
-+# define SC_VBA_STUB()
-+#endif
-+
-+#endif
---- vbahelper/inc/vbahelper/vbahelperinterface.hxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ vbahelper/inc/vbahelper/vbahelperinterface.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,121 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile: vbahelperinterface.hxx,v $
-+ * $Revision: 1.3 $
-+ *
-+ * 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.
-+ *
-+ ************************************************************************/
-+#ifndef OOVBAAPI_VBA_HELPERINTERFACE_HXX
-+#define OOVBAAPI_VBA_HELPERINTERFACE_HXX
-+
-+#include <cppuhelper/implbase1.hxx>
-+#include <ooo/vba/XHelperInterface.hpp>
-+#include <vbahelper/vbahelper.hxx>
-+#include <com/sun/star/container/XNameAccess.hpp>
-+
-+// use this class when you have an a object like
-+// interface XAnInterface which contains XHelperInterface in its inheritance hierarchy
-+// interface XAnInterface
-+// {
-+// interface XHelperInterface;
-+// [attribute, string] name;
-+// }
-+// or
-+// interface XAnInterface : XHelperInterface;
-+// {
-+// [attribute, string] name;
-+// }
-+//
-+// then this class can provide a default implementation of XHelperInterface,
-+// you can use it like this
-+// typedef InheritedHelperInterfaceImpl< XAnInterface > > AnInterfaceImpl_BASE;
-+// class AnInterfaceImpl : public AnInterfaceImpl_BASE
-+// {
-+// public:
-+// AnInterface( const Reference< HelperInterface >& xParent ) : AnInterfaceImpl_BASE( xParent ) {}
-+// // implement XAnInterface methods only, no need to implement the XHelperInterface
-+// // methods
-+// virtual void setName( const OUString& );
-+// virtual OUString getName();
-+// }
-+//
-+const ::rtl::OUString sHelperServiceName( RTL_CONSTASCII_USTRINGPARAM( "ooo.vba.HelperServiceBase" ) );
-+
-+template< typename Ifc1 >
-+class InheritedHelperInterfaceImpl : public Ifc1
-+{
-+protected:
-+ css::uno::WeakReference< ov::XHelperInterface > mxParent;
-+ css::uno::Reference< css::uno::XComponentContext > mxContext;
-+public:
-+ InheritedHelperInterfaceImpl() {}
-+ InheritedHelperInterfaceImpl( const css::uno::Reference< ov::XHelperInterface >& xParent, const css::uno::Reference< css::uno::XComponentContext >& xContext ) : mxParent( xParent ), mxContext( xContext ) {}
-+ virtual rtl::OUString& getServiceImplName() = 0;
-+ virtual css::uno::Sequence<rtl::OUString> getServiceNames() = 0;
-+
-+ // XHelperInterface Methods
-+ virtual ::sal_Int32 SAL_CALL getCreator() throw (css::script::BasicErrorException, css::uno::RuntimeException)
-+ {
-+ return 0x53756E4F;
-+ }
-+ virtual css::uno::Reference< ov::XHelperInterface > SAL_CALL getParent( ) throw (css::script::BasicErrorException, css::uno::RuntimeException) { return mxParent; }
-+
-+ virtual css::uno::Any SAL_CALL Application( ) throw (css::script::BasicErrorException, css::uno::RuntimeException) {
-+ // The application could certainly be passed around in the context - seems
-+ // to make sense
-+ css::uno::Reference< css::container::XNameAccess > xNameAccess( mxContext, css::uno::UNO_QUERY_THROW );
-+ return xNameAccess->getByName( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("Application" ) ) );
-+ }
-+
-+
-+ // XServiceInfo Methods
-+ virtual ::rtl::OUString SAL_CALL getImplementationName( ) throw (css::uno::RuntimeException) { return getServiceImplName(); }
-+ virtual ::sal_Bool SAL_CALL supportsService( const ::rtl::OUString& ServiceName ) throw (css::uno::RuntimeException)
-+ {
-+ css::uno::Sequence< rtl::OUString > sServices = getSupportedServiceNames();
-+ const rtl::OUString* pStart = sServices.getConstArray();
-+ const rtl::OUString* pEnd = pStart + sServices.getLength();
-+ for ( ; pStart != pEnd ; ++pStart )
-+ if ( (*pStart).equals( ServiceName ) )
-+ return sal_True;
-+ return sal_False;
-+ }
-+ virtual css::uno::Sequence< ::rtl::OUString > SAL_CALL getSupportedServiceNames( ) throw (css::uno::RuntimeException)
-+ {
-+ css::uno::Sequence< rtl::OUString > aNames = getServiceNames();;
-+ return aNames;
-+ }
-+ };
-+
-+template< typename Ifc1 >
-+class InheritedHelperInterfaceImpl1 : public InheritedHelperInterfaceImpl< ::cppu::WeakImplHelper1< Ifc1 > >
-+
-+{
-+typedef InheritedHelperInterfaceImpl< ::cppu::WeakImplHelper1< Ifc1 > > Base;
-+public:
-+ InheritedHelperInterfaceImpl1< Ifc1 > ( const css::uno::Reference< ov::XHelperInterface >& xParent, const css::uno::Reference< css::uno::XComponentContext >& xContext ) : Base( xParent, xContext ) {}
-+
-+};
-+#endif
---- vbahelper/inc/vbahelper/vbapropvalue.hxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ vbahelper/inc/vbahelper/vbapropvalue.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,60 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile: vbapropvalue.hxx,v $
-+ * $Revision: 1.3 $
-+ *
-+ * 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.
-+ *
-+ ************************************************************************/
-+#ifndef SC_VBA_PROPVALULE_HXX
-+#define SC_VBA_PROPVALULE_HXX
-+#include <ooo/vba/XPropValue.hpp>
-+#include <cppuhelper/implbase1.hxx>
-+
-+#include <vbahelper/vbahelper.hxx>
-+
-+typedef ::cppu::WeakImplHelper1< ov::XPropValue > PropValueImpl_BASE;
-+
-+class PropListener
-+{
-+public:
-+ virtual void setValueEvent( const css::uno::Any& value ) = 0;
-+ virtual css::uno::Any getValueEvent() = 0;
-+};
-+
-+
-+class ScVbaPropValue : public PropValueImpl_BASE
-+{
-+ PropListener* m_pListener;
-+public:
-+ ScVbaPropValue( PropListener* pListener );
-+
-+ // Attributes
-+ virtual css::uno::Any SAL_CALL getValue() throw (css::uno::RuntimeException);
-+ virtual void SAL_CALL setValue( const css::uno::Any& _value ) throw (css::uno::RuntimeException);
-+
-+ rtl::OUString SAL_CALL getDefaultPropertyName() throw (css::uno::RuntimeException) { return ::rtl::OUString::createFromAscii("Value"); }
-+
-+};
-+#endif //SC_VBA_PROPVALULE_HXX
---- vbahelper/inc/vbahelper/vbawindowbase.hxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ vbahelper/inc/vbahelper/vbawindowbase.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,66 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile:
-+ * $Revision:
-+ *
-+ * 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.
-+ *
-+ ************************************************************************/
-+#ifndef VBA_WINDOWBASE_HXX
-+#define VBA_WINDOWBASE_HXX
-+#include <cppuhelper/implbase1.hxx>
-+#include <ooo/vba/XWindowBase.hpp>
-+#include <com/sun/star/frame/XModel.hpp>
-+#include <com/sun/star/awt/XDevice.hpp>
-+
-+#include <vbahelper/vbahelperinterface.hxx>
-+
-+typedef InheritedHelperInterfaceImpl1<ov::XWindowBase > WindowBaseImpl_BASE;
-+
-+class VbaWindowBase : public WindowBaseImpl_BASE
-+{
-+protected:
-+ css::uno::Reference< css::frame::XModel > m_xModel;
-+public:
-+ VbaWindowBase( const css::uno::Reference< ov::XHelperInterface >& xParent, const css::uno::Reference< css::uno::XComponentContext >& xContext, const css::uno::Reference< css::frame::XModel >& xModel );
-+ VbaWindowBase( css::uno::Sequence< css::uno::Any > const& aArgs, css::uno::Reference< css::uno::XComponentContext > const& xContext );
-+
-+ // XWindowBase
-+ virtual sal_Int32 SAL_CALL getHeight() throw (css::uno::RuntimeException) ;
-+ virtual void SAL_CALL setHeight( sal_Int32 _height ) throw (css::uno::RuntimeException) ;
-+ virtual sal_Int32 SAL_CALL getLeft() throw (css::uno::RuntimeException) ;
-+ virtual void SAL_CALL setLeft( sal_Int32 _left ) throw (css::uno::RuntimeException) ;
-+ virtual sal_Int32 SAL_CALL getTop() throw (css::uno::RuntimeException) ;
-+ virtual void SAL_CALL setTop( sal_Int32 _top ) throw (css::uno::RuntimeException) ;
-+ virtual sal_Bool SAL_CALL getVisible() throw (css::uno::RuntimeException);
-+ virtual void SAL_CALL setVisible( sal_Bool _visible ) throw (css::uno::RuntimeException);
-+ virtual sal_Int32 SAL_CALL getWidth() throw (css::uno::RuntimeException) ;
-+ virtual void SAL_CALL setWidth( sal_Int32 _width ) throw (css::uno::RuntimeException) ;
-+
-+ // XHelperInterface
-+ virtual rtl::OUString& getServiceImplName();
-+ virtual css::uno::Sequence<rtl::OUString> getServiceNames();
-+};
-+
-+#endif //VBA_WINDOWBASE_HXX
---- vbahelper/prj/build.lst.old 1970-01-01 00:00:00.000000000 +0000
-+++ vbahelper/prj/build.lst 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,6 @@
-+vba vbahelper : oovbaapi basic sfx2 svx cppuhelper vcl comphelper svtools tools sal NULL
-+vba vbahelper usr1 - all vba_mkout NULL
-+#vba vbahelper\inc nmake - all vba_inc NULL
-+vba vbahelper\source\vbahelper nmake - all vba_vbahelper NULL
-+vba vbahelper\source\msforms nmake - all vba_msforms NULL
-+vba vbahelper\util nmake - all vba_util vba_vbahelper vba_msforms NULL
---- vbahelper/prj/d.lst.old 1970-01-01 00:00:00.000000000 +0000
-+++ vbahelper/prj/d.lst 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,18 @@
-+..\%__SRC%\lib\lib*.so %_DEST%\lib%_EXT%
-+..\%__SRC%\lib\lib*.dylib %_DEST%\lib%_EXT%
-+..\%__SRC%\slb\vbahelper.lib %_DEST%\lib%_EXT%\vbahelper.lib
-+..\%__SRC%\lib\vbahelp*.* %_DEST%\lib%_EXT%\vba*.*
-+..\%__SRC%\bin\vbahelper*.* %_DEST%\bin%_EXT%\vbahelper*.*
-+..\%__SRC%\bin\msforms*.* %_DEST%\bin%_EXT%\msforms*.*
-+
-+mkdir: %_DEST%\inc%_EXT%\basic
-+..\inc\vbahelper\vbacollectionimpl.hxx %_DEST%\inc%_EXT%\vbahelper\vbacollectionimpl.hxx
-+..\inc\vbahelper\vbahelper.hxx %_DEST%\inc%_EXT%\vbahelper\vbahelper.hxx
-+..\inc\vbahelper\helperdecl.hxx %_DEST%\inc%_EXT%\vbahelper\helperdecl.hxx
-+..\inc\vbahelper\vbahelperinterface.hxx %_DEST%\inc%_EXT%\vbahelper\vbahelperinterface.hxx
-+..\inc\vbahelper\vbaapplicationbase.hxx %_DEST%\inc%_EXT%\vbahelper\vbaapplicationbase.hxx
-+..\inc\vbahelper\vbadllapi.h %_DEST%\inc%_EXT%\vbahelper\vbadllapi.h
-+..\inc\vbahelper\vbawindowbase.hxx %_DEST%\inc%_EXT%\vbahelper\vbawindowbase.hxx
-+..\inc\vbahelper\vbadocumentbase.hxx %_DEST%\inc%_EXT%\vbahelper\vbadocumentbase.hxx
-+..\inc\vbahelper\vbapropvalue.hxx %_DEST%\inc%_EXT%\vbahelper\vbapropvalue.hxx
-+..\inc\vbahelper\vbaglobalbase.hxx %_DEST%\inc%_EXT%\vbahelper\vbaglobalbase.hxx
---- vbahelper/source/msforms/makefile.mk.old 1970-01-01 00:00:00.000000000 +0000
-+++ vbahelper/source/msforms/makefile.mk 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,78 @@
-+#*************************************************************************
-+#
-+# DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+#
-+# Copyright 2008 by Sun Microsystems, Inc.
-+#
-+# OpenOffice.org - a multi-platform office productivity suite
-+#
-+# $RCSfile: makefile.mk,v $
-+#
-+# $Revision: 1.45 $
-+#
-+# 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.
-+#
-+#*************************************************************************
-+
-+PRJ=..$/..
-+PRJNAME=vbahelper
-+TARGET=msforms
-+
-+ENABLE_EXCEPTIONS := TRUE
-+
-+# --- Settings -----------------------------------------------------
-+
-+.INCLUDE : settings.mk
-+
-+SLOFILES=\
-+ $(SLO)$/vbacontrol.obj \
-+ $(SLO)$/vbacontrols.obj \
-+ $(SLO)$/vbabutton.obj \
-+ $(SLO)$/vbacombobox.obj \
-+ $(SLO)$/vbalabel.obj \
-+ $(SLO)$/vbatextbox.obj \
-+ $(SLO)$/vbaradiobutton.obj \
-+ $(SLO)$/vbalistbox.obj \
-+ $(SLO)$/vbatogglebutton.obj \
-+ $(SLO)$/vbacheckbox.obj \
-+ $(SLO)$/vbaframe.obj \
-+ $(SLO)$/vbascrollbar.obj \
-+ $(SLO)$/vbaprogressbar.obj \
-+ $(SLO)$/vbamultipage.obj \
-+ $(SLO)$/vbalistcontrolhelper.obj \
-+ $(SLO)$/vbaspinbutton.obj \
-+ $(SLO)$/vbaimage.obj \
-+ $(SLO)$/vbapages.obj \
-+ $(SLO)$/vbauserform.obj \
-+ $(SLO)$/service.obj \
-+
-+# #FIXME vbapropvalue needs to move to vbahelper
-+
-+# --- Targets -------------------------------------------------------
-+
-+.INCLUDE : target.mk
-+
-+ALLTAR : \
-+ $(MISC)$/$(TARGET).don \
-+
-+$(SLOFILES) : $(MISC)$/$(TARGET).don
-+
-+$(MISC)$/$(TARGET).don : $(SOLARBINDIR)$/oovbaapi.rdb
-+ +$(CPPUMAKER) -O$(INCCOM)$/$(TARGET) -BUCR $(SOLARBINDIR)$/oovbaapi.rdb -X$(SOLARBINDIR)$/types.rdb && echo > $@
-+ echo $@
-+
---- vbahelper/source/msforms/service.cxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ vbahelper/source/msforms/service.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,83 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile: service.cxx,v $
-+ * $Revision: 1.4 $
-+ *
-+ * 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 "cppuhelper/implementationentry.hxx"
-+#include "com/sun/star/lang/XMultiServiceFactory.hpp"
-+#include "com/sun/star/registry/XRegistryKey.hpp"
-+#include "comphelper/servicedecl.hxx"
-+
-+// =============================================================================
-+// component exports
-+// =============================================================================
-+using namespace ::com::sun::star;
-+using namespace ::com::sun::star::uno;
-+
-+namespace sdecl = comphelper::service_decl;
-+
-+// reference service helper(s)
-+namespace controlprovider
-+{
-+extern sdecl::ServiceDecl const serviceDecl;
-+}
-+
-+namespace userform
-+{
-+extern sdecl::ServiceDecl const serviceDecl;
-+}
-+
-+extern "C"
-+{
-+ void SAL_CALL component_getImplementationEnvironment(
-+ const sal_Char ** ppEnvTypeName, uno_Environment ** /*ppEnv*/ )
-+ {
-+ OSL_TRACE("In component_getImplementationEnv");
-+ *ppEnvTypeName = CPPU_CURRENT_LANGUAGE_BINDING_NAME;
-+ }
-+
-+ sal_Bool SAL_CALL component_writeInfo(
-+ lang::XMultiServiceFactory * pServiceManager, registry::XRegistryKey * pRegistryKey )
-+ {
-+ OSL_TRACE("In component_writeInfo");
-+
-+ // Component registration
-+ return component_writeInfoHelper( pServiceManager, pRegistryKey,
-+ controlprovider::serviceDecl, userform::serviceDecl );
-+ }
-+
-+ void * SAL_CALL component_getFactory(
-+ const sal_Char * pImplName, lang::XMultiServiceFactory * pServiceManager,
-+ registry::XRegistryKey * pRegistryKey )
-+ {
-+ OSL_TRACE("In component_getFactory for %s", pImplName );
-+ void* pRet = component_getFactoryHelper(
-+ pImplName, pServiceManager, pRegistryKey, controlprovider::serviceDecl, userform::serviceDecl );
-+ OSL_TRACE("Ret is 0x%x", pRet);
-+ return pRet;
-+ }
-+}
---- vbahelper/source/msforms/vbabutton.cxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ vbahelper/source/msforms/vbabutton.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,74 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile: vbabutton.cxx,v $
-+ * $Revision: 1.3 $
-+ *
-+ * 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 "vbabutton.hxx"
-+#include <vector>
-+
-+using namespace com::sun::star;
-+using namespace ooo::vba;
-+
-+
-+const static rtl::OUString LABEL( RTL_CONSTASCII_USTRINGPARAM("Label") );
-+ScVbaButton::ScVbaButton( const uno::Reference< XHelperInterface >& xParent, const uno::Reference< uno::XComponentContext >& xContext, const uno::Reference< uno::XInterface >& xControl, const uno::Reference< frame::XModel >& xModel, AbstractGeometryAttributes* pGeomHelper ) : ButtonImpl_BASE( xParent, xContext, xControl, xModel, pGeomHelper )
-+{
-+}
-+
-+// Attributes
-+rtl::OUString SAL_CALL
-+ScVbaButton::getCaption() throw (css::uno::RuntimeException)
-+{
-+ rtl::OUString Label;
-+ m_xProps->getPropertyValue( LABEL ) >>= Label;
-+ return Label;
-+}
-+
-+void SAL_CALL
-+ScVbaButton::setCaption( const rtl::OUString& _caption ) throw (::com::sun::star::uno::RuntimeException)
-+{
-+ m_xProps->setPropertyValue( LABEL, uno::makeAny( _caption ) );
-+}
-+
-+rtl::OUString&
-+ScVbaButton::getServiceImplName()
-+{
-+ static rtl::OUString sImplName( RTL_CONSTASCII_USTRINGPARAM("ScVbaButton") );
-+ return sImplName;
-+}
-+
-+uno::Sequence< rtl::OUString >
-+ScVbaButton::getServiceNames()
-+{
-+ static uno::Sequence< rtl::OUString > aServiceNames;
-+ if ( aServiceNames.getLength() == 0 )
-+ {
-+ aServiceNames.realloc( 1 );
-+ aServiceNames[ 0 ] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.msforms.Button" ) );
-+ }
-+ return aServiceNames;
-+}
---- vbahelper/source/msforms/vbabutton.hxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ vbahelper/source/msforms/vbabutton.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,51 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile: vbabutton.hxx,v $
-+ * $Revision: 1.3 $
-+ *
-+ * 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.
-+ *
-+ ************************************************************************/
-+#ifndef SC_VBA_BUTTON_HXX
-+#define SC_VBA_BUTTON_HXX
-+#include <cppuhelper/implbase1.hxx>
-+#include <ooo/vba/msforms/XButton.hpp>
-+
-+#include "vbacontrol.hxx"
-+#include <vbahelper/vbahelper.hxx>
-+
-+typedef cppu::ImplInheritanceHelper1< ScVbaControl, ov::msforms::XButton > ButtonImpl_BASE;
-+
-+class ScVbaButton : public ButtonImpl_BASE
-+{
-+public:
-+ ScVbaButton( const css::uno::Reference< ov::XHelperInterface >& xParent, const css::uno::Reference< css::uno::XComponentContext >& xContext, const css::uno::Reference< css::uno::XInterface >& xControl, const css::uno::Reference< css::frame::XModel >& xModel, ov::AbstractGeometryAttributes* pGeomHelper );
-+ // Attributes
-+ virtual rtl::OUString SAL_CALL getCaption() throw (css::uno::RuntimeException);
-+ virtual void SAL_CALL setCaption( const rtl::OUString& _caption ) throw (css::uno::RuntimeException);
-+ //XHelperInterface
-+ virtual rtl::OUString& getServiceImplName();
-+ virtual css::uno::Sequence<rtl::OUString> getServiceNames();
-+};
-+#endif //SC_VBA_BUTTON_HXX
---- vbahelper/source/msforms/vbacheckbox.cxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ vbahelper/source/msforms/vbacheckbox.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,112 @@
-+/*************************************************************************
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile$
-+ *
-+ * $Revision$
-+ *
-+ * last change: $Author$ $Date$
-+ *
-+ * The Contents of this file are made available subject to
-+ * the terms of GNU Lesser General Public License Version 2.1.
-+ *
-+ *
-+ * GNU Lesser General Public License Version 2.1
-+ * =============================================
-+ * Copyright 2005 by Sun Microsystems, Inc.
-+ * 901 San Antonio Road, Palo Alto, CA 94303, USA
-+ *
-+ * This library is free software; you can redistribute it and/or
-+ * modify it under the terms of the GNU Lesser General Public
-+ * License version 2.1, as published by the Free Software Foundation.
-+ *
-+ * This library 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 for more details.
-+ *
-+ * You should have received a copy of the GNU Lesser General Public
-+ * License along with this library; if not, write to the Free Software
-+ * Foundation, Inc., 59 Temple Place, Suite 330, Boston,
-+ * MA 02111-1307 USA
-+ *
-+ ************************************************************************/
-+#include "vbacheckbox.hxx"
-+#include <vbahelper/helperdecl.hxx>
-+#include <vector>
-+
-+using namespace com::sun::star;
-+using namespace ooo::vba;
-+
-+
-+const static rtl::OUString LABEL( RTL_CONSTASCII_USTRINGPARAM("Label") );
-+const static rtl::OUString STATE( RTL_CONSTASCII_USTRINGPARAM("State") );
-+ScVbaCheckbox::ScVbaCheckbox( const uno::Reference< ov::XHelperInterface >& xParent, const uno::Reference< uno::XComponentContext >& xContext, const uno::Reference< uno::XInterface >& xControl, const uno::Reference< frame::XModel >& xModel, ov::AbstractGeometryAttributes* pGeomHelper ) : CheckBoxImpl_BASE( xParent, xContext, xControl, xModel, pGeomHelper )
-+{
-+}
-+
-+// Attributes
-+rtl::OUString SAL_CALL
-+ScVbaCheckbox::getCaption() throw (css::uno::RuntimeException)
-+{
-+ rtl::OUString Label;
-+ m_xProps->getPropertyValue( LABEL ) >>= Label;
-+ return Label;
-+}
-+
-+void SAL_CALL
-+ScVbaCheckbox::setCaption( const rtl::OUString& _caption ) throw (::com::sun::star::uno::RuntimeException)
-+{
-+ m_xProps->setPropertyValue( LABEL, uno::makeAny( _caption ) );
-+}
-+
-+uno::Any SAL_CALL
-+ScVbaCheckbox::getValue() throw (css::uno::RuntimeException)
-+{
-+ sal_Int16 nValue = -1;
-+ m_xProps->getPropertyValue( STATE ) >>= nValue;
-+ if( nValue != 0 )
-+ nValue = -1;
-+// return uno::makeAny( nValue );
-+// I must be missing something MSO says value should be -1 if selected, 0 if not
-+// selected
-+ return uno::makeAny( ( nValue == -1 ) ? sal_True : sal_False );
-+}
-+
-+void SAL_CALL
-+ScVbaCheckbox::setValue( const uno::Any& _value ) throw (css::uno::RuntimeException)
-+{
-+ sal_Int16 nValue = 0;
-+ sal_Bool bValue = false;
-+ if( _value >>= nValue )
-+ {
-+ if( nValue == -1)
-+ nValue = 1;
-+ }
-+ else if ( _value >>= bValue )
-+ {
-+ if ( bValue )
-+ nValue = 1;
-+ }
-+ m_xProps->setPropertyValue( STATE, uno::makeAny( nValue ) );
-+}
-+rtl::OUString&
-+ScVbaCheckbox::getServiceImplName()
-+{
-+ static rtl::OUString sImplName( RTL_CONSTASCII_USTRINGPARAM("ScVbaCheckbox") );
-+ return sImplName;
-+}
-+
-+uno::Sequence< rtl::OUString >
-+ScVbaCheckbox::getServiceNames()
-+{
-+ static uno::Sequence< rtl::OUString > aServiceNames;
-+ if ( aServiceNames.getLength() == 0 )
-+ {
-+ aServiceNames.realloc( 1 );
-+ aServiceNames[ 0 ] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.msforms.CheckBox" ) );
-+ }
-+ return aServiceNames;
-+}
-+
---- vbahelper/source/msforms/vbacheckbox.hxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ vbahelper/source/msforms/vbacheckbox.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,61 @@
-+/*************************************************************************
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile$
-+ *
-+ * $Revision$
-+ *
-+ * last change: $Author$ $Date$
-+ *
-+ * The Contents of this file are made available subject to
-+ * the terms of GNU Lesser General Public License Version 2.1.
-+ *
-+ *
-+ * GNU Lesser General Public License Version 2.1
-+ * =============================================
-+ * Copyright 2005 by Sun Microsystems, Inc.
-+ * 901 San Antonio Road, Palo Alto, CA 94303, USA
-+ *
-+ * This library is free software; you can redistribute it and/or
-+ * modify it under the terms of the GNU Lesser General Public
-+ * License version 2.1, as published by the Free Software Foundation.
-+ *
-+ * This library 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 for more details.
-+ *
-+ * You should have received a copy of the GNU Lesser General Public
-+ * License along with this library; if not, write to the Free Software
-+ * Foundation, Inc., 59 Temple Place, Suite 330, Boston,
-+ * MA 02111-1307 USA
-+ *
-+ ************************************************************************/
-+#ifndef SC_VBA_CHECKBOX_HXX
-+#define SC_VBA_CHECKBOX_HXX
-+#include <cppuhelper/implbase2.hxx>
-+#include <ooo/vba/msforms/XRadioButton.hpp>
-+
-+#include "vbacontrol.hxx"
-+#include <vbahelper/vbahelper.hxx>
-+
-+typedef cppu::ImplInheritanceHelper2< ScVbaControl, ov::msforms::XRadioButton, css::script::XDefaultProperty > CheckBoxImpl_BASE;
-+
-+class ScVbaCheckbox : public CheckBoxImpl_BASE
-+{
-+public:
-+ ScVbaCheckbox( const css::uno::Reference< ov::XHelperInterface >& xParent, const css::uno::Reference< css::uno::XComponentContext >& xContext, const css::uno::Reference< css::uno::XInterface >& xControl, const css::uno::Reference< css::frame::XModel >& xModel, ov::AbstractGeometryAttributes* pGeomHelper );
-+ // Attributes
-+ virtual rtl::OUString SAL_CALL getCaption() throw (css::uno::RuntimeException);
-+ virtual void SAL_CALL setCaption( const rtl::OUString& _caption ) throw (css::uno::RuntimeException);
-+ virtual css::uno::Any SAL_CALL getValue() throw (css::uno::RuntimeException);
-+ virtual void SAL_CALL setValue( const css::uno::Any& _value ) throw (css::uno::RuntimeException);
-+ // XDefaultProperty
-+ rtl::OUString SAL_CALL getDefaultPropertyName( ) throw (css::uno::RuntimeException) { return ::rtl::OUString::createFromAscii("Value"); }
-+ //XHelperInterface
-+ virtual rtl::OUString& getServiceImplName();
-+ virtual css::uno::Sequence<rtl::OUString> getServiceNames();
-+};
-+
-+#endif //SC_VBA_CHECKBOX_HXX
---- vbahelper/source/msforms/vbacombobox.cxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ vbahelper/source/msforms/vbacombobox.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,175 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile: vbacombobox.cxx,v $
-+ * $Revision: 1.4 $
-+ *
-+ * 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 "vbacombobox.hxx"
-+#include <vector>
-+
-+using namespace com::sun::star;
-+using namespace ooo::vba;
-+
-+
-+//SelectedItems list of integer indexes
-+//StringItemList list of items
-+
-+const static rtl::OUString TEXT( RTL_CONSTASCII_USTRINGPARAM("Text") );
-+const static rtl::OUString SELECTEDITEMS( RTL_CONSTASCII_USTRINGPARAM("SelectedItems") );
-+const static rtl::OUString ITEMS( RTL_CONSTASCII_USTRINGPARAM("StringItemList") );
-+const static rtl::OUString CONTROLSOURCEPROP( RTL_CONSTASCII_USTRINGPARAM("DataFieldProperty") );
-+
-+ScVbaComboBox::ScVbaComboBox( const uno::Reference< XHelperInterface >& xParent, const uno::Reference< uno::XComponentContext >& xContext, const uno::Reference< uno::XInterface >& xControl, const uno::Reference< frame::XModel >& xModel, AbstractGeometryAttributes* pGeomHelper, bool bDialogType ) : ComboBoxImpl_BASE( xParent, xContext, xControl, xModel, pGeomHelper ), mbDialogType( bDialogType )
-+{
-+ mpListHelper.reset( new ListControlHelper( m_xProps ) );
-+ // grab the default value property name
-+ m_xProps->getPropertyValue( CONTROLSOURCEPROP ) >>= sSourceName;
-+}
-+
-+// Attributes
-+
-+
-+// Value, [read] e.g. getValue returns the value of ooo Text propery e.g. the value in
-+// the drop down
-+uno::Any SAL_CALL
-+ScVbaComboBox::getValue() throw (uno::RuntimeException)
-+{
-+ return m_xProps->getPropertyValue( sSourceName );
-+}
-+
-+void SAL_CALL
-+ScVbaComboBox::setListIndex( const uno::Any& _value ) throw (uno::RuntimeException)
-+{
-+ uno::Sequence< sal_Int16 > sSelection(1);
-+ _value >>= sSelection[ 0 ];
-+ m_xProps->setPropertyValue( SELECTEDITEMS, uno::makeAny( sSelection ) );
-+}
-+
-+uno::Any SAL_CALL
-+ScVbaComboBox::getListIndex() throw (uno::RuntimeException)
-+{
-+ uno::Sequence< rtl::OUString > sItems;
-+ m_xProps->getPropertyValue( ITEMS ) >>= sItems;
-+ // should really return the item that has focus regardless of
-+ // it been selected
-+ if ( sItems.getLength() > 0 )
-+ {
-+ rtl::OUString sText = getText();
-+ sal_Int32 nLen = sItems.getLength();
-+ for ( sal_Int32 index = 0; sText.getLength() && index < nLen; ++index )
-+ {
-+ if ( sItems[ index ].equals( sText ) )
-+ {
-+ OSL_TRACE("getListIndex returning %d", index );
-+ return uno::makeAny( index );
-+ }
-+
-+ }
-+ }
-+ OSL_TRACE("getListIndex returning %d", -1 );
-+ return uno::makeAny( sal_Int32( -1 ) );
-+}
-+
-+// Value, [write]e.g. setValue sets the value in the drop down, and if the value is one
-+// of the values in the list then the selection is also set
-+void SAL_CALL
-+ScVbaComboBox::setValue( const uno::Any& _value ) throw (uno::RuntimeException)
-+{
-+ m_xProps->setPropertyValue( sSourceName, _value );
-+}
-+
-+// see Value
-+
-+::rtl::OUString SAL_CALL
-+ScVbaComboBox::getText() throw (uno::RuntimeException)
-+{
-+ rtl::OUString result;
-+ getValue() >>= result;
-+ return result;
-+}
-+
-+void SAL_CALL
-+ScVbaComboBox::setText( const ::rtl::OUString& _text ) throw (uno::RuntimeException)
-+{
-+ setValue( uno::makeAny( _text ) ); // seems the same
-+}
-+
-+// Methods
-+void SAL_CALL
-+ScVbaComboBox::AddItem( const uno::Any& pvargItem, const uno::Any& pvargIndex ) throw (uno::RuntimeException)
-+{
-+ mpListHelper->AddItem( pvargItem, pvargIndex );
-+}
-+
-+void SAL_CALL
-+ScVbaComboBox::removeItem( const uno::Any& index ) throw (uno::RuntimeException)
-+ {
-+ mpListHelper->removeItem( index );
-+}
-+
-+void SAL_CALL
-+ScVbaComboBox::Clear( ) throw (uno::RuntimeException)
-+ {
-+ mpListHelper->Clear();
-+ }
-+
-+void SAL_CALL
-+ScVbaComboBox::setRowSource( const rtl::OUString& _rowsource ) throw (css::uno::RuntimeException)
-+{
-+ ScVbaControl::setRowSource( _rowsource );
-+ mpListHelper->setRowSource( _rowsource );
-+ }
-+
-+sal_Int32 SAL_CALL
-+ScVbaComboBox::getListCount() throw (uno::RuntimeException)
-+{
-+ return mpListHelper->getListCount();
-+}
-+
-+uno::Any SAL_CALL
-+ScVbaComboBox::List( const ::uno::Any& pvargIndex, const uno::Any& pvarColumn ) throw (uno::RuntimeException)
-+{
-+ return mpListHelper->List( pvargIndex, pvarColumn );
-+ }
-+
-+rtl::OUString&
-+ScVbaComboBox::getServiceImplName()
-+{
-+ static rtl::OUString sImplName( RTL_CONSTASCII_USTRINGPARAM("ScVbaComboBox") );
-+ return sImplName;
-+}
-+
-+uno::Sequence< rtl::OUString >
-+ScVbaComboBox::getServiceNames()
-+{
-+ static uno::Sequence< rtl::OUString > aServiceNames;
-+ if ( aServiceNames.getLength() == 0 )
-+ {
-+ aServiceNames.realloc( 1 );
-+ aServiceNames[ 0 ] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.msforms.ComboBox" ) );
-+ }
-+ return aServiceNames;
-+}
---- vbahelper/source/msforms/vbacombobox.hxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ vbahelper/source/msforms/vbacombobox.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,80 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile: vbacombobox.hxx,v $
-+ * $Revision: 1.4 $
-+ *
-+ * 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.
-+ *
-+ ************************************************************************/
-+#ifndef SC_VBA_COMBOBOX_HXX
-+#define SC_VBA_COMBOBOX_HXX
-+#include <cppuhelper/implbase2.hxx>
-+#include <com/sun/star/uno/XComponentContext.hpp>
-+#include <com/sun/star/beans/XPropertySet.hpp>
-+#include <com/sun/star/script/XDefaultProperty.hpp>
-+#include <ooo/vba/msforms/XComboBox.hpp>
-+#include <comphelper/proparrhlp.hxx>
-+#include <comphelper/propertycontainer.hxx>
-+#include <com/sun/star/beans/PropertyAttribute.hpp>
-+
-+#include "vbacontrol.hxx"
-+#include "vbalistcontrolhelper.hxx"
-+#include <vbahelper/vbahelper.hxx>
-+
-+typedef cppu::ImplInheritanceHelper2<ScVbaControl, ov::msforms::XComboBox, css::script::XDefaultProperty > ComboBoxImpl_BASE;
-+class ScVbaComboBox : public ComboBoxImpl_BASE
-+{
-+ std::auto_ptr< ListControlHelper > mpListHelper;
-+ rtl::OUString sSourceName;
-+ rtl::OUString msDftPropName;
-+ bool mbDialogType;
-+
-+public:
-+ ScVbaComboBox( const css::uno::Reference< ov::XHelperInterface >& xParent, const css::uno::Reference< css::uno::XComponentContext >& xContext, const css::uno::Reference< css::uno::XInterface >& xControl, const css::uno::Reference< css::frame::XModel >& xModel, ov::AbstractGeometryAttributes* pGeomHelper, bool bDialogType = false );
-+
-+ // Attributes
-+ virtual css::uno::Any SAL_CALL getListIndex() throw (css::uno::RuntimeException);
-+ virtual ::sal_Int32 SAL_CALL getListCount() throw (css::uno::RuntimeException);
-+ virtual void SAL_CALL setListIndex( const css::uno::Any& _value ) throw (css::uno::RuntimeException);
-+ virtual css::uno::Any SAL_CALL getValue() throw (css::uno::RuntimeException);
-+ virtual void SAL_CALL setValue( const css::uno::Any& _value ) throw (css::uno::RuntimeException);
-+ virtual ::rtl::OUString SAL_CALL getText() throw (css::uno::RuntimeException);
-+ virtual void SAL_CALL setText( const ::rtl::OUString& _text ) throw (css::uno::RuntimeException);
-+
-+ // Methods
-+ virtual void SAL_CALL AddItem( const css::uno::Any& pvargItem, const css::uno::Any& pvargIndex ) throw (css::uno::RuntimeException);
-+ virtual void SAL_CALL removeItem( const css::uno::Any& index ) throw (css::uno::RuntimeException);
-+ virtual void SAL_CALL Clear( ) throw (css::uno::RuntimeException);
-+ virtual css::uno::Any SAL_CALL List( const css::uno::Any& pvargIndex, const css::uno::Any& pvarColumn ) throw (css::uno::RuntimeException);
-+ // XControl
-+ virtual void SAL_CALL setRowSource( const rtl::OUString& _rowsource ) throw (css::uno::RuntimeException);
-+
-+ // XDefaultProperty
-+ ::rtl::OUString SAL_CALL getDefaultPropertyName( ) throw (css::uno::RuntimeException) { return ::rtl::OUString::createFromAscii("Value"); }
-+ //XHelperInterface
-+ virtual rtl::OUString& getServiceImplName();
-+ virtual css::uno::Sequence<rtl::OUString> getServiceNames();
-+};
-+
-+#endif //
---- vbahelper/source/msforms/vbacontrol.cxx
-+++ vbahelper/source/msforms/vbacontrol.cxx
-@@ -0,0 +1,520 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile: vbacontrol.cxx,v $
-+ * $Revision: 1.3 $
-+ *
-+ * 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 <com/sun/star/form/FormComponentType.hpp>
-+#include <com/sun/star/awt/XControlModel.hpp>
-+#include <com/sun/star/awt/XControl.hpp>
-+#include <com/sun/star/awt/XWindow2.hpp>
-+#include <com/sun/star/lang/XEventListener.hpp>
-+#include <com/sun/star/drawing/XShape.hpp>
-+#include <com/sun/star/drawing/XControlShape.hpp>
-+#include <com/sun/star/awt/XControl.hpp>
-+#include <com/sun/star/frame/XModel.hpp>
-+#include <com/sun/star/view/XControlAccess.hpp>
-+#include <com/sun/star/container/XChild.hpp>
-+#include <com/sun/star/form/binding/XBindableValue.hpp>
-+#include <com/sun/star/form/binding/XListEntrySink.hpp>
-+#include <com/sun/star/table/CellAddress.hpp>
-+#include <com/sun/star/table/CellRangeAddress.hpp>
-+#include <ooo/vba/XControlProvider.hpp>
-+#ifdef VBA_OOBUILD_HACK
-+#include <svtools/bindablecontrolhelper.hxx>
-+#endif
-+#include"vbacontrol.hxx"
-+#include"vbacombobox.hxx"
-+#include "vbabutton.hxx"
-+#include "vbalabel.hxx"
-+#include "vbatextbox.hxx"
-+#include "vbaradiobutton.hxx"
-+#include "vbalistbox.hxx"
-+#include "vbatogglebutton.hxx"
-+#include "vbacheckbox.hxx"
-+#include "vbaframe.hxx"
-+#include "vbascrollbar.hxx"
-+#include "vbaprogressbar.hxx"
-+#include "vbamultipage.hxx"
-+#include "vbaspinbutton.hxx"
-+#include "vbaimage.hxx"
-+#include <vbahelper/helperdecl.hxx>
-+
-+
-+using namespace com::sun::star;
-+using namespace ooo::vba;
-+
-+uno::Reference< css::awt::XWindowPeer >
-+ScVbaControl::getWindowPeer() throw (uno::RuntimeException)
-+{
-+ uno::Reference< drawing::XControlShape > xControlShape( m_xControl, uno::UNO_QUERY );
-+
-+ uno::Reference< awt::XControlModel > xControlModel;
-+ uno::Reference< css::awt::XWindowPeer > xWinPeer;
-+ if ( !xControlShape.is() )
-+ {
-+ // would seem to be a Userform control
-+ uno::Reference< awt::XControl > xControl( m_xControl, uno::UNO_QUERY_THROW );
-+ xWinPeer = xControl->getPeer();
-+ return xWinPeer;
-+ }
-+ // form control
-+ xControlModel.set( xControlShape->getControl(), uno::UNO_QUERY_THROW );
-+
-+ uno::Reference< view::XControlAccess > xControlAccess( m_xModel->getCurrentController(), uno::UNO_QUERY_THROW );
-+ try
-+ {
-+ uno::Reference< awt::XControl > xControl( xControlAccess->getControl( xControlModel ), uno::UNO_QUERY );
-+ xWinPeer = xControl->getPeer();
-+ }
-+ catch( uno::Exception )
-+ {
-+ throw uno::RuntimeException( rtl::OUString::createFromAscii( "The Control does not exsit" ),
-+ uno::Reference< uno::XInterface >() );
-+ }
-+ return xWinPeer;
-+}
-+
-+//ScVbaControlListener
-+class ScVbaControlListener: public cppu::WeakImplHelper1< lang::XEventListener >
-+{
-+private:
-+ ScVbaControl *pControl;
-+public:
-+ ScVbaControlListener( ScVbaControl *pTmpControl );
-+ virtual ~ScVbaControlListener();
-+ virtual void SAL_CALL disposing( const lang::EventObject& rEventObject ) throw( uno::RuntimeException );
-+};
-+
-+ScVbaControlListener::ScVbaControlListener( ScVbaControl *pTmpControl ): pControl( pTmpControl )
-+{
-+}
-+
-+ScVbaControlListener::~ScVbaControlListener()
-+{
-+}
-+
-+void SAL_CALL
-+ScVbaControlListener::disposing( const lang::EventObject& ) throw( uno::RuntimeException )
-+{
-+ if( pControl )
-+ {
-+ pControl->removeResouce();
-+ pControl = NULL;
-+ }
-+}
-+
-+//ScVbaControl
-+
-+ScVbaControl::ScVbaControl( const uno::Reference< XHelperInterface >& xParent, const uno::Reference< uno::XComponentContext >& xContext, const uno::Reference< ::uno::XInterface >& xControl, const css::uno::Reference< css::frame::XModel >& xModel, AbstractGeometryAttributes* pGeomHelper ) : ControlImpl_BASE( xParent, xContext ), m_xControl( xControl ), m_xModel( xModel )
-+{
-+ //add listener
-+ m_xEventListener.set( new ScVbaControlListener( this ) );
-+ setGeometryHelper( pGeomHelper );
-+ uno::Reference< lang::XComponent > xComponent( m_xControl, uno::UNO_QUERY_THROW );
-+ xComponent->addEventListener( m_xEventListener );
-+
-+ //init m_xProps
-+ uno::Reference< drawing::XControlShape > xControlShape( m_xControl, uno::UNO_QUERY ) ;
-+ uno::Reference< awt::XControl> xUserFormControl( m_xControl, uno::UNO_QUERY ) ;
-+ if ( xControlShape.is() ) // form control
-+ m_xProps.set( xControlShape->getControl(), uno::UNO_QUERY_THROW );
-+ else if ( xUserFormControl.is() ) // userform control
-+ m_xProps.set( xUserFormControl->getModel(), uno::UNO_QUERY_THROW );
-+}
-+
-+ScVbaControl::~ScVbaControl()
-+{
-+ if( m_xControl.is() )
-+{
-+ uno::Reference< lang::XComponent > xComponent( m_xControl, uno::UNO_QUERY_THROW );
-+ xComponent->removeEventListener( m_xEventListener );
-+}
-+}
-+
-+void
-+ScVbaControl::setGeometryHelper( AbstractGeometryAttributes* pHelper )
-+{
-+ mpGeometryHelper.reset( pHelper );
-+}
-+
-+void ScVbaControl::removeResouce() throw( uno::RuntimeException )
-+{
-+ uno::Reference< lang::XComponent > xComponent( m_xControl, uno::UNO_QUERY_THROW );
-+ xComponent->removeEventListener( m_xEventListener );
-+ m_xControl= NULL;
-+ m_xProps = NULL;
-+}
-+
-+//In design model has different behavior
-+sal_Bool SAL_CALL ScVbaControl::getEnabled() throw (uno::RuntimeException)
-+{
-+ uno::Any aValue = m_xProps->getPropertyValue
-+ (rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "Enabled" ) ) );
-+ sal_Bool bRet = false;
-+ aValue >>= bRet;
-+ return bRet;
-+}
-+
-+void SAL_CALL ScVbaControl::setEnabled( sal_Bool bVisible ) throw (uno::RuntimeException)
-+{
-+ uno::Any aValue( bVisible );
-+ m_xProps->setPropertyValue
-+ (rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "Enabled" ) ), aValue);
-+
-+}
-+
-+sal_Bool SAL_CALL ScVbaControl::getVisible() throw (uno::RuntimeException)
-+{
-+ uno::Reference< awt::XWindow2 > xWindow2( getWindowPeer(), uno::UNO_QUERY_THROW );
-+ return xWindow2->isVisible();
-+}
-+
-+void SAL_CALL ScVbaControl::setVisible( sal_Bool bVisible ) throw (uno::RuntimeException)
-+{
-+ uno::Reference< awt::XWindow2 > xWindow2( getWindowPeer(), uno::UNO_QUERY_THROW );
-+ xWindow2->setVisible( bVisible );
-+}
-+double SAL_CALL ScVbaControl::getHeight() throw (uno::RuntimeException)
-+{
-+ return mpGeometryHelper->getHeight();
-+}
-+void SAL_CALL ScVbaControl::setHeight( double _height ) throw (uno::RuntimeException)
-+{
-+ mpGeometryHelper->setHeight( _height );
-+}
-+
-+double SAL_CALL ScVbaControl::getWidth() throw (uno::RuntimeException)
-+{
-+ return mpGeometryHelper->getWidth();
-+}
-+void SAL_CALL ScVbaControl::setWidth( double _width ) throw (uno::RuntimeException)
-+{
-+ mpGeometryHelper->setWidth( _width );
-+}
-+
-+double SAL_CALL
-+ScVbaControl::getLeft() throw (uno::RuntimeException)
-+{
-+ return mpGeometryHelper->getLeft();
-+}
-+
-+void SAL_CALL
-+ScVbaControl::setLeft( double _left ) throw (uno::RuntimeException)
-+{
-+ mpGeometryHelper->setLeft( _left );
-+
-+}
-+
-+double SAL_CALL
-+ScVbaControl::getTop() throw (uno::RuntimeException)
-+{
-+ return mpGeometryHelper->getTop();
-+}
-+
-+void SAL_CALL
-+ScVbaControl::setTop( double _top ) throw (uno::RuntimeException)
-+{
-+ mpGeometryHelper->setTop( _top );
-+}
-+
-+uno::Reference< uno::XInterface > SAL_CALL
-+ScVbaControl::getObject() throw (uno::RuntimeException)
-+{
-+ uno::Reference< msforms::XControl > xRet( this );
-+ return xRet;
-+}
-+
-+void SAL_CALL ScVbaControl::SetFocus() throw (uno::RuntimeException)
-+{
-+ uno::Reference< awt::XWindow > xWin( m_xControl, uno::UNO_QUERY_THROW );
-+ xWin->setFocus();
-+}
-+
-+rtl::OUString SAL_CALL
-+ScVbaControl::getControlSource() throw (uno::RuntimeException)
-+{
-+// #FIXME I *hate* having these upstream differences
-+// but this is necessary until I manage to upstream other
-+// dependant parts
-+#ifdef VBA_OOBUILD_HACK
-+ rtl::OUString sControlSource;
-+ uno::Reference< form::binding::XBindableValue > xBindable( m_xProps, uno::UNO_QUERY );
-+ if ( xBindable.is() )
-+ {
-+ try
-+ {
-+ uno::Reference< lang::XMultiServiceFactory > xFac( m_xModel, uno::UNO_QUERY_THROW );
-+ uno::Reference< beans::XPropertySet > xConvertor( xFac->createInstance( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "com.sun.star.table.CellAddressConversion" ))), uno::UNO_QUERY );
-+ uno::Reference< beans::XPropertySet > xProps( xBindable->getValueBinding(), uno::UNO_QUERY_THROW );
-+ table::CellAddress aAddress;
-+ xProps->getPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("BoundCell") ) ) >>= aAddress;
-+ xConvertor->setPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("Address") ), uno::makeAny( aAddress ) );
-+ xConvertor->getPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("XL_A1_Representation") ) ) >>= sControlSource;
-+ }
-+ catch( uno::Exception& )
-+ {
-+ }
-+ }
-+ return sControlSource;
-+#else
-+ throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("getControlSource not supported") ), uno::Reference< uno::XInterface >()); // not supported
-+#endif
-+}
-+
-+void SAL_CALL
-+ScVbaControl::setControlSource( const rtl::OUString& _controlsource ) throw (uno::RuntimeException)
-+{
-+#ifdef VBA_OOBUILD_HACK
-+ rtl::OUString sEmpty;
-+ svt::BindableControlHelper::ApplyListSourceAndBindableData( m_xModel, m_xProps, _controlsource, sEmpty );
-+#else
-+ throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("setControlSource not supported ") ).concat( _controlsource ), uno::Reference< uno::XInterface >()); // not supported
-+#endif
-+}
-+
-+rtl::OUString SAL_CALL
-+ScVbaControl::getRowSource() throw (uno::RuntimeException)
-+{
-+#ifdef VBA_OOBUILD_HACK
-+ rtl::OUString sRowSource;
-+ uno::Reference< form::binding::XListEntrySink > xListSink( m_xProps, uno::UNO_QUERY );
-+ if ( xListSink.is() )
-+ {
-+ try
-+ {
-+ uno::Reference< lang::XMultiServiceFactory > xFac( m_xModel, uno::UNO_QUERY_THROW );
-+ uno::Reference< beans::XPropertySet > xConvertor( xFac->createInstance( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "com.sun.star.table.CellRangeAddressConversion" ))), uno::UNO_QUERY );
-+
-+ uno::Reference< beans::XPropertySet > xProps( xListSink->getListEntrySource(), uno::UNO_QUERY_THROW );
-+ table::CellRangeAddress aAddress;
-+ xProps->getPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("CellRange") ) ) >>= aAddress;
-+ xConvertor->setPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("Address")), uno::makeAny( aAddress ) );
-+ xConvertor->getPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("XL_A1_Representation") ) ) >>= sRowSource;
-+ }
-+ catch( uno::Exception& )
-+ {
-+ }
-+ }
-+ return sRowSource;
-+#else
-+ throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("getRowSource not supported") ), uno::Reference< uno::XInterface >()); // not supported
-+#endif
-+}
-+
-+void SAL_CALL
-+ScVbaControl::setRowSource( const rtl::OUString& _rowsource ) throw (uno::RuntimeException)
-+{
-+#ifdef VBA_OOBUILD_HACK
-+ rtl::OUString sEmpty;
-+ svt::BindableControlHelper::ApplyListSourceAndBindableData( m_xModel, m_xProps, sEmpty, _rowsource );
-+#else
-+ throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("setRowSource not supported ") ).concat( _rowsource ), uno::Reference< uno::XInterface >()); // not supported
-+#endif
-+}
-+
-+rtl::OUString SAL_CALL
-+ScVbaControl::getName() throw (uno::RuntimeException)
-+{
-+ rtl::OUString sName;
-+ m_xProps->getPropertyValue
-+ (rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "Name" ) ) ) >>= sName;
-+ return sName;
-+
-+}
-+
-+void SAL_CALL
-+ScVbaControl::setName( const rtl::OUString& _name ) throw (uno::RuntimeException)
-+{
-+ m_xProps->setPropertyValue
-+ (rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "Name" ) ), uno::makeAny( _name ) );
-+ }
-+//ScVbaControlFactory
-+
-+ScVbaControlFactory::ScVbaControlFactory( const uno::Reference< uno::XComponentContext >& xContext, const uno::Reference< uno::XInterface >& xControl, const uno::Reference< frame::XModel >& xModel ): m_xContext( xContext ), m_xControl( xControl ), m_xModel( xModel )
-+{
-+}
-+
-+ScVbaControl* ScVbaControlFactory::createControl() throw (uno::RuntimeException)
-+{
-+ return createControl( m_xModel );
-+}
-+ScVbaControl* ScVbaControlFactory::createControl( const uno::Reference< uno::XInterface >& xParent ) throw (uno::RuntimeException)
-+{
-+ uno::Reference< drawing::XControlShape > xControlShape( m_xControl, uno::UNO_QUERY );
-+ if ( xControlShape.is() ) // form controls
-+ return createControl( xControlShape, xParent );
-+ uno::Reference< awt::XControl > xControl( m_xControl, uno::UNO_QUERY );
-+ if ( !xControl.is() )
-+ throw uno::RuntimeException(); // really we should be more informative
-+ return createControl( xControl, xParent );
-+
-+}
-+
-+ScVbaControl* ScVbaControlFactory::createControl(const uno::Reference< drawing::XControlShape >& xControlShape, const uno::Reference< uno::XInterface >& /*xParent*/ ) throw (uno::RuntimeException)
-+{
-+ uno::Reference< beans::XPropertySet > xProps( xControlShape->getControl(), uno::UNO_QUERY_THROW );
-+ sal_Int32 nClassId = -1;
-+ const static rtl::OUString sClassId( RTL_CONSTASCII_USTRINGPARAM("ClassId") );
-+ xProps->getPropertyValue( sClassId ) >>= nClassId;
-+ uno::Reference< XHelperInterface > xVbaParent; // #FIXME - should be worksheet I guess
-+ switch( nClassId )
-+ {
-+ case form::FormComponentType::COMBOBOX:
-+ return new ScVbaComboBox( xVbaParent, m_xContext, xControlShape, m_xModel, new ConcreteXShapeGeometryAttributes( m_xContext, uno::Reference< drawing::XShape >( xControlShape, uno::UNO_QUERY_THROW ) ) );
-+ case form::FormComponentType::COMMANDBUTTON:
-+ return new ScVbaButton( xVbaParent, m_xContext, xControlShape, m_xModel, new ConcreteXShapeGeometryAttributes( m_xContext, uno::Reference< drawing::XShape >( xControlShape, uno::UNO_QUERY_THROW ) ) );
-+ case form::FormComponentType::FIXEDTEXT:
-+ return new ScVbaLabel( xVbaParent, m_xContext, xControlShape, m_xModel, new ConcreteXShapeGeometryAttributes( m_xContext, uno::Reference< drawing::XShape >( xControlShape, uno::UNO_QUERY_THROW ) ) );
-+ case form::FormComponentType::TEXTFIELD:
-+ return new ScVbaTextBox( xVbaParent, m_xContext, xControlShape, m_xModel, new ConcreteXShapeGeometryAttributes( m_xContext, uno::Reference< drawing::XShape >( xControlShape, uno::UNO_QUERY_THROW ) ) );
-+ case form::FormComponentType::RADIOBUTTON:
-+ return new ScVbaRadioButton( xVbaParent, m_xContext, xControlShape, m_xModel, new ConcreteXShapeGeometryAttributes( m_xContext, uno::Reference< drawing::XShape >( xControlShape, uno::UNO_QUERY_THROW ) ) );
-+ case form::FormComponentType::LISTBOX:
-+ return new ScVbaListBox( xVbaParent, m_xContext, xControlShape, m_xModel, new ConcreteXShapeGeometryAttributes( m_xContext, uno::Reference< drawing::XShape >( xControlShape, uno::UNO_QUERY_THROW ) ) );
-+ case form::FormComponentType::SPINBUTTON:
-+ return new ScVbaSpinButton( xVbaParent, m_xContext, xControlShape, m_xModel, new ConcreteXShapeGeometryAttributes( m_xContext, uno::Reference< drawing::XShape >( xControlShape, uno::UNO_QUERY_THROW ) ) );
-+ case form::FormComponentType::IMAGECONTROL:
-+ return new ScVbaImage( xVbaParent, m_xContext, xControlShape, m_xModel, new ConcreteXShapeGeometryAttributes( m_xContext, uno::Reference< drawing::XShape >( xControlShape, uno::UNO_QUERY_THROW ) ) );
-+ default:
-+ throw uno::RuntimeException( rtl::OUString::createFromAscii(
-+ "Donot support this Control Type." ), uno::Reference< uno::XInterface >() );
-+ }
-+}
-+
-+ScVbaControl* ScVbaControlFactory::createControl( const uno::Reference< awt::XControl >& xControl, const uno::Reference< uno::XInterface >& xParent ) throw (uno::RuntimeException)
-+{
-+ uno::Reference< beans::XPropertySet > xProps( xControl->getModel(), uno::UNO_QUERY_THROW );
-+ uno::Reference< lang::XServiceInfo > xServiceInfo( xProps, uno::UNO_QUERY_THROW );
-+ ScVbaControl* pControl = NULL;
-+ uno::Reference< XHelperInterface > xVbaParent; // #FIXME - should be worksheet I guess
-+ if ( xServiceInfo->supportsService( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("com.sun.star.awt.UnoControlCheckBoxModel") ) ) )
-+ pControl = new ScVbaCheckbox( xVbaParent, m_xContext, xControl, m_xModel, new UserFormGeometryHelper( m_xContext, xControl ) );
-+ else if ( xServiceInfo->supportsService( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("com.sun.star.awt.UnoControlRadioButtonModel") ) ) )
-+ pControl = new ScVbaRadioButton( xVbaParent, m_xContext, xControl, m_xModel, new UserFormGeometryHelper( m_xContext, xControl ) );
-+ else if ( xServiceInfo->supportsService( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("com.sun.star.awt.UnoControlEditModel") ) ) )
-+ pControl = new ScVbaTextBox( xVbaParent, m_xContext, xControl, m_xModel, new UserFormGeometryHelper( m_xContext, xControl ), true );
-+ else if ( xServiceInfo->supportsService( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("com.sun.star.awt.UnoControlButtonModel") ) ) )
-+ {
-+ sal_Bool bToggle = sal_False;
-+ xProps->getPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("Toggle") ) ) >>= bToggle;
-+ if ( bToggle )
-+ pControl = new ScVbaToggleButton( xVbaParent, m_xContext, xControl, m_xModel, new UserFormGeometryHelper( m_xContext, xControl ) );
-+ else
-+ pControl = new ScVbaButton( xVbaParent, m_xContext, xControl, m_xModel, new UserFormGeometryHelper( m_xContext, xControl ) );
-+ }
-+ else if ( xServiceInfo->supportsService( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("com.sun.star.awt.UnoControlComboBoxModel") ) ) )
-+ pControl = new ScVbaComboBox( xVbaParent, m_xContext, xControl, m_xModel, new UserFormGeometryHelper( m_xContext, xControl ), true );
-+ else if ( xServiceInfo->supportsService( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("com.sun.star.awt.UnoControlListBoxModel") ) ) )
-+ pControl = new ScVbaListBox( xVbaParent, m_xContext, xControl, m_xModel, new UserFormGeometryHelper( m_xContext, xControl ) );
-+ else if ( xServiceInfo->supportsService( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("com.sun.star.awt.UnoControlFixedTextModel") ) ) )
-+ pControl = new ScVbaLabel( xVbaParent, m_xContext, xControl, m_xModel, new UserFormGeometryHelper( m_xContext, xControl ) );
-+ else if ( xServiceInfo->supportsService( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("com.sun.star.awt.UnoControlImageControlModel") ) ) )
-+ pControl = new ScVbaImage( xVbaParent, m_xContext, xControl, m_xModel, new UserFormGeometryHelper( m_xContext, xControl ) );
-+ else if ( xServiceInfo->supportsService( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("com.sun.star.awt.UnoControlProgressBarModel") ) ) )
-+ pControl = new ScVbaProgressBar( xVbaParent, m_xContext, xControl, m_xModel, new UserFormGeometryHelper( m_xContext, xControl ) );
-+ else if ( xServiceInfo->supportsService( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("com.sun.star.awt.UnoControlGroupBoxModel") ) ) )
-+ pControl = new ScVbaFrame( xVbaParent, m_xContext, xControl, m_xModel, new UserFormGeometryHelper( m_xContext, xControl ) );
-+ else if ( xServiceInfo->supportsService( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("com.sun.star.awt.UnoControlScrollBarModel") ) ) )
-+ pControl = new ScVbaScrollBar( xVbaParent, m_xContext, xControl, m_xModel, new UserFormGeometryHelper( m_xContext, xControl ) );
-+ else if ( xServiceInfo->supportsService( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("com.sun.star.awt.UnoMultiPageModel") ) ) )
-+ pControl = new ScVbaMultiPage( xVbaParent, m_xContext, xControl, m_xModel, new UserFormGeometryHelper( m_xContext, xControl ), xParent );
-+ else if ( xServiceInfo->supportsService( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("com.sun.star.awt.UnoControlSpinButtonModel") ) ) )
-+ pControl = new ScVbaSpinButton( xVbaParent, m_xContext, xControl, m_xModel, new UserFormGeometryHelper( m_xContext, xControl ) );
-+ else
-+ throw uno::RuntimeException( rtl::OUString::createFromAscii("Unsupported control " ), uno::Reference< uno::XInterface >() );
-+ return pControl;
-+}
-+
-+rtl::OUString&
-+ScVbaControl::getServiceImplName()
-+{
-+ static rtl::OUString sImplName( RTL_CONSTASCII_USTRINGPARAM("ScVbaControl") );
-+ return sImplName;
-+}
-+
-+uno::Sequence< rtl::OUString >
-+ScVbaControl::getServiceNames()
-+{
-+ static uno::Sequence< rtl::OUString > aServiceNames;
-+ if ( aServiceNames.getLength() == 0 )
-+ {
-+ aServiceNames.realloc( 1 );
-+ aServiceNames[ 0 ] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.excel.Control" ) );
-+ }
-+ return aServiceNames;
-+}
-+
-+
-+
-+typedef cppu::WeakImplHelper1< XControlProvider > ControlProvider_BASE;
-+class ControlProviderImpl : public ControlProvider_BASE
-+{
-+ uno::Reference< uno::XComponentContext > m_xCtx;
-+public:
-+ ControlProviderImpl( const uno::Reference< uno::XComponentContext >& xCtx ) : m_xCtx( xCtx ) {}
-+ virtual uno::Reference< msforms::XControl > SAL_CALL createControl( const uno::Reference< drawing::XControlShape >& xControl, const uno::Reference< frame::XModel >& xDocOwner ) throw (uno::RuntimeException);
-+ virtual uno::Reference< msforms::XControl > SAL_CALL createUserformControl( const uno::Reference< awt::XControl >& xControl, const uno::Reference< awt::XControl >& xDialog, const uno::Reference< frame::XModel >& xDocOwner ) throw (uno::RuntimeException);
-+};
-+
-+uno::Reference< msforms::XControl > SAL_CALL
-+ControlProviderImpl::createControl( const uno::Reference< drawing::XControlShape >& xControlShape, const uno::Reference< frame::XModel >& xDocOwner ) throw (uno::RuntimeException)
-+{
-+ uno::Reference< msforms::XControl > xControlToReturn;
-+ if ( xControlShape.is() )
-+ {
-+ ScVbaControlFactory controlFactory( m_xCtx, xControlShape, xDocOwner );
-+ xControlToReturn.set( controlFactory.createControl( xDocOwner ) );
-+ }
-+ return xControlToReturn;
-+
-+}
-+uno::Reference< msforms::XControl > SAL_CALL
-+ControlProviderImpl::createUserformControl( const uno::Reference< awt::XControl >& xControl, const uno::Reference< awt::XControl >& xDialog, const uno::Reference< frame::XModel >& xDocOwner ) throw (uno::RuntimeException)
-+{
-+ uno::Reference< msforms::XControl > xControlToReturn;
-+ if ( xControl.is() && xDialog.is() )
-+ {
-+
-+ ScVbaControlFactory controlFactory( m_xCtx, xControl, xDocOwner );
-+ xControlToReturn.set( controlFactory.createControl( xDialog->getModel() ) );
-+ ScVbaControl* pControl = dynamic_cast< ScVbaControl* >( xControlToReturn.get() );
-+ pControl->setGeometryHelper( new UserFormGeometryHelper( m_xCtx, xControl ) );
-+ }
-+ return xControlToReturn;
-+}
-+
-+namespace controlprovider
-+{
-+namespace sdecl = comphelper::service_decl;
-+sdecl::class_<ControlProviderImpl, sdecl::with_args<false> > serviceImpl;
-+extern sdecl::ServiceDecl const serviceDecl(
-+ serviceImpl,
-+ "ControlProviderImpl",
-+ "ooo.vba.ControlProvider" );
-+}
-+
-+
---- vbahelper/source/msforms/vbacontrol.hxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ vbahelper/source/msforms/vbacontrol.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,112 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile: vbacontrol.hxx,v $
-+ * $Revision: 1.3 $
-+ *
-+ * 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.
-+ *
-+ ************************************************************************/
-+#ifndef SC_VBA_CONTROL_HXX
-+#define SC_VBA_CONTROL_HXX
-+
-+#include <cppuhelper/implbase1.hxx>
-+#include <com/sun/star/beans/XPropertySet.hpp>
-+#include <com/sun/star/uno/XComponentContext.hpp>
-+#include <com/sun/star/script/XDefaultProperty.hpp>
-+#include <com/sun/star/drawing/XControlShape.hpp>
-+#include <com/sun/star/awt/XControl.hpp>
-+#include <com/sun/star/awt/XWindowPeer.hpp>
-+#include <ooo/vba/msforms/XControl.hpp>
-+
-+#include <vbahelper/vbahelper.hxx>
-+#include <vbahelper/vbahelperinterface.hxx>
-+#include <memory>
-+
-+//typedef ::cppu::WeakImplHelper1< ov::msforms::XControl > ControlImpl_BASE;
-+typedef InheritedHelperInterfaceImpl1< ov::msforms::XControl > ControlImpl_BASE;
-+
-+class ScVbaControl : public ControlImpl_BASE
-+{
-+private:
-+ com::sun::star::uno::Reference< com::sun::star::lang::XEventListener > m_xEventListener;
-+protected:
-+ std::auto_ptr< ov::AbstractGeometryAttributes > mpGeometryHelper;
-+ css::uno::Reference< css::beans::XPropertySet > m_xProps;
-+ css::uno::Reference< css::uno::XInterface > m_xControl;
-+ css::uno::Reference< css::frame::XModel > m_xModel;
-+
-+ virtual css::uno::Reference< css::awt::XWindowPeer > getWindowPeer() throw (css::uno::RuntimeException);
-+public:
-+ ScVbaControl( const css::uno::Reference< ov::XHelperInterface >& xParent, const css::uno::Reference< css::uno::XComponentContext >& xContext,
-+ const css::uno::Reference< css::uno::XInterface >& xControl, const css::uno::Reference< css::frame::XModel >& xModel, ov::AbstractGeometryAttributes* pHelper );
-+ virtual ~ScVbaControl();
-+ // This class will own the helper, so make sure it is allocated from
-+ // the heap
-+ void setGeometryHelper( ov::AbstractGeometryAttributes* pHelper );
-+ // XControl
-+ virtual sal_Bool SAL_CALL getEnabled() throw (css::uno::RuntimeException);
-+ virtual void SAL_CALL setEnabled( sal_Bool _enabled ) throw (css::uno::RuntimeException);
-+ virtual sal_Bool SAL_CALL getVisible() throw (css::uno::RuntimeException);
-+ virtual void SAL_CALL setVisible( sal_Bool _visible ) throw (css::uno::RuntimeException);
-+ virtual double SAL_CALL getHeight() throw (css::uno::RuntimeException);
-+ virtual void SAL_CALL setHeight( double _height ) throw (css::uno::RuntimeException);
-+ virtual double SAL_CALL getWidth() throw (css::uno::RuntimeException);
-+ virtual void SAL_CALL setWidth( double _width ) throw (css::uno::RuntimeException);
-+ virtual double SAL_CALL getLeft() throw (css::uno::RuntimeException);
-+ virtual void SAL_CALL setLeft( double _left ) throw (css::uno::RuntimeException);
-+ virtual double SAL_CALL getTop() throw (css::uno::RuntimeException);
-+ virtual void SAL_CALL setTop( double _top ) throw (css::uno::RuntimeException);
-+ virtual void SAL_CALL SetFocus( ) throw (css::uno::RuntimeException);
-+
-+ virtual css::uno::Reference< css::uno::XInterface > SAL_CALL getObject() throw (css::uno::RuntimeException);
-+ virtual rtl::OUString SAL_CALL getControlSource() throw (css::uno::RuntimeException);
-+ virtual void SAL_CALL setControlSource( const rtl::OUString& _controlsource ) throw (css::uno::RuntimeException);
-+ virtual rtl::OUString SAL_CALL getRowSource() throw (css::uno::RuntimeException);
-+ virtual void SAL_CALL setRowSource( const rtl::OUString& _rowsource ) throw (css::uno::RuntimeException);
-+ virtual rtl::OUString SAL_CALL getName() throw (css::uno::RuntimeException);
-+ virtual void SAL_CALL setName( const rtl::OUString& _name ) throw (css::uno::RuntimeException);
-+ //remove resouce because ooo.vba.excel.XControl is a wrapper of com.sun.star.drawing.XControlShape
-+ virtual void removeResouce() throw( css::uno::RuntimeException );
-+ //XHelperInterface
-+ virtual rtl::OUString& getServiceImplName();
-+ virtual css::uno::Sequence<rtl::OUString> getServiceNames();
-+};
-+
-+
-+class ScVbaControlFactory
-+{
-+public:
-+ ScVbaControlFactory( const css::uno::Reference< css::uno::XComponentContext >& xContext,
-+ const css::uno::Reference< css::uno::XInterface >& xControl, const css::uno::Reference< css::frame::XModel >& xModel );
-+ ScVbaControl* createControl() throw ( css::uno::RuntimeException );
-+ ScVbaControl* createControl( const css::uno::Reference< css::uno::XInterface >& xParent ) throw ( css::uno::RuntimeException );
-+private:
-+ ScVbaControl* createControl( const css::uno::Reference< css::awt::XControl >&, const css::uno::Reference< css::uno::XInterface >& ) throw ( css::uno::RuntimeException );
-+ ScVbaControl* createControl( const css::uno::Reference< css::drawing::XControlShape >&, const css::uno::Reference< css::uno::XInterface >& ) throw ( css::uno::RuntimeException );
-+ css::uno::Reference< css::uno::XComponentContext > m_xContext;
-+ css::uno::Reference< css::uno::XInterface > m_xControl;
-+ css::uno::Reference< css::frame::XModel > m_xModel;
-+};
-+
-+#endif//SC_VBA_CONTROL_HXX
---- vbahelper/source/msforms/vbacontrols.cxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ vbahelper/source/msforms/vbacontrols.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,232 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile$
-+ * $Revision$
-+ *
-+ * 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 "vbacontrols.hxx"
-+#include <cppuhelper/implbase2.hxx>
-+#include <com/sun/star/awt/XControlContainer.hpp>
-+#include <ooo/vba//XControlProvider.hpp>
-+#include <hash_map>
-+
-+using namespace com::sun::star;
-+using namespace ooo::vba;
-+
-+
-+typedef ::cppu::WeakImplHelper2< container::XNameAccess, container::XIndexAccess > ArrayWrapImpl;
-+
-+typedef std::hash_map< rtl::OUString, sal_Int32, ::rtl::OUStringHash,
-+ ::std::equal_to< ::rtl::OUString > > ControlIndexMap;
-+typedef std::vector< uno::Reference< awt::XControl > > ControlVec;
-+
-+class ControlArrayWrapper : public ArrayWrapImpl
-+{
-+ uno::Reference< awt::XControlContainer > mxDialog;
-+ uno::Sequence< ::rtl::OUString > msNames;
-+ ControlVec mControls;
-+ ControlIndexMap mIndices;
-+
-+ rtl::OUString getControlName( const uno::Reference< awt::XControl >& xCtrl )
-+ {
-+ uno::Reference< beans::XPropertySet > xProp( xCtrl->getModel(), uno::UNO_QUERY );
-+ rtl::OUString sName;
-+ xProp->getPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "Name" ) ) ) >>= sName;
-+ return sName;
-+ }
-+
-+public:
-+
-+ ControlArrayWrapper( const uno::Reference< awt::XControl >& xDialog )
-+ {
-+ mxDialog.set( xDialog, uno::UNO_QUERY_THROW );
-+ uno::Sequence< uno::Reference< awt::XControl > > sXControls = mxDialog->getControls();
-+
-+ msNames.realloc( sXControls.getLength() );
-+ for ( sal_Int32 i = 0; i < sXControls.getLength(); ++i )
-+ {
-+ uno::Reference< awt::XControl > xCtrl = sXControls[ i ];
-+ msNames[ i ] = getControlName( xCtrl );
-+ mControls.push_back( xCtrl );
-+ mIndices[ msNames[ i ] ] = i;
-+ }
-+ }
-+
-+ // XElementAccess
-+ virtual uno::Type SAL_CALL getElementType( ) throw (uno::RuntimeException)
-+ {
-+ return awt::XControl::static_type(0);
-+ }
-+
-+ virtual ::sal_Bool SAL_CALL hasElements( ) throw (uno::RuntimeException)
-+ {
-+ return ( mControls.size() > 0 );
-+ }
-+
-+ // XNameAcess
-+ virtual uno::Any SAL_CALL getByName( const ::rtl::OUString& aName ) throw (container::NoSuchElementException, lang::WrappedTargetException, uno::RuntimeException)
-+ {
-+ if ( !hasByName( aName ) )
-+ throw container::NoSuchElementException();
-+ return getByIndex( mIndices[ aName ] );
-+ }
-+
-+ virtual uno::Sequence< ::rtl::OUString > SAL_CALL getElementNames( ) throw (uno::RuntimeException)
-+ {
-+ return msNames;
-+ }
-+
-+ virtual ::sal_Bool SAL_CALL hasByName( const ::rtl::OUString& aName ) throw (css::uno::RuntimeException)
-+ {
-+ ControlIndexMap::iterator it = mIndices.find( aName );
-+ return it != mIndices.end();
-+ }
-+
-+ // XElementAccess
-+ virtual ::sal_Int32 SAL_CALL getCount( ) throw (css::uno::RuntimeException)
-+ {
-+ return mControls.size();
-+ }
-+
-+ virtual uno::Any SAL_CALL getByIndex( ::sal_Int32 Index ) throw (lang::IndexOutOfBoundsException, lang::WrappedTargetException, uno::RuntimeException )
-+ {
-+ if ( Index < 0 || Index >= static_cast< sal_Int32 >( mControls.size() ) )
-+ throw lang::IndexOutOfBoundsException();
-+ return uno::makeAny( mControls[ Index ] );
-+ }
-+};
-+
-+
-+class ControlsEnumWrapper : public EnumerationHelper_BASE
-+{
-+ uno::Reference<XHelperInterface > m_xParent;
-+ uno::Reference<uno::XComponentContext > m_xContext;
-+ uno::Reference<container::XIndexAccess > m_xIndexAccess;
-+ uno::Reference<awt::XControl > m_xDlg;
-+ sal_Int32 nIndex;
-+
-+public:
-+
-+ ControlsEnumWrapper( const uno::Reference< XHelperInterface >& xParent, const uno::Reference< uno::XComponentContext >& xContext, const uno::Reference< container::XIndexAccess >& xIndexAccess, const uno::Reference< awt::XControl >& xDlg ) : m_xParent( xParent ), m_xContext( xContext), m_xIndexAccess( xIndexAccess ), m_xDlg( xDlg ), nIndex( 0 ) {}
-+
-+ virtual ::sal_Bool SAL_CALL hasMoreElements( ) throw (uno::RuntimeException)
-+ {
-+ return ( nIndex < m_xIndexAccess->getCount() );
-+ }
-+
-+ virtual uno::Any SAL_CALL nextElement( ) throw (container::NoSuchElementException, lang::WrappedTargetException, uno::RuntimeException)
-+ {
-+ if ( nIndex < m_xIndexAccess->getCount() )
-+ {
-+ uno::Reference< frame::XModel > xModel;
-+ uno::Reference< awt::XControl > xControl;
-+ m_xIndexAccess->getByIndex( nIndex++ ) >>= xControl;
-+
-+ uno::Reference<lang::XMultiComponentFactory > xServiceManager( m_xContext->getServiceManager(), uno::UNO_QUERY_THROW );
-+ uno::Reference< XControlProvider > xControlProvider( xServiceManager->createInstanceWithContext( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "ooo.vba.ControlProvider" ) ), m_xContext ), uno::UNO_QUERY_THROW );
-+
-+ uno::Reference< msforms::XControl > xVBAControl( xControlProvider->createUserformControl( xControl, m_xDlg, xModel ) );
-+ return uno::makeAny( xVBAControl );
-+ }
-+ throw container::NoSuchElementException();
-+ }
-+
-+};
-+
-+
-+uno::Reference<container::XIndexAccess >
-+lcl_controlsWrapper( const uno::Reference< awt::XControl >& xDlg )
-+{
-+ return new ControlArrayWrapper( xDlg );
-+}
-+
-+ScVbaControls::ScVbaControls( const uno::Reference< XHelperInterface >& xParent, const uno::Reference< uno::XComponentContext >& xContext,
-+ const css::uno::Reference< awt::XControl >& xDialog )
-+ : ControlsImpl_BASE( xParent, xContext, lcl_controlsWrapper( xDialog ) )
-+{
-+ mxDialog.set( xDialog, uno::UNO_QUERY_THROW );
-+}
-+
-+uno::Reference< container::XEnumeration >
-+ScVbaControls::createEnumeration() throw (uno::RuntimeException)
-+{
-+ uno::Reference< container::XEnumeration > xEnum( new ControlsEnumWrapper( mxParent, mxContext, m_xIndexAccess, mxDialog ) );
-+ if ( !xEnum.is() )
-+ throw uno::RuntimeException();
-+ return xEnum;
-+}
-+
-+uno::Any
-+ScVbaControls::createCollectionObject( const css::uno::Any& aSource )
-+{
-+ // Create control from awt::XControl
-+ uno::Reference< awt::XControl > xControl;
-+ aSource >>= xControl;
-+ uno::Reference< frame::XModel > xModel;
-+ uno::Reference<lang::XMultiComponentFactory > xServiceManager( mxContext->getServiceManager(), uno::UNO_QUERY_THROW );
-+ uno::Reference< XControlProvider > xControlProvider( xServiceManager->createInstanceWithContext( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "ooo.vba.ControlProvider" ) ), mxContext ), uno::UNO_QUERY_THROW );
-+
-+ uno::Reference< msforms::XControl > xVBAControl( xControlProvider->createUserformControl( xControl, mxDialog, xModel ) );
-+
-+ return uno::makeAny( xVBAControl );
-+}
-+
-+void SAL_CALL
-+ScVbaControls::Move( double cx, double cy ) throw (uno::RuntimeException)
-+{
-+ uno::Reference< container::XEnumeration > xEnum( createEnumeration() );
-+ while ( xEnum->hasMoreElements() )
-+ {
-+ uno::Reference< msforms::XControl > xControl( xEnum->nextElement(), uno::UNO_QUERY_THROW );
-+ xControl->setLeft( xControl->getLeft() + cx );
-+ xControl->setTop( xControl->getTop() + cy );
-+ }
-+}
-+
-+uno::Type
-+ScVbaControls::getElementType() throw (uno::RuntimeException)
-+{
-+ return ooo::vba::msforms::XControl::static_type(0);
-+}
-+rtl::OUString&
-+ScVbaControls::getServiceImplName()
-+{
-+ static rtl::OUString sImplName( RTL_CONSTASCII_USTRINGPARAM("ScVbaControls") );
-+ return sImplName;
-+}
-+
-+uno::Sequence< rtl::OUString >
-+ScVbaControls::getServiceNames()
-+{
-+ static uno::Sequence< rtl::OUString > aServiceNames;
-+ if ( aServiceNames.getLength() == 0 )
-+ {
-+ aServiceNames.realloc( 1 );
-+ aServiceNames[ 0 ] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.excel.Controls" ) );
-+ }
-+ return aServiceNames;
-+}
---- vbahelper/source/msforms/vbacontrols.hxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ vbahelper/source/msforms/vbacontrols.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,62 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile$
-+ * $Revision$
-+ *
-+ * 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.
-+ *
-+ ************************************************************************/
-+#ifndef SC_VBA_CONTROLS_HXX
-+#define SC_VBA_CONTROLS_HXX
-+
-+#include <cppuhelper/implbase1.hxx>
-+#include <ooo/vba/msforms/XControls.hpp>
-+#include <com/sun/star/awt/XControl.hpp>
-+
-+#include <vbahelper/vbacollectionimpl.hxx>
-+#include <vbahelper/vbahelper.hxx>
-+
-+typedef CollTestImplHelper< ov::msforms::XControls > ControlsImpl_BASE;
-+
-+class ScVbaControls : public ControlsImpl_BASE
-+{
-+ css::uno::Reference< css::awt::XControl > mxDialog;
-+protected:
-+ virtual rtl::OUString& getServiceImplName();
-+ virtual css::uno::Sequence<rtl::OUString> getServiceNames();
-+public:
-+ ScVbaControls( const css::uno::Reference< ov::XHelperInterface >& xParent, const css::uno::Reference< css::uno::XComponentContext >& xContext,
-+ const css::uno::Reference< css::awt::XControl >& xDialog );
-+ // XControls
-+ virtual void SAL_CALL Move( double cx, double cy ) throw (css::uno::RuntimeException);
-+ // XEnumerationAccess
-+ virtual css::uno::Type SAL_CALL getElementType() throw (css::uno::RuntimeException);
-+ virtual css::uno::Reference< css::container::XEnumeration > SAL_CALL createEnumeration() throw (css::uno::RuntimeException);
-+
-+ // ScVbaCollectionBaseImpl
-+ virtual css::uno::Any createCollectionObject( const css::uno::Any& aSource );
-+
-+};
-+#endif //SC_VBA_OLEOBJECTS_HXX
-+
---- vbahelper/source/msforms/vbaframe.cxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ vbahelper/source/msforms/vbaframe.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,93 @@
-+/*************************************************************************
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile$
-+ *
-+ * $Revision$
-+ *
-+ * last change: $Author$ $Date$
-+ *
-+ * The Contents of this file are made available subject to
-+ * the terms of GNU Lesser General Public License Version 2.1.
-+ *
-+ *
-+ * GNU Lesser General Public License Version 2.1
-+ * =============================================
-+ * Copyright 2005 by Sun Microsystems, Inc.
-+ * 901 San Antonio Road, Palo Alto, CA 94303, USA
-+ *
-+ * This library is free software; you can redistribute it and/or
-+ * modify it under the terms of the GNU Lesser General Public
-+ * License version 2.1, as published by the Free Software Foundation.
-+ *
-+ * This library 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 for more details.
-+ *
-+ * You should have received a copy of the GNU Lesser General Public
-+ * License along with this library; if not, write to the Free Software
-+ * Foundation, Inc., 59 Temple Place, Suite 330, Boston,
-+ * MA 02111-1307 USA
-+ *
-+ ************************************************************************/
-+#include "vbaframe.hxx"
-+#include <vector>
-+
-+using namespace com::sun::star;
-+using namespace ooo::vba;
-+
-+
-+const static rtl::OUString LABEL( RTL_CONSTASCII_USTRINGPARAM("Label") );
-+ScVbaFrame::ScVbaFrame( const uno::Reference< XHelperInterface >& xParent, const uno::Reference< uno::XComponentContext >& xContext, const uno::Reference< uno::XInterface >& xControl, const uno::Reference< frame::XModel >& xModel, ov::AbstractGeometryAttributes* pGeomHelper ) : FrameImpl_BASE( xParent, xContext, xControl, xModel, pGeomHelper )
-+{
-+}
-+
-+// Attributes
-+rtl::OUString SAL_CALL
-+ScVbaFrame::getCaption() throw (css::uno::RuntimeException)
-+{
-+ rtl::OUString Label;
-+ m_xProps->getPropertyValue( LABEL ) >>= Label;
-+ return Label;
-+}
-+
-+void SAL_CALL
-+ScVbaFrame::setCaption( const rtl::OUString& _caption ) throw (::com::sun::star::uno::RuntimeException)
-+{
-+ m_xProps->setPropertyValue( LABEL, uno::makeAny( _caption ) );
-+}
-+
-+uno::Any SAL_CALL
-+ScVbaFrame::getValue() throw (css::uno::RuntimeException)
-+{
-+ return uno::makeAny( getCaption() );
-+}
-+
-+void SAL_CALL
-+ScVbaFrame::setValue( const uno::Any& _value ) throw (::com::sun::star::uno::RuntimeException)
-+{
-+ rtl::OUString sCaption;
-+ _value >>= sCaption;
-+ setCaption( sCaption );
-+}
-+
-+rtl::OUString&
-+ScVbaFrame::getServiceImplName()
-+{
-+ static rtl::OUString sImplName( RTL_CONSTASCII_USTRINGPARAM("ScVbaFrame") );
-+ return sImplName;
-+}
-+
-+uno::Sequence< rtl::OUString >
-+ScVbaFrame::getServiceNames()
-+{
-+ static uno::Sequence< rtl::OUString > aServiceNames;
-+ if ( aServiceNames.getLength() == 0 )
-+ {
-+ aServiceNames.realloc( 1 );
-+ aServiceNames[ 0 ] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.msforms.Frame" ) );
-+ }
-+ return aServiceNames;
-+}
---- vbahelper/source/msforms/vbaframe.hxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ vbahelper/source/msforms/vbaframe.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,58 @@
-+/*************************************************************************
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile$
-+ *
-+ * $Revision$
-+ *
-+ * last change: $Author$ $Date$
-+ *
-+ * The Contents of this file are made available subject to
-+ * the terms of GNU Lesser General Public License Version 2.1.
-+ *
-+ *
-+ * GNU Lesser General Public License Version 2.1
-+ * =============================================
-+ * Copyright 2005 by Sun Microsystems, Inc.
-+ * 901 San Antonio Road, Palo Alto, CA 94303, USA
-+ *
-+ * This library is free software; you can redistribute it and/or
-+ * modify it under the terms of the GNU Lesser General Public
-+ * License version 2.1, as published by the Free Software Foundation.
-+ *
-+ * This library 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 for more details.
-+ *
-+ * You should have received a copy of the GNU Lesser General Public
-+ * License along with this library; if not, write to the Free Software
-+ * Foundation, Inc., 59 Temple Place, Suite 330, Boston,
-+ * MA 02111-1307 USA
-+ *
-+ ************************************************************************/
-+#ifndef SC_VBA_FRAME_HXX
-+#define SC_VBA_FRAME_HXX
-+#include <cppuhelper/implbase1.hxx>
-+#include <ooo/vba/msforms/XLabel.hpp>
-+
-+#include "vbacontrol.hxx"
-+#include <vbahelper/vbahelper.hxx>
-+
-+typedef cppu::ImplInheritanceHelper1< ScVbaControl, ov::msforms::XLabel > FrameImpl_BASE;
-+
-+class ScVbaFrame : public FrameImpl_BASE
-+{
-+public:
-+ ScVbaFrame( const css::uno::Reference< ov::XHelperInterface >& xParent, const css::uno::Reference< css::uno::XComponentContext >& xContext, const css::uno::Reference< css::uno::XInterface >& xControl, const css::uno::Reference< css::frame::XModel >& xModel, ov::AbstractGeometryAttributes* pGeomHelper );
-+ // Attributes
-+ virtual css::uno::Any SAL_CALL getValue() throw (css::uno::RuntimeException);
-+ virtual void SAL_CALL setValue( const css::uno::Any& _value ) throw (css::uno::RuntimeException);
-+ virtual rtl::OUString SAL_CALL getCaption() throw (css::uno::RuntimeException);
-+ virtual void SAL_CALL setCaption( const rtl::OUString& _caption ) throw (css::uno::RuntimeException);
-+ //XHelperInterface
-+ virtual rtl::OUString& getServiceImplName();
-+ virtual css::uno::Sequence<rtl::OUString> getServiceNames();
-+};
-+#endif //SC_VBA_LABEL_HXX
---- vbahelper/source/msforms/vbaimage.cxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ vbahelper/source/msforms/vbaimage.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,59 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile$
-+ * $Revision$
-+ *
-+ * 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 "vbaimage.hxx"
-+#include <vector>
-+
-+using namespace com::sun::star;
-+using namespace ooo::vba;
-+
-+
-+const static rtl::OUString LABEL( RTL_CONSTASCII_USTRINGPARAM("Label") );
-+ScVbaImage::ScVbaImage( const uno::Reference< XHelperInterface >& xParent, const uno::Reference< uno::XComponentContext >& xContext, const uno::Reference< uno::XInterface >& xControl, const uno::Reference< frame::XModel >& xModel, AbstractGeometryAttributes* pGeomHelper ) : ImageImpl_BASE( xParent, xContext, xControl, xModel, pGeomHelper )
-+{
-+}
-+
-+rtl::OUString&
-+ScVbaImage::getServiceImplName()
-+{
-+ static rtl::OUString sImplName( RTL_CONSTASCII_USTRINGPARAM("ScVbaImage") );
-+ return sImplName;
-+}
-+
-+uno::Sequence< rtl::OUString >
-+ScVbaImage::getServiceNames()
-+{
-+ static uno::Sequence< rtl::OUString > aServiceNames;
-+ if ( aServiceNames.getLength() == 0 )
-+ {
-+ aServiceNames.realloc( 1 );
-+ aServiceNames[ 0 ] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.msforms.Image" ) );
-+ }
-+ return aServiceNames;
-+}
---- vbahelper/source/msforms/vbaimage.hxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ vbahelper/source/msforms/vbaimage.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,48 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile$
-+ * $Revision$
-+ *
-+ * 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.
-+ *
-+ ************************************************************************/
-+#ifndef SC_VBA_IMAGE_HXX
-+#define SC_VBA_IMAGE_HXX
-+#include <cppuhelper/implbase1.hxx>
-+#include <ooo/vba/msforms/XImage.hpp>
-+
-+#include "vbacontrol.hxx"
-+#include <vbahelper/vbahelper.hxx>
-+
-+typedef cppu::ImplInheritanceHelper1< ScVbaControl, ov::msforms::XImage > ImageImpl_BASE;
-+
-+class ScVbaImage : public ImageImpl_BASE
-+{
-+public:
-+ ScVbaImage( const css::uno::Reference< ov::XHelperInterface >& xParent, const css::uno::Reference< css::uno::XComponentContext >& xContext, const css::uno::Reference< css::uno::XInterface >& xControl, const css::uno::Reference< css::frame::XModel >& xModel, ov::AbstractGeometryAttributes* pGeomHelper );
-+ //XHelperInterface
-+ virtual rtl::OUString& getServiceImplName();
-+ virtual css::uno::Sequence<rtl::OUString> getServiceNames();
-+};
-+#endif //SC_VBA_IMAGE_HXX
---- vbahelper/source/msforms/vbalabel.cxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ vbahelper/source/msforms/vbalabel.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,88 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile: vbalabel.cxx,v $
-+ * $Revision: 1.3 $
-+ *
-+ * 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 "vbalabel.hxx"
-+#include <vector>
-+
-+using namespace com::sun::star;
-+using namespace ooo::vba;
-+
-+
-+const static rtl::OUString LABEL( RTL_CONSTASCII_USTRINGPARAM("Label") );
-+ScVbaLabel::ScVbaLabel( const css::uno::Reference< XHelperInterface >& xParent, const uno::Reference< uno::XComponentContext >& xContext, const uno::Reference< uno::XInterface >& xControl, const uno::Reference< frame::XModel >& xModel, ov::AbstractGeometryAttributes* pGeomHelper ) : LabelImpl_BASE( xParent, xContext, xControl, xModel, pGeomHelper )
-+{
-+}
-+
-+// Attributes
-+rtl::OUString SAL_CALL
-+ScVbaLabel::getCaption() throw (css::uno::RuntimeException)
-+{
-+ rtl::OUString Label;
-+ m_xProps->getPropertyValue( LABEL ) >>= Label;
-+ return Label;
-+}
-+
-+void SAL_CALL
-+ScVbaLabel::setCaption( const rtl::OUString& _caption ) throw (::com::sun::star::uno::RuntimeException)
-+{
-+ m_xProps->setPropertyValue( LABEL, uno::makeAny( _caption ) );
-+}
-+uno::Any SAL_CALL
-+ScVbaLabel::getValue() throw (css::uno::RuntimeException)
-+{
-+ return uno::makeAny( getCaption() );
-+}
-+
-+void SAL_CALL
-+ScVbaLabel::setValue( const uno::Any& _value ) throw (::com::sun::star::uno::RuntimeException)
-+{
-+ rtl::OUString sCaption;
-+ _value >>= sCaption;
-+ setCaption( sCaption );
-+}
-+
-+
-+rtl::OUString&
-+ScVbaLabel::getServiceImplName()
-+{
-+ static rtl::OUString sImplName( RTL_CONSTASCII_USTRINGPARAM("ScVbaLabel") );
-+ return sImplName;
-+}
-+
-+uno::Sequence< rtl::OUString >
-+ScVbaLabel::getServiceNames()
-+{
-+ static uno::Sequence< rtl::OUString > aServiceNames;
-+ if ( aServiceNames.getLength() == 0 )
-+ {
-+ aServiceNames.realloc( 1 );
-+ aServiceNames[ 0 ] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.msforms.Label" ) );
-+ }
-+ return aServiceNames;
-+}
---- vbahelper/source/msforms/vbalabel.hxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ vbahelper/source/msforms/vbalabel.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,56 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile: vbalabel.hxx,v $
-+ * $Revision: 1.3 $
-+ *
-+ * 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.
-+ *
-+ ************************************************************************/
-+#ifndef SC_VBA_LABEL_HXX
-+#define SC_VBA_LABEL_HXX
-+#include <cppuhelper/implbase1.hxx>
-+#include <ooo/vba/msforms/XLabel.hpp>
-+
-+#include "vbacontrol.hxx"
-+#include <vbahelper/vbahelper.hxx>
-+#include <cppuhelper/implbase2.hxx>
-+
-+typedef cppu::ImplInheritanceHelper2< ScVbaControl, ov::msforms::XLabel, css::script::XDefaultProperty > LabelImpl_BASE;
-+
-+class ScVbaLabel : public LabelImpl_BASE
-+{
-+public:
-+ ScVbaLabel( const css::uno::Reference< ov::XHelperInterface >& xParent, const css::uno::Reference< css::uno::XComponentContext >& xContext, const css::uno::Reference< css::uno::XInterface >& xControl, const css::uno::Reference< css::frame::XModel >& xModel, ov::AbstractGeometryAttributes* pGeomHelper );
-+ // Attributes
-+ virtual css::uno::Any SAL_CALL getValue() throw (css::uno::RuntimeException);
-+ virtual void SAL_CALL setValue( const css::uno::Any& _value ) throw (css::uno::RuntimeException);
-+ virtual rtl::OUString SAL_CALL getCaption() throw (css::uno::RuntimeException);
-+ virtual void SAL_CALL setCaption( const rtl::OUString& _caption ) throw (css::uno::RuntimeException);
-+ //XHelperInterface
-+ virtual rtl::OUString& getServiceImplName();
-+ virtual css::uno::Sequence<rtl::OUString> getServiceNames();
-+ // XDefaultProperty
-+ rtl::OUString SAL_CALL getDefaultPropertyName( ) throw (css::uno::RuntimeException) { return ::rtl::OUString::createFromAscii("Value"); }
-+};
-+#endif //SC_VBA_LABEL_HXX
---- vbahelper/source/msforms/vbalistbox.cxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ vbahelper/source/msforms/vbalistbox.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,288 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile: vbalistbox.cxx,v $
-+ * $Revision: 1.4 $
-+ *
-+ * 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 <com/sun/star/form/validation/XValidatableFormComponent.hpp>
-+
-+#include "vbalistbox.hxx"
-+#include <vector>
-+#include <comphelper/anytostring.hxx>
-+#include <com/sun/star/script/ArrayWrapper.hpp>
-+
-+using namespace com::sun::star;
-+using namespace ooo::vba;
-+
-+const static rtl::OUString TEXT( RTL_CONSTASCII_USTRINGPARAM("Text") );
-+const static rtl::OUString SELECTEDITEMS( RTL_CONSTASCII_USTRINGPARAM("SelectedItems") );
-+const static rtl::OUString ITEMS( RTL_CONSTASCII_USTRINGPARAM("StringItemList") );
-+
-+
-+ScVbaListBox::ScVbaListBox( const uno::Reference< XHelperInterface >& xParent, const uno::Reference< uno::XComponentContext >& xContext, const uno::Reference< css::uno::XInterface >& xControl, const uno::Reference< frame::XModel >& xModel, AbstractGeometryAttributes* pGeomHelper ) : ListBoxImpl_BASE( xParent, xContext, xControl, xModel, pGeomHelper )
-+{
-+ mpListHelper.reset( new ListControlHelper( m_xProps ) );
-+}
-+
-+// Attributes
-+void SAL_CALL
-+ScVbaListBox::setListIndex( const uno::Any& _value ) throw (uno::RuntimeException)
-+{
-+ sal_Int32 nIndex = 0;
-+ _value >>= nIndex;
-+ Selected( nIndex );
-+}
-+
-+uno::Any SAL_CALL
-+ScVbaListBox::getListIndex() throw (uno::RuntimeException)
-+{
-+ uno::Sequence< sal_Int16 > sSelection;
-+ m_xProps->getPropertyValue( SELECTEDITEMS ) >>= sSelection;
-+ if ( sSelection.getLength() == 0 )
-+ return uno::Any( sal_Int32( -1 ) );
-+ return uno::Any( sSelection[ 0 ] );
-+}
-+
-+uno::Any SAL_CALL
-+ScVbaListBox::getValue() throw (uno::RuntimeException)
-+{
-+ uno::Sequence< sal_Int16 > sSelection;
-+ uno::Sequence< rtl::OUString > sItems;
-+ m_xProps->getPropertyValue( SELECTEDITEMS ) >>= sSelection;
-+ m_xProps->getPropertyValue( ITEMS ) >>= sItems;
-+ if( getMultiSelect() )
-+ throw uno::RuntimeException( rtl::OUString::createFromAscii(
-+ "Attribute use invalid." ), uno::Reference< uno::XInterface >() );
-+ uno::Any aRet;
-+ if ( sSelection.getLength() )
-+ aRet = uno::makeAny( sItems[ sSelection[ 0 ] ] );
-+ return aRet;
-+}
-+
-+void SAL_CALL
-+ScVbaListBox::setValue( const uno::Any& _value ) throw (uno::RuntimeException)
-+{
-+ if( getMultiSelect() )
-+ {
-+ throw uno::RuntimeException( rtl::OUString::createFromAscii(
-+ "Attribute use invalid." ), uno::Reference< uno::XInterface >() );
-+ }
-+ rtl::OUString sValue = getAnyAsString( _value );
-+ uno::Sequence< rtl::OUString > sList;
-+ m_xProps->getPropertyValue( ITEMS ) >>= sList;
-+ uno::Sequence< sal_Int16 > nList;
-+ sal_Int16 nLength = static_cast<sal_Int16>( sList.getLength() );
-+ sal_Int16 nValue = -1;
-+ sal_Int16 i = 0;
-+ for( i = 0; i < nLength; i++ )
-+ {
-+ if( sList[i].equals( sValue ) )
-+ {
-+ nValue = i;
-+ break;
-+ }
-+ }
-+ if( nValue == -1 )
-+ throw uno::RuntimeException( rtl::OUString::createFromAscii(
-+ "Attribute use invalid." ), uno::Reference< uno::XInterface >() );
-+
-+ uno::Sequence< sal_Int16 > nSelectedIndices(1);
-+ nSelectedIndices[ 0 ] = nValue;
-+ m_xProps->setPropertyValue( SELECTEDITEMS, uno::makeAny( nSelectedIndices ) );
-+ m_xProps->setPropertyValue( TEXT, uno::makeAny( sValue ) );
-+}
-+
-+::rtl::OUString SAL_CALL
-+ScVbaListBox::getText() throw (uno::RuntimeException)
-+{
-+ rtl::OUString result;
-+ getValue() >>= result;
-+ return result;
-+}
-+
-+void SAL_CALL
-+ScVbaListBox::setText( const ::rtl::OUString& _text ) throw (uno::RuntimeException)
-+{
-+ setValue( uno::makeAny( _text ) ); // seems the same
-+}
-+
-+sal_Bool SAL_CALL
-+ScVbaListBox::getMultiSelect() throw (css::uno::RuntimeException)
-+{
-+ sal_Bool bMultiSelect = sal_False;
-+ m_xProps->getPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "MultiSelection" ) ) ) >>= bMultiSelect;
-+ return bMultiSelect;
-+}
-+
-+void SAL_CALL
-+ScVbaListBox::setMultiSelect( sal_Bool _multiselect ) throw (css::uno::RuntimeException)
-+{
-+ m_xProps->setPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "MultiSelection" ) ), uno::makeAny( _multiselect ) );
-+}
-+
-+css::uno::Any SAL_CALL
-+ScVbaListBox::Selected( sal_Int32 index ) throw (css::uno::RuntimeException)
-+{
-+ uno::Sequence< rtl::OUString > sList;
-+ m_xProps->getPropertyValue( ITEMS ) >>= sList;
-+ sal_Int16 nLength = static_cast< sal_Int16 >( sList.getLength() );
-+ // no choice but to do a horror cast as internally
-+ // the indices are but sal_Int16
-+ sal_Int16 nIndex = static_cast< sal_Int16 >( index );
-+ if( nIndex < 0 || nIndex >= nLength )
-+ throw uno::RuntimeException( rtl::OUString::createFromAscii(
-+ "Error Number." ), uno::Reference< uno::XInterface >() );
-+ m_nIndex = nIndex;
-+ return uno::makeAny( uno::Reference< XPropValue > ( new ScVbaPropValue( this ) ) );
-+}
-+
-+// Methods
-+void SAL_CALL
-+ScVbaListBox::AddItem( const uno::Any& pvargItem, const uno::Any& pvargIndex ) throw (uno::RuntimeException)
-+{
-+ mpListHelper->AddItem( pvargItem, pvargIndex );
-+ }
-+
-+void SAL_CALL
-+ScVbaListBox::removeItem( const uno::Any& index ) throw (uno::RuntimeException)
-+{
-+ mpListHelper->removeItem( index );
-+}
-+
-+void SAL_CALL
-+ScVbaListBox::Clear( ) throw (uno::RuntimeException)
-+{
-+ mpListHelper->Clear();
-+}
-+
-+// this is called when something like the following vba code is used
-+// to set the selected state of particular entries in the Listbox
-+// ListBox1.Selected( 3 ) = false
-+//PropListener
-+void
-+ScVbaListBox::setValueEvent( const uno::Any& value )
-+{
-+ sal_Bool bValue = sal_False;
-+ if( !(value >>= bValue) )
-+ throw uno::RuntimeException( rtl::OUString::createFromAscii(
-+ "Invalid type\n. need boolean." ), uno::Reference< uno::XInterface >() );
-+ uno::Sequence< sal_Int16 > nList;
-+ m_xProps->getPropertyValue( SELECTEDITEMS ) >>= nList;
-+ sal_Int16 nLength = static_cast<sal_Int16>( nList.getLength() );
-+ sal_Int16 nIndex = m_nIndex;
-+ for( sal_Int16 i = 0; i < nLength; i++ )
-+ {
-+ if( nList[i] == nIndex )
-+ {
-+ if( bValue )
-+ return;
-+ else
-+ {
-+ for( ; i < nLength - 1; i++ )
-+ {
-+ nList[i] = nList[i + 1];
-+ }
-+ nList.realloc( nLength - 1 );
-+ //m_xProps->setPropertyValue( sSourceName, uno::makeAny( nList ) );
-+ m_xProps->setPropertyValue( SELECTEDITEMS, uno::makeAny( nList ) );
-+ return;
-+ }
-+ }
-+ }
-+ if( bValue )
-+ {
-+ if( getMultiSelect() )
-+ {
-+ nList.realloc( nLength + 1 );
-+ nList[nLength] = nIndex;
-+ }
-+ else
-+ {
-+ nList.realloc( 1 );
-+ nList[0] = nIndex;
-+ }
-+ m_xProps->setPropertyValue( sSourceName, uno::makeAny( nList ) );
-+ }
-+}
-+
-+// this is called when something like the following vba code is used
-+// to determine the selected state of particular entries in the Listbox
-+// msgbox ListBox1.Selected( 3 )
-+
-+css::uno::Any
-+ScVbaListBox::getValueEvent()
-+{
-+ uno::Sequence< sal_Int16 > nList;
-+ m_xProps->getPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "SelectedItems" ) ) ) >>= nList;
-+ sal_Int32 nLength = nList.getLength();
-+ sal_Int32 nIndex = m_nIndex;
-+
-+ for( sal_Int32 i = 0; i < nLength; i++ )
-+ {
-+ if( nList[i] == nIndex )
-+ return uno::makeAny( sal_True );
-+ }
-+
-+ return uno::makeAny( sal_False );
-+}
-+
-+void SAL_CALL
-+ScVbaListBox::setRowSource( const rtl::OUString& _rowsource ) throw (uno::RuntimeException)
-+{
-+ ScVbaControl::setRowSource( _rowsource );
-+ mpListHelper->setRowSource( _rowsource );
-+}
-+
-+sal_Int32 SAL_CALL
-+ScVbaListBox::getListCount() throw (uno::RuntimeException)
-+{
-+ return mpListHelper->getListCount();
-+}
-+
-+uno::Any SAL_CALL
-+ScVbaListBox::List( const ::uno::Any& pvargIndex, const uno::Any& pvarColumn ) throw (uno::RuntimeException)
-+{
-+ return mpListHelper->List( pvargIndex, pvarColumn );
-+}
-+
-+rtl::OUString&
-+ScVbaListBox::getServiceImplName()
-+{
-+ static rtl::OUString sImplName( RTL_CONSTASCII_USTRINGPARAM("ScVbaListBox") );
-+ return sImplName;
-+}
-+
-+uno::Sequence< rtl::OUString >
-+ScVbaListBox::getServiceNames()
-+{
-+ static uno::Sequence< rtl::OUString > aServiceNames;
-+ if ( aServiceNames.getLength() == 0 )
-+ {
-+ aServiceNames.realloc( 1 );
-+ aServiceNames[ 0 ] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.msforms.ScVbaListBox" ) );
-+ }
-+ return aServiceNames;
-+}
---- vbahelper/source/msforms/vbalistbox.hxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ vbahelper/source/msforms/vbalistbox.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,90 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile: vbalistbox.hxx,v $
-+ * $Revision: 1.3 $
-+ *
-+ * 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.
-+ *
-+ ************************************************************************/
-+#ifndef SC_VBA_LISTBOX_HXX
-+#define SC_VBA_LISTBOX_HXX
-+#include <cppuhelper/implbase2.hxx>
-+#include <com/sun/star/uno/XComponentContext.hpp>
-+#include <com/sun/star/script/XDefaultProperty.hpp>
-+#include <ooo/vba/msforms/XListBox.hpp>
-+#include <com/sun/star/beans/PropertyAttribute.hpp>
-+
-+#include "vbacontrol.hxx"
-+#include <vbahelper/vbapropvalue.hxx>
-+#include "vbalistcontrolhelper.hxx"
-+#include <vbahelper/vbahelper.hxx>
-+
-+typedef cppu::ImplInheritanceHelper2<ScVbaControl, ov::msforms::XListBox, css::script::XDefaultProperty > ListBoxImpl_BASE;
-+class ScVbaListBox : public ListBoxImpl_BASE
-+ ,public PropListener
-+{
-+ std::auto_ptr< ListControlHelper > mpListHelper;
-+ rtl::OUString sSourceName;
-+ rtl::OUString msDftPropName;
-+
-+ sal_Int16 m_nIndex;
-+
-+public:
-+ ScVbaListBox( const css::uno::Reference< ov::XHelperInterface >& xParent, const css::uno::Reference< css::uno::XComponentContext >& xContext, const css::uno::Reference< css::uno::XInterface >& xControl, const css::uno::Reference< css::frame::XModel >& xModel, ov::AbstractGeometryAttributes* pGeomHelper );
-+
-+ // Attributes
-+ virtual css::uno::Any SAL_CALL getListIndex() throw (css::uno::RuntimeException);
-+ virtual void SAL_CALL setListIndex( const css::uno::Any& _value ) throw (css::uno::RuntimeException);
-+ virtual ::sal_Int32 SAL_CALL getListCount() throw (css::uno::RuntimeException);
-+ virtual css::uno::Any SAL_CALL getValue() throw (css::uno::RuntimeException);
-+ virtual void SAL_CALL setValue( const css::uno::Any& _value ) throw (css::uno::RuntimeException);
-+ virtual rtl::OUString SAL_CALL getText() throw (css::uno::RuntimeException);
-+ virtual void SAL_CALL setText( const ::rtl::OUString& _text ) throw (css::uno::RuntimeException);
-+ virtual sal_Bool SAL_CALL getMultiSelect() throw (css::uno::RuntimeException);
-+ virtual void SAL_CALL setMultiSelect( sal_Bool _multiselect ) throw (css::uno::RuntimeException);
-+ virtual css::uno::Any SAL_CALL Selected( ::sal_Int32 index ) throw (css::uno::RuntimeException);
-+
-+ // Methods
-+ virtual void SAL_CALL AddItem( const css::uno::Any& pvargItem, const css::uno::Any& pvargIndex ) throw (css::uno::RuntimeException);
-+ virtual void SAL_CALL removeItem( const css::uno::Any& index ) throw (css::uno::RuntimeException);
-+ virtual void SAL_CALL Clear( ) throw (css::uno::RuntimeException);
-+ virtual css::uno::Any SAL_CALL List( const css::uno::Any& pvargIndex, const css::uno::Any& pvarColumn ) throw (css::uno::RuntimeException);
-+ // XControl
-+ virtual void SAL_CALL setRowSource( const rtl::OUString& _rowsource ) throw (css::uno::RuntimeException);
-+
-+ // XDefaultProperty
-+ rtl::OUString SAL_CALL getDefaultPropertyName( ) throw (css::uno::RuntimeException) { return ::rtl::OUString::createFromAscii("Value"); }
-+
-+ //XHelperInterface
-+ virtual rtl::OUString& getServiceImplName();
-+ virtual css::uno::Sequence<rtl::OUString> getServiceNames();
-+
-+ //PropListener
-+ virtual void setValueEvent( const css::uno::Any& value );
-+ virtual css::uno::Any getValueEvent();
-+
-+
-+};
-+
-+#endif //
---- vbahelper/source/msforms/vbalistcontrolhelper.cxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ vbahelper/source/msforms/vbalistcontrolhelper.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,146 @@
-+#include <vbalistcontrolhelper.hxx>
-+#include <vector>
-+
-+using namespace com::sun::star;
-+using namespace ooo::vba;
-+
-+const static rtl::OUString ITEMS( RTL_CONSTASCII_USTRINGPARAM("StringItemList") );
-+
-+void SAL_CALL
-+ListControlHelper::AddItem( const uno::Any& pvargItem, const uno::Any& pvargIndex ) throw (uno::RuntimeException)
-+{
-+ if ( pvargItem.hasValue() )
-+ {
-+ uno::Sequence< rtl::OUString > sList;
-+ m_xProps->getPropertyValue( ITEMS ) >>= sList;
-+
-+ sal_Int32 nIndex = sList.getLength();
-+
-+ if ( pvargIndex.hasValue() )
-+ pvargIndex >>= nIndex;
-+
-+ rtl::OUString sString = getAnyAsString( pvargItem );
-+
-+ // if no index specified or item is to be appended to end of
-+ // list just realloc the array and set the last item
-+ if ( nIndex == sList.getLength() )
-+ {
-+ sal_Int32 nOldSize = sList.getLength();
-+ sList.realloc( nOldSize + 1 );
-+ sList[ nOldSize ] = sString;
-+ }
-+ else
-+ {
-+ // just copy those elements above the one to be inserted
-+ std::vector< rtl::OUString > sVec;
-+ // reserve just the amount we need to copy
-+ sVec.reserve( sList.getLength() - nIndex );
-+
-+ // point at first element to copy
-+ rtl::OUString* pString = sList.getArray() + nIndex;
-+ const rtl::OUString* pEndString = sList.getArray() + sList.getLength();
-+ // insert the new element
-+ sVec.push_back( sString );
-+ // copy elements
-+ for ( ; pString != pEndString; ++pString )
-+ sVec.push_back( *pString );
-+
-+ sList.realloc( sList.getLength() + 1 );
-+
-+ // point at first element to be overwritten
-+ pString = sList.getArray() + nIndex;
-+ pEndString = sList.getArray() + sList.getLength();
-+ std::vector< rtl::OUString >::iterator it = sVec.begin();
-+ for ( ; pString != pEndString; ++pString, ++it)
-+ *pString = *it;
-+ //
-+ }
-+
-+ m_xProps->setPropertyValue( ITEMS, uno::makeAny( sList ) );
-+
-+ }
-+}
-+
-+void SAL_CALL
-+ListControlHelper::removeItem( const uno::Any& index ) throw (uno::RuntimeException)
-+{
-+ sal_Int32 nIndex = 0;
-+ // for int index
-+ if ( index >>= nIndex )
-+ {
-+ uno::Sequence< rtl::OUString > sList;
-+ m_xProps->getPropertyValue( ITEMS ) >>= sList;
-+ if( nIndex < 0 || nIndex > ( sList.getLength() - 1 ) )
-+ throw uno::RuntimeException( rtl::OUString::createFromAscii( "Invalid index" ), uno::Reference< uno::XInterface > () );
-+ if( sList.hasElements() )
-+ {
-+ if( sList.getLength() == 1 )
-+ {
-+ Clear();
-+ return;
-+ }
-+ for( sal_Int32 i = nIndex; i < ( sList.getLength()-1 ); i++ )
-+ {
-+ sList[i] = sList[i+1];
-+ }
-+ sList.realloc( sList.getLength() - 1 );
-+ }
-+
-+ m_xProps->setPropertyValue( ITEMS, uno::makeAny( sList ) );
-+ }
-+}
-+
-+void SAL_CALL
-+ListControlHelper::Clear( ) throw (uno::RuntimeException)
-+{
-+ // urk, setValue doesn't seem to work !!
-+ //setValue( uno::makeAny( sal_Int16() ) );
-+ m_xProps->setPropertyValue( ITEMS, uno::makeAny( uno::Sequence< rtl::OUString >() ) );
-+}
-+
-+void SAL_CALL
-+ListControlHelper::setRowSource( const rtl::OUString& _rowsource ) throw (uno::RuntimeException)
-+{
-+ if ( _rowsource.getLength() == 0 )
-+ Clear();
-+}
-+
-+sal_Int32 SAL_CALL
-+ListControlHelper::getListCount() throw (uno::RuntimeException)
-+{
-+ uno::Sequence< rtl::OUString > sList;
-+ m_xProps->getPropertyValue( ITEMS ) >>= sList;
-+ return sList.getLength();
-+}
-+
-+uno::Any SAL_CALL
-+ListControlHelper::List( const ::uno::Any& pvargIndex, const uno::Any& pvarColumn ) throw (uno::RuntimeException)
-+{
-+ uno::Sequence< rtl::OUString > sList;
-+ m_xProps->getPropertyValue( ITEMS ) >>= sList;
-+ sal_Int16 nLength = static_cast< sal_Int16 >( sList.getLength() );
-+ uno::Any aRet;
-+ if ( pvargIndex.hasValue() )
-+ {
-+ sal_Int16 nIndex = -1;
-+ pvargIndex >>= nIndex;
-+ if( nIndex < 0 || nIndex >= nLength )
-+ throw uno::RuntimeException( rtl::OUString::createFromAscii(
-+ "Bad row Index" ), uno::Reference< uno::XInterface >() );
-+ aRet <<= sList[ nIndex ];
-+ }
-+ else if ( pvarColumn.hasValue() ) // pvarColumn on its own would be bad
-+ throw uno::RuntimeException( rtl::OUString::createFromAscii(
-+ "Bad column Index" ), uno::Reference< uno::XInterface >() );
-+ else // List() ( e.g. no args )
-+ {
-+ uno::Sequence< uno::Sequence< rtl::OUString > > sReturnArray( nLength );
-+ for ( sal_Int32 i = 0; i < nLength; ++i )
-+ {
-+ sReturnArray[ i ].realloc( 10 );
-+ sReturnArray[ i ][ 0 ] = sList[ i ];
-+ }
-+ aRet = uno::makeAny( sReturnArray );
-+ }
-+ return aRet;
-+}
---- vbahelper/source/msforms/vbalistcontrolhelper.hxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ vbahelper/source/msforms/vbalistcontrolhelper.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,20 @@
-+#ifndef SC_VBA_LISTCONTROLHELPER
-+#define SC_VBA_LISTCONTROLHELPER
-+
-+#include <vbahelper/vbahelper.hxx>
-+
-+class ListControlHelper
-+{
-+ css::uno::Reference< css::beans::XPropertySet > m_xProps;
-+
-+public:
-+ ListControlHelper( const css::uno::Reference< css::beans::XPropertySet >& rxControl ) : m_xProps( rxControl ){}
-+ virtual ~ListControlHelper() {}
-+ virtual void SAL_CALL AddItem( const css::uno::Any& pvargItem, const css::uno::Any& pvargIndex ) throw (css::uno::RuntimeException);
-+ virtual void SAL_CALL removeItem( const css::uno::Any& index ) throw (css::uno::RuntimeException);
-+ virtual void SAL_CALL setRowSource( const rtl::OUString& _rowsource ) throw (css::uno::RuntimeException);
-+ virtual ::sal_Int32 SAL_CALL getListCount() throw (css::uno::RuntimeException);
-+ virtual css::uno::Any SAL_CALL List( const css::uno::Any& pvargIndex, const css::uno::Any& pvarColumn ) throw (css::uno::RuntimeException);
-+ virtual void SAL_CALL Clear( ) throw (css::uno::RuntimeException);
-+};
-+#endif
---- vbahelper/source/msforms/vbamultipage.cxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ vbahelper/source/msforms/vbamultipage.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,132 @@
-+/*************************************************************************
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile$
-+ *
-+ * $Revision$
-+ *
-+ * last change: $Author$ $Date$
-+ *
-+ * The Contents of this file are made available subject to
-+ * the terms of GNU Lesser General Public License Version 2.1.
-+ *
-+ *
-+ * GNU Lesser General Public License Version 2.1
-+ * =============================================
-+ * Copyright 2005 by Sun Microsystems, Inc.
-+ * 901 San Antonio Road, Palo Alto, CA 94303, USA
-+ *
-+ * This library is free software; you can redistribute it and/or
-+ * modify it under the terms of the GNU Lesser General Public
-+ * License version 2.1, as published by the Free Software Foundation.
-+ *
-+ * This library 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 for more details.
-+ *
-+ * You should have received a copy of the GNU Lesser General Public
-+ * License along with this library; if not, write to the Free Software
-+ * Foundation, Inc., 59 Temple Place, Suite 330, Boston,
-+ * MA 02111-1307 USA
-+ *
-+ ************************************************************************/
-+#include "vbamultipage.hxx"
-+#include <ooo/vba/XCollection.hpp>
-+#include "vbapages.hxx"
-+#include <vector>
-+
-+using namespace com::sun::star;
-+using namespace ooo::vba;
-+
-+// uno servicename com.sun.star.awt.UnoControlProgressBarMode
-+const rtl::OUString SVALUE( RTL_CONSTASCII_USTRINGPARAM("ProgressValue") );
-+const rtl::OUString SVALUEMAX( RTL_CONSTASCII_USTRINGPARAM("ProgressValueMax") );
-+const rtl::OUString SSTEP( RTL_CONSTASCII_USTRINGPARAM("Step") );
-+
-+typedef cppu::WeakImplHelper1< container::XIndexAccess > PagesImpl_Base;
-+class PagesImpl : public PagesImpl_Base
-+{
-+ sal_Int32 mnPages;
-+public:
-+ PagesImpl( sal_Int32 nPages ) : mnPages( nPages ) {}
-+ virtual ::sal_Int32 SAL_CALL getCount() throw (uno::RuntimeException) { return mnPages; }
-+ virtual uno::Any SAL_CALL getByIndex( ::sal_Int32 Index ) throw (lang::IndexOutOfBoundsException, lang::WrappedTargetException, ::uno::RuntimeException)
-+ {
-+ if ( Index < 0 || Index > mnPages )
-+ throw lang::IndexOutOfBoundsException();
-+ return uno::makeAny( uno::Reference< uno::XInterface >() );
-+ }
-+ // XElementAccess
-+ virtual uno::Type SAL_CALL getElementType() throw (uno::RuntimeException)
-+ {
-+ // no Pages object yet #FIXME
-+ //return msforms::XPage::static_type(0);
-+ return uno::XInterface::static_type(0);
-+ }
-+ virtual ::sal_Bool SAL_CALL hasElements( ) throw (uno::RuntimeException)
-+ {
-+ return ( mnPages > 0 );
-+ }
-+};
-+uno::Reference< container::XIndexAccess >
-+ScVbaMultiPage::getPages( sal_Int32 nPages )
-+{
-+ return new PagesImpl( nPages );
-+}
-+
-+ScVbaMultiPage::ScVbaMultiPage( const uno::Reference< ov::XHelperInterface >& xParent, const uno::Reference< uno::XComponentContext >& xContext, const uno::Reference< uno::XInterface >& xControl, uno::Reference< frame::XModel >& xModel, AbstractGeometryAttributes* pGeomHelper, const uno::Reference< uno::XInterface >& xDialog ) : MultiPageImpl_BASE( xParent, xContext, xControl, xModel, pGeomHelper )
-+{
-+ mxDialogProps.set( xDialog, uno::UNO_QUERY_THROW );
-+ // set dialog step to value of multipage pseudo model
-+ setValue(getValue());
-+}
-+
-+// Attributes
-+sal_Int32 SAL_CALL
-+ScVbaMultiPage::getValue() throw (css::uno::RuntimeException)
-+{
-+ sal_Int32 nValue = 0;
-+ m_xProps->getPropertyValue( SVALUE ) >>= nValue;
-+ return nValue;
-+}
-+
-+void SAL_CALL
-+ScVbaMultiPage::setValue( const sal_Int32 _value ) throw (::com::sun::star::uno::RuntimeException)
-+{
-+ // track change in dialog ( dialog value is 1 based, 0 is a special value )
-+ m_xProps->setPropertyValue( SVALUE, uno::makeAny( _value ) );
-+ mxDialogProps->setPropertyValue( SSTEP, uno::makeAny( _value + 1) );
-+}
-+
-+
-+rtl::OUString&
-+ScVbaMultiPage::getServiceImplName()
-+{
-+ static rtl::OUString sImplName( RTL_CONSTASCII_USTRINGPARAM("ScVbaMultiPage") );
-+ return sImplName;
-+}
-+
-+uno::Any SAL_CALL
-+ScVbaMultiPage::Pages( const uno::Any& index ) throw (uno::RuntimeException)
-+{
-+ sal_Int32 nValue = 0;
-+ m_xProps->getPropertyValue( SVALUEMAX ) >>= nValue;
-+ uno::Reference< XCollection > xColl( new ScVbaPages( this, mxContext, getPages( nValue ) ) );
-+ if ( !index.hasValue() )
-+ return uno::makeAny( xColl );
-+ return xColl->Item( uno::makeAny( index ), uno::Any() );
-+}
-+
-+uno::Sequence< rtl::OUString >
-+ScVbaMultiPage::getServiceNames()
-+{
-+ static uno::Sequence< rtl::OUString > aServiceNames;
-+ if ( aServiceNames.getLength() == 0 )
-+ {
-+ aServiceNames.realloc( 1 );
-+ aServiceNames[ 0 ] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.msforms.MultiPage" ) );
-+ }
-+ return aServiceNames;
-+}
---- vbahelper/source/msforms/vbamultipage.hxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ vbahelper/source/msforms/vbamultipage.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,65 @@
-+/*************************************************************************
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile$
-+ *
-+ * $Revision$
-+ *
-+ * last change: $Author$ $Date$
-+ *
-+ * The Contents of this file are made available subject to
-+ * the terms of GNU Lesser General Public License Version 2.1.
-+ *
-+ *
-+ * GNU Lesser General Public License Version 2.1
-+ * =============================================
-+ * Copyright 2005 by Sun Microsystems, Inc.
-+ * 901 San Antonio Road, Palo Alto, CA 94303, USA
-+ *
-+ * This library is free software; you can redistribute it and/or
-+ * modify it under the terms of the GNU Lesser General Public
-+ * License version 2.1, as published by the Free Software Foundation.
-+ *
-+ * This library 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 for more details.
-+ *
-+ * You should have received a copy of the GNU Lesser General Public
-+ * License along with this library; if not, write to the Free Software
-+ * Foundation, Inc., 59 Temple Place, Suite 330, Boston,
-+ * MA 02111-1307 USA
-+ *
-+ ************************************************************************/
-+#ifndef SC_VBA_MULTIPAGE_HXX
-+#define SC_VBA_MULTIPAGE_HXX
-+#include <cppuhelper/implbase1.hxx>
-+#include <ooo/vba/msforms/XMultiPage.hpp>
-+#include <com/sun/star/container/XIndexAccess.hpp>
-+
-+#include "vbacontrol.hxx"
-+#include <vbahelper/vbahelper.hxx>
-+//#include <cppuhelper/implbase2.hxx>
-+#include <cppuhelper/implbase1.hxx>
-+
-+typedef cppu::ImplInheritanceHelper1< ScVbaControl, ov::msforms::XMultiPage > MultiPageImpl_BASE;
-+
-+class ScVbaMultiPage : public MultiPageImpl_BASE
-+{
-+ css::uno::Reference< css::container::XIndexAccess > getPages( sal_Int32 nPages );
-+ css::uno::Reference< css::beans::XPropertySet > mxDialogProps;
-+public:
-+ ScVbaMultiPage( const css::uno::Reference< ov::XHelperInterface >& xParent, const css::uno::Reference< css::uno::XComponentContext >& xContext, const css::uno::Reference< css::uno::XInterface >& xControl, css::uno::Reference< css::frame::XModel >& xModel, ov::AbstractGeometryAttributes* pGeomHelper, const css::uno::Reference< css::uno::XInterface >& xDialog );
-+ // Attributes
-+ virtual sal_Int32 SAL_CALL getValue() throw (css::uno::RuntimeException);
-+ virtual void SAL_CALL setValue( sal_Int32 _value ) throw (css::uno::RuntimeException);
-+ virtual css::uno::Any SAL_CALL Pages( const css::uno::Any& index ) throw (css::uno::RuntimeException);
-+
-+ //XHelperInterface
-+ virtual rtl::OUString& getServiceImplName();
-+ virtual css::uno::Sequence<rtl::OUString> getServiceNames();
-+ // XDefaultProperty
-+ rtl::OUString SAL_CALL getDefaultPropertyName( ) throw (css::uno::RuntimeException) { return ::rtl::OUString::createFromAscii("Value"); }
-+};
-+#endif //SC_VBA_LABEL_HXX
---- vbahelper/source/msforms/vbapages.cxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ vbahelper/source/msforms/vbapages.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,80 @@
-+/*************************************************************************
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile$
-+ *
-+ * $Revision$
-+ *
-+ * last change: $Author$ $Date$
-+ *
-+ * The Contents of this file are made available subject to
-+ * the terms of GNU Lesser General Public License Version 2.1.
-+ *
-+ *
-+ * GNU Lesser General Public License Version 2.1
-+ * =============================================
-+ * Copyright 2005 by Sun Microsystems, Inc.
-+ * 901 San Antonio Road, Palo Alto, CA 94303, USA
-+ *
-+ * This library is free software; you can redistribute it and/or
-+ * modify it under the terms of the GNU Lesser General Public
-+ * License version 2.1, as published by the Free Software Foundation.
-+ *
-+ * This library 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 for more details.
-+ *
-+ * You should have received a copy of the GNU Lesser General Public
-+ * License along with this library; if not, write to the Free Software
-+ * Foundation, Inc., 59 Temple Place, Suite 330, Boston,
-+ * MA 02111-1307 USA
-+ *
-+ ************************************************************************/
-+#include "vbapages.hxx"
-+
-+using namespace ::ooo::vba;
-+using namespace ::com::sun::star;
-+
-+ScVbaPages::ScVbaPages( const uno::Reference< XHelperInterface >& xParent, const uno::Reference< uno::XComponentContext >& xContext, const uno::Reference< container::XIndexAccess >& xPages ) throw( lang::IllegalArgumentException ) : ScVbaPages_BASE( xParent, xContext, xPages )
-+{
-+}
-+
-+uno::Type SAL_CALL
-+ScVbaPages::getElementType() throw (uno::RuntimeException)
-+{
-+ // return msforms::XPage::static_type(0);
-+ return uno::XInterface::static_type(0);
-+}
-+
-+uno::Any
-+ScVbaPages::createCollectionObject( const css::uno::Any& aSource )
-+{
-+ return aSource;
-+}
-+
-+rtl::OUString&
-+ScVbaPages::getServiceImplName()
-+{
-+ static rtl::OUString sImplName( RTL_CONSTASCII_USTRINGPARAM("ScVbaPages") );
-+ return sImplName;
-+}
-+
-+uno::Reference< container::XEnumeration > SAL_CALL
-+ScVbaPages::createEnumeration() throw (uno::RuntimeException)
-+{
-+ return uno::Reference< container::XEnumeration >();
-+}
-+
-+uno::Sequence< rtl::OUString >
-+ScVbaPages::getServiceNames()
-+{
-+ static uno::Sequence< rtl::OUString > aServiceNames;
-+ if ( aServiceNames.getLength() == 0 )
-+ {
-+ aServiceNames.realloc( 1 );
-+ aServiceNames[ 0 ] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.msform.Pages" ) );
-+ }
-+ return aServiceNames;
-+}
---- vbahelper/source/msforms/vbapages.hxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ vbahelper/source/msforms/vbapages.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,64 @@
-+/*************************************************************************
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile$
-+ *
-+ * $Revision$
-+ *
-+ * last change: $Author$ $Date$
-+ *
-+ * The Contents of this file are made available subject to
-+ * the terms of GNU Lesser General Public License Version 2.1.
-+ *
-+ *
-+ * GNU Lesser General Public License Version 2.1
-+ * =============================================
-+ * Copyright 2005 by Sun Microsystems, Inc.
-+ * 901 San Antonio Road, Palo Alto, CA 94303, USA
-+ *
-+ * This library is free software; you can redistribute it and/or
-+ * modify it under the terms of the GNU Lesser General Public
-+ * License version 2.1, as published by the Free Software Foundation.
-+ *
-+ * This library 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 for more details.
-+ *
-+ * You should have received a copy of the GNU Lesser General Public
-+ * License along with this library; if not, write to the Free Software
-+ * Foundation, Inc., 59 Temple Place, Suite 330, Boston,
-+ * MA 02111-1307 USA
-+ *
-+ ************************************************************************/
-+#ifndef SC_VBA_PAGES_HXX
-+#define SC_VBA_PAGES_HXX
-+
-+#include <ooo/vba/office/MsoShapeType.hpp>
-+#include <com/sun/star/lang/XEventListener.hpp>
-+#include <com/sun/star/beans/XPropertySet.hpp>
-+#include <ooo/vba/msforms/XPages.hpp>
-+#include <cppuhelper/implbase2.hxx>
-+#include <cppuhelper/implbase1.hxx>
-+
-+#include <vbahelper/vbacollectionimpl.hxx>
-+typedef CollTestImplHelper<
-+ov::msforms::XPages > ScVbaPages_BASE;
-+
-+class ScVbaPages : public ScVbaPages_BASE
-+{
-+protected:
-+ virtual rtl::OUString& getServiceImplName();
-+ virtual css::uno::Sequence<rtl::OUString> getServiceNames();
-+public:
-+ ScVbaPages( const css::uno::Reference< ov::XHelperInterface >& xParent, const css::uno::Reference< css::uno::XComponentContext >& xContext, const css::uno::Reference< css::container::XIndexAccess >& xPages ) throw ( css::lang::IllegalArgumentException );
-+ virtual ~ScVbaPages() {}
-+ // XEnumerationAccess
-+ virtual css::uno::Type SAL_CALL getElementType() throw (css::uno::RuntimeException);
-+ virtual css::uno::Reference< css::container::XEnumeration > SAL_CALL createEnumeration() throw (css::uno::RuntimeException);
-+ // ScVbaPages_BASE
-+ virtual css::uno::Any createCollectionObject( const css::uno::Any& aSource );
-+
-+};
-+#endif//SC_VBA_SHAPE_HXX
---- vbahelper/source/msforms/vbaprogressbar.cxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ vbahelper/source/msforms/vbaprogressbar.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,78 @@
-+/*************************************************************************
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile$
-+ *
-+ * $Revision$
-+ *
-+ * last change: $Author$ $Date$
-+ *
-+ * The Contents of this file are made available subject to
-+ * the terms of GNU Lesser General Public License Version 2.1.
-+ *
-+ *
-+ * GNU Lesser General Public License Version 2.1
-+ * =============================================
-+ * Copyright 2005 by Sun Microsystems, Inc.
-+ * 901 San Antonio Road, Palo Alto, CA 94303, USA
-+ *
-+ * This library is free software; you can redistribute it and/or
-+ * modify it under the terms of the GNU Lesser General Public
-+ * License version 2.1, as published by the Free Software Foundation.
-+ *
-+ * This library 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 for more details.
-+ *
-+ * You should have received a copy of the GNU Lesser General Public
-+ * License along with this library; if not, write to the Free Software
-+ * Foundation, Inc., 59 Temple Place, Suite 330, Boston,
-+ * MA 02111-1307 USA
-+ *
-+ ************************************************************************/
-+#include "vbaprogressbar.hxx"
-+#include <vector>
-+
-+using namespace com::sun::star;
-+using namespace ooo::vba;
-+
-+// uno servicename com.sun.star.awt.UnoControlProgressBarMode
-+const rtl::OUString SVALUE( RTL_CONSTASCII_USTRINGPARAM("ProgressValue") );
-+
-+ScVbaProgressBar::ScVbaProgressBar( const uno::Reference< ov::XHelperInterface >& xParent, const uno::Reference< uno::XComponentContext >& xContext, const uno::Reference< uno::XInterface >& xControl, const uno::Reference< frame::XModel >& xModel, AbstractGeometryAttributes* pGeomHelper ) : ProgressBarImpl_BASE( xParent, xContext, xControl, xModel, pGeomHelper )
-+{
-+}
-+
-+// Attributes
-+uno::Any SAL_CALL
-+ScVbaProgressBar::getValue() throw (css::uno::RuntimeException)
-+{
-+ return m_xProps->getPropertyValue( SVALUE );
-+}
-+
-+void SAL_CALL
-+ScVbaProgressBar::setValue( const uno::Any& _value ) throw (::com::sun::star::uno::RuntimeException)
-+{
-+ m_xProps->setPropertyValue( SVALUE, _value );
-+}
-+
-+rtl::OUString&
-+ScVbaProgressBar::getServiceImplName()
-+{
-+ static rtl::OUString sImplName( RTL_CONSTASCII_USTRINGPARAM("ScVbaProgressBar") );
-+ return sImplName;
-+}
-+
-+uno::Sequence< rtl::OUString >
-+ScVbaProgressBar::getServiceNames()
-+{
-+ static uno::Sequence< rtl::OUString > aServiceNames;
-+ if ( aServiceNames.getLength() == 0 )
-+ {
-+ aServiceNames.realloc( 1 );
-+ aServiceNames[ 0 ] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.msforms.Label" ) );
-+ }
-+ return aServiceNames;
-+}
---- vbahelper/source/msforms/vbaprogressbar.hxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ vbahelper/source/msforms/vbaprogressbar.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,59 @@
-+/*************************************************************************
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile$
-+ *
-+ * $Revision$
-+ *
-+ * last change: $Author$ $Date$
-+ *
-+ * The Contents of this file are made available subject to
-+ * the terms of GNU Lesser General Public License Version 2.1.
-+ *
-+ *
-+ * GNU Lesser General Public License Version 2.1
-+ * =============================================
-+ * Copyright 2005 by Sun Microsystems, Inc.
-+ * 901 San Antonio Road, Palo Alto, CA 94303, USA
-+ *
-+ * This library is free software; you can redistribute it and/or
-+ * modify it under the terms of the GNU Lesser General Public
-+ * License version 2.1, as published by the Free Software Foundation.
-+ *
-+ * This library 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 for more details.
-+ *
-+ * You should have received a copy of the GNU Lesser General Public
-+ * License along with this library; if not, write to the Free Software
-+ * Foundation, Inc., 59 Temple Place, Suite 330, Boston,
-+ * MA 02111-1307 USA
-+ *
-+ ************************************************************************/
-+#ifndef SC_VBA_PROGRESSBAR_HXX
-+#define SC_VBA_PROGRESSBAR_HXX
-+#include <cppuhelper/implbase1.hxx>
-+#include <ooo/vba/msforms/XProgressBar.hpp>
-+
-+#include "vbacontrol.hxx"
-+#include <vbahelper/vbahelper.hxx>
-+#include <cppuhelper/implbase2.hxx>
-+
-+typedef cppu::ImplInheritanceHelper2< ScVbaControl, ov::msforms::XProgressBar, css::script::XDefaultProperty > ProgressBarImpl_BASE;
-+
-+class ScVbaProgressBar : public ProgressBarImpl_BASE
-+{
-+public:
-+ ScVbaProgressBar( const css::uno::Reference< ov::XHelperInterface >& xParent, const css::uno::Reference< css::uno::XComponentContext >& xContext, const css::uno::Reference< css::uno::XInterface >& xControl, const css::uno::Reference< css::frame::XModel >& xModel, ov::AbstractGeometryAttributes* pGeomHelper );
-+ // Attributes
-+ virtual css::uno::Any SAL_CALL getValue() throw (css::uno::RuntimeException);
-+ virtual void SAL_CALL setValue( const css::uno::Any& _value ) throw (css::uno::RuntimeException);
-+ //XHelperInterface
-+ virtual rtl::OUString& getServiceImplName();
-+ virtual css::uno::Sequence<rtl::OUString> getServiceNames();
-+ // XDefaultProperty
-+ rtl::OUString SAL_CALL getDefaultPropertyName( ) throw (css::uno::RuntimeException) { return ::rtl::OUString::createFromAscii("Value"); }
-+};
-+#endif //SC_VBA_LABEL_HXX
---- vbahelper/source/msforms/vbaradiobutton.cxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ vbahelper/source/msforms/vbaradiobutton.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,107 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile: vbaradiobutton.cxx,v $
-+ * $Revision: 1.3 $
-+ *
-+ * 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 "vbaradiobutton.hxx"
-+#include <vector>
-+
-+using namespace com::sun::star;
-+using namespace ooo::vba;
-+
-+
-+const static rtl::OUString LABEL( RTL_CONSTASCII_USTRINGPARAM("Label") );
-+const static rtl::OUString STATE( RTL_CONSTASCII_USTRINGPARAM("State") );
-+ScVbaRadioButton::ScVbaRadioButton( const uno::Reference< XHelperInterface >& xParent, const uno::Reference< uno::XComponentContext >& xContext, const uno::Reference< uno::XInterface >& xControl, const uno::Reference< frame::XModel >& xModel, AbstractGeometryAttributes* pGeomHelper ) : RadioButtonImpl_BASE( xParent, xContext, xControl, xModel, pGeomHelper )
-+{
-+}
-+
-+// Attributes
-+rtl::OUString SAL_CALL
-+ScVbaRadioButton::getCaption() throw (css::uno::RuntimeException)
-+{
-+ rtl::OUString Label;
-+ m_xProps->getPropertyValue( LABEL ) >>= Label;
-+ return Label;
-+}
-+
-+void SAL_CALL
-+ScVbaRadioButton::setCaption( const rtl::OUString& _caption ) throw (::com::sun::star::uno::RuntimeException)
-+{
-+ m_xProps->setPropertyValue( LABEL, uno::makeAny( _caption ) );
-+}
-+
-+uno::Any SAL_CALL
-+ScVbaRadioButton::getValue() throw (css::uno::RuntimeException)
-+{
-+ sal_Int16 nValue = -1;
-+ m_xProps->getPropertyValue( STATE ) >>= nValue;
-+ if( nValue != 0 )
-+ nValue = -1;
-+// return uno::makeAny( nValue );
-+// I must be missing something MSO says value should be -1 if selected, 0 if not
-+// selected
-+ return uno::makeAny( ( nValue == -1 ) ? sal_True : sal_False );
-+
-+}
-+
-+void SAL_CALL
-+ScVbaRadioButton::setValue( const uno::Any& _value ) throw (uno::RuntimeException)
-+{
-+ sal_Int16 nValue = 0;
-+ sal_Bool bValue = sal_False;
-+ if( _value >>= nValue )
-+ {
-+ if( nValue == -1)
-+ nValue = 1;
-+ }
-+ else if ( _value >>= bValue )
-+ {
-+ if ( bValue )
-+ nValue = 1;
-+ }
-+ m_xProps->setPropertyValue( STATE, uno::makeAny( nValue ) );
-+}
-+
-+rtl::OUString&
-+ScVbaRadioButton::getServiceImplName()
-+{
-+ static rtl::OUString sImplName( RTL_CONSTASCII_USTRINGPARAM("ScVbaRadioButton") );
-+ return sImplName;
-+}
-+
-+uno::Sequence< rtl::OUString >
-+ScVbaRadioButton::getServiceNames()
-+{
-+ static uno::Sequence< rtl::OUString > aServiceNames;
-+ if ( aServiceNames.getLength() == 0 )
-+ {
-+ aServiceNames.realloc( 1 );
-+ aServiceNames[ 0 ] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.msforms.RadioButton" ) );
-+ }
-+ return aServiceNames;
-+}
---- vbahelper/source/msforms/vbaradiobutton.hxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ vbahelper/source/msforms/vbaradiobutton.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,55 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile: vbaradiobutton.hxx,v $
-+ * $Revision: 1.3 $
-+ *
-+ * 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.
-+ *
-+ ************************************************************************/
-+#ifndef SC_VBA_RADIOBUTTON_HXX
-+#define SC_VBA_RADIOBUTTON_HXX
-+#include <ooo/vba/msforms/XRadioButton.hpp>
-+#include "vbacontrol.hxx"
-+#include <vbahelper/vbahelper.hxx>
-+#include <cppuhelper/implbase2.hxx>
-+
-+typedef cppu::ImplInheritanceHelper2< ScVbaControl, ov::msforms::XRadioButton, css::script::XDefaultProperty > RadioButtonImpl_BASE;
-+
-+class ScVbaRadioButton : public RadioButtonImpl_BASE
-+{
-+public:
-+ ScVbaRadioButton( const css::uno::Reference< ov::XHelperInterface >& xParent, const css::uno::Reference< css::uno::XComponentContext >& xContext, const css::uno::Reference< css::uno::XInterface >& xControl, const css::uno::Reference< css::frame::XModel >& xModel, ov::AbstractGeometryAttributes* pGeomHelper );
-+ // Attributes
-+ virtual rtl::OUString SAL_CALL getCaption() throw (css::uno::RuntimeException);
-+ virtual void SAL_CALL setCaption( const rtl::OUString& _caption ) throw (css::uno::RuntimeException);
-+ virtual css::uno::Any SAL_CALL getValue() throw (css::uno::RuntimeException);
-+ virtual void SAL_CALL setValue(const com::sun::star::uno::Any&) throw (css::uno::RuntimeException);
-+ //XHelperInterface
-+ virtual rtl::OUString& getServiceImplName();
-+ virtual css::uno::Sequence<rtl::OUString> getServiceNames();
-+ // XDefaultProperty
-+ rtl::OUString SAL_CALL getDefaultPropertyName( ) throw (css::uno::RuntimeException) { return ::rtl::OUString::createFromAscii("Value"); }
-+
-+};
-+#endif //SC_VBA_RADIOBUTTON_HXX
---- vbahelper/source/msforms/vbascrollbar.cxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ vbahelper/source/msforms/vbascrollbar.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,139 @@
-+/*************************************************************************
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile$
-+ *
-+ * $Revision$
-+ *
-+ * last change: $Author$ $Date$
-+ *
-+ * The Contents of this file are made available subject to
-+ * the terms of GNU Lesser General Public License Version 2.1.
-+ *
-+ *
-+ * GNU Lesser General Public License Version 2.1
-+ * =============================================
-+ * Copyright 2005 by Sun Microsystems, Inc.
-+ * 901 San Antonio Road, Palo Alto, CA 94303, USA
-+ *
-+ * This library is free software; you can redistribute it and/or
-+ * modify it under the terms of the GNU Lesser General Public
-+ * License version 2.1, as published by the Free Software Foundation.
-+ *
-+ * This library 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 for more details.
-+ *
-+ * You should have received a copy of the GNU Lesser General Public
-+ * License along with this library; if not, write to the Free Software
-+ * Foundation, Inc., 59 Temple Place, Suite 330, Boston,
-+ * MA 02111-1307 USA
-+ *
-+ ************************************************************************/
-+#include "vbascrollbar.hxx"
-+#include <vector>
-+
-+using namespace com::sun::star;
-+using namespace ooo::vba;
-+
-+
-+const static rtl::OUString LARGECHANGE( RTL_CONSTASCII_USTRINGPARAM("BlockIncrement") );
-+const static rtl::OUString SMALLCHANGE( RTL_CONSTASCII_USTRINGPARAM("LineIncrement") );
-+const static rtl::OUString ORIENTATION( RTL_CONSTASCII_USTRINGPARAM("Orientation") );
-+const static rtl::OUString SCROLLVALUE( RTL_CONSTASCII_USTRINGPARAM("ScrollValue") );
-+const static rtl::OUString SCROLLMAX( RTL_CONSTASCII_USTRINGPARAM("ScrollValueMax") );
-+const static rtl::OUString SCROLLMIN( RTL_CONSTASCII_USTRINGPARAM("ScrollValueMin") );
-+
-+ScVbaScrollBar::ScVbaScrollBar( const css::uno::Reference< ov::XHelperInterface >& xParent, const uno::Reference< uno::XComponentContext >& xContext, const uno::Reference< uno::XInterface >& xControl, const uno::Reference< frame::XModel >& xModel, AbstractGeometryAttributes* pGeomHelper ) : ScrollBarImpl_BASE( xParent, xContext, xControl, xModel, pGeomHelper )
-+{
-+}
-+
-+// Attributes
-+uno::Any SAL_CALL
-+ScVbaScrollBar::getValue() throw (css::uno::RuntimeException)
-+{
-+ return m_xProps->getPropertyValue( SCROLLVALUE );
-+}
-+
-+void SAL_CALL
-+ScVbaScrollBar::setValue( const uno::Any& _value ) throw (::com::sun::star::uno::RuntimeException)
-+{
-+ m_xProps->setPropertyValue( SCROLLVALUE, _value );
-+}
-+
-+::sal_Int32 SAL_CALL
-+ScVbaScrollBar::getMax() throw (uno::RuntimeException)
-+{
-+ sal_Int32 nMax = 0;
-+ m_xProps->getPropertyValue( SCROLLMAX ) >>= nMax;
-+ return nMax;
-+}
-+
-+void SAL_CALL
-+ScVbaScrollBar::setMax( sal_Int32 nVal ) throw (uno::RuntimeException)
-+{
-+ m_xProps->setPropertyValue( SCROLLMAX, uno::makeAny( nVal ) );
-+}
-+
-+::sal_Int32 SAL_CALL
-+ScVbaScrollBar::getMin() throw (uno::RuntimeException)
-+{
-+ sal_Int32 nVal = 0;
-+ m_xProps->getPropertyValue( SCROLLMIN ) >>= nVal;
-+ return nVal;
-+}
-+
-+void SAL_CALL
-+ScVbaScrollBar::setMin( sal_Int32 nVal ) throw (uno::RuntimeException)
-+{
-+ m_xProps->setPropertyValue( SCROLLMIN, uno::makeAny( nVal ) );
-+}
-+
-+void SAL_CALL
-+ScVbaScrollBar::setLargeChange( ::sal_Int32 _largechange ) throw (uno::RuntimeException)
-+{
-+ m_xProps->setPropertyValue( LARGECHANGE, uno::makeAny( _largechange ) );
-+}
-+
-+::sal_Int32 SAL_CALL
-+ScVbaScrollBar::getLargeChange() throw (uno::RuntimeException)
-+{
-+ sal_Int32 nVal = 0;
-+ m_xProps->getPropertyValue( LARGECHANGE ) >>= nVal;
-+ return nVal;
-+}
-+
-+::sal_Int32 SAL_CALL
-+ScVbaScrollBar::getSmallChange() throw (uno::RuntimeException)
-+{
-+ sal_Int32 nSmallChange = 0;
-+ m_xProps->getPropertyValue( SMALLCHANGE ) >>= nSmallChange;
-+ return nSmallChange;
-+}
-+
-+void SAL_CALL
-+ScVbaScrollBar::setSmallChange( ::sal_Int32 _smallchange ) throw (uno::RuntimeException)
-+{
-+ m_xProps->setPropertyValue( SMALLCHANGE, uno::makeAny( _smallchange ) );
-+}
-+
-+rtl::OUString&
-+ScVbaScrollBar::getServiceImplName()
-+{
-+ static rtl::OUString sImplName( RTL_CONSTASCII_USTRINGPARAM("ScVbaScrollBar") );
-+ return sImplName;
-+}
-+
-+uno::Sequence< rtl::OUString >
-+ScVbaScrollBar::getServiceNames()
-+{
-+ static uno::Sequence< rtl::OUString > aServiceNames;
-+ if ( aServiceNames.getLength() == 0 )
-+ {
-+ aServiceNames.realloc( 1 );
-+ aServiceNames[ 0 ] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.msforms.Frame" ) );
-+ }
-+ return aServiceNames;
-+}
---- vbahelper/source/msforms/vbascrollbar.hxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ vbahelper/source/msforms/vbascrollbar.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,66 @@
-+/*************************************************************************
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile$
-+ *
-+ * $Revision$
-+ *
-+ * last change: $Author$ $Date$
-+ *
-+ * The Contents of this file are made available subject to
-+ * the terms of GNU Lesser General Public License Version 2.1.
-+ *
-+ *
-+ * GNU Lesser General Public License Version 2.1
-+ * =============================================
-+ * Copyright 2005 by Sun Microsystems, Inc.
-+ * 901 San Antonio Road, Palo Alto, CA 94303, USA
-+ *
-+ * This library is free software; you can redistribute it and/or
-+ * modify it under the terms of the GNU Lesser General Public
-+ * License version 2.1, as published by the Free Software Foundation.
-+ *
-+ * This library 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 for more details.
-+ *
-+ * You should have received a copy of the GNU Lesser General Public
-+ * License along with this library; if not, write to the Free Software
-+ * Foundation, Inc., 59 Temple Place, Suite 330, Boston,
-+ * MA 02111-1307 USA
-+ *
-+ ************************************************************************/
-+#ifndef SC_VBA_SCROLLBAR_HXX
-+#define SC_VBA_SCROLLBAR_HXX
-+#include <cppuhelper/implbase1.hxx>
-+#include <ooo/vba/msforms/XScrollBar.hpp>
-+
-+#include "vbacontrol.hxx"
-+#include <vbahelper/vbahelper.hxx>
-+
-+typedef cppu::ImplInheritanceHelper1< ScVbaControl, ov::msforms::XScrollBar > ScrollBarImpl_BASE;
-+
-+class ScVbaScrollBar : public ScrollBarImpl_BASE
-+{
-+public:
-+ ScVbaScrollBar( const css::uno::Reference< ov::XHelperInterface >& xParent, const css::uno::Reference< css::uno::XComponentContext >& xContext, const css::uno::Reference< css::uno::XInterface >& xControl, const css::uno::Reference< css::frame::XModel >& xModel, ov::AbstractGeometryAttributes* pGeomHelper );
-+ // Attributes
-+ virtual css::uno::Any SAL_CALL getValue() throw (css::uno::RuntimeException);
-+ virtual void SAL_CALL setValue( const css::uno::Any& _value ) throw (css::uno::RuntimeException);
-+ virtual ::sal_Int32 SAL_CALL getMax() throw (css::uno::RuntimeException);
-+ virtual void SAL_CALL setMax( ::sal_Int32 _max ) throw (css::uno::RuntimeException);
-+ virtual ::sal_Int32 SAL_CALL getMin() throw (css::uno::RuntimeException);
-+ virtual void SAL_CALL setMin( ::sal_Int32 _min ) throw (css::uno::RuntimeException);
-+ virtual ::sal_Int32 SAL_CALL getLargeChange() throw (css::uno::RuntimeException);
-+ virtual void SAL_CALL setLargeChange( ::sal_Int32 _largechange ) throw (css::uno::RuntimeException);
-+ virtual ::sal_Int32 SAL_CALL getSmallChange() throw (css::uno::RuntimeException);
-+ virtual void SAL_CALL setSmallChange( ::sal_Int32 _smallchange ) throw (css::uno::RuntimeException);
-+
-+
-+ //XHelperInterface
-+ virtual rtl::OUString& getServiceImplName();
-+ virtual css::uno::Sequence<rtl::OUString> getServiceNames();
-+};
-+#endif //SC_VBA_LABEL_HXX
---- vbahelper/source/msforms/vbaspinbutton.cxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ vbahelper/source/msforms/vbaspinbutton.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,109 @@
-+/*************************************************************************
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile$
-+ *
-+ * $Revision$
-+ *
-+ * last change: $Author$ $Date$
-+ *
-+ * The Contents of this file are made available subject to
-+ * the terms of GNU Lesser General Public License Version 2.1.
-+ *
-+ *
-+ * GNU Lesser General Public License Version 2.1
-+ * =============================================
-+ * Copyright 2005 by Sun Microsystems, Inc.
-+ * 901 San Antonio Road, Palo Alto, CA 94303, USA
-+ *
-+ * This library is free software; you can redistribute it and/or
-+ * modify it under the terms of the GNU Lesser General Public
-+ * License version 2.1, as published by the Free Software Foundation.
-+ *
-+ * This library 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 for more details.
-+ *
-+ * You should have received a copy of the GNU Lesser General Public
-+ * License along with this library; if not, write to the Free Software
-+ * Foundation, Inc., 59 Temple Place, Suite 330, Boston,
-+ * MA 02111-1307 USA
-+ *
-+ ************************************************************************/
-+#include "vbaspinbutton.hxx"
-+#include <vector>
-+
-+using namespace com::sun::star;
-+using namespace ooo::vba;
-+
-+
-+const static rtl::OUString ORIENTATION( RTL_CONSTASCII_USTRINGPARAM("Orientation") );
-+const static rtl::OUString SPINVALUE( RTL_CONSTASCII_USTRINGPARAM("SpinValue") );
-+const static rtl::OUString SPINMAX( RTL_CONSTASCII_USTRINGPARAM("SpinValueMax") );
-+const static rtl::OUString SPINMIN( RTL_CONSTASCII_USTRINGPARAM("SpinValueMin") );
-+
-+ScVbaSpinButton::ScVbaSpinButton( const css::uno::Reference< ov::XHelperInterface >& xParent, const uno::Reference< uno::XComponentContext >& xContext, const uno::Reference< uno::XInterface >& xControl, const uno::Reference< frame::XModel >& xModel, AbstractGeometryAttributes* pGeomHelper ) : SpinButtonImpl_BASE( xParent, xContext, xControl, xModel, pGeomHelper )
-+{
-+}
-+
-+// Attributes
-+uno::Any SAL_CALL
-+ScVbaSpinButton::getValue() throw (css::uno::RuntimeException)
-+{
-+ return m_xProps->getPropertyValue( SPINVALUE );
-+}
-+
-+void SAL_CALL
-+ScVbaSpinButton::setValue( const uno::Any& _value ) throw (::com::sun::star::uno::RuntimeException)
-+{
-+ m_xProps->setPropertyValue( SPINVALUE, _value );
-+}
-+
-+::sal_Int32 SAL_CALL
-+ScVbaSpinButton::getMax() throw (uno::RuntimeException)
-+{
-+ sal_Int32 nMax = 0;
-+ m_xProps->getPropertyValue( SPINMAX ) >>= nMax;
-+ return nMax;
-+}
-+
-+void SAL_CALL
-+ScVbaSpinButton::setMax( sal_Int32 nVal ) throw (uno::RuntimeException)
-+{
-+ m_xProps->setPropertyValue( SPINMAX, uno::makeAny( nVal ) );
-+}
-+
-+::sal_Int32 SAL_CALL
-+ScVbaSpinButton::getMin() throw (uno::RuntimeException)
-+{
-+ sal_Int32 nVal = 0;
-+ m_xProps->getPropertyValue( SPINMIN ) >>= nVal;
-+ return nVal;
-+}
-+
-+void SAL_CALL
-+ScVbaSpinButton::setMin( sal_Int32 nVal ) throw (uno::RuntimeException)
-+{
-+ m_xProps->setPropertyValue( SPINMIN, uno::makeAny( nVal ) );
-+}
-+
-+rtl::OUString&
-+ScVbaSpinButton::getServiceImplName()
-+{
-+ static rtl::OUString sImplName( RTL_CONSTASCII_USTRINGPARAM("ScVbaSpinButton") );
-+ return sImplName;
-+}
-+
-+uno::Sequence< rtl::OUString >
-+ScVbaSpinButton::getServiceNames()
-+{
-+ static uno::Sequence< rtl::OUString > aServiceNames;
-+ if ( aServiceNames.getLength() == 0 )
-+ {
-+ aServiceNames.realloc( 1 );
-+ aServiceNames[ 0 ] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.msforms.Frame" ) );
-+ }
-+ return aServiceNames;
-+}
---- vbahelper/source/msforms/vbaspinbutton.hxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ vbahelper/source/msforms/vbaspinbutton.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,61 @@
-+/*************************************************************************
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile$
-+ *
-+ * $Revision$
-+ *
-+ * last change: $Author$ $Date$
-+ *
-+ * The Contents of this file are made available subject to
-+ * the terms of GNU Lesser General Public License Version 2.1.
-+ *
-+ *
-+ * GNU Lesser General Public License Version 2.1
-+ * =============================================
-+ * Copyright 2005 by Sun Microsystems, Inc.
-+ * 901 San Antonio Road, Palo Alto, CA 94303, USA
-+ *
-+ * This library is free software; you can redistribute it and/or
-+ * modify it under the terms of the GNU Lesser General Public
-+ * License version 2.1, as published by the Free Software Foundation.
-+ *
-+ * This library 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 for more details.
-+ *
-+ * You should have received a copy of the GNU Lesser General Public
-+ * License along with this library; if not, write to the Free Software
-+ * Foundation, Inc., 59 Temple Place, Suite 330, Boston,
-+ * MA 02111-1307 USA
-+ *
-+ ************************************************************************/
-+#ifndef SC_VBA_SPINBUTTON_HXX
-+#define SC_VBA_SPINBUTTON_HXX
-+#include <cppuhelper/implbase1.hxx>
-+#include <ooo/vba/msforms/XSpinButton.hpp>
-+
-+#include "vbacontrol.hxx"
-+#include <vbahelper/vbahelper.hxx>
-+
-+typedef cppu::ImplInheritanceHelper1< ScVbaControl, ov::msforms::XSpinButton > SpinButtonImpl_BASE;
-+
-+class ScVbaSpinButton : public SpinButtonImpl_BASE
-+{
-+public:
-+ ScVbaSpinButton( const css::uno::Reference< ov::XHelperInterface >& xParent, const css::uno::Reference< css::uno::XComponentContext >& xContext, const css::uno::Reference< css::uno::XInterface >& xControl, const css::uno::Reference< css::frame::XModel >& xModel, ov::AbstractGeometryAttributes* pGeomHelper );
-+ // Attributes
-+ virtual css::uno::Any SAL_CALL getValue() throw (css::uno::RuntimeException);
-+ virtual void SAL_CALL setValue( const css::uno::Any& _value ) throw (css::uno::RuntimeException);
-+ virtual ::sal_Int32 SAL_CALL getMax() throw (css::uno::RuntimeException);
-+ virtual void SAL_CALL setMax( ::sal_Int32 _max ) throw (css::uno::RuntimeException);
-+ virtual ::sal_Int32 SAL_CALL getMin() throw (css::uno::RuntimeException);
-+ virtual void SAL_CALL setMin( ::sal_Int32 _min ) throw (css::uno::RuntimeException);
-+
-+ //XHelperInterface
-+ virtual rtl::OUString& getServiceImplName();
-+ virtual css::uno::Sequence<rtl::OUString> getServiceNames();
-+};
-+#endif //SC_VBA_SPINBUTTON_HXX
---- vbahelper/source/msforms/vbatextbox.cxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ vbahelper/source/msforms/vbatextbox.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,137 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile: vbatextbox.cxx,v $
-+ * $Revision: 1.3 $
-+ *
-+ * 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 <com/sun/star/text/XTextRange.hpp>
-+
-+#include "vbatextbox.hxx"
-+#include <vector>
-+
-+using namespace com::sun::star;
-+using namespace ooo::vba;
-+
-+
-+
-+ScVbaTextBox::ScVbaTextBox( const uno::Reference< ov::XHelperInterface >& xParent, const uno::Reference< uno::XComponentContext >& xContext, const uno::Reference< uno::XInterface >& xControl, const uno::Reference< frame::XModel >& xModel, AbstractGeometryAttributes* pGeomHelper, bool bDialog ) : TextBoxImpl_BASE( xParent, xContext, xControl, xModel, pGeomHelper ), mbDialog( bDialog )
-+{
-+}
-+
-+// Attributes
-+uno::Any SAL_CALL
-+ScVbaTextBox::getValue() throw (css::uno::RuntimeException)
-+{
-+ return uno::makeAny( getText() );
-+}
-+
-+void SAL_CALL
-+ScVbaTextBox::setValue( const uno::Any& _value ) throw (css::uno::RuntimeException)
-+{
-+ rtl::OUString sVal = getAnyAsString( _value );
-+ setText( sVal );
-+}
-+
-+//getString() will cause some imfo lose.
-+rtl::OUString SAL_CALL
-+ScVbaTextBox::getText() throw (css::uno::RuntimeException)
-+{
-+ uno::Any aValue;
-+ aValue = m_xProps->getPropertyValue
-+ (rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "Text" ) ) );
-+ rtl::OUString sString;
-+ aValue >>= sString;
-+ return sString;
-+}
-+
-+void SAL_CALL
-+ScVbaTextBox::setText( const rtl::OUString& _text ) throw (css::uno::RuntimeException)
-+{
-+ if ( !mbDialog )
-+ {
-+ uno::Reference< text::XTextRange > xTextRange( m_xProps, uno::UNO_QUERY_THROW );
-+ xTextRange->setString( _text );
-+}
-+ else
-+ m_xProps->setPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("Text") ), uno::makeAny( _text ) );
-+}
-+
-+sal_Int32 SAL_CALL
-+ScVbaTextBox::getMaxLength() throw (css::uno::RuntimeException)
-+{
-+ uno::Any aValue;
-+ aValue = m_xProps->getPropertyValue
-+ (rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "MaxTextLen" ) ) );
-+ sal_Int32 nMaxLength = 0;
-+ aValue >>= nMaxLength;
-+ return nMaxLength;
-+}
-+
-+void SAL_CALL
-+ScVbaTextBox::setMaxLength( sal_Int32 _maxlength ) throw (css::uno::RuntimeException)
-+{
-+ uno::Any aValue( _maxlength );
-+ m_xProps->setPropertyValue
-+ (rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "MaxTextLen" ) ), aValue);
-+}
-+
-+sal_Bool SAL_CALL
-+ScVbaTextBox::getMultiline() throw (css::uno::RuntimeException)
-+{
-+ uno::Any aValue;
-+ aValue = m_xProps->getPropertyValue
-+ (rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "MultiLine" ) ) );
-+ sal_Bool bRet = false;
-+ aValue >>= bRet;
-+ return bRet;
-+}
-+
-+void SAL_CALL
-+ScVbaTextBox::setMultiline( sal_Bool _multiline ) throw (css::uno::RuntimeException)
-+{
-+ uno::Any aValue( _multiline );
-+ m_xProps->setPropertyValue
-+ (rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "MultiLine" ) ), aValue);
-+}
-+
-+rtl::OUString&
-+ScVbaTextBox::getServiceImplName()
-+{
-+ static rtl::OUString sImplName( RTL_CONSTASCII_USTRINGPARAM("ScVbaTextBox") );
-+ return sImplName;
-+}
-+
-+uno::Sequence< rtl::OUString >
-+ScVbaTextBox::getServiceNames()
-+{
-+ static uno::Sequence< rtl::OUString > aServiceNames;
-+ if ( aServiceNames.getLength() == 0 )
-+ {
-+ aServiceNames.realloc( 1 );
-+ aServiceNames[ 0 ] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.msforms.TextBox" ) );
-+ }
-+ return aServiceNames;
-+}
---- vbahelper/source/msforms/vbatextbox.hxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ vbahelper/source/msforms/vbatextbox.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,57 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile: vbatextbox.hxx,v $
-+ * $Revision: 1.3 $
-+ *
-+ * 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.
-+ *
-+ ************************************************************************/
-+#ifndef SC_VBA_TEXTBOX_HXX
-+#define SC_VBA_TEXTBOX_HXX
-+#include <cppuhelper/implbase1.hxx>
-+#include <ooo/vba/msforms/XTextBox.hpp>
-+#include "vbacontrol.hxx"
-+#include <vbahelper/vbahelper.hxx>
-+
-+typedef cppu::ImplInheritanceHelper1< ScVbaControl, ov::msforms::XTextBox > TextBoxImpl_BASE;
-+
-+class ScVbaTextBox : public TextBoxImpl_BASE
-+{
-+ bool mbDialog;
-+public:
-+ ScVbaTextBox( const css::uno::Reference< ov::XHelperInterface >& xParent, const css::uno::Reference< css::uno::XComponentContext >& xContext, const css::uno::Reference< css::uno::XInterface >& xControl, const css::uno::Reference< css::frame::XModel >& xModel, ov::AbstractGeometryAttributes* pGeomHelper, bool bDialog = false );
-+ // Attributes
-+ virtual css::uno::Any SAL_CALL getValue() throw (css::uno::RuntimeException);
-+ virtual void SAL_CALL setValue( const css::uno::Any& _value ) throw (css::uno::RuntimeException);
-+ virtual rtl::OUString SAL_CALL getText() throw (css::uno::RuntimeException);
-+ virtual void SAL_CALL setText( const rtl::OUString& _text ) throw (css::uno::RuntimeException);
-+ virtual sal_Int32 SAL_CALL getMaxLength() throw (css::uno::RuntimeException);
-+ virtual void SAL_CALL setMaxLength( sal_Int32 _maxlength ) throw (css::uno::RuntimeException);
-+ virtual sal_Bool SAL_CALL getMultiline() throw (css::uno::RuntimeException);
-+ virtual void SAL_CALL setMultiline( sal_Bool _multiline ) throw (css::uno::RuntimeException);
-+ //XHelperInterface
-+ virtual rtl::OUString& getServiceImplName();
-+ virtual css::uno::Sequence<rtl::OUString> getServiceNames();
-+};
-+#endif //SC_VBA_TEXTBOX_HXX
---- vbahelper/source/msforms/vbatogglebutton.cxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ vbahelper/source/msforms/vbatogglebutton.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,108 @@
-+/*************************************************************************
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile$
-+ *
-+ * $Revision$
-+ *
-+ * last change: $Author$ $Date$
-+ *
-+ * The Contents of this file are made available subject to
-+ * the terms of GNU Lesser General Public License Version 2.1.
-+ *
-+ *
-+ * GNU Lesser General Public License Version 2.1
-+ * =============================================
-+ * Copyright 2005 by Sun Microsystems, Inc.
-+ * 901 San Antonio Road, Palo Alto, CA 94303, USA
-+ *
-+ * This library is free software; you can redistribute it and/or
-+ * modify it under the terms of the GNU Lesser General Public
-+ * License version 2.1, as published by the Free Software Foundation.
-+ *
-+ * This library 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 for more details.
-+ *
-+ * You should have received a copy of the GNU Lesser General Public
-+ * License along with this library; if not, write to the Free Software
-+ * Foundation, Inc., 59 Temple Place, Suite 330, Boston,
-+ * MA 02111-1307 USA
-+ *
-+ ************************************************************************/
-+#include "vbatogglebutton.hxx"
-+#include <vector>
-+
-+using namespace com::sun::star;
-+using namespace ooo::vba;
-+
-+
-+const static rtl::OUString LABEL( RTL_CONSTASCII_USTRINGPARAM("Label") );
-+const static rtl::OUString TOGGLE( RTL_CONSTASCII_USTRINGPARAM("Toggle") );
-+const static rtl::OUString STATE( RTL_CONSTASCII_USTRINGPARAM("State") );
-+ScVbaToggleButton::ScVbaToggleButton( const css::uno::Reference< ov::XHelperInterface >& xParent, const uno::Reference< uno::XComponentContext >& xContext, const uno::Reference< uno::XInterface >& xControl, const uno::Reference< frame::XModel >& xModel, ov::AbstractGeometryAttributes* pGeomHelper ) : ToggleButtonImpl_BASE( xParent, xContext, xControl, xModel, pGeomHelper )
-+{
-+ OSL_TRACE("ScVbaToggleButton(ctor)");
-+ m_xProps->setPropertyValue( TOGGLE, uno::makeAny( sal_True ) );
-+}
-+
-+ScVbaToggleButton::~ScVbaToggleButton()
-+{
-+ OSL_TRACE("~ScVbaToggleButton(dtor)");
-+}
-+
-+// Attributes
-+rtl::OUString SAL_CALL
-+ScVbaToggleButton::getCaption() throw (css::uno::RuntimeException)
-+{
-+ rtl::OUString Label;
-+ m_xProps->getPropertyValue( LABEL ) >>= Label;
-+ return Label;
-+}
-+
-+void SAL_CALL
-+ScVbaToggleButton::setCaption( const rtl::OUString& _caption ) throw (::com::sun::star::uno::RuntimeException)
-+{
-+ m_xProps->setPropertyValue( LABEL, uno::makeAny( _caption ) );
-+}
-+
-+uno::Any SAL_CALL
-+ScVbaToggleButton::getValue() throw (uno::RuntimeException)
-+{
-+ sal_Int16 nState = 0;
-+ m_xProps->getPropertyValue( STATE ) >>= nState;
-+ return uno::makeAny( nState ? sal_Int16( -1 ) : sal_Int16( 0 ) );
-+}
-+
-+void SAL_CALL
-+ScVbaToggleButton::setValue( const uno::Any& _value ) throw (uno::RuntimeException)
-+{
-+ sal_Int16 nState = 0;
-+ _value >>= nState;
-+ OSL_TRACE( "nState - %d", nState );
-+ nState = ( nState == -1 ) ? 1 : 0;
-+ OSL_TRACE( "nState - %d", nState );
-+ m_xProps->setPropertyValue( STATE, uno::makeAny( nState ) );
-+}
-+
-+rtl::OUString&
-+ScVbaToggleButton::getServiceImplName()
-+{
-+ static rtl::OUString sImplName( RTL_CONSTASCII_USTRINGPARAM("ScVbaToggleButton") );
-+ return sImplName;
-+}
-+
-+uno::Sequence< rtl::OUString >
-+ScVbaToggleButton::getServiceNames()
-+{
-+ static uno::Sequence< rtl::OUString > aServiceNames;
-+ if ( aServiceNames.getLength() == 0 )
-+ {
-+ aServiceNames.realloc( 1 );
-+ aServiceNames[ 0 ] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.msforms.ToggleButton" ) );
-+ }
-+ return aServiceNames;
-+}
-+
---- vbahelper/source/msforms/vbatogglebutton.hxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ vbahelper/source/msforms/vbatogglebutton.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,63 @@
-+/*************************************************************************
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile$
-+ *
-+ * $Revision$
-+ *
-+ * last change: $Author$ $Date$
-+ *
-+ * The Contents of this file are made available subject to
-+ * the terms of GNU Lesser General Public License Version 2.1.
-+ *
-+ *
-+ * GNU Lesser General Public License Version 2.1
-+ * =============================================
-+ * Copyright 2005 by Sun Microsystems, Inc.
-+ * 901 San Antonio Road, Palo Alto, CA 94303, USA
-+ *
-+ * This library is free software; you can redistribute it and/or
-+ * modify it under the terms of the GNU Lesser General Public
-+ * License version 2.1, as published by the Free Software Foundation.
-+ *
-+ * This library 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 for more details.
-+ *
-+ * You should have received a copy of the GNU Lesser General Public
-+ * License along with this library; if not, write to the Free Software
-+ * Foundation, Inc., 59 Temple Place, Suite 330, Boston,
-+ * MA 02111-1307 USA
-+ *
-+ ************************************************************************/
-+#ifndef SC_VBA_TOGGLEBUTTON_HXX
-+#define SC_VBA_TOGGLEBUTTON_HXX
-+#include <cppuhelper/implbase2.hxx>
-+#include <ooo/vba/msforms/XToggleButton.hpp>
-+
-+#include "vbacontrol.hxx"
-+#include <vbahelper/vbahelper.hxx>
-+
-+typedef cppu::ImplInheritanceHelper2< ScVbaControl, ov::msforms::XToggleButton, css::script::XDefaultProperty > ToggleButtonImpl_BASE;
-+
-+class ScVbaToggleButton : public ToggleButtonImpl_BASE
-+{
-+ rtl::OUString msDftPropName;
-+public:
-+ ScVbaToggleButton( const css::uno::Reference< ov::XHelperInterface >& xParent, const css::uno::Reference< css::uno::XComponentContext >& xContext, const css::uno::Reference< css::uno::XInterface >& xControl, const css::uno::Reference< css::frame::XModel >& xModel, ov::AbstractGeometryAttributes* pGeomHelper );
-+ ~ScVbaToggleButton();
-+ // Attributes
-+ virtual css::uno::Any SAL_CALL getValue() throw (css::uno::RuntimeException);
-+ virtual void SAL_CALL setValue( const css::uno::Any& _value ) throw (css::uno::RuntimeException);
-+
-+ virtual rtl::OUString SAL_CALL getCaption() throw (css::uno::RuntimeException);
-+ virtual void SAL_CALL setCaption( const rtl::OUString& _caption ) throw (css::uno::RuntimeException);
-+ //XHelperInterface
-+ virtual rtl::OUString& getServiceImplName();
-+ virtual css::uno::Sequence<rtl::OUString> getServiceNames();
-+ // XDefaultProperty
-+ rtl::OUString SAL_CALL getDefaultPropertyName( ) throw (css::uno::RuntimeException) { return ::rtl::OUString::createFromAscii("Value"); }
-+};
-+#endif //SC_VBA_TOGGLEBUTTON_HXX
---- vbahelper/source/msforms/vbauserform.cxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ vbahelper/source/msforms/vbauserform.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,226 @@
-+/*************************************************************************
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile$
-+ *
-+ * $Revision$
-+ *
-+ * last change: $Author$ $Date$
-+ *
-+ * The Contents of this file are made available subject to
-+ * the terms of GNU Lesser General Public License Version 2.1.
-+ *
-+ *
-+ * GNU Lesser General Public License Version 2.1
-+ * =============================================
-+ * Copyright 2005 by Sun Microsystems, Inc.
-+ * 901 San Antonio Road, Palo Alto, CA 94303, USA
-+ *
-+ * This library is free software; you can redistribute it and/or
-+ * modify it under the terms of the GNU Lesser General Public
-+ * License version 2.1, as published by the Free Software Foundation.
-+ *
-+ * This library 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 for more details.
-+ *
-+ * You should have received a copy of the GNU Lesser General Public
-+ * License along with this library; if not, write to the Free Software
-+ * Foundation, Inc., 59 Temple Place, Suite 330, Boston,
-+ * MA 02111-1307 USA
-+ *
-+ ************************************************************************/
-+#include <vbahelper/helperdecl.hxx>
-+#include "vbauserform.hxx"
-+#include <com/sun/star/awt/XControl.hpp>
-+#include <com/sun/star/awt/XControlContainer.hpp>
-+#include <com/sun/star/beans/PropertyConcept.hpp>
-+#include <basic/sbx.hxx>
-+#include <basic/sbstar.hxx>
-+#include <basic/sbmeth.hxx>
-+#include "vbacontrols.hxx"
-+
-+using namespace ::ooo::vba;
-+using namespace ::com::sun::star;
-+
-+// some little notes
-+// XDialog implementation has the following interesting bits
-+// a Controls property ( which is an array of the container controls )
-+// each item in the controls array is a XControl, where the model is
-+// basically a property bag
-+// additionally the XDialog instance has itself a model
-+// this model has a ControlModels ( array of models ) property
-+// the models in ControlModels can be accessed by name
-+// also the XDialog is a XControl ( to access the model above
-+
-+ScVbaUserForm::ScVbaUserForm( uno::Sequence< uno::Any > const& aArgs, uno::Reference< uno::XComponentContext >const& xContext ) throw ( lang::IllegalArgumentException ) : ScVbaUserForm_BASE( getXSomethingFromArgs< XHelperInterface >( aArgs, 0 ), xContext, getXSomethingFromArgs< uno::XInterface >( aArgs, 1 ), getXSomethingFromArgs< frame::XModel >( aArgs, 2 ), static_cast< ooo::vba::AbstractGeometryAttributes* >(0) ), mbDispose( true )
-+{
-+ m_xDialog.set( m_xControl, uno::UNO_QUERY_THROW );
-+ uno::Reference< awt::XControl > xControl( m_xDialog, uno::UNO_QUERY_THROW );
-+ m_xProps.set( xControl->getModel(), uno::UNO_QUERY_THROW );
-+ setGeometryHelper( new UserFormGeometryHelper( xContext, xControl ) );
-+}
-+
-+ScVbaUserForm::~ScVbaUserForm()
-+{
-+}
-+
-+void SAL_CALL
-+ScVbaUserForm::Show( ) throw (uno::RuntimeException)
-+{
-+ OSL_TRACE("ScVbaUserForm::Show( )");
-+ short aRet = 0;
-+ if ( m_xDialog.is() )
-+ aRet = m_xDialog->execute();
-+ OSL_TRACE("ScVbaUserForm::Show() execute returned %d", aRet);
-+ if ( mbDispose )
-+ {
-+ try
-+ {
-+ uno::Reference< lang::XComponent > xComp( m_xDialog, uno::UNO_QUERY_THROW );
-+ m_xDialog = NULL;
-+ xComp->dispose();
-+ mbDispose = false;
-+ }
-+ catch( uno::Exception& )
-+ {
-+ }
-+ }
-+}
-+
-+rtl::OUString SAL_CALL
-+ScVbaUserForm::getCaption() throw (::com::sun::star::uno::RuntimeException)
-+{
-+ rtl::OUString sCaption;
-+ m_xProps->getPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("Title") ) ) >>= sCaption;
-+ return sCaption;
-+}
-+void
-+ScVbaUserForm::setCaption( const ::rtl::OUString& _caption ) throw (::com::sun::star::uno::RuntimeException)
-+{
-+ m_xProps->setPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("Title") ), uno::makeAny( _caption ) );
-+}
-+
-+void SAL_CALL
-+ScVbaUserForm::Hide( ) throw (uno::RuntimeException)
-+{
-+ mbDispose = false; // hide not dispose
-+ if ( m_xDialog.is() )
-+ m_xDialog->endExecute();
-+}
-+
-+void SAL_CALL
-+ScVbaUserForm::RePaint( ) throw (uno::RuntimeException)
-+{
-+ // do nothing
-+}
-+
-+void SAL_CALL
-+ScVbaUserForm::UnloadObject( ) throw (uno::RuntimeException)
-+{
-+ mbDispose = true;
-+ if ( m_xDialog.is() )
-+ m_xDialog->endExecute();
-+}
-+
-+rtl::OUString&
-+ScVbaUserForm::getServiceImplName()
-+{
-+ static rtl::OUString sImplName( RTL_CONSTASCII_USTRINGPARAM("ScVbaUserForm") );
-+ return sImplName;
-+}
-+
-+uno::Sequence< rtl::OUString >
-+ScVbaUserForm::getServiceNames()
-+{
-+ static uno::Sequence< rtl::OUString > aServiceNames;
-+ if ( aServiceNames.getLength() == 0 )
-+ {
-+ aServiceNames.realloc( 1 );
-+ aServiceNames[ 0 ] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.excel.UserForm" ) );
-+ }
-+ return aServiceNames;
-+}
-+
-+uno::Reference< beans::XIntrospectionAccess > SAL_CALL
-+ScVbaUserForm::getIntrospection( ) throw (uno::RuntimeException)
-+{
-+ return uno::Reference< beans::XIntrospectionAccess >();
-+}
-+
-+uno::Any SAL_CALL
-+ScVbaUserForm::invoke( const ::rtl::OUString& /*aFunctionName*/, const uno::Sequence< uno::Any >& /*aParams*/, uno::Sequence< ::sal_Int16 >& /*aOutParamIndex*/, uno::Sequence< uno::Any >& /*aOutParam*/ ) throw (lang::IllegalArgumentException, script::CannotConvertException, reflection::InvocationTargetException, uno::RuntimeException)
-+{
-+ throw uno::RuntimeException(); // unsupported operation
-+}
-+
-+void SAL_CALL
-+ScVbaUserForm::setValue( const ::rtl::OUString& aPropertyName, const uno::Any& aValue ) throw (beans::UnknownPropertyException, script::CannotConvertException, reflection::InvocationTargetException, uno::RuntimeException)
-+{
-+ uno::Any aObject = getValue( aPropertyName );
-+ // The Object *must* support XDefaultProperty here because getValue will
-+ // only return properties that are Objects ( e.g. controls )
-+ // e.g. Userform1.aControl = something
-+ // 'aControl' has to support XDefaultProperty to make sense here
-+ uno::Reference< script::XDefaultProperty > xDfltProp( aObject, uno::UNO_QUERY_THROW );
-+ rtl::OUString aDfltPropName = xDfltProp->getDefaultPropertyName();
-+ uno::Reference< beans::XIntrospectionAccess > xUnoAccess( getIntrospectionAccess( aObject ) );
-+ uno::Reference< beans::XPropertySet > xPropSet( xUnoAccess->queryAdapter( ::getCppuType( (const uno::Reference< beans::XPropertySet > *)0 ) ), uno::UNO_QUERY_THROW );
-+ xPropSet->setPropertyValue( aDfltPropName, aValue );
-+}
-+
-+uno::Any SAL_CALL
-+ScVbaUserForm::getValue( const ::rtl::OUString& aPropertyName ) throw (beans::UnknownPropertyException, uno::RuntimeException)
-+{
-+ uno::Reference< awt::XControl > xDialogControl( m_xDialog, uno::UNO_QUERY_THROW );
-+ uno::Reference< awt::XControlContainer > xContainer( m_xDialog, uno::UNO_QUERY_THROW );
-+ uno::Reference< awt::XControl > xControl = xContainer->getControl( aPropertyName );
-+ ScVbaControlFactory aFac( mxContext, xControl, m_xModel );
-+ uno::Reference< msforms::XControl > xVBAControl( aFac.createControl( xDialogControl->getModel() ) );
-+ ScVbaControl* pControl = dynamic_cast< ScVbaControl* >( xVBAControl.get() );
-+ pControl->setGeometryHelper( new UserFormGeometryHelper( mxContext, xControl ) );
-+ return uno::makeAny( xVBAControl );
-+}
-+
-+::sal_Bool SAL_CALL
-+ScVbaUserForm::hasMethod( const ::rtl::OUString& /*aName*/ ) throw (uno::RuntimeException)
-+{
-+ return sal_False;
-+}
-+uno::Any SAL_CALL
-+ScVbaUserForm::Controls( const uno::Any& index ) throw (uno::RuntimeException)
-+{
-+ uno::Reference< awt::XControl > xDialogControl( m_xDialog, uno::UNO_QUERY_THROW );
-+ uno::Reference< XCollection > xControls( new ScVbaControls( this, mxContext, xDialogControl ) );
-+ if ( index.hasValue() )
-+ return uno::makeAny( xControls->Item( index, uno::Any() ) );
-+ return uno::makeAny( xControls );
-+}
-+
-+::sal_Bool SAL_CALL
-+ScVbaUserForm::hasProperty( const ::rtl::OUString& aName ) throw (uno::RuntimeException)
-+{
-+ uno::Reference< awt::XControl > xControl( m_xDialog, uno::UNO_QUERY );
-+ OSL_TRACE("ScVbaUserForm::hasProperty(%s) %d", rtl::OUStringToOString( aName, RTL_TEXTENCODING_UTF8 ).getStr(), xControl.is() );
-+ if ( xControl.is() )
-+ {
-+ uno::Reference< container::XNameAccess > xNameAccess( xControl->getModel(), uno::UNO_QUERY_THROW );
-+ sal_Bool bRes = xNameAccess->hasByName( aName );
-+ OSL_TRACE("ScVbaUserForm::hasProperty(%s) %d ---> %d", rtl::OUStringToOString( aName, RTL_TEXTENCODING_UTF8 ).getStr(), xControl.is(), bRes );
-+ return bRes;
-+ }
-+ return sal_False;
-+}
-+
-+namespace userform
-+{
-+namespace sdecl = comphelper::service_decl;
-+sdecl::vba_service_class_<ScVbaUserForm, sdecl::with_args<true> > serviceImpl;
-+extern sdecl::ServiceDecl const serviceDecl(
-+ serviceImpl,
-+ "ScVbaUserForm",
-+ "ooo.vba.msforms.UserForm" );
-+}
-+
---- vbahelper/source/msforms/vbauserform.hxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ vbahelper/source/msforms/vbauserform.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,77 @@
-+/*************************************************************************
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile$
-+ *
-+ * $Revision$
-+ *
-+ * last change: $Author$ $Date$
-+ *
-+ * The Contents of this file are made available subject to
-+ * the terms of GNU Lesser General Public License Version 2.1.
-+ *
-+ *
-+ * GNU Lesser General Public License Version 2.1
-+ * =============================================
-+ * Copyright 2005 by Sun Microsystems, Inc.
-+ * 901 San Antonio Road, Palo Alto, CA 94303, USA
-+ *
-+ * This library is free software; you can redistribute it and/or
-+ * modify it under the terms of the GNU Lesser General Public
-+ * License version 2.1, as published by the Free Software Foundation.
-+ *
-+ * This library 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 for more details.
-+ *
-+ * You should have received a copy of the GNU Lesser General Public
-+ * License along with this library; if not, write to the Free Software
-+ * Foundation, Inc., 59 Temple Place, Suite 330, Boston,
-+ * MA 02111-1307 USA
-+ *
-+ ************************************************************************/
-+#ifndef SC_VBA_USERFORM_HXX
-+#define SC_VBA_USERFORM_HXX
-+
-+#include <cppuhelper/implbase1.hxx>
-+#include <ooo/vba/msforms/XUserForm.hpp>
-+#include <com/sun/star/awt/XDialog.hpp>
-+#include <com/sun/star/frame/XModel.hpp>
-+
-+#include <vbahelper/vbahelperinterface.hxx>
-+#include "vbacontrol.hxx"
-+
-+//typedef InheritedHelperInterfaceImpl1< ov::msforms::XUserForm > ScVbaUserForm_BASE;
-+typedef cppu::ImplInheritanceHelper1< ScVbaControl, ov::msforms::XUserForm > ScVbaUserForm_BASE;
-+
-+class ScVbaUserForm : public ScVbaUserForm_BASE
-+{
-+private:
-+ css::uno::Reference< css::awt::XDialog > m_xDialog;
-+ bool mbDispose;
-+protected:
-+public:
-+ ScVbaUserForm( css::uno::Sequence< css::uno::Any > const& aArgs, css::uno::Reference< css::uno::XComponentContext >const& xContext ) throw ( css::lang::IllegalArgumentException );
-+ virtual ~ScVbaUserForm();
-+ // XUserForm
-+ virtual void SAL_CALL RePaint( ) throw (css::uno::RuntimeException);
-+ virtual void SAL_CALL Show( ) throw (css::uno::RuntimeException);
-+ // XIntrospection
-+ virtual css::uno::Reference< css::beans::XIntrospectionAccess > SAL_CALL getIntrospection( ) throw (css::uno::RuntimeException);
-+ virtual css::uno::Any SAL_CALL invoke( const ::rtl::OUString& aFunctionName, const css::uno::Sequence< css::uno::Any >& aParams, css::uno::Sequence< ::sal_Int16 >& aOutParamIndex, css::uno::Sequence< css::uno::Any >& aOutParam ) throw (css::lang::IllegalArgumentException, css::script::CannotConvertException, css::reflection::InvocationTargetException, css::uno::RuntimeException);
-+ virtual void SAL_CALL setValue( const ::rtl::OUString& aPropertyName, const css::uno::Any& aValue ) throw (css::beans::UnknownPropertyException, css::script::CannotConvertException, css::reflection::InvocationTargetException, css::uno::RuntimeException);
-+ virtual css::uno::Any SAL_CALL getValue( const ::rtl::OUString& aPropertyName ) throw (css::beans::UnknownPropertyException, css::uno::RuntimeException);
-+ virtual ::sal_Bool SAL_CALL hasMethod( const ::rtl::OUString& aName ) throw (css::uno::RuntimeException);
-+ virtual ::sal_Bool SAL_CALL hasProperty( const ::rtl::OUString& aName ) throw (css::uno::RuntimeException);
-+ virtual ::rtl::OUString SAL_CALL getCaption() throw (::com::sun::star::uno::RuntimeException);
-+ virtual void SAL_CALL setCaption( const ::rtl::OUString& _caption ) throw (::com::sun::star::uno::RuntimeException);
-+ virtual void SAL_CALL Hide( ) throw (css::uno::RuntimeException);
-+ virtual void SAL_CALL UnloadObject( ) throw (css::uno::RuntimeException);
-+ virtual css::uno::Any SAL_CALL Controls( const css::uno::Any& index ) throw (css::uno::RuntimeException);
-+ //XHelperInterface
-+ virtual rtl::OUString& getServiceImplName();
-+ virtual css::uno::Sequence<rtl::OUString> getServiceNames();
-+};
-+#endif
---- vbahelper/source/vbahelper/makefile.mk.old 1970-01-01 00:00:00.000000000 +0000
-+++ vbahelper/source/vbahelper/makefile.mk 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,66 @@
-+#*************************************************************************
-+#
-+# DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+#
-+# Copyright 2008 by Sun Microsystems, Inc.
-+#
-+# OpenOffice.org - a multi-platform office productivity suite
-+#
-+# $RCSfile: makefile.mk,v $
-+#
-+# $Revision: 1.45 $
-+#
-+# 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.
-+#
-+#*************************************************************************
-+
-+PRJ=..$/../
-+PRJNAME=vbahelper
-+TARGET=vbahelper
-+
-+ENABLE_EXCEPTIONS := TRUE
-+
-+# --- Settings -----------------------------------------------------
-+
-+.INCLUDE : settings.mk
-+
-+SLOFILES=\
-+ $(SLO)$/vbahelper.obj \
-+ $(SLO)$/vbapropvalue.obj \
-+ $(SLO)$/vbacommandbars.obj \
-+ $(SLO)$/vbacommandbar.obj \
-+ $(SLO)$/vbacommandbarcontrols.obj \
-+ $(SLO)$/vbacommandbarcontrol.obj \
-+ $(SLO)$/vbaapplicationbase.obj \
-+ $(SLO)$/vbawindowbase.obj \
-+ $(SLO)$/vbadocumentbase.obj \
-+ $(SLO)$/vbaglobalbase.obj \
-+
-+# --- Targets -------------------------------------------------------
-+
-+.INCLUDE : target.mk
-+
-+ALLTAR : \
-+ $(MISC)$/$(TARGET).don \
-+
-+$(SLOFILES) : $(MISC)$/$(TARGET).don
-+
-+$(MISC)$/$(TARGET).don : $(SOLARBINDIR)$/oovbaapi.rdb
-+ +$(CPPUMAKER) -O$(INCCOM)$/$(TARGET) -BUCR $(SOLARBINDIR)$/oovbaapi.rdb -X$(SOLARBINDIR)$/types.rdb && echo > $@
-+ echo $@
-+
---- vbahelper/source/vbahelper/vbaapplicationbase.cxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ vbahelper/source/vbahelper/vbaapplicationbase.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,139 @@
-+/*************************************************************************
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile$
-+ *
-+ * $Revision$
-+ *
-+ * last change: $Author$ $Date$
-+ *
-+ * The Contents of this file are made available subject to
-+ * the terms of GNU Lesser General Public License Version 2.1.
-+ *
-+ *
-+ * GNU Lesser General Public License Version 2.1
-+ * =============================================
-+ * Copyright 2005 by Sun Microsystems, Inc.
-+ * 901 San Antonio Road, Palo Alto, CA 94303, USA
-+ *
-+ * This library is free software; you can redistribute it and/or
-+ * modify it under the terms of the GNU Lesser General Public
-+ * License version 2.1, as published by the Free Software Foundation.
-+ *
-+ * This library 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 for more details.
-+ *
-+ * You should have received a copy of the GNU Lesser General Public
-+ * License along with this library; if not, write to the Free Software
-+ * Foundation, Inc., 59 Temple Place, Suite 330, Boston,
-+ * MA 02111-1307 USA
-+ *
-+ ************************************************************************/
-+#include "vbahelper/vbaapplicationbase.hxx"
-+#include <com/sun/star/container/XIndexAccess.hpp>
-+#include <com/sun/star/frame/XLayoutManager.hpp>
-+
-+#include "vbacommandbars.hxx"
-+
-+using namespace com::sun::star;
-+using namespace ooo::vba;
-+
-+VbaApplicationBase::VbaApplicationBase( const uno::Reference< css::uno::XComponentContext >& xContext )
-+ : ApplicationBase_BASE( uno::Reference< XHelperInterface >(), xContext )
-+{
-+}
-+
-+VbaApplicationBase::~VbaApplicationBase()
-+{
-+}
-+
-+sal_Bool SAL_CALL
-+VbaApplicationBase::getScreenUpdating() throw (uno::RuntimeException)
-+{
-+ uno::Reference< frame::XModel > xModel( getCurrentDocument(), uno::UNO_QUERY_THROW );
-+ return !xModel->hasControllersLocked();
-+}
-+
-+void SAL_CALL
-+VbaApplicationBase::setScreenUpdating(sal_Bool bUpdate) throw (uno::RuntimeException)
-+{
-+ uno::Reference< frame::XModel > xModel( getCurrentDocument(), uno::UNO_QUERY_THROW );
-+ if (bUpdate)
-+ xModel->unlockControllers();
-+ else
-+ xModel->lockControllers();
-+}
-+
-+sal_Bool SAL_CALL
-+VbaApplicationBase::getDisplayStatusBar() throw (uno::RuntimeException)
-+{
-+ uno::Reference< frame::XModel > xModel( getCurrentDocument(), uno::UNO_QUERY_THROW );
-+ uno::Reference< frame::XFrame > xFrame( xModel->getCurrentController()->getFrame(), uno::UNO_QUERY_THROW );
-+ uno::Reference< beans::XPropertySet > xProps( xFrame, uno::UNO_QUERY_THROW );
-+
-+ if( xProps.is() ){
-+ uno::Reference< frame::XLayoutManager > xLayoutManager( xProps->getPropertyValue( rtl::OUString(RTL_CONSTASCII_USTRINGPARAM("LayoutManager")) ), uno::UNO_QUERY_THROW );
-+ rtl::OUString url(RTL_CONSTASCII_USTRINGPARAM( "private:resource/statusbar/statusbar" ));
-+ if( xLayoutManager.is() && xLayoutManager->isElementVisible( url ) ){
-+ return sal_True;
-+ }
-+ }
-+ return sal_False;
-+}
-+
-+void SAL_CALL
-+VbaApplicationBase::setDisplayStatusBar(sal_Bool bDisplayStatusBar) throw (uno::RuntimeException)
-+{
-+ uno::Reference< frame::XModel > xModel( getCurrentDocument(), uno::UNO_QUERY_THROW );
-+ uno::Reference< frame::XFrame > xFrame( xModel->getCurrentController()->getFrame(), uno::UNO_QUERY_THROW );
-+ uno::Reference< beans::XPropertySet > xProps( xFrame, uno::UNO_QUERY_THROW );
-+
-+ if( xProps.is() ){
-+ uno::Reference< frame::XLayoutManager > xLayoutManager( xProps->getPropertyValue( rtl::OUString(RTL_CONSTASCII_USTRINGPARAM("LayoutManager")) ), uno::UNO_QUERY_THROW );
-+ rtl::OUString url(RTL_CONSTASCII_USTRINGPARAM( "private:resource/statusbar/statusbar" ));
-+ if( xLayoutManager.is() ){
-+ if( bDisplayStatusBar && !xLayoutManager->isElementVisible( url ) ){
-+ if( !xLayoutManager->showElement( url ) )
-+ xLayoutManager->createElement( url );
-+ return;
-+ }
-+ else if( !bDisplayStatusBar && xLayoutManager->isElementVisible( url ) ){
-+ xLayoutManager->hideElement( url );
-+ return;
-+ }
-+ }
-+ }
-+ return;
-+}
-+
-+uno::Any SAL_CALL
-+VbaApplicationBase::CommandBars( const uno::Any& aIndex ) throw (uno::RuntimeException)
-+{
-+ uno::Reference< XCommandBars > xCommandBars( new ScVbaCommandBars( this, mxContext, uno::Reference< container::XIndexAccess >() ) );
-+ if( aIndex.hasValue() )
-+ return uno::makeAny( xCommandBars->Item( aIndex, uno::Any() ) );
-+ return uno::makeAny( xCommandBars );
-+}
-+
-+rtl::OUString&
-+VbaApplicationBase::getServiceImplName()
-+{
-+ static rtl::OUString sImplName( RTL_CONSTASCII_USTRINGPARAM("VbaApplicationBase") );
-+ return sImplName;
-+}
-+uno::Sequence<rtl::OUString>
-+VbaApplicationBase::getServiceNames()
-+{
-+ static uno::Sequence< rtl::OUString > aServiceNames;
-+ if ( aServiceNames.getLength() == 0 )
-+ {
-+ aServiceNames.realloc( 1 );
-+ aServiceNames[ 0 ] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.VbaApplicationBase" ) );
-+ }
-+ return aServiceNames;
-+}
-+
-+
---- vbahelper/source/vbahelper/vbacommandbar.cxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ vbahelper/source/vbahelper/vbacommandbar.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,346 @@
-+/*************************************************************************
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile$
-+ *
-+ * $Revision$
-+ *
-+ * last change: $Author$ $Date$
-+ *
-+ * The Contents of this file are made available subject to
-+ * the terms of GNU Lesser General Public License Version 2.1.
-+ *
-+ *
-+ * GNU Lesser General Public License Version 2.1
-+ * =============================================
-+ * Copyright 2005 by Sun Microsystems, Inc.
-+ * 901 San Antonio Road, Palo Alto, CA 94303, USA
-+ *
-+ * This library is free software; you can redistribute it and/or
-+ * modify it under the terms of the GNU Lesser General Public
-+ * License version 2.1, as published by the Free Software Foundation.
-+ *
-+ * This library 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 for more details.
-+ *
-+ * You should have received a copy of the GNU Lesser General Public
-+ * License along with this library; if not, write to the Free Software
-+ * Foundation, Inc., 59 Temple Place, Suite 330, Boston,
-+ * MA 02111-1307 USA
-+ *
-+ ************************************************************************/
-+#include <com/sun/star/ui/XModuleUIConfigurationManagerSupplier.hpp>
-+#include <com/sun/star/frame/XFrame.hpp>
-+#include <com/sun/star/frame/XDesktop.hpp>
-+#include <com/sun/star/frame/XLayoutManager.hpp>
-+#include <com/sun/star/beans/XPropertySet.hpp>
-+#include <com/sun/star/container/XNameContainer.hpp>
-+#include <ooo/vba/office/MsoBarType.hpp>
-+
-+#include "vbacommandbar.hxx"
-+#include "vbacommandbarcontrols.hxx"
-+
-+using namespace com::sun::star;
-+using namespace ooo::vba;
-+
-+ScVbaCommandBar::ScVbaCommandBar( const uno::Reference< XHelperInterface > xParent, const uno::Reference< uno::XComponentContext > xContext, sal_Int32 nModuleType ) throw (uno::RuntimeException) : CommandBar_BASE( xParent, xContext )
-+{
-+ // it's a menu bar
-+ // only supporting factory menus ( no custom menus )
-+ m_xParentHardRef.set( xParent, uno::UNO_QUERY_THROW );
-+ initCommandBar();
-+ switch( nModuleType )
-+ {
-+ case 0:
-+ m_sMenuModuleName = rtl::OUString::createFromAscii( "com.sun.star.sheet.SpreadsheetDocument" );
-+ break;
-+ case 1:
-+ m_sMenuModuleName = rtl::OUString::createFromAscii( "com.sun.star.text.TextDocument" );
-+ break;
-+ default:
-+ m_sMenuModuleName = rtl::OUString::createFromAscii( "com.sun.star.text.TextDocument" );
-+ }
-+ getMenuSettings();
-+ m_bIsMenu = sal_True;
-+ m_bCustom = sal_False;
-+}
-+ScVbaCommandBar::ScVbaCommandBar( const uno::Reference< XHelperInterface > xParent, const uno::Reference< uno::XComponentContext > xContext, rtl::OUString sToolBarName, sal_Bool bTemporary, sal_Bool bCreate ) throw (uno::RuntimeException) : CommandBar_BASE( xParent, xContext )
-+{
-+ // it's a tool bar
-+ m_xParentHardRef.set( xParent, uno::UNO_QUERY_THROW );
-+ initCommandBar();
-+ m_bTemporary = bTemporary;
-+ m_bCreate = bCreate;
-+ // get OOo ToolBarName
-+ CommandBarNameMap::const_iterator iter = mCommandBarNameMap.find( sToolBarName.toAsciiLowerCase() );
-+ if( iter != mCommandBarNameMap.end() )
-+ {
-+ m_sToolBarName = iter->second;
-+ }
-+ else
-+ {
-+ m_sToolBarName = sToolBarName;
-+ }
-+ m_sUIName = m_sToolBarName;
-+ m_bIsMenu = sal_False;
-+ getToolBarSettings( m_sToolBarName );
-+}
-+void
-+ScVbaCommandBar::initCommandBar() throw (uno::RuntimeException)
-+{
-+ m_pScVbaCommandBars = dynamic_cast< ScVbaCommandBars* >( m_xParentHardRef.get() );
-+ if ( !m_pScVbaCommandBars )
-+ throw uno::RuntimeException( rtl::OUString::createFromAscii( "Parent needs to be a ScVbaCommandBars"), uno::Reference< uno::XInterface >() );
-+ m_bIsMenu = sal_False;
-+ m_bCustom = sal_False;
-+ m_bTemporary = sal_True;
-+ m_sToolBarName = rtl::OUString::createFromAscii("");
-+ m_sUIName = rtl::OUString::createFromAscii("");
-+ m_sMenuModuleName = m_pScVbaCommandBars->GetModuleName();
-+}
-+void
-+ScVbaCommandBar::getToolBarSettings( rtl::OUString sToolBarName ) throw( uno::RuntimeException )
-+{
-+ rtl::OUString sFactoryToolBar = rtl::OUString::createFromAscii("private:resource/toolbar/") + sToolBarName.toAsciiLowerCase();
-+ rtl::OUString sCustomToolBar = rtl::OUString::createFromAscii("private:resource/toolbar/custom_toolbar_") + sToolBarName;
-+ uno::Reference< lang::XMultiServiceFactory > xMSF( mxContext->getServiceManager(), uno::UNO_QUERY_THROW );
-+ uno::Reference< ui::XModuleUIConfigurationManagerSupplier > xUICfgManagerSup( xMSF->createInstance(rtl::OUString::createFromAscii("com.sun.star.ui.ModuleUIConfigurationManagerSupplier") ), uno::UNO_QUERY_THROW );
-+ m_xUICfgManager.set( xUICfgManagerSup->getUIConfigurationManager( m_pScVbaCommandBars->GetModuleName() ), uno::UNO_QUERY_THROW );
-+ m_xUICfgPers.set( m_xUICfgManager, uno::UNO_QUERY_THROW );
-+ if( m_xUICfgManager->hasSettings( sFactoryToolBar ) )
-+ {
-+ // exsiting standard ToolBar
-+ m_xBarSettings.set( m_xUICfgManager->getSettings( sFactoryToolBar, sal_True ), uno::UNO_QUERY_THROW );
-+ m_sToolBarName = sFactoryToolBar;
-+ }
-+ else if( m_xUICfgManager->hasSettings( sCustomToolBar ) )
-+ {
-+ // exisiting custom ToolBar
-+ m_xBarSettings.set( m_xUICfgManager->getSettings( sCustomToolBar, sal_True ), uno::UNO_QUERY_THROW );
-+ m_sToolBarName = sCustomToolBar;
-+ m_bCustom = sal_True;
-+ }
-+ else if( m_bCreate )
-+ {
-+ // new custom ToolBar
-+ m_xBarSettings.set( m_xUICfgManager->createSettings(), uno::UNO_QUERY_THROW );
-+ m_sToolBarName = sCustomToolBar;
-+ m_bCustom = sal_True;
-+ addCustomBar();
-+ }
-+ else
-+ throw uno::RuntimeException( rtl::OUString::createFromAscii("ToolBar do not exist"), uno::Reference< uno::XInterface >() );
-+ if( m_pScVbaCommandBars->GetWindows()->hasByName( m_sToolBarName ) )
-+ {
-+ uno::Any aToolBar = m_pScVbaCommandBars->GetWindows()->getByName( m_sToolBarName );
-+ aToolBar >>= m_aToolBar;
-+ }
-+}
-+void
-+ScVbaCommandBar::addCustomBar()
-+{
-+ uno::Reference< beans::XPropertySet > xPropertySet( m_xBarSettings, uno::UNO_QUERY_THROW );
-+ xPropertySet->setPropertyValue(rtl::OUString::createFromAscii("UIName"), uno::makeAny( m_sUIName ));
-+
-+ if( m_xUICfgManager->hasSettings(m_sToolBarName) )
-+ {
-+ m_xUICfgManager->replaceSettings( m_sToolBarName, uno::Reference< container::XIndexAccess > (m_xBarSettings, uno::UNO_QUERY_THROW ) );
-+ }
-+ else
-+ {
-+ m_xUICfgManager->insertSettings( m_sToolBarName, uno::Reference< container::XIndexAccess > (m_xBarSettings, uno::UNO_QUERY_THROW ) );
-+ }
-+ if( !m_bTemporary )
-+ {
-+ m_xUICfgPers->store();
-+ }
-+}
-+void
-+ScVbaCommandBar::getMenuSettings()
-+{
-+ try
-+ {
-+ rtl::OUString sMenuBar = rtl::OUString::createFromAscii( "private:resource/menubar/menubar" );
-+ uno::Reference< lang::XMultiServiceFactory > xMSF( mxContext->getServiceManager(), uno::UNO_QUERY_THROW );
-+ uno::Reference< ui::XModuleUIConfigurationManagerSupplier > xUICfgManagerSup( xMSF->createInstance(rtl::OUString::createFromAscii("com.sun.star.ui.ModuleUIConfigurationManagerSupplier") ), uno::UNO_QUERY_THROW );
-+ m_xUICfgManager.set( xUICfgManagerSup->getUIConfigurationManager( m_sMenuModuleName ), uno::UNO_QUERY_THROW );
-+ m_xUICfgPers.set( m_xUICfgManager, uno::UNO_QUERY_THROW );
-+ m_xBarSettings.set( m_xUICfgManager->getSettings( sMenuBar, sal_True ), uno::UNO_QUERY_THROW );
-+ }
-+ catch ( uno::Exception e)
-+ {
-+ OSL_TRACE( "getMenuSetting got a error\n" );
-+ }
-+}
-+::rtl::OUString SAL_CALL
-+ScVbaCommandBar::getName() throw ( uno::RuntimeException )
-+{
-+ // This will get a "NULL length string" when Name is not set.
-+ uno::Reference< beans::XPropertySet > xPropertySet( m_xBarSettings, uno::UNO_QUERY_THROW );
-+ uno::Any aName = xPropertySet->getPropertyValue( rtl::OUString::createFromAscii("UIName") );
-+ rtl::OUString sName;
-+ aName >>= sName;
-+ if( sName.getLength() < 1 && !m_bIsMenu )
-+ {
-+ uno::Reference< container::XNameAccess > xNameAccess( m_pScVbaCommandBars->GetWindows(), uno::UNO_QUERY_THROW );
-+ if( xNameAccess->hasByName( m_sToolBarName ) )
-+ {
-+ beans::PropertyValues aToolBar;
-+ xNameAccess->getByName( m_sToolBarName ) >>= aToolBar;
-+ sal_Int32 nCount = aToolBar.getLength();
-+ beans::PropertyValue aPropertyValue;
-+ for( sal_Int32 i = 0; i < nCount; i++ )
-+ {
-+ aPropertyValue = aToolBar[i];
-+ if( aPropertyValue.Name.equals( rtl::OUString::createFromAscii("UIName") ) )
-+ {
-+ aPropertyValue.Value >>= sName;
-+ return sName;
-+ }
-+ }
-+ }
-+ }
-+ return sName;
-+}
-+void SAL_CALL
-+ScVbaCommandBar::setName( const ::rtl::OUString& _name ) throw (uno::RuntimeException)
-+{
-+ uno::Reference< beans::XPropertySet > xPropertySet( m_xBarSettings, uno::UNO_QUERY_THROW );
-+ xPropertySet->setPropertyValue( rtl::OUString::createFromAscii("UIName"), uno::makeAny( _name ) );
-+ uno::Reference< container::XIndexAccess > xIndexAccess( m_xBarSettings, uno::UNO_QUERY_THROW );
-+
-+ if( m_xUICfgManager->hasSettings( m_sToolBarName ) )
-+ {
-+ m_xUICfgManager->replaceSettings( m_sToolBarName, xIndexAccess );
-+ }
-+ else
-+ {
-+ // toolbar not found
-+ }
-+ if( !m_bTemporary )
-+ {
-+ m_xUICfgPers->store();
-+ }
-+}
-+::sal_Bool SAL_CALL
-+ScVbaCommandBar::getVisible() throw (uno::RuntimeException)
-+{
-+ sal_Bool bVisible = sal_False;
-+ try
-+ {
-+ sal_Int32 i = 0;
-+ while( !m_aToolBar[i].Name.equals( rtl::OUString::createFromAscii( "Visible" ) ) )
-+ {
-+ i++;
-+ }
-+ m_aToolBar[i].Value >>= bVisible;
-+ }
-+ catch ( uno::Exception e )
-+ {
-+ }
-+ return bVisible;
-+}
-+void SAL_CALL
-+ScVbaCommandBar::setVisible( ::sal_Bool _visible ) throw (uno::RuntimeException)
-+{
-+ try
-+ {
-+ uno::Reference< frame::XFrame > xFrame( getCurrentDocument()->getCurrentController()->getFrame(), uno::UNO_QUERY_THROW );
-+ uno::Reference< beans::XPropertySet > xPropertySet( xFrame, uno::UNO_QUERY_THROW );
-+ uno::Reference< frame::XLayoutManager > xLayoutManager( xPropertySet->getPropertyValue( rtl::OUString::createFromAscii("LayoutManager") ), uno::UNO_QUERY_THROW );
-+ if( _visible )
-+ {
-+ xLayoutManager->createElement( m_sToolBarName );
-+ xLayoutManager->showElement( m_sToolBarName );
-+ }
-+ else
-+ {
-+ xLayoutManager->hideElement( m_sToolBarName );
-+ xLayoutManager->destroyElement( m_sToolBarName );
-+ }
-+ }
-+ catch( uno::Exception e )
-+ {
-+ OSL_TRACE( "SetVisible get an exception\n" );
-+ }
-+}
-+void SAL_CALL
-+ScVbaCommandBar::Delete( ) throw (css::script::BasicErrorException, css::uno::RuntimeException)
-+{
-+ if( m_bCustom )
-+ {
-+ if( m_xUICfgManager->hasSettings( m_sToolBarName ) )
-+ {
-+ m_xUICfgManager->removeSettings(m_sToolBarName);
-+ // make it permanent
-+ if( !m_bTemporary )
-+ {
-+ m_xUICfgPers->store();
-+ }
-+ }
-+ else
-+ {
-+ // toolbar not found
-+ // TODO throw Error
-+ }
-+ uno::Reference< container::XNameContainer > xNameContainer( m_pScVbaCommandBars->GetWindows(), uno::UNO_QUERY_THROW );
-+ if( xNameContainer->hasByName( m_sToolBarName ) )
-+ {
-+ xNameContainer->removeByName( m_sToolBarName );
-+ }
-+ }
-+}
-+uno::Any SAL_CALL
-+ScVbaCommandBar::Controls( const uno::Any& aIndex ) throw (script::BasicErrorException, uno::RuntimeException)
-+{
-+ sal_Int32 nIndex;
-+ uno::Reference< XCommandBarControls > xCommandBarControls( new ScVbaCommandBarControls( this, mxContext, uno::Reference< container::XIndexAccess >() ) );
-+ if( aIndex.hasValue() )
-+ {
-+ if( aIndex >>= nIndex )
-+ {
-+ uno::Reference< XCommandBarControl > xCommandBarControl( xCommandBarControls->Item( aIndex, uno::Any() ), uno::UNO_QUERY_THROW );
-+ return uno::makeAny( xCommandBarControl );
-+ }
-+ else
-+ throw uno::RuntimeException( rtl::OUString::createFromAscii( "invalid index" ), uno::Reference< uno::XInterface >() );
-+ }
-+ return uno::makeAny( xCommandBarControls );
-+}
-+
-+sal_Int32 SAL_CALL
-+ScVbaCommandBar::Type() throw (script::BasicErrorException, uno::RuntimeException)
-+{
-+ // #FIXME support msoBarTypePopup
-+ sal_Int32 nType = office::MsoBarType::msoBarTypePopup;
-+ nType = m_bIsMenu? office::MsoBarType::msoBarTypeNormal : office::MsoBarType::msoBarTypeMenuBar;
-+ return nType;
-+}
-+
-+uno::Any SAL_CALL
-+ScVbaCommandBar::FindControl( const uno::Any& /*aType*/, const uno::Any& /*aId*/, const uno::Any& /*aTag*/, const uno::Any& /*aVisible*/, const uno::Any& /*aRecursive*/ ) throw (script::BasicErrorException, uno::RuntimeException)
-+{
-+ // alwayse fail to find control
-+ return uno::makeAny( uno::Reference< XCommandBarControl > () );
-+}
-+
-+rtl::OUString&
-+ScVbaCommandBar::getServiceImplName()
-+{
-+ static rtl::OUString sImplName( RTL_CONSTASCII_USTRINGPARAM("ScVbaCommandBar") );
-+ return sImplName;
-+}
-+uno::Sequence<rtl::OUString>
-+ScVbaCommandBar::getServiceNames()
-+{
-+ static uno::Sequence< rtl::OUString > aServiceNames;
-+ if ( aServiceNames.getLength() == 0 )
-+ {
-+ aServiceNames.realloc( 1 );
-+ aServiceNames[ 0 ] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.CommandBar" ) );
-+ }
-+ return aServiceNames;
-+}
---- vbahelper/source/vbahelper/vbacommandbar.hxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ vbahelper/source/vbahelper/vbacommandbar.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,107 @@
-+/*************************************************************************
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile$
-+ *
-+ * $Revision$
-+ *
-+ * last change: $Author$ $Date$
-+ *
-+ * The Contents of this file are made available subject to
-+ * the terms of GNU Lesser General Public License Version 2.1.
-+ *
-+ *
-+ * GNU Lesser General Public License Version 2.1
-+ * =============================================
-+ * Copyright 2005 by Sun Microsystems, Inc.
-+ * 901 San Antonio Road, Palo Alto, CA 94303, USA
-+ *
-+ * This library is free software; you can redistribute it and/or
-+ * modify it under the terms of the GNU Lesser General Public
-+ * License version 2.1, as published by the Free Software Foundation.
-+ *
-+ * This library 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 for more details.
-+ *
-+ * You should have received a copy of the GNU Lesser General Public
-+ * License along with this library; if not, write to the Free Software
-+ * Foundation, Inc., 59 Temple Place, Suite 330, Boston,
-+ * MA 02111-1307 USA
-+ *
-+ ************************************************************************/
-+#ifndef SC_VBA_COMMANDBAR_HXX
-+#define SC_VBA_COMMANDBAR_HXX
-+
-+#include <ooo/vba/XCommandBar.hpp>
-+#include <com/sun/star/ui/XUIConfigurationManager.hpp>
-+#include <com/sun/star/ui/XUIConfigurationPersistence.hpp>
-+#include <com/sun/star/container/XIndexContainer.hpp>
-+#include <com/sun/star/beans/PropertyValues.hpp>
-+
-+#include <vbahelper/vbahelperinterface.hxx>
-+#include "vbacommandbars.hxx"
-+
-+#include <map>
-+typedef std::map< const rtl::OUString, rtl::OUString > CommandBarNameMap;
-+typedef std::pair< const rtl::OUString, rtl::OUString > CommandBarNamePair;
-+const CommandBarNamePair namePair[] = {
-+ CommandBarNamePair( rtl::OUString::createFromAscii("standard"), rtl::OUString::createFromAscii("standardbar") ),
-+ CommandBarNamePair( rtl::OUString::createFromAscii("formatting"), rtl::OUString::createFromAscii("formatobjectbar") ),
-+};
-+static const CommandBarNameMap mCommandBarNameMap( namePair, ( namePair + sizeof(namePair) / sizeof(namePair[0]) ) );
-+
-+
-+typedef InheritedHelperInterfaceImpl1< ov::XCommandBar > CommandBar_BASE;
-+
-+class ScVbaCommandBar : public CommandBar_BASE
-+{
-+private:
-+ rtl::OUString m_sToolBarName;
-+ rtl::OUString m_sMenuModuleName;
-+ rtl::OUString m_sUIName;
-+ sal_Bool m_bTemporary;
-+ sal_Bool m_bIsMenu;
-+ sal_Bool m_bCustom;
-+ sal_Bool m_bCreate;
-+ ScVbaCommandBars* m_pScVbaCommandBars;
-+ css::beans::PropertyValues m_aToolBar;
-+ // hard reference for parent
-+ css::uno::Reference< ov::XHelperInterface > m_xParentHardRef;
-+ css::uno::Reference< css::ui::XUIConfigurationManager > m_xUICfgManager;
-+ css::uno::Reference< css::ui::XUIConfigurationPersistence > m_xUICfgPers;
-+ css::uno::Reference< css::container::XIndexContainer > m_xBarSettings;
-+ void initCommandBar() throw( css::uno::RuntimeException );
-+protected:
-+ void getToolBarSettings( rtl::OUString sToolBarName ) throw( css::uno::RuntimeException );
-+ void getMenuSettings();
-+ void addCustomBar();
-+public:
-+ ScVbaCommandBar( const css::uno::Reference< ov::XHelperInterface > xParent, const css::uno::Reference< css::uno::XComponentContext > xContext, sal_Int32 nModuleType ) throw( css::uno::RuntimeException );
-+ ScVbaCommandBar( const css::uno::Reference< ov::XHelperInterface > xParent, const css::uno::Reference< css::uno::XComponentContext > xContext, rtl::OUString sToolBarName, sal_Bool bTemporary, sal_Bool bCreate ) throw( css::uno::RuntimeException );
-+
-+ sal_Bool IsMenu() { return m_bIsMenu; };
-+ css::uno::Reference< css::ui::XUIConfigurationManager > GetUICfgManager() { return m_xUICfgManager; };
-+ css::uno::Reference< css::ui::XUIConfigurationPersistence > GetUICfgPers() { return m_xUICfgPers; };
-+ css::uno::Reference< css::container::XIndexContainer > GetBarSettings() { return m_xBarSettings; };
-+ rtl::OUString GetToolBarName() { return m_sToolBarName; };
-+
-+ // Attributes
-+ virtual ::rtl::OUString SAL_CALL getName() throw (css::uno::RuntimeException);
-+ virtual void SAL_CALL setName( const ::rtl::OUString& _name ) throw (css::uno::RuntimeException);
-+ virtual ::sal_Bool SAL_CALL getVisible() throw (css::uno::RuntimeException);
-+ virtual void SAL_CALL setVisible( ::sal_Bool _visible ) throw (css::uno::RuntimeException);
-+
-+ // Methods
-+ virtual void SAL_CALL Delete( ) throw (css::script::BasicErrorException, css::uno::RuntimeException);
-+ virtual css::uno::Any SAL_CALL Controls( const css::uno::Any& aIndex ) throw (css::script::BasicErrorException, css::uno::RuntimeException);
-+ virtual sal_Int32 SAL_CALL Type( ) throw (css::script::BasicErrorException, css::uno::RuntimeException);
-+ virtual css::uno::Any SAL_CALL FindControl( const css::uno::Any& aType, const css::uno::Any& aId, const css::uno::Any& aTag, const css::uno::Any& aVisible, const css::uno::Any& aRecursive ) throw (css::script::BasicErrorException, css::uno::RuntimeException);
-+
-+ // XHelperInterface
-+ virtual rtl::OUString& getServiceImplName();
-+ virtual css::uno::Sequence<rtl::OUString> getServiceNames();
-+};
-+#endif//SC_VBA_COMMANDBAR_HXX
---- vbahelper/source/vbahelper/vbacommandbarcontrol.cxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ vbahelper/source/vbahelper/vbacommandbarcontrol.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,453 @@
-+/*************************************************************************
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile$
-+ *
-+ * $Revision$
-+ *
-+ * last change: $Author$ $Date$
-+ *
-+ * The Contents of this file are made available subject to
-+ * the terms of GNU Lesser General Public License Version 2.1.
-+ *
-+ *
-+ * GNU Lesser General Public License Version 2.1
-+ * =============================================
-+ * Copyright 2005 by Sun Microsystems, Inc.
-+ * 901 San Antonio Road, Palo Alto, CA 94303, USA
-+ *
-+ * This library is free software; you can redistribute it and/or
-+ * modify it under the terms of the GNU Lesser General Public
-+ * License version 2.1, as published by the Free Software Foundation.
-+ *
-+ * This library 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 for more details.
-+ *
-+ * You should have received a copy of the GNU Lesser General Public
-+ * License along with this library; if not, write to the Free Software
-+ * Foundation, Inc., 59 Temple Place, Suite 330, Boston,
-+ * MA 02111-1307 USA
-+ *
-+ ************************************************************************/
-+#include "vbacommandbarcontrol.hxx"
-+#include <basic/sbstar.hxx>
-+#include <basic/sbmod.hxx>
-+#include <basic/sbmeth.hxx>
-+
-+using namespace com::sun::star;
-+using namespace ooo::vba;
-+
-+uno::Any lcl_getPropertyValue( beans::PropertyValues aPropertyValues, rtl::OUString sPropertyName )
-+{
-+ sal_Int32 nCount = aPropertyValues.getLength();
-+ for( sal_Int32 i = 0; i < nCount; i++ )
-+ {
-+ if( aPropertyValues[i].Name.equalsIgnoreAsciiCase( sPropertyName ) )
-+ {
-+ return aPropertyValues[i].Value;
-+ }
-+ }
-+ return uno::Any();
-+}
-+
-+beans::PropertyValues lcl_repalcePropertyValue( beans::PropertyValues aPropertyValues, rtl::OUString sPropertyName, uno::Any aValue )
-+{
-+ sal_Int32 nCount = aPropertyValues.getLength();
-+ for( sal_Int32 i = 0; i < nCount; i++ )
-+ {
-+ if( aPropertyValues[i].Name.equalsIgnoreAsciiCase( sPropertyName ) )
-+ {
-+ aPropertyValues[i].Value = aValue;
-+ return aPropertyValues;
-+ }
-+ }
-+ return aPropertyValues;
-+}
-+
-+ScVbaCommandBarControl::ScVbaCommandBarControl( const uno::Reference< XHelperInterface > xParent, const uno::Reference< uno::XComponentContext > xContext, rtl::OUString sName, sal_Int32 nPosition, sal_Int32 nType ) throw (uno::RuntimeException) : CommandBarControl_BASE( xParent, xContext ), m_sName( sName ), m_nPosition( nPosition ), m_nType( nType )
-+{
-+ // exsiting CommandBarBarControl
-+ m_xParentHardRef.set( xParent, uno::UNO_QUERY_THROW );
-+ initObjects();
-+ if( m_xBarSettings->hasElements() )
-+ {
-+ ScVbaCommandBarControl* pParentCommandBarControl = m_pCommandBarControls->GetParentCommandBarControl();
-+ if( pParentCommandBarControl )
-+ {
-+ beans::PropertyValues aPropertyValues;
-+ pParentCommandBarControl->GetCurrentSettings()->getByIndex( pParentCommandBarControl->GetPosition() ) >>= aPropertyValues;
-+ pParentCommandBarControl->SetPropertyValues( aPropertyValues );
-+ m_xCurrentSettings.set( lcl_getPropertyValue( pParentCommandBarControl->GetPropertyValues(), rtl::OUString::createFromAscii( "ItemDescriptorContainer" ) ), uno::UNO_QUERY_THROW );
-+ }
-+ if( !m_xCurrentSettings.is() )
-+ {
-+ m_xCurrentSettings.set( m_xUICfgManager->getSettings( m_pCommandBarControls->GetParentToolBarName(), sal_True ), uno::UNO_QUERY_THROW );
-+ }
-+ }
-+ if( m_bIsMenu )
-+ {
-+ m_sBarName = rtl::OUString::createFromAscii("private:resource/menubar/menubar");
-+ }
-+ else
-+ {
-+ m_sBarName = m_pCommandBarControls->GetParentToolBarName();
-+ }
-+ m_bTemporary = sal_True;
-+}
-+ScVbaCommandBarControl::ScVbaCommandBarControl( const uno::Reference< XHelperInterface > xParent, const uno::Reference< uno::XComponentContext > xContext, rtl::OUString sName, sal_Int32 nPosition, sal_Bool bTemporary, sal_Int32 nType) throw (uno::RuntimeException) : CommandBarControl_BASE( xParent, xContext ), m_nPosition( nPosition ), m_bTemporary( bTemporary ), m_nType( nType )
-+{
-+ m_xParentHardRef.set( xParent, uno::UNO_QUERY_THROW );
-+ initObjects();
-+ if( sName.getLength() > 0 )
-+ {
-+ m_sName = sName;
-+ }
-+ m_sCommand = rtl::OUString::createFromAscii("vnd.openoffice.org:") + sName;
-+ if( m_bIsMenu )
-+ {
-+ m_sBarName = rtl::OUString::createFromAscii("private:resource/menubar/menubar");
-+ createNewMenuBarControl();
-+ }
-+ else
-+ {
-+ m_sBarName = m_pCommandBarControls->GetParentToolBarName();
-+ createNewToolBarControl();
-+ }
-+}
-+
-+void
-+ScVbaCommandBarControl::initObjects() throw (uno::RuntimeException)
-+{
-+ m_pCommandBarControls = dynamic_cast< ScVbaCommandBarControls* >( m_xParentHardRef.get() );
-+ if( !m_pCommandBarControls )
-+ throw uno::RuntimeException( rtl::OUString::createFromAscii( "Parent needs to be a ScVbaCommandBarControls"), uno::Reference< uno::XInterface >() );
-+ m_xUICfgManager.set( m_pCommandBarControls->GetUICfgManager(), uno::UNO_QUERY_THROW );
-+ m_xUICfgPers.set( m_pCommandBarControls->GetUICfgPers(), uno::UNO_QUERY_THROW );
-+ m_xBarSettings.set( m_pCommandBarControls->GetBarSettings(), uno::UNO_QUERY_THROW );
-+ m_bIsMenu = m_pCommandBarControls->IsMenu();
-+ m_sName = rtl::OUString::createFromAscii( "Custom" );
-+}
-+
-+void
-+ScVbaCommandBarControl::createNewMenuBarControl()
-+{
-+ uno::Reference< lang::XSingleComponentFactory > xMenuMSF( m_xBarSettings, uno::UNO_QUERY_THROW );
-+
-+ uno::Sequence< beans::PropertyValue > aPropertys;
-+ if( m_nType == office::MsoControlType::msoControlPopup )
-+ aPropertys = uno::Sequence< beans::PropertyValue >( 4 );
-+ else
-+ aPropertys = uno::Sequence< beans::PropertyValue >( 3 );
-+
-+ aPropertys[0].Name = rtl::OUString::createFromAscii("CommandURL");
-+ aPropertys[0].Value <<= m_sCommand;
-+ aPropertys[1].Name = rtl::OUString::createFromAscii("Label");
-+ aPropertys[1].Value <<= m_sName;
-+ aPropertys[2].Name = rtl::OUString::createFromAscii("Type");
-+ aPropertys[2].Value <<= sal_Int32(0);
-+
-+ if( m_nType == office::MsoControlType::msoControlPopup )
-+ {
-+ aPropertys[3].Name = rtl::OUString::createFromAscii("ItemDescriptorContainer");
-+ aPropertys[3].Value <<= xMenuMSF->createInstanceWithContext( mxContext );
-+ }
-+
-+ if( m_pCommandBarControls->GetParentCommandBar() != NULL )
-+ {
-+ // create a new menu
-+ m_xBarSettings->insertByIndex( m_nPosition, uno::makeAny( aPropertys ) );
-+ m_xCurrentSettings.set( m_xBarSettings, uno::UNO_QUERY_THROW );
-+ }
-+ else if( m_pCommandBarControls->GetParentCommandBarControl() != NULL )
-+ {
-+ // create a new menu entry
-+ ScVbaCommandBarControl* pPc = m_pCommandBarControls->GetParentCommandBarControl();
-+ beans::PropertyValues aPropertyValues;
-+ pPc->GetCurrentSettings()->getByIndex( pPc->GetPosition() ) >>= aPropertyValues;
-+ pPc->SetPropertyValues( aPropertyValues );
-+
-+ // has the property already been set?
-+ if( lcl_getPropertyValue( pPc->GetPropertyValues(), rtl::OUString::createFromAscii("ItemDescriptorContainer") ).hasValue() )
-+ {
-+ lcl_repalcePropertyValue( pPc->GetPropertyValues(), rtl::OUString::createFromAscii("ItemDescriptorContainer"), uno::makeAny( xMenuMSF->createInstanceWithContext( mxContext ) ) );
-+ pPc->GetCurrentSettings()->replaceByIndex( pPc->GetPosition(), uno::makeAny( pPc->GetPropertyValues() ) );
-+ }
-+ m_xCurrentSettings.set( lcl_getPropertyValue( pPc->GetPropertyValues(), rtl::OUString::createFromAscii("ItemDescriptorContainer") ), uno::UNO_QUERY_THROW );
-+ m_xCurrentSettings->insertByIndex( m_nPosition, uno::makeAny( aPropertys ) );
-+ }
-+ if( m_xUICfgManager->hasSettings( m_sBarName ) )
-+ {
-+ m_xUICfgManager->replaceSettings( m_sBarName, uno::Reference< container::XIndexAccess > (m_xBarSettings, uno::UNO_QUERY_THROW ) );
-+ }
-+ else
-+ {
-+ m_xUICfgManager->insertSettings( m_sBarName, uno::Reference< container::XIndexAccess > (m_xBarSettings, uno::UNO_QUERY_THROW ) );
-+ }
-+ if( !m_bTemporary )
-+ {
-+ m_xUICfgPers->store();
-+ }
-+}
-+
-+void
-+ScVbaCommandBarControl::createNewToolBarControl()
-+{
-+ uno::Sequence< beans::PropertyValue > aPropertys(4);
-+ aPropertys[0].Name = rtl::OUString::createFromAscii("CommandURL");
-+ aPropertys[0].Value <<= m_sCommand;
-+ aPropertys[1].Name = rtl::OUString::createFromAscii("Label");
-+ aPropertys[1].Value <<= m_sName;
-+ aPropertys[2].Name = rtl::OUString::createFromAscii("Type");
-+ aPropertys[2].Value <<= sal_Int32(0);
-+ aPropertys[3].Name = rtl::OUString::createFromAscii("IsVisible");
-+ aPropertys[3].Value <<= sal_True;
-+
-+ m_xBarSettings->insertByIndex( m_nPosition, uno::makeAny( aPropertys ) );
-+ uno::Reference< beans::XPropertySet > xPropertySet( m_xBarSettings, uno::UNO_QUERY_THROW );
-+ rtl::OUString sUIName;
-+ xPropertySet->getPropertyValue( rtl::OUString::createFromAscii("UIName") ) >>= sUIName;
-+
-+ m_xCurrentSettings.set( m_xBarSettings, uno::UNO_QUERY_THROW );
-+ if( m_xUICfgManager->hasSettings( m_sBarName ) )
-+ {
-+ m_xUICfgManager->replaceSettings( m_sBarName, uno::Reference< container::XIndexAccess > (m_xBarSettings, uno::UNO_QUERY_THROW ) );
-+ }
-+ else
-+ {
-+ m_xUICfgManager->insertSettings( m_sBarName, uno::Reference< container::XIndexAccess > (m_xBarSettings, uno::UNO_QUERY_THROW ) );
-+ }
-+ if( !m_bTemporary )
-+ {
-+ m_xUICfgPers->store();
-+ }
-+}
-+
-+::rtl::OUString SAL_CALL
-+ScVbaCommandBarControl::getCaption() throw ( uno::RuntimeException )
-+{
-+ // "Label" always empty
-+ rtl::OUString sCaption;
-+ beans::PropertyValues aPropertyValues;
-+ if( m_xCurrentSettings.is() )
-+ {
-+ m_xCurrentSettings->getByIndex( m_nPosition ) >>= aPropertyValues;
-+ lcl_getPropertyValue( aPropertyValues, rtl::OUString::createFromAscii("Label") ) >>= sCaption;
-+ }
-+ else if( m_xBarSettings.is() )
-+ {
-+ m_xBarSettings->getByIndex( m_nPosition ) >>= aPropertyValues;
-+ lcl_getPropertyValue( aPropertyValues, rtl::OUString::createFromAscii("Label") ) >>= sCaption;
-+ }
-+ return sCaption;
-+}
-+void SAL_CALL
-+ScVbaCommandBarControl::setCaption( const ::rtl::OUString& _caption ) throw (uno::RuntimeException)
-+{
-+ if( m_xCurrentSettings.is() )
-+ {
-+ beans::PropertyValues aPropertyValues;
-+ m_xCurrentSettings->getByIndex( m_nPosition ) >>= aPropertyValues;
-+ beans::PropertyValues aNewPropertyValues;
-+ aNewPropertyValues = lcl_repalcePropertyValue( aPropertyValues, rtl::OUString::createFromAscii("Label"), uno::makeAny( _caption ) );
-+ m_xCurrentSettings->replaceByIndex( m_nPosition, uno::makeAny( aNewPropertyValues ) );
-+ if( m_xUICfgManager->hasSettings( m_sBarName ) )
-+ {
-+ m_xUICfgManager->replaceSettings( m_sBarName, uno::Reference< container::XIndexAccess > (m_xBarSettings, uno::UNO_QUERY_THROW ) );
-+ }
-+ else
-+ {
-+ m_xUICfgManager->insertSettings( m_sBarName, uno::Reference< container::XIndexAccess > (m_xBarSettings, uno::UNO_QUERY_THROW ) );
-+ }
-+ // make it permanent
-+ if( !m_bTemporary )
-+ {
-+ m_xUICfgPers->store();
-+ }
-+ }
-+}
-+::rtl::OUString SAL_CALL
-+ScVbaCommandBarControl::getOnAction() throw (uno::RuntimeException)
-+{
-+ if( m_xCurrentSettings.is() )
-+ {
-+ beans::PropertyValues aPropertyValues;
-+ m_xCurrentSettings->getByIndex( m_nPosition ) >>= aPropertyValues;
-+ rtl::OUString sCommandURL;
-+ lcl_getPropertyValue( aPropertyValues, rtl::OUString::createFromAscii( "CommandURL" ) ) >>= sCommandURL;
-+ return sCommandURL;
-+ }
-+ return ::rtl::OUString();
-+}
-+void SAL_CALL
-+ScVbaCommandBarControl::setOnAction( const ::rtl::OUString& _onaction ) throw (uno::RuntimeException)
-+{
-+ if( m_xCurrentSettings.is() )
-+ {
-+ // convert the comand url into something like vnd.sun.star.script:Standard.testMacro.Macro1?language=Basic&location=document
-+ rtl::OUString aCommandURL;
-+ rtl::OUString sScheme = rtl::OUString::createFromAscii( "vnd.sun.star.script:");
-+ SbModule* pModule = StarBASIC::GetActiveModule();
-+ if( pModule )
-+ {
-+ String sTmp = _onaction;
-+ if( SbMethod* pMethod = dynamic_cast< SbMethod* >( pModule->Find( sTmp, SbxCLASS_METHOD ) ) )
-+ {
-+ if( pMethod )
-+ {
-+ sTmp.Insert( '.', 0 ).Insert( pModule->GetName(), 0 ).Insert( '.', 0 ).Insert( pModule->GetParent()->GetName(), 0 );
-+ }
-+ }
-+
-+ rtl::OUString sUrlPart2 = rtl::OUString::createFromAscii( "?language=Basic&location=document");
-+ aCommandURL = sScheme.concat( sTmp ).concat( sUrlPart2 );
-+ OSL_TRACE("**** METHOD IS %s", rtl::OUStringToOString( aCommandURL, RTL_TEXTENCODING_UTF8 ).getStr() );
-+ }
-+ else
-+ {
-+ aCommandURL = _onaction;
-+ }
-+ OSL_TRACE(" ScVbaCommandBarControl::setOnAction: %s", rtl::OUStringToOString( aCommandURL, RTL_TEXTENCODING_UTF8 ).getStr() );
-+ beans::PropertyValues aPropertyValues;
-+ m_xCurrentSettings->getByIndex( m_nPosition ) >>= aPropertyValues;
-+ beans::PropertyValues aNewPropertyValues;
-+ aNewPropertyValues = lcl_repalcePropertyValue( aPropertyValues, rtl::OUString::createFromAscii("CommandURL"), uno::makeAny( aCommandURL ) );
-+ m_xCurrentSettings->replaceByIndex( m_nPosition, uno::makeAny( aNewPropertyValues ) );
-+ if( m_xUICfgManager->hasSettings( m_sBarName ) )
-+ {
-+ m_xUICfgManager->replaceSettings( m_sBarName, uno::Reference< container::XIndexAccess > (m_xBarSettings, uno::UNO_QUERY_THROW ) );
-+ }
-+ else
-+ {
-+ m_xUICfgManager->insertSettings( m_sBarName, uno::Reference< container::XIndexAccess > (m_xBarSettings, uno::UNO_QUERY_THROW ) );
-+ }
-+ // make it permanent
-+ if( !m_bTemporary )
-+ {
-+ m_xUICfgPers->store();
-+ }
-+ }
-+}
-+::sal_Bool SAL_CALL
-+ScVbaCommandBarControl::getVisible() throw (uno::RuntimeException)
-+{
-+ // not possible in UNO?
-+ return sal_True;
-+}
-+void SAL_CALL
-+ScVbaCommandBarControl::setVisible( ::sal_Bool /*_visible*/ ) throw (uno::RuntimeException)
-+{
-+ // "IsVisilbe"
-+}
-+void SAL_CALL
-+ScVbaCommandBarControl::Delete( ) throw (css::script::BasicErrorException, css::uno::RuntimeException)
-+{
-+ if( m_xCurrentSettings.is() )
-+ {
-+ m_xCurrentSettings->removeByIndex( m_nPosition );
-+
-+ if( m_xUICfgManager->hasSettings( m_sBarName ) )
-+ {
-+ m_xUICfgManager->replaceSettings( m_sBarName, uno::Reference< container::XIndexAccess > (m_xBarSettings, uno::UNO_QUERY_THROW ) );
-+ }
-+ else
-+ {
-+ m_xUICfgManager->insertSettings( m_sBarName, uno::Reference< container::XIndexAccess > (m_xBarSettings, uno::UNO_QUERY_THROW ) );
-+ }
-+ // make it permanent
-+ if( !m_bTemporary )
-+ {
-+ m_xUICfgPers->store();
-+ }
-+ }
-+}
-+uno::Any SAL_CALL
-+ScVbaCommandBarControl::Controls( const uno::Any& aIndex ) throw (script::BasicErrorException, uno::RuntimeException)
-+{
-+ sal_Int32 nIndex;
-+ uno::Reference< XCommandBarControls > xCommandBarControls( new ScVbaCommandBarControls( this, mxContext, uno::Reference< container::XIndexAccess >() ) );
-+ if( aIndex.hasValue() )
-+ {
-+ if( aIndex >>= nIndex )
-+ {
-+ uno::Reference< XCommandBarControl > xCommandBarControl( xCommandBarControls->Item( aIndex, uno::Any() ), uno::UNO_QUERY_THROW );
-+ return uno::makeAny( xCommandBarControl );
-+ }
-+ else
-+ throw uno::RuntimeException( rtl::OUString::createFromAscii( "invalid index" ), uno::Reference< uno::XInterface >() );
-+ }
-+ return uno::makeAny( xCommandBarControls );
-+}
-+rtl::OUString&
-+ScVbaCommandBarControl::getServiceImplName()
-+{
-+ static rtl::OUString sImplName( RTL_CONSTASCII_USTRINGPARAM("ScVbaCommandBarControl") );
-+ return sImplName;
-+}
-+uno::Sequence<rtl::OUString>
-+ScVbaCommandBarControl::getServiceNames()
-+{
-+ static uno::Sequence< rtl::OUString > aServiceNames;
-+ if ( aServiceNames.getLength() == 0 )
-+ {
-+ aServiceNames.realloc( 1 );
-+ aServiceNames[ 0 ] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.CommandBarControl" ) );
-+ }
-+ return aServiceNames;
-+}
-+
-+//////////// ScVbaCommandBarPopup //////////////////////////////
-+ScVbaCommandBarPopup::ScVbaCommandBarPopup( const uno::Reference< XHelperInterface > xParent, const uno::Reference< uno::XComponentContext > xContext, rtl::OUString sName, sal_Int32 nPosition ) throw (uno::RuntimeException) : CommandBarPopup_BASE( xParent, xContext, sName, nPosition, office::MsoControlType::msoControlPopup )
-+{
-+}
-+
-+ScVbaCommandBarPopup::ScVbaCommandBarPopup( const uno::Reference< XHelperInterface > xParent, const uno::Reference< uno::XComponentContext > xContext, rtl::OUString sName, sal_Int32 nPosition, sal_Bool bTemporary ) throw (uno::RuntimeException) : CommandBarPopup_BASE( xParent, xContext, sName, nPosition, bTemporary, office::MsoControlType::msoControlPopup)
-+{
-+}
-+
-+rtl::OUString&
-+ScVbaCommandBarPopup::getServiceImplName()
-+{
-+ static rtl::OUString sImplName( RTL_CONSTASCII_USTRINGPARAM("ScVbaCommandBarPopup") );
-+ return sImplName;
-+}
-+uno::Sequence<rtl::OUString>
-+ScVbaCommandBarPopup::getServiceNames()
-+{
-+ static uno::Sequence< rtl::OUString > aServiceNames;
-+ if ( aServiceNames.getLength() == 0 )
-+ {
-+ aServiceNames.realloc( 1 );
-+ aServiceNames[ 0 ] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.CommandBarPopup" ) );
-+ }
-+ return aServiceNames;
-+}
-+
-+//////////// ScVbaCommandBarButton //////////////////////////////
-+ScVbaCommandBarButton::ScVbaCommandBarButton( const uno::Reference< XHelperInterface > xParent, const uno::Reference< uno::XComponentContext > xContext, rtl::OUString sName, sal_Int32 nPosition ) throw (uno::RuntimeException) : CommandBarButton_BASE( xParent, xContext, sName, nPosition, office::MsoControlType::msoControlButton )
-+{
-+}
-+
-+ScVbaCommandBarButton::ScVbaCommandBarButton( const uno::Reference< XHelperInterface > xParent, const uno::Reference< uno::XComponentContext > xContext, rtl::OUString sName, sal_Int32 nPosition, sal_Bool bTemporary ) throw (uno::RuntimeException) : CommandBarButton_BASE( xParent, xContext, sName, nPosition, bTemporary, office::MsoControlType::msoControlButton)
-+{
-+}
-+
-+rtl::OUString&
-+ScVbaCommandBarButton::getServiceImplName()
-+{
-+ static rtl::OUString sImplName( RTL_CONSTASCII_USTRINGPARAM("ScVbaCommandBarButton") );
-+ return sImplName;
-+}
-+uno::Sequence<rtl::OUString>
-+ScVbaCommandBarButton::getServiceNames()
-+{
-+ static uno::Sequence< rtl::OUString > aServiceNames;
-+ if ( aServiceNames.getLength() == 0 )
-+ {
-+ aServiceNames.realloc( 1 );
-+ aServiceNames[ 0 ] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.CommandBarButton" ) );
-+ }
-+ return aServiceNames;
-+}
---- vbahelper/source/vbahelper/vbacommandbarcontrol.hxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ vbahelper/source/vbahelper/vbacommandbarcontrol.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,120 @@
-+/*************************************************************************
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile$
-+ *
-+ * $Revision$
-+ *
-+ * last change: $Author$ $Date$
-+ *
-+ * The Contents of this file are made available subject to
-+ * the terms of GNU Lesser General Public License Version 2.1.
-+ *
-+ *
-+ * GNU Lesser General Public License Version 2.1
-+ * =============================================
-+ * Copyright 2005 by Sun Microsystems, Inc.
-+ * 901 San Antonio Road, Palo Alto, CA 94303, USA
-+ *
-+ * This library is free software; you can redistribute it and/or
-+ * modify it under the terms of the GNU Lesser General Public
-+ * License version 2.1, as published by the Free Software Foundation.
-+ *
-+ * This library 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 for more details.
-+ *
-+ * You should have received a copy of the GNU Lesser General Public
-+ * License along with this library; if not, write to the Free Software
-+ * Foundation, Inc., 59 Temple Place, Suite 330, Boston,
-+ * MA 02111-1307 USA
-+ *
-+ ************************************************************************/
-+#ifndef SC_VBA_COMMANDBARCONTROL_HXX
-+#define SC_VBA_COMMANDBARCONTROL_HXX
-+
-+#include <ooo/vba/XCommandBarControl.hpp>
-+#include <ooo/vba/XCommandBarPopup.hpp>
-+#include <ooo/vba/XCommandBarButton.hpp>
-+#include <ooo/vba/office/MsoControlType.hpp>
-+
-+#include <vbahelper/vbahelperinterface.hxx>
-+#include "vbacommandbarcontrols.hxx"
-+
-+typedef InheritedHelperInterfaceImpl1< ov::XCommandBarControl > CommandBarControl_BASE;
-+
-+class ScVbaCommandBarControl : public CommandBarControl_BASE
-+{
-+private:
-+ rtl::OUString m_sName;
-+ rtl::OUString m_sBarName;
-+ rtl::OUString m_sCommand;
-+ sal_Int32 m_nType;
-+ sal_Int32 m_nPosition;
-+ sal_Bool m_bTemporary;
-+ sal_Bool m_bIsMenu;
-+ ScVbaCommandBarControls* m_pCommandBarControls;
-+ css::uno::Reference< ov::XHelperInterface > m_xParentHardRef;
-+ css::uno::Reference< css::ui::XUIConfigurationManager > m_xUICfgManager;
-+ css::uno::Reference< css::ui::XUIConfigurationPersistence > m_xUICfgPers;
-+ css::uno::Reference< css::container::XIndexContainer > m_xBarSettings;
-+ css::uno::Reference< css::container::XIndexContainer > m_xCurrentSettings;
-+ css::beans::PropertyValues m_aPropertyValues;
-+
-+ void initObjects() throw (css::uno::RuntimeException);
-+ void createNewMenuBarControl();
-+ void createNewToolBarControl();
-+public:
-+ ScVbaCommandBarControl( const css::uno::Reference< ov::XHelperInterface > xParent, const css::uno::Reference< css::uno::XComponentContext > xContext, rtl::OUString sName, sal_Int32 nPosition = 0, sal_Int32 nType = ov::office::MsoControlType::msoControlButton ) throw (css::uno::RuntimeException);
-+ ScVbaCommandBarControl( const css::uno::Reference< ov::XHelperInterface > xParent, const css::uno::Reference< css::uno::XComponentContext > xContext, rtl::OUString sName, sal_Int32 nPosition, sal_Bool bTemporary, sal_Int32 nType = ov::office::MsoControlType::msoControlButton ) throw (css::uno::RuntimeException);
-+ css::uno::Reference< css::ui::XUIConfigurationManager > GetUICfgManager() { return m_xUICfgManager; };
-+ css::uno::Reference< css::ui::XUIConfigurationPersistence > GetUICfgPers() { return m_xUICfgPers; };
-+ css::uno::Reference< css::container::XIndexContainer > GetBarSettings() { return m_xBarSettings; };
-+ sal_Bool IsMenu() { return m_bIsMenu; };
-+ sal_Int32 GetPosition() { return m_nPosition; };
-+ css::uno::Reference< css::container::XIndexContainer > GetCurrentSettings() { return m_xCurrentSettings; };
-+ css::beans::PropertyValues GetPropertyValues() { return m_aPropertyValues; };
-+ void SetPropertyValues( css::beans::PropertyValues aPropertyValues ) { m_aPropertyValues = aPropertyValues; };
-+
-+ // Attributes
-+ virtual ::rtl::OUString SAL_CALL getCaption() throw (css::uno::RuntimeException);
-+ virtual void SAL_CALL setCaption( const ::rtl::OUString& _caption ) throw (css::uno::RuntimeException);
-+ virtual ::rtl::OUString SAL_CALL getOnAction() throw (css::uno::RuntimeException);
-+ virtual void SAL_CALL setOnAction( const ::rtl::OUString& _onaction ) throw (css::uno::RuntimeException);
-+ virtual ::sal_Bool SAL_CALL getVisible() throw (css::uno::RuntimeException);
-+ virtual void SAL_CALL setVisible( ::sal_Bool _visible ) throw (css::uno::RuntimeException);
-+
-+ // Methods
-+ virtual void SAL_CALL Delete( ) throw (css::script::BasicErrorException, css::uno::RuntimeException);
-+ virtual css::uno::Any SAL_CALL Controls( const css::uno::Any& aIndex ) throw (css::script::BasicErrorException, css::uno::RuntimeException);
-+
-+ // XHelperInterface
-+ virtual rtl::OUString& getServiceImplName();
-+ virtual css::uno::Sequence<rtl::OUString> getServiceNames();
-+};
-+
-+typedef cppu::ImplInheritanceHelper1< ScVbaCommandBarControl, ov::XCommandBarPopup > CommandBarPopup_BASE;
-+class ScVbaCommandBarPopup : public CommandBarPopup_BASE
-+{
-+public:
-+ ScVbaCommandBarPopup( const css::uno::Reference< ov::XHelperInterface > xParent, const css::uno::Reference< css::uno::XComponentContext > xContext, rtl::OUString sName, sal_Int32 nPosition = 0 ) throw (css::uno::RuntimeException);
-+ ScVbaCommandBarPopup( const css::uno::Reference< ov::XHelperInterface > xParent, const css::uno::Reference< css::uno::XComponentContext > xContext, rtl::OUString sName, sal_Int32 nPosition, sal_Bool bTemporary ) throw (css::uno::RuntimeException);
-+ // XHelperInterface
-+ virtual rtl::OUString& getServiceImplName();
-+ virtual css::uno::Sequence<rtl::OUString> getServiceNames();
-+};
-+
-+typedef cppu::ImplInheritanceHelper1< ScVbaCommandBarControl, ov::XCommandBarButton > CommandBarButton_BASE;
-+class ScVbaCommandBarButton : public CommandBarButton_BASE
-+{
-+public:
-+ ScVbaCommandBarButton( const css::uno::Reference< ov::XHelperInterface > xParent, const css::uno::Reference< css::uno::XComponentContext > xContext, rtl::OUString sName, sal_Int32 nPosition = 0 ) throw (css::uno::RuntimeException);
-+ ScVbaCommandBarButton( const css::uno::Reference< ov::XHelperInterface > xParent, const css::uno::Reference< css::uno::XComponentContext > xContext, rtl::OUString sName, sal_Int32 nPosition, sal_Bool bTemporary ) throw (css::uno::RuntimeException);
-+ // XHelperInterface
-+ virtual rtl::OUString& getServiceImplName();
-+ virtual css::uno::Sequence<rtl::OUString> getServiceNames();
-+};
-+
-+#endif//SC_VBA_COMMANDBARCONTROL_HXX
---- vbahelper/source/vbahelper/vbacommandbarcontrols.cxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ vbahelper/source/vbahelper/vbacommandbarcontrols.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,348 @@
-+/*************************************************************************
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile$
-+ *
-+ * $Revision$
-+ *
-+ * last change: $Author$ $Date$
-+ *
-+ * The Contents of this file are made available subject to
-+ * the terms of GNU Lesser General Public License Version 2.1.
-+ *
-+ *
-+ * GNU Lesser General Public License Version 2.1
-+ * =============================================
-+ * Copyright 2005 by Sun Microsystems, Inc.
-+ * 901 San Antonio Road, Palo Alto, CA 94303, USA
-+ *
-+ * This library is free software; you can redistribute it and/or
-+ * modify it under the terms of the GNU Lesser General Public
-+ * License version 2.1, as published by the Free Software Foundation.
-+ *
-+ * This library 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 for more details.
-+ *
-+ * You should have received a copy of the GNU Lesser General Public
-+ * License along with this library; if not, write to the Free Software
-+ * Foundation, Inc., 59 Temple Place, Suite 330, Boston,
-+ * MA 02111-1307 USA
-+ *
-+ ************************************************************************/
-+#include "vbacommandbarcontrols.hxx"
-+#include "vbacommandbarcontrol.hxx"
-+
-+using namespace com::sun::star;
-+using namespace ooo::vba;
-+
-+uno::Any lcl_getPropertyValue( beans::PropertyValues aPropertyValues, rtl::OUString sPropertyName );
-+
-+typedef ::cppu::WeakImplHelper1< container::XEnumeration > CommandBarControlEnumeration_BASE;
-+class CommandBarControlEnumeration : public CommandBarControlEnumeration_BASE
-+{
-+ //uno::Reference< uno::XComponentContext > m_xContext;
-+ ScVbaCommandBarControls* m_pCommandBarControls;
-+ sal_Int32 m_nCurrentPosition;
-+public:
-+ CommandBarControlEnumeration( ScVbaCommandBarControls* pCommandBarControls ) : m_pCommandBarControls( pCommandBarControls ), m_nCurrentPosition( 0 ) {}
-+ virtual sal_Bool SAL_CALL hasMoreElements() throw ( uno::RuntimeException )
-+ {
-+ if( m_nCurrentPosition < m_pCommandBarControls->getCount() )
-+ return sal_True;
-+ return sal_False;
-+ }
-+ virtual uno::Any SAL_CALL nextElement() throw ( container::NoSuchElementException, lang::WrappedTargetException, uno::RuntimeException )
-+ {
-+ if( hasMoreElements() )
-+ {
-+ rtl::OUString sName = m_pCommandBarControls->GetControlNameByIndex( m_nCurrentPosition );
-+ m_nCurrentPosition = m_nCurrentPosition + 1;
-+ if( sName.getLength() > 0 )
-+ return m_pCommandBarControls->createCollectionObject( uno::makeAny( sName ) );
-+ else
-+ return nextElement();
-+ }
-+ else
-+ throw container::NoSuchElementException();
-+ }
-+};
-+
-+ScVbaCommandBarControls::ScVbaCommandBarControls( const uno::Reference< XHelperInterface > xParent, const uno::Reference< uno::XComponentContext > xContext, const uno::Reference< container::XIndexAccess> xIndexAccess ) throw (uno::RuntimeException) : CommandBarControls_BASE( xParent, xContext, xIndexAccess )
-+{
-+ m_bIsMenu = sal_False;
-+ m_bHasElements = sal_False;
-+ m_xParentHardRef.set( xParent, uno::UNO_QUERY_THROW );
-+ m_pCommandBar = dynamic_cast< ScVbaCommandBar* >( m_xParentHardRef.get() );
-+ m_pCommandBarControl = dynamic_cast< ScVbaCommandBarControl* >( m_xParentHardRef.get() );
-+ if( m_pCommandBar )
-+ {
-+ m_xUICfgManager.set( m_pCommandBar->GetUICfgManager(), uno::UNO_QUERY_THROW );
-+ m_xUICfgPers.set( m_pCommandBar->GetUICfgPers(), uno::UNO_QUERY_THROW );
-+ m_xBarSettings.set( m_pCommandBar->GetBarSettings(), uno::UNO_QUERY_THROW );
-+ m_bIsMenu = m_pCommandBar->IsMenu();
-+ if( m_xBarSettings->hasElements() )
-+ {
-+ m_bHasElements = sal_True;
-+ }
-+ }
-+ else if( m_pCommandBarControl )
-+ {
-+ m_xUICfgManager.set( m_pCommandBarControl->GetUICfgManager(), uno::UNO_QUERY_THROW );
-+ m_xUICfgPers.set( m_pCommandBarControl->GetUICfgPers(), uno::UNO_QUERY_THROW );
-+ beans::PropertyValues aPropertyValues;
-+ m_pCommandBarControl->GetCurrentSettings()->getByIndex( m_pCommandBarControl->GetPosition() ) >>= aPropertyValues;
-+ m_pCommandBarControl->SetPropertyValues( aPropertyValues );
-+ m_xBarSettings.set( m_pCommandBarControl->GetCurrentSettings(), uno::UNO_QUERY_THROW );
-+
-+ uno::Any aValue = lcl_getPropertyValue( m_pCommandBarControl->GetPropertyValues(), rtl::OUString::createFromAscii("ItemDescriptorContainer") );
-+ if( aValue.hasValue() )
-+ {
-+ m_xCurrentSettings = m_pCommandBarControl->GetCurrentSettings();
-+ m_bHasElements = sal_True;
-+ }
-+ else
-+ {
-+ m_bHasElements = sal_False;
-+ }
-+ m_bIsMenu = m_pCommandBarControl->IsMenu();
-+ }
-+ else
-+ {
-+ throw uno::RuntimeException( rtl::OUString::createFromAscii("Parent needs to be a ScVbaCommandBar or a ScVbaCommandBarControl"), uno::Reference< uno::XInterface >() );
-+ }
-+}
-+rtl::OUString
-+ScVbaCommandBarControls::GetControlNameByIndex( const sal_Int32 nIndex ) throw ( uno::RuntimeException )
-+{
-+ sal_Int32 nCount = 0;
-+ if( m_bHasElements )
-+ {
-+ sal_Int32 nBarSettingsCount = m_xBarSettings->getCount();
-+ for( sal_Int32 i = 0; i < nBarSettingsCount; i++ )
-+ {
-+ beans::PropertyValues aMenuValues;
-+ m_xBarSettings->getByIndex( i ) >>= aMenuValues;
-+ for( sal_Int32 j = 0; j < aMenuValues.getLength(); j++ )
-+ {
-+ if( aMenuValues[j].Name.equalsIgnoreAsciiCase( rtl::OUString::createFromAscii( "CommandURL" ) ) )
-+ {
-+ nCount++;
-+ if( nIndex == nCount )
-+ {
-+ rtl::OUString sCommandURL;
-+ aMenuValues[j].Value >>= sCommandURL;
-+ sal_Int32 nLastIndex = sCommandURL.lastIndexOf( rtl::OUString::createFromAscii(":") );
-+ if( ( nLastIndex != -1 ) && ( ( nLastIndex +1 ) < sCommandURL.getLength() ) )
-+ {
-+ sCommandURL = sCommandURL.copy( nLastIndex + 1 );
-+ return sCommandURL;
-+ }
-+ }
-+ }
-+ }
-+ }
-+ }
-+ else
-+ throw uno::RuntimeException( rtl::OUString::createFromAscii( "Out of bound" ), uno::Reference< uno::XInterface >() );
-+ return rtl::OUString();
-+}
-+
-+// Attributes
-+sal_Int32 SAL_CALL
-+ScVbaCommandBarControls::getCount() throw (uno::RuntimeException)
-+{
-+ sal_Int32 nCount = 0;
-+ if( m_bHasElements )
-+ {
-+ sal_Int32 nBarSettingsCount = m_xBarSettings->getCount();
-+ for( sal_Int32 i = 0; i < nBarSettingsCount; i++ )
-+ {
-+ beans::PropertyValues aMenuValues;
-+ m_xBarSettings->getByIndex( i ) >>= aMenuValues;
-+ for( sal_Int32 j = 0; j < aMenuValues.getLength(); j++ )
-+ {
-+ if( aMenuValues[j].Name.equalsIgnoreAsciiCase( rtl::OUString::createFromAscii( "CommandURL" ) ) )
-+ {
-+ nCount++;
-+ }
-+ }
-+ }
-+ }
-+ return nCount;
-+}
-+// XEnumerationAccess
-+uno::Type SAL_CALL
-+ScVbaCommandBarControls::getElementType() throw ( uno::RuntimeException )
-+{
-+ return XCommandBarControls::static_type( 0 );
-+}
-+uno::Reference< container::XEnumeration >
-+ScVbaCommandBarControls::createEnumeration() throw ( uno::RuntimeException )
-+{
-+ return uno::Reference< container::XEnumeration >( new CommandBarControlEnumeration( this ) );
-+}
-+uno::Any
-+ScVbaCommandBarControls::createCollectionObject( const uno::Any& aSource )
-+{
-+ // only surport the aSource as a name string, because this class is a API wrapper
-+ rtl::OUString sName;
-+ if( aSource >>= sName )
-+ {
-+ uno::Reference< container::XIndexContainer > xCurrentSettings;
-+ beans::PropertyValues aPropertyValues;
-+ if( m_pCommandBarControl )
-+ {
-+ m_pCommandBarControl->GetCurrentSettings()->getByIndex( m_pCommandBarControl->GetPosition() ) >>= aPropertyValues;
-+ xCurrentSettings.set( lcl_getPropertyValue( aPropertyValues, rtl::OUString::createFromAscii( "ItemDescriptorContainer" ) ), uno::UNO_QUERY );
-+ if( !xCurrentSettings.is() )
-+ {
-+ xCurrentSettings.set( m_xUICfgManager->getSettings( GetParentToolBarName(), sal_True ), uno::UNO_QUERY );
-+ }
-+ }
-+
-+ sal_Int32 nPosition = -1;
-+ for( sal_Int32 i = 0; i < xCurrentSettings->getCount(); i++ )
-+ {
-+ xCurrentSettings->getByIndex( i ) >>= aPropertyValues;
-+ // Label always empty in OOo
-+ rtl::OUString sLabel;
-+ lcl_getPropertyValue( aPropertyValues, rtl::OUString::createFromAscii( "Label" ) ) >>= sLabel;
-+ if( sLabel.equalsIgnoreAsciiCase( sName ) )
-+ {
-+ nPosition = i;
-+ break;
-+ }
-+ // using CammandURL to find
-+ rtl::OUString sCommandURL;
-+ lcl_getPropertyValue( aPropertyValues, rtl::OUString::createFromAscii( "CommandURL" ) ) >>= sCommandURL;
-+ sal_Int32 nLastIndex = sCommandURL.lastIndexOf( rtl::OUString::createFromAscii(":") );
-+ if( ( nLastIndex != -1 ) && ( ( nLastIndex + 1 ) < sCommandURL.getLength() ) )
-+ {
-+ sCommandURL = sCommandURL.copy( nLastIndex + 1 );
-+ }
-+ if( sCommandURL.equalsIgnoreAsciiCase( sName ) )
-+ {
-+ nPosition = i;
-+ break;
-+ }
-+ }
-+
-+ if( nPosition != -1 )
-+ {
-+ uno::Reference< container::XIndexContainer > xSubMenu;
-+ lcl_getPropertyValue( aPropertyValues, rtl::OUString::createFromAscii( "ItemDescriptorContainer" ) ) >>= xSubMenu;
-+ ScVbaCommandBarControl* pNewCommandBarControl = NULL;
-+ if( xSubMenu.is() )
-+ pNewCommandBarControl = new ScVbaCommandBarPopup( this, mxContext, sName, nPosition );
-+ else
-+ pNewCommandBarControl = new ScVbaCommandBarButton( this, mxContext, sName, nPosition );
-+
-+ return uno::makeAny( uno::Reference< XCommandBarControl > ( pNewCommandBarControl ) );
-+ }
-+ else
-+ throw uno::RuntimeException( rtl::OUString::createFromAscii("The CommandBarControl do not exist"), uno::Reference< uno::XInterface >() );
-+
-+ }
-+ return uno::Any();
-+}
-+
-+// Methods
-+uno::Any SAL_CALL
-+ScVbaCommandBarControls::Item( const uno::Any& aIndex, const uno::Any& /*aIndex*/ ) throw (uno::RuntimeException)
-+{
-+ if( aIndex.getValueTypeClass() == uno::TypeClass_STRING )
-+ {
-+ return createCollectionObject( aIndex );
-+ }
-+ sal_Int32 nIndex = 0;
-+ if( aIndex >>= nIndex )
-+ {
-+ return createCollectionObject( uno::makeAny( GetControlNameByIndex( nIndex ) ) );
-+ }
-+
-+ return uno::Any();
-+}
-+uno::Reference< XCommandBarControl > SAL_CALL
-+ScVbaCommandBarControls::Add( const uno::Any& Type, const uno::Any& Id, const uno::Any& /*Parameter*/, const uno::Any& Before, const uno::Any& Temporary ) throw (script::BasicErrorException, uno::RuntimeException)
-+{
-+ // Parameter is not supported
-+ // the following name needs to be individually created;
-+ rtl::OUString sCaption( rtl::OUString::createFromAscii("custom Control") );
-+ rtl::OUString sCommand( rtl::OUString::createFromAscii("macro:///Standard.Module1.Test()") );
-+ sal_Int32 nType =0;
-+ sal_Int32 nPosition = 0;
-+ sal_Int32 nId;
-+ sal_Bool bTemporary = sal_True;
-+
-+ if( Type.hasValue() )
-+ if( Type >>= nType )
-+ {
-+ // evalute the type of the new control
-+ }
-+ if( Id.hasValue() )
-+ if( Id >>= nId )
-+ {
-+ // evalute the action of the new control
-+ }
-+ if( Before.hasValue() )
-+ Before >>= nPosition;
-+ else
-+ {
-+ // if Before is ignore, the new control should be placed at the end of the commandbars;
-+ if( m_pCommandBar )
-+ nPosition = getCount();
-+ else if ( m_pCommandBarControl )
-+ {
-+ css::uno::Reference< css::container::XIndexContainer > xCurrentSettings;
-+ xCurrentSettings.set( lcl_getPropertyValue( m_pCommandBarControl->GetPropertyValues(), rtl::OUString::createFromAscii("ItemDescriptorContainer") ), uno::UNO_QUERY );
-+ if( xCurrentSettings.is() )
-+ {
-+ nPosition = xCurrentSettings->getCount();
-+ }
-+ }
-+ }
-+ if( Temporary.hasValue() )
-+ if( Temporary >>= bTemporary )
-+ {
-+ // evalute the temporary of the new Control
-+ }
-+
-+ ScVbaCommandBarControl* pNewCommandBarControl = NULL;
-+ if( nType == office::MsoControlType::msoControlButton )
-+ {
-+ pNewCommandBarControl = new ScVbaCommandBarButton( this, mxContext, sCaption, nPosition, bTemporary );
-+ }
-+ else if ( nType == office::MsoControlType::msoControlPopup )
-+ {
-+ pNewCommandBarControl = new ScVbaCommandBarPopup( this, mxContext, sCaption, nPosition, bTemporary );
-+ }
-+ else
-+ {
-+ pNewCommandBarControl = new ScVbaCommandBarControl( this, mxContext, sCaption, nPosition, bTemporary );
-+ }
-+
-+ return uno::Reference< XCommandBarControl >( pNewCommandBarControl );
-+}
-+
-+// XHelperInterface
-+rtl::OUString&
-+ScVbaCommandBarControls::getServiceImplName()
-+{
-+ static rtl::OUString sImplName( RTL_CONSTASCII_USTRINGPARAM("ScVbaCommandBarControls") );
-+ return sImplName;
-+}
-+uno::Sequence<rtl::OUString>
-+ScVbaCommandBarControls::getServiceNames()
-+{
-+ static uno::Sequence< rtl::OUString > aServiceNames;
-+ if ( aServiceNames.getLength() == 0 )
-+ {
-+ aServiceNames.realloc( 1 );
-+ aServiceNames[ 0 ] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.CommandBarControls" ) );
-+ }
-+ return aServiceNames;
-+}
-+
---- vbahelper/source/vbahelper/vbacommandbarcontrols.hxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ vbahelper/source/vbahelper/vbacommandbarcontrols.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,91 @@
-+/*************************************************************************
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile$
-+ *
-+ * $Revision$
-+ *
-+ * last change: $Author$ $Date$
-+ *
-+ * The Contents of this file are made available subject to
-+ * the terms of GNU Lesser General Public License Version 2.1.
-+ *
-+ *
-+ * GNU Lesser General Public License Version 2.1
-+ * =============================================
-+ * Copyright 2005 by Sun Microsystems, Inc.
-+ * 901 San Antonio Road, Palo Alto, CA 94303, USA
-+ *
-+ * This library is free software; you can redistribute it and/or
-+ * modify it under the terms of the GNU Lesser General Public
-+ * License version 2.1, as published by the Free Software Foundation.
-+ *
-+ * This library 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 for more details.
-+ *
-+ * You should have received a copy of the GNU Lesser General Public
-+ * License along with this library; if not, write to the Free Software
-+ * Foundation, Inc., 59 Temple Place, Suite 330, Boston,
-+ * MA 02111-1307 USA
-+ *
-+ ************************************************************************/
-+#ifndef SC_VBA_COMMANDBARCONTROLS_HXX
-+#define SC_VBA_COMMANDBARCONTROLS_HXX
-+
-+#include <ooo/vba/XCommandBarControls.hpp>
-+
-+#include <vbahelper/vbahelperinterface.hxx>
-+#include "vbacommandbar.hxx"
-+#include <vbahelper/vbacollectionimpl.hxx>
-+
-+class ScVbaCommandBarControl;
-+
-+typedef CollTestImplHelper< ov::XCommandBarControls > CommandBarControls_BASE;
-+
-+class ScVbaCommandBarControls : public CommandBarControls_BASE
-+{
-+private:
-+ sal_Bool m_bIsMenu;
-+ sal_Bool m_bHasElements;
-+ ScVbaCommandBar* m_pCommandBar;
-+ ScVbaCommandBarControl* m_pCommandBarControl;
-+ css::uno::Reference< ov::XHelperInterface > m_xParentHardRef;
-+ css::uno::Reference< css::ui::XUIConfigurationManager > m_xUICfgManager;
-+ css::uno::Reference< css::ui::XUIConfigurationPersistence > m_xUICfgPers;
-+ css::uno::Reference< css::container::XIndexContainer > m_xBarSettings;
-+ css::uno::Reference< css::container::XIndexContainer > m_xCurrentSettings;
-+
-+public:
-+ ScVbaCommandBarControls( const css::uno::Reference< ov::XHelperInterface > xParent, const css::uno::Reference< css::uno::XComponentContext > xContext, const css::uno::Reference< css::container::XIndexAccess > xIndexAccess ) throw( css::uno::RuntimeException );
-+ css::uno::Reference< css::ui::XUIConfigurationManager > GetUICfgManager() { return m_xUICfgManager; };
-+ css::uno::Reference< css::ui::XUIConfigurationPersistence > GetUICfgPers() { return m_xUICfgPers; };
-+ css::uno::Reference< css::container::XIndexContainer > GetBarSettings() { return m_xBarSettings; };
-+ sal_Bool IsMenu() { return m_bIsMenu; };
-+ ScVbaCommandBar* GetParentCommandBar() { return m_pCommandBar; };
-+ ScVbaCommandBarControl* GetParentCommandBarControl() { return m_pCommandBarControl; };
-+ rtl::OUString GetParentToolBarName()
-+ {
-+ if( m_pCommandBar ) return m_pCommandBar->GetToolBarName();
-+ else return rtl::OUString();
-+ }
-+ rtl::OUString GetControlNameByIndex( const sal_Int32 nIndex ) throw ( css::uno::RuntimeException );
-+
-+ // Attributes
-+ virtual ::sal_Int32 SAL_CALL getCount() throw (css::uno::RuntimeException);
-+ // XEnumerationAccess
-+ virtual css::uno::Type SAL_CALL getElementType() throw (css::uno::RuntimeException);
-+ virtual css::uno::Reference< css::container::XEnumeration > SAL_CALL createEnumeration() throw (css::uno::RuntimeException);
-+ virtual css::uno::Any createCollectionObject( const css::uno::Any& aSource );
-+
-+ // Methods
-+ virtual css::uno::Any SAL_CALL Item( const css::uno::Any& Index, const css::uno::Any& /*Index2*/ ) throw (css::uno::RuntimeException);
-+ virtual css::uno::Reference< ov::XCommandBarControl > SAL_CALL Add( const css::uno::Any& Type, const css::uno::Any& Id, const css::uno::Any& Parameter, const css::uno::Any& Before, const css::uno::Any& Temporary ) throw (css::script::BasicErrorException, css::uno::RuntimeException);
-+ // XHelperInterface
-+ virtual rtl::OUString& getServiceImplName();
-+ virtual css::uno::Sequence<rtl::OUString> getServiceNames();
-+};
-+
-+#endif//SC_VBA_COMMANDBARCONTROLS_HXX
---- vbahelper/source/vbahelper/vbacommandbars.cxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ vbahelper/source/vbahelper/vbacommandbars.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,261 @@
-+/*************************************************************************
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile$
-+ *
-+ * $Revision$
-+ *
-+ * last change: $Author$ $Date$
-+ *
-+ * The Contents of this file are made available subject to
-+ * the terms of GNU Lesser General Public License Version 2.1.
-+ *
-+ *
-+ * GNU Lesser General Public License Version 2.1
-+ * =============================================
-+ * Copyright 2005 by Sun Microsystems, Inc.
-+ * 901 San Antonio Road, Palo Alto, CA 94303, USA
-+ *
-+ * This library is free software; you can redistribute it and/or
-+ * modify it under the terms of the GNU Lesser General Public
-+ * License version 2.1, as published by the Free Software Foundation.
-+ *
-+ * This library 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 for more details.
-+ *
-+ * You should have received a copy of the GNU Lesser General Public
-+ * License along with this library; if not, write to the Free Software
-+ * Foundation, Inc., 59 Temple Place, Suite 330, Boston,
-+ * MA 02111-1307 USA
-+ *
-+ ************************************************************************/
-+#include <com/sun/star/lang/XServiceInfo.hpp>
-+#include <com/sun/star/frame/XDesktop.hpp>
-+#include <com/sun/star/container/XNameAccess.hpp>
-+
-+#include "vbacommandbars.hxx"
-+#include "vbacommandbar.hxx"
-+
-+using namespace com::sun::star;
-+using namespace ooo::vba;
-+
-+typedef ::cppu::WeakImplHelper1< container::XEnumeration > CommandBarEnumeration_BASE;
-+
-+static rtl::OUString sSpreadsheetDocumentUrl( rtl::OUString::createFromAscii( "com.sun.star.sheet.SpreadsheetDocument" ) );
-+static rtl::OUString sTextDocumentUrl( rtl::OUString::createFromAscii( "com.sun.star.text.TextDocument" ) );
-+static rtl::OUString sWindowStateConfUrl( rtl::OUString::createFromAscii( "com.sun.star.ui.WindowStateConfiguration" ) );
-+
-+class CommandBarEnumeration : public CommandBarEnumeration_BASE
-+{
-+ uno::Reference< uno::XComponentContext > m_xContext;
-+ uno::Reference< XCommandBars > m_xCommandBars;
-+ uno::Sequence< rtl::OUString > m_sNames;
-+ sal_Int32 m_nCurrentPosition;
-+public:
-+ CommandBarEnumeration( const uno::Reference< uno::XComponentContext > xContext, const uno::Reference< XCommandBars > xCommandBars, const uno::Sequence< rtl::OUString > sNames ) : m_xContext( xContext ), m_xCommandBars( xCommandBars ), m_sNames( sNames ), m_nCurrentPosition( 0 )
-+ {
-+ }
-+ virtual sal_Bool SAL_CALL hasMoreElements() throw ( uno::RuntimeException )
-+ {
-+ if( m_nCurrentPosition < m_sNames.getLength() )
-+ return sal_True;
-+ return sal_False;
-+ }
-+ virtual uno::Any SAL_CALL nextElement() throw ( container::NoSuchElementException, lang::WrappedTargetException, uno::RuntimeException )
-+ {
-+ if( hasMoreElements() )
-+ {
-+ rtl::OUString sName( m_sNames[ m_nCurrentPosition ] );
-+ m_nCurrentPosition = m_nCurrentPosition + 1;
-+ if( sName.indexOf( rtl::OUString::createFromAscii("private:resource/toolbar/") ) != -1 )
-+ {
-+ sal_Int32 nLastIndex = sName.lastIndexOf( rtl::OUString::createFromAscii( "/" ) );
-+ if( ( nLastIndex != -1 ) && ( ( nLastIndex + 1 ) < sName.getLength() ) )
-+ {
-+ sName = sName.copy( nLastIndex + 1);
-+ if( sName.getLength() > 0 )
-+ {
-+ uno::Reference< XHelperInterface > xHelperInterface( m_xCommandBars, uno::UNO_QUERY_THROW );
-+ uno::Reference< XCommandBar > xCommandBar( new ScVbaCommandBar( xHelperInterface, m_xContext, sName, sal_True, sal_False ) );
-+ if( xCommandBar.is() )
-+ return uno::makeAny( xCommandBar );
-+ else
-+ return nextElement();
-+ }
-+ else
-+ return nextElement();
-+ }
-+ }
-+ else
-+ return nextElement();
-+ }
-+ else
-+ throw container::NoSuchElementException();
-+ return uno::Any();
-+ }
-+};
-+
-+
-+ScVbaCommandBars::ScVbaCommandBars( const uno::Reference< XHelperInterface > xParent, const uno::Reference< uno::XComponentContext > xContext, const uno::Reference< container::XIndexAccess > xIndexAccess ) : CommandBars_BASE( xParent, xContext, xIndexAccess )
-+{
-+ retrieveObjects();
-+}
-+void
-+ScVbaCommandBars::retrieveObjects() throw ( uno::RuntimeException )
-+{
-+ uno::Reference< lang::XServiceInfo > xServiceInfo( getCurrentDocument(), uno::UNO_QUERY_THROW );
-+ if( xServiceInfo->supportsService( sSpreadsheetDocumentUrl ) )
-+ {
-+ m_sModuleName = sSpreadsheetDocumentUrl;
-+ }
-+ else if( xServiceInfo->supportsService( sTextDocumentUrl ) )
-+ {
-+ m_sModuleName = sTextDocumentUrl;
-+ }
-+ else
-+ throw uno::RuntimeException( rtl::OUString::createFromAscii( "Unsupported Document" ), uno::Reference< uno::XInterface >() );
-+
-+ uno::Reference < lang::XMultiServiceFactory > xMSF( mxContext->getServiceManager(), uno::UNO_QUERY_THROW );
-+ uno::Reference < container::XNameAccess > xNameAccess( xMSF->createInstance( sWindowStateConfUrl ), uno::UNO_QUERY_THROW );
-+ m_xNameAccess.set( xNameAccess->getByName( m_sModuleName ), uno::UNO_QUERY_THROW );
-+}
-+
-+// XEnumerationAccess
-+uno::Type SAL_CALL
-+ScVbaCommandBars::getElementType() throw ( uno::RuntimeException )
-+{
-+ return XCommandBars::static_type( 0 );
-+}
-+uno::Reference< container::XEnumeration >
-+ScVbaCommandBars::createEnumeration() throw ( uno::RuntimeException )
-+{
-+ return uno::Reference< container::XEnumeration >( new CommandBarEnumeration( mxContext, this, m_xNameAccess->getElementNames() ) );
-+}
-+
-+uno::Any
-+ScVbaCommandBars::createCollectionObject( const uno::Any& aSource )
-+{
-+ // aSource should be a name at this time, because of the class is API wrapper.
-+ rtl::OUString sToolBarName;
-+ if( aSource >>= sToolBarName )
-+ {
-+ sToolBarName = sToolBarName.toAsciiLowerCase();
-+ if( sToolBarName.equalsIgnoreAsciiCase( rtl::OUString::createFromAscii("Worksheet Menu Bar") ) )
-+ {
-+ return uno::makeAny( uno::Reference< XCommandBar > ( new ScVbaCommandBar( this, mxContext, 0 ) ) );
-+ }
-+ else if( sToolBarName.equalsIgnoreAsciiCase( rtl::OUString::createFromAscii("Menu Bar") ) )
-+ {
-+ return uno::makeAny( uno::Reference< XCommandBar > ( new ScVbaCommandBar( this, mxContext, 1 ) ) );
-+ }
-+ else if( checkToolBarExist( sToolBarName ) )
-+ {
-+ return uno::makeAny( uno::Reference< XCommandBar > (new ScVbaCommandBar( this, mxContext, sToolBarName, sal_True, sal_False ) ) );
-+ }
-+ }
-+ return uno::Any();
-+}
-+
-+// XCommandBars
-+uno::Reference< XCommandBar > SAL_CALL
-+ScVbaCommandBars::Add( const css::uno::Any& Name, const css::uno::Any& /*Position*/, const css::uno::Any& /*MenuBar*/, const css::uno::Any& Temporary ) throw (css::script::BasicErrorException, css::uno::RuntimeException)
-+{
-+ // Position - MsoBar MenuBar - sal_Bool
-+ // Currently only the Name is supported.
-+ rtl::OUString sName;
-+ if( !( Name >>= sName ) )
-+ {
-+ sName = rtl::OUString::createFromAscii("Custom1");
-+ }
-+ sal_Bool bTemporary = false;
-+ if( !( Temporary >>= bTemporary ) )
-+ {
-+ bTemporary = sal_True;
-+ }
-+ return uno::Reference< XCommandBar >( new ScVbaCommandBar( this, mxContext, sName.toAsciiLowerCase(), bTemporary, sal_True ) );
-+}
-+sal_Int32 SAL_CALL
-+ScVbaCommandBars::getCount() throw(css::uno::RuntimeException)
-+{
-+ // Filter out all toolbars from the window collection
-+ sal_Int32 nCount = 0;
-+ uno::Sequence< ::rtl::OUString > allNames = m_xNameAccess->getElementNames();
-+ for( sal_Int32 i = 0; i < allNames.getLength(); i++ )
-+ {
-+ if(allNames[i].indexOf( rtl::OUString::createFromAscii("private:resource/toolbar/") ) != -1 )
-+ {
-+ nCount++;
-+ }
-+ }
-+ return nCount;
-+}
-+
-+// ScVbaCollectionBaseImpl
-+uno::Any SAL_CALL
-+ScVbaCommandBars::Item( const uno::Any& aIndex, const uno::Any& /*aIndex2*/ ) throw( uno::RuntimeException )
-+{
-+ if( aIndex.getValueTypeClass() == uno::TypeClass_STRING )
-+ {
-+ return createCollectionObject( aIndex );
-+ }
-+
-+ // hardcode if "aIndex = 1" that would return "main menu".
-+ sal_Int16 nIndex = 0;
-+ aIndex >>= nIndex;
-+ if( nIndex == 1 )
-+ {
-+ uno::Any aSource;
-+ if( m_sModuleName.equalsIgnoreAsciiCase( sSpreadsheetDocumentUrl ) )
-+ aSource <<= rtl::OUString::createFromAscii( "Worksheet Menu Bar" );
-+ else if( m_sModuleName.equalsIgnoreAsciiCase( sTextDocumentUrl ) )
-+ aSource <<= rtl::OUString::createFromAscii( "Menu Bar" );
-+ if( aSource.hasValue() )
-+ return createCollectionObject( aSource );
-+ }
-+ return uno::Any();
-+}
-+
-+sal_Bool
-+ScVbaCommandBars::checkToolBarExist( rtl::OUString sToolBarName )
-+{
-+ CommandBarNameMap::const_iterator iter = mCommandBarNameMap.find( sToolBarName.toAsciiLowerCase() );
-+ if( iter != mCommandBarNameMap.end() )
-+ {
-+ return sal_True;
-+ }
-+ uno::Sequence< ::rtl::OUString > allNames = m_xNameAccess->getElementNames();
-+ for( sal_Int32 i = 0; i < allNames.getLength(); i++ )
-+ {
-+ if(allNames[i].indexOf( rtl::OUString::createFromAscii("private:resource/toolbar/") ) != -1 )
-+ {
-+ if( allNames[i].indexOf( sToolBarName ) != -1 )
-+ {
-+ return sal_True;
-+ }
-+ }
-+ }
-+ return sal_False;
-+}
-+
-+// XHelperInterface
-+rtl::OUString&
-+ScVbaCommandBars::getServiceImplName()
-+{
-+ static rtl::OUString sImplName( RTL_CONSTASCII_USTRINGPARAM("ScVbaCommandBars") );
-+ return sImplName;
-+}
-+uno::Sequence<rtl::OUString>
-+ScVbaCommandBars::getServiceNames()
-+{
-+ static uno::Sequence< rtl::OUString > aServiceNames;
-+ if ( aServiceNames.getLength() == 0 )
-+ {
-+ aServiceNames.realloc( 1 );
-+ aServiceNames[ 0 ] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.CommandBars" ) );
-+ }
-+ return aServiceNames;
-+}
-+
---- vbahelper/source/vbahelper/vbacommandbars.hxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ vbahelper/source/vbahelper/vbacommandbars.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,79 @@
-+/*************************************************************************
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile$
-+ *
-+ * $Revision$
-+ *
-+ * last change: $Author$ $Date$
-+ *
-+ * The Contents of this file are made available subject to
-+ * the terms of GNU Lesser General Public License Version 2.1.
-+ *
-+ *
-+ * GNU Lesser General Public License Version 2.1
-+ * =============================================
-+ * Copyright 2005 by Sun Microsystems, Inc.
-+ * 901 San Antonio Road, Palo Alto, CA 94303, USA
-+ *
-+ * This library is free software; you can redistribute it and/or
-+ * modify it under the terms of the GNU Lesser General Public
-+ * License version 2.1, as published by the Free Software Foundation.
-+ *
-+ * This library 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 for more details.
-+ *
-+ * You should have received a copy of the GNU Lesser General Public
-+ * License along with this library; if not, write to the Free Software
-+ * Foundation, Inc., 59 Temple Place, Suite 330, Boston,
-+ * MA 02111-1307 USA
-+ *
-+ ************************************************************************/
-+#ifndef SC_VBA_COMMANDBARS_HXX
-+#define SC_VBA_COMMANDBARS_HXX
-+
-+#include <ooo/vba/XCommandBar.hpp>
-+#include <ooo/vba/XCommandBars.hpp>
-+#include <com/sun/star/container/XNameAccess.hpp>
-+
-+#include <cppuhelper/implbase1.hxx>
-+
-+#include <vbahelper/vbahelperinterface.hxx>
-+#include <vbahelper/vbacollectionimpl.hxx>
-+
-+typedef CollTestImplHelper< ov::XCommandBars > CommandBars_BASE;
-+
-+class ScVbaCommandBars : public CommandBars_BASE
-+{
-+private:
-+ css::uno::Reference< css::container::XNameAccess > m_xNameAccess;
-+ rtl::OUString m_sModuleName;
-+ void retrieveObjects() throw( css::uno::RuntimeException );
-+public:
-+ ScVbaCommandBars( const css::uno::Reference< ov::XHelperInterface > xParent, const css::uno::Reference< css::uno::XComponentContext > xContext, const css::uno::Reference< css::container::XIndexAccess > xIndexAccess );
-+
-+ sal_Bool checkToolBarExist( rtl::OUString sToolBarName );
-+ rtl::OUString GetModuleName(){ return m_sModuleName; };
-+ css::uno::Reference< css::container::XNameAccess > GetWindows()
-+ {
-+ retrieveObjects();
-+ return m_xNameAccess;
-+ };
-+ // XCommandBars
-+ virtual css::uno::Reference< ov::XCommandBar > SAL_CALL Add( const css::uno::Any& Name, const css::uno::Any& Position, const css::uno::Any& MenuBar, const css::uno::Any& Temporary ) throw (css::script::BasicErrorException, css::uno::RuntimeException);
-+ // XEnumerationAccess
-+ virtual css::uno::Type SAL_CALL getElementType() throw (css::uno::RuntimeException);
-+ virtual css::uno::Reference< css::container::XEnumeration > SAL_CALL createEnumeration() throw (css::uno::RuntimeException);
-+ virtual css::uno::Any createCollectionObject( const css::uno::Any& aSource );
-+
-+ virtual sal_Int32 SAL_CALL getCount() throw(css::uno::RuntimeException);
-+ virtual css::uno::Any SAL_CALL Item( const css::uno::Any& aIndex, const css::uno::Any& /*aIndex2*/ ) throw( css::uno::RuntimeException);
-+ // XHelperInterface
-+ virtual rtl::OUString& getServiceImplName();
-+ virtual css::uno::Sequence<rtl::OUString> getServiceNames();
-+};
-+
-+#endif//SC_VBA_COMMANDBARS_HXX
---- vbahelper/source/vbahelper/vbadocumentbase.cxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ vbahelper/source/vbahelper/vbadocumentbase.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,223 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile:
-+ * $Revision:
-+ *
-+ * 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 <vbahelper/vbadocumentbase.hxx>
-+#include <vbahelper/helperdecl.hxx>
-+#include <comphelper/unwrapargs.hxx>
-+
-+#include <com/sun/star/util/XModifiable.hpp>
-+#include <com/sun/star/util/XProtectable.hpp>
-+#include <com/sun/star/util/XCloseable.hpp>
-+#include <com/sun/star/frame/XStorable.hpp>
-+#include <com/sun/star/frame/XFrame.hpp>
-+#include <com/sun/star/beans/XPropertySet.hpp>
-+
-+#include <tools/urlobj.hxx>
-+#include <osl/file.hxx>
-+
-+using namespace ::com::sun::star;
-+using namespace ::ooo::vba;
-+
-+VbaDocumentBase::VbaDocumentBase( const uno::Reference< ov::XHelperInterface >& xParent, const uno::Reference< uno::XComponentContext >& xContext) :VbaDocumentBase_BASE( xParent, xContext ), mxModel(NULL)
-+{
-+}
-+
-+VbaDocumentBase::VbaDocumentBase( const uno::Reference< ov::XHelperInterface >& xParent, const uno::Reference< uno::XComponentContext >& xContext, uno::Reference< frame::XModel > xModel ) : VbaDocumentBase_BASE( xParent, xContext ), mxModel( xModel )
-+{
-+}
-+
-+VbaDocumentBase::VbaDocumentBase( uno::Sequence< uno::Any> const & args,
-+ uno::Reference< uno::XComponentContext> const & xContext ) : VbaDocumentBase_BASE( getXSomethingFromArgs< XHelperInterface >( args, 0 ), xContext ), mxModel( getXSomethingFromArgs< frame::XModel >( args, 1 ) )
-+{
-+}
-+
-+::rtl::OUString
-+VbaDocumentBase::getName() throw (uno::RuntimeException)
-+{
-+ rtl::OUString sName = getModel()->getURL();
-+ if ( sName.getLength() )
-+ {
-+
-+ INetURLObject aURL( getModel()->getURL() );
-+ ::osl::File::getSystemPathFromFileURL( aURL.GetLastName(), sName );
-+ }
-+ else
-+ {
-+ const static rtl::OUString sTitle( RTL_CONSTASCII_USTRINGPARAM("Title" ) );
-+ // process "UntitledX - $(PRODUCTNAME)"
-+ uno::Reference< frame::XFrame > xFrame( getModel()->getCurrentController()->getFrame(), uno::UNO_QUERY_THROW );
-+ uno::Reference< beans::XPropertySet > xProps( xFrame, uno::UNO_QUERY_THROW );
-+ xProps->getPropertyValue(sTitle ) >>= sName;
-+ sal_Int32 pos = 0;
-+ sName = sName.getToken(0,' ',pos);
-+ }
-+ return sName;
-+}
-+::rtl::OUString
-+VbaDocumentBase::getPath() throw (uno::RuntimeException)
-+{
-+ INetURLObject aURL( getModel()->getURL() );
-+ aURL.CutLastName();
-+ return aURL.GetURLPath();
-+}
-+
-+::rtl::OUString
-+VbaDocumentBase::getFullName() throw (uno::RuntimeException)
-+{
-+ INetURLObject aURL( getModel()->getURL() );
-+ return aURL.GetURLPath();
-+}
-+void
-+VbaDocumentBase::Close( const uno::Any &rSaveArg, const uno::Any &rFileArg,
-+ const uno::Any &rRouteArg ) throw (uno::RuntimeException)
-+{
-+ sal_Bool bSaveChanges = sal_False;
-+ rtl::OUString aFileName;
-+ sal_Bool bRouteWorkbook = sal_True;
-+
-+ rSaveArg >>= bSaveChanges;
-+ sal_Bool bFileName = ( rFileArg >>= aFileName );
-+ rRouteArg >>= bRouteWorkbook;
-+ uno::Reference< frame::XStorable > xStorable( getModel(), uno::UNO_QUERY_THROW );
-+ uno::Reference< util::XModifiable > xModifiable( getModel(), uno::UNO_QUERY_THROW );
-+
-+ if( bSaveChanges )
-+ {
-+ if( xStorable->isReadonly() )
-+ {
-+ throw uno::RuntimeException(::rtl::OUString(
-+ RTL_CONSTASCII_USTRINGPARAM( "Unable to save to a read only file ") ),
-+ uno::Reference< XInterface >() );
-+ }
-+ if( bFileName )
-+ xStorable->storeAsURL( aFileName, uno::Sequence< beans::PropertyValue >(0) );
-+ else
-+ xStorable->store();
-+ }
-+ else
-+ xModifiable->setModified( false );
-+
-+ uno::Reference< util::XCloseable > xCloseable( getModel(), uno::UNO_QUERY );
-+
-+ if( xCloseable.is() )
-+ // use close(boolean DeliverOwnership)
-+
-+ // The boolean parameter DeliverOwnership tells objects vetoing the close process that they may
-+ // assume ownership if they object the closure by throwing a CloseVetoException
-+ // Here we give up ownership. To be on the safe side, catch possible veto exception anyway.
-+ xCloseable->close(sal_True);
-+ // If close is not supported by this model - try to dispose it.
-+ // But if the model disagree with a reset request for the modify state
-+ // we shouldn't do so. Otherwhise some strange things can happen.
-+ else
-+ {
-+ uno::Reference< lang::XComponent > xDisposable ( getCurrentDocument(), uno::UNO_QUERY );
-+ if ( xDisposable.is() )
-+ xDisposable->dispose();
-+ }
-+}
-+
-+void
-+VbaDocumentBase::Protect( const uno::Any &aPassword ) throw (uno::RuntimeException)
-+{
-+ rtl::OUString rPassword;
-+ uno::Reference< util::XProtectable > xProt( getModel(), uno::UNO_QUERY_THROW );
-+ SC_VBA_FIXME(("Workbook::Protect stub"));
-+ if( aPassword >>= rPassword )
-+ xProt->protect( rPassword );
-+ else
-+ xProt->protect( rtl::OUString() );
-+}
-+
-+void
-+VbaDocumentBase::Unprotect( const uno::Any &aPassword ) throw (uno::RuntimeException)
-+{
-+ rtl::OUString rPassword;
-+ uno::Reference< util::XProtectable > xProt( getModel(), uno::UNO_QUERY_THROW );
-+ if( !xProt->isProtected() )
-+ throw uno::RuntimeException(::rtl::OUString(
-+ RTL_CONSTASCII_USTRINGPARAM( "File is already unprotected" ) ),
-+ uno::Reference< XInterface >() );
-+ else
-+ {
-+ if( aPassword >>= rPassword )
-+ xProt->unprotect( rPassword );
-+ else
-+ xProt->unprotect( rtl::OUString() );
-+ }
-+}
-+
-+void
-+VbaDocumentBase::setSaved( sal_Bool bSave ) throw (uno::RuntimeException)
-+{
-+ uno::Reference< util::XModifiable > xModifiable( getModel(), uno::UNO_QUERY_THROW );
-+ xModifiable->setModified( bSave );
-+}
-+
-+sal_Bool
-+VbaDocumentBase::getSaved() throw (uno::RuntimeException)
-+{
-+ uno::Reference< util::XModifiable > xModifiable( getModel(), uno::UNO_QUERY_THROW );
-+ return xModifiable->isModified();
-+}
-+
-+void
-+VbaDocumentBase::Save() throw (uno::RuntimeException)
-+{
-+ rtl::OUString url = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM(".uno:Save"));
-+ uno::Reference< frame::XModel > xModel = getModel();
-+ dispatchRequests(xModel,url);
-+}
-+
-+void
-+VbaDocumentBase::Activate() throw (uno::RuntimeException)
-+{
-+ uno::Reference< frame::XFrame > xFrame( getModel()->getCurrentController()->getFrame(), uno::UNO_QUERY_THROW );
-+ xFrame->activate();
-+}
-+
-+rtl::OUString&
-+VbaDocumentBase::getServiceImplName()
-+{
-+ static rtl::OUString sImplName( RTL_CONSTASCII_USTRINGPARAM("VbaDocumentBase") );
-+ return sImplName;
-+}
-+
-+uno::Sequence< rtl::OUString >
-+VbaDocumentBase::getServiceNames()
-+{
-+ static uno::Sequence< rtl::OUString > aServiceNames;
-+ if ( aServiceNames.getLength() == 0 )
-+ {
-+ aServiceNames.realloc( 1 );
-+ aServiceNames[ 0 ] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.VbaDocumentBase" ) );
-+ }
-+ return aServiceNames;
-+}
-+
---- vbahelper/source/vbahelper/vbaglobalbase.cxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ vbahelper/source/vbahelper/vbaglobalbase.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,113 @@
-+/*************************************************************************
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile$
-+ *
-+ * $Revision$
-+ *
-+ * last change: $Author$ $Date$
-+ *
-+ * The Contents of this file are made available subject to
-+ * the terms of GNU Lesser General Public License Version 2.1.
-+ *
-+ *
-+ * GNU Lesser General Public License Version 2.1
-+ * =============================================
-+ * Copyright 2005 by Sun Microsystems, Inc.
-+ * 901 San Antonio Road, Palo Alto, CA 94303, USA
-+ *
-+ * This library is free software; you can redistribute it and/or
-+ * modify it under the terms of the GNU Lesser General Public
-+ * License version 2.1, as published by the Free Software Foundation.
-+ *
-+ * This library 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 for more details.
-+ *
-+ * You should have received a copy of the GNU Lesser General Public
-+ * License along with this library; if not, write to the Free Software
-+ * Foundation, Inc., 59 Temple Place, Suite 330, Boston,
-+ * MA 02111-1307 USA
-+ *
-+ ************************************************************************/
-+#include "vbahelper/vbaglobalbase.hxx"
-+
-+#include <cppuhelper/component_context.hxx>
-+#include <comphelper/processfactory.hxx>
-+#include <com/sun/star/container/XNameContainer.hpp>
-+
-+using namespace com::sun::star;
-+using namespace ooo::vba;
-+
-+VbaGlobalsBase::VbaGlobalsBase(
-+const uno::Reference< ov::XHelperInterface >& xParent,
-+const uno::Reference< uno::XComponentContext >& xContext)
-+: Globals_BASE( xParent, xContext )
-+{
-+ // overwrite context with custom one ( that contains the application )
-+ ::cppu::ContextEntry_Init aHandlerContextInfo[] =
-+ {
-+ ::cppu::ContextEntry_Init( ::rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "Application" ) ), uno::Any() )
-+ };
-+
-+ mxContext = ::cppu::createComponentContext( aHandlerContextInfo, sizeof( aHandlerContextInfo ) / sizeof( aHandlerContextInfo[0] ), xContext );
-+
-+}
-+
-+void
-+VbaGlobalsBase::init( uno::Reference< uno::XComponentContext >const& rxContext, const uno::Any& aApplication )
-+{
-+ uno::Reference< container::XNameContainer > xNameContainer( mxContext, uno::UNO_QUERY_THROW );
-+ xNameContainer->replaceByName( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("Application") ), aApplication );
-+ uno::Reference< XHelperInterface > xParent( aApplication, uno::UNO_QUERY );
-+ mxParent = xParent;
-+}
-+
-+uno::Reference< uno::XInterface > SAL_CALL
-+VbaGlobalsBase::createInstance( const ::rtl::OUString& aServiceSpecifier ) throw (uno::Exception, uno::RuntimeException)
-+{
-+ uno::Reference< uno::XInterface > xReturn;
-+
-+ if ( hasServiceName( aServiceSpecifier ) )
-+ xReturn = mxContext->getServiceManager()->createInstanceWithContext( aServiceSpecifier, mxContext );
-+ return xReturn;
-+}
-+
-+uno::Reference< uno::XInterface > SAL_CALL
-+VbaGlobalsBase::createInstanceWithArguments( const ::rtl::OUString& ServiceSpecifier, const uno::Sequence< uno::Any >& Arguments ) throw (uno::Exception, uno::RuntimeException)
-+{
-+
-+ uno::Reference< uno::XInterface > xReturn;
-+
-+ if ( hasServiceName( ServiceSpecifier ) )
-+ xReturn = mxContext->getServiceManager()->createInstanceWithArgumentsAndContext( ServiceSpecifier, Arguments, mxContext );
-+ return xReturn;
-+}
-+
-+uno::Sequence< ::rtl::OUString > SAL_CALL
-+VbaGlobalsBase::getAvailableServiceNames( ) throw (uno::RuntimeException)
-+{
-+ static const rtl::OUString names[] = {
-+ // common
-+ ::rtl::OUString( RTL_CONSTASCII_USTRINGPARAM ( "ooo.vba.msforms.UserForm" ) ),
-+ };
-+ static uno::Sequence< rtl::OUString > serviceNames( names, sizeof( names )/ sizeof( names[0] ) );
-+ return serviceNames;
-+}
-+
-+bool
-+VbaGlobalsBase::hasServiceName( const rtl::OUString& serviceName )
-+{
-+ uno::Sequence< rtl::OUString > sServiceNames( getAvailableServiceNames() );
-+ sal_Int32 nLen = sServiceNames.getLength();
-+ for ( sal_Int32 index = 0; index < nLen; ++index )
-+ {
-+ if ( sServiceNames[ index ].equals( serviceName ) )
-+ return true;
-+ }
-+ return false;
-+}
-+
-+
---- vbahelper/source/vbahelper/vbahelper.cxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ vbahelper/source/vbahelper/vbahelper.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,1170 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile: vbahelper.cxx,v $
-+ * $Revision: 1.5.32.1 $
-+ *
-+ * 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 <cppuhelper/bootstrap.hxx>
-+#include <com/sun/star/util/XURLTransformer.hpp>
-+#include <com/sun/star/frame/XDispatchProvider.hpp>
-+#include <com/sun/star/frame/XModel.hpp>
-+#include <com/sun/star/frame/XFrame.hpp>
-+#include <com/sun/star/frame/XDesktop.hpp>
-+#include <com/sun/star/frame/XController.hpp>
-+#include <com/sun/star/uno/XComponentContext.hpp>
-+#include <com/sun/star/lang/XMultiComponentFactory.hpp>
-+#include <com/sun/star/beans/XPropertySet.hpp>
-+#include <com/sun/star/beans/XIntrospection.hpp>
-+#include <ooo/vba/msforms/XShape.hpp>
-+
-+#include <comphelper/processfactory.hxx>
-+
-+#include <sfx2/objsh.hxx>
-+#include <sfx2/viewfrm.hxx>
-+#include <sfx2/dispatch.hxx>
-+#include <sfx2/app.hxx>
-+#include <svl/stritem.hxx>
-+#include <svl/eitem.hxx>
-+#include <svl/intitem.hxx>
-+#include <svl/itemset.hxx>
-+//#include <svtools/itempool.hxx>
-+#include <sfx2/docfac.hxx>
-+#include <sfx2/viewfac.hxx>
-+
-+#include <basic/sbx.hxx>
-+#include <basic/sbstar.hxx>
-+#include <basic/basmgr.hxx>
-+#include <basic/sbmod.hxx>
-+#include <basic/sbmeth.hxx>
-+#include <rtl/math.hxx>
-+#include <sfx2/viewsh.hxx>
-+#include <math.h>
-+#include <tools/urlobj.hxx>
-+#include <osl/file.hxx>
-+#include <toolkit/awt/vclxwindow.hxx>
-+#include <toolkit/helper/vclunohelper.hxx>
-+#include <com/sun/star/frame/XModel2.hpp>
-+#include <vcl/window.hxx>
-+#include <vcl/syswin.hxx>
-+#include <tools/diagnose_ex.h>
-+
-+#ifndef OOVBA_DLLIMPLEMENTATION
-+#define OOVBA_DLLIMPLEMENTATION
-+#endif
-+
-+#include <vbahelper/vbahelper.hxx>
-+#include <sfx2/app.hxx>
-+// #FIXME needs service
-+//#include "vbashape.hxx"
-+//#include "unonames.hxx"
-+
-+using namespace ::com::sun::star;
-+using namespace ::ooo::vba;
-+
-+#define NAME_HEIGHT "Height"
-+#define NAME_WIDTH "Width"
-+
-+#define POINTTO100THMILLIMETERFACTOR 35.27778
-+
-+void unoToSbxValue( SbxVariable* pVar, const uno::Any& aValue );
-+
-+uno::Any sbxToUnoValue( SbxVariable* pVar );
-+
-+
-+namespace ooo
-+{
-+namespace vba
-+{
-+
-+uno::Reference< lang::XMultiServiceFactory > getVBAServiceFactory( SfxObjectShell* pShell )
-+{
-+ uno::Any aUnoVar;
-+ if ( !pShell || ! pShell->GetBasicManager()->GetGlobalUNOConstant( "VBAGlobals", aUnoVar ) )
-+ throw lang::IllegalArgumentException();
-+ uno::Reference< lang::XMultiServiceFactory > xVBAFactory( aUnoVar, uno::UNO_QUERY_THROW );
-+ return xVBAFactory;
-+}
-+
-+css::uno::Reference< css::uno::XInterface > createVBAUnoAPIService( SfxObjectShell* pShell, const sal_Char* _pAsciiName ) throw (css::uno::RuntimeException)
-+{
-+ OSL_PRECOND( pShell, "createVBAUnoAPIService: no shell!" );
-+ ::rtl::OUString sVarName( ::rtl::OUString::createFromAscii( _pAsciiName ) );
-+ return getVBAServiceFactory( pShell )->createInstance( sVarName );
-+}
-+
-+css::uno::Reference< css::uno::XInterface > createVBAUnoAPIServiceWithArgs( SfxObjectShell* pShell, const sal_Char* _pAsciiName, const uno::Sequence< uno::Any >& aArgs ) throw ( css::uno::RuntimeException )
-+{
-+ OSL_PRECOND( pShell, "createVBAUnoAPIService: no shell!" );
-+ ::rtl::OUString sVarName( ::rtl::OUString::createFromAscii( _pAsciiName ) );
-+ uno::Reference< uno::XInterface > xIf = getVBAServiceFactory( pShell )->createInstanceWithArguments( sVarName, aArgs );
-+ return xIf;
-+}
-+// helper method to determine if the view ( calc ) is in print-preview mode
-+bool isInPrintPreview( SfxViewFrame* pView )
-+{
-+ sal_uInt16 nViewNo = SID_VIEWSHELL1 - SID_VIEWSHELL0;
-+ if ( pView->GetObjectShell()->GetFactory().GetViewFactoryCount() >
-+nViewNo && !pView->GetObjectShell()->IsInPlaceActive() )
-+ {
-+ SfxViewFactory &rViewFactory =
-+ pView->GetObjectShell()->GetFactory().GetViewFactory(nViewNo);
-+ if ( pView->GetCurViewId() == rViewFactory.GetOrdinal() )
-+ return true;
-+ }
-+ return false;
-+}
-+#if 0
-+namespace excel // all in this namespace probably can be moved to sc
-+{
-+
-+
-+const ::rtl::OUString REPLACE_CELLS_WARNING( RTL_CONSTASCII_USTRINGPARAM( "ReplaceCellsWarning"));
-+class PasteCellsWarningReseter
-+{
-+private:
-+ bool bInitialWarningState;
-+ static uno::Reference< beans::XPropertySet > getGlobalSheetSettings() throw ( uno::RuntimeException )
-+ {
-+ static uno::Reference< beans::XPropertySet > xTmpProps( ::comphelper::getProcessServiceFactory(), uno::UNO_QUERY_THROW );
-+ static uno::Reference<uno::XComponentContext > xContext( xTmpProps->getPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "DefaultContext" ))), uno::UNO_QUERY_THROW );
-+ static uno::Reference<lang::XMultiComponentFactory > xServiceManager(
-+ xContext->getServiceManager(), uno::UNO_QUERY_THROW );
-+ static uno::Reference< beans::XPropertySet > xProps( xServiceManager->createInstanceWithContext( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "com.sun.star.sheet.GlobalSheetSettings" ) ) ,xContext ), uno::UNO_QUERY_THROW );
-+ return xProps;
-+ }
-+
-+ bool getReplaceCellsWarning() throw ( uno::RuntimeException )
-+ {
-+ sal_Bool res = sal_False;
-+ getGlobalSheetSettings()->getPropertyValue( REPLACE_CELLS_WARNING ) >>= res;
-+ return ( res == sal_True );
-+ }
-+
-+ void setReplaceCellsWarning( bool bState ) throw ( uno::RuntimeException )
-+ {
-+ getGlobalSheetSettings()->setPropertyValue( REPLACE_CELLS_WARNING, uno::makeAny( bState ) );
-+ }
-+public:
-+ PasteCellsWarningReseter() throw ( uno::RuntimeException )
-+ {
-+ bInitialWarningState = getReplaceCellsWarning();
-+ if ( bInitialWarningState )
-+ setReplaceCellsWarning( false );
-+ }
-+ ~PasteCellsWarningReseter()
-+ {
-+ if ( bInitialWarningState )
-+ {
-+ // don't allow dtor to throw
-+ try
-+ {
-+ setReplaceCellsWarning( true );
-+ }
-+ catch ( uno::Exception& /*e*/ ){}
-+ }
-+ }
-+};
-+
-+void
-+implnPaste()
-+{
-+ PasteCellsWarningReseter resetWarningBox;
-+ ScTabViewShell* pViewShell = getCurrentBestViewShell();
-+ if ( pViewShell )
-+ {
-+ pViewShell->PasteFromSystem();
-+ pViewShell->CellContentChanged();
-+ }
-+}
-+
-+
-+void
-+implnCopy()
-+{
-+ ScTabViewShell* pViewShell = getCurrentBestViewShell();
-+ if ( pViewShell )
-+ pViewShell->CopyToClip(NULL,false,false,true);
-+}
-+
-+void
-+implnCut()
-+{
-+ ScTabViewShell* pViewShell = getCurrentBestViewShell();
-+ if ( pViewShell )
-+ pViewShell->CutToClip( NULL, TRUE );
-+}
-+void implnPasteSpecial(SfxViewShell* pViewShell, USHORT nFlags,USHORT nFunction,sal_Bool bSkipEmpty, sal_Bool bTranspose)
-+{
-+ PasteCellsWarningReseter resetWarningBox;
-+ sal_Bool bAsLink(sal_False), bOtherDoc(sal_False);
-+ InsCellCmd eMoveMode = INS_NONE;
-+
-+ if ( !pTabViewShell )
-+ // none active, try next best
-+ pTabViewShell = getCurrentBestViewShell();
-+ if ( pTabViewShell )
-+ {
-+ ScViewData* pView = pTabViewShell->GetViewData();
-+ Window* pWin = ( pView != NULL ) ? pView->GetActiveWin() : NULL;
-+ if ( pView && pWin )
-+ {
-+ if ( bAsLink && bOtherDoc )
-+ pTabViewShell->PasteFromSystem(0);//SOT_FORMATSTR_ID_LINK
-+ else
-+ {
-+ ScTransferObj* pOwnClip = ScTransferObj::GetOwnClipboard( pWin );
-+ ScDocument* pDoc = NULL;
-+ if ( pOwnClip )
-+ pDoc = pOwnClip->GetDocument();
-+ pTabViewShell->PasteFromClip( nFlags, pDoc,
-+ nFunction, bSkipEmpty, bTranspose, bAsLink,
-+ eMoveMode, IDF_NONE, TRUE );
-+ pTabViewShell->CellContentChanged();
-+ }
-+ }
-+ }
-+
-+}
-+
-+ScDocShell*
-+getDocShell( css::uno::Reference< css::frame::XModel>& xModel )
-+{
-+ uno::Reference< uno::XInterface > xIf( xModel, uno::UNO_QUERY_THROW );
-+ ScModelObj* pModel = dynamic_cast< ScModelObj* >( xIf.get() );
-+ ScDocShell* pDocShell = NULL;
-+ if ( pModel )
-+ pDocShell = (ScDocShell*)pModel->GetEmbeddedObject();
-+ return pDocShell;
-+
-+}
-+
-+ScTabViewShell*
-+getBestViewShell( css::uno::Reference< css::frame::XModel>& xModel )
-+{
-+ ScDocShell* pDocShell = getDocShell( xModel );
-+ if ( pDocShell )
-+ return pDocShell->GetBestViewShell();
-+ return NULL;
-+}
-+
-+ScTabViewShell*
-+getCurrentBestViewShell()
-+{
-+ uno::Reference< frame::XModel > xModel = getCurrentDocument();
-+ return getBestViewShell( xModel );
-+}
-+
-+SfxViewFrame*
-+getCurrentViewFrame()
-+{
-+ ScTabViewShell* pViewShell = getCurrentBestViewShell();
-+ if ( pViewShell )
-+ return pViewShell->GetViewFrame();
-+ return NULL;
-+}
-+};
-+
-+#endif
-+const double Millimeter::factor = 35.27778;
-+
-+uno::Reference< beans::XIntrospectionAccess >
-+getIntrospectionAccess( const uno::Any& aObject ) throw (uno::RuntimeException)
-+{
-+ static uno::Reference< beans::XIntrospection > xIntrospection;
-+ if( !xIntrospection.is() )
-+ {
-+ uno::Reference< lang::XMultiServiceFactory > xFactory( comphelper::getProcessServiceFactory(), uno::UNO_QUERY_THROW );
-+ xIntrospection.set( xFactory->createInstance( rtl::OUString::createFromAscii("com.sun.star.beans.Introspection") ), uno::UNO_QUERY_THROW );
-+ }
-+ return xIntrospection->inspect( aObject );
-+}
-+
-+uno::Reference< script::XTypeConverter >
-+getTypeConverter( const uno::Reference< uno::XComponentContext >& xContext ) throw (uno::RuntimeException)
-+{
-+ static uno::Reference< script::XTypeConverter > xTypeConv( xContext->getServiceManager()->createInstanceWithContext( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("com.sun.star.script.Converter") ), xContext ), uno::UNO_QUERY_THROW );
-+ return xTypeConv;
-+}
-+const uno::Any&
-+aNULL()
-+{
-+ static uno::Any aNULLL = uno::makeAny( uno::Reference< uno::XInterface >() );
-+ return aNULLL;
-+}
-+
-+void dispatchExecute(SfxViewShell* pViewShell, USHORT nSlot, SfxCallMode nCall)
-+{
-+ SfxViewFrame* pViewFrame = NULL;
-+ if ( pViewShell )
-+ pViewFrame = pViewShell->GetViewFrame();
-+ if ( pViewFrame )
-+ {
-+ SfxDispatcher* pDispatcher = pViewFrame->GetDispatcher();
-+ if( pDispatcher )
-+ {
-+ pDispatcher->Execute( nSlot , nCall );
-+ }
-+ }
-+}
-+
-+void
-+dispatchRequests (uno::Reference< frame::XModel>& xModel,rtl::OUString & aUrl, uno::Sequence< beans::PropertyValue >& sProps )
-+{
-+
-+ util::URL url ;
-+ url.Complete = aUrl;
-+ rtl::OUString emptyString = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "" ));
-+ uno::Reference<frame::XController> xController = xModel->getCurrentController();
-+ uno::Reference<frame::XFrame> xFrame = xController->getFrame();
-+ uno::Reference<frame::XDispatchProvider> xDispatchProvider (xFrame,uno::UNO_QUERY_THROW);
-+ try
-+ {
-+ uno::Reference< beans::XPropertySet > xProps( ::comphelper::getProcessServiceFactory(), uno::UNO_QUERY_THROW );
-+ uno::Reference<uno::XComponentContext > xContext( xProps->getPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "DefaultContext" ))), uno::UNO_QUERY_THROW );
-+ if ( !xContext.is() )
-+ {
-+ return ;
-+ }
-+
-+ uno::Reference<lang::XMultiComponentFactory > xServiceManager(
-+ xContext->getServiceManager() );
-+ if ( !xServiceManager.is() )
-+ {
-+ return ;
-+ }
-+ uno::Reference<util::XURLTransformer> xParser( xServiceManager->createInstanceWithContext( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "com.sun.star.util.URLTransformer" ) )
-+ ,xContext), uno::UNO_QUERY_THROW );
-+ if (!xParser.is())
-+ return;
-+ xParser->parseStrict (url);
-+ }
-+ catch ( uno::Exception & /*e*/ )
-+ {
-+ return ;
-+ }
-+
-+ uno::Reference<frame::XDispatch> xDispatcher = xDispatchProvider->queryDispatch(url,emptyString,0);
-+
-+ uno::Sequence<beans::PropertyValue> dispatchProps(1);
-+
-+ sal_Int32 nProps = sProps.getLength();
-+ beans::PropertyValue* pDest = dispatchProps.getArray();
-+ if ( nProps )
-+ {
-+ dispatchProps.realloc( nProps + 1 );
-+ // need to reaccquire pDest after realloc
-+ pDest = dispatchProps.getArray();
-+ beans::PropertyValue* pSrc = sProps.getArray();
-+ for ( sal_Int32 index=0; index<nProps; ++index, ++pSrc, ++pDest )
-+ *pDest = *pSrc;
-+ }
-+
-+ (*pDest).Name = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "Silent" ));
-+ (*pDest).Value <<= (sal_Bool)sal_True;
-+
-+ if (xDispatcher.is())
-+ xDispatcher->dispatch( url, dispatchProps );
-+}
-+
-+void
-+dispatchRequests (uno::Reference< frame::XModel>& xModel,rtl::OUString & aUrl)
-+{
-+ uno::Sequence<beans::PropertyValue> dispatchProps;
-+ dispatchRequests( xModel, aUrl, dispatchProps );
-+}
-+
-+
-+
-+ uno::Reference< frame::XModel >
-+getCurrentDocument() throw (uno::RuntimeException)
-+{
-+ uno::Reference< frame::XModel > xModel;
-+ SbxObject* pBasic = dynamic_cast< SbxObject* > ( SFX_APP()->GetBasic() );
-+ SbxObject* basicChosen = pBasic ;
-+ if ( basicChosen == NULL)
-+ {
-+ OSL_TRACE("getModelFromBasic() StarBASIC* is NULL" );
-+ return xModel;
-+ }
-+ SbxObject* p = pBasic;
-+ SbxObject* pParent = p->GetParent();
-+ SbxObject* pParentParent = pParent ? pParent->GetParent() : NULL;
-+
-+ if( pParentParent )
-+ {
-+ basicChosen = pParentParent;
-+ }
-+ else if( pParent )
-+ {
-+ basicChosen = pParent;
-+ }
-+
-+
-+ uno::Any aModel;
-+ SbxVariable *pCompVar = basicChosen->Find( UniString(RTL_CONSTASCII_USTRINGPARAM("ThisComponent")), SbxCLASS_OBJECT );
-+
-+ if ( pCompVar )
-+ {
-+ aModel = sbxToUnoValue( pCompVar );
-+ if ( sal_False == ( aModel >>= xModel ) ||
-+ !xModel.is() )
-+ {
-+ // trying last gasp try the current component
-+ uno::Reference< beans::XPropertySet > xProps( ::comphelper::getProcessServiceFactory(), uno::UNO_QUERY_THROW );
-+ // test if vba service is present
-+ uno::Reference< uno::XComponentContext > xCtx( xProps->getPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "DefaultContext" ))), uno::UNO_QUERY_THROW );
-+ uno::Reference<lang::XMultiComponentFactory > xSMgr( xCtx->getServiceManager(), uno::UNO_QUERY_THROW );
-+ uno::Reference< frame::XDesktop > xDesktop (xSMgr->createInstanceWithContext(::rtl::OUString::createFromAscii("com.sun.star.frame.Desktop"), xCtx), uno::UNO_QUERY_THROW );
-+ xModel.set( xDesktop->getCurrentComponent(), uno::UNO_QUERY );
-+ if ( !xModel.is() )
-+ {
-+ throw uno::RuntimeException(
-+ rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "Can't extract model from basic ( its obviously not set yet ) therefore don't know the currently selected document") ), uno::Reference< uno::XInterface >() );
-+ }
-+ return xModel;
-+ }
-+ else
-+ {
-+ OSL_TRACE("Have model ThisComponent points to url %s",
-+ ::rtl::OUStringToOString( xModel->getURL(),
-+ RTL_TEXTENCODING_ASCII_US ).pData->buffer );
-+ }
-+ }
-+ else
-+ {
-+ OSL_TRACE("Failed to get ThisComponent");
-+ throw uno::RuntimeException(
-+ rtl::OUString(
-+ RTL_CONSTASCII_USTRINGPARAM(
-+ "Can't determine the currently selected document") ),
-+ uno::Reference< uno::XInterface >() );
-+ }
-+ return xModel;
-+}
-+
-+sal_Int32
-+OORGBToXLRGB( sal_Int32 nCol )
-+{
-+ sal_Int32 nRed = nCol;
-+ nRed &= 0x00FF0000;
-+ nRed >>= 16;
-+ sal_Int32 nGreen = nCol;
-+ nGreen &= 0x0000FF00;
-+ nGreen >>= 8;
-+ sal_Int32 nBlue = nCol;
-+ nBlue &= 0x000000FF;
-+ sal_Int32 nRGB = ( (nBlue << 16) | (nGreen << 8) | nRed );
-+ return nRGB;
-+}
-+sal_Int32
-+XLRGBToOORGB( sal_Int32 nCol )
-+{
-+ sal_Int32 nBlue = nCol;
-+ nBlue &= 0x00FF0000;
-+ nBlue >>= 16;
-+ sal_Int32 nGreen = nCol;
-+ nGreen &= 0x0000FF00;
-+ nGreen >>= 8;
-+ sal_Int32 nRed = nCol;
-+ nRed &= 0x000000FF;
-+ sal_Int32 nRGB = ( (nRed << 16) | (nGreen << 8) | nBlue );
-+ return nRGB;
-+}
-+uno::Any
-+OORGBToXLRGB( const uno::Any& aCol )
-+{
-+ sal_Int32 nCol;
-+ aCol >>= nCol;
-+ nCol = OORGBToXLRGB( nCol );
-+ return uno::makeAny( nCol );
-+}
-+uno::Any
-+XLRGBToOORGB( const uno::Any& aCol )
-+{
-+ sal_Int32 nCol;
-+ aCol >>= nCol;
-+ nCol = XLRGBToOORGB( nCol );
-+ return uno::makeAny( nCol );
-+}
-+
-+void PrintOutHelper( SfxViewShell* pViewShell, const uno::Any& From, const uno::Any& To, const uno::Any& Copies, const uno::Any& Preview, const uno::Any& /*ActivePrinter*/, const uno::Any& /*PrintToFile*/, const uno::Any& Collate, const uno::Any& PrToFileName, sal_Bool bUseSelection )
-+{
-+ sal_Int32 nTo = 0;
-+ sal_Int32 nFrom = 0;
-+ sal_Int16 nCopies = 1;
-+ sal_Bool bPreview = sal_False;
-+ sal_Bool bCollate = sal_False;
-+ sal_Bool bSelection = bUseSelection;
-+ From >>= nFrom;
-+ To >>= nTo;
-+ Copies >>= nCopies;
-+ Preview >>= bPreview;
-+ if ( nCopies > 1 ) // Collate only useful when more that 1 copy
-+ Collate >>= bCollate;
-+
-+ rtl::OUString sRange( RTL_CONSTASCII_USTRINGPARAM( "-" ) );
-+ rtl::OUString sFileName;
-+
-+ if (( nFrom || nTo ) )
-+ {
-+ if ( nFrom )
-+ sRange = ( ::rtl::OUString::valueOf( nFrom ) + sRange );
-+ if ( nTo )
-+ sRange += ::rtl::OUString::valueOf( nTo );
-+ }
-+
-+ if ( PrToFileName.getValue() )
-+ {
-+ PrToFileName >>= sFileName;
-+ }
-+ SfxViewFrame* pViewFrame = NULL;
-+ if ( pViewShell )
-+ pViewFrame = pViewShell->GetViewFrame();
-+ if ( pViewFrame )
-+ {
-+ SfxAllItemSet aArgs( SFX_APP()->GetPool() );
-+
-+ SfxBoolItem sfxCollate( SID_PRINT_COLLATE, bCollate );
-+ aArgs.Put( sfxCollate, sfxCollate.Which() );
-+ SfxInt16Item sfxCopies( SID_PRINT_COPIES, nCopies );
-+ aArgs.Put( sfxCopies, sfxCopies.Which() );
-+ if ( sFileName.getLength() )
-+ {
-+ SfxStringItem sfxFileName( SID_FILE_NAME, sFileName);
-+ aArgs.Put( sfxFileName, sfxFileName.Which() );
-+
-+ }
-+ if ( sRange.getLength() )
-+ {
-+ SfxStringItem sfxRange( SID_PRINT_PAGES, sRange );
-+ aArgs.Put( sfxRange, sfxRange.Which() );
-+ }
-+ SfxBoolItem sfxSelection( SID_SELECTION, bSelection );
-+ aArgs.Put( sfxSelection, sfxSelection.Which() );
-+ SfxBoolItem sfxAsync( SID_ASYNCHRON, sal_False );
-+ aArgs.Put( sfxAsync, sfxAsync.Which() );
-+ SfxDispatcher* pDispatcher = pViewFrame->GetDispatcher();
-+
-+ if ( pDispatcher )
-+ {
-+ if ( bPreview )
-+ {
-+ if ( !pViewFrame->GetFrame()->IsInPlace() )
-+ {
-+ // #TODO is this necessary ( calc specific )
-+// SC_MOD()->InputEnterHandler();
-+ pViewFrame->GetDispatcher()->Execute( SID_VIEWSHELL1, SFX_CALLMODE_SYNCHRON );
-+ while ( isInPrintPreview( pViewFrame ) )
-+ Application::Yield();
-+ }
-+ }
-+ else
-+ pDispatcher->Execute( (USHORT)SID_PRINTDOC, (SfxCallMode)SFX_CALLMODE_SYNCHRON, aArgs );
-+ }
-+
-+ }
-+
-+ // #FIXME #TODO
-+ // 1 ActivePrinter ( how/can we switch a printer via API? )
-+ // 2 PrintToFile ( ms behaviour if this option is specified but no
-+ // filename supplied 'PrToFileName' then the user will be prompted )
-+ // 3 Need to check behaviour of Selected sheets with range ( e.g. From & To
-+ // values ) in oOO these options are mutually exclusive
-+ // 4 There is a pop up to do with transparent objects in the print source
-+ // should be able to disable that via configuration for the duration
-+ // of this method
-+}
-+
-+ void PrintPreviewHelper( const css::uno::Any& /*EnableChanges*/, SfxViewShell* pViewShell )
-+{
-+ dispatchExecute( pViewShell, SID_VIEWSHELL1 );
-+}
-+
-+rtl::OUString getAnyAsString( const uno::Any& pvargItem ) throw ( uno::RuntimeException )
-+{
-+ uno::Type aType = pvargItem.getValueType();
-+ uno::TypeClass eTypeClass = aType.getTypeClass();
-+ rtl::OUString sString;
-+ switch ( eTypeClass )
-+ {
-+ case uno::TypeClass_BOOLEAN:
-+ {
-+ sal_Bool bBool = sal_False;
-+ pvargItem >>= bBool;
-+ sString = rtl::OUString::valueOf( bBool );
-+ break;
-+ }
-+ case uno::TypeClass_STRING:
-+ pvargItem >>= sString;
-+ break;
-+ case uno::TypeClass_FLOAT:
-+ {
-+ float aFloat = 0;
-+ pvargItem >>= aFloat;
-+ sString = rtl::OUString::valueOf( aFloat );
-+ break;
-+ }
-+ case uno::TypeClass_DOUBLE:
-+ {
-+ double aDouble = 0;
-+ pvargItem >>= aDouble;
-+ sString = rtl::OUString::valueOf( aDouble );
-+ break;
-+ }
-+ case uno::TypeClass_SHORT:
-+ case uno::TypeClass_LONG:
-+ case uno::TypeClass_BYTE:
-+ {
-+ sal_Int32 aNum = 0;
-+ pvargItem >>= aNum;
-+ sString = rtl::OUString::valueOf( aNum );
-+ break;
-+ }
-+
-+ case uno::TypeClass_HYPER:
-+ {
-+ sal_Int64 aHyper = 0;
-+ pvargItem >>= aHyper;
-+ sString = rtl::OUString::valueOf( aHyper );
-+ break;
-+ }
-+ default:
-+ throw uno::RuntimeException( rtl::OUString::createFromAscii( "Invalid type, can't convert" ), uno::Reference< uno::XInterface >() );
-+ }
-+ return sString;
-+}
-+
-+
-+rtl::OUString
-+ContainerUtilities::getUniqueName( const uno::Sequence< ::rtl::OUString >& _slist, const rtl::OUString& _sElementName, const ::rtl::OUString& _sSuffixSeparator)
-+{
-+ return getUniqueName(_slist, _sElementName, _sSuffixSeparator, sal_Int32(2));
-+}
-+
-+rtl::OUString
-+ContainerUtilities::getUniqueName( const uno::Sequence< rtl::OUString >& _slist, const rtl::OUString _sElementName, const rtl::OUString& _sSuffixSeparator, sal_Int32 _nStartSuffix)
-+{
-+ sal_Int32 a = _nStartSuffix;
-+ rtl::OUString scompname = _sElementName;
-+ bool bElementexists = true;
-+ sal_Int32 nLen = _slist.getLength();
-+ if ( nLen == 0 )
-+ return _sElementName;
-+
-+ while (bElementexists == true)
-+ {
-+ for (sal_Int32 i = 0; i < nLen; i++)
-+ {
-+ if (FieldInList(_slist, scompname) == -1)
-+ {
-+ return scompname;
-+ }
-+ }
-+ scompname = _sElementName + _sSuffixSeparator + rtl::OUString::valueOf( a++ );
-+ }
-+ return rtl::OUString();
-+}
-+
-+sal_Int32
-+ContainerUtilities::FieldInList( const uno::Sequence< rtl::OUString >& SearchList, const rtl::OUString& SearchString )
-+{
-+ sal_Int32 FieldLen = SearchList.getLength();
-+ sal_Int32 retvalue = -1;
-+ for (sal_Int32 i = 0; i < FieldLen; i++)
-+ {
-+ // I wonder why comparing lexicographically is done
-+ // when its a match is whats interesting?
-+ //if (SearchList[i].compareTo(SearchString) == 0)
-+ if ( SearchList[i].equals( SearchString ) )
-+ {
-+ retvalue = i;
-+ break;
-+ }
-+ }
-+ return retvalue;
-+
-+}
-+bool NeedEsc(sal_Unicode cCode)
-+{
-+ String sEsc(RTL_CONSTASCII_USTRINGPARAM(".^$+\\|{}()"));
-+ return (STRING_NOTFOUND != sEsc.Search(cCode));
-+}
-+
-+rtl::OUString VBAToRegexp(const rtl::OUString &rIn, bool bForLike )
-+{
-+ rtl::OUStringBuffer sResult;
-+ const sal_Unicode *start = rIn.getStr();
-+ const sal_Unicode *end = start + rIn.getLength();
-+
-+ int seenright = 0;
-+ if ( bForLike )
-+ sResult.append(static_cast<sal_Unicode>('^'));
-+
-+ while (start < end)
-+ {
-+ switch (*start)
-+ {
-+ case '?':
-+ sResult.append(static_cast<sal_Unicode>('.'));
-+ start++;
-+ break;
-+ case '*':
-+ sResult.append(rtl::OUString(RTL_CONSTASCII_USTRINGPARAM(".*")));
-+ start++;
-+ break;
-+ case '#':
-+ sResult.append(rtl::OUString(RTL_CONSTASCII_USTRINGPARAM("[0-9]")));
-+ start++;
-+ break;
-+ case '~':
-+ sResult.append(static_cast<sal_Unicode>('\\'));
-+ sResult.append(*(++start));
-+ start++;
-+ break;
-+ // dump the ~ and escape the next characture
-+ case ']':
-+ sResult.append(static_cast<sal_Unicode>('\\'));
-+ sResult.append(*start++);
-+ break;
-+ case '[':
-+ sResult.append(*start++);
-+ seenright = 0;
-+ while (start < end && !seenright)
-+ {
-+ switch (*start)
-+ {
-+ case '[':
-+ case '?':
-+ case '*':
-+ sResult.append(static_cast<sal_Unicode>('\\'));
-+ sResult.append(*start);
-+ break;
-+ case ']':
-+ sResult.append(*start);
-+ seenright = 1;
-+ break;
-+ case '!':
-+ sResult.append(static_cast<sal_Unicode>('^'));
-+ break;
-+ default:
-+ if (NeedEsc(*start))
-+ sResult.append(static_cast<sal_Unicode>('\\'));
-+ sResult.append(*start);
-+ break;
-+ }
-+ start++;
-+ }
-+ break;
-+ default:
-+ if (NeedEsc(*start))
-+ sResult.append(static_cast<sal_Unicode>('\\'));
-+ sResult.append(*start++);
-+ }
-+ }
-+
-+ if ( bForLike )
-+ sResult.append(static_cast<sal_Unicode>('$'));
-+
-+ return sResult.makeStringAndClear( );
-+}
-+
-+double getPixelTo100thMillimeterConversionFactor( css::uno::Reference< css::awt::XDevice >& xDevice, sal_Bool bVertical)
-+{
-+ double fConvertFactor = 1.0;
-+ if( bVertical )
-+ {
-+ fConvertFactor = xDevice->getInfo().PixelPerMeterY/100000;
-+ }
-+ else
-+ {
-+ fConvertFactor = xDevice->getInfo().PixelPerMeterX/100000;
-+ }
-+ return fConvertFactor;
-+}
-+
-+double PointsToPixels( css::uno::Reference< css::awt::XDevice >& xDevice, double fPoints, sal_Bool bVertical)
-+{
-+ double fConvertFactor = getPixelTo100thMillimeterConversionFactor( xDevice, bVertical );
-+ return fPoints * POINTTO100THMILLIMETERFACTOR * fConvertFactor;
-+}
-+double PixelsToPoints( css::uno::Reference< css::awt::XDevice >& xDevice, double fPixels, sal_Bool bVertical)
-+{
-+ double fConvertFactor = getPixelTo100thMillimeterConversionFactor( xDevice, bVertical );
-+ return (fPixels/fConvertFactor)/POINTTO100THMILLIMETERFACTOR;
-+}
-+
-+ConcreteXShapeGeometryAttributes::ConcreteXShapeGeometryAttributes( const css::uno::Reference< css::uno::XComponentContext >& xContext, const css::uno::Reference< css::drawing::XShape >& xShape )
-+{
-+// #FIXME needs to be an instantiable service
-+// m_xShape = new ScVbaShape( xContext, xShape );
-+}
-+
-+static uno::Reference< frame::XController > lcl_getCurrentController()
-+{
-+ const uno::Reference< frame::XModel > xWorkingDoc( SfxObjectShell::GetCurrentComponent(), uno::UNO_QUERY );
-+ uno::Reference< frame::XController > xController;
-+ if ( xWorkingDoc.is() )
-+ xController.set( xWorkingDoc->getCurrentController(), uno::UNO_SET_THROW );
-+ else
-+ xController.set( SfxObjectShell::GetCurrentComponent(), uno::UNO_QUERY_THROW );
-+ return xController;
-+}
-+
-+sal_Int32 getPointerStyle()
-+{
-+ sal_Int32 nPointerStyle( POINTER_ARROW );
-+ try
-+ {
-+ const uno::Reference< frame::XController > xController( lcl_getCurrentController(), uno::UNO_SET_THROW );
-+ const uno::Reference< frame::XFrame > xFrame ( xController->getFrame(), uno::UNO_SET_THROW );
-+ const uno::Reference< awt::XWindow > xWindow ( xFrame->getContainerWindow(), uno::UNO_SET_THROW );
-+ // why the heck isn't there an XWindowPeer::getPointer, but a setPointer only?
-+ const Window* pWindow = VCLUnoHelper::GetWindow( xWindow );
-+ if ( pWindow )
-+ nPointerStyle = pWindow->GetSystemWindow()->GetPointer().GetStyle();
-+ }
-+ catch( const uno::Exception& )
-+ {
-+ DBG_UNHANDLED_EXCEPTION();
-+ }
-+ return nPointerStyle;
-+}
-+
-+void setCursorHelper( const Pointer& rPointer, sal_Bool bOverWrite )
-+{
-+ ::std::vector< uno::Reference< frame::XController > > aControllers;
-+
-+ const uno::Reference< frame::XModel2 > xModel2( SfxObjectShell::GetCurrentComponent(), uno::UNO_QUERY );
-+ if ( xModel2.is() )
-+ {
-+ const uno::Reference< container::XEnumeration > xEnumControllers( xModel2->getControllers(), uno::UNO_SET_THROW );
-+ while ( xEnumControllers->hasMoreElements() )
-+ {
-+ const uno::Reference< frame::XController > xController( xEnumControllers->nextElement(), uno::UNO_QUERY_THROW );
-+ aControllers.push_back( xController );
-+ }
-+ }
-+ else
-+ {
-+ const uno::Reference< frame::XModel > xModel( SfxObjectShell::GetCurrentComponent(), uno::UNO_QUERY );
-+ if ( xModel.is() )
-+ {
-+ const uno::Reference< frame::XController > xController( xModel->getCurrentController(), uno::UNO_SET_THROW );
-+ aControllers.push_back( xController );
-+ }
-+ else
-+ {
-+ const uno::Reference< frame::XController > xController( SfxObjectShell::GetCurrentComponent(), uno::UNO_QUERY_THROW );
-+ aControllers.push_back( xController );
-+ }
-+ }
-+
-+ for ( ::std::vector< uno::Reference< frame::XController > >::const_iterator controller = aControllers.begin();
-+ controller != aControllers.end();
-+ ++controller
-+ )
-+ {
-+ const uno::Reference< frame::XFrame > xFrame ( (*controller)->getFrame(), uno::UNO_SET_THROW );
-+ const uno::Reference< awt::XWindow > xWindow ( xFrame->getContainerWindow(), uno::UNO_SET_THROW );
-+
-+ Window* pWindow = VCLUnoHelper::GetWindow( xWindow );
-+ OSL_ENSURE( pWindow, "ScVbaApplication::setCursor: no window!" );
-+ if ( !pWindow )
-+ continue;
-+
-+ pWindow->GetSystemWindow()->SetPointer( rPointer );
-+ pWindow->GetSystemWindow()->EnableChildPointerOverwrite( bOverWrite );
-+ }
-+}
-+
-+String docMacroExists( SfxObjectShell* pShell, const String& sMod, const String& sMacro )
-+{
-+ String sFullName;
-+ // would use the script provider to see if the macro exists but
-+ // called at this stage tdoc content handler stuff is not set up
-+ // so it fails
-+
-+ String sLibrary( RTL_CONSTASCII_USTRINGPARAM("Standard"));
-+ BasicManager* pBasicMgr = pShell-> GetBasicManager();
-+ if ( pBasicMgr )
-+ {
-+ if ( pBasicMgr->GetName().Len() )
-+ sLibrary = pBasicMgr->GetName();
-+ StarBASIC* pBasic = pBasicMgr->GetLib( sLibrary );
-+ if ( !pBasic )
-+ {
-+ USHORT nId = pBasicMgr->GetLibId( sLibrary );
-+ pBasicMgr->LoadLib( nId );
-+ pBasic = pBasicMgr->GetLib( sLibrary );
-+ }
-+ if ( pBasic )
-+ {
-+ if ( sMod.Len() ) // we wish to find the macro is a specific module
-+ {
-+ SbModule* pModule = pBasic->FindModule( sMod );
-+ if ( pModule )
-+ {
-+ SbxArray* pMethods = pModule->GetMethods();
-+ if ( pMethods )
-+ {
-+ SbMethod* pMethod = static_cast< SbMethod* >( pMethods->Find( sMacro, SbxCLASS_METHOD ) );
-+ if ( pMethod )
-+ {
-+ sFullName = sMacro;
-+ sFullName.Insert( '.', 0 ).Insert( sMod, 0 ).Insert( '.', 0 ).Insert( sLibrary, 0 );
-+ }
-+ }
-+ }
-+ }
-+ else if( SbMethod* pMethod = dynamic_cast< SbMethod* >( pBasic->Find( sMacro, SbxCLASS_METHOD ) ) )
-+ {
-+ if( SbModule* pModule = pMethod->GetModule() )
-+ {
-+ sFullName = sMacro;
-+ sFullName.Insert( '.', 0 ).Insert( pModule->GetName(), 0).Insert( '.', 0 ).Insert( sLibrary, 0 );
-+ }
-+ }
-+
-+ }
-+ }
-+ return sFullName;
-+}
-+
-+#define VBA_LEFT "PositionX"
-+#define VBA_TOP "PositionY"
-+UserFormGeometryHelper::UserFormGeometryHelper( const uno::Reference< uno::XComponentContext >& /*xContext*/, const uno::Reference< awt::XControl >& xControl )
-+{
-+ mxModel.set( xControl->getModel(), uno::UNO_QUERY_THROW );
-+}
-+ double UserFormGeometryHelper::getLeft()
-+ {
-+ sal_Int32 nLeft = 0;
-+ mxModel->getPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( VBA_LEFT ) ) ) >>= nLeft;
-+ return Millimeter::getInPoints( nLeft );
-+ }
-+ void UserFormGeometryHelper::setLeft( double nLeft )
-+ {
-+ mxModel->setPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( VBA_LEFT ) ), uno::makeAny( Millimeter::getInHundredthsOfOneMillimeter( nLeft ) ) );
-+ }
-+ double UserFormGeometryHelper::getTop()
-+ {
-+ sal_Int32 nTop = 0;
-+ mxModel->getPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( VBA_TOP ) ) ) >>= nTop;
-+ return Millimeter::getInPoints( nTop );
-+ }
-+ void UserFormGeometryHelper::setTop( double nTop )
-+ {
-+ mxModel->setPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( VBA_TOP ) ), uno::makeAny( Millimeter::getInHundredthsOfOneMillimeter( nTop ) ) );
-+ }
-+ double UserFormGeometryHelper::getHeight()
-+ {
-+ sal_Int32 nHeight = 0;
-+ mxModel->getPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( NAME_HEIGHT ) ) ) >>= nHeight;
-+ return Millimeter::getInPoints( nHeight );
-+ }
-+ void UserFormGeometryHelper::setHeight( double nHeight )
-+ {
-+ mxModel->setPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( NAME_HEIGHT ) ), uno::makeAny( Millimeter::getInHundredthsOfOneMillimeter( nHeight ) ) );
-+ }
-+ double UserFormGeometryHelper::getWidth()
-+ {
-+ sal_Int32 nWidth = 0;
-+ mxModel->getPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( NAME_WIDTH ) ) ) >>= nWidth;
-+ return Millimeter::getInPoints( nWidth );
-+ }
-+ void UserFormGeometryHelper::setWidth( double nWidth)
-+ {
-+ mxModel->setPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( NAME_WIDTH ) ), uno::makeAny( Millimeter::getInHundredthsOfOneMillimeter( nWidth ) ) );
-+ }
-+
-+ double ConcreteXShapeGeometryAttributes::getLeft()
-+ {
-+ return m_xShape->getLeft();
-+ }
-+ void ConcreteXShapeGeometryAttributes::setLeft( double nLeft )
-+ {
-+ m_xShape->setLeft( nLeft );
-+ }
-+ double ConcreteXShapeGeometryAttributes::getTop()
-+ {
-+ return m_xShape->getTop();
-+ }
-+ void ConcreteXShapeGeometryAttributes::setTop( double nTop )
-+ {
-+ m_xShape->setTop( nTop );
-+ }
-+
-+ double ConcreteXShapeGeometryAttributes::getHeight()
-+ {
-+ return m_xShape->getHeight();
-+ }
-+ void ConcreteXShapeGeometryAttributes::setHeight( double nHeight )
-+ {
-+ m_xShape->setHeight( nHeight );
-+ }
-+ double ConcreteXShapeGeometryAttributes::getWidth()
-+ {
-+ return m_xShape->getWidth();
-+ }
-+ void ConcreteXShapeGeometryAttributes::setWidth( double nWidth)
-+ {
-+ m_xShape->setHeight( nWidth );
-+ }
-+
-+
-+ ShapeHelper::ShapeHelper( const css::uno::Reference< css::drawing::XShape >& _xShape) throw (css::script::BasicErrorException ) : xShape( _xShape )
-+ {
-+ if( !xShape.is() )
-+ throw css::uno::RuntimeException( rtl::OUString::createFromAscii("No valid shape for helper"), css::uno::Reference< css::uno::XInterface >() );
-+ }
-+
-+ double ShapeHelper::getHeight()
-+ {
-+ return Millimeter::getInPoints(xShape->getSize().Height);
-+ }
-+
-+
-+ void ShapeHelper::setHeight(double _fheight) throw ( css::script::BasicErrorException )
-+ {
-+ try
-+ {
-+ css::awt::Size aSize = xShape->getSize();
-+ aSize.Height = Millimeter::getInHundredthsOfOneMillimeter(_fheight);
-+ xShape->setSize(aSize);
-+ }
-+ catch ( css::uno::Exception& /*e*/)
-+ {
-+ throw css::script::BasicErrorException( rtl::OUString(), css::uno::Reference< css::uno::XInterface >(), SbERR_METHOD_FAILED, rtl::OUString() );
-+ }
-+ }
-+
-+
-+ double ShapeHelper::getWidth()
-+ {
-+ return Millimeter::getInPoints(xShape->getSize().Width);
-+ }
-+
-+ void ShapeHelper::setWidth(double _fWidth) throw ( css::script::BasicErrorException )
-+ {
-+ try
-+ {
-+ css::awt::Size aSize = xShape->getSize();
-+ aSize.Width = Millimeter::getInHundredthsOfOneMillimeter(_fWidth);
-+ xShape->setSize(aSize);
-+ }
-+ catch (css::uno::Exception& /*e*/)
-+ {
-+ throw css::script::BasicErrorException( rtl::OUString(), css::uno::Reference< css::uno::XInterface >(), SbERR_METHOD_FAILED, rtl::OUString() );
-+ }
-+ }
-+
-+
-+ double ShapeHelper::getLeft()
-+ {
-+ return Millimeter::getInPoints(xShape->getPosition().X);
-+ }
-+
-+
-+ void ShapeHelper::setLeft(double _fLeft)
-+ {
-+ css::awt::Point aPoint = xShape->getPosition();
-+ aPoint.X = Millimeter::getInHundredthsOfOneMillimeter(_fLeft);
-+ xShape->setPosition(aPoint);
-+ }
-+
-+
-+ double ShapeHelper::getTop()
-+ {
-+ return Millimeter::getInPoints(xShape->getPosition().Y);
-+ }
-+
-+
-+ void ShapeHelper::setTop(double _fTop)
-+ {
-+ css::awt::Point aPoint = xShape->getPosition();
-+ aPoint.Y = Millimeter::getInHundredthsOfOneMillimeter(_fTop);
-+ xShape->setPosition(aPoint);
-+ }
-+
-+ void DebugHelper::exception( const rtl::OUString& DetailedMessage, const css::uno::Exception& ex, int err, const rtl::OUString& /*additionalArgument*/ ) throw( css::script::BasicErrorException )
-+ {
-+ // #TODO #FIXME ( do we want to support additionalArg here )
-+ throw css::script::BasicErrorException( DetailedMessage.concat( rtl::OUString::createFromAscii(" ") ).concat( ex.Message ), css::uno::Reference< css::uno::XInterface >(), err, rtl::OUString() );
-+ }
-+
-+ void DebugHelper::exception( int err, const rtl::OUString& additionalArgument ) throw( css::script::BasicErrorException )
-+ {
-+ exception( rtl::OUString(), css::uno::Exception(), err, additionalArgument );
-+ }
-+ void DebugHelper::exception( css::uno::Exception& ex ) throw( css::script::BasicErrorException )
-+ {
-+ exception( rtl::OUString(), ex, SbERR_INTERNAL_ERROR, rtl::OUString() );
-+ }
-+
-+ Millimeter::Millimeter():m_nMillimeter(0) {}
-+
-+ Millimeter::Millimeter(double mm):m_nMillimeter(mm) {}
-+
-+ void Millimeter::set(double mm) { m_nMillimeter = mm; }
-+ void Millimeter::setInPoints(double points)
-+ {
-+ m_nMillimeter = points * 0.352777778;
-+ // 25.4mm / 72
-+ }
-+
-+ void Millimeter::setInHundredthsOfOneMillimeter(double hmm)
-+ {
-+ m_nMillimeter = hmm / 100;
-+ }
-+
-+ double Millimeter::get()
-+ {
-+ return m_nMillimeter;
-+ }
-+ double Millimeter::getInHundredthsOfOneMillimeter()
-+ {
-+ return m_nMillimeter * 100;
-+ }
-+ double Millimeter::getInPoints()
-+ {
-+ return m_nMillimeter * 2.834645669; // 72 / 25.4mm
-+ }
-+
-+ sal_Int32 Millimeter::getInHundredthsOfOneMillimeter(double points)
-+ {
-+ sal_Int32 mm = static_cast<sal_Int32>(points * factor);
-+ return mm;
-+ }
-+
-+ double Millimeter::getInPoints(int _hmm)
-+ {
-+ double points = double( static_cast<double>(_hmm) / factor);
-+ return points;
-+ }
-+
-+
-+} // openoffice
-+} //org
---- vbahelper/source/vbahelper/vbapropvalue.cxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ vbahelper/source/vbahelper/vbapropvalue.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,48 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile: vbapropvalue.cxx,v $
-+ * $Revision: 1.3 $
-+ *
-+ * 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 "vbahelper/vbapropvalue.hxx"
-+
-+using namespace com::sun::star;
-+
-+ScVbaPropValue::ScVbaPropValue( PropListener* pListener ) : m_pListener( pListener )
-+{
-+}
-+
-+css::uno::Any SAL_CALL
-+ScVbaPropValue::getValue() throw (css::uno::RuntimeException)
-+{
-+ return m_pListener->getValueEvent();
-+}
-+
-+void SAL_CALL
-+ScVbaPropValue::setValue( const css::uno::Any& _value ) throw (css::uno::RuntimeException)
-+{
-+ m_pListener->setValueEvent( _value );
-+}
---- vbahelper/source/vbahelper/vbawindowbase.cxx.old 1970-01-01 00:00:00.000000000 +0000
-+++ vbahelper/source/vbahelper/vbawindowbase.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,180 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2008 by Sun Microsystems, Inc.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile:
-+ * $Revision:
-+ *
-+ * 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 <vbahelper/helperdecl.hxx>
-+#include <vbahelper/vbawindowbase.hxx>
-+#include <com/sun/star/awt/XWindow.hpp>
-+#include <com/sun/star/awt/XWindow2.hpp>
-+#include <com/sun/star/awt/PosSize.hpp>
-+
-+using namespace ::com::sun::star;
-+using namespace ::ooo::vba;
-+
-+VbaWindowBase::VbaWindowBase( const uno::Reference< XHelperInterface >& xParent, const uno::Reference< uno::XComponentContext >& xContext, const uno::Reference< frame::XModel >& xModel ) : WindowBaseImpl_BASE( xParent, xContext ), m_xModel( xModel )
-+{
-+}
-+
-+VbaWindowBase::VbaWindowBase( uno::Sequence< uno::Any > const & args, uno::Reference< uno::XComponentContext > const & xContext )
-+ : WindowBaseImpl_BASE( getXSomethingFromArgs< XHelperInterface >( args, 0 ), xContext ),
-+ m_xModel( getXSomethingFromArgs< frame::XModel >( args, 1 ) )
-+{
-+}
-+
-+sal_Bool SAL_CALL
-+VbaWindowBase::getVisible() throw (uno::RuntimeException)
-+{
-+ sal_Bool bVisible = sal_True;
-+ uno::Reference< frame::XController > xController( m_xModel->getCurrentController(), uno::UNO_QUERY_THROW );
-+ uno::Reference< css::awt::XWindow > xWindow (xController->getFrame()->getContainerWindow(), uno::UNO_QUERY_THROW );
-+ uno::Reference< css::awt::XWindow2 > xWindow2 (xWindow, uno::UNO_QUERY_THROW );
-+ if( xWindow2.is() )
-+ {
-+ bVisible = xWindow2->isVisible();
-+ }
-+ return bVisible;
-+}
-+
-+void SAL_CALL
-+VbaWindowBase::setVisible(sal_Bool _visible) throw (uno::RuntimeException)
-+{
-+ uno::Reference< frame::XController > xController( m_xModel->getCurrentController(), uno::UNO_QUERY_THROW );
-+ uno::Reference< css::awt::XWindow > xWindow (xController->getFrame()->getContainerWindow(), uno::UNO_QUERY_THROW );
-+ if( xWindow.is() )
-+ {
-+ xWindow->setVisible( _visible );
-+ }
-+}
-+
-+css::awt::Rectangle getPosSize( const uno::Reference< frame::XModel >& xModel )
-+{
-+ css::awt::Rectangle aRect;
-+ uno::Reference< frame::XController > xController( xModel->getCurrentController(), uno::UNO_QUERY_THROW );
-+ uno::Reference< css::awt::XWindow > xWindow (xController->getFrame()->getContainerWindow(), uno::UNO_QUERY_THROW );
-+ if( xWindow.is() )
-+ {
-+ aRect = xWindow->getPosSize();
-+ }
-+ return aRect;
-+}
-+
-+void setPosSize( const uno::Reference< frame::XModel >& xModel, sal_Int32 nValue, USHORT nFlag )
-+{
-+ uno::Reference< frame::XController > xController( xModel->getCurrentController(), uno::UNO_QUERY_THROW );
-+ uno::Reference< css::awt::XWindow > xWindow (xController->getFrame()->getContainerWindow(), uno::UNO_QUERY_THROW );
-+ if( xWindow.is() )
-+ {
-+ css::awt::Rectangle aRect = xWindow->getPosSize();
-+ switch( nFlag )
-+ {
-+ case css::awt::PosSize::X:
-+ xWindow->setPosSize( nValue, aRect.Y, 0, 0, css::awt::PosSize::X );
-+ break;
-+ case css::awt::PosSize::Y:
-+ xWindow->setPosSize( aRect.X, nValue, 0, 0, css::awt::PosSize::Y );
-+ break;
-+ case css::awt::PosSize::WIDTH:
-+ xWindow->setPosSize( 0, 0, nValue, aRect.Height, css::awt::PosSize::WIDTH );
-+ break;
-+ case css::awt::PosSize::HEIGHT:
-+ xWindow->setPosSize( 0, 0, aRect.Width, nValue, css::awt::PosSize::HEIGHT );
-+ break;
-+ default:
-+ break;
-+ }
-+ }
-+}
-+
-+sal_Int32 SAL_CALL
-+VbaWindowBase::getHeight() throw (uno::RuntimeException)
-+{
-+ css::awt::Rectangle aRect = getPosSize(m_xModel);
-+ return aRect.Height;
-+}
-+
-+void SAL_CALL
-+VbaWindowBase::setHeight( sal_Int32 _height ) throw (uno::RuntimeException)
-+{
-+ setPosSize(m_xModel, _height, css::awt::PosSize::HEIGHT);
-+}
-+
-+sal_Int32 SAL_CALL
-+VbaWindowBase::getLeft() throw (uno::RuntimeException)
-+{
-+ css::awt::Rectangle aRect = getPosSize(m_xModel);
-+ return aRect.X;
-+}
-+
-+void SAL_CALL
-+VbaWindowBase::setLeft( sal_Int32 _left ) throw (uno::RuntimeException)
-+{
-+ setPosSize(m_xModel, _left, css::awt::PosSize::X);
-+}
-+sal_Int32 SAL_CALL
-+VbaWindowBase::getTop() throw (uno::RuntimeException)
-+{
-+ css::awt::Rectangle aRect = getPosSize(m_xModel);
-+ return aRect.Y;
-+}
-+
-+void SAL_CALL
-+VbaWindowBase::setTop( sal_Int32 _top ) throw (uno::RuntimeException)
-+{
-+ setPosSize(m_xModel, _top, css::awt::PosSize::Y);
-+}
-+sal_Int32 SAL_CALL
-+VbaWindowBase::getWidth() throw (uno::RuntimeException)
-+{
-+ css::awt::Rectangle aRect = getPosSize(m_xModel);
-+ return aRect.Width;
-+}
-+
-+void SAL_CALL
-+VbaWindowBase::setWidth( sal_Int32 _width ) throw (uno::RuntimeException)
-+{
-+ setPosSize(m_xModel, _width, css::awt::PosSize::WIDTH);
-+}
-+
-+rtl::OUString&
-+VbaWindowBase::getServiceImplName()
-+{
-+ static rtl::OUString sImplName( RTL_CONSTASCII_USTRINGPARAM("VbaWindowBase") );
-+ return sImplName;
-+}
-+
-+uno::Sequence< rtl::OUString >
-+VbaWindowBase::getServiceNames()
-+{
-+ static uno::Sequence< rtl::OUString > aServiceNames;
-+ if ( aServiceNames.getLength() == 0 )
-+ {
-+ aServiceNames.realloc( 1 );
-+ aServiceNames[ 0 ] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.VbaWindowBase" ) );
-+ }
-+ return aServiceNames;
-+}
---- vbahelper/util/makefile.mk.old 1970-01-01 00:00:00.000000000 +0000
-+++ vbahelper/util/makefile.mk 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,97 @@
-+#*************************************************************************
-+#
-+# DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+#
-+# Copyright 2008 by Sun Microsystems, Inc.
-+#
-+# OpenOffice.org - a multi-platform office productivity suite
-+#
-+# $RCSfile: makefile.mk,v $
-+#
-+# $Revision: 1.24 $
-+#
-+# 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.
-+#
-+#*************************************************************************
-+
-+PRJ=..
-+
-+PRJNAME=vbahelper
-+TARGET=vbahelper
-+
-+# --- Settings ---------------------------------------------------
-+
-+.INCLUDE : settings.mk
-+
-+
-+TARGET_HELPER=vbahelper
-+SHL1TARGET= $(TARGET_HELPER)$(DLLPOSTFIX)
-+SHL1IMPLIB= i$(TARGET_HELPER)
-+
-+SHL1DEF=$(MISC)$/$(SHL1TARGET).def
-+DEF1NAME=$(SHL1TARGET)
-+
-+LIB1FILES=$(SLB)$/$(TARGET_HELPER).lib
-+
-+# dynamic libraries
-+SHL1STDLIBS= \
-+ $(CPPULIB) \
-+ $(COMPHELPERLIB) \
-+ $(CPPUHELPERLIB) \
-+ $(BASICLIB) \
-+ $(TOOLSLIB) \
-+ $(SALLIB)\
-+ $(SFXLIB) \
-+ $(SVTOOLLIB) \
-+ $(SVLLIB) \
-+ $(VCLLIB) \
-+ $(SVTOOLLIB) \
-+ $(TKLIB) \
-+
-+#SHL4DEPN=$(SHL1TARGETN)
-+SHL1LIBS=$(LIB1FILES)
-+
-+TARGET_MSFORMS=msforms
-+SHL2TARGET=$(TARGET_MSFORMS)$(DLLPOSTFIX).uno
-+SHL2IMPLIB= i$(TARGET_MSFORMS)
-+
-+SHL2VERSIONMAP=$(TARGET_MSFORMS).map
-+SHL2DEF=$(MISC)$/$(SHL2TARGET).def
-+DEF2NAME=$(SHL2TARGET)
-+SHL2STDLIBS= \
-+ $(CPPUHELPERLIB) \
-+ $(CPPULIB) \
-+ $(COMPHELPERLIB) \
-+ $(SVLIB) \
-+ $(TOOLSLIB) \
-+ $(SALLIB)\
-+ $(VBAHELPERLIB) \
-+ $(SFXLIB) \
-+ $(SVXLIB) \
-+ $(SVTOOLLIB) \
-+ $(SVLLIB) \
-+ $(VCLLIB) \
-+ $(TKLIB) \
-+ $(BASICLIB) \
-+
-+SHL2DEPN=$(SHL1TARGETN)
-+SHL2LIBS=$(SLB)$/$(TARGET_MSFORMS).lib
-+
-+# --- Targets -----------------------------------------------------------
-+
-+.INCLUDE : target.mk
---- vbahelper/util/msforms.map.old 1970-01-01 00:00:00.000000000 +0000
-+++ vbahelper/util/msforms.map 2009-04-06 16:42:01.000000000 +0000
-@@ -0,0 +1,9 @@
-+OOO_1.1 {
-+ global:
-+ component_getImplementationEnvironment;
-+ component_getFactory;
-+ component_writeInfo;
-+
-+ local:
-+ *;
-+};
---- basic/source/uno/namecont.cxx.old 2009-04-06 16:41:59.000000000 +0000
-+++ basic/source/uno/namecont.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -2730,6 +2730,10 @@ OUString SfxLibraryContainer::expand_url
- {
- // get the standard library
- String aLibName( RTL_CONSTASCII_USTRINGPARAM( "Standard" ) );
-+
-+ if ( pBasMgr->GetName().Len() )
-+ aLibName = pBasMgr->GetName();
-+
- StarBASIC* pBasic = pBasMgr->GetLib( aLibName );
- if( pBasic )
- bVBACompat = pBasic->isVBAEnabled();
---- sc/inc/cellsuno.hxx.old 2009-04-02 10:45:43.000000000 +0000
-+++ sc/inc/cellsuno.hxx 2009-04-06 16:42:01.000000000 +0000
-@@ -152,8 +152,10 @@ public:
- namespace ooo
- {
- namespace vba {
-+ namespace excel {
- class ScVbaCellRangeAccess; // Vba Helper class
- }
-+ }
- }
-
- class SC_DLLPUBLIC ScCellRangesBase : public com::sun::star::beans::XPropertySet,
-@@ -175,7 +177,7 @@ class SC_DLLPUBLIC ScCellRangesBase : pu
- {
- friend class ScTabViewObj; // fuer select()
- friend class ScTableSheetObj; // fuer createCursorByRange()
-- friend class ooo::vba::ScVbaCellRangeAccess;
-+ friend class ooo::vba::excel::ScVbaCellRangeAccess;
-
- private:
- SfxItemPropertySet aPropSet;
---- sc/source/ui/vba/vbafont.cxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbafont.cxx 2009-04-06 16:42:01.000000000 +0000
-@@ -76,7 +76,7 @@ ScVbaFont::ScVbaFont( const uno::Referen
- SfxItemSet*
- ScVbaFont::GetDataSet()
- {
-- SfxItemSet* pDataSet = ScVbaCellRangeAccess::GetDataSet( mpRangeObj );
-+ SfxItemSet* pDataSet = excel::ScVbaCellRangeAccess::GetDataSet( mpRangeObj );
- return pDataSet;
- }
-