Search code examples
cobolmainframe

The system detected a protection exception


I am trying to use the SORT feature of COBOL.

IDENTIFICATION DIVISION.                       
PROGRAM-ID. ******.                          
ENVIRONMENT DIVISION.                          
INPUT-OUTPUT SECTION.                          
FILE-CONTROL.                                  
     SELECT IN-FILE ASSIGN TO IFILE.           
     SELECT OUT-FILE ASSIGN TO OFILE.          
     SELECT SORT-FILE ASSIGN TO SORTWK.        
DATA DIVISION.                                 
FILE SECTION.                                  
SD SORT-FILE.                                  
01 SORT-REC.                                   
   05 S-NAME     PIC X(20).                    
   05 S-ADDRESS  PIC X(20).                    
   05 S-ID       PIC 9(9).                     
   05 S-CREDITS  PIC 99.                       
   05 FILLER     PIC X(29).                    
FD IN-FILE.                                    
01 IN-REC.                                     
   05 IN-NAME    PIC X(20).                    
   05 IN-ADDRESS PIC X(20).                    
   05 IN-ID      PIC 9(9).                     
   05 IN-CREDITS PIC 99.                       
   05 FILLER     PIC X(29).                    
FD OUT-FILE.                                   
01 OUT-REC       PIC X(80).                    
WORKING-STORAGE SECTION.                       
01 WS-WORK-AREA.                               
    05  EOF-SW    PIC X           VALUE SPACES.
01 WS-DETAIL-LINES.                            
   05 RPT-LINE.                                
      10 OUT-NAME    PIC X(20).                
      10 OUT-ADDRESS PIC X(20).                
      10 OUT-ID      PIC 9(9).
      10 OUT-CREDITS PIC 99.                      
      10 FILLER      PIC X(29)       VALUE SPACES.
PROCEDURE DIVISION.                               
MAIN-RTN.                                         
    SORT SORT-FILE                                
            ON ASCENDING KEY S-ID                 
            INPUT PROCEDURE READ-RELEASE          
            OUTPUT PROCEDURE RETURN-WRITE.        
    STOP RUN.                                     
OPEN-FILES-RTN.                                   
    OPEN INPUT IN-FILE.                           
    OPEN OUTPUT OUT-FILE.                         
OPEN-FILES-RTN-EXIT. EXIT.                        

READ-RELEASE.                                     
    PERFORM OPEN-FILES-RTN.                       
    PERFORM READ-INPUT                            
     UNTIL EOF-SW = 'F'.                          
READ-RELEASE-RTN-EXIT. EXIT.                      

READ-INPUT.                                       
    READ IN-FILE                                  
     AT END MOVE 'F' TO EOF-SW.                   
    RELEASE SORT-REC FROM IN-REC.                 

RETURN-WRITE.                                     
    MOVE SPACES TO EOF-SW.                        
    PERFORM WRITE-FL                              
     UNTIL EOF-SW  = 'F'.                         
    PERFORM CLOSE-FILES-RTN.                      
RETURN-WRITE-RTN-EXIT. EXIT.                      

WRITE-FL.                                         
    RETURN SORT-FILE RECORD INTO OUT-REC          
     AT END MOVE 'F' TO EOF-SW.                   
    WRITE OUT-REC.
WRITE-FL-RTN-EXIT. EXIT.   

CLOSE-FILES-RTN.           
    CLOSE IN-FILE OUT-FILE.
CLOSE-FILES-RTN-EXIT. EXIT. 

I am able to compile this program but when it comes to execute, it gives the following error:

CEE3204S The system detected a protection exception (System Completion Code=0C4). From compile unit SU98PGM6 at entry point SU98PGM6 at compile unit offset +0005517A at address 1F45517A.

I have searched about this error but I couldn't figure out what is causing this problem in my program.

I have made some changes after taking note of the comments, but am still getting the same problem with this changed code.

READ-RELEASE.                           
    PERFORM OPEN-FILES-RTN.             
    PERFORM READ-INPUT                  
     UNTIL EOF-SW = 'F'.                
