Skip to main content

[archive] Accept Event On Exception?

  • October 31, 2007
  • 5 replies
  • 0 views

[Migrated content. Thread originally posted on 29 October 2007]

Has anyone used this phrase before? I could use some help with the syntax.

I've got a COM object that handles all UI and I want the program to remain in Accept mode until something in the code forces it to end.

I'm currently using the following code snippet, which works but causes the object to lose focus every 10 seconds (as the ACCEPT EVENT loop cycles).

Display-Menu.
    CREATE MenuObject
               HANDLE IN MENU-HANDLE
               EVENT PROCEDURE Menu-Events.
    MOVE "N" TO CLOSE-OBJECT, RUN-SOMETHING.
    PERFORM UNTIL CLOSE-OBJECT = "Y"
         ACCEPT EVENT BEFORE TIME 1000 END-ACCEPT
         IF RUN-SOMETHING = "Y"
           MOVE "N" TO RUN-SOMETHING
           PERFORM Execute-Selection
         END-IF
    END-PERFORM.
    DESTROY MENU-HANDLE.

Menu-Events.
    IF EVENT-TYPE = MSG-AX-EVENT
      EVALUATE EVENT-DATA-2
          WHEN MenuItemClick
              MOVE "Y" TO RUN-SOMETHING
          WHEN MenuLogout
              MOVE "Y" TO CLOSE-OBJECT
          WHEN MenuRefresh
              PERFORM Reload-Menu   
      END-EVALUATE.



I'm thinking that using the ON EXCEPTION phrase instead of BEFORE TIME will allow me to control when the ACCEPT EVENT phrase terminates, but I can't figure out how to manage the exception.

Here's a code snippet of what I'd like to do, but I don't know how to control the exception. If I use this code the program hangs.

     01 STOP-ACCEPT                 PIC 999.

     MOVE ZERO TO STOP-ACCEPT.
     PERFORM UNTIL CLOSE-OBJECT = "Y"
         ACCEPT EVENT
              ON EXCEPTION STOP-ACCEPT CONTINUE
         END-ACCEPT
         IF RUN-SOMETHING = "Y"
           MOVE "N" TO RUN-SOMETHING
           PERFORM Execute-Selection
         END-IF
    END-PERFORM.
    DESTROY MENU-HANDLE.

Menu-Events.
    IF EVENT-TYPE = MSG-AX-EVENT
      EVALUATE EVENT-DATA-2
          WHEN MenuItemClick
              MOVE "Y" TO RUN-SOMETHING
              MOVE 27 TO STOP-ACCEPT
          WHEN MenuLogout
              MOVE "Y" TO CLOSE-OBJECT
              MOVE 27 TO STOP-ACCEPT
          WHEN MenuRefresh
              PERFORM Reload-Menu   
      END-EVALUATE.


I can't find any examples of this syntax in the documentation or on the AcuCorp website or forum. Can anyone provide an example of how this can be done?

Thanks!
Laura

5 replies

[Migrated content. Thread originally posted on 29 October 2007]

Has anyone used this phrase before? I could use some help with the syntax.

I've got a COM object that handles all UI and I want the program to remain in Accept mode until something in the code forces it to end.

I'm currently using the following code snippet, which works but causes the object to lose focus every 10 seconds (as the ACCEPT EVENT loop cycles).

Display-Menu.
    CREATE MenuObject
               HANDLE IN MENU-HANDLE
               EVENT PROCEDURE Menu-Events.
    MOVE "N" TO CLOSE-OBJECT, RUN-SOMETHING.
    PERFORM UNTIL CLOSE-OBJECT = "Y"
         ACCEPT EVENT BEFORE TIME 1000 END-ACCEPT
         IF RUN-SOMETHING = "Y"
           MOVE "N" TO RUN-SOMETHING
           PERFORM Execute-Selection
         END-IF
    END-PERFORM.
    DESTROY MENU-HANDLE.

Menu-Events.
    IF EVENT-TYPE = MSG-AX-EVENT
      EVALUATE EVENT-DATA-2
          WHEN MenuItemClick
              MOVE "Y" TO RUN-SOMETHING
          WHEN MenuLogout
              MOVE "Y" TO CLOSE-OBJECT
          WHEN MenuRefresh
              PERFORM Reload-Menu   
      END-EVALUATE.



