home *** CD-ROM | disk | FTP | other *** search
Wrap
REM Lists all items in a VENTURA 8 library [CorelSCRIPT 8] REM LibraryList.csc March, 1998 REM ⌐ 1998 Corel Corporation. All rights reserved. REM ************************************************************************************** REM This script lists all the items in the specified Ventura Library REM The resulting list is displayed in a Ventura publication. 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" #ADDRESBMP Step2BMP "Bitmaps\Step2BMP.bmp" #ADDRESBMP LastBMP "Bitmaps\LastBMP.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 '/////FUNCTION & SUBROUTINE DECLARATIONS///////////////////////////////////////// DECLARE SUB RegQuery() DECLARE FUNCTION ShowIntro%() DECLARE FUNCTION GetLIBName%() DECLARE FUNCTION ShowFinish%() DECLARE SUB GetLibInfo() DECLARE FUNCTION DoesFileExist(FileName$) AS BOOLEAN '/////GLOBAL VARIABLES ////////////////////////////////////////////////////////// GLOBAL VenturaRoot$ 'root directory where Ventura is installed GLOBAL LibraryDir$ 'directory where library files are located GLOBAL LIBName$ 'name and path of library which items are to be listed '////// LOCAL VARIABLES ///////////////////////////////////////////////////////// CONST MAXSTEP% = 3 '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 LibraryDir$ = VenturaRoot$ & "\Ventura\Library" 'initialize default library directory LIBName$= VenturaRoot$ & "\Ventura\Library" 'initialize default library name 'this section controls traversal through the dialog pages NextStep% = 1 DO SELECT CASE NextStep% CASE 1: DialogReturn% = ShowIntro() 'show Intro dialog CASE 2: DialogReturn% = GetLIBName() 'get name of library to be listed CASE 3: DialogReturn% = ShowFinish() 'show finish dialog END SELECT NextStep% = NextStep% + DialogReturn% LOOP UNTIL NextStep% = MAXSTEP + 1 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 ' ************************************************************************************** ' DoesFileExist ' This function determines whether the specified file exists. ' ' PARAMS:FileName AS STRING - The name and path of the file in question. ' RETURNS: DoesFileExist AS BOOLEAN - TRUE if the file exists. ' - FALSE if the file does not exist. ' ************************************************************************************** FUNCTION DoesFileExist(FileName$) AS BOOLEAN ON ERROR GOTO ErrorHandler FileStatus$ = FINDFIRSTFOLDER(FileName$, FILEATTR_READ_ONLY OR FILEATTR_HIDDEN OR FILEATTR_SYSTEM OR FILEATTR_ARCHIVE OR FILEATTR_NORMAL_FILE OR FILEATTR_TEMPORARY) IF FileStatus$ = "" THEN DoesFileExist = FALSE ELSE DoesFileExist = TRUE ENDIF FunctionEnd: EXIT FUNCTION ErrorHandler: SELECT CASE ErrNum CASE ELSE DoesFileExist = FALSE END SELECT RESUME AT FunctionEnd 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, "Corel VENTURA Library Wizard", 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, 185, 20, .Text2, "This wizard lists all items in the specified Corel VENTURA library." IMAGE 10, 10, 75, 130, .IntroImage GROUPBOX 10, 150, 270, 5, .LineGroupBox TEXT 95, 40, 185, 20, .Text5, "To begin listing the library items, click Next." END DIALOG IntroDialog.IntroImage.SetImage "#IntroBMP" IntroDialog.IntroImage.SetStyle STYLE_IMAGE_CENTERED IntroRet%=DIALOG(IntroDialog) IF IntroRet% = DIALOG_RETURN_CANCEL THEN STOP IF IntroRet% = 3 THEN ShowIntro = 1 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%) IF Event% = EVENT_INITIALIZATION THEN IntroDialog.BackButton.Enable FALSE ENDIF IF Event% = EVENT_MOUSE_CLICK THEN SELECT CASE ControlID% CASE IntroDialog.NextButton.GetID() IntroDialog.CloseDialog DIALOG_RETURN_NEXT CASE IntroDialog.CancelButton.GetID() IntroDialog.CloseDialog DIALOG_RETURN_CANCEL END SELECT ENDIF END FUNCTION ' ******************************************************************************* ' GetLIBName ' This function prompts the user for the name of the library. ' ' RETURNS: GetLIBName AS INTEGER - Integer indicating dialog return value. ' ******************************************************************************* FUNCTION GetLIBName% BEGIN DIALOG OBJECT GetLIBNameDialog 290, 180, "Corel VENTURA Library Wizard", SUB GetLIBNameDialogEventHandler TEXTBOX 95, 29, 185, 13, .LibNameTextBox PUSHBUTTON 234, 49, 46, 14, .BrowseButton, "&Browse..." PUSHBUTTON 135, 160, 46, 14, .BackButton, "< &Back" PUSHBUTTON 181, 160, 46, 14, .NextButton, "&Next >" CANCELBUTTON 234, 160, 46, 14, .CancelButton TEXT 95, 15, 175, 12, .Text2, "Which library would you like to use?" IMAGE 10, 10, 75, 130, .GetLIBNameImage GROUPBOX 10, 150, 270, 5, .LineGroupBox END DIALOG GetLIBNameDialog.SetStyle STYLE_INVISIBLE GetLIBNameDialog.GetLIBNameImage.SetImage "#Step2BMP" GetLIBNameDialog.GetLIBNameImage.SetStyle STYLE_IMAGE_CENTERED GetLIBNameRet% = Dialog(GetLIBNameDialog) SELECT CASE GetLIBNameRet% CASE DIALOG_RETURN_CANCEL STOP CASE DIALOG_RETURN_NEXT GetLIBName = 1 CASE DIALOG_RETURN_BACK GetLIBName = -1 END SELECT END FUNCTION ' ******************************************************************************* ' GetLIBNameDialogEventHandler ' This subroutine responds to user interface with the library name 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 GetLIBNameDialogEventHandler(BYVAL ControlID%, BYVAL Event%) ON ERROR RESUME NEXT IF Event% = EVENT_INITIALIZATION THEN GetLIBNameDialog.LibNameTextBox.SetText LIBName$ pos% = INSTR(LIBName$, ".") IF pos% = 0 THEN GetLIBNameDialog.NextButton.Enable FALSE ELSE GetLIBNameDialog.NextButton.Enable TRUE ENDIF GetLIBNameDialog.SetStyle STYLE_VISIBLE ENDIF IF Event% = EVENT_CHANGE_IN_CONTENT THEN SELECT CASE ControlID% CASE GetLIBNameDialog.LibNameTextBox.GetID() LIBName$ = GetLIBNameDialog.LibNameTextBox.gettext() pos% = INSTR(LIBName$, ".") IF pos% = 0 THEN GetLIBNameDialog.NextButton.Enable FALSE ELSE GetLIBNameDialog.NextButton.Enable TRUE ENDIF END SELECT ENDIF IF Event% = EVENT_MOUSE_CLICK THEN SELECT CASE ControlID% CASE GetLIBNameDialog.NextButton.GetID() IF DoesFileExist(LIBName$) = TRUE THEN 'library exists, continue GetLIBNameDialog.closedialog DIALOG_RETURN_NEXT ELSE MESSAGE "Cannot locate library:" & CHR(13) & LIBName$ ENDIF CASE GetLIBNameDialog.BackButton.GetID() GetLIBNameDialog.closedialog DIALOG_RETURN_BACK CASE GetLIBNameDialog.CancelButton.GetID() GetLIBNameDialog.closedialog DIALOG_RETURN_CANCEL CASE GetLIBNameDialog.BrowseButton.GetID() SETCURRFOLDER LibraryDir$ LIBName$ = GETFILEBOX("Ventura Library (*.vlb)|*.vlb", "Open Library") IF LIBName$ <> "" THEN GetLIBNameDialog.LibNameTextBox.SetText LIBName$ GetLIBNameDialog.NextButton.Enable TRUE ELSE GetLIBNameDialog.LibNameTextBox.SetText LibraryDir$ GetLIBNameDialog.NextButton.Enable FALSE ENDIF END SELECT ENDIF END SUB ' ******************************************************************************* ' ShowFinish ' This function displays the finish dialog, showing the name of the library to be ' used. ' ' PARAMS: None ' ' RETURNS: ShowIntro AS INTEGER - Integer indicating dialog return value. ' ******************************************************************************* FUNCTION ShowFinish% BEGIN DIALOG OBJECT ShowFinishDialog 290, 180, "Corel VENTURA Library Wizard", SUB ShowFinishDialogEventHandler PUSHBUTTON 181, 160, 46, 14, .FinishButton, "&Finish" CANCELBUTTON 234, 160, 46, 14, .CancelButton PUSHBUTTON 135, 160, 46, 14, .BackButton, "< &Back" IMAGE 10, 10, 75, 130, .ShowFinishImage TEXT 95, 10, 185, 12, .Text1, "The Wizard is now ready to list the items in library:" TEXT 95, 23, 185, 12, .Text2, LIBName$ TEXT 95, 45, 185, 20, .Text3, "Select Finish, then sit back and watch Ventura do your work for you." GROUPBOX 10, 150, 270, 5, .LineGroupBox END DIALOG ShowFinishDialog.SetStyle STYLE_INVISIBLE ShowFinishDialog.ShowFinishImage.SetImage "#LastBMP" ShowFinishDialog.ShowFinishImage.SetStyle STYLE_IMAGE_CENTERED ShowFinishRet% = Dialog(ShowFinishDialog) SELECT CASE ShowFinishRet% CASE DIALOG_RETURN_CANCEL STOP CASE DIALOG_RETURN_NEXT ShowFinishDialog.SetVisible FALSE GetLibInfo ShowFinish = 1 CASE DIALOG_RETURN_BACK ShowFinish = -1 END SELECT END FUNCTION ' ******************************************************************************* ' ShowFinishDialogEventHandler ' This subroutine responds to user interface with the finish 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 ShowFinishDialogEventHandler(BYVAL ControlID%, BYVAL Event%) IF Event% = EVENT_INITIALIZATION THEN ShowFinishDialog.SetStyle STYLE_VISIBLE ENDIF IF Event% = EVENT_MOUSE_CLICK THEN SELECT CASE ControlID% CASE ShowFinishDialog.FinishButton.GetID() ShowFinishDialog.CloseDialog DIALOG_RETURN_NEXT CASE ShowFinishDialog.BackButton.GetID() ShowFinishDialog.CloseDialog DIALOG_RETURN_BACK CASE ShowFinishDialog.CancelButton.GetID() ShowFinishDialog.CloseDialog DIALOG_RETURN_CANCEL END SELECT ENDIF END SUB ' ******************************************************************************* ' GetLibInfo ' This subroutine opens the specified VENTURA library, obtains a list of all ' items contained within the library, and outputs this information to a temporary ' text file. The text file is then imported in to VENTURA, and subsequently ' removed from the Windows temp folder. The library name and total number of ' items are displayed at the start of the pub. ' ' PARAMS: None ' ******************************************************************************* SUB GetLibInfo TempLibFile$ = GETTEMPFOLDER() & "TempLib.txt" OPEN TempLibFile$ FOR APPEND AS 1 BEGINWAITCURSOR WITHOBJECT OBJECT_VENTURA8 .FileLibraryOpen LIBName$ .FileLibraryView FALSE, TRUE 'small icons, show details ItemsInLIB& = .FileLibraryItemCount() PRINT #1, "@Minor Heading = " & LibName$ & CHR(13) & CHR(10) PRINT #1, "@Subheading = " & "Number of items: " & STR(ItemsInLIB&) & CHR(13) & CHR(10) FOR i% = 1 TO ItemsInLIB& .FileLibrarySelectItem i% .FileLibraryItemPropertiesGet ItemName$ PRINT #1, "@Bullet = " & STR(i%) & SPACE(2) & ItemName$ & CHR(13) & CHR(10) NEXT i% .FileLibraryClose TRUE 'close ALL open libs CLOSE 'close temporary text file 'import temporary text file containing library information .SetVisible TRUE .FileNew .FrameFirst TRUE .FileImportText TempLibFile$ END WITHOBJECT KILL TempLibFile$ ENDWAITCURSOR END SUB