home *** CD-ROM | disk | FTP | other *** search
- REM Prints a list of all files in publication [CorelSCRIPT 8]
- REM FileList.csc March, 1998
- REM ⌐ 1998 Corel Corporation. All rights reserved.
-
- REM **************************************************************************************
- REM This script prints a list of all the files contained in the current publication.
- REM The information is displayed in a new 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"
-
- '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 SUB ShowIntro()
- DECLARE SUB GetFiles(FileName$)
- DECLARE SUB PrintFiles(FileName$)
- DECLARE FUNCTION GetCurrentPub$()
-
- '/////GLOBAL VARIABLES //////////////////////////////////////////////////////////
- GLOBAL VenturaRoot$ 'root directory where Ventura is installed
-
-
- '///// MAIN ////////////////////////////////////////////////////
- RegQuery 'get root directory where Ventura is installed
- ShowIntro 'display introduction dialog
- TempFolder$ = GETTEMPFOLDER() 'get Windows temporary folder
- TempFile$ = TempFolder$ & "FileList.txt" 'temporary file containing file list information
- PubName$ = GetCurrentPub$() 'get name of active publication
- GetFiles(TempFile$) 'get a list of all files in current pub and write to a temporary file
- PrintFiles(TempFile$) 'import temporary file to a new VENTURA publication
- KILL TempFile$ 'remove temporary file
-
-
- ' *******************************************************************************
- ' 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
-
-
- ' *********************************************************************************
- ' GetFiles
- ' This subroutine creates a list of all files (in all chapters) in the current
- ' VENTURA publication and writes the information to a temporary text file
- ' specified by FileName$.
- '
- ' PARAMS: FileName$ - name of temporary text file containing file list information.
- ' *********************************************************************************
- SUB GetFiles(FileName$)
- OPEN FileName$ FOR OUTPUT AS 1
- 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
- PRINT #1, "@Minor Heading = " & CurChapter$
- 'get all text files in current chapter
- NumberOfTextFiles& = .TextFileCount()
- FOR j% = 1 TO NumberOfTextFiles&
- CurFile$ = .TextFileGetAt(j%)
- PRINT #1,
- PRINT #1, "@Bullet = " & CurFile$
- NEXT j%
- 'get all picture files in current chapter
- NumberOfPictureFiles& = .PictureFileCount()
- FOR j% = 1 TO NumberOfPictureFiles&
- CurFile$ = .PictureFileGetAt(j%)
- PRINT #1,
- PRINT #1, "@Bullet = " & CurFile$
- NEXT j%
- PRINT #1,
- NEXT i%
- END WITHOBJECT
- ENDWAITCURSOR
- CLOSE(1)
- END SUB
-
- ' *******************************************************************************
- ' PrintFiles
- ' This subroutine imports the text file containing the file list information into
- ' a new VENTURA publication.
- '
- ' PARAMS: FileName$ - name of text file to be imported.
- ' *******************************************************************************
- SUB PrintFiles(FileName$)
- BEGINWAITCURSOR
- WITHOBJECT OBJECT_VENTURA8
- .FileNew
- .FrameFirst TRUE
- .FileImportText FileName$
- END WITHOBJECT
- ENDWAITCURSOR
- END SUB
-
-
-
- ' *******************************************************************************
- ' ShowIntro
- ' This subroutine displays the introduction dialog.
- '
- ' PARAMS: None
- ' *******************************************************************************
- SUB ShowIntro
- BEGIN DIALOG OBJECT IntroDialog 290, 180, "File List Wizard", SUB IntroDialogEventHandler
- PUSHBUTTON 181, 160, 46, 14, .NextButton, "&List Files"
- CANCELBUTTON 234, 160, 46, 14, .CancelButton
- PUSHBUTTON 135, 160, 46, 14, .BackButton, "< &Back"
- TEXT 95, 10, 189, 20, .Text2, "This Wizard will create a list of all files within each chapter in the current publication."
- IMAGE 10, 10, 75, 130, .IntroImage
- GROUPBOX 10, 150, 270, 5, .LineGroupBox
- TEXT 95, 35, 185, 15, .Text5, "To create the file list, click List Files."
- END DIALOG
-
- IntroDialog.IntroImage.SetImage "#IntroBMP"
- IntroDialog.IntroImage.SetStyle STYLE_IMAGE_CENTERED
-
- IntroRet%=DIALOG(IntroDialog)
- IF IntroRet% = DIALOG_RETURN_CANCEL THEN STOP
- END SUB
-
-
- ' *******************************************************************************
- ' 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 SUB
-
-