View previous topic :: View next topic
|
Author |
Message |
mubs55
New User
Joined: 19 Apr 2006 Posts: 12
|
|
|
|
Hi,
I have 4 variables of the format S99V999.
If any of the vraiable has negative value eg -1.010 i have to display it as (1.010) without any leading zeros or leading/trailing spaces.
If the number is positive i should be displaying 1.010 without any leading/trailing zeros and spaces.
Please suggest a way out.
Thanks,
mubs55 |
|
Back to top |
|
|
William Thompson
Global Moderator
Joined: 18 Nov 2006 Posts: 3156 Location: Tucson AZ
|
|
|
|
As you have discovered, COBOL does not provide that editing ability.
I would think that you are stuck with a move and if negitive, string...... |
|
Back to top |
|
|
anand_sundaramurthy
New User
Joined: 07 May 2007 Posts: 12 Location: Chennai
|
|
|
|
Hi,
Am not sure about the negative part of your question.if its just positive if you declare the variable as z99 then it will remove all the leading and the trailing 0's.try it out. |
|
Back to top |
|
|
socker_dad
Active User
Joined: 05 Dec 2006 Posts: 177 Location: Seattle, WA
|
|
|
|
OK, I whipped this out on a quickie and I leave the refinement to you. It ain't pretty, but it works. Pardon the leading periods - this editor wants to squish everything to the left column!
Here's the code:
01 WS-NUMERIC-FIELD PIC S99V999 COMP-3 VALUE ZEROES.
01 WS-DISPLAY-NUMBER PIC -ZZ.ZZZ.
01 WS-WORK-NUMBER PIC 9(8).
01 WS-SUB PIC 9.
01 EOSUB PIC X VALUE 'N'.
PROCEDURE DIVISION.
......MOVE -12.345 TO WS-NUMERIC-FIELD.
......MOVE WS-NUMERIC-FIELD TO WS-DISPLAY-NUMBER.
......DISPLAY WS-DISPLAY-NUMBER.
......IF WS-NUMERIC-FIELD < ZERO
..........MOVE 'N' TO EOSUB
..........PERFORM VARYING WS-SUB FROM 1 BY 1
..............UNTIL WS-SUB > 8
..................OR EOSUB = 'Y'
................IF WS-DISPLAY-NUMBER (WS-SUB:1) = '-'
....................MOVE '(' TO WS-WORK-NUMBER (WS-SUB:1)
................ELSE
....................MOVE WS-DISPLAY-NUMBER (WS-SUB:1)
........................TO WS-WORK-NUMBER (WS-SUB:1)
................END-IF
..........END-PERFORM
..........MOVE ')' TO WS-WORK-NUMBER (8:1)
..........DISPLAY WS-WORK-NUMBER
......END-IF.
......GOBACK.
My output is:
-12.345
(12.345)
Of course, you will need to fuss over the trailing zeroes and space suppression when there is only 1 (or no) leading digits, but this should give you a start. After all, we had to do our own homework....... |
|
Back to top |
|
|
socker_dad
Active User
Joined: 05 Dec 2006 Posts: 177 Location: Seattle, WA
|
|
|
|
Oh yeah - EOSUB is superfluous in this code as I didn't use it for anything........ |
|
Back to top |
|
|
William Thompson
Global Moderator
Joined: 18 Nov 2006 Posts: 3156 Location: Tucson AZ
|
|
Back to top |
|
|
ramfrom84
New User
Joined: 23 Aug 2006 Posts: 93 Location: chennai
|
|
|
|
EOSUB is just Variable.. How can u use it... |
|
Back to top |
|
|
Aji
New User
Joined: 03 Feb 2006 Posts: 53 Location: Mumbai
|
|
|
|
Hi
Does the following work. (I didn't try the following, since cobol compiler is not available to me right now.)
Working-storage Section.
01 Edit_no1.
02 filler pic x value "(".
02 p_no1 pic z9.9999.
02 filler pic x value ")".
01 Edit_no2.
02 p_no2 pic z9.9999.
Procedure Division.
if given_no < 0
move given_no to p_no1
display Edit_no1
else
move given_no to p_no2
display Edit_no2
End-if.
Aji Cherian |
|
Back to top |
|
|
Raphael Bacay
New User
Joined: 04 May 2007 Posts: 58 Location: Manila, Philippines
|
|
|
|
Hi,
This problem is short and interesting. I would like to offer a solution much similar to the one above.
01 FIELDS
05 PAREN-NUM
10 A PIC X VALUE '('
10 B PIC X(6).
05 FORMATTED-INPUT
10 D PIC -Z.9999.
MOVE INPUT TO FORMATTED-INPUT
IF D < ZEROS
MOVE D TO B
INSPECT B REPLACING FIRST SPACE BY ')'
DISPLAY PAREN-NUM
ELSE
MOVE D TO B
DISPLAY B
END-IF. |
|
Back to top |
|
|
socker_dad
Active User
Joined: 05 Dec 2006 Posts: 177 Location: Seattle, WA
|
|
|
|
EOSUB would be used if you wanted to break out of processing before the high end of the WS-SUB (in this case 8) is reached.
Say you have a condition where you want to end the loop if you hit a period in the field. You would test for that value and if when it was true, move 'Y' to the EOSUB field and the loop would end. Like this:
Code: |
PERFORM VARYING WS-SUB FROM 1 BY 1
UNTIL WS-SUB > 8
OR EOSUB = 'Y'
IF WS-DISPLAY-NUMBER (WS-SUB:1) = '-'
MOVE '(' TO WS-WORK-NUMBER (WS-SUB:1)
ELSE
IF WS-DISPLAY-NUMBER(WS-SUB:1) = '.'
MOVE 'Y' TO EOSUB
ELSE
MOVE WS-DISPLAY-NUMBER (WS-SUB:1)
TO WS-WORK-NUMBER (WS-SUB:1)
END-IF
END-IF
END-PERFORM
MOVE ')' TO WS-WORK-NUMBER ((WS-SUB+1):1)
|
|
|
Back to top |
|
|
kgumraj
Active User
Joined: 01 May 2006 Posts: 151 Location: Hyderabad
|
|
|
|
Hi,
you can achive this by
Code: |
EXEC SQL
SELECT RTRIM(ABS(:WS-ABOSOLUTE-CONVERSION))
INTO :WS-CONVERTED
FROM SYSIBM.SYSDUMM1
END-EXEC.
|
|
|
Back to top |
|
|
mubs55
New User
Joined: 19 Apr 2006 Posts: 12
|
|
|
|
Thanks everyone.
I have found the solution as given below:
05 PrcfldsF OCCURS 4 TIMES.
10 PrcfldF PIC ZZ9.999.
MOVE PrcfldR (I) TO PrcfldF (I)
MOVE PrcfldF (I) TO PriceVal
IF PrcfldR (I) IS NEGATIVE
INSPECT PriceVal REPLACING
LEADING SPACES BY '(' BEFORE '.'
FIRST SPACE BY ')' AFTER '.'
INSPECT PriceVal REPLACING
LEADING '((' BY ' (' BEFORE '.'
END-IF
INSPECT PriceVal
TALLYING Space-Count FOR ALL ' ' BEFORE '.'
COMPUTE StrLen = FUNCTION LENGTH (PriceVal) - Space-Count
ADD 1 TO Space-Count
MOVE PriceVal (Space-Count: StrLen)
TO PrcfldT (I) (1:StrLen) |
|
Back to top |
|
|
|