I'm thinking that using the ON EXCEPTION phrase instead of BEFORE TIME will allow me to control when the ACCEPT EVENT phrase terminates, but I can't figure out how to manage the exception.

Here's a code snippet of what I'd like to do, but I don't know how to control the exception. If I use this code the program hangs.

     01 STOP-ACCEPT                 PIC 999.

     MOVE ZERO TO STOP-ACCEPT.
     PERFORM UNTIL CLOSE-OBJECT = "Y"
         ACCEPT EVENT
              ON EXCEPTION STOP-ACCEPT CONTINUE
         END-ACCEPT
         IF RUN-SOMETHING = "Y"
           MOVE "N" TO RUN-SOMETHING
           PERFORM Execute-Selection
         END-IF
    END-PERFORM.
    DESTROY MENU-HANDLE.

Menu-Events.
    IF EVENT-TYPE = MSG-AX-EVENT
      EVALUATE EVENT-DATA-2
          WHEN MenuItemClick
              MOVE "Y" TO RUN-SOMETHING
              MOVE 27 TO STOP-ACCEPT
          WHEN MenuLogout
              MOVE "Y" TO CLOSE-OBJECT
              MOVE 27 TO STOP-ACCEPT
          WHEN MenuRefresh
              PERFORM Reload-Menu   
      END-EVALUATE.


I can't find any examples of this syntax in the documentation or on the AcuCorp website or forum. Can anyone provide an example of how this can be done?

Thanks!
Laura
I wasn't able to figure out how to terminate an ACCEPT EVENT statement using the ON EXCEPTION clause. Instead, I'm using ACCEPT OMITTED ON EXCEPTION and using the W$KEYBUF routine to force exception keystrokes in the keyboard input buffer. :D

Here's some sample code:

01 STOP-ACCEPT            PIC 999.
   03 SELECT-KEY           VALUE 100.
   03 LOGOFF-KEY           VALUE 200.

Display-Menu.
    CREATE MenuObject
               HANDLE IN MENU-HANDLE
               EVENT PROCEDURE Menu-Events.
    * Remap the CTRL-T and CTRL-Y keys to match the hard-code exception values
    SET ENVIRONMENT "KEYSTROKE" TO "Exception=100 ^T".
    SET ENVIRONMENT "KEYSTROKE" TO "Exception=200 ^Y".
    MOVE ZERO TO STOP-ACCEPT.
    PERFORM Accept-Menu UNTIL LOGOFF-KEY.
    DESTROY MENU-HANDLE.

Accept-Menu.
    MOVE ZERO TO STOP-ACCEPT.
    ACCEPT OMITTED
          ON EXCEPTION STOP-ACCEPT
              IF SELECT-KEY OR LOGOFF-KEY
                 NEXT SENTENCE
              END-IF
    END-ACCEPT.
    CALL "W$KEYBUF" USING 3.
    IF SELECT-KEY
       PERFORM Execute-Selection.

Menu-Events.
    IF EVENT-TYPE = MSG-AX-EVENT
      EVALUATE EVENT-DATA-2
          WHEN MenuItemClick
              CALL "W$KEYBUF" USING 2, "{^T}"
          WHEN MenuLogout
              CALL "W$KEYBUF" USING 2, "{^Y}"
          WHEN MenuRefresh
              PERFORM Reload-Menu   
      END-EVALUATE.

[Migrated content. Thread originally posted on 29 October 2007]

Has anyone used this phrase before? I could use some help with the syntax.

I've got a COM object that handles all UI and I want the program to remain in Accept mode until something in the code forces it to end.

I'm currently using the following code snippet, which works but causes the object to lose focus every 10 seconds (as the ACCEPT EVENT loop cycles).

Display-Menu.
    CREATE MenuObject
               HANDLE IN MENU-HANDLE
               EVENT PROCEDURE Menu-Events.
    MOVE "N" TO CLOSE-OBJECT, RUN-SOMETHING.
    PERFORM UNTIL CLOSE-OBJECT = "Y"
         ACCEPT EVENT BEFORE TIME 1000 END-ACCEPT
         IF RUN-SOMETHING = "Y"
           MOVE "N" TO RUN-SOMETHING
           PERFORM Execute-Selection
         END-IF
    END-PERFORM.
    DESTROY MENU-HANDLE.

