NCEPLIBS-bufr  12.2.0
openclosebf.F90
Go to the documentation of this file.
1 
5 
15 recursive subroutine fortran_open(filename, lunit, format, position, iret)
16 
17  use modv_vars, only: im8b
18 
19  implicit none
20  character*(*), intent(in) :: filename, format, position
21  integer, intent(in) :: lunit
22  integer, intent(out) :: iret
23  integer my_lunit
24 
25  ! check for i8 integers
26 
27  if(im8b) then
28  im8b=.false.
29 
30  call x84(lunit,my_lunit,1)
31  call fortran_open(filename,my_lunit,format,position,iret)
32  call x48(iret,iret,1)
33 
34  im8b=.true.
35  return
36  endif
37 
38  open(lunit, file=trim(filename), form=trim(format), position=trim(position), iostat=iret)
39  return
40 end subroutine fortran_open
41 
48 recursive subroutine fortran_close(lunit, iret)
49 
50  use modv_vars, only: im8b
51 
52  implicit none
53  integer, intent(in) :: lunit
54  integer, intent(out) :: iret
55  integer my_lunit
56 
57  ! check for i8 integers
58 
59  if(im8b) then
60  im8b=.false.
61 
62  call x84(lunit,my_lunit,1)
63  call fortran_close(my_lunit,iret)
64  call x48(iret,iret,1)
65 
66  im8b=.true.
67  return
68  endif
69 
70  close(lunit, iostat=iret)
71  return
72 end subroutine fortran_close
73 
167 recursive subroutine openbf(lunit,io,lundx)
168 
169  use bufrlib
170 
171  use modv_vars, only: im8b, ifopbf, nfiles, iprt
172 
173  use moda_msgcwd
174  use moda_stbfr
175  use moda_sc3bfr
176  use moda_lushr
177  use moda_nulbfr
178  use moda_stcode
179  use moda_borts
180 
181  implicit none
182 
183  integer, intent(in) :: lunit, lundx
184  integer my_lunit, my_lundx, iprtprv, lun, il, im, lcio
185 
186  character*(*), intent(in) :: io
187  character*255 filename, fileacc
188  character*128 bort_str, errstr
189  character*28 cprint(0:4)
190  character*6 cio
191 
192  data cprint/ &
193  ' (only aborts) ', &
194  ' (limited -default) ', &
195  ' (all warnings) ', &
196  ' (all warnings+infos) ', &
197  ' (all warnings+infos+debugs)'/
198 
199  ! Check for i8 integers
200 
201  if(im8b) then
202  im8b=.false.
203  call x84(lunit,my_lunit,1)
204  call x84(lundx,my_lundx,1)
205  call openbf(my_lunit,io,my_lundx)
206  im8b=.true.
207  return
208  endif
209 
210  ! If we're catching bort errors, set a target return location if one doesn't already exist.
211 
212  if (bort_target_is_unset) then
213  bort_target_is_unset = .false.
214  caught_str_len = 0
215  call strsuc(io,cio,lcio)
216  call catch_bort_openbf_c(lunit,cio,lundx,lcio)
217  bort_target_is_unset = .true.
218  return
219  endif
220 
221  if(io=='QUIET') then
222  ! Override previous iprt value
223  iprtprv = iprt
224  iprt = lundx
225  if(iprt<-1) iprt = -1
226  if(iprt>3) iprt = 3
227  if(iprt>=0) then
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)
231  call errwrt(errstr)
232  call errwrt('++++++++++++++BUFR ARCHIVE LIBRARY+++++++++++++++++')
233  call errwrt(' ')
234  endif
235  endif
236 
237  if(ifopbf==0) then
238  ! This is the first call to this subroutine, so take care of some initial housekeeping tasks.
239  ! Note that arallocf and arallocc_c must be called before calling bfrini.
240 
241  ! Allocate internal arrays.
242  call arallocf
243  call arallocc_c
244 
245  ! Initialize some global variables.
246  call bfrini
247 
248  ifopbf = 1
249  endif
250  if( (io=='FIRST') .or. (io=='QUIET') ) return
251 
252  ! See if a file can be opened
253 
254  call status(lunit,lun,il,im)
255  if(lun==0) then
256  write(bort_str,'("BUFRLIB: OPENBF - THERE ARE ALREADY",I3," BUFR FILES OPENED, CANNOT OPEN FILE CONNECTED TO UNIT",I4)') &
257  nfiles,lunit
258  call bort(bort_str)
259  endif
260  if(il/=0) then
261  write(bort_str,'("BUFRLIB: OPENBF - THE FILE CONNECTED TO UNIT",I5," IS ALREADY OPEN")') lunit
262  call bort(bort_str)
263  endif
264  null(lun) = 0
265  isc3(lun) = 0
266  iscodes(lun) = 0
267  lus(lun) = 0
268 
269  ! Use inquire to obtain the filename associated with unit lunit
270 
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)
276  endif
277 
278  nmsg(lun) = 0
279  nsub(lun) = 0
280  msub(lun) = 0
281  inode(lun) = 0
282  idate(lun) = 0
283 
284  ! Decide how to open the file and setup the dictionary
285 
286  if(io=='IN') then
287  call openrb_c(lun,filename)
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)
293  null(lun) = 1
294  else if(io=='NUL') then
295  call wtstat(lunit,lun,1,0)
296  if(lunit/=lundx) call readdx(lunit,lun,lundx)
297  null(lun) = 1
298  else if(io=='INX') then
299  call openrb_c(lun,filename)
300  call wtstat(lunit,lun,-1,0)
301  null(lun) = 1
302  else if(io=='OUX') then
303  call openwb_c(lun,filename)
304  call wtstat(lunit,lun,1,0)
305  else if(io=='SEC3') then
306  call openrb_c(lun,filename)
307  call wtstat(lunit,lun,-1,0)
308  isc3(lun) = 1
309  else if(io=='OUT') then
310  call openwb_c(lun,filename)
311  call wtstat(lunit,lun,1,0)
312  call writdx(lunit,lun,lundx)
313  else if(io=='NODX') then
314  call openwb_c(lun,filename)
315  call wtstat(lunit,lun,1,0)
316  call readdx(lunit,lun,lundx)
317  else if(io=='APN' .or. io=='APX') then
318  call openab_c(lun,filename)
319  call wtstat(lunit,lun,1,0)
320  if(lunit/=lundx) call readdx(lunit,lun,lundx)
321  call posapx(lunit)
322  else
323  call bort('BUFRLIB: OPENBF - ILLEGAL SECOND (INPUT) ARGUMENT')
324  endif
325 
326  return
327 end subroutine openbf
328 
341 recursive subroutine closbf(lunit)
342 
343  use bufrlib
344 
345  use modv_vars, only: im8b
346 
347  use moda_nulbfr
348  use moda_borts
349 
350  implicit none
351 
352  character*128 errstr
353 
354  integer, intent(in) :: lunit
355  integer my_lunit, lun, il, im
356 
357  ! Check for i8 integers
358 
359  if(im8b) then
360  im8b=.false.
361  call x84(lunit,my_lunit,1)
362  call closbf(my_lunit)
363  im8b=.true.
364  return
365  endif
366 
367  ! If we're catching bort errors, set a target return location if one doesn't already exist.
368 
369  if (bort_target_is_unset) then
370  bort_target_is_unset = .false.
371  caught_str_len = 0
372  call catch_bort_closbf_c(lunit)
373  bort_target_is_unset = .true.
374  return
375  endif
376 
377  if ( .not. allocated(null) ) then
378  call errwrt('++++++++++++++++++++WARNING++++++++++++++++++++++')
379  errstr = 'BUFRLIB: CLOSBF WAS CALLED WITHOUT HAVING PREVIOUSLY CALLED OPENBF'
380  call errwrt(errstr)
381  call errwrt('++++++++++++++++++++WARNING++++++++++++++++++++++')
382  return
383  endif
384 
385  call status(lunit,lun,il,im)
386  if(il>0 .and. im/=0) call closmg(lunit)
387  if(il/=0 .and. null(lun)==0) call closfb_c(lun)
388  call wtstat(lunit,lun,0,0)
389 
390  ! Close Fortran unit if null(lun) = 0
391 
392  if(null(lun)==0) close(lunit)
393 
394  return
395 end subroutine closbf
396 
418 recursive subroutine status(lunit,lun,il,im)
419 
420  use modv_vars, only: im8b, nfiles
421 
422  use moda_stbfr
423 
424  implicit none
425 
426  integer, intent(in) :: lunit
427  integer, intent(out) :: lun, il, im
428  integer my_lunit, i
429 
430  character*128 bort_str, errstr
431 
432  ! Check for I8 integers
433 
434  if(im8b) then
435  im8b=.false.
436 
437  call x84(lunit,my_lunit,1)
438  call status(my_lunit,lun,il,im)
439  call x48(lun,lun,1)
440  call x48(il,il,1)
441  call x48(im,im,1)
442 
443  im8b=.true.
444  return
445  endif
446 
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
449  call bort(bort_str)
450  endif
451 
452  ! Clear the status indicators
453 
454  lun = 0
455  il = 0
456  im = 0
457 
458  ! See if the unit is already connected to the library
459 
460  if ( .not. allocated(iolun) ) then
461  call errwrt('++++++++++++++++++++WARNING++++++++++++++++++++++')
462  errstr = 'BUFRLIB: STATUS WAS CALLED WITHOUT HAVING PREVIOUSLY CALLED OPENBF'
463  call errwrt(errstr)
464  call errwrt('++++++++++++++++++++WARNING++++++++++++++++++++++')
465  return
466  endif
467 
468  do i=1,nfiles
469  if(abs(iolun(i))==lunit) lun = i
470  enddo
471 
472  ! If not, try to define it so as to connect it to the library
473 
474  if(lun==0) then
475  do i=1,nfiles
476  if(iolun(i)==0) then
477  ! File space is available, return with lun > 0, il and im remain 0
478  lun = i
479  return
480  endif
481  enddo
482  ! File space is NOT available, return with lun, il and im all 0
483  return
484  endif
485 
486  ! If the unit was already connected to the library prior to this call, then return statuses
487 
488  il = sign(1,iolun(lun))
489  im = iomsg(lun)
490 
491  return
492 end subroutine status
493 
521 subroutine wtstat(lunit,lun,il,im)
522 
523  use moda_stbfr
524 
525  implicit none
526 
527  integer, intent(in) :: lunit, lun, il, im
528 
529  character*128 bort_str
530 
531  ! Check on the arguments
532 
533  if(lunit<=0) then
534  write(bort_str,'("BUFRLIB: WTSTAT - INVALID UNIT NUMBER PASSED INTO FIRST ARGUMENT (INPUT) (=",I3,")")') lunit
535  call bort(bort_str)
536  endif
537  if(lun<=0) then
538  write(bort_str,'("BUFRLIB: WTSTAT - INVALID FILE ID PASSED INTO SECOND ARGUMENT (INPUT) (=",I3,")")') lun
539  call bort(bort_str)
540  endif
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
544  call bort(bort_str)
545  endif
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
549  call bort(bort_str)
550  endif
551 
552  ! Check on lunit-lun combination
553 
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)
557  call bort(bort_str)
558  endif
559 
560  ! Reset the file statuses
561 
562  if(il/=0) then
563  iolun(lun) = sign(lunit,il)
564  iomsg(lun) = im
565  else
566  iolun(lun) = 0
567  iomsg(lun) = 0
568  endif
569 
570  return
571 end subroutine wtstat
572 
598 recursive subroutine ufbcnt(lunit,kmsg,ksub)
599 
600  use modv_vars, only: im8b
601 
602  use moda_msgcwd
603 
604  implicit none
605 
606  integer, intent(in) :: lunit
607  integer, intent(out) :: kmsg, ksub
608  integer my_lunit, lun, il, im
609 
610  ! Check for I8 integers
611 
612  if(im8b) then
613  im8b=.false.
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)
618  im8b=.true.
619  return
620  endif
621 
622  ! Check the file status - return the message and subset counters
623 
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')
626  kmsg = nmsg(lun)
627  ksub = nsub(lun)
628 
629  return
630 end subroutine ufbcnt
631 
643 subroutine posapx(lunxx)
644 
645  use bufrlib
646 
647  use moda_mgwa
648 
649  implicit none
650 
651  integer, intent(in) :: lunxx
652  integer lunit, lun, il, im, ier, idxmsg
653 
654  lunit = abs(lunxx)
655 
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')
659 
660  ! Try to read to the end of the file
661 
662  do while (.true.)
663  call rdmsgw(lunit,mgwa,ier)
664  if(ier<0) return
665  if(idxmsg(mgwa)==1) then
666  ! This is an internal dictionary message that was generated by the NCEPLIBS-bufr software. Backspace the file pointer
667  ! and then read and store all such dictionary messages (they should be stored consecutively!) and reset the internal tables.
668  call backbufr_c(lun)
669  call rdbfdx(lunit,lun)
670  endif
671  enddo
672 
673 end subroutine posapx
674 
706 subroutine rewnbf(lunit,isr)
707 
708  use bufrlib
709 
710  use moda_msgcwd
711  use moda_bitbuf
712  use moda_bufrsr
713 
714  implicit none
715 
716  integer, intent(in) :: lunit, isr
717  integer lun, il, im, i, kdate, ier
718 
719  character*128 bort_str
720  character*8 subset
721 
722  ! Try to trap bad call problems
723  if(isr==0) then
724  call status(lunit,lun,il,im)
725  if(jsr(lun)/=0) then
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
728  call bort(bort_str)
729  endif
730  if(il==0) then
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
733  call bort(bort_str)
734  endif
735  elseif(isr==1) then
736  if(junn==0) then
737  write(bort_str,'("BUFRLIB: REWNBF - ATTEMPING TO RESTORE '// &
738  'PARAMETERS TO BUFR FILE WHICH WERE NEVER SAVED (UNIT",I3,")")') lunit
739  call bort(bort_str)
740  endif
741  if(jsr(junn)/=1) then
742  write(bort_str,'("BUFRLIB: REWNBF - ATTEMPING TO RESTORE '// &
743  'PARAMETERS TO BUFR FILE WHICH WERE NEVER SAVED (UNIT",I3,")")') lunit
744  call bort(bort_str)
745  endif
746  lun = junn
747  else
748  write(bort_str,'("BUFRLIB: REWNBF - SAVE/RESTORE SWITCH (INPUT '// &
749  'ARGUMENT ISR) IS NOT ZERO OR ONE (HERE =",I4,") (UNIT",I3,")")') isr, lunit
750  call bort(bort_str)
751  endif
752 
753  if(isr==0) then
754  ! Store the existing file parameters
755  jmsg = nmsg(lun)
756  jsub = nsub(lun)
757  if ( il > 0 ) then
758  ! The file is open for writing
759  jbit = ibit
760  jbyt = mbyt(lun)
761  do i=1,jbyt
762  jbay(i) = mbay(i,lun)
763  enddo
764  endif
765  junn = lun
766  jill = il
767  jimm = im
768  ! Reset the file for reading
769  call wtstat(lunit,lun,-1,0)
770  endif
771 
772  ! Rewind the file
773  call cewind_c(lun)
774 
775  if(isr==1) then
776  ! Restore the previous file parameters. Note that we already restored the previous value of lun earlier in this routine.
777 
778  ! Reset nmsg(lun) to 0, so that the below calls to readmg() will internally restore nmsg(lun) to the correct value.
779  nmsg(lun) = 0
780 
781  ! Note that the below calls to readmg() are valid even if the file was previously open for writing, because we haven't yet
782  ! called wtstat() to restore the file to its previous I/O status. So until then we can still read from it as though it
783  ! was an input file.
784  do i=1,jmsg
785  call readmg(lunit,subset,kdate,ier)
786  if(ier<0) then
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
789  call bort(bort_str)
790  endif
791  enddo
792 
793  if ( jill < 0 ) then
794  ! The file was previously open for reading
795  do i=1,jsub
796  call readsb(lunit,ier)
797  enddo
798  else
799  ! The file was previously open for writing
800  do i=1,jbyt
801  mbay(i,lun) = jbay(i)
802  enddo
803  nsub(lun) = jsub
804  mbyt(lun) = jbyt
805  ibit = jbit
806  endif
807 
808  ! Now restore the file to its previous I/O status
809  il = jill
810  im = jimm
811  call wtstat(lunit,lun,il,im)
812  endif
813 
814  ! Toggle the stack status indicator
815  jsr(lun) = mod(jsr(lun)+1,2)
816 
817  return
818 end subroutine rewnbf
819 
887 
888 recursive subroutine ufbtab(lunin,tab,i1,i2,iret,str)
889 
890  use modv_vars, only: part, im8b, bmiss, iac, iprt
891 
892  use moda_usrint
893  use moda_msgcwd
894  use moda_unptyp
895  use moda_bitbuf
896  use moda_tables
897 
898  implicit none
899 
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, &
907 
908  character*(*), intent(in) :: str
909  character*128 errstr
910  character*40 cref
911  character*10 tgs(maxtg)
912  character*8 subset, cval
913 
914  logical :: openit, overflow, just_count, need_node, need_newmsg
915 
916  real*8, intent(out) :: tab(i1,i2)
917  real*8 rval, ups
918 
919  common /usrstr/ nnod, ncon, nods(20), nodc(10), ivls(10), kons(10)
920 
921  save lun, openit
922 
923  equivalence(cval,rval)
924 
925  ! Statement functions
926  mps(node) = 2_8**(ibt(node))-1
927  lps(lbit) = max(2_8**(lbit)-1,1)
928 
929  ! Check for I8 integers
930  if(im8b) then
931  im8b=.false.
932  call x84(lunin,my_lunin,1)
933  call x84(i1,my_i1,1)
934  call x84(i2,my_i2,1)
935  call ufbtab(my_lunin,tab,my_i1,my_i2,iret,str)
936  call x48(iret,iret,1)
937  im8b=.true.
938  return
939  endif
940 
941  ! Set counters to zero
942  irec = 0
943  isub = 0
944 
945  ! Initialize all of the output array values to the current value for "missing"
946  tab(1:i1,1:i2) = bmiss
947 
948  iac_prev = iac
949  iac = 1
950 
951  lunit = abs(lunin)
952  just_count = lunin<lunit
953  if (.not. just_count) then
954  ! Check for special tags in string
955  call parstr(str,tgs,maxtg,ntg,' ',.true.)
956  do i=1,ntg
957  if(tgs(i)=='IREC') irec = i
958  if(tgs(i)=='ISUB') isub = i
959  enddo
960  endif
961 
962  overflow = .false.
963 
964  if(part.and.iret<0) then
965  ! The previous call to this subroutine only partially read through the file, so resume reading from
966  ! the point where it previously left off.
967  need_newmsg = .false.
968  iret = 0
969  else
970  ! Make sure subroutine openbf() has been called at least once before trying to call subroutine status();
971  ! otherwise, status() might try to access array space that hasn't yet been dynamically allocated.
972  call openbf(0,'FIRST',0)
973  call status(lunit,lun,il,im)
974  openit = il==0
975  if(openit) then
976  ! Open BUFR file connected to unit lunit if it isn't already open
977  call openbf(lunit,'INX',lunit)
978  else
979  ! If BUFR file already opened, save position and rewind to first data message
980  call rewnbf(lunit,0)
981  endif
982  need_newmsg = .true.
983  iret = 0
984  ! Check for count subset only option
985  if(just_count) then
986  do while(ireadmg(-lunit,subset,jdate)>=0)
987  iret = iret+nmsub(lunit)
988  enddo
989  endif
990  endif
991 
992  outer: do while (.not. just_count)
993 
994  if(need_newmsg) then
995  ! Read the next message from the file
996  if(ireadmg(-lunit,subset,jdate)<0) exit
997  call string(str,lun,i1,0)
998  if(irec>0) nods(irec) = 0
999  if(isub>0) nods(isub) = 0
1000  else
1001  need_newmsg=.true.
1002  endif
1003 
1004  if(msgunp(lun)/=2) then
1005  ! The message is uncompressed
1006 
1007  inner1: do while (.true.)
1008  ! Get the next subset from the message
1009  if(nsub(lun)==msub(lun)) cycle outer
1010  if(iret+1>i2) then
1011  if(part) then
1012  iret=-iret
1013  return
1014  else
1015  overflow = .true.
1016  exit outer
1017  endif
1018  endif
1019  iret = iret+1
1020  do i=1,nnod
1021  nods(i) = abs(nods(i))
1022  enddo
1023  if(msgunp(lun)==0) then
1024  mbit = mbyt(lun)*8 + 16
1025  else
1026  mbit = mbyt(lun)
1027  endif
1028  nbit = 0
1029  n = 1
1030  call usrtpl(lun,n,n)
1031  inner2: do while (.true.)
1032  ! Cycle through each node of the subset to look for the requested values
1033  if(n+1<=nval(lun)) then
1034  n = n+1
1035  node = inv(n,lun)
1036  mbit = mbit+nbit
1037  nbit = ibt(node)
1038  if(itp(node)==1) then
1039  call upb8(ival,nbit,mbit,mbay(1,lun))
1040  nbmp=int(ival)
1041  call usrtpl(lun,n,nbmp)
1042  endif
1043  do i=1,nnod
1044  if(nods(i)==node) then
1045  if(itp(node)==1) then
1046  call upb8(ival,nbit,mbit,mbay(1,lun))
1047  tab(i,iret) = ival
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
1052  cval = ' '
1053  kbit = mbit
1054  call upc(cval,nbit/8,mbay(1,lun),kbit,.true.)
1055  tab(i,iret) = rval
1056  endif
1057  nods(i) = -nods(i)
1058  cycle inner2
1059  endif
1060  enddo
1061  do i=1,nnod
1062  if(nods(i)>0) cycle inner2
1063  enddo
1064  endif
1065  exit
1066  enddo inner2
1067  ! Update the subset pointers
1068  if(msgunp(lun)==0) then
1069  ibit = mbyt(lun)*8
1070  call upb(nbyt,16,mbay(1,lun),ibit)
1071  mbyt(lun) = mbyt(lun) + nbyt
1072  else
1073  mbyt(lun) = mbit
1074  endif
1075  nsub(lun) = nsub(lun) + 1
1076  if(irec>0) tab(irec,iret) = nmsg(lun)
1077  if(isub>0) tab(isub,iret) = nsub(lun)
1078  enddo inner1
1079 
1080  else
1081  ! The message is compressed
1082 
1083  if(iret+msub(lun)>i2) then
1084  if(part) then
1085  iret=-iret
1086  return
1087  else
1088  overflow = .true.
1089  exit outer
1090  endif
1091  endif
1092  if(irec>0.or.isub>0) then
1093  do nsb=1,msub(lun)
1094  if(irec>0) tab(irec,iret+nsb) = nmsg(lun)
1095  if(isub>0) tab(isub,iret+nsb) = nsb
1096  enddo
1097  endif
1098  call usrtpl(lun,1,1)
1099  ibit = mbyt(lun)
1100  n = 0
1101  inner3: do while ( n < nval(lun) )
1102  ! Cycle through each node of each subset to look for the requested values
1103  n = n+1
1104  node = inv(n,lun)
1105  nbit = ibt(node)
1106  ityp = itp(node)
1107  if(n==1) then
1108  ! Reset the node indices
1109  do i=1,nnod
1110  nods(i) = abs(nods(i))
1111  enddo
1112  else
1113  ! Are we still looking for more values?
1114  need_node = .false.
1115  do i=1,nnod
1116  if(nods(i)>0) then
1117  need_node = .true.
1118  exit
1119  endif
1120  enddo
1121  if(.not. need_node) exit inner3
1122  endif
1123  if(ityp==1 .or. ityp==2) then
1124  call up8(lref,nbit,mbay(1,lun),ibit)
1125  call upb(linc,6,mbay(1,lun),ibit)
1126  nibit = ibit + linc*msub(lun)
1127  elseif(ityp==3) then
1128  cref=' '
1129  call upc(cref,nbit/8,mbay(1,lun),ibit,.true.)
1130  call upb(linc,6,mbay(1,lun),ibit)
1131  nibit = ibit + 8*linc*msub(lun)
1132  else
1133  cycle
1134  endif
1135  if(ityp==1) then
1136  ! This is a delayed replication node
1137  jbit = ibit + linc
1138  call up8(ninc,linc,mbay(1,lun),jbit)
1139  ival = lref+ninc
1140  call usrtpl(lun,n,int(ival))
1141  cycle
1142  endif
1143  do i=1,nnod
1144  if(node==nods(i)) then
1145  ! This is one of the requested values, so store the corresponding value from each subset in the message
1146  nods(i) = -nods(i)
1147  lret = iret
1148  if(ityp==1 .or. ityp==2) then
1149  do nsb=1,msub(lun)
1150  jbit = ibit + linc*(nsb-1)
1151  call up8(ninc,linc,mbay(1,lun),jbit)
1152  ival = lref+ninc
1153  lret = lret+1
1154  if(ninc<lps(linc)) tab(i,lret) = ups(ival,node)
1155  enddo
1156  elseif(ityp==3) then
1157  do nsb=1,msub(lun)
1158  if(linc==0) then
1159  cval = cref(1:8)
1160  else
1161  jbit = ibit + linc*(nsb-1)*8
1162  cval = ' '
1163  call upc(cval,linc,mbay(1,lun),jbit,.true.)
1164  endif
1165  lret = lret+1
1166  tab(i,lret) = rval
1167  enddo
1168  else
1169  call bort('UFBTAB - INVALID ELEMENT TYPE SPECIFIED')
1170  endif
1171  endif
1172  enddo
1173  ibit = nibit
1174  enddo inner3
1175  iret = iret+msub(lun)
1176 
1177  endif
1178 
1179  enddo outer
1180 
1181  if(overflow) then
1182  nrep = iret
1183  do while(ireadsb(lunit)==0)
1184  nrep = nrep+1
1185  enddo
1186  do while(ireadmg(-lunit,subset,jdate)>=0)
1187  nrep = nrep+nmsub(lunit)
1188  enddo
1189  if(iprt>=0) then
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'
1193  call errwrt(errstr)
1194  write ( unit=errstr, fmt='(A,I8,A,I8,A)' ) '>>>UFBTAB STORED ', iret, ' REPORTS OUT OF ', nrep, '<<<'
1195  call errwrt(errstr)
1196  call errwrt('+++++++++++++++++++++WARNING+++++++++++++++++++++++')
1197  call errwrt(' ')
1198  endif
1199  endif
1200 
1201  if(openit) then
1202  ! Close BUFR file if it was opened here
1203  call closbf(lunit)
1204  else
1205  ! Restore BUFR file to its previous status and position
1206  call rewnbf(lunit,1)
1207  endif
1208 
1209  iac = iac_prev
1210 
1211  return
1212 end subroutine ufbtab
1213 
1239 subroutine setpart ( xpart )
1240 
1241  use modv_vars, only: part
1242 
1243  implicit none
1244 
1245  logical, intent(in) :: xpart
1246 
1247  part = xpart
1248 
1249  return
1250 end subroutine setpart
1251 
subroutine arallocf
Dynamically allocate Fortran language arrays.
Definition: arallocf.F90:19
recursive subroutine bort(str)
Log an error message, then either return to or abort the application program.
Definition: borts.F90:15
subroutine upb(nval, nbits, ibay, ibit)
Decode an integer value from within a specified number of bits of an integer array,...
Definition: cidecode.F90:202
subroutine upb8(nval, nbits, ibit, ibay)
Decode an 8-byte integer value from within a specified number of bits of an integer array,...
Definition: cidecode.F90:80
real *8 function ups(ival, node)
Unpack a real*8 value from an integer by applying the proper scale and reference values.
Definition: cidecode.F90:320
subroutine up8(nval, nbits, ibay, ibit)
Decode an 8-byte integer value from within a specified number of bits of an integer array,...
Definition: cidecode.F90:128
subroutine upc(chr, nchr, ibay, ibit, cnvnull)
Decode a character string from within a specified number of bytes of an integer array,...
Definition: cidecode.F90:26
subroutine writdx(lunit, lun, lundx)
Write DX BUFR table (dictionary) messages to the beginning of an output BUFR file in lunit.
Definition: dxtable.F90:800
subroutine readdx(lunit, lun, lundx)
Initialize modules moda_tababd and moda_msgcwd with DX BUFR (dictionary) tables.
Definition: dxtable.F90:29
subroutine rdbfdx(lunit, lun)
Beginning at the current file pointer location within lunit, read a complete DX BUFR table into inter...
Definition: dxtable.F90:121
subroutine errwrt(str)
Specify a custom location for the logging of error and diagnostic messages generated by the NCEPLIBS-...
Definition: errwrt.F90:32
subroutine strsuc(str1, str2, lens)
Remove leading and trailing blanks from a character string.
Definition: misc.F90:199
subroutine bfrini
Initialize numerous global variables and arrays within internal modules and common blocks throughout ...
Definition: misc.F90:16
Wrap C NCEPLIBS-bufr functions so they can be called from within the Fortran part of the library.
Definition: bufrlib.F90:11
Declare arrays and variables used to store BUFR messages internally for multiple file IDs.
integer 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.
Definition: openclosebf.F90:16
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.
Definition: openclosebf.F90:49
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.
Definition: readwritemg.F90:44
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.
Definition: readwritesb.F90:32
subroutine parstr(str, tags, mtag, ntag, sep, limit80)
Parse a string containing one or more substrings into an array of substrings.
Definition: strings.F90:473
subroutine string(str, lun, i1, io)
Check whether a string is in the internal mnemonic string cache.
Definition: strings.F90:25
subroutine x48(iin4, iout8, nval)
Encode one or more 4-byte integer values as 8-byte integer values.
Definition: x4884.F90:18
subroutine x84(iin8, iout4, nval)
Encode one or more 8-byte integer values as 4-byte integer values.
Definition: x4884.F90:65