Host Variable Declaration - Teradata Preprocessor2

Teradata® Preprocessor2 for Embedded SQL Programmer Guide - 20.00

Deployment
VantageCloud
VantageCore
Edition
Enterprise
IntelliFlex
Lake
VMware
Product
Teradata Preprocessor2
Release Number
20.00
Published
October 2023
Language
English (United States)
Last Update
2023-11-20
dita:mapPath
nyr1691484085721.ditamap
dita:ditavalPath
obe1474387269547.ditaval
dita:id
xfi1470440464166
Product Category
Teradata Tools and Utilities

PP2 does not recognize every possible COBOL variable declaration as valid for use in a SQL statement. The table that follows lists the equivalent COBOL definitions for database data types.

For types that have no direct COBOL declaration, runtime processing allows the return of data to one of the other types. Level numbers are only examples.

The COBOL repetition factor syntax is used for the picture specification characters in the examples (that is, X(m), 9(x)), but the actual number of characters also can be used (for example, X(3) = XXX).

With COBOL, host variables can start with a numeric, but when referenced, require a colon in front.

This provides a distinction between a numeric constant and the host variable name.

Data Type Declaration Compilers Notes (following table)
BYTE No direct equivalent All 1
VARBYTE No direct equivalent All 1
CHAR(m)
01 identifier PIC X(m).
All 2
VARCHAR(m)
01 identifier
49 identifier PIC [S]9(4).
   [USAGE [IS]] COMP[UTATIONAL].
49 identifier PIC X(m)
All except MF1 and MF2 2, 3, 11
01 identifier
49 identifier PIC [S]9(4)
   [USAGE [IS]] COMP[UTATIONAL]-4.
49 identifier PIC X(m)
All but MF1, MF2, and LPI
01 identifier
49 identifier PIC [S]9(4).
   [USAGE [IS]] COMP[UTATIONAL]-5.
49 identifier PIC X(m)
MF1 and MF2
 
01 identifier
   49 identifier PIC [S]9(4) BINARY.
   49 identifier PIC X(m)
All except

MF1 and MF2

TIME
01 identifier PIC X(m)
  15
TIMESTAMP
01 identifier PIC X(m)
  16
DATE
01 identifier PIC S9(m)
   [USAGE [IS]] COMP[UTATIONAL].
All 4, 5
01 identifier PIC S9(m)
   [USAGE [IS]] COMP[UTATIONAL]-4.
All except LPI
01 identifier PIC S9(m)
   [USAGE [IS]] COMP[UTATIONAL]-5.
MF1 and MF2
01 identifier PIC S9(m)
   [USAGE [IS]] BINARY.
All
DECIMAL(m,n)
01 identifier PIC S9(m-n)V9(n)
   [USAGE [IS]] COMP[UTATIONAL]-3.
All 2, 6
01 identifier PIC S9(m-n)V9(n)
   [USAGE [IS]] PACKED-DECICMAL.
All
NUMERIC(m,n)
01 identifier PIC S9(m-n)V9(n)
   [USAGE [IS]] COMP[UTATIONAL]-3.
All 2,6
01 identifier PIC S9(m-n)V9(n)
   [USAGE [IS]] PACKED-DECICMAL.
All
FLOAT*
01 identifier
   [USAGE [IS]] COMP[UTATIONAL]-1.
All except

MF1 and MF2

7
REAL*
01 identifier
   [USAGE [IS]] COMP[UTATIONAL]-1.
All except MF1 and MF2 7
DOUBLE PRECISION*
01 identifier
   [USAGE [IS]] COMP[UTATIONAL]-1.
All except MF1 and MF2 7
FLOAT**
01 identifier
   [USAGE [IS]] COMP[UTATIONAL]-2.
All except

MF1 and MF2

7
REAL**
01 identifier
   [USAGE [IS]] COMP[UTATIONAL]-2.
All except MF1 and MF2 7
DOUBLE PRECISION**
01 identifier
   [USAGE [IS]] COMP[UTATIONAL]-2.
All except MF1 and MF2 7
BYTEINT
01 identifier PIC S9(m)[v9(n)]
   [USAGE [IS]] COMP[UTATIONAL].
All 8
01 identifier PIC S9(m)[v9(n)]
   [USAGE [IS]] COMP[UTATIONAL]-4.
All except LPI
01 identifier PIC S9(m)[v9(n)]
   [USAGE [IS]] COMP[UTATIONAL]-5.
MF1 and MF2
01 identifier PIC S9(m)[v9(n)]
   [USAGE [IS]] BINARY.
All
SMALLINT
01 identifier PIC S9(m)[v9(n)]
   [USAGE [IS]] COMP[UTATIONAL].
