home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
Computer Buyer 1998 October
/
dpcb1098.iso
/
Business
/
Ventura
/
Ventura
/
Scripts
/
UnSpace.csc
< prev
next >
Wrap
Text File
|
1998-07-07
|
9KB
|
269 lines
REM Removes double spaces [CorelSCRIPT 8]
REM UnSpace.csc March, 1998
REM ⌐ 1998 Corel Corporation. All rights reserved.
REM **************************************************************************************
REM This script replaces every instance of a double space with a single space.
REM You need an open publication to run this script.
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"
'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 ShowFinish%()
DECLARE FUNCTION RemoveSpaces%()
'/////GLOBAL VARIABLES //////////////////////////////////////////////////////////
GLOBAL VenturaRoot$ 'root directory where Ventura is installed
'////// 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
'this section controls traversal through the dialog pages
NextStep% = 1
DO
SELECT CASE NextStep%
CASE 1: DialogReturn% = ShowIntro()
CASE 2: DialogReturn% = RemoveSpaces()
CASE 3: DialogReturn% = ShowFinish()
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
' *******************************************************************************
' 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, "Ventura Space Remover", 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 removes all double spaces from your publication."
TEXT 95, 40, 185, 12, .Text3, "To begin removing spaces, click Next."
IMAGE 10, 10, 75, 130, .IntroImage
GROUPBOX 10, 150, 270, 5, .LineGroupBox
END DIALOG
IntroDialog.SetStyle STYLE_INVISIBLE
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 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
IntroDialog.SetStyle STYLE_VISIBLE
ENDIF
IF Event% = EVENT_MOUSE_CLICK THEN
SELECT CASE ControlID%
CASE IntroDialog.NextButton.GetID()
BEGINWAITCURSOR
WITHOBJECT OBJECT_VENTURA8
ENDWAITCURSOR
'Make sure there is an open pub
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
IntroDialog.closedialog DIALOG_RETURN_NEXT
ENDIF
ELSE
'STOP
ENDIF
ELSE
IntroDialog.closedialog DIALOG_RETURN_NEXT
ENDIF
END WITHOBJECT
' IntroDialog.CloseDialog DIALOG_RETURN_NEXT
CASE IntroDialog.CancelButton.GetID()
IntroDialog.CloseDialog DIALOG_RETURN_CANCEL
END SELECT
ENDIF
END SUB
' *******************************************************************************
' RemoveSpaces
' This function removes all double spaces in the active publication.
'
' PARAMS: None
'
' RETURNS: RemoveSpaces AS INTEGER - Integer indicating dialog return value.
' *******************************************************************************
FUNCTION RemoveSpaces%
ON ERROR GOTO ErrorHandler
DIM Found AS BOOLEAN
WITHOBJECT OBJECT_VENTURA8
.PageFirstLine
.EditInitFindText SPACE(2), SPACE(1)
DO
.EditReplace TRUE
Found = .EditFindText()
LOOP UNTIL Found = FALSE
RemoveSpaces = 1
ExitFunction:
END WITHOBJECT
EXIT FUNCTION
ErrorHandler:
RESUME AT ExitFunction
END FUNCTION
' *******************************************************************************
' ShowFinish
' This function displays the finish dialog.
'
' PARAMS:None
'
' RETURNS: ShowFinish AS INTEGER - Integer indicating dialog return value.
' *******************************************************************************
FUNCTION ShowFinish%
BEGIN DIALOG OBJECT FinishDialog 290, 180, "Ventura Space Remover", SUB FinishDialogEventHandler
PUSHBUTTON 181, 160, 46, 14, .NextButton, "&Done"
CANCELBUTTON 234, 160, 46, 14, .CancelButton
PUSHBUTTON 135, 160, 46, 14, .BackButton, "< &Back"
TEXT 95, 10, 185, 12, .Text1, "All double spaces have been removed."
TEXT 95, 30, 185, 12, .Text2, "To run this wizard again, click Back."
TEXT 95, 50, 185, 12, .Text3, "To exit, click Done."
IMAGE 10, 10, 75, 130, .FinishImage
GROUPBOX 10, 150, 270, 5, .LineGroupBox
END DIALOG
FinishDialog.SetStyle STYLE_INVISIBLE
FinishDialog.FinishImage.SetImage "#LastBMP"
FinishDialog.FinishImage.SetStyle STYLE_IMAGE_CENTERED
FinishRet%=DIALOG(FinishDialog)
SELECT CASE FinishRet%
CASE DIALOG_RETURN_CANCEL
STOP
CASE DIALOG_RETURN_NEXT
ShowFinish = 1
CASE DIALOG_RETURN_BACK
ShowFinish = -2
END SELECT
END FUNCTION
' *******************************************************************************
' FinishDialogEventHandler
' 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.
' *******************************************************************************
SUB FinishDialogEventHandler(BYVAL ControlID%, BYVAL Event%)
IF Event% = EVENT_INITIALIZATION THEN
FinishDialog.SetStyle STYLE_VISIBLE
FinishDialog.CancelButton.Enable FALSE
ENDIF
IF Event% = EVENT_MOUSE_CLICK THEN
SELECT CASE ControlID%
CASE FinishDialog.NextButton.GetID()
FinishDialog.CloseDialog DIALOG_RETURN_NEXT
CASE FinishDialog.BackButton.GetID()
FinishDialog.CloseDialog DIALOG_RETURN_BACK
CASE FinishDialog.CancelButton.GetID()
FinishDialog.CloseDialog DIALOG_RETURN_CANCEL
END SELECT
ENDIF
END SUB