READ-RELEASE-RTN-EXIT. EXIT.            

READ-INPUT.                             
    READ IN-FILE                        
     AT END MOVE 'F' TO EOF-SW          
     NOT AT END PERFORM PROCESS-INPUT.  

PROCESS-INPUT.                          
    MOVE IN-NAME TO S-NAME.             
    MOVE IN-ADDRESS TO S-ADDRESS.       
    MOVE IN-ID TO S-ID.                 
    MOVE IN-CREDITS TO S-CREDITS.       
    RELEASE SORT-REC.                   
PROCESS-INPUT-RTN-EXIT. EXIT.           

RETURN-WRITE.                           
    MOVE SPACES TO EOF-SW.              
    PERFORM WRITE-FL                    
     UNTIL EOF-SW = 'F'.                
    PERFORM CLOSE-FILES-RTN.            
RETURN-WRITE-RTN-EXIT. EXIT.            

WRITE-FL.                               
    RETURN SORT-FILE RECORD INTO OUT-REC
     AT END MOVE 'F' TO EOF-SW          
     NOT AT END PERFORM PROCESS-OUTPUT. 
WRITE-FL-RTN-EXIT. EXIT.                

PROCESS-OUTPUT.                         
    MOVE S-NAME TO OUT-NAME.            
    MOVE S-ADDRESS TO OUT-ADDRESS.      
    MOVE S-ID TO OUT-ID.                
    MOVE S-CREDITS TO OUT-CREDITS.
    WRITE OUT-REC.            
PROCESS-OUTPUT-RTN-EXIT. EXIT.   

Here is my JCL

