Google
 

Trailing-Edge - PDP-10 Archives - DEC_CMS-20_V1.0_SRC - cms/sources/share.bli
There are no other files named share.bli in the archive.
module share (	! Serialize access to the project library.
		ident = '1',
		%if
		    %bliss(bliss32)
		%then
		    language(bliss32),
		    addressing_mode(external=long_relative,
				    nonexternal=long_relative)
		%else
		    language(bliss36)
		%fi
		) =
begin

!
!			  COPYRIGHT (C) 1982 BY
!	      DIGITAL EQUIPMENT CORPORATION, MAYNARD, MASS.
!
! THIS SOFTWARE IS FURNISHED UNDER A LICENSE AND MAY BE USED AND  COPIED
! ONLY  IN  ACCORDANCE  WITH  THE  TERMS  OF  SUCH  LICENSE AND WITH THE
! INCLUSION OF THE ABOVE COPYRIGHT NOTICE.  THIS SOFTWARE OR  ANY  OTHER
! COPIES  THEREOF MAY NOT BE PROVIDED OR OTHERWISE MADE AVAILABLE TO ANY
! OTHER PERSON.  NO TITLE TO AND OWNERSHIP OF  THE  SOFTWARE  IS  HEREBY
! TRANSFERRED.
!
! THE INFORMATION IN THIS SOFTWARE IS SUBJECT TO CHANGE  WITHOUT  NOTICE
! AND  SHOULD  NOT  BE  CONSTRUED  AS  A COMMITMENT BY DIGITAL EQUIPMENT
! CORPORATION.
!
! DIGITAL ASSUMES NO RESPONSIBILITY FOR THE USE OR  RELIABILITY  OF  ITS
! SOFTWARE ON EQUIPMENT WHICH IS NOT SUPPLIED BY DIGITAL.
!

!++
! Facility:  CMS Library Processor
!
! Abstract:
!
!	The routines of this module assure that the commands which modify
!	the project library have exclusive access while doing so.  The routine
!	that obtains access to the library also checks that the previous
!	transaction completed successfully and that the default directory
!	is not the library.
!
! Environment: Transportable
!
! Author:  Earl Van Horn	Creation Date:  January 2, 1980
!
!--
!
! Table of Contents:
!
forward routine
    donlib : novalue,		! Relinquish access to the library.
    libini,			! Value means library is initializable.
    librea,			! Value means library is readable.
    libwri,			! Value means library is writable.
    saflib,			! Obtain safe access to the library.
    trylib ;			! Obtain safe access but do not wait.
!
! Include Files:
!
%if %bliss(bliss32) %then
    library 'sys$library:starlet';
%else
    require 'jsys:';
%fi
library 'XPORT:' ;
require 'BLISSX:' ;
require 'FILUSR:' ;
require 'SHRUSR:' ;
require 'SCONFG:' ;
require 'condit:';

!
! Macros:
!

!
! Equated Symbols:
!
literal
    k_batch_retry_seconds = 3,	! Number of seconds for a batch job to wait
				! before trying to get the library again.
    k_batch_inform=20,		! Say hello to user in batch less often than
				! online
    k_inform_every_nth = 15,	! Say hello to the user on every fifteenth attempt.
    k_max_attempts = 6000,	! Maximum number of times to try getting the
				! library before giving up.
    k_no_lib = 0,		! The library is currently not accessible
				! for reading, writing, or initializing.  The
				! value of K_NO_LIB must be different from the
				! values of K_READ_LIB, K_UPDATE_LIB,
				! K_INITIALIZE_LIB, K_RECOVER_LIB, and
				! K_VERIFY-LIB, declared in SHRUSR.REQ .
    k_online_retry_seconds = 2 ;! Number of seconds for an on-line process to
				! wait before trying to get the library again.

!
! Own Storage:
!
own
    lib_shr_status : initial(k_no_lib),
			! K_NO_LIB means no library access is allowed.
			! K_READ_LIB means the library is readable.
			! K_UPDATE_LIB means the library is updatable.
			! K_INITIALIZE_LIB means the library is initializable.
			! K_RECOVER_LIB means the library is recoverable.
			! K_VERIFY_LIB means the library is verifiable.
    $io_block(llok);    ! IOB for the library's lock file.

