MVSFORUMS.com Forum Index MVSFORUMS.com
A Community of and for MVS Professionals
 
 FAQFAQ   SearchSearch   Quick Manuals   RegisterRegister 
 ProfileProfile   Log in to check your private messagesLog in to check your private messages   Log inLog in 

S0C4 Abend in user exit E15 in syncsort.

 
Post new topic   Reply to topic   printer-friendly view    MVSFORUMS.com Forum Index -> Utilities
View previous topic :: View next topic  
Author Message
gore
Beginner


Joined: 10 Dec 2002
Posts: 46
Topics: 20
Location: Providence, RI

PostPosted: Fri Jun 20, 2003 8:25 am    Post subject: S0C4 Abend in user exit E15 in syncsort. Reply with quote

Hi,
I have written the following user exit(E15) for syncsort. This is giving me S0C4. The COBOL code has been linkedited. What is possibly wrong?I am very new to coding exits.

Code:
       IDENTIFICATION DIVISION.                                       
       PROGRAM-ID. E15SORT.                                           
       DATE-WRITTEN.  20/06/2003.                                     
       DATE-COMPILED. 20/06/2003.                                     
       AUTHOR.       ALGORE.                               
       ENVIRONMENT DIVISION.                                           
       INPUT-OUTPUT SECTION.                                           
       FILE-CONTROL.                                                   
       DATA DIVISION.                                                 
       FILE SECTION.                                                   
       WORKING-STORAGE SECTION.                                       
        01 EVEN-FLAG         PIC 9(02)     VALUE ZERO.                 
        01  USER-RETURN-CODE PIC 9(08) COMPUTATIONAL.                 
            88 ACCEPT-REC                  VALUE 0.                   
            88 DELETE-REC                  VALUE 4.                   
            88 END-EXIT                    VALUE 8.                   
            88 INSERT-REC                  VALUE 12.                   
            88 END-SORT                    VALUE 16.                   
            88 REPL-REC                    VALUE 20.             
         01  CHANGE-REC       PIC X(80)     VALUE SPACES.         
         01  WS-WORK          PIC X(80).                         
       LINKAGE SECTION.                                           
         01  EXIT-STATUS     PIC 9(8) COMPUTATIONAL.             
           88 FIRST-TIME                   VALUE 00.             
           88 LAST-TIME                    VALUE 08.             
         01  RECORD-UP       PIC X(80).                           
         01  WORK            PIC X(80).                           
       PROCEDURE DIVISION USING EXIT-STATUS, RECORD-UP, WORK.     
              MOVE RECORD-UP TO WS-WORK                           
              MOVE 20 TO RETURN-CODE                             
              INSPECT WS-WORK CONVERTING ' ' TO '0'               
              MOVE WS-WORK TO WORK                               
              GO TO RETURN-TO-SORT                               
         RETURN-TO-SORT.                                         
           IF LAST-TIME THEN MOVE 8 TO RETURN-CODE               
           ELSE MOVE 0 TO RETURN-CODE                             
           END-IF.                                               
           GOBACK.


The sort job is follows:
Code:
//N052497K JOB  (1077C720),EBA3B,     X-1394           
//         MSGCLASS=H,MSGLEVEL=1,CLASS=M,NOTIFY=N052497
/*NOTIFY   N052497                                     
//SCRATCH EXEC PGM=IEFBR14                             
//SYSPRINT DD SYSOUT=*                                 
//SYSDUMP  DD SYSOUT=*                                 
//FILE01 DD DSN=N052497.GORE,DISP=(MOD,DELETE,DELETE), 
//        SPACE=(TRK,(0,0))                             
//STEP3    EXEC PGM=SYNCSORT                           
//SYSOUT   DD  SYSOUT=*                                 
//SORTIN   DD DISP=SHR,DSN=N052497.INPUT               
//SORTOUT  DD DSN=N052497.GORE,DISP=(NEW,CATLG,DELETE) 
//MODLIB   DD DSN=N052497.QA.LOADLIB,DISP=SHR           
//SYSIN    DD *                                         
    SORT FIELDS=COPY -                                 
    MODS E15=(E15SORT,600,MODLIB,N)                     
/*                                                     


Any guidance will be appreciated.
Gore
Back to top
View user's profile Send private message
ravikumar_sri2001
Beginner


Joined: 06 Dec 2002
Posts: 117
Topics: 44
Location: Chennai,India

PostPosted: Tue Jul 01, 2003 10:50 am    Post subject: Reply with quote

Gore,

The S0C4 abend may be due to parameter miss matching beween
SORT and your COBOL program.

Thanks,
Ravi
Back to top
View user's profile Send private message
Display posts from previous:   
Post new topic   Reply to topic   printer-friendly view    MVSFORUMS.com Forum Index -> Utilities All times are GMT - 5 Hours
Page 1 of 1

 
Jump to:  
You cannot post new topics in this forum
You cannot reply to topics in this forum
You cannot edit your posts in this forum
You cannot delete your posts in this forum
You cannot vote in polls in this forum


MVSFORUMS
Powered by phpBB © 2001, 2005 phpBB Group