<?xml version="1.0" encoding="UTF-8"?>
<!DOCTYPE script:module PUBLIC "-//OpenOffice.org//DTD OfficeDocument 1.0//EN" "module.dtd">
<script:module xmlns:script="http://openoffice.org/2000/script" script:name="SF_Calc" script:language="StarBasic" script:moduleType="normal">REM =======================================================================================================================
REM ===			The ScriptForge library and its associated libraries are part of the LibreOffice project.				===
REM	===						The SFDocuments library is one of the associated libraries.									===
REM ===					Full documentation is available on https://help.libreoffice.org/								===
REM =======================================================================================================================

Option Compatible
Option ClassModule

Option Explicit

&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;
&apos;&apos;&apos;	SF_Calc
&apos;&apos;&apos;	=======
&apos;&apos;&apos;
&apos;&apos;&apos;		The SFDocuments library gathers a number of methods and properties making easy
&apos;&apos;&apos;		managing and manipulating LibreOffice documents
&apos;&apos;&apos;
&apos;&apos;&apos;		Some methods are generic for all types of documents: they are combined in the SF_Document module.
&apos;&apos;&apos;		Specific properties and methods are implemented in the concerned subclass(es) SF_Calc, SF_Base, ...
&apos;&apos;&apos;
&apos;&apos;&apos;		To workaround the absence of class inheritance in LibreOffice Basic, some redundancy is necessary
&apos;&apos;&apos;		Each subclass MUST implement also the generic methods and properties, even if they only call
&apos;&apos;&apos;		the parent methods and properties.
&apos;&apos;&apos;		They should also duplicate some generic private members as a subset of their own set of members
&apos;&apos;&apos;
&apos;&apos;&apos;		The SF_Calc module is focused on :
&apos;&apos;&apos;			- management (copy, insert, move, ...) of sheets within a Calc document
&apos;&apos;&apos;			- exchange of data between Basic data structures and Calc ranges of values
&apos;&apos;&apos;
&apos;&apos;&apos;		The current module is closely related to the &quot;UI&quot; service of the ScriptForge library
&apos;&apos;&apos;
&apos;&apos;&apos;		Service invocation examples:
&apos;&apos;&apos;		1) From the UI service
&apos;&apos;&apos;			Dim ui As Object, oDoc As Object
&apos;&apos;&apos;			Set ui = CreateScriptService(&quot;UI&quot;)
&apos;&apos;&apos;			Set oDoc = ui.CreateDocument(&quot;Calc&quot;, ...)
&apos;&apos;&apos;				&apos; or Set oDoc = ui.OpenDocument(&quot;C:\Me\MyFile.ods&quot;)
&apos;&apos;&apos;		2) Directly if the document is already opened
&apos;&apos;&apos;			Dim oDoc As Object
&apos;&apos;&apos;			Set oDoc = CreateScriptService(&quot;SFDocuments.Calc&quot;, &quot;Untitled 1&quot;)	&apos;	Default = ActiveWindow
&apos;&apos;&apos;				&apos; or Set oDoc = CreateScriptService(&quot;SFDocuments.Calc&quot;, &quot;Untitled 1&quot;)	&apos;	Untitled 1 is presumed a Calc document
&apos;&apos;&apos;			&apos; The substring &quot;SFDocuments.&quot; in the service name is optional
&apos;&apos;&apos;
&apos;&apos;&apos;		Definitions:
&apos;&apos;&apos;
&apos;&apos;&apos;			Many methods require a &quot;Sheet&quot; or a &quot;Range&quot; as argument. (NB: a single cell is considered as a special case of a Range)
&apos;&apos;&apos;			Usually, within a specific Calc instance, sheets and ranges are given as a string: &quot;SheetX&quot; and &quot;D2:F6&quot;
&apos;&apos;&apos;			Multiple ranges are not supported in this context.
&apos;&apos;&apos;			Additionally, the .Sheet and .Range methods return a reference that may be used
&apos;&apos;&apos;			as argument of a method called from another instance of the Calc service
&apos;&apos;&apos;			Example:
&apos;&apos;&apos;				Dim oDocA As Object	:	Set oDocA = ui.OpenDocument(&quot;C:\FileA.ods&quot;, Hidden := True, ReadOnly := True)
&apos;&apos;&apos;				Dim oDocB As Object	:	Set oDocB = ui.OpenDocument(&quot;C:\FileB.ods&quot;)
&apos;&apos;&apos;				oDocB.CopyToRange(oDocA.Range(&quot;SheetX.D4:F8&quot;), &quot;D2:F6&quot;)	&apos; CopyToRange(source, target)
&apos;&apos;&apos;
&apos;&apos;&apos;			Sheet: the sheet name as a string or an object produced by .Sheet()
&apos;&apos;&apos;						&quot;~&quot; = current sheet
&apos;&apos;&apos;			Range: a string designating a set of contiguous cells located in a sheet of the current instance
&apos;&apos;&apos;						&quot;~&quot; = current selection (if multiple selections, its 1st component)
&apos;&apos;&apos;					or an object produced by .Range()
&apos;&apos;&apos;				The sheet name is optional (default = active sheet). Surrounding quotes and $ signs are optional
&apos;&apos;&apos;					~.~, ~							The current selection in the active sheet
&apos;&apos;&apos;					&apos;$SheetX&apos;.D2 or $D$2			A single cell
&apos;&apos;&apos;					&apos;$SheetX&apos;.D2:F6, D2:D10			Multiple cells
&apos;&apos;&apos;					&apos;$SheetX&apos;.A:A or 3:5			All cells in the same column or row up to the last active cell
&apos;&apos;&apos;					SheetX.*						All cells up to the last active cell
&apos;&apos;&apos;					myRange							A range name at spreadsheet level
&apos;&apos;&apos;					~.yourRange, SheetX.someRange	A range name at sheet level
&apos;&apos;&apos;					myDoc.Range(&quot;SheetX.D2:F6&quot;)
&apos;&apos;&apos;											A range within the sheet SheetX in file associated with the myDoc Calc instance
&apos;&apos;&apos;
&apos;&apos;&apos;			Several methods may receive a &quot;FilterFormula&quot; as argument.
&apos;&apos;&apos;			A FilterFormula may be associated with a FilterScope: &quot;row&quot;, &quot;column&quot; or &quot;cell&quot;.
&apos;&apos;&apos;			These arguments determines on which rows/columns/cells of a range the method should be applied
&apos;&apos;&apos;			Examples:
&apos;&apos;&apos;				oDoc.ClearAll(&quot;A1:J10&quot;, FilterFormula := &quot;=(A1&lt;=0)&quot;, FilterScope := &quot;CELL&quot;)		&apos;	Clear all negative values
&apos;&apos;&apos;				oDoc.ClearAll(&quot;A2:J10&quot;, FilterFormula := &quot;=(A2&lt;&gt;A1)&quot;, FilterScope := &quot;COLUMN&quot;)	&apos;	Clear when identical to above cell
&apos;&apos;&apos;
&apos;&apos;&apos;				FilterFormula:	a Calc formula that returns TRUE or FALSE
&apos;&apos;&apos;								the formula is expressed in terms of
&apos;&apos;&apos;									- the top-left cell of the range when FilterScope = &quot;CELL&quot;
&apos;&apos;&apos;									- the topmost row of the range when FilterScope = &quot;ROW&quot;
&apos;&apos;&apos;									- the leftmost column of the range when FilterScope = &quot;COLUMN&quot;
&apos;&apos;&apos;								relative and absolute references will be interpreted correctly
&apos;&apos;&apos;				FilterScope:	the way the formula is applied, once by row, by column, or by individual cell
&apos;&apos;&apos;
&apos;&apos;&apos;		Detailed user documentation:
&apos;&apos;&apos;			https://help.libreoffice.org/latest/en-US/text/sbasic/shared/03/sf_calc.html?DbPAR=BASIC
&apos;&apos;&apos;
&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;&apos;

REM ================================================================== EXCEPTIONS

Private Const UNKNOWNFILEERROR		=	&quot;UNKNOWNFILEERROR&quot;
Private Const BASEDOCUMENTOPENERROR	=	&quot;BASEDOCUMENTOPENERROR&quot;
Private Const CALCADDRESSERROR		=	&quot;CALCADDRESSERROR&quot;
Private Const DUPLICATESHEETERROR	=	&quot;DUPLICATESHEETERROR&quot;
Private Const OFFSETADDRESSERROR	=	&quot;OFFSETADDRESSERROR&quot;
Private Const CALCFORMNOTFOUNDERROR	=	&quot;CALCFORMNOTFOUNDERROR&quot;
Private Const DUPLICATECHARTERROR	=	&quot;DUPLICATECHARTERROR&quot;
Private Const RANGEEXPORTERROR		=	&quot;RANGEEXPORTERROR&quot;

REM ============================================================= PRIVATE MEMBERS

Private [Me]					As Object
Private [_Super]				As Object		&apos;	Document superclass, which the current instance is a subclass of
Private ObjectType				As String		&apos;	Must be CALC
Private ServiceName				As String

&apos;	Window component
Private _Component				As Object		&apos;	com.sun.star.lang.XComponent

Type _Address
	ObjectType					As String		&apos;	Must be &quot;SF_CalcReference&quot;
	ServiceName					As String		&apos;	Must be &quot;SFDocuments.CalcReference&quot;
	RawAddress					As String
	Component					As Object		&apos;	com.sun.star.lang.XComponent
	SheetName					As String
	SheetIndex					As Integer
	RangeName					As String
	Height						As Long
	Width						As Long
	XSpreadSheet				As Object		&apos;	com.sun.star.sheet.XSpreadsheet
	XCellRange					As Object		&apos;	com.sun.star.table.XCellRange
End Type

Private _LastParsedAddress		As Object		&apos;	_Address type - parsed ranges are cached

REM ============================================================ MODULE CONSTANTS

Private Const cstSHEET			= 1
Private Const cstRANGE			= 2

Private Const MAXCOLS			= 2^14					&apos;	Max number of columns in a sheet
Private Const MAXROWS			= 2^20					&apos;	Max number of rows in a sheet

Private Const CALCREFERENCE		= &quot;SF_CalcReference&quot;	&apos;	Object type of _Address
Private Const SERVICEREFERENCE	= &quot;SFDocuments.CalcReference&quot;
														&apos;	Service name of _Address (used in Python)

Private Const ISCALCFORM		= 2						&apos;	Form is stored in a Calc document

