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