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 strongm on being selected by the Tek-Tips community for having the most helpful posts in the forums last week. Way to Go!

pic x(2) to hex

Status
Not open for further replies.

melimae

ISP
Jul 29, 2005
16
US
I have a text file as input to a cobol program with a 2 character field that is suppose to be hexadecimal, the file will have 00 in the field when it should actually be x'00'. How can I pull this filed into my program in a pic x(2) field and then have it represent a hex x'00'?
 
Here's something that appears to work. This manipulates the zone and numeric porions of the final hex byte in question.


01 INPUT-DATA.
03 ID-CHAR-1 PIC X(01).
03 ID-CHAR-2 PIC X(01).
01 BINARY-FIELD BINARY PIC S9(04).
01 FILLER REDEFINES BINARY-FIELD.
03 FILLER PIC X(01).
03 HEX-CHAR PIC X(01).


ACCEPT INPUT-DATA.
MOVE +0 TO BINARY-FIELD.
EVALUATE ID-CHAR-1
WHEN '0'
CONTINUE
WHEN '1'
ADD 16 TO BINARY-FIELD
WHEN '2'
ADD 32 TO BINARY-FIELD
WHEN '3'
ADD 48 TO BINARY-FIELD
.
.
.
WHEN 'E'
ADD 224 TO BINARY-FIELD
WHEN 'F'
ADD 240 TO BINARY-FIELD
END-EVALUATE.
EVALUATE ID-CHAR-2
WHEN '0'
CONTINUE
WHEN '1'
ADD 1 TO BINARY-FIELD
WHEN '2'
ADD 2 TO BINARY-FIELD
.
.
.
WHEN 'E'
ADD 14 TO BINARY-FIELD
WHEN 'F'
ADD 15 TO BINARY-FIELD
END-EVALUATE.
DISPLAY '>' HEX-CHAR '<'.

We're working with a 2-bytes binary field. Before the Evaluates, it will look like '0000 0000 0000 0000'. The 2 Evaluates are dealing with just the rightmost byte so we are working with '0000 0000'. The first Evaluate works with the leftmost half (zone) of the byte. The 2nd Evaluate works with the rightmost half (numeric) of the byte.

 
Melimae,
As you can see, the debate still rages! Could you let me know if the input field is able to contain any 2 byte hex (style) value such as FF, AB A0, etc.

The reason I ask is that you have only mentioned 00 01 02 in your examples.

Many thanks

Marc
 
The field can contain any hex value such as FA, CB, DA, 01, 0A, E1......
 
Then just use a table to cross-reference the values.

Code:
       01  TABLE-AREA.
           05  TABLE-ROWS.
               10  FILLER         PIC X(2) VALUE '00'.
               10  FILLER         PIC X(1) VALUE X'00'.
               10  FILLER         PIC X(2) VALUE '01'.
               10  FILLER         PIC X(1) VALUE X'01'.
               10  FILLER         PIC X(2) VALUE '03'.
               10  FILLER         PIC X(1) VALUE X'03'.
               ... etc.
               10  FILLER         PIC X(2) VALUE 'FF'.
               10  FILLER         PIC X(1) VALUE X'FF'.
           05  TABLE-ROW REDEFINES TABLE-ROWS OCCURS 256 TIMES.
               10  DISPLAY-VAL    PIC X(2).
               10  HEX-VAL        PIC X(1).

Clive
 
Melimae,
As you can probably tell from the discussion, there is more than one way to approach this problem, and I suspect it will be down to personal preference as to which one you choose.

My belief is that CliveC's solution, when combined with a search on the table for the first value, would be the most elegant and easy to understand. Remember that the program will need to be supported long after it is written, so clear understandable code is essential for long term maintenance. CliveC's code is precisely that, in my humble opinion.

Regards,

Marc
 
MarcLodge said:
there is more than one way to approach this problem
Well, I'll roll in my solution, just to show Marc is correct.
Code:
        01  input-field pic x(2).
        01  high-order-digit pic 99.
        01  low-order-digit  pic 99.
        01  final-result pic 9999 binary.
        01  redefines final-result.
            02  pic x.
            02  converted-value pic x.
