xref: /aoo41x/main/sw/source/ui/vba/vbafont.cxx (revision efeef26f)
1*efeef26fSAndrew Rist /**************************************************************
2*efeef26fSAndrew Rist  *
3*efeef26fSAndrew Rist  * Licensed to the Apache Software Foundation (ASF) under one
4*efeef26fSAndrew Rist  * or more contributor license agreements.  See the NOTICE file
5*efeef26fSAndrew Rist  * distributed with this work for additional information
6*efeef26fSAndrew Rist  * regarding copyright ownership.  The ASF licenses this file
7*efeef26fSAndrew Rist  * to you under the Apache License, Version 2.0 (the
8*efeef26fSAndrew Rist  * "License"); you may not use this file except in compliance
9*efeef26fSAndrew Rist  * with the License.  You may obtain a copy of the License at
10*efeef26fSAndrew Rist  *
11*efeef26fSAndrew Rist  *   http://www.apache.org/licenses/LICENSE-2.0
12*efeef26fSAndrew Rist  *
13*efeef26fSAndrew Rist  * Unless required by applicable law or agreed to in writing,
14*efeef26fSAndrew Rist  * software distributed under the License is distributed on an
15*efeef26fSAndrew Rist  * "AS IS" BASIS, WITHOUT WARRANTIES OR CONDITIONS OF ANY
16*efeef26fSAndrew Rist  * KIND, either express or implied.  See the License for the
17*efeef26fSAndrew Rist  * specific language governing permissions and limitations
18*efeef26fSAndrew Rist  * under the License.
19*efeef26fSAndrew Rist  *
20*efeef26fSAndrew Rist  *************************************************************/
21*efeef26fSAndrew Rist 
22cdf0e10cSrcweir #include "vbafont.hxx"
23cdf0e10cSrcweir #include <com/sun/star/awt/FontUnderline.hpp>
24cdf0e10cSrcweir #include <ooo/vba/word/WdUnderline.hpp>
25cdf0e10cSrcweir #include <hash_map>
26cdf0e10cSrcweir #include <ooo/vba/word/WdColorIndex.hpp>
27cdf0e10cSrcweir 
28cdf0e10cSrcweir using namespace ::ooo::vba;
29cdf0e10cSrcweir using namespace ::com::sun::star;
30cdf0e10cSrcweir 
31cdf0e10cSrcweir const uno::Any aLongAnyTrue( sal_Int16(-1) );
32cdf0e10cSrcweir const uno::Any aLongAnyFalse( sal_Int16( 0 ) );
33cdf0e10cSrcweir 
34cdf0e10cSrcweir struct MapPair
35cdf0e10cSrcweir {
36cdf0e10cSrcweir     sal_Int32 nMSOConst;
37cdf0e10cSrcweir     sal_Int32 nOOOConst;
38cdf0e10cSrcweir };
39cdf0e10cSrcweir 
40cdf0e10cSrcweir static MapPair UnderLineTable[] = {
41cdf0e10cSrcweir         { word::WdUnderline::wdUnderlineNone, com::sun::star::awt::FontUnderline::NONE },
42cdf0e10cSrcweir         { word::WdUnderline::wdUnderlineSingle, com::sun::star::awt::FontUnderline::SINGLE },
43cdf0e10cSrcweir         { word::WdUnderline::wdUnderlineWords, com::sun::star::awt::FontUnderline::SINGLE },
44cdf0e10cSrcweir         { word::WdUnderline::wdUnderlineDouble, com::sun::star::awt::FontUnderline::DOUBLE },
45cdf0e10cSrcweir         { word::WdUnderline::wdUnderlineDotted, com::sun::star::awt::FontUnderline::DOTTED },
46cdf0e10cSrcweir         { word::WdUnderline::wdUnderlineThick, com::sun::star::awt::FontUnderline::BOLDDASH },
47cdf0e10cSrcweir         { word::WdUnderline::wdUnderlineDash, com::sun::star::awt::FontUnderline::DASH },
48cdf0e10cSrcweir 	{ word::WdUnderline::wdUnderlineDotDash, com::sun::star::awt::FontUnderline::DASHDOT },
49cdf0e10cSrcweir 	{ word::WdUnderline::wdUnderlineDotDotDash, com::sun::star::awt::FontUnderline::DASHDOTDOT },
50cdf0e10cSrcweir         { word::WdUnderline::wdUnderlineWavy, com::sun::star::awt::FontUnderline::WAVE },
51cdf0e10cSrcweir         { word::WdUnderline::wdUnderlineDottedHeavy, com::sun::star::awt::FontUnderline::BOLDDOTTED },
52cdf0e10cSrcweir         { word::WdUnderline::wdUnderlineDashHeavy, com::sun::star::awt::FontUnderline::BOLDDASH },
53cdf0e10cSrcweir         { word::WdUnderline::wdUnderlineDotDashHeavy, com::sun::star::awt::FontUnderline::BOLDDASHDOT },
54cdf0e10cSrcweir         { word::WdUnderline::wdUnderlineDotDotDashHeavy, com::sun::star::awt::FontUnderline::BOLDDASHDOTDOT },
55cdf0e10cSrcweir         { word::WdUnderline::wdUnderlineWavyHeavy, com::sun::star::awt::FontUnderline::BOLDWAVE },
56cdf0e10cSrcweir         { word::WdUnderline::wdUnderlineDashLong, com::sun::star::awt::FontUnderline::LONGDASH },
57cdf0e10cSrcweir         { word::WdUnderline::wdUnderlineWavyDouble, com::sun::star::awt::FontUnderline::DOUBLEWAVE },
58cdf0e10cSrcweir         { word::WdUnderline::wdUnderlineDashLongHeavy, com::sun::star::awt::FontUnderline::BOLDLONGDASH },
59cdf0e10cSrcweir };
60cdf0e10cSrcweir 
61cdf0e10cSrcweir typedef std::hash_map< sal_Int32, sal_Int32 > ConstToConst;
62cdf0e10cSrcweir class UnderLineMapper
63cdf0e10cSrcweir {
64cdf0e10cSrcweir     ConstToConst MSO2OOO;
65cdf0e10cSrcweir     ConstToConst OOO2MSO;
66cdf0e10cSrcweir private:
UnderLineMapper()67cdf0e10cSrcweir     UnderLineMapper()
68cdf0e10cSrcweir     {
69cdf0e10cSrcweir         sal_Int32 nLen = sizeof( UnderLineTable )/ sizeof( UnderLineTable[0] );
70cdf0e10cSrcweir 
71cdf0e10cSrcweir         for ( sal_Int32 index=0; index<nLen; ++index )
72cdf0e10cSrcweir         {
73cdf0e10cSrcweir             MSO2OOO[ UnderLineTable[ index ].nMSOConst ] = UnderLineTable[ index ].nOOOConst;
74cdf0e10cSrcweir             OOO2MSO[ UnderLineTable[ index ].nOOOConst ] = UnderLineTable[ index ].nMSOConst;
75cdf0e10cSrcweir         }
76cdf0e10cSrcweir     }
77cdf0e10cSrcweir public:
propName()78cdf0e10cSrcweir     static rtl::OUString propName()
79cdf0e10cSrcweir     {
80cdf0e10cSrcweir         static rtl::OUString sPropName( RTL_CONSTASCII_USTRINGPARAM("CharUnderline") );
81cdf0e10cSrcweir         return sPropName;
82cdf0e10cSrcweir     }
83cdf0e10cSrcweir 
instance()84cdf0e10cSrcweir     static UnderLineMapper& instance()
85cdf0e10cSrcweir     {
86cdf0e10cSrcweir         static  UnderLineMapper theMapper;
87cdf0e10cSrcweir         return theMapper;
88cdf0e10cSrcweir     }
89cdf0e10cSrcweir 
getOOOFromMSO(sal_Int32 nMSOConst)90cdf0e10cSrcweir     sal_Int32 getOOOFromMSO( sal_Int32 nMSOConst ) throw( lang::IllegalArgumentException )
91cdf0e10cSrcweir     {
92cdf0e10cSrcweir         ConstToConst::iterator it = MSO2OOO.find( nMSOConst );
93cdf0e10cSrcweir         if ( it == MSO2OOO.end() )
94cdf0e10cSrcweir             throw lang::IllegalArgumentException();
95cdf0e10cSrcweir         return it->second;
96cdf0e10cSrcweir     }
getMSOFromOOO(sal_Int32 nOOOConst)97cdf0e10cSrcweir     sal_Int32 getMSOFromOOO( sal_Int32 nOOOConst ) throw( lang::IllegalArgumentException )
98cdf0e10cSrcweir     {
99cdf0e10cSrcweir         ConstToConst::iterator it = OOO2MSO.find( nOOOConst );
100cdf0e10cSrcweir         if ( it == OOO2MSO.end() )
101cdf0e10cSrcweir             throw lang::IllegalArgumentException();
102cdf0e10cSrcweir         return it->second;
103cdf0e10cSrcweir     }
104cdf0e10cSrcweir };
105cdf0e10cSrcweir 
SwVbaFont(const uno::Reference<XHelperInterface> & xParent,const uno::Reference<uno::XComponentContext> & xContext,const uno::Reference<container::XIndexAccess> & xPalette,uno::Reference<css::beans::XPropertySet> xPropertySet)106cdf0e10cSrcweir SwVbaFont::SwVbaFont( const uno::Reference< XHelperInterface >& xParent, const uno::Reference< uno::XComponentContext >& xContext, const uno::Reference< container::XIndexAccess >& xPalette, uno::Reference< css::beans::XPropertySet > xPropertySet ) throw ( css::uno::RuntimeException ) : SwVbaFont_BASE( xParent, xContext, xPalette, xPropertySet )
107cdf0e10cSrcweir {
108cdf0e10cSrcweir }
109cdf0e10cSrcweir 
110cdf0e10cSrcweir uno::Any SAL_CALL
getUnderline()111cdf0e10cSrcweir SwVbaFont::getUnderline() throw (uno::RuntimeException)
112cdf0e10cSrcweir {
113cdf0e10cSrcweir     sal_Int32 nOOVal = 0;
114cdf0e10cSrcweir     mxFont->getPropertyValue(  UnderLineMapper::propName() ) >>= nOOVal;
115cdf0e10cSrcweir     return uno::makeAny( UnderLineMapper::instance().getMSOFromOOO( nOOVal ) );
116cdf0e10cSrcweir }
117cdf0e10cSrcweir 
118cdf0e10cSrcweir void SAL_CALL
setUnderline(const uno::Any & _underline)119cdf0e10cSrcweir SwVbaFont::setUnderline( const uno::Any& _underline ) throw (uno::RuntimeException)
120cdf0e10cSrcweir {
121cdf0e10cSrcweir     sal_Int32 nMSOVal = 0;
122cdf0e10cSrcweir 
123cdf0e10cSrcweir     if ( _underline >>= nMSOVal )
124cdf0e10cSrcweir     {
125cdf0e10cSrcweir         sal_Int32 nOOVal =  UnderLineMapper::instance().getOOOFromMSO( nMSOVal );
126cdf0e10cSrcweir         mxFont->setPropertyValue(  UnderLineMapper::propName(), uno::makeAny( nOOVal ) );
127cdf0e10cSrcweir     }
128cdf0e10cSrcweir }
129cdf0e10cSrcweir 
130cdf0e10cSrcweir rtl::OUString&
getServiceImplName()131cdf0e10cSrcweir SwVbaFont::getServiceImplName()
132cdf0e10cSrcweir {
133cdf0e10cSrcweir         static rtl::OUString sImplName( RTL_CONSTASCII_USTRINGPARAM("SwVbaFont") );
134cdf0e10cSrcweir         return sImplName;
135cdf0e10cSrcweir }
136cdf0e10cSrcweir 
137cdf0e10cSrcweir void SAL_CALL
setColorIndex(const uno::Any & _colorindex)138cdf0e10cSrcweir SwVbaFont::setColorIndex( const uno::Any& _colorindex ) throw( uno::RuntimeException )
139cdf0e10cSrcweir {
140cdf0e10cSrcweir         sal_Int32 nIndex = 0;
141cdf0e10cSrcweir         _colorindex >>= nIndex;
142cdf0e10cSrcweir         return setColor( OORGBToXLRGB(mxPalette->getByIndex( nIndex )) );
143cdf0e10cSrcweir }
144cdf0e10cSrcweir 
145cdf0e10cSrcweir uno::Any SAL_CALL
getColorIndex()146cdf0e10cSrcweir SwVbaFont::getColorIndex() throw ( uno::RuntimeException )
147cdf0e10cSrcweir {
148cdf0e10cSrcweir     	sal_Int32 nColor = 0;
149cdf0e10cSrcweir 
150cdf0e10cSrcweir 	XLRGBToOORGB( getColor() ) >>= nColor;
151cdf0e10cSrcweir 	sal_Int32 nElems = mxPalette->getCount();
152cdf0e10cSrcweir 	sal_Int32 nIndex = 0;
153cdf0e10cSrcweir 	for ( sal_Int32 count=0; count<nElems; ++count )
154cdf0e10cSrcweir        	{
155cdf0e10cSrcweir 		sal_Int32 nPaletteColor = 0;
156cdf0e10cSrcweir 		mxPalette->getByIndex( count ) >>= nPaletteColor;
157cdf0e10cSrcweir 		if ( nPaletteColor == nColor )
158cdf0e10cSrcweir 		{
159cdf0e10cSrcweir 			nIndex = count;
160cdf0e10cSrcweir 			break;
161cdf0e10cSrcweir 		}
162cdf0e10cSrcweir 	}
163cdf0e10cSrcweir 	return uno::makeAny( nIndex );
164cdf0e10cSrcweir }
165cdf0e10cSrcweir uno::Any SAL_CALL
getSubscript()166cdf0e10cSrcweir SwVbaFont::getSubscript() throw ( uno::RuntimeException )
167cdf0e10cSrcweir {
168cdf0e10cSrcweir     sal_Bool bRes = sal_False;
169cdf0e10cSrcweir     SwVbaFont_BASE::getSubscript() >>= bRes;
170cdf0e10cSrcweir     if ( bRes )
171cdf0e10cSrcweir         return aLongAnyTrue;
172cdf0e10cSrcweir     return aLongAnyFalse;
173cdf0e10cSrcweir }
174cdf0e10cSrcweir 
175cdf0e10cSrcweir uno::Any SAL_CALL
getSuperscript()176cdf0e10cSrcweir SwVbaFont::getSuperscript() throw ( uno::RuntimeException )
177cdf0e10cSrcweir {
178cdf0e10cSrcweir     sal_Bool bRes = sal_False;
179cdf0e10cSrcweir     SwVbaFont_BASE::getSuperscript() >>= bRes;
180cdf0e10cSrcweir     if ( bRes )
181cdf0e10cSrcweir         return aLongAnyTrue;
182cdf0e10cSrcweir     return aLongAnyFalse;
183cdf0e10cSrcweir }
184cdf0e10cSrcweir 
185cdf0e10cSrcweir uno::Any SAL_CALL
getBold()186cdf0e10cSrcweir SwVbaFont::getBold() throw (uno::RuntimeException)
187cdf0e10cSrcweir {
188cdf0e10cSrcweir     sal_Bool bRes = sal_False;
189cdf0e10cSrcweir     SwVbaFont_BASE::getBold() >>= bRes;
190cdf0e10cSrcweir     if ( bRes )
191cdf0e10cSrcweir         return aLongAnyTrue;
192cdf0e10cSrcweir     return aLongAnyFalse;
193cdf0e10cSrcweir }
194cdf0e10cSrcweir 
195cdf0e10cSrcweir uno::Any SAL_CALL
getItalic()196cdf0e10cSrcweir SwVbaFont::getItalic() throw (uno::RuntimeException)
197cdf0e10cSrcweir {
198cdf0e10cSrcweir     sal_Bool bRes = sal_False;
199cdf0e10cSrcweir     SwVbaFont_BASE::getItalic() >>= bRes;
200cdf0e10cSrcweir     if ( bRes )
201cdf0e10cSrcweir         return aLongAnyTrue;
202cdf0e10cSrcweir     return aLongAnyFalse;
203cdf0e10cSrcweir }
204cdf0e10cSrcweir 
205cdf0e10cSrcweir uno::Any SAL_CALL
getStrikethrough()206cdf0e10cSrcweir SwVbaFont::getStrikethrough() throw (css::uno::RuntimeException)
207cdf0e10cSrcweir {
208cdf0e10cSrcweir     sal_Bool bRes = sal_False;
209cdf0e10cSrcweir     SwVbaFont_BASE::getStrikethrough() >>= bRes;
210cdf0e10cSrcweir     if ( bRes )
211cdf0e10cSrcweir         return aLongAnyTrue;
212cdf0e10cSrcweir     return aLongAnyFalse;
213cdf0e10cSrcweir }
214cdf0e10cSrcweir 
215cdf0e10cSrcweir uno::Any SAL_CALL
getShadow()216cdf0e10cSrcweir SwVbaFont::getShadow() throw (uno::RuntimeException)
217cdf0e10cSrcweir {
218cdf0e10cSrcweir     sal_Bool bRes = sal_False;
219cdf0e10cSrcweir     SwVbaFont_BASE::getShadow() >>= bRes;
220cdf0e10cSrcweir     if ( bRes )
221cdf0e10cSrcweir         return aLongAnyTrue;
222cdf0e10cSrcweir     return aLongAnyFalse;
223cdf0e10cSrcweir }
224cdf0e10cSrcweir 
225cdf0e10cSrcweir uno::Sequence< rtl::OUString >
getServiceNames()226cdf0e10cSrcweir SwVbaFont::getServiceNames()
227cdf0e10cSrcweir {
228cdf0e10cSrcweir         static uno::Sequence< rtl::OUString > aServiceNames;
229cdf0e10cSrcweir         if ( aServiceNames.getLength() == 0 )
230cdf0e10cSrcweir         {
231cdf0e10cSrcweir                 aServiceNames.realloc( 1 );
232cdf0e10cSrcweir                 aServiceNames[ 0 ] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.word.Font" ) );
233cdf0e10cSrcweir         }
234cdf0e10cSrcweir         return aServiceNames;
235cdf0e10cSrcweir }
236cdf0e10cSrcweir 
237cdf0e10cSrcweir 
238