Private Const cstSPECIALCHARS	= &quot; `~!@#$%^&amp;()-_=+{}|;,&lt;.&gt;&quot;&quot;&quot;
			&apos;	Presence of a special character forces surrounding the sheet name with single quotes in absolute addresses


REM ====================================================== CONSTRUCTOR/DESTRUCTOR

REM -----------------------------------------------------------------------------
Private Sub Class_Initialize()
	Set [Me] = Nothing
	Set [_Super] = Nothing
	ObjectType = &quot;CALC&quot;
	ServiceName = &quot;SFDocuments.Calc&quot;
	Set _Component = Nothing
	Set _LastParsedAddress = Nothing
End Sub		&apos;	SFDocuments.SF_Calc Constructor

REM -----------------------------------------------------------------------------
Private Sub Class_Terminate()
	Call Class_Initialize()
End Sub		&apos;	SFDocuments.SF_Calc Destructor

REM -----------------------------------------------------------------------------
Public Function Dispose() As Variant
	If Not IsNull([_Super]) Then Set [_Super] = [_Super].Dispose()
	Call Class_Terminate()
	Set Dispose = Nothing
End Function	&apos;	SFDocuments.SF_Calc Explicit Destructor

REM ================================================================== PROPERTIES

REM -----------------------------------------------------------------------------
Property Get CurrentSelection() As Variant
&apos;&apos;&apos;	Returns as a string the currently selected range or as an array the list of the currently selected ranges
	CurrentSelection = _PropertyGet(&quot;CurrentSelection&quot;)
End Property	&apos;	SFDocuments.SF_Calc.CurrentSelection (get)

REM -----------------------------------------------------------------------------
Property Let CurrentSelection(Optional ByVal pvSelection As Variant)
&apos;&apos;&apos;	Set the selection to a single or a multiple range
&apos;&apos;&apos;	The argument is a string or an array of strings

Dim sRange As String			&apos;	A single selection
Dim oCellRanges	As Object		&apos;	com.sun.star.sheet.SheetCellRanges
Dim vRangeAddresses As Variant	&apos;	Array of com.sun.star.table.CellRangeAddress
Dim i As Long
Const cstThisSub = &quot;SFDocuments.Calc.setCurrentSelection&quot;
Const cstSubArgs = &quot;Selection&quot;

	On Local Error GoTo Catch

Check:
	If ScriptForge.SF_Utils._EnterFunction(cstThisSub, cstSubArgs) Then
		If Not _IsStillAlive(True) Then GoTo Finally
		If IsArray(pvSelection) Then
			If Not ScriptForge.SF_Utils._ValidateArray(pvSelection, &quot;pvSelection&quot;, 1, V_STRING, True)  Then GoTo Finally
		Else
			If Not ScriptForge.SF_Utils._Validate(pvSelection, &quot;pvSelection&quot;, V_STRING) Then GoTo Finally
		End If
	End If

Try:
	If IsArray(pvSelection) Then
		Set oCellRanges = _Component.createInstance(&quot;com.sun.star.sheet.SheetCellRanges&quot;)
		vRangeAddresses = Array()
		ReDim vRangeAddresses(0 To UBound(pvSelection))
		For i = 0 To UBound(pvSelection)
			vRangeAddresses(i) = Range(pvSelection(i)).XCellRange.RangeAddress
		Next i
		oCellRanges.addRangeAddresses(vRangeAddresses, False)
		_Component.CurrentController.select(oCellRanges)
	Else
		_Component.CurrentController.select(_ParseAddress(pvSelection).XCellRange)
	End If

Finally:
	ScriptForge.SF_Utils._ExitFunction(cstThisSub)
	Exit Property
Catch:
	GoTo Finally
End Property	&apos;	SFDocuments.SF_Calc.CurrentSelection (let)

REM -----------------------------------------------------------------------------
Property Get FirstCell(Optional ByVal RangeName As Variant) As String
&apos;&apos;&apos;	Returns the First used cell in a given range or sheet
&apos;&apos;&apos;	When the argument is a sheet it will always return the &quot;sheet.$A$1&quot; cell
	FirstCell = _PropertyGet(&quot;FirstCell&quot;, RangeName)
End Property	&apos;	SFDocuments.SF_Calc.FirstCell

REM -----------------------------------------------------------------------------
Property Get FirstColumn(Optional ByVal RangeName As Variant) As Long
&apos;&apos;&apos;	Returns the leftmost column in a given sheet or range
&apos;&apos;&apos;	When the argument is a sheet it will always return 1
	FirstColumn = _PropertyGet(&quot;FirstColumn&quot;, RangeName)
End Property	&apos;	SFDocuments.SF_Calc.FirstColumn

REM -----------------------------------------------------------------------------
Property Get FirstRow(Optional ByVal RangeName As Variant) As Long
&apos;&apos;&apos;	Returns the First used column in a given range
&apos;&apos;&apos;	When the argument is a sheet it will always return 1
	FirstRow = _PropertyGet(&quot;FirstRow&quot;, RangeName)
End Property	&apos;	SFDocuments.SF_Calc.FirstRow

REM -----------------------------------------------------------------------------
Property Get Height(Optional ByVal RangeName As Variant) As Long
&apos;&apos;&apos;	Returns the height in # of rows of the given range
	Height = _PropertyGet(&quot;Height&quot;, RangeName)
End Property	&apos;	SFDocuments.SF_Calc.Height

REM -----------------------------------------------------------------------------
Property Get LastCell(Optional ByVal RangeName As Variant) As String
&apos;&apos;&apos;	Returns the last used cell in a given sheet or range
	LastCell = _PropertyGet(&quot;LastCell&quot;, RangeName)
End Property	&apos;	SFDocuments.SF_Calc.LastCell

REM -----------------------------------------------------------------------------
Property Get LastColumn(Optional ByVal RangeName As Variant) As Long
&apos;&apos;&apos;	Returns the last used column in a given sheet
	LastColumn = _PropertyGet(&quot;LastColumn&quot;, RangeName)
End Property	&apos;	SFDocuments.SF_Calc.LastColumn

REM -----------------------------------------------------------------------------
Property Get LastRow(Optional ByVal RangeName As Variant) As Long
&apos;&apos;&apos;	Returns the last used column in a given sheet
	LastRow = _PropertyGet(&quot;LastRow&quot;, RangeName)
End Property	&apos;	SFDocuments.SF_Calc.LastRow

REM -----------------------------------------------------------------------------
Property Get Range(Optional ByVal RangeName As Variant) As Variant
&apos;&apos;&apos;	Returns a (internal) range object
	Range = _PropertyGet(&quot;Range&quot;, RangeName)
End Property	&apos;	SFDocuments.SF_Calc.Range

REM -----------------------------------------------------------------------------
Property Get Region(Optional ByVal RangeName As Variant) As String
&apos;&apos;&apos;	Returns the smallest area as a range string that contains the given range
&apos;&apos;&apos;	and which is completely surrounded with empty cells
	Region = _PropertyGet(&quot;Region&quot;, RangeName)
End Property	&apos;	SFDocuments.SF_Calc.Region

REM -----------------------------------------------------------------------------
Property Get Sheet(Optional ByVal SheetName As Variant) As Variant
&apos;&apos;&apos;	Returns a (internal) sheet object
	Sheet = _PropertyGet(&quot;Sheet&quot;, SheetName)
End Property	&apos;	SFDocuments.SF_Calc.Sheet

REM -----------------------------------------------------------------------------
Property Get SheetName(Optional ByVal RangeName As Variant) As String
&apos;&apos;&apos;	Returns the sheet name part of a range
	SheetName = _PropertyGet(&quot;SheetName&quot;, RangeName)
End Property	&apos;	SFDocuments.SF_Calc.SheetName

REM -----------------------------------------------------------------------------
Property Get Sheets() As Variant
&apos;&apos;&apos;	Returns an array listing the existing sheet names
	Sheets = _PropertyGet(&quot;Sheets&quot;)
End Property	&apos;	SFDocuments.SF_Calc.Sheets

REM -----------------------------------------------------------------------------
Property Get Width(Optional ByVal RangeName As Variant) As Long
&apos;&apos;&apos;	Returns the width in # of columns of the given range
	Width = _PropertyGet(&quot;Width&quot;, RangeName)
End Property	&apos;	SFDocuments.SF_Calc.Width

REM -----------------------------------------------------------------------------
Property Get XCellRange(Optional ByVal RangeName As Variant) As Variant
&apos;&apos;&apos;	Returns a UNO object of type com.sun.star.Table.CellRange
	XCellRange = _PropertyGet(&quot;XCellRange&quot;, RangeName)
End Property	&apos;	SFDocuments.SF_Calc.XCellRange

REM -----------------------------------------------------------------------------
Property Get XSheetCellCursor(Optional ByVal RangeName As Variant) As Variant
&apos;&apos;&apos;	Returns a UNO object of type com.sun.star.sheet.XSheetCellCursor
&apos;&apos;	After having moved the cursor (gotoNext(), ...) the resulting range can be got
&apos;&apos;&apos;	back as a string with the cursor.AbsoluteName UNO property.
	XSheetCellCursor = _PropertyGet(&quot;XSheetCellCursor&quot;, RangeName)
End Property	&apos;	SFDocuments.SF_Calc.XSheetCellCursor

REM -----------------------------------------------------------------------------
Property Get XSpreadsheet(Optional ByVal SheetName As Variant) As Variant
&apos;&apos;&apos;	Returns a UNO object of type com.sun.star.sheet.XSpreadsheet
	XSpreadsheet = _PropertyGet(&quot;XSpreadsheet&quot;, SheetName)
End Property	&apos;	SFDocuments.SF_Calc.XSpreadsheet

REM ===================================================================== METHODS

REM -----------------------------------------------------------------------------
Public Function A1Style(Optional ByVal Row1 As Variant _
								, Optional ByVal Column1 As Variant _
								, Optional ByVal Row2 As Variant _
								, Optional ByVal Column2 As Variant _
								, Optional ByVal SheetName As Variant _
								) As String
&apos;&apos;&apos;	Returns a range expressed in A1-style as defined by its coordinates
&apos;&apos;&apos;	If only one pair of coordinates is given, the range will embrace only a single cell
&apos;&apos;&apos;	Args:
&apos;&apos;&apos;		Row1 : the row number of the first coordinate
&apos;&apos;&apos;		Column1 : the column number of the first coordinates
&apos;&apos;&apos;		Row2 : the row number of the second coordinate
&apos;&apos;&apos;		Column2 : the column number of the second coordinates
&apos;&apos;&apos;		SheetName: Default = the current sheet. If present, the sheet must exist.
&apos;&apos;&apos;	Returns:
&apos;&apos;&apos;		A range as a string
&apos;&apos;&apos;	Exceptions:
&apos;&apos;&apos;	Examples:
&apos;&apos;&apos;		range = oDoc.A1Style(5, 2, 10, 4, &quot;SheetX&quot;)		&apos;	&quot;&apos;$SheetX&apos;.$E$2:$J$4&quot;

Dim sA1Style As String				&apos;	Return value
Dim vSheetName As Variant			&apos;	Alias of SheetName - necessary see [Bug 145279]
Dim lTemp As Long					&apos;	To switch 2 values
Dim i As Long

Const cstThisSub = &quot;SFDocuments.Calc.A1Style&quot;
Const cstSubArgs = &quot;Row1, Column1, [Row2], [Column2], [SheetName]=&quot;&quot;&quot;&quot;&quot;

	If ScriptForge.SF_Utils._ErrorHandling() Then On Local Error GoTo Catch
	sA1Style = &quot;&quot;

Check:
	If IsMissing(Row2) Or IsEmpty(Row2) Then Row2 = 0
	If IsMissing(Column2) Or IsEmpty(Column2) Then Column2 = 0
	If IsMissing(SheetName) Or IsEmpty(SheetName) Then SheetName = &quot;~&quot;
	vSheetName = SheetName

	If ScriptForge.SF_Utils._EnterFunction(cstThisSub, cstSubArgs) Then
		If Not _IsStillAlive() Then GoTo Finally
		If Not ScriptForge.SF_Utils._Validate(Row1, &quot;Row1&quot;, ScriptForge.V_NUMERIC) Then GoTo Finally
		If Not ScriptForge.SF_Utils._Validate(Column1, &quot;Column1&quot;, ScriptForge.V_NUMERIC) Then GoTo Finally
		If Not ScriptForge.SF_Utils._Validate(Row2, &quot;Row2&quot;, ScriptForge.V_NUMERIC) Then GoTo Finally
		If Not ScriptForge.SF_Utils._Validate(Column2, &quot;Column2&quot;, ScriptForge.V_NUMERIC) Then GoTo Finally
		If Not _ValidateSheet(vSheetName, &quot;SheetName&quot;, , True, True, , , True) Then GoTo Finally
	End If

	If Row1 &gt; MAXROWS Then Row1 = MAXROWS
	If Row2 &gt; MAXROWS Then Row2 = MAXROWS
	If Column1 &gt; MAXCOLS Then Column1 = MAXCOLS
	If Column2 &gt; MAXCOLS Then Column2 = MAXCOLS

	If Row2 &gt; 0 And Row2 &lt; Row1 Then
		lTemp = Row2	:	Row2 = Row1	:	Row1 = lTemp
	End If
	If Column2 &gt; 0 And Column2 &lt; Column1 Then
		lTemp = Column2	:	Column2 = Column1	:	Column1 = lTemp
	End If

Try:
	&apos;	Surround the sheet name with single quotes when required by the presence of special characters
	vSheetName = _QuoteSheetName(vSheetName)
	&apos;	Define the new range string
	sA1Style = &quot;$&quot; &amp; vSheetName &amp; &quot;.&quot; _
					&amp; &quot;$&quot; &amp; _GetColumnName(Column1) &amp; &quot;$&quot; &amp; CLng(Row1) _
					&amp; Iif(Row2 &gt; 0 And Column2 &gt; 0, &quot;:$&quot; &amp; _GetColumnName(Column2) &amp; &quot;$&quot; &amp; CLng(Row2), &quot;&quot;)

Finally:
	A1Style = sA1Style
	ScriptForge.SF_Utils._ExitFunction(cstThisSub)
	Exit Function
Catch:
	GoTo Finally
End Function	&apos;	SFDocuments.SF_Calc.A1Style

REM -----------------------------------------------------------------------------
Public Function Activate(Optional ByVal SheetName As Variant) As Boolean
&apos;&apos;&apos; Make the current document or the given sheet active
&apos;&apos;&apos;	Args:
&apos;&apos;&apos;		SheetName: Default = the Calc document as a whole
&apos;&apos;&apos;	Returns:
&apos;&apos;&apos;		True if the document or the sheet could be made active
&apos;&apos;&apos;		Otherwise, there is no change in the actual user interface
&apos;&apos;&apos;	Examples:
&apos;&apos;&apos;		oDoc.Activate(&quot;SheetX&quot;)

Dim bActive As Boolean				&apos;	Return value
Dim oSheet As Object				&apos;	Reference to sheet
Const cstThisSub = &quot;SFDocuments.Calc.Activate&quot;
Const cstSubArgs = &quot;[SheetName]&quot;

	If ScriptForge.SF_Utils._ErrorHandling() Then On Local Error GoTo Catch
	bActive = False

Check:
	If IsMissing(SheetName) Or IsEmpty(SheetName) Then SheetName = &quot;&quot;
	If ScriptForge.SF_Utils._EnterFunction(cstThisSub, cstSubArgs) Then
		If Not _IsStillAlive() Then GoTo Finally
		If Not _ValidateSheet(SheetName, &quot;SheetName&quot;, , , True) Then GoTo Finally
	End If

Try:
	&apos;	Sheet activation, to do only when meaningful, precedes document activation
	If Len(SheetName) &gt; 0 Then
		With _Component
			Set oSheet = .getSheets.getByName(SheetName)
			Set .CurrentController.ActiveSheet = oSheet
		End With
	End If
	bActive = [_Super].Activate()

Finally:
	Activate = bActive
	ScriptForge.SF_Utils._ExitFunction(cstThisSub)
	Exit Function
Catch:
	GoTo Finally
End Function    &apos;   SFDocuments.SF_Calc.Activate

REM -----------------------------------------------------------------------------
Public Function Charts(Optional ByVal SheetName As Variant _
							, Optional ByVal ChartName As Variant _
							) As Variant
&apos;&apos;&apos; Return either the list of charts present in the given sheet or a chart object
&apos;&apos;&apos;	Args:
&apos;&apos;&apos;		SheetName: The name of an existing sheet
&apos;&apos;&apos;		ChartName: The user-defined name of the targeted chart or the zero-length string
&apos;&apos;&apos;	Returns:
&apos;&apos;&apos;		When ChartName = &quot;&quot;, return the list of the charts present in the sheet,
&apos;&apos;&apos;		otherwise, return a new chart service instance
&apos;&apos;&apos;	Examples:
&apos;&apos;&apos;		Dim oChart As Object
&apos;&apos;&apos;		Set oChart = oDoc.Charts(&quot;SheetX&quot;, &quot;myChart&quot;)

Dim vCharts As Variant				&apos;	Return value when array of chart names
Dim oChart As Object				&apos;	Return value when new chart instance
Dim oSheet As Object				&apos;	Alias of SheetName as reference
Dim oDrawPage As Object				&apos;	com.sun.star.drawing.XDrawPage
Dim oNextShape As Object			&apos;	com.sun.star.drawing.XShape
Dim sChartName As String			&apos;	Some chart name
Dim lCount As Long					&apos;	Counter for charts among all drawing objects
Dim i As Long
Const cstChartShape = &quot;com.sun.star.drawing.OLE2Shape&quot;

Const cstThisSub = &quot;SFDocuments.Calc.Charts&quot;
Const cstSubArgs = &quot;SheetName, [ChartName=&quot;&quot;&quot;&quot;]&quot;

	If ScriptForge.SF_Utils._ErrorHandling() Then On Local Error GoTo Catch
	vCharts = Array()

Check:
	If IsMissing(ChartName) Or IsEmpty(ChartName) Then ChartName = &quot;&quot;
	If ScriptForge.SF_Utils._EnterFunction(cstThisSub, cstSubArgs) Then
		If Not _IsStillAlive(True) Then GoTo Finally
		If Not _ValidateSheet(SheetName, &quot;SheetName&quot;, , True) Then GoTo Finally
		If Not ScriptForge.SF_Utils._Validate(ChartName, &quot;ChartName&quot;, V_STRING) Then GoTo Finally
	End If

Try:
	&apos;	Because the user can change it constantly, the list of valid charts has to be rebuilt at each time
	&apos;	Explore charts starting from the draw page
	Set oSheet = _Component.getSheets.getByName(SheetName)
	Set oDrawPage = oSheet.getDrawPage()
	vCharts = Array()
	Set oChart = Nothing
	lCount = -1
	For i = 0 To oDrawPage.Count - 1
		Set oNextShape = oDrawPage.getByIndex(i)
		if oNextShape.supportsService(cstChartShape) Then		&apos;	Ignore other shapes
			sChartName = oNextShape.Name										&apos;	User-defined name
			If Len(sChartName) = 0 Then sChartName = oNextShape.PersistName		&apos;	Internal name
			&apos;	Is chart found ?
			If Len(ChartName) &gt; 0 Then
				If ChartName = sChartName Then
					Set oChart = New SF_Chart
					With oChart
						Set .[Me] = oChart
						Set .[_Parent] = [Me]
						._SheetName = SheetName
						._DrawIndex = i
						._ChartName = ChartName
						._PersistentName = oNextShape.PersistName
						Set ._Shape = oNextShape
						Set ._Chart = oSheet.getCharts().getByName(._PersistentName)
						Set ._ChartObject = ._Chart.EmbeddedObject
						Set ._Diagram = ._ChartObject.Diagram
					End With
					Exit For
				End If
			End If
			&apos;	Build stack of chart names
			lCount = lCount + 1
			If UBound(vCharts) &lt; 0 Then
				vCharts = Array(sChartName)
			Else
				ReDim Preserve vCharts(0 To UBound(vCharts) + 1)
				vCharts(lCount) = sChartName
			End If
		End If
	Next i

	&apos;	Raise error when chart not found
	If Len(ChartName) &gt; 0 And IsNull(oChart) Then
		If Not ScriptForge.SF_Utils._Validate(ChartName, &quot;ChartName&quot;, V_STRING, vCharts) Then GoTo Finally
	End If

Finally:
	If Len(ChartName) = 0 Then Charts = vCharts Else Set Charts = oChart
	ScriptForge.SF_Utils._ExitFunction(cstThisSub)
	Exit Function
Catch:
	GoTo Finally
End Function    &apos;   SFDocuments.SF_Calc.Charts

REM -----------------------------------------------------------------------------
Public Sub ClearAll(Optional ByVal Range As Variant _
							, Optional FilterFormula As Variant _
							, Optional FilterScope As Variant _
							)
&apos;&apos;&apos;	Clear entirely the given range
&apos;&apos;&apos;	Args:
&apos;&apos;&apos;		Range : the cell or the range as a string that should be cleared
&apos;&apos;&apos;		FilterFormula: a Calc formula to select among the given Range
&apos;&apos;&apos;			When left empty, all the cells of the range are cleared
&apos;&apos;&apos;		FilterScope: &quot;CELL&quot; (default value), &quot;ROW&quot; or &quot;COLUMN&quot;
&apos;&apos;&apos;			When FilterFormula is present, FilterScope is mandatory
&apos;&apos;&apos;	Examples:
&apos;&apos;&apos;		oDoc.ClearAll(&quot;SheetX&quot;)						&apos; Clears the used area of the sheet
&apos;&apos;&apos;		oDoc.ClearAll(&quot;A1:J20&quot;, &quot;=($A1=0)&quot;, &quot;ROW&quot;)	&apos; Clears all rows when 1st cell is zero

	_ClearRange(&quot;All&quot;, Range, FilterFormula, FilterScope)

End Sub	&apos;	SFDocuments.SF_Calc.ClearAll

REM -----------------------------------------------------------------------------
Public Sub ClearFormats(Optional ByVal Range As Variant _
							, Optional FilterFormula As Variant _
							, Optional FilterScope As Variant _
							)
&apos;&apos;&apos;	Clear all the formatting elements of the given range
&apos;&apos;&apos;	Args:
&apos;&apos;&apos;		Range : the cell or the range as a string that should be cleared
&apos;&apos;&apos;		FilterFormula: a Calc formula to select among the given Range
&apos;&apos;&apos;			When left empty, all the cells of the range are cleared
&apos;&apos;&apos;		FilterScope: &quot;CELL&quot; (default value), &quot;ROW&quot; or &quot;COLUMN&quot;
&apos;&apos;&apos;			When FilterFormula is present, FilterScope is mandatory
&apos;&apos;&apos;	Examples:
&apos;&apos;&apos;		oDoc.ClearFormats(&quot;SheetX.*&quot;)							&apos; Clears the used area of the sheet
&apos;&apos;&apos;		oDoc.ClearFormats(&quot;A1:J20&quot;, &quot;=(MOD(A1;0)=0)&quot;, &quot;CELL&quot;)	&apos; Clears all even cells

	_ClearRange(&quot;Formats&quot;, Range, FilterFormula, FilterScope)

End Sub	&apos;	SFDocuments.SF_Calc.ClearFormats

REM -----------------------------------------------------------------------------
Public Sub ClearValues(Optional ByVal Range As Variant _
							, Optional FilterFormula As Variant _
							, Optional FilterScope As Variant _
							)
&apos;&apos;&apos;	Clear values and formulas in the given range
&apos;&apos;&apos;	Args:
&apos;&apos;&apos;		Range : the cell or the range as a string that should be cleared
&apos;&apos;&apos;		FilterFormula: a Calc formula to select among the given Range
&apos;&apos;&apos;			When left empty, all the cells of the range are cleared
&apos;&apos;&apos;		FilterScope: &quot;CELL&quot; (default value), &quot;ROW&quot; or &quot;COLUMN&quot;
&apos;&apos;&apos;			When FilterFormula is present, FilterScope is mandatory
&apos;&apos;&apos;	Examples:
&apos;&apos;&apos;		oDoc.ClearValues(&quot;SheetX.*&quot;)					&apos; Clears the used area of the sheet
&apos;&apos;&apos;		oDoc.ClearValues(&quot;A2:A20&quot;, &quot;=(A2=A1)&quot;, &quot;CELL&quot;)	&apos; Clears all duplicate cells

	_ClearRange(&quot;Values&quot;, Range, FilterFormula, FilterScope)

End Sub	&apos;	SFDocuments.SF_Calc.ClearValues

REM -----------------------------------------------------------------------------
Public Function CompactLeft(Optional ByVal Range As Variant _
								, Optional ByVal WholeColumn As Variant _
								, Optional ByVal FilterFormula As Variant _
								) As String
&apos;&apos;&apos;	Delete the columns of a specified range matching a filter expressed as a formula
&apos;&apos;&apos;	applied on each column.
&apos;&apos;&apos;	The deleted cells can span whole columns or be limited to the height of the range
&apos;&apos;&apos;	The execution of the method has no effect on the current selection
&apos;&apos;&apos;	Args:
&apos;&apos;&apos;		Range: the range in which cells have to be erased, as a string
&apos;&apos;&apos;		WholeColumn: when True (default = False), erase whole columns
&apos;&apos;&apos;		FilterFormula: the formula to be applied on each column.
&apos;&apos;&apos;			The column is erased when the formula results in True,
&apos;&apos;&apos;			The formula shall probably involve one or more cells of the first column of the range.
&apos;&apos;&apos;			By default, a column is erased when all the cells of the column are empty,
&apos;&apos;&apos;			i.e. suppose the range is &quot;A1:J200&quot; (height = 200) the default value becomes
&apos;&apos;&apos;				&quot;=(COUNTBLANK(A1:A200)=200)&quot;
&apos;&apos;&apos;	Returns:
&apos;&apos;&apos;		A string representing the location of the initial range after compaction,
&apos;&apos;&apos;		or the zero-length string if the whole range has been deleted
&apos;&apos;&apos;	Examples:
&apos;&apos;&apos;		newrange = oDoc.CompactLeft(&quot;SheetX.G1:L10&quot;)	&apos;	All empty columns of the range are suppressed
&apos;&apos;&apos;		newrange = oDoc.CompactLeft(&quot;SheetX.G1:L10&quot;, WholeColumn := True, FilterFormula := &quot;=(G$7=&quot;&quot;X&quot;&quot;)&quot;)
&apos;&apos;&apos;			&apos;	The columns having a &quot;X&quot; in row 7 are completely suppressed

Dim sCompact As String			&apos;	Return value
Dim oCompact As Object			&apos;	Return value as an _Address type
Dim lCountDeleted As Long		&apos;	Count the deleted columns
Dim vCompactRanges As Variant	&apos;	Array of ranges to be compacted based on the formula
Dim oSourceAddress As Object	&apos;	Alias of Range as _Address
Dim oPartialRange As Object		&apos;	Contiguous columns to be deleted
Dim sShiftRange As String		&apos;	Contiguous columns to be shifted
Dim i As Long

Const cstThisSub = &quot;SFDocuments.Calc.CompactLeft&quot;
Const cstSubArgs = &quot;Range, [WholeColumn=False], [FilterFormula=&quot;&quot;&quot;&quot;]&quot;

	If ScriptForge.SF_Utils._ErrorHandling() Then On Local Error GoTo Catch
	sCompact = &quot;&quot;

Check:
	If IsMissing(WholeColumn) Or IsEmpty(WholeColumn) Then WholeColumn = False
	If IsMissing(FilterFormula) Or IsEmpty(FilterFormula) Then FilterFormula = &quot;&quot;
	If ScriptForge.SF_Utils._EnterFunction(cstThisSub, cstSubArgs) Then
		If Not _IsStillAlive(True) Then GoTo Finally
		If Not ScriptForge.SF_Utils._Validate(Range, &quot;Range&quot;, V_STRING) Then GoTo Finally
		If Not ScriptForge.SF_Utils._Validate(WholeColumn, &quot;WholeColumn&quot;, ScriptForge.V_BOOLEAN) Then GoTo Finally
		If Not ScriptForge.SF_Utils._Validate(FilterFormula, &quot;FilterFormula&quot;, V_STRING) Then GoTo Finally
	End If

Try:
	Set oSourceAddress = _ParseAddress(Range)
	lCountDeleted = 0

	With oSourceAddress

		&apos;	Set the default formula =&gt; all cells are blank
		If FilterFormula = &quot;&quot; Then FilterFormula = Printf(&quot;=(COUNTBLANK(%C1%R1:%C1%R2)-&quot; &amp; .Height &amp; &quot;=0)&quot;, Range)

		&apos;	Identify the ranges to compact based on the given formula
		vCompactRanges = _ComputeFilter(oSourceAddress, FilterFormula, &quot;COLUMN&quot;)

		&apos;	Iterate through the ranges from bottom to top and shift them up
		For i = UBound(vCompactRanges) To 0 Step -1
			Set oPartialRange = vCompactRanges(i)
			ShiftLeft(oPartialRange.RangeName, WholeColumn)
			lCountDeleted = lCountDeleted + oPartialRange.Width
		Next i
	
		&apos;	Compute the final range position
		If lCountDeleted &lt; .Width Then sCompact = Offset(Range, 0, 0, 0, .Width - lCountDeleted)

		&apos;	Push to the right the cells that migrated leftwards irrelevantly
		If Not WholeColumn Then
			If Len(sCompact) &gt; 0 Then
				sShiftRange = Offset(sCompact, 0, .Width - lCountDeleted, , lCountDeleted)
			Else
				sShiftRange = .RangeName
			End If
			ShiftRight(sShiftRange, WholeColumn := False)
		End If

	End With

Finally:
	CompactLeft = sCompact
	ScriptForge.SF_Utils._ExitFunction(cstThisSub)
	Exit Function
Catch:
	&apos;	When error, return the original range
	If Not IsNull(oSourceAddress) Then sCompact = oSourceAddress.RangeName
	GoTo Finally
End Function    &apos;   SFDocuments.SF_Calc.CompactLeft

REM -----------------------------------------------------------------------------
Public Function CompactUp(Optional ByVal Range As Variant _
								, Optional ByVal WholeRow As Variant _
								, Optional ByVal FilterFormula As Variant _
								) As String
&apos;&apos;&apos;	Delete the rows of a specified range matching a filter expressed as a formula
&apos;&apos;&apos;	applied on each row.
&apos;&apos;&apos;	The deleted cells can span whole rows or be limited to the width of the range
&apos;&apos;&apos;	The execution of the method has no effect on the current selection
&apos;&apos;&apos;	Args:
&apos;&apos;&apos;		Range: the range in which cells have to be erased, as a string
&apos;&apos;&apos;		WholeRow: when True (default = False), erase whole rows
&apos;&apos;&apos;		FilterFormula: the formula to be applied on each row.
&apos;&apos;&apos;			The row is erased when the formula results in True,
&apos;&apos;&apos;			The formula shall probably involve one or more cells of the first row of the range.
&apos;&apos;&apos;			By default, a row is erased when all the cells of the row are empty,
&apos;&apos;&apos;			i.e. suppose the range is &quot;A1:J200&quot; (width = 10) the default value becomes
&apos;&apos;&apos;				&quot;=(COUNTBLANK(A1:J1)=10)&quot;
&apos;&apos;&apos;	Returns:
&apos;&apos;&apos;		A string representing the location of the initial range after compaction,
&apos;&apos;&apos;		or the zero-length string if the whole range has been deleted
&apos;&apos;&apos;	Examples:
&apos;&apos;&apos;		newrange = oDoc.CompactUp(&quot;SheetX.G1:L10&quot;)	&apos;	All empty rows of the range are suppressed
&apos;&apos;&apos;		newrange = oDoc.CompactUp(&quot;SheetX.G1:L10&quot;, WholeRow := True, FilterFormula := &quot;=(G1=&quot;&quot;X&quot;&quot;)&quot;)
&apos;&apos;&apos;			&apos;	The rows having a &quot;X&quot; in column G are completely suppressed

Dim sCompact As String			&apos;	Return value
Dim oCompact As Object			&apos;	Return value as an _Address type
Dim lCountDeleted As Long		&apos;	Count the deleted rows
Dim vCompactRanges As Variant	&apos;	Array of ranges to be compacted based on the formula
Dim oSourceAddress As Object	&apos;	Alias of Range as _Address
Dim oPartialRange As Object		&apos;	Contiguous rows to be deleted
Dim sShiftRange As String		&apos;	Contiguous rows to be shifted
Dim i As Long

Const cstThisSub = &quot;SFDocuments.Calc.CompactUp&quot;
Const cstSubArgs = &quot;Range, [WholeRow=False], [FilterFormula=&quot;&quot;&quot;&quot;]&quot;

	If ScriptForge.SF_Utils._ErrorHandling() Then On Local Error GoTo Catch
	sCompact = &quot;&quot;

Check:
	If IsMissing(WholeRow) Or IsEmpty(WholeRow) Then WholeRow = False
	If IsMissing(FilterFormula) Or IsEmpty(FilterFormula) Then FilterFormula = &quot;&quot;
	If ScriptForge.SF_Utils._EnterFunction(cstThisSub, cstSubArgs) Then
		If Not _IsStillAlive(True) Then GoTo Finally
		If Not ScriptForge.SF_Utils._Validate(Range, &quot;Range&quot;, V_STRING) Then GoTo Finally
		If Not ScriptForge.SF_Utils._Validate(WholeRow, &quot;WholeRow&quot;, ScriptForge.V_BOOLEAN) Then GoTo Finally
		If Not ScriptForge.SF_Utils._Validate(FilterFormula, &quot;FilterFormula&quot;, V_STRING) Then GoTo Finally
	End If

Try:
	Set oSourceAddress = _ParseAddress(Range)
	lCountDeleted = 0

	With oSourceAddress

		&apos;	Set the default formula =&gt; all cells are blank
		If FilterFormula = &quot;&quot; Then FilterFormula = Printf(&quot;=(COUNTBLANK(%C1%R1:%C2%R1)-&quot; &amp; .Width &amp; &quot;=0)&quot;, Range)

		&apos;	Identify the ranges to compact based on the given formula
		vCompactRanges = _ComputeFilter(oSourceAddress, FilterFormula, &quot;ROW&quot;)

		&apos;	Iterate through the ranges from bottom to top and shift them up
		For i = UBound(vCompactRanges) To 0 Step -1
			Set oPartialRange = vCompactRanges(i)
			ShiftUp(oPartialRange.RangeName, WholeRow)
			lCountDeleted = lCountDeleted + oPartialRange.Height
		Next i
	
		&apos;	Compute the final range position
		If lCountDeleted &lt; .Height Then sCompact = Offset(Range, 0, 0, .Height - lCountDeleted, 0)

		&apos;	Push downwards the cells that migrated upwards irrelevantly
		If Not WholeRow Then
			If Len(sCompact) &gt; 0 Then
				sShiftRange = Offset(sCompact, .Height - lCountDeleted, 0, lCountDeleted)
			Else
				sShiftRange = .RangeName
			End If
			ShiftDown(sShiftRange, WholeRow := False)
		End If

	End With

Finally:
	CompactUp = sCompact
	ScriptForge.SF_Utils._ExitFunction(cstThisSub)
	Exit Function
Catch:
	&apos;	When error, return the original range
	If Not IsNull(oSourceAddress) Then sCompact = oSourceAddress.RangeName
	GoTo Finally
End Function    &apos;   SFDocuments.SF_Calc.CompactUp

REM -----------------------------------------------------------------------------
Public Function CopySheet(Optional ByVal SheetName As Variant _
								, Optional ByVal NewName As Variant _
								, Optional ByVal BeforeSheet As Variant _
								) As Boolean
&apos;&apos;&apos; Copy a specified sheet before an existing sheet or at the end of the list of sheets
&apos;&apos;&apos;	The sheet to copy may be inside any open Calc document
&apos;&apos;&apos;	Args:
&apos;&apos;&apos;		SheetName: The name of the sheet to copy or its reference
&apos;&apos;&apos;		NewName: Must not exist
&apos;&apos;&apos;		BeforeSheet: The name (string) or index (numeric, starting from 1) of the sheet before which to insert
&apos;&apos;&apos;	Returns:
&apos;&apos;&apos;		True if the sheet could be copied successfully
&apos;&apos;&apos;	Exceptions:
&apos;&apos;&apos;		DUPLICATESHEETERROR		A sheet with the given name exists already
&apos;&apos;&apos;	Examples:
&apos;&apos;&apos;		oDoc.CopySheet(&quot;SheetX&quot;, &quot;SheetY&quot;)
&apos;&apos;&apos;			&apos;	Copy within the same document
&apos;&apos;&apos;		Dim oDocA As Object		:	Set oDocA = ui.OpenDocument(&quot;C:\Temp\FileA.ods&quot;, Hidden := True, ReadOnly := True)
&apos;&apos;&apos;		Dim oDocB As Object		:	Set oDocB = ui.OpenDocument(&quot;C:\Temp\FileB.ods&quot;)
&apos;&apos;&apos;		oDocB.CopySheet(oDocA.Sheet(&quot;SheetX&quot;), &quot;SheetY&quot;)
&apos;&apos;&apos;			&apos;	Copy from 1 file to another and put the new sheet at the end

Dim bCopy As Boolean				&apos;	Return value
Dim oSheets As Object				&apos;	com.sun.star.sheet.XSpreadsheets
Dim vSheets As Variant				&apos;	List of existing sheets
Dim lSheetIndex As Long				&apos;	Index of a sheet
Dim oSheet As Object				&apos;	Alias of SheetName as reference
Dim lRandom As Long					&apos;	Output of random number generator
Dim sRandom							&apos;	Random sheet name
Const cstThisSub = &quot;SFDocuments.Calc.CopySheet&quot;
Const cstSubArgs = &quot;SheetName, NewName, [BeforeSheet=&quot;&quot;&quot;&quot;]&quot;

	If ScriptForge.SF_Utils._ErrorHandling() Then On Local Error GoTo Catch
	bCopy = False

Check:
	If IsMissing(BeforeSheet) Or IsEmpty(BeforeSheet) Then BeforeSheet = 32768
	If ScriptForge.SF_Utils._EnterFunction(cstThisSub, cstSubArgs) Then
		If Not _IsStillAlive(True) Then GoTo Finally
		If Not _ValidateSheet(SheetName, &quot;SheetName&quot;, , True, , , True) Then GoTo Finally
		If Not _ValidateSheet(NewName, &quot;NewName&quot;, True) Then GoTo Finally
		If Not _ValidateSheet(BeforeSheet, &quot;BeforeSheet&quot;, , True, , True) Then GoTo Finally
	End If

Try:
	&apos;	Determine the index of the sheet before which to insert the copy
	Set oSheets = _Component.getSheets
	vSheets = oSheets.getElementNames()
	If VarType(BeforeSheet) = V_STRING Then
		lSheetIndex = ScriptForge.SF_Array.IndexOf(vSheets, BeforeSheet)
	Else
		lSheetIndex = BeforeSheet - 1
		If lSheetIndex &lt; 0 Then lSheetIndex = 0
		If lSheetIndex &gt; UBound(vSheets) Then lSheetIndex = UBound(vSheets) + 1
	End If

	&apos;	Copy sheet inside the same document OR import from another document
	If VarType(SheetName) = V_STRING Then
		_Component.getSheets.copyByName(SheetName, NewName, lSheetIndex)
	Else
		Set oSheet = SheetName
		With oSheet
			&apos;	If a sheet with same name as input exists in the target sheet, rename it first with a random name
			sRandom = &quot;&quot;
			If ScriptForge.SF_Array.Contains(vSheets, .SheetName) Then
				lRandom = ScriptForge.SF_Session.ExecuteCalcFunction(&quot;RANDBETWEEN.NV&quot;, 1, 9999999)
				sRandom = &quot;SF_&quot; &amp; Right(&quot;0000000&quot; &amp; lRandom, 7)
				oSheets.getByName(.SheetName).setName(sRandom)
			End If
			&apos;	Import i.o. Copy
			oSheets.importSheet(oSheet.Component, .SheetName, lSheetIndex)
			&apos;	Rename to new sheet name
			oSheets.getByName(.SheetName).setName(NewName)
			&apos;	Reset random name
			If Len(sRandom) &gt; 0 Then oSheets.getByName(sRandom).setName(.SheetName)
		End With
	End If
	bCopy = True

Finally:
	CopySheet = bCopy
	ScriptForge.SF_Utils._ExitFunction(cstThisSub)
	Exit Function
Catch:
	GoTo Finally
CatchDuplicate:
	ScriptForge.SF_Exception.RaiseFatal(DUPLICATESHEETERROR, &quot;NewName&quot;, NewName, &quot;Document&quot;, [_Super]._FileIdent())
	GoTo Finally
End Function    &apos;   SFDocuments.SF_Calc.CopySheet

REM -----------------------------------------------------------------------------
Public Function CopySheetFromFile(Optional ByVal FileName As Variant _
								, Optional ByVal SheetName As Variant _
								, Optional ByVal NewName As Variant _
								, Optional ByVal BeforeSheet As Variant _
								) As Boolean
&apos;&apos;&apos; Copy a specified sheet before an existing sheet or at the end of the list of sheets
&apos;&apos;&apos;	The sheet to copy is located inside any closed Calc document
&apos;&apos;&apos;	Args:
&apos;&apos;&apos;		FileName: Identifies the file to open. It must follow the SF_FileSystem.FileNaming notation
&apos;&apos;&apos;			The file must not be protected with a password
&apos;&apos;&apos;		SheetName: The name of the sheet to copy
&apos;&apos;&apos;		NewName: Must not exist
&apos;&apos;&apos;		BeforeSheet: The name (string) or index (numeric, starting from 1) of the sheet before which to insert
&apos;&apos;&apos;	Returns:
&apos;&apos;&apos;		True if the sheet could be created
&apos;&apos;&apos;		The created sheet is blank when the input file is not a Calc file
&apos;&apos;&apos;		The created sheet contains an error message when the input sheet was not found
&apos;&apos;&apos;	Exceptions:
&apos;&apos;&apos;		DUPLICATESHEETERROR		A sheet with the given name exists already
&apos;&apos;&apos;		UNKNOWNFILEERROR		The input file is unknown
&apos;&apos;&apos;	Examples:
&apos;&apos;&apos;		oDoc.CopySheetFromFile(&quot;C:\MyFile.ods&quot;, &quot;SheetX&quot;, &quot;SheetY&quot;, 3)

Dim bCopy As Boolean				&apos;	Return value
Dim oSheet As Object				&apos;	com.sun.star.sheet.XSpreadsheet
Dim sFileName As String				&apos;	URL alias of FileName
Dim FSO As Object					&apos;	SF_FileSystem
Const cstThisSub = &quot;SFDocuments.Calc.CopySheetFromFile&quot;
Const cstSubArgs = &quot;FileName, SheetName, NewName, [BeforeSheet=&quot;&quot;&quot;&quot;]&quot;

	If ScriptForge.SF_Utils._ErrorHandling() Then On Local Error GoTo Catch
	bCopy = False

Check:
	If IsMissing(BeforeSheet) Or IsEmpty(BeforeSheet) Then BeforeSheet = 32768
	If ScriptForge.SF_Utils._EnterFunction(cstThisSub, cstSubArgs) Then
		If Not _IsStillAlive(True) Then GoTo Finally
		If Not ScriptForge.SF_Utils._ValidateFile(FileName, &quot;FileName&quot;) Then GoTo Finally
		If Not ScriptForge.SF_Utils._Validate(SheetName, &quot;SheetName&quot;, V_STRING) Then GoTo Finally
		If Not _ValidateSheet(NewName, &quot;NewName&quot;, True) Then GoTo Finally
		If Not _ValidateSheet(BeforeSheet, &quot;BeforeSheet&quot;, , True, , True) Then GoTo Finally
	End If

Try:
	Set FSO = ScriptForge.SF_FileSystem
	&apos;	Does the input file exist ?
	If Not FSO.FileExists(FileName) Then GoTo CatchNotExists
	sFileName = FSO._ConvertToUrl(FileName)

	&apos;	Insert a blank new sheet and import sheet from file via link setting and deletion
	If Not InsertSheet(Newname, BeforeSheet) Then GoTo Finally
	Set oSheet = _Component.getSheets.getByName(NewName)
	With oSheet
		.link(sFileName,SheetName, &quot;&quot;, &quot;&quot;, com.sun.star.sheet.SheetLinkMode.NORMAL)
		.LinkMode = com.sun.star.sheet.SheetLinkMode.NONE
    	.LinkURL = &quot;&quot;
	End With
	bCopy = True

Finally:
	CopySheetFromFile = bCopy
	ScriptForge.SF_Utils._ExitFunction(cstThisSub)
	Exit Function
Catch:
	GoTo Finally
CatchNotExists:
	ScriptForge.SF_Exception.RaiseFatal(UNKNOWNFILEERROR, &quot;FileName&quot;, FileName)
	GoTo Finally
End Function    &apos;   SFDocuments.SF_Calc.CopySheetFromFile

REM -----------------------------------------------------------------------------
Public Function CopyToCell(Optional ByVal SourceRange As Variant _
								, Optional ByVal DestinationCell As Variant _
								) As String
&apos;&apos;&apos; Copy a specified source range to a destination range or cell
&apos;&apos;&apos;	The source range may belong to another open document
&apos;&apos;&apos;	The method imitates the behaviour of a Copy/Paste from a range to a single cell
&apos;&apos;&apos;	Args:
&apos;&apos;&apos;		SourceRange: the source range as a string if it belongs to the same document
&apos;&apos;&apos;			or as a reference if it belongs to another open Calc document
&apos;&apos;&apos;		DestinationCell: the destination of the copied range of cells, as a string
&apos;&apos;&apos;			If given as a range of cells, the destination will be reduced to its top-left cell
&apos;&apos;&apos;	Returns:
&apos;&apos;&apos;		A string representing the modified range of cells
&apos;&apos;&apos;		The modified area depends only on the size of the source area
&apos;&apos;&apos;	Examples:
&apos;&apos;&apos;		oDoc.CopyToCell(&quot;SheetX.A1:F10&quot;, &quot;SheetY.C5&quot;)
&apos;&apos;&apos;			&apos;	Copy within the same document
&apos;&apos;&apos;		Dim oDocA As Object		:	Set oDocA = ui.OpenDocument(&quot;C:\Temp\FileA.ods&quot;, Hidden := True, ReadOnly := True)
&apos;&apos;&apos;		Dim oDocB As Object		:	Set oDocB = ui.OpenDocument(&quot;C:\Temp\FileB.ods&quot;)
&apos;&apos;&apos;		oDocB.CopyToCell(oDocA.Range(&quot;SheetX.A1:F10&quot;), &quot;SheetY.C5&quot;)
&apos;&apos;&apos;			&apos;	Copy from 1 file to another

Dim sCopy As String				&apos;	Return value
Dim oSource As Object			&apos;	Alias of SourceRange to avoid &quot;Object variable not set&quot; run-time error
Dim oSourceAddress As Object	&apos;	com.sun.star.table.CellRangeAddress
Dim oDestRange As Object		&apos;	Destination as a range
Dim oDestAddress As Object		&apos;	com.sun.star.table.CellRangeAddress
Dim oDestCell As Object			&apos;	com.sun.star.table.CellAddress
Dim oSelect As Object			&apos;	Current selection in source
Dim oClipboard As Object		&apos;	com.sun.star.datatransfer.XTransferable

Const cstThisSub = &quot;SFDocuments.Calc.CopyToCell&quot;
Const cstSubArgs = &quot;SourceRange, DestinationCell&quot;

	If ScriptForge.SF_Utils._ErrorHandling() Then On Local Error GoTo Catch
	sCopy = &quot;&quot;

Check:
	If ScriptForge.SF_Utils._EnterFunction(cstThisSub, cstSubArgs) Then
		If Not _IsStillAlive(True) Then GoTo Finally
		If Not ScriptForge.SF_Utils._Validate(SourceRange, &quot;SourceRange&quot;, Array(V_STRING, ScriptForge.V_OBJECT), , , CALCREFERENCE) Then GoTo Finally
		If Not ScriptForge.SF_Utils._Validate(DestinationCell, &quot;DestinationCell&quot;, V_STRING) Then GoTo Finally
	End If

Try:
	If VarType(SourceRange) = V_STRING Then		&apos;	Same document - Use UNO copyRange method
		Set oSourceAddress = _ParseAddress(SourceRange).XCellRange.RangeAddress
		Set oDestRange = _ParseAddress(DestinationCell)
		Set oDestAddress = oDestRange.XCellRange.RangeAddress
		Set oDestCell = New com.sun.star.table.CellAddress
		With oDestAddress
			oDestCell.Sheet = .Sheet
			oDestCell.Column = .StartColumn
			oDestCell.Row = .StartRow
		End With
		oDestRange.XSpreadsheet.copyRange(oDestCell, oSourceAddress)
	Else			&apos;	Use clipboard to copy - current selection in Source should be preserved
		Set oSource = SourceRange
		With oSource
			&apos;	Keep current selection in source document
			Set oSelect = .Component.CurrentController.getSelection()
			&apos;	Select, copy the source range and paste in the top-left cell of the destination
			.Component.CurrentController.select(.XCellRange)
			Set oClipboard = .Component.CurrentController.getTransferable()
			_Component.CurrentController.select(_Offset(DestinationCell, 0, 0, 1, 1).XCellRange)
			_Component.CurrentController.insertTransferable(oClipBoard)
			&apos;	Restore previous selection in Source
			_RestoreSelections(.Component, oSelect)
			Set oSourceAddress = .XCellRange.RangeAddress
		End With
	End If

	With oSourceAddress
		sCopy = _Offset(DestinationCell, 0, 0, .EndRow - .StartRow + 1, .EndColumn - .StartColumn + 1).RangeName
	End With

Finally:
	CopyToCell = sCopy
	ScriptForge.SF_Utils._ExitFunction(cstThisSub)
	Exit Function
Catch:
	GoTo Finally
End Function    &apos;   SFDocuments.SF_Calc.CopyToCell

REM -----------------------------------------------------------------------------
Public Function CopyToRange(Optional ByVal SourceRange As Variant _
								, Optional ByVal DestinationRange As Variant _
								) As String
&apos;&apos;&apos; Copy downwards and/or rightwards a specified source range to a destination range
&apos;&apos;&apos;	The source range may belong to another open document
&apos;&apos;&apos;	The method imitates the behaviour of a Copy/Paste from a range to a larger range
&apos;&apos;&apos;		If the height (resp. width) of the destination area is &gt; 1 row (resp. column)
&apos;&apos;&apos;		then the height (resp. width) of the source must be &lt;= the height (resp. width)
&apos;&apos;&apos;		of the destination. Otherwise nothing happens
&apos;&apos;&apos;		If the height (resp.width) of the destination is = 1 then the destination
&apos;&apos;&apos;		is expanded downwards (resp. rightwards) up to the height (resp. width)
&apos;&apos;&apos;		of the source range
&apos;&apos;&apos;	Args:
&apos;&apos;&apos;		SourceRange: the source range as a string if it belongs to the same document
&apos;&apos;&apos;			or as a reference if it belongs to another open Calc document
&apos;&apos;&apos;		DestinationRange: the destination of the copied range of cells, as a string
&apos;&apos;&apos;	Returns:
&apos;&apos;&apos;		A string representing the modified range of cells
&apos;&apos;&apos;	Examples:
&apos;&apos;&apos;		oDoc.CopyToRange(&quot;SheetX.A1:F10&quot;, &quot;SheetY.C5:J5&quot;)
&apos;&apos;&apos;			&apos;	Copy within the same document
&apos;&apos;&apos;			&apos;	Returned range: $SheetY.$C$5:$J$14
&apos;&apos;&apos;		Dim oDocA As Object		:	Set oDocA = ui.OpenDocument(&quot;C:\Temp\FileA.ods&quot;, Hidden := True, ReadOnly := True)
&apos;&apos;&apos;		Dim oDocB As Object		:	Set oDocB = ui.OpenDocument(&quot;C:\Temp\FileB.ods&quot;)
&apos;&apos;&apos;		oDocB.CopyToRange(oDocA.Range(&quot;SheetX.A1:F10&quot;), &quot;SheetY.C5:J5&quot;)
&apos;&apos;&apos;			&apos;	Copy from 1 file to another

Dim sCopy As String				&apos;	Return value
Dim oSource As Object			&apos;	Alias of SourceRange to avoid &quot;Object variable not set&quot; run-time error
Dim oDestRange As Object		&apos;	Destination as a range
Dim oDestCell As Object			&apos;	com.sun.star.table.CellAddress
Dim oSelect As Object			&apos;	Current selection in source
Dim oClipboard As Object		&apos;	com.sun.star.datatransfer.XTransferable
Dim bSameDocument As Boolean	&apos;	True when source in same document as destination
Dim lHeight As Long				&apos;	Height of destination
Dim lWidth As Long				&apos;	Width of destination

Const cstThisSub = &quot;SFDocuments.Calc.CopyToRange&quot;
Const cstSubArgs = &quot;SourceRange, DestinationRange&quot;

	If ScriptForge.SF_Utils._ErrorHandling() Then On Local Error GoTo Catch
	sCopy = &quot;&quot;

Check:
	If ScriptForge.SF_Utils._EnterFunction(cstThisSub, cstSubArgs) Then
		If Not _IsStillAlive(True) Then GoTo Finally
		If Not ScriptForge.SF_Utils._Validate(SourceRange, &quot;SourceRange&quot;, Array(V_STRING, ScriptForge.V_OBJECT), , , CALCREFERENCE) Then GoTo Finally
		If Not ScriptForge.SF_Utils._Validate(DestinationRange, &quot;DestinationRange&quot;, V_STRING) Then GoTo Finally
	End If

Try:
	&apos;	Copy done via clipboard

	&apos;	Check Height/Width destination = 1 or &gt; Height/Width of source
	bSameDocument = ( VarType(SourceRange) = V_STRING )
	If bSameDocument Then Set oSource = _ParseAddress(SourceRange) Else Set oSource = SourceRange
	Set oDestRange = _ParseAddress(DestinationRange)
	With oDestRange
		lHeight = .Height
		lWidth = .Width
		If lHeight = 1 Then
			lHeight = oSource.Height		&apos;	Future height
		ElseIf lHeight &lt; oSource.Height Then
			GoTo Finally
		End If
		If lWidth = 1 Then
			lWidth = oSource.Width	&apos;	Future width
		ElseIf lWidth &lt; oSource.Width Then
			GoTo Finally
		End If
	End With

	With oSource
		&apos;	Store actual selection in source
		Set oSelect = .Component.CurrentController.getSelection()
		&apos;	Select, copy the source range and paste in the destination
		.Component.CurrentController.select(.XCellRange)
		Set oClipboard = .Component.CurrentController.getTransferable()
		_Component.CurrentController.select(oDestRange.XCellRange)
		_Component.CurrentController.insertTransferable(oClipBoard)
		&apos;	Restore selection in source
		_RestoreSelections(.Component, oSelect)
	End With

	sCopy = _Offset(oDestRange, 0, 0, lHeight, lWidth).RangeName

Finally:
	CopyToRange = sCopy
	ScriptForge.SF_Utils._ExitFunction(cstThisSub)
	Exit Function
Catch:
	GoTo Finally
End Function    &apos;   SFDocuments.SF_Calc.CopyToRange

REM -----------------------------------------------------------------------------
Public Function CreateChart(Optional ByVal ChartName As Variant _
							, Optional ByVal SheetName As Variant _
							, Optional ByVal Range As Variant _
							, Optional ColumnHeader As Variant _
							, Optional RowHeader As Variant _
							) As Variant
&apos;&apos;&apos; Return a new chart instance initialized with default values
&apos;&apos;&apos;	Args:
&apos;&apos;&apos;		ChartName: The user-defined name of the new chart
&apos;&apos;&apos;		SheetName: The name of an existing sheet
&apos;&apos;&apos;		Range: the cell or the range as a string that should be drawn
&apos;&apos;&apos;		ColumnHeader: when True, the topmost row of the range will be used to set labels for the category axis or the legend.
&apos;&apos;&apos;			Default = False
&apos;&apos;&apos;		RowHeader: when True, the leftmost column of the range will be used to set labels for the category axis or the legend.
&apos;&apos;&apos;			Default = False
&apos;&apos;&apos;	Returns:
&apos;&apos;&apos;		A new chart service instance
&apos;&apos;&apos;	Exceptions:
&apos;&apos;&apos;		DUPLICATECHARTERROR		A chart with the same name exists already in the given sheet
&apos;&apos;&apos;	Examples:
&apos;&apos;&apos;		Dim oChart As Object
&apos;&apos;&apos;		Set oChart = oDoc.CreateChart(&quot;myChart&quot;, &quot;SheetX&quot;, &quot;A1:C8&quot;, ColumnHeader := True)

Dim oChart As Object				&apos;	Return value
Dim vCharts As Variant				&apos;	List of pre-existing charts
Dim oSheet As Object				&apos;	Alias of SheetName as reference
Dim oRange As Object				&apos;	Alias of Range
Dim oRectangle as new com.sun.star.awt.Rectangle	&apos;	Simple shape

Const cstThisSub = &quot;SFDocuments.Calc.CreateChart&quot;
Const cstSubArgs = &quot;ChartName, SheetName, Range, [ColumnHeader=False], [RowHeader=False]&quot;

	If ScriptForge.SF_Utils._ErrorHandling() Then On Local Error GoTo Catch
	Set oChart = Nothing

Check:
	If IsMissing(RowHeader) Or IsEmpty(RowHeader) Then Rowheader = False
	If IsMissing(ColumnHeader) Or IsEmpty(ColumnHeader) Then ColumnHeader = False
	If ScriptForge.SF_Utils._EnterFunction(cstThisSub, cstSubArgs) Then
		If Not _IsStillAlive(True) Then GoTo Finally
		If Not ScriptForge.SF_Utils._Validate(ChartName, &quot;ChartName&quot;, V_STRING) Then GoTo Finally
		If Not _ValidateSheet(SheetName, &quot;SheetName&quot;, , True) Then GoTo Finally
		If Not ScriptForge.SF_Utils._Validate(Range, &quot;Range&quot;, V_STRING) Then GoTo Finally
		If Not ScriptForge.SF_Utils._Validate(ColumnHeader, &quot;ColumnHeader&quot;, ScriptForge.V_BOOLEAN) Then GoTo Finally
		If Not ScriptForge.SF_Utils._Validate(RowHeader, &quot;RowHeader&quot;, ScriptForge.V_BOOLEAN) Then GoTo Finally
	End If

	vCharts = Charts(SheetName)
	If ScriptForge.SF_Array.Contains(vCharts, ChartName, CaseSensitive := True) Then GoTo CatchDuplicate

Try:
	&apos;	The rectangular shape receives arbitrary values. User can Resize() it later
	With oRectangle
		.X = 0			:	.Y = 0
		.Width = 8000	:	.Height = 6000
	End With
	&apos;	Initialize sheet and range
	Set oSheet = _Component.getSheets.getByName(SheetName)
	Set oRange = _ParseAddress(Range)
	&apos;	Create the chart and get ihe corresponding chart instance
	oSheet.getCharts.addNewByName(ChartName, oRectangle, Array(oRange.XCellRange.RangeAddress), ColumnHeader, RowHeader)
	Set oChart = Charts(SheetName, ChartName)
	oChart._Shape.Name = ChartName		&apos;	Both user-defined and internal names match ChartName
	oChart._Diagram.Wall.FillColor = RGB(255, 255, 255)		&apos;	Align on background color set by the user interface by default

Finally:
	Set CreateChart = oChart
	ScriptForge.SF_Utils._ExitFunction(cstThisSub)
	Exit Function
Catch:
	GoTo Finally
CatchDuplicate:
	ScriptForge.SF_Exception.RaiseFatal(DUPLICATECHARTERROR, &quot;ChartName&quot;, ChartName, &quot;SheetName&quot;, SheetName, &quot;Document&quot;, [_Super]._FileIdent())
	GoTo Finally
End Function    &apos;   SFDocuments.SF_Calc.CreateChart

REM -----------------------------------------------------------------------------
Public Function CreatePivotTable(Optional ByVal PivotTableName As Variant _
									, Optional ByVal SourceRange As Variant _
									, Optional ByVal TargetCell As Variant _
									, Optional ByRef DataFields As Variant _
									, Optional ByRef RowFields As Variant _
									, Optional ByRef ColumnFields As Variant _
									, Optional ByVal FilterButton As Variant _
									, Optional ByVal RowTotals As Variant _
									, Optional ByVal ColumnTotals As Variant _
							) As String
&apos;&apos;&apos; Create a new pivot table with the properties defined by the arguments.
&apos;&apos;&apos;	If a pivot table with the same name exists already in the targeted sheet, it will be erased without warning.
&apos;&apos;&apos;	Args:
&apos;&apos;&apos;		PivotTableName: The user-defined name of the new pivottable
&apos;&apos;&apos;		SourceRange: The range as a string containing the raw data.
&apos;&apos;&apos;			The first row of the range is presumed to contain the field names of the new pivot table
&apos;&apos;&apos;		TargetCell: the top left cell or the range as a string where to locate the pivot table.
&apos;&apos;&apos;			Only the top left cell of the range will be considered.
&apos;&apos;&apos;		DataFields: A single string or an array of field name + function to apply, formatted like:
&apos;&apos;&apos;				Array(&quot;FieldName[;Function]&quot;, ...)
&apos;&apos;&apos;			The allowed functions are: Sum, Count, Average, Max, Min, Product, CountNums, StDev, StDevP, Var, VarP and Median.
&apos;&apos;&apos;			The default function is: When the values are all numerical, Sum is used, otherwise Count
&apos;&apos;&apos;		RowFields: A single string or an array of the field names heading the pivot table rows
&apos;&apos;&apos;		ColumnFields: A single string or an array of the field names heading the pivot table columns
&apos;&apos;&apos;		FilterButton: When True (default), display a &quot;Filter&quot; button above the pivot table
&apos;&apos;&apos;		RowTotals: When True (default), display a separate column for row totals
&apos;&apos;&apos;		ColumnTotals: When True (default), display a separate row for column totals
&apos;&apos;&apos;	Returns:
&apos;&apos;&apos;		Return the range where the new pivot table is deployed.
&apos;&apos;&apos;	Examples:
&apos;&apos;&apos;		Dim vData As Variant, oDoc As Object, sTable As String, sPivot As String
&apos;&apos;&apos;		vData = Array(Array(&quot;Item&quot;, &quot;State&quot;, &quot;Team&quot;, &quot;2002&quot;, &quot;2003&quot;, &quot;2004&quot;), _
&apos;&apos;&apos;				Array(&quot;Books&quot;, &quot;Michigan&quot;, &quot;Jean&quot;, 14788, 30222, 23490), _
&apos;&apos;&apos;				Array(&quot;Candy&quot;, &quot;Michigan&quot;, &quot;Jean&quot;, 26388, 15641, 32849), _
&apos;&apos;&apos;				Array(&quot;Pens&quot;, &quot;Michigan&quot;, &quot;Jean&quot;, 16569, 32675, 25396), _
&apos;&apos;&apos;				Array(&quot;Books&quot;, &quot;Michigan&quot;, &quot;Volker&quot;, 21961, 21242, 29009), _
&apos;&apos;&apos;				Array(&quot;Candy&quot;, &quot;Michigan&quot;, &quot;Volker&quot;, 26142, 22407, 32841))
&apos;&apos;&apos;		Set oDoc = ui.CreateDocument(&quot;Calc&quot;)
&apos;&apos;&apos;		sTable = oDoc.SetArray(&quot;A1&quot;, vData)
&apos;&apos;&apos;		sPivot = oDoc.CreatePivotTable(&quot;PT1&quot;, sTable, &quot;H1&quot;, Array(&quot;2002&quot;, &quot;2003;count&quot;, &quot;2004;average&quot;), &quot;Item&quot;, Array(&quot;State&quot;, &quot;Team&quot;), False)

Dim sPivotTable As String				&apos;	Return value
Dim vData As Variant					&apos;	Alias of DataFields
Dim vRows As Variant					&apos;	Alias of RowFields
Dim vColumns As Variant					&apos;	Alias of ColumnFields
Dim oSourceAddress As Object			&apos;	Source as an _Address
Dim oTargetAddress As Object			&apos;	Target as an _Address
Dim vHeaders As Variant					&apos;	Array of header fields in the source range
Dim oPivotTables As Object				&apos;	com.sun.star.sheet.XDataPilotTables
Dim oDescriptor As Object				&apos;	com.sun.star.sheet.DataPilotDescriptor
Dim oFields As Object					&apos;	ScDataPilotFieldsObj - Collection of fields
Dim oField As Object					&apos;	ScDataPilotFieldsObj - A single field
Dim sField As String					&apos;	A single field name
Dim sData As String						&apos;	A single data field name + function
Dim vDataField As Variant				&apos;	A single vData element, split on semicolon
Dim sFunction As String					&apos;	Function to apply on a data field (string)
Dim iFunction As Integer				&apos;	Equivalent of sFunction as com.sun.star.sheet.GeneralFunction2 constant
Dim oOutputRange As Object				&apos;	com.sun.star.table.CellRangeAddress
Dim i As Integer

Const cstThisSub = &quot;SFDocuments.Calc.CreatePivotTable&quot;
Const cstSubArgs = &quot;PivotTableName, SourceRange, TargetCell, DataFields, [RowFields], [ColumnFields]&quot; _
					&amp; &quot;, [FilterButton=True], [RowTotals=True], [ColumnTotals=True]&quot;

	If ScriptForge.SF_Utils._ErrorHandling() Then On Local Error GoTo Catch
	sPivotTable = &quot;&quot;

Check:
	If IsMissing(RowFields) Or IsEmpty(RowFields) Then RowFields = Array()
	If IsMissing(ColumnFields) Or IsEmpty(ColumnFields) Then ColumnFields = Array()
	If IsMissing(FilterButton) Or IsEmpty(FilterButton) Then FilterButton = True
	If IsMissing(RowTotals) Or IsEmpty(RowTotals) Then RowTotals = True
	If IsMissing(ColumnTotals) Or IsEmpty(ColumnTotals) Then ColumnTotals = True
	If ScriptForge.SF_Utils._EnterFunction(cstThisSub, cstSubArgs) Then
		If Not _IsStillAlive(True) Then GoTo Finally
		If Not ScriptForge.SF_Utils._Validate(PivotTableName, &quot;PivotTableName&quot;, V_STRING) Then GoTo Finally
		If Not ScriptForge.SF_Utils._Validate(SourceRange, &quot;SourceRange&quot;, V_STRING) Then GoTo Finally
		If Not ScriptForge.SF_Utils._Validate(TargetCell, &quot;TargetCell&quot;, V_STRING) Then GoTo Finally
		If IsArray(DataFields) Then
			If Not ScriptForge.SF_Utils._ValidateArray(DataFields, &quot;DataFields&quot;, 1, V_STRING, True) Then GoTo Finally
		Else
			If Not ScriptForge.SF_Utils._Validate(DataFields, &quot;DataFields&quot;, V_STRING) Then GoTo Finally
		End If
		If IsArray(RowFields) Then
			If Not ScriptForge.SF_Utils._ValidateArray(RowFields, &quot;RowFields&quot;, 1, V_STRING, True) Then GoTo Finally
		Else
			If Not ScriptForge.SF_Utils._Validate(RowFields, &quot;RowFields&quot;, V_STRING) Then GoTo Finally
		End If
		If IsArray(ColumnFields) Then
			If Not ScriptForge.SF_Utils._ValidateArray(ColumnFields, &quot;ColumnFields&quot;, 1, V_STRING, True) Then GoTo Finally
		Else
			If Not ScriptForge.SF_Utils._Validate(ColumnFields, &quot;ColumnFields&quot;, V_STRING) Then GoTo Finally
		End If
		If Not ScriptForge.SF_Utils._Validate(FilterButton, &quot;FilterButton&quot;, ScriptForge.V_BOOLEAN) Then GoTo Finally
		If Not ScriptForge.SF_Utils._Validate(RowTotals, &quot;RowTotals&quot;, ScriptForge.V_BOOLEAN) Then GoTo Finally
		If Not ScriptForge.SF_Utils._Validate(ColumnTotals, &quot;ColumnTotals&quot;, ScriptForge.V_BOOLEAN) Then GoTo Finally
	End If
	&apos;	Next statements must be outside previous If-block to force their execution even in case of internal call
	If IsArray(DataFields) Then vData = DataFields Else vData = Array(DataFields)
	If IsArray(RowFields) Then vRows = RowFields Else vRows = Array(RowFields)
	If IsArray(ColumnFields) Then vColumns = ColumnFields Else vColumns = Array(ColumnFields)

Try:

	Set oSourceAddress = _ParseAddress(SourceRange)
	vHeaders = GetValue(Offset(SourceRange, 0, 0, 1))		&apos;	Content of the first row of the source
	Set oTargetAddress = _Offset(TargetCell, 0, 0, 1, 1)	&apos;	Retain the top left cell only
	Set oPivotTables = oTargetAddress.XSpreadsheet.getDataPilotTables()

	&apos;	Initialize new pivot table
	Set oDescriptor = oPivotTables.createDataPilotDescriptor()
	oDescriptor.setSourceRange(oSourceAddress.XCellRange.RangeAddress)
	Set oFields = oDescriptor.getDataPilotFields()

	&apos;	Set row fields
	For i = 0 To UBound(vRows)
		sField = vRows(i)
		If Len(sField) &gt; 0 Then
			If Not ScriptForge.SF_Utils._Validate(sField, &quot;RowFields&quot;, V_STRING, vHeaders) Then GoTo Finally
			Set oField = oFields.getByName(sField)
			oField.Orientation = com.sun.star.sheet.DataPilotFieldOrientation.ROW
		End If
	Next i

	&apos;	Set column fields
	For i = 0 To UBound(vColumns)
		sField = vColumns(i)
		If Len(sField) &gt; 0 Then
			If Not ScriptForge.SF_Utils._Validate(sField, &quot;ColumnFields&quot;, V_STRING, vHeaders) Then GoTo Finally
			Set oField = oFields.getByName(sField)
			oField.Orientation = com.sun.star.sheet.DataPilotFieldOrientation.COLUMN
		End If
	Next i

	&apos;	Set data fields
	For i = 0 To UBound(vData)
		sData = vData(i)
		&apos;	Minimal parsing
		If Right(sData, 1) = &quot;;&quot; Then sData = Left(sData, Len(sData) - 1)
		vDataField = Split(sData, &quot;;&quot;)
		sField = vDataField(0)
		If UBound(vDataField) &gt; 0 Then sFunction = vDataField(1) Else sFunction = &quot;&quot;
		&apos;	Define field properties
		If Len(sField) &gt; 0 Then
			If Not ScriptForge.SF_Utils._Validate(sField, &quot;DataFields&quot;, V_STRING, vHeaders) Then GoTo Finally
			Set oField = oFields.getByName(sField)
			oField.Orientation = com.sun.star.sheet.DataPilotFieldOrientation.DATA
			&apos;	Associate the correct function
			With com.sun.star.sheet.GeneralFunction2
				Select Case UCase(sFunction)
					Case &quot;&quot;			:	iFunction = .AUTO
					Case &quot;SUM&quot;		:	iFunction = .SUM
					Case &quot;COUNT&quot;	:	iFunction = .COUNT
					Case &quot;AVERAGE&quot;	:	iFunction = .AVERAGE
					Case &quot;MAX&quot;		:	iFunction = .MAX
					Case &quot;MIN&quot;		:	iFunction = .MIN
					Case &quot;PRODUCT&quot;	:	iFunction = .PRODUCT
					Case &quot;COUNTNUMS&quot;:	iFunction = .COUNTNUMS
					Case &quot;STDEV&quot;	:	iFunction = .STDEV
					Case &quot;STDEVP&quot;	:	iFunction = .STDEVP
					Case &quot;VAR&quot;		:	iFunction = .VAR
					Case &quot;VARP&quot;		:	iFunction = .VARP
					Case &quot;MEDIAN&quot;	:	iFunction = .MEDIAN
					Case Else
						If Not ScriptForge.SF_Utils._Validate(sFunction, &quot;DataFields/Function&quot;, V_STRING _
								, Array(&quot;Sum&quot;, &quot;Count&quot;, &quot;Average&quot;, &quot;Max&quot;, &quot;Min&quot;, &quot;Product&quot;, &quot;CountNums&quot; _
										, &quot;StDev&quot;, &quot;StDevP&quot;, &quot;Var&quot;, &quot;VarP&quot;, &quot;Median&quot;) _
								) Then GoTo Finally
				End Select
			End With
			oField.Function2 = iFunction
		End If
	Next i

	&apos;	Remove any pivot table with same name
	If oPivotTables.hasByName(PivotTableName) Then oPivotTables.removeByName(PivotTableName)

	&apos;	Finalize the new pivot table
	oDescriptor.ShowFilterButton = FilterButton
	oDescriptor.RowGrand = RowTotals
	oDescriptor.ColumnGrand = ColumnTotals
	oPivotTables.insertNewByName(PivotTableName, oTargetAddress.XCellRange.getCellByPosition(0, 0).CellAddress, oDescriptor)

	&apos;	Determine the range of the new pivot table
	Set oOutputRange = oPivotTables.getByName(PivotTableName).OutputRange
	With oOutputRange
		sPivotTable = _Component.getSheets().getCellRangeByPosition(.StartColumn, .StartRow, .EndColumn, .EndRow, .Sheet).AbsoluteName
	End With

Finally:
	CreatePivotTable = sPivotTable
	ScriptForge.SF_Utils._ExitFunction(cstThisSub)
	Exit Function
Catch:
	GoTo Finally
End Function    &apos;   SFDocuments.SF_Calc.CreatePivotTable

REM -----------------------------------------------------------------------------
Public Function DAvg(Optional ByVal Range As Variant) As Double
&apos;&apos;&apos;	Get the average of the numeric values stored in the given range
&apos;&apos;&apos;	Args:
&apos;&apos;&apos;		Range : the range as a string where to get the values from
&apos;&apos;&apos;	Returns:
&apos;&apos;&apos;		The average of the numeric values as a double
&apos;&apos;&apos;	Examples:
&apos;&apos;&apos;		Val = oDoc.DAvg(&quot;~.A1:A1000&quot;)

Try:
	DAvg = _DFunction(&quot;DAvg&quot;, Range)

Finally:
	Exit Function
End Function	&apos;	SFDocuments.SF_Calc.DAvg

REM -----------------------------------------------------------------------------
Public Function DCount(Optional ByVal Range As Variant) As Long
&apos;&apos;&apos;	Get the number of numeric values stored in the given range
&apos;&apos;&apos;	Args:
&apos;&apos;&apos;		Range : the range as a string where to get the values from
&apos;&apos;&apos;	Returns:
&apos;&apos;&apos;		The number of numeric values as a Long
&apos;&apos;&apos;	Examples:
&apos;&apos;&apos;		Val = oDoc.DCount(&quot;~.A1:A1000&quot;)

Try:
	DCount = _DFunction(&quot;DCount&quot;, Range)

Finally:
	Exit Function
End Function	&apos;	SFDocuments.SF_Calc.DCount

REM -----------------------------------------------------------------------------
Public Function DMax(Optional ByVal Range As Variant) As Double
&apos;&apos;&apos;	Get the greatest of the numeric values stored in the given range
&apos;&apos;&apos;	Args:
&apos;&apos;&apos;		Range : the range as a string where to get the values from
&apos;&apos;&apos;	Returns:
&apos;&apos;&apos;		The greatest of the numeric values as a double
&apos;&apos;&apos;	Examples:
&apos;&apos;&apos;		Val = oDoc.DMax(&quot;~.A1:A1000&quot;)

Try:
	DMax = _DFunction(&quot;DMax&quot;, Range)

Finally:
	Exit Function
End Function	&apos;	SFDocuments.SF_Calc.DMax

REM -----------------------------------------------------------------------------
Public Function DMin(Optional ByVal Range As Variant) As Double
&apos;&apos;&apos;	Get the smallest of the numeric values stored in the given range
&apos;&apos;&apos;	Args:
&apos;&apos;&apos;		Range : the range as a string where to get the values from
&apos;&apos;&apos;	Returns:
&apos;&apos;&apos;		The smallest of the numeric values as a double
&apos;&apos;&apos;	Examples:
&apos;&apos;&apos;		Val = oDoc.DMin(&quot;~.A1:A1000&quot;)

Try:
	DMin = _DFunction(&quot;DMin&quot;, Range)

Finally:
	Exit Function
End Function	&apos;	SFDocuments.SF_Calc.DMin

REM -----------------------------------------------------------------------------
Public Function DSum(Optional ByVal Range As Variant) As Double
&apos;&apos;&apos;	Get sum of the numeric values stored in the given range
&apos;&apos;&apos;	Args:
&apos;&apos;&apos;		Range : the range as a string where to get the values from
&apos;&apos;&apos;	Returns:
&apos;&apos;&apos;		The sum of the numeric values as a double
&apos;&apos;&apos;	Examples:
&apos;&apos;&apos;		Val = oDoc.DSum(&quot;~.A1:A1000&quot;)

Try:
	DSum = _DFunction(&quot;DSum&quot;, Range)

Finally:
	Exit Function
End Function	&apos;	SFDocuments.SF_Calc.DSum

REM -----------------------------------------------------------------------------
Public Function ExportRangeToFile(Optional ByVal Range As Variant _
									, Optional ByVal FileName As Variant _
									, Optional ByVal ImageType As Variant _
									, Optional ByVal Overwrite As Variant _
									) As Boolean
&apos;&apos;&apos; Store the given range as an image to the given file location
&apos;&apos;&apos;	Actual selections are not impacted
&apos;&apos;&apos;	Inspired by https://stackoverflow.com/questions/30509532/how-to-export-cell-range-to-pdf-file
&apos;&apos;&apos;	Args:
&apos;&apos;&apos;		Range: sheet name or cell range to be exported, as a string
&apos;&apos;&apos;		FileName: Identifies the file where to save. It must follow the SF_FileSystem.FileNaming notation
&apos;&apos;&apos;		ImageType: the name of the targeted media type
&apos;&apos;&apos;			Allowed values: jpeg, pdf (default) and png
&apos;&apos;&apos;		Overwrite: True if the destination file may be overwritten (default = False)
&apos;&apos;&apos;	Returns:
&apos;&apos;&apos;		False if the document could not be saved
&apos;&apos;&apos;	Exceptions:
&apos;&apos;&apos;		RANGEEXPORTERROR		The destination has its readonly attribute set or overwriting rejected
&apos;&apos;&apos;	Examples:
&apos;&apos;&apos;		oDoc.ExportRangeToFile(&apos;SheetX.B2:J15&quot;, &quot;C:\Me\Range2.png&quot;, ImageType := &quot;png&quot;, Overwrite := True)

Dim bSaved As Boolean				&apos;	return value
Dim oSfa As Object					&apos;	com.sun.star.ucb.SimpleFileAccess
Dim sFile As String					&apos;	Alias of FileName
Dim vStoreArguments As Variant		&apos;	Array of com.sun.star.beans.PropertyValue
Dim vFilterData As Variant			&apos;	Array of com.sun.star.beans.PropertyValue
Dim FSO As Object					&apos;	SF_FileSystem
Dim vImageTypes As Variant			&apos;	Array of permitted image types
Dim vFilters As Variant				&apos;	Array of corresponding filters in the same order as vImageTypes
Dim sFilter As String				&apos;	The filter to apply
Dim oSelect As Object				&apos;	Currently selected range(s)
Dim oAddress As Object				&apos;	Alias of Range

Const cstImageTypes =	&quot;jpeg,pdf,png&quot;
Const cstFilters =		&quot;calc_jpg_Export,calc_pdf_Export,calc_png_Export&quot;

Const cstThisSub = &quot;SFDocuments.Calc.ExportRangeToFile&quot;
Const cstSubArgs = &quot;Range, FileName, [ImageType=&quot;&quot;pdf&quot;&quot;|&quot;&quot;jpeg&quot;&quot;|&quot;&quot;png&quot;&quot;], [Overwrite=False]&quot;

	If ScriptForge.SF_Utils._ErrorHandling() Then On Local Error GoTo CatchError
	bSaved = False

Check:
	If IsMissing(ImageType) Or IsEmpty(ImageType) Then ImageType = &quot;pdf&quot;
	If IsMissing(Overwrite) Or IsEmpty(Overwrite) Then Overwrite = False

	vImageTypes = Split(cstImageTypes, &quot;,&quot;)
	If ScriptForge.SF_Utils._EnterFunction(cstThisSub, cstSubArgs) Then
		If Not _IsStillAlive() Then GoTo Finally
		If Not ScriptForge.SF_Utils._Validate(Range, &quot;Range&quot;, V_STRING) Then GoTo Finally
		If Not ScriptForge.SF_Utils._ValidateFile(FileName, &quot;FileName&quot;) Then GoTo Finally
		If Not ScriptForge.SF_Utils._Validate(ImageType, &quot;ImageType&quot;, V_STRING, vImageTypes) Then GoTo Finally
		If Not ScriptForge.SF_Utils._Validate(Overwrite, &quot;Overwrite&quot;, ScriptForge.V_BOOLEAN) Then GoTo Finally
	End If

	&apos;	Check destination file overwriting
	Set FSO = CreateScriptService(&quot;FileSystem&quot;)
	sFile = FSO._ConvertToUrl(FileName)
	If FSO.FileExists(FileName) Then
		If Overwrite = False Then GoTo CatchError
		Set oSfa = ScriptForge.SF_Utils._GetUNOService(&quot;FileAccess&quot;)
		If oSfa.isReadonly(sFile) Then GoTo CatchError
	End If

Try:
	&apos;	Setup arguments
	vFilters = Split(cstFilters, &quot;,&quot;)
	sFilter = vFilters(ScriptForge.SF_Array.IndexOf(vImageTypes, ImageType, CaseSensitive := False))
	Set oAddress = _ParseAddress(Range)

	&apos;	The filter arguments differ between
	&apos;		1) pdf : store range in Selection property value
	&apos;		2) png, jpeg : save current selection, select range, restore initial selection
	If LCase(ImageType) = &quot;pdf&quot; Then
		vFilterData = Array(ScriptForge.SF_Utils._MakePropertyValue(&quot;Selection&quot;, oAddress.XCellRange)	)
		vStoreArguments = Array( _
								ScriptForge.SF_Utils._MakePropertyValue(&quot;FilterName&quot;, sFilter) _
								, ScriptForge.SF_Utils._MakePropertyValue(&quot;FilterData&quot;, vFilterData) _
								)
	Else		&apos;	png, jpeg
		&apos;	Save the current selection(s)
		Set oSelect = _Component.CurrentController.getSelection()
		_Component.CurrentController.select(oAddress.XCellRange)
		vStoreArguments = Array( _
								ScriptForge.SF_Utils._MakePropertyValue(&quot;FilterName&quot;, sFilter) _
								, ScriptForge.SF_Utils._MakePropertyValue(&quot;SelectionOnly&quot;, True) _
								)
	End If

	&apos;	Apply the filter and export
	_Component.storeToUrl(sFile, vStoreArguments)
	If LCase(ImageType) &lt;&gt; &quot;pdf&quot; Then _RestoreSelections(_Component, oSelect)

	bSaved = True

Finally:
	ExportRangeToFile = bSaved
	ScriptForge.SF_Utils._ExitFunction(cstThisSub)
	Exit Function
Catch:
	GoTo Finally
CatchError:
	ScriptForge.SF_Exception.RaiseFatal(RANGEEXPORTERROR, &quot;FileName&quot;, FileName, &quot;Overwrite&quot;, Overwrite)
	GoTo Finally
End Function   &apos;   SFDocuments.SF_Chart.ExportRangeToFile

REM -----------------------------------------------------------------------------
Public Function Forms(Optional ByVal SheetName As Variant _
							, Optional ByVal Form As Variant _
							) As Variant
&apos;&apos;&apos;	Return either
&apos;&apos;&apos;		- the list of the Forms contained in the given sheet
&apos;&apos;&apos;		- a SFDocuments.Form object based on its name or its index
&apos;&apos;&apos;	Args:
&apos;&apos;&apos;		SheetName: the name of the sheet containing the requested form or forms
&apos;&apos;&apos;		Form: a form stored in the document given by its name or its index
&apos;&apos;&apos;			When absent, the list of available forms is returned
&apos;&apos;&apos;			To get the first (unique ?) form stored in the form document, set Form = 0
&apos;&apos;&apos;	Exceptions:
&apos;&apos;&apos;		CALCFORMNOTFOUNDERROR		Form not found
&apos;&apos;&apos;	Returns:
&apos;&apos;&apos;		A zero-based array of strings if Form is absent
&apos;&apos;&apos;		An instance of the SF_Form class if Form exists
&apos;&apos;&apos;	Example:
&apos;&apos;&apos;			Dim myForm As Object, myList As Variant
&apos;&apos;&apos;				myList = oDoc.Forms(&quot;ThisSheet&quot;)
&apos;&apos;&apos;				Set myForm = oDoc.Forms(&quot;ThisSheet&quot;, 0)

Dim oForm As Object					&apos;	The new Form class instance
Dim oMainForm As Object				&apos;	com.sun.star.comp.sdb.Content
Dim oXForm As Object				&apos;	com.sun.star.form.XForm or com.sun.star.comp.forms.ODatabaseForm
Dim vFormNames As Variant			&apos;	Array of form names
Dim oForms As Object				&apos;	Forms collection
Const cstDrawPage = -1				&apos;	There is no DrawPages collection in Calc sheets

Const cstThisSub = &quot;SFDocuments.Calc.Forms&quot;
Const cstSubArgs = &quot;SheetName, [Form=&quot;&quot;&quot;&quot;]&quot;

	If ScriptForge.SF_Utils._ErrorHandling() Then On Local Error GoTo Catch

Check:
	If IsMissing(Form) Or IsEmpty(Form) Then Form = &quot;&quot;
	If ScriptForge.SF_Utils._EnterFunction(cstThisSub, cstSubArgs) Then
		If Not _IsStillAlive() Then GoTo Finally
		If Not _ValidateSheet(SheetName, &quot;SheetName&quot;, , True) Then GoTo Finally
		If Not ScriptForge.SF_Utils._Validate(Form, &quot;Form&quot;, Array(V_STRING, ScriptForge.V_NUMERIC)) Then GoTo Finally
	End If

Try:
	&apos;	Start from the Calc sheet and go down to forms
	Set oForms = _Component.getSheets.getByName(SheetName).DrawPage.Forms
	vFormNames = oForms.getElementNames()

	If Len(Form) = 0 Then	&apos;	Return the list of valid form names
		Forms = vFormNames
	Else
		If VarType(Form) = V_STRING Then	&apos;	Find the form by name
		If Not ScriptForge.SF_Utils._Validate(Form, &quot;Form&quot;, V_STRING, vFormNames) Then GoTo Finally
			Set oXForm = oForms.getByName(Form)
		Else								&apos;	Find the form by index
			If Form &lt; 0 Or Form &gt;= oForms.Count Then GoTo CatchNotFound
			Set oXForm = oForms.getByIndex(Form)
		End If
		&apos;	Create the new Form class instance
		Set oForm = SF_Register._NewForm(oXForm)
		With oForm
			Set .[_Parent] = [Me]
			._SheetName = SheetName
			._FormType = ISCALCFORM
			Set ._Component = _Component
			._Initialize()
		End With
		Set Forms = oForm
	End If

Finally:
	ScriptForge.SF_Utils._ExitFunction(cstThisSub)
	Exit Function
Catch:
	GoTo Finally
CatchNotFound:
	ScriptForge.SF_Exception.RaiseFatal(CALCFORMNOTFOUNDERROR, Form, _FileIdent())
End Function	&apos;	SFDocuments.SF_Calc.Forms

REM -----------------------------------------------------------------------------
Function GetColumnName(Optional ByVal ColumnNumber As Variant) As String
&apos;&apos;&apos;	Convert a column number (range 1, 2,..1024) into its letter counterpart (range &apos;A&apos;, &apos;B&apos;,..&apos;AMJ&apos;).
&apos;&apos;&apos;	Args:
&apos;&apos;&apos;		ColumnNumber: the column number, must be in the interval 1 ... 1024
&apos;&apos;&apos;	Returns:
&apos;&apos;&apos;		a string representation of the column name, in range &apos;A&apos;..&apos;AMJ&apos;
&apos;&apos;&apos;		If ColumnNumber is not in the allowed range, returns a zero-length string
&apos;&apos;&apos;	Example:
&apos;&apos;&apos;		MsgBox oDoc.GetColumnName(1022)	&apos;	&quot;AMH&quot;
&apos;&apos;&apos;	Adapted from a Python function by sundar nataraj
&apos;&apos;&apos;	http://stackoverflow.com/questions/23861680/convert-spreadsheet-number-to-column-letter

Dim sCol As String			&apos;	Return value
Const cstThisSub = &quot;SFDocuments.Calc.GetColumnName&quot;
Const cstSubArgs = &quot;ColumnNumber&quot;

	If ScriptForge.SF_Utils._ErrorHandling() Then On Local Error GoTo Catch
	sCol = &quot;&quot;

Check:
	If ScriptForge.SF_Utils._EnterFunction(cstThisSub, cstSubArgs) Then
		If Not SF_Utils._Validate(ColumnNumber, &quot;ColumnNumber&quot;, V_NUMERIC) Then GoTo Finally
	End If

Try:
	If (ColumnNumber &gt; 0) And (ColumnNumber &lt;= MAXCOLS) Then sCol = _GetColumnName(ColumnNumber)

Finally:
	GetColumnName = sCol
	ScriptForge.SF_Utils._ExitFunction(cstThisSub)
	Exit Function
Catch:
	GoTo Finally
End Function	&apos;	SFDocuments.SF_Calc.GetColumnName

REM -----------------------------------------------------------------------------
Public Function GetFormula(Optional ByVal Range As Variant) As Variant
&apos;&apos;&apos;	Get the formula(e) stored in the given range of cells
&apos;&apos;&apos;	Args:
&apos;&apos;&apos;		Range : the range as a string where to get the formula from
&apos;&apos;&apos;	Returns:
&apos;&apos;&apos;		A scalar, a zero-based 1D array or a zero-based 2D array of strings
&apos;&apos;&apos;	Examples:
&apos;&apos;&apos;		Val = oDoc.GetFormula(&quot;~.A1:A1000&quot;)

Dim vGet As Variant					&apos;	Return value
Dim oAddress As Object				&apos;	Alias of Range
Dim vDataArray As Variant			&apos;	DataArray compatible with .DataArray UNO property
Const cstThisSub = &quot;SFDocuments.Calc.GetFormula&quot;
Const cstSubArgs = &quot;Range&quot;

	If ScriptForge.SF_Utils._ErrorHandling() Then On Local Error GoTo Catch
	vGet = Empty

Check:
	If ScriptForge.SF_Utils._EnterFunction(cstThisSub, cstSubArgs) Then
		If Not _IsStillAlive() Then GoTo Finally
		If Not ScriptForge.SF_Utils._Validate(Range, &quot;Range&quot;, V_STRING) Then GoTo Finally
	End If

Try:
	&apos;	Get the data
	Set oAddress = _ParseAddress(Range)
	vDataArray = oAddress.XCellRange.getFormulaArray()

	&apos;	Convert the data array to scalar, vector or array
	vGet = _ConvertFromDataArray(vDataArray)

Finally:
	GetFormula = vGet
	ScriptForge.SF_Utils._ExitFunction(cstThisSub)
	Exit Function
Catch:
	GoTo Finally
End Function	&apos;	SFDocuments.SF_Calc.GetFormula

REM -----------------------------------------------------------------------------
Public Function GetProperty(Optional ByVal PropertyName As Variant _
								, Optional ObjectName As Variant _
								) As Variant
&apos;&apos;&apos;	Return the actual value of the given property
&apos;&apos;&apos;	Args:
&apos;&apos;&apos;		PropertyName: the name of the property as a string
&apos;&apos;&apos;		ObjectName: a sheet or range name
&apos;&apos;&apos;	Returns:
&apos;&apos;&apos;		The actual value of the property
&apos;&apos;&apos;	Exceptions:
&apos;&apos;&apos;		ARGUMENTERROR		The property does not exist

Const cstThisSub = &quot;SFDocuments.Calc.GetProperty&quot;
Const cstSubArgs = &quot;&quot;

	If ScriptForge.SF_Utils._ErrorHandling() Then On Local Error GoTo Catch
	GetProperty = Null

Check:
	If IsMissing(ObjectName) Or IsEMpty(ObjectName) Then ObjectName = &quot;&quot;
	If ScriptForge.SF_Utils._EnterFunction(cstThisSub, cstSubArgs) Then
		If Not ScriptForge.SF_Utils._Validate(PropertyName, &quot;PropertyName&quot;, V_STRING, Properties()) Then GoTo Catch
		If Not ScriptForge.SF_Utils._Validate(ObjectName, &quot;ObjectName&quot;, V_STRING) Then GoTo Catch
	End If

Try:
	&apos;	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)
	End If

Finally:
	ScriptForge.SF_Utils._ExitFunction(cstThisSub)
	Exit Function
Catch:
	GoTo Finally
End Function	&apos;	SFDocuments.SF_Calc.GetProperty

REM -----------------------------------------------------------------------------
Public Function GetValue(Optional ByVal Range As Variant) As Variant
&apos;&apos;&apos;	Get the value(s) stored in the given range of cells
&apos;&apos;&apos;	Args:
&apos;&apos;&apos;		Range : the range as a string where to get the value from
&apos;&apos;&apos;	Returns:
&apos;&apos;&apos;		A scalar, a zero-based 1D array or a zero-based 2D array of strings and doubles
&apos;&apos;&apos;		To convert doubles to dates, use the CDate builtin function
&apos;&apos;&apos;	Examples:
&apos;&apos;&apos;		Val = oDoc.GetValue(&quot;~.A1:A1000&quot;)

Dim vGet As Variant					&apos;	Return value
Dim oAddress As Object				&apos;	Alias of Range
Dim vDataArray As Variant			&apos;	DataArray compatible with .DataArray UNO property
Const cstThisSub = &quot;SFDocuments.Calc.GetValue&quot;
Const cstSubArgs = &quot;Range&quot;

	If ScriptForge.SF_Utils._ErrorHandling() Then On Local Error GoTo Catch
	vGet = Empty

Check:
	If ScriptForge.SF_Utils._EnterFunction(cstThisSub, cstSubArgs) Then
		If Not _IsStillAlive() Then GoTo Finally
		If Not ScriptForge.SF_Utils._Validate(Range, &quot;Range&quot;, V_STRING) Then GoTo Finally
	End If

Try:
	&apos;	Get the data
	Set oAddress = _ParseAddress(Range)
	vDataArray = oAddress.XCellRange.getDataArray()

	&apos;	Convert the data array to scalar, vector or array
	vGet = _ConvertFromDataArray(vDataArray)

Finally:
	GetValue = vGet
	ScriptForge.SF_Utils._ExitFunction(cstThisSub)
	Exit Function
Catch:
	GoTo Finally
End Function	&apos;	SFDocuments.SF_Calc.GetValue

REM -----------------------------------------------------------------------------
Public Function ImportFromCSVFile(Optional ByVal FileName As Variant _
								, Optional ByVal DestinationCell As Variant _
								, Optional ByVal FilterOptions As Variant _
								) As String
&apos;&apos;&apos; Import the content of a CSV-formatted text file starting from a given cell
&apos;&apos;&apos;	Beforehand the destination area will be cleared from any content and format
&apos;&apos;&apos;	Args:
&apos;&apos;&apos;		FileName: Identifies the file to open. It must follow the SF_FileSystem.FileNaming notation
&apos;&apos;&apos;		DestinationCell: the destination of the copied range of cells, as a string
&apos;&apos;&apos;			If given as range, the destination will be reduced to its top-left cell
&apos;&apos;&apos;		FilterOptions: The arguments of the CSV input filter.
&apos;&apos;&apos;			Read https://wiki.documentfoundation.org/Documentation/DevGuide/Spreadsheet_Documents#Filter_Options_for_the_CSV_Filter
&apos;&apos;&apos;			Default:	input file encoding is UTF8
&apos;&apos;&apos;						separator = comma, semi-colon or tabulation
&apos;&apos;&apos;						string delimiter = double quote
&apos;&apos;&apos;						all lines are included
&apos;&apos;&apos;						quoted strings are formatted as texts
&apos;&apos;&apos;						special numbers are detected
&apos;&apos;&apos;						all columns are presumed texts
&apos;&apos;&apos;						language = english/US =&gt; decimal separator is &quot;.&quot;, thousands separator = &quot;,&quot;
&apos;&apos;&apos;	Returns:
&apos;&apos;&apos;		A string representing the modified range of cells
&apos;&apos;&apos;		The modified area depends only on the content of the source file
&apos;&apos;&apos;	Exceptions:
&apos;&apos;&apos;		DOCUMENTOPENERROR			The csv file could not be opened
&apos;&apos;&apos;	Examples:
&apos;&apos;&apos;		oDoc.ImportFromCSVFile(&quot;C:\Temp\myCsvFile.csv&quot;, &quot;SheetY.C5&quot;)

Dim sImport As String			&apos;	Return value
Dim oUI As Object				&apos;	UI service
Dim oSource As Object			&apos;	New Calc document with csv loaded
Dim oSelect As Object			&apos;	Current selection in destination

Const cstFilter = &quot;Text - txt - csv (StarCalc)&quot;
Const cstFilterOptions = &quot;9/44/59/MRG,34,76,1,,1033,true,true&quot;
Const cstThisSub = &quot;SFDocuments.Calc.ImportFromCSVFile&quot;
Const cstSubArgs = &quot;FileName, DestinationCell, [FilterOptions]=&quot;&quot;9/44/59/MRG,34,76,1,,1033,true,true&quot;&quot;&quot;

&apos;	If ScriptForge.SF_Utils._ErrorHandling() Then On Local Error GoTo Catch
	sImport = &quot;&quot;

Check:
	If IsMissing(FilterOptions) Or IsEmpty(FilterOptions) Then FilterOptions = cstFilterOptions
	If ScriptForge.SF_Utils._EnterFunction(cstThisSub, cstSubArgs) Then
		If Not _IsStillAlive(True) Then GoTo Finally
		If Not ScriptForge.SF_Utils._ValidateFile(FileName, &quot;FileName&quot;) Then GoTo Finally
		If Not ScriptForge.SF_Utils._Validate(DestinationCell, &quot;DestinationCell&quot;, V_STRING) Then GoTo Finally
	End If

Try:
	&apos;	Input file is loaded in an empty worksheet. Data are copied to destination cell
	Set oUI = CreateScriptService(&quot;UI&quot;)
	Set oSource = oUI.OpenDocument(FileName _
						, ReadOnly := True _
						, Hidden := True _
						, FilterName := cstFilter _
						, FilterOptions := FilterOptions _
						)
	&apos;	Remember current selection and restore it after copy
	Set oSelect = _Component.CurrentController.getSelection()
	sImport = CopyToCell(oSource.Range(&quot;*&quot;), DestinationCell)
	_RestoreSelections(_Component, oSelect)

Finally:
	If Not IsNull(oSource) Then oSource.CloseDocument(False)
	ImportFromCSVFile = sImport
	ScriptForge.SF_Utils._ExitFunction(cstThisSub)
	Exit Function
Catch:
	GoTo Finally
End Function    &apos;   SFDocuments.SF_Calc.ImportFromCSVFile

REM -----------------------------------------------------------------------------
Public Sub ImportFromDatabase(Optional ByVal FileName As Variant _
								, Optional ByVal RegistrationName As Variant _
								, Optional ByVal DestinationCell As Variant _
								, Optional ByVal SQLCommand As Variant _
								, Optional ByVal DirectSQL As Variant _
								)
&apos;&apos;&apos; Import the content of a database table, query or resultset, i.e. the result of a SELECT SQL command,
&apos;&apos;&apos;	starting from a given cell
&apos;&apos;&apos;	Beforehand the destination area will be cleared from any content and format
&apos;&apos;&apos;	The modified area depends only on the content of the source data
&apos;&apos;&apos;	Args:
&apos;&apos;&apos;		FileName: Identifies the file to open. It must follow the SF_FileSystem.FileNaming notation
&apos;&apos;&apos;		RegistrationName: the name of a registered database
&apos;&apos;&apos;			It is ignored if FileName &lt;&gt; &quot;&quot;
&apos;&apos;&apos;		DestinationCell: the destination of the copied range of cells, as a string
&apos;&apos;&apos;			If given as a range of cells, the destination will be reduced to its top-left cell
&apos;&apos;&apos;		SQLCommand: either a table or query name (without square brackets)
&apos;&apos;&apos;			or a full SQL commands where table and fieldnames are preferably surrounded with square brackets
&apos;&apos;&apos;	Returns:
&apos;&apos;&apos;		Implemented as a Sub because the doImport UNO method does not return any error
&apos;&apos;&apos;	Exceptions:
&apos;&apos;&apos;		BASEDOCUMENTOPENERROR			The database file could not be opened
&apos;&apos;&apos;	Examples:
&apos;&apos;&apos;		oDoc.ImportFromDatabase(&quot;C:\Temp\myDbFile.odb&quot;, , &quot;SheetY.C5&quot;, &quot;SELECT * FROM [Employees] ORDER BY [LastName]&quot;)

Dim oDBContext As Object		&apos;	com.sun.star.sdb.DatabaseContext
Dim oDatabase As Object			&apos;	SFDatabases.Database service
Dim lCommandType As Long		&apos;	A com.sun.star.sheet.DataImportMode.xxx constant
Dim oQuery As Object			&apos;	com.sun.star.ucb.XContent
Dim bDirect As Boolean			&apos;	Alias of DirectSQL
Dim oDestRange As Object		&apos;	Destination as a range
Dim oDestAddress As Object		&apos;	com.sun.star.table.CellRangeAddress
Dim oDestCell As Object			&apos;	com.sun.star.table.XCell
Dim oSelect As Object			&apos;	Current selection in destination
Dim vImportOptions As Variant	&apos;	Array of PropertyValues

Const cstThisSub = &quot;SFDocuments.Calc.ImportFromDatabase&quot;
Const cstSubArgs = &quot;[FileName=&quot;&quot;&quot;&quot;], [RegistrationName=&quot;&quot;&quot;&quot;], DestinationCell, SQLCommand, [DirectSQL=False]&quot;

&apos;	If ScriptForge.SF_Utils._ErrorHandling() Then On Local Error GoTo Catch

Check:

	If IsMissing(FileName) Or IsEmpty(FileName) Then FileName = &quot;&quot;
	If IsMissing(RegistrationName) Or IsEmpty(RegistrationName) Then RegistrationName = &quot;&quot;
	If IsMissing(DirectSQL) Or IsEmpty(DirectSQL) Then DirectSQL = False
	If ScriptForge.SF_Utils._EnterFunction(cstThisSub, cstSubArgs) Then
		If Not _IsStillAlive(True) Then GoTo Finally
		If Not ScriptForge.SF_Utils._ValidateFile(FileName, &quot;FileName&quot;, , True) Then GoTo Finally
		If Not ScriptForge.SF_Utils._Validate(DestinationCell, &quot;DestinationCell&quot;, V_STRING) Then GoTo Finally
		If Not ScriptForge.SF_Utils._Validate(SQLCommand, &quot;SQLCommand&quot;, V_STRING) Then GoTo Finally
		If Not ScriptForge.SF_Utils._Validate(DirectSQL, &quot;DirectSQL&quot;, ScriptForge.V_BOOLEAN) Then GoTo Finally
	End If

	&apos;	Check the existence of FileName
	If Len(FileName) = 0 Then	&apos;	FileName has precedence over RegistrationName
		If Len(RegistrationName) = 0 Then GoTo CatchError
		Set oDBContext = ScriptForge.SF_Utils._GetUNOService(&quot;DatabaseContext&quot;)
		If Not oDBContext.hasRegisteredDatabase(RegistrationName) Then GoTo CatchError
		FileName = ScriptForge.SF_FileSystem._ConvertFromUrl(oDBContext.getDatabaseLocation(RegistrationName))
	End If
	If Not ScriptForge.SF_FileSystem.FileExists(FileName) Then GoTo CatchError

Try:
	&apos;	Check command type
	Set oDatabase = ScriptForge.SF_Services.CreateScriptService(&quot;SFDatabases.Database&quot;, FileName, , True)	&apos;	Read-only
	If IsNull(oDatabase) Then GoTo CatchError
	With oDatabase
		If ScriptForge.SF_Array.Contains(.Tables, SQLCommand) Then
			bDirect = True
			lCommandType = com.sun.star.sheet.DataImportMode.TABLE
		ElseIf ScriptForge.SF_Array.Contains(.Queries, SQLCommand) Then
			Set oQuery = .XConnection.Queries.getByName(SQLCommand)
			bDirect = Not oQuery.EscapeProcessing
			lCommandType = com.sun.star.sheet.DataImportMode.QUERY
		Else
			bDirect = DirectSQL
			lCommandType = com.sun.star.sheet.DataImportMode.SQL
			SQLCommand = ._ReplaceSquareBrackets(SQLCommand)
		End If
		.CloseDatabase()
		Set oDatabase = oDatabase.Dispose()
	End With

	&apos;	Determine the destination cell as the top-left coordinates of the given range
	Set oDestRange = _ParseAddress(DestinationCell)
	Set oDestAddress = oDestRange.XCellRange.RangeAddress
	Set oDestCell = oDestRange.XSpreadsheet.getCellByPosition(oDestAddress.StartColumn, oDestAddress.StartRow)

	&apos;	Remember current selection
	Set oSelect = _Component.CurrentController.getSelection()
	&apos;	Import arguments
	vImportOptions = Array(_
			ScriptForge.SF_Utils._MakePropertyValue(&quot;DatabaseName&quot;, ScriptForge.SF_FileSystem._ConvertToUrl(FileName)) _
			, ScriptForge.SF_Utils._MakePropertyValue(&quot;SourceObject&quot;, SQLCommand) _
			, ScriptForge.SF_Utils._MakePropertyValue(&quot;SourceType&quot;, lCommandType) _
			, ScriptForge.SF_Utils._MakePropertyValue(&quot;IsNative&quot;, bDirect) _
			)
	oDestCell.doImport(vImportOptions)
	&apos;	Restore selection after import_
	_RestoreSelections(_Component, oSelect)

Finally:
	ScriptForge.SF_Utils._ExitFunction(cstThisSub)
	Exit Sub
Catch:
	GoTo Finally
CatchError:
	SF_Exception.RaiseFatal(BASEDOCUMENTOPENERROR, &quot;FileName&quot;, FileName, &quot;RegistrationName&quot;, RegistrationName)
	GoTo Finally
End Sub		    &apos;   SFDocuments.SF_Calc.ImportFromDatabase

REM -----------------------------------------------------------------------------
Public Function InsertSheet(Optional ByVal SheetName As Variant _
								, Optional ByVal BeforeSheet As Variant _
								) As Boolean
&apos;&apos;&apos; Insert a new empty sheet before an existing sheet or at the end of the list of sheets
&apos;&apos;&apos;	Args:
&apos;&apos;&apos;		SheetName: The name of the new sheet
&apos;&apos;&apos;		BeforeSheet: The name (string) or index (numeric, starting from 1) of the sheet before which to insert
&apos;&apos;&apos;	Returns:
&apos;&apos;&apos;		True if the sheet could be inserted successfully
&apos;&apos;&apos;	Examples:
&apos;&apos;&apos;		oDoc.InsertSheet(&quot;SheetX&quot;, &quot;SheetY&quot;)

Dim bInsert As Boolean				&apos;	Return value
Dim vSheets As Variant				&apos;	List of existing sheets
Dim lSheetIndex As Long				&apos;	Index of a sheet
Const cstThisSub = &quot;SFDocuments.Calc.InsertSheet&quot;
Const cstSubArgs = &quot;SheetName, [BeforeSheet=&quot;&quot;&quot;&quot;]&quot;

	If ScriptForge.SF_Utils._ErrorHandling() Then On Local Error GoTo Catch
	bInsert = False

Check:
	If IsMissing(BeforeSheet) Or IsEmpty(BeforeSheet) Then BeforeSheet = 32768
	If ScriptForge.SF_Utils._EnterFunction(cstThisSub, cstSubArgs) Then
		If Not _IsStillAlive(True) Then GoTo Finally
		If Not _ValidateSheet(SheetName, &quot;SheetName&quot;, True) Then GoTo Finally
		If Not _ValidateSheet(BeforeSheet, &quot;BeforeSheet&quot;, , True, , True) Then GoTo Finally
	End If
	vSheets = _Component.getSheets.getElementNames()

Try:
	If VarType(BeforeSheet) = V_STRING Then
		lSheetIndex = ScriptForge.SF_Array.IndexOf(vSheets, BeforeSheet)
	Else
		lSheetIndex = BeforeSheet - 1
		If lSheetIndex &lt; 0 Then lSheetIndex = 0
		If lSheetIndex &gt; UBound(vSheets) Then lSheetIndex = UBound(vSheets) + 1
	End If
	_Component.getSheets.insertNewByName(SheetName, lSheetIndex)
	bInsert = True

Finally:
	InsertSheet = binsert
	ScriptForge.SF_Utils._ExitFunction(cstThisSub)
	Exit Function
Catch:
	GoTo Finally
End Function    &apos;   SFDocuments.SF_Calc.InsertSheet

REM -----------------------------------------------------------------------------
Public Function Methods() As Variant
&apos;&apos;&apos;	Return the list of public methods of the Calc service as an array

	Methods = Array( _
					&quot;A1Style&quot; _
					, &quot;Charts&quot; _
					, &quot;ClearAll&quot; _
					, &quot;ClearFormats&quot; _
					, &quot;ClearValues&quot; _
					, &quot;CopySheet&quot; _
					, &quot;CopySheetFromFile&quot; _
					, &quot;CopyToCell&quot; _
					, &quot;CopyToRange&quot; _
					, &quot;CreateChart&quot; _
					, &quot;DAvg&quot; _
					, &quot;DCount&quot; _
					, &quot;DMax&quot; _
					, &quot;DMin&quot; _
					, &quot;DSum&quot; _
					, &quot;ExportRangeToFile&quot; _
					, &quot;GetColumnName&quot; _
					, &quot;GetFormula&quot; _
					, &quot;GetValue&quot; _
					, &quot;ImportFromCSVFile&quot; _
					, &quot;ImportFromDatabase&quot; _
					, &quot;InsertSheet&quot; _
					, &quot;MoveRange&quot; _
					, &quot;MoveSheet&quot; _
					, &quot;Offset&quot; _
					, &quot;OpenRangeSelector&quot; _
					, &quot;Printf&quot; _
					, &quot;PrintOut&quot; _
					, &quot;RemoveSheet&quot; _
					, &quot;RenameSheet&quot; _
					, &quot;SetArray&quot; _
					, &quot;SetCellStyle&quot; _
					, &quot;SetFormula&quot; _
					, &quot;SetValue&quot; _
					, &quot;ShiftDown&quot; _
					, &quot;ShiftLeft&quot; _
					, &quot;ShiftRight&quot; _
					, &quot;ShiftUp&quot; _
					, &quot;SortRange&quot; _
					)

End Function	&apos;	SFDocuments.SF_Calc.Methods

REM -----------------------------------------------------------------------------
Public Function MoveRange(Optional ByVal Source As Variant _
								, Optional ByVal Destination As Variant _
								) As String
&apos;&apos;&apos; Move a specified source range to a destination range
&apos;&apos;&apos;	Args:
&apos;&apos;&apos;		Source: the source range of cells as a string
&apos;&apos;&apos;		Destination: the destination of the moved range of cells, as a string
&apos;&apos;&apos;			If given as a range of cells, the destination will be reduced to its top-left cell
&apos;&apos;&apos;	Returns:
&apos;&apos;&apos;		A string representing the modified range of cells
&apos;&apos;&apos;		The modified area depends only on the size of the source area
&apos;&apos;&apos;	Examples:
&apos;&apos;&apos;		oDoc.MoveRange(&quot;SheetX.A1:F10&quot;, &quot;SheetY.C5&quot;)

Dim sMove As String				&apos;	Return value
Dim oSource As Object			&apos;	Alias of Source to avoid &quot;Object variable not set&quot; run-time error
Dim oSourceAddress As Object	&apos;	com.sun.star.table.CellRangeAddress
Dim oDestRange As Object		&apos;	Destination as a range
Dim oDestAddress As Object		&apos;	com.sun.star.table.CellRangeAddress
Dim oDestCell As Object			&apos;	com.sun.star.table.CellAddress
Dim oSelect As Object			&apos;	Current selection in source
Dim oClipboard As Object		&apos;	com.sun.star.datatransfer.XTransferable
Dim oCellRanges As Object		&apos;	com.sun.star.sheet.SheetCellRanges
Dim vRangeAddresses As Variant	&apos;	Array of com.sun.star.table.CellRangeAddress
Dim i As Long

Const cstThisSub = &quot;SFDocuments.Calc.MoveRange&quot;
Const cstSubArgs = &quot;Source, Destination&quot;

	If ScriptForge.SF_Utils._ErrorHandling() Then On Local Error GoTo Catch
	sMove = &quot;&quot;

Check:
	If ScriptForge.SF_Utils._EnterFunction(cstThisSub, cstSubArgs) Then
		If Not _IsStillAlive(True) Then GoTo Finally
		If Not _Validate(Source, &quot;Source&quot;, V_STRING) Then GoTo Finally
		If Not _Validate(Destination, &quot;Destination&quot;, V_STRING) Then GoTo Finally
	End If

Try:
	Set oSourceAddress = _ParseAddress(Source).XCellRange.RangeAddress
	Set oDestRange = _ParseAddress(Destination)
	Set oDestAddress = oDestRange.XCellRange.RangeAddress
	Set oDestCell = New com.sun.star.table.CellAddress
	With oDestAddress
		oDestCell.Sheet = .Sheet
		oDestCell.Column = .StartColumn
		oDestCell.Row = .StartRow
	End With
	oDestRange.XSpreadsheet.moveRange(oDestCell, oSourceAddress)

	With oSourceAddress
		sMove = _Offset(Destination, 0, 0, .EndRow - .StartRow + 1, .EndColumn - .StartColumn + 1).RangeName
	End With

Finally:
	MoveRange = sMove
	ScriptForge.SF_Utils._ExitFunction(cstThisSub)
	Exit Function
Catch:
	GoTo Finally
End Function    &apos;   SFDocuments.SF_Calc.MoveRange

REM -----------------------------------------------------------------------------
Public Function MoveSheet(Optional ByVal SheetName As Variant _
								, Optional ByVal BeforeSheet As Variant _
								) As Boolean
&apos;&apos;&apos; Move a sheet before an existing sheet or at the end of the list of sheets
&apos;&apos;&apos;	Args:
&apos;&apos;&apos;		SheetName: The name of the sheet to move
&apos;&apos;&apos;		BeforeSheet: The name (string) or index (numeric, starting from 1) of the sheet before which to move the sheet
&apos;&apos;&apos;	Returns:
&apos;&apos;&apos;		True if the sheet could be moved successfully
&apos;&apos;&apos;	Examples:
&apos;&apos;&apos;		oDoc.MoveSheet(&quot;SheetX&quot;, &quot;SheetY&quot;)

Dim bMove As Boolean				&apos;	Return value
Dim vSheets As Variant				&apos;	List of existing sheets
Dim lSheetIndex As Long				&apos;	Index of a sheet
Const cstThisSub = &quot;SFDocuments.Calc.MoveSheet&quot;
Const cstSubArgs = &quot;SheetName, [BeforeSheet=&quot;&quot;&quot;&quot;]&quot;

	If ScriptForge.SF_Utils._ErrorHandling() Then On Local Error GoTo Catch
	bMove = False

Check:
	If IsMissing(BeforeSheet) Or IsEmpty(BeforeSheet) Then BeforeSheet = 32768
	If ScriptForge.SF_Utils._EnterFunction(cstThisSub, cstSubArgs) Then
		If Not _IsStillAlive(True) Then GoTo Finally
		If Not _ValidateSheet(SheetName, &quot;SheetName&quot;, , True) Then GoTo Finally
		If Not _ValidateSheet(BeforeSheet, &quot;BeforeSheet&quot;, , True, , True) Then GoTo Finally
	End If
	vSheets = _Component.getSheets.getElementNames()

Try:
	If VarType(BeforeSheet) = V_STRING Then
		lSheetIndex = ScriptForge.SF_Array.IndexOf(vSheets, BeforeSheet)
	Else
		lSheetIndex = BeforeSheet - 1
		If lSheetIndex &lt; 0 Then lSheetIndex = 0
		If lSheetIndex &gt; UBound(vSheets) Then lSheetIndex = UBound(vSheets) + 1
	End If
	_Component.getSheets.MoveByName(SheetName, lSheetIndex)
	bMove = True

Finally:
	MoveSheet = bMove
	ScriptForge.SF_Utils._ExitFunction(cstThisSub)
	Exit Function
Catch:
	GoTo Finally
End Function    &apos;   SFDocuments.SF_Calc.MoveSheet

REM -----------------------------------------------------------------------------
Public Function Offset(Optional ByRef Range As Variant _
								, Optional ByVal Rows As Variant _
								, Optional ByVal Columns As Variant _
								, Optional ByVal Height As Variant _
								, Optional ByVal Width As Variant _
								) As String
&apos;&apos;&apos;	Returns a new range offset by a certain number of rows and columns from a given range
&apos;&apos;&apos;	Args:
&apos;&apos;&apos;		Range : the range, as a string, from which the function searches for the new range
&apos;&apos;&apos;		Rows : the number of rows by which the reference was corrected up (negative value) or down.
&apos;&apos;&apos;				Use 0 (default) to stay in the same row.
&apos;&apos;&apos;		Columns : the number of columns by which the reference was corrected to the left (negative value) or to the right.
&apos;&apos;&apos;				Use 0 (default) to stay in the same column
&apos;&apos;&apos;		Height : the vertical height for an area that starts at the new reference position.
&apos;&apos;&apos;				Default = no vertical resizing
&apos;&apos;&apos;		Width : the horizontal width for an area that starts at the new reference position.
&apos;&apos;&apos;				Default - no horizontal resizing
&apos;&apos;&apos;		Arguments Rows and Columns must not lead to zero or negative start row or column.
&apos;&apos;&apos;		Arguments Height and Width must not lead to zero or negative count of rows or columns.
&apos;&apos;&apos;	Returns:
&apos;&apos;&apos;		A new range as a string
&apos;&apos;&apos;	Exceptions:
&apos;&apos;&apos;		OFFSETADDRESSERROR		The computed range of cells falls beyond the sheet boundaries
&apos;&apos;&apos;	Examples:
&apos;&apos;&apos;		oDoc.Offset(&quot;A1&quot;, 2, 2)			&apos;	&quot;&apos;SheetX&apos;.$C$3&quot; (A1 moved by two rows and two columns down)
&apos;&apos;&apos;		oDoc.Offset(&quot;A1&quot;, 2, 2, 5, 6)	&apos;	&quot;&apos;SheetX&apos;.$C$3:$H$7&quot;

Dim sOffset As String				&apos;	Return value
Dim oAddress As Object				&apos;	Alias of Range
Const cstThisSub = &quot;SFDocuments.Calc.Offset&quot;
Const cstSubArgs = &quot;Range, [Rows=0], [Columns=0], [Height], [Width]&quot;

	If ScriptForge.SF_Utils._ErrorHandling() Then On Local Error GoTo Catch
	sOffset = &quot;&quot;

Check:
	If IsMissing(Rows) Or IsEmpty(Rows) Then Rows = 0
	If IsMissing(Columns) Or IsEmpty(Columns) Then Columns = 0
	If IsMissing(Height) Or IsEmpty(Height) Then Height = 0
	If IsMissing(Width) Or IsEmpty(Width) Then Width = 0
	If ScriptForge.SF_Utils._EnterFunction(cstThisSub, cstSubArgs) Then
		If Not _IsStillAlive() Then GoTo Finally
		If Not ScriptForge.SF_Utils._Validate(Range, &quot;Range&quot;, V_STRING) Then GoTo Finally
		If Not ScriptForge.SF_Utils._Validate(Rows, &quot;Rows&quot;, ScriptForge.V_NUMERIC) Then GoTo Finally
		If Not ScriptForge.SF_Utils._Validate(Columns, &quot;Columns&quot;, ScriptForge.V_NUMERIC) Then GoTo Finally
		If Not ScriptForge.SF_Utils._Validate(Height, &quot;Height&quot;, ScriptForge.V_NUMERIC) Then GoTo Finally
		If Not ScriptForge.SF_Utils._Validate(Width, &quot;Width&quot;, ScriptForge.V_NUMERIC) Then GoTo Finally
	End If

Try:
	&apos;	Define the new range string
	Set oAddress = _Offset(Range, Rows, Columns, Height, Width)
	sOffset = oAddress.RangeName

Finally:
	Offset = sOffset
	ScriptForge.SF_Utils._ExitFunction(cstThisSub)
	Exit Function
Catch:
	GoTo Finally
End Function	&apos;	SFDocuments.SF_Calc.Offset

REM -----------------------------------------------------------------------------
Public Function OpenRangeSelector(Optional ByVal Title As Variant _
								, Optional ByVal Selection As Variant _
								, Optional ByVal SingleCell As Variant _
								, Optional ByVal CloseAfterSelect As Variant _
								) As String
&apos;&apos;&apos;	Activates the Calc document, opens a non-modal dialog with a text box,
&apos;&apos;&apos;	let the user make a selection in the current or another sheet and
&apos;&apos;&apos;	returns the selected area as a string.
&apos;&apos;&apos;	This method does not change the current selection.
&apos;&apos;&apos;	Args:
&apos;&apos;&apos;		Title: the title to display on the top of the dialog
&apos;&apos;&apos;		Selection: a default preselection as a String. When absent, the first element of the
&apos;&apos;&apos;			current selection is preselected.
&apos;&apos;&apos;		SingleCell: When True, only a single cell may be selected. Default = False
&apos;&apos;&apos;		CloseAfterSelect: When True (default-, the dialog is closed immediately after
&apos;&apos;&apos;			the selection. When False, the user may change his/her mind and must close
&apos;&apos;&apos;			the dialog manually.
&apos;&apos;&apos;	Returns:
&apos;&apos;&apos;		The selected range as a string, or the empty string when the user cancelled the request (close window button)
&apos;&apos;&apos;	Exceptions:
&apos;&apos;&apos;	Examples:
&apos;&apos;&apos;		Dim sSelect As String, vValues As Variant
&apos;&apos;&apos;		sSelect = oDoc.OpenRangeSelector(&quot;Select a range ...&quot;)
&apos;&apos;&apos;		If sSelect = &quot;&quot; Then Exit Function
&apos;&apos;&apos;		vValues = oDoc.GetValue(sSelect)

Dim sSelector As String				&apos;	Return value
Dim vPropertyValues As Variant		&apos;	Array of com.sun.star.beans.PropertyValue
Dim oSelection As Object			&apos;	The current selection before opening the selector
Dim oAddress As Object				&apos;	Preselected address as _Address

Const cstThisSub = &quot;SFDocuments.Calc.OpenRangeSelector&quot;
Const cstSubArgs = &quot;[Title=&quot;&quot;&quot;&quot;], [Selection=&quot;&quot;~&quot;&quot;], [SingleCell=False], [CloseAfterSelect=True]&quot;

	If ScriptForge.SF_Utils._ErrorHandling() Then On Local Error GoTo Catch
	sSelector = &quot;&quot;

Check:
	If IsMissing(Title) Or IsEmpty(Title) Then Title = &quot;&quot;
	If IsMissing(Selection) Or IsEmpty(Selection) Then Selection = &quot;~&quot;
	If IsMissing(SingleCell) Or IsEmpty(SingleCell) Then SingleCell = False
	If IsMissing(CloseAfterSelect) Or IsEmpty(CloseAfterSelect) Then CloseAfterSelect = True
	If ScriptForge.SF_Utils._EnterFunction(cstThisSub, cstSubArgs) Then
		If Not _IsStillAlive() Then GoTo Finally
		If Not ScriptForge.SF_Utils._Validate(Title, &quot;Title&quot;, V_STRING) Then GoTo Finally
		If Not ScriptForge.SF_Utils._Validate(Selection, &quot;Selection&quot;, V_STRING) Then GoTo Finally
		If Not ScriptForge.SF_Utils._Validate(SingleCell, &quot;SingleCell&quot;, ScriptForge.V_BOOLEAN) Then GoTo Finally
		If Not ScriptForge.SF_Utils._Validate(CloseAfterSelect, &quot;CloseAfterSelect&quot;, ScriptForge.V_BOOLEAN) Then GoTo Finally
	End If

Try:
	&apos;	Save the current selections
	Set oSelection = _Component.CurrentController.getSelection()

	&apos;	Process preselection and select its containing sheet
	Set oAddress = _ParseAddress(Selection)
	Activate(oAddress.SheetName)

	&apos;	Build arguments array and execute the dialog box
	With ScriptForge.SF_Utils
		vPropertyValues = Array( _
				._MakePropertyValue(&quot;Title&quot;, Title) _
				, ._MakePropertyValue(&quot;CloseOnMouseRelease&quot;, CloseAfterSelect) _
				, ._MakePropertyValue(&quot;InitialValue&quot;, oAddress.XCellRange.AbsoluteName) _
				, ._MakePropertyValue(&quot;SingleCellMode&quot;, SingleCell) _
				)
	End With
	sSelector = SF_DocumentListener.RunRangeSelector(_Component, vPropertyValues)

	&apos;	Restore the saved selections
	_RestoreSelections(_Component, oSelection)

Finally:
	OpenRangeSelector = sSelector
	ScriptForge.SF_Utils._ExitFunction(cstThisSub)
	Exit Function
Catch:
	GoTo Finally
End Function	&apos;	SFDocuments.SF_Calc.OpenRangeSelector

REM -----------------------------------------------------------------------------
Public Function Printf(Optional ByVal InputStr As Variant _
								, Optional ByVal Range As Variant _
								, Optional ByVal TokenCharacter As Variant _
								) As String
&apos;&apos;&apos;	Returns the input string after substitution of its tokens by
&apos;&apos;&apos;	their values in the given range
&apos;&apos;&apos;	This method is usually used in combination with SetFormula()
&apos;&apos;&apos;	The accepted tokens are:
&apos;&apos;&apos;		- %S	The sheet name containing the range, including single quotes when necessary
&apos;&apos;&apos;		- %R1	The row number of the topleft part of the range
&apos;&apos;&apos;		- %C1	The column letter of the topleft part of the range
&apos;&apos;&apos;		- %R2	The row number of the bottomright part of the range
&apos;&apos;&apos;		- %C2	The column letter of the bottomright part of the range
&apos;&apos;&apos;	Args:
&apos;&apos;&apos;		InputStr: usually a Calc formula or a part of a formula, but may be any string
&apos;&apos;&apos;		Range: the range, as a string from which the values of the tokens are derived
&apos;&apos;&apos;		TokenCharacter: the character identifying tokens. Default = &quot;%&quot;.
&apos;&apos;&apos;			Double the TokenCharacter to not consider it as a token.
&apos;&apos;&apos;	Returns:
&apos;&apos;&apos;		The input string after substitution of the contained tokens
&apos;&apos;&apos;	Exceptions:
&apos;&apos;&apos;	Examples:
&apos;&apos;&apos;		Assume we have in A1:E10 a matrix of numbers. To obtain the sum by row in F1:F10 ...
&apos;&apos;&apos;			Dim range As String, formula As String
&apos;&apos;&apos;				range = &quot;$A$1:$E$10&quot;)
&apos;&apos;&apos;				formula = &quot;=SUM($%C1%R1:$%C2%R1)&quot;	&apos;	&quot;=SUM($A1:$E1)&quot;, note the relative references
&apos;&apos;&apos;				oDoc.SetFormula(&quot;$F$1:$F$10&quot;, formula)
&apos;&apos;&apos;					&apos;F1 will contain	=Sum($A1:$E1)
&apos;&apos;&apos;					&apos;F2					=Sum($A2:$E2)
&apos;&apos;&apos;					&apos;	...

Dim sPrintf As String				&apos;	Return value
Dim vSubstitute As Variants			&apos;	Array of strings representing the token values
Dim oAddress As Object				&apos;	A range as an _Address object
Dim sSheetName As String			&apos;	The %S token value
Dim sC1 As String					&apos;	The %C1 token value
Dim sR1 As String					&apos;	The %R1 token value
Dim sC2 As String					&apos;	The %C2 token value
Dim sR2 As String					&apos;	The %R2 token value
Dim i As Long
Const cstPseudoToken = &quot;@#@&quot;

Const cstThisSub = &quot;SFDocuments.Calc.Printf&quot;
Const cstSubArgs = &quot;InputStr, Range, TokenCharacter=&quot;&quot;%&quot;&quot;&quot;

	If ScriptForge.SF_Utils._ErrorHandling() Then On Local Error GoTo Catch
	sPrintf = &quot;&quot;

Check:
	If IsMissing(TokenCharacter) Or IsEmpty(TokenCharacter) Then TokenCharacter = &quot;%&quot;
	If ScriptForge.SF_Utils._EnterFunction(cstThisSub, cstSubArgs) Then
		If Not _IsStillAlive() Then GoTo Finally
		If Not ScriptForge.SF_Utils._Validate(InputStr, &quot;InputStr&quot;, V_STRING) Then GoTo Finally
		If Not ScriptForge.SF_Utils._Validate(Range, &quot;Range&quot;, V_STRING) Then GoTo Finally
		If Not ScriptForge.SF_Utils._Validate(TokenCharacter, &quot;TokenCharacter&quot;, V_STRING) Then GoTo Finally
	End If

Try:
	&apos;	Define the token values
	Set oAddress = _ParseAddress(Range)
	With oAddress.XCellRange
		sC1 = _GetColumnName(.RangeAddress.StartColumn + 1)
		sR1 = CStr(.RangeAddress.StartRow + 1)
		sC2 = _GetColumnName(.RangeAddress.EndColumn + 1)
		sR2 = CStr(.RangeAddress.EndRow + 1)
		sSheetName = _QuoteSheetName(oAddress.XSpreadsheet.Name)
	End With

	&apos;	Substitute tokens by their values
	sPrintf = ScriptForge.SF_String.ReplaceStr(InputStr _
					, Array(TokenCharacter &amp; TokenCharacter _
							, TokenCharacter &amp; &quot;R1&quot; _
							, TokenCharacter &amp; &quot;C1&quot; _
							, TokenCharacter &amp; &quot;R2&quot; _
							, TokenCharacter &amp; &quot;C2&quot; _
							, TokenCharacter &amp; &quot;S&quot; _
							, cstPseudoToken _
							) _
					, Array(cstPseudoToken _
							, sR1 _
							, sC1 _
							, sR2 _
							, sC2 _
							, sSheetName _
							, TokenCharacter _
							) _
					)

Finally:
	Printf = sPrintf
	ScriptForge.SF_Utils._ExitFunction(cstThisSub)
	Exit Function
Catch:
	GoTo Finally
End Function	&apos;	SFDocuments.SF_Calc.Printf

REM -----------------------------------------------------------------------------
Public Function PrintOut(Optional ByVal SheetName As Variant _
							, Optional ByVal Pages As Variant _
							, Optional ByVal Copies As Variant _
							) As Boolean
&apos;&apos;&apos; Send the content of the given sheet to the printer.
&apos;&apos;&apos;	The printer might be defined previously by default, by the user or by the SetPrinter() method
&apos;&apos;&apos;	Args:
&apos;&apos;&apos;		SheetName: the sheet to print. Default = the active sheet
&apos;&apos;&apos;		Pages: the pages to print as a string, like in the user interface. Example: &quot;1-4;10;15-18&quot;. Default = all pages
&apos;&apos;&apos;		Copies: the number of copies
&apos;&apos;&apos;	Returns:
&apos;&apos;&apos;		True when successful
&apos;&apos;&apos;	Examples:
&apos;&apos;&apos;		oDoc.PrintOut(&quot;SheetX&quot;, &quot;1-4;10;15-18&quot;, Copies := 2)

Dim bPrint As Boolean				&apos;	Return value
Dim oSheet As Object				&apos;	SheetName as a reference

Const cstThisSub = &quot;SFDocuments.Calc.PrintOut&quot;
Const cstSubArgs = &quot;[SheetName=&quot;&quot;~&quot;&quot;], [Pages=&quot;&quot;&quot;&quot;], [Copies=1]&quot;

	If ScriptForge.SF_Utils._ErrorHandling() Then On Local Error GoTo Catch
	bPrint = False

Check:
	If IsMissing(SheetName) Or IsEmpty(SheetName) Then SheetName = &quot;&quot;
	If IsMissing(Pages) Or IsEmpty(Pages) Then Pages = &quot;&quot;
	If IsMissing(Copies) Or IsEmpty(Copies) Then Copies = 1

	If ScriptForge.SF_Utils._EnterFunction(cstThisSub, cstSubArgs) Then
		If Not _IsStillAlive() Then GoTo Finally
		If Not _ValidateSheet(SheetName, &quot;SheetName&quot;, , True, True) Then GoTo Finally
		If Not ScriptForge.SF_Utils._Validate(Pages, &quot;Pages&quot;, V_STRING) Then GoTo Finally
		If Not ScriptForge.SF_Utils._Validate(Copies, &quot;Copies&quot;, ScriptForge.V_NUMERIC) Then GoTo Finally
	End If

Try:
	If SheetName = &quot;~&quot; Then SheetName = &quot;&quot;
	&apos;	Make given sheet active
	If Len(SheetName) &gt; 0 Then
		With _Component
			Set oSheet = .getSheets.getByName(SheetName)
			Set .CurrentController.ActiveSheet = oSheet
		End With
	End If

	bPrint = [_Super].PrintOut(Pages, Copies, _Component)

Finally:
	PrintOut = bPrint
	ScriptForge.SF_Utils._ExitFunction(cstThisSub)
	Exit Function
Catch:
	GoTo Finally
End Function   &apos;   SFDocuments.SF_Calc.PrintOut

REM -----------------------------------------------------------------------------
Public Function Properties() As Variant
&apos;&apos;&apos;	Return the list or properties of the Calc class as an array

	Properties = Array( _
					&quot;CurrentSelection&quot; _
					, &quot;CustomProperties&quot; _
					, &quot;Description&quot; _
					, &quot;DocumentProperties&quot; _
					, &quot;DocumentType&quot; _
					, &quot;ExportFilters&quot; _
					, &quot;FirstCell&quot; _
					, &quot;FirstColumn&quot; _
					, &quot;FirstRow&quot; _
					, &quot;Height&quot; _
					, &quot;ImportFilters&quot; _
					, &quot;IsBase&quot; _
					, &quot;IsCalc&quot; _
					, &quot;IsDraw&quot; _
					, &quot;IsImpress&quot; _
					, &quot;IsMath&quot; _
					, &quot;IsWriter&quot; _
					, &quot;Keywords&quot; _
					, &quot;LastCell&quot; _
					, &quot;LastColumn&quot; _
					, &quot;LastRow&quot; _
					, &quot;Range&quot; _
					, &quot;Readonly&quot; _
					, &quot;Region&quot; _
					, &quot;Sheet&quot; _
					, &quot;SheetName&quot; _
					, &quot;Sheets&quot; _
					, &quot;Subject&quot; _
					, &quot;Title&quot; _
					, &quot;Width&quot; _
					, &quot;XCellRange&quot; _
					, &quot;XComponent&quot; _
					, &quot;XSheetCellCursor&quot; _
					, &quot;XSpreadsheet&quot; _
					)

End Function	&apos;	SFDocuments.SF_Calc.Properties

REM -----------------------------------------------------------------------------
Public Function RemoveSheet(Optional ByVal SheetName As Variant) As Boolean
&apos;&apos;&apos; Remove an existing sheet from the document
&apos;&apos;&apos;	Args:
&apos;&apos;&apos;		SheetName: The name of the sheet to remove
&apos;&apos;&apos;	Returns:
&apos;&apos;&apos;		True if the sheet could be removed successfully
&apos;&apos;&apos;	Examples:
&apos;&apos;&apos;		oDoc.RemoveSheet(&quot;SheetX&quot;)

Dim bRemove As Boolean				&apos;	Return value
Const cstThisSub = &quot;SFDocuments.Calc.RemoveSheet&quot;
Const cstSubArgs = &quot;SheetName&quot;

	If ScriptForge.SF_Utils._ErrorHandling() Then On Local Error GoTo Catch
	bRemove = False

Check:
	If ScriptForge.SF_Utils._EnterFunction(cstThisSub, cstSubArgs) Then
		If Not _IsStillAlive(True) Then GoTo Finally
		If Not _ValidateSheet(SheetName, &quot;SheetName&quot;, , True) Then GoTo Finally
	End If

Try:
	_Component.getSheets.RemoveByName(SheetName)
	bRemove = True

Finally:
	RemoveSheet = bRemove
	ScriptForge.SF_Utils._ExitFunction(cstThisSub)
	Exit Function
Catch:
	GoTo Finally
End Function    &apos;   SFDocuments.SF_Calc.RemoveSheet

REM -----------------------------------------------------------------------------
Public Function RenameSheet(Optional ByVal SheetName As Variant _
								, Optional ByVal NewName As Variant _
								) As Boolean
&apos;&apos;&apos; Rename a specified sheet
&apos;&apos;&apos;	Args:
&apos;&apos;&apos;		SheetName: The name of the sheet to rename
&apos;&apos;&apos;		NewName: Must not exist
&apos;&apos;&apos;	Returns:
&apos;&apos;&apos;		True if the sheet could be renamed successfully
&apos;&apos;&apos;	Exceptions:
&apos;&apos;&apos;		DUPLICATESHEETERROR		A sheet with the given name exists already
&apos;&apos;&apos;	Examples:
&apos;&apos;&apos;		oDoc.RenameSheet(&quot;SheetX&quot;, &quot;SheetY&quot;)

Dim bRename As Boolean				&apos;	Return value
Const cstThisSub = &quot;SFDocuments.Calc.RenameSheet&quot;
Const cstSubArgs = &quot;SheetName, NewName&quot;

	If ScriptForge.SF_Utils._ErrorHandling() Then On Local Error GoTo Catch
	bRename = False

Check:
	If ScriptForge.SF_Utils._EnterFunction(cstThisSub, cstSubArgs) Then
		If Not _IsStillAlive(True) Then GoTo Finally
		If Not _ValidateSheet(SheetName, &quot;SheetName&quot;, , True) Then GoTo Finally
		If Not _ValidateSheet(NewName, &quot;NewName&quot;, True) Then GoTo Finally
	End If

Try:
	_Component.getSheets.getByName(SheetName).setName(NewName)
	bRename = True

Finally:
	RenameSheet = bRename
	ScriptForge.SF_Utils._ExitFunction(cstThisSub)
	Exit Function
Catch:
	GoTo Finally
End Function    &apos;   SFDocuments.SF_Calc.RenameSheet

REM -----------------------------------------------------------------------------
Public Function SetArray(Optional ByVal TargetCell As Variant _
								, Optional ByRef Value As Variant _
								) As String
&apos;&apos;&apos;	Set the given (array of) values starting from the target cell
&apos;&apos;&apos;	The updated area expands itself from the target cell or from the top-left corner of the given range
&apos;&apos;&apos;	as far as determined by the size of the input Value.
&apos;&apos;&apos;	Vectors are always expanded vertically
&apos;&apos;&apos;	Args:
&apos;&apos;&apos;		TargetCell : the cell or the range as a string that should receive a new value
&apos;&apos;&apos;		Value: a scalar, a vector or an array with the new values
&apos;&apos;&apos;			The new values should be strings, numeric values or dates. Other types empty the corresponding cell
&apos;&apos;&apos;	Returns:
&apos;&apos;&apos;		A string representing the updated range
&apos;&apos;&apos;	Exceptions:
&apos;&apos;&apos;		OFFSETADDRESSERROR		The computed range of cells falls beyond the sheet boundaries
&apos;&apos;&apos;	Examples:
&apos;&apos;&apos;		oDoc.SetArray(&quot;SheetX.A1&quot;, SF_Array.RangeInit(1, 1000))

Dim sSet As String					&apos;	Return value
Dim oSet As Object					&apos;	_Address alias of sSet
Dim vDataArray As Variant			&apos;	DataArray compatible with .DataArray UNO property
Const cstThisSub = &quot;SFDocuments.Calc.SetArray&quot;
Const cstSubArgs = &quot;TargetCell, Value&quot;

	If ScriptForge.SF_Utils._ErrorHandling() Then On Local Error GoTo Catch
	sSet = &quot;&quot;

Check:
	If ScriptForge.SF_Utils._EnterFunction(cstThisSub, cstSubArgs) Then
		If Not _IsStillAlive() Then GoTo Finally
		If Not ScriptForge.SF_Utils._Validate(TargetCell, &quot;TargetCell&quot;, V_STRING) Then GoTo Finally
		If IsArray(Value) Then
			If Not ScriptForge.SF_Utils._ValidateArray(Value, &quot;Value&quot;) Then GoTo Finally
		Else
			If Not ScriptForge.SF_Utils._Validate(Value, &quot;Value&quot;) Then GoTo Finally
		End If
	End If

Try:
	&apos;	Convert argument to data array and derive new range from its size
	vDataArray = _ConvertToDataArray(Value)
	If UBound(vDataArray) &lt; LBound(vDataArray) Then GoTo Finally
	Set oSet = _Offset(TargetCell, 0, 0, plHeight := UBound(vDataArray) + 1, plWidth := UBound(vDataArray(0)) + 1)	&apos;	+1 : vDataArray is zero-based
	With oSet
		.XCellRange.setDataArray(vDataArray)
		sSet = .RangeName
	End With

Finally:
	SetArray = sSet
	ScriptForge.SF_Utils._ExitFunction(cstThisSub)
	Exit Function
Catch:
	GoTo Finally
End Function	&apos;	SFDocuments.SF_Calc.SetArray

REM -----------------------------------------------------------------------------
Public Function SetCellStyle(Optional ByVal TargetRange As Variant _
								, Optional ByVal Style As Variant _
								, Optional ByVal FilterFormula As Variant _
								, Optional ByVal FilterScope As Variant _
								) As String
&apos;&apos;&apos;	Apply the given cell style in the given range
&apos;&apos;&apos;	If the cell style does not exist, an error is raised
&apos;&apos;&apos;	The range is updated and the remainder of the sheet is left untouched
&apos;&apos;&apos;	Either the full range is updated or a selection based on a FilterFormula
&apos;&apos;&apos;	Args:
&apos;&apos;&apos;		TargetRange : the range as a string that should receive a new cell style
&apos;&apos;&apos;		Style: the style name as a string
&apos;&apos;&apos;		FilterFormula: a Calc formula to select among the given Range
&apos;&apos;&apos;			When left empty, all the cells of the range are formatted with the new style
&apos;&apos;&apos;		FilterScope: &quot;CELL&quot; (default value), &quot;ROW&quot; or &quot;COLUMN&quot;
&apos;&apos;&apos;			When FilterFormula is present, FilterScope is mandatory
&apos;&apos;&apos;	Returns:
&apos;&apos;&apos;		A string representing the updated range
&apos;&apos;&apos;	Examples:
&apos;&apos;&apos;		oDoc.SetCellStyle(&quot;A1:F1&quot;, &quot;Heading 2&quot;)
&apos;&apos;&apos;		oDoc.SetCellStype(&quot;A1:J20&quot;, &quot;Wrong&quot;, &quot;=(A1&lt;0)&quot;, &quot;CELL&quot;)

Dim sSet As String					&apos;	Return value
Dim oAddress As _Address				&apos;	Alias of TargetRange
Dim oStyleFamilies As Object		&apos;	com.sun.star.container.XNameAccess
Dim vStyles As Variant				&apos;	Array of existing cell styles
Dim vRanges() As Variant			&apos;	Array of filtered ranges
Dim i As Long

Const cstStyle = &quot;CellStyles&quot;
Const cstThisSub = &quot;SFDocuments.Calc.SetCellStyle&quot;
Const cstSubArgs = &quot;TargetRange, Style, [FilterFormula=&quot;&quot;], [FilterScope=&quot;&quot;CELL&quot;&quot;|&quot;&quot;ROW&quot;&quot;|&quot;&quot;COLUMN&quot;&quot;]&quot;

	If ScriptForge.SF_Utils._ErrorHandling() Then On Local Error GoTo Catch
	sSet = &quot;&quot;

Check:
	If IsMissing(FilterFormula) Or IsEmpty(FilterFormula) Then FilterFormula = &quot;&quot;
	If IsMissing(FilterScope) Or IsEmpty(FilterScope) Then FilterScope = &quot;CELL&quot;
	If ScriptForge.SF_Utils._EnterFunction(cstThisSub, cstSubArgs) Then
		If Not _IsStillAlive() Then GoTo Finally
		If Not ScriptForge.SF_Utils._Validate(TargetRange, &quot;TargetRange&quot;, Array(V_STRING, ScriptForge.V_OBJECT)) Then GoTo Finally
		&apos;	Check that the given style really exists
		Set oStyleFamilies = _Component.StyleFamilies
		If oStyleFamilies.hasByName(cstStyle) Then vStyles = oStyleFamilies.getByName(cstStyle).getElementNames() Else vStyles = Array()
		If Not ScriptForge.SF_Utils._Validate(Style, &quot;Style&quot;, V_STRING, vStyles) Then GoTo Finally
		&apos;	Filter formula
		If Not ScriptForge.SF_Utils._Validate(FilterFormula, &quot;FilterFormula&quot;, V_STRING) Then GoTo Finally
		If Len(FilterFormula) &gt; 0 Then
			If Not ScriptForge.SF_Utils._Validate(FilterScope, &quot;FilterScope&quot;, V_STRING, Array(&quot;CELL&quot;, &quot;ROW&quot;, &quot;COLUMN&quot;)) Then GoTo Finally
		Else
			If Not ScriptForge.SF_Utils._Validate(FilterScope, &quot;FilterScope&quot;, V_STRING) Then GoTo Finally
		End If
	End If

Try:
	If VarType(TargetRange) = V_STRING Then Set oAddress = _ParseAddress(TargetRange) Else Set oAddress = TargetRange
	With oAddress
		If Len(FilterFormula) = 0 Then			&apos;	When the full range should be updated
			.XCellRange.CellStyle = Style
		Else									&apos;	When the range has to be cut in subranges
			vRanges() = _ComputeFilter(oAddress, FilterFormula, UCase(FilterScope))
			For i = 0 To UBound(vRanges)
				vRanges(i).XCellRange.CellStyle = Style
			Next i
		End If
		sSet = .RangeName
	End With

Finally:
	SetCellStyle = sSet
	ScriptForge.SF_Utils._ExitFunction(cstThisSub)
	Exit Function
Catch:
	GoTo Finally
End Function	&apos;	SFDocuments.SF_Calc.SetCellStyle

REM -----------------------------------------------------------------------------
Public Function SetFormula(Optional ByVal TargetRange As Variant _
								, Optional ByRef Formula As Variant _
								) As String
&apos;&apos;&apos;	Set the given (array of) formulae in the given range
&apos;&apos;&apos;	The full range is updated and the remainder of the sheet is left untouched
&apos;&apos;&apos;	If the given formula is a string:
&apos;&apos;&apos;		the unique formula is pasted across the whole range with adjustment of the relative references
&apos;&apos;&apos;	Otherwise
&apos;&apos;&apos;		If the size of Formula &lt; the size of Range, then the other cells are emptied
&apos;&apos;&apos;		If the size of Formula &gt; the size of Range, then Formula is only partially copied
&apos;&apos;&apos;		Vectors are always expanded vertically, except if the range has a height of exactly 1 row
&apos;&apos;&apos;	Args:
&apos;&apos;&apos;		TargetRange : the range as a string that should receive a new Formula
&apos;&apos;&apos;		Formula: a scalar, a vector or an array with the new formula(e) as strings  for each cell of the range.
&apos;&apos;&apos;	Returns:
&apos;&apos;&apos;		A string representing the updated range
&apos;&apos;&apos;	Examples:
&apos;&apos;&apos;		oDoc.SetFormula(&quot;A1&quot;, &quot;=A2&quot;)
&apos;&apos;&apos;		oDoc.SetFormula(&quot;A1:F1&quot;, Array(&quot;=A2&quot;, &quot;=B2&quot;, &quot;=C2+10&quot;))		&apos;	Horizontal vector, partially empty
&apos;&apos;&apos;		oDoc.SetFormula(&quot;A1:D2&quot;, &quot;=E1&quot;)		&apos;	D2 contains the formula &quot;=H2&quot;

Dim sSet As String					&apos;	Return value.XSpreadsheet.Name)
Dim oAddress As Object				&apos;	Alias of TargetRange
Dim vDataArray As Variant			&apos;	DataArray compatible with .DataArray UNO property
Const cstThisSub = &quot;SFDocuments.Calc.SetFormula&quot;
Const cstSubArgs = &quot;TargetRange, Formula&quot;

	If ScriptForge.SF_Utils._ErrorHandling() Then On Local Error GoTo Catch
	sSet = &quot;&quot;

Check:
	If ScriptForge.SF_Utils._EnterFunction(cstThisSub, cstSubArgs) Then
		If Not _IsStillAlive() Then GoTo Finally
		If Not ScriptForge.SF_Utils._Validate(TargetRange, &quot;TargetRange&quot;, Array(V_STRING, ScriptForge.V_OBJECT)) Then GoTo Finally
		If IsArray(Formula) Then
			If Not ScriptForge.SF_Utils._ValidateArray(Formula, &quot;Formula&quot;, 0, V_STRING) Then GoTo Finally
		Else
			If Not ScriptForge.SF_Utils._Validate(Formula, &quot;Formula&quot;, V_STRING) Then GoTo Finally
		End If
	End If

Try:
	If VarType(TargetRange) = V_STRING Then Set oAddress = _ParseAddress(TargetRange) Else Set oAddress = TargetRange
	With oAddress
		If IsArray(Formula) Then
			&apos;	Convert to data array and limit its size to the size of the initial range
			vDataArray = _ConvertToDataArray(Formula, .Height - 1, .Width - 1)
			If UBound(vDataArray) &lt; LBound(vDataArray) Then GoTo Finally
			.XCellRange.setFormulaArray(vDataArray)
		Else
			With .XCellRange
				&apos;	Store formula in top-left cell and paste it along the whole range
				.getCellByPosition(0, 0).setFormula(Formula)
				.fillSeries(com.sun.star.sheet.FillDirection.TO_BOTTOM, com.sun.star.sheet.FillMode.SIMPLE, 0, 0, 0)
				.fillSeries(com.sun.star.sheet.FillDirection.TO_RIGHT, com.sun.star.sheet.FillMode.SIMPLE, 0, 0, 0)
			End With
		End If
		sSet = .RangeName
	End With

Finally:
	SetFormula = sSet
	ScriptForge.SF_Utils._ExitFunction(cstThisSub)
	Exit Function
Catch:
	GoTo Finally
End Function	&apos;	SFDocuments.SF_Calc.SetFormula

REM -----------------------------------------------------------------------------
Private Function SetProperty(Optional ByVal psProperty As String _
								, Optional ByVal pvValue As Variant _
								) As Boolean
&apos;&apos;&apos;	Set the new value of the named property
&apos;&apos;&apos;	Args:
&apos;&apos;&apos;		psProperty: the name of the property
&apos;&apos;&apos;		pvValue: the new value of the given property
&apos;&apos;&apos;	Returns:
&apos;&apos;&apos;		True if successful

Dim bSet As Boolean							&apos;	Return value
Static oSession As Object					&apos;	Alias of SF_Session
Dim cstThisSub As String
Const cstSubArgs = &quot;Value&quot;

	If ScriptForge.SF_Utils._ErrorHandling() Then On Local Error GoTo Catch
	bSet = False

	cstThisSub = &quot;SFDocuments.Calc.set&quot; &amp; psProperty
	If IsMissing(pvValue) Then pvValue = Empty
	&apos;ScriptForge.SF_Utils._EnterFunction(cstThisSub, cstSubArgs)	&apos;	Validation done in Property Lets

	If IsNull(oSession) Then Set oSession = ScriptForge.SF_Services.CreateScriptService(&quot;Session&quot;)
	bSet = True
	Select Case UCase(psProperty)
		Case UCase(&quot;CurrentSelection&quot;)
			CurrentSelection = pvValue
		Case UCase(&quot;CustomProperties&quot;)
			CustomProperties = pvValue
		Case UCase(&quot;Description&quot;)
			Description = pvValue
		Case UCase(&quot;Keywords&quot;)
			Keywords = pvValue
		Case UCase(&quot;Subject&quot;)
			Subject = pvValue
		Case UCase(&quot;Title&quot;)
			Title = pvValue
		Case Else
			bSet = False
	End Select

Finally:
	SetProperty = bSet
	&apos;ScriptForge.SF_Utils._ExitFunction(cstThisSub)
	Exit Function
Catch:
	GoTo Finally
End Function	&apos;	SFDocuments.SF_Calc.SetProperty

REM -----------------------------------------------------------------------------
Public Function SetValue(Optional ByVal TargetRange As Variant _
								, Optional ByRef Value As Variant _
								) As String
&apos;&apos;&apos;	Set the given value in the given range
&apos;&apos;&apos;	The full range is updated and the remainder of the sheet is left untouched
&apos;&apos;&apos;	If the size of Value &lt; the size of Range, then the other cells are emptied
&apos;&apos;&apos;	If the size of Value &gt; the size of Range, then Value is only partially copied
&apos;&apos;&apos;	Vectors are always expanded vertically, except if the range has a height of exactly 1 row
&apos;&apos;&apos;	Args:
&apos;&apos;&apos;		TargetRange : the range as a string that should receive a new value
&apos;&apos;&apos;		Value: a scalar, a vector or an array with the new values for each cell o.XSpreadsheet.Name)f the range.
&apos;&apos;&apos;			The new values should be strings, numeric values or dates. Other types empty the corresponding cell
&apos;&apos;&apos;	Returns:
&apos;&apos;&apos;		A string representing the updated range
&apos;&apos;&apos;	Examples:
&apos;&apos;&apos;		oDoc.SetValue(&quot;A1&quot;, 2)
&apos;&apos;&apos;		oDoc.SetValue(&quot;A1:F1&quot;, Array(1, 2, 3))		&apos;	Horizontal vector, partially empty
&apos;&apos;&apos;		oDoc.SetValue(&quot;A1:D2&quot;, SF_Array.AppendRow(Array(1, 2, 3, 4), Array(5, 6, 7, 8)))

Dim sSet As String					&apos;	Return value
Dim oAddress As Object				&apos;	Alias of TargetRange
Dim vDataArray As Variant			&apos;	DataArray compatible with .DataArray UNO property
Const cstThisSub = &quot;SFDocuments.Calc.SetValue&quot;
Const cstSubArgs = &quot;TargetRange, Value&quot;

	If ScriptForge.SF_Utils._ErrorHandling() Then On Local Error GoTo Catch
	sSet = &quot;&quot;

Check:
	If ScriptForge.SF_Utils._EnterFunction(cstThisSub, cstSubArgs) Then
		If Not _IsStillAlive() Then GoTo Finally
		If Not ScriptForge.SF_Utils._Validate(TargetRange, &quot;TargetRange&quot;, V_STRING) Then GoTo Finally
		If IsArray(Value) Then
			If Not ScriptForge.SF_Utils._ValidateArray(Value, &quot;Value&quot;) Then GoTo Finally
		Else
			If Not ScriptForge.SF_Utils._Validate(Value, &quot;Value&quot;) Then GoTo Finally
		End If
	End If

Try:
	Set oAddress = _ParseAddress(TargetRange)
	With oAddress
		&apos;	Convert to data array and limit its size to the size of the initial range
		vDataArray = _ConvertToDataArray(Value, .Height - 1, .Width - 1)
		If UBound(vDataArray) &lt; LBound(vDataArray) Then GoTo Finally
		.XCellRange.setDataArray(vDataArray)
		sSet = .RangeName
	End With

Finally:
	SetValue = sSet
	ScriptForge.SF_Utils._ExitFunction(cstThisSub)
	Exit Function
Catch:
	GoTo Finally
End Function	&apos;	SFDocuments.SF_Calc.SetValue

REM -----------------------------------------------------------------------------
Public Function ShiftDown(Optional ByVal Range As Variant _
								, Optional ByVal WholeRow As Variant _
								, Optional ByVal Rows As Variant _
								) As String
&apos;&apos;&apos;	Move a specified range and all cells below in the same columns downwards by inserting empty cells
&apos;&apos;&apos;	The inserted cells can span whole rows or be limited to the width of the range
&apos;&apos;&apos;	The height of the inserted area is provided by the Rows argument
&apos;&apos;&apos;	Nothing happens if the range shift crosses one of the edges of the worksheet
&apos;&apos;&apos;	The execution of the method has no effect on the current selection
&apos;&apos;&apos;	Args:
&apos;&apos;&apos;		Range: the range above which cells have to be inserted, as a string
&apos;&apos;&apos;		WholeRow: when True (default = False), insert whole rows
&apos;&apos;&apos;		Rows: the height of the area to insert. Default = the height of the Range argument
&apos;&apos;&apos;	Returns:
&apos;&apos;&apos;		A string representing the new location of the initial range
&apos;&apos;&apos;	Examples:
&apos;&apos;&apos;		newrange = oDoc.ShiftDown(&quot;SheetX.A1:F10&quot;)						&apos;	&quot;$SheetX.$A$11:$F$20&quot;
&apos;&apos;&apos;		newrange = oDoc.ShiftDown(&quot;SheetX.A1:F10&quot;, Rows := 3)			&apos;	&quot;$SheetX.$A$4:$F$13&quot;

Dim sShift As String			&apos;	Return value
Dim oSourceAddress As Object	&apos;	Alias of Range as _Address
Dim lHeight As Long				&apos;	Range height
Dim oShiftAddress As Object		&apos;	com.sun.star.table.CellRangeAddress - Range adjusted to the right width
Dim lShiftMode As Long			&apos;	One of the com.sun.star.sheet.CellInsertMode enum values

Const cstThisSub = &quot;SFDocuments.Calc.ShiftDown&quot;
Const cstSubArgs = &quot;Range, [WholeRow=False], [Rows]&quot;

	If ScriptForge.SF_Utils._ErrorHandling() Then On Local Error GoTo Catch
	sShift = &quot;&quot;

Check:
	If IsMissing(WholeRow) Or IsEmpty(WholeRow) Then WholeRow = False
	If IsMissing(Rows) Or IsEmpty(Rows) Then Rows = 0
	If ScriptForge.SF_Utils._EnterFunction(cstThisSub, cstSubArgs) Then
		If Not _IsStillAlive(True) Then GoTo Finally
		If Not ScriptForge.SF_Utils._Validate(Range, &quot;Range&quot;, V_STRING) Then GoTo Finally
		If Not ScriptForge.SF_Utils._Validate(WholeRow, &quot;WholeRow&quot;, ScriptForge.V_BOOLEAN) Then GoTo Finally
		If Not ScriptForge.SF_Utils._Validate(Rows, &quot;Rows&quot;, ScriptForge.V_NUMERIC) Then GoTo Finally
	End If

Try:
	Set oSourceAddress = _ParseAddress(Range)

	With oSourceAddress

		&apos;	Manage the height of the area to shift
		&apos;	The insertCells() method inserts a number of rows equal to the height of the cell range to shift
		lHeight = .Height
		If Rows &lt;= 0 Then Rows = lHeight
		If _LastCell(.XSpreadsheet)(1) + Rows &gt; MAXROWS Then GoTo Catch
		If Rows &lt;&gt; lHeight Then
			Set oShiftAddress = _Offset(oSourceAddress, 0, 0, Rows, 0).XCellRange.RangeAddress
		Else
			Set oShiftAddress = .XCellRange.RangeAddress
		End If

		&apos;	Determine the shift mode
		With com.sun.star.sheet.CellInsertMode
			If WholeRow Then lShiftMode = .ROWS Else lShiftMode = .DOWN
		End With

		&apos;	Move the cells as requested. This modifies .XCellRange
		.XSpreadsheet.insertCells(oShiftAddress, lShiftMode)

		&apos;	Determine the receiving area
		sShift = .XCellRange.AbsoluteName

	End With

Finally:
	ShiftDown = sShift
	ScriptForge.SF_Utils._ExitFunction(cstThisSub)
	Exit Function
Catch:
	&apos;	When error, return the original range
	If Not IsNull(oSourceAddress) Then sShift = oSourceAddress.RangeName
	GoTo Finally
End Function    &apos;   SFDocuments.SF_Calc.ShiftDown

REM -----------------------------------------------------------------------------
Public Function ShiftLeft(Optional ByVal Range As Variant _
								, Optional ByVal WholeColumn As Variant _
								, Optional ByVal Columns As Variant _
								) As String
&apos;&apos;&apos;	Delete the leftmost columns of a specified range and move all cells at their right leftwards
&apos;&apos;&apos;	The deleted cells can span whole columns or be limited to the height of the range
&apos;&apos;&apos;	The width of the deleted area is provided by the Columns argument
&apos;&apos;&apos;	The execution of the method has no effect on the current selection
&apos;&apos;&apos;	Args:
&apos;&apos;&apos;		Range: the range in which cells have to be erased, as a string
&apos;&apos;&apos;		WholeColumn: when True (default = False), erase whole columns
&apos;&apos;&apos;		Columns: the width of the area to delete.
&apos;&apos;&apos;			Default = the width of the Range argument, it is also its maximum value
&apos;&apos;&apos;	Returns:
&apos;&apos;&apos;		A string representing the location of the remaining part of the initial range,
&apos;&apos;&apos;		or the zero-length string if the whole range has been deleted
&apos;&apos;&apos;	Examples:
&apos;&apos;&apos;		newrange = oDoc.ShiftLeft(&quot;SheetX.G1:L10&quot;)						&apos;	&quot;&quot;&quot;
&apos;&apos;&apos;		newrange = oDoc.ShiftLeft(&quot;SheetX.G1:L10&quot;, Columns := 3)		&apos;	&quot;$SheetX.$G$1:$I$10&quot;

Dim sShift As String			&apos;	Return value
Dim oSourceAddress As Object	&apos;	Alias of Range as _Address
Dim lWidth As Long				&apos;	Range width
Dim oShiftAddress As Object		&apos;	com.sun.star.table.CellRangeAddress - Range adjusted to the right width
Dim lShiftMode As Long			&apos;	One of the com.sun.star.sheet.CellDeleteMode enum values

Const cstThisSub = &quot;SFDocuments.Calc.ShiftLeft&quot;
Const cstSubArgs = &quot;Range, [WholeColumn=False], [Columns]&quot;

	If ScriptForge.SF_Utils._ErrorHandling() Then On Local Error GoTo Catch
	sShift = &quot;&quot;

Check:
	If IsMissing(WholeColumn) Or IsEmpty(WholeColumn) Then WholeColumn = False
	If IsMissing(Columns) Or IsEmpty(Columns) Then Columns = 0
	If ScriptForge.SF_Utils._EnterFunction(cstThisSub, cstSubArgs) Then
		If Not _IsStillAlive(True) Then GoTo Finally
		If Not ScriptForge.SF_Utils._Validate(Range, &quot;Range&quot;, V_STRING) Then GoTo Finally
		If Not ScriptForge.SF_Utils._Validate(WholeColumn, &quot;WholeColumn&quot;, ScriptForge.V_BOOLEAN) Then GoTo Finally
		If Not ScriptForge.SF_Utils._Validate(Columns, &quot;Columns&quot;, ScriptForge.V_NUMERIC) Then GoTo Finally
	End If

Try:
	Set oSourceAddress = _ParseAddress(Range)
	Set _LastParsedAddress = Nothing	&apos;	Range will be erased. Force re-parsing next time

	With oSourceAddress

		&apos;	Manage the width of the area to delete
		&apos;	The removeRange() method erases a number of columns equal to the width of the cell range to delete
		lWidth = .Width
		If Columns &lt;= 0 Then Columns = lWidth
		If Columns &lt; lWidth Then
			Set oShiftAddress = _Offset(oSourceAddress, 0, 0, 0, Columns).XCellRange.RangeAddress
		Else						&apos;	Columns is capped at the range width
			Set oShiftAddress = .XCellRange.RangeAddress
		End If

		&apos;	Determine the Delete mode
		With com.sun.star.sheet.CellDeleteMode
			If WholeColumn Then lShiftMode = .COLUMNS Else lShiftMode = .LEFT
		End With

		&apos;	Move the cells as requested. This modifies .XCellRange
		.XSpreadsheet.removeRange(oShiftAddress, lShiftMode)

		&apos;	Determine the remaining area
		If Columns &lt; lWidth Then sShift = .XCellRange.AbsoluteName

	End With

Finally:
	ShiftLeft = sShift
	ScriptForge.SF_Utils._ExitFunction(cstThisSub)
	Exit Function
Catch:
	&apos;	When error, return the original range
	If Not IsNull(oSourceAddress) Then sShift = oSourceAddress.RangeName
	GoTo Finally
End Function    &apos;   SFDocuments.SF_Calc.ShiftLeft

REM -----------------------------------------------------------------------------
Public Function ShiftRight(Optional ByVal Range As Variant _
								, Optional ByVal WholeColumn As Variant _
								, Optional ByVal Columns As Variant _
								) As String
&apos;&apos;&apos;	Move a specified range and all next cells in the same rows to the right by inserting empty cells
&apos;&apos;&apos;	The inserted cells can span whole columns or be limited to the height of the range
&apos;&apos;&apos;	The width of the inserted area is provided by the Columns argument
&apos;&apos;&apos;	Nothing happens if the range shift crosses one of the edges of the worksheet
&apos;&apos;&apos;	The execution of the method has no effect on the current selection
&apos;&apos;&apos;	Args:
&apos;&apos;&apos;		Range: the range before which cells have to be inserted, as a string
&apos;&apos;&apos;		WholeColumn: when True (default = False), insert whole columns
&apos;&apos;&apos;		Columns: the width of the area to insert. Default = the width of the Range argument
&apos;&apos;&apos;	Returns:
&apos;&apos;&apos;		A string representing the new location of the initial range
&apos;&apos;&apos;	Examples:
&apos;&apos;&apos;		newrange = oDoc.ShiftRight(&quot;SheetX.A1:F10&quot;)						&apos;	&quot;$SheetX.$G$1:$L$10&quot;
&apos;&apos;&apos;		newrange = oDoc.ShiftRight(&quot;SheetX.A1:F10&quot;, Columns := 3)		&apos;	&quot;$SheetX.$D$1:$I$10&quot;

Dim sShift As String			&apos;	Return value
Dim oSourceAddress As Object	&apos;	Alias of Range as _Address
Dim lWidth As Long				&apos;	Range width
Dim oShiftAddress As Object		&apos;	com.sun.star.table.CellRangeAddress - Range adjusted to the right width
Dim lShiftMode As Long			&apos;	One of the com.sun.star.sheet.CellInsertMode enum values

Const cstThisSub = &quot;SFDocuments.Calc.ShiftRight&quot;
Const cstSubArgs = &quot;Range, [WholeColumn=False], [Columns]&quot;

	If ScriptForge.SF_Utils._ErrorHandling() Then On Local Error GoTo Catch
	sShift = &quot;&quot;

Check:
	If IsMissing(WholeColumn) Or IsEmpty(WholeColumn) Then WholeColumn = False
	If IsMissing(Columns) Or IsEmpty(Columns) Then Columns = 0
	If ScriptForge.SF_Utils._EnterFunction(cstThisSub, cstSubArgs) Then
		If Not _IsStillAlive(True) Then GoTo Finally
		If Not ScriptForge.SF_Utils._Validate(Range, &quot;Range&quot;, V_STRING) Then GoTo Finally
		If Not ScriptForge.SF_Utils._Validate(WholeColumn, &quot;WholeColumn&quot;, ScriptForge.V_BOOLEAN) Then GoTo Finally
		If Not ScriptForge.SF_Utils._Validate(Columns, &quot;Columns&quot;, ScriptForge.V_NUMERIC) Then GoTo Finally
	End If

Try:
	Set oSourceAddress = _ParseAddress(Range)

	With oSourceAddress

		&apos;	Manage the width of the area to Shift
		&apos;	The insertCells() method inserts a number of columns equal to the width of the cell range to Shift
		lWidth = .Width
		If Columns &lt;= 0 Then Columns = lWidth
		If _LastCell(.XSpreadsheet)(0) + Columns &gt; MAXCOLS Then GoTo Catch
		If Columns &lt;&gt; lWidth Then
			Set oShiftAddress = _Offset(oSourceAddress, 0, 0, 0, Columns).XCellRange.RangeAddress
		Else
			Set oShiftAddress = .XCellRange.RangeAddress
		End If

		&apos;	Determine the Shift mode
		With com.sun.star.sheet.CellInsertMode
			If WholeColumn Then lShiftMode = .COLUMNS Else lShiftMode = .RIGHT
		End With

		&apos;	Move the cells as requested. This modifies .XCellRange
		.XSpreadsheet.insertCells(oShiftAddress, lShiftMode)

		&apos;	Determine the receiving area
		sShift = .XCellRange.AbsoluteName

	End With

Finally:
	ShiftRight = sShift
	ScriptForge.SF_Utils._ExitFunction(cstThisSub)
	Exit Function
Catch:
	&apos;	When error, return the original range
	If Not IsNull(oSourceAddress) Then sShift = oSourceAddress.RangeName
	GoTo Finally
End Function    &apos;   SFDocuments.SF_Calc.ShiftRight

REM -----------------------------------------------------------------------------
Public Function ShiftUp(Optional ByVal Range As Variant _
								, Optional ByVal WholeRow As Variant _
								, Optional ByVal Rows As Variant _
								) As String
&apos;&apos;&apos;	Delete the topmost rows of a specified range and move all cells below upwards
&apos;&apos;&apos;	The deleted cells can span whole rows or be limited to the width of the range
&apos;&apos;&apos;	The height of the deleted area is provided by the Rows argument
&apos;&apos;&apos;	The execution of the method has no effect on the current selection
&apos;&apos;&apos;	Args:
&apos;&apos;&apos;		Range: the range in which cells have to be erased, as a string
&apos;&apos;&apos;		WholeRow: when True (default = False), erase whole rows
&apos;&apos;&apos;		Rows: the height of the area to delete.
&apos;&apos;&apos;			Default = the height of the Range argument, it is also its maximum value
&apos;&apos;&apos;	Returns:
&apos;&apos;&apos;		A string representing the location of the remaining part of the initial range,
&apos;&apos;&apos;		or the zero-length string if the whole range has been deleted
&apos;&apos;&apos;	Examples:
&apos;&apos;&apos;		newrange = oDoc.ShiftUp(&quot;SheetX.G1:L10&quot;)				&apos;	&quot;&quot;
&apos;&apos;&apos;		newrange = oDoc.ShiftUp(&quot;SheetX.G1:L10&quot;, Rows := 3)		&apos;	&quot;$SheetX.$G$1:$I$10&quot;

Dim sShift As String			&apos;	Return value
Dim oSourceAddress As Object	&apos;	Alias of Range as _Address
Dim lHeight As Long				&apos;	Range height
Dim oShiftAddress As Object		&apos;	com.sun.star.table.CellRangeAddress - Range adjusted to the right height
Dim lShiftMode As Long			&apos;	One of the com.sun.star.sheet.CellDeleteMode enum values

Const cstThisSub = &quot;SFDocuments.Calc.ShiftUp&quot;
Const cstSubArgs = &quot;Range, [WholeRow=False], [Rows]&quot;

	If ScriptForge.SF_Utils._ErrorHandling() Then On Local Error GoTo Catch
	sShift = &quot;&quot;

Check:
	If IsMissing(WholeRow) Or IsEmpty(WholeRow) Then WholeRow = False
	If IsMissing(Rows) Or IsEmpty(Rows) Then Rows = 0
	If ScriptForge.SF_Utils._EnterFunction(cstThisSub, cstSubArgs) Then
		If Not _IsStillAlive(True) Then GoTo Finally
		If Not ScriptForge.SF_Utils._Validate(Range, &quot;Range&quot;, V_STRING) Then GoTo Finally
		If Not ScriptForge.SF_Utils._Validate(WholeRow, &quot;WholeRow&quot;, ScriptForge.V_BOOLEAN) Then GoTo Finally
		If Not ScriptForge.SF_Utils._Validate(Rows, &quot;Rows&quot;, ScriptForge.V_NUMERIC) Then GoTo Finally
	End If

Try:
	Set oSourceAddress = _ParseAddress(Range)
	Set _LastParsedAddress = Nothing	&apos;	Range will be erased. Force re-parsing next time

	With oSourceAddress

		&apos;	Manage the height of the area to delete
		&apos;	The removeRange() method erases a number of rows equal to the height of the cell range to delete
		lHeight = .Height
		If Rows &lt;= 0 Then Rows = lHeight
		If Rows &lt; lHeight Then
			Set oShiftAddress = _Offset(oSourceAddress, 0, 0, Rows, 0).XCellRange.RangeAddress
		Else						&apos;	Rows is capped at the range height
			Set oShiftAddress = .XCellRange.RangeAddress
		End If

		&apos;	Determine the Delete mode
		With com.sun.star.sheet.CellDeleteMode
			If WholeRow Then lShiftMode = .ROWS Else lShiftMode = .UP
		End With

		&apos;	Move the cells as requested. This modifies .XCellRange
		.XSpreadsheet.removeRange(oShiftAddress, lShiftMode)

		&apos;	Determine the remaining area
		If Rows &lt; lHeight Then sShift = .XCellRange.AbsoluteName

	End With

Finally:
	ShiftUp = sShift
	ScriptForge.SF_Utils._ExitFunction(cstThisSub)
	Exit Function
Catch:
	&apos;	When error, return the original range
	If Not IsNull(oSourceAddress) Then sShift = oSourceAddress.RangeName
	GoTo Finally
End Function    &apos;   SFDocuments.SF_Calc.ShiftUp

REM -----------------------------------------------------------------------------
Public Function SortRange(Optional ByVal Range As Variant _
								, Optional ByVal SortKeys As Variant _
								, Optional ByVal SortOrder As Variant _
								, Optional ByVal DestinationCell As Variant _
								, Optional ByVal ContainsHeader As Variant _
								, Optional ByVal CaseSensitive As Variant _
								, Optional ByVal SortColumns As Variant _
								) As Variant
&apos;&apos;&apos;	Sort the given range on maximum 3 columns/rows. The sorting order may vary by column/row
&apos;&apos;&apos;	Args:
&apos;&apos;&apos;		Range: the range to sort as a string
&apos;&apos;&apos;		SortKeys: a scalar (if 1 column/row) or an array of column/row numbers starting from 1
&apos;&apos;&apos;		SortOrder: a scalar or an array of strings: &quot;ASC&quot; or &quot;DESC&quot;
&apos;&apos;&apos;			Each item is paired with the corresponding item in SortKeys
&apos;&apos;&apos;			If the SortOrder array is shorter than SortKeys, the remaining keys are sorted
&apos;&apos;&apos;				in ascending order
&apos;&apos;&apos;		DestinationCell: the destination of the sorted range of cells, as a string
&apos;&apos;&apos;			If given as range, the destination will be reduced to its top-left cell
&apos;&apos;&apos;			By default, Range is overwritten with its sorted content
&apos;&apos;&apos;		ContainsHeader: when True, the first row/column is not sorted. Default = False
&apos;&apos;&apos;		CaseSensitive: only for string comparisons, default = False
&apos;&apos;&apos;		SortColumns: when True, the columns are sorted from left to right
&apos;&apos;&apos;			Default = False: rows are sorted from top to bottom.
&apos;&apos;&apos;	Returns:
&apos;&apos;&apos;		The modified range of cells as a string
&apos;&apos;&apos;	Example:
&apos;&apos;&apos;		oDoc.SortRange(&quot;A2:J200&quot;, Array(1, 3), , Array(&quot;ASC&quot;, &quot;DESC&quot;), CaseSensitive := True)
&apos;&apos;&apos;			&apos;	Sort on columns A (ascending) and C (descending)

Dim sSort As String					&apos;	Return value
Dim oRangeAddress As _Address		&apos;	Parsed range
Dim oRange As Object				&apos;	com.sun.star.table.XCellRange
Dim oDestRange As Object			&apos;	Destination as a range
Dim oDestAddress As Object			&apos;	com.sun.star.table.CellRangeAddress
Dim oDestCell As Object				&apos;	com.sun.star.table.CellAddress
Dim vSortDescriptor As Variant		&apos;	Array of com.sun.star.beans.PropertyValue
Dim vSortFields As Variant			&apos;	Array of com.sun.star.table.TableSortField
Dim sOrder As String				&apos;	Item in SortOrder
Dim i As Long
Const cstThisSub = &quot;SFDocuments.Calc.SortRange&quot;
Const cstSubArgs = &quot;Range, SortKeys, [TargetRange=&quot;&quot;&quot;&quot;], [SortOrder=&quot;&quot;ASC&quot;&quot;], [DestinationCell=&quot;&quot;&quot;&quot;], [ContainsHeader=False], [CaseSensitive=False], [SortColumns=False]&quot;

	If ScriptForge.SF_Utils._ErrorHandling() Then On Local Error GoTo Catch
	sSort = &quot;&quot;

Check:
	If IsMissing(SortKeys) Or IsEmpty(SortKeys) Then
		SortKeys = Array(1)
	ElseIf Not IsArray(SortKeys) Then
		SortKeys = Array(SortKeys)
	End If
	If IsMissing(DestinationCell) Or IsEmpty(DestinationCell) Then DestinationCell = &quot;&quot;
	If IsMissing(SortOrder) Or IsEmpty(SortOrder) Then
		SortOrder = Array(&quot;ASC&quot;)
	ElseIf Not IsArray(SortOrder) Then
		SortOrder = Array(SortOrder)
	End If
	If IsMissing(ContainsHeader) Or IsEmpty(ContainsHeader) Then ContainsHeader = False
	If IsMissing(CaseSensitive) Or IsEmpty(CaseSensitive) Then CaseSensitive = False
	If IsMissing(SortColumns) Or IsEmpty(SortColumns) Then SortColumns = False
	If ScriptForge.SF_Utils._EnterFunction(cstThisSub, cstSubArgs) Then
		If Not _IsStillAlive() Then GoTo Finally
		If Not ScriptForge.SF_Utils._Validate(Range, &quot;Range&quot;, V_STRING) Then GoTo Finally
		If Not ScriptForge.SF_Utils._ValidateArray(SortKeys, &quot;SortKeys&quot;, 1, V_NUMERIC, True) Then GoTo Finally
		If Not ScriptForge.SF_Utils._Validate(DestinationCell, &quot;DestinationCell&quot;, V_STRING) Then GoTo Finally
		If Not ScriptForge.SF_Utils._ValidateArray(SortOrder, &quot;SortOrder&quot;, 1, V_STRING, True) Then GoTo Finally
		If Not ScriptForge.SF_Utils._Validate(ContainsHeader, &quot;ContainsHeader&quot;, ScriptForge.V_BOOLEAN) Then GoTo Finally
		If Not ScriptForge.SF_Utils._Validate(CaseSensitive, &quot;CaseSensitive&quot;, ScriptForge.V_BOOLEAN) Then GoTo Finally
		If Not ScriptForge.SF_Utils._Validate(SortColumns, &quot;SortColumns&quot;, ScriptForge.V_BOOLEAN) Then GoTo Finally
	End If
	Set oRangeAddress = _ParseAddress(Range)
	If Len(DestinationCell) &gt; 0 Then Set oDestRange = _ParseAddress(DestinationCell)

Try:
	&apos;	Initialize the sort descriptor
	Set oRange = oRangeAddress.XCellRange
	vSortDescriptor = oRange.createSortDescriptor
	vSortDescriptor = ScriptForge.SF_Utils._SetPropertyValue(vSortDescriptor, &quot;IsSortColumns&quot;, SortColumns)
	vSortDescriptor = ScriptForge.SF_Utils._SetPropertyValue(vSortDescriptor, &quot;ContainsHeader&quot;, ContainsHeader)
	vSortDescriptor = ScriptForge.SF_Utils._SetPropertyValue(vSortDescriptor, &quot;BindFormatsToContent&quot;, True)
	If Len(DestinationCell) = 0 Then
		vSortDescriptor = ScriptForge.SF_Utils._SetPropertyValue(vSortDescriptor, &quot;CopyOutputData&quot;, False)
	Else
		Set oDestAddress = oDestRange.XCellRange.RangeAddress
		Set oDestCell = New com.sun.star.table.CellAddress
		With oDestAddress
			oDestCell.Sheet = .Sheet
			oDestCell.Column = .StartColumn
			oDestCell.Row = .StartRow
		End With
		vSortDescriptor = ScriptForge.SF_Utils._SetPropertyValue(vSortDescriptor, &quot;CopyOutputData&quot;, True)
		vSortDescriptor = ScriptForge.SF_Utils._SetPropertyValue(vSortDescriptor, &quot;OutputPosition&quot;, oDestCell)
	End If
	vSortDescriptor = ScriptForge.SF_Utils._SetPropertyValue(vSortDescriptor, &quot;IsUserListEnabled&quot;, False)

	&apos;	Define the sorting keys
	vSortFields = Array()
	ReDim vSortFields(0 To UBound(SortKeys))
	For i = 0 To UBound(SortKeys)
		vSortFields(i) = New com.sun.star.table.TableSortField
		If i &gt; UBound(SortOrder) Then sOrder = &quot;&quot; Else sOrder = SortOrder(i)
		If Len(sOrder) = 0 Then sOrder = &quot;ASC&quot;
		With vSortFields(i)
			.Field = SortKeys(i) - 1
			.IsAscending = ( UCase(sOrder) = &quot;ASC&quot; )
			.IsCaseSensitive = CaseSensitive
		End With
	Next i

	&apos;	Associate the keys and the descriptor, and sort
	vSortDescriptor = ScriptForge.SF_Utils._SetPropertyValue(vSortDescriptor, &quot;SortFields&quot;, vSortFields)
	oRange.sort(vSortDescriptor)

	&apos;	Compute the changed area
	If Len(DestinationCell) = 0 Then
		sSort = oRangeAddress.RangeName
	Else
		With oRangeAddress
			sSort = _Offset(oDestRange, 0, 0, .Height, .Width).RangeName
		End With
	End If

Finally:
	SortRange = sSort
	ScriptForge.SF_Utils._ExitFunction(cstThisSub)
	Exit Function
Catch:
	GoTo Finally
End Function	&apos;	SFDocuments.SF_Calc.SortRange

REM ======================================================= SUPERCLASS PROPERTIES

REM -----------------------------------------------------------------------------
Property Get CustomProperties() As Variant
	CustomProperties = [_Super].GetProperty(&quot;CustomProperties&quot;)
End Property	&apos;	SFDocuments.SF_Calc.CustomProperties

REM -----------------------------------------------------------------------------
Property Let CustomProperties(Optional ByVal pvCustomProperties As Variant)
	[_Super].CustomProperties = pvCustomProperties
End Property	&apos;	SFDocuments.SF_Calc.CustomProperties

REM -----------------------------------------------------------------------------
Property Get Description() As Variant
	Description = [_Super].GetProperty(&quot;Description&quot;)
End Property	&apos;	SFDocuments.SF_Calc.Description

REM -----------------------------------------------------------------------------
Property Let Description(Optional ByVal pvDescription As Variant)
	[_Super].Description = pvDescription
End Property	&apos;	SFDocuments.SF_Calc.Description

REM -----------------------------------------------------------------------------
Property Get DocumentProperties() As Variant
	DocumentProperties = [_Super].GetProperty(&quot;DocumentProperties&quot;)
End Property	&apos;	SFDocuments.SF_Calc.DocumentProperties

REM -----------------------------------------------------------------------------
Property Get DocumentType() As String
	DocumentType = [_Super].GetProperty(&quot;DocumentType&quot;)
End Property	&apos;	SFDocuments.SF_Calc.DocumentType

REM -----------------------------------------------------------------------------
Property Get ExportFilters() As Variant
	ExportFilters = [_Super].GetProperty(&quot;ExportFilters&quot;)
End Property	&apos;	SFDocuments.SF_Calc.ExportFilters

REM -----------------------------------------------------------------------------
Property Get ImportFilters() As Variant
	ImportFilters = [_Super].GetProperty(&quot;ImportFilters&quot;)
End Property	&apos;	SFDocuments.SF_Calc.ImportFilters

REM -----------------------------------------------------------------------------
Property Get IsBase() As Boolean
	IsBase = [_Super].GetProperty(&quot;IsBase&quot;)
End Property	&apos;	SFDocuments.SF_Calc.IsBase

REM -----------------------------------------------------------------------------
Property Get IsCalc() As Boolean
	IsCalc = [_Super].GetProperty(&quot;IsCalc&quot;)
End Property	&apos;	SFDocuments.SF_Calc.IsCalc

REM -----------------------------------------------------------------------------
Property Get IsDraw() As Boolean
	IsDraw = [_Super].GetProperty(&quot;IsDraw&quot;)
End Property	&apos;	SFDocuments.SF_Calc.IsDraw

REM -----------------------------------------------------------------------------
Property Get IsImpress() As Boolean
	IsImpress = [_Super].GetProperty(&quot;IsImpress&quot;)
End Property	&apos;	SFDocuments.SF_Calc.IsImpress

REM -----------------------------------------------------------------------------
Property Get IsMath() As Boolean
	IsMath = [_Super].GetProperty(&quot;IsMath&quot;)
End Property	&apos;	SFDocuments.SF_Calc.IsMath

REM -----------------------------------------------------------------------------
Property Get IsWriter() As Boolean
	IsWriter = [_Super].GetProperty(&quot;IsWriter&quot;)
End Property	&apos;	SFDocuments.SF_Calc.IsWriter

REM -----------------------------------------------------------------------------
Property Get Keywords() As Variant
	Keywords = [_Super].GetProperty(&quot;Keywords&quot;)
End Property	&apos;	SFDocuments.SF_Calc.Keywords

REM -----------------------------------------------------------------------------
Property Let Keywords(Optional ByVal pvKeywords As Variant)
	[_Super].Keywords = pvKeywords
End Property	&apos;	SFDocuments.SF_Calc.Keywords

REM -----------------------------------------------------------------------------
Property Get Readonly() As Variant
	Readonly = [_Super].GetProperty(&quot;Readonly&quot;)
End Property	&apos;	SFDocuments.SF_Calc.Readonly

REM -----------------------------------------------------------------------------
Property Get Subject() As Variant
	Subject = [_Super].GetProperty(&quot;Subject&quot;)
End Property	&apos;	SFDocuments.SF_Calc.Subject

REM -----------------------------------------------------------------------------
Property Let Subject(Optional ByVal pvSubject As Variant)
	[_Super].Subject = pvSubject
End Property	&apos;	SFDocuments.SF_Calc.Subject

REM -----------------------------------------------------------------------------
Property Get Title() As Variant
	Title = [_Super].GetProperty(&quot;Title&quot;)
End Property	&apos;	SFDocuments.SF_Calc.Title

REM -----------------------------------------------------------------------------
Property Let Title(Optional ByVal pvTitle As Variant)
	[_Super].Title = pvTitle
End Property	&apos;	SFDocuments.SF_Calc.Title

REM -----------------------------------------------------------------------------
Property Get XComponent() As Variant
	XComponent = [_Super].GetProperty(&quot;XComponent&quot;)
End Property	&apos;	SFDocuments.SF_Calc.XComponent

REM ========================================================== SUPERCLASS METHODS

REM -----------------------------------------------------------------------------
&apos;Public Function Activate() As Boolean
&apos;	Activate = [_Super].Activate()
&apos;End Function    &apos;   SFDocuments.SF_Calc.Activate

REM -----------------------------------------------------------------------------
Public Function CloseDocument(Optional ByVal SaveAsk As Variant) As Boolean
	CloseDocument = [_Super].CloseDocument(SaveAsk)
End Function   &apos;   SFDocuments.SF_Calc.CloseDocument

REM -----------------------------------------------------------------------------
Public Function CreateMenu(Optional ByVal MenuHeader As Variant _
								, Optional ByVal Before As Variant _
								, Optional ByVal SubmenuChar As Variant _
								) As Object
	Set CreateMenu = [_Super].CreateMenu(MenuHeader, Before, SubmenuChar)
End Function	&apos;	SFDocuments.SF_Calc.CreateMenu

REM -----------------------------------------------------------------------------
Public Function ExportAsPDF(Optional ByVal FileName As Variant _
							, Optional ByVal Overwrite As Variant _
							, Optional ByVal Pages As Variant _
							, Optional ByVal Password As Variant _
							, Optional ByVal Watermark As Variant _
							) As Boolean
	ExportAsPDF = [_Super].ExportAsPDF(FileName, Overwrite, Pages, Password, Watermark)
End Function   &apos;   SFDocuments.SF_Calc.ExportAsPDF

REM -----------------------------------------------------------------------------
Public Function RemoveMenu(Optional ByVal MenuHeader As Variant) As Boolean
	RemoveMenu = [_Super].RemoveMenu(MenuHeader)
End Function	&apos;	SFDocuments.SF_Calc.RemoveMenu

REM -----------------------------------------------------------------------------
Public Sub RunCommand(Optional ByVal Command As Variant _
									, ParamArray Args As Variant _
									)
	[_Super].RunCommand(Command, Args)
End Sub		  &apos;   SFDocuments.SF_Calc.RunCommand

REM -----------------------------------------------------------------------------
Public Function Save() As Boolean
	Save = [_Super].Save()
End Function   &apos;   SFDocuments.SF_Calc.Save

REM -----------------------------------------------------------------------------
Public Function SaveAs(Optional ByVal FileName As Variant _
							, Optional ByVal Overwrite As Variant _
							, Optional ByVal Password As Variant _
							, Optional ByVal FilterName As Variant _
							, Optional ByVal FilterOptions As Variant _
							) As Boolean
	SaveAs = [_Super].SaveAs(FileName, Overwrite, Password, FilterName, FilterOptions)
End Function   &apos;   SFDocuments.SF_Calc.SaveAs

REM -----------------------------------------------------------------------------
Public Function SaveCopyAs(Optional ByVal FileName As Variant _
							, Optional ByVal Overwrite As Variant _
							, Optional ByVal Password As Variant _
							, Optional ByVal FilterName As Variant _
							, Optional ByVal FilterOptions As Variant _
							) As Boolean
	SaveCopyAs = [_Super].SaveCopyAs(FileName, Overwrite, Password, FilterName, FilterOptions)
End Function   &apos;   SFDocuments.SF_Calc.SaveCopyAs

REM -----------------------------------------------------------------------------
Public Function SetPrinter(Optional ByVal Printer As Variant _
							, Optional ByVal Orientation As Variant _
							, Optional ByVal PaperFormat As Variant _
							) As Boolean
	SetPrinter = [_Super].SetPrinter(Printer, Orientation, PaperFormat)
End Function	&apos;   SFDocuments.SF_Calc.SetPrinter

REM =========================================================== PRIVATE FUNCTIONS

REM -----------------------------------------------------------------------------
Private Sub _ClearRange(ByVal psTarget As String _
							, Optional ByVal Range As Variant _
							, Optional FilterFormula As Variant _
							, Optional FilterScope As Variant _
							)
&apos;&apos;&apos;	Clear the given range with the given options
&apos;&apos;&apos;	The range may be filtered by a formula for a selective clearance
&apos;&apos;&apos;	Arguments checking is done in this Sub, not in the calling one
&apos;&apos;&apos;	Args:
&apos;&apos;&apos;		psTarget: &quot;All&quot;, &quot;Formats&quot; or &quot;Values&quot;
&apos;&apos;&apos;		Range: the range to clear as a string
&apos;&apos;&apos;		FilterFormula: a selection of cells based on a Calc formula
&apos;&apos;&apos;			When left empty, all the cells of the range are cleared
&apos;&apos;&apos;		psFilterScope: &quot;CELL&quot;, &quot;ROW&quot; or &quot;COLUMN&quot;

Dim lClear As Long				&apos;	A combination of com.sun.star.sheet.CellFlags
Dim oRange As Object			&apos;	Alias of Range
Dim vRanges() As Variant		&apos;	Array of subranges resulting from the application of the filter
Dim i As Long

Dim cstThisSub As String		:	cstThisSub = &quot;SFDocuments.Calc.Clear&quot; &amp; psTarget
Const cstSubArgs = &quot;Range, [FilterFormula=&quot;&quot;], [FilterScope=&quot;&quot;CELL&quot;&quot;|&quot;&quot;ROW&quot;&quot;|&quot;&quot;COLUMN&quot;&quot;]&quot;

	If ScriptForge.SF_Utils._ErrorHandling() Then On Local Error GoTo Catch

Check:
	If IsMissing(FilterFormula) Or IsEmpty(FilterFormula) Then FilterFormula = &quot;&quot;
	If IsMissing(FilterScope) Or IsEmpty(FilterScope) Then FilterScope = &quot;CELL&quot;
	If ScriptForge.SF_Utils._EnterFunction(cstThisSub, cstSubArgs) Then
		If Not _IsStillAlive() Then GoTo Finally
		If Not ScriptForge.SF_Utils._Validate(Range, &quot;Range&quot;, Array(V_STRING, ScriptForge.V_OBJECT)) Then GoTo Finally
		If Not ScriptForge.SF_Utils._Validate(FilterFormula, &quot;FilterFormula&quot;, V_STRING) Then GoTo Finally
		If Len(FilterFormula) &gt; 0 Then
			If Not ScriptForge.SF_Utils._Validate(FilterScope, &quot;FilterScope&quot;, V_STRING, Array(&quot;CELL&quot;, &quot;ROW&quot;, &quot;COLUMN&quot;)) Then GoTo Finally
		Else
			If Not ScriptForge.SF_Utils._Validate(FilterScope, &quot;FilterScope&quot;, V_STRING) Then GoTo Finally
		End If
	End If

Try:
	With com.sun.star.sheet.CellFlags
		Select Case psTarget
			Case &quot;All&quot;
				lClear = .VALUE + .DATETIME + .STRING + .ANNOTATION + .FORMULA _
						+ .HARDATTR + .STYLES + .OBJECTS + .EDITATTR + .FORMATTED
			Case &quot;Formats&quot;
				lClear = .HARDATTR + .STYLES + .EDITATTR + .FORMATTED
			Case &quot;Values&quot;
				lClear = .VALUE + .DATETIME + .STRING + .FORMULA
		End Select
	End With

	If VarType(Range) = V_STRING Then Set oRange = _ParseAddress(Range) Else Set oRange = Range

	&apos;	Without filter, the whole range is cleared
	&apos;	Otherwise the filter cuts the range in subranges and clears them one by one
	If Len(FilterFormula) = 0 Then
		oRange.XCellRange.clearContents(lClear)
	Else
		vRanges() = _ComputeFilter(oRange, FilterFormula, UCase(FilterScope))
		For i = 0 To UBound(vRanges)
			vRanges(i).XCellRange.clearContents(lClear)
		Next i
	End If

Finally:
	ScriptForge.SF_Utils._ExitFunction(cstThisSub)
	Exit Sub
Catch:
	GoTo Finally
End Sub	&apos;	SFDocuments.SF_Calc._ClearRange

REM -----------------------------------------------------------------------------
Private Function _ComputeFilter(ByRef poRange As Object _
								, ByVal psFilterFormula As String _
								, ByVal psFilterScope As String _
								) As Variant
&apos;&apos;&apos;	Compute in the given range the cells, rows or columns for which
&apos;&apos;&apos;	the given formula returns TRUE
&apos;&apos;&apos;	Args:
&apos;&apos;&apos;		poRange: the range on which to compute the filter as an _Address type
&apos;&apos;&apos;		psFilterFormula: the formula to be applied on each row, column or cell
&apos;&apos;&apos;		psFilterSCope: &quot;ROW&quot;, &quot;COLUMN&quot; or &quot;CELL&quot;
&apos;&apos;&apos;	Returns:
&apos;&apos;&apos;		An array of ranges as objects of type _Address

Dim vRanges As Variant			&apos;	Return value
Dim oRange As Object			&apos;	A single vRanges() item
Dim lLast As Long				&apos;	Last used row or column number in the sheet containing Range
Dim oFormulaRange As _Address	&apos;	Range where the FilterFormula must be stored
Dim sFormulaDirection As String	&apos;	Either V(ertical), H(orizontal) or B(oth)
Dim vDataArray As Variant		&apos;	DataArray compatible with .DataArray UNO property
Dim vFilter As Variant			&apos;	Array of Boolean values indicating which rows should be erased
Dim bFilter As Boolean			&apos;	A single item in vFilter
Dim iDims As Integer			&apos;	Number of dimensions of vFilter()
Dim lLower As Long				&apos;	Lower level of contiguous True filter values
Dim lUpper As Long				&apos;	Upper level of contiguous True filter values
Dim i As Long, j As Long

Check:
	&apos;	Error handling is determined by the calling method
	vRanges = Array()

Try:
	With poRange

		&apos;	Compute the range where to apply the formula
		&apos;	Determine the direction of the range containing the formula vertical, horizontal or both
		Select Case psFilterScope
			Case &quot;ROW&quot;
				lLast = LastColumn(.SheetName)
				&apos;	Put formulas as a single column in the unused area at the right of the range to filter
				Set oFormulaRange = _Offset(poRange, 0, lLast - .XCellRange.RangeAddress.StartColumn + 1, 0, 1)
				sFormulaDirection = &quot;V&quot;
			Case &quot;COLUMN&quot;
				lLast = LastRow(.SheetName)
				&apos;	Put formulas as a single row in the unused area at the bottom of the range to filter
				Set oFormulaRange = _Offset(poRange, lLast - .XCellRange.RangeAddress.StartRow + 1, 0, 1, 0)
				sFormulaDirection = &quot;H&quot;
			Case &quot;CELL&quot;
				lLast = LastRow(.SheetName)
				&apos;	Put formulas as a matrix in the unused area at the bottom of the range to filter
				Set oFormulaRange = _Offset(poRange, lLast - .XCellRange.RangeAddress.StartRow + 1, 0, 0, 0)
				sFormulaDirection = &quot;B&quot;
				If oFormulaRange.Width = 1 Then
					sFormulaDirection = &quot;V&quot;
				ElseIf oFormulaRange.Height = 1 Then
					sFormulaDirection = &quot;H&quot;
				End If
		End Select

		&apos;	Apply the formula and get the result as an array of Boolean values. Clean up
		SetFormula(oFormulaRange, psFilterFormula)
		vDataArray = oFormulaRange.XCellRange.getDataArray()
		vFilter = _ConvertFromDataArray(vDataArray)
		iDims = ScriptForge.SF_Array.CountDims(vFilter)
		ClearAll(oFormulaRange)

		&apos;	Convert the filter values (0 = False, 1 = True) to a set of ranges
		Select Case iDims
			Case -1			&apos;	Scalar
				If vFilter = 1 Then vRanges = ScriptForge.SF_Array.Append(vRanges, poRange)
			Case 0			&apos;	Empty array
				&apos;	Nothing to do
			Case 1, 2		&apos;	Vector or Array
				&apos;	Strategy: group contiguous applicable rows/columns to optimize heavy operations like CompactUp, CompactLeft
				&apos;	Stack the contiguous ranges of True values in vRanges()

				&apos;	To manage vector and array with same code, setup a single fictitious loop when vector, otherwise scan array by row
				For i = 0 To Iif(iDims = 1, 0, UBound(vFilter, 1))
					lLower = -1		:	lUpper = -1

					For j = 0 To UBound(vFilter, iDims)
						If iDims = 1 Then bFilter = CBool(vFilter(j)) Else bFilter = CBool(vFilter(i, j))
						If j = UBound(vFilter, iDims) And bFilter Then	&apos;	Don&apos;t forget the last item
							If lLower &lt; 0 Then lLower = j
							lUpper = j
						ElseIf Not bFilter Then
							If lLower &gt;= 0 Then lUpper = j - 1
						ElseIf bFilter Then
							If lLower &lt; 0 Then lLower = j
						End If
						&apos;	Determine the next applicable range when one found and limit reached
						If lUpper &gt; -1 Then
							If sFormulaDirection = &quot;V&quot; Then			&apos;	ROW
								Set oRange = _Offset(poRange, lLower, 0, lUpper - lLower + 1, 0)
							ElseIf sFormulaDirection = &quot;H&quot; Then		&apos;	COLUMN
								Set oRange = _Offset(poRange, 0, lLower, 0, lUpper - lLower + 1)
							Else									&apos;	CELL
								Set oRange = _Offset(poRange, i, lLower, 1, lUpper - lLower + 1)
							End If
							If Not IsNull(oRange) Then vRanges = ScriptForge.SF_Array.Append(vRanges, oRange)
							lLower = -1		:	lUpper = -1
						End If
					Next j

				Next i
			Case Else
				&apos;	Should not happen
		End Select

	End With

Finally:
	_ComputeFilter = vRanges()
	Exit Function
End Function    &apos;   SFDocuments.SF_Calc._ComputeFilter

REM -----------------------------------------------------------------------------
Public Function _ConvertFromDataArray(ByRef pvDataArray As Variant) As Variant
&apos;&apos;&apos;	Convert a data array to a scalar, a vector or a 2D array
&apos;&apos;&apos;	Args:
&apos;&apos;&apos;		pvDataArray: an array as returned by the XCellRange.getDataArray or .getFormulaArray methods
&apos;&apos;&apos;	Returns:
&apos;&apos;&apos;		A scalar, a zero-based 1D array or a zero-based 2D array of strings and/or doubles
&apos;&apos;&apos;		To convert doubles to dates, use the CDate builtin function

Dim vArray As Variant				&apos;	Return value
Dim lMax1 As Long					&apos;	UBound of pvDataArray
Dim lMax2 As Long					&apos;	UBound of pvDataArray items
Dim i As Long
Dim j As Long

	vArray = Empty

Try:
	&apos;	Convert the data array to scalar, vector or array
	lMax1 = UBound(pvDataArray)
	If lMax1 &gt;= 0 Then
		lMax2 = UBound(pvDataArray(0))
		If lMax2 &gt;= 0 Then
			If lMax1 + lMax2 &gt; 0 Then vArray = Array()
			Select Case True
				Case lMax1 = 0 And lMax2 = 0			&apos;	Scalar
					vArray = pvDataArray(0)(0)
				Case lMax1 &gt; 0 And lMax2 = 0			&apos;	Vertical vector
					ReDim vArray(0 To lMax1)
					For i = 0 To lMax1
						vArray(i) = pvDataArray(i)(0)
					Next i
				Case lMax1 = 0 And lMax2 &gt; 0			&apos;	Horizontal vector
					ReDim vArray(0 To lMax2)
					For j = 0 To lMax2
						vArray(j) = pvDataArray(0)(j)
					Next j
				Case Else								&apos;	Array
					ReDim vArray(0 To lMax1, 0 To lMax2)
					For i = 0 To lMax1
						For j = 0 To lMax2
							vArray(i, j) = pvDataArray(i)(j)
						Next j
					Next i
			End Select
		End If
	End If

Finally:
	_ConvertFromDataArray = vArray
End Function	&apos;	SFDocuments.SF_Calc._ConvertFromDataArray

REM -----------------------------------------------------------------------------
Private Function _ConvertToCellValue(ByVal pvItem As Variant) As Variant
&apos;&apos;&apos;	Convert the argument to a valid Calc cell content

Dim vCell As Variant		&apos;	Return value

Try:
	Select Case ScriptForge.SF_Utils._VarTypeExt(pvItem)
		Case V_STRING					:		vCell = pvItem
		Case V_DATE						:		vCell = CDbl(pvItem)
		Case ScriptForge.V_NUMERIC		:		vCell = CDbl(pvItem)
		Case ScriptForge.V_BOOLEAN		:		vCell = CDbl(Iif(pvItem, 1, 0))
		Case Else						:		vCell = &quot;&quot;
	End Select

Finally:
	_ConvertToCellValue = vCell
	Exit Function
End Function	&apos;	SFDocuments.SF_Calc._ConvertToCellValue

REM -----------------------------------------------------------------------------
Private Function _ConvertToDataArray(ByRef pvArray As Variant _
								, Optional ByVal plRows As Long _
								, Optional ByVal plColumns As Long _
								) As Variant
&apos;&apos;&apos;	Create a 2-dimensions nested array (compatible with the ranges .DataArray property)
&apos;&apos;&apos;	from a scalar, a 1D array or a 2D array
&apos;&apos;&apos;	Input may be a 1D array of arrays, typically when call issued by a Python script
&apos;&apos;&apos;	Array items are converted to (possibly empty) strings or doubles
&apos;&apos;&apos;	Args:
&apos;&apos;&apos;		pvArray: the input scalar or array. If array, must be 1 or 2D otherwise it is ignored.
&apos;&apos;&apos;		plRows, plColumns: the upper bounds of the data array
&apos;&apos;&apos;			If bigger than input array, fill with zero-length strings
&apos;&apos;&apos;			If smaller than input array, truncate
&apos;&apos;&apos;			If plRows = 0 and the input array is a vector, the data array is aligned horizontally
&apos;&apos;&apos;			They are either both present or both absent
&apos;&apos;&apos;				When absent
&apos;&apos;&apos;					The size of the output is fully determined by the input array
&apos;&apos;&apos;					Vectors are aligned vertically
&apos;&apos;&apos;	Returns:
&apos;&apos;&apos;		A data array compatible with ranges .DataArray property
&apos;&apos;&apos;		The output is always an array of nested arrays

Dim vDataArray() As Variant			&apos;	Return value
Dim vVector() As Variant			&apos;	A temporary 1D array
Dim vItem As Variant				&apos;	A single input item
Dim iDims As Integer				&apos;	Number of dimensions of the input argument
Dim lMin1 As Long					&apos;	Lower bound (1) of input array
Dim lMax1 As Long					&apos;	Upper bound (1)
Dim lMin2 As Long					&apos;	Lower bound (2)
Dim lMax2 As Long					&apos;	Upper bound (2)
Dim lRows As Long					&apos;	Upper bound of vDataArray
Dim lCols As Long					&apos;	Upper bound of vVector
Dim bHorizontal As Boolean			&apos;	Horizontal vector
Dim bDataArray As Boolean			&apos;	Input array is already an array of arrays
Dim i As Long
Dim j As Long

Const cstEmpty = &quot;&quot;		&apos;	Empty cell

	If IsMissing(plRows) Or IsEmpty(plRows) Then plRows = -1
	If IsMissing(plColumns) Or IsEmpty(plColumns) Then plColumns = -1

	vDataArray = Array()

Try:
	&apos;	Check the input argument and know its boundaries
	iDims = ScriptForge.SF_Array.CountDims(pvArray)
	If iDims = 0 Or iDims &gt; 2 Then Exit Function
	lMin1 = 0		:	lMax1 = 0	&apos;	Default values
	lMin2 = 0		:	lMax2 = 0
	Select Case iDims
		Case -1													&apos;	Scalar value
		Case 1
			bHorizontal = ( plRows = 0 And plColumns &gt; 0 )
			bDataArray = IsArray(pvArray(0))
			If Not bDataArray Then
				If Not bHorizontal Then
					lMin1 = LBound(pvArray)	:	lMax1 = UBound(pvArray)
				Else
					lMin2 = LBound(pvArray)	:	lMax2 = UBound(pvArray)
				End If
			Else
				iDims = 2
				lMin1 = LBound(pvArray)	:	lMax1 = UBound(pvArray)
				lMin2 = LBound(pvArray(0))	:	lMax2 = UBound(pvArray(0))
			End If
		Case 2
			lMin1 = LBound(pvArray, 1)	:	lMax1 = UBound(pvArray, 1)
			lMin2 = LBound(pvArray, 2)	:	lMax2 = UBound(pvArray, 2)
	End Select

	&apos;	Set the output dimensions accordingly
	If plRows &gt;= 0 Then		&apos;	Dimensions of output are imposed
		lRows = plRows
		lCols = plColumns
	Else					&apos;	Dimensions of output determined by input argument
		lRows = 0		:	lCols = 0	&apos;	Default values
		Select Case iDims
			Case -1													&apos;	Scalar value
			Case 1													&apos;	Vectors are aligned vertically
				lRows = lMax1 - lMin1
			Case 2
				lRows = lMax1 - lMin1
				lCols = lMax2 - lMin2
		End Select
	End If
	ReDim vDataArray(0 To lRows)

	&apos;	Feed the output array row by row, each row being a vector
	For i = 0 To lRows
		ReDim vVector(0 To lCols)
		For j = 0 To lCols
			If i &gt; lMax1 - lMin1 Then
				vVector(j) = cstEmpty
			ElseIf j &gt; lMax2 - lMin2 Then
				vVector(j) = cstEmpty
			Else
				Select Case iDims
					Case -1		:	vItem = _ConvertToCellValue(pvArray)
					Case 1
						If bHorizontal Then
							vItem = _ConvertToCellValue(pvArray(j + lMin2))
						Else
							vItem = _ConvertToCellValue(pvArray(i + lMin1))
						End If
					Case 2
						If bDataArray Then
							vItem = _ConvertToCellValue(pvArray(i + lMin1)(j + lMin2))
						Else
							vItem = _ConvertToCellValue(pvArray(i + lMin1, j + lMin2))
						End If
				End Select
				vVector(j) = vItem
			End If
			vDataArray(i) = vVector
		Next j
	Next i

Finally:
	_ConvertToDataArray = vDataArray
	Exit Function
End Function	&apos;	SFDocuments.SF_Calc._ConvertToDataArray

REM -----------------------------------------------------------------------------
Private Function _DFunction(ByVal psFunction As String _
								, Optional ByVal Range As Variant _
								) As Double
&apos;&apos;&apos;	Apply the given function on all the numeric values stored in the given range
&apos;&apos;&apos;	Args:
&apos;&apos;&apos;		Range : the range as a string where to apply the function on
&apos;&apos;&apos;	Returns:
&apos;&apos;&apos;		The resulting value as a double

Dim dblGet As Double				&apos;	Return value
Dim oAddress As Object				&apos;	Alias of Range
Dim vFunction As Variant			&apos;	com.sun.star.sheet.GeneralFunction.XXX
Dim cstThisSub As String	:	cstThisSub = &quot;SFDocuments.Calc.&quot; &amp; psFunction
Const cstSubArgs = &quot;Range&quot;

	If ScriptForge.SF_Utils._ErrorHandling() Then On Local Error GoTo Catch
	dblGet = 0

Check:
	If ScriptForge.SF_Utils._EnterFunction(cstThisSub, cstSubArgs) Then
		If Not _IsStillAlive() Then GoTo Finally
		If Not ScriptForge.SF_Utils._Validate(Range, &quot;Range&quot;, V_STRING) Then GoTo Finally
	End If

Try:
	&apos;	Get the data
	Set oAddress = _ParseAddress(Range)
	Select Case psFunction
		Case &quot;DAvg&quot;		:	vFunction = com.sun.star.sheet.GeneralFunction.AVERAGE
		Case &quot;DCount&quot;	:	vFunction = com.sun.star.sheet.GeneralFunction.COUNTNUMS
		Case &quot;DMax&quot;		:	vFunction = com.sun.star.sheet.GeneralFunction.MAX
		Case &quot;DMin&quot;		:	vFunction = com.sun.star.sheet.GeneralFunction.MIN
		Case &quot;DSum&quot;		:	vFunction = com.sun.star.sheet.GeneralFunction.SUM
		Case Else		:	GoTo Finally
	End Select
	dblGet = oAddress.XCellRange.computeFunction(vFunction)

Finally:
	_DFunction = dblGet
	ScriptForge.SF_Utils._ExitFunction(cstThisSub)
	Exit Function
Catch:
	GoTo Finally
End Function	&apos;	SFDocuments.SF_Calc._DFunction

REM -----------------------------------------------------------------------------
Private Function _FileIdent() As String
&apos;&apos;&apos;	Returns a file identification from the information that is currently available
&apos;&apos;&apos;	Useful e.g. for display in error messages

	_FileIdent = [_Super]._FileIdent()

End Function	&apos;	SFDocuments.SF_Calc._FileIdent

REM -----------------------------------------------------------------------------
Function _GetColumnName(ByVal plColumnNumber As Long) As String
&apos;&apos;&apos;	Convert a column number (range 1, 2,..16384) into its letter counterpart (range &apos;A&apos;, &apos;B&apos;,..&apos;XFD&apos;).
&apos;&apos;&apos;	Args:
&apos;&apos;&apos;		ColumnNumber: the column number, must be in the interval 1 ... 16384
&apos;&apos;&apos;	Returns:
&apos;&apos;&apos;		a string representation of the column name, in range &apos;A&apos;..&apos;XFD&apos;
&apos;&apos;&apos;	Adapted from a Python function by sundar nataraj
&apos;&apos;&apos;	http://stackoverflow.com/questions/23861680/convert-spreadsheet-number-to-column-letter

Dim sCol As String			&apos;	Return value
Dim lDiv As Long			&apos;	Intermediate result
Dim lMod As Long			&apos;	Result of modulo 26 operation

Try:
	sCol = &quot;&quot;
	lDiv = plColumnNumber
	Do While lDiv &gt; 0
		lMod = (lDiv - 1) Mod 26
		sCol = Chr(65 + lMod) &amp; sCol
		lDiv = (lDiv - lMod) \ 26
	Loop

Finally:
	_GetColumnName = sCol
End Function	&apos;	SFDocuments.SF_Calc._GetColumnName

REM -----------------------------------------------------------------------------
Private Function _IsStillAlive(Optional ByVal pbForUpdate As Boolean _
									, Optional ByVal pbError As Boolean _
									) As Boolean
&apos;&apos;&apos;	Returns True if the document has not been closed manually or incidentally since the last use
&apos;&apos;&apos;	If dead the actual instance is disposed. The execution is cancelled when pbError = True (default)
&apos;&apos;&apos;	Args:
&apos;&apos;&apos;		pbForUpdate: if True (default = False), check additionally if document is open for editing
&apos;&apos;&apos;		pbError: if True (default), raise a fatal error

Dim bAlive As Boolean			&apos;	Return value

	If IsMissing(pbForUpdate) Then pbForUpdate = False
	If IsMissing(pbError) Then pbError = True

Try:
	bAlive = [_Super]._IsStillAlive(pbForUpdate, pbError)

Finally:
	_IsStillAlive = bAlive
	Exit Function
End Function	&apos;	SFDocuments.SF_Calc._IsStillAlive

REM -----------------------------------------------------------------------------
Private Function _LastCell(ByRef poSheet As Object) As Variant
&apos;&apos;&apos;	Returns in an array the coordinates of the last used cell in the given sheet

Dim oCursor As Object				&apos;	Cursor on the cell
Dim oRange As Object				&apos;	The used range
Dim vCoordinates(0 To 1) As Long	&apos;	Return value: (0) = Column, (1) = Row

Try:
	Set oCursor = poSheet.createCursorByRange(poSheet.getCellRangeByName(&quot;A1&quot;))
	oCursor.gotoEndOfUsedArea(True)
	Set oRange = poSheet.getCellRangeByName(oCursor.AbsoluteName)

	vCoordinates(0) = oRange.RangeAddress.EndColumn + 1
	vCoordinates(1) = oRange.RangeAddress.EndRow + 1

Finally:
	_LastCell = vCoordinates
End Function	&apos;	SFDocuments.SF_Calc._LastCell

REM -----------------------------------------------------------------------------
Public Function _Offset(ByRef pvRange As Variant _
								, ByVal plRows As Long _
								, ByVal plColumns As Long _
								, ByVal plHeight As Long _
								, ByVal plWidth As Long _
								) As Object
&apos;&apos;&apos;	Returns a new range offset by a certain number of rows and columns from a given range
&apos;&apos;&apos;	Args:
&apos;&apos;&apos;		pvRange : the range, as a string or an object, from which the function searches for the new range
&apos;&apos;&apos;		plRows : the number of rows by which the reference was corrected up (negative value) or down.
&apos;&apos;&apos;		plColumns : the number of columns by which the reference was corrected to the left (negative value) or to the right.
&apos;&apos;&apos;		plHeight : the vertical height for an area that starts at the new reference position.
&apos;&apos;&apos;		plWidth : the horizontal width for an area that starts at the new reference position.
&apos;&apos;&apos;		Arguments Rows and Columns must not lead to zero or negative start row or column.
&apos;&apos;&apos;		Arguments Height and Width must not lead to zero or negative count of rows or columns.
&apos;&apos;&apos;	Returns:
&apos;&apos;&apos;		A new range as object of type _Address
&apos;&apos;&apos;	Exceptions:
&apos;&apos;&apos;		OFFSETADDRESSERROR		The computed range of cells falls beyond the sheet boundaries

Dim oOffset As Object				&apos;	Return value
Dim oAddress As Object				&apos;	Alias of Range
Dim oSheet As Object				&apos;	com.sun.star.sheet.XSpreadsheet
Dim oRange As Object				&apos;	com.sun.star.table.XCellRange
Dim oNewRange As Object				&apos;	com.sun.star.table.XCellRange
Dim lLeft As Long					&apos;	New range coordinates
Dim lTop As Long
Dim lRight As Long
Dim lBottom As Long

	Set oOffset = Nothing

Check:
	If plHeight &lt; 0 Or plWidth &lt; 0 Then GoTo CatchAddress

Try:
	If VarType(pvRange) = V_STRING Then Set oAddress = _ParseAddress(pvRange) Else Set oAddress = pvRange
	Set oSheet = oAddress.XSpreadSheet
	Set oRange = oAddress.XCellRange.RangeAddress


	&apos;	Compute and validate new coordinates
	With oRange
		lLeft = .StartColumn + plColumns
		lTop = .StartRow + plRows
		lRight = lLeft + Iif(plWidth = 0, .EndColumn - .StartColumn, plWidth - 1)
		lBottom = lTop + Iif(plHeight = 0, .EndRow - .StartRow, plHeight - 1)
		If lLeft &lt; 0 Or lRight &lt; 0 Or lTop &lt; 0 Or lBottom &lt; 0 _
			Or lLeft &gt;= MAXCOLS Or lRight &gt;= MAXCOLS _
			Or lTop &gt;= MAXROWS Or lBottom &gt;= MAXROWS _
				Then GoTo CatchAddress
		Set oNewRange = oSheet.getCellRangeByPosition(lLeft, lTop, lRight, lBottom)
	End With

	&apos;	Define the new range address
	Set oOffset = New _Address
	With oOffset
		.ObjectType = CALCREFERENCE
		.ServiceName = SERVICEREFERENCE
		.RawAddress = oNewRange.AbsoluteName
		.Component = _Component
		.XSpreadsheet = oNewRange.Spreadsheet
		.SheetName = .XSpreadsheet.Name
		.SheetIndex = .XSpreadsheet.RangeAddress.Sheet
		.RangeName = .RawAddress
		.XCellRange = oNewRange
		.Height = oNewRange.RangeAddress.EndRow - oNewRange.RangeAddress.StartRow + 1
		.Width = oNewRange.RangeAddress.EndColumn - oNewRange.RangeAddress.StartColumn + 1
	End With

Finally:
	Set _Offset = oOffset
	Exit Function
Catch:
	GoTo Finally
CatchAddress:
	ScriptForge.SF_Exception.RaiseFatal(OFFSETADDRESSERROR, &quot;Range&quot;, oAddress.RawAddress _
				, &quot;Rows&quot;, plRows, &quot;Columns&quot;, plColumns, &quot;Height&quot;, plHeight, &quot;Width&quot;, plWidth _
				, &quot;Document&quot;, [_Super]._FileIdent())
	GoTo Finally
End Function	&apos;	SFDocuments.SF_Calc._Offset

REM -----------------------------------------------------------------------------
Private Function _ParseAddress(ByVal psAddress As String) As Object
&apos;&apos;&apos;	Parse and validate a sheet or range reference
&apos;&apos;&apos;	Syntax to parse:
&apos;&apos;&apos;		[Sheet].[Range]
&apos;&apos;&apos;			Sheet 	=&gt; [&apos;][$]sheet[&apos;] or document named range or ~
&apos;&apos;&apos;			Range	=&gt; A1:D10, A1, A:D, 10:10 ($ ignored), or sheet named range or ~
&apos;&apos;&apos;	Returns:
&apos;&apos;&apos;		An object of type _Address
&apos;&apos;&apos;	Exceptions:
&apos;&apos;&apos;		CALCADDRESSERROR		&apos;	Address could not be parsed to a valid address

Dim oAddress As Object				&apos;	Return value
Dim sAddress As String				&apos;	Alias of psAddress
Dim vRangeName As Variant			&apos;	Array Sheet/Range
Dim lStart As Long					&apos;	Position of found regex
Dim sSheet As String				&apos;	Sheet component
Dim sRange As String				&apos;	Range component
Dim oSheets As Object				&apos;	com.sun.star.sheet.XSpreadsheets
Dim oNamedRanges As Object			&apos;	com.sun.star.sheet.XNamedRanges
Dim oRangeAddress As Object			&apos;	Alias for rangeaddress
Dim vLastCell As Variant			&apos;	Result of _LastCell() method
Dim oSelect As Object				&apos;	Current selection

	&apos;	If psAddress has already been parsed, get the result back
	If Not IsNull(_LastParsedAddress) Then
		&apos;	Given argument must contain an explicit reference to a sheet
		If (InStr(psAddress, &quot;~.&quot;) = 0 And InStr(psAddress, &quot;.&quot;) &gt; 0 And psAddress = _LastParsedAddress.RawAddress) _
				Or psAddress = _LastParsedAddress.RangeName Then
			Set _ParseAddress = _LastParsedAddress
			Exit Function
		Else
			Set _LastParsedAddress = Nothing
		End If
	End If

	&apos;	Reinitialize a new _Address object
	Set oAddress = New _Address
	With oAddress
		sSheet = &quot;&quot;				:	sRange = &quot;&quot;
		.SheetName = &quot;&quot;			:	.RangeName = &quot;&quot;

		.ObjectType = CALCREFERENCE
		.ServiceName = SERVICEREFERENCE
		.RawAddress = psAddress
		Set .XSpreadSheet = Nothing	:	Set .XCellRange = Nothing

		&apos;	Remove leading &quot;$&apos; when followed with an apostrophe
		If Left(psAddress, 2) = &quot;$&apos;&quot; Then sAddress = Mid(psAddress, 2) Else sAddress = psAddress
		&apos;	Split in sheet and range components on dot not enclosed in single quotes
		vRangeName = ScriptForge.SF_String.SplitNotQuoted(sAddress, Delimiter := &quot;.&quot;, QuoteChar := &quot;&apos;&quot;)
		sSheet = ScriptForge.SF_String.Unquote(Replace(vRangeName(0), &quot;&apos;&apos;&quot;, &quot;\&apos;&quot;), QuoteChar := &quot;&apos;&quot;)
		&apos;	Keep a leading &quot;$&quot; in the sheet name only if name enclosed in single quotes
		&apos;	Notes:
		&apos;		sheet names may contain &quot;$&quot; (even &quot;$&quot; is a valid sheet name), named ranges must not
		&apos;		sheet names may contain apostrophes (except in 1st and last positions), range names must not
		If Left(vRangeName(0), 2) &lt;&gt; &quot;&apos;$&quot; And Left(sSheet, 1) = &quot;$&quot; And Len(sSheet) &gt; 1 Then sSheet = Mid(sSheet, 2)
		If UBound(vRangeName) &gt; 0 Then sRange = vRangeName(1)

		&apos;	Resolve sheet part: either a document named range, or the active sheet or a real sheet
		Set oSheets = _Component.getSheets()
		Set oNamedRanges = _Component.NamedRanges
		If oSheets.hasByName(sSheet) Then
		ElseIf sSheet = &quot;~&quot; And Len(sRange) &gt; 0 Then
			sSheet = _Component.CurrentController.ActiveSheet.Name
		ElseIf oNamedRanges.hasByName(sSheet) Then
			.XCellRange = oNamedRanges.getByName(sSheet).ReferredCells
			sSheet = oSheets.getByIndex(oNamedRanges.getByName(sSheet).ReferencePosition.Sheet).Name
		Else
			sRange = sSheet
			sSheet = _Component.CurrentController.ActiveSheet.Name
		End If
		.SheetName = sSheet
		.XSpreadSheet = oSheets.getByName(sSheet)
		.SheetIndex = .XSpreadSheet.RangeAddress.Sheet

		&apos;	Resolve range part - either a sheet named range or the current selection or a real range or &quot;&quot;
		If IsNull(.XCellRange) Then
			Set oNamedRanges = .XSpreadSheet.NamedRanges
			If sRange = &quot;~&quot; Then
				Set oSelect = _Component.CurrentController.getSelection()
				If oSelect.supportsService(&quot;com.sun.star.sheet.SheetCellRanges&quot;) Then	&apos;	Multiple selections
					Set .XCellRange = oSelect.getByIndex(0)
				Else
					Set .XCellRange = oSelect
				End If
			ElseIf sRange = &quot;*&quot; Or sRange = &quot;&quot; Then
				vLastCell = _LastCell(.XSpreadSheet)
				sRange = &quot;A1:&quot; &amp; _GetColumnName(vLastCell(0)) &amp; CStr(vLastCell(1))
				Set .XCellRange = .XSpreadSheet.getCellRangeByName(sRange)
			ElseIf oNamedRanges.hasByName(sRange) Then
				.XCellRange = oNamedRanges.getByName(sRange).ReferredCells
			Else
				On Local Error GoTo CatchError
				Set .XCellRange = .XSpreadSheet.getCellRangeByName(sRange)
				&apos;	If range reaches the limits of the sheets, reduce it up to the used area
				Set oRangeAddress = .XCellRange.RangeAddress
				If oRangeAddress.StartColumn = 0 And oRangeAddress.EndColumn = MAXCOLS - 1 Then
					vLastCell = _LastCell(.XSpreadSheet)
					sRange = &quot;A&quot; &amp; CStr(oRangeAddress.StartRow + 1) &amp; &quot;:&quot; _
									&amp; _GetColumnName(vLastCell(0)) &amp; CStr(oRangeAddress.EndRow + 1)
					Set .XCellRange = .XSpreadSheet.getCellRangeByName(sRange)
				ElseIf oRangeAddress.StartRow = 0 And oRangeAddress.EndRow = MAXROWS - 1 Then
					vLastCell = _LastCell(.XSpreadSheet)
					sRange = _GetColumnName(oRangeAddress.StartColumn + 1) &amp; &quot;1&quot; &amp; &quot;:&quot; _
									&amp; _GetColumnName(oRangeAddress.EndColumn + 1) &amp; CStr(_LastCell(.XSpreadSheet)(1))
					Set .XCellRange = .XSpreadSheet.getCellRangeByName(sRange)
				End If
			End If
		End If
		If IsNull(.XCellRange) Then GoTo CatchAddress

		Set oRangeAddress = .XCellRange.RangeAddress
		.RangeName = .XCellRange.AbsoluteName
		.Height = oRangeAddress.EndRow - oRangeAddress.StartRow + 1
		.Width = oRangeAddress.EndColumn - oRangeAddress.StartColumn + 1

		&apos;	Remember the current component in case of use outside the current instance
		Set .Component = _Component

	End With

	&apos;	Store last parsed address for reuse
	Set _LastParsedAddress = oAddress

Finally:
	Set _ParseAddress = oAddress
	Exit Function
CatchError:
	ScriptForge.SF_Exception.Clear()
CatchAddress:
	ScriptForge.SF_Exception.RaiseFatal(CALCADDRESSERROR, &quot;Range&quot;, psAddress _
				, &quot;Document&quot;, [_Super]._FileIdent())
	GoTo Finally
End Function	&apos;	SFDocuments.SF_Calc._ParseAddress

REM -----------------------------------------------------------------------------
Private Function _PropertyGet(Optional ByVal psProperty As String _
								, Optional ByVal pvArg As Variant _
								) As Variant
&apos;&apos;&apos;	Return the value of the named property
&apos;&apos;&apos;	Args:
&apos;&apos;&apos;		psProperty: the name of the property

Dim oProperties As Object			&apos;	Document or Custom properties
Dim vLastCell As Variant			&apos;	Coordinates of last used cell in a sheet
Dim oSelect As Object				&apos;	Current selection
Dim vRanges As Variant				&apos;	List of selected ranges
Dim oAddress As Object				&apos;	_Address type for range description
Dim oCursor As Object				&apos;	com.sun.star.sheet.XSheetCellCursor
Dim i As Long
Dim cstThisSub As String
Const cstSubArgs = &quot;&quot;

	_PropertyGet = False

	cstThisSub = &quot;SFDocuments.Calc.get&quot; &amp; psProperty
	ScriptForge.SF_Utils._EnterFunction(cstThisSub, cstSubArgs)
	If Not _IsStillAlive() Then GoTo Finally

	Select Case UCase(psProperty)
		Case UCase(&quot;CurrentSelection&quot;)
			Set oSelect = _Component.CurrentController.getSelection()
			If IsNull(oSelect) Then
				_PropertyGet = Array()
			ElseIf oSelect.supportsService(&quot;com.sun.star.sheet.SheetCellRanges&quot;) Then	&apos;	Multiple selections
				vRanges = Array()
				For i = 0 To oSelect.Count - 1
					vRanges = ScriptForge.SF_Array.Append(vRanges, oSelect.getByIndex(i).AbsoluteName)
				Next i
				_PropertyGet = vRanges
			Else
				_PropertyGet = oSelect.AbsoluteName
			End If
		Case UCase(&quot;Height&quot;)
			If IsMissing(pvArg) Or IsEmpty(pvArg) Then
				_PropertyGet = 0
			Else
				If Not ScriptForge.SF_Utils._Validate(pvArg, &quot;Range&quot;, V_STRING) Then GoTo Finally
				_PropertyGet = _ParseAddress(pvArg).Height
			End If
		Case UCase(&quot;FirstCell&quot;), UCase(&quot;FirstRow&quot;), UCase(&quot;FirstColumn&quot;) _
				, UCase(&quot;LastCell&quot;), UCase(&quot;LastColumn&quot;), UCase(&quot;LastRow&quot;) _
				, UCase(&quot;SheetName&quot;)
			If IsMissing(pvArg) Or IsEmpty(pvArg) Then	&apos;	Avoid errors when instance is watched in Basic IDE
				If InStr(UCase(psProperty), &quot;CELL&quot;) &gt; 0 Then _PropertyGet = &quot;&quot; Else _PropertyGet = -1
			Else
				If Not ScriptForge.SF_Utils._Validate(pvArg, &quot;Range&quot;, V_STRING) Then GoTo Finally
				Set oAddress = _ParseAddress(pvArg)
				With oAddress.XCellRange
					Select Case UCase(psProperty)
						Case UCase(&quot;FirstCell&quot;)
							_PropertyGet = A1Style(.RangeAddress.StartRow + 1, .RangeAddress.StartColumn + 1, , , oAddress.XSpreadsheet.Name)
						Case UCase(&quot;FirstColumn&quot;)	:	_PropertyGet = CLng(.RangeAddress.StartColumn + 1)
						Case UCase(&quot;FirstRow&quot;)		:	_PropertyGet = CLng(.RangeAddress.StartRow + 1)
						Case UCase(&quot;LastCell&quot;)
							_PropertyGet = A1Style(.RangeAddress.EndRow + 1, .RangeAddress.EndColumn + 1, , , oAddress.XSpreadsheet.Name)
						Case UCase(&quot;LastColumn&quot;)	:	_PropertyGet = CLng(.RangeAddress.EndColumn + 1)
						Case UCase(&quot;LastRow&quot;)		:	_PropertyGet = CLng(.RangeAddress.EndRow + 1)
						Case UCase(&quot;SheetName&quot;)		:	_PropertyGet = oAddress.XSpreadsheet.Name
					End Select
				End With
			End If
		Case UCase(&quot;Range&quot;)
			If IsMissing(pvArg) Or IsEmpty(pvArg) Then
				Set _PropertyGet = Nothing
			Else
				If Not ScriptForge.SF_Utils._Validate(pvArg, &quot;Range&quot;, V_STRING) Then GoTo Finally
				Set _PropertyGet = _ParseAddress(pvArg)
			End If
		Case UCase(&quot;Region&quot;)
			If IsMissing(pvArg) Or IsEmpty(pvArg) Then
				_PropertyGet = &quot;&quot;
			Else
				If Not ScriptForge.SF_Utils._Validate(pvArg, &quot;Range&quot;, V_STRING) Then GoTo Finally
				Set oAddress = _ParseAddress(pvArg)
				With oAddress
					Set oCursor = .XSpreadsheet.createCursorByRange(.XCellRange)
					oCursor.collapseToCurrentRegion()
					_PropertyGet = oCursor.AbsoluteName
				End With
			End If
		Case UCase(&quot;Sheet&quot;)
			If IsMissing(pvArg) Or IsEmpty(pvArg) Then
				Set _PropertyGet = Nothing
			Else
				If Not _ValidateSheet(pvArg, &quot;SheetName&quot;, , True) Then GoTo Finally
				Set _PropertyGet = _ParseAddress(pvArg)
			End If
		Case UCase(&quot;Sheets&quot;)
			_PropertyGet = _Component.getSheets.getElementNames()
		Case UCase(&quot;Width&quot;)
			If IsMissing(pvArg) Or IsEmpty(pvArg) Then
				_PropertyGet = 0
			Else
				If Not ScriptForge.SF_Utils._Validate(pvArg, &quot;Range&quot;, V_STRING) Then GoTo Finally
				_PropertyGet = _ParseAddress(pvArg).Width
			End If
		Case UCase(&quot;XCellRange&quot;)
			If IsMissing(pvArg) Or IsEmpty(pvArg) Then
				Set _PropertyGet = Nothing
			Else
				If Not ScriptForge.SF_Utils._Validate(pvArg, &quot;Range&quot;, V_STRING) Then GoTo Finally
				Set _PropertyGet = _ParseAddress(pvArg).XCellRange
			End If
		Case UCase(&quot;XSheetCellCursor&quot;)
			If IsMissing(pvArg) Or IsEmpty(pvArg) Then
				Set _PropertyGet = Nothing
			Else
				If Not ScriptForge.SF_Utils._Validate(pvArg, &quot;Range&quot;, V_STRING) Then GoTo Finally
				Set oAddress = _ParseAddress(pvArg)
				Set _PropertyGet = oAddress.XSpreadsheet.createCursorByRange(oAddress.XCellRange)
			End If
		Case UCase(&quot;XSpreadsheet&quot;)
			If IsMissing(pvArg) Or IsEmpty(pvArg) Then
				Set _PropertyGet = Nothing
			Else
				If Not _ValidateSheet(pvArg, &quot;SheetName&quot;, , True) Then GoTo Finally
				Set _PropertyGet = _Component.getSheets.getByName(pvArg)
			End If
		Case Else
			_PropertyGet = Null
	End Select

Finally:
	ScriptForge.SF_Utils._ExitFunction(cstThisSub)
	Exit Function
End Function	&apos;	SFDocuments.SF_Calc._PropertyGet

REM -----------------------------------------------------------------------------
Private Function _QuoteSheetName(ByVal psSheetName As String) As String
&apos;&apos;&apos;	Return the given sheet name surrounded with single quotes
&apos;&apos;&apos;	when required to insert the sheet name into a Calc formula
&apos;&apos;&apos;	Enclosed single quotes are doubled
&apos;&apos;&apos;	Args:
&apos;&apos;&apos;		psSheetName: the name to quote
&apos;&apos;&apos;	Returns:
&apos;&apos;&apos;		The quoted or unchanged sheet name

Dim sSheetName As String			&apos;	Return value
Dim i As Long

Try:
	&apos;	Surround the sheet name with single quotes when required by the presence of single quotes
	If InStr(psSheetName, &quot;&apos;&quot;) &gt; 0 Then
		sSheetName = &quot;&apos;&quot; &amp; Replace(psSheetName, &quot;&apos;&quot;, &quot;&apos;&apos;&quot;) &amp; &quot;&apos;&quot;
	Else
		&apos;	Surround the sheet name with single quotes when required by the presence of at least one of the special characters
		sSheetName = psSheetName
		For i = 1 To Len(cstSPECIALCHARS)
			If InStr(sSheetName, Mid(cstSPECIALCHARS, i, 1)) &gt; 0 Then
				sSheetName = &quot;&apos;&quot; &amp; sSheetName &amp; &quot;&apos;&quot;
				Exit For
			End If
		Next i
	End If

Finally:
	_QuoteSheetName = sSheetName
	Exit Function
End Function	&apos;	SFDocuments.SF_Calc._QuoteSheetName

REM -----------------------------------------------------------------------------
Private Function _Repr() As String
&apos;&apos;&apos;	Convert the SF_Calc instance to a readable string, typically for debugging purposes (DebugPrint ...)
&apos;&apos;&apos;	Args:
&apos;&apos;&apos;	Return:
&apos;&apos;&apos;		&quot;[DOCUMENT]: Type/File&quot;

	_Repr = &quot;[Calc]: &quot; &amp; [_Super]._FileIdent()

End Function	&apos;	SFDocuments.SF_Calc._Repr

REM -----------------------------------------------------------------------------
Private Sub _RestoreSelections(ByRef pvComponent As Variant _
									, ByRef pvSelection As Variant _
									)
&apos;&apos;&apos;	Set the selection to a single or a multiple range
&apos;&apos;&apos;		Does not work well when multiple selections and macro terminating in Basic IDE
&apos;&apos;&apos;	Called by the CopyToCell and CopyToRange methods
&apos;&apos;&apos;	Args:
&apos;&apos;&apos;		pvComponent: should work for foreign instances as well
&apos;&apos;&apos;		pvSelection: the stored selection done previously by Component.CurrentController.getSelection()

Dim oCellRanges	As Object		&apos;	com.sun.star.sheet.SheetCellRanges
Dim vRangeAddresses As Variant	&apos;	Array of com.sun.star.table.CellRangeAddress
Dim i As Long

Try:
	If IsArray(pvSelection) Then
		Set oCellRanges = pvComponent.createInstance(&quot;com.sun.star.sheet.SheetCellRanges&quot;)
		vRangeAddresses = Array()
		ReDim vRangeAddresses(0 To UBound(pvSelection))
		For i = 0 To UBound(pvSelection)
			vRangeAddresses(i) = pvSelection.getByIndex(i).RangeAddress
		Next i
		oCellRanges.addRangeAddresses(vRangeAddresses, False)
		pvComponent.CurrentController.select(oCellRanges)
	Else
		pvComponent.CurrentController.select(pvSelection)
	End If

Finally:
	Exit Sub
End Sub	&apos;	SFDocuments.SF_Calc._RestoreSelections

REM -----------------------------------------------------------------------------
Private Function _ValidateSheet(Optional ByRef pvSheetName As Variant _
									, Optional ByVal psArgName As String _
									, Optional ByVal pvNew As Variant _
									, Optional ByVal pvActive As Variant _
									, Optional ByVal pvOptional as Variant _
									, Optional ByVal pvNumeric As Variant _
									, Optional ByVal pvReference As Variant _
									, Optional ByVal pvResetSheet As Variant _
									) As Boolean
&apos;&apos;&apos;	Sheet designation validation function similar to the SF_Utils._ValidateXXX functions
&apos;&apos;&apos;	Args:
&apos;&apos;&apos;		pvSheetName: string or numeric position
&apos;&apos;&apos;		pvArgName: the name of the variable to be used in the error message
&apos;&apos;&apos;		pvNew: if True, sheet must not exist (default = False)
&apos;&apos;&apos;		pvActive: if True, the shortcut &quot;~&quot; is accepted (default = False)
&apos;&apos;&apos;		pvOptional: if True, a zero-length string is accepted (default = False)
&apos;&apos;&apos;		pvNumeric: if True, the sheet position is accepted (default = False)
&apos;&apos;&apos;		pvReference: if True, a sheet reference is acceptable (default = False)
&apos;&apos;&apos;			pvNumeric and pvReference must not both be = True
&apos;&apos;&apos;		pvResetSheet: if True, return in pvSheetName the correct (case-sensitive) sheet name (default = False)
&apos;&apos;&apos;	Returns
&apos;&apos;&apos;		True if valid. SheetName is reset to current value if = &quot;~&quot;
&apos;&apos;&apos;	Exceptions
&apos;&apos;&apos;		DUPLICATESHEETERROR		A sheet with the given name exists already

Dim vSheets As Variant				&apos;	List of sheets
Dim lSheet As Long					&apos;	Index in list of sheets
Dim vTypes As Variant				&apos;	Array of accepted variable types
Dim bValid As Boolean				&apos;	Return value

Check:
	If IsMissing(pvNew) Or IsEmpty(pvNew) Then pvNew = False
	If IsMissing(pvActive) Or IsEmpty(pvActive) Then pvActive = False
	If IsMissing(pvOptional) Or IsEmpty(pvOptional) Then pvOptional = False
	If IsMissing(pvNumeric) Or IsEmpty(pvNumeric) Then pvNumeric = False
	If IsMissing(pvReference) Or IsEmpty(pvReference) Then pvReference = False
	If IsMissing(pvResetSheet) Or IsEmpty(pvResetSheet) Then pvResetSheet = False

	&apos;	Define the acceptable variable types
	If pvNumeric Then
		vTypes = Array(V_STRING, V_NUMERIC)
	ElseIf pvReference Then
		vTypes = Array(V_STRING, ScriptForge.V_OBJECT)
	Else
		vTypes = V_STRING
	End If
	If Not ScriptForge.SF_Utils._Validate(pvSheetName, psArgName, vTypes, , , Iif(pvReference, CALCREFERENCE, &quot;&quot;)) Then GoTo Finally
	bValid = False

Try:
	If VarType(pvSheetName) = V_STRING Then
		If pvOptional And Len(pvSheetName) = 0 Then
		ElseIf pvActive And pvSheetName = &quot;~&quot; Then
			pvSheetName = _Component.CurrentController.ActiveSheet.Name
		Else
			vSheets = _Component.getSheets.getElementNames()
			If pvNew Then
				&apos;	ScriptForge.SF_String.FindRegex(sAddress, &quot;^&apos;[^\[\]*?:\/\\]+&apos;&quot;)
				If ScriptForge.SF_Array.Contains(vSheets, pvSheetName) Then GoTo CatchDuplicate
			Else
				If Not ScriptForge.SF_Utils._Validate(pvSheetName, psArgName, V_STRING, vSheets) Then GoTo Finally
				If pvResetSheet Then
					lSheet = ScriptForge.SF_Array.IndexOf(vSheets, pvSheetName, CaseSensitive := False)
					pvSheetName = vSheets(lSheet)
				End If
			End If
		End If
	End If
	bValid = True

Finally:
	_ValidateSheet = bValid
	Exit Function
CatchDuplicate:
	ScriptForge.SF_Exception.RaiseFatal(DUPLICATESHEETERROR, psArgName, pvSheetName, &quot;Document&quot;, [_Super]._FileIdent())
	GoTo Finally
End Function	&apos;	SFDocuments.SF_Calc._ValidateSheet

REM -----------------------------------------------------------------------------
Private Function _ValidateSheetName(ByRef psSheetName As String _
										, ByVal psArgName As String _
										) As Boolean
&apos;&apos;&apos;	Check the validity of the sheet name:
&apos;&apos;&apos;	A sheet name	- must not be empty
&apos;&apos;&apos;					- must not contain next characters: []*?:/\
&apos;&apos;&apos;					- must not use &apos; (the apostrophe) as first or last character
&apos;&apos;&apos;	Args:
&apos;&apos;&apos;		psSheetName: the name to check
&apos;&apos;&apos;		psArgName: the name of the argument to appear in error messages
&apos;&apos;&apos;	Returns:
&apos;&apos;&apos;		True when the sheet name is valid
&apos;&apos;&apos;	Exceptions:
&apos;&apos;&apos;		CALCADDRESSERROR		&apos;	Sheet name could not be parsed to a valid name

Dim bValid As Boolean				&apos;	Return value

Try:
	bValid = ( Len(psSheetName) &gt; 0 )
	If bValid Then bValid = ( Left(psSheetName, 1) &lt;&gt; &quot;&apos;&quot; And Right(psSheetName, 1) &lt;&gt; &quot;&apos;&quot; )
	If bValid Then bValid = ( Len(ScriptForge.SF_String.FindRegex(psSheetName, &quot;^[^\[\]*?:\/\\]+$&quot;, 1, CaseSensitive := False)) &gt; 0 )
	If Not bValid Then GoTo CatchSheet

Finally:
	_ValidateSheetName = bValid
	Exit Function
CatchSheet:
	ScriptForge.SF_Exception.RaiseFatal(CALCADDRESSERROR, psArgName, psSheetName _
				, &quot;Document&quot;, [_Super]._FileIdent())
	GoTo Finally
End Function	&apos;	SFDocuments.SF_Calc._ValidateSheetName

REM ============================================ END OF SFDOCUMENTS.SF_CALC
</script:module>