Menu-Events.
    IF EVENT-TYPE = MSG-AX-EVENT
      EVALUATE EVENT-DATA-2
          WHEN MenuItemClick
              MOVE "Y" TO RUN-SOMETHING
          WHEN MenuLogout
              MOVE "Y" TO CLOSE-OBJECT
          WHEN MenuRefresh
              PERFORM Reload-Menu   
      END-EVALUATE.



I'm thinking that using the ON EXCEPTION phrase instead of BEFORE TIME will allow me to control when the ACCEPT EVENT phrase terminates, but I can't figure out how to manage the exception.

Here's a code snippet of what I'd like to do, but I don't know how to control the exception. If I use this code the program hangs.

     01 STOP-ACCEPT                 PIC 999.

     MOVE ZERO TO STOP-ACCEPT.
     PERFORM UNTIL CLOSE-OBJECT = "Y"
         ACCEPT EVENT
              ON EXCEPTION STOP-ACCEPT CONTINUE
         END-ACCEPT
         IF RUN-SOMETHING = "Y"
           MOVE "N" TO RUN-SOMETHING
           PERFORM Execute-Selection
         END-IF
    END-PERFORM.
    DESTROY MENU-HANDLE.

Menu-Events.
    IF EVENT-TYPE = MSG-AX-EVENT
      EVALUATE EVENT-DATA-2
          WHEN MenuItemClick
              MOVE "Y" TO RUN-SOMETHING
              MOVE 27 TO STOP-ACCEPT
          WHEN MenuLogout
              MOVE "Y" TO CLOSE-OBJECT
              MOVE 27 TO STOP-ACCEPT
          WHEN MenuRefresh
              PERFORM Reload-Menu   
      END-EVALUATE.


I can't find any examples of this syntax in the documentation or on the AcuCorp website or forum. Can anyone provide an example of how this can be done?

Thanks!
Laura
I wasn't able to figure out how to terminate an ACCEPT EVENT statement using the ON EXCEPTION clause. Instead, I'm using ACCEPT OMITTED ON EXCEPTION and using the W$KEYBUF routine to force exception keystrokes in the keyboard input buffer. :D

Here's some sample code:

01 STOP-ACCEPT            PIC 999.
   03 SELECT-KEY           VALUE 100.
   03 LOGOFF-KEY           VALUE 200.

Display-Menu.
    CREATE MenuObject
               HANDLE IN MENU-HANDLE
               EVENT PROCEDURE Menu-Events.
    * Remap the CTRL-T and CTRL-Y keys to match the hard-code exception values
    SET ENVIRONMENT "KEYSTROKE" TO "Exception=100 ^T".
    SET ENVIRONMENT "KEYSTROKE" TO "Exception=200 ^Y".
    MOVE ZERO TO STOP-ACCEPT.
    PERFORM Accept-Menu UNTIL LOGOFF-KEY.
    DESTROY MENU-HANDLE.

Accept-Menu.
    MOVE ZERO TO STOP-ACCEPT.
    ACCEPT OMITTED
          ON EXCEPTION STOP-ACCEPT
              IF SELECT-KEY OR LOGOFF-KEY
                 NEXT SENTENCE
              END-IF
    END-ACCEPT.
    CALL "W$KEYBUF" USING 3.
    IF SELECT-KEY
       PERFORM Execute-Selection.

Menu-Events.
    IF EVENT-TYPE = MSG-AX-EVENT
      EVALUATE EVENT-DATA-2
          WHEN MenuItemClick
              CALL "W$KEYBUF" USING 2, "{^T}"
          WHEN MenuLogout
              CALL "W$KEYBUF" USING 2, "{^Y}"
          WHEN MenuRefresh
              PERFORM Reload-Menu   
      END-EVALUATE.

[Migrated content. Thread originally posted on 29 October 2007]

Has anyone used this phrase before? I could use some help with the syntax.

I've got a COM object that handles all UI and I want the program to remain in Accept mode until something in the code forces it to end.

I'm currently using the following code snippet, which works but causes the object to lose focus every 10 seconds (as the ACCEPT EVENT loop cycles).

