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

Moving PIC S9(15)V9(02) COMP-3 to output

Status
Not open for further replies.

wolves

Programmer
Jan 26, 2001
130
US
Trying to correct the following logic so that I can see the correct figure from the input to the ouput. This is how the program is stated currently:

code]
01 IN-REC.
05 AMOUNT PIC S9(15)V9(02) COMP-3.


01 OUT-REC.
05 OUT-AMT PIC 9(9).


MOVE IN-REC to OUT-REC
[/code]


Would I change the OUT-REC to read:
05 OUT-AMT PIC9(15)V99?
 
Anyway, for numeric conversion like this, do elementary move, like this:
MOVE AMOUNT OF IN-REC TO OUT-AMT OF OUT-REC
And if you want to preserve the figures, then define OUT-AMT like this:
05 OUT-AMT PIC S9(15)V99.
or if you want numeric edited:
05 OUT-AMT PIC -(15)9.99 BLANK WHEN ZERO.

Hope This Helps, PH.
Want to get great answers to your Tek-Tips questions? Have a look at FAQ219-2884 or FAQ222-2244
 
Doesn't quite work. I get the following error:

The IBM message that corresponds to the condition is:
CEE3207S The system detected a data exception (System Completion Code=0C7).



I am going to experiment some more.

thx
 
If you have that error then you have a BAD input data.

Is
01 IN-REC.
05 AMOUNT PIC S9(15)V9(02) COMP-3.
from a file you are reading?

If so fix the place where that data is populated.

To avoid the abend try

if amount of in-rec numeric
move amount of in-rec to OUT-AMT of out-rec
else
(error handling)
or
move zero to OUT-AMT of out-rec
end-if

Regards

Frederico Fonseca
SysSoft Integrated Ltd
 
The 0C7 is saying that your input amount was not a valid Comp-3 format. The code that fredericofonseca posted above which tests the input for numeric will solve the 0C7 however, your root cause is your input amount is not a valid comp-3 field.

etom
 
