[Search for users] [Overall Top Noters] [List of all Conferences] [Download this site]

Conference clt::cobol

Title:VAX/DEC COBOL
Notice:Kit,doc,performance talk info-->DIR/KEY=KIT or DOC or PERF_TALK
Moderator:PACKED::BRAFFITT
Created:Mon Feb 03 1986
Last Modified:Fri Jun 06 1997
Last Successful Update:Fri Jun 06 1997
Number of topics:3250
Total number of notes:13077

2750.0. "high-order truncation of data items" by DSSDEV::RICE () Fri Jun 03 1994 15:57

T.RTitleUserPersonal
Name
DateLines
2750.1/nowarnings :-)INTP::SARAHSome things just have to be believed to be seen.Fri Jun 03 1994 18:431
2750.2They must mean somethingDSSDEV::RICEMon Jun 06 1994 12:565
2750.3Just wondering....NWD002::GOLDSMITH_THOnward thru the FogMon Jun 06 1994 15:385
2750.4how to correct low and high order truncationsHANDVC::STEVELIUWed Feb 19 1997 04:4437
    
    what's the meaning on low and high order truncations ? when I compile
    my cobol program, I got these messages :
    
    $ cobol /standard=v3 /warnings=all p1.cob
    
            MOVE LET-CNT TO DISP-COUNT.
    .............^
    
    %COBOL-I-LOWTRUNC, Possible low-order truncation
    at line number 21 in file DISK$USER1:[STEVELIU.COBOL]P1.COB;1
    
            MOVE SUB-1 TO CHARCT.
    .............^
    
    %COBOL-I-HIGHTRUNC, Possible high-order truncation
    at line number 44 in file DISK$USER1:[STEVELIU.COBOL]P1.COB;1
    %COBOL-I-ENDDIAGS, DISK$USER1:[STEVELIU.COBOL]P1.COB;1 completed with 2
    diagnost
    ics
    
    where the affected data definition is indicated by <<< :
    
    01 TESTA-DATA            GLOBAL.
            02 LET-CNT       PIC 9(2)V9(2).  <<<
            02 IN-WORD       PIC X(20).       |
            02 DISP-COUNT    PIC 9(2).      <--
    
    01 SUB-1 PIC 9(2) COMP. <<<
                             |
    01 CHARCT PIC 99V99.   <--
    
    What should I do to correct these errors ?
    
    sl.
    
    
2750.5low-order truncation; high-order truncation and /TRUNCATEPACKED::BRAFFITTWed Feb 19 1997 09:2485
>    What should I do to correct these errors ?
    
    The program below demonstrates 2 MOVE statements you can use to
    correct these errors.
    
    In the first case with
    
	MOVE LET-CNT TO DISP-COUNT.
    
    LET-CNT has 2 decimal digits to the right of the decimal point, but
    DISP-COUNT does not.
    
    In the second case with
    
	MOVE SUB-1 TO CHARCT.
    
    SUB-1 is declared COMP.  Based on the number of digits in the PICTURE
    clause, DEC/VAX COBOL chooses a 16-bit word binary integer as the
    data type.
    
$ help cobol/truncate
COBOL

  /TRUNCATE

     /TRUNCATE
     /NOTRUNCATE  (D)

   Controls  how  the  compiler  stores  values   in   COMPUTATIONAL
   receiving items if high-order truncation is necessary.

   If  you  specify  /NOTRUNCATE,  the  compiler  truncates   values
   according  to  the  VAX hardware storage unit (word, longword, or
   quadword) allocated to the receiving item.

   If you specify /TRUNCATE, the compiler truncates values according
   to  the  number  of decimal digits specified by the PICTURE size.
   Specifying /TRUNCATE increases program execution time.
    
    /NOTRUNCATE (default)
	***C2750***
	23
	23.45
	78.00
	  678
	***END***
    
    /TRUNCATE
    	***C2750***
    	23
    	23.45
    	78.00
    	   78
    	***END***
    
IDENTIFICATION DIVISION.
PROGRAM-ID. C2750.
ENVIRONMENT DIVISION.
DATA DIVISION.
WORKING-STORAGE SECTION.
01 TESTA-DATA            GLOBAL.
   02 LET-CNT       PIC 9(2)V9(2).
   02 IN-WORD       PIC X(20).
   02 DISP-COUNT    PIC 9(2).
   02 DISP-COUNT2   PIC 9(2)V9(2).
01 SUB-1            PIC 9(2) COMP.
01 CHARCT           PIC 99V99.
01 CHARCT2          PIC 9(5).
PROCEDURE DIVISION.
P0.	DISPLAY "***C2750***".

	MOVE 23.45 TO LET-CNT.
	MOVE LET-CNT TO DISP-COUNT.
	DISPLAY DISP-COUNT  WITH CONVERSION.
	MOVE LET-CNT TO DISP-COUNT2.
	DISPLAY DISP-COUNT2 WITH CONVERSION.

	MOVE 678 TO SUB-1.
	MOVE SUB-1 TO CHARCT.
	DISPLAY CHARCT  WITH CONVERSION.
	MOVE SUB-1 TO CHARCT2.
	DISPLAY CHARCT2 WITH CONVERSION.

	DISPLAY "***END***".
	STOP RUN.