xref: /aoo42x/main/sc/source/ui/vba/vbarange.cxx (revision cdf0e10c)
1 /*************************************************************************
2  *
3  * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
4  *
5  * Copyright 2000, 2010 Oracle and/or its affiliates.
6  *
7  * OpenOffice.org - a multi-platform office productivity suite
8  *
9  * This file is part of OpenOffice.org.
10  *
11  * OpenOffice.org is free software: you can redistribute it and/or modify
12  * it under the terms of the GNU Lesser General Public License version 3
13  * only, as published by the Free Software Foundation.
14  *
15  * OpenOffice.org is distributed in the hope that it will be useful,
16  * but WITHOUT ANY WARRANTY; without even the implied warranty of
17  * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
18  * GNU Lesser General Public License version 3 for more details
19  * (a copy is included in the LICENSE file that accompanied this code).
20  *
21  * You should have received a copy of the GNU Lesser General Public License
22  * version 3 along with OpenOffice.org.  If not, see
23  * <http://www.openoffice.org/license.html>
24  * for a copy of the LGPLv3 License.
25  *
26  ************************************************************************/
27 
28 #include "vbarange.hxx"
29 
30 #include <vbahelper/helperdecl.hxx>
31 
32 #include <comphelper/unwrapargs.hxx>
33 #include <comphelper/processfactory.hxx>
34 #include <sfx2/objsh.hxx>
35 
36 #include <com/sun/star/script/ArrayWrapper.hpp>
37 #include <com/sun/star/script/vba/VBAEventId.hpp>
38 #include <com/sun/star/script/vba/XVBAEventProcessor.hpp>
39 #include <com/sun/star/sheet/XDatabaseRange.hpp>
40 #include <com/sun/star/sheet/XDatabaseRanges.hpp>
41 #include <com/sun/star/sheet/XGoalSeek.hpp>
42 #include <com/sun/star/sheet/XSheetOperation.hpp>
43 #include <com/sun/star/sheet/CellFlags.hpp>
44 #include <com/sun/star/table/XColumnRowRange.hpp>
45 #include <com/sun/star/sheet/XCellAddressable.hpp>
46 #include <com/sun/star/table/CellContentType.hpp>
47 #include <com/sun/star/sheet/XCellSeries.hpp>
48 #include <com/sun/star/text/XTextRange.hpp>
49 #include <com/sun/star/sheet/XCellRangeAddressable.hpp>
50 #include <com/sun/star/table/CellRangeAddress.hpp>
51 #include <com/sun/star/table/CellAddress.hpp>
52 #include <com/sun/star/sheet/XSpreadsheetView.hpp>
53 #include <com/sun/star/sheet/XCellRangeReferrer.hpp>
54 #include <com/sun/star/sheet/XSheetCellRange.hpp>
55 #include <com/sun/star/sheet/XSpreadsheet.hpp>
56 #include <com/sun/star/sheet/XSheetCellCursor.hpp>
57 #include <com/sun/star/sheet/XArrayFormulaRange.hpp>
58 #include <com/sun/star/sheet/XNamedRange.hpp>
59 #include <com/sun/star/sheet/XPrintAreas.hpp>
60 #include <com/sun/star/sheet/XCellRangesQuery.hpp>
61 #include <com/sun/star/beans/XPropertySet.hpp>
62 #include <com/sun/star/sheet/XFunctionAccess.hpp>
63 #include <com/sun/star/frame/XModel.hpp>
64 #include <com/sun/star/view/XSelectionSupplier.hpp>
65 #include <com/sun/star/table/XCellCursor.hpp>
66 #include <com/sun/star/table/XTableRows.hpp>
67 #include <com/sun/star/table/XTableColumns.hpp>
68 #include <com/sun/star/table/TableSortField.hpp>
69 #include <com/sun/star/util/XMergeable.hpp>
70 #include <com/sun/star/uno/XComponentContext.hpp>
71 #include <com/sun/star/lang/XMultiComponentFactory.hpp>
72 #include <com/sun/star/sheet/XSpreadsheetDocument.hpp>
73 #include <com/sun/star/util/XNumberFormatsSupplier.hpp>
74 #include <com/sun/star/util/XNumberFormats.hpp>
75 #include <com/sun/star/util/NumberFormat.hpp>
76 #include <com/sun/star/util/XNumberFormatTypes.hpp>
77 #include <com/sun/star/util/XReplaceable.hpp>
78 #include <com/sun/star/util/XSortable.hpp>
79 #include <com/sun/star/sheet/XCellRangeMovement.hpp>
80 #include <com/sun/star/sheet/XCellRangeData.hpp>
81 #include <com/sun/star/sheet/FormulaResult.hpp>
82 #include <com/sun/star/sheet/FilterOperator2.hpp>
83 #include <com/sun/star/sheet/TableFilterField.hpp>
84 #include <com/sun/star/sheet/TableFilterField2.hpp>
85 #include <com/sun/star/sheet/XSheetFilterDescriptor2.hpp>
86 #include <com/sun/star/sheet/XSheetFilterable.hpp>
87 #include <com/sun/star/sheet/FilterConnection.hpp>
88 #include <com/sun/star/util/CellProtection.hpp>
89 #include <com/sun/star/util/TriState.hpp>
90 
91 #include <com/sun/star/style/XStyleFamiliesSupplier.hpp>
92 #include <com/sun/star/awt/XDevice.hpp>
93 
94 //#include <com/sun/star/sheet/CellDeleteMode.hpp>
95 #include <com/sun/star/sheet/XCellRangeMovement.hpp>
96 #include <com/sun/star/sheet/XSubTotalCalculatable.hpp>
97 #include <com/sun/star/sheet/XSubTotalDescriptor.hpp>
98 #include <com/sun/star/sheet/GeneralFunction.hdl>
99 
100 #include <ooo/vba/excel/XlPasteSpecialOperation.hpp>
101 #include <ooo/vba/excel/XlPasteType.hpp>
102 #include <ooo/vba/excel/Constants.hpp>
103 #include <ooo/vba/excel/XlFindLookIn.hpp>
104 #include <ooo/vba/excel/XlLookAt.hpp>
105 #include <ooo/vba/excel/XlSearchOrder.hpp>
106 #include <ooo/vba/excel/XlSortOrder.hpp>
107 #include <ooo/vba/excel/XlYesNoGuess.hpp>
108 #include <ooo/vba/excel/XlSortOrientation.hpp>
109 #include <ooo/vba/excel/XlSortMethod.hpp>
110 #include <ooo/vba/excel/XlDirection.hpp>
111 #include <ooo/vba/excel/XlSortDataOption.hpp>
112 #include <ooo/vba/excel/XlDeleteShiftDirection.hpp>
113 #include <ooo/vba/excel/XlInsertShiftDirection.hpp>
114 #include <ooo/vba/excel/XlReferenceStyle.hpp>
115 #include <ooo/vba/excel/XlBordersIndex.hpp>
116 #include <ooo/vba/excel/XlPageBreak.hpp>
117 #include <ooo/vba/excel/XlAutoFilterOperator.hpp>
118 #include <ooo/vba/excel/XlAutoFillType.hpp>
119 #include <ooo/vba/excel/XlTextParsingType.hpp>
120 #include <ooo/vba/excel/XlTextQualifier.hpp>
121 #include <ooo/vba/excel/XlCellType.hpp>
122 #include <ooo/vba/excel/XlSpecialCellsValue.hpp>
123 #include <ooo/vba/excel/XlConsolidationFunction.hpp>
124 #include <ooo/vba/excel/XlSearchDirection.hpp>
125 
126 #include <scitems.hxx>
127 #include <svl/srchitem.hxx>
128 #include <cellsuno.hxx>
129 #include <dbcolect.hxx>
130 #include "docfunc.hxx"
131 #include "transobj.hxx"
132 
133 #include <sfx2/dispatch.hxx>
134 #include <sfx2/app.hxx>
135 #include <sfx2/bindings.hxx>
136 #include <sfx2/request.hxx>
137 #include <sfx2/viewfrm.hxx>
138 #include <sfx2/itemwrapper.hxx>
139 #include <sc.hrc>
140 #include <globstr.hrc>
141 #include <unonames.hxx>
142 
143 #include "vbaapplication.hxx"
144 #include "vbafont.hxx"
145 #include "vbacomment.hxx"
146 #include "vbainterior.hxx"
147 #include "vbacharacters.hxx"
148 #include "vbaborders.hxx"
149 #include "vbaworksheet.hxx"
150 #include "vbavalidation.hxx"
151 #include "vbahyperlinks.hxx"
152 
153 #include "tabvwsh.hxx"
154 #include "rangelst.hxx"
155 #include "convuno.hxx"
156 #include "compiler.hxx"
157 #include "attrib.hxx"
158 #include "undodat.hxx"
159 #include "dbdocfun.hxx"
160 #include "patattr.hxx"
161 #include "olinetab.hxx"
162 #include <comphelper/anytostring.hxx>
163 
164 #include <global.hxx>
165 
166 #include "vbaglobals.hxx"
167 #include "vbastyle.hxx"
168 #include <vector>
169 #include <vbahelper/vbacollectionimpl.hxx>
170 // begin test includes
171 #include <com/sun/star/sheet/FunctionArgument.hpp>
172 // end test includes
173 
174 #include <ooo/vba/excel/Range.hpp>
175 #include <com/sun/star/bridge/oleautomation/Date.hpp>
176 
177 using namespace ::ooo::vba;
178 using namespace ::com::sun::star;
179 using ::std::vector;
180 
181 // difference between VBA and file format width, in character units
182 const double fExtraWidth = 182.0 / 256.0;
183 
184 //    * 1 point = 1/72 inch = 20 twips
185 //    * 1 inch = 72 points = 1440 twips
186 //    * 1 cm = 567 twips
187 double lcl_hmmToPoints( double nVal ) { return ( (double)((nVal /1000 ) * 567 ) / 20 ); }
188 
189 static const sal_Int16 supportedIndexTable[] = {  excel::XlBordersIndex::xlEdgeLeft, excel::XlBordersIndex::xlEdgeTop, excel::XlBordersIndex::xlEdgeBottom, excel::XlBordersIndex::xlEdgeRight, excel::XlBordersIndex::xlDiagonalDown, excel::XlBordersIndex::xlDiagonalUp, excel::XlBordersIndex::xlInsideVertical, excel::XlBordersIndex::xlInsideHorizontal };
190 
191 sal_uInt16 lcl_pointsToTwips( double nVal )
192 {
193 	nVal = nVal * static_cast<double>(20);
194 	short nTwips = static_cast<short>(nVal);
195 	return nTwips;
196 }
197 double lcl_TwipsToPoints( sal_uInt16 nVal )
198 {
199 	double nPoints = nVal;
200 	return nPoints / 20;
201 }
202 
203 double lcl_Round2DecPlaces( double nVal )
204 {
205 	nVal  = (nVal * (double)100);
206 	long tmp = static_cast<long>(nVal);
207 	if ( ( ( nVal - tmp ) >= 0.5 ) )
208 		++tmp;
209 	nVal = tmp;
210 	nVal = nVal/100;
211 	return nVal;
212 }
213 
214 uno::Any lcl_makeRange( const uno::Reference< XHelperInterface >& xParent, const uno::Reference< uno::XComponentContext >& xContext, const uno::Any aAny, bool bIsRows, bool bIsColumns )
215 {
216 	uno::Reference< table::XCellRange > xCellRange( aAny, uno::UNO_QUERY_THROW );
217     return uno::makeAny( uno::Reference< excel::XRange >( new ScVbaRange( xParent, xContext, xCellRange, bIsRows, bIsColumns ) ) );
218 }
219 
220 uno::Reference< excel::XRange > lcl_makeXRangeFromSheetCellRanges( const uno::Reference< XHelperInterface >& xParent, const uno::Reference< uno::XComponentContext >& xContext, const uno::Reference< sheet::XSheetCellRanges >& xLocSheetCellRanges, ScDocShell* pDoc )
221 {
222 	uno::Reference< excel::XRange > xRange;
223 	uno::Sequence< table::CellRangeAddress  > sAddresses = xLocSheetCellRanges->getRangeAddresses();
224 	ScRangeList aCellRanges;
225 	sal_Int32 nLen = sAddresses.getLength();
226 	if ( nLen )
227        	{
228 	for ( sal_Int32 index = 0; index < nLen; ++index )
229 	{
230 		ScRange refRange;
231 		ScUnoConversion::FillScRange( refRange, sAddresses[ index ] );
232 		aCellRanges.Append( refRange );
233 	}
234 	// Single range
235 	if ( aCellRanges.First() == aCellRanges.Last() )
236 	{
237 		uno::Reference< table::XCellRange > xTmpRange( new ScCellRangeObj( pDoc, *aCellRanges.First() ) );
238 		xRange = new ScVbaRange( xParent, xContext, xTmpRange );
239 	}
240 	else
241 	{
242 		uno::Reference< sheet::XSheetCellRangeContainer > xRanges( new ScCellRangesObj( pDoc, aCellRanges ) );
243 		xRange = new ScVbaRange( xParent, xContext, xRanges );
244 	}
245 	}
246 	return xRange;
247 }
248 
249 ScCellRangesBase* ScVbaRange::getCellRangesBase() throw ( uno::RuntimeException )
250 {
251     if( mxRanges.is() )
252         return ScCellRangesBase::getImplementation( mxRanges );
253     if( mxRange.is() )
254         return ScCellRangesBase::getImplementation( mxRange );
255     throw uno::RuntimeException( rtl::OUString::createFromAscii("General Error creating range - Unknown" ), uno::Reference< uno::XInterface >() );
256 }
257 
258 ScCellRangeObj* ScVbaRange::getCellRangeObj() throw ( uno::RuntimeException )
259 {
260 	return dynamic_cast< ScCellRangeObj* >( getCellRangesBase() );
261 }
262 
263 ScCellRangesObj* ScVbaRange::getCellRangesObj() throw ( uno::RuntimeException )
264 {
265 	return dynamic_cast< ScCellRangesObj* >( getCellRangesBase() );
266 }
267 
268 SfxItemSet*  ScVbaRange::getCurrentDataSet( ) throw ( uno::RuntimeException )
269 {
270 	SfxItemSet* pDataSet = excel::ScVbaCellRangeAccess::GetDataSet( getCellRangesBase() );
271 	if ( !pDataSet )
272 		throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "Can't access Itemset for range" ) ), uno::Reference< uno::XInterface >() );
273 	return pDataSet;
274 }
275 
276 void ScVbaRange::fireChangeEvent()
277 {
278     if( ScVbaApplication::getDocumentEventsEnabled() )
279     {
280         if( ScDocument* pDoc = getScDocument() )
281         {
282             uno::Reference< script::vba::XVBAEventProcessor > xVBAEvents = pDoc->GetVbaEventProcessor();
283             if( xVBAEvents.is() ) try
284             {
285                 uno::Sequence< uno::Any > aArgs( 1 );
286                 aArgs[ 0 ] <<= uno::Reference< excel::XRange >( this );
287                 xVBAEvents->processVbaEvent( script::vba::VBAEventId::WORKSHEET_CHANGE, aArgs );
288             }
289             catch( uno::Exception& )
290             {
291             }
292         }
293     }
294 }
295 
296 class SingleRangeEnumeration : public EnumerationHelper_BASE
297 {
298     uno::Reference< XHelperInterface > m_xParent;
299 	uno::Reference< table::XCellRange > m_xRange;
300 	uno::Reference< uno::XComponentContext > mxContext;
301 	bool bHasMore;
302 public:
303 
304     SingleRangeEnumeration( const uno::Reference< XHelperInterface >& xParent, const uno::Reference< css::uno::XComponentContext >& xContext, const uno::Reference< table::XCellRange >& xRange ) throw ( uno::RuntimeException ) : m_xParent( xParent ), m_xRange( xRange ), mxContext( xContext ), bHasMore( true ) { }
305 	virtual ::sal_Bool SAL_CALL hasMoreElements(  ) throw (uno::RuntimeException) { return bHasMore; }
306 	virtual uno::Any SAL_CALL nextElement(  ) throw (container::NoSuchElementException, lang::WrappedTargetException, uno::RuntimeException)
307 	{
308 		if ( !bHasMore )
309 			throw container::NoSuchElementException();
310 		bHasMore = false;
311 		return uno::makeAny( m_xRange );
312 	}
313 };
314 
315 // very simple class to pass to ScVbaCollectionBaseImpl containing
316 // just one item
317 typedef ::cppu::WeakImplHelper2< container::XIndexAccess, container::XEnumerationAccess > SingleRange_BASE;
318 
319 class SingleRangeIndexAccess : public SingleRange_BASE
320 {
321 private:
322     uno::Reference< XHelperInterface > mxParent;
323 	uno::Reference< table::XCellRange > m_xRange;
324 	uno::Reference< uno::XComponentContext > mxContext;
325 	SingleRangeIndexAccess(); // not defined
326 public:
327     SingleRangeIndexAccess( const uno::Reference< XHelperInterface >& xParent, const uno::Reference< uno::XComponentContext >& xContext, const uno::Reference< table::XCellRange >& xRange ):mxParent( xParent ), m_xRange( xRange ), mxContext( xContext ) {}
328 	// XIndexAccess
329 	virtual ::sal_Int32 SAL_CALL getCount() throw (::uno::RuntimeException) { return 1; }
330 	virtual uno::Any SAL_CALL getByIndex( ::sal_Int32 Index ) throw (lang::IndexOutOfBoundsException, lang::WrappedTargetException, uno::RuntimeException)
331 	{
332 		if ( Index != 0 )
333 			throw lang::IndexOutOfBoundsException();
334 		return uno::makeAny( m_xRange );
335 	}
336         // XElementAccess
337         virtual uno::Type SAL_CALL getElementType() throw (uno::RuntimeException){ return table::XCellRange::static_type(0); }
338 
339         virtual ::sal_Bool SAL_CALL hasElements() throw (uno::RuntimeException) { return sal_True; }
340 	// XEnumerationAccess
341     virtual uno::Reference< container::XEnumeration > SAL_CALL createEnumeration() throw (uno::RuntimeException) { return new SingleRangeEnumeration( mxParent, mxContext, m_xRange ); }
342 
343 };
344 
345 
346 
347 class RangesEnumerationImpl : public EnumerationHelperImpl
348 {
349 	bool mbIsRows;
350 	bool mbIsColumns;
351 public:
352 
353     RangesEnumerationImpl( const uno::Reference< XHelperInterface >& xParent, const uno::Reference< uno::XComponentContext >& xContext, const uno::Reference< container::XEnumeration >& xEnumeration, bool bIsRows, bool bIsColumns ) throw ( uno::RuntimeException ) : EnumerationHelperImpl( xParent, xContext, xEnumeration ), mbIsRows( bIsRows ), mbIsColumns( bIsColumns ) {}
354 	virtual uno::Any SAL_CALL nextElement(  ) throw (container::NoSuchElementException, lang::WrappedTargetException, uno::RuntimeException)
355 	{
356         return lcl_makeRange( m_xParent, m_xContext, m_xEnumeration->nextElement(), mbIsRows, mbIsColumns );
357 	}
358 };
359 
360 
361 class ScVbaRangeAreas : public ScVbaCollectionBaseImpl
362 {
363 	bool mbIsRows;
364 	bool mbIsColumns;
365 public:
366     ScVbaRangeAreas( const uno::Reference< XHelperInterface >& xParent, const uno::Reference< uno::XComponentContext >& xContext, const uno::Reference< container::XIndexAccess >& xIndexAccess, bool bIsRows, bool bIsColumns ) : ScVbaCollectionBaseImpl( xParent, xContext, xIndexAccess ), mbIsRows( bIsRows ), mbIsColumns( bIsColumns ) {}
367 
368 	// XEnumerationAccess
369 	virtual uno::Reference< container::XEnumeration > SAL_CALL createEnumeration() throw (uno::RuntimeException);
370 
371 	// XElementAccess
372 	virtual uno::Type SAL_CALL getElementType() throw (uno::RuntimeException){ return excel::XRange::static_type(0); }
373 
374 	virtual uno::Any createCollectionObject( const uno::Any& aSource );
375 
376 	virtual rtl::OUString& getServiceImplName() { static rtl::OUString sDummy; return sDummy; }
377 
378 	virtual uno::Sequence< rtl::OUString > getServiceNames() { return uno::Sequence< rtl::OUString >(); }
379 
380 };
381 
382 uno::Reference< container::XEnumeration > SAL_CALL
383 ScVbaRangeAreas::createEnumeration() throw (uno::RuntimeException)
384 {
385 	uno::Reference< container::XEnumerationAccess > xEnumAccess( m_xIndexAccess, uno::UNO_QUERY_THROW );
386 	return new RangesEnumerationImpl( mxParent, mxContext, xEnumAccess->createEnumeration(), mbIsRows, mbIsColumns );
387 }
388 
389 uno::Any
390 ScVbaRangeAreas::createCollectionObject( const uno::Any& aSource )
391 {
392 	return lcl_makeRange( mxParent, mxContext, aSource, mbIsRows, mbIsColumns );
393 }
394 
395 // assume that xIf is infact a ScCellRangesBase
396 ScDocShell*
397 getDocShellFromIf( const uno::Reference< uno::XInterface >& xIf ) throw ( uno::RuntimeException )
398 {
399 	ScCellRangesBase* pUno = ScCellRangesBase::getImplementation( xIf );
400 	if ( !pUno )
401 		throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "Failed to access underlying uno range object" ) ), uno::Reference< uno::XInterface >()  );
402 	return pUno->GetDocShell();
403 }
404 
405 ScDocShell*
406 getDocShellFromRange( const uno::Reference< table::XCellRange >& xRange ) throw ( uno::RuntimeException )
407 {
408 	// need the ScCellRangesBase to get docshell
409     uno::Reference< uno::XInterface > xIf( xRange );
410 	return getDocShellFromIf(xIf );
411 }
412 
413 ScDocShell*
414 getDocShellFromRanges( const uno::Reference< sheet::XSheetCellRangeContainer >& xRanges ) throw ( uno::RuntimeException )
415 {
416 	// need the ScCellRangesBase to get docshell
417     uno::Reference< uno::XInterface > xIf( xRanges );
418 	return getDocShellFromIf(xIf );
419 }
420 
421 uno::Reference< frame::XModel > getModelFromXIf( const uno::Reference< uno::XInterface >& xIf ) throw ( uno::RuntimeException )
422 {
423 	ScDocShell* pDocShell = getDocShellFromIf(xIf );
424 	return pDocShell->GetModel();
425 }
426 
427 uno::Reference< frame::XModel > getModelFromRange( const uno::Reference< table::XCellRange >& xRange ) throw ( uno::RuntimeException )
428 {
429     // the XInterface for getImplementation can be any derived interface, no need for queryInterface
430     uno::Reference< uno::XInterface > xIf( xRange );
431 	return getModelFromXIf( xIf );
432 }
433 
434 ScDocument*
435 getDocumentFromRange( const uno::Reference< table::XCellRange >& xRange )
436 {
437 	ScDocShell* pDocShell = getDocShellFromRange( xRange );
438 	if ( !pDocShell )
439 		throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "Failed to access underlying docshell from uno range object" ) ), uno::Reference< uno::XInterface >() );
440 	ScDocument* pDoc = pDocShell->GetDocument();
441 	return pDoc;
442 }
443 
444 
445 ScDocument*
446 ScVbaRange::getScDocument() throw (uno::RuntimeException)
447 {
448 	if ( mxRanges.is() )
449 	{
450 		uno::Reference< container::XIndexAccess > xIndex( mxRanges, uno::UNO_QUERY_THROW );
451 		uno::Reference< table::XCellRange > xRange( xIndex->getByIndex( 0 ), uno::UNO_QUERY_THROW );
452 		return getDocumentFromRange( xRange );
453 	}
454 	return getDocumentFromRange( mxRange );
455 }
456 
457 ScDocShell*
458 ScVbaRange::getScDocShell() throw (uno::RuntimeException)
459 {
460 	if ( mxRanges.is() )
461 	{
462 		uno::Reference< container::XIndexAccess > xIndex( mxRanges, uno::UNO_QUERY_THROW );
463 		uno::Reference< table::XCellRange > xRange( xIndex->getByIndex( 0 ), uno::UNO_QUERY_THROW );
464 		return getDocShellFromRange( xRange );
465 	}
466 	return getDocShellFromRange( mxRange );
467 }
468 
469 /*static*/ ScVbaRange* ScVbaRange::getImplementation( const uno::Reference< excel::XRange >& rxRange )
470 {
471     // FIXME: always save to use dynamic_cast? Or better to (implement and) use XTunnel?
472     return dynamic_cast< ScVbaRange* >( rxRange.get() );
473 }
474 
475 uno::Reference< frame::XModel > ScVbaRange::getUnoModel() throw (uno::RuntimeException)
476 {
477     if( ScDocShell* pDocShell = getScDocShell() )
478         return pDocShell->GetModel();
479     throw uno::RuntimeException();
480 }
481 
482 /*static*/ uno::Reference< frame::XModel > ScVbaRange::getUnoModel( const uno::Reference< excel::XRange >& rxRange ) throw (uno::RuntimeException)
483 {
484     if( ScVbaRange* pScVbaRange = getImplementation( rxRange ) )
485         return pScVbaRange->getUnoModel();
486     throw uno::RuntimeException();
487 }
488 
489 const ScRangeList& ScVbaRange::getScRangeList() throw (uno::RuntimeException)
490 {
491     if( ScCellRangesBase* pScRangesBase = getCellRangesBase() )
492         return pScRangesBase->GetRangeList();
493     throw uno::RuntimeException( ::rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "Cannot obtain UNO range implementation object" ) ), uno::Reference< uno::XInterface >() );
494 }
495 
496 /*static*/ const ScRangeList& ScVbaRange::getScRangeList( const uno::Reference< excel::XRange >& rxRange ) throw (uno::RuntimeException)
497 {
498     if( ScVbaRange* pScVbaRange = getImplementation( rxRange ) )
499         return pScVbaRange->getScRangeList();
500     throw uno::RuntimeException( ::rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "Cannot obtain VBA range implementation object" ) ), uno::Reference< uno::XInterface >() );
501 }
502 
503 
504 class NumFormatHelper
505 {
506 	uno::Reference< util::XNumberFormatsSupplier > mxSupplier;
507 	uno::Reference< beans::XPropertySet > mxRangeProps;
508 	uno::Reference< util::XNumberFormats > mxFormats;
509 public:
510 	NumFormatHelper( const uno::Reference< table::XCellRange >& xRange )
511 	{
512 		mxSupplier.set( getModelFromRange( xRange ), uno::UNO_QUERY_THROW );
513 		mxRangeProps.set( xRange, uno::UNO_QUERY_THROW);
514 		mxFormats = mxSupplier->getNumberFormats();
515 	}
516 	uno::Reference< beans::XPropertySet > getNumberProps()
517 	{
518 		long nIndexKey = 0;
519 		uno::Any aValue = mxRangeProps->getPropertyValue(rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("NumberFormat")));
520 		aValue >>= nIndexKey;
521 
522 		if ( mxFormats.is() )
523 			return  mxFormats->getByKey( nIndexKey );
524 		return	uno::Reference< beans::XPropertySet > ();
525 	}
526 
527 	bool isBooleanType()
528 	{
529 
530 		if ( getNumberFormat() & util::NumberFormat::LOGICAL )
531 			return true;
532 		return false;
533 	}
534 
535 	bool isDateType()
536 	{
537 		sal_Int16 nType = getNumberFormat();
538 		if(( nType & util::NumberFormat::DATETIME ))
539 		{
540 			return true;
541 		}
542 		return false;
543 	}
544 
545 	rtl::OUString getNumberFormatString()
546 	{
547 		uno::Reference< uno::XInterface > xIf( mxRangeProps, uno::UNO_QUERY_THROW );
548 		ScCellRangesBase* pUnoCellRange = ScCellRangesBase::getImplementation( xIf );
549 		if ( pUnoCellRange )
550 		{
551 
552 			SfxItemSet* pDataSet = 	excel::ScVbaCellRangeAccess::GetDataSet( pUnoCellRange );
553 			SfxItemState eState = pDataSet->GetItemState( ATTR_VALUE_FORMAT, sal_True, NULL);
554 			// one of the cells in the range is not like the other ;-)
555 			// so return a zero length format to indicate that
556 			if ( eState == SFX_ITEM_DONTCARE )
557 				return rtl::OUString();
558 		}
559 
560 
561 		uno::Reference< beans::XPropertySet > xNumberProps( getNumberProps(), uno::UNO_QUERY_THROW );
562 		::rtl::OUString aFormatString;
563 		uno::Any aString = xNumberProps->getPropertyValue(rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("FormatString")));
564 		aString >>= aFormatString;
565 		return aFormatString;
566 	}
567 
568 	sal_Int16 getNumberFormat()
569 	{
570 		uno::Reference< beans::XPropertySet > xNumberProps = getNumberProps();
571 		sal_Int16 nType = ::comphelper::getINT16(
572         	xNumberProps->getPropertyValue( ::rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "Type" ) ) ) );
573 		return nType;
574 	}
575 
576 	bool setNumberFormat( const rtl::OUString& rFormat )
577 	{
578         // #163288# treat "General" as "Standard" format
579         sal_Int32 nNewIndex = 0;
580         if( !rFormat.equalsIgnoreAsciiCaseAsciiL( RTL_CONSTASCII_STRINGPARAM( "General" ) ) )
581         {
582     		lang::Locale aLocale;
583     		uno::Reference< beans::XPropertySet > xNumProps = getNumberProps();
584     		xNumProps->getPropertyValue( ::rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "Locale" ) ) ) >>= aLocale;
585     		nNewIndex = mxFormats->queryKey( rFormat, aLocale, false );
586     		if ( nNewIndex == -1 ) // format not defined
587     			nNewIndex = mxFormats->addNew( rFormat, aLocale );
588         }
589 		mxRangeProps->setPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("NumberFormat") ), uno::makeAny( nNewIndex ) );
590 		return true;
591 	}
592 
593 	bool setNumberFormat( sal_Int16 nType )
594 	{
595 		uno::Reference< beans::XPropertySet > xNumberProps = getNumberProps();
596 		lang::Locale aLocale;
597 		xNumberProps->getPropertyValue( ::rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "Locale" ) ) ) >>= aLocale;
598 		uno::Reference<util::XNumberFormatTypes> xTypes( mxFormats, uno::UNO_QUERY );
599 		if ( xTypes.is() )
600 		{
601 			sal_Int32 nNewIndex = xTypes->getStandardFormat( nType, aLocale );
602        		mxRangeProps->setPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("NumberFormat") ), uno::makeAny( nNewIndex ) );
603 			return true;
604 		}
605 		return false;
606 	}
607 
608 };
609 
610 struct CellPos
611 {
612 	CellPos():m_nRow(-1), m_nCol(-1), m_nArea(0) {};
613 	CellPos( sal_Int32 nRow, sal_Int32 nCol, sal_Int32 nArea ):m_nRow(nRow), m_nCol(nCol), m_nArea( nArea ) {};
614 sal_Int32 m_nRow;
615 sal_Int32 m_nCol;
616 sal_Int32 m_nArea;
617 };
618 
619 typedef ::cppu::WeakImplHelper1< container::XEnumeration > CellsEnumeration_BASE;
620 typedef ::std::vector< CellPos > vCellPos;
621 
622 // #FIXME - QUICK
623 // we could probably could and should modify CellsEnumeration below
624 // to handle rows and columns ( but I do this seperately for now
625 // and.. this class only handles singe areas ( does it have to handle
626 // multi area ranges?? )
627 class ColumnsRowEnumeration: public CellsEnumeration_BASE
628 {
629 	uno::Reference< uno::XComponentContext > mxContext;
630         uno::Reference< excel::XRange > mxRange;
631 	sal_Int32 mMaxElems;
632 	sal_Int32 mCurElem;
633 
634 public:
635 	ColumnsRowEnumeration( const uno::Reference< uno::XComponentContext >& xContext, const uno::Reference< excel::XRange >& xRange, sal_Int32 nElems ) : mxContext( xContext ), mxRange( xRange ), mMaxElems( nElems ), mCurElem( 0 )
636         {
637 	}
638 
639 	virtual ::sal_Bool SAL_CALL hasMoreElements() throw (::uno::RuntimeException){ return mCurElem < mMaxElems; }
640 
641 	virtual uno::Any SAL_CALL nextElement() throw (container::NoSuchElementException, lang::WrappedTargetException, uno::RuntimeException)
642 	{
643 		if ( !hasMoreElements() )
644 			throw container::NoSuchElementException();
645 		sal_Int32 vbaIndex = 1 + mCurElem++;
646 		return uno::makeAny( mxRange->Item( uno::makeAny( vbaIndex ), uno::Any() ) );
647 	}
648 };
649 
650 class CellsEnumeration : public CellsEnumeration_BASE
651 {
652     uno::WeakReference< XHelperInterface > mxParent;
653 	uno::Reference< uno::XComponentContext > mxContext;
654 	uno::Reference< XCollection > m_xAreas;
655 	vCellPos m_CellPositions;
656 	vCellPos::const_iterator m_it;
657 
658 	uno::Reference< table::XCellRange > getArea( sal_Int32 nVBAIndex ) throw ( uno::RuntimeException )
659 	{
660 		if ( nVBAIndex < 1 || nVBAIndex > m_xAreas->getCount() )
661 			throw uno::RuntimeException();
662 		uno::Reference< excel::XRange > xRange( m_xAreas->Item( uno::makeAny(nVBAIndex), uno::Any() ), uno::UNO_QUERY_THROW );
663 		uno::Reference< table::XCellRange > xCellRange( ScVbaRange::getCellRange( xRange ), uno::UNO_QUERY_THROW );
664 		return xCellRange;
665 	}
666 
667     void populateArea( sal_Int32 nVBAIndex )
668 	{
669 		uno::Reference< table::XCellRange > xRange = getArea( nVBAIndex );
670 		uno::Reference< table::XColumnRowRange > xColumnRowRange(xRange, uno::UNO_QUERY_THROW );
671 		sal_Int32 nRowCount =  xColumnRowRange->getRows()->getCount();
672 		sal_Int32 nColCount = xColumnRowRange->getColumns()->getCount();
673 		for ( sal_Int32 i=0; i<nRowCount; ++i )
674 		{
675 			for ( sal_Int32 j=0; j<nColCount; ++j )
676 				m_CellPositions.push_back( CellPos( i,j,nVBAIndex ) );
677 		}
678 	}
679 public:
680     CellsEnumeration( const uno::Reference< XHelperInterface >& xParent, const uno::Reference< uno::XComponentContext >& xContext, const uno::Reference< XCollection >& xAreas ): mxParent( xParent ), mxContext( xContext ), m_xAreas( xAreas )
681 	{
682 		sal_Int32 nItems = m_xAreas->getCount();
683 		for ( sal_Int32 index=1; index <= nItems; ++index )
684 		{
685         		populateArea( index );
686 		}
687 		m_it = m_CellPositions.begin();
688 	}
689 	virtual ::sal_Bool SAL_CALL hasMoreElements() throw (::uno::RuntimeException){ return m_it != m_CellPositions.end(); }
690 
691 	virtual uno::Any SAL_CALL nextElement() throw (container::NoSuchElementException, lang::WrappedTargetException, uno::RuntimeException)
692 	{
693 		if ( !hasMoreElements() )
694 			throw container::NoSuchElementException();
695 		CellPos aPos = *(m_it)++;
696 
697 		uno::Reference< table::XCellRange > xRangeArea = getArea( aPos.m_nArea );
698 		uno::Reference< table::XCellRange > xCellRange( xRangeArea->getCellByPosition(  aPos.m_nCol, aPos.m_nRow ), uno::UNO_QUERY_THROW );
699         return uno::makeAny( uno::Reference< excel::XRange >( new ScVbaRange( mxParent, mxContext, xCellRange ) ) );
700 
701 	}
702 };
703 
704 
705 const static ::rtl::OUString ISVISIBLE(  RTL_CONSTASCII_USTRINGPARAM( "IsVisible"));
706 const static ::rtl::OUString WIDTH(  RTL_CONSTASCII_USTRINGPARAM( "Width"));
707 const static ::rtl::OUString HEIGHT(  RTL_CONSTASCII_USTRINGPARAM( "Height"));
708 const static ::rtl::OUString POSITION(  RTL_CONSTASCII_USTRINGPARAM( "Position"));
709 const static rtl::OUString EQUALS( RTL_CONSTASCII_USTRINGPARAM("=") );
710 const static rtl::OUString NOTEQUALS( RTL_CONSTASCII_USTRINGPARAM("<>") );
711 const static rtl::OUString GREATERTHAN( RTL_CONSTASCII_USTRINGPARAM(">") );
712 const static rtl::OUString GREATERTHANEQUALS( RTL_CONSTASCII_USTRINGPARAM(">=") );
713 const static rtl::OUString LESSTHAN( RTL_CONSTASCII_USTRINGPARAM("<") );
714 const static rtl::OUString LESSTHANEQUALS( RTL_CONSTASCII_USTRINGPARAM("<=") );
715 const static rtl::OUString CONTS_HEADER( RTL_CONSTASCII_USTRINGPARAM("ContainsHeader" ));
716 const static rtl::OUString INSERTPAGEBREAKS( RTL_CONSTASCII_USTRINGPARAM("InsertPageBreaks" ));
717 const static rtl::OUString STR_ERRORMESSAGE_APPLIESTOSINGLERANGEONLY( RTL_CONSTASCII_USTRINGPARAM("The command you chose cannot be performed with multiple selections.\nSelect a single range and click the command again") );
718 const static rtl::OUString STR_ERRORMESSAGE_NOCELLSWEREFOUND( RTL_CONSTASCII_USTRINGPARAM("No cells were found") );
719 const static rtl::OUString STR_ERRORMESSAGE_APPLIESTOROWCOLUMNSONLY( RTL_CONSTASCII_USTRINGPARAM("Property only applicable for Columns and Rows") );
720 const static rtl::OUString CELLSTYLE( RTL_CONSTASCII_USTRINGPARAM("CellStyle") );
721 
722 class CellValueSetter : public ValueSetter
723 {
724 protected:
725 	uno::Any maValue;
726 	uno::TypeClass mTypeClass;
727 public:
728 	CellValueSetter( const uno::Any& aValue );
729 	virtual bool processValue( const uno::Any& aValue,  const uno::Reference< table::XCell >& xCell );
730 	virtual void visitNode( sal_Int32 x, sal_Int32 y, const uno::Reference< table::XCell >& xCell );
731 
732 };
733 
734 CellValueSetter::CellValueSetter( const uno::Any& aValue ): maValue( aValue ), mTypeClass( aValue.getValueTypeClass() ) {}
735 
736 void
737 CellValueSetter::visitNode( sal_Int32 /*i*/, sal_Int32 /*j*/, const uno::Reference< table::XCell >& xCell )
738 {
739 	processValue( maValue, xCell );
740 }
741 
742 bool
743 CellValueSetter::processValue( const uno::Any& aValue, const uno::Reference< table::XCell >& xCell )
744 {
745 
746 	bool isExtracted = false;
747 	switch ( aValue.getValueTypeClass() )
748 	{
749 		case  uno::TypeClass_BOOLEAN:
750 		{
751 			sal_Bool bState = sal_False;
752 			if ( aValue >>= bState 	 )
753 			{
754 				uno::Reference< table::XCellRange > xRange( xCell, uno::UNO_QUERY_THROW );
755 				if ( bState )
756 					xCell->setValue( (double) 1 );
757 				else
758 					xCell->setValue( (double) 0 );
759 				NumFormatHelper cellNumFormat( xRange );
760 				cellNumFormat.setNumberFormat( util::NumberFormat::LOGICAL );
761 			}
762 			break;
763 		}
764 		case uno::TypeClass_STRING:
765 		{
766 			rtl::OUString aString;
767 			if ( aValue >>= aString )
768 			{
769                 // The required behavior for a string value is:
770                 // 1. If the first character is a single quote, use the rest as a string cell, regardless of the cell's number format.
771                 // 2. Otherwise, if the cell's number format is "text", use the string value as a string cell.
772                 // 3. Otherwise, parse the string value in English locale, and apply a corresponding number format with the cell's locale
773                 //    if the cell's number format was "General".
774                 // Case 1 is handled here, the rest in ScCellObj::InputEnglishString
775 
776                 if ( aString.toChar() == '\'' )     // case 1 - handle with XTextRange
777                 {
778                     rtl::OUString aRemainder( aString.copy(1) );    // strip the quote
779                     uno::Reference< text::XTextRange > xTextRange( xCell, uno::UNO_QUERY_THROW );
780                     xTextRange->setString( aRemainder );
781                 }
782                 else
783                 {
784                     // call implementation method InputEnglishString
785                     ScCellObj* pCellObj = dynamic_cast< ScCellObj* >( xCell.get() );
786                     if ( pCellObj )
787                         pCellObj->InputEnglishString( aString );
788                 }
789 			}
790 			else
791 				isExtracted = false;
792 			break;
793 		}
794 		default:
795 		{
796 			double nDouble = 0.0;
797 			if ( aValue >>= nDouble )
798 				xCell->setValue( nDouble );
799 			else
800 				isExtracted = false;
801 			break;
802 		}
803 	}
804 	return isExtracted;
805 
806 }
807 
808 
809 class CellValueGetter : public ValueGetter
810 {
811 protected:
812 	uno::Any maValue;
813 	uno::TypeClass mTypeClass;
814 public:
815 	CellValueGetter() {}
816 	virtual void visitNode( sal_Int32 x, sal_Int32 y, const uno::Reference< table::XCell >& xCell );
817 	virtual void processValue( sal_Int32 x, sal_Int32 y, const uno::Any& aValue );
818 	const uno::Any& getValue() const { return maValue; }
819 
820 };
821 
822 void
823 CellValueGetter::processValue(  sal_Int32 /*x*/, sal_Int32 /*y*/, const uno::Any& aValue )
824 {
825 	maValue = aValue;
826 }
827 void CellValueGetter::visitNode( sal_Int32 x, sal_Int32 y, const uno::Reference< table::XCell >& xCell )
828 {
829 	uno::Any aValue;
830 	table::CellContentType eType = xCell->getType();
831 	if( eType == table::CellContentType_VALUE || eType == table::CellContentType_FORMULA )
832 	{
833 		if ( eType == table::CellContentType_FORMULA )
834 		{
835 
836 			rtl::OUString sFormula = xCell->getFormula();
837 			if ( sFormula.equals( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("=TRUE()") ) ) )
838 				aValue <<= sal_True;
839 			else if ( sFormula.equals( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("=FALSE()") ) ) )
840 				aValue <<= sal_False;
841 			else
842 			{
843 				uno::Reference< beans::XPropertySet > xProp( xCell, uno::UNO_QUERY_THROW );
844 
845 				table::CellContentType eFormulaType = table::CellContentType_VALUE;
846 				// some formulas give textual results
847 				xProp->getPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("FormulaResultType" ) ) ) >>= eFormulaType;
848 
849 				if ( eFormulaType == table::CellContentType_TEXT )
850 				{
851 					uno::Reference< text::XTextRange > xTextRange(xCell, ::uno::UNO_QUERY_THROW);
852 					aValue <<= xTextRange->getString();
853 				}
854 				else
855 					aValue <<= xCell->getValue();
856 			}
857 		}
858 		else
859 		{
860 			uno::Reference< table::XCellRange > xRange( xCell, uno::UNO_QUERY_THROW );
861 			NumFormatHelper cellFormat( xRange );
862 			if ( cellFormat.isBooleanType() )
863 				aValue = uno::makeAny( ( xCell->getValue() != 0.0 ) );
864 			else if ( cellFormat.isDateType() )
865 				aValue = uno::makeAny( bridge::oleautomation::Date( xCell->getValue() ) );
866 			else
867 				aValue <<= xCell->getValue();
868 		}
869 	}
870 	if( eType == table::CellContentType_TEXT )
871 	{
872 		uno::Reference< text::XTextRange > xTextRange(xCell, ::uno::UNO_QUERY_THROW);
873 		aValue <<= xTextRange->getString();
874 	}
875 	processValue( x,y,aValue );
876 }
877 
878 class CellFormulaValueSetter : public CellValueSetter
879 {
880 private:
881 	ScDocument*  m_pDoc;
882     formula::FormulaGrammar::Grammar m_eGrammar;
883 public:
884 	CellFormulaValueSetter( const uno::Any& aValue, ScDocument* pDoc, formula::FormulaGrammar::Grammar eGram ):CellValueSetter( aValue ),  m_pDoc( pDoc ), m_eGrammar( eGram ){}
885 protected:
886 	bool processValue( const uno::Any& aValue, const uno::Reference< table::XCell >& xCell )
887 	{
888 		rtl::OUString sFormula;
889 		double aDblValue = 0.0;
890 		if ( aValue >>= sFormula )
891 		{
892             // convert to CONV_OOO style formula string because XCell::setFormula
893             // always compile it in CONV_OOO style.  Perhaps css.sheet.FormulaParser
894             // should be used in future to directly pass formula tokens.
895             if ( m_eGrammar != formula::FormulaGrammar::GRAM_PODF_A1 && ( sFormula.trim().indexOf('=') == 0 ) )
896 			{
897 				uno::Reference< uno::XInterface > xIf( xCell, uno::UNO_QUERY_THROW );
898 				ScCellRangesBase* pUnoRangesBase = dynamic_cast< ScCellRangesBase* >( xIf.get() );
899 				if ( pUnoRangesBase )
900 				{
901 					ScRangeList aCellRanges = pUnoRangesBase->GetRangeList();
902 					ScCompiler aCompiler( m_pDoc, aCellRanges.First()->aStart );
903                     aCompiler.SetGrammar(m_eGrammar);
904 					// compile the string in the format passed in
905 					aCompiler.CompileString( sFormula );
906 					// set desired convention to that of the document
907                     aCompiler.SetGrammar( formula::FormulaGrammar::GRAM_PODF_A1 );
908 					String sConverted;
909 					aCompiler.CreateStringFromTokenArray(sConverted);
910 					sFormula = EQUALS + sConverted;
911 				}
912 			}
913 
914 			xCell->setFormula( sFormula );
915 			return true;
916 		}
917 		else if ( aValue >>= aDblValue )
918 		{
919 			xCell->setValue( aDblValue );
920 			return true;
921 		}
922 		return false;
923 	}
924 
925 };
926 
927 class CellFormulaValueGetter : public CellValueGetter
928 {
929 private:
930 	ScDocument*  m_pDoc;
931     formula::FormulaGrammar::Grammar m_eGrammar;
932 public:
933 	CellFormulaValueGetter(ScDocument* pDoc, formula::FormulaGrammar::Grammar eGram ) : CellValueGetter( ), m_pDoc( pDoc ), m_eGrammar( eGram ) {}
934 	virtual void visitNode( sal_Int32 x, sal_Int32 y, const uno::Reference< table::XCell >& xCell )
935 	{
936 		uno::Any aValue;
937 		aValue <<= xCell->getFormula();
938 		rtl::OUString sVal;
939 		aValue >>= sVal;
940 		uno::Reference< uno::XInterface > xIf( xCell, uno::UNO_QUERY_THROW );
941 		ScCellRangesBase* pUnoRangesBase = dynamic_cast< ScCellRangesBase* >( xIf.get() );
942 		if ( ( xCell->getType() == table::CellContentType_FORMULA ) &&
943 			pUnoRangesBase )
944 		{
945 			ScRangeList aCellRanges = pUnoRangesBase->GetRangeList();
946 			ScCompiler aCompiler( m_pDoc, aCellRanges.First()->aStart );
947             aCompiler.SetGrammar(formula::FormulaGrammar::GRAM_DEFAULT);
948 			aCompiler.CompileString( sVal );
949 			// set desired convention
950             aCompiler.SetGrammar( m_eGrammar );
951 			String sConverted;
952 			aCompiler.CreateStringFromTokenArray(sConverted);
953 			sVal = EQUALS + sConverted;
954 			aValue <<= sVal;
955 		}
956 
957 		processValue( x,y,aValue );
958 	}
959 
960 };
961 
962 
963 class Dim2ArrayValueGetter : public ArrayVisitor
964 {
965 protected:
966 	uno::Any maValue;
967 	ValueGetter& mValueGetter;
968 	virtual void processValue( sal_Int32 x, sal_Int32 y, const uno::Any& aValue )
969 	{
970 		uno::Sequence< uno::Sequence< uno::Any > >& aMatrix = *( uno::Sequence< uno::Sequence< uno::Any > >* )( maValue.getValue() );
971 		aMatrix[x][y] = aValue;
972 	}
973 
974 public:
975 	Dim2ArrayValueGetter(sal_Int32 nRowCount, sal_Int32 nColCount, ValueGetter& rValueGetter ): mValueGetter(rValueGetter)
976 	{
977 		uno::Sequence< uno::Sequence< uno::Any > > aMatrix;
978 		aMatrix.realloc( nRowCount );
979 		for ( sal_Int32 index = 0; index < nRowCount; ++index )
980 			aMatrix[index].realloc( nColCount );
981 		maValue <<= aMatrix;
982 	}
983 	void visitNode( sal_Int32 x, sal_Int32 y, const uno::Reference< table::XCell >& xCell )
984 
985 	{
986 		mValueGetter.visitNode( x, y, xCell );
987 		processValue( x, y, mValueGetter.getValue() );
988 	}
989 	const uno::Any& getValue() const { return maValue; }
990 
991 };
992 
993 const static rtl::OUString sNA = rtl::OUString::createFromAscii("#N/A");
994 
995 class Dim1ArrayValueSetter : public ArrayVisitor
996 {
997 	uno::Sequence< uno::Any > aMatrix;
998 	sal_Int32 nColCount;
999 	ValueSetter& mCellValueSetter;
1000 public:
1001 	Dim1ArrayValueSetter( const uno::Any& aValue, ValueSetter& rCellValueSetter ):mCellValueSetter( rCellValueSetter )
1002 	{
1003 		aValue >>= aMatrix;
1004 		nColCount = aMatrix.getLength();
1005 	}
1006 	virtual void visitNode( sal_Int32 /*x*/, sal_Int32 y, const uno::Reference< table::XCell >& xCell )
1007 	{
1008 		if ( y < nColCount )
1009 			mCellValueSetter.processValue( aMatrix[ y ], xCell );
1010 		else
1011 			mCellValueSetter.processValue( uno::makeAny( sNA ), xCell );
1012 	}
1013 };
1014 
1015 
1016 
1017 class Dim2ArrayValueSetter : public ArrayVisitor
1018 {
1019 	uno::Sequence< uno::Sequence< uno::Any > > aMatrix;
1020 	ValueSetter& mCellValueSetter;
1021 	sal_Int32 nRowCount;
1022 	sal_Int32 nColCount;
1023 public:
1024 	Dim2ArrayValueSetter( const uno::Any& aValue, ValueSetter& rCellValueSetter ) : mCellValueSetter( rCellValueSetter )
1025 	{
1026 		aValue >>= aMatrix;
1027 		nRowCount = aMatrix.getLength();
1028 		nColCount = aMatrix[0].getLength();
1029 	}
1030 
1031 	virtual void visitNode( sal_Int32 x, sal_Int32 y, const uno::Reference< table::XCell >& xCell )
1032 	{
1033 		if ( x < nRowCount && y < nColCount )
1034 			mCellValueSetter.processValue( aMatrix[ x ][ y ], xCell );
1035 		else
1036 			mCellValueSetter.processValue( uno::makeAny( sNA ), xCell );
1037 
1038 	}
1039 };
1040 
1041 class RangeProcessor
1042 {
1043 public:
1044 	virtual void process( const uno::Reference< excel::XRange >& xRange ) = 0;
1045 };
1046 
1047 class RangeValueProcessor : public RangeProcessor
1048 {
1049 	const uno::Any& m_aVal;
1050 public:
1051 	RangeValueProcessor( const uno::Any& rVal ):m_aVal( rVal ) {}
1052 	virtual void process( const uno::Reference< excel::XRange >& xRange )
1053 	{
1054 		xRange->setValue( m_aVal );
1055 	}
1056 };
1057 
1058 class RangeFormulaProcessor : public RangeProcessor
1059 {
1060 	const uno::Any& m_aVal;
1061 public:
1062 	RangeFormulaProcessor( const uno::Any& rVal ):m_aVal( rVal ) {}
1063 	virtual void process( const uno::Reference< excel::XRange >& xRange )
1064 	{
1065 		xRange->setFormula( m_aVal );
1066 	}
1067 };
1068 
1069 class RangeCountProcessor : public RangeProcessor
1070 {
1071 	sal_Int32 nCount;
1072 public:
1073 	RangeCountProcessor():nCount(0){}
1074 	virtual void process( const uno::Reference< excel::XRange >& xRange )
1075 	{
1076 		nCount = nCount + xRange->getCount();
1077 	}
1078 	sal_Int32 value() { return nCount; }
1079 };
1080 class AreasVisitor
1081 {
1082 private:
1083 	uno::Reference< XCollection > m_Areas;
1084 public:
1085 	AreasVisitor( const uno::Reference< XCollection >& rAreas ):m_Areas( rAreas ){}
1086 
1087 	void visit( RangeProcessor& processor )
1088 	{
1089 		if ( m_Areas.is() )
1090 		{
1091 			sal_Int32 nItems = m_Areas->getCount();
1092 			for ( sal_Int32 index=1; index <= nItems; ++index )
1093 			{
1094 				uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny(index), uno::Any() ), uno::UNO_QUERY_THROW );
1095 				processor.process( xRange );
1096 			}
1097 		}
1098 	}
1099 };
1100 
1101 class RangeHelper
1102 {
1103 	uno::Reference< table::XCellRange > m_xCellRange;
1104 
1105 public:
1106 	RangeHelper( const uno::Reference< table::XCellRange >& xCellRange ) throw (uno::RuntimeException) : m_xCellRange( xCellRange )
1107 	{
1108 		if ( !m_xCellRange.is() )
1109 			throw uno::RuntimeException();
1110 	}
1111 	RangeHelper( const uno::Any aCellRange ) throw (uno::RuntimeException)
1112 	{
1113 		m_xCellRange.set( aCellRange, uno::UNO_QUERY_THROW );
1114 	}
1115 	uno::Reference< sheet::XSheetCellRange > getSheetCellRange() throw (uno::RuntimeException)
1116 	{
1117 		return uno::Reference< sheet::XSheetCellRange >(m_xCellRange, uno::UNO_QUERY_THROW);
1118 	}
1119 	uno::Reference< sheet::XSpreadsheet >  getSpreadSheet() throw (uno::RuntimeException)
1120 	{
1121 		return getSheetCellRange()->getSpreadsheet();
1122 	}
1123 
1124 	uno::Reference< table::XCellRange > getCellRangeFromSheet() throw (uno::RuntimeException)
1125 	{
1126 		return uno::Reference< table::XCellRange >(getSpreadSheet(), uno::UNO_QUERY_THROW );
1127 	}
1128 
1129 	uno::Reference< sheet::XCellRangeAddressable >  getCellRangeAddressable() throw (uno::RuntimeException)
1130 	{
1131 		return uno::Reference< sheet::XCellRangeAddressable >(m_xCellRange, ::uno::UNO_QUERY_THROW);
1132 
1133 	}
1134 
1135 	uno::Reference< sheet::XSheetCellCursor > getSheetCellCursor() throw ( uno::RuntimeException )
1136 	{
1137 		return 	uno::Reference< sheet::XSheetCellCursor >( getSpreadSheet()->createCursorByRange( getSheetCellRange() ), uno::UNO_QUERY_THROW );
1138 	}
1139 
1140 	static uno::Reference< excel::XRange > createRangeFromRange( const uno::Reference< XHelperInterface >& xParent, const uno::Reference<uno::XComponentContext >& xContext,
1141 		const uno::Reference< table::XCellRange >& xRange, const uno::Reference< sheet::XCellRangeAddressable >& xCellRangeAddressable,
1142 		sal_Int32 nStartColOffset = 0, sal_Int32 nStartRowOffset = 0, sal_Int32 nEndColOffset = 0, sal_Int32 nEndRowOffset = 0 )
1143 	{
1144 		return uno::Reference< excel::XRange >( new ScVbaRange( xParent, xContext,
1145 			xRange->getCellRangeByPosition(
1146 				xCellRangeAddressable->getRangeAddress().StartColumn + nStartColOffset,
1147 				xCellRangeAddressable->getRangeAddress().StartRow + nStartRowOffset,
1148 				xCellRangeAddressable->getRangeAddress().EndColumn + nEndColOffset,
1149 				xCellRangeAddressable->getRangeAddress().EndRow + nEndRowOffset ) ) );
1150 	}
1151 
1152 };
1153 
1154 bool
1155 getCellRangesForAddress( sal_uInt16& rResFlags, const rtl::OUString& sAddress, ScDocShell* pDocSh, ScRangeList& rCellRanges, formula::FormulaGrammar::AddressConvention& eConv )
1156 {
1157 
1158 	ScDocument* pDoc = NULL;
1159 	if ( pDocSh )
1160 	{
1161 		pDoc = pDocSh->GetDocument();
1162 		String aString(sAddress);
1163 		sal_uInt16 nMask = SCA_VALID;
1164 		//sal_uInt16 nParse = rCellRanges.Parse( sAddress, pDoc, nMask, formula::FormulaGrammar::CONV_XL_A1 );
1165 		rResFlags = rCellRanges.Parse( sAddress, pDoc, nMask, eConv, 0 );
1166 		if ( rResFlags & SCA_VALID )
1167 		{
1168 			return true;
1169 		}
1170 	}
1171 	return false;
1172 }
1173 
1174 bool getScRangeListForAddress( const rtl::OUString& sName, ScDocShell* pDocSh, ScRange& refRange, ScRangeList& aCellRanges, formula::FormulaGrammar::AddressConvention aConv = formula::FormulaGrammar::CONV_XL_A1 ) throw ( uno::RuntimeException )
1175 {
1176 	// see if there is a match with a named range
1177 	uno::Reference< beans::XPropertySet > xProps( pDocSh->GetModel(), uno::UNO_QUERY_THROW );
1178 	uno::Reference< container::XNameAccess > xNameAccess( xProps->getPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("NamedRanges") ) ), uno::UNO_QUERY_THROW );
1179 	// Strangly enough you can have Range( "namedRange1, namedRange2, etc," )
1180 	// loop around each ',' seperated name
1181 	std::vector< rtl::OUString > vNames;
1182 	sal_Int32 nIndex = 0;
1183 	do
1184 	{
1185 		rtl::OUString aToken = sName.getToken( 0, ',', nIndex );
1186 		vNames.push_back( aToken );
1187 	} while ( nIndex >= 0 );
1188 
1189 	if ( !vNames.size() )
1190 		vNames.push_back( sName );
1191 
1192 	std::vector< rtl::OUString >::iterator it = vNames.begin();
1193 	std::vector< rtl::OUString >::iterator it_end = vNames.end();
1194 	for ( ; it != it_end; ++it )
1195 	{
1196 
1197 		formula::FormulaGrammar::AddressConvention eConv = aConv;
1198 		// spaces are illegal ( but the user of course can enter them )
1199 		rtl::OUString sAddress = (*it).trim();
1200 		if ( xNameAccess->hasByName( sAddress ) )
1201 		{
1202 			uno::Reference< sheet::XNamedRange > xNamed( xNameAccess->getByName( sAddress ), uno::UNO_QUERY_THROW );
1203 			sAddress = xNamed->getContent();
1204 			// As the address comes from OOO, the addressing
1205 			// style is may not be XL_A1
1206 			eConv = pDocSh->GetDocument()->GetAddressConvention();
1207 		}
1208 
1209 		sal_uInt16 nFlags = 0;
1210 		if ( !getCellRangesForAddress( nFlags, sAddress, pDocSh, aCellRanges, eConv ) )
1211 			return false;
1212 
1213 		bool bTabFromReferrer = !( nFlags & SCA_TAB_3D );
1214 
1215 		for ( ScRange* pRange = aCellRanges.First() ; pRange; pRange = aCellRanges.Next() )
1216 		{
1217 			pRange->aStart.SetCol( refRange.aStart.Col() + pRange->aStart.Col() );
1218 			pRange->aStart.SetRow( refRange.aStart.Row() + pRange->aStart.Row() );
1219 			pRange->aStart.SetTab( bTabFromReferrer ? refRange.aStart.Tab()  : pRange->aStart.Tab() );
1220 			pRange->aEnd.SetCol( refRange.aStart.Col() + pRange->aEnd.Col() );
1221 			pRange->aEnd.SetRow( refRange.aStart.Row() + pRange->aEnd.Row() );
1222 			pRange->aEnd.SetTab( bTabFromReferrer ? refRange.aEnd.Tab()  : pRange->aEnd.Tab() );
1223 		}
1224 	}
1225 	return true;
1226 }
1227 
1228 
1229 ScVbaRange*
1230 getRangeForName( const uno::Reference< uno::XComponentContext >& xContext, const rtl::OUString& sName, ScDocShell* pDocSh, table::CellRangeAddress& pAddr, formula::FormulaGrammar::AddressConvention eConv = formula::FormulaGrammar::CONV_XL_A1 ) throw ( uno::RuntimeException )
1231 {
1232 	ScRangeList aCellRanges;
1233 	ScRange refRange;
1234 	ScUnoConversion::FillScRange( refRange, pAddr );
1235 	if ( !getScRangeListForAddress ( sName, pDocSh, refRange, aCellRanges, eConv ) )
1236 		throw uno::RuntimeException();
1237 	// Single range
1238 	if ( aCellRanges.First() == aCellRanges.Last() )
1239 	{
1240 		uno::Reference< table::XCellRange > xRange( new ScCellRangeObj( pDocSh, *aCellRanges.First() ) );
1241 		uno::Reference< XHelperInterface > xFixThisParent = excel::getUnoSheetModuleObj( xRange );
1242 		return new ScVbaRange( xFixThisParent, xContext, xRange );
1243 	}
1244 	uno::Reference< sheet::XSheetCellRangeContainer > xRanges( new ScCellRangesObj( pDocSh, aCellRanges ) );
1245 
1246 	uno::Reference< XHelperInterface > xFixThisParent = excel::getUnoSheetModuleObj( xRanges );
1247 	return new ScVbaRange( xFixThisParent, xContext, xRanges );
1248 }
1249 
1250 // ----------------------------------------------------------------------------
1251 
1252 namespace {
1253 
1254 template< typename RangeType >
1255 inline table::CellRangeAddress lclGetRangeAddress( const uno::Reference< RangeType >& rxCellRange ) throw (uno::RuntimeException)
1256 {
1257     return uno::Reference< sheet::XCellRangeAddressable >( rxCellRange, uno::UNO_QUERY_THROW )->getRangeAddress();
1258 }
1259 
1260 void lclClearRange( const uno::Reference< table::XCellRange >& rxCellRange ) throw (uno::RuntimeException)
1261 {
1262     using namespace ::com::sun::star::sheet::CellFlags;
1263 	sal_Int32 nFlags = VALUE | DATETIME | STRING | ANNOTATION | FORMULA | HARDATTR | STYLES | EDITATTR | FORMATTED;
1264 	uno::Reference< sheet::XSheetOperation > xSheetOperation( rxCellRange, uno::UNO_QUERY_THROW );
1265 	xSheetOperation->clearContents( nFlags );
1266 }
1267 
1268 uno::Reference< sheet::XSheetCellRange > lclExpandToMerged( const uno::Reference< table::XCellRange >& rxCellRange, bool bRecursive ) throw (uno::RuntimeException)
1269 {
1270     uno::Reference< sheet::XSheetCellRange > xNewCellRange( rxCellRange, uno::UNO_QUERY_THROW );
1271     uno::Reference< sheet::XSpreadsheet > xSheet( xNewCellRange->getSpreadsheet(), uno::UNO_SET_THROW );
1272     table::CellRangeAddress aNewAddress = lclGetRangeAddress( xNewCellRange );
1273     table::CellRangeAddress aOldAddress;
1274     // expand as long as there are new merged ranges included
1275     do
1276     {
1277         aOldAddress = aNewAddress;
1278         uno::Reference< sheet::XSheetCellCursor > xCursor( xSheet->createCursorByRange( xNewCellRange ), uno::UNO_SET_THROW );
1279         xCursor->collapseToMergedArea();
1280         xNewCellRange.set( xCursor, uno::UNO_QUERY_THROW );
1281         aNewAddress = lclGetRangeAddress( xNewCellRange );
1282     }
1283     while( bRecursive && (aOldAddress != aNewAddress) );
1284     return xNewCellRange;
1285 }
1286 
1287 uno::Reference< sheet::XSheetCellRangeContainer > lclExpandToMerged( const uno::Reference< sheet::XSheetCellRangeContainer >& rxCellRanges, bool bRecursive ) throw (uno::RuntimeException)
1288 {
1289     if( !rxCellRanges.is() )
1290 		throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "Missing cell ranges object" ) ), uno::Reference< uno::XInterface >() );
1291     sal_Int32 nCount = rxCellRanges->getCount();
1292     if( nCount < 1 )
1293 		throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "Missing cell ranges object" ) ), uno::Reference< uno::XInterface >() );
1294 
1295     ScRangeList aScRanges;
1296     for( sal_Int32 nIndex = 0; nIndex < nCount; ++nIndex )
1297     {
1298         uno::Reference< table::XCellRange > xRange( rxCellRanges->getByIndex( nIndex ), uno::UNO_QUERY_THROW );
1299         table::CellRangeAddress aRangeAddr = lclGetRangeAddress( lclExpandToMerged( xRange, bRecursive ) );
1300     	ScRange aScRange;
1301     	ScUnoConversion::FillScRange( aScRange, aRangeAddr );
1302     	aScRanges.Append( aScRange );
1303     }
1304 	return new ScCellRangesObj( getDocShellFromRanges( rxCellRanges ), aScRanges );
1305 }
1306 
1307 void lclExpandAndMerge( const uno::Reference< table::XCellRange >& rxCellRange, bool bMerge ) throw (uno::RuntimeException)
1308 {
1309     uno::Reference< util::XMergeable > xMerge( lclExpandToMerged( rxCellRange, true ), uno::UNO_QUERY_THROW );
1310     // Calc cannot merge over merged ranges, always unmerge first
1311     xMerge->merge( sal_False );
1312     if( bMerge )
1313     {
1314         // clear all contents of the covered cells (not the top-left cell)
1315         table::CellRangeAddress aRangeAddr = lclGetRangeAddress( rxCellRange );
1316         sal_Int32 nLastColIdx = aRangeAddr.EndColumn - aRangeAddr.StartColumn;
1317         sal_Int32 nLastRowIdx = aRangeAddr.EndRow - aRangeAddr.StartRow;
1318         // clear cells of top row, right of top-left cell
1319         if( nLastColIdx > 0 )
1320             lclClearRange( rxCellRange->getCellRangeByPosition( 1, 0, nLastColIdx, 0 ) );
1321         // clear all rows below top row
1322         if( nLastRowIdx > 0 )
1323             lclClearRange( rxCellRange->getCellRangeByPosition( 0, 1, nLastColIdx, nLastRowIdx ) );
1324         // merge the range
1325         xMerge->merge( sal_True );
1326     }
1327 }
1328 
1329 util::TriState lclGetMergedState( const uno::Reference< table::XCellRange >& rxCellRange ) throw (uno::RuntimeException)
1330 {
1331     /*  1) Check if range is completely inside one single merged range. To do
1332         this, try to extend from top-left cell only (not from entire range).
1333         This will exclude cases where this range consists of several merged
1334         ranges (or parts of them). */
1335     table::CellRangeAddress aRangeAddr = lclGetRangeAddress( rxCellRange );
1336     uno::Reference< table::XCellRange > xTopLeft( rxCellRange->getCellRangeByPosition( 0, 0, 0, 0 ), uno::UNO_SET_THROW );
1337     uno::Reference< sheet::XSheetCellRange > xExpanded( lclExpandToMerged( xTopLeft, false ), uno::UNO_SET_THROW );
1338     table::CellRangeAddress aExpAddr = lclGetRangeAddress( xExpanded );
1339     // check that expanded range has more than one cell (really merged)
1340     if( ((aExpAddr.StartColumn < aExpAddr.EndColumn) || (aExpAddr.StartRow < aExpAddr.EndRow)) && ScUnoConversion::Contains( aExpAddr, aRangeAddr ) )
1341         return util::TriState_YES;
1342 
1343     /*  2) Check if this range contains any merged cells (completely or
1344         partly). This seems to be hardly possible via API, as
1345         XMergeable::getIsMerged() returns only true, if the top-left cell of a
1346         merged range is part of this range, so cases where just the lower part
1347         of a merged range is part of this range are not covered. */
1348 	ScRange aScRange;
1349 	ScUnoConversion::FillScRange( aScRange, aRangeAddr );
1350     bool bHasMerged = getDocumentFromRange( rxCellRange )->HasAttrib( aScRange, HASATTR_MERGED | HASATTR_OVERLAPPED );
1351 	return bHasMerged ? util::TriState_INDETERMINATE : util::TriState_NO;
1352 }
1353 
1354 } // namespace
1355 
1356 // ----------------------------------------------------------------------------
1357 
1358 css::uno::Reference< excel::XRange >
1359 ScVbaRange::getRangeObjectForName(
1360         const uno::Reference< uno::XComponentContext >& xContext, const rtl::OUString& sRangeName,
1361         ScDocShell* pDocSh, formula::FormulaGrammar::AddressConvention eConv ) throw ( uno::RuntimeException )
1362 {
1363 	table::CellRangeAddress refAddr;
1364 	return getRangeForName( xContext, sRangeName, pDocSh, refAddr, eConv );
1365 }
1366 
1367 
1368 table::CellRangeAddress getCellRangeAddressForVBARange( const uno::Any& aParam, ScDocShell* pDocSh,  formula::FormulaGrammar::AddressConvention aConv = formula::FormulaGrammar::CONV_XL_A1) throw ( uno::RuntimeException )
1369 {
1370 	uno::Reference< table::XCellRange > xRangeParam;
1371 	switch ( aParam.getValueTypeClass() )
1372 	{
1373 		case uno::TypeClass_STRING:
1374 		{
1375 			rtl::OUString rString;
1376 			aParam >>= rString;
1377 			ScRangeList aCellRanges;
1378 			ScRange refRange;
1379 			if ( getScRangeListForAddress ( rString, pDocSh, refRange, aCellRanges, aConv ) )
1380 			{
1381 				if ( aCellRanges.First() == aCellRanges.Last() )
1382 				{
1383 					table::CellRangeAddress aRangeAddress;
1384 					ScUnoConversion::FillApiRange( aRangeAddress, *aCellRanges.First() );
1385 					return aRangeAddress;
1386 				}
1387 			}
1388 		}
1389 		case uno::TypeClass_INTERFACE:
1390 		{
1391 			uno::Reference< excel::XRange > xRange;
1392 			aParam >>= xRange;
1393 			if ( xRange.is() )
1394 				xRange->getCellRange() >>= xRangeParam;
1395 			break;
1396 		}
1397 		default:
1398 			throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("Can't extact CellRangeAddress from type" ) ), uno::Reference< uno::XInterface >() );
1399 	}
1400     return lclGetRangeAddress( xRangeParam );
1401 }
1402 
1403 uno::Reference< XCollection >
1404 lcl_setupBorders( const uno::Reference< excel::XRange >& xParentRange, const uno::Reference<uno::XComponentContext>& xContext,  const uno::Reference< table::XCellRange >& xRange  ) throw( uno::RuntimeException )
1405 {
1406 	uno::Reference< XHelperInterface > xParent( xParentRange, uno::UNO_QUERY_THROW );
1407 	ScDocument* pDoc = getDocumentFromRange(xRange);
1408 	if ( !pDoc )
1409 		throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "Failed to access document from shell" ) ), uno::Reference< uno::XInterface >() );
1410 	ScVbaPalette aPalette( pDoc->GetDocumentShell() );
1411  	uno::Reference< XCollection > borders( new ScVbaBorders( xParent, xContext, xRange, aPalette ) );
1412 	return borders;
1413 }
1414 
1415 ScVbaRange::ScVbaRange( uno::Sequence< uno::Any> const & args,
1416     uno::Reference< uno::XComponentContext> const & xContext )  throw ( lang::IllegalArgumentException ) : ScVbaRange_BASE( getXSomethingFromArgs< XHelperInterface >( args, 0 ), xContext, getXSomethingFromArgs< beans::XPropertySet >( args, 1, false ), getModelFromXIf( getXSomethingFromArgs< uno::XInterface >( args, 1 ) ), true ), mbIsRows( sal_False ), mbIsColumns( sal_False )
1417 {
1418 	mxRange.set( mxPropertySet, uno::UNO_QUERY );
1419 	mxRanges.set( mxPropertySet, uno::UNO_QUERY );
1420 	uno::Reference< container::XIndexAccess >  xIndex;
1421 	if ( mxRange.is() )
1422 	{
1423         xIndex = new SingleRangeIndexAccess( mxParent, mxContext, mxRange );
1424 	}
1425 	else if ( mxRanges.is() )
1426 	{
1427 		xIndex.set( mxRanges, uno::UNO_QUERY_THROW );
1428 	}
1429     m_Areas = new ScVbaRangeAreas( mxParent, mxContext, xIndex, mbIsRows, mbIsColumns );
1430 }
1431 
1432 ScVbaRange::ScVbaRange( const uno::Reference< XHelperInterface >& xParent, const uno::Reference< uno::XComponentContext >& xContext, const uno::Reference< table::XCellRange >& xRange, sal_Bool bIsRows, sal_Bool bIsColumns ) throw( lang::IllegalArgumentException )
1433 : ScVbaRange_BASE( xParent, xContext, uno::Reference< beans::XPropertySet >( xRange, uno::UNO_QUERY_THROW ), getModelFromRange( xRange), true ), mxRange( xRange ),
1434                 mbIsRows( bIsRows ),
1435                 mbIsColumns( bIsColumns )
1436 {
1437 	if  ( !xContext.is() )
1438 		throw lang::IllegalArgumentException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "context is not set " ) ), uno::Reference< uno::XInterface >() , 1 );
1439 	if  ( !xRange.is() )
1440 		throw lang::IllegalArgumentException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "range is not set " ) ), uno::Reference< uno::XInterface >() , 1 );
1441 
1442     uno::Reference< container::XIndexAccess > xIndex( new SingleRangeIndexAccess( mxParent, mxContext, xRange ) );
1443     m_Areas = new ScVbaRangeAreas( mxParent, mxContext, xIndex, mbIsRows, mbIsColumns );
1444 
1445 }
1446 
1447 ScVbaRange::ScVbaRange( const uno::Reference< XHelperInterface >& xParent, const uno::Reference< uno::XComponentContext >& xContext, const uno::Reference< sheet::XSheetCellRangeContainer >& xRanges,  sal_Bool bIsRows, sal_Bool bIsColumns  ) throw ( lang::IllegalArgumentException )
1448 : ScVbaRange_BASE( xParent, xContext, uno::Reference< beans::XPropertySet >( xRanges, uno::UNO_QUERY_THROW ), getModelFromXIf( uno::Reference< uno::XInterface >( xRanges, uno::UNO_QUERY_THROW ) ), true ), mxRanges( xRanges ),mbIsRows( bIsRows ), mbIsColumns( bIsColumns )
1449 
1450 {
1451 	uno::Reference< container::XIndexAccess >  xIndex( mxRanges, uno::UNO_QUERY_THROW );
1452     m_Areas	 = new ScVbaRangeAreas( xParent, mxContext, xIndex, mbIsRows, mbIsColumns );
1453 
1454 }
1455 
1456 ScVbaRange::~ScVbaRange()
1457 {
1458 }
1459 
1460 uno::Reference< XCollection >& ScVbaRange::getBorders()
1461 {
1462 	if ( !m_Borders.is() )
1463 	{
1464 		uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny( sal_Int32(1) ), uno::Any() ), uno::UNO_QUERY_THROW );
1465 		m_Borders = lcl_setupBorders( this, mxContext, uno::Reference< table::XCellRange >( xRange->getCellRange(), uno::UNO_QUERY_THROW ) );
1466 	}
1467 	return m_Borders;
1468 }
1469 
1470 void
1471 ScVbaRange::visitArray( ArrayVisitor& visitor )
1472 {
1473     table::CellRangeAddress aRangeAddr = lclGetRangeAddress( mxRange );
1474     sal_Int32 nRowCount = aRangeAddr.EndRow - aRangeAddr.StartRow + 1;
1475     sal_Int32 nColCount = aRangeAddr.EndColumn - aRangeAddr.StartColumn + 1;
1476 	for ( sal_Int32 i=0; i<nRowCount; ++i )
1477 	{
1478 		for ( sal_Int32 j=0; j<nColCount; ++j )
1479 		{
1480 			uno::Reference< table::XCell > xCell( mxRange->getCellByPosition( j, i ), uno::UNO_QUERY_THROW );
1481 
1482 			visitor.visitNode( i, j, xCell );
1483 		}
1484 	}
1485 }
1486 
1487 
1488 
1489 uno::Any
1490 ScVbaRange::getValue( ValueGetter& valueGetter) throw (uno::RuntimeException)
1491 {
1492 	uno::Reference< table::XColumnRowRange > xColumnRowRange(mxRange, uno::UNO_QUERY_THROW );
1493 	// single cell range
1494 	if ( isSingleCellRange() )
1495 	{
1496 		visitArray( valueGetter );
1497 		return valueGetter.getValue();
1498 	}
1499 	sal_Int32 nRowCount = xColumnRowRange->getRows()->getCount();
1500 	sal_Int32 nColCount = xColumnRowRange->getColumns()->getCount();
1501 	// multi cell range ( return array )
1502 	Dim2ArrayValueGetter arrayGetter( nRowCount, nColCount, valueGetter );
1503 	visitArray( arrayGetter );
1504 	return uno::makeAny( script::ArrayWrapper( sal_False, arrayGetter.getValue() ) );
1505 }
1506 
1507 uno::Any SAL_CALL
1508 ScVbaRange::getValue() throw (uno::RuntimeException)
1509 {
1510 	// #TODO code within the test below "if ( m_Areas.... " can be removed
1511 	// Test is performed only because m_xRange is NOT set to be
1512 	// the first range in m_Areas ( to force failure while
1513 	// the implementations for each method are being updated )
1514 	if ( m_Areas->getCount() > 1 )
1515 	{
1516 		uno::Reference< excel::XRange > xRange( getArea( 0 ), uno::UNO_QUERY_THROW );
1517 		return xRange->getValue();
1518 	}
1519 
1520 	CellValueGetter valueGetter;
1521 	return getValue( valueGetter );
1522 
1523 }
1524 
1525 
1526 void
1527 ScVbaRange::setValue( const uno::Any& aValue, ValueSetter& valueSetter, bool bFireEvent ) throw (uno::RuntimeException)
1528 {
1529 	uno::TypeClass aClass = aValue.getValueTypeClass();
1530 	if ( aClass == uno::TypeClass_SEQUENCE )
1531 	{
1532 		uno::Reference< script::XTypeConverter > xConverter = getTypeConverter( mxContext );
1533 		uno::Any aConverted;
1534 		try
1535 		{
1536 			// test for single dimension, could do
1537 			// with a better test than this
1538 			if ( aValue.getValueTypeName().indexOf('[') ==  aValue.getValueTypeName().lastIndexOf('[') )
1539 			{
1540 				aConverted = xConverter->convertTo( aValue, getCppuType((uno::Sequence< uno::Any >*)0) );
1541 				Dim1ArrayValueSetter setter( aConverted, valueSetter );
1542 				visitArray( setter );
1543 			}
1544 			else
1545 			{
1546 				aConverted = xConverter->convertTo( aValue, getCppuType((uno::Sequence< uno::Sequence< uno::Any > >*)0) );
1547 				Dim2ArrayValueSetter setter( aConverted, valueSetter );
1548 				visitArray( setter );
1549 			}
1550 		}
1551 		catch ( uno::Exception& e )
1552 		{
1553 			OSL_TRACE("Bahhh, caught exception %s",
1554 				rtl::OUStringToOString( e.Message,
1555 					RTL_TEXTENCODING_UTF8 ).getStr() );
1556 		}
1557 	}
1558 	else
1559 	{
1560 		visitArray( valueSetter );
1561 	}
1562     if( bFireEvent ) fireChangeEvent();
1563 }
1564 
1565 void SAL_CALL
1566 ScVbaRange::setValue( const uno::Any  &aValue ) throw (uno::RuntimeException)
1567 {
1568 	// If this is a multiple selection apply setValue over all areas
1569 	if ( m_Areas->getCount() > 1 )
1570 	{
1571 		AreasVisitor aVisitor( m_Areas );
1572 		RangeValueProcessor valueProcessor( aValue );
1573 		aVisitor.visit( valueProcessor );
1574 		return;
1575 	}
1576 	CellValueSetter valueSetter( aValue );
1577 	setValue( aValue, valueSetter, true );
1578 }
1579 
1580 void SAL_CALL
1581 ScVbaRange::Clear() throw (uno::RuntimeException)
1582 {
1583     using namespace ::com::sun::star::sheet::CellFlags;
1584 	sal_Int32 nFlags = VALUE | DATETIME | STRING | FORMULA | HARDATTR | EDITATTR | FORMATTED;
1585 	ClearContents( nFlags, true );
1586 }
1587 
1588 //helper ClearContent
1589 void
1590 ScVbaRange::ClearContents( sal_Int32 nFlags, bool bFireEvent ) throw (uno::RuntimeException)
1591 {
1592 	// #TODO code within the test below "if ( m_Areas.... " can be removed
1593 	// Test is performed only because m_xRange is NOT set to be
1594 	// the first range in m_Areas ( to force failure while
1595 	// the implementations for each method are being updated )
1596 	if ( m_Areas->getCount() > 1 )
1597 	{
1598 		sal_Int32 nItems = m_Areas->getCount();
1599 		for ( sal_Int32 index=1; index <= nItems; ++index )
1600 		{
1601 			uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny(index), uno::Any() ), uno::UNO_QUERY_THROW );
1602 			ScVbaRange* pRange = getImplementation( xRange );
1603 			if ( pRange )
1604 				pRange->ClearContents( nFlags, false ); // do not fire for single ranges
1605 		}
1606         // fire change event for the entire range list
1607         if( bFireEvent ) fireChangeEvent();
1608 		return;
1609 	}
1610 
1611 
1612 	uno::Reference< sheet::XSheetOperation > xSheetOperation(mxRange, uno::UNO_QUERY_THROW);
1613 	xSheetOperation->clearContents( nFlags );
1614     if( bFireEvent ) fireChangeEvent();
1615 }
1616 
1617 void SAL_CALL
1618 ScVbaRange::ClearComments() throw (uno::RuntimeException)
1619 {
1620 	ClearContents( sheet::CellFlags::ANNOTATION, false );
1621 }
1622 
1623 void SAL_CALL
1624 ScVbaRange::ClearContents() throw (uno::RuntimeException)
1625 {
1626     using namespace ::com::sun::star::sheet::CellFlags;
1627 	sal_Int32 nFlags = VALUE | STRING |  DATETIME | FORMULA;
1628 	ClearContents( nFlags, true );
1629 }
1630 
1631 void SAL_CALL
1632 ScVbaRange::ClearFormats() throw (uno::RuntimeException)
1633 {
1634 	//FIXME: need to check if we need to combine FORMATTED
1635     using namespace ::com::sun::star::sheet::CellFlags;
1636 	sal_Int32 nFlags = HARDATTR | FORMATTED | EDITATTR;
1637 	ClearContents( nFlags, false );
1638 }
1639 
1640 void
1641 ScVbaRange::setFormulaValue( const uno::Any& rFormula, formula::FormulaGrammar::Grammar eGram, bool bFireEvent ) throw (uno::RuntimeException)
1642 {
1643 	// If this is a multiple selection apply setFormula over all areas
1644 	if ( m_Areas->getCount() > 1 )
1645 	{
1646 		AreasVisitor aVisitor( m_Areas );
1647 		RangeFormulaProcessor valueProcessor( rFormula );
1648 		aVisitor.visit( valueProcessor );
1649 		return;
1650 	}
1651 	CellFormulaValueSetter formulaValueSetter( rFormula, getScDocument(), eGram );
1652 	setValue( rFormula, formulaValueSetter, bFireEvent );
1653 }
1654 
1655 uno::Any
1656 ScVbaRange::getFormulaValue( formula::FormulaGrammar::Grammar eGram ) throw (uno::RuntimeException)
1657 {
1658 	// #TODO code within the test below "if ( m_Areas.... " can be removed
1659 	// Test is performed only because m_xRange is NOT set to be
1660 	// the first range in m_Areas ( to force failure while
1661 	// the implementations for each method are being updated )
1662 	if ( m_Areas->getCount() > 1 )
1663 	{
1664 		uno::Reference< excel::XRange > xRange( getArea( 0 ), uno::UNO_QUERY_THROW );
1665 		return xRange->getFormula();
1666 	}
1667 	CellFormulaValueGetter valueGetter( getScDocument(), eGram );
1668 	return getValue( valueGetter );
1669 
1670 }
1671 
1672 void
1673 ScVbaRange::setFormula(const uno::Any &rFormula ) throw (uno::RuntimeException)
1674 {
1675 	// #FIXME converting "=$a$1" e.g. CONV_XL_A1 -> CONV_OOO                        	// results in "=$a$1:a1", temporalily disable conversion
1676 	setFormulaValue( rFormula,formula::FormulaGrammar::GRAM_NATIVE_XL_A1, true );
1677 }
1678 
1679 uno::Any
1680 ScVbaRange::getFormulaR1C1() throw (::com::sun::star::uno::RuntimeException)
1681 {
1682 	return getFormulaValue( formula::FormulaGrammar::GRAM_NATIVE_XL_R1C1 );
1683 }
1684 
1685 void
1686 ScVbaRange::setFormulaR1C1(const uno::Any& rFormula ) throw (uno::RuntimeException)
1687 {
1688 	setFormulaValue( rFormula,formula::FormulaGrammar::GRAM_NATIVE_XL_R1C1, true );
1689 }
1690 
1691 uno::Any
1692 ScVbaRange::getFormula() throw (::com::sun::star::uno::RuntimeException)
1693 {
1694 	return getFormulaValue( formula::FormulaGrammar::GRAM_NATIVE_XL_A1 );
1695 }
1696 
1697 sal_Int32
1698 ScVbaRange::getCount() throw (uno::RuntimeException)
1699 {
1700 	// If this is a multiple selection apply setValue over all areas
1701 	if ( m_Areas->getCount() > 1 )
1702 	{
1703 		AreasVisitor aVisitor( m_Areas );
1704 		RangeCountProcessor valueProcessor;
1705 		aVisitor.visit( valueProcessor );
1706 		return valueProcessor.value();
1707 	}
1708 	sal_Int32 rowCount = 0;
1709 	sal_Int32 colCount = 0;
1710 	uno::Reference< table::XColumnRowRange > xColumnRowRange(mxRange, uno::UNO_QUERY_THROW );
1711 	rowCount = xColumnRowRange->getRows()->getCount();
1712 	colCount = xColumnRowRange->getColumns()->getCount();
1713 
1714 	if( IsRows() )
1715 		return rowCount;
1716 	if( IsColumns() )
1717 		return colCount;
1718 	return rowCount * colCount;
1719 }
1720 
1721 sal_Int32
1722 ScVbaRange::getRow() throw (uno::RuntimeException)
1723 {
1724 	// #TODO code within the test below "if ( m_Areas.... " can be removed
1725 	// Test is performed only because m_xRange is NOT set to be
1726 	// the first range in m_Areas ( to force failure while
1727 	// the implementations for each method are being updated )
1728 	if ( m_Areas->getCount() > 1 )
1729 	{
1730 		uno::Reference< excel::XRange > xRange( getArea( 0 ), uno::UNO_QUERY_THROW );
1731 		return xRange->getRow();
1732 	}
1733 	uno::Reference< sheet::XCellAddressable > xCellAddressable(mxRange->getCellByPosition(0, 0), uno::UNO_QUERY_THROW );
1734 	return xCellAddressable->getCellAddress().Row + 1; // Zero value indexing
1735 }
1736 
1737 sal_Int32
1738 ScVbaRange::getColumn() throw (uno::RuntimeException)
1739 {
1740 	// #TODO code within the test below "if ( m_Areas.... " can be removed
1741 	// Test is performed only because m_xRange is NOT set to be
1742 	// the first range in m_Areas ( to force failure while
1743 	// the implementations for each method are being updated )
1744 	if ( m_Areas->getCount() > 1 )
1745 	{
1746 		uno::Reference< excel::XRange > xRange( getArea( 0 ), uno::UNO_QUERY_THROW );
1747 		return xRange->getColumn();
1748 	}
1749 	uno::Reference< sheet::XCellAddressable > xCellAddressable(mxRange->getCellByPosition(0, 0), uno::UNO_QUERY_THROW );
1750 	return xCellAddressable->getCellAddress().Column + 1; // Zero value indexing
1751 }
1752 
1753 uno::Any
1754 ScVbaRange::HasFormula() throw (uno::RuntimeException)
1755 {
1756 	if ( m_Areas->getCount() > 1 )
1757 	{
1758 		sal_Int32 nItems = m_Areas->getCount();
1759 		uno::Any aResult = aNULL();
1760 		for ( sal_Int32 index=1; index <= nItems; ++index )
1761 		{
1762 			uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny(index), uno::Any() ), uno::UNO_QUERY_THROW );
1763 			// if the HasFormula for any area is different to another
1764 			// return null
1765 			if ( index > 1 )
1766 				if ( aResult != xRange->HasFormula() )
1767 					return aNULL();
1768 			aResult = xRange->HasFormula();
1769 			if ( aNULL() == aResult )
1770 				return aNULL();
1771 		}
1772 		return aResult;
1773 	}
1774 	uno::Reference< uno::XInterface > xIf( mxRange, uno::UNO_QUERY_THROW );
1775 	ScCellRangesBase* pThisRanges = dynamic_cast< ScCellRangesBase * > ( xIf.get() );
1776 	if ( pThisRanges )
1777 	{
1778 		uno::Reference<uno::XInterface>  xRanges( pThisRanges->queryFormulaCells( ( sheet::FormulaResult::ERROR | sheet::FormulaResult::VALUE |  sheet::FormulaResult::STRING ) ), uno::UNO_QUERY_THROW );
1779 		ScCellRangesBase* pFormulaRanges = dynamic_cast< ScCellRangesBase * > ( xRanges.get() );
1780 		// check if there are no formula cell, return false
1781 		if ( pFormulaRanges->GetRangeList().Count() == 0 )
1782 			return uno::makeAny(sal_False);
1783 
1784 		// chech if there are holes (where some cells are not formulas)
1785 		// or returned range is not equal to this range
1786 		if ( ( pFormulaRanges->GetRangeList().Count() > 1 )
1787 		|| ( pFormulaRanges->GetRangeList().GetObject(0)->aStart != pThisRanges->GetRangeList().GetObject(0)->aStart )
1788 		|| ( pFormulaRanges->GetRangeList().GetObject(0)->aEnd != pThisRanges->GetRangeList().GetObject(0)->aEnd ) )
1789 			return aNULL(); // should return aNULL;
1790 	}
1791 	return uno::makeAny( sal_True );
1792 }
1793 void
1794 ScVbaRange::fillSeries( sheet::FillDirection nFillDirection, sheet::FillMode nFillMode, sheet::FillDateMode nFillDateMode, double fStep, double fEndValue ) throw( uno::RuntimeException )
1795 {
1796 	if ( m_Areas->getCount() > 1 )
1797 	{
1798 		// Multi-Area Range
1799 		uno::Reference< XCollection > xCollection( m_Areas, uno::UNO_QUERY_THROW );
1800 		for ( sal_Int32 index = 1; index <= xCollection->getCount(); ++index )
1801 		{
1802 			uno::Reference< excel::XRange > xRange( xCollection->Item( uno::makeAny( index ), uno::Any() ), uno::UNO_QUERY_THROW );
1803 			ScVbaRange* pThisRange = getImplementation( xRange );
1804 			pThisRange->fillSeries( nFillDirection, nFillMode, nFillDateMode, fStep, fEndValue );
1805 
1806 		}
1807 		return;
1808 	}
1809 
1810 	uno::Reference< sheet::XCellSeries > xCellSeries(mxRange, uno::UNO_QUERY_THROW );
1811 	xCellSeries->fillSeries( nFillDirection, nFillMode, nFillDateMode, fStep, fEndValue );
1812 }
1813 
1814 void
1815 ScVbaRange::FillLeft() throw (uno::RuntimeException)
1816 {
1817 	fillSeries(sheet::FillDirection_TO_LEFT,
1818 		sheet::FillMode_SIMPLE, sheet::FillDateMode_FILL_DATE_DAY, 0, 0x7FFFFFFF);
1819 }
1820 
1821 void
1822 ScVbaRange::FillRight() throw (uno::RuntimeException)
1823 {
1824 	fillSeries(sheet::FillDirection_TO_RIGHT,
1825 		sheet::FillMode_SIMPLE, sheet::FillDateMode_FILL_DATE_DAY, 0, 0x7FFFFFFF);
1826 }
1827 
1828 void
1829 ScVbaRange::FillUp() throw (uno::RuntimeException)
1830 {
1831 	fillSeries(sheet::FillDirection_TO_TOP,
1832 		sheet::FillMode_SIMPLE, sheet::FillDateMode_FILL_DATE_DAY, 0, 0x7FFFFFFF);
1833 }
1834 
1835 void
1836 ScVbaRange::FillDown() throw (uno::RuntimeException)
1837 {
1838 	fillSeries(sheet::FillDirection_TO_BOTTOM,
1839 		sheet::FillMode_SIMPLE, sheet::FillDateMode_FILL_DATE_DAY, 0, 0x7FFFFFFF);
1840 }
1841 
1842 ::rtl::OUString
1843 ScVbaRange::getText() throw (uno::RuntimeException)
1844 {
1845 	// #TODO code within the test below "if ( m_Areas.... " can be removed
1846 	// Test is performed only because m_xRange is NOT set to be
1847 	// the first range in m_Areas ( to force failure while
1848 	// the implementations for each method are being updated )
1849 	if ( m_Areas->getCount() > 1 )
1850 	{
1851 		uno::Reference< excel::XRange > xRange( getArea( 0 ), uno::UNO_QUERY_THROW );
1852 		return xRange->getText();
1853 	}
1854 	uno::Reference< text::XTextRange > xTextRange(mxRange->getCellByPosition(0,0), uno::UNO_QUERY_THROW );
1855 	return xTextRange->getString();
1856 }
1857 
1858 uno::Reference< excel::XRange >
1859 ScVbaRange::Offset( const ::uno::Any &nRowOff, const uno::Any &nColOff ) throw (uno::RuntimeException)
1860 {
1861 	SCROW nRowOffset = 0;
1862 	SCCOL nColOffset = 0;
1863 	sal_Bool bIsRowOffset = ( nRowOff >>= nRowOffset );
1864 	sal_Bool bIsColumnOffset = ( nColOff >>= nColOffset );
1865 	ScCellRangesBase* pUnoRangesBase = getCellRangesBase();
1866 
1867 	ScRangeList aCellRanges = pUnoRangesBase->GetRangeList();
1868 
1869 
1870 	for ( ScRange* pRange = aCellRanges.First() ; pRange; pRange = aCellRanges.Next() )
1871 	{
1872 		if ( bIsColumnOffset )
1873 		{
1874 			pRange->aStart.SetCol( pRange->aStart.Col() + nColOffset );
1875 			pRange->aEnd.SetCol( pRange->aEnd.Col() + nColOffset );
1876 		}
1877 		if ( bIsRowOffset )
1878 		{
1879 			pRange->aStart.SetRow( pRange->aStart.Row() + nRowOffset );
1880 			pRange->aEnd.SetRow( pRange->aEnd.Row() + nRowOffset );
1881 		}
1882 	}
1883 
1884 	if ( aCellRanges.Count() > 1 ) // Multi-Area
1885 	{
1886 		uno::Reference< sheet::XSheetCellRangeContainer > xRanges( new ScCellRangesObj( pUnoRangesBase->GetDocShell(), aCellRanges ) );
1887 		return new ScVbaRange( mxParent, mxContext, xRanges );
1888 	}
1889 	// normal range
1890 	uno::Reference< table::XCellRange > xRange( new ScCellRangeObj( pUnoRangesBase->GetDocShell(), *aCellRanges.First() ) );
1891 	return new ScVbaRange( mxParent, mxContext, xRange  );
1892 }
1893 
1894 uno::Reference< excel::XRange >
1895 ScVbaRange::CurrentRegion() throw (uno::RuntimeException)
1896 {
1897 	// #TODO code within the test below "if ( m_Areas.... " can be removed
1898 	// Test is performed only because m_xRange is NOT set to be
1899 	// the first range in m_Areas ( to force failure while
1900 	// the implementations for each method are being updated )
1901 	if ( m_Areas->getCount() > 1 )
1902 	{
1903 		uno::Reference< excel::XRange > xRange( getArea( 0 ), uno::UNO_QUERY_THROW );
1904 		return xRange->CurrentRegion();
1905 	}
1906 
1907 	RangeHelper helper( mxRange );
1908 	uno::Reference< sheet::XSheetCellCursor > xSheetCellCursor =
1909 		helper.getSheetCellCursor();
1910 	xSheetCellCursor->collapseToCurrentRegion();
1911 	uno::Reference< sheet::XCellRangeAddressable > xCellRangeAddressable(xSheetCellCursor, uno::UNO_QUERY_THROW);
1912     return RangeHelper::createRangeFromRange( mxParent, mxContext, helper.getCellRangeFromSheet(), xCellRangeAddressable );
1913 }
1914 
1915 uno::Reference< excel::XRange >
1916 ScVbaRange::CurrentArray() throw (uno::RuntimeException)
1917 {
1918 	// #TODO code within the test below "if ( m_Areas.... " can be removed
1919 	// Test is performed only because m_xRange is NOT set to be
1920 	// the first range in m_Areas ( to force failure while
1921 	// the implementations for each method are being updated )
1922 	if ( m_Areas->getCount() > 1 )
1923 	{
1924 		uno::Reference< excel::XRange > xRange( getArea( 0 ), uno::UNO_QUERY_THROW );
1925 		return xRange->CurrentArray();
1926 	}
1927 	RangeHelper helper( mxRange );
1928 	uno::Reference< sheet::XSheetCellCursor > xSheetCellCursor =
1929 		helper.getSheetCellCursor();
1930 	xSheetCellCursor->collapseToCurrentArray();
1931 	uno::Reference< sheet::XCellRangeAddressable > xCellRangeAddressable(xSheetCellCursor, uno::UNO_QUERY_THROW);
1932     return RangeHelper::createRangeFromRange( mxParent, mxContext, helper.getCellRangeFromSheet(), xCellRangeAddressable );
1933 }
1934 
1935 uno::Any
1936 ScVbaRange::getFormulaArray() throw (uno::RuntimeException)
1937 {
1938 	// #TODO code within the test below "if ( m_Areas.... " can be removed
1939 	// Test is performed only because m_xRange is NOT set to be
1940 	// the first range in m_Areas ( to force failure while
1941 	// the implementations for each method are being updated )
1942 	if ( m_Areas->getCount() > 1 )
1943 	{
1944 		uno::Reference< excel::XRange > xRange( getArea( 0 ), uno::UNO_QUERY_THROW );
1945 		return xRange->getFormulaArray();
1946 	}
1947 
1948 	uno::Reference< sheet::XCellRangeFormula> xCellRangeFormula( mxRange, uno::UNO_QUERY_THROW );
1949 	uno::Reference< script::XTypeConverter > xConverter = getTypeConverter( mxContext );
1950 	uno::Any aMatrix;
1951 	aMatrix = xConverter->convertTo( uno::makeAny( xCellRangeFormula->getFormulaArray() ) , getCppuType((uno::Sequence< uno::Sequence< uno::Any > >*)0)  ) ;
1952 	return aMatrix;
1953 }
1954 
1955 void
1956 ScVbaRange::setFormulaArray(const uno::Any& rFormula) throw (uno::RuntimeException)
1957 {
1958 	// #TODO code within the test below "if ( m_Areas.... " can be removed
1959 	// Test is performed only because m_xRange is NOT set to be
1960 	// the first range in m_Areas ( to force failure while
1961 	// the implementations for each method are being updated )
1962 	if ( m_Areas->getCount() > 1 )
1963 	{
1964 		uno::Reference< excel::XRange > xRange( getArea( 0 ), uno::UNO_QUERY_THROW );
1965 		return xRange->setFormulaArray( rFormula );
1966 	}
1967 	// #TODO need to distinguish between getFormula and getFormulaArray e.g. (R1C1)
1968 	// but for the moment its just easier to treat them the same for setting
1969 
1970 	setFormula( rFormula );
1971 }
1972 
1973 ::rtl::OUString
1974 ScVbaRange::Characters(const uno::Any& Start, const uno::Any& Length) throw (uno::RuntimeException)
1975 {
1976 	// #TODO code within the test below "if ( m_Areas.... " can be removed
1977 	// Test is performed only because m_xRange is NOT set to be
1978 	// the first range in m_Areas ( to force failure while
1979 	// the implementations for each method are being updated )
1980 	if ( m_Areas->getCount() > 1 )
1981 	{
1982 		uno::Reference< excel::XRange > xRange( getArea( 0 ), uno::UNO_QUERY_THROW );
1983 		return xRange->Characters( Start, Length );
1984 	}
1985 
1986 	long nIndex = 0, nCount = 0;
1987 	::rtl::OUString rString;
1988 	uno::Reference< text::XTextRange > xTextRange(mxRange, ::uno::UNO_QUERY_THROW );
1989 	rString = xTextRange->getString();
1990 	if( !( Start >>= nIndex ) && !( Length >>= nCount ) )
1991 		return rString;
1992 	if(!( Start >>= nIndex ) )
1993 		nIndex = 1;
1994 	if(!( Length >>= nCount ) )
1995 		nIndex = rString.getLength();
1996 	return rString.copy( --nIndex, nCount ); // Zero value indexing
1997 }
1998 
1999 ::rtl::OUString
2000 ScVbaRange::Address(  const uno::Any& RowAbsolute, const uno::Any& ColumnAbsolute, const uno::Any& ReferenceStyle, const uno::Any& External, const uno::Any& RelativeTo ) throw (uno::RuntimeException)
2001 {
2002 	if ( m_Areas->getCount() > 1 )
2003 	{
2004 		// Multi-Area Range
2005 		rtl::OUString sAddress;
2006 		uno::Reference< XCollection > xCollection( m_Areas, uno::UNO_QUERY_THROW );
2007                 uno::Any aExternalCopy = External;
2008 		for ( sal_Int32 index = 1; index <= xCollection->getCount(); ++index )
2009 		{
2010 			uno::Reference< excel::XRange > xRange( xCollection->Item( uno::makeAny( index ), uno::Any() ), uno::UNO_QUERY_THROW );
2011 			if ( index > 1 )
2012 			{
2013 				sAddress += rtl::OUString( ',' );
2014                                 // force external to be false
2015                                 // only first address should have the
2016                                 // document and sheet specifications
2017                                 aExternalCopy = uno::makeAny(sal_False);
2018 			}
2019 			sAddress += xRange->Address( RowAbsolute, ColumnAbsolute, ReferenceStyle, aExternalCopy, RelativeTo );
2020 		}
2021 		return sAddress;
2022 
2023 	}
2024 	ScAddress::Details dDetails( formula::FormulaGrammar::CONV_XL_A1, 0, 0 );
2025 	if ( ReferenceStyle.hasValue() )
2026 	{
2027 		sal_Int32 refStyle = excel::XlReferenceStyle::xlA1;
2028 		ReferenceStyle >>= refStyle;
2029 		if ( refStyle == excel::XlReferenceStyle::xlR1C1 )
2030 			dDetails = ScAddress::Details( formula::FormulaGrammar::CONV_XL_R1C1, 0, 0 );
2031 	}
2032 	sal_uInt16 nFlags = SCA_VALID;
2033 	ScDocShell* pDocShell =  getScDocShell();
2034 	ScDocument* pDoc =  pDocShell->GetDocument();
2035 
2036 	RangeHelper thisRange( mxRange );
2037 	table::CellRangeAddress thisAddress = thisRange.getCellRangeAddressable()->getRangeAddress();
2038 	ScRange aRange( static_cast< SCCOL >( thisAddress.StartColumn ), static_cast< SCROW >( thisAddress.StartRow ), static_cast< SCTAB >( thisAddress.Sheet ), static_cast< SCCOL >( thisAddress.EndColumn ), static_cast< SCROW >( thisAddress.EndRow ), static_cast< SCTAB >( thisAddress.Sheet ) );
2039 	String sRange;
2040 	sal_uInt16 ROW_ABSOLUTE = ( SCA_ROW_ABSOLUTE | SCA_ROW2_ABSOLUTE );
2041 	sal_uInt16 COL_ABSOLUTE = ( SCA_COL_ABSOLUTE | SCA_COL2_ABSOLUTE );
2042 	// default
2043 	nFlags |= ( SCA_TAB_ABSOLUTE | SCA_COL_ABSOLUTE | SCA_ROW_ABSOLUTE | SCA_TAB2_ABSOLUTE | SCA_COL2_ABSOLUTE | SCA_ROW2_ABSOLUTE );
2044 	if ( RowAbsolute.hasValue() )
2045 	{
2046 		sal_Bool bVal = sal_True;
2047 		RowAbsolute >>= bVal;
2048 		if ( !bVal )
2049 			nFlags &= ~ROW_ABSOLUTE;
2050 	}
2051 	if ( ColumnAbsolute.hasValue() )
2052 	{
2053 		sal_Bool bVal = sal_True;
2054 		ColumnAbsolute >>= bVal;
2055 		if ( !bVal )
2056 			nFlags &= ~COL_ABSOLUTE;
2057 	}
2058 	sal_Bool bLocal = sal_False;
2059 	if ( External.hasValue() )
2060 	{
2061 		External >>= bLocal;
2062 		if (  bLocal )
2063 			nFlags |= SCA_TAB_3D | SCA_FORCE_DOC;
2064 	}
2065 	if ( RelativeTo.hasValue() )
2066 	{
2067 		// #TODO should I throw an error if R1C1 is not set?
2068 
2069 		table::CellRangeAddress refAddress = getCellRangeAddressForVBARange( RelativeTo, pDocShell );
2070 		dDetails = ScAddress::Details( formula::FormulaGrammar::CONV_XL_R1C1, static_cast< SCROW >( refAddress.StartRow ), static_cast< SCCOL >( refAddress.StartColumn ) );
2071 	}
2072 	aRange.Format( sRange,  nFlags, pDoc, dDetails );
2073 	return sRange;
2074 }
2075 
2076 uno::Reference < excel::XFont >
2077 ScVbaRange::Font() throw ( script::BasicErrorException, uno::RuntimeException)
2078 {
2079 	uno::Reference< beans::XPropertySet > xProps(mxRange, ::uno::UNO_QUERY );
2080 	ScDocument* pDoc = getScDocument();
2081 	if ( mxRange.is() )
2082 		xProps.set(mxRange, ::uno::UNO_QUERY );
2083 	else if ( mxRanges.is() )
2084 		xProps.set(mxRanges, ::uno::UNO_QUERY );
2085 	if ( !pDoc )
2086 		throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "Failed to access document from shell" ) ), uno::Reference< uno::XInterface >() );
2087 
2088 	ScVbaPalette aPalette( pDoc->GetDocumentShell() );
2089 	ScCellRangeObj* pRangeObj = NULL;
2090 	try
2091 	{
2092 		pRangeObj = getCellRangeObj();
2093 	}
2094 	catch( uno::Exception& )
2095 	{
2096 	}
2097 	return  new ScVbaFont( this, mxContext, aPalette, xProps, pRangeObj );
2098 }
2099 
2100 uno::Reference< excel::XRange >
2101 ScVbaRange::Cells( const uno::Any &nRowIndex, const uno::Any &nColumnIndex ) throw(uno::RuntimeException)
2102 {
2103 	// #TODO code within the test below "if ( m_Areas.... " can be removed
2104 	// Test is performed only because m_xRange is NOT set to be
2105 	// the first range in m_Areas ( to force failure while
2106 	// the implementations for each method are being updated )
2107 	if ( m_Areas->getCount() > 1 )
2108 	{
2109 		uno::Reference< excel::XRange > xRange( getArea( 0 ), uno::UNO_QUERY_THROW );
2110 		return xRange->Cells( nRowIndex, nColumnIndex );
2111 	}
2112 
2113     // Performance: Use a common helper method for ScVbaRange::Cells and ScVbaWorksheet::Cells,
2114     // instead of creating a new ScVbaRange object in often-called ScVbaWorksheet::Cells
2115     return CellsHelper( mxParent, mxContext, mxRange, nRowIndex, nColumnIndex );
2116 }
2117 
2118 // static
2119 uno::Reference< excel::XRange >
2120 ScVbaRange::CellsHelper( const uno::Reference< ov::XHelperInterface >& xParent,
2121                          const uno::Reference< uno::XComponentContext >& xContext,
2122                          const uno::Reference< css::table::XCellRange >& xRange,
2123                          const uno::Any &nRowIndex, const uno::Any &nColumnIndex ) throw(uno::RuntimeException)
2124 {
2125 	sal_Int32 nRow = 0, nColumn = 0;
2126 
2127 	sal_Bool bIsIndex = nRowIndex.hasValue();
2128 	sal_Bool bIsColumnIndex = nColumnIndex.hasValue();
2129 
2130 	// Sometimes we might get a float or a double or whatever
2131 	// set in the Any, we should convert as appropriate
2132 	// #FIXME - perhaps worth turning this into some sort of
2133 	// convertion routine e.g. bSuccess = getValueFromAny( nRow, nRowIndex, getCppuType((sal_Int32*)0) )
2134 	if ( nRowIndex.hasValue() && !( nRowIndex >>= nRow ) )
2135 	{
2136 		uno::Reference< script::XTypeConverter > xConverter = getTypeConverter( xContext );
2137 		uno::Any aConverted;
2138 		try
2139 		{
2140 			aConverted = xConverter->convertTo( nRowIndex, getCppuType((sal_Int32*)0) );
2141 			bIsIndex = ( aConverted >>= nRow );
2142 		}
2143 		catch( uno::Exception& ) {} // silence any errors
2144 	}
2145 	if ( bIsColumnIndex && !( nColumnIndex >>= nColumn ) )
2146 	{
2147 		uno::Reference< script::XTypeConverter > xConverter = getTypeConverter( xContext );
2148 		uno::Any aConverted;
2149 		try
2150 		{
2151 			aConverted = xConverter->convertTo( nColumnIndex, getCppuType((sal_Int32*)0) );
2152 			bIsColumnIndex = ( aConverted >>= nColumn );
2153 		}
2154 		catch( uno::Exception& ) {} // silence any errors
2155 	}
2156 
2157 	RangeHelper thisRange( xRange );
2158 	table::CellRangeAddress thisRangeAddress =  thisRange.getCellRangeAddressable()->getRangeAddress();
2159 	uno::Reference< table::XCellRange > xSheetRange = thisRange.getCellRangeFromSheet();
2160 	if( !bIsIndex && !bIsColumnIndex ) // .Cells
2161 		// #FIXE needs proper parent ( Worksheet )
2162 		return uno::Reference< excel::XRange >( new ScVbaRange( xParent, xContext, xRange ) );
2163 
2164 	sal_Int32 nIndex = --nRow;
2165 	if( bIsIndex && !bIsColumnIndex ) // .Cells(n)
2166 	{
2167 		uno::Reference< table::XColumnRowRange > xColumnRowRange(xRange, ::uno::UNO_QUERY_THROW);
2168 		sal_Int32 nColCount = xColumnRowRange->getColumns()->getCount();
2169 
2170 		if ( !nIndex || nIndex < 0 )
2171 			nRow = 0;
2172 		else
2173 			nRow = nIndex / nColCount;
2174 		nColumn = nIndex % nColCount;
2175 	}
2176 	else
2177 		--nColumn;
2178 	nRow = nRow + thisRangeAddress.StartRow;
2179 	nColumn =  nColumn + thisRangeAddress.StartColumn;
2180 	return new ScVbaRange( xParent, xContext, xSheetRange->getCellRangeByPosition( nColumn, nRow,                                        nColumn, nRow ) );
2181 }
2182 
2183 void
2184 ScVbaRange::Select() throw (uno::RuntimeException)
2185 {
2186 	ScCellRangesBase* pUnoRangesBase = getCellRangesBase();
2187 	if ( !pUnoRangesBase )
2188 		throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "Failed to access underlying uno range object" ) ), uno::Reference< uno::XInterface >()  );
2189 	ScDocShell* pShell = pUnoRangesBase->GetDocShell();
2190 	if ( pShell )
2191 	{
2192 		uno::Reference< frame::XModel > xModel( pShell->GetModel(), uno::UNO_QUERY_THROW );
2193 		uno::Reference< view::XSelectionSupplier > xSelection( xModel->getCurrentController(), uno::UNO_QUERY_THROW );
2194 		if ( mxRanges.is() )
2195 			xSelection->select( uno::Any( lclExpandToMerged( mxRanges, true ) ) );
2196 		else
2197 			xSelection->select( uno::Any( lclExpandToMerged( mxRange, true ) ) );
2198 		// set focus on document e.g.
2199 		// ThisComponent.CurrentController.Frame.getContainerWindow.SetFocus
2200 		try
2201 		{
2202 			uno::Reference< frame::XController > xController( xModel->getCurrentController(), uno::UNO_QUERY_THROW );
2203 			uno::Reference< frame::XFrame > xFrame( xController->getFrame(), uno::UNO_QUERY_THROW );
2204 			uno::Reference< awt::XWindow > xWin( xFrame->getContainerWindow(), uno::UNO_QUERY_THROW );
2205 			xWin->setFocus();
2206 		}
2207 		catch( uno::Exception& )
2208 		{
2209 		}
2210 	}
2211 }
2212 
2213 bool cellInRange( const table::CellRangeAddress& rAddr, const sal_Int32& nCol, const sal_Int32& nRow )
2214 {
2215 	if ( nCol >= rAddr.StartColumn && nCol <= rAddr.EndColumn &&
2216 		nRow >= rAddr.StartRow && nRow <= rAddr.EndRow )
2217 		return true;
2218 	return false;
2219 }
2220 
2221 void setCursor(  const SCCOL& nCol, const SCROW& nRow, const uno::Reference< frame::XModel >& xModel,  bool bInSel = true )
2222 {
2223 	ScTabViewShell* pShell = excel::getBestViewShell( xModel );
2224 	if ( pShell )
2225 	{
2226 		if ( bInSel )
2227 			pShell->SetCursor( nCol, nRow );
2228 		else
2229 			pShell->MoveCursorAbs( nCol, nRow, SC_FOLLOW_NONE, sal_False, sal_False, sal_True, sal_False );
2230 	}
2231 }
2232 
2233 void
2234 ScVbaRange::Activate() throw (uno::RuntimeException)
2235 {
2236 	// get first cell of current range
2237 	uno::Reference< table::XCellRange > xCellRange;
2238 	if ( mxRanges.is() )
2239 	{
2240 		uno::Reference< container::XIndexAccess > xIndex( mxRanges, uno::UNO_QUERY_THROW  );
2241 		xCellRange.set( xIndex->getByIndex( 0 ), uno::UNO_QUERY_THROW );
2242 	}
2243 	else
2244 		xCellRange.set( mxRange, uno::UNO_QUERY_THROW );
2245 
2246 	RangeHelper thisRange( xCellRange );
2247 	uno::Reference< sheet::XCellRangeAddressable > xThisRangeAddress = thisRange.getCellRangeAddressable();
2248 	table::CellRangeAddress thisRangeAddress = xThisRangeAddress->getRangeAddress();
2249         uno::Reference< frame::XModel > xModel;
2250         ScDocShell* pShell = getScDocShell();
2251 
2252         if ( pShell )
2253             xModel = pShell->GetModel();
2254 
2255         if ( !xModel.is() )
2256             throw uno::RuntimeException();
2257 
2258 	// get current selection
2259 	uno::Reference< sheet::XCellRangeAddressable > xRange( xModel->getCurrentSelection(), ::uno::UNO_QUERY);
2260 
2261 	uno::Reference< sheet::XSheetCellRanges > xRanges( xModel->getCurrentSelection(), ::uno::UNO_QUERY);
2262 
2263 	if ( xRanges.is() )
2264 	{
2265 		uno::Sequence< table::CellRangeAddress > nAddrs = xRanges->getRangeAddresses();
2266 		for ( sal_Int32 index = 0; index < nAddrs.getLength(); ++index )
2267 		{
2268 			if ( cellInRange( nAddrs[index], thisRangeAddress.StartColumn, thisRangeAddress.StartRow ) )
2269 			{
2270 				setCursor( static_cast< SCCOL >( thisRangeAddress.StartColumn ), static_cast< SCROW >( thisRangeAddress.StartRow ), xModel );
2271 				return;
2272 			}
2273 
2274 		}
2275 	}
2276 
2277 	if ( xRange.is() && cellInRange( xRange->getRangeAddress(), thisRangeAddress.StartColumn, thisRangeAddress.StartRow ) )
2278 		setCursor( static_cast< SCCOL >( thisRangeAddress.StartColumn ), static_cast< SCROW >( thisRangeAddress.StartRow ), xModel );
2279 	else
2280 	{
2281 		// if this range is multi cell select the range other
2282 		// wise just position the cell at this single range position
2283 		if ( isSingleCellRange() )
2284 			// This top-leftmost cell of this Range is not in the current
2285 			// selection so just select this range
2286 			setCursor( static_cast< SCCOL >( thisRangeAddress.StartColumn ), static_cast< SCROW >( thisRangeAddress.StartRow ), xModel, false  );
2287 		else
2288 			Select();
2289 	}
2290 
2291 }
2292 
2293 uno::Reference< excel::XRange >
2294 ScVbaRange::Rows(const uno::Any& aIndex ) throw (uno::RuntimeException)
2295 {
2296 	SCROW nStartRow = 0;
2297 	SCROW nEndRow = 0;
2298 
2299 	sal_Int32 nValue = 0;
2300 	rtl::OUString sAddress;
2301 
2302 	if ( aIndex.hasValue() )
2303 	{
2304 		ScCellRangesBase* pUnoRangesBase = getCellRangesBase();
2305 		ScRangeList aCellRanges = pUnoRangesBase->GetRangeList();
2306 
2307 		ScRange aRange = *aCellRanges.First();
2308 		if( aIndex >>= nValue )
2309 		{
2310 			aRange.aStart.SetRow( aRange.aStart.Row() + --nValue );
2311 			aRange.aEnd.SetRow( aRange.aStart.Row() );
2312 		}
2313 
2314 		else if ( aIndex >>= sAddress )
2315 		{
2316 			ScAddress::Details dDetails( formula::FormulaGrammar::CONV_XL_A1, 0, 0 );
2317 			ScRange tmpRange;
2318 			tmpRange.ParseRows( sAddress, getDocumentFromRange( mxRange ), dDetails );
2319 			nStartRow = tmpRange.aStart.Row();
2320 			nEndRow = tmpRange.aEnd.Row();
2321 
2322 			aRange.aStart.SetRow( aRange.aStart.Row() + nStartRow );
2323 			aRange.aEnd.SetRow( aRange.aStart.Row() + ( nEndRow  - nStartRow ));
2324 		}
2325 		else
2326 			throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("Illegal param" ) ), uno::Reference< uno::XInterface >() );
2327 
2328 		if ( aRange.aStart.Row() < 0 || aRange.aEnd.Row() < 0 )
2329 			throw uno::RuntimeException( rtl::OUString::createFromAscii("Internal failure, illegal param"), uno::Reference< uno::XInterface >() );
2330 		// return a normal range ( even for multi-selection
2331 		uno::Reference< table::XCellRange > xRange( new ScCellRangeObj( pUnoRangesBase->GetDocShell(), aRange ) );
2332 		return new ScVbaRange( mxParent, mxContext, xRange, true  );
2333 	}
2334 	// Rows() - no params
2335 	if ( m_Areas->getCount() > 1 )
2336 		return new ScVbaRange(  mxParent, mxContext, mxRanges, true );
2337 	return new ScVbaRange(  mxParent, mxContext, mxRange, true );
2338 }
2339 
2340 uno::Reference< excel::XRange >
2341 ScVbaRange::Columns(const uno::Any& aIndex ) throw (uno::RuntimeException)
2342 {
2343 	SCCOL nStartCol = 0;
2344 	SCCOL nEndCol = 0;
2345 
2346 	sal_Int32 nValue = 0;
2347 	rtl::OUString sAddress;
2348 
2349 	ScCellRangesBase* pUnoRangesBase = getCellRangesBase();
2350 	ScRangeList aCellRanges = pUnoRangesBase->GetRangeList();
2351 
2352 	ScRange aRange = *aCellRanges.First();
2353 	if ( aIndex.hasValue() )
2354 	{
2355 		if ( aIndex >>= nValue )
2356 		{
2357 			aRange.aStart.SetCol( aRange.aStart.Col() + static_cast< SCCOL > ( --nValue ) );
2358 			aRange.aEnd.SetCol( aRange.aStart.Col() );
2359 		}
2360 
2361 		else if ( aIndex >>= sAddress )
2362 		{
2363 			ScAddress::Details dDetails( formula::FormulaGrammar::CONV_XL_A1, 0, 0 );
2364 			ScRange tmpRange;
2365 			tmpRange.ParseCols( sAddress, getDocumentFromRange( mxRange ), dDetails );
2366 			nStartCol = tmpRange.aStart.Col();
2367 			nEndCol = tmpRange.aEnd.Col();
2368 
2369 			aRange.aStart.SetCol( aRange.aStart.Col() + nStartCol );
2370 			aRange.aEnd.SetCol( aRange.aStart.Col() + ( nEndCol  - nStartCol ));
2371 		}
2372 		else
2373 			throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("Illegal param" ) ), uno::Reference< uno::XInterface >() );
2374 
2375 		if ( aRange.aStart.Col() < 0 || aRange.aEnd.Col() < 0 )
2376 			throw uno::RuntimeException( rtl::OUString::createFromAscii("Internal failure, illegal param"), uno::Reference< uno::XInterface >() );
2377 	}
2378 	// Columns() - no params
2379 	uno::Reference< table::XCellRange > xRange( new ScCellRangeObj( pUnoRangesBase->GetDocShell(), aRange ) );
2380 	return new ScVbaRange( mxParent, mxContext, xRange, false, true  );
2381 }
2382 
2383 void
2384 ScVbaRange::setMergeCells( const uno::Any& aIsMerged ) throw (script::BasicErrorException, uno::RuntimeException)
2385 {
2386     bool bMerge = extractBoolFromAny( aIsMerged );
2387 
2388     if( mxRanges.is() )
2389     {
2390         sal_Int32 nCount = mxRanges->getCount();
2391 
2392         // VBA does nothing (no error) if the own ranges overlap somehow
2393         ::std::vector< table::CellRangeAddress > aList;
2394         for( sal_Int32 nIndex = 0; nIndex < nCount; ++nIndex )
2395         {
2396             uno::Reference< sheet::XCellRangeAddressable > xRangeAddr( mxRanges->getByIndex( nIndex ), uno::UNO_QUERY_THROW );
2397             table::CellRangeAddress aAddress = xRangeAddr->getRangeAddress();
2398             for( ::std::vector< table::CellRangeAddress >::const_iterator aIt = aList.begin(), aEnd = aList.end(); aIt != aEnd; ++aIt )
2399                 if( ScUnoConversion::Intersects( *aIt, aAddress ) )
2400                     return;
2401             aList.push_back( aAddress );
2402         }
2403 
2404         // (un)merge every range after it has been extended to intersecting merged ranges from sheet
2405         for( sal_Int32 nIndex = 0; nIndex < nCount; ++nIndex )
2406         {
2407             uno::Reference< table::XCellRange > xRange( mxRanges->getByIndex( nIndex ), uno::UNO_QUERY_THROW );
2408             lclExpandAndMerge( xRange, bMerge );
2409         }
2410         return;
2411     }
2412 
2413     // otherwise, merge single range
2414     lclExpandAndMerge( mxRange, bMerge );
2415 }
2416 
2417 uno::Any
2418 ScVbaRange::getMergeCells() throw (script::BasicErrorException, uno::RuntimeException)
2419 {
2420     if( mxRanges.is() )
2421     {
2422         sal_Int32 nCount = mxRanges->getCount();
2423         for( sal_Int32 nIndex = 0; nIndex < nCount; ++nIndex )
2424         {
2425             uno::Reference< table::XCellRange > xRange( mxRanges->getByIndex( nIndex ), uno::UNO_QUERY_THROW );
2426             util::TriState eMerged = lclGetMergedState( xRange );
2427             /*  Excel always returns NULL, if one range of the range list is
2428                 partly or completely merged. Even if all ranges are completely
2429                 merged, the return value is still NULL. */
2430             if( eMerged != util::TriState_NO )
2431                 return aNULL();
2432         }
2433         // no range is merged anyhow, return false
2434         return uno::Any( false );
2435     }
2436 
2437     // otherwise, check single range
2438     switch( lclGetMergedState( mxRange ) )
2439     {
2440         case util::TriState_YES:    return uno::Any( true );
2441         case util::TriState_NO:     return uno::Any( false );
2442         default:                    return aNULL();
2443     }
2444 }
2445 
2446 void
2447 ScVbaRange::Copy(const ::uno::Any& Destination) throw (uno::RuntimeException)
2448 {
2449 	if ( m_Areas->getCount() > 1 )
2450 		throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("That command cannot be used on multiple selections" ) ), uno::Reference< uno::XInterface >() );
2451 	if ( Destination.hasValue() )
2452 	{
2453 		uno::Reference< excel::XRange > xRange( Destination, uno::UNO_QUERY_THROW );
2454 		uno::Any aRange = xRange->getCellRange();
2455 		uno::Reference< table::XCellRange > xCellRange;
2456 		aRange >>= xCellRange;
2457 		uno::Reference< sheet::XSheetCellRange > xSheetCellRange(xCellRange, ::uno::UNO_QUERY_THROW);
2458 		uno::Reference< sheet::XSpreadsheet > xSheet = xSheetCellRange->getSpreadsheet();
2459 		uno::Reference< table::XCellRange > xDest( xSheet, uno::UNO_QUERY_THROW );
2460 		uno::Reference< sheet::XCellRangeMovement > xMover( xSheet, uno::UNO_QUERY_THROW);
2461 		uno::Reference< sheet::XCellAddressable > xDestination( xDest->getCellByPosition(
2462 												xRange->getColumn()-1,xRange->getRow()-1), uno::UNO_QUERY_THROW );
2463 		uno::Reference< sheet::XCellRangeAddressable > xSource( mxRange, uno::UNO_QUERY);
2464 		xMover->copyRange( xDestination->getCellAddress(), xSource->getRangeAddress() );
2465 	}
2466 	else
2467 	{
2468 		uno::Reference< frame::XModel > xModel = getModelFromRange( mxRange );
2469 		Select();
2470 		excel::implnCopy( xModel );
2471 	}
2472 }
2473 
2474 void
2475 ScVbaRange::Cut(const ::uno::Any& Destination) throw (uno::RuntimeException)
2476 {
2477 	if ( m_Areas->getCount() > 1 )
2478 		throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("That command cannot be used on multiple selections" ) ), uno::Reference< uno::XInterface >() );
2479 	if (Destination.hasValue())
2480 	{
2481 		uno::Reference< excel::XRange > xRange( Destination, uno::UNO_QUERY_THROW );
2482 		uno::Reference< table::XCellRange > xCellRange( xRange->getCellRange(), uno::UNO_QUERY_THROW );
2483 		uno::Reference< sheet::XSheetCellRange > xSheetCellRange(xCellRange, ::uno::UNO_QUERY_THROW );
2484 		uno::Reference< sheet::XSpreadsheet > xSheet = xSheetCellRange->getSpreadsheet();
2485 		uno::Reference< table::XCellRange > xDest( xSheet, uno::UNO_QUERY_THROW );
2486 		uno::Reference< sheet::XCellRangeMovement > xMover( xSheet, uno::UNO_QUERY_THROW);
2487 		uno::Reference< sheet::XCellAddressable > xDestination( xDest->getCellByPosition(
2488 												xRange->getColumn()-1,xRange->getRow()-1), uno::UNO_QUERY);
2489 		uno::Reference< sheet::XCellRangeAddressable > xSource( mxRange, uno::UNO_QUERY);
2490 		xMover->moveRange( xDestination->getCellAddress(), xSource->getRangeAddress() );
2491 	}
2492 	{
2493 		uno::Reference< frame::XModel > xModel = getModelFromRange( mxRange );
2494 		Select();
2495 		excel::implnCut( xModel );
2496 	}
2497 }
2498 
2499 void
2500 ScVbaRange::setNumberFormat( const uno::Any& aFormat ) throw ( script::BasicErrorException, uno::RuntimeException)
2501 {
2502 	rtl::OUString sFormat;
2503 	aFormat >>= sFormat;
2504 	if ( m_Areas->getCount() > 1 )
2505 	{
2506 		sal_Int32 nItems = m_Areas->getCount();
2507 		for ( sal_Int32 index=1; index <= nItems; ++index )
2508 		{
2509 			uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny(index), uno::Any() ), uno::UNO_QUERY_THROW );
2510 			xRange->setNumberFormat( aFormat );
2511 		}
2512 		return;
2513 	}
2514 	NumFormatHelper numFormat( mxRange );
2515 	numFormat.setNumberFormat( sFormat );
2516 }
2517 
2518 uno::Any
2519 ScVbaRange::getNumberFormat() throw ( script::BasicErrorException, uno::RuntimeException)
2520 {
2521 
2522 	if ( m_Areas->getCount() > 1 )
2523 	{
2524 		sal_Int32 nItems = m_Areas->getCount();
2525 		uno::Any aResult = aNULL();
2526 		for ( sal_Int32 index=1; index <= nItems; ++index )
2527 		{
2528 			uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny(index), uno::Any() ), uno::UNO_QUERY_THROW );
2529 			// if the numberformat of one area is different to another
2530 			// return null
2531 			if ( index > 1 )
2532 				if ( aResult != xRange->getNumberFormat() )
2533 					return aNULL();
2534 			aResult = xRange->getNumberFormat();
2535 			if ( aNULL() == aResult )
2536 				return aNULL();
2537 		}
2538 		return aResult;
2539 	}
2540 	NumFormatHelper numFormat( mxRange );
2541 	rtl::OUString sFormat = numFormat.getNumberFormatString();
2542 	if ( sFormat.getLength() > 0 )
2543 		return uno::makeAny( sFormat );
2544 	return aNULL();
2545 }
2546 
2547 uno::Reference< excel::XRange >
2548 ScVbaRange::Resize( const uno::Any &RowSize, const uno::Any &ColumnSize ) throw (uno::RuntimeException)
2549 {
2550 	long nRowSize = 0, nColumnSize = 0;
2551 	sal_Bool bIsRowChanged = ( RowSize >>= nRowSize ), bIsColumnChanged = ( ColumnSize >>= nColumnSize );
2552 	uno::Reference< table::XColumnRowRange > xColumnRowRange(mxRange, ::uno::UNO_QUERY_THROW);
2553 	uno::Reference< sheet::XSheetCellRange > xSheetRange(mxRange, ::uno::UNO_QUERY_THROW);
2554 	uno::Reference< sheet::XSheetCellCursor > xCursor( xSheetRange->getSpreadsheet()->createCursorByRange(xSheetRange), ::uno::UNO_QUERY_THROW );
2555 
2556 	if( !bIsRowChanged )
2557 		nRowSize = xColumnRowRange->getRows()->getCount();
2558 	if( !bIsColumnChanged )
2559 		nColumnSize = xColumnRowRange->getColumns()->getCount();
2560 
2561 	xCursor->collapseToSize( nColumnSize, nRowSize );
2562 	uno::Reference< sheet::XCellRangeAddressable > xCellRangeAddressable(xCursor, ::uno::UNO_QUERY_THROW );
2563 	uno::Reference< table::XCellRange > xRange( xSheetRange->getSpreadsheet(), ::uno::UNO_QUERY_THROW );
2564 	return new ScVbaRange( mxParent, mxContext,xRange->getCellRangeByPosition(
2565 										xCellRangeAddressable->getRangeAddress().StartColumn,
2566 										xCellRangeAddressable->getRangeAddress().StartRow,
2567 										xCellRangeAddressable->getRangeAddress().EndColumn,
2568 										xCellRangeAddressable->getRangeAddress().EndRow ) );
2569 }
2570 
2571 void
2572 ScVbaRange::setWrapText( const uno::Any& aIsWrapped ) throw (script::BasicErrorException, uno::RuntimeException)
2573 {
2574 	if ( m_Areas->getCount() > 1 )
2575 	{
2576 		sal_Int32 nItems = m_Areas->getCount();
2577 		uno::Any aResult;
2578 		for ( sal_Int32 index=1; index <= nItems; ++index )
2579 		{
2580 			uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny(index), uno::Any() ), uno::UNO_QUERY_THROW );
2581 			xRange->setWrapText( aIsWrapped );
2582 		}
2583 		return;
2584 	}
2585 
2586 	uno::Reference< beans::XPropertySet > xProps(mxRange, ::uno::UNO_QUERY_THROW );
2587 	bool bIsWrapped = extractBoolFromAny( aIsWrapped );
2588 	xProps->setPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "IsTextWrapped" ) ), uno::Any( bIsWrapped ) );
2589 }
2590 
2591 uno::Any
2592 ScVbaRange::getWrapText() throw (script::BasicErrorException, uno::RuntimeException)
2593 {
2594 	if ( m_Areas->getCount() > 1 )
2595 	{
2596 		sal_Int32 nItems = m_Areas->getCount();
2597 		uno::Any aResult;
2598 		for ( sal_Int32 index=1; index <= nItems; ++index )
2599 		{
2600 				uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny(index), uno::Any() ), uno::UNO_QUERY_THROW );
2601 				if ( index > 1 )
2602 				if ( aResult != xRange->getWrapText() )
2603 					return aNULL();
2604 			aResult = xRange->getWrapText();
2605 		}
2606 		return aResult;
2607 	}
2608 
2609 	SfxItemSet* pDataSet = getCurrentDataSet();
2610 
2611 	SfxItemState eState = pDataSet->GetItemState( ATTR_LINEBREAK, sal_True, NULL);
2612 	if ( eState == SFX_ITEM_DONTCARE )
2613 		return aNULL();
2614 
2615 	uno::Reference< beans::XPropertySet > xProps(mxRange, ::uno::UNO_QUERY_THROW );
2616 	uno::Any aValue = xProps->getPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "IsTextWrapped" ) ) );
2617 	return aValue;
2618 }
2619 
2620 uno::Reference< excel::XInterior > ScVbaRange::Interior( ) throw ( script::BasicErrorException, uno::RuntimeException)
2621 {
2622 	uno::Reference< beans::XPropertySet > xProps( mxRange, uno::UNO_QUERY_THROW );
2623         return new ScVbaInterior ( this, mxContext, xProps, getScDocument() );
2624 }
2625 uno::Reference< excel::XRange >
2626 ScVbaRange::Range( const uno::Any &Cell1, const uno::Any &Cell2 ) throw (uno::RuntimeException)
2627 {
2628     return Range( Cell1, Cell2, false );
2629 }
2630 uno::Reference< excel::XRange >
2631 ScVbaRange::Range( const uno::Any &Cell1, const uno::Any &Cell2, bool bForceUseInpuRangeTab ) throw (uno::RuntimeException)
2632 
2633 {
2634 	uno::Reference< table::XCellRange > xCellRange = mxRange;
2635 
2636 	if ( m_Areas->getCount() > 1 )
2637 	{
2638 		uno::Reference< container::XIndexAccess > xIndex( mxRanges, uno::UNO_QUERY_THROW );
2639 		xCellRange.set( xIndex->getByIndex( 0 ), uno::UNO_QUERY_THROW );
2640 	}
2641 	else
2642 		xCellRange.set( mxRange );
2643 
2644 	RangeHelper thisRange( xCellRange );
2645 	uno::Reference< table::XCellRange > xRanges = thisRange.getCellRangeFromSheet();
2646 	uno::Reference< sheet::XCellRangeAddressable > xAddressable( xRanges, uno::UNO_QUERY_THROW );
2647 
2648 	uno::Reference< table::XCellRange > xReferrer =
2649 		xRanges->getCellRangeByPosition( getColumn()-1, getRow()-1,
2650 				xAddressable->getRangeAddress().EndColumn,
2651 				xAddressable->getRangeAddress().EndRow );
2652 	// xAddressable now for this range
2653 	xAddressable.set( xReferrer, uno::UNO_QUERY_THROW );
2654 
2655 	if( !Cell1.hasValue() )
2656 		throw uno::RuntimeException(
2657 			rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( " Invalid Argument " ) ),
2658 			uno::Reference< XInterface >() );
2659 
2660 	table::CellRangeAddress resultAddress;
2661 	table::CellRangeAddress parentRangeAddress = xAddressable->getRangeAddress();
2662 
2663 	ScRange aRange;
2664 	// Cell1 defined only
2665 	if ( !Cell2.hasValue() )
2666 	{
2667 		rtl::OUString sName;
2668 		Cell1 >>= sName;
2669 		RangeHelper referRange( xReferrer );
2670 		table::CellRangeAddress referAddress = referRange.getCellRangeAddressable()->getRangeAddress();
2671 		return getRangeForName( mxContext, sName, getScDocShell(), referAddress );
2672 
2673 	}
2674 	else
2675 	{
2676 		table::CellRangeAddress  cell1, cell2;
2677 		cell1 = getCellRangeAddressForVBARange( Cell1, getScDocShell() );
2678 		// Cell1 & Cell2 defined
2679 		// Excel seems to combine the range as the range defined by
2680 		// the combination of Cell1 & Cell2
2681 
2682 		cell2 = getCellRangeAddressForVBARange( Cell2, getScDocShell() );
2683 
2684 		resultAddress.StartColumn = ( cell1.StartColumn <  cell2.StartColumn ) ? cell1.StartColumn : cell2.StartColumn;
2685 		resultAddress.StartRow = ( cell1.StartRow <  cell2.StartRow ) ? cell1.StartRow : cell2.StartRow;
2686 		resultAddress.EndColumn = ( cell1.EndColumn >  cell2.EndColumn ) ? cell1.EndColumn : cell2.EndColumn;
2687 		resultAddress.EndRow = ( cell1.EndRow >  cell2.EndRow ) ? cell1.EndRow : cell2.EndRow;
2688 		if ( bForceUseInpuRangeTab )
2689 		{
2690 			// this is a call from Application.Range( x,y )
2691 			// its possiblefor x or y to specify a different sheet from
2692 			// the current or active on ( but they must be the same )
2693 			if ( cell1.Sheet != cell2.Sheet )
2694 				throw uno::RuntimeException();
2695 			parentRangeAddress.Sheet = cell1.Sheet;
2696 		}
2697 		else
2698 		{
2699 			// this is not a call from Application.Range( x,y )
2700 			// if a different sheet from this range is specified it's
2701 			// an error
2702 			if ( parentRangeAddress.Sheet != cell1.Sheet
2703 			|| parentRangeAddress.Sheet != cell2.Sheet
2704 			)
2705 				throw uno::RuntimeException();
2706 
2707 		}
2708 		ScUnoConversion::FillScRange( aRange, resultAddress );
2709 	}
2710 	ScRange parentAddress;
2711 	ScUnoConversion::FillScRange( parentAddress, parentRangeAddress);
2712 	if ( aRange.aStart.Col() >= 0 && aRange.aStart.Row() >= 0 && aRange.aEnd.Col() >= 0 && aRange.aEnd.Row() >= 0 )
2713 	{
2714 		sal_Int32 nStartX = parentAddress.aStart.Col() + aRange.aStart.Col();
2715 		sal_Int32 nStartY = parentAddress.aStart.Row() + aRange.aStart.Row();
2716 		sal_Int32 nEndX = parentAddress.aStart.Col() + aRange.aEnd.Col();
2717 		sal_Int32 nEndY = parentAddress.aStart.Row() + aRange.aEnd.Row();
2718 
2719 		if ( nStartX <= nEndX && nEndX <= parentAddress.aEnd.Col() &&
2720 			 nStartY <= nEndY && nEndY <= parentAddress.aEnd.Row() )
2721 		{
2722 			ScRange aNew( (SCCOL)nStartX, (SCROW)nStartY, parentAddress.aStart.Tab(),
2723 						  (SCCOL)nEndX, (SCROW)nEndY, parentAddress.aEnd.Tab() );
2724 			xCellRange = new ScCellRangeObj( getScDocShell(), aNew );
2725 		}
2726 	}
2727 
2728 	return new ScVbaRange( mxParent, mxContext, xCellRange );
2729 
2730 }
2731 
2732 // Allow access to underlying openoffice uno api ( useful for debugging
2733 // with openoffice basic )
2734 uno::Any SAL_CALL ScVbaRange::getCellRange(  ) throw (uno::RuntimeException)
2735 {
2736 	uno::Any aAny;
2737 	if ( mxRanges.is() )
2738 		aAny <<= mxRanges;
2739 	else if ( mxRange.is() )
2740 		aAny <<= mxRange;
2741 	return aAny;
2742 }
2743 
2744 /*static*/ uno::Any ScVbaRange::getCellRange( const uno::Reference< excel::XRange >& rxRange ) throw (uno::RuntimeException)
2745 {
2746     if( ScVbaRange* pVbaRange = getImplementation( rxRange ) )
2747         return pVbaRange->getCellRange();
2748     throw uno::RuntimeException();
2749 }
2750 
2751 static sal_uInt16
2752 getPasteFlags (sal_Int32 Paste)
2753 {
2754 	sal_uInt16 nFlags = IDF_NONE;
2755 	switch (Paste) {
2756         case excel::XlPasteType::xlPasteComments:
2757 		nFlags = IDF_NOTE;break;
2758         case excel::XlPasteType::xlPasteFormats:
2759 		nFlags = IDF_ATTRIB;break;
2760         case excel::XlPasteType::xlPasteFormulas:
2761 		nFlags = IDF_FORMULA;break;
2762         case excel::XlPasteType::xlPasteFormulasAndNumberFormats :
2763         case excel::XlPasteType::xlPasteValues:
2764 #ifdef VBA_OOBUILD_HACK
2765 		nFlags = ( IDF_VALUE | IDF_DATETIME | IDF_STRING | IDF_SPECIAL_BOOLEAN ); break;
2766 #else
2767 		nFlags = ( IDF_VALUE | IDF_DATETIME | IDF_STRING ); break;
2768 #endif
2769         case excel::XlPasteType::xlPasteValuesAndNumberFormats:
2770 		nFlags = IDF_VALUE | IDF_ATTRIB; break;
2771         case excel::XlPasteType::xlPasteColumnWidths:
2772         case excel::XlPasteType::xlPasteValidation:
2773 		nFlags = IDF_NONE;break;
2774 	case excel::XlPasteType::xlPasteAll:
2775         case excel::XlPasteType::xlPasteAllExceptBorders:
2776 	default:
2777 		nFlags = IDF_ALL;break;
2778 	};
2779 return nFlags;
2780 }
2781 
2782 static sal_uInt16
2783 getPasteFormulaBits( sal_Int32 Operation)
2784 {
2785 	sal_uInt16 nFormulaBits = PASTE_NOFUNC ;
2786 	switch (Operation)
2787 	{
2788 	case excel::XlPasteSpecialOperation::xlPasteSpecialOperationAdd:
2789 		nFormulaBits = PASTE_ADD;break;
2790 	case excel::XlPasteSpecialOperation::xlPasteSpecialOperationSubtract:
2791 		nFormulaBits = PASTE_SUB;break;
2792 	case excel::XlPasteSpecialOperation::xlPasteSpecialOperationMultiply:
2793 		nFormulaBits = PASTE_MUL;break;
2794 	case excel::XlPasteSpecialOperation::xlPasteSpecialOperationDivide:
2795 		nFormulaBits = PASTE_DIV;break;
2796 
2797 	case excel::XlPasteSpecialOperation::xlPasteSpecialOperationNone:
2798 	default:
2799 		nFormulaBits = PASTE_NOFUNC; break;
2800 	};
2801 
2802 return nFormulaBits;
2803 }
2804 void SAL_CALL
2805 ScVbaRange::PasteSpecial( const uno::Any& Paste, const uno::Any& Operation, const uno::Any& SkipBlanks, const uno::Any& Transpose ) throw (::com::sun::star::uno::RuntimeException)
2806 {
2807 	if ( m_Areas->getCount() > 1 )
2808 		throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("That command cannot be used on multiple selections" ) ), uno::Reference< uno::XInterface >() );
2809         ScDocShell* pShell = getScDocShell();
2810 
2811         uno::Reference< frame::XModel > xModel( ( pShell ? pShell->GetModel() : NULL ), uno::UNO_QUERY_THROW );
2812 	uno::Reference< view::XSelectionSupplier > xSelection( xModel->getCurrentController(), uno::UNO_QUERY_THROW );
2813 	// save old selection
2814 	uno::Reference< uno::XInterface > xSel( xModel->getCurrentSelection() );
2815 	// select this range
2816 	xSelection->select( uno::makeAny( mxRange ) );
2817 	// set up defaults
2818 	sal_Int32 nPaste = excel::XlPasteType::xlPasteAll;
2819 	sal_Int32 nOperation = excel::XlPasteSpecialOperation::xlPasteSpecialOperationNone;
2820 	sal_Bool bTranspose = sal_False;
2821 	sal_Bool bSkipBlanks = sal_False;
2822 
2823 	if ( Paste.hasValue() )
2824 		Paste >>= nPaste;
2825 	if ( Operation.hasValue() )
2826 		Operation >>= nOperation;
2827 	if ( SkipBlanks.hasValue() )
2828 		SkipBlanks >>= bSkipBlanks;
2829 	if ( Transpose.hasValue() )
2830 		Transpose >>= bTranspose;
2831 
2832 	sal_uInt16 nFlags = getPasteFlags(nPaste);
2833 	sal_uInt16 nFormulaBits = getPasteFormulaBits(nOperation);
2834 	excel::implnPasteSpecial(pShell->GetModel(), nFlags,nFormulaBits,bSkipBlanks,bTranspose);
2835 	// restore selection
2836 	xSelection->select( uno::makeAny( xSel ) );
2837 }
2838 
2839 uno::Reference< excel::XRange >
2840 ScVbaRange::getEntireColumnOrRow( bool bColumn ) throw (uno::RuntimeException)
2841 {
2842 	ScCellRangesBase* pUnoRangesBase = getCellRangesBase();
2843 	// copy the range list
2844 	ScRangeList aCellRanges = pUnoRangesBase->GetRangeList();
2845 
2846 	for ( ScRange* pRange = aCellRanges.First() ; pRange; pRange = aCellRanges.Next() )
2847 	{
2848 		if ( bColumn )
2849 		{
2850 			pRange->aStart.SetRow( 0 );
2851 			pRange->aEnd.SetRow( MAXROW );
2852 		}
2853 		else
2854 		{
2855 			pRange->aStart.SetCol( 0 );
2856 			pRange->aEnd.SetCol( MAXCOL );
2857 		}
2858 	}
2859 	if ( aCellRanges.Count() > 1 ) // Multi-Area
2860 	{
2861 		uno::Reference< sheet::XSheetCellRangeContainer > xRanges( new ScCellRangesObj( pUnoRangesBase->GetDocShell(), aCellRanges ) );
2862 
2863 		return new ScVbaRange( mxParent, mxContext, xRanges, !bColumn, bColumn );
2864 	}
2865 	uno::Reference< table::XCellRange > xRange( new ScCellRangeObj( pUnoRangesBase->GetDocShell(), *aCellRanges.First() ) );
2866 	return new ScVbaRange( mxParent, mxContext, xRange, !bColumn, bColumn  );
2867 }
2868 
2869 uno::Reference< excel::XRange > SAL_CALL
2870 ScVbaRange::getEntireRow() throw (uno::RuntimeException)
2871 {
2872 	return getEntireColumnOrRow(false);
2873 }
2874 
2875 uno::Reference< excel::XRange > SAL_CALL
2876 ScVbaRange::getEntireColumn() throw (uno::RuntimeException)
2877 {
2878 	return getEntireColumnOrRow();
2879 }
2880 
2881 uno::Reference< excel::XComment > SAL_CALL
2882 ScVbaRange::AddComment( const uno::Any& Text ) throw (uno::RuntimeException)
2883 {
2884     // if there is already a comment in the top-left cell then throw
2885     if( getComment().is() )
2886         throw uno::RuntimeException();
2887 
2888 	// workaround: Excel allows to create empty comment, Calc does not
2889 	::rtl::OUString aNoteText;
2890 	if( Text.hasValue() && !(Text >>= aNoteText) )
2891         throw uno::RuntimeException();
2892     if( aNoteText.getLength() == 0 )
2893         aNoteText = ::rtl::OUString( sal_Unicode( ' ' ) );
2894 
2895     // try to create a new annotation
2896     table::CellRangeAddress aRangePos = lclGetRangeAddress( mxRange );
2897     table::CellAddress aNotePos( aRangePos.Sheet, aRangePos.StartColumn, aRangePos.StartRow );
2898     uno::Reference< sheet::XSheetCellRange > xCellRange( mxRange, uno::UNO_QUERY_THROW );
2899     uno::Reference< sheet::XSheetAnnotationsSupplier > xAnnosSupp( xCellRange->getSpreadsheet(), uno::UNO_QUERY_THROW );
2900     uno::Reference< sheet::XSheetAnnotations > xAnnos( xAnnosSupp->getAnnotations(), uno::UNO_SET_THROW );
2901     xAnnos->insertNew( aNotePos, aNoteText );
2902 	return new ScVbaComment( this, mxContext, getUnoModel(), mxRange );
2903 }
2904 
2905 uno::Reference< excel::XComment > SAL_CALL
2906 ScVbaRange::getComment() throw (uno::RuntimeException)
2907 {
2908 	// intentional behavior to return a null object if no
2909 	// comment defined
2910 	uno::Reference< excel::XComment > xComment( new ScVbaComment( this, mxContext, getUnoModel(), mxRange ) );
2911 	if ( !xComment->Text( uno::Any(), uno::Any(), uno::Any() ).getLength() )
2912 		return NULL;
2913 	return xComment;
2914 
2915 }
2916 
2917 uno::Reference< beans::XPropertySet >
2918 getRowOrColumnProps( const uno::Reference< table::XCellRange >& xCellRange, bool bRows ) throw ( uno::RuntimeException )
2919 {
2920 	uno::Reference< table::XColumnRowRange > xColRow( xCellRange, uno::UNO_QUERY_THROW );
2921 	uno::Reference< beans::XPropertySet > xProps;
2922 	if ( bRows )
2923 		xProps.set( xColRow->getRows(), uno::UNO_QUERY_THROW );
2924 	else
2925 		xProps.set( xColRow->getColumns(), uno::UNO_QUERY_THROW );
2926 	return xProps;
2927 }
2928 
2929 uno::Any SAL_CALL
2930 ScVbaRange::getHidden() throw (uno::RuntimeException)
2931 {
2932 	// if multi-area result is the result of the
2933 	// first area
2934 	if ( m_Areas->getCount() > 1 )
2935 	{
2936 		uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny(sal_Int32(1)), uno::Any() ), uno::UNO_QUERY_THROW );
2937 		return xRange->getHidden();
2938 	}
2939 	bool bIsVisible = false;
2940 	try
2941 	{
2942 		uno::Reference< beans::XPropertySet > xProps = getRowOrColumnProps( mxRange, mbIsRows );
2943 		if ( !( xProps->getPropertyValue( ISVISIBLE ) >>= bIsVisible ) )
2944 			throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "Failed to get IsVisible property")), uno::Reference< uno::XInterface >() );
2945 	}
2946 	catch( uno::Exception& e )
2947 	{
2948 		throw uno::RuntimeException( e.Message, uno::Reference< uno::XInterface >() );
2949 	}
2950 	return uno::makeAny( !bIsVisible );
2951 }
2952 
2953 void SAL_CALL
2954 ScVbaRange::setHidden( const uno::Any& _hidden ) throw (uno::RuntimeException)
2955 {
2956 	if ( m_Areas->getCount() > 1 )
2957 	{
2958 		sal_Int32 nItems = m_Areas->getCount();
2959 		for ( sal_Int32 index=1; index <= nItems; ++index )
2960 		{
2961 			uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny(index), uno::Any() ), uno::UNO_QUERY_THROW );
2962 			xRange->setHidden( _hidden );
2963 		}
2964 		return;
2965 	}
2966 
2967     bool bHidden = extractBoolFromAny( _hidden );
2968 	try
2969 	{
2970 		uno::Reference< beans::XPropertySet > xProps = getRowOrColumnProps( mxRange, mbIsRows );
2971 		xProps->setPropertyValue( ISVISIBLE, uno::Any( !bHidden ) );
2972 	}
2973 	catch( uno::Exception& e )
2974 	{
2975 		throw uno::RuntimeException( e.Message, uno::Reference< uno::XInterface >() );
2976 	}
2977 }
2978 
2979 ::sal_Bool SAL_CALL
2980 ScVbaRange::Replace( const ::rtl::OUString& What, const ::rtl::OUString& Replacement, const uno::Any& LookAt, const uno::Any& SearchOrder, const uno::Any& MatchCase, const uno::Any& MatchByte, const uno::Any& SearchFormat, const uno::Any& ReplaceFormat  ) throw (uno::RuntimeException)
2981 {
2982 	if ( m_Areas->getCount() > 1 )
2983 	{
2984 		for ( sal_Int32 index = 1; index <= m_Areas->getCount(); ++index )
2985 		{
2986 			uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny( index ), uno::Any() ), uno::UNO_QUERY_THROW );
2987 			xRange->Replace( What, Replacement,  LookAt, SearchOrder, MatchCase, MatchByte, SearchFormat, ReplaceFormat );
2988 		}
2989 		return sal_True; // seems to return true always ( or at least I haven't found the trick of
2990 	}
2991 
2992 	// sanity check required params
2993 	if ( !What.getLength() /*|| !Replacement.getLength()*/ )
2994 		throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("Range::Replace, missing params" )) , uno::Reference< uno::XInterface >() );
2995 	rtl::OUString sWhat = VBAToRegexp( What);
2996 	// #TODO #FIXME SearchFormat & ReplacesFormat are not processed
2997 	// What do we do about MatchByte.. we don't seem to support that
2998 	const SvxSearchItem& globalSearchOptions = ScGlobal::GetSearchItem();
2999 	SvxSearchItem newOptions( globalSearchOptions );
3000 
3001 	sal_Int16 nLook =  globalSearchOptions.GetWordOnly() ?  excel::XlLookAt::xlPart : excel::XlLookAt::xlWhole;
3002 	sal_Int16 nSearchOrder = globalSearchOptions.GetRowDirection() ? excel::XlSearchOrder::xlByRows : excel::XlSearchOrder::xlByColumns;
3003 
3004 	sal_Bool bMatchCase = sal_False;
3005 	uno::Reference< util::XReplaceable > xReplace( mxRange, uno::UNO_QUERY );
3006 	if ( xReplace.is() )
3007 	{
3008 		uno::Reference< util::XReplaceDescriptor > xDescriptor =
3009 			xReplace->createReplaceDescriptor();
3010 
3011 		xDescriptor->setSearchString( sWhat);
3012 		xDescriptor->setPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( SC_UNO_SRCHREGEXP ) ), uno::makeAny( sal_True ) );
3013 		xDescriptor->setReplaceString( Replacement);
3014 		if ( LookAt.hasValue() )
3015 		{
3016 			// sets SearchWords ( true is Cell match )
3017 			nLook =  ::comphelper::getINT16( LookAt );
3018 			sal_Bool bSearchWords = sal_False;
3019 			if ( nLook == excel::XlLookAt::xlPart )
3020 				bSearchWords = sal_False;
3021 			else if ( nLook == excel::XlLookAt::xlWhole )
3022 				bSearchWords = sal_True;
3023 			else
3024 				throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("Range::Replace, illegal value for LookAt" )) , uno::Reference< uno::XInterface >() );
3025 			// set global search props ( affects the find dialog
3026 			// and of course the defaults for this method
3027 			newOptions.SetWordOnly( bSearchWords );
3028 			xDescriptor->setPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( SC_UNO_SRCHWORDS ) ), uno::makeAny( bSearchWords ) );
3029 		}
3030 		// sets SearchByRow ( true for Rows )
3031 		if ( SearchOrder.hasValue() )
3032 		{
3033 			nSearchOrder =  ::comphelper::getINT16( SearchOrder );
3034 			sal_Bool bSearchByRow = sal_False;
3035 			if ( nSearchOrder == excel::XlSearchOrder::xlByColumns )
3036 				bSearchByRow = sal_False;
3037 			else if ( nSearchOrder == excel::XlSearchOrder::xlByRows )
3038 				bSearchByRow = sal_True;
3039 			else
3040 				throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("Range::Replace, illegal value for SearchOrder" )) , uno::Reference< uno::XInterface >() );
3041 
3042 			newOptions.SetRowDirection( bSearchByRow );
3043 			xDescriptor->setPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( SC_UNO_SRCHBYROW ) ), uno::makeAny( bSearchByRow ) );
3044 		}
3045 		if ( MatchCase.hasValue() )
3046 		{
3047 			// SearchCaseSensitive
3048 			MatchCase >>= bMatchCase;
3049 			xDescriptor->setPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( SC_UNO_SRCHCASE ) ), uno::makeAny( bMatchCase ) );
3050 		}
3051 
3052 		ScGlobal::SetSearchItem( newOptions );
3053 		// ignore MatchByte for the moment, its not supported in
3054 		// OOo.org afaik
3055 
3056 		uno::Reference< util::XSearchDescriptor > xSearch( xDescriptor, uno::UNO_QUERY );
3057 		xReplace->replaceAll( xSearch );
3058 	}
3059 	return sal_True; // always
3060 }
3061 
3062 uno::Reference< excel::XRange > SAL_CALL
3063 ScVbaRange::Find( const uno::Any& What, const uno::Any& After, const uno::Any& LookIn, const uno::Any& LookAt, const uno::Any& SearchOrder, const uno::Any& SearchDirection, const uno::Any& MatchCase, const uno::Any& /*MatchByte*/, const uno::Any& /*SearchFormat*/ ) throw (uno::RuntimeException)
3064 {
3065     // return a Range object that represents the first cell where that information is found.
3066     rtl::OUString sWhat;
3067     sal_Int32 nWhat = 0;
3068     double fWhat = 0.0;
3069 
3070     // string.
3071     if( What >>= sWhat )
3072     {
3073         if( !sWhat.getLength() )
3074 		    throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("Range::Find, missing params" )) , uno::Reference< uno::XInterface >() );
3075     }
3076     else if( What >>= nWhat )
3077     {
3078         sWhat = rtl::OUString::valueOf( nWhat );
3079     }
3080     else if( What >>= fWhat )
3081     {
3082         sWhat = rtl::OUString::valueOf( fWhat );
3083     }
3084     else
3085 	    throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("Range::Find, missing params" )) , uno::Reference< uno::XInterface >() );
3086 
3087     rtl::OUString sSearch = VBAToRegexp( sWhat );
3088 
3089 	const SvxSearchItem& globalSearchOptions = ScGlobal::GetSearchItem();
3090 	SvxSearchItem newOptions( globalSearchOptions );
3091 
3092 	sal_Int16 nLookAt =  globalSearchOptions.GetWordOnly() ?  excel::XlLookAt::xlPart : excel::XlLookAt::xlWhole;
3093 	sal_Int16 nSearchOrder = globalSearchOptions.GetRowDirection() ? excel::XlSearchOrder::xlByRows : excel::XlSearchOrder::xlByColumns;
3094 
3095 	uno::Reference< util::XSearchable > xSearch( mxRange, uno::UNO_QUERY );
3096     if( xSearch.is() )
3097     {
3098         uno::Reference< util::XSearchDescriptor > xDescriptor = xSearch->createSearchDescriptor();
3099         xDescriptor->setSearchString( sSearch );
3100         xDescriptor->setPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( SC_UNO_SRCHREGEXP ) ), uno::Any( true ) );
3101 
3102         uno::Reference< excel::XRange > xAfterRange;
3103         uno::Reference< table::XCellRange > xStartCell;
3104         if( After >>= xAfterRange )
3105         {
3106             // After must be a single cell in the range
3107             if( xAfterRange->getCount() > 1 )
3108 		        throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("After must be a single cell." )) , uno::Reference< uno::XInterface >() );
3109             uno::Reference< excel::XRange > xCell( Cells( uno::makeAny( xAfterRange->getRow() ), uno::makeAny( xAfterRange->getColumn() ) ), uno::UNO_QUERY );
3110             if( !xCell.is() )
3111 		        throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("After must be in range." )) , uno::Reference< uno::XInterface >() );
3112             xStartCell.set( xAfterRange->getCellRange(), uno::UNO_QUERY_THROW );
3113         }
3114 
3115         // LookIn
3116         if( LookIn.hasValue() )
3117         {
3118             sal_Int32 nLookIn = 0;
3119             if( LookIn >>= nLookIn )
3120             {
3121                 sal_Int16 nSearchType = 0;
3122                 switch( nLookIn )
3123                 {
3124                     case excel::XlFindLookIn::xlComments :
3125                         nSearchType = SVX_SEARCHIN_NOTE; // Notes
3126                     break;
3127                     case excel::XlFindLookIn::xlFormulas :
3128                         nSearchType = SVX_SEARCHIN_FORMULA;
3129                     break;
3130                     case excel::XlFindLookIn::xlValues :
3131                         nSearchType = SVX_SEARCHIN_VALUE;
3132                     break;
3133                     default:
3134 		                throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("Range::Replace, illegal value for LookIn." )) , uno::Reference< uno::XInterface >() );
3135                 }
3136                 newOptions.SetCellType( nSearchType );
3137                 xDescriptor->setPropertyValue( rtl::OUString::createFromAscii( "SearchType" ), uno::makeAny( nSearchType ) );
3138             }
3139         }
3140 
3141         // LookAt
3142 		if ( LookAt.hasValue() )
3143 		{
3144 			nLookAt =  ::comphelper::getINT16( LookAt );
3145 			sal_Bool bSearchWords = sal_False;
3146 			if ( nLookAt == excel::XlLookAt::xlPart )
3147 				bSearchWords = sal_False;
3148 			else if ( nLookAt == excel::XlLookAt::xlWhole )
3149 				bSearchWords = sal_True;
3150 			else
3151 				throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("Range::Replace, illegal value for LookAt" )) , uno::Reference< uno::XInterface >() );
3152 			newOptions.SetWordOnly( bSearchWords );
3153 			xDescriptor->setPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( SC_UNO_SRCHWORDS ) ), uno::makeAny( bSearchWords ) );
3154         }
3155 
3156         // SearchOrder
3157 		if ( SearchOrder.hasValue() )
3158 		{
3159 			nSearchOrder =  ::comphelper::getINT16( SearchOrder );
3160 			sal_Bool bSearchByRow = sal_False;
3161 			if ( nSearchOrder == excel::XlSearchOrder::xlByColumns )
3162 				bSearchByRow = sal_False;
3163 			else if ( nSearchOrder == excel::XlSearchOrder::xlByRows )
3164 				bSearchByRow = sal_True;
3165 			else
3166 				throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("Range::Replace, illegal value for SearchOrder" )) , uno::Reference< uno::XInterface >() );
3167 
3168 			newOptions.SetRowDirection( bSearchByRow );
3169 			xDescriptor->setPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( SC_UNO_SRCHBYROW ) ), uno::makeAny( bSearchByRow ) );
3170 		}
3171 
3172         // SearchDirection
3173         if ( SearchDirection.hasValue() )
3174         {
3175             sal_Int32 nSearchDirection = 0;
3176             if( SearchDirection >>= nSearchDirection )
3177             {
3178                 sal_Bool bSearchBackwards = sal_False;
3179                 if ( nSearchDirection == excel::XlSearchDirection::xlNext )
3180                     bSearchBackwards = sal_False;
3181                 else if( nSearchDirection == excel::XlSearchDirection::xlPrevious )
3182                     bSearchBackwards = sal_True;
3183                 else
3184 				    throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("Range::Replace, illegal value for SearchDirection" )) , uno::Reference< uno::XInterface >() );
3185                 newOptions.SetBackward( bSearchBackwards );
3186                 xDescriptor->setPropertyValue( rtl::OUString::createFromAscii( "SearchBackwards" ), uno::makeAny( bSearchBackwards ) );
3187             }
3188         }
3189 
3190         // MatchCase
3191         sal_Bool bMatchCase = sal_False;
3192 		if ( MatchCase.hasValue() )
3193 		{
3194 			// SearchCaseSensitive
3195 			if( !( MatchCase >>= bMatchCase ) )
3196 			    throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("Range::Replace, illegal value for MatchCase" )) , uno::Reference< uno::XInterface >() );
3197 		}
3198         xDescriptor->setPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( SC_UNO_SRCHCASE ) ), uno::makeAny( bMatchCase ) );
3199 
3200         // MatchByte
3201         // SearchFormat
3202         // ignore
3203 
3204 		ScGlobal::SetSearchItem( newOptions );
3205 
3206 		uno::Reference< uno::XInterface > xInterface = xStartCell.is() ? xSearch->findNext( xStartCell, xDescriptor) : xSearch->findFirst( xDescriptor );
3207 		uno::Reference< table::XCellRange > xCellRange( xInterface, uno::UNO_QUERY );
3208         if ( xCellRange.is() )
3209         {
3210             uno::Reference< excel::XRange > xResultRange = new ScVbaRange( mxParent, mxContext, xCellRange );
3211             if( xResultRange.is() )
3212             {
3213                 xResultRange->Select();
3214                 return xResultRange;
3215             }
3216         }
3217 
3218     }
3219 
3220     return uno::Reference< excel::XRange >();
3221 }
3222 
3223 uno::Reference< table::XCellRange > processKey( const uno::Any& Key, uno::Reference<  uno::XComponentContext >& xContext, ScDocShell* pDocSh )
3224 {
3225 	uno::Reference< excel::XRange > xKeyRange;
3226 	if ( Key.getValueType() == excel::XRange::static_type() )
3227 	{
3228 		xKeyRange.set( Key, uno::UNO_QUERY_THROW );
3229 	}
3230 	else if ( Key.getValueType() == ::getCppuType( static_cast< const rtl::OUString* >(0) )  )
3231 
3232 	{
3233 		rtl::OUString sRangeName = ::comphelper::getString( Key );
3234 		table::CellRangeAddress  aRefAddr;
3235 		if ( !pDocSh )
3236 			throw uno::RuntimeException( rtl::OUString(RTL_CONSTASCII_USTRINGPARAM("Range::Sort no docshell to calculate key param")), uno::Reference< uno::XInterface >() );
3237 		xKeyRange = getRangeForName( xContext, sRangeName, pDocSh, aRefAddr );
3238 	}
3239 	else
3240 		throw uno::RuntimeException( rtl::OUString(RTL_CONSTASCII_USTRINGPARAM("Range::Sort illegal type value for key param")), uno::Reference< uno::XInterface >() );
3241 	uno::Reference< table::XCellRange > xKey;
3242 	xKey.set( xKeyRange->getCellRange(), uno::UNO_QUERY_THROW );
3243 	return xKey;
3244 }
3245 
3246 // helper method for Sort
3247 sal_Int32 findSortPropertyIndex( const uno::Sequence< beans::PropertyValue >& props,
3248 const rtl::OUString& sPropName ) throw( uno::RuntimeException )
3249 {
3250 	const beans::PropertyValue* pProp = props.getConstArray();
3251 	sal_Int32 nItems = props.getLength();
3252 
3253 	 sal_Int32 count=0;
3254 	for ( ; count < nItems; ++count, ++pProp )
3255 		if ( pProp->Name.equals( sPropName ) )
3256 			return count;
3257 	if ( count == nItems )
3258 		throw uno::RuntimeException( rtl::OUString(RTL_CONSTASCII_USTRINGPARAM("Range::Sort unknown sort property")), uno::Reference< uno::XInterface >() );
3259 	return -1; //should never reach here ( satisfy compiler )
3260 }
3261 
3262 // helper method for Sort
3263 void updateTableSortField( const uno::Reference< table::XCellRange >& xParentRange,
3264 	const uno::Reference< table::XCellRange >& xColRowKey, sal_Int16 nOrder,
3265 	table::TableSortField& aTableField, sal_Bool bIsSortColumn, sal_Bool bMatchCase ) throw ( uno::RuntimeException )
3266 {
3267 		RangeHelper parentRange( xParentRange );
3268 		RangeHelper colRowRange( xColRowKey );
3269 
3270 		table::CellRangeAddress parentRangeAddress = parentRange.getCellRangeAddressable()->getRangeAddress();
3271 
3272 		table::CellRangeAddress colRowKeyAddress = colRowRange.getCellRangeAddressable()->getRangeAddress();
3273 
3274 		// make sure that upper left poing of key range is within the
3275 		// parent range
3276 		if (  ( !bIsSortColumn && colRowKeyAddress.StartColumn >= parentRangeAddress.StartColumn &&
3277 			colRowKeyAddress.StartColumn <= parentRangeAddress.EndColumn ) || ( bIsSortColumn &&
3278 			colRowKeyAddress.StartRow >= parentRangeAddress.StartRow &&
3279 			colRowKeyAddress.StartRow <= parentRangeAddress.EndRow  ) )
3280 		{
3281 			//determine col/row index
3282 			if ( bIsSortColumn )
3283 				aTableField.Field = colRowKeyAddress.StartRow - parentRangeAddress.StartRow;
3284 			else
3285 				aTableField.Field = colRowKeyAddress.StartColumn - parentRangeAddress.StartColumn;
3286 			aTableField.IsCaseSensitive = bMatchCase;
3287 
3288 			if ( nOrder ==  excel::XlSortOrder::xlAscending )
3289 				aTableField.IsAscending = sal_True;
3290 			else
3291 				aTableField.IsAscending = sal_False;
3292 		}
3293 		else
3294 			throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "Illegal Key param" ) ), uno::Reference< uno::XInterface >() );
3295 
3296 
3297 }
3298 
3299 void SAL_CALL
3300 ScVbaRange::Sort( const uno::Any& Key1, const uno::Any& Order1, const uno::Any& Key2, const uno::Any& /*Type*/, const uno::Any& Order2, const uno::Any& Key3, const uno::Any& Order3, const uno::Any& Header, const uno::Any& OrderCustom, const uno::Any& MatchCase, const uno::Any& Orientation, const uno::Any& SortMethod,  const uno::Any& DataOption1, const uno::Any& DataOption2, const uno::Any& DataOption3  ) throw (uno::RuntimeException)
3301 {
3302 	// #TODO# #FIXME# can we do something with Type
3303 	if ( m_Areas->getCount() > 1 )
3304 		throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("That command cannot be used on multiple selections" ) ), uno::Reference< uno::XInterface >() );
3305 
3306 	sal_Int16 nDataOption1 = excel::XlSortDataOption::xlSortNormal;
3307 	sal_Int16 nDataOption2 = excel::XlSortDataOption::xlSortNormal;
3308 	sal_Int16 nDataOption3 = excel::XlSortDataOption::xlSortNormal;
3309 
3310 	ScDocument* pDoc = getScDocument();
3311 	if ( !pDoc )
3312 		throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "Failed to access document from shell" ) ), uno::Reference< uno::XInterface >() );
3313 
3314 	RangeHelper thisRange( mxRange );
3315 	table::CellRangeAddress thisRangeAddress = thisRange.getCellRangeAddressable()->getRangeAddress();
3316 	ScSortParam aSortParam;
3317 	SCTAB nTab = thisRangeAddress.Sheet;
3318 	pDoc->GetSortParam( aSortParam, nTab );
3319 
3320 	if ( DataOption1.hasValue() )
3321 		DataOption1 >>= nDataOption1;
3322 	if ( DataOption2.hasValue() )
3323 		DataOption2 >>= nDataOption2;
3324 	if ( DataOption3.hasValue() )
3325 		DataOption3 >>= nDataOption3;
3326 
3327 	// 1) #TODO #FIXME need to process DataOption[1..3] not used currently
3328 	// 2) #TODO #FIXME need to refactor this ( below ) into a IsSingleCell() method
3329 	uno::Reference< table::XColumnRowRange > xColumnRowRange(mxRange, uno::UNO_QUERY_THROW );
3330 
3331 	// 'Fraid I don't remember what I was trying to achieve here ???
3332 /*
3333 	if (  isSingleCellRange() )
3334 	{
3335 		uno::Reference< XRange > xCurrent = CurrentRegion();
3336 		xCurrent->Sort( Key1, Order1, Key2, Type, Order2, Key3, Order3, Header, OrderCustom, MatchCase, Orientation, SortMethod, DataOption1, DataOption2, DataOption3 );
3337 		return;
3338 	}
3339 */
3340 	// set up defaults
3341 
3342 	sal_Int16 nOrder1 = aSortParam.bAscending[0] ? excel::XlSortOrder::xlAscending : excel::XlSortOrder::xlDescending;
3343 	sal_Int16 nOrder2 = aSortParam.bAscending[1] ? excel::XlSortOrder::xlAscending : excel::XlSortOrder::xlDescending;
3344 	sal_Int16 nOrder3 = aSortParam.bAscending[2] ? excel::XlSortOrder::xlAscending : excel::XlSortOrder::xlDescending;
3345 
3346 	sal_Int16 nCustom = aSortParam.nUserIndex;
3347 	sal_Int16 nSortMethod = excel::XlSortMethod::xlPinYin;
3348 	sal_Bool bMatchCase = aSortParam.bCaseSens;
3349 
3350 	// seems to work opposite to expected, see below
3351 	sal_Int16 nOrientation = aSortParam.bByRow ?  excel::XlSortOrientation::xlSortColumns :  excel::XlSortOrientation::xlSortRows;
3352 
3353 	if ( Orientation.hasValue() )
3354 	{
3355 		// Documentation says xlSortRows is default but that doesn't appear to be
3356 		// the case. Also it appears that xlSortColumns is the default which
3357 		// strangely enought sorts by Row
3358 		nOrientation = ::comphelper::getINT16( Orientation );
3359 		// persist new option to be next calls default
3360 		if ( nOrientation == excel::XlSortOrientation::xlSortRows )
3361 			aSortParam.bByRow = sal_False;
3362 		else
3363 			aSortParam.bByRow = sal_True;
3364 
3365 	}
3366 
3367 	sal_Bool bIsSortColumns=sal_False; // sort by row
3368 
3369 	if ( nOrientation == excel::XlSortOrientation::xlSortRows )
3370 		bIsSortColumns = sal_True;
3371 	sal_Int16 nHeader = 0;
3372 #ifdef VBA_OOBUILD_HACK
3373 	nHeader = aSortParam.nCompatHeader;
3374 #endif
3375 	sal_Bool bContainsHeader = sal_False;
3376 
3377 	if ( Header.hasValue() )
3378 	{
3379 		nHeader = ::comphelper::getINT16( Header );
3380 #ifdef VBA_OOBUILD_HACK
3381 		aSortParam.nCompatHeader = nHeader;
3382 #endif
3383 	}
3384 
3385 	if ( nHeader == excel::XlYesNoGuess::xlGuess )
3386 	{
3387 		bool bHasColHeader = pDoc->HasColHeader(  static_cast< SCCOL >( thisRangeAddress.StartColumn ), static_cast< SCROW >( thisRangeAddress.StartRow ), static_cast< SCCOL >( thisRangeAddress.EndColumn ), static_cast< SCROW >( thisRangeAddress.EndRow ), static_cast< SCTAB >( thisRangeAddress.Sheet ));
3388 		bool bHasRowHeader = pDoc->HasRowHeader(  static_cast< SCCOL >( thisRangeAddress.StartColumn ), static_cast< SCROW >( thisRangeAddress.StartRow ), static_cast< SCCOL >( thisRangeAddress.EndColumn ), static_cast< SCROW >( thisRangeAddress.EndRow ), static_cast< SCTAB >( thisRangeAddress.Sheet ) );
3389 		if ( bHasColHeader || bHasRowHeader )
3390 			nHeader =  excel::XlYesNoGuess::xlYes;
3391 		else
3392 			nHeader =  excel::XlYesNoGuess::xlNo;
3393 #ifdef VBA_OOBUILD_HACK
3394 		aSortParam.nCompatHeader = nHeader;
3395 #endif
3396 	}
3397 
3398 	if ( nHeader == excel::XlYesNoGuess::xlYes )
3399 		bContainsHeader = sal_True;
3400 
3401 	if ( SortMethod.hasValue() )
3402 	{
3403 		nSortMethod = ::comphelper::getINT16( SortMethod );
3404 	}
3405 
3406 	if ( OrderCustom.hasValue() )
3407 	{
3408 		OrderCustom >>= nCustom;
3409 		--nCustom; // 0-based in OOo
3410 		aSortParam.nUserIndex = nCustom;
3411 	}
3412 
3413 	if ( MatchCase.hasValue() )
3414 	{
3415 		MatchCase >>= bMatchCase;
3416 		aSortParam.bCaseSens = bMatchCase;
3417 	}
3418 
3419 	if ( Order1.hasValue() )
3420 	{
3421 		nOrder1 = ::comphelper::getINT16(Order1);
3422 		if (  nOrder1 == excel::XlSortOrder::xlAscending )
3423 			aSortParam.bAscending[0]  = sal_True;
3424 		else
3425 			aSortParam.bAscending[0]  = sal_False;
3426 
3427 	}
3428 	if ( Order2.hasValue() )
3429 	{
3430 		nOrder2 = ::comphelper::getINT16(Order2);
3431 		if ( nOrder2 == excel::XlSortOrder::xlAscending )
3432 			aSortParam.bAscending[1]  = sal_True;
3433 		else
3434 			aSortParam.bAscending[1]  = sal_False;
3435 	}
3436 	if ( Order3.hasValue() )
3437 	{
3438 		nOrder3 = ::comphelper::getINT16(Order3);
3439 		if ( nOrder3 == excel::XlSortOrder::xlAscending )
3440 			aSortParam.bAscending[2]  = sal_True;
3441 		else
3442 			aSortParam.bAscending[2]  = sal_False;
3443 	}
3444 
3445 	uno::Reference< table::XCellRange > xKey1;
3446 	uno::Reference< table::XCellRange > xKey2;
3447 	uno::Reference< table::XCellRange > xKey3;
3448 	ScDocShell* pDocShell = getScDocShell();
3449 	xKey1 = processKey( Key1, mxContext, pDocShell );
3450 	if ( !xKey1.is() )
3451 		throw uno::RuntimeException( rtl::OUString(RTL_CONSTASCII_USTRINGPARAM("Range::Sort needs a key1 param")), uno::Reference< uno::XInterface >() );
3452 
3453 	if ( Key2.hasValue() )
3454 		xKey2 = processKey( Key2, mxContext, pDocShell );
3455 	if ( Key3.hasValue() )
3456 		xKey3 = processKey( Key3, mxContext, pDocShell );
3457 
3458 	uno::Reference< util::XSortable > xSort( mxRange, uno::UNO_QUERY_THROW );
3459 	uno::Sequence< beans::PropertyValue > sortDescriptor = xSort->createSortDescriptor();
3460 	sal_Int32 nTableSortFieldIndex = findSortPropertyIndex( sortDescriptor, rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("SortFields") ) );
3461 
3462 	uno::Sequence< table::TableSortField > sTableFields(1);
3463 	sal_Int32 nTableIndex = 0;
3464 	updateTableSortField(  mxRange, xKey1, nOrder1, sTableFields[ nTableIndex++ ], bIsSortColumns, bMatchCase );
3465 
3466 	if ( xKey2.is() )
3467 	{
3468 		sTableFields.realloc( sTableFields.getLength() + 1 );
3469 		updateTableSortField(  mxRange, xKey2, nOrder2, sTableFields[ nTableIndex++ ], bIsSortColumns, bMatchCase );
3470 	}
3471 	if ( xKey3.is()  )
3472 	{
3473 		sTableFields.realloc( sTableFields.getLength() + 1 );
3474 		updateTableSortField(  mxRange, xKey3, nOrder3, sTableFields[ nTableIndex++ ], bIsSortColumns, bMatchCase );
3475 	}
3476 	sortDescriptor[ nTableSortFieldIndex ].Value <<= sTableFields;
3477 
3478 	sal_Int32 nIndex = 	findSortPropertyIndex( sortDescriptor,  rtl::OUString(RTL_CONSTASCII_USTRINGPARAM("IsSortColumns")) );
3479 	sortDescriptor[ nIndex ].Value <<= bIsSortColumns;
3480 
3481 	nIndex = 	findSortPropertyIndex( sortDescriptor, CONTS_HEADER );
3482 	sortDescriptor[ nIndex ].Value <<= bContainsHeader;
3483 
3484 	pDoc->SetSortParam( aSortParam, nTab );
3485 	xSort->sort( sortDescriptor );
3486 
3487 	// #FIXME #TODO
3488 	// The SortMethod param is not processed ( not sure what its all about, need to
3489 
3490 }
3491 
3492 uno::Reference< excel::XRange > SAL_CALL
3493 ScVbaRange::End( ::sal_Int32 Direction )  throw (uno::RuntimeException)
3494 {
3495 	if ( m_Areas->getCount() > 1 )
3496 	{
3497 		uno::Reference< excel::XRange > xRange( getArea( 0 ), uno::UNO_QUERY_THROW );
3498 		return xRange->End( Direction );
3499 	}
3500 
3501 
3502 	// #FIXME #TODO
3503 	// euch! found my orig implementation sucked, so
3504 	// trying this even suckier one ( really need to use/expose code in
3505 	// around  ScTabView::MoveCursorArea(), thats the bit that calcutes
3506 	// where the cursor should go )
3507 	// Main problem with this method is the ultra hacky attempt to preserve
3508 	// the ActiveCell, there should be no need to go to these extreems
3509 
3510 	// Save ActiveCell pos ( to restore later )
3511 	uno::Any aDft;
3512 	uno::Reference< excel::XApplication > xApplication( Application(), uno::UNO_QUERY_THROW );
3513 	rtl::OUString sActiveCell = xApplication->getActiveCell()->Address(aDft, aDft, aDft, aDft, aDft );
3514 
3515 	// position current cell upper left of this range
3516 	Cells( uno::makeAny( (sal_Int32) 1 ), uno::makeAny( (sal_Int32) 1 ) )->Select();
3517 
3518         uno::Reference< frame::XModel > xModel = getModelFromRange( mxRange );
3519 
3520 	SfxViewFrame* pViewFrame = excel::getViewFrame( xModel );
3521 	if ( pViewFrame )
3522 	{
3523 		SfxAllItemSet aArgs( SFX_APP()->GetPool() );
3524 		// Hoping this will make sure this slot is called
3525 		// synchronously
3526 		SfxBoolItem sfxAsync( SID_ASYNCHRON, sal_False );
3527 		aArgs.Put( sfxAsync, sfxAsync.Which() );
3528 		SfxDispatcher* pDispatcher = pViewFrame->GetDispatcher();
3529 
3530 		sal_uInt16 nSID = 0;
3531 
3532 		switch( Direction )
3533 		{
3534 			case excel::XlDirection::xlDown:
3535 				nSID = SID_CURSORBLKDOWN;
3536 				break;
3537 			case excel::XlDirection::xlUp:
3538 				nSID = SID_CURSORBLKUP;
3539 				break;
3540 			case excel::XlDirection::xlToLeft:
3541 				nSID = SID_CURSORBLKLEFT;
3542 				break;
3543 			case excel::XlDirection::xlToRight:
3544 				nSID = SID_CURSORBLKRIGHT;
3545 				break;
3546 			default:
3547 				throw uno::RuntimeException( ::rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( ": Invalid ColumnIndex" ) ), uno::Reference< uno::XInterface >() );
3548 		}
3549 		if ( pDispatcher )
3550 		{
3551 			pDispatcher->Execute( nSID, (SfxCallMode)SFX_CALLMODE_SYNCHRON, aArgs );
3552 		}
3553 	}
3554 
3555 	// result is the ActiveCell
3556 	rtl::OUString sMoved =	xApplication->getActiveCell()->Address(aDft, aDft, aDft, aDft, aDft );
3557 
3558 	// restore old ActiveCell
3559 	uno::Any aVoid;
3560 
3561 	uno::Reference< excel::XRange > xOldActiveCell( xApplication->getActiveSheet()->Range( uno::makeAny( sActiveCell ), aVoid ), uno::UNO_QUERY_THROW );
3562 	xOldActiveCell->Select();
3563 
3564 	uno::Reference< excel::XRange > resultCell;
3565 
3566 	resultCell.set( xApplication->getActiveSheet()->Range( uno::makeAny( sMoved ), aVoid ), uno::UNO_QUERY_THROW );
3567 
3568 	// return result
3569 
3570 	return resultCell;
3571 }
3572 
3573 bool
3574 ScVbaRange::isSingleCellRange()
3575 {
3576     uno::Reference< sheet::XCellRangeAddressable > xAddressable( mxRange, uno::UNO_QUERY );
3577     if ( xAddressable.is() )
3578     {
3579         table::CellRangeAddress aRangeAddr = xAddressable->getRangeAddress();
3580         return ( aRangeAddr.EndColumn == aRangeAddr.StartColumn && aRangeAddr.EndRow == aRangeAddr.StartRow );
3581     }
3582     return false;
3583 }
3584 
3585 uno::Reference< excel::XCharacters > SAL_CALL
3586 ScVbaRange::characters( const uno::Any& Start, const uno::Any& Length ) throw (uno::RuntimeException)
3587 {
3588 	if ( !isSingleCellRange() )
3589 		throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("Can't create Characters property for multicell range ") ), uno::Reference< uno::XInterface >() );
3590 	uno::Reference< text::XSimpleText > xSimple(mxRange->getCellByPosition(0,0) , uno::UNO_QUERY_THROW );
3591 	ScDocument* pDoc = getDocumentFromRange(mxRange);
3592 	if ( !pDoc )
3593 		throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "Failed to access document from shell" ) ), uno::Reference< uno::XInterface >() );
3594 
3595 	ScVbaPalette aPalette( pDoc->GetDocumentShell() );
3596 	return  new ScVbaCharacters( this, mxContext, aPalette, xSimple, Start, Length );
3597 }
3598 
3599  void SAL_CALL
3600 ScVbaRange::Delete( const uno::Any& Shift ) throw (uno::RuntimeException)
3601 {
3602 	if ( m_Areas->getCount() > 1 )
3603 	{
3604 		sal_Int32 nItems = m_Areas->getCount();
3605 		for ( sal_Int32 index=1; index <= nItems; ++index )
3606 		{
3607 			uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny(index), uno::Any() ), uno::UNO_QUERY_THROW );
3608 			xRange->Delete( Shift );
3609 		}
3610 		return;
3611 	}
3612 	sheet::CellDeleteMode mode = sheet::CellDeleteMode_NONE ;
3613 	RangeHelper thisRange( mxRange );
3614 	table::CellRangeAddress thisAddress = thisRange.getCellRangeAddressable()->getRangeAddress();
3615 	if ( Shift.hasValue() )
3616 	{
3617 		sal_Int32 nShift = 0;
3618 		Shift >>= nShift;
3619 		switch ( nShift )
3620 		{
3621 			case excel::XlDeleteShiftDirection::xlShiftUp:
3622 				mode = sheet::CellDeleteMode_UP;
3623 				break;
3624 			case excel::XlDeleteShiftDirection::xlShiftToLeft:
3625 				mode = sheet::CellDeleteMode_LEFT;
3626 				break;
3627 			default:
3628 				throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM ("Illegal paramater ") ), uno::Reference< uno::XInterface >() );
3629 		}
3630 	}
3631 	else
3632         {
3633 		bool bFullRow = ( thisAddress.StartColumn == 0 && thisAddress.EndColumn == MAXCOL );
3634 	        sal_Int32 nCols = thisAddress.EndColumn - thisAddress.StartColumn;
3635 	        sal_Int32 nRows = thisAddress.EndRow - thisAddress.StartRow;
3636 		if ( mbIsRows || bFullRow || ( nCols >=  nRows ) )
3637 			mode = sheet::CellDeleteMode_UP;
3638 		else
3639 			mode = sheet::CellDeleteMode_LEFT;
3640 	}
3641 	uno::Reference< sheet::XCellRangeMovement > xCellRangeMove( thisRange.getSpreadSheet(), uno::UNO_QUERY_THROW );
3642 	xCellRangeMove->removeRange( thisAddress, mode );
3643 
3644 }
3645 
3646 //XElementAccess
3647 sal_Bool SAL_CALL
3648 ScVbaRange::hasElements() throw (uno::RuntimeException)
3649 {
3650 	uno::Reference< table::XColumnRowRange > xColumnRowRange(mxRange, uno::UNO_QUERY );
3651 	if ( xColumnRowRange.is() )
3652 		if ( xColumnRowRange->getRows()->getCount() ||
3653 			xColumnRowRange->getColumns()->getCount() )
3654 			return sal_True;
3655 	return sal_False;
3656 }
3657 
3658 // XEnumerationAccess
3659 uno::Reference< container::XEnumeration > SAL_CALL
3660 ScVbaRange::createEnumeration() throw (uno::RuntimeException)
3661 {
3662 	if ( mbIsColumns || mbIsRows )
3663 	{
3664 		uno::Reference< table::XColumnRowRange > xColumnRowRange(mxRange, uno::UNO_QUERY );
3665 		uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny( sal_Int32(1) ), uno::Any() ), uno::UNO_QUERY_THROW );
3666                 sal_Int32 nElems = 0;
3667 		if ( mbIsColumns )
3668 			nElems = xColumnRowRange->getColumns()->getCount();
3669 		else
3670 			nElems = xColumnRowRange->getRows()->getCount();
3671                 return new ColumnsRowEnumeration( mxContext, xRange, nElems );
3672 
3673 	}
3674     return new CellsEnumeration( mxParent, mxContext, m_Areas );
3675 }
3676 
3677 ::rtl::OUString SAL_CALL
3678 ScVbaRange::getDefaultMethodName(  ) throw (uno::RuntimeException)
3679 {
3680 	const static rtl::OUString sName( RTL_CONSTASCII_USTRINGPARAM("Item") );
3681 	return sName;
3682 }
3683 
3684 
3685 // returns calc internal col. width ( in points )
3686 double
3687 ScVbaRange::getCalcColWidth( const table::CellRangeAddress& rAddress) throw (uno::RuntimeException)
3688 {
3689 	ScDocument* pDoc = getScDocument();
3690 	sal_uInt16 nWidth = pDoc->GetOriginalWidth( static_cast< SCCOL >( rAddress.StartColumn ), static_cast< SCTAB >( rAddress.Sheet ) );
3691 	double nPoints = lcl_TwipsToPoints( nWidth );
3692 	nPoints = lcl_Round2DecPlaces( nPoints );
3693 	return nPoints;
3694 }
3695 
3696 double
3697 ScVbaRange::getCalcRowHeight( const table::CellRangeAddress& rAddress ) throw (uno::RuntimeException)
3698 {
3699 	ScDocument* pDoc = getDocumentFromRange( mxRange );
3700 	sal_uInt16 nWidth = pDoc->GetOriginalHeight( rAddress.StartRow, rAddress.Sheet );
3701 	double nPoints = lcl_TwipsToPoints( nWidth );
3702 	nPoints = lcl_Round2DecPlaces( nPoints );
3703 	return nPoints;
3704 }
3705 
3706 // return Char Width in points
3707 double getDefaultCharWidth( ScDocShell* pDocShell )
3708 {
3709     ScDocument* pDoc = pDocShell->GetDocument();
3710     OutputDevice* pRefDevice = pDoc->GetRefDevice();
3711     ScPatternAttr* pAttr = pDoc->GetDefPattern();
3712     ::Font aDefFont;
3713     pAttr->GetFont( aDefFont, SC_AUTOCOL_BLACK, pRefDevice );
3714     pRefDevice->SetFont( aDefFont );
3715     long nCharWidth = pRefDevice->GetTextWidth( String( '0' ) );        // 1/100th mm
3716     return lcl_hmmToPoints( nCharWidth );
3717 }
3718 
3719 uno::Any SAL_CALL
3720 ScVbaRange::getColumnWidth() throw (uno::RuntimeException)
3721 {
3722 	sal_Int32 nLen = m_Areas->getCount();
3723 	if ( nLen > 1 )
3724 	{
3725 		uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny( sal_Int32(1) ), uno::Any() ), uno::UNO_QUERY_THROW );
3726 		return xRange->getColumnWidth();
3727 	}
3728 
3729 	double nColWidth = 	0;
3730 	ScDocShell* pShell = getScDocShell();
3731 	if ( pShell )
3732 	{
3733 		uno::Reference< frame::XModel > xModel = pShell->GetModel();
3734 		double defaultCharWidth = getDefaultCharWidth( pShell );
3735 		RangeHelper thisRange( mxRange );
3736 		table::CellRangeAddress thisAddress = thisRange.getCellRangeAddressable()->getRangeAddress();
3737 		sal_Int32 nStartCol = thisAddress.StartColumn;
3738 		sal_Int32 nEndCol = thisAddress.EndColumn;
3739 		sal_uInt16 nColTwips = 0;
3740 		for( sal_Int32 nCol = nStartCol ; nCol <= nEndCol; ++nCol )
3741 		{
3742 			thisAddress.StartColumn = nCol;
3743 			sal_uInt16 nCurTwips = pShell->GetDocument()->GetOriginalWidth( static_cast< SCCOL >( thisAddress.StartColumn ), static_cast< SCTAB >( thisAddress.Sheet ) );
3744 			if ( nCol == nStartCol )
3745 				nColTwips =  nCurTwips;
3746 			if ( nColTwips != nCurTwips )
3747 				return aNULL();
3748 		}
3749         nColWidth = lcl_TwipsToPoints( nColTwips );
3750         if ( nColWidth != 0.0 )
3751             nColWidth = ( nColWidth / defaultCharWidth ) - fExtraWidth;
3752 	}
3753 	nColWidth = lcl_Round2DecPlaces( nColWidth );
3754 	return uno::makeAny( nColWidth );
3755 }
3756 
3757 void SAL_CALL
3758 ScVbaRange::setColumnWidth( const uno::Any& _columnwidth ) throw (uno::RuntimeException)
3759 {
3760 	sal_Int32 nLen = m_Areas->getCount();
3761 	if ( nLen > 1 )
3762 	{
3763 		for ( sal_Int32 index = 1; index != nLen; ++index )
3764 		{
3765 			uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny( sal_Int32(index) ), uno::Any() ), uno::UNO_QUERY_THROW );
3766 			xRange->setColumnWidth( _columnwidth );
3767 		}
3768 		return;
3769 	}
3770 	double nColWidth = 0;
3771 	_columnwidth >>= nColWidth;
3772 	nColWidth = lcl_Round2DecPlaces( nColWidth );
3773         ScDocShell* pDocShell = getScDocShell();
3774         if ( pDocShell )
3775         {
3776             if ( nColWidth != 0.0 )
3777                 nColWidth = ( nColWidth + fExtraWidth ) * getDefaultCharWidth( pDocShell );
3778 			RangeHelper thisRange( mxRange );
3779 			table::CellRangeAddress thisAddress = thisRange.getCellRangeAddressable()->getRangeAddress();
3780 			sal_uInt16 nTwips = lcl_pointsToTwips( nColWidth );
3781 
3782 			ScDocFunc aFunc(*pDocShell);
3783 			SCCOLROW nColArr[2];
3784 			nColArr[0] = thisAddress.StartColumn;
3785 			nColArr[1] = thisAddress.EndColumn;
3786             // #163561# use mode SC_SIZE_DIRECT: hide for width 0, show for other values
3787             aFunc.SetWidthOrHeight( sal_True, 1, nColArr, thisAddress.Sheet, SC_SIZE_DIRECT,
3788 		                                                                        nTwips, sal_True, sal_True );
3789 
3790 		}
3791 }
3792 
3793 uno::Any SAL_CALL
3794 ScVbaRange::getWidth() throw (uno::RuntimeException)
3795 {
3796 	if ( m_Areas->getCount() > 1 )
3797 	{
3798 		uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny( sal_Int32(1) ), uno::Any() ), uno::UNO_QUERY_THROW );
3799 		return xRange->getWidth();
3800 	}
3801 	uno::Reference< table::XColumnRowRange > xColRowRange( mxRange, uno::UNO_QUERY_THROW );
3802 	uno::Reference< container::XIndexAccess > xIndexAccess( xColRowRange->getColumns(), uno::UNO_QUERY_THROW );
3803 	sal_Int32 nElems = xIndexAccess->getCount();
3804 	double nWidth = 0;
3805 	for ( sal_Int32 index=0; index<nElems; ++index )
3806 	{
3807 		uno::Reference< sheet::XCellRangeAddressable > xAddressable( xIndexAccess->getByIndex( index ), uno::UNO_QUERY_THROW );
3808 		double nTmpWidth = getCalcColWidth( xAddressable->getRangeAddress() );
3809 		nWidth += nTmpWidth;
3810 	}
3811 	return uno::makeAny( nWidth );
3812 }
3813 
3814 uno::Any SAL_CALL
3815 ScVbaRange::Areas( const uno::Any& item) throw (uno::RuntimeException)
3816 {
3817 	if ( !item.hasValue() )
3818 		return uno::makeAny( m_Areas );
3819 	return m_Areas->Item( item, uno::Any() );
3820 }
3821 
3822 uno::Reference< excel::XRange >
3823 ScVbaRange::getArea( sal_Int32 nIndex ) throw( css::uno::RuntimeException )
3824 {
3825 	if ( !m_Areas.is() )
3826 		throw uno::RuntimeException( rtl::OUString(RTL_CONSTASCII_USTRINGPARAM("No areas available")), uno::Reference< uno::XInterface >() );
3827 	uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny( ++nIndex ), uno::Any() ), uno::UNO_QUERY_THROW );
3828 	return xRange;
3829 }
3830 
3831 uno::Any
3832 ScVbaRange::Borders( const uno::Any& item ) throw( script::BasicErrorException, uno::RuntimeException )
3833 {
3834 	if ( !item.hasValue() )
3835 		return uno::makeAny( getBorders() );
3836 	return getBorders()->Item( item, uno::Any() );
3837 }
3838 
3839 uno::Any SAL_CALL
3840 ScVbaRange::BorderAround( const css::uno::Any& LineStyle, const css::uno::Any& Weight,
3841                 const css::uno::Any& ColorIndex, const css::uno::Any& Color ) throw (css::uno::RuntimeException)
3842 {
3843     sal_Int32 nCount = getBorders()->getCount();
3844 
3845     for( sal_Int32 i = 0; i < nCount; i++ )
3846     {
3847         const sal_Int32 nLineType = supportedIndexTable[i];
3848         switch( nLineType )
3849         {
3850             case excel::XlBordersIndex::xlEdgeLeft:
3851             case excel::XlBordersIndex::xlEdgeTop:
3852             case excel::XlBordersIndex::xlEdgeBottom:
3853             case excel::XlBordersIndex::xlEdgeRight:
3854             {
3855                 uno::Reference< excel::XBorder > xBorder( m_Borders->Item( uno::makeAny( nLineType ), uno::Any() ), uno::UNO_QUERY_THROW );
3856                 if( LineStyle.hasValue() )
3857                 {
3858                     xBorder->setLineStyle( LineStyle );
3859                 }
3860                 if( Weight.hasValue() )
3861                 {
3862                     xBorder->setWeight( Weight );
3863                 }
3864                 if( ColorIndex.hasValue() )
3865                 {
3866                     xBorder->setColorIndex( ColorIndex );
3867                 }
3868                 if( Color.hasValue() )
3869                 {
3870                     xBorder->setColor( Color );
3871                 }
3872                 break;
3873             }
3874             case excel::XlBordersIndex::xlInsideVertical:
3875             case excel::XlBordersIndex::xlInsideHorizontal:
3876             case excel::XlBordersIndex::xlDiagonalDown:
3877             case excel::XlBordersIndex::xlDiagonalUp:
3878                 break;
3879             default:
3880                 return uno::makeAny( sal_False );
3881         }
3882     }
3883     return uno::makeAny( sal_True );
3884 }
3885 
3886 uno::Any SAL_CALL
3887 ScVbaRange::getRowHeight() throw (uno::RuntimeException)
3888 {
3889 	sal_Int32 nLen = m_Areas->getCount();
3890 	if ( nLen > 1 )
3891 	{
3892 		uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny( sal_Int32(1) ), uno::Any() ), uno::UNO_QUERY_THROW );
3893 		return xRange->getRowHeight();
3894 	}
3895 
3896 	// if any row's RowHeight in the
3897 	// range is different from any other then return NULL
3898 	RangeHelper thisRange( mxRange );
3899 	table::CellRangeAddress thisAddress = thisRange.getCellRangeAddressable()->getRangeAddress();
3900 
3901 	sal_Int32 nStartRow = thisAddress.StartRow;
3902 	sal_Int32 nEndRow = thisAddress.EndRow;
3903         sal_uInt16 nRowTwips = 0;
3904 	// #TODO probably possible to use the SfxItemSet ( and see if
3905 	//  SFX_ITEM_DONTCARE is set ) to improve performance
3906 // #CHECKME looks like this is general behaviour not just row Range specific
3907 //	if ( mbIsRows )
3908 	ScDocShell* pShell = getScDocShell();
3909 	if ( pShell )
3910 	{
3911 		for ( sal_Int32 nRow = nStartRow ; nRow <= nEndRow; ++nRow )
3912 		{
3913 			thisAddress.StartRow = nRow;
3914 			sal_uInt16 nCurTwips = pShell->GetDocument()->GetOriginalHeight( thisAddress.StartRow, thisAddress.Sheet );
3915 			if ( nRow == nStartRow )
3916 				nRowTwips = nCurTwips;
3917 			if ( nRowTwips != nCurTwips )
3918 				return aNULL();
3919 		}
3920 	}
3921 	double nHeight = lcl_Round2DecPlaces( lcl_TwipsToPoints( nRowTwips ) );
3922 	return uno::makeAny( nHeight );
3923 }
3924 
3925 void SAL_CALL
3926 ScVbaRange::setRowHeight( const uno::Any& _rowheight) throw (uno::RuntimeException)
3927 {
3928 	sal_Int32 nLen = m_Areas->getCount();
3929 	if ( nLen > 1 )
3930 	{
3931 		for ( sal_Int32 index = 1; index != nLen; ++index )
3932 		{
3933 			uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny( sal_Int32(index) ), uno::Any() ), uno::UNO_QUERY_THROW );
3934 			xRange->setRowHeight( _rowheight );
3935 		}
3936 		return;
3937 	}
3938 	double nHeight = 0; // Incomming height is in points
3939         _rowheight >>= nHeight;
3940 	nHeight = lcl_Round2DecPlaces( nHeight );
3941 	RangeHelper thisRange( mxRange );
3942 	table::CellRangeAddress thisAddress = thisRange.getCellRangeAddressable()->getRangeAddress();
3943 	sal_uInt16 nTwips = lcl_pointsToTwips( nHeight );
3944 
3945 	ScDocShell* pDocShell = getDocShellFromRange( mxRange );
3946 	ScDocFunc aFunc(*pDocShell);
3947 	SCCOLROW nRowArr[2];
3948 	nRowArr[0] = thisAddress.StartRow;
3949 	nRowArr[1] = thisAddress.EndRow;
3950     // #163561# use mode SC_SIZE_DIRECT: hide for height 0, show for other values
3951     aFunc.SetWidthOrHeight( sal_False, 1, nRowArr, thisAddress.Sheet, SC_SIZE_DIRECT,
3952                                                                         nTwips, sal_True, sal_True );
3953 }
3954 
3955 uno::Any SAL_CALL
3956 ScVbaRange::getPageBreak() throw (uno::RuntimeException)
3957 {
3958 	sal_Int32 nPageBreak = excel::XlPageBreak::xlPageBreakNone;
3959 	ScDocShell* pShell = getDocShellFromRange( mxRange );
3960 	if ( pShell )
3961 	{
3962 		RangeHelper thisRange( mxRange );
3963 		table::CellRangeAddress thisAddress = thisRange.getCellRangeAddressable()->getRangeAddress();
3964 		sal_Bool bColumn = sal_False;
3965 
3966 		if (thisAddress.StartRow==0)
3967 		    bColumn = sal_True;
3968 
3969 		uno::Reference< frame::XModel > xModel = pShell->GetModel();
3970 		if ( xModel.is() )
3971 		{
3972 	        ScDocument* pDoc =  getDocumentFromRange( mxRange );
3973 
3974             ScBreakType nBreak = BREAK_NONE;
3975 			if ( !bColumn )
3976                 nBreak = pDoc->HasRowBreak(thisAddress.StartRow, thisAddress.Sheet);
3977 			else
3978                 nBreak = pDoc->HasColBreak(thisAddress.StartColumn, thisAddress.Sheet);
3979 
3980             if (nBreak & BREAK_PAGE)
3981 			    nPageBreak = excel::XlPageBreak::xlPageBreakAutomatic;
3982 
3983             if (nBreak & BREAK_MANUAL)
3984 			    nPageBreak = excel::XlPageBreak::xlPageBreakManual;
3985 		}
3986 	}
3987 
3988 	return uno::makeAny( nPageBreak );
3989 }
3990 
3991 void SAL_CALL
3992 ScVbaRange::setPageBreak( const uno::Any& _pagebreak) throw (uno::RuntimeException)
3993 {
3994 	sal_Int32 nPageBreak = 0;
3995     _pagebreak >>= nPageBreak;
3996 
3997 	ScDocShell* pShell = getDocShellFromRange( mxRange );
3998 	if ( pShell )
3999 	{
4000 		RangeHelper thisRange( mxRange );
4001 		table::CellRangeAddress thisAddress = thisRange.getCellRangeAddressable()->getRangeAddress();
4002 		if ((thisAddress.StartColumn==0) && (thisAddress.StartRow==0))
4003 		    return;
4004 		sal_Bool bColumn = sal_False;
4005 
4006 		if (thisAddress.StartRow==0)
4007 		    bColumn = sal_True;
4008 
4009 		ScAddress aAddr( static_cast<SCCOL>(thisAddress.StartColumn), thisAddress.StartRow, thisAddress.Sheet );
4010 		uno::Reference< frame::XModel > xModel = pShell->GetModel();
4011 		if ( xModel.is() )
4012 		{
4013 			ScTabViewShell* pViewShell = excel::getBestViewShell( xModel );
4014 			if ( nPageBreak == excel::XlPageBreak::xlPageBreakManual )
4015 			    pViewShell->InsertPageBreak( bColumn, sal_True, &aAddr);
4016 			else if ( nPageBreak == excel::XlPageBreak::xlPageBreakNone )
4017 			    pViewShell->DeletePageBreak( bColumn, sal_True, &aAddr);
4018 		}
4019 	}
4020 }
4021 
4022 uno::Any SAL_CALL
4023 ScVbaRange::getHeight() throw (uno::RuntimeException)
4024 {
4025 	if ( m_Areas->getCount() > 1 )
4026 	{
4027 		uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny( sal_Int32(1) ), uno::Any() ), uno::UNO_QUERY_THROW );
4028 		return xRange->getHeight();
4029 	}
4030 
4031 	uno::Reference< table::XColumnRowRange > xColRowRange( mxRange, uno::UNO_QUERY_THROW );
4032 	uno::Reference< container::XIndexAccess > xIndexAccess( xColRowRange->getRows(), uno::UNO_QUERY_THROW );
4033 	sal_Int32 nElems = xIndexAccess->getCount();
4034 	double nHeight = 0;
4035 	for ( sal_Int32 index=0; index<nElems; ++index )
4036 	{
4037         	uno::Reference< sheet::XCellRangeAddressable > xAddressable( xIndexAccess->getByIndex( index ), uno::UNO_QUERY_THROW );
4038 		nHeight += getCalcRowHeight(xAddressable->getRangeAddress() );
4039 	}
4040 	return uno::makeAny( nHeight );
4041 }
4042 
4043 awt::Point
4044 ScVbaRange::getPosition() throw ( uno::RuntimeException )
4045 {
4046         awt::Point aPoint;
4047 	uno::Reference< beans::XPropertySet > xProps;
4048 	if ( mxRange.is() )
4049 		xProps.set( mxRange, uno::UNO_QUERY_THROW );
4050 	else
4051 		xProps.set( mxRanges, uno::UNO_QUERY_THROW );
4052 	xProps->getPropertyValue(POSITION) >>= aPoint;
4053 	return aPoint;
4054 }
4055 uno::Any SAL_CALL
4056 ScVbaRange::getLeft() throw (uno::RuntimeException)
4057 {
4058 	// helperapi returns the first ranges left ( and top below )
4059 	if ( m_Areas->getCount() > 1 )
4060 		return getArea( 0 )->getLeft();
4061         awt::Point aPoint = getPosition();
4062 	return uno::makeAny( lcl_hmmToPoints( aPoint.X ) );
4063 }
4064 
4065 
4066 uno::Any SAL_CALL
4067 ScVbaRange::getTop() throw (uno::RuntimeException)
4068 {
4069 	// helperapi returns the first ranges top
4070 	if ( m_Areas->getCount() > 1 )
4071 		return getArea( 0 )->getTop();
4072         awt::Point aPoint= getPosition();
4073 	return uno::makeAny( lcl_hmmToPoints( aPoint.Y ) );
4074 }
4075 
4076 uno::Reference< excel::XWorksheet >
4077 ScVbaRange::getWorksheet() throw (uno::RuntimeException)
4078 {
4079 	// #TODO #FIXME parent should always be set up ( currently thats not
4080 	// the case )
4081 	uno::Reference< excel::XWorksheet > xSheet( getParent(), uno::UNO_QUERY );
4082 	if ( !xSheet.is() )
4083 	{
4084 		uno::Reference< table::XCellRange > xRange = mxRange;
4085 
4086 		if ( mxRanges.is() ) // assign xRange to first range
4087 		{
4088 			uno::Reference< container::XIndexAccess > xIndex( mxRanges, uno::UNO_QUERY_THROW );
4089 			xRange.set( xIndex->getByIndex( 0 ), uno::UNO_QUERY_THROW );
4090 		}
4091 		ScDocShell* pDocShell = getDocShellFromRange(xRange);
4092 		RangeHelper rHelper(xRange);
4093 		// parent should be Thisworkbook
4094        	xSheet.set( new ScVbaWorksheet( uno::Reference< XHelperInterface >(), mxContext,rHelper.getSpreadSheet(),pDocShell->GetModel()) );
4095 	}
4096 	return xSheet;
4097 }
4098 
4099 // #TODO remove this ugly application processing
4100 // Process an application Range request e.g. 'Range("a1,b2,a4:b6")
4101 uno::Reference< excel::XRange >
4102 ScVbaRange::ApplicationRange( const uno::Reference< uno::XComponentContext >& xContext, const css::uno::Any &Cell1, const css::uno::Any &Cell2 ) throw (css::uno::RuntimeException)
4103 {
4104 	// Althought the documentation seems clear that Range without a
4105 	// qualifier then its a shortcut for ActiveSheet.Range
4106 	// however, similarly Application.Range is apparently also a
4107 	// shortcut for ActiveSheet.Range
4108 	// The is however a subtle behavioural difference I've come across
4109 	// wrt to named ranges.
4110 	// If a named range "test" exists { Sheet1!$A1 } and the active sheet
4111 	// is Sheet2 then the following will fail
4112 	// msgbox ActiveSheet.Range("test").Address ' failes
4113 	// msgbox WorkSheets("Sheet2").Range("test").Address
4114 	// but !!!
4115 	// msgbox Range("test").Address ' works
4116 	// msgbox Application.Range("test").Address ' works
4117 
4118 	// Single param Range
4119 	rtl::OUString sRangeName;
4120 	Cell1 >>= sRangeName;
4121 	if ( Cell1.hasValue() && !Cell2.hasValue() && sRangeName.getLength() )
4122 	{
4123 		const static rtl::OUString sNamedRanges( RTL_CONSTASCII_USTRINGPARAM("NamedRanges"));
4124 		uno::Reference< beans::XPropertySet > xPropSet( getCurrentExcelDoc(xContext), uno::UNO_QUERY_THROW );
4125 
4126 		uno::Reference< container::XNameAccess > xNamed( xPropSet->getPropertyValue( sNamedRanges ), uno::UNO_QUERY_THROW );
4127 		uno::Reference< sheet::XCellRangeReferrer > xReferrer;
4128 		try
4129 		{
4130 			xReferrer.set ( xNamed->getByName( sRangeName ), uno::UNO_QUERY );
4131 		}
4132 		catch( uno::Exception& /*e*/ )
4133 		{
4134 			// do nothing
4135 		}
4136 		if ( xReferrer.is() )
4137 		{
4138 			uno::Reference< table::XCellRange > xRange = xReferrer->getReferredCells();
4139 			if ( xRange.is() )
4140 			{
4141 				uno::Reference< excel::XRange > xVbRange =  new ScVbaRange( excel::getUnoSheetModuleObj( xRange ), xContext, xRange );
4142 				return xVbRange;
4143 			}
4144 		}
4145 	}
4146 	uno::Reference< sheet::XSpreadsheetView > xView( getCurrentExcelDoc(xContext)->getCurrentController(), uno::UNO_QUERY );
4147 	uno::Reference< table::XCellRange > xSheetRange( xView->getActiveSheet(), uno::UNO_QUERY_THROW );
4148 	ScVbaRange* pRange = new ScVbaRange( excel::getUnoSheetModuleObj( xSheetRange ), xContext, xSheetRange );
4149 	uno::Reference< excel::XRange > xVbSheetRange( pRange );
4150 	return pRange->Range( Cell1, Cell2, true );
4151 }
4152 
4153 uno::Reference< sheet::XDatabaseRanges >
4154 lcl_GetDataBaseRanges( ScDocShell* pShell ) throw ( uno::RuntimeException )
4155 {
4156 	uno::Reference< frame::XModel > xModel;
4157 	if ( pShell )
4158 		xModel.set( pShell->GetModel(), uno::UNO_QUERY_THROW );
4159 	uno::Reference< beans::XPropertySet > xModelProps( xModel, uno::UNO_QUERY_THROW );
4160 	uno::Reference< sheet::XDatabaseRanges > xDBRanges( xModelProps->getPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("DatabaseRanges") ) ), uno::UNO_QUERY_THROW );
4161 	return xDBRanges;
4162 }
4163 // returns the XDatabaseRange for the autofilter on sheet (nSheet)
4164 // also populates sName with the name of range
4165 uno::Reference< sheet::XDatabaseRange >
4166 lcl_GetAutoFiltRange( ScDocShell* pShell, sal_Int16 nSheet, rtl::OUString& sName )
4167 {
4168 	uno::Reference< container::XIndexAccess > xIndexAccess( lcl_GetDataBaseRanges( pShell ), uno::UNO_QUERY_THROW );
4169 	uno::Reference< sheet::XDatabaseRange > xDataBaseRange;
4170 	table::CellRangeAddress dbAddress;
4171 	for ( sal_Int32 index=0; index < xIndexAccess->getCount(); ++index )
4172 	{
4173 		uno::Reference< sheet::XDatabaseRange > xDBRange( xIndexAccess->getByIndex( index ), uno::UNO_QUERY_THROW );
4174 		uno::Reference< container::XNamed > xNamed( xDBRange, uno::UNO_QUERY_THROW );
4175 		// autofilters work weirdly with openoffice, unnamed is the default
4176 		// named range which is used to create an autofilter, but
4177 		// its also possible that another name could be used
4178 		//     this also causes problems when an autofilter is created on
4179 		//     another sheet
4180 		// ( but.. you can use any named range )
4181 		dbAddress = xDBRange->getDataArea();
4182 		if ( dbAddress.Sheet == nSheet )
4183 		{
4184 			sal_Bool bHasAuto = sal_False;
4185 			uno::Reference< beans::XPropertySet > xProps( xDBRange, uno::UNO_QUERY_THROW );
4186 			xProps->getPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("AutoFilter") ) ) >>= bHasAuto;
4187 			if ( bHasAuto )
4188 			{
4189 				sName = xNamed->getName();
4190 				xDataBaseRange=xDBRange;
4191 				break;
4192 			}
4193 		}
4194 	}
4195 	return xDataBaseRange;
4196 }
4197 
4198 // Helper functions for AutoFilter
4199 ScDBData* lcl_GetDBData_Impl( ScDocShell* pDocShell, sal_Int16 nSheet )
4200 {
4201 	rtl::OUString sName;
4202 	lcl_GetAutoFiltRange( pDocShell, nSheet, sName );
4203 	OSL_TRACE("lcl_GetDBData_Impl got autofilter range %s for sheet %d",
4204 		rtl::OUStringToOString( sName, RTL_TEXTENCODING_UTF8 ).getStr() , nSheet );
4205 	ScDBData* pRet = NULL;
4206 	if (pDocShell)
4207 	{
4208 		ScDBCollection* pNames = pDocShell->GetDocument()->GetDBCollection();
4209 		if (pNames)
4210 		{
4211 			sal_uInt16 nPos = 0;
4212 			if (pNames->SearchName( sName , nPos ))
4213 				pRet = (*pNames)[nPos];
4214 		}
4215 	}
4216 	return pRet;
4217 }
4218 
4219 void lcl_SelectAll( ScDocShell* pDocShell, ScQueryParam& aParam )
4220 {
4221 	if ( pDocShell )
4222 	{
4223 		ScViewData* pViewData = pDocShell->GetViewData();
4224 		if ( pViewData )
4225 		{
4226 			OSL_TRACE("Pushing out SelectAll query");
4227 			pViewData->GetView()->Query( aParam, NULL, sal_True );
4228 		}
4229 	}
4230 }
4231 
4232 ScQueryParam lcl_GetQueryParam( ScDocShell* pDocShell, sal_Int16 nSheet )
4233 {
4234 	ScDBData* pDBData = lcl_GetDBData_Impl( pDocShell, nSheet );
4235 	ScQueryParam aParam;
4236 	if (pDBData)
4237 	{
4238 		pDBData->GetQueryParam( aParam );
4239 	}
4240 	return aParam;
4241 }
4242 
4243 void lcl_SetAllQueryForField( ScQueryParam& aParam, SCCOLROW nField )
4244 {
4245 	bool bFound = false;
4246 	SCSIZE i = 0;
4247 	for (; i<MAXQUERY && !bFound; i++)
4248 	{
4249 		ScQueryEntry& rEntry = aParam.GetEntry(i);
4250 		if ( rEntry.nField == nField)
4251 		{
4252 			OSL_TRACE("found at pos %d", i );
4253 			bFound = true;
4254 		}
4255 	}
4256 	if ( bFound )
4257 	{
4258 		OSL_TRACE("field %d to delete at pos %d", nField, ( i - 1 ) );
4259 		aParam.DeleteQuery(--i);
4260 	}
4261 }
4262 
4263 
4264 void lcl_SetAllQueryForField( ScDocShell* pDocShell, SCCOLROW nField, sal_Int16 nSheet )
4265 {
4266 	ScQueryParam aParam = lcl_GetQueryParam( pDocShell, nSheet );
4267 	lcl_SetAllQueryForField( aParam, nField );
4268 	lcl_SelectAll( pDocShell, aParam );
4269 }
4270 
4271 // Modifies sCriteria, and nOp depending on the value of sCriteria
4272 void lcl_setTableFieldsFromCriteria( rtl::OUString& sCriteria1, uno::Reference< beans::XPropertySet >& xDescProps, sheet::TableFilterField2& rFilterField )
4273 {
4274 	// #TODO make this more efficient and cycle through
4275 	// sCriteria1 character by character to pick up <,<>,=, * etc.
4276 	// right now I am more concerned with just getting it to work right
4277 
4278 	sCriteria1 = sCriteria1.trim();
4279 	// table of translation of criteria text to FilterOperators
4280 	// <>searchtext - NOT_EQUAL
4281 	//  =searchtext - EQUAL
4282 	//  *searchtext - startwith
4283 	//  <>*searchtext - doesn't startwith
4284 	//  *searchtext* - contains
4285 	//  <>*searchtext* - doesn't contain
4286 	// [>|>=|<=|...]searchtext for GREATER_value, GREATER_EQUAL_value etc.
4287 	sal_Int32 nPos = 0;
4288 	bool bIsNumeric = false;
4289 	if ( ( nPos = sCriteria1.indexOf( EQUALS ) ) == 0 )
4290 	{
4291 		if ( sCriteria1.getLength() == EQUALS.getLength() )
4292             rFilterField.Operator = sheet::FilterOperator2::EMPTY;
4293 		else
4294 		{
4295             rFilterField.Operator = sheet::FilterOperator2::EQUAL;
4296 			sCriteria1 = sCriteria1.copy( EQUALS.getLength() );
4297 			sCriteria1 = VBAToRegexp( sCriteria1 );
4298 			// UseRegularExpressions
4299 			if ( xDescProps.is() )
4300 				xDescProps->setPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "UseRegularExpressions" ) ), uno::Any( sal_True ) );
4301 		}
4302 
4303 	}
4304 	else if ( ( nPos = sCriteria1.indexOf( NOTEQUALS ) ) == 0 )
4305 	{
4306 		if ( sCriteria1.getLength() == NOTEQUALS.getLength() )
4307             rFilterField.Operator = sheet::FilterOperator2::NOT_EMPTY;
4308 		else
4309 		{
4310             rFilterField.Operator = sheet::FilterOperator2::NOT_EQUAL;
4311 			sCriteria1 = sCriteria1.copy( NOTEQUALS.getLength() );
4312 			sCriteria1 = VBAToRegexp( sCriteria1 );
4313 			// UseRegularExpressions
4314 			if ( xDescProps.is() )
4315 				xDescProps->setPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "UseRegularExpressions" ) ), uno::Any( sal_True ) );
4316 		}
4317 	}
4318 	else if ( ( nPos = sCriteria1.indexOf( GREATERTHAN ) ) == 0 )
4319 	{
4320 		bIsNumeric = true;
4321 		if ( ( nPos = sCriteria1.indexOf( GREATERTHANEQUALS ) ) == 0 )
4322 		{
4323 			sCriteria1 = sCriteria1.copy( GREATERTHANEQUALS.getLength() );
4324             rFilterField.Operator = sheet::FilterOperator2::GREATER_EQUAL;
4325 		}
4326 		else
4327 		{
4328 			sCriteria1 = sCriteria1.copy( GREATERTHAN.getLength() );
4329             rFilterField.Operator = sheet::FilterOperator2::GREATER;
4330 		}
4331 
4332 	}
4333 	else if ( ( nPos = sCriteria1.indexOf( LESSTHAN ) ) == 0 )
4334 	{
4335 		bIsNumeric = true;
4336 		if ( ( nPos = sCriteria1.indexOf( LESSTHANEQUALS ) ) == 0 )
4337 		{
4338 			sCriteria1 = sCriteria1.copy( LESSTHANEQUALS.getLength() );
4339             rFilterField.Operator = sheet::FilterOperator2::LESS_EQUAL;
4340 		}
4341 		else
4342 		{
4343 			sCriteria1 = sCriteria1.copy( LESSTHAN.getLength() );
4344             rFilterField.Operator = sheet::FilterOperator2::LESS;
4345 		}
4346 
4347 	}
4348 	else
4349         rFilterField.Operator = sheet::FilterOperator2::EQUAL;
4350 
4351 	if ( bIsNumeric )
4352 	{
4353 		rFilterField.IsNumeric= sal_True;
4354 		rFilterField.NumericValue = sCriteria1.toDouble();
4355 	}
4356 	rFilterField.StringValue = sCriteria1;
4357 }
4358 
4359 void SAL_CALL
4360 ScVbaRange::AutoFilter( const uno::Any& Field, const uno::Any& Criteria1, const uno::Any& Operator, const uno::Any& Criteria2, const uno::Any& VisibleDropDown ) throw (uno::RuntimeException)
4361 {
4362 	// Is there an existing autofilter
4363 	RangeHelper thisRange( mxRange );
4364 	table::CellRangeAddress thisAddress = thisRange.getCellRangeAddressable()->getRangeAddress();
4365 	sal_Int16 nSheet = thisAddress.Sheet;
4366 	ScDocShell* pShell = getScDocShell();
4367 	sal_Bool bHasAuto = sal_False;
4368 	rtl::OUString sAutofiltRangeName;
4369 	uno::Reference< sheet::XDatabaseRange > xDataBaseRange = lcl_GetAutoFiltRange( pShell, nSheet, sAutofiltRangeName );
4370 	if ( xDataBaseRange.is() )
4371 		bHasAuto = true;
4372 
4373 	uno::Reference< table::XCellRange > xFilterRange;
4374 	if ( !bHasAuto )
4375 	{
4376 		if (  m_Areas->getCount() > 1 )
4377 			throw uno::RuntimeException( STR_ERRORMESSAGE_APPLIESTOSINGLERANGEONLY, uno::Reference< uno::XInterface >() );
4378 
4379 		table::CellRangeAddress autoFiltAddress;
4380 		//CurrentRegion()
4381 		if ( isSingleCellRange() )
4382 		{
4383 			uno::Reference< excel::XRange > xCurrent( CurrentRegion() );
4384 			if ( xCurrent.is() )
4385 			{
4386 				ScVbaRange* pRange = getImplementation( xCurrent );
4387 				if ( pRange->isSingleCellRange() )
4388 					throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("Can't create AutoFilter") ), uno::Reference< uno::XInterface >() );
4389 				if ( pRange )
4390 				{
4391 					RangeHelper currentRegion( pRange->mxRange );
4392 					autoFiltAddress = currentRegion.getCellRangeAddressable()->getRangeAddress();
4393 				}
4394 			}
4395 		}
4396 		else // multi-cell range
4397 		{
4398 			RangeHelper multiCellRange( mxRange );
4399 			autoFiltAddress = multiCellRange.getCellRangeAddressable()->getRangeAddress();
4400             // #163530# Filter box shows only entry of first row
4401             ScDocument* pDocument = ( pShell ? pShell->GetDocument() : NULL );
4402             if ( pDocument )
4403             {
4404                 SCCOL nStartCol = autoFiltAddress.StartColumn;
4405                 SCROW nStartRow = autoFiltAddress.StartRow;
4406                 SCCOL nEndCol = autoFiltAddress.EndColumn;
4407                 SCROW nEndRow = autoFiltAddress.EndRow;
4408                 pDocument->GetDataArea( autoFiltAddress.Sheet, nStartCol, nStartRow, nEndCol, nEndRow, sal_True, true );
4409                 autoFiltAddress.StartColumn = nStartCol;
4410                 autoFiltAddress.StartRow = nStartRow;
4411                 autoFiltAddress.EndColumn = nEndCol;
4412                 autoFiltAddress.EndRow = nEndRow;
4413             }
4414 		}
4415 
4416 		uno::Reference< sheet::XDatabaseRanges > xDBRanges = lcl_GetDataBaseRanges( pShell );
4417 		if ( xDBRanges.is() )
4418 		{
4419 			rtl::OUString sGenName( RTL_CONSTASCII_USTRINGPARAM("VBA_Autofilter_") );
4420 			sGenName += rtl::OUString::valueOf( static_cast< sal_Int32 >( nSheet ) );
4421 			OSL_TRACE("Going to add new autofilter range.. name %s",
4422 				rtl::OUStringToOString( sGenName, RTL_TEXTENCODING_UTF8 ).getStr() , nSheet );
4423 			if ( !xDBRanges->hasByName( sGenName ) )
4424 				xDBRanges->addNewByName(  sGenName, autoFiltAddress );
4425 			xDataBaseRange.set( xDBRanges->getByName(  sGenName ), uno::UNO_QUERY_THROW );
4426 		}
4427 		if ( !xDataBaseRange.is() )
4428 			throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("Failed to find the autofilter placeholder range" ) ), uno::Reference< uno::XInterface >() );
4429 
4430 		uno::Reference< beans::XPropertySet > xDBRangeProps( xDataBaseRange, uno::UNO_QUERY_THROW );
4431 		// set autofilt
4432 		xDBRangeProps->setPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("AutoFilter") ), uno::Any(sal_True) );
4433 		// set header (autofilter always need column headers)
4434 		uno::Reference< beans::XPropertySet > xFiltProps( xDataBaseRange->getFilterDescriptor(), uno::UNO_QUERY_THROW );
4435 		xFiltProps->setPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ContainsHeader") ), uno::Any( sal_True ) );
4436 	}
4437 
4438 
4439 	sal_Int32 nField = 0; // *IS* 1 based
4440 	rtl::OUString sCriteria1;
4441 	sal_Int32 nOperator = excel::XlAutoFilterOperator::xlAnd;
4442 
4443 	sal_Bool bVisible = sal_True;
4444 	bool  bChangeDropDown = false;
4445 	VisibleDropDown >>= bVisible;
4446 
4447 	if ( bVisible == bHasAuto ) // dropdown is displayed/notdisplayed as
4448 								// required
4449 		bVisible = sal_False;
4450 	else
4451 		bChangeDropDown = true;
4452 	sheet::FilterConnection nConn = sheet::FilterConnection_AND;
4453 	double nCriteria1 = 0;
4454 
4455 	bool bHasCritValue = Criteria1.hasValue();
4456 	bool bCritHasNumericValue = sal_False; // not sure if a numeric criteria is possible
4457 	if ( bHasCritValue )
4458 		bCritHasNumericValue = ( Criteria1 >>= nCriteria1 );
4459 
4460 	if (  !Field.hasValue() && ( Criteria1.hasValue() || Operator.hasValue() || Criteria2.hasValue() ) )
4461 		throw uno::RuntimeException();
4462 	// Use the normal uno api, sometimes e.g. when you want to use ALL as the filter
4463 	// we can't use refresh as the uno interface doesn't have a concept of ALL
4464 	// in this case we just call the core calc functionality -
4465 	bool bAll = false;
4466 	if ( ( Field >>= nField )  )
4467 	{
4468         uno::Reference< sheet::XSheetFilterDescriptor2 > xDesc(
4469                 xDataBaseRange->getFilterDescriptor(), uno::UNO_QUERY );
4470         if ( xDesc.is() )
4471         {
4472             uno::Sequence< sheet::TableFilterField2 > sTabFilts;
4473             uno::Reference< beans::XPropertySet > xDescProps( xDesc, uno::UNO_QUERY_THROW );
4474 		if ( Criteria1.hasValue() )
4475 		{
4476 			sTabFilts.realloc( 1 );
4477             sTabFilts[0].Operator = sheet::FilterOperator2::EQUAL;// sensible default
4478 			if ( !bCritHasNumericValue )
4479 			{
4480 				Criteria1 >>= sCriteria1;
4481 				sTabFilts[0].IsNumeric = bCritHasNumericValue;
4482 				if ( bHasCritValue && sCriteria1.getLength() )
4483 					lcl_setTableFieldsFromCriteria( sCriteria1, xDescProps, sTabFilts[0]  );
4484 				else
4485 					bAll = true;
4486 			}
4487 			else // numeric
4488 			{
4489 				sTabFilts[0].IsNumeric = sal_True;
4490 				sTabFilts[0].NumericValue = nCriteria1;
4491 			}
4492 		}
4493 		else // no value specified
4494 			bAll = true;
4495 		// not sure what the relationship between Criteria1 and Operator is,
4496 		// e.g. can you have a Operator without a Criteria ? in openoffice it
4497 		if ( Operator.hasValue()  && ( Operator >>= nOperator ) )
4498 		{
4499 			// if its a bottom/top Ten(Percent/Value) and there
4500 			// is no value specified for critera1 set it to 10
4501 			if ( !bCritHasNumericValue && !sCriteria1.getLength() && ( nOperator != excel::XlAutoFilterOperator::xlOr ) && ( nOperator != excel::XlAutoFilterOperator::xlAnd ) )
4502 			{
4503 				sTabFilts[0].IsNumeric = sal_True;
4504 				sTabFilts[0].NumericValue = 10;
4505 				bAll = false;
4506 			}
4507 			switch ( nOperator )
4508 			{
4509 				case excel::XlAutoFilterOperator::xlBottom10Items:
4510                     sTabFilts[0].Operator = sheet::FilterOperator2::BOTTOM_VALUES;
4511 					break;
4512 				case excel::XlAutoFilterOperator::xlBottom10Percent:
4513                     sTabFilts[0].Operator = sheet::FilterOperator2::BOTTOM_PERCENT;
4514 					break;
4515 				case excel::XlAutoFilterOperator::xlTop10Items:
4516                     sTabFilts[0].Operator = sheet::FilterOperator2::TOP_VALUES;
4517 					break;
4518 				case excel::XlAutoFilterOperator::xlTop10Percent:
4519                     sTabFilts[0].Operator = sheet::FilterOperator2::TOP_PERCENT;
4520 					break;
4521 				case excel::XlAutoFilterOperator::xlOr:
4522 					nConn = sheet::FilterConnection_OR;
4523 					break;
4524 				case excel::XlAutoFilterOperator::xlAnd:
4525 					nConn = sheet::FilterConnection_AND;
4526 					break;
4527 				default:
4528 					throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("UnknownOption") ), uno::Reference< uno::XInterface >() );
4529 
4530 			}
4531 
4532 		}
4533 		if ( !bAll )
4534 		{
4535 			sTabFilts[0].Connection = sheet::FilterConnection_AND;
4536 			sTabFilts[0].Field = (nField - 1);
4537 
4538 			rtl::OUString sCriteria2;
4539 			if ( Criteria2.hasValue() ) // there is a Criteria2
4540 			{
4541 				sTabFilts.realloc(2);
4542 				sTabFilts[1].Field = sTabFilts[0].Field;
4543 				sTabFilts[1].Connection = nConn;
4544 
4545 				if ( Criteria2 >>= sCriteria2 )
4546 				{
4547 					if ( sCriteria2.getLength() > 0 )
4548 					{
4549 						uno::Reference< beans::XPropertySet > xProps;
4550 						lcl_setTableFieldsFromCriteria( sCriteria2, xProps,  sTabFilts[1] );
4551 						sTabFilts[1].IsNumeric = sal_False;
4552 					}
4553 				}
4554 				else // numeric
4555 				{
4556 					Criteria2 >>= sTabFilts[1].NumericValue;
4557 					sTabFilts[1].IsNumeric = sal_True;
4558                     sTabFilts[1].Operator = sheet::FilterOperator2::EQUAL;
4559 				}
4560 			}
4561 		}
4562 
4563         xDesc->setFilterFields2( sTabFilts );
4564 		if ( !bAll )
4565 		{
4566 			xDataBaseRange->refresh();
4567 		}
4568 		else
4569 			// was 0 based now seems to be 1
4570 			lcl_SetAllQueryForField( pShell, nField, nSheet );
4571         }
4572 	}
4573 	else
4574 	{
4575 		// this is just to toggle autofilter on and off ( not to be confused with
4576 		// a VisibleDropDown option combined with a field, in that case just the
4577 		// button should be disabled ) - currently we don't support that
4578 		bChangeDropDown = true;
4579 		uno::Reference< beans::XPropertySet > xDBRangeProps( xDataBaseRange, uno::UNO_QUERY_THROW );
4580 		if ( bHasAuto )
4581 		{
4582 			// find the any field with the query and select all
4583 			ScQueryParam aParam = lcl_GetQueryParam( pShell, nSheet );
4584 			SCSIZE i = 0;
4585 			for (; i<MAXQUERY; i++)
4586 			{
4587 				ScQueryEntry& rEntry = aParam.GetEntry(i);
4588 				if ( rEntry.bDoQuery )
4589 					lcl_SetAllQueryForField( pShell, rEntry.nField, nSheet );
4590 			}
4591 			// remove exising filters
4592             uno::Reference< sheet::XSheetFilterDescriptor2 > xSheetFilterDescriptor(
4593                     xDataBaseRange->getFilterDescriptor(), uno::UNO_QUERY );
4594             if( xSheetFilterDescriptor.is() )
4595 			    xSheetFilterDescriptor->setFilterFields2( uno::Sequence< sheet::TableFilterField2 >() );
4596 		}
4597 		xDBRangeProps->setPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("AutoFilter") ), uno::Any(!bHasAuto) );
4598 
4599 	}
4600 }
4601 
4602 void SAL_CALL
4603 ScVbaRange::Insert( const uno::Any& Shift, const uno::Any& /* CopyOrigin */ ) throw (uno::RuntimeException)
4604 {
4605 	// It appears ( from the web ) that the undocumented CopyOrigin
4606 	// param should contain member of enum XlInsertFormatOrigin
4607 	// which can have values xlFormatFromLeftOrAbove or xlFormatFromRightOrBelow
4608 	// #TODO investigate resultant behaviour using these constants
4609 	// currently just processing Shift
4610 
4611 	sheet::CellInsertMode mode = sheet::CellInsertMode_NONE;
4612 	if ( Shift.hasValue() )
4613 	{
4614 		sal_Int32 nShift = 0;
4615 		Shift >>= nShift;
4616 		switch ( nShift )
4617 		{
4618 			case excel::XlInsertShiftDirection::xlShiftToRight:
4619 				mode = sheet::CellInsertMode_RIGHT;
4620 				break;
4621 			case excel::XlInsertShiftDirection::xlShiftDown:
4622 				mode = sheet::CellInsertMode_DOWN;
4623 				break;
4624 			default:
4625 				throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM ("Illegal paramater ") ), uno::Reference< uno::XInterface >() );
4626 		}
4627 	}
4628 	else
4629 	{
4630 		if ( getRow() >=  getColumn() )
4631 			mode = sheet::CellInsertMode_DOWN;
4632 		else
4633 			mode = sheet::CellInsertMode_RIGHT;
4634 	}
4635 	RangeHelper thisRange( mxRange );
4636 	table::CellRangeAddress thisAddress = thisRange.getCellRangeAddressable()->getRangeAddress();
4637 	uno::Reference< sheet::XCellRangeMovement > xCellRangeMove( thisRange.getSpreadSheet(), uno::UNO_QUERY_THROW );
4638 	xCellRangeMove->insertCells( thisAddress, mode );
4639 
4640     // Paste from clipboard only if the clipboard content was copied via VBA, and not already pasted via VBA again.
4641     // "Insert" behavior should not depend on random clipboard content previously copied by the user.
4642     ScTransferObj* pClipObj = ScTransferObj::GetOwnClipboard( NULL );
4643     if ( pClipObj && pClipObj->GetUseInApi() )
4644 	{
4645 		// After the insert ( this range ) actually has moved
4646 		ScRange aRange( static_cast< SCCOL >( thisAddress.StartColumn ), static_cast< SCROW >( thisAddress.StartRow ), static_cast< SCTAB >( thisAddress.Sheet ), static_cast< SCCOL >( thisAddress.EndColumn ), static_cast< SCROW >( thisAddress.EndRow ), static_cast< SCTAB >( thisAddress.Sheet ) );
4647 	 	uno::Reference< table::XCellRange > xRange( new ScCellRangeObj( getDocShellFromRange( mxRange ) , aRange ) );
4648 		uno::Reference< excel::XRange > xVbaRange( new ScVbaRange( mxParent, mxContext, xRange, mbIsRows, mbIsColumns ) );
4649 		xVbaRange->PasteSpecial( uno::Any(), uno::Any(), uno::Any(), uno::Any() );
4650 	}
4651 }
4652 
4653 void SAL_CALL
4654 ScVbaRange::Autofit() throw (uno::RuntimeException)
4655 {
4656 	sal_Int32 nLen = m_Areas->getCount();
4657 	if ( nLen > 1 )
4658 	{
4659 		for ( sal_Int32 index = 1; index != nLen; ++index )
4660 		{
4661 			uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny( sal_Int32(index) ), uno::Any() ), uno::UNO_QUERY_THROW );
4662 			xRange->Autofit();
4663 		}
4664 		return;
4665 	}
4666 		// if the range is a not a row or column range autofit will
4667 		// throw an error
4668 
4669 		if ( !( mbIsColumns || mbIsRows ) )
4670 			DebugHelper::exception(SbERR_METHOD_FAILED, rtl::OUString());
4671         ScDocShell* pDocShell = getDocShellFromRange( mxRange );
4672         if ( pDocShell )
4673         {
4674 			RangeHelper thisRange( mxRange );
4675 			table::CellRangeAddress thisAddress = thisRange.getCellRangeAddressable()->getRangeAddress();
4676 
4677 			ScDocFunc aFunc(*pDocShell);
4678 			SCCOLROW nColArr[2];
4679 			nColArr[0] = thisAddress.StartColumn;
4680 			nColArr[1] = thisAddress.EndColumn;
4681 			sal_Bool bDirection = sal_True;
4682 			if ( mbIsRows )
4683 			{
4684 				bDirection = sal_False;
4685 				nColArr[0] = thisAddress.StartRow;
4686 				nColArr[1] = thisAddress.EndRow;
4687 			}
4688 			aFunc.SetWidthOrHeight( bDirection, 1, nColArr, thisAddress.Sheet, SC_SIZE_OPTIMAL,
4689 		                                                                        0, sal_True, sal_True );
4690 
4691 	}
4692 }
4693 
4694 /***************************************************************************************
4695  * interface for text:
4696  * com.sun.star.text.XText, com.sun.star.table.XCell, com.sun.star.container.XEnumerationAccess
4697  * com.sun.star.text.XTextRange,
4698  * the main problem is to recognize the numeric and date, which assosiate with DecimalSeparator, ThousandsSeparator,
4699  * TrailingMinusNumbers and FieldInfo.
4700 ***************************************************************************************/
4701 void SAL_CALL
4702 ScVbaRange::TextToColumns( const css::uno::Any& Destination, const css::uno::Any& DataType, const css::uno::Any& TextQualifier,
4703         const css::uno::Any& ConsecutinveDelimiter, const css::uno::Any& Tab, const css::uno::Any& Semicolon, const css::uno::Any& Comma,
4704         const css::uno::Any& Space, const css::uno::Any& Other, const css::uno::Any& OtherChar, const css::uno::Any& /*FieldInfo*/,
4705         const css::uno::Any& DecimalSeparator, const css::uno::Any& ThousandsSeparator, const css::uno::Any& /*TrailingMinusNumbers*/  ) throw (css::uno::RuntimeException)
4706 {
4707     uno::Reference< excel::XRange > xRange;
4708     if( Destination.hasValue() )
4709     {
4710         if( !( Destination >>= xRange ) )
4711             throw uno::RuntimeException( rtl::OUString::createFromAscii( "Destination parameter should be a range" ),
4712                     uno::Reference< uno::XInterface >() );
4713         OSL_TRACE("set range\n");
4714     }
4715     else
4716     {
4717         //set as current
4718         xRange = this;
4719         OSL_TRACE("set range as himself\n");
4720     }
4721 
4722    sal_Int16 xlTextParsingType = excel::XlTextParsingType::xlDelimited;
4723     if ( DataType.hasValue() )
4724     {
4725         if( !( DataType >>= xlTextParsingType ) )
4726             throw uno::RuntimeException( rtl::OUString::createFromAscii( "DataType parameter should be a short" ),
4727                     uno::Reference< uno::XInterface >() );
4728         OSL_TRACE("set Datatype\n" );
4729     }
4730     sal_Bool bDilimited = ( xlTextParsingType == excel::XlTextParsingType::xlDelimited );
4731 
4732     sal_Int16 xlTextQualifier = excel::XlTextQualifier::xlTextQualifierDoubleQuote;
4733     if( TextQualifier.hasValue() )
4734     {
4735         if( !( TextQualifier >>= xlTextQualifier ))
4736              throw uno::RuntimeException( rtl::OUString::createFromAscii( "TextQualifier parameter should be a short" ),
4737                     uno::Reference< uno::XInterface >() );
4738         OSL_TRACE("set TextQualifier\n");
4739     }
4740 
4741     sal_Bool bConsecutinveDelimiter = sal_False;
4742     if( ConsecutinveDelimiter.hasValue() )
4743     {
4744         if( !( ConsecutinveDelimiter >>= bConsecutinveDelimiter ) )
4745             throw uno::RuntimeException( rtl::OUString::createFromAscii( "ConsecutinveDelimiter parameter should be a boolean" ),
4746                     uno::Reference< uno::XInterface >() );
4747         OSL_TRACE("set ConsecutinveDelimiter\n");
4748     }
4749 
4750     sal_Bool bTab = sal_False;
4751     if( Tab.hasValue() && bDilimited )
4752     {
4753         if( !( Tab >>= bTab ) )
4754             throw uno::RuntimeException( rtl::OUString::createFromAscii( "Tab parameter should be a boolean" ),
4755                     uno::Reference< uno::XInterface >() );
4756         OSL_TRACE("set Tab\n");
4757     }
4758 
4759     sal_Bool bSemicolon = sal_False;
4760     if( Semicolon.hasValue() && bDilimited )
4761     {
4762         if( !( Semicolon >>= bSemicolon ) )
4763             throw uno::RuntimeException( rtl::OUString::createFromAscii( "Semicolon parameter should be a boolean" ),
4764                     uno::Reference< uno::XInterface >() );
4765         OSL_TRACE("set Semicolon\n");
4766     }
4767     sal_Bool bComma = sal_False;
4768     if( Comma.hasValue() && bDilimited )
4769     {
4770         if( !( Comma >>= bComma ) )
4771             throw uno::RuntimeException( rtl::OUString::createFromAscii( "Comma parameter should be a boolean" ),
4772                     uno::Reference< uno::XInterface >() );
4773         OSL_TRACE("set Comma\n");
4774     }
4775     sal_Bool bSpace = sal_False;
4776     if( Space.hasValue() && bDilimited )
4777     {
4778         if( !( Space >>= bSpace ) )
4779             throw uno::RuntimeException( rtl::OUString::createFromAscii( "Space parameter should be a boolean" ),
4780                     uno::Reference< uno::XInterface >() );
4781         OSL_TRACE("set Space\n");
4782     }
4783     sal_Bool bOther = sal_False;
4784     rtl::OUString sOtherChar;
4785     if( Other.hasValue() && bDilimited )
4786     {
4787         if( Other >>= bOther )
4788         {
4789             if( OtherChar.hasValue() )
4790                 if( !( OtherChar >>= sOtherChar ) )
4791                     throw uno::RuntimeException( rtl::OUString::createFromAscii( "OtherChar parameter should be a String" ),
4792                         uno::Reference< uno::XInterface >() );
4793         OSL_TRACE("set OtherChar\n" );
4794         }
4795      else if( bOther )
4796             throw uno::RuntimeException( rtl::OUString::createFromAscii( "Other parameter should be a True" ),
4797                     uno::Reference< uno::XInterface >() );
4798     }
4799  //TODO* FieldInfo   Optional Variant. An array containing parse information for the individual columns of data. The interpretation depends on the value of DataType. When the data is delimited, this argument is an array of two-element arrays, with each two-element array specifying the conversion options for a particular column. The first element is the column number (1-based), and the second element is one of the xlColumnDataType  constants specifying how the column is parsed.
4800 
4801     rtl::OUString sDecimalSeparator;
4802     if( DecimalSeparator.hasValue() )
4803     {
4804         if( !( DecimalSeparator >>= sDecimalSeparator ) )
4805             throw uno::RuntimeException( rtl::OUString::createFromAscii( "DecimalSeparator parameter should be a String" ),
4806                 uno::Reference< uno::XInterface >() );
4807         OSL_TRACE("set DecimalSeparator\n" );
4808     }
4809     rtl::OUString sThousandsSeparator;
4810     if( ThousandsSeparator.hasValue() )
4811     {
4812         if( !( ThousandsSeparator >>= sThousandsSeparator ) )
4813             throw uno::RuntimeException( rtl::OUString::createFromAscii( "ThousandsSeparator parameter should be a String" ),
4814                 uno::Reference< uno::XInterface >() );
4815         OSL_TRACE("set ThousandsSpeparator\n" );
4816     }
4817  //TODO* TrailingMinusNumbers  Optional Variant. Numbers that begin with a minus character.
4818 }
4819 
4820 uno::Any SAL_CALL
4821 ScVbaRange::Hyperlinks( const uno::Any& aIndex ) throw (uno::RuntimeException)
4822 {
4823     /*  The range object always returns a new Hyperlinks object containing a
4824         fixed list of existing hyperlinks in the range.
4825         See vbahyperlinks.hxx for more details. */
4826 
4827     // get the global hyperlink object of the sheet (sheet should always be the parent of a Range object)
4828     uno::Reference< excel::XWorksheet > xWorksheet( getParent(), uno::UNO_QUERY_THROW );
4829     uno::Reference< excel::XHyperlinks > xSheetHlinks( xWorksheet->Hyperlinks( uno::Any() ), uno::UNO_QUERY_THROW );
4830     ScVbaHyperlinksRef xScSheetHlinks( dynamic_cast< ScVbaHyperlinks* >( xSheetHlinks.get() ) );
4831     if( !xScSheetHlinks.is() )
4832         throw uno::RuntimeException( ::rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "Cannot obtain hyperlinks implementation object" ) ), uno::Reference< uno::XInterface >() );
4833 
4834     // create a new local hyperlinks object based on the sheet hyperlinks
4835     ScVbaHyperlinksRef xHlinks( new ScVbaHyperlinks( getParent(), mxContext, xScSheetHlinks, getScRangeList() ) );
4836     if( aIndex.hasValue() )
4837         return xHlinks->Item( aIndex, uno::Any() );
4838     return uno::Any( uno::Reference< excel::XHyperlinks >( xHlinks.get() ) );
4839 }
4840 
4841 css::uno::Reference< excel::XValidation > SAL_CALL
4842 ScVbaRange::getValidation() throw (css::uno::RuntimeException)
4843 {
4844 	if ( !m_xValidation.is() )
4845 		m_xValidation = new ScVbaValidation( this, mxContext, mxRange );
4846 	return m_xValidation;
4847 }
4848 
4849 namespace {
4850 
4851 sal_Unicode lclGetPrefixChar( const uno::Reference< table::XCell >& rxCell ) throw (uno::RuntimeException)
4852 {
4853     /*  TODO/FIXME: We need an apostroph-prefix property at the cell to
4854         implement this correctly. For now, return an apostroph for every text
4855         cell.
4856 
4857         TODO/FIXME: When Application.TransitionNavigKeys is supported and true,
4858         this function needs to inspect the cell formatting and return different
4859         prefixes according to the horizontal cell alignment.
4860      */
4861     return (rxCell->getType() == table::CellContentType_TEXT) ? '\'' : 0;
4862 }
4863 
4864 sal_Unicode lclGetPrefixChar( const uno::Reference< table::XCellRange >& rxRange ) throw (uno::RuntimeException)
4865 {
4866     /*  This implementation is able to handle different prefixes (needed if
4867         Application.TransitionNavigKeys is true). The function lclGetPrefixChar
4868         for single cells called from here may return any prefix. If that
4869         function returns an empty prefix (NUL character) or different non-empty
4870         prefixes for two cells, this function returns 0.
4871      */
4872     sal_Unicode cCurrPrefix = 0;
4873     table::CellRangeAddress aRangeAddr = lclGetRangeAddress( rxRange );
4874     sal_Int32 nEndCol = aRangeAddr.EndColumn - aRangeAddr.StartColumn;
4875     sal_Int32 nEndRow = aRangeAddr.EndRow - aRangeAddr.StartRow;
4876     for( sal_Int32 nRow = 0; nRow <= nEndRow; ++nRow )
4877     {
4878         for( sal_Int32 nCol = 0; nCol <= nEndCol; ++nCol )
4879         {
4880             uno::Reference< table::XCell > xCell( rxRange->getCellByPosition( nCol, nRow ), uno::UNO_SET_THROW );
4881             sal_Unicode cNewPrefix = lclGetPrefixChar( xCell );
4882             if( (cNewPrefix == 0) || ((cCurrPrefix != 0) && (cNewPrefix != cCurrPrefix)) )
4883                 return 0;
4884             cCurrPrefix = cNewPrefix;
4885         }
4886     }
4887     // all cells contain the same prefix - return it
4888     return cCurrPrefix;
4889 }
4890 
4891 sal_Unicode lclGetPrefixChar( const uno::Reference< sheet::XSheetCellRangeContainer >& rxRanges ) throw (uno::RuntimeException)
4892 {
4893     sal_Unicode cCurrPrefix = 0;
4894     uno::Reference< container::XEnumerationAccess > xRangesEA( rxRanges, uno::UNO_QUERY_THROW );
4895     uno::Reference< container::XEnumeration > xRangesEnum( xRangesEA->createEnumeration(), uno::UNO_SET_THROW );
4896     while( xRangesEnum->hasMoreElements() )
4897     {
4898         uno::Reference< table::XCellRange > xRange( xRangesEnum->nextElement(), uno::UNO_QUERY_THROW );
4899         sal_Unicode cNewPrefix = lclGetPrefixChar( xRange );
4900         if( (cNewPrefix == 0) || ((cCurrPrefix != 0) && (cNewPrefix != cCurrPrefix)) )
4901             return 0;
4902         cCurrPrefix = cNewPrefix;
4903     }
4904     // all ranges contain the same prefix - return it
4905     return cCurrPrefix;
4906 }
4907 
4908 inline uno::Any lclGetPrefixVariant( sal_Unicode cPrefixChar )
4909 {
4910     return uno::Any( (cPrefixChar == 0) ? ::rtl::OUString() : ::rtl::OUString( cPrefixChar ) );
4911 }
4912 
4913 } // namespace
4914 
4915 uno::Any SAL_CALL ScVbaRange::getPrefixCharacter() throw (uno::RuntimeException)
4916 {
4917     /*  (1) If Application.TransitionNavigKeys is false, this function returns
4918         an apostroph character if the text cell begins with an apostroph
4919         character (formula return values are not taken into account); otherwise
4920         an empty string.
4921 
4922         (2) If Application.TransitionNavigKeys is true, this function returns
4923         an apostroph character, if the cell is left-aligned; a double-quote
4924         character, if the cell is right-aligned; a circumflex character, if the
4925         cell is centered; a backslash character, if the cell is set to filled;
4926         or an empty string, if nothing of the above.
4927 
4928         If a range or a list of ranges contains texts with leading apostroph
4929         character as well as other cells, this function returns an empty
4930         string.
4931      */
4932 
4933     if( mxRange.is() )
4934         return lclGetPrefixVariant( lclGetPrefixChar( mxRange ) );
4935     if( mxRanges.is() )
4936         return lclGetPrefixVariant( lclGetPrefixChar( mxRanges ) );
4937 	throw uno::RuntimeException( ::rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "Unexpected empty Range object" ) ), uno::Reference< uno::XInterface >() );
4938 }
4939 
4940 uno::Any ScVbaRange::getShowDetail() throw ( css::uno::RuntimeException)
4941 {
4942 	// #FIXME, If the specified range is in a PivotTable report
4943 
4944 	// In MSO VBA, the specified range must be a single summary column or row in an outline. otherwise throw exception
4945 	if( m_Areas->getCount() > 1 )
4946 		throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("Can not get Range.ShowDetail attribute ")), uno::Reference< uno::XInterface >() );
4947 
4948 	sal_Bool bShowDetail = sal_False;
4949 
4950 	RangeHelper helper( mxRange );
4951 	uno::Reference< sheet::XSheetCellCursor > xSheetCellCursor = helper.getSheetCellCursor();
4952 	xSheetCellCursor->collapseToCurrentRegion();
4953 	uno::Reference< sheet::XCellRangeAddressable > xCellRangeAddressable(xSheetCellCursor, uno::UNO_QUERY_THROW);
4954 	table::CellRangeAddress aOutlineAddress = xCellRangeAddressable->getRangeAddress();
4955 
4956 	// check if the specified range is a single summary column or row.
4957 	table::CellRangeAddress thisAddress = helper.getCellRangeAddressable()->getRangeAddress();
4958 	if( (thisAddress.StartRow == thisAddress.EndRow &&  thisAddress.EndRow == aOutlineAddress.EndRow ) ||
4959 		(thisAddress.StartColumn == thisAddress.EndColumn && thisAddress.EndColumn == aOutlineAddress.EndColumn ))
4960 	{
4961 		sal_Bool bColumn =thisAddress.StartRow == thisAddress.EndRow ? sal_False:sal_True;
4962 		ScDocument* pDoc = getDocumentFromRange( mxRange );
4963 		ScOutlineTable* pOutlineTable = pDoc->GetOutlineTable(static_cast<SCTAB>(thisAddress.Sheet), sal_True);
4964 		const ScOutlineArray* pOutlineArray =  bColumn ? pOutlineTable->GetColArray(): pOutlineTable->GetRowArray();
4965 		if( pOutlineArray )
4966 		{
4967 			SCCOLROW nPos = bColumn ? (SCCOLROW)(thisAddress.EndColumn-1):(SCCOLROW)(thisAddress.EndRow-1);
4968 			ScOutlineEntry* pEntry = pOutlineArray->GetEntryByPos( 0, nPos );
4969 			if( pEntry )
4970 			{
4971 				bShowDetail = !pEntry->IsHidden();
4972 				return uno::makeAny( bShowDetail );
4973 			}
4974 		}
4975 	}
4976 	else
4977 	{
4978 		throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("Can not set Range.ShowDetail attribute ")), uno::Reference< uno::XInterface >() );
4979 	}
4980     return aNULL();
4981 }
4982 
4983 void ScVbaRange::setShowDetail(const uno::Any& aShowDetail) throw ( css::uno::RuntimeException)
4984 {
4985 	// #FIXME, If the specified range is in a PivotTable report
4986 
4987 	// In MSO VBA, the specified range must be a single summary column or row in an outline. otherwise throw exception
4988 	if( m_Areas->getCount() > 1 )
4989 		throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("Can not set Range.ShowDetail attribute ")), uno::Reference< uno::XInterface >() );
4990 
4991 	bool bShowDetail = extractBoolFromAny( aShowDetail );
4992 
4993 	RangeHelper helper( mxRange );
4994 	uno::Reference< sheet::XSheetCellCursor > xSheetCellCursor = helper.getSheetCellCursor();
4995 	xSheetCellCursor->collapseToCurrentRegion();
4996 	uno::Reference< sheet::XCellRangeAddressable > xCellRangeAddressable(xSheetCellCursor, uno::UNO_QUERY_THROW);
4997 	table::CellRangeAddress aOutlineAddress = xCellRangeAddressable->getRangeAddress();
4998 
4999 	// check if the specified range is a single summary column or row.
5000 	table::CellRangeAddress thisAddress = helper.getCellRangeAddressable()->getRangeAddress();
5001 	if( (thisAddress.StartRow == thisAddress.EndRow &&  thisAddress.EndRow == aOutlineAddress.EndRow ) ||
5002 		(thisAddress.StartColumn == thisAddress.EndColumn && thisAddress.EndColumn == aOutlineAddress.EndColumn ))
5003 	{
5004 		// #FIXME, seems there is a different behavior between MSO and OOo.
5005 		//	In OOo, the showDetail will show all the level entrys, while only show the first level entry in MSO
5006 		uno::Reference< sheet::XSheetOutline > xSheetOutline( helper.getSpreadSheet(), uno::UNO_QUERY_THROW );
5007 		if( bShowDetail )
5008 			xSheetOutline->showDetail( aOutlineAddress );
5009 		else
5010 			xSheetOutline->hideDetail( aOutlineAddress );
5011 	}
5012 	else
5013 	{
5014 		throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("Can not set Range.ShowDetail attribute ")), uno::Reference< uno::XInterface >() );
5015 	}
5016 }
5017 
5018 uno::Reference< excel::XRange > SAL_CALL
5019 ScVbaRange::MergeArea() throw (script::BasicErrorException, uno::RuntimeException)
5020 {
5021     uno::Reference< sheet::XSheetCellRange > xMergeShellCellRange(mxRange->getCellRangeByPosition(0,0,0,0), uno::UNO_QUERY_THROW);
5022     uno::Reference< sheet::XSheetCellCursor > xMergeSheetCursor(xMergeShellCellRange->getSpreadsheet()->createCursorByRange( xMergeShellCellRange ), uno::UNO_QUERY_THROW);
5023     if( xMergeSheetCursor.is() )
5024     {
5025         xMergeSheetCursor->collapseToMergedArea();
5026         uno::Reference<sheet::XCellRangeAddressable> xMergeCellAddress(xMergeSheetCursor, uno::UNO_QUERY_THROW);
5027         if( xMergeCellAddress.is() )
5028         {
5029             table::CellRangeAddress aCellAddress = xMergeCellAddress->getRangeAddress();
5030             if( aCellAddress.StartColumn ==0 && aCellAddress.EndColumn==0 &&
5031                 aCellAddress.StartRow==0 && aCellAddress.EndRow==0)
5032             {
5033                 return new ScVbaRange( mxParent,mxContext,mxRange );
5034             }
5035             else
5036             {
5037                 ScRange refRange( static_cast< SCCOL >( aCellAddress.StartColumn ), static_cast< SCROW >( aCellAddress.StartRow ), static_cast< SCTAB >( aCellAddress.Sheet ),
5038                                   static_cast< SCCOL >( aCellAddress.EndColumn ), static_cast< SCROW >( aCellAddress.EndRow ), static_cast< SCTAB >( aCellAddress.Sheet ) );
5039                 uno::Reference< table::XCellRange > xRange( new ScCellRangeObj( getScDocShell() , refRange ) );
5040                 return new ScVbaRange( mxParent, mxContext,xRange );
5041             }
5042         }
5043     }
5044     return new ScVbaRange( mxParent, mxContext, mxRange );
5045 }
5046 
5047 void SAL_CALL
5048 ScVbaRange::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 ) throw (uno::RuntimeException)
5049 {
5050 	ScDocShell* pShell = NULL;
5051 
5052 	sal_Int32 nItems = m_Areas->getCount();
5053 	uno::Sequence< 	table::CellRangeAddress > printAreas( nItems );
5054 	uno::Reference< sheet::XPrintAreas > xPrintAreas;
5055 	for ( sal_Int32 index=1; index <= nItems; ++index )
5056 	{
5057 		uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny(index), uno::Any() ), uno::UNO_QUERY_THROW );
5058 
5059 		RangeHelper thisRange( xRange->getCellRange() );
5060 		table::CellRangeAddress rangeAddress = thisRange.getCellRangeAddressable()->getRangeAddress();
5061 		if ( index == 1 )
5062 		{
5063 			ScVbaRange* pRange = getImplementation( xRange );
5064 			// initialise the doc shell and the printareas
5065 			pShell = getDocShellFromRange( pRange->mxRange );
5066 			xPrintAreas.set( thisRange.getSpreadSheet(), uno::UNO_QUERY_THROW );
5067 		}
5068 		printAreas[ index - 1 ] = rangeAddress;
5069 	}
5070 	if ( pShell )
5071 	{
5072 		if ( xPrintAreas.is() )
5073 		{
5074 			xPrintAreas->setPrintAreas( printAreas );
5075 			uno::Reference< frame::XModel > xModel = pShell->GetModel();
5076 			PrintOutHelper( excel::getBestViewShell( xModel ), From, To, Copies, Preview, ActivePrinter, PrintToFile, Collate, PrToFileName, sal_True );
5077 		}
5078 	}
5079 }
5080 
5081 void SAL_CALL
5082 ScVbaRange::AutoFill(  const uno::Reference< excel::XRange >& Destination, const uno::Any& Type ) throw (uno::RuntimeException)
5083 {
5084 	uno::Reference< excel::XRange > xDest( Destination, uno::UNO_QUERY_THROW );
5085 	ScVbaRange* pRange = getImplementation( xDest );
5086 	RangeHelper destRangeHelper( pRange->mxRange );
5087 	table::CellRangeAddress destAddress = destRangeHelper.getCellRangeAddressable()->getRangeAddress();
5088 
5089 	RangeHelper thisRange( mxRange );
5090 	table::CellRangeAddress thisAddress = thisRange.getCellRangeAddressable()->getRangeAddress();
5091 	ScRange sourceRange;
5092 	ScRange destRange;
5093 
5094 	ScUnoConversion::FillScRange( destRange, destAddress );
5095 	ScUnoConversion::FillScRange( sourceRange, thisAddress );
5096 
5097 
5098 	// source is valid
5099 //	if (  !sourceRange.In( destRange ) )
5100 //		throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "source not in destination" ) ), uno::Reference< uno::XInterface >() );
5101 
5102 	FillDir eDir = FILL_TO_BOTTOM;
5103 	double fStep = 1.0;
5104 
5105 	ScRange aRange( destRange );
5106 	ScRange aSourceRange( destRange );
5107 
5108 	// default to include the number of Rows in the source range;
5109 	SCCOLROW nSourceCount = ( sourceRange.aEnd.Row() - sourceRange.aStart.Row() ) + 1;
5110 	SCCOLROW nCount = 0;
5111 
5112 	if ( sourceRange != destRange )
5113 	{
5114 		// Find direction of fill, vertical or horizontal
5115 		if ( sourceRange.aStart == destRange.aStart )
5116 		{
5117 			if ( sourceRange.aEnd.Row() == destRange.aEnd.Row() )
5118 			{
5119 				nSourceCount = ( sourceRange.aEnd.Col() - sourceRange.aStart.Col() + 1 );
5120 				aSourceRange.aEnd.SetCol( static_cast<SCCOL>( aSourceRange.aStart.Col() + nSourceCount - 1 ) );
5121 				eDir = FILL_TO_RIGHT;
5122 				nCount = aRange.aEnd.Col() - aSourceRange.aEnd.Col();
5123 			}
5124 			else if ( sourceRange.aEnd.Col() == destRange.aEnd.Col() )
5125 			{
5126 				aSourceRange.aEnd.SetRow( static_cast<SCROW>( aSourceRange.aStart.Row() + nSourceCount ) - 1 );
5127 				nCount = aRange.aEnd.Row() - aSourceRange.aEnd.Row();
5128 				eDir = FILL_TO_BOTTOM;
5129 			}
5130 		}
5131 
5132 		else if ( aSourceRange.aEnd == destRange.aEnd )
5133 		{
5134 			if ( sourceRange.aStart.Col() == destRange.aStart.Col() )
5135 			{
5136 				aSourceRange.aStart.SetRow( static_cast<SCROW>( aSourceRange.aEnd.Row() - nSourceCount + 1 ) );
5137 				nCount = aSourceRange.aStart.Row() - aRange.aStart.Row();
5138 				eDir = FILL_TO_TOP;
5139 				fStep = -fStep;
5140 			}
5141 			else if ( sourceRange.aStart.Row() == destRange.aStart.Row() )
5142 			{
5143 				nSourceCount = ( sourceRange.aEnd.Col() - sourceRange.aStart.Col() ) + 1;
5144 				aSourceRange.aStart.SetCol( static_cast<SCCOL>( aSourceRange.aEnd.Col() - nSourceCount + 1 ) );
5145 				nCount = aSourceRange.aStart.Col() - aRange.aStart.Col();
5146 				eDir = FILL_TO_LEFT;
5147 				fStep = -fStep;
5148 			}
5149 		}
5150 	}
5151 	ScDocShell* pDocSh= getDocShellFromRange( mxRange );
5152 
5153 	FillCmd eCmd = FILL_AUTO;
5154 	FillDateCmd eDateCmd = FILL_DAY;
5155 
5156 #ifdef VBA_OOBUILD_HACK
5157 	double fEndValue =  MAXDOUBLE;
5158 #endif
5159 
5160 	if ( Type.hasValue() )
5161 	{
5162 		sal_Int16 nFillType = excel::XlAutoFillType::xlFillDefault;
5163 		Type >>= nFillType;
5164 		switch ( nFillType )
5165 		{
5166 			case excel::XlAutoFillType::xlFillCopy:
5167 				eCmd = 	FILL_SIMPLE;
5168 				fStep = 0.0;
5169 				break;
5170 			case excel::XlAutoFillType::xlFillDays:
5171 				eCmd = FILL_DATE;
5172 				break;
5173 			case excel::XlAutoFillType::xlFillMonths:
5174 				eCmd = FILL_DATE;
5175 				eDateCmd = FILL_MONTH;
5176 				break;
5177 			case excel::XlAutoFillType::xlFillWeekdays:
5178 				eCmd = FILL_DATE;
5179 				eDateCmd = FILL_WEEKDAY;
5180 				break;
5181 			case excel::XlAutoFillType::xlFillYears:
5182 				eCmd = FILL_DATE;
5183 				eDateCmd = FILL_YEAR;
5184 				break;
5185 			case excel::XlAutoFillType::xlGrowthTrend:
5186 				eCmd = FILL_GROWTH;
5187 				break;
5188 			case excel::XlAutoFillType::xlFillFormats:
5189 				throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "xlFillFormat not supported for AutoFill" ) ), uno::Reference< uno::XInterface >() );
5190 			case excel::XlAutoFillType::xlFillValues:
5191 			case excel::XlAutoFillType::xlFillSeries:
5192 			case excel::XlAutoFillType::xlLinearTrend:
5193 				eCmd = FILL_LINEAR;
5194 				break;
5195 			case excel::XlAutoFillType::xlFillDefault:
5196 			default:
5197 				eCmd = 	FILL_AUTO;
5198 				break;
5199 		}
5200 	}
5201 	ScDocFunc aFunc(*pDocSh);
5202 #ifdef VBA_OOBUILD_HACK
5203 	aFunc.FillAuto( aSourceRange, NULL, eDir, eCmd, eDateCmd, nCount, fStep, fEndValue, sal_True, sal_True );
5204 #endif
5205 }
5206 sal_Bool SAL_CALL
5207 ScVbaRange::GoalSeek( const uno::Any& Goal, const uno::Reference< excel::XRange >& ChangingCell ) throw (uno::RuntimeException)
5208 {
5209 	ScDocShell* pDocShell = getScDocShell();
5210 	sal_Bool bRes = sal_True;
5211 	ScVbaRange* pRange = static_cast< ScVbaRange* >( ChangingCell.get() );
5212 	if ( pDocShell && pRange )
5213 	{
5214 		uno::Reference< sheet::XGoalSeek > xGoalSeek(  pDocShell->GetModel(), uno::UNO_QUERY_THROW );
5215 		RangeHelper thisRange( mxRange );
5216 		table::CellRangeAddress thisAddress = thisRange.getCellRangeAddressable()->getRangeAddress();
5217 		RangeHelper changingCellRange( pRange->mxRange );
5218 		table::CellRangeAddress changingCellAddr = changingCellRange.getCellRangeAddressable()->getRangeAddress();
5219 		rtl::OUString sGoal = getAnyAsString( Goal );
5220 		table::CellAddress thisCell( thisAddress.Sheet, thisAddress.StartColumn, thisAddress.StartRow );
5221 		table::CellAddress changingCell( changingCellAddr.Sheet, changingCellAddr.StartColumn, changingCellAddr.StartRow );
5222 		sheet::GoalResult res = xGoalSeek->seekGoal( thisCell, changingCell, sGoal );
5223 		ChangingCell->setValue( uno::makeAny( res.Result ) );
5224 
5225 		// openoffice behaves differently, result is 0 if the divergence is too great
5226                 // but... if it detects 0 is the value it requires then it will use that
5227 		// e.g. divergence & result both = 0.0 does NOT mean there is an error
5228 		if ( ( res.Divergence != 0.0 ) && ( res.Result == 0.0 ) )
5229 			bRes = sal_False;
5230 	}
5231 	else
5232 		bRes = sal_False;
5233 	return bRes;
5234 }
5235 
5236 void
5237 ScVbaRange::Calculate(  ) throw (script::BasicErrorException, uno::RuntimeException)
5238 {
5239 	getWorksheet()->Calculate();
5240 }
5241 
5242 uno::Reference< excel::XRange > SAL_CALL
5243 ScVbaRange::Item( const uno::Any& row, const uno::Any& column ) throw (script::BasicErrorException, uno::RuntimeException)
5244 {
5245 	if ( mbIsRows || mbIsColumns )
5246 	{
5247 		if ( column.hasValue() )
5248 			DebugHelper::exception(SbERR_BAD_PARAMETER, rtl::OUString() );
5249 		uno::Reference< excel::XRange > xRange;
5250 		if ( mbIsColumns )
5251 			xRange = Columns( row );
5252 		else
5253 			xRange = Rows( row );
5254 		return xRange;
5255 	}
5256 	return Cells( row, column );
5257 }
5258 
5259 void
5260 ScVbaRange::AutoOutline(  ) throw (script::BasicErrorException, uno::RuntimeException)
5261 {
5262 	// #TODO #FIXME needs to check for summary row/col ( whatever they are )
5263 	// not valid for multi Area Addresses
5264 	if ( m_Areas->getCount() > 1 )
5265 		DebugHelper::exception(SbERR_METHOD_FAILED, STR_ERRORMESSAGE_APPLIESTOSINGLERANGEONLY);
5266 	// So needs to either span an entire Row or a just be a single cell
5267 	// ( that contains a summary RowColumn )
5268 	// also the Single cell cause doesn't seem to be handled specially in
5269 	// this code ( ported from the helperapi RangeImpl.java,
5270 	// RangeRowsImpl.java, RangesImpl.java, RangeSingleCellImpl.java
5271 	RangeHelper thisRange( mxRange );
5272 	table::CellRangeAddress thisAddress = thisRange.getCellRangeAddressable()->getRangeAddress();
5273 
5274 	if ( isSingleCellRange() || mbIsRows )
5275 	{
5276 		uno::Reference< sheet::XSheetOutline > xSheetOutline( thisRange.getSpreadSheet(), uno::UNO_QUERY_THROW );
5277        		 xSheetOutline->autoOutline( thisAddress );
5278 	}
5279 	else
5280 		DebugHelper::exception(SbERR_METHOD_FAILED, rtl::OUString());
5281 }
5282 
5283 void SAL_CALL
5284 ScVbaRange:: ClearOutline(  ) throw (script::BasicErrorException, uno::RuntimeException)
5285 {
5286 	if ( m_Areas->getCount() > 1 )
5287 	{
5288 		sal_Int32 nItems = m_Areas->getCount();
5289 		for ( sal_Int32 index=1; index <= nItems; ++index )
5290 		{
5291 			uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny(index), uno::Any() ), uno::UNO_QUERY_THROW );
5292 			xRange->ClearOutline();
5293 		}
5294 		return;
5295 	}
5296 	RangeHelper thisRange( mxRange );
5297 	table::CellRangeAddress thisAddress = thisRange.getCellRangeAddressable()->getRangeAddress();
5298 	uno::Reference< sheet::XSheetOutline > xSheetOutline( thisRange.getSpreadSheet(), uno::UNO_QUERY_THROW );
5299         xSheetOutline->clearOutline();
5300 }
5301 
5302 void
5303 ScVbaRange::groupUnGroup( bool bUnGroup ) throw ( script::BasicErrorException, uno::RuntimeException )
5304 {
5305 	if ( m_Areas->getCount() > 1 )
5306 		 DebugHelper::exception(SbERR_METHOD_FAILED, STR_ERRORMESSAGE_APPLIESTOSINGLERANGEONLY);
5307 	table::TableOrientation nOrient = table::TableOrientation_ROWS;
5308 	if ( mbIsColumns )
5309 		nOrient = table::TableOrientation_COLUMNS;
5310 	RangeHelper thisRange( mxRange );
5311 	table::CellRangeAddress thisAddress = thisRange.getCellRangeAddressable()->getRangeAddress();
5312 	uno::Reference< sheet::XSheetOutline > xSheetOutline( thisRange.getSpreadSheet(), uno::UNO_QUERY_THROW );
5313 	if ( bUnGroup )
5314 	        xSheetOutline->ungroup( thisAddress, nOrient );
5315 	else
5316 	        xSheetOutline->group( thisAddress, nOrient );
5317 }
5318 
5319 void SAL_CALL
5320 ScVbaRange::Group(  ) throw (script::BasicErrorException, uno::RuntimeException)
5321 {
5322 	groupUnGroup();
5323 }
5324 void SAL_CALL
5325 ScVbaRange::Ungroup(  ) throw (script::BasicErrorException, uno::RuntimeException)
5326 {
5327 	groupUnGroup(true);
5328 }
5329 
5330 void lcl_mergeCellsOfRange( const uno::Reference< table::XCellRange >& xCellRange, sal_Bool _bMerge = sal_True ) throw ( uno::RuntimeException )
5331 {
5332         uno::Reference< util::XMergeable > xMergeable( xCellRange, uno::UNO_QUERY_THROW );
5333         xMergeable->merge(_bMerge);
5334 }
5335 void SAL_CALL
5336 ScVbaRange::Merge( const uno::Any& Across ) throw (script::BasicErrorException, uno::RuntimeException)
5337 {
5338 	if ( m_Areas->getCount() > 1 )
5339 	{
5340 		sal_Int32 nItems = m_Areas->getCount();
5341 		for ( sal_Int32 index=1; index <= nItems; ++index )
5342 		{
5343 			uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny(index), uno::Any() ), uno::UNO_QUERY_THROW );
5344 			xRange->Merge(Across);
5345 		}
5346 		return;
5347 	}
5348 	uno::Reference< table::XCellRange > oCellRange;
5349 	sal_Bool bAcross = sal_False;
5350 	Across >>= bAcross;
5351 	if ( !bAcross )
5352 		lcl_mergeCellsOfRange( mxRange );
5353 	else
5354 	{
5355 		uno::Reference< excel::XRange > oRangeRowsImpl = Rows( uno::Any() );
5356 		// #TODO #FIXME this seems incredibly lame, this can't be right
5357 		for (sal_Int32 i=1; i <= oRangeRowsImpl->getCount();i++)
5358 		{
5359                		oRangeRowsImpl->Cells( uno::makeAny( i ), uno::Any() )->Merge( uno::makeAny( sal_False ) );
5360            	}
5361 	}
5362 }
5363 
5364 void SAL_CALL
5365 ScVbaRange::UnMerge(  ) throw (script::BasicErrorException, uno::RuntimeException)
5366 {
5367 	if ( m_Areas->getCount() > 1 )
5368 	{
5369 		sal_Int32 nItems = m_Areas->getCount();
5370 		for ( sal_Int32 index=1; index <= nItems; ++index )
5371 		{
5372 			uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny(index), uno::Any() ), uno::UNO_QUERY_THROW );
5373 			xRange->UnMerge();
5374 		}
5375 		return;
5376 	}
5377 	lcl_mergeCellsOfRange( mxRange, sal_False);
5378 }
5379 
5380 uno::Any SAL_CALL
5381 ScVbaRange::getStyle() throw (uno::RuntimeException)
5382 {
5383 	if ( m_Areas->getCount() > 1 )
5384 	{
5385 		uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny( sal_Int32( 1 ) ), uno::Any() ), uno::UNO_QUERY_THROW  );
5386 		return xRange->getStyle();
5387 	}
5388 	uno::Reference< beans::XPropertySet > xProps( mxRange, uno::UNO_QUERY_THROW );
5389 	rtl::OUString sStyleName;
5390     xProps->getPropertyValue(CELLSTYLE) >>= sStyleName;
5391 	ScDocShell* pShell = getScDocShell();
5392 	uno::Reference< frame::XModel > xModel( pShell->GetModel() );
5393 	uno::Reference< excel::XStyle > xStyle = new ScVbaStyle( this, mxContext,  sStyleName, xModel );
5394 	return uno::makeAny( xStyle );
5395 }
5396 void SAL_CALL
5397 ScVbaRange::setStyle( const uno::Any& _style ) throw (uno::RuntimeException)
5398 {
5399 	if ( m_Areas->getCount() > 1 )
5400 	{
5401 		uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny( sal_Int32( 1 ) ), uno::Any() ), uno::UNO_QUERY_THROW );
5402 		xRange->setStyle( _style );
5403 		return;
5404 	}
5405 	uno::Reference< beans::XPropertySet > xProps( mxRange, uno::UNO_QUERY_THROW );
5406 	uno::Reference< excel::XStyle > xStyle;
5407 	_style >>= xStyle;
5408 	xProps->setPropertyValue(CELLSTYLE, uno::makeAny(xStyle->getName()));
5409 }
5410 
5411 uno::Reference< excel::XRange >
5412 ScVbaRange::PreviousNext( bool bIsPrevious )
5413 {
5414 	ScMarkData markedRange;
5415 	ScRange refRange;
5416 	RangeHelper thisRange( mxRange );
5417 
5418 	ScUnoConversion::FillScRange( refRange, thisRange.getCellRangeAddressable()->getRangeAddress());
5419 	markedRange. SetMarkArea( refRange );
5420 	short nMove = bIsPrevious ? -1 : 1;
5421 
5422 	SCCOL nNewX = refRange.aStart.Col();
5423 	SCROW nNewY = refRange.aStart.Row();
5424 	SCTAB nTab = refRange.aStart.Tab();
5425 
5426 	ScDocument* pDoc = getScDocument();
5427 	pDoc->GetNextPos( nNewX,nNewY, nTab, nMove,0, sal_True,sal_True, markedRange );
5428 	refRange.aStart.SetCol( nNewX );
5429 	refRange.aStart.SetRow( nNewY );
5430 	refRange.aStart.SetTab( nTab );
5431 	refRange.aEnd.SetCol( nNewX );
5432 	refRange.aEnd.SetRow( nNewY );
5433 	refRange.aEnd.SetTab( nTab );
5434 
5435 	uno::Reference< table::XCellRange > xRange( new ScCellRangeObj( getScDocShell() , refRange ) );
5436 
5437 	return new ScVbaRange( mxParent, mxContext, xRange );
5438 }
5439 
5440 uno::Reference< excel::XRange > SAL_CALL
5441 ScVbaRange::Next() throw (script::BasicErrorException, uno::RuntimeException)
5442 {
5443 	if ( m_Areas->getCount() > 1 )
5444 	{
5445 		uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny( sal_Int32( 1 ) ), uno::Any() ) , uno::UNO_QUERY_THROW  );
5446 		return xRange->Next();
5447 	}
5448 	return PreviousNext( false );
5449 }
5450 
5451 uno::Reference< excel::XRange > SAL_CALL
5452 ScVbaRange::Previous() throw (script::BasicErrorException, uno::RuntimeException)
5453 {
5454 	if ( m_Areas->getCount() > 1 )
5455 	{
5456 		uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny( sal_Int32( 1 ) ), uno::Any() ), uno::UNO_QUERY_THROW  );
5457 		return xRange->Previous();
5458 	}
5459 	return PreviousNext( true );
5460 }
5461 
5462 uno::Reference< excel::XRange > SAL_CALL
5463 ScVbaRange::SpecialCells( const uno::Any& _oType, const uno::Any& _oValue) throw ( script::BasicErrorException )
5464 {
5465 	bool bIsSingleCell = isSingleCellRange();
5466 	bool bIsMultiArea = ( m_Areas->getCount() > 1 );
5467 	ScVbaRange* pRangeToUse = this;
5468 	sal_Int32 nType = 0;
5469 	if ( !( _oType >>= nType ) )
5470 		DebugHelper::exception(SbERR_BAD_PARAMETER, rtl::OUString() );
5471 	switch(nType)
5472 	{
5473 		case excel::XlCellType::xlCellTypeSameFormatConditions:
5474 		case excel::XlCellType::xlCellTypeAllValidation:
5475 		case excel::XlCellType::xlCellTypeSameValidation:
5476 			DebugHelper::exception(SbERR_NOT_IMPLEMENTED, rtl::OUString());
5477 			break;
5478 		case excel::XlCellType::xlCellTypeBlanks:
5479 		case excel::XlCellType::xlCellTypeComments:
5480 		case excel::XlCellType::xlCellTypeConstants:
5481 		case excel::XlCellType::xlCellTypeFormulas:
5482 		case excel::XlCellType::xlCellTypeVisible:
5483 		case excel::XlCellType::xlCellTypeLastCell:
5484 		{
5485 			if ( bIsMultiArea )
5486 			{
5487 				// need to process each area, gather the results and
5488 				// create a new range from those
5489 				std::vector< table::CellRangeAddress > rangeResults;
5490 				sal_Int32 nItems = ( m_Areas->getCount() + 1 );
5491 				for ( sal_Int32 index=1; index <= nItems; ++index )
5492 				{
5493 					uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny(index), uno::Any() ), uno::UNO_QUERY_THROW );
5494 					xRange = xRange->SpecialCells( _oType,  _oValue);
5495 					ScVbaRange* pRange = getImplementation( xRange );
5496 					if ( xRange.is() && pRange )
5497 					{
5498 						sal_Int32 nElems = ( pRange->m_Areas->getCount() + 1 );
5499 						for ( sal_Int32 nArea = 1; nArea < nElems; ++nArea )
5500 						{
5501 							uno::Reference< excel::XRange > xTmpRange( m_Areas->Item( uno::makeAny( nArea ), uno::Any() ), uno::UNO_QUERY_THROW );
5502 							RangeHelper rHelper( xTmpRange->getCellRange() );
5503 							rangeResults.push_back( rHelper.getCellRangeAddressable()->getRangeAddress() );
5504 						}
5505 					}
5506 				}
5507 				ScRangeList aCellRanges;
5508 				std::vector< table::CellRangeAddress >::iterator it = rangeResults.begin();
5509 				std::vector< table::CellRangeAddress >::iterator it_end = rangeResults.end();
5510 				for ( ; it != it_end; ++ it )
5511 				{
5512 					ScRange refRange;
5513 					ScUnoConversion::FillScRange( refRange, *it );
5514 					aCellRanges.Append( refRange );
5515 				}
5516 				// Single range
5517 				if ( aCellRanges.First() == aCellRanges.Last() )
5518 				{
5519 					uno::Reference< table::XCellRange > xRange( new ScCellRangeObj( getScDocShell(), *aCellRanges.First() ) );
5520 					return new ScVbaRange( mxParent, mxContext, xRange );
5521 				}
5522 				uno::Reference< sheet::XSheetCellRangeContainer > xRanges( new ScCellRangesObj( getScDocShell(), aCellRanges ) );
5523 
5524 				return new ScVbaRange( mxParent, mxContext, xRanges );
5525 			}
5526 			else if ( bIsSingleCell )
5527 			{
5528 				uno::Reference< excel::XRange > xUsedRange = getWorksheet()->getUsedRange();
5529 				pRangeToUse = static_cast< ScVbaRange* >( xUsedRange.get() );
5530 			}
5531 
5532 			break;
5533 		}
5534 		default:
5535 		DebugHelper::exception(SbERR_BAD_PARAMETER, rtl::OUString() );
5536 			break;
5537 	}
5538 	if ( !pRangeToUse )
5539 		DebugHelper::exception(SbERR_METHOD_FAILED, rtl::OUString() );
5540 	return pRangeToUse->SpecialCellsImpl( nType, _oValue );
5541 }
5542 
5543 sal_Int32 lcl_getFormulaResultFlags(const uno::Any& aType) throw ( script::BasicErrorException )
5544 {
5545 	sal_Int32 nType = excel::XlSpecialCellsValue::xlNumbers;
5546 	aType >>= nType;
5547 	sal_Int32 nRes = sheet::FormulaResult::VALUE;
5548 
5549 	switch(nType)
5550 	{
5551 		case excel::XlSpecialCellsValue::xlErrors:
5552 			nRes= sheet::FormulaResult::ERROR;
5553 			break;
5554 		case excel::XlSpecialCellsValue::xlLogical:
5555 			//TODO bc93774: ask NN if this is really an appropriate substitute
5556 			nRes = sheet::FormulaResult::VALUE;
5557 			break;
5558 		case excel::XlSpecialCellsValue::xlNumbers:
5559 			nRes = sheet::FormulaResult::VALUE;
5560 			break;
5561 		case excel::XlSpecialCellsValue::xlTextValues:
5562 			nRes = sheet::FormulaResult::STRING;
5563 			break;
5564 		default:
5565 			DebugHelper::exception(SbERR_BAD_PARAMETER, rtl::OUString() );
5566 	}
5567 	return nRes;
5568 }
5569 
5570 uno::Reference< excel::XRange >
5571 ScVbaRange::SpecialCellsImpl( sal_Int32 nType, const uno::Any& _oValue) throw ( script::BasicErrorException )
5572 {
5573 	uno::Reference< excel::XRange > xRange;
5574 	try
5575 	{
5576 		uno::Reference< sheet::XCellRangesQuery > xQuery( mxRange, uno::UNO_QUERY_THROW );
5577 		uno::Reference< excel::XRange > oLocRangeImpl;
5578 		uno::Reference< sheet::XSheetCellRanges > xLocSheetCellRanges;
5579 		switch(nType)
5580 		{
5581 			case excel::XlCellType::xlCellTypeAllFormatConditions:
5582 			case excel::XlCellType::xlCellTypeSameFormatConditions:
5583 			case excel::XlCellType::xlCellTypeAllValidation:
5584 			case excel::XlCellType::xlCellTypeSameValidation:
5585 				// Shouldn't get here ( should be filtered out by
5586 				// ScVbaRange::SpecialCells()
5587 				DebugHelper::exception(SbERR_NOT_IMPLEMENTED, rtl::OUString());
5588 				break;
5589 			case excel::XlCellType::xlCellTypeBlanks:
5590 				xLocSheetCellRanges = xQuery->queryEmptyCells();
5591 				break;
5592 			case excel::XlCellType::xlCellTypeComments:
5593 				xLocSheetCellRanges = xQuery->queryContentCells(sheet::CellFlags::ANNOTATION);
5594 				break;
5595 			case excel::XlCellType::xlCellTypeConstants:
5596 				xLocSheetCellRanges = xQuery->queryContentCells(23);
5597 				break;
5598 			case excel::XlCellType::xlCellTypeFormulas:
5599 			{
5600 				sal_Int32 nFormulaResult = lcl_getFormulaResultFlags(_oValue);
5601 				xLocSheetCellRanges = xQuery->queryFormulaCells(nFormulaResult);
5602 				break;
5603 			}
5604 			case excel::XlCellType::xlCellTypeLastCell:
5605 				xRange = Cells( uno::makeAny( getCount() ), uno::Any() );
5606 			case excel::XlCellType::xlCellTypeVisible:
5607 				xLocSheetCellRanges = xQuery->queryVisibleCells();
5608 				break;
5609 			default:
5610 				DebugHelper::exception(SbERR_BAD_PARAMETER, rtl::OUString() );
5611 				break;
5612 		}
5613 		if (xLocSheetCellRanges.is())
5614 		{
5615 			xRange = lcl_makeXRangeFromSheetCellRanges( getParent(), mxContext, xLocSheetCellRanges, getScDocShell() );
5616 		}
5617 	}
5618 	catch (uno::Exception& )
5619 	{
5620 		DebugHelper::exception(SbERR_METHOD_FAILED, STR_ERRORMESSAGE_NOCELLSWEREFOUND);
5621 	}
5622 	return xRange;
5623 }
5624 
5625 void SAL_CALL
5626 ScVbaRange::RemoveSubtotal(  ) throw (script::BasicErrorException, uno::RuntimeException)
5627 {
5628 	uno::Reference< sheet::XSubTotalCalculatable > xSub( mxRange, uno::UNO_QUERY_THROW );
5629 	xSub->removeSubTotals();
5630 }
5631 
5632 void SAL_CALL
5633 ScVbaRange::Subtotal( ::sal_Int32 _nGroupBy, ::sal_Int32 _nFunction, const uno::Sequence< ::sal_Int32 >& _nTotalList, const uno::Any& aReplace, const uno::Any& PageBreaks, const uno::Any& /*SummaryBelowData*/ ) throw (script::BasicErrorException, uno::RuntimeException)
5634 {
5635 	try
5636 	{
5637 		sal_Bool bDoReplace = sal_False;
5638 		aReplace >>= bDoReplace;
5639 		sal_Bool bAddPageBreaks = sal_False;
5640 		PageBreaks >>= bAddPageBreaks;
5641 
5642 		uno::Reference< sheet::XSubTotalCalculatable> xSub(mxRange, uno::UNO_QUERY_THROW );
5643 		uno::Reference< sheet::XSubTotalDescriptor > xSubDesc = xSub->createSubTotalDescriptor(sal_True);
5644 		uno::Reference< beans::XPropertySet > xSubDescPropertySet( xSubDesc, uno::UNO_QUERY_THROW );
5645 		xSubDescPropertySet->setPropertyValue(INSERTPAGEBREAKS, uno::makeAny( bAddPageBreaks));
5646 		sal_Int32 nLen = _nTotalList.getLength();
5647 		uno::Sequence< sheet::SubTotalColumn > aColumns( nLen );
5648 		for (int i = 0; i < nLen; i++)
5649 		{
5650 			aColumns[i].Column = _nTotalList[i] - 1;
5651 			switch (_nFunction)
5652 			{
5653 				case excel::XlConsolidationFunction::xlAverage:
5654 					aColumns[i].Function = sheet::GeneralFunction_AVERAGE;
5655 					break;
5656 				case excel::XlConsolidationFunction::xlCount:
5657 					aColumns[i].Function = sheet::GeneralFunction_COUNT;
5658 					break;
5659 				case excel::XlConsolidationFunction::xlCountNums:
5660 					aColumns[i].Function = sheet::GeneralFunction_COUNTNUMS;
5661 					break;
5662 				case excel::XlConsolidationFunction::xlMax:
5663 					aColumns[i].Function = sheet::GeneralFunction_MAX;
5664 					break;
5665 				case excel::XlConsolidationFunction::xlMin:
5666 					aColumns[i].Function = sheet::GeneralFunction_MIN;
5667 					break;
5668 				case excel::XlConsolidationFunction::xlProduct:
5669 					aColumns[i].Function = sheet::GeneralFunction_PRODUCT;
5670 					break;
5671 				case excel::XlConsolidationFunction::xlStDev:
5672 					aColumns[i].Function = sheet::GeneralFunction_STDEV;
5673 					break;
5674 				case excel::XlConsolidationFunction::xlStDevP:
5675 					aColumns[i].Function = sheet::GeneralFunction_STDEVP;
5676 					break;
5677 				case excel::XlConsolidationFunction::xlSum:
5678 					aColumns[i].Function = sheet::GeneralFunction_SUM;
5679 					break;
5680 				case excel::XlConsolidationFunction::xlUnknown:
5681 					aColumns[i].Function = sheet::GeneralFunction_NONE;
5682 					break;
5683 				case excel::XlConsolidationFunction::xlVar:
5684 					aColumns[i].Function = sheet::GeneralFunction_VAR;
5685 					break;
5686 				case excel::XlConsolidationFunction::xlVarP:
5687 					aColumns[i].Function = sheet::GeneralFunction_VARP;
5688 					break;
5689 				default:
5690 					DebugHelper::exception(SbERR_BAD_PARAMETER, rtl::OUString()) ;
5691 					return;
5692 			}
5693 		}
5694 		xSubDesc->addNew(aColumns, _nGroupBy - 1);
5695 		xSub->applySubTotals(xSubDesc, bDoReplace);
5696 	}
5697 	catch (uno::Exception& )
5698 	{
5699 		DebugHelper::exception(SbERR_METHOD_FAILED, rtl::OUString());
5700 	}
5701 }
5702 
5703 rtl::OUString&
5704 ScVbaRange::getServiceImplName()
5705 {
5706 	static rtl::OUString sImplName( RTL_CONSTASCII_USTRINGPARAM("ScVbaRange") );
5707 	return sImplName;
5708 }
5709 
5710 uno::Sequence< rtl::OUString >
5711 ScVbaRange::getServiceNames()
5712 {
5713 	static uno::Sequence< rtl::OUString > aServiceNames;
5714 	if ( aServiceNames.getLength() == 0 )
5715 	{
5716 		aServiceNames.realloc( 1 );
5717 		aServiceNames[ 0 ] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.excel.Range" ) );
5718 	}
5719 	return aServiceNames;
5720 }
5721 
5722 namespace range
5723 {
5724 namespace sdecl = comphelper::service_decl;
5725 sdecl::vba_service_class_<ScVbaRange, sdecl::with_args<true> > serviceImpl;
5726 extern sdecl::ServiceDecl const serviceDecl(
5727     serviceImpl,
5728     "SvVbaRange",
5729     "ooo.vba.excel.Range" );
5730 }
5731