1*b3f79822SAndrew Rist /**************************************************************
2cdf0e10cSrcweir *
3*b3f79822SAndrew Rist * Licensed to the Apache Software Foundation (ASF) under one
4*b3f79822SAndrew Rist * or more contributor license agreements. See the NOTICE file
5*b3f79822SAndrew Rist * distributed with this work for additional information
6*b3f79822SAndrew Rist * regarding copyright ownership. The ASF licenses this file
7*b3f79822SAndrew Rist * to you under the Apache License, Version 2.0 (the
8*b3f79822SAndrew Rist * "License"); you may not use this file except in compliance
9*b3f79822SAndrew Rist * with the License. You may obtain a copy of the License at
10*b3f79822SAndrew Rist *
11*b3f79822SAndrew Rist * http://www.apache.org/licenses/LICENSE-2.0
12*b3f79822SAndrew Rist *
13*b3f79822SAndrew Rist * Unless required by applicable law or agreed to in writing,
14*b3f79822SAndrew Rist * software distributed under the License is distributed on an
15*b3f79822SAndrew Rist * "AS IS" BASIS, WITHOUT WARRANTIES OR CONDITIONS OF ANY
16*b3f79822SAndrew Rist * KIND, either express or implied. See the License for the
17*b3f79822SAndrew Rist * specific language governing permissions and limitations
18*b3f79822SAndrew Rist * under the License.
19*b3f79822SAndrew Rist *
20*b3f79822SAndrew Rist *************************************************************/
21*b3f79822SAndrew Rist
22*b3f79822SAndrew Rist
23cdf0e10cSrcweir #include <vbahelper/helperdecl.hxx>
24cdf0e10cSrcweir #include <tools/urlobj.hxx>
25cdf0e10cSrcweir #include <comphelper/unwrapargs.hxx>
26cdf0e10cSrcweir
27cdf0e10cSrcweir #include <com/sun/star/util/XModifiable.hpp>
28cdf0e10cSrcweir #include <com/sun/star/util/XProtectable.hpp>
29cdf0e10cSrcweir #include <com/sun/star/sheet/XSpreadsheetView.hpp>
30cdf0e10cSrcweir #include <com/sun/star/sheet/XSpreadsheetDocument.hpp>
31cdf0e10cSrcweir #include <com/sun/star/frame/XStorable.hpp>
32cdf0e10cSrcweir #include <com/sun/star/frame/XFrame.hpp>
33cdf0e10cSrcweir #include <com/sun/star/beans/XPropertySet.hpp>
34cdf0e10cSrcweir #include <ooo/vba/excel/XlFileFormat.hpp>
35cdf0e10cSrcweir
36cdf0e10cSrcweir #include "scextopt.hxx"
37cdf0e10cSrcweir #include "vbaworksheet.hxx"
38cdf0e10cSrcweir #include "vbaworksheets.hxx"
39cdf0e10cSrcweir #include "vbaworkbook.hxx"
40cdf0e10cSrcweir #include "vbawindows.hxx"
41cdf0e10cSrcweir #include "vbastyles.hxx"
42cdf0e10cSrcweir #include "excelvbahelper.hxx"
43cdf0e10cSrcweir #include "vbapalette.hxx"
44cdf0e10cSrcweir #include <osl/file.hxx>
45cdf0e10cSrcweir #include <stdio.h>
46cdf0e10cSrcweir #include "vbanames.hxx" // Amelia Wang
47cdf0e10cSrcweir #include "nameuno.hxx"
48cdf0e10cSrcweir #include "docoptio.hxx"
49cdf0e10cSrcweir #include "unonames.hxx"
50cdf0e10cSrcweir
51cdf0e10cSrcweir // Much of the impl. for the equivalend UNO module is
52cdf0e10cSrcweir // sc/source/ui/unoobj/docuno.cxx, viewuno.cxx
53cdf0e10cSrcweir
54cdf0e10cSrcweir using namespace ::ooo::vba;
55cdf0e10cSrcweir using namespace ::com::sun::star;
56cdf0e10cSrcweir
57cdf0e10cSrcweir class ActiveSheet : public ScVbaWorksheet
58cdf0e10cSrcweir {
59cdf0e10cSrcweir protected:
getModel()60cdf0e10cSrcweir virtual uno::Reference< frame::XModel > getModel()
61cdf0e10cSrcweir {
62cdf0e10cSrcweir return getCurrentExcelDoc( mxContext );
63cdf0e10cSrcweir }
getSheet()64cdf0e10cSrcweir virtual uno::Reference< sheet::XSpreadsheet > getSheet()
65cdf0e10cSrcweir {
66cdf0e10cSrcweir uno::Reference< frame::XModel > xModel = getModel();
67cdf0e10cSrcweir uno::Reference< sheet::XSpreadsheet > xSheet;
68cdf0e10cSrcweir if ( xModel.is() )
69cdf0e10cSrcweir {
70cdf0e10cSrcweir uno::Reference< sheet::XSpreadsheetView > xSpreadsheet(
71cdf0e10cSrcweir xModel->getCurrentController(), uno::UNO_QUERY );
72cdf0e10cSrcweir if ( xSpreadsheet.is() )
73cdf0e10cSrcweir xSheet = xSpreadsheet->getActiveSheet();
74cdf0e10cSrcweir }
75cdf0e10cSrcweir return xSheet;
76cdf0e10cSrcweir }
77cdf0e10cSrcweir public:
ActiveSheet(const uno::Reference<XHelperInterface> & xParent,const uno::Reference<uno::XComponentContext> & xContext)78cdf0e10cSrcweir ActiveSheet( const uno::Reference< XHelperInterface >& xParent, const uno::Reference< uno::XComponentContext >& xContext ) : ScVbaWorksheet( xParent, xContext ) {}
79cdf0e10cSrcweir
80cdf0e10cSrcweir };
81cdf0e10cSrcweir
82cdf0e10cSrcweir uno::Sequence< sal_Int32 > ScVbaWorkbook::ColorData;
83cdf0e10cSrcweir
initColorData(const uno::Sequence<sal_Int32> & sColors)84cdf0e10cSrcweir void ScVbaWorkbook::initColorData( const uno::Sequence< sal_Int32 >& sColors )
85cdf0e10cSrcweir {
86cdf0e10cSrcweir const sal_Int32* pSource = sColors.getConstArray();
87cdf0e10cSrcweir sal_Int32* pDest = ColorData.getArray();
88cdf0e10cSrcweir const sal_Int32* pEnd = pSource + sColors.getLength();
89cdf0e10cSrcweir for ( ; pSource != pEnd; ++pSource, ++pDest )
90cdf0e10cSrcweir *pDest = *pSource;
91cdf0e10cSrcweir }
92cdf0e10cSrcweir
93cdf0e10cSrcweir
94cdf0e10cSrcweir void SAL_CALL
ResetColors()95cdf0e10cSrcweir ScVbaWorkbook::ResetColors( ) throw (::script::BasicErrorException, ::uno::RuntimeException)
96cdf0e10cSrcweir {
97cdf0e10cSrcweir uno::Reference< container::XIndexAccess > xIndexAccess( ScVbaPalette::getDefaultPalette(), uno::UNO_QUERY_THROW );
98cdf0e10cSrcweir sal_Int32 nLen = xIndexAccess->getCount();
99cdf0e10cSrcweir ColorData.realloc( nLen );
100cdf0e10cSrcweir
101cdf0e10cSrcweir uno::Sequence< sal_Int32 > dDefaultColors( nLen );
102cdf0e10cSrcweir sal_Int32* pDest = dDefaultColors.getArray();
103cdf0e10cSrcweir for ( sal_Int32 index=0; index < nLen; ++pDest, ++index )
104cdf0e10cSrcweir xIndexAccess->getByIndex( index ) >>= (*pDest);
105cdf0e10cSrcweir initColorData( dDefaultColors );
106cdf0e10cSrcweir }
107cdf0e10cSrcweir
108cdf0e10cSrcweir ::uno::Any SAL_CALL
Colors(const::uno::Any & Index)109cdf0e10cSrcweir ScVbaWorkbook::Colors( const ::uno::Any& Index ) throw (::script::BasicErrorException, ::uno::RuntimeException)
110cdf0e10cSrcweir {
111cdf0e10cSrcweir uno::Any aRet;
112cdf0e10cSrcweir if ( Index.getValue() )
113cdf0e10cSrcweir {
114cdf0e10cSrcweir sal_Int32 nIndex = 0;
115cdf0e10cSrcweir Index >>= nIndex;
116cdf0e10cSrcweir aRet = uno::makeAny( XLRGBToOORGB( ColorData[ --nIndex ] ) );
117cdf0e10cSrcweir }
118cdf0e10cSrcweir else
119cdf0e10cSrcweir aRet = uno::makeAny( ColorData );
120cdf0e10cSrcweir return aRet;
121cdf0e10cSrcweir }
122cdf0e10cSrcweir
123cdf0e10cSrcweir ::sal_Int32 SAL_CALL
FileFormat()124cdf0e10cSrcweir ScVbaWorkbook::FileFormat( ) throw (::script::BasicErrorException, ::uno::RuntimeException)
125cdf0e10cSrcweir {
126cdf0e10cSrcweir sal_Int32 aFileFormat = 0;
127cdf0e10cSrcweir rtl::OUString aFilterName;
128cdf0e10cSrcweir uno::Sequence< beans::PropertyValue > aArgs = getModel()->getArgs();
129cdf0e10cSrcweir
130cdf0e10cSrcweir // #FIXME - seems suspect should we not walk through the properties
131cdf0e10cSrcweir // to find the FilterName
132cdf0e10cSrcweir if (aArgs[0].Name.equalsAscii( "FilterName")) {
133cdf0e10cSrcweir aArgs[0].Value >>= aFilterName;
134cdf0e10cSrcweir } else {
135cdf0e10cSrcweir aArgs[1].Value >>= aFilterName;
136cdf0e10cSrcweir }
137cdf0e10cSrcweir
138cdf0e10cSrcweir if (aFilterName.equalsAscii("Text - txt - csv (StarCalc)")) {
139cdf0e10cSrcweir aFileFormat = excel::XlFileFormat::xlCSV; //xlFileFormat.
140cdf0e10cSrcweir }
141cdf0e10cSrcweir
142cdf0e10cSrcweir if (aFilterName.equalsAscii("DBF")) {
143cdf0e10cSrcweir aFileFormat = excel::XlFileFormat::xlDBF4;
144cdf0e10cSrcweir }
145cdf0e10cSrcweir
146cdf0e10cSrcweir if (aFilterName.equalsAscii("DIF")) {
147cdf0e10cSrcweir aFileFormat = excel::XlFileFormat::xlDIF;
148cdf0e10cSrcweir }
149cdf0e10cSrcweir
150cdf0e10cSrcweir if (aFilterName.equalsAscii("Lotus")) {
151cdf0e10cSrcweir aFileFormat = excel::XlFileFormat::xlWK3;
152cdf0e10cSrcweir }
153cdf0e10cSrcweir
154cdf0e10cSrcweir if (aFilterName.equalsAscii("MS Excel 4.0")) {
155cdf0e10cSrcweir aFileFormat = excel::XlFileFormat::xlExcel4Workbook;
156cdf0e10cSrcweir }
157cdf0e10cSrcweir
158cdf0e10cSrcweir if (aFilterName.equalsAscii("MS Excel 5.0/95")) {
159cdf0e10cSrcweir aFileFormat = excel::XlFileFormat::xlExcel5;
160cdf0e10cSrcweir }
161cdf0e10cSrcweir
162cdf0e10cSrcweir if (aFilterName.equalsAscii("MS Excel 97")) {
163cdf0e10cSrcweir aFileFormat = excel::XlFileFormat::xlExcel9795;
164cdf0e10cSrcweir }
165cdf0e10cSrcweir
166cdf0e10cSrcweir if (aFilterName.equalsAscii("HTML (StarCalc)")) {
167cdf0e10cSrcweir aFileFormat = excel::XlFileFormat::xlHtml;
168cdf0e10cSrcweir }
169cdf0e10cSrcweir
170cdf0e10cSrcweir if (aFilterName.equalsAscii("calc_StarOffice_XML_Calc_Template")) {
171cdf0e10cSrcweir aFileFormat = excel::XlFileFormat::xlTemplate;
172cdf0e10cSrcweir }
173cdf0e10cSrcweir
174cdf0e10cSrcweir if (aFilterName.equalsAscii("StarOffice XML (Calc)")) {
175cdf0e10cSrcweir aFileFormat = excel::XlFileFormat::xlWorkbookNormal;
176cdf0e10cSrcweir }
177cdf0e10cSrcweir if (aFilterName.equalsAscii("calc8")) {
178cdf0e10cSrcweir aFileFormat = excel::XlFileFormat::xlWorkbookNormal;
179cdf0e10cSrcweir }
180cdf0e10cSrcweir
181cdf0e10cSrcweir return aFileFormat;
182cdf0e10cSrcweir }
183cdf0e10cSrcweir
184cdf0e10cSrcweir void
init()185cdf0e10cSrcweir ScVbaWorkbook::init()
186cdf0e10cSrcweir {
187cdf0e10cSrcweir if ( !ColorData.getLength() )
188cdf0e10cSrcweir ResetColors();
189cdf0e10cSrcweir }
ScVbaWorkbook(const css::uno::Reference<ov::XHelperInterface> & xParent,const css::uno::Reference<css::uno::XComponentContext> & xContext)190cdf0e10cSrcweir ScVbaWorkbook::ScVbaWorkbook( const css::uno::Reference< ov::XHelperInterface >& xParent, const css::uno::Reference< css::uno::XComponentContext >& xContext) :ScVbaWorkbook_BASE( xParent, xContext )
191cdf0e10cSrcweir {
192cdf0e10cSrcweir //#FIXME this persists the color data per office instance and
193cdf0e10cSrcweir // not per workbook instance, need to hook the data into XModel
194cdf0e10cSrcweir // ( e.g. we already store the imported palette in there )
195cdf0e10cSrcweir // so we should,
196cdf0e10cSrcweir // a) make the class that does that a service
197cdf0e10cSrcweir // b) make that service implement XIndexContainer
198cdf0e10cSrcweir init();
199cdf0e10cSrcweir }
200cdf0e10cSrcweir
ScVbaWorkbook(const css::uno::Reference<ov::XHelperInterface> & xParent,const css::uno::Reference<css::uno::XComponentContext> & xContext,css::uno::Reference<css::frame::XModel> xModel)201cdf0e10cSrcweir ScVbaWorkbook::ScVbaWorkbook( const css::uno::Reference< ov::XHelperInterface >& xParent, const css::uno::Reference< css::uno::XComponentContext >& xContext, css::uno::Reference< css::frame::XModel > xModel ) : ScVbaWorkbook_BASE( xParent, xContext, xModel )
202cdf0e10cSrcweir {
203cdf0e10cSrcweir init();
204cdf0e10cSrcweir }
205cdf0e10cSrcweir
ScVbaWorkbook(uno::Sequence<uno::Any> const & args,uno::Reference<uno::XComponentContext> const & xContext)206cdf0e10cSrcweir ScVbaWorkbook::ScVbaWorkbook( uno::Sequence< uno::Any> const & args,
207cdf0e10cSrcweir uno::Reference< uno::XComponentContext> const & xContext ) : ScVbaWorkbook_BASE( args, xContext )
208cdf0e10cSrcweir {
209cdf0e10cSrcweir init();
210cdf0e10cSrcweir }
211cdf0e10cSrcweir
212cdf0e10cSrcweir uno::Reference< excel::XWorksheet >
getActiveSheet()213cdf0e10cSrcweir ScVbaWorkbook::getActiveSheet() throw (uno::RuntimeException)
214cdf0e10cSrcweir {
215cdf0e10cSrcweir uno::Reference< frame::XModel > xModel( getCurrentExcelDoc( mxContext ), uno::UNO_SET_THROW );
216cdf0e10cSrcweir uno::Reference< sheet::XSpreadsheetView > xView( xModel->getCurrentController(), uno::UNO_QUERY_THROW );
217cdf0e10cSrcweir uno::Reference< sheet::XSpreadsheet > xSheet( xView->getActiveSheet(), uno::UNO_SET_THROW );
218cdf0e10cSrcweir // #162503# return the original sheet module wrapper object, instead of a new instance
219c83e58a0SMichael Stahl uno::Reference< excel::XWorksheet > xWorksheet( excel::getUnoSheetModuleObj( xSheet ), uno::UNO_QUERY );
220c83e58a0SMichael Stahl if( xWorksheet.is() ) return xWorksheet;
221c83e58a0SMichael Stahl // #i116936# excel::getUnoSheetModuleObj() may return null in documents without global VBA mode enabled
222c83e58a0SMichael Stahl return new ScVbaWorksheet( this, mxContext, xSheet, xModel );
223cdf0e10cSrcweir }
224cdf0e10cSrcweir
225cdf0e10cSrcweir uno::Any SAL_CALL
Sheets(const uno::Any & aIndex)226cdf0e10cSrcweir ScVbaWorkbook::Sheets( const uno::Any& aIndex ) throw (uno::RuntimeException)
227cdf0e10cSrcweir {
228cdf0e10cSrcweir return Worksheets( aIndex );
229cdf0e10cSrcweir }
230cdf0e10cSrcweir
231cdf0e10cSrcweir uno::Any SAL_CALL
Worksheets(const uno::Any & aIndex)232cdf0e10cSrcweir ScVbaWorkbook::Worksheets( const uno::Any& aIndex ) throw (uno::RuntimeException)
233cdf0e10cSrcweir {
234cdf0e10cSrcweir uno::Reference< frame::XModel > xModel( getModel() );
235cdf0e10cSrcweir uno::Reference <sheet::XSpreadsheetDocument> xSpreadDoc( xModel, uno::UNO_QUERY_THROW );
236cdf0e10cSrcweir uno::Reference<container::XIndexAccess > xSheets( xSpreadDoc->getSheets(), uno::UNO_QUERY_THROW );
237cdf0e10cSrcweir uno::Reference< XCollection > xWorkSheets( new ScVbaWorksheets( this, mxContext, xSheets, xModel ) );
238cdf0e10cSrcweir if ( aIndex.getValueTypeClass() == uno::TypeClass_VOID )
239cdf0e10cSrcweir {
240cdf0e10cSrcweir return uno::Any( xWorkSheets );
241cdf0e10cSrcweir }
242cdf0e10cSrcweir // pass on to collection
243cdf0e10cSrcweir return uno::Any( xWorkSheets->Item( aIndex, uno::Any() ) );
244cdf0e10cSrcweir }
245cdf0e10cSrcweir uno::Any SAL_CALL
Windows(const uno::Any & aIndex)246cdf0e10cSrcweir ScVbaWorkbook::Windows( const uno::Any& aIndex ) throw (uno::RuntimeException)
247cdf0e10cSrcweir {
248cdf0e10cSrcweir
249cdf0e10cSrcweir uno::Reference< excel::XWindows > xWindows( new ScVbaWindows( getParent(), mxContext ) );
250cdf0e10cSrcweir if ( aIndex.getValueTypeClass() == uno::TypeClass_VOID )
251cdf0e10cSrcweir return uno::Any( xWindows );
252cdf0e10cSrcweir return uno::Any( xWindows->Item( aIndex, uno::Any() ) );
253cdf0e10cSrcweir }
254cdf0e10cSrcweir
255cdf0e10cSrcweir void SAL_CALL
Activate()256cdf0e10cSrcweir ScVbaWorkbook::Activate() throw (uno::RuntimeException)
257cdf0e10cSrcweir {
258cdf0e10cSrcweir VbaDocumentBase::Activate();
259cdf0e10cSrcweir }
260cdf0e10cSrcweir
261cdf0e10cSrcweir ::sal_Bool
getProtectStructure()262cdf0e10cSrcweir ScVbaWorkbook::getProtectStructure() throw (uno::RuntimeException)
263cdf0e10cSrcweir {
264cdf0e10cSrcweir uno::Reference< util::XProtectable > xProt( getModel(), uno::UNO_QUERY_THROW );
265cdf0e10cSrcweir return xProt->isProtected();
266cdf0e10cSrcweir }
267cdf0e10cSrcweir
getPrecisionAsDisplayed()268cdf0e10cSrcweir ::sal_Bool SAL_CALL ScVbaWorkbook::getPrecisionAsDisplayed() throw (uno::RuntimeException)
269cdf0e10cSrcweir {
270cdf0e10cSrcweir uno::Reference< frame::XModel > xModel( getModel(), uno::UNO_QUERY_THROW );
271cdf0e10cSrcweir ScDocument* pDoc = excel::getDocShell( xModel )->GetDocument();
272cdf0e10cSrcweir return pDoc->GetDocOptions().IsCalcAsShown();
273cdf0e10cSrcweir }
274cdf0e10cSrcweir
setPrecisionAsDisplayed(sal_Bool _precisionAsDisplayed)275cdf0e10cSrcweir void SAL_CALL ScVbaWorkbook::setPrecisionAsDisplayed( sal_Bool _precisionAsDisplayed ) throw (uno::RuntimeException)
276cdf0e10cSrcweir {
277cdf0e10cSrcweir uno::Reference< frame::XModel > xModel( getModel(), uno::UNO_QUERY_THROW );
278cdf0e10cSrcweir ScDocument* pDoc = excel::getDocShell( xModel )->GetDocument();
279cdf0e10cSrcweir ScDocOptions aOpt = pDoc->GetDocOptions();
280cdf0e10cSrcweir aOpt.SetCalcAsShown( _precisionAsDisplayed );
281cdf0e10cSrcweir pDoc->SetDocOptions( aOpt );
282cdf0e10cSrcweir }
283cdf0e10cSrcweir
284cdf0e10cSrcweir void
SaveCopyAs(const rtl::OUString & sFileName)285cdf0e10cSrcweir ScVbaWorkbook::SaveCopyAs( const rtl::OUString& sFileName ) throw ( uno::RuntimeException)
286cdf0e10cSrcweir {
287cdf0e10cSrcweir rtl::OUString aURL;
288cdf0e10cSrcweir osl::FileBase::getFileURLFromSystemPath( sFileName, aURL );
289cdf0e10cSrcweir uno::Reference< frame::XStorable > xStor( getModel(), uno::UNO_QUERY_THROW );
290cdf0e10cSrcweir uno::Sequence< beans::PropertyValue > storeProps(1);
291cdf0e10cSrcweir storeProps[0].Name = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "FilterName" ) );
292cdf0e10cSrcweir storeProps[0].Value <<= rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "MS Excel 97" ) );
293cdf0e10cSrcweir xStor->storeToURL( aURL, storeProps );
294cdf0e10cSrcweir }
295cdf0e10cSrcweir
296cdf0e10cSrcweir css::uno::Any SAL_CALL
Styles(const uno::Any & Item)297cdf0e10cSrcweir ScVbaWorkbook::Styles( const uno::Any& Item ) throw (uno::RuntimeException)
298cdf0e10cSrcweir {
299cdf0e10cSrcweir // quick look and Styles object doesn't seem to have a valid parent
300cdf0e10cSrcweir // or a least the object browser just shows an object that has no
301cdf0e10cSrcweir // variables ( therefore... leave as NULL for now )
302cdf0e10cSrcweir uno::Reference< XCollection > dStyles = new ScVbaStyles( uno::Reference< XHelperInterface >(), mxContext, getModel() );
303cdf0e10cSrcweir if ( Item.hasValue() )
304cdf0e10cSrcweir return dStyles->Item( Item, uno::Any() );
305cdf0e10cSrcweir return uno::makeAny( dStyles );
306cdf0e10cSrcweir }
307cdf0e10cSrcweir
308cdf0e10cSrcweir // Amelia Wang
309cdf0e10cSrcweir uno::Any SAL_CALL
Names(const uno::Any & aIndex)310cdf0e10cSrcweir ScVbaWorkbook::Names( const uno::Any& aIndex ) throw (uno::RuntimeException)
311cdf0e10cSrcweir {
312cdf0e10cSrcweir uno::Reference< frame::XModel > xModel( getModel(), uno::UNO_SET_THROW );
313cdf0e10cSrcweir uno::Reference< beans::XPropertySet > xProps( xModel, uno::UNO_QUERY_THROW );
314cdf0e10cSrcweir uno::Reference< sheet::XNamedRanges > xNamedRanges( xProps->getPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("NamedRanges") ) ), uno::UNO_QUERY_THROW );
315cdf0e10cSrcweir uno::Reference< XCollection > xNames( new ScVbaNames( this, mxContext, xNamedRanges, xModel ) );
316cdf0e10cSrcweir if ( aIndex.hasValue() )
317cdf0e10cSrcweir return uno::Any( xNames->Item( aIndex, uno::Any() ) );
318cdf0e10cSrcweir return uno::Any( xNames );
319cdf0e10cSrcweir }
320cdf0e10cSrcweir
321cdf0e10cSrcweir rtl::OUString&
getServiceImplName()322cdf0e10cSrcweir ScVbaWorkbook::getServiceImplName()
323cdf0e10cSrcweir {
324cdf0e10cSrcweir static rtl::OUString sImplName( RTL_CONSTASCII_USTRINGPARAM("ScVbaWorkbook") );
325cdf0e10cSrcweir return sImplName;
326cdf0e10cSrcweir }
327cdf0e10cSrcweir
328cdf0e10cSrcweir uno::Sequence< rtl::OUString >
getServiceNames()329cdf0e10cSrcweir ScVbaWorkbook::getServiceNames()
330cdf0e10cSrcweir {
331cdf0e10cSrcweir static uno::Sequence< rtl::OUString > aServiceNames;
332cdf0e10cSrcweir if ( aServiceNames.getLength() == 0 )
333cdf0e10cSrcweir {
334cdf0e10cSrcweir aServiceNames.realloc( 1 );
335cdf0e10cSrcweir aServiceNames[ 0 ] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.excel.Workbook" ) );
336cdf0e10cSrcweir }
337cdf0e10cSrcweir return aServiceNames;
338cdf0e10cSrcweir }
339cdf0e10cSrcweir
340cdf0e10cSrcweir ::rtl::OUString SAL_CALL
getCodeName()341cdf0e10cSrcweir ScVbaWorkbook::getCodeName() throw (css::uno::RuntimeException)
342cdf0e10cSrcweir {
343cdf0e10cSrcweir uno::Reference< beans::XPropertySet > xModelProp( getModel(), uno::UNO_QUERY_THROW );
344cdf0e10cSrcweir return xModelProp->getPropertyValue( ::rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "CodeName" ) ) ).get< ::rtl::OUString >();
345cdf0e10cSrcweir }
346cdf0e10cSrcweir
347cdf0e10cSrcweir namespace workbook
348cdf0e10cSrcweir {
349cdf0e10cSrcweir namespace sdecl = comphelper::service_decl;
350cdf0e10cSrcweir sdecl::vba_service_class_<ScVbaWorkbook, sdecl::with_args<true> > serviceImpl;
351cdf0e10cSrcweir extern sdecl::ServiceDecl const serviceDecl(
352cdf0e10cSrcweir serviceImpl,
353cdf0e10cSrcweir "ScVbaWorkbook",
354cdf0e10cSrcweir "ooo.vba.excel.Workbook" );
355cdf0e10cSrcweir }
356