Top
NetCOBOL V11.0 Syntax Samples
FUJITSU Software

1.24 JUSTIFIED Clause

Normally, character data is left-justified. However, items that specify the JUSTIFIED clause are right-justified. The JUSTIFIED clause is useful for displaying data right-justified.

000010 @OPTIONS MAIN
000020*----------------------------------------------------------------------
000030* The JUSTIFIED RIGHT clause specifies that the character string 
000035* is right-justified.
000040*----------------------------------------------------------------------
000050 IDENTIFICATION   DIVISION.
000060 PROGRAM-ID.      SAMPLE.
000070 DATA             DIVISION.
000080 WORKING-STORAGE SECTION.
000090*----------------------------------------------------------------------
000100* The JUSTIFIED RIGHT clause is specified for items that are to be 
000110* stored or displayed right-justified.
000120*----------------------------------------------------------------------
000130 01 CARD.
000140    02 TEAM-1     PIC X(10).
000150    02            PIC X(02) VALUE "VS".
000160    02 TEAM-2     PIC X(10) JUSTIFIED RIGHT.
000170    02            PIC X(02) VALUE SPACE.
000180    02 PLACE      PIC X(25).
000190*----------------------------------------------------------------------
000200 PROCEDURE      DIVISION.
000210     DISPLAY "** Today's match card **".
000220     DISPLAY " ".
000230     MOVE "Japan"  TO TEAM-1.
000240*----------------------------------------------------------------------
000250* The character string is stored right-justified.
000260*----------------------------------------------------------------------
000270     MOVE "Brazil" TO TEAM-2.
000280*----------------------------------------------------------------------
000290     MOVE "Sydney" TO PLACE.
000300     DISPLAY CARD.
000310**
000320     MOVE "Italia"      TO TEAM-1.
000330     MOVE "USA"   TO TEAM-2.
000340     MOVE "Canberra" TO PLACE.
000350     DISPLAY CARD.
000360 END PROGRAM SAMPLE.