43 SUBROUTINE nemtbd(LUN,ITAB,NSEQ,NEMS,IRPS,KNTS)
48 CHARACTER*128 BORT_STR
49 CHARACTER*8 NEMO,NEMS,NEMT,NEMF
50 CHARACTER*6 ADN30,CLEMON
52 dimension nems(*),irps(*),knts(*)
58 IF(itab.LE.0 .OR. itab.GT.
ntbd(lun))
GOTO 900
76 nemo =
tabd(itab,lun)(7:14)
78 CALL uptdd(itab,lun,0,ndsc)
80 IF(idsc.LT.
ifxy(
'300000'))
GOTO 901
81 IF(idsc.GT.
ifxy(
'363255'))
GOTO 901
87 IF(nseq+1.GT.
maxcd)
GOTO 903
88 CALL uptdd(itab,lun,j,idsc)
90 CALL numtab(lun,idsc,nemt,tab,iret)
99 knts(nseq+1) = abs(iret)
100 ELSEIF(iret.GT.0)
THEN
106 ELSEIF(tab.EQ.
'F')
THEN
110 IF(.NOT.rep)
GOTO 904
113 ELSEIF(tab.EQ.
'D'.OR.tab.EQ.
'C')
THEN
117 ELSEIF(tab.EQ.
'B')
THEN
120 IF((nemt(1:1).EQ.
'.').AND.(j.LT.ndsc))
THEN
124 CALL uptdd(itab,lun,j+1,idsc)
126 CALL numtab(lun,idsc,nemf,tab,iret)
128 IF(tab.NE.
'B')
GOTO 906
140 900
WRITE(bort_str,
'("BUFRLIB: NEMTBD - ITAB (",I7,") NOT FOUND IN '//
143 901
WRITE(bort_str,
'("BUFRLIB: NEMTBD - INTEGER REPRESENTATION OF '//
144 .
'DESCRIPTOR FOR TABLE D MNEMONIC ",A," (",I7,") IS OUTSIDE '//
145 .
'RANGE 0-65535 (65535 -> 3-63-255)")') nemo,idsc
147 903
WRITE(bort_str,
'("BUFRLIB: NEMTBD - THERE ARE MORE THAN '//
148 .
'(",I4,") DESCRIPTORS (THE LIMIT) IN TABLE D SEQUENCE '//
149 .
'MNEMONIC ",A)')
maxcd, nemo
151 904
WRITE(bort_str,
'("BUFRLIB: NEMTBD - REPLICATOR IS OUT OF ORDER '//
152 .
'IN TABLE D SEQUENCE MNEMONIC ",A)') nemo
154 905 clemon = adn30(idsc,6)
155 WRITE(bort_str,
'("BUFRLIB: NEMTBD - UNRECOGNIZED DESCRIPTOR '//
156 .
'",A," IN TABLE D SEQUENCE MNEMONIC ",A)') clemon,nemo
158 906
WRITE(bort_str,
'("BUFRLIB: NEMTBD - A ''FOLLOWING VALUE'' '//
159 .
'MNEMONIC (",A,") IS FROM TABLE ",A,", IT MUST BE FROM TABLE B'//
subroutine bort(STR)
Log one error message and abort application program.
function ifxy(ADSC)
Convert an FXY value from its 6 character representation to its WMO bit-wise representation.
This module contains array and variable declarations used to store DX BUFR tables internally for mult...
character *600, dimension(:,:), allocatable tabd
Table D entries for each internal I/O stream.
integer, dimension(:), allocatable ntbd
Number of Table D entries for each internal I/O stream (up to a maximum of MAXTBD,...
integer, dimension(:,:), allocatable idnd
Bit-wise representations of the FXY values corresponding to tabd.
This module declares and initializes the MAXCD variable.
integer, public maxcd
Maximum number of child descriptors that can be included within the sequence definition of a Table D ...
subroutine nemtbd(LUN, ITAB, NSEQ, NEMS, IRPS, KNTS)
This subroutine returns information about a Table D descriptor from the internal DX BUFR tables.
subroutine numtab(LUN, IDN, NEMO, TAB, IRET)
Get information about a descriptor, based on the WMO bit-wise representation of an FXY value.
subroutine rsvfvm(NEM1, NEM2)
This subroutine steps through the "following value" mnemonic NEM1 and, for each "....
subroutine uptdd(ID, LUN, IENT, IRET)
Returns the WMO bit-wise representation of the FXY value corresponding to a child mnemonic of a Table...