Skip to main content

How to 'OPEN EXTEND' a Line Sequential file in shared mode?

  • February 15, 2013
  • 0 replies
  • 0 views

Problem:

How to 'OPEN EXTEND'  a Line Sequential file in shared mode?

"shared mode" meaning than more processes will be able to open the same Line Sequential at the same time.

This KB applies to Server Express and Net Express.

Resolution:

Just add in the SELECT clause the LOCK MODE clause, as pasted  and attached  below

       IDENTIFICATION DIVISION.

       PROGRAM-ID. wfilsEXT.

       ENVIRONMENT DIVISION.                                                    

       INPUT-OUTPUT SECTION.                                                    

       FILE-CONTROL.                                                            

           SELECT LS-FILE    ASSIGN TO dynamic FILS

           organization line sequential

           lock mode automatic                          *>   <<<<=====================

           status STFIC.

       DATA DIVISION.                                                           

       FILE SECTION.                                                            

       FD  LS-FILE.

       01  LS-REC              PIC X(132).

       WORKING-STORAGE SECTION.

       01 STFIC PIC xx.

       01 lgind-status redefines STFIC.

           03 status-key-1    pic x.

           03 status-key-2    pic x.

           03 status-key-bin redefines status-key-2 pic x comp-x.

       01 key-2-disp          pic 999.

       01 work-msg            pic x(5).

       01 FILS                pic x(50).

       01 acc pic x.

       PROCEDURE DIVISION.

           move "FILS.dat" to FILS

           display "*--> OPEN OUTPUT "

           open output  ls-file

           if stfic not ="00" perform disp-status end-if

           if stfic = "00" or stfic  = x"3941"

                   continue

           else stop run

           end-if

           if stfic = "00"

               display "*--> CLOSE "

               close       LS-FILE

               if stfic not ="00" perform disp-status end-if

           end-if

      *    open extend sharing with all other LS-FILE

           open extend  LS-FILE

           if stfic not ="00" perform disp-status end-if

           if stfic = "00" or stfic  = x"3941"

                   continue

           else stop run

           end-if

           display "*--> OPEN extend done  "  accept acc

           move all "a" to LS-REC

           write           LS-REC

           if stfic not ="00" perform disp-status end-if

           display "*--> write done  "  accept acc

           close ls-file

           if stfic not ="00" perform disp-status end-if

            stop run.

      ******************

      *Disp-status

      ******************

       disp-status.

           if status-key-1 = "9"

               move status-key-bin to key-2-disp

           else

               move status-key-2 to key-2-disp

           end-if

           move spaces to work-msg

           string status-key-1 delimited by size

                  " " delimited by size

                  key-2-disp delimited by size

                  " " delimited by size

                  into work-msg

           display "*--> extended FS: " work-msg

Attachments:

wfilsext.cbl

Old KB# 4520