!
! External References:
!
external
    f_rb_clspd,			! rolbck on open files pending(ROLBCK)
    f_rb_pending ;		! rolbck pending(ROLBCK)
    
external literal
	s_baddir,
	s_badlib,
	s_busy,
	s_inuse,		! library in use
	s_isinit,
	s_nolib,
	s_privdis,		! privileges disabled
	s_proceed,		! proceeding
	s_retbad,
	s_setlib,		! use set library command
	s_undeflib,
	s_useverrec,
	s_waiting;		! still waiting

external routine
    badiob : novalue,		! Report a library problem involving an iob.
    batrun,			! Test if this is a batch job.
    bug : novalue,		! Report a bug.
    chklib,			! check library for correct file retention count
    chkprv,			! check for user elevated privileges
    dellog,
    err,
    erriob,
    ers,			! Report a user mistake.
    intclr,			! clear batch interlock
    intset,			! set batch interlock
    isdir,			! Return TRUE if the specified directory exists
    isfile,			! Return TRUE if the specified file exists.
    nowtrn,			! Return TRUE if a transaction is being made.
    oldtrn,			! Return TRUE if prior transaction incomplete.
    protec : novalue,		! Establish the protection codes for a file.
    sysmsg,			! Talk to the user.
    hibernate : novalue ;	! Wait for the specified interval.
global routine donlib : novalue =

!++
! Functional Description:
!
!	This routine relinquishes the access to the library that was
!	established by SAFLIB or TRYLIB.  It may not be called unless access
!	has been so established.  It also must not be called if a transaction
!	is now being made, i.e., if BEGTRN has been called but there has not
!	been a corresponding call to ENDTRN or CANTRN.
!
! Formal Parameters:
!
!	None
!
! Implicit Inputs:
!
!	The own variable LIB_SHR_STATUS declared in this module.
!
! Implicit Outputs:
!
!	The own variable LIB_SHR_STATUS declared in this module.
!
! Routine Value:
! Completion Codes:
!
!	None
!
! Side Effects:
!
!	The library is relinquished for access by other users.  The library
!	may be written only when all readers have relinquished.
!
!--

    begin	! DONLIB

    if .lib_shr_status eql k_no_lib
    then
	bug(lit('Unnecessary call to DONLIB')) ;

    ! Make sure any transaction is complete or canceled.
    if nowtrn()
    then
	bug(lit('DONLIB called during a transaction')) ;

    ! Release the library.
    if  not $step_close(iob = llok_iob, failure = 0)
    then
	badiob(llok_iob, lit('DONLIB cannot close the lock file')) ;

    ! disallow rolbck since transaction is complete
    IF .f_rb_pending
    THEN
	f_rb_pending = false ;
    
    IF .f_rb_clspd
    THEN
	f_rb_clspd = false ;
    
    lib_shr_status = k_no_lib ;

    end ;	! DONLIB
global routine libini =

!++
! Functional Description:
!
!	This routine returns TRUE if and only if the library is secure for
!	initialization, as is done by calling SAFLIB or TRYLIB.
!
! Formal Parameters:
!
!	None
!
! Implicit Inputs:
!
!	The own variable LIB_SHR_STATUS declared in this module.
!
! Implicit Outputs:
!
!	None
!
! Routine Value:
! Completion Codes:
!
!	TRUE means the library can be initialized.  FALSE means not.
!
! Side Effects:
!
!	None
!
!--

    begin	! LIBINI

    .lib_shr_status eql k_initialize_lib

    end ;	! LIBINI
global routine librea =

!++
! Functional Description:
!
!	This routine returns TRUE if and only if the library may be read
!	without	interference from other users.  This is the case just when the
!	library is currently readable, updatable, initializable, recoverable,
!	or verifiable.
!
! Formal Parameters:
!
!	None
!
! Implicit Inputs:
!
!	The own variable LIB_SHR_STATUS declared in this module.
!
! Implicit Outputs:
!
!	None
!
! Routine Value:
! Completion Codes:
!
!	TRUE means the library can be safely read. FALSE means not.
!
! Side Effects:
!
!	None
!
!--

    begin	! LIBREA

    .lib_shr_status neq k_no_lib

    end ;	! LIBREA
