SYNCHRONIZED   [ ON Sync-Var ]     [Statement-1]     [Statement-2]     [Statement-n]   [END-SYNCHRONIZED]  | 
 working-storage section.  77 t1     handle of thread.  77 t2     handle of thread.  77 t3     handle of thread.  77 varx   pic XX.  procedure division.  main.     move "AA" to varx     perform thread p1 handle t1.     perform thread p2 handle t2.     perform thread p3 handle t3.     ACCEPT OMITTED     STOP RUN.   p1.            perform UNTIL 1 = 2        MOVE "AA" TO varx      end-perform.     p2.            perform UNTIL 1 = 2        MOVE "BB" TO varx      end-perform.     p3.            perform UNTIL 1 = 2        IF varx = "AA" or "BB"           continue        ELSE           display "Unexpected condition! varx=" varx           STOP RUN        END-IF      end-perform.        | 
 working-storage section.  77 t1     handle of thread.  77 t2     handle of thread.  77 t3     handle of thread.  77 varx   pic XX.  procedure division.  main.     move "AA" to varx     perform thread p1 handle t1.     perform thread p2 handle t2.     perform thread p3 handle t3.     ACCEPT OMITTED     STOP RUN.   p1.            perform UNTIL 1 = 2        SYNCHRONIZED        MOVE "AA" TO varx        END-SYNCHRONIZED      end-perform.     p2.            perform UNTIL 1 = 2        SYNCHRONIZED        MOVE "BB" TO varx        END-SYNCHRONIZED      end-perform.     p3.            perform UNTIL 1 = 2        SYNCHRONIZED        IF varx = "AA" or "BB"           continue        ELSE           display "Unexpected condition! varx=" varx           STOP RUN        END-IF        END-SYNCHRONIZED      end-perform.       | 
 working-storage section.  77 t1     handle of thread.  77 t2     handle of thread.  77 t3     handle of thread.  01 vars.     03 var1   pic 9(3).     03 var2   pic 9(5).  procedure division.  main.     move 1 to var1     move 2 to var2     perform thread P1 handle t1.     perform thread P2 handle t2.     perform thread P3 handle t3.     ACCEPT OMITTED     STOP RUN.   p1.            perform UNTIL 1 = 2        MOVE 1 TO var1      end-perform.     p2.            perform UNTIL 1 = 2        MOVE 2 TO var2      end-perform.     p3.            perform UNTIL 1 = 2        add 1 to var1        add 1 to var2      end-perform.  | 
 working-storage section.  77 t1     handle of thread.  77 t2     handle of thread.  77 t3     handle of thread.  01 vars.     03 var1   pic 9(3).     03 var2   pic 9(5).  procedure division.  main.     move 1 to var1     move 2 to var2     perform thread P1 handle t1.     perform thread P2 handle t2.     perform thread P3 handle t3.     ACCEPT OMITTED     STOP RUN.   p1.            perform UNTIL 1 = 2        SYNCHRONIZED        MOVE 1 TO var1        END-SYNCHRONIZED      end-perform.     p2.            perform UNTIL 1 = 2        SYNCHRONIZED        MOVE 2 TO var2        END-SYNCHRONIZED      end-perform.     p3.            perform UNTIL 1 = 2        SYNCHRONIZED        add 1 to var1        add 1 to var2        END-SYNCHRONIZED      end-perform.  | 
       program-id. proga.        working-storage section.        77 t1     handle of thread.        01 vars.           03 var1   pic 9(3).           03 var2   pic 9(5).        procedure division.        main.           move 1 to var1           move 2 to var2           call thread "progb" handle in t1 using vars.           call "c$sleep" using 1           perform para2.           ACCEPT OMITTED           STOP RUN.         para2.                  perform UNTIL 1 = 2              MOVE 2 TO var1              MOVE 2 TO var2            end-perform.    | 
       program-id. progb.        working-storage section.        linkage section.        01 vars.           03 var1   pic 9(3).           03 var2   pic 9(5).        procedure division using vars.        main.            perform UNTIL 1 = 2              MOVE 1 TO var1              MOVE 1 TO var2            end-perform.               goback.  | 
       identification division.        class-id. myclass as "myclass".        identification division.        factory.        working-storage section.        public.        77 MYLOCK  pic x.        procedure division.        end factory.  | 
       program-id. proga.        configuration section.        repository.            class myclass as "myclass".        working-storage section.        77 t1     handle of thread.        01 vars.           03 var1   pic 9(3).           03 var2   pic 9(5).        procedure division.        main.           move 1 to var1           move 2 to var2           call thread "progb" handle in t1 using vars.           call "c$sleep" using 1           perform para2.           ACCEPT OMITTED           STOP RUN.         para2.                  perform UNTIL 1 = 2             SYNCHRONIZED on myclass:>MYLOCK              MOVE 2 TO var1              MOVE 2 TO var2             END-SYNCHRONIZED            end-perform.    | 
       program-id. progb.        configuration section.        repository.            class myclass as "myclass".        working-storage section.        linkage section.        01 vars.           03 var1   pic 9(3).           03 var2   pic 9(5).        procedure division using vars.        main.            perform UNTIL 1 = 2             SYNCHRONIZED on myclass:>MYLOCK               MOVE 1 TO var1               MOVE 1 TO var2             END-SYNCHRONIZED            end-perform.               goback.  |