IBM Mainframe Forum Index
 
Log In
 
IBM Mainframe Forum Index Mainframe: Search IBM Mainframe Forum: FAQ Register
 

Rounding the cents to zero


IBM Mainframe Forums -> COBOL Programming
Post new topic   Reply to topic
View previous topic :: View next topic  
Author Message
dharmaraok

New User


Joined: 10 Mar 2011
Posts: 45
Location: india

PostPosted: Sat Jun 21, 2014 8:25 am
Reply with quote

I have an dollar amount like $184.44 or $50.07 . In need round off the decimals values only to zero.

ouput should be like $184.00 and $50.00

I tried with round function and but I am not getting the correct value . Could you please let me know how can I approach this.
Back to top
View user's profile Send private message
Bill Woodger

Moderator Emeritus


Joined: 09 Mar 2011
Posts: 7309
Location: Inside the Matrix

PostPosted: Sat Jun 21, 2014 1:09 pm
Reply with quote

What do you want done with .50, .51 or .99?

Assuming that your data is for output-readable-by-human:

Code:
05  nice-name.
    10  nice-name-dollar-value PIC $(3)9.
    10  FILLER                 PIC X(3) VALUE ".00".

COMPUTE nice-name-dollar-value ROUDED =
        your calculaiton


The length of the field with the editing symbol is of course your choice, I've only picked something as an example
Back to top
View user's profile Send private message
Marso

REXX Moderator


Joined: 13 Mar 2006
Posts: 1353
Location: Israel

PostPosted: Mon Jun 23, 2014 2:09 pm
Reply with quote

Just for fun, I have written this small program:
Code:
       WORKING-STORAGE SECTION.
      *-----------------------*
       01  round3-var.                                   
           03 round3-num1                pic s9(10)v9(2).
           03 round3-num2                pic s9(10)v9(2).
           03 round3-dsp1                pic z(10).9(2).
           03 round3-dsp2                pic z(10).9(2).
Code:
       PROCEDURE DIVISION.
      *==================*
           MOVE 184.44 TO ROUND3-NUM1 
           PERFORM C064R-COMPUTE       
           MOVE 30451.85 TO ROUND3-NUM1
           PERFORM C064R-COMPUTE       
                                                       
       C064R-COMPUTE SECTION.                         
      *---------------------*                         
           COMPUTE ROUND3-NUM2 ROUNDED =               
               (ROUND3-NUM1 / 100) * 100               
           MOVE ROUND3-NUM1 TO ROUND3-DSP1             
           MOVE ROUND3-NUM2 TO ROUND3-DSP2             
           DISPLAY 'Num2 = (Num1 / 100) * 100      '   
               'Num1=' ROUND3-DSP1 ' Num2=' ROUND3-DSP2
                                                       
           COMPUTE ROUND3-NUM2 ROUNDED =               
               (ROUND3-NUM1 / 1000) * 1000             
           MOVE ROUND3-NUM1 TO ROUND3-DSP1             
           MOVE ROUND3-NUM2 TO ROUND3-DSP2             
           DISPLAY 'Num2 = (Num1 / 1000) * 1000    '   
               'Num1=' ROUND3-DSP1 ' Num2=' ROUND3-DSP2
                                                       
           COMPUTE ROUND3-NUM2 ROUNDED =               
               (ROUND3-NUM1 / 10000) * 10000           
           MOVE ROUND3-NUM1 TO ROUND3-DSP1             
           MOVE ROUND3-NUM2 TO ROUND3-DSP2             
           DISPLAY 'Num2 = (Num1 / 10000) * 10000  '   
               'Num1=' ROUND3-DSP1 ' Num2=' ROUND3-DSP2
           .                                           
       C064R-EXIT.                                     
           EXIT.                                       

