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