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