Was this helpful?
Data Type Conversion
A COBOL data item must be compatible with the Ingres value it represents. Numeric Ingres values can be set by and retrieved into COBOL numeric and numeric edited items, and Ingres character values can be set by and retrieved into COBOL character data items, that is, alphabetic, alphanumeric, and alphanumeric edited items.
Data type conversion occurs automatically for different numeric types, such as from floating-point Ingres database column values into integer COBOL variables, and for character strings, such as from varying-length Ingres character fields into fixed-length COBOL character string buffers.
Ingres does not automatically convert between numeric and character types, such as from Ingres integer fields into COBOL alphanumeric data items. You must use the Ingres type conversion functions, the Ingres ascii function, or the COBOL STRING statement to effect such conversion.
The following table shows the default type compatibility for each Ingres data type. Note that some COBOL types are omitted from the table because they do not exactly match a Ingres type. Use of those types necessitates some runtime conversion, which may possibly result in some loss of precision.
UNIX: There is no exact match for float, so use COMP-3. 
Ingres Types and Corresponding COBOL Data Types
The following table list Ingres types with their corresponding COBOL data types.
Ingres Type
UNIX COBOL Type
VMS COBOL Type
cN
PIC X(N)
PIC X(N)
text(N)
PIC X(N)
PIC X(N)
char(N)
PIC X(N).
PIC X(N).
varchar(N)
PIC X(N).
PIC X(N).
i1
PIC S9(2) USAGE COMP.
PIC S9(2) USAGE COMP.
i2
PIC S9(4) USAGE COMP.
PIC S9(4) USAGE COMP.
i4
PIC S9(9) USAGE COMP.
PIC S9(9) USAGE COMP.
f4
PIC S9(10)V9(8) USAGE COMP-3.
USAGE COMP-1.
f8
PIC S9(10)V9(8) USAGE COMP-3.
USAGE COMP-2
date
PIC X(25).
PIC X(25).
money
PIC S9(10)V9(8) USAGE COMP-3.
USAGE COMP-2.
decimal
PIC S9(P-S)V(S) USAGE COMP-3.
PICS9(P-S)V(S)
USAGE COMP-3.
Note that Ingres stores decimal as signed. Thus, use a signed decimal variable if it interacts with a Ingres decimal type. Also, Ingres allows a maximum precision of 39 while COBOL allows only 18.
Decimal Type Conversion
A Ingres decimal value that will not fit into a COBOL variable will either be truncated if there is loss of scale or cause a runtime error if loss of significant digits.
Runtime Numeric Type Conversion
The Ingres runtime system provides automatic data type conversion between numeric-type values in the database and the forms system and numeric COBOL data items. It follows the standard COBOL type conversion rules. For example, if you assign the value in a scaled COMP-3 data item for UNIX or a COMP-1 data item for VMS to an integer-valued field in a form, the digits after the decimal point of the data item's value are truncated. Runtime errors are generated for overflow on conversion.
The preprocessor generates COBOL MOVE statements to convert various COBOL data types. These can again be converted at runtime based on the final value being set or retrieved. Note that the standard COBOL data conversion rules hold for all these generated MOVE statements, with a potential loss of precision.
Floats are coerced to decimal types by Ingres at runtime. The preprocessor uses temporary data items when moving values between numeric DISPLAY data items and Ingres objects. Depending on the PICTURE clause of the DISPLAY item, these temporary data items are either:
COMP-3 or 4-byte COMP-5 for UNIX
or
COMP-2 or 4-byte COMP for VMS
Numeric DISPLAY Items and Temporary Data Items
Numeric DISPLAY Item's Picture
Temporary Item's Data Type - UNIX
Temporary Item's Data Type - VMS
With scaling
PIC S9(9)V9(9) USAGE COMP-3
COMP-2
With > 10 numeric digits
PIC S9(9)V9(9) USAGE COMP-3
COMP-2
No scaling and 10 numeric digits
4-byte COMP-5
4-byte COMP
COMP-3 items used to set or receive Ingres values also require some runtime conversion. This is not true if you are setting or receiving decimal data. This is true for Micro Focus COBOL when float values are received into COMP-3.
The preprocessor also generates code to use a temporary data item when Ingres data is to interact with a COBOL unscaled COMP data item whose picture string is exactly 10.
UNIX: Because a COBOL non-scaled numeric item whose picture contains 10 or fewer digits is regarded as compatible with the Ingres integer type, EQUEL/COBOL assigns such data to a temporary COBOL 4-byte COMP-5 data item to allow it to interact with Ingres integer data. Note that the range of the Ingres i4 type does not include all 10-digit numbers. If you have 10-digit numeric data outside the Ingres range, you should use a COMP-3 data item and choose the Ingres float type.
You can use only COMP data items or items that get assigned to temporary 4-byte COMP-5 data items (as described above) to set the values of Ingres integer objects, such as table field row numbers. You can, however, use any numeric data items to set and retrieve numeric values in Ingres database tables or forms.
The Ingres money type is represented as a COMP-3 data item. 
VMS: A COBOL non-scaled numeric item whose picture contains 10 or fewer digits is regarded as compatible with the Ingres integer type. However, the VAX standard data type for an unscaled 10-digit COMP item is a quadword (8 bytes). Therefore, EQUEL/COBOL assigns such data to a temporary COBOL 4-byte COMP data item to allow it to interact with Ingres integer data. Note that the range of the Ingres i4 type does not include all 10-digit numbers. If you have 10-digit numeric data outside the Ingres range you should use a COMP-1 or COMP-2 data item and choose the Ingres float type.
You can use only COMP data items or items that get assigned to temporary 4-byte COMP data items (as described above) to set the values of Ingres integer objects, such as table field row numbers. You can, however, use any numeric data items to set and retrieve numeric values in Ingres database tables or forms.
The Ingres money type is represented as COMP-2, an 8-byte floating-point value.
Runtime Character Conversion
Automatic conversion occurs between Ingres character string values and COBOL character variables (alphabetic, alphanumeric, and alphanumeric edited data items). There are four string-valued Ingres objects that can interact with character variables:
Ingres names, such as form and column names
Database columns of type c or char
Database columns of type text or varchar
Form fields of type c
Several considerations apply when dealing with character string conversions, both to and from Ingres.
The conversion of COBOL character variables used to represent Ingres names is simple: trailing blanks are truncated from the variables, because the blanks make no sense in that context. For example, the string constants "empform " and "empform" refer to the same form and "employees " and "employees" refer to the same database table.
The conversion of other Ingres objects is a bit more complicated. First, the storage of character data in Ingres differs according to whether the medium of storage is a database column of type c or char, a database column of type text or varchar, or a character-type form field. Ingres pads columns of type c and char with blanks to their declared length. Conversely, it does not add blanks to the data in columns of type text, or varchar in form fields.
Second, the COBOL convention is to blank-pad fixed-length character strings. For example, the character string "abc" may be stored in a COBOL PIC X(5) data item as the string "abc" followed by two blanks.
When character data is retrieved from a database column or form field into a COBOL character variable and the variable is longer than the value being retrieved, the variable is padded with blanks. If the variable is shorter than the value being retrieved, the value is truncated. You must always ensure that the variable is at least as long as the column or field, in order to avoid truncation of data. You should note that, when a value is transferred into a data item from a Ingres object, it is copied directly into the variable storage area without regard to the COBOL special insertion rules.
When inserting character data into an Ingres database column or form field from a COBOL variable, note the following conventions:
When data is inserted from a COBOL variable into a database column of type c or char and the column is longer than the variable, the column is padded with blanks. If the column is shorter than the variable, the data is truncated to the length of the column.
When data is inserted from a COBOL variable into a database column of type text or varchar and the column is longer than the variable, no padding of the column takes place. Furthermore, by default, all trailing blanks in the data are truncated before the data is inserted into the text or varchar column. For example, when a string "abc" stored in a COBOL PIC X(5) data item as "abc " (refer to above) is inserted into the text or varchar column, the two trailing blanks are removed and only the string "abc" is stored in the database column. To retain such trailing blanks, you can use the Ingres notrim function. It has the following syntax:
notrim(charvar)
where charvar is a character variable. An example that demonstrates this feature follows this section. If the text or varchar column is shorter than the variable, the data is truncated to the length of the column.
When data is inserted from a COBOL variable into a c form field and the field is longer than the variable, no padding of the field takes place. In addition, all trailing blanks in the data are truncated before the data is inserted into the field. If the field is shorter than the data (even after all trailing blanks have been truncated), the data is truncated to the length of the field.
When comparing character data in a Ingres database column with character data in a COBOL variable, note the following convention:
When comparing data in a c, character, or varchar database column with data in a character variable, all trailing blank are ignored. Initial and embedded blanks are significant in character, text, and varchar; they are ignored in c.
IMPORTANT!  As previously described, the conversion of character string data between Ingres objects and COBOL variables often involves the trimming or padding of trailing blanks, with resultant change to the data. If trailing blanks have significance in your application, give careful consideration to the effect of any data conversion.
The Ingres date data type is represented as a 25-byte character string: PIC X(25).
The program fragment in the following examples demonstrates the notrim function and the truncation rules explained above:
UNIX:
DATA DIVISION.
WORKING-STORAGE SECTION
##  01 ROW        PIC S9(4) USAGE COMP.
##  01 DATA       PIC X(7).

