Let's understand Mainframe
Home Tutorials Interview Q&A Quiz Mainframe Memes Contact us About us

Module 5: Data Division


USAGE Clause

  • In order to understand USAGE clause properly, first please refer previous sections “Basic of Internal Representation of Data in Mainframe”, “Zoned Decimal”, “Packed Decimal” and “Floating point binary number” <LINK>
  • In general, any computer system can store data in more than one internal form. In COBOL, a programmer can use USAGE clause to specify how the data item to be stored internally.
  • The internal data representation plays very important role in data computation and program efficiency. Thus choosing proper USAGE type is very important for numeric data item
  • Default USAGE clause is DISPLAY which uses 1 byte to store each digit of numeric item. This DISPLAY usage can reduce the program efficiency if numeric item defined with DISPLAY usage is involved in some calculations. Let’s see how.
  • When calculations are done on numeric data items with USAGE IS DISPLAY, the computer has to convert the numeric values to their binary equivalents before the calculation can be done. When the result has been computed the computer has to reconvert it to ASCII/EBCDIC digits. Conversion to and from ASCII/EBCDIC digits slows down computations.
  • For this reason, COMPUTATION usage can be used. Its name also implies that is used for such computations only and it can also saves memory as compared to DISPLAY usage that we will see below
  • USAGE clause is used to specify the type of storage and if properly chosen can help in increasing program efficiency and saving memory.
  • USAGE is optional to specify.
  • USAGE clause cannot be specified for 66, 77 and 88 level number
  • USAGE clause if used on group item, it applies to all the elementary items of that group.
  • The basic syntax of USAGE clause is:-

    USAGE IS usage-type

  • usage-type can be DISPLAY, COMP, COMP-1, COMP-2, COMP-3, COMP-4, COMP-5, INDEX, POINTER
  • Let’s understand each usage type:-
  • NOTE:- It is suggested to first read “Basic of Internal Representation of Data in Mainframe”, “Zoned Decimal”, “Packed Decimal” and “Floating point binary number” <LINK> for proper understanding of all USAGE types
  • DISPLAY usage
    • DISPLAY is default usage.
    • A byte is used to represent each character of data item. Thus, the number of bytes required equals to the size of data item
    • When USAGE IS DISPLAY used for signed numeric data item, it is represented in zoned decimal representation.
  • COMP & COMP-4 usage
    • COMPUTATIONAL, COMPUTATIONAL-4 is same as COMP & COMP-4
    • COMP data items are represented in pure binary form. The number of bytes required for data items described as COMP or COMP-4 are as follows:-
      PICTURE Number of bytes required in storage
      S9(01) to S9(04) 2 bytes
      S9(05) to S9(09) 4 bytes
      S9(10) to S9(18) 8 bytes
    • The left most bit of the storage is used to store sign. (1 for negative and 0 for positive)
    • The PICTURE of COMP data item should not contain any character other than 9 and S.
  • COMP-1 or COMPUTATION-1 usage
    • COMP-1 data item is represented as single precision floating point number (32-bits).
    • Out of these 32-bits, first left most bit is used to represent sign, next 7 bits to represent exponent and last (right most) 23 bits are used to represent Mantissa.
    • Suitable for arithmetic operations
    • The PICTURE clause cannot be specified for COMP-1
    • For conditional expressions, the class condition cannot be used for COMP-1 or COMPUTATIONAL-1 internal floating-point data items
  • COMP-2 or COMPUTATION-2 usage
    • COMP-2 data item is represented as double precision floating point number (64-bits).
    • Out of these 64-bits, first left most bit is used to represent sign, next 11 bits to represent exponent and last (right most) 52 bits are used to represent Mantissa.
    • Used for high precision calculations
    • The PICTURE clause cannot be specified for COMP-2
    • For conditional expressions, the class condition cannot be used for COMP-2 or COMPUTATIONAL-2 internal floating-point data items
  • COMP-3 or PACKED-DECIMAL usage
    • This is the equivalent of PACKED-DECIMAL.
    • COMP-3 data item is represented in packed decimal format.
    • A packed decimal representation uses the first four bits of each byte to store one digit and last four bit of each byte(except last byte) to store another digit. The sign is stored in last four bits (X‘C’ for positive, X‘D’ for negative) of last byte. Thus in case of packed decimal representation it occupies less space compared to zoned decimal representation as each byte(except last byte) can store two digits.
    • Example:-
      Picture clause Decimal Value Hex Representation
      PIC S9(4) COMP-3 -1234 X’1234D’
      PIC S9(4) COMP-3 +1234 X’1234C’
      PIC 9(4) COMP-3 1234 X’1234F’
    • PIC 9(N) USAGE IS COMP-3 will require (N+1)/2 bytes.
  • COMP-5 usage
    • COMP-5 data item are represented as binary data like COMP and the memory usage is also same. But these data item can contain values up to the capacity of the native binary representation (2, 4 or 8 bytes), rather than being limited to the value implied by the number of nines in the picture for the item (as is the case for USAGE BINARY data).
    • When numeric data is moved or stored into a COMP-5 item, truncation occurs at the binary field size rather than at the COBOL picture size limit. When a COMP-5 item is referenced, the full binary field size is used in the operation.
    • The following table shows several PICTURE clause, number of bytes required in storage, and the range of values it can store
    • It is important to note that COMP or COMP-4 also can store till 32767 if the program is compiled with TRUC(BIN) whereas COMO-5 behaves so independent of compiler option. This is useful when the data is coming from non-COBOL compilers
  • INDEX usage
    • A data item defined with INDEX phrase is called as index data item.
    • It is used to preserve the index value of an array (array will be explained in Module 9 <LINK>). It takes fixed 4 bytes of storage and thus PIC must not be used for index data items
    • Example:-

      01 IDX USAGE IS INDEX

    • Above example defines the index IDX.
    • Index data items can only be used in :- SEARCH or SET statement, A relation condition, The USING phrase of PROCEDURE DIVISION or The using phrase of CALL statement. These concepts will be explained in later Modules <LINK>
  • POINTER usage
    • A data item defined with POINTER phrase is called as pointer data item.
    • It is used accomplish limited base addressing. In simple words, it is used to store address of any data item.
    • It takes fixed 4 bytes of storage and thus PIC must not be used for pointer data items
    • Example:-

      01 WS-PTR USAGE IS POINTER

    • Above example declares pointer data item WS-PTR as a 4 byte field which can store address of linkage section data item.
    • Pointer data items can only be used in:- SET statement, Relation condition, The USING phrase of CALL statement, an ENTRY statement, or the procedure division header
    • A VALUE clause for a pointer data item can contain only NULL or NULLS. NULL is special pointer which points to nothing. We can set a pointer data item to NULL in procedure division as well. Below example can depict that:-

      SET WS-PTR TO NULL.

    • A pointer points to nothing unless we set it to point some group or elementary data item of LINKAGE SECTION. Below is an example which depicts how we can point to group element using pointer data item

      WORKING–STORAGE SECTION. 01 WS-PTR USAGE IS POINTER. LINKAGE SECTION. 01 DATE-STR. 05 DD PIC X(02). 05 MM PIC X(02). 05 YYYY PIC X(04). In PROCEDURE-DIVISION, SET WS-PTR TO ADDRESS OF DATE-STR.

    • Above SET statement written in Procedure division sets the addressability. Now WS-PTR points to an linkage section item DATE-STR
    • Dereferencing can be done using:-

      SET ADDRESS OF WS-PTR TO DATE-STR.






© copyright mainframebug.com
Privacy Policy