NCEPLIBS-bufr  12.0.0
nemtbd.f
Go to the documentation of this file.
1 C> @file
2 C> @brief Get information about a Table D descriptor
3 C>
4 C> @author J. Woollen @date 1994-01-06
5 
6 C> This subroutine returns information about a Table D descriptor
7 C> from the internal DX BUFR tables.
8 C>
9 C> @param[in] LUN - integer: Internal I/O stream index associated
10 C> with DX BUFR tables
11 C> @param[in] ITAB - integer: Positional index of descriptor within
12 C> internal Table D
13 C> @param[out] NSEQ - integer: Number of child mnemonics for descriptor
14 C> @param[out] NEMS - character*8(*): Child mnemonics
15 C> @param[out] IRPS - integer(*): Array of values corresponding to NEMS
16 C> - 5, if corresponding NEMS value is a Table D
17 C> mnemonic using 1-bit delayed replication
18 C> - 4, if corresponding NEMS value is a Table D
19 C> mnemonic using 8-bit delayed (stack) replication
20 C> - 3, if corresponding NEMS value is a Table D
21 C> mnemonic using 8-bit delayed replication
22 C> - 2, if corresponding NEMS value is a Table D
23 C> mnemonic using 16-bit delayed replication
24 C> - 1, if corresponding NEMS value is a Table D
25 C> mnemonic using regular (non-delayed) replication
26 C> - 0, otherwise
27 C> @param[out] KNTS -- integer(*): Array of values corresponding to NEMS
28 C> - Number of replications, if corresponding NEMS
29 C> value is a Table D mnemonic using regular
30 C> (non-delayed) replication
31 C> - 0, otherwise
32 C>
33 C> @remarks
34 C> - This subroutine does not recursively resolve any child mnemonics
35 C> which may themselves be Table D mnemonics. Instead, this subroutine
36 C> only returns the list of mnemonics which are direct children of the
37 C> descriptor referenced by ITAB. This information should have already
38 C> been stored into internal arrays via previous calls to subroutine
39 C> pktdd().
40 C>
41 C> @author J. Woollen @date 1994-01-06
42 
43  SUBROUTINE nemtbd(LUN,ITAB,NSEQ,NEMS,IRPS,KNTS)
44 
45  USE modv_maxcd
46  USE moda_tababd
47 
48  CHARACTER*128 BORT_STR
49  CHARACTER*8 NEMO,NEMS,NEMT,NEMF
50  CHARACTER*6 ADN30,CLEMON
51  CHARACTER*1 TAB
52  dimension nems(*),irps(*),knts(*)
53  LOGICAL REP
54 
55 C-----------------------------------------------------------------------
56 C-----------------------------------------------------------------------
57 
58  IF(itab.LE.0 .OR. itab.GT.ntbd(lun)) GOTO 900
59 
60  rep = .false.
61 
62 C CLEAR THE RETURN VALUES
63 C -----------------------
64 
65  nseq = 0
66 
67  DO i=1,maxcd
68  nems(i) = ' '
69  irps(i) = 0
70  knts(i) = 0
71  ENDDO
72 
73 C PARSE THE TABLE D ENTRY
74 C -----------------------
75 
76  nemo = tabd(itab,lun)(7:14)
77  idsc = idnd(itab,lun)
78  CALL uptdd(itab,lun,0,ndsc)
79 
80  IF(idsc.LT.ifxy('300000')) GOTO 901
81  IF(idsc.GT.ifxy('363255')) GOTO 901
82 
83 C Loop through each child mnemonic.
84 
85 c .... DK: What happens here if NDSC=0 ?
86  DO j=1,ndsc
87  IF(nseq+1.GT.maxcd) GOTO 903
88  CALL uptdd(itab,lun,j,idsc)
89 c .... get NEMT from IDSC
90  CALL numtab(lun,idsc,nemt,tab,iret)
91  IF(tab.EQ.'R') THEN
92  IF(rep) GOTO 904
93  rep = .true.
94  IF(iret.LT.0) THEN
95 
96 C F=1 regular (i.e. non-delayed) replication.
97 
98  irps(nseq+1) = 1
99  knts(nseq+1) = abs(iret)
100  ELSEIF(iret.GT.0) THEN
101 
102 C Delayed replication.
103 
104  irps(nseq+1) = iret
105  ENDIF
106  ELSEIF(tab.EQ.'F') THEN
107 
108 C Replication factor.
109 
110  IF(.NOT.rep) GOTO 904
111  irps(nseq+1) = iret
112  rep = .false.
113  ELSEIF(tab.EQ.'D'.OR.tab.EQ.'C') THEN
114  rep = .false.
115  nseq = nseq+1
116  nems(nseq) = nemt
117  ELSEIF(tab.EQ.'B') THEN
118  rep = .false.
119  nseq = nseq+1
120  IF((nemt(1:1).EQ.'.').AND.(j.LT.ndsc)) THEN
121 
122 C This is a "following value" mnemonic.
123 
124  CALL uptdd(itab,lun,j+1,idsc)
125 c .... get NEMF from IDSC
126  CALL numtab(lun,idsc,nemf,tab,iret)
127  CALL rsvfvm(nemt,nemf)
128  IF(tab.NE.'B') GOTO 906
129  ENDIF
130  nems(nseq) = nemt
131  ELSE
132  GOTO 905
133  ENDIF
134  ENDDO
135 
136 C EXITS
137 C -----
138 
139  RETURN
140 900 WRITE(bort_str,'("BUFRLIB: NEMTBD - ITAB (",I7,") NOT FOUND IN '//
141  . 'TABLE D")') itab
142  CALL bort(bort_str)
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
146  CALL bort(bort_str)
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
150  CALL bort(bort_str)
151 904 WRITE(bort_str,'("BUFRLIB: NEMTBD - REPLICATOR IS OUT OF ORDER '//
152  . 'IN TABLE D SEQUENCE MNEMONIC ",A)') nemo
153  CALL bort(bort_str)
154 905 clemon = adn30(idsc,6)
155  WRITE(bort_str,'("BUFRLIB: NEMTBD - UNRECOGNIZED DESCRIPTOR '//
156  . '",A," IN TABLE D SEQUENCE MNEMONIC ",A)') clemon,nemo
157  CALL bort(bort_str)
158 906 WRITE(bort_str,'("BUFRLIB: NEMTBD - A ''FOLLOWING VALUE'' '//
159  . 'MNEMONIC (",A,") IS FROM TABLE ",A,", IT MUST BE FROM TABLE B'//
160  . '")') nemf,tab
161  CALL bort(bort_str)
162  END
subroutine bort(STR)
Log one error message and abort application program.
Definition: bort.f:18
function ifxy(ADSC)
Convert an FXY value from its 6 character representation to its WMO bit-wise representation.
Definition: ifxy.f:34
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.
Definition: nemtbd.f:44
subroutine numtab(LUN, IDN, NEMO, TAB, IRET)
Get information about a descriptor, based on the WMO bit-wise representation of an FXY value.
Definition: numtab.f:42
subroutine rsvfvm(NEM1, NEM2)
This subroutine steps through the "following value" mnemonic NEM1 and, for each "....
Definition: rsvfvm.f:27
subroutine uptdd(ID, LUN, IENT, IRET)
Returns the WMO bit-wise representation of the FXY value corresponding to a child mnemonic of a Table...
Definition: uptdd.f:28