boba poorna
boba poorna

Reputation: 251

convert alphanumeric PIC X(02) to hex value 9(01) COMP-3 in cobol

I have Alphanumeric value = '86' and its length is defined as PIC x(02). I need to convert it into hex x'86' and its length is defined as PIC 9(01) comp-3.

example:

01 WS-ALPHANUMERIC PIC X(02) VALUE '86'.   
01 WS-HEX          PIC 9(01) COMP-3.

PROCEDURE DIVISION.

MOVE WS-ALPHANUMERIC   TO WS-HEX.

DISPLAY WS-HEX.

STOP RUN

I am getting x'FF' in my spool. But I am expecting x'86'.

Upvotes: 0

Views: 1504

Answers (2)

Q.Reindeerson
Q.Reindeerson

Reputation: 158

  1. Why your code doesn't produce the output you're expecting

It is just guessing from my part for on my computer it doesn't work that way.

When you MOVE from WS-ALPHANUMERIC to WS-HEX, the string '86' in transformed in the decimal number 86.

However WS-HEX is only one byte long and in the COMP-3 format. This format can only store one decimal digit and the sign. I'm guessing that on your environment when you move a bigger number than the capacity to a COMP-3 it take the biggest hexadecimal value it can hold : 0xF. In my environment it would just take the digit 6 of the number 86.

So when you display, it is converted to a usage display so you have your firt 0xF for the usage formatting and then your 0xF for the "overflow" I guess.

On my computer you would just get a 0xF6.

  1. A solution to produce the expected output

Disclaimer : I originally thought that your input would only be decimals, like '87596', '12' or '88'. This solution does not work for hexadecimals input like 'F1' ou '99F'. I built more complete solutions below in items 3 and 4 by improving this one

The solution I propose can take up to 16 digits in the input string if your system is 64bit because it takes 4 bits to store a hexadecimal digit.

Therefore if you want a larger input you'll have to use more than one result variable.

If you want to have it in only one byte, you just have to make Result a PIC 9(1) instead of PIC 9(18)

IDENTIFICATION DIVISION.
PROGRAM-ID. CNVRSN.

ENVIRONMENT DIVISION.

DATA DIVISION.
WORKING-STORAGE SECTION.

      01  RawInput PIC X(02) VALUE '86'.

      01  FormattedInput PIC 9(16).
      01  FractionedInput REDEFINES FormattedInput
         05 Digit PIC 9 OCCURS 16.          
      01  Shifting PIC 9(18) COMP-5 VALUE 1. 
      01  I PIC 99 COMP-5.

      01  Result PIC 9(18) COMP-5 VALUE 0.
      01  DisplayResult REDEFINES Result PIC X(8).
     


PROCEDURE DIVISION.

       MOVE RawInput TO FormattedInput.
  
       PERFORM VARYING I FROM LENGTH OF FractionedInput
                    BY -1 UNTIL I < 1
  
        COMPUTE Result = Result + Digit(I)*Shifting
        MULTIPLY 16 BY Shifting
  
       END-PERFORM
  
       DISPLAY 'DisplayResult : ' DisplayResult
       .
END PROGRAM CNVRSN.

The code works by transforming the string in a number of USAGE DISPLAY with the first move MOVE RawInput to FormattedInput.

We use the fact that each digit has the same format as a number of just one digit (PIC 9). This allows us to split the number in elements of an array with the REDEFINES of FomattedInput inFractionedInput

As you can see I traverse the array from the end to start because the least significant byte is at the end of the array (highest address in memory), not at the start (lowest address in memory).

Then we place each the hexadecimal digit in the correct place by shifting them to the left by 2^4 (a nibble, which is the size of a hexadecimal digit) as many times as required.

  1. A solution that accepts the full hexadecimal input range (memory intensive)

Here is the code :

IDENTIFICATION DIVISION.
PROGRAM-ID. CNVRSN.

ENVIRONMENT DIVISION.

DATA DIVISION.
WORKING-STORAGE SECTION.

  01  RawInput PIC X(02) VALUE '86'.

  01  FormattedInput PIC X(16).
  01  FractionedInput REDEFINES FormattedInput
     05 Digit PIC X OCCURS 16.          
  01  I PIC 99 COMP-5.
  
  01  ConversionTableInitializer. 
    05 FILLER PIC X(192).
    05 TenToFifteen PIC X(06) VALUE X'0A0B0C0D0E0F'.
    05 FILLER PIC X(41).
    05 ZeroToNine PIC X(10) VALUE X'00010203040506070809'.

  01  ConversionTable Redefines ConversionTableInitializer. 
    05 DigitConverter PIC 99 COMP-5 OCCURS 249.

  01  Result PIC 9(18) COMP-5 VALUE 0.
  01  DisplayResult REDEFINES Result PIC X(8).
 

PROCEDURE DIVISION.
   MOVE RawInput TO FormattedInput.

   PERFORM VARYING I FROM 1 BY 1 
                     UNTIL I > LENGTH OF FractionedInput
                        OR Digit(I) = SPACE


    COMPUTE Result = Result*16 + DigitConverter(Digit(I))

   END-PERFORM

   DISPLAY 'DisplayResult : ' DisplayResult
   .
END PROGRAM CNVRSN.

The idea in this solution is to convert each character (0,1...,E,F) to its value in hexadecimal. For this we use the value of their encoding as a string (0xC1 = 0d193 for A for instance) as the index of an array.