Be careful here. If OUT-AMT is not used in this program (and it's unlikely that it is), it is not necessarily an error as the cited comp-3 field does, in fact, occupy 9 bytes. I would have either defined it as filler, or, more accurately, defined it to match AMOUNT of IN-REC (including the COMP-3). The change you propose will change the length of the output record which will likely break programs that use that file unless they are all recompiled with the new record definition.

Regards.

Glenn
 
Here is the difference I get:

Using
Code:
01  IN-REC.                                        
    05 AMOUNT               PIC S9(15)V9(02) COMP-3. 
           

01 OUT-REC.
   05 OUT-AMT           PIC 9(9).


if amount of in-rec numeric
   move amount of in-rec to OUT-AMT of out-rec
else
   (error handling)
    or
   move zero to OUT-AMT of out-rec
end-if

OUTPUT = XXX X XXXXX .XXXXXX.XXXXX .000000061

Using:
Code:
01  IN-REC.                                        
    05 AMOUNT               PIC S9(15)V9(02) COMP-3. 
           

01 OUT-REC.
   05 OUT-AMT           PIC S9(15)V99.


if amount of in-rec numeric
   move amount of in-rec to OUT-AMT of out-rec
else
   (error handling)
    or
   move zero to OUT-AMT of out-rec
end-if


OUTPUT = XXX X XXXXX .XXXXXX.XXXXX .0000000000000000{


Any ideas?
 
This is not the full code.

Please post the full code, with all the definitions of the fields involved, as well as the origin/population of the in and out records.

Then we can help.

Regards

Frederico Fonseca
SysSoft Integrated Ltd
 
if amount of in-rec numeric
move amount of in-rec to OUT-AMT of out-rec
else
(error handling)
or
move zero to OUT-AMT of out-rec
end-if


how would this work if my input which is my input file is PIC S9(15)V9(02) COMP-3. It will not read this comp field as numeric, is that correct?
 
Rather than moving zeroes to your output field *IF* you are trying to "see" the bad data, try moving the (bad) input field to an alphanumeric output field. You would then want to "look at" your output with a HEX editor (ISPF on IBM mainframes would work fine).

As you are getting an LE error message, I assume you ARE on an IBM mainframe. Check your compiler option setting for the NUMPROC compiler option. This impacts what is and is NOT considered valid numeric data.

See:



Bill Klein
 
Here is the last one I tried with results below:

Code:
ENVIRONMENT DIVISION.
CONFIGURATION SECTION.           
INPUT-OUTPUT SECTION.
FILE-CONTROL.

SELECT OUTFILE          ASSIGN S-OUTFILE.
SELECT INFILE          ASSIGN S-INFILE.
I-O-CONTROL.

DATA DIVISION.
FILE SECTION.

FD  INFILE
   RECORDING MODE IS F
   LABEL RECORDS ARE OMITTED
   RECORD CONTAINS 100 CHARACTERS
   BLOCK CONTAINS 0 RECORDS
   DATA RECORD IS INREC.
   01  INREC          PIC X(100).

   FD  OUTFILE
   RECORDING MODE IS F
   LABEL RECORDS ARE OMITTED
   RECORD CONTAINS 100 CHARACTERS
   BLOCK CONTAINS 0 RECORDS
   DATA RECORD IS OUTREC.

   01  OUTREC.
    05  OUTFIELDA                  PIC X(20).
    05  FILLER                   PIC X(01) VALUE '.'.
    05  OUTFIELDSB                 PIC X(06).
    05  FILLER                   PIC X(01) VALUE '.'.
    05  OUTFIELDSC                PIC X(12).
    05  FILLER                   PIC X(01) VALUE '.'.
    05  OUT-AMT                  PIC S9(15)V99.
    05  FILLER                   PIC X(46).

  WORKING-STORAGE SECTION.
      
   COPY INRECFD.
   (01   IN-REC.
  	 05   FIELDA          PIC X(20).
  	 05   FIELDB          PIC X(6).
  	 05   FIELDC          PIC X(12).
         05   MONEY-FIELD.
    	   10   AMOUNT        PIC S9(15) COMP-3.)

*----------------------------------------------------------------*
*                       PROCEDURE DIVISION                       *
*----------------------------------------------------------------*
PROCEDURE DIVISION.
0000-MAINLINE.

PERFORM 1000-INITIALIZATION THRU
           1000-INITIALIZATION-EXIT

PERFORM 2000-MAIN-PROCESS THRU
         2000-MAIN-PROCESS-EXIT
UNTIL EOF-SW = 'Y'

PERFORM 3000-TERMINATE THRU
            3000-TERMINATE-EXIT
           .
0000-MAINLINE-EXIT.
     GOBACK.

 1000-START.
          
    OPEN OUTPUT OUTFILE
   OPEN INPUT  INFILE

    MOVE 'N'                        TO EOF-SW
    READ INFILE                     INTO IN-REC
      AT END
     MOVE 'Y'                        TO EOF-SW
     GO TO 1000-START-EXIT
    END-READ

 MOVE 'N'                        TO EOF-SW.

1000-START-EXIT.
   EXIT.

2000-MAIN-PROCESS.

INITIALIZE OUTREC
MOVE FIELDA            TO OUTFIELDA
MOVE FIELDB            TO OUTFIELDB
MOVE FIELDC            TO OUTFIELDC
MOVE AMOUNT            TO OUT-AMT
WRITE OUTREC
      
READ INFILE             INTO IN-REC
AT END
 MOVE 'Y' TO EOF-SW
 GO TO 2000-MAIN-PROCESS-EXIT
END-READ.
          
2000-MAIN-PROCESS-EXIT.
           EXIT.

3000-TERMINATE.
           
CLOSE OUTFILE
CLOSE INFILE

         .
3000-TERMINATE-EXIT.
           EXIT.

INPUT FILE FORMAT (Fields A, B C and the Amount{starts with .... since its a comp3 field) are all sorted by the JCL below.)

X AAAAAAAAAAAAAAA D 130024 11111126199407BBBBBBCCCCCCCCCCCC 1994.........@
X AAAAAAAAAAAAAAA C 07998 00111111111199411BBBBBBCCCCCCCCCCCC233790 ....... È%
X AAAAAAAAAAAAAAA C 07998 00111111113199411BBBBBBCCCCCCCCCCCC 1991....... È_
X AAAAAAAAAAAAAAA C 30377 11111111199301BBBBBBCCCCCCCCCCCC233090 ........ëý
X AAAAAAAAAAAAAAA C 30377 11111126199308BBBBBBCCCCCCCCCCCC ........c.
X AAAAAAAAAAAAAAA C 30379 11111128199308BBBBBBCCCCCCCCCCCC233090 .......mË'
X AAAAAAAAAAAAAAA C 30379 11111108199309BBBBBBCCCCCCCCCCCC .........<
X AAAAAAAAAAAAAAA D 00139 11111116199301BBBBBBCCCCCCCCCCCC233090 .........(



JCL:
Code:
//SYSOUT   DD  SYSOUT=*
//SYSPRINT DD  SYSOUT=*
//SYSLIST  DD  SYSOUT=*
//SORTWK01 DD  UNIT=SYSDA,SPACE=(CYL,(50))
//SORTWK02 DD  UNIT=SYSDA,SPACE=(CYL,(50))
//SORTWK03 DD  UNIT=SYSDA,SPACE=(CYL,(50))
//SORTIN   DD  DSN=INPUT.FILE.DECEM,DISP=SHR
//SORTOUT  DD  DSN=OUTPUT.FILE.DECEM.SORTED,
//             DISP=(NEW,CATLG,DELETE),
//             UNIT=DISK,
//             SPACE=(CYL,(5,5),RLSE),
//             DCB=(RECFM=FB,LRECL=100,BLKSIZE=27900)
//SYSIN    DD  *
   SORT FIELDS=(17,20,CH,A,51,6,CH,A,57,12,CH,A)
   SUM FIELDS=(79,9,PD)
   OUTREC FIELDS=(17,20,51,6,57,12,79,9)
  END
/*

OUTPUT = XXX X XXXXX .XXXXXX.XXXXX .0000000000000000{


 
Did this get a clean compile? No message against the erroneous parenthesis after COMP-3?

Bill Klein
 
The
(01 IN-REC.
05 FIELDA PIC X(20).
05 FIELDB PIC X(6).
05 FIELDC PIC X(12).
05 MONEY-FIELD.
10 AMOUNT PIC S9(15) COMP-3.)

was just an add-in to show the Copybook. I forgot to mention that when I put it in.
It did compile cleanly so if you see other mistakes, it was either a cut and paste error or a space issue when I copied it from the screen.
 
Got it working. But one last problem, I can't figure out.

Code:
01  IN-REC.                                        
    05 AMOUNT        PIC S9(15)V9(02) COMP-3. 
           

01 OUT-REC.
   05 OUT-AMT        PIC ----,---,---,--9.99.


01 WS-REC
   05 AMT            PIC S9(15)V99.


MOVE IN-REC T0 WS-REC
MOVE WS-REC to OUT-REC

New OUTPUT:

;AAAAAAAAAAAAAAAAAAAA.BBBBBB.CCCCCCCCCCCCCCC. 61.07

Here is my output defined: (as you can see above, I have '.' periods instead of '~' in my output file. Never seen this before.

Code:
01  OUTREC.
           05  FIELDA                   PIC X(20).
           05  FILLER                   PIC X(01) VALUE '~'.
           05  FIELDB                   PIC X(06).
           05  FILLER                   PIC X(01) VALUE '~'.
           05  FIELDB                   PIC X(12).
           05  FILLER                   PIC X(01) VALUE '~'.
           05  OUT-AMT                  PIC ----,---,---,--9.99.
 
Look at the "periods" in HEX. If you are using ISPF to "browse" your output file, it (under certain circumstances) shows a "." to represent an "unprintable" character.

Bill Klein
 
Yes,

sure looks like it is printing low values or unprintable character. Wonder why? never had a problem before printing another character.

Code:
.CCCCC       .              61.07
0CCEFF4444444044444444444444FF4FF
049299000000000000000000000061B07
 
Check your compile error messages. I've never seen it work to put VALUE clauses in a record layout defined under an FD. It usually gives you a warning error message that says it is not allowed and disregards it. It has to do with buffer storage and the fact that no storage is defined at the start of your program as it is with Working-Storage. It isn't allocated until you do the OPEN.
 
You are absolutely correct, I should have known this. Basic stuff.

Thx, will try and sure it will work out.
 
Do you still have problems?

...just a detail:
You know that your output record definition is inconsistent with your file description.
FD 100 CHARACTERS <--> length of outfile = 104 bytes.

Besides that I don't see a test on NUMERIC in your program. The input might be incorrect.

Also, I have some problems matching your sort string with the program given:
Code:
SORT FIELDS=(17,20,CH,A,51,6,CH,A,57,12,CH,A)
SUM FIELDS=(79,9,PD)
OUTREC FIELDS=(17,20,51,6,57,12,79,9)
I expected: SUM FIELDS=(42,9,PD)
...if I counted correctly!

But I must be overlooking something because I can also not match any of your sort fields:
SORT FIELDS=(17,20,CH,A,51,6,CH,A,57,12,CH,A)
on the fields of the following outfile record:

Code:
01  OUTREC.
  05  OUTFIELDA       PIC X(20).
  05  FILLER          PIC X(01) VALUE '.'.
  05  OUTFIELDSB      PIC X(06).
  05  FILLER          PIC X(01) VALUE '.'.
  05  OUTFIELDSC      PIC X(12).
  05  FILLER          PIC X(01) VALUE '.'.
  05  OUT-AMT         PIC S9(15)V99.
  05  FILLER          PIC X(46).
My (current) best guess for the sort string is:
SORT FIELDS=(1,20,CH,A,22,6,CH,A,29,12,CH,A)

Was there some job step in between, or am I mistaken?

All this makes me very nervous concerning the input file.
Are you sure that the input file definition (IN-REC) as given exactly matches the input file records?

If the problem is not solved yet can you then please show the complete JCL!


Regards, Wim.
 
Thx for the help all. Yes, I did copy the wrong sort and sum fields from the wrong JCL, working on 2 computers got my screen copies all backwards. I did get it work.
I took the value clauses out of the FD and copied it to a copybook and all worked out just fine.

Thx again.
 
Status
Not open for further replies.

Part and Inventory Search

Sponsor

Back
Top