[an error occurred while processing this directive]

HP OpenVMS Systems Documentation

Content starts here

OpenVMS Utility Routines Manual


Previous Contents Index

  1. Call LBR$INI_CONTROL, specifying that the function to be performed is update and the library type is text.
  2. Call LBR$LOOKUP_KEY to find the key associated with the module you want to delete.
  3. Call LBR$DELETE_KEY to delete the key associated with the module you want to delete. If more than one key points to the module, you need to call LBR$LOOKUP_KEY and LBR$DELETE_KEY for each key.
  4. Call LBR$DELETE_DATA to delete the module (the module header and data) from the library.

12.2.5 Using Multiple Keys and Multiple Indexes

You can point to the same module with more than one key. The keys can be in the primary index (index 1) or alternate indexes (indexes 2 through 10). The best method is to reserve the primary index for module names. In system-defined object libraries, index 2 contains the global symbols defined by the various modules.

Example 12-5 illustrates the way that keys can be associated with modules.

Example 12-5 Associating Keys with Modules

SUBROUTINE ALIAS (INDEX)
! Catalogs modules by alias

INTEGER STATUS,        ! Return status
        INDEX,         ! Library index
        TXTRFA (2)     ! RFA of module
CHARACTER*31 MODNAME,  ! Name of module
             ALIASNAME ! Name of alias
INTEGER MODNAME_LEN    ! Length of module name
INTEGER ALIASNAME_LEN  ! Length of alias name
! VMS library procedures
INTEGER LBR$LOOKUP_KEY,
        LBR$SET_INDEX,
        LBR$INSERT_KEY,
        LIB$GET_INPUT,
        LIB$GET_VALUE
        LIB$LOCC
! Return codes
EXTERNAL LBR$_KEYNOTFND, ! Key not found
         LBR$_DUPKEY,    ! Duplicate key
         RMS$_EOF,       ! End of text in module
         DOLIB_NOMOD     ! No such module
! Get module name from /ALIAS on command line
CALL CLI$GET_VALUE ('ALIAS', MODNAME)
! Calculate length of module name
MODNAME_LEN = LIB$LOCC (' ', MODNAME) - 1
! Look up module name in library index
STATUS = LBR$LOOKUP_KEY (INDEX,
                         MODNAME (1:MODNAME_LEN),
                         TXTRFA)
