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