bump product version to 4.1.6.2
[LibreOffice.git] / sc / source / ui / vba / vbaapplication.cxx
blob13c62fe168269f61b8faca85c870c83c1111ddaf
1 /* -*- Mode: C++; tab-width: 4; indent-tabs-mode: nil; c-basic-offset: 4 -*- */
2 /*
3 * This file is part of the LibreOffice project.
5 * This Source Code Form is subject to the terms of the Mozilla Public
6 * License, v. 2.0. If a copy of the MPL was not distributed with this
7 * file, You can obtain one at http://mozilla.org/MPL/2.0/.
9 * This file incorporates work covered by the following license notice:
11 * Licensed to the Apache Software Foundation (ASF) under one or more
12 * contributor license agreements. See the NOTICE file distributed
13 * with this work for additional information regarding copyright
14 * ownership. The ASF licenses this file to you under the Apache
15 * License, Version 2.0 (the "License"); you may not use this file
16 * except in compliance with the License. You may obtain a copy of
17 * the License at http://www.apache.org/licenses/LICENSE-2.0 .
20 #include <stdio.h>
22 #include <com/sun/star/frame/XLayoutManager.hpp>
23 #include <com/sun/star/frame/XLayoutManager.hpp>
24 #include <com/sun/star/frame/XDesktop.hpp>
25 #include <com/sun/star/lang/XServiceInfo.hpp>
26 #include <com/sun/star/sheet/XCalculatable.hpp>
27 #include <com/sun/star/sheet/XCellRangeAddressable.hpp>
28 #include <com/sun/star/sheet/XCellRangeReferrer.hpp>
29 #include <com/sun/star/sheet/XNamedRanges.hpp>
30 #include <com/sun/star/sheet/XSpreadsheetView.hpp>
31 #include <com/sun/star/sheet/XSpreadsheets.hpp>
32 #include <com/sun/star/task/XStatusIndicatorSupplier.hpp>
33 #include <com/sun/star/task/XStatusIndicator.hpp>
34 #include <com/sun/star/util/PathSettings.hpp>
35 #include <com/sun/star/view/XSelectionSupplier.hpp>
36 #include <ooo/vba/XExecutableDialog.hpp>
37 #include <ooo/vba/excel/XlCalculation.hpp>
38 #include <ooo/vba/excel/XlMousePointer.hpp>
40 #include "vbaapplication.hxx"
41 #include "vbaworkbooks.hxx"
42 #include "vbaworkbook.hxx"
43 #include "vbaworksheets.hxx"
44 #include "vbarange.hxx"
45 #include "vbawsfunction.hxx"
46 #include "vbadialogs.hxx"
47 #include "vbawindow.hxx"
48 #include "vbawindows.hxx"
49 #include "vbaglobals.hxx"
50 #include "vbamenubars.hxx"
51 #include "tabvwsh.hxx"
52 #include "gridwin.hxx"
53 #include "vbanames.hxx"
54 #include <vbahelper/vbashape.hxx>
55 #include "vbatextboxshape.hxx"
56 #include "vbaassistant.hxx"
57 #include "sc.hrc"
58 #include "macromgr.hxx"
59 #include "defaultsoptions.hxx"
61 #include <osl/file.hxx>
62 #include <rtl/instance.hxx>
64 #include <sfx2/request.hxx>
65 #include <sfx2/objsh.hxx>
66 #include <sfx2/viewfrm.hxx>
67 #include <sfx2/app.hxx>
69 #include <comphelper/processfactory.hxx>
71 #include <toolkit/awt/vclxwindow.hxx>
72 #include <toolkit/helper/vclunohelper.hxx>
74 #include <tools/diagnose_ex.h>
75 #include <tools/urlobj.hxx>
77 #include <docuno.hxx>
79 #include <basic/sbx.hxx>
80 #include <basic/sbstar.hxx>
81 #include <basic/sbuno.hxx>
82 #include <basic/sbmeth.hxx>
84 #include "convuno.hxx"
85 #include "cellsuno.hxx"
86 #include "miscuno.hxx"
87 #include "unonames.hxx"
88 #include "docsh.hxx"
89 #include <vbahelper/helperdecl.hxx>
90 #include "excelvbahelper.hxx"
92 #include <basic/sbmod.hxx>
93 #include <basic/sbxobj.hxx>
95 #include "viewutil.hxx"
96 #include "docoptio.hxx"
98 using namespace ::ooo::vba;
99 using namespace ::com::sun::star;
100 using ::com::sun::star::uno::Reference;
101 using ::com::sun::star::uno::UNO_QUERY_THROW;
102 using ::com::sun::star::uno::UNO_QUERY;
104 // #TODO is this defined somewhere else?
105 #if ( defined UNX ) //unix
106 #define FILE_PATH_SEPARATOR "/"
107 #else // windows
108 #define FILE_PATH_SEPARATOR "\\"
109 #endif
111 // ============================================================================
113 /** Global application settings shared by all open workbooks. */
114 struct ScVbaAppSettings
116 sal_Int32 mnCalculation;
117 sal_Bool mbDisplayAlerts;
118 sal_Bool mbEnableEvents;
119 sal_Bool mbExcel4Menus;
120 sal_Bool mbDisplayNoteIndicator;
121 sal_Bool mbShowWindowsInTaskbar;
122 sal_Bool mbEnableCancelKey;
123 explicit ScVbaAppSettings();
126 ScVbaAppSettings::ScVbaAppSettings() :
127 mnCalculation( excel::XlCalculation::xlCalculationAutomatic ),
128 mbDisplayAlerts( sal_True ),
129 mbEnableEvents( sal_True ),
130 mbExcel4Menus( sal_False ),
131 mbDisplayNoteIndicator( sal_True ),
132 mbShowWindowsInTaskbar( sal_True ),
133 mbEnableCancelKey( sal_False )
137 struct ScVbaStaticAppSettings : public ::rtl::Static< ScVbaAppSettings, ScVbaStaticAppSettings > {};
139 // ============================================================================
141 ScVbaApplication::ScVbaApplication( const uno::Reference<uno::XComponentContext >& xContext ) :
142 ScVbaApplication_BASE( xContext ),
143 mrAppSettings( ScVbaStaticAppSettings::get() )
147 ScVbaApplication::~ScVbaApplication()
151 /*static*/ bool ScVbaApplication::getDocumentEventsEnabled()
153 return ScVbaStaticAppSettings::get().mbEnableEvents;
156 SfxObjectShell* ScVbaApplication::GetDocShell( const uno::Reference< frame::XModel >& xModel ) throw (uno::RuntimeException)
158 return static_cast< SfxObjectShell* >( excel::getDocShell( xModel ) );
161 OUString SAL_CALL
162 ScVbaApplication::getExactName( const OUString& aApproximateName ) throw (uno::RuntimeException)
164 uno::Reference< beans::XExactName > xWSF( new ScVbaWSFunction( this, mxContext ) );
165 return xWSF->getExactName( aApproximateName );
168 uno::Reference< beans::XIntrospectionAccess > SAL_CALL
169 ScVbaApplication::getIntrospection() throw(css::uno::RuntimeException)
171 uno::Reference< script::XInvocation > xWSF( new ScVbaWSFunction( this, mxContext ) );
172 return xWSF->getIntrospection();
175 uno::Any SAL_CALL
176 ScVbaApplication::invoke( const 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)
178 /* When calling the functions directly at the Application object, no runtime
179 errors are thrown, but the error is inserted into the return value. */
180 uno::Any aAny;
183 uno::Reference< script::XInvocation > xWSF( new ScVbaWSFunction( this, mxContext ) );
184 aAny = xWSF->invoke( FunctionName, Params, OutParamIndex, OutParam );
186 catch (const uno::Exception&)
188 aAny <<= script::BasicErrorException( OUString(), uno::Reference< uno::XInterface >(), 1000, OUString() );
190 return aAny;
193 void SAL_CALL
194 ScVbaApplication::setValue( const OUString& PropertyName, const uno::Any& Value ) throw(beans::UnknownPropertyException, script::CannotConvertException, reflection::InvocationTargetException, uno::RuntimeException)
196 uno::Reference< script::XInvocation > xWSF( new ScVbaWSFunction( this, mxContext ) );
197 xWSF->setValue( PropertyName, Value );
200 uno::Any SAL_CALL
201 ScVbaApplication::getValue( const OUString& PropertyName ) throw(beans::UnknownPropertyException, uno::RuntimeException)
203 uno::Reference< script::XInvocation > xWSF( new ScVbaWSFunction( this, mxContext ) );
204 return xWSF->getValue( PropertyName );
207 sal_Bool SAL_CALL
208 ScVbaApplication::hasMethod( const OUString& Name ) throw(uno::RuntimeException)
210 uno::Reference< script::XInvocation > xWSF( new ScVbaWSFunction( this, mxContext ) );
211 return xWSF->hasMethod( Name );
214 sal_Bool SAL_CALL
215 ScVbaApplication::hasProperty( const OUString& Name ) throw(uno::RuntimeException)
217 uno::Reference< script::XInvocation > xWSF( new ScVbaWSFunction( this, mxContext ) );
218 return xWSF->hasProperty( Name );
221 uno::Reference< excel::XWorkbook >
222 ScVbaApplication::getActiveWorkbook() throw (uno::RuntimeException)
224 uno::Reference< frame::XModel > xModel( getCurrentExcelDoc( mxContext ), uno::UNO_SET_THROW );
225 uno::Reference< excel::XWorkbook > xWorkbook( getVBADocument( xModel ), uno::UNO_QUERY );
226 if( xWorkbook.is() ) return xWorkbook;
227 // #i116936# getVBADocument() may return null in documents without global VBA mode enabled
228 return new ScVbaWorkbook( this, mxContext, xModel );
231 uno::Reference< excel::XWorkbook > SAL_CALL
232 ScVbaApplication::getThisWorkbook() throw (uno::RuntimeException)
234 uno::Reference< frame::XModel > xModel( getThisExcelDoc( mxContext ), uno::UNO_SET_THROW );
235 uno::Reference< excel::XWorkbook > xWorkbook( getVBADocument( xModel ), uno::UNO_QUERY );
236 if( xWorkbook.is() ) return xWorkbook;
237 // #i116936# getVBADocument() may return null in documents without global VBA mode enabled
238 return new ScVbaWorkbook( this, mxContext, xModel );
241 uno::Reference< XAssistant > SAL_CALL
242 ScVbaApplication::getAssistant() throw (uno::RuntimeException)
244 return uno::Reference< XAssistant >( new ScVbaAssistant( this, mxContext ) );
247 uno::Any SAL_CALL
248 ScVbaApplication::getSelection() throw (uno::RuntimeException)
250 OSL_TRACE("** ScVbaApplication::getSelection() ** ");
251 uno::Reference< frame::XModel > xModel( getCurrentDocument() );
253 Reference< view::XSelectionSupplier > xSelSupp( xModel->getCurrentController(), UNO_QUERY_THROW );
254 Reference< beans::XPropertySet > xPropSet( xSelSupp, UNO_QUERY_THROW );
255 OUString aPropName( SC_UNO_FILTERED_RANGE_SELECTION );
256 uno::Any aOldVal = xPropSet->getPropertyValue( aPropName );
257 uno::Any any;
258 any <<= false;
259 xPropSet->setPropertyValue( aPropName, any );
260 uno::Reference< uno::XInterface > aSelection = ScUnoHelpFunctions::AnyToInterface(
261 xSelSupp->getSelection() );
262 xPropSet->setPropertyValue( aPropName, aOldVal );
264 if (!aSelection.is())
266 throw uno::RuntimeException(
267 OUString("failed to obtain current selection"),
268 uno::Reference< uno::XInterface >() );
271 uno::Reference< lang::XServiceInfo > xServiceInfo( aSelection, uno::UNO_QUERY_THROW );
272 OUString sImplementationName = xServiceInfo->getImplementationName();
274 if( sImplementationName.equalsIgnoreAsciiCase("com.sun.star.drawing.SvxShapeCollection") )
276 uno::Reference< drawing::XShapes > xShapes( aSelection, uno::UNO_QUERY_THROW );
277 uno::Reference< container::XIndexAccess > xIndexAccess( xShapes, uno::UNO_QUERY_THROW );
278 uno::Reference< drawing::XShape > xShape( xIndexAccess->getByIndex(0), uno::UNO_QUERY_THROW );
279 // if ScVbaShape::getType( xShape ) == office::MsoShapeType::msoAutoShape
280 // and the uno object implements the com.sun.star.drawing.Text service
281 // return a textboxshape object
282 if ( ScVbaShape::getType( xShape ) == office::MsoShapeType::msoAutoShape )
284 uno::Reference< lang::XServiceInfo > xShapeServiceInfo( xShape, uno::UNO_QUERY_THROW );
285 if ( xShapeServiceInfo->supportsService( OUString( "com.sun.star.drawing.Text" ) ) )
287 return uno::makeAny( uno::Reference< msforms::XTextBoxShape >(new ScVbaTextBoxShape( mxContext, xShape, xShapes, xModel ) ) );
290 return uno::makeAny( uno::Reference< msforms::XShape >(new ScVbaShape( this, mxContext, xShape, xShapes, xModel, ScVbaShape::getType( xShape ) ) ) );
292 else if( xServiceInfo->supportsService( OUString("com.sun.star.sheet.SheetCellRange") ) ||
293 xServiceInfo->supportsService( OUString("com.sun.star.sheet.SheetCellRanges") ) )
295 uno::Reference< table::XCellRange > xRange( aSelection, ::uno::UNO_QUERY);
296 if ( !xRange.is() )
298 uno::Reference< sheet::XSheetCellRangeContainer > xRanges( aSelection, ::uno::UNO_QUERY);
299 if ( xRanges.is() )
300 return uno::makeAny( uno::Reference< excel::XRange >( new ScVbaRange( excel::getUnoSheetModuleObj( xRanges ), mxContext, xRanges ) ) );
303 return uno::makeAny( uno::Reference< excel::XRange >(new ScVbaRange( excel::getUnoSheetModuleObj( xRange ), mxContext, xRange ) ) );
305 else
307 throw uno::RuntimeException( sImplementationName + OUString(
308 " not supported"), uno::Reference< uno::XInterface >() );
312 uno::Reference< excel::XRange >
313 ScVbaApplication::getActiveCell() throw (uno::RuntimeException )
315 uno::Reference< sheet::XSpreadsheetView > xView( getCurrentDocument()->getCurrentController(), uno::UNO_QUERY_THROW );
316 uno::Reference< table::XCellRange > xRange( xView->getActiveSheet(), ::uno::UNO_QUERY_THROW);
317 ScTabViewShell* pViewShell = excel::getCurrentBestViewShell(mxContext);
318 if ( !pViewShell )
319 throw uno::RuntimeException( OUString("No ViewShell available"), uno::Reference< uno::XInterface >() );
320 ScViewData* pTabView = pViewShell->GetViewData();
321 if ( !pTabView )
322 throw uno::RuntimeException( OUString("No ViewData available"), uno::Reference< uno::XInterface >() );
324 sal_Int32 nCursorX = pTabView->GetCurX();
325 sal_Int32 nCursorY = pTabView->GetCurY();
327 // #i117392# excel::getUnoSheetModuleObj() may return null in documents without global VBA mode enabled
328 return new ScVbaRange( excel::getUnoSheetModuleObj( xRange ), mxContext, xRange->getCellRangeByPosition( nCursorX, nCursorY, nCursorX, nCursorY ) );
331 uno::Any SAL_CALL
332 ScVbaApplication::International( sal_Int32 /*Index*/ ) throw (uno::RuntimeException)
334 // complete stub for now
335 // #TODO flesh out some of the Indices we could handle
336 uno::Any aRet;
337 return aRet;
340 uno::Any SAL_CALL
341 ScVbaApplication::Workbooks( const uno::Any& aIndex ) throw (uno::RuntimeException)
343 uno::Reference< XCollection > xWorkBooks( new ScVbaWorkbooks( this, mxContext ) );
344 if ( aIndex.getValueTypeClass() == uno::TypeClass_VOID )
346 // void then somebody did Workbooks.something in vba
347 return uno::Any( xWorkBooks );
350 return uno::Any ( xWorkBooks->Item( aIndex, uno::Any() ) );
353 uno::Any SAL_CALL
354 ScVbaApplication::Worksheets( const uno::Any& aIndex ) throw (uno::RuntimeException)
356 uno::Reference< excel::XWorkbook > xWorkbook( getActiveWorkbook(), uno::UNO_SET_THROW );
357 return xWorkbook->Worksheets( aIndex );
360 uno::Any SAL_CALL
361 ScVbaApplication::WorksheetFunction( ) throw (::com::sun::star::uno::RuntimeException)
363 return uno::makeAny( uno::Reference< script::XInvocation >( new ScVbaWSFunction( this, mxContext ) ) );
366 uno::Any SAL_CALL
367 ScVbaApplication::Evaluate( const OUString& Name ) throw (uno::RuntimeException)
369 // #TODO Evaluate allows other things to be evaluated, e.g. functions
370 // I think ( like SIN(3) etc. ) need to investigate that
371 // named Ranges also? e.g. [MyRange] if so need a list of named ranges
372 uno::Any aVoid;
373 return uno::Any( getActiveWorkbook()->getActiveSheet()->Range( uno::Any( Name ), aVoid ) );
376 uno::Any
377 ScVbaApplication::Dialogs( const uno::Any &aIndex ) throw (uno::RuntimeException)
379 uno::Reference< excel::XDialogs > xDialogs( new ScVbaDialogs( uno::Reference< XHelperInterface >( this ), mxContext, getCurrentDocument() ) );
380 if( !aIndex.hasValue() )
381 return uno::Any( xDialogs );
382 return uno::Any( xDialogs->Item( aIndex ) );
385 uno::Reference< excel::XWindow > SAL_CALL
386 ScVbaApplication::getActiveWindow() throw (uno::RuntimeException)
388 uno::Reference< frame::XModel > xModel = getCurrentDocument();
389 uno::Reference< frame::XController > xController( xModel->getCurrentController(), uno::UNO_SET_THROW );
390 uno::Reference< XHelperInterface > xParent( getActiveWorkbook(), uno::UNO_QUERY_THROW );
391 uno::Reference< excel::XWindow > xWin( new ScVbaWindow( xParent, mxContext, xModel, xController ) );
392 return xWin;
395 uno::Any SAL_CALL
396 ScVbaApplication::getCutCopyMode() throw (uno::RuntimeException)
398 //# FIXME TODO, implementation
399 uno::Any result;
400 result <<= sal_False;
401 return result;
404 void SAL_CALL
405 ScVbaApplication::setCutCopyMode( const uno::Any& /* _cutcopymode */ ) throw (uno::RuntimeException)
407 //# FIXME TODO, implementation
410 uno::Any SAL_CALL
411 ScVbaApplication::getStatusBar() throw (uno::RuntimeException)
413 return uno::makeAny( !getDisplayStatusBar() );
416 void SAL_CALL
417 ScVbaApplication::setStatusBar( const uno::Any& _statusbar ) throw (uno::RuntimeException)
419 OUString sText;
420 sal_Bool bDefault = false;
421 uno::Reference< frame::XModel > xModel( getCurrentDocument(), uno::UNO_QUERY_THROW );
422 uno::Reference< task::XStatusIndicatorSupplier > xStatusIndicatorSupplier( xModel->getCurrentController(), uno::UNO_QUERY_THROW );
423 uno::Reference< task::XStatusIndicator > xStatusIndicator( xStatusIndicatorSupplier->getStatusIndicator(), uno::UNO_QUERY_THROW );
424 if( _statusbar >>= sText )
426 setDisplayStatusBar( sal_True );
427 if ( !sText.isEmpty() )
428 xStatusIndicator->start( sText, 100 );
429 else
430 xStatusIndicator->end(); // restore normal state for empty text
432 else if( _statusbar >>= bDefault )
434 if( bDefault == false )
436 xStatusIndicator->end();
437 setDisplayStatusBar( sal_True );
440 else
441 throw uno::RuntimeException( OUString( "Invalid prarameter. It should be a string or False" ),
442 uno::Reference< uno::XInterface >() );
445 ::sal_Int32 SAL_CALL
446 ScVbaApplication::getCalculation() throw (uno::RuntimeException)
448 // TODO: in Excel, this is an application-wide setting
449 uno::Reference<sheet::XCalculatable> xCalc(getCurrentDocument(), uno::UNO_QUERY_THROW);
450 if(xCalc->isAutomaticCalculationEnabled())
451 return excel::XlCalculation::xlCalculationAutomatic;
452 else
453 return excel::XlCalculation::xlCalculationManual;
456 void SAL_CALL
457 ScVbaApplication::setCalculation( ::sal_Int32 _calculation ) throw (uno::RuntimeException)
459 // TODO: in Excel, this is an application-wide setting
460 uno::Reference< sheet::XCalculatable > xCalc(getCurrentDocument(), uno::UNO_QUERY_THROW);
461 switch(_calculation)
463 case excel::XlCalculation::xlCalculationManual:
464 xCalc->enableAutomaticCalculation(false);
465 break;
466 case excel::XlCalculation::xlCalculationAutomatic:
467 case excel::XlCalculation::xlCalculationSemiautomatic:
468 xCalc->enableAutomaticCalculation(sal_True);
469 break;
473 uno::Any SAL_CALL
474 ScVbaApplication::Windows( const uno::Any& aIndex ) throw (uno::RuntimeException)
476 uno::Reference< excel::XWindows > xWindows( new ScVbaWindows( this, mxContext ) );
477 if ( aIndex.getValueTypeClass() == uno::TypeClass_VOID )
478 return uno::Any( xWindows );
479 return uno::Any( xWindows->Item( aIndex, uno::Any() ) );
481 void SAL_CALL
482 ScVbaApplication::wait( double time ) throw (uno::RuntimeException)
484 StarBASIC* pBasic = SFX_APP()->GetBasic();
485 SbxArrayRef aArgs = new SbxArray;
486 SbxVariableRef aRef = new SbxVariable;
487 aRef->PutDouble( time );
488 aArgs->Put( aRef, 1 );
489 SbMethod* pMeth = (SbMethod*)pBasic->GetRtl()->Find( OUString("WaitUntil"), SbxCLASS_METHOD );
491 if ( pMeth )
493 pMeth->SetParameters( aArgs );
494 SbxVariableRef refTemp = pMeth;
495 // forces a broadcast
496 SbxVariableRef pNew = new SbxMethod( *((SbxMethod*)pMeth));
500 uno::Any SAL_CALL
501 ScVbaApplication::Range( const uno::Any& Cell1, const uno::Any& Cell2 ) throw (uno::RuntimeException)
503 uno::Reference< excel::XRange > xVbRange = ScVbaRange::ApplicationRange( mxContext, Cell1, Cell2 );
504 return uno::makeAny( xVbRange );
507 uno::Any SAL_CALL
508 ScVbaApplication::Names( const css::uno::Any& aIndex ) throw ( uno::RuntimeException )
510 uno::Reference< frame::XModel > xModel( getCurrentDocument(), uno::UNO_QUERY_THROW );
511 uno::Reference< beans::XPropertySet > xPropertySet( xModel, uno::UNO_QUERY_THROW );
512 uno::Reference< sheet::XNamedRanges > xNamedRanges( xPropertySet->getPropertyValue(
513 OUString( "NamedRanges" ) ), uno::UNO_QUERY_THROW );
515 css::uno::Reference< excel::XNames > xNames ( new ScVbaNames( this , mxContext , xNamedRanges , xModel ) );
516 if ( aIndex.getValueTypeClass() == uno::TypeClass_VOID )
518 return uno::Any( xNames );
520 return uno::Any( xNames->Item( aIndex, uno::Any() ) );
524 uno::Reference< excel::XWorksheet > SAL_CALL
525 ScVbaApplication::getActiveSheet() throw (uno::RuntimeException)
527 uno::Reference< excel::XWorksheet > result;
528 uno::Reference< excel::XWorkbook > xWorkbook( getActiveWorkbook(), uno::UNO_QUERY );
529 if ( xWorkbook.is() )
531 uno::Reference< excel::XWorksheet > xWorksheet(
532 xWorkbook->getActiveSheet(), uno::UNO_QUERY );
533 if ( xWorksheet.is() )
535 result = xWorksheet;
539 if ( !result.is() )
541 // Fixme - check if this is reasonable/desired behavior
542 throw uno::RuntimeException( OUString( "No activeSheet available" ),
543 uno::Reference< uno::XInterface >() );
545 return result;
549 /*******************************************************************************
550 * In msdn:
551 * Reference Optional Variant. The destination. Can be a Range
552 * object, a string that contains a cell reference in R1C1-style notation,
553 * or a string that contains a Visual Basic procedure name.
554 * Scroll Optional Variant. True to scrol, False to not scroll through
555 * the window. The default is False.
556 * Parser is split to three parts, Range, R1C1 string and procedure name.
557 * by test excel, it seems Scroll no effect. ???
558 *******************************************************************************/
559 void SAL_CALL
560 ScVbaApplication::GoTo( const uno::Any& Reference, const uno::Any& Scroll ) throw (uno::RuntimeException)
562 //test Scroll is a boolean
563 sal_Bool bScroll = false;
564 //R1C1-style string or a string of procedure name.
566 if( Scroll.hasValue() )
568 sal_Bool aScroll = false;
569 if( Scroll >>= aScroll )
571 bScroll = aScroll;
573 else
574 throw uno::RuntimeException( OUString( "second parameter should be boolean" ),
575 uno::Reference< uno::XInterface >() );
578 OUString sRangeName;
579 if( Reference >>= sRangeName )
581 uno::Reference< frame::XModel > xModel( getCurrentDocument(), uno::UNO_QUERY_THROW );
582 uno::Reference< sheet::XSpreadsheetView > xSpreadsheet(
583 xModel->getCurrentController(), uno::UNO_QUERY_THROW );
584 uno::Reference< sheet::XSpreadsheet > xDoc = xSpreadsheet->getActiveSheet();
586 ScTabViewShell* pShell = excel::getCurrentBestViewShell( mxContext );
587 ScGridWindow* gridWindow = (ScGridWindow*)pShell->GetWindow();
590 uno::Reference< excel::XRange > xVbaSheetRange = ScVbaRange::getRangeObjectForName(
591 mxContext, sRangeName, excel::getDocShell( xModel ), formula::FormulaGrammar::CONV_XL_R1C1 );
593 if( bScroll )
595 xVbaSheetRange->Select();
596 uno::Reference< excel::XWindow > xWindow = getActiveWindow();
597 ScSplitPos eWhich = pShell->GetViewData()->GetActivePart();
598 sal_Int32 nValueX = pShell->GetViewData()->GetPosX(WhichH(eWhich));
599 sal_Int32 nValueY = pShell->GetViewData()->GetPosY(WhichV(eWhich));
600 xWindow->SmallScroll( uno::makeAny( (sal_Int16)(xVbaSheetRange->getRow() - 1) ),
601 uno::makeAny( (sal_Int16)nValueY ),
602 uno::makeAny( (sal_Int16)(xVbaSheetRange->getColumn() - 1) ),
603 uno::makeAny( (sal_Int16)nValueX ) );
604 gridWindow->GrabFocus();
606 else
608 xVbaSheetRange->Select();
609 gridWindow->GrabFocus();
612 catch (const uno::RuntimeException&)
614 //maybe this should be a procedure name
615 //TODO for procedure name
616 //browse::XBrowseNodeFactory is a singlton. OUString( "/singletons/com.sun.star.script.browse.theBrowseNodeFactory")
617 //and the createView( browse::BrowseNodeFactoryViewTypes::MACROSELECTOR ) to get a root browse::XBrowseNode.
618 //for query XInvocation interface.
619 //but how to directly get the XInvocation?
620 throw uno::RuntimeException( OUString( "invalid reference for range name, it should be procedure name" ),
621 uno::Reference< uno::XInterface >() );
623 return;
625 uno::Reference< excel::XRange > xRange;
626 if( Reference >>= xRange )
628 uno::Reference< excel::XRange > xVbaRange( Reference, uno::UNO_QUERY );
629 ScTabViewShell* pShell = excel::getCurrentBestViewShell( mxContext );
630 ScGridWindow* gridWindow = (ScGridWindow*)pShell->GetWindow();
631 if ( xVbaRange.is() )
633 //TODO bScroll should be using, In this time, it doesenot have effection
634 if( bScroll )
636 xVbaRange->Select();
637 uno::Reference< excel::XWindow > xWindow = getActiveWindow();
638 ScSplitPos eWhich = pShell->GetViewData()->GetActivePart();
639 sal_Int32 nValueX = pShell->GetViewData()->GetPosX(WhichH(eWhich));
640 sal_Int32 nValueY = pShell->GetViewData()->GetPosY(WhichV(eWhich));
641 xWindow->SmallScroll( uno::makeAny( (sal_Int16)(xVbaRange->getRow() - 1) ),
642 uno::makeAny( (sal_Int16)nValueY ),
643 uno::makeAny( (sal_Int16)(xVbaRange->getColumn() - 1) ),
644 uno::makeAny( (sal_Int16)nValueX ) );
645 gridWindow->GrabFocus();
647 else
649 xVbaRange->Select();
650 gridWindow->GrabFocus();
653 return;
655 throw uno::RuntimeException( OUString( "invalid reference or name" ),
656 uno::Reference< uno::XInterface >() );
659 sal_Int32 SAL_CALL
660 ScVbaApplication::getCursor() throw (uno::RuntimeException)
662 sal_Int32 nPointerStyle = getPointerStyle(getCurrentDocument());
664 switch( nPointerStyle )
666 case POINTER_ARROW:
667 return excel::XlMousePointer::xlNorthwestArrow;
668 case POINTER_NULL:
669 return excel::XlMousePointer::xlDefault;
670 case POINTER_WAIT:
671 return excel::XlMousePointer::xlWait;
672 case POINTER_TEXT:
673 return excel::XlMousePointer::xlIBeam;
674 default:
675 return excel::XlMousePointer::xlDefault;
679 void SAL_CALL
680 ScVbaApplication::setCursor( sal_Int32 _cursor ) throw (uno::RuntimeException)
684 uno::Reference< frame::XModel > xModel( getCurrentDocument(), uno::UNO_QUERY_THROW );
685 switch( _cursor )
687 case excel::XlMousePointer::xlNorthwestArrow:
689 const Pointer& rPointer( POINTER_ARROW );
690 setCursorHelper( xModel, rPointer, false );
691 break;
693 case excel::XlMousePointer::xlWait:
694 case excel::XlMousePointer::xlIBeam:
696 const Pointer& rPointer( static_cast< PointerStyle >( _cursor ) );
697 //It will set the edit window, toobar and statusbar's mouse pointer.
698 setCursorHelper( xModel, rPointer, sal_True );
699 break;
701 case excel::XlMousePointer::xlDefault:
703 const Pointer& rPointer( POINTER_NULL );
704 setCursorHelper( xModel, rPointer, false );
705 break;
707 default:
708 throw uno::RuntimeException( OUString("Unknown value for Cursor pointer"), uno::Reference< uno::XInterface >() );
709 // TODO: isn't this a flaw in the API? It should be allowed to throw an
710 // IllegalArgumentException, or so
713 catch (const uno::Exception&)
715 DBG_UNHANDLED_EXCEPTION();
719 // #TODO perhaps we should switch the return type depending of the filter
720 // type, e.g. return Calc for Calc and Excel if its an imported doc
721 OUString SAL_CALL
722 ScVbaApplication::getName() throw (uno::RuntimeException)
724 static OUString appName("Microsoft Excel" );
725 return appName;
728 // #TODO #FIXME get/setDisplayAlerts are just stub impl
729 // here just the status of the switch is set
730 // the function that throws an error message needs to
731 // evaluate this switch in order to know whether it has to disable the
732 // error message thrown by OpenOffice
734 void SAL_CALL
735 ScVbaApplication::setDisplayAlerts(sal_Bool displayAlerts) throw (uno::RuntimeException)
737 mrAppSettings.mbDisplayAlerts = displayAlerts;
740 sal_Bool SAL_CALL
741 ScVbaApplication::getDisplayAlerts() throw (uno::RuntimeException)
743 return mrAppSettings.mbDisplayAlerts;
746 void SAL_CALL
747 ScVbaApplication::setEnableEvents(sal_Bool bEnable) throw (uno::RuntimeException)
749 mrAppSettings.mbEnableEvents = bEnable;
752 sal_Bool SAL_CALL
753 ScVbaApplication::getEnableEvents() throw (uno::RuntimeException)
755 return mrAppSettings.mbEnableEvents;
758 void SAL_CALL
759 ScVbaApplication::setEnableCancelKey(sal_Bool bEnable) throw (uno::RuntimeException)
761 // Stub, does nothing
762 mrAppSettings.mbEnableCancelKey = bEnable;
765 sal_Bool SAL_CALL
766 ScVbaApplication::getEnableCancelKey() throw (uno::RuntimeException)
768 return mrAppSettings.mbEnableCancelKey;
771 sal_Bool SAL_CALL
772 ScVbaApplication::getDisplayFullScreen() throw (uno::RuntimeException)
774 SfxViewShell* pShell = excel::getCurrentBestViewShell( mxContext );
775 if ( pShell )
776 return ScViewUtil::IsFullScreen( *pShell );
777 return sal_False;
780 void SAL_CALL
781 ScVbaApplication::setDisplayFullScreen( sal_Bool bSet ) throw (uno::RuntimeException)
783 // #FIXME calling ScViewUtil::SetFullScreen( *pShell, bSet );
784 // directly results in a strange crash, using dispatch instead
785 if ( bSet != getDisplayFullScreen() )
786 dispatchRequests( getCurrentDocument(), OUString(".uno:FullScreen") );
789 sal_Bool SAL_CALL
790 ScVbaApplication::getDisplayScrollBars() throw (uno::RuntimeException)
792 ScTabViewShell* pShell = excel::getCurrentBestViewShell( mxContext );
793 if ( pShell )
795 return ( pShell->GetViewData()->IsHScrollMode() && pShell->GetViewData()->IsVScrollMode() );
797 return true;
800 void SAL_CALL
801 ScVbaApplication::setDisplayScrollBars( sal_Bool bSet ) throw (uno::RuntimeException)
803 // use uno here as it does all he repainting etc. magic
804 uno::Reference< sheet::XSpreadsheetView > xView( getCurrentDocument()->getCurrentController(), uno::UNO_QUERY_THROW );
805 uno::Reference< beans::XPropertySet > xProps( xView, uno::UNO_QUERY );
806 xProps->setPropertyValue( OUString("HasVerticalScrollBar"), uno::makeAny( bSet ) );
807 xProps->setPropertyValue( OUString("HasHorizontalScrollBar"), uno::makeAny( bSet ) );
810 sal_Bool SAL_CALL
811 ScVbaApplication::getDisplayExcel4Menus() throw (css::uno::RuntimeException)
813 return mrAppSettings.mbExcel4Menus;
816 void SAL_CALL
817 ScVbaApplication::setDisplayExcel4Menus( sal_Bool bSet ) throw (css::uno::RuntimeException)
819 mrAppSettings.mbExcel4Menus = bSet;
822 sal_Bool SAL_CALL
823 ScVbaApplication::getDisplayNoteIndicator() throw (css::uno::RuntimeException)
825 return mrAppSettings.mbDisplayNoteIndicator;
828 void SAL_CALL
829 ScVbaApplication::setDisplayNoteIndicator( sal_Bool bSet ) throw (css::uno::RuntimeException)
831 mrAppSettings.mbDisplayNoteIndicator = bSet;
834 sal_Bool SAL_CALL
835 ScVbaApplication::getShowWindowsInTaskbar() throw (css::uno::RuntimeException)
837 return mrAppSettings.mbShowWindowsInTaskbar;
840 void SAL_CALL
841 ScVbaApplication::setShowWindowsInTaskbar( sal_Bool bSet ) throw (css::uno::RuntimeException)
843 mrAppSettings.mbShowWindowsInTaskbar = bSet;
846 sal_Bool SAL_CALL
847 ScVbaApplication::getIteration() throw (css::uno::RuntimeException)
849 return SC_MOD()->GetDocOptions().IsIter();
852 void SAL_CALL
853 ScVbaApplication::setIteration( sal_Bool bSet ) throw (css::uno::RuntimeException)
855 uno::Reference< lang::XMultiComponentFactory > xSMgr(
856 mxContext->getServiceManager(), uno::UNO_QUERY_THROW );
858 uno::Reference< frame::XDesktop > xDesktop
859 (xSMgr->createInstanceWithContext( "com.sun.star.frame.Desktop" , mxContext), uno::UNO_QUERY_THROW );
860 uno::Reference< container::XEnumeration > xComponents = xDesktop->getComponents()->createEnumeration();
861 while ( xComponents->hasMoreElements() )
863 uno::Reference< lang::XServiceInfo > xServiceInfo( xComponents->nextElement(), uno::UNO_QUERY );
864 if ( xServiceInfo.is() && xServiceInfo->supportsService( "com.sun.star.sheet.SpreadsheetDocument" ) )
866 uno::Reference< beans::XPropertySet > xProps( xServiceInfo, uno::UNO_QUERY );
867 if ( xProps.is() )
868 xProps->setPropertyValue( SC_UNO_ITERENABLED, uno::Any( bSet ) );
871 ScDocOptions aOpts( SC_MOD()->GetDocOptions() );
872 aOpts.SetIter( bSet );
873 SC_MOD()->SetDocOptions( aOpts );
876 void SAL_CALL
877 ScVbaApplication::Calculate() throw( script::BasicErrorException , uno::RuntimeException )
879 uno::Reference< frame::XModel > xModel( getCurrentDocument(), uno::UNO_QUERY_THROW );
880 uno::Reference< sheet::XCalculatable > xCalculatable( getCurrentDocument(), uno::UNO_QUERY_THROW );
881 xCalculatable->calculateAll();
884 static uno::Reference< util::XPathSettings > lcl_getPathSettingsService( const uno::Reference< uno::XComponentContext >& xContext ) throw ( uno::RuntimeException )
886 static uno::Reference< util::XPathSettings > xPathSettings;
887 if ( !xPathSettings.is() )
889 xPathSettings.set( util::PathSettings::create( xContext ) );
891 return xPathSettings;
893 OUString ScVbaApplication::getOfficePath( const OUString& _sPathType ) throw ( uno::RuntimeException )
895 OUString sRetPath;
896 uno::Reference< util::XPathSettings > xProps = lcl_getPathSettingsService( mxContext );
899 OUString sUrl;
900 xProps->getPropertyValue( _sPathType ) >>= sUrl;
902 // if its a list of paths then use the last one
903 sal_Int32 nIndex = sUrl.lastIndexOf( ';' ) ;
904 if ( nIndex > 0 )
905 sUrl = sUrl.copy( nIndex + 1 );
906 ::osl::File::getSystemPathFromFileURL( sUrl, sRetPath );
908 catch (const uno::Exception&)
910 DebugHelper::exception(SbERR_METHOD_FAILED, OUString());
912 return sRetPath;
915 void SAL_CALL
916 ScVbaApplication::setDefaultFilePath( const OUString& DefaultFilePath ) throw (uno::RuntimeException)
918 uno::Reference< util::XPathSettings > xProps = lcl_getPathSettingsService( mxContext );
919 OUString aURL;
920 osl::FileBase::getFileURLFromSystemPath( DefaultFilePath, aURL );
921 xProps->setWork( aURL );
924 OUString SAL_CALL
925 ScVbaApplication::getDefaultFilePath() throw (uno::RuntimeException)
927 return getOfficePath( OUString("Work"));
930 OUString SAL_CALL
931 ScVbaApplication::getLibraryPath() throw (uno::RuntimeException)
933 return getOfficePath( OUString("Basic"));
936 OUString SAL_CALL
937 ScVbaApplication::getTemplatesPath() throw (uno::RuntimeException)
939 return getOfficePath( OUString("Template"));
942 OUString SAL_CALL
943 ScVbaApplication::getPathSeparator() throw (uno::RuntimeException)
945 static OUString sPathSep( FILE_PATH_SEPARATOR );
946 return sPathSep;
949 // ----------------------------------------------------------------------------
950 // Helpers for Intersect and Union
952 namespace {
954 typedef ::std::list< ScRange > ListOfScRange;
956 /** Appends all ranges of a VBA Range object in the passed Any to the list of ranges. */
957 void lclAddToListOfScRange( ListOfScRange& rList, const uno::Any& rArg )
958 throw (script::BasicErrorException, uno::RuntimeException)
960 if( rArg.hasValue() )
962 uno::Reference< excel::XRange > xRange( rArg, uno::UNO_QUERY_THROW );
963 uno::Reference< XCollection > xCol( xRange->Areas( uno::Any() ), uno::UNO_QUERY_THROW );
964 for( sal_Int32 nIdx = 1, nCount = xCol->getCount(); nIdx <= nCount; ++nIdx )
966 uno::Reference< excel::XRange > xAreaRange( xCol->Item( uno::Any( nIdx ), uno::Any() ), uno::UNO_QUERY_THROW );
967 uno::Reference< sheet::XCellRangeAddressable > xAddressable( xAreaRange->getCellRange(), uno::UNO_QUERY_THROW );
968 ScRange aScRange;
969 ScUnoConversion::FillScRange( aScRange, xAddressable->getRangeAddress() );
970 rList.push_back( aScRange );
975 /** Returns true, if the passed ranges can be expressed by a single range. The
976 new range will be contained in r1 then, the range r2 can be removed. */
977 bool lclTryJoin( ScRange& r1, const ScRange& r2 )
979 // 1) r2 is completely inside r1
980 if( r1.In( r2 ) )
981 return true;
983 // 2) r1 is completely inside r2
984 if( r2.In( r1 ) )
986 r1 = r2;
987 return true;
990 SCCOL n1L = r1.aStart.Col();
991 SCCOL n1R = r1.aEnd.Col();
992 SCROW n1T = r1.aStart.Row();
993 SCROW n1B = r1.aEnd.Row();
994 SCCOL n2L = r2.aStart.Col();
995 SCCOL n2R = r2.aEnd.Col();
996 SCROW n2T = r2.aStart.Row();
997 SCROW n2B = r2.aEnd.Row();
999 // 3) r1 and r2 have equal upper and lower border
1000 if( (n1T == n2T) && (n1B == n2B) )
1002 // check that r1 overlaps or touches r2
1003 if( ((n1L < n2L) && (n2L - 1 <= n1R)) || ((n2L < n1L) && (n1L - 1 <= n2R)) )
1005 r1.aStart.SetCol( ::std::min( n1L, n2L ) );
1006 r1.aEnd.SetCol( ::std::max( n1R, n2R ) );
1007 return true;
1009 return false;
1012 // 4) r1 and r2 have equal left and right border
1013 if( (n1L == n2L) && (n1R == n2R) )
1015 // check that r1 overlaps or touches r2
1016 if( ((n1T < n2T) && (n2T + 1 <= n1B)) || ((n2T < n1T) && (n1T + 1 <= n2B)) )
1018 r1.aStart.SetRow( ::std::min( n1T, n2T ) );
1019 r1.aEnd.SetRow( ::std::max( n1B, n2B ) );
1020 return true;
1022 return false;
1025 // 5) cannot join these ranges
1026 return false;
1029 /** Strips out ranges that are contained by other ranges, joins ranges that can be joined
1030 together (aligned borders, e.g. A4:D10 and B4:E10 would be combined to A4:E10. */
1031 void lclJoinRanges( ListOfScRange& rList )
1033 ListOfScRange::iterator aOuterIt = rList.begin();
1034 while( aOuterIt != rList.end() )
1036 bool bAnyErased = false; // true = any range erased from rList
1037 ListOfScRange::iterator aInnerIt = rList.begin();
1038 while( aInnerIt != rList.end() )
1040 bool bInnerErased = false; // true = aInnerIt erased from rList
1041 // do not compare a range with itself
1042 if( (aOuterIt != aInnerIt) && lclTryJoin( *aOuterIt, *aInnerIt ) )
1044 // aOuterIt points to joined range, aInnerIt will be removed
1045 aInnerIt = rList.erase( aInnerIt );
1046 bInnerErased = bAnyErased = true;
1048 /* If aInnerIt has been erased from rList, it already points to
1049 the next element (return value of list::erase()). */
1050 if( !bInnerErased )
1051 ++aInnerIt;
1053 // if any range has been erased, repeat outer loop with the same range
1054 if( !bAnyErased )
1055 ++aOuterIt;
1059 /** Intersects the passed list with all ranges of a VBA Range object in the passed Any. */
1060 void lclIntersectRanges( ListOfScRange& rList, const uno::Any& rArg )
1061 throw (script::BasicErrorException, uno::RuntimeException)
1063 // extract the ranges from the passed argument, will throw on invalid data
1064 ListOfScRange aList2;
1065 lclAddToListOfScRange( aList2, rArg );
1066 // do nothing, if the passed list is already empty
1067 if( !rList.empty() && !aList2.empty() )
1069 // save original list in a local
1070 ListOfScRange aList1;
1071 aList1.swap( rList );
1072 // join ranges from passed argument
1073 lclJoinRanges( aList2 );
1074 // calculate intersection of the ranges in both lists
1075 for( ListOfScRange::const_iterator aOuterIt = aList1.begin(), aOuterEnd = aList1.end(); aOuterIt != aOuterEnd; ++aOuterIt )
1077 for( ListOfScRange::const_iterator aInnerIt = aList2.begin(), aInnerEnd = aList2.end(); aInnerIt != aInnerEnd; ++aInnerIt )
1079 if( aOuterIt->Intersects( *aInnerIt ) )
1081 ScRange aIsectRange(
1082 std::max( aOuterIt->aStart.Col(), aInnerIt->aStart.Col() ),
1083 std::max( aOuterIt->aStart.Row(), aInnerIt->aStart.Row() ),
1084 std::max( aOuterIt->aStart.Tab(), aInnerIt->aStart.Tab() ),
1085 std::min( aOuterIt->aEnd.Col(), aInnerIt->aEnd.Col() ),
1086 std::min( aOuterIt->aEnd.Row(), aInnerIt->aEnd.Row() ),
1087 std::min( aOuterIt->aEnd.Tab(), aInnerIt->aEnd.Tab() ) );
1088 rList.push_back( aIsectRange );
1092 // again, join the result ranges
1093 lclJoinRanges( rList );
1097 /** Creates a VBA Range object from the passed list of ranges. */
1098 uno::Reference< excel::XRange > lclCreateVbaRange(
1099 const uno::Reference< uno::XComponentContext >& rxContext,
1100 const uno::Reference< frame::XModel >& rxModel,
1101 const ListOfScRange& rList ) throw (uno::RuntimeException)
1103 ScDocShell* pDocShell = excel::getDocShell( rxModel );
1104 if( !pDocShell ) throw uno::RuntimeException();
1106 ScRangeList aCellRanges;
1107 for( ListOfScRange::const_iterator aIt = rList.begin(), aEnd = rList.end(); aIt != aEnd; ++aIt )
1108 aCellRanges.Append( *aIt );
1110 if( aCellRanges.size() == 1 )
1112 uno::Reference< table::XCellRange > xRange( new ScCellRangeObj( pDocShell, *aCellRanges.front() ) );
1113 return new ScVbaRange( excel::getUnoSheetModuleObj( xRange ), rxContext, xRange );
1115 if( aCellRanges.size() > 1 )
1117 uno::Reference< sheet::XSheetCellRangeContainer > xRanges( new ScCellRangesObj( pDocShell, aCellRanges ) );
1118 return new ScVbaRange( excel::getUnoSheetModuleObj( xRanges ), rxContext, xRanges );
1120 return 0;
1123 } // namespace
1125 // ----------------------------------------------------------------------------
1127 uno::Reference< excel::XRange > SAL_CALL ScVbaApplication::Intersect(
1128 const uno::Reference< excel::XRange >& rArg1, const uno::Reference< excel::XRange >& rArg2,
1129 const uno::Any& rArg3, const uno::Any& rArg4, const uno::Any& rArg5, const uno::Any& rArg6,
1130 const uno::Any& rArg7, const uno::Any& rArg8, const uno::Any& rArg9, const uno::Any& rArg10,
1131 const uno::Any& rArg11, const uno::Any& rArg12, const uno::Any& rArg13, const uno::Any& rArg14,
1132 const uno::Any& rArg15, const uno::Any& rArg16, const uno::Any& rArg17, const uno::Any& rArg18,
1133 const uno::Any& rArg19, const uno::Any& rArg20, const uno::Any& rArg21, const uno::Any& rArg22,
1134 const uno::Any& rArg23, const uno::Any& rArg24, const uno::Any& rArg25, const uno::Any& rArg26,
1135 const uno::Any& rArg27, const uno::Any& rArg28, const uno::Any& rArg29, const uno::Any& rArg30 )
1136 throw (script::BasicErrorException, uno::RuntimeException)
1138 if( !rArg1.is() || !rArg2.is() )
1139 DebugHelper::exception( SbERR_BAD_PARAMETER, OUString() );
1141 // initialize the result list with 1st parameter, join its ranges together
1142 ListOfScRange aList;
1143 lclAddToListOfScRange( aList, uno::Any( rArg1 ) );
1144 lclJoinRanges( aList );
1146 // process all other parameters, this updates the list with intersection
1147 lclIntersectRanges( aList, uno::Any( rArg2 ) );
1148 lclIntersectRanges( aList, rArg3 );
1149 lclIntersectRanges( aList, rArg4 );
1150 lclIntersectRanges( aList, rArg5 );
1151 lclIntersectRanges( aList, rArg6 );
1152 lclIntersectRanges( aList, rArg7 );
1153 lclIntersectRanges( aList, rArg8 );
1154 lclIntersectRanges( aList, rArg9 );
1155 lclIntersectRanges( aList, rArg10 );
1156 lclIntersectRanges( aList, rArg11 );
1157 lclIntersectRanges( aList, rArg12 );
1158 lclIntersectRanges( aList, rArg13 );
1159 lclIntersectRanges( aList, rArg14 );
1160 lclIntersectRanges( aList, rArg15 );
1161 lclIntersectRanges( aList, rArg16 );
1162 lclIntersectRanges( aList, rArg17 );
1163 lclIntersectRanges( aList, rArg18 );
1164 lclIntersectRanges( aList, rArg19 );
1165 lclIntersectRanges( aList, rArg20 );
1166 lclIntersectRanges( aList, rArg21 );
1167 lclIntersectRanges( aList, rArg22 );
1168 lclIntersectRanges( aList, rArg23 );
1169 lclIntersectRanges( aList, rArg24 );
1170 lclIntersectRanges( aList, rArg25 );
1171 lclIntersectRanges( aList, rArg26 );
1172 lclIntersectRanges( aList, rArg27 );
1173 lclIntersectRanges( aList, rArg28 );
1174 lclIntersectRanges( aList, rArg29 );
1175 lclIntersectRanges( aList, rArg30 );
1177 // create the VBA Range object
1178 return lclCreateVbaRange( mxContext, getCurrentDocument(), aList );
1181 uno::Reference< excel::XRange > SAL_CALL ScVbaApplication::Union(
1182 const uno::Reference< excel::XRange >& rArg1, const uno::Reference< excel::XRange >& rArg2,
1183 const uno::Any& rArg3, const uno::Any& rArg4, const uno::Any& rArg5, const uno::Any& rArg6,
1184 const uno::Any& rArg7, const uno::Any& rArg8, const uno::Any& rArg9, const uno::Any& rArg10,
1185 const uno::Any& rArg11, const uno::Any& rArg12, const uno::Any& rArg13, const uno::Any& rArg14,
1186 const uno::Any& rArg15, const uno::Any& rArg16, const uno::Any& rArg17, const uno::Any& rArg18,
1187 const uno::Any& rArg19, const uno::Any& rArg20, const uno::Any& rArg21, const uno::Any& rArg22,
1188 const uno::Any& rArg23, const uno::Any& rArg24, const uno::Any& rArg25, const uno::Any& rArg26,
1189 const uno::Any& rArg27, const uno::Any& rArg28, const uno::Any& rArg29, const uno::Any& rArg30 )
1190 throw (script::BasicErrorException, uno::RuntimeException)
1192 if( !rArg1.is() || !rArg2.is() )
1193 DebugHelper::exception( SbERR_BAD_PARAMETER, OUString() );
1195 ListOfScRange aList;
1196 lclAddToListOfScRange( aList, uno::Any( rArg1 ) );
1197 lclAddToListOfScRange( aList, uno::Any( rArg2 ) );
1198 lclAddToListOfScRange( aList, rArg3 );
1199 lclAddToListOfScRange( aList, rArg4 );
1200 lclAddToListOfScRange( aList, rArg5 );
1201 lclAddToListOfScRange( aList, rArg6 );
1202 lclAddToListOfScRange( aList, rArg7 );
1203 lclAddToListOfScRange( aList, rArg8 );
1204 lclAddToListOfScRange( aList, rArg9 );
1205 lclAddToListOfScRange( aList, rArg10 );
1206 lclAddToListOfScRange( aList, rArg11 );
1207 lclAddToListOfScRange( aList, rArg12 );
1208 lclAddToListOfScRange( aList, rArg13 );
1209 lclAddToListOfScRange( aList, rArg14 );
1210 lclAddToListOfScRange( aList, rArg15 );
1211 lclAddToListOfScRange( aList, rArg16 );
1212 lclAddToListOfScRange( aList, rArg17 );
1213 lclAddToListOfScRange( aList, rArg18 );
1214 lclAddToListOfScRange( aList, rArg19 );
1215 lclAddToListOfScRange( aList, rArg20 );
1216 lclAddToListOfScRange( aList, rArg21 );
1217 lclAddToListOfScRange( aList, rArg22 );
1218 lclAddToListOfScRange( aList, rArg23 );
1219 lclAddToListOfScRange( aList, rArg24 );
1220 lclAddToListOfScRange( aList, rArg25 );
1221 lclAddToListOfScRange( aList, rArg26 );
1222 lclAddToListOfScRange( aList, rArg27 );
1223 lclAddToListOfScRange( aList, rArg28 );
1224 lclAddToListOfScRange( aList, rArg29 );
1225 lclAddToListOfScRange( aList, rArg30 );
1227 // simply join together all ranges as much as possible, strip out covered ranges etc.
1228 lclJoinRanges( aList );
1230 // create the VBA Range object
1231 return lclCreateVbaRange( mxContext, getCurrentDocument(), aList );
1234 double
1235 ScVbaApplication::InchesToPoints( double Inches ) throw (uno::RuntimeException )
1237 double result = ( Inches * 72.0 );
1238 return result;
1241 void
1242 ScVbaApplication::Volatile( const uno::Any& aVolatile ) throw ( uno::RuntimeException )
1244 sal_Bool bVolatile = sal_True;
1245 aVolatile >>= bVolatile;
1246 SbMethod* pMeth = StarBASIC::GetActiveMethod();
1247 if ( pMeth )
1249 OSL_TRACE("ScVbaApplication::Volatile() In method ->%s<-", OUStringToOString( pMeth->GetName(), RTL_TEXTENCODING_UTF8 ).getStr() );
1250 uno::Reference< frame::XModel > xModel( getCurrentDocument() );
1251 ScDocument* pDoc = excel::getDocShell( xModel )->GetDocument();
1252 pDoc->GetMacroManager()->SetUserFuncVolatile( pMeth->GetName(), bVolatile);
1255 // this is bound to break when loading the document
1256 return;
1259 ::sal_Bool SAL_CALL
1260 ScVbaApplication::getDisplayFormulaBar() throw ( css::uno::RuntimeException )
1262 sal_Bool bRes = false;
1263 ScTabViewShell* pViewShell = excel::getCurrentBestViewShell( mxContext );
1264 if ( pViewShell )
1266 SfxBoolItem sfxFormBar( FID_TOGGLEINPUTLINE);
1267 SfxAllItemSet reqList( SFX_APP()->GetPool() );
1268 reqList.Put( sfxFormBar );
1270 pViewShell->GetState( reqList );
1271 const SfxPoolItem *pItem=0;
1272 if ( reqList.GetItemState( FID_TOGGLEINPUTLINE, false, &pItem ) == SFX_ITEM_SET )
1273 bRes = ((SfxBoolItem*)pItem)->GetValue();
1275 return bRes;
1278 void SAL_CALL
1279 ScVbaApplication::setDisplayFormulaBar( ::sal_Bool _displayformulabar ) throw ( css::uno::RuntimeException )
1281 ScTabViewShell* pViewShell = excel::getCurrentBestViewShell( mxContext );
1282 if ( pViewShell && ( _displayformulabar != getDisplayFormulaBar() ) )
1284 SfxBoolItem sfxFormBar( FID_TOGGLEINPUTLINE, _displayformulabar);
1285 SfxAllItemSet reqList( SFX_APP()->GetPool() );
1286 SfxRequest aReq( FID_TOGGLEINPUTLINE, 0, reqList );
1287 pViewShell->Execute( aReq );
1291 uno::Any SAL_CALL
1292 ScVbaApplication::Caller( const uno::Any& /*aIndex*/ ) throw ( uno::RuntimeException )
1294 StarBASIC* pBasic = SFX_APP()->GetBasic();
1295 SbMethod* pMeth = (SbMethod*)pBasic->GetRtl()->Find( OUString("FuncCaller"), SbxCLASS_METHOD );
1296 uno::Any aRet;
1297 if ( pMeth )
1299 SbxVariableRef refTemp = pMeth;
1300 // forces a broadcast
1301 SbxVariableRef pNew = new SbxMethod( *((SbxMethod*)pMeth));
1302 OSL_TRACE("pNew has type %d and string value %s", pNew->GetType(), OUStringToOString( pNew->GetOUString(), RTL_TEXTENCODING_UTF8 ).getStr() );
1303 aRet = sbxToUnoValue( pNew );
1305 return aRet;
1308 uno::Any SAL_CALL ScVbaApplication::GetOpenFilename(
1309 const uno::Any& rFileFilter, const uno::Any& rFilterIndex, const uno::Any& rTitle,
1310 const uno::Any& rButtonText, const uno::Any& rMultiSelect ) throw (uno::RuntimeException)
1312 uno::Sequence< uno::Any > aArgs( 6 );
1313 aArgs[ 0 ] <<= getThisExcelDoc( mxContext );
1314 aArgs[ 1 ] = rFileFilter;
1315 aArgs[ 2 ] = rFilterIndex;
1316 aArgs[ 3 ] = rTitle;
1317 aArgs[ 4 ] = rButtonText;
1318 aArgs[ 5 ] = rMultiSelect;
1319 uno::Reference< lang::XMultiComponentFactory > xFactory( mxContext->getServiceManager(), uno::UNO_SET_THROW );
1320 uno::Reference< XExecutableDialog > xFilePicker( xFactory->createInstanceWithArgumentsAndContext(
1321 OUString( "ooo.vba.OpenFilePicker" ), aArgs, mxContext ), uno::UNO_QUERY_THROW );
1322 return xFilePicker->execute();
1325 uno::Any SAL_CALL ScVbaApplication::GetSaveAsFilename(
1326 const uno::Any& rInitialFileName, const uno::Any& rFileFilter, const uno::Any& rFilterIndex,
1327 const uno::Any& rTitle, const uno::Any& rButtonText ) throw (uno::RuntimeException)
1329 uno::Sequence< uno::Any > aArgs( 6 );
1330 aArgs[ 0 ] <<= getThisExcelDoc( mxContext );
1331 aArgs[ 1 ] = rInitialFileName;
1332 aArgs[ 2 ] = rFileFilter;
1333 aArgs[ 3 ] = rFilterIndex;
1334 aArgs[ 4 ] = rTitle;
1335 aArgs[ 5 ] = rButtonText;
1336 uno::Reference< lang::XMultiComponentFactory > xFactory( mxContext->getServiceManager(), uno::UNO_SET_THROW );
1337 uno::Reference< XExecutableDialog > xFilePicker( xFactory->createInstanceWithArgumentsAndContext(
1338 OUString( "ooo.vba.SaveAsFilePicker" ), aArgs, mxContext ), uno::UNO_QUERY_THROW );
1339 return xFilePicker->execute();
1342 uno::Reference< frame::XModel >
1343 ScVbaApplication::getCurrentDocument() throw (css::uno::RuntimeException)
1345 return getCurrentExcelDoc(mxContext);
1348 uno::Any SAL_CALL
1349 ScVbaApplication::MenuBars( const uno::Any& aIndex ) throw (uno::RuntimeException)
1351 uno::Reference< XCommandBars > xCommandBars( CommandBars( uno::Any() ), uno::UNO_QUERY_THROW );
1352 uno::Reference< XCollection > xMenuBars( new ScVbaMenuBars( this, mxContext, xCommandBars ) );
1353 if ( aIndex.hasValue() )
1355 return uno::Any ( xMenuBars->Item( aIndex, uno::Any() ) );
1358 return uno::Any( xMenuBars );
1361 void SAL_CALL ScVbaApplication::OnKey( const OUString& Key, const uno::Any& Procedure ) throw (uno::RuntimeException)
1365 // Perhaps we can catch some excel specific
1366 // related behaviour here
1367 VbaApplicationBase::OnKey( Key, Procedure );
1369 catch( container::NoSuchElementException& )
1371 // #TODO special handling for unhandled
1372 // bindings
1376 void SAL_CALL ScVbaApplication::Undo() throw (uno::RuntimeException)
1378 uno::Reference< frame::XModel > xModel( getThisExcelDoc( mxContext ), uno::UNO_SET_THROW );
1380 ScTabViewShell* pViewShell = excel::getBestViewShell( xModel );
1381 if ( pViewShell )
1382 dispatchExecute( pViewShell, SID_UNDO );
1385 OUString
1386 ScVbaApplication::getServiceImplName()
1388 return OUString("ScVbaApplication");
1391 uno::Sequence< OUString >
1392 ScVbaApplication::getServiceNames()
1394 static uno::Sequence< OUString > aServiceNames;
1395 if ( aServiceNames.getLength() == 0 )
1397 aServiceNames.realloc( 1 );
1398 aServiceNames[ 0 ] = OUString("ooo.vba.excel.Application" );
1400 return aServiceNames;
1403 namespace application
1405 namespace sdecl = comphelper::service_decl;
1406 sdecl::vba_service_class_<ScVbaApplication, sdecl::with_args<false> > serviceImpl;
1407 extern sdecl::ServiceDecl const serviceDecl(
1408 serviceImpl,
1409 "ScVbaApplication",
1410 "ooo.vba.excel.Application" );
1413 /* vim:set shiftwidth=4 softtabstop=4 expandtab: */