summaryrefslogtreecommitdiff
path: root/patches/vba/vba-dont-load-for-odf.diff
diff options
context:
space:
mode:
Diffstat (limited to 'patches/vba/vba-dont-load-for-odf.diff')
-rw-r--r--patches/vba/vba-dont-load-for-odf.diff522
1 files changed, 0 insertions, 522 deletions
diff --git a/patches/vba/vba-dont-load-for-odf.diff b/patches/vba/vba-dont-load-for-odf.diff
deleted file mode 100644
index 1e714f865..000000000
--- a/patches/vba/vba-dont-load-for-odf.diff
+++ /dev/null
@@ -1,522 +0,0 @@
-From 9c77225910a7bc637ecbaf83659502c816866621 Mon Sep 17 00:00:00 2001
-From: Jan Holesovsky <kendy@suse.cz>
-Date: Fri, 14 May 2010 17:00:03 +0200
-Subject: [PATCH 392/878] vba-dont-load-for-odf.diff
-
----
- forms/source/misc/InterfaceContainer.cxx | 2 +-
- sc/source/core/data/documen2.cxx | 3 +-
- sc/source/core/tool/interpr4.cxx | 4 +-
- sc/source/filter/excel/excimp8.cxx | 11 ++++
- sc/source/ui/docshell/docsh.cxx | 2 +
- sc/source/ui/docshell/docsh2.cxx | 2 +
- sc/source/ui/unoobj/servuno.cxx | 18 +++++--
- sc/util/makefile.mk | 1 -
- svx/source/form/fmundo.cxx | 47 ++++++++++-------
- sw/source/core/doc/doc.cxx | 3 +-
- sw/source/core/unocore/unocoll.cxx | 13 +++--
- sw/util/makefile.mk | 1 -
- vbahelper/inc/vbahelper/vbaaccesshelper.hxx | 79 +++++++++++++++++++++++++++
- vbahelper/inc/vbahelper/vbahelper.hxx | 12 +++--
- vbahelper/prj/d.lst | 1 +
- vbahelper/source/vbahelper/vbahelper.cxx | 16 ------
- 16 files changed, 158 insertions(+), 57 deletions(-)
- create mode 100644 vbahelper/inc/vbahelper/vbaaccesshelper.hxx
-
-diff --git a/forms/source/misc/InterfaceContainer.cxx b/forms/source/misc/InterfaceContainer.cxx
-index de4e1a2..6b7acbc 100644
---- a/forms/source/misc/InterfaceContainer.cxx
-+++ b/forms/source/misc/InterfaceContainer.cxx
-@@ -145,9 +145,9 @@ OInterfaceContainer::fakeVbaEventsHack( sal_Int32 _nIndex )
- {
- try
- {
-+ Reference< XCodeNameQuery > xNameQuery( xDocFac->createInstance( rtl::OUString::createFromAscii( "ooo.vba.VBACodeNameProvider" ) ), UNO_QUERY_THROW );
- 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 );
-diff --git a/sc/source/core/data/documen2.cxx b/sc/source/core/data/documen2.cxx
-index 5b4e826..a732d8d 100644
---- a/sc/source/core/data/documen2.cxx
-+++ b/sc/source/core/data/documen2.cxx
-@@ -95,6 +95,7 @@
- #include "clipparam.hxx"
- #include "macromgr.hxx"
- #include <com/sun/star/document/XVbaEventsHelper.hpp>
-+#include <vbahelper/vbaaccesshelper.hxx>
-
- // pImpl because including lookupcache.hxx in document.hxx isn't wanted, and
- // dtor plus helpers are convenient.
-@@ -1257,7 +1258,7 @@ using namespace com::sun::star;
- uno::Reference< document::XVbaEventsHelper >
- ScDocument::GetVbaEventsHelper()
- {
-- if( !mxVbaEventsHelper.is() )
-+ if( !mxVbaEventsHelper.is() && pShell && ooo::vba::isAlienExcelDoc( *pShell ) )
- {
- try
- {
-diff --git a/sc/source/core/tool/interpr4.cxx b/sc/source/core/tool/interpr4.cxx
-index a4e9af2..03e9c90 100644
---- a/sc/source/core/tool/interpr4.cxx
-+++ b/sc/source/core/tool/interpr4.cxx
-@@ -78,8 +78,8 @@
- #include <map>
- #include <algorithm>
- #include <functional>
--#include <vbahelper/vbahelper.hxx>
- #include <basic/basmgr.hxx>
-+#include <vbahelper/vbaaccesshelper.hxx>
- #include <memory>
-
- using namespace com::sun::star;
-@@ -2710,7 +2710,7 @@ lcl_setVBARange( ScRange& aRange, ScDocument* pDok, SbxVariable* pPar )
- uno::Sequence< uno::Any > aArgs(2);
- aArgs[0] = uno::Any( uno::Reference< uno::XInterface >() ); // dummy parent
- aArgs[1] = uno::Any( xCellRange );
-- xVBARange = ov::createVBAUnoAPIServiceWithArgs( pDok->GetDocumentShell(), "ooo.vba.excel.Range", aArgs );
-+ xVBARange = ooo::vba::createVBAUnoAPIServiceWithArgs( pDok->GetDocumentShell(), "ooo.vba.excel.Range", aArgs );
- if ( xVBARange.is() )
- {
- String sDummy(RTL_CONSTASCII_USTRINGPARAM("A-Range") );
-diff --git a/sc/source/filter/excel/excimp8.cxx b/sc/source/filter/excel/excimp8.cxx
-index 05c4384..32a529a 100644
---- a/sc/source/filter/excel/excimp8.cxx
-+++ b/sc/source/filter/excel/excimp8.cxx
-@@ -275,6 +275,17 @@ void ImportExcel8::ReadBasic( void )
- {
- SvxImportMSVBasic aBasicImport( *pShell, *xRootStrg, bLoadCode, bLoadStrg );
- bool bAsComment = !bLoadExecutable;
-+ if ( !bAsComment )
-+ {
-+ uno::Any aGlobs;
-+ uno::Sequence< uno::Any > aArgs(1);
-+ aArgs[ 0 ] <<= pShell->GetModel();
-+ aGlobs <<= ::comphelper::getProcessServiceFactory()->createInstanceWithArguments( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "ooo.vba.excel.Globals" ) ), aArgs );
-+ pShell->GetBasicManager()->SetGlobalUNOConstant( "VBAGlobals", aGlobs );
-+ BasicManager* pAppMgr = SFX_APP()->GetBasicManager();
-+ if ( pAppMgr )
-+ pAppMgr->SetGlobalUNOConstant( "ThisExcelDoc", aArgs[ 0 ] );
-+ }
- aBasicImport.Import( EXC_STORAGE_VBA_PROJECT, EXC_STORAGE_VBA, bAsComment );
- if ( !bAsComment )
- {
-diff --git a/sc/source/ui/docshell/docsh.cxx b/sc/source/ui/docshell/docsh.cxx
-index 4e3ae87..5bc2743 100644
---- a/sc/source/ui/docshell/docsh.cxx
-+++ b/sc/source/ui/docshell/docsh.cxx
-@@ -370,6 +370,7 @@ void ScDocShell::AfterXMLLoading(sal_Bool bRet)
- }
- else
- aDocument.SetInsertingFromOtherDoc( FALSE );
-+#if 0
- // add vba globals ( if they are availabl )
- uno::Any aGlobs;
- uno::Sequence< uno::Any > aArgs(1);
-@@ -396,6 +397,7 @@ void ScDocShell::AfterXMLLoading(sal_Bool bRet)
- if ( xEvt.is() )
- xEvt->setIgnoreEvents( sal_False );
- #endif
-+#endif
- aDocument.SetImportingXML( FALSE );
- aDocument.EnableExecuteLink( true );
- aDocument.EnableUndo( TRUE );
-diff --git a/sc/source/ui/docshell/docsh2.cxx b/sc/source/ui/docshell/docsh2.cxx
-index 91a9204..8ca6e5f 100644
---- a/sc/source/ui/docshell/docsh2.cxx
-+++ b/sc/source/ui/docshell/docsh2.cxx
-@@ -102,6 +102,7 @@ BOOL __EXPORT ScDocShell::InitNew( const uno::Reference < embed::XStorage >& xSt
-
- InitItems();
- CalcOutputFactor();
-+#if 0
- uno::Any aGlobs;
- uno::Sequence< uno::Any > aArgs(1);
- aArgs[ 0 ] <<= GetModel();
-@@ -121,6 +122,7 @@ BOOL __EXPORT ScDocShell::InitNew( const uno::Reference < embed::XStorage >& xSt
- BasicManager* pAppMgr = SFX_APP()->GetBasicManager();
- if ( pAppMgr )
- pAppMgr->SetGlobalUNOConstant( "ThisExcelDoc", aArgs[ 0 ] );
-+#endif
-
- return bRet;
- }
-diff --git a/sc/source/ui/unoobj/servuno.cxx b/sc/source/ui/unoobj/servuno.cxx
-index aec4384..e97bf57 100644
---- a/sc/source/ui/unoobj/servuno.cxx
-+++ b/sc/source/ui/unoobj/servuno.cxx
-@@ -66,7 +66,7 @@
- #include <com/sun/star/script/ScriptEventDescriptor.hpp>
- #include <comphelper/componentcontext.hxx>
- #include <cppuhelper/component_context.hxx>
--#include <vbahelper/vbahelper.hxx>
-+#include <vbahelper/vbaaccesshelper.hxx>
- using namespace ::com::sun::star;
-
- class ScVbaObjectForCodeNameProvider : public ::cppu::WeakImplHelper1< container::XNameAccess >
-@@ -84,7 +84,7 @@ public:
- 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 );
-+ maWorkbook <<= ooo::vba::createVBAUnoAPIServiceWithArgs( mpDocShell, "ooo.vba.excel.Workbook", aArgs );
- }
-
- virtual ::sal_Bool SAL_CALL hasByName( const ::rtl::OUString& aName ) throw (::com::sun::star::uno::RuntimeException )
-@@ -117,7 +117,7 @@ public:
- aArgs[0] = maWorkbook;
- aArgs[1] = uno::Any( xModel );
- aArgs[2] = uno::Any( rtl::OUString( sSheetName ) );
-- maCachedObject <<= ov::createVBAUnoAPIServiceWithArgs( mpDocShell, "ooo.vba.excel.Worksheet", aArgs );
-+ maCachedObject <<= ooo::vba::createVBAUnoAPIServiceWithArgs( mpDocShell, "ooo.vba.excel.Worksheet", aArgs );
- break;
- }
- }
-@@ -532,10 +532,18 @@ uno::Reference<uno::XInterface> ScServiceProvider::MakeInstance(
- }
- break;
- case SC_SERVICE_VBAOBJECTPROVIDER:
-- xRet.set(static_cast<container::XNameAccess*>(new ScVbaObjectForCodeNameProvider( pDocShell )));
-+ if ( pDocShell && ooo::vba::isAlienExcelDoc( *pDocShell ) )
-+ {
-+ OSL_TRACE("**** creating VBA Object mapper");
-+ xRet.set(static_cast<container::XNameAccess*>(new ScVbaObjectForCodeNameProvider( pDocShell )));
-+ }
- break;
- case SC_SERVICE_VBACODENAMEPROVIDER:
-- xRet.set(static_cast<document::XCodeNameQuery*>(new ScVbaCodeNameProvider( pDocShell )));
-+ if ( pDocShell && ooo::vba::isAlienExcelDoc( *pDocShell ) )
-+ {
-+ OSL_TRACE("**** creating VBA Object provider");
-+ xRet.set(static_cast<document::XCodeNameQuery*>(new ScVbaCodeNameProvider( pDocShell )));
-+ }
- break;
- }
- return xRet;
-diff --git a/sc/util/makefile.mk b/sc/util/makefile.mk
-index a20cc03..cccfae0 100644
---- a/sc/util/makefile.mk
-+++ b/sc/util/makefile.mk
-@@ -75,7 +75,6 @@ SHL1IMPLIB= sci
-
- # dynamic libraries
- SHL1STDLIBS= \
-- $(VBAHELPERLIB) \
- $(BASICLIB) \
- $(SFXLIB) \
- $(SVTOOLLIB) \
-diff --git a/svx/source/form/fmundo.cxx b/svx/source/form/fmundo.cxx
-index 5082693..6112fdc 100644
---- a/svx/source/form/fmundo.cxx
-+++ b/svx/source/form/fmundo.cxx
-@@ -95,25 +95,7 @@ class ScriptEventListenerWrapper : public ScriptEventListener_BASE
- public:
- ScriptEventListenerWrapper( FmFormModel& _rModel) throw ( RuntimeException ) : pModel(&_rModel)
- {
-- Reference < XPropertySet > xProps(
-- ::comphelper::getProcessServiceFactory(), UNO_QUERY );
-- if ( xProps.is() )
-- {
-- Reference< XComponentContext > xCtx( xProps->getPropertyValue(
-- rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "DefaultContext" ))), UNO_QUERY );
-- if ( xCtx.is() )
-- {
-- Reference< XMultiComponentFactory > xMFac(
-- xCtx->getServiceManager(), UNO_QUERY );
-- if ( xMFac.is() )
-- {
-- m_vbaListener.set( xMFac->createInstanceWithContext(
-- rtl::OUString( RTL_CONSTASCII_USTRINGPARAM(
-- "ooo.vba.EventListener" ) ), xCtx ),
-- UNO_QUERY_THROW );
-- }
-- }
-- }
-+
- }
- // XEventListener
- virtual void SAL_CALL disposing(const EventObject& ) throw( RuntimeException ){}
-@@ -141,6 +123,33 @@ public:
- private:
- void setModel()
- {
-+ if ( !m_vbaListener.is() )
-+ {
-+ Reference < XPropertySet > xProps(
-+ ::comphelper::getProcessServiceFactory(), UNO_QUERY );
-+ if ( xProps.is() )
-+ {
-+ Reference< XComponentContext > xCtx( xProps->getPropertyValue(
-+ rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "DefaultContext" ))), UNO_QUERY );
-+ if ( xCtx.is() )
-+ {
-+ Reference< XMultiComponentFactory > xMFac(
-+ xCtx->getServiceManager(), UNO_QUERY );
-+ SfxObjectShellRef xObjSh = pModel->GetObjectShell();
-+ Reference< XMultiServiceFactory > xDocFac;
-+ if ( xObjSh.Is() )
-+ xDocFac.set( xObjSh->GetModel(), UNO_QUERY );
-+
-+ if ( xMFac.is() )
-+ {
-+ m_vbaListener.set( xMFac->createInstanceWithContext(
-+ rtl::OUString( RTL_CONSTASCII_USTRINGPARAM(
-+ "ooo.vba.EventListener" ) ), xCtx ),
-+ UNO_QUERY_THROW );
-+ }
-+ }
-+ }
-+ }
- Reference< XPropertySet > xProps( m_vbaListener, UNO_QUERY );
- if ( xProps.is() )
- {
-diff --git a/sw/source/core/doc/doc.cxx b/sw/source/core/doc/doc.cxx
-index a223dc7..1f61019 100644
---- a/sw/source/core/doc/doc.cxx
-+++ b/sw/source/core/doc/doc.cxx
-@@ -107,6 +107,7 @@
-
- #include <osl/diagnose.h>
- #include <osl/interlck.h>
-+#include <vbahelper/vbaaccesshelper.hxx>
-
- /* @@@MAINTAINABILITY-HORROR@@@
- Probably unwanted dependency on SwDocShell
-@@ -2007,7 +2008,7 @@ void SwDoc::ChkCondColls()
- uno::Reference< document::XVbaEventsHelper >
- SwDoc::GetVbaEventsHelper()
- {
-- if( !mxVbaEventsHelper.is() )
-+ if( !mxVbaEventsHelper.is() && GetDocShell() && ooo::vba::isAlienWordDoc( *GetDocShell() ) )
- {
- try
- {
-diff --git a/sw/source/core/unocore/unocoll.cxx b/sw/source/core/unocore/unocoll.cxx
-index 73acb2d..25c8297 100644
---- a/sw/source/core/unocore/unocoll.cxx
-+++ b/sw/source/core/unocore/unocoll.cxx
-@@ -81,7 +81,7 @@
- #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 <vbahelper/vbaaccesshelper.hxx>
- #include <basic/basmgr.hxx>
-
- using ::rtl::OUString;
-@@ -255,7 +255,7 @@ public:
- 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 );
-+ uno::Reference< uno::XInterface > xDocObj = ooo::vba::createVBAUnoAPIServiceWithArgs( mpDocShell, "ooo.vba.word.Document" , aArgs );
- OSL_TRACE("Creating Object ( ooo.vba.word.Document ) 0x%x", xDocObj.get() );
- return uno::makeAny( xDocObj );
- }
-@@ -583,14 +583,17 @@ uno::Reference< uno::XInterface > SwXServiceProvider::MakeInstance(sal_uInt16
- break;
- case SW_SERVICE_VBACODENAMEPROVIDER :
- {
-- SwVbaCodeNameProvider* pObjProv = new SwVbaCodeNameProvider( pDoc->GetDocShell() );
-- xRet = (cppu::OWeakObject*)pObjProv;
-+ if ( pDoc->GetDocShell() && ooo::vba::isAlienWordDoc( *pDoc->GetDocShell() ) )
-+ {
-+ SwVbaCodeNameProvider* pObjProv = new SwVbaCodeNameProvider( pDoc->GetDocShell() );
-+ xRet = (cppu::OWeakObject*)pObjProv;
-+ }
- }
- break;
- case SW_SERVICE_VBAPROJECTNAMEPROVIDER :
- {
- uno::Reference< container::XNameContainer > xProjProv = pDoc->GetVBATemplateToProjectCache();
-- if ( !xProjProv.is() )
-+ if ( !xProjProv.is() && pDoc->GetDocShell() && ooo::vba::isAlienWordDoc( *pDoc->GetDocShell() ) )
- {
- xProjProv = new SwVbaProjectNameProvider( pDoc->GetDocShell() );
- pDoc->SetVBATemplateToProjectCache( xProjProv );
-diff --git a/sw/util/makefile.mk b/sw/util/makefile.mk
-index 88f6731..6c74b8f 100644
---- a/sw/util/makefile.mk
-+++ b/sw/util/makefile.mk
-@@ -123,7 +123,6 @@ SHL1STDLIBS+= \
- $(SALHELPERLIB) \
- $(ICUUCLIB) \
- $(I18NUTILLIB) \
-- $(VBAHELPERLIB) \
- $(AVMEDIALIB)
-
- .IF "$(GUI)"=="WNT"
-diff --git a/vbahelper/inc/vbahelper/vbaaccesshelper.hxx b/vbahelper/inc/vbahelper/vbaaccesshelper.hxx
-new file mode 100644
-index 0000000..79bb44c
---- /dev/null
-+++ b/vbahelper/inc/vbahelper/vbaaccesshelper.hxx
-@@ -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: 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_ACCESS_HELPER_HXX
-+#define OOVBAAPI_VBA_ACCESS_HELPER_HXX
-+
-+#include <com/sun/star/beans/XPropertySet.hpp>
-+#include <basic/basmgr.hxx>
-+#include <sfx2/objsh.hxx>
-+#include <sfx2/docfilt.hxx>
-+#include <sfx2/docfile.hxx>
-+#define VBAHELPER_DLLIMPLEMENTATION
-+#include <vbahelper/vbadllapi.h>
-+#include <memory>
-+namespace css = ::com::sun::star;
-+namespace ooo
-+{
-+ namespace vba
-+ {
-+
-+ VBAHELPER_DLLPRIVATE inline css::uno::Reference< css::lang::XMultiServiceFactory > getVBAServiceFactory( SfxObjectShell* pShell )
-+ {
-+ css::uno::Any aUnoVar;
-+ if ( !pShell || ! pShell->GetBasicManager()->GetGlobalUNOConstant( "VBAGlobals", aUnoVar ) )
-+ throw css::lang::IllegalArgumentException();
-+ css::uno::Reference< css::lang::XMultiServiceFactory > xVBAFactory( aUnoVar, css::uno::UNO_QUERY_THROW );
-+ return xVBAFactory;
-+ }
-+
-+ VBAHELPER_DLLPUBLIC inline 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)
-+ {
-+ OSL_PRECOND( pShell, "createVBAUnoAPIService: no shell!" );
-+ ::rtl::OUString sVarName( ::rtl::OUString::createFromAscii( _pAsciiName ) );
-+ css::uno::Reference< css::uno::XInterface > xIf = getVBAServiceFactory( pShell )->createInstanceWithArguments( sVarName, aArgs );
-+ return xIf;
-+ }
-+
-+
-+ VBAHELPER_DLLPRIVATE inline bool isAlienDoc( SfxObjectShell& rDocShell, const char* pMimeType )
-+ {
-+ bool bRes( false );
-+ const SfxFilter *pFilt = rDocShell.GetMedium()->GetFilter();
-+ if ( pFilt && pFilt->IsAlienFormat() )
-+ bRes = ( pFilt->GetMimeType().CompareToAscii( pMimeType ) == 0 );
-+ return bRes;
-+ }
-+ VBAHELPER_DLLPUBLIC inline bool isAlienExcelDoc( SfxObjectShell& rDocShell ) { return isAlienDoc( rDocShell, "application/vnd.ms-excel" ); }
-+ VBAHELPER_DLLPUBLIC inline bool isAlienWordDoc( SfxObjectShell& rDocShell ) { return isAlienDoc( rDocShell, "application/vnd.ms-word" ); }
-+
-+ } // openoffice
-+} // org
-+
-+#endif
-diff --git a/vbahelper/inc/vbahelper/vbahelper.hxx b/vbahelper/inc/vbahelper/vbahelper.hxx
-index 8ec59f8..89b0298 100644
---- a/vbahelper/inc/vbahelper/vbahelper.hxx
-+++ b/vbahelper/inc/vbahelper/vbahelper.hxx
-@@ -38,17 +38,19 @@
- #include <com/sun/star/lang/IllegalArgumentException.hpp>
- #include <com/sun/star/awt/XControl.hpp>
- #include <com/sun/star/awt/XDevice.hpp>
-+#include <basic/basmgr.hxx>
- #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 <sfx2/objsh.hxx>
-+#include <sfx2/docfilt.hxx>
-+#include <sfx2/docfile.hxx>
- #include <vcl/pointr.hxx>
--#define VBAHELPER_DLLIMPLEMENTATION
--#include <vbahelper/vbadllapi.h>
- #include <memory>
--namespace css = ::com::sun::star;
-+#include "vbaaccesshelper.hxx"
-
-+namespace css = ::com::sun::star;
- namespace ooo
- {
- namespace vba
-@@ -65,7 +67,7 @@ namespace ooo
- }
- VBAHELPER_DLLPUBLIC SfxObjectShell* getSfxObjShell( const css::uno::Reference< css::frame::XModel >& xModel ) throw ( css::uno::RuntimeException);
- 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);
-+
- css::uno::Reference< css::frame::XModel > getCurrentDoc( const rtl::OUString& sKey ) throw (css::uno::RuntimeException);
- VBAHELPER_DLLPUBLIC css::uno::Reference< css::frame::XModel > getCurrentExcelDoc( const css::uno::Reference< css::uno::XComponentContext >& xContext ) throw (css::uno::RuntimeException);
- VBAHELPER_DLLPUBLIC css::uno::Reference< css::frame::XModel > getCurrentWordDoc( const css::uno::Reference< css::uno::XComponentContext >& xContext ) throw (css::uno::RuntimeException);
-diff --git a/vbahelper/prj/d.lst b/vbahelper/prj/d.lst
-index db11559..2d20ab1 100644
---- a/vbahelper/prj/d.lst
-+++ b/vbahelper/prj/d.lst
-@@ -8,6 +8,7 @@
- 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\vbaaccesshelper.hxx %_DEST%\inc%_EXT%\vbahelper\vbaaccesshelper.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
-diff --git a/vbahelper/source/vbahelper/vbahelper.cxx b/vbahelper/source/vbahelper/vbahelper.cxx
-index fd99816..2f57755 100644
---- a/vbahelper/source/vbahelper/vbahelper.cxx
-+++ b/vbahelper/source/vbahelper/vbahelper.cxx
-@@ -102,15 +102,6 @@ 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!" );
-@@ -118,13 +109,6 @@ css::uno::Reference< css::uno::XInterface > createVBAUnoAPIService( SfxObjectShe
- 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 )
- {
---
-1.7.0.1
-