Tek-Tips is the largest IT community on the Internet today!

Members share and learn making Tek-Tips Forums the best source of peer-reviewed technical information on the Internet!

  • Congratulations SkipVought on being selected by the Tek-Tips community for having the most helpful posts in the forums last week. Way to Go!

string together a list 1

Status
Not open for further replies.

hawley26

Programmer
Oct 29, 2003
6
0
0
US
I am trying to string a list of numbers together. I am able to string them together but would like to see the leading zero dropped. Any suggestions or ideas?

Code snippet:
01 PV-PROGRAM-VARIABLES.
05 PV-STR-NBR-FULL PIC 9(04) VALUE ZEROS.
05 PV-MULTI-STR PIC X(500) VALUE SPACES.

in a paragraph:
STRING PC-QUOTE DELIMITED BY SIZE
PV-STR-NBR DELIMITED BY SIZE
PC-QUOTE DELIMITED BY SIZE
PC-COMMA DELIMITED BY SIZE
PV-MULTI-STR DELIMITED BY SIZE
INTO PM164-EXCLD-STR
MOVE PM164-EXCLD-STR TO PV-MULTI-STR

Results:
'1224','1027','1023','0784','0658','0657','0559','0382'


What I want:
'1224','1027','1023','784','658','657','559','382'
 
To drop the leading zeros I would try to use display-field , i.e:
first I would redefíne the number field
Code:
05  PV-STR-NBR-FULL          PIC  9(04)  VALUE ZEROS.
05  PV-STR-NBR-FULL-RED      PIC  ZZZ9.
and then I would use in the string concatenation the display-field instead of the original field so:
Code:
STRING PC-QUOTE                       DELIMITED BY SIZE
       PV-STR-NBR-FULL-RED            DELIMITED BY SIZE
       PC-QUOTE                       DELIMITED BY SIZE
       PC-COMMA                       DELIMITED BY SIZE
       PV-MULTI-STR                   DELIMITED BY SIZE
                                      INTO PM164-EXCLD-STR
 
Oops, for redefinition you need to write
Code:
05  PV-STR-NBR-FULL-RED REDEFINES PV-STR-NBR-FULL PIC ZZZ9.
 
Rather than suppressing the leading zeros you really need to exclude them. In other words, just using the redefines suggested, you would still wind up with the following results:

'1224','1027','1023','_784','_658','_657','_559','_382'

where the underscores would actually be blanks but are shown above as underscores to make them visible.

What you really need is to drop the leading zeros. You can do this simply enough using an INSPECT statement and reference modification.

Try the following:
Code:
77 START      PIC 9(2) VALUE ZEROS.
...
MOVE 1 TO START
INSPECT PV-STR-NBR-FULL           TALLYING START
                                  FOR LEADING ZEROS
STRING PC-QUOTE                   DELIMITED BY SIZE
       PV-STR-NBR-FULL (START:)   DELIMITED BY SIZE
       PC-QUOTE                   DELIMITED BY SIZE
       PC-COMMA                   DELIMITED BY SIZE
       PV-MULTI-STR               DELIMITED BY SIZE
                                  INTO PM164-EXCLD-STR

Please note that START is initialized to 1 (not zero) so that it points to the first non-blank (non-zero) character when the inspect is done.

Code what you mean,
and mean what you code!
But by all means post your code!

Razalas
 
Or using this with the display field will probably works too:
Code:
STRING PC-QUOTE                       DELIMITED BY SIZE
       PV-STR-NBR-FULL-RED            [red]DELIMITED BY SPACE[/red]
       PC-QUOTE                       DELIMITED BY SIZE
       PC-COMMA                       DELIMITED BY SIZE
       PV-MULTI-STR                   DELIMITED BY SIZE
                                      INTO PM164-EXCLD-STR
 
Mikrom,

I think what you are suggesting would give a result like:

'1224','1027','1023','','','','',''

using the sample result from the original post.

Code what you mean,
and mean what you code!
But by all means post your code!

Razalas
 
