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