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!

Pic x(??) Move to Comp3

Status
Not open for further replies.

workbytes

Programmer
Nov 7, 2002
4
US
I'm trying to move a field that is defined as
Pic S9(05) Comp-3., to a field defined as
Pic X(03)..can someone help. I'm new at this, and
am thinking I'll have to create a working storage
field to move one of the fields into, but not
sure????
 
Hi workbytes!

You can't move the COMP-3 directly. You'll have to REDEFINE it or handle it similar to this:
Code:
01 WS-RECORD.
   05  MY-BYTE-FIELD.
       10  MY-COMP-3-FIELD       PIC S9(5) COMP-3.
   05  etc
[\code]
MY-BYTE-FIELD is a 3-byte, DISPLAY field (because it is a group item) and can be moved to another 3-byte field directly.

Good luck!

Glenn 
Brainbench MVP for COBOL II
 
This is a fair dinkum doosie.
I would do this.
CODE
000037*
000038 01 WW-SOURCE-FIELD PIC S9(05) COMP-3.
000039*
000040 01 WW-TEMP-GRP.
000041 03 WW-TEMP-NUM PIC S9(05) COMP-3.
000042*
000043 01 WW-TARGET-FIELD PIC X(03).
000092*
000093 MOVE WW-SOURCE-FIELD TO WW-TEMP-GRP.
000094 MOVE WW-TEMP-GRP TO WW-TARGET-FIELD.
000095*
\CODE

Here is a program to calculate the size of a field.
Instead of 1 field, you could put in a record layout
which would then calculate the accumulated size
of all the fields, and thus the record size.
You have to compile it each time.
I have been lazy and left a few of my "pre-compiler"
statements in the code, but I'm sure you could create
a standard COBOL syntax program from it.

CODE
000001 @-COPYRIGHT
000002 @-SET
000003 IDENTIFICATION DIVISION.
000004 PROGRAM-ID. EXPER.
000005 AUTHOR. Grace Hopper.
000006 DATE-WRITTEN. 4th March, 1999.
000007 DATE-COMPILED.
000008*HISTORY. 20021120 19415370.
000009*PC. E:\SPECTRUM\CONTROL\WBPC\EXPER2\20021120\19415359\EXPER2.PRE
000010*REMARKS. Experiment.
000011 ENVIRONMENT DIVISION.
000012 CONFIGURATION SECTION.
000013*SOURCE-COMPUTER. IBM-PC WITH DEBUGGING MODE.
000014 SOURCE-COMPUTER. IBM-PC.
000015 OBJECT-COMPUTER. IBM-PC.
000016 SPECIAL-NAMES.
000017 CONSOLE IS CRT
000018 CURSOR IS WX-CURSOR
000019 CRT STATUS IS WW-KEY-STATUS.
000020 DATA DIVISION.
000021 WORKING-STORAGE SECTION.
000022*
000023 01 WW-PROGRAM-DATE-TIME-STAMP.
000024 03 WW-PROGRAM-DATE-STAMP PIC X(08) VALUE '20021120'.
000025 03 WW-PROGRAM-TIME-STAMP PIC X(08) VALUE '19415370'.
000026*
000027 01 WW-PROGRAM-VERSION PIC X(04) VALUE '0096'.
000028*
000029 01 WW-PAYMENT-STATUS PIC X(02).
000030*
000031 77 WW-FIELD PIC X(01).
000032 88 END-OF-FIELD VALUE 'X'.
000033*
000034 01 WI-CAPT PIC 9(05).
000035*
000036 01 WW-X3 PIC X(03).
000037*
000038 01 WW-SOURCE-FIELD PIC S9(05) COMP-3.
000039*
000040 01 WW-TEMP-GRP.
000041 03 WW-TEMP-NUM PIC S9(05) COMP-3.
000042*
000043 01 WW-TARGET-FIELD PIC X(03).
000044*
000045 01 WW3-GRP.
000046 03 WW3-NUM PIC S9(05) COMP-3.
000047*
000048 01 WO-DISP-NO PIC 9(05)-.
000049*
000050 W-CURRENT-TIME
000051 W-CURRENT-DATE
000052 W-GENERAL
000053 W-DTS
000054 W-FILE-STATUS
000055 W-FUNCTION-KEYS
000056 W-DEBUG
000057 W-RPM
000058 W-EMPTY-CHARS
000059*
000060*=================================================================
000061*
000062 PROCEDURE DIVISION.
000063*
000064 0000-MAIN-CONTROL SECTION.
000065*
000066 MOVE '0000-MAIN-CONTROL' TO WO-MODULE.
000067*
000068 CONTROL-PARAGRAPH.
000069 MOVE "EXPER" TO WO-PROGRAM.
000070 PERFORM X-INIT-DEBUG.
000071*
000072 PERFORM 1000-INITIALIZE.
000073 PERFORM 2000-PROCESS.
000074 PERFORM 3000-FINALIZE.
000075*
000076 GO TO Z-TERMINATE.
000077*
000078 EXIT-PARAGRAPH.
000079 EXIT.
000080*
000081*=================================================================
000082*
000083 1000-INITIALIZE SECTION.
000084*
000085 MOVE '1000-INITIALIZE' TO WO-MODULE.
000086*
000087 CONTROL-PARAGRAPH.
000088*
000089* ACCEPT WI-CAPT FROM COMMAND-LINE.
000090 ACCEPT WI-CAPT FROM CRT.
000091 MOVE WI-CAPT TO WW-SOURCE-FIELD.
000092*
000093 MOVE WW-SOURCE-FIELD TO WW-TEMP-GRP.
000094 MOVE WW-TEMP-GRP TO WW-TARGET-FIELD.
000095*
000096 MOVE WW-TARGET-FIELD TO WW3-GRP.
000097 MOVE WW3-NUM TO WO-DISP-NO.
000098 MOVE WO-DISP-NO TO WO-DEBUG-MSG.
000099 PERFORM X-DEBUG.
000100*
000101 EXIT-PARAGRAPH.
000102 EXIT.
000103*
000104*=================================================================
000105*
000106 2000-PROCESS SECTION.
000107*
000108 MOVE '2000-PROCESS' TO WO-MODULE.
000109*
000110 CONTROL-PARAGRAPH.
000111*
000112*
000113 EXIT-PARAGRAPH.
000114 EXIT.
000115*
000116*=================================================================
000117*
000118 3000-FINALIZE SECTION.
000119*
000120 MOVE '3000-FINALIZE' TO WO-MODULE.
000121*
000122 CONTROL-PARAGRAPH.
000123*
000124*
000125 EXIT-PARAGRAPH.
000126 EXIT.
000127+
000128 X-INIT-EMPTY-CHARS
000129 X-INIT-DEBUG
000130 X-DEBUG
000131 X-CLOSE (DUMMY)
000132 X-GET-CURRENT-DATE
000133 X-GET-CURRENT-TIME
000134 X-KEY-STATUS
000135 Z-TERMINATE (STOP RUN)