END IF
! Insert aliases if module exists
IF (STATUS) THEN
  ! Set to index 2
  STATUS = LBR$SET_INDEX (INDEX, 2)
  IF (.NOT. STATUS) CALL LIB$SIGNAL (%VAL (STATUS))
  ! Get alias name from /ALIAS on command line
  STATUS = CLI$GET_VALUE ('ALIAS', ALIASNAME)
  ! Insert aliases in index 2 until bad return status
  ! which indicates end of qualifier values
  DO WHILE (STATUS)
    ! Calculate length of alias name
    ALIASNAME_LEN = LIB$LOCC (' ', ALIASNAME) - 1
    ! Put alias name in index
    STATUS = LBR$INSERT_KEY (INDEX,
                             ALIASNAME (1:ALIASNAME_LEN),
                             TXTRFA)
    IF ((.NOT. STATUS) .AND.
        (STATUS .NE. %LOC (LBR$_DUPKEY)) THEN
      CALL LIB$SIGNAL (%VAL (STATUS))
    END IF
    ! Get another alias
    STATUS = CLI$GET_VALUE ('ALIAS', ALIASNAME)
  END DO

  ! Issue warning if module does not exist
ELSE IF (STATUS .EQ. %LOC (LBR$_KEYNOTFND)) THEN
  CALL LIB$SIGNAL (DOLIB_NOMOD,
                   %VAL (1),
                   MODNAME (1:MODNAME_LEN))
ELSE
  CALL LIB$SIGNAL (%VAL (STATUS))
END IF

! Exit
END

You can look up a module using any of the keys associated with it. The following code fragment checks index 2 for a key if the lookup in the primary index fails:


STATUS = LBR$SET_INDEX (INDEX, 1)
IF (.NOT. STATUS) CALL LIB$SIGNAL (%VAL (STATUS))
STATUS = LBR$LOOKUP_KEY (INDEX,
                         MODNAME (1:MODNAME_LEN),
                         TXTRFA)
IF (STATUS .EQ. %LOC (LBR$_KEYNOTFND)) THEN
  STATUS = LBR$SET_INDEX (INDEX, 2)
  IF (.NOT. STATUS) CALL LIB$SIGNAL (%VAL (STATUS))
  STATUS = LBR$LOOKUP_KEY (INDEX,
                           MODNAME (1:MODNAME_LEN),
                           TXTRFA)
  IF (.NOT. STATUS) CALL LIB$SIGNAL (%VAL (STATUS))
END IF

There are two ways to identify the keys associated with a module:

  • Use the LBR$LOOKUP_KEY routine to look up the module using one of the keys.
  • Use LBR$SEARCH to search applicable indexes for the keys. LBR$SEARCH calls a user-written routine each time it retrieves a key. The routine must be an integer function defined as external that returns a success (odd number) or failure (even number) status. LBR$SEARCH stops processing on a return status of failure.
The subroutine in Example 12-6 lists the names of keys in index 2 (the aliases) that point to a module identified on the command line by the module's name in the primary index.

Example 12-6 Listing Keys Associated with a Module

   .
   .
   .
SUBROUTINE SHOWAL (INDEX)
! Lists aliases for a module

INTEGER STATUS,      ! Return status
        INDEX,       ! Library index
        TXTRFA (2)   ! RFA for module text
CHARACTER*31 MODNAME ! Name of module
INTEGER MODNAME_LEN  ! Length of module name
! VMS library procedures
INTEGER LBR$LOOKUP_KEY,
        LBR$SEARCH,
        LIB$LOCC
! Return codes
EXTERNAL LBR$_KEYNOTFND, ! Key not found
         DOLIB_NOMOD     ! No such module
! Search routine
EXTERNAL SEARCH
INTEGER SEARCH
! Get module name and calculate length
CALL CLI$GET_VALUE ('SHOWALIAS', MODNAME)
MODNAME_LEN = LIB$LOCC (' ', MODNAME) - 1
! Look up module in index 1
  STATUS = LBR$LOOKUP_KEY (INDEX,
                           MODNAME (1:MODNAME_LEN),
                           TXTRFA)
IF (.NOT. STATUS) CALL LIB$SIGNAL (%VAL (STATUS))
! Search for alias names in index 2
  STATUS = LBR$SEARCH (INDEX,
                       2,
                       TXTRFA,
                       SEARCH)

END
INTEGER FUNCTION SEARCH (ALIASNAME, RFA)
! Function called for each alias name pointing to MODNAME
! Displays the alias name
INTEGER STATUS_OK,        ! Good return status
        RFA (2)           ! RFA of module
PARAMETER (STATUS_OK = 1) ! Odd number
CHARACTER*(*) ALIASNAME   ! Name of module
! Display module name
TYPE *, MODNAME

! Exit
SEARCH = STATUS_OK
END

12.2.6 Accessing Module Headers

You can store user information in the header of each module up to the total size of the header specified at library creation time in the CRE$L_UHDMAX option. The total size of each header in bytes is the value of MHD$B_USRDAT plus the value assigned to the CRE$L_UHDMAX option. The value of MHD$B_USRDAT is defined by the macro $MHDDEF; the default value is 16 bytes.

To put user data into a module header, first locate the module with LBR$LOOKUP_KEY; then move the data to the module header by invoking LBR$SET_MODULE, specifying the first argument (index value returned by LBR$INI_CONTROL), the second argument (RFA returned by LBR$LOOKUP_KEY), and the fifth argument (character string containing the user data).

To read user data from a module header, first locate the module with LBR$LOOKUP_KEY; then, retrieve the entire module header by invoking LBR$SET_MODULE, specifying the first, second, third (character string to receive the contents of the module header), and fourth (length of the module header) arguments. The user data starts at the byte offset defined by MHD$B_USRDAT. Convert this value to a character string subscript by adding 1.

Example 12-7 displays the user data portion of module headers on SYS$OUTPUT and applies updates from SYS$INPUT.

Example 12-7 Displaying the Module Header

   .
   .
   .
SUBROUTINE MODHEAD (INDEX)
! Modifies module headers

INTEGER STATUS,        ! Return status
        INDEX,         ! Library index
        TXTRFA (2)     ! RFA of module
CHARACTER*31 MODNAME   ! Name of module
INTEGER MODNAME_LEN    ! Length of module name
CHARACTER*80 HEADER    ! Module header
INTEGER HEADER_LEN     ! Length of module header
INTEGER USER_START     ! Start of user data in header
CHARACTER*64 USERDATA  ! User data part of header
INTEGER*2 USERDATA_LEN ! Length of user data
! VMS library procedures
INTEGER LBR$LOOKUP_KEY,
        LBR$SET_MODULE,
        LIB$GET_INPUT,
        LIB$PUT_OUTPUT,
        CLI$GET_VALUE,
        LIB$LOCC
! Offset to user data --- defined in $MHDDEF
EXTERNAL MHD$B_USRDAT
! Return codes
EXTERNAL LBR$_KEYNOTFND, ! Key not found
         DOLIB_NOMOD     ! No such module
! Calculate start of user data in header
USER_START = %LOC (MHD$B_USRDAT) + 1
! Get module name from /MODHEAD on command line
STATUS = CLI$GET_VALUE ('MODHEAD', MODNAME)
! Get module headers until bad return status
! which indicates end of qualifier values
DO WHILE (STATUS)

  ! Calculate length of module name
  MODNAME_LEN = LIB$LOCC (' ', MODNAME) - 1
  ! Look up module name in library index
  STATUS = LBR$LOOKUP_KEY (INDEX,
                           MODNAME (1:MODNAME_LEN),
                           TXTRFA)

  ! Get header if module exists
  IF (STATUS) THEN
    STATUS = LBR$SET_MODULE (INDEX,
                             TXTRFA,
                             HEADER,
                             HEADER_LEN)
    IF (.NOT. STATUS) CALL LIB$SIGNAL (%VAL (STATUS))
    ! Display header and solicit replacement
    STATUS = LIB$PUT_OUTPUT
    ('User data for module '//MODNAME (1:MODNAME_LEN)//':')
    IF (.NOT. STATUS) CALL LIB$SIGNAL (%VAL (STATUS))
    STATUS = LIB$PUT_OUTPUT
    (HEADER (USER_START:HEADER_LEN))
    IF (.NOT. STATUS) CALL LIB$SIGNAL (%VAL (STATUS))
    STATUS = LIB$PUT_OUTPUT
    ('Enter replacement text below or just hit return:')
    IF (.NOT. STATUS) CALL LIB$SIGNAL (%VAL (STATUS))
    STATUS = LIB$GET_INPUT (USERDATA,, USERDATA_LEN)
    IF (.NOT. STATUS) CALL LIB$SIGNAL (%VAL (STATUS))
    ! Replace user data
    IF (USERDATA_LEN .GT. 0) THEN
      STATUS = LBR$SET_MODULE (INDEX,
                               TXTRFA,,,
                               USERDATA (1:USERDATA_LEN))
    END IF

    ! Issue warning if module does not exist
  ELSE IF (STATUS .EQ. %LOC (LBR$_KEYNOTFND)) THEN
    CALL LIB$SIGNAL (DOLIB_NOMOD,
                     %VAL (1),
                     MODNAME (1:MODNAME_LEN))
  ELSE
    CALL LIB$SIGNAL (%VAL (STATUS))
  END IF

  ! Get another module name
  STATUS = CLI$GET_VALUE ('MODHEAD', MODNAME)
END DO

! Exit
END

12.2.7 Reading Library Headers

Call LBR$GET_HEADER to obtain general information concerning the library. Pass the value returned by LBR$INI_CONTROL as the first argument. LBR$GET_HEADER returns the information to the second argument, which must be an array of 128 longwords. The LHI symbols identify the significant longwords of the array by their byte offsets into the array. Convert these values to subscripts by dividing by 4 and adding 1.

Example 12-8 reads the library header and displays some information from it.

Example 12-8 Reading Library Headers

   .
   .
   .
SUBROUTINE TYPEINFO (INDEX)
! Types the type, major ID, and minor ID
! of a library to SYS$OUTPUT

INTEGER STATUS             ! Return status
        INDEX,             ! Library index
        HEADER (128),      ! Structure for header information
        TYPE,              ! Subscripts for header structure
        MAJOR_ID,
        MINOR_ID
CHARACTER*8 MAJOR_ID_TEXT, ! Display info in character format
            MINOR_ID_TEXT
! VMS library procedures
INTEGER LBR$GET_HEADER,
        LIB$PUT_OUTPUT
! Offsets for header --- defined in $LHIDEF
EXTERNAL LHI$L_TYPE,
         LHI$L_MAJORID,
         LHI$L_MINORID
! Library type values --- defined in $LBRDEF
EXTERNAL LBR$C_TYP_OBJ,
         LBR$C_TYP_MLB,
         LBR$C_TYP_HLP,
         LBR$C_TYP_TXT
! Get header information
STATUS = LBR$GET_HEADER (INDEX, HEADER)
IF (.NOT. STATUS) CALL LIB$SIGNAL (%VAL (STATUS))
! Calculate subscripts for header structure
TYPE = %LOC (LHI$L_TYPE) / 4 + 1
MAJOR_ID = %LOC (LHI$L_MAJORID) / 4 + 1
MINOR_ID = %LOC (LHI$L_MINORID) / 4 + 1
! Display library type
IF (HEADER (TYPE) .EQ. %LOC (LBR$C_TYP_OBJ)) THEN
  STATUS = LIB$PUT_OUTPUT ('Library type: object')
ELSE IF (HEADER (TYPE) .EQ. %LOC (LBR$C_TYP_MLB)) THEN
  STATUS = LIB$PUT_OUTPUT ('Library type: macro')
ELSE IF (HEADER (TYPE) .EQ. %LOC (LBR$C_TYP_HLP)) THEN
  STATUS = LIB$PUT_OUTPUT ('Library type: help')
ELSE IF (HEADER (TYPE) .EQ. %LOC (LBR$C_TYP_TXT)) THEN
  STATUS = LIB$PUT_OUTPUT ('Library type: text')
ELSE
  STATUS = LIB$PUT_OUTPUT ('Library type: unknown')
END IF
IF (.NOT. STATUS) CALL LIB$SIGNAL (%VAL (STATUS))
! Convert and display major ID
WRITE (UNIT=MAJOR_ID_TEXT,
       FMT='(I)') HEADER (MAJOR_ID)
STATUS = LIB$PUT_OUTPUT ('Major ID: '//MAJOR_ID_TEXT)
IF (.NOT. STATUS) CALL LIB$SIGNAL (%VAL (STATUS))
! Convert and display minor ID
WRITE (UNIT=MINOR_ID_TEXT,
       FMT='(I)') HEADER (MINOR_ID)
STATUS = LIB$PUT_OUTPUT ('Minor ID: '//MINOR_ID_TEXT)
IF (.NOT. STATUS) CALL LIB$SIGNAL (%VAL (STATUS))

! Exit
END

12.2.8 Displaying Help Text

You can display text from a help library by calling the LBR$OUTPUT_HELP routine and specifying the output routine, the keywords, and the name of the library. You must also specify the input routine if the prompting mode flag is set or if the flags argument is omitted.

Note

If you specify subprograms in an argument list, they must be declared as external.

You can use the LIB$PUT_OUTPUT and LIB$GET_INPUT routines to specify the output routine and the input routine. (If you use your own routines, make sure the argument lists are the same as for LIB$PUT_OUTPUT and LIB$GET_INPUT.) Do not call LBR$INI_CONTROL and LBR$OPEN before calling LBR$OUTPUT_HELP.

Example 12-9 solicits keywords from SYS$INPUT and displays the text associated with those keywords on SYS$OUTPUT, thus inhibiting the prompting facility.

Example 12-9 Displaying Text from a Help Library

PROGRAM GET_HELP

! Prints help text from a help library
CHARACTER*31 LIBSPEC   ! Library name
CHARACTER*15 KEYWORD   ! Keyword in help library
INTEGER*2 LIBSPEC_LEN, ! Length of name
          KEYWORD_LEN  ! Length of keyword
INTEGER FLAGS,         ! Help flags
        STATUS         ! Return status
! VMS library procedures
INTEGER LBR$OUTPUT_HELP,
        LIB$GET_INPUT,
        LIB$PUT_OUTPUT
EXTERNAL LIB$GET_INPUT,
         LIB$PUT_OUTPUT
! Error codes
EXTERNAL RMS$_EOF,      ! End-of-file
         LIB$_INPSTRTRU ! Input string truncated
! Flag values --- defined in $HLPDEF
EXTERNAL HLP$M_PROMPT,
         HLP$M_PROCESS,
         HLP$M_GROUP,
         HLP$M_SYSTEM,
         HLP$M_LIBLIST,
         HLP$M_HELP
! Get library name
STATUS = LIB$GET_INPUT (LIBSPEC,
                        'Library: ',
                        LIBSPEC_LEN)
IF (.NOT. STATUS) CALL LIB$SIGNAL (%VAL (STATUS))
IF (LIBSPEC_LEN .EQ. 0) THEN
  LIBSPEC = 'HELPLIB'
  LIBSPEC_LEN = 7
END IF
! Set flags for no prompting
FLAGS = %LOC (HLP$_PROCESS) +
        %LOC (HLP$_GROUP) +
        %LOC (HLP$_SYSTEM)

! Get first keyword
STATUS = LIB$GET_INPUT (KEYWORD,
                        'Keyword or Ctrl/Z: ',
                        KEYWORD_LEN)
IF ((.NOT. STATUS) .AND.
    (STATUS .NE. %LOC (LIB$_INPSTRTRU)) .AND.
    (STATUS .NE. %LOC (RMS$_EOF))) THEN
  CALL LIB$SIGNAL (%VAL (STATUS))
END IF
! Display text until end-of-file
DO WHILE (STATUS .NE. %LOC (RMS$_EOF))
  STATUS = LBR$OUTPUT_HELP (LIB$PUT_OUTPUT,,
                            KEYWORD (1:KEYWORD_LEN),
                            LIBSPEC (1:LIBSPEC_LEN),
                            FLAGS,
                            LIB$GET_INPUT)
  IF (.NOT. STATUS) CALL LIB$SIGNAL (%VAL (STATUS))
  ! Get another keyword
  STATUS = LIB$GET_INPUT (KEYWORD,
                          'Keyword or Ctrl/Z: ',
                          KEYWORD_LEN)
  IF ((.NOT. STATUS) .AND.
      (STATUS .NE. %LOC (LIB$_INPSTRTRU)) .AND.
      (STATUS .NE. %LOC (RMS$_EOF))) THEN
    CALL LIB$SIGNAL (%VAL (STATUS))
  END IF
END DO

! Exit
END

12.2.9 Listing and Processing Index Entries

You can process index entries an entry at a time by invoking LBR$GET_INDEX. The fourth argument specifies a match name for the entry or entries in the index to be processed: you can include the asterisk (*) and percent (%) characters in the match name for generic processing. For example, MOD* means all entries whose names begin with MOD; and MOD% means all entries whose names are four characters and begin with MOD.

The third argument names a user-written routine that is executed once for each index entry specified by the fourth argument. The routine must be a function declared as external that returns a success (odd number) or failure (even number) status. LBR$GET_INDEX processing stops on a return status of failure. Declare the first argument passed to the function as a passed-length character argument; this argument contains the name of the index entry. Declare the second argument as an integer array of two elements.

Example 12-10 obtains a match name from the command line and displays the names of the matching entries from index 1 (the index containing the names of the modules).

Example 12-10 Displaying Index Entries

SUBROUTINE LIST (INDEX)
! Lists modules in the library

INTEGER STATUS,        ! Return status
        INDEX,         ! Library index
CHARACTER*31 MATCHNAME ! Name of module to list
INTEGER MATCHNAME_LEN  ! Length of match name
! VMS library procedures
INTEGER address LBR$GET_INDEX,
        LIB$LOCC
! Match routine
INTEGER MATCH
EXTERNAL MATCH
! Get module name and calculate length
CALL CLI$GET_VALUE ('LIST', MATCHNAME)
MATCHNAME_LEN = LIB$LOCC (' ', MATCHNAME) - 1
! Call routine to display module names
STATUS = LBR$GET_INDEX (INDEX,
                          1, ! Primary index
                          MATCH,
                          MATCHNAME (1:MATCHNAME_LEN))
IF (.NOT. STATUS) CALL LIB$SIGNAL (%VAL (STATUS))

! Exit
END
INTEGER FUNCTION MATCH (MODNAME, RFA)
! Function called for each module matched by MATCHNAME
! Displays the module name
INTEGER STATUS_OK,        ! Good return status
        RFA (2)           ! RFA of module name in index
PARAMETER (STATUS_OK = 1) ! Odd value
CHARACTER*(*) MODNAME     ! Name of module
! Display the name
TYPE *, MODNAME ! Display module name

! Exit
MATCH = STATUS_OK
END

12.3 LBR Routines

This section describes the individual LBR routines.


LBR$CLOSE

The LBR$CLOSE routine closes an open library.

Format

LBR$CLOSE library_index


RETURNS


OpenVMS usage: cond_value
type: longword (unsigned)
access: write only
mechanism: by value

Longword condition value. Most utility routines return a condition value in R0. Condition values that this routine can return are listed under Condition Values Returned.


Argument

library_index


OpenVMS usage: longword_unsigned
type: longword (unsigned)
access: read only
mechanism: by reference

Library control index returned by the LBR$INI_CONTROL routine. The library_index argument is the address of the longword that contains the index.

Description

When you are finished working with a library, you should call LBR$CLOSE to close it. Upon successful completion, LBR$CLOSE closes the open library and deallocates all of the memory used for processing it.

Condition Values Returned

LBR$_ILLCTL Specified library control index not valid.
LBR$_LIBNOTOPN Specified library not open.

LBR$DELETE_DATA

The LBR$DELETE_DATA routine deletes the module header and data associated with the specified module.

Format

LBR$DELETE_DATA library_index ,txtrfa


RETURNS


OpenVMS usage: cond_value
type: longword (unsigned)
access: write only
mechanism: by value

Longword condition value. Most utility routines return a condition value in R0. Condition values that this routine can return are listed under Condition Values Returned.


Arguments

library_index


OpenVMS usage: longword_unsigned
type: longword (unsigned)
access: read only
mechanism: by reference

Library control index returned by the LBR$INI_CONTROL routine. The library_index argument is the address of the longword that contains the index.

txtrfa


OpenVMS usage: vector_longword_unsigned
type: longword (unsigned)
access: read only
mechanism: by reference

Record's file address (RFA) of the module header for the module you want to delete. The txtrfa argument is the address of the 2-longword array that contains the RFA. You can obtain the RFA of a module header by calling LBR$LOOKUP_exit KEY or LBR$PUT_RECORD.

Description

If you want to delete a library module, you must first call LBR$DELETE_KEY to delete any keys that point to it. If no library index keys are pointing to the module header, LBR$DELETE_DATA deletes the module header and associated data records; otherwise, this routine returns the error LBR$_STILLKEYS.

Note that other LBR routines may reuse data blocks that contain no data.


Condition Values Returned

LBR$_ILLCTL Specified library control index not valid.
LBR$_INVRFA Specified RFA not valid.
LBR$_LIBNOTOPN Specified library not open.
LBR$_STILLKEYS Keys in other indexes still point at the module header. Therefore, the specified module was not deleted.


Previous Next Contents Index