Compaq ACMS for OpenVMS
Writing Server Procedures


Previous Contents Index

3.2.5 Migrating Existing Step Procedures to Participate in Distributed Transactions

If you modify existing step procedures to participate in distributed transactions that start in calling tasks, you must:

If you perform neither of the above steps, the task appears to execute correctly; however, the end of the distributed transaction is not coordinated with the end of the database transaction. This occurs because Rdb or DBMS does not know that you want the database operation to participate in the transaction if you do not pass the TID. Therefore, the database transaction starts and ends as it did before the task was changed to use distributed transactions.

If you perform the first step but not the second, the COMMIT or ROLLBACK statement returns an error. By specifying the TID, you include your database operation in the distributed transaction. You cannot use the COMMIT or ROLLBACK verbs to end a database transaction that is participating in a distributed transaction.

3.3 Returning Status to the Task Definition

In most situations, a task needs to know whether or not the work done in a processing step is successful so that it can determine what to do next. This means that the step procedure must pass this information back to the task. You can pass this information back to the task in one of two ways:

The following sections describe these methods.

Note

ACMS requires initialization, termination, and cancel procedures to return a status. If they do not return status, results are unpredictable.

3.3.1 Returning Status with a Status Return Facility

All OpenVMS programming languages that follow the OpenVMS calling standard supply a mechanism for returning status from a subprogram or function. For example, in COBOL you can return status by specifying a variable in the GIVING clause of a Procedure Division statement and assigning a status value to this variable:


PROCEDURE DIVISION GIVING status-result. 

The return status from the subprogram or function is automatically returned to the task in the system workspace ACMS$PROCESSING_STATUS. ACMS moves the return status value to the ACMS$L_STATUS field, which is one of four fields in the ACMS$PROCESSING_STATUS workspace. The four fields are the following:

ACMS$L_STATUS
ACMS$T_SEVERITY_LEVEL
ACMS$T_STATUS_TYPE
ACMS$T_STATUS_MESSAGE

ACMS then sets the values of the fields ACMS$T_SEVERITY_LEVEL and ACMS$T_STATUS_TYPE to correspond to the return status value in ACMS$L_STATUS.

Table 3-1 show the values of the ACMS$T_STATUS_TYPE field. The binary value in the table refers to the value of the low-order bit in ACMS$L_STATUS.

Table 3-1 Values for ACMS$T_STATUS_TYPE
Status Type Binary Value Meaning
G 1 GOOD
Represents successful completion of a step procedure.
B 0 BAD
Represents the failure of a step procedure.

Table 3-2 lists the values for the ACMS$T_SEVERITY_LEVEL field. The binary value in the table refers to the value of the three low-order bits in ACMS$L_STATUS.

Table 3-2 Values for ACMS$T_SEVERITY_LEVEL
Severity Level Binary Value Meaning
S 001 SUCCESS
I 011 INFORMATION
W 000 WARNING
E 010 ERROR
F 100 FATAL
? Other Invalid severity level

A task can check the ACMS$T_STATUS_TYPE or the ACMS$T_SEVERITY_LEVEL field to determine what action to take.

ACMS sets initial values for the fields in the ACMS$PROCESSING_STATUS workspace as follows:
Field Initial value
ACMS$L_STATUS 1 (normal successful completion)
ACMS$T_SEVERITY_LEVEL S (SUCCESS)
ACMS$T_STATUS_TYPE G (GOOD)
ACMS$T_STATUS_MESSAGE Spaces

Note

ACMS puts information into the ACMS$PROCESSING_STATUS workspace whether or not your procedure explicitly returns a status. You must be careful to use this workspace in a task definition only when your procedure returns a status. Otherwise, the results are unpredictable.

3.3.2 Returning Status in User-Defined Workspaces

Returning status to a task in a user-defined workspace is useful if you return a value to DECforms that determines what message DECforms displays.

To return status from a step procedure to a task in a user-defined workspace, define a status field in a workspace used by the task. Example 3-4 shows the CDD definition for a workspace called TASK_CONTROL.

Example 3-4 Record Description for TASK_CONTROL

CDO> SHOW RECORD pers_cdd.task_control/FULL 
Definition of record TASK_CONTROL 
|   Contains field           STEP_STATUS 
|   |   Datatype                 text size is 8 characters 
    . 
    . 
    . 

