gnucobol-users
[Top][All Lists]
Advanced

[Date Prev][Date Next][Thread Prev][Thread Next][Date Index][Thread Index]

[open-cobol-list] initialization problems


From: David Korn
Subject: [open-cobol-list] initialization problems
Date: Wed Feb 25 18:39:01 2004

cc: address@hidden
Subject: initialization problems
--------

I have enclosed two programs that demonstrate the initialization
is not working correctly.  In both of these programs the field
that is being displayed does not have an initial value.
In the first program, if you remove the declaration for either
IP1B036-BUILD-FICB-INTFC or IP1B002-FICB, then FIX-120793
gets initialized to '0'.  Otherwise, it is an empty string.

It might be the same bug that causes both.

=====================prog19.c======================
       IDENTIFICATION DIVISION.
       PROGRAM-ID.    PROG19.
       DATA DIVISION.
       WORKING-STORAGE SECTION.
       01  SWITCH-LIST.
           05  FIX-120793.
               10  FIX-120793-FLAG     PIC  X(01) VALUE '0'.
                   88  WRITE-OUT-COMMENTS         VALUE '0'.
                   88  COMMENTS-WRITTEN           VALUE '1'.
       01  IP1B036-BUILD-FICB-INTFC.
           05  IP1B036-RTND-DATA.
               10  IP1B036-RTN-CODE                  PIC S9(04) COMP.
                   88  B036-OK                           VALUE +0.
       LINKAGE SECTION.
       01  IP1B002-FICB.
           05  IP1B002-DEFAULT-VALUES.
               10  IP1B002-DFLT-LOG-TBL.
                   15  IP1B002-LOG-LEVEL         PIC  9(02)
                           OCCURS       8 TIMES
                           INDEXED BY   IP1B002-LOG-TYPE.
       PROCEDURE DIVISION.
          DISPLAY 'FLAG=' FIX-120793-FLAG.
          GOBACK.
=====================end prog19.c======================

=====================prog18.c======================
       IDENTIFICATION DIVISION.
       PROGRAM-ID.     PROG18.
       DATA DIVISION.
       WORKING-STORAGE SECTION.
       01  IP1B053-IP1AS19-CALL-AREA.
           05  IP1B053-IP1AS19-TIME.
               10  IP1B053-IP1AS19-TIME-B        PIC  9(09) COMP.
               10  FILLER                        PIC  9(09) COMP.
           05  IP1B053-TIME-2 REDEFINES IP1B053-IP1AS19-TIME.
               10  IP1B053-IP1AS19-TIME-D        PIC  9(15) COMP-3.
           05  IP1B053-IP1AS19-DATE              PIC  9(15) COMP-3.
       01  IP1B053-IP1AS19-CALL-REDEF REDEFINES
           IP1B053-IP1AS19-CALL-AREA.
           05  IP1B053-IP1AS19-INDIC             PIC  X(01).
               88  B053-ABSTIME-FORMAT           VALUE 'B'.
               88  B053-CLOCK-FORMAT             VALUE 'D'.
       PROCEDURE DIVISION.
           DISPLAY      'INDIC=' IP1B053-IP1AS19-INDIC.
           GOBACK.
=====================end prog18.c======================


David Korn
address@hidden


reply via email to

[Prev in Thread] Current Thread [Next in Thread]