54 SUBROUTINE nemtbd(LUN,ITAB,NSEQ,NEMS,IRPS,KNTS)
59 CHARACTER*128 BORT_STR
60 CHARACTER*8 NEMO,NEMS,NEMT,NEMF
61 CHARACTER*6 ADN30,CLEMON
63 dimension nems(*),irps(*),knts(*)
69 IF(itab.LE.0 .OR. itab.GT.
ntbd(lun))
GOTO 900
87 nemo =
tabd(itab,lun)(7:14)
89 CALL uptdd(itab,lun,0,ndsc)
91 IF(idsc.LT.
ifxy(
'300000'))
GOTO 901
92 IF(idsc.GT.
ifxy(
'363255'))
GOTO 901
99 IF(nseq+1.GT.
maxcd)
GOTO 903
100 CALL uptdd(itab,lun,j,idsc)
102 CALL numtab(lun,idsc,nemt,tab,iret)
111 knts(nseq+1) = abs(iret)
112 ELSEIF(iret.GT.0)
THEN
118 ELSEIF(tab.EQ.
'F')
THEN
122 IF(.NOT.rep)
GOTO 904
125 ELSEIF(tab.EQ.
'D'.OR.tab.EQ.
'C')
THEN
129 ELSEIF(tab.EQ.
'B')
THEN
132 IF((nemt(1:1).EQ.
'.').AND.(j.LT.ndsc))
THEN
136 CALL uptdd(itab,lun,j+1,idsc)
138 CALL numtab(lun,idsc,nemf,tab,iret)
140 IF(tab.NE.
'B')
GOTO 906
152900
WRITE(bort_str,
'("BUFRLIB: NEMTBD - ITAB (",I7,") NOT FOUND IN '//
155901
WRITE(bort_str,
'("BUFRLIB: NEMTBD - INTEGER REPRESENTATION OF '//
156 .
'DESCRIPTOR FOR TABLE D MNEMONIC ",A," (",I7,") IS OUTSIDE '//
157 .
'RANGE 0-65535 (65535 -> 3-63-255)")') nemo,idsc
159902
WRITE(bort_str,
'("BUFRLIB: NEMTBD - TABLE D MNEMONIC ",A," IS A'//
160 .
' ZERO LENGTH SEQUENCE")') nemo
162903
WRITE(bort_str,
'("BUFRLIB: NEMTBD - THERE ARE MORE THAN '//
163 .
'(",I4,") DESCRIPTORS (THE LIMIT) IN TABLE D SEQUENCE '//
164 .
'MNEMONIC ",A)')
maxcd, nemo
166904
WRITE(bort_str,
'("BUFRLIB: NEMTBD - REPLICATOR IS OUT OF ORDER '//
167 .
'IN TABLE D SEQUENCE MNEMONIC ",A)') nemo
169905 clemon = adn30(idsc,6)
170 WRITE(bort_str,
'("BUFRLIB: NEMTBD - UNRECOGNIZED DESCRIPTOR '//
171 .
'",A," IN TABLE D SEQUENCE MNEMONIC ",A)') clemon,nemo
173906
WRITE(bort_str,
'("BUFRLIB: NEMTBD - A ''FOLLOWING VALUE'' '//
174 .
'MNEMONIC (",A,") IS FROM TABLE ",A,", IT MUST BE FROM TABLE B'//
subroutine bort(STR)
This subroutine calls subroutine errwrt() to log an error message, then calls subroutine bort_exit() ...
function ifxy(ADSC)
This function converts an FXY value from its 6 character representation to its bit-wise (integer) rep...
This module contains array and variable declarations used to store DX BUFR tables internally for mult...
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.
character *600, dimension(:,:), allocatable tabd
Table D entries for each internal I/O stream.
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)
This subroutine returns information about a descriptor from the internal DX BUFR tables,...
subroutine rsvfvm(NEM1, NEM2)
THIS SUBROUTINE STEPS THROUGH THE "FOLLOWING VALUE" MNEMONIC NEM1 AND, FOR EACH "....
subroutine uptdd(ID, LUN, IENT, IRET)
THIS SUBROUTINE RETURNS THE BIT-WISE REPRESENTATION OF THE FXY VALUE CORRESPONDING TO,...