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

Converting a packed field 2

Status
Not open for further replies.

Psepha

Programmer
Nov 15, 2001
5
US
Hi All - new to this group, cannot find the answer to this question in previous threadss so apologies if it has been asked before.
I am trying to convert a packed field that can contain alpha numerics to a displayable format.
For example a PIC X field containing the value x'C4'. I want to convert this into an PIC XX - 'C4' so it can be displayed. I cannot find any shift operators in COBOL (eg the << and >> equivalents in C) so am a bit(?) stuck. Would prefer not to revert to an assembler routine to do this. Using COBOL 370 on IBM Mainframe.
Any help very much appreciated

Regards
Mike
 
Hi,

If you have a packed field of one byte, you define that like

01 packed-field pic s9(1) packed-decimal.

If you want to convert it, you define:

01 converted-field pic -9.

conversion is:

move packed-field to converted-field.

to show:

display &quot;converted-field = &quot; converted-field.

You can do this with sizes until

S9(18)

which are 18 ciphers; 10 bytes packed; 18 bytes zoned numeric.

Regards,

Crox

 
Hi Crox,
Thanks for you help in this but I'm not sure I may have explained myself. I have tried the suggested code but a move from a PIC S9(1) to a PIC -9 results in a S0C7 abend unless the field is a numeric representation - code snippet so someone can see if I am missing the point

FILE SECTION.
FD INPUT-FILE.
01 INPUT-RECORD.
03 INPUT-VALUE PIC S9(1) PACKED-DECIMAL.
.
.
01 WS-PIC99 PIC -9.
.
OPEN INPUT INPUT-FILE.
READ INPUT-FILE.
MOVE INPUT-VALUE TO WS-PIC99.
CLOSE INPUT-FILE.
DISPLAY WS-PIC99.

....The MOVE statement causes an S0C7
the data I am using is

D
------
C44444
400000

- hex print representation. The packed field is not decimal, it is just a packed binary field. Have tried to look at every working storage field type I can think of but have not managed to figure out if it is possible to split a single byte into two characters - the 'C' and the '4'. Probably shouldn't use the 'C' in case this is confused with a sign in the example - how about splitting x'Q4' (one byte) into 'Q4' displayable two bytes. I starting to think this is not possible?

Thanks again

Mike


 
The field INPUT-VALUE may be defined as PACKED-DECIMAL (i.e. COMP-3) but the content is definitely not a packed-decimal value. Since your move statement will result in placing a non-packed-decimal (i.e. non-numeric) value into WS-PIC99 the SOC7 is the proper result. You could move the INPUT-VALUE to a COMP field but this would then display 196 (i.e x'C4' = 196). Since your intent is to display the field in binary or hex and you want to do it in COBOL this requires a little more work.

Take a look at the following, it may be helpful...


Good Luck,

Saginaw
helpdesk@simotime.com
 
Before the move you can test if it is numeric.

If you want to convert from any character to hex, you can use a conversion program. Hereafter you see an example of a conversion routine which I use on the PC. Also you can convert using some IBM utilities: IEBPTPCH with TOTCONV=HEX or things like that.

Regards,

Crox

Code:
000010*$CALL
000100 IDENTIFICATION DIVISION.
000200 PROGRAM-ID. BIN2HEX.
000300 ENVIRONMENT DIVISION.
000400 CONFIGURATION SECTION.
000500 SOURCE-COMPUTER. IBM-PC.
000600 OBJECT-COMPUTER. IBM-PC.
000700 SPECIAL-NAMES.
000800     DECIMAL-POINT IS COMMA.
000900 INPUT-OUTPUT SECTION.
001000 FILE-CONTROL.
001100 DATA DIVISION.
001200 FILE SECTION.
001300 WORKING-STORAGE SECTION.
001400 01  HULPVELDEN.
001500     03  SUB-STRING                  PIC S9(4) COMP-5.
001600     03  TABEL-HEX.
001700         05  FILLER                  PIC X(32) VALUE
001800     '000102030405060708090A0B0C0D0E0F'.
001900         05  FILLER                  PIC X(32) VALUE
002000     '101112131415161718191A1B1C1D1E1F'.
002100         05  FILLER                  PIC X(32) VALUE
002200     '202122232425262728292A2B2C2D2E2F'.
002300         05  FILLER                  PIC X(32) VALUE
002400     '303132333435363738393A3B3C3D3E3F'.
002500         05  FILLER                  PIC X(32) VALUE
002600     '404142434445464748494A4B4C4D4E4F'.
002700         05  FILLER                  PIC X(32) VALUE
002800     '505152535455565758595A5B5C5D5E5F'.
002900         05  FILLER                  PIC X(32) VALUE
003000     '606162636465666768696A6B6C6D6E6F'.
003100         05  FILLER                  PIC X(32) VALUE
003200     '707172737475767778797A7B7C7D7E7F'.
003300         05  FILLER                  PIC X(32) VALUE
003400     '808182838485868788898A8B8C8D8E8F'.
003500         05  FILLER                  PIC X(32) VALUE
003600     '909192939495969798999A9B9C9D9E9F'.
003700         05  FILLER                  PIC X(32) VALUE
003800     'A0A1A2A3A4A5A6A7A8A9AAABACADAEAF'.
003900         05  FILLER                  PIC X(32) VALUE
004000     'B0B1B2B3B4B5B6B7B8B9BABBBCBDBEBF'.
004100         05  FILLER                  PIC X(32) VALUE
004200     'C0C1C2C3C4C5C6C7C8C9CACBCCCDCECF'.
004300         05  FILLER                  PIC X(32) VALUE
004400     'D0D1D2D3D4D5D6D7D8D9DADBDCDDDEDF'.
004500         05  FILLER                  PIC X(32) VALUE
004600     'E0E1E2E3E4E5E6E7E8E9EAEBECEDEEEF'.
004700         05  FILLER                  PIC X(32) VALUE
004800     'F0F1F2F3F4F5F6F7F8F9FAFBFCFDFEFF'.
004900     03  FILLER REDEFINES TABEL-HEX.
005000         05  FILLER                  PIC XX.
005100         05  HEX-OMSCHRIJVING OCCURS 255
005200                                     PIC XX.
005300
005400     03  TEMP.
005500         05  FILLER                  PIC X VALUE LOW-VALUE.
005600         05  TESTWAARDE              PIC X.
005700     03  SUB REDEFINES TEMP          PIC S9(4) COMP.
005800
005900 LINKAGE SECTION.
006000 01  LNK-LENGTE-STRING               PIC S9(4) COMP-5.
006100
006200 01  LNK-TE-CONVERTEREN-STRING.
006300     03  LNK-NORMAAL-TEKEN  OCCURS 1 TO 16000
006400         DEPENDING ON LNK-LENGTE-STRING
006500                                     PIC X.
006600
006700 01  LNK-HEX-STRING.
006800     03  LNK-HEX-TEKEN      OCCURS 1 TO 32000
006900         DEPENDING ON LNK-LENGTE-STRING
007000                                     PIC XX.
007100
007200 PROCEDURE DIVISION.
007300 HOOFD SECTION.
007400     ENTRY 'USR_BIN2HEX' USING LNK-LENGTE-STRING
007500                               LNK-TE-CONVERTEREN-STRING
007600                               LNK-HEX-STRING.
007700 HOO-01.
007800     PERFORM VARYING SUB-STRING FROM +1 BY +1 UNTIL
007900                     SUB-STRING > LNK-LENGTE-STRING
008000          MOVE LNK-NORMAAL-TEKEN (SUB-STRING) TO TESTWAARDE
008100          MOVE HEX-OMSCHRIJVING  (SUB) TO
008200               LNK-HEX-TEKEN     (SUB-STRING)
008300     END-PERFORM.
008400 HOO-99.
008500     GOBACK.


 
Here's a trickier, but much shorter piece of code.

