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