home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
Computer Buyer 1998 October
/
dpcb1098.iso
/
Business
/
Ventura
/
Ventura
/
Scripts
/
EnableExportOnSave.csc
< prev
next >
Wrap
Text File
|
1998-07-07
|
25KB
|
568 lines
REM Sets Export On Save for all text files in current pub[CorelSCRIPT 8]
REM EnableExportOnSave.csc March, 1998
REM ⌐ 1998 Corel Corporation. All rights reserved.
REM **************************************************************************************
REM This script identifies all text files in the current publication. A list of all files
REM is then presented to the user to select those files to be set to export on save. The
REM specified files are set to export on save, names changed as required, and the
REM publication is saved to implement the new settings.
REM **************************************************************************************
' Create a temporary folder to provide a path for the include files
' -this enables the include files to be located
#addfol "..\..\Scripts"
#include "ScpConst.csi"
#include "VPConst.csi"
' Embed bitmaps if script is to be compiled into exe or csb formats
' -this will eliminate the need to include these files
#ADDRESBMP IntroBMP "Bitmaps\IntroBMP.bmp"
'Constants for Dialog Return Values
GLOBAL CONST DIALOG_RETURN_CANCEL% = 2
GLOBAL CONST DIALOG_RETURN_NEXT% = 3
GLOBAL CONST DIALOG_RETURN_BACK% = 4
GLOBAL CONST DIALOG_RETURN_BROWSE% = 5
'Constants for file specifications
GLOBAL CONST MAX_FILES% = 100 'number of text files in publication
GLOBAL CONST EXPORT_FORMAT_TYPES% = 4 'number of export format types
'/////FUNCTION & SUBROUTINE DECLARATIONS/////////////////////////////////////////////////
DECLARE SUB RegQuery()
DECLARE SUB CreateFolder(Folder$)
DECLARE SUB SetToExport()
DECLARE FUNCTION ShowIntro%()
DECLARE FUNCTION ShowFileList%()
DECLARE FUNCTION GetCurrentPub$()
DECLARE FUNCTION GetPublicationDir$(CurrentPublication$)
'/////GLOBAL VARIABLES ///////////////////////////////////////////////////////////////////
GLOBAL VenturaRoot$ 'Root directory of Ventura from registry
GLOBAL SelectedFiles$(MAX_FILES) 'array of selected files to set to Export on Save
GLOBAL SelectedChapters$(MAX_FILES) 'array of selected chapters corresponding to selected files
GLOBAL SelectedFilesCount% 'number of files selected to set to Export on Save
GLOBAL CurrentDir$ 'name of the current directory
GLOBAL ExportFilters%(EXPORT_FORMAT_TYPES) 'array of export filter types (integers corresponding to the format type)
ExportFilters%(1) = FILTER_VEN_ANSI 'ANSI Text
ExportFilters%(2) = FILTER_VEN_ASCII 'ASCII Text
ExportFilters%(3) = FILTER_VEN_ASCII_8BIT 'ASCII 8-bit Text
ExportFilters%(4) = FILTER_RTF 'Rich Text Format
GLOBAL ExportExtensions$(EXPORT_FORMAT_TYPES)'array of export filter extensions
ExportExtensions$(1) = "TXT" 'ANSI Text
ExportExtensions$(2) = "TXT" 'ASCII Text
ExportExtensions$(3) = "TXT" 'ASCII 8-bit Text
ExportExtensions$(4) = "RTF" 'Rich Text Format
GLOBAL ExportFormats$(EXPORT_FORMAT_TYPES) 'array of export filter formats (these are the strings used by the drop-down list of filter types)
ExportFormats$(1) = "ANSI Text (*.TXT)" 'ANSI Text
ExportFormats$(2) = "ASCII Text (*.TXT)" 'ASCII Text
ExportFormats$(3) = "ASCII 8-bit Text (*.TXT)" 'ASCII 8-bit Text
ExportFormats$(4) = "Rich Text Format (*.RTF)" 'Rich Text Format
GLOBAL FilterSelection% 'index corresponding to filter selection
FilterSelection% = 1 'initialize filter selection to first element (ie. ANSI text)
'/////LOCAL DECLARATIONS//////////////////////////////////////////////////////////////////
CONST MAXSTEP% = 2 'maximum number of pages in the Wizard
DIM DialogReturn% 'identifies user's selection for next step in Wizard
DIM NextStep% 'specifies which page appears next in the Wizard
'///// MAIN ////////////////////////////////////////////////////////////////////////////////
ON ERROR GOTO ErrorHandler
RegQuery 'get root directory where Ventura is installed
CurrentPub$ = GetCurrentPub$() 'get name of current (active) publication
CurrentDir$ = GetPublicationDir$(CurrentPub$) 'get directory of current (active) publication
'this section controls traversal through the Wizard pages
NextStep% = 1
DO
SELECT CASE NextStep%
CASE 1: DialogReturn% = ShowIntro() 'display Intro dialog
CASE 2: DialogReturn% = ShowFileList() 'display File list dialog
END SELECT
NextStep% = NextStep% + DialogReturn%
LOOP UNTIL NextStep% = MAXSTEP + 1
SetToExport 'set selected files to export on save
ExitScript:
STOP
ErrorHandler:
SELECT CASE ErrNum
CASE 800
MESSAGE "FATAL ERROR" & CHR(13) & "Script will now exit."
RESUME AT ExitScript
CASE ELSE
MESSAGE "ERROR: " & STR(ErrNum) & CHR(13) & "Script will now exit."
RESUME AT ExitScript
END SELECT
' *******************************************************************************
' RegQuery
' This subroutine queries the Registry to determine the root directory where
' Ventura is installed.
' *******************************************************************************
SUB RegQuery
ON ERROR GOTO ErrorHandler
'get Ventura config directory
VentDir$ = REGISTRYQUERY(HKEY_LOCAL_MACHINE,VENTURA_REGQUERY_CONST,"ConfigDir")
'isolate Ventura root directory from Ventura config directory
first% = 1
pos% = 1
DO WHILE first <> 0
first = INSTR(VentDir$, "\", first )
IF first <> 0 THEN
pos = first
first = first + 1
END IF
LOOP
VenturaRoot$ = LEFT(VentDir$, pos - 1) 'root directory where Ventura is installed
EXIT SUB
ErrorHandler:
MESSAGE "Error reading registry:" & CHR(13) & RegString$
ErrNum = 800
END SUB
' *******************************************************************************
' GetCurrentPub
' This function queries VENTURA for the name of the current publication. IF no
' publication is open, the user is prompted to open one before continuing.
'
' PARAMS: None
'
' RETURNS: GetCurrentPub$ - the name of the current publication.
' *******************************************************************************
FUNCTION GetCurrentPub$()
BEGINWAITCURSOR
WITHOBJECT OBJECT_VENTURA8
ENDWAITCURSOR
IF .CountWindows() = 0 THEN
PubMsg$ = "You need an open publication to run this script." & CHR(13) & "Open one now?"
MsgVal% = MESSAGEBOX(PubMsg$, "WARNING", MB_YES_NO OR MB_STOP_ICON)
IF MsgVal% = MSG_YES THEN 'Yes, open a pub
SETCURRFOLDER VenturaRoot$
PubName$ = GETFILEBOX("Publication files (*.VP*)|*.VP*", , , ,"*.vp*", VenturaRoot$ & "\Ventura\Samples" )
IF PubName$ <> "" THEN
.SetVisible TRUE
.FileOpen PubName$, , TRUE, 1, TRUE, FALSE
ELSE
STOP
ENDIF
ELSE
STOP
ENDIF
ENDIF
GetCurrentPub$ = .PublicationName()
END WITHOBJECT
END FUNCTION
' *********************************************************************************
' GetPublicationDir
' This function separates the directory from the name of the specified publication.
'
' PARAMS: CurrentPublication$ - the publication from which to obtain the directory.
'
' RETURN: GetPublicationDir$ - the directory that the specified pub resides in.
' *********************************************************************************
FUNCTION GetPublicationDir$(CurrentPublication$)
'IF name doesn't contain a directory, default to Ventura root directory
NoDir% = INSTR(CurrentPublication$, "\", 1)
IF NoDir% = 0 THEN
GetPublicationDir$ = VenturaRoot$ & "\Ventura\Samples"
ELSE
first% = 1
pos% = 1
WHILE first% <> 0
first% = INSTR(CurrentPublication$, "\", first%)
IF first% <> 0 THEN
pos% = first%
first% = first% + 1
ENDIF
WEND
GetPublicationDir$ = LEFT(CurrentPublication$, pos% - 1)
ENDIF
END FUNCTION
' *******************************************************************************
' ShowIntro
' This function displays the introduction dialog.
'
' PARAMS: None
'
' RETURNS: ShowIntro AS INTEGER - Integer indicating dialog return value.
' *******************************************************************************
FUNCTION ShowIntro%
BEGIN DIALOG OBJECT IntroDialog 290, 180, "Set Files to Export On Save", SUB IntroDialogEventHandler
PUSHBUTTON 181, 160, 46, 14, .NextButton, "&Next >"
CANCELBUTTON 234, 160, 46, 14, .CancelButton
PUSHBUTTON 135, 160, 46, 14, .BackButton, "< &Back"
TEXT 95, 10, 189, 20, .Text2, "This Wizard guides you through the steps necessary to set all text files to Export on Save."
TEXT 95, 40, 185, 20, .Text3, "Specify a directory and select a format in which to save the exported files."
IMAGE 10, 10, 75, 130, .IntroImage
GROUPBOX 10, 150, 270, 5, .LineGroupBox
DDLISTBOX 140, 120, 140, 59, .FormatDDListBox
TEXT 95, 122, 43, 12, .Text4, "&Text Format:"
TEXT 95, 78, 30, 12, .Text5, "&Directory:"
TEXTBOX 140, 75, 140, 13, .DirectoryTextBox
PUSHBUTTON 234, 92, 46, 14, .BrowseButton, "B&rowse"
END DIALOG
IntroDialog.SetStyle STYLE_INVISIBLE
IntroDialog.IntroImage.SetImage "#IntroBMP"
IntroDialog.IntroImage.SetStyle STYLE_IMAGE_CENTERED
IntroRet%=DIALOG(IntroDialog)
IF IntroRet% = DIALOG_RETURN_CANCEL THEN STOP
IF IntroRet% = DIALOG_RETURN_NEXT THEN
FilterSelection% = IntroDialog.FormatDDListBox.GetSelect()
ShowIntro = 1
ENDIF
END FUNCTION
' *******************************************************************************
' IntroDialogEventHandler
' This subroutine responds to user interface with the introduction dialog.
'
' PARAMS: BYVAL ControlID% - Integer indicating the dialog control that is
' generating a dialog event.
' BYVAL Event% - Integer indicating the dialog event that has occurred.
' *******************************************************************************
SUB IntroDialogEventHandler(BYVAL ControlID%, BYVAL Event%)
DIM FolderStatus AS BOOLEAN
IF Event% = EVENT_INITIALIZATION THEN
IntroDialog.BackButton.Enable FALSE
IntroDialog.SetStyle STYLE_VISIBLE
IntroDialog.DirectoryTextBox.SetText CurrentDir$
IntroDialog.FormatDDListBox.SetArray ExportFormats$
IntroDialog.FormatDDListBox.SetSelect FilterSelection%
ENDIF
IF Event% = EVENT_CHANGE_IN_CONTENT THEN
CurrentDir$ = IntroDialog.DirectoryTextBox.GetText()
ENDIF
IF Event% = EVENT_MOUSE_CLICK THEN
SELECT CASE ControlID%
CASE IntroDialog.NextButton.GetID()
CurrentDir$ = IntroDialog.DirectoryTextBox.GetText()
FolderStatus = MKFOLDER(CurrentDir$)
IF FolderStatus = FALSE THEN
IntroDialog.CloseDialog DIALOG_RETURN_NEXT
ELSE
CreateFolder CurrentDir$
IntroDialog.CloseDialog DIALOG_RETURN_NEXT
ENDIF
CASE IntroDialog.CancelButton.GetID()
IntroDialog.CloseDialog DIALOG_RETURN_CANCEL
CASE IntroDialog.BrowseButton.GetID()
NewFolder$ = GETFOLDER(CurrentDir$)
IF NewFolder$ <> "" THEN CurrentDir$ = NewFolder$
IntroDialog.DirectoryTextBox.SetText CurrentDir$
CASE IntroDialog.FormatDDListBox.GetID()
FilterSelection% = IntroDialog.FormatDDListBox.GetSelect()
END SELECT
ENDIF
END SUB
' *******************************************************************************
' ShowFileList
' This function displays the list of available files (FileList).
'
' PARAMS: None
'
' RETURNS: ShowIntro AS INTEGER - Integer indicating dialog return value.
' *******************************************************************************
FUNCTION ShowFileList
BEGIN DIALOG OBJECT ShowFileListDialog 290, 180, "VENTURA File Export Wizard", SUB FileListDialogEventHandler '"Corel VENTURA Conversion Wizard - Done"
LISTBOX 10, 25, 100, 107, .FilesListBox
PUSHBUTTON 122, 33, 46, 14, .SelectButton, "&Select >>"
PUSHBUTTON 122, 49, 46, 14, .DeselectButton, "<< &Deselect"
PUSHBUTTON 123, 95, 46, 14, .SelectAllButton, "Select &All"
PUSHBUTTON 123, 112, 46, 14, .DeselectAllButton, "D&eselect All"
LISTBOX 180, 26, 100, 107, .SelectedFilesListBox
PUSHBUTTON 135, 160, 46, 14, .BackButton, "< &Back"
PUSHBUTTON 181, 160, 46, 14, .NextButton, "&Finish"
CANCELBUTTON 234, 160, 46, 14, .CancelButton
LISTBOX 180, 27, 100, 107, .SelectedChaptersListBox
TEXT 10, 2, 269, 11, .Text2, "Select the files you wish to set to Export on Save."
TEXT 10, 14, 56, 10, .Text4, "Available files:"
TEXT 88, 14, 20, 10, .FilesCountText, ""
TEXT 180, 14, 61, 10, .Text5, "Selected files:"
TEXT 258, 14, 20, 10, .SelectedFilesCountText, ""
LISTBOX 10, 25, 100, 107, .ChapterListBox
TEXT 10, 136, 270, 12, .StatusText, "No files selected"
GROUPBOX 10, 150, 270, 5, .LineGroupBox
END DIALOG
ShowFileListDialog.SetStyle STYLE_INVISIBLE
ShowFileListDialog.StatusText.SetStyle STYLE_SUNKEN
ShowFileListRet% = DIALOG(ShowFileListDialog)
SELECT CASE ShowFileListRet%
CASE DIALOG_RETURN_CANCEL
STOP
CASE DIALOG_RETURN_NEXT
ShowFileList = 1
CASE DIALOG_RETURN_BACK
ShowFileList = -1
END SELECT
END FUNCTION
' *******************************************************************************
' FileListDialogEventHandler
' This subroutine responds to user interface with the file list dialog.
'
' PARAMS: BYVAL ControlID% - Integer indicating the dialog control that is
' generating a dialog event.
' BYVAL Event% - Integer indicating the dialog event that has occurred.
' *******************************************************************************
SUB FileListDialogEventHandler(BYVAL ControlID%, BYVAL Event%)
IF Event% = EVENT_INITIALIZATION THEN
ShowFileListDialog.ChapterListBox.SetStyle STYLE_INVISIBLE
ShowFileListDialog.SelectedChaptersListBox.SetStyle STYLE_INVISIBLE
ShowFileListDialog.FilesCountText.SetStyle STYLE_RIGHT_JUSTIFY
ShowFileListDialog.SelectedFilesCountText.SetStyle STYLE_RIGHT_JUSTIFY
IF ShowFileListDialog.SelectedFilesListBox.GetItemCount() = 0 THEN
ShowFileListDialog.NextButton.Enable FALSE
ELSE
ShowFileListDialog.NextButton.Enable TRUE
ENDIF
BEGINWAITCURSOR
WITHOBJECT OBJECT_VENTURA8
'FOR every chapter in publication
NumberOfChapters& = .ChapterCount()
FOR i% = 1 TO NumberOfChapters&
CurChapter$ = .ChapterGetAt(i%)
.ViewGoToPage , CurChapter$, GOTO_RELATIVE_TO_CHAPTER, GOTO_PAGE_FIRST, FALSE
'FOR every text file in chapter
NumberOfTextFiles& = .TextFileCount()
FOR j% = 1 TO NumberOfTextFiles&
CurFile$ = .TextFileGetAt(j%)
ShowFileListDialog.FilesListBox.AddItem CurFile$
ShowFileListDialog.ChapterListBox.AddItem CurChapter$
NEXT j%
NEXT i%
END WITHOBJECT
ENDWAITCURSOR
ShowFileListDialog.FilesListBox.SetSelect 1
ShowFileListDialog.StatusText.SetText CurrentDir$
ShowFileListDialog.FilesCountText.SetText ShowFileListDialog.FilesListBox.GetItemCount()
ShowFileListDialog.SelectedFilesCountText.SetText ShowFileListDialog.SelectedFilesListBox.GetItemCount()
ShowFileListDialog.SetStyle STYLE_VISIBLE
ENDIF
IF Event% = EVENT_MOUSE_CLICK THEN
SELECT CASE ControlID%
CASE ShowFileListDialog.NextButton.GetID()
SelectedFilesCount% = ShowFileListDialog.SelectedFilesListBox.GetItemCount()
REDIM SelectedFiles$(SelectedFilesCount) 'redimension array to accomodate all selected files
REDIM SelectedChapters$(SelectedFilesCount)
FOR i% = 1 TO SelectedFilesCount% 'FOR all items in selected files list
SelectedFiles$(i%) = ShowFileListDialog.SelectedFilesListBox.GetItem(i%) 'add selection to FilesList
SelectedChapters$(i%) = ShowFileListDialog.SelectedChaptersListBox.GetItem(i%)
NEXT i%
ShowFileListDialog.closedialog DIALOG_RETURN_NEXT
CASE ShowFileListDialog.BackButton.GetID()
ShowFileListDialog.closedialog DIALOG_RETURN_BACK
CASE ShowFileListDialog.SelectButton.GetID()
indx% = ShowFileListDialog.FilesListBox.GetSelect() 'get index of selection
IF indx%=0 THEN 'no files selected
IF ShowFileListDialog.FilesListBox.GetItemCount() = 0 THEN
MESSAGE "There are no files available for selection."
ELSE
MESSAGE "Please select a file from the available files list."
ENDIF
ELSE
ShowFileListDialog.SelectedFilesListBox.AddItem ShowFileListDialog.FilesListBox.GetItem(indx%) 'add selection to SelectedFilesList
ShowFileListDialog.FilesListBox.RemoveItem indx% 'remove selection from available files list
ShowFileListDialog.SelectedChaptersListBox.AddItem ShowFileListDialog.ChapterListBox.GetItem(indx%) 'add selection to selected path list
ShowFileListDialog.ChapterListBox.RemoveItem indx% 'remove selection from available paths list
IF indx% > ShowFileListDialog.FilesListBox.GetItemCount() THEN
ShowFileListDialog.FilesListBox.SetSelect indx%-1
ELSE
ShowFileListDialog.FilesListBox.SetSelect indx%
ENDIF
ShowFileListDialog.StatusText.SetText CurrentDir$
ShowFileListDialog.SelectedFilesListBox.SetSelect 0
ENDIF
CASE ShowFileListDialog.DeselectButton.GetID()
indx% = ShowFileListDialog.SelectedFilesListBox.GetSelect() 'get index of selection
IF indx%=0 THEN 'no files selected
IF ShowFileListDialog.SelectedFilesListBox.GetItemCount() = 0 THEN
MESSAGE "There are no files available for deselection"
ELSE
MESSAGE "Please select a file from the selected files list."
ENDIF
ELSE
ShowFileListDialog.FilesListBox.AddItem ShowFileListDialog.SelectedFilesListBox.GetItem(indx%) 'add selection to FilesList
ShowFileListDialog.SelectedFilesListBox.RemoveItem indx% 'remove selection from selected files list
ShowFileListDialog.ChapterListBox.AddItem ShowFileListDialog.SelectedChaptersListBox.GetItem(indx%) 'add selection to available path list
ShowFileListDialog.SelectedChaptersListBox.RemoveItem indx% 'remove selection from selected path list
IF indx% > ShowFileListDialog.SelectedFilesListBox.GetItemCount() THEN
ShowFileListDialog.SelectedFilesListBox.SetSelect indx%-1
ELSE
ShowFileListDialog.SelectedFilesListBox.SetSelect indx%
ENDIF
ShowFileListDialog.StatusText.SetText CurrentDir$
ShowFileListDialog.FilesListBox.SetSelect 0
ENDIF
CASE ShowFileListDialog.SelectAllButton.GetID()
ShowFileListDialog.StatusText.SetText "All files selected."
ShowFileListDialog.SelectedFilesListBox.SetSelect 0
WHILE ShowFileListDialog.FilesListBox.GetItemCount() > 0 'while there are available files
ShowFileListDialog.SelectedFilesListBox.AddItem ShowFileListDialog.FilesListBox.GetItem(1) 'add selection to SelectedFilesList
ShowFileListDialog.FilesListBox.RemoveItem 1 'remove selection from available files list
ShowFileListDialog.SelectedChaptersListBox.AddItem ShowFileListDialog.ChapterListBox.GetItem(1) 'add selection to selected path list
ShowFileListDialog.ChapterListBox.RemoveItem 1 'remove selection from available paths list
ShowFileListDialog.FilesCountText.SetText ShowFileListDialog.FilesListBox.GetItemCount() 'number of available files
ShowFileListDialog.SelectedFilesCountText.SetText ShowFileListDialog.SelectedFilesListBox.GetItemCount() 'number of selected files
WEND
CASE ShowFileListDialog.DeselectAllButton.GetID()
ShowFileListDialog.StatusText.SetText "No files selected."
ShowFileListDialog.FilesListBox.SetSelect 0
WHILE ShowFileListDialog.SelectedFilesListBox.GetItemCount() > 0 'while there are selected files
ShowFileListDialog.FilesListBox.AddItem ShowFileListDialog.SelectedFilesListBox.GetItem(1) 'add selection to FilesList
ShowFileListDialog.SelectedFilesListBox.RemoveItem 1 'remove selection from selected files list
ShowFileListDialog.ChapterListBox.AddItem ShowFileListDialog.SelectedChaptersListBox.GetItem(1) 'add selection to available path list
ShowFileListDialog.SelectedChaptersListBox.RemoveItem 1 'remove selection from selected path list
ShowFileListDialog.FilesCountText.SetText ShowFileListDialog.FilesListBox.GetItemCount() 'number of available files
ShowFileListDialog.SelectedFilesCountText.SetText ShowFileListDialog.SelectedFilesListBox.GetItemCount() 'number of selected files
WEND
CASE ShowFileListDialog.CancelButton.GetID()
ShowFileListDialog.closedialog DIALOG_RETURN_CANCEL
CASE ShowFileListDialog.FilesListBox.GetID() 'files list
ShowFileListDialog.StatusText.SetText CurrentDir$
ShowFileListDialog.SelectedFilesListBox.SetSelect 0
CASE ShowFileListDialog.SelectedFilesListBox.GetID() 'selected files list
ShowFileListDialog.StatusText.SetText CurrentDir$
ShowFileListDialog.FilesListBox.SetSelect 0
END SELECT
ShowFileListDialog.FilesCountText.SetText ShowFileListDialog.FilesListBox.GetItemCount() 'number of available files
ShowFileListDialog.SelectedFilesCountText.SetText ShowFileListDialog.SelectedFilesListBox.GetItemCount() 'number of selected files
ENDIF
IF Event% = EVENT_DBL_MOUSE_CLICK THEN
SELECT CASE ControlID%
CASE ShowFileListDialog.FilesListBox.GetID()
indx% = ShowFileListDialog.FilesListBox.GetSelect() 'get index of selection
ShowFileListDialog.SelectedFilesListBox.AddItem ShowFileListDialog.FilesListBox.GetItem(indx%) 'add selection to SelectedFilesList
ShowFileListDialog.FilesListBox.RemoveItem indx% 'remove selection from available files list
ShowFileListDialog.SelectedChaptersListBox.AddItem ShowFileListDialog.ChapterListBox.GetItem(indx%) 'add selection to selected path list
ShowFileListDialog.ChapterListBox.RemoveItem indx% 'remove selection from available paths list
IF indx% > ShowFileListDialog.FilesListBox.GetItemCount() THEN
ShowFileListDialog.FilesListBox.SetSelect indx%-1
ELSE
ShowFileListDialog.FilesListBox.SetSelect indx%
ENDIF
CASE ShowFileListDialog.SelectedFilesListBox.GetID() 'selected files list
indx% = ShowFileListDialog.SelectedFilesListBox.GetSelect() 'get index of selection
ShowFileListDialog.FilesListBox.AddItem ShowFileListDialog.SelectedFilesListBox.GetItem(indx%) 'add selection to FilesList
ShowFileListDialog.SelectedFilesListBox.RemoveItem indx% 'remove selection from selected files list
ShowFileListDialog.ChapterListBox.AddItem ShowFileListDialog.SelectedChaptersListBox.GetItem(indx%) 'add selection to available path list
ShowFileListDialog.SelectedChaptersListBox.RemoveItem indx% 'remove selection from selected path list
IF indx% > ShowFileListDialog.SelectedFilesListBox.GetItemCount() THEN
ShowFileListDialog.SelectedFilesListBox.SetSelect indx%-1
ELSE
ShowFileListDialog.SelectedFilesListBox.SetSelect indx%
ENDIF
END SELECT
ShowFileListDialog.FilesCountText.SetText ShowFileListDialog.FilesListBox.GetItemCount() 'number of available files
ShowFileListDialog.SelectedFilesCountText.SetText ShowFileListDialog.SelectedFilesListBox.GetItemCount() 'number of selected files
ENDIF
IF ShowFileListDialog.SelectedFilesListBox.GetItemCount() = 0 THEN
ShowFileListDialog.NextButton.Enable FALSE
ELSE
ShowFileListDialog.NextButton.Enable TRUE
ENDIF
END SUB
' *******************************************************************************
' SetToExport
' This function sets the selected files to Export on save. The publication is
' then saved to implement the set.
'
' PARAMS: None
' *******************************************************************************
SUB SetToExport
ON ERROR RESUME NEXT
BEGINWAITCURSOR
WITHOBJECT OBJECT_VENTURA8
FOR i% = 1 TO SelectedFilesCount%
pos% = INSTR(SelectedFiles$(i%), ".")
IF pos% = 0 THEN
NewName$ = SelectedFiles$(i%) & "."
ELSE
NewName$ = LEFT(SelectedFiles$(i%),pos%)
ENDIF
NewName$ = CurrentDir$ & "\" & NewName$ & ExportExtensions$(FilterSelection%)
.FileRenameTextFile SelectedFiles$(i%) ,NewName$ , ExportFilters%(FilterSelection%), TRUE, SelectedChapters$(i%)
NEXT i%
.FileSave (.PublicationName())
END WITHOBJECT
ENDWAITCURSOR
END SUB
' *******************************************************************************
' CreateFolder
' This subroutine creates the specified folder.
'
' PARAMS: Folder$ - the folder to create.
' *******************************************************************************
SUB CreateFolder(Folder$)
DIM FolderStatus AS BOOLEAN
Temp$ = Folder$
FolderStatus = MKFOLDER(Temp$)
IF FINDFIRSTFOLDER(Temp$, 1 OR 2 OR 4 OR 16 OR 32 or 128 OR 256 OR 2048) = "" THEN
DO WHILE FolderStatus = FALSE
first% = 1
pos% = 1
DO WHILE first <> 0
first% = INSTR(Temp$, "\", first%)
IF first% <> 0 THEN
pos% = first%
first% = first% + 1
END IF
LOOP
Temp$ = LEFT(Temp$, pos% - 1)
FolderStatus = MKFOLDER(Temp$)
LOOP
FolderStatus = MKFOLDER(Temp$)
IF FolderStatus = FALSE THEN CreateFolder(Folder$)
ENDIF
END SUB