How to replace spaces at the right into zeros at the left in COBOL?

16,317

Solution 1

You should test your code with an input of all blanks.

If you are absolutely certain of the quality of the data, and with or without the check for blanks, you can do this:

   ID DIVISION.
   PROGRAM-ID. VARSWAP.
   DATA DIVISION.
   WORKING-STORAGE SECTION. 

       01 VARIN   PIC X(10).
          88  NO-VARIN-PRESENT VALUE SPACE.
       01 VARSWAP PIC 9(10).

   PROCEDURE DIVISION.

       MOVE '123456    ' TO VARIN
       IF NO-VARIN-PRESENT
           do what your spec says
       ELSE
           UNSTRING VARIN DELIMITED BY ' ' INTO VARSWAP
       END-IF

       DISPLAY VARSWAP

      GOBACK
      .

I don't like destroying the input, so I changed that.

A popular way to do it is, FUNCTION REVERSE ( your-field ), followed by INSPECT reversed-field TALLYING ... FOR LEADING SPACES. You can use FUNCTION LENGTH early in your program to determine the length of the fields (and ensure they are the same length) and then, setting your VARIN to ZERO first, use reference-modification for the source and the target - source will be ( 1 : calculated-length-of-data ) target will be ( calculated-start-for-right-justification : ) (not specifying the length uses the remaining part of the field).

There are also variable-length fields, byte-by-byte MOVEs (sometimes preferred by "traditionalists", but the least clear of the lot).

Exactly how you do it depends on your data. If you need to validate the data, you need code for that first, and that will make the choice more clear to you. If your data is, guaranteed, clean, then...

I know it is only an example, but I hope you use nicer data-names for real.

Solution 2

