NCEPLIBS-bufr  12.0.0
ufbtab.f
Go to the documentation of this file.
1 C> @file
2 C> @brief Read one or more data values from every data subset in a
3 C> BUFR file
4 C>
5 C> @author J. Woollen @date 1994-01-06
6 
7 C> This subroutine reads through every data subset in a BUFR file
8 C> and returns one or more specified data values from each subset.
9 C>
10 C> This provides a useful way to scan the ranges of one or more
11 C> specified data values across all of the data subsets within an
12 C> entire BUFR file. It is similar to subroutine ufbtam(), except
13 C> that ufbtam() works on data subsets within internal arrays.
14 C>
15 C> It is the user's responsibility to ensure that TAB is dimensioned
16 C> sufficiently large enough to accommodate the number of data values
17 C> that are to be read from the BUFR file. Specifically, each row of
18 C> TAB will contain the data values read from a different data subset,
19 C> so the value I2 must be at least as large as the total number of data
20 C> subsets in the BUFR file.
21 C>
22 C> If logical unit ABS(LUNIN) has already been opened
23 C> via a previous call to subroutine openbf(), then this subroutine
24 C> will save the current file position, rewind the file to the
25 C> beginning, read through the entire file, and then restore it to its
26 C> previous file position. Otherwise, if logical unit ABS(LUNIN) has
27 C> not already been opened via a previous call to subroutine openbf(),
28 C> then this subroutine will open it via an internal call to
29 C> subroutine openbf(), read through the entire file, and then close
30 C> it via an internal call to subroutine closbf().
31 C>
32 C> @remarks
33 C> - If LUNIN < 0, the number of data subsets in the BUFR file will
34 C> still be returned in IRET; however, STR will be ignored,
35 C> and all of the values returned in TAB will contain the current
36 C> placeholder value for "missing" data.
37 C> - If any of the Table B mnemonics in STR are replicated within the
38 C> data subset definition for the BUFR file, then this subroutine will
39 C> only return the value corresponding to the first occurrence of each
40 C> such mnemonic (counting from the beginning of the data subset
41 C> definition) within the corresponding row of TAB.
42 C> - There are a few additional special mnemonics that can be
43 C> included within STR when calling this subroutine, and which in turn
44 C> will result in special information being returned within the
45 C> corresponding location in TAB:
46 C> - IREC - returns the number of the BUFR message within the
47 C> file pointed to by ABS(LUNIN) (counting from the
48 C> beginning of the file) in which the current data
49 C> subset resides
50 C> - ISUB - returns the number of the current data subset within
51 C> the BUFR message pointed to by IREC, counting from
52 C> the beginning of the message
53 C>
54 C> @param[in] LUNIN -- integer: Absolute value is Fortran logical
55 C> unit number for BUFR file
56 C> @param[out] TAB -- real*8(*,*): Data values
57 C> @param[in] I1 -- integer: First dimension of TAB as allocated
58 C> within the calling program
59 C> @param[in] I2 -- integer: Second dimension of TAB as allocated
60 C> within the calling program
61 C> @param[out] IRET -- integer: Number of data subsets in BUFR file
62 C> @param[in] STR -- character*(*): String of blank-separated
63 C> Table B mnemonics, in one-to-one correspondence
64 C> with the number of data values that will be read
65 C> from each data subset within the first dimension of
66 C> TAB (see [DX BUFR Tables](@ref dfbftab) for further
67 C> information about Table B mnemonics)
68 C>
69 C> @author J. Woollen @date 1994-01-06
70 
71  RECURSIVE SUBROUTINE ufbtab(LUNIN,TAB,I1,I2,IRET,STR)
72 
73  USE modv_bmiss
74  USE modv_im8b
75 
76  USE moda_usrint
77  USE moda_msgcwd
78  USE moda_unptyp
79  USE moda_bitbuf
80  USE moda_tables
81 
82  COMMON /usrstr/ nnod,ncon,nods(20),nodc(10),ivls(10),kons(10)
83  COMMON /acmode/ iac
84  COMMON /quiet / iprt
85 
86  CHARACTER*(*) str
87  CHARACTER*128 errstr
88  CHARACTER*40 cref
89  CHARACTER*10 tgs(100)
90  CHARACTER*8 subset,cval
91  equivalence(cval,rval)
92  INTEGER*8 ival,lref,ninc,mps,lps
93  LOGICAL openit,just_count
94  real*8 tab(i1,i2),rval,ups
95 
96  DATA maxtg /100/
97 
98 C-----------------------------------------------------------------------
99  mps(node) = 2_8**(ibt(node))-1
100  lps(lbit) = max(2_8**(lbit)-1,1)
101 C-----------------------------------------------------------------------
102 
103 C CHECK FOR I8 INTEGERS
104 C ---------------------
105 
106  IF(im8b) THEN
107  im8b=.false.
108 
109  CALL x84(lunin,my_lunin,1)
110  CALL x84(i1,my_i1,1)
111  CALL x84(i2,my_i2,1)
112  CALL ufbtab(my_lunin,tab,my_i1,my_i2,iret,str)
113  CALL x48(iret,iret,1)
114 
115  im8b=.true.
116  RETURN
117  ENDIF
118 
119 C SET COUNTERS TO ZERO
120 C --------------------
121 
122  iret = 0
123  irec = 0
124  isub = 0
125  iacc = iac
126 
127 C CHECK FOR COUNT SUBSET ONLY OPTION (RETURNING THE BUFRLIB'S GLOBAL
128 C VALUE FOR MISSING IN OUTPUT ARRAY) INDICATED BY NEGATIVE UNIT
129 C ------------------------------------------------------------------
130 
131  lunit = abs(lunin)
132  just_count = lunin.LT.lunit
133 
134 C Make sure OPENBF has been called at least once before trying to
135 C call STATUS; otherwise, STATUS might try to access array space
136 C that hasn't yet been dynamically allocated.
137  CALL openbf(0,'FIRST',0)
138 
139  CALL status(lunit,lun,il,im)
140  openit = il.EQ.0
141 
142  IF(openit) THEN
143 
144 C OPEN BUFR FILE CONNECTED TO UNIT LUNIT IF IT IS NOT ALREADY OPEN
145 C ----------------------------------------------------------------
146 
147  CALL openbf(lunit,'INX',lunit)
148  ELSE
149 
150 C IF BUFR FILE ALREADY OPENED, SAVE POSITION & REWIND TO FIRST DATA MSG
151 C ---------------------------------------------------------------------
152 
153  CALL rewnbf(lunit,0)
154  ENDIF
155 
156  iac = 1
157 
158 C SET THE OUTPUT ARRAY VALUES TO THE BUFRLIB'S GLOBAL VALUE FOR
159 C MISSING (BMISS)
160 C -------------------------------------------------------------
161 
162  DO j=1,i2
163  DO i=1,i1
164  tab(i,j) = bmiss
165  ENDDO
166  ENDDO
167 
168  IF(just_count) THEN
169 
170 C COME HERE FOR COUNT ONLY OPTION (OUTPUT ARRAY VALUES REMAIN MISSING)
171 C --------------------------------------------------------------------
172 
173  DO WHILE(ireadmg(-lunit,subset,jdate).GE.0)
174  iret = iret+nmsub(lunit)
175  ENDDO
176  GOTO 25
177  ENDIF
178 
179 C OTHERWISE, CHECK FOR SPECIAL TAGS IN STRING
180 C -------------------------------------------
181 
182  CALL parstr(str,tgs,maxtg,ntg,' ',.true.)
183  DO i=1,ntg
184  IF(tgs(i).EQ.'IREC') irec = i
185  IF(tgs(i).EQ.'ISUB') isub = i
186  ENDDO
187 
188 C READ A MESSAGE AND PARSE A STRING
189 C ---------------------------------
190 
191 10 IF(ireadmg(-lunit,subset,jdate).LT.0) GOTO 25
192  CALL string(str,lun,i1,0)
193  IF(irec.GT.0) nods(irec) = 0
194  IF(isub.GT.0) nods(isub) = 0
195 
196 C PARSE THE MESSAGE DEPENDING ON WHETHER COMPRESSED OR NOT
197 C --------------------------------------------------------
198 
199  if(msgunp(lun)==2) goto 115
200 
201 C ---------------------------------------------
202 C THIS BRANCH IS FOR UNCOMPRESSED MESSAGES
203 C ---------------------------------------------
204 C SEE IF THERE IS ANOTHER SUBSET IN THE MESSAGE
205 C ---------------------------------------------
206 
207 15 IF(nsub(lun).EQ.msub(lun)) GOTO 10
208  IF(iret+1.GT.i2) GOTO 99
209  iret = iret+1
210 
211  DO i=1,nnod
212  nods(i) = abs(nods(i))
213  ENDDO
214 
215 C PARSE THE STRING NODES FROM A SUBSET
216 C ------------------------------------
217 
218  if(msgunp(lun)==0) mbit = mbyt(lun)*8 + 16
219  if(msgunp(lun)==1) mbit = mbyt(lun)
220 
221  nbit = 0
222  n = 1
223  CALL usrtpl(lun,n,n)
224 20 IF(n+1.LE.nval(lun)) THEN
225  n = n+1
226  node = inv(n,lun)
227  mbit = mbit+nbit
228  nbit = ibt(node)
229  IF(itp(node).EQ.1) THEN
230  CALL upb8(ival,nbit,mbit,mbay(1,lun))
231  nbmp=int(ival)
232  CALL usrtpl(lun,n,nbmp)
233  ENDIF
234  DO i=1,nnod
235  IF(nods(i).EQ.node) THEN
236  IF(itp(node).EQ.1) THEN
237  CALL upb8(ival,nbit,mbit,mbay(1,lun))
238  tab(i,iret) = ival
239  ELSEIF(itp(node).EQ.2) THEN
240  CALL upb8(ival,nbit,mbit,mbay(1,lun))
241  IF(ival.LT.mps(node)) tab(i,iret) = ups(ival,node)
242  ELSEIF(itp(node).EQ.3) THEN
243  cval = ' '
244  kbit = mbit
245  CALL upc(cval,nbit/8,mbay(1,lun),kbit,.true.)
246  tab(i,iret) = rval
247  ENDIF
248  nods(i) = -nods(i)
249  GOTO 20
250  ENDIF
251  ENDDO
252  DO i=1,nnod
253  IF(nods(i).GT.0) GOTO 20
254  ENDDO
255  ENDIF
256 
257 C UPDATE THE SUBSET POINTERS BEFORE NEXT READ
258 C -------------------------------------------
259 
260  if(msgunp(lun)==0) then
261  ibit = mbyt(lun)*8
262  CALL upb(nbyt,16,mbay(1,lun),ibit)
263  mbyt(lun) = mbyt(lun) + nbyt
264  elseif(msgunp(lun)==1) then
265  mbyt(lun)=mbit
266  endif
267 
268  nsub(lun) = nsub(lun) + 1
269  IF(irec.GT.0) tab(irec,iret) = nmsg(lun)
270  IF(isub.GT.0) tab(isub,iret) = nsub(lun)
271  GOTO 15
272 
273 C ---------------------------------------------
274 C THIS BRANCH IS FOR COMPRESSED MESSAGES
275 C ---------------------------------------------
276 C STORE ANY MESSAGE AND/OR SUBSET COUNTERS
277 C ---------------------------------------------
278 
279 C CHECK ARRAY BOUNDS
280 C ------------------
281 
282 115 IF(iret+msub(lun).GT.i2) GOTO 99
283 
284 C STORE MESG/SUBS TOKENS
285 C ----------------------
286 
287  IF(irec.GT.0.OR.isub.GT.0) THEN
288  DO nsb=1,msub(lun)
289  IF(irec.GT.0) tab(irec,iret+nsb) = nmsg(lun)
290  IF(isub.GT.0) tab(isub,iret+nsb) = nsb
291  ENDDO
292  ENDIF
293 
294 C SETUP A NEW SUBSET TEMPLATE, PREPARE TO SUB-SURF
295 C ------------------------------------------------
296 
297  CALL usrtpl(lun,1,1)
298  ibit = mbyt(lun)
299  n = 0
300 
301 C UNCOMPRESS CHOSEN NODES INTO THE TAB ARRAY (FIRST OCCURANCES ONLY)
302 C ------------------------------------------------------------------
303 
304 C READ ELEMENTS LOOP
305 C ------------------
306 
307 120 DO n=n+1,nval(lun)
308  node = inv(n,lun)
309  nbit = ibt(node)
310  ityp = itp(node)
311 
312 C FIRST TIME IN RESET NODE INDEXES, OR CHECK FOR NODE(S) STILL NEEDED
313 C -------------------------------------------------------------------
314 
315  IF(n.EQ.1) THEN
316  DO i=1,nnod
317  nods(i) = abs(nods(i))
318  ENDDO
319  ELSE
320  DO i=1,nnod
321  IF(nods(i).GT.0) GOTO 125
322  ENDDO
323  GOTO 135
324  ENDIF
325 
326 C FIND THE EXTENT OF THE NEXT SUB-GROUP
327 C -------------------------------------
328 
329 125 IF(ityp.EQ.1.OR.ityp.EQ.2) THEN
330  CALL up8(lref,nbit,mbay(1,lun),ibit)
331  CALL upb(linc, 6,mbay(1,lun),ibit)
332  nibit = ibit + linc*msub(lun)
333  ELSEIF(ityp.EQ.3) THEN
334  cref=' '
335  CALL upc(cref,nbit/8,mbay(1,lun),ibit,.true.)
336  CALL upb(linc, 6,mbay(1,lun),ibit)
337  nibit = ibit + 8*linc*msub(lun)
338  ELSE
339  GOTO 120
340  ENDIF
341 
342 C PROCESS A TYPE1 NODE INTO NVAL
343 C ------------------------------
344 
345  IF(ityp.EQ.1) THEN
346  jbit = ibit + linc
347  CALL up8(ninc,linc,mbay(1,lun),jbit)
348  ival = lref+ninc
349  CALL usrtpl(lun,n,int(ival))
350  GOTO 120
351  ENDIF
352 
353 C LOOP OVER STRING NODES
354 C ----------------------
355 
356  DO i=1,nnod
357 
358 C CHOSEN NODES LOOP - KEEP TRACK OF NODES NEEDED AND NODES FOUND
359 C --------------------------------------------------------------
360 
361  IF(node.NE.nods(i)) GOTO 130
362  nods(i) = -nods(i)
363  lret = iret
364 
365 C PROCESS A FOUND NODE INTO TAB
366 C -----------------------------
367 
368  IF(ityp.EQ.1.OR.ityp.EQ.2) THEN
369  DO nsb=1,msub(lun)
370  jbit = ibit + linc*(nsb-1)
371  CALL up8(ninc,linc,mbay(1,lun),jbit)
372  ival = lref+ninc
373  lret = lret+1
374  IF(ninc.LT.lps(linc)) tab(i,lret) = ups(ival,node)
375  ENDDO
376  ELSEIF(ityp.EQ.3) THEN
377  DO nsb=1,msub(lun)
378  IF(linc.EQ.0) THEN
379  cval = cref(1:8)
380  ELSE
381  jbit = ibit + linc*(nsb-1)*8
382  cval = ' '
383  CALL upc(cval,linc,mbay(1,lun),jbit,.true.)
384  ENDIF
385  lret = lret+1
386  tab(i,lret) = rval
387  ENDDO
388  ELSE
389  CALL bort('UFBTAB - INVALID ELEMENT TYPE SPECIFIED')
390  ENDIF
391 
392 C END OF LOOPS FOR COMPRESSED MESSAGE PARSING
393 C -------------------------------------------
394 
395 130 CONTINUE
396  ENDDO
397  ibit = nibit
398 
399 C END OF READ ELEMENTS LOOP
400 C -------------------------
401 
402  ENDDO
403 135 iret = iret+msub(lun)
404 
405 C END OF MESSAGE PARSING - GO BACK FOR ANOTHER
406 C --------------------------------------------
407 
408  GOTO 10
409 
410 C -------------------------------------------
411 C ERROR PROCESSING AND EXIT ROUTES BELOW
412 C -------------------------------------------
413 C EMERGENCY ROOM TREATMENT FOR ARRAY OVERFLOW
414 C -------------------------------------------
415 
416 99 nrep = iret
417  DO WHILE(ireadsb(lunit).EQ.0)
418  nrep = nrep+1
419  ENDDO
420  DO WHILE(ireadmg(-lunit,subset,jdate).GE.0)
421  nrep = nrep+nmsub(lunit)
422  ENDDO
423  IF(iprt.GE.0) THEN
424  CALL errwrt('+++++++++++++++++++++WARNING+++++++++++++++++++++++')
425  WRITE ( unit=errstr, fmt='(A,A,I8,A,A)' )
426  . 'BUFRLIB: UFBTAB - THE NO. OF DATA SUBSETS IN THE BUFR FILE ',
427  . .GT.'IS LIMIT OF ', i2, ' IN THE 4TH ARG. (INPUT) - ',
428  . 'INCOMPLETE READ'
429  CALL errwrt(errstr)
430  WRITE ( unit=errstr, fmt='(A,I8,A,I8,A)' )
431  . '>>>UFBTAB STORED ', iret, ' REPORTS OUT OF ', nrep, '<<<'
432  CALL errwrt(errstr)
433  CALL errwrt('+++++++++++++++++++++WARNING+++++++++++++++++++++++')
434  CALL errwrt(' ')
435  ENDIF
436 
437 
438 25 IF(openit) THEN
439 
440 C CLOSE BUFR FILE IF IT WAS OPENED HERE
441 C -------------------------------------
442 
443  CALL closbf(lunit)
444  ELSE
445 
446 C RESTORE BUFR FILE TO PREV. STATUS & POSITION IF NOT ORIG. OPENED HERE
447 C ---------------------------------------------------------------------
448 
449  CALL rewnbf(lunit,1)
450  ENDIF
451 
452  iac = iacc
453 
454 C EXITS
455 C -----
456 
457  RETURN
458  END
subroutine bort(STR)
Log one error message and abort application program.
Definition: bort.f:18
recursive subroutine closbf(LUNIT)
Close the connection between logical unit LUNIT and the NCEPLIBS-bufr software.
Definition: closbf.f:24
subroutine errwrt(STR)
This subroutine allows the user to specify a custom location for the logging of error and diagnostic ...
Definition: errwrt.f:36
recursive function ireadmg(LUNIT, SUBSET, IDATE)
Calls NCEPLIBS-bufr subroutine readmg() and passes back its return code as the function value.
Definition: ireadmg.f:27
recursive function ireadsb(LUNIT)
Calls NCEPLIBS-bufr subroutine readsb() and passes back its return code as the function value.
Definition: ireadsb.f:20
This module contains array and variable declarations used to store BUFR messages internally for multi...
integer ibit
Bit pointer within IBAY.
integer, dimension(:,:), allocatable mbay
Current BUFR message for each internal I/O stream.
integer, dimension(:), allocatable mbyt
Length (in bytes) of current BUFR message for each internal I/O stream.
This module contains declarations for arrays used to store information about the current BUFR message...
integer, dimension(:), allocatable nmsg
Current message pointer within logical unit.
integer, dimension(:), allocatable msub
Total number of data subsets in message.
integer, dimension(:), allocatable nsub
Current subset pointer within message.
This module contains array and variable declarations used to store the internal jump/link table.
integer, dimension(:), allocatable ibt
Bit widths corresponding to tag and typ:
integer, dimension(:), allocatable itp
Integer type values corresponding to typ:
This module contains an array declaration used to store, for each I/O stream index from which a BUFR ...
integer, dimension(:), allocatable msgunp
Flag indicating how to unpack data subsets from BUFR message:
This module contains declarations for arrays used to store data values and associated metadata for th...
integer, dimension(:), allocatable nval
Number of data values in BUFR data subset.
integer, dimension(:,:), allocatable, target inv
Inventory pointer which links each data value to its corresponding node in the internal jump/link tab...
This module declares and initializes the BMISS variable.
Definition: modules_vars.F90:9
real *8, public bmiss
Current placeholder value to represent "missing" data when reading from or writing to BUFR files; thi...
This module declares and initializes the IM8B variable.
logical, public im8b
Status indicator to keep track of whether all future calls to BUFRLIB subroutines and functions from ...
recursive function nmsub(LUNIT)
This function returns the total number of data subsets available within the BUFR message that was mos...
Definition: nmsub.f:22
recursive subroutine openbf(LUNIT, IO, LUNDX)
Connects a new file to the NCEPLIBS-bufr software for input or output operations, or initializes the ...
Definition: openbf.f:124
subroutine parstr(STR, TAGS, MTAG, NTAG, SEP, LIMIT80)
Parse a string containing one or more substrings into an array of substrings.
Definition: parstr.f:24
subroutine rewnbf(LUNIT, ISR)
This subroutine, depending on the value of ISR, will either:
Definition: rewnbf.f:38
recursive subroutine status(LUNIT, LUN, IL, IM)
Check whether a specified Fortran logical unit number is currently connected to the NCEPLIBS-bufr sof...
Definition: status.f:36
subroutine string(STR, LUN, I1, IO)
This subroutine checks to see if a user-specified character string is in the string cache (arrays in ...
Definition: string.f:28
recursive subroutine ufbtab(LUNIN, TAB, I1, I2, IRET, STR)
This subroutine reads through every data subset in a BUFR file and returns one or more specified data...
Definition: ufbtab.f:72
subroutine up8(nval, nbits, ibay, ibit)
This subroutine decodes an 8-byte integer value from within a specified number of bits of an integer ...
Definition: up8.f:27
subroutine upb8(nval, nbits, ibit, ibay)
This subroutine decodes an 8-byte integer value from within a specified number of bits of an integer ...
Definition: upb8.f:26
subroutine upb(NVAL, NBITS, IBAY, IBIT)
This subroutine decodes an integer value from within a specified number of bits of an integer array,...
Definition: upb.f:28
subroutine upc(CHR, NCHR, IBAY, IBIT, CNVNULL)
Decode a character string from an integer array.
Definition: upc.f:32
real *8 function ups(IVAL, NODE)
This function unpacks a real*8 user value from a packed BUFR integer by applying the proper scale and...
Definition: ups.f:22
subroutine usrtpl(LUN, INVN, NBMP)
Store the subset template into internal arrays.
Definition: usrtpl.f:22
subroutine x48(IIN4, IOUT8, NVAL)
Encode one or more 4-byte integer values as 8-byte integer values.
Definition: x48.F:19
subroutine x84(IIN8, IOUT4, NVAL)
Encode one or more 8-byte integer values as 4-byte integer values.
Definition: x84.F:19