summaryrefslogtreecommitdiff
path: root/wizards/source/sfdocuments/SF_Writer.xba
diff options
context:
space:
mode:
Diffstat (limited to 'wizards/source/sfdocuments/SF_Writer.xba')
-rw-r--r--wizards/source/sfdocuments/SF_Writer.xba491
1 files changed, 477 insertions, 14 deletions
diff --git a/wizards/source/sfdocuments/SF_Writer.xba b/wizards/source/sfdocuments/SF_Writer.xba
index ebdff7f78386..1ff52244533d 100644
--- a/wizards/source/sfdocuments/SF_Writer.xba
+++ b/wizards/source/sfdocuments/SF_Writer.xba
@@ -26,8 +26,22 @@ Option Explicit
''' the parent methods and properties.
''' They should also duplicate some generic private members as a subset of their own set of members
'''
-''' The SF_Writer module is focused on :
-''' TBD
+''' The SF_Writer module is focused on selecting, reading, inserting, modifying texts and values
+''' on well-identified and predefined places in the document.
+''' Usually such customization of the document starts from a predefined template.
+''' Multiple customizations are also known as mail merging.
+'''
+''' As a consequence, focus is not on text formatting, except by the application of styles
+''' onto the targeted text fragments.
+'''
+''' The positions in the text where customization can take place easily are:
+''' - the start and end positions of the text body
+''' - the start and end positions of text frames
+''' - bookmarks
+''' - text fields
+''' - the start and end positions of document sections
+''' - writer tables and table cells
+''' - the area currently selected by the user, i.e. the "visible" selection
'''
''' The current module is closely related to the "UI" service of the ScriptForge library
'''
@@ -39,12 +53,35 @@ Option Explicit
''' ' or Set oDoc = ui.OpenDocument("C:\Me\MyFile.odt")
''' 2) Directly if the document is already opened
''' Dim oDoc As Object
-''' Set oDoc = CreateScriptService("SFDocuments.Writer", "Untitled 1") ' Default = ActiveWindow
+''' Set oDoc = CreateScriptService("SFDocuments.Writer", ThisComponent) ' Default = ActiveWindow
''' ' or Set oDoc = CreateScriptService("SFDocuments.Writer", "Untitled 1") ' Untitled 1 is presumed a Writer document
''' ' The substring "SFDocuments." in the service name is optional
'''
-''' Definitions:
-''' TBD
+''' Definitions:
+''' Many methods require a "TextRange" as argument.
+''' A textrange is a string describing the scope on which to apply the method.
+''' Such a textrange corresponds either with a single insertion point or with a (text) interval between 2 insertion points.
+''' Multiple textranges are not supported in this context.
+'''
+''' TextRange: a string containing one of next variants :
+''' (names may be surrounded with single or double quotes)
+''' "~" or "SELECTION" or "SEL" = current selection (if multiple selections, its 1st component)
+''' "BODY" = the main text of the actual document instance
+''' "FRAME!name" = the text contained in a text frame
+''' "BOOKMARK!name" = the given bookmark, may be zero or more characters long
+''' "FIELD!name" = a user text field
+''' "SECTION!name" = the text contained in a section
+''' "TABLE!name!" = the whole cellrange of a table
+''' "TABLE!name!cellrange" = a cell (cellrange = "B3") or a range of cells ("A2:B3")
+''' "WORD+3" = 3 words after the current selection
+''' "SENTENCE-1" = the sentence before the current selection
+''' "PARAGRAPH" or "§" = the paragraph containing the current selection (0 is the default)
+''' optionally combined with next control character:
+''' "|": start or end of string
+''' "|~" = the point immediately before the current visible selection (starting point)
+''' "~|" = the point immediately after the current visible selection (ending point)
+''' "~", "|~|" = the full visible selection
+'''
'''
''' Detailed user documentation:
''' https://help.libreoffice.org/latest/en-US/text/sbasic/shared/03/sf_writer.html?DbPAR=BASIC
@@ -54,6 +91,7 @@ Option Explicit
REM ================================================================== EXCEPTIONS
Private Const WRITERFORMNOTFOUNDERROR = "WRITERFORMNOTFOUNDERROR"
+Private Const WRITERRANGEERROR = "WRITERRANGEERROR"
REM ============================================================= PRIVATE MEMBERS
@@ -66,6 +104,22 @@ Private ServiceName As String
' Window component
Private _Component As Object ' com.sun.star.lang.XComponent
+' Text Range
+Type _TextRange
+ RangeString As String ' The input string
+ Target As String ' Selection or Body or Frame or ...
+ TargetName As String ' Name of Frame or Table or ...
+ TargetCell As String ' Cell
+ TargetObject As Object ' Field, TableCell, Section, ... object
+ Offset As Long ' Number of utems to right (+)or to left (-)
+ StartPoint As Boolean ' When True, vertical bar before target
+ EndPoint As Boolean ' When True, vertical bar after target
+ Anchor As Object ' com.sun.star.text.XTextRange
+ Text As Object ' com.sun.star.text.XText
+ Cursor As Object ' com.sun.star.text.XTextCursor
+ Location As String ' BODY or FOOTNOTE or HEADER/FOOTER ...
+End Type
+
REM ============================================================ MODULE CONSTANTS
Const ISDOCFORM = 1 ' Form is stored in a Writer document
@@ -96,6 +150,86 @@ End Function ' SFDocuments.SF_Writer Explicit Destructor
REM ================================================================== PROPERTIES
+REM -----------------------------------------------------------------------------
+Property Get Bookmarks() As Variant
+''' Return the list of currently available bookmarks as a zero-based array
+ Bookmarks = _PropertyGet("Bookmarks")
+End Property ' SFDocuments.SF_Writer.Bookmarks (get)
+
+REM -----------------------------------------------------------------------------
+Property Get CurrentSelection() As Variant
+''' Return the list of currently available CurrentSelection as a zero-based array
+ CurrentSelection = _PropertyGet("CurrentSelection")
+End Property ' SFDocuments.SF_Writer.CurrentSelection (get)
+
+REM -----------------------------------------------------------------------------
+Property Let CurrentSelection(Optional ByVal pvSelection As Variant)
+''' Set the selection to a single or a multiple range
+''' The argument can be:
+''' - a string (a textrange)
+''' - a com.sun.star.text.XTextRange object
+''' - a collection of com.sun.star.text.XTextRange objects
+
+Dim vSelection As Variant ' Alias of pvSelection
+Dim oSelection As Object ' com.sun.star.text.XTextRange
+Dim sType As String ' session.UnoObjectType()
+Dim oSess As Object : Set oSess = ScriptForge.SF_Session
+Dim i As Long
+
+Const cstThisSub = "SFDocuments.Writer.setCurrentSelection"
+Const cstSubArgs = "Selection"
+
+ If ScriptForge.SF_Utils._ErrorHandling() Then On Local Error GoTo Catch
+
+Check:
+ If ScriptForge.SF_Utils._EnterFunction(cstThisSub, cstSubArgs) Then
+ If Not _IsStillAlive(True) Then GoTo Finally
+ If Not ScriptForge.SF_Utils._Validate(pvSelection, "Selection", Array(V_STRING, ScriptForge.V_Object)) Then GoTo Finally
+ End If
+
+Try:
+ vSelection = pvSelection ' Necessary to avoid the "Object variable not set" error
+ With _Component.CurrentController
+ If VarType(vSelection) = V_STRING Then
+ Set oSelection = _ParseRange(vSelection).Cursor
+ If Not IsNull(oSelection) Then .select(oSelection)
+ Else
+ sType = oSess.UnoObjectType(vSelection)
+ Select Case sType
+ Case "SwXTextRanges" ' Argument is a multiple selection
+ For i = 0 To vSelection.Count - 1
+ If oSess.UnoObjectType(vSelection.getByIndex(i)) <> "SwXTextRange" Then GoTo Catch ' Do nothing
+ Next i
+ .select(vSelection)
+ Case "SwXTextRange", "SwXTextCursor", "SwXTextTableCursor" ' Argument is a simple selection (anchor/cursor)
+ .select(vSelection)
+ Case Else
+ End Select
+ End If
+ End With
+
+Finally:
+ ScriptForge.SF_Utils._ExitFunction(cstThisSub)
+ Exit Property
+Catch:
+ GoTo Finally
+End Property ' SFDocuments.SF_Writer.CurrentSelection (let)
+
+REM -----------------------------------------------------------------------------
+Property Get Fields() As Variant
+''' Return the list of currently available fields as a zero-based array
+''' Are considered only next field-types:
+''' - user fields: com.sun.star.text.textfield.User
+''' - variable fields: com.sun.star.text.textfield.SetExpression
+ Fields = _PropertyGet("Fields")
+End Property ' SFDocuments.SF_Writer.Fields (get)
+
+REM -----------------------------------------------------------------------------
+Property Get Frames() As Variant
+''' Return the list of currently available frames as a zero-based array
+ Frames = _PropertyGet("Frames")
+End Property ' SFDocuments.SF_Writer.Frames (get)
+
REM ===================================================================== METHODS
REM -----------------------------------------------------------------------------
@@ -173,12 +307,10 @@ End Function ' SFDocuments.SF_Writer.Forms
REM -----------------------------------------------------------------------------
Public Function GetProperty(Optional ByVal PropertyName As Variant _
- , Optional ObjectName As Variant _
) As Variant
''' Return the actual value of the given property
''' Args:
''' PropertyName: the name of the property as a string
-''' ObjectName: a sheet or range name
''' Returns:
''' The actual value of the property
''' Exceptions:
@@ -191,20 +323,16 @@ Const cstSubArgs = ""
GetProperty = Null
Check:
- If IsMissing(ObjectName) Or IsEmpty(ObjectName) Then ObjectName = ""
If ScriptForge.SF_Utils._EnterFunction(cstThisSub, cstSubArgs) Then
If Not ScriptForge.SF_Utils._Validate(PropertyName, "PropertyName", V_STRING, Properties()) Then GoTo Catch
- If Not ScriptForge.SF_Utils._Validate(ObjectName, "ObjectName", V_STRING) Then GoTo Catch
End If
Try:
' Superclass or subclass property ?
If ScriptForge.SF_Array.Contains([_Super].Properties(), PropertyName) Then
GetProperty = [_Super].GetProperty(PropertyName)
- ElseIf Len(ObjectName) = 0 Then
- GetProperty = _PropertyGet(PropertyName)
Else
- GetProperty = _PropertyGet(PropertyName, ObjectName)
+ GetProperty = _PropertyGet(PropertyName)
End If
Finally:
@@ -305,12 +433,16 @@ Public Function Properties() As Variant
''' Return the list or properties of the Writer class as an array
Properties = Array( _
- "CustomProperties" _
+ "Bookmarks" _
+ , "CurrentSelection" _
+ , "CustomProperties" _
, "Description" _
, "DocumentProperties" _
, "DocumentType" _
, "ExportFilters" _
+ , "Fields" _
, "FileSystem" _
+ , "Frames" _
, "ImportFilters" _
, "IsBase" _
, "IsCalc" _
@@ -665,6 +797,310 @@ Finally:
End Function ' SFDocuments.SF_Writer._IsStillAlive
REM -----------------------------------------------------------------------------
+Private Function _ParseRange(psTextRange As String) As Object
+''' Parse and validate a text range passed as a string
+''' Syntax to parse:
+''' [|]~ or "SELECTION" or "SEL"[|]
+''' [|]BODY[|]
+''' [|]FRAME!name[|]
+''' BOOKMARK!name
+''' FIELD!name
+''' [|]SECTION!name[|]
+''' TABLE!name!cell
+''' [|]WORD±n[|]
+''' [|]SENTENCE±n[|]
+''' [|]PARAGRAPH±n or §±n[|]
+''' A name must be surrounded with single or double quotes when it contains a space or a not alphanumeric character
+''' Returns:
+''' An object of type _TextRange
+''' Exceptions:
+''' WRITERRANGEERROR ' Text range could not be parsed to a valid location
+
+Dim oTextRange As Object ' Return value
+Dim bParsing As Boolean ' When True, parsing could identify the target
+Dim lSelects As Long ' Number of items in the current selection
+Dim sTarget As String ' Alias of _TextRange.Target
+Dim sString As String ' Work variable
+Dim sLeft1 As String ' The 1st character of sString
+Dim sSign As String ' + or -
+Dim oColl As Object ' Collection of TargetObjects (bookmarks or frames or ...)
+Dim oItem As Object ' An item in the oColl collection
+Dim vNames As Variant ' Array of the available object names within a collection
+Dim oStr As Object : Set oStr = ScriptForge.SF_String
+Dim bMove As Boolean ' Return value of a cursor move
+Dim i As Long
+
+ ' Reinitialize a new _TextRange object
+ Set oTextRange = New _TextRange
+ With oTextRange
+ Set .TargetObject = Nothing
+ .RangeString = "" : .Target = "" : .TargetName = "" : .TargetCell = ""
+ .Offset = 0 : .StartPoint = False : .EndPoint = False
+ Set .Anchor = Nothing : Set .Text = Nothing : Set .Cursor = Nothing
+ .Location = ""
+ End With
+
+ ' Identify the type of range with adequate regular expressions
+ With oTextRange
+ .RangeString = psTextRange
+ .StartPoint = ( Left(psTextRange, 1) = "|" )
+ .EndPoint = ( Right(psTextRange, 1) = "|" )
+
+ Select Case True
+ ' Parsing is done with regular expressions because names may really contain any character, including "ç"
+
+ ' Selection
+ Case oStr.IsRegex(psTextRange, "\|?\s*(~|SEL|SELECTION)\s*\|?")
+ .Target = "Selection"
+ If _Component.CurrentSelection.ImplementationName = "SwXTextRanges" Then
+ lSelects = _Component.CurrentSelection.Count
+ If lSelects > 0 Then
+ Set .Anchor = _Component.CurrentSelection.getByIndex(lSelects - 1)
+ If .StartPoint And Not .EndPoint Then
+ Set .Anchor = .Anchor.Start
+ ElseIf Not .StartPoint And .EndPoint Then
+ Set .Anchor = .Anchor.End
+ End If
+ Set .Text = .Anchor.Text
+ Set .Cursor = .Text.createTextCursorByRange(.Anchor)
+ End If
+ End If
+ If IsNull(.Cursor) Then .Location = _Component.CurrentSelection.ImplementationName
+
+ ' WORD, SENTENCE, PARAGRAPH
+ Case oStr.IsRegex(psTextRange, "\|?\s*(PARAGRAPH|§|SENTENCE|WORD)\s*([+-][0-9]+)?\s*\|?")
+ If InStr(psTextRange, "+") > 0 Then
+ sSign = "+"
+ ElseIf InStr(psTextRange, "-") > 0 Then
+ sSign= "-"
+ End If
+ If Len(sSign) > 0 Then sTarget = Split(psTextRange, sSign)(0) Else sTarget = psTextRange
+ If InStr(Iif(.StartPoint, 2, 1), sTarget, "PARAGRAPH", 1) > 0 Or InStr(Iif(.StartPoint, 2, 1), sTarget, "§", 1) > 0 Then
+ .Target = "Paragraph"
+ ElseIf InStr(Iif(.StartPoint, 2, 1), sTarget, "SENTENCE", 1) > 0 Then
+ .Target = "Sentence"
+ ElseIf InStr(Iif(.StartPoint, 2, 1), sTarget, "WORD", 1) > 0 Then
+ .Target = "Word"
+ End If
+
+ ' Identify the offset
+ If Len(sSign) = 0 Then
+ .Offset = 0
+ Else
+ sString = Split(psTextRange, sSign)(1)
+ If .EndPoint Then sString = Left(sString, Len(sString) - 1)
+ .Offset = CLng(sString) * Iif(sSign = "+", 1, -1)
+ End If
+
+ ' Build the cursor pointing at the current selection
+ If _Component.CurrentSelection.ImplementationName = "SwXTextRanges" Then
+ lSelects = _Component.CurrentSelection.Count
+ If lSelects > 0 Then
+ Set .Anchor = _Component.CurrentSelection.getByIndex(lSelects - 1)
+ Set .Text = .Anchor.Text
+ Set .Cursor = .Text.createTextCursorByRange(.Anchor)
+ End If
+ End If
+ If IsNull(.Cursor) Then
+ .Location = _Component.CurrentSelection.ImplementationName
+ Else
+ ' Move the cursor to the requested area
+ With .Cursor
+ Select Case oTextRange.Target
+ Case "Word"
+ bMove = .gotoStartOfWord(False)
+ If bMove Then
+ For i = 1 To Abs(oTextRange.Offset)
+ If sSign = "+" Then bMove = .gotoNextWord(False) Else bMove = .gotoPreviousWord(False)
+ If sSign = "+" Then
+ If Not bMove Then Exit For
+ If .isEndOfSentence() Then i = i - 1 ' Loop to do once more
+ Else
+ bMove = .goLeft(1, False) ' Additional trial to bypass some locks (tabs, list items, ... ?)
+ If Not bMove Then Exit For
+ End If
+ Next i
+ End If
+ ' Cursor is always at the start of a word, move it when necessary
+ If Not oTextRange.StartPoint And oTextRange.EndPoint Then
+ .gotoEndOfWord(False)
+ ElseIf oTextRange.StartPoint = oTextRange.EndPoint Then
+ .gotoEndOfWord(True)
+ End If
+ Case "Sentence"
+ bMove = .gotoStartOfSentence(False)
+ If bMove Then
+ For i = 1 To Abs(oTextRange.Offset)
+ If sSign = "+" Then bMove = .gotoNextSentence(False) Else bMove = .gotoPreviousSentence(False)
+ If sSign = "+" Then
+ If .isEndOfParagraph() Then bMove = .goRight(1, False)
+ Else
+ bMove = .goLeft(1, False) ' Additional trial to bypass some locks (tabs, list items, ... ?)
+ If .isStartOfParagraph() Then bMove = .goLeft(1, False)
+ End If
+ If Not bMove Then Exit For
+ Next i
+ End If
+ ' Cursor is always at the start of a sentence, move it when necessary
+ If Not oTextRange.StartPoint And oTextRange.EndPoint Then
+ .gotoEndOfSentence(False)
+ ElseIf oTextRange.StartPoint = oTextRange.EndPoint Then
+ .gotoEndOfSentence(True)
+ End If
+ Case "Paragraph"
+ bMove = .gotoStartOfParagraph(False)
+ If bMove Then
+ For i = 1 To Abs(oTextRange.Offset)
+ If sSign = "+" Then bMove = .gotoNextParagraph(False) Else bMove = .gotoPreviousParagraph(False)
+ If sSign = "+" Then
+ If .isEndOfParagraph() Then bMove = .goRight(1, False)
+ Else
+ bMove = .goLeft(1, False) ' Additional trial to bypass some locks (tabs, list items, ... ?)
+ If .isStartOfParagraph() Then bMove = .goLeft(1, False)
+ End If
+ If Not bMove Then Exit For
+ Next i
+ End If
+ ' Cursor is always at the start of a Paragraph, move it when necessary
+ If Not oTextRange.StartPoint And oTextRange.EndPoint Then
+ .gotoEndOfParagraph(False)
+ ElseIf oTextRange.StartPoint = oTextRange.EndPoint Then
+ .gotoEndOfParagraph(True)
+ End If
+ End Select
+ End With
+ End If
+
+ ' Bookmarks, Fields, Frames, Sections
+ Case oStr.IsRegex(psTextRange, "\|?\s*(BOOKMARK|FIELD|FRAME|SECTION)!([\w\s]+|'[^']+'|""[^""]+"")\|?")
+ sTarget = Split(psTextRange, "!")(0)
+ If InStr(Iif(.StartPoint, 2, 1), sTarget, "BOOKMARK", 1) > 0 Then
+ .Target = "Bookmark"
+ ElseIf InStr(Iif(.StartPoint, 2, 1), sTarget, "FIELD", 1) > 0 Then
+ .Target = "Field"
+ ElseIf InStr(Iif(.StartPoint, 2, 1), sTarget, "FRAME", 1) > 0 Then
+ .Target = "Frame"
+ ElseIf InStr(Iif(.StartPoint, 2, 1), sTarget, "SECTION", 1) > 0 Then
+ .Target = "Section"
+ End If
+
+ ' Identify section or frame or bookmark or field by its name
+ sString = Split(psTextRange, "!")(1)
+ If .EndPoint Then sString = Left(sString, Len(sString) - 1)
+ sLeft1 = Left(sString, 1)
+ If (sLeft1 = """" Or sLeft1 = "'") And Len(sString) > 2 Then .TargetName = Trim(Mid(sString, 2, Len(sString) - 2)) Else .TargetName = Trim(sString)
+ Select Case .Target
+ Case "Bookmark" : Set oColl = _Component.getBookmarks()
+ Case "Field" : Set oColl = _Component.getTextFieldMasters()
+ .TargetName = "com.sun.star.text.fieldmaster.User." & .TargetName
+ If Not oColl.hasByName(.TargetName) Then .TargetName = Replace(.TargetName, ".User.", ".SetExpression.")
+ Case "Frame" : Set oColl = _Component.getTextFrames()
+ Case "Section" : Set oColl = _Component.getTextSections()
+ End Select
+ If .Target = "Field" Then vNames = Fields() Else vNames = oColl.getElementNames()
+ If Not ScriptForge.SF_Utils._Validate(.TargetName, .Target, V_STRING, vNames) Then GoTo Finally
+ Set .TargetObject = oColl.getByName(.TargetName)
+
+ ' Set text, anchor and cursor: order varies depending on target
+ Select Case .Target
+ Case "Bookmark", "Field", "Section"
+ If .Target = "Field" Then Set .Anchor = .TargetObject.DependentTextFields(0).Anchor Else Set .Anchor = .TargetObject.Anchor
+ If .StartPoint And Not .EndPoint Then
+ Set .Anchor = .Anchor.Start
+ ElseIf Not .StartPoint And .EndPoint Then
+ Set .Anchor = .Anchor.End
+ End If
+ Set .Text = .Anchor.Text
+ Set .Cursor = .Text.createTextCursorByRange(.Anchor)
+ Case "Frame"
+ Set .Text = .TargetObject.Start.Text
+ Set .Anchor = .Text.Anchor
+ Set .Cursor = .Text.createTextCursor()
+ If .StartPoint And Not .EndPoint Then
+ .Cursor.gotoStart(False)
+ ElseIf Not .StartPoint And .EndPoint Then
+ .Cursor.gotoEnd(False)
+ Else
+ .Cursor.gotoStart(False)
+ .Cursor.gotoEnd(True)
+ End If
+ Case Else
+ End Select
+
+ ' Body
+ Case oStr.IsRegex(psTextRange, "\|0\s*?BODY\s*\|?")
+ Set .Text = _Component.Text
+ Set .Anchor = .Text.Start
+ Set .Cursor = .Text.createTextCursor()
+ If .StartPoint And Not .EndPoint Then
+ .Cursor.gotoStart(False)
+ ElseIf Not .StartPoint And .EndPoint Then
+ Set .Anchor = .Text.End
+ .Cursor.gotoEnd(False)
+ Else
+ .Cursor.gotoStart(False)
+ .Cursor.gotoEnd(True)
+ End If
+
+ ' Table cell
+ Case oStr.IsRegex(psTextRange, "\|?\s*TABLE!([\w\s]+|'[^']+'|""[^""]+"")![\s]*[A-Za-z]+[1-9][0-9]*\s*\|?")
+ .Target = "TableCell"
+ ' Identify table by its name
+ sString = Split(psTextRange, "!")(1)
+ sLeft1 = Left(sString, 1)
+ If (sLeft1 = """" Or sLeft1 = "'") And Len(sString) > 2 Then .TargetName = Trim(Mid(sString, 2, Len(sString) - 2)) Else .TargetName = Trim(sString)
+ Set oColl = _Component.getTextTables()
+ vNames = oColl.getElementNames()
+ If Not ScriptForge.SF_Utils._Validate(.TargetName, .Target, V_STRING, vNames) Then GoTo Finally
+ Set oItem = oColl.getByName(.TargetName)
+ .TargetCell = Split(psTextRange, "!")(2)
+ ' Set text, anchor and cursor
+ Set .TargetObject = oItem.getCellByName(.TargetCell)
+ If IsNull(.TargetObject) Then GoTo CatchRange ' The given range is out of the scope of the table
+ Set .Text = .TargetObject.Text
+ Set .Anchor = .Text.Start
+ Set .Cursor = .Text.createTextCursor()
+ If .StartPoint And Not .EndPoint Then
+ .Cursor.gotoStart(False)
+ ElseIf Not .StartPoint And .EndPoint Then
+ Set .Anchor = .Text.End
+ .Cursor.gotoEnd(False)
+ Else
+ .Cursor.gotoStart(False)
+ .Cursor.gotoEnd(True)
+ End If
+
+ Case Else
+ GoTo CatchRange
+ End Select
+
+ ' Determine Location if not yet done
+ If .Location = "" And Not IsNull(.Text) Then
+ Select Case .Text.ImplementationName
+ Case "SwXBodyText" : .Location = "Body"
+ Case "SwXTextFrame" : .Location = "Frame"
+ Case "SwXCell" : .Location = "Cell"
+ Case "SwXHeadFootText" : .Location = "Header/Footer"
+ Case "SwXFootnote" : .Location = "Footnote/Endnote"
+ Case "SwXShape" : .Location = "Shape"
+ Case Else : .Location = .Text.ImplementationName
+ End Select
+ End If
+
+ End With
+
+Finally:
+ Set _ParseRange = oTextRange
+ Exit Function
+CatchError:
+ ScriptForge.SF_Exception.Clear()
+CatchRange:
+ ScriptForge.SF_Exception.RaiseFatal(WRITERRANGEERROR, "TextRange", psTextRange _
+ , "Document", [_Super]._FileIdent())
+ GoTo Finally
+End Function ' SFDocuments.SF_Writer._ParseRange
+
+REM -----------------------------------------------------------------------------
Private Function _PropertyGet(Optional ByVal psProperty As String _
, Optional ByVal pvArg As Variant _
) As Variant
@@ -672,6 +1108,11 @@ Private Function _PropertyGet(Optional ByVal psProperty As String _
''' Args:
''' psProperty: the name of the property
+Dim oFieldMasters As Object ' SwXTextFieldMasters
+Dim vMasters As Variant ' Array of SwXTextFieldMasters
+Dim oMaster As Object ' A single SwXTextFieldMasters
+Dim sField As String ' A text field full name
+Dim vFieldNames As Variant ' Array of field names as strings
Dim cstThisSub As String
Const cstSubArgs = ""
@@ -681,7 +1122,29 @@ Const cstSubArgs = ""
ScriptForge.SF_Utils._EnterFunction(cstThisSub, cstSubArgs)
If Not _IsStillAlive() Then GoTo Finally
- Select Case psProperty
+ Select Case UCase(psProperty)
+ Case UCase("Bookmarks")
+ _PropertyGet = _Component.getBookmarks().getElementNames()
+ Case UCase("CurrentSelection")
+ _PropertyGet = _Component.CurrentSelection
+ Case UCase("Fields")
+ vFieldNames = Array()
+ Set oFieldMasters = _Component.getTextFieldMasters()
+ vMasters = oFieldMasters.getElementNames()
+ For Each sField In vMasters
+ If ScriptForge.SF_String.StartsWith(sField, "com.sun.star.text.fieldmaster.User") Then
+ Set oMaster = oFieldMasters.getByName(sField)
+ vFieldNames = ScriptForge.SF_Array.InsertSorted(vFieldNames, oMaster.Name, CaseSensitive := True)
+ ElseIf ScriptForge.SF_String.StartsWith(sField, "com.sun.star.text.fieldmaster.SetExpression") Then
+ Set oMaster = oFieldMasters.getByName(sField)
+ If oMaster.SubType = com.sun.star.text.SetVariableType.VAR Then
+ vFieldNames = ScriptForge.SF_Array.InsertSorted(vFieldNames, oMaster.Name, CaseSensitive := True)
+ End If
+ End If
+ Next sField
+ _PropertyGet = vFieldNames
+ Case UCase("Frames")
+ _PropertyGet = _Component.getTextFrames().getElementNames()
Case Else
_PropertyGet = Null
End Select