[an error occurred while processing this directive]

HP OpenVMS Systems Documentation

Content starts here

Compaq ACMS for OpenVMS
Writing Server Procedures


Previous Contents Index

2.4.6.2 Cancel Procedure for RMS Files

Write a server cancel procedure when you use RMS in the following situations:

  • If you access an RMS file in a distributed transaction
    If you allow the server to remain active when a task is canceled, you must use a cancel procedure to unlock any records that a step procedure locks after a distributed transaction aborts.
  • If you write a task that retains context in a server between two processing steps
    If you allow the server to remain active when a task is canceled between two processing steps, you must use a cancel procedure to unlock any records locked by the first processing step.

Example 2-12 illustrates a server cancel procedure written in COBOL that uses the UNLOCK statement to release any records locked in the Employee and History files. If an error occurs, the procedure logs the error in the ACMS audit trail log by calling LIB$SIGNAL and returns the ACMS$_RNDWN status to force ACMS to run down the server process. If no errors are detected, the procedure returns the ACMS$_RNDWNIFINT status; in this case, ACMS runs down the server process only if the execution of a step procedure was interrupted due to the cancel.

Example 2-12 Server Cancel Procedure in COBOL for RMS Files

IDENTIFICATION DIVISION.
PROGRAM-ID. pers_upd_server_can_proc.

ENVIRONMENT DIVISION.


INPUT-OUTPUT SECTION.
FILE-CONTROL.
SELECT  emp_file
        ORGANIZATION INDEXED
        ACCESS RANDOM
        ASSIGN TO "emp_file:employee_file.dat".


SELECT  hist_file
        ORGANIZATION INDEXED
        ACCESS RANDOM
        ASSIGN TO "hist_file:history_file.dat".

I-O-CONTROL.
APPLY LOCK-HOLDING ON emp_file,
                      hist_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.

FD      hist_file
        EXTERNAL
        DATA RECORD IS history_record
        RECORD KEY hist_badge_number OF history_record.
COPY "pers_cdd.history_record" FROM DICTIONARY.


WORKING-STORAGE SECTION.

01  status_result               PIC S9(5) COMP.

01  ACMS$_RNDWNIFINT            PIC S9(5) COMP
                                VALUE IS EXTERNAL ACMS$_RNDWNIFINT.
01  ACMS$_RNDWN                 PIC S9(5) COMP
                                VALUE IS EXTERNAL ACMS$_RNDWN.

PROCEDURE DIVISION GIVING status_result.


DECLARATIVES.
employee_file SECTION.
    USE AFTER STANDARD ERROR PROCEDURE ON emp_file.
employee_file_handler.
        CALL "LIB$SIGNAL" USING BY VALUE RMS-STS OF emp_file,
                                BY VALUE RMS-STV OF emp_file
        MOVE ACMS$_RNDWN TO status_result.
        EXIT PROGRAM.
history_file SECTION.
    USE AFTER STANDARD ERROR PROCEDURE ON hist_file.
history_file_handler.
        CALL "LIB$SIGNAL" USING BY VALUE RMS-STS OF hist_file,
                                BY VALUE RMS-STV OF hist_file
        MOVE ACMS$_RNDWN TO status_result.
        EXIT PROGRAM.
END DECLARATIVES.


MAIN SECTION.

000-start.
    UNLOCK emp_file ALL RECORDS.
    UNLOCK hist_file ALL RECORDS.
    MOVE ACMS$_RNDWNIFINT TO status_result.

999-end.
    EXIT PROGRAM.

Example 2-13 illustrates a server cancel procedure written in BASIC that uses the FREE statement to release any records locked in the Employee and History files. If an error occurs, the procedure returns the ACMS$_RNDWN status to force ACMS to run down the server process. The EXIT HANDLER statement is used to resignal the error so that ACMS writes it to the audit trail log. If no errors are detected, the procedure returns the ACMS$_RNDWNIFINT status; in this case, ACMS runs down the server process only if the execution of a step procedure was interrupted due to the cancel.

Example 2-13 Server Cancel Procedure in BASIC

    FUNCTION LONG pers_upd_server_can_proc

    %INCLUDE "pers_files:pers_common_defns"

    EXTERNAL LONG CONSTANT ACMS$_RNDWNIFINT
    EXTERNAL LONG CONSTANT ACMS$_RNDWN


    WHEN ERROR IN
        FREE # emp_file
        FREE # hist_file
        pers_upd_server_can_proc = ACMS$_RNDWNIFINT
    USE
        pers_upd_server_can_proc = ACMS$_RNDWN
        EXIT HANDLER
    END WHEN

    END FUNCTION


