NCEPLIBS-bufr  12.2.0
readwritemg.F90
Go to the documentation of this file.
1 
5 
43 recursive subroutine readmg(lunxx,subset,jdate,iret)
44 
45  use bufrlib
46 
47  use modv_vars, only: im8b, iprt
48 
49  use moda_msgcwd
50  use moda_sc3bfr
51  use moda_bitbuf
52  use moda_borts
53 
54  implicit none
55 
56  integer, intent(in) :: lunxx
57  integer, intent(out) :: jdate, iret
58  integer my_lunxx, lunit, lun, il, im, ier, idxmsg
59 
60  character*8, intent(out) :: subset
61  character*9 csubset
62  character*128 errstr
63 
64  ! Check for I8 integers
65 
66  if(im8b) then
67  im8b = .false.
68  call x84(lunxx,my_lunxx,1)
69  call readmg(my_lunxx,subset,jdate,iret)
70  call x48(jdate,jdate,1)
71  call x48(iret,iret,1)
72  im8b = .true.
73  return
74  endif
75 
76  ! If we're catching bort errors, set a target return location if one doesn't already exist.
77 
78  if (bort_target_is_unset) then
79  bort_target_is_unset = .false.
80  caught_str_len = 0
81  call catch_bort_readmg_c(lunxx,csubset,jdate,len(csubset),iret)
82  subset(1:8) = csubset(1:8)
83  bort_target_is_unset = .true.
84  return
85  endif
86 
87  iret = 0
88  lunit = abs(lunxx)
89 
90  ! Check the file status
91 
92  call status(lunit,lun,il,im)
93  if(il==0) call bort('BUFRLIB: READMG - INPUT BUFR FILE IS CLOSED, IT MUST BE OPEN FOR INPUT')
94  if(il>0) call bort('BUFRLIB: READMG - INPUT BUFR FILE IS OPEN FOR OUTPUT, IT MUST BE OPEN FOR INPUT')
95  call wtstat(lunit,lun,il,1)
96 
97  ! Read a message into the internal message buffer
98 
99  do while (.true.)
100  call rdmsgw(lunit,mbay(1,lun),ier)
101  if(ier==-1) then
102  ! EOF on attempted read
103  call wtstat(lunit,lun,il,0)
104  inode(lun) = 0
105  idate(lun) = 0
106  subset = ' '
107  jdate = 0
108  iret = -1
109  return
110  endif
111 
112  ! Parse the message section contents
113  if(isc3(lun)/=0) call reads3(lun)
114  call cktaba(lun,subset,jdate,iret)
115 
116  ! Check for a dictionary message
117  if(idxmsg(mbay(1,lun))/=1) return
118 
119  ! This is an internal dictionary message that was generated by the NCEPLIBS-bufr software.
120  if(isc3(lun)/=0) return
121 
122  ! Section 3 decoding isn't being used, so backspace the file pointer and then use subroutine rdbfdx() to read in
123  ! all such dictionary messages (they should be stored consecutively!) and reset the internal tables.
124  call backbufr_c(lun)
125  call rdbfdx(lunit,lun)
126  if(iprt>=1) then
127  call errwrt('++++++++++++++BUFR ARCHIVE LIBRARY+++++++++++++++++')
128  errstr = 'BUFRLIB: READMG - INTERNAL DICTIONARY MESSAGE READ; ACCOUNT FOR IT THEN READ IN NEXT MESSAGE WITHOUT RETURNING'
129  call errwrt(errstr)
130  call errwrt('++++++++++++++BUFR ARCHIVE LIBRARY+++++++++++++++++')
131  call errwrt(' ')
132  endif
133  enddo
134 
135 end subroutine readmg
136 
152 recursive integer function ireadmg(lunit,subset,idate) result(iret)
153 
154  use modv_vars, only: im8b
155 
156  implicit none
157 
158  integer, intent(in) :: lunit
159  integer, intent(out) :: idate
160  integer my_lunit
161 
162  character*8, intent(out) :: subset
163 
164  ! Check for I8 integers
165 
166  if(im8b) then
167  im8b = .false.
168  call x84(lunit,my_lunit,1)
169  iret=ireadmg(my_lunit,subset,idate)
170  call x48(idate,idate,1)
171  im8b = .true.
172  return
173  endif
174 
175  call readmg(lunit,subset,idate,iret)
176 
177  return
178 end function ireadmg
179 
223 recursive subroutine readerme(mesg,lunit,subset,jdate,iret)
224 
225  use modv_vars, only: mxmsgl, im8b, nbytw, iprt, bmostr
226 
227  use moda_sc3bfr
228  use moda_idrdm
229  use moda_bitbuf
230 
231  implicit none
232 
233  integer, intent(in) :: lunit, mesg(*)
234  integer, intent(out) :: jdate, iret
235  integer my_lunit, iec0(2), lun, il, im, ii, lnmsg, lmsg, idxmsg, iupbs3
236 
237  character*8, intent(out) :: subset
238  character*8 sec0
239  character*128 errstr, bort_str
240 
241  logical endtbl
242 
243  equivalence(sec0,iec0)
244 
245  ! Check for I8 integers
246 
247  if(im8b) then
248  im8b=.false.
249 
250  call x84(lunit,my_lunit,1)
251  call readerme(mesg,my_lunit,subset,jdate,iret)
252  call x48(jdate,jdate,1)
253  call x48(iret,iret,1)
254 
255  im8b=.true.
256  return
257  endif
258 
259  iret = 0
260 
261  ! Check the file status
262 
263  call status(lunit,lun,il,im)
264  if(il==0) call bort('BUFRLIB: READERME - INPUT BUFR FILE IS CLOSED, IT MUST BE OPEN FOR INPUT')
265  if(il>0) call bort('BUFRLIB: READERME - INPUT BUFR FILE IS OPEN FOR OUTPUT, IT MUST BE OPEN FOR INPUT')
266  call wtstat(lunit,lun,il, 1)
267 
268  ! Copy the input message into the internal message buffer
269 
270  iec0(1) = mesg(1)
271  iec0(2) = mesg(2)
272  lnmsg = lmsg(sec0)
273  if(lnmsg*nbytw>mxmsgl) then
274  write(bort_str,'("BUFRLIB: READERME - INPUT BUFR MESSAGE LENGTH",1X,I6," BYTES) IS LARGER THAN '// &
275  'LIMIT OF ",I6," BYTES")') lnmsg*nbytw, mxmsgl
276  call bort(bort_str)
277  endif
278  do ii=1,lnmsg
279  mbay(ii,lun) = mesg(ii)
280  enddo
281 
282  ! Confirm that the first 4 bytes of SEC0 contain 'BUFR'.
283 
284  if(sec0(1:4)/=bmostr) &
285  call bort('BUFRLIB: READERME - FIRST 4 BYTES READ FROM RECORD NOT "BUFR", DOES NOT CONTAIN BUFR DATA')
286 
287  ! Parse the message section contents
288 
289  if(isc3(lun)/=0) call reads3(lun)
290  call cktaba(lun,subset,jdate,iret)
291  if(isc3(lun)/=0) return
292 
293  ! Check for a DX dictionary message
294 
295  ! A new DX dictionary table can be passed in as a consecutive set of DX dictionary messages. Each message should be passed
296  ! in one at a time, via input argument mesg during consecutive calls to this subroutine, and all such messages will be
297  ! treated as a single dictionary table up until the next message is passed in which either contains no data subsets or
298  ! else is a non-DX dictionary message.
299 
300  endtbl = .false.
301  if(idxmsg(mbay(1,lun))==1) then
302  ! This is a DX dictionary message that was generated by the NCEPLIBS-bufr software.
303  if(iupbs3(mbay(1,lun),'NSUB')==0) then
304  ! But it doesn't contain any actual dictionary information, so assume we've reached the end of the dictionary table.
305  if(idrdm(lun)>0) then
306  endtbl = .true.
307  endif
308  else
309  if(idrdm(lun)==0) then
310  ! This is the first DX dictionary message that is part of a new dictionary table.
311  call dxinit(lun,0)
312  endif
313  idrdm(lun) = idrdm(lun) + 1
314  call stbfdx(lun,mbay(1,lun))
315  endif
316  else if(idrdm(lun)>0) then
317  ! This is the first non-DX dictionary message received following a string of DX dictionary messages, so assume we've
318  ! reached the end of the dictionary table.
319  endtbl = .true.
320  endif
321 
322  if(endtbl) then
323  if ( iprt >= 2 ) then
324  call errwrt('+++++++++++++++++++++++++++++++++++++++++++++++++')
325  write ( unit=errstr, fmt='(A,I3,A)' ) &
326  'BUFRLIB: READERME - STORED NEW DX TABLE CONSISTING OF (', idrdm(lun), ') MESSAGES;'
327  call errwrt(errstr)
328  errstr = 'WILL APPLY THIS TABLE TO ALL SUBSEQUENT DATA MESSAGES UNTIL NEXT DX TABLE IS PASSED IN'
329  call errwrt(errstr)
330  call errwrt('+++++++++++++++++++++++++++++++++++++++++++++++++')
331  call errwrt(' ')
332  endif
333  idrdm(lun) = 0
334  call makestab
335  endif
336 
337  return
338 end subroutine readerme
339 
349 subroutine rdmsgw(lunit,mesg,iret)
350 
351  use bufrlib
352 
353  use modv_vars, only: mxmsgld4
354 
355  implicit none
356 
357  integer, intent(in) :: lunit
358  integer, intent(out) :: mesg(*), iret
359  integer lun, il, im
360 
361  call status(lunit,lun,il,im)
362  iret = -2
363  do while (iret<=-2)
364  iret = crdbufr_c(lun,mesg,mxmsgld4)
365  if(iret==-3) call errwrt('BUFRLIB: RDMSGW - SKIPPING OVERLARGE MESSAGE')
366  if(iret==-2) call errwrt('BUFRLIB: RDMSGW - SKIPPING CORRUPTED MESSAGE')
367  end do
368 
369  return
370 end subroutine rdmsgw
371 
401 recursive subroutine openmb(lunit,subset,jdate)
402 
403  use modv_vars, only: im8b
404 
405  use moda_msgcwd
406 
407  implicit none
408 
409  integer, intent(in) :: lunit, jdate
410  integer my_lunit, my_jdate, lun, il, im, mtyp, mstb, inod, i4dy
411 
412  character*(*), intent(in) :: subset
413 
414  logical open
415 
416  ! Check for I8 integers
417 
418  if(im8b) then
419  im8b=.false.
420 
421  call x84(lunit,my_lunit,1)
422  call x84(jdate,my_jdate,1)
423  call openmb(my_lunit,subset,my_jdate)
424 
425  im8b=.true.
426  return
427  endif
428 
429  ! Check the file status
430 
431  call status(lunit,lun,il,im)
432  if(il==0) call bort('BUFRLIB: OPENMB - OUTPUT BUFR FILE IS CLOSED, IT MUST BE OPEN FOR OUTPUT')
433  if(il<0) call bort('BUFRLIB: OPENMB - OUTPUT BUFR FILE IS OPEN FOR INPUT, IT MUST BE OPEN FOR OUTPUT')
434 
435  ! Get some subset particulars
436 
437  call nemtba(lun,subset,mtyp,mstb,inod)
438  open = im==0 .or. inod/=inode(lun) .or. i4dy(jdate)/=idate(lun)
439 
440  ! Maybe(?) open a new or different type of message
441 
442  if(open) then
443  call closmg(lunit)
444  call wtstat(lunit,lun,il, 1)
445  inode(lun) = inod
446  idate(lun) = i4dy(jdate)
447  ! Initialize the open message
448  call msgini(lun)
449  call usrtpl(lun,1,1)
450  endif
451 
452  return
453 end subroutine openmb
454 
473 recursive subroutine openmg(lunit,subset,jdate)
474 
475  use modv_vars, only: im8b
476 
477  use moda_msgcwd
478 
479  implicit none
480 
481  integer, intent(in) :: lunit, jdate
482  integer my_lunit, my_jdate, lun, il, im, mtyp, mstb, inod, i4dy
483 
484  character*(*), intent(in) :: subset
485 
486  ! Check for I8 integers
487 
488  if(im8b) then
489  im8b=.false.
490 
491  call x84(lunit,my_lunit,1)
492  call x84(jdate,my_jdate,1)
493  call openmg(my_lunit,subset,my_jdate)
494 
495  im8b=.true.
496  return
497  endif
498 
499  ! Check the file status
500 
501  call status(lunit,lun,il,im)
502  if(il==0) call bort('BUFRLIB: OPENMG - OUTPUT BUFR FILE IS CLOSED, IT MUST BE OPEN FOR OUTPUT')
503  if(il<0) call bort('BUFRLIB: OPENMG - OUTPUT BUFR FILE IS OPEN FOR INPUT, IT MUST BE OPEN FOR OUTPUT')
504  if(im/=0) call closmg(lunit)
505  call wtstat(lunit,lun,il, 1)
506 
507  ! Get some subset particulars
508 
509  call nemtba(lun,subset,mtyp,mstb,inod)
510  inode(lun) = inod
511  idate(lun) = i4dy(jdate)
512 
513  ! Initialize the open message
514 
515  call msgini(lun)
516  call usrtpl(lun,1,1)
517 
518  return
519 end subroutine openmg
520 
537 recursive subroutine closmg(lunin)
538 
539  use modv_vars, only: im8b
540 
541  use moda_msgcwd
542  use moda_msglim
543  use moda_bitbuf
544 
545  implicit none
546 
547  integer, intent(in) :: lunin
548  integer my_lunin, lunit, lun, il, im
549 
550  ! Check for I8 integers
551 
552  if(im8b) then
553  im8b=.false.
554 
555  call x84(lunin,my_lunin,1)
556  call closmg(my_lunin)
557 
558  im8b=.true.
559  return
560  endif
561 
562  ! Check the file status
563 
564  lunit = abs(lunin)
565  call status(lunit,lun,il,im)
566  if(lunit/=lunin) msglim(lun) = 0
567  if(il==0) call bort('BUFRLIB: CLOSMG - OUTPUT BUFR FILE IS CLOSED, IT MUST BE OPEN FOR OUTPUT')
568  if(il<0) call bort('BUFRLIB: CLOSMG - OUTPUT BUFR FILE IS OPEN FOR INPUT, IT MUST BE OPEN FOR OUTPUT')
569  if(im/=0) then
570  if(nsub(lun)>0) then
571  call msgwrt(lunit,mbay(1,lun),mbyt(lun))
572  else if(nsub(lun)==0.and.nmsg(lun)<msglim(lun)) then
573  call msgwrt(lunit,mbay(1,lun),mbyt(lun))
574  else if(nsub(lun)<0) then
575  call wrcmps(-lunit)
576  endif
577  endif
578  call wtstat(lunit,lun,il,0)
579 
580  return
581 end subroutine closmg
582 
602 subroutine msgwrt(lunit,mesg,mgbyt)
603 
604  use bufrlib
605 
606  use modv_vars, only: mxmsgld4, iprt, nby5, bmostr, bmcstr
607 
608  use moda_nulbfr
609  use moda_bufrmg
610  use moda_mgwa
611  use moda_mgwb
612  use moda_s01cm
613  use moda_tnkrcp
614  use moda_msgstd
615 
616  implicit none
617 
618  integer, intent(in) :: lunit, mgbyt, mesg(*)
619  integer iec0(2), mbyt, ibit, kbit, ii, jj, len0, len1, len2, len3, len4, l5, iad4, iad5, lun, il, im, npbyt, mwrd, &
620  nmwrd, iupbs01, idxmsg
621 
622  character*128 errstr
623 
624  ! Make a local copy of the input message for use within this subroutine, since internal calls to any or all of the
625  ! subroutines stndrd(), cnved4(), pkbs1(), atrcpt(), etc. may end up modifying the message before it finally gets
626  ! written out to lunit.
627 
628  mbyt = mgbyt
629 
630  iec0(1) = mesg(1)
631  iec0(2) = mesg(2)
632  ibit = 32
633  call pkb(mbyt,24,iec0,ibit)
634 
635  do ii = 1, nmwrd(iec0)
636  mgwa(ii) = mesg(ii)
637  enddo
638 
639  ! Overwrite any values within Section 0 or Section 1 that were requested via previous calls to pkvs01(). If a request
640  ! was made to change the BUFR edition number to 4, then actually convert the message as well.
641 
642  if(ns01v>0) then
643  do jj=1,ns01v
644  if(cmnem(jj)=='BEN') then
645  if(ivmnem(jj)==4) then
646  ! Install Section 0 byte count for use by cnved4()
647  ibit = 32
648  call pkb(mbyt,24,mgwa,ibit)
649  call cnved4(mgwa,mxmsgld4,mgwb)
650  ! Compute mbyt for the new edition 4 message
651  mbyt = iupbs01(mgwb,'LENM')
652  ! Copy the mgwb array back into mgwa
653  do ii = 1, nmwrd(mgwb)
654  mgwa(ii) = mgwb(ii)
655  enddo
656  endif
657  else
658  ! Overwrite the requested value
659  call pkbs1(ivmnem(jj),mgwa,cmnem(jj))
660  endif
661  enddo
662  endif
663 
664  ! Standardize the message if requested via module @ref moda_msgstd. However, we don't want to do this if the message
665  ! contains DX BUFR table information, because in that case it's already standard.
666 
667  if ( ( csmf=='Y' ) .and. ( idxmsg(mgwa)/=1 ) ) then
668  ! Install Section 0 byte count and Section 5 '7777' into the original message. This is necessary because
669  ! subroutine stndrd() requires a complete and well-formed BUFR message as its input.
670  ibit = 32
671  call pkb(mbyt,24,mgwa,ibit)
672  ibit = (mbyt-4)*8
673  call pkc(bmcstr,nby5,mgwa,ibit)
674  call stndrd(lunit,mgwa,mxmsgld4,mgwb)
675  ! Compute mbyt for the new standardized message
676  mbyt = iupbs01(mgwb,'LENM')
677  ! Copy the mgwb array back into mgwa
678  do ii = 1, nmwrd(mgwb)
679  mgwa(ii) = mgwb(ii)
680  enddo
681  endif
682 
683  ! Append the tank receipt time to Section 1 if requested via module @ref moda_tnkrcp, unless the message contains
684  ! DX BUFR table information.
685 
686  if ( ( ctrt=='Y' ) .and. ( idxmsg(mgwa)/=1 ) ) then
687  ! Install Section 0 byte count for use by subroutine atrcpt()
688  ibit = 32
689  call pkb(mbyt,24,mgwa,ibit)
690  call atrcpt(mgwa,mxmsgld4,mgwb)
691  ! Compute mbyt for the revised message
692  mbyt = iupbs01(mgwb,'LENM')
693  ! Copy the mgwb array back into mgwa
694  do ii = 1, nmwrd(mgwb)
695  mgwa(ii) = mgwb(ii)
696  enddo
697  endif
698 
699  ! Get the section lengths.
700 
701  call getlens(mgwa,4,len0,len1,len2,len3,len4,l5)
702 
703  ! Depending on the edition number of the message, we need to ensure that each section within the message has an even
704  ! number of bytes.
705 
706  if(iupbs01(mgwa,'BEN')<4) then
707  if(mod(len1,2)/=0) call bort ('BUFRLIB: MSGWRT - LENGTH OF SECTION 1 IS NOT A MULTIPLE OF 2')
708  if(mod(len2,2)/=0) call bort ('BUFRLIB: MSGWRT - LENGTH OF SECTION 2 IS NOT A MULTIPLE OF 2')
709  if(mod(len3,2)/=0) call bort ('BUFRLIB: MSGWRT - LENGTH OF SECTION 3 IS NOT A MULTIPLE OF 2')
710  if(mod(len4,2)/=0) then
711  ! Pad Section 4 with an additional byte that is zeroed out
712  iad4 = len0+len1+len2+len3
713  iad5 = iad4+len4
714  ibit = iad4*8
715  len4 = len4+1
716  call pkb(len4,24,mgwa,ibit)
717  ibit = iad5*8
718  call pkb(0,8,mgwa,ibit)
719  mbyt = mbyt+1
720  endif
721  endif
722 
723  ! Write Section 0 byte count and Section 5
724 
725  ibit = 0
726  call pkc(bmostr, 4,mgwa,ibit)
727  call pkb(mbyt,24,mgwa,ibit)
728 
729  kbit = (mbyt-4)*8
730  call pkc(bmcstr,nby5,mgwa,kbit)
731 
732  ! Zero out the extra bytes which will be written. Note that the BUFR message is stored within the integer array mgwa(*),
733  ! (rather than within a character array), so we need to make sure that the "7777" Is followed by zeroed-out bytes up to
734  ! the boundary of the last machine word that will be written out.
735 
736  call padmsg(mgwa,mxmsgld4,npbyt)
737 
738  ! Write the message plus padding to a word boundary if null(lun) = 0
739 
740  mwrd = nmwrd(mgwa)
741  call status(lunit,lun,il,im)
742  if(null(lun)==0) then
743  call blocks(mgwa,mwrd)
744  call cwrbufr_c(lun,mgwa,mwrd)
745  endif
746 
747  if(iprt>=2) then
748  call errwrt('++++++++++++++BUFR ARCHIVE LIBRARY+++++++++++++++++')
749  write ( unit=errstr, fmt='(A,I4,A,I7)') 'BUFRLIB: MSGWRT: LUNIT =', lunit, ', BYTES =', mbyt+npbyt
750  call errwrt(errstr)
751  call errwrt('++++++++++++++BUFR ARCHIVE LIBRARY+++++++++++++++++')
752  call errwrt(' ')
753  endif
754 
755  ! Save a memory copy of this message, unless it's a DX message.
756 
757  if(idxmsg(mgwa)/=1) then
758  ! Store a copy of this message within module @ref moda_bufrmg, for possible later retrieval during a future call to
759  ! subroutine writsa()
760  msglen(lun) = mwrd
761  do ii=1,msglen(lun)
762  msgtxt(ii,lun) = mgwa(ii)
763  enddo
764  endif
765 
766  return
767 end subroutine msgwrt
768 
776 subroutine msgini(lun)
777 
778  use modv_vars, only: mtv, nby0, nby1, nby2, nby3, nby5, bmostr, bmcstr, fxy_fbit, fxy_sbyct, fxy_drf8
779 
780  use moda_msgcwd
781  use moda_ufbcpl
782  use moda_bitbuf
783  use moda_tables
784 
785  implicit none
786 
787  integer, intent(in) :: lun
788  integer nby4, nbyt, mtyp, msbt, inod, isub, iret, mcen, mear, mmon, mday, mour, mmin, mbit, ifxy
789 
790  character*128 bort_str
791  character*8 subtag
792  character tab
793 
794  ! Get the message tag and type, and break up the date
795 
796  subtag = tag(inode(lun))(1:8)
797  call nemtba(lun,subtag,mtyp,msbt,inod)
798  if(inode(lun)/=inod) then
799  write(bort_str,'("BUFRLIB: MSGINI - MISMATCH BETWEEN INODE (=",I7,") & POSITIONAL INDEX, INOD (",I7,") '// &
800  'OF SUBTAG (",A,") IN DICTIONARY")') inode(lun), inod, subtag
801  call bort(bort_str)
802  endif
803  call nemtab(lun,subtag,isub,tab,iret)
804  if(iret==0) then
805  write(bort_str,'("BUFRLIB: MSGINI - TABLE A MESSAGE TYPE MNEMONIC ",A," NOT FOUND IN INTERNAL TABLE D ARRAYS")') subtag
806  call bort(bort_str)
807  endif
808 
809  ! Date can be YYMMDDHH or YYYYMMDDHH
810 
811  mcen = mod(idate(lun)/10**8,100)+1
812  mear = mod(idate(lun)/10**6,100)
813  mmon = mod(idate(lun)/10**4,100)
814  mday = mod(idate(lun)/10**2,100)
815  mour = mod(idate(lun) ,100)
816  mmin = 0
817 
818  if(mcen==1) call bort ('BUFRLIB: MSGINI - BUFR MESSAGE DATE (IDATE) is 0000000000')
819 
820  if(mear==0) mcen = mcen-1
821  if(mear==0) mear = 100
822 
823  ! Initialize the message
824 
825  mbit = 0
826  nby4 = 4
827  nbyt = nby0+nby1+nby2+nby3+nby4+nby5
828 
829  ! Section 0
830 
831  call pkc(bmostr, 4 , mbay(1,lun),mbit)
832  call pkb(nbyt , 24 , mbay(1,lun),mbit)
833  call pkb( 3 , 8 , mbay(1,lun),mbit)
834 
835  ! Section 1
836 
837  call pkb(nby1 , 24 , mbay(1,lun),mbit)
838  call pkb( 0 , 8 , mbay(1,lun),mbit)
839  call pkb( 3 , 8 , mbay(1,lun),mbit)
840  call pkb( 7 , 8 , mbay(1,lun),mbit)
841  call pkb( 0 , 8 , mbay(1,lun),mbit)
842  call pkb( 0 , 8 , mbay(1,lun),mbit)
843  call pkb(mtyp , 8 , mbay(1,lun),mbit)
844  call pkb(msbt , 8 , mbay(1,lun),mbit)
845  call pkb( mtv , 8 , mbay(1,lun),mbit)
846  call pkb( 0 , 8 , mbay(1,lun),mbit)
847  call pkb(mear , 8 , mbay(1,lun),mbit)
848  call pkb(mmon , 8 , mbay(1,lun),mbit)
849  call pkb(mday , 8 , mbay(1,lun),mbit)
850  call pkb(mour , 8 , mbay(1,lun),mbit)
851  call pkb(mmin , 8 , mbay(1,lun),mbit)
852  call pkb(mcen , 8 , mbay(1,lun),mbit)
853 
854  ! Section 3
855 
856  call pkb(nby3 , 24 , mbay(1,lun),mbit)
857  call pkb( 0 , 8 , mbay(1,lun),mbit)
858  call pkb( 0 , 16 , mbay(1,lun),mbit)
859  call pkb(2**7 , 8 , mbay(1,lun),mbit)
860  call pkb(ifxy(fxy_sbyct), 16, mbay(1,lun),mbit)
861  call pkb(isub , 16 , mbay(1,lun),mbit)
862  call pkb(ifxy('102000') , 16, mbay(1,lun),mbit)
863  call pkb(ifxy(fxy_drf8) , 16, mbay(1,lun),mbit)
864  call pkb(ifxy('206001') , 16, mbay(1,lun),mbit)
865  call pkb(ifxy(fxy_fbit), 16, mbay(1,lun),mbit)
866  call pkb( 0 , 8 , mbay(1,lun),mbit)
867 
868  ! Section 4
869 
870  call pkb(nby4 , 24 , mbay(1,lun),mbit)
871  call pkb( 0 , 8 , mbay(1,lun),mbit)
872 
873  ! Section 5
874 
875  call pkc(bmcstr,nby5, mbay(1,lun),mbit)
876 
877  ! Double check initial message length
878 
879  if(mod(mbit,8)/=0) call bort('BUFRLIB: MSGINI - INITIALIZED MESSAGE DOES NOT END ON A BYTE BOUNDARY')
880  if(mbit/8/=nbyt) then
881  write(bort_str,'("BUFRLIB: MSGINI - NUMBER OF BYTES STORED FOR INITIALIZED MESSAGE (",I6,") IS NOT THE SAME AS FIRST '// &
882  'CALCULATED, NBYT (",I6)') mbit/8, nbyt
883  call bort(bort_str)
884  endif
885 
886  nmsg(lun) = nmsg(lun)+1
887  nsub(lun) = 0
888  mbyt(lun) = nbyt
889 
890  luncpy(lun)=0
891 
892  return
893 end subroutine msgini
894 
905 logical function msgfull(msiz,itoadd,mxsiz) result(bool)
906 
907  use modv_vars, only: maxnc
908 
909  use moda_tnkrcp
910  use moda_msgstd
911 
912  implicit none
913 
914  integer, intent(in) :: msiz, itoadd, mxsiz
915  integer iwgbyt
916 
917  ! Allow for at least 11 additional bytes of "wiggle room" in the message, because subroutine msgwrt() may do any or all
918  ! of the following:
919  ! 3 bytes may be added by a call to subroutine cnved4()
920  ! + 1 byte (at most) of padding may be added to Section 4
921  ! + 7 bytes (at most) of padding may be added up to the next word boundary after Section 5
922  ! ----
923  ! 11
924  iwgbyt = 11
925 
926  ! But subroutine msgwrt() may also do any of all of the following:
927 
928  ! 6 bytes may be added by a call to subroutine atrcpt()
929  if(ctrt=='Y') iwgbyt = iwgbyt + 6
930 
931  ! (maxnc*2) bytes (at most) may be added by a call to subroutine stndrd()
932  if(csmf=='Y') iwgbyt = iwgbyt + (maxnc*2)
933 
934  ! Determine whether the subset will fit.
935 
936  if ( ( msiz + itoadd + iwgbyt ) > mxsiz ) then
937  bool = .true.
938  else
939  bool = .false.
940  endif
941 
942  return
943 end function msgfull
944 
962 recursive subroutine maxout(maxo)
963 
964  use modv_vars, only: mxmsgl, im8b, iprt
965 
966  use moda_bitbuf
967 
968  implicit none
969 
970  integer, intent(in) :: maxo
971  integer my_maxo, newsiz, nxstr, ldxa, ldxb, ldxd, ld30
972 
973  character*128 errstr
974  character*56 dxstr
975 
976  common /dxtab/ nxstr(10), ldxa(10), ldxb(10), ldxd(10), ld30(10), dxstr(10)
977 
978  ! Check for I8 integers
979 
980  if(im8b) then
981  im8b=.false.
982 
983  call x84(maxo,my_maxo,1)
984  call maxout(my_maxo)
985 
986  im8b=.true.
987  return
988  endif
989 
990  if((maxo==0).or.(maxo>mxmsgl)) then
991  newsiz = mxmsgl
992  else
993  newsiz = maxo
994  endif
995 
996  if(iprt>=0) then
997  if(maxbyt/=newsiz) then
998  call errwrt('++++++++++++++BUFR ARCHIVE LIBRARY+++++++++++++++++')
999  write ( unit=errstr, fmt='(A,A,I7,A,I7)' ) 'BUFRLIB: MAXOUT - THE RECORD LENGTH OF ALL BUFR MESSAGES ',&
1000  'CREATED FROM THIS POINT ON IS BEING CHANGED FROM ', maxbyt, ' TO ', newsiz
1001  call errwrt(errstr)
1002  call errwrt('++++++++++++++BUFR ARCHIVE LIBRARY+++++++++++++++++')
1003  call errwrt(' ')
1004  endif
1005  endif
1006 
1007  maxbyt = newsiz
1008 
1009  return
1010 end subroutine maxout
1011 
1020 integer function igetmxby() result(iret)
1021 
1022  use moda_bitbuf
1023 
1024  implicit none
1025 
1026  iret = maxbyt
1027 
1028  return
1029 end function igetmxby
1030 
1041 subroutine padmsg(mesg,lmesg,npbyt)
1042 
1043  use modv_vars, only: nbytw
1044 
1045  implicit none
1046 
1047  integer, intent(in) :: lmesg
1048  integer, intent(inout) :: mesg(*)
1049  integer, intent(out) :: npbyt
1050  integer nmw, nmb, ibit, i, nmwrd, iupbs01
1051 
1052  ! Make sure that the array is big enough to hold the additional byte padding that will be appended to the
1053  ! end of the message.
1054 
1055  nmw = nmwrd(mesg)
1056  if(nmw>lmesg) call bort('BUFRLIB: PADMSG - CANNOT ADD PADDING TO MESSAGE ARRAY; TRY A LARGER DIMENSION FOR THIS ARRAY')
1057 
1058  ! Pad from the end of the message up to the next 8-byte boundary.
1059 
1060  nmb = iupbs01(mesg,'LENM')
1061  ibit = nmb*8
1062  npbyt = ( nmw * nbytw ) - nmb
1063  do i = 1, npbyt
1064  call pkb(0,8,mesg,ibit)
1065  enddo
1066 
1067  return
1068 end subroutine padmsg
1069 
1080 recursive integer function nmsub(lunit) result(iret)
1081 
1082  use modv_vars, only: im8b
1083 
1084  use moda_msgcwd
1085 
1086  implicit none
1087 
1088  integer, intent(in) :: lunit
1089  integer my_lunit, lun, il, im
1090 
1091  ! Check for I8 integers
1092 
1093  if(im8b) then
1094  im8b=.false.
1095 
1096  call x84(lunit,my_lunit,1)
1097  iret=nmsub(my_lunit)
1098 
1099  im8b=.true.
1100  return
1101  endif
1102 
1103  iret = 0
1104 
1105  ! Check the file status
1106 
1107  call status(lunit,lun,il,im)
1108  if(il==0) call bort('BUFRLIB: NMSUB - INPUT BUFR FILE IS CLOSED, IT MUST BE OPEN FOR INPUT')
1109  if(il>0) call bort('BUFRLIB: NMSUB - INPUT BUFR FILE IS OPEN FOR OUTPUT, IT MUST BE OPEN FOR INPUT')
1110  if(im==0) call bort('BUFRLIB: NMSUB - A MESSAGE MUST BE OPEN IN INPUT BUFR FILE, NONE ARE')
1111 
1112  iret = msub(lun)
1113 
1114  return
1115 end function nmsub
1116 
1130 integer function nmwrd(mbay) result(iret)
1131 
1132  use modv_vars, only: nbytw
1133 
1134  implicit none
1135 
1136  integer, intent(in) :: mbay(*)
1137  integer lenm, iupbs01
1138 
1139  lenm = iupbs01(mbay,'LENM')
1140  if(lenm==0) then
1141  iret = 0
1142  else
1143  iret = ((lenm/8)+1)*(8/nbytw)
1144  endif
1145 
1146  return
1147 end function nmwrd
1148 
1162 integer function lmsg(sec0) result(iret)
1163 
1164  implicit none
1165 
1166  integer msec0(2), nmwrd
1167 
1168  character*8, intent(in) :: sec0
1169  character*8 csec0
1170 
1171  equivalence(msec0,csec0)
1172 
1173  csec0 = sec0
1174  iret = nmwrd(msec0)
1175 
1176  return
1177 end function lmsg
1178 
1198 recursive subroutine getlens (mbay,ll,len0,len1,len2,len3,len4,len5)
1199 
1200  use modv_vars, only: im8b, nby5
1201 
1202  implicit none
1203 
1204  integer, intent(in) :: mbay(*), ll
1205  integer, intent(out) :: len0, len1, len2, len3, len4, len5
1206  integer my_ll, iad2, iad3, iad4, iupbs01, iupb
1207 
1208  ! Check for I8 integers.
1209  if(im8b) then
1210  im8b=.false.
1211  call x84(ll,my_ll,1)
1212  call getlens(mbay,my_ll,len0,len1,len2,len3,len4,len5)
1213  call x48(len0,len0,1)
1214  call x48(len1,len1,1)
1215  call x48(len2,len2,1)
1216  call x48(len3,len3,1)
1217  call x48(len4,len4,1)
1218  call x48(len5,len5,1)
1219  im8b=.true.
1220  return
1221  endif
1222 
1223  len0 = -1
1224  len1 = -1
1225  len2 = -1
1226  len3 = -1
1227  len4 = -1
1228  len5 = -1
1229 
1230  if(ll<0) return
1231  len0 = iupbs01(mbay,'LEN0')
1232 
1233  if(ll<1) return
1234  len1 = iupbs01(mbay,'LEN1')
1235 
1236  if(ll<2) return
1237  iad2 = len0 + len1
1238  len2 = iupb(mbay,iad2+1,24) * iupbs01(mbay,'ISC2')
1239 
1240  if(ll<3) return
1241  iad3 = iad2 + len2
1242  len3 = iupb(mbay,iad3+1,24)
1243 
1244  if(ll<4) return
1245  iad4 = iad3 + len3
1246  len4 = iupb(mbay,iad4+1,24)
1247 
1248  if(ll<5) return
1249  len5 = nby5
1250 
1251  return
1252 end subroutine getlens
1253 
1278 recursive subroutine cnved4(msgin,lmsgot,msgot)
1279 
1280  use modv_vars, only: im8b, nbytw
1281 
1282  implicit none
1283 
1284  integer, intent(in) :: msgin(*), lmsgot
1285  integer, intent(out) :: msgot(*)
1286  integer my_lmsgot, i, nmw, len0, len1, len2, len3, l4, l5, iad2, iad4, lenm, lenmot, len1ot, len3ot, ibit, iupbs01, nmwrd
1287 
1288  ! Check for I8 integers.
1289 
1290  if(im8b) then
1291  im8b=.false.
1292  call x84 ( lmsgot, my_lmsgot, 1 )
1293  call cnved4 ( msgin, my_lmsgot*2, msgot )
1294  im8b=.true.
1295  return
1296  endif
1297 
1298  if(iupbs01(msgin,'BEN')==4) then
1299 
1300  ! The input message is already encoded using edition 4, so just copy it from msgin to msgot and then return.
1301 
1302  nmw = nmwrd(msgin)
1303  if(nmw>lmsgot) &
1304  call bort('BUFRLIB: CNVED4 - OVERFLOW OF OUTPUT (EDITION 4) MESSAGE ARRAY; TRY A LARGER DIMENSION FOR THIS ARRAY')
1305  do i = 1, nmw
1306  msgot(i) = msgin(i)
1307  enddo
1308  return
1309  endif
1310 
1311  ! Get some section lengths and addresses from the input message.
1312 
1313  call getlens(msgin,3,len0,len1,len2,len3,l4,l5)
1314 
1315  iad2 = len0 + len1
1316  iad4 = iad2 + len2 + len3
1317 
1318  lenm = iupbs01(msgin,'LENM')
1319 
1320  ! Check for overflow of the output array. Note that the new edition 4 message will be a total of 3 bytes longer than the
1321  ! input message (i.e. 4 more bytes in Section 1, but 1 fewer byte in Section 3).
1322 
1323  lenmot = lenm + 3
1324  if(lenmot>(lmsgot*nbytw)) &
1325  call bort('BUFRLIB: CNVED4 - OVERFLOW OF OUTPUT (EDITION 4) MESSAGE ARRAY; TRY A LARGER DIMENSION FOR THIS ARRAY')
1326 
1327  len1ot = len1 + 4
1328  len3ot = len3 - 1
1329 
1330  ! Write Section 0 of the new message into the output array.
1331 
1332  call mvb ( msgin, 1, msgot, 1, 4 )
1333  ibit = 32
1334  call pkb ( lenmot, 24, msgot, ibit )
1335  call pkb ( 4, 8, msgot, ibit )
1336 
1337  ! Write Section 1 of the new message into the output array.
1338 
1339  call pkb ( len1ot, 24, msgot, ibit )
1340  call pkb ( iupbs01(msgin,'BMT'), 8, msgot, ibit )
1341  call pkb ( iupbs01(msgin,'OGCE'), 16, msgot, ibit )
1342  call pkb ( iupbs01(msgin,'GSES'), 16, msgot, ibit )
1343  call pkb ( iupbs01(msgin,'USN'), 8, msgot, ibit )
1344  call pkb ( iupbs01(msgin,'ISC2')*128, 8, msgot, ibit )
1345  call pkb ( iupbs01(msgin,'MTYP'), 8, msgot, ibit )
1346  ! Set a default of 255 for the international subcategory.
1347  call pkb ( 255, 8, msgot, ibit )
1348  call pkb ( iupbs01(msgin,'MSBT'), 8, msgot, ibit )
1349  call pkb ( iupbs01(msgin,'MTV'), 8, msgot, ibit )
1350  call pkb ( iupbs01(msgin,'MTVL'), 8, msgot, ibit )
1351  call pkb ( iupbs01(msgin,'YEAR'), 16, msgot, ibit )
1352  call pkb ( iupbs01(msgin,'MNTH'), 8, msgot, ibit )
1353  call pkb ( iupbs01(msgin,'DAYS'), 8, msgot, ibit )
1354  call pkb ( iupbs01(msgin,'HOUR'), 8, msgot, ibit )
1355  call pkb ( iupbs01(msgin,'MINU'), 8, msgot, ibit )
1356  ! Set a default of 0 for the second.
1357  call pkb ( 0, 8, msgot, ibit )
1358 
1359  ! Copy Section 2 (if it exists) through the next-to-last byte of Section 3 from the input array to the output array.
1360 
1361  call mvb ( msgin, iad2+1, msgot, (ibit/8)+1, len2+len3-1 )
1362 
1363  ! Store the length of the new Section 3.
1364 
1365  ibit = ( len0 + len1ot + len2 ) * 8
1366  call pkb ( len3ot, 24, msgot, ibit )
1367 
1368  ! Copy Section 4 and Section 5 from the input array to the output array.
1369 
1370  ibit = ibit + ( len3ot * 8 ) - 24
1371  call mvb ( msgin, iad4+1, msgot, (ibit/8)+1, lenm-iad4 )
1372 
1373  return
1374 end subroutine cnved4
1375 
1387 recursive integer function ifbget(lunit) result(iret)
1388 
1389  use modv_vars, only: im8b
1390 
1391  use moda_msgcwd
1392 
1393  implicit none
1394 
1395  integer, intent(in) :: lunit
1396  integer my_lunit, lun, il, im
1397 
1398  ! Check for I8 integers
1399 
1400  if(im8b) then
1401  im8b=.false.
1402  call x84(lunit,my_lunit,1)
1403  iret=ifbget(my_lunit)
1404  im8b=.true.
1405  return
1406  endif
1407 
1408  iret = -1
1409 
1410  ! Make sure a file/message is open for input
1411 
1412  call status(lunit,lun,il,im)
1413  if(il==0) call bort('BUFRLIB: IFBGET - INPUT BUFR FILE IS CLOSED, IT MUST BE OPEN FOR INPUT')
1414  if(il>0) call bort('BUFRLIB: IFBGET - INPUT BUFR FILE IS OPEN FOR OUTPUT, IT MUST BE OPEN FOR INPUT')
1415  if(im==0) call bort('BUFRLIB: IFBGET - A MESSAGE MUST BE OPEN IN INPUT BUFR FILE, NONE ARE')
1416 
1417  ! Check if there's another subset in the message
1418 
1419  if(nsub(lun)<msub(lun)) iret = 0
1420 
1421  return
1422 end function ifbget
subroutine blocks(mbay, mwrd)
Encapsulate a BUFR message with IEEE Fortran control words as specified via the most recent call to s...
Definition: blocks.F90:37
recursive subroutine bort(str)
Log an error message, then either return to or abort the application program.
Definition: borts.F90:15
recursive integer function iupb(mbay, nbyt, nbit)
Decode an integer value from within a specified number of bits of an integer array,...
Definition: cidecode.F90:226
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
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 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 stbfdx(lun, mesg)
Copy a DX BUFR tables message into the internal memory arrays in module moda_tababd.
Definition: dxtable.F90:979
subroutine dxinit(lun, ioi)
Clear out the internal arrays (in module moda_tababd) holding the DX BUFR table, then optionally init...
Definition: dxtable.F90:604
integer function idxmsg(mesg)
Check whether a BUFR message contains DX BUFR tables information that was generated by the NCEPLIBS-b...
Definition: dxtable.F90:1112
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 nemtab(lun, nemo, idn, tab, iret)
Get information about a descriptor, based on a mnemonic.
Definition: fxy.F90:434
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 mbay
Current BUFR message for each file ID.
integer, dimension(:), allocatable mbyt
Length (in bytes) of current BUFR message for each file ID.
integer maxbyt
Maximum length of an output BUFR message.
Declare variables used to optionally catch and return any future bort error string to the application...
integer caught_str_len
Length of bort error string.
logical bort_target_is_unset
.true.
Declare arrays used to store, for each output file ID, a copy of the BUFR message that was most recen...
integer, dimension(:), allocatable msglen
Length (in integers) of BUFR message most recently written to each output file ID.
integer, dimension(:,:), allocatable msgtxt
BUFR message most recently written to each output file ID.
Declare an array used by subroutine readerme() to read in a new DX dictionary table as a consecutive ...
integer, dimension(:), allocatable idrdm
DX BUFR tables message count for each file ID.
Declare an array used by various subroutines and functions to hold a temporary working copy of a BUFR...
integer, dimension(:), allocatable mgwa
Temporary working copy of BUFR message.
Declare an array used by various subroutines and functions to hold a temporary working copy of a BUFR...
integer, dimension(:), allocatable mgwb
Temporary working copy of BUFR message.
Declare arrays used to store information about the current BUFR message that is in the process of bei...
integer, dimension(:), allocatable inode
Table A mnemonic for type of BUFR message.
integer, dimension(:), allocatable idate
Section 1 date-time of message.
integer, dimension(:), allocatable nmsg
Current message pointer within logical unit.
integer, dimension(:), allocatable msub
Total number of data subsets in message.
integer, dimension(:), allocatable nsub
Current subset pointer within message.
Declare an array used to keep track of which logical units should not have any empty (zero data subse...
integer, dimension(:), allocatable msglim
Tracking index for each file ID.
Declare a variable used to indicate whether output BUFR messages should be standardized.
character csmf
Flag indicating whether BUFR output messages are to be standardized; this variable is initialized to ...
Declare an array used to store a switch for each file ID, indicating whether any BUFR messages should...
integer, dimension(:), allocatable null
Output switch for each file ID:
Declare arrays and variables used to store custom values for certain mnemonics within Sections 0 and ...
integer, dimension(:), allocatable ivmnem
Custom values for use within Sections 0 and 1 of all future output BUFR messages written to all Fortr...
integer ns01v
Number of custom values stored.
character *8, dimension(:), allocatable cmnem
Section 0 and 1 mnemonics corresponding to ivmnem.
Declare an array used to store a switch for each file ID, indicating whether BUFR messages read from ...
integer, dimension(:), allocatable isc3
Section 3 switch for each file ID:
Declare arrays and variables used to store the internal jump/link table.
character *10, dimension(:), allocatable tag
Mnemonics in the jump/link table.
Declare variables used to store tank receipt time information within Section 1 of BUFR messages.
character ctrt
Flag indicating whether tank receipt times are to be included within output BUFR messages; this varia...
Declare an array used to store, for each file ID, the logical unit number corresponding to a separate...
integer, dimension(:), allocatable luncpy
Logical unit numbers used to copy long character strings between BUFR data subsets.
recursive subroutine status(lunit, lun, il, im)
Check whether a specified Fortran logical unit number is currently connected to the NCEPLIBS-bufr sof...
subroutine wtstat(lunit, lun, il, im)
Update file status in library internals.
subroutine padmsg(mesg, lmesg, npbyt)
Pad a BUFR message with zeroed-out bytes from the end of the message up to the next 8-byte boundary.
recursive subroutine maxout(maxo)
Specify the maximum length of a BUFR message that can be written to any output file by the NCEPLIBS-b...
integer function lmsg(sec0)
Given a character string containing Section 0 from a BUFR message, determine the array size (in integ...
logical function msgfull(msiz, itoadd, mxsiz)
Check whether the current data subset in the internal arrays will fit within the current BUFR message...
recursive subroutine openmg(lunit, subset, jdate)
Open and initialize a new BUFR message within internal arrays, for eventual output to logical unit lu...
recursive subroutine openmb(lunit, subset, jdate)
Open and initialize a new BUFR message within internal arrays, for eventual output to logical unit lu...
recursive subroutine closmg(lunin)
Close the BUFR message that is currently open for writing within internal arrays associated with logi...
recursive integer function nmsub(lunit)
Get the total number of data subsets available within the BUFR message that was most recently opened ...
integer function nmwrd(mbay)
Given an integer array containing Section 0 from a BUFR message, determine the array size (in integer...
integer function igetmxby()
Get the maximum length of a BUFR message that can be written to an output file by the NCEPLIBS-bufr s...
recursive subroutine readerme(mesg, lunit, subset, jdate, iret)
Read a BUFR message from a memory array.
recursive subroutine readmg(lunxx, subset, jdate, iret)
Read the next BUFR message from logical unit abs(lunxx) into internal arrays.
Definition: readwritemg.F90:44
recursive subroutine getlens(mbay, ll, len0, len1, len2, len3, len4, len5)
Read the section lengths of a BUFR message, up to a specified point in the message.
recursive integer function ifbget(lunit)
Check whether there are any more data subsets available to be read from a BUFR message.
subroutine rdmsgw(lunit, mesg, iret)
Read the next BUFR message from logical unit lunit as an array of integer words.
recursive subroutine cnved4(msgin, lmsgot, msgot)
Convert a BUFR edition 3 message to BUFR edition 4.
recursive integer function ireadmg(lunit, subset, idate)
Call subroutine readmg() and pass back its return code as the function value.
subroutine msgini(lun)
Initialize, within the internal arrays, a new uncompressed BUFR message for output.
subroutine msgwrt(lunit, mesg, mgbyt)
Perform final checks and updates on a BUFR message before writing it to a specified Fortran logical u...
subroutine usrtpl(lun, invn, nbmp)
Expand a subset template within internal arrays.
subroutine cktaba(lun, subset, jdate, iret)
Get the Table A mnemonic from Sections 1 and 3 of a BUFR message.
Definition: s013vals.F90:1264
recursive integer function iupbs01(mbay, s01mnem)
Read a specified value from within Section 0 or Section 1 of a BUFR message.
Definition: s013vals.F90:247
recursive subroutine pkbs1(ival, mbay, s1mnem)
Write a specified value into a specified location within Section 1 of a BUFR message,...
Definition: s013vals.F90:520
recursive integer function iupbs3(mbay, s3mnem)
Read a specified value from within Section 3 of a BUFR message.
Definition: s013vals.F90:348
subroutine reads3(lun)
Read the Section 3 descriptors from the BUFR message in mbay(1,lun), then use the BUFR master tables ...
Definition: s013vals.F90:685
recursive integer function i4dy(idate)
Convert a date-time with a 2-digit year (YYMMDDHH) to a date-time with a 4-digit year (YYYYMMDDHH) us...
Definition: s013vals.F90:1064
recursive subroutine stndrd(lunit, msgin, lmsgot, msgot)
Standardize a BUFR message.
Definition: standard.F90:75
recursive subroutine atrcpt(msgin, lmsgot, msgot)
Read an input message and output an equivalent BUFR message with a tank receipt time added to Section...
Definition: tankrcpt.F90:24
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