merge the formfield patch from ooo-build
[ooovba.git] / sc / source / ui / vba / vbaapplication.cxx
blob6af5925b3e9fc7e7e447520524fe6d9a99491a4d
1 /*************************************************************************
3 * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
4 *
5 * Copyright 2008 by Sun Microsystems, Inc.
7 * OpenOffice.org - a multi-platform office productivity suite
9 * $RCSfile: vbaapplication.cxx,v $
10 * $Revision: 1.7 $
12 * This file is part of OpenOffice.org.
14 * OpenOffice.org is free software: you can redistribute it and/or modify
15 * it under the terms of the GNU Lesser General Public License version 3
16 * only, as published by the Free Software Foundation.
18 * OpenOffice.org is distributed in the hope that it will be useful,
19 * but WITHOUT ANY WARRANTY; without even the implied warranty of
20 * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
21 * GNU Lesser General Public License version 3 for more details
22 * (a copy is included in the LICENSE file that accompanied this code).
24 * You should have received a copy of the GNU Lesser General Public License
25 * version 3 along with OpenOffice.org. If not, see
26 * <http://www.openoffice.org/license.html>
27 * for a copy of the LGPLv3 License.
29 ************************************************************************/
30 #include <stdio.h>
33 #include<com/sun/star/sheet/XSpreadsheetView.hpp>
34 #include <com/sun/star/sheet/XSpreadsheets.hpp>
35 #include<com/sun/star/view/XSelectionSupplier.hpp>
36 #include <com/sun/star/lang/XServiceInfo.hpp>
37 #include<ooo/vba/excel/XlCalculation.hpp>
38 #include <com/sun/star/sheet/XCellRangeReferrer.hpp>
39 #include <com/sun/star/sheet/XCalculatable.hpp>
40 #include <com/sun/star/frame/XLayoutManager.hpp>
41 #include <com/sun/star/task/XStatusIndicatorSupplier.hpp>
42 #include <com/sun/star/task/XStatusIndicator.hpp>
43 #include <ooo/vba/excel/XlMousePointer.hpp>
44 #include <com/sun/star/sheet/XNamedRanges.hpp>
45 #include <com/sun/star/sheet/XCellRangeAddressable.hpp>
46 #include<ooo/vba/XCommandBars.hpp>
48 #include "vbaapplication.hxx"
49 #include "vbaworkbooks.hxx"
50 #include "vbaworkbook.hxx"
51 #include "vbaworksheets.hxx"
52 #include "vbarange.hxx"
53 #include "vbawsfunction.hxx"
54 #include "vbadialogs.hxx"
55 #include "vbawindow.hxx"
56 #include "vbawindows.hxx"
57 #include "vbaglobals.hxx"
58 #include "vbamenubars.hxx"
59 #include "tabvwsh.hxx"
60 #include "gridwin.hxx"
61 #include "vbanames.hxx"
62 #include <vbahelper/vbashape.hxx>
63 #include "vbatextboxshape.hxx"
64 #include "vbaassistant.hxx"
65 #include "sc.hrc"
66 #include "macromgr.hxx"
68 #include <osl/file.hxx>
70 #include <sfx2/request.hxx>
71 #include <sfx2/objsh.hxx>
72 #include <sfx2/viewfrm.hxx>
73 #include <sfx2/app.hxx>
75 #include <toolkit/awt/vclxwindow.hxx>
76 #include <toolkit/helper/vclunohelper.hxx>
78 #include <tools/diagnose_ex.h>
80 #include <docuno.hxx>
82 #include <basic/sbx.hxx>
83 #include <basic/sbstar.hxx>
84 #include <basic/sbuno.hxx>
85 #include <basic/sbmeth.hxx>
87 #include "convuno.hxx"
88 #include "cellsuno.hxx"
89 #include "miscuno.hxx"
90 #include "unonames.hxx"
91 #include "docsh.hxx"
92 #include <vbahelper/helperdecl.hxx>
93 #include "excelvbahelper.hxx"
95 #include <basic/sbmeth.hxx>
96 #include <basic/sbmod.hxx>
97 #include <basic/sbstar.hxx>
98 #include <basic/sbx.hxx>
99 #include <basic/sbxobj.hxx>
100 #include <basic/sbuno.hxx>
101 using namespace ::ooo::vba;
102 using namespace ::com::sun::star;
103 using ::com::sun::star::uno::Reference;
104 using ::com::sun::star::uno::UNO_QUERY_THROW;
105 using ::com::sun::star::uno::UNO_QUERY;
106 using ::rtl::OUString;
108 // Enable our own join detection for Intersection and Union
109 // should be more efficient than using ScRangeList::Join ( because
110 // we already are testing the same things )
112 #define OWN_JOIN 1
114 // #TODO is this defined somewhere else?
115 #if ( defined UNX ) || ( defined OS2 ) //unix
116 #define FILE_PATH_SEPERATOR "/"
117 #else // windows
118 #define FILE_PATH_SEPERATOR "\\"
119 #endif
121 uno::Any sbxToUnoValue( SbxVariable* pVar );
123 class ActiveWorkbook : public ScVbaWorkbook
125 protected:
126 virtual uno::Reference< frame::XModel > getModel()
128 return getCurrentExcelDoc(mxContext);
130 public:
131 ActiveWorkbook( const uno::Reference< XHelperInterface >& xParent, const uno::Reference< uno::XComponentContext >& xContext) : ScVbaWorkbook( xParent, xContext ){}
134 ScVbaApplication::ScVbaApplication( const uno::Reference<uno::XComponentContext >& xContext ): ScVbaApplication_BASE( xContext ), m_xCalculation( excel::XlCalculation::xlCalculationAutomatic )
138 ScVbaApplication::~ScVbaApplication()
142 SfxObjectShell* ScVbaApplication::GetDocShell( const uno::Reference< frame::XModel >& xModel ) throw (uno::RuntimeException)
144 return static_cast< SfxObjectShell* >( excel::getDocShell( xModel ) );
147 uno::Reference< excel::XWorkbook >
148 ScVbaApplication::getActiveWorkbook() throw (uno::RuntimeException)
150 return new ActiveWorkbook( this, mxContext );
152 uno::Reference< excel::XWorkbook > SAL_CALL
153 ScVbaApplication::getThisWorkbook() throw (uno::RuntimeException)
155 return getActiveWorkbook();
158 uno::Reference< XAssistant > SAL_CALL
159 ScVbaApplication::getAssistant() throw (uno::RuntimeException)
161 return uno::Reference< XAssistant >( new ScVbaAssistant( this, mxContext ) );
164 uno::Any SAL_CALL
165 ScVbaApplication::getSelection() throw (uno::RuntimeException)
167 OSL_TRACE("** ScVbaApplication::getSelection() ** ");
168 uno::Reference< frame::XModel > xModel( getCurrentDocument() );
170 Reference< view::XSelectionSupplier > xSelSupp( xModel->getCurrentController(), UNO_QUERY_THROW );
171 Reference< beans::XPropertySet > xPropSet( xSelSupp, UNO_QUERY_THROW );
172 OUString aPropName = OUString::createFromAscii( SC_UNO_FILTERED_RANGE_SELECTION );
173 uno::Any aOldVal = xPropSet->getPropertyValue( aPropName );
174 uno::Any any;
175 any <<= sal_False;
176 xPropSet->setPropertyValue( aPropName, any );
177 uno::Reference< uno::XInterface > aSelection = ScUnoHelpFunctions::AnyToInterface(
178 xSelSupp->getSelection() );
179 xPropSet->setPropertyValue( aPropName, aOldVal );
181 if (!aSelection.is())
183 throw uno::RuntimeException(
184 rtl::OUString::createFromAscii("failed to obtain current selection"),
185 uno::Reference< uno::XInterface >() );
188 uno::Reference< lang::XServiceInfo > xServiceInfo( aSelection, uno::UNO_QUERY_THROW );
189 rtl::OUString sImplementationName = xServiceInfo->getImplementationName();
191 if( sImplementationName.equalsIgnoreAsciiCaseAscii("com.sun.star.drawing.SvxShapeCollection") )
193 uno::Reference< drawing::XShapes > xShapes( aSelection, uno::UNO_QUERY_THROW );
194 uno::Reference< container::XIndexAccess > xIndexAccess( xShapes, uno::UNO_QUERY_THROW );
195 uno::Reference< drawing::XShape > xShape( xIndexAccess->getByIndex(0), uno::UNO_QUERY_THROW );
196 // if ScVbaShape::getType( xShape ) == office::MsoShapeType::msoAutoShape
197 // and the uno object implements the com.sun.star.drawing.Text service
198 // return a textboxshape object
199 if ( ScVbaShape::getType( xShape ) == office::MsoShapeType::msoAutoShape )
201 uno::Reference< lang::XServiceInfo > xShapeServiceInfo( xShape, uno::UNO_QUERY_THROW );
202 if ( xShapeServiceInfo->supportsService( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "com.sun.star.drawing.Text" ) ) ) )
204 return uno::makeAny( uno::Reference< msforms::XTextBoxShape >(new ScVbaTextBoxShape( mxContext, xShape, xShapes, xModel ) ) );
207 return uno::makeAny( uno::Reference< msforms::XShape >(new ScVbaShape( this, mxContext, xShape, xShapes, xModel, ScVbaShape::getType( xShape ) ) ) );
209 else if( xServiceInfo->supportsService( rtl::OUString::createFromAscii("com.sun.star.sheet.SheetCellRange")) ||
210 xServiceInfo->supportsService( rtl::OUString::createFromAscii("com.sun.star.sheet.SheetCellRanges")))
212 uno::Reference< table::XCellRange > xRange( aSelection, ::uno::UNO_QUERY);
213 if ( !xRange.is() )
215 uno::Reference< sheet::XSheetCellRangeContainer > xRanges( aSelection, ::uno::UNO_QUERY);
216 if ( xRanges.is() )
217 return uno::makeAny( uno::Reference< excel::XRange >( new ScVbaRange( this, mxContext, xRanges ) ) );
220 return uno::makeAny( uno::Reference< excel::XRange >(new ScVbaRange( this, mxContext, xRange ) ) );
222 else
224 throw uno::RuntimeException( sImplementationName + rtl::OUString::createFromAscii(" not surpported"), uno::Reference< uno::XInterface >() );
228 uno::Reference< excel::XRange >
229 ScVbaApplication::getActiveCell() throw (uno::RuntimeException )
231 uno::Reference< sheet::XSpreadsheetView > xView( getCurrentDocument()->getCurrentController(), uno::UNO_QUERY_THROW );
232 uno::Reference< table::XCellRange > xRange( xView->getActiveSheet(), ::uno::UNO_QUERY_THROW);
233 ScTabViewShell* pViewShell = excel::getCurrentBestViewShell(mxContext);
234 if ( !pViewShell )
235 throw uno::RuntimeException( rtl::OUString::createFromAscii("No ViewShell available"), uno::Reference< uno::XInterface >() );
236 ScViewData* pTabView = pViewShell->GetViewData();
237 if ( !pTabView )
238 throw uno::RuntimeException( rtl::OUString::createFromAscii("No ViewData available"), uno::Reference< uno::XInterface >() );
240 sal_Int32 nCursorX = pTabView->GetCurX();
241 sal_Int32 nCursorY = pTabView->GetCurY();
243 return new ScVbaRange( this, mxContext, xRange->getCellRangeByPosition( nCursorX, nCursorY, nCursorX, nCursorY ) );
246 uno::Any SAL_CALL
247 ScVbaApplication::Workbooks( const uno::Any& aIndex ) throw (uno::RuntimeException)
249 uno::Reference< XCollection > xWorkBooks( new ScVbaWorkbooks( this, mxContext ) );
250 if ( aIndex.getValueTypeClass() == uno::TypeClass_VOID )
252 // void then somebody did Workbooks.something in vba
253 return uno::Any( xWorkBooks );
256 return uno::Any ( xWorkBooks->Item( aIndex, uno::Any() ) );
259 uno::Any SAL_CALL
260 ScVbaApplication::Worksheets( const uno::Any& aIndex ) throw (uno::RuntimeException)
262 uno::Reference< excel::XWorkbook > xWorkbook( getActiveWorkbook(), uno::UNO_QUERY );
263 uno::Any result;
264 if ( xWorkbook.is() )
265 result = xWorkbook->Worksheets( aIndex );
267 else
268 // Fixme - check if this is reasonable/desired behavior
269 throw uno::RuntimeException( rtl::OUString::createFromAscii(
270 "No ActiveWorkBook available" ), uno::Reference< uno::XInterface >() );
272 return result;
275 uno::Any SAL_CALL
276 ScVbaApplication::WorksheetFunction( ) throw (::com::sun::star::uno::RuntimeException)
278 return uno::makeAny( uno::Reference< script::XInvocation >( new ScVbaWSFunction( this, mxContext) ) );
281 uno::Any SAL_CALL
282 ScVbaApplication::Evaluate( const ::rtl::OUString& Name ) throw (uno::RuntimeException)
284 // #TODO Evaluate allows other things to be evaluated, e.g. functions
285 // I think ( like SIN(3) etc. ) need to investigate that
286 // named Ranges also? e.g. [MyRange] if so need a list of named ranges
287 uno::Any aVoid;
288 return uno::Any( getActiveWorkbook()->getActiveSheet()->Range( uno::Any( Name ), aVoid ) );
291 uno::Any
292 ScVbaApplication::Dialogs( const uno::Any &aIndex ) throw (uno::RuntimeException)
294 uno::Reference< excel::XDialogs > xDialogs( new ScVbaDialogs( uno::Reference< XHelperInterface >( this ), mxContext, getCurrentDocument() ) );
295 if( !aIndex.hasValue() )
296 return uno::Any( xDialogs );
297 return uno::Any( xDialogs->Item( aIndex ) );
300 uno::Reference< excel::XWindow > SAL_CALL
301 ScVbaApplication::getActiveWindow() throw (uno::RuntimeException)
303 // #FIXME sofar can't determine Parent
304 return new ScVbaWindow( uno::Reference< XHelperInterface >(), mxContext, getCurrentDocument() );
307 uno::Any SAL_CALL
308 ScVbaApplication::getCutCopyMode() throw (uno::RuntimeException)
310 //# FIXME TODO, implementation
311 uno::Any result;
312 result <<= sal_False;
313 return result;
316 void SAL_CALL
317 ScVbaApplication::setCutCopyMode( const uno::Any& /*_cutcopymode*/ ) throw (uno::RuntimeException)
319 //# FIXME TODO, implementation
322 uno::Any SAL_CALL
323 ScVbaApplication::getStatusBar() throw (uno::RuntimeException)
325 return uno::makeAny( !getDisplayStatusBar() );
328 void SAL_CALL
329 ScVbaApplication::setStatusBar( const uno::Any& _statusbar ) throw (uno::RuntimeException)
331 rtl::OUString sText;
332 sal_Bool bDefault = sal_False;
333 uno::Reference< frame::XModel > xModel( getCurrentDocument(), uno::UNO_QUERY_THROW );
334 uno::Reference< task::XStatusIndicatorSupplier > xStatusIndicatorSupplier( xModel->getCurrentController(), uno::UNO_QUERY_THROW );
335 uno::Reference< task::XStatusIndicator > xStatusIndicator( xStatusIndicatorSupplier->getStatusIndicator(), uno::UNO_QUERY_THROW );
336 if( _statusbar >>= sText )
338 setDisplayStatusBar( sal_True );
339 xStatusIndicator->start( sText, 100 );
340 //xStatusIndicator->setText( sText );
342 else if( _statusbar >>= bDefault )
344 if( bDefault == sal_False )
346 xStatusIndicator->end();
347 setDisplayStatusBar( sal_True );
350 else
351 throw uno::RuntimeException( rtl::OUString::createFromAscii( "Invalid prarameter. It should be a string or False" ),
352 uno::Reference< uno::XInterface >() );
355 double SAL_CALL
356 ScVbaApplication::CountA( const uno::Any& arg1 ) throw (uno::RuntimeException)
358 double result = 0;
359 uno::Reference< script::XInvocation > xInvoc( WorksheetFunction(), uno::UNO_QUERY_THROW );
360 if ( xInvoc.is() )
362 static rtl::OUString FunctionName( RTL_CONSTASCII_USTRINGPARAM("CountA" ) );
363 uno::Sequence< uno::Any > Params(1);
364 Params[0] = arg1;
365 uno::Sequence< sal_Int16 > OutParamIndex;
366 uno::Sequence< uno::Any > OutParam;
367 xInvoc->invoke( FunctionName, Params, OutParamIndex, OutParam ) >>= result;
369 return result;
372 ::sal_Int32 SAL_CALL
373 ScVbaApplication::getCalculation() throw (uno::RuntimeException)
375 uno::Reference<sheet::XCalculatable> xCalc(getCurrentDocument(), uno::UNO_QUERY_THROW);
376 if(xCalc->isAutomaticCalculationEnabled())
377 return excel::XlCalculation::xlCalculationAutomatic;
378 else
379 return excel::XlCalculation::xlCalculationManual;
382 void SAL_CALL
383 ScVbaApplication::setCalculation( ::sal_Int32 _calculation ) throw (uno::RuntimeException)
385 uno::Reference< sheet::XCalculatable > xCalc(getCurrentDocument(), uno::UNO_QUERY_THROW);
386 switch(_calculation)
388 case excel::XlCalculation::xlCalculationManual:
389 xCalc->enableAutomaticCalculation(sal_False);
390 break;
391 case excel::XlCalculation::xlCalculationAutomatic:
392 case excel::XlCalculation::xlCalculationSemiautomatic:
393 xCalc->enableAutomaticCalculation(sal_True);
394 break;
398 uno::Any SAL_CALL
399 ScVbaApplication::Windows( const uno::Any& aIndex ) throw (uno::RuntimeException)
401 uno::Reference< excel::XWindows > xWindows( new ScVbaWindows( this, mxContext ) );
402 if ( aIndex.getValueTypeClass() == uno::TypeClass_VOID )
403 return uno::Any( xWindows );
404 return uno::Any( xWindows->Item( aIndex, uno::Any() ) );
406 void SAL_CALL
407 ScVbaApplication::wait( double time ) throw (uno::RuntimeException)
409 StarBASIC* pBasic = SFX_APP()->GetBasic();
410 SFX_APP()->EnterBasicCall();
411 SbxArrayRef aArgs = new SbxArray;
412 SbxVariableRef aRef = new SbxVariable;
413 aRef->PutDouble( time );
414 aArgs->Put( aRef, 1 );
415 SbMethod* pMeth = (SbMethod*)pBasic->GetRtl()->Find( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("WaitUntil") ), SbxCLASS_METHOD );
417 if ( pMeth )
419 pMeth->SetParameters( aArgs );
420 SbxVariableRef refTemp = pMeth;
421 // forces a broadcast
422 SbxVariableRef pNew = new SbxMethod( *((SbxMethod*)pMeth));
424 SFX_APP()->LeaveBasicCall();
428 uno::Any SAL_CALL
429 ScVbaApplication::Range( const uno::Any& Cell1, const uno::Any& Cell2 ) throw (uno::RuntimeException)
431 uno::Reference< excel::XRange > xVbRange = ScVbaRange::ApplicationRange( mxContext, Cell1, Cell2 );
432 return uno::makeAny( xVbRange );
435 uno::Any SAL_CALL
436 ScVbaApplication::Names( const css::uno::Any& aIndex ) throw ( uno::RuntimeException )
438 uno::Reference< frame::XModel > xModel( getCurrentDocument(), uno::UNO_QUERY_THROW );
439 uno::Reference< beans::XPropertySet > xPropertySet( xModel, uno::UNO_QUERY_THROW );
440 uno::Reference< sheet::XNamedRanges > xNamedRanges( xPropertySet->getPropertyValue( rtl::OUString::createFromAscii("NamedRanges")) , uno::UNO_QUERY_THROW );
441 css::uno::Reference< excel::XNames > xNames ( new ScVbaNames( this , mxContext , xNamedRanges , xModel ) );
442 if ( aIndex.getValueTypeClass() == uno::TypeClass_VOID )
444 return uno::Any( xNames );
446 return uno::Any( xNames->Item( aIndex, uno::Any() ) );
450 uno::Reference< excel::XWorksheet > SAL_CALL
451 ScVbaApplication::getActiveSheet() throw (uno::RuntimeException)
453 uno::Reference< excel::XWorksheet > result;
454 uno::Reference< excel::XWorkbook > xWorkbook( getActiveWorkbook(), uno::UNO_QUERY );
455 if ( xWorkbook.is() )
457 uno::Reference< excel::XWorksheet > xWorksheet(
458 xWorkbook->getActiveSheet(), uno::UNO_QUERY );
459 if ( xWorksheet.is() )
461 result = xWorksheet;
465 if ( !result.is() )
467 // Fixme - check if this is reasonable/desired behavior
468 throw uno::RuntimeException( rtl::OUString::createFromAscii(
469 "No activeSheet available" ), uno::Reference< uno::XInterface >() );
471 return result;
475 /*******************************************************************************
476 * In msdn:
477 * Reference Optional Variant. The destination. Can be a Range
478 * object, a string that contains a cell reference in R1C1-style notation,
479 * or a string that contains a Visual Basic procedure name.
480 * Scroll Optional Variant. True to scrol, False to not scroll through
481 * the window. The default is False.
482 * Parser is split to three parts, Range, R1C1 string and procedure name.
483 * by test excel, it seems Scroll no effect. ???
484 *******************************************************************************/
485 void SAL_CALL
486 ScVbaApplication::GoTo( const uno::Any& Reference, const uno::Any& Scroll ) throw (uno::RuntimeException)
488 //test Scroll is a boolean
489 sal_Bool bScroll = sal_False;
490 //R1C1-style string or a string of procedure name.
492 if( Scroll.hasValue() )
494 sal_Bool aScroll = sal_False;
495 if( Scroll >>= aScroll )
497 bScroll = aScroll;
499 else
500 throw uno::RuntimeException( rtl::OUString::createFromAscii( "sencond parameter should be boolean" ),
501 uno::Reference< uno::XInterface >() );
504 rtl::OUString sRangeName;
505 if( Reference >>= sRangeName )
507 uno::Reference< frame::XModel > xModel( getCurrentDocument(), uno::UNO_QUERY_THROW );
508 uno::Reference< sheet::XSpreadsheetView > xSpreadsheet(
509 xModel->getCurrentController(), uno::UNO_QUERY_THROW );
510 uno::Reference< sheet::XSpreadsheet > xDoc = xSpreadsheet->getActiveSheet();
512 ScTabViewShell* pShell = excel::getCurrentBestViewShell( mxContext );
513 ScGridWindow* gridWindow = (ScGridWindow*)pShell->GetWindow();
516 uno::Reference< excel::XRange > xVbaSheetRange = ScVbaRange::getRangeObjectForName( mxContext, sRangeName, excel::getDocShell( xModel ), formula::FormulaGrammar::CONV_XL_R1C1 );
518 if( bScroll )
520 xVbaSheetRange->Select();
521 uno::Reference< excel::XWindow > xWindow = getActiveWindow();
522 ScSplitPos eWhich = pShell->GetViewData()->GetActivePart();
523 sal_Int32 nValueX = pShell->GetViewData()->GetPosX(WhichH(eWhich));
524 sal_Int32 nValueY = pShell->GetViewData()->GetPosY(WhichV(eWhich));
525 xWindow->SmallScroll( uno::makeAny( (sal_Int16)(xVbaSheetRange->getRow() - 1) ),
526 uno::makeAny( (sal_Int16)nValueY ),
527 uno::makeAny( (sal_Int16)(xVbaSheetRange->getColumn() - 1) ),
528 uno::makeAny( (sal_Int16)nValueX ) );
529 gridWindow->GrabFocus();
531 else
533 xVbaSheetRange->Select();
534 gridWindow->GrabFocus();
537 catch( uno::RuntimeException )
539 //maybe this should be a procedure name
540 //TODO for procedure name
541 //browse::XBrowseNodeFactory is a singlton. OUString::createFromAscii( "/singletons/com.sun.star.script.browse.theBrowseNodeFactory")
542 //and the createView( browse::BrowseNodeFactoryViewTypes::MACROSELECTOR ) to get a root browse::XBrowseNode.
543 //for query XInvocation interface.
544 //but how to directly get the XInvocation?
545 throw uno::RuntimeException( rtl::OUString::createFromAscii( "invalid reference for range name, it should be procedure name" ),
546 uno::Reference< uno::XInterface >() );
548 return;
550 uno::Reference< excel::XRange > xRange;
551 if( Reference >>= xRange )
553 uno::Reference< excel::XRange > xVbaRange( Reference, uno::UNO_QUERY );
554 ScTabViewShell* pShell = excel::getCurrentBestViewShell( mxContext );
555 ScGridWindow* gridWindow = (ScGridWindow*)pShell->GetWindow();
556 if ( xVbaRange.is() )
558 //TODO bScroll should be using, In this time, it doesenot have effection
559 if( bScroll )
561 xVbaRange->Select();
562 uno::Reference< excel::XWindow > xWindow = getActiveWindow();
563 ScSplitPos eWhich = pShell->GetViewData()->GetActivePart();
564 sal_Int32 nValueX = pShell->GetViewData()->GetPosX(WhichH(eWhich));
565 sal_Int32 nValueY = pShell->GetViewData()->GetPosY(WhichV(eWhich));
566 xWindow->SmallScroll( uno::makeAny( (sal_Int16)(xVbaRange->getRow() - 1) ),
567 uno::makeAny( (sal_Int16)nValueY ),
568 uno::makeAny( (sal_Int16)(xVbaRange->getColumn() - 1) ),
569 uno::makeAny( (sal_Int16)nValueX ) );
570 gridWindow->GrabFocus();
572 else
574 xVbaRange->Select();
575 gridWindow->GrabFocus();
578 return;
580 throw uno::RuntimeException( rtl::OUString::createFromAscii( "invalid reference or name" ),
581 uno::Reference< uno::XInterface >() );
584 sal_Int32 SAL_CALL
585 ScVbaApplication::getCursor() throw (uno::RuntimeException)
587 sal_Int32 nPointerStyle = getPointerStyle(getCurrentDocument());
589 switch( nPointerStyle )
591 case POINTER_ARROW:
592 return excel::XlMousePointer::xlNorthwestArrow;
593 case POINTER_NULL:
594 return excel::XlMousePointer::xlDefault;
595 case POINTER_WAIT:
596 return excel::XlMousePointer::xlWait;
597 case POINTER_TEXT:
598 return excel::XlMousePointer::xlIBeam;
599 default:
600 return excel::XlMousePointer::xlDefault;
604 void SAL_CALL
605 ScVbaApplication::setCursor( sal_Int32 _cursor ) throw (uno::RuntimeException)
609 uno::Reference< frame::XModel > xModel( getCurrentDocument(), uno::UNO_QUERY_THROW );
610 switch( _cursor )
612 case excel::XlMousePointer::xlNorthwestArrow:
614 const Pointer& rPointer( POINTER_ARROW );
615 setCursorHelper( xModel, rPointer, sal_False );
616 break;
618 case excel::XlMousePointer::xlWait:
619 case excel::XlMousePointer::xlIBeam:
621 const Pointer& rPointer( static_cast< PointerStyle >( _cursor ) );
622 //It will set the edit window, toobar and statusbar's mouse pointer.
623 setCursorHelper( xModel, rPointer, sal_True );
624 break;
626 case excel::XlMousePointer::xlDefault:
628 const Pointer& rPointer( POINTER_NULL );
629 setCursorHelper( xModel, rPointer, sal_False );
630 break;
632 default:
633 throw uno::RuntimeException( rtl::OUString(
634 RTL_CONSTASCII_USTRINGPARAM("Unknown value for Cursor pointer")), uno::Reference< uno::XInterface >() );
635 // TODO: isn't this a flaw in the API? It should be allowed to throw an
636 // IllegalArgumentException, or so
639 catch( const uno::Exception& )
641 DBG_UNHANDLED_EXCEPTION();
645 // #TODO perhaps we should switch the return type depending of the filter
646 // type, e.g. return Calc for Calc and Excel if its an imported doc
647 rtl::OUString SAL_CALL
648 ScVbaApplication::getName() throw (uno::RuntimeException)
650 static rtl::OUString appName( RTL_CONSTASCII_USTRINGPARAM("Microsoft Excel" ) );
651 return appName;
654 // #TODO #FIXME get/setDisplayAlerts are just stub impl
655 void SAL_CALL
656 ScVbaApplication::setDisplayAlerts(sal_Bool /*displayAlerts*/) throw (uno::RuntimeException)
660 sal_Bool SAL_CALL
661 ScVbaApplication::getDisplayAlerts() throw (uno::RuntimeException)
663 return sal_True;
665 void SAL_CALL
666 ScVbaApplication::Calculate() throw( script::BasicErrorException , uno::RuntimeException )
668 uno::Reference< frame::XModel > xModel( getCurrentDocument(), uno::UNO_QUERY_THROW );
669 uno::Reference< sheet::XCalculatable > xCalculatable( getCurrentDocument(), uno::UNO_QUERY_THROW );
670 xCalculatable->calculateAll();
673 uno::Reference< beans::XPropertySet > lcl_getPathSettingsService( const uno::Reference< uno::XComponentContext >& xContext ) throw ( uno::RuntimeException )
675 static uno::Reference< beans::XPropertySet > xPathSettings;
676 if ( !xPathSettings.is() )
678 uno::Reference< lang::XMultiComponentFactory > xSMgr( xContext->getServiceManager(), uno::UNO_QUERY_THROW );
679 xPathSettings.set( xSMgr->createInstanceWithContext(::rtl::OUString::createFromAscii("com.sun.star.util.PathSettings"), xContext), uno::UNO_QUERY_THROW );
681 return xPathSettings;
683 rtl::OUString ScVbaApplication::getOfficePath( const rtl::OUString& _sPathType ) throw ( uno::RuntimeException )
685 rtl::OUString sRetPath;
686 uno::Reference< beans::XPropertySet > xProps = lcl_getPathSettingsService( mxContext );
689 rtl::OUString sUrl;
690 xProps->getPropertyValue( _sPathType ) >>= sUrl;
692 // if its a list of paths then use the last one
693 sal_Int32 nIndex = sUrl.lastIndexOf( ';' ) ;
694 if ( nIndex > 0 )
695 sUrl = sUrl.copy( nIndex + 1 );
696 ::osl::File::getSystemPathFromFileURL( sUrl, sRetPath );
698 catch (uno::Exception&)
700 DebugHelper::exception(SbERR_METHOD_FAILED, rtl::OUString());
702 return sRetPath;
704 void SAL_CALL
705 ScVbaApplication::setDefaultFilePath( const ::rtl::OUString& DefaultFilePath ) throw (script::BasicErrorException, uno::RuntimeException)
707 uno::Reference< beans::XPropertySet > xProps = lcl_getPathSettingsService( mxContext );
708 rtl::OUString aURL;
709 osl::FileBase::getFileURLFromSystemPath( DefaultFilePath, aURL );
710 xProps->setPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("Work")), uno::makeAny( aURL ) );
715 ::rtl::OUString SAL_CALL
716 ScVbaApplication::getDefaultFilePath( ) throw (script::BasicErrorException, uno::RuntimeException)
718 return getOfficePath( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("Work")));
721 ::rtl::OUString SAL_CALL
722 ScVbaApplication::LibraryPath( ) throw (script::BasicErrorException, uno::RuntimeException)
724 return getOfficePath( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("Basic")));
727 ::rtl::OUString SAL_CALL
728 ScVbaApplication::TemplatesPath( ) throw (script::BasicErrorException, uno::RuntimeException)
730 return getOfficePath( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("Template")));
733 ::rtl::OUString SAL_CALL
734 ScVbaApplication::PathSeparator( ) throw (script::BasicErrorException, uno::RuntimeException)
736 static rtl::OUString sPathSep( RTL_CONSTASCII_USTRINGPARAM( FILE_PATH_SEPERATOR ) );
737 return sPathSep;
740 typedef std::list< ScRange > Ranges;
741 typedef std::list< ScRangeList > RangesList;
743 void lcl_addRangesToVec( RangesList& vRanges, const uno::Any& aArg ) throw ( script::BasicErrorException, uno::RuntimeException )
745 ScRangeList theRanges;
746 uno::Reference< excel::XRange > xRange( aArg, uno::UNO_QUERY_THROW );
747 uno::Reference< XCollection > xCol( xRange->Areas( uno::Any() ), uno::UNO_QUERY_THROW );
748 sal_Int32 nCount = xCol->getCount();
749 for( sal_Int32 i = 1; i <= nCount; ++i )
751 uno::Reference< excel::XRange > xAreaRange( xCol->Item( uno::makeAny( sal_Int32(i) ), uno::Any() ), uno::UNO_QUERY_THROW );
752 uno::Reference< sheet::XCellRangeAddressable > xAddressable( xAreaRange->getCellRange(), uno::UNO_QUERY_THROW );
753 table::CellRangeAddress addr = xAddressable->getRangeAddress();
754 ScRange refRange;
755 ScUnoConversion::FillScRange( refRange, addr );
756 theRanges.Append( refRange );
758 vRanges.push_back( theRanges );
761 void lcl_addRangeToVec( Ranges& vRanges, const uno::Any& aArg ) throw ( script::BasicErrorException, uno::RuntimeException )
763 uno::Reference< excel::XRange > xRange( aArg, uno::UNO_QUERY_THROW );
764 uno::Reference< XCollection > xCol( xRange->Areas( uno::Any() ), uno::UNO_QUERY_THROW );
765 sal_Int32 nCount = xCol->getCount();
766 for( sal_Int32 i = 1; i <= nCount; ++i )
768 uno::Reference< excel::XRange > xAreaRange( xCol->Item( uno::makeAny( sal_Int32(i) ), uno::Any() ), uno::UNO_QUERY_THROW );
769 uno::Reference< sheet::XCellRangeAddressable > xAddressable( xAreaRange->getCellRange(), uno::UNO_QUERY_THROW );
770 table::CellRangeAddress addr = xAddressable->getRangeAddress();
771 ScRange refRange;
772 ScUnoConversion::FillScRange( refRange, addr );
773 vRanges.push_back( refRange );
777 bool lcl_canJoin( ScRange& r1, ScRange& r2 )
779 bool bCanJoin = false;
780 SCCOL startEndColDiff = r2.aStart.Col() - r1.aEnd.Col();
781 SCROW startEndRowDiff = r2.aStart.Row() - r1.aEnd.Row();
782 SCCOL startColDiff = r2.aStart.Col() - r1.aStart.Col();
783 SCCOL endColDiff = r2.aEnd.Col() - r1.aEnd.Col();
784 SCROW startRowDiff = r2.aStart.Row() - r1.aStart.Row();
785 SCROW endRowDiff = r2.aEnd.Row() - r1.aEnd.Row();
786 if ( ( startRowDiff == endRowDiff ) && startRowDiff == 0 && startColDiff >=0 && endColDiff > 0 && ( startEndColDiff <= 1 && startEndColDiff >= -r1.aEnd.Col() ) )
787 bCanJoin = true;
788 else if ( ( startColDiff == endColDiff ) && startColDiff == 0 && startRowDiff >= 0 && endRowDiff > 0 && ( startEndRowDiff <= 1 && startEndRowDiff >= -r1.aEnd.Row() ) )
789 bCanJoin = true;
790 #ifdef DEBUG
791 String sr1;
792 String sr2;
793 r1.Format( sr1, SCA_VALID ) ;
794 r2.Format( sr2, SCA_VALID ) ;
795 OSL_TRACE(" canJoin address %s with %s %s ( startRowDiff(%d), endRowDiff(%d), startColDiff(%d) endColDiff(%d) startEndRowDiff(%d), startEndColDiff(%d) ",
796 rtl::OUStringToOString( sr1, RTL_TEXTENCODING_UTF8 ).getStr(),
797 rtl::OUStringToOString( sr2, RTL_TEXTENCODING_UTF8 ).getStr(), bCanJoin ? "true" : "false", startRowDiff, endRowDiff, startColDiff, endColDiff, startEndRowDiff, startEndColDiff );
798 #endif
799 return bCanJoin;
801 // strips out ranges that contain other ranges, also
802 // if the borders of the intersecting ranges are alligned
803 // then the the range is extended to the larger
804 // e.g. Range("A4:D10"), Range("B4:E10") would be combined
805 // to Range("A4:E10")
806 void lcl_strip_containedRanges( Ranges& vRanges )
808 // get rid of ranges that are surrounded by other ranges
809 for( Ranges::iterator it = vRanges.begin(); it != vRanges.end(); ++it )
811 for( Ranges::iterator it_inner = vRanges.begin(); it_inner != vRanges.end(); ++it_inner )
813 if ( it != it_inner )
815 #ifdef DEBUG
816 String r1;
817 String r2;
818 it->Format( r1, SCA_VALID ) ;
819 it_inner->Format( r2, SCA_VALID ) ;
820 OSL_TRACE( "try strip/join address %s with %s ",
821 rtl::OUStringToOString( r1, RTL_TEXTENCODING_UTF8 ).getStr(),
822 rtl::OUStringToOString( r2, RTL_TEXTENCODING_UTF8 ).getStr() );
823 #endif
824 if ( it->In( *it_inner ) )
825 it_inner = vRanges.erase( it_inner );
826 else if ( it_inner->In( *it ) )
827 it = vRanges.erase( it );
828 #ifndef OWN_JOIN
829 else if ( (*it_inner).aStart.Row() == (*it).aStart.Row()
830 && (*it_inner).aEnd.Row() == (*it).aEnd.Row() )
832 it->ExtendTo( *it_inner );
833 it_inner = vRanges.erase( it_inner );
835 #else
836 else if ( lcl_canJoin( *it, *it_inner ) )
838 it->ExtendTo( *it_inner );
839 it_inner = vRanges.erase( it_inner );
841 else if ( lcl_canJoin( *it_inner, *it) )
843 it_inner->ExtendTo( *it );
844 it = vRanges.erase( it );
846 #endif
853 Ranges
854 lcl_intersectionImpl( ScRangeList& rl1, ScRangeList& rl2 )
856 Ranges intersections;
857 for ( USHORT x = 0 ; x < rl1.Count(); ++x )
859 for ( USHORT y = 0 ; y < rl2.Count(); ++y )
861 #ifdef DEBUG
862 String r1;
863 String r2;
864 rl1.GetObject( x )->Format( r1, SCA_VALID ) ;
865 rl2.GetObject( y )->Format( r2, SCA_VALID ) ;
866 OSL_TRACE( "comparing address %s with %s ",
867 rtl::OUStringToOString( r1, RTL_TEXTENCODING_UTF8 ).getStr(),
868 rtl::OUStringToOString( r2, RTL_TEXTENCODING_UTF8 ).getStr() );
869 #endif
870 if( rl1.GetObject( x )->Intersects( *rl2.GetObject( y ) ) )
872 ScRange aIntersection = ScRange( Max( rl1.GetObject( x )->aStart.Col(), rl2.GetObject( y )->aStart.Col() ),
873 Max( rl1.GetObject( x )->aStart.Row(), rl2.GetObject( y )->aStart.Row() ),
874 Max( rl1.GetObject( x )->aStart.Tab(), rl2.GetObject( y )->aStart.Tab() ),
875 Min( rl1.GetObject( x )->aEnd.Col(), rl2.GetObject( y )->aEnd.Col() ),
876 Min( rl1.GetObject( x )->aEnd.Row(), rl2.GetObject( y )->aEnd.Row() ),
877 Min( rl1.GetObject( x )->aEnd.Tab(), rl2.GetObject( y )->aEnd.Tab() ) );
878 intersections.push_back( aIntersection );
882 lcl_strip_containedRanges( intersections );
883 return intersections;
886 // Intersection of a set of ranges ( where each range is represented by a ScRangeList e.g.
887 // any range can be a multi-area range )
888 // An intersection is performed between each range in the set of ranges.
889 // The resulting set of intersections is then processed to strip out any
890 // intersections that contain other intersections ( and also ranges that directly line up
891 // are joined ) ( see lcl_strip_containedRanges )
892 RangesList lcl_intersections( RangesList& vRanges )
894 RangesList intersections;
895 for( RangesList::iterator it = vRanges.begin(); it != vRanges.end(); ++it )
897 Ranges intermediateList;
898 for( RangesList::iterator it_inner = vRanges.begin(); it_inner != vRanges.end(); ++it_inner )
900 if ( it != it_inner )
902 Ranges ranges = lcl_intersectionImpl( *it, *it_inner );
903 for ( Ranges::iterator range_it = ranges.begin(); range_it != ranges.end(); ++range_it )
904 intermediateList.push_back( *range_it );
907 it = vRanges.erase( it ); // remove it so we don't include it in the next pass.
909 ScRangeList argIntersect;
910 lcl_strip_containedRanges( intermediateList );
912 for( Ranges::iterator it_inter = intermediateList.begin(); it_inter != intermediateList.end(); ++it_inter )
913 #ifndef OWN_JOIN
914 argIntersect.Join( *it_inter );
915 #else
916 argIntersect.Append( *it_inter );
917 #endif
919 intersections.push_back( argIntersect );
921 return intersections;
924 uno::Reference< excel::XRange > SAL_CALL
925 ScVbaApplication::Intersect( const uno::Reference< excel::XRange >& Arg1, const uno::Reference< excel::XRange >& Arg2, const uno::Any& Arg3, const uno::Any& Arg4, const uno::Any& Arg5, const uno::Any& Arg6, const uno::Any& Arg7, const uno::Any& Arg8, const uno::Any& Arg9, const uno::Any& Arg10, const uno::Any& Arg11, const uno::Any& Arg12, const uno::Any& Arg13, const uno::Any& Arg14, const uno::Any& Arg15, const uno::Any& Arg16, const uno::Any& Arg17, const uno::Any& Arg18, const uno::Any& Arg19, const uno::Any& Arg20, const uno::Any& Arg21, const uno::Any& Arg22, const uno::Any& Arg23, const uno::Any& Arg24, const uno::Any& Arg25, const uno::Any& Arg26, const uno::Any& Arg27, const uno::Any& Arg28, const uno::Any& Arg29, const uno::Any& Arg30 ) throw (script::BasicErrorException, uno::RuntimeException)
927 if ( !Arg1.is() || !Arg2.is() )
928 DebugHelper::exception(SbERR_BAD_PARAMETER, rtl::OUString() );
930 RangesList vRanges;
931 lcl_addRangesToVec( vRanges, uno::makeAny( Arg1 ) );
932 lcl_addRangesToVec( vRanges, uno::makeAny( Arg2 ) );
934 if ( Arg3.hasValue() )
935 lcl_addRangesToVec( vRanges, Arg3 );
936 if ( Arg4.hasValue() )
937 lcl_addRangesToVec( vRanges, Arg4 );
938 if ( Arg5.hasValue() )
939 lcl_addRangesToVec( vRanges, Arg5 );
940 if ( Arg6.hasValue() )
941 lcl_addRangesToVec( vRanges, Arg6 );
942 if ( Arg7.hasValue() )
943 lcl_addRangesToVec( vRanges, Arg7 );
944 if ( Arg8.hasValue() )
945 lcl_addRangesToVec( vRanges, Arg8 );
946 if ( Arg9.hasValue() )
947 lcl_addRangesToVec( vRanges, Arg9 );
948 if ( Arg10.hasValue() )
949 lcl_addRangesToVec( vRanges, Arg10 );
950 if ( Arg11.hasValue() )
951 lcl_addRangesToVec( vRanges, Arg11 );
952 if ( Arg12.hasValue() )
953 lcl_addRangesToVec( vRanges, Arg12 );
954 if ( Arg13.hasValue() )
955 lcl_addRangesToVec( vRanges, Arg13 );
956 if ( Arg14.hasValue() )
957 lcl_addRangesToVec( vRanges, Arg14 );
958 if ( Arg15.hasValue() )
959 lcl_addRangesToVec( vRanges, Arg15 );
960 if ( Arg16.hasValue() )
961 lcl_addRangesToVec( vRanges, Arg16 );
962 if ( Arg17.hasValue() )
963 lcl_addRangesToVec( vRanges, Arg17 );
964 if ( Arg18.hasValue() )
965 lcl_addRangesToVec( vRanges, Arg18 );
966 if ( Arg19.hasValue() )
967 lcl_addRangesToVec( vRanges, Arg19 );
968 if ( Arg20.hasValue() )
969 lcl_addRangesToVec( vRanges, Arg20 );
970 if ( Arg21.hasValue() )
971 lcl_addRangesToVec( vRanges, Arg21 );
972 if ( Arg22.hasValue() )
973 lcl_addRangesToVec( vRanges, Arg22 );
974 if ( Arg23.hasValue() )
975 lcl_addRangesToVec( vRanges, Arg23 );
976 if ( Arg24.hasValue() )
977 lcl_addRangesToVec( vRanges, Arg24 );
978 if ( Arg25.hasValue() )
979 lcl_addRangesToVec( vRanges, Arg25 );
980 if ( Arg26.hasValue() )
981 lcl_addRangesToVec( vRanges, Arg26 );
982 if ( Arg27.hasValue() )
983 lcl_addRangesToVec( vRanges, Arg27 );
984 if ( Arg28.hasValue() )
985 lcl_addRangesToVec( vRanges, Arg28 );
986 if ( Arg29.hasValue() )
987 lcl_addRangesToVec( vRanges, Arg29 );
988 if ( Arg30.hasValue() )
989 lcl_addRangesToVec( vRanges, Arg30 );
991 uno::Reference< excel::XRange > xRefRange;
993 ScRangeList aCellRanges;
994 // first pass - gets the set of all possible interections of Arg1..ArgN
995 RangesList intersections = lcl_intersections( vRanges );
996 // second pass - gets the intersections of the intersections ( don't ask, but this
997 // is what seems to happen )
998 if ( intersections.size() > 1)
999 intersections = lcl_intersections( intersections );
1000 for( RangesList::iterator it = intersections.begin(); it != intersections.end(); ++it )
1002 for ( USHORT x = 0 ; x < it->Count(); ++x )
1003 #ifndef OWN_JOIN
1004 aCellRanges.Join( *it->GetObject(x) );
1005 #else
1006 aCellRanges.Append( *it->GetObject(x) );
1007 #endif
1010 uno::Reference< frame::XModel > xModel( getCurrentDocument(), uno::UNO_QUERY_THROW );
1011 ScDocShell* pDocShell = excel::getDocShell( xModel );
1012 if ( aCellRanges.Count() == 1 )
1014 xRefRange = new ScVbaRange( uno::Reference< XHelperInterface >(), mxContext, new ScCellRangeObj( pDocShell, *aCellRanges.First() ) );
1016 else if ( aCellRanges.Count() > 1 )
1018 uno::Reference< sheet::XSheetCellRangeContainer > xRanges( new ScCellRangesObj( pDocShell, aCellRanges ) );
1019 xRefRange = new ScVbaRange( uno::Reference< XHelperInterface >(), mxContext, xRanges );
1022 return xRefRange;
1025 uno::Reference< excel::XRange > SAL_CALL
1026 ScVbaApplication::Union( const uno::Reference< excel::XRange >& Arg1, const uno::Reference< excel::XRange >& Arg2, const uno::Any& Arg3, const uno::Any& Arg4, const uno::Any& Arg5, const uno::Any& Arg6, const uno::Any& Arg7, const uno::Any& Arg8, const uno::Any& Arg9, const uno::Any& Arg10, const uno::Any& Arg11, const uno::Any& Arg12, const uno::Any& Arg13, const uno::Any& Arg14, const uno::Any& Arg15, const uno::Any& Arg16, const uno::Any& Arg17, const uno::Any& Arg18, const uno::Any& Arg19, const uno::Any& Arg20, const uno::Any& Arg21, const uno::Any& Arg22, const uno::Any& Arg23, const uno::Any& Arg24, const uno::Any& Arg25, const uno::Any& Arg26, const uno::Any& Arg27, const uno::Any& Arg28, const uno::Any& Arg29, const uno::Any& Arg30 ) throw (script::BasicErrorException, uno::RuntimeException)
1028 if ( !Arg1.is() || !Arg2.is() )
1029 DebugHelper::exception(SbERR_BAD_PARAMETER, rtl::OUString() );
1031 uno::Reference< excel::XRange > xRange;
1032 Ranges vRanges;
1033 lcl_addRangeToVec( vRanges, uno::makeAny( Arg1 ) );
1034 lcl_addRangeToVec( vRanges, uno::makeAny( Arg2 ) );
1036 if ( Arg3.hasValue() )
1037 lcl_addRangeToVec( vRanges, Arg3 );
1038 if ( Arg4.hasValue() )
1039 lcl_addRangeToVec( vRanges, Arg4 );
1040 if ( Arg5.hasValue() )
1041 lcl_addRangeToVec( vRanges, Arg5 );
1042 if ( Arg6.hasValue() )
1043 lcl_addRangeToVec( vRanges, Arg6 );
1044 if ( Arg7.hasValue() )
1045 lcl_addRangeToVec( vRanges, Arg7 );
1046 if ( Arg8.hasValue() )
1047 lcl_addRangeToVec( vRanges, Arg8 );
1048 if ( Arg9.hasValue() )
1049 lcl_addRangeToVec( vRanges, Arg9 );
1050 if ( Arg10.hasValue() )
1051 lcl_addRangeToVec( vRanges, Arg10 );
1052 if ( Arg11.hasValue() )
1053 lcl_addRangeToVec( vRanges, Arg11 );
1054 if ( Arg12.hasValue() )
1055 lcl_addRangeToVec( vRanges, Arg12 );
1056 if ( Arg13.hasValue() )
1057 lcl_addRangeToVec( vRanges, Arg13 );
1058 if ( Arg14.hasValue() )
1059 lcl_addRangeToVec( vRanges, Arg14 );
1060 if ( Arg15.hasValue() )
1061 lcl_addRangeToVec( vRanges, Arg15 );
1062 if ( Arg16.hasValue() )
1063 lcl_addRangeToVec( vRanges, Arg16 );
1064 if ( Arg17.hasValue() )
1065 lcl_addRangeToVec( vRanges, Arg17 );
1066 if ( Arg18.hasValue() )
1067 lcl_addRangeToVec( vRanges, Arg18 );
1068 if ( Arg19.hasValue() )
1069 lcl_addRangeToVec( vRanges, Arg19 );
1070 if ( Arg20.hasValue() )
1071 lcl_addRangeToVec( vRanges, Arg20 );
1072 if ( Arg21.hasValue() )
1073 lcl_addRangeToVec( vRanges, Arg21 );
1074 if ( Arg22.hasValue() )
1075 lcl_addRangeToVec( vRanges, Arg22 );
1076 if ( Arg23.hasValue() )
1077 lcl_addRangeToVec( vRanges, Arg23 );
1078 if ( Arg24.hasValue() )
1079 lcl_addRangeToVec( vRanges, Arg24 );
1080 if ( Arg25.hasValue() )
1081 lcl_addRangeToVec( vRanges, Arg25 );
1082 if ( Arg26.hasValue() )
1083 lcl_addRangeToVec( vRanges, Arg26 );
1084 if ( Arg27.hasValue() )
1085 lcl_addRangeToVec( vRanges, Arg27 );
1086 if ( Arg28.hasValue() )
1087 lcl_addRangeToVec( vRanges, Arg28 );
1088 if ( Arg29.hasValue() )
1089 lcl_addRangeToVec( vRanges, Arg29 );
1090 if ( Arg30.hasValue() )
1091 lcl_addRangeToVec( vRanges, Arg30 );
1093 ScRangeList aCellRanges;
1094 lcl_strip_containedRanges( vRanges );
1096 for( Ranges::iterator it = vRanges.begin(); it != vRanges.end(); ++it )
1097 aCellRanges.Append( *it );
1099 uno::Reference< frame::XModel > xModel( getCurrentDocument(), uno::UNO_QUERY_THROW );
1100 ScDocShell* pDocShell = excel::getDocShell( xModel );
1101 if ( aCellRanges.Count() == 1 )
1103 // normal range
1104 xRange = new ScVbaRange( uno::Reference< XHelperInterface >(), mxContext, new ScCellRangeObj( pDocShell, *aCellRanges.First() ) );
1106 else if ( aCellRanges.Count() > 1 ) // Multi-Area
1108 uno::Reference< sheet::XSheetCellRangeContainer > xRanges( new ScCellRangesObj( pDocShell, aCellRanges ) );
1109 xRange = new ScVbaRange( uno::Reference< XHelperInterface >(), mxContext, xRanges );
1112 // #FIXME need proper (WorkSheet) parent
1113 return xRange;
1116 void
1117 ScVbaApplication::Volatile( const uno::Any& aVolatile ) throw ( uno::RuntimeException )
1119 sal_Bool bVolatile = sal_True;
1120 aVolatile >>= bVolatile;
1121 SbMethod* pMeth = StarBASIC::GetActiveMethod();
1122 if ( pMeth )
1124 OSL_TRACE("ScVbaApplication::Volatile() In method ->%s<-", rtl::OUStringToOString( pMeth->GetName(), RTL_TEXTENCODING_UTF8 ).getStr() );
1125 uno::Reference< frame::XModel > xModel( getCurrentDocument() );
1126 ScDocument* pDoc = excel::getDocShell( xModel )->GetDocument();
1127 pDoc->GetMacroManager()->SetUserFuncVolatile( pMeth->GetName(), bVolatile);
1130 // this is bound to break when loading the document
1131 return;
1134 ::sal_Bool SAL_CALL
1135 ScVbaApplication::getDisplayFormulaBar() throw ( css::uno::RuntimeException )
1137 sal_Bool bRes = sal_False;
1138 ScTabViewShell* pViewShell = excel::getCurrentBestViewShell( mxContext );
1139 if ( pViewShell )
1141 SfxBoolItem sfxFormBar( FID_TOGGLEINPUTLINE);
1142 SfxAllItemSet reqList( SFX_APP()->GetPool() );
1143 reqList.Put( sfxFormBar );
1145 pViewShell->GetState( reqList );
1146 const SfxPoolItem *pItem=0;
1147 if ( reqList.GetItemState( FID_TOGGLEINPUTLINE, sal_False, &pItem ) == SFX_ITEM_SET )
1148 bRes = ((SfxBoolItem*)pItem)->GetValue();
1150 return bRes;
1153 void SAL_CALL
1154 ScVbaApplication::setDisplayFormulaBar( ::sal_Bool _displayformulabar ) throw ( css::uno::RuntimeException )
1156 ScTabViewShell* pViewShell = excel::getCurrentBestViewShell( mxContext );
1157 if ( pViewShell && ( _displayformulabar != getDisplayFormulaBar() ) )
1159 SfxBoolItem sfxFormBar( FID_TOGGLEINPUTLINE, _displayformulabar);
1160 SfxAllItemSet reqList( SFX_APP()->GetPool() );
1161 SfxRequest aReq( FID_TOGGLEINPUTLINE, 0, reqList );
1162 pViewShell->Execute( aReq );
1166 uno::Any SAL_CALL
1167 ScVbaApplication::Caller( const uno::Any& /*aIndex*/ ) throw ( uno::RuntimeException )
1169 StarBASIC* pBasic = SFX_APP()->GetBasic();
1170 SFX_APP()->EnterBasicCall();
1171 SbMethod* pMeth = (SbMethod*)pBasic->GetRtl()->Find( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("FuncCaller") ), SbxCLASS_METHOD );
1172 uno::Any aRet;
1173 if ( pMeth )
1175 SbxVariableRef refTemp = pMeth;
1176 // forces a broadcast
1177 SbxVariableRef pNew = new SbxMethod( *((SbxMethod*)pMeth));
1178 OSL_TRACE("pNew has type %d and string value %s", pNew->GetType(), rtl::OUStringToOString( pNew->GetString(), RTL_TEXTENCODING_UTF8 ).getStr() );
1179 aRet = sbxToUnoValue( pNew );
1181 SFX_APP()->LeaveBasicCall();
1182 return aRet;
1185 uno::Reference< frame::XModel >
1186 ScVbaApplication::getCurrentDocument() throw (css::uno::RuntimeException)
1188 return getCurrentExcelDoc(mxContext);
1191 uno::Any SAL_CALL
1192 ScVbaApplication::MenuBars( const uno::Any& aIndex ) throw (uno::RuntimeException)
1194 uno::Reference< XCommandBars > xCommandBars( CommandBars( uno::Any() ), uno::UNO_QUERY_THROW );
1195 uno::Reference< XCollection > xMenuBars( new ScVbaMenuBars( this, mxContext, xCommandBars ) );
1196 if ( aIndex.hasValue() )
1198 return uno::Any ( xMenuBars->Item( aIndex, uno::Any() ) );
1201 return uno::Any( xMenuBars );
1204 rtl::OUString&
1205 ScVbaApplication::getServiceImplName()
1207 static rtl::OUString sImplName( RTL_CONSTASCII_USTRINGPARAM("ScVbaApplication") );
1208 return sImplName;
1211 uno::Sequence< rtl::OUString >
1212 ScVbaApplication::getServiceNames()
1214 static uno::Sequence< rtl::OUString > aServiceNames;
1215 if ( aServiceNames.getLength() == 0 )
1217 aServiceNames.realloc( 1 );
1218 aServiceNames[ 0 ] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.excel.Application" ) );
1220 return aServiceNames;
1223 namespace application
1225 namespace sdecl = comphelper::service_decl;
1226 sdecl::vba_service_class_<ScVbaApplication, sdecl::with_args<false> > serviceImpl;
1227 extern sdecl::ServiceDecl const serviceDecl(
1228 serviceImpl,
1229 "ScVbaApplication",
1230 "ooo.vba.excel.Application" );