This is very wasteful of memory for we allocate 249 bytes to store only 16 nibbles of information. However to access the element of an array is a very fast operation: We are trading the memory usage for cpu efficiency. The underlying idea in this solution is a hashtable. This solution is nothing but a very primitive hash table where the hash function is the identity function (A very, very bad hash function).

  1. Another solution that accepts the full hexadecimal input range (CPU intensive)

Disclaimer : This solution was proposed by @Jim Castro in the comments.

IDENTIFICATION DIVISION. 
PROGRAM-ID. CNVRSN.

ENVIRONMENT DIVISION.

DATA DIVISION.
WORKING-STORAGE SECTION.

  01  RawInput PIC X(02) VALUE '86'.

  01  FormattedInput PIC X(16).
  01  FractionedInput REDEFINES FormattedInput
     05 Digit PIC 9 OCCURS 16.          
  01  ConversionString PIC X(16) VALUE '0123456789ABCDEF'.
  01  ConversionTable REDEFINES ConversionString.
     05 ConversionEntry OCCURS 16 INDEXED BY Idx.                          
       10 HexDigit PIC X.   

  01  I PIC 99 COMP-5.
  


  01  Result PIC 9(18) COMP-5 VALUE 0.
  01  DisplayResult REDEFINES Result PIC X(8).
 


PROCEDURE DIVISION.

   MOVE RawInput TO FormattedInput.

   PERFORM VARYING I FROM 1 BY 1 
                     UNTIL I > LENGTH OF FractionedInput
                        OR Digit(I) = SPACE


    SET Idx To 1
    SEARCH ConversionEntry
      WHEN HexDigit(Idx) = Digit(I)
         COMPUTE Result = Result*16 + Idx - 1            
    END-SEARCH
    

   END-PERFORM

   DISPLAY 'DisplayResult : ' DisplayResult
   .
 END PROGRAM CNVRSN.

Here the idea is still to convert the string digit to its value. However instead of trading off memory efficiency for cpu efficiency we are doing the converse.

We have a ConversionTable where each character string is located at the index that convey the value they are supposed to convey + 1 (because in COBOL arrays are 0 based). We juste have to find the matching character and then the index of the matching character is equal to the value in hexadecimal.

  1. Conclusion

There are several ways to do what you want. The fundamental idea is to :

  1. Implement a way to convert a character to its hexadecimal value
  2. Traverse all the characters of the input string and use their position to give them the correct weight.

Your solution will always be a trade off between memory efficiency and time efficiency. Sometimes you want to preserve your memory, sometimes you want the execution to be real fast. Sometimes you wand to find a middle ground.

To go in this direction we could improve the solution of the item 3 in terms of memory at the expense of the cpu. This would be a compromise between item 3 and 4. To do it we could use a modulo operation to restrict the number of possibilities to store. Going this way would mean implementing a real hashtable.

Upvotes: 2

Gilbert Le Blanc
Gilbert Le Blanc

Reputation: 51515

I don't have access to an IBM mainframe to test this code.

When I run the code on an online GnuCOBOL v2.2 compiler, I'm stuck with ASCII instead of EBCDIC.

I've posted the code. Here's what you have to do.

  • Make sure the top byte comes out to 8 and the bottom byte comes out to 6. You're converting the EBCDIC values to intager values. Values A - F hex will have different EBCDIC values than values 0 - 9.
  • Make sure the multiply and add are correct

Here's the code. You'll have to fix it to work with EBCDIC.

IDENTIFICATION DIVISION.
PROGRAM-ID. CONVERSION.

DATA DIVISION.
WORKING-STORAGE SECTION.
01 WS-ALPHANUMERIC              PIC X(02) VALUE '86'.

01 WS-WORK-FIELDS.
   05 WS-INPUT.
      10 WS-ONE. 
         15 WS-TOP-BYTE         PIC 99 COMP.
      10 WS-TWO.
         15 WS-BOTTOM-BYTE      PIC 99 COMP.
   05 WS-ACCUMULATOR            PIC S9(4) COMP.
   05 FILLER                    REDEFINES WS-ACCUMULATOR.
      10 FILLER                 PIC X.
      10 WS-HEX                 PIC X.

PROCEDURE DIVISION.
0000-BEGIN.
    MOVE WS-ALPHANUMERIC TO WS-INPUT
    DISPLAY WS-INPUT

    COMPUTE WS-TOP-BYTE = WS-TOP-BYTE - 183
    COMPUTE WS-BOTTOM-BYTE = WS-BOTTOM-BYTE - 183

    IF WS-TOP-BYTE NOT LESS THAN 16
        COMPUTE WS-TOP-BYTE = WS-TOP-BYTE - 57
    END-IF   

    IF WS-BOTTOM-BYTE NOT LESS THAN 16
        COMPUTE WS-BOTTOM-BYTE = WS-BOTTOM-BYTE - 57
    END-IF  
    
    DISPLAY WS-TOP-BYTE
    DISPLAY WS-BOTTOM-BYTE

    MOVE WS-TOP-BYTE TO WS-ACCUMULATOR
    MULTIPLY 16 BY WS-ACUMULATOR
    ADD WS-BOTTOM-BYTE TO WS-ACCUMULATOR

    DISPLAY WS-ACCUMULATOR
    DISPLAY WS-HEX

    GOBACK.

Upvotes: 0

Related Questions