C$SOCKET
The C$SOCKET library routine provides a number of functions to manage sockets.
Syntax:
 CALL "C$SOCKET" USING opCode 
                       parameters
                GIVING returnCode
Parameters:
opCode
Function to be executed. Valid values, defined in issocket.def, are:
 
Creates a new server socket on specific port
 
Accepts connections
 
Creates a new client connecting to a server socket
 
Closes a socket
 
Writes data into socket
 
Read data from socket
 
Flush socket data
 
Empty socket
 
Returns the name of the pc hosting the socket
 
Returns the machine name associated to the socket
 
Returns the IP address associated to the socket
 
Returns machine name, IP and port associated to the socket
 
Returns the error-code of last operation
 
Returns the next readable socket
parameters
Parameters depend on the opcode.
Note: Acucobol-GT op-codes names having the prefix "AGS-" instead of "CSOCKET-" are supported for compatibility.
Return code:
returnCode can be any signed numeric data item. The meaning depends on the opcode.
Examples:
Example - Socket server program to listen messages from different clients and respond to them
       program-id. sockserver.
 
       working-storage section.
       copy "issocket.def".
 
       78  data-len        value 1024.
       77  sock-hnd-1      usage handle.
       77  sock-hnd-2      usage handle.
       77  client-data     pic x(data-len).
       77  bytes-read      pic s9999.
       77  sock-timeout    signed-int value -1.
       77  sock-thread     pic 9(4).
 
       procedure division chaining sock-thread.
       main.
           call "c$socket" using csocket-create-server, sock-thread
                           giving sock-hnd-1.
           if sock-hnd-1 = null
              perform exit-program
           end-if.
 
           perform until client-data(1:9) = "sockclose"
               call "c$socket" using csocket-next-read, sock-hnd-1,
                                     sock-timeout giving sock-hnd-2
               move sock-hnd-2 to return-code
               if return-code = -1
                   call "c$socket" using csocket-close, sock-hnd-1
                   call "c$sleep" using 4
                   go to main
               end-if
               if return-code = 0
                   exit perform 
               end-if
               if sock-hnd-2 = sock-hnd-1
                   call "c$socket" using csocket-accept, sock-hnd-1
                   exit perform
               end-if
               call "c$socket" using csocket-read, sock-hnd-2,
                                     client-data, data-len
                               giving bytes-read
               if bytes-read = data-len
                   if client-data(1:9not = "sockclose"
                       perform process-request
                   end-if
               else
                   if bytes-read = -1
                       call "c$socket" using csocket-close, sock-hnd-2
                   else
                       move "01 Resend data" to client-data
                       call "c$socket" using csocket-write, sock-hnd-2,
                                       client-data, data-len
                   end-if
               end-if
           end-perform.
           perform exit-program.
 
       exit-program.
           goback.
 
       process-request.
            move "00 data ok" to client-data
            call "c$socket" using csocket-write, sock-hnd-2,
                                  client-data, data-len.