Previous Topic
Table Of Contents
Parent Topic
Next Topic

High-Level Language SWSFRED (SWPFRD) Function

Related Topics

Web Server API Function Index


May be used in Shadow/REXX
May be used from Other REXX Interpreters
HLL Entry point name is SWPFRD

SWSFRED (entry point "SWPFRD") is a high level function used to retrieve a block of data from files sent to the server in a Post operation.

SWSPostFileRead is the "c" definition for the entry point.

SWSPOSTFILEREAD is the "COBOL" definition for the entry point.

SWSFRED is the "PL/I" definition for the entry point.

CALL Arguments

The SWSFRED (entry point "SWPFRD") function takes four arguments. All four arguments must be specified on the call.

 

Arg
No.
HLL Argument Type I/O Description of Argument
C COBOL PL/I
1 HDBC Usage Pointer PTR Input The Web Server connection handle. This is an opaque, four-byte address pointer. Because the connection handle is currently not used, it must be set to zero (NULL).
2 UDWORD PIC S9(5) COMP FIXED BIN(31) Input A four-byte integer containing the number of files to retrieve data from. This must be an integer in the range of 1 to the return value of a SWSFCNT call.
3 PTR PIC X(nnn) char[nnn] Output A buffer to receive the data being retrieved. The data will be returned in either ASCII (binary), or EBCDIC (translated) based upon the current setting of the file attributes.
4 UDWORD PIC S9(5) COMP FIXED BIN(31) InOut A four-byte integer containing the length of the buffer. This field is updated to reflect the number of bytes returned in the buffer. A length of zero indicates end-of-file.

Top

Return Values

SWSFRED:

  • Returns a block of data from a Posted file and returns the length of the block.
  • Always sets a signed numeric return code value.

Possible values are:

SWS_SUCCESS
The operation succeeded. The file data has been placed in the buffer provided, and the length variable has been updated.
SWS_ERROR
A parameter validation or run-time error was encountered. Error information is available using the SWSERROR function.
SWS_ENVIRONMENT_ERROR
The request can not be processed because of a run-time environmental error. For example, you invoked the API service outside of a Web transaction procedure or from outside the server's address space. Use the server's wrap-around trace to obtain diagnostic information.
SWS_INVALID_HANDLE
The connection handle argument is invalid. No error information can be returned using SWSERROR.
Any other value
The operation has failed
 

The SWSFRED operation is logged to the Server's wrap-around trace file with the returned data and completion code.

 

PL/I Example

   %INCLUDE SPCPHD;               /* INCLUDE STANDARD HEADER FILE    */
                                   /* (includes definition of SWSPFI) */
    DCL   SCONN     PTR;           /* Connection Handle               */
    DCL   FICNT     FIXED BIN(31);  /* Number of files                */
    DCL   BUFF      CHAR(500);      /* Buffer                         */
    DCL   BLEN      FIXED BIN(31);  /* Data length                    */
    ADDR(SCONN)->DMHX=0;            /* Zero connection handle         */
    CALL SWSFCNT(SCONN              /* Get the file count             */
             FICNT);
    RC=PLIRETV();                   /* Get return code                */
    IF RC ^=SWS_SUCCESS THEN        /* exit if bad RC                 */
             EXIT;
    DO I = 1 TO FICNT;              /* Examine each file              */
       BLEN = STORAGE(BUFF);        /* Force to loop at least once    */
       DO WHILE BLEN > 0;
         BLEN = STORAGE(BUFF);      /* Set maximum size to get        */
         CALL SWSFRED(SCONN, BUFF, BLEN); /* Get a block of file data */
         RC = PLIRETV();
         IF RC ^=SWS_SUCCESS THEN   /* exit if bad RC                 */
             EXIT;
         ...                        /* Process File                   */
       END;
    END;

Top

C Example

    HDBC  sConn      =NULL             /* Connection Handle   */
     long  FICNT;                      /* file count          */
     long  RC                          /* return code         */
     int   i;
     char  buff[500]
     int   blen;
     SWS_POST_FILE_INFO_BLOCK info;    /* file attributes     */
     rc = SWSPostFileCount (sConn,     /* Get the file count  */
           &FICNT);
     If(rc ^=SWS_Success) return;      /* exit if bad rc      */
     for (i = 1; i <+ FICNT; i++) {    /* look at each file   */
       blen = sizeof(buff);         /* force to loop at least once */
       while (blen > 0) {              /* read all the data   */
         blen = sizeof(buff);          /* re-set the length   */
         rc = SWSPostFileRead(&sConn,  /* Get data            */
                    buff               /* data buffer         */
                    &blen;             /* size of line        */
       If(rc ^=SWS_SUCCESS) return;    /* exit if bad rc      */
       ...                             /* Process file        */
     };
    };
         

 

COBOL Example

    COPY SBCPHD.
    77 SCONN         USAGE IS POINTER.
    77 FICNT         PIC S9(5) COMP.
    77 I-COUNT       PIC S9(5) COMP VALUE 0.
    77 READ-SIZE     PIC S9(5) COMP VALUE 0.
    77 READ-BUF      PIC X(300).
    CALL SWSPOSTFILECOUNT USING SCONN,
             FICNT.
    MOVE RETURN CODE TO WS-SWSAPI-RETURN-CODE.
    IF NOT SWS-SUCCESS GOBACK.
    PERFORM 0000-SWSREADFILE-ROUTINE WITH TEST BEFORE
      VARYING I-COUNT FROM 1 BY 1 UNTIL I-COUNT > FICNT.
    GOBACK.
*
    0000-SWSREADFILE-ROUTINE.
      MOVE 300 TO READ-SIZE.
      PERFORM 0000-SWSREADBLOCK-ROUTINE WITH TEST BEFORE
        UNTIL READ-SIZE = 0.
*
    0000-SWSREADFILE-EXIT.
      EXIT.
*
    0000-SWSREADBLOCK-ROUTINE.
      MOVE 300 TO READ-SIZE.
      CALL SWSPOSTFILEREAD USING CONNECTION-HANDLE
                                    I-COUNT
                                    READ-BUF
                                    READ-SIZE.
 
     IF RETURN-CODE IS NOT EQUAL TO ZERO
        GOBACK.
*       process file
        ...
     0000-SWSREADBLOCK-EXIT.
        EXIT.


Top