summaryrefslogtreecommitdiff
path: root/patches/vba/vba-msvbahelper-splitbuilt.diff
diff options
context:
space:
mode:
Diffstat (limited to 'patches/vba/vba-msvbahelper-splitbuilt.diff')
-rw-r--r--patches/vba/vba-msvbahelper-splitbuilt.diff1767
1 files changed, 0 insertions, 1767 deletions
diff --git a/patches/vba/vba-msvbahelper-splitbuilt.diff b/patches/vba/vba-msvbahelper-splitbuilt.diff
deleted file mode 100644
index e381984da..000000000
--- a/patches/vba/vba-msvbahelper-splitbuilt.diff
+++ /dev/null
@@ -1,1767 +0,0 @@
-diff --git filter/inc/filter/msfilter/msvbahelper.hxx filter/inc/filter/msfilter/msvbahelper.hxx
-deleted file mode 100644
-index 1623fd3..0000000
---- filter/inc/filter/msfilter/msvbahelper.hxx
-+++ /dev/null
-@@ -1,59 +0,0 @@
--/* -*- Mode: C++; tab-width: 4; indent-tabs-mode: nil; c-basic-offset: 4 -*- */
--/*************************************************************************
-- *
-- * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-- *
-- * Copyright 2000, 2010 Oracle and/or its affiliates.
-- *
-- * OpenOffice.org - a multi-platform office productivity suite
-- *
-- * This file is part of OpenOffice.org.
-- *
-- * OpenOffice.org is free software: you can redistribute it and/or modify
-- * it under the terms of the GNU Lesser General Public License version 3
-- * only, as published by the Free Software Foundation.
-- *
-- * OpenOffice.org is distributed in the hope that it will be useful,
-- * but WITHOUT ANY WARRANTY; without even the implied warranty of
-- * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
-- * GNU Lesser General Public License version 3 for more details
-- * (a copy is included in the LICENSE file that accompanied this code).
-- *
-- * You should have received a copy of the GNU Lesser General Public License
-- * version 3 along with OpenOffice.org. If not, see
-- * <http://www.openoffice.org/license.html>
-- * for a copy of the LGPLv3 License.
-- *
-- ************************************************************************/
--#ifndef _MSVBAHELPER_HXX
--#define _MSVBAHELPER_HXX
--
--#include <sfx2/objsh.hxx>
--#include "filter/msfilter/msfilterdllapi.h"
--
--namespace ooo { namespace vba
--{
-- class MSFILTER_DLLPUBLIC VBAMacroResolvedInfo
-- {
-- SfxObjectShell* mpDocContext;
-- bool mbFound;
-- String msResolvedMacro;
-- public:
-- VBAMacroResolvedInfo() : mpDocContext(NULL), mbFound( false ){}
-- void SetResolved( bool bRes ) { mbFound = bRes; }
-- bool IsResolved() { return mbFound; }
-- void SetMacroDocContext(SfxObjectShell* pShell ) { mpDocContext = pShell; }
-- SfxObjectShell* MacroDocContext() { return mpDocContext; }
-- String ResolvedMacro() { return msResolvedMacro; }
-- void SetResolvedMacro(const String& sMacro ) { msResolvedMacro = sMacro; }
-- };
--
-- MSFILTER_DLLPUBLIC String makeMacroURL( const String& sMacroName );
-- MSFILTER_DLLPUBLIC ::rtl::OUString extractMacroName( const ::rtl::OUString& rMacroUrl );
-- MSFILTER_DLLPUBLIC VBAMacroResolvedInfo resolveVBAMacro( SfxObjectShell* pShell, const rtl::OUString& sMod, bool bSearchGlobalTemplates = false );
-- MSFILTER_DLLPUBLIC sal_Bool executeMacro( SfxObjectShell* pShell, const String& sMacroName, com::sun::star::uno::Sequence< com::sun::star::uno::Any >& aArgs, com::sun::star::uno::Any& aRet, const com::sun::star::uno::Any& aCaller );
--} }
--
--#endif
--
--/* vim:set shiftwidth=4 softtabstop=4 expandtab: */
-diff --git filter/source/msfilter/makefile.mk filter/source/msfilter/makefile.mk
-index c59a126..b37dc7b 100644
---- filter/source/msfilter/makefile.mk
-+++ filter/source/msfilter/makefile.mk
-@@ -52,7 +52,6 @@ SLOFILES= \
- $(SLO)$/msfiltertracer.obj \
- $(SLO)$/svdfppt.obj \
- $(SLO)$/svxmsbas2.obj \
-- $(SLO)$/msvbahelper.obj \
- $(SLO)$/mstoolbar.obj\
-
- SHL1TARGET= msfilter$(DLLPOSTFIX)
-diff --git filter/source/msfilter/mstoolbar.cxx filter/source/msfilter/mstoolbar.cxx
-index eead43c..3b92f80 100644
---- filter/source/msfilter/mstoolbar.cxx
-+++ filter/source/msfilter/mstoolbar.cxx
-@@ -5,6 +5,7 @@
- #include <com/sun/star/ui/XImageManager.hpp>
- #include <com/sun/star/ui/ItemType.hpp>
- #include <com/sun/star/ui/ItemStyle.hpp>
-+#include <com/sun/star/script/theVBAMacroHelper.hpp>
- #include <com/sun/star/frame/XLayoutManager.hpp>
- #include <fstream>
- #include <vcl/graph.hxx>
-@@ -15,10 +16,10 @@
- #include <basic/basmgr.hxx>
- #include <svtools/filterutils.hxx>
- #include <boost/scoped_array.hpp>
--#include <filter/msfilter/msvbahelper.hxx>
- #include <svtools/miscopt.hxx>
- #include <vcl/svapp.hxx>
- #include <vcl/window.hxx>
-+#include <comphelper/processfactory.hxx>
-
- using namespace com::sun::star;
-
-@@ -488,9 +489,18 @@ TBCGeneralInfo::ImportToolBarControlData( CustomToolBarImportHelper& helper, std
- if ( extraInfo.getOnAction().getLength() )
- {
- aProp.Name = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("CommandURL") );
-- ooo::vba::VBAMacroResolvedInfo aMacroInf = ooo::vba::resolveVBAMacro( &helper.GetDocShell(), extraInfo.getOnAction(), true );
-- if ( aMacroInf.IsResolved() )
-- aProp.Value = helper.createCommandFromMacro( aMacroInf.ResolvedMacro() );
-+ uno::Reference< script::XVBAMacroResolvedInfo > xMacroInf;
-+ try
-+ {
-+ uno::Reference< script::XVBAMacroHelper > xMacroHelper = script::theVBAMacroHelper::get( comphelper::getProcessComponentContext() );
-+ xMacroInf = xMacroHelper->resolveVBAMacro( helper.GetDocShell().GetModel(), extraInfo.getOnAction(), sal_True );
-+ }
-+ catch( uno::Exception& e )
-+ {
-+ }
-+
-+ if ( xMacroInf.is() && xMacroInf->getResolved() )
-+ aProp.Value = helper.createCommandFromMacro( xMacroInf->getResolvedMacro() );
- else
- aProp.Value <<= rtl::OUString::createFromAscii("UnResolvedMacro[").concat( extraInfo.getOnAction() ).concat( rtl::OUString::createFromAscii("]") );
- sControlData.push_back( aProp );
-diff --git filter/source/msfilter/msvbahelper.cxx filter/source/msfilter/msvbahelper.cxx
-deleted file mode 100644
-index 64256f6..0000000
---- filter/source/msfilter/msvbahelper.cxx
-+++ /dev/null
-@@ -1,414 +0,0 @@
--/* -*- Mode: C++; tab-width: 4; indent-tabs-mode: nil; c-basic-offset: 4 -*- */
--/*************************************************************************
-- *
-- * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-- *
-- * Copyright 2000, 2010 Oracle and/or its affiliates.
-- *
-- * OpenOffice.org - a multi-platform office productivity suite
-- *
-- * This file is part of OpenOffice.org.
-- *
-- * OpenOffice.org is free software: you can redistribute it and/or modify
-- * it under the terms of the GNU Lesser General Public License version 3
-- * only, as published by the Free Software Foundation.
-- *
-- * OpenOffice.org is distributed in the hope that it will be useful,
-- * but WITHOUT ANY WARRANTY; without even the implied warranty of
-- * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
-- * GNU Lesser General Public License version 3 for more details
-- * (a copy is included in the LICENSE file that accompanied this code).
-- *
-- * You should have received a copy of the GNU Lesser General Public License
-- * version 3 along with OpenOffice.org. If not, see
-- * <http://www.openoffice.org/license.html>
-- * for a copy of the LGPLv3 License.
-- *
-- ************************************************************************/
--// MARKER(update_precomp.py): autogen include statement, do not remove
--#include "precompiled_filter.hxx"
--
--#include <filter/msfilter/msvbahelper.hxx>
--#include <basic/sbx.hxx>
--#include <basic/sbstar.hxx>
--#include <basic/basmgr.hxx>
--#include <basic/sbmod.hxx>
--#include <basic/sbmeth.hxx>
--#include <com/sun/star/document/XDocumentPropertiesSupplier.hpp>
--#include <com/sun/star/document/XDocumentProperties.hpp>
--#include <com/sun/star/document/XDocumentInfoSupplier.hpp>
--#include <com/sun/star/script/vba/XVBACompatibility.hpp>
--#include <tools/urlobj.hxx>
--#include <osl/file.hxx>
--#include <unotools/pathoptions.hxx>
--
--using namespace ::com::sun::star;
--
--namespace ooo { namespace vba {
--
--const static rtl::OUString sUrlPart0 = rtl::OUString::createFromAscii( "vnd.sun.star.script:");
--const static rtl::OUString sUrlPart1 = rtl::OUString::createFromAscii( "?language=Basic&location=document");
--
--String makeMacroURL( const String& sMacroName )
--{
-- return sUrlPart0.concat( sMacroName ).concat( sUrlPart1 ) ;
--}
--
--::rtl::OUString extractMacroName( const ::rtl::OUString& rMacroUrl )
--{
-- if( (rMacroUrl.getLength() > sUrlPart0.getLength() + sUrlPart1.getLength()) &&
-- rMacroUrl.match( sUrlPart0 ) &&
-- rMacroUrl.match( sUrlPart1, rMacroUrl.getLength() - sUrlPart1.getLength() ) )
-- {
-- return rMacroUrl.copy( sUrlPart0.getLength(), rMacroUrl.getLength() - sUrlPart0.getLength() - sUrlPart1.getLength() );
-- }
-- return ::rtl::OUString();
--}
--
--SfxObjectShell* findShellForUrl( const rtl::OUString& sMacroURLOrPath )
--{
-- SfxObjectShell* pFoundShell=NULL;
-- SfxObjectShell* pShell = SfxObjectShell::GetFirst();
-- INetURLObject aObj;
-- aObj.SetURL( sMacroURLOrPath );
-- bool bIsURL = aObj.GetProtocol() != INET_PROT_NOT_VALID;
-- rtl::OUString aURL;
-- if ( bIsURL )
-- aURL = sMacroURLOrPath;
-- else
-- {
-- osl::FileBase::getFileURLFromSystemPath( sMacroURLOrPath, aURL );
-- aObj.SetURL( aURL );
-- }
-- OSL_TRACE("Trying to find shell for url %s", rtl::OUStringToOString( aURL, RTL_TEXTENCODING_UTF8 ).getStr() );
-- while ( pShell )
-- {
--
-- uno::Reference< frame::XModel > xModel = pShell->GetModel();
-- // are we searching for a template? if so we have to cater for the
-- // fact that in openoffice a document opened from a template is always
-- // a new document :/
-- if ( xModel.is() )
-- {
-- OSL_TRACE("shell 0x%x has model with url %s and we look for %s", pShell
-- , rtl::OUStringToOString( xModel->getURL(), RTL_TEXTENCODING_UTF8 ).getStr()
-- , rtl::OUStringToOString( aURL, RTL_TEXTENCODING_UTF8 ).getStr()
-- );
-- if ( sMacroURLOrPath.endsWithIgnoreAsciiCaseAsciiL( ".dot", 4 ) )
-- {
-- uno::Reference< document::XDocumentInfoSupplier > xDocInfoSupp( xModel, uno::UNO_QUERY );
-- if( xDocInfoSupp.is() )
-- {
-- uno::Reference< document::XDocumentPropertiesSupplier > xDocPropSupp( xDocInfoSupp->getDocumentInfo(), uno::UNO_QUERY_THROW );
-- uno::Reference< document::XDocumentProperties > xDocProps( xDocPropSupp->getDocumentProperties(), uno::UNO_QUERY_THROW );
-- rtl::OUString sCurrName = xDocProps->getTemplateName();
-- if( sMacroURLOrPath.lastIndexOf( sCurrName ) >= 0 )
-- {
-- pFoundShell = pShell;
-- break;
-- }
-- }
-- }
-- else
-- {
-- // sometimes just the name of the document ( without the path
-- // is used
-- bool bDocNameNoPathMatch = false;
-- if ( aURL.getLength() && aURL.indexOf( '/' ) == -1 )
-- {
-- sal_Int32 lastSlashIndex = xModel->getURL().lastIndexOf( '/' );
-- if ( lastSlashIndex > -1 )
-- {
-- bDocNameNoPathMatch = xModel->getURL().copy( lastSlashIndex + 1 ).equals( aURL );
-- if ( !bDocNameNoPathMatch )
-- {
-- rtl::OUString aTmpName = rtl::OUString::createFromAscii("'") + xModel->getURL().copy( lastSlashIndex + 1 ) + rtl::OUString::createFromAscii("'");
-- bDocNameNoPathMatch = aTmpName.equals( aURL );
-- }
-- }
-- }
--
-- if ( aURL.equals( xModel->getURL() ) || bDocNameNoPathMatch )
-- {
-- pFoundShell = pShell;
-- break;
-- }
-- }
-- }
-- pShell = SfxObjectShell::GetNext( *pShell );
-- }
-- return pFoundShell;
--}
--
--// sMod can be empty ( but we really need the library to search in )
--// if sMod is empty and a macro is found then sMod is updated
--bool hasMacro( SfxObjectShell* pShell, const String& sLibrary, String& sMod, const String& sMacro )
--{
-- bool bFound = false;
-- if ( sLibrary.Len() && sMacro.Len() )
-- {
-- OSL_TRACE("** Searching for %s.%s in library %s"
-- ,rtl::OUStringToOString( sMod, RTL_TEXTENCODING_UTF8 ).getStr()
-- ,rtl::OUStringToOString( sMacro, RTL_TEXTENCODING_UTF8 ).getStr()
-- ,rtl::OUStringToOString( sLibrary, RTL_TEXTENCODING_UTF8 ).getStr() );
-- 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 )
-- bFound = true;
-- }
-- }
-- }
-- else if( SbMethod* pMethod = dynamic_cast< SbMethod* >( pBasic->Find( sMacro, SbxCLASS_METHOD ) ) )
-- {
-- if( SbModule* pModule = pMethod->GetModule() )
-- {
-- sMod = pModule->GetName();
-- bFound = true;
-- }
-- }
-- }
-- }
-- }
-- return bFound;
--}
--void parseMacro( const rtl::OUString& sMacro, String& sContainer, String& sModule, String& sProcedure )
--{
-- sal_Int32 nMacroDot = sMacro.lastIndexOf( '.' );
--
-- if ( nMacroDot != -1 )
-- {
-- sProcedure = sMacro.copy( nMacroDot + 1 );
--
-- sal_Int32 nContainerDot = sMacro.lastIndexOf( '.', nMacroDot - 1 );
-- if ( nContainerDot != -1 )
-- {
-- sModule = sMacro.copy( nContainerDot + 1, nMacroDot - nContainerDot - 1 );
-- sContainer = sMacro.copy( 0, nContainerDot );
-- }
-- else
-- sModule = sMacro.copy( 0, nMacroDot );
-- }
-- else
-- sProcedure = sMacro;
--}
--
--VBAMacroResolvedInfo resolveVBAMacro( SfxObjectShell* pShell, const rtl::OUString& MacroName, bool bSearchGlobalTemplates )
--{
-- VBAMacroResolvedInfo aRes;
-- if ( !pShell )
-- return aRes;
-- aRes.SetMacroDocContext( pShell );
--
-- // the name may be enclosed in apostrophs
-- ::rtl::OUString sMacroUrl = MacroName;
-- sal_Int32 nMacroLen = MacroName.getLength();
-- if( (nMacroLen >= 2) && (MacroName[0] == '\'') && (MacroName[nMacroLen-1] == '\'') )
-- sMacroUrl = MacroName.copy( 1, nMacroLen - 2 );
--
-- // parse the macro name
-- sal_Int32 nDocSepIndex = sMacroUrl.indexOf( '!' );
--
-- String sContainer;
-- String sModule;
-- String sProcedure;
--
-- if( nDocSepIndex > 0 )
-- {
-- // macro specified by document name
-- // find document shell for document name and call ourselves
-- // recursively
--
-- // assume for now that the document name is *this* document
-- String sDocUrlOrPath = sMacroUrl.copy( 0, nDocSepIndex );
-- sMacroUrl = sMacroUrl.copy( nDocSepIndex + 1 );
-- OSL_TRACE("doc search, current shell is 0x%x", pShell );
-- SfxObjectShell* pFoundShell = NULL;
-- if( bSearchGlobalTemplates )
-- {
-- SvtPathOptions aPathOpt;
-- String aAddinPath = aPathOpt.GetAddinPath();
-- if( rtl::OUString( sDocUrlOrPath ).indexOf( aAddinPath ) == 0 )
-- pFoundShell = pShell;
-- }
-- if( pFoundShell == NULL )
-- pFoundShell = findShellForUrl( sDocUrlOrPath );
-- OSL_TRACE("doc search, after find, found shell is 0x%x", pFoundShell );
-- aRes = resolveVBAMacro( pFoundShell, sMacroUrl, bSearchGlobalTemplates );
-- return aRes;
-- }
-- else
-- {
-- // macro is contained in 'this' document ( or code imported from a template
-- // where that template is a global template or perhaps the template this
-- // document is created from )
--
-- // macro format = Container.Module.Procedure
-- parseMacro( sMacroUrl, sContainer, sModule, sProcedure );
-- uno::Reference< lang::XMultiServiceFactory> xSF( pShell->GetModel(), uno::UNO_QUERY);
-- uno::Reference< container::XNameContainer > xPrjNameCache;
-- if ( xSF.is() )
-- xPrjNameCache.set( xSF->createInstance( rtl::OUString(RTL_CONSTASCII_USTRINGPARAM( "ooo.vba.VBAProjectNameProvider" ) ) ), uno::UNO_QUERY );
--
-- std::vector< rtl::OUString > sSearchList;
--
-- if ( sContainer.Len() > 0 )
-- {
-- // get the Project associated with the Container
-- if ( xPrjNameCache.is() )
-- {
-- if ( xPrjNameCache->hasByName( sContainer ) )
-- {
-- rtl::OUString sProject;
-- xPrjNameCache->getByName( sContainer ) >>= sProject;
-- sContainer = sProject;
-- }
-- }
-- sSearchList.push_back( sContainer ); // First Lib to search
-- }
-- else
-- {
-- // Ok, if we have no Container specified then we need to search them in order, this document, template this document created from, global templates,
-- // get the name of Project/Library for 'this' document
-- rtl::OUString sThisProject = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("Standard") );
-- try
-- {
-- uno::Reference< beans::XPropertySet > xProps( pShell->GetModel(), uno::UNO_QUERY_THROW );
-- uno::Reference< script::vba::XVBACompatibility > xVBAMode( xProps->getPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("BasicLibraries") ) ), uno::UNO_QUERY_THROW );
-- sThisProject = xVBAMode->getProjectName();
-- }
-- catch( uno::Exception& /*e*/) {}
--
-- sSearchList.push_back( sThisProject ); // First Lib to search
-- if ( xPrjNameCache.is() )
-- {
-- // is this document created from a template?
-- uno::Reference< document::XDocumentInfoSupplier > xDocInfoSupp( pShell->GetModel(), uno::UNO_QUERY_THROW );
-- uno::Reference< document::XDocumentPropertiesSupplier > xDocPropSupp( xDocInfoSupp->getDocumentInfo(), uno::UNO_QUERY_THROW );
-- uno::Reference< document::XDocumentProperties > xDocProps( xDocPropSupp->getDocumentProperties(), uno::UNO_QUERY_THROW );
--
-- rtl::OUString sCreatedFrom = xDocProps->getTemplateURL();
-- if ( sCreatedFrom.getLength() )
-- {
-- INetURLObject aObj;
-- aObj.SetURL( sCreatedFrom );
-- bool bIsURL = aObj.GetProtocol() != INET_PROT_NOT_VALID;
-- rtl::OUString aURL;
-- if ( bIsURL )
-- aURL = sCreatedFrom;
-- else
-- {
-- osl::FileBase::getFileURLFromSystemPath( sCreatedFrom, aURL );
-- aObj.SetURL( aURL );
-- }
-- sCreatedFrom = aObj.GetLastName();
-- }
--
-- sal_Int32 nIndex = sCreatedFrom.lastIndexOf( '.' );
-- if ( nIndex != -1 )
-- sCreatedFrom = sCreatedFrom.copy( 0, nIndex );
--
-- rtl::OUString sPrj;
-- if ( sCreatedFrom.getLength() && xPrjNameCache->hasByName( sCreatedFrom ) )
-- {
-- xPrjNameCache->getByName( sCreatedFrom ) >>= sPrj;
-- // Make sure we don't double up with this project
-- if ( !sPrj.equals( sThisProject ) )
-- sSearchList.push_back( sPrj );
-- }
--
-- // get list of global template Names
-- uno::Sequence< rtl::OUString > sTemplateNames = xPrjNameCache->getElementNames();
-- sal_Int32 nLen = sTemplateNames.getLength();
-- for ( sal_Int32 index = 0; ( bSearchGlobalTemplates && index < nLen ); ++index )
-- {
--
-- if ( !sCreatedFrom.equals( sTemplateNames[ index ] ) )
-- {
-- if ( xPrjNameCache->hasByName( sTemplateNames[ index ] ) )
-- {
-- xPrjNameCache->getByName( sTemplateNames[ index ] ) >>= sPrj;
-- // Make sure we don't double up with this project
-- if ( !sPrj.equals( sThisProject ) )
-- sSearchList.push_back( sPrj );
-- }
-- }
--
-- }
-- }
-- }
-- std::vector< rtl::OUString >::iterator it_end = sSearchList.end();
-- for ( std::vector< rtl::OUString >::iterator it = sSearchList.begin(); it != it_end; ++it )
-- {
-- bool bRes = hasMacro( pShell, *it, sModule, sProcedure );
-- if ( bRes )
-- {
-- aRes.SetResolved( true );
-- aRes.SetMacroDocContext( pShell );
-- sContainer = *it;
-- break;
-- }
-- }
-- aRes.SetResolvedMacro( sProcedure.Insert( '.', 0 ).Insert( sModule, 0).Insert( '.', 0 ).Insert( sContainer, 0 ) );
-- }
--
-- return aRes;
--}
--
--// Treat the args as possible inouts ( convertion at bottom of method )
--sal_Bool executeMacro( SfxObjectShell* pShell, const String& sMacroName, uno::Sequence< uno::Any >& aArgs, uno::Any& aRet, const uno::Any& /*aCaller*/)
--{
-- sal_Bool bRes = sal_False;
-- if ( !pShell )
-- return bRes;
-- rtl::OUString sUrl = makeMacroURL( sMacroName );
--
-- uno::Sequence< sal_Int16 > aOutArgsIndex;
-- uno::Sequence< uno::Any > aOutArgs;
--
-- try
-- { ErrCode nErr( ERRCODE_BASIC_INTERNAL_ERROR );
-- if ( pShell )
-- {
-- nErr = pShell->CallXScript( sUrl,
-- aArgs, aRet, aOutArgsIndex, aOutArgs, false );
-- sal_Int32 nLen = aOutArgs.getLength();
-- // convert any out params to seem like they were inouts
-- if ( nLen )
-- {
-- for ( sal_Int32 index=0; index < nLen; ++index )
-- {
-- sal_Int32 nOutIndex = aOutArgsIndex[ index ];
-- aArgs[ nOutIndex ] = aOutArgs[ index ];
-- }
-- }
-- }
-- bRes = ( nErr == ERRCODE_NONE );
-- }
-- catch ( uno::Exception& )
-- {
-- bRes = sal_False;
-- }
-- return bRes;
--}
--} } // vba // ooo
--
--/* vim:set shiftwidth=4 softtabstop=4 expandtab: */
-diff --git offapi/com/sun/star/script/VBAMacroHelper.idl offapi/com/sun/star/script/VBAMacroHelper.idl
-new file mode 100644
-index 0000000..e971b8c
---- /dev/null
-+++ offapi/com/sun/star/script/VBAMacroHelper.idl
-@@ -0,0 +1,15 @@
-+#ifndef com_sun_star_script_VBAMacroHelper_idl
-+#define com_sun_star_script_VBAMacroHelper_idl
-+#ifndef __com_sun_star_uno_XInterface_idl__
-+#include <com/sun/star/uno/XInterface.idl>
-+#endif
-+#ifndef __com_sun_star_script_XVBAMacroHelper_idl__
-+#include <com/sun/star/script/XVBAMacroHelper.idl>
-+#endif
-+#ifndef __com_sun_star_frame_XModel_idl__
-+#include <com/sun/star/frame/XModel.idl>
-+#endif
-+module com { module sun { module star { module script {
-+singleton theVBAMacroHelper : ::com::sun::star::script::XVBAMacroHelper;
-+}; }; }; };
-+#endif
-diff --git offapi/com/sun/star/script/XVBAMacroHelper.idl offapi/com/sun/star/script/XVBAMacroHelper.idl
-new file mode 100644
-index 0000000..04ef842
---- /dev/null
-+++ offapi/com/sun/star/script/XVBAMacroHelper.idl
-@@ -0,0 +1,22 @@
-+#ifndef com_sun_star_script_XVBAMacroHelper_idl
-+#define com_sun_star_script_XVBAMacroHelper_idl
-+#ifndef __com_sun_star_uno_XInterface_idl__
-+#include <com/sun/star/uno/XInterface.idl>
-+#endif
-+#ifndef __com_sun_star_script_XVBAMacroResolvedInfo_idl__
-+#include <com/sun/star/script/XVBAMacroResolvedInfo.idl>
-+#endif
-+#ifndef __com_sun_star_frame_XModel_idl__
-+#include <com/sun/star/frame/XModel.idl>
-+#endif
-+
-+module com { module sun { module star { module script {
-+interface XVBAMacroHelper : com::sun::star::uno::XInterface
-+{
-+ string makeMacroURL( [in] string sMacroName );
-+ string extractMacroNameFromURL( [in] string sURL );
-+ com::sun::star::script::XVBAMacroResolvedInfo resolveVBAMacro( [in] com::sun::star::frame::XModel model, [in] string moduleName, [in] boolean bSearchGlobalTemplates );
-+ boolean executeMacro( [in] com::sun::star::frame::XModel model, [in] string smacroName, [inout] sequence< any > aArgs, [inout] any aRet, [in] any aCaller );
-+};
-+}; }; }; };
-+#endif
-diff --git offapi/com/sun/star/script/XVBAMacroResolvedInfo.idl offapi/com/sun/star/script/XVBAMacroResolvedInfo.idl
-new file mode 100644
-index 0000000..7d4b37e
---- /dev/null
-+++ offapi/com/sun/star/script/XVBAMacroResolvedInfo.idl
-@@ -0,0 +1,18 @@
-+#ifndef com_sun_star_script_XVBAMacroResolvedInfo_idl
-+#define com_sun_star_script_XVBAMacroResolvedInfo_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 com { module sun { module star { module script {
-+interface XVBAMacroResolvedInfo
-+{
-+ [attribute] boolean Resolved;
-+ [attribute] string ResolvedMacro;
-+ [attribute] com::sun::star::frame::XModel DocumentContext;
-+};
-+}; }; }; };
-+#endif
-diff --git offapi/com/sun/star/script/makefile.mk offapi/com/sun/star/script/makefile.mk
-index 8c46453..bc75a92 100644
---- offapi/com/sun/star/script/makefile.mk
-+++ offapi/com/sun/star/script/makefile.mk
-@@ -51,7 +51,11 @@ IDLFILES=\
- XLibraryQueryExecutable.idl \
- ModuleSizeExceededRequest.idl\
- ModuleInfo.idl\
-- ModuleType.idl
-+ ModuleType.idl\
-+ XVBAMacroHelper.idl\
-+ XVBAMacroResolvedInfo.idl\
-+ VBAMacroHelper.idl\
-+ ModuleType.idl\
-
- # ------------------------------------------------------------------
-
-diff --git sc/source/filter/excel/makefile.mk sc/source/filter/excel/makefile.mk
-index a84f4aa..e8b170e 100644
---- sc/source/filter/excel/makefile.mk
-+++ sc/source/filter/excel/makefile.mk
-@@ -146,6 +146,7 @@ EXCEPTIONSFILES = \
- $(SLO)$/xistring.obj \
- $(SLO)$/xistyle.obj \
- $(SLO)$/xladdress.obj \
-+ $(SLO)$/xlescher.obj \
- $(SLO)$/xiescher.obj \
- $(SLO)$/xlchart.obj \
- $(SLO)$/xlformula.obj \
-diff --git sc/source/filter/excel/xlescher.cxx sc/source/filter/excel/xlescher.cxx
-index 3360b02..9f6ed58 100644
---- sc/source/filter/excel/xlescher.cxx
-+++ sc/source/filter/excel/xlescher.cxx
-@@ -32,6 +32,7 @@
-
- #include <com/sun/star/drawing/XControlShape.hpp>
- #include <com/sun/star/script/ScriptEventDescriptor.hpp>
-+
- #include <svx/unoapi.hxx>
- #include "document.hxx"
- #include "xestream.hxx"
-diff --git sc/source/filter/excel/xltools.cxx sc/source/filter/excel/xltools.cxx
-index e2bb19d..51146d5 100644
---- sc/source/filter/excel/xltools.cxx
-+++ sc/source/filter/excel/xltools.cxx
-@@ -34,7 +34,6 @@
- #include <unotools/fontcvt.hxx>
- #include <sfx2/objsh.hxx>
- #include <editeng/editstat.hxx>
--#include <filter/msfilter/msvbahelper.hxx>
- #include "xestream.hxx"
- #include "document.hxx"
- #include "docuno.hxx"
-@@ -46,8 +45,15 @@
- #include "xistream.hxx"
- #include "xiroot.hxx"
- #include "xltools.hxx"
-+#include <comphelper/processfactory.hxx>
-+#include <com/sun/star/script/theVBAMacroHelper.hpp>
-
- using ::rtl::OUString;
-+using ::com::sun::star::uno::Reference;
-+
-+using ::com::sun::star::script::XVBAMacroHelper;
-+using ::com::sun::star::script::XVBAMacroResolvedInfo;
-+using ::com::sun::star::script::theVBAMacroHelper;
-
- // GUID import/export =========================================================
-
-@@ -695,9 +701,16 @@ const OUString XclTools::maSbMacroSuffix( RTL_CONSTASCII_USTRINGPARAM( "?languag
- OUString XclTools::GetSbMacroUrl( const String& rMacroName, SfxObjectShell* pDocShell )
- {
- OSL_ENSURE( rMacroName.Len() > 0, "XclTools::GetSbMacroUrl - macro name is empty" );
-- ::ooo::vba::VBAMacroResolvedInfo aMacroInfo = ::ooo::vba::resolveVBAMacro( pDocShell, rMacroName, false );
-- if( aMacroInfo.IsResolved() )
-- return ::ooo::vba::makeMacroURL( aMacroInfo.ResolvedMacro() );
-+ try
-+ {
-+ Reference< XVBAMacroHelper > xMacroHelper = theVBAMacroHelper::get( comphelper::getProcessComponentContext() );
-+ Reference< XVBAMacroResolvedInfo > xResolvedMacro = xMacroHelper->resolveVBAMacro( pDocShell->GetModel(), rMacroName, sal_False );
-+ if ( xResolvedMacro->getResolved() )
-+ return xMacroHelper->makeMacroURL( xResolvedMacro->getResolvedMacro() );
-+ }
-+ catch( com::sun::star::uno::Exception& )
-+ {
-+ }
- return OUString();
- }
-
-diff --git sc/source/ui/vba/vbasheetobject.cxx sc/source/ui/vba/vbasheetobject.cxx
-index 215a62c..daad041 100755
---- sc/source/ui/vba/vbasheetobject.cxx
-+++ sc/source/ui/vba/vbasheetobject.cxx
-@@ -32,11 +32,12 @@
- #include <com/sun/star/script/ScriptEventDescriptor.hpp>
- #include <com/sun/star/script/XEventAttacherManager.hpp>
- #include <com/sun/star/style/VerticalAlignment.hpp>
-+#include <com/sun/star/script/theVBAMacroHelper.hpp>
-+
- #include <ooo/vba/excel/Constants.hpp>
- #include <ooo/vba/excel/XlOrientation.hpp>
- #include <ooo/vba/excel/XlPlacement.hpp>
- #include <rtl/ustrbuf.hxx>
--#include <filter/msfilter/msvbahelper.hxx>
- #include <oox/helper/helper.hxx>
- #include "vbafont.hxx"
-
-@@ -308,6 +309,13 @@ ScVbaControlObjectBase::ScVbaControlObjectBase(
- break;
- // no default, to let the compiler complain about missing case
- }
-+ try
-+ {
-+ m_xMacroHelper = script::theVBAMacroHelper::get( mxContext );
-+ }
-+ catch( uno::Exception& )
-+ {
-+ }
- }
-
- // XSheetObject attributes
-@@ -333,8 +341,8 @@ OUString SAL_CALL ScVbaControlObjectBase::getOnAction() throw (uno::RuntimeExcep
- const script::ScriptEventDescriptor* pEventEnd = pEvent + aEvents.getLength();
- const OUString aScriptType = CREATE_OUSTRING( "Script" );
- for( ; pEvent < pEventEnd; ++pEvent )
-- if( (pEvent->ListenerType == maListenerType) && (pEvent->EventMethod == maEventMethod) && (pEvent->ScriptType == aScriptType) )
-- return extractMacroName( pEvent->ScriptCode );
-+ if( (pEvent->ListenerType == maListenerType) && (pEvent->EventMethod == maEventMethod) && (pEvent->ScriptType == aScriptType) && m_xMacroHelper.is() )
-+ return m_xMacroHelper->extractMacroNameFromURL( pEvent->ScriptCode );
- }
- return OUString();
- }
-@@ -348,16 +356,17 @@ void SAL_CALL ScVbaControlObjectBase::setOnAction( const OUString& rMacroName )
- try { xEventMgr->revokeScriptEvent( nIndex, maListenerType, maEventMethod, OUString() ); } catch( uno::Exception& ) {}
-
- // if a macro name has been passed, try to attach it to the event
-- if( rMacroName.getLength() > 0 )
-+ if( rMacroName.getLength() > 0 && m_xMacroHelper.is() )
- {
-- VBAMacroResolvedInfo aResolvedMacro = resolveVBAMacro( getSfxObjShell( mxModel ), rMacroName );
-- if( !aResolvedMacro.IsResolved() )
-+ uno::Reference< script::XVBAMacroResolvedInfo > xResolvedMacro = m_xMacroHelper->resolveVBAMacro( mxModel, rMacroName, sal_False );
-+;
-+ if( !xResolvedMacro->getResolved() )
- throw uno::RuntimeException();
- script::ScriptEventDescriptor aDescriptor;
- aDescriptor.ListenerType = maListenerType;
- aDescriptor.EventMethod = maEventMethod;
- aDescriptor.ScriptType = CREATE_OUSTRING( "Script" );
-- aDescriptor.ScriptCode = makeMacroURL( aResolvedMacro.ResolvedMacro() );
-+ aDescriptor.ScriptCode = m_xMacroHelper->makeMacroURL( xResolvedMacro->getResolvedMacro() );
- xEventMgr->registerScriptEvent( nIndex, aDescriptor );
- }
- }
-diff --git sc/source/ui/vba/vbasheetobject.hxx sc/source/ui/vba/vbasheetobject.hxx
-index a7af036..e5f3c21 100755
---- sc/source/ui/vba/vbasheetobject.hxx
-+++ sc/source/ui/vba/vbasheetobject.hxx
-@@ -33,6 +33,7 @@
- #include <ooo/vba/excel/XControlObject.hpp>
- #include <ooo/vba/excel/XSheetObject.hpp>
- #include <vbahelper/vbahelperinterface.hxx>
-+#include <com/sun/star/script/XVBAMacroHelper.hpp>
- #include "vbapalette.hxx"
-
- namespace com { namespace sun { namespace star {
-@@ -173,8 +174,10 @@ protected:
- protected:
- css::uno::Reference< css::container::XIndexContainer > mxFormIC;
- css::uno::Reference< css::beans::XPropertySet > mxControlProps;
-+ css::uno::Reference< css::script::XVBAMacroHelper > m_xMacroHelper;
- ::rtl::OUString maListenerType;
- ::rtl::OUString maEventMethod;
-+
- };
-
- // ============================================================================
-diff --git scripting/source/vbaevents/eventhelper.cxx scripting/source/vbaevents/eventhelper.cxx
-index 53dc7d2..89f10fc 100644
---- scripting/source/vbaevents/eventhelper.cxx
-+++ scripting/source/vbaevents/eventhelper.cxx
-@@ -78,10 +78,7 @@
- #include <basic/sbmeth.hxx>
- #include <basic/sbmod.hxx>
- #include <basic/sbx.hxx>
--#include <filter/msfilter/msvbahelper.hxx>
--
--
--
-+#include <com/sun/star/script/theVBAMacroHelper.hpp>
-
- // for debug
- #include <comphelper/anytostring.hxx>
-@@ -762,6 +759,7 @@ private:
-
- Reference< XComponentContext > m_xContext;
- Reference< frame::XModel > m_xModel;
-+ Reference< script::XVBAMacroHelper > m_xMacroHelper;
- SfxObjectShell* mpShell;
- sal_Bool m_bDocClosed;
- rtl::OUString msProject;
-@@ -773,6 +771,13 @@ OPropertyContainer(GetBroadcastHelper()), m_xContext( rxContext ), m_bDocClosed(
- registerProperty( EVENTLSTNR_PROPERTY_MODEL, EVENTLSTNR_PROPERTY_ID_MODEL,
- beans::PropertyAttribute::TRANSIENT, &m_xModel, ::getCppuType( &m_xModel ) );
- msProject = rtl::OUString::createFromAscii("Standard");
-+ try
-+ {
-+ m_xMacroHelper = script::theVBAMacroHelper::get( m_xContext );
-+ }
-+ catch( Exception& )
-+ {
-+ }
- }
-
- void
-@@ -1000,7 +1005,7 @@ EventListener::firing_Impl(const ScriptEvent& evt, Any* pRet ) throw(RuntimeExce
- ::rtl::OUString::createFromAscii("VBAInterop");
-
- // let default handlers deal with non vba stuff
-- if ( !evt.ScriptType.equals( vbaInterOp ) )
-+ if ( !evt.ScriptType.equals( vbaInterOp ) || !m_xMacroHelper.is() )
- return;
- lang::EventObject aEvent;
- evt.Arguments[ 0 ] >>= aEvent;
-@@ -1024,8 +1024,8 @@
-
- OSL_TRACE("*** trying to invoke %s ",
- rtl::OUStringToOString( sToResolve, RTL_TEXTENCODING_UTF8 ).getStr() );
-- ooo::vba::VBAMacroResolvedInfo aMacroResolvedInfo = ooo::vba::resolveVBAMacro( mpShell, sToResolve );
-- if ( aMacroResolvedInfo.IsResolved() )
-+ Reference< script::XVBAMacroResolvedInfo > xMacroResolvedInfo = m_xMacroHelper->resolveVBAMacro( m_xModel, sToResolve, sal_False );
-+ if ( xMacroResolvedInfo->getResolved() )
- {
-
- if (! txInfo->ApproveRule(evt, txInfo->pPara) )
-@@ -1117,7 +1122,7 @@ EventListener::firing_Impl(const ScriptEvent& evt, Any* pRet ) throw(RuntimeExce
- // call basic event handlers for event
-
- // create script url
-- rtl::OUString url = aMacroResolvedInfo.ResolvedMacro();
-+ rtl::OUString url = xMacroResolvedInfo->getResolvedMacro();
-
- OSL_TRACE("resolved script = %s",
- rtl::OUStringToOString( url,
-@@ -1126,11 +1131,11 @@ EventListener::firing_Impl(const ScriptEvent& evt, Any* pRet ) throw(RuntimeExce
- {
- uno::Any aDummyCaller = uno::makeAny( rtl::OUString::createFromAscii("Error") );
- if ( pRet )
-- ooo::vba::executeMacro( mpShell, url, aArguments, *pRet, aDummyCaller );
-+ m_xMacroHelper->executeMacro( m_xModel, url, aArguments, *pRet, aDummyCaller );
- else
- {
- uno::Any aRet;
-- ooo::vba::executeMacro( mpShell, url, aArguments, aRet, aDummyCaller );
-+ m_xMacroHelper->executeMacro( m_xModel, url, aArguments, aRet, aDummyCaller );
- }
- }
- catch ( uno::Exception& e )
---- scripting/source/vbaevents/makefile.mk.old 2010-09-03 21:26:41.000000000 +0200
-+++ scripting/source/vbaevents/makefile.mk 2010-09-03 21:41:27.000000000 +0200
-@@ -69,7 +69,6 @@ SHL1STDLIBS= \
- $(BASICLIB) \
- $(COMPHELPERLIB) \
- $(SFXLIB) \
-- $(MSFILTERLIB) \
- $(CPPULIB) \
- $(TOOLSLIB) \
- $(SALLIB)
-diff --git svx/source/unodraw/makefile.mk svx/source/unodraw/makefile.mk
-index 6815f28..8ea6b81 100644
---- svx/source/unodraw/makefile.mk
-+++ svx/source/unodraw/makefile.mk
-@@ -41,6 +41,7 @@ ENABLE_EXCEPTIONS=TRUE
-
- LIB1TARGET= $(SLB)$/$(TARGET)-core.lib
- LIB1OBJFILES= \
-+ $(SLO)$/msvbahelper.obj \
- $(SLO)$/UnoGraphicExporter.obj \
- $(SLO)$/XPropertyTable.obj \
- $(SLO)$/UnoNameItemTable.obj \
-diff --git svx/source/unodraw/msvbahelper.cxx svx/source/unodraw/msvbahelper.cxx
-new file mode 100644
-index 0000000..f818b95
---- /dev/null
-+++ svx/source/unodraw/msvbahelper.cxx
-@@ -0,0 +1,533 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2000, 2010 Oracle and/or its affiliates.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * This file is part of OpenOffice.org.
-+ *
-+ * OpenOffice.org is free software: you can redistribute it and/or modify
-+ * it under the terms of the GNU Lesser General Public License version 3
-+ * only, as published by the Free Software Foundation.
-+ *
-+ * OpenOffice.org is distributed in the hope that it will be useful,
-+ * but WITHOUT ANY WARRANTY; without even the implied warranty of
-+ * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
-+ * GNU Lesser General Public License version 3 for more details
-+ * (a copy is included in the LICENSE file that accompanied this code).
-+ *
-+ * You should have received a copy of the GNU Lesser General Public License
-+ * version 3 along with OpenOffice.org. If not, see
-+ * <http://www.openoffice.org/license.html>
-+ * for a copy of the LGPLv3 License.
-+ *
-+ ************************************************************************/
-+// MARKER(update_precomp.py): autogen include statement, do not remove
-+#include "precompiled_svx.hxx"
-+
-+#include "msvbahelper.hxx"
-+#include <basic/sbx.hxx>
-+#include <basic/sbstar.hxx>
-+#include <basic/basmgr.hxx>
-+#include <basic/sbmod.hxx>
-+#include <basic/sbmeth.hxx>
-+#include <com/sun/star/document/XDocumentPropertiesSupplier.hpp>
-+#include <com/sun/star/document/XDocumentProperties.hpp>
-+#include <com/sun/star/document/XDocumentInfoSupplier.hpp>
-+#include <com/sun/star/script/vba/XVBACompatibility.hpp>
-+#include <com/sun/star/script/XVBAMacroHelper.hpp>
-+
-+#include <tools/urlobj.hxx>
-+#include <osl/file.hxx>
-+#include <unotools/pathoptions.hxx>
-+#include <cppuhelper/implbase1.hxx>
-+#include <com/sun/star/lang/XUnoTunnel.hpp>
-+
-+using namespace ::com::sun::star;
-+
-+const static rtl::OUString sUrlPart0 = rtl::OUString::createFromAscii( "vnd.sun.star.script:");
-+const static rtl::OUString sUrlPart1 = rtl::OUString::createFromAscii( "?language=Basic&location=document");
-+
-+namespace svx {
-+
-+// old code from msvbahelper ( was in filter ), we need to define an uno service to break some
-+// compile time dependencies for the split build. Additionally the location of this service has
-+// been just chosen for // convenience, really putting the service in any library that is
-+// generally available/loaded is good. The decision to not to put this service in an existing
-+// vba library is intentional as we already call the resolve macro stuff from the binary filters
-+// ( even if the vba functionality is not enabled ) - but... calling this ( service ) could be
-+// determined at runtime so I guess. So, in theory we could put this code in a vba specific
-+// library. ( anyway, lets leave it here for the moment )
-+
-+class VBAMacroResolvedInfo
-+{
-+ SfxObjectShell* mpDocContext;
-+ bool mbFound;
-+ String msResolvedMacro;
-+
-+ public:
-+ VBAMacroResolvedInfo() : mpDocContext(NULL), mbFound( false ){}
-+ void SetResolved( bool bRes ) { mbFound = bRes; }
-+ bool IsResolved() const { return mbFound; }
-+ void SetMacroDocContext(SfxObjectShell* pShell ) { mpDocContext = pShell; }
-+ SfxObjectShell* MacroDocContext() const { return mpDocContext; }
-+ String ResolvedMacro() const { return msResolvedMacro; }
-+ void SetResolvedMacro(const String& sMacro ) { msResolvedMacro = sMacro; }
-+};
-+
-+String makeMacroURLImpl( const String& sMacroName )
-+{
-+ return sUrlPart0.concat( sMacroName ).concat( sUrlPart1 ) ;
-+}
-+
-+::rtl::OUString extractMacroFromURL( const ::rtl::OUString& rMacroUrl )
-+{
-+ if( (rMacroUrl.getLength() > sUrlPart0.getLength() + sUrlPart1.getLength()) &&
-+ rMacroUrl.match( sUrlPart0 ) &&
-+ rMacroUrl.match( sUrlPart1, rMacroUrl.getLength() - sUrlPart1.getLength() ) )
-+ {
-+ return rMacroUrl.copy( sUrlPart0.getLength(), rMacroUrl.getLength() - sUrlPart0.getLength() - sUrlPart1.getLength() );
-+ }
-+ return ::rtl::OUString();
-+}
-+
-+SfxObjectShell* findShellForUrl( const rtl::OUString& sMacroURLOrPath )
-+{
-+ SfxObjectShell* pFoundShell=NULL;
-+ SfxObjectShell* pShell = SfxObjectShell::GetFirst();
-+ INetURLObject aObj;
-+ aObj.SetURL( sMacroURLOrPath );
-+ bool bIsURL = aObj.GetProtocol() != INET_PROT_NOT_VALID;
-+ rtl::OUString aURL;
-+ if ( bIsURL )
-+ aURL = sMacroURLOrPath;
-+ else
-+ {
-+ osl::FileBase::getFileURLFromSystemPath( sMacroURLOrPath, aURL );
-+ aObj.SetURL( aURL );
-+ }
-+ OSL_TRACE("Trying to find shell for url %s", rtl::OUStringToOString( aURL, RTL_TEXTENCODING_UTF8 ).getStr() );
-+ while ( pShell )
-+ {
-+
-+ uno::Reference< frame::XModel > xModel = pShell->GetModel();
-+ // are we searching for a template? if so we have to cater for the
-+ // fact that in openoffice a document opened from a template is always
-+ // a new document :/
-+ if ( xModel.is() )
-+ {
-+ OSL_TRACE("shell 0x%x has model with url %s and we look for %s", pShell
-+ , rtl::OUStringToOString( xModel->getURL(), RTL_TEXTENCODING_UTF8 ).getStr()
-+ , rtl::OUStringToOString( aURL, RTL_TEXTENCODING_UTF8 ).getStr()
-+ );
-+ if ( sMacroURLOrPath.endsWithIgnoreAsciiCaseAsciiL( ".dot", 4 ) )
-+ {
-+ uno::Reference< document::XDocumentInfoSupplier > xDocInfoSupp( xModel, uno::UNO_QUERY );
-+ if( xDocInfoSupp.is() )
-+ {
-+ uno::Reference< document::XDocumentPropertiesSupplier > xDocPropSupp( xDocInfoSupp->getDocumentInfo(), uno::UNO_QUERY_THROW );
-+ uno::Reference< document::XDocumentProperties > xDocProps( xDocPropSupp->getDocumentProperties(), uno::UNO_QUERY_THROW );
-+ rtl::OUString sCurrName = xDocProps->getTemplateName();
-+ if( sMacroURLOrPath.lastIndexOf( sCurrName ) >= 0 )
-+ {
-+ pFoundShell = pShell;
-+ break;
-+ }
-+ }
-+ }
-+ else
-+ {
-+ // sometimes just the name of the document ( without the path
-+ // is used
-+ bool bDocNameNoPathMatch = false;
-+ if ( aURL.getLength() && aURL.indexOf( '/' ) == -1 )
-+ {
-+ sal_Int32 lastSlashIndex = xModel->getURL().lastIndexOf( '/' );
-+ if ( lastSlashIndex > -1 )
-+ {
-+ bDocNameNoPathMatch = xModel->getURL().copy( lastSlashIndex + 1 ).equals( aURL );
-+ if ( !bDocNameNoPathMatch )
-+ {
-+ rtl::OUString aTmpName = rtl::OUString::createFromAscii("'") + xModel->getURL().copy( lastSlashIndex + 1 ) + rtl::OUString::createFromAscii("'");
-+ bDocNameNoPathMatch = aTmpName.equals( aURL );
-+ }
-+ }
-+ }
-+
-+ if ( aURL.equals( xModel->getURL() ) || bDocNameNoPathMatch )
-+ {
-+ pFoundShell = pShell;
-+ break;
-+ }
-+ }
-+ }
-+ pShell = SfxObjectShell::GetNext( *pShell );
-+ }
-+ return pFoundShell;
-+}
-+
-+// sMod can be empty ( but we really need the library to search in )
-+// if sMod is empty and a macro is found then sMod is updated
-+bool hasMacro( SfxObjectShell* pShell, const String& sLibrary, String& sMod, const String& sMacro )
-+{
-+ bool bFound = false;
-+ if ( sLibrary.Len() && sMacro.Len() )
-+ {
-+ OSL_TRACE("** Searching for %s.%s in library %s"
-+ ,rtl::OUStringToOString( sMod, RTL_TEXTENCODING_UTF8 ).getStr()
-+ ,rtl::OUStringToOString( sMacro, RTL_TEXTENCODING_UTF8 ).getStr()
-+ ,rtl::OUStringToOString( sLibrary, RTL_TEXTENCODING_UTF8 ).getStr() );
-+ 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 )
-+ bFound = true;
-+ }
-+ }
-+ }
-+ else if( SbMethod* pMethod = dynamic_cast< SbMethod* >( pBasic->Find( sMacro, SbxCLASS_METHOD ) ) )
-+ {
-+ if( SbModule* pModule = pMethod->GetModule() )
-+ {
-+ sMod = pModule->GetName();
-+ bFound = true;
-+ }
-+ }
-+ }
-+ }
-+ }
-+ return bFound;
-+}
-+void parseMacro( const rtl::OUString& sMacro, String& sContainer, String& sModule, String& sProcedure )
-+{
-+ sal_Int32 nMacroDot = sMacro.lastIndexOf( '.' );
-+
-+ if ( nMacroDot != -1 )
-+ {
-+ sProcedure = sMacro.copy( nMacroDot + 1 );
-+
-+ sal_Int32 nContainerDot = sMacro.lastIndexOf( '.', nMacroDot - 1 );
-+ if ( nContainerDot != -1 )
-+ {
-+ sModule = sMacro.copy( nContainerDot + 1, nMacroDot - nContainerDot - 1 );
-+ sContainer = sMacro.copy( 0, nContainerDot );
-+ }
-+ else
-+ sModule = sMacro.copy( 0, nMacroDot );
-+ }
-+ else
-+ sProcedure = sMacro;
-+}
-+
-+VBAMacroResolvedInfo resolveVBAMacroImpl( SfxObjectShell* pShell, const rtl::OUString& MacroName, sal_Bool bSearchGlobalTemplates )
-+{
-+ VBAMacroResolvedInfo aRes;
-+ if ( !pShell )
-+ return aRes;
-+ aRes.SetMacroDocContext( pShell );
-+
-+ // the name may be enclosed in apostrophs
-+ ::rtl::OUString sMacroUrl = MacroName;
-+ sal_Int32 nMacroLen = MacroName.getLength();
-+ if( (nMacroLen >= 2) && (MacroName[0] == '\'') && (MacroName[nMacroLen-1] == '\'') )
-+ sMacroUrl = MacroName.copy( 1, nMacroLen - 2 );
-+
-+ // parse the macro name
-+ sal_Int32 nDocSepIndex = sMacroUrl.indexOf( '!' );
-+
-+ String sContainer;
-+ String sModule;
-+ String sProcedure;
-+
-+ if( nDocSepIndex > 0 )
-+ {
-+ // macro specified by document name
-+ // find document shell for document name and call ourselves
-+ // recursively
-+
-+ // assume for now that the document name is *this* document
-+ String sDocUrlOrPath = sMacroUrl.copy( 0, nDocSepIndex );
-+ sMacroUrl = sMacroUrl.copy( nDocSepIndex + 1 );
-+ OSL_TRACE("doc search, current shell is 0x%x", pShell );
-+ SfxObjectShell* pFoundShell = NULL;
-+ if( bSearchGlobalTemplates )
-+ {
-+ SvtPathOptions aPathOpt;
-+ String aAddinPath = aPathOpt.GetAddinPath();
-+ if( rtl::OUString( sDocUrlOrPath ).indexOf( aAddinPath ) == 0 )
-+ pFoundShell = pShell;
-+ }
-+ if( pFoundShell == NULL )
-+ pFoundShell = findShellForUrl( sDocUrlOrPath );
-+ OSL_TRACE("doc search, after find, found shell is 0x%x", pFoundShell );
-+ aRes = resolveVBAMacroImpl( pFoundShell, sMacroUrl, bSearchGlobalTemplates );
-+ return aRes;
-+ }
-+ else
-+ {
-+ // macro is contained in 'this' document ( or code imported from a template
-+ // where that template is a global template or perhaps the template this
-+ // document is created from )
-+
-+ // macro format = Container.Module.Procedure
-+ parseMacro( sMacroUrl, sContainer, sModule, sProcedure );
-+ uno::Reference< lang::XMultiServiceFactory> xSF( pShell->GetModel(), uno::UNO_QUERY);
-+ uno::Reference< container::XNameContainer > xPrjNameCache;
-+ if ( xSF.is() )
-+ xPrjNameCache.set( xSF->createInstance( rtl::OUString(RTL_CONSTASCII_USTRINGPARAM( "ooo.vba.VBAProjectNameProvider" ) ) ), uno::UNO_QUERY );
-+
-+ std::vector< rtl::OUString > sSearchList;
-+
-+ if ( sContainer.Len() > 0 )
-+ {
-+ // get the Project associated with the Container
-+ if ( xPrjNameCache.is() )
-+ {
-+ if ( xPrjNameCache->hasByName( sContainer ) )
-+ {
-+ rtl::OUString sProject;
-+ xPrjNameCache->getByName( sContainer ) >>= sProject;
-+ sContainer = sProject;
-+ }
-+ }
-+ sSearchList.push_back( sContainer ); // First Lib to search
-+ }
-+ else
-+ {
-+ // Ok, if we have no Container specified then we need to search them in order, this document, template this document created from, global templates,
-+ // get the name of Project/Library for 'this' document
-+ rtl::OUString sThisProject = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("Standard") );
-+ try
-+ {
-+ uno::Reference< beans::XPropertySet > xProps( pShell->GetModel(), uno::UNO_QUERY_THROW );
-+ uno::Reference< script::vba::XVBACompatibility > xVBAMode( xProps->getPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("BasicLibraries") ) ), uno::UNO_QUERY_THROW );
-+ sThisProject = xVBAMode->getProjectName();
-+ }
-+ catch( uno::Exception& /*e*/) {}
-+
-+ sSearchList.push_back( sThisProject ); // First Lib to search
-+ if ( xPrjNameCache.is() )
-+ {
-+ // is this document created from a template?
-+ uno::Reference< document::XDocumentInfoSupplier > xDocInfoSupp( pShell->GetModel(), uno::UNO_QUERY_THROW );
-+ uno::Reference< document::XDocumentPropertiesSupplier > xDocPropSupp( xDocInfoSupp->getDocumentInfo(), uno::UNO_QUERY_THROW );
-+ uno::Reference< document::XDocumentProperties > xDocProps( xDocPropSupp->getDocumentProperties(), uno::UNO_QUERY_THROW );
-+
-+ rtl::OUString sCreatedFrom = xDocProps->getTemplateURL();
-+ if ( sCreatedFrom.getLength() )
-+ {
-+ INetURLObject aObj;
-+ aObj.SetURL( sCreatedFrom );
-+ bool bIsURL = aObj.GetProtocol() != INET_PROT_NOT_VALID;
-+ rtl::OUString aURL;
-+ if ( bIsURL )
-+ aURL = sCreatedFrom;
-+ else
-+ {
-+ osl::FileBase::getFileURLFromSystemPath( sCreatedFrom, aURL );
-+ aObj.SetURL( aURL );
-+ }
-+ sCreatedFrom = aObj.GetLastName();
-+ }
-+
-+ sal_Int32 nIndex = sCreatedFrom.lastIndexOf( '.' );
-+ if ( nIndex != -1 )
-+ sCreatedFrom = sCreatedFrom.copy( 0, nIndex );
-+
-+ rtl::OUString sPrj;
-+ if ( sCreatedFrom.getLength() && xPrjNameCache->hasByName( sCreatedFrom ) )
-+ {
-+ xPrjNameCache->getByName( sCreatedFrom ) >>= sPrj;
-+ // Make sure we don't double up with this project
-+ if ( !sPrj.equals( sThisProject ) )
-+ sSearchList.push_back( sPrj );
-+ }
-+
-+ // get list of global template Names
-+ uno::Sequence< rtl::OUString > sTemplateNames = xPrjNameCache->getElementNames();
-+ sal_Int32 nLen = sTemplateNames.getLength();
-+ for ( sal_Int32 index = 0; ( bSearchGlobalTemplates && index < nLen ); ++index )
-+ {
-+
-+ if ( !sCreatedFrom.equals( sTemplateNames[ index ] ) )
-+ {
-+ if ( xPrjNameCache->hasByName( sTemplateNames[ index ] ) )
-+ {
-+ xPrjNameCache->getByName( sTemplateNames[ index ] ) >>= sPrj;
-+ // Make sure we don't double up with this project
-+ if ( !sPrj.equals( sThisProject ) )
-+ sSearchList.push_back( sPrj );
-+ }
-+ }
-+
-+ }
-+ }
-+ }
-+ std::vector< rtl::OUString >::iterator it_end = sSearchList.end();
-+ for ( std::vector< rtl::OUString >::iterator it = sSearchList.begin(); it != it_end; ++it )
-+ {
-+ bool bRes = hasMacro( pShell, *it, sModule, sProcedure );
-+ if ( bRes )
-+ {
-+ aRes.SetResolved( true );
-+ aRes.SetMacroDocContext( pShell );
-+ sContainer = *it;
-+ break;
-+ }
-+ }
-+ aRes.SetResolvedMacro( sProcedure.Insert( '.', 0 ).Insert( sModule, 0).Insert( '.', 0 ).Insert( sContainer, 0 ) );
-+ }
-+
-+ return aRes;
-+}
-+
-+// Treat the args as possible inouts ( convertion at bottom of method )
-+sal_Bool executeMacroImpl( SfxObjectShell* pShell, const String& sMacroName, uno::Sequence< uno::Any >& aArgs, uno::Any& aRet, const uno::Any& /*aCaller*/ )
-+{
-+ sal_Bool bRes = sal_False;
-+ if ( !pShell )
-+ return bRes;
-+ rtl::OUString sUrl = makeMacroURLImpl( sMacroName );
-+
-+ uno::Sequence< sal_Int16 > aOutArgsIndex;
-+ uno::Sequence< uno::Any > aOutArgs;
-+
-+ try
-+ { ErrCode nErr( ERRCODE_BASIC_INTERNAL_ERROR );
-+ if ( pShell )
-+ {
-+ nErr = pShell->CallXScript( sUrl,
-+ aArgs, aRet, aOutArgsIndex, aOutArgs, false );
-+ sal_Int32 nLen = aOutArgs.getLength();
-+ // convert any out params to seem like they were inouts
-+ if ( nLen )
-+ {
-+ for ( sal_Int32 index=0; index < nLen; ++index )
-+ {
-+ sal_Int32 nOutIndex = aOutArgsIndex[ index ];
-+ aArgs[ nOutIndex ] = aOutArgs[ index ];
-+ }
-+ }
-+ }
-+ bRes = ( nErr == ERRCODE_NONE );
-+ }
-+ catch ( uno::Exception& )
-+ {
-+ bRes = sal_False;
-+ }
-+ return bRes;
-+}
-+
-+SfxObjectShell* getShellFromModel( const uno::Reference< frame::XModel >& rxModel )
-+{
-+ SfxObjectShell* pFoundShell = NULL;
-+ try
-+ {
-+ uno::Reference< lang::XUnoTunnel > xObjShellTunnel( rxModel, uno::UNO_QUERY );
-+ if ( xObjShellTunnel.is() )
-+ pFoundShell = reinterpret_cast<SfxObjectShell*>( xObjShellTunnel->getSomething(SfxObjectShell::getUnoTunnelId()));
-+ }
-+ catch( uno::Exception& )
-+ {
-+ }
-+ return pFoundShell;
-+}
-+//wrapper service(s)
-+
-+class VBAMacroResolvedInfoWrapper : public ::cppu::WeakImplHelper1< script::XVBAMacroResolvedInfo >
-+{
-+ sal_Bool mbResolved;
-+ rtl::OUString msResolvedMacro;
-+ uno::Reference< frame::XModel > mxDocCtx;
-+ public:
-+ VBAMacroResolvedInfoWrapper( const VBAMacroResolvedInfo& rInfo ) : mbResolved( rInfo.IsResolved() ), msResolvedMacro( rInfo.ResolvedMacro() ), mxDocCtx( rInfo.MacroDocContext() ? rInfo.MacroDocContext()->GetModel() : NULL )
-+ {
-+ }
-+ // Attributes
-+ virtual ::sal_Bool SAL_CALL getResolved() throw (uno::RuntimeException) { return mbResolved; }
-+ virtual void SAL_CALL setResolved( ::sal_Bool _resolved ) throw (uno::RuntimeException){ mbResolved = _resolved; }
-+ virtual ::rtl::OUString SAL_CALL getResolvedMacro() throw (uno::RuntimeException) { return msResolvedMacro; }
-+ virtual void SAL_CALL setResolvedMacro( const ::rtl::OUString& _resolvedmacro ) throw (uno::RuntimeException) { msResolvedMacro = _resolvedmacro; }
-+ virtual uno::Reference< frame::XModel > SAL_CALL getDocumentContext() throw (uno::RuntimeException) { return mxDocCtx; }
-+ virtual void SAL_CALL setDocumentContext( const uno::Reference< frame::XModel >& _documentcontext ) throw (uno::RuntimeException) { mxDocCtx = _documentcontext; }
-+};
-+
-+class VBAMacroHelper : public ::cppu::WeakImplHelper1< script::XVBAMacroHelper >
-+{
-+
-+ public:
-+ VBAMacroHelper() {}
-+ // Methods
-+ virtual ::rtl::OUString SAL_CALL makeMacroURL( const ::rtl::OUString& sMacroName ) throw (uno::RuntimeException);
-+ virtual ::rtl::OUString SAL_CALL extractMacroNameFromURL( const ::rtl::OUString& sURL ) throw (uno::RuntimeException);
-+ virtual uno::Reference< script::XVBAMacroResolvedInfo > SAL_CALL resolveVBAMacro( const uno::Reference< frame::XModel >& model, const ::rtl::OUString& moduleName, ::sal_Bool bSearchGlobalTemplates ) throw (uno::RuntimeException);
-+ virtual ::sal_Bool SAL_CALL executeMacro( const uno::Reference< frame::XModel >& model, const ::rtl::OUString& smacroName, uno::Sequence< uno::Any >& aArgs, uno::Any& aRet, const uno::Any& aCaller ) throw (uno::RuntimeException);
-+};
-+
-+::rtl::OUString SAL_CALL
-+VBAMacroHelper::makeMacroURL( const ::rtl::OUString& sMacroName ) throw (uno::RuntimeException)
-+{
-+ rtl::OUString sMacro = makeMacroURLImpl( sMacroName );
-+ return sMacro;
-+}
-+
-+::rtl::OUString SAL_CALL
-+VBAMacroHelper::extractMacroNameFromURL( const ::rtl::OUString& sURL ) throw (uno::RuntimeException)
-+{
-+ rtl::OUString sMacro = extractMacroFromURL( sURL );
-+ return sMacro;
-+}
-+uno::Reference< script::XVBAMacroResolvedInfo > SAL_CALL
-+VBAMacroHelper::resolveVBAMacro( const uno::Reference< frame::XModel >& model, const ::rtl::OUString& moduleName, ::sal_Bool bSearchGlobalTemplates ) throw (uno::RuntimeException)
-+{
-+ VBAMacroResolvedInfo tmpInfo = resolveVBAMacroImpl( getShellFromModel( model ), moduleName, bSearchGlobalTemplates );
-+ uno::Reference< script::XVBAMacroResolvedInfo > xMacro = new VBAMacroResolvedInfoWrapper( tmpInfo );
-+ return xMacro;
-+}
-+
-+// Treat the args as possible inouts ( convertion at bottom of method )
-+::sal_Bool SAL_CALL
-+VBAMacroHelper::executeMacro( const uno::Reference< frame::XModel >& model, const ::rtl::OUString& smacroName, uno::Sequence< uno::Any >& aArgs, uno::Any& aRet, const uno::Any& aCaller ) throw (uno::RuntimeException)
-+{
-+ return executeMacroImpl( getShellFromModel( model ), smacroName, aArgs, aRet, aCaller );
-+}
-+
-+uno::Reference< uno::XInterface > SAL_CALL VBAMacroHelper_createInstance(const uno::Reference< ::com::sun::star::lang::XMultiServiceFactory > & /*rSMgr*/ ) throw( uno::Exception )
-+{
-+ uno::Reference< script::XVBAMacroHelper > xHelper( new VBAMacroHelper() );
-+ return xHelper;
-+}
-+
-+uno::Sequence< ::rtl::OUString > SAL_CALL VBAMacroHelper_getSupportedServiceNames() throw()
-+{
-+ uno::Sequence< rtl::OUString > aSupportedServiceNames( 1 );
-+ aSupportedServiceNames[0] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "com.sun.star.script.VBAMacroHelper" ) );
-+ return aSupportedServiceNames;
-+}
-+
-+::rtl::OUString VBAMacroHelper_getImplementationName() throw()
-+{
-+ return rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "com.sun.star.script.VBAMacroHelper" ) );
-+}
-+
-+} // svx
-diff --git svx/source/unodraw/msvbahelper.hxx svx/source/unodraw/msvbahelper.hxx
-new file mode 100644
-index 0000000..59abd2f
---- /dev/null
-+++ svx/source/unodraw/msvbahelper.hxx
-@@ -0,0 +1,39 @@
-+/*************************************************************************
-+ *
-+ * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-+ *
-+ * Copyright 2000, 2010 Oracle and/or its affiliates.
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * This file is part of OpenOffice.org.
-+ *
-+ * OpenOffice.org is free software: you can redistribute it and/or modify
-+ * it under the terms of the GNU Lesser General Public License version 3
-+ * only, as published by the Free Software Foundation.
-+ *
-+ * OpenOffice.org is distributed in the hope that it will be useful,
-+ * but WITHOUT ANY WARRANTY; without even the implied warranty of
-+ * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
-+ * GNU Lesser General Public License version 3 for more details
-+ * (a copy is included in the LICENSE file that accompanied this code).
-+ *
-+ * You should have received a copy of the GNU Lesser General Public License
-+ * version 3 along with OpenOffice.org. If not, see
-+ * <http://www.openoffice.org/license.html>
-+ * for a copy of the LGPLv3 License.
-+ *
-+ ************************************************************************/
-+#ifndef _MSVBAHELPER_HXX
-+#define _MSVBAHELPER_HXX
-+
-+#include <sfx2/objsh.hxx>
-+#include "svx/svxdllapi.h"
-+
-+namespace svx {
-+ SVX_DLLPUBLIC ::com::sun::star::uno::Reference< ::com::sun::star::uno::XInterface > SAL_CALL VBAMacroHelper_createInstance(const ::com::sun::star::uno::Reference< ::com::sun::star::lang::XMultiServiceFactory > & rSMgr) throw( ::com::sun::star::uno::Exception );
-+ SVX_DLLPUBLIC ::com::sun::star::uno::Sequence< ::rtl::OUString > SAL_CALL VBAMacroHelper_getSupportedServiceNames() throw();
-+ SVX_DLLPUBLIC ::rtl::OUString SAL_CALL VBAMacroHelper_getImplementationName() throw();
-+} //svx
-+
-+#endif
-diff --git svx/source/unodraw/unoctabl.cxx svx/source/unodraw/unoctabl.cxx
-index 060ab89..6503abc 100644
---- svx/source/unodraw/unoctabl.cxx
-+++ svx/source/unodraw/unoctabl.cxx
-@@ -40,6 +40,7 @@
- #include "xmlgrhlp.hxx"
- #include "tbunocontroller.hxx"
- #include "tbunosearchcontrollers.hxx"
-+#include "msvbahelper.hxx"
-
- using namespace ::com::sun::star;
- using namespace ::rtl;
-@@ -274,6 +275,17 @@ static void writeInfo (
- xNewKey->createKey( rServices.getConstArray()[i]);
- }
-
-+static void writeSingletonInfo (
-+ registry::XRegistryKey * pRegistryKey,
-+ const OUString& rImplementationName,
-+ const OUString& rSingletonName )
-+{
-+ uno::Reference< registry::XRegistryKey > xNewKey(
-+ pRegistryKey->createKey(
-+ OUString( rImplementationName + OUString( RTL_CONSTASCII_USTRINGPARAM("/UNO/SINGLETONS/") ) + rSingletonName ) ) );
-+
-+ xNewKey->setStringValue( rImplementationName );
-+}
- SAL_DLLPUBLIC_EXPORT sal_Bool SAL_CALL component_writeInfo (
- void * , void * pRegistryKey)
- {
-@@ -288,6 +300,8 @@ SAL_DLLPUBLIC_EXPORT sal_Bool SAL_CALL component_writeInfo (
- writeInfo( pKey, EnhancedCustomShapeEngine_getImplementationName(), EnhancedCustomShapeEngine_getSupportedServiceNames() );
- writeInfo( pKey, svx::RecoveryUI::st_getImplementationName(), svx::RecoveryUI::st_getSupportedServiceNames() );
- writeInfo( pKey, svx::GraphicExporter_getImplementationName(), svx::GraphicExporter_getSupportedServiceNames() );
-+ writeInfo( pKey, svx::VBAMacroHelper_getImplementationName(), svx::VBAMacroHelper_getSupportedServiceNames() );
-+ writeSingletonInfo( pKey, svx::VBAMacroHelper_getImplementationName(), rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "com.sun.star.script.theVBAMacroHelper" ) ) );
- writeInfo( pKey, svx::FontHeightToolBoxControl::getImplementationName_Static(), svx::FontHeightToolBoxControl::getSupportedServiceNames_Static() );
-
- writeInfo( pKey, svx::FindTextToolbarController::getImplementationName_Static(), svx::FindTextToolbarController::getSupportedServiceNames_Static() );
-@@ -358,6 +372,13 @@ SAL_DLLPUBLIC_EXPORT void * SAL_CALL component_getFactory (
- svx::GraphicExporter_createInstance,
- svx::GraphicExporter_getSupportedServiceNames() );
- }
-+ else if( svx::VBAMacroHelper_getImplementationName().equalsAscii( pImplName ) )
-+ {
-+ xFactory = ::cppu::createSingleFactory( reinterpret_cast< lang::XMultiServiceFactory * >( pServiceManager ),
-+ svx::VBAMacroHelper_getImplementationName(),
-+ svx::VBAMacroHelper_createInstance,
-+ svx::VBAMacroHelper_getSupportedServiceNames() );
-+ }
- else if ( svx::FontHeightToolBoxControl::getImplementationName_Static().equalsAscii( pImplName ) )
- {
- xFactory = createSingleFactory( reinterpret_cast< lang::XMultiServiceFactory * >( pServiceManager ),
-diff --git sw/source/filter/ww8/ww8par.cxx sw/source/filter/ww8/ww8par.cxx
-index c71f885..394b2af 100644
---- sw/source/filter/ww8/ww8par.cxx
-+++ sw/source/filter/ww8/ww8par.cxx
-@@ -155,7 +155,6 @@ using namespace nsHdFtFlags;
- #include <com/sun/star/document/XEventsSupplier.hpp>
- #include <com/sun/star/container/XNameReplace.hpp>
- #include <com/sun/star/frame/XModel.hpp>
--#include <filter/msfilter/msvbahelper.hxx>
- #include <unotools/pathoptions.hxx>
- #include <com/sun/star/ucb/XSimpleFileAccess.hpp>
-
-diff --git vbahelper/inc/vbahelper/vbaapplicationbase.hxx vbahelper/inc/vbahelper/vbaapplicationbase.hxx
-index d1ef76c..737274d 100644
---- vbahelper/inc/vbahelper/vbaapplicationbase.hxx
-+++ vbahelper/inc/vbahelper/vbaapplicationbase.hxx
-@@ -30,6 +30,8 @@
- #include <ooo/vba/XHelperInterface.hpp>
- #include <ooo/vba/XApplicationBase.hpp>
- #include <vbahelper/vbahelperinterface.hxx>
-+#include <com/sun/star/script/XVBAMacroHelper.hpp>
-+
- #include <sfx2/objsh.hxx>
-
- typedef InheritedHelperInterfaceImpl1< ov::XApplicationBase > ApplicationBase_BASE;
-@@ -41,6 +43,7 @@ class VBAHELPER_DLLPUBLIC VbaApplicationBase : public ApplicationBase_BASE
- VbaApplicationBase_Impl* m_pImpl;
-
- protected:
-+ css::uno::Reference< css::script::XVBAMacroHelper > m_xMacroHelper;
- VbaApplicationBase( const css::uno::Reference< css::uno::XComponentContext >& xContext );
- virtual ~VbaApplicationBase();
-
-diff --git vbahelper/inc/vbahelper/vbaeventshelperbase.hxx vbahelper/inc/vbahelper/vbaeventshelperbase.hxx
-index b0dd184..8443251 100755
---- vbahelper/inc/vbahelper/vbaeventshelperbase.hxx
-+++ vbahelper/inc/vbahelper/vbaeventshelperbase.hxx
-@@ -30,6 +30,7 @@
-
- #include <com/sun/star/lang/XEventListener.hpp>
- #include <com/sun/star/script/vba/XVBAEventProcessor.hpp>
-+#include <com/sun/star/script/XVBAMacroHelper.hpp>
- #include <cppuhelper/implbase2.hxx>
- #include <map>
- #include <deque>
-@@ -147,7 +148,9 @@ private:
- void stopListening();
-
- protected:
-+ css::uno::Reference< css::script::XVBAMacroHelper > mxMacroHelper;
- css::uno::Reference< css::frame::XModel > mxModel;
-+ css::uno::Reference< css::uno::XComponentContext > mxContext;
- SfxObjectShell* mpShell;
-
- private:
-diff --git vbahelper/source/msforms/vbacombobox.cxx vbahelper/source/msforms/vbacombobox.cxx
-index 5c05894..f7346f4 100644
---- vbahelper/source/msforms/vbacombobox.cxx
-+++ vbahelper/source/msforms/vbacombobox.cxx
-@@ -26,7 +26,6 @@
- ************************************************************************/
- #include "vbacombobox.hxx"
- #include <vector>
--#include <filter/msfilter/msvbahelper.hxx>
- #include <basic/sbstar.hxx>
- #include <basic/sbmod.hxx>
-
-diff --git vbahelper/source/vbahelper/vbaapplicationbase.cxx vbahelper/source/vbahelper/vbaapplicationbase.cxx
-index bb12c44..1541d97 100644
---- vbahelper/source/vbahelper/vbaapplicationbase.cxx
-+++ vbahelper/source/vbahelper/vbaapplicationbase.cxx
-@@ -40,9 +40,10 @@
- #include <com/sun/star/document/XDocumentPropertiesSupplier.hpp>
- #include <com/sun/star/document/XEmbeddedScripts.hpp>
- #include <com/sun/star/awt/XWindow2.hpp>
-+#include <com/sun/star/script/theVBAMacroHelper.hpp>
-+#include <comphelper/processfactory.hxx>
-
- #include <hash_map>
--#include <filter/msfilter/msvbahelper.hxx>
- #include <tools/datetime.hxx>
-
- #include <basic/sbx.hxx>
-@@ -182,6 +183,13 @@ VbaApplicationBase::VbaApplicationBase( const uno::Reference< uno::XComponentCon
- : ApplicationBase_BASE( uno::Reference< XHelperInterface >(), xContext )
- , m_pImpl( new VbaApplicationBase_Impl )
- {
-+ try
-+ {
-+ m_xMacroHelper = script::theVBAMacroHelper::get( comphelper::getProcessComponentContext() );
-+ }
-+ catch( uno::Exception& e )
-+ {
-+ }
- }
-
- VbaApplicationBase::~VbaApplicationBase()
-@@ -345,8 +353,10 @@ uno::Any SAL_CALL VbaApplicationBase::Run( const ::rtl::OUString& MacroName, con
-
-
- // search the global tempalte
-- VBAMacroResolvedInfo aMacroInfo = resolveVBAMacro( getSfxObjShell( aMacroDocumentModel ), sMacro_only_Name, sal_True );
-- if( aMacroInfo.IsResolved() )
-+ uno::Reference< script::XVBAMacroResolvedInfo > xMacroInfo;
-+ if ( m_xMacroHelper.is() )
-+ xMacroInfo = m_xMacroHelper->resolveVBAMacro( getCurrentDocument(), MacroName, sal_True );
-+ if( xMacroInfo->getResolved() )
- {
- // handle the arguments
- const uno::Any* aArgsPtrArray[] = { &varg1, &varg2, &varg3, &varg4, &varg5, &varg6, &varg7, &varg8, &varg9, &varg10, &varg11, &varg12, &varg13, &varg14, &varg15, &varg16, &varg17, &varg18, &varg19, &varg20, &varg21, &varg22, &varg23, &varg24, &varg25, &varg26, &varg27, &varg28, &varg29, &varg30 };
-@@ -372,7 +382,7 @@ uno::Any SAL_CALL VbaApplicationBase::Run( const ::rtl::OUString& MacroName, con
-
- uno::Any aRet;
- uno::Any aDummyCaller;
-- executeMacro( aMacroInfo.MacroDocContext(), aMacroInfo.ResolvedMacro(), aArgs, aRet, aDummyCaller );
-+ m_xMacroHelper->executeMacro( xMacroInfo->getDocumentContext(), xMacroInfo->getResolvedMacro(), aArgs, aRet, aDummyCaller );
-
- return aRet;
- }
-diff --git vbahelper/source/vbahelper/vbacommandbarcontrol.cxx vbahelper/source/vbahelper/vbacommandbarcontrol.cxx
-index 1b2d013..3378a4d 100644
---- vbahelper/source/vbahelper/vbacommandbarcontrol.cxx
-+++ vbahelper/source/vbahelper/vbacommandbarcontrol.cxx
-@@ -27,7 +27,8 @@
- #include "vbacommandbarcontrol.hxx"
- #include "vbacommandbarcontrols.hxx"
- #include <vbahelper/vbahelper.hxx>
--#include <filter/msfilter/msvbahelper.hxx>
-+#include <com/sun/star/script/theVBAMacroHelper.hpp>
-+#include <comphelper/processfactory.hxx>
-
- using namespace com::sun::star;
- using namespace ooo::vba;
-@@ -78,10 +79,11 @@ ScVbaCommandBarControl::setOnAction( const ::rtl::OUString& _onaction ) throw (u
- {
- // get the current model
- uno::Reference< frame::XModel > xModel( pCBarHelper->getModel() );
-- VBAMacroResolvedInfo aResolvedMacro = ooo::vba::resolveVBAMacro( getSfxObjShell( xModel ), _onaction, true );
-- if ( aResolvedMacro.IsResolved() )
-+ uno::Reference< script::XVBAMacroHelper > xMacroHelper = script::theVBAMacroHelper::get( comphelper::getProcessComponentContext() );
-+ uno::Reference< script::XVBAMacroResolvedInfo > xResolvedMacro = xMacroHelper->resolveVBAMacro( xModel, _onaction, sal_True );
-+ if ( xResolvedMacro->getResolved() )
- {
-- rtl::OUString aCommandURL = ooo::vba::makeMacroURL( aResolvedMacro.ResolvedMacro() );
-+ rtl::OUString aCommandURL = xMacroHelper->makeMacroURL( xResolvedMacro->getResolvedMacro() );
- OSL_TRACE(" ScVbaCommandBarControl::setOnAction: %s", rtl::OUStringToOString( aCommandURL, RTL_TEXTENCODING_UTF8 ).getStr() );
- setPropertyValue( m_aPropertyValues, rtl::OUString::createFromAscii("CommandURL"), uno::makeAny( aCommandURL ) );
- ApplyChange();
-diff --git vbahelper/source/vbahelper/vbaeventshelperbase.cxx vbahelper/source/vbahelper/vbaeventshelperbase.cxx
-index ee6eccb..43f63f3 100755
---- vbahelper/source/vbahelper/vbaeventshelperbase.cxx
-+++ vbahelper/source/vbahelper/vbaeventshelperbase.cxx
-@@ -26,14 +26,15 @@
- ************************************************************************/
-
- #include "vbahelper/vbaeventshelperbase.hxx"
--#include <filter/msfilter/msvbahelper.hxx>
-+#include <com/sun/star/script/theVBAMacroHelper.hpp>
-
- using namespace ::com::sun::star;
- using namespace ::ooo::vba;
-
- // ============================================================================
-
--VbaEventsHelperBase::VbaEventsHelperBase( const uno::Sequence< uno::Any >& rArgs, const uno::Reference< uno::XComponentContext >& /*xContext*/ ) :
-+VbaEventsHelperBase::VbaEventsHelperBase( const uno::Sequence< uno::Any >& rArgs, const uno::Reference< uno::XComponentContext >& xContext ) :
-+ mxContext( xContext ),
- mpShell( 0 ),
- mbDisposed( false )
- {
-@@ -49,6 +50,17 @@ VbaEventsHelperBase::VbaEventsHelperBase( const uno::Sequence< uno::Any >& rArgs
- catch( uno::Exception& )
- {
- }
-+ try
-+ {
-+ // Our custom context does not handler requests for singletons
-+ // we need to get the system context for that
-+ uno::Reference< beans::XPropertySet > xProps( mxContext->getServiceManager(), uno::UNO_QUERY_THROW );
-+ uno::Reference< uno::XComponentContext > xDfltContext( xProps->getPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("DefaultContext") ) ), uno::UNO_QUERY_THROW );
-+ mxMacroHelper = script::theVBAMacroHelper::get( xDfltContext );
-+ }
-+ catch( uno::Exception& )
-+ {
-+ }
- }
-
- VbaEventsHelperBase::~VbaEventsHelperBase()
-@@ -111,7 +123,7 @@ void SAL_CALL VbaEventsHelperBase::processVbaEvent( sal_Int32 nEventId, const un
- // search the event handler macro in the document
- ::rtl::OUString aMacroPath = getEventHandlerPath( rInfo, aEventArgs );
- bool bEventSuccess = false;
-- if( aMacroPath.getLength() > 0 )
-+ if( mxMacroHelper.is() && aMacroPath.getLength() > 0 )
- {
- // build the argument list
- uno::Sequence< uno::Any > aVbaArgs = implBuildArgumentList( rInfo, aEventArgs );
-@@ -124,7 +136,9 @@ void SAL_CALL VbaEventsHelperBase::processVbaEvent( sal_Int32 nEventId, const un
- }
- // execute the event handler
- uno::Any aRet, aCaller;
-- bEventSuccess = executeMacro( mpShell, aMacroPath, aVbaArgs, aRet, aCaller );
-+
-+ bEventSuccess = mxMacroHelper->executeMacro( mpShell->GetModel(), aMacroPath, aVbaArgs, aRet, aCaller );
-+
- // extract new cancel value
- if( rInfo.mnCancelIndex >= 0 )
- {
-@@ -200,7 +214,14 @@ const VbaEventsHelperBase::EventHandlerInfo& VbaEventsHelperBase::getEventHandle
- append( sal_Unicode( '.' ) ).append( rInfo.maMacroName ).makeStringAndClear();
- break;
- }
-- return resolveVBAMacro( mpShell, aMacroName ).ResolvedMacro();
-+ rtl::OUString sResolvedMacro;
-+ if ( mxMacroHelper.is() )
-+ {
-+ uno::Reference< script::XVBAMacroResolvedInfo > xResolvedMacroInfo = mxMacroHelper->resolveVBAMacro( mpShell->GetModel(), aMacroName, sal_False );
-+ if ( xResolvedMacroInfo.is() )
-+ sResolvedMacro = xResolvedMacroInfo->getResolvedMacro();
-+ }
-+ return sResolvedMacro;
- }
-
- void VbaEventsHelperBase::stopListening()
---- vbahelper/util/makefile.mk.old 2010-09-03 20:43:41.000000000 +0200
-+++ vbahelper/util/makefile.mk 2010-09-03 21:09:21.000000000 +0200
-@@ -60,7 +60,6 @@ SHL1STDLIBS= \
- $(SVLLIB) \
- $(VCLLIB) \
- $(SVTOOLLIB) \
-- $(MSFILTERLIB) \
- $(TKLIB)
-
- SHL1DEPN=