NCEPLIBS-bufr  12.2.0
readwritesb.F90
Go to the documentation of this file.
1 
5 
31 recursive subroutine readsb(lunit,iret)
32 
33  use bufrlib
34 
35  use modv_vars, only: im8b
36 
37  use moda_msgcwd
38  use moda_unptyp
39  use moda_bitbuf
40  use moda_bitmaps
41  use moda_stcode
42  use moda_borts
43 
44  implicit none
45 
46  integer, intent(in) :: lunit
47  integer, intent(out) :: iret
48  integer my_lunit, lun, il, im, ier, nbyt
49 
50  ! Check for I8 integers
51 
52  if(im8b) then
53  im8b=.false.
54  call x84(lunit,my_lunit,1)
55  call readsb(my_lunit,iret)
56  call x48(iret,iret,1)
57  im8b=.true.
58  return
59  endif
60 
61  ! If we're catching bort errors, set a target return location if one doesn't already exist.
62 
63  if (bort_target_is_unset) then
64  bort_target_is_unset = .false.
65  caught_str_len = 0
66  call catch_bort_readsb_c(lunit,iret)
67  bort_target_is_unset = .true.
68  return
69  endif
70 
71  iret = -1
72 
73  ! Check the file status
74 
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')
78  if(im==0) return
79 
80  ! See if there is another subset in the message
81 
82  if(nsub(lun)==msub(lun)) return
83  nsub(lun) = nsub(lun) + 1
84 
85  ! Read the next subset and reset the pointers
86 
87  nbtm = 0
88  lstnod = 0
89  lstnodct = 0
90  iscodes(lun) = 0
91  linbtm = .false.
92 
93  if(msgunp(lun)==0) then
94  ibit = mbyt(lun)*8
95  call upb(nbyt,16,mbay(1,lun),ibit)
96  call rdtree(lun,ier)
97  if(ier/=0) return
98  mbyt(lun) = mbyt(lun) + nbyt
99  elseif(msgunp(lun)==1) then
100  ! message with "standard" Section 3
101  ibit = mbyt(lun)
102  call rdtree(lun,ier)
103  if(ier/=0) return
104  mbyt(lun) = ibit
105  else
106  ! compressed message
107  call rdcmps(lun)
108  if (iscodes(lun) /= 0) return
109  endif
110 
111  iret = 0
112 
113  return
114 end subroutine readsb
115 
127 recursive integer function ireadsb(lunit) result(iret)
128 
129  use modv_vars, only: im8b
130 
131  implicit none
132 
133  integer, intent(in) :: lunit
134  integer my_lunit
135 
136  ! Check for I8 integers.
137 
138  if(im8b) then
139  im8b=.false.
140  call x84(lunit,my_lunit,1)
141  iret=ireadsb(my_lunit)
142  im8b=.true.
143  return
144  endif
145 
146  call readsb(lunit,iret)
147 
148  return
149 end function ireadsb
150 
176 recursive subroutine readns(lunit,subset,jdate,iret)
177 
178  use bufrlib
179 
180  use modv_vars, only: im8b, lendat
181 
182  use moda_msgcwd
183  use moda_tables
184  use moda_borts
185 
186  implicit none
187 
188  integer, intent(in) :: lunit
189  integer, intent(out) :: jdate, iret
190  integer my_lunit, lun, il, im
191 
192  character*8, intent(out) :: subset
193  character*9 csubset
194 
195  ! Check for I8 integers
196 
197  if(im8b) then
198  im8b=.false.
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)
203  im8b=.true.
204  return
205  endif
206 
207  ! If we're catching bort errors, set a target return location if one doesn't already exist.
208 
209  if (bort_target_is_unset) then
210  bort_target_is_unset = .false.
211  caught_str_len = 0
212  call catch_bort_readns_c(lunit,csubset,jdate,len(csubset),iret)
213  subset(1:8) = csubset(1:8)
214  bort_target_is_unset = .true.
215  return
216  endif
217 
218  ! Refresh the subset and jdate parameters
219 
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
224  subset = ' '
225  else
226  subset = tag(inode(lun))(1:8)
227  endif
228  jdate = idate(lun)
229  if (lendat/=10) jdate = mod(jdate,10**8)
230 
231  ! Read the next subset in the BUFR file
232 
233  do while (.true.)
234  call readsb(lunit,iret)
235  if (iret==0) exit
236  call readmg(lunit,subset,jdate,iret)
237  if (iret/=0) exit
238  enddo
239 
240  return
241 end subroutine readns
242 
261 recursive integer function ireadns(lunit,subset,idate) result(iret)
262 
263  use modv_vars, only: im8b
264 
265  implicit none
266 
267  integer, intent(in) :: lunit
268  integer, intent(out) :: idate
269  integer my_lunit
270 
271  character*8, intent(out) :: subset
272 
273  ! Check for I8 integers.
274 
275  if(im8b) then
276  im8b=.false.
277  call x84(lunit,my_lunit,1)
278  iret=ireadns(my_lunit,subset,idate)
279  call x48(idate,idate,1)
280  im8b=.true.
281  return
282  endif
283 
284  call readns(lunit,subset,idate,iret)
285 
286  return
287 end function ireadns
288 
323 recursive subroutine writsb(lunit)
324 
325  use modv_vars, only: im8b
326 
327  use moda_msgcmp
328 
329  implicit none
330 
331  integer, intent(in) :: lunit
332  integer my_lunit, lun, il, im
333 
334  ! Check for I8 integers
335 
336  if(im8b) then
337  im8b=.false.
338 
339  call x84 ( lunit, my_lunit, 1 )
340  call writsb ( my_lunit )
341 
342  im8b=.true.
343  return
344  endif
345 
346  ! Check the file status
347 
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')
352 
353  ! Pack up the subset and put it into the message
354 
355  call wrtree(lun)
356  if( ccmf=='Y' ) then
357  call wrcmps(lunit)
358  else
359  call msgupd(lunit,lun)
360  endif
361 
362  return
363 end subroutine writsb
364 
443 recursive subroutine writsa(lunxx,lmsgt,msgt,msgl)
444 
445  use modv_vars, only: im8b
446 
447  use moda_bufrmg
448  use moda_msgcmp
449 
450  implicit none
451 
452  integer, intent(in) :: lunxx, lmsgt
453  integer, intent(out) :: msgt(*), msgl
454  integer my_lunxx, my_lmsgt, lunit, lun, il, im, n
455 
456  ! Check for I8 integers
457 
458  if(im8b) then
459  im8b=.false.
460 
461  call x84 ( lunxx, my_lunxx, 1 )
462  call x84 ( lmsgt, my_lmsgt, 1 )
463  call writsa ( my_lunxx, my_lmsgt*2, msgt, msgl )
464  msgl = msgl/2
465  call x48 ( msgl, msgl, 1 )
466 
467  im8b=.true.
468  return
469  endif
470 
471  lunit = abs(lunxx)
472 
473  ! Check the file status
474 
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')
479 
480  ! If lunxx < 0, force memory msg to be written (w/o any current subset)
481 
482  if(lunxx<0) call closmg(lunit)
483 
484  ! Is there a completed BUFR message to be returned?
485 
486  if(msglen(lun)>0) then
487  if(msglen(lun)>lmsgt) call bort('BUFRLIB: WRITSA - OVERFLOW OF OUTPUT BUFR MESSAGE ARRAY; TRY A LARGER '// &
488  'DIMENSION FOR THIS ARRAY')
489  msgl = msglen(lun)
490  do n=1,msgl
491  msgt(n) = msgtxt(n,lun)
492  enddo
493  msglen(lun) = 0
494  else
495  msgl = 0
496  endif
497 
498  if(lunxx<0) return
499 
500  ! Pack up the subset and put it into the message
501 
502  call wrtree(lun)
503  if( ccmf=='Y' ) then
504  call wrcmps(lunit)
505  else
506  call msgupd(lunit,lun)
507  endif
508 
509  ! If the just-completed call to wrcmps() or msgupd() for this subset caused a message to be flushed to abs(lunxx), then
510  ! attempt to retrieve and return that message now. Otherwise, we run the risk that the next call to openmb() or openmg()
511  ! might cause another message to be flushed, and thus overwrite the current message within array msgtxt before we
512  ! had the chance to retrieve it during the next call to writsa().
513 
514  ! Also note that, in rare instances (e.g. if the byte count of the most recent subset is > 65530), we could end up with
515  ! two BUFR messages available to be returned from this one call to writsa(). If sufficient space is available in the
516  ! msgt array, then go ahead and return both messages now.
517 
518  if( (msglen(lun)>0) .and. (msgl+msglen(lun)<=lmsgt) ) then
519  do n = 1,msglen(lun)
520  msgt(msgl+n) = msgtxt(n,lun)
521  enddo
522  msgl = msgl+msglen(lun)
523  msglen(lun) = 0
524  endif
525 
526  return
527 end subroutine writsa
528 
556 recursive subroutine rdmgsb(lunit,imsg,isub)
557 
558  use modv_vars, only: im8b
559 
560  use moda_msgcwd
561  use moda_bitbuf
562 
563  implicit none
564 
565  integer, intent(in) :: lunit, imsg, isub
566  integer my_lunit, my_imsg, my_isub, lun, il, im, i, jdate, iret
567 
568  character*128 bort_str
569  character*8 subset
570 
571  ! Check for I8 integers
572 
573  if(im8b) then
574  im8b=.false.
575 
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)
580 
581  im8b=.true.
582  return
583  endif
584 
585  ! Open the file and skip to message #imsg
586 
587  call openbf(lunit,'IN',lunit)
588  call status(lunit,lun,il,im)
589 
590  ! Note that we need to use subroutine readmg() to actually read in all of the messages (including the
591  ! first (imsg-1) messages!), just in case there are any embedded dictionary messages in the file.
592 
593  do i=1,imsg
594  call readmg(lunit,subset,jdate,iret)
595  if(iret<0) then
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
598  call bort(bort_str)
599  endif
600  enddo
601 
602  ! Position at subset #isub
603 
604  do i=1,isub
605  call readsb(lunit,iret)
606  if(iret<0) then
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
609  call bort(bort_str)
610  endif
611  enddo
612 
613  return
614 end subroutine rdmgsb
615 
633 subroutine msgupd(lunit,lun)
634 
635  use modv_vars, only: iprt, nby0, nby1, nby2, nby3
636 
637  use moda_msgcwd
638  use moda_bitbuf
639  use moda_h4wlc
640 
641  implicit none
642 
643  integer, intent(in) :: lunit, lun
644  integer ibyt, lbyt, lbit, nbyt, ii, iupb
645 
646  logical msgfull
647 
648  character*128 errstr
649 
650  ! Pad the subset buffer
651 
652  call pad(ibay,ibit,ibyt,8)
653 
654  ! Check whether the new subset should be written into the currently open message
655 
656  if(msgfull(mbyt(lun),ibyt,maxbyt) .or. ((ibyt>65530).and.(nsub(lun)>0))) then
657  ! No it should not, either because it doesn't fit
658  ! OR
659  ! It has byte count > 65530 (sufficiently close to the upper limit for the 16 bit byte counter placed at the beginning
660  ! of each subset), and the current message has at least one subset in it
661  !
662  ! In either of these cases, we need to write out the current message and then create a new one to hold the current subset
663  call msgwrt(lunit,mbay(1,lun),mbyt(lun))
664  call msgini(lun)
665  endif
666 
667  if(msgfull(mbyt(lun),ibyt,maxbyt)) then
668  ! This is an overlarge subset that won't fit in any message given the current value of maxbyt, so discard the subset
669  ! and exit gracefully.
670  if(iprt>=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, '}'
674  call errwrt(errstr)
675  call errwrt('>>>>>>>OVERLARGE SUBSET DISCARDED FROM FILE<<<<<<<<')
676  call errwrt('+++++++++++++++++++++WARNING+++++++++++++++++++++++')
677  call errwrt(' ')
678  endif
679  call usrtpl(lun,1,1)
680  return
681  endif
682 
683  ! Set a byte count and transfer the subset buffer into the message
684 
685  lbit = 0
686  call pkb(ibyt,16,ibay,lbit)
687 
688  ! Note that we want to append the data for this subset to the end of Section 4, but the value in mbyt(lun) already includes
689  ! the length of Section 5 (i.e. 4 bytes). Therefore, we need to begin writing at the point 3 bytes prior to the byte
690  ! currently pointed to by mbyt(lun).
691 
692  call mvb(ibay,1,mbay(1,lun),mbyt(lun)-3,ibyt)
693 
694  ! Update the subset and byte counters
695 
696  mbyt(lun) = mbyt(lun) + ibyt
697  nsub(lun) = nsub(lun) + 1
698 
699  lbit = (nby0+nby1+nby2+4)*8
700  call pkb(nsub(lun),16,mbay(1,lun),lbit)
701 
702  lbyt = nby0+nby1+nby2+nby3
703  nbyt = iupb(mbay(1,lun),lbyt+1,24)
704  lbit = lbyt*8
705  call pkb(nbyt+ibyt,24,mbay(1,lun),lbit)
706 
707  ! If any long character strings are being held internally for storage into this subset, store them now
708 
709  if(nh4wlc>0) then
710  do ii = 1, nh4wlc
711  call writlc(luh4wlc(ii),chh4wlc(ii),sth4wlc(ii))
712  enddo
713  nh4wlc = 0
714  endif
715 
716  ! If the subset byte count is > 65530, then give it its own one-subset message (cannot have any other subsets in this
717  ! message because their beginning would be beyond the upper limit of 65535 in the 16-bit byte counter, meaning they
718  ! could not be located!)
719 
720  if(ibyt>65530) then
721  if(iprt>=1) then
722  call errwrt('+++++++++++++++++++++WARNING+++++++++++++++++++++++')
723  write ( unit=errstr, fmt='(A,I7,A,A)') 'BUFRLIB: MSGUPD - SUBSET HAS BYTE COUNT = ',ibyt,' > UPPER LIMIT OF 65535'
724  call errwrt(errstr)
725  call errwrt('>>>>>>>WILL BE WRITTEN INTO ITS OWN MESSAGE<<<<<<<<')
726  call errwrt('+++++++++++++++++++++WARNING+++++++++++++++++++++++')
727  call errwrt(' ')
728  endif
729  call msgwrt(lunit,mbay(1,lun),mbyt(lun))
730  call msgini(lun)
731  endif
732 
733  ! Reset the user arrays
734 
735  call usrtpl(lun,1,1)
736 
737  return
738 end subroutine msgupd
739 
769 subroutine pad(ibay,ibit,ibyt,ipadb)
770 
771  implicit none
772 
773  integer, intent(inout) :: ibay(*), ibit
774  integer, intent(in) :: ipadb
775  integer, intent(out) :: ibyt
776  integer ipad
777 
778  character*128 bort_str
779 
780  ! Pad the subset to an ipadb bit boundary
781 
782  ipad = ipadb - mod(ibit+8,ipadb)
783  ! First pack the # of bits being padded (this is a delayed replication factor)
784  call pkb(ipad,8,ibay,ibit)
785  ! Now pad with zeroes to the byte boundary
786  call pkb(0,ipad,ibay,ibit)
787  ibyt = ibit/8
788 
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
792  call bort(bort_str)
793  endif
794 
795  return
796 end subroutine pad
797 
823 recursive integer function lcmgdf(lunit,subset) result(iret)
824 
825  use modv_vars, only: im8b
826 
827  use moda_tables
828 
829  implicit none
830 
831  integer, intent(in) :: lunit
832  integer my_lunit, lun, il, im, mtyp, msbt, inod, nte, i
833 
834  character*8, intent(in) :: subset
835 
836  ! Check for I8 integers.
837 
838  if(im8b) then
839  im8b=.false.
840 
841  call x84(lunit,my_lunit,1)
842  iret=lcmgdf(my_lunit,subset)
843 
844  im8b=.true.
845  return
846  endif
847 
848  iret = 0
849 
850  ! Get lun from lunit.
851 
852  call status(lunit,lun,il,im)
853  if (il==0) call bort('BUFRLIB: LCMGDF - INPUT BUFR FILE IS CLOSED, IT MUST BE OPEN')
854 
855  ! Confirm that subset is defined for this logical unit.
856 
857  call nemtba(lun,subset,mtyp,msbt,inod)
858 
859  ! Check if there's a long character string in the definition.
860 
861  nte = isc(inod)-inod
862 
863  do i = 1, nte
864  if ( (typ(inod+i)=='CHR') .and. (ibt(inod+i)>64) ) then
865  iret = 1
866  return
867  endif
868  enddo
869 
870  iret = 0
871 
872  return
873 end function lcmgdf
874 
899 recursive subroutine ufbpos(lunit,irec,isub,subset,jdate)
900 
901  use bufrlib
902 
903  use modv_vars, only: im8b
904 
905  use moda_msgcwd
906  use moda_bitbuf
907 
908  implicit none
909 
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
913 
914  character*128 bort_str
915  character*8, intent(out) :: subset
916 
917  ! Check for I8 integers
918 
919  if(im8b) then
920  im8b=.false.
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)
926  im8b=.true.
927  return
928  endif
929 
930  ! Make sure a file is open for input
931 
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')
935 
936  if(irec<=0) then
937  write(bort_str,'("BUFRLIB: UFBPOS - REQUESTED MESSAGE NUMBER TO READ IN (",I5,") IS NOT VALID")') irec
938  call bort(bort_str)
939  endif
940  if(isub<=0) then
941  write(bort_str,'("BUFRLIB: UFBPOS - REQUESTED SUBSET NUMBER TO READ IN (",I5,") IS NOT VALID")') isub
942  call bort(bort_str)
943  endif
944 
945  ! See where pointers are currently located
946 
947  call ufbcnt(lunit,jrec,jsub)
948 
949  ! Rewind file if requested pointers are behind current pointers
950 
951  if(irec<jrec .or. (irec==jrec.and.isub<jsub)) then
952  call cewind_c(lun)
953  nmsg(lun) = 0
954  nsub(lun) = 0
955  call ufbcnt(lunit,jrec,jsub)
956  endif
957 
958  ! Read subset #isub from message #irec from file
959 
960  do while (irec>jrec)
961  call readmg(lunit,subset,jdate,iret)
962  if(iret<0) then
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
965  call bort(bort_str)
966  endif
967  call ufbcnt(lunit,jrec,jsub)
968  enddo
969 
970  do while (isub>jsub)
971  call readsb(lunit,iret)
972  if(iret/=0) then
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
975  call bort(bort_str)
976  endif
977  call ufbcnt(lunit,jrec,jsub)
978  enddo
979 
980  return
981 end subroutine ufbpos
982 
994 subroutine rdtree(lun,iret)
995 
996  use modv_vars, only: bmiss
997 
998  use moda_usrint
999  use moda_usrbit
1000  use moda_ival
1001  use moda_bitbuf
1002  use moda_tables
1003 
1004  implicit none
1005 
1006  integer, intent(in) :: lun
1007  integer, intent(out) :: iret
1008  integer ier, n, node, kbit, nbt, icbfms, igetrfel
1009 
1010  character*8 cval
1011 
1012  real*8 rval, ups
1013 
1014  equivalence(cval,rval)
1015 
1016  iret = 0
1017 
1018  ! Cycle through a subset setting up the template
1019 
1020  mbit(1) = ibit
1021  nbit(1) = 0
1022  call rcstpl(lun,ier)
1023  if(ier/=0) then
1024  iret = -1
1025  return
1026  endif
1027 
1028  ! Loop through each element of the subset, unpacking each value and then converting it to the proper type
1029 
1030  do n=1,nval(lun)
1031  call upb8(ival(n),nbit(n),mbit(n),mbay(1,lun))
1032  node = inv(n,lun)
1033  if(itp(node)==1) then
1034  ! The unpacked value is a delayed descriptor replication factor.
1035  val(n,lun) = ival(n)
1036  elseif(itp(node)==2) then
1037  ! The unpacked value is a real.
1038  nrfelm(n,lun) = igetrfel(n,lun)
1039  if (ival(n)<2_8**ibt(node)-1) then
1040  val(n,lun) = ups(ival(n),node)
1041  else
1042  val(n,lun) = bmiss
1043  endif
1044  elseif(itp(node)==3) then
1045  ! The value is a character string, so unpack it using an equivalenced real*8 value. Note that a maximum of 8 characters
1046  ! will be unpacked here, so a separate subsequent call to subroutine readlc() will be needed to fully unpack any string
1047  ! longer than 8 characters.
1048  cval = ' '
1049  kbit = mbit(n)
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
1053  val(n,lun) = bmiss
1054  else
1055  val(n,lun) = rval
1056  endif
1057  endif
1058  enddo
1059 
1060  ibit = nbit(nval(lun))+mbit(nval(lun))
1061 
1062  return
1063 end subroutine rdtree
1064 
1073 subroutine wrtree(lun)
1074 
1075  use moda_usrint
1076  use moda_ival
1077  use moda_ufbcpl
1078  use moda_bitbuf
1079  use moda_tables
1080 
1081  implicit none
1082 
1083  integer, intent(in) :: lun
1084  integer*8 ipks
1085  integer n, node, nbit, ncr, numchr, jj, ibfms, igetrfel, imrkopr
1086 
1087  character*120 lstr
1088  character*8 cval
1089 
1090  real*8 rval
1091 
1092  equivalence(cval,rval)
1093 
1094  ! Convert user numbers into scaled integers
1095 
1096  do n=1,nval(lun)
1097  node = inv(n,lun)
1098  nrfelm(n,lun) = igetrfel(n,lun)
1099  if(itp(node)==1) then
1100  ival(n) = nint(val(n,lun))
1101  elseif(typ(node)=='NUM') then
1102  if( (ibfms(val(n,lun))==1) .or. (val(n,lun)/=val(n,lun)) ) then
1103  ! The user number is either "missing" or NaN.
1104  ival(n) = -1
1105  else
1106  ival(n) = ipks(val(n,lun),node)
1107  endif
1108  call strbtm(n,lun,int(ival(n)))
1109  endif
1110  enddo
1111 
1112  ! Pack the user array into the subset buffer
1113 
1114  ibit = 16
1115 
1116  do n=1,nval(lun)
1117  node = inv(n,lun)
1118  if(itp(node)<3) then
1119  ! The value to be packed is numeric.
1120  if ( imrkopr(tag(node)) == 1 ) then
1121  nbit = ibt(inv(nrfelm(n,lun),lun))
1122  else
1123  nbit = ibt(node)
1124  endif
1125  call pkb8(ival(n),nbit,ibay,ibit)
1126  else
1127  ! The value to be packed is a character string.
1128  ncr=ibt(node)/8
1129  if ( ncr>8 .and. luncpy(lun)/=0 ) then
1130  ! The string is longer than 8 characters and there was a preceeding call to ufbcpy() involving this output unit,
1131  ! so read the long string with readlc() and then write it into the output buffer using pkc().
1132  call readlc(luncpy(lun),lstr,tag(node))
1133  call pkc(lstr,ncr,ibay,ibit)
1134  else
1135  rval = val(n,lun)
1136  if(ibfms(rval)/=0) then
1137  ! The value is "missing", so set all bits to 1 before packing the field as a character string.
1138  numchr = min(ncr,len(lstr))
1139  do jj = 1, numchr
1140  call ipkm(lstr(jj:jj),1,255)
1141  enddo
1142  call pkc(lstr,numchr,ibay,ibit)
1143  else
1144  ! The value is not "missing", so pack the equivalenced character string. Note that a maximum of 8 characters
1145  ! will be packed here, so a separate subsequent call to subroutine writlc() will be needed to fully encode any
1146  ! string longer than 8 characters.
1147  call pkc(cval,ncr,ibay,ibit)
1148  endif
1149  endif
1150  endif
1151  enddo
1152 
1153  ! Reset ufbcpy() file pointer
1154 
1155  luncpy(lun)=0
1156 
1157  return
1158 end subroutine wrtree
1159 
1172 subroutine rcstpl(lun,iret)
1173 
1174  use modv_vars, only: maxjl, maxss, maxrcr, iprt
1175 
1176  use moda_usrint
1177  use moda_usrbit
1178  use moda_msgcwd
1179  use moda_bitbuf
1180  use moda_tables
1181  use moda_usrtmp
1182 
1183  implicit none
1184 
1185  character*128 bort_str
1186 
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
1190 
1191  iret = 0
1192 
1193  ! Set the initial values for the template
1194 
1195  inv(1,lun) = inode(lun)
1196  val(1,lun) = 0
1197  nbmp(1,1) = 1
1198  nbmp(2,1) = 1
1199  nodi = inode(lun)
1200  node = inode(lun)
1201  mbmp = 1
1202  nval(lun) = 1
1203  nr = 0
1204  knx(1:maxrcr) = 0
1205 
1206  outer: do while (.true.)
1207 
1208  ! Set up the parameters for a level of recursion
1209 
1210  nr = nr+1
1211  if(nr>maxrcr) then
1212  write(bort_str,'("BUFRLIB: RCSTPL - THE NUMBER OF RECURSION LEVELS EXCEEDS THE LIMIT (",I3,")")') maxrcr
1213  call bort(bort_str)
1214  endif
1215  nbmp(1,nr) = 1
1216  nbmp(2,nr) = mbmp
1217 
1218  n1 = iseq(node,1)
1219  n2 = iseq(node,2)
1220  if(n1==0) then
1221  write(bort_str,'("BUFRLIB: RCSTPL - UNSET EXPANSION SEGMENT ",A)') tag(nodi)
1222  call bort(bort_str)
1223  endif
1224  if(n2-n1+1>maxjl) then
1225  if(iprt>=0) then
1226  call errwrt('++++++++++++++BUFR ARCHIVE LIBRARY+++++++++++++++++')
1227  call errwrt('BUFRLIB: RCSTPL - MAXJL OVERFLOW; SUBSET SKIPPED')
1228  call errwrt('++++++++++++++BUFR ARCHIVE LIBRARY+++++++++++++++++')
1229  endif
1230  iret = -1
1231  return
1232  endif
1233  newn(1,nr) = 1
1234  newn(2,nr) = n2-n1+1
1235 
1236  do n=1,newn(2,nr)
1237  nn = jseq(n+n1-1)
1238  iutmp(n,nr) = nn
1239  vutmp(n,nr) = vali(nn)
1240  enddo
1241 
1242  do while (.true.)
1243 
1244  ! Store nodes at some recursion level
1245 
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
1251  if(iprt>=0) then
1252  call errwrt('++++++++++++++BUFR ARCHIVE LIBRARY+++++++++++++++++')
1253  call errwrt('BUFRLIB: RCSTPL - MAXSS OVERFLOW; SUBSET SKIPPED')
1254  call errwrt('++++++++++++++BUFR ARCHIVE LIBRARY+++++++++++++++++')
1255  endif
1256  iret = -1
1257  return
1258  endif
1259  nval(lun) = nval(lun)+1
1260  node = iutmp(j,nr)
1261  ! inv is positional index in internal jump/link table for packed subset element nval(lun) in mbay
1262  inv(nval(lun),lun) = node
1263  ! mbit is the bit in mbay pointing to where the packed subset element nval(lun) begins
1264  mbit(nval(lun)) = mbit(nval(lun)-1)+nbit(nval(lun)-1)
1265  ! nbit is the number of bits in mbay occupied by packed subset element nval(lun)
1266  nrfelm(nval(lun),lun) = igetrfel(nval(lun),lun)
1267  nbit(nval(lun)) = ibt(node)
1268  if(nbit(nval(lun))==1) then
1269  ! Check whether this is a bitmap entry
1270  call upbb(ivob,nbit(nval(lun)),mbit(nval(lun)),mbay(1,lun))
1271  call strbtm(nval(lun),lun,ivob)
1272  endif
1273  ! Actual unpacked subset values are initialized here
1274  val(nval(lun),lun) = vutmp(j,nr)
1275  if(itp(node)==1) then
1276  call upbb(mbmp,nbit(nval(lun)),mbit(nval(lun)),mbay(1,lun))
1277  newn(1,nr) = j+1
1278  nbmp(1,nr) = i
1279  cycle outer
1280  endif
1281  enddo
1282  new = nval(lun)-knx(nr)
1283  val(knx(nr)+1,lun) = val(knx(nr)+1,lun) + new
1284  knx(nr) = 0
1285  enddo
1286 
1287  ! Check if we need to continue one recursion level back
1288 
1289  if(nr-1 == 0) exit outer
1290  nr = nr-1
1291  enddo
1292 
1293  enddo outer
1294 
1295  return
1296 end subroutine rcstpl
1297 
1308 subroutine usrtpl(lun,invn,nbmp)
1309 
1310  use modv_vars, only: maxjl, maxss, iprt
1311 
1312  use moda_usrint
1313  use moda_msgcwd
1314  use moda_tables
1315  use moda_ivttmp
1316  use moda_stcode
1317 
1318  implicit none
1319 
1320  integer, intent(in) :: lun, invn, nbmp
1321  integer i, j, ival, jval, n, n1, n2, nodi, node, newn, invr, knvn
1322 
1323  character*128 bort_str, errstr
1324 
1325  logical drp, drs, drb, drx
1326 
1327  if(iprt>=2) then
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))
1331  call errwrt(errstr)
1332  call errwrt('++++++++++++++BUFR ARCHIVE LIBRARY+++++++++++++++++')
1333  call errwrt(' ')
1334  endif
1335 
1336  if(nbmp<=0) then
1337  if(iprt>=1) then
1338  call errwrt('+++++++++++++++++++++WARNING+++++++++++++++++++++++')
1339  call errwrt(.LE.'BUFRLIB: USRTPL - NBMP 0 - IMMEDIATE RETURN')
1340  call errwrt('+++++++++++++++++++++WARNING+++++++++++++++++++++++')
1341  call errwrt(' ')
1342  endif
1343  return
1344  endif
1345 
1346  drp = .false.
1347  drs = .false.
1348  drx = .false.
1349 
1350  ! Set up a node expansion
1351 
1352  if(invn==1) then
1353  ! The node is a Table A mnemonic
1354  nodi = inode(lun)
1355  inv(1,lun) = nodi
1356  nval(lun) = 1
1357  if(nbmp/=1) then
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)
1360  call bort(bort_str)
1361  endif
1362  elseif(invn>0 .and. invn<=nval(lun)) then
1363  ! The node is (hopefully) a delayed replication factor
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)
1375  call bort(bort_str)
1376  endif
1377  if(.not.drx) then
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)
1380  call bort(bort_str)
1381  endif
1382  if(ival<0) then
1383  write(bort_str,'("BUFRLIB: USRTPL - REPLICATION FACTOR IS NEGATIVE (=",I5,") (",A,")")') ival, tag(nodi)
1384  call bort(bort_str)
1385  endif
1386  if(ival+nbmp>jval) then
1387  write(bort_str,'("BUFRLIB: USRTPL - REPLICATION FACTOR OVERFLOW (EXCEEDS MAXIMUM OF",I6," (",A,")")') jval, tag(nodi)
1388  call errwrt(bort_str)
1389  iscodes(lun) = 1
1390  return
1391  endif
1392  else
1393  write(bort_str,'("BUFRLIB: USRTPL - INVENTORY INDEX {FIRST '// &
1394  'ARGUMENT (INPUT)} OUT OF BOUNDS (=",I5,", RANGE IS 1 TO",I6,") ")') invn, nval(lun)
1395  call bort(bort_str)
1396  endif
1397 
1398  ! Recall a pre-fab node expansion segment
1399 
1400  newn = 0
1401  n1 = iseq(nodi,1)
1402  n2 = iseq(nodi,2)
1403 
1404  if(n1==0) then
1405  write(bort_str,'("BUFRLIB: USRTPL - UNSET EXPANSION SEGMENT (",A,")")') tag(nodi)
1406  call bort(bort_str)
1407  endif
1408  if(n2-n1+1>maxjl) then
1409  write(bort_str,'("BUFRLIB: USRTPL - TEMPLATE ARRAY OVERFLOW, EXCEEDS THE LIMIT (",I6,") (",A,")")') maxjl, tag(nodi)
1410  call bort(bort_str)
1411  endif
1412 
1413  do n=n1,n2
1414  newn = newn+1
1415  itmp(newn) = jseq(n)
1416  vtmp(newn) = vali(jseq(n))
1417  enddo
1418 
1419  ! Move old nodes and store new ones
1420 
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)
1424  call bort(bort_str)
1425  endif
1426 
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)
1430  enddo
1431 
1432  if(drp.or.drs) vtmp(1) = newn
1433  knvn = invn
1434 
1435  do i=1,nbmp
1436  do j=1,newn
1437  knvn = knvn+1
1438  inv(knvn,lun) = itmp(j)
1439  val(knvn,lun) = vtmp(j)
1440  enddo
1441  enddo
1442 
1443  ! Reset pointers and counters
1444 
1445  nval(lun) = nval(lun) + newn*nbmp
1446 
1447  if(iprt>=2) then
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)
1451  call errwrt(errstr)
1452  do i=1,newn
1453  write ( unit=errstr, fmt='(2(A,I5),A,A10)' ) 'For I = ', i, ', ITMP(I) = ', itmp(i), ', TAG(ITMP(I)) = ', tag(itmp(i))
1454  call errwrt(errstr)
1455  enddo
1456  call errwrt('++++++++++++++BUFR ARCHIVE LIBRARY+++++++++++++++++')
1457  call errwrt(' ')
1458  endif
1459 
1460  if(drx) then
1461  node = nodi
1462  invr = invn
1463  outer: do while (.true.)
1464  node = jmpb(node)
1465  if(node<=0) exit
1466  if(itp(node)==0) then
1467  do invr=invr-1,1,-1
1468  if(inv(invr,lun)==node) then
1469  val(invr,lun) = val(invr,lun)+newn*nbmp
1470  cycle outer
1471  endif
1472  enddo
1473  write(bort_str,'("BUFRLIB: USRTPL - BAD BACKUP STRATEGY (",A,")")') tag(nodi)
1474  call bort(bort_str)
1475  else
1476  cycle
1477  endif
1478  enddo outer
1479  endif
1480 
1481  return
1482 end subroutine usrtpl
1483 
1497 recursive subroutine invmrg(lubfi,lubfj)
1498 
1499  use modv_vars, only: im8b
1500 
1501  use moda_usrint
1502  use moda_tables
1503  use moda_mrgcom
1504 
1505  implicit none
1506 
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, &
1509  n, ioff, nwords, ibfms
1510 
1511  character*128 bort_str
1512 
1513  logical herei, herej, missi, missj, samei
1514 
1515  ! Check for I8 integers
1516 
1517  if(im8b) then
1518  im8b=.false.
1519  call x84(lubfi,my_lubfi,1)
1520  call x84(lubfj,my_lubfj,1)
1521  call invmrg(my_lubfi,my_lubfj)
1522  im8b=.true.
1523  return
1524  endif
1525 
1526  is = 1
1527  js = 1
1528 
1529  ! Get the unit pointers
1530 
1531  call status(lubfi,luni,il,im)
1532  call status(lubfj,lunj,jl,jm)
1533 
1534  ! Step through the buffers comparing the inventory and merging data
1535 
1536  do while(is<=nval(luni))
1537  ! Confirm we're at the same node in each buffer
1538  node = inv(is,luni)
1539  nodj = inv(js,lunj)
1540  if(node/=nodj) then
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
1543  call bort(bort_str)
1544  endif
1545 
1546  ityp = itp(node)
1547  if(ityp==1) then
1548  ! Do an entire sequence replacement
1549  if(typ(node)=='DRB') then
1550  ioff = 0
1551  else
1552  ioff = 1
1553  endif
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)
1560  enddo
1561  do n=0,iwrds
1562  inv(js+n,lunj) = inv(is+n,luni)
1563  val(js+n,lunj) = val(is+n,luni)
1564  enddo
1565  nval(lunj) = nval(lunj)+iwrds-jwrds
1566  jwrds = iwrds
1567  nrpl = nrpl+1
1568  endif
1569  is = is+iwrds
1570  js = js+jwrds
1571  elseif((ityp==2).or.(ityp==3)) then
1572  ! Fill missing values
1573  herei = ibfms(val(is,luni))==0
1574  herej = ibfms(val(js,lunj))==0
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)
1580  nmrg = nmrg+1
1581  elseif(herei.and.herej.and..not.samei) then
1582  namb = namb+1
1583  endif
1584  endif
1585 
1586  ! Bump the counters and go check the next pair
1587  is = is + 1
1588  js = js + 1
1589  enddo
1590 
1591  ntot = ntot+1
1592 
1593  return
1594 end subroutine invmrg
1595 
1604 integer function nwords(n,lun) result(iret)
1605 
1606  use moda_usrint
1607 
1608  implicit none
1609 
1610  integer, intent(in) :: n, lun
1611  integer k
1612 
1613  iret = 0
1614 
1615  do k=1,nint(val(n,lun))
1616  iret = iret + nint(val(iret+n+1,lun))
1617  enddo
1618 
1619  return
1620 end function nwords
subroutine strbtm(n, lun, ival)
Store internal information in module moda_bitmaps if the input element is part of a bitmap.
Definition: bitmaps.F90:20
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 upbb(nval, nbits, ibit, ibay)
Decode an integer value from within a specified number of bits of an integer array,...
Definition: cidecode.F90:154
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 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 pkc(chr, nchr, ibay, ibit)
Encode a character string within a specified number of bytes of an integer array, starting at the bit...
Definition: ciencode.F90:25
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 ...
Definition: ciencode.F90:194
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...
Definition: ciencode.F90:140
subroutine pkb8(nval, nbits, ibay, ibit)
Encode an 8-byte integer value within a specified number of bits of an integer array,...
Definition: ciencode.F90:97
subroutine rdcmps(lun)
Read the next compressed BUFR data subset into internal arrays.
Definition: compress.F90:112
subroutine wrcmps(lunix)
Write a compressed BUFR data subset.
Definition: compress.F90:386
subroutine mvb(ib1, nb1, ib2, nb2, nbm)
Copy a specified number of bytes from one packed binary array to another.
Definition: copydata.F90:729
subroutine nemtba(lun, nemo, mtyp, msbt, inod)
Get information about a Table A descriptor from the internal DX BUFR tables.
Definition: dxtable.F90:1236
subroutine errwrt(str)
Specify a custom location for the logging of error and diagnostic messages generated by the NCEPLIBS-...
Definition: errwrt.F90:32
integer function ibfms(r8val)
Check whether a real*8 data value returned from a previous call to any of the NCEPLIBS-bufr values-re...
Definition: missing.F90:25
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, 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.
Definition: readwritemg.F90:44
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.
Definition: readwritesb.F90:32
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.
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