39 character*6 cds3(maxnc),numb,
adn30
55 IF (
ireadmt( lun ) .EQ. 1 )
THEN
69 CALL upds3 (
mbay(1,lun), maxnc, cds3, ncds3 )
71 ids3(ii) =
ifxy( cds3(ii) )
83 IF (
ncnem .GT. 0 )
THEN
85 DO WHILE ( (.NOT.incach) .AND. (ii.LE.
ncnem) )
86 IF ( ncds3 .EQ.
ndc(ii) )
THEN
89 DO WHILE ( (incach) .AND. (jj.LE.ncds3) )
90 IF ( ids3(jj) .EQ.
idcach(ii,jj) )
THEN
102 IF ( iprt .GE. 2 )
THEN
103 CALL errwrt(
'+++++++++++++++++++++++++++++++++++++++++++++++++')
104 errstr =
'BUFRLIB: READS3 - RE-USED CACHE LIST FOR ' //
cnem(ii)
106 CALL errwrt(
'+++++++++++++++++++++++++++++++++++++++++++++++++')
109 tamnem(lun) =
cnem(ii)
123 WRITE ( tamnem(lun),
'(A5,I3.3)')
'MSTTB', n
124 cseq =
'TABLE A MNEMONIC ' // tamnem(lun)
129 IF (
ncnem .GT. mxcnem )
GOTO 900
135 IF ( iprt .GE. 2 )
THEN
136 CALL errwrt(
'+++++++++++++++++++++++++++++++++++++++++++++++++')
137 errstr =
'BUFRLIB: READS3 - STORED CACHE LIST FOR ' //
140 CALL errwrt(
'+++++++++++++++++++++++++++++++++++++++++++++++++')
147 numb =
adn30( idn, 6 )
152 CALL stntbia ( n, lun, numb, tamnem(lun), cseq )
157 CALL stseq ( lun, irepct, idn, tamnem(lun), cseq, ids3, ncds3 )
164900
CALL bort(
'BUFRLIB: READS3 - MXCNEM OVERFLOW')
character *(*) function adn30(IDN, L30)
This function converts an FXY value from its bit-wise (integer) representation to its 5 or 6 characte...
subroutine bort(STR)
This subroutine calls subroutine errwrt() to log an error message, then calls subroutine bort_exit() ...
subroutine dxinit(LUN, IOI)
THIS SUBROUTINE INITIALIZES THE INTERNAL ARRAYS (IN MODULE TABABD) HOLDING THE DICTIONARY TABLE.
subroutine errwrt(STR)
This subroutine allows the user to specify a custom location for the logging of error and diagnostic ...
function ifxy(ADSC)
This function converts an FXY value from its 6 character representation to its bit-wise (integer) rep...
function igetntbi(LUN, CTB)
This function returns the next available index for storing an entry within a specified internal DX BU...
function igettdi(IFLAG)
DEPENDING ON THE VALUE OF THE INPUT FLAG, THIS FUNCTION EITHER RETURNS THE NEXT USABLE SCRATCH TABLE ...
integer function ireadmt(LUN)
This function checks the most recent BUFR message that was read via a call to one of the message-read...
subroutine makestab
THIS SUBROUTINE CONSTRUCTS AN INTERNAL JUMP/LINK TABLE WITHIN MODULE TABLES, USING THE INFORMATION WI...
This module contains array and variable declarations used to store BUFR messages internally for multi...
integer, dimension(:,:), allocatable mbay
Current BUFR message for each internal I/O stream.
This module contains array and variable declarations for the internal Table A mnemonic cache that is ...
integer, dimension(mxcnem, maxnc) idcach
Bit-wise representations of the child descriptors for the corresponding Table A mnemonic in cnem.
integer ncnem
Number of entries in the internal Table A mnemonic cache (up to a maximum of MXCNEM).
character *8, dimension(mxcnem) cnem
Table A mnemonics.
integer, dimension(mxcnem) ndc
Number of child descriptors for the corresponding Table A mnemonic in cnem.
subroutine reads3(LUN)
THIS SUBROUTINE READS THE SECTION 3 DESCRIPTORS FROM THE BUFR MESSAGE IN MBAY(1,LUN).
subroutine stntbia(N, LUN, NUMB, NEMO, CELSQ)
THIS SUBROUTINE STORES A NEW ENTRY WITHIN INTERNAL BUFR TABLE A.
void stseq(f77int *lun, f77int *irepct, f77int *idn, char nemo[8], char cseq[55], f77int cdesc[], f77int *ncdesc)
Given the bit-wise (integer) representation of a WMO-standard Table D descriptor, this subroutine use...
subroutine upds3(MBAY, LCDS3, CDS3, NDS3)
This subroutine returns the sequence of data descriptors contained within Section 3 of a BUFR message...