xref: /aoo41x/main/sc/source/ui/vba/vbaformat.cxx (revision cdf0e10c)
1 /*************************************************************************
2  *
3  * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
4  *
5  * Copyright 2000, 2010 Oracle and/or its affiliates.
6  *
7  * OpenOffice.org - a multi-platform office productivity suite
8  *
9  * This file is part of OpenOffice.org.
10  *
11  * OpenOffice.org is free software: you can redistribute it and/or modify
12  * it under the terms of the GNU Lesser General Public License version 3
13  * only, as published by the Free Software Foundation.
14  *
15  * OpenOffice.org is distributed in the hope that it will be useful,
16  * but WITHOUT ANY WARRANTY; without even the implied warranty of
17  * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
18  * GNU Lesser General Public License version 3 for more details
19  * (a copy is included in the LICENSE file that accompanied this code).
20  *
21  * You should have received a copy of the GNU Lesser General Public License
22  * version 3 along with OpenOffice.org.  If not, see
23  * <http://www.openoffice.org/license.html>
24  * for a copy of the LGPLv3 License.
25  *
26  ************************************************************************/
27 #include "vbaformat.hxx"
28 #include <ooo/vba/excel/XStyle.hpp>
29 #include <ooo/vba/excel/XlVAlign.hpp>
30 #include <ooo/vba/excel/XlHAlign.hpp>
31 #include <ooo/vba/excel/XlOrientation.hpp>
32 #include <ooo/vba/excel/Constants.hpp>
33 #include <ooo/vba/excel/XRange.hpp>
34 #include <com/sun/star/table/CellVertJustify.hpp>
35 #include <com/sun/star/table/CellHoriJustify.hpp>
36 #include <com/sun/star/table/CellOrientation.hpp>
37 #include <com/sun/star/table/XCellRange.hpp>
38 #include <com/sun/star/text/WritingMode.hpp>
39 #include <com/sun/star/util/CellProtection.hpp>
40 
41 #include <rtl/math.hxx>
42 
43 #include "excelvbahelper.hxx"
44 #include "vbaborders.hxx"
45 #include "vbapalette.hxx"
46 #include "vbafont.hxx"
47 #include "vbainterior.hxx"
48 
49 #include <unonames.hxx>
50 #include <cellsuno.hxx>
51 #include <scitems.hxx>
52 #include <attrib.hxx>
53 
54 using namespace ::ooo::vba;
55 using namespace ::com::sun::star;
56 
57 #define FORMATSTRING "FormatString"
58 #define LOCALE "Locale"
59 
60 template< typename Ifc1 >
61 ScVbaFormat< Ifc1 >::ScVbaFormat( const uno::Reference< XHelperInterface >& xParent, const uno::Reference< uno::XComponentContext > & xContext, const uno::Reference< beans::XPropertySet >& _xPropertySet, const uno::Reference< frame::XModel >& xModel, bool bCheckAmbiguoity ) throw ( script::BasicErrorException ) : ScVbaFormat_BASE( xParent, xContext ), m_aDefaultLocale( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("en") ), rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "US") ), rtl::OUString() ), mxPropertySet( _xPropertySet ), mxModel( xModel ), mbCheckAmbiguoity( bCheckAmbiguoity ), mbAddIndent( sal_False )
62 {
63 	try
64 	{
65 		if ( !mxModel.is() )
66 			DebugHelper::exception(SbERR_METHOD_FAILED, rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "XModel Interface could not be retrieved") ) );
67         // mxServiceInfo is unused,
68         // mxNumberFormatsSupplier is initialized when needed in initializeNumberFormats.
69 	}
70 	catch (uno::Exception& )
71 	{
72 		DebugHelper::exception(SbERR_METHOD_FAILED, rtl::OUString() );
73 	}
74 }
75 
76 template< typename Ifc1 >
77 void SAL_CALL
78 ScVbaFormat<Ifc1>::setVerticalAlignment( const uno::Any& _oAlignment)   throw (script::BasicErrorException, uno::RuntimeException)
79 {
80 	try
81 	{
82 		uno::Any aVal;
83 		sal_Int32 nAlignment = 0;
84 		if ( !(_oAlignment >>= nAlignment ))
85 			throw uno::RuntimeException();
86 		switch (nAlignment)
87 		{
88 			case excel::XlVAlign::xlVAlignBottom :
89 				aVal =  uno::makeAny( table::CellVertJustify_BOTTOM );
90 				break;
91 			case excel::XlVAlign::xlVAlignCenter :
92 				aVal = uno::makeAny( table::CellVertJustify_CENTER );
93 				break;
94 			case excel::XlVAlign::xlVAlignDistributed:
95 			case excel::XlVAlign::xlVAlignJustify:
96 				aVal = uno::makeAny( table::CellVertJustify_STANDARD );
97 				break;
98 
99 			case excel::XlVAlign::xlVAlignTop:
100 				aVal = uno::makeAny( table::CellVertJustify_TOP);
101 				break;
102 			default:
103 				aVal = uno::makeAny( table::CellVertJustify_STANDARD );
104 				break;
105 		}
106 		mxPropertySet->setPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( SC_UNONAME_CELLVJUS ) ), aVal );
107 	}
108 	catch (uno::Exception& )
109 	{
110 		DebugHelper::exception(SbERR_METHOD_FAILED, rtl::OUString());
111 	}
112 }
113 
114 template< typename Ifc1 >
115 uno::Any SAL_CALL
116 ScVbaFormat<Ifc1>::getVerticalAlignment(  ) throw (script::BasicErrorException, uno::RuntimeException)
117 {
118 	uno::Any aResult = aNULL();
119 	try
120 	{
121 		if (!isAmbiguous( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( SC_UNONAME_CELLVJUS ) ) ) )
122 		{
123 			table::CellVertJustify aAPIAlignment;
124 			mxPropertySet->getPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( SC_UNONAME_CELLVJUS ) ) ) >>= aAPIAlignment;
125 			switch( aAPIAlignment )
126 			{
127 				case table::CellVertJustify_BOTTOM:
128 					aResult = uno::makeAny( excel::XlVAlign::xlVAlignBottom );
129 					break;
130 				case table::CellVertJustify_CENTER:
131 					aResult = uno::makeAny( excel::XlVAlign::xlVAlignCenter );
132 					break;
133 				case table::CellVertJustify_STANDARD:
134 					aResult = uno::makeAny( excel::XlVAlign::xlVAlignBottom );
135 					break;
136 				case table::CellVertJustify_TOP:
137 					aResult = uno::makeAny( excel::XlVAlign::xlVAlignTop );
138 					break;
139 				default:
140 					break;
141 			}
142 		}
143 	}
144 	catch (uno::Exception& )
145 	{
146 		DebugHelper::exception(SbERR_METHOD_FAILED, rtl::OUString());
147 	}
148 	return aResult;
149 }
150 
151 template< typename Ifc1 >
152 void SAL_CALL
153 ScVbaFormat<Ifc1>::setHorizontalAlignment( const uno::Any& HorizontalAlignment ) throw (script::BasicErrorException, uno::RuntimeException)
154 {
155 	try
156 	{
157 		uno::Any aVal;
158 		sal_Int32 nAlignment = 0;
159 		if ( !( HorizontalAlignment >>= nAlignment ) )
160 			throw uno::RuntimeException();
161 		switch ( nAlignment )
162 		{
163 			case excel::XlHAlign::xlHAlignJustify:
164 				aVal = uno::makeAny( table::CellHoriJustify_BLOCK);
165 				break;
166 			case excel::XlHAlign::xlHAlignCenter:
167 				aVal = uno::makeAny( table::CellHoriJustify_CENTER );
168 				break;
169 			case excel::XlHAlign::xlHAlignDistributed:
170 				aVal = uno::makeAny( table::CellHoriJustify_BLOCK);
171 				break;
172 			case excel::XlHAlign::xlHAlignLeft:
173 				aVal = uno::makeAny( table::CellHoriJustify_LEFT);
174 				break;
175 			case excel::XlHAlign::xlHAlignRight:
176 				aVal = uno::makeAny( table::CellHoriJustify_RIGHT);
177 				break;
178 		}
179 		// #FIXME what about the default case above?
180 		// shouldn't need the test below
181 		if ( aVal.hasValue() )
182 			mxPropertySet->setPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( SC_UNONAME_CELLHJUS ) ), aVal );
183 	}
184 	catch (uno::Exception& )
185 	{
186 		DebugHelper::exception(SbERR_METHOD_FAILED, rtl::OUString() );
187 	}
188 
189 }
190 
191 template< typename Ifc1 >
192 uno::Any SAL_CALL
193 ScVbaFormat<Ifc1>::getHorizontalAlignment(  ) throw (script::BasicErrorException, uno::RuntimeException)
194 {
195 	uno::Any NRetAlignment = aNULL();
196 	try
197 	{
198 		rtl::OUString sHoriJust( RTL_CONSTASCII_USTRINGPARAM( SC_UNONAME_CELLHJUS ) );
199 		if (!isAmbiguous(sHoriJust))
200 		{
201 			table::CellHoriJustify aAPIAlignment = table::CellHoriJustify_BLOCK;
202 
203 			if ( mxPropertySet->getPropertyValue(sHoriJust) >>= aAPIAlignment )
204 			{
205 				switch( aAPIAlignment )
206 				{
207 					case table::CellHoriJustify_BLOCK:
208 						NRetAlignment = uno::makeAny( excel::XlHAlign::xlHAlignJustify );
209 						break;
210 					case table::CellHoriJustify_CENTER:
211 						NRetAlignment = uno::makeAny( excel::XlHAlign::xlHAlignCenter );
212 						break;
213 					case table::CellHoriJustify_LEFT:
214 						NRetAlignment = uno::makeAny( excel::XlHAlign::xlHAlignLeft );
215 						break;
216 					case table::CellHoriJustify_RIGHT:
217 						NRetAlignment =  uno::makeAny( excel::XlHAlign::xlHAlignRight );
218 						break;
219 					 default: // handle those other cases with a NULL return
220 						break;
221 				}
222 			}
223 		}
224 	}
225 	catch (uno::Exception& )
226 	{
227 		DebugHelper::exception(SbERR_METHOD_FAILED, rtl::OUString() );
228 	}
229 	return NRetAlignment;
230 }
231 
232 template< typename Ifc1 >
233 void SAL_CALL
234 ScVbaFormat<Ifc1>::setOrientation( const uno::Any& _aOrientation ) throw (script::BasicErrorException, uno::RuntimeException)
235 {
236 	try
237 	{
238 		sal_Int32 nOrientation = 0;
239 		if ( !( _aOrientation >>= nOrientation ) )
240 			throw uno::RuntimeException();
241 		uno::Any aVal;
242 		switch( nOrientation )
243 		{
244 			case excel::XlOrientation::xlDownward:
245 				aVal = uno::makeAny( table::CellOrientation_TOPBOTTOM);
246 				break;
247 			case excel::XlOrientation::xlHorizontal:
248 				aVal = uno::makeAny( table::CellOrientation_STANDARD );
249 				mxPropertySet->setPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( SC_UNONAME_ROTANG ) ), uno::makeAny( sal_Int32(0) ) );
250 				break;
251 			case excel::XlOrientation::xlUpward:
252 				aVal = uno::makeAny( table::CellOrientation_BOTTOMTOP);
253 				break;
254 			case excel::XlOrientation::xlVertical:
255 				aVal = uno::makeAny( table::CellOrientation_STACKED);
256 				break;
257 		}
258 		// #FIXME what about the default case above?
259 		// shouldn't need the test below
260 		if ( aVal.hasValue() )
261 			mxPropertySet->setPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( SC_UNONAME_CELLORI ) ), aVal );
262 
263 	}
264 	catch (uno::Exception& )
265 	{
266 		DebugHelper::exception(SbERR_METHOD_FAILED, rtl::OUString() );
267 	}
268 }
269 template< typename Ifc1 >
270 uno::Any SAL_CALL
271 ScVbaFormat<Ifc1>::getOrientation(  ) throw (script::BasicErrorException, uno::RuntimeException)
272 {
273 	uno::Any NRetOrientation = aNULL();
274 	try
275 	{
276 		if (!isAmbiguous(rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( SC_UNONAME_CELLORI ) )))
277 		{
278 			table::CellOrientation aOrientation = table::CellOrientation_STANDARD;
279 			if ( !(  mxPropertySet->getPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( SC_UNONAME_CELLORI ) ) ) >>= aOrientation ) )
280 				throw uno::RuntimeException();
281 
282 			switch(aOrientation)
283 			{
284 				case table::CellOrientation_STANDARD:
285 					NRetOrientation = uno::makeAny( excel::XlOrientation::xlHorizontal );
286 					break;
287 				case table::CellOrientation_BOTTOMTOP:
288 					NRetOrientation = uno::makeAny( excel::XlOrientation::xlUpward );
289 					break;
290 				case table::CellOrientation_TOPBOTTOM:
291 					NRetOrientation = uno::makeAny( excel::XlOrientation::xlDownward );
292 					break;
293 				case table::CellOrientation_STACKED:
294 					NRetOrientation = uno::makeAny( excel::XlOrientation::xlVertical );
295 					break;
296 				default:
297 					NRetOrientation = uno::makeAny( excel::XlOrientation::xlHorizontal );
298 			}
299 		}
300 	}
301 	catch (uno::Exception& )
302 	{
303 		DebugHelper::exception(SbERR_METHOD_FAILED, rtl::OUString());
304 	}
305 	return NRetOrientation;
306 }
307 
308 template< typename Ifc1 >
309 void SAL_CALL
310 ScVbaFormat<Ifc1>::setWrapText( const uno::Any& _aWrapText ) throw (script::BasicErrorException, uno::RuntimeException)
311 {
312 	try
313 	{
314 		mxPropertySet->setPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( SC_UNONAME_WRAP ) ), _aWrapText);
315 	}
316 	catch (uno::Exception& )
317 	{
318 		DebugHelper::exception(SbERR_METHOD_FAILED, rtl::OUString() );
319 	}
320 }
321 
322 template< typename Ifc1 >
323 uno::Any SAL_CALL
324 ScVbaFormat<Ifc1>::getWrapText(  ) throw (script::BasicErrorException, uno::RuntimeException)
325 {
326 	uno::Any aWrap = aNULL();
327 	try
328 	{
329 		rtl::OUString aPropName( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( SC_UNONAME_WRAP ) ) );
330 		if (!isAmbiguous( aPropName ))
331 		{
332 			aWrap = mxPropertySet->getPropertyValue(aPropName);
333 		}
334 	}
335 	catch (uno::Exception& )
336 	{
337 		DebugHelper::exception(SbERR_METHOD_FAILED, rtl::OUString() );
338 	}
339 	return aWrap;
340 }
341 
342 template< typename Ifc1 >
343 uno::Any SAL_CALL
344 ScVbaFormat<Ifc1>::Borders( const uno::Any& Index ) throw (script::BasicErrorException, uno::RuntimeException )
345 {
346 	ScVbaPalette aPalette( excel::getDocShell( mxModel ) );
347 	uno::Reference< XCollection > xColl =  new ScVbaBorders( thisHelperIface(), ScVbaFormat_BASE::mxContext, uno::Reference< table::XCellRange >( mxPropertySet, uno::UNO_QUERY_THROW ), aPalette );
348 
349 	if ( Index.hasValue() )
350 	{
351 		return xColl->Item( Index, uno::Any() );
352 	}
353 	return uno::makeAny( xColl );
354 }
355 
356 template< typename Ifc1 >
357 uno::Reference< excel::XFont > SAL_CALL
358 ScVbaFormat<Ifc1>::Font(  ) throw (script::BasicErrorException, uno::RuntimeException)
359 {
360 	ScVbaPalette aPalette( excel::getDocShell( mxModel ) );
361 	return new ScVbaFont( thisHelperIface(), ScVbaFormat_BASE::mxContext, aPalette, mxPropertySet );
362 }
363 
364 template< typename Ifc1 >
365 uno::Reference< excel::XInterior > SAL_CALL
366 ScVbaFormat<Ifc1>::Interior(  ) throw (script::BasicErrorException, uno::RuntimeException)
367 {
368 	return new ScVbaInterior( thisHelperIface(), ScVbaFormat_BASE::mxContext, mxPropertySet );
369 }
370 
371 template< typename Ifc1 >
372 uno::Any SAL_CALL
373 ScVbaFormat<Ifc1>::getNumberFormatLocal(  ) throw (script::BasicErrorException, uno::RuntimeException)
374 {
375 	uno::Any aRet = uno::makeAny( rtl::OUString() );
376 	try
377 	{
378 		rtl::OUString sPropName( RTL_CONSTASCII_USTRINGPARAM( SC_UNO_NUMBERFO ) );
379 		if (!isAmbiguous( sPropName ))
380 		{
381 
382 			initializeNumberFormats();
383 
384 			sal_Int32 nFormat = 0;
385 			if ( ! (mxPropertySet->getPropertyValue( sPropName ) >>= nFormat ) )
386 				throw uno::RuntimeException();
387 
388 			rtl::OUString sFormat;
389 			xNumberFormats->getByKey(nFormat)->getPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( FORMATSTRING ))) >>= sFormat;
390 			aRet = uno::makeAny( sFormat.toAsciiLowerCase() );
391 
392 		}
393 	}
394 	catch (uno::Exception& )
395 	{
396 		DebugHelper::exception(SbERR_METHOD_FAILED, rtl::OUString());
397 	}
398 	return aRet;
399 
400 }
401 
402 template< typename Ifc1 >
403 void
404 ScVbaFormat<Ifc1>::setNumberFormat( lang::Locale _aLocale, const rtl::OUString& _sFormatString) throw( script::BasicErrorException )
405 {
406 	try
407 	{
408 		initializeNumberFormats();
409 		sal_Int32 nFormat = xNumberFormats->queryKey(_sFormatString, _aLocale , sal_True);
410 		if (nFormat == -1)
411 		{
412 			xNumberFormats->addNew(_sFormatString, _aLocale);
413 		}
414 		mxPropertySet->setPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( SC_UNO_NUMBERFO ) ), uno::makeAny( nFormat ) );
415 	}
416 	catch (uno::Exception& )
417 	{
418 		DebugHelper::exception(SbERR_METHOD_FAILED, rtl::OUString());
419 	}
420 }
421 
422 template< typename Ifc1 >
423 void SAL_CALL
424 ScVbaFormat<Ifc1>::setNumberFormatLocal( const uno::Any& _oLocalFormatString ) throw (script::BasicErrorException, uno::RuntimeException)
425 {
426 	try
427 	{
428 		rtl::OUString sLocalFormatString;
429 		sal_Int32 nFormat = -1;
430 		rtl::OUString sNumFormat( RTL_CONSTASCII_USTRINGPARAM( SC_UNO_NUMBERFO ) );
431 		if ( !(_oLocalFormatString >>= sLocalFormatString )
432 		|| !( mxPropertySet->getPropertyValue(sNumFormat) >>= nFormat ) )
433 			throw uno::RuntimeException();
434 
435 		sLocalFormatString = sLocalFormatString.toAsciiUpperCase();
436 		initializeNumberFormats();
437 		lang::Locale aRangeLocale;
438 		xNumberFormats->getByKey(nFormat)->getPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( LOCALE ) ) ) >>= aRangeLocale;
439 		sal_Int32 nNewFormat = xNumberFormats->queryKey(sLocalFormatString, aRangeLocale, sal_True);
440 
441 		if (nNewFormat == -1)
442 			nNewFormat = xNumberFormats->addNew(sLocalFormatString, aRangeLocale);
443 		mxPropertySet->setPropertyValue(sNumFormat, uno::makeAny( nNewFormat ));
444 	}
445 	catch (uno::Exception& )
446 	{
447 		DebugHelper::exception(SbERR_METHOD_FAILED, rtl::OUString() );
448 	}
449 }
450 
451 template< typename Ifc1 >
452 void SAL_CALL
453 ScVbaFormat<Ifc1>::setNumberFormat( const uno::Any& _oFormatString ) throw (script::BasicErrorException, uno::RuntimeException)
454 {
455 	try
456 	{
457 		rtl::OUString sFormatString;
458 		if ( !( _oFormatString >>= sFormatString ) )
459 			throw uno::RuntimeException();
460 
461 		sFormatString = sFormatString.toAsciiUpperCase();
462 
463 		lang::Locale aDefaultLocale = m_aDefaultLocale;
464 		initializeNumberFormats();
465 		sal_Int32 nFormat = xNumberFormats->queryKey(sFormatString, aDefaultLocale, sal_True);
466 
467 		if (nFormat == -1)
468 			nFormat = xNumberFormats->addNew(sFormatString, aDefaultLocale);
469 
470 		lang::Locale aRangeLocale;
471 		xNumberFormats->getByKey(nFormat)->getPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( LOCALE ) ) ) >>= aRangeLocale;
472 		sal_Int32 nNewFormat = xNumberFormatTypes->getFormatForLocale(nFormat, aRangeLocale);
473 		mxPropertySet->setPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( SC_UNO_NUMBERFO ) ), uno::makeAny( nNewFormat));
474 	}
475 	catch (uno::Exception& )
476 	{
477 		DebugHelper::exception(SbERR_METHOD_FAILED, rtl::OUString());
478 	}
479 
480 }
481 
482 template< typename Ifc1 >
483 void SAL_CALL
484 ScVbaFormat<Ifc1>::setIndentLevel( const uno::Any& _aLevel ) throw (script::BasicErrorException, uno::RuntimeException)
485 {
486 	try
487 	{
488 		sal_Int32 nLevel = 0;
489 		if ( !(_aLevel >>= nLevel ) )
490 			throw uno::RuntimeException();
491 		table::CellHoriJustify aAPIAlignment = table::CellHoriJustify_STANDARD;
492 
493 		rtl::OUString sHoriJust( RTL_CONSTASCII_USTRINGPARAM( SC_UNONAME_CELLHJUS ) );
494 		if ( !( mxPropertySet->getPropertyValue(sHoriJust) >>= aAPIAlignment ) )
495 			throw uno::RuntimeException();
496 		if (aAPIAlignment == table::CellHoriJustify_STANDARD)
497 			mxPropertySet->setPropertyValue( sHoriJust, uno::makeAny( table::CellHoriJustify_LEFT) ) ;
498 		mxPropertySet->setPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( SC_UNONAME_PINDENT ) ), uno::makeAny( sal_Int16(nLevel * 352.8) ) );
499 	}
500 	catch (uno::Exception& )
501 	{
502 		DebugHelper::exception(SbERR_METHOD_FAILED, rtl::OUString());
503 	}
504 }
505 
506 template< typename Ifc1 >
507 uno::Any SAL_CALL
508 ScVbaFormat<Ifc1>::getIndentLevel(  ) throw (script::BasicErrorException, uno::RuntimeException)
509 {
510 	uno::Any NRetIndentLevel = aNULL();
511 	try
512 	{
513 		rtl::OUString sParaIndent( RTL_CONSTASCII_USTRINGPARAM( SC_UNONAME_PINDENT ) );
514 		if (!isAmbiguous(sParaIndent))
515 		{
516 			sal_Int16 IndentLevel = 0;
517 			if ( ( mxPropertySet->getPropertyValue(sParaIndent) >>= IndentLevel  ) )
518 				NRetIndentLevel = uno::makeAny( sal_Int32( rtl::math::round(static_cast<double>( IndentLevel ) / 352.8)) );
519 			else
520 				NRetIndentLevel = uno::makeAny( sal_Int32(0) );
521 		}
522 	}
523 	catch (uno::Exception& )
524 	{
525 		DebugHelper::exception(SbERR_METHOD_FAILED, rtl::OUString());
526 	}
527 	return NRetIndentLevel;
528 }
529 
530 template< typename Ifc1 >
531 void SAL_CALL
532 ScVbaFormat<Ifc1>::setLocked( const uno::Any& _aLocked ) throw (script::BasicErrorException, uno::RuntimeException)
533 {
534 	try
535 	{
536 		sal_Bool bIsLocked = sal_False;
537 		if ( !( _aLocked >>= bIsLocked ) )
538 			throw uno::RuntimeException();
539 		util::CellProtection aCellProtection;
540 		rtl::OUString sCellProt( RTL_CONSTASCII_USTRINGPARAM( SC_UNONAME_CELLPRO ) );
541 		mxPropertySet->getPropertyValue(sCellProt) >>= aCellProtection;
542 		aCellProtection.IsLocked = bIsLocked;
543 		mxPropertySet->setPropertyValue(sCellProt, uno::makeAny( aCellProtection ) );
544 	}
545 	catch (uno::Exception& )
546 	{
547 		DebugHelper::exception(SbERR_METHOD_FAILED, rtl::OUString() );
548 	}
549 }
550 
551 template< typename Ifc1 >
552 void SAL_CALL
553 ScVbaFormat<Ifc1>::setFormulaHidden( const uno::Any& FormulaHidden ) throw (script::BasicErrorException, uno::RuntimeException)
554 {
555 	try
556 	{
557 		sal_Bool bIsFormulaHidden = sal_False;
558 		FormulaHidden >>= bIsFormulaHidden;
559 		util::CellProtection aCellProtection;
560 		rtl::OUString sCellProt( RTL_CONSTASCII_USTRINGPARAM( SC_UNONAME_CELLPRO ) );
561 		mxPropertySet->getPropertyValue(sCellProt) >>= aCellProtection;
562 		aCellProtection.IsFormulaHidden = bIsFormulaHidden;
563 		mxPropertySet->setPropertyValue(sCellProt,uno::makeAny(aCellProtection));
564 	}
565 	catch (uno::Exception& )
566 	{
567 		DebugHelper::exception( SbERR_METHOD_FAILED, rtl::OUString() );
568 	}
569 }
570 
571 template< typename Ifc1 >
572 uno::Any SAL_CALL
573 ScVbaFormat<Ifc1>::getLocked(  ) throw (script::BasicErrorException, uno::RuntimeException)
574 {
575 	uno::Any aCellProtection = aNULL();
576 	try
577 	{
578 		rtl::OUString sCellProt( RTL_CONSTASCII_USTRINGPARAM( SC_UNONAME_CELLPRO ) );
579 
580 		if (!isAmbiguous(sCellProt))
581 		{
582 			SfxItemSet* pDataSet = getCurrentDataSet();
583 			if ( pDataSet )
584 			{
585 				const ScProtectionAttr& rProtAttr = (const ScProtectionAttr &) pDataSet->Get(ATTR_PROTECTION, sal_True);
586 				SfxItemState eState = pDataSet->GetItemState(ATTR_PROTECTION, sal_True, NULL);
587 				if(eState != SFX_ITEM_DONTCARE)
588 					aCellProtection =  uno::makeAny(rProtAttr.GetProtection());
589 			}
590 			else // fallback to propertyset
591 			{
592 				util::CellProtection cellProtection;
593 				mxPropertySet->getPropertyValue(sCellProt) >>= aCellProtection;
594 				aCellProtection = uno::makeAny( cellProtection.IsLocked );
595 			}
596 		}
597 	}
598 	catch (uno::Exception& )
599 	{
600 		DebugHelper::exception(SbERR_METHOD_FAILED, rtl::OUString());
601 	}
602 	return aCellProtection;
603 }
604 
605 template< typename Ifc1 >
606 uno::Any SAL_CALL
607 ScVbaFormat<Ifc1>::getFormulaHidden(  ) throw (script::BasicErrorException, uno::RuntimeException)
608 {
609 	uno::Any aBoolRet = aNULL();
610 	try
611 	{
612 		rtl::OUString sCellProt( RTL_CONSTASCII_USTRINGPARAM( SC_UNONAME_CELLPRO ) );
613 		if (!isAmbiguous(sCellProt))
614 		{
615 			SfxItemSet* pDataSet = getCurrentDataSet();
616 			if ( pDataSet )
617 			{
618 				const ScProtectionAttr& rProtAttr = (const ScProtectionAttr &) pDataSet->Get(ATTR_PROTECTION, sal_True);
619 				SfxItemState eState = pDataSet->GetItemState(ATTR_PROTECTION, sal_True, NULL);
620 				if(eState != SFX_ITEM_DONTCARE)
621 					aBoolRet = uno::makeAny(rProtAttr.GetHideFormula());
622 			}
623 			else
624 			{
625 				util::CellProtection aCellProtection;
626 				mxPropertySet->getPropertyValue(sCellProt) >>= aCellProtection;
627 				aBoolRet = uno::makeAny( aCellProtection.IsFormulaHidden );
628 			}
629 		}
630 	}
631 	catch (uno::Exception e)
632 	{
633 		DebugHelper::exception(SbERR_METHOD_FAILED, rtl::OUString());
634 	}
635 	return aBoolRet;
636 }
637 
638 template< typename Ifc1 >
639 void SAL_CALL
640 ScVbaFormat<Ifc1>::setShrinkToFit( const uno::Any& ShrinkToFit ) throw (script::BasicErrorException, uno::RuntimeException)
641 {
642 	try
643 	{
644 		mxPropertySet->setPropertyValue(rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( SC_UNONAME_SHRINK_TO_FIT ) ), ShrinkToFit);
645 	}
646 	catch (uno::Exception& )
647 	{
648 		DebugHelper::exception(SbERR_NOT_IMPLEMENTED, rtl::OUString() );
649 	}
650 
651 }
652 
653 template< typename Ifc1 >
654 uno::Any SAL_CALL
655 ScVbaFormat<Ifc1>::getShrinkToFit(  ) throw (script::BasicErrorException, uno::RuntimeException)
656 {
657 	uno::Any aRet = aNULL();
658 	try
659 	{
660 		rtl::OUString sShrinkToFit( RTL_CONSTASCII_USTRINGPARAM( SC_UNONAME_SHRINK_TO_FIT ) );
661 		if (!isAmbiguous(sShrinkToFit))
662 			aRet = mxPropertySet->getPropertyValue(sShrinkToFit);
663 	}
664 	catch (uno::Exception& )
665 	{
666 		DebugHelper::exception(SbERR_NOT_IMPLEMENTED, rtl::OUString());
667 	}
668 	return aRet;
669 }
670 
671 template< typename Ifc1 >
672 void SAL_CALL
673 ScVbaFormat<Ifc1>::setReadingOrder( const uno::Any& ReadingOrder ) throw (script::BasicErrorException, uno::RuntimeException)
674 {
675 	try
676 	{
677 		sal_Int32 nReadingOrder = 0;
678 		if ( !(ReadingOrder >>= nReadingOrder ))
679 			throw uno::RuntimeException();
680 		uno::Any aVal;
681 		switch(nReadingOrder)
682 		{
683 			case excel::Constants::xlLTR:
684 				aVal = uno::makeAny( text::WritingMode_LR_TB );
685 				break;
686 			case excel::Constants::xlRTL:
687 				aVal = uno::makeAny( text::WritingMode_RL_TB );
688 				break;
689 			case excel::Constants::xlContext:
690 				DebugHelper::exception(SbERR_NOT_IMPLEMENTED, rtl::OUString());
691 				break;
692 			default:
693 				DebugHelper::exception(SbERR_METHOD_FAILED, rtl::OUString());
694 		}
695 		mxPropertySet->setPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( SC_UNONAME_WRITING ) ), aVal );
696 	}
697 	catch (uno::Exception& )
698 	{
699 		DebugHelper::exception(SbERR_METHOD_FAILED, rtl::OUString());
700 	}
701 
702 }
703 
704 template< typename Ifc1 >
705 uno::Any SAL_CALL
706 ScVbaFormat<Ifc1>::getReadingOrder(  ) throw (script::BasicErrorException, uno::RuntimeException)
707 {
708 	uno::Any NRetReadingOrder = aNULL();
709 	try
710 	{
711 		rtl::OUString sWritingMode( RTL_CONSTASCII_USTRINGPARAM( SC_UNONAME_WRITING ) );
712 		if (!isAmbiguous(sWritingMode))
713 		{
714 			text::WritingMode aWritingMode = text::WritingMode_LR_TB;
715 			if ( ( mxPropertySet->getPropertyValue(sWritingMode) ) >>= aWritingMode )
716 			switch (aWritingMode){
717 				case text::WritingMode_LR_TB:
718 					NRetReadingOrder = uno::makeAny(excel::Constants::xlLTR);
719 					break;
720 				case text::WritingMode_RL_TB:
721 					NRetReadingOrder = uno::makeAny(excel::Constants::xlRTL);
722 					break;
723 				default:
724 					NRetReadingOrder = uno::makeAny(excel::Constants::xlRTL);
725 			}
726 		}
727 	}
728 	catch (uno::Exception& )
729 	{
730 		DebugHelper::exception(SbERR_NOT_IMPLEMENTED, rtl::OUString());
731 	}
732 	return NRetReadingOrder;
733 
734 }
735 
736 template< typename Ifc1 >
737 uno::Any SAL_CALL
738 ScVbaFormat< Ifc1 >::getNumberFormat(  ) throw (script::BasicErrorException, uno::RuntimeException)
739 {
740 	uno::Any aFormat = aNULL();
741 	try
742 	{
743 		sal_Int32 nFormat = -1;
744 		rtl::OUString sNumFormat( RTL_CONSTASCII_USTRINGPARAM( SC_UNO_NUMBERFO ) );
745 		if (!isAmbiguous(sNumFormat) &&
746 			( mxPropertySet->getPropertyValue(sNumFormat) >>= nFormat) )
747 		{
748 			initializeNumberFormats();
749 
750 			sal_Int32 nNewFormat = xNumberFormatTypes->getFormatForLocale(nFormat, getDefaultLocale() );
751 			rtl::OUString sFormat;
752 			xNumberFormats->getByKey(nNewFormat)->getPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( FORMATSTRING ))) >>= sFormat;
753 			aFormat = uno::makeAny( sFormat );
754 		}
755 	}
756 	catch (uno::Exception& )
757 	{
758 		DebugHelper::exception(SbERR_METHOD_FAILED, rtl::OUString());
759 	}
760 	return aFormat;
761 }
762 
763 template< typename Ifc1 >
764 bool
765 ScVbaFormat<Ifc1>::isAmbiguous(const rtl::OUString& _sPropertyName) throw ( script::BasicErrorException )
766 {
767 	bool bResult = false;
768 	try
769 	{
770 		if (mbCheckAmbiguoity)
771 			bResult = ( getXPropertyState()->getPropertyState(_sPropertyName) == beans::PropertyState_AMBIGUOUS_VALUE );
772 	}
773 	catch (uno::Exception& )
774 	{
775 		DebugHelper::exception(SbERR_METHOD_FAILED, rtl::OUString());
776 	}
777 	return bResult;
778 }
779 
780 template< typename Ifc1 >
781 void
782 ScVbaFormat<Ifc1>::initializeNumberFormats() throw ( script::BasicErrorException )
783 {
784 	if ( !xNumberFormats.is() )
785 	{
786 		mxNumberFormatsSupplier.set( mxModel, uno::UNO_QUERY_THROW );
787 		xNumberFormats = mxNumberFormatsSupplier->getNumberFormats();
788 		xNumberFormatTypes.set( xNumberFormats, uno::UNO_QUERY ); // _THROW?
789 	}
790 }
791 
792 template< typename Ifc1 >
793 uno::Reference< beans::XPropertyState >
794 ScVbaFormat<Ifc1>::getXPropertyState() throw ( uno::RuntimeException )
795 {
796 	if ( !xPropertyState.is() )
797 		xPropertyState.set( mxPropertySet, uno::UNO_QUERY_THROW );
798 	return xPropertyState;
799 }
800 
801 template< typename Ifc1 >
802 rtl::OUString&
803 ScVbaFormat<Ifc1>::getServiceImplName()
804 {
805         static rtl::OUString sImplName( RTL_CONSTASCII_USTRINGPARAM("ScVbaFormat") );
806         return sImplName;
807 }
808 
809 template< typename Ifc1 >
810 uno::Sequence< rtl::OUString >
811 ScVbaFormat<Ifc1>::getServiceNames()
812 {
813         static uno::Sequence< rtl::OUString > aServiceNames;
814         if ( aServiceNames.getLength() == 0 )
815         {
816                 aServiceNames.realloc( 1 );
817                 aServiceNames[ 0 ] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.excel.Format" ) );
818         }
819         return aServiceNames;
820 }
821 
822 template< typename Ifc1 >
823 ScCellRangesBase*
824 ScVbaFormat<Ifc1>::getCellRangesBase() throw ( ::uno::RuntimeException )
825 {
826     return ScCellRangesBase::getImplementation( mxPropertySet );
827 }
828 
829 template< typename Ifc1 >
830 SfxItemSet*
831 ScVbaFormat<Ifc1>::getCurrentDataSet( ) throw ( uno::RuntimeException )
832 {
833 	SfxItemSet* pDataSet = excel::ScVbaCellRangeAccess::GetDataSet( getCellRangesBase() );
834 	if ( !pDataSet )
835 		throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "Can't access Itemset for XPropertySet" ) ), uno::Reference< uno::XInterface >() );
836 	return pDataSet;
837 }
838 
839 
840 template class ScVbaFormat< excel::XStyle >;
841 template class ScVbaFormat< excel::XRange >;
842 
843 
844