##  DECLARE.

PROCEDURE DIVISION.
BEGIN.
##  MOVE "abc " TO DATA.

*   Set up the table for testing
##  CREATE texttype (#row = i2, #data = text(10))

*   The first APPEND adds the string "abc"  (blanks
*   truncated)
##  APPEND TO texttype (#row = 1, #data = data)

*   The second APPEND adds the string "abc ", 
*   with 4 trailing   blanks
##  APPEND TO texttype (#row = 2, #data = NOTRIM(data))

*   The RETRIEVE will get the second row because 
*   the NOTRIM   function in the previous APPEND 
*   caused trailing blanks to be inserted as data.

##  RETRIEVE (row = texttype.#row)
##  WHERE length(texttype.#data) = 7

    DISPLAY "Row found = " ROW. 

VMS:
DATA DIVISION.
WORKING-STORAGE SECTION

##   01 ROW           PIC S9(4) USAGE COMP.
##   01 DATA          PIC X(7).
##   DECLARE.

PROCEDURE DIVISION.
BEGIN.

*     Set up the table for testing
##    CREATE texttype (#row = i2, #data = text(10))

*     The first APPEND adds the string "abc" 
*     (blanks truncated)
##    APPEND TO texttype (#row = 1, #data = data)

*     The second APPEND adds the string "abc ", with 
*     4 trailing   blanks
##    APPEND TO texttype (#row = 2, #data = NOTRIM(data))

*     The RETRIEVE will get the second row because 
*     the NOTRIM function  in the previous APPEND 
*     caused trailing blanks to be inserted as  data.

##    RETRIEVE (row = texttype.#row)
##       WHERE length(texttype.#data) = 7
      DISPLAY "Row found = " ROW.  
Last modified date: 11/28/2023