15 recursive subroutine fortran_open(filename, lunit, format, position, iret)
17 use modv_vars,
only: im8b
20 character*(*),
intent(in) :: filename, format, position
21 integer,
intent(in) :: lunit
22 integer,
intent(out) :: iret
30 call x84(lunit,my_lunit,1)
31 call fortran_open(filename,my_lunit,
format,position,iret)
38 open(lunit, file=trim(filename), form=trim(format), position=trim(position), iostat=iret)
50 use modv_vars,
only: im8b
53 integer,
intent(in) :: lunit
54 integer,
intent(out) :: iret
62 call x84(lunit,my_lunit,1)
70 close(lunit, iostat=iret)
167 recursive subroutine openbf(lunit,io,lundx)
171 use modv_vars,
only: im8b, ifopbf, nfiles, iprt
183 integer,
intent(in) :: lunit, lundx
184 integer my_lunit, my_lundx, iprtprv, lun, il, im, lcio
186 character*(*),
intent(in) :: io
187 character*255 filename, fileacc
188 character*128 bort_str, errstr
189 character*28 cprint(0:4)
194 ' (limited -default) ', &
195 ' (all warnings) ', &
196 ' (all warnings+infos) ', &
197 ' (all warnings+infos+debugs)'/
203 call x84(lunit,my_lunit,1)
204 call x84(lundx,my_lundx,1)
205 call openbf(my_lunit,io,my_lundx)
225 if(iprt<-1) iprt = -1
228 call errwrt(
'++++++++++++++BUFR ARCHIVE LIBRARY+++++++++++++++++')
229 write ( unit=errstr, fmt=
'(A,I3,A,A,I3,A)' )
'BUFRLIB: OPENBF - DEGREE OF MESSAGE PRINT INDICATOR CHNGED FROM', &
230 iprtprv,cprint(iprtprv+1),
' TO',iprt,cprint(iprt+1)
232 call errwrt(
'++++++++++++++BUFR ARCHIVE LIBRARY+++++++++++++++++')
250 if( (io==
'FIRST') .or. (io==
'QUIET') )
return
254 call status(lunit,lun,il,im)
256 write(bort_str,
'("BUFRLIB: OPENBF - THERE ARE ALREADY",I3," BUFR FILES OPENED, CANNOT OPEN FILE CONNECTED TO UNIT",I4)') &
261 write(bort_str,
'("BUFRLIB: OPENBF - THE FILE CONNECTED TO UNIT",I5," IS ALREADY OPEN")') lunit
271 if (io/=
'NUL' .and. io/=
'INUL')
then
272 inquire(lunit,access=fileacc)
273 if(fileacc==
'UNDEFINED')
open(lunit)
274 inquire(lunit,name=filename)
275 filename=trim(filename)//char(0)
288 call wtstat(lunit,lun,-1,0)
289 call readdx(lunit,lun,lundx)
290 else if(io==
'INUL')
then
291 call wtstat(lunit,lun,-1,0)
292 if(lunit/=lundx)
call readdx(lunit,lun,lundx)
294 else if(io==
'NUL')
then
295 call wtstat(lunit,lun,1,0)
296 if(lunit/=lundx)
call readdx(lunit,lun,lundx)
298 else if(io==
'INX')
then
300 call wtstat(lunit,lun,-1,0)
302 else if(io==
'OUX')
then
304 call wtstat(lunit,lun,1,0)
305 else if(io==
'SEC3')
then
307 call wtstat(lunit,lun,-1,0)
309 else if(io==
'OUT')
then
311 call wtstat(lunit,lun,1,0)
312 call writdx(lunit,lun,lundx)
313 else if(io==
'NODX')
then
315 call wtstat(lunit,lun,1,0)
316 call readdx(lunit,lun,lundx)
317 else if(io==
'APN' .or. io==
'APX')
then
319 call wtstat(lunit,lun,1,0)
320 if(lunit/=lundx)
call readdx(lunit,lun,lundx)
323 call bort(
'BUFRLIB: OPENBF - ILLEGAL SECOND (INPUT) ARGUMENT')
345 use modv_vars,
only: im8b
354 integer,
intent(in) :: lunit
355 integer my_lunit, lun, il, im
361 call x84(lunit,my_lunit,1)
377 if ( .not.
allocated(
null) )
then
378 call errwrt(
'++++++++++++++++++++WARNING++++++++++++++++++++++')
379 errstr =
'BUFRLIB: CLOSBF WAS CALLED WITHOUT HAVING PREVIOUSLY CALLED OPENBF'
381 call errwrt(
'++++++++++++++++++++WARNING++++++++++++++++++++++')
385 call status(lunit,lun,il,im)
386 if(il>0 .and. im/=0)
call closmg(lunit)
388 call wtstat(lunit,lun,0,0)
392 if(
null(lun)==0)
close(lunit)
418 recursive subroutine status(lunit,lun,il,im)
420 use modv_vars,
only: im8b, nfiles
426 integer,
intent(in) :: lunit
427 integer,
intent(out) :: lun, il, im
430 character*128 bort_str, errstr
437 call x84(lunit,my_lunit,1)
438 call status(my_lunit,lun,il,im)
447 if(lunit<=0 .or. lunit>99)
then
448 write(bort_str,
'("BUFRLIB: STATUS - INPUT UNIT NUMBER (",I3,") OUTSIDE LEGAL RANGE OF 1-99")') lunit
460 if ( .not.
allocated(
iolun) )
then
461 call errwrt(
'++++++++++++++++++++WARNING++++++++++++++++++++++')
462 errstr =
'BUFRLIB: STATUS WAS CALLED WITHOUT HAVING PREVIOUSLY CALLED OPENBF'
464 call errwrt(
'++++++++++++++++++++WARNING++++++++++++++++++++++')
469 if(abs(
iolun(i))==lunit) lun = i
488 il = sign(1,
iolun(lun))
527 integer,
intent(in) :: lunit, lun, il, im
529 character*128 bort_str
534 write(bort_str,
'("BUFRLIB: WTSTAT - INVALID UNIT NUMBER PASSED INTO FIRST ARGUMENT (INPUT) (=",I3,")")') lunit
538 write(bort_str,
'("BUFRLIB: WTSTAT - INVALID FILE ID PASSED INTO SECOND ARGUMENT (INPUT) (=",I3,")")') lun
541 if(il<-1 .or. il>1)
then
542 write(bort_str,
'("BUFRLIB: WTSTAT - INVALID LOGICAL UNIT STATUS INDICATOR PASSED INTO THIRD ARGUMENT '// &
543 '(INPUT) (=",I4,")")') il
546 if(im< 0 .or. im>1)
then
547 write(bort_str,
'("BUFRLIB: WTSTAT - INVALID BUFR MESSAGE STATUS INDICATOR PASSED INTO FOURTH ARGUMENT '// &
548 '(INPUT) (=",I4,")")') im
554 if(abs(
iolun(lun))/=lunit .and. (
iolun(lun)/=0))
then
555 write(bort_str,
'("BUFRLIB: WTSTAT - ATTEMPTING TO REDEFINE EXISTING FILE UNIT (LOGICAL UNIT '// &
556 'NUMBER ",I3,")")')
iolun(lun)
563 iolun(lun) = sign(lunit,il)
598 recursive subroutine ufbcnt(lunit,kmsg,ksub)
600 use modv_vars,
only: im8b
606 integer,
intent(in) :: lunit
607 integer,
intent(out) :: kmsg, ksub
608 integer my_lunit, lun, il, im
614 call x84(lunit,my_lunit,1)
615 call ufbcnt(my_lunit,kmsg,ksub)
616 call x48(kmsg,kmsg,1)
617 call x48(ksub,ksub,1)
624 call status(lunit,lun,il,im)
625 if(il==0)
call bort(
'BUFRLIB: UFBCNT - BUFR FILE IS CLOSED, IT MUST BE OPEN FOR EITHER INPUT OR OUTPUT')
651 integer,
intent(in) :: lunxx
652 integer lunit, lun, il, im, ier, idxmsg
656 call status(lunit,lun,il,im)
657 if(il==0)
call bort(
'BUFRLIB: POSAPX - INPUT BUFR FILE IS CLOSED, IT MUST BE OPEN FOR OUTPUT')
658 if(il<0)
call bort(
'BUFRLIB: POSAPX - INPUT BUFR FILE IS OPEN FOR INPUT, IT MUST BE OPEN FOR OUTPUT')
665 if(idxmsg(
mgwa)==1)
then
716 integer,
intent(in) :: lunit, isr
717 integer lun, il, im, i, kdate, ier
719 character*128 bort_str
724 call status(lunit,lun,il,im)
726 write(bort_str,
'("BUFRLIB: REWNBF - ATTEMPING TO SAVE '// &
727 'PARAMETERS FOR FILE FOR WHICH THEY HAVE ALREADY BEEN SAVED (AND NOT YET RESTORED) (UNIT",I3,")")') lunit
731 write(bort_str,
'("BUFRLIB: REWNBF - ATTEMPING TO SAVE '// &
732 'PARAMETERS FOR BUFR FILE WHICH IS NOT OPENED FOR EITHER INPUT OR OUTPUT) (UNIT",I3,")")') lunit
737 write(bort_str,
'("BUFRLIB: REWNBF - ATTEMPING TO RESTORE '// &
738 'PARAMETERS TO BUFR FILE WHICH WERE NEVER SAVED (UNIT",I3,")")') lunit
742 write(bort_str,
'("BUFRLIB: REWNBF - ATTEMPING TO RESTORE '// &
743 'PARAMETERS TO BUFR FILE WHICH WERE NEVER SAVED (UNIT",I3,")")') lunit
748 write(bort_str,
'("BUFRLIB: REWNBF - SAVE/RESTORE SWITCH (INPUT '// &
749 'ARGUMENT ISR) IS NOT ZERO OR ONE (HERE =",I4,") (UNIT",I3,")")') isr, lunit
769 call wtstat(lunit,lun,-1,0)
785 call readmg(lunit,subset,kdate,ier)
787 write(bort_str,
'("BUFRLIB: REWNBF - HIT END OF FILE BEFORE '// &
788 'REPOSITIONING BUFR FILE IN UNIT",I3," TO ORIGINAL MESSAGE NO.",I5)') lunit,
jmsg
811 call wtstat(lunit,lun,il,im)
815 jsr(lun) = mod(
jsr(lun)+1,2)
888 recursive subroutine ufbtab(lunin,tab,i1,i2,iret,str)
890 use modv_vars,
only: part, im8b, bmiss, iac, iprt
900 integer*8 ival, lref, ninc, mps, lps
901 integer,
intent(in) :: lunin, i1, i2
902 integer,
intent(inout) :: iret
903 integer,
parameter :: maxtg = 100
904 integer nnod, ncon, nods, nodc, ivls, kons, my_lunin, my_i1, my_i2, lunit, lun, il, im, irec, isub, i, n, ntg, &
905 jdate, jbit, kbit, lbit, mbit, nbit, nibit, nbyt, nsb, node, nbmp, nrep, lret, linc, iac_prev, ityp, &
908 character*(*),
intent(in) :: str
911 character*10 tgs(maxtg)
912 character*8 subset, cval
914 logical :: openit, overflow, just_count, need_node, need_newmsg
916 real*8,
intent(out) :: tab(i1,i2)
919 common /usrstr/ nnod, ncon, nods(20), nodc(10), ivls(10), kons(10)
923 equivalence(cval,rval)
926 mps(node) = 2_8**(
ibt(node))-1
927 lps(lbit) = max(2_8**(lbit)-1,1)
932 call x84(lunin,my_lunin,1)
935 call ufbtab(my_lunin,tab,my_i1,my_i2,iret,str)
936 call x48(iret,iret,1)
946 tab(1:i1,1:i2) = bmiss
952 just_count = lunin<lunit
953 if (.not. just_count)
then
955 call parstr(str,tgs,maxtg,ntg,
' ',.true.)
957 if(tgs(i)==
'IREC') irec = i
958 if(tgs(i)==
'ISUB') isub = i
964 if(part.and.iret<0)
then
967 need_newmsg = .false.
973 call status(lunit,lun,il,im)
977 call openbf(lunit,
'INX',lunit)
986 do while(
ireadmg(-lunit,subset,jdate)>=0)
987 iret = iret+
nmsub(lunit)
992 outer:
do while (.not. just_count)
996 if(
ireadmg(-lunit,subset,jdate)<0)
exit
998 if(irec>0) nods(irec) = 0
999 if(isub>0) nods(isub) = 0
1007 inner1:
do while (.true.)
1009 if(
nsub(lun)==
msub(lun)) cycle outer
1021 nods(i) = abs(nods(i))
1024 mbit =
mbyt(lun)*8 + 16
1031 inner2:
do while (.true.)
1033 if(n+1<=
nval(lun))
then
1038 if(
itp(node)==1)
then
1039 call upb8(ival,nbit,mbit,
mbay(1,lun))
1044 if(nods(i)==node)
then
1045 if(
itp(node)==1)
then
1046 call upb8(ival,nbit,mbit,
mbay(1,lun))
1048 elseif(
itp(node)==2)
then
1049 call upb8(ival,nbit,mbit,
mbay(1,lun))
1050 if(ival<mps(node)) tab(i,iret) =
ups(ival,node)
1051 elseif(
itp(node)==3)
then
1054 call upc(cval,nbit/8,
mbay(1,lun),kbit,.true.)
1062 if(nods(i)>0) cycle inner2
1076 if(irec>0) tab(irec,iret) =
nmsg(lun)
1077 if(isub>0) tab(isub,iret) =
nsub(lun)
1083 if(iret+
msub(lun)>i2)
then
1092 if(irec>0.or.isub>0)
then
1094 if(irec>0) tab(irec,iret+nsb) =
nmsg(lun)
1095 if(isub>0) tab(isub,iret+nsb) = nsb
1101 inner3:
do while ( n <
nval(lun) )
1110 nods(i) = abs(nods(i))
1121 if(.not. need_node)
exit inner3
1123 if(ityp==1 .or. ityp==2)
then
1127 elseif(ityp==3)
then
1138 call up8(ninc,linc,
mbay(1,lun),jbit)
1140 call usrtpl(lun,n,int(ival))
1144 if(node==nods(i))
then
1148 if(ityp==1 .or. ityp==2)
then
1150 jbit =
ibit + linc*(nsb-1)
1151 call up8(ninc,linc,
mbay(1,lun),jbit)
1154 if(ninc<lps(linc)) tab(i,lret) =
ups(ival,node)
1156 elseif(ityp==3)
then
1161 jbit =
ibit + linc*(nsb-1)*8
1163 call upc(cval,linc,
mbay(1,lun),jbit,.true.)
1169 call bort(
'UFBTAB - INVALID ELEMENT TYPE SPECIFIED')
1175 iret = iret+
msub(lun)
1186 do while(
ireadmg(-lunit,subset,jdate)>=0)
1187 nrep = nrep+
nmsub(lunit)
1190 call errwrt(
'+++++++++++++++++++++WARNING+++++++++++++++++++++++')
1191 write ( unit=errstr, fmt=
'(A,A,I8,A)' )
'BUFRLIB: UFBTAB - THE NO. OF DATA SUBSETS IN THE BUFR FILE ', &
1192 .GT.
'IS LIMIT OF ', i2,
' IN THE 4TH ARG. (INPUT) - INCOMPLETE READ'
1194 write ( unit=errstr, fmt=
'(A,I8,A,I8,A)' )
'>>>UFBTAB STORED ', iret,
' REPORTS OUT OF ', nrep,
'<<<'
1196 call errwrt(
'+++++++++++++++++++++WARNING+++++++++++++++++++++++')
1241 use modv_vars,
only: part
1245 logical,
intent(in) :: xpart
subroutine arallocf
Dynamically allocate Fortran language arrays.
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 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 up8(nval, nbits, ibay, ibit)
Decode an 8-byte integer value from within a specified number of bits of an integer array,...
subroutine upc(chr, nchr, ibay, ibit, cnvnull)
Decode a character string from within a specified number of bytes of an integer array,...
subroutine writdx(lunit, lun, lundx)
Write DX BUFR table (dictionary) messages to the beginning of an output BUFR file in lunit.
subroutine readdx(lunit, lun, lundx)
Initialize modules moda_tababd and moda_msgcwd with DX BUFR (dictionary) tables.
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 strsuc(str1, str2, lens)
Remove leading and trailing blanks from a character string.
subroutine bfrini
Initialize numerous global variables and arrays within internal modules and common blocks throughout ...
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 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.
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 and variables needed to store the current position within a BUFR file.
integer jill
File status indicator of BUFR file.
integer jimm
Message status indicator of BUFR file.
integer, dimension(:), allocatable jsr
Indicator of stack status when entering subroutine rewnbf().
integer jmsg
Sequential number of BUFR message, counting from the beginning of the file.
integer jbit
Bit pointer within BUFR message.
integer jsub
Sequential number of BUFR data subset, counting from the beginning of the current BUFR message.
integer junn
File ID of BUFR file.
integer jbyt
Length (in bytes) of BUFR message.
integer, dimension(:), allocatable jbay
BUFR message.
Declare an array used by subroutine makestab() to keep track of which logical units share DX BUFR tab...
integer, dimension(:), allocatable lus
Tracking index 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 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 switch for each file ID, indicating whether any BUFR messages should...
integer, dimension(:), allocatable null
Output switch for each file ID:
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 used to store file and message status indicators for all logical units that have been ...
integer, dimension(:), allocatable iolun
File status indicators.
integer, dimension(:), allocatable iomsg
Message status indicator corresponding to iolun, denoting whether a BUFR message is currently open wi...
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 ibt
Bit widths corresponding to tag and typ:
integer, dimension(:), allocatable itp
Integer type values corresponding to typ:
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 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.
integer, dimension(:,:), allocatable, target inv
Inventory pointer which links each data value to its corresponding node in the internal jump/link tab...
recursive subroutine closbf(lunit)
Close the connection between logical unit lunit and the NCEPLIBS-bufr software.
subroutine rewnbf(lunit, isr)
Store or restore parameters associated with a BUFR file.
recursive subroutine fortran_open(filename, lunit, format, position, iret)
Open a Fortran file on the local system.
recursive subroutine openbf(lunit, io, lundx)
Connect a new file to the NCEPLIBS-bufr software for input or output operations, or initialize the li...
subroutine setpart(xpart)
Specify whether future calls to subroutine ufbtab() should attempt to return full or partial results.
recursive subroutine fortran_close(lunit, iret)
Close a Fortran file on the local system.
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...
subroutine wtstat(lunit, lun, il, im)
Update file status in library internals.
recursive subroutine ufbtab(lunin, tab, i1, i2, iret, str)
Read through every data subset in a BUFR file and return one or more specified data values from each ...
subroutine posapx(lunxx)
Position an output BUFR file for appending.
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 ...
recursive subroutine readmg(lunxx, subset, jdate, iret)
Read the next BUFR message from logical unit abs(lunxx) into internal arrays.
subroutine rdmsgw(lunit, mesg, iret)
Read the next BUFR message from logical unit lunit as an array of integer words.
recursive integer function ireadmg(lunit, subset, idate)
Call subroutine readmg() and pass back its return code as the function value.
subroutine usrtpl(lun, invn, nbmp)
Expand a subset template within internal arrays.
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 parstr(str, tags, mtag, ntag, sep, limit80)
Parse a string containing one or more substrings into an array of substrings.
subroutine string(str, lun, i1, io)
Check whether a string is in the internal mnemonic string cache.
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.