In Example 3-4, STEP_STATUS is an 8-character text field into which the step procedure writes a character string indicating whether or not it has completed successfully. The task uses the step status field to determine the completion status of the step procedure. The task uses the contents of the workspace field to determine what to do next.

Example 3-5 and Example 3-6 illustrate how to return status in a user-defined workspace. The step procedure first initializes the status field to SUCCESS; it then writes a new record to an employee master file. If a record with the same key already exists, the procedure stores the error text DUPLICAT in the status field. The task uses the contents of the status field to determine if the step procedure successfully stored the new employee record.

Note

ACMS does not initialize workspaces every time it begins a step procedure. Therefore, you must ensure that a step procedure stores the correct status before it completes. For example, the step procedure illustrated in Example 3-5 always initializes the status to SUCCESS at the beginning. This is necessary if a user incorrectly enters a badge number that is already on file for an employee. After the user corrects the mistake, the step procedure is called again, and the WRITE operation succeeds. In this case, the step procedure must return a success status to ensure that the task continues normally when the step procedure completes.

3.3.2.1 COBOL Procedure for Returning Status in a User-Defined Workspace

Example 3-5 illustrates a complete step procedure for a simple data entry task. In this example, the step procedure first initializes the STEP_STATUS field to SUCCESS. If the write operation fails with a duplicate-key error, the step procedure stores DUPLICAT in the STEP_STATUS field using the INVALID KEY clause.

Example 3-5 COBOL Procedure for Returning Status in a User-Defined Workspace

IDENTIFICATION DIVISION. 
PROGRAM-ID. pers_add_employee_proc. 
 
ENVIRONMENT DIVISION. 
 
INPUT-OUTPUT SECTION. 
FILE-CONTROL. 
SELECT  emp_file 
        ORGANIZATION INDEXED 
        ACCESS RANDOM 
        ASSIGN TO "emp_file:employee.dat". 
 
I-O-CONTROL. 
APPLY LOCK-HOLDING ON emp_file. 
 
DATA DIVISION. 
 
FILE SECTION. 
FD      emp_file 
        EXTERNAL 
        DATA RECORD IS employee_record 
        RECORD KEY emp_badge_number OF employee_record. 
COPY "pers_cdd.employee_record" FROM DICTIONARY. 
WORKING-STORAGE SECTION. 
 
LINKAGE SECTION. 
COPY "pers_cdd.task_control" FROM DICTIONARY. 
COPY "pers_cdd.employee_record" FROM DICTIONARY 
    REPLACING ==employee_record== BY ==emp_wksp_record==. 
 
PROCEDURE DIVISION USING task_control, emp_wksp_record. 
MAIN SECTION. 
 
000-start. 
    MOVE "SUCCESS" TO step_status OF task_control.
    WRITE employee_record FROM emp_wksp_record 
        ALLOWING NO OTHERS 
        INVALID KEY
            MOVE "DUPLICAT" TO step_status OF task_control
        NOT INVALID KEY 
            UNLOCK emp_file ALL RECORDS 
    END-WRITE. 
 
999-end. 
    EXIT PROGRAM. 

3.3.2.2 BASIC Procedure for Returning Status in a User-Defined Workspace

Example 3-6 illustrates a complete step procedure for a simple data entry task. In this example, the step procedure first initializes the STEP_STATUS field to SUCCESS. If the write operation fails with a duplicate-key error, the step procedure uses an error handler to store DUPLICAT in the STEP_STATUS field.

Example 3-6 BASIC Procedure for Returning Status in a User-Defined Workspace

 
    FUNCTION LONG pers_add_employee_proc(                       & 
                                task_control task_ctrl_wksp,    & 
                                employee_record emp_wksp ) 
 
    %INCLUDE "pers_files:pers_common_defns" 
 
    %INCLUDE %FROM %CDD "pers_cdd.employee_record" 
    %INCLUDE %FROM %CDD "pers_cdd.task_control" 
 
    MAP ( emp_map ) employee_record emp_rec 
 
    WHEN ERROR IN 
        task_ctrl_wksp::step_status = "SUCCESS"
        MOVE TO # emp_file, emp_wksp 
        PUT # emp_file 
        UNLOCK # emp_file 
    USE 
        SELECT ERR 
            CASE basicerr_duplicate_key
                task_ctrl_wksp::step_status = "DUPLICAT"
            CASE ELSE 
                CALL ACMS$RAISE_NONREC_EXCEPTION( RMSSTATUS( emp_file ) ) 
                EXIT HANDLER 
        END SELECT 
    END WHEN 
 
    END FUNCTION 

