31 recursive subroutine readsb(lunit,iret)
35 use modv_vars,
only: im8b
46 integer,
intent(in) :: lunit
47 integer,
intent(out) :: iret
48 integer my_lunit, lun, il, im, ier, nbyt
54 call x84(lunit,my_lunit,1)
75 call status(lunit,lun,il,im)
76 if(il==0)
call bort(
'BUFRLIB: READSB - INPUT BUFR FILE IS CLOSED, IT MUST BE OPEN FOR INPUT')
77 if(il>0)
call bort(
'BUFRLIB: READSB - INPUT BUFR FILE IS OPEN FOR OUTPUT, IT MUST BE OPEN FOR INPUT')
99 elseif(
msgunp(lun)==1)
then
127 recursive integer function ireadsb(lunit)
result(iret)
129 use modv_vars,
only: im8b
133 integer,
intent(in) :: lunit
140 call x84(lunit,my_lunit,1)
176 recursive subroutine readns(lunit,subset,jdate,iret)
180 use modv_vars,
only: im8b, lendat
188 integer,
intent(in) :: lunit
189 integer,
intent(out) :: jdate, iret
190 integer my_lunit, lun, il, im
192 character*8,
intent(out) :: subset
199 call x84(lunit,my_lunit,1)
200 call readns(my_lunit,subset,jdate,iret)
201 call x48(jdate,jdate,1)
202 call x48(iret,iret,1)
213 subset(1:8) = csubset(1:8)
220 call status(lunit,lun,il,im)
221 if(il==0)
call bort(
'BUFRLIB: READNS - INPUT BUFR FILE IS CLOSED, IT MUST BE OPEN FOR INPUT')
222 if(il>0)
call bort(
'BUFRLIB: READNS - INPUT BUFR FILE IS OPEN FOR OUTPUT, IT MUST BE OPEN FOR INPUT')
223 if(
inode(lun)==0)
then
229 if (lendat/=10) jdate = mod(jdate,10**8)
236 call readmg(lunit,subset,jdate,iret)
261 recursive integer function ireadns(lunit,subset,idate)
result(iret)
263 use modv_vars,
only: im8b
267 integer,
intent(in) :: lunit
268 integer,
intent(out) :: idate
271 character*8,
intent(out) :: subset
277 call x84(lunit,my_lunit,1)
278 iret=
ireadns(my_lunit,subset,idate)
279 call x48(idate,idate,1)
284 call readns(lunit,subset,idate,iret)
325 use modv_vars,
only: im8b
331 integer,
intent(in) :: lunit
332 integer my_lunit, lun, il, im
339 call x84 ( lunit, my_lunit, 1 )
348 call status(lunit,lun,il,im)
349 if(il==0)
call bort(
'BUFRLIB: WRITSB - OUTPUT BUFR FILE IS CLOSED, IT MUST BE OPEN FOR OUTPUT')
350 if(il<0)
call bort(
'BUFRLIB: WRITSB - OUTPUT BUFR FILE IS OPEN FOR INPUT, IT MUST BE OPEN FOR OUTPUT')
351 if(im==0)
call bort(
'BUFRLIB: WRITSB - A MESSAGE MUST BE OPEN IN OUTPUT BUFR FILE, NONE ARE')
443 recursive subroutine writsa(lunxx,lmsgt,msgt,msgl)
445 use modv_vars,
only: im8b
452 integer,
intent(in) :: lunxx, lmsgt
453 integer,
intent(out) :: msgt(*), msgl
454 integer my_lunxx, my_lmsgt, lunit, lun, il, im, n
461 call x84 ( lunxx, my_lunxx, 1 )
462 call x84 ( lmsgt, my_lmsgt, 1 )
463 call writsa ( my_lunxx, my_lmsgt*2, msgt, msgl )
465 call x48 ( msgl, msgl, 1 )
475 call status(lunit,lun,il,im)
476 if(il==0)
call bort(
'BUFRLIB: WRITSA - OUTPUT BUFR FILE IS CLOSED, IT MUST BE OPEN FOR OUTPUT')
477 if(il<0)
call bort(
'BUFRLIB: WRITSA - OUTPUT BUFR FILE IS OPEN FOR INPUT, IT MUST BE OPEN FOR OUTPUT')
478 if(im==0)
call bort(
'BUFRLIB: WRITSA - A MESSAGE MUST BE OPEN IN OUTPUT BUFR FILE, NONE ARE')
482 if(lunxx<0)
call closmg(lunit)
487 if(
msglen(lun)>lmsgt)
call bort(
'BUFRLIB: WRITSA - OVERFLOW OF OUTPUT BUFR MESSAGE ARRAY; TRY A LARGER '// &
488 'DIMENSION FOR THIS ARRAY')
518 if( (
msglen(lun)>0) .and. (msgl+
msglen(lun)<=lmsgt) )
then
520 msgt(msgl+n) =
msgtxt(n,lun)
556 recursive subroutine rdmgsb(lunit,imsg,isub)
558 use modv_vars,
only: im8b
565 integer,
intent(in) :: lunit, imsg, isub
566 integer my_lunit, my_imsg, my_isub, lun, il, im, i, jdate, iret
568 character*128 bort_str
576 call x84(lunit,my_lunit,1)
577 call x84(imsg,my_imsg,1)
578 call x84(isub,my_isub,1)
579 call rdmgsb(my_lunit,my_imsg,my_isub)
587 call openbf(lunit,
'IN',lunit)
588 call status(lunit,lun,il,im)
594 call readmg(lunit,subset,jdate,iret)
596 write(bort_str,
'("BUFRLIB: RDMGSB - HIT END OF FILE BEFORE READING REQUESTED MESSAGE NO.",I5," IN '//&
597 'BUFR FILE CONNECTED TO UNIT",I4)') imsg,lunit
607 write(bort_str,
'("BUFRLIB: RDMGSB - ALL SUBSETS READ BEFORE READING REQ. SUBSET NO.",I3," IN '// &
608 'REQ. MSG NO.",I5," IN BUFR FILE CONNECTED TO UNIT",I4)') isub,imsg,lunit
635 use modv_vars,
only: iprt, nby0, nby1, nby2, nby3
643 integer,
intent(in) :: lunit, lun
644 integer ibyt, lbyt, lbit, nbyt, ii, iupb
656 if(msgfull(
mbyt(lun),ibyt,
maxbyt) .or. ((ibyt>65530).and.(
nsub(lun)>0)))
then
671 call errwrt(
'+++++++++++++++++++++WARNING+++++++++++++++++++++++')
672 write ( unit=errstr, fmt=
'(A,A,I7,A)')
'BUFRLIB: MSGUPD - SUBSET LONGER THAN ANY POSSIBLE MESSAGE ', &
673 '{MAXIMUM MESSAGE LENGTH = ',
maxbyt,
'}'
675 call errwrt(
'>>>>>>>OVERLARGE SUBSET DISCARDED FROM FILE<<<<<<<<')
676 call errwrt(
'+++++++++++++++++++++WARNING+++++++++++++++++++++++')
699 lbit = (nby0+nby1+nby2+4)*8
702 lbyt = nby0+nby1+nby2+nby3
703 nbyt = iupb(
mbay(1,lun),lbyt+1,24)
705 call pkb(nbyt+ibyt,24,
mbay(1,lun),lbit)
722 call errwrt(
'+++++++++++++++++++++WARNING+++++++++++++++++++++++')
723 write ( unit=errstr, fmt=
'(A,I7,A,A)')
'BUFRLIB: MSGUPD - SUBSET HAS BYTE COUNT = ',ibyt,
' > UPPER LIMIT OF 65535'
725 call errwrt(
'>>>>>>>WILL BE WRITTEN INTO ITS OWN MESSAGE<<<<<<<<')
726 call errwrt(
'+++++++++++++++++++++WARNING+++++++++++++++++++++++')
769 subroutine pad(ibay,ibit,ibyt,ipadb)
773 integer,
intent(inout) :: ibay(*), ibit
774 integer,
intent(in) :: ipadb
775 integer,
intent(out) :: ibyt
778 character*128 bort_str
782 ipad = ipadb - mod(ibit+8,ipadb)
784 call pkb(ipad,8,ibay,ibit)
786 call pkb(0,ipad,ibay,ibit)
789 if(mod(ibit,8)/=0)
then
790 write(bort_str,
'("BUFRLIB: PAD - THE NUMBER OF BITS IN A PACKED'// &
791 ' SUBSET AFTER PADDING (",I8,") IS NOT A MULTIPLE OF 8")') ibit
823 recursive integer function lcmgdf(lunit,subset)
result(iret)
825 use modv_vars,
only: im8b
831 integer,
intent(in) :: lunit
832 integer my_lunit, lun, il, im, mtyp, msbt, inod, nte, i
834 character*8,
intent(in) :: subset
841 call x84(lunit,my_lunit,1)
842 iret=
lcmgdf(my_lunit,subset)
852 call status(lunit,lun,il,im)
853 if (il==0)
call bort(
'BUFRLIB: LCMGDF - INPUT BUFR FILE IS CLOSED, IT MUST BE OPEN')
857 call nemtba(lun,subset,mtyp,msbt,inod)
864 if ( (
typ(inod+i)==
'CHR') .and. (
ibt(inod+i)>64) )
then
899 recursive subroutine ufbpos(lunit,irec,isub,subset,jdate)
903 use modv_vars,
only: im8b
910 integer,
intent(in) :: lunit, irec, isub
911 integer,
intent(out) :: jdate
912 integer my_lunit, my_irec, my_isub, lun, il, im, jrec, jsub, iret
914 character*128 bort_str
915 character*8,
intent(out) :: subset
921 call x84(lunit,my_lunit,1)
922 call x84(irec,my_irec,1)
923 call x84(isub,my_isub,1)
924 call ufbpos(my_lunit,my_irec,my_isub,subset,jdate)
925 call x48(jdate,jdate,1)
932 call status(lunit,lun,il,im)
933 if(il==0)
call bort(
'BUFRLIB: UFBPOS - INPUT BUFR FILE IS CLOSED, IT MUST BE OPEN FOR INPUT')
934 if(il>0)
call bort(
'BUFRLIB: UFBPOS - INPUT BUFR FILE IS OPEN FOR OUTPUT, IT MUST BE OPEN FOR INPUT')
937 write(bort_str,
'("BUFRLIB: UFBPOS - REQUESTED MESSAGE NUMBER TO READ IN (",I5,") IS NOT VALID")') irec
941 write(bort_str,
'("BUFRLIB: UFBPOS - REQUESTED SUBSET NUMBER TO READ IN (",I5,") IS NOT VALID")') isub
947 call ufbcnt(lunit,jrec,jsub)
951 if(irec<jrec .or. (irec==jrec.and.isub<jsub))
then
955 call ufbcnt(lunit,jrec,jsub)
961 call readmg(lunit,subset,jdate,iret)
963 write(bort_str,
'("BUFRLIB: UFBPOS - REQUESTED MESSAGE NUMBER '// &
964 'TO READ IN (",I5,") EXCEEDS THE NUMBER OF MESSAGES IN THE FILE (",I5,")")') irec, jrec
967 call ufbcnt(lunit,jrec,jsub)
973 write(bort_str,
'("BUFRLIB: UFBPOS - REQ. SUBSET NUMBER TO READ'// &
974 ' IN (",I5,") EXCEEDS THE NUMBER OF SUBSETS (",I5,") IN THE REQ. MESSAGE (",I5,")")') isub, jsub, irec
977 call ufbcnt(lunit,jrec,jsub)
996 use modv_vars,
only: bmiss
1006 integer,
intent(in) :: lun
1007 integer,
intent(out) :: iret
1008 integer ier, n, node, kbit, nbt, icbfms, igetrfel
1014 equivalence(cval,rval)
1033 if(
itp(node)==1)
then
1036 elseif(
itp(node)==2)
then
1038 nrfelm(n,lun) = igetrfel(n,lun)
1039 if (
ival(n)<2_8**
ibt(node)-1)
then
1044 elseif(
itp(node)==3)
then
1050 nbt = min(8,
nbit(n)/8)
1051 call upc(cval,nbt,
mbay(1,lun),kbit,.true.)
1052 if (
nbit(n)<=64 .and. icbfms(cval,nbt)/=0)
then
1083 integer,
intent(in) :: lun
1085 integer n, node, nbit, ncr, numchr, jj, ibfms, igetrfel, imrkopr
1092 equivalence(cval,rval)
1098 nrfelm(n,lun) = igetrfel(n,lun)
1099 if(
itp(node)==1)
then
1101 elseif(
typ(node)==
'NUM')
then
1102 if( (ibfms(
val(n,lun))==1) .or. (
val(n,lun)/=
val(n,lun)) )
then
1106 ival(n) = ipks(
val(n,lun),node)
1118 if(
itp(node)<3)
then
1120 if ( imrkopr(
tag(node)) == 1 )
then
1129 if ( ncr>8 .and.
luncpy(lun)/=0 )
then
1136 if(ibfms(rval)/=0)
then
1138 numchr = min(ncr,len(lstr))
1140 call ipkm(lstr(jj:jj),1,255)
1174 use modv_vars,
only: maxjl, maxss, maxrcr, iprt
1185 character*128 bort_str
1187 integer,
intent(in) :: lun
1188 integer,
intent(out) :: iret
1189 integer nbmp(2,maxrcr), newn(2,maxrcr), knx(maxrcr), nodi, node, mbmp, nr, i, j, n, nn, n1, n2, new, ivob, igetrfel
1206 outer:
do while (.true.)
1212 write(bort_str,
'("BUFRLIB: RCSTPL - THE NUMBER OF RECURSION LEVELS EXCEEDS THE LIMIT (",I3,")")') maxrcr
1221 write(bort_str,
'("BUFRLIB: RCSTPL - UNSET EXPANSION SEGMENT ",A)')
tag(nodi)
1224 if(n2-n1+1>maxjl)
then
1226 call errwrt(
'++++++++++++++BUFR ARCHIVE LIBRARY+++++++++++++++++')
1227 call errwrt(
'BUFRLIB: RCSTPL - MAXJL OVERFLOW; SUBSET SKIPPED')
1228 call errwrt(
'++++++++++++++BUFR ARCHIVE LIBRARY+++++++++++++++++')
1234 newn(2,nr) = n2-n1+1
1246 do i=nbmp(1,nr),nbmp(2,nr)
1247 if(knx(nr)==0) knx(nr) =
nval(lun)
1248 if(i>nbmp(1,nr)) newn(1,nr) = 1
1249 do j=newn(1,nr),newn(2,nr)
1250 if(
nval(lun)+1>maxss)
then
1252 call errwrt(
'++++++++++++++BUFR ARCHIVE LIBRARY+++++++++++++++++')
1253 call errwrt(
'BUFRLIB: RCSTPL - MAXSS OVERFLOW; SUBSET SKIPPED')
1254 call errwrt(
'++++++++++++++BUFR ARCHIVE LIBRARY+++++++++++++++++')
1275 if(
itp(node)==1)
then
1282 new =
nval(lun)-knx(nr)
1283 val(knx(nr)+1,lun) =
val(knx(nr)+1,lun) + new
1289 if(nr-1 == 0)
exit outer
1310 use modv_vars,
only: maxjl, maxss, iprt
1320 integer,
intent(in) :: lun, invn, nbmp
1321 integer i, j, ival, jval, n, n1, n2, nodi, node, newn, invr, knvn
1323 character*128 bort_str, errstr
1325 logical drp, drs, drb, drx
1328 call errwrt(
'++++++++++++++BUFR ARCHIVE LIBRARY+++++++++++++++++')
1329 write ( unit=errstr, fmt=
'(A,I3,A,I7,A,I5,A,A10)' ) &
1330 'BUFRLIB: USRTPL - LUN:INVN:NBMP:TAG(INODE(LUN)) = ', lun,
':', invn,
':', nbmp,
':',
tag(
inode(lun))
1332 call errwrt(
'++++++++++++++BUFR ARCHIVE LIBRARY+++++++++++++++++')
1338 call errwrt(
'+++++++++++++++++++++WARNING+++++++++++++++++++++++')
1339 call errwrt(.LE.
'BUFRLIB: USRTPL - NBMP 0 - IMMEDIATE RETURN')
1340 call errwrt(
'+++++++++++++++++++++WARNING+++++++++++++++++++++++')
1358 write(bort_str,
'("BUFRLIB: USRTPL - THIRD ARGUMENT (INPUT) = ",'// &
1359 'I4,", MUST BE 1 WHEN SECOND ARGUMENT (INPUT) IS 1 (SUBSET NODE) (",A,")")') nbmp,
tag(nodi)
1362 elseif(invn>0 .and. invn<=
nval(lun))
then
1364 nodi =
inv(invn,lun)
1365 drp =
typ(nodi) ==
'DRP'
1366 drs =
typ(nodi) ==
'DRS'
1367 drb =
typ(nodi) ==
'DRB'
1368 drx = drp .or. drs .or. drb
1369 ival = nint(
val(invn,lun))
1370 jval = 2**
ibt(nodi)-1
1371 val(invn,lun) = ival+nbmp
1372 if(drb.and.nbmp/=1)
then
1373 write(bort_str,
'("BUFRLIB: USRTPL - THIRD ARGUMENT (INPUT) = ",'// &
1374 'I4,", MUST BE 1 WHEN NODE IS DRB (1-BIT DELAYED REPL. FACTOR) (",A,")")') nbmp,
tag(nodi)
1378 write(bort_str,
'("BUFRLIB: USRTPL - NODE IS OF TYPE ",A," - IT '// &
1379 'MUST BE EITHER A SUBSET OR DELAYED REPL. FACTOR (",A,")")')
typ(nodi),
tag(nodi)
1383 write(bort_str,
'("BUFRLIB: USRTPL - REPLICATION FACTOR IS NEGATIVE (=",I5,") (",A,")")') ival,
tag(nodi)
1386 if(ival+nbmp>jval)
then
1387 write(bort_str,
'("BUFRLIB: USRTPL - REPLICATION FACTOR OVERFLOW (EXCEEDS MAXIMUM OF",I6," (",A,")")') jval,
tag(nodi)
1393 write(bort_str,
'("BUFRLIB: USRTPL - INVENTORY INDEX {FIRST '// &
1394 'ARGUMENT (INPUT)} OUT OF BOUNDS (=",I5,", RANGE IS 1 TO",I6,") ")') invn,
nval(lun)
1405 write(bort_str,
'("BUFRLIB: USRTPL - UNSET EXPANSION SEGMENT (",A,")")')
tag(nodi)
1408 if(n2-n1+1>maxjl)
then
1409 write(bort_str,
'("BUFRLIB: USRTPL - TEMPLATE ARRAY OVERFLOW, EXCEEDS THE LIMIT (",I6,") (",A,")")') maxjl,
tag(nodi)
1421 if(
nval(lun)+newn*nbmp>maxss)
then
1422 write(bort_str,
'("BUFRLIB: USRTPL - INVENTORY OVERFLOW (",I6,"), EXCEEDS THE LIMIT (",I6,") (",A,")")') &
1423 nval(lun)+newn*nbmp, maxss,
tag(nodi)
1427 do j=
nval(lun),invn+1,-1
1428 inv(j+newn*nbmp,lun) =
inv(j,lun)
1429 val(j+newn*nbmp,lun) =
val(j,lun)
1432 if(drp.or.drs)
vtmp(1) = newn
1448 call errwrt(
'++++++++++++++BUFR ARCHIVE LIBRARY+++++++++++++++++')
1449 write ( unit=errstr, fmt=
'(A,A,A10,2(A,I5),A,I7)' )
'BUFRLIB: USRTPL - TAG(INV(INVN,LUN)):NEWN:NBMP:', &
1450 'NVAL(LUN) = ',
tag(
inv(invn,lun)),
':', newn,
':', nbmp,
':',
nval(lun)
1453 write ( unit=errstr, fmt=
'(2(A,I5),A,A10)' )
'For I = ', i,
', ITMP(I) = ',
itmp(i),
', TAG(ITMP(I)) = ',
tag(
itmp(i))
1456 call errwrt(
'++++++++++++++BUFR ARCHIVE LIBRARY+++++++++++++++++')
1463 outer:
do while (.true.)
1466 if(
itp(node)==0)
then
1468 if(
inv(invr,lun)==node)
then
1469 val(invr,lun) =
val(invr,lun)+newn*nbmp
1473 write(bort_str,
'("BUFRLIB: USRTPL - BAD BACKUP STRATEGY (",A,")")')
tag(nodi)
1499 use modv_vars,
only: im8b
1507 integer,
intent(in) :: lubfi, lubfj
1508 integer my_lubfi, my_lubfj, luni, il, im, lunj, jl, jm, is, js, node, nodj, ityp, iwrds, jwrds, &
1511 character*128 bort_str
1513 logical herei, herej, missi, missj, samei
1519 call x84(lubfi,my_lubfi,1)
1520 call x84(lubfj,my_lubfj,1)
1521 call invmrg(my_lubfi,my_lubfj)
1531 call status(lubfi,luni,il,im)
1532 call status(lubfj,lunj,jl,jm)
1536 do while(is<=
nval(luni))
1541 write(bort_str,
'("BUFRLIB: INVMRG - NODE FROM INPUT BUFR FILE '// &
1542 '(",I7,") DOES NOT EQUAL NODE FROM OUTPUT BUFR FILE (",I7,"), TABULAR MISMATCH")') node, nodj
1549 if(
typ(node)==
'DRB')
then
1554 iwrds =
nwords(is,luni)+ioff
1555 jwrds =
nwords(js,lunj)+ioff
1556 if(iwrds>ioff .and. jwrds==ioff)
then
1557 do n=
nval(lunj),js+1,-1
1558 inv(n+iwrds-jwrds,lunj) =
inv(n,lunj)
1559 val(n+iwrds-jwrds,lunj) =
val(n,lunj)
1562 inv(js+n,lunj) =
inv(is+n,luni)
1563 val(js+n,lunj) =
val(is+n,luni)
1565 nval(lunj) =
nval(lunj)+iwrds-jwrds
1571 elseif((ityp==2).or.(ityp==3))
then
1575 missi = .not.(herei)
1576 missj = .not.(herej)
1577 samei =
val(is,luni)==
val(js,lunj)
1578 if(herei.and.missj)
then
1579 val(js,lunj) =
val(is,luni)
1581 elseif(herei.and.herej.and..not.samei)
then
1610 integer,
intent(in) :: n, lun
1615 do k=1,nint(
val(n,lun))
1616 iret = iret + nint(
val(iret+n+1,lun))
subroutine strbtm(n, lun, ival)
Store internal information in module moda_bitmaps if the input element is part of a bitmap.
recursive subroutine bort(str)
Log an error message, then either return to or abort the application program.
subroutine upb(nval, nbits, ibay, ibit)
Decode an integer value from within a specified number of bits of an integer array,...
subroutine upbb(nval, nbits, ibit, ibay)
Decode an integer value from within a specified number of bits of an integer array,...
subroutine upb8(nval, nbits, ibit, ibay)
Decode an 8-byte integer value from within a specified number of bits of an integer array,...
real *8 function ups(ival, node)
Unpack a real*8 value from an integer by applying the proper scale and reference values.
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 pkb8(nval, nbits, ibay, ibit)
Encode an 8-byte integer value within a specified number of bits of an integer array,...
subroutine rdcmps(lun)
Read the next compressed BUFR data subset into internal arrays.
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 errwrt(str)
Specify a custom location for the logging of error and diagnostic messages generated by the NCEPLIBS-...
integer function ibfms(r8val)
Check whether a real*8 data value returned from a previous call to any of the NCEPLIBS-bufr values-re...
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 ibay
Current data subset.
integer ibit
Bit pointer within ibay.
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 arrays and variables used to store bitmaps internally within a data subset definition.
integer lstnod
Most recent jump/link table entry that was processed by function igetrfel() and whose corresponding v...
integer nbtm
Number of stored bitmaps for the current data subset (up to a maximum of mxbtm).
integer lstnodct
Current count of consecutive occurrences of lstnod.
logical linbtm
true if a bitmap is in the process of being read for the current data subset; false otherwise.
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 arrays and variables needed to store long character strings (greater than 8 bytes) via subrou...
integer nh4wlc
Number of long character strings being stored.
character *14, dimension(:), allocatable sth4wlc
Table B mnemonics associated with long character strings.
integer, dimension(:), allocatable luh4wlc
File ID for associated output file.
character *120, dimension(:), allocatable chh4wlc
Long character strings.
Declare an array used to pack or unpack all of the values of a BUFR data subset.
integer *8, dimension(:), allocatable ival
BUFR data subset values.
Declare arrays which provide working space in several subprograms (usrtpl() and ufbcup()) which manip...
real *8, dimension(:), allocatable vtmp
val array elements for new sections of a growing subset buffer.
integer, dimension(:), allocatable itmp
inv array elements for new sections of a growing subset buffer.
Declare variables for use when merging parts of different data subsets.
integer nmrg
Number of merges.
integer ntot
Total number of calls to subroutine invmrg().
integer namb
Number of potential merges that weren't made because of ambiguities.
integer nrpl
Number of expansions of Table D mnemonics using short (1-bit) delayed replication.
Declare a variable used to indicate whether output BUFR messages should be compressed.
character ccmf
Flag indicating whether BUFR output messages are to be compressed; this variable is initialized to a ...
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 store a status code for each file ID if an error or other abnormal result oc...
integer, dimension(:), allocatable iscodes
Abnormal status codes.
Declare arrays and variables used to store the internal jump/link table.
integer, dimension(:), allocatable jseq
Temporary storage used in expanding sequences.
integer, dimension(:,:), allocatable iseq
Temporary storage used in expanding sequences.
integer, dimension(:), allocatable isc
Scale factors corresponding to tag and typ:
integer, dimension(:), allocatable ibt
Bit widths corresponding to tag and typ:
real *8, dimension(:), allocatable vali
Initialized data values corresponding to typ:
character *3, dimension(:), allocatable typ
Type indicators corresponding to tag:
integer, dimension(:), allocatable jmpb
Jump backward indices corresponding to tag and typ:
character *10, dimension(:), allocatable tag
Mnemonics in the jump/link table.
integer, dimension(:), allocatable itp
Integer type values corresponding to typ:
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.
Declare an array used to store, for each file ID from which a BUFR message is currently being read as...
integer, dimension(:), allocatable msgunp
Flag indicating how to unpack data subsets from BUFR message:
Declare arrays for internal storage of pointers to BUFR data subset values.
integer, dimension(:), allocatable nbit
Length (in bits) of each packed data value in data subset.
integer, dimension(:), allocatable mbit
Pointer in data subset to first bit of each packed data value.
Declare arrays used to store data values and associated metadata for the current BUFR data subset in ...
integer, dimension(:), allocatable nval
Number of data values in BUFR data subset.
real *8, dimension(:,:), allocatable, target val
Data values.
integer, dimension(:,:), allocatable, target inv
Inventory pointer which links each data value to its corresponding node in the internal jump/link tab...
integer, dimension(:,:), allocatable nrfelm
Referenced data value, for data values which refer to a previous data value in the BUFR data subset v...
Declare arrays used in subroutine rcstpl() to store subset segments that are being copied from a subs...
integer, dimension(:,:), allocatable iutmp
inv array elements for new sections of a growing subset buffer.
real *8, dimension(:,:), allocatable vutmp
val array elements for new sections of a growing subset buffer.
recursive subroutine openbf(lunit, io, lundx)
Connect a new file to the NCEPLIBS-bufr software for input or output operations, or initialize the li...
recursive subroutine ufbcnt(lunit, kmsg, ksub)
Get the current location of the file pointer within a BUFR file, in terms of a message number countin...
recursive subroutine status(lunit, lun, il, im)
Check whether a specified Fortran logical unit number is currently connected to the NCEPLIBS-bufr sof...
recursive subroutine closmg(lunin)
Close the BUFR message that is currently open for writing within internal arrays associated with logi...
recursive subroutine readmg(lunxx, subset, jdate, iret)
Read the next BUFR message from logical unit abs(lunxx) into internal arrays.
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...
recursive subroutine ufbpos(lunit, irec, isub, subset, jdate)
Jump forwards or backwards to a specified data subset within a BUFR file.
subroutine pad(ibay, ibit, ibyt, ipadb)
Pad a BUFR data subset with zeroed-out bits up to the next byte boundary.
subroutine rdtree(lun, iret)
Read the next uncompressed BUFR data subset into internal arrays.
subroutine wrtree(lun)
Pack a BUFR data subset.
subroutine msgupd(lunit, lun)
Write an uncompressed BUFR data subset.
subroutine usrtpl(lun, invn, nbmp)
Expand a subset template within internal arrays.
recursive subroutine writsa(lunxx, lmsgt, msgt, msgl)
Write a complete data subset into a BUFR message, and return each completed message within a memory a...
recursive integer function ireadns(lunit, subset, idate)
Call subroutine readns() and pass back its return code as the function value.
integer function nwords(n, lun)
Compute the length of a specified delayed replication sequence within a data subset.
recursive subroutine writsb(lunit)
Write a complete data subset into a BUFR message, for eventual output to logical unit lunit.
recursive subroutine invmrg(lubfi, lubfj)
Merge parts of data subsets which have duplicate space and time coordinates but different or unique o...
recursive integer function ireadsb(lunit)
Call subroutine readsb() and pass back its return code as the function value.
recursive subroutine readsb(lunit, iret)
Read the next data subset from a BUFR message.
subroutine rcstpl(lun, iret)
Initialize a subset template within internal arrays.
recursive integer function lcmgdf(lunit, subset)
Check whether the subset definition for a given message type contains any long character strings (gre...
recursive subroutine rdmgsb(lunit, imsg, isub)
Read a specified data subset from a BUFR file.
recursive subroutine readns(lunit, subset, jdate, iret)
Read the next data subset from a BUFR file.
recursive subroutine readlc(lunit, chr, str)
Read a long character string (greater than 8 bytes) from a data subset.
recursive subroutine writlc(lunit, chr, str)
Write a long character string (greater than 8 bytes) to a data subset.
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.