xref: /AOO41X/main/sc/source/ui/vba/vbaapplication.cxx (revision cdf0e10c4e3984b49a9502b011690b615761d4a3)
1*cdf0e10cSrcweir /*************************************************************************
2*cdf0e10cSrcweir  *
3*cdf0e10cSrcweir  * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
4*cdf0e10cSrcweir  *
5*cdf0e10cSrcweir  * Copyright 2000, 2010 Oracle and/or its affiliates.
6*cdf0e10cSrcweir  *
7*cdf0e10cSrcweir  * OpenOffice.org - a multi-platform office productivity suite
8*cdf0e10cSrcweir  *
9*cdf0e10cSrcweir  * This file is part of OpenOffice.org.
10*cdf0e10cSrcweir  *
11*cdf0e10cSrcweir  * OpenOffice.org is free software: you can redistribute it and/or modify
12*cdf0e10cSrcweir  * it under the terms of the GNU Lesser General Public License version 3
13*cdf0e10cSrcweir  * only, as published by the Free Software Foundation.
14*cdf0e10cSrcweir  *
15*cdf0e10cSrcweir  * OpenOffice.org is distributed in the hope that it will be useful,
16*cdf0e10cSrcweir  * but WITHOUT ANY WARRANTY; without even the implied warranty of
17*cdf0e10cSrcweir  * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
18*cdf0e10cSrcweir  * GNU Lesser General Public License version 3 for more details
19*cdf0e10cSrcweir  * (a copy is included in the LICENSE file that accompanied this code).
20*cdf0e10cSrcweir  *
21*cdf0e10cSrcweir  * You should have received a copy of the GNU Lesser General Public License
22*cdf0e10cSrcweir  * version 3 along with OpenOffice.org.  If not, see
23*cdf0e10cSrcweir  * <http://www.openoffice.org/license.html>
24*cdf0e10cSrcweir  * for a copy of the LGPLv3 License.
25*cdf0e10cSrcweir  *
26*cdf0e10cSrcweir  ************************************************************************/
27*cdf0e10cSrcweir 
28*cdf0e10cSrcweir #include <stdio.h>
29*cdf0e10cSrcweir 
30*cdf0e10cSrcweir #include <com/sun/star/sheet/XSpreadsheetView.hpp>
31*cdf0e10cSrcweir #include <com/sun/star/sheet/XSpreadsheets.hpp>
32*cdf0e10cSrcweir #include <com/sun/star/view/XSelectionSupplier.hpp>
33*cdf0e10cSrcweir #include <com/sun/star/lang/XServiceInfo.hpp>
34*cdf0e10cSrcweir #include <ooo/vba/excel/XlCalculation.hpp>
35*cdf0e10cSrcweir #include <com/sun/star/sheet/XCellRangeReferrer.hpp>
36*cdf0e10cSrcweir #include <com/sun/star/sheet/XCalculatable.hpp>
37*cdf0e10cSrcweir #include <com/sun/star/frame/XLayoutManager.hpp>
38*cdf0e10cSrcweir #include <com/sun/star/task/XStatusIndicatorSupplier.hpp>
39*cdf0e10cSrcweir #include <com/sun/star/task/XStatusIndicator.hpp>
40*cdf0e10cSrcweir #include <ooo/vba/excel/XlMousePointer.hpp>
41*cdf0e10cSrcweir #include <com/sun/star/sheet/XNamedRanges.hpp>
42*cdf0e10cSrcweir #include <com/sun/star/sheet/XCellRangeAddressable.hpp>
43*cdf0e10cSrcweir #include <ooo/vba/XExecutableDialog.hpp>
44*cdf0e10cSrcweir 
45*cdf0e10cSrcweir #include "vbaapplication.hxx"
46*cdf0e10cSrcweir #include "vbaworkbooks.hxx"
47*cdf0e10cSrcweir #include "vbaworkbook.hxx"
48*cdf0e10cSrcweir #include "vbaworksheets.hxx"
49*cdf0e10cSrcweir #include "vbarange.hxx"
50*cdf0e10cSrcweir #include "vbawsfunction.hxx"
51*cdf0e10cSrcweir #include "vbadialogs.hxx"
52*cdf0e10cSrcweir #include "vbawindow.hxx"
53*cdf0e10cSrcweir #include "vbawindows.hxx"
54*cdf0e10cSrcweir #include "vbaglobals.hxx"
55*cdf0e10cSrcweir #include "tabvwsh.hxx"
56*cdf0e10cSrcweir #include "gridwin.hxx"
57*cdf0e10cSrcweir #include "vbanames.hxx"
58*cdf0e10cSrcweir #include <vbahelper/vbashape.hxx>
59*cdf0e10cSrcweir #include "vbatextboxshape.hxx"
60*cdf0e10cSrcweir #include "vbaassistant.hxx"
61*cdf0e10cSrcweir #include "sc.hrc"
62*cdf0e10cSrcweir 
63*cdf0e10cSrcweir #include <osl/file.hxx>
64*cdf0e10cSrcweir #include <rtl/instance.hxx>
65*cdf0e10cSrcweir 
66*cdf0e10cSrcweir #include <sfx2/request.hxx>
67*cdf0e10cSrcweir #include <sfx2/objsh.hxx>
68*cdf0e10cSrcweir #include <sfx2/viewfrm.hxx>
69*cdf0e10cSrcweir #include <sfx2/app.hxx>
70*cdf0e10cSrcweir 
71*cdf0e10cSrcweir #include <toolkit/awt/vclxwindow.hxx>
72*cdf0e10cSrcweir #include <toolkit/helper/vclunohelper.hxx>
73*cdf0e10cSrcweir 
74*cdf0e10cSrcweir #include <tools/diagnose_ex.h>
75*cdf0e10cSrcweir 
76*cdf0e10cSrcweir #include <docuno.hxx>
77*cdf0e10cSrcweir 
78*cdf0e10cSrcweir #include <basic/sbx.hxx>
79*cdf0e10cSrcweir #include <basic/sbstar.hxx>
80*cdf0e10cSrcweir #include <basic/sbuno.hxx>
81*cdf0e10cSrcweir #include <basic/sbmeth.hxx>
82*cdf0e10cSrcweir 
83*cdf0e10cSrcweir #include "convuno.hxx"
84*cdf0e10cSrcweir #include "cellsuno.hxx"
85*cdf0e10cSrcweir #include "docsh.hxx"
86*cdf0e10cSrcweir #include <vbahelper/helperdecl.hxx>
87*cdf0e10cSrcweir #include "excelvbahelper.hxx"
88*cdf0e10cSrcweir 
89*cdf0e10cSrcweir 
90*cdf0e10cSrcweir using namespace ::ooo::vba;
91*cdf0e10cSrcweir using namespace ::com::sun::star;
92*cdf0e10cSrcweir 
93*cdf0e10cSrcweir // #TODO is this defined somewhere else?
94*cdf0e10cSrcweir #if ( defined UNX ) || ( defined OS2 ) //unix
95*cdf0e10cSrcweir #define FILE_PATH_SEPERATOR "/"
96*cdf0e10cSrcweir #else // windows
97*cdf0e10cSrcweir #define FILE_PATH_SEPERATOR "\\"
98*cdf0e10cSrcweir #endif
99*cdf0e10cSrcweir 
100*cdf0e10cSrcweir uno::Any sbxToUnoValue( SbxVariable* pVar );
101*cdf0e10cSrcweir 
102*cdf0e10cSrcweir // ============================================================================
103*cdf0e10cSrcweir 
104*cdf0e10cSrcweir /** Global application settings shared by all open workbooks. */
105*cdf0e10cSrcweir struct ScVbaAppSettings
106*cdf0e10cSrcweir {
107*cdf0e10cSrcweir     sal_Int32 mnCalculation;
108*cdf0e10cSrcweir     sal_Bool mbDisplayAlerts;
109*cdf0e10cSrcweir     sal_Bool mbEnableEvents;
110*cdf0e10cSrcweir 
111*cdf0e10cSrcweir     explicit ScVbaAppSettings();
112*cdf0e10cSrcweir };
113*cdf0e10cSrcweir 
114*cdf0e10cSrcweir ScVbaAppSettings::ScVbaAppSettings() :
115*cdf0e10cSrcweir     mnCalculation( excel::XlCalculation::xlCalculationAutomatic ),
116*cdf0e10cSrcweir     mbDisplayAlerts( sal_True ),
117*cdf0e10cSrcweir     mbEnableEvents( sal_True )
118*cdf0e10cSrcweir {
119*cdf0e10cSrcweir }
120*cdf0e10cSrcweir 
121*cdf0e10cSrcweir struct ScVbaStaticAppSettings : public ::rtl::Static< ScVbaAppSettings, ScVbaStaticAppSettings > {};
122*cdf0e10cSrcweir 
123*cdf0e10cSrcweir // ============================================================================
124*cdf0e10cSrcweir 
125*cdf0e10cSrcweir ScVbaApplication::ScVbaApplication( const uno::Reference<uno::XComponentContext >& xContext ) :
126*cdf0e10cSrcweir     ScVbaApplication_BASE( xContext ),
127*cdf0e10cSrcweir     mrAppSettings( ScVbaStaticAppSettings::get() )
128*cdf0e10cSrcweir {
129*cdf0e10cSrcweir }
130*cdf0e10cSrcweir 
131*cdf0e10cSrcweir ScVbaApplication::~ScVbaApplication()
132*cdf0e10cSrcweir {
133*cdf0e10cSrcweir }
134*cdf0e10cSrcweir 
135*cdf0e10cSrcweir /*static*/ bool ScVbaApplication::getDocumentEventsEnabled()
136*cdf0e10cSrcweir {
137*cdf0e10cSrcweir     return ScVbaStaticAppSettings::get().mbEnableEvents;
138*cdf0e10cSrcweir }
139*cdf0e10cSrcweir 
140*cdf0e10cSrcweir SfxObjectShell* ScVbaApplication::GetDocShell( const uno::Reference< frame::XModel >& xModel ) throw (uno::RuntimeException)
141*cdf0e10cSrcweir {
142*cdf0e10cSrcweir     return static_cast< SfxObjectShell* >( excel::getDocShell( xModel ) );
143*cdf0e10cSrcweir }
144*cdf0e10cSrcweir 
145*cdf0e10cSrcweir ::rtl::OUString SAL_CALL
146*cdf0e10cSrcweir ScVbaApplication::getExactName( const ::rtl::OUString& aApproximateName ) throw (uno::RuntimeException)
147*cdf0e10cSrcweir {
148*cdf0e10cSrcweir     uno::Reference< beans::XExactName > xWSF( new ScVbaWSFunction( this, mxContext ) );
149*cdf0e10cSrcweir     return xWSF->getExactName( aApproximateName );
150*cdf0e10cSrcweir }
151*cdf0e10cSrcweir 
152*cdf0e10cSrcweir uno::Reference< beans::XIntrospectionAccess > SAL_CALL
153*cdf0e10cSrcweir ScVbaApplication::getIntrospection() throw(css::uno::RuntimeException)
154*cdf0e10cSrcweir {
155*cdf0e10cSrcweir     uno::Reference< script::XInvocation > xWSF( new ScVbaWSFunction( this, mxContext ) );
156*cdf0e10cSrcweir     return xWSF->getIntrospection();
157*cdf0e10cSrcweir }
158*cdf0e10cSrcweir 
159*cdf0e10cSrcweir uno::Any SAL_CALL
160*cdf0e10cSrcweir ScVbaApplication::invoke( const ::rtl::OUString& FunctionName, const uno::Sequence< uno::Any >& Params, uno::Sequence< sal_Int16 >& OutParamIndex, uno::Sequence< uno::Any >& OutParam) throw(lang::IllegalArgumentException, script::CannotConvertException, reflection::InvocationTargetException, uno::RuntimeException)
161*cdf0e10cSrcweir {
162*cdf0e10cSrcweir     /*  When calling the functions directly at the Application object, no runtime
163*cdf0e10cSrcweir         errors are thrown, but the error is inserted into the return value. */
164*cdf0e10cSrcweir     uno::Any aAny;
165*cdf0e10cSrcweir     try
166*cdf0e10cSrcweir     {
167*cdf0e10cSrcweir         uno::Reference< script::XInvocation > xWSF( new ScVbaWSFunction( this, mxContext ) );
168*cdf0e10cSrcweir         aAny = xWSF->invoke( FunctionName, Params, OutParamIndex, OutParam );
169*cdf0e10cSrcweir     }
170*cdf0e10cSrcweir     catch( uno::Exception& )
171*cdf0e10cSrcweir     {
172*cdf0e10cSrcweir         aAny <<= script::BasicErrorException( ::rtl::OUString(), uno::Reference< uno::XInterface >(), 1000, ::rtl::OUString() );
173*cdf0e10cSrcweir     }
174*cdf0e10cSrcweir     return aAny;
175*cdf0e10cSrcweir }
176*cdf0e10cSrcweir 
177*cdf0e10cSrcweir void SAL_CALL
178*cdf0e10cSrcweir ScVbaApplication::setValue( const ::rtl::OUString& PropertyName, const uno::Any& Value ) throw(beans::UnknownPropertyException, script::CannotConvertException, reflection::InvocationTargetException, uno::RuntimeException)
179*cdf0e10cSrcweir {
180*cdf0e10cSrcweir     uno::Reference< script::XInvocation > xWSF( new ScVbaWSFunction( this, mxContext ) );
181*cdf0e10cSrcweir     xWSF->setValue( PropertyName, Value );
182*cdf0e10cSrcweir }
183*cdf0e10cSrcweir 
184*cdf0e10cSrcweir uno::Any SAL_CALL
185*cdf0e10cSrcweir ScVbaApplication::getValue( const ::rtl::OUString& PropertyName ) throw(beans::UnknownPropertyException, uno::RuntimeException)
186*cdf0e10cSrcweir {
187*cdf0e10cSrcweir     uno::Reference< script::XInvocation > xWSF( new ScVbaWSFunction( this, mxContext ) );
188*cdf0e10cSrcweir     return xWSF->getValue( PropertyName );
189*cdf0e10cSrcweir }
190*cdf0e10cSrcweir 
191*cdf0e10cSrcweir sal_Bool SAL_CALL
192*cdf0e10cSrcweir ScVbaApplication::hasMethod( const ::rtl::OUString& Name ) throw(uno::RuntimeException)
193*cdf0e10cSrcweir {
194*cdf0e10cSrcweir     uno::Reference< script::XInvocation > xWSF( new ScVbaWSFunction( this, mxContext ) );
195*cdf0e10cSrcweir     return xWSF->hasMethod( Name );
196*cdf0e10cSrcweir }
197*cdf0e10cSrcweir 
198*cdf0e10cSrcweir sal_Bool SAL_CALL
199*cdf0e10cSrcweir ScVbaApplication::hasProperty( const ::rtl::OUString& Name ) throw(uno::RuntimeException)
200*cdf0e10cSrcweir {
201*cdf0e10cSrcweir     uno::Reference< script::XInvocation > xWSF( new ScVbaWSFunction( this, mxContext ) );
202*cdf0e10cSrcweir     return xWSF->hasProperty( Name );
203*cdf0e10cSrcweir }
204*cdf0e10cSrcweir 
205*cdf0e10cSrcweir uno::Reference< excel::XWorkbook >
206*cdf0e10cSrcweir ScVbaApplication::getActiveWorkbook() throw (uno::RuntimeException)
207*cdf0e10cSrcweir {
208*cdf0e10cSrcweir     // will throw if active document is not in VBA compatibility mode (no object for codename)
209*cdf0e10cSrcweir     return uno::Reference< excel::XWorkbook >( getVBADocument( getCurrentExcelDoc( mxContext ) ), uno::UNO_QUERY_THROW );
210*cdf0e10cSrcweir }
211*cdf0e10cSrcweir 
212*cdf0e10cSrcweir uno::Reference< excel::XWorkbook > SAL_CALL
213*cdf0e10cSrcweir ScVbaApplication::getThisWorkbook() throw (uno::RuntimeException)
214*cdf0e10cSrcweir {
215*cdf0e10cSrcweir     // should never throw as this model is in VBA compatibility mode
216*cdf0e10cSrcweir     return uno::Reference< excel::XWorkbook >( getVBADocument( getThisExcelDoc( mxContext ) ), uno::UNO_QUERY_THROW );
217*cdf0e10cSrcweir }
218*cdf0e10cSrcweir 
219*cdf0e10cSrcweir uno::Reference< XAssistant > SAL_CALL
220*cdf0e10cSrcweir ScVbaApplication::getAssistant() throw (uno::RuntimeException)
221*cdf0e10cSrcweir {
222*cdf0e10cSrcweir     return uno::Reference< XAssistant >( new ScVbaAssistant( this, mxContext ) );
223*cdf0e10cSrcweir }
224*cdf0e10cSrcweir 
225*cdf0e10cSrcweir uno::Any SAL_CALL
226*cdf0e10cSrcweir ScVbaApplication::getSelection() throw (uno::RuntimeException)
227*cdf0e10cSrcweir {
228*cdf0e10cSrcweir     OSL_TRACE("** ScVbaApplication::getSelection() ** ");
229*cdf0e10cSrcweir     uno::Reference< frame::XModel > xModel( getCurrentDocument() );
230*cdf0e10cSrcweir     uno::Reference< lang::XServiceInfo > xServiceInfo( xModel->getCurrentSelection(), uno::UNO_QUERY_THROW );
231*cdf0e10cSrcweir     rtl::OUString sImpementaionName = xServiceInfo->getImplementationName();
232*cdf0e10cSrcweir     if( sImpementaionName.equalsIgnoreAsciiCaseAscii("com.sun.star.drawing.SvxShapeCollection") )
233*cdf0e10cSrcweir     {
234*cdf0e10cSrcweir         uno::Reference< drawing::XShapes > xShapes( xModel->getCurrentSelection(), uno::UNO_QUERY_THROW );
235*cdf0e10cSrcweir         uno::Reference< container::XIndexAccess > xIndexAccess( xShapes, uno::UNO_QUERY_THROW );
236*cdf0e10cSrcweir         uno::Reference< drawing::XShape > xShape( xIndexAccess->getByIndex(0), uno::UNO_QUERY_THROW );
237*cdf0e10cSrcweir 	// if ScVbaShape::getType( xShape ) == office::MsoShapeType::msoAutoShape
238*cdf0e10cSrcweir 	// and the uno object implements the com.sun.star.drawing.Text service
239*cdf0e10cSrcweir 	// return a textboxshape object
240*cdf0e10cSrcweir 	if ( ScVbaShape::getType( xShape ) == office::MsoShapeType::msoAutoShape )
241*cdf0e10cSrcweir 	{
242*cdf0e10cSrcweir 		uno::Reference< lang::XServiceInfo > xShapeServiceInfo( xShape, uno::UNO_QUERY_THROW );
243*cdf0e10cSrcweir 		if ( xShapeServiceInfo->supportsService( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "com.sun.star.drawing.Text" ) ) )  )
244*cdf0e10cSrcweir 		{
245*cdf0e10cSrcweir                 return uno::makeAny( uno::Reference< msforms::XTextBoxShape >(new ScVbaTextBoxShape( mxContext, xShape, xShapes, xModel ) ) );
246*cdf0e10cSrcweir 		}
247*cdf0e10cSrcweir 	}
248*cdf0e10cSrcweir         return uno::makeAny( uno::Reference< msforms::XShape >(new ScVbaShape( this, mxContext, xShape, xShapes, xModel, ScVbaShape::getType( xShape ) ) ) );
249*cdf0e10cSrcweir     }
250*cdf0e10cSrcweir     else if( xServiceInfo->supportsService( rtl::OUString::createFromAscii("com.sun.star.sheet.SheetCellRange")) ||
251*cdf0e10cSrcweir              xServiceInfo->supportsService( rtl::OUString::createFromAscii("com.sun.star.sheet.SheetCellRanges")))
252*cdf0e10cSrcweir     {
253*cdf0e10cSrcweir 	    uno::Reference< table::XCellRange > xRange( getCurrentDocument()->getCurrentSelection(), ::uno::UNO_QUERY);
254*cdf0e10cSrcweir 	    if ( !xRange.is() )
255*cdf0e10cSrcweir 	    {
256*cdf0e10cSrcweir 		    uno::Reference< sheet::XSheetCellRangeContainer > xRanges( getCurrentDocument()->getCurrentSelection(), ::uno::UNO_QUERY);
257*cdf0e10cSrcweir 		    if ( xRanges.is() )
258*cdf0e10cSrcweir                 return uno::makeAny( uno::Reference< excel::XRange >( new ScVbaRange( excel::getUnoSheetModuleObj( xRanges ), mxContext, xRanges ) ) );
259*cdf0e10cSrcweir 
260*cdf0e10cSrcweir 	    }
261*cdf0e10cSrcweir         return uno::makeAny( uno::Reference< excel::XRange >(new ScVbaRange( excel::getUnoSheetModuleObj( xRange ), mxContext, xRange ) ) );
262*cdf0e10cSrcweir     }
263*cdf0e10cSrcweir     else
264*cdf0e10cSrcweir     {
265*cdf0e10cSrcweir         throw uno::RuntimeException( sImpementaionName + rtl::OUString::createFromAscii(" not suported"), uno::Reference< uno::XInterface >() );
266*cdf0e10cSrcweir     }
267*cdf0e10cSrcweir }
268*cdf0e10cSrcweir 
269*cdf0e10cSrcweir uno::Reference< excel::XRange >
270*cdf0e10cSrcweir ScVbaApplication::getActiveCell() throw (uno::RuntimeException )
271*cdf0e10cSrcweir {
272*cdf0e10cSrcweir 	uno::Reference< sheet::XSpreadsheetView > xView( getCurrentDocument()->getCurrentController(), uno::UNO_QUERY_THROW );
273*cdf0e10cSrcweir 	uno::Reference< table::XCellRange > xRange( xView->getActiveSheet(), ::uno::UNO_QUERY_THROW);
274*cdf0e10cSrcweir 	ScTabViewShell* pViewShell = excel::getCurrentBestViewShell(mxContext);
275*cdf0e10cSrcweir 	if ( !pViewShell )
276*cdf0e10cSrcweir 		throw uno::RuntimeException( rtl::OUString::createFromAscii("No ViewShell available"), uno::Reference< uno::XInterface >() );
277*cdf0e10cSrcweir 	ScViewData* pTabView = pViewShell->GetViewData();
278*cdf0e10cSrcweir 	if ( !pTabView )
279*cdf0e10cSrcweir 		throw uno::RuntimeException( rtl::OUString::createFromAscii("No ViewData available"), uno::Reference< uno::XInterface >() );
280*cdf0e10cSrcweir 
281*cdf0e10cSrcweir 	sal_Int32 nCursorX = pTabView->GetCurX();
282*cdf0e10cSrcweir 	sal_Int32 nCursorY = pTabView->GetCurY();
283*cdf0e10cSrcweir 
284*cdf0e10cSrcweir     // #i117392# excel::getUnoSheetModuleObj() may return null in documents without global VBA mode enabled
285*cdf0e10cSrcweir 	return new ScVbaRange( excel::getUnoSheetModuleObj( xRange ), mxContext, xRange->getCellRangeByPosition( nCursorX, nCursorY, nCursorX, nCursorY ) );
286*cdf0e10cSrcweir }
287*cdf0e10cSrcweir 
288*cdf0e10cSrcweir uno::Any SAL_CALL
289*cdf0e10cSrcweir ScVbaApplication::Workbooks( const uno::Any& aIndex ) throw (uno::RuntimeException)
290*cdf0e10cSrcweir {
291*cdf0e10cSrcweir 	uno::Reference< XCollection > xWorkBooks( new ScVbaWorkbooks( this, mxContext ) );
292*cdf0e10cSrcweir 	if (  aIndex.getValueTypeClass() == uno::TypeClass_VOID )
293*cdf0e10cSrcweir 	{
294*cdf0e10cSrcweir 		// void then somebody did Workbooks.something in vba
295*cdf0e10cSrcweir 	    return uno::Any( xWorkBooks );
296*cdf0e10cSrcweir 	}
297*cdf0e10cSrcweir 
298*cdf0e10cSrcweir 	return uno::Any ( xWorkBooks->Item( aIndex, uno::Any() ) );
299*cdf0e10cSrcweir }
300*cdf0e10cSrcweir 
301*cdf0e10cSrcweir uno::Any SAL_CALL
302*cdf0e10cSrcweir ScVbaApplication::Worksheets( const uno::Any& aIndex ) throw (uno::RuntimeException)
303*cdf0e10cSrcweir {
304*cdf0e10cSrcweir     uno::Reference< excel::XWorkbook > xWorkbook( getActiveWorkbook(), uno::UNO_SET_THROW );
305*cdf0e10cSrcweir     return xWorkbook->Worksheets( aIndex );
306*cdf0e10cSrcweir }
307*cdf0e10cSrcweir 
308*cdf0e10cSrcweir uno::Any SAL_CALL
309*cdf0e10cSrcweir ScVbaApplication::WorksheetFunction( ) throw (::com::sun::star::uno::RuntimeException)
310*cdf0e10cSrcweir {
311*cdf0e10cSrcweir     return uno::makeAny( uno::Reference< script::XInvocation >( new ScVbaWSFunction( this, mxContext ) ) );
312*cdf0e10cSrcweir }
313*cdf0e10cSrcweir 
314*cdf0e10cSrcweir uno::Any SAL_CALL
315*cdf0e10cSrcweir ScVbaApplication::Evaluate( const ::rtl::OUString& Name ) throw (uno::RuntimeException)
316*cdf0e10cSrcweir {
317*cdf0e10cSrcweir 	// #TODO Evaluate allows other things to be evaluated, e.g. functions
318*cdf0e10cSrcweir 	// I think ( like SIN(3) etc. ) need to investigate that
319*cdf0e10cSrcweir 	// named Ranges also? e.g. [MyRange] if so need a list of named ranges
320*cdf0e10cSrcweir 	uno::Any aVoid;
321*cdf0e10cSrcweir 	return uno::Any( getActiveWorkbook()->getActiveSheet()->Range( uno::Any( Name ), aVoid ) );
322*cdf0e10cSrcweir }
323*cdf0e10cSrcweir 
324*cdf0e10cSrcweir uno::Any
325*cdf0e10cSrcweir ScVbaApplication::Dialogs( const uno::Any &aIndex ) throw (uno::RuntimeException)
326*cdf0e10cSrcweir {
327*cdf0e10cSrcweir 	uno::Reference< excel::XDialogs > xDialogs( new ScVbaDialogs( uno::Reference< XHelperInterface >( this ), mxContext, getCurrentDocument() ) );
328*cdf0e10cSrcweir 	if( !aIndex.hasValue() )
329*cdf0e10cSrcweir 		return uno::Any( xDialogs );
330*cdf0e10cSrcweir 	return uno::Any( xDialogs->Item( aIndex ) );
331*cdf0e10cSrcweir }
332*cdf0e10cSrcweir 
333*cdf0e10cSrcweir uno::Reference< excel::XWindow > SAL_CALL
334*cdf0e10cSrcweir ScVbaApplication::getActiveWindow() throw (uno::RuntimeException)
335*cdf0e10cSrcweir {
336*cdf0e10cSrcweir 	uno::Reference< frame::XModel > xModel = getCurrentDocument();
337*cdf0e10cSrcweir 	uno::Reference< frame::XController > xController( xModel->getCurrentController(), uno::UNO_SET_THROW );
338*cdf0e10cSrcweir 	uno::Reference< XHelperInterface > xParent( getActiveWorkbook(), uno::UNO_QUERY_THROW );
339*cdf0e10cSrcweir 	uno::Reference< excel::XWindow > xWin( new ScVbaWindow( xParent, mxContext, xModel, xController ) );
340*cdf0e10cSrcweir 	return xWin;
341*cdf0e10cSrcweir }
342*cdf0e10cSrcweir 
343*cdf0e10cSrcweir uno::Any SAL_CALL
344*cdf0e10cSrcweir ScVbaApplication::getCutCopyMode() throw (uno::RuntimeException)
345*cdf0e10cSrcweir {
346*cdf0e10cSrcweir 	//# FIXME TODO, implementation
347*cdf0e10cSrcweir 	uno::Any result;
348*cdf0e10cSrcweir 	result <<= sal_False;
349*cdf0e10cSrcweir 	return result;
350*cdf0e10cSrcweir }
351*cdf0e10cSrcweir 
352*cdf0e10cSrcweir void SAL_CALL
353*cdf0e10cSrcweir ScVbaApplication::setCutCopyMode( const uno::Any& /*_cutcopymode*/ ) throw (uno::RuntimeException)
354*cdf0e10cSrcweir {
355*cdf0e10cSrcweir 	//# FIXME TODO, implementation
356*cdf0e10cSrcweir }
357*cdf0e10cSrcweir 
358*cdf0e10cSrcweir uno::Any SAL_CALL
359*cdf0e10cSrcweir ScVbaApplication::getStatusBar() throw (uno::RuntimeException)
360*cdf0e10cSrcweir {
361*cdf0e10cSrcweir 	return uno::makeAny( !getDisplayStatusBar() );
362*cdf0e10cSrcweir }
363*cdf0e10cSrcweir 
364*cdf0e10cSrcweir void SAL_CALL
365*cdf0e10cSrcweir ScVbaApplication::setStatusBar( const uno::Any& _statusbar ) throw (uno::RuntimeException)
366*cdf0e10cSrcweir {
367*cdf0e10cSrcweir     rtl::OUString sText;
368*cdf0e10cSrcweir     sal_Bool bDefault = sal_False;
369*cdf0e10cSrcweir 	uno::Reference< frame::XModel > xModel( getCurrentDocument(), uno::UNO_QUERY_THROW );
370*cdf0e10cSrcweir     uno::Reference< task::XStatusIndicatorSupplier > xStatusIndicatorSupplier( xModel->getCurrentController(), uno::UNO_QUERY_THROW );
371*cdf0e10cSrcweir     uno::Reference< task::XStatusIndicator > xStatusIndicator( xStatusIndicatorSupplier->getStatusIndicator(), uno::UNO_QUERY_THROW );
372*cdf0e10cSrcweir     if( _statusbar >>= sText )
373*cdf0e10cSrcweir     {
374*cdf0e10cSrcweir         setDisplayStatusBar( sal_True );
375*cdf0e10cSrcweir         if ( sText.getLength() )
376*cdf0e10cSrcweir             xStatusIndicator->start( sText, 100 );
377*cdf0e10cSrcweir         else
378*cdf0e10cSrcweir             xStatusIndicator->end();        // restore normal state for empty text
379*cdf0e10cSrcweir     }
380*cdf0e10cSrcweir     else if( _statusbar >>= bDefault )
381*cdf0e10cSrcweir     {
382*cdf0e10cSrcweir         if( bDefault == sal_False )
383*cdf0e10cSrcweir         {
384*cdf0e10cSrcweir             xStatusIndicator->end();
385*cdf0e10cSrcweir             setDisplayStatusBar( sal_True );
386*cdf0e10cSrcweir         }
387*cdf0e10cSrcweir     }
388*cdf0e10cSrcweir     else
389*cdf0e10cSrcweir         throw uno::RuntimeException( rtl::OUString::createFromAscii( "Invalid prarameter. It should be a string or False" ),
390*cdf0e10cSrcweir             uno::Reference< uno::XInterface >() );
391*cdf0e10cSrcweir }
392*cdf0e10cSrcweir 
393*cdf0e10cSrcweir ::sal_Int32 SAL_CALL
394*cdf0e10cSrcweir ScVbaApplication::getCalculation() throw (uno::RuntimeException)
395*cdf0e10cSrcweir {
396*cdf0e10cSrcweir     // TODO: in Excel, this is an application-wide setting
397*cdf0e10cSrcweir 	uno::Reference<sheet::XCalculatable> xCalc(getCurrentDocument(), uno::UNO_QUERY_THROW);
398*cdf0e10cSrcweir 	if(xCalc->isAutomaticCalculationEnabled())
399*cdf0e10cSrcweir 		return excel::XlCalculation::xlCalculationAutomatic;
400*cdf0e10cSrcweir 	else
401*cdf0e10cSrcweir 		return excel::XlCalculation::xlCalculationManual;
402*cdf0e10cSrcweir }
403*cdf0e10cSrcweir 
404*cdf0e10cSrcweir void SAL_CALL
405*cdf0e10cSrcweir ScVbaApplication::setCalculation( ::sal_Int32 _calculation ) throw (uno::RuntimeException)
406*cdf0e10cSrcweir {
407*cdf0e10cSrcweir     // TODO: in Excel, this is an application-wide setting
408*cdf0e10cSrcweir 	uno::Reference< sheet::XCalculatable > xCalc(getCurrentDocument(), uno::UNO_QUERY_THROW);
409*cdf0e10cSrcweir 	switch(_calculation)
410*cdf0e10cSrcweir 	{
411*cdf0e10cSrcweir 		case excel::XlCalculation::xlCalculationManual:
412*cdf0e10cSrcweir 			xCalc->enableAutomaticCalculation(sal_False);
413*cdf0e10cSrcweir 			break;
414*cdf0e10cSrcweir 		case excel::XlCalculation::xlCalculationAutomatic:
415*cdf0e10cSrcweir 		case excel::XlCalculation::xlCalculationSemiautomatic:
416*cdf0e10cSrcweir 			xCalc->enableAutomaticCalculation(sal_True);
417*cdf0e10cSrcweir 			break;
418*cdf0e10cSrcweir 	}
419*cdf0e10cSrcweir }
420*cdf0e10cSrcweir 
421*cdf0e10cSrcweir uno::Any SAL_CALL
422*cdf0e10cSrcweir ScVbaApplication::Windows( const uno::Any& aIndex  ) throw (uno::RuntimeException)
423*cdf0e10cSrcweir {
424*cdf0e10cSrcweir 	uno::Reference< excel::XWindows >  xWindows( new ScVbaWindows( this, mxContext ) );
425*cdf0e10cSrcweir 	if ( aIndex.getValueTypeClass() == uno::TypeClass_VOID )
426*cdf0e10cSrcweir 		return uno::Any( xWindows );
427*cdf0e10cSrcweir 	return uno::Any( xWindows->Item( aIndex, uno::Any() ) );
428*cdf0e10cSrcweir }
429*cdf0e10cSrcweir void SAL_CALL
430*cdf0e10cSrcweir ScVbaApplication::wait( double time ) throw (uno::RuntimeException)
431*cdf0e10cSrcweir {
432*cdf0e10cSrcweir 	StarBASIC* pBasic = SFX_APP()->GetBasic();
433*cdf0e10cSrcweir 	SbxArrayRef aArgs = new SbxArray;
434*cdf0e10cSrcweir 	SbxVariableRef aRef = new SbxVariable;
435*cdf0e10cSrcweir 	aRef->PutDouble( time );
436*cdf0e10cSrcweir 	aArgs->Put(  aRef, 1 );
437*cdf0e10cSrcweir 	SbMethod* pMeth = (SbMethod*)pBasic->GetRtl()->Find( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("WaitUntil") ), SbxCLASS_METHOD );
438*cdf0e10cSrcweir 
439*cdf0e10cSrcweir 	if ( pMeth )
440*cdf0e10cSrcweir 	{
441*cdf0e10cSrcweir 		pMeth->SetParameters( aArgs );
442*cdf0e10cSrcweir 		SbxVariableRef refTemp = pMeth;
443*cdf0e10cSrcweir 		// forces a broadcast
444*cdf0e10cSrcweir 		SbxVariableRef pNew = new  SbxMethod( *((SbxMethod*)pMeth));
445*cdf0e10cSrcweir 	}
446*cdf0e10cSrcweir }
447*cdf0e10cSrcweir 
448*cdf0e10cSrcweir uno::Any SAL_CALL
449*cdf0e10cSrcweir ScVbaApplication::Range( const uno::Any& Cell1, const uno::Any& Cell2 ) throw (uno::RuntimeException)
450*cdf0e10cSrcweir {
451*cdf0e10cSrcweir 	uno::Reference< excel::XRange > xVbRange = ScVbaRange::ApplicationRange( mxContext, Cell1, Cell2 );
452*cdf0e10cSrcweir 	return uno::makeAny( xVbRange );
453*cdf0e10cSrcweir }
454*cdf0e10cSrcweir 
455*cdf0e10cSrcweir uno::Any SAL_CALL
456*cdf0e10cSrcweir ScVbaApplication::Names( const css::uno::Any& aIndex ) throw ( uno::RuntimeException )
457*cdf0e10cSrcweir {
458*cdf0e10cSrcweir     uno::Reference< frame::XModel > xModel( getCurrentDocument(), uno::UNO_QUERY_THROW );
459*cdf0e10cSrcweir     uno::Reference< beans::XPropertySet > xPropertySet( xModel, uno::UNO_QUERY_THROW );
460*cdf0e10cSrcweir     uno::Reference< sheet::XNamedRanges > xNamedRanges( xPropertySet->getPropertyValue( rtl::OUString::createFromAscii("NamedRanges")) , uno::UNO_QUERY_THROW );
461*cdf0e10cSrcweir     css::uno::Reference< excel::XNames > xNames ( new ScVbaNames( this , mxContext , xNamedRanges , xModel ) );
462*cdf0e10cSrcweir     if (  aIndex.getValueTypeClass() == uno::TypeClass_VOID )
463*cdf0e10cSrcweir     {
464*cdf0e10cSrcweir         return uno::Any( xNames );
465*cdf0e10cSrcweir }
466*cdf0e10cSrcweir     return uno::Any( xNames->Item( aIndex, uno::Any() ) );
467*cdf0e10cSrcweir }
468*cdf0e10cSrcweir 
469*cdf0e10cSrcweir 
470*cdf0e10cSrcweir uno::Reference< excel::XWorksheet > SAL_CALL
471*cdf0e10cSrcweir ScVbaApplication::getActiveSheet() throw (uno::RuntimeException)
472*cdf0e10cSrcweir {
473*cdf0e10cSrcweir     uno::Reference< excel::XWorksheet > result;
474*cdf0e10cSrcweir     uno::Reference< excel::XWorkbook > xWorkbook( getActiveWorkbook(), uno::UNO_QUERY );
475*cdf0e10cSrcweir     if ( xWorkbook.is() )
476*cdf0e10cSrcweir     {
477*cdf0e10cSrcweir         uno::Reference< excel::XWorksheet > xWorksheet(
478*cdf0e10cSrcweir             xWorkbook->getActiveSheet(), uno::UNO_QUERY );
479*cdf0e10cSrcweir         if ( xWorksheet.is() )
480*cdf0e10cSrcweir         {
481*cdf0e10cSrcweir             result = xWorksheet;
482*cdf0e10cSrcweir         }
483*cdf0e10cSrcweir     }
484*cdf0e10cSrcweir 
485*cdf0e10cSrcweir     if ( !result.is() )
486*cdf0e10cSrcweir     {
487*cdf0e10cSrcweir         // Fixme - check if this is reasonable/desired behavior
488*cdf0e10cSrcweir         throw uno::RuntimeException( rtl::OUString::createFromAscii(
489*cdf0e10cSrcweir             "No activeSheet available" ), uno::Reference< uno::XInterface >() );
490*cdf0e10cSrcweir     }
491*cdf0e10cSrcweir     return result;
492*cdf0e10cSrcweir 
493*cdf0e10cSrcweir }
494*cdf0e10cSrcweir 
495*cdf0e10cSrcweir /*******************************************************************************
496*cdf0e10cSrcweir  *  In msdn:
497*cdf0e10cSrcweir  *  Reference   Optional Variant. The destination. Can be a Range
498*cdf0e10cSrcweir  *  object, a string that contains a cell reference in R1C1-style notation,
499*cdf0e10cSrcweir  *  or a string that contains a Visual Basic procedure name.
500*cdf0e10cSrcweir  *  Scroll   Optional Variant. True to scrol, False to not scroll through
501*cdf0e10cSrcweir  *  the window. The default is False.
502*cdf0e10cSrcweir  *  Parser is split to three parts, Range, R1C1 string and procedure name.
503*cdf0e10cSrcweir  *  by test excel, it seems Scroll no effect. ???
504*cdf0e10cSrcweir *******************************************************************************/
505*cdf0e10cSrcweir void SAL_CALL
506*cdf0e10cSrcweir ScVbaApplication::GoTo( const uno::Any& Reference, const uno::Any& Scroll ) throw (uno::RuntimeException)
507*cdf0e10cSrcweir {
508*cdf0e10cSrcweir     //test Scroll is a boolean
509*cdf0e10cSrcweir     sal_Bool bScroll = sal_False;
510*cdf0e10cSrcweir     //R1C1-style string or a string of procedure name.
511*cdf0e10cSrcweir 
512*cdf0e10cSrcweir     if( Scroll.hasValue() )
513*cdf0e10cSrcweir     {
514*cdf0e10cSrcweir         sal_Bool aScroll = sal_False;
515*cdf0e10cSrcweir         if( Scroll >>= aScroll )
516*cdf0e10cSrcweir         {
517*cdf0e10cSrcweir             bScroll = aScroll;
518*cdf0e10cSrcweir         }
519*cdf0e10cSrcweir         else
520*cdf0e10cSrcweir             throw uno::RuntimeException( rtl::OUString::createFromAscii( "sencond parameter should be boolean" ),
521*cdf0e10cSrcweir                     uno::Reference< uno::XInterface >() );
522*cdf0e10cSrcweir     }
523*cdf0e10cSrcweir 
524*cdf0e10cSrcweir     rtl::OUString sRangeName;
525*cdf0e10cSrcweir     if( Reference >>= sRangeName )
526*cdf0e10cSrcweir     {
527*cdf0e10cSrcweir         uno::Reference< frame::XModel > xModel( getCurrentDocument(), uno::UNO_QUERY_THROW );
528*cdf0e10cSrcweir         uno::Reference< sheet::XSpreadsheetView > xSpreadsheet(
529*cdf0e10cSrcweir                 xModel->getCurrentController(), uno::UNO_QUERY_THROW );
530*cdf0e10cSrcweir         uno::Reference< sheet::XSpreadsheet > xDoc = xSpreadsheet->getActiveSheet();
531*cdf0e10cSrcweir 
532*cdf0e10cSrcweir         ScTabViewShell* pShell = excel::getCurrentBestViewShell( mxContext );
533*cdf0e10cSrcweir         ScGridWindow* gridWindow = (ScGridWindow*)pShell->GetWindow();
534*cdf0e10cSrcweir         try
535*cdf0e10cSrcweir         {
536*cdf0e10cSrcweir             uno::Reference< excel::XRange > xVbaSheetRange = ScVbaRange::getRangeObjectForName(
537*cdf0e10cSrcweir                 mxContext, sRangeName, excel::getDocShell( xModel ), formula::FormulaGrammar::CONV_XL_R1C1 );
538*cdf0e10cSrcweir 
539*cdf0e10cSrcweir             if( bScroll )
540*cdf0e10cSrcweir             {
541*cdf0e10cSrcweir                 xVbaSheetRange->Select();
542*cdf0e10cSrcweir                 uno::Reference< excel::XWindow >  xWindow = getActiveWindow();
543*cdf0e10cSrcweir                 ScSplitPos eWhich = pShell->GetViewData()->GetActivePart();
544*cdf0e10cSrcweir                 sal_Int32 nValueX = pShell->GetViewData()->GetPosX(WhichH(eWhich));
545*cdf0e10cSrcweir                 sal_Int32 nValueY = pShell->GetViewData()->GetPosY(WhichV(eWhich));
546*cdf0e10cSrcweir                 xWindow->SmallScroll( uno::makeAny( (sal_Int16)(xVbaSheetRange->getRow() - 1) ),
547*cdf0e10cSrcweir                          uno::makeAny( (sal_Int16)nValueY ),
548*cdf0e10cSrcweir                          uno::makeAny( (sal_Int16)(xVbaSheetRange->getColumn() - 1)  ),
549*cdf0e10cSrcweir                          uno::makeAny( (sal_Int16)nValueX ) );
550*cdf0e10cSrcweir                 gridWindow->GrabFocus();
551*cdf0e10cSrcweir             }
552*cdf0e10cSrcweir             else
553*cdf0e10cSrcweir             {
554*cdf0e10cSrcweir                 xVbaSheetRange->Select();
555*cdf0e10cSrcweir                 gridWindow->GrabFocus();
556*cdf0e10cSrcweir             }
557*cdf0e10cSrcweir         }
558*cdf0e10cSrcweir         catch( uno::RuntimeException )
559*cdf0e10cSrcweir         {
560*cdf0e10cSrcweir             //maybe this should be a procedure name
561*cdf0e10cSrcweir             //TODO for procedure name
562*cdf0e10cSrcweir             //browse::XBrowseNodeFactory is a singlton. OUString::createFromAscii( "/singletons/com.sun.star.script.browse.theBrowseNodeFactory")
563*cdf0e10cSrcweir             //and the createView( browse::BrowseNodeFactoryViewTypes::MACROSELECTOR ) to get a root browse::XBrowseNode.
564*cdf0e10cSrcweir             //for query XInvocation interface.
565*cdf0e10cSrcweir             //but how to directly get the XInvocation?
566*cdf0e10cSrcweir             throw uno::RuntimeException( rtl::OUString::createFromAscii( "invalid reference for range name, it should be procedure name" ),
567*cdf0e10cSrcweir                     uno::Reference< uno::XInterface >() );
568*cdf0e10cSrcweir         }
569*cdf0e10cSrcweir         return;
570*cdf0e10cSrcweir     }
571*cdf0e10cSrcweir     uno::Reference< excel::XRange > xRange;
572*cdf0e10cSrcweir     if( Reference >>= xRange )
573*cdf0e10cSrcweir     {
574*cdf0e10cSrcweir         uno::Reference< excel::XRange > xVbaRange( Reference, uno::UNO_QUERY );
575*cdf0e10cSrcweir         ScTabViewShell* pShell = excel::getCurrentBestViewShell( mxContext );
576*cdf0e10cSrcweir         ScGridWindow* gridWindow = (ScGridWindow*)pShell->GetWindow();
577*cdf0e10cSrcweir         if ( xVbaRange.is() )
578*cdf0e10cSrcweir         {
579*cdf0e10cSrcweir             //TODO bScroll should be using, In this time, it doesenot have effection
580*cdf0e10cSrcweir             if( bScroll )
581*cdf0e10cSrcweir             {
582*cdf0e10cSrcweir                 xVbaRange->Select();
583*cdf0e10cSrcweir                 uno::Reference< excel::XWindow >  xWindow = getActiveWindow();
584*cdf0e10cSrcweir                 ScSplitPos eWhich = pShell->GetViewData()->GetActivePart();
585*cdf0e10cSrcweir                 sal_Int32 nValueX = pShell->GetViewData()->GetPosX(WhichH(eWhich));
586*cdf0e10cSrcweir                 sal_Int32 nValueY = pShell->GetViewData()->GetPosY(WhichV(eWhich));
587*cdf0e10cSrcweir                 xWindow->SmallScroll( uno::makeAny( (sal_Int16)(xVbaRange->getRow() - 1) ),
588*cdf0e10cSrcweir                          uno::makeAny( (sal_Int16)nValueY ),
589*cdf0e10cSrcweir                          uno::makeAny( (sal_Int16)(xVbaRange->getColumn() - 1)  ),
590*cdf0e10cSrcweir                          uno::makeAny( (sal_Int16)nValueX ) );
591*cdf0e10cSrcweir                 gridWindow->GrabFocus();
592*cdf0e10cSrcweir             }
593*cdf0e10cSrcweir             else
594*cdf0e10cSrcweir             {
595*cdf0e10cSrcweir                 xVbaRange->Select();
596*cdf0e10cSrcweir                 gridWindow->GrabFocus();
597*cdf0e10cSrcweir             }
598*cdf0e10cSrcweir         }
599*cdf0e10cSrcweir         return;
600*cdf0e10cSrcweir     }
601*cdf0e10cSrcweir     throw uno::RuntimeException( rtl::OUString::createFromAscii( "invalid reference or name" ),
602*cdf0e10cSrcweir             uno::Reference< uno::XInterface >() );
603*cdf0e10cSrcweir }
604*cdf0e10cSrcweir 
605*cdf0e10cSrcweir sal_Int32 SAL_CALL
606*cdf0e10cSrcweir ScVbaApplication::getCursor() throw (uno::RuntimeException)
607*cdf0e10cSrcweir {
608*cdf0e10cSrcweir     sal_Int32 nPointerStyle =  getPointerStyle(getCurrentDocument());
609*cdf0e10cSrcweir 
610*cdf0e10cSrcweir     switch( nPointerStyle )
611*cdf0e10cSrcweir     {
612*cdf0e10cSrcweir         case POINTER_ARROW:
613*cdf0e10cSrcweir             return excel::XlMousePointer::xlNorthwestArrow;
614*cdf0e10cSrcweir         case POINTER_NULL:
615*cdf0e10cSrcweir             return excel::XlMousePointer::xlDefault;
616*cdf0e10cSrcweir         case POINTER_WAIT:
617*cdf0e10cSrcweir             return excel::XlMousePointer::xlWait;
618*cdf0e10cSrcweir         case POINTER_TEXT:
619*cdf0e10cSrcweir             return excel::XlMousePointer::xlIBeam;
620*cdf0e10cSrcweir         default:
621*cdf0e10cSrcweir             return excel::XlMousePointer::xlDefault;
622*cdf0e10cSrcweir     }
623*cdf0e10cSrcweir }
624*cdf0e10cSrcweir 
625*cdf0e10cSrcweir void SAL_CALL
626*cdf0e10cSrcweir ScVbaApplication::setCursor( sal_Int32 _cursor ) throw (uno::RuntimeException)
627*cdf0e10cSrcweir {
628*cdf0e10cSrcweir     try
629*cdf0e10cSrcweir     {
630*cdf0e10cSrcweir 	uno::Reference< frame::XModel > xModel( getCurrentDocument(), uno::UNO_QUERY_THROW );
631*cdf0e10cSrcweir         switch( _cursor )
632*cdf0e10cSrcweir         {
633*cdf0e10cSrcweir             case excel::XlMousePointer::xlNorthwestArrow:
634*cdf0e10cSrcweir             {
635*cdf0e10cSrcweir                 const Pointer& rPointer( POINTER_ARROW );
636*cdf0e10cSrcweir                 setCursorHelper( xModel, rPointer, sal_False );
637*cdf0e10cSrcweir                 break;
638*cdf0e10cSrcweir             }
639*cdf0e10cSrcweir             case excel::XlMousePointer::xlWait:
640*cdf0e10cSrcweir             case excel::XlMousePointer::xlIBeam:
641*cdf0e10cSrcweir             {
642*cdf0e10cSrcweir                 const Pointer& rPointer( static_cast< PointerStyle >( _cursor ) );
643*cdf0e10cSrcweir                 //It will set the edit window, toobar and statusbar's mouse pointer.
644*cdf0e10cSrcweir                 setCursorHelper( xModel, rPointer, sal_True );
645*cdf0e10cSrcweir                 break;
646*cdf0e10cSrcweir             }
647*cdf0e10cSrcweir             case excel::XlMousePointer::xlDefault:
648*cdf0e10cSrcweir             {
649*cdf0e10cSrcweir                 const Pointer& rPointer( POINTER_NULL );
650*cdf0e10cSrcweir                 setCursorHelper( xModel, rPointer, sal_False );
651*cdf0e10cSrcweir                 break;
652*cdf0e10cSrcweir             }
653*cdf0e10cSrcweir             default:
654*cdf0e10cSrcweir                 throw uno::RuntimeException( rtl::OUString(
655*cdf0e10cSrcweir                         RTL_CONSTASCII_USTRINGPARAM("Unknown value for Cursor pointer")), uno::Reference< uno::XInterface >() );
656*cdf0e10cSrcweir                 // TODO: isn't this a flaw in the API? It should be allowed to throw an
657*cdf0e10cSrcweir                 // IllegalArgumentException, or so
658*cdf0e10cSrcweir         }
659*cdf0e10cSrcweir     }
660*cdf0e10cSrcweir     catch( const uno::Exception& )
661*cdf0e10cSrcweir     {
662*cdf0e10cSrcweir     	DBG_UNHANDLED_EXCEPTION();
663*cdf0e10cSrcweir     }
664*cdf0e10cSrcweir }
665*cdf0e10cSrcweir 
666*cdf0e10cSrcweir // #TODO perhaps we should switch the return type depending of the filter
667*cdf0e10cSrcweir // type, e.g. return Calc for Calc and Excel if its an imported doc
668*cdf0e10cSrcweir rtl::OUString SAL_CALL
669*cdf0e10cSrcweir ScVbaApplication::getName() throw (uno::RuntimeException)
670*cdf0e10cSrcweir {
671*cdf0e10cSrcweir 	static rtl::OUString appName( RTL_CONSTASCII_USTRINGPARAM("Microsoft Excel" ) );
672*cdf0e10cSrcweir 	return appName;
673*cdf0e10cSrcweir }
674*cdf0e10cSrcweir 
675*cdf0e10cSrcweir // #TODO #FIXME get/setDisplayAlerts are just stub impl
676*cdf0e10cSrcweir // here just the status of the switch is set
677*cdf0e10cSrcweir // the function that throws an error message needs to
678*cdf0e10cSrcweir // evaluate this switch in order to know whether it has to disable the
679*cdf0e10cSrcweir // error message thrown by OpenOffice
680*cdf0e10cSrcweir 
681*cdf0e10cSrcweir void SAL_CALL
682*cdf0e10cSrcweir ScVbaApplication::setDisplayAlerts(sal_Bool displayAlerts) throw (uno::RuntimeException)
683*cdf0e10cSrcweir {
684*cdf0e10cSrcweir     mrAppSettings.mbDisplayAlerts = displayAlerts;
685*cdf0e10cSrcweir }
686*cdf0e10cSrcweir 
687*cdf0e10cSrcweir sal_Bool SAL_CALL
688*cdf0e10cSrcweir ScVbaApplication::getDisplayAlerts() throw (uno::RuntimeException)
689*cdf0e10cSrcweir {
690*cdf0e10cSrcweir 	return mrAppSettings.mbDisplayAlerts;
691*cdf0e10cSrcweir }
692*cdf0e10cSrcweir 
693*cdf0e10cSrcweir void SAL_CALL
694*cdf0e10cSrcweir ScVbaApplication::setEnableEvents(sal_Bool bEnable) throw (uno::RuntimeException)
695*cdf0e10cSrcweir {
696*cdf0e10cSrcweir 	mrAppSettings.mbEnableEvents = bEnable;
697*cdf0e10cSrcweir }
698*cdf0e10cSrcweir 
699*cdf0e10cSrcweir sal_Bool SAL_CALL
700*cdf0e10cSrcweir ScVbaApplication::getEnableEvents() throw (uno::RuntimeException)
701*cdf0e10cSrcweir {
702*cdf0e10cSrcweir 	return mrAppSettings.mbEnableEvents;
703*cdf0e10cSrcweir }
704*cdf0e10cSrcweir 
705*cdf0e10cSrcweir void SAL_CALL
706*cdf0e10cSrcweir ScVbaApplication::Calculate() throw(  script::BasicErrorException , uno::RuntimeException )
707*cdf0e10cSrcweir {
708*cdf0e10cSrcweir 	uno::Reference< frame::XModel > xModel( getCurrentDocument(), uno::UNO_QUERY_THROW );
709*cdf0e10cSrcweir 	uno::Reference< sheet::XCalculatable > xCalculatable( getCurrentDocument(), uno::UNO_QUERY_THROW );
710*cdf0e10cSrcweir 	xCalculatable->calculateAll();
711*cdf0e10cSrcweir }
712*cdf0e10cSrcweir 
713*cdf0e10cSrcweir uno::Reference< beans::XPropertySet > lcl_getPathSettingsService( const uno::Reference< uno::XComponentContext >& xContext ) throw ( uno::RuntimeException )
714*cdf0e10cSrcweir {
715*cdf0e10cSrcweir 	static uno::Reference< beans::XPropertySet >  xPathSettings;
716*cdf0e10cSrcweir 	if ( !xPathSettings.is() )
717*cdf0e10cSrcweir 	{
718*cdf0e10cSrcweir 		uno::Reference< lang::XMultiComponentFactory > xSMgr( xContext->getServiceManager(), uno::UNO_QUERY_THROW );
719*cdf0e10cSrcweir 		xPathSettings.set( xSMgr->createInstanceWithContext(::rtl::OUString::createFromAscii("com.sun.star.util.PathSettings"), xContext), uno::UNO_QUERY_THROW );
720*cdf0e10cSrcweir 	}
721*cdf0e10cSrcweir 	return xPathSettings;
722*cdf0e10cSrcweir }
723*cdf0e10cSrcweir rtl::OUString ScVbaApplication::getOfficePath( const rtl::OUString& _sPathType ) throw ( uno::RuntimeException )
724*cdf0e10cSrcweir {
725*cdf0e10cSrcweir 	rtl::OUString sRetPath;
726*cdf0e10cSrcweir 	uno::Reference< beans::XPropertySet > xProps = lcl_getPathSettingsService( mxContext );
727*cdf0e10cSrcweir 	try
728*cdf0e10cSrcweir 	{
729*cdf0e10cSrcweir 		rtl::OUString sUrl;
730*cdf0e10cSrcweir 	 	xProps->getPropertyValue( _sPathType ) >>= sUrl;
731*cdf0e10cSrcweir 
732*cdf0e10cSrcweir 		// if its a list of paths then use the last one
733*cdf0e10cSrcweir 		sal_Int32 nIndex =  sUrl.lastIndexOf( ';' ) ;
734*cdf0e10cSrcweir 		if ( nIndex > 0 )
735*cdf0e10cSrcweir 			sUrl = sUrl.copy( nIndex + 1 );
736*cdf0e10cSrcweir 		::osl::File::getSystemPathFromFileURL( sUrl, sRetPath );
737*cdf0e10cSrcweir 	}
738*cdf0e10cSrcweir 	catch (uno::Exception&)
739*cdf0e10cSrcweir 	{
740*cdf0e10cSrcweir 		DebugHelper::exception(SbERR_METHOD_FAILED, rtl::OUString());
741*cdf0e10cSrcweir 	}
742*cdf0e10cSrcweir 	return sRetPath;
743*cdf0e10cSrcweir }
744*cdf0e10cSrcweir 
745*cdf0e10cSrcweir void SAL_CALL
746*cdf0e10cSrcweir ScVbaApplication::setDefaultFilePath( const ::rtl::OUString& DefaultFilePath ) throw (uno::RuntimeException)
747*cdf0e10cSrcweir {
748*cdf0e10cSrcweir 	uno::Reference< beans::XPropertySet > xProps = lcl_getPathSettingsService( mxContext );
749*cdf0e10cSrcweir 	rtl::OUString aURL;
750*cdf0e10cSrcweir 	osl::FileBase::getFileURLFromSystemPath( DefaultFilePath, aURL );
751*cdf0e10cSrcweir 	xProps->setPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("Work")), uno::Any( aURL ) );
752*cdf0e10cSrcweir }
753*cdf0e10cSrcweir 
754*cdf0e10cSrcweir ::rtl::OUString SAL_CALL
755*cdf0e10cSrcweir ScVbaApplication::getDefaultFilePath() throw (uno::RuntimeException)
756*cdf0e10cSrcweir {
757*cdf0e10cSrcweir 	return getOfficePath( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("Work")));
758*cdf0e10cSrcweir }
759*cdf0e10cSrcweir 
760*cdf0e10cSrcweir ::rtl::OUString SAL_CALL
761*cdf0e10cSrcweir ScVbaApplication::getLibraryPath() throw (uno::RuntimeException)
762*cdf0e10cSrcweir {
763*cdf0e10cSrcweir 	return getOfficePath( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("Basic")));
764*cdf0e10cSrcweir }
765*cdf0e10cSrcweir 
766*cdf0e10cSrcweir ::rtl::OUString SAL_CALL
767*cdf0e10cSrcweir ScVbaApplication::getTemplatesPath() throw (uno::RuntimeException)
768*cdf0e10cSrcweir {
769*cdf0e10cSrcweir 	return getOfficePath( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("Template")));
770*cdf0e10cSrcweir }
771*cdf0e10cSrcweir 
772*cdf0e10cSrcweir ::rtl::OUString SAL_CALL
773*cdf0e10cSrcweir ScVbaApplication::getPathSeparator() throw (uno::RuntimeException)
774*cdf0e10cSrcweir {
775*cdf0e10cSrcweir 	static rtl::OUString sPathSep( RTL_CONSTASCII_USTRINGPARAM( FILE_PATH_SEPERATOR ) );
776*cdf0e10cSrcweir 	return sPathSep;
777*cdf0e10cSrcweir }
778*cdf0e10cSrcweir 
779*cdf0e10cSrcweir // ----------------------------------------------------------------------------
780*cdf0e10cSrcweir // Helpers for Intersect and Union
781*cdf0e10cSrcweir 
782*cdf0e10cSrcweir namespace {
783*cdf0e10cSrcweir 
784*cdf0e10cSrcweir typedef ::std::list< ScRange > ListOfScRange;
785*cdf0e10cSrcweir 
786*cdf0e10cSrcweir /** Appends all ranges of a VBA Range object in the passed Any to the list of ranges. */
787*cdf0e10cSrcweir void lclAddToListOfScRange( ListOfScRange& rList, const uno::Any& rArg )
788*cdf0e10cSrcweir         throw (script::BasicErrorException, uno::RuntimeException)
789*cdf0e10cSrcweir {
790*cdf0e10cSrcweir     if( rArg.hasValue() )
791*cdf0e10cSrcweir     {
792*cdf0e10cSrcweir         uno::Reference< excel::XRange > xRange( rArg, uno::UNO_QUERY_THROW );
793*cdf0e10cSrcweir         uno::Reference< XCollection > xCol( xRange->Areas( uno::Any() ), uno::UNO_QUERY_THROW );
794*cdf0e10cSrcweir         for( sal_Int32 nIdx = 1, nCount = xCol->getCount(); nIdx <= nCount; ++nIdx )
795*cdf0e10cSrcweir         {
796*cdf0e10cSrcweir             uno::Reference< excel::XRange > xAreaRange( xCol->Item( uno::Any( nIdx ), uno::Any() ), uno::UNO_QUERY_THROW );
797*cdf0e10cSrcweir             uno::Reference< sheet::XCellRangeAddressable > xAddressable( xAreaRange->getCellRange(), uno::UNO_QUERY_THROW );
798*cdf0e10cSrcweir             ScRange aScRange;
799*cdf0e10cSrcweir             ScUnoConversion::FillScRange( aScRange, xAddressable->getRangeAddress() );
800*cdf0e10cSrcweir             rList.push_back( aScRange );
801*cdf0e10cSrcweir         }
802*cdf0e10cSrcweir     }
803*cdf0e10cSrcweir }
804*cdf0e10cSrcweir 
805*cdf0e10cSrcweir /** Returns true, if the passed ranges can be expressed by a single range. The
806*cdf0e10cSrcweir     new range will be contained in r1 then, the range r2 can be removed. */
807*cdf0e10cSrcweir bool lclTryJoin( ScRange& r1, const ScRange& r2 )
808*cdf0e10cSrcweir {
809*cdf0e10cSrcweir     // 1) r2 is completely inside r1
810*cdf0e10cSrcweir     if( r1.In( r2 ) )
811*cdf0e10cSrcweir         return true;
812*cdf0e10cSrcweir 
813*cdf0e10cSrcweir     // 2) r1 is completely inside r2
814*cdf0e10cSrcweir     if( r2.In( r1 ) )
815*cdf0e10cSrcweir     {
816*cdf0e10cSrcweir         r1 = r2;
817*cdf0e10cSrcweir         return true;
818*cdf0e10cSrcweir     }
819*cdf0e10cSrcweir 
820*cdf0e10cSrcweir     SCCOL n1L = r1.aStart.Col();
821*cdf0e10cSrcweir     SCCOL n1R = r1.aEnd.Col();
822*cdf0e10cSrcweir     SCROW n1T = r1.aStart.Row();
823*cdf0e10cSrcweir     SCROW n1B = r1.aEnd.Row();
824*cdf0e10cSrcweir     SCCOL n2L = r2.aStart.Col();
825*cdf0e10cSrcweir     SCCOL n2R = r2.aEnd.Col();
826*cdf0e10cSrcweir     SCROW n2T = r2.aStart.Row();
827*cdf0e10cSrcweir     SCROW n2B = r2.aEnd.Row();
828*cdf0e10cSrcweir 
829*cdf0e10cSrcweir     // 3) r1 and r2 have equal upper and lower border
830*cdf0e10cSrcweir     if( (n1T == n2T) && (n1B == n2B) )
831*cdf0e10cSrcweir     {
832*cdf0e10cSrcweir         // check that r1 overlaps or touches r2
833*cdf0e10cSrcweir         if( ((n1L < n2L) && (n2L - 1 <= n1R)) || ((n2L < n1L) && (n1L - 1 <= n2R)) )
834*cdf0e10cSrcweir         {
835*cdf0e10cSrcweir             r1.aStart.SetCol( ::std::min( n1L, n2L ) );
836*cdf0e10cSrcweir             r1.aEnd.SetCol( ::std::max( n1R, n2R ) );
837*cdf0e10cSrcweir             return true;
838*cdf0e10cSrcweir         }
839*cdf0e10cSrcweir         return false;
840*cdf0e10cSrcweir     }
841*cdf0e10cSrcweir 
842*cdf0e10cSrcweir     // 4) r1 and r2 have equal left and right border
843*cdf0e10cSrcweir     if( (n1L == n2L) && (n1R == n2R) )
844*cdf0e10cSrcweir     {
845*cdf0e10cSrcweir         // check that r1 overlaps or touches r2
846*cdf0e10cSrcweir         if( ((n1T < n2T) && (n2T + 1 <= n1B)) || ((n2T < n1T) && (n1T + 1 <= n2B)) )
847*cdf0e10cSrcweir         {
848*cdf0e10cSrcweir             r1.aStart.SetRow( ::std::min( n1T, n2T ) );
849*cdf0e10cSrcweir             r1.aEnd.SetRow( ::std::max( n1B, n2B ) );
850*cdf0e10cSrcweir             return true;
851*cdf0e10cSrcweir         }
852*cdf0e10cSrcweir         return false;
853*cdf0e10cSrcweir     }
854*cdf0e10cSrcweir 
855*cdf0e10cSrcweir     // 5) cannot join these ranges
856*cdf0e10cSrcweir     return false;
857*cdf0e10cSrcweir }
858*cdf0e10cSrcweir 
859*cdf0e10cSrcweir /** Strips out ranges that are contained by other ranges, joins ranges that can be joined
860*cdf0e10cSrcweir     together (aligned borders, e.g. A4:D10 and B4:E10 would be combined to A4:E10. */
861*cdf0e10cSrcweir void lclJoinRanges( ListOfScRange& rList )
862*cdf0e10cSrcweir {
863*cdf0e10cSrcweir     ListOfScRange::iterator aOuterIt = rList.begin();
864*cdf0e10cSrcweir     while( aOuterIt != rList.end() )
865*cdf0e10cSrcweir     {
866*cdf0e10cSrcweir         bool bAnyErased = false;    // true = any range erased from rList
867*cdf0e10cSrcweir         ListOfScRange::iterator aInnerIt = rList.begin();
868*cdf0e10cSrcweir         while( aInnerIt != rList.end() )
869*cdf0e10cSrcweir         {
870*cdf0e10cSrcweir             bool bInnerErased = false;   // true = aInnerIt erased from rList
871*cdf0e10cSrcweir             // do not compare a range with itself
872*cdf0e10cSrcweir             if( (aOuterIt != aInnerIt) && lclTryJoin( *aOuterIt, *aInnerIt ) )
873*cdf0e10cSrcweir             {
874*cdf0e10cSrcweir                 // aOuterIt points to joined range, aInnerIt will be removed
875*cdf0e10cSrcweir 				aInnerIt = rList.erase( aInnerIt );
876*cdf0e10cSrcweir                 bInnerErased = bAnyErased = true;
877*cdf0e10cSrcweir             }
878*cdf0e10cSrcweir             /*  If aInnerIt has been erased from rList, it already points to
879*cdf0e10cSrcweir                 the next element (return value of list::erase()). */
880*cdf0e10cSrcweir             if( !bInnerErased )
881*cdf0e10cSrcweir                 ++aInnerIt;
882*cdf0e10cSrcweir 		}
883*cdf0e10cSrcweir         // if any range has been erased, repeat outer loop with the same range
884*cdf0e10cSrcweir         if( !bAnyErased )
885*cdf0e10cSrcweir             ++aOuterIt;
886*cdf0e10cSrcweir 	}
887*cdf0e10cSrcweir }
888*cdf0e10cSrcweir 
889*cdf0e10cSrcweir /** Intersects the passed list with all ranges of a VBA Range object in the passed Any. */
890*cdf0e10cSrcweir void lclIntersectRanges( ListOfScRange& rList, const uno::Any& rArg )
891*cdf0e10cSrcweir         throw (script::BasicErrorException, uno::RuntimeException)
892*cdf0e10cSrcweir {
893*cdf0e10cSrcweir     // extract the ranges from the passed argument, will throw on invalid data
894*cdf0e10cSrcweir     ListOfScRange aList2;
895*cdf0e10cSrcweir     lclAddToListOfScRange( aList2, rArg );
896*cdf0e10cSrcweir     // do nothing, if the passed list is already empty
897*cdf0e10cSrcweir     if( !rList.empty() && !aList2.empty() )
898*cdf0e10cSrcweir     {
899*cdf0e10cSrcweir         // save original list in a local
900*cdf0e10cSrcweir         ListOfScRange aList1;
901*cdf0e10cSrcweir         aList1.swap( rList );
902*cdf0e10cSrcweir         // join ranges from passed argument
903*cdf0e10cSrcweir         lclJoinRanges( aList2 );
904*cdf0e10cSrcweir         // calculate intersection of the ranges in both lists
905*cdf0e10cSrcweir         for( ListOfScRange::const_iterator aOuterIt = aList1.begin(), aOuterEnd = aList1.end(); aOuterIt != aOuterEnd; ++aOuterIt )
906*cdf0e10cSrcweir         {
907*cdf0e10cSrcweir             for( ListOfScRange::const_iterator aInnerIt = aList2.begin(), aInnerEnd = aList2.end(); aInnerIt != aInnerEnd; ++aInnerIt )
908*cdf0e10cSrcweir             {
909*cdf0e10cSrcweir                 if( aOuterIt->Intersects( *aInnerIt ) )
910*cdf0e10cSrcweir                 {
911*cdf0e10cSrcweir                     ScRange aIsectRange(
912*cdf0e10cSrcweir                         Max( aOuterIt->aStart.Col(), aInnerIt->aStart.Col() ),
913*cdf0e10cSrcweir                         Max( aOuterIt->aStart.Row(), aInnerIt->aStart.Row() ),
914*cdf0e10cSrcweir                         Max( aOuterIt->aStart.Tab(), aInnerIt->aStart.Tab() ),
915*cdf0e10cSrcweir                         Min( aOuterIt->aEnd.Col(),   aInnerIt->aEnd.Col() ),
916*cdf0e10cSrcweir                         Min( aOuterIt->aEnd.Row(),   aInnerIt->aEnd.Row() ),
917*cdf0e10cSrcweir                         Min( aOuterIt->aEnd.Tab(),   aInnerIt->aEnd.Tab() ) );
918*cdf0e10cSrcweir                     rList.push_back( aIsectRange );
919*cdf0e10cSrcweir                 }
920*cdf0e10cSrcweir             }
921*cdf0e10cSrcweir         }
922*cdf0e10cSrcweir         // again, join the result ranges
923*cdf0e10cSrcweir         lclJoinRanges( rList );
924*cdf0e10cSrcweir     }
925*cdf0e10cSrcweir }
926*cdf0e10cSrcweir 
927*cdf0e10cSrcweir /** Creates a VBA Range object from the passed list of ranges. */
928*cdf0e10cSrcweir uno::Reference< excel::XRange > lclCreateVbaRange(
929*cdf0e10cSrcweir         const uno::Reference< uno::XComponentContext >& rxContext,
930*cdf0e10cSrcweir         const uno::Reference< frame::XModel >& rxModel,
931*cdf0e10cSrcweir         const ListOfScRange& rList ) throw (uno::RuntimeException)
932*cdf0e10cSrcweir {
933*cdf0e10cSrcweir     ScDocShell* pDocShell = excel::getDocShell( rxModel );
934*cdf0e10cSrcweir     if( !pDocShell ) throw uno::RuntimeException();
935*cdf0e10cSrcweir 
936*cdf0e10cSrcweir 	ScRangeList aCellRanges;
937*cdf0e10cSrcweir 	for( ListOfScRange::const_iterator aIt = rList.begin(), aEnd = rList.end(); aIt != aEnd; ++aIt )
938*cdf0e10cSrcweir 		aCellRanges.Append( *aIt );
939*cdf0e10cSrcweir 
940*cdf0e10cSrcweir 	if( aCellRanges.Count() == 1 )
941*cdf0e10cSrcweir 	{
942*cdf0e10cSrcweir         uno::Reference< table::XCellRange > xRange( new ScCellRangeObj( pDocShell, *aCellRanges.First() ) );
943*cdf0e10cSrcweir 		return new ScVbaRange( excel::getUnoSheetModuleObj( xRange ), rxContext, xRange );
944*cdf0e10cSrcweir 	}
945*cdf0e10cSrcweir 	if( aCellRanges.Count() > 1 )
946*cdf0e10cSrcweir 	{
947*cdf0e10cSrcweir 		uno::Reference< sheet::XSheetCellRangeContainer > xRanges( new ScCellRangesObj( pDocShell, aCellRanges ) );
948*cdf0e10cSrcweir     	return new ScVbaRange( excel::getUnoSheetModuleObj( xRanges ), rxContext, xRanges );
949*cdf0e10cSrcweir 	}
950*cdf0e10cSrcweir 	return 0;
951*cdf0e10cSrcweir }
952*cdf0e10cSrcweir 
953*cdf0e10cSrcweir } // namespace
954*cdf0e10cSrcweir 
955*cdf0e10cSrcweir // ----------------------------------------------------------------------------
956*cdf0e10cSrcweir 
957*cdf0e10cSrcweir uno::Reference< excel::XRange > SAL_CALL ScVbaApplication::Intersect(
958*cdf0e10cSrcweir         const uno::Reference< excel::XRange >& rArg1, const uno::Reference< excel::XRange >& rArg2,
959*cdf0e10cSrcweir         const uno::Any& rArg3, const uno::Any& rArg4, const uno::Any& rArg5, const uno::Any& rArg6,
960*cdf0e10cSrcweir         const uno::Any& rArg7, const uno::Any& rArg8, const uno::Any& rArg9, const uno::Any& rArg10,
961*cdf0e10cSrcweir         const uno::Any& rArg11, const uno::Any& rArg12, const uno::Any& rArg13, const uno::Any& rArg14,
962*cdf0e10cSrcweir         const uno::Any& rArg15, const uno::Any& rArg16, const uno::Any& rArg17, const uno::Any& rArg18,
963*cdf0e10cSrcweir         const uno::Any& rArg19, const uno::Any& rArg20, const uno::Any& rArg21, const uno::Any& rArg22,
964*cdf0e10cSrcweir         const uno::Any& rArg23, const uno::Any& rArg24, const uno::Any& rArg25, const uno::Any& rArg26,
965*cdf0e10cSrcweir         const uno::Any& rArg27, const uno::Any& rArg28, const uno::Any& rArg29, const uno::Any& rArg30 )
966*cdf0e10cSrcweir         throw (script::BasicErrorException, uno::RuntimeException)
967*cdf0e10cSrcweir {
968*cdf0e10cSrcweir     if( !rArg1.is() || !rArg2.is() )
969*cdf0e10cSrcweir         DebugHelper::exception( SbERR_BAD_PARAMETER, rtl::OUString() );
970*cdf0e10cSrcweir 
971*cdf0e10cSrcweir     // initialize the result list with 1st parameter, join its ranges together
972*cdf0e10cSrcweir     ListOfScRange aList;
973*cdf0e10cSrcweir     lclAddToListOfScRange( aList, uno::Any( rArg1 ) );
974*cdf0e10cSrcweir 	lclJoinRanges( aList );
975*cdf0e10cSrcweir 
976*cdf0e10cSrcweir     // process all other parameters, this updates the list with intersection
977*cdf0e10cSrcweir     lclIntersectRanges( aList, uno::Any( rArg2 ) );
978*cdf0e10cSrcweir     lclIntersectRanges( aList, rArg3 );
979*cdf0e10cSrcweir     lclIntersectRanges( aList, rArg4 );
980*cdf0e10cSrcweir     lclIntersectRanges( aList, rArg5 );
981*cdf0e10cSrcweir     lclIntersectRanges( aList, rArg6 );
982*cdf0e10cSrcweir     lclIntersectRanges( aList, rArg7 );
983*cdf0e10cSrcweir     lclIntersectRanges( aList, rArg8 );
984*cdf0e10cSrcweir     lclIntersectRanges( aList, rArg9 );
985*cdf0e10cSrcweir     lclIntersectRanges( aList, rArg10 );
986*cdf0e10cSrcweir     lclIntersectRanges( aList, rArg11 );
987*cdf0e10cSrcweir     lclIntersectRanges( aList, rArg12 );
988*cdf0e10cSrcweir     lclIntersectRanges( aList, rArg13 );
989*cdf0e10cSrcweir     lclIntersectRanges( aList, rArg14 );
990*cdf0e10cSrcweir     lclIntersectRanges( aList, rArg15 );
991*cdf0e10cSrcweir     lclIntersectRanges( aList, rArg16 );
992*cdf0e10cSrcweir     lclIntersectRanges( aList, rArg17 );
993*cdf0e10cSrcweir     lclIntersectRanges( aList, rArg18 );
994*cdf0e10cSrcweir     lclIntersectRanges( aList, rArg19 );
995*cdf0e10cSrcweir     lclIntersectRanges( aList, rArg20 );
996*cdf0e10cSrcweir     lclIntersectRanges( aList, rArg21 );
997*cdf0e10cSrcweir     lclIntersectRanges( aList, rArg22 );
998*cdf0e10cSrcweir     lclIntersectRanges( aList, rArg23 );
999*cdf0e10cSrcweir     lclIntersectRanges( aList, rArg24 );
1000*cdf0e10cSrcweir     lclIntersectRanges( aList, rArg25 );
1001*cdf0e10cSrcweir     lclIntersectRanges( aList, rArg26 );
1002*cdf0e10cSrcweir     lclIntersectRanges( aList, rArg27 );
1003*cdf0e10cSrcweir     lclIntersectRanges( aList, rArg28 );
1004*cdf0e10cSrcweir     lclIntersectRanges( aList, rArg29 );
1005*cdf0e10cSrcweir     lclIntersectRanges( aList, rArg30 );
1006*cdf0e10cSrcweir 
1007*cdf0e10cSrcweir     // create the VBA Range object
1008*cdf0e10cSrcweir     return lclCreateVbaRange( mxContext, getCurrentDocument(), aList );
1009*cdf0e10cSrcweir }
1010*cdf0e10cSrcweir 
1011*cdf0e10cSrcweir uno::Reference< excel::XRange > SAL_CALL ScVbaApplication::Union(
1012*cdf0e10cSrcweir         const uno::Reference< excel::XRange >& rArg1, const uno::Reference< excel::XRange >& rArg2,
1013*cdf0e10cSrcweir         const uno::Any& rArg3, const uno::Any& rArg4, const uno::Any& rArg5, const uno::Any& rArg6,
1014*cdf0e10cSrcweir         const uno::Any& rArg7, const uno::Any& rArg8, const uno::Any& rArg9, const uno::Any& rArg10,
1015*cdf0e10cSrcweir         const uno::Any& rArg11, const uno::Any& rArg12, const uno::Any& rArg13, const uno::Any& rArg14,
1016*cdf0e10cSrcweir         const uno::Any& rArg15, const uno::Any& rArg16, const uno::Any& rArg17, const uno::Any& rArg18,
1017*cdf0e10cSrcweir         const uno::Any& rArg19, const uno::Any& rArg20, const uno::Any& rArg21, const uno::Any& rArg22,
1018*cdf0e10cSrcweir         const uno::Any& rArg23, const uno::Any& rArg24, const uno::Any& rArg25, const uno::Any& rArg26,
1019*cdf0e10cSrcweir         const uno::Any& rArg27, const uno::Any& rArg28, const uno::Any& rArg29, const uno::Any& rArg30 )
1020*cdf0e10cSrcweir         throw (script::BasicErrorException, uno::RuntimeException)
1021*cdf0e10cSrcweir {
1022*cdf0e10cSrcweir     if( !rArg1.is() || !rArg2.is() )
1023*cdf0e10cSrcweir         DebugHelper::exception( SbERR_BAD_PARAMETER, rtl::OUString() );
1024*cdf0e10cSrcweir 
1025*cdf0e10cSrcweir     ListOfScRange aList;
1026*cdf0e10cSrcweir     lclAddToListOfScRange( aList, uno::Any( rArg1 ) );
1027*cdf0e10cSrcweir     lclAddToListOfScRange( aList, uno::Any( rArg2 ) );
1028*cdf0e10cSrcweir     lclAddToListOfScRange( aList, rArg3 );
1029*cdf0e10cSrcweir     lclAddToListOfScRange( aList, rArg4 );
1030*cdf0e10cSrcweir     lclAddToListOfScRange( aList, rArg5 );
1031*cdf0e10cSrcweir     lclAddToListOfScRange( aList, rArg6 );
1032*cdf0e10cSrcweir     lclAddToListOfScRange( aList, rArg7 );
1033*cdf0e10cSrcweir     lclAddToListOfScRange( aList, rArg8 );
1034*cdf0e10cSrcweir     lclAddToListOfScRange( aList, rArg9 );
1035*cdf0e10cSrcweir     lclAddToListOfScRange( aList, rArg10 );
1036*cdf0e10cSrcweir     lclAddToListOfScRange( aList, rArg11 );
1037*cdf0e10cSrcweir     lclAddToListOfScRange( aList, rArg12 );
1038*cdf0e10cSrcweir     lclAddToListOfScRange( aList, rArg13 );
1039*cdf0e10cSrcweir     lclAddToListOfScRange( aList, rArg14 );
1040*cdf0e10cSrcweir     lclAddToListOfScRange( aList, rArg15 );
1041*cdf0e10cSrcweir     lclAddToListOfScRange( aList, rArg16 );
1042*cdf0e10cSrcweir     lclAddToListOfScRange( aList, rArg17 );
1043*cdf0e10cSrcweir     lclAddToListOfScRange( aList, rArg18 );
1044*cdf0e10cSrcweir     lclAddToListOfScRange( aList, rArg19 );
1045*cdf0e10cSrcweir     lclAddToListOfScRange( aList, rArg20 );
1046*cdf0e10cSrcweir     lclAddToListOfScRange( aList, rArg21 );
1047*cdf0e10cSrcweir     lclAddToListOfScRange( aList, rArg22 );
1048*cdf0e10cSrcweir     lclAddToListOfScRange( aList, rArg23 );
1049*cdf0e10cSrcweir     lclAddToListOfScRange( aList, rArg24 );
1050*cdf0e10cSrcweir     lclAddToListOfScRange( aList, rArg25 );
1051*cdf0e10cSrcweir     lclAddToListOfScRange( aList, rArg26 );
1052*cdf0e10cSrcweir     lclAddToListOfScRange( aList, rArg27 );
1053*cdf0e10cSrcweir     lclAddToListOfScRange( aList, rArg28 );
1054*cdf0e10cSrcweir     lclAddToListOfScRange( aList, rArg29 );
1055*cdf0e10cSrcweir     lclAddToListOfScRange( aList, rArg30 );
1056*cdf0e10cSrcweir 
1057*cdf0e10cSrcweir     // simply join together all ranges as much as possible, strip out covered ranges etc.
1058*cdf0e10cSrcweir 	lclJoinRanges( aList );
1059*cdf0e10cSrcweir 
1060*cdf0e10cSrcweir     // create the VBA Range object
1061*cdf0e10cSrcweir     return lclCreateVbaRange( mxContext, getCurrentDocument(), aList );
1062*cdf0e10cSrcweir }
1063*cdf0e10cSrcweir 
1064*cdf0e10cSrcweir void
1065*cdf0e10cSrcweir ScVbaApplication::Volatile( const uno::Any& aVolatile )  throw ( uno::RuntimeException )
1066*cdf0e10cSrcweir {
1067*cdf0e10cSrcweir 	sal_Bool bVolatile = sal_True;
1068*cdf0e10cSrcweir 	aVolatile >>= bVolatile;
1069*cdf0e10cSrcweir 	return;
1070*cdf0e10cSrcweir }
1071*cdf0e10cSrcweir 
1072*cdf0e10cSrcweir void SAL_CALL
1073*cdf0e10cSrcweir ScVbaApplication::DoEvents() throw ( uno::RuntimeException )
1074*cdf0e10cSrcweir {
1075*cdf0e10cSrcweir }
1076*cdf0e10cSrcweir ::sal_Bool SAL_CALL
1077*cdf0e10cSrcweir ScVbaApplication::getDisplayFormulaBar() throw ( css::uno::RuntimeException )
1078*cdf0e10cSrcweir {
1079*cdf0e10cSrcweir 	sal_Bool bRes = sal_False;
1080*cdf0e10cSrcweir 	ScTabViewShell* pViewShell = excel::getCurrentBestViewShell( mxContext );
1081*cdf0e10cSrcweir 	if ( pViewShell )
1082*cdf0e10cSrcweir 	{
1083*cdf0e10cSrcweir 		SfxBoolItem sfxFormBar( FID_TOGGLEINPUTLINE);
1084*cdf0e10cSrcweir 		SfxAllItemSet reqList(  SFX_APP()->GetPool() );
1085*cdf0e10cSrcweir 		reqList.Put( sfxFormBar );
1086*cdf0e10cSrcweir 
1087*cdf0e10cSrcweir 		pViewShell->GetState( reqList );
1088*cdf0e10cSrcweir 		const SfxPoolItem *pItem=0;
1089*cdf0e10cSrcweir 		if ( reqList.GetItemState( FID_TOGGLEINPUTLINE, sal_False, &pItem ) == SFX_ITEM_SET )
1090*cdf0e10cSrcweir 			bRes =   ((SfxBoolItem*)pItem)->GetValue();
1091*cdf0e10cSrcweir 	}
1092*cdf0e10cSrcweir 	return bRes;
1093*cdf0e10cSrcweir }
1094*cdf0e10cSrcweir 
1095*cdf0e10cSrcweir void SAL_CALL
1096*cdf0e10cSrcweir ScVbaApplication::setDisplayFormulaBar( ::sal_Bool _displayformulabar ) throw ( css::uno::RuntimeException )
1097*cdf0e10cSrcweir {
1098*cdf0e10cSrcweir 	ScTabViewShell* pViewShell = excel::getCurrentBestViewShell( mxContext );
1099*cdf0e10cSrcweir 	if ( pViewShell && ( _displayformulabar !=  getDisplayFormulaBar() ) )
1100*cdf0e10cSrcweir 	{
1101*cdf0e10cSrcweir 		SfxBoolItem sfxFormBar( FID_TOGGLEINPUTLINE, _displayformulabar);
1102*cdf0e10cSrcweir 		SfxAllItemSet reqList(  SFX_APP()->GetPool() );
1103*cdf0e10cSrcweir 		SfxRequest aReq( FID_TOGGLEINPUTLINE, 0, reqList );
1104*cdf0e10cSrcweir 		pViewShell->Execute( aReq );
1105*cdf0e10cSrcweir 	}
1106*cdf0e10cSrcweir }
1107*cdf0e10cSrcweir 
1108*cdf0e10cSrcweir uno::Any SAL_CALL
1109*cdf0e10cSrcweir ScVbaApplication::Caller( const uno::Any& /*aIndex*/ ) throw ( uno::RuntimeException )
1110*cdf0e10cSrcweir {
1111*cdf0e10cSrcweir 	StarBASIC* pBasic = SFX_APP()->GetBasic();
1112*cdf0e10cSrcweir 	SbMethod* pMeth = (SbMethod*)pBasic->GetRtl()->Find( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("FuncCaller") ), SbxCLASS_METHOD );
1113*cdf0e10cSrcweir 	uno::Any aRet;
1114*cdf0e10cSrcweir 	if ( pMeth )
1115*cdf0e10cSrcweir 	{
1116*cdf0e10cSrcweir 		SbxVariableRef refTemp = pMeth;
1117*cdf0e10cSrcweir 		// forces a broadcast
1118*cdf0e10cSrcweir 		SbxVariableRef pNew = new  SbxMethod( *((SbxMethod*)pMeth));
1119*cdf0e10cSrcweir                 OSL_TRACE("pNew has type %d and string value %s", pNew->GetType(), rtl::OUStringToOString( pNew->GetString(), RTL_TEXTENCODING_UTF8 ).getStr() );
1120*cdf0e10cSrcweir 		aRet = sbxToUnoValue( pNew );
1121*cdf0e10cSrcweir 	}
1122*cdf0e10cSrcweir 	return aRet;
1123*cdf0e10cSrcweir }
1124*cdf0e10cSrcweir 
1125*cdf0e10cSrcweir uno::Any SAL_CALL ScVbaApplication::GetOpenFilename(
1126*cdf0e10cSrcweir         const uno::Any& rFileFilter, const uno::Any& rFilterIndex, const uno::Any& rTitle,
1127*cdf0e10cSrcweir         const uno::Any& rButtonText, const uno::Any& rMultiSelect ) throw (uno::RuntimeException)
1128*cdf0e10cSrcweir {
1129*cdf0e10cSrcweir     uno::Sequence< uno::Any > aArgs( 6 );
1130*cdf0e10cSrcweir     aArgs[ 0 ] <<= getThisExcelDoc( mxContext );
1131*cdf0e10cSrcweir     aArgs[ 1 ] = rFileFilter;
1132*cdf0e10cSrcweir     aArgs[ 2 ] = rFilterIndex;
1133*cdf0e10cSrcweir     aArgs[ 3 ] = rTitle;
1134*cdf0e10cSrcweir     aArgs[ 4 ] = rButtonText;
1135*cdf0e10cSrcweir     aArgs[ 5 ] = rMultiSelect;
1136*cdf0e10cSrcweir 	uno::Reference< lang::XMultiComponentFactory > xFactory( mxContext->getServiceManager(), uno::UNO_SET_THROW );
1137*cdf0e10cSrcweir 	uno::Reference< XExecutableDialog > xFilePicker( xFactory->createInstanceWithArgumentsAndContext(
1138*cdf0e10cSrcweir         ::rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "ooo.vba.OpenFilePicker" ) ), aArgs, mxContext ), uno::UNO_QUERY_THROW );
1139*cdf0e10cSrcweir     return xFilePicker->execute();
1140*cdf0e10cSrcweir }
1141*cdf0e10cSrcweir 
1142*cdf0e10cSrcweir uno::Any SAL_CALL ScVbaApplication::GetSaveAsFilename(
1143*cdf0e10cSrcweir         const uno::Any& rInitialFileName, const uno::Any& rFileFilter, const uno::Any& rFilterIndex,
1144*cdf0e10cSrcweir         const uno::Any& rTitle, const uno::Any& rButtonText ) throw (uno::RuntimeException)
1145*cdf0e10cSrcweir {
1146*cdf0e10cSrcweir     uno::Sequence< uno::Any > aArgs( 6 );
1147*cdf0e10cSrcweir     aArgs[ 0 ] <<= getThisExcelDoc( mxContext );
1148*cdf0e10cSrcweir     aArgs[ 1 ] = rInitialFileName;
1149*cdf0e10cSrcweir     aArgs[ 2 ] = rFileFilter;
1150*cdf0e10cSrcweir     aArgs[ 3 ] = rFilterIndex;
1151*cdf0e10cSrcweir     aArgs[ 4 ] = rTitle;
1152*cdf0e10cSrcweir     aArgs[ 5 ] = rButtonText;
1153*cdf0e10cSrcweir 	uno::Reference< lang::XMultiComponentFactory > xFactory( mxContext->getServiceManager(), uno::UNO_SET_THROW );
1154*cdf0e10cSrcweir 	uno::Reference< XExecutableDialog > xFilePicker( xFactory->createInstanceWithArgumentsAndContext(
1155*cdf0e10cSrcweir         ::rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "ooo.vba.SaveAsFilePicker" ) ), aArgs, mxContext ), uno::UNO_QUERY_THROW );
1156*cdf0e10cSrcweir     return xFilePicker->execute();
1157*cdf0e10cSrcweir }
1158*cdf0e10cSrcweir 
1159*cdf0e10cSrcweir uno::Reference< frame::XModel >
1160*cdf0e10cSrcweir ScVbaApplication::getCurrentDocument() throw (css::uno::RuntimeException)
1161*cdf0e10cSrcweir {
1162*cdf0e10cSrcweir     return getCurrentExcelDoc(mxContext);
1163*cdf0e10cSrcweir }
1164*cdf0e10cSrcweir 
1165*cdf0e10cSrcweir rtl::OUString&
1166*cdf0e10cSrcweir ScVbaApplication::getServiceImplName()
1167*cdf0e10cSrcweir {
1168*cdf0e10cSrcweir 	static rtl::OUString sImplName( RTL_CONSTASCII_USTRINGPARAM("ScVbaApplication") );
1169*cdf0e10cSrcweir 	return sImplName;
1170*cdf0e10cSrcweir }
1171*cdf0e10cSrcweir 
1172*cdf0e10cSrcweir uno::Sequence< rtl::OUString >
1173*cdf0e10cSrcweir ScVbaApplication::getServiceNames()
1174*cdf0e10cSrcweir {
1175*cdf0e10cSrcweir 	static uno::Sequence< rtl::OUString > aServiceNames;
1176*cdf0e10cSrcweir 	if ( aServiceNames.getLength() == 0 )
1177*cdf0e10cSrcweir 	{
1178*cdf0e10cSrcweir 		aServiceNames.realloc( 1 );
1179*cdf0e10cSrcweir 		aServiceNames[ 0 ] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.excel.Application" ) );
1180*cdf0e10cSrcweir 	}
1181*cdf0e10cSrcweir 	return aServiceNames;
1182*cdf0e10cSrcweir }
1183*cdf0e10cSrcweir 
1184*cdf0e10cSrcweir namespace application
1185*cdf0e10cSrcweir {
1186*cdf0e10cSrcweir namespace sdecl = comphelper::service_decl;
1187*cdf0e10cSrcweir sdecl::vba_service_class_<ScVbaApplication, sdecl::with_args<false> > serviceImpl;
1188*cdf0e10cSrcweir extern sdecl::ServiceDecl const serviceDecl(
1189*cdf0e10cSrcweir     serviceImpl,
1190*cdf0e10cSrcweir     "ScVbaApplication",
1191*cdf0e10cSrcweir     "ooo.vba.excel.Application" );
1192*cdf0e10cSrcweir }
1193