All 9
01 identifier PIC S9(m)[v9(n)]
   [USAGE [IS]] COMP[UTATIONAL]-4.
All except LPI
01 identifier PIC S9(m)[v9(n)]
   [USAGE [IS]] COMP[UTATIONAL]-5.
MF1 and MF2
01 identifier PIC S9(m)[v9(n)]
   [USAGE [IS]] BINARY.
All
INTEGER
01 identifier PIC S9(m)[v9(n)]
   [USAGE [IS]] COMP[UTATIONAL].
All 10
01 identifier PIC S9(m)[v9(n)]
   [USAGE [IS]] COMP[UTATIONAL]-4.
All except LPI
01 identifier PIC S9(m)[v9(n)]
   [USAGE [IS]] COMP[UTATIONAL]-5.
MF1 and MF2
01 identifier PIC S9(m)[v9(n)]
   [USAGE [IS]] BINARY.
All
GRAPHIC(m)
01 identifier PIC G(m)
   [USAGE [IS] ] DISPLAY-1
All 12
VARGRAPHIC (m)
01 identifier.
     49 identifier PIC S9(4) <comp>
     49 identifier PIC G(m)
      [USAGE [IS] ] DISPLAY-1
All 12, 13
ZONED DECIMAL(m,n)
01 identifier PIC S9(m-n)V9(n)
      [USAGE [IS]] DISPLAY
All 14
01 identifier PIC S9(m-n)V9(n)
      [USAGE [IS]] DISPLAY SIGN LEADING
All
01 identifier PIC S9(m-n)V9(n)
      [USAGE [IS]] DISPLAY SIGN TRAILING
All
01 identifier PIC S9(m-n)V9(n)
     [USAGE [IS]] DISPLAY SIGN LEADING
     SEPARATE
All
01 identifier PIC S9(m-n)V9(n)
     [USAGE [IS]] DISPLAY SIGN TRAILING
     SEPARATE
All
  * single precision

** double precision

Notes

  1. Data can be returned to any valid host variable, although PP2 performs no data conversion.
  2. The integer m must be positive.
  3. Multiple PIC X(m) fields can be declared following the COMP field; COMP field should be set to the length used, not to exceed the total length of the PIC X fields.

    Level 49 identifiers can be coded as FILLER.

  4. For MF1, the integer m must be positive such that 7 m 9. Otherwise, the integer m must be positive such that 5 m 9.
  5. The database normally returns a DATE type field as an integer.

    It is possible to return the value in character string format, as long as the length of the receiving field is sufficient.

    The DATEFORM=ANSIDATE format returns the DATE type field as CHAR (10).

  6. Integer n must be positive; if n is zero, the V9(n) portion may be omitted.
  7. A PICTURE clause may be included in the definition.

    PP2 ignores the PICTURE clause.

  8. m and n are positive integers such that 1≤ (m+n) ≤ 2.

    The value is treated as BYTEINT without scalar for MF1 and SMALLINT without scalar for all other COBOL compilers.

  9. m and n are positive integers such that 3 ≤ (m+n) ≤ 4. The value is treated as SMALLINT without scalar.

    For COBOL II applications that must assign a value greater than 9999 to a SMALL INTEGER, PP2 provides an assembler routine, PPRMVHW, to move the value.

    The routine expects two parameters as input:

    The field to contain the value and an integer field which contains the value to assign.

    As an example,
    77     Field1     PIC S9(4)     COMP.
    77     FIELD2     PIC S9(9)     COMP
                                    VALUE
                                    +32000.
    
      CALL   ’PPRMVHW’  USING FIELD1, FIELD2.

    FIELD1 receives the value +32000 upon return from PPRMVHW.

  10. For MF1, the integer m must be positive such that 7 ≤ m ≤ 9.

    Otherwise, the integer m must be positive such that 5 ≤ m ≤ 9.

    The value is treated as INTEGER without scalar.

  11. For LPI, the first level 49 field (length subfield) must be named if the varying character host variable is defined within a structure.
  12. The integer “m” is the number of graphic characters (not bytes) and must be positive. If “m” is not specified, a default of GRAPHIC(1) is used.
  13. Multiple PIC G(m) fields may be declared following the COMP field; the COMP field should be set to the length used, not to exceed the total length of the PIC G(m) fields. Level 49 identifiers may be coded as FILLER.
  14. The integers m and n must be positive, and m must be greater than n.

    This is a COBOL specific host data type, described here for documentation purposes only.

    If n is 0, omit the V9(n) portion.

  15. For TIME, the length of the char identifier should be 15.
  16. For TIMESTAMP, the length of the char identifier should be 35.