xref: /aoo42x/main/sw/source/ui/vba/vbaview.cxx (revision cdf0e10c)
1*cdf0e10cSrcweir /*************************************************************************
2*cdf0e10cSrcweir  *
3*cdf0e10cSrcweir  * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
4*cdf0e10cSrcweir  *
5*cdf0e10cSrcweir  * Copyright 2000, 2010 Oracle and/or its affiliates.
6*cdf0e10cSrcweir  *
7*cdf0e10cSrcweir  * OpenOffice.org - a multi-platform office productivity suite
8*cdf0e10cSrcweir  *
9*cdf0e10cSrcweir  * This file is part of OpenOffice.org.
10*cdf0e10cSrcweir  *
11*cdf0e10cSrcweir  * OpenOffice.org is free software: you can redistribute it and/or modify
12*cdf0e10cSrcweir  * it under the terms of the GNU Lesser General Public License version 3
13*cdf0e10cSrcweir  * only, as published by the Free Software Foundation.
14*cdf0e10cSrcweir  *
15*cdf0e10cSrcweir  * OpenOffice.org is distributed in the hope that it will be useful,
16*cdf0e10cSrcweir  * but WITHOUT ANY WARRANTY; without even the implied warranty of
17*cdf0e10cSrcweir  * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
18*cdf0e10cSrcweir  * GNU Lesser General Public License version 3 for more details
19*cdf0e10cSrcweir  * (a copy is included in the LICENSE file that accompanied this code).
20*cdf0e10cSrcweir  *
21*cdf0e10cSrcweir  * You should have received a copy of the GNU Lesser General Public License
22*cdf0e10cSrcweir  * version 3 along with OpenOffice.org.  If not, see
23*cdf0e10cSrcweir  * <http://www.openoffice.org/license.html>
24*cdf0e10cSrcweir  * for a copy of the LGPLv3 License.
25*cdf0e10cSrcweir  *
26*cdf0e10cSrcweir  ************************************************************************/
27*cdf0e10cSrcweir #include "vbaview.hxx"
28*cdf0e10cSrcweir #include <vbahelper/vbahelper.hxx>
29*cdf0e10cSrcweir #include <tools/diagnose_ex.h>
30*cdf0e10cSrcweir #include <com/sun/star/beans/XPropertySet.hpp>
31*cdf0e10cSrcweir #include <com/sun/star/view/XViewSettingsSupplier.hpp>
32*cdf0e10cSrcweir #include <com/sun/star/text/XTextViewCursorSupplier.hpp>
33*cdf0e10cSrcweir #include <com/sun/star/text/XText.hpp>
34*cdf0e10cSrcweir #include <com/sun/star/text/XTextTable.hpp>
35*cdf0e10cSrcweir #include <com/sun/star/table/XCellRange.hpp>
36*cdf0e10cSrcweir #include <com/sun/star/text/XTextDocument.hpp>
37*cdf0e10cSrcweir #include <com/sun/star/text/XFootnotesSupplier.hpp>
38*cdf0e10cSrcweir #include <com/sun/star/text/XEndnotesSupplier.hpp>
39*cdf0e10cSrcweir #include <com/sun/star/container/XIndexAccess.hpp>
40*cdf0e10cSrcweir #include <com/sun/star/container/XEnumerationAccess.hpp>
41*cdf0e10cSrcweir #include <com/sun/star/container/XEnumeration.hpp>
42*cdf0e10cSrcweir #include <com/sun/star/frame/XController.hpp>
43*cdf0e10cSrcweir #include <com/sun/star/lang/XServiceInfo.hpp>
44*cdf0e10cSrcweir #include <ooo/vba/word/WdSpecialPane.hpp>
45*cdf0e10cSrcweir #include <ooo/vba/word/WdViewType.hpp>
46*cdf0e10cSrcweir #include <ooo/vba/word/WdSeekView.hpp>
47*cdf0e10cSrcweir 
48*cdf0e10cSrcweir #include "wordvbahelper.hxx"
49*cdf0e10cSrcweir #include "vbaheaderfooterhelper.hxx"
50*cdf0e10cSrcweir #include <view.hxx>
51*cdf0e10cSrcweir 
52*cdf0e10cSrcweir using namespace ::ooo::vba;
53*cdf0e10cSrcweir using namespace ::com::sun::star;
54*cdf0e10cSrcweir 
55*cdf0e10cSrcweir static const sal_Int32 DEFAULT_BODY_DISTANCE = 500;
56*cdf0e10cSrcweir 
57*cdf0e10cSrcweir SwVbaView::SwVbaView( const uno::Reference< ooo::vba::XHelperInterface >& rParent, const uno::Reference< uno::XComponentContext >& rContext,
58*cdf0e10cSrcweir     const uno::Reference< frame::XModel >& rModel ) throw ( uno::RuntimeException ) :
59*cdf0e10cSrcweir     SwVbaView_BASE( rParent, rContext ), mxModel( rModel )
60*cdf0e10cSrcweir {
61*cdf0e10cSrcweir     uno::Reference< frame::XController > xController = mxModel->getCurrentController();
62*cdf0e10cSrcweir 
63*cdf0e10cSrcweir     uno::Reference< text::XTextViewCursorSupplier > xTextViewCursorSupp( xController, uno::UNO_QUERY_THROW );
64*cdf0e10cSrcweir     mxViewCursor = xTextViewCursorSupp->getViewCursor();
65*cdf0e10cSrcweir 
66*cdf0e10cSrcweir     uno::Reference< view::XViewSettingsSupplier > xViewSettingSupp( xController, uno::UNO_QUERY_THROW );
67*cdf0e10cSrcweir     mxViewSettings.set( xViewSettingSupp->getViewSettings(), uno::UNO_QUERY_THROW );
68*cdf0e10cSrcweir }
69*cdf0e10cSrcweir 
70*cdf0e10cSrcweir SwVbaView::~SwVbaView()
71*cdf0e10cSrcweir {
72*cdf0e10cSrcweir }
73*cdf0e10cSrcweir 
74*cdf0e10cSrcweir ::sal_Int32 SAL_CALL
75*cdf0e10cSrcweir SwVbaView::getSeekView() throw (css::uno::RuntimeException)
76*cdf0e10cSrcweir {
77*cdf0e10cSrcweir     // FIXME: if the view cursor is in table, field, section and frame
78*cdf0e10cSrcweir     // handle if the cursor is in table
79*cdf0e10cSrcweir     uno::Reference< text::XText > xCurrentText = mxViewCursor->getText();
80*cdf0e10cSrcweir     uno::Reference< beans::XPropertySet > xCursorProps( mxViewCursor, uno::UNO_QUERY_THROW );
81*cdf0e10cSrcweir     uno::Reference< text::XTextContent > xTextContent;
82*cdf0e10cSrcweir     while( xCursorProps->getPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("TextTable") ) ) >>= xTextContent )
83*cdf0e10cSrcweir     {
84*cdf0e10cSrcweir         xCurrentText = xTextContent->getAnchor()->getText();
85*cdf0e10cSrcweir         xCursorProps.set( xCurrentText->createTextCursor(), uno::UNO_QUERY_THROW );
86*cdf0e10cSrcweir     }
87*cdf0e10cSrcweir     uno::Reference< lang::XServiceInfo > xServiceInfo( xCurrentText, uno::UNO_QUERY_THROW );
88*cdf0e10cSrcweir     rtl::OUString aImplName = xServiceInfo->getImplementationName();
89*cdf0e10cSrcweir     if( aImplName.equalsAscii("SwXBodyText") )
90*cdf0e10cSrcweir     {
91*cdf0e10cSrcweir         return word::WdSeekView::wdSeekMainDocument;
92*cdf0e10cSrcweir     }
93*cdf0e10cSrcweir     else if( aImplName.equalsAscii("SwXHeadFootText") )
94*cdf0e10cSrcweir     {
95*cdf0e10cSrcweir         if( HeaderFooterHelper::isHeader( mxModel, xCurrentText ) )
96*cdf0e10cSrcweir         {
97*cdf0e10cSrcweir             if( HeaderFooterHelper::isFirstPageHeader( mxModel, xCurrentText ) )
98*cdf0e10cSrcweir                 return word::WdSeekView::wdSeekFirstPageHeader;
99*cdf0e10cSrcweir             else if( HeaderFooterHelper::isEvenPagesHeader( mxModel, xCurrentText ) )
100*cdf0e10cSrcweir                 return word::WdSeekView::wdSeekEvenPagesHeader;
101*cdf0e10cSrcweir             else
102*cdf0e10cSrcweir                 return word::WdSeekView::wdSeekPrimaryHeader;
103*cdf0e10cSrcweir         }
104*cdf0e10cSrcweir         else
105*cdf0e10cSrcweir         {
106*cdf0e10cSrcweir             if( HeaderFooterHelper::isFirstPageFooter( mxModel, xCurrentText ) )
107*cdf0e10cSrcweir                 return word::WdSeekView::wdSeekFirstPageFooter;
108*cdf0e10cSrcweir             else if( HeaderFooterHelper::isEvenPagesFooter( mxModel, xCurrentText ) )
109*cdf0e10cSrcweir                 return word::WdSeekView::wdSeekEvenPagesFooter;
110*cdf0e10cSrcweir             else
111*cdf0e10cSrcweir                 return word::WdSeekView::wdSeekPrimaryFooter;
112*cdf0e10cSrcweir         }
113*cdf0e10cSrcweir     }
114*cdf0e10cSrcweir     else if( aImplName.equalsAscii("SwXFootnote") )
115*cdf0e10cSrcweir     {
116*cdf0e10cSrcweir         if( xServiceInfo->supportsService( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("com.sun.star.text.Endnote") ) ) )
117*cdf0e10cSrcweir             return word::WdSeekView::wdSeekEndnotes;
118*cdf0e10cSrcweir         else
119*cdf0e10cSrcweir             return word::WdSeekView::wdSeekFootnotes;
120*cdf0e10cSrcweir     }
121*cdf0e10cSrcweir 
122*cdf0e10cSrcweir     return word::WdSeekView::wdSeekMainDocument;
123*cdf0e10cSrcweir }
124*cdf0e10cSrcweir 
125*cdf0e10cSrcweir void SAL_CALL
126*cdf0e10cSrcweir SwVbaView::setSeekView( ::sal_Int32 _seekview ) throw (css::uno::RuntimeException)
127*cdf0e10cSrcweir {
128*cdf0e10cSrcweir     // FIXME: save the current cursor position, if the cursor is in the main
129*cdf0e10cSrcweir     // document, so we can jump back to this position, if the macro sets
130*cdf0e10cSrcweir     // the ViewMode back to wdSeekMainDocument
131*cdf0e10cSrcweir 
132*cdf0e10cSrcweir     // if( _seekview == getSeekView() )
133*cdf0e10cSrcweir     //    return;
134*cdf0e10cSrcweir 
135*cdf0e10cSrcweir     switch( _seekview )
136*cdf0e10cSrcweir     {
137*cdf0e10cSrcweir         case word::WdSeekView::wdSeekFirstPageFooter:
138*cdf0e10cSrcweir         case word::WdSeekView::wdSeekFirstPageHeader:
139*cdf0e10cSrcweir         case word::WdSeekView::wdSeekCurrentPageFooter:
140*cdf0e10cSrcweir         case word::WdSeekView::wdSeekCurrentPageHeader:
141*cdf0e10cSrcweir         case word::WdSeekView::wdSeekPrimaryFooter:
142*cdf0e10cSrcweir         case word::WdSeekView::wdSeekPrimaryHeader:
143*cdf0e10cSrcweir         case word::WdSeekView::wdSeekEvenPagesFooter:
144*cdf0e10cSrcweir         case word::WdSeekView::wdSeekEvenPagesHeader:
145*cdf0e10cSrcweir         {
146*cdf0e10cSrcweir             // need to test
147*cdf0e10cSrcweir             mxViewCursor->gotoRange( getHFTextRange( _seekview ), sal_False );
148*cdf0e10cSrcweir             break;
149*cdf0e10cSrcweir         }
150*cdf0e10cSrcweir         case word::WdSeekView::wdSeekFootnotes:
151*cdf0e10cSrcweir         {
152*cdf0e10cSrcweir             uno::Reference< text::XFootnotesSupplier > xFootnotesSupp( mxModel, uno::UNO_QUERY_THROW );
153*cdf0e10cSrcweir             uno::Reference< container::XIndexAccess > xFootnotes( xFootnotesSupp->getFootnotes(), uno::UNO_QUERY_THROW );
154*cdf0e10cSrcweir             if( xFootnotes->getCount() > 0 )
155*cdf0e10cSrcweir             {
156*cdf0e10cSrcweir                 uno::Reference< text::XText > xText( xFootnotes->getByIndex(0), uno::UNO_QUERY_THROW );
157*cdf0e10cSrcweir                 mxViewCursor->gotoRange( xText->getStart(), sal_False );
158*cdf0e10cSrcweir             }
159*cdf0e10cSrcweir             else
160*cdf0e10cSrcweir             {
161*cdf0e10cSrcweir                 DebugHelper::exception( SbERR_NO_ACTIVE_OBJECT, rtl::OUString() );
162*cdf0e10cSrcweir             }
163*cdf0e10cSrcweir             break;
164*cdf0e10cSrcweir         }
165*cdf0e10cSrcweir         case word::WdSeekView::wdSeekEndnotes:
166*cdf0e10cSrcweir         {
167*cdf0e10cSrcweir             uno::Reference< text::XEndnotesSupplier > xEndnotesSupp( mxModel, uno::UNO_QUERY_THROW );
168*cdf0e10cSrcweir             uno::Reference< container::XIndexAccess > xEndnotes( xEndnotesSupp->getEndnotes(), uno::UNO_QUERY_THROW );
169*cdf0e10cSrcweir             if( xEndnotes->getCount() > 0 )
170*cdf0e10cSrcweir             {
171*cdf0e10cSrcweir                 uno::Reference< text::XText > xText( xEndnotes->getByIndex(0), uno::UNO_QUERY_THROW );
172*cdf0e10cSrcweir                 mxViewCursor->gotoRange( xText->getStart(), sal_False );
173*cdf0e10cSrcweir             }
174*cdf0e10cSrcweir             else
175*cdf0e10cSrcweir             {
176*cdf0e10cSrcweir                 DebugHelper::exception( SbERR_NO_ACTIVE_OBJECT, rtl::OUString() );
177*cdf0e10cSrcweir             }
178*cdf0e10cSrcweir             break;
179*cdf0e10cSrcweir         }
180*cdf0e10cSrcweir         case word::WdSeekView::wdSeekMainDocument:
181*cdf0e10cSrcweir         {
182*cdf0e10cSrcweir             uno::Reference< text::XTextDocument > xTextDocument( mxModel, uno::UNO_QUERY_THROW );
183*cdf0e10cSrcweir             uno::Reference< text::XText > xText = xTextDocument->getText();
184*cdf0e10cSrcweir             mxViewCursor->gotoRange( getFirstObjectPosition( xText ), sal_False );
185*cdf0e10cSrcweir             break;
186*cdf0e10cSrcweir         }
187*cdf0e10cSrcweir     }
188*cdf0e10cSrcweir }
189*cdf0e10cSrcweir 
190*cdf0e10cSrcweir ::sal_Int32 SAL_CALL
191*cdf0e10cSrcweir SwVbaView::getSplitSpecial() throw (css::uno::RuntimeException)
192*cdf0e10cSrcweir {
193*cdf0e10cSrcweir     return word::WdSpecialPane::wdPaneNone;
194*cdf0e10cSrcweir }
195*cdf0e10cSrcweir 
196*cdf0e10cSrcweir void SAL_CALL
197*cdf0e10cSrcweir SwVbaView::setSplitSpecial( ::sal_Int32/* _splitspecial */) throw (css::uno::RuntimeException)
198*cdf0e10cSrcweir {
199*cdf0e10cSrcweir     // not support in Writer
200*cdf0e10cSrcweir }
201*cdf0e10cSrcweir 
202*cdf0e10cSrcweir ::sal_Bool SAL_CALL
203*cdf0e10cSrcweir SwVbaView::getTableGridLines() throw (css::uno::RuntimeException)
204*cdf0e10cSrcweir {
205*cdf0e10cSrcweir     sal_Bool bShowTableGridLine = sal_False;
206*cdf0e10cSrcweir     mxViewSettings->getPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ShowTableBoundaries"))) >>= bShowTableGridLine;
207*cdf0e10cSrcweir     return bShowTableGridLine;
208*cdf0e10cSrcweir }
209*cdf0e10cSrcweir 
210*cdf0e10cSrcweir void SAL_CALL
211*cdf0e10cSrcweir SwVbaView::setTableGridLines( ::sal_Bool _tablegridlines ) throw (css::uno::RuntimeException)
212*cdf0e10cSrcweir {
213*cdf0e10cSrcweir     mxViewSettings->setPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ShowTableBoundaries")), uno::makeAny( _tablegridlines ) );
214*cdf0e10cSrcweir }
215*cdf0e10cSrcweir 
216*cdf0e10cSrcweir ::sal_Int32 SAL_CALL
217*cdf0e10cSrcweir SwVbaView::getType() throw (css::uno::RuntimeException)
218*cdf0e10cSrcweir {
219*cdf0e10cSrcweir     // FIXME: handle wdPrintPreview type
220*cdf0e10cSrcweir     sal_Bool bOnlineLayout = sal_False;
221*cdf0e10cSrcweir     mxViewSettings->getPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ShowOnlineLayout"))) >>= bOnlineLayout;
222*cdf0e10cSrcweir     return bOnlineLayout ? word::WdViewType::wdWebView : word::WdViewType::wdPrintView;
223*cdf0e10cSrcweir }
224*cdf0e10cSrcweir 
225*cdf0e10cSrcweir void SAL_CALL
226*cdf0e10cSrcweir SwVbaView::setType( ::sal_Int32 _type ) throw (css::uno::RuntimeException)
227*cdf0e10cSrcweir {
228*cdf0e10cSrcweir     // FIXME: handle wdPrintPreview type
229*cdf0e10cSrcweir     switch( _type )
230*cdf0e10cSrcweir     {
231*cdf0e10cSrcweir         case word::WdViewType::wdPrintView:
232*cdf0e10cSrcweir         case word::WdViewType::wdNormalView:
233*cdf0e10cSrcweir         {
234*cdf0e10cSrcweir             mxViewSettings->setPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ShowOnlineLayout")), uno::makeAny( sal_False ) );
235*cdf0e10cSrcweir             break;
236*cdf0e10cSrcweir         }
237*cdf0e10cSrcweir         case word::WdViewType::wdWebView:
238*cdf0e10cSrcweir         {
239*cdf0e10cSrcweir             mxViewSettings->setPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ShowOnlineLayout")), uno::makeAny( sal_True ) );
240*cdf0e10cSrcweir             break;
241*cdf0e10cSrcweir         }
242*cdf0e10cSrcweir         case word::WdViewType::wdPrintPreview:
243*cdf0e10cSrcweir         {
244*cdf0e10cSrcweir             PrintPreviewHelper( uno::Any(),word::getView( mxModel ) );
245*cdf0e10cSrcweir             break;
246*cdf0e10cSrcweir         }
247*cdf0e10cSrcweir         default:
248*cdf0e10cSrcweir             DebugHelper::exception( SbERR_NOT_IMPLEMENTED, rtl::OUString() );
249*cdf0e10cSrcweir 
250*cdf0e10cSrcweir     }
251*cdf0e10cSrcweir }
252*cdf0e10cSrcweir 
253*cdf0e10cSrcweir uno::Reference< text::XTextRange > SwVbaView::getHFTextRange( sal_Int32 nType ) throw (uno::RuntimeException)
254*cdf0e10cSrcweir {
255*cdf0e10cSrcweir     mxModel->lockControllers();
256*cdf0e10cSrcweir 
257*cdf0e10cSrcweir     rtl::OUString aPropIsOn;
258*cdf0e10cSrcweir     rtl::OUString aPropIsShared;
259*cdf0e10cSrcweir     rtl::OUString aPropBodyDistance;
260*cdf0e10cSrcweir     rtl::OUString aPropText;
261*cdf0e10cSrcweir 
262*cdf0e10cSrcweir     switch( nType )
263*cdf0e10cSrcweir     {
264*cdf0e10cSrcweir         case word::WdSeekView::wdSeekCurrentPageFooter:
265*cdf0e10cSrcweir         case word::WdSeekView::wdSeekFirstPageFooter:
266*cdf0e10cSrcweir         case word::WdSeekView::wdSeekPrimaryFooter:
267*cdf0e10cSrcweir         case word::WdSeekView::wdSeekEvenPagesFooter:
268*cdf0e10cSrcweir         {
269*cdf0e10cSrcweir             aPropIsOn = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("FooterIsOn") );
270*cdf0e10cSrcweir             aPropIsShared = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("FooterIsShared") );
271*cdf0e10cSrcweir             aPropBodyDistance = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("FooterBodyDistance") );
272*cdf0e10cSrcweir             aPropText = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("FooterText") );
273*cdf0e10cSrcweir             break;
274*cdf0e10cSrcweir         }
275*cdf0e10cSrcweir         case word::WdSeekView::wdSeekCurrentPageHeader:
276*cdf0e10cSrcweir         case word::WdSeekView::wdSeekFirstPageHeader:
277*cdf0e10cSrcweir         case word::WdSeekView::wdSeekPrimaryHeader:
278*cdf0e10cSrcweir         case word::WdSeekView::wdSeekEvenPagesHeader:
279*cdf0e10cSrcweir         {
280*cdf0e10cSrcweir             aPropIsOn = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("HeaderIsOn") );
281*cdf0e10cSrcweir             aPropIsShared = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("HeaderIsShared") );
282*cdf0e10cSrcweir             aPropBodyDistance = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("HeaderBodyDistance") );
283*cdf0e10cSrcweir             aPropText = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("HeaderText") );
284*cdf0e10cSrcweir             break;
285*cdf0e10cSrcweir         }
286*cdf0e10cSrcweir     }
287*cdf0e10cSrcweir 
288*cdf0e10cSrcweir     uno::Reference< text::XPageCursor > xPageCursor( mxViewCursor, uno::UNO_QUERY_THROW );
289*cdf0e10cSrcweir 
290*cdf0e10cSrcweir     if( nType == word::WdSeekView::wdSeekFirstPageFooter
291*cdf0e10cSrcweir         || nType == word::WdSeekView::wdSeekFirstPageHeader )
292*cdf0e10cSrcweir     {
293*cdf0e10cSrcweir         xPageCursor->jumpToFirstPage();
294*cdf0e10cSrcweir     }
295*cdf0e10cSrcweir 
296*cdf0e10cSrcweir     uno::Reference< style::XStyle > xStyle;
297*cdf0e10cSrcweir     uno::Reference< text::XText > xText;
298*cdf0e10cSrcweir     switch( nType )
299*cdf0e10cSrcweir     {
300*cdf0e10cSrcweir         case word::WdSeekView::wdSeekPrimaryFooter:
301*cdf0e10cSrcweir         case word::WdSeekView::wdSeekPrimaryHeader:
302*cdf0e10cSrcweir         case word::WdSeekView::wdSeekEvenPagesFooter:
303*cdf0e10cSrcweir         case word::WdSeekView::wdSeekEvenPagesHeader:
304*cdf0e10cSrcweir         {
305*cdf0e10cSrcweir             // The primary header is the first header of the section.
306*cdf0e10cSrcweir             // If the header is not shared between odd and even pages
307*cdf0e10cSrcweir             // the odd page's header is the primary header. If the
308*cdf0e10cSrcweir             // first page's header is different from the rest of the
309*cdf0e10cSrcweir             // document, it is NOT the primary header ( the next primary
310*cdf0e10cSrcweir             // header would be on page 3 )
311*cdf0e10cSrcweir             // The even pages' header is only available if the header is
312*cdf0e10cSrcweir             // not shared and the current style is applied to a page with
313*cdf0e10cSrcweir             // an even page number
314*cdf0e10cSrcweir             uno::Reference< beans::XPropertySet > xCursorProps( mxViewCursor, uno::UNO_QUERY_THROW );
315*cdf0e10cSrcweir             rtl::OUString aPageStyleName;
316*cdf0e10cSrcweir             xCursorProps->getPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("PageStyleName"))) >>= aPageStyleName;
317*cdf0e10cSrcweir             if( aPageStyleName.equalsAscii("First Page") )
318*cdf0e10cSrcweir             {
319*cdf0e10cSrcweir                 // go to the beginning of where the next style is used
320*cdf0e10cSrcweir                 sal_Bool hasNextPage = sal_False;
321*cdf0e10cSrcweir                 xStyle = word::getCurrentPageStyle( mxModel );
322*cdf0e10cSrcweir                 do
323*cdf0e10cSrcweir                 {
324*cdf0e10cSrcweir                     hasNextPage = xPageCursor->jumpToNextPage();
325*cdf0e10cSrcweir                 }
326*cdf0e10cSrcweir                 while( hasNextPage && ( xStyle == word::getCurrentPageStyle( mxModel ) ) );
327*cdf0e10cSrcweir 
328*cdf0e10cSrcweir                 if( !hasNextPage )
329*cdf0e10cSrcweir                     DebugHelper::exception( SbERR_BAD_ACTION, rtl::OUString() );
330*cdf0e10cSrcweir             }
331*cdf0e10cSrcweir             break;
332*cdf0e10cSrcweir         }
333*cdf0e10cSrcweir         default:
334*cdf0e10cSrcweir         {
335*cdf0e10cSrcweir             break;
336*cdf0e10cSrcweir         }
337*cdf0e10cSrcweir     }
338*cdf0e10cSrcweir 
339*cdf0e10cSrcweir     xStyle = word::getCurrentPageStyle( mxModel );
340*cdf0e10cSrcweir     uno::Reference< beans::XPropertySet > xPageProps( xStyle, uno::UNO_QUERY_THROW );
341*cdf0e10cSrcweir     sal_Bool isOn = sal_False;
342*cdf0e10cSrcweir     xPageProps->getPropertyValue( aPropIsOn ) >>= isOn;
343*cdf0e10cSrcweir     sal_Bool isShared =  sal_False;
344*cdf0e10cSrcweir     xPageProps->getPropertyValue( aPropIsShared ) >>= isShared;
345*cdf0e10cSrcweir     if( !isOn )
346*cdf0e10cSrcweir     {
347*cdf0e10cSrcweir         xPageProps->setPropertyValue( aPropIsOn, uno::makeAny( sal_True ) );
348*cdf0e10cSrcweir         xPageProps->setPropertyValue( aPropBodyDistance, uno::makeAny( DEFAULT_BODY_DISTANCE ) );
349*cdf0e10cSrcweir     }
350*cdf0e10cSrcweir     if( !isShared )
351*cdf0e10cSrcweir     {
352*cdf0e10cSrcweir         rtl::OUString aTempPropText = aPropText;
353*cdf0e10cSrcweir         if( nType == word::WdSeekView::wdSeekEvenPagesFooter
354*cdf0e10cSrcweir             || nType == word::WdSeekView::wdSeekEvenPagesHeader )
355*cdf0e10cSrcweir         {
356*cdf0e10cSrcweir             aTempPropText += rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("Left") );
357*cdf0e10cSrcweir         }
358*cdf0e10cSrcweir         else
359*cdf0e10cSrcweir         {
360*cdf0e10cSrcweir             aTempPropText += rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("Right") );
361*cdf0e10cSrcweir         }
362*cdf0e10cSrcweir         xText.set( xPageProps->getPropertyValue( aTempPropText), uno::UNO_QUERY_THROW );
363*cdf0e10cSrcweir     }
364*cdf0e10cSrcweir     else
365*cdf0e10cSrcweir     {
366*cdf0e10cSrcweir         if( nType == word::WdSeekView::wdSeekEvenPagesFooter
367*cdf0e10cSrcweir             || nType == word::WdSeekView::wdSeekEvenPagesHeader )
368*cdf0e10cSrcweir         {
369*cdf0e10cSrcweir             DebugHelper::exception( SbERR_BAD_ACTION, rtl::OUString() );
370*cdf0e10cSrcweir         }
371*cdf0e10cSrcweir         xText.set( xPageProps->getPropertyValue( aPropText ), uno::UNO_QUERY_THROW );
372*cdf0e10cSrcweir     }
373*cdf0e10cSrcweir 
374*cdf0e10cSrcweir     mxModel->unlockControllers();
375*cdf0e10cSrcweir     if( !xText.is() )
376*cdf0e10cSrcweir     {
377*cdf0e10cSrcweir         DebugHelper::exception( SbERR_INTERNAL_ERROR, rtl::OUString() );
378*cdf0e10cSrcweir     }
379*cdf0e10cSrcweir     uno::Reference< text::XTextRange > xTextRange = getFirstObjectPosition( xText );
380*cdf0e10cSrcweir     return xTextRange;
381*cdf0e10cSrcweir }
382*cdf0e10cSrcweir 
383*cdf0e10cSrcweir uno::Reference< text::XTextRange > SwVbaView::getFirstObjectPosition( const uno::Reference< text::XText >& xText ) throw (uno::RuntimeException)
384*cdf0e10cSrcweir {
385*cdf0e10cSrcweir     // if the first object is table, get the position of first cell
386*cdf0e10cSrcweir     uno::Reference< text::XTextRange > xTextRange;
387*cdf0e10cSrcweir     uno::Reference< container::XEnumerationAccess > xParaAccess( xText, uno::UNO_QUERY_THROW );
388*cdf0e10cSrcweir     uno::Reference< container::XEnumeration> xParaEnum = xParaAccess->createEnumeration();
389*cdf0e10cSrcweir     if( xParaEnum->hasMoreElements() )
390*cdf0e10cSrcweir     {
391*cdf0e10cSrcweir         uno::Reference< lang::XServiceInfo > xServiceInfo( xParaEnum->nextElement(), uno::UNO_QUERY_THROW );
392*cdf0e10cSrcweir         if( xServiceInfo->supportsService( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("com.sun.star.text.TextTable") ) ) )
393*cdf0e10cSrcweir         {
394*cdf0e10cSrcweir             uno::Reference< table::XCellRange > xCellRange( xServiceInfo, uno::UNO_QUERY_THROW );
395*cdf0e10cSrcweir             uno::Reference< text::XText> xFirstCellText( xCellRange->getCellByPosition(0, 0), uno::UNO_QUERY_THROW );
396*cdf0e10cSrcweir             xTextRange = xFirstCellText->getStart();
397*cdf0e10cSrcweir         }
398*cdf0e10cSrcweir     }
399*cdf0e10cSrcweir     if( !xTextRange.is() )
400*cdf0e10cSrcweir         xTextRange = xText->getStart();
401*cdf0e10cSrcweir     return xTextRange;
402*cdf0e10cSrcweir }
403*cdf0e10cSrcweir 
404*cdf0e10cSrcweir rtl::OUString&
405*cdf0e10cSrcweir SwVbaView::getServiceImplName()
406*cdf0e10cSrcweir {
407*cdf0e10cSrcweir 	static rtl::OUString sImplName( RTL_CONSTASCII_USTRINGPARAM("SwVbaView") );
408*cdf0e10cSrcweir 	return sImplName;
409*cdf0e10cSrcweir }
410*cdf0e10cSrcweir 
411*cdf0e10cSrcweir uno::Sequence< rtl::OUString >
412*cdf0e10cSrcweir SwVbaView::getServiceNames()
413*cdf0e10cSrcweir {
414*cdf0e10cSrcweir 	static uno::Sequence< rtl::OUString > aServiceNames;
415*cdf0e10cSrcweir 	if ( aServiceNames.getLength() == 0 )
416*cdf0e10cSrcweir 	{
417*cdf0e10cSrcweir 		aServiceNames.realloc( 1 );
418*cdf0e10cSrcweir 		aServiceNames[ 0 ] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.word.View" ) );
419*cdf0e10cSrcweir 	}
420*cdf0e10cSrcweir 	return aServiceNames;
421*cdf0e10cSrcweir }
422*cdf0e10cSrcweir 
423