57 REAL*8 FUNCTION getvalnb ( LUNIT, TAGPV, NTAGPV, TAGNB, NTAGNB )
65 CHARACTER*(*) tagpv, tagnb
74 CALL status (lunit, lun, il, im )
75 IF ( il .GE. 0 )
RETURN
76 IF ( inode(lun) .NE. inv(1,lun) )
RETURN
81 CALL fstag( lun, tagpv, ntagpv, 1, npv, iret )
82 IF ( iret .NE. 0 )
RETURN
87 CALL fstag( lun, tagnb, ntagnb, npv, nnb, iret )
88 IF ( iret .NE. 0 )
RETURN
subroutine fstag(LUN, UTAG, NUTAG, NIN, NOUT, IRET)
THIS SUBROUTINE FINDS THE (NUTAG)th OCCURRENCE OF MNEMONIC UTAG WITHIN THE CURRENT OVERALL SUBSET DEF...
real *8 function getvalnb(LUNIT, TAGPV, NTAGPV, TAGNB, NTAGNB)
This function can be used to read a data value corresponding to a specific occurrence of a mnemonic w...
This module contains array and variable declarations used to store the internal jump/link table.
This module declares and initializes the BMISS variable.
real *8, public bmiss
Current placeholder value to represent "missing" data when reading from or writing to BUFR files; thi...
subroutine status(LUNIT, LUN, IL, IM)
This subroutine checks whether a specified Fortran logical unit number is currently connected to the ...