global routine libwri =

!++
! Functional Description:
!
!	This routine returns TRUE if and only if the library can be
!	written without interference from other users.  This is true just
!	when the library is updatable, initializable, or recoverable.
!
! Formal Parameters:
!
!	None
!
! Implicit Inputs:
!
!	The own variable LIB_SHR_STATUS declared in this module.
!
! Implicit Outputs:
!
!	None
!
! Routine Value:
! Completion Codes:
!
!	TRUE means the library is writable.  FALSE means not.
!
! Side Effects:
!
!	None
!
!--

    begin	! LIBWRI

    .lib_shr_status eql k_update_lib or
    .lib_shr_status eql k_initialize_lib or
    .lib_shr_status eql k_recover_lib

    end ;	! LIBWRI
global routine saflib(how_to_share) =

!++
! Functional Description:
!
!	This routine secures the library for the type of activity indicated
!	by the parameter.  Other users (that call this routine or TRYLIB) will
!	be prevented from accessing the library according to the type of
!	activity they request.
!
!	In addition to preventing undesired concurrent access, the routine
!	checks that the previous transaction was completed.  If the previous
!	transaction was not completed, the library may be inconsistent, and
!	recovery is necessary.  The user is informed, but recovery is not done.
!	This check is omitted if the library is requested for verification
!	or recovery.
!
!	The routine also checks that the default directory is not the library.
!
!	If the desired access is obtained, and all checks are passed, TRUE
!	is returned.  Otherwise, the user is informed of the problem
!	and FALSE is returned.
!
!	This routine must not be called again until DONLIB has been called.
!
!	When attempting to obtain the desired access, the routine will
!	wait a reasonable interval for other users to relinquish the
!	library.  The current user will be informed about this wait
!	and the reason for it.  If the wait is excessive (on the order of
!	5 hours) the user will be informed that we are giving up, and
!	FALSE will be returned.
!
!	Thus, if this routine returns FALSE, it may be assumed that all
!	reasonable attempts have been made to secure the library, and that
!	the command should be terminated.
!
! Formal Parameters:
!
!	how_to_share:	The allowed values of this parameter are declared
!			in SHRUSR.REQ:
!
!				K_READ_LIB means several users can read the
!				library, but none are allowed to modify.
!
!				K_UPDATE_LIB means the current user can update
!				the library, and no other user is allowed
!				any access to the library, not even to read.
!
!				K_INITIALIZE_LIB means the current user can
!				initialize the library, and no other user is
!				allowed any access to the library.
!
!				K_RECOVER_LIB means the current user can
!				recover the library, and no other user is
!				allowed any access to the library.
!
!				K_VERIFY_LIB means the current user can read
!				the library for verification, and no other
!				user is allowed to modify the library.  This is
!				the same as K_READ_LIB, except the existence
!				of an incomplete transaction is ignored.
!
! Implicit Inputs:
!
!	The own variable LIB_SHR_STATUS declared in this module.
!
! Implicit Outputs:
!
!	The own variable LIB_SHR_STATUS declared in this module.
!
! Routine Value:
! Completion Codes:
!
!	TRUE means the library may safely be used as requested.
!	FALSE means the library may not be used, and the user has been
!	informed.
!
! Side Effects:
!
!	The library is opened for the type of access requested.  This may
!	involve a delay until the desired access can be obtained.
!
!--

    begin	! SAFLIB
    local
	attempts,			! Number of unsuccessful attempts
					! to open the library's lock file.
	inform_interval,		! Number of tries between messages
	is_batch,			! true if we are in batch
	is_library,			! Means the default directory is
					! the library directory.
	status,				! Status code from XPORT.
	valid ;				! Means a directory
					! specification is valid.

    ! Make sure the call to SAFLIB is legal.
    if .lib_shr_status neq k_no_lib
    then
	bug(lit('Conflicting or redundant call to SAFLIB')) ;

    ! Make sure the library exists.
    if not isdir(len_comma_ptr(lib), valid, k_null)
    then
	begin		! Library not found.
	if .valid
	then
	    err(s_nolib,lit(%string(fac_name,' library not found'))) ;
	ers(s_setlib,lit(%string('Use the ',fac_name,
			' SET LIBRARY command'))) ;
	end ;		! Library not found.

    ! If the default directory exists, make sure it is not the library.
    if isdir(len_comma_ptr(''), valid, is_library)
    then
	begin	! default directory is present.
	if .is_library
	then
	    begin	! Bad default directory.
	    ers(s_baddir,
		lit(%string('Your default directory cannot be the ',
				fac_name,' library'))) ;
	    return false ;
	    end ;	! Bad default directory.
	end ;	! default directory is present.

    ! Make sure the user isn't running with excessive privileges
    if
	chkprv()
    then
	!remind him that he is running privileged and
	!that we have temporarily taken his privileges away
	sysmsg(s_privdis,lit('BYPASS or SYSPRV temporarily disabled'),0);

    ! Check the presence or absense of the lock file according to the kind of
    ! access needed.
    if isfile(len_comma_ptr(%string(lib, lok)), k_null)
    then
	begin	! Lock file is present.
	if .how_to_share eql k_initialize_lib
	then
	    begin	! Already initialized.
	    ers(s_isinit,
		lit(%string('Your ',fac_name,
			' library has already been initialized'))) ;
	    return false ;
	    end ;	! Already initialized.
	end	! Lock file is present.
    else
	begin	! Lock file is absent.
	if .how_to_share neq k_initialize_lib
	then
	    begin	! Never initialized.
	    ers(s_setlib,lit(%string('Use the ',
		fac_name,' SET LIBRARY command'))) ;
	    end		! Never initialized.
	else
	    begin	! Create and protect the lock file.
	    literal
		k_lok_access = k_r_access or k_w_access or k_d_access or k_l_access ;
					! Access rights for the lock file.

	    ! Create the lock file.
	    if step$_created neq (status = $step_open(iob = llok_iob,
				 failure = 0, options = overwrite,
				 file_spec = %string(lib, lok)))
	    then
	      badiob(llok_iob, lit(%string(fac_name,
			' cannot create the lock file')));

	    ! Set its protection, assuming a group library for now.
	    protec(llok_iob, k_null, k_lok_access, k_lok_access, 0) ;

	    ! Close the file to establish its protection codes.
	    if not $step_close(iob = llok_iob, failure = 0)
	    then
		badiob(llok_iob, lit(%string(fac_name,
				' cannot close the lock file'))) ;

	    end ;	! Create and protect the lock file
	end ;	! Lock file is absent.

    ! Initialize the LOK file's IOB for the type of library access needed.
    ! ***** See work-around for XPORT bug, below ***
    $io_block_init(llok);
    selectone .how_to_share of
	set	! Kind of sharing.
	[k_read_lib, k_verify_lib]:
	    llok_iob[iob$v_input] = 1 ;
	[k_update_lib, k_initialize_lib, k_recover_lib]:
	    llok_iob[iob$v_append] = 1 ;
	[otherwise]:
	    bug(lit('Invalid argument to SAFLIB')) ;
	tes ;	! Kind of sharing.

    ! A batch job that repeatedly runs should not hog the library.
    if
	batrun()
    then
	begin
	is_batch=true;
	inform_interval=k_batch_inform;
	!try to set batch interlock.  If it fails, someone else
	!needs the library
	while
	    not intset()
	do
	    hibernate(k_batch_retry_seconds)
	end
    else
	begin
	is_batch=false;
	inform_interval=k_inform_every_nth
	end;


    !+
    !   Grab the library as soon as it is available by attempting
    !   to open 00fac_name.LOK . FILE$OPEN is used to do this but in
    !   the case of the 00fac_name.LOK file the normal re-tries done
    !   by FILE$OPEN in the case of failure are BYPASSED. All
    !   re-tries to open the 00fac_name.LOK file are handled from this 
    !   routine
    !-
    
    attempts = 0 ;
    until (status = $step_open(iob = llok_iob, failure = 0,
				file_spec = (%string(lib,lok)))) do
	begin	! Failed to get the library.    

	if
	    .is_batch
	then
	    !clear the interlock flag so batch can't have priority
	    intclr();

	! *** Work-around til an XPORT bug is fixed. ***
	if .how_to_share eql k_read_lib or .how_to_share eql k_verify_lib
	then
	    llok_iob[iob$v_input] = 1
	else
	    llok_iob[iob$v_append] = 1 ;
	! *** End of work-around. ***

	! Punt on any unexpected status.
	if 
            .status neq step$_file_lock
	then
	    if .status eql step$_no_access
	    then
		begin	! Don't have the right privileges
	        erriob(s_badlib,llok_iob,lit(%string(fac_name,
				' cannot obtain the library'))) ;
		dellog(lit(lib));
		ers(s_undeflib,lit(%string(fac_name,' library is now undefined')));
		end	! Don't have the right privileges
	    else
	        badiob(llok_iob,lit(%string(fac_name,
				' cannot obtain the library'))) ;

	! Limit the number of attempts.
	attempts = .attempts + 1 ;
	if .attempts geq k_max_attempts
	then
	    begin	! Library is busy.
	    ers(s_busy,
		lit(%string('Your ',fac_name,' library is busy;  please try again later')));
	    return false ;
	    end ;	! Library is busy.
	
	if .attempts eql 1
	then
	    sysmsg( s_inuse,
		lit(%string('Your ',fac_name,' library is in use;  please wait')),0)
	else
	    if ((.attempts - 1) mod .inform_interval) eql 0
	    then
		sysmsg(s_waiting,lit('Still waiting'),0) ;

	if
	    .is_batch
	then
	    !wait until we can get the interlock
	    begin
	    do
		hibernate(k_batch_retry_seconds)
	    until
		intset()
	    end
	else
	    !try to get the interlock file
	    begin
	    intset();
	    hibernate(k_online_retry_seconds)
	    end

	end ;	! Failed to get the library.

    !The library is now in our possession, clear the
    ! interlock
    intclr();

    ! The .LOK file is now open, make sure the file retention count
    ! for the library is reasonable
    status=chklib(llok_iob);
    if
	.status neq 0 and
	.status leq filvrs
    then
	begin
	ers(s_retbad,cat('Library file retention count is too small;',
		'  no operations can be done safely in the library'));
	return false
	end;

    ! The library is now secure.  LIB_SHR_STATUS is tested indirectly by
    ! OLDTRN, below.
    lib_shr_status = .how_to_share ;

    ! Make sure the last transaction completed, unless recovery or
    ! verification is being done.
    if .how_to_share neq k_recover_lib and .how_to_share neq k_verify_lib
    then
	if oldtrn()
	then
	    begin	! Incomplete transaction.
	    err(s_useverrec,lit(%string('The last transaction was not finished;',
			%string('  Use ',fac_name,' VERIFY/RECOVER')))) ;

	    ! Relinquish the library.
	    if not $step_close(iob = llok_iob, failure = 0)
	    then
		badiob(llok_iob, lit(%string(fac_name,
			' could not relinquish library'))) ;

	    lib_shr_status = k_no_lib ;
	    return false ;
	    end ;	! Incomplete transaction.

    ! Tell the user his vigil is over.
    if .attempts gtr 0
    then
	sysmsg(s_proceed,lit('Proceeding'),0) ;

    true
    end ;	! SAFLIB
