home *** CD-ROM | disk | FTP | other *** search
- REM Prints a list of all accelerator keys [CorelSCRIPT 8]
- REM KeyboardShortcuts.csc March, 1998
- REM ⌐ 1998 Corel Corporation. All rights reserved.
-
- REM *****************************************************************************
- REM This script outputs a listing of all Ventura's accelerator keys in a
- REM formatted Ventura publication.
- REM The list is written to a temporary file, then imported into Ventura.
- REM The user can cancel the operation at any time - the script will complete
- REM the listing in progress, then display the partial listing with a message
- REM indicating the script was terminated at the user's request.
- 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 LastBMP "Bitmaps\LastBMP.bmp"
- #ADDRESBMP FullPageBMP "Bitmaps\FullPage.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 ShowProgress()
- DECLARE SUB ListingSub(BYVAL MenuIndexValue&)
- DECLARE SUB ProgressDialogEventHandler(BYVAL ControlID%, BYVAL Event%)
- DECLARE SUB Initialize()
-
- '/////GLOBAL VARIABLES //////////////////////////////////////////////////////////
- GLOBAL VenturaRoot$ 'root directory where Ventura is installed
- GLOBAL MenuCount& 'number of menus for which to obtain accelerator keys
- GLOBAL MenuIndex& 'index referencing the menu being queried
- GLOBAL MenuString$ 'expression displayed in progess dialog indicating the name of the menu being queried
- GLOBAL MenuName$ 'name of the menu in question
- GLOBAL ShowFinish AS BOOLEAN 'flag used to open/close progress indicator
- GLOBAL TempFile$ 'temporary file containing the list of accelerator keys
-
-
- ' *******************************************************************************
- ' MAIN
- ' *******************************************************************************
- ON ERROR GOTO ErrorHandler
-
- RegQuery 'get root directory where Ventura is installed
- ShowIntro 'display introduction dialog
- TempFile$ = GETTEMPFOLDER() & "AccelTmp.txt" 'temporary file containing accelerator information
- MenuString$ = "Writing keyboard accelerators...." 'initialize Menu string to first message
- ShowProgress 'display progress dialog
- KILL TempFile$ 'remove temporary file
-
- STOP
-
- ErrorHandler:
- KILL TempFile$ 'remove temporary file
- SELECT CASE ErrNum
- CASE 302
- RESUME NEXT
- CASE ELSE
- MESSAGE "FATAL ERROR " & STR(ErrNum) & CHR(13) & "Script will now exit"
- STOP
- 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
-
-
- ' *******************************************************************************
- ' ShowIntro
- ' This subroutine displays the introduction dialog.
- '
- ' PARAMS: None
- ' *******************************************************************************
- SUB ShowIntro
- BEGIN DIALOG OBJECT IntroDialog 290, 180, "Keyboard Accelerators 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 produces a list of all keyboard accelerator keys."
- TEXT 95, 40, 185, 18, .Text3, "To begin listing accelerator keys, click Next."
- IMAGE 10, 10, 75, 130, .IntroImage
- GROUPBOX 10, 150, 270, 5, .LineGroupBox
- 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
- IF ShowFinish = TRUE THEN IntroDialog.CancelButton.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
-
-
-
- ' *******************************************************************************
- ' ShowProgress
- ' This function displays a progress bar indicating the progress of the operation.
- '
- ' PARAMS: None
- '
- ' RETURNS: ShowProgress AS INTEGER - Integer indicating dialog return value.
- ' *******************************************************************************
- SUB ShowProgress
- BEGIN DIALOG OBJECT ProgressDialog 260, 60, "Custom Keyboard Accelerators", SUB ProgressDialogEventHandler
- CANCELBUTTON 203, 42, 46, 16, .CancelButton
- PROGRESS 54, 28, 195, 8, .Progress1
- IMAGE 9, 8, 34, 30, .ProgressImage
- TEXT 57, 12, 190, 12, .ProgressText, MenuString$
- END DIALOG
-
- ProgressDialog.SetTimer(1)
- ProgressDialog.Progress1.SetMinRange(1)
- ProgressDialog.Progress1.SetMaxRange(1200)
- ProgressDialog.Progress1.SetIncrement(1)
- ProgressDialog.Progress1.SetValue(2)
- ProgressDialog.ProgressImage.SetImage "#FullPageBMP"
- ProgressDialog.ProgressText.SetText MenuString$
- ProgressDialog.ProgressText.SetStyle STYLE_SUNKEN
- MenuIndex& = 1
-
- IntroDialog.IntroImage.SetImage "#LastBMP"
- IntroDialog.NextButton.SetText "Exit"
-
- ProgressDialogRet% = DIALOG(ProgressDialog)
- IF ProgressDialogRet% = DIALOG_RETURN_CANCEL THEN
- IntroDialog.Text2.SetText "Wizard has been terminated at the user's request."
- IntroDialog.Text3.SetText "Listing is incomplete."
- ELSE
- IntroDialog.Text2.SetText "Wizard has completed successfully"
- IntroDialog.Text3.SetText "Listing is complete."
- ENDIF
- ShowFinish = TRUE
- WITHOBJECT OBJECT_VENTURA8
- .FileNew
- .FrameFirst TRUE
- .FileImportText TempFile$
- END WITHOBJECT
-
- IntroRet% = DIALOG(IntroDialog)
- IF IntroRet% = DIALOG_RETURN_CANCEL THEN STOP
- END FUNCTION
-
-
- ' *******************************************************************************
- ' ProgressDialogEventHandler
- ' This subroutine responds to user interface with the progress dialog.
- '
- ' PARAMS: ControlID% - identifies which dialog control to respond to.
- ' Event% - identifies which event to respond to (ie. mouse click, etc.).
- ' *******************************************************************************
- SUB ProgressDialogEventHandler(BYVAL ControlID%, BYVAL Event%)
- IF Event% = EVENT_INITIALIZATION THEN
- Initialize
- ENDIF
-
- IF Event% = EVENT_MOUSE_CLICK THEN
- IF ControlID% = ProgressDialog.CancelButton.GetID() THEN ProgressDialog.CloseDialog(DIALOG_RETURN_CANCEL)
- ENDIF
-
- IF Event = EVENT_TIMER_EVENT THEN
- ListingSub MenuIndex
- ENDIF
- END SUB
-
-
- ' *******************************************************************************
- ' Initialize
- ' This subroutine creates a new publication and sets paragraph tags.
- '
- ' PARAMS: None
- ' *******************************************************************************
- SUB Initialize
- ON ERROR GOTO ErrorHandler
- BEGINWAITCURSOR
- WITHOBJECT OBJECT_VENTURA8
- ENDWAITCURSOR
- .SetVisible TRUE
- MenuCount& = .CustomGetMenuCount()
- END WITHOBJECT
- EXIT SUB
- ErrorHandler:
- MESSAGE "ERROR: " & STR(ErrNum) & CHR(13) & "Could not format paragraph tags."
- ErrNum = 800
- END SUB
-
-
- ' *******************************************************************************
- ' ListingSub
- ' This subroutine lists the accelerator keys for each menu.
- '
- ' PARAMS: MenuIndexValue& - The index identifying the menu for which to print
- ' accelerator keys.
- ' *******************************************************************************
- SUB ListingSub(BYVAL MenuIndexValue&)
- IF MenuIndex& > MenuCount& THEN
- ProgressDialog.CloseDialog(1)
- ELSE
- OPEN TempFile$ FOR APPEND AS 1
- WITHOBJECT OBJECT_VENTURA8
-
- 'list menu title - formatting with Minor Heading tag
- .CustomGetMenuAt MenuIndex&, MenuName$, CmdCount&
- MenuString$ = "Accelerators for " & MenuName$ & " Menu"
- ProgressDialog.ProgressText.SetText MenuString$
- PRINT #1, "@Minor Heading = " & MenuString$
-
- 'list each menu item and its accelerator key - formatting with Bullet tag
- CmdIndex& = 1
- DO WHILE CmdIndex& <= CmdCount&
- .CustomGetCommandAt MenuIndex&, CmdIndex&, CmdName$, Accel$
- IF CmdName$ = "" THEN
- CmdString$ = "----------------" & CHR(13) & CHR(10)
- ELSE
- CmdString$ = CmdName$ & CHR(9) & " [" & Accel$ & "]" & CHR(13) & CHR(10)
- ENDIF
- PRINT #1,
- PRINT #1, "@Bullet = " & CmdString$
- CmdIndex& = CmdIndex& + 1
- ProgressDialog.Progress1.step
- LOOP
- MenuIndex& = MenuIndex& + 1
- PRINT #1,
- END WITHOBJECT
- CLOSE(1)
- ENDIF
- END SUB
-
-