[COLOR=red yellow]       * assumes binary is stored big-endian[/color]
...
        move 0 to high-order-digit, low-order-digit.
        inspect "0123456789ABCDEF"
            tallying high-order-digit 
            for characters before initial input-field (1:1).
        inspect "0123456789ABCDEF"
            tallying low-order-digit 
            for characters before initial input-field (2:1).
        if  high-order-digit < 16
        and low-order-digit  < 16
            compute final-result =
                    high-order-digit * 16 + low-order-digit
        else
            display input-field, " is not valid hex"
        end-if

Tom Morrison
 
Tom,
A perfect example!! Brilliant code that deserves instant dismissal.

Big-endian? Isn't that a 'said the actress to the bishop' joke?

Marc
 
Hi Melimae,

Now I think I see what you want. Here's a minor variation on the theme:
Code:
WS
05  wrk-fld.
    10  hld-fld  pic x(2).
    10  fil      pic x.
05  num-fld      redefines
    wrk-fld      pic 9(3).

05  packed-fld   pic 9(3) comp-3.
05  hex-fld      redefines
    packed-fld   pic x(1).

PD

move your-fld    to hld-fld
inspect hld-fld  converting
        'ABCDEF' to X'FAFBFCFDFEFF'  
move wrk-fld     to packed-fld 
display '>' hex-fld '<'
I've used the converse of this technique to print hex data.

Regards, Jack.

"A problem well stated is a problem half solved" -- Charles F. Kettering
 
You know there may be some other way to convert this really fast in an Assembly Program or utility.

If you do not like my post feel free to point out your opinion or my errors.
 
I use IBM COBOL of some kind with the intrisic function of CHAR I can convert an integer to a character in the coalating sequence. The rest is simple base 16 math.
You could do this real fast in some versions of C++ which can convert text to a number in any base x number system.
You might want to make sure the accept card or input is not
blank and the result is less than the last number in the coalating sequence.


Someone will always mess up and use "a" instead of "A" for input.

I was just tinkering with this. Handling each character as a base 16 number may be a simpler and less complex approach.

ACCEPT JOB-CARD-1.
MOVE JOB-CARD-1 (1:1) TO WS-TEMP-1.
PERFORM 100-HEX-ORD.
MOVE WS-NBR TO WS-NBR-1.
MOVE JOB-CARD-1 (2:1) TO WS-TEMP-1.
PERFORM 100-HEX-ORD.
COMPUTE WS-NBR-1 = ( ( WS-NBR-1 * 16 ) + WS-NBR )
MOVE FUNCTION CHAR(WS-NBR-1) TO HEX-CHAR

(char(int) is an ibm intrinsic function and I do not know if that is COBOL Standard). When you use a literal in an expression like move X'124' you are using the coalating sequence to assign it to a symbol not in the normal alphabet. I wonder if you can say move x'<variable>' but I dont think you can do that. That is why IBM has CHAR() and ORD().

100-HEX-ORD.
If WS-TEMP-IN = '1'
WS-NBR = 1
ELSE IF WS-TEMP-IN = '2'
WS-NBR = 2
ELSE IF WS-TEMP-IN = '3'
WS-NBR = 3
ELSE IF WS-TEMP-IN = '4'
WS-NBR = 4
ELSE IF WS-TEMP-IN = '5'
WS-NBR = 5
ELSE IF WS-TEMP-IN = '6'
WS-NBR = 6
ELSE IF WS-TEMP-IN = '7'
WS-NBR = 7
ELSE IF WS-TEMP-IN = '9'
WS-NBR = 9
ELSE IF WS-TEMP-IN = '0'
WS-NBR = 0
ELSE IF WS-TEMP-IN = 'A' or 'a'
WS-NBR = 10
ELSE IF WS-TEMP-IN = 'B' or 'b'
WS-NBR = 11
ELSE IF WS-TEMP-IN = 'C' or 'c'
WS-NBR = 12
ELSE IF WS-TEMP-IN = 'D' or 'd'
WS-NBR = 13
ELSE IF WS-TEMP-IN = 'E' or 'e'
WS-NBR = 14
ELSE IF WS-TEMP-IN = 'F' or 'f'
WS-NBR = 15.

We have probably beat this to death already, but I was board.



If you do not like my post feel free to point out your opinion or my errors.
 
