Re: Fw: Hex to Decimal Conversion in COBOL

2007-12-19 Thread Howard Brazee
My code has: 01 PASSED-DBCONV-RECORD. 02 PASSED-DBCONV-DISPLAY-DBKEY. 03 PASSED-DBCONV-PAGE PIC X(08). 03 PASSED-DBCONV-PAGE-N REDEFINES PASSED-DBCONV-PAGE

Re: Hex to Decimal Conversion in COBOL

2007-12-18 Thread Tom Simons
If the input is 5 characters of hex-digit binary values: 05 fldin pic x value '0b01020304'. and the output should be a binary fullword (x'000b1234'=725,556): 05 fldout pic 9(8) comp value 725556. then a single move (pack) instruction, with appropriate work areas, will do the conversion

Re: Fw: Hex to Decimal Conversion in COBOL

2007-12-18 Thread Paul Gilmartin
On Tue, 18 Dec 2007 09:29:14 -0500, Hardee, Charles H wrote: >Consider this: > >... >COMPUTE OUTPUT-VALUE = OUTPUT-VALUE * 16 + WORK-VALUE >... > Much better. >-Original Message- >From: IBM Mainframe Discussion List [mailto:[EMAIL PROTECTED] On >Behalf Of Bill Klein > >To do t

Re: Fw: Hex to Decimal Conversion in COBOL

2007-12-18 Thread Hardee, Charles H
t: Tuesday, December 18, 2007 7:00 AM To: IBM-MAIN@BAMA.UA.EDU Subject: Fw: Fw: Hex to Decimal Conversion in COBOL To do this manually, If you have "B1234" (each character taking 1 byte) then the "manual" conversion would be (4 * (16 ** 0)) + (3 * (16 ** 1)) + (2

Fw: Fw: Hex to Decimal Conversion in COBOL

2007-12-18 Thread Bill Klein
To do this manually, If you have "B1234" (each character taking 1 byte) then the "manual" conversion would be (4 * (16 ** 0)) + (3 * (16 ** 1)) + (2 * (16 ** 2)) + (1 * (16 ** 3)) + (11 * (16 ** 4) You would need to first convert A to 10, B to 11 ... F to 16 "Srini" <[EMAIL PROT

Fw: Hex to Decimal Conversion in COBOL

2007-12-17 Thread Bill Klein
When you say 5 character HEX value Do you mean something like PIC X(10) with values of "A12F33FFdd" - or do you mean that you are actually receiving data in "binary" which you are considering "hex"? If it is something like the first example, then the most common way to "solve" this in COBOL i

Re: Hex to Decimal Conversion in COBOL

2007-12-17 Thread Howard Brazee
On Sun, 16 Dec 2007 23:28:05 -0800 (PST), Srini <[EMAIL PROTECTED]> wrote: >I am receiving 5 character HEX value from a file and the requirement >is to convert the 5 character HEX value to Decimal in a COBOL program. >Is there any function/verb available in COBOL to convert the HEX vale >to Decima