Bill Woodger mentioned: "There are also ... byte-by-byte MOVEs (sometimes preferred by "traditionalists", but the least clear of the lot)." Here is one such solution that I hope is reasonably clear. Below are two version. First, a solution updated for the suggestions below. Second, the original solution proposed, to reference in understanding the comments made. Thank you, Bill, for your good suggestions! I might learn to write good COBOL one of these days :)

   IDENTIFICATION DIVISION.
   PROGRAM-ID. SHIFT-RIGHT.
  * SITUATION ON STACKOVERFLOW.COM:
  * I HAVE AN ALPHANUMERIC VARIABLE WITH A LENGTH OF 10. 
  * IT CONTAINS A NUMBER AT THE BEGINNING, THE REST OF THE DIGITS 
  * ARE FILLED WITH SPACES. THEN I NEED TO MOVE THE STRING TO THE 
  * LEFT AND PUT THE NUMBER OF SPACES WITH '0' AT THE BEGINING. 
  * THIS EXAMPLES SPEAKS FOR THEMSELVES:

  * INPUT            OUTPUT
  * ==============================
  * '123456    ' ->  '0000123456'
  * '12345678  ' ->  '0012345678'
  * '123456789 ' ->  '0123456789'
  * '1234567890' ->  '1234567890'
  *
  * ASSUME INPUT DATA VALIDATION DONE ELSEWHERE.


   ENVIRONMENT DIVISION.
   INPUT-OUTPUT SECTION.
   FILE-CONTROL.

   DATA DIVISION.
   FILE SECTION.

   WORKING-STORAGE SECTION.
   01  STRING-IN                   PIC X(10).
   01  STRING-OUT                  PIC X(10).
   01  STRING-LENGTH               PIC 99 USAGE COMP.
   01  CHAR-IN-NUM                 PIC 99 USAGE COMP.
   01  CHAR-OUT-NUM                PIC 99 USAGE COMP.

   PROCEDURE DIVISION.
   MAIN.
       PERFORM INITIALIZE-LENGTH
       MOVE '123456    ' TO STRING-IN
       PERFORM MAKE-AND-SHOW
       MOVE '12345678  ' TO STRING-IN
       PERFORM MAKE-AND-SHOW
       MOVE '123456789 ' TO STRING-IN
       PERFORM MAKE-AND-SHOW
       MOVE '1234567890' TO STRING-IN
       PERFORM MAKE-AND-SHOW
       MOVE SPACES TO STRING-IN
       PERFORM MAKE-AND-SHOW
       STOP RUN
       .

   INITIALIZE-LENGTH.
       MOVE LENGTH OF STRING-IN TO STRING-LENGTH
       IF LENGTH OF STRING-OUT NOT = STRING-LENGTH
           DISPLAY 'LENGTH OF STRING-IN, ' STRING-LENGTH ', '
                   'NOT EQUAL TO LENGTH OF STRING-OUT, '
                   LENGTH OF STRING-OUT
           STOP RUN
       END-IF
       .

   MAKE-AND-SHOW.
       PERFORM MAKE-STRING-OUT
       PERFORM SHOW-BEFORE-AFTER
       .

   MAKE-STRING-OUT.
       MOVE ZEROS         TO STRING-OUT
       MOVE STRING-LENGTH TO CHAR-OUT-NUM
                             CHAR-IN-NUM
       PERFORM STRING-LENGTH TIMES
           IF STRING-IN (CHAR-IN-NUM:1) NOT = SPACE
               MOVE STRING-IN (CHAR-IN-NUM:1) 
                 TO STRING-OUT (CHAR-OUT-NUM:1)
               SUBTRACT 1 FROM CHAR-OUT-NUM
           END-IF
           SUBTRACT 1 FROM CHAR-IN-NUM
       END-PERFORM
       .

   SHOW-BEFORE-AFTER.
       DISPLAY "STRING IN:  '" STRING-IN "'"
       DISPLAY "STRING OUT: '" STRING-OUT "'"
       DISPLAY " "
       .


  **********************************************
  * EARLIER VERSION, BEFORE IMPROVEMENTS 
  * SUGGESTED IN COMMENTS
  **********************************************

   IDENTIFICATION DIVISION.
   PROGRAM-ID. SHIFT-LEFT.
  * SITUATION ON STACKOVERFLOW.COM:
  * I HAVE AN ALPHANUMERIC VARIABLE WITH A LENGTH OF 10. 
  * IT CONTAINS A NUMBER AT THE BEGINNING, THE REST OF THE DIGITS 
  * ARE FILLED WITH SPACES. THEN I NEED TO MOVE THE STRING TO THE 
  * LEFT AND PUT THE NUMBER OF SPACES WITH '0' AT THE BEGINING. 
  * THIS EXAMPLES SPEAKS FOR THEMSELVES:

  * INPUT            OUTPUT
  * ==============================
  * '123456    ' ->  '0000123456'
  * '12345678  ' ->  '0012345678'
  * '123456789 ' ->  '0123456789'
  * '1234567890' ->  '1234567890'
  *
  * ASSUME INPUT DATA VALIDATION DONE ELSEWHERE.


   ENVIRONMENT DIVISION.
   INPUT-OUTPUT SECTION.
   FILE-CONTROL.

   DATA DIVISION.
   FILE SECTION.

   WORKING-STORAGE SECTION.
   01  STRING-IN                   PIC X(10).
   01  STRING-OUT                  PIC X(10).
   01  CHAR-IN-NUM                 PIC 99 USAGE COMP-3.
   01  CHAR-OUT-NUM                PIC 99 USAGE COMP-3.

   PROCEDURE DIVISION.
   MAIN.
       MOVE '123456    ' TO STRING-IN
       PERFORM MAKE-AND-SHOW
       MOVE '12345678  ' TO STRING-IN
       PERFORM MAKE-AND-SHOW
       MOVE '12345678  ' TO STRING-IN
       PERFORM MAKE-AND-SHOW
       MOVE '123456789 ' TO STRING-IN
       PERFORM MAKE-AND-SHOW
       MOVE '1234567890' TO STRING-IN
       PERFORM MAKE-AND-SHOW

       STOP RUN
       .

   MAKE-AND-SHOW.
       PERFORM MAKE-STRING-OUT
       PERFORM SHOW-BEFORE-AFTER
       .

   MAKE-STRING-OUT.
       MOVE SPACES TO STRING-OUT
       MOVE 10     TO CHAR-OUT-NUM
       PERFORM VARYING CHAR-IN-NUM FROM 10 BY -1
           UNTIL CHAR-IN-NUM < 1
           IF STRING-IN (CHAR-IN-NUM:1) NOT = SPACE
               MOVE STRING-IN (CHAR-IN-NUM:1) 
                 TO STRING-OUT (CHAR-OUT-NUM:1)
               SUBTRACT 1 FROM CHAR-OUT-NUM
           END-IF
       END-PERFORM
       PERFORM UNTIL CHAR-OUT-NUM < 1
           MOVE ZERO TO STRING-OUT (CHAR-OUT-NUM:1)
           SUBTRACT 1 FROM CHAR-OUT-NUM
       END-PERFORM
       .

   SHOW-BEFORE-AFTER.
       DISPLAY "STRING IN:  '" STRING-IN "'"
       DISPLAY "STRING OUT: '" STRING-OUT "'"
       DISPLAY " "
       .

