home *** CD-ROM | disk | FTP | other *** search
- REM Resizes selected objects [CorelSCRIPT 8]
- REM ResizeObjects.csc March, 1998
- REM ⌐ 1998 Corel Corporation. All rights reserved.
-
- REM **************************************************************************************
- REM This script resizes the selected object or group of objects.
- REM An object(s) must be selected (message appears if no selection).
- REM Objects cannot be resized off the page.
- REM User is informed of an invalid selection (ie. master page, text, etc.).
- 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
-
- 'Constants for setting aspect ratio
- GLOBAL CONST SEPARATE_ASPECT% = 0
- GLOBAL CONST MAINTAIN_ASPECT% = 1
-
- '/////FUNCTION & SUBROUTINE DECLARATIONS/////////////////////////////////////////
- DECLARE SUB RegQuery()
- DECLARE SUB GetResizeInfo()
- DECLARE SUB Resize()
-
- '/////GLOBAL VARIABLES //////////////////////////////////////////////////////////
- GLOBAL VenturaRoot$ 'root directory where Ventura is installed
- GLOBAL AspectRatio& 'specifies whether to maintain aspect ratio: 0-separate aspect ratio; 1-maintain aspect ratio
- GLOBAL HorizontalResize& 'specifies the amount to scale the object horizontally
- GLOBAL VerticalResize& 'specifies the amount to scale the object vertically
-
-
- ' **************************************************************************************
- ' MAIN
- ' **************************************************************************************
- ON ERROR GOTO ErrorHandler
-
- RegQuery 'get root directory where Ventura is installed
- GetResizeInfo 'get size of selected object and resize as required
-
- 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
-
-
- ' *******************************************************************************
- ' GetResizeInfo
- ' This function prompts the user for resizing information.
- '
- ' PARAMS: None
- ' *******************************************************************************
- SUB GetResizeInfo
- BEGIN DIALOG OBJECT GetResizeInfoDialog 290, 180, "Object Resizer", SUB GetResizeInfoDialogEventHandler
- PUSHBUTTON 181, 160, 46, 14, .NextButton, "&Apply"
- CANCELBUTTON 234, 160, 46, 14, .CancelButton
- PUSHBUTTON 135, 160, 46, 14, .BackButton, "< &Back"
- TEXT 95, 10, 185, 12, .Text1, "This wizard resizes the selected object(s)."
- IMAGE 10, 10, 75, 130, .GetResizeInfoImage
- GROUPBOX 10, 150, 270, 5, .LineGroupBox
- GROUPBOX 95, 27, 185, 55, .GroupBox2, "Resize:"
- TEXT 222, 40, 10, 11, .Text6, "%"
- TEXT 222, 61, 10, 11, .Text7, "%"
- TEXT 115, 40, 50, 12, .Text5, "&Horizontal:"
- SPINCONTROL 174, 39, 40, 12, .HorizontalSpinControl
- TEXT 116, 61, 50, 12, .Text4, "&Vertical:"
- SPINCONTROL 174, 59, 40, 12, .VerticalSpinControl
- CHECKBOX 99, 93, 94, 11, .MaintainAspectCheckBox, "&Maintain aspect ratio"
- TEXT 95, 117, 185, 10, .Text8, "Positive values increase the size of the object(s)."
- TEXT 95, 129, 185, 9, .Text9, "Negative values decrease the size of the object(s)."
- END DIALOG
-
- GetResizeInfoDialog.SetStyle STYLE_INVISIBLE
- GetResizeInfoDialog.GetResizeInfoImage.SetImage "#IntroBMP"
- GetResizeInfoDialog.GetResizeInfoImage.SetStyle STYLE_IMAGE_CENTERED
- GetResizeInfoDialog.MaintainAspectCheckBox.SetThreeState FALSE
-
- GetResizeInfoRet% = DIALOG(GetResizeInfoDialog)
- IF GetResizeInfoRet% = DIALOG_RETURN_CANCEL THEN STOP
- END FUNCTION
-
-
- ' *******************************************************************************
- ' GetResizeInfoDialogEventHandler
- ' This subroutine responds to user interface with the GetResizeInfoDialog.
- '
- ' 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 GetResizeInfoDialogEventHandler(BYVAL ControlID%, BYVAL Event%)
- IF Event% = EVENT_INITIALIZATION THEN
- GetResizeInfoDialog.BackButton.Enable FALSE
- GetResizeInfoDialog.HorizontalSpinControl.SetMinRange -99
- GetResizeInfoDialog.HorizontalSpinControl.SetMaxRange 1000
- GetResizeInfoDialog.VerticalSpinControl.SetMinRange -99
- GetResizeInfoDialog.VerticalSpinControl.SetMaxRange 1000
- GetResizeInfoDialog.HorizontalSpinControl.SetValue 0
- GetResizeInfoDialog.VerticalSpinControl.SetValue 0
- GetResizeInfoDialog.SetStyle STYLE_VISIBLE
- ENDIF
-
- IF Event% = EVENT_CHANGE_IN_CONTENT THEN
- SELECT CASE ControlID%
- CASE GetResizeInfoDialog.HorizontalSpinControl.GetID()
- IF AspectRatio = MAINTAIN_ASPECT THEN
- GetResizeInfoDialog.VerticalSpinControl.SetValue GetResizeInfoDialog.HorizontalSpinControl.GetValue()
- ENDIF
- CASE GetResizeInfoDialog.VerticalSpinControl.GetID()
- IF AspectRatio = MAINTAIN_ASPECT THEN
- GetResizeInfoDialog.HorizontalSpinControl.SetValue GetResizeInfoDialog.VerticalSpinControl.GetValue()
- ENDIF
- END SELECT
- ENDIF
-
- IF Event% = EVENT_MOUSE_CLICK THEN
- SELECT CASE ControlID%
- CASE GetResizeInfoDialog.NextButton.GetID()
- HorizontalResize& = GetResizeInfoDialog.HorizontalSpinControl.GetValue()
- VerticalResize& = GetResizeInfoDialog.VerticalSpinControl.GetValue()
- Resize
- ' GetResizeInfoDialog.CloseDialog DIALOG_RETURN_NEXT
- CASE GetResizeInfoDialog.CancelButton.GetID()
- GetResizeInfoDialog.CloseDialog DIALOG_RETURN_CANCEL
- CASE GetResizeInfoDialog.MaintainAspectCheckBox.GetID()
- AspectRatio& = GetResizeInfoDialog.MaintainAspectCheckBox.GetValue()
- IF AspectRatio = MAINTAIN_ASPECT THEN
- GetResizeInfoDialog.VerticalSpinControl.SetValue GetResizeInfoDialog.HorizontalSpinControl.GetValue()
- ENDIF
- END SELECT
- ENDIF
- END FUNCTION
-
-
- ' *******************************************************************************
- ' Resize
- ' This function applies the specified horizontal and vertical resizing to the
- ' selected object(s).
- '
- ' PARAMS: None
- ' *******************************************************************************
- SUB Resize
- ON ERROR GOTO ErrorHandler
- WITHOBJECT OBJECT_VENTURA8
- .SetVisible TRUE
- SelectStatus& = .GetSelectionType()
- IF SelectStatus& < 2 THEN 'nothing selected
- MESSAGE "You need to select something first!"
- ELSEIF SelectStatus& = 2 THEN 'not a valid selection
- MESSAGE "That is not a valid selection!"
- ELSE
- HorizontalResize& = (HorizontalResize& * 1000) + 100000
- VerticalResize& = (VerticalResize& * 1000) + 100000
- .ResizeObject HorizontalResize&, VerticalResize&
- ENDIF
- END WITHOBJECT
- EXIT SUB
-
- ErrorHandler:
- SELECT CASE ErrNum
- CASE IS > 1000
- RESUME NEXT
- CASE ELSE
- MESSAGE "FATAL ERROR !!" & CHR(13) & "Number: " & STR(ErrNum) & CHR(13) & "Script will now exit"
- ' STOP
- END SELECT
- END SUB
-