bump product version to 4.1.6.2
[LibreOffice.git] / sc / source / ui / vba / vbarange.cxx
bloba2470f125552aec9addb548fdacb7c3a96cecbbb
1 /* -*- Mode: C++; tab-width: 4; indent-tabs-mode: nil; c-basic-offset: 4 -*- */
2 /*
3 * This file is part of the LibreOffice project.
5 * This Source Code Form is subject to the terms of the Mozilla Public
6 * License, v. 2.0. If a copy of the MPL was not distributed with this
7 * file, You can obtain one at http://mozilla.org/MPL/2.0/.
9 * This file incorporates work covered by the following license notice:
11 * Licensed to the Apache Software Foundation (ASF) under one or more
12 * contributor license agreements. See the NOTICE file distributed
13 * with this work for additional information regarding copyright
14 * ownership. The ASF licenses this file to you under the Apache
15 * License, Version 2.0 (the "License"); you may not use this file
16 * except in compliance with the License. You may obtain a copy of
17 * the License at http://www.apache.org/licenses/LICENSE-2.0 .
20 #include "vbarange.hxx"
22 #include <vbahelper/helperdecl.hxx>
24 #include <comphelper/unwrapargs.hxx>
25 #include <comphelper/processfactory.hxx>
26 #include <sfx2/objsh.hxx>
28 #include <com/sun/star/script/ArrayWrapper.hpp>
29 #include <com/sun/star/script/vba/VBAEventId.hpp>
30 #include <com/sun/star/script/vba/XVBAEventProcessor.hpp>
31 #include <com/sun/star/sheet/XDatabaseRange.hpp>
32 #include <com/sun/star/sheet/XUnnamedDatabaseRanges.hpp>
33 #include <com/sun/star/sheet/XGoalSeek.hpp>
34 #include <com/sun/star/sheet/XSheetOperation.hpp>
35 #include <com/sun/star/sheet/CellFlags.hpp>
36 #include <com/sun/star/table/XColumnRowRange.hpp>
37 #include <com/sun/star/sheet/XCellAddressable.hpp>
38 #include <com/sun/star/table/CellContentType.hpp>
39 #include <com/sun/star/sheet/XCellSeries.hpp>
40 #include <com/sun/star/text/XTextRange.hpp>
41 #include <com/sun/star/sheet/XCellRangeAddressable.hpp>
42 #include <com/sun/star/table/CellAddress.hpp>
43 #include <com/sun/star/table/CellRangeAddress.hpp>
44 #include <com/sun/star/sheet/XSpreadsheetView.hpp>
45 #include <com/sun/star/sheet/XCellRangeReferrer.hpp>
46 #include <com/sun/star/sheet/XSheetCellRange.hpp>
47 #include <com/sun/star/sheet/XSpreadsheet.hpp>
48 #include <com/sun/star/sheet/XSheetCellCursor.hpp>
49 #include <com/sun/star/sheet/XArrayFormulaRange.hpp>
50 #include <com/sun/star/sheet/XNamedRange.hpp>
51 #include <com/sun/star/sheet/XPrintAreas.hpp>
52 #include <com/sun/star/sheet/XCellRangesQuery.hpp>
53 #include <com/sun/star/beans/XPropertySet.hpp>
54 #include <com/sun/star/sheet/XFunctionAccess.hpp>
55 #include <com/sun/star/frame/XModel.hpp>
56 #include <com/sun/star/view/XSelectionSupplier.hpp>
57 #include <com/sun/star/table/XCellCursor.hpp>
58 #include <com/sun/star/table/XTableRows.hpp>
59 #include <com/sun/star/table/XTableColumns.hpp>
60 #include <com/sun/star/table/TableSortField.hpp>
61 #include <com/sun/star/util/XMergeable.hpp>
62 #include <com/sun/star/uno/XComponentContext.hpp>
63 #include <com/sun/star/lang/XMultiComponentFactory.hpp>
64 #include <com/sun/star/sheet/XSpreadsheetDocument.hpp>
65 #include <com/sun/star/util/XNumberFormatsSupplier.hpp>
66 #include <com/sun/star/util/XNumberFormats.hpp>
67 #include <com/sun/star/util/NumberFormat.hpp>
68 #include <com/sun/star/util/XNumberFormatTypes.hpp>
69 #include <com/sun/star/util/XReplaceable.hpp>
70 #include <com/sun/star/util/XSortable.hpp>
71 #include <com/sun/star/sheet/XCellRangeMovement.hpp>
72 #include <com/sun/star/sheet/XCellRangeData.hpp>
73 #include <com/sun/star/sheet/FormulaResult.hpp>
74 #include <com/sun/star/sheet/FilterOperator2.hpp>
75 #include <com/sun/star/sheet/TableFilterField.hpp>
76 #include <com/sun/star/sheet/TableFilterField2.hpp>
77 #include <com/sun/star/sheet/XSheetFilterDescriptor2.hpp>
78 #include <com/sun/star/sheet/XSheetFilterable.hpp>
79 #include <com/sun/star/sheet/FilterConnection.hpp>
80 #include <com/sun/star/util/CellProtection.hpp>
81 #include <com/sun/star/util/TriState.hpp>
83 #include <com/sun/star/style/XStyleFamiliesSupplier.hpp>
84 #include <com/sun/star/awt/XDevice.hpp>
86 #include <com/sun/star/sheet/XSubTotalCalculatable.hpp>
87 #include <com/sun/star/sheet/XSubTotalDescriptor.hpp>
88 #include <com/sun/star/sheet/GeneralFunction.hpp>
90 #include <com/sun/star/sheet/XSheetAnnotationsSupplier.hpp>
91 #include <com/sun/star/sheet/XSheetAnnotations.hpp>
93 #include <ooo/vba/excel/XlPasteSpecialOperation.hpp>
94 #include <ooo/vba/excel/XlPasteType.hpp>
95 #include <ooo/vba/excel/Constants.hpp>
96 #include <ooo/vba/excel/XlFindLookIn.hpp>
97 #include <ooo/vba/excel/XlLookAt.hpp>
98 #include <ooo/vba/excel/XlSearchOrder.hpp>
99 #include <ooo/vba/excel/XlSortOrder.hpp>
100 #include <ooo/vba/excel/XlYesNoGuess.hpp>
101 #include <ooo/vba/excel/XlSortOrientation.hpp>
102 #include <ooo/vba/excel/XlSortMethod.hpp>
103 #include <ooo/vba/excel/XlDirection.hpp>
104 #include <ooo/vba/excel/XlSortDataOption.hpp>
105 #include <ooo/vba/excel/XlDeleteShiftDirection.hpp>
106 #include <ooo/vba/excel/XlInsertShiftDirection.hpp>
107 #include <ooo/vba/excel/XlReferenceStyle.hpp>
108 #include <ooo/vba/excel/XlBordersIndex.hpp>
109 #include <ooo/vba/excel/XlPageBreak.hpp>
110 #include <ooo/vba/excel/XlAutoFilterOperator.hpp>
111 #include <ooo/vba/excel/XlAutoFillType.hpp>
112 #include <ooo/vba/excel/XlTextParsingType.hpp>
113 #include <ooo/vba/excel/XlTextQualifier.hpp>
114 #include <ooo/vba/excel/XlCellType.hpp>
115 #include <ooo/vba/excel/XlSpecialCellsValue.hpp>
116 #include <ooo/vba/excel/XlConsolidationFunction.hpp>
117 #include <ooo/vba/excel/XlSearchDirection.hpp>
119 #include <scitems.hxx>
120 #include <svl/srchitem.hxx>
121 #include <cellsuno.hxx>
122 #include <dbdata.hxx>
123 #include "docfunc.hxx"
124 #include <docuno.hxx>
126 #include <sfx2/dispatch.hxx>
127 #include <sfx2/app.hxx>
128 #include <sfx2/bindings.hxx>
129 #include <sfx2/request.hxx>
130 #include <sfx2/viewfrm.hxx>
131 #include <sfx2/itemwrapper.hxx>
132 #include <sc.hrc>
133 #include <globstr.hrc>
134 #include <unonames.hxx>
136 #include "vbaapplication.hxx"
137 #include "vbafont.hxx"
138 #include "vbacomment.hxx"
139 #include "vbainterior.hxx"
140 #include "vbacharacters.hxx"
141 #include "vbaborders.hxx"
142 #include "vbaworksheet.hxx"
143 #include "vbavalidation.hxx"
144 #include "vbahyperlinks.hxx"
146 #include "tabvwsh.hxx"
147 #include "rangelst.hxx"
148 #include "convuno.hxx"
149 #include "compiler.hxx"
150 #include "attrib.hxx"
151 #include "undodat.hxx"
152 #include "dbdocfun.hxx"
153 #include "patattr.hxx"
154 #include "olinetab.hxx"
155 #include "transobj.hxx"
156 #include "queryentry.hxx"
157 #include "markdata.hxx"
158 #include <comphelper/anytostring.hxx>
160 #include <global.hxx>
162 #include "vbaglobals.hxx"
163 #include "vbastyle.hxx"
164 #include "vbaname.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 // difference between VBA and file format width, in character units
179 const double fExtraWidth = 182.0 / 256.0;
181 // * 1 point = 1/72 inch = 20 twips
182 // * 1 inch = 72 points = 1440 twips
183 // * 1 cm = 567 twips
184 static double lcl_hmmToPoints( double nVal ) { return ( (double)((nVal /1000 ) * 567 ) / 20 ); }
186 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 };
188 static sal_uInt16 lcl_pointsToTwips( double nVal )
190 nVal = nVal * static_cast<double>(20);
191 short nTwips = static_cast<short>(nVal);
192 return nTwips;
194 static double lcl_TwipsToPoints( sal_uInt16 nVal )
196 double nPoints = nVal;
197 return nPoints / 20;
200 static double lcl_Round2DecPlaces( double nVal )
202 nVal = (nVal * (double)100);
203 long tmp = static_cast<long>(nVal);
204 if ( ( ( nVal - tmp ) >= 0.5 ) )
205 ++tmp;
206 nVal = tmp;
207 nVal = nVal/100;
208 return nVal;
211 static uno::Any lcl_makeRange( const uno::Reference< XHelperInterface >& xParent, const uno::Reference< uno::XComponentContext >& xContext, const uno::Any aAny, bool bIsRows, bool bIsColumns )
213 uno::Reference< table::XCellRange > xCellRange( aAny, uno::UNO_QUERY_THROW );
214 return uno::makeAny( uno::Reference< excel::XRange >( new ScVbaRange( xParent, xContext, xCellRange, bIsRows, bIsColumns ) ) );
217 static 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 )
219 uno::Reference< excel::XRange > xRange;
220 uno::Sequence< table::CellRangeAddress > sAddresses = xLocSheetCellRanges->getRangeAddresses();
221 ScRangeList aCellRanges;
222 sal_Int32 nLen = sAddresses.getLength();
223 if ( nLen )
225 for ( sal_Int32 index = 0; index < nLen; ++index )
227 ScRange refRange;
228 ScUnoConversion::FillScRange( refRange, sAddresses[ index ] );
229 aCellRanges.Append( refRange );
231 // Single range
232 if ( aCellRanges.size() == 1 )
234 uno::Reference< table::XCellRange > xTmpRange( new ScCellRangeObj( pDoc, *aCellRanges.front() ) );
235 xRange = new ScVbaRange( xParent, xContext, xTmpRange );
237 else
239 uno::Reference< sheet::XSheetCellRangeContainer > xRanges( new ScCellRangesObj( pDoc, aCellRanges ) );
240 xRange = new ScVbaRange( xParent, xContext, xRanges );
243 return xRange;
246 ScCellRangesBase* ScVbaRange::getCellRangesBase() throw ( uno::RuntimeException )
248 if( mxRanges.is() )
249 return ScCellRangesBase::getImplementation( mxRanges );
250 if( mxRange.is() )
251 return ScCellRangesBase::getImplementation( mxRange );
252 throw uno::RuntimeException( OUString("General Error creating range - Unknown" ), uno::Reference< uno::XInterface >() );
255 ScCellRangeObj* ScVbaRange::getCellRangeObj() throw ( uno::RuntimeException )
257 return dynamic_cast< ScCellRangeObj* >( getCellRangesBase() );
260 SfxItemSet* ScVbaRange::getCurrentDataSet( ) throw ( uno::RuntimeException )
262 SfxItemSet* pDataSet = excel::ScVbaCellRangeAccess::GetDataSet( getCellRangesBase() );
263 if ( !pDataSet )
264 throw uno::RuntimeException( OUString( "Can't access Itemset for range" ), uno::Reference< uno::XInterface >() );
265 return pDataSet;
268 void ScVbaRange::fireChangeEvent()
270 if( ScVbaApplication::getDocumentEventsEnabled() )
272 if( ScDocument* pDoc = getScDocument() )
274 uno::Reference< script::vba::XVBAEventProcessor > xVBAEvents = pDoc->GetVbaEventProcessor();
275 if( xVBAEvents.is() ) try
277 uno::Sequence< uno::Any > aArgs( 1 );
278 aArgs[ 0 ] <<= uno::Reference< excel::XRange >( this );
279 xVBAEvents->processVbaEvent( script::vba::VBAEventId::WORKSHEET_CHANGE, aArgs );
281 catch( uno::Exception& )
288 class SingleRangeEnumeration : public EnumerationHelper_BASE
290 uno::Reference< XHelperInterface > m_xParent;
291 uno::Reference< table::XCellRange > m_xRange;
292 uno::Reference< uno::XComponentContext > mxContext;
293 bool bHasMore;
294 public:
296 SingleRangeEnumeration( const uno::Reference< XHelperInterface >& xParent, const uno::Reference< css::uno::XComponentContext >& xContext, const uno::Reference< table::XCellRange >& xRange ) throw ( uno::RuntimeException ) : m_xParent( xParent ), m_xRange( xRange ), mxContext( xContext ), bHasMore( true ) { }
297 virtual ::sal_Bool SAL_CALL hasMoreElements( ) throw (uno::RuntimeException) { return bHasMore; }
298 virtual uno::Any SAL_CALL nextElement( ) throw (container::NoSuchElementException, lang::WrappedTargetException, uno::RuntimeException)
300 if ( !bHasMore )
301 throw container::NoSuchElementException();
302 bHasMore = false;
303 return uno::makeAny( m_xRange );
307 // very simple class to pass to ScVbaCollectionBaseImpl containing
308 // just one item
309 typedef ::cppu::WeakImplHelper2< container::XIndexAccess, container::XEnumerationAccess > SingleRange_BASE;
311 class SingleRangeIndexAccess : public SingleRange_BASE
313 private:
314 uno::Reference< XHelperInterface > mxParent;
315 uno::Reference< table::XCellRange > m_xRange;
316 uno::Reference< uno::XComponentContext > mxContext;
317 SingleRangeIndexAccess(); // not defined
318 public:
319 SingleRangeIndexAccess( const uno::Reference< XHelperInterface >& xParent, const uno::Reference< uno::XComponentContext >& xContext, const uno::Reference< table::XCellRange >& xRange ):mxParent( xParent ), m_xRange( xRange ), mxContext( xContext ) {}
320 // XIndexAccess
321 virtual ::sal_Int32 SAL_CALL getCount() throw (::uno::RuntimeException) { return 1; }
322 virtual uno::Any SAL_CALL getByIndex( ::sal_Int32 Index ) throw (lang::IndexOutOfBoundsException, lang::WrappedTargetException, uno::RuntimeException)
324 if ( Index != 0 )
325 throw lang::IndexOutOfBoundsException();
326 return uno::makeAny( m_xRange );
328 // XElementAccess
329 virtual uno::Type SAL_CALL getElementType() throw (uno::RuntimeException){ return table::XCellRange::static_type(0); }
331 virtual ::sal_Bool SAL_CALL hasElements() throw (uno::RuntimeException) { return sal_True; }
332 // XEnumerationAccess
333 virtual uno::Reference< container::XEnumeration > SAL_CALL createEnumeration() throw (uno::RuntimeException) { return new SingleRangeEnumeration( mxParent, mxContext, m_xRange ); }
339 class RangesEnumerationImpl : public EnumerationHelperImpl
341 bool mbIsRows;
342 bool mbIsColumns;
343 public:
345 RangesEnumerationImpl( const uno::Reference< XHelperInterface >& xParent, const uno::Reference< uno::XComponentContext >& xContext, const uno::Reference< container::XEnumeration >& xEnumeration, bool bIsRows, bool bIsColumns ) throw ( uno::RuntimeException ) : EnumerationHelperImpl( xParent, xContext, xEnumeration ), mbIsRows( bIsRows ), mbIsColumns( bIsColumns ) {}
346 virtual uno::Any SAL_CALL nextElement( ) throw (container::NoSuchElementException, lang::WrappedTargetException, uno::RuntimeException)
348 return lcl_makeRange( m_xParent, m_xContext, m_xEnumeration->nextElement(), mbIsRows, mbIsColumns );
353 class ScVbaRangeAreas : public ScVbaCollectionBaseImpl
355 bool mbIsRows;
356 bool mbIsColumns;
357 public:
358 ScVbaRangeAreas( const uno::Reference< XHelperInterface >& xParent, const uno::Reference< uno::XComponentContext >& xContext, const uno::Reference< container::XIndexAccess >& xIndexAccess, bool bIsRows, bool bIsColumns ) : ScVbaCollectionBaseImpl( xParent, xContext, xIndexAccess ), mbIsRows( bIsRows ), mbIsColumns( bIsColumns ) {}
360 // XEnumerationAccess
361 virtual uno::Reference< container::XEnumeration > SAL_CALL createEnumeration() throw (uno::RuntimeException);
363 // XElementAccess
364 virtual uno::Type SAL_CALL getElementType() throw (uno::RuntimeException){ return excel::XRange::static_type(0); }
366 virtual uno::Any createCollectionObject( const uno::Any& aSource );
368 virtual OUString getServiceImplName() { return OUString(); }
370 virtual uno::Sequence< OUString > getServiceNames() { return uno::Sequence< OUString >(); }
374 uno::Reference< container::XEnumeration > SAL_CALL
375 ScVbaRangeAreas::createEnumeration() throw (uno::RuntimeException)
377 uno::Reference< container::XEnumerationAccess > xEnumAccess( m_xIndexAccess, uno::UNO_QUERY_THROW );
378 return new RangesEnumerationImpl( mxParent, mxContext, xEnumAccess->createEnumeration(), mbIsRows, mbIsColumns );
381 uno::Any
382 ScVbaRangeAreas::createCollectionObject( const uno::Any& aSource )
384 return lcl_makeRange( mxParent, mxContext, aSource, mbIsRows, mbIsColumns );
387 // assume that xIf is infact a ScCellRangesBase
388 ScDocShell*
389 getDocShellFromIf( const uno::Reference< uno::XInterface >& xIf ) throw ( uno::RuntimeException )
391 ScCellRangesBase* pUno = ScCellRangesBase::getImplementation( xIf );
392 if ( !pUno )
393 throw uno::RuntimeException( OUString( "Failed to access underlying uno range object" ), uno::Reference< uno::XInterface >() );
394 return pUno->GetDocShell();
397 ScDocShell*
398 getDocShellFromRange( const uno::Reference< table::XCellRange >& xRange ) throw ( uno::RuntimeException )
400 // need the ScCellRangesBase to get docshell
401 uno::Reference< uno::XInterface > xIf( xRange );
402 return getDocShellFromIf(xIf );
405 ScDocShell*
406 getDocShellFromRanges( const uno::Reference< sheet::XSheetCellRangeContainer >& xRanges ) throw ( uno::RuntimeException )
408 // need the ScCellRangesBase to get docshell
409 uno::Reference< uno::XInterface > xIf( xRanges );
410 return getDocShellFromIf(xIf );
413 uno::Reference< frame::XModel > getModelFromXIf( const uno::Reference< uno::XInterface >& xIf ) throw ( uno::RuntimeException )
415 ScDocShell* pDocShell = getDocShellFromIf(xIf );
416 return pDocShell->GetModel();
419 uno::Reference< frame::XModel > getModelFromRange( const uno::Reference< table::XCellRange >& xRange ) throw ( uno::RuntimeException )
421 // the XInterface for getImplementation can be any derived interface, no need for queryInterface
422 uno::Reference< uno::XInterface > xIf( xRange );
423 return getModelFromXIf( xIf );
426 ScDocument*
427 getDocumentFromRange( const uno::Reference< table::XCellRange >& xRange )
429 ScDocShell* pDocShell = getDocShellFromRange( xRange );
430 if ( !pDocShell )
431 throw uno::RuntimeException( OUString( "Failed to access underlying docshell from uno range object" ), uno::Reference< uno::XInterface >() );
432 ScDocument* pDoc = pDocShell->GetDocument();
433 return pDoc;
436 ScDocument*
437 ScVbaRange::getScDocument() throw (uno::RuntimeException)
439 if ( mxRanges.is() )
441 uno::Reference< container::XIndexAccess > xIndex( mxRanges, uno::UNO_QUERY_THROW );
442 uno::Reference< table::XCellRange > xRange( xIndex->getByIndex( 0 ), uno::UNO_QUERY_THROW );
443 return getDocumentFromRange( xRange );
445 return getDocumentFromRange( mxRange );
448 ScDocShell*
449 ScVbaRange::getScDocShell() throw (uno::RuntimeException)
451 if ( mxRanges.is() )
453 uno::Reference< container::XIndexAccess > xIndex( mxRanges, uno::UNO_QUERY_THROW );
454 uno::Reference< table::XCellRange > xRange( xIndex->getByIndex( 0 ), uno::UNO_QUERY_THROW );
455 return getDocShellFromRange( xRange );
457 return getDocShellFromRange( mxRange );
460 ScVbaRange* ScVbaRange::getImplementation( const uno::Reference< excel::XRange >& rxRange )
462 // FIXME: always save to use dynamic_cast? Or better to (implement and) use XTunnel?
463 return dynamic_cast< ScVbaRange* >( rxRange.get() );
466 uno::Reference< frame::XModel > ScVbaRange::getUnoModel() throw (uno::RuntimeException)
468 if( ScDocShell* pDocShell = getScDocShell() )
469 return pDocShell->GetModel();
470 throw uno::RuntimeException();
473 uno::Reference< frame::XModel > ScVbaRange::getUnoModel( const uno::Reference< excel::XRange >& rxRange ) throw (uno::RuntimeException)
475 if( ScVbaRange* pScVbaRange = getImplementation( rxRange ) )
476 return pScVbaRange->getUnoModel();
477 throw uno::RuntimeException();
480 const ScRangeList& ScVbaRange::getScRangeList() throw (uno::RuntimeException)
482 if( ScCellRangesBase* pScRangesBase = getCellRangesBase() )
483 return pScRangesBase->GetRangeList();
484 throw uno::RuntimeException( OUString( "Cannot obtain UNO range implementation object" ), uno::Reference< uno::XInterface >() );
487 const ScRangeList& ScVbaRange::getScRangeList( const uno::Reference< excel::XRange >& rxRange ) throw (uno::RuntimeException)
489 if( ScVbaRange* pScVbaRange = getImplementation( rxRange ) )
490 return pScVbaRange->getScRangeList();
491 throw uno::RuntimeException( OUString( "Cannot obtain VBA range implementation object" ), uno::Reference< uno::XInterface >() );
495 class NumFormatHelper
497 uno::Reference< util::XNumberFormatsSupplier > mxSupplier;
498 uno::Reference< beans::XPropertySet > mxRangeProps;
499 uno::Reference< util::XNumberFormats > mxFormats;
500 public:
501 NumFormatHelper( const uno::Reference< table::XCellRange >& xRange )
503 mxSupplier.set( getModelFromRange( xRange ), uno::UNO_QUERY_THROW );
504 mxRangeProps.set( xRange, uno::UNO_QUERY_THROW);
505 mxFormats = mxSupplier->getNumberFormats();
507 uno::Reference< beans::XPropertySet > getNumberProps()
509 long nIndexKey = 0;
510 uno::Any aValue = mxRangeProps->getPropertyValue( "NumberFormat" );
511 aValue >>= nIndexKey;
513 if ( mxFormats.is() )
514 return mxFormats->getByKey( nIndexKey );
515 return uno::Reference< beans::XPropertySet > ();
518 bool isBooleanType()
521 if ( getNumberFormat() & util::NumberFormat::LOGICAL )
522 return true;
523 return false;
526 bool isDateType()
528 sal_Int16 nType = getNumberFormat();
529 if(( nType & util::NumberFormat::DATETIME ))
531 return true;
533 return false;
536 OUString getNumberFormatString()
538 uno::Reference< uno::XInterface > xIf( mxRangeProps, uno::UNO_QUERY_THROW );
539 ScCellRangesBase* pUnoCellRange = ScCellRangesBase::getImplementation( xIf );
540 if ( pUnoCellRange )
543 SfxItemSet* pDataSet = excel::ScVbaCellRangeAccess::GetDataSet( pUnoCellRange );
544 SfxItemState eState = pDataSet->GetItemState( ATTR_VALUE_FORMAT, true, NULL);
545 // one of the cells in the range is not like the other ;-)
546 // so return a zero length format to indicate that
547 if ( eState == SFX_ITEM_DONTCARE )
548 return OUString();
552 uno::Reference< beans::XPropertySet > xNumberProps( getNumberProps(), uno::UNO_QUERY_THROW );
553 OUString aFormatString;
554 uno::Any aString = xNumberProps->getPropertyValue( "FormatString" );
555 aString >>= aFormatString;
556 return aFormatString;
559 sal_Int16 getNumberFormat()
561 uno::Reference< beans::XPropertySet > xNumberProps = getNumberProps();
562 sal_Int16 nType = ::comphelper::getINT16(
563 xNumberProps->getPropertyValue( "Type" ) );
564 return nType;
567 bool setNumberFormat( const OUString& rFormat )
569 // #163288# treat "General" as "Standard" format
570 sal_Int32 nNewIndex = 0;
571 if( !rFormat.equalsIgnoreAsciiCase( "General" ) )
573 lang::Locale aLocale;
574 uno::Reference< beans::XPropertySet > xNumProps = getNumberProps();
575 xNumProps->getPropertyValue( "Locale" ) >>= aLocale;
576 nNewIndex = mxFormats->queryKey( rFormat, aLocale, false );
577 if ( nNewIndex == -1 ) // format not defined
578 nNewIndex = mxFormats->addNew( rFormat, aLocale );
580 mxRangeProps->setPropertyValue( "NumberFormat", uno::makeAny( nNewIndex ) );
581 return true;
584 bool setNumberFormat( sal_Int16 nType )
586 uno::Reference< beans::XPropertySet > xNumberProps = getNumberProps();
587 lang::Locale aLocale;
588 xNumberProps->getPropertyValue( "Locale" ) >>= aLocale;
589 uno::Reference<util::XNumberFormatTypes> xTypes( mxFormats, uno::UNO_QUERY );
590 if ( xTypes.is() )
592 sal_Int32 nNewIndex = xTypes->getStandardFormat( nType, aLocale );
593 mxRangeProps->setPropertyValue( "NumberFormat", uno::makeAny( nNewIndex ) );
594 return true;
596 return false;
601 struct CellPos
603 CellPos():m_nRow(-1), m_nCol(-1), m_nArea(0) {};
604 CellPos( sal_Int32 nRow, sal_Int32 nCol, sal_Int32 nArea ):m_nRow(nRow), m_nCol(nCol), m_nArea( nArea ) {};
605 sal_Int32 m_nRow;
606 sal_Int32 m_nCol;
607 sal_Int32 m_nArea;
610 typedef ::cppu::WeakImplHelper1< container::XEnumeration > CellsEnumeration_BASE;
611 typedef ::std::vector< CellPos > vCellPos;
613 // #FIXME - QUICK
614 // we could probably could and should modify CellsEnumeration below
615 // to handle rows and columns ( but I do this separately for now
616 // and.. this class only handles singe areas ( does it have to handle
617 // multi area ranges?? )
618 class ColumnsRowEnumeration: public CellsEnumeration_BASE
620 uno::Reference< uno::XComponentContext > mxContext;
621 uno::Reference< excel::XRange > mxRange;
622 sal_Int32 mMaxElems;
623 sal_Int32 mCurElem;
625 public:
626 ColumnsRowEnumeration( const uno::Reference< uno::XComponentContext >& xContext, const uno::Reference< excel::XRange >& xRange, sal_Int32 nElems ) : mxContext( xContext ), mxRange( xRange ), mMaxElems( nElems ), mCurElem( 0 )
630 virtual ::sal_Bool SAL_CALL hasMoreElements() throw (::uno::RuntimeException){ return mCurElem < mMaxElems; }
632 virtual uno::Any SAL_CALL nextElement() throw (container::NoSuchElementException, lang::WrappedTargetException, uno::RuntimeException)
634 if ( !hasMoreElements() )
635 throw container::NoSuchElementException();
636 sal_Int32 vbaIndex = 1 + mCurElem++;
637 return uno::makeAny( mxRange->Item( uno::makeAny( vbaIndex ), uno::Any() ) );
641 class CellsEnumeration : public CellsEnumeration_BASE
643 uno::WeakReference< XHelperInterface > mxParent;
644 uno::Reference< uno::XComponentContext > mxContext;
645 uno::Reference< XCollection > m_xAreas;
646 vCellPos m_CellPositions;
647 vCellPos::const_iterator m_it;
649 uno::Reference< table::XCellRange > getArea( sal_Int32 nVBAIndex ) throw ( uno::RuntimeException )
651 if ( nVBAIndex < 1 || nVBAIndex > m_xAreas->getCount() )
652 throw uno::RuntimeException();
653 uno::Reference< excel::XRange > xRange( m_xAreas->Item( uno::makeAny(nVBAIndex), uno::Any() ), uno::UNO_QUERY_THROW );
654 uno::Reference< table::XCellRange > xCellRange( ScVbaRange::getCellRange( xRange ), uno::UNO_QUERY_THROW );
655 return xCellRange;
658 void populateArea( sal_Int32 nVBAIndex )
660 uno::Reference< table::XCellRange > xRange = getArea( nVBAIndex );
661 uno::Reference< table::XColumnRowRange > xColumnRowRange(xRange, uno::UNO_QUERY_THROW );
662 sal_Int32 nRowCount = xColumnRowRange->getRows()->getCount();
663 sal_Int32 nColCount = xColumnRowRange->getColumns()->getCount();
664 for ( sal_Int32 i=0; i<nRowCount; ++i )
666 for ( sal_Int32 j=0; j<nColCount; ++j )
667 m_CellPositions.push_back( CellPos( i,j,nVBAIndex ) );
670 public:
671 CellsEnumeration( const uno::Reference< XHelperInterface >& xParent, const uno::Reference< uno::XComponentContext >& xContext, const uno::Reference< XCollection >& xAreas ): mxParent( xParent ), mxContext( xContext ), m_xAreas( xAreas )
673 sal_Int32 nItems = m_xAreas->getCount();
674 for ( sal_Int32 index=1; index <= nItems; ++index )
676 populateArea( index );
678 m_it = m_CellPositions.begin();
680 virtual ::sal_Bool SAL_CALL hasMoreElements() throw (::uno::RuntimeException){ return m_it != m_CellPositions.end(); }
682 virtual uno::Any SAL_CALL nextElement() throw (container::NoSuchElementException, lang::WrappedTargetException, uno::RuntimeException)
684 if ( !hasMoreElements() )
685 throw container::NoSuchElementException();
686 CellPos aPos = *(m_it)++;
688 uno::Reference< table::XCellRange > xRangeArea = getArea( aPos.m_nArea );
689 uno::Reference< table::XCellRange > xCellRange( xRangeArea->getCellByPosition( aPos.m_nCol, aPos.m_nRow ), uno::UNO_QUERY_THROW );
690 return uno::makeAny( uno::Reference< excel::XRange >( new ScVbaRange( mxParent, mxContext, xCellRange ) ) );
696 const static OUString ISVISIBLE( "IsVisible");
697 const static OUString POSITION( "Position");
698 const static OUString EQUALS( "=" );
699 const static OUString NOTEQUALS( "<>" );
700 const static OUString GREATERTHAN( ">" );
701 const static OUString GREATERTHANEQUALS( ">=" );
702 const static OUString LESSTHAN( "<" );
703 const static OUString LESSTHANEQUALS( "<=" );
704 const static OUString CONTS_HEADER( "ContainsHeader" );
705 const static OUString INSERTPAGEBREAKS( "InsertPageBreaks" );
706 const static OUString STR_ERRORMESSAGE_APPLIESTOSINGLERANGEONLY( "The command you chose cannot be performed with multiple selections.\nSelect a single range and click the command again" );
707 const static OUString STR_ERRORMESSAGE_NOCELLSWEREFOUND( "No cells were found" );
708 const static OUString CELLSTYLE( "CellStyle" );
710 class CellValueSetter : public ValueSetter
712 protected:
713 uno::Any maValue;
714 uno::TypeClass mTypeClass;
715 public:
716 CellValueSetter( const uno::Any& aValue );
717 virtual bool processValue( const uno::Any& aValue, const uno::Reference< table::XCell >& xCell );
718 virtual void visitNode( sal_Int32 x, sal_Int32 y, const uno::Reference< table::XCell >& xCell );
722 CellValueSetter::CellValueSetter( const uno::Any& aValue ): maValue( aValue ), mTypeClass( aValue.getValueTypeClass() ) {}
724 void
725 CellValueSetter::visitNode( sal_Int32 /*i*/, sal_Int32 /*j*/, const uno::Reference< table::XCell >& xCell )
727 processValue( maValue, xCell );
730 bool
731 CellValueSetter::processValue( const uno::Any& aValue, const uno::Reference< table::XCell >& xCell )
734 bool isExtracted = false;
735 switch ( aValue.getValueTypeClass() )
737 case uno::TypeClass_BOOLEAN:
739 sal_Bool bState = false;
740 if ( aValue >>= bState )
742 uno::Reference< table::XCellRange > xRange( xCell, uno::UNO_QUERY_THROW );
743 if ( bState )
744 xCell->setValue( (double) 1 );
745 else
746 xCell->setValue( (double) 0 );
747 NumFormatHelper cellNumFormat( xRange );
748 cellNumFormat.setNumberFormat( util::NumberFormat::LOGICAL );
750 break;
752 case uno::TypeClass_STRING:
754 OUString aString;
755 if ( aValue >>= aString )
757 // The required behavior for a string value is:
758 // 1. If the first character is a single quote, use the rest as a string cell, regardless of the cell's number format.
759 // 2. Otherwise, if the cell's number format is "text", use the string value as a string cell.
760 // 3. Otherwise, parse the string value in English locale, and apply a corresponding number format with the cell's locale
761 // if the cell's number format was "General".
762 // Case 1 is handled here, the rest in ScCellObj::InputEnglishString
764 if ( aString.toChar() == '\'' ) // case 1 - handle with XTextRange
766 OUString aRemainder( aString.copy(1) ); // strip the quote
767 uno::Reference< text::XTextRange > xTextRange( xCell, uno::UNO_QUERY_THROW );
768 xTextRange->setString( aRemainder );
770 else
772 // call implementation method InputEnglishString
773 ScCellObj* pCellObj = dynamic_cast< ScCellObj* >( xCell.get() );
774 if ( pCellObj )
775 pCellObj->InputEnglishString( aString );
778 else
779 isExtracted = false;
780 break;
782 default:
784 double nDouble = 0.0;
785 if ( aValue >>= nDouble )
787 uno::Reference< table::XCellRange > xRange( xCell, uno::UNO_QUERY_THROW );
788 NumFormatHelper cellFormat( xRange );
789 // If we are setting a number and the cell types was logical
790 // then we need to reset the logical format. ( see case uno::TypeClass_BOOLEAN:
791 // handling above )
792 if ( cellFormat.isBooleanType() )
793 cellFormat.setNumberFormat("General");
794 xCell->setValue( nDouble );
796 else
797 isExtracted = false;
798 break;
801 return isExtracted;
806 class CellValueGetter : public ValueGetter
808 protected:
809 uno::Any maValue;
810 uno::TypeClass mTypeClass;
811 public:
812 CellValueGetter() {}
813 virtual void visitNode( sal_Int32 x, sal_Int32 y, const uno::Reference< table::XCell >& xCell );
814 virtual void processValue( sal_Int32 x, sal_Int32 y, const uno::Any& aValue );
815 const uno::Any& getValue() const { return maValue; }
819 void
820 CellValueGetter::processValue( sal_Int32 /*x*/, sal_Int32 /*y*/, const uno::Any& aValue )
822 maValue = aValue;
824 void CellValueGetter::visitNode( sal_Int32 x, sal_Int32 y, const uno::Reference< table::XCell >& xCell )
826 uno::Any aValue;
827 table::CellContentType eType = xCell->getType();
828 if( eType == table::CellContentType_VALUE || eType == table::CellContentType_FORMULA )
830 if ( eType == table::CellContentType_FORMULA )
833 OUString sFormula = xCell->getFormula();
834 if ( sFormula == "=TRUE()" )
835 aValue <<= sal_True;
836 else if ( sFormula == "=FALSE()" )
837 aValue <<= false;
838 else
840 uno::Reference< beans::XPropertySet > xProp( xCell, uno::UNO_QUERY_THROW );
842 table::CellContentType eFormulaType = table::CellContentType_VALUE;
843 // some formulas give textual results
844 xProp->getPropertyValue( "FormulaResultType" ) >>= eFormulaType;
846 if ( eFormulaType == table::CellContentType_TEXT )
848 uno::Reference< text::XTextRange > xTextRange(xCell, ::uno::UNO_QUERY_THROW);
849 aValue <<= xTextRange->getString();
851 else
852 aValue <<= xCell->getValue();
855 else
857 uno::Reference< table::XCellRange > xRange( xCell, uno::UNO_QUERY_THROW );
858 NumFormatHelper cellFormat( xRange );
859 if ( cellFormat.isBooleanType() )
860 aValue = uno::makeAny( ( xCell->getValue() != 0.0 ) );
861 else if ( cellFormat.isDateType() )
862 aValue = uno::makeAny( bridge::oleautomation::Date( xCell->getValue() ) );
863 else
864 aValue <<= xCell->getValue();
867 if( eType == table::CellContentType_TEXT )
869 uno::Reference< text::XTextRange > xTextRange(xCell, ::uno::UNO_QUERY_THROW);
870 aValue <<= xTextRange->getString();
872 processValue( x,y,aValue );
875 class CellFormulaValueSetter : public CellValueSetter
877 private:
878 ScDocument* m_pDoc;
879 formula::FormulaGrammar::Grammar m_eGrammar;
880 public:
881 CellFormulaValueSetter( const uno::Any& aValue, ScDocument* pDoc, formula::FormulaGrammar::Grammar eGram ):CellValueSetter( aValue ), m_pDoc( pDoc ), m_eGrammar( eGram ){}
882 protected:
883 bool processValue( const uno::Any& aValue, const uno::Reference< table::XCell >& xCell )
885 OUString sFormula;
886 double aDblValue = 0.0;
887 if ( aValue >>= sFormula )
889 // convert to GRAM_PODF_A1 style grammar because XCell::setFormula
890 // always compile it in that grammar. Perhaps
891 // css.sheet.FormulaParser should be used in future to directly
892 // pass formula tokens when that API stabilizes.
893 if ( m_eGrammar != formula::FormulaGrammar::GRAM_PODF_A1 && ( sFormula.trim().indexOf('=') == 0 ) )
895 uno::Reference< uno::XInterface > xIf( xCell, uno::UNO_QUERY_THROW );
896 ScCellRangesBase* pUnoRangesBase = dynamic_cast< ScCellRangesBase* >( xIf.get() );
897 if ( pUnoRangesBase )
899 ScRangeList aCellRanges = pUnoRangesBase->GetRangeList();
900 ScCompiler aCompiler( m_pDoc, aCellRanges.front()->aStart );
901 aCompiler.SetGrammar(m_eGrammar);
902 // compile the string in the format passed in
903 aCompiler.CompileString( sFormula );
904 // set desired convention to that of the document
905 aCompiler.SetGrammar( formula::FormulaGrammar::GRAM_PODF_A1 );
906 String sConverted;
907 aCompiler.CreateStringFromTokenArray(sConverted);
908 sFormula = EQUALS + sConverted;
912 xCell->setFormula( sFormula );
913 return true;
915 else if ( aValue >>= aDblValue )
917 xCell->setValue( aDblValue );
918 return true;
920 return false;
925 class CellFormulaValueGetter : public CellValueGetter
927 private:
928 ScDocument* m_pDoc;
929 formula::FormulaGrammar::Grammar m_eGrammar;
930 public:
931 CellFormulaValueGetter(ScDocument* pDoc, formula::FormulaGrammar::Grammar eGram ) : CellValueGetter( ), m_pDoc( pDoc ), m_eGrammar( eGram ) {}
932 virtual void visitNode( sal_Int32 x, sal_Int32 y, const uno::Reference< table::XCell >& xCell )
934 uno::Any aValue;
935 aValue <<= xCell->getFormula();
936 OUString sVal;
937 aValue >>= sVal;
938 uno::Reference< uno::XInterface > xIf( xCell, uno::UNO_QUERY_THROW );
939 ScCellRangesBase* pUnoRangesBase = dynamic_cast< ScCellRangesBase* >( xIf.get() );
940 if ( ( xCell->getType() == table::CellContentType_FORMULA ) &&
941 pUnoRangesBase )
943 ScRangeList aCellRanges = pUnoRangesBase->GetRangeList();
944 ScCompiler aCompiler( m_pDoc, aCellRanges.front()->aStart );
945 aCompiler.SetGrammar(formula::FormulaGrammar::GRAM_DEFAULT);
946 aCompiler.CompileString( sVal );
947 // set desired convention
948 aCompiler.SetGrammar( m_eGrammar );
949 String sConverted;
950 aCompiler.CreateStringFromTokenArray(sConverted);
951 sVal = EQUALS + sConverted;
952 aValue <<= sVal;
955 processValue( x,y,aValue );
961 class Dim2ArrayValueGetter : public ArrayVisitor
963 protected:
964 uno::Any maValue;
965 ValueGetter& mValueGetter;
966 virtual void processValue( sal_Int32 x, sal_Int32 y, const uno::Any& aValue )
968 uno::Sequence< uno::Sequence< uno::Any > >& aMatrix = *( uno::Sequence< uno::Sequence< uno::Any > >* )( maValue.getValue() );
969 aMatrix[x][y] = aValue;
972 public:
973 Dim2ArrayValueGetter(sal_Int32 nRowCount, sal_Int32 nColCount, ValueGetter& rValueGetter ): mValueGetter(rValueGetter)
975 uno::Sequence< uno::Sequence< uno::Any > > aMatrix;
976 aMatrix.realloc( nRowCount );
977 for ( sal_Int32 index = 0; index < nRowCount; ++index )
978 aMatrix[index].realloc( nColCount );
979 maValue <<= aMatrix;
981 void visitNode( sal_Int32 x, sal_Int32 y, const uno::Reference< table::XCell >& xCell )
984 mValueGetter.visitNode( x, y, xCell );
985 processValue( x, y, mValueGetter.getValue() );
987 const uno::Any& getValue() const { return maValue; }
991 const static OUString sNA("#N/A");
993 class Dim1ArrayValueSetter : public ArrayVisitor
995 uno::Sequence< uno::Any > aMatrix;
996 sal_Int32 nColCount;
997 ValueSetter& mCellValueSetter;
998 public:
999 Dim1ArrayValueSetter( const uno::Any& aValue, ValueSetter& rCellValueSetter ):mCellValueSetter( rCellValueSetter )
1001 aValue >>= aMatrix;
1002 nColCount = aMatrix.getLength();
1004 virtual void visitNode( sal_Int32 /*x*/, sal_Int32 y, const uno::Reference< table::XCell >& xCell )
1006 if ( y < nColCount )
1007 mCellValueSetter.processValue( aMatrix[ y ], xCell );
1008 else
1009 mCellValueSetter.processValue( uno::makeAny( sNA ), xCell );
1015 class Dim2ArrayValueSetter : public ArrayVisitor
1017 uno::Sequence< uno::Sequence< uno::Any > > aMatrix;
1018 ValueSetter& mCellValueSetter;
1019 sal_Int32 nRowCount;
1020 sal_Int32 nColCount;
1021 public:
1022 Dim2ArrayValueSetter( const uno::Any& aValue, ValueSetter& rCellValueSetter ) : mCellValueSetter( rCellValueSetter )
1024 aValue >>= aMatrix;
1025 nRowCount = aMatrix.getLength();
1026 nColCount = aMatrix[0].getLength();
1029 virtual void visitNode( sal_Int32 x, sal_Int32 y, const uno::Reference< table::XCell >& xCell )
1031 if ( x < nRowCount && y < nColCount )
1032 mCellValueSetter.processValue( aMatrix[ x ][ y ], xCell );
1033 else
1034 mCellValueSetter.processValue( uno::makeAny( sNA ), xCell );
1039 class RangeProcessor
1041 public:
1042 virtual void process( const uno::Reference< excel::XRange >& xRange ) = 0;
1044 protected:
1045 ~RangeProcessor() {}
1048 class RangeValueProcessor : public RangeProcessor
1050 const uno::Any& m_aVal;
1051 public:
1052 RangeValueProcessor( const uno::Any& rVal ):m_aVal( rVal ) {}
1053 virtual ~RangeValueProcessor() {}
1054 virtual void process( const uno::Reference< excel::XRange >& xRange )
1056 xRange->setValue( m_aVal );
1060 class RangeFormulaProcessor : public RangeProcessor
1062 const uno::Any& m_aVal;
1063 public:
1064 RangeFormulaProcessor( const uno::Any& rVal ):m_aVal( rVal ) {}
1065 virtual ~RangeFormulaProcessor() {}
1066 virtual void process( const uno::Reference< excel::XRange >& xRange )
1068 xRange->setFormula( m_aVal );
1072 class RangeCountProcessor : public RangeProcessor
1074 sal_Int32 nCount;
1075 public:
1076 RangeCountProcessor():nCount(0){}
1077 virtual ~RangeCountProcessor() {}
1078 virtual void process( const uno::Reference< excel::XRange >& xRange )
1080 nCount = nCount + xRange->getCount();
1082 sal_Int32 value() { return nCount; }
1084 class AreasVisitor
1086 private:
1087 uno::Reference< XCollection > m_Areas;
1088 public:
1089 AreasVisitor( const uno::Reference< XCollection >& rAreas ):m_Areas( rAreas ){}
1091 void visit( RangeProcessor& processor )
1093 if ( m_Areas.is() )
1095 sal_Int32 nItems = m_Areas->getCount();
1096 for ( sal_Int32 index=1; index <= nItems; ++index )
1098 uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny(index), uno::Any() ), uno::UNO_QUERY_THROW );
1099 processor.process( xRange );
1105 class RangeHelper
1107 uno::Reference< table::XCellRange > m_xCellRange;
1109 public:
1110 RangeHelper( const uno::Reference< table::XCellRange >& xCellRange ) throw (uno::RuntimeException) : m_xCellRange( xCellRange )
1112 if ( !m_xCellRange.is() )
1113 throw uno::RuntimeException();
1115 RangeHelper( const uno::Any aCellRange ) throw (uno::RuntimeException)
1117 m_xCellRange.set( aCellRange, uno::UNO_QUERY_THROW );
1119 uno::Reference< sheet::XSheetCellRange > getSheetCellRange() throw (uno::RuntimeException)
1121 return uno::Reference< sheet::XSheetCellRange >(m_xCellRange, uno::UNO_QUERY_THROW);
1123 uno::Reference< sheet::XSpreadsheet > getSpreadSheet() throw (uno::RuntimeException)
1125 return getSheetCellRange()->getSpreadsheet();
1128 uno::Reference< table::XCellRange > getCellRangeFromSheet() throw (uno::RuntimeException)
1130 return uno::Reference< table::XCellRange >(getSpreadSheet(), uno::UNO_QUERY_THROW );
1133 uno::Reference< sheet::XCellRangeAddressable > getCellRangeAddressable() throw (uno::RuntimeException)
1135 return uno::Reference< sheet::XCellRangeAddressable >(m_xCellRange, ::uno::UNO_QUERY_THROW);
1139 uno::Reference< sheet::XSheetCellCursor > getSheetCellCursor() throw ( uno::RuntimeException )
1141 return uno::Reference< sheet::XSheetCellCursor >( getSpreadSheet()->createCursorByRange( getSheetCellRange() ), uno::UNO_QUERY_THROW );
1144 static uno::Reference< excel::XRange > createRangeFromRange( const uno::Reference< XHelperInterface >& xParent, const uno::Reference<uno::XComponentContext >& xContext,
1145 const uno::Reference< table::XCellRange >& xRange, const uno::Reference< sheet::XCellRangeAddressable >& xCellRangeAddressable,
1146 sal_Int32 nStartColOffset = 0, sal_Int32 nStartRowOffset = 0, sal_Int32 nEndColOffset = 0, sal_Int32 nEndRowOffset = 0 )
1148 return uno::Reference< excel::XRange >( new ScVbaRange( xParent, xContext,
1149 xRange->getCellRangeByPosition(
1150 xCellRangeAddressable->getRangeAddress().StartColumn + nStartColOffset,
1151 xCellRangeAddressable->getRangeAddress().StartRow + nStartRowOffset,
1152 xCellRangeAddressable->getRangeAddress().EndColumn + nEndColOffset,
1153 xCellRangeAddressable->getRangeAddress().EndRow + nEndRowOffset ) ) );
1158 bool
1159 ScVbaRange::getCellRangesForAddress( sal_uInt16& rResFlags, const OUString& sAddress, ScDocShell* pDocSh, ScRangeList& rCellRanges, formula::FormulaGrammar::AddressConvention& eConv, char cDelimiter )
1162 ScDocument* pDoc = NULL;
1163 if ( pDocSh )
1165 pDoc = pDocSh->GetDocument();
1166 sal_uInt16 nMask = SCA_VALID;
1167 rResFlags = rCellRanges.Parse( sAddress, pDoc, nMask, eConv, 0, cDelimiter );
1168 if ( rResFlags & SCA_VALID )
1170 return true;
1173 return false;
1176 bool getScRangeListForAddress( const OUString& sName, ScDocShell* pDocSh, ScRange& refRange, ScRangeList& aCellRanges, formula::FormulaGrammar::AddressConvention aConv = formula::FormulaGrammar::CONV_XL_A1 ) throw ( uno::RuntimeException )
1178 // see if there is a match with a named range
1179 uno::Reference< beans::XPropertySet > xProps( pDocSh->GetModel(), uno::UNO_QUERY_THROW );
1180 uno::Reference< container::XNameAccess > xNameAccess( xProps->getPropertyValue( "NamedRanges" ), uno::UNO_QUERY_THROW );
1181 // Strangly enough you can have Range( "namedRange1, namedRange2, etc," )
1182 // loop around each ',' separated name
1183 std::vector< OUString > vNames;
1184 sal_Int32 nIndex = 0;
1187 OUString aToken = sName.getToken( 0, ',', nIndex );
1188 vNames.push_back( aToken );
1189 } while ( nIndex >= 0 );
1191 if ( vNames.empty() )
1192 vNames.push_back( sName );
1194 std::vector< OUString >::iterator it = vNames.begin();
1195 std::vector< OUString >::iterator it_end = vNames.end();
1196 for ( ; it != it_end; ++it )
1199 formula::FormulaGrammar::AddressConvention eConv = aConv;
1200 // spaces are illegal ( but the user of course can enter them )
1201 OUString sAddress = (*it).trim();
1202 // if a local name ( on the active sheet ) exists this will
1203 // take precedence over a global with the same name
1204 bool bLocalName = false;
1205 if ( !xNameAccess->hasByName( sAddress ) && pDocSh )
1207 // try a local name
1208 ScDocument* pDoc = pDocSh->GetDocument();
1209 if ( pDoc )
1211 SCTAB nCurTab = pDocSh->GetCurTab();
1212 ScRangeName* pRangeName = pDoc->GetRangeName(nCurTab);
1213 if (pRangeName)
1215 bLocalName = pRangeName->findByUpperName(ScGlobal::pCharClass->uppercase(sAddress)) != NULL;
1216 // TODO: Handle local names correctly.
1217 (void)bLocalName;
1221 char aChar = 0;
1222 if ( xNameAccess->hasByName( sAddress ) )
1224 uno::Reference< sheet::XNamedRange > xNamed( xNameAccess->getByName( sAddress ), uno::UNO_QUERY_THROW );
1225 sAddress = xNamed->getContent();
1226 // As the address comes from OOO, the addressing
1227 // style is may not be XL_A1
1228 eConv = pDocSh->GetDocument()->GetAddressConvention();
1229 aChar = ';';
1232 sal_uInt16 nFlags = 0;
1233 if ( !ScVbaRange::getCellRangesForAddress( nFlags, sAddress, pDocSh, aCellRanges, eConv, aChar ) )
1234 return false;
1236 bool bTabFromReferrer = !( nFlags & SCA_TAB_3D );
1238 for ( size_t i = 0, nRanges = aCellRanges.size(); i < nRanges; ++i )
1240 ScRange* pRange = aCellRanges[ i ];
1241 pRange->aStart.SetCol( refRange.aStart.Col() + pRange->aStart.Col() );
1242 pRange->aStart.SetRow( refRange.aStart.Row() + pRange->aStart.Row() );
1243 pRange->aStart.SetTab( bTabFromReferrer ? refRange.aStart.Tab() : pRange->aStart.Tab() );
1244 pRange->aEnd.SetCol( refRange.aStart.Col() + pRange->aEnd.Col() );
1245 pRange->aEnd.SetRow( refRange.aStart.Row() + pRange->aEnd.Row() );
1246 pRange->aEnd.SetTab( bTabFromReferrer ? refRange.aEnd.Tab() : pRange->aEnd.Tab() );
1249 return true;
1253 ScVbaRange*
1254 getRangeForName( const uno::Reference< uno::XComponentContext >& xContext, const OUString& sName, ScDocShell* pDocSh, table::CellRangeAddress& pAddr, formula::FormulaGrammar::AddressConvention eConv = formula::FormulaGrammar::CONV_XL_A1 ) throw ( uno::RuntimeException )
1256 ScRangeList aCellRanges;
1257 ScRange refRange;
1258 ScUnoConversion::FillScRange( refRange, pAddr );
1259 if ( !getScRangeListForAddress ( sName, pDocSh, refRange, aCellRanges, eConv ) )
1260 throw uno::RuntimeException();
1261 // Single range
1262 if ( aCellRanges.size() == 1 )
1264 uno::Reference< table::XCellRange > xRange( new ScCellRangeObj( pDocSh, *aCellRanges.front() ) );
1265 uno::Reference< XHelperInterface > xFixThisParent = excel::getUnoSheetModuleObj( xRange );
1266 return new ScVbaRange( xFixThisParent, xContext, xRange );
1268 uno::Reference< sheet::XSheetCellRangeContainer > xRanges( new ScCellRangesObj( pDocSh, aCellRanges ) );
1270 uno::Reference< XHelperInterface > xFixThisParent = excel::getUnoSheetModuleObj( xRanges );
1271 return new ScVbaRange( xFixThisParent, xContext, xRanges );
1274 // ----------------------------------------------------------------------------
1276 namespace {
1278 template< typename RangeType >
1279 inline table::CellRangeAddress lclGetRangeAddress( const uno::Reference< RangeType >& rxCellRange ) throw (uno::RuntimeException)
1281 return uno::Reference< sheet::XCellRangeAddressable >( rxCellRange, uno::UNO_QUERY_THROW )->getRangeAddress();
1284 void lclClearRange( const uno::Reference< table::XCellRange >& rxCellRange ) throw (uno::RuntimeException)
1286 using namespace ::com::sun::star::sheet::CellFlags;
1287 sal_Int32 nFlags = VALUE | DATETIME | STRING | ANNOTATION | FORMULA | HARDATTR | STYLES | EDITATTR | FORMATTED;
1288 uno::Reference< sheet::XSheetOperation > xSheetOperation( rxCellRange, uno::UNO_QUERY_THROW );
1289 xSheetOperation->clearContents( nFlags );
1292 uno::Reference< sheet::XSheetCellRange > lclExpandToMerged( const uno::Reference< table::XCellRange >& rxCellRange, bool bRecursive ) throw (uno::RuntimeException)
1294 uno::Reference< sheet::XSheetCellRange > xNewCellRange( rxCellRange, uno::UNO_QUERY_THROW );
1295 uno::Reference< sheet::XSpreadsheet > xSheet( xNewCellRange->getSpreadsheet(), uno::UNO_SET_THROW );
1296 table::CellRangeAddress aNewAddress = lclGetRangeAddress( xNewCellRange );
1297 table::CellRangeAddress aOldAddress;
1298 // expand as long as there are new merged ranges included
1301 aOldAddress = aNewAddress;
1302 uno::Reference< sheet::XSheetCellCursor > xCursor( xSheet->createCursorByRange( xNewCellRange ), uno::UNO_SET_THROW );
1303 xCursor->collapseToMergedArea();
1304 xNewCellRange.set( xCursor, uno::UNO_QUERY_THROW );
1305 aNewAddress = lclGetRangeAddress( xNewCellRange );
1307 while( bRecursive && (aOldAddress != aNewAddress) );
1308 return xNewCellRange;
1311 uno::Reference< sheet::XSheetCellRangeContainer > lclExpandToMerged( const uno::Reference< sheet::XSheetCellRangeContainer >& rxCellRanges, bool bRecursive ) throw (uno::RuntimeException)
1313 if( !rxCellRanges.is() )
1314 throw uno::RuntimeException( OUString( "Missing cell ranges object" ), uno::Reference< uno::XInterface >() );
1315 sal_Int32 nCount = rxCellRanges->getCount();
1316 if( nCount < 1 )
1317 throw uno::RuntimeException( OUString( "Missing cell ranges object" ), uno::Reference< uno::XInterface >() );
1319 ScRangeList aScRanges;
1320 for( sal_Int32 nIndex = 0; nIndex < nCount; ++nIndex )
1322 uno::Reference< table::XCellRange > xRange( rxCellRanges->getByIndex( nIndex ), uno::UNO_QUERY_THROW );
1323 table::CellRangeAddress aRangeAddr = lclGetRangeAddress( lclExpandToMerged( xRange, bRecursive ) );
1324 ScRange aScRange;
1325 ScUnoConversion::FillScRange( aScRange, aRangeAddr );
1326 aScRanges.Append( aScRange );
1328 return new ScCellRangesObj( getDocShellFromRanges( rxCellRanges ), aScRanges );
1331 void lclExpandAndMerge( const uno::Reference< table::XCellRange >& rxCellRange, bool bMerge ) throw (uno::RuntimeException)
1333 uno::Reference< util::XMergeable > xMerge( lclExpandToMerged( rxCellRange, true ), uno::UNO_QUERY_THROW );
1334 // Calc cannot merge over merged ranges, always unmerge first
1335 xMerge->merge( false );
1336 if( bMerge )
1338 // clear all contents of the covered cells (not the top-left cell)
1339 table::CellRangeAddress aRangeAddr = lclGetRangeAddress( rxCellRange );
1340 sal_Int32 nLastColIdx = aRangeAddr.EndColumn - aRangeAddr.StartColumn;
1341 sal_Int32 nLastRowIdx = aRangeAddr.EndRow - aRangeAddr.StartRow;
1342 // clear cells of top row, right of top-left cell
1343 if( nLastColIdx > 0 )
1344 lclClearRange( rxCellRange->getCellRangeByPosition( 1, 0, nLastColIdx, 0 ) );
1345 // clear all rows below top row
1346 if( nLastRowIdx > 0 )
1347 lclClearRange( rxCellRange->getCellRangeByPosition( 0, 1, nLastColIdx, nLastRowIdx ) );
1348 // merge the range
1349 xMerge->merge( sal_True );
1353 util::TriState lclGetMergedState( const uno::Reference< table::XCellRange >& rxCellRange ) throw (uno::RuntimeException)
1355 /* 1) Check if range is completely inside one single merged range. To do
1356 this, try to extend from top-left cell only (not from entire range).
1357 This will exclude cases where this range consists of several merged
1358 ranges (or parts of them). */
1359 table::CellRangeAddress aRangeAddr = lclGetRangeAddress( rxCellRange );
1360 uno::Reference< table::XCellRange > xTopLeft( rxCellRange->getCellRangeByPosition( 0, 0, 0, 0 ), uno::UNO_SET_THROW );
1361 uno::Reference< sheet::XSheetCellRange > xExpanded( lclExpandToMerged( xTopLeft, false ), uno::UNO_SET_THROW );
1362 table::CellRangeAddress aExpAddr = lclGetRangeAddress( xExpanded );
1363 // check that expanded range has more than one cell (really merged)
1364 if( ((aExpAddr.StartColumn < aExpAddr.EndColumn) || (aExpAddr.StartRow < aExpAddr.EndRow)) && ScUnoConversion::Contains( aExpAddr, aRangeAddr ) )
1365 return util::TriState_YES;
1367 /* 2) Check if this range contains any merged cells (completely or
1368 partly). This seems to be hardly possible via API, as
1369 XMergeable::getIsMerged() returns only true, if the top-left cell of a
1370 merged range is part of this range, so cases where just the lower part
1371 of a merged range is part of this range are not covered. */
1372 ScRange aScRange;
1373 ScUnoConversion::FillScRange( aScRange, aRangeAddr );
1374 bool bHasMerged = getDocumentFromRange( rxCellRange )->HasAttrib( aScRange, HASATTR_MERGED | HASATTR_OVERLAPPED );
1375 return bHasMerged ? util::TriState_INDETERMINATE : util::TriState_NO;
1378 } // namespace
1380 // ----------------------------------------------------------------------------
1382 css::uno::Reference< excel::XRange >
1383 ScVbaRange::getRangeObjectForName(
1384 const uno::Reference< uno::XComponentContext >& xContext, const OUString& sRangeName,
1385 ScDocShell* pDocSh, formula::FormulaGrammar::AddressConvention eConv ) throw ( uno::RuntimeException )
1387 table::CellRangeAddress refAddr;
1388 return getRangeForName( xContext, sRangeName, pDocSh, refAddr, eConv );
1391 table::CellRangeAddress getCellRangeAddressForVBARange( const uno::Any& aParam, ScDocShell* pDocSh, formula::FormulaGrammar::AddressConvention aConv = formula::FormulaGrammar::CONV_XL_A1) throw ( uno::RuntimeException )
1393 uno::Reference< table::XCellRange > xRangeParam;
1394 switch ( aParam.getValueTypeClass() )
1396 case uno::TypeClass_STRING:
1398 OUString rString;
1399 aParam >>= rString;
1400 ScRangeList aCellRanges;
1401 ScRange refRange;
1402 if ( getScRangeListForAddress ( rString, pDocSh, refRange, aCellRanges, aConv ) )
1404 if ( aCellRanges.size() == 1 )
1406 table::CellRangeAddress aRangeAddress;
1407 ScUnoConversion::FillApiRange( aRangeAddress, *aCellRanges.front() );
1408 return aRangeAddress;
1412 case uno::TypeClass_INTERFACE:
1414 uno::Reference< excel::XRange > xRange;
1415 aParam >>= xRange;
1416 if ( xRange.is() )
1417 xRange->getCellRange() >>= xRangeParam;
1418 break;
1420 default:
1421 throw uno::RuntimeException( OUString( "Can't extact CellRangeAddress from type" ), uno::Reference< uno::XInterface >() );
1423 return lclGetRangeAddress( xRangeParam );
1426 static uno::Reference< XCollection >
1427 lcl_setupBorders( const uno::Reference< excel::XRange >& xParentRange, const uno::Reference<uno::XComponentContext>& xContext, const uno::Reference< table::XCellRange >& xRange ) throw( uno::RuntimeException )
1429 uno::Reference< XHelperInterface > xParent( xParentRange, uno::UNO_QUERY_THROW );
1430 ScDocument* pDoc = getDocumentFromRange(xRange);
1431 if ( !pDoc )
1432 throw uno::RuntimeException( OUString( "Failed to access document from shell" ), uno::Reference< uno::XInterface >() );
1433 ScVbaPalette aPalette( pDoc->GetDocumentShell() );
1434 uno::Reference< XCollection > borders( new ScVbaBorders( xParent, xContext, xRange, aPalette ) );
1435 return borders;
1438 ScVbaRange::ScVbaRange( uno::Sequence< uno::Any> const & args,
1439 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( false ), mbIsColumns( false )
1441 mxRange.set( mxPropertySet, uno::UNO_QUERY );
1442 mxRanges.set( mxPropertySet, uno::UNO_QUERY );
1443 uno::Reference< container::XIndexAccess > xIndex;
1444 if ( mxRange.is() )
1446 xIndex = new SingleRangeIndexAccess( mxParent, mxContext, mxRange );
1448 else if ( mxRanges.is() )
1450 xIndex.set( mxRanges, uno::UNO_QUERY_THROW );
1452 m_Areas = new ScVbaRangeAreas( mxParent, mxContext, xIndex, mbIsRows, mbIsColumns );
1455 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 )
1456 : ScVbaRange_BASE( xParent, xContext, uno::Reference< beans::XPropertySet >( xRange, uno::UNO_QUERY_THROW ), getModelFromRange( xRange), true ), mxRange( xRange ),
1457 mbIsRows( bIsRows ),
1458 mbIsColumns( bIsColumns )
1460 if ( !xContext.is() )
1461 throw lang::IllegalArgumentException( OUString( "context is not set " ), uno::Reference< uno::XInterface >() , 1 );
1462 if ( !xRange.is() )
1463 throw lang::IllegalArgumentException( OUString( "range is not set " ), uno::Reference< uno::XInterface >() , 1 );
1465 uno::Reference< container::XIndexAccess > xIndex( new SingleRangeIndexAccess( mxParent, mxContext, xRange ) );
1466 m_Areas = new ScVbaRangeAreas( mxParent, mxContext, xIndex, mbIsRows, mbIsColumns );
1470 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 )
1471 : 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 )
1474 uno::Reference< container::XIndexAccess > xIndex( mxRanges, uno::UNO_QUERY_THROW );
1475 m_Areas = new ScVbaRangeAreas( xParent, mxContext, xIndex, mbIsRows, mbIsColumns );
1479 ScVbaRange::~ScVbaRange()
1483 uno::Reference< XCollection >& ScVbaRange::getBorders()
1485 if ( !m_Borders.is() )
1487 uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny( sal_Int32(1) ), uno::Any() ), uno::UNO_QUERY_THROW );
1488 m_Borders = lcl_setupBorders( this, mxContext, uno::Reference< table::XCellRange >( xRange->getCellRange(), uno::UNO_QUERY_THROW ) );
1490 return m_Borders;
1493 void
1494 ScVbaRange::visitArray( ArrayVisitor& visitor )
1496 table::CellRangeAddress aRangeAddr = lclGetRangeAddress( mxRange );
1497 sal_Int32 nRowCount = aRangeAddr.EndRow - aRangeAddr.StartRow + 1;
1498 sal_Int32 nColCount = aRangeAddr.EndColumn - aRangeAddr.StartColumn + 1;
1499 for ( sal_Int32 i=0; i<nRowCount; ++i )
1501 for ( sal_Int32 j=0; j<nColCount; ++j )
1503 uno::Reference< table::XCell > xCell( mxRange->getCellByPosition( j, i ), uno::UNO_QUERY_THROW );
1505 visitor.visitNode( i, j, xCell );
1510 uno::Any
1511 ScVbaRange::getValue( ValueGetter& valueGetter) throw (uno::RuntimeException)
1513 uno::Reference< table::XColumnRowRange > xColumnRowRange(mxRange, uno::UNO_QUERY_THROW );
1514 // single cell range
1515 if ( isSingleCellRange() )
1517 visitArray( valueGetter );
1518 return valueGetter.getValue();
1520 sal_Int32 nRowCount = xColumnRowRange->getRows()->getCount();
1521 sal_Int32 nColCount = xColumnRowRange->getColumns()->getCount();
1522 // multi cell range ( return array )
1523 Dim2ArrayValueGetter arrayGetter( nRowCount, nColCount, valueGetter );
1524 visitArray( arrayGetter );
1525 return uno::makeAny( script::ArrayWrapper( false, arrayGetter.getValue() ) );
1528 uno::Any SAL_CALL
1529 ScVbaRange::getValue() throw (uno::RuntimeException)
1531 // #TODO code within the test below "if ( m_Areas.... " can be removed
1532 // Test is performed only because m_xRange is NOT set to be
1533 // the first range in m_Areas ( to force failure while
1534 // the implementations for each method are being updated )
1535 if ( m_Areas->getCount() > 1 )
1537 uno::Reference< excel::XRange > xRange( getArea( 0 ), uno::UNO_QUERY_THROW );
1538 return xRange->getValue();
1541 CellValueGetter valueGetter;
1542 return getValue( valueGetter );
1547 void
1548 ScVbaRange::setValue( const uno::Any& aValue, ValueSetter& valueSetter, bool bFireEvent ) throw (uno::RuntimeException)
1550 uno::TypeClass aClass = aValue.getValueTypeClass();
1551 if ( aClass == uno::TypeClass_SEQUENCE )
1553 uno::Reference< script::XTypeConverter > xConverter = getTypeConverter( mxContext );
1554 uno::Any aConverted;
1557 // test for single dimension, could do
1558 // with a better test than this
1559 if ( aValue.getValueTypeName().indexOf('[') == aValue.getValueTypeName().lastIndexOf('[') )
1561 aConverted = xConverter->convertTo( aValue, getCppuType((uno::Sequence< uno::Any >*)0) );
1562 Dim1ArrayValueSetter setter( aConverted, valueSetter );
1563 visitArray( setter );
1565 else
1567 aConverted = xConverter->convertTo( aValue, getCppuType((uno::Sequence< uno::Sequence< uno::Any > >*)0) );
1568 Dim2ArrayValueSetter setter( aConverted, valueSetter );
1569 visitArray( setter );
1572 catch ( const uno::Exception& e )
1574 OSL_TRACE("Bahhh, caught exception %s",
1575 OUStringToOString( e.Message,
1576 RTL_TEXTENCODING_UTF8 ).getStr() );
1579 else
1581 visitArray( valueSetter );
1583 if( bFireEvent ) fireChangeEvent();
1586 void SAL_CALL
1587 ScVbaRange::setValue( const uno::Any &aValue ) throw (uno::RuntimeException)
1589 // If this is a multiple selection apply setValue over all areas
1590 if ( m_Areas->getCount() > 1 )
1592 AreasVisitor aVisitor( m_Areas );
1593 RangeValueProcessor valueProcessor( aValue );
1594 aVisitor.visit( valueProcessor );
1595 return;
1597 CellValueSetter valueSetter( aValue );
1598 setValue( aValue, valueSetter, true );
1601 void SAL_CALL
1602 ScVbaRange::Clear() throw (uno::RuntimeException)
1604 using namespace ::com::sun::star::sheet::CellFlags;
1605 sal_Int32 nFlags = VALUE | DATETIME | STRING | FORMULA | HARDATTR | EDITATTR | FORMATTED;
1606 ClearContents( nFlags, true );
1609 //helper ClearContent
1610 void
1611 ScVbaRange::ClearContents( sal_Int32 nFlags, bool bFireEvent ) throw (uno::RuntimeException)
1613 // #TODO code within the test below "if ( m_Areas.... " can be removed
1614 // Test is performed only because m_xRange is NOT set to be
1615 // the first range in m_Areas ( to force failure while
1616 // the implementations for each method are being updated )
1617 if ( m_Areas->getCount() > 1 )
1619 sal_Int32 nItems = m_Areas->getCount();
1620 for ( sal_Int32 index=1; index <= nItems; ++index )
1622 uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny(index), uno::Any() ), uno::UNO_QUERY_THROW );
1623 ScVbaRange* pRange = getImplementation( xRange );
1624 if ( pRange )
1625 pRange->ClearContents( nFlags, false ); // do not fire for single ranges
1627 // fire change event for the entire range list
1628 if( bFireEvent ) fireChangeEvent();
1629 return;
1633 uno::Reference< sheet::XSheetOperation > xSheetOperation(mxRange, uno::UNO_QUERY_THROW);
1634 xSheetOperation->clearContents( nFlags );
1635 if( bFireEvent ) fireChangeEvent();
1638 void SAL_CALL
1639 ScVbaRange::ClearComments() throw (uno::RuntimeException)
1641 ClearContents( sheet::CellFlags::ANNOTATION, false );
1644 void SAL_CALL
1645 ScVbaRange::ClearContents() throw (uno::RuntimeException)
1647 using namespace ::com::sun::star::sheet::CellFlags;
1648 sal_Int32 nFlags = VALUE | DATETIME | STRING | FORMULA;
1649 ClearContents( nFlags, true );
1652 void SAL_CALL
1653 ScVbaRange::ClearFormats() throw (uno::RuntimeException)
1655 // FIXME: need to check if we need to combine FORMATTED
1656 using namespace ::com::sun::star::sheet::CellFlags;
1657 sal_Int32 nFlags = HARDATTR | FORMATTED | EDITATTR;
1658 ClearContents( nFlags, false );
1661 void
1662 ScVbaRange::setFormulaValue( const uno::Any& rFormula, formula::FormulaGrammar::Grammar eGram, bool bFireEvent ) throw (uno::RuntimeException)
1664 // If this is a multiple selection apply setFormula over all areas
1665 if ( m_Areas->getCount() > 1 )
1667 AreasVisitor aVisitor( m_Areas );
1668 RangeFormulaProcessor valueProcessor( rFormula );
1669 aVisitor.visit( valueProcessor );
1670 return;
1672 CellFormulaValueSetter formulaValueSetter( rFormula, getScDocument(), eGram );
1673 setValue( rFormula, formulaValueSetter, bFireEvent );
1676 uno::Any
1677 ScVbaRange::getFormulaValue( formula::FormulaGrammar::Grammar eGram ) throw (uno::RuntimeException)
1679 // #TODO code within the test below "if ( m_Areas.... " can be removed
1680 // Test is performed only because m_xRange is NOT set to be
1681 // the first range in m_Areas ( to force failure while
1682 // the implementations for each method are being updated )
1683 if ( m_Areas->getCount() > 1 )
1685 uno::Reference< excel::XRange > xRange( getArea( 0 ), uno::UNO_QUERY_THROW );
1686 return xRange->getFormula();
1688 CellFormulaValueGetter valueGetter( getScDocument(), eGram );
1689 return getValue( valueGetter );
1693 void
1694 ScVbaRange::setFormula(const uno::Any &rFormula ) throw (uno::RuntimeException)
1696 // #FIXME converting "=$a$1" e.g. CONV_XL_A1 -> CONV_OOO // results in "=$a$1:a1", temporalily disable conversion
1697 setFormulaValue( rFormula,formula::FormulaGrammar::GRAM_NATIVE_XL_A1, true );
1700 uno::Any
1701 ScVbaRange::getFormulaR1C1() throw (::com::sun::star::uno::RuntimeException)
1703 return getFormulaValue( formula::FormulaGrammar::GRAM_NATIVE_XL_R1C1 );
1706 void
1707 ScVbaRange::setFormulaR1C1(const uno::Any& rFormula ) throw (uno::RuntimeException)
1709 setFormulaValue( rFormula,formula::FormulaGrammar::GRAM_NATIVE_XL_R1C1, true );
1712 uno::Any
1713 ScVbaRange::getFormula() throw (::com::sun::star::uno::RuntimeException)
1715 return getFormulaValue( formula::FormulaGrammar::GRAM_NATIVE_XL_A1 );
1718 sal_Int32
1719 ScVbaRange::getCount() throw (uno::RuntimeException)
1721 // If this is a multiple selection apply setValue over all areas
1722 if ( m_Areas->getCount() > 1 )
1724 AreasVisitor aVisitor( m_Areas );
1725 RangeCountProcessor valueProcessor;
1726 aVisitor.visit( valueProcessor );
1727 return valueProcessor.value();
1729 sal_Int32 rowCount = 0;
1730 sal_Int32 colCount = 0;
1731 uno::Reference< table::XColumnRowRange > xColumnRowRange(mxRange, uno::UNO_QUERY_THROW );
1732 rowCount = xColumnRowRange->getRows()->getCount();
1733 colCount = xColumnRowRange->getColumns()->getCount();
1735 if( IsRows() )
1736 return rowCount;
1737 if( IsColumns() )
1738 return colCount;
1739 return rowCount * colCount;
1742 sal_Int32
1743 ScVbaRange::getRow() throw (uno::RuntimeException)
1745 // #TODO code within the test below "if ( m_Areas.... " can be removed
1746 // Test is performed only because m_xRange is NOT set to be
1747 // the first range in m_Areas ( to force failure while
1748 // the implementations for each method are being updated )
1749 if ( m_Areas->getCount() > 1 )
1751 uno::Reference< excel::XRange > xRange( getArea( 0 ), uno::UNO_QUERY_THROW );
1752 return xRange->getRow();
1754 uno::Reference< sheet::XCellAddressable > xCellAddressable(mxRange->getCellByPosition(0, 0), uno::UNO_QUERY_THROW );
1755 return xCellAddressable->getCellAddress().Row + 1; // Zero value indexing
1758 sal_Int32
1759 ScVbaRange::getColumn() 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 )
1767 uno::Reference< excel::XRange > xRange( getArea( 0 ), uno::UNO_QUERY_THROW );
1768 return xRange->getColumn();
1770 uno::Reference< sheet::XCellAddressable > xCellAddressable(mxRange->getCellByPosition(0, 0), uno::UNO_QUERY_THROW );
1771 return xCellAddressable->getCellAddress().Column + 1; // Zero value indexing
1774 uno::Any
1775 ScVbaRange::HasFormula() throw (uno::RuntimeException)
1777 if ( m_Areas->getCount() > 1 )
1779 sal_Int32 nItems = m_Areas->getCount();
1780 uno::Any aResult = aNULL();
1781 for ( sal_Int32 index=1; index <= nItems; ++index )
1783 uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny(index), uno::Any() ), uno::UNO_QUERY_THROW );
1784 // if the HasFormula for any area is different to another
1785 // return null
1786 if ( index > 1 )
1787 if ( aResult != xRange->HasFormula() )
1788 return aNULL();
1789 aResult = xRange->HasFormula();
1790 if ( aNULL() == aResult )
1791 return aNULL();
1793 return aResult;
1795 uno::Reference< uno::XInterface > xIf( mxRange, uno::UNO_QUERY_THROW );
1796 ScCellRangesBase* pThisRanges = dynamic_cast< ScCellRangesBase * > ( xIf.get() );
1797 if ( pThisRanges )
1799 uno::Reference<uno::XInterface> xRanges( pThisRanges->queryFormulaCells( ( sheet::FormulaResult::ERROR | sheet::FormulaResult::VALUE | sheet::FormulaResult::STRING ) ), uno::UNO_QUERY_THROW );
1800 ScCellRangesBase* pFormulaRanges = dynamic_cast< ScCellRangesBase * > ( xRanges.get() );
1801 // check if there are no formula cell, return false
1802 if ( pFormulaRanges->GetRangeList().empty() )
1803 return uno::makeAny(sal_False);
1805 // chech if there are holes (where some cells are not formulas)
1806 // or returned range is not equal to this range
1807 if ( ( pFormulaRanges->GetRangeList().size() > 1 )
1808 || ( pFormulaRanges->GetRangeList().front()->aStart != pThisRanges->GetRangeList().front()->aStart )
1809 || ( pFormulaRanges->GetRangeList().front()->aEnd != pThisRanges->GetRangeList().front()->aEnd )
1811 return aNULL(); // should return aNULL;
1813 return uno::makeAny( sal_True );
1815 void
1816 ScVbaRange::fillSeries( sheet::FillDirection nFillDirection, sheet::FillMode nFillMode, sheet::FillDateMode nFillDateMode, double fStep, double fEndValue ) throw( uno::RuntimeException )
1818 if ( m_Areas->getCount() > 1 )
1820 // Multi-Area Range
1821 uno::Reference< XCollection > xCollection( m_Areas, uno::UNO_QUERY_THROW );
1822 for ( sal_Int32 index = 1; index <= xCollection->getCount(); ++index )
1824 uno::Reference< excel::XRange > xRange( xCollection->Item( uno::makeAny( index ), uno::Any() ), uno::UNO_QUERY_THROW );
1825 ScVbaRange* pThisRange = getImplementation( xRange );
1826 pThisRange->fillSeries( nFillDirection, nFillMode, nFillDateMode, fStep, fEndValue );
1829 return;
1832 uno::Reference< sheet::XCellSeries > xCellSeries(mxRange, uno::UNO_QUERY_THROW );
1833 xCellSeries->fillSeries( nFillDirection, nFillMode, nFillDateMode, fStep, fEndValue );
1836 void
1837 ScVbaRange::FillLeft() throw (uno::RuntimeException)
1839 fillSeries(sheet::FillDirection_TO_LEFT,
1840 sheet::FillMode_SIMPLE, sheet::FillDateMode_FILL_DATE_DAY, 0, 0x7FFFFFFF);
1843 void
1844 ScVbaRange::FillRight() throw (uno::RuntimeException)
1846 fillSeries(sheet::FillDirection_TO_RIGHT,
1847 sheet::FillMode_SIMPLE, sheet::FillDateMode_FILL_DATE_DAY, 0, 0x7FFFFFFF);
1850 void
1851 ScVbaRange::FillUp() throw (uno::RuntimeException)
1853 fillSeries(sheet::FillDirection_TO_TOP,
1854 sheet::FillMode_SIMPLE, sheet::FillDateMode_FILL_DATE_DAY, 0, 0x7FFFFFFF);
1857 void
1858 ScVbaRange::FillDown() throw (uno::RuntimeException)
1860 fillSeries(sheet::FillDirection_TO_BOTTOM,
1861 sheet::FillMode_SIMPLE, sheet::FillDateMode_FILL_DATE_DAY, 0, 0x7FFFFFFF);
1864 OUString
1865 ScVbaRange::getText() throw (uno::RuntimeException)
1867 // #TODO code within the test below "if ( m_Areas.... " can be removed
1868 // Test is performed only because m_xRange is NOT set to be
1869 // the first range in m_Areas ( to force failure while
1870 // the implementations for each method are being updated )
1871 if ( m_Areas->getCount() > 1 )
1873 uno::Reference< excel::XRange > xRange( getArea( 0 ), uno::UNO_QUERY_THROW );
1874 return xRange->getText();
1876 uno::Reference< text::XTextRange > xTextRange(mxRange->getCellByPosition(0,0), uno::UNO_QUERY_THROW );
1877 return xTextRange->getString();
1880 uno::Reference< excel::XRange >
1881 ScVbaRange::Offset( const ::uno::Any &nRowOff, const uno::Any &nColOff ) throw (uno::RuntimeException)
1883 SCROW nRowOffset = 0;
1884 SCCOL nColOffset = 0;
1885 sal_Bool bIsRowOffset = ( nRowOff >>= nRowOffset );
1886 sal_Bool bIsColumnOffset = ( nColOff >>= nColOffset );
1887 ScCellRangesBase* pUnoRangesBase = getCellRangesBase();
1889 ScRangeList aCellRanges = pUnoRangesBase->GetRangeList();
1892 for ( size_t i = 0, nRanges = aCellRanges.size(); i < nRanges; ++i )
1894 ScRange* pRange = aCellRanges[ i ];
1895 if ( bIsColumnOffset )
1897 pRange->aStart.SetCol( pRange->aStart.Col() + nColOffset );
1898 pRange->aEnd.SetCol( pRange->aEnd.Col() + nColOffset );
1900 if ( bIsRowOffset )
1902 pRange->aStart.SetRow( pRange->aStart.Row() + nRowOffset );
1903 pRange->aEnd.SetRow( pRange->aEnd.Row() + nRowOffset );
1907 if ( aCellRanges.size() > 1 ) // Multi-Area
1909 uno::Reference< sheet::XSheetCellRangeContainer > xRanges( new ScCellRangesObj( pUnoRangesBase->GetDocShell(), aCellRanges ) );
1910 return new ScVbaRange( mxParent, mxContext, xRanges );
1912 // normal range
1913 uno::Reference< table::XCellRange > xRange( new ScCellRangeObj( pUnoRangesBase->GetDocShell(), *aCellRanges.front() ) );
1914 return new ScVbaRange( mxParent, mxContext, xRange );
1917 uno::Reference< excel::XRange >
1918 ScVbaRange::CurrentRegion() throw (uno::RuntimeException)
1920 // #TODO code within the test below "if ( m_Areas.... " can be removed
1921 // Test is performed only because m_xRange is NOT set to be
1922 // the first range in m_Areas ( to force failure while
1923 // the implementations for each method are being updated )
1924 if ( m_Areas->getCount() > 1 )
1926 uno::Reference< excel::XRange > xRange( getArea( 0 ), uno::UNO_QUERY_THROW );
1927 return xRange->CurrentRegion();
1930 RangeHelper helper( mxRange );
1931 uno::Reference< sheet::XSheetCellCursor > xSheetCellCursor =
1932 helper.getSheetCellCursor();
1933 xSheetCellCursor->collapseToCurrentRegion();
1934 uno::Reference< sheet::XCellRangeAddressable > xCellRangeAddressable(xSheetCellCursor, uno::UNO_QUERY_THROW);
1935 return RangeHelper::createRangeFromRange( mxParent, mxContext, helper.getCellRangeFromSheet(), xCellRangeAddressable );
1938 uno::Reference< excel::XRange >
1939 ScVbaRange::CurrentArray() throw (uno::RuntimeException)
1941 // #TODO code within the test below "if ( m_Areas.... " can be removed
1942 // Test is performed only because m_xRange is NOT set to be
1943 // the first range in m_Areas ( to force failure while
1944 // the implementations for each method are being updated )
1945 if ( m_Areas->getCount() > 1 )
1947 uno::Reference< excel::XRange > xRange( getArea( 0 ), uno::UNO_QUERY_THROW );
1948 return xRange->CurrentArray();
1950 RangeHelper helper( mxRange );
1951 uno::Reference< sheet::XSheetCellCursor > xSheetCellCursor =
1952 helper.getSheetCellCursor();
1953 xSheetCellCursor->collapseToCurrentArray();
1954 uno::Reference< sheet::XCellRangeAddressable > xCellRangeAddressable(xSheetCellCursor, uno::UNO_QUERY_THROW);
1955 return RangeHelper::createRangeFromRange( mxParent, mxContext, helper.getCellRangeFromSheet(), xCellRangeAddressable );
1958 uno::Any
1959 ScVbaRange::getFormulaArray() throw (uno::RuntimeException)
1961 // #TODO code within the test below "if ( m_Areas.... " can be removed
1962 // Test is performed only because m_xRange is NOT set to be
1963 // the first range in m_Areas ( to force failure while
1964 // the implementations for each method are being updated )
1965 if ( m_Areas->getCount() > 1 )
1967 uno::Reference< excel::XRange > xRange( getArea( 0 ), uno::UNO_QUERY_THROW );
1968 return xRange->getFormulaArray();
1971 uno::Reference< sheet::XCellRangeFormula> xCellRangeFormula( mxRange, uno::UNO_QUERY_THROW );
1972 uno::Reference< script::XTypeConverter > xConverter = getTypeConverter( mxContext );
1973 uno::Any aSingleValueOrMatrix;
1974 // When dealing with a single element ( embedded in the sequence of sequence ) unwrap and return
1975 // that value
1976 uno::Sequence< uno::Sequence<rtl::OUString> > aTmpSeq = xCellRangeFormula->getFormulaArray();
1977 if ( aTmpSeq.getLength() == 1 )
1979 if ( aTmpSeq[ 0 ].getLength() == 1 )
1980 aSingleValueOrMatrix <<= aTmpSeq[ 0 ][ 0 ];
1982 else
1983 aSingleValueOrMatrix = xConverter->convertTo( uno::makeAny( aTmpSeq ) , getCppuType((uno::Sequence< uno::Sequence< uno::Any > >*)0) ) ;
1984 return aSingleValueOrMatrix;
1987 void
1988 ScVbaRange::setFormulaArray(const uno::Any& rFormula) throw (uno::RuntimeException)
1990 // #TODO code within the test below "if ( m_Areas.... " can be removed
1991 // Test is performed only because m_xRange is NOT set to be
1992 // the first range in m_Areas ( to force failure while
1993 // the implementations for each method are being updated )
1994 if ( m_Areas->getCount() > 1 )
1996 uno::Reference< excel::XRange > xRange( getArea( 0 ), uno::UNO_QUERY_THROW );
1997 return xRange->setFormulaArray( rFormula );
1999 // #TODO need to distinguish between getFormula and getFormulaArray e.g. (R1C1)
2000 // but for the moment its just easier to treat them the same for setting
2002 setFormula( rFormula );
2005 OUString
2006 ScVbaRange::Characters(const uno::Any& Start, const uno::Any& Length) throw (uno::RuntimeException)
2008 // #TODO code within the test below "if ( m_Areas.... " can be removed
2009 // Test is performed only because m_xRange is NOT set to be
2010 // the first range in m_Areas ( to force failure while
2011 // the implementations for each method are being updated )
2012 if ( m_Areas->getCount() > 1 )
2014 uno::Reference< excel::XRange > xRange( getArea( 0 ), uno::UNO_QUERY_THROW );
2015 return xRange->Characters( Start, Length );
2018 long nIndex = 0, nCount = 0;
2019 OUString rString;
2020 uno::Reference< text::XTextRange > xTextRange(mxRange, ::uno::UNO_QUERY_THROW );
2021 rString = xTextRange->getString();
2022 if( !( Start >>= nIndex ) && !( Length >>= nCount ) )
2023 return rString;
2024 if(!( Start >>= nIndex ) )
2025 nIndex = 1;
2026 if(!( Length >>= nCount ) )
2027 nIndex = rString.getLength();
2028 return rString.copy( --nIndex, nCount ); // Zero value indexing
2031 OUString
2032 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)
2034 if ( m_Areas->getCount() > 1 )
2036 // Multi-Area Range
2037 OUString sAddress;
2038 uno::Reference< XCollection > xCollection( m_Areas, uno::UNO_QUERY_THROW );
2039 uno::Any aExternalCopy = External;
2040 for ( sal_Int32 index = 1; index <= xCollection->getCount(); ++index )
2042 uno::Reference< excel::XRange > xRange( xCollection->Item( uno::makeAny( index ), uno::Any() ), uno::UNO_QUERY_THROW );
2043 if ( index > 1 )
2045 sAddress += OUString( ',' );
2046 // force external to be false
2047 // only first address should have the
2048 // document and sheet specifications
2049 aExternalCopy = uno::makeAny(sal_False);
2051 sAddress += xRange->Address( RowAbsolute, ColumnAbsolute, ReferenceStyle, aExternalCopy, RelativeTo );
2053 return sAddress;
2056 ScAddress::Details dDetails( formula::FormulaGrammar::CONV_XL_A1, 0, 0 );
2057 if ( ReferenceStyle.hasValue() )
2059 sal_Int32 refStyle = excel::XlReferenceStyle::xlA1;
2060 ReferenceStyle >>= refStyle;
2061 if ( refStyle == excel::XlReferenceStyle::xlR1C1 )
2062 dDetails = ScAddress::Details( formula::FormulaGrammar::CONV_XL_R1C1, 0, 0 );
2064 sal_uInt16 nFlags = SCA_VALID;
2065 ScDocShell* pDocShell = getScDocShell();
2066 ScDocument* pDoc = pDocShell->GetDocument();
2068 RangeHelper thisRange( mxRange );
2069 table::CellRangeAddress thisAddress = thisRange.getCellRangeAddressable()->getRangeAddress();
2070 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 ) );
2071 String sRange;
2072 sal_uInt16 ROW_ABSOLUTE = ( SCA_ROW_ABSOLUTE | SCA_ROW2_ABSOLUTE );
2073 sal_uInt16 COL_ABSOLUTE = ( SCA_COL_ABSOLUTE | SCA_COL2_ABSOLUTE );
2074 // default
2075 nFlags |= ( SCA_TAB_ABSOLUTE | SCA_COL_ABSOLUTE | SCA_ROW_ABSOLUTE | SCA_TAB2_ABSOLUTE | SCA_COL2_ABSOLUTE | SCA_ROW2_ABSOLUTE );
2076 if ( RowAbsolute.hasValue() )
2078 sal_Bool bVal = sal_True;
2079 RowAbsolute >>= bVal;
2080 if ( !bVal )
2081 nFlags &= ~ROW_ABSOLUTE;
2083 if ( ColumnAbsolute.hasValue() )
2085 sal_Bool bVal = sal_True;
2086 ColumnAbsolute >>= bVal;
2087 if ( !bVal )
2088 nFlags &= ~COL_ABSOLUTE;
2090 sal_Bool bLocal = false;
2091 if ( External.hasValue() )
2093 External >>= bLocal;
2094 if ( bLocal )
2095 nFlags |= SCA_TAB_3D | SCA_FORCE_DOC;
2097 if ( RelativeTo.hasValue() )
2099 // #TODO should I throw an error if R1C1 is not set?
2101 table::CellRangeAddress refAddress = getCellRangeAddressForVBARange( RelativeTo, pDocShell );
2102 dDetails = ScAddress::Details( formula::FormulaGrammar::CONV_XL_R1C1, static_cast< SCROW >( refAddress.StartRow ), static_cast< SCCOL >( refAddress.StartColumn ) );
2104 aRange.Format( sRange, nFlags, pDoc, dDetails );
2105 return sRange;
2108 uno::Reference < excel::XFont >
2109 ScVbaRange::Font() throw ( script::BasicErrorException, uno::RuntimeException)
2111 uno::Reference< beans::XPropertySet > xProps(mxRange, ::uno::UNO_QUERY );
2112 ScDocument* pDoc = getScDocument();
2113 if ( mxRange.is() )
2114 xProps.set(mxRange, ::uno::UNO_QUERY );
2115 else if ( mxRanges.is() )
2116 xProps.set(mxRanges, ::uno::UNO_QUERY );
2117 if ( !pDoc )
2118 throw uno::RuntimeException( OUString( "Failed to access document from shell" ), uno::Reference< uno::XInterface >() );
2120 ScVbaPalette aPalette( pDoc->GetDocumentShell() );
2121 ScCellRangeObj* pRangeObj = NULL;
2124 pRangeObj = getCellRangeObj();
2126 catch( uno::Exception& )
2129 return new ScVbaFont( this, mxContext, aPalette, xProps, pRangeObj );
2132 uno::Reference< excel::XRange >
2133 ScVbaRange::Cells( const uno::Any &nRowIndex, const uno::Any &nColumnIndex ) throw(uno::RuntimeException)
2135 // #TODO code within the test below "if ( m_Areas.... " can be removed
2136 // Test is performed only because m_xRange is NOT set to be
2137 // the first range in m_Areas ( to force failure while
2138 // the implementations for each method are being updated )
2139 if ( m_Areas->getCount() > 1 )
2141 uno::Reference< excel::XRange > xRange( getArea( 0 ), uno::UNO_QUERY_THROW );
2142 return xRange->Cells( nRowIndex, nColumnIndex );
2145 // Performance: Use a common helper method for ScVbaRange::Cells and ScVbaWorksheet::Cells,
2146 // instead of creating a new ScVbaRange object in often-called ScVbaWorksheet::Cells
2147 return CellsHelper( mxParent, mxContext, mxRange, nRowIndex, nColumnIndex );
2150 // static
2151 uno::Reference< excel::XRange >
2152 ScVbaRange::CellsHelper( const uno::Reference< ov::XHelperInterface >& xParent,
2153 const uno::Reference< uno::XComponentContext >& xContext,
2154 const uno::Reference< css::table::XCellRange >& xRange,
2155 const uno::Any &nRowIndex, const uno::Any &nColumnIndex ) throw(uno::RuntimeException)
2157 sal_Int32 nRow = 0, nColumn = 0;
2159 sal_Bool bIsIndex = nRowIndex.hasValue();
2160 sal_Bool bIsColumnIndex = nColumnIndex.hasValue();
2162 // Sometimes we might get a float or a double or whatever
2163 // set in the Any, we should convert as appropriate
2164 // #FIXME - perhaps worth turning this into some sort of
2165 // convertion routine e.g. bSuccess = getValueFromAny( nRow, nRowIndex, getCppuType((sal_Int32*)0) )
2166 uno::Any aRowIndexAny = nRowIndex;
2167 if ( aRowIndexAny.hasValue() && !( aRowIndexAny >>= nRow ) )
2169 uno::Reference< script::XTypeConverter > xConverter = getTypeConverter( xContext );
2170 uno::Any aConverted;
2173 aConverted = xConverter->convertTo( aRowIndexAny, getCppuType((sal_Int32*)0) );
2174 bIsIndex = ( aConverted >>= nRow );
2176 catch( uno::Exception& ) {} // silence any errors
2179 uno::Any aColumnAny = nColumnIndex;
2181 if ( bIsColumnIndex )
2183 // Column index can be a col address e.g Cells( 1, "B" ) etc.
2184 OUString sCol;
2185 if ( nColumnIndex >>= sCol )
2187 ScAddress::Details dDetails( formula::FormulaGrammar::CONV_XL_A1, 0, 0 );
2188 ScRange tmpRange;
2189 sal_uInt16 flags = tmpRange.ParseCols( sCol, getDocumentFromRange( xRange ), dDetails );
2190 if ( ( flags & 0x200 ) != 0x200 )
2191 throw uno::RuntimeException();
2192 nColumn = tmpRange.aStart.Col() + 1;
2194 else
2196 if ( !( aColumnAny >>= nColumn ) )
2198 uno::Reference< script::XTypeConverter > xConverter = getTypeConverter( xContext );
2199 uno::Any aConverted;
2202 aConverted = xConverter->convertTo( aColumnAny, getCppuType((sal_Int32*)0) );
2203 bIsColumnIndex = ( aConverted >>= nColumn );
2205 catch( uno::Exception& ) {} // silence any errors
2209 RangeHelper thisRange( xRange );
2210 table::CellRangeAddress thisRangeAddress = thisRange.getCellRangeAddressable()->getRangeAddress();
2211 uno::Reference< table::XCellRange > xSheetRange = thisRange.getCellRangeFromSheet();
2212 if( !bIsIndex && !bIsColumnIndex ) // .Cells
2213 // #FIXE needs proper parent ( Worksheet )
2214 return uno::Reference< excel::XRange >( new ScVbaRange( xParent, xContext, xRange ) );
2216 sal_Int32 nIndex = --nRow;
2217 if( bIsIndex && !bIsColumnIndex ) // .Cells(n)
2219 uno::Reference< table::XColumnRowRange > xColumnRowRange(xRange, ::uno::UNO_QUERY_THROW);
2220 sal_Int32 nColCount = xColumnRowRange->getColumns()->getCount();
2222 if ( !nIndex || nIndex < 0 )
2223 nRow = 0;
2224 else
2225 nRow = nIndex / nColCount;
2226 nColumn = nIndex % nColCount;
2228 else
2229 --nColumn;
2230 nRow = nRow + thisRangeAddress.StartRow;
2231 nColumn = nColumn + thisRangeAddress.StartColumn;
2232 return new ScVbaRange( xParent, xContext, xSheetRange->getCellRangeByPosition( nColumn, nRow, nColumn, nRow ) );
2235 void
2236 ScVbaRange::Select() throw (uno::RuntimeException)
2238 ScCellRangesBase* pUnoRangesBase = getCellRangesBase();
2239 if ( !pUnoRangesBase )
2240 throw uno::RuntimeException( OUString( "Failed to access underlying uno range object" ), uno::Reference< uno::XInterface >() );
2241 ScDocShell* pShell = pUnoRangesBase->GetDocShell();
2242 if ( pShell )
2244 uno::Reference< frame::XModel > xModel( pShell->GetModel(), uno::UNO_QUERY_THROW );
2245 uno::Reference< view::XSelectionSupplier > xSelection( xModel->getCurrentController(), uno::UNO_QUERY_THROW );
2246 if ( mxRanges.is() )
2247 xSelection->select( uno::Any( lclExpandToMerged( mxRanges, true ) ) );
2248 else
2249 xSelection->select( uno::Any( lclExpandToMerged( mxRange, true ) ) );
2250 // set focus on document e.g.
2251 // ThisComponent.CurrentController.Frame.getContainerWindow.SetFocus
2254 uno::Reference< frame::XController > xController( xModel->getCurrentController(), uno::UNO_QUERY_THROW );
2255 uno::Reference< frame::XFrame > xFrame( xController->getFrame(), uno::UNO_QUERY_THROW );
2256 uno::Reference< awt::XWindow > xWin( xFrame->getContainerWindow(), uno::UNO_QUERY_THROW );
2257 xWin->setFocus();
2259 catch( uno::Exception& )
2265 bool cellInRange( const table::CellRangeAddress& rAddr, const sal_Int32& nCol, const sal_Int32& nRow )
2267 if ( nCol >= rAddr.StartColumn && nCol <= rAddr.EndColumn &&
2268 nRow >= rAddr.StartRow && nRow <= rAddr.EndRow )
2269 return true;
2270 return false;
2273 void setCursor( const SCCOL& nCol, const SCROW& nRow, const uno::Reference< frame::XModel >& xModel, bool bInSel = true )
2275 ScTabViewShell* pShell = excel::getBestViewShell( xModel );
2276 if ( pShell )
2278 if ( bInSel )
2279 pShell->SetCursor( nCol, nRow );
2280 else
2281 pShell->MoveCursorAbs( nCol, nRow, SC_FOLLOW_NONE, false, false, sal_True, false );
2285 void
2286 ScVbaRange::Activate() throw (uno::RuntimeException)
2288 // get first cell of current range
2289 uno::Reference< table::XCellRange > xCellRange;
2290 if ( mxRanges.is() )
2292 uno::Reference< container::XIndexAccess > xIndex( mxRanges, uno::UNO_QUERY_THROW );
2293 xCellRange.set( xIndex->getByIndex( 0 ), uno::UNO_QUERY_THROW );
2295 else
2296 xCellRange.set( mxRange, uno::UNO_QUERY_THROW );
2298 RangeHelper thisRange( xCellRange );
2299 uno::Reference< sheet::XCellRangeAddressable > xThisRangeAddress = thisRange.getCellRangeAddressable();
2300 table::CellRangeAddress thisRangeAddress = xThisRangeAddress->getRangeAddress();
2301 uno::Reference< frame::XModel > xModel;
2302 ScDocShell* pShell = getScDocShell();
2304 if ( pShell )
2305 xModel = pShell->GetModel();
2307 if ( !xModel.is() )
2308 throw uno::RuntimeException();
2310 // get current selection
2311 uno::Reference< sheet::XCellRangeAddressable > xRange( xModel->getCurrentSelection(), ::uno::UNO_QUERY);
2313 uno::Reference< sheet::XSheetCellRanges > xRanges( xModel->getCurrentSelection(), ::uno::UNO_QUERY);
2315 if ( xRanges.is() )
2317 uno::Sequence< table::CellRangeAddress > nAddrs = xRanges->getRangeAddresses();
2318 for ( sal_Int32 index = 0; index < nAddrs.getLength(); ++index )
2320 if ( cellInRange( nAddrs[index], thisRangeAddress.StartColumn, thisRangeAddress.StartRow ) )
2322 setCursor( static_cast< SCCOL >( thisRangeAddress.StartColumn ), static_cast< SCROW >( thisRangeAddress.StartRow ), xModel );
2323 return;
2329 if ( xRange.is() && cellInRange( xRange->getRangeAddress(), thisRangeAddress.StartColumn, thisRangeAddress.StartRow ) )
2330 setCursor( static_cast< SCCOL >( thisRangeAddress.StartColumn ), static_cast< SCROW >( thisRangeAddress.StartRow ), xModel );
2331 else
2333 // if this range is multi cell select the range other
2334 // wise just position the cell at this single range position
2335 if ( isSingleCellRange() )
2336 // This top-leftmost cell of this Range is not in the current
2337 // selection so just select this range
2338 setCursor( static_cast< SCCOL >( thisRangeAddress.StartColumn ), static_cast< SCROW >( thisRangeAddress.StartRow ), xModel, false );
2339 else
2340 Select();
2345 uno::Reference< excel::XRange >
2346 ScVbaRange::Rows(const uno::Any& aIndex ) throw (uno::RuntimeException)
2348 OUString sAddress;
2350 if ( aIndex.hasValue() )
2352 sal_Int32 nValue = 0;
2353 ScCellRangesBase* pUnoRangesBase = getCellRangesBase();
2354 ScRangeList aCellRanges = pUnoRangesBase->GetRangeList();
2356 ScRange aRange = *aCellRanges.front();
2357 if( aIndex >>= nValue )
2359 aRange.aStart.SetRow( aRange.aStart.Row() + --nValue );
2360 aRange.aEnd.SetRow( aRange.aStart.Row() );
2362 else if ( aIndex >>= sAddress )
2364 ScAddress::Details dDetails( formula::FormulaGrammar::CONV_XL_A1, 0, 0 );
2365 ScRange tmpRange;
2366 tmpRange.ParseRows( sAddress, getDocumentFromRange( mxRange ), dDetails );
2367 SCROW nStartRow = tmpRange.aStart.Row();
2368 SCROW nEndRow = tmpRange.aEnd.Row();
2370 aRange.aStart.SetRow( aRange.aStart.Row() + nStartRow );
2371 aRange.aEnd.SetRow( aRange.aStart.Row() + ( nEndRow - nStartRow ));
2373 else
2374 throw uno::RuntimeException( OUString( "Illegal param" ), uno::Reference< uno::XInterface >() );
2376 if ( aRange.aStart.Row() < 0 || aRange.aEnd.Row() < 0 )
2377 throw uno::RuntimeException( OUString("Internal failure, illegal param"), uno::Reference< uno::XInterface >() );
2378 // return a normal range ( even for multi-selection
2379 uno::Reference< table::XCellRange > xRange( new ScCellRangeObj( pUnoRangesBase->GetDocShell(), aRange ) );
2380 return new ScVbaRange( mxParent, mxContext, xRange, true );
2382 // Rows() - no params
2383 if ( m_Areas->getCount() > 1 )
2384 return new ScVbaRange( mxParent, mxContext, mxRanges, true );
2385 return new ScVbaRange( mxParent, mxContext, mxRange, true );
2388 uno::Reference< excel::XRange >
2389 ScVbaRange::Columns(const uno::Any& aIndex ) throw (uno::RuntimeException)
2391 OUString sAddress;
2393 ScCellRangesBase* pUnoRangesBase = getCellRangesBase();
2394 ScRangeList aCellRanges = pUnoRangesBase->GetRangeList();
2396 ScRange aRange = *aCellRanges.front();
2397 if ( aIndex.hasValue() )
2399 sal_Int32 nValue = 0;
2400 if ( aIndex >>= nValue )
2402 aRange.aStart.SetCol( aRange.aStart.Col() + static_cast< SCCOL > ( --nValue ) );
2403 aRange.aEnd.SetCol( aRange.aStart.Col() );
2406 else if ( aIndex >>= sAddress )
2408 ScAddress::Details dDetails( formula::FormulaGrammar::CONV_XL_A1, 0, 0 );
2409 ScRange tmpRange;
2410 tmpRange.ParseCols( sAddress, getDocumentFromRange( mxRange ), dDetails );
2411 SCCOL nStartCol = tmpRange.aStart.Col();
2412 SCCOL nEndCol = tmpRange.aEnd.Col();
2414 aRange.aStart.SetCol( aRange.aStart.Col() + nStartCol );
2415 aRange.aEnd.SetCol( aRange.aStart.Col() + ( nEndCol - nStartCol ));
2417 else
2418 throw uno::RuntimeException( OUString( "Illegal param" ), uno::Reference< uno::XInterface >() );
2420 if ( aRange.aStart.Col() < 0 || aRange.aEnd.Col() < 0 )
2421 throw uno::RuntimeException( OUString("Internal failure, illegal param"), uno::Reference< uno::XInterface >() );
2423 // Columns() - no params
2424 uno::Reference< table::XCellRange > xRange( new ScCellRangeObj( pUnoRangesBase->GetDocShell(), aRange ) );
2425 return new ScVbaRange( mxParent, mxContext, xRange, false, true );
2428 void
2429 ScVbaRange::setMergeCells( const uno::Any& aIsMerged ) throw (script::BasicErrorException, uno::RuntimeException)
2431 bool bMerge = extractBoolFromAny( aIsMerged );
2433 if( mxRanges.is() )
2435 sal_Int32 nCount = mxRanges->getCount();
2437 // VBA does nothing (no error) if the own ranges overlap somehow
2438 ::std::vector< table::CellRangeAddress > aList;
2439 for( sal_Int32 nIndex = 0; nIndex < nCount; ++nIndex )
2441 uno::Reference< sheet::XCellRangeAddressable > xRangeAddr( mxRanges->getByIndex( nIndex ), uno::UNO_QUERY_THROW );
2442 table::CellRangeAddress aAddress = xRangeAddr->getRangeAddress();
2443 for( ::std::vector< table::CellRangeAddress >::const_iterator aIt = aList.begin(), aEnd = aList.end(); aIt != aEnd; ++aIt )
2444 if( ScUnoConversion::Intersects( *aIt, aAddress ) )
2445 return;
2446 aList.push_back( aAddress );
2449 // (un)merge every range after it has been extended to intersecting merged ranges from sheet
2450 for( sal_Int32 nIndex = 0; nIndex < nCount; ++nIndex )
2452 uno::Reference< table::XCellRange > xRange( mxRanges->getByIndex( nIndex ), uno::UNO_QUERY_THROW );
2453 lclExpandAndMerge( xRange, bMerge );
2455 return;
2458 // otherwise, merge single range
2459 lclExpandAndMerge( mxRange, bMerge );
2462 uno::Any
2463 ScVbaRange::getMergeCells() throw (script::BasicErrorException, uno::RuntimeException)
2465 if( mxRanges.is() )
2467 sal_Int32 nCount = mxRanges->getCount();
2468 for( sal_Int32 nIndex = 0; nIndex < nCount; ++nIndex )
2470 uno::Reference< table::XCellRange > xRange( mxRanges->getByIndex( nIndex ), uno::UNO_QUERY_THROW );
2471 util::TriState eMerged = lclGetMergedState( xRange );
2472 /* Excel always returns NULL, if one range of the range list is
2473 partly or completely merged. Even if all ranges are completely
2474 merged, the return value is still NULL. */
2475 if( eMerged != util::TriState_NO )
2476 return aNULL();
2478 // no range is merged anyhow, return false
2479 return uno::Any( false );
2482 // otherwise, check single range
2483 switch( lclGetMergedState( mxRange ) )
2485 case util::TriState_YES: return uno::Any( true );
2486 case util::TriState_NO: return uno::Any( false );
2487 default: return aNULL();
2491 void
2492 ScVbaRange::Copy(const ::uno::Any& Destination) throw (uno::RuntimeException)
2494 if ( m_Areas->getCount() > 1 )
2495 throw uno::RuntimeException( OUString("That command cannot be used on multiple selections" ), uno::Reference< uno::XInterface >() );
2496 if ( Destination.hasValue() )
2498 uno::Reference< excel::XRange > xRange( Destination, uno::UNO_QUERY_THROW );
2499 uno::Any aRange = xRange->getCellRange();
2500 uno::Reference< table::XCellRange > xCellRange;
2501 aRange >>= xCellRange;
2502 uno::Reference< sheet::XSheetCellRange > xSheetCellRange(xCellRange, ::uno::UNO_QUERY_THROW);
2503 uno::Reference< sheet::XSpreadsheet > xSheet = xSheetCellRange->getSpreadsheet();
2504 uno::Reference< table::XCellRange > xDest( xSheet, uno::UNO_QUERY_THROW );
2505 uno::Reference< sheet::XCellRangeMovement > xMover( xSheet, uno::UNO_QUERY_THROW);
2506 uno::Reference< sheet::XCellAddressable > xDestination( xDest->getCellByPosition(
2507 xRange->getColumn()-1,xRange->getRow()-1), uno::UNO_QUERY_THROW );
2508 uno::Reference< sheet::XCellRangeAddressable > xSource( mxRange, uno::UNO_QUERY);
2509 xMover->copyRange( xDestination->getCellAddress(), xSource->getRangeAddress() );
2510 if ( ScVbaRange* pRange = getImplementation( xRange ) )
2511 pRange->fireChangeEvent();
2513 else
2515 uno::Reference< frame::XModel > xModel = getModelFromRange( mxRange );
2516 Select();
2517 excel::implnCopy( xModel );
2521 void
2522 ScVbaRange::Cut(const ::uno::Any& Destination) throw (uno::RuntimeException)
2524 if ( m_Areas->getCount() > 1 )
2525 throw uno::RuntimeException( OUString( "That command cannot be used on multiple selections" ), uno::Reference< uno::XInterface >() );
2526 if (Destination.hasValue())
2528 uno::Reference< excel::XRange > xRange( Destination, uno::UNO_QUERY_THROW );
2529 uno::Reference< table::XCellRange > xCellRange( xRange->getCellRange(), uno::UNO_QUERY_THROW );
2530 uno::Reference< sheet::XSheetCellRange > xSheetCellRange(xCellRange, ::uno::UNO_QUERY_THROW );
2531 uno::Reference< sheet::XSpreadsheet > xSheet = xSheetCellRange->getSpreadsheet();
2532 uno::Reference< table::XCellRange > xDest( xSheet, uno::UNO_QUERY_THROW );
2533 uno::Reference< sheet::XCellRangeMovement > xMover( xSheet, uno::UNO_QUERY_THROW);
2534 uno::Reference< sheet::XCellAddressable > xDestination( xDest->getCellByPosition(
2535 xRange->getColumn()-1,xRange->getRow()-1), uno::UNO_QUERY);
2536 uno::Reference< sheet::XCellRangeAddressable > xSource( mxRange, uno::UNO_QUERY);
2537 xMover->moveRange( xDestination->getCellAddress(), xSource->getRangeAddress() );
2539 else
2541 uno::Reference< frame::XModel > xModel = getModelFromRange( mxRange );
2542 Select();
2543 excel::implnCut( xModel );
2547 void
2548 ScVbaRange::setNumberFormat( const uno::Any& aFormat ) throw ( script::BasicErrorException, uno::RuntimeException)
2550 OUString sFormat;
2551 aFormat >>= sFormat;
2552 if ( m_Areas->getCount() > 1 )
2554 sal_Int32 nItems = m_Areas->getCount();
2555 for ( sal_Int32 index=1; index <= nItems; ++index )
2557 uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny(index), uno::Any() ), uno::UNO_QUERY_THROW );
2558 xRange->setNumberFormat( aFormat );
2560 return;
2562 NumFormatHelper numFormat( mxRange );
2563 numFormat.setNumberFormat( sFormat );
2566 uno::Any
2567 ScVbaRange::getNumberFormat() throw ( script::BasicErrorException, uno::RuntimeException)
2570 if ( m_Areas->getCount() > 1 )
2572 sal_Int32 nItems = m_Areas->getCount();
2573 uno::Any aResult = aNULL();
2574 for ( sal_Int32 index=1; index <= nItems; ++index )
2576 uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny(index), uno::Any() ), uno::UNO_QUERY_THROW );
2577 // if the numberformat of one area is different to another
2578 // return null
2579 if ( index > 1 )
2580 if ( aResult != xRange->getNumberFormat() )
2581 return aNULL();
2582 aResult = xRange->getNumberFormat();
2583 if ( aNULL() == aResult )
2584 return aNULL();
2586 return aResult;
2588 NumFormatHelper numFormat( mxRange );
2589 OUString sFormat = numFormat.getNumberFormatString();
2590 if ( !sFormat.isEmpty() )
2591 return uno::makeAny( sFormat );
2592 return aNULL();
2595 uno::Reference< excel::XRange >
2596 ScVbaRange::Resize( const uno::Any &RowSize, const uno::Any &ColumnSize ) throw (uno::RuntimeException)
2598 long nRowSize = 0, nColumnSize = 0;
2599 sal_Bool bIsRowChanged = ( RowSize >>= nRowSize ), bIsColumnChanged = ( ColumnSize >>= nColumnSize );
2600 uno::Reference< table::XColumnRowRange > xColumnRowRange(mxRange, ::uno::UNO_QUERY_THROW);
2601 uno::Reference< sheet::XSheetCellRange > xSheetRange(mxRange, ::uno::UNO_QUERY_THROW);
2602 uno::Reference< sheet::XSheetCellCursor > xCursor( xSheetRange->getSpreadsheet()->createCursorByRange(xSheetRange), ::uno::UNO_QUERY_THROW );
2604 if( !bIsRowChanged )
2605 nRowSize = xColumnRowRange->getRows()->getCount();
2606 if( !bIsColumnChanged )
2607 nColumnSize = xColumnRowRange->getColumns()->getCount();
2609 xCursor->collapseToSize( nColumnSize, nRowSize );
2610 uno::Reference< sheet::XCellRangeAddressable > xCellRangeAddressable(xCursor, ::uno::UNO_QUERY_THROW );
2611 uno::Reference< table::XCellRange > xRange( xSheetRange->getSpreadsheet(), ::uno::UNO_QUERY_THROW );
2612 return new ScVbaRange( mxParent, mxContext,xRange->getCellRangeByPosition(
2613 xCellRangeAddressable->getRangeAddress().StartColumn,
2614 xCellRangeAddressable->getRangeAddress().StartRow,
2615 xCellRangeAddressable->getRangeAddress().EndColumn,
2616 xCellRangeAddressable->getRangeAddress().EndRow ) );
2619 void
2620 ScVbaRange::setWrapText( const uno::Any& aIsWrapped ) throw (script::BasicErrorException, uno::RuntimeException)
2622 if ( m_Areas->getCount() > 1 )
2624 sal_Int32 nItems = m_Areas->getCount();
2625 uno::Any aResult;
2626 for ( sal_Int32 index=1; index <= nItems; ++index )
2628 uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny(index), uno::Any() ), uno::UNO_QUERY_THROW );
2629 xRange->setWrapText( aIsWrapped );
2631 return;
2634 uno::Reference< beans::XPropertySet > xProps(mxRange, ::uno::UNO_QUERY_THROW );
2635 bool bIsWrapped = extractBoolFromAny( aIsWrapped );
2636 xProps->setPropertyValue( "IsTextWrapped", uno::Any( bIsWrapped ) );
2639 uno::Any
2640 ScVbaRange::getWrapText() throw (script::BasicErrorException, uno::RuntimeException)
2642 if ( m_Areas->getCount() > 1 )
2644 sal_Int32 nItems = m_Areas->getCount();
2645 uno::Any aResult;
2646 for ( sal_Int32 index=1; index <= nItems; ++index )
2648 uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny(index), uno::Any() ), uno::UNO_QUERY_THROW );
2649 if ( index > 1 )
2650 if ( aResult != xRange->getWrapText() )
2651 return aNULL();
2652 aResult = xRange->getWrapText();
2654 return aResult;
2657 SfxItemSet* pDataSet = getCurrentDataSet();
2659 SfxItemState eState = pDataSet->GetItemState( ATTR_LINEBREAK, true, NULL);
2660 if ( eState == SFX_ITEM_DONTCARE )
2661 return aNULL();
2663 uno::Reference< beans::XPropertySet > xProps(mxRange, ::uno::UNO_QUERY_THROW );
2664 uno::Any aValue = xProps->getPropertyValue( "IsTextWrapped" );
2665 return aValue;
2668 uno::Reference< excel::XInterior > ScVbaRange::Interior( ) throw ( script::BasicErrorException, uno::RuntimeException)
2670 uno::Reference< beans::XPropertySet > xProps( mxRange, uno::UNO_QUERY_THROW );
2671 return new ScVbaInterior ( this, mxContext, xProps, getScDocument() );
2673 uno::Reference< excel::XRange >
2674 ScVbaRange::Range( const uno::Any &Cell1, const uno::Any &Cell2 ) throw (uno::RuntimeException)
2676 return Range( Cell1, Cell2, false );
2678 uno::Reference< excel::XRange >
2679 ScVbaRange::Range( const uno::Any &Cell1, const uno::Any &Cell2, bool bForceUseInpuRangeTab ) throw (uno::RuntimeException)
2682 uno::Reference< table::XCellRange > xCellRange = mxRange;
2684 if ( m_Areas->getCount() > 1 )
2686 uno::Reference< container::XIndexAccess > xIndex( mxRanges, uno::UNO_QUERY_THROW );
2687 xCellRange.set( xIndex->getByIndex( 0 ), uno::UNO_QUERY_THROW );
2689 else
2690 xCellRange.set( mxRange );
2692 RangeHelper thisRange( xCellRange );
2693 uno::Reference< table::XCellRange > xRanges = thisRange.getCellRangeFromSheet();
2694 uno::Reference< sheet::XCellRangeAddressable > xAddressable( xRanges, uno::UNO_QUERY_THROW );
2696 uno::Reference< table::XCellRange > xReferrer =
2697 xRanges->getCellRangeByPosition( getColumn()-1, getRow()-1,
2698 xAddressable->getRangeAddress().EndColumn,
2699 xAddressable->getRangeAddress().EndRow );
2700 // xAddressable now for this range
2701 xAddressable.set( xReferrer, uno::UNO_QUERY_THROW );
2703 if( !Cell1.hasValue() )
2704 throw uno::RuntimeException(
2705 OUString( " Invalid Argument " ),
2706 uno::Reference< XInterface >() );
2708 table::CellRangeAddress resultAddress;
2709 table::CellRangeAddress parentRangeAddress = xAddressable->getRangeAddress();
2711 ScRange aRange;
2712 // Cell1 defined only
2713 if ( !Cell2.hasValue() )
2715 OUString sName;
2716 Cell1 >>= sName;
2717 RangeHelper referRange( xReferrer );
2718 table::CellRangeAddress referAddress = referRange.getCellRangeAddressable()->getRangeAddress();
2719 return getRangeForName( mxContext, sName, getScDocShell(), referAddress );
2722 else
2724 table::CellRangeAddress cell1, cell2;
2725 cell1 = getCellRangeAddressForVBARange( Cell1, getScDocShell() );
2726 // Cell1 & Cell2 defined
2727 // Excel seems to combine the range as the range defined by
2728 // the combination of Cell1 & Cell2
2730 cell2 = getCellRangeAddressForVBARange( Cell2, getScDocShell() );
2732 resultAddress.StartColumn = ( cell1.StartColumn < cell2.StartColumn ) ? cell1.StartColumn : cell2.StartColumn;
2733 resultAddress.StartRow = ( cell1.StartRow < cell2.StartRow ) ? cell1.StartRow : cell2.StartRow;
2734 resultAddress.EndColumn = ( cell1.EndColumn > cell2.EndColumn ) ? cell1.EndColumn : cell2.EndColumn;
2735 resultAddress.EndRow = ( cell1.EndRow > cell2.EndRow ) ? cell1.EndRow : cell2.EndRow;
2736 if ( bForceUseInpuRangeTab )
2738 // this is a call from Application.Range( x,y )
2739 // its possiblefor x or y to specify a different sheet from
2740 // the current or active on ( but they must be the same )
2741 if ( cell1.Sheet != cell2.Sheet )
2742 throw uno::RuntimeException();
2743 parentRangeAddress.Sheet = cell1.Sheet;
2745 else
2747 // this is not a call from Application.Range( x,y )
2748 // if a different sheet from this range is specified it's
2749 // an error
2750 if ( parentRangeAddress.Sheet != cell1.Sheet
2751 || parentRangeAddress.Sheet != cell2.Sheet
2753 throw uno::RuntimeException();
2756 ScUnoConversion::FillScRange( aRange, resultAddress );
2758 ScRange parentAddress;
2759 ScUnoConversion::FillScRange( parentAddress, parentRangeAddress);
2760 if ( aRange.aStart.Col() >= 0 && aRange.aStart.Row() >= 0 && aRange.aEnd.Col() >= 0 && aRange.aEnd.Row() >= 0 )
2762 sal_Int32 nStartX = parentAddress.aStart.Col() + aRange.aStart.Col();
2763 sal_Int32 nStartY = parentAddress.aStart.Row() + aRange.aStart.Row();
2764 sal_Int32 nEndX = parentAddress.aStart.Col() + aRange.aEnd.Col();
2765 sal_Int32 nEndY = parentAddress.aStart.Row() + aRange.aEnd.Row();
2767 if ( nStartX <= nEndX && nEndX <= parentAddress.aEnd.Col() &&
2768 nStartY <= nEndY && nEndY <= parentAddress.aEnd.Row() )
2770 ScRange aNew( (SCCOL)nStartX, (SCROW)nStartY, parentAddress.aStart.Tab(),
2771 (SCCOL)nEndX, (SCROW)nEndY, parentAddress.aEnd.Tab() );
2772 xCellRange = new ScCellRangeObj( getScDocShell(), aNew );
2776 return new ScVbaRange( mxParent, mxContext, xCellRange );
2780 // Allow access to underlying openoffice uno api ( useful for debugging
2781 // with openoffice basic )
2782 uno::Any SAL_CALL ScVbaRange::getCellRange( ) throw (uno::RuntimeException)
2784 uno::Any aAny;
2785 if ( mxRanges.is() )
2786 aAny <<= mxRanges;
2787 else if ( mxRange.is() )
2788 aAny <<= mxRange;
2789 return aAny;
2792 uno::Any ScVbaRange::getCellRange( const uno::Reference< excel::XRange >& rxRange ) throw (uno::RuntimeException)
2794 if( ScVbaRange* pVbaRange = getImplementation( rxRange ) )
2795 return pVbaRange->getCellRange();
2796 throw uno::RuntimeException();
2799 static sal_uInt16
2800 getPasteFlags (sal_Int32 Paste)
2802 sal_uInt16 nFlags = IDF_NONE;
2803 switch (Paste) {
2804 case excel::XlPasteType::xlPasteComments:
2805 nFlags = IDF_NOTE;break;
2806 case excel::XlPasteType::xlPasteFormats:
2807 nFlags = IDF_ATTRIB;break;
2808 case excel::XlPasteType::xlPasteFormulas:
2809 nFlags = IDF_FORMULA;break;
2810 case excel::XlPasteType::xlPasteFormulasAndNumberFormats :
2811 case excel::XlPasteType::xlPasteValues:
2812 nFlags = ( IDF_VALUE | IDF_DATETIME | IDF_STRING | IDF_SPECIAL_BOOLEAN ); break;
2813 case excel::XlPasteType::xlPasteValuesAndNumberFormats:
2814 nFlags = IDF_VALUE | IDF_ATTRIB; break;
2815 case excel::XlPasteType::xlPasteColumnWidths:
2816 case excel::XlPasteType::xlPasteValidation:
2817 nFlags = IDF_NONE;break;
2818 case excel::XlPasteType::xlPasteAll:
2819 case excel::XlPasteType::xlPasteAllExceptBorders:
2820 default:
2821 nFlags = IDF_ALL;break;
2823 return nFlags;
2826 static sal_uInt16
2827 getPasteFormulaBits( sal_Int32 Operation)
2829 sal_uInt16 nFormulaBits = PASTE_NOFUNC ;
2830 switch (Operation)
2832 case excel::XlPasteSpecialOperation::xlPasteSpecialOperationAdd:
2833 nFormulaBits = PASTE_ADD;break;
2834 case excel::XlPasteSpecialOperation::xlPasteSpecialOperationSubtract:
2835 nFormulaBits = PASTE_SUB;break;
2836 case excel::XlPasteSpecialOperation::xlPasteSpecialOperationMultiply:
2837 nFormulaBits = PASTE_MUL;break;
2838 case excel::XlPasteSpecialOperation::xlPasteSpecialOperationDivide:
2839 nFormulaBits = PASTE_DIV;break;
2841 case excel::XlPasteSpecialOperation::xlPasteSpecialOperationNone:
2842 default:
2843 nFormulaBits = PASTE_NOFUNC; break;
2846 return nFormulaBits;
2848 void SAL_CALL
2849 ScVbaRange::PasteSpecial( const uno::Any& Paste, const uno::Any& Operation, const uno::Any& SkipBlanks, const uno::Any& Transpose ) throw (::com::sun::star::uno::RuntimeException)
2851 if ( m_Areas->getCount() > 1 )
2852 throw uno::RuntimeException( OUString( "That command cannot be used on multiple selections" ), uno::Reference< uno::XInterface >() );
2853 ScDocShell* pShell = getScDocShell();
2855 uno::Reference< frame::XModel > xModel( ( pShell ? pShell->GetModel() : NULL ), uno::UNO_QUERY_THROW );
2856 uno::Reference< view::XSelectionSupplier > xSelection( xModel->getCurrentController(), uno::UNO_QUERY_THROW );
2857 // select this range
2858 xSelection->select( uno::makeAny( mxRange ) );
2859 // set up defaults
2860 sal_Int32 nPaste = excel::XlPasteType::xlPasteAll;
2861 sal_Int32 nOperation = excel::XlPasteSpecialOperation::xlPasteSpecialOperationNone;
2862 sal_Bool bTranspose = false;
2863 sal_Bool bSkipBlanks = false;
2865 if ( Paste.hasValue() )
2866 Paste >>= nPaste;
2867 if ( Operation.hasValue() )
2868 Operation >>= nOperation;
2869 if ( SkipBlanks.hasValue() )
2870 SkipBlanks >>= bSkipBlanks;
2871 if ( Transpose.hasValue() )
2872 Transpose >>= bTranspose;
2874 sal_uInt16 nFlags = getPasteFlags(nPaste);
2875 sal_uInt16 nFormulaBits = getPasteFormulaBits(nOperation);
2876 excel::implnPasteSpecial(pShell->GetModel(), nFlags,nFormulaBits,bSkipBlanks,bTranspose);
2879 uno::Reference< excel::XRange >
2880 ScVbaRange::getEntireColumnOrRow( bool bColumn ) throw (uno::RuntimeException)
2882 ScCellRangesBase* pUnoRangesBase = getCellRangesBase();
2883 // copy the range list
2884 ScRangeList aCellRanges = pUnoRangesBase->GetRangeList();
2886 for ( size_t i = 0, nRanges = aCellRanges.size(); i < nRanges; ++i )
2888 ScRange* pRange = aCellRanges[ i ];
2889 if ( bColumn )
2891 pRange->aStart.SetRow( 0 );
2892 pRange->aEnd.SetRow( MAXROW );
2894 else
2896 pRange->aStart.SetCol( 0 );
2897 pRange->aEnd.SetCol( MAXCOL );
2900 if ( aCellRanges.size() > 1 ) // Multi-Area
2902 uno::Reference< sheet::XSheetCellRangeContainer > xRanges( new ScCellRangesObj( pUnoRangesBase->GetDocShell(), aCellRanges ) );
2904 return new ScVbaRange( mxParent, mxContext, xRanges, !bColumn, bColumn );
2906 uno::Reference< table::XCellRange > xRange( new ScCellRangeObj( pUnoRangesBase->GetDocShell(), *aCellRanges.front() ) );
2907 return new ScVbaRange( mxParent, mxContext, xRange, !bColumn, bColumn );
2910 uno::Reference< excel::XRange > SAL_CALL
2911 ScVbaRange::getEntireRow() throw (uno::RuntimeException)
2913 return getEntireColumnOrRow(false);
2916 uno::Reference< excel::XRange > SAL_CALL
2917 ScVbaRange::getEntireColumn() throw (uno::RuntimeException)
2919 return getEntireColumnOrRow();
2922 uno::Reference< excel::XComment > SAL_CALL
2923 ScVbaRange::AddComment( const uno::Any& Text ) throw (uno::RuntimeException)
2925 // if there is already a comment in the top-left cell then throw
2926 if( getComment().is() )
2927 throw uno::RuntimeException();
2929 // workaround: Excel allows to create empty comment, Calc does not
2930 OUString aNoteText;
2931 if( Text.hasValue() && !(Text >>= aNoteText) )
2932 throw uno::RuntimeException();
2933 if( aNoteText.isEmpty() )
2934 aNoteText = OUString( sal_Unicode( ' ' ) );
2936 // try to create a new annotation
2937 table::CellRangeAddress aRangePos = lclGetRangeAddress( mxRange );
2938 table::CellAddress aNotePos( aRangePos.Sheet, aRangePos.StartColumn, aRangePos.StartRow );
2939 uno::Reference< sheet::XSheetCellRange > xCellRange( mxRange, uno::UNO_QUERY_THROW );
2940 uno::Reference< sheet::XSheetAnnotationsSupplier > xAnnosSupp( xCellRange->getSpreadsheet(), uno::UNO_QUERY_THROW );
2941 uno::Reference< sheet::XSheetAnnotations > xAnnos( xAnnosSupp->getAnnotations(), uno::UNO_SET_THROW );
2942 xAnnos->insertNew( aNotePos, aNoteText );
2943 return new ScVbaComment( this, mxContext, getUnoModel(), mxRange );
2946 uno::Reference< excel::XComment > SAL_CALL
2947 ScVbaRange::getComment() throw (uno::RuntimeException)
2949 // intentional behavior to return a null object if no
2950 // comment defined
2951 uno::Reference< excel::XComment > xComment( new ScVbaComment( this, mxContext, getUnoModel(), mxRange ) );
2952 if ( xComment->Text( uno::Any(), uno::Any(), uno::Any() ).isEmpty() )
2953 return NULL;
2954 return xComment;
2958 uno::Reference< beans::XPropertySet >
2959 getRowOrColumnProps( const uno::Reference< table::XCellRange >& xCellRange, bool bRows ) throw ( uno::RuntimeException )
2961 uno::Reference< table::XColumnRowRange > xColRow( xCellRange, uno::UNO_QUERY_THROW );
2962 uno::Reference< beans::XPropertySet > xProps;
2963 if ( bRows )
2964 xProps.set( xColRow->getRows(), uno::UNO_QUERY_THROW );
2965 else
2966 xProps.set( xColRow->getColumns(), uno::UNO_QUERY_THROW );
2967 return xProps;
2970 uno::Any SAL_CALL
2971 ScVbaRange::getHidden() throw (uno::RuntimeException)
2973 // if multi-area result is the result of the
2974 // first area
2975 if ( m_Areas->getCount() > 1 )
2977 uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny(sal_Int32(1)), uno::Any() ), uno::UNO_QUERY_THROW );
2978 return xRange->getHidden();
2980 bool bIsVisible = false;
2983 uno::Reference< beans::XPropertySet > xProps = getRowOrColumnProps( mxRange, mbIsRows );
2984 if ( !( xProps->getPropertyValue( ISVISIBLE ) >>= bIsVisible ) )
2985 throw uno::RuntimeException( OUString( "Failed to get IsVisible property"), uno::Reference< uno::XInterface >() );
2987 catch( const uno::Exception& e )
2989 throw uno::RuntimeException( e.Message, uno::Reference< uno::XInterface >() );
2991 return uno::makeAny( !bIsVisible );
2994 void SAL_CALL
2995 ScVbaRange::setHidden( const uno::Any& _hidden ) throw (uno::RuntimeException)
2997 if ( m_Areas->getCount() > 1 )
2999 sal_Int32 nItems = m_Areas->getCount();
3000 for ( sal_Int32 index=1; index <= nItems; ++index )
3002 uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny(index), uno::Any() ), uno::UNO_QUERY_THROW );
3003 xRange->setHidden( _hidden );
3005 return;
3008 bool bHidden = extractBoolFromAny( _hidden );
3011 uno::Reference< beans::XPropertySet > xProps = getRowOrColumnProps( mxRange, mbIsRows );
3012 xProps->setPropertyValue( ISVISIBLE, uno::Any( !bHidden ) );
3014 catch( const uno::Exception& e )
3016 throw uno::RuntimeException( e.Message, uno::Reference< uno::XInterface >() );
3020 ::sal_Bool SAL_CALL
3021 ScVbaRange::Replace( const OUString& What, const 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)
3023 if ( m_Areas->getCount() > 1 )
3025 for ( sal_Int32 index = 1; index <= m_Areas->getCount(); ++index )
3027 uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny( index ), uno::Any() ), uno::UNO_QUERY_THROW );
3028 xRange->Replace( What, Replacement, LookAt, SearchOrder, MatchCase, MatchByte, SearchFormat, ReplaceFormat );
3030 return sal_True; // seems to return true always ( or at least I haven't found the trick of
3033 // sanity check required params
3034 if ( What.isEmpty() )
3035 throw uno::RuntimeException( OUString( "Range::Replace, missing params" ) , uno::Reference< uno::XInterface >() );
3036 OUString sWhat = VBAToRegexp( What);
3037 // #TODO #FIXME SearchFormat & ReplacesFormat are not processed
3038 // What do we do about MatchByte.. we don't seem to support that
3039 const SvxSearchItem& globalSearchOptions = ScGlobal::GetSearchItem();
3040 SvxSearchItem newOptions( globalSearchOptions );
3042 sal_Int16 nLook = globalSearchOptions.GetWordOnly() ? excel::XlLookAt::xlPart : excel::XlLookAt::xlWhole;
3043 sal_Int16 nSearchOrder = globalSearchOptions.GetRowDirection() ? excel::XlSearchOrder::xlByRows : excel::XlSearchOrder::xlByColumns;
3045 sal_Bool bMatchCase = false;
3046 uno::Reference< util::XReplaceable > xReplace( mxRange, uno::UNO_QUERY );
3047 if ( xReplace.is() )
3049 uno::Reference< util::XReplaceDescriptor > xDescriptor =
3050 xReplace->createReplaceDescriptor();
3052 xDescriptor->setSearchString( sWhat);
3053 xDescriptor->setPropertyValue( SC_UNO_SRCHREGEXP, uno::makeAny( sal_True ) );
3054 xDescriptor->setReplaceString( Replacement);
3055 if ( LookAt.hasValue() )
3057 // sets SearchWords ( true is Cell match )
3058 nLook = ::comphelper::getINT16( LookAt );
3059 sal_Bool bSearchWords = false;
3060 if ( nLook == excel::XlLookAt::xlPart )
3061 bSearchWords = false;
3062 else if ( nLook == excel::XlLookAt::xlWhole )
3063 bSearchWords = sal_True;
3064 else
3065 throw uno::RuntimeException( OUString( "Range::Replace, illegal value for LookAt" ) , uno::Reference< uno::XInterface >() );
3066 // set global search props ( affects the find dialog
3067 // and of course the defaults for this method
3068 newOptions.SetWordOnly( bSearchWords );
3069 xDescriptor->setPropertyValue( SC_UNO_SRCHWORDS, uno::makeAny( bSearchWords ) );
3071 // sets SearchByRow ( true for Rows )
3072 if ( SearchOrder.hasValue() )
3074 nSearchOrder = ::comphelper::getINT16( SearchOrder );
3075 sal_Bool bSearchByRow = false;
3076 if ( nSearchOrder == excel::XlSearchOrder::xlByColumns )
3077 bSearchByRow = false;
3078 else if ( nSearchOrder == excel::XlSearchOrder::xlByRows )
3079 bSearchByRow = sal_True;
3080 else
3081 throw uno::RuntimeException( OUString( "Range::Replace, illegal value for SearchOrder" ) , uno::Reference< uno::XInterface >() );
3083 newOptions.SetRowDirection( bSearchByRow );
3084 xDescriptor->setPropertyValue( SC_UNO_SRCHBYROW, uno::makeAny( bSearchByRow ) );
3086 if ( MatchCase.hasValue() )
3088 // SearchCaseSensitive
3089 MatchCase >>= bMatchCase;
3090 xDescriptor->setPropertyValue( SC_UNO_SRCHCASE, uno::makeAny( bMatchCase ) );
3093 ScGlobal::SetSearchItem( newOptions );
3094 // ignore MatchByte for the moment, its not supported in
3095 // OOo.org afaik
3097 uno::Reference< util::XSearchDescriptor > xSearch( xDescriptor, uno::UNO_QUERY );
3098 xReplace->replaceAll( xSearch );
3100 return sal_True; // always
3103 uno::Reference< excel::XRange > SAL_CALL
3104 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)
3106 // return a Range object that represents the first cell where that information is found.
3107 OUString sWhat;
3108 sal_Int32 nWhat = 0;
3109 double fWhat = 0.0;
3111 // string.
3112 if( What >>= sWhat )
3114 if( sWhat.isEmpty() )
3115 throw uno::RuntimeException( OUString( "Range::Find, missing params" ) , uno::Reference< uno::XInterface >() );
3117 else if( What >>= nWhat )
3119 sWhat = OUString::valueOf( nWhat );
3121 else if( What >>= fWhat )
3123 sWhat = OUString::valueOf( fWhat );
3125 else
3126 throw uno::RuntimeException( OUString( "Range::Find, missing params" ) , uno::Reference< uno::XInterface >() );
3128 OUString sSearch = VBAToRegexp( sWhat );
3130 const SvxSearchItem& globalSearchOptions = ScGlobal::GetSearchItem();
3131 SvxSearchItem newOptions( globalSearchOptions );
3133 sal_Int16 nLookAt = globalSearchOptions.GetWordOnly() ? excel::XlLookAt::xlPart : excel::XlLookAt::xlWhole;
3134 sal_Int16 nSearchOrder = globalSearchOptions.GetRowDirection() ? excel::XlSearchOrder::xlByRows : excel::XlSearchOrder::xlByColumns;
3136 uno::Reference< util::XSearchable > xSearch( mxRange, uno::UNO_QUERY );
3137 if( xSearch.is() )
3139 uno::Reference< util::XSearchDescriptor > xDescriptor = xSearch->createSearchDescriptor();
3140 xDescriptor->setSearchString( sSearch );
3141 xDescriptor->setPropertyValue( SC_UNO_SRCHREGEXP, uno::Any( true ) );
3143 uno::Reference< excel::XRange > xAfterRange;
3144 uno::Reference< table::XCellRange > xStartCell;
3145 if( After >>= xAfterRange )
3147 // After must be a single cell in the range
3148 if( xAfterRange->getCount() > 1 )
3149 throw uno::RuntimeException( OUString( "After must be a single cell." ) , uno::Reference< uno::XInterface >() );
3150 uno::Reference< excel::XRange > xCell( Cells( uno::makeAny( xAfterRange->getRow() ), uno::makeAny( xAfterRange->getColumn() ) ), uno::UNO_QUERY );
3151 if( !xCell.is() )
3152 throw uno::RuntimeException( OUString( "After must be in range." ) , uno::Reference< uno::XInterface >() );
3153 xStartCell.set( xAfterRange->getCellRange(), uno::UNO_QUERY_THROW );
3156 // LookIn
3157 if( LookIn.hasValue() )
3159 sal_Int32 nLookIn = 0;
3160 if( LookIn >>= nLookIn )
3162 sal_Int16 nSearchType = 0;
3163 switch( nLookIn )
3165 case excel::XlFindLookIn::xlComments :
3166 nSearchType = SVX_SEARCHIN_NOTE; // Notes
3167 break;
3168 case excel::XlFindLookIn::xlFormulas :
3169 nSearchType = SVX_SEARCHIN_FORMULA;
3170 break;
3171 case excel::XlFindLookIn::xlValues :
3172 nSearchType = SVX_SEARCHIN_VALUE;
3173 break;
3174 default:
3175 throw uno::RuntimeException( OUString( "Range::Replace, illegal value for LookIn." ) , uno::Reference< uno::XInterface >() );
3177 newOptions.SetCellType( nSearchType );
3178 xDescriptor->setPropertyValue( "SearchType", uno::makeAny( nSearchType ) );
3182 // LookAt
3183 if ( LookAt.hasValue() )
3185 nLookAt = ::comphelper::getINT16( LookAt );
3186 sal_Bool bSearchWords = false;
3187 if ( nLookAt == excel::XlLookAt::xlPart )
3188 bSearchWords = false;
3189 else if ( nLookAt == excel::XlLookAt::xlWhole )
3190 bSearchWords = sal_True;
3191 else
3192 throw uno::RuntimeException( OUString( "Range::Replace, illegal value for LookAt" ) , uno::Reference< uno::XInterface >() );
3193 newOptions.SetWordOnly( bSearchWords );
3194 xDescriptor->setPropertyValue( SC_UNO_SRCHWORDS, uno::makeAny( bSearchWords ) );
3197 // SearchOrder
3198 if ( SearchOrder.hasValue() )
3200 nSearchOrder = ::comphelper::getINT16( SearchOrder );
3201 sal_Bool bSearchByRow = false;
3202 if ( nSearchOrder == excel::XlSearchOrder::xlByColumns )
3203 bSearchByRow = false;
3204 else if ( nSearchOrder == excel::XlSearchOrder::xlByRows )
3205 bSearchByRow = sal_True;
3206 else
3207 throw uno::RuntimeException( OUString( "Range::Replace, illegal value for SearchOrder" ) , uno::Reference< uno::XInterface >() );
3209 newOptions.SetRowDirection( bSearchByRow );
3210 xDescriptor->setPropertyValue( SC_UNO_SRCHBYROW, uno::makeAny( bSearchByRow ) );
3213 // SearchDirection
3214 if ( SearchDirection.hasValue() )
3216 sal_Int32 nSearchDirection = 0;
3217 if( SearchDirection >>= nSearchDirection )
3219 sal_Bool bSearchBackwards = false;
3220 if ( nSearchDirection == excel::XlSearchDirection::xlNext )
3221 bSearchBackwards = false;
3222 else if( nSearchDirection == excel::XlSearchDirection::xlPrevious )
3223 bSearchBackwards = sal_True;
3224 else
3225 throw uno::RuntimeException( OUString( "Range::Replace, illegal value for SearchDirection" ) , uno::Reference< uno::XInterface >() );
3226 newOptions.SetBackward( bSearchBackwards );
3227 xDescriptor->setPropertyValue( "SearchBackwards", uno::makeAny( bSearchBackwards ) );
3231 // MatchCase
3232 sal_Bool bMatchCase = false;
3233 if ( MatchCase.hasValue() )
3235 // SearchCaseSensitive
3236 if( !( MatchCase >>= bMatchCase ) )
3237 throw uno::RuntimeException( OUString( "Range::Replace, illegal value for MatchCase" ) , uno::Reference< uno::XInterface >() );
3239 xDescriptor->setPropertyValue( SC_UNO_SRCHCASE, uno::makeAny( bMatchCase ) );
3241 // MatchByte
3242 // SearchFormat
3243 // ignore
3245 ScGlobal::SetSearchItem( newOptions );
3247 uno::Reference< uno::XInterface > xInterface = xStartCell.is() ? xSearch->findNext( xStartCell, xDescriptor) : xSearch->findFirst( xDescriptor );
3248 uno::Reference< table::XCellRange > xCellRange( xInterface, uno::UNO_QUERY );
3249 // if we are searching from a starting cell and failed to find a match
3250 // then try from the beginning
3251 if ( !xCellRange.is() && xStartCell.is() )
3253 xInterface = xSearch->findFirst( xDescriptor );
3254 xCellRange.set( xInterface, uno::UNO_QUERY );
3256 if ( xCellRange.is() )
3258 uno::Reference< excel::XRange > xResultRange = new ScVbaRange( mxParent, mxContext, xCellRange );
3259 if( xResultRange.is() )
3261 xResultRange->Select();
3262 return xResultRange;
3268 return uno::Reference< excel::XRange >();
3271 uno::Reference< table::XCellRange > processKey( const uno::Any& Key, uno::Reference< uno::XComponentContext >& xContext, ScDocShell* pDocSh )
3273 uno::Reference< excel::XRange > xKeyRange;
3274 if ( Key.getValueType() == excel::XRange::static_type() )
3276 xKeyRange.set( Key, uno::UNO_QUERY_THROW );
3278 else if ( Key.getValueType() == ::getCppuType( static_cast< const OUString* >(0) ) )
3281 OUString sRangeName = ::comphelper::getString( Key );
3282 table::CellRangeAddress aRefAddr;
3283 if ( !pDocSh )
3284 throw uno::RuntimeException( OUString("Range::Sort no docshell to calculate key param"), uno::Reference< uno::XInterface >() );
3285 xKeyRange = getRangeForName( xContext, sRangeName, pDocSh, aRefAddr );
3287 else
3288 throw uno::RuntimeException( OUString("Range::Sort illegal type value for key param"), uno::Reference< uno::XInterface >() );
3289 uno::Reference< table::XCellRange > xKey;
3290 xKey.set( xKeyRange->getCellRange(), uno::UNO_QUERY_THROW );
3291 return xKey;
3294 // helper method for Sort
3295 sal_Int32 findSortPropertyIndex( const uno::Sequence< beans::PropertyValue >& props,
3296 const OUString& sPropName ) throw( uno::RuntimeException )
3298 const beans::PropertyValue* pProp = props.getConstArray();
3299 sal_Int32 nItems = props.getLength();
3301 sal_Int32 count=0;
3302 for ( ; count < nItems; ++count, ++pProp )
3303 if ( pProp->Name.equals( sPropName ) )
3304 return count;
3305 if ( count == nItems )
3306 throw uno::RuntimeException( OUString("Range::Sort unknown sort property"), uno::Reference< uno::XInterface >() );
3307 return -1; //should never reach here ( satisfy compiler )
3310 // helper method for Sort
3311 void updateTableSortField( const uno::Reference< table::XCellRange >& xParentRange,
3312 const uno::Reference< table::XCellRange >& xColRowKey, sal_Int16 nOrder,
3313 table::TableSortField& aTableField, sal_Bool bIsSortColumn, sal_Bool bMatchCase ) throw ( uno::RuntimeException )
3315 RangeHelper parentRange( xParentRange );
3316 RangeHelper colRowRange( xColRowKey );
3318 table::CellRangeAddress parentRangeAddress = parentRange.getCellRangeAddressable()->getRangeAddress();
3320 table::CellRangeAddress colRowKeyAddress = colRowRange.getCellRangeAddressable()->getRangeAddress();
3322 // make sure that upper left poing of key range is within the
3323 // parent range
3324 if ( ( !bIsSortColumn && colRowKeyAddress.StartColumn >= parentRangeAddress.StartColumn &&
3325 colRowKeyAddress.StartColumn <= parentRangeAddress.EndColumn ) || ( bIsSortColumn &&
3326 colRowKeyAddress.StartRow >= parentRangeAddress.StartRow &&
3327 colRowKeyAddress.StartRow <= parentRangeAddress.EndRow ) )
3329 //determine col/row index
3330 if ( bIsSortColumn )
3331 aTableField.Field = colRowKeyAddress.StartRow - parentRangeAddress.StartRow;
3332 else
3333 aTableField.Field = colRowKeyAddress.StartColumn - parentRangeAddress.StartColumn;
3334 aTableField.IsCaseSensitive = bMatchCase;
3336 if ( nOrder == excel::XlSortOrder::xlAscending )
3337 aTableField.IsAscending = sal_True;
3338 else
3339 aTableField.IsAscending = false;
3341 else
3342 throw uno::RuntimeException( OUString( "Illegal Key param" ), uno::Reference< uno::XInterface >() );
3347 void SAL_CALL
3348 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)
3350 // #TODO# #FIXME# can we do something with Type
3351 if ( m_Areas->getCount() > 1 )
3352 throw uno::RuntimeException( OUString( "That command cannot be used on multiple selections" ), uno::Reference< uno::XInterface >() );
3354 sal_Int16 nDataOption1 = excel::XlSortDataOption::xlSortNormal;
3355 sal_Int16 nDataOption2 = excel::XlSortDataOption::xlSortNormal;
3356 sal_Int16 nDataOption3 = excel::XlSortDataOption::xlSortNormal;
3358 ScDocument* pDoc = getScDocument();
3359 if ( !pDoc )
3360 throw uno::RuntimeException( OUString( "Failed to access document from shell" ), uno::Reference< uno::XInterface >() );
3362 RangeHelper thisRange( mxRange );
3363 table::CellRangeAddress thisRangeAddress = thisRange.getCellRangeAddressable()->getRangeAddress();
3364 ScSortParam aSortParam;
3365 SCTAB nTab = thisRangeAddress.Sheet;
3366 pDoc->GetSortParam( aSortParam, nTab );
3368 if ( DataOption1.hasValue() )
3369 DataOption1 >>= nDataOption1;
3370 if ( DataOption2.hasValue() )
3371 DataOption2 >>= nDataOption2;
3372 if ( DataOption3.hasValue() )
3373 DataOption3 >>= nDataOption3;
3375 // 1) #TODO #FIXME need to process DataOption[1..3] not used currently
3376 // 2) #TODO #FIXME need to refactor this ( below ) into a IsSingleCell() method
3377 uno::Reference< table::XColumnRowRange > xColumnRowRange(mxRange, uno::UNO_QUERY_THROW );
3379 // set up defaults
3381 sal_Int16 nOrder1 = aSortParam.maKeyState[1].bAscending ? excel::XlSortOrder::xlAscending : excel::XlSortOrder::xlDescending;
3382 sal_Int16 nOrder2 = aSortParam.maKeyState[2].bAscending ? excel::XlSortOrder::xlAscending : excel::XlSortOrder::xlDescending;
3383 sal_Int16 nOrder3 = aSortParam.maKeyState[3].bAscending ? excel::XlSortOrder::xlAscending : excel::XlSortOrder::xlDescending;
3385 sal_Int16 nCustom = aSortParam.nUserIndex;
3386 sal_Int16 nSortMethod = excel::XlSortMethod::xlPinYin;
3387 sal_Bool bMatchCase = aSortParam.bCaseSens;
3389 // seems to work opposite to expected, see below
3390 sal_Int16 nOrientation = aSortParam.bByRow ? excel::XlSortOrientation::xlSortColumns : excel::XlSortOrientation::xlSortRows;
3392 if ( Orientation.hasValue() )
3394 // Documentation says xlSortRows is default but that doesn't appear to be
3395 // the case. Also it appears that xlSortColumns is the default which
3396 // strangely enough sorts by Row
3397 nOrientation = ::comphelper::getINT16( Orientation );
3398 // persist new option to be next calls default
3399 if ( nOrientation == excel::XlSortOrientation::xlSortRows )
3400 aSortParam.bByRow = false;
3401 else
3402 aSortParam.bByRow = sal_True;
3406 sal_Bool bIsSortColumns=false; // sort by row
3408 if ( nOrientation == excel::XlSortOrientation::xlSortRows )
3409 bIsSortColumns = sal_True;
3410 sal_Int16 nHeader = 0;
3411 nHeader = aSortParam.nCompatHeader;
3412 sal_Bool bContainsHeader = false;
3414 if ( Header.hasValue() )
3416 nHeader = ::comphelper::getINT16( Header );
3417 aSortParam.nCompatHeader = nHeader;
3420 if ( nHeader == excel::XlYesNoGuess::xlGuess )
3422 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 ));
3423 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 ) );
3424 if ( bHasColHeader || bHasRowHeader )
3425 nHeader = excel::XlYesNoGuess::xlYes;
3426 else
3427 nHeader = excel::XlYesNoGuess::xlNo;
3428 aSortParam.nCompatHeader = nHeader;
3431 if ( nHeader == excel::XlYesNoGuess::xlYes )
3432 bContainsHeader = sal_True;
3434 if ( SortMethod.hasValue() )
3436 nSortMethod = ::comphelper::getINT16( SortMethod );
3439 if ( OrderCustom.hasValue() )
3441 OrderCustom >>= nCustom;
3442 --nCustom; // 0-based in OOo
3443 aSortParam.nUserIndex = nCustom;
3446 if ( MatchCase.hasValue() )
3448 MatchCase >>= bMatchCase;
3449 aSortParam.bCaseSens = bMatchCase;
3452 if ( Order1.hasValue() )
3454 nOrder1 = ::comphelper::getINT16(Order1);
3455 if ( nOrder1 == excel::XlSortOrder::xlAscending )
3456 aSortParam.maKeyState[0].bAscending = true;
3457 else
3458 aSortParam.maKeyState[0].bAscending = false;
3461 if ( Order2.hasValue() )
3463 nOrder2 = ::comphelper::getINT16(Order2);
3464 if ( nOrder2 == excel::XlSortOrder::xlAscending )
3465 aSortParam.maKeyState[1].bAscending = true;
3466 else
3467 aSortParam.maKeyState[1].bAscending = false;
3469 if ( Order3.hasValue() )
3471 nOrder3 = ::comphelper::getINT16(Order3);
3472 if ( nOrder3 == excel::XlSortOrder::xlAscending )
3473 aSortParam.maKeyState[2].bAscending = true;
3474 else
3475 aSortParam.maKeyState[2].bAscending = false;
3478 uno::Reference< table::XCellRange > xKey1;
3479 uno::Reference< table::XCellRange > xKey2;
3480 uno::Reference< table::XCellRange > xKey3;
3481 ScDocShell* pDocShell = getScDocShell();
3482 xKey1 = processKey( Key1, mxContext, pDocShell );
3483 if ( !xKey1.is() )
3484 throw uno::RuntimeException( OUString("Range::Sort needs a key1 param"), uno::Reference< uno::XInterface >() );
3486 if ( Key2.hasValue() )
3487 xKey2 = processKey( Key2, mxContext, pDocShell );
3488 if ( Key3.hasValue() )
3489 xKey3 = processKey( Key3, mxContext, pDocShell );
3491 uno::Reference< util::XSortable > xSort( mxRange, uno::UNO_QUERY_THROW );
3492 uno::Sequence< beans::PropertyValue > sortDescriptor = xSort->createSortDescriptor();
3493 sal_Int32 nTableSortFieldIndex = findSortPropertyIndex( sortDescriptor, OUString( "SortFields" ) );
3495 uno::Sequence< table::TableSortField > sTableFields(1);
3496 sal_Int32 nTableIndex = 0;
3497 updateTableSortField( mxRange, xKey1, nOrder1, sTableFields[ nTableIndex++ ], bIsSortColumns, bMatchCase );
3499 if ( xKey2.is() )
3501 sTableFields.realloc( sTableFields.getLength() + 1 );
3502 updateTableSortField( mxRange, xKey2, nOrder2, sTableFields[ nTableIndex++ ], bIsSortColumns, bMatchCase );
3504 if ( xKey3.is() )
3506 sTableFields.realloc( sTableFields.getLength() + 1 );
3507 updateTableSortField( mxRange, xKey3, nOrder3, sTableFields[ nTableIndex++ ], bIsSortColumns, bMatchCase );
3509 sortDescriptor[ nTableSortFieldIndex ].Value <<= sTableFields;
3511 sal_Int32 nIndex = findSortPropertyIndex( sortDescriptor, OUString("IsSortColumns") );
3512 sortDescriptor[ nIndex ].Value <<= bIsSortColumns;
3514 nIndex = findSortPropertyIndex( sortDescriptor, CONTS_HEADER );
3515 sortDescriptor[ nIndex ].Value <<= bContainsHeader;
3517 pDoc->SetSortParam( aSortParam, nTab );
3518 xSort->sort( sortDescriptor );
3520 // #FIXME #TODO
3521 // The SortMethod param is not processed ( not sure what its all about, need to
3522 (void)nSortMethod;
3525 uno::Reference< excel::XRange > SAL_CALL
3526 ScVbaRange::End( ::sal_Int32 Direction ) throw (uno::RuntimeException)
3528 if ( m_Areas->getCount() > 1 )
3530 uno::Reference< excel::XRange > xRange( getArea( 0 ), uno::UNO_QUERY_THROW );
3531 return xRange->End( Direction );
3534 // #FIXME #TODO
3535 // euch! found my orig implementation sucked, so
3536 // trying this even suckier one ( really need to use/expose code in
3537 // around ScTabView::MoveCursorArea(), thats the bit that calcutes
3538 // where the cursor should go )
3539 // Main problem with this method is the ultra hacky attempt to preserve
3540 // the ActiveCell, there should be no need to go to these extreems
3542 // Save ActiveCell pos ( to restore later )
3543 uno::Any aDft;
3544 uno::Reference< excel::XApplication > xApplication( Application(), uno::UNO_QUERY_THROW );
3545 OUString sActiveCell = xApplication->getActiveCell()->Address(aDft, aDft, aDft, aDft, aDft );
3547 // position current cell upper left of this range
3548 Cells( uno::makeAny( (sal_Int32) 1 ), uno::makeAny( (sal_Int32) 1 ) )->Select();
3550 uno::Reference< frame::XModel > xModel = getModelFromRange( mxRange );
3552 SfxViewFrame* pViewFrame = excel::getViewFrame( xModel );
3553 if ( pViewFrame )
3555 SfxAllItemSet aArgs( SFX_APP()->GetPool() );
3556 // Hoping this will make sure this slot is called
3557 // synchronously
3558 SfxBoolItem sfxAsync( SID_ASYNCHRON, sal_False );
3559 aArgs.Put( sfxAsync, sfxAsync.Which() );
3560 SfxDispatcher* pDispatcher = pViewFrame->GetDispatcher();
3562 sal_uInt16 nSID = 0;
3564 switch( Direction )
3566 case excel::XlDirection::xlDown:
3567 nSID = SID_CURSORBLKDOWN;
3568 break;
3569 case excel::XlDirection::xlUp:
3570 nSID = SID_CURSORBLKUP;
3571 break;
3572 case excel::XlDirection::xlToLeft:
3573 nSID = SID_CURSORBLKLEFT;
3574 break;
3575 case excel::XlDirection::xlToRight:
3576 nSID = SID_CURSORBLKRIGHT;
3577 break;
3578 default:
3579 throw uno::RuntimeException( OUString( ": Invalid ColumnIndex" ), uno::Reference< uno::XInterface >() );
3581 if ( pDispatcher )
3583 pDispatcher->Execute( nSID, (SfxCallMode)SFX_CALLMODE_SYNCHRON, aArgs );
3587 // result is the ActiveCell
3588 OUString sMoved = xApplication->getActiveCell()->Address(aDft, aDft, aDft, aDft, aDft );
3590 // restore old ActiveCell
3591 uno::Any aVoid;
3593 uno::Reference< excel::XRange > xOldActiveCell( xApplication->getActiveSheet()->Range( uno::makeAny( sActiveCell ), aVoid ), uno::UNO_QUERY_THROW );
3594 xOldActiveCell->Select();
3596 uno::Reference< excel::XRange > resultCell;
3597 resultCell.set( xApplication->getActiveSheet()->Range( uno::makeAny( sMoved ), aVoid ), uno::UNO_QUERY_THROW );
3599 // return result
3600 return resultCell;
3603 bool
3604 ScVbaRange::isSingleCellRange()
3606 uno::Reference< sheet::XCellRangeAddressable > xAddressable( mxRange, uno::UNO_QUERY );
3607 if ( xAddressable.is() )
3609 table::CellRangeAddress aRangeAddr = xAddressable->getRangeAddress();
3610 return ( aRangeAddr.EndColumn == aRangeAddr.StartColumn && aRangeAddr.EndRow == aRangeAddr.StartRow );
3612 return false;
3615 uno::Reference< excel::XCharacters > SAL_CALL
3616 ScVbaRange::characters( const uno::Any& Start, const uno::Any& Length ) throw (uno::RuntimeException)
3618 if ( !isSingleCellRange() )
3619 throw uno::RuntimeException( OUString( "Can't create Characters property for multicell range " ), uno::Reference< uno::XInterface >() );
3620 uno::Reference< text::XSimpleText > xSimple(mxRange->getCellByPosition(0,0) , uno::UNO_QUERY_THROW );
3621 ScDocument* pDoc = getDocumentFromRange(mxRange);
3622 if ( !pDoc )
3623 throw uno::RuntimeException( OUString( "Failed to access document from shell" ), uno::Reference< uno::XInterface >() );
3625 ScVbaPalette aPalette( pDoc->GetDocumentShell() );
3626 return new ScVbaCharacters( this, mxContext, aPalette, xSimple, Start, Length );
3629 void SAL_CALL
3630 ScVbaRange::Delete( const uno::Any& Shift ) throw (uno::RuntimeException)
3632 if ( m_Areas->getCount() > 1 )
3634 sal_Int32 nItems = m_Areas->getCount();
3635 for ( sal_Int32 index=1; index <= nItems; ++index )
3637 uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny(index), uno::Any() ), uno::UNO_QUERY_THROW );
3638 xRange->Delete( Shift );
3640 return;
3642 sheet::CellDeleteMode mode = sheet::CellDeleteMode_NONE ;
3643 RangeHelper thisRange( mxRange );
3644 table::CellRangeAddress thisAddress = thisRange.getCellRangeAddressable()->getRangeAddress();
3645 if ( Shift.hasValue() )
3647 sal_Int32 nShift = 0;
3648 Shift >>= nShift;
3649 switch ( nShift )
3651 case excel::XlDeleteShiftDirection::xlShiftUp:
3652 mode = sheet::CellDeleteMode_UP;
3653 break;
3654 case excel::XlDeleteShiftDirection::xlShiftToLeft:
3655 mode = sheet::CellDeleteMode_LEFT;
3656 break;
3657 default:
3658 throw uno::RuntimeException( OUString( "Illegal parameter " ), uno::Reference< uno::XInterface >() );
3661 else
3663 bool bFullRow = ( thisAddress.StartColumn == 0 && thisAddress.EndColumn == MAXCOL );
3664 sal_Int32 nCols = thisAddress.EndColumn - thisAddress.StartColumn;
3665 sal_Int32 nRows = thisAddress.EndRow - thisAddress.StartRow;
3666 if ( mbIsRows || bFullRow || ( nCols >= nRows ) )
3667 mode = sheet::CellDeleteMode_UP;
3668 else
3669 mode = sheet::CellDeleteMode_LEFT;
3671 uno::Reference< sheet::XCellRangeMovement > xCellRangeMove( thisRange.getSpreadSheet(), uno::UNO_QUERY_THROW );
3672 xCellRangeMove->removeRange( thisAddress, mode );
3676 //XElementAccess
3677 sal_Bool SAL_CALL
3678 ScVbaRange::hasElements() throw (uno::RuntimeException)
3680 uno::Reference< table::XColumnRowRange > xColumnRowRange(mxRange, uno::UNO_QUERY );
3681 if ( xColumnRowRange.is() )
3682 if ( xColumnRowRange->getRows()->getCount() ||
3683 xColumnRowRange->getColumns()->getCount() )
3684 return sal_True;
3685 return false;
3688 // XEnumerationAccess
3689 uno::Reference< container::XEnumeration > SAL_CALL
3690 ScVbaRange::createEnumeration() throw (uno::RuntimeException)
3692 if ( mbIsColumns || mbIsRows )
3694 uno::Reference< table::XColumnRowRange > xColumnRowRange(mxRange, uno::UNO_QUERY );
3695 uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny( sal_Int32(1) ), uno::Any() ), uno::UNO_QUERY_THROW );
3696 sal_Int32 nElems = 0;
3697 if ( mbIsColumns )
3698 nElems = xColumnRowRange->getColumns()->getCount();
3699 else
3700 nElems = xColumnRowRange->getRows()->getCount();
3701 return new ColumnsRowEnumeration( mxContext, xRange, nElems );
3704 return new CellsEnumeration( mxParent, mxContext, m_Areas );
3707 OUString SAL_CALL
3708 ScVbaRange::getDefaultMethodName( ) throw (uno::RuntimeException)
3710 const static OUString sName( "Item" );
3711 return sName;
3714 // returns calc internal col. width ( in points )
3715 double
3716 ScVbaRange::getCalcColWidth( const table::CellRangeAddress& rAddress) throw (uno::RuntimeException)
3718 ScDocument* pDoc = getScDocument();
3719 sal_uInt16 nWidth = pDoc->GetOriginalWidth( static_cast< SCCOL >( rAddress.StartColumn ), static_cast< SCTAB >( rAddress.Sheet ) );
3720 double nPoints = lcl_TwipsToPoints( nWidth );
3721 nPoints = lcl_Round2DecPlaces( nPoints );
3722 return nPoints;
3725 double
3726 ScVbaRange::getCalcRowHeight( const table::CellRangeAddress& rAddress ) throw (uno::RuntimeException)
3728 ScDocument* pDoc = getDocumentFromRange( mxRange );
3729 sal_uInt16 nWidth = pDoc->GetOriginalHeight( rAddress.StartRow, rAddress.Sheet );
3730 double nPoints = lcl_TwipsToPoints( nWidth );
3731 nPoints = lcl_Round2DecPlaces( nPoints );
3732 return nPoints;
3735 // return Char Width in points
3736 double getDefaultCharWidth( ScDocShell* pDocShell )
3738 ScDocument* pDoc = pDocShell->GetDocument();
3739 OutputDevice* pRefDevice = pDoc->GetRefDevice();
3740 ScPatternAttr* pAttr = pDoc->GetDefPattern();
3741 ::Font aDefFont;
3742 pAttr->GetFont( aDefFont, SC_AUTOCOL_BLACK, pRefDevice );
3743 pRefDevice->SetFont( aDefFont );
3744 long nCharWidth = pRefDevice->GetTextWidth( String( '0' ) ); // 1/100th mm
3745 return lcl_hmmToPoints( nCharWidth );
3748 uno::Any SAL_CALL
3749 ScVbaRange::getColumnWidth() throw (uno::RuntimeException)
3751 sal_Int32 nLen = m_Areas->getCount();
3752 if ( nLen > 1 )
3754 uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny( sal_Int32(1) ), uno::Any() ), uno::UNO_QUERY_THROW );
3755 return xRange->getColumnWidth();
3758 double nColWidth = 0;
3759 ScDocShell* pShell = getScDocShell();
3760 if ( pShell )
3762 double defaultCharWidth = getDefaultCharWidth( pShell );
3763 RangeHelper thisRange( mxRange );
3764 table::CellRangeAddress thisAddress = thisRange.getCellRangeAddressable()->getRangeAddress();
3765 sal_Int32 nStartCol = thisAddress.StartColumn;
3766 sal_Int32 nEndCol = thisAddress.EndColumn;
3767 sal_uInt16 nColTwips = 0;
3768 for( sal_Int32 nCol = nStartCol ; nCol <= nEndCol; ++nCol )
3770 thisAddress.StartColumn = nCol;
3771 sal_uInt16 nCurTwips = pShell->GetDocument()->GetOriginalWidth( static_cast< SCCOL >( thisAddress.StartColumn ), static_cast< SCTAB >( thisAddress.Sheet ) );
3772 if ( nCol == nStartCol )
3773 nColTwips = nCurTwips;
3774 if ( nColTwips != nCurTwips )
3775 return aNULL();
3777 nColWidth = lcl_TwipsToPoints( nColTwips );
3778 if ( nColWidth != 0.0 )
3779 nColWidth = ( nColWidth / defaultCharWidth ) - fExtraWidth;
3781 nColWidth = lcl_Round2DecPlaces( nColWidth );
3782 return uno::makeAny( nColWidth );
3785 void SAL_CALL
3786 ScVbaRange::setColumnWidth( const uno::Any& _columnwidth ) throw (uno::RuntimeException)
3788 sal_Int32 nLen = m_Areas->getCount();
3789 if ( nLen > 1 )
3791 for ( sal_Int32 index = 1; index != nLen; ++index )
3793 uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny( sal_Int32(index) ), uno::Any() ), uno::UNO_QUERY_THROW );
3794 xRange->setColumnWidth( _columnwidth );
3796 return;
3798 double nColWidth = 0;
3799 _columnwidth >>= nColWidth;
3800 nColWidth = lcl_Round2DecPlaces( nColWidth );
3801 ScDocShell* pDocShell = getScDocShell();
3802 if ( pDocShell )
3804 if ( nColWidth != 0.0 )
3805 nColWidth = ( nColWidth + fExtraWidth ) * getDefaultCharWidth( pDocShell );
3806 RangeHelper thisRange( mxRange );
3807 table::CellRangeAddress thisAddress = thisRange.getCellRangeAddressable()->getRangeAddress();
3808 sal_uInt16 nTwips = lcl_pointsToTwips( nColWidth );
3810 SCCOLROW nColArr[2];
3811 nColArr[0] = thisAddress.StartColumn;
3812 nColArr[1] = thisAddress.EndColumn;
3813 // #163561# use mode SC_SIZE_DIRECT: hide for width 0, show for other values
3814 pDocShell->GetDocFunc().SetWidthOrHeight( true, 1, nColArr, thisAddress.Sheet,
3815 SC_SIZE_DIRECT, nTwips, true, true );
3820 uno::Any SAL_CALL
3821 ScVbaRange::getWidth() throw (uno::RuntimeException)
3823 if ( m_Areas->getCount() > 1 )
3825 uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny( sal_Int32(1) ), uno::Any() ), uno::UNO_QUERY_THROW );
3826 return xRange->getWidth();
3828 uno::Reference< table::XColumnRowRange > xColRowRange( mxRange, uno::UNO_QUERY_THROW );
3829 uno::Reference< container::XIndexAccess > xIndexAccess( xColRowRange->getColumns(), uno::UNO_QUERY_THROW );
3830 sal_Int32 nElems = xIndexAccess->getCount();
3831 double nWidth = 0;
3832 for ( sal_Int32 index=0; index<nElems; ++index )
3834 uno::Reference< sheet::XCellRangeAddressable > xAddressable( xIndexAccess->getByIndex( index ), uno::UNO_QUERY_THROW );
3835 double nTmpWidth = getCalcColWidth( xAddressable->getRangeAddress() );
3836 nWidth += nTmpWidth;
3838 return uno::makeAny( nWidth );
3841 uno::Any SAL_CALL
3842 ScVbaRange::Areas( const uno::Any& item) throw (uno::RuntimeException)
3844 if ( !item.hasValue() )
3845 return uno::makeAny( m_Areas );
3846 return m_Areas->Item( item, uno::Any() );
3849 uno::Reference< excel::XRange >
3850 ScVbaRange::getArea( sal_Int32 nIndex ) throw( css::uno::RuntimeException )
3852 if ( !m_Areas.is() )
3853 throw uno::RuntimeException( OUString("No areas available"), uno::Reference< uno::XInterface >() );
3854 uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny( ++nIndex ), uno::Any() ), uno::UNO_QUERY_THROW );
3855 return xRange;
3858 uno::Any
3859 ScVbaRange::Borders( const uno::Any& item ) throw( script::BasicErrorException, uno::RuntimeException )
3861 if ( !item.hasValue() )
3862 return uno::makeAny( getBorders() );
3863 return getBorders()->Item( item, uno::Any() );
3866 uno::Any SAL_CALL
3867 ScVbaRange::BorderAround( const css::uno::Any& LineStyle, const css::uno::Any& Weight,
3868 const css::uno::Any& ColorIndex, const css::uno::Any& Color ) throw (css::uno::RuntimeException)
3870 sal_Int32 nCount = getBorders()->getCount();
3872 for( sal_Int32 i = 0; i < nCount; i++ )
3874 const sal_Int32 nLineType = supportedIndexTable[i];
3875 switch( nLineType )
3877 case excel::XlBordersIndex::xlEdgeLeft:
3878 case excel::XlBordersIndex::xlEdgeTop:
3879 case excel::XlBordersIndex::xlEdgeBottom:
3880 case excel::XlBordersIndex::xlEdgeRight:
3882 uno::Reference< excel::XBorder > xBorder( m_Borders->Item( uno::makeAny( nLineType ), uno::Any() ), uno::UNO_QUERY_THROW );
3883 if( LineStyle.hasValue() )
3885 xBorder->setLineStyle( LineStyle );
3887 if( Weight.hasValue() )
3889 xBorder->setWeight( Weight );
3891 if( ColorIndex.hasValue() )
3893 xBorder->setColorIndex( ColorIndex );
3895 if( Color.hasValue() )
3897 xBorder->setColor( Color );
3899 break;
3901 case excel::XlBordersIndex::xlInsideVertical:
3902 case excel::XlBordersIndex::xlInsideHorizontal:
3903 case excel::XlBordersIndex::xlDiagonalDown:
3904 case excel::XlBordersIndex::xlDiagonalUp:
3905 break;
3906 default:
3907 return uno::makeAny( false );
3910 return uno::makeAny( sal_True );
3913 uno::Any SAL_CALL
3914 ScVbaRange::getRowHeight() throw (uno::RuntimeException)
3916 sal_Int32 nLen = m_Areas->getCount();
3917 if ( nLen > 1 )
3919 uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny( sal_Int32(1) ), uno::Any() ), uno::UNO_QUERY_THROW );
3920 return xRange->getRowHeight();
3923 // if any row's RowHeight in the
3924 // range is different from any other then return NULL
3925 RangeHelper thisRange( mxRange );
3926 table::CellRangeAddress thisAddress = thisRange.getCellRangeAddressable()->getRangeAddress();
3928 sal_Int32 nStartRow = thisAddress.StartRow;
3929 sal_Int32 nEndRow = thisAddress.EndRow;
3930 sal_uInt16 nRowTwips = 0;
3931 // #TODO probably possible to use the SfxItemSet ( and see if
3932 // SFX_ITEM_DONTCARE is set ) to improve performance
3933 // #CHECKME looks like this is general behaviour not just row Range specific
3934 // if ( mbIsRows )
3935 ScDocShell* pShell = getScDocShell();
3936 if ( pShell )
3938 for ( sal_Int32 nRow = nStartRow ; nRow <= nEndRow; ++nRow )
3940 thisAddress.StartRow = nRow;
3941 sal_uInt16 nCurTwips = pShell->GetDocument()->GetOriginalHeight( thisAddress.StartRow, thisAddress.Sheet );
3942 if ( nRow == nStartRow )
3943 nRowTwips = nCurTwips;
3944 if ( nRowTwips != nCurTwips )
3945 return aNULL();
3948 double nHeight = lcl_Round2DecPlaces( lcl_TwipsToPoints( nRowTwips ) );
3949 return uno::makeAny( nHeight );
3952 void SAL_CALL
3953 ScVbaRange::setRowHeight( const uno::Any& _rowheight) throw (uno::RuntimeException)
3955 sal_Int32 nLen = m_Areas->getCount();
3956 if ( nLen > 1 )
3958 for ( sal_Int32 index = 1; index != nLen; ++index )
3960 uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny( sal_Int32(index) ), uno::Any() ), uno::UNO_QUERY_THROW );
3961 xRange->setRowHeight( _rowheight );
3963 return;
3965 double nHeight = 0; // Incomming height is in points
3966 _rowheight >>= nHeight;
3967 nHeight = lcl_Round2DecPlaces( nHeight );
3968 RangeHelper thisRange( mxRange );
3969 table::CellRangeAddress thisAddress = thisRange.getCellRangeAddressable()->getRangeAddress();
3970 sal_uInt16 nTwips = lcl_pointsToTwips( nHeight );
3972 ScDocShell* pDocShell = getDocShellFromRange( mxRange );
3973 SCCOLROW nRowArr[2];
3974 nRowArr[0] = thisAddress.StartRow;
3975 nRowArr[1] = thisAddress.EndRow;
3976 pDocShell->GetDocFunc().SetWidthOrHeight( false, 1, nRowArr, thisAddress.Sheet, SC_SIZE_ORIGINAL,
3977 nTwips, true, true );
3980 uno::Any SAL_CALL
3981 ScVbaRange::getPageBreak() throw (uno::RuntimeException)
3983 sal_Int32 nPageBreak = excel::XlPageBreak::xlPageBreakNone;
3984 ScDocShell* pShell = getDocShellFromRange( mxRange );
3985 if ( pShell )
3987 RangeHelper thisRange( mxRange );
3988 table::CellRangeAddress thisAddress = thisRange.getCellRangeAddressable()->getRangeAddress();
3989 sal_Bool bColumn = false;
3991 if (thisAddress.StartRow==0)
3992 bColumn = true;
3994 uno::Reference< frame::XModel > xModel = pShell->GetModel();
3995 if ( xModel.is() )
3997 ScDocument* pDoc = getDocumentFromRange( mxRange );
3999 ScBreakType nBreak = BREAK_NONE;
4000 if ( !bColumn )
4001 nBreak = pDoc->HasRowBreak(thisAddress.StartRow, thisAddress.Sheet);
4002 else
4003 nBreak = pDoc->HasColBreak(thisAddress.StartColumn, thisAddress.Sheet);
4005 if (nBreak & BREAK_PAGE)
4006 nPageBreak = excel::XlPageBreak::xlPageBreakAutomatic;
4008 if (nBreak & BREAK_MANUAL)
4009 nPageBreak = excel::XlPageBreak::xlPageBreakManual;
4013 return uno::makeAny( nPageBreak );
4016 void SAL_CALL
4017 ScVbaRange::setPageBreak( const uno::Any& _pagebreak) throw (uno::RuntimeException)
4019 sal_Int32 nPageBreak = 0;
4020 _pagebreak >>= nPageBreak;
4022 ScDocShell* pShell = getDocShellFromRange( mxRange );
4023 if ( pShell )
4025 RangeHelper thisRange( mxRange );
4026 table::CellRangeAddress thisAddress = thisRange.getCellRangeAddressable()->getRangeAddress();
4027 if ((thisAddress.StartColumn==0) && (thisAddress.StartRow==0))
4028 return;
4029 sal_Bool bColumn = false;
4031 if (thisAddress.StartRow==0)
4032 bColumn = true;
4034 ScAddress aAddr( static_cast<SCCOL>(thisAddress.StartColumn), thisAddress.StartRow, thisAddress.Sheet );
4035 uno::Reference< frame::XModel > xModel = pShell->GetModel();
4036 if ( xModel.is() )
4038 ScTabViewShell* pViewShell = excel::getBestViewShell( xModel );
4039 if ( nPageBreak == excel::XlPageBreak::xlPageBreakManual )
4040 pViewShell->InsertPageBreak( bColumn, sal_True, &aAddr);
4041 else if ( nPageBreak == excel::XlPageBreak::xlPageBreakNone )
4042 pViewShell->DeletePageBreak( bColumn, sal_True, &aAddr);
4047 uno::Any SAL_CALL
4048 ScVbaRange::getHeight() throw (uno::RuntimeException)
4050 if ( m_Areas->getCount() > 1 )
4052 uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny( sal_Int32(1) ), uno::Any() ), uno::UNO_QUERY_THROW );
4053 return xRange->getHeight();
4056 uno::Reference< table::XColumnRowRange > xColRowRange( mxRange, uno::UNO_QUERY_THROW );
4057 uno::Reference< container::XIndexAccess > xIndexAccess( xColRowRange->getRows(), uno::UNO_QUERY_THROW );
4058 sal_Int32 nElems = xIndexAccess->getCount();
4059 double nHeight = 0;
4060 for ( sal_Int32 index=0; index<nElems; ++index )
4062 uno::Reference< sheet::XCellRangeAddressable > xAddressable( xIndexAccess->getByIndex( index ), uno::UNO_QUERY_THROW );
4063 nHeight += getCalcRowHeight(xAddressable->getRangeAddress() );
4065 return uno::makeAny( nHeight );
4068 awt::Point
4069 ScVbaRange::getPosition() throw ( uno::RuntimeException )
4071 awt::Point aPoint;
4072 uno::Reference< beans::XPropertySet > xProps;
4073 if ( mxRange.is() )
4074 xProps.set( mxRange, uno::UNO_QUERY_THROW );
4075 else
4076 xProps.set( mxRanges, uno::UNO_QUERY_THROW );
4077 xProps->getPropertyValue( POSITION ) >>= aPoint;
4078 return aPoint;
4080 uno::Any SAL_CALL
4081 ScVbaRange::getLeft() throw (uno::RuntimeException)
4083 // helperapi returns the first ranges left ( and top below )
4084 if ( m_Areas->getCount() > 1 )
4085 return getArea( 0 )->getLeft();
4086 awt::Point aPoint = getPosition();
4087 return uno::makeAny( lcl_hmmToPoints( aPoint.X ) );
4091 uno::Any SAL_CALL
4092 ScVbaRange::getTop() throw (uno::RuntimeException)
4094 // helperapi returns the first ranges top
4095 if ( m_Areas->getCount() > 1 )
4096 return getArea( 0 )->getTop();
4097 awt::Point aPoint= getPosition();
4098 return uno::makeAny( lcl_hmmToPoints( aPoint.Y ) );
4102 uno::Reference< sheet::XCellRangeReferrer > getNamedRange( const uno::Reference< uno::XInterface >& xIf, const uno::Reference< table::XCellRange >& thisRange )
4104 uno::Reference< beans::XPropertySet > xProps( xIf, uno::UNO_QUERY_THROW );
4105 uno::Reference< container::XNameAccess > xNameAccess( xProps->getPropertyValue( "NamedRanges" ), uno::UNO_QUERY_THROW );
4107 uno::Sequence< OUString > sNames = xNameAccess->getElementNames();
4108 // uno::Reference< table::XCellRange > thisRange( getCellRange(), uno::UNO_QUERY_THROW );
4109 uno::Reference< sheet::XCellRangeReferrer > xNamedRange;
4110 for ( sal_Int32 i=0; i < sNames.getLength(); ++i )
4112 uno::Reference< sheet::XCellRangeReferrer > xName( xNameAccess->getByName( sNames[ i ] ), uno::UNO_QUERY );
4113 if ( xName.is() )
4115 if ( thisRange == xName->getReferredCells() )
4117 xNamedRange = xName;
4118 break;
4122 return xNamedRange;
4125 uno::Reference< excel::XName >
4126 ScVbaRange::getName() throw (uno::RuntimeException)
4128 uno::Reference< beans::XPropertySet > xProps( getUnoModel(), uno::UNO_QUERY );
4129 uno::Reference< table::XCellRange > thisRange( getCellRange(), uno::UNO_QUERY_THROW );
4130 // Application range
4131 uno::Reference< sheet::XCellRangeReferrer > xNamedRange = getNamedRange( xProps, thisRange );
4133 if ( !xNamedRange.is() )
4135 // not in application range then assume it might be in
4136 // sheet namedranges
4137 RangeHelper aRange( thisRange );
4138 uno::Reference< sheet::XSpreadsheet > xSheet = aRange.getSpreadSheet();
4139 xProps.set( xSheet, uno::UNO_QUERY );
4140 // impl here
4141 xNamedRange = getNamedRange( xProps, thisRange );
4143 if ( xProps.is() && xNamedRange.is() )
4145 uno::Reference< sheet::XNamedRanges > xNamedRanges( xProps, uno::UNO_QUERY_THROW );
4146 uno::Reference< sheet::XNamedRange > xName( xNamedRange, uno::UNO_QUERY_THROW );
4147 return new ScVbaName( mxParent, mxContext, xName, xNamedRanges, getUnoModel() );
4149 return uno::Reference< excel::XName >();
4152 uno::Reference< excel::XWorksheet >
4153 ScVbaRange::getWorksheet() throw (uno::RuntimeException)
4155 // #TODO #FIXME parent should always be set up ( currently thats not
4156 // the case )
4157 uno::Reference< excel::XWorksheet > xSheet( getParent(), uno::UNO_QUERY );
4158 if ( !xSheet.is() )
4160 uno::Reference< table::XCellRange > xRange = mxRange;
4162 if ( mxRanges.is() ) // assign xRange to first range
4164 uno::Reference< container::XIndexAccess > xIndex( mxRanges, uno::UNO_QUERY_THROW );
4165 xRange.set( xIndex->getByIndex( 0 ), uno::UNO_QUERY_THROW );
4167 ScDocShell* pDocShell = getDocShellFromRange(xRange);
4168 RangeHelper rHelper(xRange);
4169 // parent should be Thisworkbook
4170 xSheet.set( new ScVbaWorksheet( uno::Reference< XHelperInterface >(), mxContext,rHelper.getSpreadSheet(),pDocShell->GetModel()) );
4172 return xSheet;
4175 // #TODO remove this ugly application processing
4176 // Process an application Range request e.g. 'Range("a1,b2,a4:b6")
4177 uno::Reference< excel::XRange >
4178 ScVbaRange::ApplicationRange( const uno::Reference< uno::XComponentContext >& xContext, const css::uno::Any &Cell1, const css::uno::Any &Cell2 ) throw (css::uno::RuntimeException)
4180 // Althought the documentation seems clear that Range without a
4181 // qualifier then its a shortcut for ActiveSheet.Range
4182 // however, similarly Application.Range is apparently also a
4183 // shortcut for ActiveSheet.Range
4184 // The is however a subtle behavioural difference I've come across
4185 // wrt to named ranges.
4186 // If a named range "test" exists { Sheet1!$A1 } and the active sheet
4187 // is Sheet2 then the following will fail
4188 // msgbox ActiveSheet.Range("test").Address ' failes
4189 // msgbox WorkSheets("Sheet2").Range("test").Address
4190 // but !!!
4191 // msgbox Range("test").Address ' works
4192 // msgbox Application.Range("test").Address ' works
4194 // Single param Range
4195 OUString sRangeName;
4196 Cell1 >>= sRangeName;
4197 if ( Cell1.hasValue() && !Cell2.hasValue() && !sRangeName.isEmpty() )
4199 const static OUString sNamedRanges( "NamedRanges");
4200 uno::Reference< beans::XPropertySet > xPropSet( getCurrentExcelDoc(xContext), uno::UNO_QUERY_THROW );
4202 uno::Reference< container::XNameAccess > xNamed( xPropSet->getPropertyValue( sNamedRanges ), uno::UNO_QUERY_THROW );
4203 uno::Reference< sheet::XCellRangeReferrer > xReferrer;
4206 xReferrer.set ( xNamed->getByName( sRangeName ), uno::UNO_QUERY );
4208 catch( uno::Exception& /*e*/ )
4210 // do nothing
4212 if ( xReferrer.is() )
4214 uno::Reference< table::XCellRange > xRange = xReferrer->getReferredCells();
4215 if ( xRange.is() )
4217 uno::Reference< excel::XRange > xVbRange = new ScVbaRange( excel::getUnoSheetModuleObj( xRange ), xContext, xRange );
4218 return xVbRange;
4223 uno::Reference< sheet::XSpreadsheetView > xView( getCurrentExcelDoc(xContext)->getCurrentController(), uno::UNO_QUERY );
4224 uno::Reference< table::XCellRange > xSheetRange( xView->getActiveSheet(), uno::UNO_QUERY_THROW );
4225 ScVbaRange* pRange = new ScVbaRange( excel::getUnoSheetModuleObj( xSheetRange ), xContext, xSheetRange );
4226 uno::Reference< excel::XRange > xVbSheetRange( pRange );
4227 return pRange->Range( Cell1, Cell2, true );
4230 // Helper functions for AutoFilter
4231 static ScDBData* lcl_GetDBData_Impl( ScDocShell* pDocShell, sal_Int16 nSheet )
4233 ScDBData* pRet = NULL;
4234 if (pDocShell)
4236 pRet = pDocShell->GetDocument()->GetAnonymousDBData(nSheet);
4238 return pRet;
4241 static void lcl_SelectAll( ScDocShell* pDocShell, ScQueryParam& aParam )
4243 if ( pDocShell )
4245 ScViewData* pViewData = pDocShell->GetViewData();
4246 if ( pViewData )
4248 OSL_TRACE("Pushing out SelectAll query");
4249 pViewData->GetView()->Query( aParam, NULL, sal_True );
4254 static ScQueryParam lcl_GetQueryParam( ScDocShell* pDocShell, sal_Int16 nSheet )
4256 ScDBData* pDBData = lcl_GetDBData_Impl( pDocShell, nSheet );
4257 ScQueryParam aParam;
4258 if (pDBData)
4260 pDBData->GetQueryParam( aParam );
4262 return aParam;
4265 static void lcl_SetAllQueryForField( ScDocShell* pDocShell, SCCOLROW nField, sal_Int16 nSheet )
4267 ScQueryParam aParam = lcl_GetQueryParam( pDocShell, nSheet );
4268 aParam.RemoveEntryByField(nField);
4269 lcl_SelectAll( pDocShell, aParam );
4272 // Modifies sCriteria, and nOp depending on the value of sCriteria
4273 static void lcl_setTableFieldsFromCriteria( OUString& sCriteria1, uno::Reference< beans::XPropertySet >& xDescProps, sheet::TableFilterField2& rFilterField )
4275 // #TODO make this more efficient and cycle through
4276 // sCriteria1 character by character to pick up <,<>,=, * etc.
4277 // right now I am more concerned with just getting it to work right
4279 sCriteria1 = sCriteria1.trim();
4280 // table of translation of criteria text to FilterOperators
4281 // <>searchtext - NOT_EQUAL
4282 // =searchtext - EQUAL
4283 // *searchtext - startwith
4284 // <>*searchtext - doesn't startwith
4285 // *searchtext* - contains
4286 // <>*searchtext* - doesn't contain
4287 // [>|>=|<=|...]searchtext for GREATER_value, GREATER_EQUAL_value etc.
4288 sal_Int32 nPos = 0;
4289 bool bIsNumeric = false;
4290 if ( ( nPos = sCriteria1.indexOf( EQUALS ) ) == 0 )
4292 if ( sCriteria1.getLength() == EQUALS.getLength() )
4293 rFilterField.Operator = sheet::FilterOperator2::EMPTY;
4294 else
4296 rFilterField.Operator = sheet::FilterOperator2::EQUAL;
4297 sCriteria1 = sCriteria1.copy( EQUALS.getLength() );
4298 sCriteria1 = VBAToRegexp( sCriteria1 );
4299 // UseRegularExpressions
4300 if ( xDescProps.is() )
4301 xDescProps->setPropertyValue( "UseRegularExpressions", uno::Any( sal_True ) );
4305 else if ( ( nPos = sCriteria1.indexOf( NOTEQUALS ) ) == 0 )
4307 if ( sCriteria1.getLength() == NOTEQUALS.getLength() )
4308 rFilterField.Operator = sheet::FilterOperator2::NOT_EMPTY;
4309 else
4311 rFilterField.Operator = sheet::FilterOperator2::NOT_EQUAL;
4312 sCriteria1 = sCriteria1.copy( NOTEQUALS.getLength() );
4313 sCriteria1 = VBAToRegexp( sCriteria1 );
4314 // UseRegularExpressions
4315 if ( xDescProps.is() )
4316 xDescProps->setPropertyValue( "UseRegularExpressions", uno::Any( sal_True ) );
4319 else if ( ( nPos = sCriteria1.indexOf( GREATERTHAN ) ) == 0 )
4321 bIsNumeric = true;
4322 if ( ( nPos = sCriteria1.indexOf( GREATERTHANEQUALS ) ) == 0 )
4324 sCriteria1 = sCriteria1.copy( GREATERTHANEQUALS.getLength() );
4325 rFilterField.Operator = sheet::FilterOperator2::GREATER_EQUAL;
4327 else
4329 sCriteria1 = sCriteria1.copy( GREATERTHAN.getLength() );
4330 rFilterField.Operator = sheet::FilterOperator2::GREATER;
4334 else if ( ( nPos = sCriteria1.indexOf( LESSTHAN ) ) == 0 )
4336 bIsNumeric = true;
4337 if ( ( nPos = sCriteria1.indexOf( LESSTHANEQUALS ) ) == 0 )
4339 sCriteria1 = sCriteria1.copy( LESSTHANEQUALS.getLength() );
4340 rFilterField.Operator = sheet::FilterOperator2::LESS_EQUAL;
4342 else
4344 sCriteria1 = sCriteria1.copy( LESSTHAN.getLength() );
4345 rFilterField.Operator = sheet::FilterOperator2::LESS;
4349 else
4350 rFilterField.Operator = sheet::FilterOperator2::EQUAL;
4352 if ( bIsNumeric )
4354 rFilterField.IsNumeric= sal_True;
4355 rFilterField.NumericValue = sCriteria1.toDouble();
4357 rFilterField.StringValue = sCriteria1;
4360 void SAL_CALL
4361 ScVbaRange::AutoFilter( const uno::Any& aField, const uno::Any& Criteria1, const uno::Any& Operator, const uno::Any& Criteria2, const uno::Any& VisibleDropDown ) throw (uno::RuntimeException)
4363 // Is there an existing autofilter
4364 RangeHelper thisRange( mxRange );
4365 table::CellRangeAddress thisAddress = thisRange.getCellRangeAddressable()->getRangeAddress();
4366 sal_Int16 nSheet = thisAddress.Sheet;
4367 ScDocShell* pShell = getScDocShell();
4368 sal_Bool bHasAuto = false;
4369 uno::Reference< sheet::XDatabaseRange > xDataBaseRange = excel::GetAutoFiltRange( pShell, nSheet );
4370 if ( xDataBaseRange.is() )
4371 bHasAuto = true;
4373 uno::Reference< table::XCellRange > xFilterRange;
4374 if ( !bHasAuto )
4376 if ( m_Areas->getCount() > 1 )
4377 throw uno::RuntimeException( STR_ERRORMESSAGE_APPLIESTOSINGLERANGEONLY, uno::Reference< uno::XInterface >() );
4379 table::CellRangeAddress autoFiltAddress;
4380 //CurrentRegion()
4381 if ( isSingleCellRange() )
4383 uno::Reference< excel::XRange > xCurrent( CurrentRegion() );
4384 if ( xCurrent.is() )
4386 ScVbaRange* pRange = getImplementation( xCurrent );
4387 if ( pRange )
4389 if ( pRange->isSingleCellRange() )
4390 throw uno::RuntimeException( OUString( "Can't create AutoFilter" ), uno::Reference< uno::XInterface >() );
4391 RangeHelper currentRegion( pRange->mxRange );
4392 autoFiltAddress = currentRegion.getCellRangeAddressable()->getRangeAddress();
4396 else // multi-cell range
4398 RangeHelper multiCellRange( mxRange );
4399 autoFiltAddress = multiCellRange.getCellRangeAddressable()->getRangeAddress();
4400 // #163530# Filter box shows only entry of first row
4401 ScDocument* pDocument = ( pShell ? pShell->GetDocument() : NULL );
4402 if ( pDocument )
4404 SCCOL nStartCol = autoFiltAddress.StartColumn;
4405 SCROW nStartRow = autoFiltAddress.StartRow;
4406 SCCOL nEndCol = autoFiltAddress.EndColumn;
4407 SCROW nEndRow = autoFiltAddress.EndRow;
4408 pDocument->GetDataArea( autoFiltAddress.Sheet, nStartCol, nStartRow, nEndCol, nEndRow, true, true );
4409 autoFiltAddress.StartColumn = nStartCol;
4410 autoFiltAddress.StartRow = nStartRow;
4411 autoFiltAddress.EndColumn = nEndCol;
4412 autoFiltAddress.EndRow = nEndRow;
4416 uno::Reference< sheet::XUnnamedDatabaseRanges > xDBRanges = excel::GetUnnamedDataBaseRanges( pShell );
4417 if ( xDBRanges.is() )
4419 OSL_TRACE("Going to add new autofilter range.. sheet %i", nSheet );
4420 if ( !xDBRanges->hasByTable( nSheet ) )
4421 xDBRanges->setByTable( autoFiltAddress );
4422 xDataBaseRange.set( xDBRanges->getByTable(nSheet ), uno::UNO_QUERY_THROW );
4424 if ( !xDataBaseRange.is() )
4425 throw uno::RuntimeException( OUString( "Failed to find the autofilter placeholder range" ), uno::Reference< uno::XInterface >() );
4427 uno::Reference< beans::XPropertySet > xDBRangeProps( xDataBaseRange, uno::UNO_QUERY_THROW );
4428 // set autofilt
4429 xDBRangeProps->setPropertyValue( "AutoFilter", uno::Any(sal_True) );
4430 // set header (autofilter always need column headers)
4431 uno::Reference< beans::XPropertySet > xFiltProps( xDataBaseRange->getFilterDescriptor(), uno::UNO_QUERY_THROW );
4432 sal_Bool bHasColHeader = false;
4433 ScDocument* pDoc = pShell ? pShell->GetDocument() : NULL;
4435 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 : false;
4436 xFiltProps->setPropertyValue( "ContainsHeader", uno::Any( bHasColHeader ) );
4440 sal_Int32 nField = 0; // *IS* 1 based
4441 OUString sCriteria1;
4442 sal_Int32 nOperator = excel::XlAutoFilterOperator::xlAnd;
4444 sal_Bool bVisible = sal_True;
4445 VisibleDropDown >>= bVisible;
4447 if ( bVisible == bHasAuto ) // dropdown is displayed/notdisplayed as required
4448 bVisible = false;
4449 sheet::FilterConnection nConn = sheet::FilterConnection_AND;
4450 double nCriteria1 = 0;
4452 bool bHasCritValue = Criteria1.hasValue();
4453 bool bCritHasNumericValue = false; // not sure if a numeric criteria is possible
4454 if ( bHasCritValue )
4455 bCritHasNumericValue = ( Criteria1 >>= nCriteria1 );
4457 if ( !aField.hasValue() && ( Criteria1.hasValue() || Operator.hasValue() || Criteria2.hasValue() ) )
4458 throw uno::RuntimeException();
4459 bool bAll = false;
4460 uno::Any Field( aField );
4461 if ( !( Field >>= nField ) )
4463 uno::Reference< script::XTypeConverter > xConverter = getTypeConverter( mxContext );
4466 Field = xConverter->convertTo( aField, getCppuType( (sal_Int32*)0 ) );
4468 catch( uno::Exception& )
4472 // Use the normal uno api, sometimes e.g. when you want to use ALL as the filter
4473 // we can't use refresh as the uno interface doesn't have a concept of ALL
4474 // in this case we just call the core calc functionality -
4475 if ( ( Field >>= nField ) )
4477 uno::Reference< sheet::XSheetFilterDescriptor2 > xDesc(
4478 xDataBaseRange->getFilterDescriptor(), uno::UNO_QUERY );
4479 if ( xDesc.is() )
4481 uno::Sequence< sheet::TableFilterField2 > sTabFilts;
4482 uno::Reference< beans::XPropertySet > xDescProps( xDesc, uno::UNO_QUERY_THROW );
4483 if ( Criteria1.hasValue() )
4485 sTabFilts.realloc( 1 );
4486 sTabFilts[0].Operator = sheet::FilterOperator2::EQUAL;// sensible default
4487 if ( !bCritHasNumericValue )
4489 Criteria1 >>= sCriteria1;
4490 sTabFilts[0].IsNumeric = bCritHasNumericValue;
4491 if ( bHasCritValue && !sCriteria1.isEmpty() )
4492 lcl_setTableFieldsFromCriteria( sCriteria1, xDescProps, sTabFilts[0] );
4493 else
4494 bAll = true;
4496 else // numeric
4498 sTabFilts[0].IsNumeric = sal_True;
4499 sTabFilts[0].NumericValue = nCriteria1;
4502 else // no value specified
4503 bAll = true;
4504 // not sure what the relationship between Criteria1 and Operator is,
4505 // e.g. can you have a Operator without a Criteria ? in openoffice it
4506 if ( Operator.hasValue() && ( Operator >>= nOperator ) )
4508 // if its a bottom/top Ten(Percent/Value) and there
4509 // is no value specified for criteria1 set it to 10
4510 if ( !bCritHasNumericValue && sCriteria1.isEmpty() && ( nOperator != excel::XlAutoFilterOperator::xlOr ) && ( nOperator != excel::XlAutoFilterOperator::xlAnd ) )
4512 sTabFilts[0].IsNumeric = sal_True;
4513 sTabFilts[0].NumericValue = 10;
4514 bAll = false;
4516 switch ( nOperator )
4518 case excel::XlAutoFilterOperator::xlBottom10Items:
4519 sTabFilts[0].Operator = sheet::FilterOperator2::BOTTOM_VALUES;
4520 break;
4521 case excel::XlAutoFilterOperator::xlBottom10Percent:
4522 sTabFilts[0].Operator = sheet::FilterOperator2::BOTTOM_PERCENT;
4523 break;
4524 case excel::XlAutoFilterOperator::xlTop10Items:
4525 sTabFilts[0].Operator = sheet::FilterOperator2::TOP_VALUES;
4526 break;
4527 case excel::XlAutoFilterOperator::xlTop10Percent:
4528 sTabFilts[0].Operator = sheet::FilterOperator2::TOP_PERCENT;
4529 break;
4530 case excel::XlAutoFilterOperator::xlOr:
4531 nConn = sheet::FilterConnection_OR;
4532 break;
4533 case excel::XlAutoFilterOperator::xlAnd:
4534 nConn = sheet::FilterConnection_AND;
4535 break;
4536 default:
4537 throw uno::RuntimeException( OUString( "UnknownOption" ), uno::Reference< uno::XInterface >() );
4542 if ( !bAll )
4544 sTabFilts[0].Connection = sheet::FilterConnection_AND;
4545 sTabFilts[0].Field = (nField - 1);
4547 OUString sCriteria2;
4548 if ( Criteria2.hasValue() ) // there is a Criteria2
4550 sTabFilts.realloc(2);
4551 sTabFilts[1].Field = sTabFilts[0].Field;
4552 sTabFilts[1].Connection = nConn;
4554 if ( Criteria2 >>= sCriteria2 )
4556 if ( !sCriteria2.isEmpty() )
4558 uno::Reference< beans::XPropertySet > xProps;
4559 lcl_setTableFieldsFromCriteria( sCriteria2, xProps, sTabFilts[1] );
4560 sTabFilts[1].IsNumeric = false;
4563 else // numeric
4565 Criteria2 >>= sTabFilts[1].NumericValue;
4566 sTabFilts[1].IsNumeric = sal_True;
4567 sTabFilts[1].Operator = sheet::FilterOperator2::EQUAL;
4572 xDesc->setFilterFields2( sTabFilts );
4573 if ( !bAll )
4575 xDataBaseRange->refresh();
4577 else
4578 // was 0 based now seems to be 1
4579 lcl_SetAllQueryForField( pShell, nField, nSheet );
4582 else
4584 // this is just to toggle autofilter on and off ( not to be confused with
4585 // a VisibleDropDown option combined with a field, in that case just the
4586 // button should be disabled ) - currently we don't support that
4587 uno::Reference< beans::XPropertySet > xDBRangeProps( xDataBaseRange, uno::UNO_QUERY_THROW );
4588 if ( bHasAuto )
4590 // find the any field with the query and select all
4591 ScQueryParam aParam = lcl_GetQueryParam( pShell, nSheet );
4592 for (SCSIZE i = 0; i< aParam.GetEntryCount(); ++i)
4594 ScQueryEntry& rEntry = aParam.GetEntry(i);
4595 if ( rEntry.bDoQuery )
4596 lcl_SetAllQueryForField( pShell, rEntry.nField, nSheet );
4598 // remove exising filters
4599 uno::Reference< sheet::XSheetFilterDescriptor2 > xSheetFilterDescriptor(
4600 xDataBaseRange->getFilterDescriptor(), uno::UNO_QUERY );
4601 if( xSheetFilterDescriptor.is() )
4602 xSheetFilterDescriptor->setFilterFields2( uno::Sequence< sheet::TableFilterField2 >() );
4604 xDBRangeProps->setPropertyValue( "AutoFilter", uno::Any(!bHasAuto) );
4609 void SAL_CALL
4610 ScVbaRange::Insert( const uno::Any& Shift, const uno::Any& /*CopyOrigin*/ ) throw (uno::RuntimeException)
4612 // It appears ( from the web ) that the undocumented CopyOrigin
4613 // param should contain member of enum XlInsertFormatOrigin
4614 // which can have values xlFormatFromLeftOrAbove or xlFormatFromRightOrBelow
4615 // #TODO investigate resultant behaviour using these constants
4616 // currently just processing Shift
4618 sheet::CellInsertMode mode = sheet::CellInsertMode_NONE;
4619 if ( Shift.hasValue() )
4621 sal_Int32 nShift = 0;
4622 Shift >>= nShift;
4623 switch ( nShift )
4625 case excel::XlInsertShiftDirection::xlShiftToRight:
4626 mode = sheet::CellInsertMode_RIGHT;
4627 break;
4628 case excel::XlInsertShiftDirection::xlShiftDown:
4629 mode = sheet::CellInsertMode_DOWN;
4630 break;
4631 default:
4632 throw uno::RuntimeException( OUString( "Illegal parameter " ), uno::Reference< uno::XInterface >() );
4635 else
4637 if ( getRow() >= getColumn() )
4638 mode = sheet::CellInsertMode_DOWN;
4639 else
4640 mode = sheet::CellInsertMode_RIGHT;
4642 RangeHelper thisRange( mxRange );
4643 table::CellRangeAddress thisAddress = thisRange.getCellRangeAddressable()->getRangeAddress();
4644 uno::Reference< sheet::XCellRangeMovement > xCellRangeMove( thisRange.getSpreadSheet(), uno::UNO_QUERY_THROW );
4645 xCellRangeMove->insertCells( thisAddress, mode );
4647 // Paste from clipboard only if the clipboard content was copied via VBA, and not already pasted via VBA again.
4648 // "Insert" behavior should not depend on random clipboard content previously copied by the user.
4649 ScTransferObj* pClipObj = ScTransferObj::GetOwnClipboard( NULL );
4650 if ( pClipObj && pClipObj->GetUseInApi() )
4652 // After the insert ( this range ) actually has moved
4653 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 ) );
4654 uno::Reference< table::XCellRange > xRange( new ScCellRangeObj( getDocShellFromRange( mxRange ) , aRange ) );
4655 uno::Reference< excel::XRange > xVbaRange( new ScVbaRange( mxParent, mxContext, xRange, mbIsRows, mbIsColumns ) );
4656 xVbaRange->PasteSpecial( uno::Any(), uno::Any(), uno::Any(), uno::Any() );
4660 void SAL_CALL
4661 ScVbaRange::Autofit() throw (uno::RuntimeException)
4663 sal_Int32 nLen = m_Areas->getCount();
4664 if ( nLen > 1 )
4666 for ( sal_Int32 index = 1; index != nLen; ++index )
4668 uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny( sal_Int32(index) ), uno::Any() ), uno::UNO_QUERY_THROW );
4669 xRange->Autofit();
4671 return;
4673 // if the range is a not a row or column range autofit will
4674 // throw an error
4676 if ( !( mbIsColumns || mbIsRows ) )
4677 DebugHelper::exception(SbERR_METHOD_FAILED, OUString());
4678 ScDocShell* pDocShell = getDocShellFromRange( mxRange );
4679 if ( pDocShell )
4681 RangeHelper thisRange( mxRange );
4682 table::CellRangeAddress thisAddress = thisRange.getCellRangeAddressable()->getRangeAddress();
4684 SCCOLROW nColArr[2];
4685 nColArr[0] = thisAddress.StartColumn;
4686 nColArr[1] = thisAddress.EndColumn;
4687 sal_Bool bDirection = sal_True;
4688 if ( mbIsRows )
4690 bDirection = false;
4691 nColArr[0] = thisAddress.StartRow;
4692 nColArr[1] = thisAddress.EndRow;
4694 pDocShell->GetDocFunc().SetWidthOrHeight( bDirection, 1, nColArr, thisAddress.Sheet,
4695 SC_SIZE_OPTIMAL, 0, true, true );
4699 uno::Any SAL_CALL
4700 ScVbaRange::Hyperlinks( const uno::Any& aIndex ) throw (uno::RuntimeException)
4702 /* The range object always returns a new Hyperlinks object containing a
4703 fixed list of existing hyperlinks in the range.
4704 See vbahyperlinks.hxx for more details. */
4706 // get the global hyperlink object of the sheet (sheet should always be the parent of a Range object)
4707 uno::Reference< excel::XWorksheet > xWorksheet( getParent(), uno::UNO_QUERY_THROW );
4708 uno::Reference< excel::XHyperlinks > xSheetHlinks( xWorksheet->Hyperlinks( uno::Any() ), uno::UNO_QUERY_THROW );
4709 ScVbaHyperlinksRef xScSheetHlinks( dynamic_cast< ScVbaHyperlinks* >( xSheetHlinks.get() ) );
4710 if( !xScSheetHlinks.is() )
4711 throw uno::RuntimeException( OUString( "Cannot obtain hyperlinks implementation object" ), uno::Reference< uno::XInterface >() );
4713 // create a new local hyperlinks object based on the sheet hyperlinks
4714 ScVbaHyperlinksRef xHlinks( new ScVbaHyperlinks( getParent(), mxContext, xScSheetHlinks, getScRangeList() ) );
4715 if( aIndex.hasValue() )
4716 return xHlinks->Item( aIndex, uno::Any() );
4717 return uno::Any( uno::Reference< excel::XHyperlinks >( xHlinks.get() ) );
4720 css::uno::Reference< excel::XValidation > SAL_CALL
4721 ScVbaRange::getValidation() throw (css::uno::RuntimeException)
4723 if ( !m_xValidation.is() )
4724 m_xValidation = new ScVbaValidation( this, mxContext, mxRange );
4725 return m_xValidation;
4728 namespace {
4730 sal_Unicode lclGetPrefixChar( const uno::Reference< table::XCell >& rxCell ) throw (uno::RuntimeException)
4732 /* TODO/FIXME: We need an apostroph-prefix property at the cell to
4733 implement this correctly. For now, return an apostroph for every text
4734 cell.
4736 TODO/FIXME: When Application.TransitionNavigKeys is supported and true,
4737 this function needs to inspect the cell formatting and return different
4738 prefixes according to the horizontal cell alignment.
4740 return (rxCell->getType() == table::CellContentType_TEXT) ? '\'' : 0;
4743 sal_Unicode lclGetPrefixChar( const uno::Reference< table::XCellRange >& rxRange ) throw (uno::RuntimeException)
4745 /* This implementation is able to handle different prefixes (needed if
4746 Application.TransitionNavigKeys is true). The function lclGetPrefixChar
4747 for single cells called from here may return any prefix. If that
4748 function returns an empty prefix (NUL character) or different non-empty
4749 prefixes for two cells, this function returns 0.
4751 sal_Unicode cCurrPrefix = 0;
4752 table::CellRangeAddress aRangeAddr = lclGetRangeAddress( rxRange );
4753 sal_Int32 nEndCol = aRangeAddr.EndColumn - aRangeAddr.StartColumn;
4754 sal_Int32 nEndRow = aRangeAddr.EndRow - aRangeAddr.StartRow;
4755 for( sal_Int32 nRow = 0; nRow <= nEndRow; ++nRow )
4757 for( sal_Int32 nCol = 0; nCol <= nEndCol; ++nCol )
4759 uno::Reference< table::XCell > xCell( rxRange->getCellByPosition( nCol, nRow ), uno::UNO_SET_THROW );
4760 sal_Unicode cNewPrefix = lclGetPrefixChar( xCell );
4761 if( (cNewPrefix == 0) || ((cCurrPrefix != 0) && (cNewPrefix != cCurrPrefix)) )
4762 return 0;
4763 cCurrPrefix = cNewPrefix;
4766 // all cells contain the same prefix - return it
4767 return cCurrPrefix;
4770 sal_Unicode lclGetPrefixChar( const uno::Reference< sheet::XSheetCellRangeContainer >& rxRanges ) throw (uno::RuntimeException)
4772 sal_Unicode cCurrPrefix = 0;
4773 uno::Reference< container::XEnumerationAccess > xRangesEA( rxRanges, uno::UNO_QUERY_THROW );
4774 uno::Reference< container::XEnumeration > xRangesEnum( xRangesEA->createEnumeration(), uno::UNO_SET_THROW );
4775 while( xRangesEnum->hasMoreElements() )
4777 uno::Reference< table::XCellRange > xRange( xRangesEnum->nextElement(), uno::UNO_QUERY_THROW );
4778 sal_Unicode cNewPrefix = lclGetPrefixChar( xRange );
4779 if( (cNewPrefix == 0) || ((cCurrPrefix != 0) && (cNewPrefix != cCurrPrefix)) )
4780 return 0;
4781 cCurrPrefix = cNewPrefix;
4783 // all ranges contain the same prefix - return it
4784 return cCurrPrefix;
4787 inline uno::Any lclGetPrefixVariant( sal_Unicode cPrefixChar )
4789 return uno::Any( (cPrefixChar == 0) ? OUString() : OUString( cPrefixChar ) );
4792 } // namespace
4794 uno::Any SAL_CALL ScVbaRange::getPrefixCharacter() throw (uno::RuntimeException)
4796 /* (1) If Application.TransitionNavigKeys is false, this function returns
4797 an apostroph character if the text cell begins with an apostroph
4798 character (formula return values are not taken into account); otherwise
4799 an empty string.
4801 (2) If Application.TransitionNavigKeys is true, this function returns
4802 an apostroph character, if the cell is left-aligned; a double-quote
4803 character, if the cell is right-aligned; a circumflex character, if the
4804 cell is centered; a backslash character, if the cell is set to filled;
4805 or an empty string, if nothing of the above.
4807 If a range or a list of ranges contains texts with leading apostroph
4808 character as well as other cells, this function returns an empty
4809 string.
4812 if( mxRange.is() )
4813 return lclGetPrefixVariant( lclGetPrefixChar( mxRange ) );
4814 if( mxRanges.is() )
4815 return lclGetPrefixVariant( lclGetPrefixChar( mxRanges ) );
4816 throw uno::RuntimeException( OUString( "Unexpected empty Range object" ), uno::Reference< uno::XInterface >() );
4819 uno::Any ScVbaRange::getShowDetail() throw ( css::uno::RuntimeException)
4821 // #FIXME, If the specified range is in a PivotTable report
4823 // In MSO VBA, the specified range must be a single summary column or row in an outline. otherwise throw exception
4824 if( m_Areas->getCount() > 1 )
4825 throw uno::RuntimeException( OUString( "Can not get Range.ShowDetail attribute "), uno::Reference< uno::XInterface >() );
4827 sal_Bool bShowDetail = false;
4829 RangeHelper helper( mxRange );
4830 uno::Reference< sheet::XSheetCellCursor > xSheetCellCursor = helper.getSheetCellCursor();
4831 xSheetCellCursor->collapseToCurrentRegion();
4832 uno::Reference< sheet::XCellRangeAddressable > xCellRangeAddressable(xSheetCellCursor, uno::UNO_QUERY_THROW);
4833 table::CellRangeAddress aOutlineAddress = xCellRangeAddressable->getRangeAddress();
4835 // check if the specified range is a single summary column or row.
4836 table::CellRangeAddress thisAddress = helper.getCellRangeAddressable()->getRangeAddress();
4837 if( (thisAddress.StartRow == thisAddress.EndRow && thisAddress.EndRow == aOutlineAddress.EndRow ) ||
4838 (thisAddress.StartColumn == thisAddress.EndColumn && thisAddress.EndColumn == aOutlineAddress.EndColumn ))
4840 sal_Bool bColumn =thisAddress.StartRow == thisAddress.EndRow ? false:sal_True;
4841 ScDocument* pDoc = getDocumentFromRange( mxRange );
4842 ScOutlineTable* pOutlineTable = pDoc->GetOutlineTable(static_cast<SCTAB>(thisAddress.Sheet), sal_True);
4843 const ScOutlineArray* pOutlineArray = bColumn ? pOutlineTable->GetColArray(): pOutlineTable->GetRowArray();
4844 if( pOutlineArray )
4846 SCCOLROW nPos = bColumn ? (SCCOLROW)(thisAddress.EndColumn-1):(SCCOLROW)(thisAddress.EndRow-1);
4847 const ScOutlineEntry* pEntry = pOutlineArray->GetEntryByPos( 0, nPos );
4848 if( pEntry )
4850 bShowDetail = !pEntry->IsHidden();
4851 return uno::makeAny( bShowDetail );
4855 else
4857 throw uno::RuntimeException( OUString( "Can not set Range.ShowDetail attribute "), uno::Reference< uno::XInterface >() );
4859 return aNULL();
4862 void ScVbaRange::setShowDetail(const uno::Any& aShowDetail) throw ( css::uno::RuntimeException)
4864 // #FIXME, If the specified range is in a PivotTable report
4866 // In MSO VBA, the specified range must be a single summary column or row in an outline. otherwise throw exception
4867 if( m_Areas->getCount() > 1 )
4868 throw uno::RuntimeException( OUString( "Can not set Range.ShowDetail attribute "), uno::Reference< uno::XInterface >() );
4870 bool bShowDetail = extractBoolFromAny( aShowDetail );
4872 RangeHelper helper( mxRange );
4873 uno::Reference< sheet::XSheetCellCursor > xSheetCellCursor = helper.getSheetCellCursor();
4874 xSheetCellCursor->collapseToCurrentRegion();
4875 uno::Reference< sheet::XCellRangeAddressable > xCellRangeAddressable(xSheetCellCursor, uno::UNO_QUERY_THROW);
4876 table::CellRangeAddress aOutlineAddress = xCellRangeAddressable->getRangeAddress();
4878 // check if the specified range is a single summary column or row.
4879 table::CellRangeAddress thisAddress = helper.getCellRangeAddressable()->getRangeAddress();
4880 if( (thisAddress.StartRow == thisAddress.EndRow && thisAddress.EndRow == aOutlineAddress.EndRow ) ||
4881 (thisAddress.StartColumn == thisAddress.EndColumn && thisAddress.EndColumn == aOutlineAddress.EndColumn ))
4883 // #FIXME, seems there is a different behavior between MSO and OOo.
4884 // In OOo, the showDetail will show all the level entrys, while only show the first level entry in MSO
4885 uno::Reference< sheet::XSheetOutline > xSheetOutline( helper.getSpreadSheet(), uno::UNO_QUERY_THROW );
4886 if( bShowDetail )
4887 xSheetOutline->showDetail( aOutlineAddress );
4888 else
4889 xSheetOutline->hideDetail( aOutlineAddress );
4891 else
4893 throw uno::RuntimeException( OUString( "Can not set Range.ShowDetail attribute "), uno::Reference< uno::XInterface >() );
4897 uno::Reference< excel::XRange > SAL_CALL
4898 ScVbaRange::MergeArea() throw (script::BasicErrorException, uno::RuntimeException)
4900 uno::Reference< sheet::XSheetCellRange > xMergeShellCellRange(mxRange->getCellRangeByPosition(0,0,0,0), uno::UNO_QUERY_THROW);
4901 uno::Reference< sheet::XSheetCellCursor > xMergeSheetCursor(xMergeShellCellRange->getSpreadsheet()->createCursorByRange( xMergeShellCellRange ), uno::UNO_QUERY_THROW);
4902 if( xMergeSheetCursor.is() )
4904 xMergeSheetCursor->collapseToMergedArea();
4905 uno::Reference<sheet::XCellRangeAddressable> xMergeCellAddress(xMergeSheetCursor, uno::UNO_QUERY_THROW);
4906 if( xMergeCellAddress.is() )
4908 table::CellRangeAddress aCellAddress = xMergeCellAddress->getRangeAddress();
4909 if( aCellAddress.StartColumn ==0 && aCellAddress.EndColumn==0 &&
4910 aCellAddress.StartRow==0 && aCellAddress.EndRow==0)
4912 return new ScVbaRange( mxParent,mxContext,mxRange );
4914 else
4916 ScRange refRange( static_cast< SCCOL >( aCellAddress.StartColumn ), static_cast< SCROW >( aCellAddress.StartRow ), static_cast< SCTAB >( aCellAddress.Sheet ),
4917 static_cast< SCCOL >( aCellAddress.EndColumn ), static_cast< SCROW >( aCellAddress.EndRow ), static_cast< SCTAB >( aCellAddress.Sheet ) );
4918 uno::Reference< table::XCellRange > xRange( new ScCellRangeObj( getScDocShell() , refRange ) );
4919 return new ScVbaRange( mxParent, mxContext,xRange );
4923 return new ScVbaRange( mxParent, mxContext, mxRange );
4926 void SAL_CALL
4927 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)
4929 ScDocShell* pShell = NULL;
4931 sal_Int32 nItems = m_Areas->getCount();
4932 uno::Sequence< table::CellRangeAddress > printAreas( nItems );
4933 uno::Reference< sheet::XPrintAreas > xPrintAreas;
4934 for ( sal_Int32 index=1; index <= nItems; ++index )
4936 uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny(index), uno::Any() ), uno::UNO_QUERY_THROW );
4938 RangeHelper thisRange( xRange->getCellRange() );
4939 table::CellRangeAddress rangeAddress = thisRange.getCellRangeAddressable()->getRangeAddress();
4940 if ( index == 1 )
4942 ScVbaRange* pRange = getImplementation( xRange );
4943 // initialise the doc shell and the printareas
4944 pShell = getDocShellFromRange( pRange->mxRange );
4945 xPrintAreas.set( thisRange.getSpreadSheet(), uno::UNO_QUERY_THROW );
4947 printAreas[ index - 1 ] = rangeAddress;
4949 if ( pShell )
4951 if ( xPrintAreas.is() )
4953 xPrintAreas->setPrintAreas( printAreas );
4954 uno::Reference< frame::XModel > xModel = pShell->GetModel();
4955 PrintOutHelper( excel::getBestViewShell( xModel ), From, To, Copies, Preview, ActivePrinter, PrintToFile, Collate, PrToFileName, sal_True );
4960 void SAL_CALL
4961 ScVbaRange::AutoFill( const uno::Reference< excel::XRange >& Destination, const uno::Any& Type ) throw (uno::RuntimeException)
4963 uno::Reference< excel::XRange > xDest( Destination, uno::UNO_QUERY_THROW );
4964 ScVbaRange* pRange = getImplementation( xDest );
4965 RangeHelper destRangeHelper( pRange->mxRange );
4966 table::CellRangeAddress destAddress = destRangeHelper.getCellRangeAddressable()->getRangeAddress();
4968 RangeHelper thisRange( mxRange );
4969 table::CellRangeAddress thisAddress = thisRange.getCellRangeAddressable()->getRangeAddress();
4970 ScRange sourceRange;
4971 ScRange destRange;
4973 ScUnoConversion::FillScRange( destRange, destAddress );
4974 ScUnoConversion::FillScRange( sourceRange, thisAddress );
4976 FillDir eDir = FILL_TO_BOTTOM;
4977 double fStep = 1.0;
4979 ScRange aRange( destRange );
4980 ScRange aSourceRange( destRange );
4982 // default to include the number of Rows in the source range;
4983 SCCOLROW nSourceCount = ( sourceRange.aEnd.Row() - sourceRange.aStart.Row() ) + 1;
4984 SCCOLROW nCount = 0;
4986 if ( sourceRange != destRange )
4988 // Find direction of fill, vertical or horizontal
4989 if ( sourceRange.aStart == destRange.aStart )
4991 if ( sourceRange.aEnd.Row() == destRange.aEnd.Row() )
4993 nSourceCount = ( sourceRange.aEnd.Col() - sourceRange.aStart.Col() + 1 );
4994 aSourceRange.aEnd.SetCol( static_cast<SCCOL>( aSourceRange.aStart.Col() + nSourceCount - 1 ) );
4995 eDir = FILL_TO_RIGHT;
4996 nCount = aRange.aEnd.Col() - aSourceRange.aEnd.Col();
4998 else if ( sourceRange.aEnd.Col() == destRange.aEnd.Col() )
5000 aSourceRange.aEnd.SetRow( static_cast<SCROW>( aSourceRange.aStart.Row() + nSourceCount ) - 1 );
5001 nCount = aRange.aEnd.Row() - aSourceRange.aEnd.Row();
5002 eDir = FILL_TO_BOTTOM;
5006 else if ( aSourceRange.aEnd == destRange.aEnd )
5008 if ( sourceRange.aStart.Col() == destRange.aStart.Col() )
5010 aSourceRange.aStart.SetRow( static_cast<SCROW>( aSourceRange.aEnd.Row() - nSourceCount + 1 ) );
5011 nCount = aSourceRange.aStart.Row() - aRange.aStart.Row();
5012 eDir = FILL_TO_TOP;
5013 fStep = -fStep;
5015 else if ( sourceRange.aStart.Row() == destRange.aStart.Row() )
5017 nSourceCount = ( sourceRange.aEnd.Col() - sourceRange.aStart.Col() ) + 1;
5018 aSourceRange.aStart.SetCol( static_cast<SCCOL>( aSourceRange.aEnd.Col() - nSourceCount + 1 ) );
5019 nCount = aSourceRange.aStart.Col() - aRange.aStart.Col();
5020 eDir = FILL_TO_LEFT;
5021 fStep = -fStep;
5026 FillCmd eCmd = FILL_AUTO;
5027 FillDateCmd eDateCmd = FILL_DAY;
5029 if ( Type.hasValue() )
5031 sal_Int16 nFillType = excel::XlAutoFillType::xlFillDefault;
5032 Type >>= nFillType;
5033 switch ( nFillType )
5035 case excel::XlAutoFillType::xlFillCopy:
5036 eCmd = FILL_SIMPLE;
5037 fStep = 0.0;
5038 break;
5039 case excel::XlAutoFillType::xlFillDays:
5040 eCmd = FILL_DATE;
5041 break;
5042 case excel::XlAutoFillType::xlFillMonths:
5043 eCmd = FILL_DATE;
5044 eDateCmd = FILL_MONTH;
5045 break;
5046 case excel::XlAutoFillType::xlFillWeekdays:
5047 eCmd = FILL_DATE;
5048 eDateCmd = FILL_WEEKDAY;
5049 break;
5050 case excel::XlAutoFillType::xlFillYears:
5051 eCmd = FILL_DATE;
5052 eDateCmd = FILL_YEAR;
5053 break;
5054 case excel::XlAutoFillType::xlGrowthTrend:
5055 eCmd = FILL_GROWTH;
5056 break;
5057 case excel::XlAutoFillType::xlFillFormats:
5058 throw uno::RuntimeException( OUString( "xlFillFormat not supported for AutoFill" ), uno::Reference< uno::XInterface >() );
5059 case excel::XlAutoFillType::xlFillValues:
5060 case excel::XlAutoFillType::xlFillSeries:
5061 case excel::XlAutoFillType::xlLinearTrend:
5062 eCmd = FILL_LINEAR;
5063 break;
5064 case excel::XlAutoFillType::xlFillDefault:
5065 default:
5066 eCmd = FILL_AUTO;
5067 break;
5070 double fEndValue = MAXDOUBLE;
5071 ScDocShell* pDocSh = getDocShellFromRange( mxRange );
5072 pDocSh->GetDocFunc().FillAuto( aSourceRange, NULL, eDir, eCmd, eDateCmd,
5073 nCount, fStep, fEndValue, sal_True, sal_True );
5075 sal_Bool SAL_CALL
5076 ScVbaRange::GoalSeek( const uno::Any& Goal, const uno::Reference< excel::XRange >& ChangingCell ) throw (uno::RuntimeException)
5078 ScDocShell* pDocShell = getScDocShell();
5079 sal_Bool bRes = sal_True;
5080 ScVbaRange* pRange = static_cast< ScVbaRange* >( ChangingCell.get() );
5081 if ( pDocShell && pRange )
5083 uno::Reference< sheet::XGoalSeek > xGoalSeek( pDocShell->GetModel(), uno::UNO_QUERY_THROW );
5084 RangeHelper thisRange( mxRange );
5085 table::CellRangeAddress thisAddress = thisRange.getCellRangeAddressable()->getRangeAddress();
5086 RangeHelper changingCellRange( pRange->mxRange );
5087 table::CellRangeAddress changingCellAddr = changingCellRange.getCellRangeAddressable()->getRangeAddress();
5088 OUString sGoal = getAnyAsString( Goal );
5089 table::CellAddress thisCell( thisAddress.Sheet, thisAddress.StartColumn, thisAddress.StartRow );
5090 table::CellAddress changingCell( changingCellAddr.Sheet, changingCellAddr.StartColumn, changingCellAddr.StartRow );
5091 sheet::GoalResult res = xGoalSeek->seekGoal( thisCell, changingCell, sGoal );
5092 ChangingCell->setValue( uno::makeAny( res.Result ) );
5094 // openoffice behaves differently, result is 0 if the divergence is too great
5095 // but... if it detects 0 is the value it requires then it will use that
5096 // e.g. divergence & result both = 0.0 does NOT mean there is an error
5097 if ( ( res.Divergence != 0.0 ) && ( res.Result == 0.0 ) )
5098 bRes = false;
5100 else
5101 bRes = false;
5102 return bRes;
5105 void
5106 ScVbaRange::Calculate( ) throw (script::BasicErrorException, uno::RuntimeException)
5108 getWorksheet()->Calculate();
5111 uno::Reference< excel::XRange > SAL_CALL
5112 ScVbaRange::Item( const uno::Any& row, const uno::Any& column ) throw (script::BasicErrorException, uno::RuntimeException)
5114 if ( mbIsRows || mbIsColumns )
5116 if ( column.hasValue() )
5117 DebugHelper::exception(SbERR_BAD_PARAMETER, OUString() );
5118 uno::Reference< excel::XRange > xRange;
5119 if ( mbIsColumns )
5120 xRange = Columns( row );
5121 else
5122 xRange = Rows( row );
5123 return xRange;
5125 return Cells( row, column );
5128 void
5129 ScVbaRange::AutoOutline( ) throw (script::BasicErrorException, uno::RuntimeException)
5131 // #TODO #FIXME needs to check for summary row/col ( whatever they are )
5132 // not valid for multi Area Addresses
5133 if ( m_Areas->getCount() > 1 )
5134 DebugHelper::exception(SbERR_METHOD_FAILED, STR_ERRORMESSAGE_APPLIESTOSINGLERANGEONLY);
5135 // So needs to either span an entire Row or a just be a single cell
5136 // ( that contains a summary RowColumn )
5137 // also the Single cell cause doesn't seem to be handled specially in
5138 // this code ( ported from the helperapi RangeImpl.java,
5139 // RangeRowsImpl.java, RangesImpl.java, RangeSingleCellImpl.java
5140 RangeHelper thisRange( mxRange );
5141 table::CellRangeAddress thisAddress = thisRange.getCellRangeAddressable()->getRangeAddress();
5143 if ( isSingleCellRange() || mbIsRows )
5145 uno::Reference< sheet::XSheetOutline > xSheetOutline( thisRange.getSpreadSheet(), uno::UNO_QUERY_THROW );
5146 xSheetOutline->autoOutline( thisAddress );
5148 else
5149 DebugHelper::exception(SbERR_METHOD_FAILED, OUString());
5152 void SAL_CALL
5153 ScVbaRange:: ClearOutline( ) throw (script::BasicErrorException, uno::RuntimeException)
5155 if ( m_Areas->getCount() > 1 )
5157 sal_Int32 nItems = m_Areas->getCount();
5158 for ( sal_Int32 index=1; index <= nItems; ++index )
5160 uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny(index), uno::Any() ), uno::UNO_QUERY_THROW );
5161 xRange->ClearOutline();
5163 return;
5165 RangeHelper thisRange( mxRange );
5166 uno::Reference< sheet::XSheetOutline > xSheetOutline( thisRange.getSpreadSheet(), uno::UNO_QUERY_THROW );
5167 xSheetOutline->clearOutline();
5170 void
5171 ScVbaRange::groupUnGroup( bool bUnGroup ) throw ( script::BasicErrorException, uno::RuntimeException )
5173 if ( m_Areas->getCount() > 1 )
5174 DebugHelper::exception(SbERR_METHOD_FAILED, STR_ERRORMESSAGE_APPLIESTOSINGLERANGEONLY);
5175 table::TableOrientation nOrient = table::TableOrientation_ROWS;
5176 if ( mbIsColumns )
5177 nOrient = table::TableOrientation_COLUMNS;
5178 RangeHelper thisRange( mxRange );
5179 table::CellRangeAddress thisAddress = thisRange.getCellRangeAddressable()->getRangeAddress();
5180 uno::Reference< sheet::XSheetOutline > xSheetOutline( thisRange.getSpreadSheet(), uno::UNO_QUERY_THROW );
5181 if ( bUnGroup )
5182 xSheetOutline->ungroup( thisAddress, nOrient );
5183 else
5184 xSheetOutline->group( thisAddress, nOrient );
5187 void SAL_CALL
5188 ScVbaRange::Group( ) throw (script::BasicErrorException, uno::RuntimeException)
5190 groupUnGroup();
5192 void SAL_CALL
5193 ScVbaRange::Ungroup( ) throw (script::BasicErrorException, uno::RuntimeException)
5195 groupUnGroup(true);
5198 static void lcl_mergeCellsOfRange( const uno::Reference< table::XCellRange >& xCellRange, sal_Bool _bMerge = sal_True ) throw ( uno::RuntimeException )
5200 uno::Reference< util::XMergeable > xMergeable( xCellRange, uno::UNO_QUERY_THROW );
5201 xMergeable->merge(_bMerge);
5203 void SAL_CALL
5204 ScVbaRange::Merge( const uno::Any& Across ) throw (script::BasicErrorException, uno::RuntimeException)
5206 if ( m_Areas->getCount() > 1 )
5208 sal_Int32 nItems = m_Areas->getCount();
5209 for ( sal_Int32 index=1; index <= nItems; ++index )
5211 uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny(index), uno::Any() ), uno::UNO_QUERY_THROW );
5212 xRange->Merge(Across);
5214 return;
5216 uno::Reference< table::XCellRange > oCellRange;
5217 sal_Bool bAcross = false;
5218 Across >>= bAcross;
5219 if ( !bAcross )
5220 lcl_mergeCellsOfRange( mxRange );
5221 else
5223 uno::Reference< excel::XRange > oRangeRowsImpl = Rows( uno::Any() );
5224 // #TODO #FIXME this seems incredibly lame, this can't be right
5225 for (sal_Int32 i=1; i <= oRangeRowsImpl->getCount();i++)
5227 oRangeRowsImpl->Cells( uno::makeAny( i ), uno::Any() )->Merge( uno::makeAny( false ) );
5232 void SAL_CALL
5233 ScVbaRange::UnMerge( ) throw (script::BasicErrorException, uno::RuntimeException)
5235 if ( m_Areas->getCount() > 1 )
5237 sal_Int32 nItems = m_Areas->getCount();
5238 for ( sal_Int32 index=1; index <= nItems; ++index )
5240 uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny(index), uno::Any() ), uno::UNO_QUERY_THROW );
5241 xRange->UnMerge();
5243 return;
5245 lcl_mergeCellsOfRange( mxRange, false);
5248 uno::Any SAL_CALL
5249 ScVbaRange::getStyle() throw (uno::RuntimeException)
5251 if ( m_Areas->getCount() > 1 )
5253 uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny( sal_Int32( 1 ) ), uno::Any() ), uno::UNO_QUERY_THROW );
5254 return xRange->getStyle();
5256 uno::Reference< beans::XPropertySet > xProps( mxRange, uno::UNO_QUERY_THROW );
5257 OUString sStyleName;
5258 xProps->getPropertyValue( CELLSTYLE ) >>= sStyleName;
5259 ScDocShell* pShell = getScDocShell();
5260 uno::Reference< frame::XModel > xModel( pShell->GetModel() );
5261 uno::Reference< excel::XStyle > xStyle = new ScVbaStyle( this, mxContext, sStyleName, xModel );
5262 return uno::makeAny( xStyle );
5264 void SAL_CALL
5265 ScVbaRange::setStyle( const uno::Any& _style ) throw (uno::RuntimeException)
5267 if ( m_Areas->getCount() > 1 )
5269 uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny( sal_Int32( 1 ) ), uno::Any() ), uno::UNO_QUERY_THROW );
5270 xRange->setStyle( _style );
5271 return;
5273 uno::Reference< beans::XPropertySet > xProps( mxRange, uno::UNO_QUERY_THROW );
5274 uno::Reference< excel::XStyle > xStyle;
5275 _style >>= xStyle;
5276 xProps->setPropertyValue( CELLSTYLE, uno::makeAny( xStyle->getName() ) );
5279 uno::Reference< excel::XRange >
5280 ScVbaRange::PreviousNext( bool bIsPrevious )
5282 ScMarkData markedRange;
5283 ScRange refRange;
5284 RangeHelper thisRange( mxRange );
5286 ScUnoConversion::FillScRange( refRange, thisRange.getCellRangeAddressable()->getRangeAddress());
5287 markedRange. SetMarkArea( refRange );
5288 short nMove = bIsPrevious ? -1 : 1;
5290 SCCOL nNewX = refRange.aStart.Col();
5291 SCROW nNewY = refRange.aStart.Row();
5292 SCTAB nTab = refRange.aStart.Tab();
5294 ScDocument* pDoc = getScDocument();
5295 pDoc->GetNextPos( nNewX,nNewY, nTab, nMove,0, true,true, markedRange );
5296 refRange.aStart.SetCol( nNewX );
5297 refRange.aStart.SetRow( nNewY );
5298 refRange.aStart.SetTab( nTab );
5299 refRange.aEnd.SetCol( nNewX );
5300 refRange.aEnd.SetRow( nNewY );
5301 refRange.aEnd.SetTab( nTab );
5303 uno::Reference< table::XCellRange > xRange( new ScCellRangeObj( getScDocShell() , refRange ) );
5305 return new ScVbaRange( mxParent, mxContext, xRange );
5308 uno::Reference< excel::XRange > SAL_CALL
5309 ScVbaRange::Next() throw (script::BasicErrorException, uno::RuntimeException)
5311 if ( m_Areas->getCount() > 1 )
5313 uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny( sal_Int32( 1 ) ), uno::Any() ) , uno::UNO_QUERY_THROW );
5314 return xRange->Next();
5316 return PreviousNext( false );
5319 uno::Reference< excel::XRange > SAL_CALL
5320 ScVbaRange::Previous() throw (script::BasicErrorException, uno::RuntimeException)
5322 if ( m_Areas->getCount() > 1 )
5324 uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny( sal_Int32( 1 ) ), uno::Any() ), uno::UNO_QUERY_THROW );
5325 return xRange->Previous();
5327 return PreviousNext( true );
5330 uno::Reference< excel::XRange > SAL_CALL
5331 ScVbaRange::SpecialCells( const uno::Any& _oType, const uno::Any& _oValue) throw ( script::BasicErrorException )
5333 bool bIsSingleCell = isSingleCellRange();
5334 bool bIsMultiArea = ( m_Areas->getCount() > 1 );
5335 ScVbaRange* pRangeToUse = this;
5336 uno::Reference< excel::XRange > xUsedRange( getWorksheet()->getUsedRange() );
5337 sal_Int32 nType = 0;
5338 if ( !( _oType >>= nType ) )
5339 DebugHelper::exception(SbERR_BAD_PARAMETER, OUString() );
5340 switch(nType)
5342 case excel::XlCellType::xlCellTypeSameFormatConditions:
5343 case excel::XlCellType::xlCellTypeAllValidation:
5344 case excel::XlCellType::xlCellTypeSameValidation:
5345 DebugHelper::exception(SbERR_NOT_IMPLEMENTED, OUString());
5346 break;
5347 case excel::XlCellType::xlCellTypeBlanks:
5348 case excel::XlCellType::xlCellTypeComments:
5349 case excel::XlCellType::xlCellTypeConstants:
5350 case excel::XlCellType::xlCellTypeFormulas:
5351 case excel::XlCellType::xlCellTypeVisible:
5352 case excel::XlCellType::xlCellTypeLastCell:
5354 if ( bIsMultiArea )
5356 // need to process each area, gather the results and
5357 // create a new range from those
5358 std::vector< table::CellRangeAddress > rangeResults;
5359 sal_Int32 nItems = ( m_Areas->getCount() + 1 );
5360 for ( sal_Int32 index=1; index <= nItems; ++index )
5362 uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny(index), uno::Any() ), uno::UNO_QUERY_THROW );
5363 xRange = xRange->SpecialCells( _oType, _oValue);
5364 ScVbaRange* pRange = getImplementation( xRange );
5365 if ( xRange.is() && pRange )
5367 sal_Int32 nElems = ( pRange->m_Areas->getCount() + 1 );
5368 for ( sal_Int32 nArea = 1; nArea < nElems; ++nArea )
5370 uno::Reference< excel::XRange > xTmpRange( m_Areas->Item( uno::makeAny( nArea ), uno::Any() ), uno::UNO_QUERY_THROW );
5371 RangeHelper rHelper( xTmpRange->getCellRange() );
5372 rangeResults.push_back( rHelper.getCellRangeAddressable()->getRangeAddress() );
5376 ScRangeList aCellRanges;
5377 std::vector< table::CellRangeAddress >::iterator it = rangeResults.begin();
5378 std::vector< table::CellRangeAddress >::iterator it_end = rangeResults.end();
5379 for ( ; it != it_end; ++ it )
5381 ScRange refRange;
5382 ScUnoConversion::FillScRange( refRange, *it );
5383 aCellRanges.Append( refRange );
5385 // Single range
5386 if ( aCellRanges.size() == 1 )
5388 uno::Reference< table::XCellRange > xRange( new ScCellRangeObj( getScDocShell(), *aCellRanges.front() ) );
5389 return new ScVbaRange( mxParent, mxContext, xRange );
5391 uno::Reference< sheet::XSheetCellRangeContainer > xRanges( new ScCellRangesObj( getScDocShell(), aCellRanges ) );
5393 return new ScVbaRange( mxParent, mxContext, xRanges );
5395 else if ( bIsSingleCell )
5397 pRangeToUse = static_cast< ScVbaRange* >( xUsedRange.get() );
5400 break;
5402 default:
5403 DebugHelper::exception(SbERR_BAD_PARAMETER, OUString() );
5404 break;
5406 if ( !pRangeToUse )
5407 DebugHelper::exception(SbERR_METHOD_FAILED, OUString() );
5408 return pRangeToUse->SpecialCellsImpl( nType, _oValue );
5411 static sal_Int32 lcl_getFormulaResultFlags(const uno::Any& aType) throw ( script::BasicErrorException )
5413 sal_Int32 nType = excel::XlSpecialCellsValue::xlNumbers;
5414 aType >>= nType;
5415 sal_Int32 nRes = sheet::FormulaResult::VALUE;
5417 switch(nType)
5419 case excel::XlSpecialCellsValue::xlErrors:
5420 nRes= sheet::FormulaResult::ERROR;
5421 break;
5422 case excel::XlSpecialCellsValue::xlLogical:
5423 //TODO bc93774: ask NN if this is really an appropriate substitute
5424 nRes = sheet::FormulaResult::VALUE;
5425 break;
5426 case excel::XlSpecialCellsValue::xlNumbers:
5427 nRes = sheet::FormulaResult::VALUE;
5428 break;
5429 case excel::XlSpecialCellsValue::xlTextValues:
5430 nRes = sheet::FormulaResult::STRING;
5431 break;
5432 default:
5433 DebugHelper::exception(SbERR_BAD_PARAMETER, OUString() );
5435 return nRes;
5438 uno::Reference< excel::XRange >
5439 ScVbaRange::SpecialCellsImpl( sal_Int32 nType, const uno::Any& _oValue) throw ( script::BasicErrorException )
5441 uno::Reference< excel::XRange > xRange;
5444 uno::Reference< sheet::XCellRangesQuery > xQuery( mxRange, uno::UNO_QUERY_THROW );
5445 uno::Reference< excel::XRange > oLocRangeImpl;
5446 uno::Reference< sheet::XSheetCellRanges > xLocSheetCellRanges;
5447 switch(nType)
5449 case excel::XlCellType::xlCellTypeAllFormatConditions:
5450 case excel::XlCellType::xlCellTypeSameFormatConditions:
5451 case excel::XlCellType::xlCellTypeAllValidation:
5452 case excel::XlCellType::xlCellTypeSameValidation:
5453 // Shouldn't get here ( should be filtered out by
5454 // ScVbaRange::SpecialCells()
5455 DebugHelper::exception(SbERR_NOT_IMPLEMENTED, OUString());
5456 break;
5457 case excel::XlCellType::xlCellTypeBlanks:
5458 xLocSheetCellRanges = xQuery->queryEmptyCells();
5459 break;
5460 case excel::XlCellType::xlCellTypeComments:
5461 xLocSheetCellRanges = xQuery->queryContentCells(sheet::CellFlags::ANNOTATION);
5462 break;
5463 case excel::XlCellType::xlCellTypeConstants:
5464 xLocSheetCellRanges = xQuery->queryContentCells(23);
5465 break;
5466 case excel::XlCellType::xlCellTypeFormulas:
5468 sal_Int32 nFormulaResult = lcl_getFormulaResultFlags(_oValue);
5469 xLocSheetCellRanges = xQuery->queryFormulaCells(nFormulaResult);
5470 break;
5472 case excel::XlCellType::xlCellTypeLastCell:
5473 xRange = Cells( uno::makeAny( getCount() ), uno::Any() );
5474 case excel::XlCellType::xlCellTypeVisible:
5475 xLocSheetCellRanges = xQuery->queryVisibleCells();
5476 break;
5477 default:
5478 DebugHelper::exception(SbERR_BAD_PARAMETER, OUString() );
5479 break;
5481 if (xLocSheetCellRanges.is())
5483 xRange = lcl_makeXRangeFromSheetCellRanges( getParent(), mxContext, xLocSheetCellRanges, getScDocShell() );
5486 catch (uno::Exception& )
5488 DebugHelper::exception(SbERR_METHOD_FAILED, STR_ERRORMESSAGE_NOCELLSWEREFOUND);
5490 return xRange;
5493 void SAL_CALL
5494 ScVbaRange::RemoveSubtotal( ) throw (script::BasicErrorException, uno::RuntimeException)
5496 uno::Reference< sheet::XSubTotalCalculatable > xSub( mxRange, uno::UNO_QUERY_THROW );
5497 xSub->removeSubTotals();
5500 void SAL_CALL
5501 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)
5505 sal_Bool bDoReplace = false;
5506 aReplace >>= bDoReplace;
5507 sal_Bool bAddPageBreaks = false;
5508 PageBreaks >>= bAddPageBreaks;
5510 uno::Reference< sheet::XSubTotalCalculatable> xSub(mxRange, uno::UNO_QUERY_THROW );
5511 uno::Reference< sheet::XSubTotalDescriptor > xSubDesc = xSub->createSubTotalDescriptor(sal_True);
5512 uno::Reference< beans::XPropertySet > xSubDescPropertySet( xSubDesc, uno::UNO_QUERY_THROW );
5513 xSubDescPropertySet->setPropertyValue(INSERTPAGEBREAKS, uno::makeAny( bAddPageBreaks));
5514 sal_Int32 nLen = _nTotalList.getLength();
5515 uno::Sequence< sheet::SubTotalColumn > aColumns( nLen );
5516 for (int i = 0; i < nLen; i++)
5518 aColumns[i].Column = _nTotalList[i] - 1;
5519 switch (_nFunction)
5521 case excel::XlConsolidationFunction::xlAverage:
5522 aColumns[i].Function = sheet::GeneralFunction_AVERAGE;
5523 break;
5524 case excel::XlConsolidationFunction::xlCount:
5525 aColumns[i].Function = sheet::GeneralFunction_COUNT;
5526 break;
5527 case excel::XlConsolidationFunction::xlCountNums:
5528 aColumns[i].Function = sheet::GeneralFunction_COUNTNUMS;
5529 break;
5530 case excel::XlConsolidationFunction::xlMax:
5531 aColumns[i].Function = sheet::GeneralFunction_MAX;
5532 break;
5533 case excel::XlConsolidationFunction::xlMin:
5534 aColumns[i].Function = sheet::GeneralFunction_MIN;
5535 break;
5536 case excel::XlConsolidationFunction::xlProduct:
5537 aColumns[i].Function = sheet::GeneralFunction_PRODUCT;
5538 break;
5539 case excel::XlConsolidationFunction::xlStDev:
5540 aColumns[i].Function = sheet::GeneralFunction_STDEV;
5541 break;
5542 case excel::XlConsolidationFunction::xlStDevP:
5543 aColumns[i].Function = sheet::GeneralFunction_STDEVP;
5544 break;
5545 case excel::XlConsolidationFunction::xlSum:
5546 aColumns[i].Function = sheet::GeneralFunction_SUM;
5547 break;
5548 case excel::XlConsolidationFunction::xlUnknown:
5549 aColumns[i].Function = sheet::GeneralFunction_NONE;
5550 break;
5551 case excel::XlConsolidationFunction::xlVar:
5552 aColumns[i].Function = sheet::GeneralFunction_VAR;
5553 break;
5554 case excel::XlConsolidationFunction::xlVarP:
5555 aColumns[i].Function = sheet::GeneralFunction_VARP;
5556 break;
5557 default:
5558 DebugHelper::exception(SbERR_BAD_PARAMETER, OUString()) ;
5559 return;
5562 xSubDesc->addNew(aColumns, _nGroupBy - 1);
5563 xSub->applySubTotals(xSubDesc, bDoReplace);
5565 catch (uno::Exception& )
5567 DebugHelper::exception(SbERR_METHOD_FAILED, OUString());
5571 OUString
5572 ScVbaRange::getServiceImplName()
5574 return OUString("ScVbaRange");
5577 uno::Sequence< OUString >
5578 ScVbaRange::getServiceNames()
5580 static uno::Sequence< OUString > aServiceNames;
5581 if ( aServiceNames.getLength() == 0 )
5583 aServiceNames.realloc( 1 );
5584 aServiceNames[ 0 ] = OUString( "ooo.vba.excel.Range" );
5586 return aServiceNames;
5589 sal_Bool SAL_CALL
5590 ScVbaRange::hasError() throw (uno::RuntimeException)
5592 double dResult = false;
5593 uno::Reference< excel::XApplication > xApplication( Application(), uno::UNO_QUERY_THROW );
5594 uno::Reference< script::XInvocation > xInvoc( xApplication->WorksheetFunction(), uno::UNO_QUERY_THROW );
5596 static OUString FunctionName( "IsError" );
5597 uno::Sequence< uno::Any > Params(1);
5598 uno::Reference< excel::XRange > aRange( this );
5599 Params[0] = uno::makeAny( aRange );
5600 uno::Sequence< sal_Int16 > OutParamIndex;
5601 uno::Sequence< uno::Any > OutParam;
5602 xInvoc->invoke( FunctionName, Params, OutParamIndex, OutParam ) >>= dResult;
5603 if ( dResult > 0.0 )
5604 return sal_True;
5605 return false;
5608 namespace range
5610 namespace sdecl = comphelper::service_decl;
5611 sdecl::vba_service_class_<ScVbaRange, sdecl::with_args<true> > serviceImpl;
5612 extern sdecl::ServiceDecl const serviceDecl(
5613 serviceImpl,
5614 "SvVbaRange",
5615 "ooo.vba.excel.Range" );
5618 /* vim:set shiftwidth=4 softtabstop=4 expandtab: */