\CODE

 
Sorry - wrong program was cut/pasted in previous response.
Try this one to calculate field size.
CODE

000001 @-COPYRIGHT
000002 @-SET
000003 IDENTIFICATION DIVISION.
000004 PROGRAM-ID. CALCSIZE.
000005 AUTHOR. Grace Hopper.
000006 DATE-WRITTEN. 03-01-1999.
000007 DATE-COMPILED.
000008*HISTORY. 20021120 19435931.
000009*PC. E:\SPECTRUM\CONTROL\WBPC\CALCSIZE\20021120\19435920\CALCSIZE.PRE
000010*REMARKS. Calculates the bytes in a picture.
000011 ENVIRONMENT DIVISION.
000012 CONFIGURATION SECTION.
000013*SOURCE-COMPUTER. IBM-PC WITH DEBUGGING MODE.
000014 SOURCE-COMPUTER. IBM-PC.
000015 OBJECT-COMPUTER. IBM-PC.
000016 SPECIAL-NAMES.
000017 CONSOLE IS CRT
000018 CURSOR IS WX-CURSOR.
000019 DATA DIVISION.
000020 WORKING-STORAGE SECTION.
000021*
000022 01 WW-PROGRAM-DATE-TIME-STAMP.
000023 03 WW-PROGRAM-DATE-STAMP PIC X(08) VALUE '20021120'.
000024 03 WW-PROGRAM-TIME-STAMP PIC X(08) VALUE '19435931'.
000025*
000026 01 WW-PROGRAM-VERSION PIC X(04) VALUE '0030'.
000027*
000028 W-GENERAL
000029 W-DEBUG
000030 W-FUNCTION-KEYS
000031*
000032 01 TEST-RECORD.
000033 03 FILLER PIC S9(05) COMP-3.
000034*
000035 01 WW-9999-BYTES PIC X(9999).
000036 01 WF-OVERFLOW PIC X(01).
000037 01 WW-EST-SIZE PIC 9(04).
000038 01 WO-EST-SIZE PIC Z,ZZ9.
000039*
000040*=================================================================
000041*
000042 PROCEDURE DIVISION.
000043*
000044 0000-MAINLINE SECTION.
000045*
000046 MOVE '0000-MAINLINE' TO WO-MODULE.
000047*
000048 CONTROL-PARAGRAPH.
000049 MOVE 'CALCSIZE' TO WO-PROGRAM.
000050 PERFORM X-INIT-DEBUG.
000051*
000052 PERFORM 1000-INITIALIZE.
000053 PERFORM 2000-PROCESS.
000054 PERFORM 3000-FINALIZE.
000055*
000056 GO TO Z-TERMINATE.
000057*
000058 EXIT-PARAGRAPH.
000059 EXIT.
000060*
000061*=================================================================
000062*
000063 1000-INITIALIZE SECTION.
000064*
000065 MOVE '1000-INITIALIZE' TO WO-MODULE.
000066*
000067 CONTROL-PARAGRAPH.
000068*
000069 DISPLAY SPACE AT 0101 WITH BG 1 FG 7.
000070*
000071 EXIT-PARAGRAPH.
000072 EXIT.
000073*
000074*=================================================================
000075*
000076 2000-PROCESS SECTION.
000077*
000078 MOVE '2000-PROCESS' TO WO-MODULE.
000079*
000080 CONTROL-PARAGRAPH.
000081*
000082 MOVE 1 TO WW-POINTER.
000083*
000084 STRING
000085 TEST-RECORD DEL SIZE
000086 INTO WW-9999-BYTES
000087 WITH POINTER WW-POINTER
000088 ON OVERFLOW
000089 DISPLAY '*** TEST FIELD GREATER THAN 9999 BYTES ***'
000090 END-STRING.
000091*
000092 COMPUTE WW-EST-SIZE = WW-POINTER - 1.
000093*
000094 EXIT-PARAGRAPH.
000095 EXIT.
000096*
000097*=================================================================
000098*
000099 3000-FINALIZE SECTION.
000100*
000101 MOVE '3000-FINALIZE' TO WO-MODULE.
000102*
000103 CONTROL-PARAGRAPH.
000104*
000105 MOVE WW-EST-SIZE TO WO-EST-SIZE.
000106 DISPLAY 'ESTIMATED SIZE = ' WO-EST-SIZE.
000107*
000108 MOVE '0301' TO WX-CURSOR.
000109 DISPLAY ' ' AT WX-CURSOR.
000110*
000111 EXIT-PARAGRAPH.
000112 EXIT.
000113+
000114 X-CLOSE (DUMMY)
000115 X-KEY-STATUS
000116 X-INIT-DEBUG
000117 X-DEBUG
000118 X-SHOW-EXPLANATION
000119 Z-TERMINATE (STOP RUN)

