xref: /aoo41x/main/sc/source/ui/vba/vbawindow.cxx (revision cdf0e10c)
1 /*************************************************************************
2  *
3  * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
4  *
5  * Copyright 2000, 2010 Oracle and/or its affiliates.
6  *
7  * OpenOffice.org - a multi-platform office productivity suite
8  *
9  * This file is part of OpenOffice.org.
10  *
11  * OpenOffice.org is free software: you can redistribute it and/or modify
12  * it under the terms of the GNU Lesser General Public License version 3
13  * only, as published by the Free Software Foundation.
14  *
15  * OpenOffice.org is distributed in the hope that it will be useful,
16  * but WITHOUT ANY WARRANTY; without even the implied warranty of
17  * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
18  * GNU Lesser General Public License version 3 for more details
19  * (a copy is included in the LICENSE file that accompanied this code).
20  *
21  * You should have received a copy of the GNU Lesser General Public License
22  * version 3 along with OpenOffice.org.  If not, see
23  * <http://www.openoffice.org/license.html>
24  * for a copy of the LGPLv3 License.
25  *
26  ************************************************************************/
27 #include <vbahelper/helperdecl.hxx>
28 #include "vbawindow.hxx"
29 #include "vbaworksheets.hxx"
30 #include "vbaworksheet.hxx"
31 #include "vbaglobals.hxx"
32 #include "vbapane.hxx"
33 #include <com/sun/star/sheet/XSpreadsheetDocument.hpp>
34 #include <com/sun/star/sheet/XSpreadsheet.hpp>
35 #include <com/sun/star/container/XNamed.hpp>
36 #include <com/sun/star/view/DocumentZoomType.hpp>
37 #include <com/sun/star/table/CellRangeAddress.hpp>
38 #include <ooo/vba/excel/XlWindowState.hpp>
39 #include <ooo/vba/excel/XlWindowView.hpp>
40 #include <ooo/vba/excel/Constants.hpp>
41 #include <com/sun/star/awt/XWindow.hpp>
42 #include <com/sun/star/awt/XWindow2.hpp>
43 #include <com/sun/star/awt/PosSize.hpp>
44 
45 #include <docsh.hxx>
46 #include <tabvwsh.hxx>
47 #include <docuno.hxx>
48 #include <sc.hrc>
49 #include <hash_map>
50 #include <sfx2/viewfrm.hxx>
51 #include <vcl/wrkwin.hxx>
52 #include "unonames.hxx"
53 
54 using namespace ::com::sun::star;
55 using namespace ::ooo::vba;
56 using namespace ::ooo::vba::excel::XlWindowState;
57 
58 typedef  std::hash_map< rtl::OUString,
59 SCTAB, ::rtl::OUStringHash,
60 ::std::equal_to< ::rtl::OUString > > NameIndexHash;
61 
62 typedef std::vector< uno::Reference< sheet::XSpreadsheet > > Sheets;
63 
64 typedef ::cppu::WeakImplHelper1< container::XEnumeration > Enumeration_BASE;
65 
66 typedef ::cppu::WeakImplHelper3< container::XEnumerationAccess
67 	, com::sun::star::container::XIndexAccess
68 	, com::sun::star::container::XNameAccess
69 	> SelectedSheets_BASE;
70 
71 
72 class SelectedSheetsEnum : public Enumeration_BASE
73 {
74 public:
75 	uno::Reference< uno::XComponentContext > m_xContext;
76 	Sheets m_sheets;
77 	uno::Reference< frame::XModel > m_xModel;
78 	Sheets::const_iterator m_it;
79 
80 	SelectedSheetsEnum( const uno::Reference< uno::XComponentContext >& xContext, const Sheets& sheets, const uno::Reference< frame::XModel >& xModel ) throw ( uno::RuntimeException ) :  m_xContext( xContext ), m_sheets( sheets ), m_xModel( xModel )
81 	{
82 		m_it = m_sheets.begin();
83 	}
84 	// XEnumeration
85 	virtual ::sal_Bool SAL_CALL hasMoreElements(  ) throw (uno::RuntimeException)
86 	{
87 		return m_it != m_sheets.end();
88 	}
89 	virtual uno::Any SAL_CALL nextElement(  ) throw (container::NoSuchElementException, lang::WrappedTargetException, uno::RuntimeException)
90 	{
91 		if ( !hasMoreElements() )
92 		{
93 			throw container::NoSuchElementException();
94 		}
95 		// #FIXME needs ThisWorkbook as parent
96 		return uno::makeAny( uno::Reference< excel::XWorksheet > ( new ScVbaWorksheet( uno::Reference< XHelperInterface >(), m_xContext, *(m_it++), m_xModel ) ) );
97 	}
98 
99 
100 };
101 
102 class SelectedSheetsEnumAccess : public SelectedSheets_BASE
103 {
104 	uno::Reference< uno::XComponentContext > m_xContext;
105 	NameIndexHash namesToIndices;
106 	Sheets sheets;
107 	uno::Reference< frame::XModel > m_xModel;
108 public:
109 	SelectedSheetsEnumAccess( const uno::Reference< uno::XComponentContext >& xContext, const uno::Reference< frame::XModel >& xModel ):m_xContext( xContext ), m_xModel( xModel )
110 	{
111 		ScModelObj* pModel = static_cast< ScModelObj* >( m_xModel.get() );
112 		if ( !pModel )
113 			throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "Cannot obtain current document" ) ), uno::Reference< uno::XInterface >() );
114 		ScDocShell* pDocShell = (ScDocShell*)pModel->GetEmbeddedObject();
115 		if ( !pDocShell )
116 			throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "Cannot obtain docshell" ) ), uno::Reference< uno::XInterface >() );
117 		ScTabViewShell* pViewShell = excel::getBestViewShell( m_xModel );
118 		if ( !pViewShell )
119 			throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "Cannot obtain view shell" ) ), uno::Reference< uno::XInterface >() );
120 
121 		SCTAB nTabCount = pDocShell->GetDocument()->GetTableCount();
122 		uno::Sequence<sal_Int32> aSheets( nTabCount );
123 		SCTAB nIndex = 0;
124 		const ScMarkData& rMarkData = pViewShell->GetViewData()->GetMarkData();
125 		sheets.reserve( nTabCount );
126 		uno::Reference <sheet::XSpreadsheetDocument> xSpreadSheet( m_xModel, uno::UNO_QUERY_THROW );
127 		uno::Reference <container::XIndexAccess> xIndex( xSpreadSheet->getSheets(), uno::UNO_QUERY_THROW );
128 		for ( SCTAB nTab=0; nTab<nTabCount; nTab++ )
129 		{
130 			if ( rMarkData.GetTableSelect(nTab) )
131 			{
132 				uno::Reference< sheet::XSpreadsheet > xSheet( xIndex->getByIndex( nTab ), uno::UNO_QUERY_THROW );
133 				uno::Reference< container::XNamed > xNamed( xSheet, uno::UNO_QUERY_THROW );
134 				sheets.push_back( xSheet );
135 				namesToIndices[ xNamed->getName() ] = nIndex++;
136 			}
137 		}
138 
139 	}
140 
141 	//XEnumerationAccess
142 	virtual uno::Reference< container::XEnumeration > SAL_CALL createEnumeration(  ) throw (uno::RuntimeException)
143 	{
144 		return new SelectedSheetsEnum( m_xContext, sheets, m_xModel  );
145 	}
146 	// XIndexAccess
147 	virtual ::sal_Int32 SAL_CALL getCount(  ) throw (uno::RuntimeException)
148 	{
149 		return sheets.size();
150 	}
151 	virtual uno::Any SAL_CALL getByIndex( ::sal_Int32 Index ) throw ( lang::IndexOutOfBoundsException, lang::WrappedTargetException, uno::RuntimeException)
152 	{
153 		if ( Index < 0
154 		|| static_cast< Sheets::size_type >( Index ) >= sheets.size() )
155 			throw lang::IndexOutOfBoundsException();
156 
157 		return uno::makeAny( sheets[ Index ] );
158 	}
159 
160 	//XElementAccess
161 	virtual uno::Type SAL_CALL getElementType(  ) throw (uno::RuntimeException)
162 	{
163 		return excel::XWorksheet::static_type(0);
164 	}
165 
166 	virtual ::sal_Bool SAL_CALL hasElements(  ) throw (uno::RuntimeException)
167 	{
168 		return (sheets.size() > 0);
169 	}
170 
171 	//XNameAccess
172 	virtual uno::Any SAL_CALL getByName( const ::rtl::OUString& aName ) throw (container::NoSuchElementException, lang::WrappedTargetException, uno::RuntimeException)
173 	{
174 		NameIndexHash::const_iterator it = namesToIndices.find( aName );
175 		if ( it == namesToIndices.end() )
176 			throw container::NoSuchElementException();
177 		return uno::makeAny( sheets[ it->second ] );
178 
179 	}
180 
181 	virtual uno::Sequence< ::rtl::OUString > SAL_CALL getElementNames(  ) throw (uno::RuntimeException)
182 	{
183 		uno::Sequence< ::rtl::OUString > names( namesToIndices.size() );
184 		::rtl::OUString* pString = names.getArray();
185 		NameIndexHash::const_iterator it = namesToIndices.begin();
186 		NameIndexHash::const_iterator it_end = namesToIndices.end();
187 		for ( ; it != it_end; ++it, ++pString )
188 			*pString = it->first;
189 		return names;
190 	}
191 
192 	virtual ::sal_Bool SAL_CALL hasByName( const ::rtl::OUString& aName ) throw (uno::RuntimeException)
193 	{
194 		NameIndexHash::const_iterator it = namesToIndices.find( aName );
195 		return (it != namesToIndices.end());
196 	}
197 
198 
199 };
200 
201 ScVbaWindow::ScVbaWindow(
202         const uno::Reference< XHelperInterface >& xParent,
203         const uno::Reference< uno::XComponentContext >& xContext,
204         const uno::Reference< frame::XModel >& xModel,
205         const uno::Reference< frame::XController >& xController ) throw (uno::RuntimeException) :
206     WindowImpl_BASE( xParent, xContext, xModel, xController )
207 {
208     init();
209 }
210 
211 ScVbaWindow::ScVbaWindow(
212         const uno::Sequence< uno::Any >& args,
213         const uno::Reference< uno::XComponentContext >& xContext ) throw (uno::RuntimeException) :
214     WindowImpl_BASE( args, xContext )
215 {
216     init();
217 }
218 
219 void
220 ScVbaWindow::init()
221 {
222     /*  This method is called from the constructor, thus the own refcount is
223         still zero. The implementation of ActivePane() uses a UNO reference of
224         this (to set this window as parent of the pane obejct). This requires
225         the own refcount to be non-zero, otherwise this instance will be
226         desctructed immediately! Guard the call to ActivePane() in try/catch to
227         not miss the decrementation of the reference count on exception. */
228     osl_incrementInterlockedCount( &m_refCount );
229     try
230     {
231 	   m_xPane = ActivePane();
232 	}
233     catch( uno::Exception& )
234     {
235     }
236     osl_decrementInterlockedCount( &m_refCount );
237 }
238 
239 uno::Reference< beans::XPropertySet >
240 ScVbaWindow::getControllerProps() throw (uno::RuntimeException)
241 {
242 	return uno::Reference< beans::XPropertySet >( getController(), uno::UNO_QUERY_THROW );
243 }
244 
245 uno::Reference< beans::XPropertySet >
246 ScVbaWindow::getFrameProps() throw (uno::RuntimeException)
247 {
248 	return uno::Reference< beans::XPropertySet >( getController()->getFrame(), uno::UNO_QUERY_THROW );
249 }
250 
251 uno::Reference< awt::XDevice >
252 ScVbaWindow::getDevice() throw (uno::RuntimeException)
253 {
254     return uno::Reference< awt::XDevice >( getWindow(), uno::UNO_QUERY_THROW );
255 }
256 
257 void
258 ScVbaWindow::Scroll( const uno::Any& Down, const uno::Any& Up, const uno::Any& ToRight, const uno::Any& ToLeft, bool bLargeScroll ) throw (uno::RuntimeException)
259 {
260     if( !m_xPane.is() )
261         throw uno::RuntimeException();
262 	if( bLargeScroll )
263 		m_xPane->LargeScroll( Down, Up, ToRight, ToLeft );
264 	else
265 		m_xPane->SmallScroll( Down, Up, ToRight, ToLeft );
266 }
267 
268 void SAL_CALL
269 ScVbaWindow::SmallScroll( const uno::Any& Down, const uno::Any& Up, const uno::Any& ToRight, const uno::Any& ToLeft ) throw (uno::RuntimeException)
270 {
271 	Scroll( Down, Up, ToRight, ToLeft );
272 }
273 
274 void SAL_CALL
275 ScVbaWindow::LargeScroll( const uno::Any& Down, const uno::Any& Up, const uno::Any& ToRight, const uno::Any& ToLeft ) throw (uno::RuntimeException)
276 {
277 	Scroll( Down, Up, ToRight, ToLeft, true );
278 }
279 
280 uno::Any SAL_CALL
281 ScVbaWindow::SelectedSheets( const uno::Any& aIndex ) throw (uno::RuntimeException)
282 {
283 	uno::Reference< container::XEnumerationAccess > xEnumAccess( new SelectedSheetsEnumAccess( mxContext, m_xModel ) );
284 	// #FIXME needs a workbook as a parent
285 	uno::Reference< excel::XWorksheets > xSheets(  new ScVbaWorksheets( uno::Reference< XHelperInterface >(), mxContext, xEnumAccess, m_xModel ) );
286 	if ( aIndex.hasValue() )
287 	{
288 		uno::Reference< XCollection > xColl( xSheets, uno::UNO_QUERY_THROW );
289 		return xColl->Item( aIndex, uno::Any() );
290 	}
291 	return uno::makeAny( xSheets );
292 }
293 
294 void SAL_CALL
295 ScVbaWindow::ScrollWorkbookTabs( const uno::Any& /*Sheets*/, const uno::Any& /*Position*/ ) throw (uno::RuntimeException)
296 {
297 // #TODO #FIXME need some implementation to scroll through the tabs
298 // but where is this done?
299 /*
300 	sal_Int32 nSheets = 0;
301 	sal_Int32 nPosition = 0;
302 	throw uno::RuntimeException( rtl::OUString::createFromAscii("No Implemented" ), uno::Reference< uno::XInterface >() );
303 	sal_Bool bSheets = ( Sheets >>= nSheets );
304 	sal_Bool bPosition = ( Position >>= nPosition );
305 	if ( bSheets || bPosition ) // at least one param specified
306 		if ( bSheets )
307 			;// use sheets
308 		else if ( bPosition )
309 			; //use position
310 */
311 
312 }
313 
314 uno::Any SAL_CALL
315 ScVbaWindow::getCaption() throw (uno::RuntimeException)
316 {
317 	static rtl::OUString sCrud(RTL_CONSTASCII_USTRINGPARAM(" - OpenOffice.org Calc" ) );
318 	static sal_Int32 nCrudLen = sCrud.getLength();
319 
320 	rtl::OUString sTitle;
321 	getFrameProps()->getPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM ( SC_UNONAME_TITLE ) ) ) >>= sTitle;
322 	sal_Int32 nCrudIndex = sTitle.indexOf( sCrud );
323 	// adjust title ( by removing crud )
324 	// sCrud string present
325 	if ( nCrudIndex != -1 )
326 	{
327 		// and ends with sCrud
328 		if ( ( nCrudLen + nCrudIndex ) == sTitle.getLength() )
329 		{
330 			sTitle = sTitle.copy( 0, nCrudIndex );
331 			ScVbaWorkbook workbook( uno::Reference< XHelperInterface >( Application(), uno::UNO_QUERY_THROW ), mxContext, m_xModel );
332 			rtl::OUString sName = workbook.getName();
333 			// rather bizare hack to make sure the name behavior
334 			// is like XL
335 			// if the adjusted title == workbook name, use name
336 			// if the adjusted title != workbook name but ...
337 			// 	name == title + extension ( .csv, ,odt, .xls )
338 			//	etc. then also use the name
339 
340 			if ( !sTitle.equals( sName ) )
341 			{
342 				static rtl::OUString sDot( RTL_CONSTASCII_USTRINGPARAM(".") );
343 				// starts with title
344 				if ( sName.indexOf( sTitle ) == 0 )
345 					// extention starts immediately after
346 					if ( sName.match( sDot, sTitle.getLength() ) )
347 						sTitle = sName;
348 			}
349 		}
350 	}
351 	return uno::makeAny( sTitle );
352 }
353 
354 void SAL_CALL
355 ScVbaWindow::setCaption( const uno::Any& _caption ) throw (uno::RuntimeException)
356 {
357 	getFrameProps()->setPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( SC_UNONAME_TITLE ) ), _caption );
358 }
359 
360 uno::Any SAL_CALL
361 ScVbaWindow::getScrollRow() throw (uno::RuntimeException)
362 {
363     sal_Int32 nValue = 0;
364     // !! TODO !! get view shell from controller
365     ScTabViewShell* pViewShell = excel::getBestViewShell( m_xModel );
366 	if ( pViewShell )
367 	{
368 	    ScSplitPos eWhich = pViewShell->GetViewData()->GetActivePart();
369 	    nValue = pViewShell->GetViewData()->GetPosY(WhichV(eWhich));
370 	}
371 
372     return uno::makeAny( nValue + 1);
373 }
374 
375 void SAL_CALL
376 ScVbaWindow::setScrollRow( const uno::Any& _scrollrow ) throw (uno::RuntimeException)
377 {
378     // !! TODO !! get view shell from controller
379 	ScTabViewShell* pViewShell = excel::getBestViewShell( m_xModel );
380 	if ( pViewShell )
381 	{
382 		sal_Int32 scrollRow = 0;
383 	    _scrollrow >>= scrollRow;
384 	    ScSplitPos eWhich = pViewShell->GetViewData()->GetActivePart();
385 	    sal_Int32 nOldValue = pViewShell->GetViewData()->GetPosY(WhichV(eWhich)) + 1;
386 		pViewShell->ScrollLines(0, scrollRow - nOldValue);
387 	}
388 }
389 
390 uno::Any SAL_CALL
391 ScVbaWindow::getScrollColumn() throw (uno::RuntimeException)
392 {
393     sal_Int32 nValue = 0;
394     // !! TODO !! get view shell from controller
395     ScTabViewShell* pViewShell = excel::getBestViewShell( m_xModel );
396 	if ( pViewShell )
397 	{
398 	    ScSplitPos eWhich = pViewShell->GetViewData()->GetActivePart();
399 	    nValue = pViewShell->GetViewData()->GetPosX(WhichH(eWhich));
400 	}
401 
402     return uno::makeAny( nValue + 1);
403 }
404 
405 void SAL_CALL
406 ScVbaWindow::setScrollColumn( const uno::Any& _scrollcolumn ) throw (uno::RuntimeException)
407 {
408     // !! TODO !! get view shell from controller
409 	ScTabViewShell* pViewShell = excel::getBestViewShell( m_xModel );
410 	if ( pViewShell )
411 	{
412 		sal_Int32 scrollColumn = 0;
413 	    _scrollcolumn >>= scrollColumn;
414 	    ScSplitPos eWhich = pViewShell->GetViewData()->GetActivePart();
415 	    sal_Int32 nOldValue = pViewShell->GetViewData()->GetPosX(WhichH(eWhich)) + 1;
416 		pViewShell->ScrollLines(scrollColumn - nOldValue, 0);
417 	}
418 }
419 
420 uno::Any SAL_CALL
421 ScVbaWindow::getWindowState() throw (uno::RuntimeException)
422 {
423     sal_Int32 nwindowState = xlNormal;
424     // !! TODO !! get view shell from controller
425     ScTabViewShell* pViewShell = excel::getBestViewShell( m_xModel );
426     SfxViewFrame* pViewFrame = pViewShell -> GetViewFrame();
427     WorkWindow* pWork = (WorkWindow*) pViewFrame->GetFrame().GetSystemWindow();
428     if ( pWork )
429     {
430         if ( pWork -> IsMaximized())
431             nwindowState = xlMaximized;
432         else if (pWork -> IsMinimized())
433             nwindowState = xlMinimized;
434     }
435     return uno::makeAny( nwindowState );
436 }
437 
438 void SAL_CALL
439 ScVbaWindow::setWindowState( const uno::Any& _windowstate ) throw (uno::RuntimeException)
440 {
441 	sal_Int32 nwindowState = xlMaximized;
442 	_windowstate >>= nwindowState;
443     // !! TODO !! get view shell from controller
444 	ScTabViewShell* pViewShell = excel::getBestViewShell( m_xModel );
445 	SfxViewFrame* pViewFrame = pViewShell -> GetViewFrame();
446     WorkWindow* pWork = (WorkWindow*) pViewFrame->GetFrame().GetSystemWindow();
447     if ( pWork )
448     {
449         if ( nwindowState == xlMaximized)
450             pWork -> Maximize();
451         else if (nwindowState == xlMinimized)
452             pWork -> Minimize();
453         else if (nwindowState == xlNormal)
454             pWork -> Restore();
455         else
456             throw uno::RuntimeException( rtl::OUString(RTL_CONSTASCII_USTRINGPARAM( "Invalid Parameter" ) ), uno::Reference< uno::XInterface >() );
457     }
458 }
459 
460 void
461 ScVbaWindow::Activate() throw (css::uno::RuntimeException)
462 {
463 	ScVbaWorkbook workbook( uno::Reference< XHelperInterface >( Application(), uno::UNO_QUERY_THROW ), mxContext, m_xModel );
464 
465 	workbook.Activate();
466 }
467 
468 void
469 ScVbaWindow::Close( const uno::Any& SaveChanges, const uno::Any& FileName, const uno::Any& RouteWorkBook ) throw (uno::RuntimeException)
470 {
471 	ScVbaWorkbook workbook( uno::Reference< XHelperInterface >( Application(), uno::UNO_QUERY_THROW ), mxContext, m_xModel );
472 	workbook.Close(SaveChanges, FileName, RouteWorkBook );
473 }
474 
475 uno::Reference< excel::XPane > SAL_CALL
476 ScVbaWindow::ActivePane() throw (script::BasicErrorException, uno::RuntimeException)
477 {
478     uno::Reference< sheet::XViewPane > xViewPane( getController(), uno::UNO_QUERY_THROW );
479 	return new ScVbaPane( this, mxContext, m_xModel, xViewPane );
480 }
481 
482 uno::Reference< excel::XRange > SAL_CALL
483 ScVbaWindow::ActiveCell(  ) throw (script::BasicErrorException, uno::RuntimeException)
484 {
485 	uno::Reference< excel::XApplication > xApplication( Application(), uno::UNO_QUERY_THROW );
486 	return xApplication->getActiveCell();
487 }
488 
489 uno::Any SAL_CALL
490 ScVbaWindow::Selection(  ) throw (script::BasicErrorException, uno::RuntimeException)
491 {
492 	uno::Reference< excel::XApplication > xApplication( Application(), uno::UNO_QUERY_THROW );
493 	return xApplication->getSelection();
494 }
495 
496 uno::Reference< excel::XRange > SAL_CALL
497 ScVbaWindow::RangeSelection() throw (script::BasicErrorException, uno::RuntimeException)
498 {
499     /*  TODO / FIXME: According to documentation, this method returns the range
500         selection even if shapes are selected. */
501     return uno::Reference< excel::XRange >( Selection(), uno::UNO_QUERY_THROW );
502 }
503 
504 ::sal_Bool SAL_CALL
505 ScVbaWindow::getDisplayGridlines() throw (uno::RuntimeException)
506 {
507 	rtl::OUString sName( RTL_CONSTASCII_USTRINGPARAM( SC_UNO_SHOWGRID ) );
508 	sal_Bool bGrid = sal_True;
509 	getControllerProps()->getPropertyValue( sName ) >>= bGrid;
510 	return bGrid;
511 }
512 
513 
514 void SAL_CALL
515 ScVbaWindow::setDisplayGridlines( ::sal_Bool _displaygridlines ) throw (uno::RuntimeException)
516 {
517 	rtl::OUString sName( RTL_CONSTASCII_USTRINGPARAM( SC_UNO_SHOWGRID ) );
518 	getControllerProps()->setPropertyValue( sName, uno::makeAny( _displaygridlines ));
519 }
520 
521 ::sal_Bool SAL_CALL
522 ScVbaWindow::getDisplayHeadings() throw (uno::RuntimeException)
523 {
524 	rtl::OUString sName( RTL_CONSTASCII_USTRINGPARAM( SC_UNO_COLROWHDR ) );
525 	sal_Bool bHeading = sal_True;
526 	getControllerProps()->getPropertyValue( sName ) >>= bHeading;
527 	return bHeading;
528 }
529 
530 void SAL_CALL
531 ScVbaWindow::setDisplayHeadings( ::sal_Bool _bDisplayHeadings ) throw (uno::RuntimeException)
532 {
533 	rtl::OUString sName( RTL_CONSTASCII_USTRINGPARAM( SC_UNO_COLROWHDR ) );
534 	getControllerProps()->setPropertyValue( sName, uno::makeAny( _bDisplayHeadings ));
535 }
536 
537 ::sal_Bool SAL_CALL
538 ScVbaWindow::getDisplayHorizontalScrollBar() throw (uno::RuntimeException)
539 {
540 	rtl::OUString sName( RTL_CONSTASCII_USTRINGPARAM( SC_UNO_HORSCROLL ) );
541 	sal_Bool bHorizontalScrollBar = sal_True;
542 	getControllerProps()->getPropertyValue( sName ) >>= bHorizontalScrollBar;
543 	return bHorizontalScrollBar;
544 }
545 
546 void SAL_CALL
547 ScVbaWindow::setDisplayHorizontalScrollBar( ::sal_Bool _bDisplayHorizontalScrollBar ) throw (uno::RuntimeException)
548 {
549 	rtl::OUString sName( RTL_CONSTASCII_USTRINGPARAM( SC_UNO_HORSCROLL ) );
550 	getControllerProps()->setPropertyValue( sName, uno::makeAny( _bDisplayHorizontalScrollBar ));
551 }
552 
553 ::sal_Bool SAL_CALL
554 ScVbaWindow::getDisplayOutline() throw (uno::RuntimeException)
555 {
556 	rtl::OUString sName( RTL_CONSTASCII_USTRINGPARAM( SC_UNO_OUTLSYMB ) );
557 	sal_Bool bOutline = sal_True;
558 	getControllerProps()->getPropertyValue( sName ) >>= bOutline;
559 	return bOutline;
560 }
561 
562 void SAL_CALL
563 ScVbaWindow::setDisplayOutline( ::sal_Bool _bDisplayOutline ) throw (uno::RuntimeException)
564 {
565 	rtl::OUString sName( RTL_CONSTASCII_USTRINGPARAM( SC_UNO_OUTLSYMB ) );
566 	getControllerProps()->setPropertyValue( sName, uno::makeAny( _bDisplayOutline ));
567 }
568 
569 ::sal_Bool SAL_CALL
570 ScVbaWindow::getDisplayVerticalScrollBar() throw (uno::RuntimeException)
571 {
572 	rtl::OUString sName( RTL_CONSTASCII_USTRINGPARAM( SC_UNO_VERTSCROLL ) );
573 	sal_Bool bVerticalScrollBar = sal_True;
574 	getControllerProps()->getPropertyValue( sName ) >>= bVerticalScrollBar;
575 	return bVerticalScrollBar;
576 }
577 
578 void SAL_CALL
579 ScVbaWindow::setDisplayVerticalScrollBar( ::sal_Bool _bDisplayVerticalScrollBar ) throw (uno::RuntimeException)
580 {
581 	rtl::OUString sName( RTL_CONSTASCII_USTRINGPARAM( SC_UNO_VERTSCROLL ) );
582 	getControllerProps()->setPropertyValue( sName, uno::makeAny( _bDisplayVerticalScrollBar ));
583 }
584 
585 ::sal_Bool SAL_CALL
586 ScVbaWindow::getDisplayWorkbookTabs() throw (uno::RuntimeException)
587 {
588 	rtl::OUString sName( RTL_CONSTASCII_USTRINGPARAM( SC_UNO_SHEETTABS ) );
589 	sal_Bool bWorkbookTabs = sal_True;
590 	getControllerProps()->getPropertyValue( sName ) >>= bWorkbookTabs;
591 	return bWorkbookTabs;
592 }
593 
594 void SAL_CALL
595 ScVbaWindow::setDisplayWorkbookTabs( ::sal_Bool _bDisplayWorkbookTabs ) throw (uno::RuntimeException)
596 {
597 	rtl::OUString sName( RTL_CONSTASCII_USTRINGPARAM( SC_UNO_SHEETTABS ) );
598 	getControllerProps()->setPropertyValue( sName, uno::makeAny( _bDisplayWorkbookTabs ));
599 }
600 
601 ::sal_Bool SAL_CALL
602 ScVbaWindow::getFreezePanes() throw (uno::RuntimeException)
603 {
604     uno::Reference< sheet::XViewFreezable > xViewFreezable( getController(), uno::UNO_QUERY_THROW );
605 	return xViewFreezable->hasFrozenPanes();
606 }
607 
608 void SAL_CALL
609 ScVbaWindow::setFreezePanes( ::sal_Bool /*_bFreezePanes*/ ) throw (uno::RuntimeException)
610 {
611     uno::Reference< sheet::XViewPane > xViewPane( getController(), uno::UNO_QUERY_THROW );
612     uno::Reference< sheet::XViewSplitable > xViewSplitable( xViewPane, uno::UNO_QUERY_THROW );
613     uno::Reference< sheet::XViewFreezable > xViewFreezable( xViewPane, uno::UNO_QUERY_THROW );
614 	if( xViewSplitable->getIsWindowSplit() )
615 	{
616 		// if there is a split we freeze at the split
617 		sal_Int32 nColumn = getSplitColumn();
618 		sal_Int32 nRow = getSplitRow();
619 		xViewFreezable->freezeAtPosition( nColumn, nRow );
620 	}
621 	else
622 	{
623 		// otherwise we freeze in the center of the visible sheet
624 		table::CellRangeAddress aCellRangeAddress = xViewPane->getVisibleRange();
625 		sal_Int32 nColumn = aCellRangeAddress.StartColumn + (( aCellRangeAddress.EndColumn - aCellRangeAddress.StartColumn )/2 );
626 		sal_Int32 nRow = aCellRangeAddress.StartRow + (( aCellRangeAddress.EndRow - aCellRangeAddress.StartRow )/2 );
627 		xViewFreezable->freezeAtPosition( nColumn, nRow );
628 	}
629 }
630 
631 ::sal_Bool SAL_CALL
632 ScVbaWindow::getSplit() throw (uno::RuntimeException)
633 {
634     uno::Reference< sheet::XViewSplitable > xViewSplitable( getController(), uno::UNO_QUERY_THROW );
635 	return xViewSplitable->getIsWindowSplit();
636 }
637 
638 void SAL_CALL
639 ScVbaWindow::setSplit( ::sal_Bool _bSplit ) throw (uno::RuntimeException)
640 {
641 	if( !_bSplit )
642 	{
643         uno::Reference< sheet::XViewSplitable > xViewSplitable( getController(), uno::UNO_QUERY_THROW );
644 		xViewSplitable->splitAtPosition(0,0);
645 	}
646 	else
647 	{
648         uno::Reference< sheet::XViewFreezable > xViewFreezable( getController(), uno::UNO_QUERY_THROW );
649 		uno::Reference< excel::XRange > xRange = ActiveCell();
650 		sal_Int32 nRow = xRange->getRow();
651 		sal_Int32 nColumn = xRange->getColumn();
652 		xViewFreezable->freezeAtPosition( nColumn-1, nRow-1 );
653 		SplitAtDefinedPosition( sal_True );
654 	}
655 }
656 
657 sal_Int32 SAL_CALL
658 ScVbaWindow::getSplitColumn() throw (uno::RuntimeException)
659 {
660     uno::Reference< sheet::XViewSplitable > xViewSplitable( getController(), uno::UNO_QUERY_THROW );
661 	return xViewSplitable->getSplitColumn();
662 }
663 
664 void SAL_CALL
665 ScVbaWindow::setSplitColumn( sal_Int32 _splitcolumn ) throw (uno::RuntimeException)
666 {
667 	if( getSplitColumn() != _splitcolumn )
668 	{
669         uno::Reference< sheet::XViewFreezable > xViewFreezable( getController(), uno::UNO_QUERY_THROW );
670 		sal_Bool bFrozen = getFreezePanes();
671 		sal_Int32 nRow = getSplitRow();
672 		xViewFreezable->freezeAtPosition( _splitcolumn, nRow );
673 		SplitAtDefinedPosition( !bFrozen );
674 	}
675 }
676 
677 double SAL_CALL
678 ScVbaWindow::getSplitHorizontal() throw (uno::RuntimeException)
679 {
680     uno::Reference< sheet::XViewSplitable > xViewSplitable( getController(), uno::UNO_QUERY_THROW );
681 	return PixelsToPoints( getDevice(), xViewSplitable->getSplitHorizontal(), sal_True );
682 }
683 
684 void SAL_CALL
685 ScVbaWindow::setSplitHorizontal( double _splithorizontal ) throw (uno::RuntimeException)
686 {
687     uno::Reference< sheet::XViewSplitable > xViewSplitable( getController(), uno::UNO_QUERY_THROW );
688 	double fHoriPixels = PointsToPixels( getDevice(), _splithorizontal, sal_True );
689     xViewSplitable->splitAtPosition( static_cast< sal_Int32 >( fHoriPixels ), 0 );
690 }
691 
692 sal_Int32 SAL_CALL
693 ScVbaWindow::getSplitRow() throw (uno::RuntimeException)
694 {
695     uno::Reference< sheet::XViewSplitable > xViewSplitable( getController(), uno::UNO_QUERY_THROW );
696 	sal_Int32 nValue = xViewSplitable->getSplitRow();
697 	return nValue ? nValue - 1 : nValue;
698 }
699 
700 void SAL_CALL
701 ScVbaWindow::setSplitRow( sal_Int32 _splitrow ) throw (uno::RuntimeException)
702 {
703 	if( getSplitRow() != _splitrow )
704 	{
705         uno::Reference< sheet::XViewFreezable > xViewFreezable( getController(), uno::UNO_QUERY_THROW );
706 		sal_Bool bFrozen = getFreezePanes();
707 		sal_Int32 nColumn = getSplitColumn();
708 		xViewFreezable->freezeAtPosition( nColumn , _splitrow );
709 		SplitAtDefinedPosition( !bFrozen );
710 	}
711 }
712 
713 double SAL_CALL
714 ScVbaWindow::getSplitVertical() throw (uno::RuntimeException)
715 {
716     uno::Reference< sheet::XViewSplitable > xViewSplitable( getController(), uno::UNO_QUERY_THROW );
717 	return PixelsToPoints( getDevice(), xViewSplitable->getSplitVertical(), sal_False );
718 }
719 
720 void SAL_CALL
721 ScVbaWindow::setSplitVertical(double _splitvertical ) throw (uno::RuntimeException)
722 {
723     uno::Reference< sheet::XViewSplitable > xViewSplitable( getController(), uno::UNO_QUERY_THROW );
724 	double fVertiPixels = PointsToPixels( getDevice(), _splitvertical, sal_False );
725 	xViewSplitable->splitAtPosition( 0, static_cast<sal_Int32>( fVertiPixels ) );
726 }
727 
728 void ScVbaWindow::SplitAtDefinedPosition(sal_Bool _bUnFreezePane)
729 {
730     uno::Reference< sheet::XViewSplitable > xViewSplitable( getController(), uno::UNO_QUERY_THROW );
731     uno::Reference< sheet::XViewFreezable > xViewFreezable( xViewSplitable, uno::UNO_QUERY_THROW );
732 	sal_Int32 nVertSplit = xViewSplitable->getSplitVertical();
733 	sal_Int32 nHoriSplit = xViewSplitable->getSplitHorizontal();
734 	if( _bUnFreezePane )
735 		xViewFreezable->freezeAtPosition(0,0);
736 	xViewSplitable->splitAtPosition(nHoriSplit, nVertSplit);
737 }
738 
739 uno::Any SAL_CALL
740 ScVbaWindow::getZoom() throw (uno::RuntimeException)
741 {
742 	uno::Reference< beans::XPropertySet > xProps = getControllerProps();
743 	rtl::OUString sName( RTL_CONSTASCII_USTRINGPARAM( SC_UNO_ZOOMTYPE ) );
744 	sal_Int16 nZoomType = view::DocumentZoomType::PAGE_WIDTH;
745 	xProps->getPropertyValue( sName ) >>= nZoomType;
746 	if( nZoomType == view::DocumentZoomType::PAGE_WIDTH )
747 	{
748 		return uno::makeAny( sal_True );
749 	}
750 	else if( nZoomType == view::DocumentZoomType::BY_VALUE )
751 	{
752 		sName = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM(SC_UNO_ZOOMVALUE));
753 		sal_Int16 nZoom = 100;
754 		xProps->getPropertyValue( sName ) >>= nZoom;
755 		return uno::makeAny( nZoom );
756 	}
757     return uno::Any();
758 }
759 
760 void SAL_CALL
761 ScVbaWindow::setZoom( const uno::Any& _zoom ) throw (uno::RuntimeException)
762 {
763     sal_Int16 nZoom = 100;
764     _zoom >>= nZoom;
765     uno::Reference <sheet::XSpreadsheetDocument> xSpreadDoc( m_xModel, uno::UNO_QUERY_THROW );
766     uno::Reference< excel::XWorksheet > xActiveSheet = ActiveSheet();
767     SCTAB nTab = 0;
768     if ( !ScVbaWorksheets::nameExists (xSpreadDoc, xActiveSheet->getName(), nTab) )
769         throw uno::RuntimeException();
770     std::vector< SCTAB > vTabs;
771     vTabs.push_back( nTab );
772     excel::implSetZoom( m_xModel, nZoom, vTabs );
773 }
774 
775 uno::Reference< excel::XWorksheet > SAL_CALL
776 ScVbaWindow::ActiveSheet(  ) throw (script::BasicErrorException, uno::RuntimeException)
777 {
778 	uno::Reference< excel::XApplication > xApplication( Application(), uno::UNO_QUERY_THROW );
779 	return xApplication->getActiveSheet();
780 }
781 
782 uno::Any SAL_CALL
783 ScVbaWindow::getView() throw (uno::RuntimeException)
784 {
785 	// not supported now
786 	sal_Int32 nWindowView = excel::XlWindowView::xlNormalView;
787 	return uno::makeAny( nWindowView );
788 }
789 
790 void SAL_CALL
791 ScVbaWindow::setView( const uno::Any& _view) throw (uno::RuntimeException)
792 {
793 	sal_Int32 nWindowView = excel::XlWindowView::xlNormalView;
794 	_view >>= nWindowView;
795 	sal_uInt16 nSlot = FID_NORMALVIEWMODE;
796 	switch ( nWindowView )
797 	{
798 		case excel::XlWindowView::xlNormalView:
799 			nSlot = FID_NORMALVIEWMODE;
800 			break;
801 		case excel::XlWindowView::xlPageBreakPreview:
802 			nSlot = FID_PAGEBREAKMODE;
803 			break;
804 		default:
805 			DebugHelper::exception(SbERR_BAD_PARAMETER, rtl::OUString() );
806 	}
807     // !! TODO !! get view shell from controller
808 	ScTabViewShell* pViewShell = excel::getBestViewShell( m_xModel );
809 	if ( pViewShell )
810 		dispatchExecute( pViewShell, nSlot );
811 }
812 
813 uno::Reference< excel::XRange > SAL_CALL
814 ScVbaWindow::getVisibleRange() throw (uno::RuntimeException)
815 {
816     uno::Reference< container::XIndexAccess > xPanesIA( getController(), uno::UNO_QUERY_THROW );
817     uno::Reference< sheet::XViewPane > xTopLeftPane( xPanesIA->getByIndex( 0 ), uno::UNO_QUERY_THROW );
818     uno::Reference< excel::XPane > xPane( new ScVbaPane( this, mxContext, m_xModel, xTopLeftPane ) );
819     return xPane->getVisibleRange();
820 }
821 
822 sal_Int32 SAL_CALL
823 ScVbaWindow::PointsToScreenPixelsX(sal_Int32 _points) throw (css::script::BasicErrorException, css::uno::RuntimeException)
824 {
825 	sal_Int32 nHundredthsofOneMillimeters = Millimeter::getInHundredthsOfOneMillimeter( _points );
826 	double fConvertFactor = (getDevice()->getInfo().PixelPerMeterX/100000);
827 	return static_cast<sal_Int32>(fConvertFactor * nHundredthsofOneMillimeters );
828 }
829 
830 sal_Int32 SAL_CALL
831 ScVbaWindow::PointsToScreenPixelsY(sal_Int32 _points) throw (css::script::BasicErrorException, css::uno::RuntimeException)
832 {
833 	sal_Int32 nHundredthsofOneMillimeters = Millimeter::getInHundredthsOfOneMillimeter( _points );
834 	double fConvertFactor = (getDevice()->getInfo().PixelPerMeterY/100000);
835 	return static_cast<sal_Int32>(fConvertFactor * nHundredthsofOneMillimeters );
836 }
837 
838 void SAL_CALL
839 ScVbaWindow::PrintOut( const css::uno::Any& From, const css::uno::Any&To, const css::uno::Any& Copies, const css::uno::Any& Preview, const css::uno::Any& ActivePrinter, const css::uno::Any& PrintToFile, const css::uno::Any& Collate, const css::uno::Any& PrToFileName ) throw (css::script::BasicErrorException, css::uno::RuntimeException)
840 {
841 	// need test, print current active sheet
842     // !! TODO !! get view shell from controller
843 	PrintOutHelper( excel::getBestViewShell( m_xModel ), From, To, Copies, Preview, ActivePrinter, PrintToFile, Collate, PrToFileName, sal_True );
844 }
845 
846 void SAL_CALL
847 ScVbaWindow::PrintPreview( const css::uno::Any& EnableChanges ) throw (css::script::BasicErrorException, css::uno::RuntimeException)
848 {
849 	// need test, print preview current active sheet
850     // !! TODO !! get view shell from controller
851 	PrintPreviewHelper( EnableChanges, excel::getBestViewShell( m_xModel ) );
852 }
853 
854 rtl::OUString&
855 ScVbaWindow::getServiceImplName()
856 {
857 	static rtl::OUString sImplName( RTL_CONSTASCII_USTRINGPARAM("ScVbaWindow") );
858 	return sImplName;
859 }
860 
861 uno::Sequence< rtl::OUString >
862 ScVbaWindow::getServiceNames()
863 {
864 	static uno::Sequence< rtl::OUString > aServiceNames;
865 	if ( aServiceNames.getLength() == 0 )
866 	{
867 		aServiceNames.realloc( 1 );
868 		aServiceNames[ 0 ] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.excel.Window" ) );
869 	}
870 	return aServiceNames;
871 }
872 namespace window
873 {
874 namespace sdecl = comphelper::service_decl;
875 sdecl::vba_service_class_<ScVbaWindow, sdecl::with_args<true> > serviceImpl;
876 extern sdecl::ServiceDecl const serviceDecl(
877     serviceImpl,
878     "ScVbaWindow",
879     "ooo.vba.excel.Window" );
880 }
881