xref: /AOO41X/main/sc/source/ui/vba/vbahelper.cxx (revision b3f79822e811ac3493b185030a72c3c5a51f32d8)
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
10cdf0e10cSrcweir  *
11*b3f79822SAndrew Rist  *   http://www.apache.org/licenses/LICENSE-2.0
12cdf0e10cSrcweir  *
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.
19cdf0e10cSrcweir  *
20*b3f79822SAndrew Rist  *************************************************************/
21*b3f79822SAndrew Rist 
22*b3f79822SAndrew Rist 
23cdf0e10cSrcweir #include <cppuhelper/bootstrap.hxx>
24cdf0e10cSrcweir #include <com/sun/star/util/XURLTransformer.hpp>
25cdf0e10cSrcweir #include <com/sun/star/frame/XDispatchProvider.hpp>
26cdf0e10cSrcweir #include <com/sun/star/frame/XModel.hpp>
27cdf0e10cSrcweir #include <com/sun/star/frame/XFrame.hpp>
28cdf0e10cSrcweir #include <com/sun/star/frame/XDesktop.hpp>
29cdf0e10cSrcweir #include <com/sun/star/frame/XController.hpp>
30cdf0e10cSrcweir #include <com/sun/star/uno/XComponentContext.hpp>
31cdf0e10cSrcweir #include <com/sun/star/lang/XMultiComponentFactory.hpp>
32cdf0e10cSrcweir #include <com/sun/star/beans/XPropertySet.hpp>
33cdf0e10cSrcweir #include <com/sun/star/beans/XIntrospection.hpp>
34cdf0e10cSrcweir 
35cdf0e10cSrcweir #include <comphelper/processfactory.hxx>
36cdf0e10cSrcweir 
37cdf0e10cSrcweir #include <sfx2/objsh.hxx>
38cdf0e10cSrcweir #include <sfx2/viewfrm.hxx>
39cdf0e10cSrcweir #include <sfx2/dispatch.hxx>
40cdf0e10cSrcweir #include <sfx2/app.hxx>
41cdf0e10cSrcweir #include <svl/stritem.hxx>
42cdf0e10cSrcweir 
43cdf0e10cSrcweir #include <docuno.hxx>
44cdf0e10cSrcweir 
45cdf0e10cSrcweir #include <basic/sbx.hxx>
46cdf0e10cSrcweir #include <basic/sbstar.hxx>
47cdf0e10cSrcweir #include <rtl/math.hxx>
48cdf0e10cSrcweir 
49cdf0e10cSrcweir #include <math.h>
50cdf0e10cSrcweir #include "vbahelper.hxx"
51cdf0e10cSrcweir #include "tabvwsh.hxx"
52cdf0e10cSrcweir #include "transobj.hxx"
53cdf0e10cSrcweir #include "scmod.hxx"
54cdf0e10cSrcweir #include "vbashape.hxx"
55cdf0e10cSrcweir #include "unonames.hxx"
56cdf0e10cSrcweir #include "cellsuno.hxx"
57cdf0e10cSrcweir using namespace ::com::sun::star;
58cdf0e10cSrcweir using namespace ::ooo::vba;
59cdf0e10cSrcweir 
60cdf0e10cSrcweir #define POINTTO100THMILLIMETERFACTOR 35.27778
61cdf0e10cSrcweir void unoToSbxValue( SbxVariable* pVar, const uno::Any& aValue );
62cdf0e10cSrcweir 
63cdf0e10cSrcweir uno::Any sbxToUnoValue( SbxVariable* pVar );
64cdf0e10cSrcweir 
65cdf0e10cSrcweir 
66cdf0e10cSrcweir namespace ooo
67cdf0e10cSrcweir {
68cdf0e10cSrcweir namespace vba
69cdf0e10cSrcweir {
70cdf0e10cSrcweir 
71cdf0e10cSrcweir const double Millimeter::factor =  35.27778;
72cdf0e10cSrcweir 
73cdf0e10cSrcweir uno::Reference< beans::XIntrospectionAccess >
getIntrospectionAccess(const uno::Any & aObject)74cdf0e10cSrcweir getIntrospectionAccess( const uno::Any& aObject ) throw (uno::RuntimeException)
75cdf0e10cSrcweir {
76cdf0e10cSrcweir 	static uno::Reference< beans::XIntrospection > xIntrospection;
77cdf0e10cSrcweir 	if( !xIntrospection.is() )
78cdf0e10cSrcweir 	{
79cdf0e10cSrcweir 		uno::Reference< lang::XMultiServiceFactory > xFactory( comphelper::getProcessServiceFactory(), uno::UNO_QUERY_THROW );
80cdf0e10cSrcweir 		xIntrospection.set( xFactory->createInstance( rtl::OUString::createFromAscii("com.sun.star.beans.Introspection") ), uno::UNO_QUERY_THROW );
81cdf0e10cSrcweir 	}
82cdf0e10cSrcweir 	return xIntrospection->inspect( aObject );
83cdf0e10cSrcweir }
84cdf0e10cSrcweir 
85cdf0e10cSrcweir uno::Reference< script::XTypeConverter >
getTypeConverter(const uno::Reference<uno::XComponentContext> & xContext)86cdf0e10cSrcweir getTypeConverter( const uno::Reference< uno::XComponentContext >& xContext ) throw (uno::RuntimeException)
87cdf0e10cSrcweir {
88cdf0e10cSrcweir 	static uno::Reference< script::XTypeConverter > xTypeConv( xContext->getServiceManager()->createInstanceWithContext( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("com.sun.star.script.Converter") ), xContext ), uno::UNO_QUERY_THROW );
89cdf0e10cSrcweir 	return xTypeConv;
90cdf0e10cSrcweir }
91cdf0e10cSrcweir // helper method to determine if the view ( calc ) is in print-preview mode
isInPrintPreview(SfxViewFrame * pView)92cdf0e10cSrcweir bool isInPrintPreview( SfxViewFrame* pView )
93cdf0e10cSrcweir {
94cdf0e10cSrcweir 	sal_uInt16 nViewNo = SID_VIEWSHELL1 - SID_VIEWSHELL0;
95cdf0e10cSrcweir 	if ( pView->GetObjectShell()->GetFactory().GetViewFactoryCount() >
96cdf0e10cSrcweir nViewNo && !pView->GetObjectShell()->IsInPlaceActive() )
97cdf0e10cSrcweir 	{
98cdf0e10cSrcweir 		SfxViewFactory &rViewFactory =
99cdf0e10cSrcweir 			pView->GetObjectShell()->GetFactory().GetViewFactory(nViewNo);
100cdf0e10cSrcweir 		if (  pView->GetCurViewId() == rViewFactory.GetOrdinal() )
101cdf0e10cSrcweir 			return true;
102cdf0e10cSrcweir 	}
103cdf0e10cSrcweir 	return false;
104cdf0e10cSrcweir }
105cdf0e10cSrcweir const ::rtl::OUString REPLACE_CELLS_WARNING(  RTL_CONSTASCII_USTRINGPARAM( "ReplaceCellsWarning"));
106cdf0e10cSrcweir const uno::Any&
aNULL()107cdf0e10cSrcweir aNULL()
108cdf0e10cSrcweir {
109cdf0e10cSrcweir  	static  uno::Any aNULLL = uno::makeAny( uno::Reference< uno::XInterface >() );
110cdf0e10cSrcweir 	return aNULLL;
111cdf0e10cSrcweir }
112cdf0e10cSrcweir 
113cdf0e10cSrcweir class PasteCellsWarningReseter
114cdf0e10cSrcweir {
115cdf0e10cSrcweir private:
116cdf0e10cSrcweir 	bool bInitialWarningState;
getGlobalSheetSettings()117cdf0e10cSrcweir 	static uno::Reference< beans::XPropertySet > getGlobalSheetSettings() throw ( uno::RuntimeException )
118cdf0e10cSrcweir 	{
119cdf0e10cSrcweir 		static uno::Reference< beans::XPropertySet > xTmpProps( ::comphelper::getProcessServiceFactory(), uno::UNO_QUERY_THROW );
120cdf0e10cSrcweir 		static uno::Reference<uno::XComponentContext > xContext( xTmpProps->getPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "DefaultContext" ))), uno::UNO_QUERY_THROW );
121cdf0e10cSrcweir 		static uno::Reference<lang::XMultiComponentFactory > xServiceManager(
122cdf0e10cSrcweir 				xContext->getServiceManager(), uno::UNO_QUERY_THROW );
123cdf0e10cSrcweir 		static uno::Reference< beans::XPropertySet > xProps( xServiceManager->createInstanceWithContext( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "com.sun.star.sheet.GlobalSheetSettings" ) ) ,xContext ), uno::UNO_QUERY_THROW );
124cdf0e10cSrcweir 		return xProps;
125cdf0e10cSrcweir 	}
126cdf0e10cSrcweir 
getReplaceCellsWarning()127cdf0e10cSrcweir 	bool getReplaceCellsWarning() throw ( uno::RuntimeException )
128cdf0e10cSrcweir 	{
129cdf0e10cSrcweir 		sal_Bool res = sal_False;
130cdf0e10cSrcweir 		getGlobalSheetSettings()->getPropertyValue( REPLACE_CELLS_WARNING ) >>= res;
131cdf0e10cSrcweir 		return ( res == sal_True );
132cdf0e10cSrcweir 	}
133cdf0e10cSrcweir 
setReplaceCellsWarning(bool bState)134cdf0e10cSrcweir 	void setReplaceCellsWarning( bool bState ) throw ( uno::RuntimeException )
135cdf0e10cSrcweir 	{
136cdf0e10cSrcweir 		getGlobalSheetSettings()->setPropertyValue( REPLACE_CELLS_WARNING, uno::makeAny( bState ) );
137cdf0e10cSrcweir 	}
138cdf0e10cSrcweir public:
PasteCellsWarningReseter()139cdf0e10cSrcweir 	PasteCellsWarningReseter() throw ( uno::RuntimeException )
140cdf0e10cSrcweir 	{
141cdf0e10cSrcweir 		bInitialWarningState = getReplaceCellsWarning();
142cdf0e10cSrcweir 		if ( bInitialWarningState )
143cdf0e10cSrcweir 			setReplaceCellsWarning( false );
144cdf0e10cSrcweir 	}
~PasteCellsWarningReseter()145cdf0e10cSrcweir 	~PasteCellsWarningReseter()
146cdf0e10cSrcweir 	{
147cdf0e10cSrcweir 		if ( bInitialWarningState )
148cdf0e10cSrcweir 		{
149cdf0e10cSrcweir 			// don't allow dtor to throw
150cdf0e10cSrcweir 			try
151cdf0e10cSrcweir 			{
152cdf0e10cSrcweir 				setReplaceCellsWarning( true );
153cdf0e10cSrcweir 			}
154cdf0e10cSrcweir 			catch ( uno::Exception& /*e*/ ){}
155cdf0e10cSrcweir 		}
156cdf0e10cSrcweir 	}
157cdf0e10cSrcweir };
158cdf0e10cSrcweir 
dispatchExecute(css::uno::Reference<css::frame::XModel> & xModel,sal_uInt16 nSlot,SfxCallMode nCall)159cdf0e10cSrcweir void dispatchExecute(css::uno::Reference< css::frame::XModel>& xModel, sal_uInt16 nSlot, SfxCallMode nCall)
160cdf0e10cSrcweir {
161cdf0e10cSrcweir 	ScTabViewShell* pViewShell = getBestViewShell( xModel );
162cdf0e10cSrcweir 	SfxViewFrame* pViewFrame = NULL;
163cdf0e10cSrcweir 	if ( pViewShell )
164cdf0e10cSrcweir 		pViewFrame = pViewShell->GetViewFrame();
165cdf0e10cSrcweir 	if ( pViewFrame )
166cdf0e10cSrcweir 	{
167cdf0e10cSrcweir 		SfxDispatcher* pDispatcher = pViewFrame->GetDispatcher();
168cdf0e10cSrcweir 		if( pDispatcher )
169cdf0e10cSrcweir 		{
170cdf0e10cSrcweir 			pDispatcher->Execute( nSlot , nCall );
171cdf0e10cSrcweir 		}
172cdf0e10cSrcweir 	}
173cdf0e10cSrcweir }
174cdf0e10cSrcweir 
175cdf0e10cSrcweir void
implnPaste()176cdf0e10cSrcweir implnPaste()
177cdf0e10cSrcweir {
178cdf0e10cSrcweir 	PasteCellsWarningReseter resetWarningBox;
179cdf0e10cSrcweir 	ScTabViewShell* pViewShell = getCurrentBestViewShell();
180cdf0e10cSrcweir 	if ( pViewShell )
181cdf0e10cSrcweir 	{
182cdf0e10cSrcweir 		pViewShell->PasteFromSystem();
183cdf0e10cSrcweir 		pViewShell->CellContentChanged();
184cdf0e10cSrcweir 	}
185cdf0e10cSrcweir }
186cdf0e10cSrcweir 
187cdf0e10cSrcweir 
188cdf0e10cSrcweir void
implnCopy()189cdf0e10cSrcweir implnCopy()
190cdf0e10cSrcweir {
191cdf0e10cSrcweir 	ScTabViewShell* pViewShell = getCurrentBestViewShell();
192cdf0e10cSrcweir 	if ( pViewShell )
193cdf0e10cSrcweir 		pViewShell->CopyToClip(NULL,false,false,true);
194cdf0e10cSrcweir }
195cdf0e10cSrcweir 
196cdf0e10cSrcweir void
implnCut()197cdf0e10cSrcweir implnCut()
198cdf0e10cSrcweir {
199cdf0e10cSrcweir 	ScTabViewShell* pViewShell =  getCurrentBestViewShell();
200cdf0e10cSrcweir 	if ( pViewShell )
201cdf0e10cSrcweir 		pViewShell->CutToClip( NULL, sal_True );
202cdf0e10cSrcweir }
203cdf0e10cSrcweir 
implnPasteSpecial(sal_uInt16 nFlags,sal_uInt16 nFunction,sal_Bool bSkipEmpty,sal_Bool bTranspose)204cdf0e10cSrcweir void implnPasteSpecial(sal_uInt16 nFlags,sal_uInt16 nFunction,sal_Bool bSkipEmpty, sal_Bool bTranspose)
205cdf0e10cSrcweir {
206cdf0e10cSrcweir 	PasteCellsWarningReseter resetWarningBox;
207cdf0e10cSrcweir 	sal_Bool bAsLink(sal_False), bOtherDoc(sal_False);
208cdf0e10cSrcweir 	InsCellCmd eMoveMode = INS_NONE;
209cdf0e10cSrcweir 
210cdf0e10cSrcweir 	ScTabViewShell* pTabViewShell = ScTabViewShell::GetActiveViewShell();
211cdf0e10cSrcweir 	if ( !pTabViewShell )
212cdf0e10cSrcweir 		// none active, try next best
213cdf0e10cSrcweir 		pTabViewShell = getCurrentBestViewShell();
214cdf0e10cSrcweir 	if ( pTabViewShell )
215cdf0e10cSrcweir 	{
216cdf0e10cSrcweir 		ScViewData* pView = pTabViewShell->GetViewData();
217cdf0e10cSrcweir 		Window* pWin = ( pView != NULL ) ? pView->GetActiveWin() : NULL;
218cdf0e10cSrcweir 		if ( pView && pWin )
219cdf0e10cSrcweir 		{
220cdf0e10cSrcweir 			if ( bAsLink && bOtherDoc )
221cdf0e10cSrcweir 				pTabViewShell->PasteFromSystem(0);//SOT_FORMATSTR_ID_LINK
222cdf0e10cSrcweir 			else
223cdf0e10cSrcweir 			{
224cdf0e10cSrcweir 				ScTransferObj* pOwnClip = ScTransferObj::GetOwnClipboard( pWin );
225cdf0e10cSrcweir 				ScDocument* pDoc = NULL;
226cdf0e10cSrcweir 				if ( pOwnClip )
227cdf0e10cSrcweir 					pDoc = pOwnClip->GetDocument();
228cdf0e10cSrcweir 				pTabViewShell->PasteFromClip( nFlags, pDoc,
229cdf0e10cSrcweir 					nFunction, bSkipEmpty, bTranspose, bAsLink,
230cdf0e10cSrcweir 					eMoveMode, IDF_NONE, sal_True );
231cdf0e10cSrcweir 				pTabViewShell->CellContentChanged();
232cdf0e10cSrcweir 			}
233cdf0e10cSrcweir 		}
234cdf0e10cSrcweir 	}
235cdf0e10cSrcweir 
236cdf0e10cSrcweir }
237cdf0e10cSrcweir 
238cdf0e10cSrcweir  uno::Reference< frame::XModel >
getCurrentDocument()239cdf0e10cSrcweir getCurrentDocument() throw (uno::RuntimeException)
240cdf0e10cSrcweir {
241cdf0e10cSrcweir 	uno::Reference< frame::XModel > xModel;
242cdf0e10cSrcweir 	SbxObject* pBasic = dynamic_cast< SbxObject* > ( SFX_APP()->GetBasic() );
243cdf0e10cSrcweir 	SbxObject* basicChosen =  pBasic ;
244cdf0e10cSrcweir 	if ( basicChosen == NULL)
245cdf0e10cSrcweir 	{
246cdf0e10cSrcweir 		OSL_TRACE("getModelFromBasic() StarBASIC* is NULL" );
247cdf0e10cSrcweir 		return xModel;
248cdf0e10cSrcweir 	}
249cdf0e10cSrcweir     SbxObject* p = pBasic;
250cdf0e10cSrcweir     SbxObject* pParent = p->GetParent();
251cdf0e10cSrcweir     SbxObject* pParentParent = pParent ? pParent->GetParent() : NULL;
252cdf0e10cSrcweir 
253cdf0e10cSrcweir     if( pParentParent )
254cdf0e10cSrcweir     {
255cdf0e10cSrcweir         basicChosen = pParentParent;
256cdf0e10cSrcweir     }
257cdf0e10cSrcweir     else if( pParent )
258cdf0e10cSrcweir     {
259cdf0e10cSrcweir         basicChosen = pParent;
260cdf0e10cSrcweir     }
261cdf0e10cSrcweir 
262cdf0e10cSrcweir 
263cdf0e10cSrcweir     uno::Any aModel;
264cdf0e10cSrcweir     SbxVariable *pCompVar = basicChosen->Find(  UniString(RTL_CONSTASCII_USTRINGPARAM("ThisComponent")), SbxCLASS_OBJECT );
265cdf0e10cSrcweir 
266cdf0e10cSrcweir 	if ( pCompVar )
267cdf0e10cSrcweir 	{
268cdf0e10cSrcweir 		aModel = sbxToUnoValue( pCompVar );
269cdf0e10cSrcweir 		if ( sal_False == ( aModel >>= xModel ) ||
270cdf0e10cSrcweir 			!xModel.is() )
271cdf0e10cSrcweir 		{
272cdf0e10cSrcweir 			// trying last gasp try the current component
273cdf0e10cSrcweir 			uno::Reference< beans::XPropertySet > xProps( ::comphelper::getProcessServiceFactory(), uno::UNO_QUERY_THROW );
274cdf0e10cSrcweir 			// test if vba service is present
275cdf0e10cSrcweir 			uno::Reference< uno::XComponentContext > xCtx( xProps->getPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "DefaultContext" ))), uno::UNO_QUERY_THROW );
276cdf0e10cSrcweir 			uno::Reference<lang::XMultiComponentFactory > xSMgr( xCtx->getServiceManager(), uno::UNO_QUERY_THROW );
277cdf0e10cSrcweir 			uno::Reference< frame::XDesktop > xDesktop (xSMgr->createInstanceWithContext(::rtl::OUString::createFromAscii("com.sun.star.frame.Desktop"), xCtx), uno::UNO_QUERY_THROW );
278cdf0e10cSrcweir 			xModel.set( xDesktop->getCurrentComponent(), uno::UNO_QUERY );
279cdf0e10cSrcweir 			if ( !xModel.is() )
280cdf0e10cSrcweir 			{
281cdf0e10cSrcweir 				throw uno::RuntimeException(
282cdf0e10cSrcweir 					rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "Can't extract model from basic ( its obviously not set yet ) therefore don't know the currently selected document") ), uno::Reference< uno::XInterface >() );
283cdf0e10cSrcweir 			}
284cdf0e10cSrcweir 			return xModel;
285cdf0e10cSrcweir 		}
286cdf0e10cSrcweir 		else
287cdf0e10cSrcweir 		{
288cdf0e10cSrcweir 			OSL_TRACE("Have model ThisComponent points to url %s",
289cdf0e10cSrcweir 			::rtl::OUStringToOString( xModel->getURL(),
290cdf0e10cSrcweir 				RTL_TEXTENCODING_ASCII_US ).pData->buffer );
291cdf0e10cSrcweir 		}
292cdf0e10cSrcweir 	}
293cdf0e10cSrcweir 	else
294cdf0e10cSrcweir 	{
295cdf0e10cSrcweir 		OSL_TRACE("Failed to get ThisComponent");
296cdf0e10cSrcweir 		throw uno::RuntimeException(
297cdf0e10cSrcweir 			rtl::OUString(
298cdf0e10cSrcweir 				RTL_CONSTASCII_USTRINGPARAM(
299cdf0e10cSrcweir 					"Can't determine the currently selected document") ),
300cdf0e10cSrcweir 			uno::Reference< uno::XInterface >() );
301cdf0e10cSrcweir 	}
302cdf0e10cSrcweir 	return xModel;
303cdf0e10cSrcweir }
304cdf0e10cSrcweir 
305cdf0e10cSrcweir ScDocShell*
getDocShell(css::uno::Reference<css::frame::XModel> & xModel)306cdf0e10cSrcweir getDocShell( css::uno::Reference< css::frame::XModel>& xModel )
307cdf0e10cSrcweir {
308cdf0e10cSrcweir 	uno::Reference< uno::XInterface > xIf( xModel, uno::UNO_QUERY_THROW );
309cdf0e10cSrcweir 	ScModelObj* pModel = dynamic_cast< ScModelObj* >( xIf.get() );
310cdf0e10cSrcweir 	ScDocShell* pDocShell = NULL;
311cdf0e10cSrcweir 	if ( pModel )
312cdf0e10cSrcweir 		pDocShell = (ScDocShell*)pModel->GetEmbeddedObject();
313cdf0e10cSrcweir 	return pDocShell;
314cdf0e10cSrcweir 
315cdf0e10cSrcweir }
316cdf0e10cSrcweir 
317cdf0e10cSrcweir ScTabViewShell*
getBestViewShell(css::uno::Reference<css::frame::XModel> & xModel)318cdf0e10cSrcweir getBestViewShell(  css::uno::Reference< css::frame::XModel>& xModel )
319cdf0e10cSrcweir {
320cdf0e10cSrcweir 	ScDocShell* pDocShell = getDocShell( xModel );
321cdf0e10cSrcweir 	if ( pDocShell )
322cdf0e10cSrcweir 		return pDocShell->GetBestViewShell();
323cdf0e10cSrcweir 	return NULL;
324cdf0e10cSrcweir }
325cdf0e10cSrcweir 
326cdf0e10cSrcweir ScTabViewShell*
getCurrentBestViewShell()327cdf0e10cSrcweir getCurrentBestViewShell()
328cdf0e10cSrcweir {
329cdf0e10cSrcweir 	uno::Reference< frame::XModel > xModel = getCurrentDocument();
330cdf0e10cSrcweir 	return getBestViewShell( xModel );
331cdf0e10cSrcweir }
332cdf0e10cSrcweir 
333cdf0e10cSrcweir SfxViewFrame*
getCurrentViewFrame()334cdf0e10cSrcweir getCurrentViewFrame()
335cdf0e10cSrcweir {
336cdf0e10cSrcweir 	ScTabViewShell* pViewShell = getCurrentBestViewShell();
337cdf0e10cSrcweir 	if ( pViewShell )
338cdf0e10cSrcweir 		return pViewShell->GetViewFrame();
339cdf0e10cSrcweir 	return NULL;
340cdf0e10cSrcweir }
341cdf0e10cSrcweir 
342cdf0e10cSrcweir sal_Int32
OORGBToXLRGB(sal_Int32 nCol)343cdf0e10cSrcweir OORGBToXLRGB( sal_Int32 nCol )
344cdf0e10cSrcweir {
345cdf0e10cSrcweir 	sal_Int32 nRed = nCol;
346cdf0e10cSrcweir 	nRed &= 0x00FF0000;
347cdf0e10cSrcweir 	nRed >>= 16;
348cdf0e10cSrcweir 	sal_Int32 nGreen = nCol;
349cdf0e10cSrcweir 	nGreen &= 0x0000FF00;
350cdf0e10cSrcweir 	nGreen >>= 8;
351cdf0e10cSrcweir 	sal_Int32 nBlue = nCol;
352cdf0e10cSrcweir 	nBlue &= 0x000000FF;
353cdf0e10cSrcweir 	sal_Int32 nRGB =  ( (nBlue << 16) | (nGreen << 8) | nRed );
354cdf0e10cSrcweir 	return nRGB;
355cdf0e10cSrcweir }
356cdf0e10cSrcweir sal_Int32
XLRGBToOORGB(sal_Int32 nCol)357cdf0e10cSrcweir XLRGBToOORGB( sal_Int32 nCol )
358cdf0e10cSrcweir {
359cdf0e10cSrcweir 	sal_Int32 nBlue = nCol;
360cdf0e10cSrcweir 	nBlue &= 0x00FF0000;
361cdf0e10cSrcweir 	nBlue >>= 16;
362cdf0e10cSrcweir 	sal_Int32 nGreen = nCol;
363cdf0e10cSrcweir 	nGreen &= 0x0000FF00;
364cdf0e10cSrcweir 	nGreen >>= 8;
365cdf0e10cSrcweir 	sal_Int32 nRed = nCol;
366cdf0e10cSrcweir 	nRed &= 0x000000FF;
367cdf0e10cSrcweir 	sal_Int32 nRGB =  ( (nRed << 16) | (nGreen << 8) | nBlue );
368cdf0e10cSrcweir 	return nRGB;
369cdf0e10cSrcweir }
370cdf0e10cSrcweir uno::Any
OORGBToXLRGB(const uno::Any & aCol)371cdf0e10cSrcweir OORGBToXLRGB( const uno::Any& aCol )
372cdf0e10cSrcweir {
373cdf0e10cSrcweir 	sal_Int32 nCol=0;
374cdf0e10cSrcweir 	aCol >>= nCol;
375cdf0e10cSrcweir 	nCol = OORGBToXLRGB( nCol );
376cdf0e10cSrcweir 	return uno::makeAny( nCol );
377cdf0e10cSrcweir }
378cdf0e10cSrcweir uno::Any
XLRGBToOORGB(const uno::Any & aCol)379cdf0e10cSrcweir XLRGBToOORGB(  const uno::Any& aCol )
380cdf0e10cSrcweir {
381cdf0e10cSrcweir 	sal_Int32 nCol=0;
382cdf0e10cSrcweir 	aCol >>= nCol;
383cdf0e10cSrcweir 	nCol = XLRGBToOORGB( nCol );
384cdf0e10cSrcweir 	return uno::makeAny( nCol );
385cdf0e10cSrcweir }
386cdf0e10cSrcweir 
PrintOutHelper(const uno::Any & From,const uno::Any & To,const uno::Any & Copies,const uno::Any & Preview,const uno::Any &,const uno::Any &,const uno::Any & Collate,const uno::Any & PrToFileName,css::uno::Reference<frame::XModel> & xModel,sal_Bool bUseSelection)387cdf0e10cSrcweir void PrintOutHelper( const uno::Any& From, const uno::Any& To, const uno::Any& Copies, const uno::Any& Preview, const uno::Any& /*ActivePrinter*/, const uno::Any& /*PrintToFile*/, const uno::Any& Collate, const uno::Any& PrToFileName, css::uno::Reference< frame::XModel >& xModel, sal_Bool bUseSelection  )
388cdf0e10cSrcweir {
389cdf0e10cSrcweir 	sal_Int32 nTo = 0;
390cdf0e10cSrcweir 	sal_Int32 nFrom = 0;
391cdf0e10cSrcweir 	sal_Int16 nCopies = 1;
392cdf0e10cSrcweir 	sal_Bool bPreview = sal_False;
393cdf0e10cSrcweir 	sal_Bool bCollate = sal_False;
394cdf0e10cSrcweir 	sal_Bool bSelection = bUseSelection;
395cdf0e10cSrcweir 	From >>= nFrom;
396cdf0e10cSrcweir 	To >>= nTo;
397cdf0e10cSrcweir 	Copies >>= nCopies;
398cdf0e10cSrcweir 	Preview >>= bPreview;
399cdf0e10cSrcweir 	if ( nCopies > 1 ) // Collate only useful when more that 1 copy
400cdf0e10cSrcweir 		Collate >>= bCollate;
401cdf0e10cSrcweir 
402cdf0e10cSrcweir 	rtl::OUString sRange(  RTL_CONSTASCII_USTRINGPARAM( "-" ) );
403cdf0e10cSrcweir 	rtl::OUString sFileName;
404cdf0e10cSrcweir 
405cdf0e10cSrcweir 	if (( nFrom || nTo ) )
406cdf0e10cSrcweir 	{
407cdf0e10cSrcweir 		if ( nFrom )
408cdf0e10cSrcweir 			sRange = ( ::rtl::OUString::valueOf( nFrom ) + sRange );
409cdf0e10cSrcweir 		if ( nTo )
410cdf0e10cSrcweir 			sRange += ::rtl::OUString::valueOf( nTo );
411cdf0e10cSrcweir 	}
412cdf0e10cSrcweir 
413cdf0e10cSrcweir 	if (  PrToFileName.getValue() )
414cdf0e10cSrcweir 	{
415cdf0e10cSrcweir 		PrToFileName >>= sFileName;
416cdf0e10cSrcweir 	}
417cdf0e10cSrcweir 	ScTabViewShell* pViewShell = getBestViewShell( xModel );
418cdf0e10cSrcweir 	SfxViewFrame* pViewFrame = NULL;
419cdf0e10cSrcweir 	if ( pViewShell )
420cdf0e10cSrcweir 		pViewFrame = pViewShell->GetViewFrame();
421cdf0e10cSrcweir 	if ( pViewFrame )
422cdf0e10cSrcweir 	{
423cdf0e10cSrcweir 		SfxAllItemSet aArgs( SFX_APP()->GetPool() );
424cdf0e10cSrcweir 
425cdf0e10cSrcweir 		SfxBoolItem sfxCollate( SID_PRINT_COLLATE, bCollate );
426cdf0e10cSrcweir 		aArgs.Put( sfxCollate, sfxCollate.Which() );
427cdf0e10cSrcweir 		SfxInt16Item sfxCopies( SID_PRINT_COPIES, nCopies );
428cdf0e10cSrcweir 		aArgs.Put( sfxCopies, sfxCopies.Which() );
429cdf0e10cSrcweir 		if ( sFileName.getLength() )
430cdf0e10cSrcweir 		{
431cdf0e10cSrcweir 			SfxStringItem sfxFileName( SID_FILE_NAME, sFileName);
432cdf0e10cSrcweir 			aArgs.Put( sfxFileName, sfxFileName.Which() );
433cdf0e10cSrcweir 
434cdf0e10cSrcweir 		}
435cdf0e10cSrcweir 		if (  sRange.getLength() )
436cdf0e10cSrcweir 		{
437cdf0e10cSrcweir 			SfxStringItem sfxRange( SID_PRINT_PAGES, sRange );
438cdf0e10cSrcweir 			aArgs.Put( sfxRange, sfxRange.Which() );
439cdf0e10cSrcweir 		}
440cdf0e10cSrcweir 		SfxBoolItem sfxSelection( SID_SELECTION, bSelection );
441cdf0e10cSrcweir 		aArgs.Put( sfxSelection, sfxSelection.Which() );
442cdf0e10cSrcweir 		SfxBoolItem sfxAsync( SID_ASYNCHRON, sal_False );
443cdf0e10cSrcweir 		aArgs.Put( sfxAsync, sfxAsync.Which() );
444cdf0e10cSrcweir 		SfxDispatcher* pDispatcher = pViewFrame->GetDispatcher();
445cdf0e10cSrcweir 
446cdf0e10cSrcweir 		if ( pDispatcher )
447cdf0e10cSrcweir 		{
448cdf0e10cSrcweir 			if ( bPreview )
449cdf0e10cSrcweir 			{
450cdf0e10cSrcweir 				if ( !pViewFrame->GetFrame().IsInPlace() )
451cdf0e10cSrcweir 				{
452cdf0e10cSrcweir 					SC_MOD()->InputEnterHandler();
453cdf0e10cSrcweir 					pViewFrame->GetDispatcher()->Execute( SID_VIEWSHELL1, SFX_CALLMODE_SYNCHRON );
454cdf0e10cSrcweir 					while ( isInPrintPreview( pViewFrame ) )
455cdf0e10cSrcweir 						Application::Yield();
456cdf0e10cSrcweir 				}
457cdf0e10cSrcweir 			}
458cdf0e10cSrcweir 			else
459cdf0e10cSrcweir 				pDispatcher->Execute( (sal_uInt16)SID_PRINTDOC, (SfxCallMode)SFX_CALLMODE_SYNCHRON, aArgs );
460cdf0e10cSrcweir 		}
461cdf0e10cSrcweir 
462cdf0e10cSrcweir 	}
463cdf0e10cSrcweir 
464cdf0e10cSrcweir 	// #FIXME #TODO
465cdf0e10cSrcweir 	// 1 ActivePrinter ( how/can we switch a printer via API? )
466cdf0e10cSrcweir 	// 2 PrintToFile ( ms behaviour if this option is specified but no
467cdf0e10cSrcweir 	//   filename supplied 'PrToFileName' then the user will be prompted )
468cdf0e10cSrcweir 	// 3 Need to check behaviour of Selected sheets with range ( e.g. From & To
469cdf0e10cSrcweir 	//    values ) in oOO these options are mutually exclusive
470cdf0e10cSrcweir 	// 4 There is a pop up to do with transparent objects in the print source
471cdf0e10cSrcweir 	//   should be able to disable that via configuration for the duration
472cdf0e10cSrcweir 	//   of this method
473cdf0e10cSrcweir }
474cdf0e10cSrcweir 
PrintPreviewHelper(const css::uno::Any &,css::uno::Reference<css::frame::XModel> & xModel)475cdf0e10cSrcweir  void PrintPreviewHelper( const css::uno::Any& /*EnableChanges*/, css::uno::Reference< css::frame::XModel >& xModel )
476cdf0e10cSrcweir {
477cdf0e10cSrcweir 	dispatchExecute( xModel, SID_VIEWSHELL1 );
478cdf0e10cSrcweir }
479cdf0e10cSrcweir 
getAnyAsString(const uno::Any & pvargItem)480cdf0e10cSrcweir rtl::OUString getAnyAsString( const uno::Any& pvargItem ) throw ( uno::RuntimeException )
481cdf0e10cSrcweir {
482cdf0e10cSrcweir 	uno::Type aType = pvargItem.getValueType();
483cdf0e10cSrcweir 	uno::TypeClass eTypeClass = aType.getTypeClass();
484cdf0e10cSrcweir 	rtl::OUString sString;
485cdf0e10cSrcweir 	switch ( eTypeClass )
486cdf0e10cSrcweir 	{
487cdf0e10cSrcweir 		case uno::TypeClass_BOOLEAN:
488cdf0e10cSrcweir 		{
489cdf0e10cSrcweir 			sal_Bool bBool = sal_False;
490cdf0e10cSrcweir 			pvargItem >>= bBool;
491cdf0e10cSrcweir 			sString = rtl::OUString::valueOf( bBool );
492cdf0e10cSrcweir 			break;
493cdf0e10cSrcweir 		}
494cdf0e10cSrcweir 		case uno::TypeClass_STRING:
495cdf0e10cSrcweir 			pvargItem >>= sString;
496cdf0e10cSrcweir 			break;
497cdf0e10cSrcweir 		case uno::TypeClass_FLOAT:
498cdf0e10cSrcweir 			{
499cdf0e10cSrcweir 				float aFloat = 0;
500cdf0e10cSrcweir 				pvargItem >>= aFloat;
501cdf0e10cSrcweir 				sString = rtl::OUString::valueOf( aFloat );
502cdf0e10cSrcweir 				break;
503cdf0e10cSrcweir 			}
504cdf0e10cSrcweir 		case uno::TypeClass_DOUBLE:
505cdf0e10cSrcweir 			{
506cdf0e10cSrcweir 				double aDouble = 0;
507cdf0e10cSrcweir 				pvargItem >>= aDouble;
508cdf0e10cSrcweir 				sString = rtl::OUString::valueOf( aDouble );
509cdf0e10cSrcweir 				break;
510cdf0e10cSrcweir 			}
511cdf0e10cSrcweir 		case uno::TypeClass_SHORT:
512cdf0e10cSrcweir 		case uno::TypeClass_LONG:
513cdf0e10cSrcweir 		case uno::TypeClass_BYTE:
514cdf0e10cSrcweir 			{
515cdf0e10cSrcweir 				sal_Int32 aNum = 0;
516cdf0e10cSrcweir 				pvargItem >>= aNum;
517cdf0e10cSrcweir 				sString = rtl::OUString::valueOf( aNum );
518cdf0e10cSrcweir 				break;
519cdf0e10cSrcweir 			}
520cdf0e10cSrcweir 
521cdf0e10cSrcweir 		case uno::TypeClass_HYPER:
522cdf0e10cSrcweir 			{
523cdf0e10cSrcweir 				sal_Int64 aHyper = 0;
524cdf0e10cSrcweir 				pvargItem >>= aHyper;
525cdf0e10cSrcweir 				sString = rtl::OUString::valueOf( aHyper );
526cdf0e10cSrcweir 				break;
527cdf0e10cSrcweir 			}
528cdf0e10cSrcweir 		default:
529cdf0e10cSrcweir        			throw uno::RuntimeException( rtl::OUString::createFromAscii( "Invalid type, can't convert" ), uno::Reference< uno::XInterface >() );
530cdf0e10cSrcweir 	}
531cdf0e10cSrcweir 	return sString;
532cdf0e10cSrcweir }
533cdf0e10cSrcweir 
534cdf0e10cSrcweir 
535cdf0e10cSrcweir rtl::OUString
getUniqueName(const uno::Sequence<::rtl::OUString> & _slist,const rtl::OUString & _sElementName,const::rtl::OUString & _sSuffixSeparator)536cdf0e10cSrcweir ContainerUtilities::getUniqueName( const uno::Sequence< ::rtl::OUString >&  _slist, const rtl::OUString& _sElementName, const ::rtl::OUString& _sSuffixSeparator)
537cdf0e10cSrcweir {
538cdf0e10cSrcweir 	return getUniqueName(_slist, _sElementName, _sSuffixSeparator, sal_Int32(2));
539cdf0e10cSrcweir }
540cdf0e10cSrcweir 
541cdf0e10cSrcweir rtl::OUString
getUniqueName(const uno::Sequence<rtl::OUString> & _slist,const rtl::OUString _sElementName,const rtl::OUString & _sSuffixSeparator,sal_Int32 _nStartSuffix)542cdf0e10cSrcweir ContainerUtilities::getUniqueName( const uno::Sequence< rtl::OUString >& _slist, const rtl::OUString _sElementName, const rtl::OUString& _sSuffixSeparator, sal_Int32 _nStartSuffix)
543cdf0e10cSrcweir {
544cdf0e10cSrcweir 	sal_Int32 a = _nStartSuffix;
545cdf0e10cSrcweir 	rtl::OUString scompname = _sElementName;
546cdf0e10cSrcweir 	bool bElementexists = true;
547cdf0e10cSrcweir 	sal_Int32 nLen = _slist.getLength();
548cdf0e10cSrcweir 	if ( nLen == 0 )
549cdf0e10cSrcweir 		return _sElementName;
550cdf0e10cSrcweir 
551cdf0e10cSrcweir 	while (bElementexists == true)
552cdf0e10cSrcweir 	{
553cdf0e10cSrcweir 		for (sal_Int32 i = 0; i < nLen; i++)
554cdf0e10cSrcweir 		{
555cdf0e10cSrcweir 			if (FieldInList(_slist, scompname) == -1)
556cdf0e10cSrcweir 			{
557cdf0e10cSrcweir 				return scompname;
558cdf0e10cSrcweir 			}
559cdf0e10cSrcweir 		}
560cdf0e10cSrcweir 		scompname = _sElementName + _sSuffixSeparator + rtl::OUString::valueOf( a++ );
561cdf0e10cSrcweir 	}
562cdf0e10cSrcweir 	return rtl::OUString();
563cdf0e10cSrcweir }
564cdf0e10cSrcweir 
565cdf0e10cSrcweir sal_Int32
FieldInList(const uno::Sequence<rtl::OUString> & SearchList,const rtl::OUString & SearchString)566cdf0e10cSrcweir ContainerUtilities::FieldInList( const uno::Sequence< rtl::OUString >& SearchList, const rtl::OUString& SearchString )
567cdf0e10cSrcweir {
568cdf0e10cSrcweir 	sal_Int32 FieldLen = SearchList.getLength();
569cdf0e10cSrcweir 	sal_Int32 retvalue = -1;
570cdf0e10cSrcweir 	for (sal_Int32 i = 0; i < FieldLen; i++)
571cdf0e10cSrcweir 	{
572cdf0e10cSrcweir 		// I wonder why comparing lexicographically is done
573cdf0e10cSrcweir 		// when its a match is whats interesting?
574cdf0e10cSrcweir 		//if (SearchList[i].compareTo(SearchString) == 0)
575cdf0e10cSrcweir 		if ( SearchList[i].equals( SearchString ) )
576cdf0e10cSrcweir 		{
577cdf0e10cSrcweir 			retvalue = i;
578cdf0e10cSrcweir 			break;
579cdf0e10cSrcweir 		}
580cdf0e10cSrcweir 	}
581cdf0e10cSrcweir 	return retvalue;
582cdf0e10cSrcweir 
583cdf0e10cSrcweir }
NeedEsc(sal_Unicode cCode)584cdf0e10cSrcweir bool NeedEsc(sal_Unicode cCode)
585cdf0e10cSrcweir {
586cdf0e10cSrcweir 	String sEsc(RTL_CONSTASCII_USTRINGPARAM(".^$+\\|{}()"));
587cdf0e10cSrcweir 	return (STRING_NOTFOUND != sEsc.Search(cCode));
588cdf0e10cSrcweir }
589cdf0e10cSrcweir 
VBAToRegexp(const rtl::OUString & rIn,bool bForLike)590cdf0e10cSrcweir rtl::OUString VBAToRegexp(const rtl::OUString &rIn, bool bForLike )
591cdf0e10cSrcweir {
592cdf0e10cSrcweir 	rtl::OUStringBuffer sResult;
593cdf0e10cSrcweir 	const sal_Unicode *start = rIn.getStr();
594cdf0e10cSrcweir 	const sal_Unicode *end = start + rIn.getLength();
595cdf0e10cSrcweir 
596cdf0e10cSrcweir 	int seenright = 0;
597cdf0e10cSrcweir 	if ( bForLike )
598cdf0e10cSrcweir 		sResult.append(static_cast<sal_Unicode>('^'));
599cdf0e10cSrcweir 
600cdf0e10cSrcweir 	while (start < end)
601cdf0e10cSrcweir 	{
602cdf0e10cSrcweir 		switch (*start)
603cdf0e10cSrcweir 		{
604cdf0e10cSrcweir 			case '?':
605cdf0e10cSrcweir 				sResult.append(static_cast<sal_Unicode>('.'));
606cdf0e10cSrcweir 				start++;
607cdf0e10cSrcweir 				break;
608cdf0e10cSrcweir 			case '*':
609cdf0e10cSrcweir 				sResult.append(rtl::OUString(RTL_CONSTASCII_USTRINGPARAM(".*")));
610cdf0e10cSrcweir 				start++;
611cdf0e10cSrcweir 				break;
612cdf0e10cSrcweir 			case '#':
613cdf0e10cSrcweir 				sResult.append(rtl::OUString(RTL_CONSTASCII_USTRINGPARAM("[0-9]")));
614cdf0e10cSrcweir 				start++;
615cdf0e10cSrcweir 				break;
616cdf0e10cSrcweir 			case '~':
617cdf0e10cSrcweir 				sResult.append(static_cast<sal_Unicode>('\\'));
618cdf0e10cSrcweir 				sResult.append(*(++start));
619cdf0e10cSrcweir 				start++;
620cdf0e10cSrcweir 				break;
621cdf0e10cSrcweir 				// dump the ~ and escape the next characture
622cdf0e10cSrcweir 			case ']':
623cdf0e10cSrcweir 				sResult.append(static_cast<sal_Unicode>('\\'));
624cdf0e10cSrcweir 				sResult.append(*start++);
625cdf0e10cSrcweir 				break;
626cdf0e10cSrcweir 			case '[':
627cdf0e10cSrcweir 				sResult.append(*start++);
628cdf0e10cSrcweir 				seenright = 0;
629cdf0e10cSrcweir 				while (start < end && !seenright)
630cdf0e10cSrcweir 				{
631cdf0e10cSrcweir 					switch (*start)
632cdf0e10cSrcweir 					{
633cdf0e10cSrcweir 						case '[':
634cdf0e10cSrcweir 						case '?':
635cdf0e10cSrcweir 						case '*':
636cdf0e10cSrcweir 						sResult.append(static_cast<sal_Unicode>('\\'));
637cdf0e10cSrcweir 						sResult.append(*start);
638cdf0e10cSrcweir 							break;
639cdf0e10cSrcweir 						case ']':
640cdf0e10cSrcweir 						sResult.append(*start);
641cdf0e10cSrcweir 							seenright = 1;
642cdf0e10cSrcweir 							break;
643cdf0e10cSrcweir 						case '!':
644cdf0e10cSrcweir 							sResult.append(static_cast<sal_Unicode>('^'));
645cdf0e10cSrcweir 							break;
646cdf0e10cSrcweir 						default:
647cdf0e10cSrcweir 						if (NeedEsc(*start))
648cdf0e10cSrcweir 							sResult.append(static_cast<sal_Unicode>('\\'));
649cdf0e10cSrcweir 						sResult.append(*start);
650cdf0e10cSrcweir 							break;
651cdf0e10cSrcweir 					}
652cdf0e10cSrcweir 					start++;
653cdf0e10cSrcweir 				}
654cdf0e10cSrcweir 				break;
655cdf0e10cSrcweir 			default:
656cdf0e10cSrcweir 				if (NeedEsc(*start))
657cdf0e10cSrcweir 					sResult.append(static_cast<sal_Unicode>('\\'));
658cdf0e10cSrcweir 				sResult.append(*start++);
659cdf0e10cSrcweir 		}
660cdf0e10cSrcweir 	}
661cdf0e10cSrcweir 
662cdf0e10cSrcweir 	if ( bForLike )
663cdf0e10cSrcweir 		sResult.append(static_cast<sal_Unicode>('$'));
664cdf0e10cSrcweir 
665cdf0e10cSrcweir 	return sResult.makeStringAndClear( );
666cdf0e10cSrcweir }
667cdf0e10cSrcweir 
getPixelTo100thMillimeterConversionFactor(css::uno::Reference<css::awt::XDevice> & xDevice,sal_Bool bVertical)668cdf0e10cSrcweir double getPixelTo100thMillimeterConversionFactor( css::uno::Reference< css::awt::XDevice >& xDevice, sal_Bool bVertical)
669cdf0e10cSrcweir {
670cdf0e10cSrcweir 	double fConvertFactor = 1.0;
671cdf0e10cSrcweir 	if( bVertical )
672cdf0e10cSrcweir 	{
673cdf0e10cSrcweir 		fConvertFactor = xDevice->getInfo().PixelPerMeterY/100000;
674cdf0e10cSrcweir 	}
675cdf0e10cSrcweir 	else
676cdf0e10cSrcweir 	{
677cdf0e10cSrcweir 		fConvertFactor = xDevice->getInfo().PixelPerMeterX/100000;
678cdf0e10cSrcweir 	}
679cdf0e10cSrcweir 	return fConvertFactor;
680cdf0e10cSrcweir }
681cdf0e10cSrcweir 
PointsToPixels(css::uno::Reference<css::awt::XDevice> & xDevice,double fPoints,sal_Bool bVertical)682cdf0e10cSrcweir double PointsToPixels( css::uno::Reference< css::awt::XDevice >& xDevice, double fPoints, sal_Bool bVertical)
683cdf0e10cSrcweir {
684cdf0e10cSrcweir 	double fConvertFactor = getPixelTo100thMillimeterConversionFactor( xDevice, bVertical );
685cdf0e10cSrcweir 	return fPoints * POINTTO100THMILLIMETERFACTOR * fConvertFactor;
686cdf0e10cSrcweir }
PixelsToPoints(css::uno::Reference<css::awt::XDevice> & xDevice,double fPixels,sal_Bool bVertical)687cdf0e10cSrcweir double PixelsToPoints( css::uno::Reference< css::awt::XDevice >& xDevice, double fPixels, sal_Bool bVertical)
688cdf0e10cSrcweir {
689cdf0e10cSrcweir 	double fConvertFactor = getPixelTo100thMillimeterConversionFactor( xDevice, bVertical );
690cdf0e10cSrcweir 	return (fPixels/fConvertFactor)/POINTTO100THMILLIMETERFACTOR;
691cdf0e10cSrcweir }
692cdf0e10cSrcweir 
ConcreteXShapeGeometryAttributes(const css::uno::Reference<css::uno::XComponentContext> & xContext,const css::uno::Reference<css::drawing::XShape> & xShape)693cdf0e10cSrcweir ConcreteXShapeGeometryAttributes::ConcreteXShapeGeometryAttributes( const css::uno::Reference< css::uno::XComponentContext >& xContext, const css::uno::Reference< css::drawing::XShape >& xShape )
694cdf0e10cSrcweir {
695cdf0e10cSrcweir 	m_xShape = new ScVbaShape( xContext, xShape );
696cdf0e10cSrcweir }
697cdf0e10cSrcweir 
698cdf0e10cSrcweir #define VBA_LEFT "PositionX"
699cdf0e10cSrcweir #define VBA_TOP "PositionY"
UserFormGeometryHelper(const uno::Reference<uno::XComponentContext> &,const uno::Reference<awt::XControl> & xControl)700cdf0e10cSrcweir UserFormGeometryHelper::UserFormGeometryHelper( const uno::Reference< uno::XComponentContext >& /*xContext*/, const uno::Reference< awt::XControl >& xControl )
701cdf0e10cSrcweir {
702cdf0e10cSrcweir     mxModel.set( xControl->getModel(), uno::UNO_QUERY_THROW );
703cdf0e10cSrcweir }
getLeft()704cdf0e10cSrcweir     double UserFormGeometryHelper::getLeft()
705cdf0e10cSrcweir     {
706cdf0e10cSrcweir 	sal_Int32 nLeft = 0;
707cdf0e10cSrcweir 	mxModel->getPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( VBA_LEFT ) ) ) >>= nLeft;
708cdf0e10cSrcweir 	return Millimeter::getInPoints( nLeft );
709cdf0e10cSrcweir     }
setLeft(double nLeft)710cdf0e10cSrcweir     void UserFormGeometryHelper::setLeft( double nLeft )
711cdf0e10cSrcweir     {
712cdf0e10cSrcweir         mxModel->setPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( VBA_LEFT ) ), uno::makeAny( Millimeter::getInHundredthsOfOneMillimeter( nLeft ) ) );
713cdf0e10cSrcweir     }
getTop()714cdf0e10cSrcweir     double UserFormGeometryHelper::getTop()
715cdf0e10cSrcweir     {
716cdf0e10cSrcweir 	sal_Int32 nTop = 0;
717cdf0e10cSrcweir 	mxModel->getPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( 	VBA_TOP ) ) ) >>= nTop;
718cdf0e10cSrcweir 	return Millimeter::getInPoints( nTop );
719cdf0e10cSrcweir     }
setTop(double nTop)720cdf0e10cSrcweir     void UserFormGeometryHelper::setTop( double nTop )
721cdf0e10cSrcweir     {
722cdf0e10cSrcweir 	mxModel->setPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( 	VBA_TOP ) ), uno::makeAny( Millimeter::getInHundredthsOfOneMillimeter( nTop ) ) );
723cdf0e10cSrcweir     }
getHeight()724cdf0e10cSrcweir     double UserFormGeometryHelper::getHeight()
725cdf0e10cSrcweir     {
726cdf0e10cSrcweir 	sal_Int32 nHeight = 0;
727cdf0e10cSrcweir 	mxModel->getPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( 	SC_UNONAME_CELLHGT ) ) ) >>= nHeight;
728cdf0e10cSrcweir 	return Millimeter::getInPoints( nHeight );
729cdf0e10cSrcweir     }
setHeight(double nHeight)730cdf0e10cSrcweir     void UserFormGeometryHelper::setHeight( double nHeight )
731cdf0e10cSrcweir     {
732cdf0e10cSrcweir 	mxModel->setPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( 	SC_UNONAME_CELLHGT ) ), uno::makeAny( Millimeter::getInHundredthsOfOneMillimeter( nHeight ) ) );
733cdf0e10cSrcweir     }
getWidth()734cdf0e10cSrcweir     double UserFormGeometryHelper::getWidth()
735cdf0e10cSrcweir     {
736cdf0e10cSrcweir 	sal_Int32 nWidth = 0;
737cdf0e10cSrcweir 	mxModel->getPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( 	SC_UNONAME_CELLWID ) ) ) >>= nWidth;
738cdf0e10cSrcweir 	return Millimeter::getInPoints( nWidth );
739cdf0e10cSrcweir     }
setWidth(double nWidth)740cdf0e10cSrcweir     void UserFormGeometryHelper::setWidth( double nWidth)
741cdf0e10cSrcweir     {
742cdf0e10cSrcweir 	mxModel->setPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( 	SC_UNONAME_CELLWID ) ), uno::makeAny(  Millimeter::getInHundredthsOfOneMillimeter( nWidth ) ) );
743cdf0e10cSrcweir     }
744cdf0e10cSrcweir 
745cdf0e10cSrcweir SfxItemSet*
GetDataSet(ScCellRangeObj * pRangeObj)746cdf0e10cSrcweir ScVbaCellRangeAccess::GetDataSet( ScCellRangeObj* pRangeObj )
747cdf0e10cSrcweir {
748cdf0e10cSrcweir 	SfxItemSet* pDataSet = pRangeObj ? pRangeObj->GetCurrentDataSet( true ) : NULL ;
749cdf0e10cSrcweir 	return pDataSet;
750cdf0e10cSrcweir 
751cdf0e10cSrcweir }
752cdf0e10cSrcweir 
753cdf0e10cSrcweir } // vba
754cdf0e10cSrcweir } // ooo
755