30 use modv_vars,
only: iprt
34 integer,
intent(in) :: lunit, lun, lundx
35 integer lud, ildx, imdx
41 call status(lundx,lud,ildx,imdx)
45 if (lunit==lundx)
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'
52 call errwrt(
'++++++++++++BUFR ARCHIVE LIBRARY+++++++++++++++')
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
64 call errwrt(
'++++++++++++BUFR ARCHIVE LIBRARY+++++++++++++++')
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
76 call errwrt(
'++++++++++++BUFR ARCHIVE LIBRARY+++++++++++++++')
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'
88 call errwrt(
'++++++++++++BUFR ARCHIVE LIBRARY+++++++++++++++')
94 call bort(
'BUFRLIB: READDX - CANNOT DETERMINE SOURCE OF INPUT DICTIONARY TABLE')
124 use modv_vars,
only: iprt
130 integer,
intent(in) :: lunit, lun
131 integer ict, ier, idxmsg, iupbs3
144 do while ( .not. done )
146 if ( ier == -1 )
then
152 else if ( ier == -2 )
then
153 call bort(
'BUFRLIB: RDBFDX - ERROR READING A BUFR DICTIONARY MESSAGE')
154 else if ( idxmsg(
mgwa) /= 1 )
then
159 else if ( iupbs3(
mgwa,
'NSUB') == 0 )
then
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;'
174 errstr =
'WILL APPLY THIS TABLE TO ALL SUBSEQUENT DATA IN FILE UNTIL NEXT DX TABLE IS FOUND'
176 call errwrt(
'+++++++++++++++++++++++++++++++++++++++++++++++++')
202 integer,
intent(in) :: lundx, lun
203 integer ios, iret, n, numbck, nemock, igetntbi
205 character*128 bort_str1
206 character*156 bort_str2
209 character*6 numb, nmb2
220 read(lundx,
'(A80)', iostat = ios) card
226 if(card(1: 1)==
'*') cycle
227 if(card(3:10)==
'--------') cycle
228 if(card(3:10)==
' ') cycle
229 if(card(3:10)==
'MNEMONIC') cycle
230 if(card(3:10)==
'TABLE D') cycle
231 if(card(3:10)==
'TABLE B') cycle
233 if(card(12:12)==
'|' .and. card(21:21)==
'|')
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)
245 if(nmb2(1:1)==
'A') nmb2(1:1) =
'3'
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)
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)
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)
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)
272 if(numb(1:1)==
'A')
then
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)
285 if(numb(1:1)==
'0')
then
287 call stntbi ( igetntbi(lun,
'B'), lun, numb, nemo, card(23:) )
291 if(numb(1:1)==
'3')
then
293 call stntbi ( igetntbi(lun,
'D'), lun, numb, nemo, card(23:) )
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)
304 if(card(12:12)==
'|' .and. card(19:19)/=
'|')
then
310 if(card(12:12)==
'|' .and. card(19:19)==
'|')
then
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)
334 use modv_vars,
only: reps, idnr
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
342 character*128 bort_str1, bort_str2
344 character*80,
intent(in) :: card
345 character*(maxtag) atag, tags(maxtgs)
346 character*8 nemo, nema, nemb
347 character*6 adn30, clemon
361 call nemtab(lun,nemo,idn,tab,iseq)
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)
367 call parstr(seqs,tags,maxtgs,ntag,
' ',.true.)
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)
381 if(atag(1:1)==reps(i))
then
386 if(atag(j:j)==reps(i+5))
then
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)
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)
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)
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)
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)
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)
437 call nemtab(lun,atag,idn,tab,iret)
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)
448 if(atag(1:1)==
'.')
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)
458 nemb = tags(n+1)(1:8)
459 call numtab(lun,idn,nema,tab,itab)
460 call nemtab(lun,nemb,jdn,tab,iret)
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)
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)
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)
483 if(irep>0)
call pktdd(iseq,lun,idnr(irep)+numr,iret)
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)
491 call pktdd(iseq,lun,idn,iret)
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)
519 integer,
intent(in) :: lun
520 integer idsn, iele, iret
522 character*128 bort_str1, bort_str2
523 character*80,
intent(in) :: card
525 character*11 refr, refr_orig
527 character*4 scal, scal_orig
528 character*3 bitw, bitw_orig
545 call nemtab(lun,nemo,idsn,tab,iele)
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)
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)
560 tabb(iele,lun)(71:94) = unit
563 call jstnum(scal,sign,iret)
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)
569 tabb(iele,lun)(95:95) = sign
570 tabb(iele,lun)(96:98) = scal(1:3)
573 call jstnum(refr,sign,iret)
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)
579 tabb(iele,lun)( 99: 99) = sign
580 tabb(iele,lun)(100:109) = refr(1:10)
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)
589 tabb(iele,lun)(110:112) = bitw
605 use modv_vars,
only: idnr, fxy_fbit, fxy_sbyct, fxy_drf16, fxy_drf8, fxy_drf1
611 integer,
intent(in) :: lun, ioi
612 integer ninib, ninid, n, i, iret, ifxy
614 character*8 inib(6,5),inid(5)
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'/
645 call pktdd(i,lun,0,iret)
652 inib(1,1) = fxy_sbyct
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)
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)
690 subroutine dxmini(mbay,mbyt,mb4,mba,mbb,mbd)
692 use modv_vars,
only: mxmsgld4, mtv, nby0, nby1, nby2, nby5, bmostr, idxv
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, &
700 character*128 bort_str
703 common /dxtab/ nxstr(10), ldxa(10), ldxb(10), ldxd(10), ld30(10), dxstr(10)
725 len3 = 7 + nxstr(idxs) + 1
727 mbyt = nby0+nby1+nby2+len3+nby4+nby5
729 if(mod(len3,2)/=0)
call bort (
'BUFRLIB: DXMINI - LENGTH OF SECTION 3 IS NOT A MULTIPLE OF 2')
733 call pkc(bmostr , 4 , mbay,mbit)
734 call pkb( mbyt , 24 , mbay,mbit)
735 call pkb( 3 , 8 , mbay,mbit)
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)
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)
763 call pkb(iupm(dxstr(idxs)(i:i),8),8,mbay,mbit)
765 call pkb( 0 , 8 , mbay,mbit)
770 call pkb( nby4 , 24 , mbay,mbit)
771 call pkb( 0 , 8 , mbay,mbit)
773 call pkb( 0 , 8 , mbay,mbit)
775 call pkb( 0 , 8 , mbay,mbit)
777 call pkb( 0 , 8 , mbay,mbit)
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
803 integer,
intent(in) :: lunit, lun, lundx
805 character*128 bort_str
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
817 call readdx(lunit,lun,lundx)
839 use modv_vars,
only: im8b, idxv
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
851 common /dxtab/ nxstr(10), ldxa(10), ldxb(10), ldxd(10), ld30(10), dxstr(10)
863 call x84(lundx,my_lundx,1)
864 call x84(lunot,my_lunot,1)
865 call wrdxtb(my_lundx,my_lunot)
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')
877 call status(lundx,ldx,il,im)
878 if(il==0)
call bort(
'BUFRLIB: WRDXTB - DX TABLE FILE IS CLOSED, IT MUST BE OPEN')
882 if(lundx/=lunot)
call cpbfdx(ldx,lot)
934 nseq =
iupm(
tabd(i,lot)(ldd+1:ldd+1),8)
935 lend = ldd+1 + l30*nseq
965 mbit = (len0+len1+len2+4)*8
980 use modv_vars,
only: maxcd, idxv
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
991 character*128 bort_str
992 character*128 tabb1, tabb2
998 character*6 numb, cidn
1000 common /dxtab/ nxstr(10), ldxa(10), ldxb(10), ldxd(10), ld30(10), dxstr(10)
1002 data ldxbd /38, 70, 8*0/
1003 data ldxbe /42, 42, 8*0/
1006 ja(i) = ia+1+lda*(i-1)
1007 jb(i) = ib+1+ldb*(i-1)
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)')
1016 call getlens(mesg,3,len0,len1,len2,len3,l4,l5)
1020 call upc(dxcmp,nxstr(idxs),mesg,jbit,.false.)
1021 if(dxcmp/=dxstr(idxs))
call bort(
'BUFRLIB: STBFDX - UNEXPECTED DICTIONARY MESSAGE CONTENTS')
1033 la = iupb(mesg,ia,8)
1035 lb = iupb(mesg,ib,8)
1037 ld = iupb(mesg,id,8)
1042 n = igetntbi(lun,
'A')
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)
1054 n = igetntbi(lun,
'B')
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)
1066 tabb(n,lun)(71:94) = unit
1073 n = igetntbi(lun,
'D')
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)
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
1087 ndd = id+ldd+2 + (j-1)*l30
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')
1094 id = id+ldd+1 + nd*l30
1095 if(iupb(mesg,id+1,8)==0) id = id+1
1111 integer function idxmsg( mesg )
result( iret )
1115 integer,
intent(in) :: mesg(*)
1121 if ( (
iupbs01(mesg,
'MTYP')==11) .and. &
1147 integer,
intent(in) :: lun
1150 character,
intent(in) :: ctb
1151 character*128 bort_str
1153 if ( ctb ==
'A' )
then
1154 iret =
ntba(lun) + 1
1156 else if ( ctb ==
'B' )
then
1157 iret =
ntbb(lun) + 1
1160 iret =
ntbd(lun) + 1
1163 if ( iret > imax )
then
1164 write(bort_str,
'("BUFRLIB: IGETNTBI - NUMBER OF INTERNAL TABLE",A1," ENTRIES EXCEEDS THE LIMIT (",I4,")")') ctb, imax
1191 integer,
intent(in) :: lun
1192 integer,
intent(out) :: mtyp, msbt, inod
1195 character*(*),
intent(in) :: nemo
1196 character*128 bort_str
1203 if(
taba(i,lun)(4:11)==nemo)
then
1204 mtyp =
idna(i,lun,1)
1205 msbt =
idna(i,lun,2)
1207 if(mtyp<0 .or. mtyp>255)
then
1208 write(bort_str,
'("BUFRLIB: NEMTBAX - INVALID MESSAGE TYPE (",I4,") RETURNED FOR MENMONIC ",A)') mtyp, nemo
1211 if(msbt<0 .or. msbt>255)
then
1212 write(bort_str,
'("BUFRLIB: NEMTBAX - INVALID MESSAGE SUBTYPE (",I4,") RETURNED FOR MENMONIC ",A)') msbt, nemo
1239 integer,
intent(in) :: lun
1240 integer,
intent(out) :: mtyp, msbt, inod
1242 character*(*),
intent(in) :: nemo
1243 character*128 bort_str
1247 call nemtbax(lun,nemo,mtyp,msbt,inod)
1249 write(bort_str,
'("BUFRLIB: NEMTBA - CAN''T FIND MNEMONIC ",A)') nemo
1266 subroutine nemtbb(lun,itab,unit,iscl,iref,ibit)
1272 integer,
intent(in) :: lun, itab
1273 integer,
intent(out) :: iscl, iref, ibit
1276 character*128 bort_str
1277 character*24,
intent(out) :: unit
1280 if(itab<=0 .or. itab>
ntbb(lun))
then
1281 write(bort_str,
'("BUFRLIB: NEMTBB - ITAB (",I7,") NOT FOUND IN TABLE B")') itab
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)
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
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")') &
1334 subroutine nemtbd(lun,itab,nseq,nems,irps,knts)
1336 use modv_vars,
only: maxcd
1342 integer,
intent(in) :: lun, itab
1343 integer,
intent(out) :: nseq, irps(*), knts(*)
1344 integer i, j, ndsc, idsc, iret
1346 character*128 bort_str
1347 character*8,
intent(out) :: nems(*)
1348 character*8 nemo, nemt, nemf
1351 if(itab<=0 .or. itab>
ntbd(lun))
then
1352 write(bort_str,
'("BUFRLIB: NEMTBD - ITAB (",I7,") NOT FOUND IN TABLE D")') itab
1368 nemo =
tabd(itab,lun)(7:14)
1369 idsc =
idnd(itab,lun)
1370 call uptdd(itab,lun,0,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
1380 call uptdd(itab,lun,j,idsc)
1381 call numtab(lun,idsc,nemt,tab,iret)
1386 knts(nseq+1) = abs(iret)
1391 elseif(tab==
'F')
then
1394 elseif(tab==
'D'.or.tab==
'C')
then
1397 elseif(tab==
'B')
then
1399 if((nemt(1:1)==
'.').and.(j<ndsc))
then
1401 call uptdd(itab,lun,j+1,idsc)
1402 call numtab(lun,idsc,nemf,tab,iret)
1434 recursive subroutine nemdefs ( lunit, nemo, celem, cunit, iret )
1436 use modv_vars,
only: im8b
1442 integer,
intent(in) :: lunit
1443 integer,
intent(out) :: iret
1444 integer my_lunit, lun, il, im, idn, iloc, ls
1446 character*(*),
intent(in) :: nemo
1447 character*(*),
intent(out) :: celem, cunit
1454 call x84 ( lunit, my_lunit, 1 )
1455 call nemdefs ( my_lunit, nemo, celem, cunit, iret )
1456 call x48 ( iret, iret, 1 )
1465 call status( lunit, lun, il, im )
1466 if ( il == 0 )
return
1470 call nemtab( lun, nemo, idn, tab, iloc )
1471 if ( ( iloc == 0 ) .or. ( tab /=
'B' ) )
return
1476 ls = min(len(celem),55)
1477 celem(1:ls) =
tabb(iloc,lun)(16:15+ls)
1480 ls = min(len(cunit),24)
1481 cunit(1:ls) =
tabb(iloc,lun)(71:70+ls)
1508 character,
intent(in) :: nemo*8, numb*6
1509 character*128 bort_str
1511 integer,
intent(in) :: 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
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
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
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
1554 integer,
intent(in) :: n, lun
1555 integer i, mtyp, msbt
1557 character*(*),
intent(in) :: numb, nemo, celsq
1558 character*128 bort_str
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
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
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)
1581 if ( verify( nemo(3:8),
'1234567890' ) == 0 )
then
1583 read ( nemo,
'(2X,2I3)') mtyp, msbt
1584 idna(n,lun,1) = mtyp
1585 idna(n,lun,2) = msbt
1588 read ( numb(4:6),
'(I3)')
idna(n,lun,1)
1609 subroutine stntbi ( n, lun, numb, nemo, celsq )
1615 integer,
intent(in) :: n, lun
1618 character*(*),
intent(in) :: numb, nemo, celsq
1620 call nenubd ( nemo, numb, lun )
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)
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)
1656 use modv_vars,
only: maxcd, iprt, idxv
1662 integer,
intent(in) :: id, lun, idn
1663 integer,
intent(out) :: iret
1664 integer nxstr, ldxa, ldxb, ldxd, ld30, ldd, nd, idm, iupm
1666 character*128 errstr
1669 common /dxtab/ nxstr(10), ldxa(10), ldxb(10), ldxd(10), ld30(10), dxstr(10)
1673 ldd = ldxd(idxv+1)+1
1677 call ipkm(
tabd(id,lun)(ldd:ldd),1,0)
1684 nd = iupm(
tabd(id,lun)(ldd:ldd),8)
1686 if(nd<0 .or. nd==maxcd)
then
1688 call errwrt(
'+++++++++++++++++++++WARNING+++++++++++++++++++++++')
1690 write ( unit=errstr, fmt=
'(A,I4,A)' )
'BUFRLIB: PKTDD - BAD COUNTER VALUE (=', nd,
') - RETURN WITH IRET = -1'
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'
1696 call errwrt(
'+++++++++++++++++++++WARNING+++++++++++++++++++++++')
1703 call ipkm(
tabd(id,lun)(ldd:ldd),1,nd)
1709 idm = ldd+1 + (nd-1)*2
1710 call ipkm(
tabd(id,lun)(idm:idm+1),2,idn)
1713 end subroutine pktdd
1730 use modv_vars,
only: idxv
1736 integer,
intent(in) :: id, lun, ient
1737 integer,
intent(out) :: iret
1738 integer nxstr, ldxa, ldxb, ldxd, ld30, ldd, ndsc, idsc, iupm
1740 character*128 bort_str
1743 common /dxtab/ nxstr(10), ldxa(10), ldxb(10), ldxd(10), ld30(10), dxstr(10)
1747 ldd = ldxd(idxv+1)+1
1748 ndsc = iupm(
tabd(id,lun)(ldd:ldd),8)
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
1759 idsc = ldd+1 + (ient-1)*2
1760 iret = iupm(
tabd(id,lun)(idsc:idsc+1),16)
1763 end subroutine uptdd
1788 character*8,
intent(inout) :: nem1
1789 character*8,
intent(in) :: nem2
1798 if(nem1(i:i)==
'.')
then
1799 nem1(i:i) = nem2(j:j)
recursive subroutine bort(str)
Log an error message, then either return to or abort the application program.
recursive subroutine bort2(str1, str2)
Log two error messages, then either return to or abort the application program.
recursive integer function iupb(mbay, nbyt, nbit)
Decode an integer value from within a specified number of bits of an integer array,...
recursive integer function iupm(cbay, nbits)
Decode an integer value from within a specified number of bits of a character string,...
subroutine upc(chr, nchr, ibay, ibit, cnvnull)
Decode a character string from within a specified number of bytes of an integer array,...
subroutine pkc(chr, nchr, ibay, ibit)
Encode a character string within a specified number of bytes of an integer array, starting at the bit...
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 ...
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...
subroutine cpbfdx(lud, lun)
Copy all of the DX BUFR table information from one unit to another within internal memory.
subroutine elemdx(card, lun)
Decode the scale factor, reference value, bit width and units (i.e., the "elements") from a Table B m...
subroutine nemtbb(lun, itab, unit, iscl, iref, ibit)
Get information about a Table B descriptor from the internal DX BUFR tables.
subroutine dxmini(mbay, mbyt, mb4, mba, mbb, mbd)
Initialize a DX BUFR tables (dictionary) message, writing all the preliminary information into Sectio...
subroutine nemtba(lun, nemo, mtyp, msbt, inod)
Get information about a Table A descriptor from the internal DX BUFR tables.
subroutine rdusdx(lundx, lun)
Read and parse a file containing a user-supplied DX BUFR table in character format,...
subroutine rsvfvm(nem1, nem2)
Process a "following value" mnemonic.
subroutine seqsdx(card, lun)
Decode the Table D sequence information from a mnemonic definition card that was previously read from...
recursive subroutine wrdxtb(lundx, lunot)
Generate one or more BUFR messages from the DX BUFR tables information associated with a given BUFR f...
subroutine nemtbax(lun, nemo, mtyp, msbt, inod)
Get information about a Table A descriptor from the internal DX BUFR tables.
subroutine nemtbd(lun, itab, nseq, nems, irps, knts)
Get information about a Table D descriptor from the internal DX BUFR tables.
subroutine stntbi(n, lun, numb, nemo, celsq)
Store a new entry within internal BUFR Table B or D.
subroutine pktdd(id, lun, idn, iret)
Store information about a child mnemonic within the internal BUFR Table D.
subroutine stntbia(n, lun, numb, nemo, celsq)
Store a new entry within internal BUFR Table A.
subroutine stbfdx(lun, mesg)
Copy a DX BUFR tables message into the internal memory arrays in module moda_tababd.
subroutine writdx(lunit, lun, lundx)
Write DX BUFR table (dictionary) messages to the beginning of an output BUFR file in lunit.
recursive subroutine nemdefs(lunit, nemo, celem, cunit, iret)
Get the element name and units associated with a Table B descriptor.
integer function igetntbi(lun, ctb)
Get the next available index for storing an entry within a specified internal DX BUFR table.
subroutine readdx(lunit, lun, lundx)
Initialize modules moda_tababd and moda_msgcwd with DX BUFR (dictionary) tables.
subroutine dxinit(lun, ioi)
Clear out the internal arrays (in module moda_tababd) holding the DX BUFR table, then optionally init...
subroutine nenubd(nemo, numb, lun)
Confirm that a mnemonic and FXY value haven't already been defined.
integer function idxmsg(mesg)
Check whether a BUFR message contains DX BUFR tables information that was generated by the NCEPLIBS-b...
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...
subroutine rdbfdx(lunit, lun)
Beginning at the current file pointer location within lunit, read a complete DX BUFR table into inter...
subroutine errwrt(str)
Specify a custom location for the logging of error and diagnostic messages generated by the NCEPLIBS-...
subroutine nemtab(lun, nemo, idn, tab, iret)
Get information about a descriptor, based on a mnemonic.
subroutine numtab(lun, idn, nemo, tab, iret)
Get information about a descriptor, based on the WMO bit-wise representation of an FXY value.
character *(*) function adn30(idn, ldn)
Convert an FXY value from its WMO bit-wise representation to a character string of length 5 or 6.
subroutine makestab
Build the entire internal jump/link table within module moda_tables, using all of the internal BUFR t...
subroutine jstnum(str, sign, iret)
Left-justify a character string containing an encoded integer, by removing all leading blanks and any...
recursive subroutine strnum(str, num, iret)
Decode an integer from a character string.
subroutine capit(str)
Capitalize all of the alphabetic characters in a string.
Wrap C NCEPLIBS-bufr functions so they can be called from within the Fortran part of the library.
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.
subroutine parstr(str, tags, mtag, ntag, sep, limit80)
Parse a string containing one or more substrings into an array of substrings.
subroutine x48(iin4, iout8, nval)
Encode one or more 4-byte integer values as 8-byte integer values.
subroutine x84(iin8, iout4, nval)
Encode one or more 8-byte integer values as 4-byte integer values.