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