Chapter 3
Writing Step Procedures

This chapter discusses writing step procedures for ACMS tasks. The suggestions in this chapter apply to users of all languages and all data management systems. The material in this chapter provides a basis for Chapter 4, which contains information and examples specific to Rdb software using SQL, Rdb using RDO, DBMS software, and RMS software.

This chapter discusses the following topics:

  • Using workspaces with step procedures
    Explains how tasks use workspaces to pass data between processing steps and exchange steps, and describes the ACMS-supplied system workspaces.
  • Using procedures in distributed transactions
    Tells how to write new step procedures and how to migrate existing procedures to participate in distributed transactions.
  • Returning status to the task definition
    Discusses how to return status to the task definition using a status return facility or a user-defined workspace.
  • Handling error conditions
    Discusses how step procedures handle error conditions by processing error messages and raising recoverable and nonrecoverable exceptions.
  • Performing terminal I/O from a procedure server
    Explains how programs that run in procedure servers can perform I/O directly to a terminal, which is useful for preexisting programs that you convert to single-step tasks.

3.1 Using Workspaces with Step Procedures

An ACMS task uses workspaces to pass information between the task definition and step procedures and DECforms forms. Workspaces are temporary data storage areas, which are passed to step procedures as parameters. Workspaces are passed by reference (that is, the address is passed), with write access.

Figure 3-1 illustrates the way a task uses workspaces to pass data between a form and a step procedure. Once a workspace and its fields have been declared (in CDD, for example), you can use a form to input data and store it in workspace fields. You can then pass that data to a database or RMS file for storage.

Figure 3-1 How ACMS Applications Use Workspaces


3.1.1 Using ACMS-Supplied System Workspaces

ACMS provides special-purpose task workspaces, called system workspaces, which contain information about the state of a task. This information might be useful to the step procedures called by the task.

ACMS supplies the following system workspaces:

  • ACMS$SELECTION_STRING
    This workspace makes information from an ACMS menu available to the task, forms, and step procedures. You can also use this workspace to pass parameters to DCL command procedures.
    Appendix A and Compaq ACMS for OpenVMS Writing Applications contain more information about this workspace.

  • ACMS$PROCESSING_STATUS
    A task can use the fields of this workspace to determine the completion status of a step procedure. In addition, ACMS stores information about exceptions in this workspace.
    Section 3.3, Chapter 5, and Appendix A contain more information about using this workspace.
  • ACMS$TASK_INFORMATION
    ACMS stores task execution information such as task ID, sequence number, and task name in this workspace. You can use this workspace, for example, to determine the name of the device from which a task was submitted (for security reasons) or to ascertain whether the task was submitted from a remote node.
    Appendix A contains reference information about this workspace.

System workspaces are always available to ACMS tasks. ACMS gives each task its own copy of all three workspaces and initializes each workspace when a task is selected.

Note

Step procedures must not modify the contents of the ACMS$PROCESSING_STATUS or ACMS$TASK_INFORMATION workspaces. Step procedures can, however, modify the contents of the ACMS$SELECTION_STRING workspace.

3.1.2 Identifying Workspaces

You must define record definitions for all the workspaces used by your task. A step procedure reads from or writes to the workspaces using the record names and field names from the record definitions. ACMS takes its workspace definitions from CDD record definitions.

Note

If the programming language you use does not support CDD, you must also define the workspace records in the step procedure.

Example 3-1 shows part of a task definition that declares the VR_CUSTOMERS_WKSP in the USE WORKSPACES clause and passes it to the procedure VR_GET_CUSTOMER_PROC in the CALL statement.

Example 3-1 Referencing a Workspace in a Task Definition

REPLACE TASK VR_DISPLAY_CU_TASK

USE WORKSPACES VR_CUSTOMERS_WKSP,

                      .
                      .
                      .
BLOCK WORK WITH FORM I/O IS


GET_CUSTOMERS:
  PROCESSING
      CALL VR_GET_CUSTOMER_PROC USING VR_CUSTOMERS_WKSP,
                .
                .
                .
END DEFINITION;

To receive the contents of the workspace named in the task definition, the programming language you use must be able to receive parameters from the calling program. For example, in COBOL, the parameters used to pass information are defined in the Linkage Section and are named in the Procedure Division header.

Example 3-2 shows part of a COBOL procedure that also refers to VR_CUSTOMERS_WKSP.

Example 3-2 COBOL Procedure that Names a Workspace

