xref: /aoo41x/main/sc/source/ui/vba/vbasheetobjects.cxx (revision cdf0e10c)
1 /*************************************************************************
2  *
3  * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
4  *
5  * Copyright 2000, 2010 Oracle and/or its affiliates.
6  *
7  * OpenOffice.org - a multi-platform office productivity suite
8  *
9  * This file is part of OpenOffice.org.
10  *
11  * OpenOffice.org is free software: you can redistribute it and/or modify
12  * it under the terms of the GNU Lesser General Public License version 3
13  * only, as published by the Free Software Foundation.
14  *
15  * OpenOffice.org is distributed in the hope that it will be useful,
16  * but WITHOUT ANY WARRANTY; without even the implied warranty of
17  * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
18  * GNU Lesser General Public License version 3 for more details
19  * (a copy is included in the LICENSE file that accompanied this code).
20  *
21  * You should have received a copy of the GNU Lesser General Public License
22  * version 3 along with OpenOffice.org.  If not, see
23  * <http://www.openoffice.org/license.html>
24  * for a copy of the LGPLv3 License.
25  *
26  ************************************************************************/
27 
28 #include "vbasheetobjects.hxx"
29 #include <vector>
30 #include <rtl/math.hxx>
31 #include <com/sun/star/beans/XPropertySet.hpp>
32 #include <com/sun/star/container/XIndexContainer.hpp>
33 #include <com/sun/star/container/XNamed.hpp>
34 #include <com/sun/star/drawing/XControlShape.hpp>
35 #include <com/sun/star/drawing/XDrawPageSupplier.hpp>
36 #include <com/sun/star/drawing/XShapes.hpp>
37 #include <com/sun/star/form/FormComponentType.hpp>
38 #include <com/sun/star/form/XForm.hpp>
39 #include <com/sun/star/form/XFormComponent.hpp>
40 #include <com/sun/star/form/XFormsSupplier.hpp>
41 #include <oox/helper/helper.hxx>
42 #include "vbasheetobject.hxx"
43 
44 using ::rtl::OUString;
45 using namespace ::com::sun::star;
46 using namespace ::ooo::vba;
47 
48 // ============================================================================
49 
50 namespace {
51 
52 template< typename Type >
53 inline bool lclGetProperty( Type& orValue, const uno::Reference< beans::XPropertySet >& rxPropSet, const OUString& rPropName )
54 {
55     try
56     {
57         return rxPropSet->getPropertyValue( rPropName ) >>= orValue;
58     }
59     catch( uno::Exception& )
60     {
61     }
62     return false;
63 }
64 
65 /** Rounds the passed value to a multiple of 0.75 and converts it to 1/100 mm. */
66 inline double lclPointsToHmm( const uno::Any& rPoints ) throw (uno::RuntimeException)
67 {
68     return PointsToHmm( ::rtl::math::approxFloor( rPoints.get< double >() / 0.75 ) * 0.75 );
69 }
70 
71 } // namespace
72 
73 // ============================================================================
74 // Base implementations
75 // ============================================================================
76 
77 /** Container for a specific type of drawing object in a spreadsheet.
78 
79     Derived classes provide all required functionality specific to the type of
80     shapes covered by the container.
81  */
82 class ScVbaObjectContainer : public ::cppu::WeakImplHelper1< container::XIndexAccess >
83 {
84 public:
85     explicit ScVbaObjectContainer(
86         const uno::Reference< XHelperInterface >& rxParent,
87         const uno::Reference< uno::XComponentContext >& rxContext,
88         const uno::Reference< frame::XModel >& rxModel,
89         const uno::Reference< sheet::XSpreadsheet >& rxSheet,
90         const uno::Type& rVbaType ) throw (uno::RuntimeException);
91 
92     /** Returns the VBA helper interface of the VBA collection object. */
93     inline const uno::Reference< XHelperInterface >& getParent() const { return mxParent; }
94     /** Returns the component context of the VBA collection object. */
95     inline const uno::Reference< uno::XComponentContext >& getContext() const { return mxContext; }
96     /** Returns the VBA type information of the objects in this container. */
97     inline const uno::Type& getVbaType() const { return maVbaType; }
98 
99     /** Collects all shapes supported by this instance and inserts them into
100         the internal shape vector. */
101     void collectShapes() throw (uno::RuntimeException);
102     /** Creates and returns a new UNO shape. */
103     uno::Reference< drawing::XShape > createShape( const awt::Point& rPos, const awt::Size& rSize ) throw (uno::RuntimeException);
104     /** Inserts the passed shape into the draw page and into this container, and returns its index in the draw page. */
105     sal_Int32 insertShape( const uno::Reference< drawing::XShape >& rxShape ) throw (uno::RuntimeException);
106     /** Creates and returns a new VBA implementation object for the passed shape. */
107     ::rtl::Reference< ScVbaSheetObjectBase > createVbaObject( const uno::Reference< drawing::XShape >& rxShape ) throw (uno::RuntimeException);
108     /** Creates and returns a new VBA implementation object for the passed shape in an Any. */
109     uno::Any createCollectionObject( const uno::Any& rSource ) throw (uno::RuntimeException);
110     /** Returns the VBA implementation object with the specified name. */
111     uno::Any getItemByStringIndex( const OUString& rIndex ) throw (uno::RuntimeException);
112 
113     // XIndexAccess
114     virtual sal_Int32 SAL_CALL getCount() throw (uno::RuntimeException);
115     virtual uno::Any SAL_CALL getByIndex( sal_Int32 nIndex ) throw (lang::IndexOutOfBoundsException, lang::WrappedTargetException, uno::RuntimeException);
116 
117     // XElementAccess
118     virtual uno::Type SAL_CALL getElementType() throw (uno::RuntimeException);
119     virtual sal_Bool SAL_CALL hasElements() throw (uno::RuntimeException);
120 
121 protected:
122     /** Derived classes return true, if the passed shape is supported by the instance. */
123     virtual bool implPickShape( const uno::Reference< drawing::XShape >& rxShape ) const = 0;
124     /** Derived classes create and return a new VBA implementation object for the passed shape. */
125     virtual ScVbaSheetObjectBase* implCreateVbaObject( const uno::Reference< drawing::XShape >& rxShape ) throw (uno::RuntimeException) = 0;
126     /** Derived classes return the service name of the UNO shape. */
127     virtual OUString implGetShapeServiceName() const = 0;
128 
129     /** Returns the shape name via 'Name' property of the UNO shape. May be overwritten. */
130     virtual OUString implGetShapeName( const uno::Reference< drawing::XShape >& rxShape ) const throw (uno::RuntimeException);
131     /** Is called when a new UNO shape has been created but not yet inserted into the drawing page. */
132     virtual void implOnShapeCreated( const uno::Reference< drawing::XShape >& rxShape ) throw (uno::RuntimeException);
133     /** Is called when a new UNO shape has been inserted into the drawing page. */
134     virtual void implOnShapeInserted( const uno::Reference< drawing::XShape >& rxShape ) throw (uno::RuntimeException);
135 
136 protected:
137     uno::Reference< XHelperInterface > mxParent;
138     uno::Reference< uno::XComponentContext > mxContext;
139     uno::Reference< frame::XModel > mxModel;
140     uno::Reference< lang::XMultiServiceFactory > mxFactory;
141     uno::Reference< drawing::XShapes > mxShapes;
142 
143 private:
144     typedef ::std::vector< uno::Reference< drawing::XShape > > ShapeVector;
145     const uno::Type maVbaType;
146     ShapeVector maShapes;
147 };
148 
149 // ----------------------------------------------------------------------------
150 
151 ScVbaObjectContainer::ScVbaObjectContainer(
152         const uno::Reference< XHelperInterface >& rxParent,
153         const uno::Reference< uno::XComponentContext >& rxContext,
154         const uno::Reference< frame::XModel >& rxModel,
155         const uno::Reference< sheet::XSpreadsheet >& rxSheet,
156         const uno::Type& rVbaType ) throw (uno::RuntimeException) :
157     mxParent( rxParent ),
158     mxContext( rxContext ),
159     mxModel( rxModel, uno::UNO_SET_THROW ),
160     mxFactory( rxModel, uno::UNO_QUERY_THROW ),
161     maVbaType( rVbaType )
162 {
163     uno::Reference< drawing::XDrawPageSupplier > xDrawPageSupp( rxSheet, uno::UNO_QUERY_THROW );
164     mxShapes.set( xDrawPageSupp->getDrawPage(), uno::UNO_QUERY_THROW );
165 }
166 
167 void ScVbaObjectContainer::collectShapes() throw (uno::RuntimeException)
168 {
169     maShapes.clear();
170     for( sal_Int32 nIndex = 0, nCount = mxShapes->getCount(); nIndex < nCount; ++nIndex )
171     {
172         uno::Reference< drawing::XShape > xShape( mxShapes->getByIndex( nIndex ), uno::UNO_QUERY_THROW );
173         if( implPickShape( xShape ) )
174             maShapes.push_back( xShape );
175     }
176 }
177 
178 uno::Reference< drawing::XShape > ScVbaObjectContainer::createShape( const awt::Point& rPos, const awt::Size& rSize ) throw (uno::RuntimeException)
179 {
180     uno::Reference< drawing::XShape > xShape( mxFactory->createInstance( implGetShapeServiceName() ), uno::UNO_QUERY_THROW );
181     xShape->setPosition( rPos );
182     xShape->setSize( rSize );
183     implOnShapeCreated( xShape );
184     return xShape;
185 }
186 
187 sal_Int32 ScVbaObjectContainer::insertShape( const uno::Reference< drawing::XShape >& rxShape ) throw (uno::RuntimeException)
188 {
189     mxShapes->add( rxShape );
190     maShapes.push_back( rxShape );
191     implOnShapeInserted( rxShape );
192     return mxShapes->getCount() - 1;
193 }
194 
195 ::rtl::Reference< ScVbaSheetObjectBase > ScVbaObjectContainer::createVbaObject(
196     const uno::Reference< drawing::XShape >& rxShape ) throw (uno::RuntimeException)
197 {
198     return implCreateVbaObject( rxShape );
199 }
200 
201 uno::Any ScVbaObjectContainer::createCollectionObject( const uno::Any& rSource ) throw (uno::RuntimeException)
202 {
203     uno::Reference< drawing::XShape > xShape( rSource, uno::UNO_QUERY_THROW );
204     uno::Reference< excel::XSheetObject > xSheetObject( implCreateVbaObject( xShape ) );
205     return uno::Any( xSheetObject );
206 }
207 
208 uno::Any ScVbaObjectContainer::getItemByStringIndex( const OUString& rIndex ) throw (uno::RuntimeException)
209 {
210     for( ShapeVector::iterator aIt = maShapes.begin(), aEnd = maShapes.end(); aIt != aEnd; ++aIt )
211         if( rIndex == implGetShapeName( *aIt ) )
212             return createCollectionObject( uno::Any( *aIt ) );
213     throw uno::RuntimeException();
214 }
215 
216 // XIndexAccess
217 
218 sal_Int32 SAL_CALL ScVbaObjectContainer::getCount() throw (uno::RuntimeException)
219 {
220     return static_cast< sal_Int32 >( maShapes.size() );
221 }
222 
223 uno::Any SAL_CALL ScVbaObjectContainer::getByIndex( sal_Int32 nIndex )
224         throw (lang::IndexOutOfBoundsException, lang::WrappedTargetException, uno::RuntimeException)
225 {
226     if( (0 <= nIndex) && (nIndex < getCount()) )
227         return uno::Any( maShapes[ static_cast< size_t >( nIndex ) ] );
228     throw lang::IndexOutOfBoundsException();
229 }
230 
231 // XElementAccess
232 
233 uno::Type SAL_CALL ScVbaObjectContainer::getElementType() throw (uno::RuntimeException)
234 {
235     return drawing::XShape::static_type( 0 );
236 }
237 
238 sal_Bool SAL_CALL ScVbaObjectContainer::hasElements() throw (uno::RuntimeException)
239 {
240     return !maShapes.empty();
241 }
242 
243 // private
244 
245 OUString ScVbaObjectContainer::implGetShapeName( const uno::Reference< drawing::XShape >& rxShape ) const throw (uno::RuntimeException)
246 {
247     uno::Reference< beans::XPropertySet > xPropSet( rxShape, uno::UNO_QUERY_THROW );
248     return xPropSet->getPropertyValue( CREATE_OUSTRING( "Name" ) ).get< OUString >();
249 }
250 
251 void ScVbaObjectContainer::implOnShapeCreated( const uno::Reference< drawing::XShape >& /*rxShape*/ ) throw (uno::RuntimeException)
252 {
253 }
254 
255 void ScVbaObjectContainer::implOnShapeInserted( const uno::Reference< drawing::XShape >& /*rxShape*/ ) throw (uno::RuntimeException)
256 {
257 }
258 
259 // ============================================================================
260 
261 class ScVbaObjectEnumeration : public SimpleEnumerationBase
262 {
263 public:
264     explicit ScVbaObjectEnumeration( const ScVbaObjectContainerRef& rxContainer );
265     virtual uno::Any createCollectionObject( const uno::Any& rSource );
266 
267 private:
268     ScVbaObjectContainerRef mxContainer;
269 };
270 
271 // ----------------------------------------------------------------------------
272 
273 ScVbaObjectEnumeration::ScVbaObjectEnumeration( const ScVbaObjectContainerRef& rxContainer ) :
274     SimpleEnumerationBase( rxContainer->getParent(), rxContainer->getContext(), rxContainer.get() ),
275     mxContainer( rxContainer )
276 {
277 }
278 
279 uno::Any ScVbaObjectEnumeration::createCollectionObject( const uno::Any& rSource )
280 {
281     return mxContainer->createCollectionObject( rSource );
282 }
283 
284 // ============================================================================
285 
286 ScVbaSheetObjectsBase::ScVbaSheetObjectsBase( const ScVbaObjectContainerRef& rxContainer ) throw (css::uno::RuntimeException) :
287     ScVbaSheetObjects_BASE( rxContainer->getParent(), rxContainer->getContext(), rxContainer.get() ),
288     mxContainer( rxContainer )
289 {
290     mxContainer->collectShapes();
291 }
292 
293 ScVbaSheetObjectsBase::~ScVbaSheetObjectsBase()
294 {
295 }
296 
297 void ScVbaSheetObjectsBase::collectShapes() throw (uno::RuntimeException)
298 {
299     mxContainer->collectShapes();
300 }
301 
302 // XEnumerationAccess
303 
304 uno::Reference< container::XEnumeration > SAL_CALL ScVbaSheetObjectsBase::createEnumeration() throw (uno::RuntimeException)
305 {
306     return new ScVbaObjectEnumeration( mxContainer );
307 }
308 
309 // XElementAccess
310 
311 uno::Type SAL_CALL ScVbaSheetObjectsBase::getElementType() throw (uno::RuntimeException)
312 {
313     return mxContainer->getVbaType();
314 }
315 
316 // ScVbaCollectionBase
317 
318 uno::Any ScVbaSheetObjectsBase::createCollectionObject( const uno::Any& rSource )
319 {
320     return mxContainer->createCollectionObject( rSource );
321 }
322 
323 uno::Any ScVbaSheetObjectsBase::getItemByStringIndex( const OUString& rIndex ) throw (uno::RuntimeException)
324 {
325     return mxContainer->getItemByStringIndex( rIndex );
326 }
327 
328 // ============================================================================
329 // Graphic object containers supporting ooo.vba.excel.XGraphicObject
330 // ============================================================================
331 
332 ScVbaGraphicObjectsBase::ScVbaGraphicObjectsBase( const ScVbaObjectContainerRef& rxContainer ) throw (uno::RuntimeException) :
333     ScVbaGraphicObjects_BASE( rxContainer )
334 {
335 }
336 
337 // XGraphicObjects
338 
339 uno::Any SAL_CALL ScVbaGraphicObjectsBase::Add( const uno::Any& rLeft, const uno::Any& rTop, const uno::Any& rWidth, const uno::Any& rHeight ) throw (uno::RuntimeException)
340 {
341     /*  Extract double values from passed Anys (the lclPointsToHmm() helper
342         function will throw a RuntimeException on any error), and convert from
343         points to 1/100 mm. */
344     awt::Point aPos( lclPointsToHmm( rLeft ), lclPointsToHmm( rTop ) );
345     awt::Size aSize( lclPointsToHmm( rWidth ), lclPointsToHmm( rHeight ) );
346     // TODO: translate coordinates for RTL sheets
347     if( (aPos.X < 0) || (aPos.Y < 0) || (aSize.Width <= 0) || (aSize.Height <= 0) )
348         throw uno::RuntimeException();
349 
350     // create the UNO shape
351     uno::Reference< drawing::XShape > xShape( mxContainer->createShape( aPos, aSize ), uno::UNO_SET_THROW );
352     sal_Int32 nIndex = mxContainer->insertShape( xShape );
353 
354     // create and return the VBA object
355     ::rtl::Reference< ScVbaSheetObjectBase > xVbaObject = mxContainer->createVbaObject( xShape );
356     xVbaObject->setDefaultProperties( nIndex );
357     return uno::Any( uno::Reference< excel::XSheetObject >( xVbaObject.get() ) );
358 }
359 
360 // ============================================================================
361 // Drawing controls
362 // ============================================================================
363 
364 class ScVbaControlContainer : public ScVbaObjectContainer
365 {
366 public:
367     explicit ScVbaControlContainer(
368         const uno::Reference< XHelperInterface >& rxParent,
369         const uno::Reference< uno::XComponentContext >& rxContext,
370         const uno::Reference< frame::XModel >& rxModel,
371         const uno::Reference< sheet::XSpreadsheet >& rxSheet,
372         const uno::Type& rVbaType,
373         const OUString& rModelServiceName,
374         sal_Int16 nComponentType ) throw (uno::RuntimeException);
375 
376 protected:
377     uno::Reference< container::XIndexContainer > createForm() throw (uno::RuntimeException);
378 
379     virtual bool implPickShape( const uno::Reference< drawing::XShape >& rxShape ) const;
380     virtual OUString implGetShapeServiceName() const;
381     virtual bool implCheckProperties( const uno::Reference< beans::XPropertySet >& rxModelProps ) const;
382     virtual OUString implGetShapeName( const uno::Reference< drawing::XShape >& rxShape ) const throw (uno::RuntimeException);
383     virtual void implOnShapeCreated( const uno::Reference< drawing::XShape >& rxShape ) throw (uno::RuntimeException);
384 
385 protected:
386     uno::Reference< container::XIndexContainer > mxFormIC;
387     OUString maModelServiceName;
388     sal_Int16 mnComponentType;
389 };
390 
391 // ----------------------------------------------------------------------------
392 
393 ScVbaControlContainer::ScVbaControlContainer(
394         const uno::Reference< XHelperInterface >& rxParent,
395         const uno::Reference< uno::XComponentContext >& rxContext,
396         const uno::Reference< frame::XModel >& rxModel,
397         const uno::Reference< sheet::XSpreadsheet >& rxSheet,
398         const uno::Type& rVbaType,
399         const OUString& rModelServiceName,
400         sal_Int16 nComponentType ) throw (uno::RuntimeException) :
401     ScVbaObjectContainer( rxParent, rxContext, rxModel, rxSheet, rVbaType ),
402     maModelServiceName( rModelServiceName ),
403     mnComponentType( nComponentType )
404 {
405 }
406 
407 uno::Reference< container::XIndexContainer > ScVbaControlContainer::createForm() throw (uno::RuntimeException)
408 {
409     if( !mxFormIC.is() )
410     {
411         uno::Reference< form::XFormsSupplier > xFormsSupp( mxShapes, uno::UNO_QUERY_THROW );
412         uno::Reference< container::XNameContainer > xFormsNC( xFormsSupp->getForms(), uno::UNO_SET_THROW );
413         OUString aFormName = CREATE_OUSTRING( "Standard" );
414         if( xFormsNC->hasByName( aFormName ) )
415         {
416             mxFormIC.set( xFormsNC->getByName( aFormName ), uno::UNO_QUERY_THROW );
417         }
418         else
419         {
420             uno::Reference< form::XForm > xForm( mxFactory->createInstance( CREATE_OUSTRING( "com.sun.star.form.component.Form" ) ), uno::UNO_QUERY_THROW );
421             xFormsNC->insertByName( aFormName, uno::Any( xForm ) );
422             mxFormIC.set( xForm, uno::UNO_QUERY_THROW );
423         }
424     }
425     return mxFormIC;
426 }
427 
428 bool ScVbaControlContainer::implPickShape( const uno::Reference< drawing::XShape >& rxShape ) const
429 {
430     try
431     {
432         uno::Reference< drawing::XControlShape > xControlShape( rxShape, uno::UNO_QUERY_THROW );
433         uno::Reference< beans::XPropertySet > xModelProps( xControlShape->getControl(), uno::UNO_QUERY_THROW );
434         sal_Int16 nClassId = -1;
435         return lclGetProperty( nClassId, xModelProps, CREATE_OUSTRING( "ClassId" ) ) &&
436             (nClassId == mnComponentType) && implCheckProperties( xModelProps );
437     }
438     catch( uno::Exception& )
439     {
440     }
441     return false;
442 }
443 
444 OUString ScVbaControlContainer::implGetShapeServiceName() const
445 {
446     return CREATE_OUSTRING( "com.sun.star.drawing.ControlShape" );
447 }
448 
449 bool ScVbaControlContainer::implCheckProperties( const uno::Reference< beans::XPropertySet >& /*rxModelProps*/ ) const
450 {
451     return true;
452 }
453 
454 OUString ScVbaControlContainer::implGetShapeName( const uno::Reference< drawing::XShape >& rxShape ) const throw (uno::RuntimeException)
455 {
456     uno::Reference< drawing::XControlShape > xControlShape( rxShape, uno::UNO_QUERY_THROW );
457     return uno::Reference< container::XNamed >( xControlShape->getControl(), uno::UNO_QUERY_THROW )->getName();
458 }
459 
460 void ScVbaControlContainer::implOnShapeCreated( const uno::Reference< drawing::XShape >& rxShape ) throw (uno::RuntimeException)
461 {
462     // passed shape must be a control shape
463     uno::Reference< drawing::XControlShape > xControlShape( rxShape, uno::UNO_QUERY_THROW );
464 
465     // create the UNO control model
466     uno::Reference< form::XFormComponent > xFormComponent( mxFactory->createInstance( maModelServiceName ), uno::UNO_QUERY_THROW );
467     uno::Reference< awt::XControlModel > xControlModel( xFormComponent, uno::UNO_QUERY_THROW );
468 
469     // insert the control model into the form and the shape
470     createForm();
471     mxFormIC->insertByIndex( mxFormIC->getCount(), uno::Any( xFormComponent ) );
472     xControlShape->setControl( xControlModel );
473 }
474 
475 // ============================================================================
476 // Push button
477 // ============================================================================
478 
479 class ScVbaButtonContainer : public ScVbaControlContainer
480 {
481 public:
482     explicit ScVbaButtonContainer(
483         const uno::Reference< XHelperInterface >& rxParent,
484         const uno::Reference< uno::XComponentContext >& rxContext,
485         const uno::Reference< frame::XModel >& rxModel,
486         const uno::Reference< sheet::XSpreadsheet >& rxSheet ) throw (uno::RuntimeException);
487 
488 protected:
489     virtual ScVbaSheetObjectBase* implCreateVbaObject( const uno::Reference< drawing::XShape >& rxShape ) throw (uno::RuntimeException);
490     virtual bool implCheckProperties( const uno::Reference< beans::XPropertySet >& rxModelProps ) const;
491 };
492 
493 // ----------------------------------------------------------------------------
494 
495 ScVbaButtonContainer::ScVbaButtonContainer(
496         const uno::Reference< XHelperInterface >& rxParent,
497         const uno::Reference< uno::XComponentContext >& rxContext,
498         const uno::Reference< frame::XModel >& rxModel,
499         const uno::Reference< sheet::XSpreadsheet >& rxSheet ) throw (uno::RuntimeException) :
500     ScVbaControlContainer(
501         rxParent, rxContext, rxModel, rxSheet,
502         excel::XButton::static_type( 0 ),
503         CREATE_OUSTRING( "com.sun.star.form.component.CommandButton" ),
504         form::FormComponentType::COMMANDBUTTON )
505 {
506 }
507 
508 ScVbaSheetObjectBase* ScVbaButtonContainer::implCreateVbaObject( const uno::Reference< drawing::XShape >& rxShape ) throw (uno::RuntimeException)
509 {
510     uno::Reference< drawing::XControlShape > xControlShape( rxShape, uno::UNO_QUERY_THROW );
511     return new ScVbaButton( mxParent, mxContext, mxModel, createForm(), xControlShape );
512 }
513 
514 bool ScVbaButtonContainer::implCheckProperties( const uno::Reference< beans::XPropertySet >& rxModelProps ) const
515 {
516     // do not insert toggle buttons into the 'Buttons' collection
517     bool bToggle = false;
518     return lclGetProperty( bToggle, rxModelProps, CREATE_OUSTRING( "Toggle" ) ) && !bToggle;
519 }
520 
521 // ============================================================================
522 
523 ScVbaButtons::ScVbaButtons(
524         const uno::Reference< XHelperInterface >& rxParent,
525         const uno::Reference< uno::XComponentContext >& rxContext,
526         const uno::Reference< frame::XModel >& rxModel,
527         const uno::Reference< sheet::XSpreadsheet >& rxSheet ) throw (uno::RuntimeException) :
528     ScVbaGraphicObjectsBase( new ScVbaButtonContainer( rxParent, rxContext, rxModel, rxSheet ) )
529 {
530 }
531 
532 VBAHELPER_IMPL_XHELPERINTERFACE( ScVbaButtons, "ooo.vba.excel.Buttons" )
533 
534 // ============================================================================
535