NCEPLIBS-bufr 11.7.1
tabsub.f
Go to the documentation of this file.
1C> @file
2C> @author WOOLLEN @date 1994-01-06
3
4C> THIS SUBROUTINE BUILDS THE ENTIRE JUMP/LINK TREE (I.E.,
5C> INCLUDING RECURSIVELY RESOLVING ALL "CHILD" MNEMONICS) FOR A TABLE
6C> A MNEMONIC (NEMO) WITHIN THE INTERNAL JUMP/LINK TABLE.
7C>
8C> PROGRAM HISTORY LOG:
9C> 1994-01-06 J. WOOLLEN -- ORIGINAL AUTHOR
10C> 1998-07-08 J. WOOLLEN -- REPLACED CALL TO CRAY LIBRARY ROUTINE
11C> "ABORT" WITH CALL TO NEW INTERNAL BUFRLIB
12C> ROUTINE "BORT"
13C> 2000-09-19 J. WOOLLEN -- ADDED CAPABILITY TO ENCODE AND DECODE DATA
14C> USING THE OPERATOR DESCRIPTORS (BUFR TABLE
15C> C) FOR CHANGING WIDTH AND CHANGING SCALE
16C> 2003-11-04 J. ATOR -- ADDED DOCUMENTATION
17C> 2003-11-04 S. BENDER -- ADDED REMARKS/BUFRLIB ROUTINE
18C> INTERDEPENDENCIES
19C> 2003-11-04 D. KEYSER -- MAXJL (MAXIMUM NUMBER OF JUMP/LINK ENTRIES)
20C> INCREASED FROM 15000 TO 16000 (WAS IN
21C> VERIFICATION VERSION); UNIFIED/PORTABLE FOR
22C> WRF; ADDED HISTORY DOCUMENTATION; OUTPUTS
23C> MORE COMPLETE DIAGNOSTIC INFO WHEN ROUTINE
24C> TERMINATES ABNORMALLY
25C> 2005-11-29 J. ATOR -- ADDED SUPPORT FOR 207 AND 208 OPERATORS
26C> 2012-03-02 J. ATOR -- ADDED SUPPORT FOR 203 OPERATOR
27C> 2012-04-19 J. ATOR -- FIXED BUG FOR CASES WHERE A TABLE C OPERATOR
28C> IMMEDIATELY FOLLOWS A TABLE D SEQUENCE
29C> 2014-12-10 J. ATOR -- USE MODULES INSTEAD OF COMMON BLOCKS
30C> 2016-05-24 J. ATOR -- STORE TABLE C OPERATORS IN MODULE BITMAPS
31C> 2017-04-03 J. ATOR -- ADD A DIMENSION TO ALL TCO ARRAYS SO THAT
32C> EACH SUBSET DEFINITION IN THE JUMP/LINK
33C> TABLE HAS ITS OWN SET OF TABLE C OPERATORS
34C>
35C> USAGE: CALL TABSUB (LUN, NEMO)
36C> INPUT ARGUMENT LIST:
37C> LUN - INTEGER: I/O STREAM INDEX INTO INTERNAL MEMORY ARRAYS
38C> NEMO - CHARACTER*8: TABLE A MNEMONIC
39C>
40C> THIS ROUTINE CALLS: BORT INCTAB IOKOPER NEMTAB
41C> NEMTBD TABENT
42C> THIS ROUTINE IS CALLED BY: MAKESTAB
43C> Normally not called by any application
44C> programs.
45C>
46 SUBROUTINE tabsub(LUN,NEMO)
47
48 USE modv_mxtamc
49 USE modv_mxtco
50
51 USE moda_tables
52 USE moda_nmikrp
53 USE moda_nrv203
54 USE moda_bitmaps
55
56 COMMON /tabccc/ icdw,icsc,icrv,incw
57
58 CHARACTER*128 BORT_STR
59 CHARACTER*8 NEMO,NEMS
60 CHARACTER*1 TAB
61 dimension drop(10),jmp0(10),nodl(10),ntag(10,2)
62 LOGICAL DROP,LTAMC
63
64 DATA maxlim /10/
65
66C-----------------------------------------------------------------------
67C-----------------------------------------------------------------------
68
69C CHECK THE MNEMONIC
70C ------------------
71
72C Note that Table A mnemonics, in addition to being stored within
73C internal BUFR Table A array TABA(*,LUN), are also stored as
74C Table D mnemonics within internal BUFR Table D array TABD(*,LUN).
75C Thus, the following test is valid.
76
77 CALL nemtab(lun,nemo,idn,tab,itab)
78 IF(tab.NE.'D') GOTO 900
79
80C STORE A SUBSET NODE AND JUMP/LINK THE TREE
81C ------------------------------------------
82
83 CALL inctab(nemo,'SUB',node)
84 jump(node) = node+1
85 jmpb(node) = 0
86 link(node) = 0
87 ibt(node) = 0
88 irf(node) = 0
89 isc(node) = 0
90
91 CALL nemtbd(lun,itab,nseq,nem(1,1),irp(1,1),krp(1,1))
92 ntag(1,1) = 1
93 ntag(1,2) = nseq
94 jmp0(1) = node
95 nodl(1) = node
96 limb = 1
97
98 icdw = 0
99 icsc = 0
100 icrv = 1
101 incw = 0
102
103 ibtnrv = 0
104 ipfnrv = 0
105
106 IF(ntamc+1.GT.mxtamc) GOTO 913
107 inodtamc(ntamc+1) = node
108 ntco(ntamc+1) = 0
109 ltamc = .false.
110
111C THIS LOOP RESOLVES ENTITIES IN A SUBSET BY EMULATING RECURSION
112C --------------------------------------------------------------
113
1141 DO n=ntag(limb,1),ntag(limb,2)
115
116 ntag(limb,1) = n+1
117 drop(limb) = n.EQ.ntag(limb,2)
118
119 CALL nemtab(lun,nem(n,limb),idn,tab,itab)
120 nems = nem(n,limb)
121
122C SPECIAL TREATMENT FOR CERTAIN OPERATOR DESCRIPTORS (TAB=C)
123C ----------------------------------------------------------
124
125 IF(tab.EQ.'C') THEN
126 READ(nems,'(3X,I3)') iyyy
127 IF(itab.EQ.1) THEN
128 IF(iyyy.NE.0) THEN
129 IF(icdw.NE.0) GOTO 907
130 icdw = iyyy-128
131 ELSE
132 icdw = 0
133 ENDIF
134 ELSEIF(itab.EQ.2) THEN
135 IF(iyyy.NE.0) THEN
136 IF(icsc.NE.0) GOTO 908
137 icsc = iyyy-128
138 ELSE
139 icsc = 0
140 ENDIF
141 ELSEIF(itab.EQ.3) THEN
142 IF(iyyy.EQ.0) THEN
143
144C Stop applying new reference values to subset nodes.
145C Instead, revert to the use of standard Table B values.
146
147 IF(ipfnrv.EQ.0) GOTO 911
148 DO jj=ipfnrv,nnrv
149 ienrv(jj) = ntab
150 ENDDO
151 ipfnrv = 0
152 ELSEIF(iyyy.EQ.255) THEN
153
154C End the definition of new reference values.
155
156 ibtnrv = 0
157 ELSE
158
159C Begin the definition of new reference values.
160
161 IF(ibtnrv.NE.0) GOTO 909
162 ibtnrv = iyyy
163 ENDIF
164 ELSEIF(itab.EQ.7) THEN
165 IF(iyyy.GT.0) THEN
166 IF(icdw.NE.0) GOTO 907
167 IF(icsc.NE.0) GOTO 908
168 icdw = ((10*iyyy)+2)/3
169 icsc = iyyy
170 icrv = 10**iyyy
171 ELSE
172 icsc = 0
173 icdw = 0
174 icrv = 1
175 ENDIF
176 ELSEIF(itab.EQ.8) THEN
177 incw = iyyy
178 ELSEIF((itab.GE.21).AND.(iokoper(nems).EQ.1)) THEN
179
180C Save the location of this operator within the
181C jump/link table, for possible later use.
182
183 IF(.NOT.ltamc) THEN
184 ltamc = .true.
185 ntamc = ntamc+1
186 END IF
187 IF(ntco(ntamc)+1.GT.mxtco) GOTO 912
188 ntco(ntamc) = ntco(ntamc)+1
189 ctco(ntamc,ntco(ntamc)) = nems(1:6)
191 ENDIF
192 ELSE
193 nodl(limb) = ntab+1
194 irep = irp(n,limb)
195 iknt = krp(n,limb)
196 jum0 = jmp0(limb)
197 CALL tabent(lun,nems,tab,itab,irep,iknt,jum0)
198 ENDIF
199
200 IF(tab.EQ.'D') THEN
201
202C Note here how a new tree "LIMB" is created (and is then
203C immediately recursively resolved) whenever a Table D mnemonic
204C contains another Table D mnemonic as one of its children.
205
206 limb = limb+1
207 IF(limb.GT.maxlim) GOTO 901
208 CALL nemtbd(lun,itab,nseq,nem(1,limb),irp(1,limb),krp(1,limb))
209 ntag(limb,1) = 1
210 ntag(limb,2) = nseq
211 jmp0(limb) = ntab
212 GOTO 1
213 ELSEIF(drop(limb)) THEN
2142 link(nodl(limb)) = 0
215 limb = limb-1
216 IF(limb.EQ.0 ) THEN
217 IF(icrv.NE.1) GOTO 904
218 IF(icdw.NE.0) GOTO 902
219 IF(icsc.NE.0) GOTO 903
220 IF(incw.NE.0) GOTO 905
221 IF(ibtnrv.NE.0) GOTO 910
222 IF(ipfnrv.NE.0) THEN
223
224C One or more new reference values were defined for this
225C subset, but there was no subsequent 2-03-000 operator,
226C so set all IENRV(*) values for this subset to point to
227C the last element of the subset within the jump/link table.
228C Note that, if there had been a subsequent 2-03-000
229C operator, then these IENRV(*) values would have already
230C been properly set above.
231
232 DO jj=ipfnrv,nnrv
233 ienrv(jj) = ntab
234 ENDDO
235 ENDIF
236 GOTO 100
237 ENDIF
238 IF(drop(limb)) GOTO 2
239 link(nodl(limb)) = ntab+1
240 GOTO 1
241 ELSEIF(tab.NE.'C') THEN
242 link(nodl(limb)) = ntab+1
243 ENDIF
244
245 ENDDO
246
247 GOTO 906
248
249C EXITS
250C -----
251
252100 RETURN
253900 WRITE(bort_str,'("BUFRLIB: TABSUB - SUBSET NODE NOT IN TABLE D '//
254 . '(TAB=",A,") FOR INPUT MNEMONIC ",A)') tab,nemo
255 CALL bort(bort_str)
256901 WRITE(bort_str,'("BUFRLIB: TABSUB - THERE ARE TOO MANY NESTED '//
257 . 'TABLE D SEQUENCES (TREES) WITHIN INPUT MNEMONIC ",A," - THE '//
258 . 'LIMIT IS",I4)') nemo,maxlim
259 CALL bort(bort_str)
260902 WRITE(bort_str,'("BUFRLIB: TABSUB - A 2-01-YYY OPERATOR WAS '//
261 . 'NOT CANCELLED IN THE TREE BUILT FROM INPUT MNEMONIC ",A)') nemo
262 CALL bort(bort_str)
263903 WRITE(bort_str,'("BUFRLIB: TABSUB - A 2-02-YYY OPERATOR WAS '//
264 . 'NOT CANCELLED IN THE TREE BUILT FROM INPUT MNEMONIC ",A)') nemo
265 CALL bort(bort_str)
266904 WRITE(bort_str,'("BUFRLIB: TABSUB - A 2-07-YYY OPERATOR WAS '//
267 . 'NOT CANCELLED IN THE TREE BUILT FROM INPUT MNEMONIC ",A)') nemo
268 CALL bort(bort_str)
269905 WRITE(bort_str,'("BUFRLIB: TABSUB - A 2-08-YYY OPERATOR WAS '//
270 . 'NOT CANCELLED IN THE TREE BUILT FROM INPUT MNEMONIC ",A)') nemo
271 CALL bort(bort_str)
272906 WRITE(bort_str,'("BUFRLIB: TABSUB - ENTITIES WERE NOT '//
273 . 'SUCCESSFULLY RESOLVED (BY EMULATING RESURSION) FOR SUBSET '//
274 . 'DEFINED BY TBL A MNEM. ",A)') nemo
275 CALL bort(bort_str)
276907 WRITE(bort_str,'("BUFRLIB: TABSUB - THERE ARE TWO SIMULTANEOUS '//
277 . 'CHANGE DATA WIDTH OPERATIONS IN THE TREE BUILT FROM INPUT ' //
278 . 'MNEMONIC ",A)') nemo
279 CALL bort(bort_str)
280908 WRITE(bort_str,'("BUFRLIB: TABSUB - THERE ARE TWO SIMULTANEOUS '//
281 . 'CHANGE DATA SCALE OPERATIONS IN THE TREE BUILT FROM INPUT ' //
282 . 'MNEMONIC ",A)') nemo
283 CALL bort(bort_str)
284909 WRITE(bort_str,'("BUFRLIB: TABSUB - THERE ARE TWO SIMULTANEOUS '//
285 . 'CHANGE REF VALUE OPERATIONS IN THE TREE BUILT FROM INPUT ' //
286 . 'MNEMONIC ",A)') nemo
287 CALL bort(bort_str)
288910 WRITE(bort_str,'("BUFRLIB: TABSUB - A 2-03-YYY OPERATOR WAS '//
289 . 'APPLIED WITHOUT ANY SUBSEQUENT 2-03-255 OPERATOR FOR '//
290 . 'INPUT MNEMONIC ",A)') nemo
291 CALL bort(bort_str)
292911 WRITE(bort_str,'("BUFRLIB: TABSUB - A 2-03-000 OPERATOR WAS '//
293 . 'ENCOUNTERED WITHOUT ANY PRIOR 2-03-YYY OPERATOR FOR '//
294 . 'INPUT MNEMONIC ",A)') nemo
295 CALL bort(bort_str)
296912 CALL bort('BUFRLIB: TABSUB - MXTCO OVERFLOW')
297913 CALL bort('BUFRLIB: TABSUB - MXTAMC OVERFLOW')
298 END
subroutine bort(STR)
This subroutine calls subroutine errwrt() to log an error message, then calls subroutine bort_exit() ...
Definition: bort.f:23
subroutine inctab(ATAG, ATYP, NODE)
THIS SUBROUTINE RETURNS THE NEXT AVAILABLE POSITIONAL INDEX FOR WRITING INTO THE INTERNAL JUMP/LINK T...
Definition: inctab.f:44
integer function iokoper(NEMO)
This function determines whether a specified mnemonic is a Table C operator supported by the BUFRLIB ...
Definition: iokoper.f:24
This module contains array and variable declarations used to store bitmaps internally within a data s...
Definition: moda_bitmaps.F:13
integer, dimension(:), allocatable inodtamc
Entries within jump/link table which contain Table A mnemonics.
Definition: moda_bitmaps.F:78
integer, dimension(:,:), allocatable inodtco
Entries within jump/link table which contain Table C operators.
Definition: moda_bitmaps.F:81
integer ntamc
Number of Table A mnemonics in jump/link table (up to a maximum of MXTAMC) which contain at least one...
Definition: moda_bitmaps.F:74
integer, dimension(:), allocatable ntco
Number of Table C operators (with an XX value of 21 or greater) within the data subset definition of ...
Definition: moda_bitmaps.F:79
character *6, dimension(:,:), allocatable ctco
Table C operators corresponding to inodtco.
Definition: moda_bitmaps.F:80
This module contains array and variable declarations for use with any 2-03-YYY (change reference valu...
Definition: moda_nrv203.F:15
integer nnrv
Number of entries in the jump/link table which contain new reference values (up to a maximum of MXNRV...
Definition: moda_nrv203.F:56
integer, dimension(:), allocatable ienrv
End of entry range in jump/link table, within which the corresponding new reference value in nrv will...
Definition: moda_nrv203.F:63
integer ipfnrv
A number between 1 and nnrv, denoting the first entry within the module arrays which applies to the c...
Definition: moda_nrv203.F:58
integer ibtnrv
Number of bits in Section 4 occupied by each new reference value for the current 2-03-YYY operator in...
Definition: moda_nrv203.F:57
This module contains array and variable declarations used to store the internal jump/link table.
Definition: moda_tables.F:13
integer, dimension(:), allocatable link
Link indices corresponding to tag, typ and jmpb:
Definition: moda_tables.F:136
integer, dimension(:), allocatable isc
Scale factors corresponding to tag and typ:
Definition: moda_tables.F:140
integer, dimension(:), allocatable jump
Jump forward indices corresponding to tag and typ:
Definition: moda_tables.F:135
integer, dimension(:), allocatable ibt
Bit widths corresponding to tag and typ:
Definition: moda_tables.F:138
integer ntab
Number of entries in the jump/link table.
Definition: moda_tables.F:131
integer, dimension(:), allocatable irf
Reference values corresponding to tag and typ:
Definition: moda_tables.F:139
integer, dimension(:), allocatable jmpb
Jump backward indices corresponding to tag and typ:
Definition: moda_tables.F:137
This module declares and initializes the MXTAMC variable.
Definition: modv_MXTAMC.f:13
integer mxtamc
Maximum number of Table A mnemonics in the internal jump/link table which contain at least one Table ...
Definition: modv_MXTAMC.f:20
This module declares and initializes the MXTCO variable.
Definition: modv_MXTCO.f:13
integer mxtco
Maximum number of Table C operators with an XX value of 21 or greater that can appear within the data...
Definition: modv_MXTCO.f:20
subroutine nemtab(LUN, NEMO, IDN, TAB, IRET)
This subroutine returns information about a descriptor from the internal DX BUFR tables,...
Definition: nemtab.f:45
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:55
subroutine tabent(LUN, NEMO, TAB, ITAB, IREP, IKNT, JUM0)
THIS SUBROUTINE BUILDS AND STORES AN ENTRY FOR A TABLE B OR TABLE D MNEMONIC (NEMO) WITHIN THE INTERN...
Definition: tabent.f:52
subroutine tabsub(LUN, NEMO)
THIS SUBROUTINE BUILDS THE ENTIRE JUMP/LINK TREE (I.E., INCLUDING RECURSIVELY RESOLVING ALL "CHILD" M...
Definition: tabsub.f:47