1 /*************************************************************************
3 * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
5 * Copyright 2008 by Sun Microsystems, Inc.
7 * OpenOffice.org - a multi-platform office productivity suite
12 * This file is part of OpenOffice.org.
14 * OpenOffice.org is free software: you can redistribute it and/or modify
15 * it under the terms of the GNU Lesser General Public License version 3
16 * only, as published by the Free Software Foundation.
18 * OpenOffice.org is distributed in the hope that it will be useful,
19 * but WITHOUT ANY WARRANTY; without even the implied warranty of
20 * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
21 * GNU Lesser General Public License version 3 for more details
22 * (a copy is included in the LICENSE file that accompanied this code).
24 * You should have received a copy of the GNU Lesser General Public License
25 * version 3 along with OpenOffice.org. If not, see
26 * <http://www.openoffice.org/license.html>
27 * for a copy of the LGPLv3 License.
29 ************************************************************************/
30 #include "vbaselection.hxx"
31 #include <vbahelper/vbahelper.hxx>
32 #include <tools/diagnose_ex.h>
33 #include "vbarange.hxx"
34 #include "vbafind.hxx"
35 #include "wordvbahelper.hxx"
36 #include <com/sun/star/text/XTextRange.hpp>
37 #include <com/sun/star/text/XTextTable.hpp>
38 #include <com/sun/star/text/XTextTableCursor.hpp>
39 #include <com/sun/star/text/ControlCharacter.hpp>
40 #include <com/sun/star/table/XCell.hpp>
41 #include <ooo/vba/word/WdUnits.hpp>
42 #include <ooo/vba/word/WdMovementType.hpp>
43 #include <ooo/vba/word/WdGoToItem.hpp>
44 #include <ooo/vba/word/WdGoToDirection.hpp>
45 #include <ooo/vba/word/XBookmark.hpp>
46 #include <ooo/vba/word/XApplication.hpp>
47 #include <com/sun/star/text/XPageCursor.hpp>
49 #include "unocoll.hxx"
50 #include "vbatable.hxx"
51 #include <com/sun/star/view/XSelectionSupplier.hpp>
52 #include <com/sun/star/view/XViewCursor.hpp>
53 #include <ooo/vba/word/WdInformation.hpp>
54 #include <ooo/vba/word/WdHeaderFooterIndex.hpp>
55 #include "vbainformationhelper.hxx"
56 #include "vbafield.hxx"
57 #include "vbaheaderfooter.hxx"
58 #include "vbaheaderfooterhelper.hxx"
59 #include <vbahelper/vbashaperange.hxx>
60 #include <com/sun/star/drawing/XDrawPageSupplier.hpp>
61 #include <com/sun/star/drawing/XDrawPage.hpp>
63 using namespace ::ooo::vba
;
64 using namespace ::com::sun::star
;
66 SwVbaSelection::SwVbaSelection( const uno::Reference
< ooo::vba::XHelperInterface
>& rParent
, const uno::Reference
< uno::XComponentContext
>& rContext
, const uno::Reference
< frame::XModel
>& rModel
) throw ( uno::RuntimeException
) : SwVbaSelection_BASE( rParent
, rContext
), mxModel( rModel
)
68 mxTextViewCursor
= word::getXTextViewCursor( mxModel
);
71 SwVbaSelection::~SwVbaSelection()
75 uno::Reference
< text::XTextRange
> SwVbaSelection::GetSelectedRange() throw ( uno::RuntimeException
)
77 uno::Reference
< text::XTextRange
> xTextRange
;
78 uno::Reference
< lang::XServiceInfo
> xServiceInfo( mxModel
->getCurrentSelection(), uno::UNO_QUERY_THROW
);
79 if( xServiceInfo
->supportsService( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("com.sun.star.text.TextRanges") ) ) )
81 uno::Reference
< container::XIndexAccess
> xTextRanges( xServiceInfo
, uno::UNO_QUERY_THROW
);
82 if( xTextRanges
->getCount() > 0 )
84 // if there are multipul selection, just return the last selected Range.
85 xTextRange
.set( xTextRanges
->getByIndex( xTextRanges
->getCount()-1 ), uno::UNO_QUERY_THROW
);
90 throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("Not implemented") ), uno::Reference
< uno::XInterface
>() );
95 uno::Reference
< word::XRange
> SAL_CALL
96 SwVbaSelection::getRange() throw ( uno::RuntimeException
)
98 uno::Reference
< text::XTextRange
> xTextRange
= GetSelectedRange();
99 uno::Reference
< text::XTextDocument
> xDocument( mxModel
, uno::UNO_QUERY_THROW
);
100 return uno::Reference
< word::XRange
>( new SwVbaRange( this, mxContext
, xDocument
, xTextRange
->getStart(), xTextRange
->getEnd(), mxTextViewCursor
->getText() ) );
103 rtl::OUString SAL_CALL
104 SwVbaSelection::getText() throw ( uno::RuntimeException
)
106 return getRange()->getText();
110 SwVbaSelection::setText( const rtl::OUString
& rText
) throw ( uno::RuntimeException
)
112 getRange()->setText( rText
);
116 SwVbaSelection::TypeText( const rtl::OUString
& rText
) throw ( uno::RuntimeException
)
118 // FIXME: handle the property Options.ReplaceSelection, the default value is TRUE
123 SwVbaSelection::HomeKey( const uno::Any
& _unit
, const uno::Any
& _extend
) throw ( uno::RuntimeException
)
125 sal_Int32 nUnit
= word::WdUnits::wdLine
;
126 sal_Int32 nExtend
= word::WdMovementType::wdMove
;
132 case word::WdUnits::wdStory
:
134 // go to the begin of the document
135 rtl::OUString url
= rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( ".uno:GoToStartOfDoc"));
136 dispatchRequests( mxModel
,url
);
137 // If something is selected, it needs to go twice
138 dispatchRequests( mxModel
,url
);
141 case word::WdUnits::wdLine
:
143 // go to the begin of the Line
144 rtl::OUString url
= rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( ".uno:GoToStartOfLine"));
145 dispatchRequests( mxModel
,url
);
150 throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("Not implemented") ), uno::Reference
< uno::XInterface
>() );
157 SwVbaSelection::EndKey( const uno::Any
& _unit
, const uno::Any
& _extend
) throw ( uno::RuntimeException
)
159 sal_Int32 nUnit
= word::WdUnits::wdLine
;
160 sal_Int32 nExtend
= word::WdMovementType::wdMove
;
166 case word::WdUnits::wdStory
:
168 // go to the end of the document
169 rtl::OUString url
= rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( ".uno:GoToEndOfDoc"));
170 dispatchRequests( mxModel
,url
);
171 // If something is selected, it needs to go twice
172 dispatchRequests( mxModel
,url
);
175 case word::WdUnits::wdLine
:
177 // go to the end of the Line
178 rtl::OUString url
= rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( ".uno:GoToEndOfLine"));
179 dispatchRequests( mxModel
,url
);
184 throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("Not implemented") ), uno::Reference
< uno::XInterface
>() );
191 SwVbaSelection::Delete( const uno::Any
& /*_unit*/, const uno::Any
& /*_count*/ ) throw ( uno::RuntimeException
)
193 // FIXME: handle the arguments: _unit and _count
194 rtl::OUString url
= rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( ".uno:Delete"));
195 dispatchRequests( mxModel
,url
);
198 void SwVbaSelection::NextCell( sal_Int32 nCount
, E_DIRECTION eDirection
) throw ( uno::RuntimeException
)
200 uno::Reference
< beans::XPropertySet
> xCursorProps( mxTextViewCursor
, uno::UNO_QUERY_THROW
);
201 uno::Reference
< text::XTextTable
> xTextTable
;
202 uno::Reference
< table::XCell
> xCell
;
203 xCursorProps
->getPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("TextTable") ) ) >>= xTextTable
;
204 xCursorProps
->getPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("Cell") ) ) >>= xCell
;
205 if( !xTextTable
.is() || !xCell
.is() )
207 DebugHelper::exception(SbERR_BAD_ARGUMENT
, rtl::OUString());
210 uno::Reference
< beans::XPropertySet
> xCellProps( xCell
, uno::UNO_QUERY_THROW
);
211 rtl::OUString aCellName
;
212 xCellProps
->getPropertyValue( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("CellName") ) ) >>= aCellName
;
213 uno::Reference
< text::XTextTableCursor
> xTextTableCursor
= xTextTable
->createCursorByCellName( aCellName
);
214 // move the table cursor
219 xTextTableCursor
->goLeft( nCount
, sal_False
);
224 xTextTableCursor
->goRight( nCount
, sal_False
);
229 xTextTableCursor
->goUp( nCount
, sal_False
);
234 xTextTableCursor
->goDown( nCount
, sal_False
);
239 DebugHelper::exception(SbERR_BAD_ARGUMENT
, rtl::OUString());
243 // move the view cursor
244 xCell
= xTextTable
->getCellByName( xTextTableCursor
->getRangeName() );
245 mxTextViewCursor
->gotoRange( uno::Reference
< text::XTextRange
>( xCell
, uno::UNO_QUERY_THROW
), sal_False
);
249 SwVbaSelection::MoveRight( const uno::Any
& _unit
, const uno::Any
& _count
, const uno::Any
& _extend
) throw ( uno::RuntimeException
)
251 sal_Int32 nUnit
= word::WdUnits::wdCharacter
;
252 sal_Int32 nCount
= 1;
253 sal_Int32 nExtend
= word::WdMovementType::wdMove
;
255 if( _unit
.hasValue() )
257 if( _count
.hasValue() )
259 if( _extend
.hasValue() )
267 // TODO: call MoveLeft;
268 MoveLeft( _unit
, uno::makeAny( -nCount
), _extend
);
274 case word::WdUnits::wdCell
:
276 if( nExtend
== word::WdMovementType::wdExtend
)
278 DebugHelper::exception(SbERR_BAD_ARGUMENT
, rtl::OUString());
281 NextCell( nCount
, MOVE_RIGHT
);
286 throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("Not implemented") ), uno::Reference
< uno::XInterface
>() );
294 SwVbaSelection::MoveLeft( const uno::Any
& _unit
, const uno::Any
& _count
, const uno::Any
& _extend
) throw ( uno::RuntimeException
)
296 sal_Int32 nUnit
= word::WdUnits::wdCharacter
;
297 sal_Int32 nCount
= 1;
298 sal_Int32 nExtend
= word::WdMovementType::wdMove
;
300 if( _unit
.hasValue() )
302 if( _count
.hasValue() )
304 if( _extend
.hasValue() )
312 MoveRight( _unit
, uno::makeAny( -nCount
), _extend
);
318 case word::WdUnits::wdCell
:
320 if( nExtend
== word::WdMovementType::wdExtend
)
322 DebugHelper::exception(SbERR_BAD_ARGUMENT
, rtl::OUString());
325 NextCell( nCount
, MOVE_LEFT
);
330 throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("Not implemented") ), uno::Reference
< uno::XInterface
>() );
338 SwVbaSelection::MoveDown( const uno::Any
& _unit
, const uno::Any
& _count
, const uno::Any
& _extend
) throw ( uno::RuntimeException
)
340 sal_Int32 nUnit
= word::WdUnits::wdCharacter
;
341 sal_Int32 nCount
= 1;
342 sal_Int32 nExtend
= word::WdMovementType::wdMove
;
344 if( _unit
.hasValue() )
346 if( _count
.hasValue() )
348 if( _extend
.hasValue() )
356 // TODO: call MoveLeft;
357 //MoveUp( _unit, uno::makeAny( -nCount ), _extend );
363 case word::WdUnits::wdLine
:
365 uno::Reference
< view::XViewCursor
> xViewCursor( mxTextViewCursor
, uno::UNO_QUERY_THROW
);
366 sal_Bool bExpand
= ( nExtend
== word::WdMovementType::wdMove
) ? sal_False
: sal_True
;
367 xViewCursor
->goDown( nCount
, bExpand
);
372 throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("Not implemented") ), uno::Reference
< uno::XInterface
>() );
380 SwVbaSelection::TypeParagraph() throw ( uno::RuntimeException
)
382 // #FIXME: if the selection is an entire paragraph, it's replaced
383 // by the new paragraph
384 sal_Bool isCollapsed
= mxTextViewCursor
->isCollapsed();
387 mxTextViewCursor
->collapseToStart();
391 SwVbaSelection::InsertParagraph() throw ( uno::RuntimeException
)
393 // #FIME: the selection should include the new paragraph.
394 getRange()->InsertParagraph();
398 SwVbaSelection::InsertParagraphBefore() throw ( uno::RuntimeException
)
400 getRange()->InsertParagraphBefore();
404 SwVbaSelection::InsertParagraphAfter() throw ( uno::RuntimeException
)
406 getRange()->InsertParagraphAfter();
409 uno::Reference
< word::XParagraphFormat
> SAL_CALL
410 SwVbaSelection::getParagraphFormat() throw ( uno::RuntimeException
)
412 return getRange()->getParagraphFormat();
416 SwVbaSelection::setParagraphFormat( const uno::Reference
< word::XParagraphFormat
>& rParagraphFormat
) throw ( uno::RuntimeException
)
418 return getRange()->setParagraphFormat( rParagraphFormat
);
421 uno::Reference
< word::XFind
> SAL_CALL
422 SwVbaSelection::getFind() throw ( uno::RuntimeException
)
424 uno::Reference
< text::XTextRange
> xTextRange
= GetSelectedRange();
425 return uno::Reference
< word::XFind
>( new SwVbaFind( this, mxContext
, mxModel
, xTextRange
) );
428 uno::Reference
< word::XStyle
> SAL_CALL
429 SwVbaSelection::getStyle() throw ( uno::RuntimeException
)
431 return getRange()->getStyle();
435 SwVbaSelection::setStyle( const uno::Reference
< word::XStyle
>& rStyle
) throw ( uno::RuntimeException
)
437 return getRange()->setStyle( rStyle
);
440 uno::Reference
< word::XFont
> SAL_CALL
441 SwVbaSelection::getFont() throw ( uno::RuntimeException
)
443 return getRange()->getFont();
447 SwVbaSelection::TypeBackspace() throw ( uno::RuntimeException
)
449 rtl::OUString url
= rtl::OUString( RTL_CONSTASCII_USTRINGPARAM( ".uno:SwBackspace"));
450 dispatchRequests( mxModel
,url
);
453 uno::Reference
< word::XRange
> SAL_CALL
SwVbaSelection::GoTo( const uno::Any
& _what
, const uno::Any
& _which
, const uno::Any
& _count
, const uno::Any
& _name
) throw (uno::RuntimeException
)
456 if( ( _what
>>= nWhat
) != sal_True
)
457 DebugHelper::exception(SbERR_BAD_ARGUMENT
, rtl::OUString());
460 case word::WdGoToItem::wdGoToBookmark
:
463 uno::Reference
< word::XApplication
> xApplication( Application(), uno::UNO_QUERY_THROW
);
464 uno::Reference
< word::XBookmark
> xBookmark( xApplication
->getActiveDocument()->Bookmarks(_name
), uno::UNO_QUERY_THROW
);
466 //return uno::Reference< word::XRange >( xBookmark->Range(), uno::UNO_QUERY_THROW );
469 case word::WdGoToItem::wdGoToPage
:
471 uno::Reference
< text::XPageCursor
> xPageCursor( mxTextViewCursor
, uno::UNO_QUERY_THROW
);
472 sal_Int32 nCurrPage
= xPageCursor
->getPage();
473 sal_Int32 nLastPage
= word::getPageCount( mxModel
);
474 sal_Int32 nCount
= 0;
475 if( _count
.hasValue() )
477 sal_Int32 nWhich
= 0;
478 if( _which
.hasValue() )
483 case word::WdGoToDirection::wdGoToLast
:
488 case word::WdGoToDirection::wdGoToNext
:
490 nPage
= nCurrPage
+ 1;
493 case word::WdGoToDirection::wdGoToPrevious
:
495 nPage
= nCurrPage
- 1;
505 if( nPage
> nLastPage
)
507 xPageCursor
->jumpToPage( ( sal_Int16
)( nPage
) );
510 case word::WdGoToItem::wdGoToSection
:
512 // TODO: implement Section object
515 throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("Not implemented") ), uno::Reference
< uno::XInterface
>() );
520 ::sal_Int32 SAL_CALL
SwVbaSelection::getLanguageID() throw (uno::RuntimeException
)
522 return getRange()->getLanguageID();
525 void SAL_CALL
SwVbaSelection::setLanguageID( ::sal_Int32 _languageid
) throw (uno::RuntimeException
)
527 getRange()->setLanguageID( _languageid
);
530 uno::Any SAL_CALL
SwVbaSelection::Information( sal_Int32 _type
) throw (uno::RuntimeException
)
533 //uno::Reference< view::XSelectionSupplier > xSel( mxModel->getCurrentController(), uno::UNO_QUERY_THROW );
534 //uno::Any aSelectedObject = xSel->getSelection();
537 case word::WdInformation::wdActiveEndPageNumber
:
539 result
= uno::makeAny( SwVbaInformationHelper::handleWdActiveEndPageNumber( mxTextViewCursor
) );
542 case word::WdInformation::wdNumberOfPagesInDocument
:
544 result
= uno::makeAny( SwVbaInformationHelper::handleWdNumberOfPagesInDocument( mxModel
) );
547 case word::WdInformation::wdVerticalPositionRelativeToPage
:
549 result
= uno::makeAny( SwVbaInformationHelper::handleWdVerticalPositionRelativeToPage( mxModel
, mxTextViewCursor
) );
553 throw uno::RuntimeException( rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("Not implemented") ), uno::Reference
< uno::XInterface
>() );
555 // This method fails to restore the previouse selection
556 //xSel->select( aSelectedObject );
560 void SAL_CALL
SwVbaSelection::InsertBreak( const uno::Any
& _breakType
) throw (uno::RuntimeException
)
562 getRange()->InsertBreak( _breakType
);
566 SwVbaSelection::Tables( const uno::Any
& aIndex
) throw (uno::RuntimeException
)
568 // Hacky implementation due to missing api ( and lack of knowledge )
569 // we can only support a selection that is a single table
570 if ( !aIndex
.hasValue() ) // currently we can't support multiple tables in a selection
571 throw uno::RuntimeException();
572 // if the current selection is a XTextTableCursor and the index is 1 then we can service this request, otherwise we just have to throw
573 uno::Reference
< text::XTextTableCursor
> xTextTableCursor( mxModel
->getCurrentSelection(), uno::UNO_QUERY
);
575 if ( !xTextTableCursor
.is() )
576 throw uno::RuntimeException();
578 sal_Int32 nIndex
= 0;
584 throw uno::RuntimeException();
585 SwXTextTableCursor
* pTTCursor
= dynamic_cast< SwXTextTableCursor
* >( xTextTableCursor
.get() );
588 SwFrmFmt
* pFmt
= pTTCursor
->GetFrmFmt();
589 rtl::OUString sTableName
;
592 uno::Reference
< text::XTextTable
> xTbl
= SwXTextTables::GetObject(*pFmt
);
593 uno::Reference
< css::text::XTextDocument
> xTextDoc( mxModel
, uno::UNO_QUERY_THROW
);
594 uno::Reference
< word::XTable
> xVBATbl
= new SwVbaTable( mxParent
, mxContext
, xTextDoc
, xTbl
);
603 SwVbaSelection::Fields( const uno::Any
& index
) throw (uno::RuntimeException
)
605 uno::Reference
< XCollection
> xCol( new SwVbaFields( mxParent
, mxContext
, mxModel
) );
606 if ( index
.hasValue() )
607 return xCol
->Item( index
, uno::Any() );
608 return uno::makeAny( xCol
);
611 uno::Reference
< word::XHeaderFooter
> SAL_CALL
612 SwVbaSelection::getHeaderFooter() throw ( uno::RuntimeException
)
614 uno::Reference
< text::XText
> xCurrentText
= word::getXTextViewCursor( mxModel
)->getText();
615 if( HeaderFooterHelper::isHeader( mxModel
, xCurrentText
) || HeaderFooterHelper::isFooter( mxModel
, xCurrentText
) )
617 uno::Reference
< beans::XPropertySet
> xPageStyleProps( word::getCurrentPageStyle( mxModel
), uno::UNO_QUERY_THROW
);
618 sal_Int32 nIndex
= word::WdHeaderFooterIndex::wdHeaderFooterPrimary
;
619 sal_Bool isHeader
= HeaderFooterHelper::isHeader( mxModel
, xCurrentText
);
620 if( HeaderFooterHelper::isEvenPagesHeader( mxModel
, xCurrentText
) || HeaderFooterHelper::isEvenPagesFooter( mxModel
, xCurrentText
) )
621 nIndex
= word::WdHeaderFooterIndex::wdHeaderFooterEvenPages
;
622 else if( HeaderFooterHelper::isFirstPageHeader( mxModel
, xCurrentText
) || HeaderFooterHelper::isFirstPageFooter( mxModel
, xCurrentText
) )
623 nIndex
= word::WdHeaderFooterIndex::wdHeaderFooterFirstPage
;
625 return uno::Reference
< word::XHeaderFooter
>( new SwVbaHeaderFooter( this, mxContext
, mxModel
, xPageStyleProps
, isHeader
, nIndex
) );
628 return uno::Reference
< word::XHeaderFooter
>();
632 SwVbaSelection::ShapeRange( ) throw (uno::RuntimeException
)
634 uno::Reference
< drawing::XShapes
> xShapes( mxModel
->getCurrentSelection(), uno::UNO_QUERY
);
637 throw uno::RuntimeException();
639 uno::Reference
< drawing::XDrawPageSupplier
> xDrawPageSupplier( mxModel
, uno::UNO_QUERY_THROW
);
640 uno::Reference
< drawing::XDrawPage
> xDrawPage
= xDrawPageSupplier
->getDrawPage();
641 uno::Reference
< container::XIndexAccess
> xShapesAccess( xShapes
, uno::UNO_QUERY_THROW
);
642 return uno::makeAny( uno::Reference
< msforms::XShapeRange
>( new ScVbaShapeRange( this, mxContext
, xShapesAccess
, xDrawPage
, mxModel
) ) );
645 ::sal_Int32 SAL_CALL
SwVbaSelection::getStart() throw (uno::RuntimeException
)
647 return getRange()->getStart();
650 void SAL_CALL
SwVbaSelection::setStart( ::sal_Int32 _start
) throw (uno::RuntimeException
)
652 getRange()->setStart( _start
);
654 ::sal_Int32 SAL_CALL
SwVbaSelection::getEnd() throw (uno::RuntimeException
)
656 return getRange()->getEnd();
659 void SAL_CALL
SwVbaSelection::setEnd( ::sal_Int32 _end
) throw (uno::RuntimeException
)
661 getRange()->setEnd( _end
);
665 SwVbaSelection::getServiceImplName()
667 static rtl::OUString
sImplName( RTL_CONSTASCII_USTRINGPARAM("SwVbaSelection") );
671 uno::Sequence
< rtl::OUString
>
672 SwVbaSelection::getServiceNames()
674 static uno::Sequence
< rtl::OUString
> aServiceNames
;
675 if ( aServiceNames
.getLength() == 0 )
677 aServiceNames
.realloc( 1 );
678 aServiceNames
[ 0 ] = rtl::OUString( RTL_CONSTASCII_USTRINGPARAM("ooo.vba.word.Selection" ) );
680 return aServiceNames
;