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!

Unpacking comp-3, generically 1

Status
Not open for further replies.
Jul 15, 2009
6
IE
Good evening folks.

This is a real peach....
Consider this problem: an input string from a VSAM file is a packed decimal of one of the following forms:

S9...9V9...9
S9...9V9(#)
S9(#)V9...9
S9(#)V9(#)

where # is 1 to 9 and s9...9 will at most be nine 9's.

What I'm trying to do is unpack this, retaining the sign and the decimal point and then STRING'ing it to a varible before writing it to a file.

I have got this working for the 'easy' packed numbers, i.e. ones without decimal points (e.g. S9...9 and S9(#) ) What I do is firstly inspect the string, if it has no brackets I count up the number of nines and then move it to a Pic X of the correct size, also checking if it's positive or negative and using reference modification to place the + or - and then the unpacked number. If it has a bracket I unstring the value inside the brackets and do the same as before.

I'm stumped with the decimal point though.
Is there a generic way I can efficiently 'move' the packed field to a Pic X that will cover all cases (e.g. PIC X(21) to account for the sign, nine 9's, decimal point, nine 9's)

I have a feeling this could be done by a similar method to the ones I've got unpacked, such as counting up nine's either side of the V, and using some sort of reference modification to move this to the PIC X and then move the appropriate part of the PIC X to my output again by reference modification.


Any guidance on this would be hugely appreciated!

Thanks
Markus
Ireland.
 
Why not simply move the comp-3 into a -(9)9.9(9) ?

Hope This Helps, PH.
FAQ219-2884
FAQ181-2886
 
I should have mentioned that I have a separate VSAM file that contains the PIC description of the field i'm reading in. So say my current read in data is 'xxx' then I also have a variable telling me that it's pic is 'PIX x(3)'

cheers!
 
Hi PHV.

Thanks for the quick reply - I'm pretty much brand new at COBOL so very much learning as I go. Could you explain what the -(9)9.9(9) is?
 
Have a look at PICTURE in your cobol documentation.

Hope This Helps, PH.
FAQ219-2884
FAQ181-2886
 
No big deal I think.

1. Count the number of 9's in the PIC, e.g. S9(3)V9(4) has seven 9's. Store in NUMBER-OF-NINES.

2. As part of the counting above, retain the number of nines following the decimal point. Store in NUMBER-OF-DECIMALS.

3. Do something like this to get the field moved to your final result (assuming field starts at byte 1 of WS-INPUT-RECORD; if not adjust the ref mod in the MOVE to start elsewhere):

Code:
01  WS-INPUT-RECORD             PIC X(80).
01  WS-WORK-FIELD.
    05  WS-WORK-FIELD           PIC S9(18) COMP-3.
    05  WS-WORK-FIELD-1         REDEFINES WS-WORK-FIELD
                                PIC S9(17)V9(01) COMP-3.
    05  WS-WORK-FIELD-2         REDEFINES WS-WORK-FIELD
                                PIC S9(16)V9(02) COMP-3.

01  WS-OFFSET                   PIC S9(4) COMP.
01  WS-LENGTH                   PIC S9(4) COMP.

MOVE LOW-VALUES              TO WS-WORK-FIELD
COMPUTE WS-LENGTH ROUNDED    = (NUMBER-OF-NINES + 1) / 2
COMPUTE WS-OFFSET            = LENGTH OF WS-WORK-FIELD -
                               WS-LENGTH + 1
MOVE WS-INPUT-RECORD(1:WS-LENGTH) TO
     WS-WORK-FIELD(WS-OFFSET:)

EVALUATE NUMBER-OF-DECIMALS
    WHEN 0
        MOVE WS-WORK-FIELD    TO WS-RESULT
    WHEN 1
        MOVE WS-WORK-FIELD-1  TO WS-RESULT
etc.

It's not terribly pretty, but it should be fast and accurate.

Regards,

Glenn
 
This precise problem was discussed at great length in an earlier thread.
 
After taking these posts into consideration I think my main problem is that the input packed decimal is in a character string.

I need to move this to an S9 of the appropriate size, which can vary from record to record, so that it becomes 'unpacked', and then move the unpacked S9 to my data-output variable.

It looks like 81 IF statements will have to be used, along with 162 working storage variables to account for all possible inputs?
 
Hi Markus,

It sounds like you have a VSAM file that contains records that have comp-3 fields w/PICs that vary from S9V9 to
S9(09)V9(09).

Why don't you show us some recs in the file and the file record description. It might give us a better insight into the problem you're facing.



Regards, Jack.

"A problem well stated is a problem half solved" -- Charles F. Kettering
 
You can use referance modification to move the packed decimal field into the right-most bytes of a zero-initialied packed decimal working-storage field PIC S9(18).
Then unpack that field into a PIC 9(18)- display field. Next, use reference modification to extract the specified digits and place the decimal point. Only two fields required other than the source and target, and no IF statements.
 
I'm not sure I fully understand what you're wanting to do, but if it's what I think it is, I should say the V in the definition is only an implied decimal point.

So S9v99 is the same as S999 when it comes to storage. So you can do as webrabbit implies. Put the value to a PIC 9(18)- value (that's as much stored text as if it's in a PIC X value), and then assemble the final result based on the datatype you get in input.

Measurement is not management.
 
Hi Guys,
Sorry for the slow reply.

the first VSAM contains the records like so:
KEY DATA
CLAUAP1H, N0002640000000000000...
CLAUAP2H, N0002640000000000000...
etc...

the second VSAM contains
key start pos length data type in this position
CLBC0009, 0046 0003 S999V99
CLBC0010, 0049 0002 S999
CLBC0004, 0012 0005 X(5)
CLBC0005, 0017 0003 XXX
etc.

So I read through the first VSAM like this
CONTROL-REC(W-START-POS:W-REC-LEN)
incrementing the start position by the length each time.

I then inspect the 'type' from the second VSAM, for the simple cases I see that they just contain X's so I move them to the appropriate working storage variable and then write that variable out to a sequential file.

As I said, my problem is when the data contains a V, I have to unpack the packed decimal which is currently stored in a character string.

Thanks
Mark
 
I didn't test it very much and the output isn't too pretty but hopefully it'll give you an idea of what we've been trying to say.

Code:
 IDENTIFICATION DIVISION.
 PROGRAM-ID. UNPACK.
* PROGRAM TO DEMONSTRATE UNPACKING OF COMP-3 DATA VALUES GIVEN
* KNOWN DATA TYPE DESCRIPTION AND LENGTH OF THE DATA
 ENVIRONMENT DIVISION.
 DATA DIVISION.
 WORKING-STORAGE SECTION.
 01  INPUT-DATA-VALUES.
     04  INPUT-DATA-VALUE         PIC S9(5)V99 COMP-3 VALUE 23.
     04  INPUT-DATA-TEXT REDEFINES INPUT-DATA-VALUE PIC X(4).
     04  INPUT-DATA-AREA          PIC X(30).

* DATA BELOW ARE INPUT FROM THE DATA TYPE DESCRIPTOR DATA.
* INPUT-DECIMALS = 2, INPUT-DDSIZE = 7 WHERE PIC S9(5)V99.
* INPUT-DATA-SIZE = ACTUAL SIZE OF COMP-3 INPUT DATA
     04  INPUT-DECIMALS           PIC 99 VALUE 2.
     04  INPUT-DDSIZE             PIC 99 VALUE 7.
     04  INPUT-DATA-SIZE          PIC 9(5) VALUE 4.

 01  PROC-VARIABLES.
     04  PROC-STORE-VAR           PIC S9(18) COMP-3.
     04  PROC-STORE-TEXT REDEFINES PROC-STORE-VAR PIC X(10) JUST RIGHT.
     04  PROC-STORE-NUMVAL        PIC 9(18)+.
     04  PROC-STORE-DISPLAY REDEFINES PROC-STORE-NUMVAL PIC X(19).

     04  DATA-POSITION            PIC S9(4) BINARY.
     04  PERIOD-POSITION          PIC S9(4) BINARY.
     04  NUMBER-SPACES            PIC S9(4) BINARY.

 01  OUTPUT-DATA-VALUE            PIC X(30).

 PROCEDURE DIVISION.
 0000-START SECTION.
* PROLOGUE TO BE ABLE TO SIMULATE WHAT WAS DESCRIBED IN THE QUESTION
     MOVE INPUT-DATA-TEXT TO INPUT-DATA-AREA.
     PERFORM 1000-PROCESS.
     GOBACK.

 1000-PROCESS SECTION.
     PERFORM 1100-CONVERT-TO-TEXT.
     DISPLAY "DEBUG FOR NEXT STEP: " PROC-STORE-DISPLAY.

* ASSEMBLE FINAL NUMBER
     MOVE 0 TO NUMBER-SPACES.
     INSPECT PROC-STORE-DISPLAY TALLYING NUMBER-SPACES FOR LEADING "0".
     COMPUTE DATA-POSITION = 18 - INPUT-DDSIZE.
     COMPUTE PERIOD-POSITION = 18 - INPUT-DECIMALS.
     DISPLAY "SPACES: " NUMBER-SPACES  " DATA: " DATA-POSITION " PERIOD: " PERIOD-POSITION.

     IF INPUT-DECIMALS = 0
       STRING PROC-STORE-DISPLAY (19:1) DELIMITED BY SIZE
              PROC-STORE-DISPLAY (DATA-POSITION + 1:INPUT-DDSIZE) DELIMITED BY SIZE
         INTO OUTPUT-DATA-VALUE
       END-STRING
     ELSE
       STRING PROC-STORE-DISPLAY (19:1) DELIMITED BY SIZE
              PROC-STORE-DISPLAY (DATA-POSITION + 1:PERIOD-POSITION - DATA-POSITION) DELIMITED BY SIZE
              "." DELIMITED BY SIZE
              PROC-STORE-DISPLAY (PERIOD-POSITION + 1:INPUT-DECIMALS) DELIMITED BY SIZE
         INTO OUTPUT-DATA-VALUE
       END-STRING
     END-IF.
     DISPLAY "    CONVERTED VALUE: " OUTPUT-DATA-VALUE.

 1100-CONVERT-TO-TEXT SECTION.
* MOVE DATA AREA TO LARGE NON-DECIMAL COMP VALUE.
     MOVE INPUT-DATA-AREA (1:INPUT-DATA-SIZE) TO PROC-STORE-TEXT.
* REPLACE FILLER SPACE VALUES WITH LOW-VALUES TO CORRECT THE DATA FORMAT
     INSPECT PROC-STORE-TEXT REPLACING LEADING SPACES BY LOW-VALUES.
* CONVERT TO DISPLAY FORMAT.
     MOVE PROC-STORE-VAR TO PROC-STORE-NUMVAL.

Measurement is not management.
 
Did this help any? Still having problems?

Measurement is not management.
 
Hi Glenn,

Yes, the skeleton program you provided definitely helped me structure my program properly and use the reference modification/navigate the decimal point.
Looking at it now - it's not as complex as I first thought thanks to everyones advice. Getting more and more used to this verbose language which is actually quite pwerful :)
 
Status
Not open for further replies.

Part and Inventory Search

Sponsor

Back
Top