3.4 Handling Error Conditions

When you design a task and its components, include logic that checks the status of steps for their successful completion. For example, a task definition for an employee update task includes these steps:

  1. Display a form that asks the user for an employee number.
  2. Call a procedure to read the data for that employee.
    The step procedure reads the record; it then checks the status of the read operation and performs one of the following:
  3. Check the status from the step procedure:
  4. Display a form that shows the employee's record and asks the user for changes to the record information.
  5. Call a procedure to rewrite the changed employee information.
    The step procedure rewrites the record; it then checks the status of the rewrite operation and performs one of the following:
  6. Check the status from step procedure:

See Compaq ACMS for OpenVMS Writing Applications for information about how to write task definitions.

A step procedure can use a number of alternative methods for returning information about recoverable error conditions to the task:

The following sections discuss processing error messages in step procedures and raising exceptions in step procedures.

3.4.1 Processing Error Messages

If a step procedure detects a recoverable error, you must inform users of the problem. With this information, they can then decide how to continue.

In ACMS, you can choose among several methods of returning error messages to users. These methods are distinguished by where the message text is obtained and processed:

3.4.1.1 Using a Message File in the Task Definition

Using this method, you retrieve the error message text from a message file in the task definition based on the OpenVMS return status from the step procedure. You use a return status facility to return the status from the step procedure to the task, as discussed in section Section 3.3.1.

ACMS stores the return status in the ACMS$PROCESSING_STATUS workspace, which the task can check and then retrieve error message text from the message file, as explained in Chapter 5. This is the most common method for returning information about a recoverable error condition from the step procedure to the task.

The advantages of this method are that it is simple to use in both the step procedure and the task definition, and you can change messages without recompiling the procedure. A disadvantage of this method is that you cannot use more informative error messages containing additional information; you can use only simple literal error messages. For example, you cannot include a specific employee number in this message:


    "Employee ID already exists on file" 

To use a message file in a task definition, follow these steps:

  1. In the step procedure, return the failure status associated with the error condition.
    For example, in COBOL:


    MOVE persmsg_empexists TO return_status. 
    GO TO 999-end. 
    

    For example, in BASIC:


    EXIT FUNCTION persmsg_empexists 
    

  2. In the task definition, check the return status from the procedure in the ACMS$PROCESSING_STATUS workspace.
    If the step procedure returns an error status, retrieve the error message text based on the return status and go to an exchange step that displays the error message on the form. For example:


    PROCESSING 
        WORK IS 
            CALL pers_add_employee_proc USING 
                        task_control, 
                        employee_record 
        ACTION IS 
            IF ( ACMS$T_STATUS_TYPE = "B" ) 
            THEN 
                GET ERROR MESSAGE; 
                GOTO STEP get_new_employee_data; 
            END IF; 
    

3.4.1.2 Using a Message File in the Step Procedure

Using this method, you retrieve the error message text from a message file in the step procedure.

Use OpenVMS system services or run-time library (RTL) routines to retrieve and process the error message text in the step procedure. See OpenVMS System Services Reference Manual and OpenVMS RTL Library (LIB$) Manual for more information on using the OpenVMS Formatted ASCII Output (FAO) facility.

An advantage to this method is that you can return more informative error messages to the user by including additional information in the error message text. For example:


"Employee ID: 123456, last name: SMITH, already exists on file" 

A disadvantage of this method is that you might have to modify a step procedure if you need to change the error message text. If the order of FAO arguments does not change when you modify the error message, then you do not need to modify the step procedure. However, if the order of the FAO arguments does change, then you must modify and recompile the step procedure, and relink the procedure server image.

