xref: /AOO41X/main/sc/source/ui/vba/vbachart.cxx (revision b3f79822e811ac3493b185030a72c3c5a51f32d8)
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
10cdf0e10cSrcweir  *
11*b3f79822SAndrew Rist  *   http://www.apache.org/licenses/LICENSE-2.0
12cdf0e10cSrcweir  *
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.
19cdf0e10cSrcweir  *
20*b3f79822SAndrew Rist  *************************************************************/
21*b3f79822SAndrew Rist 
22*b3f79822SAndrew Rist 
23cdf0e10cSrcweir #include "vbachart.hxx"
24cdf0e10cSrcweir #include <com/sun/star/beans/XPropertySet.hpp>
25cdf0e10cSrcweir #include <com/sun/star/sheet/XCellRangeAddressable.hpp>
26cdf0e10cSrcweir #include <com/sun/star/chart/XAxisXSupplier.hpp>
27cdf0e10cSrcweir #include <com/sun/star/chart/XAxisYSupplier.hpp>
28cdf0e10cSrcweir #include <com/sun/star/chart/XAxisZSupplier.hpp>
29cdf0e10cSrcweir #include <com/sun/star/chart/XTwoAxisXSupplier.hpp>
30cdf0e10cSrcweir #include <com/sun/star/chart/XTwoAxisYSupplier.hpp>
31cdf0e10cSrcweir #include <com/sun/star/chart/XChartDataArray.hpp>
32cdf0e10cSrcweir #include <com/sun/star/chart/ChartSymbolType.hpp>
33cdf0e10cSrcweir #include <com/sun/star/chart/ChartSolidType.hpp>
34cdf0e10cSrcweir #include <com/sun/star/chart/ChartDataRowSource.hpp>
35cdf0e10cSrcweir #include <com/sun/star/chart/ChartDataCaption.hpp>
36cdf0e10cSrcweir #include <ooo/vba/excel/XlChartType.hpp>
37cdf0e10cSrcweir #include <ooo/vba/excel/XlRowCol.hpp>
38cdf0e10cSrcweir #include <ooo/vba/excel/XlAxisType.hpp>
39cdf0e10cSrcweir #include <ooo/vba/excel/XlAxisGroup.hpp>
40cdf0e10cSrcweir 
41cdf0e10cSrcweir #include <basic/sberrors.hxx>
42cdf0e10cSrcweir #include "vbachartobject.hxx"
43cdf0e10cSrcweir #include "vbarange.hxx"
44cdf0e10cSrcweir #include "vbacharttitle.hxx"
45cdf0e10cSrcweir #include "vbaaxes.hxx"
46cdf0e10cSrcweir 
47cdf0e10cSrcweir using namespace ::com::sun::star;
48cdf0e10cSrcweir using namespace ::ooo::vba;
49cdf0e10cSrcweir using namespace ::ooo::vba::excel::XlChartType;
50cdf0e10cSrcweir using namespace ::ooo::vba::excel::XlRowCol;
51cdf0e10cSrcweir using namespace ::ooo::vba::excel::XlAxisType;
52cdf0e10cSrcweir using namespace ::ooo::vba::excel::XlAxisGroup;
53cdf0e10cSrcweir 
54cdf0e10cSrcweir const rtl::OUString CHART_NAME( RTL_CONSTASCII_USTRINGPARAM("Name") );
55cdf0e10cSrcweir // #TODO move this constant to vbaseries.[ch]xx ( when it exists )
56cdf0e10cSrcweir const rtl::OUString DEFAULTSERIESPREFIX( RTL_CONSTASCII_USTRINGPARAM("Series") );
57cdf0e10cSrcweir const rtl::OUString DATAROWSOURCE( RTL_CONSTASCII_USTRINGPARAM("DataRowSource") );
58cdf0e10cSrcweir const rtl::OUString UPDOWN( RTL_CONSTASCII_USTRINGPARAM("UpDown") );
59cdf0e10cSrcweir const rtl::OUString VOLUME( RTL_CONSTASCII_USTRINGPARAM("Volume") );
60cdf0e10cSrcweir const rtl::OUString LINES( RTL_CONSTASCII_USTRINGPARAM("Lines") );
61cdf0e10cSrcweir const rtl::OUString SPLINETYPE( RTL_CONSTASCII_USTRINGPARAM("SplineType") );
62cdf0e10cSrcweir const rtl::OUString SYMBOLTYPE( RTL_CONSTASCII_USTRINGPARAM("SymbolType") );
63cdf0e10cSrcweir const rtl::OUString DEEP( RTL_CONSTASCII_USTRINGPARAM("Deep") );
64cdf0e10cSrcweir const rtl::OUString SOLIDTYPE( RTL_CONSTASCII_USTRINGPARAM("SolidType") );
65cdf0e10cSrcweir const rtl::OUString VERTICAL( RTL_CONSTASCII_USTRINGPARAM("Vertical") );
66cdf0e10cSrcweir const rtl::OUString PERCENT( RTL_CONSTASCII_USTRINGPARAM("Percent") );
67cdf0e10cSrcweir const rtl::OUString STACKED( RTL_CONSTASCII_USTRINGPARAM("Stacked") );
68cdf0e10cSrcweir const rtl::OUString DIM3D( RTL_CONSTASCII_USTRINGPARAM("Dim3D") );
69cdf0e10cSrcweir const rtl::OUString HASMAINTITLE( RTL_CONSTASCII_USTRINGPARAM("HasMainTitle") );
70cdf0e10cSrcweir const rtl::OUString HASLEGEND( RTL_CONSTASCII_USTRINGPARAM("HasLegend") );
71cdf0e10cSrcweir const rtl::OUString DATACAPTION( RTL_CONSTASCII_USTRINGPARAM("DataCaption") );
72cdf0e10cSrcweir 
ScVbaChart(const css::uno::Reference<ov::XHelperInterface> & _xParent,const css::uno::Reference<css::uno::XComponentContext> & _xContext,const css::uno::Reference<css::lang::XComponent> & _xChartComponent,const css::uno::Reference<css::table::XTableChart> & _xTableChart)73cdf0e10cSrcweir ScVbaChart::ScVbaChart( const css::uno::Reference< ov::XHelperInterface >& _xParent, const css::uno::Reference< css::uno::XComponentContext >& _xContext, const css::uno::Reference< css::lang::XComponent >& _xChartComponent, const css::uno::Reference< css::table::XTableChart >& _xTableChart ) : ChartImpl_BASE( _xParent, _xContext ), mxTableChart( _xTableChart )
74cdf0e10cSrcweir {
75cdf0e10cSrcweir 	mxChartDocument.set( _xChartComponent, uno::UNO_QUERY_THROW ) ;
76cdf0e10cSrcweir 	// #TODO is is possible that the XPropertySet interface is not set
77cdf0e10cSrcweir 	// code in setPlotBy seems to indicate that this is possible? but
78cdf0e10cSrcweir 	// additionally there is no check in most of the places where it is used
79cdf0e10cSrcweir 	// ( and therefore could possibly be NULL )
80cdf0e10cSrcweir 	// I'm going to let it throw for the moment ( npower )
81cdf0e10cSrcweir 	mxDiagramPropertySet.set( mxChartDocument->getDiagram(), uno::UNO_QUERY_THROW );
82cdf0e10cSrcweir 	mxChartPropertySet.set( _xChartComponent, uno::UNO_QUERY_THROW ) ;
83cdf0e10cSrcweir }
84cdf0e10cSrcweir 
85cdf0e10cSrcweir ::rtl::OUString SAL_CALL
getName()86cdf0e10cSrcweir ScVbaChart::getName() throw (css::uno::RuntimeException)
87cdf0e10cSrcweir {
88cdf0e10cSrcweir 	rtl::OUString sName;
89cdf0e10cSrcweir 	uno::Reference< beans::XPropertySet > xProps( mxChartDocument, uno::UNO_QUERY_THROW );
90cdf0e10cSrcweir 	try
91cdf0e10cSrcweir 	{
92cdf0e10cSrcweir 		xProps->getPropertyValue( CHART_NAME ) >>= sName;
93cdf0e10cSrcweir 	}
94cdf0e10cSrcweir 	catch( uno::Exception e ) // swallow exceptions
95cdf0e10cSrcweir 	{
96cdf0e10cSrcweir 	}
97cdf0e10cSrcweir 	return sName;
98cdf0e10cSrcweir }
99cdf0e10cSrcweir 
100cdf0e10cSrcweir uno::Any  SAL_CALL
SeriesCollection(const uno::Any &)101cdf0e10cSrcweir ScVbaChart::SeriesCollection(const uno::Any&) throw (uno::RuntimeException)
102cdf0e10cSrcweir {
103cdf0e10cSrcweir 	return uno::Any();
104cdf0e10cSrcweir }
105cdf0e10cSrcweir 
106cdf0e10cSrcweir ::sal_Int32 SAL_CALL
getChartType()107cdf0e10cSrcweir ScVbaChart::getChartType() throw ( uno::RuntimeException, script::BasicErrorException)
108cdf0e10cSrcweir {
109cdf0e10cSrcweir 	sal_Int32 nChartType = -1;
110cdf0e10cSrcweir 	try
111cdf0e10cSrcweir 	{
112cdf0e10cSrcweir 		rtl::OUString sDiagramType = mxChartDocument->getDiagram()->getDiagramType();
113cdf0e10cSrcweir 		if (sDiagramType.equals( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "com.sun.star.chart.AreaDiagram" ))))
114cdf0e10cSrcweir 		{
115cdf0e10cSrcweir 			if (is3D())
116cdf0e10cSrcweir 			{
117cdf0e10cSrcweir 				nChartType = getStackedType(xl3DAreaStacked, xl3DAreaStacked100, xl3DArea);
118cdf0e10cSrcweir 			}
119cdf0e10cSrcweir 			else
120cdf0e10cSrcweir 			{
121cdf0e10cSrcweir 				nChartType = getStackedType(xlAreaStacked, xlAreaStacked100, xlArea);
122cdf0e10cSrcweir 			}
123cdf0e10cSrcweir 		}
124cdf0e10cSrcweir 		else if (sDiagramType.equals( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("com.sun.star.chart.PieDiagram"))))
125cdf0e10cSrcweir 		{
126cdf0e10cSrcweir 			if (is3D())
127cdf0e10cSrcweir 				nChartType = xl3DPie;
128cdf0e10cSrcweir 			else
129cdf0e10cSrcweir 				nChartType = xlPie;                 /*TODO XlChartType  xlPieExploded, XlChartType xlPieOfPie */
130cdf0e10cSrcweir 		}
131cdf0e10cSrcweir 		else if (sDiagramType.equals( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("com.sun.star.chart.BarDiagram"))))
132cdf0e10cSrcweir 		{
133cdf0e10cSrcweir 			sal_Int32 nSolidType = chart::ChartSolidType::RECTANGULAR_SOLID;
134cdf0e10cSrcweir 			if (mxDiagramPropertySet->getPropertySetInfo()->hasPropertyByName(SOLIDTYPE))
135cdf0e10cSrcweir 			{       //in 2D diagrams 'SolidType' may not be set
136cdf0e10cSrcweir 				if (is3D())
137cdf0e10cSrcweir 					mxDiagramPropertySet->getPropertyValue(SOLIDTYPE) >>= nSolidType;
138cdf0e10cSrcweir 			}
139cdf0e10cSrcweir 			switch (nSolidType)
140cdf0e10cSrcweir 			{
141cdf0e10cSrcweir 				case chart::ChartSolidType::CONE:
142cdf0e10cSrcweir 					nChartType = getSolidType(xlConeCol, xlConeColStacked, xlConeColStacked100, xlConeColClustered, xlConeBarStacked, xlConeBarStacked100, xlConeBarClustered);
143cdf0e10cSrcweir 					break;
144cdf0e10cSrcweir 				case chart::ChartSolidType::CYLINDER:
145cdf0e10cSrcweir 					nChartType = getSolidType(xlCylinderCol, xlCylinderColStacked, xlCylinderColStacked100, xlCylinderColClustered, xlCylinderBarStacked, xlCylinderBarStacked100, xlCylinderBarClustered);
146cdf0e10cSrcweir 					break;
147cdf0e10cSrcweir 				case chart::ChartSolidType::PYRAMID:
148cdf0e10cSrcweir 					nChartType = getSolidType(xlPyramidCol, xlPyramidColStacked, xlPyramidColStacked100, xlPyramidColClustered, xlPyramidBarStacked, xlPyramidBarStacked100, xlPyramidBarClustered);
149cdf0e10cSrcweir 					break;
150cdf0e10cSrcweir 				default: // RECTANGULAR_SOLID
151cdf0e10cSrcweir 					if (is3D())
152cdf0e10cSrcweir 					{
153cdf0e10cSrcweir 						nChartType = getSolidType(xl3DColumn, xl3DColumnStacked, xl3DColumnStacked100, xl3DColumnClustered, xl3DBarStacked, xl3DBarStacked100, xl3DBarClustered);
154cdf0e10cSrcweir 					}
155cdf0e10cSrcweir 					else
156cdf0e10cSrcweir 					{
157cdf0e10cSrcweir 						nChartType = getSolidType(xlColumnClustered,  xlColumnStacked, xlColumnStacked100, xlColumnClustered, xlBarStacked, xlBarStacked100, xlBarClustered);
158cdf0e10cSrcweir 					}
159cdf0e10cSrcweir 					break;
160cdf0e10cSrcweir 				}
161cdf0e10cSrcweir 			}
162cdf0e10cSrcweir 		else if (sDiagramType.equals( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("com.sun.star.chart.StockDiagram"))))
163cdf0e10cSrcweir 		{
164cdf0e10cSrcweir 			sal_Bool bVolume = sal_False;
165cdf0e10cSrcweir 			mxDiagramPropertySet->getPropertyValue(VOLUME) >>= bVolume;
166cdf0e10cSrcweir 			if (bVolume)
167cdf0e10cSrcweir 			{
168cdf0e10cSrcweir 				nChartType = getStockUpDownValue(xlStockVOHLC, xlStockVHLC);
169cdf0e10cSrcweir 			}
170cdf0e10cSrcweir 			else
171cdf0e10cSrcweir 			{
172cdf0e10cSrcweir 				nChartType = getStockUpDownValue(xlStockOHLC, xlStockHLC);
173cdf0e10cSrcweir 			}
174cdf0e10cSrcweir 		}
175cdf0e10cSrcweir 		else if (sDiagramType.equals( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("com.sun.star.chart.XYDiagram"))))
176cdf0e10cSrcweir 		{
177cdf0e10cSrcweir 			sal_Bool bHasLines = sal_False;
178cdf0e10cSrcweir 			mxDiagramPropertySet->getPropertyValue(LINES) >>= bHasLines;
179cdf0e10cSrcweir 			sal_Int32 nSplineType = 0;
180cdf0e10cSrcweir 			mxDiagramPropertySet->getPropertyValue(SPLINETYPE) >>= nSplineType;
181cdf0e10cSrcweir 			if (nSplineType == 1)
182cdf0e10cSrcweir 			{
183cdf0e10cSrcweir 				nChartType = getMarkerType(xlXYScatterSmooth, xlXYScatterSmoothNoMarkers);
184cdf0e10cSrcweir 			}
185cdf0e10cSrcweir 			else if (bHasLines)
186cdf0e10cSrcweir 			{
187cdf0e10cSrcweir 				nChartType = getMarkerType(xlXYScatterLines, xlXYScatterLinesNoMarkers);
188cdf0e10cSrcweir 			}
189cdf0e10cSrcweir 			else
190cdf0e10cSrcweir 			{
191cdf0e10cSrcweir 				nChartType = xlXYScatter;
192cdf0e10cSrcweir 			}
193cdf0e10cSrcweir 		}
194cdf0e10cSrcweir 		else if (sDiagramType.equals( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("com.sun.star.chart.LineDiagram"))))
195cdf0e10cSrcweir 		{
196cdf0e10cSrcweir 			if (is3D())
197cdf0e10cSrcweir 			{
198cdf0e10cSrcweir 				nChartType = xl3DLine;
199cdf0e10cSrcweir 			}
200cdf0e10cSrcweir 			else if (hasMarkers())
201cdf0e10cSrcweir 			{
202cdf0e10cSrcweir 				nChartType = getStackedType(xlLineMarkersStacked, xlLineMarkersStacked100, xlLineMarkers);
203cdf0e10cSrcweir 			}
204cdf0e10cSrcweir 			else
205cdf0e10cSrcweir 			{
206cdf0e10cSrcweir 				nChartType = getStackedType(xlLineStacked, xlLineStacked100, xlLine);
207cdf0e10cSrcweir 			}
208cdf0e10cSrcweir 		}
209cdf0e10cSrcweir 		else if (sDiagramType.equals( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("com.sun.star.chart.DonutDiagram"))))
210cdf0e10cSrcweir 		{
211cdf0e10cSrcweir 			nChartType = xlDoughnut;                    // TODO DoughnutExploded ??
212cdf0e10cSrcweir 		}
213cdf0e10cSrcweir 		else if (sDiagramType.equals( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("com.sun.star.chart.NetDiagram"))))
214cdf0e10cSrcweir 		{
215cdf0e10cSrcweir 			nChartType = getMarkerType(xlRadarMarkers, xlRadar);
216cdf0e10cSrcweir 		}
217cdf0e10cSrcweir 	}
218cdf0e10cSrcweir 	catch (uno::Exception& )
219cdf0e10cSrcweir 	{
220cdf0e10cSrcweir 		throw script::BasicErrorException( rtl::OUString(), uno::Reference< uno::XInterface >(), SbERR_METHOD_FAILED, rtl::OUString() );
221cdf0e10cSrcweir 	}
222cdf0e10cSrcweir 	return nChartType;
223cdf0e10cSrcweir }
224cdf0e10cSrcweir 
225cdf0e10cSrcweir void SAL_CALL
setChartType(::sal_Int32 _nChartType)226cdf0e10cSrcweir ScVbaChart::setChartType( ::sal_Int32 _nChartType ) throw ( uno::RuntimeException, script::BasicErrorException)
227cdf0e10cSrcweir {
228cdf0e10cSrcweir try
229cdf0e10cSrcweir {
230cdf0e10cSrcweir 	switch (_nChartType)
231cdf0e10cSrcweir 	{
232cdf0e10cSrcweir 		case xlColumnClustered:
233cdf0e10cSrcweir 		case xlColumnStacked:
234cdf0e10cSrcweir 		case xlColumnStacked100:
235cdf0e10cSrcweir 		case xl3DColumnClustered:
236cdf0e10cSrcweir 		case xl3DColumnStacked:
237cdf0e10cSrcweir 		case xl3DColumnStacked100:
238cdf0e10cSrcweir 		case xl3DColumn:
239cdf0e10cSrcweir 		case xlBarClustered:
240cdf0e10cSrcweir 		case xlBarStacked:
241cdf0e10cSrcweir 		case xlBarStacked100:
242cdf0e10cSrcweir 		case xl3DBarClustered:
243cdf0e10cSrcweir 		case xl3DBarStacked:
244cdf0e10cSrcweir 		case xl3DBarStacked100:
245cdf0e10cSrcweir 		case xlConeColClustered:
246cdf0e10cSrcweir 		case xlConeColStacked:
247cdf0e10cSrcweir 		case xlConeColStacked100:
248cdf0e10cSrcweir 		case xlConeBarClustered:
249cdf0e10cSrcweir 		case xlConeBarStacked:
250cdf0e10cSrcweir 		case xlConeBarStacked100:
251cdf0e10cSrcweir 		case xlConeCol:
252cdf0e10cSrcweir 		case xlPyramidColClustered:
253cdf0e10cSrcweir 		case xlPyramidColStacked:
254cdf0e10cSrcweir 		case xlPyramidColStacked100:
255cdf0e10cSrcweir 		case xlPyramidBarClustered:
256cdf0e10cSrcweir 		case xlPyramidBarStacked:
257cdf0e10cSrcweir 		case xlPyramidBarStacked100:
258cdf0e10cSrcweir 		case xlPyramidCol:
259cdf0e10cSrcweir 		case xlCylinderColClustered:
260cdf0e10cSrcweir 		case xlCylinderColStacked:
261cdf0e10cSrcweir 		case xlCylinderColStacked100:
262cdf0e10cSrcweir 		case xlCylinderBarClustered:
263cdf0e10cSrcweir 		case xlCylinderBarStacked:
264cdf0e10cSrcweir 		case xlCylinderBarStacked100:
265cdf0e10cSrcweir 		case xlCylinderCol:
266cdf0e10cSrcweir 		case xlSurface: // not possible
267cdf0e10cSrcweir 		case xlSurfaceWireframe:
268cdf0e10cSrcweir 		case xlSurfaceTopView:
269cdf0e10cSrcweir 		case xlSurfaceTopViewWireframe:
270cdf0e10cSrcweir 			setDiagram( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("com.sun.star.chart.BarDiagram")));
271cdf0e10cSrcweir 			break;
272cdf0e10cSrcweir 		case xlLine:
273cdf0e10cSrcweir 		case xl3DLine:
274cdf0e10cSrcweir 		case xlLineStacked:
275cdf0e10cSrcweir 		case xlLineStacked100:
276cdf0e10cSrcweir 		case xlLineMarkers:
277cdf0e10cSrcweir 		case xlLineMarkersStacked:
278cdf0e10cSrcweir 		case xlLineMarkersStacked100:
279cdf0e10cSrcweir 			setDiagram( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("com.sun.star.chart.LineDiagram")));
280cdf0e10cSrcweir 			break;
281cdf0e10cSrcweir 		case xl3DArea:
282cdf0e10cSrcweir 		case xlArea:
283cdf0e10cSrcweir 		case xlAreaStacked:
284cdf0e10cSrcweir 		case xlAreaStacked100:
285cdf0e10cSrcweir 		case xl3DAreaStacked:
286cdf0e10cSrcweir 		case xl3DAreaStacked100:
287cdf0e10cSrcweir 			setDiagram( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("com.sun.star.chart.AreaDiagram")) );
288cdf0e10cSrcweir 			break;
289cdf0e10cSrcweir 		case xlDoughnut:
290cdf0e10cSrcweir 		case xlDoughnutExploded:
291cdf0e10cSrcweir 			setDiagram( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("com.sun.star.chart.DonutDiagram") ) );
292cdf0e10cSrcweir 			break;
293cdf0e10cSrcweir 		case xlStockHLC:
294cdf0e10cSrcweir 		case xlStockOHLC:
295cdf0e10cSrcweir 		case xlStockVHLC:
296cdf0e10cSrcweir 		case xlStockVOHLC:
297cdf0e10cSrcweir 			setDiagram( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("com.sun.star.chart.StockDiagram")));
298cdf0e10cSrcweir 			mxDiagramPropertySet->setPropertyValue( UPDOWN, uno::makeAny(sal_Bool((_nChartType == xlStockOHLC) || (_nChartType == xlStockVOHLC))));
299cdf0e10cSrcweir 			mxDiagramPropertySet->setPropertyValue(VOLUME, uno::makeAny(sal_Bool((_nChartType == xlStockVHLC) || (_nChartType == xlStockVOHLC))));
300cdf0e10cSrcweir 			break;
301cdf0e10cSrcweir 
302cdf0e10cSrcweir 		case xlPieOfPie:                            // not possible
303cdf0e10cSrcweir 		case xlPieExploded: // SegmentOffset an ChartDataPointProperties ->am XDiagram abholen //wie macht Excel das?
304cdf0e10cSrcweir 		case xl3DPieExploded:
305cdf0e10cSrcweir 		case xl3DPie:
306cdf0e10cSrcweir 		case xlPie:
307cdf0e10cSrcweir 		case xlBarOfPie:                            // not possible (Zoom pie)
308cdf0e10cSrcweir 			setDiagram( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("com.sun.star.chart.PieDiagram")));
309cdf0e10cSrcweir 			break;
310cdf0e10cSrcweir 
311cdf0e10cSrcweir 		case xlRadar:
312cdf0e10cSrcweir 		case xlRadarMarkers:
313cdf0e10cSrcweir 		case xlRadarFilled:
314cdf0e10cSrcweir 			setDiagram( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("com.sun.star.chart.NetDiagram")));
315cdf0e10cSrcweir 			break;
316cdf0e10cSrcweir 		case xlXYScatter:
317cdf0e10cSrcweir 		case xlBubble:                      // not possible
318cdf0e10cSrcweir 		case xlBubble3DEffect:              // not possible
319cdf0e10cSrcweir 		case xlXYScatterLines:
320cdf0e10cSrcweir 		case xlXYScatterLinesNoMarkers:
321cdf0e10cSrcweir 		case xlXYScatterSmooth:
322cdf0e10cSrcweir 		case xlXYScatterSmoothNoMarkers:
323cdf0e10cSrcweir 			setDiagram( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("com.sun.star.chart.XYDiagram")));
324cdf0e10cSrcweir 			switch(_nChartType)
325cdf0e10cSrcweir 			{
326cdf0e10cSrcweir 				case xlXYScatter:
327cdf0e10cSrcweir 				case xlBubble:                      // not possible
328cdf0e10cSrcweir 				case xlBubble3DEffect:              // not possible
329cdf0e10cSrcweir 					mxDiagramPropertySet->setPropertyValue(LINES, uno::makeAny( sal_False ));
330cdf0e10cSrcweir 					break;
331cdf0e10cSrcweir 				case xlXYScatterLines:
332cdf0e10cSrcweir 				case xlXYScatterLinesNoMarkers:
333cdf0e10cSrcweir 					mxDiagramPropertySet->setPropertyValue(LINES, uno::makeAny( sal_True ));
334cdf0e10cSrcweir 					break;
335cdf0e10cSrcweir 				case xlXYScatterSmooth:
336cdf0e10cSrcweir 				case xlXYScatterSmoothNoMarkers:
337cdf0e10cSrcweir 					mxDiagramPropertySet->setPropertyValue(SPLINETYPE, uno::makeAny( sal_Int32(1)));
338cdf0e10cSrcweir 					break;
339cdf0e10cSrcweir 				default:
340cdf0e10cSrcweir 					break;
341cdf0e10cSrcweir 			}
342cdf0e10cSrcweir 			break;
343cdf0e10cSrcweir 		default:
344cdf0e10cSrcweir 			throw script::BasicErrorException( rtl::OUString(), uno::Reference< uno::XInterface >(), SbERR_CONVERSION, rtl::OUString() );
345cdf0e10cSrcweir 	}
346cdf0e10cSrcweir 
347cdf0e10cSrcweir 	switch (_nChartType)
348cdf0e10cSrcweir 	{
349cdf0e10cSrcweir 		case xlLineMarkers:
350cdf0e10cSrcweir 		case xlLineMarkersStacked:
351cdf0e10cSrcweir 		case xlLineMarkersStacked100:
352cdf0e10cSrcweir 		case xlRadarMarkers:
353cdf0e10cSrcweir 		case xlXYScatterLines:
354cdf0e10cSrcweir 		case xlXYScatterSmooth:
355cdf0e10cSrcweir 		case xlXYScatter:
356cdf0e10cSrcweir 		case xlBubble:                      // not possible
357cdf0e10cSrcweir 		case xlBubble3DEffect:              // not possible
358cdf0e10cSrcweir 			mxDiagramPropertySet->setPropertyValue(SYMBOLTYPE, uno::makeAny( chart::ChartSymbolType::AUTO));
359cdf0e10cSrcweir 			break;
360cdf0e10cSrcweir 		default:
361cdf0e10cSrcweir 			if (mxDiagramPropertySet->getPropertySetInfo()->hasPropertyByName(SYMBOLTYPE))
362cdf0e10cSrcweir 			{
363cdf0e10cSrcweir 				mxDiagramPropertySet->setPropertyValue(SYMBOLTYPE, uno::makeAny(chart::ChartSymbolType::NONE));
364cdf0e10cSrcweir 			}
365cdf0e10cSrcweir 			break;
366cdf0e10cSrcweir 	}
367cdf0e10cSrcweir 
368cdf0e10cSrcweir 	switch (_nChartType)
369cdf0e10cSrcweir 	{
370cdf0e10cSrcweir 		case xlConeCol:
371cdf0e10cSrcweir 		case xlPyramidCol:
372cdf0e10cSrcweir 		case xlCylinderCol:
373cdf0e10cSrcweir 		case xl3DColumn:
374cdf0e10cSrcweir 		case xlSurface:                         // not possible
375cdf0e10cSrcweir 		case xlSurfaceWireframe:
376cdf0e10cSrcweir 		case xlSurfaceTopView:
377cdf0e10cSrcweir 		case xlSurfaceTopViewWireframe:
378cdf0e10cSrcweir 			mxDiagramPropertySet->setPropertyValue(DEEP,uno::makeAny( sal_True ));
379cdf0e10cSrcweir 			break;
380cdf0e10cSrcweir 		default:
381cdf0e10cSrcweir 				if (mxDiagramPropertySet->getPropertySetInfo()->hasPropertyByName(DEEP))
382cdf0e10cSrcweir 				{
383cdf0e10cSrcweir 					mxDiagramPropertySet->setPropertyValue(DEEP, uno::makeAny( sal_False));
384cdf0e10cSrcweir 				}
385cdf0e10cSrcweir 				break;
386cdf0e10cSrcweir 		}
387cdf0e10cSrcweir 
388cdf0e10cSrcweir 
389cdf0e10cSrcweir 		switch (_nChartType)
390cdf0e10cSrcweir 		{
391cdf0e10cSrcweir 				case xlConeColClustered:
392cdf0e10cSrcweir 				case xlConeColStacked:
393cdf0e10cSrcweir 				case xlConeColStacked100:
394cdf0e10cSrcweir 				case xlConeBarClustered:
395cdf0e10cSrcweir 				case xlConeBarStacked:
396cdf0e10cSrcweir 				case xlConeBarStacked100:
397cdf0e10cSrcweir 				case xlConeCol:
398cdf0e10cSrcweir 						mxDiagramPropertySet->setPropertyValue(SOLIDTYPE, uno::makeAny(chart::ChartSolidType::CONE));
399cdf0e10cSrcweir 						break;
400cdf0e10cSrcweir 				case xlPyramidColClustered:
401cdf0e10cSrcweir 				case xlPyramidColStacked:
402cdf0e10cSrcweir 				case xlPyramidColStacked100:
403cdf0e10cSrcweir 				case xlPyramidBarClustered:
404cdf0e10cSrcweir 				case xlPyramidBarStacked:
405cdf0e10cSrcweir 				case xlPyramidBarStacked100:
406cdf0e10cSrcweir 				case xlPyramidCol:
407cdf0e10cSrcweir 						mxDiagramPropertySet->setPropertyValue(SOLIDTYPE, uno::makeAny(chart::ChartSolidType::PYRAMID));
408cdf0e10cSrcweir 						break;
409cdf0e10cSrcweir 				case xlCylinderColClustered:
410cdf0e10cSrcweir 				case xlCylinderColStacked:
411cdf0e10cSrcweir 				case xlCylinderColStacked100:
412cdf0e10cSrcweir 				case xlCylinderBarClustered:
413cdf0e10cSrcweir 				case xlCylinderBarStacked:
414cdf0e10cSrcweir 				case xlCylinderBarStacked100:
415cdf0e10cSrcweir 				case xlCylinderCol:
416cdf0e10cSrcweir 						mxDiagramPropertySet->setPropertyValue(SOLIDTYPE, uno::makeAny(chart::ChartSolidType::CYLINDER));
417cdf0e10cSrcweir 						break;
418cdf0e10cSrcweir 				default:
419cdf0e10cSrcweir 					if (mxDiagramPropertySet->getPropertySetInfo()->hasPropertyByName(SOLIDTYPE))
420cdf0e10cSrcweir 					{
421cdf0e10cSrcweir 							mxDiagramPropertySet->setPropertyValue(SOLIDTYPE, uno::makeAny(chart::ChartSolidType::RECTANGULAR_SOLID));
422cdf0e10cSrcweir 					}
423cdf0e10cSrcweir 					break;
424cdf0e10cSrcweir 		}
425cdf0e10cSrcweir 
426cdf0e10cSrcweir 		switch ( _nChartType)
427cdf0e10cSrcweir 		{
428cdf0e10cSrcweir 			case xlConeCol:
429cdf0e10cSrcweir 			case xlConeColClustered:
430cdf0e10cSrcweir 			case xlConeColStacked:
431cdf0e10cSrcweir 			case xlConeColStacked100:
432cdf0e10cSrcweir 			case xlPyramidColClustered:
433cdf0e10cSrcweir 			case xlPyramidColStacked:
434cdf0e10cSrcweir 			case xlPyramidColStacked100:
435cdf0e10cSrcweir 			case xlCylinderColClustered:
436cdf0e10cSrcweir 			case xlCylinderColStacked:
437cdf0e10cSrcweir 			case xlCylinderColStacked100:
438cdf0e10cSrcweir 			case xlColumnClustered:
439cdf0e10cSrcweir 			case xlColumnStacked:
440cdf0e10cSrcweir 			case xlColumnStacked100:
441cdf0e10cSrcweir 			case xl3DColumnClustered:
442cdf0e10cSrcweir 			case xl3DColumnStacked:
443cdf0e10cSrcweir 			case xl3DColumnStacked100:
444cdf0e10cSrcweir 			case xlSurface: // not possible
445cdf0e10cSrcweir 			case xlSurfaceWireframe:
446cdf0e10cSrcweir 			case xlSurfaceTopView:
447cdf0e10cSrcweir 			case xlSurfaceTopViewWireframe:
448cdf0e10cSrcweir 				mxDiagramPropertySet->setPropertyValue(VERTICAL, uno::makeAny( sal_True));
449cdf0e10cSrcweir 				break;
450cdf0e10cSrcweir 			default:
451cdf0e10cSrcweir 				if (mxDiagramPropertySet->getPropertySetInfo()->hasPropertyByName(VERTICAL))
452cdf0e10cSrcweir 				{
453cdf0e10cSrcweir 					mxDiagramPropertySet->setPropertyValue(VERTICAL, uno::makeAny(sal_False));
454cdf0e10cSrcweir 				}
455cdf0e10cSrcweir 				break;
456cdf0e10cSrcweir 		}
457cdf0e10cSrcweir 
458cdf0e10cSrcweir 		switch (_nChartType)
459cdf0e10cSrcweir 		{
460cdf0e10cSrcweir 			case xlColumnStacked:
461cdf0e10cSrcweir 			case xl3DColumnStacked:
462cdf0e10cSrcweir 			case xlBarStacked:
463cdf0e10cSrcweir 			case xl3DBarStacked:
464cdf0e10cSrcweir 			case xlLineStacked:
465cdf0e10cSrcweir 			case xlLineMarkersStacked:
466cdf0e10cSrcweir 			case xlAreaStacked:
467cdf0e10cSrcweir 			case xl3DAreaStacked:
468cdf0e10cSrcweir 			case xlCylinderColStacked:
469cdf0e10cSrcweir 			case xlCylinderBarStacked:
470cdf0e10cSrcweir 			case xlConeColStacked:
471cdf0e10cSrcweir 			case xlConeBarStacked:
472cdf0e10cSrcweir 			case xlPyramidColStacked:
473cdf0e10cSrcweir 			case xlPyramidBarStacked:
474cdf0e10cSrcweir 				mxDiagramPropertySet->setPropertyValue(PERCENT, uno::makeAny( sal_False ));
475cdf0e10cSrcweir 				mxDiagramPropertySet->setPropertyValue(STACKED, uno::makeAny( sal_True ));
476cdf0e10cSrcweir 				break;
477cdf0e10cSrcweir 			case xlPyramidColStacked100:
478cdf0e10cSrcweir 			case xlPyramidBarStacked100:
479cdf0e10cSrcweir 			case xlConeColStacked100:
480cdf0e10cSrcweir 			case xlConeBarStacked100:
481cdf0e10cSrcweir 			case xlCylinderBarStacked100:
482cdf0e10cSrcweir 			case xlCylinderColStacked100:
483cdf0e10cSrcweir 			case xl3DAreaStacked100:
484cdf0e10cSrcweir 			case xlLineMarkersStacked100:
485cdf0e10cSrcweir 			case xlAreaStacked100:
486cdf0e10cSrcweir 			case xlLineStacked100:
487cdf0e10cSrcweir 			case xl3DBarStacked100:
488cdf0e10cSrcweir 			case xlBarStacked100:
489cdf0e10cSrcweir 			case xl3DColumnStacked100:
490cdf0e10cSrcweir 			case xlColumnStacked100:
491cdf0e10cSrcweir 				mxDiagramPropertySet->setPropertyValue(STACKED, uno::makeAny( sal_True));
492cdf0e10cSrcweir 				mxDiagramPropertySet->setPropertyValue(PERCENT, uno::makeAny( sal_True ));
493cdf0e10cSrcweir 				break;
494cdf0e10cSrcweir 			default:
495cdf0e10cSrcweir 				mxDiagramPropertySet->setPropertyValue(PERCENT, uno::makeAny( sal_False));
496cdf0e10cSrcweir 				mxDiagramPropertySet->setPropertyValue(STACKED, uno::makeAny( sal_False));
497cdf0e10cSrcweir 				break;
498cdf0e10cSrcweir 		}
499cdf0e10cSrcweir 		switch (_nChartType)
500cdf0e10cSrcweir 		{
501cdf0e10cSrcweir 			case xl3DArea:
502cdf0e10cSrcweir 			case xl3DAreaStacked:
503cdf0e10cSrcweir 			case xl3DAreaStacked100:
504cdf0e10cSrcweir 			case xl3DBarClustered:
505cdf0e10cSrcweir 			case xl3DBarStacked:
506cdf0e10cSrcweir 			case xl3DBarStacked100:
507cdf0e10cSrcweir 			case xl3DColumn:
508cdf0e10cSrcweir 			case xl3DColumnClustered:
509cdf0e10cSrcweir 			case xl3DColumnStacked:
510cdf0e10cSrcweir 			case xl3DColumnStacked100:
511cdf0e10cSrcweir 			case xl3DLine:
512cdf0e10cSrcweir 			case xl3DPie:
513cdf0e10cSrcweir 			case xl3DPieExploded:
514cdf0e10cSrcweir 			case xlConeColClustered:
515cdf0e10cSrcweir 			case xlConeColStacked:
516cdf0e10cSrcweir 			case xlConeColStacked100:
517cdf0e10cSrcweir 			case xlConeBarClustered:
518cdf0e10cSrcweir 			case xlConeBarStacked:
519cdf0e10cSrcweir 			case xlConeBarStacked100:
520cdf0e10cSrcweir 			case xlConeCol:
521cdf0e10cSrcweir 			case xlPyramidColClustered:
522cdf0e10cSrcweir 			case xlPyramidColStacked:
523cdf0e10cSrcweir 			case xlPyramidColStacked100:
524cdf0e10cSrcweir 			case xlPyramidBarClustered:
525cdf0e10cSrcweir 			case xlPyramidBarStacked:
526cdf0e10cSrcweir 			case xlPyramidBarStacked100:
527cdf0e10cSrcweir 			case xlPyramidCol:
528cdf0e10cSrcweir 			case xlCylinderColClustered:
529cdf0e10cSrcweir 			case xlCylinderColStacked:
530cdf0e10cSrcweir 			case xlCylinderColStacked100:
531cdf0e10cSrcweir 			case xlCylinderBarClustered:
532cdf0e10cSrcweir 			case xlCylinderBarStacked:
533cdf0e10cSrcweir 			case xlCylinderBarStacked100:
534cdf0e10cSrcweir 			case xlCylinderCol:
535cdf0e10cSrcweir 				mxDiagramPropertySet->setPropertyValue(DIM3D, uno::makeAny( sal_True));
536cdf0e10cSrcweir 				break;
537cdf0e10cSrcweir 			default:
538cdf0e10cSrcweir 				if (mxDiagramPropertySet->getPropertySetInfo()->hasPropertyByName(DIM3D))
539cdf0e10cSrcweir 				{
540cdf0e10cSrcweir 					mxDiagramPropertySet->setPropertyValue(DIM3D, uno::makeAny( sal_False));
541cdf0e10cSrcweir 				}
542cdf0e10cSrcweir 				break;
543cdf0e10cSrcweir 		}
544cdf0e10cSrcweir 	}
545cdf0e10cSrcweir 	catch ( uno::Exception& )
546cdf0e10cSrcweir 	{
547cdf0e10cSrcweir 		throw script::BasicErrorException( rtl::OUString(), uno::Reference< uno::XInterface >(), SbERR_METHOD_FAILED, rtl::OUString() );
548cdf0e10cSrcweir 	}
549cdf0e10cSrcweir }
550cdf0e10cSrcweir 
551cdf0e10cSrcweir void SAL_CALL
Activate()552cdf0e10cSrcweir ScVbaChart::Activate() throw (script::BasicErrorException, uno::RuntimeException)
553cdf0e10cSrcweir {
554cdf0e10cSrcweir 	// #TODO how are Chart sheets handled ( I know we don't even consider
555cdf0e10cSrcweir 	// them in the worksheets/sheets collections ), but.....???
556cdf0e10cSrcweir 	// note: in vba for excel the parent of a Chart sheet is a workbook,
557cdf0e10cSrcweir 	// e.g. 'ThisWorkbook'
558cdf0e10cSrcweir 	uno::Reference< XHelperInterface > xParent( getParent() );
559cdf0e10cSrcweir 	ScVbaChartObject* pChartObj = static_cast< ScVbaChartObject* >( xParent.get() );
560cdf0e10cSrcweir 	if ( pChartObj )
561cdf0e10cSrcweir 		pChartObj->Activate();
562cdf0e10cSrcweir 	else
563cdf0e10cSrcweir 		throw script::BasicErrorException( rtl::OUString(), uno::Reference< uno::XInterface >(), SbERR_METHOD_FAILED, rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( "no ChartObject as parent" ) ) );
564cdf0e10cSrcweir }
565cdf0e10cSrcweir 
566cdf0e10cSrcweir void SAL_CALL
setSourceData(const css::uno::Reference<::ooo::vba::excel::XRange> & _xCalcRange,const css::uno::Any & _aPlotBy)567cdf0e10cSrcweir ScVbaChart::setSourceData( const css::uno::Reference< ::ooo::vba::excel::XRange >& _xCalcRange, const css::uno::Any& _aPlotBy ) throw (css::script::BasicErrorException, css::uno::RuntimeException)
568cdf0e10cSrcweir {
569cdf0e10cSrcweir 	try
570cdf0e10cSrcweir 	{
571cdf0e10cSrcweir 		uno::Sequence< table::CellRangeAddress > mRangeAddresses(1);
572cdf0e10cSrcweir 		table::CellRangeAddress mSingleRangeAddress;
573cdf0e10cSrcweir 
574cdf0e10cSrcweir 		uno::Reference< sheet::XCellRangeAddressable > xAddressable( _xCalcRange->getCellRange(), uno::UNO_QUERY_THROW );
575cdf0e10cSrcweir 		mSingleRangeAddress = xAddressable->getRangeAddress();
576cdf0e10cSrcweir 
577cdf0e10cSrcweir 		mRangeAddresses[0] = mSingleRangeAddress;
578cdf0e10cSrcweir 
579cdf0e10cSrcweir 		mxTableChart->setRanges(mRangeAddresses);
580cdf0e10cSrcweir 
581cdf0e10cSrcweir 		sal_Bool bsetRowHeaders = sal_False;
582cdf0e10cSrcweir 		sal_Bool bsetColumnHeaders = sal_False;
583cdf0e10cSrcweir 
584cdf0e10cSrcweir 		ScVbaRange* pRange = static_cast< ScVbaRange* >( _xCalcRange.get() );
585cdf0e10cSrcweir 		if ( pRange )
586cdf0e10cSrcweir 		{
587cdf0e10cSrcweir 			ScDocument* pDoc = pRange->getScDocument();
588cdf0e10cSrcweir 			if ( pDoc )
589cdf0e10cSrcweir 			{
590cdf0e10cSrcweir 				bsetRowHeaders = pDoc->HasRowHeader(  static_cast< SCCOL >( mSingleRangeAddress.StartColumn ), static_cast< SCROW >( mSingleRangeAddress.StartRow ), static_cast< SCCOL >( mSingleRangeAddress.EndColumn ), static_cast< SCROW >( mSingleRangeAddress.EndRow ), static_cast< SCTAB >( mSingleRangeAddress.Sheet ) );;
591cdf0e10cSrcweir 				bsetColumnHeaders =  pDoc->HasColHeader(  static_cast< SCCOL >( mSingleRangeAddress.StartColumn ), static_cast< SCROW >( mSingleRangeAddress.StartRow ), static_cast< SCCOL >( mSingleRangeAddress.EndColumn ), static_cast< SCROW >( mSingleRangeAddress.EndRow ), static_cast< SCTAB >( mSingleRangeAddress.Sheet ));
592cdf0e10cSrcweir ;
593cdf0e10cSrcweir 			}
594cdf0e10cSrcweir 		}
595cdf0e10cSrcweir 		mxTableChart->setHasRowHeaders(bsetRowHeaders);
596cdf0e10cSrcweir 		mxTableChart->setHasColumnHeaders(bsetColumnHeaders);
597cdf0e10cSrcweir 
598cdf0e10cSrcweir 		if ((!bsetColumnHeaders) || (!bsetRowHeaders))
599cdf0e10cSrcweir 		{
600cdf0e10cSrcweir 			uno::Reference< chart::XChartDataArray > xChartDataArray( mxChartDocument->getData(), uno::UNO_QUERY_THROW );
601cdf0e10cSrcweir 			if (!bsetColumnHeaders)
602cdf0e10cSrcweir 			{
603cdf0e10cSrcweir 				xChartDataArray->setColumnDescriptions( getDefaultSeriesDescriptions(xChartDataArray->getColumnDescriptions().getLength() ));
604cdf0e10cSrcweir 			}
605cdf0e10cSrcweir 			if (!bsetRowHeaders)
606cdf0e10cSrcweir 			{
607cdf0e10cSrcweir 				xChartDataArray->setRowDescriptions(getDefaultSeriesDescriptions(xChartDataArray->getRowDescriptions().getLength() ));
608cdf0e10cSrcweir 			}
609cdf0e10cSrcweir 		}
610cdf0e10cSrcweir 
611cdf0e10cSrcweir 		if ( _aPlotBy.hasValue() )
612cdf0e10cSrcweir 		{
613cdf0e10cSrcweir 			sal_Int32 nVal = 0;
614cdf0e10cSrcweir 			_aPlotBy >>= nVal;
615cdf0e10cSrcweir 			setPlotBy( nVal );
616cdf0e10cSrcweir 		}
617cdf0e10cSrcweir 		else
618cdf0e10cSrcweir 		{
619cdf0e10cSrcweir 			sal_Int32 nRows =  mSingleRangeAddress.EndRow - mSingleRangeAddress.StartRow;
620cdf0e10cSrcweir 			sal_Int32 nCols = mSingleRangeAddress.EndColumn - mSingleRangeAddress.StartColumn;
621cdf0e10cSrcweir 			// AutoDetect emulation
622cdf0e10cSrcweir 			if ( nRows > nCols )
623cdf0e10cSrcweir 				setPlotBy( xlColumns );
624cdf0e10cSrcweir 			else if ( nRows <= nCols )
625cdf0e10cSrcweir 				setPlotBy( xlRows );
626cdf0e10cSrcweir 		}
627cdf0e10cSrcweir 	}
628cdf0e10cSrcweir 	catch (uno::Exception& )
629cdf0e10cSrcweir 	{
630cdf0e10cSrcweir 		throw script::BasicErrorException( rtl::OUString(), uno::Reference< uno::XInterface >(), SbERR_METHOD_FAILED, rtl::OUString() );
631cdf0e10cSrcweir 	}
632cdf0e10cSrcweir }
633cdf0e10cSrcweir 
634cdf0e10cSrcweir uno::Sequence< rtl::OUString >
getDefaultSeriesDescriptions(sal_Int32 _nCount)635cdf0e10cSrcweir ScVbaChart::getDefaultSeriesDescriptions( sal_Int32 _nCount )
636cdf0e10cSrcweir {
637cdf0e10cSrcweir 	uno::Sequence< rtl::OUString > sDescriptions ( _nCount );
638cdf0e10cSrcweir 	sal_Int32 nLen = sDescriptions.getLength();
639cdf0e10cSrcweir 	for (sal_Int32 i = 0; i < nLen; i++)
640cdf0e10cSrcweir 	{
641cdf0e10cSrcweir 		sDescriptions[i] = DEFAULTSERIESPREFIX + rtl::OUString::valueOf(i+1);
642cdf0e10cSrcweir 	}
643cdf0e10cSrcweir 	return sDescriptions;
644cdf0e10cSrcweir }
645cdf0e10cSrcweir 
646cdf0e10cSrcweir void
setDefaultChartType()647cdf0e10cSrcweir ScVbaChart::setDefaultChartType() throw ( script::BasicErrorException )
648cdf0e10cSrcweir {
649cdf0e10cSrcweir 	setChartType( xlColumnClustered );
650cdf0e10cSrcweir }
651cdf0e10cSrcweir 
652cdf0e10cSrcweir void
setPlotBy(::sal_Int32 _nPlotBy)653cdf0e10cSrcweir ScVbaChart::setPlotBy( ::sal_Int32 _nPlotBy ) throw (css::script::BasicErrorException, css::uno::RuntimeException)
654cdf0e10cSrcweir {
655cdf0e10cSrcweir 	try
656cdf0e10cSrcweir 	{
657cdf0e10cSrcweir 		if ( !mxDiagramPropertySet.is() )
658cdf0e10cSrcweir 			setDefaultChartType();
659cdf0e10cSrcweir 		switch (_nPlotBy)
660cdf0e10cSrcweir 		{
661cdf0e10cSrcweir 			case xlRows:
662cdf0e10cSrcweir 				mxDiagramPropertySet->setPropertyValue( DATAROWSOURCE,  uno::makeAny( chart::ChartDataRowSource_ROWS ) );
663cdf0e10cSrcweir 				break;
664cdf0e10cSrcweir 			case xlColumns:
665cdf0e10cSrcweir 				mxDiagramPropertySet->setPropertyValue( DATAROWSOURCE, uno::makeAny( chart::ChartDataRowSource_COLUMNS) );
666cdf0e10cSrcweir 				break;
667cdf0e10cSrcweir 			default:
668cdf0e10cSrcweir 				throw script::BasicErrorException( rtl::OUString(), uno::Reference< uno::XInterface >(), SbERR_METHOD_FAILED, rtl::OUString() );
669cdf0e10cSrcweir 		}
670cdf0e10cSrcweir 	}
671cdf0e10cSrcweir 	catch (uno::Exception& )
672cdf0e10cSrcweir 	{
673cdf0e10cSrcweir 		throw script::BasicErrorException( rtl::OUString(), uno::Reference< uno::XInterface >(), SbERR_METHOD_FAILED, rtl::OUString() );
674cdf0e10cSrcweir 	}
675cdf0e10cSrcweir }
676cdf0e10cSrcweir 
677cdf0e10cSrcweir ::sal_Int32 SAL_CALL
getPlotBy()678cdf0e10cSrcweir ScVbaChart::getPlotBy(  ) throw (script::BasicErrorException, uno::RuntimeException)
679cdf0e10cSrcweir {
680cdf0e10cSrcweir 	try
681cdf0e10cSrcweir 	{
682cdf0e10cSrcweir 		chart::ChartDataRowSource aChartDataRowSource;
683cdf0e10cSrcweir 		mxDiagramPropertySet->getPropertyValue(DATAROWSOURCE) >>= aChartDataRowSource;
684cdf0e10cSrcweir 		if (aChartDataRowSource == chart::ChartDataRowSource_COLUMNS)
685cdf0e10cSrcweir 		{
686cdf0e10cSrcweir 			return xlColumns;
687cdf0e10cSrcweir 		}
688cdf0e10cSrcweir 		else
689cdf0e10cSrcweir 		{
690cdf0e10cSrcweir 			return xlRows;
691cdf0e10cSrcweir 		}
692cdf0e10cSrcweir 	}
693cdf0e10cSrcweir 	catch (uno::Exception& )
694cdf0e10cSrcweir 	{
695cdf0e10cSrcweir 		throw script::BasicErrorException( rtl::OUString(), uno::Reference< uno::XInterface >(), SbERR_METHOD_FAILED, rtl::OUString() );
696cdf0e10cSrcweir 	}
697cdf0e10cSrcweir }
698cdf0e10cSrcweir 
699cdf0e10cSrcweir void
setDiagram(const rtl::OUString & _sDiagramType)700cdf0e10cSrcweir ScVbaChart::setDiagram( const rtl::OUString& _sDiagramType ) throw( script::BasicErrorException )
701cdf0e10cSrcweir {
702cdf0e10cSrcweir 	try
703cdf0e10cSrcweir 	{
704cdf0e10cSrcweir 		uno::Reference< lang::XMultiServiceFactory > xMSF( mxChartDocument, uno::UNO_QUERY_THROW );
705cdf0e10cSrcweir 		uno::Reference< chart::XDiagram > xDiagram( xMSF->createInstance( _sDiagramType ), uno::UNO_QUERY_THROW  );
706cdf0e10cSrcweir 		mxChartDocument->setDiagram( xDiagram );
707cdf0e10cSrcweir 		mxDiagramPropertySet.set( xDiagram, uno::UNO_QUERY_THROW );
708cdf0e10cSrcweir 	}
709cdf0e10cSrcweir 	catch ( uno::Exception& )
710cdf0e10cSrcweir 	{
711cdf0e10cSrcweir 		throw script::BasicErrorException( rtl::OUString(), uno::Reference< uno::XInterface >(), SbERR_METHOD_FAILED, rtl::OUString() );
712cdf0e10cSrcweir 	}
713cdf0e10cSrcweir }
714cdf0e10cSrcweir 
715cdf0e10cSrcweir // #TODO find out why we have Location/getLocation ? there is afaiks no
716cdf0e10cSrcweir // Location property, just a Location function for the Chart object
717cdf0e10cSrcweir sal_Int32 SAL_CALL
Location()718cdf0e10cSrcweir ScVbaChart::Location() throw (css::script::BasicErrorException, css::uno::RuntimeException)
719cdf0e10cSrcweir {
720cdf0e10cSrcweir 	return getLocation();
721cdf0e10cSrcweir }
722cdf0e10cSrcweir 
723cdf0e10cSrcweir sal_Int32 SAL_CALL
getLocation()724cdf0e10cSrcweir ScVbaChart::getLocation() throw (css::script::BasicErrorException, css::uno::RuntimeException)
725cdf0e10cSrcweir {
726cdf0e10cSrcweir 	 return -1;
727cdf0e10cSrcweir }
728cdf0e10cSrcweir 
729cdf0e10cSrcweir void SAL_CALL
setLocation(::sal_Int32,const css::uno::Any &)730cdf0e10cSrcweir ScVbaChart::setLocation( ::sal_Int32 /*where*/, const css::uno::Any& /*Name*/ ) throw (script::BasicErrorException, uno::RuntimeException)
731cdf0e10cSrcweir {
732cdf0e10cSrcweir 	// Helper api just stubs out the code <shrug>
733cdf0e10cSrcweir 	// #TODO come back and make sense out of this
734cdf0e10cSrcweir //        String sheetName = null;
735cdf0e10cSrcweir //
736cdf0e10cSrcweir //        if ((name != null) && name instanceof String) {
737cdf0e10cSrcweir //            sheetName = (String) name;
738cdf0e10cSrcweir //        }
739cdf0e10cSrcweir //        XSpreadsheetDocument xShDoc = (XSpreadsheetDocument) UnoRuntime.queryInterface( XSpreadsheetDocument.class,getXModel() );
740cdf0e10cSrcweir //        com.sun.star.sheet.XSpreadsheets xSheets = xShDoc.Sheets();
741cdf0e10cSrcweir //
742cdf0e10cSrcweir //        switch (where) {
743cdf0e10cSrcweir //        case ClLocationType.clLocationAsObject_value: //{
744cdf0e10cSrcweir //
745cdf0e10cSrcweir //            if (sheetName == null) {
746cdf0e10cSrcweir //                DebugHelper.writeInfo("Can't embed in Chart without knowing SheetName");
747cdf0e10cSrcweir //                return;
748cdf0e10cSrcweir //            }
749cdf0e10cSrcweir //
750cdf0e10cSrcweir //            try {
751cdf0e10cSrcweir //                Any any = (Any) xSheets.getByName(sheetName);
752cdf0e10cSrcweir //                chartSheet = (XSpreadsheet) any.getObject();
753cdf0e10cSrcweir //
754cdf0e10cSrcweir //                // chartSheet = (XSpreadsheet) xSheets.getByName( sheetName );
755cdf0e10cSrcweir //            } catch (NoSuchElementException e) {
756cdf0e10cSrcweir //                // TODO Auto-generated catch block
757cdf0e10cSrcweir //                e.printStackTrace();
758cdf0e10cSrcweir //
759cdf0e10cSrcweir //                return;
760cdf0e10cSrcweir //            } catch (WrappedTargetException e) {
761cdf0e10cSrcweir //                // TODO Auto-generated catch block
762cdf0e10cSrcweir //                e.printStackTrace();
763cdf0e10cSrcweir //
764cdf0e10cSrcweir //                return;
765cdf0e10cSrcweir //            } catch (java.lang.Exception e) {
766cdf0e10cSrcweir //                e.printStackTrace();
767cdf0e10cSrcweir //            }
768cdf0e10cSrcweir //
769cdf0e10cSrcweir //            XTableChartsSupplier xTCS = (XTableChartsSupplier) UnoRuntime.queryInterface( XTableChartsSupplier.class, chartSheet);
770cdf0e10cSrcweir //            XTableCharts xTableCharts = xTCS.getCharts();
771cdf0e10cSrcweir //            XIndexAccess xIA = (XIndexAccess) UnoRuntime.queryInterface( XIndexAccess.class, xTableCharts);
772cdf0e10cSrcweir //            int numCharts = xIA.getCount();
773cdf0e10cSrcweir //            chartName = "Chart " + (numCharts + 1);
774cdf0e10cSrcweir //
775cdf0e10cSrcweir //            //}
776cdf0e10cSrcweir //            break;
777cdf0e10cSrcweir //
778cdf0e10cSrcweir //        case ClLocationType.clLocationAsNewSheet_value:
779cdf0e10cSrcweir //        case ClLocationType.clLocationAutomatic_value:default: //{
780cdf0e10cSrcweir //            chartName = "Chart 1"; // Since it's a new sheet, it's the first on it...
781cdf0e10cSrcweir //
782cdf0e10cSrcweir //            XIndexAccess xSheetIA = (XIndexAccess) UnoRuntime.queryInterface( XIndexAccess.class, xSheets);
783cdf0e10cSrcweir //
784cdf0e10cSrcweir //            short newSheetNum = (short) (xSheetIA.getCount() + 1);
785cdf0e10cSrcweir //
786cdf0e10cSrcweir //            if (sheetName == null){
787cdf0e10cSrcweir //                sheetName = "ChartSheet " + newSheetNum; // Why not?
788cdf0e10cSrcweir //            }
789cdf0e10cSrcweir //            // DPK TODO : Probably should use Sheets to create this!
790cdf0e10cSrcweir //            xSheets.insertNewByName(sheetName, newSheetNum);
791cdf0e10cSrcweir //
792cdf0e10cSrcweir //            try {
793cdf0e10cSrcweir //                chartSheet =
794cdf0e10cSrcweir //                    (XSpreadsheet) xSheets.getByName(sheetName);
795cdf0e10cSrcweir //            } catch (NoSuchElementException e) {
796cdf0e10cSrcweir //                // TODO Auto-generated catch block
797cdf0e10cSrcweir //                e.printStackTrace();
798cdf0e10cSrcweir //
799cdf0e10cSrcweir //                return;
800cdf0e10cSrcweir //            } catch (WrappedTargetException e) {
801cdf0e10cSrcweir //                // TODO Auto-generated catch block
802cdf0e10cSrcweir //                e.printStackTrace();
803cdf0e10cSrcweir //
804cdf0e10cSrcweir //                return;
805cdf0e10cSrcweir //            }
806cdf0e10cSrcweir //
807cdf0e10cSrcweir //            //}
808cdf0e10cSrcweir //            break;
809cdf0e10cSrcweir //        }
810cdf0e10cSrcweir //
811cdf0e10cSrcweir //        // Last thing should be a call to createChartForReal(), one of them
812cdf0e10cSrcweir //        // should succeed.
813cdf0e10cSrcweir //        createChartForReal();
814cdf0e10cSrcweir 
815cdf0e10cSrcweir }
816cdf0e10cSrcweir 
817cdf0e10cSrcweir sal_Bool SAL_CALL
getHasTitle()818cdf0e10cSrcweir ScVbaChart::getHasTitle(  ) throw (script::BasicErrorException, uno::RuntimeException)
819cdf0e10cSrcweir {
820cdf0e10cSrcweir 	sal_Bool bHasTitle = sal_False;
821cdf0e10cSrcweir 	try
822cdf0e10cSrcweir 	{
823cdf0e10cSrcweir 		mxChartPropertySet->getPropertyValue(HASMAINTITLE) >>= bHasTitle;
824cdf0e10cSrcweir 	}
825cdf0e10cSrcweir 	catch (uno::Exception& )
826cdf0e10cSrcweir 	{
827cdf0e10cSrcweir 		throw script::BasicErrorException( rtl::OUString(), uno::Reference< uno::XInterface >(), SbERR_METHOD_FAILED, rtl::OUString() );
828cdf0e10cSrcweir 	}
829cdf0e10cSrcweir 	return bHasTitle;
830cdf0e10cSrcweir }
831cdf0e10cSrcweir 
832cdf0e10cSrcweir void SAL_CALL
setHasTitle(::sal_Bool bTitle)833cdf0e10cSrcweir ScVbaChart::setHasTitle( ::sal_Bool bTitle ) throw (script::BasicErrorException, uno::RuntimeException)
834cdf0e10cSrcweir {
835cdf0e10cSrcweir 	try
836cdf0e10cSrcweir 	{
837cdf0e10cSrcweir 		mxChartPropertySet->setPropertyValue(HASMAINTITLE, uno::makeAny( bTitle ));
838cdf0e10cSrcweir 	}
839cdf0e10cSrcweir 	catch (uno::Exception& )
840cdf0e10cSrcweir 	{
841cdf0e10cSrcweir 		throw script::BasicErrorException( rtl::OUString(), uno::Reference< uno::XInterface >(), SbERR_METHOD_FAILED, rtl::OUString() );
842cdf0e10cSrcweir 	}
843cdf0e10cSrcweir 
844cdf0e10cSrcweir }
845cdf0e10cSrcweir 
846cdf0e10cSrcweir ::sal_Bool SAL_CALL
getHasLegend()847cdf0e10cSrcweir ScVbaChart::getHasLegend(  ) throw (script::BasicErrorException, uno::RuntimeException)
848cdf0e10cSrcweir {
849cdf0e10cSrcweir 	sal_Bool bHasLegend = sal_False;
850cdf0e10cSrcweir 	try
851cdf0e10cSrcweir 	{
852cdf0e10cSrcweir 		mxChartPropertySet->getPropertyValue(HASLEGEND) >>= bHasLegend;
853cdf0e10cSrcweir 	}
854cdf0e10cSrcweir 	catch (uno::Exception& )
855cdf0e10cSrcweir 	{
856cdf0e10cSrcweir 		throw script::BasicErrorException( rtl::OUString(), uno::Reference< uno::XInterface >(), SbERR_METHOD_FAILED, rtl::OUString() );
857cdf0e10cSrcweir 	}
858cdf0e10cSrcweir 	return bHasLegend;
859cdf0e10cSrcweir }
860cdf0e10cSrcweir 
861cdf0e10cSrcweir void SAL_CALL
setHasLegend(::sal_Bool bLegend)862cdf0e10cSrcweir ScVbaChart::setHasLegend( ::sal_Bool bLegend ) throw (script::BasicErrorException, uno::RuntimeException)
863cdf0e10cSrcweir {
864cdf0e10cSrcweir 	try
865cdf0e10cSrcweir 	{
866cdf0e10cSrcweir 		mxChartPropertySet->setPropertyValue(HASLEGEND, uno::makeAny(bLegend));
867cdf0e10cSrcweir 	}
868cdf0e10cSrcweir 	catch (uno::Exception& )
869cdf0e10cSrcweir 	{
870cdf0e10cSrcweir 		throw script::BasicErrorException( rtl::OUString(), uno::Reference< uno::XInterface >(), SbERR_METHOD_FAILED, rtl::OUString() );
871cdf0e10cSrcweir 	}
872cdf0e10cSrcweir }
873cdf0e10cSrcweir 
874cdf0e10cSrcweir uno::Reference< excel::XChartTitle > SAL_CALL
getChartTitle()875cdf0e10cSrcweir ScVbaChart::getChartTitle(  ) throw (script::BasicErrorException, uno::RuntimeException)
876cdf0e10cSrcweir {
877cdf0e10cSrcweir 	uno::Reference< drawing::XShape > xTitleShape = mxChartDocument->getTitle();
878cdf0e10cSrcweir 	// #TODO check parent
879cdf0e10cSrcweir 	return new ScVbaChartTitle(this, mxContext, xTitleShape);
880cdf0e10cSrcweir }
881cdf0e10cSrcweir 
882cdf0e10cSrcweir uno::Any SAL_CALL
Axes(const uno::Any & Type,const uno::Any & AxisGroup)883cdf0e10cSrcweir ScVbaChart::Axes( const uno::Any& Type, const uno::Any& AxisGroup ) throw (script::BasicErrorException, uno::RuntimeException)
884cdf0e10cSrcweir {
885cdf0e10cSrcweir 	// mmm chart probably is the parent, #TODO check parent
886cdf0e10cSrcweir 	uno::Reference< excel::XAxes > xAxes = new ScVbaAxes( this, mxContext, this );
887cdf0e10cSrcweir 	if ( !Type.hasValue() )
888cdf0e10cSrcweir 		return uno::makeAny( xAxes );
889cdf0e10cSrcweir 	return xAxes->Item( Type, AxisGroup );
890cdf0e10cSrcweir }
891cdf0e10cSrcweir bool
is3D()892cdf0e10cSrcweir ScVbaChart::is3D() throw ( uno::RuntimeException )
893cdf0e10cSrcweir {
894cdf0e10cSrcweir 	// #TODO perhaps provide limited Debughelper functionality
895cdf0e10cSrcweir 	sal_Bool is3d = sal_False;
896cdf0e10cSrcweir 	mxDiagramPropertySet->getPropertyValue(DIM3D) >>= is3d;
897cdf0e10cSrcweir 	return is3d;
898cdf0e10cSrcweir }
899cdf0e10cSrcweir 
900cdf0e10cSrcweir sal_Int32
getStackedType(sal_Int32 _nStacked,sal_Int32 _n100PercentStacked,sal_Int32 _nUnStacked)901cdf0e10cSrcweir ScVbaChart::getStackedType( sal_Int32 _nStacked, sal_Int32 _n100PercentStacked, sal_Int32 _nUnStacked ) throw ( uno::RuntimeException )
902cdf0e10cSrcweir {
903cdf0e10cSrcweir 	// #TODO perhaps provide limited Debughelper functionality
904cdf0e10cSrcweir 	if (isStacked())
905cdf0e10cSrcweir 	{
906cdf0e10cSrcweir 		if (is100PercentStacked())
907cdf0e10cSrcweir 			return _n100PercentStacked;
908cdf0e10cSrcweir 		else
909cdf0e10cSrcweir 			return _nStacked;
910cdf0e10cSrcweir 	}
911cdf0e10cSrcweir 	else
912cdf0e10cSrcweir 		return _nUnStacked;
913cdf0e10cSrcweir }
914cdf0e10cSrcweir 
915cdf0e10cSrcweir bool
isStacked()916cdf0e10cSrcweir ScVbaChart::isStacked() throw ( uno::RuntimeException )
917cdf0e10cSrcweir {
918cdf0e10cSrcweir 	// #TODO perhaps provide limited Debughelper functionality
919cdf0e10cSrcweir 	sal_Bool bStacked = sal_False;
920cdf0e10cSrcweir 	mxDiagramPropertySet->getPropertyValue(STACKED) >>= bStacked;
921cdf0e10cSrcweir 	return bStacked;
922cdf0e10cSrcweir }
923cdf0e10cSrcweir 
924cdf0e10cSrcweir bool
is100PercentStacked()925cdf0e10cSrcweir ScVbaChart::is100PercentStacked() throw ( uno::RuntimeException )
926cdf0e10cSrcweir {
927cdf0e10cSrcweir 	// #TODO perhaps provide limited Debughelper functionality
928cdf0e10cSrcweir 	sal_Bool b100Percent = sal_False;
929cdf0e10cSrcweir 	mxDiagramPropertySet->getPropertyValue(PERCENT) >>= b100Percent;
930cdf0e10cSrcweir 	return b100Percent;
931cdf0e10cSrcweir }
932cdf0e10cSrcweir 
933cdf0e10cSrcweir sal_Int32
getSolidType(sal_Int32 _nDeep,sal_Int32 _nVertiStacked,sal_Int32 _nVerti100PercentStacked,sal_Int32 _nVertiUnStacked,sal_Int32 _nHoriStacked,sal_Int32 _nHori100PercentStacked,sal_Int32 _nHoriUnStacked)934cdf0e10cSrcweir ScVbaChart::getSolidType(sal_Int32 _nDeep, sal_Int32 _nVertiStacked, sal_Int32 _nVerti100PercentStacked, sal_Int32 _nVertiUnStacked, sal_Int32 _nHoriStacked, sal_Int32 _nHori100PercentStacked, sal_Int32 _nHoriUnStacked) throw ( script::BasicErrorException )
935cdf0e10cSrcweir {
936cdf0e10cSrcweir 	sal_Bool bIsVertical = true;
937cdf0e10cSrcweir 	try
938cdf0e10cSrcweir 	{
939cdf0e10cSrcweir 		mxDiagramPropertySet->getPropertyValue(VERTICAL) >>= bIsVertical;
940cdf0e10cSrcweir 		sal_Bool bIsDeep = false;
941cdf0e10cSrcweir 		mxDiagramPropertySet->getPropertyValue(DEEP) >>= bIsDeep;
942cdf0e10cSrcweir 
943cdf0e10cSrcweir 		if (bIsDeep)
944cdf0e10cSrcweir 		{
945cdf0e10cSrcweir 			return _nDeep;
946cdf0e10cSrcweir 		}
947cdf0e10cSrcweir 		else
948cdf0e10cSrcweir 		{
949cdf0e10cSrcweir 			if (bIsVertical)
950cdf0e10cSrcweir 			{
951cdf0e10cSrcweir 				return getStackedType(_nVertiStacked, _nVerti100PercentStacked, _nVertiUnStacked);
952cdf0e10cSrcweir 			}
953cdf0e10cSrcweir 			else
954cdf0e10cSrcweir 			{
955cdf0e10cSrcweir 				return getStackedType(_nHoriStacked, _nHori100PercentStacked, _nHoriUnStacked);
956cdf0e10cSrcweir 			}
957cdf0e10cSrcweir 		}
958cdf0e10cSrcweir 	}
959cdf0e10cSrcweir 	catch (uno::Exception& )
960cdf0e10cSrcweir 	{
961cdf0e10cSrcweir 		throw script::BasicErrorException( rtl::OUString(), uno::Reference< uno::XInterface >(), SbERR_METHOD_FAILED, rtl::OUString() );
962cdf0e10cSrcweir 	}
963cdf0e10cSrcweir }
964cdf0e10cSrcweir 
965cdf0e10cSrcweir 
966cdf0e10cSrcweir sal_Int32
getStockUpDownValue(sal_Int32 _nUpDown,sal_Int32 _nNotUpDown)967cdf0e10cSrcweir ScVbaChart::getStockUpDownValue(sal_Int32 _nUpDown, sal_Int32 _nNotUpDown) throw (script::BasicErrorException)
968cdf0e10cSrcweir {
969cdf0e10cSrcweir 	sal_Bool bUpDown = sal_False;
970cdf0e10cSrcweir 	try
971cdf0e10cSrcweir 	{
972cdf0e10cSrcweir 		mxDiagramPropertySet->getPropertyValue(UPDOWN) >>= bUpDown;
973cdf0e10cSrcweir 		if (bUpDown)
974cdf0e10cSrcweir 		{
975cdf0e10cSrcweir 			return _nUpDown;
976cdf0e10cSrcweir 		}
977cdf0e10cSrcweir 		else
978cdf0e10cSrcweir 		{
979cdf0e10cSrcweir 			return _nNotUpDown;
980cdf0e10cSrcweir 		}
981cdf0e10cSrcweir 	}
982cdf0e10cSrcweir 	catch (uno::Exception& )
983cdf0e10cSrcweir 	{
984cdf0e10cSrcweir         rtl::OUString aTemp;    // temporary needed for g++ 3.3.5
985cdf0e10cSrcweir 		script::BasicErrorException( aTemp, uno::Reference< uno::XInterface >(), SbERR_METHOD_FAILED, rtl::OUString() );
986cdf0e10cSrcweir 	}
987cdf0e10cSrcweir 	return _nNotUpDown;
988cdf0e10cSrcweir }
989cdf0e10cSrcweir 
990cdf0e10cSrcweir bool
hasMarkers()991cdf0e10cSrcweir ScVbaChart::hasMarkers() throw ( script::BasicErrorException )
992cdf0e10cSrcweir {
993cdf0e10cSrcweir 	bool bHasMarkers = false;
994cdf0e10cSrcweir 	try
995cdf0e10cSrcweir 	{
996cdf0e10cSrcweir 		sal_Int32 nSymbol=0;
997cdf0e10cSrcweir 		mxDiagramPropertySet->getPropertyValue(SYMBOLTYPE) >>= nSymbol;
998cdf0e10cSrcweir 		bHasMarkers = nSymbol != chart::ChartSymbolType::NONE;
999cdf0e10cSrcweir 	}
1000cdf0e10cSrcweir 	catch ( uno::Exception& )
1001cdf0e10cSrcweir 	{
1002cdf0e10cSrcweir         rtl::OUString aTemp;    // temporary needed for g++ 3.3.5
1003cdf0e10cSrcweir 		script::BasicErrorException( aTemp, uno::Reference< uno::XInterface >(), SbERR_METHOD_FAILED, rtl::OUString() );
1004cdf0e10cSrcweir 	}
1005cdf0e10cSrcweir 	return bHasMarkers;
1006cdf0e10cSrcweir }
1007cdf0e10cSrcweir 
1008cdf0e10cSrcweir sal_Int32
getMarkerType(sal_Int32 _nWithMarkers,sal_Int32 _nWithoutMarkers)1009cdf0e10cSrcweir ScVbaChart::getMarkerType(sal_Int32 _nWithMarkers, sal_Int32 _nWithoutMarkers) throw ( script::BasicErrorException )
1010cdf0e10cSrcweir {
1011cdf0e10cSrcweir 	if (hasMarkers())
1012cdf0e10cSrcweir 		return _nWithMarkers;
1013cdf0e10cSrcweir 	return _nWithoutMarkers;
1014cdf0e10cSrcweir }
1015cdf0e10cSrcweir 
1016cdf0e10cSrcweir void
assignDiagramAttributes()1017cdf0e10cSrcweir ScVbaChart::assignDiagramAttributes()
1018cdf0e10cSrcweir {
1019cdf0e10cSrcweir 	xAxisXSupplier.set( mxDiagramPropertySet, uno::UNO_QUERY_THROW );
1020cdf0e10cSrcweir 	xAxisYSupplier.set( mxDiagramPropertySet, uno::UNO_QUERY_THROW );
1021cdf0e10cSrcweir 	xAxisZSupplier.set( mxDiagramPropertySet, uno::UNO_QUERY_THROW );
1022cdf0e10cSrcweir 	xTwoAxisXSupplier.set( mxDiagramPropertySet, uno::UNO_QUERY_THROW );
1023cdf0e10cSrcweir 	xTwoAxisYSupplier.set( mxDiagramPropertySet, uno::UNO_QUERY_THROW );
1024cdf0e10cSrcweir }
1025cdf0e10cSrcweir 
1026cdf0e10cSrcweir bool
isSeriesIndexValid(sal_Int32 _seriesindex)1027cdf0e10cSrcweir ScVbaChart::isSeriesIndexValid(sal_Int32 _seriesindex) throw( script::BasicErrorException )
1028cdf0e10cSrcweir {
1029cdf0e10cSrcweir 	bool bret = false;
1030cdf0e10cSrcweir 	try
1031cdf0e10cSrcweir 	{
1032cdf0e10cSrcweir 		uno::Reference< chart::XChartDataArray > xChartDataArray( mxChartDocument->getData(), uno::UNO_QUERY_THROW );
1033cdf0e10cSrcweir 		//        dblValues = xChartDataArray.getData();
1034cdf0e10cSrcweir 		//TODO I guess we have to differentiate between XlRowCol
1035cdf0e10cSrcweir 		if ( !xChartDataArray.is() )
1036cdf0e10cSrcweir 		{
1037cdf0e10cSrcweir 			if (getPlotBy() == xlRows)
1038cdf0e10cSrcweir 			{
1039cdf0e10cSrcweir 				if ((_seriesindex < xChartDataArray->getRowDescriptions().getLength() ) && (_seriesindex >= 0))
1040cdf0e10cSrcweir 					bret = true;
1041cdf0e10cSrcweir 			}
1042cdf0e10cSrcweir 			else
1043cdf0e10cSrcweir 			{
1044cdf0e10cSrcweir 				if ((_seriesindex < xChartDataArray->getColumnDescriptions().getLength() ) && (_seriesindex >= 0))
1045cdf0e10cSrcweir 					bret = true;
1046cdf0e10cSrcweir 			}
1047cdf0e10cSrcweir 		}
1048cdf0e10cSrcweir 	}
1049cdf0e10cSrcweir 	catch (uno::Exception& )
1050cdf0e10cSrcweir 	{
1051cdf0e10cSrcweir 		throw script::BasicErrorException( rtl::OUString(), uno::Reference< uno::XInterface >(), SbERR_METHOD_FAILED, rtl::OUString() );
1052cdf0e10cSrcweir 	}
1053cdf0e10cSrcweir 	if (!bret)
1054cdf0e10cSrcweir 	{
1055cdf0e10cSrcweir 		throw script::BasicErrorException( rtl::OUString(), uno::Reference< uno::XInterface >(), SbERR_OUT_OF_RANGE, rtl::OUString() );
1056cdf0e10cSrcweir 	}
1057cdf0e10cSrcweir 	return bret;
1058cdf0e10cSrcweir }
1059cdf0e10cSrcweir 
1060cdf0e10cSrcweir bool
areIndicesValid(sal_Int32 _seriesindex,sal_Int32 _valindex)1061cdf0e10cSrcweir ScVbaChart::areIndicesValid( sal_Int32 _seriesindex, sal_Int32 _valindex) throw ( css::script::BasicErrorException )
1062cdf0e10cSrcweir {
1063cdf0e10cSrcweir 	if (isSeriesIndexValid(_seriesindex))
1064cdf0e10cSrcweir 	{
1065cdf0e10cSrcweir 		uno::Reference< chart::XChartDataArray > xChartDataArray( mxChartDocument->getData(), uno::UNO_QUERY_THROW );
1066cdf0e10cSrcweir 		dblValues = xChartDataArray->getData();
1067cdf0e10cSrcweir 		return (_valindex < dblValues[_seriesindex].getLength() );
1068cdf0e10cSrcweir         }
1069cdf0e10cSrcweir 	return false;
1070cdf0e10cSrcweir }
1071cdf0e10cSrcweir 
1072cdf0e10cSrcweir sal_Int32
getSeriesIndex(rtl::OUString _sseriesname)1073cdf0e10cSrcweir ScVbaChart::getSeriesIndex(rtl::OUString _sseriesname) throw ( script::BasicErrorException )
1074cdf0e10cSrcweir {
1075cdf0e10cSrcweir 	uno::Reference< chart::XChartDataArray > xChartDataArray( mxChartDocument->getData(), uno::UNO_QUERY_THROW );
1076cdf0e10cSrcweir 	if (getPlotBy() == xlRows)
1077cdf0e10cSrcweir 		return ContainerUtilities::FieldInList(xChartDataArray->getRowDescriptions(), _sseriesname);
1078cdf0e10cSrcweir 	return ContainerUtilities::FieldInList(xChartDataArray->getColumnDescriptions(), _sseriesname);
1079cdf0e10cSrcweir }
1080cdf0e10cSrcweir void
setSeriesName(sal_Int32 _index,rtl::OUString _sname)1081cdf0e10cSrcweir ScVbaChart::setSeriesName(sal_Int32 _index, rtl::OUString _sname) throw ( script::BasicErrorException )
1082cdf0e10cSrcweir {
1083cdf0e10cSrcweir 	uno::Reference< chart::XChartDataArray > xChartDataArray( mxChartDocument->getData(), uno::UNO_QUERY_THROW );
1084cdf0e10cSrcweir 	if (isSeriesIndexValid(_index))
1085cdf0e10cSrcweir 	{
1086cdf0e10cSrcweir 		uno::Sequence< rtl::OUString > sDescriptions = xChartDataArray->getColumnDescriptions();
1087cdf0e10cSrcweir 		sDescriptions[_index] = _sname;
1088cdf0e10cSrcweir 		xChartDataArray->setColumnDescriptions(sDescriptions);
1089cdf0e10cSrcweir 	}
1090cdf0e10cSrcweir }
1091cdf0e10cSrcweir 
1092cdf0e10cSrcweir sal_Int32
getSeriesCount()1093cdf0e10cSrcweir ScVbaChart::getSeriesCount() throw ( script::BasicErrorException )
1094cdf0e10cSrcweir {
1095cdf0e10cSrcweir 	uno::Reference< chart::XChartDataArray > xChartDataArray( mxChartDocument->getData(), uno::UNO_QUERY_THROW );
1096cdf0e10cSrcweir 
1097cdf0e10cSrcweir 	if (getPlotBy() == xlRows)
1098cdf0e10cSrcweir 		return xChartDataArray->getRowDescriptions().getLength();
1099cdf0e10cSrcweir 	return xChartDataArray->getColumnDescriptions().getLength();
1100cdf0e10cSrcweir 
1101cdf0e10cSrcweir }
1102cdf0e10cSrcweir 
1103cdf0e10cSrcweir rtl::OUString
getSeriesName(sal_Int32 _index)1104cdf0e10cSrcweir ScVbaChart::getSeriesName(sal_Int32 _index) throw ( script::BasicErrorException )
1105cdf0e10cSrcweir {
1106cdf0e10cSrcweir 	uno::Reference< chart::XChartDataArray > xChartDataArray( mxChartDocument->getData(), uno::UNO_QUERY_THROW );
1107cdf0e10cSrcweir         uno::Sequence< rtl::OUString > sDescriptions;
1108cdf0e10cSrcweir 	rtl::OUString sName;
1109cdf0e10cSrcweir 	if (isSeriesIndexValid(_index))
1110cdf0e10cSrcweir 	{
1111cdf0e10cSrcweir 		if (getPlotBy() == xlRows)
1112cdf0e10cSrcweir 			sDescriptions = xChartDataArray->getRowDescriptions();
1113cdf0e10cSrcweir 		else
1114cdf0e10cSrcweir 			sDescriptions = xChartDataArray->getColumnDescriptions();
1115cdf0e10cSrcweir 		sName =  sDescriptions[_index];
1116cdf0e10cSrcweir         }
1117cdf0e10cSrcweir         return sName;
1118cdf0e10cSrcweir }
1119cdf0e10cSrcweir 
1120cdf0e10cSrcweir double
getValue(sal_Int32 _seriesindex,sal_Int32 _valindex)1121cdf0e10cSrcweir ScVbaChart::getValue(sal_Int32 _seriesindex, sal_Int32 _valindex) throw ( script::BasicErrorException )
1122cdf0e10cSrcweir {
1123cdf0e10cSrcweir 	double result = -1.0;
1124cdf0e10cSrcweir 	if (areIndicesValid(_seriesindex, _valindex))
1125cdf0e10cSrcweir 	{
1126cdf0e10cSrcweir 		if (getPlotBy() == xlRows)
1127cdf0e10cSrcweir 			result =  dblValues[_seriesindex][_valindex];
1128cdf0e10cSrcweir 		else
1129cdf0e10cSrcweir 			result =  dblValues[_valindex][_seriesindex];
1130cdf0e10cSrcweir 	}
1131cdf0e10cSrcweir 	return result;
1132cdf0e10cSrcweir }
1133cdf0e10cSrcweir 
1134cdf0e10cSrcweir sal_Int32
getValuesCount(sal_Int32 _seriesIndex)1135cdf0e10cSrcweir ScVbaChart::getValuesCount(sal_Int32 _seriesIndex) throw ( script::BasicErrorException )
1136cdf0e10cSrcweir {
1137cdf0e10cSrcweir 	sal_Int32 nCount = 0;
1138cdf0e10cSrcweir 	uno::Reference< chart::XChartDataArray > xChartDataArray( mxChartDocument->getData(), uno::UNO_QUERY_THROW );
1139cdf0e10cSrcweir 	if (isSeriesIndexValid(_seriesIndex))
1140cdf0e10cSrcweir 	{
1141cdf0e10cSrcweir 		dblValues = xChartDataArray->getData();
1142cdf0e10cSrcweir 		if (getPlotBy() == xlRows)
1143cdf0e10cSrcweir 			nCount = dblValues[_seriesIndex].getLength();
1144cdf0e10cSrcweir 		else
1145cdf0e10cSrcweir 			nCount =  dblValues.getLength();
1146cdf0e10cSrcweir 	}
1147cdf0e10cSrcweir 	return nCount;
1148cdf0e10cSrcweir }
1149cdf0e10cSrcweir 
1150cdf0e10cSrcweir 
1151cdf0e10cSrcweir uno::Reference< excel::XDataLabels >
DataLabels(const uno::Reference<ov::excel::XSeries>)1152cdf0e10cSrcweir ScVbaChart::DataLabels( const uno::Reference< ov::excel::XSeries > /*_oSeries*/ ) throw ( css::script::BasicErrorException )
1153cdf0e10cSrcweir {
1154cdf0e10cSrcweir 	if ( true )
1155cdf0e10cSrcweir 		throw script::BasicErrorException( rtl::OUString(), uno::Reference< uno::XInterface >(), SbERR_METHOD_FAILED, rtl::OUString() );
1156cdf0e10cSrcweir 	// #TODO #FIXE provide implementation
1157cdf0e10cSrcweir 	return uno::Reference< excel::XDataLabels > ();
1158cdf0e10cSrcweir }
1159cdf0e10cSrcweir 
1160cdf0e10cSrcweir bool
getHasDataCaption(const uno::Reference<css::beans::XPropertySet> & _xPropertySet)1161cdf0e10cSrcweir ScVbaChart::getHasDataCaption( const uno::Reference< css::beans::XPropertySet >& _xPropertySet )throw ( script::BasicErrorException )
1162cdf0e10cSrcweir {
1163cdf0e10cSrcweir 	bool bResult = false;
1164cdf0e10cSrcweir 	try
1165cdf0e10cSrcweir 	{
1166cdf0e10cSrcweir 		sal_Int32 nChartDataCaption = 0;
1167cdf0e10cSrcweir 		_xPropertySet->getPropertyValue(DATACAPTION) >>= nChartDataCaption;
1168cdf0e10cSrcweir 		bResult = (nChartDataCaption != chart::ChartDataCaption::NONE);
1169cdf0e10cSrcweir 	}
1170cdf0e10cSrcweir 	catch (uno::Exception& )
1171cdf0e10cSrcweir 	{
1172cdf0e10cSrcweir 		throw script::BasicErrorException( rtl::OUString(), uno::Reference< uno::XInterface >(), SbERR_METHOD_FAILED, rtl::OUString() );
1173cdf0e10cSrcweir 	}
1174cdf0e10cSrcweir 	return bResult;
1175cdf0e10cSrcweir }
1176cdf0e10cSrcweir 
1177cdf0e10cSrcweir void
setHasDataCaption(const uno::Reference<beans::XPropertySet> & _xPropertySet,bool _bHasDataLabels)1178cdf0e10cSrcweir ScVbaChart::setHasDataCaption( const uno::Reference< beans::XPropertySet >& _xPropertySet, bool _bHasDataLabels )throw ( script::BasicErrorException )
1179cdf0e10cSrcweir {
1180cdf0e10cSrcweir 	try
1181cdf0e10cSrcweir 	{
1182cdf0e10cSrcweir 		if ( _bHasDataLabels )
1183cdf0e10cSrcweir 			_xPropertySet->setPropertyValue(DATACAPTION, uno::makeAny ( chart::ChartDataCaption::VALUE) );
1184cdf0e10cSrcweir 		else
1185cdf0e10cSrcweir 			_xPropertySet->setPropertyValue(DATACAPTION, uno::makeAny ( chart::ChartDataCaption::NONE) );
1186cdf0e10cSrcweir 	}
1187cdf0e10cSrcweir 	catch (uno::Exception& )
1188cdf0e10cSrcweir 	{
1189cdf0e10cSrcweir 		throw script::BasicErrorException( rtl::OUString(), uno::Reference< uno::XInterface >(), SbERR_METHOD_FAILED, rtl::OUString() );
1190cdf0e10cSrcweir 	}
1191cdf0e10cSrcweir }
1192cdf0e10cSrcweir 
1193cdf0e10cSrcweir uno::Reference< beans::XPropertySet >
getAxisPropertySet(sal_Int32 _nAxisType,sal_Int32 _nAxisGroup)1194cdf0e10cSrcweir ScVbaChart::getAxisPropertySet(sal_Int32 _nAxisType, sal_Int32 _nAxisGroup) throw ( script::BasicErrorException )
1195cdf0e10cSrcweir {
1196cdf0e10cSrcweir 	assignDiagramAttributes();
1197cdf0e10cSrcweir 	uno::Reference< beans::XPropertySet > xAxisProps;
1198cdf0e10cSrcweir 	switch(_nAxisType)
1199cdf0e10cSrcweir 	{
1200cdf0e10cSrcweir 		case xlCategory:
1201cdf0e10cSrcweir 			if (_nAxisGroup == xlPrimary)
1202cdf0e10cSrcweir 			{
1203cdf0e10cSrcweir 				xAxisProps = xAxisXSupplier->getXAxis();
1204cdf0e10cSrcweir 			}
1205cdf0e10cSrcweir 			else if (_nAxisGroup == xlSecondary)
1206cdf0e10cSrcweir 			{
1207cdf0e10cSrcweir 				xAxisProps = xTwoAxisXSupplier->getSecondaryXAxis();
1208cdf0e10cSrcweir 			}
1209cdf0e10cSrcweir 			break;
1210cdf0e10cSrcweir 		case xlSeriesAxis:
1211cdf0e10cSrcweir //                if (_nAxisGroup == xlPrimary){
1212cdf0e10cSrcweir 			xAxisProps = xAxisZSupplier->getZAxis();
1213cdf0e10cSrcweir 			break;
1214cdf0e10cSrcweir //                }
1215cdf0e10cSrcweir //                else if (_nAxisGroup == xlSecondary){
1216cdf0e10cSrcweir  //                   return xTwoAxisXSupplier.getSecondaryZAxis();
1217cdf0e10cSrcweir  //               }
1218cdf0e10cSrcweir 		case xlValue:
1219cdf0e10cSrcweir 			if (_nAxisGroup == xlPrimary)
1220cdf0e10cSrcweir 				xAxisProps = xAxisYSupplier->getYAxis();
1221cdf0e10cSrcweir 			else if (_nAxisGroup == xlSecondary)
1222cdf0e10cSrcweir 				xAxisProps = xTwoAxisYSupplier->getSecondaryYAxis();
1223cdf0e10cSrcweir 			break;
1224cdf0e10cSrcweir 		default:
1225cdf0e10cSrcweir 			return xAxisProps;
1226cdf0e10cSrcweir 		}
1227cdf0e10cSrcweir 	return xAxisProps;
1228cdf0e10cSrcweir }
1229cdf0e10cSrcweir 
1230cdf0e10cSrcweir 
1231cdf0e10cSrcweir rtl::OUString&
getServiceImplName()1232cdf0e10cSrcweir ScVbaChart::getServiceImplName()
1233cdf0e10cSrcweir {
1234cdf0e10cSrcweir 	static rtl::OUString sImplName( RTL_CONSTASCII_USTRINGPARAM("ScVbaChart") );
1235cdf0e10cSrcweir 	return sImplName;
1236cdf0e10cSrcweir }
1237cdf0e10cSrcweir 
1238cdf0e10cSrcweir uno::Sequence< rtl::OUString >
getServiceNames()1239cdf0e10cSrcweir ScVbaChart::getServiceNames()
1240cdf0e10cSrcweir {
1241cdf0e10cSrcweir 	static uno::Sequence< rtl::OUString > aServiceNames;
1242cdf0e10cSrcweir 	if ( aServiceNames.getLength() == 0 )
1243cdf0e10cSrcweir 	{
1244cdf0e10cSrcweir 		aServiceNames.realloc( 1 );
1245cdf0e10cSrcweir 		aServiceNames[ 0 ] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.excel.Chart" ) );
1246cdf0e10cSrcweir 	}
1247cdf0e10cSrcweir 	return aServiceNames;
1248cdf0e10cSrcweir }
1249cdf0e10cSrcweir 
1250