Data Type Definitions of ILE CEE APIs

The data types that are used in the parameter tables for each ILE CEE API are defined in Data Type Definitions across ILE Languages. The information in the ILE RPG column assumes RPG D-Specification coding.

Data Type Definitions across ILE Languages

Data Type Description ILE C ILE COBOL ILE RPG
CHAR A 1-byte unsigned character typedef unsigned char _CHAR;
PIC X
blank or A in data type
column
To/L of 1

UCHAR A 1-byte unsigned character typedef unsigned char _UCHAR;
PIC X
blank or A in data type
column
To/L of 1

SCHAR A 1-byte signed character typedef signed char _SCHAR;
PIC X
blank or A in data type
column
To/L of 1

INT2 A 2-byte signed integer typedef signed short _INT2;
PIC S9(4) BINARY
I in data type column
To/L of 5
decimal positions = 0

UINT2 A 2-byte unsigned integer typedef unsigned short _UINT2;
PIC 9(4) BINARY
U in data type column
To/L of 5
decimal positions = 0

INT4 A 4-byte signed integer typedef signed int _INT4;
PIC S9(9) BINARY
I in data type column
To/L of 10
decimal positions = 0

UINT4 A 4-byte unsigned integer typedef unsigned int _UINT4;
PIC 9(9) BINARY
U in data type column
To/L of 10
decimal positions = 0

FLOAT4 A 4-byte single-precision floating-point number typedef float _FLOAT4;
COMP-1
F in data type column
To/L of 4

FLOAT8 An 8-byte double-precision floating-point number typedef double _FLOAT8;
COMP-2
F in data type column
To/L of 8

COMPLEX8 An 8-byte complex number, whose real and imaginary parts are each 4-byte single-precision floating-point numbers. Used only by ILE math routines.
typedef struct {
   float  real,
          imaginary;
} _COMPLEX8;

01 complex8
  02 real comp-1
  02 imag comp-1

  Name        To/L
  Entry       Entry
complex8  DS
   real         4F
   imaginary    4F

COMPLEX16 A 16-byte complex number whose real and imaginary parts are each 8-byte double-precision floating-point numbers. Used only by ILE math routines.
typedef struct {
   double real,
          imaginary;
} _COMPLEX16;

01 complex16
  02 real comp-2
  02 imag comp-2

  Name        To/L
  Entry       Entry
complex16 DS
   real         8F
   imaginary    8F

BITS A set of adjacent bits within a single storage unit. The notation is _BITS: x, where x is the field width in bits. (BITS may also be used to define unsigned integers.) typedef unsigned int _BITS;
Not applicable Not applicable
POINTER A platform-dependent address pointer typedef void * _POINTER;
USAGE IS POINTER
* in data type column
procedure pointer = 
            ProcPtr
basing pointer is the 
default if ProcPtr is 
not defined in
the keyword section.

INVPTR An invocation pointer
typedef void * _INVPTR;
#pragma pointer (_INVPTR,
INVPTR)

Not applicable Not applicable
LBLPTR A label pointer
typedef void * _LBLPTR;
#pragma pointer (_LBLPTR,
LBLPTR)

Not applicable Not applicable
CHARn A string (character array) of length n typedef char[n] _CHAR[n]; PIC X(n)
blank or A in data type
column
To/L >= 1

VFLOAT An ILE variable-length floating-point number used for polymorphic parameter declarations. The length may be any one of 4, 8, or 16 bytes corresponding to single, double, and extended precision.
typedef union {
   float TypeFloat4;
   double TypeFloat8;
   long double TypeFloat16;
} _VFLOAT;

Not applicable Not applicable
VSTRING An ILE string of arbitrary length used for polymorphic string parameter declarations. The string may be any one of a fixed-length string, a null-terminated varying string (known as an "ASCIIZ") or a length-prefixed string.
(See note 1)
typedef union {
    struct {
       _INT2    length;
       _CHAR255 string;
    } l2pstring;
    struct {
       _INT4    length;
       _CHAR255 string;
    } l4pstring;
    _CHAR1 stringz;
} _VSTRING;
01 string4
  02 len pic 9(9) 
          binary
  02 txt pic x(n)
01 string2
  REDEFINES string4
  02 len pic 9(4) 
          binary
  02 txt pic x(n)

   Name         To/L
   Entry        Entry
vstring    DS
   len        1   2I 0
   txt        3   n
   len2       1   4I 0
   txt2       5   n

FEEDBACK A mapping of the feedback (condition) token (fc)
typedef volatile struct {
   _UINT2 MsgSev;
   _UINT2 MsgNo;
   _BITS Case     :2;
   _BITS Severity :3;
   _BITS Control  :3;
   _CHAR Facility_ID[3];
   _UINT4 I_S_Info;
} _FEEDBACK;

01 fc
  02 sev   pic 9(4) 
             binary
  02 msgno pic 9(4) 
             binary
  02 flgs  pic x(1)
  02 facid pic x(3)
  02 isi   pic 9(9) 
             binary

   Name         To/L
   Entry        Entry
fc         DS
   sev            5U
   msgno          5U
   flags          1
   facid          3
   isi           10U

CEE-ENTRY A generic entry constant
struct {
_POINTER address;
_POINTER nesting;
}

01 STRUC-NAME.
  05 STRUC-ADDRESS 
           POINTER.
  05 STRUC-NESTING 
           POINTER.

DCEE_ENTRY   DS
D Address_Ptr *  ProcPtr
D Nesting_Ptr *  ProcPtr

HDLR_ ENTRY A procedure pointer used on the CEEHDLR and CEEHDLU APIs.
typedef void (*_HDLR_ENTRY)
           ( _FEEDBACK *,
             _POINTER *,
             _INT4 *,
             _FEEDBACK * );

77 HDLR_ENTRY
     PROCEDURE-
	    POINTER

DHDLR_ENTRY *  ProcPtr

RTX_ENTRY A procedure pointer used on the CEERTX and CEEUTX APIs.
typedef void (*_RTX_ENTRY)
             ( _POINTER *);

77 RTX_ENTRY
     PROCEDURE-
	 POINTER

DRTX_ENTRY *  ProcPtr

RAGE_ ENTRY A procedure pointer used on the CEE4RAGE API.
typedef void (*_RAGE_ENTRY)
             ( _UINT4 *,
               _UINT4 *,
               _UINT4 *,
               _UINT4 * );

77 RAGE_ENTRY
     PROCEDURE-
	 POINTER

DRAGE_ENTRY *  ProcPtr

CEELABEL A target label to a code point within a call stack entry.
typedef volatile struct {
    _INVPTR invocation;
    _LBLPTR label;
} _CEELABEL;

Not applicable Not applicable
Note:
1 The typedef for VSTRING is only an indication of the variable string. For ILE C purposes this should be coded as char *.

Strong alignment is assumed in all data structures. Each item is aligned on the proper boundary for its type, with padding if necessary.

For more information about using ILE CEE APIs, see the following sections:




[ Back to top | ILE CEE APIs | APIs by category ]