Skip to main content development
   toolset
 
  Easy400   |       iSeries home
Public-Source
 
Introduction
Tutorial
Examples
FAQ
Index
Download
 
 

 
2.8 - Data handling functions


  •  QChar2Hex  - Convert a character string to hexadecimal
    Input parameter:
    • input character string (char 16000)
    Returned value:
    • computed hexadecimal character string (char 32000)

    Example:
                ...         ...         ...
           SPECIAL-NAMES.
                 copy CPYSPCNAME of CGICBLDEV2-QCBLLESRC.
                ...         ...         ...
          * Variables for QChar2Hex procedure
               05     CharsIn             PIC  X(16000).
               05     CharsOut            PIC  X(32000).
                ...         ...         ...
          * Convert char string CharsIn to hex string CharsOut
                call 'QCHAR2HEX' using CharsIn
                                 returning into CharsOut.
    

    See also program TCHAR2HEX.

  •  QHex2Char  - Convert an hexadecimal string to character
    Input parameter:
    • input hexadecimal character string (char 32000)
    Returned value:
    • computed character string (char 16000)

    Example:
                ...         ...         ...
           SPECIAL-NAMES.
                 copy CPYSPCNAME of CGICBLDEV2-QCBLLESRC.
                ...         ...         ...
          * Variables for QHex2Char procedure
               05     CharsIn             PIC  X(32000).
               05     CharsOut            PIC  X(16000).
                ...         ...         ...
          * Convert hex string CharsIn to char string CharsOut
                call 'QHEX2CHAR' using CharsIn
                                 returning into CharsOut.
    

    See also program THEX2CHAR.

  •  QUppify  - Convert a character string to uppercase
    Input parameter:
    • character string to be converted uppercase (char 32767)
    Returned value:
    • character string converted to uppercase (char 32767)

    Example:
                ...         ...         ...
           SPECIAL-NAMES.
                 copy CPYSPCNAME of CGICBLDEV2-QCBLLESRC.
                ...         ...         ...
          * Variables for Quppify procedure
               05     CharsIn             PIC  X(32767).
               05     CharsOut            PIC  X(32767).
                ...         ...         ...
          * Convert char string CharsIn to uppercase into string CharsOut
                call 'QUPPIFY' using CharsIn
                               returning into CharsOut.
    


  •  QLowfy  - Convert a character string to lowercase
    Input parameter:
    • character string to be converted lowercase (char 32767)
    Returned value:
    • character string converted to lowercase (char 32767)

    Example:
                ...         ...         ...
           SPECIAL-NAMES.
                 copy CPYSPCNAME of CGICBLDEV2-QCBLLESRC.
                ...         ...         ...
          * Variables for Qlowfy procedure
               05     CharsIn             PIC  X(32767).
               05     CharsOut            PIC  X(32767).
                ...         ...         ...
          * Convert char string CharsIn to lowercase into string CharsOut
                call 'QLOWFY' using CharsIn
                              returning into CharsOut.
    


  •  QChkNbr  - Check for a valid number
    Checks a character string to see if it contains a valid number. The only valid characters are -0123456789 and the character being used as the decimal point.

    The following parameters must be passed:

    1. Output: - numeric field containing
      • 0 = no error
      • -1 = some error(s)
    2. Input: - 32 byte character field containing data intended to be a valid decimal number.

    Example:
                    ...         ...         ...
          * Variables for QChkNbr procedure
               05     isNumeric           PIC  S9(10) comp-3 value 0.
               05     char32              PIC  X(32).
            ...         ...         ...
          * Check for numeric value
               call procedure 'QCHKNBR' using isNumeric
                                              char32.
    

    See also program RANDOMINT.




  •     Contact