To use a message file in a step procedure, follow these steps:

  1. Define a field in a user-defined workspace to hold the error message text. For example:


    task_status_msg       DATATYPE TEXT 80. 
    

  2. In the step procedure, use the SYS$GETMSG and SYS$FAO system services, or the LIB$SYS_GETMSG and LIB$SYS_FAO RTL routines to obtain and process the error message text.
    For example, in COBOL:


            . 
            . 
            . 
    DATA DIVISION. 
    WORKING-STORAGE SECTION. 
     
    01  persmsg_empexists           PIC S9(5) COMP 
                                    VALUE IS EXTERNAL persmsg_empexists. 
    01  msg_format_string           PIC X(80). 
    01  text_only_flag              PIC S9(5) COMP 
                                    VALUE IS 1. 
    01  sts                         PIC S9(5) COMP. 
    01  return_status               PIC S9(5) COMP. 
     
            . 
            . 
            . 
     
    PROCEDURE DIVISION ... GIVING return_status. 
            . 
            . 
            . 
     
    * 
    * Call LIB$SYS_GETMSG to get error message text associated with 
    * the 'employee already exists' error. Note that we use 1 as the 
    * message text flag since we want only the message text, not the 
    * facility code or severity level. 
    * 
        CALL "LIB$SYS_GETMSG" USING 
                    BY REFERENCE persmsg_empexists 
                    OMITTED, 
                    BY DESCRIPTOR msg_format_string, 
                    BY REFERENCE text_only_flag 
            GIVING sts. 
        IF sts IS FAILURE 
        THEN 
            CALL "LIB$STOP" USING BY VALUE sts 
        END-IF. 
     
     
    * 
    * Call LIB$SYS_FAO to format the 'employee already exists' error 
    * message text to include the employee's badge number and last 
    * name, using the message text as the FAO control string. 
    * 
        CALL "LIB$SYS_FAO" USING 
                    BY DESCRIPTOR msg_format_string, 
                    OMITTED, 
                    BY DESCRIPTOR task_status_msg, 
                    BY DESCRIPTOR emp_badge_number, 
                    BY DESCRIPTOR emp_last_name 
            GIVING sts. 
        IF sts IS FAILURE 
        THEN 
            CALL "LIB$STOP" USING BY VALUE sts 
        END-IF. 
     
     
    * 
    * Return failure status to task. Note that the task simply uses 
    * the return status as a success/failure indicator; it does not 
    * use the value of the return status to process the message text. 
    * 
        MOVE persmsg_empexists TO return_status. 
        GO TO 999-end. 
    

    For example, in BASIC:


            . 
            . 
            . 
        EXTERNAL LONG FUNCTION  LIB$SYS_GETMSG,                         & 
                                LIB$SYS_FAO 
     
        EXTERNAL LONG CONSTANT  persmsg_empexists 
        DECLARE STRING  msg_format_string,                              & 
                LONG    sts 
            . 
            . 
            . 
     
        !+ 
        ! Call LIB$SYS_MSGMSG to error message text associated with the 
        ! 'employee already exists" error. Note that we use 1 as the 
        ! message text flag since we only want the message text, not the 
        ! facility code or severity level. 
        !- 
        sts = LIB$SYS_GETMSG( persmsg_empexists,                        & 
                              0% BY VALUE,                              & 
                              msg_format_string,                        & 
                              1% ) 
     
        IF ( sts AND 1% ) = 0% 
        THEN 
                CALL LIB$STOP( sts BY VALUE ) 
        END IF 
        !+ 
        ! Call LIB$SYS_FAO to format the 'employee already exists' error 
        ! message text to include the employee's badge number and last 
        ! name, using the message text as the FAO control string. 
        !- 
        sts = LIB$SYS_FAO( msg_format_string,                           & 
                           0% BY VALUE,                                 & 
                           task_ctl_rec::task_status_msg,               & 
                           emp_rec::emp_badge_number,                   & 
                           TRM$( emp_rec::emp_last_name ) ) 
        IF ( sts AND 1% ) = 0% 
        THEN 
            CALL LIB$STOP( sts BY VALUE ) 
        END IF 
        !+ 
        ! Return failure status indicator to task. Note that the task 
        ! simply uses the return status as a success/failure indicator, 
        ! it does not use the value of the return status to process the 
        ! message text. 
        !- 
        EXIT FUNCTION persmsg_empexists 
    

  3. In the task definition, check the return status from the procedure in the ACMS$PROCESSING_STATUS workspace.
    If the step procedure returns a failure status, then go to an exchange step that displays the error message from the step procedure on the form. For example:


    PROCESSING 
        WORK IS 
            CALL pers_add_employee_proc USING 
                        task_control, 
                        employee_record 
        ACTION IS 
            IF ( ACMS$T_STATUS_TYPE = "B" ) 
            THEN 
                GOTO STEP get_new_employee_data; 
            END IF; 
    


Previous Next Contents Index