ibmi-brunch-learn

Announcement

Collapse
No announcement yet.

Did the Condition Handler Run?

Collapse
X
 
  • Filter
  • Time
  • Show
Clear All
new posts

  • Did the Condition Handler Run?

    I finally figured out how to make a COBOL program register a condition handler. The code runs, but it doesn't do what I want it to do. Please tell me if I am overlooking something.

    Here's the module that registers the handler:

    Code:
    Identification division.
    Program-ID. QAD02910L.
    
    Environment division.
    Configuration section.
    Special-names.
        Linkage SYS       for "CEEHDLR"
        Linkage procedure for "MONMSGHDLR".
    
    Data division.
    Working-storage section.
    01  procPtr             procedure-pointer.
    01  pErrHdlr_UserData   pointer.
    01  errhdlr_UserData    pic x(4).
    01  fc                  pic x(12) value low-value.
    
    Procedure division.
    
    Main-process.
           set procPtr to entry "MONMSGHDLR"
           move "xxxx" to errhdlr_UserData
           set pErrHdlr_UserData to address of errhdlr_UserData
           call "CEEHDLR" using procPtr, pErrhdlr_UserData, fc
           call "PROOF1"
    	   goback.
    There is no program called PROOF1. The condition handler kicks in and sets a status code to "10" (resume).

    Code:
    IDENTIFICATION DIVISION.
    PROGRAM-ID. MonmsgHdlr.
    
    DATA DIVISION.
    WORKING-STORAGE SECTION.
    01 MSG PIC X(128).
    LINKAGE SECTION.
    01 CURR-TOKEN PIC X(12).
    01 TOKEN-PTR PIC S9(9) BINARY.
    01 RC PIC S9(9) BINARY.
    01 NEW-TOKEN PIC X(12).
    
    PROCEDURE DIVISION USING CURR-TOKEN, TOKEN-PTR, RC, NEW-TOKEN.
    PROC-DIV SECTION.
    MAIN-001.
         DISPLAY "MonmsgHandler is active...".
         MOVE 10 TO RC.
         MOVE "*OMIT" TO NEW-TOKEN.
    MAIN-END.
         EXIT PROGRAM.
    AFAIK, there is no way for the first module to know (at the point of the goback) whether the handler kicked in or not. The only think I can think of is to have the condition handler update something external (a database file, a data area, an environment variable, etc.) that the first module could test. That would slow down the program immensely.

    Am I missing something?

  • #2
    Re: Did the Condition Handler Run?

    Isn't that what pErrHdlr_UserData is for, so that data can be passed between the handler and the main program?

    Comment


    • #3
      Re: Did the Condition Handler Run?

      Originally posted by TedHolt
      AFAIK, there is no way for the first module to know (at the point of the goback) whether the handler kicked in or not. The only think I can think of is to have the condition handler update something external (a database file, a data area, an environment variable, etc.) that the first module could test. That would slow down the program immensely.

      Am I missing something?
      I was reminded of this post and figured I'd add a thought. Since both modules are COBOL, you might try adding a WS item to both. An example item might be:
      Code:
          01  extComm             pic x(10) external.
      I figure you'll catch on to that quickly. And I suppose other forms of external or "exported" data items might be useful if no other suggestions come up.

      For me, a difficult part is your concern over performance. Is that primarily a concern over accessing an external object?
      Tom

      There are only two hard things in Computer Science: cache invalidation, naming things and off-by-one errors.

      Why is it that all of the instruments seeking intelligent life in the universe are pointed away from Earth?

      Comment


      • #4
        Re: Did the Condition Handler Run?

        Thanks for your comments, fellows. I got to thinking about what UserName10 said and here's what I came up with. It works, but I'm afraid there's some danger in the code that I'm not aware of.

        I set Condition-data to zero before calling PROOF1. If PROOF1 exists, Condition-data remains at zero. If PROOF1 does not exist, CBLHANDLE runs and changes Condition-data to one. I have not tried to trap any other types of errors with this code.

        I think I can use this for now, but I'm going to have to continue to understand condition handlers. Does anybody see any problem with this approach?

        Code:
        Identification division.                               
        Program-ID. QAD02912L.                                 
                                                               
        Environment division.                                  
        Configuration section.                                 
        Special-names.                                         
            Linkage SYS       for "CEEHDLR"                    
            Linkage procedure for "CBLHANDLE".                 
                                                               
        Data division.                                         
        Working-storage section.                               
        01  procPtr             procedure-pointer.             
        01  pCondition-data     pointer.                       
        01  Condition-data      pic x.                         
            88  Condition-was-raised       value "1".          
            88  No-raised-condition        value "0".          
        01  Feedback-code       pic x(12) value low-value.     
                                                               
        Procedure division.                                    
                                                               
        Main-process.                                          
               set procPtr to entry "CBLHANDLE"                
               set pCondition-data to address of Condition-data
               call "CEEHDLR" using procPtr, pCondition-data,  
                                    Feedback-code
                                                 
               set No-raised-condition to true   
               call "PROOF1"                     
               if Condition-was-raised           
                  ************* do whatever to handle the error ********************
               else                              
                  ************* do whatever when no error occurred *****************
               end-if                            
               goback.
        Code:
        Identification division.                                       
        Program-ID. CblHandle.                                         
                                                                       
        Data division.                                                 
        Linkage section.                                               
        01 LS-Current-condition      pic x(12).                        
        01 LS-Token-address                    pointer.                
        01 LS-Return-code            pic s9(9) binary.                 
        01 LS-New-condition          pic x(12).                        
                                                                       
        01 LS-Token                  pic x.                            
                                                                       
        Procedure division using LS-Current-condition, LS-Token-address
                                 LS-Return-code, LS-New-condition.     
        Main.                                                          
             set address of LS-Token to LS-Token-address               
             move 10  to LS-return-code                                
             move "1" to LS-Token                                      
             exit program.

        Comment

        Working...
        X