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