NCEPLIBS-bufr 11.7.1
makestab.f
Go to the documentation of this file.
1C> @file
2C> @author WOOLLEN @date 1994-01-06
3
4C> THIS SUBROUTINE CONSTRUCTS AN INTERNAL JUMP/LINK TABLE
5C> WITHIN MODULE TABLES, USING THE INFORMATION WITHIN THE
6C> INTERNAL BUFR TABLE ARRAYS (WITHIN MODULE TABABD) FOR ALL OF
7C> THE LUN (I.E., I/O STREAM INDEX) VALUES THAT ARE CURRENTLY DEFINED TO
8C> THE BUFR ARCHIVE LIBRARY SOFTWARE. NOTE THAT THE ENTIRE JUMP/LINK
9C> TABLE WILL ALWAYS BE COMPLETELY RECONSTRUCTED FROM SCRATCH, EVEN IF
10C> SOME OF THE INFORMATION WITHIN THE INTERNAL BUFR TABLE ARRAYS
11C> ALREADY EXISTED THERE AT THE TIME OF THE PREVIOUS CALL TO THIS
12C> SUBROUTINE, BECAUSE THERE MAY HAVE BEEN OTHER EVENTS THAT HAVE TAKEN
13C> PLACE SINCE THE PREVIOUS CALL TO THIS SUBROUTINE THAT HAVE NOT YET
14C> BEEN REFLECTED WITHIN THE INTERNAL JUMP/LINK TABLE, SUCH AS, E.G.
15C> THE UNLINKING OF AN LUN VALUE FROM THE BUFR ARCHIVE LIBRARY SOFTWARE
16C> VIA A CALL TO BUFR ARCHIVE LIBRARY SUBROUTINE CLOSBF.
17C>
18C> PROGRAM HISTORY LOG:
19C> 1994-01-06 J. WOOLLEN -- ORIGINAL AUTHOR
20C> 1995-06-28 J. WOOLLEN -- INCREASED THE SIZE OF INTERNAL BUFR TABLE
21C> ARRAYS IN ORDER TO HANDLE BIGGER FILES
22C> 1998-07-08 J. WOOLLEN -- REPLACED CALL TO CRAY LIBRARY ROUTINE
23C> "ABORT" WITH CALL TO NEW INTERNAL BUFRLIB
24C> ROUTINE "BORT"
25C> 1999-11-18 J. WOOLLEN -- THE NUMBER OF BUFR FILES WHICH CAN BE
26C> OPENED AT ONE TIME INCREASED FROM 10 TO 32
27C> (NECESSARY IN ORDER TO PROCESS MULTIPLE
28C> BUFR FILES UNDER THE MPI)
29C> 2003-11-04 J. ATOR -- ADDED DOCUMENTATION
30C> 2003-11-04 S. BENDER -- ADDED REMARKS/BUFRLIB ROUTINE
31C> INTERDEPENDENCIES
32C> 2003-11-04 D. KEYSER -- MAXJL (MAXIMUM NUMBER OF JUMP/LINK ENTRIES)
33C> INCREASED FROM 15000 TO 16000 (WAS IN
34C> VERIFICATION VERSION); UNIFIED/PORTABLE FOR
35C> WRF; ADDED HISTORY DOCUMENTATION; OUTPUTS
36C> MORE COMPLETE DIAGNOSTIC INFO WHEN ROUTINE
37C> TERMINATES ABNORMALLY; NOW ALLOWS FOR THE
38C> POSSIBILITY THAT A CONNECTED FILE MAY NOT
39C> CONTAIN ANY DICTIONARY TABLE INFO (E.G.,
40C> AN EMPTY FILE), SUBSEQUENT CONNECTED FILES
41C> WHICH ARE NOT EMPTY WILL NO LONGER GET
42C> TRIPPED UP BY THIS (THIS AVOIDS THE NEED
43C> FOR AN APPLICATION PROGRAM TO DISCONNECT
44C> ANY EMPTY FILES VIA A CALL TO CLOSBF)
45C> 2009-03-18 J. WOOLLEN -- ADDED LOGIC TO RESPOND TO THE CASES WHERE
46C> AN INPUT FILE'S TABLES CHANGE IN MIDSTREAM.
47C> THE NEW LOGIC MOSTLY ADDRESSES CASES WHERE
48C> OTHER FILES ARE CONNECTED TO THE TABLES OF
49C> THE FILE WHOSE TABLES HAVE CHANGED.
50C> 2009-06-25 J. ATOR -- TWEAK WOOLLEN LOGIC TO HANDLE SPECIAL CASE
51C> WHERE TABLE WAS RE-READ FOR A PARTICULAR
52C> LOGICAL UNIT BUT IS STILL THE SAME ACTUAL
53C> TABLE AS BEFORE AND IS STILL SHARING THAT
54C> TABLE WITH A DIFFERENT LOGICAL UNIT
55C> 2009-11-17 J. ATOR -- ADDED CHECK TO PREVENT WRITING OUT OF TABLE
56C> INFORMATION WHEN A TABLE HAS BEEN RE-READ
57C> WITHIN A SHARED LOGICAL UNIT BUT HASN'T
58C> REALLY CHANGED
59C> 2014-12-10 J. ATOR -- USE MODULES INSTEAD OF COMMON BLOCKS
60C> 2017-04-03 J. ATOR -- INCLUDE MODULE BITMAPS AND INITIALIZATION
61C> OF NTAMC
62C>
63C> USAGE: CALL MAKESTAB
64C>
65C> REMARKS:
66C> THIS ROUTINE CALLS: BORT CHEKSTAB CLOSMG CPBFDX
67C> ERRWRT ICMPDX ISHRDX STRCLN
68C> TABSUB WRDXTB
69C> THIS ROUTINE IS CALLED BY: RDBFDX RDMEMM RDUSDX READDX
70C> READERME READS3
71C> Normally not called by any application
72C> programs.
73C>
74 SUBROUTINE makestab
75
76 USE modv_bmiss
77 USE modv_maxjl
78 USE modv_nfiles
79
80 USE moda_usrint
81 USE moda_stbfr
82 USE moda_lushr
83 USE moda_xtab
84 USE moda_tababd
85 USE moda_tables
86 USE moda_nrv203
87 USE moda_bitmaps
88
89 COMMON /quiet/ iprt
90
91 CHARACTER*128 BORT_STR,ERRSTR
92 CHARACTER*8 NEMO
93 LOGICAL EXPAND
94
95C-----------------------------------------------------------------------
96C-----------------------------------------------------------------------
97
98C RESET POINTER TABLE AND STRING CACHE
99C ------------------------------------
100
101 ntab = 0
102 nnrv = 0
103 ntamc = 0
104 CALL strcln
105
106C FIGURE OUT WHICH UNITS SHARE TABLES
107C -----------------------------------
108
109C The LUS array is static between calls to this subroutine, and it
110C keeps track of which logical units share dictionary table
111C information:
112C if LUS(I) = 0, then IOLUN(I) does not share dictionary table
113C information with any other logical unit
114C if LUS(I) > 0, then IOLUN(I) shares dictionary table
115C information with logical unit IOLUN(LUS(I))
116C if LUS(I) < 0, then IOLUN(I) does not now, but at one point in
117C the past, shared dictionary table information
118C with logical unit IOLUN(ABS(LUS(I)))
119
120C The XTAB array is non-static and is recomputed within the below
121C loop during each call to this subroutine:
122C if XTAB(I) = .TRUE., then the dictionary table information
123C has changed for IOLUN(I) since the last
124C call to this subroutine
125C if XTAB(I) = .FALSE., then the dictionary table information
126C has not changed for IOLUN(I) since the
127C last call to this subroutine
128
129 DO lun=1,nfiles
130 xtab(lun) = .false.
131 IF(iolun(lun).EQ.0) THEN
132
133C Logical unit IOLUN(LUN) is not defined to the BUFRLIB.
134
135 lus(lun) = 0
136 ELSE IF(mtab(1,lun).EQ.0) THEN
137
138C New dictionary table information has been read for logical
139C unit IOLUN(LUN) since the last call to this subroutine.
140
141 xtab(lun) = .true.
142 IF(lus(lun).NE.0) THEN
143 IF(iolun(abs(lus(lun))).EQ.0) THEN
144 lus(lun) = 0
145 ELSE IF(lus(lun).GT.0) THEN
146
147C IOLUN(LUN) was sharing table information with logical
148C unit IOLUN(LUS(LUN)), so check whether the table
149C information has really changed. If not, then IOLUN(LUN)
150C just re-read a copy of the exact same table information
151C as before, and therefore it can continue to share with
152C logical unit IOLUN(LUS(LUN)).
153
154 IF(icmpdx(lus(lun),lun).EQ.1) THEN
155 xtab(lun) = .false.
156 CALL cpbfdx(lus(lun),lun)
157 ELSE
158 lus(lun) = (-1)*lus(lun)
159 ENDIF
160 ELSE IF(icmpdx(abs(lus(lun)),lun).EQ.1) THEN
161
162C IOLUN(LUN) was not sharing table information with logical
163C unit IOLUN(LUS(LUN)), but it did at one point in the past
164C and now once again has the same table information as that
165C logical unit. Since the two units shared table
166C information at one point in the past, allow them to do
167C so again.
168
169 xtab(lun) = .false.
170 lus(lun) = abs(lus(lun))
171 CALL cpbfdx(lus(lun),lun)
172 ENDIF
173 ENDIF
174 ELSE IF(lus(lun).GT.0) THEN
175
176C Logical unit IOLUN(LUN) is sharing table information with
177C logical unit IOLUN(LUS(LUN)), so make sure that the latter
178C unit is still defined to the BUFRLIB.
179
180 IF(iolun(lus(lun)).EQ.0) THEN
181 lus(lun) = 0
182 ELSE IF( xtab(lus(lun)) .AND.
183 + (icmpdx(lus(lun),lun).EQ.0) ) THEN
184
185C The table information for logical unit IOLUN(LUS(LUN))
186C just changed (in midstream). If IOLUN(LUN) is an output
187C file, then we will have to update it with the new table
188C information later on in this subroutine. Otherwise,
189C IOLUN(LUN) is an input file and is no longer sharing
190C tables with IOLUN(LUS(LUN)).
191
192 IF(iolun(lun).LT.0) lus(lun) = (-1)*lus(lun)
193 ENDIF
194 ELSE
195
196C Determine whether logical unit IOLUN(LUN) is sharing table
197C information with any other logical units.
198
199 lum = 1
200 DO WHILE ((lum.LT.lun).AND.(lus(lun).EQ.0))
201 IF(ishrdx(lum,lun).EQ.1) THEN
202 lus(lun) = lum
203 ELSE
204 lum = lum+1
205 ENDIF
206 ENDDO
207 ENDIF
208 ENDDO
209
210C INITIALIZE JUMP/LINK TABLES WITH SUBSETS/SEQUENCES/ELEMENTS
211C -----------------------------------------------------------
212
213 DO lun=1,nfiles
214
215 IF(iolun(lun).NE.0 .AND. ntba(lun).GT.0) THEN
216
217C Reset any existing inventory pointers.
218
219 IF(iomsg(lun).NE.0) THEN
220 IF(lus(lun).EQ.0) THEN
221 inc = (ntab+1)-mtab(1,lun)
222 ELSE
223 inc = mtab(1,lus(lun))-mtab(1,lun)
224 ENDIF
225 DO n=1,nval(lun)
226 inv(n,lun) = inv(n,lun)+inc
227 ENDDO
228 ENDIF
229
230 IF(lus(lun).LE.0) THEN
231
232C The dictionary table information corresponding to logical
233C unit IOLUN(LUN) has not yet been written into the internal
234C jump/link table, so add it in now.
235
236 CALL chekstab(lun)
237 DO itba=1,ntba(lun)
238 inod = ntab+1
239 nemo = taba(itba,lun)(4:11)
240 CALL tabsub(lun,nemo)
241 mtab(itba,lun) = inod
242 isc(inod) = ntab
243 ENDDO
244 ELSE IF( xtab(lus(lun)) .AND.
245 + (icmpdx(lus(lun),lun).EQ.0) ) THEN
246
247C Logical unit IOLUN(LUN) is an output file that is sharing
248C table information with logical unit IOLUN(LUS(LUN)) whose
249C table just changed (in midstream). Flush any existing data
250C messages from IOLUN(LUN), then update the table information
251C for this logical unit with the corresponding new table
252C information from IOLUN(LUS(LUN)), then update IOLUN(LUN)
253C itself with a copy of the new table information.
254
255 lunit = abs(iolun(lun))
256 IF(iomsg(lun).NE.0) CALL closmg(lunit)
257 CALL cpbfdx(lus(lun),lun)
258 lundx = abs(iolun(lus(lun)))
259 CALL wrdxtb(lundx,lunit)
260 ENDIF
261
262 ENDIF
263
264 ENDDO
265
266C STORE TYPES AND INITIAL VALUES AND COUNTS
267C -----------------------------------------
268
269 DO node=1,ntab
270 IF(typ(node).EQ.'SUB') THEN
271 vali(node) = 0
272 knti(node) = 1
273 itp(node) = 0
274 ELSEIF(typ(node).EQ.'SEQ') THEN
275 vali(node) = 0
276 knti(node) = 1
277 itp(node) = 0
278 ELSEIF(typ(node).EQ.'RPC') THEN
279 vali(node) = 0
280 knti(node) = 0
281 itp(node) = 0
282 ELSEIF(typ(node).EQ.'RPS') THEN
283 vali(node) = 0
284 knti(node) = 0
285 itp(node) = 0
286 ELSEIF(typ(node).EQ.'REP') THEN
287 vali(node) = bmiss
288 knti(node) = irf(node)
289 itp(node) = 0
290 ELSEIF(typ(node).EQ.'DRS') THEN
291 vali(node) = 0
292 knti(node) = 1
293 itp(node) = 1
294 ELSEIF(typ(node).EQ.'DRP') THEN
295 vali(node) = 0
296 knti(node) = 1
297 itp(node) = 1
298 ELSEIF(typ(node).EQ.'DRB') THEN
299 vali(node) = 0
300 knti(node) = 0
301 itp(node) = 1
302 ELSEIF(typ(node).EQ.'NUM') THEN
303 vali(node) = bmiss
304 knti(node) = 1
305 itp(node) = 2
306 ELSEIF(typ(node).EQ.'CHR') THEN
307 vali(node) = bmiss
308 knti(node) = 1
309 itp(node) = 3
310 ELSE
311 GOTO 901
312 ENDIF
313 ENDDO
314
315C SET UP EXPANSION SEGMENTS FOR TYPE 'SUB', 'DRP', AND 'DRS' NODES
316C ----------------------------------------------------------------
317
318 newn = 0
319
320 DO n=1,ntab
321 iseq(n,1) = 0
322 iseq(n,2) = 0
323 expand = typ(n).EQ.'SUB' .OR. typ(n).EQ.'DRP' .OR. typ(n).EQ.'DRS'
324 . .OR. typ(n).EQ.'REP' .OR. typ(n).EQ.'DRB'
325 IF(expand) THEN
326 iseq(n,1) = newn+1
327 noda = n
328 node = n+1
329 DO k=1,maxjl
330 knt(k) = 0
331 ENDDO
332 IF(typ(noda).EQ.'REP') knt(node) = knti(noda)
333 IF(typ(noda).NE.'REP') knt(node) = 1
334
3351 newn = newn+1
336 IF(newn.GT.maxjl) GOTO 902
337 jseq(newn) = node
338 knt(node) = max(knti(node),knt(node))
3392 IF(jump(node)*knt(node).GT.0) THEN
340 node = jump(node)
341 GOTO 1
342 ELSE IF(link(node).GT.0) THEN
343 node = link(node)
344 GOTO 1
345 ELSE
346 node = jmpb(node)
347 IF(node.EQ.noda) GOTO 3
348 IF(node.EQ.0 ) GOTO 903
349 knt(node) = max(knt(node)-1,0)
350 GOTO 2
351 ENDIF
3523 iseq(n,2) = newn
353 ENDIF
354 ENDDO
355
356C PRINT THE SEQUENCE TABLES
357C ------------------------
358
359 IF(iprt.GE.2) THEN
360 CALL errwrt('++++++++++++++BUFR ARCHIVE LIBRARY+++++++++++++++++')
361 DO i=1,ntab
362 WRITE ( unit=errstr, fmt='(A,I5,2X,A10,A5,6I8)' )
363 . 'BUFRLIB: MAKESTAB ', i, tag(i), typ(i), jmpb(i), jump(i),
364 . link(i), ibt(i), irf(i), isc(i)
365 CALL errwrt(errstr)
366 ENDDO
367 CALL errwrt('++++++++++++++BUFR ARCHIVE LIBRARY+++++++++++++++++')
368 CALL errwrt(' ')
369 ENDIF
370
371C EXITS
372C -----
373
374 RETURN
375900 WRITE(bort_str,'("BUFRLIB: MAKESTAB - MNEMONIC ",A," IS '//
376 . 'DUPLICATED IN SUBSET: ",A)') nemo,tag(n1)
377 CALL bort(bort_str)
378901 WRITE(bort_str,'("BUFRLIB: MAKESTAB - UNKNOWN TYPE ",A)')typ(node)
379 CALL bort(bort_str)
380902 WRITE(bort_str,'("BUFRLIB: MAKESTAB - NUMBER OF JSEQ ENTRIES IN'//
381 . ' JUMP/LINK TABLE EXCEEDS THE LIMIT (",I6,")")') maxjl
382 CALL bort(bort_str)
383903 WRITE(bort_str,'("BUFRLIB: MAKESTAB - NODE IS ZERO, FAILED TO '//
384 . 'CIRCULATE (TAG IS ",A,")")') tag(n)
385 CALL bort(bort_str)
386 END
subroutine bort(STR)
This subroutine calls subroutine errwrt() to log an error message, then calls subroutine bort_exit() ...
Definition: bort.f:23
subroutine chekstab(LUN)
THIS SUBROUTINE CHECKS THAT AN INTERNAL BUFR TABLE REPRESENTATION IS SELF-CONSISTENT AND FULLY DEFINE...
Definition: chekstab.f:40
subroutine closmg(LUNIN)
This subroutine closes the BUFR message that is currently open for writing within internal arrays ass...
Definition: closmg.f:41
subroutine cpbfdx(LUD, LUN)
THIS SUBROUTINE COPIES BUFR TABLE (DICTIONARY) MESSAGES FROM ONE LOCATION TO ANOTHER WITHIN INTERNAL ...
Definition: cpbfdx.f:36
subroutine errwrt(STR)
This subroutine allows the user to specify a custom location for the logging of error and diagnostic ...
Definition: errwrt.f:42
integer function icmpdx(LUD, LUN)
This function determines whether the full set of associated DX BUFR Table information is identical be...
Definition: icmpdx.f:34
integer function ishrdx(LUD, LUN)
This function determines whether the same DX BUFR Table is being shared between two Fortran logical u...
Definition: ishrdx.f:30
subroutine makestab
THIS SUBROUTINE CONSTRUCTS AN INTERNAL JUMP/LINK TABLE WITHIN MODULE TABLES, USING THE INFORMATION WI...
Definition: makestab.f:75
This module contains array and variable declarations used to store bitmaps internally within a data s...
Definition: moda_bitmaps.F:13
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
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
This module contains array and variable declarations used to store DX BUFR tables internally for mult...
Definition: moda_tababd.F:10
character *128, dimension(:,:), allocatable taba
Table A entries for each internal I/O stream.
Definition: moda_tababd.F:58
integer, dimension(:,:), allocatable mtab
Entries within jump/link table corresponding to taba.
Definition: moda_tababd.F:54
integer, dimension(:), allocatable ntba
Number of Table A entries for each internal I/O stream (up to a maximum of MAXTBA,...
Definition: moda_tababd.F:51
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 itp
Integer type values corresponding to typ:
Definition: moda_tables.F:141
integer, dimension(:), allocatable isc
Scale factors corresponding to tag and typ:
Definition: moda_tables.F:140
character *3, dimension(:), allocatable typ
Type indicators corresponding to tag:
Definition: moda_tables.F:133
integer, dimension(:), allocatable jump
Jump forward indices corresponding to tag and typ:
Definition: moda_tables.F:135
integer, dimension(:), allocatable knti
Initialized replication counts corresponding to typ and jump:
Definition: moda_tables.F:143
integer, dimension(:), allocatable ibt
Bit widths corresponding to tag and typ:
Definition: moda_tables.F:138
character *10, dimension(:), allocatable tag
Mnemonics in the jump/link table.
Definition: moda_tables.F:132
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
real *8, dimension(:), allocatable vali
Initialized data values corresponding to typ:
Definition: moda_tables.F:142
integer, dimension(:), allocatable jmpb
Jump backward indices corresponding to tag and typ:
Definition: moda_tables.F:137
This module declares and initializes the BMISS variable.
Definition: modv_BMISS.f90:9
real *8, public bmiss
Current placeholder value to represent "missing" data when reading from or writing to BUFR files; thi...
Definition: modv_BMISS.f90:15
This module declares and initializes the MAXJL variable.
Definition: modv_MAXJL.f:13
integer maxjl
Maximum number of entries in the internal jump/link table.
Definition: modv_MAXJL.f:18
This module declares and initializes the NFILES variable.
Definition: modv_NFILES.f90:12
integer, public nfiles
Maximum number of BUFR files that can be connected to the BUFRLIB software (for reading or writing) a...
Definition: modv_NFILES.f90:17
subroutine strcln
THIS SUBROUTINE RESETS THE MNEMONIC STRING CACHE IN THE BUFR INTERFACE (ARRAYS IN COMMON BLOCK /STCAC...
Definition: strcln.f:29
subroutine tabsub(LUN, NEMO)
THIS SUBROUTINE BUILDS THE ENTIRE JUMP/LINK TREE (I.E., INCLUDING RECURSIVELY RESOLVING ALL "CHILD" M...
Definition: tabsub.f:47
subroutine wrdxtb(LUNDX, LUNOT)
THIS SUBROUTINE WRITES BUFR TABLE (DICTIONARY) MESSAGES ASSOCIATED WITH THE BUFR FILE IN LUNDX TO THE...
Definition: wrdxtb.f:37