Display-Menu.
    CREATE MenuObject
               HANDLE IN MENU-HANDLE
               EVENT PROCEDURE Menu-Events.
    MOVE "N" TO CLOSE-OBJECT, RUN-SOMETHING.
    PERFORM UNTIL CLOSE-OBJECT = "Y"
         ACCEPT EVENT BEFORE TIME 1000 END-ACCEPT
         IF RUN-SOMETHING = "Y"
           MOVE "N" TO RUN-SOMETHING
           PERFORM Execute-Selection
         END-IF
    END-PERFORM.
    DESTROY MENU-HANDLE.

Menu-Events.
    IF EVENT-TYPE = MSG-AX-EVENT
      EVALUATE EVENT-DATA-2
          WHEN MenuItemClick
              MOVE "Y" TO RUN-SOMETHING
          WHEN MenuLogout
              MOVE "Y" TO CLOSE-OBJECT
          WHEN MenuRefresh
              PERFORM Reload-Menu   
      END-EVALUATE.



I'm thinking that using the ON EXCEPTION phrase instead of BEFORE TIME will allow me to control when the ACCEPT EVENT phrase terminates, but I can't figure out how to manage the exception.

Here's a code snippet of what I'd like to do, but I don't know how to control the exception. If I use this code the program hangs.

     01 STOP-ACCEPT                 PIC 999.

     MOVE ZERO TO STOP-ACCEPT.
     PERFORM UNTIL CLOSE-OBJECT = "Y"
         ACCEPT EVENT
              ON EXCEPTION STOP-ACCEPT CONTINUE
         END-ACCEPT
         IF RUN-SOMETHING = "Y"
           MOVE "N" TO RUN-SOMETHING
           PERFORM Execute-Selection
         END-IF
    END-PERFORM.
    DESTROY MENU-HANDLE.

Menu-Events.
    IF EVENT-TYPE = MSG-AX-EVENT
      EVALUATE EVENT-DATA-2
          WHEN MenuItemClick
              MOVE "Y" TO RUN-SOMETHING
              MOVE 27 TO STOP-ACCEPT
          WHEN MenuLogout
              MOVE "Y" TO CLOSE-OBJECT
              MOVE 27 TO STOP-ACCEPT
          WHEN MenuRefresh
              PERFORM Reload-Menu   
      END-EVALUATE.


I can't find any examples of this syntax in the documentation or on the AcuCorp website or forum. Can anyone provide an example of how this can be done?

Thanks!
Laura
To terminate an ACCEPT from an event procedure Set EVENT-ACTION to EVENT-ACTION-TERMINATE

[Migrated content. Thread originally posted on 29 October 2007]

Has anyone used this phrase before? I could use some help with the syntax.

I've got a COM object that handles all UI and I want the program to remain in Accept mode until something in the code forces it to end.

I'm currently using the following code snippet, which works but causes the object to lose focus every 10 seconds (as the ACCEPT EVENT loop cycles).

Display-Menu.
    CREATE MenuObject
               HANDLE IN MENU-HANDLE
               EVENT PROCEDURE Menu-Events.
    MOVE "N" TO CLOSE-OBJECT, RUN-SOMETHING.
    PERFORM UNTIL CLOSE-OBJECT = "Y"
         ACCEPT EVENT BEFORE TIME 1000 END-ACCEPT
         IF RUN-SOMETHING = "Y"
           MOVE "N" TO RUN-SOMETHING
           PERFORM Execute-Selection
         END-IF
    END-PERFORM.
    DESTROY MENU-HANDLE.

Menu-Events.
    IF EVENT-TYPE = MSG-AX-EVENT
      EVALUATE EVENT-DATA-2
          WHEN MenuItemClick
              MOVE "Y" TO RUN-SOMETHING
          WHEN MenuLogout
              MOVE "Y" TO CLOSE-OBJECT
          WHEN MenuRefresh
              PERFORM Reload-Menu   
      END-EVALUATE.



I'm thinking that using the ON EXCEPTION phrase instead of BEFORE TIME will allow me to control when the ACCEPT EVENT phrase terminates, but I can't figure out how to manage the exception.