Solution 3

If you have intrinsics, shuffle a FUNCTION TRIM, with LEADING or TRAILING as fits purpose, through a pic 9. TRAILING in this case, or both in the example below.

identification division.
program-id. rjust.

data division.
working-storage section.
01 str    pic x(10) value '123       '.
01 some-n pic 9(10).

procedure division.

move function trim(str) to some-n
move some-n to str

display some-n, " : ", str end-display
goback.

0000000123 : 0000000123

As Bill mentioned above with validation, this assumes all spaces is the equivalent of 0. That may or may not be a sane thing to allow. Non digits being an issue as well.

Solution 4

The easiest way is to use the WITH CONVERSION clause on the move statement, and if you aren't sure of the input, add the ON EXCEPTION clause.

IDENTIFICATION DIVISION.
PROGRAM-ID. ONCONVERSION.
ENVIRONMENT DIVISION.
DATA DIVISION.
WORKING-STORAGE SECTION. 

    01 VARIN  PIC X(10).
    01 VAROUT PIC 9(10).

PROCEDURE DIVISION.
    MOVE '123456    ' TO VARIN

    MOVE VARIN TO VAROUT WITH CONVERSION
    ON EXCEPTION
        MOVE ZERO TO VAROUT
    END-MOVE

    DISPLAY VARIN

    STOP RUN.

Solution 5

I am surprised no one has suggested using NUMVAL here...

IDENTIFICATION DIVISION.
PROGRAM-ID. EXAMPLE.
DATA DIVISION.
WORKING-STORAGE SECTION.
01  VARIN     PIC X(10).
01  VAROUT    PIC 9(10).
PROCEDURE DIVISION.
    MOVE '123456    ' TO VARIN
    COMPUTE VAROUT = FUNCTION NUMVAL(VARIN)
    DISPLAY '>' VARIN '<'
    DISPLAY '>' VAROUT '<'
    GOBACK
    .

which produces...

>123456    <
>0000123456<

The problem with this approach is that if the NUMVAL argument does not convert to numeric the program throws an exception and dies. Also this is not very efficient from a CPU usage point of view because it requires character to binary numeric conversion and back to display format again (all done under the covers but takes cycles).

As a general rule I would not recommend using NUMVAL (even if it looks like a 'nicer' solution). I would stick with the solution as presented in the original question. That solution is computationally efficient and is a common idiom used in COOBL programming.

Share:
16,317
mllamazares
Author by

mllamazares

Updated on June 05, 2022