and when executed, I received the following output:
Code:
Num2 = (Num1 / 100) * 100      Num1=       184.44 Num2=       184.40
Num2 = (Num1 / 1000) * 1000    Num1=       184.44 Num2=       184.00
Num2 = (Num1 / 10000) * 10000  Num1=       184.44 Num2=       180.00
Num2 = (Num1 / 100) * 100      Num1=     30451.85 Num2=     30451.80
Num2 = (Num1 / 1000) * 1000    Num1=     30451.85 Num2=     30451.00
Num2 = (Num1 / 10000) * 10000  Num1=     30451.85 Num2=     30450.00

Surprisingly, the second option does what you need (I say surprisingly because I expected the 1st one to work)
Back to top
View user's profile Send private message
Marso

REXX Moderator


Joined: 13 Mar 2006
Posts: 1353
Location: Israel

PostPosted: Mon Jun 23, 2014 2:20 pm
Reply with quote

OK...
I have removed the ROUNDED clause from the COMPUTE.
The program contains now:
Code:
           COMPUTE ROUND3-NUM2 = (ROUND3-NUM1 / 100) * 100   
           MOVE ROUND3-NUM1 TO ROUND3-DSP1                   
           MOVE ROUND3-NUM2 TO ROUND3-DSP2                   
           DISPLAY 'Num2 = (Num1 / 100) * 100      '         
               'Num1=' ROUND3-DSP1 ' Num2=' ROUND3-DSP2       
                                                             
           COMPUTE ROUND3-NUM2 = (ROUND3-NUM1 / 1000) * 1000 
           MOVE ROUND3-NUM1 TO ROUND3-DSP1                   
           MOVE ROUND3-NUM2 TO ROUND3-DSP2                   
           DISPLAY 'Num2 = (Num1 / 1000) * 1000    '         
               'Num1=' ROUND3-DSP1 ' Num2=' ROUND3-DSP2       
                                                             
           COMPUTE ROUND3-NUM2 = (ROUND3-NUM1 / 10000) * 10000
           MOVE ROUND3-NUM1 TO ROUND3-DSP1                   
           MOVE ROUND3-NUM2 TO ROUND3-DSP2                   
           DISPLAY 'Num2 = (Num1 / 10000) * 10000  '         
               'Num1=' ROUND3-DSP1 ' Num2=' ROUND3-DSP2       
The result is more to my liking:
Code:
Num2 = (Num1 / 100) * 100      Num1=       184.44 Num2=       184.00
Num2 = (Num1 / 1000) * 1000    Num1=       184.44 Num2=       180.00
Num2 = (Num1 / 10000) * 10000  Num1=       184.44 Num2=       100.00
Num2 = (Num1 / 100) * 100      Num1=     30451.85 Num2=     30451.00
Num2 = (Num1 / 1000) * 1000    Num1=     30451.85 Num2=     30450.00
Num2 = (Num1 / 10000) * 10000  Num1=     30451.85 Num2=     30400.00

So, so far, you could use:
Code:
           COMPUTE ROUND3-NUM2 = (ROUND3-NUM1 / 100) * 100   
And, if you need to round up:
Code:
           COMPUTE ROUND3-NUM2 = ((ROUND3-NUM1 + 0.5) / 100) * 100
Back to top
View user's profile Send private message
Marso

REXX Moderator


Joined: 13 Mar 2006
Posts: 1353
Location: Israel

PostPosted: Wed Jun 25, 2014 1:59 pm
Reply with quote

Just found another way to do this:
Code:
    03 num1                pic s9(10)v9(2) comp-3.
    03 num2                pic s9(10)v9(2) comp-3.

    COMPUTE NUM2 = FUNCTION INTEGER (NUM1)

Test program gave:
Code:
Num2 = Function Integer (Num1) Num1=       184.44 Num2=       184.00
Num2 = Function Integer (Num1) Num1=     30451.85 Num2=     30451.00
Back to top
View user's profile Send private message
Bill Woodger

Moderator Emeritus


Joined: 09 Mar 2011
Posts: 7309
Location: Inside the Matrix

