Suppressing leading zeroes

11,516

Solution 1

Didn't use any functions, as those are site-dependant.

So the result is quite a monster(and I won't spend more time refining it) :

   01  WS.
       05  W-AMOUNT                    PIC 9(09)v99.
       05  W-AMOUNT-ALPHA              REDEFINES W-AMOUNT
                                       PIC X(01) OCCURS 11.
       05  W-DISPLAY                   PIC X(25).
       05  W-DISPLAY-TAB               REDEFINES W-DISPLAY
                                       PIC X(01) OCCURS 25.
       05  W-SENTENCE                  PIC X(12)
                                       VALUE " TO PAY SOON".
       05  W-SENTENCE-TAB              REDEFINES W-SENTENCE
                                       PIC X(01) OCCURS 12.
       05  W-SENTENCE-LENGTH           PIC 9(04) COMP-5.
       05  W-POSITION-AMOUNT           PIC 9(04) COMP-5.
       05  W-POSITION-SENTENCE         PIC 9(04) COMP-5.
       05  W-POSITION-DISPLAY          PIC 9(04) COMP-5.
       05  W-LEADING-ZEROES            PIC X(01).
           88  STILL-LEADING-ZEROES    VALUE "Y".
           88  NO-MORE-LEADING-ZEROES  VALUE "N".

followed by :

   PROCEDURE DIVISION.
  *-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-
   CONTROL-PROCEDURE.
  **
  * The main procedure of the program
  **
       MOVE 15314.16 TO  W-AMOUNT
       PERFORM SUB-PROCEDURE
       DISPLAY  "LOAN AMOUNT $"
       W-DISPLAY
       MOVE 314.16 TO  W-AMOUNT
       PERFORM SUB-PROCEDURE
       DISPLAY  "LOAN AMOUNT $" W-DISPLAY
       GOBACK
       .
   SUB-PROCEDURE.
       MOVE ZERO   TO  W-POSITION-DISPLAY
                       W-POSITION-SENTENCE
       MOVE SPACES TO  W-DISPLAY
       SET STILL-LEADING-ZEROES TO TRUE
       PERFORM VARYING     W-POSITION-AMOUNT
               FROM        1 BY 1
               UNTIL       W-POSITION-AMOUNT > 9
           IF (W-AMOUNT-ALPHA (W-POSITION-AMOUNT)
              NOT EQUAL ZERO) THEN 
              SET NO-MORE-LEADING-ZEROES TO TRUE
           END-IF
           IF NO-MORE-LEADING-ZEROES THEN 
               ADD 1 TO W-POSITION-DISPLAY
               MOVE W-AMOUNT-ALPHA (W-POSITION-AMOUNT)
                 TO W-DISPLAY-TAB  (W-POSITION-DISPLAY)
           END-IF
       END-PERFORM
       ADD 1 TO    W-POSITION-DISPLAY
       MOVE "." TO W-DISPLAY-TAB (W-POSITION-DISPLAY)
       ADD 1 TO    W-POSITION-DISPLAY
       MOVE        W-AMOUNT-ALPHA (W-POSITION-AMOUNT)
         TO        W-DISPLAY-TAB  (W-POSITION-DISPLAY)
       ADD 1 TO    W-POSITION-DISPLAY
                   W-POSITION-AMOUNT
       MOVE        W-AMOUNT-ALPHA (W-POSITION-AMOUNT)
         TO        W-DISPLAY-TAB  (W-POSITION-DISPLAY)
       MOVE LENGTH OF W-SENTENCE TO W-SENTENCE-LENGTH
       PERFORM W-SENTENCE-LENGTH TIMES
           ADD  1  TO  W-POSITION-DISPLAY
                       W-POSITION-SENTENCE
           MOVE W-SENTENCE-TAB     (W-POSITION-SENTENCE)
             TO W-DISPLAY-TAB      (W-POSITION-DISPLAY)
       END-PERFORM
       .

final result :

LOAN AMOUNT $15314.16 TO PAY SOON     
LOAN AMOUNT $314.16 TO PAY SOON  

There are plenty of ways optimizing it(especially the way I'm handling digits behind the dot, it's absolutely awful, but I'm doing it while watching other things, so I went to simpler things). I would not dare submitting that to code review. But it works.

Solution 2

Since you seem to have concerns over what a reviewer may say, here's the code which actually does what you have asked for:

   UNSTRING edited-field
             DELIMITED BY ALL SPACE
                                INTO ignore-this
                                     no-leading-space-field

I'm not at all sure how that would be difficult to review. It does need these definitions:

01  edited-field                        PIC Z(10).99.
01  no-leading-space-field              PIC x(13).
01  ignore-this                         PIC X.

If you are talking of optimisation for performance, then you'd need to work on the code that gazzz0x2z provided in their answer. But then your reviewer will get all confused again with multiple lines of code.


COBOL verbs STRING and UNSTRING have been around since the 1974 COBOL Standard, so should be widely available. For manipulation of regular text they have many uses.

   IDENTIFICATION DIVISION.
   PROGRAM-ID. supspace.
   DATA DIVISION.
   WORKING-STORAGE SECTION.
   01  unedited-field                      PIC 9(9)v99.
   01  edited-field                        PIC Z(10).99.
   01  no-leading-space-field              PIC x(13).
   01  output-text                         PIC x(80).
   01  text-intro                          PIC x(13) VALUE 
                                             "LOAN AMOUNT $".
   01  text-outro                          PIC x(12) VALUE 
                                             " TO PAY SOON".
   01  ignore-this                         PIC X.
   PROCEDURE DIVISION.
       MOVE 0.01                    TO unedited-field
       PERFORM                      the-work
       MOVE 123.01                  TO unedited-field
       PERFORM                      the-work
       MOVE ZERO                    TO unedited-field
       PERFORM                      the-work
       MOVE 123456789.01            TO unedited-field
       PERFORM                      the-work
       GOBACK
       .
   the-work.
       PERFORM                      left-justify-edit
       PERFORM                      assemble-output
       DISPLAY 
              output-text
       .
   left-justify-edit.
       MOVE unedited-field          TO edited-field
       UNSTRING edited-field
                 DELIMITED BY ALL SPACE
                                    INTO ignore-this
                                         no-leading-space-field
       .
   assemble-output.
       MOVE SPACE                   TO output-text
       STRING 
              text-intro
               DELIMITED BY SIZE
              no-leading-space-field
               DELIMITED BY SPACE
              text-outro
               DELIMITED BY SIZE
                                    INTO output-text
       .

Output is:

LOAN AMOUNT $.01 TO PAY SOON
LOAN AMOUNT $123.01 TO PAY SOON
LOAN AMOUNT $.00 TO PAY SOON
LOAN AMOUNT $123456789.01 TO PAY SOON

Note that edited-field is define one byte longer than otherwise necessary, Z(10) instead of Z(9). This is to ensure that there is always at least one leading space for the DELIMITED of the UNSTRING.

Note that STRING does not space-pad its target field when the resultant value is less than the size of the target, so if the resultant value can be variable in length, clear the target field before the using the STRING verb.

UNSTRING uses specified delimiters to split a single field into multiple fields.

The key to how it works is the field ignore-this and the DELIMITED BY ALL SPACE, and the guaranteed presence of at least one leading space.

ALL SPACE is any number of spaces from one to the size of the field it is being applied to. Any delimiter named in UNSTRING is not included in the INTO fields. The presence of a leading delimiter means that the first INTO field will "contain" a zero-length piece of data, space-padded to the length of that first INTO field. The second INTO field will contain the data with no leading spaces, and will be space-padded to the length of that field.

STRING takes multiple fields, which can be delimited by data within them, and puts them together to make one piece of data which is placed in the INTO field, with truncation if necessary, but without space-padding if the data is shorter than the INTO field.

In the STRING as used here, only SPACE is a delimiter, rather than ALL SPACE, as a single space is sufficient to delimit and the code will be faster than using ALL SPACE.

Solution 3

Here is a sample, "to spec", but it may not be "to vendor", depending on how old the compiler is, as gazzz0x2z pointed out. (FUNCTION TRIM was in the 1989 amendment, so 26 years later...) EDIT: Turns out, that's a mistake. As Bill pointed out, TRIM is only in the recent spec from 2014. I be dissin' where I shouldn't be dissin'. Leaving the comment in, and drooping head in shame.

   identification division.
   program-id. left-just.

   data division.
   working-storage section.
   01 amount      pic 9(9)v99 value 100.00.
   01 dollars     pic $(8)9.99.
   01 show-loan   pic x(32).

   procedure division.
   move amount to dollars
   string
       "LOAN AMOUNT " delimited by size
       function trim(dollars leading) delimited by size
     into show-loan
   display function trim(show-loan trailing)
   goback.
   end program left-just.

Solution 4

This uses part of my code here.

https://codereview.stackexchange.com/questions/69220/trim-functions-in-cobol

ws-amount                           pic 9(09)V99.
ws-formated-amount                  pic $$$$,$$$,$$9.99.
ws-output-message                   pic X(27).

MOVE ws-amount
  TO ws-formated-amount.
MOVE ws-formated-amount
  TO STR-VALUE-IN.
MOVE FUNCTION LENGTH (ws-formated-amount)
  TO STR-LENGTH-IN.
PERFORM 5100-LTRIM.
MOVE SPACES TO ws-output-message.
STRING
   'LOAN AMOUNT '
   STR-VALUE-OUT (1:STR-LENGTH-OUT)
       DELIMITED SIZE
INTO
   ws-output-message
END-STRING.
Share:
11,516
Maxcc0
Author by

Maxcc0

Updated on June 28, 2022

Comments

  • Maxcc0
    Maxcc0 almost 2 years

    We use a numeric-edited picture clause Z(4).99 to supress leading zeroes. It replaces leading zeros with spaces. My question here is, can we remove those spaces and display only the actual value without leading spaces?

    I have ws-amount which is pic 9(09)v99. If I move 100 into it,it will look like 00000010000. But in my report I need it to be displayed like "LOAN AMOUNT $100.00".

    • Bill Woodger
      Bill Woodger over 8 years
      Why do you want to do this? On a report it'll look like a bag-o'-crap. So what do you want to do this for?
    • gazzz0x2z
      gazzz0x2z over 8 years
      depends on the report. "You must pay 319.58$" is not better with more spaces.
    • Bill Woodger
      Bill Woodger over 8 years
      @gazzz0x2z "You must pay 319.58$bbbbb or we will terminate with extreme prejudice" is no better, though. So why I asked. Could be a "CSV". A leading zero shouldn't matter there (it has no significance) unless the receiver gets all weird about it. Again if a CSV, what follows the number. Left-justified may not be sufficient. So need to know before an answer...
    • gazzz0x2z
      gazzz0x2z over 8 years
      Yez, I agree. We need more info. Just wanted to point out that the demand MIGHT be something important to do. of course, maybe not. Sometimes, the best code is no code at all.
    • Brian Tiffin
      Brian Tiffin over 8 years
      If you have FUNCTION TRIM, then it is FUNCTION TRIM(field LEADING)
    • Maxcc0
      Maxcc0 over 8 years
      I have a variable ws-amount pic 9(09)v99. so if i move 100 into it,it will look like 000000100.00. But in my report i need it to be displayed like " LOAN AMOUNT $100.00". How to do this??
    • Bill Woodger
      Bill Woodger over 8 years
      @gazzz0x2z you were correct :-)
    • Bill Woodger
      Bill Woodger over 8 years
      You have enough reputation to vote now :-)
  • Maxcc0
    Maxcc0 over 8 years
    Thanks, the above suggestions are really helpful although it requires optimization otherwise the reviewer will have a headache reviewing the code :P. Thanks a lot guys :)
  • Bill Woodger
    Bill Woodger over 8 years
    @Maxcc0 What sort of optimization are you talking about? If you have limits within which you have to work, you need to include those in the question. There's one, count it, one, instruction doing what you have asked for (the UNSTRING). Looking at you username, can we add the Mainframe tag to the question?
  • gazzz0x2z
    gazzz0x2z over 8 years
    I feel sad that your only upvote is mine. Your answer is much cleaner than mine.
  • Maxcc0
    Maxcc0 over 8 years
    I don't have any limitations but the more we include lines in the code the less redable it gets. Yes you can add the mainframe tag. Thanks again for the optimization tip.
  • Bill Woodger
    Bill Woodger over 8 years
    @gazzz0x2z we're a small "community" here, so not many votes is usual. The only upvote on yours is mine :-) There's till time anyway.
  • Bill Woodger
    Bill Woodger over 8 years
    @Maxcc0 It should not be the number of lines of code that make a program harder to read. With good names, good program structure and good code structure, large programs are readable. With none of that, even small programs are unreadable. Number of lines of source is not the way to assess complexity.
  • gazzz0x2z
    gazzz0x2z over 8 years
    @Bill : good programmes write far less lines of code for the same functionalities... But not by trying to reduce the program size. They do it by simplifying the flow of data & treatments. Excess of LOC usually comes from lack of DRY. I've seen 30,000 lines monster with 400 times the same database call, just with different elements hardcoded. Better use 20 more lines for making a reusable database call... (in other words, you're right, trying to reduce LOC count just for the sake of it is usually a bad idea)
  • Bill Woodger
    Bill Woodger over 8 years
    As far as I can tell, TRIM only formally appears in the 2014 Standard.
  • Brian Tiffin
    Brian Tiffin over 8 years
    Oh, so I'm 25 years early then. My bad.
  • Kennah
    Kennah over 8 years
    TRIM also appears in the Kennah Standard codereview.stackexchange.com/questions/69220/…
  • Kennah
    Kennah over 8 years
    Good catch, @BillWoodger