Here's a code snippet of what I'd like to do, but I don't know how to control the exception. If I use this code the program hangs.

     01 STOP-ACCEPT                 PIC 999.

     MOVE ZERO TO STOP-ACCEPT.
     PERFORM UNTIL CLOSE-OBJECT = "Y"
         ACCEPT EVENT
              ON EXCEPTION STOP-ACCEPT CONTINUE
         END-ACCEPT
         IF RUN-SOMETHING = "Y"
           MOVE "N" TO RUN-SOMETHING
           PERFORM Execute-Selection
         END-IF
    END-PERFORM.
    DESTROY MENU-HANDLE.

Menu-Events.
    IF EVENT-TYPE = MSG-AX-EVENT
      EVALUATE EVENT-DATA-2
          WHEN MenuItemClick
              MOVE "Y" TO RUN-SOMETHING
              MOVE 27 TO STOP-ACCEPT
          WHEN MenuLogout
              MOVE "Y" TO CLOSE-OBJECT
              MOVE 27 TO STOP-ACCEPT
          WHEN MenuRefresh
              PERFORM Reload-Menu   
      END-EVALUATE.


I can't find any examples of this syntax in the documentation or on the AcuCorp website or forum. Can anyone provide an example of how this can be done?

Thanks!
Laura
To terminate an ACCEPT from an event procedure Set EVENT-ACTION to EVENT-ACTION-TERMINATE

[Migrated content. Thread originally posted on 29 October 2007]

Has anyone used this phrase before? I could use some help with the syntax.

I've got a COM object that handles all UI and I want the program to remain in Accept mode until something in the code forces it to end.

I'm currently using the following code snippet, which works but causes the object to lose focus every 10 seconds (as the ACCEPT EVENT loop cycles).

Display-Menu.
    CREATE MenuObject
               HANDLE IN MENU-HANDLE
               EVENT PROCEDURE Menu-Events.
    MOVE "N" TO CLOSE-OBJECT, RUN-SOMETHING.
    PERFORM UNTIL CLOSE-OBJECT = "Y"
         ACCEPT EVENT BEFORE TIME 1000 END-ACCEPT
         IF RUN-SOMETHING = "Y"
           MOVE "N" TO RUN-SOMETHING
           PERFORM Execute-Selection
         END-IF
    END-PERFORM.
    DESTROY MENU-HANDLE.

Menu-Events.
    IF EVENT-TYPE = MSG-AX-EVENT
      EVALUATE EVENT-DATA-2
          WHEN MenuItemClick
              MOVE "Y" TO RUN-SOMETHING
          WHEN MenuLogout
              MOVE "Y" TO CLOSE-OBJECT
          WHEN MenuRefresh
              PERFORM Reload-Menu   
      END-EVALUATE.



I'm thinking that using the ON EXCEPTION phrase instead of BEFORE TIME will allow me to control when the ACCEPT EVENT phrase terminates, but I can't figure out how to manage the exception.

Here's a code snippet of what I'd like to do, but I don't know how to control the exception. If I use this code the program hangs.

     01 STOP-ACCEPT                 PIC 999.

     MOVE ZERO TO STOP-ACCEPT.
     PERFORM UNTIL CLOSE-OBJECT = "Y"
         ACCEPT EVENT
              ON EXCEPTION STOP-ACCEPT CONTINUE
         END-ACCEPT
         IF RUN-SOMETHING = "Y"
           MOVE "N" TO RUN-SOMETHING
           PERFORM Execute-Selection
         END-IF
    END-PERFORM.
    DESTROY MENU-HANDLE.

Menu-Events.
    IF EVENT-TYPE = MSG-AX-EVENT
      EVALUATE EVENT-DATA-2
          WHEN MenuItemClick
              MOVE "Y" TO RUN-SOMETHING
              MOVE 27 TO STOP-ACCEPT
          WHEN MenuLogout
              MOVE "Y" TO CLOSE-OBJECT
              MOVE 27 TO STOP-ACCEPT
          WHEN MenuRefresh
              PERFORM Reload-Menu   
      END-EVALUATE.


I can't find any examples of this syntax in the documentation or on the AcuCorp website or forum. Can anyone provide an example of how this can be done?

Thanks!
Laura
To terminate an ACCEPT from an event procedure Set EVENT-ACTION to EVENT-ACTION-TERMINATE