1*b3f79822SAndrew Rist /**************************************************************
2cdf0e10cSrcweir *
3*b3f79822SAndrew Rist * Licensed to the Apache Software Foundation (ASF) under one
4*b3f79822SAndrew Rist * or more contributor license agreements. See the NOTICE file
5*b3f79822SAndrew Rist * distributed with this work for additional information
6*b3f79822SAndrew Rist * regarding copyright ownership. The ASF licenses this file
7*b3f79822SAndrew Rist * to you under the Apache License, Version 2.0 (the
8*b3f79822SAndrew Rist * "License"); you may not use this file except in compliance
9*b3f79822SAndrew Rist * with the License. You may obtain a copy of the License at
10*b3f79822SAndrew Rist *
11*b3f79822SAndrew Rist * http://www.apache.org/licenses/LICENSE-2.0
12*b3f79822SAndrew Rist *
13*b3f79822SAndrew Rist * Unless required by applicable law or agreed to in writing,
14*b3f79822SAndrew Rist * software distributed under the License is distributed on an
15*b3f79822SAndrew Rist * "AS IS" BASIS, WITHOUT WARRANTIES OR CONDITIONS OF ANY
16*b3f79822SAndrew Rist * KIND, either express or implied. See the License for the
17*b3f79822SAndrew Rist * specific language governing permissions and limitations
18*b3f79822SAndrew Rist * under the License.
19*b3f79822SAndrew Rist *
20*b3f79822SAndrew Rist *************************************************************/
21*b3f79822SAndrew Rist
22*b3f79822SAndrew Rist
23cdf0e10cSrcweir
24cdf0e10cSrcweir #include "vbasheetobject.hxx"
25cdf0e10cSrcweir #include <com/sun/star/awt/TextAlign.hpp>
26cdf0e10cSrcweir #include <com/sun/star/container/XIndexContainer.hpp>
27cdf0e10cSrcweir #include <com/sun/star/drawing/XControlShape.hpp>
28cdf0e10cSrcweir #include <com/sun/star/script/ScriptEventDescriptor.hpp>
29cdf0e10cSrcweir #include <com/sun/star/script/XEventAttacherManager.hpp>
30cdf0e10cSrcweir #include <com/sun/star/style/VerticalAlignment.hpp>
31cdf0e10cSrcweir #include <ooo/vba/excel/Constants.hpp>
32cdf0e10cSrcweir #include <ooo/vba/excel/XlOrientation.hpp>
33cdf0e10cSrcweir #include <ooo/vba/excel/XlPlacement.hpp>
34cdf0e10cSrcweir #include <rtl/ustrbuf.hxx>
35cdf0e10cSrcweir #include <filter/msfilter/msvbahelper.hxx>
36cdf0e10cSrcweir #include <oox/helper/helper.hxx>
37cdf0e10cSrcweir #include <svx/unoshape.hxx>
38cdf0e10cSrcweir #include "vbafont.hxx"
39cdf0e10cSrcweir #include "drwlayer.hxx"
40cdf0e10cSrcweir
41cdf0e10cSrcweir using ::rtl::OUString;
42cdf0e10cSrcweir using namespace ::com::sun::star;
43cdf0e10cSrcweir using namespace ::ooo::vba;
44cdf0e10cSrcweir
45cdf0e10cSrcweir // ============================================================================
46cdf0e10cSrcweir
ScVbaButtonCharacters(const uno::Reference<XHelperInterface> & rxParent,const uno::Reference<uno::XComponentContext> & rxContext,const uno::Reference<beans::XPropertySet> & rxPropSet,const ScVbaPalette & rPalette,const uno::Any & rStart,const uno::Any & rLength)47cdf0e10cSrcweir ScVbaButtonCharacters::ScVbaButtonCharacters(
48cdf0e10cSrcweir const uno::Reference< XHelperInterface >& rxParent,
49cdf0e10cSrcweir const uno::Reference< uno::XComponentContext >& rxContext,
50cdf0e10cSrcweir const uno::Reference< beans::XPropertySet >& rxPropSet,
51cdf0e10cSrcweir const ScVbaPalette& rPalette,
52cdf0e10cSrcweir const uno::Any& rStart,
53cdf0e10cSrcweir const uno::Any& rLength ) throw (uno::RuntimeException) :
54cdf0e10cSrcweir ScVbaButtonCharacters_BASE( rxParent, rxContext ),
55cdf0e10cSrcweir maPalette( rPalette ),
56cdf0e10cSrcweir mxPropSet( rxPropSet, uno::UNO_SET_THROW )
57cdf0e10cSrcweir {
58cdf0e10cSrcweir // extract optional start parameter (missing or invalid -> from beginning)
59cdf0e10cSrcweir if( !(rStart >>= mnStart) || (mnStart < 1) )
60cdf0e10cSrcweir mnStart = 1;
61cdf0e10cSrcweir --mnStart; // VBA is 1-based, rtl string is 0-based
62cdf0e10cSrcweir
63cdf0e10cSrcweir // extract optional length parameter (missing or invalid -> to end)
64cdf0e10cSrcweir if( !(rLength >>= mnLength) || (mnLength < 1) )
65cdf0e10cSrcweir mnLength = SAL_MAX_INT32;
66cdf0e10cSrcweir }
67cdf0e10cSrcweir
~ScVbaButtonCharacters()68cdf0e10cSrcweir ScVbaButtonCharacters::~ScVbaButtonCharacters()
69cdf0e10cSrcweir {
70cdf0e10cSrcweir }
71cdf0e10cSrcweir
72cdf0e10cSrcweir // XCharacters attributes
73cdf0e10cSrcweir
getCaption()74cdf0e10cSrcweir OUString SAL_CALL ScVbaButtonCharacters::getCaption() throw (uno::RuntimeException)
75cdf0e10cSrcweir {
76cdf0e10cSrcweir // ignore invalid mnStart and/or mnLength members
77cdf0e10cSrcweir OUString aString = getFullString();
78cdf0e10cSrcweir sal_Int32 nStart = ::std::min( mnStart, aString.getLength() );
79cdf0e10cSrcweir sal_Int32 nLength = ::std::min( mnLength, aString.getLength() - nStart );
80cdf0e10cSrcweir return aString.copy( nStart, nLength );
81cdf0e10cSrcweir }
82cdf0e10cSrcweir
setCaption(const OUString & rCaption)83cdf0e10cSrcweir void SAL_CALL ScVbaButtonCharacters::setCaption( const OUString& rCaption ) throw (uno::RuntimeException)
84cdf0e10cSrcweir {
85cdf0e10cSrcweir /* Replace the covered text with the passed text, ignore invalid mnStart
86cdf0e10cSrcweir and/or mnLength members. This operation does not affect the mnLength
87cdf0e10cSrcweir parameter. If the inserted text is longer than mnLength, the additional
88cdf0e10cSrcweir characters are not covered by this object. If the inserted text is
89cdf0e10cSrcweir shorter than mnLength, other uncovered characters from the original
90cdf0e10cSrcweir string will be covered now, thus may be changed with subsequent
91cdf0e10cSrcweir operations. */
92cdf0e10cSrcweir OUString aString = getFullString();
93cdf0e10cSrcweir sal_Int32 nStart = ::std::min( mnStart, aString.getLength() );
94cdf0e10cSrcweir sal_Int32 nLength = ::std::min( mnLength, aString.getLength() - nStart );
95cdf0e10cSrcweir setFullString( aString.replaceAt( nStart, nLength, rCaption ) );
96cdf0e10cSrcweir }
97cdf0e10cSrcweir
getCount()98cdf0e10cSrcweir sal_Int32 SAL_CALL ScVbaButtonCharacters::getCount() throw (uno::RuntimeException)
99cdf0e10cSrcweir {
100cdf0e10cSrcweir // always return the total length of the caption
101cdf0e10cSrcweir return getFullString().getLength();
102cdf0e10cSrcweir }
103cdf0e10cSrcweir
getText()104cdf0e10cSrcweir OUString SAL_CALL ScVbaButtonCharacters::getText() throw (uno::RuntimeException)
105cdf0e10cSrcweir {
106cdf0e10cSrcweir // Text attribute same as Caption attribute?
107cdf0e10cSrcweir return getCaption();
108cdf0e10cSrcweir }
109cdf0e10cSrcweir
setText(const OUString & rText)110cdf0e10cSrcweir void SAL_CALL ScVbaButtonCharacters::setText( const OUString& rText ) throw (uno::RuntimeException)
111cdf0e10cSrcweir {
112cdf0e10cSrcweir // Text attribute same as Caption attribute?
113cdf0e10cSrcweir setCaption( rText );
114cdf0e10cSrcweir }
115cdf0e10cSrcweir
getFont()116cdf0e10cSrcweir uno::Reference< excel::XFont > SAL_CALL ScVbaButtonCharacters::getFont() throw (uno::RuntimeException)
117cdf0e10cSrcweir {
118cdf0e10cSrcweir return new ScVbaFont( this, mxContext, maPalette, mxPropSet, 0, true );
119cdf0e10cSrcweir }
120cdf0e10cSrcweir
setFont(const uno::Reference<excel::XFont> &)121cdf0e10cSrcweir void SAL_CALL ScVbaButtonCharacters::setFont( const uno::Reference< excel::XFont >& /*rxFont*/ ) throw (uno::RuntimeException)
122cdf0e10cSrcweir {
123cdf0e10cSrcweir // TODO
124cdf0e10cSrcweir }
125cdf0e10cSrcweir
126cdf0e10cSrcweir // XCharacters methods
127cdf0e10cSrcweir
Insert(const OUString & rString)128cdf0e10cSrcweir void SAL_CALL ScVbaButtonCharacters::Insert( const OUString& rString ) throw (uno::RuntimeException)
129cdf0e10cSrcweir {
130cdf0e10cSrcweir /* The Insert() operation is in fact "replace covered characters", at
131cdf0e10cSrcweir least for buttons... It seems there is no easy way to really insert a
132cdf0e10cSrcweir substring. This operation does not affect the mnLength parameter. */
133cdf0e10cSrcweir setCaption( rString );
134cdf0e10cSrcweir }
135cdf0e10cSrcweir
Delete()136cdf0e10cSrcweir void SAL_CALL ScVbaButtonCharacters::Delete() throw (uno::RuntimeException)
137cdf0e10cSrcweir {
138cdf0e10cSrcweir /* The Delete() operation is nothing else than "replace with empty string".
139cdf0e10cSrcweir This does not affect the mnLength parameter, multiple calls of Delete()
140cdf0e10cSrcweir will remove characters as long as there are some more covered by this
141cdf0e10cSrcweir object. */
142cdf0e10cSrcweir setCaption( OUString() );
143cdf0e10cSrcweir }
144cdf0e10cSrcweir
145cdf0e10cSrcweir // XHelperInterface
146cdf0e10cSrcweir
147cdf0e10cSrcweir VBAHELPER_IMPL_XHELPERINTERFACE( ScVbaButtonCharacters, "ooo.vba.excel.Characters" )
148cdf0e10cSrcweir
149cdf0e10cSrcweir // private
150cdf0e10cSrcweir
getFullString() const151cdf0e10cSrcweir OUString ScVbaButtonCharacters::getFullString() const throw (uno::RuntimeException)
152cdf0e10cSrcweir {
153cdf0e10cSrcweir return mxPropSet->getPropertyValue( CREATE_OUSTRING( "Label" ) ).get< OUString >();
154cdf0e10cSrcweir }
155cdf0e10cSrcweir
setFullString(const OUString & rString)156cdf0e10cSrcweir void ScVbaButtonCharacters::setFullString( const OUString& rString ) throw (uno::RuntimeException)
157cdf0e10cSrcweir {
158cdf0e10cSrcweir mxPropSet->setPropertyValue( CREATE_OUSTRING( "Label" ), uno::Any( rString ) );
159cdf0e10cSrcweir }
160cdf0e10cSrcweir
161cdf0e10cSrcweir // ============================================================================
162cdf0e10cSrcweir
ScVbaSheetObjectBase(const uno::Reference<XHelperInterface> & rxParent,const uno::Reference<uno::XComponentContext> & rxContext,const uno::Reference<frame::XModel> & rxModel,const uno::Reference<drawing::XShape> & rxShape)163cdf0e10cSrcweir ScVbaSheetObjectBase::ScVbaSheetObjectBase(
164cdf0e10cSrcweir const uno::Reference< XHelperInterface >& rxParent,
165cdf0e10cSrcweir const uno::Reference< uno::XComponentContext >& rxContext,
166cdf0e10cSrcweir const uno::Reference< frame::XModel >& rxModel,
167cdf0e10cSrcweir const uno::Reference< drawing::XShape >& rxShape ) throw (uno::RuntimeException) :
168cdf0e10cSrcweir ScVbaSheetObject_BASE( rxParent, rxContext ),
169cdf0e10cSrcweir maPalette( rxModel ),
170cdf0e10cSrcweir mxModel( rxModel, uno::UNO_SET_THROW ),
171cdf0e10cSrcweir mxShape( rxShape, uno::UNO_SET_THROW ),
172cdf0e10cSrcweir mxShapeProps( rxShape, uno::UNO_QUERY_THROW )
173cdf0e10cSrcweir {
174cdf0e10cSrcweir }
175cdf0e10cSrcweir
176cdf0e10cSrcweir // XSheetObject attributes
177cdf0e10cSrcweir
getLeft()178cdf0e10cSrcweir double SAL_CALL ScVbaSheetObjectBase::getLeft() throw (uno::RuntimeException)
179cdf0e10cSrcweir {
180cdf0e10cSrcweir return HmmToPoints( mxShape->getPosition().X );
181cdf0e10cSrcweir }
182cdf0e10cSrcweir
setLeft(double fLeft)183cdf0e10cSrcweir void SAL_CALL ScVbaSheetObjectBase::setLeft( double fLeft ) throw (uno::RuntimeException)
184cdf0e10cSrcweir {
185cdf0e10cSrcweir if( fLeft < 0.0 )
186cdf0e10cSrcweir throw uno::RuntimeException();
187cdf0e10cSrcweir mxShape->setPosition( awt::Point( PointsToHmm( fLeft ), mxShape->getPosition().Y ) );
188cdf0e10cSrcweir }
189cdf0e10cSrcweir
getTop()190cdf0e10cSrcweir double SAL_CALL ScVbaSheetObjectBase::getTop() throw (uno::RuntimeException)
191cdf0e10cSrcweir {
192cdf0e10cSrcweir return HmmToPoints( mxShape->getPosition().Y );
193cdf0e10cSrcweir }
194cdf0e10cSrcweir
setTop(double fTop)195cdf0e10cSrcweir void SAL_CALL ScVbaSheetObjectBase::setTop( double fTop ) throw (uno::RuntimeException)
196cdf0e10cSrcweir {
197cdf0e10cSrcweir if( fTop < 0.0 )
198cdf0e10cSrcweir throw uno::RuntimeException();
199cdf0e10cSrcweir mxShape->setPosition( awt::Point( mxShape->getPosition().X, PointsToHmm( fTop ) ) );
200cdf0e10cSrcweir }
201cdf0e10cSrcweir
getWidth()202cdf0e10cSrcweir double SAL_CALL ScVbaSheetObjectBase::getWidth() throw (uno::RuntimeException)
203cdf0e10cSrcweir {
204cdf0e10cSrcweir return HmmToPoints( mxShape->getSize().Width );
205cdf0e10cSrcweir }
206cdf0e10cSrcweir
setWidth(double fWidth)207cdf0e10cSrcweir void SAL_CALL ScVbaSheetObjectBase::setWidth( double fWidth ) throw (uno::RuntimeException)
208cdf0e10cSrcweir {
209cdf0e10cSrcweir if( fWidth <= 0.0 )
210cdf0e10cSrcweir throw uno::RuntimeException();
211cdf0e10cSrcweir mxShape->setSize( awt::Size( PointsToHmm( fWidth ), mxShape->getSize().Height ) );
212cdf0e10cSrcweir }
213cdf0e10cSrcweir
getHeight()214cdf0e10cSrcweir double SAL_CALL ScVbaSheetObjectBase::getHeight() throw (uno::RuntimeException)
215cdf0e10cSrcweir {
216cdf0e10cSrcweir return HmmToPoints( mxShape->getSize().Height );
217cdf0e10cSrcweir }
218cdf0e10cSrcweir
setHeight(double fHeight)219cdf0e10cSrcweir void SAL_CALL ScVbaSheetObjectBase::setHeight( double fHeight ) throw (uno::RuntimeException)
220cdf0e10cSrcweir {
221cdf0e10cSrcweir if( fHeight <= 0.0 )
222cdf0e10cSrcweir throw uno::RuntimeException();
223cdf0e10cSrcweir mxShape->setSize( awt::Size( mxShape->getSize().Width, PointsToHmm( fHeight ) ) );
224cdf0e10cSrcweir }
225cdf0e10cSrcweir
getName()226cdf0e10cSrcweir OUString SAL_CALL ScVbaSheetObjectBase::getName() throw (uno::RuntimeException)
227cdf0e10cSrcweir {
228cdf0e10cSrcweir return mxShapeProps->getPropertyValue( CREATE_OUSTRING( "Name" ) ).get< OUString >();
229cdf0e10cSrcweir }
230cdf0e10cSrcweir
setName(const OUString & rName)231cdf0e10cSrcweir void SAL_CALL ScVbaSheetObjectBase::setName( const OUString& rName ) throw (uno::RuntimeException)
232cdf0e10cSrcweir {
233cdf0e10cSrcweir mxShapeProps->setPropertyValue( CREATE_OUSTRING( "Name" ), uno::Any( rName ) );
234cdf0e10cSrcweir }
235cdf0e10cSrcweir
getPlacement()236cdf0e10cSrcweir sal_Int32 SAL_CALL ScVbaSheetObjectBase::getPlacement() throw (uno::RuntimeException)
237cdf0e10cSrcweir {
238cdf0e10cSrcweir sal_Int32 nRet = excel::XlPlacement::xlMoveAndSize;
239cdf0e10cSrcweir SvxShape* pShape = SvxShape::getImplementation( mxShape );
240cdf0e10cSrcweir if(pShape)
241cdf0e10cSrcweir {
242cdf0e10cSrcweir SdrObject* pObj = pShape->GetSdrObject();
243cdf0e10cSrcweir if (pObj)
244cdf0e10cSrcweir {
245cdf0e10cSrcweir ScAnchorType eType = ScDrawLayer::GetAnchor(pObj);
246cdf0e10cSrcweir if (eType == SCA_PAGE)
247cdf0e10cSrcweir nRet = excel::XlPlacement::xlFreeFloating;
248cdf0e10cSrcweir }
249cdf0e10cSrcweir }
250cdf0e10cSrcweir return nRet;
251cdf0e10cSrcweir }
252cdf0e10cSrcweir
setPlacement(sal_Int32 nPlacement)253cdf0e10cSrcweir void SAL_CALL ScVbaSheetObjectBase::setPlacement( sal_Int32 nPlacement ) throw (uno::RuntimeException)
254cdf0e10cSrcweir {
255cdf0e10cSrcweir SvxShape* pShape = SvxShape::getImplementation( mxShape );
256cdf0e10cSrcweir if(pShape)
257cdf0e10cSrcweir {
258cdf0e10cSrcweir SdrObject* pObj = pShape->GetSdrObject();
259cdf0e10cSrcweir if (pObj)
260cdf0e10cSrcweir {
261cdf0e10cSrcweir ScAnchorType eType = SCA_CELL;
262cdf0e10cSrcweir if ( nPlacement == excel::XlPlacement::xlFreeFloating )
263cdf0e10cSrcweir eType = SCA_PAGE;
264cdf0e10cSrcweir
265cdf0e10cSrcweir // xlMove is not supported, treated as SCA_CELL (xlMoveAndSize)
266cdf0e10cSrcweir
267cdf0e10cSrcweir ScDrawLayer::SetAnchor(pObj, eType);
268cdf0e10cSrcweir }
269cdf0e10cSrcweir }
270cdf0e10cSrcweir }
271cdf0e10cSrcweir
getPrintObject()272cdf0e10cSrcweir sal_Bool SAL_CALL ScVbaSheetObjectBase::getPrintObject() throw (uno::RuntimeException)
273cdf0e10cSrcweir {
274cdf0e10cSrcweir // not supported
275cdf0e10cSrcweir return sal_True;
276cdf0e10cSrcweir }
277cdf0e10cSrcweir
setPrintObject(sal_Bool)278cdf0e10cSrcweir void SAL_CALL ScVbaSheetObjectBase::setPrintObject( sal_Bool /*bPrintObject*/ ) throw (uno::RuntimeException)
279cdf0e10cSrcweir {
280cdf0e10cSrcweir // not supported
281cdf0e10cSrcweir }
282cdf0e10cSrcweir
283cdf0e10cSrcweir // private
284cdf0e10cSrcweir
setDefaultProperties(sal_Int32 nIndex)285cdf0e10cSrcweir void ScVbaSheetObjectBase::setDefaultProperties( sal_Int32 nIndex ) throw (uno::RuntimeException)
286cdf0e10cSrcweir {
287cdf0e10cSrcweir OUString aName = ::rtl::OUStringBuffer( implGetBaseName() ).append( sal_Unicode( ' ' ) ).append( nIndex + 1 ).makeStringAndClear();
288cdf0e10cSrcweir setName( aName );
289cdf0e10cSrcweir implSetDefaultProperties();
290cdf0e10cSrcweir }
291cdf0e10cSrcweir
implSetDefaultProperties()292cdf0e10cSrcweir void ScVbaSheetObjectBase::implSetDefaultProperties() throw (uno::RuntimeException)
293cdf0e10cSrcweir {
294cdf0e10cSrcweir }
295cdf0e10cSrcweir
296cdf0e10cSrcweir // ============================================================================
297cdf0e10cSrcweir
ScVbaControlObjectBase(const uno::Reference<XHelperInterface> & rxParent,const uno::Reference<uno::XComponentContext> & rxContext,const uno::Reference<frame::XModel> & rxModel,const uno::Reference<container::XIndexContainer> & rxFormIC,const uno::Reference<drawing::XControlShape> & rxControlShape,ListenerType eListenerType)298cdf0e10cSrcweir ScVbaControlObjectBase::ScVbaControlObjectBase(
299cdf0e10cSrcweir const uno::Reference< XHelperInterface >& rxParent,
300cdf0e10cSrcweir const uno::Reference< uno::XComponentContext >& rxContext,
301cdf0e10cSrcweir const uno::Reference< frame::XModel >& rxModel,
302cdf0e10cSrcweir const uno::Reference< container::XIndexContainer >& rxFormIC,
303cdf0e10cSrcweir const uno::Reference< drawing::XControlShape >& rxControlShape,
304cdf0e10cSrcweir ListenerType eListenerType ) throw (uno::RuntimeException) :
305cdf0e10cSrcweir ScVbaControlObject_BASE( rxParent, rxContext, rxModel, uno::Reference< drawing::XShape >( rxControlShape, uno::UNO_QUERY_THROW ) ),
306cdf0e10cSrcweir mxFormIC( rxFormIC, uno::UNO_SET_THROW ),
307cdf0e10cSrcweir mxControlProps( rxControlShape->getControl(), uno::UNO_QUERY_THROW )
308cdf0e10cSrcweir {
309cdf0e10cSrcweir // set listener and event name to be used for OnAction attribute
310cdf0e10cSrcweir switch( eListenerType )
311cdf0e10cSrcweir {
312cdf0e10cSrcweir case LISTENER_ACTION:
313cdf0e10cSrcweir maListenerType = CREATE_OUSTRING( "XActionListener" );
314cdf0e10cSrcweir maEventMethod = CREATE_OUSTRING( "actionPerformed" );
315cdf0e10cSrcweir break;
316cdf0e10cSrcweir case LISTENER_MOUSE:
317cdf0e10cSrcweir maListenerType = CREATE_OUSTRING( "XMouseListener" );
318cdf0e10cSrcweir maEventMethod = CREATE_OUSTRING( "mouseReleased" );
319cdf0e10cSrcweir break;
320cdf0e10cSrcweir case LISTENER_TEXT:
321cdf0e10cSrcweir maListenerType = CREATE_OUSTRING( "XTextListener" );
322cdf0e10cSrcweir maEventMethod = CREATE_OUSTRING( "textChanged" );
323cdf0e10cSrcweir break;
324cdf0e10cSrcweir case LISTENER_VALUE:
325cdf0e10cSrcweir maListenerType = CREATE_OUSTRING( "XAdjustmentListener" );
326cdf0e10cSrcweir maEventMethod = CREATE_OUSTRING( "adjustmentValueChanged" );
327cdf0e10cSrcweir break;
328cdf0e10cSrcweir case LISTENER_CHANGE:
329cdf0e10cSrcweir maListenerType = CREATE_OUSTRING( "XChangeListener" );
330cdf0e10cSrcweir maEventMethod = CREATE_OUSTRING( "changed" );
331cdf0e10cSrcweir break;
332cdf0e10cSrcweir // no default, to let the compiler complain about missing case
333cdf0e10cSrcweir }
334cdf0e10cSrcweir }
335cdf0e10cSrcweir
336cdf0e10cSrcweir // XSheetObject attributes
337cdf0e10cSrcweir
getName()338cdf0e10cSrcweir OUString SAL_CALL ScVbaControlObjectBase::getName() throw (uno::RuntimeException)
339cdf0e10cSrcweir {
340cdf0e10cSrcweir return mxControlProps->getPropertyValue( CREATE_OUSTRING( "Name" ) ).get< OUString >();
341cdf0e10cSrcweir }
342cdf0e10cSrcweir
setName(const OUString & rName)343cdf0e10cSrcweir void SAL_CALL ScVbaControlObjectBase::setName( const OUString& rName ) throw (uno::RuntimeException)
344cdf0e10cSrcweir {
345cdf0e10cSrcweir mxControlProps->setPropertyValue( CREATE_OUSTRING( "Name" ), uno::Any( rName ) );
346cdf0e10cSrcweir }
347cdf0e10cSrcweir
getOnAction()348cdf0e10cSrcweir OUString SAL_CALL ScVbaControlObjectBase::getOnAction() throw (uno::RuntimeException)
349cdf0e10cSrcweir {
350cdf0e10cSrcweir uno::Reference< script::XEventAttacherManager > xEventMgr( mxFormIC, uno::UNO_QUERY_THROW );
351cdf0e10cSrcweir sal_Int32 nIndex = getModelIndexInForm();
352cdf0e10cSrcweir uno::Sequence< script::ScriptEventDescriptor > aEvents = xEventMgr->getScriptEvents( nIndex );
353cdf0e10cSrcweir if( aEvents.hasElements() )
354cdf0e10cSrcweir {
355cdf0e10cSrcweir const script::ScriptEventDescriptor* pEvent = aEvents.getConstArray();
356cdf0e10cSrcweir const script::ScriptEventDescriptor* pEventEnd = pEvent + aEvents.getLength();
357cdf0e10cSrcweir const OUString aScriptType = CREATE_OUSTRING( "Script" );
358cdf0e10cSrcweir for( ; pEvent < pEventEnd; ++pEvent )
359cdf0e10cSrcweir if( (pEvent->ListenerType == maListenerType) && (pEvent->EventMethod == maEventMethod) && (pEvent->ScriptType == aScriptType) )
360cdf0e10cSrcweir return extractMacroName( pEvent->ScriptCode );
361cdf0e10cSrcweir }
362cdf0e10cSrcweir return OUString();
363cdf0e10cSrcweir }
364cdf0e10cSrcweir
setOnAction(const OUString & rMacroName)365cdf0e10cSrcweir void SAL_CALL ScVbaControlObjectBase::setOnAction( const OUString& rMacroName ) throw (uno::RuntimeException)
366cdf0e10cSrcweir {
367cdf0e10cSrcweir uno::Reference< script::XEventAttacherManager > xEventMgr( mxFormIC, uno::UNO_QUERY_THROW );
368cdf0e10cSrcweir sal_Int32 nIndex = getModelIndexInForm();
369cdf0e10cSrcweir
370cdf0e10cSrcweir // first, remove a registered event (try/catch just in case implementation throws)
371cdf0e10cSrcweir try { xEventMgr->revokeScriptEvent( nIndex, maListenerType, maEventMethod, OUString() ); } catch( uno::Exception& ) {}
372cdf0e10cSrcweir
373cdf0e10cSrcweir // if a macro name has been passed, try to attach it to the event
374cdf0e10cSrcweir if( rMacroName.getLength() > 0 )
375cdf0e10cSrcweir {
376cdf0e10cSrcweir MacroResolvedInfo aResolvedMacro = resolveVBAMacro( getSfxObjShell( mxModel ), rMacroName );
377cdf0e10cSrcweir if( !aResolvedMacro.mbFound )
378cdf0e10cSrcweir throw uno::RuntimeException();
379cdf0e10cSrcweir script::ScriptEventDescriptor aDescriptor;
380cdf0e10cSrcweir aDescriptor.ListenerType = maListenerType;
381cdf0e10cSrcweir aDescriptor.EventMethod = maEventMethod;
382cdf0e10cSrcweir aDescriptor.ScriptType = CREATE_OUSTRING( "Script" );
383cdf0e10cSrcweir aDescriptor.ScriptCode = makeMacroURL( aResolvedMacro.msResolvedMacro );
384cdf0e10cSrcweir xEventMgr->registerScriptEvent( nIndex, aDescriptor );
385cdf0e10cSrcweir }
386cdf0e10cSrcweir }
387cdf0e10cSrcweir
getPrintObject()388cdf0e10cSrcweir sal_Bool SAL_CALL ScVbaControlObjectBase::getPrintObject() throw (uno::RuntimeException)
389cdf0e10cSrcweir {
390cdf0e10cSrcweir return mxControlProps->getPropertyValue( CREATE_OUSTRING( "Printable" ) ).get< sal_Bool >();
391cdf0e10cSrcweir }
392cdf0e10cSrcweir
setPrintObject(sal_Bool bPrintObject)393cdf0e10cSrcweir void SAL_CALL ScVbaControlObjectBase::setPrintObject( sal_Bool bPrintObject ) throw (uno::RuntimeException)
394cdf0e10cSrcweir {
395cdf0e10cSrcweir mxControlProps->setPropertyValue( CREATE_OUSTRING( "Printable" ), uno::Any( bPrintObject ) );
396cdf0e10cSrcweir }
397cdf0e10cSrcweir
398cdf0e10cSrcweir // XControlObject attributes
399cdf0e10cSrcweir
getAutoSize()400cdf0e10cSrcweir sal_Bool SAL_CALL ScVbaControlObjectBase::getAutoSize() throw (uno::RuntimeException)
401cdf0e10cSrcweir {
402cdf0e10cSrcweir // not supported
403cdf0e10cSrcweir return sal_False;
404cdf0e10cSrcweir }
405cdf0e10cSrcweir
setAutoSize(sal_Bool)406cdf0e10cSrcweir void SAL_CALL ScVbaControlObjectBase::setAutoSize( sal_Bool /*bAutoSize*/ ) throw (uno::RuntimeException)
407cdf0e10cSrcweir {
408cdf0e10cSrcweir // not supported
409cdf0e10cSrcweir }
410cdf0e10cSrcweir
411cdf0e10cSrcweir // private
412cdf0e10cSrcweir
getModelIndexInForm() const413cdf0e10cSrcweir sal_Int32 ScVbaControlObjectBase::getModelIndexInForm() const throw (uno::RuntimeException)
414cdf0e10cSrcweir {
415cdf0e10cSrcweir for( sal_Int32 nIndex = 0, nCount = mxFormIC->getCount(); nIndex < nCount; ++nIndex )
416cdf0e10cSrcweir {
417cdf0e10cSrcweir uno::Reference< beans::XPropertySet > xProps( mxFormIC->getByIndex( nIndex ), uno::UNO_QUERY_THROW );
418cdf0e10cSrcweir if( mxControlProps.get() == xProps.get() )
419cdf0e10cSrcweir return nIndex;
420cdf0e10cSrcweir }
421cdf0e10cSrcweir throw uno::RuntimeException();
422cdf0e10cSrcweir }
423cdf0e10cSrcweir
424cdf0e10cSrcweir // ============================================================================
425cdf0e10cSrcweir
ScVbaButton(const uno::Reference<XHelperInterface> & rxParent,const uno::Reference<uno::XComponentContext> & rxContext,const uno::Reference<frame::XModel> & rxModel,const uno::Reference<container::XIndexContainer> & rxFormIC,const uno::Reference<drawing::XControlShape> & rxControlShape)426cdf0e10cSrcweir ScVbaButton::ScVbaButton(
427cdf0e10cSrcweir const uno::Reference< XHelperInterface >& rxParent,
428cdf0e10cSrcweir const uno::Reference< uno::XComponentContext >& rxContext,
429cdf0e10cSrcweir const uno::Reference< frame::XModel >& rxModel,
430cdf0e10cSrcweir const uno::Reference< container::XIndexContainer >& rxFormIC,
431cdf0e10cSrcweir const uno::Reference< drawing::XControlShape >& rxControlShape ) throw (uno::RuntimeException) :
432cdf0e10cSrcweir ScVbaButton_BASE( rxParent, rxContext, rxModel, rxFormIC, rxControlShape, LISTENER_ACTION )
433cdf0e10cSrcweir {
434cdf0e10cSrcweir }
435cdf0e10cSrcweir
436cdf0e10cSrcweir // XButton attributes
437cdf0e10cSrcweir
getCaption()438cdf0e10cSrcweir OUString SAL_CALL ScVbaButton::getCaption() throw (uno::RuntimeException)
439cdf0e10cSrcweir {
440cdf0e10cSrcweir return mxControlProps->getPropertyValue( CREATE_OUSTRING( "Label" ) ).get< OUString >();
441cdf0e10cSrcweir }
442cdf0e10cSrcweir
setCaption(const OUString & rCaption)443cdf0e10cSrcweir void SAL_CALL ScVbaButton::setCaption( const OUString& rCaption ) throw (uno::RuntimeException)
444cdf0e10cSrcweir {
445cdf0e10cSrcweir mxControlProps->setPropertyValue( CREATE_OUSTRING( "Label" ), uno::Any( rCaption ) );
446cdf0e10cSrcweir }
447cdf0e10cSrcweir
getFont()448cdf0e10cSrcweir uno::Reference< excel::XFont > SAL_CALL ScVbaButton::getFont() throw (uno::RuntimeException)
449cdf0e10cSrcweir {
450cdf0e10cSrcweir return new ScVbaFont( this, mxContext, maPalette, mxControlProps, 0, true );
451cdf0e10cSrcweir }
452cdf0e10cSrcweir
setFont(const uno::Reference<excel::XFont> &)453cdf0e10cSrcweir void SAL_CALL ScVbaButton::setFont( const uno::Reference< excel::XFont >& /*rxFont*/ ) throw (uno::RuntimeException)
454cdf0e10cSrcweir {
455cdf0e10cSrcweir // TODO
456cdf0e10cSrcweir }
457cdf0e10cSrcweir
getHorizontalAlignment()458cdf0e10cSrcweir sal_Int32 SAL_CALL ScVbaButton::getHorizontalAlignment() throw (uno::RuntimeException)
459cdf0e10cSrcweir {
460cdf0e10cSrcweir switch( mxControlProps->getPropertyValue( CREATE_OUSTRING( "Align" ) ).get< sal_Int16 >() )
461cdf0e10cSrcweir {
462cdf0e10cSrcweir case awt::TextAlign::LEFT: return excel::Constants::xlLeft;
463cdf0e10cSrcweir case awt::TextAlign::RIGHT: return excel::Constants::xlRight;
464cdf0e10cSrcweir case awt::TextAlign::CENTER: return excel::Constants::xlCenter;
465cdf0e10cSrcweir }
466cdf0e10cSrcweir return excel::Constants::xlCenter;
467cdf0e10cSrcweir }
468cdf0e10cSrcweir
setHorizontalAlignment(sal_Int32 nAlign)469cdf0e10cSrcweir void SAL_CALL ScVbaButton::setHorizontalAlignment( sal_Int32 nAlign ) throw (uno::RuntimeException)
470cdf0e10cSrcweir {
471cdf0e10cSrcweir sal_Int32 nAwtAlign = awt::TextAlign::CENTER;
472cdf0e10cSrcweir switch( nAlign )
473cdf0e10cSrcweir {
474cdf0e10cSrcweir case excel::Constants::xlLeft: nAwtAlign = awt::TextAlign::LEFT; break;
475cdf0e10cSrcweir case excel::Constants::xlRight: nAwtAlign = awt::TextAlign::RIGHT; break;
476cdf0e10cSrcweir case excel::Constants::xlCenter: nAwtAlign = awt::TextAlign::CENTER; break;
477cdf0e10cSrcweir }
478cdf0e10cSrcweir // form controls expect short value
479cdf0e10cSrcweir mxControlProps->setPropertyValue( CREATE_OUSTRING( "Align" ), uno::Any( static_cast< sal_Int16 >( nAwtAlign ) ) );
480cdf0e10cSrcweir }
481cdf0e10cSrcweir
getVerticalAlignment()482cdf0e10cSrcweir sal_Int32 SAL_CALL ScVbaButton::getVerticalAlignment() throw (uno::RuntimeException)
483cdf0e10cSrcweir {
484cdf0e10cSrcweir switch( mxControlProps->getPropertyValue( CREATE_OUSTRING( "VerticalAlign" ) ).get< style::VerticalAlignment >() )
485cdf0e10cSrcweir {
486cdf0e10cSrcweir case style::VerticalAlignment_TOP: return excel::Constants::xlTop;
487cdf0e10cSrcweir case style::VerticalAlignment_BOTTOM: return excel::Constants::xlBottom;
488cdf0e10cSrcweir case style::VerticalAlignment_MIDDLE: return excel::Constants::xlCenter;
489cdf0e10cSrcweir default:;
490cdf0e10cSrcweir }
491cdf0e10cSrcweir return excel::Constants::xlCenter;
492cdf0e10cSrcweir }
493cdf0e10cSrcweir
setVerticalAlignment(sal_Int32 nAlign)494cdf0e10cSrcweir void SAL_CALL ScVbaButton::setVerticalAlignment( sal_Int32 nAlign ) throw (uno::RuntimeException)
495cdf0e10cSrcweir {
496cdf0e10cSrcweir style::VerticalAlignment eAwtAlign = style::VerticalAlignment_MIDDLE;
497cdf0e10cSrcweir switch( nAlign )
498cdf0e10cSrcweir {
499cdf0e10cSrcweir case excel::Constants::xlTop: eAwtAlign = style::VerticalAlignment_TOP; break;
500cdf0e10cSrcweir case excel::Constants::xlBottom: eAwtAlign = style::VerticalAlignment_BOTTOM; break;
501cdf0e10cSrcweir case excel::Constants::xlCenter: eAwtAlign = style::VerticalAlignment_MIDDLE; break;
502cdf0e10cSrcweir }
503cdf0e10cSrcweir mxControlProps->setPropertyValue( CREATE_OUSTRING( "VerticalAlign" ), uno::Any( eAwtAlign ) );
504cdf0e10cSrcweir }
505cdf0e10cSrcweir
getOrientation()506cdf0e10cSrcweir sal_Int32 SAL_CALL ScVbaButton::getOrientation() throw (uno::RuntimeException)
507cdf0e10cSrcweir {
508cdf0e10cSrcweir // not supported
509cdf0e10cSrcweir return excel::XlOrientation::xlHorizontal;
510cdf0e10cSrcweir }
511cdf0e10cSrcweir
setOrientation(sal_Int32)512cdf0e10cSrcweir void SAL_CALL ScVbaButton::setOrientation( sal_Int32 /*nOrientation*/ ) throw (uno::RuntimeException)
513cdf0e10cSrcweir {
514cdf0e10cSrcweir // not supported
515cdf0e10cSrcweir }
516cdf0e10cSrcweir
517cdf0e10cSrcweir // XButton methods
518cdf0e10cSrcweir
Characters(const uno::Any & rStart,const uno::Any & rLength)519cdf0e10cSrcweir uno::Reference< excel::XCharacters > SAL_CALL ScVbaButton::Characters( const uno::Any& rStart, const uno::Any& rLength ) throw (uno::RuntimeException)
520cdf0e10cSrcweir {
521cdf0e10cSrcweir return new ScVbaButtonCharacters( this, mxContext, mxControlProps, maPalette, rStart, rLength );
522cdf0e10cSrcweir }
523cdf0e10cSrcweir
524cdf0e10cSrcweir // XHelperInterface
525cdf0e10cSrcweir
526cdf0e10cSrcweir VBAHELPER_IMPL_XHELPERINTERFACE( ScVbaButton, "ooo.vba.excel.Button" )
527cdf0e10cSrcweir
528cdf0e10cSrcweir // private
529cdf0e10cSrcweir
implGetBaseName() const530cdf0e10cSrcweir OUString ScVbaButton::implGetBaseName() const
531cdf0e10cSrcweir {
532cdf0e10cSrcweir return CREATE_OUSTRING( "Button" );
533cdf0e10cSrcweir }
534cdf0e10cSrcweir
implSetDefaultProperties()535cdf0e10cSrcweir void ScVbaButton::implSetDefaultProperties() throw (uno::RuntimeException)
536cdf0e10cSrcweir {
537cdf0e10cSrcweir setCaption( getName() );
538cdf0e10cSrcweir }
539cdf0e10cSrcweir
540cdf0e10cSrcweir // ============================================================================
541