summaryrefslogtreecommitdiff
path: root/patches/vba/vba-fixup-macrosearch.diff
diff options
context:
space:
mode:
Diffstat (limited to 'patches/vba/vba-fixup-macrosearch.diff')
-rw-r--r--patches/vba/vba-fixup-macrosearch.diff1581
1 files changed, 0 insertions, 1581 deletions
diff --git a/patches/vba/vba-fixup-macrosearch.diff b/patches/vba/vba-fixup-macrosearch.diff
deleted file mode 100644
index db726c457..000000000
--- a/patches/vba/vba-fixup-macrosearch.diff
+++ /dev/null
@@ -1,1581 +0,0 @@
-diff --git sc/source/filter/excel/xlescher.cxx sc/source/filter/excel/xlescher.cxx
-index 2109a0a..88eb9d0 100644
---- sc/source/filter/excel/xlescher.cxx
-+++ sc/source/filter/excel/xlescher.cxx
-@@ -45,6 +45,7 @@
- #include <basic/sbmod.hxx>
- #include <basic/sbmeth.hxx>
- #include <basic/basmgr.hxx>
-+#include <svx/msvbahelper.hxx>
-
- using ::rtl::OUString;
- using ::com::sun::star::uno::Reference;
-@@ -306,7 +307,6 @@ Reference< XControlModel > XclControlHelper::GetControlModel( Reference< XShape
- }
-
- #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 )
-@@ -314,27 +314,10 @@ OUString XclControlHelper::GetScMacroName( const String& rXclMacroName, SfxObjec
- String sTmp( rXclMacroName );
- if( rXclMacroName.Len() > 0 )
- {
-- String sProjectName( RTL_CONSTASCII_USTRINGPARAM("Standard") );
-+ ooo::vba::VBAMacroResolvedInfo aMacro = ooo::vba::resolveVBAMacro( pDocShell, rXclMacroName, false );
-+ if ( aMacro.IsResolved() )
-+ return ooo::vba::makeMacroURL( aMacro.ResolvedMacro() );
-
-- if ( pDocShell && pDocShell->GetBasicManager()->GetName().Len() > 0 )
-- sProjectName = pDocShell->GetBasicManager()->GetName();
--
-- if ( ( sTmp.Search( '.' ) == STRING_NOTFOUND) && pDocShell )
-- {
-- if( StarBASIC* pBasic = pDocShell->GetBasicManager()->GetLib( sProjectName ) )
-- {
-- if( SbMethod* pMethod = dynamic_cast< SbMethod* >( pBasic->Find( sTmp, SbxCLASS_METHOD ) ) )
-- {
-- if( SbModule* pModule = pMethod->GetModule() )
-- {
-- sTmp.Insert( '.', 0 ).Insert( pModule->GetName(), 0 );
-- }
-- }
-- }
-- }
-- sProjectName.Append( '.' );
-- sTmp.Insert( sProjectName, 0 );
-- return CREATE_OUSTRING( EXC_MACRO_SCHEME ) + sTmp + CREATE_OUSTRING( EXC_MACRONAME_SUF );
- }
- return OUString();
- }
-diff --git sc/source/ui/unoobj/docuno.cxx sc/source/ui/unoobj/docuno.cxx
-index af78648..16a1c03 100644
---- sc/source/ui/unoobj/docuno.cxx
-+++ sc/source/ui/unoobj/docuno.cxx
-@@ -1793,6 +1793,12 @@ sal_Int64 SAL_CALL ScModelObj::getSomething(
- return sal::static_int_cast<sal_Int64>(reinterpret_cast<sal_IntPtr>(this));
- }
-
-+ if ( rId.getLength() == 16 &&
-+ 0 == rtl_compareMemory( SfxObjectShell::getUnoTunnelId().getConstArray(),
-+ rId.getConstArray(), 16 ) )
-+ {
-+ return sal::static_int_cast<sal_Int64>(reinterpret_cast<sal_IntPtr>(pDocShell ));
-+ }
- // aggregated number formats supplier has XUnoTunnel, too
- // interface from aggregated object must be obtained via queryAggregation
-
-diff --git sc/source/ui/vba/vbaeventshelper.cxx sc/source/ui/vba/vbaeventshelper.cxx
-index 3948ac6..36e1115 100644
---- sc/source/ui/vba/vbaeventshelper.cxx
-+++ sc/source/ui/vba/vbaeventshelper.cxx
-@@ -614,8 +614,8 @@ rtl::OUString
- ScVbaEventsHelper::getMacroPath( const sal_Int32 nEventId, const SCTAB nTab )
- {
- SfxObjectShell* pShell = pDoc->GetDocumentShell();
-- rtl::OUString sMacroPath;
-- rtl::OUString sMacroName = getEventName( nEventId );
-+ String sMacroName = getEventName( nEventId );
-+ VBAMacroResolvedInfo sMacroResolvedInfo;
- switch( nEventId )
- {
- // Worksheet
-@@ -629,8 +629,9 @@ ScVbaEventsHelper::getMacroPath( const sal_Int32 nEventId, const SCTAB nTab )
- case VBAEVENT_WORKSHEET_PIVOTTABLEUPDATE :
- case VBAEVENT_WORKSHEET_SELECTIONCHANGE :
- {
-- rtl::OUString aSheetModuleName = getSheetModuleName( nTab );
-- sMacroPath = findVBAMacro( pShell, aSheetModuleName, sMacroName );
-+ String aSheetModuleName = getSheetModuleName( nTab );
-+ sMacroName.Insert( '.', 0 ).Insert( aSheetModuleName, 0);
-+ sMacroResolvedInfo = resolveVBAMacro( pShell, sMacroName );
- break;
- }
- // Workbook
-@@ -664,13 +665,14 @@ ScVbaEventsHelper::getMacroPath( const sal_Int32 nEventId, const SCTAB nTab )
- sWorkbookModuleName = aExtDocSettings.maGlobCodeName;
- }
-
-- sMacroPath = findVBAMacro( pShell, sWorkbookModuleName, sMacroName );
-+ sMacroName.Insert( '.', 0 ).Insert( sWorkbookModuleName, 0);
-+ sMacroResolvedInfo = resolveVBAMacro( pShell, sMacroName );
- break;
- }
- default:
- break;
- }
-- return sMacroPath;
-+ return sMacroResolvedInfo.ResolvedMacro();
- }
-
- sal_Bool ScVbaEventsHelper::processVbaEvent( const sal_Int32 nEventId, const uno::Sequence< uno::Any >& rArgs, const SCTAB nTab )
-@@ -681,6 +683,7 @@ sal_Bool ScVbaEventsHelper::processVbaEvent( const sal_Int32 nEventId, const uno
- sal_Bool bCancel = sal_False;
- uno::Sequence< uno::Any > aArgs;
- uno::Any aRet;
-+ uno::Any aDummyCaller;
-
- // For most cases, there is no corresponsible event macro in the document.
- // It is better fo check if the event macro exists before process the arguments to improve performance.
-@@ -777,7 +780,7 @@ sal_Bool ScVbaEventsHelper::processVbaEvent( const sal_Int32 nEventId, const uno
- // process Cancel argument
- aArgs = uno::Sequence< uno::Any >(1);
- aArgs[0] <<= bCancel;
-- executeMacro( pShell, sMacroPath, aArgs, aRet );
-+ executeMacro( pShell, sMacroPath, aArgs, aRet, aDummyCaller );
- aArgs[0] >>= bCancel;
- return bCancel;
- }
-@@ -787,7 +790,7 @@ sal_Bool ScVbaEventsHelper::processVbaEvent( const sal_Int32 nEventId, const uno
- aArgs = uno::Sequence< uno::Any >(2);
- aArgs[0] = rArgs[0];
- aArgs[1] <<= bCancel;
-- executeMacro( pShell, sMacroPath, aArgs, aRet );
-+ executeMacro( pShell, sMacroPath, aArgs, aRet, aDummyCaller );
- aArgs[1] >>= bCancel;
- return bCancel;
- }
-@@ -805,7 +808,7 @@ sal_Bool ScVbaEventsHelper::processVbaEvent( const sal_Int32 nEventId, const uno
- }
-
- // excute the macro
-- result = executeMacro( pShell, sMacroPath, aArgs, aRet );
-+ result = executeMacro( pShell, sMacroPath, aArgs, aRet, aDummyCaller );
- }
-
- return result;
-diff --git scripting/prj/build.lst scripting/prj/build.lst
-index fc33238..f216009 100644
---- scripting/prj/build.lst
-+++ scripting/prj/build.lst
-@@ -1,4 +1,4 @@
--tc scripting : oovbaapi bridges rdbmaker vcl xmlscript basic sfx2 rhino BSH:beanshell javaunohelper NULL
-+tc scripting : oovbaapi svx bridges rdbmaker vcl xmlscript basic sfx2 rhino BSH:beanshell javaunohelper NULL
- tc scripting usr1 - all tc1_mkout NULL
- tc scripting\inc nmake - all tc1_inc NULL
- tc scripting\source\provider nmake - all tc1_scriptingprovider tc1_inc NULL
-diff --git scripting/source/vbaevents/eventhelper.cxx scripting/source/vbaevents/eventhelper.cxx
-index 84dc900..f85ac51 100644
---- scripting/source/vbaevents/eventhelper.cxx
-+++ scripting/source/vbaevents/eventhelper.cxx
-@@ -35,14 +35,11 @@
- #include <basic/sbmeth.hxx>
- #include <basic/sbmod.hxx>
- #include <basic/sbx.hxx>
--
--
--
-+#include <svx/msvbahelper.hxx>
-
- // for debug
- #include <comphelper/anytostring.hxx>
-
--
- #include <com/sun/star/lang/XMultiComponentFactory.hpp>
- #include <com/sun/star/script/XScriptListener.hpp>
- #include <cppuhelper/implbase1.hxx>
-@@ -771,7 +768,7 @@ EventListener::getPropertySetInfo( ) throw (RuntimeException)
- // EventListener
-
- void
--EventListener::firing_Impl(const ScriptEvent& evt, Any* /*pRet*/ ) throw(RuntimeException)
-+EventListener::firing_Impl(const ScriptEvent& evt, Any* pRet ) throw(RuntimeException)
- {
- OSL_TRACE("EventListener::firing_Impl( FAKE VBA_EVENTS )");
- static const ::rtl::OUString vbaInterOp =
-@@ -842,22 +839,16 @@ EventListener::firing_Impl(const ScriptEvent& evt, Any* /*pRet*/ ) throw(Runtime
- sMacroLoc = sMacroLoc.concat( sScriptCode ).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 ? pBasic->FindModule( sScriptCode ) : NULL;
--
-- for ( ; pModule && txInfo != txInfo_end; ++txInfo )
-+ for ( ; txInfo != txInfo_end; ++txInfo )
- {
-+ rtl::OUString sTemp = sName.concat( (*txInfo).sVBAName );
- // see if we have a match for the handlerextension
- // where ScriptCode is methodname_handlerextension
-- rtl::OUString sTemp = sName.concat( (*txInfo).sVBAName );
--
-+ rtl::OUString sToResolve = sMacroLoc.concat( sTemp );
- OSL_TRACE("*** trying to invoke %s ",
-- rtl::OUStringToOString( sTemp, RTL_TEXTENCODING_UTF8 ).getStr() );
-- SbMethod* pMeth = static_cast< SbMethod* >( pModule->Find( sTemp, SbxCLASS_METHOD ) );
-- if ( pMeth )
-+ rtl::OUStringToOString( sToResolve, RTL_TEXTENCODING_UTF8 ).getStr() );
-+ ooo::vba::VBAMacroResolvedInfo aMacroResolvedInfo = ooo::vba::resolveVBAMacro( mpShell, sToResolve );
-+ if ( aMacroResolvedInfo.IsResolved() )
- {
- // !! translate arguments & emulate events where necessary
- Sequence< Any > aArguments;
-@@ -869,31 +860,22 @@ EventListener::firing_Impl(const ScriptEvent& evt, Any* /*pRet*/ ) throw(Runtime
- {
- // call basic event handlers for event
-
-- static rtl::OUString part1 = rtl::OUString::createFromAscii( "vnd.sun.star.script:");
-- static rtl::OUString part2 = rtl::OUString::createFromAscii("?language=Basic&location=document");
--
- // create script url
-- rtl::OUString url = part1 + sMacroLoc + sTemp + part2;
-+ rtl::OUString url = aMacroResolvedInfo.ResolvedMacro();
-
-- OSL_TRACE("script url = %s",
-+ OSL_TRACE("resolved script = %s",
- rtl::OUStringToOString( url,
- RTL_TEXTENCODING_UTF8 ).getStr() );
-- Sequence< sal_Int16 > aOutArgsIndex;
-- Sequence< Any > aOutArgs;
- try
- {
-- uno::Reference< script::provider::XScript > xScript = xScriptProvider->getScript( url );
-- if ( xScript.is() )
-- {
-- uno::Reference< beans::XPropertySet > xProps( xScript, uno::UNO_QUERY );
-- if ( xProps.is() )
-- {
-- Sequence< Any > aCallerHack(1);
-- aCallerHack[ 0 ] = uno::makeAny( rtl::OUString::createFromAscii("Error") );
-- xProps->setPropertyValue( rtl::OUString::createFromAscii( "Caller" ), uno::makeAny( aCallerHack ) );
-- }
-- xScript->invoke( aArguments, aOutArgsIndex, aOutArgs );
-- }
-+ uno::Any aDummyCaller = uno::makeAny( rtl::OUString::createFromAscii("Error") );
-+ if ( pRet )
-+ ooo::vba::executeMacro( mpShell, url, aArguments, *pRet, aDummyCaller );
-+ else
-+ {
-+ uno::Any aRet;
-+ ooo::vba::executeMacro( mpShell, url, aArguments, aRet, aDummyCaller );
-+ }
- }
- catch ( uno::Exception& e )
- {
-diff --git scripting/source/vbaevents/makefile.mk scripting/source/vbaevents/makefile.mk
-index eabb67e..96f4e3d 100644
---- scripting/source/vbaevents/makefile.mk
-+++ scripting/source/vbaevents/makefile.mk
-@@ -46,6 +46,7 @@ SHL1STDLIBS= \
- $(BASICLIB) \
- $(COMPHELPERLIB) \
- $(SFXLIB) \
-+ $(SVXMSFILTERLIB) \
- $(CPPULIB) \
- $(TOOLSLIB) \
- $(SALLIB)
-diff --git sfx2/inc/sfx2/objsh.hxx sfx2/inc/sfx2/objsh.hxx
-index c65280b..3f2d197 100644
---- sfx2/inc/sfx2/objsh.hxx
-+++ sfx2/inc/sfx2/objsh.hxx
-@@ -265,6 +265,7 @@ public:
- TYPEINFO();
- SFX_DECL_INTERFACE(SFX_INTERFACE_SFXDOCSH)
-
-+ static const com::sun::star::uno::Sequence<sal_Int8>& getUnoTunnelId();
- /* Stampit disable/enable cancel button for print jobs
- default = true = enable! */
- void Stamp_SetPrintCancelState(sal_Bool bState);
-@@ -885,6 +886,7 @@ public:
- virtual sal_Bool PutValue( const com::sun::star::uno::Any& rVal, BYTE nMemberId = 0 );
- SfxObjectShell* GetObjectShell() const
- { return pObjSh; }
-+
- };
-
- #endif
-diff --git sfx2/source/doc/objserv.cxx sfx2/source/doc/objserv.cxx
-index d16f0c8..dd4f044 100644
---- sfx2/source/doc/objserv.cxx
-+++ sfx2/source/doc/objserv.cxx
-@@ -1480,3 +1480,19 @@ void SfxObjectShell::SignScriptingContent()
- ImplSign( TRUE );
- }
-
-+// static
-+const uno::Sequence<sal_Int8>& SfxObjectShell::getUnoTunnelId()
-+{
-+ static uno::Sequence<sal_Int8> * pSeq = 0;
-+ if( !pSeq )
-+ {
-+ osl::Guard< osl::Mutex > aGuard( osl::Mutex::getGlobalMutex() );
-+ if( !pSeq )
-+ {
-+ static uno::Sequence< sal_Int8 > aSeq( 16 );
-+ rtl_createUuid( (sal_uInt8*)aSeq.getArray(), 0, sal_True );
-+ pSeq = &aSeq;
-+ }
-+ }
-+ return *pSeq;
-+}
-diff --git svx/inc/svx/mstoolbar.hxx svx/inc/svx/mstoolbar.hxx
-index b3667a8..5d76eaf 100644
---- svx/inc/svx/mstoolbar.hxx
-+++ svx/inc/svx/mstoolbar.hxx
-@@ -55,6 +55,7 @@ public:
- void applyIcons();
- rtl::OUString MSOCommandToOOCommand( sal_Int16 msoCmd );
- rtl::OUString MSOTCIDToOOCommand( sal_Int16 msoTCID );
-+ SfxObjectShell& GetDocShell() { return mrDocSh; }
- };
-
- class SVX_DLLPUBLIC TBBase
-diff --git svx/inc/svx/msvbahelper.hxx svx/inc/svx/msvbahelper.hxx
-index 8be6901..294f26e 100644
---- svx/inc/svx/msvbahelper.hxx
-+++ svx/inc/svx/msvbahelper.hxx
-@@ -35,9 +35,24 @@
-
- namespace ooo { namespace vba
- {
-+ class SVX_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; }
-+ };
-+
- SVX_DLLPUBLIC String makeMacroURL( const String& sMacroName );
-- SVX_DLLPUBLIC String findVBAMacro( SfxObjectShell* pShell, const String& sMod, const String& sMacro );
-- SVX_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 );
-+ SVX_DLLPUBLIC VBAMacroResolvedInfo resolveVBAMacro( SfxObjectShell* pShell, const rtl::OUString& sMod, bool bSearchGlobalTemplates = false );
-+ SVX_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
-diff --git svx/inc/svxmsbas.hxx svx/inc/svxmsbas.hxx
-index a777795..fab5faf 100644
---- svx/inc/svxmsbas.hxx
-+++ svx/inc/svxmsbas.hxx
-@@ -91,6 +91,7 @@ public:
- static ULONG GetSaveWarningOfMSVBAStorage( SfxObjectShell &rDocS );
-
- static String GetMSBasicStorageName();
-+ rtl::OUString GetVBAProjectName() { return msProjectName; }
- private:
- SotStorageRef xRoot;
- SfxObjectShell &rDocSh;
-diff --git svx/source/msfilter/mstoolbar.cxx svx/source/msfilter/mstoolbar.cxx
-index 9579db7..fa66fe5 100644
---- svx/source/msfilter/mstoolbar.cxx
-+++ svx/source/msfilter/mstoolbar.cxx
-@@ -12,6 +12,7 @@
- #include <basic/basmgr.hxx>
- #include <svtools/filterutils.hxx>
- #include <boost/scoped_array.hpp>
-+#include <svx/msvbahelper.hxx>
-
- int TBBase::nIndent = 0;
-
-@@ -67,16 +68,8 @@ CustomToolBarImportHelper::createCommandFromMacro( const rtl::OUString& sCmd )
- //"vnd.sun.star.script:Standard.Module1.Main?language=Basic&location=document"
- 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 = scheme + sProject + sCmd + part2;
-+ rtl::OUString scriptURL = scheme + sCmd + part2;
- return uno::makeAny( scriptURL );
- }
-
-@@ -377,7 +370,9 @@ TBCGeneralInfo::ImportToolBarControlData( CustomToolBarImportHelper& helper, std
- if ( extraInfo.getOnAction().getLength() )
- {
- aProp.Name = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("CommandURL") );
-- aProp.Value = helper.createCommandFromMacro( extraInfo.getOnAction() );
-+ ooo::vba::VBAMacroResolvedInfo aMacroInf = ooo::vba::resolveVBAMacro( &helper.GetDocShell(), extraInfo.getOnAction(), true );
-+ if ( aMacroInf.IsResolved() )
-+ aProp.Value = helper.createCommandFromMacro( aMacroInf.ResolvedMacro() );
- sControlData.push_back( aProp );
- }
-
-@@ -390,7 +385,7 @@ TBCGeneralInfo::ImportToolBarControlData( CustomToolBarImportHelper& helper, std
- sControlData.push_back( aProp );
-
- aProp.Name = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("HelpURL") );
-- aProp.Value = uno::makeAny( helper.createCommandFromMacro( tooltip.getString() ) );
-+ aProp.Value = uno::makeAny( tooltip.getString() );
- sControlData.push_back( aProp );
-
- // #TODO find out what is the property for tooltip?
-diff --git svx/source/msfilter/msvbahelper.cxx svx/source/msfilter/msvbahelper.cxx
-index 5875cf7..d02746f 100644
---- svx/source/msfilter/msvbahelper.cxx
-+++ svx/source/msfilter/msvbahelper.cxx
-@@ -34,6 +34,11 @@
- #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 <tools/urlobj.hxx>
-+#include <osl/file.hxx>
-
- using namespace ::com::sun::star;
-
-@@ -44,91 +49,335 @@ namespace ooo { namespace vba {
-
- String makeMacroURL( const String& sMacroName )
- {
-- return sUrlPart0.concat( sMacroName ).concat( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM(".") ) ).concat( sUrlPart1 ) ;
-+ return sUrlPart0.concat( sMacroName ).concat( sUrlPart1 ) ;
- }
-
--String findVBAMacro( SfxObjectShell* pShell, const String& sMod, const String& sMacro )
-+SfxObjectShell* findShellForUrl( const rtl::OUString& sMacroURLOrPath )
- {
-- 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;
-+ 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
-+ {
-+ if ( aURL.equals( xModel->getURL() ) )
-+ {
-+ pFoundShell = pShell;
-+ break;
-+ }
-+ }
-+ }
-+ pShell = SfxObjectShell::GetNext( *pShell );
-+ }
-+ return pFoundShell;
- }
-
--// 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 )
-+// 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 )
- {
-- // until ObjectModules ( and persisting of codenames ) is supported, if this is a
-- // document saved from XL then we won't be able to determine the codename for the Workbook
-- // Module, so... we have no choice but to search all modules for the moment, thus the macro
-- // passed in should be the fully specified name.
-- rtl::OUString sUrl = makeMacroURL( sMacroName );
-- uno::Sequence< sal_Int16 > aOutArgsIndex;
-- uno::Sequence< uno::Any > aOutArgs;
-- ErrCode nErr = pShell->CallXScript( sUrl, aArgs, aRet,
-- aOutArgsIndex, aOutArgs, sal_False );
--
-- // Script Executed?
-- if ( nErr != ERRCODE_NONE )
-- return sal_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 ];
-- }
--
-- }
-- return sal_True;
-+ 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 );
-+ // parse the macro name
-+ sal_Int32 nDocSepIndex = MacroName.indexOfAsciiL( "!", 1 );
-+ String sMacroUrl = MacroName;
-+
-+ 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 = MacroName.copy( 0, nDocSepIndex );
-+ sMacroUrl = MacroName.copy( nDocSepIndex + 1 );
-+ OSL_TRACE("doc search, current shell is 0x%x", pShell );
-+ SfxObjectShell* pFoundShell = findShellForUrl( sDocUrlOrPath );
-+ OSL_TRACE("doc search, after find, found shell is 0x%x", pFoundShell );
-+ aRes = resolveVBAMacro( pFoundShell, sMacroUrl );
-+ }
-+ 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( MacroName, 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;
-+ BasicManager* pBasicMgr = pShell-> GetBasicManager();
-+ if ( pBasicMgr )
-+ {
-+ if ( pBasicMgr->GetName().Len() )
-+ sThisProject = pBasicMgr->GetName();
-+ else // cater for the case where VBA is not enabled
-+ sThisProject = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("Standard") );
-+ }
-+ 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
-+ {
-+ uno::Reference< script::provider::XScriptProvider > xScriptProvider;
-+ uno::Reference< script::provider::XScriptProviderSupplier > xSPS( pShell->GetModel(), uno::UNO_QUERY_THROW );
-+
-+ xScriptProvider.set( xSPS->getScriptProvider(), uno::UNO_QUERY_THROW );
-+
-+ uno::Reference< script::provider::XScript > xScript( xScriptProvider->getScript( sUrl ), uno::UNO_QUERY_THROW );
-+
-+ if ( aCaller.hasValue() )
-+ {
-+ uno::Reference< beans::XPropertySet > xProps( xScript, uno::UNO_QUERY );
-+ if ( xProps.is() )
-+ {
-+ uno::Sequence< uno::Any > aCallerHack(1);
-+ aCallerHack[ 0 ] = aCaller;
-+ xProps->setPropertyValue( rtl::OUString::createFromAscii( "Caller" ), uno::makeAny( aCallerHack ) );
-+ }
-+ }
-+
-+
-+ xScript->invoke( aArgs, aOutArgsIndex, aOutArgs );
-+
-+ 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 = sal_True;
-+ }
-+ catch ( uno::Exception& e )
-+ {
-+ bRes = sal_False;
-+ }
-+ return bRes;
-+}
- } } // vba // ooo
---- sw/inc/doc.hxx
-+++ sw/inc/doc.hxx
-@@ -417,6 +417,7 @@ class SW_DLLPUBLIC SwDoc :
-
- // table of forbidden characters of this document
- vos::ORef<SvxForbiddenCharactersTable> xForbiddenCharsTable;
-+ com::sun::star::uno::Reference<com::sun::star::container::XNameContainer> m_xTemplateToProjectCache;
-
- // --> OD 2007-10-26 #i83479#
- public:
-@@ -2127,6 +2128,8 @@ public:
- {
- return n32DummyCompatabilityOptions2;
- }
-+ void SetVBATemplateToProjectCache( com::sun::star::uno::Reference< com::sun::star::container::XNameContainer >& xCache ) { m_xTemplateToProjectCache = xCache; };
-+ com::sun::star::uno::Reference< com::sun::star::container::XNameContainer > GetVBATemplateToProjectCache() { return m_xTemplateToProjectCache; };
-
- ::sfx2::IXmlIdRegistry& GetXmlIdRegistry();
- SwDoc* CreateCopy() const;
-diff --git sw/inc/unocoll.hxx sw/inc/unocoll.hxx
-index e9da66c..2c6bd02 100644
---- sw/inc/unocoll.hxx
-+++ sw/inc/unocoll.hxx
-@@ -197,8 +197,9 @@ class SwUnoCollection
- #define SW_SERVICE_TYPE_FORMFIELDMARK 108
- #define SW_SERVICE_VBAOBJECTPROVIDER 109
- #define SW_SERVICE_VBACODENAMEPROVIDER 110
-+#define SW_SERVICE_VBAPROJECTNAMEPROVIDER 111
-
--#define SW_SERVICE_LAST SW_SERVICE_VBACODENAMEPROVIDER
-+#define SW_SERVICE_LAST SW_SERVICE_VBAPROJECTNAMEPROVIDER
-
- #define SW_SERVICE_INVALID USHRT_MAX
-
-diff --git sw/source/core/unocore/unocoll.cxx sw/source/core/unocore/unocoll.cxx
-index 54797da..e3cded8 100644
---- sw/source/core/unocore/unocoll.cxx
-+++ sw/source/core/unocore/unocoll.cxx
-@@ -163,6 +163,71 @@ public:
- }
- };
-
-+typedef std::hash_map< rtl::OUString, rtl::OUString, rtl::OUStringHash > StringHashMap;
-+class SwVbaProjectNameProvider : public ::cppu::WeakImplHelper1< container::XNameContainer >
-+{
-+ SwDocShell* mpDocShell;
-+ StringHashMap mTemplateToProject;
-+public:
-+ SwVbaProjectNameProvider( SwDocShell* pDocShell ) : mpDocShell( pDocShell )
-+ {
-+ }
-+ virtual ::sal_Bool SAL_CALL hasByName( const ::rtl::OUString& aName ) throw (::com::sun::star::uno::RuntimeException )
-+ {
-+ return ( mTemplateToProject.find( aName ) != mTemplateToProject.end() );
-+ }
-+ virtual ::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();
-+ return uno::makeAny( mTemplateToProject.find( aName )->second );
-+ }
-+ virtual ::com::sun::star::uno::Sequence< ::rtl::OUString > SAL_CALL getElementNames( ) throw (::com::sun::star::uno::RuntimeException)
-+ {
-+ uno::Sequence< rtl::OUString > aElements( mTemplateToProject.size() );
-+ StringHashMap::iterator it_end = mTemplateToProject.end();
-+ sal_Int32 index = 0;
-+ for ( StringHashMap::iterator it = mTemplateToProject.begin(); it != it_end; ++it, ++index )
-+ aElements[ index ] = it->first;
-+ return aElements;
-+ }
-+
-+ virtual void SAL_CALL insertByName( const rtl::OUString& aName, const uno::Any& aElement ) throw ( com::sun::star::lang::IllegalArgumentException, com::sun::star::container::ElementExistException, com::sun::star::lang::WrappedTargetException )
-+ {
-+
-+ rtl::OUString sProjectName;
-+ aElement >>= sProjectName;
-+ OSL_TRACE("** Template cache inserting template name %s with project %s"
-+ , rtl::OUStringToOString( aName, RTL_TEXTENCODING_UTF8 ).getStr()
-+ , rtl::OUStringToOString( sProjectName, RTL_TEXTENCODING_UTF8 ).getStr() );
-+ mTemplateToProject[ aName ] = sProjectName;
-+ }
-+
-+ virtual void SAL_CALL removeByName( const rtl::OUString& Name ) throw ( com::sun::star::container::NoSuchElementException, com::sun::star::lang::WrappedTargetException )
-+ {
-+ if ( !hasByName( Name ) )
-+ throw container::NoSuchElementException();
-+ mTemplateToProject.erase( Name );
-+ }
-+ virtual void SAL_CALL replaceByName( const rtl::OUString& aName, const uno::Any& aElement ) throw ( com::sun::star::lang::IllegalArgumentException, com::sun::star::container::NoSuchElementException, com::sun::star::lang::WrappedTargetException )
-+ {
-+ if ( !hasByName( aName ) )
-+ throw container::NoSuchElementException();
-+ insertByName( aName, aElement ); // insert will overwrite
-+ }
-+ // XElemenAccess
-+ virtual ::com::sun::star::uno::Type SAL_CALL getElementType( ) throw (::com::sun::star::uno::RuntimeException)
-+ {
-+ return ::getCppuType((const rtl::OUString*)0);
-+ }
-+ virtual ::sal_Bool SAL_CALL hasElements( ) throw (::com::sun::star::uno::RuntimeException )
-+ {
-+
-+ return ( mTemplateToProject.size() > 0 );
-+ }
-+
-+};
-+
- class SwVbaObjectForCodeNameProvider : public ::cppu::WeakImplHelper1< container::XNameAccess >
- {
- SwDocShell* mpDocShell;
-@@ -325,6 +390,7 @@ const ProvNamesId_Type __FAR_DATA aProvNamesId[] =
- { "com.sun.star.chart2.data.DataProvider", SW_SERVICE_CHART2_DATA_PROVIDER },
- { "ooo.vba.VBAObjectModuleObjectProvider", SW_SERVICE_VBAOBJECTPROVIDER },
- { "ooo.vba.VBACodeNameProvider", SW_SERVICE_VBACODENAMEPROVIDER },
-+ { "ooo.vba.VBAProjectNameProvider", SW_SERVICE_VBAPROJECTNAMEPROVIDER },
-
- // case-correct versions of the service names (see #i67811)
- { CSS_TEXT_TEXTFIELD_DATE_TIME, SW_SERVICE_FIELDTYPE_DATETIME },
-@@ -517,6 +583,18 @@ uno::Reference< uno::XInterface > SwXServiceProvider::MakeInstance(sal_uInt16
- xRet = (cppu::OWeakObject*)pObjProv;
- }
- break;
-+ case SW_SERVICE_VBAPROJECTNAMEPROVIDER :
-+ {
-+ uno::Reference< container::XNameContainer > xProjProv = pDoc->GetVBATemplateToProjectCache();
-+ if ( !xProjProv.is() )
-+ {
-+ xProjProv = new SwVbaProjectNameProvider( pDoc->GetDocShell() );
-+ pDoc->SetVBATemplateToProjectCache( xProjProv );
-+ }
-+ //xRet = (cppu::OWeakObject*)xProjProv;
-+ xRet = xProjProv;
-+ }
-+ break;
- case SW_SERVICE_TYPE_FOOTNOTE :
- xRet = (cppu::OWeakObject*)new SwXFootnote(sal_False);
- break;
-diff --git sw/source/filter/ww8/ww8par.cxx sw/source/filter/ww8/ww8par.cxx
-index 90efd7b..e1366a2 100644
---- sw/source/filter/ww8/ww8par.cxx
-+++ sw/source/filter/ww8/ww8par.cxx
-@@ -161,7 +161,7 @@ using namespace nsHdFtFlags;
- #include <svtools/pathoptions.hxx>
- #include <com/sun/star/ucb/XSimpleFileAccess.hpp>
-
--const static String sModule( RTL_CONSTASCII_USTRINGPARAM("ThisDocument"));
-+const static String sThisDocument( RTL_CONSTASCII_USTRINGPARAM("ThisDocument"));
-
- struct DocEventNameTable
- {
-@@ -191,10 +191,10 @@ bool registerDocEvent( SfxObjectShell* pShell )
- 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 );
-+ String sMacroName = String::CreateFromAscii( pTable->sMacroName ).Insert( '.', 0 ).Insert( sThisDocument, 0);
- // fail to search the macro if the module is not specified.
-- String sFullPath = ooo::vba::findVBAMacro( pShell, sModule, sMacroName );
-- if( sFullPath.Len() == 0 )
-+ ooo::vba::VBAMacroResolvedInfo aMacroInfo = ooo::vba::resolveVBAMacro( pShell, sMacroName );
-+ if( !aMacroInfo.IsResolved() )
- continue;
-
- uno::Sequence< beans::PropertyValue > aEvents;
-@@ -203,7 +203,7 @@ bool registerDocEvent( SfxObjectShell* pShell )
- aOpenEvt[ 0 ].Name = sEvtType;
- aOpenEvt[ 0 ].Value = uno::makeAny(sScript);
- aOpenEvt[ 1 ].Name = sScript;
-- rtl::OUString sUrl = ooo::vba::makeMacroURL( sFullPath );
-+ rtl::OUString sUrl = ooo::vba::makeMacroURL( aMacroInfo.ResolvedMacro() );
- aOpenEvt[ 1 ].Value = uno::makeAny(sUrl);
- sal_Int32 nPos = aEvents.getLength();
-
-@@ -3834,6 +3834,39 @@ void SwWW8ImplReader::ReadDocInfo()
- }
- }
-
-+void lcl_createTemplateToProjectEntry( const uno::Reference< container::XNameContainer >& xPrjNameCache, const rtl::OUString& sTemplatePathOrURL, const rtl::OUString& sVBAProjName )
-+{
-+ if ( xPrjNameCache.is() )
-+ {
-+ INetURLObject aObj;
-+ aObj.SetURL( sTemplatePathOrURL );
-+ bool bIsURL = aObj.GetProtocol() != INET_PROT_NOT_VALID;
-+ rtl::OUString aURL;
-+ if ( bIsURL )
-+ aURL = sTemplatePathOrURL;
-+ else
-+ {
-+ osl::FileBase::getFileURLFromSystemPath( sTemplatePathOrURL, aURL );
-+ aObj.SetURL( aURL );
-+ }
-+ try
-+ {
-+ rtl::OUString templateNameWithExt = aObj.GetLastName();
-+ rtl::OUString templateName;
-+ sal_Int32 nIndex = templateNameWithExt.lastIndexOf( '.' );
-+ //xPrjNameCache->insertByName( templateNameWithExt, uno::makeAny( sVBAProjName ) );
-+ if ( nIndex != -1 )
-+ {
-+ templateName = templateNameWithExt.copy( 0, nIndex );
-+ xPrjNameCache->insertByName( templateName, uno::makeAny( sVBAProjName ) );
-+ }
-+ }
-+ catch( uno::Exception& )
-+ {
-+ }
-+ }
-+}
-+
- class WW8Customizations
- {
- SvStream* mpTableStream;
-@@ -3863,7 +3896,7 @@ bool WW8Customizations::Import( SwDocShell* pShell )
- return aTCG.ImportCustomToolBar( *pShell );
- }
-
--bool SwWW8ImplReader::ReadGlobalTemplateSettings()
-+bool SwWW8ImplReader::ReadGlobalTemplateSettings( const rtl::OUString& sCreatedFrom, const uno::Reference< container::XNameContainer >& xPrjNameCache )
- {
- SvtPathOptions aPathOpt;
- String aAddinPath = aPathOpt.GetAddinPath();
-@@ -3878,11 +3911,6 @@ bool SwWW8ImplReader::ReadGlobalTemplateSettings()
- sal_Int32 nEntries = sGlobalTemplates.getLength();
- bool bRes = true;
- const SvtFilterOptions* pVBAFlags = SvtFilterOptions::Get();
-- uno::Reference< document::XDocumentInfoSupplier > xDocInfoSupp( mpDocShell->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();
- for ( sal_Int32 i=0; i<nEntries; ++i )
- {
- INetURLObject aObj;
-@@ -3897,13 +3925,17 @@ bool SwWW8ImplReader::ReadGlobalTemplateSettings()
- continue; // don't try and read the same document as ourselves
-
- SotStorageRef rRoot = new SotStorage( aURL, STREAM_STD_READWRITE, STORAGE_TRANSACTED );
-+
- // Read Macro Projects
- SvxImportMSVBasic aVBasic(*mpDocShell, *rRoot,
- pVBAFlags->IsLoadWordBasicCode(),
- pVBAFlags->IsLoadWordBasicStorage() );
-+
-+
- String s1(CREATE_CONST_ASC("Macros"));
- String s2(CREATE_CONST_ASC("VBA"));
- int nRet = aVBasic.Import( s1, s2, ! pVBAFlags->IsLoadWordBasicCode() );
-+ lcl_createTemplateToProjectEntry( xPrjNameCache, aURL, aVBasic.GetVBAProjectName() );
- // Read toolbars & menus
- SvStorageStreamRef refMainStream = rRoot->OpenSotStream( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("WordDocument") ) );
- refMainStream->SetNumberFormatInt(NUMBERFORMAT_INT_LITTLEENDIAN);
-@@ -4183,10 +4215,20 @@ ULONG SwWW8ImplReader::CoreLoad(WW8Glossary *pGloss, const SwPosition &rPos)
- // dissable below for 3.1 at the moment, 'cause it's kinda immature
- // similarly the project reference in svx/source/msvba
- #if 1
-+ uno::Reference< document::XDocumentInfoSupplier > xDocInfoSupp( mpDocShell->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();
-+ uno::Reference< container::XNameContainer > xPrjNameCache;
-+ uno::Reference< lang::XMultiServiceFactory> xSF(mpDocShell->GetModel(), uno::UNO_QUERY);
-+ if ( xSF.is() )
-+ xPrjNameCache.set( xSF->createInstance( rtl::OUString(RTL_CONSTASCII_USTRINGPARAM( "ooo.vba.VBAProjectNameProvider" ) ) ), uno::UNO_QUERY );
-+
- // Read Global templates
-- ReadGlobalTemplateSettings();
-+ ReadGlobalTemplateSettings( sCreatedFrom, xPrjNameCache );
- #endif
-- // Create and insert Excel vba Globals
-+ // Create and insert Word vba Globals
- uno::Any aGlobs;
- aGlobs <<= ::comphelper::getProcessServiceFactory()->createInstance( ::rtl::OUString::createFromAscii( "ooo.vba.word.Globals") );
- mpDocShell->GetBasicManager()->SetGlobalUNOConstant( "VBAGlobals", aGlobs );
-@@ -4200,6 +4242,7 @@ ULONG SwWW8ImplReader::CoreLoad(WW8Glossary *pGloss, const SwPosition &rPos)
- // dissable below for 3.1 at the moment, 'cause it's kinda immature
- // similarly the project reference in svx/source/msvba
- #if 1
-+ lcl_createTemplateToProjectEntry( xPrjNameCache, sCreatedFrom, aVBasic.GetVBAProjectName() );
- WW8Customizations aCustomisations( pTableStream, *pWwFib );
- aCustomisations.Import( mpDocShell );
- #endif
-diff --git sw/source/filter/ww8/ww8par.hxx sw/source/filter/ww8/ww8par.hxx
-index 89ab0d6..9389568 100644
---- sw/source/filter/ww8/ww8par.hxx
-+++ sw/source/filter/ww8/ww8par.hxx
-@@ -1415,7 +1415,7 @@ private:
- // determine object attribute "Layout in Table Cell"
- bool IsObjectLayoutInTableCell( const UINT32 nLayoutInTableCell ) const;
- // <--
-- bool ReadGlobalTemplateSettings();
-+ bool ReadGlobalTemplateSettings( const rtl::OUString& sCreatedFrom, const com::sun::star::uno::Reference< com::sun::star::container::XNameContainer >& xPrjNameMap );
- //No copying
- SwWW8ImplReader(const SwWW8ImplReader &);
- SwWW8ImplReader& operator=(const SwWW8ImplReader&);
-diff --git sw/source/ui/uno/unotxdoc.cxx sw/source/ui/uno/unotxdoc.cxx
-index 0aacbda..9bc3d85 100644
---- sw/source/ui/uno/unotxdoc.cxx
-+++ sw/source/ui/uno/unotxdoc.cxx
-@@ -225,6 +225,12 @@ sal_Int64 SAL_CALL SwXTextDocument::getSomething( const Sequence< sal_Int8 >& rI
- {
- return sal::static_int_cast< sal_Int64 >( reinterpret_cast< sal_IntPtr >( this ));
- }
-+ if( rId.getLength() == 16
-+ && 0 == rtl_compareMemory( SfxObjectShell::getUnoTunnelId().getConstArray(),
-+ rId.getConstArray(), 16 ) )
-+ {
-+ return sal::static_int_cast<sal_Int64>(reinterpret_cast<sal_IntPtr>(pDocShell ));
-+ }
-
- sal_Int64 nRet = SfxBaseModel::getSomething( rId );
- if ( nRet )
-diff --git vbahelper/inc/vbahelper/vbahelper.hxx vbahelper/inc/vbahelper/vbahelper.hxx
-index 1849437..77eb2a3 100644
---- vbahelper/inc/vbahelper/vbahelper.hxx
-+++ vbahelper/inc/vbahelper/vbahelper.hxx
-@@ -63,6 +63,7 @@ namespace ooo
- throw css::lang::IllegalArgumentException();
- return aSomething;
- }
-+ 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);
- VBAHELPER_DLLPUBLIC css::uno::Reference< css::frame::XModel > getCurrentDocument() throw (css::uno::RuntimeException);
-diff --git vbahelper/source/vbahelper/vbaapplicationbase.cxx vbahelper/source/vbahelper/vbaapplicationbase.cxx
-index a424b35..0d9f52e 100644
---- vbahelper/source/vbahelper/vbaapplicationbase.cxx
-+++ vbahelper/source/vbahelper/vbaapplicationbase.cxx
-@@ -134,234 +134,39 @@ VbaApplicationBase::getVersion() throw (uno::RuntimeException)
-
- void SAL_CALL VbaApplicationBase::Run( const ::rtl::OUString& MacroName, const uno::Any& varg1, const uno::Any& varg2, const uno::Any& varg3, const uno::Any& varg4, const uno::Any& varg5, const uno::Any& varg6, const uno::Any& varg7, const uno::Any& varg8, const uno::Any& varg9, const uno::Any& varg10, const uno::Any& varg11, const uno::Any& varg12, const uno::Any& varg13, const uno::Any& varg14, const uno::Any& varg15, const uno::Any& varg16, const uno::Any& varg17, const uno::Any& varg18, const uno::Any& varg19, const uno::Any& varg20, const uno::Any& varg21, const uno::Any& varg22, const uno::Any& varg23, const uno::Any& varg24, const uno::Any& varg25, const uno::Any& varg26, const uno::Any& varg27, const uno::Any& varg28, const uno::Any& varg29, const uno::Any& varg30 ) throw (uno::RuntimeException)
- {
-- // parse the macro name
-- sal_Int32 nDocSepIndex = MacroName.indexOfAsciiL( "!", 1 );
-- String sMacroUrl = MacroName;
-- uno::Reference< frame::XModel > xModel;
-- if( nDocSepIndex > 0 )
-+ VBAMacroResolvedInfo aMacroInfo = resolveVBAMacro( GetDocShell( getCurrentDocument() ), MacroName );
-+ if( aMacroInfo.IsResolved() )
- {
-- rtl::OUString sTemplate = MacroName.copy( 0, nDocSepIndex );
-- OSL_TRACE("VbaApplicationBase::Run, template name: %s", rtl::OUStringToOString( sTemplate, RTL_TEXTENCODING_UTF8 ).getStr() );
-- sMacroUrl = MacroName.copy( nDocSepIndex + 1 );
-- OSL_TRACE("VbaApplicationBase::Run, macro name: %s", rtl::OUStringToOString( sMacroUrl, RTL_TEXTENCODING_UTF8 ).getStr() );
-+ // 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 };
-
-- // get the template model
-- uno::Reference< lang::XMultiComponentFactory > xSMgr( mxContext->getServiceManager(), uno::UNO_QUERY_THROW );
-+ int nArg = sizeof( aArgsPtrArray ) / sizeof( aArgsPtrArray[0] );
-+ uno::Sequence< uno::Any > aArgs( nArg );
-
-- uno::Reference< frame::XDesktop > xDesktop
-- (xSMgr->createInstanceWithContext(::rtl::OUString::createFromAscii("com.sun.star.frame.Desktop"), mxContext), uno::UNO_QUERY_THROW );
-- uno::Reference< container::XEnumeration > mxComponents = xDesktop->getComponents()->createEnumeration();
-- sal_Int32 nCount = 0;
-- while( mxComponents->hasMoreElements() )
-- {
-- uno::Reference< document::XDocumentInfoSupplier > xDocInfoSupp( mxComponents->nextElement(), 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();
-- OSL_TRACE("VbaApplicationBase::Run, current template %d name: %s", ++nCount, rtl::OUStringToOString( sCurrName, RTL_TEXTENCODING_UTF8 ).getStr() );
-- // FIXME: should be check the full path of the template
-- if( sTemplate.lastIndexOf( sCurrName ) >= 0 )
-- {
-- xModel.set( xDocInfoSupp, uno::UNO_QUERY_THROW );
-- break;
-- }
-- }
-+ const uno::Any** pArg = aArgsPtrArray;
-+ const uno::Any** pArgEnd = ( aArgsPtrArray + nArg );
-+
-+ sal_Int32 nLastArgWithValue = 0;
-+ sal_Int32 nArgProcessed = 0;
-+
-+ for ( ; pArg != pArgEnd; ++pArg, ++nArgProcessed )
-+ {
-+ aArgs[ nArgProcessed ] = **pArg;
-+ if( (*pArg)->hasValue() )
-+ nLastArgWithValue = nArgProcessed;
- }
-- }
-- else
-- {
-- xModel = getCurrentDocument();
-- }
-
-- if( !xModel.is() )
-- {
-- throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("Fail to find the template in Application.Run") ), uno::Reference< uno::XInterface >() );
-- }
-+ // resize array to position of last param with value
-+ aArgs.realloc( nArgProcessed + 1 );
-
-- String sMacro;
-- String sModule;
-- sal_Int32 nTokens = sMacroUrl.GetTokenCount( '.' );
-- xub_StrLen nToken = 0;
-- xub_StrLen nIndex = 0;
-- // only support ThisModule.ThisMacro
-- if( nTokens == 2 )
-- {
-- sModule = sMacroUrl.GetToken( nToken, '.', nIndex );
-- sMacro = sMacroUrl.GetToken( nToken, '.', nIndex );
-+ uno::Any aRet;
-+ uno::Any aDummyCaller;
-+ executeMacro( aMacroInfo.MacroDocContext(), aMacroInfo.ResolvedMacro(), aArgs, aRet, aDummyCaller );
- }
- else
- {
- throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("The macro doesn't exist") ), uno::Reference< uno::XInterface >() );
- }
--
-- SfxObjectShell* pShell = GetDocShell( xModel );
-- if( pShell )
-- {
-- sMacroUrl = findVBAMacro( pShell, sModule, sMacro );
-- if( sMacroUrl.Len() )
-- {
-- // handle the arguments
-- uno::Sequence< uno::Any > aArgs;
-- if( varg1.hasValue() )
-- {
-- aArgs.realloc( aArgs.getLength() + 1 );
-- aArgs[ aArgs.getLength() ] = varg1;
-- }
-- if( varg2.hasValue() )
-- {
-- aArgs.realloc( aArgs.getLength() + 1 );
-- aArgs[ aArgs.getLength() ] = varg2;
-- }
-- if( varg3.hasValue() )
-- {
-- aArgs.realloc( aArgs.getLength() + 1 );
-- aArgs[ aArgs.getLength() ] = varg3;
-- }
-- if( varg4.hasValue() )
-- {
-- aArgs.realloc( aArgs.getLength() + 1 );
-- aArgs[ aArgs.getLength() ] = varg4;
-- }
-- if( varg5.hasValue() )
-- {
-- aArgs.realloc( aArgs.getLength() + 1 );
-- aArgs[ aArgs.getLength() ] = varg5;
-- }
-- if( varg6.hasValue() )
-- {
-- aArgs.realloc( aArgs.getLength() + 1 );
-- aArgs[ aArgs.getLength() ] = varg6;
-- }
-- if( varg7.hasValue() )
-- {
-- aArgs.realloc( aArgs.getLength() + 1 );
-- aArgs[ aArgs.getLength() ] = varg7;
-- }
-- if( varg8.hasValue() )
-- {
-- aArgs.realloc( aArgs.getLength() + 1 );
-- aArgs[ aArgs.getLength() ] = varg8;
-- }
-- if( varg9.hasValue() )
-- {
-- aArgs.realloc( aArgs.getLength() + 1 );
-- aArgs[ aArgs.getLength() ] = varg9;
-- }
-- if( varg10.hasValue() )
-- {
-- aArgs.realloc( aArgs.getLength() + 1 );
-- aArgs[ aArgs.getLength() ] = varg10;
-- }
-- if( varg11.hasValue() )
-- {
-- aArgs.realloc( aArgs.getLength() + 1 );
-- aArgs[ aArgs.getLength() ] = varg11;
-- }
-- if( varg12.hasValue() )
-- {
-- aArgs.realloc( aArgs.getLength() + 1 );
-- aArgs[ aArgs.getLength() ] = varg12;
-- }
-- if( varg13.hasValue() )
-- {
-- aArgs.realloc( aArgs.getLength() + 1 );
-- aArgs[ aArgs.getLength() ] = varg13;
-- }
-- if( varg14.hasValue() )
-- {
-- aArgs.realloc( aArgs.getLength() + 1 );
-- aArgs[ aArgs.getLength() ] = varg14;
-- }
-- if( varg15.hasValue() )
-- {
-- aArgs.realloc( aArgs.getLength() + 1 );
-- aArgs[ aArgs.getLength() ] = varg15;
-- }
-- if( varg16.hasValue() )
-- {
-- aArgs.realloc( aArgs.getLength() + 1 );
-- aArgs[ aArgs.getLength() ] = varg16;
-- }
-- if( varg17.hasValue() )
-- {
-- aArgs.realloc( aArgs.getLength() + 1 );
-- aArgs[ aArgs.getLength() ] = varg17;
-- }
-- if( varg18.hasValue() )
-- {
-- aArgs.realloc( aArgs.getLength() + 1 );
-- aArgs[ aArgs.getLength() ] = varg18;
-- }
-- if( varg19.hasValue() )
-- {
-- aArgs.realloc( aArgs.getLength() + 1 );
-- aArgs[ aArgs.getLength() ] = varg19;
-- }
-- if( varg20.hasValue() )
-- {
-- aArgs.realloc( aArgs.getLength() + 1 );
-- aArgs[ aArgs.getLength() ] = varg20;
-- }
-- if( varg21.hasValue() )
-- {
-- aArgs.realloc( aArgs.getLength() + 1 );
-- aArgs[ aArgs.getLength() ] = varg21;
-- }
-- if( varg22.hasValue() )
-- {
-- aArgs.realloc( aArgs.getLength() + 1 );
-- aArgs[ aArgs.getLength() ] = varg22;
-- }
-- if( varg23.hasValue() )
-- {
-- aArgs.realloc( aArgs.getLength() + 1 );
-- aArgs[ aArgs.getLength() ] = varg23;
-- }
-- if( varg24.hasValue() )
-- {
-- aArgs.realloc( aArgs.getLength() + 1 );
-- aArgs[ aArgs.getLength() ] = varg24;
-- }
-- if( varg25.hasValue() )
-- {
-- aArgs.realloc( aArgs.getLength() + 1 );
-- aArgs[ aArgs.getLength() ] = varg25;
-- }
-- if( varg26.hasValue() )
-- {
-- aArgs.realloc( aArgs.getLength() + 1 );
-- aArgs[ aArgs.getLength() ] = varg26;
-- }
-- if( varg27.hasValue() )
-- {
-- aArgs.realloc( aArgs.getLength() + 1 );
-- aArgs[ aArgs.getLength() ] = varg27;
-- }
-- if( varg28.hasValue() )
-- {
-- aArgs.realloc( aArgs.getLength() + 1 );
-- aArgs[ aArgs.getLength() ] = varg28;
-- }
-- if( varg29.hasValue() )
-- {
-- aArgs.realloc( aArgs.getLength() + 1 );
-- aArgs[ aArgs.getLength() ] = varg29;
-- }
-- if( varg30.hasValue() )
-- {
-- aArgs.realloc( aArgs.getLength() + 1 );
-- aArgs[ aArgs.getLength() ] = varg30;
-- }
-- uno::Any aRet;
-- executeMacro( pShell, sMacroUrl, aArgs, aRet );
-- }
-- else
-- {
-- throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("The macro doesn't exist") ), uno::Reference< uno::XInterface >() );
-- }
-- }
- }
-
- float SAL_CALL VbaApplicationBase::CentimetersToPoints( float _Centimeters ) throw (uno::RuntimeException)
-diff --git vbahelper/source/vbahelper/vbacommandbarcontrol.cxx vbahelper/source/vbahelper/vbacommandbarcontrol.cxx
-index 718cdd0..2fcce8a 100644
---- vbahelper/source/vbahelper/vbacommandbarcontrol.cxx
-+++ vbahelper/source/vbahelper/vbacommandbarcontrol.cxx
-@@ -36,6 +36,8 @@
- #include <basic/sbstar.hxx>
- #include <basic/sbmod.hxx>
- #include <basic/sbmeth.hxx>
-+#include <vbahelper/vbahelper.hxx>
-+#include <svx/msvbahelper.hxx>
-
- using namespace com::sun::star;
- using namespace ooo::vba;
-@@ -286,79 +288,31 @@ ScVbaCommandBarControl::setOnAction( const ::rtl::OUString& _onaction ) throw (u
- {
- 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();
-- StarBASIC* pLib = pModule ? dynamic_cast< StarBASIC* >( pModule->GetParent() ) : NULL;
--
-- // Ok, we should be able to deal with the following params for onAction
-- // a) macro ( we assume the macro lives in this Project ( that is not really a valid assumption but we can't currently search outside this Library yet )
-- // b) module.macro ( again assume the macro is in this Project )
-- // c) project.module.macro fully specified
--
-- if( pModule && pLib )
-+ // get the current model
-+ uno::Reference< frame::XModel > xModel( getCurrentDocument() );
-+ VBAMacroResolvedInfo aResolvedMacro = ooo::vba::resolveVBAMacro( getSfxObjShell( xModel ), _onaction, true );
-+ if ( aResolvedMacro.IsResolved() )
- {
-- String sProject;
-- String sModule;
-- String sMacro = _onaction;
--
-- sal_Int32 nMacroDot = _onaction.lastIndexOf( '.' );
--
-- if ( nMacroDot != -1 )
-+ rtl::OUString aCommandURL = ooo::vba::makeMacroURL( aResolvedMacro.ResolvedMacro() );
-+ 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 ) )
- {
-- sMacro = _onaction.copy( nMacroDot + 1 );
--
-- sal_Int32 nProjectDot = _onaction.lastIndexOf( '.', nMacroDot - 1 );
-- if ( nProjectDot != -1 )
-- {
-- sModule = _onaction.copy( nProjectDot + 1, nMacroDot - nProjectDot - 1 );
-- pModule = NULL; // force full spec. no search
--
-- }
-- else
-- sModule = _onaction.copy( 0, nMacroDot );
-- pModule = pLib->FindModule( sModule );
-+ m_xUICfgManager->replaceSettings( m_sBarName, uno::Reference< container::XIndexAccess > (m_xBarSettings, uno::UNO_QUERY_THROW ) );
- }
--
-- // Hopefully eventually if no project is specified 'Find' below
-- // will do the right thing
-- if( SbMethod* pMethod = dynamic_cast< SbMethod* >( pModule ? pModule->Find( sMacro, SbxCLASS_METHOD ) : NULL ) )
-+ else
- {
-- if( pMethod )
-- {
-- sModule = pModule->GetName();
-- sProject = pModule->GetParent()->GetName();
-- }
-+ m_xUICfgManager->insertSettings( m_sBarName, uno::Reference< container::XIndexAccess > (m_xBarSettings, uno::UNO_QUERY_THROW ) );
-+ }
-+ // make it permanent
-+ if( !m_bTemporary )
-+ {
-+ m_xUICfgPers->store();
- }
-- sMacro.Insert( '.', 0 ).Insert( sModule, 0 ).Insert( '.', 0 ).Insert( sProject, 0 );
--
-- rtl::OUString sUrlPart2 = rtl::OUString::createFromAscii( "?language=Basic&location=document");
-- aCommandURL = sScheme.concat( sMacro ).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();
- }
- }
- }
-diff --git vbahelper/source/vbahelper/vbahelper.cxx vbahelper/source/vbahelper/vbahelper.cxx
-index 57bca7c..97ebb3b 100644
---- vbahelper/source/vbahelper/vbahelper.cxx
-+++ vbahelper/source/vbahelper/vbahelper.cxx
-@@ -67,6 +67,7 @@
- #include <toolkit/awt/vclxwindow.hxx>
- #include <toolkit/helper/vclunohelper.hxx>
- #include <com/sun/star/frame/XModel2.hpp>
-+#include <com/sun/star/lang/XUnoTunnel.hpp>
- #include <vcl/window.hxx>
- #include <vcl/syswin.hxx>
- #include <tools/diagnose_ex.h>
-@@ -1116,7 +1117,19 @@ UserFormGeometryHelper::UserFormGeometryHelper( const uno::Reference< uno::XComp
- double points = double( static_cast<double>(_hmm) / factor);
- return points;
- }
--
-+
-+ SfxObjectShell* getSfxObjShell( const uno::Reference< frame::XModel >& xModel ) throw (uno::RuntimeException)
-+ {
-+ SfxObjectShell* pFoundShell = NULL;
-+ if ( xModel.is() )
-+ {
-+ uno::Reference< lang::XUnoTunnel > xObjShellTunnel( xModel, uno::UNO_QUERY_THROW );
-+ pFoundShell = reinterpret_cast<SfxObjectShell*>( xObjShellTunnel->getSomething(SfxObjectShell::getUnoTunnelId()));
-+ }
-+ if ( !pFoundShell )
-+ throw uno::RuntimeException();
-+ return pFoundShell;
-+ }
-
- } // openoffice
- } //org