summaryrefslogtreecommitdiff
path: root/sc/source/ui/vba/vbarange.cxx
diff options
context:
space:
mode:
authorVladimir Glazounov <vg@openoffice.org>2007-12-07 10:01:04 +0000
committerVladimir Glazounov <vg@openoffice.org>2007-12-07 10:01:04 +0000
commit03fada55177203341471d6a57f1fd66060bf5028 (patch)
tree49290cd1127d067077e5c19c7d13715d25d8bdff /sc/source/ui/vba/vbarange.cxx
parent6e8488ee3fb1fc600b62597a51a58b5d3197dbe6 (diff)
INTEGRATION: CWS npower8 (1.2.4); FILE MERGED
2007/11/30 10:57:33 npower 1.2.4.12: compare widths based on twips not the converted doubles which seem to exhibit strange fp related ( or maybe even gcc specific ) problems, these result in some of the comparisons failing when they shouldn't Issue number: Submitted by: Reviewed by: 2007/11/05 17:07:21 npower 1.2.4.11: Issue number: #i77189# 2007/10/31 21:00:26 npower 1.2.4.10: Issue number: #i77189# warning as error removal 2007/10/30 16:18:48 npower 1.2.4.9: #i77189# 2007/10/30 11:53:39 npower 1.2.4.8: #i68901# 2007/10/16 09:36:59 npower 1.2.4.7: #i77189# 2007/10/11 19:24:24 npower 1.2.4.6: RESYNC: (1.2-1.3); FILE MERGED 2007/09/03 12:19:42 npower 1.2.4.5: #i77189# sync with oobuild 2007/07/23 11:47:24 npower 1.2.4.4: i#77189# 2007/07/18 13:46:47 npower 1.2.4.3: #i77189# sync ooo-build and this module 2007/05/13 07:09:06 npower 1.2.4.2: wrong constant def Issue number: Submitted by: Reviewed by: 2007/05/10 11:23:10 npower 1.2.4.1: -m#i77189#
Diffstat (limited to 'sc/source/ui/vba/vbarange.cxx')
-rw-r--r--sc/source/ui/vba/vbarange.cxx2120
1 files changed, 1682 insertions, 438 deletions
diff --git a/sc/source/ui/vba/vbarange.cxx b/sc/source/ui/vba/vbarange.cxx
index 53db82b83..f3cfdeac8 100644
--- a/sc/source/ui/vba/vbarange.cxx
+++ b/sc/source/ui/vba/vbarange.cxx
@@ -4,9 +4,9 @@
*
* $RCSfile: vbarange.cxx,v $
*
- * $Revision: 1.3 $
+ * $Revision: 1.4 $
*
- * last change: $Author: vg $ $Date: 2007-08-30 10:05:05 $
+ * last change: $Author: vg $ $Date: 2007-12-07 11:01:04 $
*
* The Contents of this file are made available subject to
* the terms of GNU Lesser General Public License Version 2.1.
@@ -32,10 +32,16 @@
* MA 02111-1307 USA
*
************************************************************************/
+#include "helperdecl.hxx"
+
+#include <comphelper/unwrapargs.hxx>
#include <comphelper/processfactory.hxx>
#include <sfx2/objsh.hxx>
#include <com/sun/star/script/ArrayWrapper.hpp>
+#include <com/sun/star/sheet/XDatabaseRange.hpp>
+#include <com/sun/star/sheet/XDatabaseRanges.hpp>
+#include <com/sun/star/sheet/XGoalSeek.hpp>
#include <com/sun/star/sheet/XSheetOperation.hpp>
#include <com/sun/star/sheet/CellFlags.hpp>
#include <com/sun/star/table/XColumnRowRange.hpp>
@@ -45,6 +51,7 @@
#include <com/sun/star/text/XTextRange.hpp>
#include <com/sun/star/sheet/XCellRangeAddressable.hpp>
#include <com/sun/star/table/CellRangeAddress.hpp>
+#include <com/sun/star/table/CellAddress.hpp>
#include <com/sun/star/sheet/XSpreadsheetView.hpp>
#include <com/sun/star/sheet/XCellRangeReferrer.hpp>
#include <com/sun/star/sheet/XSheetCellRange.hpp>
@@ -53,6 +60,7 @@
#include <com/sun/star/sheet/XArrayFormulaRange.hpp>
#include <com/sun/star/sheet/XNamedRange.hpp>
#include <com/sun/star/sheet/XPrintAreas.hpp>
+#include <com/sun/star/sheet/XCellRangesQuery.hpp>
#include <com/sun/star/beans/XPropertySet.hpp>
#include <com/sun/star/sheet/XFunctionAccess.hpp>
#include <com/sun/star/frame/XModel.hpp>
@@ -77,12 +85,16 @@
#include <com/sun/star/sheet/TableFilterField.hpp>
#include <com/sun/star/sheet/XSheetFilterable.hpp>
#include <com/sun/star/sheet/FilterConnection.hpp>
+#include <com/sun/star/util/CellProtection.hpp>
#include <com/sun/star/style/XStyleFamiliesSupplier.hpp>
#include <com/sun/star/awt/XDevice.hpp>
//#include <com/sun/star/sheet/CellDeleteMode.hpp>
#include <com/sun/star/sheet/XCellRangeMovement.hpp>
+#include <com/sun/star/sheet/XSubTotalCalculatable.hpp>
+#include <com/sun/star/sheet/XSubTotalDescriptor.hpp>
+#include <com/sun/star/sheet/GeneralFunction.hdl>
#include <org/openoffice/excel/XlPasteSpecialOperation.hpp>
#include <org/openoffice/excel/XlPasteType.hpp>
@@ -105,6 +117,9 @@
#include <org/openoffice/excel/XlAutoFillType.hpp>
#include <org/openoffice/excel/XlTextParsingType.hpp>
#include <org/openoffice/excel/XlTextQualifier.hpp>
+#include <org/openoffice/excel/XlCellType.hpp>
+#include <org/openoffice/excel/XlSpecialCellsValue.hpp>
+#include <org/openoffice/excel/XlConsolidationFunction.hpp>
#include <scitems.hxx>
#include <svx/srchitem.hxx>
@@ -138,20 +153,25 @@
#include "attrib.hxx"
#include "undodat.hxx"
#include "dbdocfun.hxx"
+#include "patattr.hxx"
#include <comphelper/anytostring.hxx>
#include <global.hxx>
#include "vbaglobals.hxx"
+#include "vbastyle.hxx"
#include <vector>
#include <vbacollectionimpl.hxx>
// begin test includes
#include <com/sun/star/sheet/FunctionArgument.hpp>
// end test includes
+#include <org/openoffice/excel/Range.hpp>
+
using namespace ::org::openoffice;
using namespace ::com::sun::star;
+
// * 1 point = 1/72 inch = 20 twips
// * 1 inch = 72 points = 1440 twips
// * 1 cm = 567 twips
@@ -183,34 +203,64 @@ double lcl_Round2DecPlaces( double nVal )
return nVal;
}
-uno::Any lcl_makeRange( uno::Reference< uno::XComponentContext >& xContext, const uno::Any aAny )
+uno::Any lcl_makeRange( uno::Reference< uno::XComponentContext >& xContext, const uno::Any aAny, bool bIsRows, bool bIsColumns )
{
uno::Reference< table::XCellRange > xCellRange( aAny, uno::UNO_QUERY_THROW );
- return uno::makeAny( uno::Reference< excel::XRange >( new ScVbaRange( xContext, xCellRange ) ) );
+ // #FIXME need proper (WorkSheet) parent
+ return uno::makeAny( uno::Reference< excel::XRange >( new ScVbaRange( uno::Reference< vba::XHelperInterface >(), xContext, xCellRange, bIsRows, bIsColumns ) ) );
+}
+
+uno::Reference< excel::XRange > lcl_makeXRangeFromSheetCellRanges( const uno::Reference< vba::XHelperInterface >& xParent, const uno::Reference< uno::XComponentContext >& xContext, const uno::Reference< sheet::XSheetCellRanges >& xLocSheetCellRanges, ScDocShell* pDoc )
+{
+ uno::Reference< excel::XRange > xRange;
+ uno::Sequence< table::CellRangeAddress > sAddresses = xLocSheetCellRanges->getRangeAddresses();
+ ScRangeList aCellRanges;
+ sal_Int32 nLen = sAddresses.getLength();
+ for ( sal_Int32 index = 0; index < nLen; ++index )
+ {
+ ScRange refRange;
+ ScUnoConversion::FillScRange( refRange, sAddresses[ index ] );
+ aCellRanges.Append( refRange );
+ }
+ // Single range
+ if ( aCellRanges.First() == aCellRanges.Last() )
+ {
+ uno::Reference< table::XCellRange > xTmpRange( new ScCellRangeObj( pDoc, *aCellRanges.First() ) );
+ // #FIXME need proper (WorkSheet) parent
+ xRange = new ScVbaRange( xParent, xContext, xTmpRange );
+ }
+ else
+ {
+ uno::Reference< sheet::XSheetCellRangeContainer > xRanges( new ScCellRangesObj( pDoc, aCellRanges ) );
+ // #FIXME need proper (WorkSheet) parent
+ xRange = new ScVbaRange( xParent, xContext, xRanges );
+ }
+ return xRange;
}
SfxItemSet* ScVbaRange::getCurrentDataSet( ) throw ( uno::RuntimeException )
{
- uno::Reference< uno::XInterface > xIf( mxRange, uno::UNO_QUERY_THROW );
- //ScCellRangeObj* pUnoCellRange = dynamic_cast< ScCellRangeObj* >( xIf.get() );
- // FOR_UPSTREAM_BUILD
- /*SfxItemSet* pDataSet = pUnoCellRange->GetCurrentDataSet( true );
+ uno::Reference< uno::XInterface > xIf;
+ if ( mxRanges.is() )
+ xIf.set( mxRanges, uno::UNO_QUERY_THROW );
+ else
+ xIf.set( mxRange, uno::UNO_QUERY_THROW );
+ ScCellRangeObj* pUnoCellRange = dynamic_cast< ScCellRangeObj* >( xIf.get() );
+ SfxItemSet* pDataSet = pUnoCellRange ? pUnoCellRange->GetCurrentDataSet( true ) : NULL ;
if ( !pDataSet )
throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "Can't access Itemset for range" ) ), uno::Reference< uno::XInterface >() );
return pDataSet;
- */
- return NULL;
}
class SingleRangeEnumeration : public EnumerationHelper_BASE
{
uno::Reference< table::XCellRange > m_xRange;
- uno::Reference< uno::XComponentContext > m_xContext;
+ uno::Reference< uno::XComponentContext > mxContext;
bool bHasMore;
public:
- SingleRangeEnumeration( const uno::Reference< css::uno::XComponentContext >& xContext, const uno::Reference< table::XCellRange >& xRange ) throw ( uno::RuntimeException ) : m_xRange( xRange ), m_xContext( xContext ), bHasMore( true ) { }
+ SingleRangeEnumeration( const uno::Reference< css::uno::XComponentContext >& xContext, const uno::Reference< table::XCellRange >& xRange ) throw ( uno::RuntimeException ) : m_xRange( xRange ), mxContext( xContext ), bHasMore( true ) { }
virtual ::sal_Bool SAL_CALL hasMoreElements( ) throw (uno::RuntimeException) { return bHasMore; }
virtual uno::Any SAL_CALL nextElement( ) throw (container::NoSuchElementException, lang::WrappedTargetException, uno::RuntimeException)
{
@@ -229,10 +279,10 @@ class SingleRangeIndexAccess : public SingleRange_BASE
{
private:
uno::Reference< table::XCellRange > m_xRange;
- uno::Reference< uno::XComponentContext > m_xContext;
+ uno::Reference< uno::XComponentContext > mxContext;
SingleRangeIndexAccess(); // not defined
public:
- SingleRangeIndexAccess( const uno::Reference< uno::XComponentContext >& xContext, const uno::Reference< table::XCellRange >& xRange ):m_xRange( xRange ), m_xContext( xContext ) {}
+ SingleRangeIndexAccess( const uno::Reference< uno::XComponentContext >& xContext, const uno::Reference< table::XCellRange >& xRange ):m_xRange( xRange ), mxContext( xContext ) {}
// XIndexAccess
virtual ::sal_Int32 SAL_CALL getCount() throw (::uno::RuntimeException) { return 1; }
virtual uno::Any SAL_CALL getByIndex( ::sal_Int32 Index ) throw (lang::IndexOutOfBoundsException, lang::WrappedTargetException, uno::RuntimeException)
@@ -246,7 +296,7 @@ public:
virtual ::sal_Bool SAL_CALL hasElements() throw (uno::RuntimeException) { return sal_True; }
// XEnumerationAccess
- virtual uno::Reference< container::XEnumeration > SAL_CALL createEnumeration() throw (uno::RuntimeException) { return new SingleRangeEnumeration( m_xContext, m_xRange ); }
+ virtual uno::Reference< container::XEnumeration > SAL_CALL createEnumeration() throw (uno::RuntimeException) { return new SingleRangeEnumeration( mxContext, m_xRange ); }
};
@@ -254,21 +304,24 @@ public:
class RangesEnumerationImpl : public EnumerationHelperImpl
{
+ bool mbIsRows;
+ bool mbIsColumns;
public:
- RangesEnumerationImpl( const uno::Reference< uno::XComponentContext >& xContext, const uno::Reference< container::XEnumeration >& xEnumeration ) throw ( uno::RuntimeException ) : EnumerationHelperImpl( xContext, xEnumeration ) {}
+ RangesEnumerationImpl( const uno::Reference< uno::XComponentContext >& xContext, const uno::Reference< container::XEnumeration >& xEnumeration, bool bIsRows, bool bIsColumns ) throw ( uno::RuntimeException ) : EnumerationHelperImpl( xContext, xEnumeration ), mbIsRows( bIsRows ), mbIsColumns( bIsColumns ) {}
virtual uno::Any SAL_CALL nextElement( ) throw (container::NoSuchElementException, lang::WrappedTargetException, uno::RuntimeException)
{
- return lcl_makeRange( m_xContext, m_xEnumeration->nextElement() );
+ return lcl_makeRange( m_xContext, m_xEnumeration->nextElement(), mbIsRows, mbIsColumns );
}
};
class ScVbaRangeAreas : public ScVbaCollectionBaseImpl
{
-
+ bool mbIsRows;
+ bool mbIsColumns;
public:
- ScVbaRangeAreas( const uno::Reference< uno::XComponentContext >& xContext, const uno::Reference< container::XIndexAccess >& xIndexAccess ) : ScVbaCollectionBaseImpl( xContext, xIndexAccess ) {}
+ ScVbaRangeAreas( const uno::Reference< uno::XComponentContext >& xContext, const uno::Reference< container::XIndexAccess >& xIndexAccess, bool bIsRows, bool bIsColumns ) : ScVbaCollectionBaseImpl( uno::Reference< vba::XHelperInterface >(), xContext, xIndexAccess ), mbIsRows( bIsRows ), mbIsColumns( bIsColumns ) {}
// XEnumerationAccess
virtual uno::Reference< container::XEnumeration > SAL_CALL createEnumeration() throw (uno::RuntimeException);
@@ -277,37 +330,59 @@ public:
virtual uno::Type SAL_CALL getElementType() throw (uno::RuntimeException){ return excel::XRange::static_type(0); }
virtual uno::Any createCollectionObject( const uno::Any& aSource );
-};
+ virtual rtl::OUString& getServiceImplName() { static rtl::OUString sDummy; return sDummy; }
+
+ virtual uno::Sequence< rtl::OUString > getServiceNames() { return uno::Sequence< rtl::OUString >(); }
+
+};
uno::Reference< container::XEnumeration > SAL_CALL
ScVbaRangeAreas::createEnumeration() throw (uno::RuntimeException)
{
uno::Reference< container::XEnumerationAccess > xEnumAccess( m_xIndexAccess, uno::UNO_QUERY_THROW );
- return new RangesEnumerationImpl( m_xContext, xEnumAccess->createEnumeration() );
+ return new RangesEnumerationImpl( mxContext, xEnumAccess->createEnumeration(), mbIsRows, mbIsColumns );
}
uno::Any
ScVbaRangeAreas::createCollectionObject( const uno::Any& aSource )
{
- return lcl_makeRange( m_xContext, aSource );
+ return lcl_makeRange( mxContext, aSource, mbIsRows, mbIsColumns );
}
-
-
-
-ScDocShell* getDocShellFromRange( const uno::Reference< table::XCellRange >& xRange )
+// assume that xIf is infact a ScCellRangesBase
+ScDocShell*
+getDocShellFromIf( const uno::Reference< uno::XInterface >& xIf ) throw ( uno::RuntimeException )
{
- // need the ScCellRangesBase to get docshell
- uno::Reference< uno::XInterface > xIf( xRange, uno::UNO_QUERY_THROW );
ScCellRangesBase* pUno= dynamic_cast< ScCellRangesBase* >( xIf.get() );
if ( !pUno )
throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "Failed to access underlying uno range object" ) ), uno::Reference< uno::XInterface >() );
return pUno->GetDocShell();
}
-ScDocument* getDocumentFromRange( const uno::Reference< table::XCellRange >& xRange )
+ScDocShell*
+getDocShellFromRange( const uno::Reference< table::XCellRange >& xRange ) throw ( uno::RuntimeException )
+{
+ // need the ScCellRangesBase to get docshell
+ uno::Reference< uno::XInterface > xIf( xRange, uno::UNO_QUERY_THROW );
+ return getDocShellFromIf(xIf );
+}
+
+uno::Reference< frame::XModel > getModelFromXIf( const uno::Reference< uno::XInterface >& xIf ) throw ( uno::RuntimeException )
+{
+ ScDocShell* pDocShell = getDocShellFromIf(xIf );
+ return pDocShell->GetModel();
+}
+
+uno::Reference< frame::XModel > getModelFromRange( const uno::Reference< table::XCellRange >& xRange ) throw ( uno::RuntimeException )
+{
+ uno::Reference< uno::XInterface > xIf( xRange, uno::UNO_QUERY_THROW );
+ return getModelFromXIf( xIf );
+}
+
+ScDocument*
+getDocumentFromRange( const uno::Reference< table::XCellRange >& xRange )
{
ScDocShell* pDocShell = getDocShellFromRange( xRange );
if ( !pDocShell )
@@ -316,6 +391,31 @@ ScDocument* getDocumentFromRange( const uno::Reference< table::XCellRange >& xRa
return pDoc;
}
+
+ScDocument*
+ScVbaRange::getScDocument()
+{
+ if ( mxRanges.is() )
+ {
+ uno::Reference< container::XIndexAccess > xIndex( mxRanges, uno::UNO_QUERY_THROW );
+ uno::Reference< table::XCellRange > xRange( xIndex->getByIndex( 0 ), uno::UNO_QUERY_THROW );
+ return getDocumentFromRange( xRange );
+ }
+ return getDocumentFromRange( mxRange );
+}
+
+ScDocShell*
+ScVbaRange::getScDocShell()
+{
+ if ( mxRanges.is() )
+ {
+ uno::Reference< container::XIndexAccess > xIndex( mxRanges, uno::UNO_QUERY_THROW );
+ uno::Reference< table::XCellRange > xRange( xIndex->getByIndex( 0 ), uno::UNO_QUERY_THROW );
+ return getDocShellFromRange( xRange );
+ }
+ return getDocShellFromRange( mxRange );
+}
+
class NumFormatHelper
{
uno::Reference< util::XNumberFormatsSupplier > mxSupplier;
@@ -324,7 +424,7 @@ class NumFormatHelper
public:
NumFormatHelper( const uno::Reference< table::XCellRange >& xRange )
{
- mxSupplier.set( getCurrentDocument(), uno::UNO_QUERY_THROW );
+ mxSupplier.set( getModelFromRange( xRange ), uno::UNO_QUERY_THROW );
mxRangeProps.set( xRange, uno::UNO_QUERY_THROW);
mxFormats = mxSupplier->getNumberFormats();
}
@@ -353,15 +453,13 @@ public:
ScCellRangeObj* pUnoCellRange = dynamic_cast< ScCellRangeObj* >( xIf.get() );
if ( pUnoCellRange )
{
- // FOR_UPSTREAM_BUILD
- /*
+
SfxItemSet* pDataSet = pUnoCellRange->GetCurrentDataSet( true );
SfxItemState eState = pDataSet->GetItemState( ATTR_VALUE_FORMAT, TRUE, NULL);
// one of the cells in the range is not like the other ;-)
// so return a zero length format to indicate that
if ( eState == SFX_ITEM_DONTCARE )
return rtl::OUString();
- */
}
@@ -413,10 +511,11 @@ public:
struct CellPos
{
- CellPos():m_nRow(-1), m_nCol(-1) {};
- CellPos( sal_Int32 nRow, sal_Int32 nCol ):m_nRow(nRow), m_nCol(nCol) {};
+ CellPos():m_nRow(-1), m_nCol(-1), m_nArea(0) {};
+ CellPos( sal_Int32 nRow, sal_Int32 nCol, sal_Int32 nArea ):m_nRow(nRow), m_nCol(nCol), m_nArea( nArea ) {};
sal_Int32 m_nRow;
sal_Int32 m_nCol;
+sal_Int32 m_nArea;
};
typedef ::cppu::WeakImplHelper1< container::XEnumeration > CellsEnumeration_BASE;
@@ -424,19 +523,43 @@ typedef vector< CellPos > vCellPos;
class CellsEnumeration : public CellsEnumeration_BASE
{
- uno::Reference< uno::XComponentContext > m_xContext;
- uno::Reference< table::XCellRange > m_xRange;
+ uno::Reference< uno::XComponentContext > mxContext;
+ uno::Reference< vba::XCollection > m_xAreas;
vCellPos m_CellPositions;
vCellPos::const_iterator m_it;
-public:
- CellsEnumeration( const uno::Reference< uno::XComponentContext >& xContext, const uno::Reference< table::XCellRange >& xRange ): m_xContext( xContext ), m_xRange( xRange )
+ uno::Reference< table::XCellRange > getArea( sal_Int32 nVBAIndex ) throw ( uno::RuntimeException )
{
- uno::Reference< table::XColumnRowRange > xColumnRowRange(m_xRange, uno::UNO_QUERY_THROW );
+ if ( nVBAIndex < 1 || nVBAIndex > m_xAreas->getCount() )
+ throw uno::RuntimeException();
+ uno::Reference< excel::XRange > xRange( m_xAreas->Item( uno::makeAny(nVBAIndex), uno::Any() ), uno::UNO_QUERY_THROW );
+ ScVbaRange* pRange = dynamic_cast< ScVbaRange* >( xRange.get() );
+ uno::Reference< table::XCellRange > xCellRange;
+ if ( !pRange )
+ throw uno::RuntimeException();
+ xCellRange.set( pRange->getCellRange(), uno::UNO_QUERY_THROW );;
+ return xCellRange;
+
+ }
+ void populateArea( sal_Int32 nVBAIndex )
+ {
+ uno::Reference< table::XCellRange > xRange = getArea( nVBAIndex );
+ uno::Reference< table::XColumnRowRange > xColumnRowRange(xRange, uno::UNO_QUERY_THROW );
sal_Int32 nRowCount = xColumnRowRange->getRows()->getCount();
sal_Int32 nColCount = xColumnRowRange->getColumns()->getCount();
for ( sal_Int32 i=0; i<nRowCount; ++i )
+ {
for ( sal_Int32 j=0; j<nColCount; ++j )
- m_CellPositions.push_back( CellPos( i,j ) );
+ m_CellPositions.push_back( CellPos( i,j,nVBAIndex ) );
+ }
+ }
+public:
+ CellsEnumeration( const uno::Reference< uno::XComponentContext >& xContext, const uno::Reference< vba::XCollection >& xAreas ): mxContext( xContext ), m_xAreas( xAreas )
+ {
+ sal_Int32 nItems = m_xAreas->getCount();
+ for ( sal_Int32 index=1; index <= nItems; ++index )
+ {
+ populateArea( index );
+ }
m_it = m_CellPositions.begin();
}
virtual ::sal_Bool SAL_CALL hasMoreElements() throw (::uno::RuntimeException){ return m_it != m_CellPositions.end(); }
@@ -446,8 +569,12 @@ public:
if ( !hasMoreElements() )
throw container::NoSuchElementException();
CellPos aPos = *(m_it)++;
- uno::Reference< table::XCellRange > xCellRange( m_xRange->getCellByPosition( aPos.m_nCol, aPos.m_nRow ), uno::UNO_QUERY_THROW );
- return uno::makeAny( uno::Reference< excel::XRange >( new ScVbaRange( m_xContext, xCellRange ) ) );
+
+ uno::Reference< table::XCellRange > xRangeArea = getArea( aPos.m_nArea );
+ uno::Reference< table::XCellRange > xCellRange( xRangeArea->getCellByPosition( aPos.m_nCol, aPos.m_nRow ), uno::UNO_QUERY_THROW );
+ // #FIXME need proper (WorkSheet) parent
+ return uno::makeAny( uno::Reference< excel::XRange >( new ScVbaRange( uno::Reference< vba::XHelperInterface >(), mxContext, xCellRange ) ) );
+
}
};
@@ -455,8 +582,19 @@ public:
const static ::rtl::OUString ISVISIBLE( RTL_CONSTASCII_USTRINGPARAM( "IsVisible"));
const static ::rtl::OUString WIDTH( RTL_CONSTASCII_USTRINGPARAM( "Width"));
const static ::rtl::OUString HEIGHT( RTL_CONSTASCII_USTRINGPARAM( "Height"));
+const static ::rtl::OUString POSITION( RTL_CONSTASCII_USTRINGPARAM( "Position"));
const static rtl::OUString EQUALS( RTL_CONSTASCII_USTRINGPARAM("=") );
+const static rtl::OUString NOTEQUALS( RTL_CONSTASCII_USTRINGPARAM("<>") );
+const static rtl::OUString GREATERTHAN( RTL_CONSTASCII_USTRINGPARAM(">") );
+const static rtl::OUString GREATERTHANEQUALS( RTL_CONSTASCII_USTRINGPARAM(">=") );
+const static rtl::OUString LESSTHAN( RTL_CONSTASCII_USTRINGPARAM("<") );
+const static rtl::OUString LESSTHANEQUALS( RTL_CONSTASCII_USTRINGPARAM("<=") );
const static rtl::OUString CONTS_HEADER( RTL_CONSTASCII_USTRINGPARAM("ContainsHeader" ));
+const static rtl::OUString INSERTPAGEBREAKS( RTL_CONSTASCII_USTRINGPARAM("InsertPageBreaks" ));
+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") );
+const static rtl::OUString STR_ERRORMESSAGE_NOCELLSWEREFOUND( RTL_CONSTASCII_USTRINGPARAM("No cells were found") );
+const static rtl::OUString STR_ERRORMESSAGE_APPLIESTOROWCOLUMNSONLY( RTL_CONSTASCII_USTRINGPARAM("Property only applicable for Columns and Rows") );
+const static rtl::OUString CELLSTYLE( RTL_CONSTASCII_USTRINGPARAM("CellStyle") );
class CellValueSetter : public ValueSetter
{
@@ -553,13 +691,28 @@ void CellValueGetter::visitNode( sal_Int32 x, sal_Int32 y, const uno::Reference<
{
if ( eType == table::CellContentType_FORMULA )
{
+
rtl::OUString sFormula = xCell->getFormula();
if ( sFormula.equals( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("=TRUE()") ) ) )
aValue <<= sal_True;
else if ( sFormula.equals( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("=FALSE()") ) ) )
aValue <<= sal_False;
else
- aValue <<= xCell->getValue();
+ {
+ uno::Reference< beans::XPropertySet > xProp( xCell, uno::UNO_QUERY_THROW );
+
+ table::CellContentType eFormulaType = table::CellContentType_VALUE;
+ // some formulas give textual results
+ xProp->getPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("FormulaResultType" ) ) ) >>= eFormulaType;
+
+ if ( eFormulaType == table::CellContentType_TEXT )
+ {
+ uno::Reference< text::XTextRange > xTextRange(xCell, ::uno::UNO_QUERY_THROW);
+ aValue <<= xTextRange->getString();
+ }
+ else
+ aValue <<= xCell->getValue();
+ }
}
else
{
@@ -594,7 +747,8 @@ protected:
{
// get current convention
ScAddress::Convention eConv = m_pDoc->GetAddressConvention();
- if ( eConv != m_eConv )
+ // only convert/compile 'real' formulas
+ if ( eConv != m_eConv && ( sFormula.trim().indexOf('=') == 0 ) )
{
uno::Reference< uno::XInterface > xIf( xCell, uno::UNO_QUERY_THROW );
ScCellRangesBase* pUnoRangesBase = dynamic_cast< ScCellRangesBase* >( xIf.get() );
@@ -763,14 +917,14 @@ public:
class RangeCountProcessor : public RangeProcessor
{
- double nCount;
+ sal_Int32 nCount;
public:
RangeCountProcessor():nCount(0){}
virtual void process( const uno::Reference< excel::XRange >& xRange )
{
nCount = nCount + xRange->getCount();
}
- double value() { return nCount; }
+ sal_Int32 value() { return nCount; }
};
class AreasVisitor
{
@@ -786,7 +940,7 @@ public:
sal_Int32 nItems = m_Areas->getCount();
for ( sal_Int32 index=1; index <= nItems; ++index )
{
- uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny(index) ), uno::UNO_QUERY_THROW );
+ uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny(index), uno::Any() ), uno::UNO_QUERY_THROW );
processor.process( xRange );
}
}
@@ -835,7 +989,8 @@ public:
static uno::Reference< excel::XRange > createRangeFromRange( const uno::Reference<uno::XComponentContext >& xContext, const uno::Reference< table::XCellRange >& xRange, const uno::Reference< sheet::XCellRangeAddressable >& xCellRangeAddressable, sal_Int32 nStartColOffset = 0, sal_Int32 nStartRowOffset = 0,
sal_Int32 nEndColOffset = 0, sal_Int32 nEndRowOffset = 0 )
{
- return uno::Reference< excel::XRange >( new ScVbaRange( xContext,
+ // #FIXME need proper (WorkSheet) parent
+ return uno::Reference< excel::XRange >( new ScVbaRange( uno::Reference< vba::XHelperInterface >(), xContext,
xRange->getCellRangeByPosition(
xCellRangeAddressable->getRangeAddress().StartColumn + nStartColOffset,
xCellRangeAddressable->getRangeAddress().StartRow + nStartRowOffset,
@@ -845,34 +1000,6 @@ public:
};
-static table::CellRangeAddress getCellRangeAddress( const uno::Any& aParam,
-const uno::Reference< sheet::XSpreadsheet >& xDoc )
-{
- uno::Reference< table::XCellRange > xRangeParam;
- switch ( aParam.getValueTypeClass() )
- {
- case uno::TypeClass_STRING:
- {
- rtl::OUString rString;
- aParam >>= rString;
- xRangeParam = ScVbaRange::getCellRangeForName( rString, xDoc );
- break;
- }
- case uno::TypeClass_INTERFACE:
- {
- uno::Reference< excel::XRange > xRange;
- aParam >>= xRange;
- if ( xRange.is() )
- xRange->getCellRange() >>= xRangeParam;
- break;
- }
- default:
- throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("Can't extact CellRangeAddress from type" ) ), uno::Reference< uno::XInterface >() );
- }
- uno::Reference< sheet::XCellRangeAddressable > xAddressable( xRangeParam, uno::UNO_QUERY_THROW );
- return xAddressable->getRangeAddress();
-}
-
bool
getCellRangesForAddress( USHORT& rResFlags, const rtl::OUString& sAddress, ScDocShell* pDocSh, ScRangeList& rCellRanges, ScAddress::Convention& eConv )
{
@@ -893,68 +1020,149 @@ getCellRangesForAddress( USHORT& rResFlags, const rtl::OUString& sAddress, ScDoc
return false;
}
-ScVbaRange*
-getRangeForName( const uno::Reference< uno::XComponentContext >& xContext, const rtl::OUString& sName, ScDocShell* pDocSh, table::CellRangeAddress& pAddr ) throw ( uno::RuntimeException )
+bool getScRangeListForAddress( const rtl::OUString& sName, ScDocShell* pDocSh, ScRange& refRange, ScRangeList& aCellRanges, ScAddress::Convention aConv = ScAddress::CONV_XL_A1 ) throw ( uno::RuntimeException )
{
- rtl::OUString sAddress = sName;
- ScAddress::Convention eConv = ScAddress::CONV_XL_A1;
// see if there is a match with a named range
- uno::Reference< beans::XPropertySet > xProps( getCurrentDocument(), uno::UNO_QUERY_THROW );
+ uno::Reference< beans::XPropertySet > xProps( pDocSh->GetModel(), uno::UNO_QUERY_THROW );
uno::Reference< container::XNameAccess > xNameAccess( xProps->getPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("NamedRanges") ) ), uno::UNO_QUERY_THROW );
-
- if ( xNameAccess->hasByName( sName ) )
+ // Strangly enough you can have Range( "namedRange1, namedRange2, etc," )
+ // loop around each ',' seperated name
+ std::vector< rtl::OUString > vNames;
+ sal_Int32 nIndex = 0;
+ do
{
- uno::Reference< sheet::XNamedRange > xNamed( xNameAccess->getByName( sName ), uno::UNO_QUERY_THROW );
- sAddress = xNamed->getContent();
- // As the address comes from OOO, the addressing
- // style is may not be XL_A1
- eConv = pDocSh->GetDocument()->GetAddressConvention();
- }
- ScRange refRange;
- ScUnoConversion::FillScRange( refRange, pAddr );
- ScRangeList aCellRanges;
- USHORT nFlags = 0;
- if ( !getCellRangesForAddress( nFlags, sAddress, pDocSh, aCellRanges, eConv ) )
- throw uno::RuntimeException();
+ rtl::OUString aToken = sName.getToken( 0, ',', nIndex );
+ vNames.push_back( aToken );
+ } while ( nIndex >= 0 );
- bool bTabFromReferrer = !( nFlags & SCA_TAB_3D );
+ if ( !vNames.size() )
+ vNames.push_back( sName );
- for ( ScRange* pRange = aCellRanges.First() ; pRange; pRange = aCellRanges.Next() )
+ std::vector< rtl::OUString >::iterator it = vNames.begin();
+ std::vector< rtl::OUString >::iterator it_end = vNames.end();
+ for ( ; it != it_end; ++it )
{
- pRange->aStart.SetCol( refRange.aStart.Col() + pRange->aStart.Col() );
- pRange->aStart.SetRow( refRange.aStart.Row() + pRange->aStart.Row() );
- pRange->aStart.SetTab( bTabFromReferrer ? refRange.aStart.Tab() : pRange->aStart.Tab() );
- pRange->aEnd.SetCol( refRange.aStart.Col() + pRange->aEnd.Col() );
- pRange->aEnd.SetRow( refRange.aStart.Row() + pRange->aEnd.Row() );
- pRange->aEnd.SetTab( bTabFromReferrer ? refRange.aEnd.Tab() : pRange->aEnd.Tab() );
+
+ ScAddress::Convention eConv = aConv;
+ // spaces are illegal ( but the user of course can enter them )
+ rtl::OUString sAddress = (*it).trim();
+ if ( xNameAccess->hasByName( sAddress ) )
+ {
+ uno::Reference< sheet::XNamedRange > xNamed( xNameAccess->getByName( sAddress ), uno::UNO_QUERY_THROW );
+ sAddress = xNamed->getContent();
+ // As the address comes from OOO, the addressing
+ // style is may not be XL_A1
+ eConv = pDocSh->GetDocument()->GetAddressConvention();
+ }
+
+ USHORT nFlags = 0;
+ if ( !getCellRangesForAddress( nFlags, sAddress, pDocSh, aCellRanges, eConv ) )
+ return false;
+
+ bool bTabFromReferrer = !( nFlags & SCA_TAB_3D );
+
+ for ( ScRange* pRange = aCellRanges.First() ; pRange; pRange = aCellRanges.Next() )
+ {
+ pRange->aStart.SetCol( refRange.aStart.Col() + pRange->aStart.Col() );
+ pRange->aStart.SetRow( refRange.aStart.Row() + pRange->aStart.Row() );
+ pRange->aStart.SetTab( bTabFromReferrer ? refRange.aStart.Tab() : pRange->aStart.Tab() );
+ pRange->aEnd.SetCol( refRange.aStart.Col() + pRange->aEnd.Col() );
+ pRange->aEnd.SetRow( refRange.aStart.Row() + pRange->aEnd.Row() );
+ pRange->aEnd.SetTab( bTabFromReferrer ? refRange.aEnd.Tab() : pRange->aEnd.Tab() );
+ }
}
+ return true;
+}
+
+ScVbaRange*
+getRangeForName( const uno::Reference< uno::XComponentContext >& xContext, const rtl::OUString& sName, ScDocShell* pDocSh, table::CellRangeAddress& pAddr, ScAddress::Convention eConv = ScAddress::CONV_XL_A1 ) throw ( uno::RuntimeException )
+{
+ ScRangeList aCellRanges;
+ ScRange refRange;
+ ScUnoConversion::FillScRange( refRange, pAddr );
+ if ( !getScRangeListForAddress ( sName, pDocSh, refRange, aCellRanges, eConv ) )
+ throw uno::RuntimeException();
// Single range
if ( aCellRanges.First() == aCellRanges.Last() )
{
uno::Reference< table::XCellRange > xRange( new ScCellRangeObj( pDocSh, *aCellRanges.First() ) );
- return new ScVbaRange( xContext, xRange );
+ // #FIXME need proper (WorkSheet) parent
+ return new ScVbaRange( uno::Reference< vba::XHelperInterface >(), xContext, xRange );
}
uno::Reference< sheet::XSheetCellRangeContainer > xRanges( new ScCellRangesObj( pDocSh, aCellRanges ) );
- return new ScVbaRange( xContext, xRanges );
-
+ // #FIXME need proper (WorkSheet) parent
+ return new ScVbaRange( uno::Reference< vba::XHelperInterface >(), xContext, xRanges );
+}
+
+css::uno::Reference< excel::XRange >
+ScVbaRange::getRangeObjectForName( const uno::Reference< uno::XComponentContext >& xContext, const rtl::OUString& sRangeName, ScDocShell* pDocSh, ScAddress::Convention eConv ) throw ( uno::RuntimeException )
+{
+ table::CellRangeAddress refAddr;
+ return getRangeForName( xContext, sRangeName, pDocSh, refAddr, eConv );
+}
+
+
+table::CellRangeAddress getCellRangeAddressForVBARange( const uno::Any& aParam, ScDocShell* pDocSh, ScAddress::Convention aConv = ScAddress::CONV_XL_A1) throw ( uno::RuntimeException )
+{
+ uno::Reference< table::XCellRange > xRangeParam;
+ switch ( aParam.getValueTypeClass() )
+ {
+ case uno::TypeClass_STRING:
+ {
+ rtl::OUString rString;
+ aParam >>= rString;
+ ScRangeList aCellRanges;
+ ScRange refRange;
+ if ( getScRangeListForAddress ( rString, pDocSh, refRange, aCellRanges, aConv ) )
+ {
+ if ( aCellRanges.First() == aCellRanges.Last() )
+ {
+ table::CellRangeAddress aRangeAddress;
+ ScUnoConversion::FillApiRange( aRangeAddress, *aCellRanges.First() );
+ return aRangeAddress;
+ }
+ }
+ }
+ case uno::TypeClass_INTERFACE:
+ {
+ uno::Reference< excel::XRange > xRange;
+ aParam >>= xRange;
+ if ( xRange.is() )
+ xRange->getCellRange() >>= xRangeParam;
+ break;
+ }
+ default:
+ throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("Can't extact CellRangeAddress from type" ) ), uno::Reference< uno::XInterface >() );
+ }
+ uno::Reference< sheet::XCellRangeAddressable > xAddressable( xRangeParam, uno::UNO_QUERY_THROW );
+ return xAddressable->getRangeAddress();
+
}
uno::Reference< vba::XCollection >
-lcl_setupBorders( const uno::Reference<uno::XComponentContext>& xContext, uno::Reference< table::XCellRange >& xRange ) throw( uno::RuntimeException )
+lcl_setupBorders( const uno::Reference< excel::XRange >& xParentRange, const uno::Reference<uno::XComponentContext>& xContext, const uno::Reference< table::XCellRange >& xRange ) throw( uno::RuntimeException )
{
+ uno::Reference< vba::XHelperInterface > xParent( xParentRange, uno::UNO_QUERY_THROW );
ScDocument* pDoc = getDocumentFromRange(xRange);
if ( !pDoc )
throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "Failed to access document from shell" ) ), uno::Reference< uno::XInterface >() );
ScVbaPalette aPalette( pDoc->GetDocumentShell() );
- uno::Reference< vba::XCollection > borders( new ScVbaBorders( xContext, xRange, aPalette ) );
+ uno::Reference< vba::XCollection > borders( new ScVbaBorders( xParent, xContext, xRange, aPalette ) );
return borders;
}
-ScVbaRange::ScVbaRange( const uno::Reference< uno::XComponentContext >& xContext, const uno::Reference< table::XCellRange >& xRange, sal_Bool bIsRows, sal_Bool bIsColumns ) throw( lang::IllegalArgumentException )
-: mxRange( xRange ),
- m_xContext(xContext),
+ScVbaRange::ScVbaRange( uno::Sequence< uno::Any> const & args,
+ uno::Reference< uno::XComponentContext> const & xContext ) throw ( lang::IllegalArgumentException ) : ScVbaRange_BASE( getXSomethingFromArgs< vba::XHelperInterface >( args, 0 ), xContext, getXSomethingFromArgs< beans::XPropertySet >( args, 1, false ), getModelFromRange( getXSomethingFromArgs< table::XCellRange >( args, 1 ) ), true ), mbIsRows( sal_False ), mbIsColumns( sal_False )
+{
+ mxRange.set( mxPropertySet, uno::UNO_QUERY_THROW );
+ uno::Reference< container::XIndexAccess > xIndex( new SingleRangeIndexAccess( mxContext, mxRange ) );
+ m_Areas = new ScVbaRangeAreas( mxContext, xIndex, mbIsRows, mbIsColumns );
+}
+
+ScVbaRange::ScVbaRange( const uno::Reference< vba::XHelperInterface >& xParent, const uno::Reference< uno::XComponentContext >& xContext, const uno::Reference< table::XCellRange >& xRange, sal_Bool bIsRows, sal_Bool bIsColumns ) throw( lang::IllegalArgumentException )
+: ScVbaRange_BASE( xParent, xContext, uno::Reference< beans::XPropertySet >( xRange, uno::UNO_QUERY_THROW ), getModelFromRange( xRange), true ), mxRange( xRange ),
mbIsRows( bIsRows ),
mbIsColumns( bIsColumns )
{
@@ -963,37 +1171,32 @@ ScVbaRange::ScVbaRange( const uno::Reference< uno::XComponentContext >& xContext
if ( !xRange.is() )
throw lang::IllegalArgumentException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "range is not set " ) ), uno::Reference< uno::XInterface >() , 1 );
- uno::Reference< container::XIndexAccess > xIndex( new SingleRangeIndexAccess( m_xContext, xRange ) );
- m_Areas = new ScVbaRangeAreas( m_xContext, xIndex );
-
- m_Borders = lcl_setupBorders( m_xContext, mxRange );
+ uno::Reference< container::XIndexAccess > xIndex( new SingleRangeIndexAccess( mxContext, xRange ) );
+ m_Areas = new ScVbaRangeAreas( mxContext, xIndex, mbIsRows, mbIsColumns );
}
-ScVbaRange::ScVbaRange( const uno::Reference< uno::XComponentContext >& xContext, const uno::Reference< sheet::XSheetCellRangeContainer >& xRanges, sal_Bool bIsRows, sal_Bool bIsColumns ) throw ( lang::IllegalArgumentException )
-:m_xContext(xContext), mxRanges( xRanges ),mbIsRows( bIsRows ), mbIsColumns( bIsColumns )
+ScVbaRange::ScVbaRange( const uno::Reference< vba::XHelperInterface >& xParent, const uno::Reference< uno::XComponentContext >& xContext, const uno::Reference< sheet::XSheetCellRangeContainer >& xRanges, sal_Bool bIsRows, sal_Bool bIsColumns ) throw ( lang::IllegalArgumentException )
+: 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 )
{
uno::Reference< container::XIndexAccess > xIndex( mxRanges, uno::UNO_QUERY_THROW );
- m_Areas = new ScVbaRangeAreas( m_xContext, xIndex );
+ m_Areas = new ScVbaRangeAreas( mxContext, xIndex, mbIsRows, mbIsColumns );
- // Some methods functions seem to operate on the first range defined
- // but I don't want to enable the line below right now, I'd prefer the
- // Selection stuff to be non functional and enable it method by method
- //m_xRange.set( mxRanges->getByIndex( 0 );
- uno::Reference< table::XCellRange > xRange( mxRanges->getByIndex(0), uno::UNO_QUERY_THROW );
- m_Borders = lcl_setupBorders( m_xContext, xRange );
}
ScVbaRange::~ScVbaRange()
{
}
-uno::Reference< script::XTypeConverter >
-ScVbaRange::getTypeConverter() throw (uno::RuntimeException)
+uno::Reference< vba::XCollection >& ScVbaRange::getBorders()
{
- static uno::Reference< script::XTypeConverter > xTypeConv( m_xContext->getServiceManager()->createInstanceWithContext( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("com.sun.star.script.Converter") ), m_xContext ), uno::UNO_QUERY_THROW );
- return xTypeConv;
+ if ( !m_Borders.is() )
+ {
+ uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny( sal_Int32(1) ), uno::Any() ), uno::UNO_QUERY_THROW );
+ m_Borders = lcl_setupBorders( this, mxContext, uno::Reference< table::XCellRange >( xRange->getCellRange(), uno::UNO_QUERY_THROW ) );
+ }
+ return m_Borders;
}
void
@@ -1058,7 +1261,7 @@ ScVbaRange::setValue( const uno::Any &aValue, ValueSetter& valueSetter ) thro
uno::TypeClass aClass = aValue.getValueTypeClass();
if ( aClass == uno::TypeClass_SEQUENCE )
{
- uno::Reference< script::XTypeConverter > xConverter = getTypeConverter();
+ uno::Reference< script::XTypeConverter > xConverter = getTypeConverter( mxContext );
uno::Any aConverted;
try
{
@@ -1125,7 +1328,7 @@ ScVbaRange::ClearContents( sal_Int32 nFlags ) throw (uno::RuntimeException)
sal_Int32 nItems = m_Areas->getCount();
for ( sal_Int32 index=1; index <= nItems; ++index )
{
- uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny(index) ), uno::UNO_QUERY_THROW );
+ uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny(index), uno::Any() ), uno::UNO_QUERY_THROW );
ScVbaRange* pRange = dynamic_cast< ScVbaRange* >( xRange.get() );
if ( pRange )
pRange->ClearContents( nFlags );
@@ -1171,7 +1374,7 @@ ScVbaRange::setFormulaValue( const uno::Any& rFormula, ScAddress::Convention eCo
aVisitor.visit( valueProcessor );
return;
}
- CellFormulaValueSetter formulaValueSetter( rFormula, getDocumentFromRange( mxRange ), eConv );
+ CellFormulaValueSetter formulaValueSetter( rFormula, getScDocument(), eConv );
setValue( rFormula, formulaValueSetter );
}
@@ -1187,7 +1390,7 @@ ScVbaRange::getFormulaValue( ScAddress::Convention eConv) throw (uno::RuntimeExc
uno::Reference< excel::XRange > xRange( getArea( 0 ), uno::UNO_QUERY_THROW );
return xRange->getFormula();
}
- CellFormulaValueGetter valueGetter( getDocumentFromRange( mxRange ), eConv );
+ CellFormulaValueGetter valueGetter( getScDocument(), eConv );
return getValue( valueGetter );
}
@@ -1218,7 +1421,7 @@ ScVbaRange::getFormula() throw (::com::sun::star::uno::RuntimeException)
return getFormulaValue( ScAddress::CONV_XL_A1 );
}
-double
+sal_Int32
ScVbaRange::getCount() throw (uno::RuntimeException)
{
// If this is a multiple selection apply setValue over all areas
@@ -1229,10 +1432,12 @@ ScVbaRange::getCount() throw (uno::RuntimeException)
aVisitor.visit( valueProcessor );
return valueProcessor.value();
}
- double rowCount, colCount;
+ sal_Int32 rowCount = 0;
+ sal_Int32 colCount = 0;
uno::Reference< table::XColumnRowRange > xColumnRowRange(mxRange, uno::UNO_QUERY_THROW );
rowCount = xColumnRowRange->getRows()->getCount();
colCount = xColumnRowRange->getColumns()->getCount();
+
if( IsRows() )
return rowCount;
if( IsColumns() )
@@ -1281,7 +1486,7 @@ ScVbaRange::HasFormula() throw (uno::RuntimeException)
uno::Any aResult = aNULL();
for ( sal_Int32 index=1; index <= nItems; ++index )
{
- uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny(index) ), uno::UNO_QUERY_THROW );
+ uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny(index), uno::Any() ), uno::UNO_QUERY_THROW );
// if the HasFormula for any area is different to another
// return null
if ( index > 1 )
@@ -1321,7 +1526,7 @@ ScVbaRange::fillSeries( sheet::FillDirection nFillDirection, sheet::FillMode nFi
uno::Reference< vba::XCollection > xCollection( m_Areas, uno::UNO_QUERY_THROW );
for ( sal_Int32 index = 1; index <= xCollection->getCount(); ++index )
{
- uno::Reference< excel::XRange > xRange( xCollection->Item( uno::makeAny( index ) ), uno::UNO_QUERY_THROW );
+ uno::Reference< excel::XRange > xRange( xCollection->Item( uno::makeAny( index ), uno::Any() ), uno::UNO_QUERY_THROW );
ScVbaRange* pThisRange = dynamic_cast< ScVbaRange* >( xRange.get() );
pThisRange->fillSeries( nFillDirection, nFillMode, nFillDateMode, fStep, fEndValue );
@@ -1406,12 +1611,11 @@ ScVbaRange::Offset( const ::uno::Any &nRowOff, const uno::Any &nColOff ) throw (
if ( aCellRanges.Count() > 1 ) // Multi-Area
{
uno::Reference< sheet::XSheetCellRangeContainer > xRanges( new ScCellRangesObj( pUnoRangesBase->GetDocShell(), aCellRanges ) );
-
- return uno::Reference< excel::XRange >( new ScVbaRange( m_xContext, xRanges ) );
+ return new ScVbaRange( getParent(), mxContext, xRanges );
}
// normal range
uno::Reference< table::XCellRange > xRange( new ScCellRangeObj( pUnoRangesBase->GetDocShell(), *aCellRanges.First() ) );
- return new ScVbaRange( m_xContext, xRange );
+ return new ScVbaRange( getParent(), mxContext, xRange );
}
uno::Reference< excel::XRange >
@@ -1432,7 +1636,7 @@ ScVbaRange::CurrentRegion() throw (uno::RuntimeException)
helper.getSheetCellCursor();
xSheetCellCursor->collapseToCurrentRegion();
uno::Reference< sheet::XCellRangeAddressable > xCellRangeAddressable(xSheetCellCursor, uno::UNO_QUERY_THROW);
- return RangeHelper::createRangeFromRange( m_xContext, helper.getCellRangeFromSheet(), xCellRangeAddressable );
+ return RangeHelper::createRangeFromRange( mxContext, helper.getCellRangeFromSheet(), xCellRangeAddressable );
}
uno::Reference< excel::XRange >
@@ -1452,7 +1656,7 @@ ScVbaRange::CurrentArray() throw (uno::RuntimeException)
helper.getSheetCellCursor();
xSheetCellCursor->collapseToCurrentArray();
uno::Reference< sheet::XCellRangeAddressable > xCellRangeAddressable(xSheetCellCursor, uno::UNO_QUERY_THROW);
- return RangeHelper::createRangeFromRange( m_xContext, helper.getCellRangeFromSheet(), xCellRangeAddressable );
+ return RangeHelper::createRangeFromRange( mxContext, helper.getCellRangeFromSheet(), xCellRangeAddressable );
}
uno::Any
@@ -1469,7 +1673,7 @@ ScVbaRange::getFormulaArray() throw (uno::RuntimeException)
}
uno::Reference< sheet::XCellRangeFormula> xCellRangeFormula( mxRange, uno::UNO_QUERY_THROW );
- uno::Reference< script::XTypeConverter > xConverter = getTypeConverter();
+ uno::Reference< script::XTypeConverter > xConverter = getTypeConverter( mxContext );
uno::Any aMatrix;
aMatrix = xConverter->convertTo( uno::makeAny( xCellRangeFormula->getFormulaArray() ) , getCppuType((uno::Sequence< uno::Sequence< uno::Any > >*)0) ) ;
return aMatrix;
@@ -1530,7 +1734,7 @@ ScVbaRange::Address( const uno::Any& RowAbsolute, const uno::Any& ColumnAbsolut
uno::Any aExternalCopy = External;
for ( sal_Int32 index = 1; index <= xCollection->getCount(); ++index )
{
- uno::Reference< excel::XRange > xRange( xCollection->Item( uno::makeAny( index ) ), uno::UNO_QUERY_THROW );
+ uno::Reference< excel::XRange > xRange( xCollection->Item( uno::makeAny( index ), uno::Any() ), uno::UNO_QUERY_THROW );
if ( index > 1 )
{
sAddress += rtl::OUString( ',' );
@@ -1553,7 +1757,9 @@ ScVbaRange::Address( const uno::Any& RowAbsolute, const uno::Any& ColumnAbsolut
dDetails = ScAddress::Details( ScAddress::CONV_XL_R1C1, 0, 0 );
}
USHORT nFlags = SCA_VALID;
- ScDocument* pDoc = getDocumentFromRange( mxRange );
+ ScDocShell* pDocShell = getScDocShell();
+ ScDocument* pDoc = pDocShell->GetDocument();
+
RangeHelper thisRange( mxRange );
table::CellRangeAddress thisAddress = thisRange.getCellRangeAddressable()->getRangeAddress();
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 ) );
@@ -1587,7 +1793,7 @@ ScVbaRange::Address( const uno::Any& RowAbsolute, const uno::Any& ColumnAbsolut
{
// #TODO should I throw an error if R1C1 is not set?
- table::CellRangeAddress refAddress = getCellRangeAddress( RelativeTo, thisRange.getSpreadSheet() );
+ table::CellRangeAddress refAddress = getCellRangeAddressForVBARange( RelativeTo, pDocShell );
dDetails = ScAddress::Details( ScAddress::CONV_XL_R1C1, static_cast< SCROW >( refAddress.StartRow ), static_cast< SCCOL >( refAddress.StartColumn ) );
}
aRange.Format( sRange, nFlags, pDoc, dDetails );
@@ -1595,15 +1801,27 @@ ScVbaRange::Address( const uno::Any& RowAbsolute, const uno::Any& ColumnAbsolut
}
uno::Reference < excel::XFont >
-ScVbaRange::Font() throw (uno::RuntimeException)
+ScVbaRange::Font() throw ( script::BasicErrorException, uno::RuntimeException)
{
uno::Reference< beans::XPropertySet > xProps(mxRange, ::uno::UNO_QUERY );
- ScDocument* pDoc = getDocumentFromRange(mxRange);
+ ScDocument* pDoc = getScDocument();
+ if ( mxRange.is() )
+ xProps.set(mxRange, ::uno::UNO_QUERY );
+ else if ( mxRanges.is() )
+ xProps.set(mxRanges, ::uno::UNO_QUERY );
if ( !pDoc )
throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "Failed to access document from shell" ) ), uno::Reference< uno::XInterface >() );
ScVbaPalette aPalette( pDoc->GetDocumentShell() );
- return uno::Reference< excel::XFont >( new ScVbaFont( aPalette, xProps, getCurrentDataSet() ) );
+ SfxItemSet* pSet = NULL;
+ try
+ {
+ pSet = getCurrentDataSet();
+ }
+ catch( uno::Exception& )
+ {
+ }
+ return new ScVbaFont( this, mxContext, aPalette, xProps, pSet );
}
uno::Reference< excel::XRange >
@@ -1626,7 +1844,8 @@ ScVbaRange::Cells( const uno::Any &nRowIndex, const uno::Any &nColumnIndex ) thr
table::CellRangeAddress thisRangeAddress = thisRange.getCellRangeAddressable()->getRangeAddress();
uno::Reference< table::XCellRange > xSheetRange = thisRange.getCellRangeFromSheet();
if( !bIsIndex && !bIsColumnIndex ) // .Cells
- return uno::Reference< excel::XRange >( new ScVbaRange( m_xContext, mxRange ) );
+ // #FIXE needs proper parent ( Worksheet )
+ return uno::Reference< excel::XRange >( new ScVbaRange( uno::Reference< vba::XHelperInterface >(), mxContext, mxRange ) );
sal_Int32 nIndex = --nRow;
if( bIsIndex && !bIsColumnIndex ) // .Cells(n)
@@ -1644,8 +1863,7 @@ ScVbaRange::Cells( const uno::Any &nRowIndex, const uno::Any &nColumnIndex ) thr
--nColumn;
nRow = nRow + thisRangeAddress.StartRow;
nColumn = nColumn + thisRangeAddress.StartColumn;
-
- return uno::Reference< excel::XRange >( new ScVbaRange( m_xContext, xSheetRange->getCellRangeByPosition( nColumn, nRow, nColumn, nRow ) ) );
+ return new ScVbaRange( getParent(), mxContext, xSheetRange->getCellRangeByPosition( nColumn, nRow, nColumn, nRow ) );
}
void
@@ -1657,7 +1875,7 @@ ScVbaRange::Select() throw (uno::RuntimeException)
ScDocShell* pShell = pUnoRangesBase->GetDocShell();
if ( pShell )
{
- uno::Reference< frame::XModel > xModel( getCurrentDocument(), uno::UNO_QUERY_THROW );
+ uno::Reference< frame::XModel > xModel( pShell->GetModel(), uno::UNO_QUERY_THROW );
uno::Reference< view::XSelectionSupplier > xSelection( xModel->getCurrentController(), uno::UNO_QUERY_THROW );
if ( mxRanges.is() )
xSelection->select( uno::makeAny( mxRanges ) );
@@ -1689,7 +1907,17 @@ void setCursor( const SCCOL& nCol, const SCROW& nRow, bool bInSel = true )
void
ScVbaRange::Activate() throw (uno::RuntimeException)
{
- RangeHelper thisRange( mxRange );
+ // get first cell of current range
+ uno::Reference< table::XCellRange > xCellRange;
+ if ( mxRanges.is() )
+ {
+ uno::Reference< container::XIndexAccess > xIndex( mxRanges, uno::UNO_QUERY_THROW );
+ xCellRange.set( xIndex->getByIndex( 0 ), uno::UNO_QUERY_THROW );
+ }
+ else
+ xCellRange.set( mxRange, uno::UNO_QUERY_THROW );
+
+ RangeHelper thisRange( xCellRange );
uno::Reference< sheet::XCellRangeAddressable > xThisRangeAddress = thisRange.getCellRangeAddressable();
table::CellRangeAddress thisRangeAddress = xThisRangeAddress->getRangeAddress();
@@ -1731,111 +1959,127 @@ ScVbaRange::Activate() throw (uno::RuntimeException)
uno::Reference< excel::XRange >
ScVbaRange::Rows(const uno::Any& aIndex ) throw (uno::RuntimeException)
{
- // #TODO code within the test below "if ( m_Areas.... " can be removed
- // Test is performed only because m_xRange is NOT set to be
- // the first range in m_Areas ( to force failure while
- // the implementations for each method are being updated )
- if ( m_Areas->getCount() > 1 )
- {
- uno::Reference< excel::XRange > xRange( getArea( 0 ), uno::UNO_QUERY_THROW );
- return xRange->Rows( aIndex );
- }
-
+ SCROW nStartRow = 0;
+ SCROW nEndRow = 0;
+
sal_Int32 nValue = 0;
rtl::OUString sAddress;
- if( aIndex.hasValue() )
+
+ if ( aIndex.hasValue() )
{
- uno::Reference< sheet::XCellRangeAddressable > xAddressable( mxRange, uno::UNO_QUERY );
- table::CellRangeAddress aAddress = xAddressable->getRangeAddress();
+ ScCellRangesBase* pUnoRangesBase = getCellRangesBase();
+ ScRangeList aCellRanges = pUnoRangesBase->GetRangeList();
+
+ ScRange aRange = *aCellRanges.First();
if( aIndex >>= nValue )
{
- aAddress.StartRow = --nValue;
- aAddress.EndRow = nValue;
+ aRange.aStart.SetRow( aRange.aStart.Row() + --nValue );
+ aRange.aEnd.SetRow( aRange.aStart.Row() );
}
-
+
else if ( aIndex >>= sAddress )
{
- ScAddress::Details dDetails( ScAddress::CONV_XL_A1, 0, 0 );
- ScRange aRange;
- aRange.ParseRows( sAddress, getDocumentFromRange( mxRange ), dDetails );
- aAddress.StartRow = aRange.aStart.Row();
- aAddress.EndRow = aRange.aEnd.Row();
+ ScAddress::Details dDetails( ScAddress::CONV_XL_A1, 0, 0 );
+ ScRange tmpRange;
+ tmpRange.ParseRows( sAddress, getDocumentFromRange( mxRange ), dDetails );
+ nStartRow = tmpRange.aStart.Row();
+ nEndRow = tmpRange.aEnd.Row();
+
+ aRange.aStart.SetRow( aRange.aStart.Row() + nStartRow );
+ aRange.aEnd.SetRow( aRange.aStart.Row() + ( nEndRow - nStartRow ));
}
else
throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("Illegal param" ) ), uno::Reference< uno::XInterface >() );
-
- return uno::Reference< excel::XRange >( new ScVbaRange( m_xContext, mxRange->getCellRangeByPosition(
- aAddress.StartColumn, aAddress.StartRow,
- aAddress.EndColumn, aAddress.EndRow ), true ) );
+
+ if ( aRange.aStart.Row() < 0 || aRange.aEnd.Row() < 0 )
+ throw uno::RuntimeException( rtl::OUString::createFromAscii("Internal failure, illegal param"), uno::Reference< uno::XInterface >() );
+ // return a normal range ( even for multi-selection
+ uno::Reference< table::XCellRange > xRange( new ScCellRangeObj( pUnoRangesBase->GetDocShell(), aRange ) );
+ return new ScVbaRange( getParent(), mxContext, xRange, true );
}
- // Questionable return, I'm just copying the invalid Any::value path
- // above. Would seem to me that this is an internal error and
- // warrants an exception thrown
- return uno::Reference< excel::XRange >( new ScVbaRange( m_xContext, mxRange, true ) );
+ // Rows() - no params
+ if ( m_Areas->getCount() > 1 )
+ return new ScVbaRange( getParent(), mxContext, mxRanges, true );
+ return new ScVbaRange( getParent(), mxContext, mxRange, true );
}
uno::Reference< excel::XRange >
-ScVbaRange::Columns( const uno::Any& aIndex ) throw (uno::RuntimeException)
+ScVbaRange::Columns(const uno::Any& aIndex ) throw (uno::RuntimeException)
{
- // #TODO code within the test below "if ( m_Areas.... " can be removed
- // Test is performed only because m_xRange is NOT set to be
- // the first range in m_Areas ( to force failure while
- // the implementations for each method are being updated )
- if ( m_Areas->getCount() > 1 )
- {
- uno::Reference< excel::XRange > xRange( getArea( 0 ), uno::UNO_QUERY_THROW );
- return xRange->Columns( aIndex );
- }
+ SCCOL nStartCol = 0;
+ SCCOL nEndCol = 0;
+
+ sal_Int32 nValue = 0;
+ rtl::OUString sAddress;
+
+ ScCellRangesBase* pUnoRangesBase = getCellRangesBase();
+ ScRangeList aCellRanges = pUnoRangesBase->GetRangeList();
+
+ ScRange aRange = *aCellRanges.First();
if ( aIndex.hasValue() )
{
- uno::Reference< excel::XRange > xRange;
- sal_Int32 nValue = 0;
- rtl::OUString sAddress;
- RangeHelper thisRange( mxRange );
- uno::Reference< sheet::XCellRangeAddressable > xThisRangeAddress = thisRange.getCellRangeAddressable();
- uno::Reference< table::XCellRange > xRanges = thisRange.getCellRangeFromSheet();
- table::CellRangeAddress thisRangeAddress = xThisRangeAddress->getRangeAddress();
- uno::Reference< table::XCellRange > xReferrer = xRanges->getCellRangeByPosition( thisRangeAddress.StartColumn, thisRangeAddress.StartRow, MAXCOL, thisRangeAddress.EndRow );
-
if ( aIndex >>= nValue )
{
- --nValue;
- // col value can expand outside this range
- // rows however cannot
-
- thisRangeAddress.StartColumn = nValue;
- thisRangeAddress.EndColumn = nValue;
+ aRange.aStart.SetCol( aRange.aStart.Col() + static_cast< SCCOL > ( --nValue ) );
+ aRange.aEnd.SetCol( aRange.aStart.Col() );
}
- else if ( aIndex >>= sAddress )
+
+ else if ( aIndex >>= sAddress )
{
ScAddress::Details dDetails( ScAddress::CONV_XL_A1, 0, 0 );
- ScRange aRange;
- aRange.ParseCols( sAddress, getDocumentFromRange( mxRange ), dDetails );
- thisRangeAddress.StartColumn = aRange.aStart.Col();
- thisRangeAddress.EndColumn = aRange.aEnd.Col();
+ ScRange tmpRange;
+ tmpRange.ParseCols( sAddress, getDocumentFromRange( mxRange ), dDetails );
+ nStartCol = tmpRange.aStart.Col();
+ nEndCol = tmpRange.aEnd.Col();
+
+ aRange.aStart.SetCol( aRange.aStart.Col() + nStartCol );
+ aRange.aEnd.SetCol( aRange.aStart.Col() + ( nEndCol - nStartCol ));
}
else
throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("Illegal param" ) ), uno::Reference< uno::XInterface >() );
- return uno::Reference< excel::XRange >( new ScVbaRange( m_xContext, xReferrer->getCellRangeByPosition( thisRangeAddress.StartColumn, thisRangeAddress.StartRow, thisRangeAddress.EndColumn, thisRangeAddress.EndRow ), false, true ) );
+
+ if ( aRange.aStart.Col() < 0 || aRange.aEnd.Col() < 0 )
+ throw uno::RuntimeException( rtl::OUString::createFromAscii("Internal failure, illegal param"), uno::Reference< uno::XInterface >() );
}
- // otherwise return this object ( e.g for columns property with no
- // params
- return uno::Reference< excel::XRange >( new ScVbaRange( m_xContext, mxRange, false, true ) );
-}
+ // Columns() - no params
+ //return new ScVbaRange( getParent(), mxContext, mxRange, false, true );
+ uno::Reference< table::XCellRange > xRange( new ScCellRangeObj( pUnoRangesBase->GetDocShell(), aRange ) );
+ return new ScVbaRange( getParent(), mxContext, xRange, false, true );
+}
void
-ScVbaRange::setMergeCells( sal_Bool bIsMerged ) throw (uno::RuntimeException)
+ScVbaRange::setMergeCells( const uno::Any& aIsMerged ) throw (script::BasicErrorException, uno::RuntimeException)
{
+ sal_Bool bIsMerged = sal_False;
+ aIsMerged >>= bIsMerged;
uno::Reference< util::XMergeable > xMerge( mxRange, ::uno::UNO_QUERY_THROW );
//FIXME need to check whether all the cell contents are retained or lost by popping up a dialog
xMerge->merge( bIsMerged );
}
-sal_Bool
-ScVbaRange::getMergeCells() throw (uno::RuntimeException)
+uno::Any
+ScVbaRange::getMergeCells() throw (script::BasicErrorException, uno::RuntimeException)
{
+ sal_Int32 nItems = m_Areas->getCount();
+
+ if ( nItems > 1 )
+ {
+ uno::Any aResult = aNULL();
+ for ( sal_Int32 index=1; index != nItems; ++index )
+ {
+ uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny(index), uno::Any() ), uno::UNO_QUERY_THROW );
+ if ( index > 1 )
+ if ( aResult != xRange->getMergeCells() )
+ return aNULL();
+ aResult = xRange->getMergeCells();
+ if ( aNULL() == aResult )
+ return aNULL();
+ }
+ return aResult;
+
+ }
uno::Reference< util::XMergeable > xMerge( mxRange, ::uno::UNO_QUERY_THROW );
- return xMerge->getIsMerged();
+ return uno::makeAny( xMerge->getIsMerged() );
}
void
@@ -1890,7 +2134,7 @@ ScVbaRange::Cut(const ::uno::Any& Destination) throw (uno::RuntimeException)
}
void
-ScVbaRange::setNumberFormat( const uno::Any& aFormat ) throw (uno::RuntimeException)
+ScVbaRange::setNumberFormat( const uno::Any& aFormat ) throw ( script::BasicErrorException, uno::RuntimeException)
{
rtl::OUString sFormat;
aFormat >>= sFormat;
@@ -1899,7 +2143,7 @@ ScVbaRange::setNumberFormat( const uno::Any& aFormat ) throw (uno::RuntimeExcept
sal_Int32 nItems = m_Areas->getCount();
for ( sal_Int32 index=1; index <= nItems; ++index )
{
- uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny(index) ), uno::UNO_QUERY_THROW );
+ uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny(index), uno::Any() ), uno::UNO_QUERY_THROW );
xRange->setNumberFormat( aFormat );
}
return;
@@ -1909,7 +2153,7 @@ ScVbaRange::setNumberFormat( const uno::Any& aFormat ) throw (uno::RuntimeExcept
}
uno::Any
-ScVbaRange::getNumberFormat() throw (uno::RuntimeException)
+ScVbaRange::getNumberFormat() throw ( script::BasicErrorException, uno::RuntimeException)
{
if ( m_Areas->getCount() > 1 )
@@ -1918,7 +2162,7 @@ ScVbaRange::getNumberFormat() throw (uno::RuntimeException)
uno::Any aResult = aNULL();
for ( sal_Int32 index=1; index <= nItems; ++index )
{
- uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny(index) ), uno::UNO_QUERY_THROW );
+ uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny(index), uno::Any() ), uno::UNO_QUERY_THROW );
// if the numberformat of one area is different to another
// return null
if ( index > 1 )
@@ -1954,15 +2198,15 @@ ScVbaRange::Resize( const uno::Any &RowSize, const uno::Any &ColumnSize ) throw
xCursor->collapseToSize( nColumnSize, nRowSize );
uno::Reference< sheet::XCellRangeAddressable > xCellRangeAddressable(xCursor, ::uno::UNO_QUERY_THROW );
uno::Reference< table::XCellRange > xRange( xSheetRange->getSpreadsheet(), ::uno::UNO_QUERY_THROW );
- return uno::Reference< excel::XRange >( new ScVbaRange( m_xContext,xRange->getCellRangeByPosition(
+ return new ScVbaRange( getParent(), mxContext,xRange->getCellRangeByPosition(
xCellRangeAddressable->getRangeAddress().StartColumn,
xCellRangeAddressable->getRangeAddress().StartRow,
xCellRangeAddressable->getRangeAddress().EndColumn,
- xCellRangeAddressable->getRangeAddress().EndRow ) ) );
+ xCellRangeAddressable->getRangeAddress().EndRow ) );
}
void
-ScVbaRange::setWrapText( const uno::Any& aIsWrapped ) throw (uno::RuntimeException)
+ScVbaRange::setWrapText( const uno::Any& aIsWrapped ) throw (script::BasicErrorException, uno::RuntimeException)
{
if ( m_Areas->getCount() > 1 )
{
@@ -1970,7 +2214,7 @@ ScVbaRange::setWrapText( const uno::Any& aIsWrapped ) throw (uno::RuntimeExcepti
uno::Any aResult;
for ( sal_Int32 index=1; index <= nItems; ++index )
{
- uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny(index) ), uno::UNO_QUERY_THROW );
+ uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny(index), uno::Any() ), uno::UNO_QUERY_THROW );
xRange->setWrapText( aIsWrapped );
}
return;
@@ -1981,7 +2225,7 @@ ScVbaRange::setWrapText( const uno::Any& aIsWrapped ) throw (uno::RuntimeExcepti
}
uno::Any
-ScVbaRange::getWrapText() throw (uno::RuntimeException)
+ScVbaRange::getWrapText() throw (script::BasicErrorException, uno::RuntimeException)
{
if ( m_Areas->getCount() > 1 )
{
@@ -1989,8 +2233,8 @@ ScVbaRange::getWrapText() throw (uno::RuntimeException)
uno::Any aResult;
for ( sal_Int32 index=1; index <= nItems; ++index )
{
- uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny(index) ), uno::UNO_QUERY_THROW );
- if ( index > 1 )
+ uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny(index), uno::Any() ), uno::UNO_QUERY_THROW );
+ if ( index > 1 )
if ( aResult != xRange->getWrapText() )
return aNULL();
aResult = xRange->getWrapText();
@@ -2009,10 +2253,10 @@ ScVbaRange::getWrapText() throw (uno::RuntimeException)
return aValue;
}
-uno::Reference< excel::XInterior > ScVbaRange::Interior( ) throw (uno::RuntimeException)
+uno::Reference< excel::XInterior > ScVbaRange::Interior( ) throw ( script::BasicErrorException, uno::RuntimeException)
{
uno::Reference< beans::XPropertySet > xProps( mxRange, uno::UNO_QUERY_THROW );
- return uno::Reference<excel::XInterior> (new ScVbaInterior ( m_xContext, xProps, getDocumentFromRange( mxRange ) ));
+ return new ScVbaInterior ( this, mxContext, xProps, getScDocument() );
}
uno::Reference< excel::XRange >
ScVbaRange::Range( const uno::Any &Cell1, const uno::Any &Cell2 ) throw (uno::RuntimeException)
@@ -2023,7 +2267,17 @@ uno::Reference< excel::XRange >
ScVbaRange::Range( const uno::Any &Cell1, const uno::Any &Cell2, bool bForceUseInpuRangeTab ) throw (uno::RuntimeException)
{
- RangeHelper thisRange( mxRange );
+ uno::Reference< table::XCellRange > xCellRange = mxRange;
+
+ if ( m_Areas->getCount() > 1 )
+ {
+ uno::Reference< container::XIndexAccess > xIndex( mxRanges, uno::UNO_QUERY_THROW );
+ xCellRange.set( xIndex->getByIndex( 0 ), uno::UNO_QUERY_THROW );
+ }
+ else
+ xCellRange.set( mxRange );
+
+ RangeHelper thisRange( xCellRange );
uno::Reference< table::XCellRange > xRanges = thisRange.getCellRangeFromSheet();
uno::Reference< sheet::XCellRangeAddressable > xAddressable( xRanges, uno::UNO_QUERY_THROW );
@@ -2051,18 +2305,18 @@ ScVbaRange::Range( const uno::Any &Cell1, const uno::Any &Cell2, bool bForceUseI
Cell1 >>= sName;
RangeHelper referRange( xReferrer );
table::CellRangeAddress referAddress = referRange.getCellRangeAddressable()->getRangeAddress();
- return getRangeForName( m_xContext, sName, getDocShellFromRange( mxRange ), referAddress );
+ return getRangeForName( mxContext, sName, getScDocShell(), referAddress );
}
else
{
table::CellRangeAddress cell1, cell2;
- cell1 = getCellRangeAddress( Cell1, thisRange.getSpreadSheet() );
+ cell1 = getCellRangeAddressForVBARange( Cell1, getScDocShell() );
// Cell1 & Cell2 defined
// Excel seems to combine the range as the range defined by
// the combination of Cell1 & Cell2
- cell2 = getCellRangeAddress( Cell2, thisRange.getSpreadSheet() );
+ cell2 = getCellRangeAddressForVBARange( Cell2, getScDocShell() );
resultAddress.StartColumn = ( cell1.StartColumn < cell2.StartColumn ) ? cell1.StartColumn : cell2.StartColumn;
resultAddress.StartRow = ( cell1.StartRow < cell2.StartRow ) ? cell1.StartRow : cell2.StartRow;
@@ -2092,7 +2346,6 @@ ScVbaRange::Range( const uno::Any &Cell1, const uno::Any &Cell2, bool bForceUseI
}
ScRange parentAddress;
ScUnoConversion::FillScRange( parentAddress, parentRangeAddress);
- uno::Reference< table::XCellRange > xCellRange;
if ( aRange.aStart.Col() >= 0 && aRange.aStart.Row() >= 0 && aRange.aEnd.Col() >= 0 && aRange.aEnd.Row() >= 0 )
{
sal_Int32 nStartX = parentAddress.aStart.Col() + aRange.aStart.Col();
@@ -2105,11 +2358,11 @@ ScVbaRange::Range( const uno::Any &Cell1, const uno::Any &Cell2, bool bForceUseI
{
ScRange aNew( (SCCOL)nStartX, (SCROW)nStartY, parentAddress.aStart.Tab(),
(SCCOL)nEndX, (SCROW)nEndY, parentAddress.aEnd.Tab() );
- xCellRange = new ScCellRangeObj( getDocShellFromRange( mxRange ), aNew );
+ xCellRange = new ScCellRangeObj( getScDocShell(), aNew );
}
}
- return uno::Reference< excel::XRange > ( new ScVbaRange( m_xContext, xCellRange ) );
+ return new ScVbaRange( getParent(), mxContext, xCellRange );
}
@@ -2139,9 +2392,11 @@ getPasteFlags (sal_Int32 Paste)
nFlags = IDF_FORMULA;break;
case excel::XlPasteType::xlPasteFormulasAndNumberFormats :
case excel::XlPasteType::xlPasteValues:
- // FOR_UPSTREAM_BUILD
- //nFlags = ( IDF_VALUE | IDF_DATETIME | IDF_STRING | IDF_SPECIAL_BOOLEAN ); break;
+#ifdef VBA_OOBUILD_HACK
+ nFlags = ( IDF_VALUE | IDF_DATETIME | IDF_STRING | IDF_SPECIAL_BOOLEAN ); break;
+#else
nFlags = ( IDF_VALUE | IDF_DATETIME | IDF_STRING ); break;
+#endif
case excel::XlPasteType::xlPasteValuesAndNumberFormats:
nFlags = IDF_VALUE | IDF_ATTRIB; break;
case excel::XlPasteType::xlPasteColumnWidths:
@@ -2182,6 +2437,11 @@ ScVbaRange::PasteSpecial( const uno::Any& Paste, const uno::Any& Operation, cons
{
if ( m_Areas->getCount() > 1 )
throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("That command cannot be used on multiple selections" ) ), uno::Reference< uno::XInterface >() );
+ uno::Reference< view::XSelectionSupplier > xSelection( getCurrentDocument()->getCurrentController(), uno::UNO_QUERY_THROW );
+ // save old selection
+ uno::Reference< uno::XInterface > xSel( getCurrentDocument()->getCurrentSelection() );
+ // select this range
+ xSelection->select( uno::makeAny( mxRange ) );
// set up defaults
sal_Int32 nPaste = excel::XlPasteType::xlPasteAll;
sal_Int32 nOperation = excel::XlPasteSpecialOperation::xlPasteSpecialOperationNone;
@@ -2200,6 +2460,8 @@ ScVbaRange::PasteSpecial( const uno::Any& Paste, const uno::Any& Operation, cons
USHORT nFlags = getPasteFlags(nPaste);
USHORT nFormulaBits = getPasteFormulaBits(nOperation);
implnPasteSpecial(nFlags,nFormulaBits,bSkipBlanks,bTranspose);
+ // restore selection
+ xSelection->select( uno::makeAny( xSel ) );
}
uno::Reference< excel::XRange >
@@ -2226,10 +2488,10 @@ ScVbaRange::getEntireColumnOrRow( bool bColumn ) throw (uno::RuntimeException)
{
uno::Reference< sheet::XSheetCellRangeContainer > xRanges( new ScCellRangesObj( pUnoRangesBase->GetDocShell(), aCellRanges ) );
- return uno::Reference< excel::XRange >( new ScVbaRange( m_xContext, xRanges, !bColumn, bColumn ) );
+ return new ScVbaRange( getParent(), mxContext, xRanges, !bColumn, bColumn );
}
uno::Reference< table::XCellRange > xRange( new ScCellRangeObj( pUnoRangesBase->GetDocShell(), *aCellRanges.First() ) );
- return new ScVbaRange( m_xContext, xRange, !bColumn, bColumn );
+ return new ScVbaRange( getParent(), mxContext, xRange, !bColumn, bColumn );
}
uno::Reference< excel::XRange > SAL_CALL
@@ -2247,7 +2509,8 @@ ScVbaRange::getEntireColumn() throw (uno::RuntimeException)
uno::Reference< excel::XComment > SAL_CALL
ScVbaRange::AddComment( const uno::Any& Text ) throw (uno::RuntimeException)
{
- uno::Reference< excel::XComment > xComment( new ScVbaComment( m_xContext, mxRange ) );
+
+ uno::Reference< excel::XComment > xComment( new ScVbaComment( this, mxContext, mxRange ) );
// if you don't pass a valid text or if there is already a comment
// associated with the range then return NULL
if ( !xComment->Text( Text, uno::Any(), uno::Any() ).getLength()
@@ -2261,7 +2524,7 @@ ScVbaRange::getComment() throw (uno::RuntimeException)
{
// intentional behavior to return a null object if no
// comment defined
- uno::Reference< excel::XComment > xComment( new ScVbaComment( m_xContext, mxRange ) );
+ uno::Reference< excel::XComment > xComment( new ScVbaComment( this, mxContext, mxRange ) );
if ( !xComment->Text( uno::Any(), uno::Any(), uno::Any() ).getLength() )
return NULL;
return xComment;
@@ -2287,7 +2550,7 @@ ScVbaRange::getHidden() throw (uno::RuntimeException)
// first area
if ( m_Areas->getCount() > 1 )
{
- uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny(sal_Int32(1)) ), uno::UNO_QUERY_THROW );
+ uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny(sal_Int32(1)), uno::Any() ), uno::UNO_QUERY_THROW );
return xRange->getHidden();
}
bool bIsVisible = false;
@@ -2312,15 +2575,14 @@ ScVbaRange::setHidden( const uno::Any& _hidden ) throw (uno::RuntimeException)
sal_Int32 nItems = m_Areas->getCount();
for ( sal_Int32 index=1; index <= nItems; ++index )
{
- uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny(index) ), uno::UNO_QUERY_THROW );
+ uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny(index), uno::Any() ), uno::UNO_QUERY_THROW );
xRange->setHidden( _hidden );
}
return;
}
sal_Bool bHidden = sal_False;
- if ( !(_hidden >>= bHidden) )
- throw uno::RuntimeException( ::rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "Failed to extract param for Hidden property" ) ), uno::Reference< uno::XInterface >() );
+ _hidden >>= bHidden;
try
{
@@ -2333,6 +2595,19 @@ ScVbaRange::setHidden( const uno::Any& _hidden ) throw (uno::RuntimeException)
}
}
+rtl::OUString lcl_replaceAll( const rtl::OUString& rString, rtl::OUString sWhat, rtl::OUString sWith )
+{
+ rtl::OUString sString( rString );
+ sal_Int32 offset = 0;
+ sal_Int32 nWithLen = sWith.getLength();
+ while ((offset = sString.indexOf(sWhat )) >= 0)
+ {
+ sString = sString.replaceAt(offset, nWithLen, sWith);
+ offset += nWithLen;
+ }
+ return sString;
+}
+
::sal_Bool SAL_CALL
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)
{
@@ -2340,15 +2615,16 @@ ScVbaRange::Replace( const ::rtl::OUString& What, const ::rtl::OUString& Replace
{
for ( sal_Int32 index = 1; index <= m_Areas->getCount(); ++index )
{
- uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny( index ) ), uno::UNO_QUERY_THROW );
+ uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny( index ), uno::Any() ), uno::UNO_QUERY_THROW );
xRange->Replace( What, Replacement, LookAt, SearchOrder, MatchCase, MatchByte, SearchFormat, ReplaceFormat );
}
return sal_True; // seems to return true always ( or at least I haven't found the trick of
}
+
// sanity check required params
- if ( !What.getLength() || !Replacement.getLength() )
+ if ( !What.getLength() /*|| !Replacement.getLength()*/ )
throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("Range::Replace, missing params" )) , uno::Reference< uno::XInterface >() );
-
+ rtl::OUString sWhat = VBAToRegexp( What);
// #TODO #FIXME SearchFormat & ReplacesFormat are not processed
// What do we do about MatchByte.. we don't seem to support that
const SvxSearchItem& globalSearchOptions = ScGlobal::GetSearchItem();
@@ -2358,14 +2634,14 @@ ScVbaRange::Replace( const ::rtl::OUString& What, const ::rtl::OUString& Replace
sal_Int16 nSearchOrder = globalSearchOptions.GetRowDirection() ? excel::XlSearchOrder::xlByRows : excel::XlSearchOrder::xlByColumns;
sal_Bool bMatchCase = sal_False;
-
uno::Reference< util::XReplaceable > xReplace( mxRange, uno::UNO_QUERY );
if ( xReplace.is() )
{
uno::Reference< util::XReplaceDescriptor > xDescriptor =
xReplace->createReplaceDescriptor();
- xDescriptor->setSearchString( What);
+ xDescriptor->setSearchString( sWhat);
+ xDescriptor->setPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( SC_UNO_SRCHREGEXP ) ), uno::makeAny( sal_True ) );
xDescriptor->setReplaceString( Replacement);
if ( LookAt.hasValue() )
{
@@ -2415,38 +2691,26 @@ ScVbaRange::Replace( const ::rtl::OUString& What, const ::rtl::OUString& Replace
return sal_True; // always
}
-uno::Reference< table::XCellRange >
-ScVbaRange::getCellRangeForName( const rtl::OUString& sRangeName, const uno::Reference< sheet::XSpreadsheet >& xDoc, ScAddress::Convention aConv )
-{
- uno::Reference< uno::XInterface > xRanges( xDoc, uno::UNO_QUERY_THROW );
- ScCellRangeObj* pRanges = dynamic_cast< ScCellRangeObj* >( xRanges.get() );
- ScAddress::Convention eConv = aConv;//ScAddress::CONV_XL_A1; the default.
-
- ScAddress::Details dDetails( eConv, 0, 0 );
-
- uno::Reference< table::XCellRange > xRange;
- if ( pRanges )
- xRange = pRanges->getCellRangeByName( sRangeName, dDetails );
- return xRange;
-}
-
-uno::Reference< table::XCellRange > processKey( const uno::Any& Key, uno::Reference< table::XCellRange >& xRange )
+uno::Reference< table::XCellRange > processKey( const uno::Any& Key, uno::Reference< uno::XComponentContext >& xContext, ScDocShell* pDocSh )
{
- uno::Reference< table::XCellRange > xKey;
+ uno::Reference< excel::XRange > xKeyRange;
if ( Key.getValueType() == excel::XRange::static_type() )
{
- uno::Reference< excel::XRange > xKeyRange( Key, uno::UNO_QUERY_THROW );
- xKey.set( xKeyRange->getCellRange(), uno::UNO_QUERY_THROW );
+ xKeyRange.set( Key, uno::UNO_QUERY_THROW );
}
else if ( Key.getValueType() == ::getCppuType( static_cast< const rtl::OUString* >(0) ) )
{
rtl::OUString sRangeName = ::comphelper::getString( Key );
- RangeHelper dRange( xRange );
- xKey = ScVbaRange::getCellRangeForName( sRangeName, dRange.getSpreadSheet() );
+ table::CellRangeAddress aRefAddr;
+ if ( !pDocSh )
+ throw uno::RuntimeException( rtl::OUString(RTL_CONSTASCII_USTRINGPARAM("Range::Sort no docshell to calculate key param")), uno::Reference< uno::XInterface >() );
+ xKeyRange = getRangeForName( xContext, sRangeName, pDocSh, aRefAddr );
}
else
throw uno::RuntimeException( rtl::OUString(RTL_CONSTASCII_USTRINGPARAM("Range::Sort illegal type value for key param")), uno::Reference< uno::XInterface >() );
+ uno::Reference< table::XCellRange > xKey;
+ xKey.set( xKeyRange->getCellRange(), uno::UNO_QUERY_THROW );
return xKey;
}
@@ -2514,17 +2778,15 @@ ScVbaRange::Sort( const uno::Any& Key1, const uno::Any& Order1, const uno::Any&
sal_Int16 nDataOption2 = excel::XlSortDataOption::xlSortNormal;;
sal_Int16 nDataOption3 = excel::XlSortDataOption::xlSortNormal;
- ScDocument* pDoc = getDocumentFromRange( mxRange );
+ ScDocument* pDoc = getScDocument();
if ( !pDoc )
throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "Failed to access document from shell" ) ), uno::Reference< uno::XInterface >() );
RangeHelper thisRange( mxRange );
table::CellRangeAddress thisRangeAddress = thisRange.getCellRangeAddressable()->getRangeAddress();
- //SCTAB nTab = thisRangeAddress.Sheet;
-
ScSortParam aSortParam;
- // FOR_UPSTREAM_BUILD
- //pDoc->GetSortParam( aSortParam, nTab );
+ SCTAB nTab = thisRangeAddress.Sheet;
+ pDoc->GetSortParam( aSortParam, nTab );
if ( DataOption1.hasValue() )
DataOption1 >>= nDataOption1;
@@ -2577,17 +2839,18 @@ ScVbaRange::Sort( const uno::Any& Key1, const uno::Any& Order1, const uno::Any&
if ( nOrientation == excel::XlSortOrientation::xlSortRows )
bIsSortColumns = sal_True;
-
- // FOR_UPSTREAM_BUILD
- //sal_Int16 nHeader = aSortParam.nCompatHeader;
sal_Int16 nHeader = 0;
+#ifdef VBA_OOBUILD_HACK
+ nHeader = aSortParam.nCompatHeader;
+#endif
sal_Bool bContainsHeader = sal_False;
if ( Header.hasValue() )
{
nHeader = ::comphelper::getINT16( Header );
- // FOR_UPSTREAM_BUILD
- //aSortParam.nCompatHeader = nHeader;
+#ifdef VBA_OOBUILD_HACK
+ aSortParam.nCompatHeader = nHeader;
+#endif
}
if ( nHeader == excel::XlYesNoGuess::xlGuess )
@@ -2598,9 +2861,9 @@ ScVbaRange::Sort( const uno::Any& Key1, const uno::Any& Order1, const uno::Any&
nHeader = excel::XlYesNoGuess::xlYes;
else
nHeader = excel::XlYesNoGuess::xlNo;
- // save set param as default
- // FOR_UPSTREAM_BUILD
- //aSortParam.nCompatHeader = nHeader;
+#ifdef VBA_OOBUILD_HACK
+ aSortParam.nCompatHeader = nHeader;
+#endif
}
if ( nHeader == excel::XlYesNoGuess::xlYes )
@@ -2653,15 +2916,15 @@ ScVbaRange::Sort( const uno::Any& Key1, const uno::Any& Order1, const uno::Any&
uno::Reference< table::XCellRange > xKey1;
uno::Reference< table::XCellRange > xKey2;
uno::Reference< table::XCellRange > xKey3;
-
- xKey1 = processKey( Key1, mxRange );
+ ScDocShell* pDocShell = getScDocShell();
+ xKey1 = processKey( Key1, mxContext, pDocShell );
if ( !xKey1.is() )
throw uno::RuntimeException( rtl::OUString(RTL_CONSTASCII_USTRINGPARAM("Range::Sort needs a key1 param")), uno::Reference< uno::XInterface >() );
if ( Key2.hasValue() )
- xKey2 = processKey( Key2, mxRange );
+ xKey2 = processKey( Key2, mxContext, pDocShell );
if ( Key3.hasValue() )
- xKey3 = processKey( Key3, mxRange );
+ xKey3 = processKey( Key3, mxContext, pDocShell );
uno::Reference< util::XSortable > xSort( mxRange, uno::UNO_QUERY_THROW );
uno::Sequence< beans::PropertyValue > sortDescriptor = xSort->createSortDescriptor();
@@ -2689,8 +2952,7 @@ ScVbaRange::Sort( const uno::Any& Key1, const uno::Any& Order1, const uno::Any&
nIndex = findSortPropertyIndex( sortDescriptor, CONTS_HEADER );
sortDescriptor[ nIndex ].Value <<= bContainsHeader;
- // FOR_UPSTREAM_BUILD
- //pDoc->SetSortParam( aSortParam, nTab );
+ pDoc->SetSortParam( aSortParam, nTab );
xSort->sort( sortDescriptor );
// #FIXME #TODO
@@ -2719,7 +2981,7 @@ ScVbaRange::End( ::sal_Int32 Direction ) throw (uno::RuntimeException)
// Save ActiveCell pos ( to restore later )
uno::Any aDft;
rtl::OUString sActiveCell = ScVbaGlobals::getGlobalsImpl(
- m_xContext )->getApplication()->getActiveCell()->Address(aDft, aDft, aDft, aDft, aDft );
+ mxContext )->getApplication()->getActiveCell()->Address(aDft, aDft, aDft, aDft, aDft );
// position current cell upper left of this range
Cells( uno::makeAny( (sal_Int32) 1 ), uno::makeAny( (sal_Int32) 1 ) )->Select();
@@ -2761,17 +3023,17 @@ ScVbaRange::End( ::sal_Int32 Direction ) throw (uno::RuntimeException)
// result is the ActiveCell
rtl::OUString sMoved = ScVbaGlobals::getGlobalsImpl(
- m_xContext )->getApplication()->getActiveCell()->Address(aDft, aDft, aDft, aDft, aDft );
+ mxContext )->getApplication()->getActiveCell()->Address(aDft, aDft, aDft, aDft, aDft );
// restore old ActiveCell
uno::Any aVoid;
uno::Reference< excel::XRange > xOldActiveCell( ScVbaGlobals::getGlobalsImpl(
- m_xContext )->getActiveSheet()->Range( uno::makeAny( sActiveCell ), aVoid ), uno::UNO_QUERY_THROW );
+ mxContext )->getActiveSheet()->Range( uno::makeAny( sActiveCell ), aVoid ), uno::UNO_QUERY_THROW );
xOldActiveCell->Select();
uno::Reference< excel::XRange > resultCell;
resultCell.set( ScVbaGlobals::getGlobalsImpl(
- m_xContext )->getActiveSheet()->Range( uno::makeAny( sMoved ), aVoid ), uno::UNO_QUERY_THROW );
+ mxContext )->getActiveSheet()->Range( uno::makeAny( sMoved ), aVoid ), uno::UNO_QUERY_THROW );
// return result
@@ -2781,8 +3043,8 @@ ScVbaRange::End( ::sal_Int32 Direction ) throw (uno::RuntimeException)
bool
ScVbaRange::isSingleCellRange()
{
- uno::Reference< table::XColumnRowRange > xColumnRowRange(mxRange, uno::UNO_QUERY_THROW );
- if ( xColumnRowRange->getRows()->getCount() == 1 && xColumnRowRange->getColumns()->getCount() == 1 )
+ uno::Reference< table::XColumnRowRange > xColumnRowRange(mxRange, uno::UNO_QUERY);
+ if ( xColumnRowRange.is() && xColumnRowRange->getRows()->getCount() == 1 && xColumnRowRange->getColumns()->getCount() == 1 )
return true;
return false;
}
@@ -2798,7 +3060,7 @@ ScVbaRange::characters( const uno::Any& Start, const uno::Any& Length ) throw (u
throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "Failed to access document from shell" ) ), uno::Reference< uno::XInterface >() );
ScVbaPalette aPalette( pDoc->GetDocumentShell() );
- return uno::Reference< excel::XCharacters >( new ScVbaCharacters( m_xContext, aPalette, xSimple, Start, Length ) );
+ return new ScVbaCharacters( this, mxContext, aPalette, xSimple, Start, Length );
}
void SAL_CALL
@@ -2810,7 +3072,7 @@ ScVbaRange::Delete( const uno::Any& Shift ) throw (uno::RuntimeException)
sal_Int32 nItems = m_Areas->getCount();
for ( sal_Int32 index=1; index <= nItems; ++index )
{
- uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny(index) ), uno::UNO_QUERY_THROW );
+ uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny(index), uno::Any() ), uno::UNO_QUERY_THROW );
xRange->Delete( Shift );
}
return;
@@ -2859,7 +3121,7 @@ ScVbaRange::hasElements() throw (uno::RuntimeException)
uno::Reference< container::XEnumeration > SAL_CALL
ScVbaRange::createEnumeration() throw (uno::RuntimeException)
{
- return new CellsEnumeration( m_xContext, mxRange );
+ return new CellsEnumeration( mxContext, m_Areas );
}
::rtl::OUString SAL_CALL
@@ -2883,7 +3145,7 @@ getDeviceFromDoc( const uno::Reference< frame::XModel >& xModel ) throw( uno::Ru
double
ScVbaRange::getCalcColWidth( const table::CellRangeAddress& rAddress) throw (uno::RuntimeException)
{
- ScDocument* pDoc = getDocumentFromRange( mxRange );
+ ScDocument* pDoc = getScDocument();
USHORT nWidth = pDoc->GetOriginalWidth( static_cast< SCCOL >( rAddress.StartColumn ), static_cast< SCTAB >( rAddress.Sheet ) );
double nPoints = lcl_TwipsToPoints( nWidth );
nPoints = lcl_Round2DecPlaces( nPoints );
@@ -2929,17 +3191,36 @@ double getDefaultCharWidth( const uno::Reference< frame::XModel >& xModel ) thro
uno::Any SAL_CALL
ScVbaRange::getColumnWidth() throw (uno::RuntimeException)
{
+ sal_Int32 nLen = m_Areas->getCount();
+ if ( nLen > 1 )
+ {
+ uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny( sal_Int32(1) ), uno::Any() ), uno::UNO_QUERY_THROW );
+ return xRange->getColumnWidth();
+ }
+
double nColWidth = 0;
- ScDocShell* pShell = getDocShellFromRange( mxRange );
+ ScDocShell* pShell = getScDocShell();
if ( pShell )
{
+ uno::Reference< frame::XModel > xModel = pShell->GetModel();
+ double defaultCharWidth = getDefaultCharWidth( xModel );
RangeHelper thisRange( mxRange );
table::CellRangeAddress thisAddress = thisRange.getCellRangeAddressable()->getRangeAddress();
- uno::Reference< table::XColumnRowRange > xColRowRange( mxRange, uno::UNO_QUERY_THROW );
- uno::Reference< beans::XPropertySet > xProps( xColRowRange->getColumns(), uno::UNO_QUERY_THROW );
- uno::Reference< frame::XModel > xModel = pShell->GetModel();
+ sal_Int32 nStartCol = thisAddress.StartColumn;
+ sal_Int32 nEndCol = thisAddress.EndColumn;
+ USHORT nColTwips = 0;
+ for( sal_Int32 nCol = nStartCol ; nCol <= nEndCol; ++nCol )
+ {
+ thisAddress.StartColumn = nCol;
+ USHORT nCurTwips = pShell->GetDocument()->GetOriginalWidth( static_cast< SCCOL >( thisAddress.StartColumn ), static_cast< SCTAB >( thisAddress.Sheet ) );
+ if ( nCol == nStartCol )
+ nColTwips = nCurTwips;
+ if ( nColTwips != nCurTwips )
+ return aNULL();
+ }
+ nColWidth = lcl_Round2DecPlaces( lcl_TwipsToPoints( nColTwips ) );
if ( xModel.is() )
- nColWidth = getCalcColWidth(thisAddress) / getDefaultCharWidth( xModel );
+ nColWidth = nColWidth / defaultCharWidth;
}
nColWidth = lcl_Round2DecPlaces( nColWidth );
return uno::makeAny( nColWidth );
@@ -2948,10 +3229,20 @@ ScVbaRange::getColumnWidth() throw (uno::RuntimeException)
void SAL_CALL
ScVbaRange::setColumnWidth( const uno::Any& _columnwidth ) throw (uno::RuntimeException)
{
+ sal_Int32 nLen = m_Areas->getCount();
+ if ( nLen > 1 )
+ {
+ for ( sal_Int32 index = 1; index != nLen; ++index )
+ {
+ uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny( sal_Int32(index) ), uno::Any() ), uno::UNO_QUERY_THROW );
+ xRange->setColumnWidth( _columnwidth );
+ }
+ return;
+ }
double nColWidth = 0;
_columnwidth >>= nColWidth;
nColWidth = lcl_Round2DecPlaces( nColWidth );
- ScDocShell* pDocShell = getDocShellFromRange( mxRange );
+ ScDocShell* pDocShell = getScDocShell();
if ( pDocShell )
{
uno::Reference< frame::XModel > xModel = pDocShell->GetModel();
@@ -2977,6 +3268,11 @@ ScVbaRange::setColumnWidth( const uno::Any& _columnwidth ) throw (uno::RuntimeEx
uno::Any SAL_CALL
ScVbaRange::getWidth() throw (uno::RuntimeException)
{
+ if ( m_Areas->getCount() > 1 )
+ {
+ uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny( sal_Int32(1) ), uno::Any() ), uno::UNO_QUERY_THROW );
+ return xRange->getWidth();
+ }
uno::Reference< table::XColumnRowRange > xColRowRange( mxRange, uno::UNO_QUERY_THROW );
uno::Reference< container::XIndexAccess > xIndexAccess( xColRowRange->getColumns(), uno::UNO_QUERY_THROW );
sal_Int32 nElems = xIndexAccess->getCount();
@@ -2995,7 +3291,7 @@ ScVbaRange::Areas( const uno::Any& item) throw (uno::RuntimeException)
{
if ( !item.hasValue() )
return uno::makeAny( m_Areas );
- return m_Areas->Item( item );
+ return m_Areas->Item( item, uno::Any() );
}
uno::Reference< excel::XRange >
@@ -3003,24 +3299,24 @@ ScVbaRange::getArea( sal_Int32 nIndex ) throw( css::uno::RuntimeException )
{
if ( !m_Areas.is() )
throw uno::RuntimeException( rtl::OUString(RTL_CONSTASCII_USTRINGPARAM("No areas available")), uno::Reference< uno::XInterface >() );
- uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny( ++nIndex ) ), uno::UNO_QUERY_THROW );
+ uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny( ++nIndex ), uno::Any() ), uno::UNO_QUERY_THROW );
return xRange;
}
uno::Any
-ScVbaRange::Borders( const uno::Any& item ) throw( css::uno::RuntimeException )
+ScVbaRange::Borders( const uno::Any& item ) throw( script::BasicErrorException, uno::RuntimeException )
{
if ( !item.hasValue() )
- return uno::makeAny( m_Borders );
- return m_Borders->Item( item );
+ return uno::makeAny( getBorders() );
+ return getBorders()->Item( item, uno::Any() );
}
uno::Any SAL_CALL
ScVbaRange::BorderAround( const css::uno::Any& LineStyle, const css::uno::Any& Weight,
const css::uno::Any& ColorIndex, const css::uno::Any& Color ) throw (css::uno::RuntimeException)
{
- sal_Int32 nCount = m_Borders->getCount();
- uno::Reference< excel::XBorders > xBorders( m_Borders, uno::UNO_QUERY_THROW);
+ sal_Int32 nCount = getBorders()->getCount();
+
for( sal_Int32 i = 0; i < nCount; i++ )
{
const sal_Int32 nLineType = supportedIndexTable[i];
@@ -3031,7 +3327,7 @@ ScVbaRange::BorderAround( const css::uno::Any& LineStyle, const css::uno::Any& W
case excel::XlBordersIndex::xlEdgeBottom:
case excel::XlBordersIndex::xlEdgeRight:
{
- uno::Reference< excel::XBorder > xBorder( m_Borders->Item( uno::makeAny( nLineType ) ), uno::UNO_QUERY_THROW );
+ uno::Reference< excel::XBorder > xBorder( m_Borders->Item( uno::makeAny( nLineType ), uno::Any() ), uno::UNO_QUERY_THROW );
if( LineStyle.hasValue() )
{
xBorder->setLineStyle( LineStyle );
@@ -3065,16 +3361,50 @@ ScVbaRange::BorderAround( const css::uno::Any& LineStyle, const css::uno::Any& W
uno::Any SAL_CALL
ScVbaRange::getRowHeight() throw (uno::RuntimeException)
{
+ sal_Int32 nLen = m_Areas->getCount();
+ if ( nLen > 1 )
+ {
+ uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny( sal_Int32(1) ), uno::Any() ), uno::UNO_QUERY_THROW );
+ return xRange->getRowHeight();
+ }
+
+ // if this range is a 'Rows' range, then if any row's RowHeight in the
+ // range is different from any other then return NULL
RangeHelper thisRange( mxRange );
table::CellRangeAddress thisAddress = thisRange.getCellRangeAddressable()->getRangeAddress();
+
+ sal_Int32 nStartRow = thisAddress.StartRow;
+ sal_Int32 nEndRow = thisAddress.EndRow;
double nHeight = getCalcRowHeight( thisAddress );
+ // #TODO probably possible to use the SfxItemSet ( and see if
+ // SFX_ITEM_DONTCARE is set ) to improve performance
+ if ( mbIsRows )
+ {
+ for ( sal_Int32 nRow = nStartRow ; nRow <= nEndRow; ++nRow )
+ {
+ thisAddress.StartRow = nRow;
+ double nCurHeight = getCalcRowHeight( thisAddress );
+ if ( nHeight != nCurHeight )
+ return aNULL();
+ }
+ }
return uno::makeAny( nHeight );
}
void SAL_CALL
ScVbaRange::setRowHeight( const uno::Any& _rowheight) throw (uno::RuntimeException)
{
- double nHeight = 0; // Incomming height is in points
+ sal_Int32 nLen = m_Areas->getCount();
+ if ( nLen > 1 )
+ {
+ for ( sal_Int32 index = 1; index != nLen; ++index )
+ {
+ uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny( sal_Int32(index) ), uno::Any() ), uno::UNO_QUERY_THROW );
+ xRange->setRowHeight( _rowheight );
+ }
+ return;
+ }
+ double nHeight = 0; // Incomming height is in points
_rowheight >>= nHeight;
nHeight = lcl_Round2DecPlaces( nHeight );
RangeHelper thisRange( mxRange );
@@ -3093,7 +3423,7 @@ ScVbaRange::setRowHeight( const uno::Any& _rowheight) throw (uno::RuntimeExcepti
uno::Any SAL_CALL
ScVbaRange::getPageBreak() throw (uno::RuntimeException)
{
- sal_Int32 nPageBreak = excel::XlPageBreak::XlPageBreakNone;
+ sal_Int32 nPageBreak = excel::XlPageBreak::xlPageBreakNone;
ScDocShell* pShell = getDocShellFromRange( mxRange );
if ( pShell )
{
@@ -3116,10 +3446,10 @@ ScVbaRange::getPageBreak() throw (uno::RuntimeException)
nFlag = pDoc -> GetColFlags(static_cast<SCCOL>(thisAddress.StartColumn), thisAddress.Sheet);
if ( nFlag & CR_PAGEBREAK)
- nPageBreak = excel::XlPageBreak::XlPageBreakAutomatic;
+ nPageBreak = excel::XlPageBreak::xlPageBreakAutomatic;
if ( nFlag & CR_MANUALBREAK)
- nPageBreak = excel::XlPageBreak::XlPageBreakManual;
+ nPageBreak = excel::XlPageBreak::xlPageBreakManual;
}
}
@@ -3149,9 +3479,9 @@ ScVbaRange::setPageBreak( const uno::Any& _pagebreak) throw (uno::RuntimeExcepti
if ( xModel.is() )
{
ScTabViewShell* pViewShell = getBestViewShell( xModel );
- if ( nPageBreak == excel::XlPageBreak::XlPageBreakManual )
+ if ( nPageBreak == excel::XlPageBreak::xlPageBreakManual )
pViewShell->InsertPageBreak( bColumn, TRUE, &aAddr);
- else if ( nPageBreak == excel::XlPageBreak::XlPageBreakNone )
+ else if ( nPageBreak == excel::XlPageBreak::xlPageBreakNone )
pViewShell->DeletePageBreak( bColumn, TRUE, &aAddr);
}
}
@@ -3160,6 +3490,12 @@ ScVbaRange::setPageBreak( const uno::Any& _pagebreak) throw (uno::RuntimeExcepti
uno::Any SAL_CALL
ScVbaRange::getHeight() throw (uno::RuntimeException)
{
+ if ( m_Areas->getCount() > 1 )
+ {
+ uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny( sal_Int32(1) ), uno::Any() ), uno::UNO_QUERY_THROW );
+ return xRange->getHeight();
+ }
+
uno::Reference< table::XColumnRowRange > xColRowRange( mxRange, uno::UNO_QUERY_THROW );
uno::Reference< container::XIndexAccess > xIndexAccess( xColRowRange->getRows(), uno::UNO_QUERY_THROW );
sal_Int32 nElems = xIndexAccess->getCount();
@@ -3172,12 +3508,60 @@ ScVbaRange::getHeight() throw (uno::RuntimeException)
return uno::makeAny( nHeight );
}
+awt::Point
+ScVbaRange::getPosition() throw ( uno::RuntimeException )
+{
+ awt::Point aPoint;
+ uno::Reference< beans::XPropertySet > xProps;
+ if ( mxRange.is() )
+ xProps.set( mxRange, uno::UNO_QUERY_THROW );
+ else
+ xProps.set( mxRanges, uno::UNO_QUERY_THROW );
+ xProps->getPropertyValue(POSITION) >>= aPoint;
+ return aPoint;
+}
+uno::Any SAL_CALL
+ScVbaRange::getLeft() throw (uno::RuntimeException)
+{
+ // helperapi returns the first ranges left ( and top below )
+ if ( m_Areas->getCount() > 1 )
+ return getArea( 0 )->getLeft();
+ awt::Point aPoint = getPosition();
+ return uno::makeAny( lcl_hmmToPoints( aPoint.X ) );
+}
+
+
+uno::Any SAL_CALL
+ScVbaRange::getTop() throw (uno::RuntimeException)
+{
+ // helperapi returns the first ranges top
+ if ( m_Areas->getCount() > 1 )
+ return getArea( 0 )->getTop();
+ awt::Point aPoint= getPosition();
+ return uno::makeAny( lcl_hmmToPoints( aPoint.Y ) );
+}
+
uno::Reference< excel::XWorksheet >
ScVbaRange::getWorksheet() throw (uno::RuntimeException)
{
- ScDocShell* pDocShell = getDocShellFromRange(mxRange);
- RangeHelper* rHelper = new RangeHelper(mxRange);
- return new ScVbaWorksheet(m_xContext,rHelper->getSpreadSheet(),pDocShell->GetModel());
+ // #TODO #FIXME parent should always be set up ( currently thats not
+ // the case )
+ uno::Reference< excel::XWorksheet > xSheet( getParent(), uno::UNO_QUERY );
+ if ( !xSheet.is() )
+ {
+ uno::Reference< table::XCellRange > xRange = mxRange;
+
+ if ( mxRanges.is() ) // assign xRange to first range
+ {
+ uno::Reference< container::XIndexAccess > xIndex( mxRanges, uno::UNO_QUERY_THROW );
+ xRange.set( xIndex->getByIndex( 0 ), uno::UNO_QUERY_THROW );
+ }
+ ScDocShell* pDocShell = getDocShellFromRange(xRange);
+ RangeHelper rHelper(xRange);
+ // parent should be Thisworkbook
+ xSheet.set( new ScVbaWorksheet( uno::Reference< vba::XHelperInterface >(), mxContext,rHelper.getSpreadSheet(),pDocShell->GetModel()) );
+ }
+ return xSheet;
}
ScCellRangesBase*
@@ -3241,59 +3625,298 @@ ScVbaRange::ApplicationRange( const uno::Reference< uno::XComponentContext >& xC
uno::Reference< table::XCellRange > xRange = xReferrer->getReferredCells();
if ( xRange.is() )
{
- uno::Reference< excel::XRange > xVbRange = new ScVbaRange( xContext, xRange );
+ // #FIXME need proper (WorkSheet) parent
+ uno::Reference< excel::XRange > xVbRange = new ScVbaRange( uno::Reference< vba::XHelperInterface >(), xContext, xRange );
return xVbRange;
}
}
}
uno::Reference< sheet::XSpreadsheetView > xView( getCurrentDocument()->getCurrentController(), uno::UNO_QUERY );
uno::Reference< table::XCellRange > xSheetRange( xView->getActiveSheet(), uno::UNO_QUERY_THROW );
- ScVbaRange* pRange = new ScVbaRange( xContext, xSheetRange );
+ ScVbaRange* pRange = new ScVbaRange( uno::Reference< vba::XHelperInterface >(), xContext, xSheetRange );
uno::Reference< excel::XRange > xVbSheetRange( pRange );
return pRange->Range( Cell1, Cell2, true );
}
+uno::Reference< sheet::XDatabaseRanges >
+lcl_GetDataBaseRanges( ScDocShell* pShell ) throw ( uno::RuntimeException )
+{
+ uno::Reference< frame::XModel > xModel;
+ if ( pShell )
+ xModel.set( pShell->GetModel(), uno::UNO_QUERY_THROW );
+ uno::Reference< beans::XPropertySet > xModelProps( xModel, uno::UNO_QUERY_THROW );
+ uno::Reference< sheet::XDatabaseRanges > xDBRanges( xModelProps->getPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("DatabaseRanges") ) ), uno::UNO_QUERY_THROW );
+ return xDBRanges;
+}
+// returns the XDatabaseRange for the autofilter on sheet (nSheet)
+// also populates sName with the name of range
+uno::Reference< sheet::XDatabaseRange >
+lcl_GetAutoFiltRange( ScDocShell* pShell, sal_Int16 nSheet, rtl::OUString& sName )
+{
+ uno::Reference< container::XIndexAccess > xIndexAccess( lcl_GetDataBaseRanges( pShell ), uno::UNO_QUERY_THROW );
+ uno::Reference< sheet::XDatabaseRange > xDataBaseRange;
+ table::CellRangeAddress dbAddress;
+ for ( sal_Int32 index=0; index < xIndexAccess->getCount(); ++index )
+ {
+ uno::Reference< sheet::XDatabaseRange > xDBRange( xIndexAccess->getByIndex( index ), uno::UNO_QUERY_THROW );
+ uno::Reference< container::XNamed > xNamed( xDBRange, uno::UNO_QUERY_THROW );
+ // autofilters work weirdly with openoffice, unnamed is the default
+ // named range which is used to create an autofilter, but
+ // its also possible that another name could be used
+ // this also causes problems when an autofilter is created on
+ // another sheet
+ // ( but.. you can use any named range )
+ dbAddress = xDBRange->getDataArea();
+ if ( dbAddress.Sheet == nSheet )
+ {
+ sal_Bool bHasAuto = sal_False;
+ uno::Reference< beans::XPropertySet > xProps( xDBRange, uno::UNO_QUERY_THROW );
+ xProps->getPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("AutoFilter") ) ) >>= bHasAuto;
+ if ( bHasAuto )
+ {
+ sName = xNamed->getName();
+ xDataBaseRange=xDBRange;
+ break;
+ }
+ }
+ }
+ return xDataBaseRange;
+}
-void SAL_CALL
-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)
+// Helper functions for AutoFilter
+ScDBData* lcl_GetDBData_Impl( ScDocShell* pDocShell, sal_Int16 nSheet )
{
- // #TODO We could probably hook into the autofilter stuff better
- // or at least seperate the code in dbfunc so it could be shared
- // currently a cut'n'paste fest exists below :-(
+ rtl::OUString sName;
+ lcl_GetAutoFiltRange( pDocShell, nSheet, sName );
+ OSL_TRACE("lcl_GetDBData_Impl got autofilter range %s for sheet %d",
+ rtl::OUStringToOString( sName, RTL_TEXTENCODING_UTF8 ).getStr() , nSheet );
+ ScDBData* pRet = NULL;
+ if (pDocShell)
+ {
+ ScDBCollection* pNames = pDocShell->GetDocument()->GetDBCollection();
+ if (pNames)
+ {
+ USHORT nPos = 0;
+ if (pNames->SearchName( sName , nPos ))
+ pRet = (*pNames)[nPos];
+ }
+ }
+ return pRet;
+}
- ScDocument* pDoc = getDocumentFromRange( mxRange );
- ScDocShell* pDocSh = getDocShellFromRange( mxRange );
- ScDocShellModificator aModificator( *pDocSh );
- sal_Bool bHasAuto = sal_True;
- RangeHelper thisRange( mxRange );
- table::CellRangeAddress thisAddress = thisRange.getCellRangeAddressable()->getRangeAddress();
+void lcl_SelectAll( ScDocShell* pDocShell, ScQueryParam& aParam )
+{
+ if ( pDocShell )
+ {
+ ScViewData* pViewData = pDocShell->GetViewData();
+ if ( pViewData )
+ {
+ OSL_TRACE("Pushing out SelectAll query");
+ pViewData->GetView()->Query( aParam, NULL, TRUE );
+ }
+ }
+}
- ScRange aRange;
- ScUnoConversion::FillScRange( aRange, thisAddress );
- ScDBData* pDBData = pDocSh->GetDBData( aRange, SC_DB_MAKE, TRUE );
- ScQueryParam aParam;
- pDBData->GetQueryParam( aParam );
- SCROW nRow = aParam.nRow1;
- SCTAB nTab = aRange.aStart.Tab();
- INT16 nFlag;
+ScQueryParam lcl_GetQueryParam( ScDocShell* pDocShell, sal_Int16 nSheet )
+{
+ ScDBData* pDBData = lcl_GetDBData_Impl( pDocShell, nSheet );
+ ScQueryParam aParam;
+ if (pDBData)
+ {
+ pDBData->GetQueryParam( aParam );
+ }
+ return aParam;
+}
- for (SCCOL nCol=aParam.nCol1; nCol<=aParam.nCol2 && ( bHasAuto == sal_True ); nCol++)
+void lcl_SetAllQueryForField( ScQueryParam& aParam, SCCOLROW nField )
+{
+ bool bFound = false;
+ SCSIZE i = 0;
+ for (; i<MAXQUERY && !bFound; i++)
{
- nFlag = ((ScMergeFlagAttr*) pDoc->GetAttr( nCol, nRow, nTab, ATTR_MERGE_FLAG ))->GetValue();
+ ScQueryEntry& rEntry = aParam.GetEntry(i);
+ if ( rEntry.nField == nField)
+ {
+ OSL_TRACE("found at pos %d", i );
+ bFound = true;
+ }
+ }
+ if ( bFound )
+ {
+ OSL_TRACE("field %d to delete at pos %d", nField, ( i - 1 ) );
+ aParam.DeleteQuery(--i);
+ }
+}
+
+
+void lcl_SetAllQueryForField( ScDocShell* pDocShell, SCCOLROW nField, sal_Int16 nSheet )
+{
+ ScQueryParam aParam = lcl_GetQueryParam( pDocShell, nSheet );
+ lcl_SetAllQueryForField( aParam, nField );
+ lcl_SelectAll( pDocShell, aParam );
+}
+
+// Modifies sCriteria, and nOp depending on the value of sCriteria
+void lcl_setTableFieldsFromCriteria( rtl::OUString& sCriteria1, uno::Reference< beans::XPropertySet >& xDescProps, sheet::TableFilterField& rFilterField )
+{
+ // #TODO make this more efficient and cycle through
+ // sCriteria1 character by character to pick up <,<>,=, * etc.
+ // right now I am more concerned with just getting it to work right
+
+ sCriteria1 = sCriteria1.trim();
+ // table of translation of criteria text to FilterOperators
+ // <>searchtext - NOT_EQUAL
+ // =searchtext - EQUAL
+ // *searchtext - startwith
+ // <>*searchtext - doesn't startwith
+ // *searchtext* - contains
+ // <>*searchtext* - doesn't contain
+ // [>|>=|<=|...]searchtext for GREATER_value, GREATER_EQUAL_value etc.
+ sal_Int32 nPos = 0;
+ bool bIsNumeric = false;
+ if ( ( nPos = sCriteria1.indexOf( EQUALS ) ) == 0 )
+ {
+ if ( sCriteria1.getLength() == EQUALS.getLength() )
+ rFilterField.Operator = sheet::FilterOperator_EMPTY;
+ else
+ {
+ rFilterField.Operator = sheet::FilterOperator_EQUAL;
+ sCriteria1 = sCriteria1.copy( EQUALS.getLength() );
+ sCriteria1 = VBAToRegexp( sCriteria1 );
+ // UseRegularExpressions
+ if ( xDescProps.is() )
+ xDescProps->setPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "UseRegularExpressions" ) ), uno::Any( sal_True ) );
+ }
- if ( (nFlag & SC_MF_AUTO) == 0 )
- bHasAuto = sal_False;
+ }
+ else if ( ( nPos = sCriteria1.indexOf( NOTEQUALS ) ) == 0 )
+ {
+ if ( sCriteria1.getLength() == NOTEQUALS.getLength() )
+ rFilterField.Operator = sheet::FilterOperator_NOT_EMPTY;
+ else
+ {
+ rFilterField.Operator = sheet::FilterOperator_NOT_EQUAL;
+ sCriteria1 = sCriteria1.copy( NOTEQUALS.getLength() );
+ sCriteria1 = VBAToRegexp( sCriteria1 );
+ // UseRegularExpressions
+ if ( xDescProps.is() )
+ xDescProps->setPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "UseRegularExpressions" ) ), uno::Any( sal_True ) );
+ }
}
+ else if ( ( nPos = sCriteria1.indexOf( GREATERTHAN ) ) == 0 )
+ {
+ bIsNumeric = true;
+ if ( ( nPos = sCriteria1.indexOf( GREATERTHANEQUALS ) ) == 0 )
+ {
+ sCriteria1 = sCriteria1.copy( GREATERTHANEQUALS.getLength() );
+ rFilterField.Operator = sheet::FilterOperator_GREATER_EQUAL;
+ }
+ else
+ {
+ sCriteria1 = sCriteria1.copy( GREATERTHAN.getLength() );
+ rFilterField.Operator = sheet::FilterOperator_GREATER;
+ }
- OSL_TRACE("Auto is set ? %s", bHasAuto ? "true" : "false" );
+ }
+ else if ( ( nPos = sCriteria1.indexOf( LESSTHAN ) ) == 0 )
+ {
+ bIsNumeric = true;
+ if ( ( nPos = sCriteria1.indexOf( LESSTHANEQUALS ) ) == 0 )
+ {
+ sCriteria1 = sCriteria1.copy( LESSTHANEQUALS.getLength() );
+ rFilterField.Operator = sheet::FilterOperator_LESS_EQUAL;
+ }
+ else
+ {
+ sCriteria1 = sCriteria1.copy( LESSTHAN.getLength() );
+ rFilterField.Operator = sheet::FilterOperator_LESS;
+ }
- // for the moment we only process first Criteria1
+ }
+ else
+ rFilterField.Operator = sheet::FilterOperator_EQUAL;
+
+ if ( bIsNumeric )
+ {
+ rFilterField.IsNumeric= sal_True;
+ rFilterField.NumericValue = sCriteria1.toDouble();
+ }
+ rFilterField.StringValue = sCriteria1;
+}
+
+void SAL_CALL
+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)
+{
+ // Is there an existing autofilter
+ RangeHelper thisRange( mxRange );
+ table::CellRangeAddress thisAddress = thisRange.getCellRangeAddressable()->getRangeAddress();
+ sal_Int16 nSheet = thisAddress.Sheet;
+ ScDocShell* pShell = getScDocShell();
+ sal_Bool bHasAuto = sal_False;
+ rtl::OUString sAutofiltRangeName;
+ uno::Reference< sheet::XDatabaseRange > xDataBaseRange = lcl_GetAutoFiltRange( pShell, nSheet, sAutofiltRangeName );
+ if ( xDataBaseRange.is() )
+ bHasAuto = true;
+
+ uno::Reference< table::XCellRange > xFilterRange;
+ if ( !bHasAuto )
+ {
+ if ( m_Areas->getCount() > 1 )
+ throw uno::RuntimeException( STR_ERRORMESSAGE_APPLIESTOSINGLERANGEONLY, uno::Reference< uno::XInterface >() );
+
+ table::CellRangeAddress autoFiltAddress;
+ //CurrentRegion()
+ if ( isSingleCellRange() )
+ {
+ uno::Reference< excel::XRange > xCurrent( CurrentRegion() );
+ if ( xCurrent.is() )
+ {
+ ScVbaRange* pRange = dynamic_cast< ScVbaRange* >( xCurrent.get() );
+ if ( pRange->isSingleCellRange() )
+ throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("Can't create AutoFilter") ), uno::Reference< uno::XInterface >() );
+ if ( pRange )
+ {
+ RangeHelper currentRegion( pRange->mxRange );
+ autoFiltAddress = currentRegion.getCellRangeAddressable()->getRangeAddress();
+ }
+ }
+ }
+ else // multi-cell range
+ {
+ RangeHelper multiCellRange( mxRange );
+ autoFiltAddress = multiCellRange.getCellRangeAddressable()->getRangeAddress();
+ }
+
+ uno::Reference< sheet::XDatabaseRanges > xDBRanges = lcl_GetDataBaseRanges( pShell );
+ if ( xDBRanges.is() )
+ {
+ rtl::OUString sGenName( RTL_CONSTASCII_USTRINGPARAM("VBA_Autofilter_") );
+ sGenName += rtl::OUString::valueOf( static_cast< sal_Int32 >( nSheet ) );
+ OSL_TRACE("Going to add new autofilter range.. name %s",
+ rtl::OUStringToOString( sGenName, RTL_TEXTENCODING_UTF8 ).getStr() , nSheet );
+ if ( !xDBRanges->hasByName( sGenName ) )
+ xDBRanges->addNewByName( sGenName, autoFiltAddress );
+ xDataBaseRange.set( xDBRanges->getByName( sGenName ), uno::UNO_QUERY_THROW );
+ }
+ if ( !xDataBaseRange.is() )
+ throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("Failed to find the autofilter placeholder range" ) ), uno::Reference< uno::XInterface >() );
+
+ uno::Reference< beans::XPropertySet > xDBRangeProps( xDataBaseRange, uno::UNO_QUERY_THROW );
+ // set autofilt
+ xDBRangeProps->setPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("AutoFilter") ), uno::Any(sal_True) );
+ // set header
+ uno::Reference< beans::XPropertySet > xFiltProps( xDataBaseRange->getFilterDescriptor(), uno::UNO_QUERY_THROW );
+ sal_Bool bHasColHeader = sal_False;
+ ScDocument* pDoc = pShell ? pShell->GetDocument() : NULL;
- sal_Int32 nField = 0; // *IS* 1 based
- rtl::OUString sCriteria1;
- sal_Int32 nOperator = excel::XlAutoFilterOperator::xlAnd;
+ bHasColHeader = pDoc->HasColHeader( static_cast< SCCOL >( autoFiltAddress.StartColumn ), static_cast< SCROW >( autoFiltAddress.StartRow ), static_cast< SCCOL >( autoFiltAddress.EndColumn ), static_cast< SCROW >( autoFiltAddress.EndRow ), static_cast< SCTAB >( autoFiltAddress.Sheet ) ) ? sal_True : sal_False;
+ xFiltProps->setPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ContainsHeader") ), uno::Any( bHasColHeader ) );
+ }
+ sal_Int32 nField = 0; // *IS* 1 based
+ rtl::OUString sCriteria1;
+ sal_Int32 nOperator = excel::XlAutoFilterOperator::xlAnd;
sal_Bool bVisible = sal_True;
bool bChangeDropDown = false;
@@ -3304,117 +3927,149 @@ ScVbaRange::AutoFilter( const uno::Any& Field, const uno::Any& Criteria1, const
bVisible = sal_False;
else
bChangeDropDown = true;
-
- sheet::FilterOperator nOp = sheet::FilterOperator_EQUAL;
sheet::FilterConnection nConn = sheet::FilterConnection_AND;
double nCriteria1 = 0;
bool bHasCritValue = Criteria1.hasValue();
- bool bCritHasNumericValue = sal_False;
+ bool bCritHasNumericValue = sal_False; // not sure if a numeric criteria is possible
if ( bHasCritValue )
bCritHasNumericValue = ( Criteria1 >>= nCriteria1 );
- if ( ( Field >>= nField )
- || Criteria1.hasValue()
- || ( Operator >>= nOperator )
- || VisibleDropDown.hasValue()
- )
- {
- Criteria1 >>= sCriteria1;
- uno::Reference< sheet::XSheetFilterable > xFilt( mxRange, uno::UNO_QUERY_THROW );
- uno::Reference< sheet::XSheetFilterDescriptor > xDesc = xFilt->createFilterDescriptor( sal_True );
- uno::Sequence< sheet::TableFilterField > sTabFilts = xDesc->getFilterFields();
- sTabFilts.realloc( 1 );
- sTabFilts[0].IsNumeric = bCritHasNumericValue;
- OSL_TRACE("No filt fields is %d", sTabFilts.getLength() );
-
- if ( bHasCritValue && sCriteria1.getLength() )
- {
- if ( sCriteria1.equals( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("=") ) ) )
- nOp = sheet::FilterOperator_EMPTY;
- else if ( sCriteria1.equals( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("<>") ) ) )
- nOp = sheet::FilterOperator_NOT_EMPTY;
- else
- nOp = sheet::FilterOperator_EQUAL;
+ if ( !Field.hasValue() && ( Criteria1.hasValue() || Operator.hasValue() || Criteria2.hasValue() ) )
+ throw uno::RuntimeException();
+ // Use the normal uno api, sometimes e.g. when you want to use ALL as the filter
+ // we can't use refresh as the uno interface doesn't have a concept of ALL
+ // in this case we just call the core calc functionality -
+ bool bAll = false;;
+ if ( ( Field >>= nField ) )
+ {
+ uno::Sequence< sheet::TableFilterField > sTabFilts;
+ uno::Reference< sheet::XSheetFilterDescriptor > xDesc = xDataBaseRange->getFilterDescriptor();
+ uno::Reference< beans::XPropertySet > xDescProps( xDesc, uno::UNO_QUERY_THROW );
+ if ( Criteria1.hasValue() )
+ {
+ sTabFilts.realloc( 1 );
+ sTabFilts[0].Operator = sheet::FilterOperator_EQUAL;// sensible default
+ if ( !bCritHasNumericValue )
+ {
+ Criteria1 >>= sCriteria1;
+ sTabFilts[0].IsNumeric = bCritHasNumericValue;
+ if ( bHasCritValue && sCriteria1.getLength() )
+ lcl_setTableFieldsFromCriteria( sCriteria1, xDescProps, sTabFilts[0] );
+ else
+ bAll = true;
+ }
+ else // numeric
+ {
+ sTabFilts[0].IsNumeric = sal_True;
+ sTabFilts[0].NumericValue = nCriteria1;
+ }
}
-
- if ( Operator.hasValue() )
+ else // no value specified
+ bAll = true;
+ // not sure what the relationship between Criteria1 and Operator is,
+ // e.g. can you have a Operator without a Criteria ? in openoffice it
+ if ( Operator.hasValue() && ( Operator >>= nOperator ) )
{
// if its a bottom/top Ten(Percent/Value) and there
// is no value specified for critera1 set it to 10
if ( !bCritHasNumericValue && !sCriteria1.getLength() && ( nOperator != excel::XlAutoFilterOperator::xlOr ) && ( nOperator != excel::XlAutoFilterOperator::xlAnd ) )
{
- nCriteria1 = 10;
sTabFilts[0].IsNumeric = sal_True;
+ sTabFilts[0].NumericValue = 10;
+ bAll = false;
}
switch ( nOperator )
{
case excel::XlAutoFilterOperator::xlBottom10Items:
- nOp = sheet::FilterOperator_BOTTOM_VALUES;
+ sTabFilts[0].Operator = sheet::FilterOperator_BOTTOM_VALUES;
break;
case excel::XlAutoFilterOperator::xlBottom10Percent:
- nOp = sheet::FilterOperator_BOTTOM_PERCENT;
+ sTabFilts[0].Operator = sheet::FilterOperator_BOTTOM_PERCENT;
break;
case excel::XlAutoFilterOperator::xlTop10Items:
- nOp = sheet::FilterOperator_TOP_VALUES;
+ sTabFilts[0].Operator = sheet::FilterOperator_TOP_VALUES;
break;
case excel::XlAutoFilterOperator::xlTop10Percent:
- nOp = sheet::FilterOperator_TOP_PERCENT;
+ sTabFilts[0].Operator = sheet::FilterOperator_TOP_PERCENT;
break;
case excel::XlAutoFilterOperator::xlOr:
- nConn = sheet::FilterConnection_OR;
+ nConn = sheet::FilterConnection_OR;
+ break;
case excel::XlAutoFilterOperator::xlAnd:
- nConn = sheet::FilterConnection_AND;
+ nConn = sheet::FilterConnection_AND;
+ break;
default:
throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("UnknownOption") ), uno::Reference< uno::XInterface >() );
}
}
- sTabFilts[0].Connection = nConn;
- if ( nField > 0 )
+ if ( !bAll )
+ {
+ sTabFilts[0].Connection = sheet::FilterConnection_AND;
sTabFilts[0].Field = (nField - 1);
- else
- sTabFilts[0].Field = 0;
- sTabFilts[0].Operator = nOp;
- if( sTabFilts[0].IsNumeric )
- sTabFilts[0].NumericValue = nCriteria1;
- else
- sTabFilts[0].StringValue = sCriteria1;
+
+ rtl::OUString sCriteria2;
+ if ( Criteria2.hasValue() ) // there is a Criteria2
+ {
+ sTabFilts.realloc(2);
+ sTabFilts[1].Field = sTabFilts[0].Field;
+ sTabFilts[1].Connection = nConn;
+
+ if ( Criteria2 >>= sCriteria2 )
+ {
+ if ( sCriteria2.getLength() > 0 )
+ {
+ uno::Reference< beans::XPropertySet > xProps;
+ lcl_setTableFieldsFromCriteria( sCriteria2, xProps, sTabFilts[1] );
+ sTabFilts[1].IsNumeric = sal_False;
+ }
+ }
+ else // numeric
+ {
+ Criteria2 >>= sTabFilts[1].NumericValue;
+ sTabFilts[1].IsNumeric = sal_True;
+ sTabFilts[1].Operator = sheet::FilterOperator_EQUAL;
+ }
+ }
+ }
xDesc->setFilterFields( sTabFilts );
- uno::Reference< beans::XPropertySet > xProps( xDesc, uno::UNO_QUERY_THROW );
- xProps->setPropertyValue( CONTS_HEADER, uno::makeAny( sal_True ) );
- xFilt->filter( xDesc );
-
+ if ( !bAll )
+ {
+ xDataBaseRange->refresh();
+ }
+ else
+ // was 0 based now seems to be 1
+ lcl_SetAllQueryForField( pShell, nField, nSheet );
}
else
- bChangeDropDown = true;
- // enable drop down
- if ( bChangeDropDown )
{
- ScRange aTmpRange;
- pDBData->GetArea( aTmpRange );
- for (SCCOL nCol=aParam.nCol1; nCol<=aParam.nCol2; nCol++)
- {
- nFlag = ((ScMergeFlagAttr*) pDoc->GetAttr( nCol, nRow, nTab, ATTR_MERGE_FLAG ))->GetValue();
- if ( bVisible )
- pDoc->ApplyAttr( nCol, nRow, nTab, ScMergeFlagAttr( nFlag | SC_MF_AUTO ) );
- else
- pDoc->ApplyAttr( nCol, nRow, nTab, ScMergeFlagAttr( nFlag &~ SC_MF_AUTO ) );
- }
- if ( !bVisible )
+ // this is just to toggle autofilter on and off ( not to be confused with
+ // a VisibleDropDown option combined with a field, in that case just the
+ // button should be disabled ) - currently we don't support that
+ bChangeDropDown = true;
+ uno::Reference< beans::XPropertySet > xDBRangeProps( xDataBaseRange, uno::UNO_QUERY_THROW );
+ if ( bHasAuto )
{
- SCSIZE nEC = aParam.GetEntryCount();
- for (SCSIZE i=0; i<nEC; i++)
- aParam.GetEntry(i).bDoQuery = FALSE;
- aParam.bDuplicate = TRUE;
- ScDBDocFunc aDBDocFunc( *pDocSh );
- aDBDocFunc.Query( nTab, aParam, &aTmpRange, TRUE, FALSE );
+ // find the any field with the query and select all
+ ScQueryParam aParam = lcl_GetQueryParam( pShell, nSheet );
+ SCSIZE i = 0;
+ for (; i<MAXQUERY; i++)
+ {
+ ScQueryEntry& rEntry = aParam.GetEntry(i);
+ if ( rEntry.bDoQuery )
+ lcl_SetAllQueryForField( pShell, rEntry.nField, nSheet );
+ }
+ // remove exising filters
+ xDataBaseRange->getFilterDescriptor()->setFilterFields( uno::Sequence< sheet::TableFilterField >() );
}
- pDocSh->PostPaint( aParam.nCol1, nRow, nTab, aParam.nCol2, nRow, nTab, PAINT_GRID );
- }
+ xDBRangeProps->setPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("AutoFilter") ), uno::Any(!bHasAuto) );
+
+ }
}
+
void SAL_CALL
ScVbaRange::Insert( const uno::Any& Shift, const uno::Any& /*CopyOrigin*/ ) throw (uno::RuntimeException)
{
@@ -3456,6 +4111,21 @@ ScVbaRange::Insert( const uno::Any& Shift, const uno::Any& /*CopyOrigin*/ ) thro
void SAL_CALL
ScVbaRange::Autofit() throw (uno::RuntimeException)
{
+ sal_Int32 nLen = m_Areas->getCount();
+ if ( nLen > 1 )
+ {
+ for ( sal_Int32 index = 1; index != nLen; ++index )
+ {
+ uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny( sal_Int32(index) ), uno::Any() ), uno::UNO_QUERY_THROW );
+ xRange->Autofit();
+ }
+ return;
+ }
+ // if the range is a not a row or column range autofit will
+ // throw an error
+
+ if ( !mbIsColumns )
+ DebugHelper::exception(SbERR_METHOD_FAILED, rtl::OUString());
ScDocShell* pDocShell = getDocShellFromRange( mxRange );
if ( pDocShell )
{
@@ -3466,7 +4136,14 @@ ScVbaRange::Autofit() throw (uno::RuntimeException)
SCCOLROW nColArr[2];
nColArr[0] = thisAddress.StartColumn;
nColArr[1] = thisAddress.EndColumn;
- aFunc.SetWidthOrHeight( TRUE, 1, nColArr, thisAddress.Sheet, SC_SIZE_OPTIMAL,
+ BOOL bDirection = TRUE;
+ if ( mbIsRows )
+ {
+ bDirection = FALSE;
+ nColArr[0] = thisAddress.StartRow;
+ nColArr[1] = thisAddress.EndRow;
+ }
+ aFunc.SetWidthOrHeight( bDirection, 1, nColArr, thisAddress.Sheet, SC_SIZE_OPTIMAL,
0, TRUE, TRUE );
}
@@ -3485,7 +4162,6 @@ ScVbaRange::TextToColumns( const css::uno::Any& Destination, const css::uno::Any
const css::uno::Any& Space, const css::uno::Any& Other, const css::uno::Any& OtherChar, const css::uno::Any& /*FieldInfo*/,
const css::uno::Any& DecimalSeparator, const css::uno::Any& ThousandsSeparator, const css::uno::Any& /*TrailingMinusNumbers*/ ) throw (css::uno::RuntimeException)
{
- OSL_TRACE("nJust for test\n");
uno::Reference< excel::XRange > xRange;
if( Destination.hasValue() )
{
@@ -3603,10 +4279,31 @@ css::uno::Reference< excel::XValidation > SAL_CALL
ScVbaRange::getValidation() throw (css::uno::RuntimeException)
{
if ( !m_xValidation.is() )
- m_xValidation = new ScVbaValidation( m_xContext, mxRange );
+ m_xValidation = new ScVbaValidation( this, mxContext, mxRange );
return m_xValidation;
}
+uno::Any ScVbaRange::getFormulaHidden() throw ( script::BasicErrorException, css::uno::RuntimeException)
+{
+ SfxItemSet* pDataSet = getCurrentDataSet();
+ const ScProtectionAttr& rProtAttr = (const ScProtectionAttr &)
+ pDataSet->Get(ATTR_PROTECTION, TRUE);
+ SfxItemState eState = pDataSet->GetItemState(ATTR_PROTECTION, TRUE, NULL);
+ if(eState == SFX_ITEM_DONTCARE)
+ return aNULL();
+ return uno::makeAny(rProtAttr.GetHideFormula());
+
+}
+void ScVbaRange::setFormulaHidden(const uno::Any& Hidden) throw ( script::BasicErrorException, css::uno::RuntimeException)
+{
+ uno::Reference< beans::XPropertySet > xProps(mxRange, ::uno::UNO_QUERY_THROW);
+ util::CellProtection rCellAttr;
+ xProps->getPropertyValue(rtl::OUString(RTL_CONSTASCII_USTRINGPARAM(SC_UNONAME_CELLPRO))) >>= rCellAttr;
+ Hidden >>= rCellAttr.IsFormulaHidden;
+ xProps->setPropertyValue(rtl::OUString( RTL_CONSTASCII_USTRINGPARAM(SC_UNONAME_CELLPRO)), uno::makeAny(rCellAttr));
+}
+
+
void SAL_CALL
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)
{
@@ -3617,7 +4314,7 @@ ScVbaRange::PrintOut( const uno::Any& From, const uno::Any& To, const uno::Any&
uno::Reference< sheet::XPrintAreas > xPrintAreas;
for ( sal_Int32 index=1; index <= nItems; ++index )
{
- uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny(index) ), uno::UNO_QUERY_THROW );
+ uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny(index), uno::Any() ), uno::UNO_QUERY_THROW );
RangeHelper thisRange( xRange->getCellRange() );
table::CellRangeAddress rangeAddress = thisRange.getCellRangeAddressable()->getRangeAddress();
@@ -3716,7 +4413,9 @@ ScVbaRange::AutoFill( const uno::Reference< excel::XRange >& Destination, const
FillCmd eCmd = FILL_AUTO;
FillDateCmd eDateCmd = FILL_DAY;
- //double fEndValue = MAXDOUBLE;
+#ifdef VBA_OOBUILD_HACK
+ double fEndValue = MAXDOUBLE;
+#endif
if ( Type.hasValue() )
{
@@ -3761,8 +4460,553 @@ ScVbaRange::AutoFill( const uno::Reference< excel::XRange >& Destination, const
}
}
ScDocFunc aFunc(*pDocSh);
- // FOR_UPSTREAM_BUILD
- /*aFunc.FillAuto( aSourceRange, NULL, eDir, eCmd, eDateCmd,
- nCount, fStep, fEndValue, TRUE, TRUE );
- */
+#ifdef VBA_OOBUILD_HACK
+ aFunc.FillAuto( aSourceRange, NULL, eDir, eCmd, eDateCmd, nCount, fStep, fEndValue, TRUE, TRUE );
+#endif
+}
+sal_Bool SAL_CALL
+ScVbaRange::GoalSeek( const uno::Any& Goal, const uno::Reference< excel::XRange >& ChangingCell ) throw (uno::RuntimeException)
+{
+ ScDocShell* pDocShell = getScDocShell();
+ sal_Bool bRes = sal_True;
+ ScVbaRange* pRange = static_cast< ScVbaRange* >( ChangingCell.get() );
+ if ( pDocShell && pRange )
+ {
+ uno::Reference< sheet::XGoalSeek > xGoalSeek( pDocShell->GetModel(), uno::UNO_QUERY_THROW );
+ RangeHelper thisRange( mxRange );
+ table::CellRangeAddress thisAddress = thisRange.getCellRangeAddressable()->getRangeAddress();
+ RangeHelper changingCellRange( pRange->mxRange );
+ table::CellRangeAddress changingCellAddr = changingCellRange.getCellRangeAddressable()->getRangeAddress();
+ rtl::OUString sGoal = getAnyAsString( Goal );
+ table::CellAddress thisCell( thisAddress.Sheet, thisAddress.StartColumn, thisAddress.StartRow );
+ table::CellAddress changingCell( changingCellAddr.Sheet, changingCellAddr.StartColumn, changingCellAddr.StartRow );
+ sheet::GoalResult res = xGoalSeek->seekGoal( thisCell, changingCell, sGoal );
+ ChangingCell->setValue( uno::makeAny( res.Result ) );
+
+ // openoffice behaves differently, result is 0 if the divergence is too great
+ // but... if it detects 0 is the value it requires then it will use that
+ // e.g. divergence & result both = 0.0 does NOT mean there is an error
+ if ( ( res.Divergence != 0.0 ) && ( res.Result == 0.0 ) )
+ bRes = sal_False;
+ }
+ else
+ bRes = sal_False;
+ return bRes;
+}
+
+void
+ScVbaRange::Calculate( ) throw (script::BasicErrorException, uno::RuntimeException)
+{
+ getWorksheet()->Calculate();
+}
+
+uno::Reference< excel::XRange > SAL_CALL
+ScVbaRange::Item( const uno::Any& row, const uno::Any& column ) throw (script::BasicErrorException, uno::RuntimeException)
+{
+ if ( mbIsRows || mbIsColumns )
+ {
+ if ( column.hasValue() )
+ DebugHelper::exception(SbERR_BAD_PARAMETER, rtl::OUString() );
+ uno::Reference< excel::XRange > xRange;
+ if ( mbIsColumns )
+ xRange = Columns( row );
+ else
+ xRange = Rows( row );
+ return xRange;
+ }
+ return Cells( row, column );
+}
+
+void
+ScVbaRange::AutoOutline( ) throw (script::BasicErrorException, uno::RuntimeException)
+{
+ // #TODO #FIXME needs to check for summary row/col ( whatever they are )
+ // not valid for multi Area Addresses
+ if ( m_Areas->getCount() )
+ DebugHelper::exception(SbERR_METHOD_FAILED, STR_ERRORMESSAGE_APPLIESTOSINGLERANGEONLY);
+ // So needs to either span an entire Row or a just be a single cell
+ // ( that contains a summary RowColumn )
+ // also the Single cell cause doesn't seem to be handled specially in
+ // this code ( ported from the helperapi RangeImpl.java,
+ // RangeRowsImpl.java, RangesImpl.java, RangeSingleCellImpl.java
+ RangeHelper thisRange( mxRange );
+ table::CellRangeAddress thisAddress = thisRange.getCellRangeAddressable()->getRangeAddress();
+
+ if ( isSingleCellRange() || mbIsRows )
+ {
+ uno::Reference< sheet::XSheetOutline > xSheetOutline( thisRange.getSpreadSheet(), uno::UNO_QUERY_THROW );
+ xSheetOutline->autoOutline( thisAddress );
+ }
+ else
+ DebugHelper::exception(SbERR_METHOD_FAILED, rtl::OUString());
+}
+
+void SAL_CALL
+ScVbaRange:: ClearOutline( ) throw (script::BasicErrorException, uno::RuntimeException)
+{
+ if ( m_Areas->getCount() > 1 )
+ {
+ sal_Int32 nItems = m_Areas->getCount();
+ for ( sal_Int32 index=1; index <= nItems; ++index )
+ {
+ uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny(index), uno::Any() ), uno::UNO_QUERY_THROW );
+ xRange->ClearOutline();
+ }
+ return;
+ }
+ RangeHelper thisRange( mxRange );
+ table::CellRangeAddress thisAddress = thisRange.getCellRangeAddressable()->getRangeAddress();
+ uno::Reference< sheet::XSheetOutline > xSheetOutline( thisRange.getSpreadSheet(), uno::UNO_QUERY_THROW );
+ xSheetOutline->clearOutline();
+}
+
+void
+ScVbaRange::groupUnGroup( bool bUnGroup ) throw ( script::BasicErrorException, uno::RuntimeException )
+{
+ if ( m_Areas->getCount() > 1 )
+ DebugHelper::exception(SbERR_METHOD_FAILED, STR_ERRORMESSAGE_APPLIESTOSINGLERANGEONLY);
+ table::TableOrientation nOrient = table::TableOrientation_ROWS;
+ if ( mbIsColumns )
+ nOrient = table::TableOrientation_COLUMNS;
+ RangeHelper thisRange( mxRange );
+ table::CellRangeAddress thisAddress = thisRange.getCellRangeAddressable()->getRangeAddress();
+ uno::Reference< sheet::XSheetOutline > xSheetOutline( thisRange.getSpreadSheet(), uno::UNO_QUERY_THROW );
+ if ( bUnGroup )
+ xSheetOutline->ungroup( thisAddress, nOrient );
+ else
+ xSheetOutline->group( thisAddress, nOrient );
+}
+
+void SAL_CALL
+ScVbaRange::Group( ) throw (script::BasicErrorException, uno::RuntimeException)
+{
+ groupUnGroup();
+}
+void SAL_CALL
+ScVbaRange::Ungroup( ) throw (script::BasicErrorException, uno::RuntimeException)
+{
+ groupUnGroup(true);
+}
+
+void lcl_mergeCellsOfRange( const uno::Reference< table::XCellRange >& xCellRange, sal_Bool _bMerge = sal_True ) throw ( uno::RuntimeException )
+{
+ uno::Reference< util::XMergeable > xMergeable( xCellRange, uno::UNO_QUERY_THROW );
+ xMergeable->merge(_bMerge);
+}
+void SAL_CALL
+ScVbaRange::Merge( const uno::Any& Across ) throw (script::BasicErrorException, uno::RuntimeException)
+{
+ if ( m_Areas->getCount() > 1 )
+ {
+ sal_Int32 nItems = m_Areas->getCount();
+ for ( sal_Int32 index=1; index <= nItems; ++index )
+ {
+ uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny(index), uno::Any() ), uno::UNO_QUERY_THROW );
+ xRange->Merge(Across);
+ }
+ return;
+ }
+ uno::Reference< table::XCellRange > oCellRange;
+ sal_Bool bAcross = sal_False;
+ Across >>= bAcross;
+ if ( !bAcross )
+ lcl_mergeCellsOfRange( mxRange );
+ else
+ {
+ uno::Reference< excel::XRange > oRangeRowsImpl = Rows( uno::Any() );
+ // #TODO #FIXME this seems incredibly lame, this can't be right
+ for (sal_Int32 i=1; i <= oRangeRowsImpl->getCount();i++)
+ {
+ oRangeRowsImpl->Cells( uno::makeAny( i ), uno::Any() )->Merge( uno::makeAny( sal_False ) );
+ }
+ }
+}
+
+void SAL_CALL
+ScVbaRange::UnMerge( ) throw (script::BasicErrorException, uno::RuntimeException)
+{
+ if ( m_Areas->getCount() > 1 )
+ {
+ sal_Int32 nItems = m_Areas->getCount();
+ for ( sal_Int32 index=1; index <= nItems; ++index )
+ {
+ uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny(index), uno::Any() ), uno::UNO_QUERY_THROW );
+ xRange->UnMerge();
+ }
+ return;
+ }
+ lcl_mergeCellsOfRange( mxRange, sal_False);
+}
+
+uno::Any SAL_CALL
+ScVbaRange::getStyle() throw (uno::RuntimeException)
+{
+ if ( m_Areas->getCount() > 1 )
+ {
+ uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny( sal_Int32( 1 ) ), uno::Any() ), uno::UNO_QUERY_THROW );
+ return xRange->getStyle();
+ }
+ uno::Reference< beans::XPropertySet > xProps( mxRange, uno::UNO_QUERY_THROW );
+ rtl::OUString sStyleName;
+ ScDocShell* pShell = getScDocShell();
+ uno::Reference< frame::XModel > xModel( pShell->GetModel() );
+ uno::Reference< excel::XStyle > xStyle = new ScVbaStyle( this, mxContext, sStyleName, xModel );
+ return uno::makeAny( xStyle );
+}
+void SAL_CALL
+ScVbaRange::setStyle( const uno::Any& _style ) throw (uno::RuntimeException)
+{
+ if ( m_Areas->getCount() > 1 )
+ {
+ uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny( sal_Int32( 1 ) ), uno::Any() ), uno::UNO_QUERY_THROW );
+ xRange->setStyle( _style );
+ return;
+ }
+ uno::Reference< beans::XPropertySet > xProps( mxRange, uno::UNO_QUERY_THROW );
+ uno::Reference< excel::XStyle > xStyle;
+ _style >>= xStyle;
+ xProps->setPropertyValue(CELLSTYLE, uno::makeAny(xStyle->getName()));
+}
+
+uno::Reference< excel::XRange >
+ScVbaRange::PreviousNext( bool bIsPrevious )
+{
+ ScMarkData markedRange;
+ ScRange refRange;
+ RangeHelper thisRange( mxRange );
+
+ ScUnoConversion::FillScRange( refRange, thisRange.getCellRangeAddressable()->getRangeAddress());
+ markedRange. SetMarkArea( refRange );
+ short nMove = bIsPrevious ? -1 : 1;
+
+ SCCOL nNewX = refRange.aStart.Col();
+ SCROW nNewY = refRange.aStart.Row();
+ SCTAB nTab = refRange.aStart.Tab();
+
+ ScDocument* pDoc = getScDocument();
+ pDoc->GetNextPos( nNewX,nNewY, nTab, nMove,0, TRUE,TRUE, markedRange );
+ refRange.aStart.SetCol( nNewX );
+ refRange.aStart.SetRow( nNewY );
+ refRange.aStart.SetTab( nTab );
+ refRange.aEnd.SetCol( nNewX );
+ refRange.aEnd.SetRow( nNewY );
+ refRange.aEnd.SetTab( nTab );
+
+ uno::Reference< table::XCellRange > xRange( new ScCellRangeObj( getScDocShell() , refRange ) );
+
+ return new ScVbaRange( getParent(), mxContext, xRange );
+}
+
+uno::Reference< excel::XRange > SAL_CALL
+ScVbaRange::Next() throw (script::BasicErrorException, uno::RuntimeException)
+{
+ if ( m_Areas->getCount() > 1 )
+ {
+ uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny( sal_Int32( 1 ) ), uno::Any() ) , uno::UNO_QUERY_THROW );
+ return xRange->Next();
+ }
+ return PreviousNext( false );
+}
+
+uno::Reference< excel::XRange > SAL_CALL
+ScVbaRange::Previous() throw (script::BasicErrorException, uno::RuntimeException)
+{
+ if ( m_Areas->getCount() > 1 )
+ {
+ uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny( sal_Int32( 1 ) ), uno::Any() ), uno::UNO_QUERY_THROW );
+ return xRange->Previous();
+ }
+ return PreviousNext( true );
+}
+
+uno::Reference< excel::XRange > SAL_CALL
+ScVbaRange::SpecialCells( const uno::Any& _oType, const uno::Any& _oValue) throw ( script::BasicErrorException )
+{
+ bool bIsSingleCell = isSingleCellRange();
+ bool bIsMultiArea = ( m_Areas->getCount() > 1 );
+ ScVbaRange* pRangeToUse = this;
+ sal_Int32 nType = 0;
+ if ( !( _oType >>= nType ) )
+ DebugHelper::exception(SbERR_BAD_PARAMETER, rtl::OUString() );
+ switch(nType)
+ {
+ case excel::XlCellType::xlCellTypeSameFormatConditions:
+ case excel::XlCellType::xlCellTypeAllValidation:
+ case excel::XlCellType::xlCellTypeSameValidation:
+ DebugHelper::exception(SbERR_NOT_IMPLEMENTED, rtl::OUString());
+ break;
+ case excel::XlCellType::xlCellTypeBlanks:
+ case excel::XlCellType::xlCellTypeComments:
+ case excel::XlCellType::xlCellTypeConstants:
+ case excel::XlCellType::xlCellTypeFormulas:
+ case excel::XlCellType::xlCellTypeVisible:
+ {
+ if ( bIsMultiArea )
+ {
+ // need to process each area, gather the results and
+ // create a new range from those
+ std::vector< table::CellRangeAddress > rangeResults;
+ sal_Int32 nItems = ( m_Areas->getCount() + 1 );
+ for ( sal_Int32 index=1; index <= nItems; ++index )
+ {
+ uno::Reference< excel::XRange > xRange( m_Areas->Item( uno::makeAny(index), uno::Any() ), uno::UNO_QUERY_THROW );
+ xRange = xRange->SpecialCells( _oType, _oValue);
+ ScVbaRange* pRange = dynamic_cast< ScVbaRange* >( xRange.get() );
+ if ( xRange.is() && pRange )
+ {
+ sal_Int32 nElems = ( pRange->m_Areas->getCount() + 1 );
+ for ( sal_Int32 nArea = 1; nArea < nElems; ++nArea )
+ {
+ uno::Reference< excel::XRange > xTmpRange( m_Areas->Item( uno::makeAny( nArea ), uno::Any() ), uno::UNO_QUERY_THROW );
+ RangeHelper rHelper( xTmpRange->getCellRange() );
+ rangeResults.push_back( rHelper.getCellRangeAddressable()->getRangeAddress() );
+ }
+ }
+ }
+ ScRangeList aCellRanges;
+ std::vector< table::CellRangeAddress >::iterator it = rangeResults.begin();
+ std::vector< table::CellRangeAddress >::iterator it_end = rangeResults.end();
+ for ( ; it != it_end; ++ it )
+ {
+ ScRange refRange;
+ ScUnoConversion::FillScRange( refRange, *it );
+ aCellRanges.Append( refRange );
+ }
+ // Single range
+ if ( aCellRanges.First() == aCellRanges.Last() )
+ {
+ uno::Reference< table::XCellRange > xRange( new ScCellRangeObj( getScDocShell(), *aCellRanges.First() ) );
+ // #FIXME need proper (WorkSheet) parent
+ return new ScVbaRange( getParent(), mxContext, xRange );
+ }
+ uno::Reference< sheet::XSheetCellRangeContainer > xRanges( new ScCellRangesObj( getScDocShell(), aCellRanges ) );
+
+ // #FIXME need proper (WorkSheet) parent
+ return new ScVbaRange( getParent(), mxContext, xRanges );
+ }
+ else if ( bIsSingleCell )
+ {
+ uno::Reference< excel::XRange > xUsedRange = getWorksheet()->getUsedRange();
+ pRangeToUse = static_cast< ScVbaRange* >( xUsedRange.get() );
+ }
+
+ break;
+ }
+ default:
+ DebugHelper::exception(SbERR_BAD_PARAMETER, rtl::OUString() );
+ break;
+ }
+ if ( !pRangeToUse )
+ DebugHelper::exception(SbERR_METHOD_FAILED, rtl::OUString() );
+ return pRangeToUse->SpecialCellsImpl( nType, _oValue );
+}
+
+sal_Int32 lcl_getFormulaResultFlags(const uno::Any& aType) throw ( script::BasicErrorException )
+{
+ sal_Int32 nType = excel::XlSpecialCellsValue::xlNumbers;
+ aType >>= nType;
+ sal_Int32 nRes = sheet::FormulaResult::VALUE;
+
+ switch(nType)
+ {
+ case excel::XlSpecialCellsValue::xlErrors:
+ nRes= sheet::FormulaResult::ERROR;
+ break;
+ case excel::XlSpecialCellsValue::xlLogical:
+ //TODO bc93774: ask NN if this is really an appropriate substitute
+ nRes = sheet::FormulaResult::VALUE;
+ break;
+ case excel::XlSpecialCellsValue::xlNumbers:
+ nRes = sheet::FormulaResult::VALUE;
+ break;
+ case excel::XlSpecialCellsValue::xlTextValues:
+ nRes = sheet::FormulaResult::STRING;
+ break;
+ default:
+ DebugHelper::exception(SbERR_BAD_PARAMETER, rtl::OUString() );
+ }
+ return nRes;
+}
+
+uno::Reference< excel::XRange >
+ScVbaRange::SpecialCellsImpl( sal_Int32 nType, const uno::Any& _oValue) throw ( script::BasicErrorException )
+{
+ uno::Reference< excel::XRange > xRange;
+ try
+ {
+ uno::Reference< sheet::XCellRangesQuery > xQuery( mxRange, uno::UNO_QUERY_THROW );
+ uno::Reference< excel::XRange > oLocRangeImpl;
+ uno::Reference< sheet::XSheetCellRanges > xLocSheetCellRanges;
+ switch(nType)
+ {
+ case excel::XlCellType::xlCellTypeAllFormatConditions:
+ case excel::XlCellType::xlCellTypeSameFormatConditions:
+ case excel::XlCellType::xlCellTypeAllValidation:
+ case excel::XlCellType::xlCellTypeSameValidation:
+ // Shouldn't get here ( should be filtered out by
+ // ScVbaRange::SpecialCells()
+ DebugHelper::exception(SbERR_NOT_IMPLEMENTED, rtl::OUString());
+ break;
+ case excel::XlCellType::xlCellTypeBlanks:
+ xLocSheetCellRanges = xQuery->queryEmptyCells();
+ break;
+ case excel::XlCellType::xlCellTypeComments:
+ xLocSheetCellRanges = xQuery->queryContentCells(sheet::CellFlags::ANNOTATION);
+ break;
+ case excel::XlCellType::xlCellTypeConstants:
+ xLocSheetCellRanges = xQuery->queryContentCells(23);
+ break;
+ case excel::XlCellType::xlCellTypeFormulas:
+ {
+ sal_Int32 nFormulaResult = lcl_getFormulaResultFlags(_oValue);
+ xLocSheetCellRanges = xQuery->queryFormulaCells(nFormulaResult);
+ break;
+ }
+ case excel::XlCellType::xlCellTypeLastCell:
+ xRange = Cells( uno::makeAny( getCount() ), uno::Any() );
+ case excel::XlCellType::xlCellTypeVisible:
+ xLocSheetCellRanges = xQuery->queryVisibleCells();
+ break;
+ default:
+ DebugHelper::exception(SbERR_BAD_PARAMETER, rtl::OUString() );
+ break;
+ }
+ if (xLocSheetCellRanges.is())
+ {
+ xRange = lcl_makeXRangeFromSheetCellRanges( getParent(), mxContext, xLocSheetCellRanges, getScDocShell() );
+ }
+ }
+ catch (uno::Exception& )
+ {
+ DebugHelper::exception(SbERR_METHOD_FAILED, STR_ERRORMESSAGE_NOCELLSWEREFOUND);
+ }
+ return xRange;
+}
+
+void SAL_CALL
+ScVbaRange::RemoveSubtotal( ) throw (script::BasicErrorException, uno::RuntimeException)
+{
+ uno::Reference< sheet::XSubTotalCalculatable > xSub( mxRange, uno::UNO_QUERY_THROW );
+ xSub->removeSubTotals();
+}
+
+void SAL_CALL
+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)
+{
+ try
+ {
+ sal_Bool bDoReplace = sal_False;
+ aReplace >>= bDoReplace;
+ sal_Bool bAddPageBreaks = sal_False;
+ PageBreaks >>= bAddPageBreaks;
+
+ uno::Reference< sheet::XSubTotalCalculatable> xSub;
+ uno::Reference< sheet::XSubTotalDescriptor > xSubDesc = xSub->createSubTotalDescriptor(sal_True);
+ uno::Reference< beans::XPropertySet > xSubDescPropertySet( xSubDesc, uno::UNO_QUERY_THROW );
+ xSubDescPropertySet->setPropertyValue(INSERTPAGEBREAKS, uno::makeAny( bAddPageBreaks));
+ sal_Int32 nLen = _nTotalList.getLength();
+ uno::Sequence< sheet::SubTotalColumn > aColumns( nLen );
+ for (int i = 0; i < nLen; i++)
+ {
+ aColumns[i].Column = _nTotalList[i] - 1;
+ switch (_nFunction)
+ {
+ case excel::XlConsolidationFunction::xlAverage:
+ aColumns[i].Function = sheet::GeneralFunction_AVERAGE;
+ break;
+ case excel::XlConsolidationFunction::xlCount:
+ aColumns[i].Function = sheet::GeneralFunction_COUNT;
+ break;
+ case excel::XlConsolidationFunction::xlCountNums:
+ aColumns[i].Function = sheet::GeneralFunction_COUNTNUMS;
+ break;
+ case excel::XlConsolidationFunction::xlMax:
+ aColumns[i].Function = sheet::GeneralFunction_MAX;
+ break;
+ case excel::XlConsolidationFunction::xlMin:
+ aColumns[i].Function = sheet::GeneralFunction_MIN;
+ break;
+ case excel::XlConsolidationFunction::xlProduct:
+ aColumns[i].Function = sheet::GeneralFunction_PRODUCT;
+ break;
+ case excel::XlConsolidationFunction::xlStDev:
+ aColumns[i].Function = sheet::GeneralFunction_STDEV;
+ break;
+ case excel::XlConsolidationFunction::xlStDevP:
+ aColumns[i].Function = sheet::GeneralFunction_STDEVP;
+ break;
+ case excel::XlConsolidationFunction::xlSum:
+ aColumns[i].Function = sheet::GeneralFunction_SUM;
+ break;
+ case excel::XlConsolidationFunction::xlUnknown:
+ aColumns[i].Function = sheet::GeneralFunction_NONE;
+ break;
+ case excel::XlConsolidationFunction::xlVar:
+ aColumns[i].Function = sheet::GeneralFunction_VAR;
+ break;
+ case excel::XlConsolidationFunction::xlVarP:
+ aColumns[i].Function = sheet::GeneralFunction_VARP;
+ break;
+ default:
+ DebugHelper::exception(SbERR_BAD_PARAMETER, rtl::OUString()) ;
+ return;
+ }
+ }
+ xSubDesc->addNew(aColumns, _nGroupBy - 1);
+ xSub->applySubTotals(xSubDesc, bDoReplace);
+ }
+ catch (uno::Exception& )
+ {
+ DebugHelper::exception(SbERR_METHOD_FAILED, rtl::OUString());
+ }
+}
+
+uno::Reference< excel::XRange >
+ScVbaRange::intersect( const css::uno::Reference< oo::excel::XRange >& xRange ) throw (script::BasicErrorException, uno::RuntimeException)
+{
+ uno::Reference< excel::XRange > xResult;
+ try
+ {
+ uno::Reference< sheet::XCellRangesQuery > xQuery( mxRange, uno::UNO_QUERY_THROW );
+ RangeHelper aRange( xRange->getCellRange() );
+ table::CellRangeAddress aAddress = aRange.getCellRangeAddressable()->getRangeAddress();
+ uno::Reference< sheet::XSheetCellRanges > xIntersectRanges = xQuery->queryIntersection( aAddress );
+ xResult = lcl_makeXRangeFromSheetCellRanges( getParent(), mxContext, xIntersectRanges, getScDocShell() );
+
+
+ }
+ catch( uno::Exception& )
+ {
+ DebugHelper::exception(SbERR_METHOD_FAILED, rtl::OUString());
+ }
+ return xResult;
+}
+
+rtl::OUString&
+ScVbaRange::getServiceImplName()
+{
+ static rtl::OUString sImplName( RTL_CONSTASCII_USTRINGPARAM("ScVbaRange") );
+ return sImplName;
+}
+
+uno::Sequence< rtl::OUString >
+ScVbaRange::getServiceNames()
+{
+ static uno::Sequence< rtl::OUString > aServiceNames;
+ if ( aServiceNames.getLength() == 0 )
+ {
+ aServiceNames.realloc( 1 );
+ aServiceNames[ 0 ] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("org.openoffice.excel.Range" ) );
+ }
+ return aServiceNames;
+}
+
+namespace range
+{
+namespace sdecl = comphelper::service_decl;
+sdecl::vba_service_class_<ScVbaRange, sdecl::with_args<true> > serviceImpl;
+extern sdecl::ServiceDecl const serviceDecl(
+ serviceImpl,
+ "SvVbaRange",
+ "org.openoffice.excel.Range" );
}