NTOP

The NTOP call converts an IP address from its numeric binary form into a standard text presentation form. On successful completion, NTOP returns the converted IP address in the buffer provided.

The following requirements apply to this call:

Figure 1 shows an example of NTOP call instructions.

Figure 1. NTOP call instruction example
    WORKING-STORAGE SECTION.
        01  SOC-ACCEPT-FUNCTION      PIC X(16)  VALUE IS 'ACCEPT'.
        01  SOC-NTOP-FUNCTION        PIC X(16)  VALUE IS 'NTOP'.
        01  S                        PIC 9(4) BINARY.
        
    * IPv4 socket structure.
        01  NAME.
            03  FAMILY      PIC 9(4) BINARY.
            03  PORT        PIC 9(4) BINARY.
            03  IP-ADDRESS  PIC 9(8) BINARY.
            03  RESERVED    PIC X(8).

    * IPv6 socket structure.
        01  NAME.
            03  FAMILY      PIC 9(4) BINARY.
            03  PORT        PIC 9(4) BINARY.
            03  FLOWINFO    PIC 9(8) BINARY.
            03  IP-ADDRESS.
                10 FILLER   PIC 9(16) BINARY.
                10 FILLER   PIC 9(16) BINARY.
            03  SCOPE-ID    PIC 9(8) BINARY.
        01  NTOP-FAMILY     PIC 9(8) BINARY.
        01  ERRNO           PIC 9(8) BINARY.
        01  RETCODE         PIC S9(8) BINARY.

        01  PRESENTABLE-ADDRESS      PIC X(45).
        01  PRESENTABLE-ADDRESS-LEN  PIC 9(4) BINARY.

    PROCEDURE DIVISION.

         CALL 'EZASOKET' USING SOC-ACCEPT-FUNCTION S NAME
               ERRNO RETCODE.
         CALL 'EZASOKET' USING SOC-NTOP-FUNCTION NTOP-FAMILY IP-ADDRESS 
                 PRESENTABLE-ADDRESS 
               PRESENTABLE-ADDRESS-LEN ERRNO RETURN-CODE.