Top
NetCOBOL V11.0 Syntax Samples
FUJITSU Software

1.23 GLOBAL Clause

The GLOBAL clause is used to define data that is to be shared among different nested programs. Data items that are defined as GLOBAL can be referenced from child programs.

000010 @OPTIONS MAIN
000020*----------------------------------------------------------------------
000030* The GLOBAL clause can define variables that have a global attribute.
000040*----------------------------------------------------------------------
000050 IDENTIFICATION   DIVISION.
000060 PROGRAM-ID.      SAMPLE.
000070 DATA             DIVISION.
000080 WORKING-STORAGE  SECTION.
000090*----------------------------------------------------------------------
000100* The GLOBAL clause is specified to declare a global attribute.
000110* Variables that have a global attribute can also be referenced from 
000115* child programs.
000120*----------------------------------------------------------------------
000130  01 IN-DATA      IS GLOBAL PIC X(80).
000140  01 ED-DATA      IS GLOBAL.
000150     02 ELM       OCCURS 8 TIMES PIC X(16).
000160*----------------------------------------------------------------------
000170 PROCEDURE        DIVISION.
000180     CALL "IN-PROC".
000190     CALL "ED-PROC".
000200     CALL "OUT-PROC".
000210     EXIT PROGRAM.
000220**
000230 IDENTIFICATION   DIVISION.
000240 PROGRAM-ID.      IN-PROC.
000250 PROCEDURE        DIVISION.
000260     DISPLAY "The input character string is delimited by a space."
000270     DISPLAY "Please input the character string. >>" WITH NO ADVANCING.
000280*----------------------------------------------------------------------
000290* Values are set for the item IN-DATA that has the global attribute.
000300*----------------------------------------------------------------------
000310     ACCEPT IN-DATA FROM CONSOLE.
000320*----------------------------------------------------------------------
000330     EXIT PROGRAM.
000340 END PROGRAM IN-PROC.
000350**
000360 IDENTIFICATION   DIVISION.
000370 PROGRAM-ID.      ED-PROC.
000380 PROCEDURE        DIVISION.
000390*----------------------------------------------------------------------
000400* The item IN-DATA that has the global attribute is edited.
000410*----------------------------------------------------------------------
000420     UNSTRING IN-DATA DELIMITED BY SPACE
000430                      INTO ELM(1) ELM(2) ELM(3) ELM(4)
000440                           ELM(5) ELM(6) ELM(7) ELM(8).
000450*----------------------------------------------------------------------
000460     EXIT PROGRAM.
000470 END PROGRAM ED-PROC.
000480**
000490 IDENTIFICATION   DIVISION.
000500 PROGRAM-ID.      OUT-PROC.
000510 PROCEDURE        DIVISION.
000520     DISPLAY " ".
000530*----------------------------------------------------------------------
000540* The item ED-DATA that has the global attribute is referenced.
000550*----------------------------------------------------------------------
000560     DISPLAY "Unstring data:" ED-DATA.
000570*----------------------------------------------------------------------
000580     EXIT PROGRAM.
000590 END PROGRAM OUT-PROC.
000600 END PROGRAM SAMPLE.