IDENTIFICATION DIVISION.
***********************************************************
PROGRAM-ID. VR-GET-CUSTOMER-PROC IS INITIAL.
.
.
.


LINKAGE SECTION.
*
* Copy CUSTOMERS record from the CDD
*

EXEC SQL INCLUDE FROM DICTIONARY
            'AVERTZ_CDD_WKSP:VR_CUSTOMERS_WKSP'
END-EXEC.
.
.
.

PROCEDURE DIVISION USING VR_CUSTOMERS_WKSP,
                          .
                          .
                          .
                   GIVING RET-STAT.

Example 3-3 shows part of the CDD record definition of VR_CUSTOMERS_WKSP.

Example 3-3 CDD Record Definition for VR_CUSTOMERS_WKSP Workspace

DEFINE RECORD VR_CUSTOMERS_WKSP.
.
.
.
CUSTOMER_ID.
CU_LAST_NAME.
CU_FIRST_NAME.
CU_MIDDLE_INITIAL.
CU_FIRST_ADDRESS_LINE.
.
.
.
END RECORD.

Assign an initial value to any non-binary fields for testing in DECforms. For example, set the initial value of each character field in the record definition to blanks, as shown in this CDD field definition:


DEFINE FIELD CU_LAST NAME                 DATATYPE TEXT SIZE IS 20
        INITIAL VALUE IS "                    ".

See the CDD documentation for additional information on assigning initial values.

3.2 Using Procedures in Distributed Transactions

This section discusses the considerations to keep in mind when you write a procedure that accesses a resource manager in a distributed transaction.

A resource manager controls shared access to a set of recoverable resources on behalf of application programs. A resource is a set of one or more data items in a database or an RMS file. The term recoverable means that all updates to the resources either can be made permanent or can be undone, and that the integrity of the resources can be recovered after a failure such as a system crash.

The following sections discuss:

  • Participation of a procedure in a distributed transaction
  • Use of database transactions or recovery units with distributed transactions
  • Obtaining the Transaction ID
  • Retaining context in distributed transactions
  • Migrating existing step procedures to participate in distributed transactions

3.2.1 Determining the Participation of a Procedure in a Distributed Transaction

The following rules determine the participation of a procedure in a distributed transaction:

  • When a processing step that executes within a block delimiting a distributed transaction calls a procedure, that procedure automatically participates in the distributed transaction. For example:


    BLOCK WITH TRANSACTION
        PROCESSING
            CALL    vr_store_cu_proc
            IN      vr_cu_update_server
            USING   vr_control_wksp,
                    vr_customers_wksp,
                    vr_trans_wksp;
               .
               .
               .
    END BLOCK WORK;
          .
          .
          .
    

    Because the processing step executes within the bounds of a distributed transaction, the server automatically participates in the distributed transaction.
  • When a processing step that delimits a distributed transaction calls a procedure, that procedure automatically participates in the distributed transaction. For example:


    PROCESSING WITH TRANSACTION
        CALL    vr_store_cu_proc
        IN      vr_cu_update_server
        USING   vr_control_wksp,
                vr_customers_wksp,
                vr_trans_wksp;
              .
              .
              .
    

    Use this method if a single step procedure needs to update multiple resources. For example, you might choose this method for a procedure that updates an RMS file as well as an Rdb database. You can also use this method if a task has only one step, which is a processing step.
  • You can explicitly exclude a procedure server from a distributed transaction by using the WITH NONPARTICIPATING SERVER phrase on the processing step of a task definition:


    PROCESSING WITH NONPARTICIPATING SERVER
    

See Compaq ACMS for OpenVMS Writing Applications for more information on writing definitions of tasks that use distributed transactions.

In ACMS, you can start a distributed transaction in either an agent program, a task, or a step procedure. Compaq ACMS for OpenVMS Concepts and Design Guidelines explains the relative advantages and disadvantages of starting a distributed transaction in each of these locations.

You can also start a distributed transaction in a task and, from that task, call a procedure that acts as an agent. The agent program can call a task on a remote node, and the called task can access databases locally on that node, thus reducing network traffic and increasing the efficiency of the application.

See Compaq ACMS for OpenVMS Concepts and Design Guidelines for more information about using a task to update a remote database. See Compaq ACMS for OpenVMS Systems Interface Programming for detailed information about using a step procedure as an agent program.

Note

Do not call the $START_TRANS, $END_TRANS, or $ABORT_TRANS system services from a step procedure that is participating in a distributed transaction started by a task or an agent program. If you do call these services under these conditions, they either return an error status or hang until the task is canceled by the terminal user or system operator.

