TDRCVPRM

Description

Retrieves the data from an RPC parameter sent by a remote client.

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 HOST-VARIABLE      PIC X(n). 
01 HOST-VARIABLE-TYPE PIC S9(9)  USAGE COMP SYNC.
01 MAX-DATA-LENGTH    PIC S9(9)  USAGE COMP SYNC.
01 ACTUAL-DATA-LENGTH PIC S9(9)  USAGE COMP SYNC.
CALL 'TDRCVPRM' USING TDPROC, RETCODE, PARM-ID,
               HOST-VARIABLE, HOST-VARIABLE-TYPE,
                MAX-DATA-LENGTH, ACTUAL-DATA-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.

RETCODE

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

PARM-ID

(I) Number of the parameter or cursor parameter to be received. Parameters are numbered sequentially with the first parameter number one.

HOST-VARIABLE

(O) Host program variable where the parameter data is stored.

HOST-VARIABLE-TYPE

(I) Datatype of the HOST-VARIABLE. This is the datatype that is used in mainframe processing of this parameter.

MAX-DATA-LENGTH

(I) Maximum length of the data that can be stored in the named HOST-VARIABLE. For TDSVARYCHAR, TDSVARYBIN, and TDSVARYGRAPHIC parameters, this value does not include the 2 bytes for the “LL” length specification.

For graphic datatypes, this is the number of double-byte characters. For a Sybase numeric or decimal parameter, it is 35. For other datatypes, it is the number of bytes.

To determine the maximum length of the incoming data, use TDINFPRM. For fixed-length datatypes, this value is ignored.

ACTUAL-DATA-LENGTH

(O) Variable where the actual length of the received data is returned. For TDSVARYCHAR, TDSVARYBIN, and TDSVARYGRAPHIC parameters, this value does not include the 2 bytes for the “LL” length specification. If this length is greater than the specified MAX-DATA-LENGTH, the data is truncated, and TDRCVPRM returns TDS-TRUNCATION-OCCURRED.

For graphic datatypes, this is the number of double-byte characters; for other datatypes, it is the number of bytes.

Returns

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

Table 3-24: TDRCVPRM 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-DATE-CONVERSION-ERROR (-23)

Error in conversion of datetime data. This can be a result of trying to convert short datetime (TDSDATETIME4) for a client using an early TDS version. TDS versions earlier than 4.2 do not support the short datetime datatype.

TDS-DECIMAL-CONVERSION-ERROR (-24)

Error in conversion of packed decimal data.

TDS-ENTRY-NOT-FOUND (-8)

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

TDS-FLOAT-CONVERSION-ERROR (-21)

Error in conversion of float values.

TDS-INVALID-DATA-CONVERSION (-172)

Incompatible datatypes. The source datatype cannot be converted into the requested result datatype.

TDS-INVALID-DATA-TYPE (-171)

Illegal datatype. A Sybase datatype supplied in the call is not supported and the conversion cannot be done. The operation failed.

TDS-INVALID-ID-VALUE (-10)

The specified column or parameter number is greater than the system maximum. Sybase allows as many columns per table result and parameters per RPC as the system maximum.

TDS-INVALID-LENGTH (-173)

Wrong length. The length specified in the xxx-LENGTH argument is too long.

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-INVALID-VAR-ADDRESS (-175)

Specified variable address is invalid. No variable with the specified name exists. A NULL value was specified. The operation failed.

TDS-MONEY-CONVERSION-ERROR (-22)

Error in conversion of TDSMONEY-type data. This can be a result of trying to convert to short money (TDSMONEY4) for a client using an early TDS version. TDS versions earlier than 4.2 do not support the short money datatype.

TDS-NO-PARM-PRESENT (103)

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

TDS-TRUNCATION-OCCURRED (-13)

Data was truncated. The actual data length was longer than the maximum data length allotted for this data.

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 TDRCVPRM. The transaction does the following: 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.

Example 2

The following code fragment illustrates the use of TDRCVPRM in a Gateway-Library program that uses the IMS TM implicit API. This example is taken from the sample program in Appendix D, “Sample RPC Application for IMS TM (Implicit).”

 
 *    ------------------------------------------------------------
 *    establish gateway environment
 *    ------------------------------------------------------------
     CALL ‘TDINIT’ USING IO-PCB, GWL-RC, GWL-INIT-HANDLE.
      .
      . [check return code]
      .
 *    ------------------------------------------------------------
 *    set program type to MPP 
 *    ------------------------------------------------------------
     CALL ‘TDSETPT’ USING  GWL-INIT-HANDLE, GWL-RC, 
                            GWL-PROG-TYPE, GWL-SPA-PTR, 
                            TDS-NULL, TDS- NULL.
          . [check return code]
      .
 *    ------------------------------------------------------------
 *    accept client request
 *    ------------------------------------------------------------
     CALL ‘TDACCEPT’ USING GWL-PROC, GWL-RC, GWL-INIT-HANDLE,
                            SNA-CONNECTION-NAME, SNA-SUBC.
      .
      . [check return code]
      .
 *----------------------------------------------------------------
  READ-IN-USER-PARM.
 *----------------------------------------------------------------
      MOVE ‘Y’ TO SEND-DONE-SW.
      MOVE ‘N’ TO ALL-DONE-SW.
      MOVE SPACES TO CALL-ERROR.
      MOVE ZEROES TO CALL-ERROR-RC CTR-ROWS.
      MOVE 1 TO CTR-COLUMN.
      MOVE LENGTH OF PARM-DEPT TO WRKLEN1.
CALL ‘TDRCVPRM’ USING  GWL-PROC, GWL-RC, PARM-ID1, PARM-DEPT, 
                        TDSCHAR, WRKLEN1, PARM-L. 
     IF GWL-RC NOT EQUAL TO ZEROES THEN 
            MOVE ‘TDRCVPRM’ TO CALL-ERROR 
            PERFORM DISPLAY-CALL-ERROR 
      END-IF. 

Usage


Datatype conversions

If the parameter datatype is different from the one specified in HOST-VARIABLE-TYPE, TDRCVPRM converts it to the specified datatype before processing (implicit conversion).

Table 3-25 shows which implicit conversions can be performed by TDRCVPRM.


For Japanese users

See also

Related functions

Related topics