//******** JOB 1,'*****',NOTIFY=*******                    
//JOBLIB   DD  DSN=*******.*******.*******,DISP=SHR         
//STEP0    EXEC PGM=SU98PGM6                               
//IFILE    DD DSN=*******.*******.*******.*******(*******),DISP=SHR
//SORTWK   DD DSN=*******.*******.*******.*******,DISP=SHR          
//OFILE    DD DSN=*******.*******.*******.*******,              
//            DISP=(NEW,CATLG,DELETE),                     
//            DCB=(BLKSIZE=0,LRECL=80,RECFM=FB),           
//            SPACE=(CYL,(1,1),RLSE),                      
//            UNIT=SYSDA                                   
/*         

Solution

  • The output for the //SYSOUT DD can be confusing when using COBOL, SORT (DFSORT or SyncSORT) and Language Environment which may give you run-time messages, as they all use SYSOUT by default, and the messages will appear intermingled.

    Fortunately, you can change the default behaviour, as shown here for DFSORT and Language Envrionment (there are many ways in LE to specify the option, the most flexible is a //CEEOPTS DD in your JCL): https://stackoverflow.com/a/29521423/1927206

    COBOL itself has a compiler option, OUTDD. the value defaults to SYSOUT, but you can specify any OUTDD(xxxx)


    OK, having seen your JCL and your comments about how a DISPLAY statement in your program affects the data, I've managed a partial reproduce.

    I use DFSORT, and I don't get your exact behaviour so I'm going to assume you use SYNCSORT.

    The behaviour I can get having removed the //SYSOUT DD from my JCL is this message:

    IGZ0026W The SORT-RETURN special register was never referenced, but the current content indicated the sort or merge operation in program STOB87 on line number 46 was unsuccessful.

    When I add the //SYSOUT back into the JCL, the program runs successfully.

    When I take the //SYSOUT out and add a DISPLAY before the SORT, the program works. This is because if there is no //SYSOUT in the JCL the first DISPLAY which is executed will cause one to be dynamically created (the output will appear in the spool as though it were a separate JOB, with the same name and jobnumber).

    In my case DFSORT is complaining about the missing //SYSOUT. With the DISPLAY, the //SYSOUT is not missing at the time DFSORT starts.

    I have to assume that SYNCSORT is facing a similar issue, but the run-time COBOL message is not produced and SYNCSORT itself fails on the next RELEASE.

    Although this seems like a simple and common issue, because we always copy a piece of JCL to make a new piece of JCL, //SYSOUT is always there.

    Consult the Enterprise COBOL Programming Guide, Chapter 12 I think, and see how to use SORT-RETURN to confirm that the SORT completed successfully.

    I'm pretty sure that if you include the //SYSOUT in your JCL you will no longer get the abend, whether or not you have a DISPLAY.

    The reason for the high "offset" is that the abend processor is unable to identify the entry-point of your SORT product, so keeps searching backwards to find something it can identify, and locates your program entry-point and then calculates the incorrect offset. This can also happen when CALLing some Assembler programs.


    Firstly, to your S0C4, which is a Protection Exception, which means you are attempting to access storage which doesn't "belong" to you for the access you want.

    You are getting a S0C4 in program SU98PGM6. You have cunningly obliterated your PROGRAM-ID name when posting here, which probably hasn't helped.

    SU98PGM6 is not your program. The abend (Abnormal End) is at offset X'0005517A' in the failing program. That means, from the "start" of the program (the Entry Point) the instruction at offset/displacement X'0005517A' is the one which attempted the bad thing. That offset, which in decimal is 348538, indicates a fairly large program. Your program is very small.

    There are many ways that this can come about. For instance, you may have copied the JCL from somewhere else, and failed to change the EXEC PGM=. You may have a program of the same name as yours earlier in the STEPLIB concatenation. You may have compiled the wrong program. Etc.

    When you get an abend, always confirm that the compile listing you have is for the program that abended. An easy and useful way to do this is:

       01  W-WHEN-COMPILED                     PIC X(8)BX(8).
    
       ...
    
      * where it can only be executed once:
           MOVE WHEN-COMPILED           TO W-WHEN-COMPILED
           DISPLAY 
                   "yourname COMPILED ON " 
                   W-WHEN-COMPILED
    

    "yourname" you replace with the text following PROGRAM-ID.

    The output will be like this:

    yourname COMPILED ON 11/24/15 10.35.26
    

    That will match the date/time in the heading on each page of the compile listing.

    If you run a program and don't get that output, or you get output but it is not the output expected, then you know your program is not the one running.

    Now to your program.

    1. You do not need to use input/output procedures to be able to SORT
    2. You should always use the FILE STATUS clause of the SELECT statement, and always check the file-status fields (one per file) that you define, after each IO operation. Testing the file-status field for an input file will allow you to identify end-of-file without the need for the tortuous AT END/NOT AT END construct
    3. If you use sort procedures, COBOL does the IO. If you don't, and use compiler option FASTSRT, your SORT product will do the IO, which will be much more efficient than COBOL.
    4. Unless you are selecting or reformatting records, you don't need the sort procedures
    5. Since you are using INTO, which does an implicit MOVE of the record, you don't need to also MOVE the data individually
    6. COBOL, since compilers supporting the 1985 Standard, which I'm fairly sure you will have, have "scope terminators". Prior to that, the only scope-terminator was the full-stop/period. These days, use the explicit, specific scope-terminators when using "imperative statements" and for all conditional statements. In your case, replace use READ/END-READ, RETURN/END-RETURN
    7. Only use full-stops/periods in the PROCEDURE DIVISION where they are required, and not on a line of code. This aids the moving/copying of code from one location to another
    8. Use 88-level condition-names for tests, rather than literals. You can make the name exactly meaningful, so nobody ever has to wonder what 'F' means in a particular context

    To simply SORT a file in a COBOL program, look at SORT ... USING ... GIVING... and use compiler option FASTSRT (if possible).

    You are not yet aware of the implications of paragraphs (or SECTIONs) and the EXIT statement.

    When using PERFORM or a SORT PROCEDURE execution is transferred to the code in the paragraph, and returns control when the next paragraph is reached.

    Your "exit" paragraphs as you have coded are never used, but someone looking at the code will assume (if they are silly, and a lot of people will make the assumption) that you have used THRU and they'll stick in a GO TO the "exit" paragraph. Then they'll be surprised that the program behaves badly (if they're luck) and will eventually work out that they have used GO TO to transfer control out of the range of the PERFORM/PROCEDURE.

    If your local standards enforce the use of exit-paragraphs, then you must use THRU in your PERFORM and PROCEDURE statements.

    Exit-paragraphs are entirely useless, and do nothing but provide a target-label for a GO TO, meaning that someone in the future will likely use a GO TO for "convenience".

    Here's your original program with the exit-paragraphs removed:

    IDENTIFICATION DIVISION.                       
    PROGRAM-ID. ******.                          
    ENVIRONMENT DIVISION.                          
    INPUT-OUTPUT SECTION.                          
    FILE-CONTROL.                                  
         SELECT IN-FILE ASSIGN TO IFILE.           
         SELECT OUT-FILE ASSIGN TO OFILE.          
         SELECT SORT-FILE ASSIGN TO SORTWK.        
    DATA DIVISION.                                 
    FILE SECTION.                                  
    SD SORT-FILE.                                  
    01 SORT-REC.                                   
       05 S-NAME     PIC X(20).                    
       05 S-ADDRESS  PIC X(20).                    
       05 S-ID       PIC 9(9).                     
       05 S-CREDITS  PIC 99.                       
       05 FILLER     PIC X(29).                    
    FD IN-FILE.                                    
    01 IN-REC.                                     
       05 IN-NAME    PIC X(20).                    
       05 IN-ADDRESS PIC X(20).                    
       05 IN-ID      PIC 9(9).                     
       05 IN-CREDITS PIC 99.                       
       05 FILLER     PIC X(29).                    
    FD OUT-FILE.                                   
    01 OUT-REC       PIC X(80).                    
    WORKING-STORAGE SECTION.                       
    01 WS-WORK-AREA.                               
        05  EOF-SW    PIC X           VALUE SPACES.
    01 WS-DETAIL-LINES.                            
       05 RPT-LINE.                                
          10 OUT-NAME    PIC X(20).                
          10 OUT-ADDRESS PIC X(20).                
          10 OUT-ID      PIC 9(9).
          10 OUT-CREDITS PIC 99.                      
          10 FILLER      PIC X(29)       VALUE SPACES.
    PROCEDURE DIVISION.                               
        SORT SORT-FILE                                
                ON ASCENDING KEY S-ID                 
                INPUT PROCEDURE READ-RELEASE          
                OUTPUT PROCEDURE RETURN-WRITE        
        GOBACK
        .                                     
    OPEN-FILES-RTN.                                   
        OPEN INPUT IN-FILE                           
        OPEN OUTPUT OUT-FILE
        .                         
    
    READ-RELEASE.                                     
        PERFORM OPEN-FILES-RTN
        PERFORM READ-INPUT                            
         UNTIL EOF-SW = 'F'                          
        .
    
    READ-INPUT.                                       
        READ IN-FILE                                  
         AT END MOVE 'F' TO EOF-SW
        END-READ                   
        RELEASE SORT-REC FROM IN-REC
        .
    
    RETURN-WRITE.                                     
        MOVE SPACES TO EOF-SW
        PERFORM WRITE-FL                              
         UNTIL EOF-SW  = 'F'                         
        PERFORM CLOSE-FILES-RTN                      
        .
    
    WRITE-FL.                                         
        RETURN SORT-FILE RECORD INTO OUT-REC          
         AT END MOVE 'F' TO EOF-SW
        END-RETURN
        WRITE OUT-REC
        .
    
    CLOSE-FILES-RTN.           
        CLOSE IN-FILE OUT-FILE
        .
    

    I've also changed the STOP RUN to GOBACK, which is much more flexible, and removed your first paragraph-name, as it is unnecessary and for people new to COBOL implies too much (COBOL itself has no concept of "main" as it may be pertinent in other languages you may know).