xref: /aoo42x/main/sw/source/ui/vba/vbafont.cxx (revision cdf0e10c)
1*cdf0e10cSrcweir #include "vbafont.hxx"
2*cdf0e10cSrcweir #include <com/sun/star/awt/FontUnderline.hpp>
3*cdf0e10cSrcweir #include <ooo/vba/word/WdUnderline.hpp>
4*cdf0e10cSrcweir #include <hash_map>
5*cdf0e10cSrcweir #include <ooo/vba/word/WdColorIndex.hpp>
6*cdf0e10cSrcweir 
7*cdf0e10cSrcweir using namespace ::ooo::vba;
8*cdf0e10cSrcweir using namespace ::com::sun::star;
9*cdf0e10cSrcweir 
10*cdf0e10cSrcweir const uno::Any aLongAnyTrue( sal_Int16(-1) );
11*cdf0e10cSrcweir const uno::Any aLongAnyFalse( sal_Int16( 0 ) );
12*cdf0e10cSrcweir 
13*cdf0e10cSrcweir struct MapPair
14*cdf0e10cSrcweir {
15*cdf0e10cSrcweir     sal_Int32 nMSOConst;
16*cdf0e10cSrcweir     sal_Int32 nOOOConst;
17*cdf0e10cSrcweir };
18*cdf0e10cSrcweir 
19*cdf0e10cSrcweir static MapPair UnderLineTable[] = {
20*cdf0e10cSrcweir         { word::WdUnderline::wdUnderlineNone, com::sun::star::awt::FontUnderline::NONE },
21*cdf0e10cSrcweir         { word::WdUnderline::wdUnderlineSingle, com::sun::star::awt::FontUnderline::SINGLE },
22*cdf0e10cSrcweir         { word::WdUnderline::wdUnderlineWords, com::sun::star::awt::FontUnderline::SINGLE },
23*cdf0e10cSrcweir         { word::WdUnderline::wdUnderlineDouble, com::sun::star::awt::FontUnderline::DOUBLE },
24*cdf0e10cSrcweir         { word::WdUnderline::wdUnderlineDotted, com::sun::star::awt::FontUnderline::DOTTED },
25*cdf0e10cSrcweir         { word::WdUnderline::wdUnderlineThick, com::sun::star::awt::FontUnderline::BOLDDASH },
26*cdf0e10cSrcweir         { word::WdUnderline::wdUnderlineDash, com::sun::star::awt::FontUnderline::DASH },
27*cdf0e10cSrcweir 	{ word::WdUnderline::wdUnderlineDotDash, com::sun::star::awt::FontUnderline::DASHDOT },
28*cdf0e10cSrcweir 	{ word::WdUnderline::wdUnderlineDotDotDash, com::sun::star::awt::FontUnderline::DASHDOTDOT },
29*cdf0e10cSrcweir         { word::WdUnderline::wdUnderlineWavy, com::sun::star::awt::FontUnderline::WAVE },
30*cdf0e10cSrcweir         { word::WdUnderline::wdUnderlineDottedHeavy, com::sun::star::awt::FontUnderline::BOLDDOTTED },
31*cdf0e10cSrcweir         { word::WdUnderline::wdUnderlineDashHeavy, com::sun::star::awt::FontUnderline::BOLDDASH },
32*cdf0e10cSrcweir         { word::WdUnderline::wdUnderlineDotDashHeavy, com::sun::star::awt::FontUnderline::BOLDDASHDOT },
33*cdf0e10cSrcweir         { word::WdUnderline::wdUnderlineDotDotDashHeavy, com::sun::star::awt::FontUnderline::BOLDDASHDOTDOT },
34*cdf0e10cSrcweir         { word::WdUnderline::wdUnderlineWavyHeavy, com::sun::star::awt::FontUnderline::BOLDWAVE },
35*cdf0e10cSrcweir         { word::WdUnderline::wdUnderlineDashLong, com::sun::star::awt::FontUnderline::LONGDASH },
36*cdf0e10cSrcweir         { word::WdUnderline::wdUnderlineWavyDouble, com::sun::star::awt::FontUnderline::DOUBLEWAVE },
37*cdf0e10cSrcweir         { word::WdUnderline::wdUnderlineDashLongHeavy, com::sun::star::awt::FontUnderline::BOLDLONGDASH },
38*cdf0e10cSrcweir };
39*cdf0e10cSrcweir 
40*cdf0e10cSrcweir typedef std::hash_map< sal_Int32, sal_Int32 > ConstToConst;
41*cdf0e10cSrcweir class UnderLineMapper
42*cdf0e10cSrcweir {
43*cdf0e10cSrcweir     ConstToConst MSO2OOO;
44*cdf0e10cSrcweir     ConstToConst OOO2MSO;
45*cdf0e10cSrcweir private:
46*cdf0e10cSrcweir     UnderLineMapper()
47*cdf0e10cSrcweir     {
48*cdf0e10cSrcweir         sal_Int32 nLen = sizeof( UnderLineTable )/ sizeof( UnderLineTable[0] );
49*cdf0e10cSrcweir 
50*cdf0e10cSrcweir         for ( sal_Int32 index=0; index<nLen; ++index )
51*cdf0e10cSrcweir         {
52*cdf0e10cSrcweir             MSO2OOO[ UnderLineTable[ index ].nMSOConst ] = UnderLineTable[ index ].nOOOConst;
53*cdf0e10cSrcweir             OOO2MSO[ UnderLineTable[ index ].nOOOConst ] = UnderLineTable[ index ].nMSOConst;
54*cdf0e10cSrcweir         }
55*cdf0e10cSrcweir     }
56*cdf0e10cSrcweir public:
57*cdf0e10cSrcweir     static rtl::OUString propName()
58*cdf0e10cSrcweir     {
59*cdf0e10cSrcweir         static rtl::OUString sPropName( RTL_CONSTASCII_USTRINGPARAM("CharUnderline") );
60*cdf0e10cSrcweir         return sPropName;
61*cdf0e10cSrcweir     }
62*cdf0e10cSrcweir 
63*cdf0e10cSrcweir     static UnderLineMapper& instance()
64*cdf0e10cSrcweir     {
65*cdf0e10cSrcweir         static  UnderLineMapper theMapper;
66*cdf0e10cSrcweir         return theMapper;
67*cdf0e10cSrcweir     }
68*cdf0e10cSrcweir 
69*cdf0e10cSrcweir     sal_Int32 getOOOFromMSO( sal_Int32 nMSOConst ) throw( lang::IllegalArgumentException )
70*cdf0e10cSrcweir     {
71*cdf0e10cSrcweir         ConstToConst::iterator it = MSO2OOO.find( nMSOConst );
72*cdf0e10cSrcweir         if ( it == MSO2OOO.end() )
73*cdf0e10cSrcweir             throw lang::IllegalArgumentException();
74*cdf0e10cSrcweir         return it->second;
75*cdf0e10cSrcweir     }
76*cdf0e10cSrcweir     sal_Int32 getMSOFromOOO( sal_Int32 nOOOConst ) throw( lang::IllegalArgumentException )
77*cdf0e10cSrcweir     {
78*cdf0e10cSrcweir         ConstToConst::iterator it = OOO2MSO.find( nOOOConst );
79*cdf0e10cSrcweir         if ( it == OOO2MSO.end() )
80*cdf0e10cSrcweir             throw lang::IllegalArgumentException();
81*cdf0e10cSrcweir         return it->second;
82*cdf0e10cSrcweir     }
83*cdf0e10cSrcweir };
84*cdf0e10cSrcweir 
85*cdf0e10cSrcweir 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 )
86*cdf0e10cSrcweir {
87*cdf0e10cSrcweir }
88*cdf0e10cSrcweir 
89*cdf0e10cSrcweir uno::Any SAL_CALL
90*cdf0e10cSrcweir SwVbaFont::getUnderline() throw (uno::RuntimeException)
91*cdf0e10cSrcweir {
92*cdf0e10cSrcweir     sal_Int32 nOOVal = 0;
93*cdf0e10cSrcweir     mxFont->getPropertyValue(  UnderLineMapper::propName() ) >>= nOOVal;
94*cdf0e10cSrcweir     return uno::makeAny( UnderLineMapper::instance().getMSOFromOOO( nOOVal ) );
95*cdf0e10cSrcweir }
96*cdf0e10cSrcweir 
97*cdf0e10cSrcweir void SAL_CALL
98*cdf0e10cSrcweir SwVbaFont::setUnderline( const uno::Any& _underline ) throw (uno::RuntimeException)
99*cdf0e10cSrcweir {
100*cdf0e10cSrcweir     sal_Int32 nMSOVal = 0;
101*cdf0e10cSrcweir 
102*cdf0e10cSrcweir     if ( _underline >>= nMSOVal )
103*cdf0e10cSrcweir     {
104*cdf0e10cSrcweir         sal_Int32 nOOVal =  UnderLineMapper::instance().getOOOFromMSO( nMSOVal );
105*cdf0e10cSrcweir         mxFont->setPropertyValue(  UnderLineMapper::propName(), uno::makeAny( nOOVal ) );
106*cdf0e10cSrcweir     }
107*cdf0e10cSrcweir }
108*cdf0e10cSrcweir 
109*cdf0e10cSrcweir rtl::OUString&
110*cdf0e10cSrcweir SwVbaFont::getServiceImplName()
111*cdf0e10cSrcweir {
112*cdf0e10cSrcweir         static rtl::OUString sImplName( RTL_CONSTASCII_USTRINGPARAM("SwVbaFont") );
113*cdf0e10cSrcweir         return sImplName;
114*cdf0e10cSrcweir }
115*cdf0e10cSrcweir 
116*cdf0e10cSrcweir void SAL_CALL
117*cdf0e10cSrcweir SwVbaFont::setColorIndex( const uno::Any& _colorindex ) throw( uno::RuntimeException )
118*cdf0e10cSrcweir {
119*cdf0e10cSrcweir         sal_Int32 nIndex = 0;
120*cdf0e10cSrcweir         _colorindex >>= nIndex;
121*cdf0e10cSrcweir         return setColor( OORGBToXLRGB(mxPalette->getByIndex( nIndex )) );
122*cdf0e10cSrcweir }
123*cdf0e10cSrcweir 
124*cdf0e10cSrcweir uno::Any SAL_CALL
125*cdf0e10cSrcweir SwVbaFont::getColorIndex() throw ( uno::RuntimeException )
126*cdf0e10cSrcweir {
127*cdf0e10cSrcweir     	sal_Int32 nColor = 0;
128*cdf0e10cSrcweir 
129*cdf0e10cSrcweir 	XLRGBToOORGB( getColor() ) >>= nColor;
130*cdf0e10cSrcweir 	sal_Int32 nElems = mxPalette->getCount();
131*cdf0e10cSrcweir 	sal_Int32 nIndex = 0;
132*cdf0e10cSrcweir 	for ( sal_Int32 count=0; count<nElems; ++count )
133*cdf0e10cSrcweir        	{
134*cdf0e10cSrcweir 		sal_Int32 nPaletteColor = 0;
135*cdf0e10cSrcweir 		mxPalette->getByIndex( count ) >>= nPaletteColor;
136*cdf0e10cSrcweir 		if ( nPaletteColor == nColor )
137*cdf0e10cSrcweir 		{
138*cdf0e10cSrcweir 			nIndex = count;
139*cdf0e10cSrcweir 			break;
140*cdf0e10cSrcweir 		}
141*cdf0e10cSrcweir 	}
142*cdf0e10cSrcweir 	return uno::makeAny( nIndex );
143*cdf0e10cSrcweir }
144*cdf0e10cSrcweir uno::Any SAL_CALL
145*cdf0e10cSrcweir SwVbaFont::getSubscript() throw ( uno::RuntimeException )
146*cdf0e10cSrcweir {
147*cdf0e10cSrcweir     sal_Bool bRes = sal_False;
148*cdf0e10cSrcweir     SwVbaFont_BASE::getSubscript() >>= bRes;
149*cdf0e10cSrcweir     if ( bRes )
150*cdf0e10cSrcweir         return aLongAnyTrue;
151*cdf0e10cSrcweir     return aLongAnyFalse;
152*cdf0e10cSrcweir }
153*cdf0e10cSrcweir 
154*cdf0e10cSrcweir uno::Any SAL_CALL
155*cdf0e10cSrcweir SwVbaFont::getSuperscript() throw ( uno::RuntimeException )
156*cdf0e10cSrcweir {
157*cdf0e10cSrcweir     sal_Bool bRes = sal_False;
158*cdf0e10cSrcweir     SwVbaFont_BASE::getSuperscript() >>= bRes;
159*cdf0e10cSrcweir     if ( bRes )
160*cdf0e10cSrcweir         return aLongAnyTrue;
161*cdf0e10cSrcweir     return aLongAnyFalse;
162*cdf0e10cSrcweir }
163*cdf0e10cSrcweir 
164*cdf0e10cSrcweir uno::Any SAL_CALL
165*cdf0e10cSrcweir SwVbaFont::getBold() throw (uno::RuntimeException)
166*cdf0e10cSrcweir {
167*cdf0e10cSrcweir     sal_Bool bRes = sal_False;
168*cdf0e10cSrcweir     SwVbaFont_BASE::getBold() >>= bRes;
169*cdf0e10cSrcweir     if ( bRes )
170*cdf0e10cSrcweir         return aLongAnyTrue;
171*cdf0e10cSrcweir     return aLongAnyFalse;
172*cdf0e10cSrcweir }
173*cdf0e10cSrcweir 
174*cdf0e10cSrcweir uno::Any SAL_CALL
175*cdf0e10cSrcweir SwVbaFont::getItalic() throw (uno::RuntimeException)
176*cdf0e10cSrcweir {
177*cdf0e10cSrcweir     sal_Bool bRes = sal_False;
178*cdf0e10cSrcweir     SwVbaFont_BASE::getItalic() >>= bRes;
179*cdf0e10cSrcweir     if ( bRes )
180*cdf0e10cSrcweir         return aLongAnyTrue;
181*cdf0e10cSrcweir     return aLongAnyFalse;
182*cdf0e10cSrcweir }
183*cdf0e10cSrcweir 
184*cdf0e10cSrcweir uno::Any SAL_CALL
185*cdf0e10cSrcweir SwVbaFont::getStrikethrough() throw (css::uno::RuntimeException)
186*cdf0e10cSrcweir {
187*cdf0e10cSrcweir     sal_Bool bRes = sal_False;
188*cdf0e10cSrcweir     SwVbaFont_BASE::getStrikethrough() >>= bRes;
189*cdf0e10cSrcweir     if ( bRes )
190*cdf0e10cSrcweir         return aLongAnyTrue;
191*cdf0e10cSrcweir     return aLongAnyFalse;
192*cdf0e10cSrcweir }
193*cdf0e10cSrcweir 
194*cdf0e10cSrcweir uno::Any SAL_CALL
195*cdf0e10cSrcweir SwVbaFont::getShadow() throw (uno::RuntimeException)
196*cdf0e10cSrcweir {
197*cdf0e10cSrcweir     sal_Bool bRes = sal_False;
198*cdf0e10cSrcweir     SwVbaFont_BASE::getShadow() >>= bRes;
199*cdf0e10cSrcweir     if ( bRes )
200*cdf0e10cSrcweir         return aLongAnyTrue;
201*cdf0e10cSrcweir     return aLongAnyFalse;
202*cdf0e10cSrcweir }
203*cdf0e10cSrcweir 
204*cdf0e10cSrcweir uno::Sequence< rtl::OUString >
205*cdf0e10cSrcweir SwVbaFont::getServiceNames()
206*cdf0e10cSrcweir {
207*cdf0e10cSrcweir         static uno::Sequence< rtl::OUString > aServiceNames;
208*cdf0e10cSrcweir         if ( aServiceNames.getLength() == 0 )
209*cdf0e10cSrcweir         {
210*cdf0e10cSrcweir                 aServiceNames.realloc( 1 );
211*cdf0e10cSrcweir                 aServiceNames[ 0 ] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.word.Font" ) );
212*cdf0e10cSrcweir         }
213*cdf0e10cSrcweir         return aServiceNames;
214*cdf0e10cSrcweir }
215*cdf0e10cSrcweir 
216*cdf0e10cSrcweir 
217