global routine trylib(how_to_share, a_valid) =

!++
! Functional Description:
!
!	This routine secures the library for the type of activity indicated
!	by the first parameter.  Other users (that call this routine or SAFLIB)
!	will be prevented from accessing the library according to the type of
!	activity they request.
!
!	In addition to preventing undesired concurrent access, the routine
!	checks that the previous transaction was completed.  If the previous
!	transaction was not completed, the library may be inconsistent, and
!	recovery is necessary.  The user is informed, but recovery is not done.
!	This check is omitted if the library is requested for verification
!	or recovery.
!
!	The routine also checks that the default directory is not the library.
!
!	If the library is in use by another process, this routine does not
!	wait, but returns FALSE.  No message is produced in this case.
!
!	If this routine returns TRUE, the library has been obtained and
!	neither this routine nor SAFLIB may be called again until DONLIB has
!	been called.
!
! Formal Parameters:
!
!	HOW_TO_SHARE	The allowed values of this parameter are declared
!			in SHRUSR.REQ:
!
!				K_READ_LIB means several users can read the
!				library, but none are allowed to modify.
!
!				K_UPDATE_LIB means the current user can update
!				the library, and no other user is allowed
!				any access to the library, not even to read.
!
!				K_INITIALIZE_LIB means the current user can
!				initialize the library, and no other user is
!				allowed any access to the library.
!
!				K_RECOVER_LIB means the current user can
!				recover the library, and no other user is
!				allowed any access to the library.
!
!				K_VERIFY_LIB means the current user can read
!				the library for verification, and no other
!				user is allowed to modify the library.  This is
!				the same as K_READ_LIB, except the existence
!				of an incomplete transaction is ignored.
!
!	A_VALID		Address of a fullword where this routine will store
!			TRUE or FALSE according to whether or not the checks
!			mentioned in the functional description are passed.
!
!			If TRUE is stored and TRUE is returned as the routine
!			value, the library may be used as requested.  If TRUE
!			is stored and FALSE is returned, the library is in use.
!			No message is produced in either case.
!
!			If FALSE is stored, FALSE is always returned, and the
!			user is informed of the check which failed.
!
! Implicit Inputs:
!
!	The own variable LIB_SHR_STATUS declared in this module.
!
! Implicit Outputs:
!
!	The own variable LIB_SHR_STATUS declared in this module.
!
! Routine Value:
! Completion Codes:
!
!	TRUE means the library may safely be used as requested.
!	FALSE means the library may not be used, and the user has been
!	informed if the reason is other than the fact that the library
!	is already in use.
!
! Side Effects:
!
!	The library is opened for the type of access requested.
!
!--

    begin	! TRYLIB
    bind
	valid = .a_valid ;
    local
	is_library,			! Means the default directory is
					! the library directory.
	status,				! Status code from XPORT.
	spec_ok ;			! Means a directory
					! specification is valid.

    ! Make sure the call to TRYLIB is legal.
    if .lib_shr_status neq k_no_lib
    then
	bug(lit('Conflicting or redundant call to TRYLIB')) ;

    ! Assume a check will fail.
    valid = false ;

    ! Make sure the library exists.
    if not isdir(len_comma_ptr(lib), spec_ok, k_null)
    then
	begin		! Library not found.
	if .spec_ok
	then
	    err(s_nolib,lit(%string(fac_name,' library not found'))) ;
	ers(s_setlib,lit(%string('Use the ',fac_name,
				' SET LIBRARY command')),0) ;
	end ;		! Library not found.

    ! If the default directory exists, make sure it is not the library.
    if isdir(len_comma_ptr(''), spec_ok, is_library)
    then
	begin	! default directory is present.
	if .is_library
	then
	    begin	! Bad default directory.
	    ers(s_baddir,
		lit(%string('Your default directory cannot be the ',
			fac_name,' library'))) ;
	    return false ;
	    end ;	! Bad default directory.
	end ;	! default directory is present.

    ! Make sure the user isn't running with excessive privileges
    if
	chkprv()
    then
	!remind him that he is running privileged and
	!that we have temporarily taken his privileges away
	sysmsg(s_privdis,lit('BYPASS or SYSPRV temporarily disabled'),0);

    ! Check the presence or absense of the lock file according to the kind of
    ! access needed.
    if isfile(len_comma_ptr(%string(lib, lok)), k_null)
    then
	begin	! Lock file is present.
	if .how_to_share eql k_initialize_lib
	then
	    begin	! Already initialized.
	    ers(s_isinit,
		lit(%string('Your ',fac_name,
			' library has already been initialized'))) ;
	    return false ;
	    end ;	! Already initialized.
	end	! Lock file is present.
    else
	begin	! Lock file is absent.
	if .how_to_share neq k_initialize_lib
	then
	    begin	! Never initialized.
	    ers(s_setlib,lit(%string('Use the ',
		fac_name,' SET LIBRARY command'))) ;
	    end		! Never initialized.
	else
	    begin	! Create and protect the lock file.
	    literal
		k_lok_access = k_r_access or k_w_access or k_d_access ;
					! Access rights for the lock file.

	    ! Create the lock file.
	    if step$_created neq (status = $step_open(iob = llok_iob,
				 failure = 0, options = overwrite,
				 file_spec = %string(lib, lok)))
	    then
		badiob(llok_iob, lit(%string(fac_name,
			' cannot create the lock file')));

	    ! Set its protection, assuming a group library for now.
	    protec(llok_iob, k_null, k_lok_access, k_lok_access, 0) ;

	    ! Close the file to establish its protection codes.
	    if not $step_close(iob = llok_iob, failure = 0)
	    then
		badiob(llok_iob, lit(%string(fac_name,
				' cannot close the lock file'))) ;

	    end ;	! Create and protect the lock file
	end ;	! Lock file is absent.

    ! Initialize the LOK file's IOB for the type of library access needed.
    selectone .how_to_share of
	set	! Kind of sharing.
	[k_read_lib, k_verify_lib]:
	    llok_iob[iob$v_input] = 1 ;
	[k_update_lib, k_initialize_lib, k_recover_lib]:
	    llok_iob[iob$v_append] = 1 ;
	[otherwise]:
	    bug(lit('Invalid argument to TRYLIB')) ;
	tes ;	! Kind of sharing.

    !+
    !   Grab the library as soon as it is available by attempting
    !   to open 00fac_name.LOK . FILE$OPEN is used to do this but in
    !   the case of the 00fac_name.LOK file the normal re-tries done
    !   by FILE$OPEN in the case of failure are BYPASSED. All
    !   re-tries to open the 00fac_name.LOK file may be handled from this 
    !   routine if desired.
    !-

    if not (status = $step_open(iob = llok_iob, failure = 0,
				file_spec = (%string(lib,lok))))
    then
	begin	! Failed to get the library.    

	if 
            .status neq step$_file_lock
	then
	    if .status eql step$_no_access
	    then
		begin	! Don't have the right privileges
	        erriob(s_badlib,llok_iob,lit(%string(fac_name,
			' cannot obtain the library'))) ;
		dellog(lit(lib));
		ers(s_undeflib,lit(%string(fac_name,' library is now undefined')));
		end	! Don't have the right privileges
	    else
	        badiob(llok_iob,lit(%string(fac_name,
			' cannot obtain the library'))) ;

	end	! Failed to get the library.
    else
	begin	! Succeeded in getting the library.

	! The .LOK file is now open, make sure the file retention count
	! for the library is reasonable
	status=chklib(llok_iob);
	if
	    .status neq 0 and
	    .status leq filvrs
	then
	    begin
	    ers(s_retbad,cat('Library file retention count is too small;',
			'  no operations can be done safely in the library'));
	    return false
	    end;

	! The library is now secure.  LIB_SHR_STATUS is tested indirectly by
	! OLDTRN, below.
	lib_shr_status = .how_to_share ;

	! Make sure the last transaction completed, unless recovery or
	! verification is being done.
	if .how_to_share neq k_recover_lib and .how_to_share neq k_verify_lib
	then
	    begin	! Neither recovering nor verifying.
	    if oldtrn()
	    then
		begin	! Incomplete transaction.
		err(s_useverrec,lit(%string(
			'The last transaction was not finished;',
			%string('  Use ',fac_name,' VERIFY/RECOVER')))) ;

		! Relinquish the library.
		if not $step_close(iob = llok_iob, failure = 0)
		then
		    badiob(llok_iob,
				lit(%string(fac_name,
				' could not relinquish library'))) ;

		lib_shr_status = k_no_lib ;
		return false ;
		end ;	! Incomplete transaction.
	    end ;	! Neither recovering nor verifying.

	end ;	! Succeeded in getting the library.

    ! All checks were passed.
    valid = true ;

    .lib_shr_status eql .how_to_share
    
    end ;	! TRYLIB
end				! Module SHARE
eludom