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