home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
PC World Komputer 1998 October A
/
Pcwk10a98.iso
/
Corel
/
Ventura8
/
Ventura
/
Scripts
/
HyphenationEditor.csc
< prev
next >
Wrap
Text File
|
1998-07-08
|
12KB
|
321 lines
REM Edits the Hyphenation Exception List[CorelSCRIPT 8]
REM HyphenationEditor.csc February 4, 1998
REM ⌐ 1998 Corel Corporation. All rights reserved.
REM *****************************************************************************
REM This script helps edit the VENTURA Hyphenation Exception List (HyphUser.dic).
REM VENTURA must be closed in order for the edit to take effect.
REM Note - This script can be compiled as an executable, then launched from
REM Explorer or a shortcut on the desktop.
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 Step2BMP "Bitmaps\Step2BMP.bmp"
#ADDRESBMP Step3BMP "Bitmaps\Step3BMP.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 FUNCTION FindWindow LIB "user32" (BYVAL lpClassName AS STRING, BYVAL lpWindowName AS LONG) AS LONG ALIAS "FindWindowA"
DECLARE SUB RegQuery()
DECLARE FUNCTION GetEditOption%()
DECLARE FUNCTION GetEdit%()
DECLARE FUNCTION PerformEdit%()
DECLARE FUNCTION IsVPRunning() AS BOOLEAN
'/////GLOBAL VARIABLES & CONSTANTS////////////////////////////////////////////////////////
GLOBAL VenturaRoot$ 'root directory where Ventura is
GLOBAL HyphFile$ 'name of hyphenation exception list file to edit
GLOBAL TempFile$ 'temporary file containing edit information
'/////LOCAL DECLARATIONS//////////////////////////////////////////////////////////////////
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
TempFile$ = GETTEMPFOLDER() & "DictTemp.txt" 'temporary file to hold dictionary information
HyphFile$ = VenturaRoot$ & "\Ventura\HyphUser.dic" 'name of file containing hyphenation exception list
'this section controls traversal throught the Wizard pages
NextStep% = 1
DO
SELECT CASE NextStep%
CASE 1: DialogReturn% = GetEditOption() 'prompt user for type of edit
CASE 2: DialogReturn% = GetEdit() 'prompt user for edit information
CASE 3: DialogReturn% = PerformEdit() 'write edit information to dictionary file
END SELECT
NextStep% = NextStep% + DialogReturn%
LOOP UNTIL NextStep% = MAXSTEP + 1
ExitScript:
STOP
ErrorHandler:
SELECT CASE ErrNum
CLOSE
KILL TempFile$
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 .
' *******************************************************************************
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
EXIT SUB
ErrorHandler:
MESSAGE "Error reading registry:" & CHR(13) & RegString$
ErrNum = 800
END SUB
' *******************************************************************************
' IsVPRunning
' This function checks to see if Ventura is running.
'
' PARAMS: None
'
' RETURNS: IsVPRunning AS BOOLEAN - TRUE if Ventura is running; otherwise FALSE.
' *******************************************************************************
FUNCTION IsVPRunning() AS BOOLEAN
WinCount& = FindWindow("Ventura 8.0", 0)
IF WinCount& <> 0 THEN
IsVPRunning = TRUE
ELSE
IsVPRunning = FALSE
ENDIF
END FUNCTION
' *******************************************************************************
' GetEditOption
' This function ensures that VENTURA is not running before beginning the edit.
' If VENTURA is running, the user is advised to close it before proceeding.
'
' PARAMS: None
'
' RETURNS: ShowProgress AS INTEGER - Integer indicating dialog return value.
' *******************************************************************************
FUNCTION GetEditOption%
BEGIN DIALOG OBJECT GetEditOptionDialog 290, 180, "Hyphenation Exception List Editor", SUB GetEditOptionDialogEventHandler
PUSHBUTTON 181, 160, 46, 14, .NextButton, "&Next >"
CANCELBUTTON 234, 160, 46, 14, .CancelButton
PUSHBUTTON 135, 160, 46, 14, .BackButton, "< &Back"
TEXT 95, 12, 185, 20, .Text3, "This wizard helps you edit the Hyphenation Exception List."
GROUPBOX 10, 150, 270, 5, .LineGroupBox
IMAGE 10, 10, 75, 130, .GetEditOptionImage
TEXT 95, 30, 185, 40, .Text4, "To begin, click Next."
TEXT 94, 125, 188, 20, .Text5, "NOTE: Ensure that VENTURA is closed before proceeding."
END DIALOG
GetEditOptionDialog.GetEditOptionImage.SetImage "#Step2BMP"
GetEditOptionDialog.GetEditOptionImage.SetStyle STYLE_IMAGE_CENTERED
GetEditOptionDialog.SetStyle STYLE_VISIBLE
GetEditOptionRet% = Dialog(GetEditOptionDialog)
SELECT CASE GetEditOptionRet%
CASE DIALOG_RETURN_CANCEL
STOP
CASE DIALOG_RETURN_NEXT
GetEditOptionDialog.SetVisible FALSE
COPY HyphFile$, TempFile$, 0
GetEditOption = 1
END SELECT
END FUNCTION
' *******************************************************************************
' GetEditOptionDialogEventHandler
' This subroutine responds to user interface with the get edit option 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 GetEditOptionDialogEventHandler(BYVAL ControlID%, BYVAL Event%)
IF Event% = EVENT_INITIALIZATION THEN
GetEditOptionDialog.Text4.SetVisible TRUE
GetEditOptionDialog.BackButton.Enable FALSE
GetEditOptionDialog.Text5.SetVisible FALSE
'IF Ventura is running, prompt user to close the app before continuing.
IF IsVPRunning() = TRUE THEN
GetEditOptionDialog.Text3.SetText "You cannot run this script when VENTURA is open."
GetEditOptionDialog.Text4.SetText "To run this script, close VENTURA, navigate to the VENTURA\SCRIPTS folder, and double-click HyphenationEditor.CSC."
GetEditOptionDialog.NextButton.Enable FALSE
EXIT SUB
ENDIF
ENDIF
IF Event% = EVENT_MOUSE_CLICK THEN
SELECT CASE ControlID
CASE GetEditOptionDialog.NextButton.GetID()
GetEditOptionDialog.closedialog DIALOG_RETURN_NEXT
CASE GetEditOptionDialog.CancelButton.GetID()
GetEditOptionDialog.closedialog DIALOG_RETURN_CANCEL
END SELECT
ENDIF
END SUB
' *******************************************************************************
' GetEdit
' This function displays the contents of the user selected dictionary, and prompts
' the user to add or delete words. The changes are written to the dictionary file
' when the user selects the 'Save Edit' button.
' The list is sorted alphabetically.
'
' PARAMS: None
'
' RETURNS: GetEdit AS INTEGER - Integer indicating dialog return value.
' *******************************************************************************
FUNCTION GetEdit%
BEGIN DIALOG OBJECT GetEditDialog 290, 180, "Hyphenation Exception List Editor", SUB GetEditDialogEventHandler
TEXTBOX 95, 46, 130, 14, .EditTextBox
PUSHBUTTON 233, 47, 46, 14, .AcceptPushButton, "&Accept"
LISTBOX 95, 66, 185, 59, .EditListBox
PUSHBUTTON 135, 160, 46, 14, .BackButton, "< &Back"
PUSHBUTTON 181, 160, 46, 14, .NextButton, "&Save Edit"
CANCELBUTTON 234, 160, 46, 14, .CancelButton
TEXT 95, 3, 185, 18, .Text2, "To add a new word to the exception list, type the word in the text box and click Accept."
GROUPBOX 10, 150, 270, 5, .LineGroupBox
TEXT 130, 130, 150, 12, .StatusText, ""
TEXT 95, 130, 28, 12, .Text8, "Editing:"
IMAGE 10, 10, 75, 130, .GetEditImage
TEXT 94, 21, 184, 19, .Text4, "To edit an existing entry, double-click the word, make the necessary changes in the text box, and click Accept."
END DIALOG
GetEditDialog.GetEditImage.SetImage "#Step3BMP"
GetEditDialog.GetEditImage.SetStyle STYLE_IMAGE_CENTERED
GetEditDialog.EditListBox.SetStyle STYLE_SORTING 'sort list alphabetically
GetEditDialog.StatusText.SetStyle STYLE_SUNKEN
GetEditRet% = DIALOG(GetEditDialog)
SELECT CASE GetEditRet%
CASE DIALOG_RETURN_CANCEL
KILL TempFile$
STOP
CASE DIALOG_RETURN_NEXT
GetEdit = 1
CASE DIALOG_RETURN_BACK
KILL TempFile$
GetEdit = -1
END SELECT
END FUNCTION
' *******************************************************************************
' GetEditDialogEventHandler
' This subroutine responds to user interface with the Get Edit dialog.
'
' PARAMS: ControlID% - identifies which dialog control to respond to.
' Event% - identifies which event to respond to (ie. mouse click, etc.).
' *******************************************************************************
SUB GetEditDialogEventHandler(BYVAL ControlID%, BYVAL Event%)
IF Event% = EVENT_INITIALIZATION THEN
GetEditDialog.EditTextBox.SetText ""
GetEditDialog.StatusText.SetText HyphFile$
OPEN TempFile$ FOR INPUT AS 1
WHILE NOT EOF(1)
LINE INPUT #1, Word$
GetEditDialog.EditListBox.AddItem Word$
WEND
CLOSE
ENDIF
IF Event% = EVENT_MOUSE_CLICK THEN
SELECT CASE ControlID%
CASE GetEditDialog.NextButton.GetID()
ItemCount& = GetEditDialog.EditListBox.GetItemCount()
OPEN TempFile$ FOR OUTPUT AS 2
FOR i% = 1 TO ItemCount&
Word$ = GetEditDialog.EditListBox.GetItem(i%)
PRINT #2, Word
NEXT i%
CLOSE
GetEditDialog.closedialog DIALOG_RETURN_NEXT
CASE GetEditDialog.BackButton.GetID()
GetEditDialog.closedialog DIALOG_RETURN_BACK
CASE GetEditDialog.CancelButton.GetID()
GetEditDialog.closedialog DIALOG_RETURN_CANCEL
CASE GetEditDialog.AcceptPushButton.GetID()
Entry$ = LCASE(GetEditDialog.EditTextBox.GetText()) 'need to convert to lowercase as algorithm requires this
IF Entry$ <> "" THEN GetEditDialog.EditListBox.AddItem Entry$
GetEditDialog.EditTextBox.SetText ""
END SELECT
ENDIF
IF Event% = EVENT_DBL_MOUSE_CLICK THEN
SELECT CASE ControlID%
CASE GetEditDialog.EditListBox.GetID()
indx% = GetEditDialog.EditListBox.GetSelect()
GetEditDialog.EditTextBox.SetText GetEditDialog.EditListBox.GetItem(indx%)
GetEditDialog.EditListBox.RemoveItem indx%
END SELECT
ENDIF
END SUB
' *******************************************************************************
' PerformEdit
' This function saves the edit to the original dictionary file.
' A message is displayed indicating the success/failure of the operation.
'
' PARAMS: None
' *******************************************************************************
FUNCTION PerformEdit%
CopyStatus = COPY(TempFile$, HyphFile$, 0)
IF CopyStatus = TRUE THEN
MESSAGE "Your edit was successful."
ELSE
MESSAGE "Your edit was not successful."
ENDIF
KILL TempFile$
PerformEdit% = 1
END FUNCTION