Comments

  • mllamazares
    mllamazares almost 2 years

    I have an alphanumeric variable with a length of 10. It contains a number at the beginning, the rest of the digits are filled with spaces. Then I need to move the string to the left and put the number of spaces with '0' at the begining. This examples speaks for themselves:

    INPUT            OUTPUT
    ==============================
    '123456    ' ->  '0000123456'
    '12345678  ' ->  '0012345678'
    '123456789 ' ->  '0123456789'
    '1234567890' ->  '1234567890'
    

    Then I tought in something like this:

    Check this COBOL fiddle where you can try: http://ideone.com/mgbKZ3 (just click on edit)

       IDENTIFICATION DIVISION.
       PROGRAM-ID. VARSWAP.
       ENVIRONMENT DIVISION.
       DATA DIVISION.
       WORKING-STORAGE SECTION. 
    
           01 VARIN   PIC X(10).
           01 VARSWAP PIC X(10) JUSTIFIED RIGHT.
    
       PROCEDURE DIVISION.
    
           MOVE '123456    ' TO VARIN
    
           UNSTRING VARIN DELIMITED BY ' ' INTO VARSWAP
    
           INSPECT VARSWAP REPLACING LEADING SPACE BY '0'
    
           MOVE VARSWAP TO VARIN
    
           DISPLAY VARIN
    
           STOP RUN.
    

    Returns:

    0000123456
    

    It seems work ok, but I wonder if you have a better, simpler, or clearer way to do it.

  • Bill Woodger
    Bill Woodger about 10 years
    Not all implementations of intrinsic functions have TRIM, perhaps only the more extensive implementations :-)
  • Bill Woodger
    Bill Woodger about 10 years
    WITH CONVERSION is not standard COBOL, nor is END-MOVE. After the ON EXCEPTION, what is your source field? Is is it zero, space or invalid? Can't tell, can you? You may want to edit your DISPLAY copied from the original, and indicate which COBOL you are using. "Easy" is relative...
  • mllamazares
    mllamazares about 10 years
    Yeah, in my case I don't have TRIM function.
  • Bill Woodger
    Bill Woodger about 10 years
    Even with editing characters in the field, NUMVAL/NUMVALC has that kicker - fails with bad data, as you point out. On the Mainframe it is not converted to binary (or not alone), results are return as floating-point values, even worse amounts of conversion code... can't bring myself to use it :-) For a simple, always valid, string of numeric data, UNSTRING for sure. Yes, 99/100 who know about JUST RIGHT will INSPECT. Doesn't mean they won't understand when a naturally right-justified field is used instead, which also does the zero-fill by default. Others will NUMVAL without a qualm...
  • Bill Woodger
    Bill Woodger about 10 years
    @Candil you can get GNU COBOL from SourceForge. And then use TRIM. Even just for practice and fun out-of-hours.
  • Bill Woodger
    Bill Woodger about 10 years
    We'll get the Perl people all excited shortly :-) Nicely laid out. I'd MOVE ZERO TO STRING-OUT, make the first PERFORM TIMES and kill the second PERFORM. I'd make the COMP-3s into COMP. Traditionalists, traditionally, wouldn't have used reference-modification...
  • Valdis Grinbergs
    Valdis Grinbergs about 10 years
    Thanks, Bill, that is even better. Here is the paragraph rewritten: MAKE-STRING-OUT. MOVE ZEROS TO STRING-OUT MOVE 10 TO CHAR-OUT-NUM CHAR-IN-NUM PERFORM 10 TIMES IF STRING-IN (CHAR-IN-NUM:1) NOT = SPACE MOVE STRING-IN (CHAR-IN-NUM:1) TO STRING-OUT (CHAR-OUT-NUM:1) SUBTRACT 1 FROM CHAR-OUT-NUM END-IF SUBTRACT 1 FROM CHAR-IN-NUM END-PERFORM .
  • Bill Woodger
    Bill Woodger about 10 years
    Another suggestion. If you want to avoid the literal 10s, you can use LENGTH OF (if available to you) or FUNCTION LENGTH ( STRING-IN ). You can use the same method to get the length of the output field, and check they are equal. Stick them in a field, and use the field for setting values and the TIMES. Do all of that up at the top of the program. A little protection against unknowing program-changes, and minimise those pesky literal which should all be the same, until the same maintainer hits it and gets all but one... Edit whatever you are happy with into your answer.
  • Bill Woodger
    Bill Woodger about 10 years
    There is no need to have the old version explicitly in your answer. Comments on SO are ephemeral. Once you finish your update, we can delete them. The original code still exists in the edit revision history anyway. Comments can always be flagged, obsolete, two chatty, not consturctive. Questions/Answers can be flagged to request removal of comments which are no longer useful as well.
  • Scott Nelson
    Scott Nelson about 10 years
    I guess I've been using AcuCobol too long that I didn't realize that WITH CONVERSION is non-standard. My intent is that, if the conversion fails, I would move zero to the output. Another option would be to have more elaborate diagnostics in that case, perhaps even STOP "BAD DATA".