Tek-Tips is the largest IT community on the Internet today!

Members share and learn making Tek-Tips Forums the best source of peer-reviewed technical information on the Internet!

  • Congratulations SkipVought on being selected by the Tek-Tips community for having the most helpful posts in the forums last week. Way to Go!

How do I convert hex into numeric

Status
Not open for further replies.

jk9427

Programmer
Apr 3, 2012
1
0
0
US
I have a program where a field is being passed in through linkage, and need to convert it into numeric to use it. Is there a simple way to convert this data to 5 digit numeric value?

LINKAGE SECTION.

01 port PIC X(4).
 
Yup. How you do this depends on the content of the field.

Post samples of all of the data patterns that might be in this field (i.e leading or trailing spaces, imbedded decimal point, imbedded sign, etc).
 
I wrote a routine (20 years ago) that accomplished that task.
It is written in RM/COBOL, COMP-4 is a binary formant in this compiler (COMP-X for Micro Focus).
The characters must be cheeked to be in range 0-9 or A-F(upper case), max input 18 characters.
I have also the versa routine dec2hex.cbl, that input numeric value and output hex values.
Code:
000001 IDENTIFICATION DIVISION.
000002 PROGRAM-ID. HEX2DEC.
000003 ENVIRONMENT DIVISION.
000004 CONFIGURATION SECTION.
000005 DATA DIVISION.
000006 WORKING-STORAGE SECTION.
000007 01  I                PIC S9(4) COMP-3.
000008 01  J                PIC S9(4) COMP-3.
000009 01  K                PIC S9(4) COMP-3.
000010 01  NN               PIC XX VALUE LOW-VALUES.
000011 01  NN-R REDEFINES NN.
000012     02 FILLER        PIC X.
000013     02 N-X           PIC X.
000014 01  N REDEFINES NN   PIC 9(4) COMP-4.
000015 01  X-18             PIC X(18) VALUE SPACES.
000016 01  X-18-R REDEFINES X-18.
000017     02 VEC-X-18      PIC X OCCURS 18.
000018 01  N-18-X.
000019     02 N-18          PIC 9(18) COMP-4.
000020 01  N-18-X-R REDEFINES N-18-X.
000021     02 VEC-N-18      PIC X OCCURS 8.
000022 01  F-18             PIC ----,---,---,---,---,---.
000023 01  XX               PIC XX VALUE LOW-VALUES.
000024 01  XX-R REDEFINES XX.
000025     02 FILLER        PIC X.
000026     02 X             PIC X.
000027 01  X-9 REDEFINES XX PIC 9(4) COMP-4.
000028 01  VECTOR.
000029     02 VEC   PIC X OCCURS 18.
000030 01  VECTOR-HEX PIC X(132)
000031       VALUE   "00000001000200030004000500060007000800090010001100@A01
000032-            "1200130014001500000016003200480064008000960112012801@B
000033-            "44016001760192020802240240    ".                    @C
000034 01  VECTOR-HEX REDEFINES VECTOR-HEX.
000035     02 VEC-HEX PIC 9(4) OCCURS 32.
000036 01  VECTOR-OUT.
000037     02 VEC-OUT PIC X OCCURS 9.
000038*********************************************************************
000039 PROCEDURE DIVISION.
000040 MAIN SECTION.
000041 1.  DISPLAY "ENTER HEX VALUES:".
000042     ACCEPT X-18.
000043     PERFORM HEX-TO-DEC.
000044     MOVE N-18 TO F-18.
000045     DISPLAY F-18.
000046     GOBACK.
000047 HEX-TO-DEC.
000048     MOVE X-18 TO VECTOR.
000049     MOVE LOW-VALUES TO VECTOR-OUT.
000050     MOVE 0 TO J.
000051     PERFORM HEX-TO-DEC2 THRU EX-HEX-TO-DEC
000052                          VARYING I FROM 1 BY 2 UNTIL I > 9.
000053     MOVE 0 TO N-18.
000054     MOVE 8 TO K.
000055     PERFORM HEX-TO-DEC1 VARYING I FROM J BY -1 UNTIL I < 1.
000056    HEX-TO-DEC1.
000057     MOVE VEC-OUT(I) TO VEC-N-18(K).
000058     SUBTRACT 1 FROM K.
000059    HEX-TO-DEC2.
000060     MOVE 0 TO X-9.
000061     MOVE VEC(I) TO X.
000062     IF X NUMERIC SUBTRACT 31 FROM X-9 GIVING K
000063      ELSE IF X NOT < "A" AND NOT > "F"
000064                     SUBTRACT 38 FROM X-9 GIVING K
000065                ELSE MOVE 77 TO I
000066                     GO TO EX-HEX-TO-DEC.
000067     MOVE VEC-HEX(K) TO N.
000068     ADD 1 I GIVING K.
000069     MOVE 0 TO X-9.
000070     MOVE VEC(K) TO X.
000071     IF X NUMERIC SUBTRACT 47 FROM X-9 GIVING K
000072      ELSE IF X NOT < "A" AND NOT > "F"
000073                     SUBTRACT 54 FROM X-9 GIVING K
000074                ELSE MOVE "0" TO VEC-X-18(K)
000075                     MOVE 1 TO K.
000076     ADD VEC-HEX(K) TO N.
000077     ADD 1 TO J.
000078     MOVE N-X TO VEC-OUT(J).
000079 EX-HEX-TO-DEC.
 
You can use the inspect verb to solve:
INSPECT PORT REPLACING LEADING SPACES BY "0".
MOVE PORT TO WS-PORT-NUM.

;where WS-PORT-NUM will be defined as PIC 9(05).
 
Delta, you assuming that the data is justified right, What if spaces ,if exist, is in the right side,And what if there is more then 4 characters?.

I don't sure that input file with 'X' format like 'F4C3" will be converted to its binary value.
 
As the TS has not bothered to provide any feedback in almost a month, further investment n the topic is probably wasted. . .

delta403,
Your "solution" will not work for all cases and we don't have a proper definition of the "requirement".
 
People say "hex" quite often without much of a clue.

For all we know this might be a 32-bit signed or unsigned binary integer.
 
Hex is an abbreviation to the word HexaDecimal. Pertaining to a numbering system which uses 16 as the base (as opposed to 10. BTW, the word in English HEX is to perform magic...




 
Pertaining to a numbering system which uses 16 as the base
For this dialog i suspect there is no need to consider base 16 numbers.

On the mainframe every byte will contain a value between x'00' and x'FF' - usually with no concern for "numbering". If the "field" is not defined as some kind of binary number, the values are not base 16 - they are simply 1s and 0s.

If a binary is presented as a pic x(4) field, redefine the x(4) as a pic 9(9) comp for the unsigned value or s9(9) for a signed value. You need to know which as the values depend on whether the value is sined or not.



 
Then simply move the redefined parm value to the "numeric" field.

Meant to have this in the prior reply, but cojuld not "edit" the post. . .
 
Status
Not open for further replies.

Part and Inventory Search

Sponsor

Back
Top