PostPosted: Wed Jun 25, 2014 4:58 pm
Reply with quote

Marso, I'm wondering what you find deficient with my solution :-)

If truncation is desired, the ROUNDED is simply removed.

However, with TS/OP not bothering to clarify...

I don't think we ever need ( x / 100 ) * 100 in COBOL, nor FUNCTION INTEGER, as it can always be done in the data.
Back to top
View user's profile Send private message
Raghu navaikulam

Active User


Joined: 27 Sep 2008
Posts: 193
Location: chennai

PostPosted: Wed Jun 25, 2014 10:00 pm
Reply with quote

Hi,
try this

77 NUMB1 PIC $$$$.00.

move data to numb1.
display numb1.

Regards
Raghu
Back to top
View user's profile Send private message
Bill Woodger

Moderator Emeritus


Joined: 09 Mar 2011
Posts: 7309
Location: Inside the Matrix

PostPosted: Wed Jun 25, 2014 10:46 pm
Reply with quote

That'd do as the target, ROUNDED or without ROUNDED to truncate. I'm not sure if the compiler is clever enough these days to do it without extra effort :-)
Back to top
View user's profile Send private message
Bill Woodger

Moderator Emeritus


Joined: 09 Mar 2011
Posts: 7309
Location: Inside the Matrix

PostPosted: Fri Jun 27, 2014 11:43 pm
Reply with quote

Just checked on the code for the .00, it is extra generated. Added in a couple of Marso's for comparison as well:

Code:
       01  W-DOLLARS-TO-DISP-1.
           05  W-DTD1-DOLLARS PIC 9(7).
           05  FILLER         PIC XXX VALUE ".00".

           COMPUTE W-DTD1-DOLLARS ROUNDED = W-DOLLARS-PACKED

000018  COMPUTE                                                                 
   0003EC  D204 D160 8068          MVC   352(5,13),104(8)        TS2=0         
   0003F2  F045 D160 003E          SRP   352(5,13),62(0),5       TS2=0         
   0003F8  960F D164               OI    356(13),X'0F'           TS2=4         
   0003FC  F363 8018 D161          UNPK  24(7,8),353(4,13)       W-DTD1-DOLLARS

       01  W-DOLLARS-TO-DISP-2 PIC 9(7).00.

           COMPUTE W-DOLLARS-TO-DISP-2 ROUNDED = W-DOLLARS-PACKED

000020  COMPUTE                                                                 
   00040C  D20C D160 A08F          MVC   352(13,13),143(10)      TS2=0         
   000412  D204 D170 8068          MVC   368(5,13),104(8)        TS2=16         
   000418  F045 D170 003E          SRP   368(5,13),62(0),5       TS2=16         
   00041E  9200 D170               MVI   368(13),X'00'           TS2=16         
   000422  960F D174               OI    372(13),X'0F'           TS2=20         
   000426  DE0C D160 D170          ED    352(13,13),368(13)      TS2=0         
   00042C  4740 B1BA               BC    4,442(0,11)             GN=16(000436) 
   000430  D202 D16A A03E          MVC   362(3,13),62(10)        TS2=10         
   000436                 GN=16    EQU   *                                     
   000436  D209 8028 D163          MVC   40(10,8),355(13)        W-DOLLARS-TO-DI

       01  W-DOLLARS-TO-DISP-3 PIC 9(7).99.

           COMPUTE W-DOLLARS-TO-DISP-3  =
                    FUNCTION INTEGER (W-DOLLARS-PACKED + 0.5)