The IBM COBOL for OS/390 and VM (and later IBM MVS and OS/390) compiler all support the ANSI/ISO 1989 Intrinsic Functions module. They do not, however, support one byte binary fields (which I don't think is really necessary for this).

Consider using the folloiwng (compatible across platforms and compilers - regardless of ASCII or EBCDIC - as long as they include '89 Standard intrinsic functions).

Code:
01  Input-2-digits   Pic 99.
01  Output-One-byte  Pic X.
    ...
Move Function CHAR (Input-2-digits + 1) 
      to Output-One-Byte

NOTE:
The reason for the "+ 1" is that the ANSI/ISO standard use "ordinal" numbers for the CHAR and ORD intribnsic functions, so
CHAR(1) = X"00"
and
ORD(X"00") = 1

This is COUNTER-INTUITIVE to many programers, but is the way things work (in the standard)

Again, this approach will work regardless of ASCII/EBCDIC (or any other) codeset and should be portable across most (not all) currently sold compilers.

Bill Klein
 
OOPS,
Please realize that my last reply was WRONG, given the input description that you give us. You said that the input would be in "hex" (2 characters), e.g
00 = X'00'
BUT
AB = (some charcter)

would also be valid. Therefore, to use the approach I suggested, you need to

A) allow for a 3 digit (not 2 digit) input (up to 255 or 256)

B) need to convert the "hex" value decimal (numeric).

You will need to convert based on the fact that "A-F" are valid in the first or second position and "multiply" by powers of 16 to get the correct numeric value. Then, once you do have a base-10 value, you can use the code I presented above.

Bill Klein
 
Because I didn't handle the first response correctly, I thought that I would also post a (complete program, you would only need snippets) for converting HEX (in display format) to decimal values.

Code:
       Identification Division.
        Program-ID. HEX2DEC.
       Data Division.
        Working-Storage Section.
       01  Input-Hex.
           05 IH-Byte-1   	Pic X(01).
           05 IH-Byte-2		Pic X(01).
       01  Output-Dec  Pic 9(03).
       01  Temp-Stuff.
           05  Ones-Place  	Pic S9(02)	Value Zero.
           05  Sixteens-Place 	Pic S9(03)	Value Zero.
           05  			Pic X(01)	Value "N".
               88  Error-Occured 		Value "Y". 
       Procedure Division.
        Mainline.
           Display "Enter Hex Value:" with no advancing
           Accept Input-Hex from Console
           Evaluate True 
             When IH-Byte-2 Numeric
               Move IH-Byte-2 to Ones-Place
             When Function Upper-Case (IH-Byte-2) = "A"
               Move 10 to Ones-Place
             When Function Upper-Case (IH-Byte-2) = "B"
               Move 11 to Ones-Place
             When Function Upper-Case (IH-Byte-2) = "C"
               Move 12 to Ones-Place
             When Function Upper-Case (IH-Byte-2) = "D"
               Move 13 to Ones-Place
             When Function Upper-Case (IH-Byte-2) = "E"
               Move 14 to Ones-Place
             When Function Upper-Case (IH-Byte-2) = "F"
               Move 15 to Ones-Place
             When Other
               Display "Invalid Second byte:" IH-Byte-2
               Set Error-Occured to true
           End-Evaluate
      *     
           Evaluate True 
             When IH-Byte-1 Numeric
               Compute Sixteens-Place = Function NumVal (IH-Byte-1) * 16
             When Function Upper-Case (IH-Byte-1) = "A"
                Compute Sixteens-Place = 10 * 16
             When Function Upper-Case (IH-Byte-1) = "B"
                Compute Sixteens-Place = 11 * 16
             When Function Upper-Case (IH-Byte-1) = "C"
                Compute Sixteens-Place = 12 * 16
             When Function Upper-Case (IH-Byte-1) = "D"
                Compute Sixteens-Place = 13 * 16
             When Function Upper-Case (IH-Byte-1) = "E"
                Compute Sixteens-Place = 14 * 16
             When Function Upper-Case (IH-Byte-1) = "F"
                Compute Sixteens-Place = 15 * 16
             When Other
               Display "Invalid First byte:" IH-Byte-1
               Set Error-Occured to true
           End-Evaluate
      *               
           Compute Output-Dec = Sixteens-Place + Ones-Place        
           If not Error-Occured
               Display "For Hex Value:" Input-Hex
               Display "  the Decimal value is:" Output-Dec
           End-If    
           Stop Run.

Needless to say, there are a NUMBER of other ways that this could be done.

Bill Klein
 
Status
Not open for further replies.

Part and Inventory Search

Sponsor

Back
Top