42 SUBROUTINE gettagre ( LUNIT, TAGI, NTAGI, TAGRE, NTAGRE, IRET )
48 CHARACTER*(*) TAGI, TAGRE
59 CALL status( lunit, lun, il, im )
60 IF ( il .EQ. 0 )
RETURN
61 IF ( inode(lun) .NE. inv(1,lun) )
RETURN
65 CALL fstag( lun, tagi, ntagi, 1, ni, iret )
66 IF ( iret .NE. 0 )
RETURN
68 IF ( nre .GT. 0 )
THEN
70 tagre =
tag(inv(nre,lun))
71 CALL strsuc( tagre, tagtmp, ltre )
74 IF (
tag(inv(ii,lun))(1:ltre) .EQ. tagre(1:ltre) )
THEN
subroutine fstag(LUN, UTAG, NUTAG, NIN, NOUT, IRET)
THIS SUBROUTINE FINDS THE (NUTAG)th OCCURRENCE OF MNEMONIC UTAG WITHIN THE CURRENT OVERALL SUBSET DEF...
subroutine gettagre(LUNIT, TAGI, NTAGI, TAGRE, NTAGRE, IRET)
This subroutine determines whether a specified Table B mnemonic references another Table B mnemonic w...
This module contains array and variable declarations used to store the internal jump/link table.
character *10, dimension(:), allocatable tag
Mnemonics in the jump/link table.
subroutine status(LUNIT, LUN, IL, IM)
This subroutine checks whether a specified Fortran logical unit number is currently connected to the ...
subroutine strsuc(STR1, STR2, LENS)
This subroutine removes leading and trailing blanks from a character string.