z/OS Communications Server: IP IMS Sockets Guide
Previous topic | Next topic | Contents | Contact z/OS | Library | PDF


EZACIC06

z/OS Communications Server: IP IMS Sockets Guide
SC27-3653-00

The SELECT and SELECTEX call uses bit strings to specify the sockets to test and to return the results of the test. Because bit strings are difficult to manage in COBOL, you might want to use the EZACIC06 utility program to translate them to character strings to be used with the SELECT or SELECTEX call.

Figure 1 shows an example of EZACIC06 call instructions.

Figure 1. EZACIC06 call instruction example
WORKING-STORAGE SECTION.                                                 
    01  CHAR-MASK.                                              
        05 CHAR-STRING              PIC X(nn).                  
                                                                
    01  CHAR-ARRAY                  REDEFINES CHAR-MASK.        
        05  CHAR-ENTRY-TABLE        OCCURS nn TIMES.            
            10  CHAR-ENTRY          PIC X(1).                   
    01  BIT-MASK.                                               
        05 BIT-ARRAY-FWDS           OCCURS (nn+31)/32 TIMES.    
           10  BIT_ARRAY_WORD       PIC 9 (8) COMP.             
                                                                
    01  BIT-FUNCTION-CODES.                                     
        05  CTOB                    PIC X(4) VALUE 'CTOB'.      
        05  BTOC                    PIC X(4) VALUE 'BTOC'.      
                                                                
    01  CHAR-MASK-LENGTH            PIC 9(8) COMP VALUE nn.     
                                                                
                                                                
                                                                
   PROCEDURE CALL (to convert from character to binary)         
     CALL 'EZACIC06' USING CTOB                                 
                           BIT-MASK                             
                           CHAR-MASK                            
                           CHAR-MASK-LENGTH                     
                           RETCODE.                             
                                                                
                                                                
   PROCEDURE CALL (to convert from binary to character)         
     CALL 'EZACIC06' USING BTOC                                 
                           BIT-MASK                             
                           CHAR-MASK                            
                           CHAR-MASK-LENGTH                     
                           RETCODE.                             
 
 

For equivalent PL/I and assembly language declarations, see Converting parameter descriptions.

CHAR-MASK
Specifies the character array where nn is the maximum number of sockets in the array. The first character in the array represents socket 0, the second represents socket 1, and so on. Note that the index is 1 greater than the socket number [for example, CHAR-ENTRY(1) represents socket 0, CHAR-ENTRY (2) represents socket 1, and so on.]
BIT-MASK
Specifies the bit string to be translated for the SELECT call. Within each fullword of the bit string, the bits are ordered right to left. The rightmost bit in the first fullword represents socket 0 and the leftmost bit represents socket 31. The rightmost bit in the second fullword represents socket 32 and the leftmost bit represents socket 63. The number of fullwords in the bit string should be calculated by dividing the sum of 31 and the character array length by 32 (truncate the remainder).
COMMAND
BTOC specifies bit string to character array translation.

CTOB specifies character array to bit string translation.

CHAR-MASK-LENGTH
Specifies the length of the character array. This field should be no greater than 1 plus the MAXSNO value returned on the INITAPI (which is usually the same as the MAXSOC value specified on the INITAPI).
RETCODE
A binary field that returns one of the following values:
Value
Description
0
Successful call.
-1
Check ERRNO for an error code.

Examples

If you want to use the SELECT call to test sockets 0, 5, and 32, and you are using a character array to represent the sockets, you must set the appropriate characters in the character array to 1. In this example, index positions 1, 6 and 33 in the character array are set to 1. Then you can call EZACIC06 with the COMMAND parameter set to CTOB. When EZACIC06 returns, the first fullword of BIT-MASK contains B'00000000000000000000000000100001' to indicate that sockets 0 and 5 will be checked. The second word of BIT-MASK contains B'00000000000000000000000000000001' to indicate that socket 32 will be checked. These instructions process the bit string shown in the following example:
MOVE ZEROS TO CHAR-STRING.
MOVE '1' TO CHAR-ENTRY(1), CHAR-ENTRY(6), CHAR-ENTRY(33).
CALL 'EZACIC06' USING TOKEN CTOB BIT-MASK CH-MASK
      CHAR-MASK-LENGTH RETCODE.
MOVE BIT-MASK TO ....
When the select call returns and you want to check the bit-mask string for socket activity, enter the following instructions.
MOVE ..... TO BIT-MASK.
CALL 'EZACIC06' USING TOKEN BTOC BIT-MASK CH-MASK
         CHAR-MASK-LENGTH RETCODE.
PERFORM TEST-SOCKET THRU TEST-SOCKET-EXIT  VARYING IDX
     FROM 1 BY 1 UNTIL IDX EQUAL CHAR-MASK-LENGTH.
 
TEST-SOCKET.
      IF CHAR-ENTRY(IDX) EQUAL '1'
           THEN PERFORM SOCKET-RESPONSE THRU SOCKET-RESPONSE-EXIT
           ELSE NEXT SENTENCE.
TEST-SOCKET-EXIT.
      EXIT.

Go to the previous page Go to the next page




Copyright IBM Corporation 1990, 2014