| Author | 
		  Message
		 | 
		
		  | tjfunny1 | 
		  
		    
			  
				 Posted: Fri Aug 09, 2002 11:13 am    Post subject: Rollback after abend not working | 
				     | 
			   
			 
		   | 
		
		
		    Apprentice
 
 Joined: 17 Jun 2002 Posts: 35 Location: Atlanta 
  | 
		  
		    
			  
				The manual states if an application abends (OS/390), that messages in a local unit of work will rollback (syncpoint=yes).  But this isn't occurring, the messages are deleted from the queue. We are using MQ v5.2 on OS/390 w/o RRS.
 
 
Our cobol program's logic is:
 
/*****************************/
 
count=0
 
do until count = 7
 
       mqgmo-syncpoint + mqgmo-convert+ mqgmo-fail-if-quiescing
 
       mqget (w/syncpoint option
 
       count++ 
 
end do
 
 
    divide by zero	(this abends the code BEFORE the MQCMIT occurs
 
 
MQCMIT	(this would commit/delete the messages from the queue
 
MQDISC
 
/****************************/
 
 
This logic results in a S0CB abend, but the 7 messages are not rolled back.
 
 
The IBM MQSeries documentation says:  (we aren't invoking the RRS with their code, we use the CSQBSTUB)
 
 
"If the program ends abnormally, an implicit backout occurs. On OS/390, an implicit syncpoint occurs if the program ends normally without first calling MQDISC
 
 
The Qmgr attribute for SYNCPOINT =YES
 
MAXUMSG = 200,000,000
 
MAXSMSG = 200,000,000
 
 
Kudos to the one who answers _________________ TJ
 
IBM Certified System Administrator Websphere MQ v5.3 | 
			   
			 
		   | 
		
		
		  | Back to top | 
		  
		  	
		   | 
		
		
		    | 
		
		
		  | sgopal | 
		  
		    
			  
				 Posted: Fri Aug 09, 2002 11:58 am    Post subject:  | 
				     | 
			   
			 
		   | 
		
		
		   Acolyte
 
 Joined: 30 Jul 2002 Posts: 63
  
  | 
		  
		    
			  
				If your program does MQGET with MQGMO-SYNCPOINT option then any abend before MQCommit should rollback the message. 
 
 
This is one of the basic MQSeries feature, Can you post your code in the forum. Particularily, wud like to know the GMO you set before MQGET and the place of abend. | 
			   
			 
		   | 
		
		
		  | Back to top | 
		  
		  	
		   | 
		
		
		    | 
		
		
		  | tjfunny1 | 
		  
		    
			  
				 Posted: Fri Aug 09, 2002 1:54 pm    Post subject:  | 
				     | 
			   
			 
		   | 
		
		
		    Apprentice
 
 Joined: 17 Jun 2002 Posts: 35 Location: Atlanta 
  | 
		  
		    
			  
				the gmo options are shown above
 
 
   
	| Quote: | 
   
  
	| mqgmo-syncpoint + mqgmo-convert+ mqgmo-fail-if-quiescing  | 
   
 
 _________________ TJ
 
IBM Certified System Administrator Websphere MQ v5.3 | 
			   
			 
		   | 
		
		
		  | Back to top | 
		  
		  	
		   | 
		
		
		    | 
		
		
		  | sgopal | 
		  
		    
			  
				 Posted: Fri Aug 09, 2002 4:09 pm    Post subject:  | 
				     | 
			   
			 
		   | 
		
		
		   Acolyte
 
 Joined: 30 Jul 2002 Posts: 63
  
  | 
		  
		    
			  
				I dont see any problem in GMO options and your program logic..
 
 
It looks to be a bug in your code only..
 
 
Post your complete source code or mail it to my email add... | 
			   
			 
		   | 
		
		
		  | Back to top | 
		  
		  	
		   | 
		
		
		    | 
		
		
		  | tjfunny1 | 
		  
		    
			  
				 Posted: Mon Aug 12, 2002 5:26 am    Post subject: code | 
				     | 
			   
			 
		   | 
		
		
		    Apprentice
 
 Joined: 17 Jun 2002 Posts: 35 Location: Atlanta 
  | 
		  
		    
			  
				here is the cobol source (has options for browsing)    
 
NOTE: the 8 )  converts to     for some reason in the code below
 
   
	| Quote: | 
   
  
	
 
000300* ------------------------------------------------------------- *
 
000400 IDENTIFICATION DIVISION.                                        
 
000500* ------------------------------------------------------------- *
 
000600 PROGRAM-ID. MQGETWRT.                                           
 
000700*REMARKS                                                         
 
000800*****************************************************************
 
001800*  MODULE NAME      : MQGETWRT                                  *
 
001900*                                                               *
 
002000*  Environment      : MVS Batch; COBOL II                       *
 
002100*                                                               *
 
002200*  Description : Sample program to get a number of messages     *
 
002300*                FROM A QUEUE AND WRITE INTO A DATASET          *
 
002400*                                                               *
 
002500*  Notes       : The maximum message length is 65536. Messages  *
 
002600*                greater than this will not cause an error but  *
 
002700*                will be truncated.                             *
 
002800*                The syncpoint option is ignored when browsing. *
 
002900*                                                               *
 
009700*****************************************************************
 
009800* ------------------------------------------------------------- *
 
009900 ENVIRONMENT DIVISION.                                           
 
009910 CONFIGURATION SECTION.                                          
 
009920 SOURCE-COMPUTER. IBM-370.                                       
 
009930 OBJECT-COMPUTER. IBM-370.                                       
 
009940                                                                 
 
009950 INPUT-OUTPUT SECTION.                                           
 
009960 FILE-CONTROL.                                                   
 
009970                                                                 
 
010000     SELECT OUTPUT-FILE                                          
 
010100            ASSIGN TO MQDATAO.                                   
 
010110                                                                 
 
010120* ------------------------------------------------------------- *
 
010200 DATA DIVISION.                                                  
 
010300* ------------------------------------------------------------- *
 
010400 FILE SECTION.                                                   
 
010500* ------------------------------------------------------------- *
 
010530 FD  OUTPUT-FILE                                                 
 
010540     LABEL RECORDS ARE STANDARD                                  
 
010550     RECORD CONTAINS 13296 CHARACTERS                            
 
010560     DATA RECORD IS MQDATAO-REC.                                 
 
010570                                                                 
 
010571 01 MQDATAO-REC                PIC X(13296).                     
 
010580                                                                 
 
010590* ------------------------------------------------------------- *
 
010600 WORKING-STORAGE SECTION.                                        
 
010700* ------------------------------------------------------------- *
 
010800*                                                                
 
010810* COPY-BOOKS                                                     
 
010820  COPY WA999950.                                                 
 
010830  COPY WD999950.                                                 
 
010840  COPY WWG99650.                                                 
 
010850  COPY WW999850.                                                 
 
010860*                                                                
 
010870 01 WS-MQDATAO-REC                PIC X(13296).                  
 
010880*                                                                
 
010900*    W00 - General work fields                                   
 
011000*                                                               
 
011100 01  W00-RETURN-CODE             PIC S9(4) BINARY VALUE ZERO.   
 
011200 01  W00-LOOP                    PIC S9(9) BINARY VALUE 0.      
 
011300 01  W00-NUMGETS                 PIC S9(9) BINARY VALUE 0.      
 
011400 01  W00-ERROR-MESSAGE           PIC X(4  VALUE SPACES.        
 
011500 01  W00-MSGBUFFER.                                             
 
011600   02  W00-MSGBUFFER-ARRAY         PIC X(1) OCCURS 65536 TIMES. 
 
011700 01  W00-MSGLENGTH               PIC S9(9) BINARY VALUE 65536.  
 
011800 01  W00-DATALENGTH              PIC S9(9) BINARY VALUE 0.      
 
011900*                                                               
 
012000*    Parameter variables                                        
 
012100*                                                               
 
012200 01  W00-QMGR                    PIC X(4 .                     
 
012300 01  W00-QNAME                   PIC X(4 .                     
 
012400 01  W00-NUMMSGS-NUM             PIC 9(4) VALUE 0.              
 
012500 01  W00-NUMMSGS                 PIC S9(9) BINARY VALUE 1.      
 
012600 01  W00-BROWSE-GET              PIC X(1) VALUE 'D'.            
 
012700     88 BROWSE-GET      VALUE 'B'.                              
 
012800     88 DESTRUCTIVE-GET VALUE 'D'.                              
 
012900 01  W00-SYNCPOINT               PIC X(1) VALUE ' '.          
 
013000     88 SYNCPOINT       VALUE 'S'.                            
 
013100     88 NO-SYNCPOINT    VALUE 'N'.                            
 
013101                                                              
 
013102 01  W01-PARMS.                                               
 
013110    05  W01-QMGR                    PIC X(4  VALUE 'CSQ1'.   
 
013120    05  W01-QNAME     PIC X(4  VALUE 'GADV.TEST.C.ACTUPD.Q'. 
 
013130    05  W01-NUMMSGS-NUM             PIC 9(4) VALUE 0.         
 
013140    05  W01-NUMMSGS                 PIC S9(9) BINARY VALUE 1. 
 
013151    05  W01-BROWSE-GET              PIC X(1) VALUE 'D'.       
 
013160      88 BROWSE-GET1     VALUE 'B'.                           
 
013170      88 DESTRUCTIV1-GET VALUE 'D'.                           
 
013180    05  W01-SYNCPOINT               PIC X(1) VALUE 'S'.       
 
013190      88 SYNCPOINT1      VALUE 'S'.                           
 
013191      88 NO-SYNCPOINT1   VALUE 'N'.                           
 
013200*                                                             
 
013300*    W03 - API fields                                         
 
013400*                                                             
 
013500 01  W03-HCONN                   PIC S9(9) BINARY VALUE 0.    
 
013600 01  W03-HOBJ                    PIC S9(9) BINARY VALUE 0.      
 
013700 01  W03-OPENOPTIONS             PIC S9(9) BINARY.              
 
013800 01  W03-COMPCODE                PIC S9(9) BINARY.              
 
013900 01  W03-REASON                  PIC S9(9) BINARY.              
 
014000*                                                               
 
014100*    API control blocks                                         
 
014200*                                                               
 
014300 01  MQM-OBJECT-DESCRIPTOR.                                     
 
014400     COPY CMQODV.                                               
 
014500 01  MQM-MESSAGE-DESCRIPTOR.                                    
 
014600     COPY CMQMDV.                                               
 
014700 01  MQM-GET-MESSAGE-OPTIONS.                                   
 
014800     COPY CMQGMOV.                                              
 
014900*                                                               
 
015000*    MQV contains constants (for filling in the control blocks) 
 
015100*    and return codes (for testing the result of a call)        
 
015200*                                                               
 
015300 01  MQM-CONSTANTS.                                             
 
015400     COPY CMQV SUPPRESS.                                        
 
015500*                                                                 
 
015600*                                                                 
 
015700* ------------------------------------------------------------- * 
 
015800 LINKAGE SECTION.                                                 
 
015900* ------------------------------------------------------------- * 
 
016000 01  PARMDATA.                                                    
 
016100     05  PARM-LEN                PIC S9(03) BINARY.               
 
016200     05  PARM-STRING             PIC X(100).                      
 
016300*                                                                 
 
016400     EJECT                                                        
 
016500* ------------------------------------------------------------- * 
 
016600 PROCEDURE DIVISION USING PARMDATA.                               
 
016700* ------------------------------------------------------------- * 
 
016800* ------------------------------------------------------------- * 
 
016900 A-MAIN SECTION.                                                  
 
017000* ------------------------------------------------------------- * 
 
017100*                                                                 
 
017200*    If no parameters passed to program then display              
 
017300*    error message and exit                                       
 
017400     MOVE LENGTH OF W01-PARMS TO PARM-LEN                       
 
017410                                                                
 
017500     IF PARM-LEN = 0 THEN                                       
 
017600        PERFORM USAGE-ERROR                                     
 
017700        MOVE 8 TO W00-RETURN-CODE                               
 
017800        GO TO A-MAIN-END                                        
 
017900     END-IF.                                                    
 
018000*                                                               
 
018100*    Move parameters into corresponding variables               
 
018200*                                                               
 
018210     OPEN OUTPUT OUTPUT-FILE.                                   
 
018220                                                                
 
018300     UNSTRING PARM-STRING DELIMITED BY ALL ','                  
 
018400                  INTO W00-QMGR                                 
 
018500                       W00-QNAME                                
 
018600                       W00-NUMMSGS-NUM                          
 
018700                       W00-BROWSE-GET                           
 
018800                       W00-SYNCPOINT.                           
 
018900     MOVE W00-NUMMSGS-NUM   TO W00-NUMMSGS.                     
 
018910                                                           
 
018911     MOVE W01-QMGR         TO  W00-QMGR                    
 
018912     MOVE W01-QNAME        TO  W00-QNAME                   
 
018913     MOVE W01-NUMMSGS-NUM  TO  W00-NUMMSGS-NUM             
 
018920     MOVE W01-BROWSE-GET   TO  W00-BROWSE-GET              
 
018930     MOVE W01-SYNCPOINT    TO  W00-SYNCPOINT.              
 
019000*                                                          
 
019100*    Display parameters to be used in the program          
 
019200*                                                          
 
019300     DISPLAY '==========================================='.
 
019400     DISPLAY 'PARAMETERS PASSED :'.                        
 
019500     DISPLAY '   QMGR        - ', W00-QMGR.                
 
019600     DISPLAY '   QNAME       - ', W00-QNAME.               
 
019700     DISPLAY '   NUMMSGS     - ', W00-NUMMSGS.             
 
019800     DISPLAY '   GET         - ', W00-BROWSE-GET.          
 
019900     DISPLAY '   SYNCPOINT   - ', W00-SYNCPOINT.           
 
020000     DISPLAY '==========================================='.
 
020100*                                                          
 
020200*                                                          
 
020300*                                                             
 
020400*    Connect to the queue manager                             
 
020500*                                                             
 
020600     CALL 'MQCONN' USING W00-QMGR                             
 
020700                         W03-HCONN                            
 
020800                         W03-COMPCODE                         
 
020900                         W03-REASON.                          
 
021000*                                                             
 
021100*    If connection failed then display error message and exit 
 
021200*                                                             
 
021300     IF (W03-COMPCODE NOT = MQCC-OK) THEN                     
 
021400        MOVE 'MQCONN'   TO W00-ERROR-MESSAGE                  
 
021500        PERFORM DISPLAY-ERROR-MESSAGE                         
 
021600        MOVE W03-REASON TO W00-RETURN-CODE                    
 
021700        GO TO A-MAIN-END                                      
 
021800     END-IF.                                                  
 
021900     DISPLAY 'MQCONN SUCCESSFUL'.                             
 
022000*                                                             
 
022100*                                                             
 
022200*    Open the queue for input shared and browse          
 
022300*                                                        
 
022400     COMPUTE W03-OPENOPTIONS = MQOO-INPUT-SHARED +       
 
022500                               MQOO-BROWSE.              
 
022600     MOVE W00-QNAME   TO MQOD-OBJECTNAME.                
 
022700*                                                        
 
022800     CALL 'MQOPEN' USING W03-HCONN                       
 
022900                         MQOD                            
 
023000                         W03-OPENOPTIONS                 
 
023100                         W03-HOBJ                        
 
023200                         W03-COMPCODE                    
 
023300                         W03-REASON.                     
 
023400*                                                        
 
023500*    If open failed display error message and exit       
 
023600*                                                        
 
023700     IF (W03-COMPCODE NOT = MQCC-OK) THEN                
 
023800        MOVE 'MQOPEN'   TO W00-ERROR-MESSAGE             
 
023900        PERFORM DISPLAY-ERROR-MESSAGE                    
 
024000        MOVE W03-REASON TO W00-RETURN-CODE               
 
024100        GO TO A-MAIN-DISCONNECT                         
 
024200     END-IF.                                            
 
024300*    DISPLAY 'MQOPEN SUCCESSFUL'.                       
 
024400*                                                       
 
024500*                                                       
 
024600*    Setup MQGMO-OPTIONS depending on parameters passed 
 
024700*    into program                                       
 
024800*                                                       
 
025020** testing 08/07                                        
 
025024     COMPUTE MQGMO-OPTIONS = MQGMO-NO-WAIT +                
 
025025                             MQGMO-ACCEPT-TRUNCATED-MSG +   
 
025030                             MQGMO-SYNCPOINT +              
 
025031                             MQGMO-CONVERT +                
 
025033                             MQGMO-FAIL-IF-QUIESCING.       
 
025060                                                            
 
025600*                                                           
 
025700     IF BROWSE-GET THEN                                     
 
025800        ADD MQGMO-BROWSE-FIRST TO MQGMO-OPTIONS             
 
025900     END-IF.                                                
 
026300*                                                           
 
026310     MOVE 3 TO W00-NUMMSGS.                                 
 
026320                                                            
 
026400     PERFORM WITH TEST BEFORE VARYING W00-LOOP FROM 0 BY 1  
 
026500         UNTIL (W00-LOOP >= W00-NUMMSGS)                    
 
026600*                                                           
 
026700         MOVE MQMI-NONE TO MQMD-MSGID                       
 
026800         MOVE MQCI-NONE TO MQMD-CORRELID                    
 
026900*                                                               
 
027000         CALL 'MQGET' USING W03-HCONN                           
 
027100                            W03-HOBJ                            
 
027200                            MQMD                                
 
027300                            MQGMO                               
 
027400                            W00-MSGLENGTH                       
 
027500                            W00-MSGBUFFER                       
 
027600                            W00-DATALENGTH                      
 
027700                            W03-COMPCODE                        
 
027800                            W03-REASON                          
 
027900*                                                               
 
028000*    If get failed then display error message and               
 
028100*    break out of the loop.                                     
 
028200*    Otherwise display the message received                     
 
028300*                                                               
 
028400         IF (W03-COMPCODE NOT = MQCC-OK) AND                    
 
028500            (W03-REASON NOT = MQRC-TRUNCATED-MSG-ACCEPTED) THEN 
 
028600            MOVE 'MQGET'     TO W00-ERROR-MESSAGE               
 
028700            PERFORM DISPLAY-ERROR-MESSAGE                       
 
028800            MOVE W00-NUMMSGS TO W00-LOOP                       
 
028900            MOVE W03-REASON  TO W00-RETURN-CODE                
 
029000         ELSE                                                  
 
029100            IF W03-REASON = MQRC-TRUNCATED-MSG-ACCEPTED THEN   
 
029410                    continue                                   
 
029500            ELSE                                               
 
029510               MOVE W00-MSGBUFFER TO WS-MQDATAO-REC            
 
029520               WRITE MQDATAO-REC FROM WS-MQDATAO-REC           
 
029530                                                               
 
029710                    continue                                   
 
029800            END-IF                                             
 
029900            ADD 1 TO W00-NUMGETS                               
 
030000         END-IF                                                
 
030100*                                                              
 
030200*    If browsing the queue then change the                     
 
030300*    MQGMO browse options                                      
 
030400*                                                              
 
030500         IF (W00-LOOP = 0) AND BROWSE-GET THEN                 
 
030600            SUBTRACT MQGMO-BROWSE-FIRST FROM MQGMO-OPTIONS     
 
030700            ADD      MQGMO-BROWSE-NEXT  TO   MQGMO-OPTIONS     
 
030800         END-IF                                                
 
030900*                                                              
 
031000     END-PERFORM.                                              
 
031100*                                                              
 
031200*    Display the number of messages successfully got           
 
031300*    from the queue.                                           
 
031400*                                                              
 
031500*    DISPLAY W00-NUMGETS, ' MESSAGES GOT FROM QUEUE'.          
 
031600*                                                              
 
031700*                                                              
 
031800*    If program started with syncpoint and destructive get     
 
031900*    selected then execute syncpoint                           
 
032000*                                                              
 
032110     IF SYNCPOINT                     THEN                     
 
032200        CALL 'MQCMIT' USING W03-HCONN                          
 
032300                            W03-COMPCODE                       
 
032400                            W03-REASON                         
 
032500        IF (W03-COMPCODE NOT = MQCC-OK) THEN                   
 
032600           MOVE 'MQCMIT'   TO W00-ERROR-MESSAGE          
 
032700           PERFORM DISPLAY-ERROR-MESSAGE                 
 
032800           MOVE W03-REASON TO W00-RETURN-CODE            
 
032900        ELSE                                             
 
033000*          DISPLAY 'MQCMIT SUCCESSFUL'                   
 
033001                    continue                             
 
033002        END-IF                                           
 
033003      ELSE                                               
 
033004           CALL 'MQBACK' USING W03-HCONN                 
 
033005                               W03-COMPCODE              
 
033006                               W03-REASON                
 
033007           IF (W03-COMPCODE NOT = MQCC-OK) THEN          
 
033008              MOVE 'MQBACK'   TO W00-ERROR-MESSAGE       
 
033009              PERFORM DISPLAY-ERROR-MESSAGE              
 
033010              MOVE W03-REASON TO W00-RETURN-CODE         
 
033020*                   continue                             
 
033030           ELSE                                          
 
033040*              DISPLAY 'MQCMIT SUCCESSFUL'               
 
033050                    continue                             
 
033060           END-IF                                      
 
033200     END-IF.                                           
 
033300*                                                      
 
033400*                                                      
 
033500*    Close the queue                                   
 
033600*                                                      
 
033700     CALL 'MQCLOSE' USING W03-HCONN                    
 
033800                          W03-HOBJ                     
 
033900                          MQCO-NONE                    
 
034000                          W03-COMPCODE                 
 
034100                          W03-REASON.                  
 
034200     IF (W03-COMPCODE NOT = MQCC-OK) THEN              
 
034300        MOVE 'MQCLOSE'  TO W00-ERROR-MESSAGE           
 
034400        PERFORM DISPLAY-ERROR-MESSAGE                  
 
034500        MOVE W03-REASON TO W00-RETURN-CODE             
 
034600     ELSE                                              
 
034700        DISPLAY 'MQCLOSE SUCCESSFUL'                   
 
034710                    continue                           
 
034800     END-IF.                                           
 
035100*                                                       
 
035200 A-MAIN-DISCONNECT.                                     
 
035300*                                                       
 
035400*    Disconnect from the queue manager                  
 
035500*                                                       
 
035510     CLOSE OUTPUT-FILE.                                 
 
035600     CALL 'MQDISC' USING W03-HCONN                      
 
035700                         W03-COMPCODE                   
 
035800                         W03-REASON.                    
 
035900     IF (W03-COMPCODE NOT = MQCC-OK) THEN               
 
036000        MOVE 'MQDISC'   TO W00-ERROR-MESSAGE            
 
036100        PERFORM DISPLAY-ERROR-MESSAGE                   
 
036200        MOVE W03-REASON TO W00-RETURN-CODE              
 
036300     ELSE                                               
 
036400        DISPLAY 'MQDISC SUCCESSFUL'                     
 
036410                    continue                            
 
036500     END-IF.                                            
 
036700 A-MAIN-END.                                                      
 
036800*                                                                 
 
036900*                                                                 
 
037000     MOVE W00-RETURN-CODE TO RETURN-CODE                          
 
037100     STOP RUN.                                                    
 
037200*                                                                 
 
037300* ------------------------------------------------------------- * 
 
037400 USAGE-ERROR SECTION.                                             
 
037500* ------------------------------------------------------------- * 
 
037600*                                                                 
 
037700     DISPLAY '==================================================' 
 
037800     DISPLAY 'PARAMETERS FOR PROGRAM :'.                          
 
037900     DISPLAY '     QMGR       - QUEUE MANGER'.                    
 
038000     DISPLAY '     QNAME      - QUEUE NAME'.                      
 
038100     DISPLAY '     NUMMSGS    - NUMBER OF MESSAGES'.              
 
038200     DISPLAY '     GET        - (B)ROWSE / (D)ESTRUCTIVE GET'.    
 
038300     DISPLAY '     SYNCPOINT  - (N)O / (S)YNCPOINT'.              
 
038400     DISPLAY '=================================================='.
 
038500*                                                                
 
038600 USAGE-ERROR-END.                                                
 
038700*                                                                
 
038800*    RETURN TO PERFORMING FUNCTION                               
 
038900*                                                                
 
039000     EXIT.                                                       
 
039100*                                                                
 
039200* ------------------------------------------------------------- *
 
039300 DISPLAY-ERROR-MESSAGE SECTION.                                  
 
039400* ------------------------------------------------------------- *
 
039500*                                                                
 
039600     DISPLAY '************************************************'. 
 
039700     DISPLAY '* ', W00-ERROR-MESSAGE.                            
 
039800     DISPLAY '* COMPLETION CODE : ', W03-COMPCODE.               
 
039900     DISPLAY '* REASON CODE     : ', W03-REASON.                 
 
040000     DISPLAY '************************************************'. 
 
040100*                                                                
 
040200 DISPLAY-ERROR-MESSAGE-END.                                      
 
040400*    RETURN TO PERFORMING FUNCTION                                
 
040500*                                                                 
 
040600     EXIT.                                                        
 
040700*                                                                 
 
040710  ABEND ROUTINE                                                   
 
040720* -------------                                                   
 
040730*S999-000-SYSTEM-ABORT SECTION.                                   
 
040731* ABEND ROUTINE                                                   
 
040732* -------------                                                   
 
040733*S999-000-SYSTEM-ABORT SECTION.                                   
 
040734*                                                                 
 
040735*                    COPY S9996.                                  
 
040740*                                                                 
 
040800* ------------------------------------------------------------- * 
 
040900*                        END OF PROGRAM                           
 
041000* ------------------------------------------------------------- * 
 
 | 
   
 
 | 
			   
			 
		   | 
		
		
		  | Back to top | 
		  
		  	
		   | 
		
		
		    | 
		
		
		  | tjfunny1 | 
		  
		    
			  
				 Posted: Mon Aug 12, 2002 5:32 am    Post subject: footnote to above code | 
				     | 
			   
			 
		   | 
		
		
		    Apprentice
 
 Joined: 17 Jun 2002 Posts: 35 Location: Atlanta 
  | 
		  
		    
			  
				we added the following code to cause a S0CB abend:
 
WTT-TEST = 0  (thus divide by zero error)
 
   
	| Quote: | 
   
  
	002700*                                                   
 
002710      IF W00-LOOP  = 4                              
 
002720      COMPUTE WTT1-TEST = W00-NUMMSGS/WTT-TEST      
 
002730                                                    
 
002740      END-IF                                        
 
 | 
   
 
 | 
			   
			 
		   | 
		
		
		  | Back to top | 
		  
		  	
		   | 
		
		
		    | 
		
		
		  | oz1ccg | 
		  
		    
			  
				 Posted: Mon Aug 12, 2002 6:01 am    Post subject:  | 
				     | 
			   
			 
		   | 
		
		
		    Yatiri
 
 Joined: 10 Feb 2002 Posts: 628 Location: Denmark 
  | 
		  
		    
		   | 
		
		
		  | Back to top | 
		  
		  	
		   | 
		
		
		    | 
		
		
		  | bob_buxton | 
		  
		    
			  
				 Posted: Mon Aug 12, 2002 7:20 am    Post subject:  | 
				     | 
			   
			 
		   | 
		
		
		    Master
 
 Joined: 23 Aug 2001 Posts: 266 Location: England 
  | 
		  
		    
			  
				I think you need to check the 'Disable Smilies in this post'  box to avoid your cobol code x(48) turning into a smiley character. _________________ Bob Buxton
 
Ex-Websphere MQ Development | 
			   
			 
		   | 
		
		
		  | Back to top | 
		  
		  	
		   | 
		
		
		    | 
		
		
		  | tjfunny1 | 
		  
		    
			  
				 Posted: Thu Aug 15, 2002 1:30 pm    Post subject: Solution found | 
				     | 
			   
			 
		   | 
		
		
		    Apprentice
 
 Joined: 17 Jun 2002 Posts: 35 Location: Atlanta 
  | 
		  
		    
			  
				Thanks to all, we found the developer had a JCL problem and a logic problem (see above). 
 
 
To test the syncpoint, I created a client app from Windows that set Syncpoint. I added a routine to do a memset with an invalid size, which abended/halted the program. (I left out the MQCMIT call on purpose). My program ran as advertised, and the messages rolled back. 
 
 
We also discovered that the developer was using Xpediter (CA) debug tool to walkthru the code. It seems the Xpediter will issue a graceful disconnect from MQ (thus causing an explicit commit). 
 
 
Anyone ever seen this issue with Xpediter before?
 
TJ | 
			   
			 
		   | 
		
		
		  | Back to top | 
		  
		  	
		   | 
		
		
		    | 
		
		
		  | oz1ccg | 
		  
		    
			  
				 Posted: Fri Aug 16, 2002 2:02 am    Post subject:  | 
				     | 
			   
			 
		   | 
		
		
		    Yatiri
 
 Joined: 10 Feb 2002 Posts: 628 Location: Denmark 
  | 
		  
		    
			  
				I've tried the program, and it work perfectly under OS/390 v.2.9 using Language Environment(LE). If the program abends the messages stays on the queue. Yes it's required that the program abends!      
 
As stated earlier the behavior depends on LE configuration.
 
 
 
About Xpediter: Yes, and it's even documented....
 
 
For Xpediter/TSO it's found in the HELP EXIT:
 
   
	| Code: | 
   
  
	EXIT                                                                          
 
                                                                              
 
The EXIT command terminates the current test session.  The EXIT               
 
command closes all files and returns you to the appropriate test              
 
screen.  It is allowed from any screen and from any point in a test.          
 
A record of the command is written to the log.                                
 
                                                                              
 
If the EXIT command is omitted when testing in unattended batch mode,         
 
XPEDITER/TSO determines the end of the test by recognizing either a           
 
new TEST or INTERCEPT command in the BTS environment.  When the job           
 
consists of a single test and the EXIT command is omitted, the last           
 
XPEDITER/TSO command determines the end of the test.                          
 
                                                                              
 
+--- EXIT PRIMARY COMMAND SYNTAX --------------------------------------------+
 
!                                                                            !
 
! >>--EXIT--.-------.--.--------------.----><                                !
 
!           ! ABEND !  ! -abend code- !                                      !
 
!                                                                            !
 
+----------------------------------------------------------------------------+
 
 GENERAL USAGE NOTES                                                     
 
                                                                         
 
 1.  EXIT is usually assigned to PF4/16.                                 
 
                                                                         
 
 2.  When testing in interactive mode with ISPF support, the EXIT        
 
     command returns you to the XPEDITER/TSO Test Menu.  The following   
 
     message is reported in the upper right corner:                      
 
                                                                         
 
         Log & Script Created                                            
 
                                                                         
 
     Refer to the section on ISPF support in the XPEDITER/TSO and        
 
     XPEDITER/IMS PL/I User's Guide, COBOL User's Guide, or Assembler    
 
     User's Guide for further details regarding the disposition of       
 
     log and script datasets.                                            
 
                                                                         
 
 3.  Use the RETEST command within a test session instead of the EXIT    
 
     command to load a fresh copy of the load module before starting     
 
     the next test.  Refer to the "RETEST" command in the current        
 
     combined XPEDITER/TSO REFERENCE manual for additional               
 
     information on the use of the RETEST command in interactive         
 
     testing.                                                            
 
                                                                         
 
 4.  Unlike other databases, DB2 databases tested in the IMS/DB          
 
     environment are not committed when the EXIT command is issued.  To  
 
     commit these DB2 databases on test completion, use the GO command.       
 
                                                                              
 
 5.  The keword ABEND can be added to the command. This will cause            
 
     XPEDITER to terminate the current test session with an abend.            
 
     Optionally, an abend code can be specified. The abend code must be       
 
     in the form of Sxxx or Uxxxx, where xxx or xxxx is the                   
 
     abend code.                                                              
 
                                                                              
 
                                                                              
 
 COBOL SPECIFIC USAGE NOTE                                                    
 
                                                                              
 
 1.  Terminating a test session with the EXIT command while INTERNAL          
 
     SORT is active can result in a "system abend".  To prevent this          
 
     problem, sort activities must be terminated before you exit the          
 
     user program.  To terminate a SORT, complete the following:              
 
                                                                              
 
         MOVE 16 TO SORT-RETURN                                               
 
         GO 1                                                                 
 
         GOTO <RELEASE statement number>  or  GOTO <RETURN statement number>  
 
              (depending on whether the SORT is active in the INPUT           
 
               procedure or the OUTPUT procedure)                             
 
         GO 1 (Enter GO 1 until you are out of the INPUT or OUTPUT            
 
               procedure depending on where the SORT is active.               
 
               You should be at statement after the SORT.)                    
 
 | 
   
 
                                                                              
 
 
Expediter/CICS just abeds your transaction if you're leaving Xpediter.
 
 
I hope it might help you.....  a bit offtopic.
 
 
Just my $0.02    _________________ Regards, Jørgen
 
Home of BlockIP2, the last free MQ Security exit  ver. 3.00
 
Cert. on WMQ, WBIMB, SWIFT. | 
			   
			 
		   | 
		
		
		  | Back to top | 
		  
		  	
		   | 
		
		
		    | 
		
		
		  | tjfunny1 | 
		  
		    
			  
				 Posted: Fri Aug 16, 2002 4:13 am    Post subject: JCL | 
				     | 
			   
			 
		   | 
		
		
		    Apprentice
 
 Joined: 17 Jun 2002 Posts: 35 Location: Atlanta 
  | 
		  
		    
			  
				Jorgen,
 
Could you post your JCL (leaving out your userid).  I would like to compare it to ours.
 
 
Thanks,
 
TJ | 
			   
			 
		   | 
		
		
		  | Back to top | 
		  
		  	
		   | 
		
		
		    | 
		
		
		  | oz1ccg | 
		  
		    
			  
				 Posted: Fri Aug 16, 2002 6:00 am    Post subject:  | 
				     | 
			   
			 
		   | 
		
		
		    Yatiri
 
 Joined: 10 Feb 2002 Posts: 628 Location: Denmark 
  | 
		  
		    
			  
				That's no problem:
 
   
	| Code: | 
   
  
	//ABTEST EXEC PGM=<progname>
 
//STEPLIB  DD DISP=SHR,DSN=SYSA.<qmgr>.PARMLOAD       
 
//         DD DISP=SHR,DSN=<project>.LOAD          
 
//SYSPRINT DD SYSOUT=*                              
 
//MQDATAO  DD SYSOUT=*                               | 
   
 
 
 
I changed the program a bit, because I didn't have the copybooks, and incoperated the abend lines. Thats all.
 
 
There are nothing here in my JCL, the reason for including PARMLOAD, is I'm using default QMGR.
 
 
Just my $0.02    _________________ Regards, Jørgen
 
Home of BlockIP2, the last free MQ Security exit  ver. 3.00
 
Cert. on WMQ, WBIMB, SWIFT. | 
			   
			 
		   | 
		
		
		  | Back to top | 
		  
		  	
		   | 
		
		
		    | 
		
		
		  | tjfunny1 | 
		  
		    
			  
				 Posted: Fri Aug 16, 2002 6:51 am    Post subject: PARMs | 
				     | 
			   
			 
		   | 
		
		
		    Apprentice
 
 Joined: 17 Jun 2002 Posts: 35 Location: Atlanta 
  | 
		  
		    
			  
				one thing about the JCL, you can pass parameters to it
 
 
PARM=(Qmgr,Queue)
 
 
Otherwise, it will connect to the default Qmgr and the SYSTEM.DEFAULT.LOCAL.QUEUE
 
 
TJ | 
			   
			 
		   | 
		
		
		  | Back to top | 
		  
		  	
		   | 
		
		
		    | 
		
		
		  | oz1ccg | 
		  
		    
			  
				 Posted: Fri Aug 16, 2002 10:39 pm    Post subject:  | 
				     | 
			   
			 
		   | 
		
		
		    Yatiri
 
 Joined: 10 Feb 2002 Posts: 628 Location: Denmark 
  | 
		  
		    
			  
				Well, that's right. I didn't spend many seconds studying the program, I just checked if the flow was ok.
 
 
The eliminate the copy books, change queue names, compile and run.
 
 
I've tried it with and without syncpoint option, same result rollback on abend (because the MQGMO allways set MQGMO-SYNCPOINT. But as I said very early in this thread, I would bet on a bad LE setting, this problem is not limited to MQSeries, this problem must also exists in DB2. Have you tried it there ? Do some updates, deletes, inserts etc. without commit and then abned your program, so it shoukd do a roll back.
 
 
Just my $0.02    _________________ Regards, Jørgen
 
Home of BlockIP2, the last free MQ Security exit  ver. 3.00
 
Cert. on WMQ, WBIMB, SWIFT. | 
			   
			 
		   | 
		
		
		  | Back to top | 
		  
		  	
		   | 
		
		
		    | 
		
		
		  | oz1ccg | 
		  
		    
			  
				 Posted: Mon Aug 19, 2002 4:04 am    Post subject:  | 
				     | 
			   
			 
		   | 
		
		
		    Yatiri
 
 Joined: 10 Feb 2002 Posts: 628 Location: Denmark 
  | 
		  
		    
			  
				I was looking in some of my personal archives from acient times(converting to LE) and found some usefull information (I guess everybody other than me remembers    ):
 
 
We can overwrite LE options on the EXEC statement:
 
 
   
	| Code: | 
   
  
	//ABTEST EXEC PGM=<progname>,
 
//  PARM='//RPTOPTS(ON),ABTERMENC(ABEND)'
 
//STEPLIB  DD DISP=SHR,DSN=SYSA.<qmgr>.PARMLOAD        
 
//         DD DISP=SHR,DSN=<project>.LOAD          
 
//SYSPRINT DD SYSOUT=*                              
 
//MQDATAO  DD SYSOUT=*    | 
   
 
 
 
It might require minor chanes in the application program to allow the LE runtime overwrite options Remember the two slashes//.
 
 
When using RPTOPTS, LE reports options used.
 
ABTERMENC(ABEND), tells LE to abend insted of issueing default rc=3000.
 
 
Just my $0.02    _________________ Regards, Jørgen
 
Home of BlockIP2, the last free MQ Security exit  ver. 3.00
 
Cert. on WMQ, WBIMB, SWIFT. | 
			   
			 
		   | 
		
		
		  | Back to top | 
		  
		  	
		   | 
		
		
		    | 
		
		
		  | 
		    
		   |