summaryrefslogtreecommitdiff
path: root/patches/vba/vba-commandbar-fix.diff
diff options
context:
space:
mode:
Diffstat (limited to 'patches/vba/vba-commandbar-fix.diff')
-rw-r--r--patches/vba/vba-commandbar-fix.diff654
1 files changed, 0 insertions, 654 deletions
diff --git a/patches/vba/vba-commandbar-fix.diff b/patches/vba/vba-commandbar-fix.diff
deleted file mode 100644
index 3b4ade591..000000000
--- a/patches/vba/vba-commandbar-fix.diff
+++ /dev/null
@@ -1,654 +0,0 @@
---- oovbaapi/ooo/vba/XCommandBar.idl.old 2009-04-02 10:36:29.000000000 +0000
-+++ oovbaapi/ooo/vba/XCommandBar.idl 2009-04-06 16:42:00.000000000 +0000
-@@ -57,6 +57,8 @@ interface XCommandBar
-
- void Delete() raises ( com::sun::star::script::BasicErrorException );
- any Controls( [in] any Index ) raises ( com::sun::star::script::BasicErrorException );
-+ long Type() raises ( com::sun::star::script::BasicErrorException );
-+ any FindControl( [in] any Type, [in] any Id, [in] any Tag, [in] any Visible, [in] any Recursive ) raises ( com::sun::star::script::BasicErrorException );
- };
-
- }; };
---- oovbaapi/ooo/vba/XCommandBarButton.idl.old 1970-01-01 00:00:00.000000000 +0000
-+++ oovbaapi/ooo/vba/XCommandBarButton.idl 2009-04-06 16:42:00.000000000 +0000
-@@ -0,0 +1,52 @@
-+/*************************************************************************
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile$
-+ *
-+ * $Revision$
-+ *
-+ * last change: $Author$ $Date$
-+ *
-+ * The Contents of this file are made available subject to
-+ * the terms of GNU Lesser General Public License Version 2.1.
-+ *
-+ *
-+ * GNU Lesser General Public License Version 2.1
-+ * =============================================
-+ * Copyright 2005 by Sun Microsystems, Inc.
-+ * 901 San Antonio Road, Palo Alto, CA 94303, USA
-+ *
-+ * This library is free software; you can redistribute it and/or
-+ * modify it under the terms of the GNU Lesser General Public
-+ * License version 2.1, as published by the Free Software Foundation.
-+ *
-+ * This library is distributed in the hope that it will be useful,
-+ * but WITHOUT ANY WARRANTY; without even the implied warranty of
-+ * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
-+ * Lesser General Public License for more details.
-+ *
-+ * You should have received a copy of the GNU Lesser General Public
-+ * License along with this library; if not, write to the Free Software
-+ * Foundation, Inc., 59 Temple Place, Suite 330, Boston,
-+ * MA 02111-1307 USA
-+ *
-+ ************************************************************************/
-+#ifndef __ooo_vba_XCommandBarButton_idl__
-+#define __ooo_vba_XCommandBarButton_idl__
-+
-+#ifndef __com_sun_star_uno_XInterface_idl__
-+#include <com/sun/star/uno/XInterface.idl>
-+#endif
-+//=============================================================================
-+
-+module ooo { module vba {
-+//=============================================================================
-+
-+interface XCommandBarButton: com::sun::star::uno::XInterface
-+{
-+};
-+
-+}; };
-+
-+#endif
---- oovbaapi/ooo/vba/XCommandBarPopup.idl.old 1970-01-01 00:00:00.000000000 +0000
-+++ oovbaapi/ooo/vba/XCommandBarPopup.idl 2009-04-06 16:42:00.000000000 +0000
-@@ -0,0 +1,52 @@
-+/*************************************************************************
-+ *
-+ * OpenOffice.org - a multi-platform office productivity suite
-+ *
-+ * $RCSfile$
-+ *
-+ * $Revision$
-+ *
-+ * last change: $Author$ $Date$
-+ *
-+ * The Contents of this file are made available subject to
-+ * the terms of GNU Lesser General Public License Version 2.1.
-+ *
-+ *
-+ * GNU Lesser General Public License Version 2.1
-+ * =============================================
-+ * Copyright 2005 by Sun Microsystems, Inc.
-+ * 901 San Antonio Road, Palo Alto, CA 94303, USA
-+ *
-+ * This library is free software; you can redistribute it and/or
-+ * modify it under the terms of the GNU Lesser General Public
-+ * License version 2.1, as published by the Free Software Foundation.
-+ *
-+ * This library is distributed in the hope that it will be useful,
-+ * but WITHOUT ANY WARRANTY; without even the implied warranty of
-+ * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
-+ * Lesser General Public License for more details.
-+ *
-+ * You should have received a copy of the GNU Lesser General Public
-+ * License along with this library; if not, write to the Free Software
-+ * Foundation, Inc., 59 Temple Place, Suite 330, Boston,
-+ * MA 02111-1307 USA
-+ *
-+ ************************************************************************/
-+#ifndef __ooo_vba_XCommandBarPopup_idl__
-+#define __ooo_vba_XCommandBarPopup_idl__
-+
-+#ifndef __com_sun_star_uno_XInterface_idl__
-+#include <com/sun/star/uno/XInterface.idl>
-+#endif
-+//=============================================================================
-+
-+module ooo { module vba {
-+//=============================================================================
-+
-+interface XCommandBarPopup: com::sun::star::uno::XInterface
-+{
-+};
-+
-+}; };
-+
-+#endif
---- oovbaapi/ooo/vba/makefile.mk.old 2009-04-06 16:41:59.000000000 +0000
-+++ oovbaapi/ooo/vba/makefile.mk 2009-04-06 16:42:00.000000000 +0000
-@@ -52,6 +52,8 @@ IDLFILES=\
- XCommandBarControls.idl\
- XCommandBar.idl\
- XCommandBars.idl\
-+ XCommandBarPopup.idl\
-+ XCommandBarButton.idl\
- Globals.idl\
-
- # ------------------------------------------------------------------
---- sc/source/ui/vba/vbacommandbar.cxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbacommandbar.cxx 2009-04-06 16:42:00.000000000 +0000
-@@ -37,6 +37,7 @@
- #include <com/sun/star/frame/XDesktop.hpp>
- #include <com/sun/star/frame/XLayoutManager.hpp>
- #include <com/sun/star/beans/XPropertySet.hpp>
-+#include <ooo/vba/office/MsoBarType.hpp>
-
- #include "vbacommandbar.hxx"
- #include "vbacommandbarcontrols.hxx"
-@@ -99,7 +100,7 @@ ScVbaCommandBar::initCommandBar() throw
- m_bTemporary = sal_True;
- m_sToolBarName = rtl::OUString::createFromAscii("");
- m_sUIName = rtl::OUString::createFromAscii("");
-- m_sMenuModuleName = rtl::OUString::createFromAscii( "com.sun.star.sheet.SpreadsheetDocument" );
-+ m_sMenuModuleName = m_pScVbaCommandBars->GetModuleName();
- }
- void
- ScVbaCommandBar::getToolBarSettings( rtl::OUString sToolBarName ) throw( uno::RuntimeException )
-@@ -310,6 +311,23 @@ ScVbaCommandBar::Controls( const uno::An
- }
- return uno::makeAny( xCommandBarControls );
- }
-+
-+sal_Int32 SAL_CALL
-+ScVbaCommandBar::Type() throw (script::BasicErrorException, uno::RuntimeException)
-+{
-+ // #FIXME support msoBarTypePopup
-+ sal_Int32 nType = office::MsoBarType::msoBarTypePopup;
-+ nType = m_bIsMenu? office::MsoBarType::msoBarTypeNormal : office::MsoBarType::msoBarTypeMenuBar;
-+ return nType;
-+}
-+
-+uno::Any SAL_CALL
-+ScVbaCommandBar::FindControl( const uno::Any& /*aType*/, const uno::Any& /*aId*/, const uno::Any& /*aTag*/, const uno::Any& /*aVisible*/, const uno::Any& /*aRecursive*/ ) throw (script::BasicErrorException, uno::RuntimeException)
-+{
-+ // alwayse fail to find control
-+ return uno::makeAny( uno::Reference< XCommandBarControl > () );
-+}
-+
- rtl::OUString&
- ScVbaCommandBar::getServiceImplName()
- {
---- sc/source/ui/vba/vbacommandbar.hxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbacommandbar.hxx 2009-04-06 16:42:00.000000000 +0000
-@@ -97,6 +97,8 @@ public:
- // Methods
- virtual void SAL_CALL Delete( ) throw (css::script::BasicErrorException, css::uno::RuntimeException);
- virtual css::uno::Any SAL_CALL Controls( const css::uno::Any& aIndex ) throw (css::script::BasicErrorException, css::uno::RuntimeException);
-+ virtual sal_Int32 SAL_CALL Type( ) throw (css::script::BasicErrorException, css::uno::RuntimeException);
-+ virtual css::uno::Any SAL_CALL FindControl( const css::uno::Any& aType, const css::uno::Any& aId, const css::uno::Any& aTag, const css::uno::Any& aVisible, const css::uno::Any& aRecursive ) throw (css::script::BasicErrorException, css::uno::RuntimeException);
-
- // XHelperInterface
- virtual rtl::OUString& getServiceImplName();
---- sc/source/ui/vba/vbacommandbarcontrol.cxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbacommandbarcontrol.cxx 2009-04-06 16:42:00.000000000 +0000
-@@ -33,6 +33,8 @@
- *
- ************************************************************************/
- #include "vbacommandbarcontrol.hxx"
-+#include <basic/sbstar.hxx>
-+#include <basic/sbmod.hxx>
-
- using namespace com::sun::star;
- using namespace ooo::vba;
-@@ -64,7 +66,7 @@ beans::PropertyValues lcl_repalcePropert
- return aPropertyValues;
- }
-
--ScVbaCommandBarControl::ScVbaCommandBarControl( const uno::Reference< XHelperInterface > xParent, const uno::Reference< uno::XComponentContext > xContext, rtl::OUString sName ) throw (uno::RuntimeException) : CommandBarControl_BASE( xParent, xContext ), m_sName( sName )
-+ScVbaCommandBarControl::ScVbaCommandBarControl( const uno::Reference< XHelperInterface > xParent, const uno::Reference< uno::XComponentContext > xContext, rtl::OUString sName, sal_Int32 nPosition, sal_Int32 nType ) throw (uno::RuntimeException) : CommandBarControl_BASE( xParent, xContext ), m_sName( sName ), m_nPosition( nPosition ), m_nType( nType )
- {
- // exsiting CommandBarBarControl
- m_xParentHardRef.set( xParent, uno::UNO_QUERY_THROW );
-@@ -83,34 +85,6 @@ ScVbaCommandBarControl::ScVbaCommandBarC
- {
- m_xCurrentSettings.set( m_xUICfgManager->getSettings( m_pCommandBarControls->GetParentToolBarName(), sal_True ), uno::UNO_QUERY_THROW );
- }
-- for( sal_Int32 i = 0; i < m_xCurrentSettings->getCount(); i++ )
-- {
-- beans::PropertyValues aPropertyValuesTemp;
-- m_xCurrentSettings->getByIndex( i ) >>= aPropertyValuesTemp;
-- // Label always empty in OOo
-- rtl::OUString sLabel;
-- lcl_getPropertyValue( aPropertyValuesTemp, rtl::OUString::createFromAscii( "Label" ) ) >>= sLabel;
-- if( sLabel.equalsIgnoreAsciiCase( sName ) )
-- {
-- m_nPosition = i;
-- break;
-- }
-- // using CammandURL to find
-- rtl::OUString sCommandURL;
-- lcl_getPropertyValue( aPropertyValuesTemp, rtl::OUString::createFromAscii( "CommandURL" ) ) >>= sCommandURL;
-- sal_Int32 nLastIndex = sCommandURL.lastIndexOf( rtl::OUString::createFromAscii(":") );
-- if( ( nLastIndex != -1 ) && ( ( nLastIndex + 1 ) < sCommandURL.getLength() ) )
-- {
-- sCommandURL = sCommandURL.copy( nLastIndex + 1 );
-- }
-- if( sCommandURL.equalsIgnoreAsciiCase( sName ) )
-- {
-- m_nPosition = i;
-- break;
-- }
-- }
-- if( m_nPosition == -1 )
-- throw uno::RuntimeException( rtl::OUString::createFromAscii("The CommandBarControl do not exist"), uno::Reference< uno::XInterface >() );
- }
- if( m_bIsMenu )
- {
-@@ -122,7 +96,7 @@ ScVbaCommandBarControl::ScVbaCommandBarC
- }
- m_bTemporary = sal_True;
- }
--ScVbaCommandBarControl::ScVbaCommandBarControl( const uno::Reference< XHelperInterface > xParent, const uno::Reference< uno::XComponentContext > xContext, rtl::OUString sName, rtl::OUString sCommand, sal_Int32 nPosition, sal_Bool bTemporary ) throw (uno::RuntimeException) : CommandBarControl_BASE( xParent, xContext ), m_nPosition( nPosition ), m_bTemporary( bTemporary )
-+ScVbaCommandBarControl::ScVbaCommandBarControl( const uno::Reference< XHelperInterface > xParent, const uno::Reference< uno::XComponentContext > xContext, rtl::OUString sName, sal_Int32 nPosition, sal_Bool bTemporary, sal_Int32 nType) throw (uno::RuntimeException) : CommandBarControl_BASE( xParent, xContext ), m_nPosition( nPosition ), m_bTemporary( bTemporary ), m_nType( nType )
- {
- m_xParentHardRef.set( xParent, uno::UNO_QUERY_THROW );
- initObjects();
-@@ -130,14 +104,7 @@ ScVbaCommandBarControl::ScVbaCommandBarC
- {
- m_sName = sName;
- }
-- if( sCommand.getLength() > 0 )
-- {
-- m_sCommand = sCommand;
-- }
-- else
-- {
-- m_sCommand = rtl::OUString::createFromAscii("vnd.openoffice.org:") + sName;
-- }
-+ m_sCommand = rtl::OUString::createFromAscii("vnd.openoffice.org:") + sName;
- if( m_bIsMenu )
- {
- m_sBarName = rtl::OUString::createFromAscii("private:resource/menubar/menubar");
-@@ -161,27 +128,32 @@ ScVbaCommandBarControl::initObjects() th
- m_xBarSettings.set( m_pCommandBarControls->GetBarSettings(), uno::UNO_QUERY_THROW );
- m_bIsMenu = m_pCommandBarControls->IsMenu();
- m_sName = rtl::OUString::createFromAscii( "Custom" );
-- m_nPosition = -1;
- }
-
- void
- ScVbaCommandBarControl::createNewMenuBarControl()
- {
-- uno::Sequence< beans::PropertyValue > aPropertys(4);
-+ uno::Reference< lang::XSingleComponentFactory > xMenuMSF( m_xBarSettings, uno::UNO_QUERY_THROW );
-+
-+ uno::Sequence< beans::PropertyValue > aPropertys;
-+ if( m_nType == office::MsoControlType::msoControlPopup )
-+ aPropertys = uno::Sequence< beans::PropertyValue >( 4 );
-+ else
-+ aPropertys = uno::Sequence< beans::PropertyValue >( 3 );
-+
- aPropertys[0].Name = rtl::OUString::createFromAscii("CommandURL");
- aPropertys[0].Value <<= m_sCommand;
- aPropertys[1].Name = rtl::OUString::createFromAscii("Label");
- aPropertys[1].Value <<= m_sName;
- aPropertys[2].Name = rtl::OUString::createFromAscii("Type");
-- aPropertys[2].Value <<= m_nType;
-- aPropertys[3].Name = rtl::OUString::createFromAscii("ItemDescriptorContainer");
-+ aPropertys[2].Value <<= sal_Int32(0);
-
-- m_xBarSettings->insertByIndex( m_nPosition, uno::makeAny( aPropertys ) );
-- uno::Reference< beans::XPropertySet > xPropertySet( m_xBarSettings, uno::UNO_QUERY_THROW );
-- rtl::OUString sUIName;
-- xPropertySet->getPropertyValue( rtl::OUString::createFromAscii("UIName") ) >>= sUIName;
-+ if( m_nType == office::MsoControlType::msoControlPopup )
-+ {
-+ aPropertys[3].Name = rtl::OUString::createFromAscii("ItemDescriptorContainer");
-+ aPropertys[3].Value <<= xMenuMSF->createInstanceWithContext( mxContext );
-+ }
-
-- uno::Reference< lang::XSingleComponentFactory > xMenuMSF( m_xBarSettings, uno::UNO_QUERY_THROW );
- if( m_pCommandBarControls->GetParentCommandBar() != NULL )
- {
- // create a new menu
-@@ -191,7 +163,6 @@ ScVbaCommandBarControl::createNewMenuBar
- else if( m_pCommandBarControls->GetParentCommandBarControl() != NULL )
- {
- // create a new menu entry
-- // change the parent MenuItem to a PopupMenu
- ScVbaCommandBarControl* pPc = m_pCommandBarControls->GetParentCommandBarControl();
- beans::PropertyValues aPropertyValues;
- pPc->GetCurrentSettings()->getByIndex( pPc->GetPosition() ) >>= aPropertyValues;
-@@ -204,7 +175,7 @@ ScVbaCommandBarControl::createNewMenuBar
- pPc->GetCurrentSettings()->replaceByIndex( pPc->GetPosition(), uno::makeAny( pPc->GetPropertyValues() ) );
- }
- m_xCurrentSettings.set( lcl_getPropertyValue( pPc->GetPropertyValues(), rtl::OUString::createFromAscii("ItemDescriptorContainer") ), uno::UNO_QUERY_THROW );
-- m_xCurrentSettings->insertByIndex( m_nPosition, uno::makeAny( m_aPropertyValues ) );
-+ m_xCurrentSettings->insertByIndex( m_nPosition, uno::makeAny( aPropertys ) );
- }
- if( m_xUICfgManager->hasSettings( m_sBarName ) )
- {
-@@ -229,7 +200,7 @@ ScVbaCommandBarControl::createNewToolBar
- aPropertys[1].Name = rtl::OUString::createFromAscii("Label");
- aPropertys[1].Value <<= m_sName;
- aPropertys[2].Name = rtl::OUString::createFromAscii("Type");
-- aPropertys[2].Value <<= m_nType;
-+ aPropertys[2].Value <<= sal_Int32(0);
- aPropertys[3].Name = rtl::OUString::createFromAscii("IsVisible");
- aPropertys[3].Value <<= sal_True;
-
-@@ -314,10 +285,25 @@ ScVbaCommandBarControl::setOnAction( con
- {
- if( m_xCurrentSettings.is() )
- {
-+ // convert the comand url into something like vnd.sun.star.script:Standard.testMacro.Macro1?language=Basic&location=document
-+ rtl::OUString aCommandURL;
-+ rtl::OUString sUrlPart = rtl::OUString::createFromAscii( "vnd.sun.star.script:Standard.");
-+ SbModule* pModule = StarBASIC::GetActiveModule();
-+ if( pModule && ( _onaction.indexOf( sUrlPart ) == -1 ) )
-+ {
-+ rtl::OUString sUrlPart1 = rtl::OUString::createFromAscii( "?language=Basic&location=document");
-+ aCommandURL = sUrlPart.concat( pModule->GetName() ).concat( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM(".") ) ).concat( _onaction ).concat( sUrlPart1 );
-+ }
-+ else
-+ {
-+ aCommandURL = _onaction;
-+ }
-+ OSL_TRACE(" ScVbaCommandBarControl::setOnAction: %s", rtl::OUStringToOString( aCommandURL, RTL_TEXTENCODING_UTF8 ).getStr() );
-+
- beans::PropertyValues aPropertyValues;
- m_xCurrentSettings->getByIndex( m_nPosition ) >>= aPropertyValues;
- beans::PropertyValues aNewPropertyValues;
-- aNewPropertyValues = lcl_repalcePropertyValue( aPropertyValues, rtl::OUString::createFromAscii("CommandURL"), uno::makeAny( _onaction ) );
-+ 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 ) )
- {
-@@ -401,3 +387,57 @@ ScVbaCommandBarControl::getServiceNames(
- }
- return aServiceNames;
- }
-+
-+//////////// ScVbaCommandBarPopup //////////////////////////////
-+ScVbaCommandBarPopup::ScVbaCommandBarPopup( const uno::Reference< XHelperInterface > xParent, const uno::Reference< uno::XComponentContext > xContext, rtl::OUString sName, sal_Int32 nPosition ) throw (uno::RuntimeException) : CommandBarPopup_BASE( xParent, xContext, sName, nPosition, office::MsoControlType::msoControlPopup )
-+{
-+}
-+
-+ScVbaCommandBarPopup::ScVbaCommandBarPopup( const uno::Reference< XHelperInterface > xParent, const uno::Reference< uno::XComponentContext > xContext, rtl::OUString sName, sal_Int32 nPosition, sal_Bool bTemporary ) throw (uno::RuntimeException) : CommandBarPopup_BASE( xParent, xContext, sName, nPosition, bTemporary, office::MsoControlType::msoControlPopup)
-+{
-+}
-+
-+rtl::OUString&
-+ScVbaCommandBarPopup::getServiceImplName()
-+{
-+ static rtl::OUString sImplName( RTL_CONSTASCII_USTRINGPARAM("ScVbaCommandBarPopup") );
-+ return sImplName;
-+}
-+uno::Sequence<rtl::OUString>
-+ScVbaCommandBarPopup::getServiceNames()
-+{
-+ static uno::Sequence< rtl::OUString > aServiceNames;
-+ if ( aServiceNames.getLength() == 0 )
-+ {
-+ aServiceNames.realloc( 1 );
-+ aServiceNames[ 0 ] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.CommandBarPopup" ) );
-+ }
-+ return aServiceNames;
-+}
-+
-+//////////// ScVbaCommandBarButton //////////////////////////////
-+ScVbaCommandBarButton::ScVbaCommandBarButton( const uno::Reference< XHelperInterface > xParent, const uno::Reference< uno::XComponentContext > xContext, rtl::OUString sName, sal_Int32 nPosition ) throw (uno::RuntimeException) : CommandBarButton_BASE( xParent, xContext, sName, nPosition, office::MsoControlType::msoControlButton )
-+{
-+}
-+
-+ScVbaCommandBarButton::ScVbaCommandBarButton( const uno::Reference< XHelperInterface > xParent, const uno::Reference< uno::XComponentContext > xContext, rtl::OUString sName, sal_Int32 nPosition, sal_Bool bTemporary ) throw (uno::RuntimeException) : CommandBarButton_BASE( xParent, xContext, sName, nPosition, bTemporary, office::MsoControlType::msoControlButton)
-+{
-+}
-+
-+rtl::OUString&
-+ScVbaCommandBarButton::getServiceImplName()
-+{
-+ static rtl::OUString sImplName( RTL_CONSTASCII_USTRINGPARAM("ScVbaCommandBarButton") );
-+ return sImplName;
-+}
-+uno::Sequence<rtl::OUString>
-+ScVbaCommandBarButton::getServiceNames()
-+{
-+ static uno::Sequence< rtl::OUString > aServiceNames;
-+ if ( aServiceNames.getLength() == 0 )
-+ {
-+ aServiceNames.realloc( 1 );
-+ aServiceNames[ 0 ] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.CommandBarButton" ) );
-+ }
-+ return aServiceNames;
-+}
---- sc/source/ui/vba/vbacommandbarcontrol.hxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbacommandbarcontrol.hxx 2009-04-06 16:42:00.000000000 +0000
-@@ -36,6 +36,9 @@
- #define SC_VBA_COMMANDBARCONTROL_HXX
-
- #include <ooo/vba/XCommandBarControl.hpp>
-+#include <ooo/vba/XCommandBarPopup.hpp>
-+#include <ooo/vba/XCommandBarButton.hpp>
-+#include <ooo/vba/office/MsoControlType.hpp>
-
- #include "vbahelperinterface.hxx"
- #include "vbacommandbarcontrols.hxx"
-@@ -64,8 +67,12 @@ private:
- void createNewMenuBarControl();
- void createNewToolBarControl();
- public:
-- ScVbaCommandBarControl( const css::uno::Reference< ov::XHelperInterface > xParent, const css::uno::Reference< css::uno::XComponentContext > xContext, rtl::OUString sName ) throw (css::uno::RuntimeException);
-- ScVbaCommandBarControl( const css::uno::Reference< ov::XHelperInterface > xParent, const css::uno::Reference< css::uno::XComponentContext > xContext, rtl::OUString sName, rtl::OUString sCommand, sal_Int32 nPosition, sal_Bool bTemporary ) throw (css::uno::RuntimeException);
-+ ScVbaCommandBarControl( const css::uno::Reference< ov::XHelperInterface > xParent, const css::uno::Reference< css::uno::XComponentContext > xContext, rtl::OUString sName, sal_Int32 nPosition = 0, sal_Int32 nType = ov::office::MsoControlType::msoControlButton ) throw (css::uno::RuntimeException);
-+ ScVbaCommandBarControl( const css::uno::Reference< ov::XHelperInterface > xParent, const css::uno::Reference< css::uno::XComponentContext > xContext, rtl::OUString sName, sal_Int32 nPosition, sal_Bool bTemporary, sal_Int32 nType = ov::office::MsoControlType::msoControlButton ) throw (css::uno::RuntimeException);
-+ css::uno::Reference< css::ui::XUIConfigurationManager > GetUICfgManager() { return m_xUICfgManager; };
-+ css::uno::Reference< css::ui::XUIConfigurationPersistence > GetUICfgPers() { return m_xUICfgPers; };
-+ css::uno::Reference< css::container::XIndexContainer > GetBarSettings() { return m_xBarSettings; };
-+ sal_Bool IsMenu() { return m_bIsMenu; };
- sal_Int32 GetPosition() { return m_nPosition; };
- css::uno::Reference< css::container::XIndexContainer > GetCurrentSettings() { return m_xCurrentSettings; };
- css::beans::PropertyValues GetPropertyValues() { return m_aPropertyValues; };
-@@ -87,4 +94,27 @@ public:
- virtual rtl::OUString& getServiceImplName();
- virtual css::uno::Sequence<rtl::OUString> getServiceNames();
- };
-+
-+typedef cppu::ImplInheritanceHelper1< ScVbaCommandBarControl, ov::XCommandBarPopup > CommandBarPopup_BASE;
-+class ScVbaCommandBarPopup : public CommandBarPopup_BASE
-+{
-+public:
-+ ScVbaCommandBarPopup( const css::uno::Reference< ov::XHelperInterface > xParent, const css::uno::Reference< css::uno::XComponentContext > xContext, rtl::OUString sName, sal_Int32 nPosition = 0 ) throw (css::uno::RuntimeException);
-+ ScVbaCommandBarPopup( const css::uno::Reference< ov::XHelperInterface > xParent, const css::uno::Reference< css::uno::XComponentContext > xContext, rtl::OUString sName, sal_Int32 nPosition, sal_Bool bTemporary ) throw (css::uno::RuntimeException);
-+ // XHelperInterface
-+ virtual rtl::OUString& getServiceImplName();
-+ virtual css::uno::Sequence<rtl::OUString> getServiceNames();
-+};
-+
-+typedef cppu::ImplInheritanceHelper1< ScVbaCommandBarControl, ov::XCommandBarButton > CommandBarButton_BASE;
-+class ScVbaCommandBarButton : public CommandBarButton_BASE
-+{
-+public:
-+ ScVbaCommandBarButton( const css::uno::Reference< ov::XHelperInterface > xParent, const css::uno::Reference< css::uno::XComponentContext > xContext, rtl::OUString sName, sal_Int32 nPosition = 0 ) throw (css::uno::RuntimeException);
-+ ScVbaCommandBarButton( const css::uno::Reference< ov::XHelperInterface > xParent, const css::uno::Reference< css::uno::XComponentContext > xContext, rtl::OUString sName, sal_Int32 nPosition, sal_Bool bTemporary ) throw (css::uno::RuntimeException);
-+ // XHelperInterface
-+ virtual rtl::OUString& getServiceImplName();
-+ virtual css::uno::Sequence<rtl::OUString> getServiceNames();
-+};
-+
- #endif//SC_VBA_COMMANDBARCONTROL_HXX
---- sc/source/ui/vba/vbacommandbarcontrols.cxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbacommandbarcontrols.cxx 2009-04-06 16:42:00.000000000 +0000
-@@ -38,6 +38,8 @@
- using namespace com::sun::star;
- using namespace ooo::vba;
-
-+uno::Any lcl_getPropertyValue( beans::PropertyValues aPropertyValues, rtl::OUString sPropertyName );
-+
- typedef ::cppu::WeakImplHelper1< container::XEnumeration > CommandBarControlEnumeration_BASE;
- class CommandBarControlEnumeration : public CommandBarControlEnumeration_BASE
- {
-@@ -88,6 +90,24 @@ ScVbaCommandBarControls::ScVbaCommandBar
- }
- else if( m_pCommandBarControl )
- {
-+ m_xUICfgManager.set( m_pCommandBarControl->GetUICfgManager(), uno::UNO_QUERY_THROW );
-+ m_xUICfgPers.set( m_pCommandBarControl->GetUICfgPers(), uno::UNO_QUERY_THROW );
-+ beans::PropertyValues aPropertyValues;
-+ m_pCommandBarControl->GetCurrentSettings()->getByIndex( m_pCommandBarControl->GetPosition() ) >>= aPropertyValues;
-+ m_pCommandBarControl->SetPropertyValues( aPropertyValues );
-+ m_xBarSettings.set( m_pCommandBarControl->GetCurrentSettings(), uno::UNO_QUERY_THROW );
-+
-+ uno::Any aValue = lcl_getPropertyValue( m_pCommandBarControl->GetPropertyValues(), rtl::OUString::createFromAscii("ItemDescriptorContainer") );
-+ if( aValue.hasValue() )
-+ {
-+ m_xCurrentSettings = m_pCommandBarControl->GetCurrentSettings();
-+ m_bHasElements = sal_True;
-+ }
-+ else
-+ {
-+ m_bHasElements = sal_False;
-+ }
-+ m_bIsMenu = m_pCommandBarControl->IsMenu();
- }
- else
- {
-@@ -170,7 +190,62 @@ ScVbaCommandBarControls::createCollectio
- // only surport the aSource as a name string, because this class is a API wrapper
- rtl::OUString sName;
- if( aSource >>= sName )
-- return uno::makeAny( uno::Reference< XCommandBarControl > ( new ScVbaCommandBarControl( this, mxContext, sName ) ) );
-+ {
-+ uno::Reference< container::XIndexContainer > xCurrentSettings;
-+ beans::PropertyValues aPropertyValues;
-+ if( m_pCommandBarControl )
-+ {
-+ m_pCommandBarControl->GetCurrentSettings()->getByIndex( m_pCommandBarControl->GetPosition() ) >>= aPropertyValues;
-+ xCurrentSettings.set( lcl_getPropertyValue( aPropertyValues, rtl::OUString::createFromAscii( "ItemDescriptorContainer" ) ), uno::UNO_QUERY );
-+ if( !xCurrentSettings.is() )
-+ {
-+ xCurrentSettings.set( m_xUICfgManager->getSettings( GetParentToolBarName(), sal_True ), uno::UNO_QUERY );
-+ }
-+ }
-+
-+ sal_Int32 nPosition = -1;
-+ for( sal_Int32 i = 0; i < xCurrentSettings->getCount(); i++ )
-+ {
-+ xCurrentSettings->getByIndex( i ) >>= aPropertyValues;
-+ // Label always empty in OOo
-+ rtl::OUString sLabel;
-+ lcl_getPropertyValue( aPropertyValues, rtl::OUString::createFromAscii( "Label" ) ) >>= sLabel;
-+ if( sLabel.equalsIgnoreAsciiCase( sName ) )
-+ {
-+ nPosition = i;
-+ break;
-+ }
-+ // using CammandURL to find
-+ rtl::OUString sCommandURL;
-+ lcl_getPropertyValue( aPropertyValues, rtl::OUString::createFromAscii( "CommandURL" ) ) >>= sCommandURL;
-+ sal_Int32 nLastIndex = sCommandURL.lastIndexOf( rtl::OUString::createFromAscii(":") );
-+ if( ( nLastIndex != -1 ) && ( ( nLastIndex + 1 ) < sCommandURL.getLength() ) )
-+ {
-+ sCommandURL = sCommandURL.copy( nLastIndex + 1 );
-+ }
-+ if( sCommandURL.equalsIgnoreAsciiCase( sName ) )
-+ {
-+ nPosition = i;
-+ break;
-+ }
-+ }
-+
-+ if( nPosition != -1 )
-+ {
-+ uno::Reference< container::XIndexContainer > xSubMenu;
-+ lcl_getPropertyValue( aPropertyValues, rtl::OUString::createFromAscii( "ItemDescriptorContainer" ) ) >>= xSubMenu;
-+ ScVbaCommandBarControl* pNewCommandBarControl = NULL;
-+ if( xSubMenu.is() )
-+ pNewCommandBarControl = new ScVbaCommandBarPopup( this, mxContext, sName, nPosition );
-+ else
-+ pNewCommandBarControl = new ScVbaCommandBarButton( this, mxContext, sName, nPosition );
-+
-+ return uno::makeAny( uno::Reference< XCommandBarControl > ( pNewCommandBarControl ) );
-+ }
-+ else
-+ throw uno::RuntimeException( rtl::OUString::createFromAscii("The CommandBarControl do not exist"), uno::Reference< uno::XInterface >() );
-+
-+ }
- return uno::Any();
- }
-
-@@ -213,16 +288,43 @@ ScVbaCommandBarControls::Add( const uno:
- // evalute the action of the new control
- }
- if( Before.hasValue() )
-- if( Before >>= nPosition )
-+ Before >>= nPosition;
-+ else
-+ {
-+ // if Before is ignore, the new control should be placed at the end of the commandbars;
-+ if( m_pCommandBar )
-+ nPosition = getCount();
-+ else if ( m_pCommandBarControl )
- {
-- // evalute the position of the new Control
-+ css::uno::Reference< css::container::XIndexContainer > xCurrentSettings;
-+ xCurrentSettings.set( lcl_getPropertyValue( m_pCommandBarControl->GetPropertyValues(), rtl::OUString::createFromAscii("ItemDescriptorContainer") ), uno::UNO_QUERY );
-+ if( xCurrentSettings.is() )
-+ {
-+ nPosition = xCurrentSettings->getCount();
-+ }
- }
-+ }
- if( Temporary.hasValue() )
- if( Temporary >>= bTemporary )
- {
- // evalute the temporary of the new Control
- }
-- return uno::Reference< XCommandBarControl > ( new ScVbaCommandBarControl( this, mxContext, sCaption, sCommand, nPosition, bTemporary ) );
-+
-+ ScVbaCommandBarControl* pNewCommandBarControl = NULL;
-+ if( nType == office::MsoControlType::msoControlButton )
-+ {
-+ pNewCommandBarControl = new ScVbaCommandBarButton( this, mxContext, sCaption, nPosition, bTemporary );
-+ }
-+ else if ( nType == office::MsoControlType::msoControlPopup )
-+ {
-+ pNewCommandBarControl = new ScVbaCommandBarPopup( this, mxContext, sCaption, nPosition, bTemporary );
-+ }
-+ else
-+ {
-+ pNewCommandBarControl = new ScVbaCommandBarControl( this, mxContext, sCaption, nPosition, bTemporary );
-+ }
-+
-+ return uno::Reference< XCommandBarControl >( pNewCommandBarControl );
- }
-
- // XHelperInterface
---- sc/source/ui/vba/vbacommandbarcontrols.hxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbacommandbarcontrols.hxx 2009-04-06 16:42:00.000000000 +0000
-@@ -56,6 +56,7 @@ private:
- css::uno::Reference< css::ui::XUIConfigurationManager > m_xUICfgManager;
- css::uno::Reference< css::ui::XUIConfigurationPersistence > m_xUICfgPers;
- css::uno::Reference< css::container::XIndexContainer > m_xBarSettings;
-+ css::uno::Reference< css::container::XIndexContainer > m_xCurrentSettings;
-
- public:
- ScVbaCommandBarControls( const css::uno::Reference< ov::XHelperInterface > xParent, const css::uno::Reference< css::uno::XComponentContext > xContext, const css::uno::Reference< css::container::XIndexAccess > xIndexAccess ) throw( css::uno::RuntimeException );
---- sc/source/ui/vba/vbacommandbars.cxx.old 2009-04-02 10:45:35.000000000 +0000
-+++ sc/source/ui/vba/vbacommandbars.cxx 2009-04-06 16:42:00.000000000 +0000
-@@ -201,6 +201,20 @@ ScVbaCommandBars::Item( const uno::Any&
- {
- return createCollectionObject( aIndex );
- }
-+
-+ // hardcode if "aIndex = 1" that would return "main menu".
-+ sal_Int16 nIndex = 0;
-+ aIndex >>= nIndex;
-+ if( nIndex == 1 )
-+ {
-+ uno::Any aSource;
-+ if( m_sModuleName.equalsIgnoreAsciiCase( sSpreadsheetDocumentUrl ) )
-+ aSource <<= rtl::OUString::createFromAscii( "Worksheet Menu Bar" );
-+ else if( m_sModuleName.equalsIgnoreAsciiCase( sTextDocumentUrl ) )
-+ aSource <<= rtl::OUString::createFromAscii( "Menu Bar" );
-+ if( aSource.hasValue() )
-+ return createCollectionObject( aSource );
-+ }
- return uno::Any();
- }
-