TDLOCPRM

Description

Returns the ID number of a parameter when the parameter name is received.

Syntax

COPY SYGWCOB.
01 TDPROC           PIC S9(9) USAGE COMP SYNC.
01 PARM-ID          PIC S9(9) USAGE COMP SYNC.
01 PARM-NAME        PIC X(n).
01 PARM-NAME-LENGTH PIC S9(9) USAGE COMP SYNC.
CALL 'TDLOCPRM' USING TDPROC, PARM-ID, PARM-NAME,
                PARM-NAME-LENGTH.

Parameters

TDPROC

(I) Handle for this client/server connection. This must be the same value specified in the associated TDACCEPT call. The TDPROC handle corresponds to the connection and command handles in Open Client Client-Library.

PARM-ID

(O) Variable where the number of the named parameter is returned. Parameters are numbered sequentially; the ID of the first parameter is 1. If a 0 is returned here, TDLOCPRM could not find a parameter with the specified name.

PARM-NAME

(I) The name associated with the desired parameter. This name corresponds to the parameter name in the Open Client DB-Library dbrpcparam routine.

PARM-NAME-LENGTH

(I) The actual length of the PARM-NAME.

Returns

This function has no RETCODE argument. It returns the parameter ID in the PARM-ID argument, or a 0 if it finds no parameter with the specified name.

Examples

Example 1

The following code fragment illustrates a typical use of TDLOCPRM. The transaction calls TDNUMPRM to determine how many parameters to retrieve, calls TDLOCPRM to ascertain the number of the parameter with the information it wants, calls TDINFPRM for a description of the parameter, and calls TDRCVPRM to retrieve the parameter data. This example is taken from the sample program, SYCCSAR2, in Appendix B, “Sample RPC Application for CICS.”

 *    Get number of parameters ... should be two
 
      CALL 'TDNUMPRM' USING GWL-PROC, GWL-NUMPRM-PARMS.
 
      IF GWL-NUMPRM-PARMS NOT = 2 THEN
          PERFORM TDNUMPRM-ERROR
          GO TO END-PROGRAM
      END-IF.
 
 *    Get return parameter information
 
      MOVE 1 TO GWL-INFPRM-ID.
      PERFORM GET-PARM-INFO.
 
      (IF GWL-INFPRM-STATUS NOT = TDS-RETURN-VALUE AND
      IF GWL-INFPRM-STATUS NOT = TDS-RETURN-VALUE-NULLABLE) THEN
          PERFORM TDINFPRM-NOT-RETURN-PARM-ERROR
          GO TO END-PROGRAM
      END-IF.
 
      MOVE GWL-INFPRM-USER-DATA TO GWL-SETPRM-USER-DATA.
      MOVE GWL-INFPRM-ID        TO GWL-SETPRM-ID.
      MOVE GWL-INFPRM-DATA-L    TO GWL-SETPRM-DATA-L.
      MOVE GWL-INFPRM-TYPE      TO GWL-SETPRM-TYPE.
 
 *    Get department id parameter number from known name
 
      MOVE '@parm2' TO GWL-INFPRM-NAME.
      MOVE 6        TO GWL-INFPRM-NAME-L.
 
      CALL 'TDLOCPRM' USING GWL-PROC, GWL-INFPRM-ID,
                            GWL-INFPRM-NAME, GWL-INFPRM-NAME-L.
 
 *    Get department parameter information
 
      PERFORM GET-PARM-INFO.
 
      IF GWL-INFPRM-TYPE NOT = TDSVARYCHAR THEN
          PERFORM TDINFPRM-NOT-CHAR-PARM-ERROR
          GO TO END-PROGRAM
      END-IF.
 
 *    Get department parameter data
 
      CALL 'TDRCVPRM' USING GWL-PROC, GWL-RC, GWL-INFPRM-ID,
                            PARM-DEPT, GWL-INFPRM-TYPE,
                            GWL-INFPRM-MAX-DATA-L,
                            GWL-RCVPRM-DATA-L.
*-----------------------------------------------------------------
  GET-PARM-INFO.
*-----------------------------------------------------------------
      CALL 'TDINFPRM' USING GWL-PROC, GWL-RC, GWL-INFPRM-ID,
                            GWL-INFPRM-TYPE, GWL-INFPRM-DATA-L,
                            GWL-INFPRM-MAX-DATA-L
                            GWL-INFPRM-STATUS, GWL-INFPRM-NAME,
                            GWL-INFPRM-NAME-L,
                            GWL-INFPRM-USER-DATA.

Usage

See also

Related functions

Related documents