\CODE
 
Hi WB,

I think the ques has to be asked: "What do you expect to be contained in the pic x field?"

Suppose you have X'00012C' in your comp-3 field. What do you want to see in the pic x field? Is it X'00012C'?

I notice you define it as 3 bytes, so unless you expect the field to be truncated and converted to X'F0F1C2', you want X'00012C'.

What say you?

Regards, Jack.
 
I want the field truncated. I have 2 fields to compare.
It they miscompare, I'm writing them to a report.
The 2 fields I'm comparing are:

cp-activ-months Pic 9(03).
master-cp-months-activ Pic S9(05) comp-3.

I have zeroes in the cp-activ-months, and want to get zeroes in master-cp-months-activ, if the field contains, low-values, spaces, is not numeric, anything aside from a valid value.

Looking at hex for master-cp-months-activ, I find some records with low values, and some with spaces. The records in field, cp-activ-months has zeroes in it for hex.
I can't code to move zeroes into this field, because I get an error re: packed field.
 
workbytes -

1. A simple "if master-cp-months-activ not numeric" test should identify times when the field is not a valid number and you can then move zeros to it.

2. cp-activ-months should never have low-values (hex zeros) in it if it is a valid DISPLAY NUMERIC data item. If it does, the same technique will work for it as I describe above. Are you sure it isn't/shouldn't be defined as a BINARY value? In that case, x'000000' would be zero and x'000001' would be one, etc. If it is truly DISPLAY NUMERIC as you've shown it (assuming no USAGE BINARY at an enclosing group level), a zero (in ASCII) is x'202020' and a one ix x'202021'.

3. Truncation is not needed. After fixing up the fields as described above, simply test for equality. COBOL automatically deals with extending the shorter field and converting internal numeric representations as needed to properly compare the values.

4. There is absolutely no reason a MOVE ZEROS TO ... should fail for either field. Trying to move hex zeros via a hexadecimal literal is definitely a no-no however.
Code:
if cp-activ-months not numeric
    move zeros                 to cp-activ-months
end-if
if master-cp-months-activ not numeric
    move zeros                 to master-cp-months-activ
end-if
if cp-activ-months not = master-cp-months-activ
    move "fields do not equal" to report-line
    write report-line 
        after advancing 1 line
end-if
[\code]
Good luck!

Glenn
 
Hi WB,

I notice that your display field has no sign while your comp-3 field has. I'd suggest that they both be defined as having a sign.

BTW, how are the fields populated? It sounds like data is being read into them or they are populated via a group move. I also noticed that the pic x(03) field is now a
pic 9(03). I'm guessing the pic x was a typo.

Regards, Jack.
 
Status
Not open for further replies.

Part and Inventory Search

Sponsor

Back
Top