000022  COMPUTE                                                                 
   000446  F8F4 D148 8068          ZAP   328(16,13),104(5,8)     TS1=0         
   00044C  FA51 D152 A043          AP    338(6,13),67(2,10)      TS1=10         
   000452  D204 D160 D152          MVC   352(5,13),338(13)       TS2=0         
   000458  D100 D164 D157          MVN   356(1,13),343(13)       TS2=4         
   00045E  F844 D158 D160          ZAP   344(5,13),352(5,13)     TS1=16         
   000464  F951 D152 C022          CP    338(6,13),34(2,12)      TS1=10         
   00046A  47B0 B214               BC    11,532(0,11)            GN=18(000490) 
   00046E  F854 D160 D158          ZAP   352(6,13),344(5,13)     TS2=0         
   000474  F050 D160 0002          SRP   352(6,13),2(0),0        TS2=0         
   00047A  D505 D160 D152          CLC   352(6,13),338(13)       TS2=0         
   000480  4780 B214               BC    8,532(0,11)             GN=19(000490) 
   000484  FA40 D158 A045          AP    344(5,13),69(1,10)      TS1=16         
   00048A  F844 D158 D158          ZAP   344(5,13),344(5,13)     TS1=16         
   000490                 GN=19    EQU   *                                     
   000490                 GN=18    EQU   *                                     
   000490  D20C D160 A082          MVC   352(13,13),130(10)      TS2=0         
   000496  F853 D170 D159          ZAP   368(6,13),345(4,13)     TS2=16         
   00049C  F040 D171 0002          SRP   369(5,13),2(0),0        TS2=17         
   0004A2  DE0C D160 D170          ED    352(13,13),368(13)      TS2=0         
   0004A8                 GN=21    EQU   *                                     
   0004A8  D209 8038 D163          MVC   56(10,8),355(13)        W-DOLLARS-TO-DI

       01  W-DOLLARS-TO-DISP-4 PIC 9(7).99.

           COMPUTE W-DOLLARS-TO-DISP-4  =
                    ((W-DOLLARS-PACKED + 0.5) / 100) * 100

000025  COMPUTE                                                                 
   0004B8  F8F4 D148 8068          ZAP   328(16,13),104(5,8)     TS1=0         
   0004BE  FA51 D152 A043          AP    338(6,13),67(2,10)      TS1=10         
   0004C4  D207 D160 D150          MVC   352(8,13),336(13)       TS2=0         
   0004CA  FD71 D160 A041          DP    352(8,13),65(2,10)      TS2=0         
   0004D0  F8F5 D148 D160          ZAP   328(16,13),352(6,13)    TS1=0         
   0004D6  FC71 D150 A041          MP    336(8,13),65(2,10)      TS1=8         
   0004DC  D20C D160 A082          MVC   352(13,13),130(10)      TS2=0         
   0004E2  F854 D170 D153          ZAP   368(6,13),339(5,13)     TS2=16         
   0004E8  DE0C D160 D170          ED    352(13,13),368(13)      TS2=0         
   0004EE                 GN=24    EQU   *                                     
   0004EE  D209 8048 D163          MVC   72(10,8),355(13)        W-DOLLARS-TO-DI



All get the same result, which is one important thing anyway.
Back to top
View user's profile Send private message
Marso

REXX Moderator


Joined: 13 Mar 2006
Posts: 1353
Location: Israel

PostPosted: Sat Jun 28, 2014 12:19 am
Reply with quote

Bill Woodger wrote:
Marso, I'm wondering what you find deficient with my solution :-)
Nothing! Was just having some geek fun. (and I think I'm not the only one!) icon_smile.gif
Back to top
View user's profile Send private message
View previous topic :: :: View next topic  
Post new topic   Reply to topic View Bookmarks
All times are GMT + 6 Hours
Forum Index -> COBOL Programming

 


Similar Topics
Topic Forum Replies
No new posts Prevent rounding of COMP-2 when displ... COBOL Programming 5
No new posts COBOL - ROUNDING OFF TO NEAREST 1 $ COBOL Programming 4
No new posts Calculate and rounding up value usin... DFSORT/ICETOOL 23
No new posts Rounding off to the next decimal number COBOL Programming 17
No new posts Rounding off the rate value COBOL Programming 2
Search our Forums:

Back to Top