51 . NSCL, NREF, NBTS, IRET )
69 CALL status( lunit, lun, il, im )
70 IF ( il .EQ. 0 )
RETURN
71 IF ( inode(lun) .NE. inv(1,lun) )
RETURN
76 CALL fstag( lun, nemo, nnemo, 1, nidx, ierfst )
77 IF ( ierfst .NE. 0 )
RETURN
82 IF ( (
typ(node) .NE.
'NUM' ) .AND. (
typ(node) .NE.
'CHR' ) )
95 IF (
nnrv .GT. 0 )
THEN
102 CALL strsuc( nemo, tagn, ltn )
103 IF ( ( ltn .LE. 0 ) .OR. ( ltn .GT. 8 ) )
RETURN
106 IF ( ( node .NE.
inodnrv(jj) ) .AND.
107 . ( tagn(1:8) .EQ.
tagnrv(jj) ) .AND.
108 . ( node .GE.
isnrv(jj) ) .AND.
109 . ( node .LE.
ienrv(jj) ) )
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...
This module contains array and variable declarations for use with any 2-03-YYY (change reference valu...
integer nnrv
Number of entries in the jump/link table which contain new reference values (up to a maximum of MXNRV...
integer, dimension(:), allocatable ienrv
End of entry range in jump/link table, within which the corresponding new reference value in nrv will...
integer, dimension(:), allocatable isnrv
Start of entry range in jump/link table, within which the corresponding new reference value in nrv wi...
integer, dimension(:), allocatable inodnrv
Entries within jump/link table which contain new reference values.
integer *8, dimension(:), allocatable nrv
New reference values corresponding to inodnrv.
character *8, dimension(:), allocatable tagnrv
Table B mnemonic to which the corresponding new reference value in nrv applies.
This module contains array and variable declarations used to store the internal jump/link table.
integer, dimension(:), allocatable isc
Scale factors corresponding to tag and typ:
character *3, dimension(:), allocatable typ
Type indicators corresponding to tag:
integer, dimension(:), allocatable ibt
Bit widths corresponding to tag and typ:
integer, dimension(:), allocatable irf
Reference values corresponding to tag and typ:
subroutine nemspecs(LUNIT, NEMO, NNEMO, NSCL, NREF, NBTS, IRET)
Given a Table B mnemonic defined within a data subset, this subroutine returns the scale factor,...
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.