xref: /trunk/main/sc/source/ui/vba/vbaworksheet.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 <vbahelper/helperdecl.hxx>
29 #include <cppuhelper/queryinterface.hxx>
30 
31 #include "vbaworksheet.hxx"
32 
33 #include <com/sun/star/beans/XPropertySet.hpp>
34 #include <com/sun/star/beans/XIntrospectionAccess.hpp>
35 #include <com/sun/star/beans/XIntrospection.hpp>
36 #include <com/sun/star/container/XNamed.hpp>
37 #include <com/sun/star/util/XProtectable.hpp>
38 #include <com/sun/star/table/XCellRange.hpp>
39 #include <com/sun/star/sheet/XSpreadsheetView.hpp>
40 #include <com/sun/star/sheet/XSpreadsheetDocument.hpp>
41 #include <com/sun/star/sheet/XCalculatable.hpp>
42 #include <com/sun/star/sheet/XCellRangeAddressable.hpp>
43 #include <com/sun/star/sheet/XCellRangeReferrer.hpp>
44 #include <com/sun/star/sheet/XSheetCellRange.hpp>
45 #include <com/sun/star/sheet/XSheetCellCursor.hpp>
46 #include <com/sun/star/sheet/XSheetAnnotationsSupplier.hpp>
47 #include <com/sun/star/sheet/XUsedAreaCursor.hpp>
48 #include <com/sun/star/sheet/XSpreadsheets.hpp>
49 #include <com/sun/star/sheet/XSheetPastable.hpp>
50 #include <com/sun/star/sheet/XCellAddressable.hpp>
51 #include <com/sun/star/sheet/XSheetOutline.hpp>
52 #include <com/sun/star/sheet/XSheetPageBreak.hpp>
53 #include <com/sun/star/sheet/XDataPilotTablesSupplier.hpp>
54 #include <com/sun/star/sheet/XNamedRanges.hpp>
55 #include <com/sun/star/util/XURLTransformer.hpp>
56 #include <com/sun/star/frame/XDispatchProvider.hpp>
57 #include <com/sun/star/frame/XComponentLoader.hpp>
58 #include <com/sun/star/table/XColumnRowRange.hpp>
59 #include <com/sun/star/table/XTableChartsSupplier.hpp>
60 #include <com/sun/star/drawing/XDrawPageSupplier.hpp>
61 #include <com/sun/star/drawing/XControlShape.hpp>
62 #include <com/sun/star/form/FormComponentType.hpp>
63 #include <com/sun/star/form/XFormsSupplier.hpp>
64 #include <ooo/vba/excel/XlEnableSelection.hpp>
65 #include <ooo/vba/excel/XlSheetVisibility.hpp>
66 #include <ooo/vba/excel/XWorkbook.hpp>
67 #include <ooo/vba/XControlProvider.hpp>
68 
69 #include <comphelper/processfactory.hxx>
70 #include <vbahelper/vbashapes.hxx>
71 
72 #include <tools/string.hxx>
73 
74 //zhangyun showdataform
75 #include <sfx2/sfxdlg.hxx>
76 #include "scabstdlg.hxx"
77 #include "tabvwsh.hxx"
78 #include "scitems.hxx"
79 
80 #include <svx/svdouno.hxx>
81 #include <svx/svdpage.hxx>
82 
83 #include "cellsuno.hxx"
84 #include "drwlayer.hxx"
85 
86 #include "scextopt.hxx"
87 #include "vbaoutline.hxx"
88 #include "vbarange.hxx"
89 #include "vbacomments.hxx"
90 #include "vbachartobjects.hxx"
91 #include "vbapivottables.hxx"
92 #include "vbaoleobject.hxx"
93 #include "vbaoleobjects.hxx"
94 #include "vbapagesetup.hxx"
95 #include "vbapagebreaks.hxx"
96 #include "vbaworksheets.hxx"
97 #include "vbahyperlinks.hxx"
98 #include "vbasheetobjects.hxx"
99 #include "vbanames.hxx"
100 
101 #define STANDARDWIDTH 2267
102 #define STANDARDHEIGHT 427
103 #define DOESNOTEXIST -1
104 
105 using namespace com::sun::star;
106 using namespace ooo::vba;
107 
108 static void getNewSpreadsheetName (rtl::OUString &aNewName, rtl::OUString aOldName, uno::Reference <sheet::XSpreadsheetDocument>& xSpreadDoc )
109 {
110 	if (!xSpreadDoc.is())
111 		throw lang::IllegalArgumentException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "getNewSpreadsheetName() xSpreadDoc is null" ) ), uno::Reference< uno::XInterface  >(), 1 );
112 	static rtl::OUString aUnderScre( RTL_CONSTASCII_USTRINGPARAM( "_" ) );
113 	int currentNum =2;
114 	aNewName = aOldName + aUnderScre+ String::CreateFromInt32(currentNum) ;
115 	SCTAB nTab = 0;
116 	while ( ScVbaWorksheets::nameExists(xSpreadDoc,aNewName, nTab ) )
117 	{
118 		aNewName = aOldName + aUnderScre +
119 		String::CreateFromInt32(++currentNum) ;
120 	}
121 }
122 
123 static void removeAllSheets( uno::Reference <sheet::XSpreadsheetDocument>& xSpreadDoc, rtl::OUString aSheetName)
124 {
125 	if (!xSpreadDoc.is())
126 		throw lang::IllegalArgumentException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "removeAllSheets() xSpreadDoc is null" ) ), uno::Reference< uno::XInterface  >(), 1 );
127 	uno::Reference<sheet::XSpreadsheets> xSheets = xSpreadDoc->getSheets();
128 	uno::Reference <container::XIndexAccess> xIndex( xSheets, uno::UNO_QUERY );
129 
130 	if ( xIndex.is() )
131 	{
132 		uno::Reference<container::XNameContainer> xNameContainer(xSheets,uno::UNO_QUERY_THROW);
133 		for (sal_Int32 i = xIndex->getCount() -1; i>= 1; i--)
134 		{
135 			uno::Reference< sheet::XSpreadsheet > xSheet(xIndex->getByIndex(i), uno::UNO_QUERY);
136 			uno::Reference< container::XNamed > xNamed( xSheet, uno::UNO_QUERY_THROW );
137 			if (xNamed.is())
138 			{
139 				xNameContainer->removeByName(xNamed->getName());
140 			}
141 		}
142 
143 		uno::Reference< sheet::XSpreadsheet > xSheet(xIndex->getByIndex(0), uno::UNO_QUERY);
144         uno::Reference< container::XNamed > xNamed( xSheet, uno::UNO_QUERY_THROW );
145 		if (xNamed.is())
146 		{
147 			xNamed->setName(aSheetName);
148 		}
149 	}
150 }
151 
152 static uno::Reference<frame::XModel>
153 openNewDoc(rtl::OUString aSheetName )
154 {
155 	uno::Reference<frame::XModel> xModel;
156 	try
157 	{
158 		uno::Reference< beans::XPropertySet > xProps( ::comphelper::getProcessServiceFactory(), uno::UNO_QUERY_THROW );
159 		uno::Reference< uno::XComponentContext > xContext(  xProps->getPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "DefaultContext" ))), uno::UNO_QUERY_THROW );
160 		uno::Reference<lang::XMultiComponentFactory > xServiceManager(
161 										xContext->getServiceManager(), uno::UNO_QUERY_THROW );
162 
163 		uno::Reference <frame::XComponentLoader > xComponentLoader(
164 						xServiceManager->createInstanceWithContext(
165 						rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "com.sun.star.frame.Desktop" ) ),
166 						xContext ), uno::UNO_QUERY_THROW );
167 
168 		uno::Reference<lang::XComponent > xComponent( xComponentLoader->loadComponentFromURL(
169 				rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "private:factory/scalc" ) ),
170 				rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "_blank" ) ), 0,
171 				uno::Sequence < ::com::sun::star::beans::PropertyValue >() ) );
172 		uno::Reference <sheet::XSpreadsheetDocument> xSpreadDoc( xComponent, uno::UNO_QUERY_THROW );
173 		if ( xSpreadDoc.is() )
174 		{
175 			removeAllSheets(xSpreadDoc,aSheetName);
176 		}
177 		xModel.set(xSpreadDoc,uno::UNO_QUERY_THROW);
178 	}
179 	catch ( uno::Exception & /*e*/ )
180 	{
181 	}
182 	return xModel;
183 }
184 
185 ScVbaWorksheet::ScVbaWorksheet( const uno::Reference< XHelperInterface >& xParent, const uno::Reference< uno::XComponentContext >& xContext ) : WorksheetImpl_BASE( xParent, xContext ), mbVeryHidden( false )
186 {
187 }
188 
189 ScVbaWorksheet::ScVbaWorksheet(const uno::Reference< XHelperInterface >& xParent, const uno::Reference< uno::XComponentContext >& xContext,
190 		const uno::Reference< sheet::XSpreadsheet >& xSheet,
191 		const uno::Reference< frame::XModel >& xModel ) throw (uno::RuntimeException) : WorksheetImpl_BASE( xParent, xContext ), mxSheet( xSheet ), mxModel(xModel), mbVeryHidden( false )
192 {
193 }
194 
195 ScVbaWorksheet::ScVbaWorksheet( uno::Sequence< uno::Any> const & args,
196     uno::Reference< uno::XComponentContext> const & xContext ) throw ( lang::IllegalArgumentException ) :  WorksheetImpl_BASE( getXSomethingFromArgs< XHelperInterface >( args, 0 ), xContext ), mxModel( getXSomethingFromArgs< frame::XModel >( args, 1 ) ), mbVeryHidden( false )
197 {
198 	if ( args.getLength() < 3 )
199 		throw lang::IllegalArgumentException();
200 
201 	rtl::OUString sSheetName;
202 	args[2] >>= sSheetName;
203 
204 	uno::Reference< sheet::XSpreadsheetDocument > xSpreadDoc( mxModel, uno::UNO_QUERY_THROW );
205 	uno::Reference< container::XNameAccess > xNameAccess( xSpreadDoc->getSheets(), uno::UNO_QUERY_THROW );
206 	mxSheet.set( xNameAccess->getByName( sSheetName ), uno::UNO_QUERY_THROW );
207 }
208 
209 ScVbaWorksheet::~ScVbaWorksheet()
210 {
211 }
212 
213 ::rtl::OUString
214 ScVbaWorksheet::getName() throw (uno::RuntimeException)
215 {
216 	uno::Reference< container::XNamed > xNamed( getSheet(), uno::UNO_QUERY_THROW );
217 	return xNamed->getName();
218 }
219 
220 void
221 ScVbaWorksheet::setName(const ::rtl::OUString &rName ) throw (uno::RuntimeException)
222 {
223 	uno::Reference< container::XNamed > xNamed( getSheet(), uno::UNO_QUERY_THROW );
224 	xNamed->setName( rName );
225 }
226 
227 sal_Int32
228 ScVbaWorksheet::getVisible() throw (uno::RuntimeException)
229 {
230 	uno::Reference< beans::XPropertySet > xProps( getSheet(), uno::UNO_QUERY_THROW );
231 	bool bVisible = false;
232 	xProps->getPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "IsVisible" ) ) ) >>= bVisible;
233 	using namespace ::ooo::vba::excel::XlSheetVisibility;
234 	return bVisible ? xlSheetVisible : (mbVeryHidden ? xlSheetVeryHidden : xlSheetHidden);
235 }
236 
237 void
238 ScVbaWorksheet::setVisible( sal_Int32 nVisible ) throw (uno::RuntimeException)
239 {
240     using namespace ::ooo::vba::excel::XlSheetVisibility;
241     bool bVisible = true;
242     switch( nVisible )
243     {
244         case xlSheetVisible: case 1:  // Excel accepts -1 and 1 for visible sheets
245             bVisible = true;
246             mbVeryHidden = false;
247         break;
248         case xlSheetHidden:
249             bVisible = false;
250             mbVeryHidden = false;
251         break;
252         case xlSheetVeryHidden:
253             bVisible = false;
254             mbVeryHidden = true;
255         break;
256         default:
257             throw uno::RuntimeException();
258     }
259 	uno::Reference< beans::XPropertySet > xProps( getSheet(), uno::UNO_QUERY_THROW );
260 	xProps->setPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "IsVisible" ) ), uno::Any( bVisible ) );
261 }
262 
263 sal_Int16
264 ScVbaWorksheet::getIndex() throw (uno::RuntimeException)
265 {
266 	return getSheetID() + 1;
267 }
268 
269 sal_Int32
270 ScVbaWorksheet::getEnableSelection() throw (uno::RuntimeException)
271 {
272     uno::Reference <sheet::XSpreadsheetDocument> xSpreadDoc( getModel(), uno::UNO_QUERY_THROW );
273     SCTAB nTab = 0;
274     if ( ScVbaWorksheets::nameExists(xSpreadDoc, getName(), nTab) )
275     {
276         uno::Reference< frame::XModel > xModel( getModel(), uno::UNO_QUERY_THROW );
277         ScDocument* pDoc = excel::getDocShell( xModel )->GetDocument();
278         ScTableProtection* pProtect = pDoc->GetTabProtection(nTab);
279 		sal_Bool bLockedCells = sal_False;
280 		sal_Bool bUnlockedCells = sal_False;
281 		if( pProtect )
282 		{
283         	bLockedCells   = pProtect->isOptionEnabled(ScTableProtection::SELECT_LOCKED_CELLS);
284         	bUnlockedCells = pProtect->isOptionEnabled(ScTableProtection::SELECT_UNLOCKED_CELLS);
285 		}
286         if( bLockedCells )
287             return excel::XlEnableSelection::xlNoRestrictions;
288         if( bUnlockedCells )
289             return excel::XlEnableSelection::xlUnlockedCells;
290         return excel::XlEnableSelection::xlNoSelection;
291     }
292     else
293 		throw uno::RuntimeException(::rtl::OUString(
294                                 RTL_CONSTASCII_USTRINGPARAM( "Sheet Name does not exist. ") ),
295                                 uno::Reference< XInterface >() );
296     return excel::XlEnableSelection::xlNoSelection;
297 }
298 
299 
300 void
301 ScVbaWorksheet::setEnableSelection( sal_Int32 nSelection ) throw (uno::RuntimeException)
302 {
303     if( (nSelection != excel::XlEnableSelection::xlNoRestrictions) &&
304         (nSelection != excel::XlEnableSelection::xlUnlockedCells) &&
305         (nSelection != excel::XlEnableSelection::xlNoSelection) )
306     {
307         DebugHelper::exception(SbERR_BAD_PARAMETER, rtl::OUString() );
308     }
309 
310     uno::Reference <sheet::XSpreadsheetDocument> xSpreadDoc( getModel(), uno::UNO_QUERY_THROW );
311     SCTAB nTab = 0;
312     if ( ScVbaWorksheets::nameExists(xSpreadDoc, getName(), nTab) )
313     {
314         uno::Reference< frame::XModel > xModel( getModel(), uno::UNO_QUERY_THROW );
315         ScDocument* pDoc = excel::getDocShell( xModel )->GetDocument();
316         ScTableProtection* pProtect = pDoc->GetTabProtection(nTab);
317         // default is xlNoSelection
318         sal_Bool bLockedCells = sal_False;
319         sal_Bool bUnlockedCells = sal_False;
320         if( nSelection == excel::XlEnableSelection::xlNoRestrictions )
321         {
322             bLockedCells = sal_True;
323             bUnlockedCells = sal_True;
324         }
325         else if( nSelection == excel::XlEnableSelection::xlUnlockedCells )
326         {
327             bUnlockedCells = sal_True;
328         }
329 		if( pProtect )
330 		{
331         	pProtect->setOption( ScTableProtection::SELECT_LOCKED_CELLS, bLockedCells );
332         	pProtect->setOption( ScTableProtection::SELECT_UNLOCKED_CELLS, bUnlockedCells );
333 		}
334     }
335     else
336 		throw uno::RuntimeException(::rtl::OUString(
337                                 RTL_CONSTASCII_USTRINGPARAM( "Sheet Name does not exist. ") ),
338                                 uno::Reference< XInterface >() );
339 
340 }
341 
342 uno::Reference< beans::XPropertySet > ScVbaWorksheet::getFirstDBRangeProperties() throw (uno::RuntimeException)
343 {
344     uno::Reference< beans::XPropertySet > xModelProps( mxModel, uno::UNO_QUERY_THROW );
345     uno::Reference< container::XIndexAccess > xDBRangesIA( xModelProps->getPropertyValue(
346         ::rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "DatabaseRanges" ) ) ), uno::UNO_QUERY_THROW );
347 
348     for( sal_Int32 nIndex = 0, nCount = xDBRangesIA->getCount(); nIndex < nCount; ++nIndex )
349     {
350         uno::Reference< sheet::XCellRangeReferrer > xDBRange( xDBRangesIA->getByIndex( nIndex ), uno::UNO_QUERY_THROW );
351         // check if the database area is on this sheet
352         uno::Reference< sheet::XCellRangeAddressable > xRangeAddr( xDBRange->getReferredCells(), uno::UNO_QUERY_THROW );
353         if( getSheetID() == xRangeAddr->getRangeAddress().Sheet )
354             return uno::Reference< beans::XPropertySet >( xDBRange, uno::UNO_QUERY_THROW );
355     }
356     return uno::Reference< beans::XPropertySet >();
357 }
358 
359 sal_Bool SAL_CALL ScVbaWorksheet::getAutoFilterMode() throw (uno::RuntimeException)
360 {
361     uno::Reference< beans::XPropertySet > xDBRangeProps = getFirstDBRangeProperties();
362     sal_Bool bAutoFilterMode = sal_False;
363     return
364         xDBRangeProps.is() &&
365         (xDBRangeProps->getPropertyValue( ::rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "AutoFilter" ) ) ) >>= bAutoFilterMode) &&
366         bAutoFilterMode;
367 }
368 
369 void SAL_CALL ScVbaWorksheet::setAutoFilterMode( sal_Bool bAutoFilterMode ) throw (uno::RuntimeException)
370 {
371     uno::Reference< beans::XPropertySet > xDBRangeProps = getFirstDBRangeProperties();
372     if( xDBRangeProps.is() )
373         xDBRangeProps->setPropertyValue( ::rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "AutoFilter" ) ), uno::Any( bAutoFilterMode ) );
374 }
375 
376 uno::Reference< excel::XRange >
377 ScVbaWorksheet::getUsedRange() throw (uno::RuntimeException)
378 {
379  	uno::Reference< sheet::XSheetCellRange > xSheetCellRange(getSheet(), uno::UNO_QUERY_THROW );
380 	uno::Reference< sheet::XSheetCellCursor > xSheetCellCursor( getSheet()->createCursorByRange( xSheetCellRange ), uno::UNO_QUERY_THROW );
381 	uno::Reference<sheet::XUsedAreaCursor> xUsedCursor(xSheetCellCursor,uno::UNO_QUERY_THROW);
382 	xUsedCursor->gotoStartOfUsedArea( false );
383 	xUsedCursor->gotoEndOfUsedArea( true );
384 	uno::Reference< table::XCellRange > xRange( xSheetCellCursor, uno::UNO_QUERY);
385 	return new ScVbaRange(this, mxContext, xRange);
386 }
387 
388 uno::Reference< excel::XOutline >
389 ScVbaWorksheet::Outline( ) throw (uno::RuntimeException)
390 {
391 	uno::Reference<sheet::XSheetOutline> xOutline(getSheet(),uno::UNO_QUERY_THROW);
392 	return new ScVbaOutline( this, mxContext, xOutline);
393 }
394 
395 uno::Reference< excel::XPageSetup >
396 ScVbaWorksheet::PageSetup( ) throw (uno::RuntimeException)
397 {
398 	return new ScVbaPageSetup( this, mxContext, getSheet(), getModel() );
399 }
400 
401 uno::Any
402 ScVbaWorksheet::HPageBreaks( const uno::Any& aIndex ) throw (uno::RuntimeException)
403 {
404     uno::Reference< sheet::XSheetPageBreak > xSheetPageBreak(getSheet(),uno::UNO_QUERY_THROW);
405     uno::Reference< excel::XHPageBreaks > xHPageBreaks( new ScVbaHPageBreaks( this, mxContext, xSheetPageBreak));
406    if ( aIndex.hasValue() )
407       return xHPageBreaks->Item( aIndex, uno::Any());
408    return uno::makeAny( xHPageBreaks );
409 }
410 
411 uno::Any
412 ScVbaWorksheet::VPageBreaks( const uno::Any& aIndex ) throw ( uno::RuntimeException )
413 {
414 	uno::Reference< sheet::XSheetPageBreak > xSheetPageBreak( getSheet(), uno::UNO_QUERY_THROW );
415 	uno::Reference< excel::XVPageBreaks > xVPageBreaks( new ScVbaVPageBreaks( this, mxContext, xSheetPageBreak ) );
416 	if( aIndex.hasValue() )
417 		return xVPageBreaks->Item( aIndex, uno::Any());
418 	return uno::makeAny( xVPageBreaks );
419 }
420 
421 sal_Int32
422 ScVbaWorksheet::getStandardWidth() throw (uno::RuntimeException)
423 {
424 	return STANDARDWIDTH ;
425 }
426 
427 sal_Int32
428 ScVbaWorksheet::getStandardHeight() throw (uno::RuntimeException)
429 {
430 	return STANDARDHEIGHT;
431 }
432 
433 sal_Bool
434 ScVbaWorksheet::getProtectionMode() throw (uno::RuntimeException)
435 {
436 	return sal_False;
437 }
438 
439 sal_Bool
440 ScVbaWorksheet::getProtectContents()throw (uno::RuntimeException)
441 {
442 	uno::Reference<util::XProtectable > xProtectable(getSheet(), uno::UNO_QUERY_THROW);
443 	return xProtectable->isProtected();
444 }
445 
446 sal_Bool
447 ScVbaWorksheet::getProtectDrawingObjects() throw (uno::RuntimeException)
448 {
449 	return sal_False;
450 }
451 
452 sal_Bool
453 ScVbaWorksheet::getProtectScenarios() throw (uno::RuntimeException)
454 {
455 	return sal_False;
456 }
457 
458 void
459 ScVbaWorksheet::Activate() throw (uno::RuntimeException)
460 {
461 	uno::Reference< sheet::XSpreadsheetView > xSpreadsheet(
462         	getModel()->getCurrentController(), uno::UNO_QUERY_THROW );
463 	xSpreadsheet->setActiveSheet(getSheet());
464 }
465 
466 void
467 ScVbaWorksheet::Select() throw (uno::RuntimeException)
468 {
469 	Activate();
470 }
471 
472 void
473 ScVbaWorksheet::Move( const uno::Any& Before, const uno::Any& After ) throw (uno::RuntimeException)
474 {
475 	uno::Reference<excel::XWorksheet> xSheet;
476 	rtl::OUString aCurrSheetName = getName();
477 
478 	if (!(Before >>= xSheet) && !(After >>=xSheet)&& !(Before.hasValue()) && !(After.hasValue()))
479 	{
480 		uno::Reference< sheet::XSheetCellCursor > xSheetCellCursor = getSheet()->createCursor( );
481 		uno::Reference<sheet::XUsedAreaCursor> xUsedCursor(xSheetCellCursor,uno::UNO_QUERY_THROW);
482         	uno::Reference< table::XCellRange > xRange1( xSheetCellCursor, uno::UNO_QUERY);
483 		// #FIXME needs worksheet as parent
484 		uno::Reference<excel::XRange> xRange =  new ScVbaRange( this, mxContext, xRange1);
485 		if (xRange.is())
486 			xRange->Select();
487 		excel::implnCopy(mxModel);
488 		uno::Reference<frame::XModel> xModel = openNewDoc(aCurrSheetName);
489 		if (xModel.is())
490 		{
491 			excel::implnPaste(xModel);
492 			Delete();
493 		}
494 		return ;
495 	}
496 
497 	uno::Reference <sheet::XSpreadsheetDocument> xSpreadDoc( getModel(), uno::UNO_QUERY_THROW );
498 	SCTAB nDest = 0;
499 	if ( ScVbaWorksheets::nameExists (xSpreadDoc, xSheet->getName(), nDest) )
500 	{
501 		sal_Bool bAfter = After.hasValue();
502 		if (bAfter)
503 			nDest++;
504 		uno::Reference<sheet::XSpreadsheets> xSheets = xSpreadDoc->getSheets();
505 		xSheets->moveByName(aCurrSheetName,nDest);
506 	}
507 }
508 
509 void
510 ScVbaWorksheet::Copy( const uno::Any& Before, const uno::Any& After ) throw (uno::RuntimeException)
511 {
512 	uno::Reference<excel::XWorksheet> xSheet;
513 	rtl::OUString aCurrSheetName =getName();
514 	if (!(Before >>= xSheet) && !(After >>=xSheet)&& !(Before.hasValue()) && !(After.hasValue()))
515 	{
516 		uno::Reference< sheet::XSheetCellCursor > xSheetCellCursor = getSheet()->createCursor( );
517 		uno::Reference<sheet::XUsedAreaCursor> xUsedCursor(xSheetCellCursor,uno::UNO_QUERY_THROW);
518         	uno::Reference< table::XCellRange > xRange1( xSheetCellCursor, uno::UNO_QUERY);
519 		uno::Reference<excel::XRange> xRange =  new ScVbaRange( this, mxContext, xRange1);
520 		if (xRange.is())
521 			xRange->Select();
522 		excel::implnCopy(mxModel);
523 		uno::Reference<frame::XModel> xModel = openNewDoc(aCurrSheetName);
524 		if (xModel.is())
525 		{
526 			excel::implnPaste(xModel);
527 		}
528 		return;
529 	}
530 
531 	uno::Reference <sheet::XSpreadsheetDocument> xSpreadDoc( getModel(), uno::UNO_QUERY );
532 	SCTAB nDest = 0;
533 	rtl::OUString aSheetName = xSheet->getName();
534 	if ( ScVbaWorksheets::nameExists (xSpreadDoc, aSheetName, nDest ) )
535 	{
536 		sal_Bool bAfter = After.hasValue();
537 		if(bAfter)
538 			  nDest++;
539 		uno::Reference<sheet::XSpreadsheets> xSheets = xSpreadDoc->getSheets();
540 		getNewSpreadsheetName(aSheetName,aCurrSheetName,xSpreadDoc);
541 		xSheets->copyByName(aCurrSheetName,aSheetName,nDest);
542 	}
543 }
544 
545 
546 void
547 ScVbaWorksheet::Paste( const uno::Any& Destination, const uno::Any& /*Link*/ ) throw (uno::RuntimeException)
548 {
549 	// #TODO# #FIXME# Link is not used
550 	uno::Reference<excel::XRange> xRange( Destination, uno::UNO_QUERY );
551 	if ( xRange.is() )
552 		xRange->Select();
553 	excel::implnPaste( mxModel );
554 }
555 
556 void
557 ScVbaWorksheet::Delete() throw (uno::RuntimeException)
558 {
559 	uno::Reference <sheet::XSpreadsheetDocument> xSpreadDoc( getModel(), uno::UNO_QUERY_THROW );
560 	rtl::OUString aSheetName = getName();
561 	if ( xSpreadDoc.is() )
562 	{
563 		SCTAB nTab = 0;
564 		if (!ScVbaWorksheets::nameExists(xSpreadDoc, aSheetName, nTab ))
565 		{
566 			return;
567 		}
568 		uno::Reference<sheet::XSpreadsheets> xSheets = xSpreadDoc->getSheets();
569 		uno::Reference<container::XNameContainer> xNameContainer(xSheets,uno::UNO_QUERY_THROW);
570 		xNameContainer->removeByName(aSheetName);
571         mxSheet.clear();
572 	}
573 }
574 
575 uno::Reference< excel::XWorksheet >
576 ScVbaWorksheet::getSheetAtOffset(SCTAB offset) throw (uno::RuntimeException)
577 {
578 	uno::Reference <sheet::XSpreadsheetDocument> xSpreadDoc( getModel(), uno::UNO_QUERY_THROW );
579 	uno::Reference <sheet::XSpreadsheets> xSheets( xSpreadDoc->getSheets(), uno::UNO_QUERY_THROW );
580 	uno::Reference <container::XIndexAccess> xIndex( xSheets, uno::UNO_QUERY_THROW );
581 
582 	SCTAB nIdx = 0;
583 	if ( !ScVbaWorksheets::nameExists (xSpreadDoc, getName(), nIdx ) )
584 		return uno::Reference< excel::XWorksheet >();
585 	nIdx = nIdx + offset;
586 	uno::Reference< sheet::XSpreadsheet > xSheet(xIndex->getByIndex(nIdx), uno::UNO_QUERY_THROW);
587 	// parent will be the parent of 'this' worksheet
588 	return new ScVbaWorksheet (getParent(), mxContext, xSheet, getModel());
589 }
590 
591 uno::Reference< excel::XWorksheet >
592 ScVbaWorksheet::getNext() throw (uno::RuntimeException)
593 {
594 	return getSheetAtOffset(static_cast<SCTAB>(1));
595 }
596 
597 uno::Reference< excel::XWorksheet >
598 ScVbaWorksheet::getPrevious() throw (uno::RuntimeException)
599 {
600 	return getSheetAtOffset(-1);
601 }
602 
603 
604 void
605 ScVbaWorksheet::Protect( const uno::Any& Password, const uno::Any& /*DrawingObjects*/, const uno::Any& /*Contents*/, const uno::Any& /*Scenarios*/, const uno::Any& /*UserInterfaceOnly*/ ) throw (uno::RuntimeException)
606 {
607 	// #TODO# #FIXME# is there anything we can do witht the unused param
608 	// can the implementation use anything else here
609 	uno::Reference<util::XProtectable > xProtectable(getSheet(), uno::UNO_QUERY_THROW);
610 	::rtl::OUString aPasswd;
611 	Password >>= aPasswd;
612 	xProtectable->protect( aPasswd );
613 }
614 
615 void
616 ScVbaWorksheet::Unprotect( const uno::Any& Password ) throw (uno::RuntimeException)
617 {
618 	uno::Reference<util::XProtectable > xProtectable(getSheet(), uno::UNO_QUERY_THROW);
619 	::rtl::OUString aPasswd;
620 	Password >>= aPasswd;
621 	xProtectable->unprotect( aPasswd );
622 }
623 
624 void
625 ScVbaWorksheet::Calculate() throw (uno::RuntimeException)
626 {
627 	uno::Reference <sheet::XCalculatable> xReCalculate(getModel(), uno::UNO_QUERY_THROW);
628 	xReCalculate->calculate();
629 }
630 
631 uno::Reference< excel::XRange >
632 ScVbaWorksheet::Range( const ::uno::Any& Cell1, const ::uno::Any& Cell2 ) throw (uno::RuntimeException)
633 {
634 	uno::Reference< excel::XRange > xSheetRange( new ScVbaRange( this, mxContext
635 , uno::Reference< table::XCellRange >( getSheet(), uno::UNO_QUERY_THROW ) ) );
636 	return xSheetRange->Range( Cell1, Cell2 );
637 }
638 
639 void
640 ScVbaWorksheet::CheckSpelling( const uno::Any& /*CustomDictionary*/,const uno::Any& /*IgnoreUppercase*/,const uno::Any& /*AlwaysSuggest*/, const uno::Any& /*SpellingLang*/ ) throw (uno::RuntimeException)
641 {
642 	// #TODO# #FIXME# unused params above, can we do anything with those
643 	rtl::OUString url = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( ".uno:SpellDialog"));
644 	uno::Reference< frame::XModel > xModel( getModel() );
645 	dispatchRequests(xModel,url);
646 }
647 
648 uno::Reference< excel::XRange >
649 ScVbaWorksheet::getSheetRange() throw (uno::RuntimeException)
650 {
651 	uno::Reference< table::XCellRange > xRange( getSheet(),uno::UNO_QUERY_THROW );
652 	return uno::Reference< excel::XRange >( new ScVbaRange( this, mxContext, xRange ) );
653 }
654 
655 // These are hacks - we prolly (somehow) need to inherit
656 // the vbarange functionality here ...
657 uno::Reference< excel::XRange >
658 ScVbaWorksheet::Cells( const ::uno::Any &nRow, const ::uno::Any &nCol )
659 		throw (uno::RuntimeException)
660 {
661     // Performance optimization for often-called Cells method:
662     // Use a common helper method instead of creating a new ScVbaRange object
663     uno::Reference< table::XCellRange > xRange( getSheet(), uno::UNO_QUERY_THROW );
664     return ScVbaRange::CellsHelper( this, mxContext, xRange, nRow, nCol );
665 }
666 
667 uno::Reference< excel::XRange >
668 ScVbaWorksheet::Rows(const uno::Any& aIndex ) throw (uno::RuntimeException)
669 {
670 	return getSheetRange()->Rows( aIndex );
671 }
672 
673 uno::Reference< excel::XRange >
674 ScVbaWorksheet::Columns( const uno::Any& aIndex ) throw (uno::RuntimeException)
675 {
676 	return getSheetRange()->Columns( aIndex );
677 }
678 
679 uno::Any SAL_CALL
680 ScVbaWorksheet::ChartObjects( const uno::Any& Index ) throw (uno::RuntimeException)
681 {
682 	if ( !mxCharts.is() )
683 	{
684 		uno::Reference< table::XTableChartsSupplier > xChartSupplier( getSheet(), uno::UNO_QUERY_THROW );
685 		uno::Reference< table::XTableCharts > xTableCharts = xChartSupplier->getCharts();
686 
687 		uno::Reference< drawing::XDrawPageSupplier > xDrawPageSupplier( mxSheet, uno::UNO_QUERY_THROW );
688 		mxCharts = new ScVbaChartObjects(  this, mxContext, xTableCharts, xDrawPageSupplier );
689 	}
690 	if ( Index.hasValue() )
691 	{
692 		uno::Reference< XCollection > xColl( mxCharts, uno::UNO_QUERY_THROW );
693 		return xColl->Item( Index, uno::Any() );
694 	}
695 	else
696 		return uno::makeAny( mxCharts );
697 
698 }
699 
700 uno::Any SAL_CALL
701 ScVbaWorksheet::PivotTables( const uno::Any& Index ) throw (uno::RuntimeException)
702 {
703 	uno::Reference< css::sheet::XSpreadsheet > xSheet = getSheet();
704 	uno::Reference< sheet::XDataPilotTablesSupplier > xTables(xSheet, uno::UNO_QUERY_THROW ) ;
705 	uno::Reference< container::XIndexAccess > xIndexAccess( xTables->getDataPilotTables(), uno::UNO_QUERY_THROW );
706 
707 	uno::Reference< XCollection > xColl(  new ScVbaPivotTables( this, mxContext, xIndexAccess ) );
708 	if ( Index.hasValue() )
709 		return xColl->Item( Index, uno::Any() );
710 	return uno::makeAny( xColl );
711 }
712 
713 uno::Any SAL_CALL
714 ScVbaWorksheet::Comments( const uno::Any& Index ) throw (uno::RuntimeException)
715 {
716 	uno::Reference< css::sheet::XSpreadsheet > xSheet = getSheet();
717 	uno::Reference< sheet::XSheetAnnotationsSupplier > xAnnosSupp( xSheet, uno::UNO_QUERY_THROW );
718 	uno::Reference< sheet::XSheetAnnotations > xAnnos( xAnnosSupp->getAnnotations(), uno::UNO_QUERY_THROW );
719 	uno::Reference< container::XIndexAccess > xIndexAccess( xAnnos, uno::UNO_QUERY_THROW );
720 	uno::Reference< XCollection > xColl(  new ScVbaComments( this, mxContext, mxModel, xIndexAccess ) );
721 	if ( Index.hasValue() )
722 		return xColl->Item( Index, uno::Any() );
723 	return uno::makeAny( xColl );
724 }
725 
726 uno::Any SAL_CALL
727 ScVbaWorksheet::Hyperlinks( const uno::Any& aIndex ) throw (uno::RuntimeException)
728 {
729     /*  The worksheet always returns the same Hyperlinks object.
730         See vbahyperlinks.hxx for more details. */
731     if( !mxHlinks.is() )
732         mxHlinks.set( new ScVbaHyperlinks( this, mxContext ) );
733 	if( aIndex.hasValue() )
734 		return uno::Reference< XCollection >( mxHlinks, uno::UNO_QUERY_THROW )->Item( aIndex, uno::Any() );
735     return uno::Any( mxHlinks );
736 }
737 
738 uno::Any SAL_CALL
739 ScVbaWorksheet::Names( const css::uno::Any& aIndex ) throw (uno::RuntimeException)
740 {
741     // fake sheet-local names by returning all global names
742     // #163498# initialize Names object with correct parent (this worksheet)
743     // TODO: real sheet-local names...
744 	uno::Reference< beans::XPropertySet > xProps( mxModel, uno::UNO_QUERY_THROW );
745 	uno::Reference< sheet::XNamedRanges > xNamedRanges(  xProps->getPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("NamedRanges") ) ), uno::UNO_QUERY_THROW );
746 	uno::Reference< XCollection > xNames( new ScVbaNames( this, mxContext, xNamedRanges, mxModel ) );
747     if ( aIndex.hasValue() )
748         return uno::Any( xNames->Item( aIndex, uno::Any() ) );
749 	return uno::Any( xNames );
750 }
751 
752 uno::Any SAL_CALL
753 ScVbaWorksheet::OLEObjects( const uno::Any& Index ) throw (uno::RuntimeException)
754 {
755     uno::Reference< sheet::XSpreadsheet > xSpreadsheet( getSheet(), uno::UNO_QUERY_THROW );
756     uno::Reference< drawing::XDrawPageSupplier > xDrawPageSupplier( xSpreadsheet, uno::UNO_QUERY_THROW );
757     uno::Reference< drawing::XDrawPage > xDrawPage( xDrawPageSupplier->getDrawPage(), uno::UNO_QUERY_THROW );
758     uno::Reference< container::XIndexAccess > xIndexAccess( xDrawPage, uno::UNO_QUERY_THROW );
759 
760     uno::Reference< excel::XOLEObjects >xOleObjects( new ScVbaOLEObjects( this, mxContext, xIndexAccess ) );
761     if( Index.hasValue() )
762         return xOleObjects->Item( Index, uno::Any() );
763     return uno::Any( xOleObjects );
764 }
765 
766 uno::Any SAL_CALL
767 ScVbaWorksheet::Shapes( const uno::Any& aIndex ) throw (uno::RuntimeException)
768 {
769     uno::Reference< sheet::XSpreadsheet > xSpreadsheet( getSheet(), uno::UNO_QUERY_THROW );
770     uno::Reference< drawing::XDrawPageSupplier > xDrawPageSupplier( xSpreadsheet, uno::UNO_QUERY_THROW );
771     uno::Reference< drawing::XShapes > xShapes( xDrawPageSupplier->getDrawPage(), uno::UNO_QUERY_THROW );
772     uno::Reference< container::XIndexAccess > xIndexAccess( xShapes, uno::UNO_QUERY_THROW );
773 
774    uno::Reference< msforms::XShapes> xVbaShapes( new ScVbaShapes( this, mxContext, xIndexAccess, getModel() ) );
775    if ( aIndex.hasValue() )
776       return xVbaShapes->Item( aIndex, uno::Any() );
777    return uno::makeAny( xVbaShapes );
778 }
779 
780 uno::Any SAL_CALL
781 ScVbaWorksheet::Buttons( const uno::Any& rIndex ) throw (uno::RuntimeException)
782 {
783     if( !mxButtons.is() )
784         mxButtons.set( new ScVbaButtons( this, mxContext, mxModel, mxSheet ) );
785     else
786         mxButtons->collectShapes();
787     if( rIndex.hasValue() )
788         return mxButtons->Item( rIndex, uno::Any() );
789     return uno::Any( uno::Reference< XCollection >( mxButtons.get() ) );
790 }
791 
792 uno::Any SAL_CALL
793 ScVbaWorksheet::CheckBoxes( const uno::Any& /*rIndex*/ ) throw (uno::RuntimeException)
794 {
795     throw uno::RuntimeException();
796 }
797 
798 uno::Any SAL_CALL
799 ScVbaWorksheet::DropDowns( const uno::Any& /*rIndex*/ ) throw (uno::RuntimeException)
800 {
801     throw uno::RuntimeException();
802 }
803 
804 uno::Any SAL_CALL
805 ScVbaWorksheet::GroupBoxes( const uno::Any& /*rIndex*/ ) throw (uno::RuntimeException)
806 {
807     throw uno::RuntimeException();
808 }
809 
810 uno::Any SAL_CALL
811 ScVbaWorksheet::Labels( const uno::Any& /*rIndex*/ ) throw (uno::RuntimeException)
812 {
813     throw uno::RuntimeException();
814 }
815 
816 uno::Any SAL_CALL
817 ScVbaWorksheet::ListBoxes( const uno::Any& /*rIndex*/ ) throw (uno::RuntimeException)
818 {
819     throw uno::RuntimeException();
820 }
821 
822 uno::Any SAL_CALL
823 ScVbaWorksheet::OptionButtons( const uno::Any& /*rIndex*/ ) throw (uno::RuntimeException)
824 {
825     throw uno::RuntimeException();
826 }
827 
828 uno::Any SAL_CALL
829 ScVbaWorksheet::ScrollBars( const uno::Any& /*rIndex*/ ) throw (uno::RuntimeException)
830 {
831     throw uno::RuntimeException();
832 }
833 
834 uno::Any SAL_CALL
835 ScVbaWorksheet::Spinners( const uno::Any& /*rIndex*/ ) throw (uno::RuntimeException)
836 {
837     throw uno::RuntimeException();
838 }
839 
840 void SAL_CALL
841 ScVbaWorksheet::ShowDataForm( ) throw (uno::RuntimeException)
842 {
843 #ifdef VBA_OOBUILD_HACK
844 	uno::Reference< frame::XModel > xModel( getModel(), uno::UNO_QUERY_THROW );
845 	ScTabViewShell* pTabViewShell = excel::getBestViewShell( xModel );
846 
847 	ScAbstractDialogFactory* pFact = ScAbstractDialogFactory::Create();
848 	DBG_ASSERT(pFact, "ScAbstractFactory create fail!");//CHINA001
849 
850 	AbstractScDataFormDlg* pDlg = pFact->CreateScDataFormDlg( pTabViewShell->GetDialogParent(),RID_SCDLG_DATAFORM, pTabViewShell);
851 	DBG_ASSERT(pDlg, "Dialog create fail!");//CHINA001
852 
853 	pDlg->Execute();
854 #else
855 	throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("Not implemented") ), uno::Reference< uno::XInterface >() );
856 #endif
857 }
858 
859 uno::Any SAL_CALL
860 ScVbaWorksheet::Evaluate( const ::rtl::OUString& Name ) throw (uno::RuntimeException)
861 {
862 	// #TODO Evaluate allows other things to be evaluated, e.g. functions
863 	// I think ( like SIN(3) etc. ) need to investigate that
864 	// named Ranges also? e.g. [MyRange] if so need a list of named ranges
865 	uno::Any aVoid;
866 	return uno::Any( Range( uno::Any( Name ), aVoid ) );
867 }
868 
869 
870 uno::Reference< beans::XIntrospectionAccess > SAL_CALL
871 ScVbaWorksheet::getIntrospection(  ) throw (uno::RuntimeException)
872 {
873 	return uno::Reference< beans::XIntrospectionAccess >();
874 }
875 
876 uno::Any SAL_CALL
877 ScVbaWorksheet::invoke( const ::rtl::OUString& aFunctionName, const uno::Sequence< uno::Any >& /*aParams*/, uno::Sequence< ::sal_Int16 >& /*aOutParamIndex*/, uno::Sequence< uno::Any >& /*aOutParam*/ ) throw (lang::IllegalArgumentException, script::CannotConvertException, reflection::InvocationTargetException, uno::RuntimeException)
878 {
879 	OSL_TRACE("** ScVbaWorksheet::invoke( %s ), will barf",
880 		rtl::OUStringToOString( aFunctionName, RTL_TEXTENCODING_UTF8 ).getStr() );
881 
882 	throw uno::RuntimeException(); // unsupported operation
883 }
884 
885 void SAL_CALL
886 ScVbaWorksheet::setValue( const ::rtl::OUString& aPropertyName, const uno::Any& aValue ) throw (beans::UnknownPropertyException, script::CannotConvertException, reflection::InvocationTargetException, uno::RuntimeException)
887 {
888     setDefaultPropByIntrospection( uno::makeAny( getValue( aPropertyName ) ), aValue );
889 }
890 uno::Any SAL_CALL
891 ScVbaWorksheet::getValue( const ::rtl::OUString& aPropertyName ) throw (beans::UnknownPropertyException, uno::RuntimeException)
892 {
893     uno::Reference< drawing::XControlShape > xControlShape( getControlShape( aPropertyName ), uno::UNO_QUERY_THROW );
894 
895     uno::Reference<lang::XMultiComponentFactory > xServiceManager( mxContext->getServiceManager(), uno::UNO_QUERY_THROW );
896     uno::Reference< XControlProvider > xControlProvider( xServiceManager->createInstanceWithContext( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "ooo.vba.ControlProvider" ) ), mxContext ), uno::UNO_QUERY_THROW );
897     uno::Reference< msforms::XControl > xControl( xControlProvider->createControl(  xControlShape, getModel() ) );
898     return uno::makeAny( xControl );
899 }
900 
901 ::sal_Bool SAL_CALL
902 ScVbaWorksheet::hasMethod( const ::rtl::OUString& /*aName*/ ) throw (uno::RuntimeException)
903 {
904 	return sal_False;
905 }
906 
907 uno::Reference< container::XNameAccess >
908 ScVbaWorksheet::getFormControls()
909 {
910 	uno::Reference< container::XNameAccess > xFormControls;
911 	try
912 	{
913 		uno::Reference< sheet::XSpreadsheet > xSpreadsheet( getSheet(), uno::UNO_QUERY_THROW );
914 		uno::Reference< drawing::XDrawPageSupplier > xDrawPageSupplier( xSpreadsheet, uno::UNO_QUERY_THROW );
915 		uno::Reference< form::XFormsSupplier >  xFormSupplier( xDrawPageSupplier->getDrawPage(), uno::UNO_QUERY_THROW );
916     		uno::Reference< container::XIndexAccess > xIndexAccess( xFormSupplier->getForms(), uno::UNO_QUERY_THROW );
917 		// get the www-standard container ( maybe we should access the
918 		// 'www-standard' by name rather than index, this seems an
919 		// implementation detail
920 		if( xIndexAccess->hasElements() )
921 			xFormControls.set( xIndexAccess->getByIndex(0), uno::UNO_QUERY );
922 
923 	}
924 	catch( uno::Exception& )
925 	{
926 	}
927 	return xFormControls;
928 
929 				}
930 ::sal_Bool SAL_CALL
931 ScVbaWorksheet::hasProperty( const ::rtl::OUString& aName ) throw (uno::RuntimeException)
932 {
933 	uno::Reference< container::XNameAccess > xFormControls( getFormControls() );
934 	if ( xFormControls.is() )
935 		return xFormControls->hasByName( aName );
936 	return sal_False;
937 }
938 
939 uno::Any
940 ScVbaWorksheet::getControlShape( const ::rtl::OUString& sName )
941 {
942     // ideally we would get an XControl object but it appears an XControl
943     // implementation only exists for a Control implementation optained from the
944     // view ( e.g. in basic you would get this from
945     // thiscomponent.currentcontroller.getControl( controlModel ) )
946     // and the thing to realise is that it is only possible to get an XControl
947     // for a currently displayed control :-( often we would want to modify
948     // a control not on the active sheet. But.. you can always access the
949     // XControlShape from the DrawPage whether that is the active drawpage or not
950 
951     uno::Reference< drawing::XDrawPageSupplier > xDrawPageSupplier( getSheet(), uno::UNO_QUERY_THROW );
952     uno::Reference< container::XIndexAccess > xIndexAccess( xDrawPageSupplier->getDrawPage(), uno::UNO_QUERY_THROW );
953 
954     sal_Int32 nCount = xIndexAccess->getCount();
955     for( int index = 0; index < nCount; index++ )
956     {
957         uno::Any aUnoObj =  xIndexAccess->getByIndex( index );
958  		// It seems there are some drawing objects that can not query into Control shapes?
959         uno::Reference< drawing::XControlShape > xControlShape( aUnoObj, uno::UNO_QUERY );
960  		if( xControlShape.is() )
961  		{
962      	    uno::Reference< container::XNamed > xNamed( xControlShape->getControl(), uno::UNO_QUERY_THROW );
963         if( sName.equals( xNamed->getName() ))
964         {
965             return aUnoObj;
966         }
967  		}
968     }
969     return uno::Any();
970 }
971 
972 
973 rtl::OUString&
974 ScVbaWorksheet::getServiceImplName()
975 {
976 	static rtl::OUString sImplName( RTL_CONSTASCII_USTRINGPARAM("ScVbaWorksheet") );
977 	return sImplName;
978 }
979 void SAL_CALL
980 ScVbaWorksheet::setEnableCalculation( ::sal_Bool bEnableCalculation ) throw ( script::BasicErrorException, uno::RuntimeException)
981 {
982 	uno::Reference <sheet::XCalculatable> xCalculatable(getModel(), uno::UNO_QUERY_THROW);
983         xCalculatable->enableAutomaticCalculation( bEnableCalculation);
984 }
985 ::sal_Bool SAL_CALL
986 ScVbaWorksheet::getEnableCalculation(  ) throw (css::script::BasicErrorException, css::uno::RuntimeException)
987 {
988 	uno::Reference <sheet::XCalculatable> xCalculatable(getModel(), uno::UNO_QUERY_THROW);
989 	return xCalculatable->isAutomaticCalculationEnabled();
990 }
991 
992 uno::Sequence< rtl::OUString >
993 ScVbaWorksheet::getServiceNames()
994 {
995 	static uno::Sequence< rtl::OUString > aServiceNames;
996 	if ( aServiceNames.getLength() == 0 )
997 	{
998 		aServiceNames.realloc( 1 );
999 		aServiceNames[ 0 ] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.excel.Worksheet" ) );
1000 	}
1001 	return aServiceNames;
1002 }
1003 
1004 rtl::OUString SAL_CALL
1005 ScVbaWorksheet::getCodeName() throw (css::uno::RuntimeException)
1006 {
1007     uno::Reference< beans::XPropertySet > xSheetProp( mxSheet, uno::UNO_QUERY_THROW );
1008     return xSheetProp->getPropertyValue( ::rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "CodeName" ) ) ).get< ::rtl::OUString >();
1009 }
1010 
1011 sal_Int16
1012 ScVbaWorksheet::getSheetID() throw (uno::RuntimeException)
1013 {
1014 	uno::Reference< sheet::XCellRangeAddressable > xAddressable( mxSheet, uno::UNO_QUERY_THROW );
1015 	return xAddressable->getRangeAddress().Sheet;
1016 }
1017 
1018 void SAL_CALL
1019 ScVbaWorksheet::PrintOut( const uno::Any& From, const uno::Any& To, const uno::Any& Copies, const uno::Any& Preview, const uno::Any& ActivePrinter, const uno::Any& PrintToFile, const uno::Any& Collate, const uno::Any& PrToFileName, const uno::Any& IgnorePrintAreas ) throw (uno::RuntimeException)
1020 {
1021 	sal_Int32 nTo = 0;
1022 	sal_Int32 nFrom = 0;
1023 	sal_Int16 nCopies = 1;
1024 	sal_Bool bCollate = sal_False;
1025 	sal_Bool bSelection = sal_False;
1026     sal_Bool bIgnorePrintAreas = sal_False;
1027 	From >>= nFrom;
1028 	To >>= nTo;
1029 	Copies >>= nCopies;
1030     IgnorePrintAreas >>= bIgnorePrintAreas;
1031 	if ( nCopies > 1 ) // Collate only useful when more that 1 copy
1032 		Collate >>= bCollate;
1033 
1034 	if ( !( nFrom || nTo ) )
1035 		bSelection = sal_True;
1036 
1037     uno::Reference< frame::XModel > xModel( getModel(), uno::UNO_QUERY_THROW );
1038 	PrintOutHelper( excel::getBestViewShell( xModel ), From, To, Copies, Preview, ActivePrinter, PrintToFile, Collate, PrToFileName, bSelection );
1039 }
1040 
1041 namespace worksheet
1042 {
1043 namespace sdecl = comphelper::service_decl;
1044 sdecl::vba_service_class_<ScVbaWorksheet, sdecl::with_args<true> > serviceImpl;
1045 extern sdecl::ServiceDecl const serviceDecl(
1046     serviceImpl,
1047     "ScVbaWorksheet",
1048     "ooo.vba.excel.Worksheet" );
1049 }
1050