Sends an error or informational message to the client.
COPY SYGWCOB.
01 TDPROC PIC S9(9) USAGE COMP SYNC. 01 RETCODE PIC S9(9) USAGE COMP SYNC. 01 MESSAGE-TYPE PIC S9(9) USAGE COMP SYNC. 01 MESSAGE-NUMBER PIC S9(9) USAGE COMP SYNC. 01 SEVERITY PIC S9(9) USAGE COMP SYNC. 01 ERROR-STATE PIC S9(9) USAGE COMP SYNC. 01 LINE-ID PIC S9(9) USAGE COMP SYNC. 01 TRANSACTION-ID PIC X(n). 01 TRANSACTION-ID-LENGTH PIC S9(9) USAGE COMP SYNC. 01 MESSAGE-TEXT PIC X(n). 01 MESSAGE-LENGTH PIC S9(9) USAGE COMP SYNC.
CALL 'TDSNDMSG' USING TDPROC, RETCODE, MESSAGE-TYPE, MESSAGE-NUMBER, SEVERITY, ERROR-STATE, LINE-ID, TRANSACTION-ID, TRANSACTION-ID-LENGTH, MESSAGE-TEXT, MESSAGE-LENGTH.
(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.
(O) Variable where the result of function execution is returned. Its value is one of the codes listed in Table 3-40.
(I) Category of message being sent. Indicates whether it is an informational message or an error message. Assign this argument one of the following values:
TDS-INFO-MSG (1) |
Message is an informational message. |
TDS-ERROR-MSG (2) |
Message is an error message. |
(I) Message number. This value is always four bytes in length. Where possible, use Sybase-compatible error numbers.
For messages sent to Open Client programs, this value is stored in the SMSG-NO field of the Open Client CS-SERVERMSG structure.
(I) Severity level of the error. A value of 10 or less represents an informational message.
For messages sent to Open Client clients, this value is stored in the SMSG-SEV field of the Open Client CS-SERVERMSG structure.
Specify one of the following severity values:
TDS-INFO-SEV (0) |
Informational message |
TDS-ERROR-SEV (10) |
Error message |
(I) Error state number. This number provides additional information about the context of the error.
For messages sent to Open Client clients, this value is stored in the SMSG-STATE field of the Open Client CS-SERVERMSG structure.
(I) An additional identifier assigned by the program. You determine how to use this argument at your site.
For messages sent to Open Client clients, this value is stored in the SMSG-LINE field of the Open Client CS-SERVERMSG structure.
(I) Identifier of the transaction that is currently executing. This value identifies the transaction that is issuing the error message.
Under CICS: This is the TRANSID from the CICS PCT.
Under IMS TM: This is the transaction name defined when the system is generated.
Under MVS: This is the APPC transaction name defined in the transaction profile.
(I) Length of the TRANSACTION-ID. For graphic datatypes, this is the number of double-byte characters; for other datatypes, it is the number of bytes.
Under CICS: For CICS Version 1.7, this value is always 4 or less. For later versions, it is the actual length of the transaction ID, which can be greater than 4.
Under IMS TM: This value is always 8 or less.
Under MVS: This is the APPC transaction name defined in the transaction profile. This value is normally 8 or less.
(I) The text of the message.
For messages sent to Open Client clients, this value is stored in the SMSG-TEXT field of the Open Client CS-SERVERMSG structure.
(I) Length of the message text. The maximum permitted length for a message is 512 bytes.
If you are using the Japanese Conversion Module (JCM), it adjusts this length to the length used by the client character set.
For messages sent to Open Client clients, this value is stored in the SMSG-TEXT-LEN field of the CS-SERVERMSG structure.
The RETCODE argument can contain any of the return values listed in Table 3-40.
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-ILLEGAL-REQUEST (-5) |
Illegal function. The operation failed. This code can indicate that a client application is trying to use a Gateway-Library function that is not supported for clients (for example, TDSNDROW). |
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-LENGTH (-173) |
Wrong length. The length specified in the MESSAGE-LENGTH argument is too long. |
TDS-INVALID-NAMELENGTH (-179) |
Invalid name length. The length specified for the column, parameter, message, or server name is invalid. |
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-STATUS (-174) |
Invalid status value. The value entered in the STATUS field is invalid. |
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-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. |
The following code fragment shows how a program uses TDSNDMSG to send an error message to a client. This example is taken from the sample program, SYCCSAR2, in Appendix B, “Sample RPC Application for CICS.”
*----------------------------------------------------------------- SEND-SQL-ERROR. *----------------------------------------------------------------- MOVE SQLCODE TO MSG-SQL-ERROR-C. MOVE SQLERRMC TO MSG-SQL-ERROR-K. * ------------------------------------------------------------- * ensure possible non-printables translated to spaces * ------------------------------------------------------------- PERFORM VARYING MSG-SQL-ERROR-SS FROM 1 BY 1 UNTIL MSG-SQL-ERROR-SS > SQLERRML IF MSG-SQL-ERROR-K-CHARS(MSG-SQL-ERROR-SS) < SPACE OR MSG-SQL-ERROR-K-CHARS(MSG-SQL-ERROR-SS) > '9' THEN MOVE SPACE TO MSG-SQL-ERROR-K-CHARS(MSG-SQL-ERROR-SS) END-IF END-PERFORM. MOVE MSG-SQL-ERROR TO MSG-TEXT. MOVE LENGTH OF MSG-SQL-ERROR TO MSG-TEXT-L. PERFORM SEND-ERROR-MESSAGE. *----------------------------------------------------------------- SEND-ERROR-MESSAGE. *----------------------------------------------------------------- MOVE 'N' TO SEND-DONE-SW. MOVE MSG-SEVERITY-ERROR TO MSG-SEVERITY. MOVE MSG-NR-ERROR TO MSG-NR. MOVE TDS-ERROR-MSG TO MSG-TYPE. PERFORM SEND-MESSAGE. *----------------------------------------------------------------- SEND-MESSAGE. *----------------------------------------------------------------- MOVE LENGTH OF MSG-RPC TO MSG-RPC-L. * Ensure we're in right state to send a message CALL 'TDSTATUS' USING GWL-PROC, GWL-RC, GWL-STATUS-NR, GWL-STATUS-DONE, GWL-STATUS-COUNT, GWL-STATUS-COMM, GWL-STATUS-RETURN-CODE, GWL-STATUS-SUBCODE. IF (GWL-RC = TDS-OK AND GWL-STATUS-COMM = TDS-RECEIVE) THEN CALL 'TDSNDMSG' USING GWL-PROC, GWL-RC, MSG-TYPE, MSG-NR, MSG-SEVERITY, TDS-ZERO, TDS-ZERO, MSG-RPC, MSG-RPC-L, MSG-TEXT, MSG-TEXT-L END-IF.
This code fragment illustrates the use of TDSTATUS and TDSNDMSG in a Gateway-Library transaction using the IMS TM implicit API. This example is taken from the sample program in Appendix D, “Sample RPC Application for IMS TM (Implicit).”
*----------------------------------------------------------------- SEND-ERROR-MESSAGE. *----------------------------------------------------------------- MOVE 'N' TO SEND-DONE-SW. MOVE TDS-ERROR-MSG TO MSG-TYPE. MOVE LENGTH OF MSG-RPC TO MSG-RPC-L.
* Ensure we're in right state to send a message
CALL 'TDSTATUS' USING GWL-PROC, GWL-RC, GWL-STATUS-NR, GWL-STATUS-DONE, GWL-STATUS-COUNT, GWL-STATUS-COMM, GWL-STATUS-RETURN-CODE, GWL-STATUS-SUBCODE.
IF (GWL-RC = TDS-OK AND GWL-STATUS-COMM = TDS-RECEIVE) THEN
CALL 'TDSNDMSG' USING GWL-PROC, GWL-RC, MSG-TYPE, MSG-NR, MSG-SEVERITY, TDS-ZERO, TDS-ZERO, MSG-RPC, MSG-RPC-L, MSG-TEXT, MSG-TEXT-L END-IF.
IMS TM Users: The term “message” is
used here in the narrow sense of error or informational messages
sent to the client; it is not used in the IMS TM sense of message
processing.
A server application uses this function to send an error or informational message to a remote client.
Errors related to the operation of the TRS are recorded in its error log, available to the TRS administrator. Errors related to the client program are passed on to the requesting client. A client handles an Open ServerConnect error message like any error returned by Adaptive Server.
Messages can be sent before a row is described or after all rows are sent. An application can call TDSNDMSG either before a TDESCRIB or after the last TDSNDROW call for the described row. No messages can be sent between a TDESCRIB and a TDSNDROW or between two TDSNDROW calls.
Your application must be in SEND state for this function to execute successfully. If it is not in SEND state, TDSNDMSG returns TDS-WRONG-STATE. Call TDRESULT to put your application in SEND state.
A transaction can send a message to a client after TDSNDDON only if the value of the TDSNDDON argument STATUS is TDS-DONE-CONTINUE, and the value of CONN-OPTIONS is TDS-FLUSH. If the value of CONN-OPTIONS is TDS-ENDRPC or TDS-ENDREPLY, no messages can be sent after a TDSNDDON call is issued.
If the JCM is used, TDSNDMSG converts the message data from the mainframe character set to the workstation character set and adjusts the message length before sending, if necessary.
Related documents
Open Client DB-Library Reference Manual (dbmsghandle)
Mainframe Connect Client Option and Server Option Messages and Codes
Mainframe Connect DirectConnect for z/OS Option User's Guide for Transaction Router Services
Copyright © 2005. Sybase Inc. All rights reserved. |
![]() |