43 recursive subroutine readmg(lunxx,subset,jdate,iret)
47 use modv_vars,
only: im8b, iprt
56 integer,
intent(in) :: lunxx
57 integer,
intent(out) :: jdate, iret
58 integer my_lunxx, lunit, lun, il, im, ier,
idxmsg
60 character*8,
intent(out) :: subset
68 call x84(lunxx,my_lunxx,1)
69 call readmg(my_lunxx,subset,jdate,iret)
70 call x48(jdate,jdate,1)
82 subset(1:8) = csubset(1:8)
92 call status(lunit,lun,il,im)
93 if(il==0)
call bort(
'BUFRLIB: READMG - INPUT BUFR FILE IS CLOSED, IT MUST BE OPEN FOR INPUT')
94 if(il>0)
call bort(
'BUFRLIB: READMG - INPUT BUFR FILE IS OPEN FOR OUTPUT, IT MUST BE OPEN FOR INPUT')
95 call wtstat(lunit,lun,il,1)
103 call wtstat(lunit,lun,il,0)
114 call cktaba(lun,subset,jdate,iret)
120 if(
isc3(lun)/=0)
return
127 call errwrt(
'++++++++++++++BUFR ARCHIVE LIBRARY+++++++++++++++++')
128 errstr =
'BUFRLIB: READMG - INTERNAL DICTIONARY MESSAGE READ; ACCOUNT FOR IT THEN READ IN NEXT MESSAGE WITHOUT RETURNING'
130 call errwrt(
'++++++++++++++BUFR ARCHIVE LIBRARY+++++++++++++++++')
152 recursive integer function ireadmg(lunit,subset,idate)
result(iret)
154 use modv_vars,
only: im8b
158 integer,
intent(in) :: lunit
159 integer,
intent(out) :: idate
162 character*8,
intent(out) :: subset
168 call x84(lunit,my_lunit,1)
169 iret=
ireadmg(my_lunit,subset,idate)
170 call x48(idate,idate,1)
175 call readmg(lunit,subset,idate,iret)
223 recursive subroutine readerme(mesg,lunit,subset,jdate,iret)
225 use modv_vars,
only: mxmsgl, im8b, nbytw, iprt, bmostr
233 integer,
intent(in) :: lunit, mesg(*)
234 integer,
intent(out) :: jdate, iret
237 character*8,
intent(out) :: subset
239 character*128 errstr, bort_str
243 equivalence(sec0,iec0)
250 call x84(lunit,my_lunit,1)
251 call readerme(mesg,my_lunit,subset,jdate,iret)
252 call x48(jdate,jdate,1)
253 call x48(iret,iret,1)
263 call status(lunit,lun,il,im)
264 if(il==0)
call bort(
'BUFRLIB: READERME - INPUT BUFR FILE IS CLOSED, IT MUST BE OPEN FOR INPUT')
265 if(il>0)
call bort(
'BUFRLIB: READERME - INPUT BUFR FILE IS OPEN FOR OUTPUT, IT MUST BE OPEN FOR INPUT')
266 call wtstat(lunit,lun,il, 1)
273 if(lnmsg*nbytw>mxmsgl)
then
274 write(bort_str,
'("BUFRLIB: READERME - INPUT BUFR MESSAGE LENGTH",1X,I6," BYTES) IS LARGER THAN '// &
275 'LIMIT OF ",I6," BYTES")') lnmsg*nbytw, mxmsgl
279 mbay(ii,lun) = mesg(ii)
284 if(sec0(1:4)/=bmostr) &
285 call bort(
'BUFRLIB: READERME - FIRST 4 BYTES READ FROM RECORD NOT "BUFR", DOES NOT CONTAIN BUFR DATA')
290 call cktaba(lun,subset,jdate,iret)
291 if(
isc3(lun)/=0)
return
305 if(
idrdm(lun)>0)
then
309 if(
idrdm(lun)==0)
then
316 else if(
idrdm(lun)>0)
then
323 if ( iprt >= 2 )
then
324 call errwrt(
'+++++++++++++++++++++++++++++++++++++++++++++++++')
325 write ( unit=errstr, fmt=
'(A,I3,A)' ) &
326 'BUFRLIB: READERME - STORED NEW DX TABLE CONSISTING OF (',
idrdm(lun),
') MESSAGES;'
328 errstr =
'WILL APPLY THIS TABLE TO ALL SUBSEQUENT DATA MESSAGES UNTIL NEXT DX TABLE IS PASSED IN'
330 call errwrt(
'+++++++++++++++++++++++++++++++++++++++++++++++++')
353 use modv_vars,
only: mxmsgld4
357 integer,
intent(in) :: lunit
358 integer,
intent(out) :: mesg(*), iret
361 call status(lunit,lun,il,im)
365 if(iret==-3)
call errwrt(
'BUFRLIB: RDMSGW - SKIPPING OVERLARGE MESSAGE')
366 if(iret==-2)
call errwrt(
'BUFRLIB: RDMSGW - SKIPPING CORRUPTED MESSAGE')
401 recursive subroutine openmb(lunit,subset,jdate)
403 use modv_vars,
only: im8b
409 integer,
intent(in) :: lunit, jdate
410 integer my_lunit, my_jdate, lun, il, im, mtyp, mstb, inod,
i4dy
412 character*(*),
intent(in) :: subset
421 call x84(lunit,my_lunit,1)
422 call x84(jdate,my_jdate,1)
423 call openmb(my_lunit,subset,my_jdate)
431 call status(lunit,lun,il,im)
432 if(il==0)
call bort(
'BUFRLIB: OPENMB - OUTPUT BUFR FILE IS CLOSED, IT MUST BE OPEN FOR OUTPUT')
433 if(il<0)
call bort(
'BUFRLIB: OPENMB - OUTPUT BUFR FILE IS OPEN FOR INPUT, IT MUST BE OPEN FOR OUTPUT')
437 call nemtba(lun,subset,mtyp,mstb,inod)
444 call wtstat(lunit,lun,il, 1)
473 recursive subroutine openmg(lunit,subset,jdate)
475 use modv_vars,
only: im8b
481 integer,
intent(in) :: lunit, jdate
482 integer my_lunit, my_jdate, lun, il, im, mtyp, mstb, inod,
i4dy
484 character*(*),
intent(in) :: subset
491 call x84(lunit,my_lunit,1)
492 call x84(jdate,my_jdate,1)
493 call openmg(my_lunit,subset,my_jdate)
501 call status(lunit,lun,il,im)
502 if(il==0)
call bort(
'BUFRLIB: OPENMG - OUTPUT BUFR FILE IS CLOSED, IT MUST BE OPEN FOR OUTPUT')
503 if(il<0)
call bort(
'BUFRLIB: OPENMG - OUTPUT BUFR FILE IS OPEN FOR INPUT, IT MUST BE OPEN FOR OUTPUT')
504 if(im/=0)
call closmg(lunit)
505 call wtstat(lunit,lun,il, 1)
509 call nemtba(lun,subset,mtyp,mstb,inod)
539 use modv_vars,
only: im8b
547 integer,
intent(in) :: lunin
548 integer my_lunin, lunit, lun, il, im
555 call x84(lunin,my_lunin,1)
565 call status(lunit,lun,il,im)
566 if(lunit/=lunin)
msglim(lun) = 0
567 if(il==0)
call bort(
'BUFRLIB: CLOSMG - OUTPUT BUFR FILE IS CLOSED, IT MUST BE OPEN FOR OUTPUT')
568 if(il<0)
call bort(
'BUFRLIB: CLOSMG - OUTPUT BUFR FILE IS OPEN FOR INPUT, IT MUST BE OPEN FOR OUTPUT')
574 else if(
nsub(lun)<0)
then
578 call wtstat(lunit,lun,il,0)
606 use modv_vars,
only: mxmsgld4, iprt, nby5, bmostr, bmcstr
618 integer,
intent(in) :: lunit, mgbyt, mesg(*)
619 integer iec0(2), mbyt, ibit, kbit, ii, jj, len0, len1, len2, len3, len4, l5, iad4, iad5, lun, il, im, npbyt, mwrd, &
620 nmwrd, iupbs01, idxmsg
633 call pkb(mbyt,24,iec0,ibit)
635 do ii = 1, nmwrd(iec0)
644 if(
cmnem(jj)==
'BEN')
then
651 mbyt = iupbs01(
mgwb,
'LENM')
653 do ii = 1, nmwrd(
mgwb)
667 if ( (
csmf==
'Y' ) .and. ( idxmsg(
mgwa)/=1 ) )
then
673 call pkc(bmcstr,nby5,
mgwa,ibit)
676 mbyt = iupbs01(
mgwb,
'LENM')
678 do ii = 1, nmwrd(
mgwb)
686 if ( (
ctrt==
'Y' ) .and. ( idxmsg(
mgwa)/=1 ) )
then
692 mbyt = iupbs01(
mgwb,
'LENM')
694 do ii = 1, nmwrd(
mgwb)
706 if(iupbs01(
mgwa,
'BEN')<4)
then
707 if(mod(len1,2)/=0)
call bort (
'BUFRLIB: MSGWRT - LENGTH OF SECTION 1 IS NOT A MULTIPLE OF 2')
708 if(mod(len2,2)/=0)
call bort (
'BUFRLIB: MSGWRT - LENGTH OF SECTION 2 IS NOT A MULTIPLE OF 2')
709 if(mod(len3,2)/=0)
call bort (
'BUFRLIB: MSGWRT - LENGTH OF SECTION 3 IS NOT A MULTIPLE OF 2')
710 if(mod(len4,2)/=0)
then
712 iad4 = len0+len1+len2+len3
730 call pkc(bmcstr,nby5,
mgwa,kbit)
741 call status(lunit,lun,il,im)
742 if(
null(lun)==0)
then
748 call errwrt(
'++++++++++++++BUFR ARCHIVE LIBRARY+++++++++++++++++')
749 write ( unit=errstr, fmt=
'(A,I4,A,I7)')
'BUFRLIB: MSGWRT: LUNIT =', lunit,
', BYTES =', mbyt+npbyt
751 call errwrt(
'++++++++++++++BUFR ARCHIVE LIBRARY+++++++++++++++++')
757 if(idxmsg(
mgwa)/=1)
then
778 use modv_vars,
only: mtv, nby0, nby1, nby2, nby3, nby5, bmostr, bmcstr, fxy_fbit, fxy_sbyct, fxy_drf8
787 integer,
intent(in) :: lun
788 integer nby4, nbyt, mtyp, msbt, inod, isub, iret, mcen, mear, mmon, mday, mour, mmin, mbit, ifxy
790 character*128 bort_str
797 call nemtba(lun,subtag,mtyp,msbt,inod)
798 if(
inode(lun)/=inod)
then
799 write(bort_str,
'("BUFRLIB: MSGINI - MISMATCH BETWEEN INODE (=",I7,") & POSITIONAL INDEX, INOD (",I7,") '// &
800 'OF SUBTAG (",A,") IN DICTIONARY")')
inode(lun), inod, subtag
803 call nemtab(lun,subtag,isub,tab,iret)
805 write(bort_str,
'("BUFRLIB: MSGINI - TABLE A MESSAGE TYPE MNEMONIC ",A," NOT FOUND IN INTERNAL TABLE D ARRAYS")') subtag
811 mcen = mod(
idate(lun)/10**8,100)+1
812 mear = mod(
idate(lun)/10**6,100)
813 mmon = mod(
idate(lun)/10**4,100)
814 mday = mod(
idate(lun)/10**2,100)
815 mour = mod(
idate(lun) ,100)
818 if(mcen==1)
call bort (
'BUFRLIB: MSGINI - BUFR MESSAGE DATE (IDATE) is 0000000000')
820 if(mear==0) mcen = mcen-1
821 if(mear==0) mear = 100
827 nbyt = nby0+nby1+nby2+nby3+nby4+nby5
831 call pkc(bmostr, 4 ,
mbay(1,lun),mbit)
832 call pkb(nbyt , 24 ,
mbay(1,lun),mbit)
833 call pkb( 3 , 8 ,
mbay(1,lun),mbit)
837 call pkb(nby1 , 24 ,
mbay(1,lun),mbit)
838 call pkb( 0 , 8 ,
mbay(1,lun),mbit)
839 call pkb( 3 , 8 ,
mbay(1,lun),mbit)
840 call pkb( 7 , 8 ,
mbay(1,lun),mbit)
841 call pkb( 0 , 8 ,
mbay(1,lun),mbit)
842 call pkb( 0 , 8 ,
mbay(1,lun),mbit)
843 call pkb(mtyp , 8 ,
mbay(1,lun),mbit)
844 call pkb(msbt , 8 ,
mbay(1,lun),mbit)
845 call pkb( mtv , 8 ,
mbay(1,lun),mbit)
846 call pkb( 0 , 8 ,
mbay(1,lun),mbit)
847 call pkb(mear , 8 ,
mbay(1,lun),mbit)
848 call pkb(mmon , 8 ,
mbay(1,lun),mbit)
849 call pkb(mday , 8 ,
mbay(1,lun),mbit)
850 call pkb(mour , 8 ,
mbay(1,lun),mbit)
851 call pkb(mmin , 8 ,
mbay(1,lun),mbit)
852 call pkb(mcen , 8 ,
mbay(1,lun),mbit)
856 call pkb(nby3 , 24 ,
mbay(1,lun),mbit)
857 call pkb( 0 , 8 ,
mbay(1,lun),mbit)
858 call pkb( 0 , 16 ,
mbay(1,lun),mbit)
859 call pkb(2**7 , 8 ,
mbay(1,lun),mbit)
860 call pkb(ifxy(fxy_sbyct), 16,
mbay(1,lun),mbit)
861 call pkb(isub , 16 ,
mbay(1,lun),mbit)
862 call pkb(ifxy(
'102000') , 16,
mbay(1,lun),mbit)
863 call pkb(ifxy(fxy_drf8) , 16,
mbay(1,lun),mbit)
864 call pkb(ifxy(
'206001') , 16,
mbay(1,lun),mbit)
865 call pkb(ifxy(fxy_fbit), 16,
mbay(1,lun),mbit)
866 call pkb( 0 , 8 ,
mbay(1,lun),mbit)
870 call pkb(nby4 , 24 ,
mbay(1,lun),mbit)
871 call pkb( 0 , 8 ,
mbay(1,lun),mbit)
875 call pkc(bmcstr,nby5,
mbay(1,lun),mbit)
879 if(mod(mbit,8)/=0)
call bort(
'BUFRLIB: MSGINI - INITIALIZED MESSAGE DOES NOT END ON A BYTE BOUNDARY')
880 if(mbit/8/=nbyt)
then
881 write(bort_str,
'("BUFRLIB: MSGINI - NUMBER OF BYTES STORED FOR INITIALIZED MESSAGE (",I6,") IS NOT THE SAME AS FIRST '// &
882 'CALCULATED, NBYT (",I6)') mbit/8, nbyt
905 logical function msgfull(msiz,itoadd,mxsiz)
result(bool)
907 use modv_vars,
only: maxnc
914 integer,
intent(in) :: msiz, itoadd, mxsiz
929 if(
ctrt==
'Y') iwgbyt = iwgbyt + 6
932 if(
csmf==
'Y') iwgbyt = iwgbyt + (maxnc*2)
936 if ( ( msiz + itoadd + iwgbyt ) > mxsiz )
then
964 use modv_vars,
only: mxmsgl, im8b, iprt
970 integer,
intent(in) :: maxo
971 integer my_maxo, newsiz, nxstr, ldxa, ldxb, ldxd, ld30
976 common /dxtab/ nxstr(10), ldxa(10), ldxb(10), ldxd(10), ld30(10), dxstr(10)
983 call x84(maxo,my_maxo,1)
990 if((maxo==0).or.(maxo>mxmsgl))
then
998 call errwrt(
'++++++++++++++BUFR ARCHIVE LIBRARY+++++++++++++++++')
999 write ( unit=errstr, fmt=
'(A,A,I7,A,I7)' )
'BUFRLIB: MAXOUT - THE RECORD LENGTH OF ALL BUFR MESSAGES ',&
1000 'CREATED FROM THIS POINT ON IS BEING CHANGED FROM ',
maxbyt,
' TO ', newsiz
1002 call errwrt(
'++++++++++++++BUFR ARCHIVE LIBRARY+++++++++++++++++')
1043 use modv_vars,
only: nbytw
1047 integer,
intent(in) :: lmesg
1048 integer,
intent(inout) :: mesg(*)
1049 integer,
intent(out) :: npbyt
1050 integer nmw, nmb, ibit, i, nmwrd, iupbs01
1056 if(nmw>lmesg)
call bort(
'BUFRLIB: PADMSG - CANNOT ADD PADDING TO MESSAGE ARRAY; TRY A LARGER DIMENSION FOR THIS ARRAY')
1060 nmb = iupbs01(mesg,
'LENM')
1062 npbyt = ( nmw * nbytw ) - nmb
1064 call pkb(0,8,mesg,ibit)
1080 recursive integer function nmsub(lunit)
result(iret)
1082 use modv_vars,
only: im8b
1088 integer,
intent(in) :: lunit
1089 integer my_lunit, lun, il, im
1096 call x84(lunit,my_lunit,1)
1097 iret=
nmsub(my_lunit)
1107 call status(lunit,lun,il,im)
1108 if(il==0)
call bort(
'BUFRLIB: NMSUB - INPUT BUFR FILE IS CLOSED, IT MUST BE OPEN FOR INPUT')
1109 if(il>0)
call bort(
'BUFRLIB: NMSUB - INPUT BUFR FILE IS OPEN FOR OUTPUT, IT MUST BE OPEN FOR INPUT')
1110 if(im==0)
call bort(
'BUFRLIB: NMSUB - A MESSAGE MUST BE OPEN IN INPUT BUFR FILE, NONE ARE')
1130 integer function nmwrd(mbay)
result(iret)
1132 use modv_vars,
only: nbytw
1136 integer,
intent(in) :: mbay(*)
1143 iret = ((lenm/8)+1)*(8/nbytw)
1162 integer function lmsg(sec0)
result(iret)
1166 integer msec0(2),
nmwrd
1168 character*8,
intent(in) :: sec0
1171 equivalence(msec0,csec0)
1198 recursive subroutine getlens (mbay,ll,len0,len1,len2,len3,len4,len5)
1200 use modv_vars,
only: im8b, nby5
1204 integer,
intent(in) :: mbay(*), ll
1205 integer,
intent(out) :: len0, len1, len2, len3, len4, len5
1211 call x84(ll,my_ll,1)
1212 call getlens(mbay,my_ll,len0,len1,len2,len3,len4,len5)
1213 call x48(len0,len0,1)
1214 call x48(len1,len1,1)
1215 call x48(len2,len2,1)
1216 call x48(len3,len3,1)
1217 call x48(len4,len4,1)
1218 call x48(len5,len5,1)
1238 len2 =
iupb(mbay,iad2+1,24) *
iupbs01(mbay,
'ISC2')
1242 len3 =
iupb(mbay,iad3+1,24)
1246 len4 =
iupb(mbay,iad4+1,24)
1278 recursive subroutine cnved4(msgin,lmsgot,msgot)
1280 use modv_vars,
only: im8b, nbytw
1284 integer,
intent(in) :: msgin(*), lmsgot
1285 integer,
intent(out) :: msgot(*)
1286 integer my_lmsgot, i, nmw, len0, len1, len2, len3, l4, l5, iad2, iad4, lenm, lenmot, len1ot, len3ot, ibit,
iupbs01,
nmwrd
1292 call x84 ( lmsgot, my_lmsgot, 1 )
1293 call cnved4 ( msgin, my_lmsgot*2, msgot )
1298 if(
iupbs01(msgin,
'BEN')==4)
then
1304 call bort(
'BUFRLIB: CNVED4 - OVERFLOW OF OUTPUT (EDITION 4) MESSAGE ARRAY; TRY A LARGER DIMENSION FOR THIS ARRAY')
1313 call getlens(msgin,3,len0,len1,len2,len3,l4,l5)
1316 iad4 = iad2 + len2 + len3
1324 if(lenmot>(lmsgot*nbytw)) &
1325 call bort(
'BUFRLIB: CNVED4 - OVERFLOW OF OUTPUT (EDITION 4) MESSAGE ARRAY; TRY A LARGER DIMENSION FOR THIS ARRAY')
1332 call mvb ( msgin, 1, msgot, 1, 4 )
1334 call pkb ( lenmot, 24, msgot, ibit )
1335 call pkb ( 4, 8, msgot, ibit )
1339 call pkb ( len1ot, 24, msgot, ibit )
1340 call pkb (
iupbs01(msgin,
'BMT'), 8, msgot, ibit )
1341 call pkb (
iupbs01(msgin,
'OGCE'), 16, msgot, ibit )
1342 call pkb (
iupbs01(msgin,
'GSES'), 16, msgot, ibit )
1343 call pkb (
iupbs01(msgin,
'USN'), 8, msgot, ibit )
1344 call pkb (
iupbs01(msgin,
'ISC2')*128, 8, msgot, ibit )
1345 call pkb (
iupbs01(msgin,
'MTYP'), 8, msgot, ibit )
1347 call pkb ( 255, 8, msgot, ibit )
1348 call pkb (
iupbs01(msgin,
'MSBT'), 8, msgot, ibit )
1349 call pkb (
iupbs01(msgin,
'MTV'), 8, msgot, ibit )
1350 call pkb (
iupbs01(msgin,
'MTVL'), 8, msgot, ibit )
1351 call pkb (
iupbs01(msgin,
'YEAR'), 16, msgot, ibit )
1352 call pkb (
iupbs01(msgin,
'MNTH'), 8, msgot, ibit )
1353 call pkb (
iupbs01(msgin,
'DAYS'), 8, msgot, ibit )
1354 call pkb (
iupbs01(msgin,
'HOUR'), 8, msgot, ibit )
1355 call pkb (
iupbs01(msgin,
'MINU'), 8, msgot, ibit )
1357 call pkb ( 0, 8, msgot, ibit )
1361 call mvb ( msgin, iad2+1, msgot, (ibit/8)+1, len2+len3-1 )
1365 ibit = ( len0 + len1ot + len2 ) * 8
1366 call pkb ( len3ot, 24, msgot, ibit )
1370 ibit = ibit + ( len3ot * 8 ) - 24
1371 call mvb ( msgin, iad4+1, msgot, (ibit/8)+1, lenm-iad4 )
1387 recursive integer function ifbget(lunit)
result(iret)
1389 use modv_vars,
only: im8b
1395 integer,
intent(in) :: lunit
1396 integer my_lunit, lun, il, im
1402 call x84(lunit,my_lunit,1)
1412 call status(lunit,lun,il,im)
1413 if(il==0)
call bort(
'BUFRLIB: IFBGET - INPUT BUFR FILE IS CLOSED, IT MUST BE OPEN FOR INPUT')
1414 if(il>0)
call bort(
'BUFRLIB: IFBGET - INPUT BUFR FILE IS OPEN FOR OUTPUT, IT MUST BE OPEN FOR INPUT')
1415 if(im==0)
call bort(
'BUFRLIB: IFBGET - A MESSAGE MUST BE OPEN IN INPUT BUFR FILE, NONE ARE')
subroutine blocks(mbay, mwrd)
Encapsulate a BUFR message with IEEE Fortran control words as specified via the most recent call to s...
recursive subroutine bort(str)
Log an error message, 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,...
subroutine pkc(chr, nchr, ibay, ibit)
Encode a character string within a specified number of bytes of an integer array, starting at the bit...
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 wrcmps(lunix)
Write a compressed BUFR data subset.
subroutine mvb(ib1, nb1, ib2, nb2, nbm)
Copy a specified number of bytes from one packed binary array to another.
subroutine nemtba(lun, nemo, mtyp, msbt, inod)
Get information about a Table A descriptor from the internal DX BUFR tables.
subroutine stbfdx(lun, mesg)
Copy a DX BUFR tables message into the internal memory arrays in module moda_tababd.
subroutine dxinit(lun, ioi)
Clear out the internal arrays (in module moda_tababd) holding the DX BUFR table, then optionally init...
integer function idxmsg(mesg)
Check whether a BUFR message contains DX BUFR tables information that was generated by the NCEPLIBS-b...
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 makestab
Build the entire internal jump/link table within module moda_tables, using all of the internal BUFR t...
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, dimension(:,:), allocatable mbay
Current BUFR message for each file ID.
integer, dimension(:), allocatable mbyt
Length (in bytes) of current BUFR message for each file ID.
integer maxbyt
Maximum length of an output BUFR message.
Declare variables used to optionally catch and return any future bort error string to the application...
integer caught_str_len
Length of bort error string.
logical bort_target_is_unset
.true.
Declare arrays used to store, for each output file ID, a copy of the BUFR message that was most recen...
integer, dimension(:), allocatable msglen
Length (in integers) of BUFR message most recently written to each output file ID.
integer, dimension(:,:), allocatable msgtxt
BUFR message most recently written to each output file ID.
Declare an array used by subroutine readerme() to read in a new DX dictionary table as a consecutive ...
integer, dimension(:), allocatable idrdm
DX BUFR tables message count for each file ID.
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 an array used by various subroutines and functions to hold a temporary working copy of a BUFR...
integer, dimension(:), allocatable mgwb
Temporary working copy of BUFR message.
Declare arrays used to store information about the current BUFR message that is in the process of bei...
integer, dimension(:), allocatable inode
Table A mnemonic for type of BUFR message.
integer, dimension(:), allocatable idate
Section 1 date-time of 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.
Declare an array used to keep track of which logical units should not have any empty (zero data subse...
integer, dimension(:), allocatable msglim
Tracking index for each file ID.
Declare a variable used to indicate whether output BUFR messages should be standardized.
character csmf
Flag indicating whether BUFR output messages are to be standardized; this variable is initialized to ...
Declare an array used to store a switch for each file ID, indicating whether any BUFR messages should...
integer, dimension(:), allocatable null
Output switch for each file ID:
Declare arrays and variables used to store custom values for certain mnemonics within Sections 0 and ...
integer, dimension(:), allocatable ivmnem
Custom values for use within Sections 0 and 1 of all future output BUFR messages written to all Fortr...
integer ns01v
Number of custom values stored.
character *8, dimension(:), allocatable cmnem
Section 0 and 1 mnemonics corresponding to ivmnem.
Declare an array used to store a switch for each file ID, indicating whether BUFR messages read from ...
integer, dimension(:), allocatable isc3
Section 3 switch for each file ID:
Declare arrays and variables used to store the internal jump/link table.
character *10, dimension(:), allocatable tag
Mnemonics in the jump/link table.
Declare variables used to store tank receipt time information within Section 1 of BUFR messages.
character ctrt
Flag indicating whether tank receipt times are to be included within output BUFR messages; this varia...
Declare an array used to store, for each file ID, the logical unit number corresponding to a separate...
integer, dimension(:), allocatable luncpy
Logical unit numbers used to copy long character strings between BUFR data subsets.
recursive subroutine status(lunit, lun, il, im)
Check whether a specified Fortran logical unit number is currently connected to the NCEPLIBS-bufr sof...
subroutine wtstat(lunit, lun, il, im)
Update file status in library internals.
subroutine padmsg(mesg, lmesg, npbyt)
Pad a BUFR message with zeroed-out bytes from the end of the message up to the next 8-byte boundary.
recursive subroutine maxout(maxo)
Specify the maximum length of a BUFR message that can be written to any output file by the NCEPLIBS-b...
integer function lmsg(sec0)
Given a character string containing Section 0 from a BUFR message, determine the array size (in integ...
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 openmg(lunit, subset, jdate)
Open and initialize a new BUFR message within internal arrays, for eventual output to logical unit lu...
recursive subroutine openmb(lunit, subset, jdate)
Open and initialize a new BUFR message within internal arrays, for eventual output to logical unit lu...
recursive subroutine closmg(lunin)
Close the BUFR message that is currently open for writing within internal arrays associated with logi...
recursive integer function nmsub(lunit)
Get the total number of data subsets available within the BUFR message that was most recently opened ...
integer function nmwrd(mbay)
Given an integer array containing Section 0 from a BUFR message, determine the array size (in integer...
integer function igetmxby()
Get the maximum length of a BUFR message that can be written to an output file by the NCEPLIBS-bufr s...
recursive subroutine readerme(mesg, lunit, subset, jdate, iret)
Read a BUFR message from a memory array.
recursive subroutine readmg(lunxx, subset, jdate, iret)
Read the next BUFR message from logical unit abs(lunxx) into internal arrays.
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.
recursive integer function ifbget(lunit)
Check whether there are any more data subsets available to be read from a BUFR message.
subroutine rdmsgw(lunit, mesg, iret)
Read the next BUFR message from logical unit lunit as an array of integer words.
recursive subroutine cnved4(msgin, lmsgot, msgot)
Convert a BUFR edition 3 message to BUFR edition 4.
recursive integer function ireadmg(lunit, subset, idate)
Call subroutine readmg() and pass back its return code as the function value.
subroutine msgini(lun)
Initialize, within the internal arrays, a new uncompressed BUFR message for output.
subroutine msgwrt(lunit, mesg, mgbyt)
Perform final checks and updates on a BUFR message before writing it to a specified Fortran logical u...
subroutine usrtpl(lun, invn, nbmp)
Expand a subset template within internal arrays.
subroutine cktaba(lun, subset, jdate, iret)
Get the Table A mnemonic from Sections 1 and 3 of a BUFR message.
recursive integer function iupbs01(mbay, s01mnem)
Read a specified value from within Section 0 or Section 1 of a BUFR message.
recursive subroutine pkbs1(ival, mbay, s1mnem)
Write a specified value into a specified location within Section 1 of a BUFR message,...
recursive integer function iupbs3(mbay, s3mnem)
Read a specified value from within Section 3 of a BUFR message.
subroutine reads3(lun)
Read the Section 3 descriptors from the BUFR message in mbay(1,lun), then use the BUFR master tables ...
recursive integer function i4dy(idate)
Convert a date-time with a 2-digit year (YYMMDDHH) to a date-time with a 4-digit year (YYYYMMDDHH) us...
recursive subroutine stndrd(lunit, msgin, lmsgot, msgot)
Standardize a BUFR message.
recursive subroutine atrcpt(msgin, lmsgot, msgot)
Read an input message and output an equivalent BUFR message with a tank receipt time added to Section...
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.