Razalas,
You are right, my suggestion would not work. I tried what you suggested and it works fantastic !
Here is the example I tried:
Code:
       IDENTIFICATION DIVISION.
       PROGRAM-ID.                     POKUS01.
       AUTHOR.                         ROMANAPS.
       DATE-WRITTEN.                   2008-02-10.


       ENVIRONMENT DIVISION.
       CONFIGURATION SECTION.
       SOURCE-COMPUTER.                IBM-ISERIES.
       OBJECT-COMPUTER.                IBM-ISERIES.
       SPECIAL-NAMES.
           CURRENCY SIGN IS '$'
           DECIMAL-POINT IS COMMA
           .

       DATA DIVISION.
       WORKING-STORAGE SECTION.
       01  NUMBERS.
           05 TAB-IDX                           PIC 9(02).
           05 TAB-REC OCCURS 0 TO 99 TIMES DEPENDING ON TAB-IDX.
              10 TAB-NUM                        PIC 9(04).
      *       10 TAB-NUM-RED REDEFINES TAB-NUM  PIC ZZZ9.

       01  NUM-LIST                             PIC X(200).

       01  TEMP-VARS.
           05 I                                 PIC 9(02).
           05 START-IDX                         PIC 9(02).

       PROCEDURE DIVISION.
       MAIN.
           PERFORM FILL-TABLE-WITH-NUMBERS
           PERFORM CREATE-LIST-OF-NUMBERS
           PERFORM DISPLAY-LIST-OF-NUMBERS.
           PERFORM GOBACK-PARA
           .

       FILL-TABLE-WITH-NUMBERS.
           INITIALIZE NUMBERS
           ADD 1 TO TAB-IDX
           MOVE 1224 TO TAB-NUM (TAB-IDX)
           ADD 1 TO TAB-IDX
           MOVE 1027 TO TAB-NUM (TAB-IDX)
           ADD 1 TO TAB-IDX
           MOVE 1023 TO TAB-NUM (TAB-IDX)
           ADD 1 TO TAB-IDX
           MOVE 0784 TO TAB-NUM (TAB-IDX)
           ADD 1 TO TAB-IDX
           MOVE 0658 TO TAB-NUM (TAB-IDX)
           ADD 1 TO TAB-IDX
           MOVE 0657 TO TAB-NUM (TAB-IDX)
           ADD 1 TO TAB-IDX
           MOVE 0559 TO TAB-NUM (TAB-IDX)
           ADD 1 TO TAB-IDX
           MOVE 0382 TO TAB-NUM (TAB-IDX)
           .

       CREATE-LIST-OF-NUMBERS.
           INITIALIZE NUM-LIST.
           PERFORM VARYING I FROM 1 BY 1 UNTIL I > TAB-IDX
             MOVE 1 TO START-IDX
      *      Compute starting index for numbers beginning with zeros
             INSPECT TAB-NUM (I) TALLYING START-IDX
                                 FOR LEADING ZEROS
      *      append Comma to the List
             IF I > 1
                STRING NUM-LIST DELIMITED BY SPACE
                       ','      DELIMITED BY SIZE
                       INTO NUM-LIST
                END-STRING
             END-IF
      *      append Number to the List
             STRING NUM-LIST                DELIMITED BY SPACE
                    QUOTE                   DELIMITED BY SIZE
                    TAB-NUM (I)(START-IDX:) DELIMITED BY SIZE
                    QUOTE                   DELIMITED BY SIZE
                    INTO NUM-LIST
             END-STRING
           END-PERFORM
           .

       DISPLAY-LIST-OF-NUMBERS.
           DISPLAY NUM-LIST
           .

       GOBACK-PARA.
           GOBACK
           .

The resulting NUM-LIST is
Code:
'1224','1027','1023','784','658','657','559','382'
 
Thank you both, mikrom and razalas, for your help. Razalas idea worked perfect!!!!
 
I wrote a routine that output any formatted number, and adjust it to left, plus output the length.
Code:
 01 N PIC 9(4) VALUE 0123.
 01 Z PIC Z(9).
***** CALL-NUM2LEFT *****
 01  INP-NUM        PIC X(25).
 01  OUT-NUM        PIC X(25).
 01  OUT-NUM-LENGTH PIC 9(4).
***********************************

MOVE N TO Z.
MOVE Z TO TO INP-NUM.
CALL "num2left" USING INP-NUM OUT-NUM OUT-NUM-LENGTH.
IF OUT-NUM-LENGTH > 0 MOVE OUT-NUM(1:OUT-NUM-LENGTH) TO SOME-OUT-FIELD.
Code:
000001 IDENTIFICATION DIVISION.
000002 PROGRAM-ID. NUM2LEFT.
000003 ENVIRONMENT DIVISION.
000004 DATA DIVISION.
000005 WORKING-STORAGE SECTION.
000006 01  I            PIC 9(4) COMP-6.
000007 LINKAGE SECTION.
000008 01  INP-NUM      PIC X(25).
000009 01  OUT-NUM      PIC X(25).
000010 01  OUT-LENGTH   PIC 9(4).
000011 PROCEDURE DIVISION USING INP-NUM OUT-NUM OUT-LENGTH.
000012 1.  MOVE SPACES TO OUT-NUM.
000013     MOVE ZEROES TO I.
000014     INSPECT INP-NUM TALLYING I FOR LEADING SPACES.
000015     SUBTRACT 25 FROM I GIVING OUT-LENGTH.
000016     IF OUT-LENGTH > 0 ADD 1 TO I
000017                       MOVE INP-NUM(I:) TO OUT-NUM
000018                       PERFORM OUT-OUT-LENGTH.
000019     EXIT PROGRAM.
000020 OUT-OUT-LENGTH.
000021     MOVE 25 TO OUT-LENGTH.
000022     PERFORM VARYING I FROM 1 BY 1 UNTIL I > 25
000023             IF OUT-NUM(I:1) = SPACE
000024                              SUBTRACT 1 FROM I GIVING OUT-LENGTH
000025                              MOVE 77 TO I, END-IF
000026             END-PERFORM.
000027 EX-OUT-OUT-LENGTH.
 
Status
Not open for further replies.

Part and Inventory Search

Sponsor

Back
Top