Accelerator Manual (G06.27+, H06.04+, J06.03+)
Data Type Correspondence and Return Value Sizes
Accelerator Manual—527303-003
A-2
Table A-1. Integer Types, Part 1
8-Bit Integer 16-Bit Integer 32-Bit Integer
BASIC STRING INT
INT(16)
INT(32)
Cchar 
1
unsigned char
signed char
int in the 16-bit data model
short
unsigned
int in the 32-bit or wide data 
model
long
unsigned long
COBOL Alphabetic
Numeric DISPLAY
Alphanumeric-Edited
Alphanumeric 
Numeric-Edited
PIC S9(n) COMP or PIC (n)   
COMP without P or V, 1≤n≤4
Index Data Item 
2
NATIVE-2 
3
PIC S9(n) COMP or PIC 9(n) 
COMP without P or V, 5
≤n≤9
Index Data Item 
2
NATIVE-4 
3
FORTRAN -- INTEGER 
4
INTEGER*2
INTEGER*4
Pascal BYTE
Enumeration, unpacked, 
≤256 members
Subrange, unpacked, 
n...m, 0
≤n and m≤255
INTEGER
INT16
CARDINAL [1]
BYTE or CHAR value parameter
Enumeration, unpacked, 
>256 
members
Subrange, unpacked, n...m,
-32768
≤n and m≤32767, but at 
least n or m outside 0...255 range
LONGINT
INT32
Subrange, unpacked n...m, 
-2147483648
≤n and 
m
≤2147483647, but at least n or 
m outside -32768...32767 range
SQL CHAR NUMERIC(1)...NUMERIC(4) 
PIC9(1)COMP...PIC9(4)COMP 
SMALLINT
NUMERIC(5)...NUMERIC(9) 
PIC9(1)COMP...PIC9(9) COMP 
INTEGER
TAL STRING
UNSIGNED(16)
INT
UNSIGNED(16)
INT(32)
Return Value 
Size (Words)
11 2
1
 Unsigned Integer
2
 Index Data Item is a 16-bit integer in COBOL 74 and a 32-bit integer in COBOL85.
3
 HP COBOL85 only.
4
 INTEGER is normally equivalent to INTEGER*2. The INTEGER*4 and INTEGER*8 compiler directives redefine 
INTEGER.