3.2.2 Using Database Transactions or Recovery Units with Distributed Transactions

The unit of interaction with a database that begins with a start-transaction statement is called a database transaction. The Rdb and DBMS documentation refer to this unit as a transaction. A set of RMS recoverable operations is referred to as a recovery unit. To avoid possible confusion with the term distributed transactions, this manual uses the term database transaction when referring to this unit for Rdb and DBMS database products and recovery unit when referring to this unit for RMS files. The term database transaction is used whether transactions are distributed or nondistributed.

Depending on the database you are using, you start a database transaction with one of the following statements:

Database product Statement that starts a distributed transaction
Rdb using SQL SET TRANSACTION
Rdb using RDO START_TRANSACTION
DBMS READY

Instructions for starting database transactions are in Chapter 4.

Note that RMS files that are marked for recovery participate automatically in a distributed transaction; in other words, no special syntax is necessary.

The DML verbs COMMIT or ROLLBACK commit or roll back an independent database transaction or a recovery unit that is not participating in a distributed transaction. However, a database transaction that participates in a distributed transaction is automatically committed or rolled back when the distributed transaction ends. Therefore, you cannot use the COMMIT or ROLLBACK DML verbs to end a database transaction that participates in a distributed transaction. The COMMIT and ROLLBACK verbs fail and return an error if you try to use them to end a database transaction that is participating in a distributed transaction.

If a processing step participates in a distributed transaction, you must start the database transaction in the step procedure. You cannot use database-specific or RMS-specific recovery declarations in task definitions in conjunction with distributed transactions. ADU does not allow the use of the WITH SQL/RDB/DBMS/RMS RECOVERY phrase in the definition of a task that is within the bounds of a distributed transaction. These phrases are declining functionality.

Important

Always specify a lock timeout interval when you use Rdb or DBMS in a distributed transaction. This ensures that ACMS can successfully cancel a task that is waiting for a database lock. By specifying a lock timeout interval, you ensure that the task is canceled as soon as the timeout interval expires. If you do not specify a lock timeout interval, ACMS cannot cancel the task until the lock is granted. See Chapter 4 for more information on specifying a lock timeout interval.

3.2.3 Obtaining the Transaction ID (TID)

ACMS automatically obtains a transaction ID (TID) when you start a distributed transaction. Whenever a step procedure is called as part of a distributed transaction, ACMS establishes the TID as the default TID of the server process.

For an Rdb or DBMS database transaction to participate in a distributed transaction, you must explicitly pass the TID to Rdb or DBMS when you start the database transaction. In contrast, RMS automatically accesses the TID for files that are marked for recovery-unit journaling. Therefore, no special action is necessary; a step procedure does not need to obtain the TID when using RMS with distributed transactions.

ACMS provides a service, called ACMS$GET_TID, that a step procedure can call to obtain the TID before using the database. For example:


CALL "ACMS$GET_TID" USING CS-TID GIVING RET_STAT.

See Chapter 9 for full details on the ACMS$GET_TID service. See Chapter 4 for information on how to pass the TID to Rdb and DBMS.

3.2.4 Retaining Server Context in Distributed Transactions

The following rules apply to retaining server context in a distributed transaction:

  • Context must be retained in a server that participates in a distributed transaction until the end of the transaction. At the end of the distributed transaction, the task must release context in all the servers that participated in the transaction. ADU automatically supplies default server context actions for transaction steps and steps that participate in distributed transactions. (See Compaq ACMS for OpenVMS Writing Applications for more information about server context.)
  • A task definition can contain multiple processing steps that call one or more server procedures in the same server within a single distributed transaction. Within a single task, a single server process is used for all the processing steps that call step procedures in the same server. In this case, the first step procedure called within a distributed transaction must ready a database for the current procedure and any subsequent step procedures called by the task. For example, if the first step procedure accesses an Rdb database, the procedure must reserve those relations that are required by the current procedure as well as those relations that are required by subsequent step procedures.
    A different situation occurs when a task calls another task as part of a distributed transaction. The called task does not share server context with the parent task; the parent and called tasks use different server processes. Therefore, the first procedure called by the called task must ready a database for the current and any subsequent server procedures used by the called task.
  • Both the Rdb and DBMS database products support only a single active database transaction in one process at a time. Therefore, once a server participates in a distributed transaction, the server must remain reserved to the distributed transaction until the transaction ends. See Compaq ACMS for OpenVMS Writing Applications for more information about retaining server context.


Previous Next Contents Index