home *** CD-ROM | disk | FTP | other *** search
Wrap
REM Parses an EPS File for font and colour information[CorelSCRIPT 8] REM EPSInformation.csc March 13, 1998 REM ⌐ 1998 Corel Corporation. All rights reserved. REM This script parses an EPS file for the plate names and font names. REM For the Colours: REM %%DocumentProcessColors: Cyan Black REM %%DocumentCustomColors: (PANTONE 226 CV) REM For the fonts assumed to be resident on the device: REM %%DocumentNeededResources: font Times-Roman REM For the fonts that have had the font info included: REM %%DocumentSuppliedResources: procset wCorel6Dict REM %%+ font AmericanaXBdCnBT REM %%+ font Times-Roman #addfol "..\..\Scripts" #include "ScpConst.csi" #include "VPConst.csi" #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 GLOBAL CONST LIST_SIZE% = 100 '/////FUNCTION & SUBROUTINE DECLARATIONS///////////////////////////////////////////////// DECLARE SUB RegQuery() DECLARE FUNCTION ShowIntro%() DECLARE FUNCTION GetEPSFile%() DECLARE FUNCTION GetEPSInfo%() DECLARE FUNCTION ShowFinish%() DECLARE FUNCTION SaveToFile(SaveFile$) AS BOOLEAN '/////GLOBAL VARIABLES & CONSTANTS//////////////////////////////////////////////////////// GLOBAL VenturaRoot$ 'Ventura root installation directory from registry GLOBAL EPSFile$ GLOBAL EPSList$(LIST_SIZE) GLOBAL EPSIndex& EPSIndex=0 '/////LOCAL DECLARATIONS////////////////////////////////////////////////////////////////// DIM DialogReturn% DIM NextStep% MAXSTEP% = 4 ' ************************************************************************************** ' MAIN ' ************************************************************************************** ON ERROR GOTO ErrorHandler RegQuery 'get root directory where Ventura is installed SETCURRFOLDER VenturaRoot$ EPSFile$ = "*.eps" NextStep = 1 DO SELECT CASE NextStep CASE 1: DialogReturn = ShowIntro() 'Show Intro dialog CASE 2: DialogReturn = GetEPSFile() ' CASE 3: DialogReturn = GETEPSInfo() ' CASE 4: DialogReturn = ShowFinish() 'Show finish dialog with result of search 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 VentDir$ = REGISTRYQUERY(HKEY_LOCAL_MACHINE,VENTURA_REGQUERY_CONST,"ConfigDir") 'Root directory where Ventura is installed 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 Visual CADD is installed EXIT SUB ErrorHandler: MESSAGE "Error reading registry." ErrNum = 800 END SUB ' ************************************************************************************** ' ShowIntro ' This function displays the introduction dialog. ' ' PARAMS: None ' ' RETURNS: ShowIntro AS INTEGER - Integer indicating dialog return value(user selection) ' ************************************************************************************** FUNCTION ShowIntro% BEGIN DIALOG OBJECT IntroDialog 290, 180, "EPS Information 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 extracts fonts and colors used in Encapsulated Postscript (EPS) files." IMAGE 10, 10, 75, 130, .IntroImage GROUPBOX 10, 150, 270, 5, .LineGroupBox TEXT 95, 40, 185, 20, .Text5, "To begin, 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% = DIALOG_RETURN_NEXT THEN ShowIntro = 1 END FUNCTION ' ************************************************************************************** ' IntroDialogEventHandler ' This subroutine handles events for the Intro 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 in the dialog box ' ************************************************************************************** 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 ' ************************************************************************************** ' GetEPSFile ' This function prompts the user to select an eps file. ' ' RETURNS: GetEPSFile AS INTEGER - Integer indicating dialog return value(user selection) ' ************************************************************************************** FUNCTION GetEPSFile% BEGIN DIALOG OBJECT EPSFileDialog 290, 180, "EPS Information Wizard", SUB EPSFileDialogEventHandler TEXTBOX 95, 29, 185, 13, .EPSFileTextBox PUSHBUTTON 234, 49, 46, 14, .BrowseButton, "&Browse..." PUSHBUTTON 135, 160, 46, 14, .BackButton, "< &Back" PUSHBUTTON 181, 160, 46, 14, .NextButton, "&Process" CANCELBUTTON 234, 160, 46, 14, .CancelButton TEXT 95, 15, 175, 12, .Text2, "Which EPS file would you like to use?" IMAGE 10, 10, 75, 130, .EPSFileImage GROUPBOX 10, 150, 270, 5, .LineGroupBox TEXT 95, 111, 185, 30, .Text3, "Once you have selected an EPS file, click Process to extract the font and color information. This may take several minutes." END DIALOG EPSFileDialog.SetStyle STYLE_INVISIBLE EPSFileDialog.EPSFileImage.SetImage "#Step2BMP" EPSFileDialog.EPSFileImage.SetStyle STYLE_IMAGE_CENTERED EPSFileDialogRet% = Dialog(EPSFileDialog) SELECT CASE EPSFileDialogRet% CASE DIALOG_RETURN_CANCEL STOP CASE DIALOG_RETURN_NEXT GetEPSFile = 1 CASE DIALOG_RETURN_BACK GetEPSFile = -1 END SELECT END FUNCTION ' ************************************************************************************** ' EPSFileDialogEventHandler ' This subroutine handles events for 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 in the dialog box ' ************************************************************************************** SUB EPSFileDialogEventHandler(BYVAL ControlID%, BYVAL Event%) ON ERROR RESUME NEXT IF Event% = EVENT_INITIALIZATION THEN EPSFileDialog.EPSFileTextBox.SetText EPSFile$ pos% = INSTR(EPSFile$, ".") IF pos% = 0 THEN EPSFileDialog.NextButton.Enable FALSE ELSE EPSFileDialog.NextButton.Enable TRUE ENDIF EPSFileDialog.SetStyle STYLE_VISIBLE ENDIF IF Event% = EVENT_CHANGE_IN_CONTENT THEN SELECT CASE ControlID% CASE EPSFileDialog.EPSFileTextBox.GetID() EPSFile$ = EPSFileDialog.EPSFileTextBox.GetText() ' pos% = INSTR(EPSFile$, ".") IF pos% = 0 THEN EPSFileDialog.NextButton.Enable FALSE ELSE EPSFileDialog.NextButton.Enable TRUE ENDIF END SELECT ENDIF IF Event% = EVENT_MOUSE_CLICK THEN SELECT CASE ControlID% CASE EPSFileDialog.NextButton.GetID() OPEN EPSFile$ FOR APPEND AS 1 IF LOF(1) > 0 THEN FileExists = TRUE CLOSE IF FileExists = TRUE THEN EPSFileDialog.closedialog DIALOG_RETURN_NEXT ELSE KILL EPSFile$ MESSAGE "Cannot locate file:" & CHR(13) & EPSFile$ ENDIF CASE EPSFileDialog.BackButton.GetID() EPSFileDialog.closedialog DIALOG_RETURN_BACK CASE EPSFileDialog.CancelButton.GetID() EPSFileDialog.closedialog DIALOG_RETURN_CANCEL CASE EPSFileDialog.BrowseButton.GetID() EPSFile$ = GETFILEBOX("Encapsulated Postscript File (*.eps)|*.eps", "Open File", 0, EPSFile$) IF EPSFile$ <> "" THEN EPSFileDialog.EPSFileTextBox.SetText EPSFile$ EPSFileDialog.NextButton.Enable TRUE ELSE EPSFileDialog.EPSFileTextBox.SetText VenturaRoot$ EPSFileDialog.NextButton.Enable FALSE ENDIF END SELECT ENDIF END SUB ' ************************************************************************************** ' GetEPSInfo ' This function parases the specified eps file for font and color information. ' ' PARAMS: ' ' RETURNS: GetEPSInfo AS INTEGER - Integer indicating dialog return value(user selection) ' ************************************************************************************** FUNCTION GetEPSInfo% BEGINWAITCURSOR ON ERROR GOTO ErrorHandler DIM EndFile AS BOOLEAN NewSize& = LIST_SIZE FOR x%=1 TO EPSIndex& SETEMPTY EPSList$(x%) NEXT x% EPSIndex& = 0 OPEN EPSFile$ FOR INPUT AS 1 seek 1, 33 'ignore first 32 bytes of binary data Count%=0 EndFile=FALSE DO UNTIL EndFile=TRUE 'Get first fields of each line INPUT #1, Section$ IF INSTR(Section$, "%%") <> 0 THEN 'Does string start with %% 'IF section field is valid (ie. one we are looking for), add it to list ValidPColor% = INSTR(Section$, "%%DocumentProcessColors:") 'Does string contain %%DocumentProcessColors: ValidCColor% = INSTR(Section$, "%%DocumentCustomColors:") 'Does string contain %%DocumentCustomColors: ValidNRes% = INSTR(Section$, "%%DocumentNeededResources:") 'Does string contain %%DocumentNeededResources: ValidSRes% = INSTR(Section$, "%%DocumentSuppliedResources:") 'Does string contain %%DocumentSuppliedResources: ValidFont% = INSTR(Section$, "%%+ font:", 0) 'Does string contain %%+ font: IF ValidPColor% <> 0 OR ValidCColor% <> 0 OR ValidNRes% <> 0 OR ValidSRes% <> 0 OR ValidFont% <> 0 THEN 'String is valid EPSIndex = EPSIndex& + 1 IF EPSIndex& MOD 100 = 0 THEN NewSize& = NewSize& + LIST_SIZE REDIM PRESERVE EPSList$(NewSize&) ENDIF EPSList$(EPSIndex&) = RIGHT(Section$, LEN(Section$)-2) ENDIF Count = Count+1 ENDIF FileEnd% = INSTR(Section, "*", 0) OR INSTR(Section, "EOF") 'Does string contain * IF FileEnd <>0 THEN 'File End found EndFile=TRUE ENDIF LOOP CLOSE(1) GetEPSInfo=1 ENDWAITCURSOR EXIT FUNCTION ErrorHandler: SELECT CASE ErrNum CASE 200 TO 205 MESSAGE "ERROR. Unable to open file: " & CHR(13) & EPSFile$ RESUME AT FunctionEnd CASE ELSE MESSAGE STR(ErrNum) RESUME NEXT END SELECT FunctionEnd: GetEPSInfo=-1 'go back to previous dialog END FUNCTION ' ************************************************************************************** ' ShowFinish ' This function displays the font and color information for the specified eps file. ' The user is given the option of saving the information to a text file. ' ' PARAMS: None ' ' RETURNS: ShowFinish AS INTEGER - Integer indicating dialog return value(user selection) ' ************************************************************************************** FUNCTION ShowFinish% EPSSize%=LEN(EPSFile$) TXTSize% = LEN("EPS") TXTFile$ = LEFT(EPSFile$, EPSSize-TXTSize) & "TXT" BEGIN DIALOG OBJECT ShowFinishDialog 290, 180, "EPS Information Wizard", SUB ShowFinishDialogEventHandler PUSHBUTTON 135, 160, 46, 14, .BackButton, "< &Back" PUSHBUTTON 181, 160, 46, 14, .FinishButton, "&Finish" CANCELBUTTON 234, 160, 46, 14, .CancelButton IMAGE 10, 10, 75, 130, .ShowFinishImage GROUPBOX 10, 150, 270, 5, .LineGroupBox TEXT 95, 10, 185, 12, .Text2, "Here is the information extracted from the file:" PUSHBUTTON 234, 130, 46, 14, .SaveButton, "&Save" LISTBOX 95, 39, 185, 80, .InfoListBox TEXT 95, 125, 129, 19, .Text4, "To save the information to a text file, click Save." TEXT 95, 23, 185, 12, .Text3, EPSFile$ 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 ShowFinish = 1 CASE DIALOG_RETURN_BACK ShowFinish = -2 END SELECT END FUNCTION ' ************************************************************************************** ' ShowFinishDialogEventHandler ' This subroutine handles events for 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 in the dialog box ' ************************************************************************************** SUB ShowFinishDialogEventHandler(BYVAL ControlID%, BYVAL Event%) IF Event% = EVENT_INITIALIZATION THEN ShowFinishDialog.SetStyle STYLE_VISIBLE ShowFinishDialog.InfoListBox.SetArray EPSList$ ShowFinishDialog.CancelButton.Enable FALSE 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 CASE ShowFinishDialog.SaveButton.GetID() SaveFile$ = GETFILEBOX("Text files (*.txt)|*.txt", "Save As", 1, "EPSInfo.txt", "txt", VenturaRoot$) IF SaveFile <> "" THEN SaveStatus = SaveToFile(SaveFile$) IF SaveStatus = TRUE THEN MESSAGE "Save successful" ELSE MESSAGE "Unable to save to " & CHR(13) & SaveFile$ ENDIF ENDIF END SELECT ENDIF END SUB ' ************************************************************************************** ' SaveToFile ' This function saves the extracted eps information to a text file. ' ' RETURNS: SaveToFile AS INTEGER - Integer indicating dialog return value(user selection) ' ************************************************************************************** FUNCTION SaveToFile(SaveFile$) AS BOOLEAN ON ERROR GOTO ErrorHandler CLOSE OPEN SaveFile$ FOR OUTPUT AS 1 PRINT #1, EPSFile$ FOR i%=1 TO EPSIndex& PRINT #1, EPSList(i%) NEXT i% CLOSE(1) SaveToFile = TRUE EXIT FUNCTION ErrorHandler: CLOSE SaveToFile = FALSE END FUNCTION