WORKING-STORAGE:

01 TRANSLATE-DATA PIC 9(4) BINARY VALUE ZEROS.
01 REDEFINES TRANSLATE-DATA.
05 PIC X.
05 TRANSLATE-BYTE PIC X.

01 FIRST-NIBBLE PIC 99.
01 SECOND-NIBBLE PIC 99.

01 HEX-TABLE PIC X(16) VALUE '0123456789ABCDEF'.
01 REDEFINES HEX-TABLE.
05 HEX-CHAR OCCURS 16 TIMES
PIC X.

PROCEDURE DIVISION:

MOVE char-to-translate TO TRANSLATE-BYTE.
DIVIDE 16 INTO TRANSLATE-DATA GIVING FIRST-NIBBLE
REMAINDER SECOND-NIBBLE.
STRING HEX-CHAR (FIRST-NIBBLE + 1)
HEX-CHAR (SECOND-NIBBLE + 1) DELIMITED BY SIZE
INTO hex-translation.

Substitute your own variable names for char-to-translate and hex-translation.

This will work provided that your system does binary numbers left to right. If it does them right to left, swap the first TRANSLATE-BYTE line with the one before it.

I can provide an explanation of why this will work if anyone is interested.

Hope this helps,

Betty Scherber
Brainbench MVP for COBOL II
 
Hi Betty,

A shorter source but much more cpu-time. On the mainframe we still pay something like US$ 0.50 per second.

Binary numbers should be stored from left to right. The native format COMP-5 in pc/dos/wintel environments is the other way around. Sometimes even a compiler directive influences this.

It is strange that there is still no FUNCTION for this work. In your source you can perhaps use MOD.

Regards,

Crox
 
There is probably an assembly bit of code to rearrange the last byte after unpacking or a one command Macro to do it in assembly. In assembly class we use to do this before displaying a packed number, but I don't remember the steps. If you do not like my post feel free to point out your opinion or my errors.
 
Hi Mike,

Here's my recipe:

Code:
05  WS-WORK-PACKED              PIC S9(002)  COMP-3.
05  REDEFINES WS-WORK-PACKED.
    10  YOUR-BYTE               PIC  X(001).

05  WS-WORK-UNPACKED            PIC  9(003).
05  REDEFINES WS-WORK-UNPACKED.
    10  WS-WORK-UNPACKED-1      PIC  9(002).

100-CONVERT-HEX-DATA.
*-----------------------------------------------------------
*===> CONVERTS HEX DATA FOR DISPLAY PURPOSES
* E.G. X&quot;04FB&quot; ====> X&quot;F0F4C6C2&quot; OR 04FB CHARACTER
*-----------------------------------------------------------
MOVE WS-WORK-PACKED TO WS-WORK-UNPACKED
INSPECT WS-WORK-UNPACKED CONVERTING
X&quot;FAFBFCFDFEFF&quot; TO &quot;ABCDEF&quot;


Before you exec this code move your byte to YOUR-BYTE (make sure the byte isn't converted in the move, e.g. redefine it as pic x).

Bon appetit.

Regards, Jack.
 
All,
Many thanks for the replies - For Info went for a variation of Bettys code in the end - but all were a help as made me think (for a change) about various solution

Thanks again

Mike
 
Status
Not open for further replies.

Part and Inventory Search

Sponsor

Back
Top