NCEPLIBS-bufr  12.2.0
dxtable.F90
Go to the documentation of this file.
1 
5 
28 subroutine readdx(lunit,lun,lundx)
29 
30  use modv_vars, only: iprt
31 
32  implicit none
33 
34  integer, intent(in) :: lunit, lun, lundx
35  integer lud, ildx, imdx
36 
37  character*128 errstr
38 
39  ! Get the status of unit lundx
40 
41  call status(lundx,lud,ildx,imdx)
42 
43  ! Read a dictionary table from the indicated source
44 
45  if (lunit==lundx) then
46  ! Source is input BUFR file in lunit
47  if(iprt>=2) then
48  call errwrt('++++++++++++BUFR ARCHIVE LIBRARY+++++++++++++++')
49  write ( unit=errstr, fmt='(A,A,I3,A)' ) 'BUFRLIB: READDX - READING BUFR DICTIONARY TABLE FROM ', &
50  'INPUT BUFR FILE IN UNIT ', lundx, ' INTO INTERNAL ARRAYS'
51  call errwrt(errstr)
52  call errwrt('++++++++++++BUFR ARCHIVE LIBRARY+++++++++++++++')
53  call errwrt(' ')
54  endif
55  rewind lunit
56  call rdbfdx(lunit,lun)
57  elseif(ildx==-1) then
58  ! Source is input BUFR file in lundx; BUFR file in lunit may be input or output
59  if(iprt>=2) then
60  call errwrt('++++++++++++BUFR ARCHIVE LIBRARY+++++++++++++++')
61  write ( unit=errstr, fmt='(A,A,I3,A,A,I3)' ) 'BUFRLIB: READDX - COPYING BUFR DCTY TBL FROM INTERNAL ', &
62  'ARRAYS ASSOC. W/ INPUT UNIT ', lundx, ' TO THOSE ASSOC. W/ UNIT ', lunit
63  call errwrt(errstr)
64  call errwrt('++++++++++++BUFR ARCHIVE LIBRARY+++++++++++++++')
65  call errwrt(' ')
66  endif
67  call cpbfdx(lud,lun)
68  call makestab
69  elseif(ildx==1) then
70  ! Source is output BUFR file in lundx; BUFR file in lunit may be input or output
71  if(iprt>=2) then
72  call errwrt('++++++++++++BUFR ARCHIVE LIBRARY+++++++++++++++')
73  write ( unit=errstr, fmt='(A,A,I3,A,A,I3)' ) 'BUFRLIB: READDX - COPYING BUFR DCTY TBL FROM INTERNAL ', &
74  'ARRAYS ASSOC. W/ OUTPUT UNIT ', lundx, ' TO THOSE ASSOC. W/ UNIT ', lunit
75  call errwrt(errstr)
76  call errwrt('++++++++++++BUFR ARCHIVE LIBRARY+++++++++++++++')
77  call errwrt(' ')
78  endif
79  call cpbfdx(lud,lun)
80  call makestab
81  elseif(ildx==0) then
82  ! Source is user-supplied character table in lundx; BUFR file in lunit may be input or output
83  if(iprt>=2) then
84  call errwrt('++++++++++++BUFR ARCHIVE LIBRARY+++++++++++++++')
85  write ( unit=errstr, fmt='(A,A,I3,A)' ) 'BUFRLIB: READDX - READING BUFR DICTIONARY TABLE FROM ', &
86  'USER-SUPPLIED TEXT FILE IN UNIT ', lundx, ' INTO INTERNAL ARRAYS'
87  call errwrt(errstr)
88  call errwrt('++++++++++++BUFR ARCHIVE LIBRARY+++++++++++++++')
89  call errwrt(' ')
90  endif
91  rewind lundx
92  call rdusdx(lundx,lun)
93  else
94  call bort('BUFRLIB: READDX - CANNOT DETERMINE SOURCE OF INPUT DICTIONARY TABLE')
95  endif
96 
97  return
98 end subroutine readdx
99 
120 subroutine rdbfdx(lunit,lun)
121 
122  use bufrlib
123 
124  use modv_vars, only: iprt
125 
126  use moda_mgwa
127 
128  implicit none
129 
130  integer, intent(in) :: lunit, lun
131  integer ict, ier, idxmsg, iupbs3
132 
133  character*128 errstr
134 
135  logical done
136 
137  call dxinit(lun,0)
138 
139  ict = 0
140  done = .false.
141 
142  ! Read a complete dictionary table from lunit, as a set of one or more DX dictionary messages.
143 
144  do while ( .not. done )
145  call rdmsgw ( lunit, mgwa, ier )
146  if ( ier == -1 ) then
147  ! Don't abort for an end-of-file condition, since it may be possible for a file to end with dictionary messages.
148  ! Instead, backspace the file pointer and let the calling routine diagnose the end-of-file condition and deal with
149  ! it as it sees fit.
150  call backbufr_c(lun)
151  done = .true.
152  else if ( ier == -2 ) then
153  call bort('BUFRLIB: RDBFDX - ERROR READING A BUFR DICTIONARY MESSAGE')
154  else if ( idxmsg(mgwa) /= 1 ) then
155  ! This is a non-DX dictionary message. Assume we've reached the end of the dictionary table, and backspace lunit
156  ! so that the next read (e.g. in the calling routine) will get this same message.
157  call backbufr_c(lun)
158  done = .true.
159  else if ( iupbs3(mgwa,'NSUB') == 0 ) then
160  ! This is a DX dictionary message, but it doesn't contain any actual dictionary information. Assume we've reached
161  ! the end of the dictionary table.
162  done = .true.
163  else
164  ! Store this message into module @ref moda_tababd.
165  ict = ict + 1
166  call stbfdx(lun,mgwa)
167  endif
168  enddo
169 
170  if ( iprt >= 2 ) then
171  call errwrt('+++++++++++++++++++++++++++++++++++++++++++++++++')
172  write ( unit=errstr, fmt='(A,I3,A)' ) 'BUFRLIB: RDBFDX - STORED NEW DX TABLE CONSISTING OF (', ict, ') MESSAGES;'
173  call errwrt(errstr)
174  errstr = 'WILL APPLY THIS TABLE TO ALL SUBSEQUENT DATA IN FILE UNTIL NEXT DX TABLE IS FOUND'
175  call errwrt(errstr)
176  call errwrt('+++++++++++++++++++++++++++++++++++++++++++++++++')
177  call errwrt(' ')
178  endif
179 
180  call makestab
181 
182  return
183 end subroutine rdbfdx
184 
196 subroutine rdusdx(lundx,lun)
197 
198  use moda_tababd
199 
200  implicit none
201 
202  integer, intent(in) :: lundx, lun
203  integer ios, iret, n, numbck, nemock, igetntbi
204 
205  character*128 bort_str1
206  character*156 bort_str2
207  character*80 card
208  character*8 nemo
209  character*6 numb, nmb2
210 
211  ! Initialize the dictionary table control word partition arrays with apriori Table B and D entries
212 
213  call dxinit(lun,1)
214  rewind lundx
215 
216  ! Read user cards until there are no more
217 
218  do while (.true.)
219 
220  read(lundx, '(A80)', iostat = ios) card
221  if (ios/=0) then
222  call makestab
223  return
224  endif
225 
226  if(card(1: 1)== '*') cycle ! comment line
227  if(card(3:10)=='--------') cycle ! separation line
228  if(card(3:10)==' ') cycle ! blank line
229  if(card(3:10)=='MNEMONIC') cycle ! header line
230  if(card(3:10)=='TABLE D') cycle ! header line
231  if(card(3:10)=='TABLE B') cycle ! header line
232 
233  if(card(12:12)=='|' .and. card(21:21)=='|') then
234 
235  ! Parse a descriptor definition card
236  nemo = card(3:10) ! nemo is the (up to) 8-character mnemonic
237  iret=nemock(nemo)
238  if(iret==-2) then
239  write(bort_str1,'("BUFRLIB: RDUSDX - CARD READ IN IS: ",A)') card
240  write(bort_str2,'(18X,"MNEMONIC ",A," IN USER DICTIONARY HAS INVALID CHARACTERS")') nemo
241  call bort2(bort_str1,bort_str2)
242  endif
243  numb = card(14:19) ! numb is the 6-character FXY value corresponding to nemo
244  nmb2 = numb
245  if(nmb2(1:1)=='A') nmb2(1:1) = '3'
246  iret=numbck(nmb2)
247  if(iret==-1) then
248  write(bort_str1,'("BUFRLIB: RDUSDX - CARD READ IN IS: ",A)') card
249  write(bort_str2,'(18X,"DESCRIPTOR NUMBER ",A," IN USER '// &
250  'DICTIONARY HAS AN INVALID FIRST CHARACTER (F VALUE) - MUST BE A, 0 OR 3")') numb
251  call bort2(bort_str1,bort_str2)
252  endif
253  if(iret==-2) then
254  write(bort_str1,'("BUFRLIB: RDUSDX - CARD READ IN IS: ",A)') card
255  write(bort_str2,'(18X,"DESCRIPTOR NUMBER ",A," IN USER '// &
256  'DICTIONARY HAS NON-NUMERIC VALUES IN CHARACTERS 2-6 (X AND Y VALUES)")') numb
257  call bort2(bort_str1,bort_str2)
258  endif
259  if(iret==-3) then
260  write(bort_str1,'("BUFRLIB: RDUSDX - CARD READ IN IS: ",A)') card
261  write(bort_str2,'(18X,"DESCRIPTOR NUMBER ",A," IN USER '// &
262  'DICTIONARY HAS INVALID NUMBER IN CHARACTERS 2-3 (X VALUE) - MUST BE BETWEEN 00 AND 63")') numb
263  call bort2(bort_str1,bort_str2)
264  endif
265  if(iret==-4) then
266  write(bort_str1,'("BUFRLIB: RDUSDX - CARD READ IN IS: ",A)') card
267  write(bort_str2,'(18X,"DESCRIPTOR NUMBER ",A," IN USER '// &
268  'DICTIONARY HAS INVALID NUMBER IN CHARACTERS 4-6 (Y VALUE) - MUST BE BETWEEN 000 AND 255")') numb
269  call bort2(bort_str1,bort_str2)
270  endif
271 
272  if(numb(1:1)=='A') then
273  ! Table A descriptor found
274  n = igetntbi( lun, 'A' )
275  call stntbia ( n, lun, numb, nemo, card(23:) )
276  if ( idna(n,lun,1) == 11 ) then
277  write(bort_str1,'("BUFRLIB: RDUSDX - CARD READ IN IS: ",A)') card
278  write(bort_str2,'(18X,"USER-DEFINED MESSAGE TYPE ""011"" IS RESERVED FOR DICTIONARY MESSAGES")')
279  call bort2(bort_str1,bort_str2)
280  endif
281  ! Replace "A" with "3" so Table D descriptor will be found in card as well (see below).
282  numb(1:1) = '3'
283  endif
284 
285  if(numb(1:1)=='0') then
286  ! Table B descriptor found
287  call stntbi ( igetntbi(lun,'B'), lun, numb, nemo, card(23:) )
288  cycle
289  endif
290 
291  if(numb(1:1)=='3') then
292  ! Table D descriptor found
293  call stntbi ( igetntbi(lun,'D'), lun, numb, nemo, card(23:) )
294  cycle
295  endif
296 
297  write(bort_str1,'("BUFRLIB: RDUSDX - CARD READ IN IS: ",A)') card
298  write(bort_str2,'(18X,"DESCRIPTOR NUMBER ",A," IN USER '// &
299  'DICTIONARY HAS AN INVALID FIRST CHARACTER (F VALUE) - MUST BE A, 0 OR 3")') numb
300  call bort2(bort_str1,bort_str2)
301 
302  endif
303 
304  if(card(12:12)=='|' .and. card(19:19)/='|') then
305  ! Parse a sequence definition card
306  call seqsdx(card,lun)
307  cycle
308  endif
309 
310  if(card(12:12)=='|' .and. card(19:19)=='|') then
311  ! Parse an element definition card
312  call elemdx(card,lun)
313  cycle
314  endif
315 
316  ! Can't figure out what kind of card it is
317  write(bort_str1,'("BUFRLIB: RDUSDX - CARD READ IN IS: ",A)') card
318  write(bort_str2,'(18X,"THIS CARD HAS A BAD FORMAT - IT IS NOT RECOGNIZED BY THIS SUBROUTINE")')
319  call bort2(bort_str1,bort_str2)
320  enddo
321 
322 end subroutine rdusdx
323 
332 subroutine seqsdx(card,lun)
333 
334  use modv_vars, only: reps, idnr
335 
336  implicit none
337 
338  integer, intent(in) :: lun
339  integer ntag, idn, jdn, iseq, irep, i, j, n, itab, iret, ier, numr, nemock
340  integer, parameter :: maxtgs = 250, maxtag = 13
341 
342  character*128 bort_str1, bort_str2
343  character*80 seqs
344  character*80, intent(in) :: card
345  character*(maxtag) atag, tags(maxtgs)
346  character*8 nemo, nema, nemb
347  character*6 adn30, clemon
348  character tab
349 
350  ! Find the sequence tag in Table D and parse the sequence string
351 
352  nemo = card( 3:10)
353  seqs = card(14:78)
354 
355  ! Note that an entry for this mnemonic should already exist within the internal BUFR Table D array tabd(*,LUN); this entry
356  ! should have been created by subroutine rdusdx() when the mnemonic and its associated FXY value and description were
357  ! initially defined within a card read from the "Descriptor Definition" section at the top of the user-supplied DX BUFR
358  ! table in character format. Now, we need to retrieve the positional index for that entry within tabd(*,lun) so that we
359  ! can access the entry and then add the decoded sequence information to it.
360 
361  call nemtab(lun,nemo,idn,tab,iseq)
362  if(tab/='D') then
363  write(bort_str1,'("BUFRLIB: SEQSDX - CARD READ IN IS: ",A)') card
364  write(bort_str2,'(18X,"MNEMONIC ",A," IS NOT A TABLE D ENTRY (UNDEFINED, TAB=",A,")")') nemo,tab
365  call bort2(bort_str1,bort_str2)
366  endif
367  call parstr(seqs,tags,maxtgs,ntag,' ',.true.)
368  if(ntag==0) then
369  write(bort_str1,'("BUFRLIB: SEQSDX - CARD READ IN IS: ",A)') card
370  write(bort_str2,'(18X,"TABLE D SEQUENCE (PARENT) MNEMONIC ",A," DOES NOT CONTAIN ANY CHILD MNEMONICS")') nemo
371  call bort2(bort_str1,bort_str2)
372  endif
373 
374  do n=1,ntag
375  atag = tags(n)
376  irep = 0
377 
378  ! Check for a replicator
379 
380  outer: do i=1,5
381  if(atag(1:1)==reps(i)) then
382  ! Note that reps(*), which contains all of the symbols used to denote all of the various replication schemes that
383  ! are possible within a user-supplied BUFR dictionary table in character format, was previously defined within
384  ! subroutine bfrini().
385  do j=2,maxtag
386  if(atag(j:j)==reps(i+5)) then
387  ! Note that subroutine strnum() will return numr = 0 if the string passed to it contains all blanks
388  ! (as *should* be the case whenever i = 2 '(' ')', 3 '{' '}', 4 '[' ']', or 5 '<' '>').
389  ! However, when i = 1 '"' '"', then subroutine strnum() will return numr = (the number of replications for
390  ! the mnemonic using F=1 "regular" (i.e. non-delayed) replication).
391  call strnum(atag(j+1:maxtag),numr,ier)
392  if(i==1 .and. numr<=0) then
393  write(bort_str1,'("BUFRLIB: SEQSDX - CARD READ IN IS: ",A)') card
394  write(bort_str2,'(9X,"TBL D MNEM. ",A," CONTAINS REG. REPL. '// &
395  'CHILD MNEM. ",A," W/ INVALID # OF REPLICATIONS (",I3,") AFTER 2ND QUOTE")') nemo,tags(n),numr
396  call bort2(bort_str1,bort_str2)
397  endif
398  if(i==1 .and. numr>255) then
399  write(bort_str1,'("BUFRLIB: SEQSDX - CARD READ IN IS: ",A)') card
400  write(bort_str2,'(18X,"TBL D MNEM. ",A," CONTAINS REG. REPL. '// &
401  'CHILD MNEM. ",A," W/ # OF REPLICATIONS (",I3,") > LIMIT OF 255")') nemo,tags(n),numr
402  call bort2(bort_str1,bort_str2)
403  endif
404  if(i/=1 .and. numr/=0) then
405  write(bort_str1,'("BUFRLIB: SEQSDX - CARD READ IN IS: ",A)') card
406  write(bort_str2,'(18X,"TBL D MNEM. ",A," CONTAINS DELAYED REPL. '// &
407  'CHILD MNEM. ",A," W/ # OF REPL. (",I3,") SPECIFIED - A NO-NO")') nemo,tags(n),numr
408  call bort2(bort_str1,bort_str2)
409  endif
410  atag = atag(2:j-1)
411  irep = i
412  exit outer
413  endif
414  enddo
415  write(bort_str1,'("BUFRLIB: SEQSDX - CARD READ IN IS: ",A)') card
416  write(bort_str2,'(18X,"TABLE D SEQUENCE (PARENT) MNEMONIC ",A,'// &
417  '" CONTAINS A BADLY FORMED CHILD MNEMONIC ",A)') nemo,tags(n)
418  call bort2(bort_str1,bort_str2)
419  endif
420  enddo outer
421 
422  ! Check for a valid tag
423 
424  iret=nemock(atag)
425  if(iret==-1) then
426  write(bort_str1,'("BUFRLIB: SEQSDX - CARD READ IN IS: ",A)') card
427  write(bort_str2,'(18X,"TABLE D (PARENT) MNEMONIC ",A," CONTAINS'// &
428  ' A CHILD MNEMONIC ",A," NOT BETWEEN 1 & 8 CHARACTERS")') nemo,tags(n)
429  call bort2(bort_str1,bort_str2)
430  endif
431  if(iret==-2) then
432  write(bort_str1,'("BUFRLIB: SEQSDX - CARD READ IN IS: ",A)') card
433  write(bort_str2,'(18X,"TABLE D (PARENT) MNEMONIC ",A," CONTAINS'// &
434  ' A CHILD MNEMONIC ",A," WITH INVALID CHARACTERS")') nemo,tags(n)
435  call bort2(bort_str1,bort_str2)
436  endif
437  call nemtab(lun,atag,idn,tab,iret)
438  if(iret>0) then
439  ! Note that the next code line checks that we are not trying to replicate a Table B mnemonic (which is currently not
440  ! allowed). The logic works because, for replicated mnemonics, irep = i = (the index within reps(*) of the symbol
441  ! associated with the type of replication in question (e.g. "{, "<", etc.))
442  if(tab=='B' .and. irep/=0) then
443  write(bort_str1,'("BUFRLIB: SEQSDX - CARD READ IN IS: ",A)') card
444  write(bort_str2,'(18X,"TABLE D (PARENT) MNEMONIC ",A," CONTAINS'// &
445  ' A REPLICATED CHILD TABLE B MNEMONIC ",A," - A NO-NO")') nemo,tags(n)
446  call bort2(bort_str1,bort_str2)
447  endif
448  if(atag(1:1)=='.') then
449  ! This mnemonic is a "following value" mnemonic (i.e. it relates to the mnemonic that immediately follows it within
450  ! the user-supplied character-format BUFR dictionary table sequence), so confirm that it contains, as a substring,
451  ! this mnemonic that immediately follows it.
452  if(n==ntag) then
453  write(bort_str1,'("BUFRLIB: SEQSDX - CARD READ IN IS: ",A)') card
454  write(bort_str2,'(18X,"TBL D (PARENT) MNEM. ",A," CONTAINS A '// &
455  '''FOLLOWING VALUE'' MNEMONIC WHICH IS LAST IN THE STRING")') nemo
456  call bort2(bort_str1,bort_str2)
457  endif
458  nemb = tags(n+1)(1:8)
459  call numtab(lun,idn,nema,tab,itab)
460  call nemtab(lun,nemb,jdn,tab,iret)
461  call rsvfvm(nema,nemb)
462  if(nema/=atag) then
463  write(bort_str1,'("BUFRLIB: SEQSDX - CARD READ IN IS: ",A)') card
464  write(bort_str2,'(18X,"TBL D (PARENT) MNEM. ",A," CONTAINS AN '// &
465  'INVALID ''FOLLOWING VALUE'' MNEMONIC ",A,"(SHOULD BE ",A,")")') nemo,tags(n),nema
466  call bort2(bort_str1,bort_str2)
467  endif
468  if(tab/='B') then
469  write(bort_str1,'("BUFRLIB: SEQSDX - CARD READ IN IS: ",A)') card
470  write(bort_str2,'(18X,"TBL D (PARENT) MNEM. ",A,", THE MNEM. ",'// &
471  'A," FOLLOWING A ''FOLLOWING VALUE'' MNEM. IS NOT A TBL B ENTRY")') nemo,nemb
472  call bort2(bort_str1,bort_str2)
473  endif
474  endif
475  else
476  write(bort_str1,'("BUFRLIB: SEQSDX - CARD READ IN IS: ",A)') card
477  write(bort_str2,'(18X,"TABLE D SEQUENCE (PARENT) MNEMONIC ",A,'// &
478  '" CONTAINS A CHILD MNEMONIC ",A," NOT FOUND IN ANY TABLE")') nemo,tags(n)
479  call bort2(bort_str1,bort_str2)
480  endif
481 
482  ! Write the descriptor string into the tabd array, but first look for a replication descriptor
483  if(irep>0) call pktdd(iseq,lun,idnr(irep)+numr,iret)
484  if(iret<0) then
485  clemon = adn30(idnr(irep)+numr,6)
486  write(bort_str1,'("BUFRLIB: SEQSDX - CARD READ IN IS: ",A)') card
487  write(bort_str2,'(9X,"TBL D (PARENT) MNEM. ",A," - BAD RETURN '// &
488  'FROM PKTDD TRYING TO STORE REPL. DESC. ",A,", SEE PREV. WARNING MSG")') nemo,clemon
489  call bort2(bort_str1,bort_str2)
490  endif
491  call pktdd(iseq,lun,idn,iret)
492  if(iret<0) then
493  write(bort_str1,'("BUFRLIB: SEQSDX - CARD READ IN IS: ",A)') card
494  write(bort_str2,'(9X,"TBL D (PARENT) MNEM. ",A," - BAD RETURN '// &
495  'FROM PKTDD TRYING TO STORE CHILD MNEM. ",A,", SEE PREV. WARNING MSG")') nemo,tags(n)
496  call bort2(bort_str1,bort_str2)
497  endif
498 
499  enddo
500 
501  return
502 end subroutine seqsdx
503 
513 subroutine elemdx(card,lun)
514 
515  use moda_tababd
516 
517  implicit none
518 
519  integer, intent(in) :: lun
520  integer idsn, iele, iret
521 
522  character*128 bort_str1, bort_str2
523  character*80, intent(in) :: card
524  character*24 unit
525  character*11 refr, refr_orig
526  character*8 nemo
527  character*4 scal, scal_orig
528  character*3 bitw, bitw_orig
529  character sign, tab
530 
531  ! Capture the various elements characteristics
532 
533  nemo = card( 3:10)
534  scal = card(14:17)
535  refr = card(21:31)
536  bitw = card(35:37)
537  unit = card(41:64)
538  ! Make sure the units are all capitalized
539  call capit(unit)
540 
541  ! Find the element tag in Table B. Note that an entry for this mnemonic should already exist within the internal
542  ! BUFR Table B array tabb(*,lun). We now need to retrieve the positional index for that entry within tabb(*,lun)
543  ! so that we can access the entry and then add the scale factor, reference value, bit width, and units to it.
544 
545  call nemtab(lun,nemo,idsn,tab,iele)
546  if(tab/='B') then
547  write(bort_str1,'("BUFRLIB: ELEMDX - CARD READ IN IS: ",A)') card
548  write(bort_str2,'(18X,"MNEMONIC ",A," IS NOT A TABLE B ENTRY (UNDEFINED, TAB=",A,")")') nemo,tab
549  call bort2(bort_str1,bort_str2)
550  endif
551 
552  ! Left justify and store characteristics
553 
554  unit = adjustl(unit)
555  if(unit==' ') then
556  write(bort_str1,'("BUFRLIB: ELEMDX - CARD READ IN IS: ",A)') card
557  write(bort_str2,'(18X,"UNITS FIELD IS EMPTY")')
558  call bort2(bort_str1,bort_str2)
559  endif
560  tabb(iele,lun)(71:94) = unit
561 
562  scal_orig=scal
563  call jstnum(scal,sign,iret)
564  if(iret/=0) then
565  write(bort_str1,'("BUFRLIB: ELEMDX - CARD READ IN IS: ",A)') card
566  write(bort_str2,'(18X,"PARSED SCALE VALUE (=",A,") IS NOT NUMERIC")') scal_orig
567  call bort2(bort_str1,bort_str2)
568  endif
569  tabb(iele,lun)(95:95) = sign
570  tabb(iele,lun)(96:98) = scal(1:3)
571 
572  refr_orig=refr
573  call jstnum(refr,sign,iret)
574  if(iret/=0) then
575  write(bort_str1,'("BUFRLIB: ELEMDX - CARD READ IN IS: ",A)') card
576  write(bort_str2,'(18X,"PARSED REFERENCE VALUE (=",A,") IS NOT NUMERIC")') refr_orig
577  call bort2(bort_str1,bort_str2)
578  endif
579  tabb(iele,lun)( 99: 99) = sign
580  tabb(iele,lun)(100:109) = refr(1:10)
581 
582  bitw_orig=bitw
583  call jstnum(bitw,sign,iret)
584  if(iret/=0 .or. sign=='-') then
585  write(bort_str1,'("BUFRLIB: ELEMDX - CARD READ IN IS: ",A)') card
586  write(bort_str2,'(18X,"PARSED BIT WIDTH VALUE (=",A,") IS NOT NUMERIC")') bitw_orig
587  call bort2(bort_str1,bort_str2)
588  endif
589  tabb(iele,lun)(110:112) = bitw
590 
591  return
592 end subroutine elemdx
593 
603 subroutine dxinit(lun,ioi)
604 
605  use modv_vars, only: idnr, fxy_fbit, fxy_sbyct, fxy_drf16, fxy_drf8, fxy_drf1
606 
607  use moda_tababd
608 
609  implicit none
610 
611  integer, intent(in) :: lun, ioi
612  integer ninib, ninid, n, i, iret, ifxy
613 
614  character*8 inib(6,5),inid(5)
615  character*6 adn30
616 
617  data inib / '------','BYTCNT ','BYTES ','+0','+0','16', &
618  '------','BITPAD ','NONE ','+0','+0','1 ', &
619  fxy_drf1,'DRF1BIT ','NUMERIC','+0','+0','1 ', &
620  fxy_drf8,'DRF8BIT ','NUMERIC','+0','+0','8 ', &
621  fxy_drf16,'DRF16BIT','NUMERIC','+0','+0','16'/
622  data ninib /5/
623 
624  data inid /' ', &
625  'DRP16BIT', &
626  'DRP8BIT ', &
627  'DRPSTAK ', &
628  'DRP1BIT '/
629  data ninid /5/
630 
631  ! Clear out a table partition
632 
633  ntba(lun) = 0
634  do i=1,ntba(0)
635  taba(i,lun) = ' '
636  mtab(i,lun) = 0
637  enddo
638 
639  ntbb(lun) = 0
640  tabb(1:ntbb(0),lun) = ' '
641 
642  ntbd(lun) = 0
643  do i=1,ntbd(0)
644  tabd(i,lun) = ' '
645  call pktdd(i,lun,0,iret)
646  enddo
647 
648  if(ioi==0) return
649 
650  ! Initialize table with apriori Table B and D entries
651 
652  inib(1,1) = fxy_sbyct
653  inib(1,2) = fxy_fbit
654 
655  do i=1,ninib
656  ntbb(lun) = ntbb(lun)+1
657  idnb(i,lun) = ifxy(inib(1,i))
658  tabb(i,lun)( 1: 6) = inib(1,i)(1:6)
659  tabb(i,lun)( 7: 70) = inib(2,i)
660  tabb(i,lun)( 71: 94) = inib(3,i)
661  tabb(i,lun)( 95: 98) = inib(4,i)(1:4)
662  tabb(i,lun)( 99:109) = inib(5,i)
663  tabb(i,lun)(110:112) = inib(6,i)(1:3)
664  enddo
665 
666  do i=2,ninid
667  n = ntbd(lun)+1
668  idnd(n,lun) = idnr(i)
669  tabd(n,lun)(1: 6) = adn30(idnr(i),6)
670  tabd(n,lun)(7:70) = inid(i)
671  call pktdd(n,lun,idnr(1),iret)
672  call pktdd(n,lun,idnr(i+5),iret)
673  ntbd(lun) = n
674  enddo
675 
676  return
677 end subroutine dxinit
678 
690 subroutine dxmini(mbay,mbyt,mb4,mba,mbb,mbd)
691 
692  use modv_vars, only: mxmsgld4, mtv, nby0, nby1, nby2, nby5, bmostr, idxv
693 
694  implicit none
695 
696  integer, intent(out) :: mbay(*), mbyt, mb4, mba, mbb, mbd
697  integer nxstr, ldxa, ldxb, ldxd, ld30, mtyp, msbt, mbit, ih, id, im, iy, i, nsub, idxs, ldxs, &
698  len3, nby4, iupm
699 
700  character*128 bort_str
701  character*56 dxstr
702 
703  common /dxtab/ nxstr(10), ldxa(10), ldxb(10), ldxd(10), ld30(10), dxstr(10)
704 
705  msbt = idxv
706 
707  ! Initialize the message
708 
709  mbit = 0
710  mbay(1:mxmsgld4) = 0
711 
712  ! For DX table messages, the Section 1 date is simply zeroed out. Note that there is logic in function idxmsg()
713  ! which relies on this.
714  ih = 0
715  id = 0
716  im = 0
717  iy = 0
718 
719  mtyp = 11 ! DX table messages are always type 11, per WMO BUFR Table A
720  nsub = 1
721 
722  idxs = idxv+1
723  ldxs = nxstr(idxs)
724 
725  len3 = 7 + nxstr(idxs) + 1
726  nby4 = 7
727  mbyt = nby0+nby1+nby2+len3+nby4+nby5
728 
729  if(mod(len3,2)/=0) call bort ('BUFRLIB: DXMINI - LENGTH OF SECTION 3 IS NOT A MULTIPLE OF 2')
730 
731  ! Section 0
732 
733  call pkc(bmostr , 4 , mbay,mbit)
734  call pkb( mbyt , 24 , mbay,mbit)
735  call pkb( 3 , 8 , mbay,mbit)
736 
737  ! Section 1
738 
739  call pkb( nby1 , 24 , mbay,mbit)
740  call pkb( 0 , 8 , mbay,mbit)
741  call pkb( 3 , 8 , mbay,mbit)
742  call pkb( 7 , 8 , mbay,mbit)
743  call pkb( 0 , 8 , mbay,mbit)
744  call pkb( 0 , 8 , mbay,mbit)
745  call pkb( mtyp , 8 , mbay,mbit)
746  call pkb( msbt , 8 , mbay,mbit)
747  call pkb( mtv , 8 , mbay,mbit)
748  call pkb( idxv , 8 , mbay,mbit)
749  call pkb( iy , 8 , mbay,mbit)
750  call pkb( im , 8 , mbay,mbit)
751  call pkb( id , 8 , mbay,mbit)
752  call pkb( ih , 8 , mbay,mbit)
753  call pkb( 0 , 8 , mbay,mbit)
754  call pkb( 0 , 8 , mbay,mbit)
755 
756  ! Section 3
757 
758  call pkb( len3 , 24 , mbay,mbit)
759  call pkb( 0 , 8 , mbay,mbit)
760  call pkb( 1 , 16 , mbay,mbit)
761  call pkb( 2**7 , 8 , mbay,mbit)
762  do i=1,ldxs
763  call pkb(iupm(dxstr(idxs)(i:i),8),8,mbay,mbit)
764  enddo
765  call pkb( 0 , 8 , mbay,mbit)
766 
767  ! Section 4
768 
769  mb4 = mbit/8+1
770  call pkb( nby4 , 24 , mbay,mbit)
771  call pkb( 0 , 8 , mbay,mbit)
772  mba = mbit/8+1
773  call pkb( 0 , 8 , mbay,mbit)
774  mbb = mbit/8+1
775  call pkb( 0 , 8 , mbay,mbit)
776  mbd = mbit/8+1
777  call pkb( 0 , 8 , mbay,mbit)
778 
779  if(mbit/8+nby5/=mbyt) then
780  write(bort_str,'("BUFRLIB: DXMINI - NUMBER OF BYTES STORED FOR '// &
781  'A MESSAGE (",I6,") IS NOT THE SAME AS FIRST CALCULATED, MBYT (",I6)') mbit/8+nby5,mbyt
782  call bort(bort_str)
783  endif
784 
785  return
786 end subroutine dxmini
787 
799 subroutine writdx(lunit,lun,lundx)
800 
801  implicit none
802 
803  integer, intent(in) :: lunit, lun, lundx
804 
805  character*128 bort_str
806 
807  ! The table must be coming from an input file
808 
809  if(lunit==lundx) then
810  write(bort_str,'("BUFRLIB: WRITDX - FILES CONTAINING BUFR DATA '// &
811  'AND DICTIONARY TABLE CANNOT BE THE SAME (HERE BOTH SHARE FORTRAN UNIT NUMBER ",I3,")")') lunit
812  call bort(bort_str)
813  endif
814 
815  ! Must first call readdx() to generate internal dictionary table arrays, before calling wrdxtb()
816 
817  call readdx(lunit,lun,lundx)
818  call wrdxtb(lunit,lunit)
819 
820  return
821 end subroutine writdx
822 
837 recursive subroutine wrdxtb(lundx,lunot)
838 
839  use modv_vars, only: im8b, idxv
840 
841  use moda_tababd
842  use moda_mgwa
843  use moda_bitbuf, only: maxbyt
844 
845  implicit none
846 
847  integer, intent(in) :: lundx, lunot
848  integer nxstr, ldxa, ldxb, ldxd, ld30, my_lundx, my_lunot, ldx, lot, il, im, lda, ldb, ldd, l30, nseq, &
849  mbit, mbyt, mby4, mbya, mbyb, mbyd, i, j, jj, idn, lend, len0, len1, len2, l3, l4, l5, iupb, iupm
850 
851  common /dxtab/ nxstr(10), ldxa(10), ldxb(10), ldxd(10), ld30(10), dxstr(10)
852 
853  character*56 dxstr
854  character*6 adn30
855 
856  logical msgfull
857 
858  ! Check for I8 integers
859 
860  if(im8b) then
861  im8b=.false.
862 
863  call x84(lundx,my_lundx,1)
864  call x84(lunot,my_lunot,1)
865  call wrdxtb(my_lundx,my_lunot)
866 
867  im8b=.true.
868  return
869  endif
870 
871  ! Check file statuses
872 
873  call status(lunot,lot,il,im)
874  if(il==0) call bort('BUFRLIB: WRDXTB - OUTPUT BUFR FILE IS CLOSED, IT MUST BE OPEN FOR OUTPUT')
875  if(il<0) call bort('BUFRLIB: WRDXTB - OUTPUT BUFR FILE IS OPEN FOR INPUT, IT MUST BE OPEN FOR OUTPUT')
876 
877  call status(lundx,ldx,il,im)
878  if(il==0) call bort('BUFRLIB: WRDXTB - DX TABLE FILE IS CLOSED, IT MUST BE OPEN')
879 
880  ! If files are different, copy internal table information from lundx to lunot
881 
882  if(lundx/=lunot) call cpbfdx(ldx,lot)
883 
884  ! Generate and write out BUFR dictionary messages to lunot
885 
886  call dxmini(mgwa,mbyt,mby4,mbya,mbyb,mbyd)
887 
888  lda = ldxa(idxv+1)
889  ldb = ldxb(idxv+1)
890  ldd = ldxd(idxv+1)
891  l30 = ld30(idxv+1)
892 
893  ! Table A information
894 
895  do i=1,ntba(lot)
896  if(msgfull(mbyt,lda,maxbyt).or.(iupb(mgwa,mbya,8)==255)) then
897  call msgwrt(lunot,mgwa,mbyt)
898  call dxmini(mgwa,mbyt,mby4,mbya,mbyb,mbyd)
899  endif
900  mbit = 8*(mby4-1)
901  call pkb(iupb(mgwa,mby4,24)+lda,24,mgwa,mbit)
902  mbit = 8*(mbya-1)
903  call pkb(iupb(mgwa,mbya,8)+1,8,mgwa,mbit)
904  mbit = 8*(mbyb-1)
905  call pkc(taba(i,lot),lda,mgwa,mbit)
906  call pkb(0,8,mgwa,mbit)
907  call pkb(0,8,mgwa,mbit)
908  mbyt = mbyt+lda
909  mbyb = mbyb+lda
910  mbyd = mbyd+lda
911  enddo
912 
913  ! Table B information
914 
915  do i=1,ntbb(lot)
916  if(msgfull(mbyt,ldb,maxbyt).or.(iupb(mgwa,mbyb,8)==255)) then
917  call msgwrt(lunot,mgwa,mbyt)
918  call dxmini(mgwa,mbyt,mby4,mbya,mbyb,mbyd)
919  endif
920  mbit = 8*(mby4-1)
921  call pkb(iupb(mgwa,mby4,24)+ldb,24,mgwa,mbit)
922  mbit = 8*(mbyb-1)
923  call pkb(iupb(mgwa,mbyb,8)+1,8,mgwa,mbit)
924  mbit = 8*(mbyd-1)
925  call pkc(tabb(i,lot),ldb,mgwa,mbit)
926  call pkb(0,8,mgwa,mbit)
927  mbyt = mbyt+ldb
928  mbyd = mbyd+ldb
929  enddo
930 
931  ! Table D information
932 
933  do i=1,ntbd(lot)
934  nseq = iupm(tabd(i,lot)(ldd+1:ldd+1),8)
935  lend = ldd+1 + l30*nseq
936  if(msgfull(mbyt,lend,maxbyt).or.(iupb(mgwa,mbyd,8)==255)) then
937  call msgwrt(lunot,mgwa,mbyt)
938  call dxmini(mgwa,mbyt,mby4,mbya,mbyb,mbyd)
939  endif
940  mbit = 8*(mby4-1)
941  call pkb(iupb(mgwa,mby4,24)+lend,24,mgwa,mbit)
942  mbit = 8*(mbyd-1)
943  call pkb(iupb(mgwa,mbyd,8)+1,8,mgwa,mbit)
944  mbit = 8*(mbyt-4)
945  call pkc(tabd(i,lot),ldd,mgwa,mbit)
946  call pkb(nseq,8,mgwa,mbit)
947  do j=1,nseq
948  jj = ldd+2 + (j-1)*2
949  idn = iupm(tabd(i,lot)(jj:jj+1),16)
950  call pkc(adn30(idn,l30),l30,mgwa,mbit)
951  enddo
952  mbyt = mbyt+lend
953  enddo
954 
955  ! Write the unwritten (leftover) message.
956 
957  call msgwrt(lunot,mgwa,mbyt)
958 
959  ! Write out one additional (dummy) DX message containing zero subsets. This will serve as a delimiter for this set of
960  ! table messages within output unit lunot, just in case the next thing written to lunot ends up being another set of
961  ! table messages.
962 
963  call dxmini(mgwa,mbyt,mby4,mbya,mbyb,mbyd)
964  call getlens(mgwa,2,len0,len1,len2,l3,l4,l5)
965  mbit = (len0+len1+len2+4)*8
966  call pkb(0,16,mgwa,mbit)
967  call msgwrt(lunot,mgwa,mbyt)
968 
969  return
970 end subroutine wrdxtb
971 
978 subroutine stbfdx(lun,mesg)
979 
980  use modv_vars, only: maxcd, idxv
981 
982  use moda_tababd
983 
984  implicit none
985 
986  integer, intent(in) :: lun, mesg(*)
987  integer nxstr, ldxa, ldxb, ldxd, ld30, ldxbd(10), ldxbe(10), ja, jb, idxs, i3, i, j, n, nd, ndd, idn, &
988  jbit, len0, len1, len2, len3, l4, l5, lda, ldb, ldd, ldbd, ldbe, l30, ia, la, ib, lb, id, ld, iret, &
989  ifxy, iupb, iupbs01, igetntbi, idn30
990 
991  character*128 bort_str
992  character*128 tabb1, tabb2
993  character*56 dxstr
994  character*55 cseq
995  character*50 dxcmp
996  character*24 unit
997  character*8 nemo
998  character*6 numb, cidn
999 
1000  common /dxtab/ nxstr(10), ldxa(10), ldxb(10), ldxd(10), ld30(10), dxstr(10)
1001 
1002  data ldxbd /38, 70, 8*0/
1003  data ldxbe /42, 42, 8*0/
1004 
1005  ! Statement functions
1006  ja(i) = ia+1+lda*(i-1)
1007  jb(i) = ib+1+ldb*(i-1)
1008 
1009  ! Get some preliminary information from the message
1010 
1011  idxs = iupbs01(mesg,'MSBT')+1
1012  if(idxs>idxv+1) idxs = iupbs01(mesg,'MTVL')+1
1013  if(ldxa(idxs)==0 .or. ldxb(idxs)==0 .or. ldxd(idxs)==0) call bort('BUFRLIB: STBFDX - UNEXPECTED DICTIONARY '// &
1014  'MESSAGE SUBTYPE OR LOCAL VERSION NUMBER (E.G., L.V.N. HIGHER THAN KNOWN)')
1015 
1016  call getlens(mesg,3,len0,len1,len2,len3,l4,l5)
1017  i3 = len0+len1+len2
1018  dxcmp = ' '
1019  jbit = 8*(i3+7)
1020  call upc(dxcmp,nxstr(idxs),mesg,jbit,.false.)
1021  if(dxcmp/=dxstr(idxs)) call bort('BUFRLIB: STBFDX - UNEXPECTED DICTIONARY MESSAGE CONTENTS')
1022 
1023  ! Section 4 - read definitions for Tables A, B and D
1024 
1025  lda = ldxa(idxs)
1026  ldb = ldxb(idxs)
1027  ldd = ldxd(idxs)
1028  ldbd = ldxbd(idxs)
1029  ldbe = ldxbe(idxs)
1030  l30 = ld30(idxs)
1031 
1032  ia = i3+len3+5
1033  la = iupb(mesg,ia,8)
1034  ib = ja(la+1)
1035  lb = iupb(mesg,ib,8)
1036  id = jb(lb+1)
1037  ld = iupb(mesg,id,8)
1038 
1039  ! Table A
1040 
1041  do i=1,la
1042  n = igetntbi(lun,'A')
1043  jbit = 8*(ja(i)-1)
1044  call upc(taba(n,lun),lda,mesg,jbit,.true.)
1045  numb = ' '//taba(n,lun)(1:3)
1046  nemo = taba(n,lun)(4:11)
1047  cseq = taba(n,lun)(13:67)
1048  call stntbia(n,lun,numb,nemo,cseq)
1049  enddo
1050 
1051  ! Table B
1052 
1053  do i=1,lb
1054  n = igetntbi(lun,'B')
1055  jbit = 8*(jb(i)-1)
1056  call upc(tabb1,ldbd,mesg,jbit,.true.)
1057  jbit = 8*(jb(i)+ldbd-1)
1058  call upc(tabb2,ldbe,mesg,jbit,.true.)
1059  tabb(n,lun) = tabb1(1:ldxbd(idxv+1))//tabb2(1:ldxbe(idxv+1))
1060  numb = tabb(n,lun)(1:6)
1061  nemo = tabb(n,lun)(7:14)
1062  call nenubd(nemo,numb,lun)
1063  idnb(n,lun) = ifxy(numb)
1064  unit = tabb(n,lun)(71:94)
1065  call capit(unit)
1066  tabb(n,lun)(71:94) = unit
1067  ntbb(lun) = n
1068  enddo
1069 
1070  ! Table D
1071 
1072  do i=1,ld
1073  n = igetntbi(lun,'D')
1074  jbit = 8*id
1075  call upc(tabd(n,lun),ldd,mesg,jbit,.true.)
1076  numb = tabd(n,lun)(1:6)
1077  nemo = tabd(n,lun)(7:14)
1078  call nenubd(nemo,numb,lun)
1079  idnd(n,lun) = ifxy(numb)
1080  nd = iupb(mesg,id+ldd+1,8)
1081  if(nd>maxcd) then
1082  write(bort_str,'("BUFRLIB: STBFDX - NUMBER OF DESCRIPTORS IN '// &
1083  'TABLE D ENTRY ",A," IN BUFR TABLE (",I4,") EXCEEDS THE LIMIT (",I4,")")') nemo,nd,maxcd
1084  call bort(bort_str)
1085  endif
1086  do j=1,nd
1087  ndd = id+ldd+2 + (j-1)*l30
1088  jbit = 8*(ndd-1)
1089  call upc(cidn,l30,mesg,jbit,.true.)
1090  idn = idn30(cidn,l30)
1091  call pktdd(n,lun,idn,iret)
1092  if(iret<0) call bort('BUFRLIB: STBFDX - BAD RETURN FROM BUFRLIB ROUTINE PKTDD, SEE PREVIOUS WARNING MESSAGE')
1093  enddo
1094  id = id+ldd+1 + nd*l30
1095  if(iupb(mesg,id+1,8)==0) id = id+1
1096  ntbd(lun) = n
1097  enddo
1098 
1099  return
1100 end subroutine stbfdx
1101 
1111 integer function idxmsg( mesg ) result( iret )
1112 
1113  implicit none
1114 
1115  integer, intent(in) :: mesg(*)
1116  integer iupbs01
1117 
1118  ! Note that the following test relies upon logic within subroutine dxmini() which zeroes out the Section 1 date of
1119  ! all DX dictionary messages.
1120 
1121  if ( (iupbs01(mesg,'MTYP')==11) .and. &
1122  (iupbs01(mesg,'MNTH')==0) .and. (iupbs01(mesg,'DAYS')==0) .and. (iupbs01(mesg,'HOUR')==0) ) then
1123  iret = 1
1124  else
1125  iret = 0
1126  end if
1127 
1128  return
1129 end function idxmsg
1130 
1141 integer function igetntbi ( lun, ctb ) result(iret)
1142 
1143  use moda_tababd
1144 
1145  implicit none
1146 
1147  integer, intent(in) :: lun
1148  integer imax
1149 
1150  character, intent(in) :: ctb
1151  character*128 bort_str
1152 
1153  if ( ctb == 'A' ) then
1154  iret = ntba(lun) + 1
1155  imax = ntba(0)
1156  else if ( ctb == 'B' ) then
1157  iret = ntbb(lun) + 1
1158  imax = ntbb(0)
1159  else ! ctb == 'D'
1160  iret = ntbd(lun) + 1
1161  imax = ntbd(0)
1162  endif
1163  if ( iret > imax ) then
1164  write(bort_str,'("BUFRLIB: IGETNTBI - NUMBER OF INTERNAL TABLE",A1," ENTRIES EXCEEDS THE LIMIT (",I4,")")') ctb, imax
1165  call bort(bort_str)
1166  endif
1167 
1168  return
1169 end function igetntbi
1170 
1185 subroutine nemtbax(lun,nemo,mtyp,msbt,inod)
1186 
1187  use moda_tababd
1188 
1189  implicit none
1190 
1191  integer, intent(in) :: lun
1192  integer, intent(out) :: mtyp, msbt, inod
1193  integer i
1194 
1195  character*(*), intent(in) :: nemo
1196  character*128 bort_str
1197 
1198  inod = 0
1199 
1200  ! Look for nemo in Table A
1201 
1202  do i=1,ntba(lun)
1203  if(taba(i,lun)(4:11)==nemo) then
1204  mtyp = idna(i,lun,1)
1205  msbt = idna(i,lun,2)
1206  inod = mtab(i,lun)
1207  if(mtyp<0 .or. mtyp>255) then
1208  write(bort_str,'("BUFRLIB: NEMTBAX - INVALID MESSAGE TYPE (",I4,") RETURNED FOR MENMONIC ",A)') mtyp, nemo
1209  call bort(bort_str)
1210  endif
1211  if(msbt<0 .or. msbt>255) then
1212  write(bort_str,'("BUFRLIB: NEMTBAX - INVALID MESSAGE SUBTYPE (",I4,") RETURNED FOR MENMONIC ",A)') msbt, nemo
1213  call bort(bort_str)
1214  endif
1215  exit
1216  endif
1217  enddo
1218 
1219  return
1220 end subroutine nemtbax
1221 
1235 subroutine nemtba(lun,nemo,mtyp,msbt,inod)
1236 
1237  implicit none
1238 
1239  integer, intent(in) :: lun
1240  integer, intent(out) :: mtyp, msbt, inod
1241 
1242  character*(*), intent(in) :: nemo
1243  character*128 bort_str
1244 
1245  ! Look for nemo in Table A
1246 
1247  call nemtbax(lun,nemo,mtyp,msbt,inod)
1248  if(inod==0) then
1249  write(bort_str,'("BUFRLIB: NEMTBA - CAN''T FIND MNEMONIC ",A)') nemo
1250  call bort(bort_str)
1251  endif
1252 
1253  return
1254 end subroutine nemtba
1255 
1266 subroutine nemtbb(lun,itab,unit,iscl,iref,ibit)
1267 
1268  use moda_tababd
1269 
1270  implicit none
1271 
1272  integer, intent(in) :: lun, itab
1273  integer, intent(out) :: iscl, iref, ibit
1274  integer idn, ierns
1275 
1276  character*128 bort_str
1277  character*24, intent(out) :: unit
1278  character*8 nemo
1279 
1280  if(itab<=0 .or. itab>ntbb(lun)) then
1281  write(bort_str,'("BUFRLIB: NEMTBB - ITAB (",I7,") NOT FOUND IN TABLE B")') itab
1282  call bort(bort_str)
1283  endif
1284 
1285  ! Pull out Table B information
1286 
1287  idn = idnb(itab,lun)
1288  nemo = tabb(itab,lun)( 7:14)
1289  unit = tabb(itab,lun)(71:94)
1290  call strnum(tabb(itab,lun)( 95: 98),iscl,ierns)
1291  call strnum(tabb(itab,lun)( 99:109),iref,ierns)
1292  call strnum(tabb(itab,lun)(110:112),ibit,ierns)
1293 
1294  ! Check Table B contents
1295 
1296  if(unit(1:5)/='CCITT' .and. ibit>32) then
1297  write(bort_str,'("BUFRLIB: NEMTBB - BIT WIDTH FOR NON-CHARACTER TABLE B MNEMONIC ",A," (",I7,") IS > 32")') nemo,ibit
1298  call bort(bort_str)
1299  endif
1300  if(unit(1:5)=='CCITT' .and. mod(ibit,8)/=0) then
1301  write(bort_str,'("BUFRLIB: NEMTBB - BIT WIDTH FOR CHARACTER TABLE B MNEMONIC ",A," (",I7,") IS NOT A MULTIPLE OF 8")') &
1302  nemo,ibit
1303  call bort(bort_str)
1304  endif
1305 
1306  return
1307 end subroutine nemtbb
1308 
1334 subroutine nemtbd(lun,itab,nseq,nems,irps,knts)
1335 
1336  use modv_vars, only: maxcd
1337 
1338  use moda_tababd
1339 
1340  implicit none
1341 
1342  integer, intent(in) :: lun, itab
1343  integer, intent(out) :: nseq, irps(*), knts(*)
1344  integer i, j, ndsc, idsc, iret
1345 
1346  character*128 bort_str
1347  character*8, intent(out) :: nems(*)
1348  character*8 nemo, nemt, nemf
1349  character tab
1350 
1351  if(itab<=0 .or. itab>ntbd(lun)) then
1352  write(bort_str,'("BUFRLIB: NEMTBD - ITAB (",I7,") NOT FOUND IN TABLE D")') itab
1353  call bort(bort_str)
1354  endif
1355 
1356  ! Clear the return values
1357 
1358  nseq = 0
1359 
1360  do i=1,maxcd
1361  nems(i) = ' '
1362  irps(i) = 0
1363  knts(i) = 0
1364  enddo
1365 
1366  ! Parse the Table D entry
1367 
1368  nemo = tabd(itab,lun)(7:14)
1369  idsc = idnd(itab,lun)
1370  call uptdd(itab,lun,0,ndsc)
1371 
1372  ! Loop through each child mnemonic
1373 
1374  do j=1,ndsc
1375  if(nseq+1>maxcd) then
1376  write(bort_str,'("BUFRLIB: NEMTBD - THERE ARE MORE THAN '// &
1377  '(",I4,") DESCRIPTORS (THE LIMIT) IN TABLE D SEQUENCE MNEMONIC ",A)') maxcd, nemo
1378  call bort(bort_str)
1379  endif
1380  call uptdd(itab,lun,j,idsc)
1381  call numtab(lun,idsc,nemt,tab,iret)
1382  if(tab=='R') then
1383  if(iret<0) then
1384  ! Regular (i.e. non-delayed) replication
1385  irps(nseq+1) = 1
1386  knts(nseq+1) = abs(iret)
1387  elseif(iret>0) then
1388  ! Delayed replication
1389  irps(nseq+1) = iret
1390  endif
1391  elseif(tab=='F') then
1392  ! Replication factor
1393  irps(nseq+1) = iret
1394  elseif(tab=='D'.or.tab=='C') then
1395  nseq = nseq+1
1396  nems(nseq) = nemt
1397  elseif(tab=='B') then
1398  nseq = nseq+1
1399  if((nemt(1:1)=='.').and.(j<ndsc)) then
1400  ! This is a "following value" mnemonic
1401  call uptdd(itab,lun,j+1,idsc)
1402  call numtab(lun,idsc,nemf,tab,iret)
1403  call rsvfvm(nemt,nemf)
1404  endif
1405  nems(nseq) = nemt
1406  endif
1407  enddo
1408 
1409  return
1410 end subroutine nemtbd
1411 
1434 recursive subroutine nemdefs ( lunit, nemo, celem, cunit, iret )
1435 
1436  use modv_vars, only: im8b
1437 
1438  use moda_tababd
1439 
1440  implicit none
1441 
1442  integer, intent(in) :: lunit
1443  integer, intent(out) :: iret
1444  integer my_lunit, lun, il, im, idn, iloc, ls
1445 
1446  character*(*), intent(in) :: nemo
1447  character*(*), intent(out) :: celem, cunit
1448  character tab
1449 
1450  ! Check for I8 integers.
1451 
1452  if(im8b) then
1453  im8b=.false.
1454  call x84 ( lunit, my_lunit, 1 )
1455  call nemdefs ( my_lunit, nemo, celem, cunit, iret )
1456  call x48 ( iret, iret, 1 )
1457  im8b=.true.
1458  return
1459  endif
1460 
1461  iret = -1
1462 
1463  ! Get lun from lunit.
1464 
1465  call status( lunit, lun, il, im )
1466  if ( il == 0 ) return
1467 
1468  ! Find the requested mnemonic in the internal Table B arrays.
1469 
1470  call nemtab( lun, nemo, idn, tab, iloc )
1471  if ( ( iloc == 0 ) .or. ( tab /= 'B' ) ) return
1472 
1473  ! Get the element name and units of the requested mnemonic.
1474 
1475  celem = ' '
1476  ls = min(len(celem),55)
1477  celem(1:ls) = tabb(iloc,lun)(16:15+ls)
1478 
1479  cunit = ' '
1480  ls = min(len(cunit),24)
1481  cunit(1:ls) = tabb(iloc,lun)(71:70+ls)
1482 
1483  iret = 0
1484 
1485  return
1486 end subroutine nemdefs
1487 
1502 subroutine nenubd(nemo,numb,lun)
1503 
1504  use moda_tababd
1505 
1506  implicit none
1507 
1508  character, intent(in) :: nemo*8, numb*6
1509  character*128 bort_str
1510 
1511  integer, intent(in) :: lun
1512  integer n
1513 
1514  do n=1,ntbb(lun)
1515  if(numb==tabb(n,lun)(1:6)) then
1516  write(bort_str,'("BUFRLIB: NENUBD - TABLE B FXY VALUE (",A,") HAS ALREADY BEEN DEFINED (DUPLICATE)")') numb
1517  call bort(bort_str)
1518  endif
1519  if(nemo==tabb(n,lun)(7:14)) then
1520  write(bort_str,'("BUFRLIB: NENUBD - TABLE B MNEMONIC (",A,") HAS ALREADY BEEN DEFINED (DUPLICATE)")') nemo
1521  call bort(bort_str)
1522  endif
1523  enddo
1524 
1525  do n=1,ntbd(lun)
1526  if(numb==tabd(n,lun)(1:6)) then
1527  write(bort_str,'("BUFRLIB: NENUBD - TABLE D FXY VALUE (",A,") HAS ALREADY BEEN DEFINED (DUPLICATE)")') numb
1528  call bort(bort_str)
1529  endif
1530  if(nemo==tabd(n,lun)(7:14)) then
1531  write(bort_str,'("BUFRLIB: NENUBD - TABLE D MNEMONIC (",A,") HAS ALREADY BEEN DEFINED (DUPLICATE)")') nemo
1532  call bort(bort_str)
1533  endif
1534  enddo
1535 
1536  return
1537 end subroutine nenubd
1538 
1548 subroutine stntbia ( n, lun, numb, nemo, celsq )
1549 
1550  use moda_tababd
1551 
1552  implicit none
1553 
1554  integer, intent(in) :: n, lun
1555  integer i, mtyp, msbt
1556 
1557  character*(*), intent(in) :: numb, nemo, celsq
1558  character*128 bort_str
1559 
1560  ! Confirm that neither nemo nor numb has already been defined within the internal BUFR Table A for the given lun.
1561 
1562  do i=1,ntba(lun)
1563  if(numb(4:6)==taba(i,lun)(1:3)) then
1564  write(bort_str,'("BUFRLIB: STNTBIA - TABLE A FXY VALUE (",A,") HAS ALREADY BEEN DEFINED (DUPLICATE)")') numb
1565  call bort(bort_str)
1566  endif
1567  if(nemo(1:8)==taba(i,lun)(4:11)) then
1568  write(bort_str,'("BUFRLIB: STNTBIA - TABLE A MNEMONIC (",A,") HAS ALREADY BEEN DEFINED (DUPLICATE)")') nemo
1569  call bort(bort_str)
1570  endif
1571  enddo
1572 
1573  ! Store the values within the internal BUFR Table A.
1574 
1575  taba(n,lun)(1:3) = numb(4:6)
1576  taba(n,lun)(4:11) = nemo(1:8)
1577  taba(n,lun)(13:67) = celsq(1:55)
1578 
1579  ! Decode and store the message type and subtype.
1580 
1581  if ( verify( nemo(3:8), '1234567890' ) == 0 ) then
1582  ! Message type & subtype obtained directly from Table A mnemonic
1583  read ( nemo,'(2X,2I3)') mtyp, msbt
1584  idna(n,lun,1) = mtyp
1585  idna(n,lun,2) = msbt
1586  else
1587  ! Message type obtained from Y value of Table A seq. descriptor
1588  read ( numb(4:6),'(I3)') idna(n,lun,1)
1589  ! Message subtype hardwired to zero
1590  idna(n,lun,2) = 0
1591  endif
1592 
1593  ! Update the count of internal Table A entries.
1594 
1595  ntba(lun) = n
1596 
1597  return
1598 end subroutine stntbia
1599 
1609 subroutine stntbi ( n, lun, numb, nemo, celsq )
1610 
1611  use moda_tababd
1612 
1613  implicit none
1614 
1615  integer, intent(in) :: n, lun
1616  integer ifxy
1617 
1618  character*(*), intent(in) :: numb, nemo, celsq
1619 
1620  call nenubd ( nemo, numb, lun )
1621 
1622  if ( numb(1:1) == '0') then
1623  idnb(n,lun) = ifxy(numb)
1624  tabb(n,lun)(1:6) = numb(1:6)
1625  tabb(n,lun)(7:14) = nemo(1:8)
1626  tabb(n,lun)(16:70) = celsq(1:55)
1627  ntbb(lun) = n
1628  else ! numb(1:1) == '3'
1629  idnd(n,lun) = ifxy(numb)
1630  tabd(n,lun)(1:6) = numb(1:6)
1631  tabd(n,lun)(7:14) = nemo(1:8)
1632  tabd(n,lun)(16:70) = celsq(1:55)
1633  ntbd(lun) = n
1634  endif
1635 
1636  return
1637 end subroutine stntbi
1638 
1654 subroutine pktdd(id,lun,idn,iret)
1655 
1656  use modv_vars, only: maxcd, iprt, idxv
1657 
1658  use moda_tababd
1659 
1660  implicit none
1661 
1662  integer, intent(in) :: id, lun, idn
1663  integer, intent(out) :: iret
1664  integer nxstr, ldxa, ldxb, ldxd, ld30, ldd, nd, idm, iupm
1665 
1666  character*128 errstr
1667  character*56 dxstr
1668 
1669  common /dxtab/ nxstr(10), ldxa(10), ldxb(10), ldxd(10), ld30(10), dxstr(10)
1670 
1671  ! ldd points to the byte within tabd(id,lun) which contains (in packed integer format) a count of the number of child
1672  ! mnemonics stored thus far for this parent mnemonic.
1673  ldd = ldxd(idxv+1)+1
1674 
1675  ! Zero the counter if idn is zero
1676  if(idn==0) then
1677  call ipkm(tabd(id,lun)(ldd:ldd),1,0)
1678  iret = 0
1679  return
1680  endif
1681 
1682  ! Update the stored descriptor count for this Table D entry. nd is the (unpacked) count of the number of child mnemonics
1683  ! stored thus far for this parent mnemonic.
1684  nd = iupm(tabd(id,lun)(ldd:ldd),8)
1685 
1686  if(nd<0 .or. nd==maxcd) then
1687  if(iprt>=0) then
1688  call errwrt('+++++++++++++++++++++WARNING+++++++++++++++++++++++')
1689  if(nd<0) then
1690  write ( unit=errstr, fmt='(A,I4,A)' ) 'BUFRLIB: PKTDD - BAD COUNTER VALUE (=', nd, ') - RETURN WITH IRET = -1'
1691  else
1692  write ( unit=errstr, fmt='(A,I4,A,A)' ) 'BUFRLIB: PKTDD - MAXIMUM NUMBER OF CHILD MNEMONICS (=', &
1693  maxcd, ') ALREADY STORED FOR THIS PARENT - RETURN WITH IRET = -1'
1694  endif
1695  call errwrt(errstr)
1696  call errwrt('+++++++++++++++++++++WARNING+++++++++++++++++++++++')
1697  call errwrt(' ')
1698  endif
1699  iret = -1
1700  return
1701  else
1702  nd = nd+1
1703  call ipkm(tabd(id,lun)(ldd:ldd),1,nd)
1704  iret = nd
1705  endif
1706 
1707  ! Pack and store the descriptor. idm points to the starting byte within tabd(id,lun) at which the idn value for this
1708  ! child mnemonic will be stored (as a packed integer of width = 2 bytes).
1709  idm = ldd+1 + (nd-1)*2
1710  call ipkm(tabd(id,lun)(idm:idm+1),2,idn)
1711 
1712  return
1713 end subroutine pktdd
1714 
1728 subroutine uptdd(id,lun,ient,iret)
1729 
1730  use modv_vars, only: idxv
1731 
1732  use moda_tababd
1733 
1734  implicit none
1735 
1736  integer, intent(in) :: id, lun, ient
1737  integer, intent(out) :: iret
1738  integer nxstr, ldxa, ldxb, ldxd, ld30, ldd, ndsc, idsc, iupm
1739 
1740  character*128 bort_str
1741  character*56 dxstr
1742 
1743  common /dxtab/ nxstr(10), ldxa(10), ldxb(10), ldxd(10), ld30(10), dxstr(10)
1744 
1745  ! Check if ient is in bounds
1746 
1747  ldd = ldxd(idxv+1)+1
1748  ndsc = iupm(tabd(id,lun)(ldd:ldd),8)
1749  if(ient==0) then
1750  iret = ndsc
1751  return
1752  elseif(ient<0 .or. ient>ndsc) then
1753  write(bort_str,'("BUFRLIB: UPTDD - VALUE OF THIRD ARGUMENT IENT (INPUT) IS OUT OF RANGE (IENT =",I4,")")') ient
1754  call bort(bort_str)
1755  endif
1756 
1757  ! Return the descriptor indicated by ient
1758 
1759  idsc = ldd+1 + (ient-1)*2
1760  iret = iupm(tabd(id,lun)(idsc:idsc+1),16)
1761 
1762  return
1763 end subroutine uptdd
1764 
1784 subroutine rsvfvm(nem1,nem2)
1785 
1786  implicit none
1787 
1788  character*8, intent(inout) :: nem1
1789  character*8, intent(in) :: nem2
1790 
1791  integer i, j
1792 
1793  do i=1,len(nem1)
1794  if(i==1) then
1795  ! Skip the initial ".", and initialize J.
1796  j = 1
1797  else
1798  if(nem1(i:i)=='.') then
1799  nem1(i:i) = nem2(j:j)
1800  j = j+1
1801  endif
1802  endif
1803  enddo
1804 
1805  return
1806 end subroutine rsvfvm
recursive subroutine bort(str)
Log an error message, then either return to or abort the application program.
Definition: borts.F90:15
recursive subroutine bort2(str1, str2)
Log two error messages, then either return to or abort the application program.
Definition: borts.F90:48
recursive integer function iupb(mbay, nbyt, nbit)
Decode an integer value from within a specified number of bits of an integer array,...
Definition: cidecode.F90:226
recursive integer function iupm(cbay, nbits)
Decode an integer value from within a specified number of bits of a character string,...
Definition: cidecode.F90:265
subroutine upc(chr, nchr, ibay, ibit, cnvnull)
Decode a character string from within a specified number of bytes of an integer array,...
Definition: cidecode.F90:26
subroutine pkc(chr, nchr, ibay, ibit)
Encode a character string within a specified number of bytes of an integer array, starting at the bit...
Definition: ciencode.F90:25
recursive subroutine ipkm(cbay, nbyt, n)
Encode an integer value within a specified number of bytes of a character string, up to a maximum of ...
Definition: ciencode.F90:194
subroutine pkb(nval, nbits, ibay, ibit)
Encode an integer value within a specified number of bits of an integer array, starting at the bit im...
Definition: ciencode.F90:140
subroutine cpbfdx(lud, lun)
Copy all of the DX BUFR table information from one unit to another within internal memory.
Definition: copydata.F90:676
subroutine elemdx(card, lun)
Decode the scale factor, reference value, bit width and units (i.e., the "elements") from a Table B m...
Definition: dxtable.F90:514
subroutine nemtbb(lun, itab, unit, iscl, iref, ibit)
Get information about a Table B descriptor from the internal DX BUFR tables.
Definition: dxtable.F90:1267
subroutine dxmini(mbay, mbyt, mb4, mba, mbb, mbd)
Initialize a DX BUFR tables (dictionary) message, writing all the preliminary information into Sectio...
Definition: dxtable.F90:691
subroutine nemtba(lun, nemo, mtyp, msbt, inod)
Get information about a Table A descriptor from the internal DX BUFR tables.
Definition: dxtable.F90:1236
subroutine rdusdx(lundx, lun)
Read and parse a file containing a user-supplied DX BUFR table in character format,...
Definition: dxtable.F90:197
subroutine rsvfvm(nem1, nem2)
Process a "following value" mnemonic.
Definition: dxtable.F90:1785
subroutine seqsdx(card, lun)
Decode the Table D sequence information from a mnemonic definition card that was previously read from...
Definition: dxtable.F90:333
recursive subroutine wrdxtb(lundx, lunot)
Generate one or more BUFR messages from the DX BUFR tables information associated with a given BUFR f...
Definition: dxtable.F90:838
subroutine nemtbax(lun, nemo, mtyp, msbt, inod)
Get information about a Table A descriptor from the internal DX BUFR tables.
Definition: dxtable.F90:1186
subroutine nemtbd(lun, itab, nseq, nems, irps, knts)
Get information about a Table D descriptor from the internal DX BUFR tables.
Definition: dxtable.F90:1335
subroutine stntbi(n, lun, numb, nemo, celsq)
Store a new entry within internal BUFR Table B or D.
Definition: dxtable.F90:1610
subroutine pktdd(id, lun, idn, iret)
Store information about a child mnemonic within the internal BUFR Table D.
Definition: dxtable.F90:1655
subroutine stntbia(n, lun, numb, nemo, celsq)
Store a new entry within internal BUFR Table A.
Definition: dxtable.F90:1549
subroutine stbfdx(lun, mesg)
Copy a DX BUFR tables message into the internal memory arrays in module moda_tababd.
Definition: dxtable.F90:979
subroutine writdx(lunit, lun, lundx)
Write DX BUFR table (dictionary) messages to the beginning of an output BUFR file in lunit.
Definition: dxtable.F90:800
recursive subroutine nemdefs(lunit, nemo, celem, cunit, iret)
Get the element name and units associated with a Table B descriptor.
Definition: dxtable.F90:1435
integer function igetntbi(lun, ctb)
Get the next available index for storing an entry within a specified internal DX BUFR table.
Definition: dxtable.F90:1142
subroutine readdx(lunit, lun, lundx)
Initialize modules moda_tababd and moda_msgcwd with DX BUFR (dictionary) tables.
Definition: dxtable.F90:29
subroutine dxinit(lun, ioi)
Clear out the internal arrays (in module moda_tababd) holding the DX BUFR table, then optionally init...
Definition: dxtable.F90:604
subroutine nenubd(nemo, numb, lun)
Confirm that a mnemonic and FXY value haven't already been defined.
Definition: dxtable.F90:1503
integer function idxmsg(mesg)
Check whether a BUFR message contains DX BUFR tables information that was generated by the NCEPLIBS-b...
Definition: dxtable.F90:1112
subroutine uptdd(id, lun, ient, iret)
Get the WMO bit-wise representation of the FXY value corresponding to a child mnemonic in a Table D s...
Definition: dxtable.F90:1729
subroutine rdbfdx(lunit, lun)
Beginning at the current file pointer location within lunit, read a complete DX BUFR table into inter...
Definition: dxtable.F90:121
subroutine errwrt(str)
Specify a custom location for the logging of error and diagnostic messages generated by the NCEPLIBS-...
Definition: errwrt.F90:32
subroutine nemtab(lun, nemo, idn, tab, iret)
Get information about a descriptor, based on a mnemonic.
Definition: fxy.F90:434
subroutine numtab(lun, idn, nemo, tab, iret)
Get information about a descriptor, based on the WMO bit-wise representation of an FXY value.
Definition: fxy.F90:359
character *(*) function adn30(idn, ldn)
Convert an FXY value from its WMO bit-wise representation to a character string of length 5 or 6.
Definition: fxy.F90:18
subroutine jstnum(str, sign, iret)
Left-justify a character string containing an encoded integer, by removing all leading blanks and any...
Definition: misc.F90:282
recursive subroutine strnum(str, num, iret)
Decode an integer from a character string.
Definition: misc.F90:156
subroutine capit(str)
Capitalize all of the alphabetic characters in a string.
Definition: misc.F90:334
Wrap C NCEPLIBS-bufr functions so they can be called from within the Fortran part of the library.
Definition: bufrlib.F90:11
Declare arrays and variables used to store BUFR messages internally for multiple file IDs.
integer maxbyt
Maximum length of an output BUFR message.
Declare an array used by various subroutines and functions to hold a temporary working copy of a BUFR...
integer, dimension(:), allocatable mgwa
Temporary working copy of BUFR message.
Declare arrays and variables used to store DX BUFR tables internally for multiple file IDs.
integer, dimension(:), allocatable ntba
Number of Table A entries for each file ID (up to a maximum of maxtba, whose value is stored in array...
character *600, dimension(:,:), allocatable tabd
Table D entries for each file ID.
character *128, dimension(:,:), allocatable taba
Table A entries for each file ID.
integer, dimension(:,:), allocatable mtab
Entries within jump/link table corresponding to taba.
integer, dimension(:,:,:), allocatable idna
Message types (in array element 1) and subtypes (in array element 2) corresponding to taba.
integer, dimension(:), allocatable ntbd
Number of Table D entries for each file ID (up to a maximum of maxtbd, whose value is stored in array...
integer, dimension(:), allocatable ntbb
Number of Table B entries for each file ID (up to a maximum of maxtbb, whose value is stored in array...
integer, dimension(:,:), allocatable idnd
WMO bit-wise representations of the FXY values corresponding to tabd.
integer, dimension(:,:), allocatable idnb
WMO bit-wise representations of the FXY values corresponding to tabb.
character *128, dimension(:,:), allocatable tabb
Table B entries for each file ID.
recursive subroutine status(lunit, lun, il, im)
Check whether a specified Fortran logical unit number is currently connected to the NCEPLIBS-bufr sof...
logical function msgfull(msiz, itoadd, mxsiz)
Check whether the current data subset in the internal arrays will fit within the current BUFR message...
recursive subroutine getlens(mbay, ll, len0, len1, len2, len3, len4, len5)
Read the section lengths of a BUFR message, up to a specified point in the message.
subroutine rdmsgw(lunit, mesg, iret)
Read the next BUFR message from logical unit lunit as an array of integer words.
subroutine msgwrt(lunit, mesg, mgbyt)
Perform final checks and updates on a BUFR message before writing it to a specified Fortran logical u...
recursive integer function iupbs01(mbay, s01mnem)
Read a specified value from within Section 0 or Section 1 of a BUFR message.
Definition: s013vals.F90:247
subroutine parstr(str, tags, mtag, ntag, sep, limit80)
Parse a string containing one or more substrings into an array of substrings.
Definition: strings.F90:473
subroutine x48(iin4, iout8, nval)
Encode one or more 4-byte integer values as 8-byte integer values.
Definition: x4884.F90:18
subroutine x84(iin8, iout4, nval)
Encode one or more 8-byte integer values as 4-byte integer values.
Definition: x4884.F90:65