TDINFPRM

Description

Retrieves parameter type, datatype, and length information about a specified RPC parameter.

Syntax

COPY SYGWCOB.
01 TDPROC             PIC S9(9)  USAGE COMP SYNC.
01 RETCODE            PIC S9(9)  USAGE COMP SYNC.
01 PARM-ID            PIC S9(9)  USAGE COMP SYNC.
01 DATATYPE           PIC S9(9)  USAGE COMP SYNC.
01 ACTUAL-DATA-LENGTH PIC S9(9)  USAGE COMP SYNC.
01 MAX-DATA-LENGTH    PIC S9(9)  USAGE COMP SYNC.
01 PARM-STATUS        PIC S9(9)  USAGE COMP SYNC.
01 PARM-NAME          PIC X(30).
01 PARM-NAME-LENGTH   PIC S9(9)  USAGE COMP SYNC.
01 USER-DATATYPE      PIC S9(9)  USAGE COMP SYNC.
CALL 'TDINFPRM' USING  TDPROC,RETCODE, PARM-ID,
               DATATYPE, ACTUAL-DATA-LENGTH,
               MAX-DATA-LENGTH, PARM-STATUS,PARM-NAME, 
                 PARM-NAME-LENGTH,USER-DATATYPE.

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.

RETCODE

(O) Variable where the result of function execution is returned. Its value is one of the codes listed in Table 3-18.

PARM-ID

(I) Number of the parameter with the information that is requested. Parameters are numbered sequentially; the first parameter is number 1.

DATATYPE

(O) Variable where the Open Client datatype of the parameter is returned. The datatype is specified by the client.

ACTUAL-DATA-LENGTH

(O) Variable where the actual length of the parameter data is returned. For TDSVARYCHAR, TDSVARYBIN, and TDSVARYGRAPHIC parameters, this value does not include the 2 bytes for the “LL” length specification.

MAX-DATA-LENGTH

(O) Variable where the maximum length allowed for the parameter’s data is returned. This value is specified by the client in the parameter definition. For TDSVARYCHAR, TDSVARYBIN, and TDSVARYGRAPHIC parameters, this value does not include the 2 bytes for the “LL” length specification.

PARM-STATUS

(O) Variable where the parameter’s status is returned. This argument indicates whether the named parameter is a return parameter. It returns one of the following values, depending on the TDS version you are using.

  • For TDS 4.6:

    TDS-INPUT-VALUE (0)

    Parameter is not a return parameter.

    TDS-RETURN-VALUE (1)

    Parameter is a return parameter.

  • For TDS 5.0:

    TDS-INPUT-VALUE-NULLABLE (32)

    Parameter is a nullable non-return parameter.

    TDS-RETURN-VALUE-NULLABLE (33)

    Parameter is a nullable return parameter.

    The client specifies the value of this argument.

PARM-NAME

(O) Variable where the name of the incoming parameter is stored. This is the name given to the parameter by the client.

PARM-NAME-LENGTH

(O) Variable where the length of the parameter name is returned. The name length is specified by the client when the RPC is sent.

USER-DATATYPE

(O) Variable where the user-assigned datatype for this parameter is stored. This argument is used for return parameters only.

Returns

The RETCODE argument can contain any of the return values listed in Table 3-18.

Table 3-18: TDINFPRM return values

Return value

Meaning

TDS-OK (0)

Function completed successfully.

TDS-CANCEL-RECEIVED (-12)

Operation canceled. The remote partner issued a cancel. The current operation failed.

TDS-CONNECTION-FAILED (-4998)

Connection abended. The client/server connection abnormally ended (for example, the LU 6.2 session crashed or the remote transaction abended).

TDS-CONNECTION-TERMINATED (-4997)

Connection closed. The remote partner closed (deallocated) the client/server connection.

TDS-ENTRY-NOT-FOUND (-8)

The specified column number, transaction number, or parameter does not exist.

TDS-INVALID-PARAMETER (-4)

Invalid parameter value. The value assigned to one or more of the arguments supplied in the call is not valid. The operation failed.

TDS-INVALID-TDPROC (-18)

Error in specifying a value for the TDPROC argument.

TDS-NO-PARM-PRESENT (103)

No incoming parameters present. TDRCVPRM cannot retrieve a parameter because no more parameters were accepted. The operation failed.

TDS-WRONG-STATE (-6)

This function cannot be used in the current communication state. For example, your program tried to send a reply before it read in all of the client parameters. The application was still in RECEIVE state and could not send. The operation failed.

Examples

Example 1

The following code fragment illustrates a typical use of TDINFPRM. The transaction: calls TDNUMPRM to determine how many parameters to retrieve; calls TDLOCPRM to ascertain the number of the parameter whose information it wants; calls TDINFPRM for a description of the parameter; 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