summaryrefslogtreecommitdiff
path: root/sc/source/ui/vba/vbainterior.cxx
diff options
context:
space:
mode:
authorOliver Bolte <obo@openoffice.org>2009-02-13 13:03:24 +0000
committerOliver Bolte <obo@openoffice.org>2009-02-13 13:03:24 +0000
commit90e0834d5612cf75e9a21b3a6bab10f6a98ac053 (patch)
treee81fbf0a382cf14023e45571b6f6e48396a52659 /sc/source/ui/vba/vbainterior.cxx
parent6fed8a270237f81690addb2f5853e372535d66a9 (diff)
CWS-TOOLING: integrate CWS npower11
2009-01-21 11:00:00 +0100 npower r266639 : replace ScAddress::CONV_XL_R1C1 with formula::FormulaGrammar::CONV_XL_R1C1 2009-01-21 10:58:33 +0100 npower r266638 : fixup access for changes to compiler.[ch]xx 2009-01-21 10:57:46 +0100 npower r266637 : replace the static with non-static member ( to align with the latest m39 ) changes 2009-01-20 11:53:52 +0100 npower r266562 : CWS-TOOLING: rebase CWS npower11 to trunk@266428 (milestone: DEV300:m39) 2009-01-09 23:31:00 +0100 cloph r266122 : fix typo (missing "="), initialize variables to avoid WaE breakage 2009-01-09 11:57:20 +0100 npower r266071 : wae Mac OSX gcc-4.0.1 (PPC) 2009-01-08 11:09:49 +0100 npower r265986 : wae - Mac OSX gcc-4.0.1 (PPC) 2009-01-07 10:33:20 +0100 npower r265952 : wae Mac OSX gcc-4.0.1 2008-12-18 19:14:10 +0100 npower r265712 : wae for wntmsci12 target 2008-12-17 16:14:54 +0100 npower r265640 : add Outline property for Font, also remove growing list of friend classes for ScCellRangeObj and replace by a single class. 2008-12-17 16:11:02 +0100 npower r265639 : fix path variable for 3.1, also tweak the unix logs 2008-12-11 02:39:58 +0100 hanbo r265233 : fix the vba/vba namespace of constants 2008-11-25 17:05:39 +0100 npower r264317 : namespace changes 2008-11-25 14:12:37 +0100 npower r264308 : revert changes made by mistake when migrating cws 2008-11-25 13:30:59 +0100 npower r264296 : i#93944# namespace changes 2008-11-25 13:29:25 +0100 npower r264293 : i#93944# namespace changes 2008-11-25 13:27:08 +0100 npower r264289 : i#93944# namespace changes 2008-11-24 18:24:17 +0100 npower r264263 : svn migration 2008-11-24 18:22:47 +0100 npower r264262 : not needed anymore 2008-11-24 18:21:23 +0100 npower r264261 : svn migration 2008-11-24 18:18:31 +0100 npower r264260 : svn migration
Diffstat (limited to 'sc/source/ui/vba/vbainterior.cxx')
-rw-r--r--sc/source/ui/vba/vbainterior.cxx303
1 files changed, 281 insertions, 22 deletions
diff --git a/sc/source/ui/vba/vbainterior.cxx b/sc/source/ui/vba/vbainterior.cxx
index 381600ad8d81..bb85b6c21922 100644
--- a/sc/source/ui/vba/vbainterior.cxx
+++ b/sc/source/ui/vba/vbainterior.cxx
@@ -34,8 +34,11 @@
#include <com/sun/star/beans/XIntrospectionAccess.hpp>
#include <com/sun/star/reflection/XIdlMethod.hpp>
#include <com/sun/star/beans/MethodConcept.hpp>
+#include <com/sun/star/beans/NamedValue.hpp>
+#include <com/sun/star/xml/AttributeData.hpp>
-#include <org/openoffice/excel/XlColorIndex.hpp>
+#include <ooo/vba/excel/XlColorIndex.hpp>
+#include <ooo/vba/excel/XlPattern.hpp>
#include <comphelper/processfactory.hxx>
#include <cppuhelper/queryinterface.hxx>
@@ -44,12 +47,53 @@
#include "vbainterior.hxx"
#include "vbapalette.hxx"
+
+#define STATIC_TABLE_SIZE( array ) (sizeof(array)/sizeof(*(array)))
+#define COLORMAST 0xFFFFFF
+const sal_uInt16 EXC_COLOR_WINDOWBACK = 65;
+typedef std::map< sal_Int32, sal_Int32 > PatternMap;
+typedef std::pair< sal_Int32, sal_Int32 > PatternPair;
using namespace ::com::sun::star;
-using namespace ::org::openoffice;
+using namespace ::ooo::vba;
+using namespace ::ooo::vba::excel::XlPattern;
static const rtl::OUString BACKCOLOR( RTL_CONSTASCII_USTRINGPARAM( "CellBackColor" ) );
+static const rtl::OUString PATTERN( RTL_CONSTASCII_USTRINGPARAM( "Pattern" ) );
+static const rtl::OUString PATTERNCOLOR( RTL_CONSTASCII_USTRINGPARAM( "PatternColor" ) );
-ScVbaInterior::ScVbaInterior( const uno::Reference< vba::XHelperInterface >& xParent, const uno::Reference< uno::XComponentContext >& xContext, const uno::Reference< beans::XPropertySet >& xProps, ScDocument* pScDoc ) throw ( lang::IllegalArgumentException) : ScVbaInterior_BASE( xParent, xContext ), m_xProps(xProps), m_pScDoc( pScDoc )
+PatternMap lcl_getPatternMap()
{
+ PatternMap aPatternMap;
+ aPatternMap.insert( PatternPair( xlPatternAutomatic, 0 ) );
+ aPatternMap.insert( PatternPair( xlPatternChecker, 9 ) );
+ aPatternMap.insert( PatternPair( xlPatternCrissCross, 16 ) );
+ aPatternMap.insert( PatternPair( xlPatternDown, 7 ) );
+ aPatternMap.insert( PatternPair( xlPatternGray16, 17 ) );
+ aPatternMap.insert( PatternPair( xlPatternGray25, 4 ) );
+ aPatternMap.insert( PatternPair( xlPatternGray50, 2 ) );
+ aPatternMap.insert( PatternPair( xlPatternGray75, 3 ) );
+ aPatternMap.insert( PatternPair( xlPatternGray8, 18 ) );
+ aPatternMap.insert( PatternPair( xlPatternGrid, 15 ) );
+ aPatternMap.insert( PatternPair( xlPatternHorizontal, 5 ) );
+ aPatternMap.insert( PatternPair( xlPatternLightDown, 13 ) );
+ aPatternMap.insert( PatternPair( xlPatternLightHorizontal, 11 ) );
+ aPatternMap.insert( PatternPair( xlPatternLightUp, 14 ) );
+ aPatternMap.insert( PatternPair( xlPatternLightVertical, 12 ) );
+ aPatternMap.insert( PatternPair( xlPatternNone, 0 ) );
+ aPatternMap.insert( PatternPair( xlPatternSemiGray75, 10 ) );
+ aPatternMap.insert( PatternPair( xlPatternSolid, 0 ) );
+ aPatternMap.insert( PatternPair( xlPatternUp, 8 ) );
+ aPatternMap.insert( PatternPair( xlPatternVertical, 6 ) );
+ return aPatternMap;
+}
+
+static PatternMap aPatternMap( lcl_getPatternMap() );
+
+ScVbaInterior::ScVbaInterior( const uno::Reference< XHelperInterface >& xParent, const uno::Reference< uno::XComponentContext >& xContext, const uno::Reference< beans::XPropertySet >& xProps, ScDocument* pScDoc ) throw ( lang::IllegalArgumentException) : ScVbaInterior_BASE( xParent, xContext ), m_xProps(xProps), m_pScDoc( pScDoc )
+{
+ // auto color
+ //m_aPattColor.SetColor( (sal_uInt32)0xFFFFFFFF );
+ m_aPattColor.SetColor( (sal_uInt32)0x0 );
+ m_nPattern = 0L;
if ( !m_xProps.is() )
throw lang::IllegalArgumentException( rtl::OUString(RTL_CONSTASCII_USTRINGPARAM( "properties") ), uno::Reference< uno::XInterface >(), 2 );
}
@@ -57,15 +101,50 @@ ScVbaInterior::ScVbaInterior( const uno::Reference< vba::XHelperInterface >& xPa
uno::Any
ScVbaInterior::getColor() throw (uno::RuntimeException)
{
- uno::Any aAny;
- aAny = OORGBToXLRGB( m_xProps->getPropertyValue( BACKCOLOR ) );
- return aAny;
+ Color aBackColor( GetBackColor() );
+ return uno::makeAny( OORGBToXLRGB( aBackColor.GetColor() ) );
}
void
ScVbaInterior::setColor( const uno::Any& _color ) throw (uno::RuntimeException)
{
- m_xProps->setPropertyValue( BACKCOLOR , XLRGBToOORGB(_color));
+ sal_Int32 nColor = 0;
+ if( _color >>= nColor )
+ {
+ SetUserDefinedAttributes( BACKCOLOR, SetAttributeData( XLRGBToOORGB( nColor ) ) );
+ //m_xProps->setPropertyValue( BACKCOLOR , XLRGBToOORGB(_color));
+ SetMixedColor();
+ }
+}
+
+void
+ScVbaInterior::SetMixedColor()
+{
+ // pattern
+ uno::Any aPattern = GetUserDefinedAttributes( PATTERN );
+ if( aPattern.hasValue() )
+ {
+ m_nPattern = GetAttributeData( aPattern );
+ }
+ sal_Int32 nPattern = aPatternMap[ m_nPattern ];
+ // pattern color
+ uno::Any aPatternColor = GetUserDefinedAttributes( PATTERNCOLOR );
+ if( aPatternColor.hasValue() )
+ {
+ sal_uInt32 nPatternColor = GetAttributeData( aPatternColor );
+ m_aPattColor.SetColor( nPatternColor );
+ }
+ sal_Int32 nPatternColor = m_aPattColor.GetColor();
+ // back color
+ Color aBackColor( GetBackColor() );
+ // set mixed color
+ Color aMixedColor;
+ if( nPattern > 0 )
+ aMixedColor = GetPatternColor( Color(nPatternColor), aBackColor, (sal_uInt32)nPattern );
+ else
+ aMixedColor = GetPatternColor( aBackColor, aBackColor, (sal_uInt32)nPattern );
+ sal_Int32 nMixedColor = aMixedColor.GetColor() & COLORMAST;
+ m_xProps->setPropertyValue( BACKCOLOR , uno::makeAny( nMixedColor ) );
}
uno::Reference< container::XIndexAccess >
@@ -83,28 +162,28 @@ ScVbaInterior::setColorIndex( const css::uno::Any& _colorindex ) throw (css::uno
{
sal_Int32 nIndex = 0;
_colorindex >>= nIndex;
+
+ // setColor expects colors in XL RGB values
+ // #FIXME this is daft we convert OO RGB val to XL RGB val and
+ // then back again to OO RGB value
+ setColor( OORGBToXLRGB( GetIndexColor( nIndex ) ) );
+}
+uno::Any
+ScVbaInterior::GetIndexColor( const sal_Int32& nColorIndex )
+{
+ sal_Int32 nIndex = nColorIndex;
// #FIXME xlColorIndexAutomatic & xlColorIndexNone are not really
// handled properly here
-
if ( !nIndex || ( nIndex == excel::XlColorIndex::xlColorIndexAutomatic ) || ( nIndex == excel::XlColorIndex::xlColorIndexNone ) )
nIndex = 2; // default is white ( this maybe will probably break, e.g. we may at some stage need to know what this interior is, a cell or something else and then pick a default colour based on that )
--nIndex; // OOo indices are zero bases
uno::Reference< container::XIndexAccess > xIndex = getPalette();
- // setColor expects colors in XL RGB values
- // #FIXME this is daft we convert OO RGB val to XL RGB val and
- // then back again to OO RGB value
- setColor( OORGBToXLRGB(xIndex->getByIndex( nIndex )) );
+ return xIndex->getByIndex( nIndex );
}
-uno::Any SAL_CALL
-ScVbaInterior::getColorIndex() throw ( css::uno::RuntimeException )
+sal_Int32
+ScVbaInterior::GetColorIndex( const sal_Int32 nColor )
{
- sal_Int32 nColor = 0;
- // getColor returns Xl ColorValue, need to convert it to OO val
- // as the palette deals with OO RGB values
- // #FIXME this is daft in getColor we convert OO RGB val to XL RGB val
- // and then back again to OO RGB value
- XLRGBToOORGB( getColor() ) >>= nColor;
uno::Reference< container::XIndexAccess > xIndex = getPalette();
sal_Int32 nElems = xIndex->getCount();
sal_Int32 nIndex = -1;
@@ -118,7 +197,187 @@ ScVbaInterior::getColorIndex() throw ( css::uno::RuntimeException )
break;
}
}
- return uno::makeAny( nIndex );
+ return nIndex;
+}
+
+uno::Any SAL_CALL
+ScVbaInterior::getColorIndex() throw ( css::uno::RuntimeException )
+{
+ sal_Int32 nColor = 0;
+ // getColor returns Xl ColorValue, need to convert it to OO val
+ // as the palette deals with OO RGB values
+ // #FIXME this is daft in getColor we convert OO RGB val to XL RGB val
+ // and then back again to OO RGB value
+ XLRGBToOORGB( getColor() ) >>= nColor;
+
+ return uno::makeAny( GetIndexColor( nColor ) );
+}
+Color
+ScVbaInterior::GetPatternColor( const Color& rPattColor, const Color& rBackColor, sal_uInt32 nXclPattern )
+{
+ // 0x00 == 0% transparence (full rPattColor)
+ // 0x80 == 100% transparence (full rBackColor)
+ static const sal_uInt8 pnRatioTable[] =
+ {
+ 0x80, 0x00, 0x40, 0x20, 0x60, 0x40, 0x40, 0x40, // 00 - 07
+ 0x40, 0x40, 0x20, 0x60, 0x60, 0x60, 0x60, 0x48, // 08 - 15
+ 0x50, 0x70, 0x78 // 16 - 18
+ };
+ return ( nXclPattern < STATIC_TABLE_SIZE( pnRatioTable ) ) ?
+ GetMixedColor( rPattColor, rBackColor, pnRatioTable[ nXclPattern ] ) : rPattColor;
+}
+Color
+ScVbaInterior::GetMixedColor( const Color& rFore, const Color& rBack, sal_uInt8 nTrans )
+{
+ return Color(
+ nTrans,
+ GetMixedColorComp( rFore.GetRed(), rBack.GetRed(), nTrans ),
+ GetMixedColorComp( rFore.GetGreen(), rBack.GetGreen(), nTrans ),
+ GetMixedColorComp( rFore.GetBlue(), rBack.GetBlue(), nTrans ));
+}
+sal_uInt8
+ScVbaInterior::GetMixedColorComp( sal_uInt8 nFore, sal_uInt8 nBack, sal_uInt8 nTrans )
+{
+ sal_uInt32 nTemp = ((static_cast< sal_Int32 >( nBack ) - nFore) * nTrans) / 0x80 + nFore;
+ return static_cast< sal_uInt8 >( nTemp );
+}
+uno::Reference< container::XNameContainer >
+ScVbaInterior::GetAttributeContainer()
+{
+ return uno::Reference < container::XNameContainer > ( m_xProps->getPropertyValue( rtl::OUString::createFromAscii( "UserDefinedAttributes" ) ), uno::UNO_QUERY_THROW );
+}
+sal_Int32
+ScVbaInterior::GetAttributeData( uno::Any aValue )
+{
+ xml::AttributeData aDataValue;
+ if( aValue >>= aDataValue )
+ {
+ return aDataValue.Value.toInt32();
+ }
+ return sal_Int32( 0 );
+}
+uno::Any
+ScVbaInterior::SetAttributeData( sal_Int32 nValue )
+{
+ xml::AttributeData aAttributeData;
+ //aAttributeData.Namespace = rtl::OUString::createFromAscii( "ooo.vba.excel.CellPatten");
+ aAttributeData.Type = rtl::OUString::createFromAscii( "sal_Int32" );
+ aAttributeData.Value = rtl::OUString::valueOf( nValue );
+ return uno::makeAny( aAttributeData );
+}
+uno::Any
+ScVbaInterior::GetUserDefinedAttributes( const rtl::OUString& sName )
+{
+ uno::Reference< container::XNameContainer > xNameContainer( GetAttributeContainer(), uno::UNO_QUERY_THROW );
+ if( xNameContainer->hasByName( sName ) )
+ {
+ return xNameContainer->getByName( sName );
+ }
+ return uno::Any();
+}
+void
+ScVbaInterior::SetUserDefinedAttributes( const rtl::OUString& sName, const uno::Any& aValue )
+{
+ if( aValue.hasValue() )
+ {
+ uno::Reference< container::XNameContainer > xNameContainer( GetAttributeContainer(), uno::UNO_QUERY_THROW );
+ if( xNameContainer->hasByName( sName ) )
+ xNameContainer->removeByName( sName );
+ xNameContainer->insertByName( sName, aValue );
+ m_xProps->setPropertyValue( rtl::OUString::createFromAscii( "UserDefinedAttributes" ), uno::makeAny( xNameContainer ) );
+ }
+}
+// OOo do not support below API
+uno::Any SAL_CALL
+ScVbaInterior::getPattern() throw (uno::RuntimeException)
+{
+ // XlPattern
+ uno::Any aPattern = GetUserDefinedAttributes( PATTERN );
+ if( aPattern.hasValue() )
+ return uno::makeAny( GetAttributeData( aPattern ) );
+ return uno::makeAny( excel::XlPattern::xlPatternNone );
+}
+void SAL_CALL
+ScVbaInterior::setPattern( const uno::Any& _pattern ) throw (uno::RuntimeException)
+{
+ if( _pattern >>= m_nPattern )
+ {
+ SetUserDefinedAttributes( PATTERN, SetAttributeData( m_nPattern ) );
+ SetMixedColor();
+ }
+ else
+ throw uno::RuntimeException( rtl::OUString::createFromAscii( "Invalid Pattern index" ), uno::Reference< uno::XInterface >() );
+}
+Color
+ScVbaInterior::GetBackColor()
+{
+ sal_Int32 nColor = 0;
+ Color aBackColor;
+ uno::Any aColor = GetUserDefinedAttributes( BACKCOLOR );
+ if( aColor.hasValue() )
+ {
+ nColor = GetAttributeData( aColor );
+ aBackColor.SetColor( nColor );
+ }
+ else
+ {
+ uno::Any aAny;
+ aAny = OORGBToXLRGB( m_xProps->getPropertyValue( BACKCOLOR ) );
+ if( aAny >>= nColor )
+ {
+ nColor = XLRGBToOORGB( nColor );
+ aBackColor.SetColor( nColor );
+ SetUserDefinedAttributes( BACKCOLOR, SetAttributeData( nColor ) );
+ }
+ }
+ return aBackColor;
+}
+uno::Any SAL_CALL
+ScVbaInterior::getPatternColor() throw (uno::RuntimeException)
+{
+ // 0 is the default color. no filled.
+ uno::Any aPatternColor = GetUserDefinedAttributes( PATTERNCOLOR );
+ if( aPatternColor.hasValue() )
+ {
+ sal_uInt32 nPatternColor = GetAttributeData( aPatternColor );
+ return uno::makeAny( OORGBToXLRGB( nPatternColor ) );
+ }
+ return uno::makeAny( sal_Int32( 0 ) );
+}
+void SAL_CALL
+ScVbaInterior::setPatternColor( const uno::Any& _patterncolor ) throw (uno::RuntimeException)
+{
+ sal_Int32 nPattColor = 0;
+ if( _patterncolor >>= nPattColor )
+ {
+ SetUserDefinedAttributes( PATTERNCOLOR, SetAttributeData( XLRGBToOORGB( nPattColor ) ) );
+ SetMixedColor();
+ }
+ else
+ throw uno::RuntimeException( rtl::OUString::createFromAscii( "Invalid Pattern Color" ), uno::Reference< uno::XInterface >() );
+}
+uno::Any SAL_CALL
+ScVbaInterior::getPatternColorIndex() throw (uno::RuntimeException)
+{
+ sal_Int32 nColor = 0;
+ XLRGBToOORGB( getPatternColor() ) >>= nColor;
+
+ return uno::makeAny( GetIndexColor( nColor ) );
+}
+void SAL_CALL
+ScVbaInterior::setPatternColorIndex( const uno::Any& _patterncolorindex ) throw (uno::RuntimeException)
+{
+ sal_Int32 nColorIndex = 0;
+ if( _patterncolorindex >>= nColorIndex )
+ {
+ if( nColorIndex == 0 )
+ return;
+ sal_Int32 nPattColor = 0;
+ GetIndexColor( nColorIndex ) >>= nPattColor;
+ setPatternColor( uno::makeAny( OORGBToXLRGB( nPattColor ) ) );
+ }
+ else
+ throw uno::RuntimeException( rtl::OUString::createFromAscii( "Invalid Pattern Color" ), uno::Reference< uno::XInterface >() );
}
rtl::OUString&
@@ -135,7 +394,7 @@ ScVbaInterior::getServiceNames()
if ( aServiceNames.getLength() == 0 )
{
aServiceNames.realloc( 1 );
- aServiceNames[ 0 ] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("org.openoffice.excel.Interior" ) );
+ aServiceNames[ 0 ] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.excel.Interior" ) );
}
return aServiceNames;
}