NCEPLIBS-bufr  12.2.0
s013vals.F90
Go to the documentation of this file.
1 
5 
47 recursive subroutine gets1loc(s1mnem,iben,isbyt,iwid,iret)
48 
49  use modv_vars, only: im8b
50 
51  implicit none
52 
53  character*(*), intent(in) :: s1mnem
54 
55  integer, intent(in) :: iben
56  integer, intent(out) :: isbyt, iwid, iret
57  integer my_iben
58 
59  ! Check for I8 integers.
60 
61  if(im8b) then
62  im8b=.false.
63 
64  call x84(iben,my_iben,1)
65  call gets1loc(s1mnem,my_iben,isbyt,iwid,iret)
66  call x48(isbyt,isbyt,1)
67  call x48(iwid,iwid,1)
68  call x48(iret,iret,1)
69 
70  im8b=.true.
71  return
72  endif
73 
74  iret = 0
75  iwid = 8
76 
77  if(s1mnem=='LEN1') then
78  isbyt = 1
79  iwid = 24
80  else if(s1mnem=='BMT') then
81  isbyt = 4
82  else if(s1mnem=='OGCE') then
83  if(iben==3) then
84  isbyt = 6
85  else
86  ! Note that this location is actually the same for both edition 2 and edition 4 of BUFR
87  isbyt = 5
88  iwid = 16
89  endif
90  else if(s1mnem=='GSES') then
91  if(iben==3) then
92  isbyt = 5
93  else if(iben==4) then
94  isbyt = 7
95  iwid = 16
96  else
97  iret = -1
98  endif
99  else if(s1mnem=='USN') then
100  if(iben==4) then
101  isbyt = 9
102  else
103  isbyt = 7
104  endif
105  else if(s1mnem=='ISC2') then
106  iwid = 1
107  if(iben==4) then
108  isbyt = 10
109  else
110  isbyt = 8
111  endif
112  else if(s1mnem=='MTYP') then
113  if(iben==4) then
114  isbyt = 11
115  else
116  isbyt = 9
117  endif
118  else if(s1mnem=='MSBTI') then
119  if(iben==4) then
120  isbyt = 12
121  else
122  iret = -1
123  endif
124  else if(s1mnem=='MSBT') then
125  if(iben==4) then
126  isbyt = 13
127  else
128  isbyt = 10
129  endif
130  else if(s1mnem=='MTV') then
131  if(iben==4) then
132  isbyt = 14
133  else
134  isbyt = 11
135  endif
136  else if(s1mnem=='MTVL') then
137  if(iben==4) then
138  isbyt = 15
139  else
140  isbyt = 12
141  endif
142  else if(s1mnem=='YEAR') then
143  if(iben==4) then
144  isbyt = 16
145  iwid = 16
146  else
147  iret = -1
148  endif
149  else if(s1mnem=='YCEN') then
150  if(iben<4) then
151  isbyt = 13
152  else
153  iret = -1
154  endif
155  else if(s1mnem=='CENT') then
156  if(iben<4) then
157  isbyt = 18
158  else
159  iret = -1
160  endif
161  else if(s1mnem=='MNTH') then
162  if(iben==4) then
163  isbyt = 18
164  else
165  isbyt = 14
166  endif
167  else if(s1mnem=='DAYS') then
168  if(iben==4) then
169  isbyt = 19
170  else
171  isbyt = 15
172  endif
173  else if(s1mnem=='HOUR') then
174  if(iben==4) then
175  isbyt = 20
176  else
177  isbyt = 16
178  endif
179  else if(s1mnem=='MINU') then
180  if(iben==4) then
181  isbyt = 21
182  else
183  isbyt = 17
184  endif
185  else if(s1mnem=='SECO') then
186  if(iben==4) then
187  isbyt = 22
188  else
189  iret = -1
190  endif
191  else
192  iret = -1
193  endif
194 
195  return
196 end subroutine gets1loc
197 
246 recursive integer function iupbs01(mbay,s01mnem) result(iret)
247 
248  use modv_vars, only: im8b, nby0
249 
250  implicit none
251 
252  character*(*), intent(in) :: s01mnem
253 
254  integer, intent(in) :: mbay(*)
255  integer ival, iupb, i4dy, iben, isbyt, iwid, iretgs, iyoc, icen
256 
257  logical ok4cent
258 
259  ! This statement function checks whether its input value contains a valid century value.
260  ok4cent(ival) = ((ival>=19).and.(ival<=21))
261 
262  ! Check for I8 integers.
263 
264  if(im8b) then
265  im8b=.false.
266 
267  iret = iupbs01(mbay,s01mnem)
268 
269  im8b=.true.
270  return
271  endif
272 
273  ! Handle some simple requests that do not depend on the BUFR edition number.
274 
275  if(s01mnem=='LENM') then
276  iret = iupb(mbay,5,24)
277  return
278  endif
279 
280  if(s01mnem=='LEN0') then
281  iret = nby0
282  return
283  endif
284 
285  ! Get the BUFR edition number.
286 
287  iben = iupb(mbay,8,8)
288  if(s01mnem=='BEN') then
289  iret = iben
290  return
291  endif
292 
293  ! Use the BUFR edition number to handle any other requests.
294 
295  call gets1loc(s01mnem,iben,isbyt,iwid,iretgs)
296  if(iretgs==0) then
297  iret = iupb(mbay,nby0+isbyt,iwid)
298  if(s01mnem=='CENT') then
299 
300  ! Test whether the returned value was a valid century value.
301 
302  if(.not.ok4cent(iret)) iret = -1
303  endif
304  else if( (s01mnem=='YEAR') .and. (iben<4) ) then
305 
306  ! Calculate the 4-digit year.
307 
308  iyoc = iupb(mbay,21,8)
309  icen = iupb(mbay,26,8)
310 
311  ! Does icen contain a valid century value?
312 
313  if(ok4cent(icen)) then
314  ! YES, so use it to calculate the 4-digit year. Note that, by international convention, the year 2000 was the 100th
315  ! year of the 20th century, and the year 2001 was the 1st year of the 21st century
316  iret = (icen-1)*100 + iyoc
317  else
318  ! NO, so use a windowing technique to determine the 4-digit year from the year of the century.
319  iret = i4dy(mod(iyoc,100)*1000000)/10**6
320  endif
321  else
322  iret = -1
323  endif
324 
325  return
326 end function iupbs01
327 
347 recursive integer function iupbs3(mbay,s3mnem) result(iret)
348 
349  use modv_vars, only: im8b
350 
351  implicit none
352 
353  character*(*), intent(in) :: s3mnem
354 
355  integer, intent(in) :: mbay(*)
356  integer len0, len1, len2, len3, l4, l5, ipt, ival, imask, iupb
357 
358  ! Check for I8 integers.
359 
360  if(im8b) then
361  im8b=.false.
362 
363  iret = iupbs3(mbay,s3mnem)
364 
365  im8b=.true.
366  return
367  endif
368 
369  ! Skip to the beginning of Section 3.
370 
371  call getlens(mbay,3,len0,len1,len2,len3,l4,l5)
372  ipt = len0 + len1 + len2
373 
374  ! Unpack the requested value.
375 
376  if(s3mnem=='NSUB') then
377  iret = iupb(mbay,ipt+5,16)
378  else if( (s3mnem=='IOBS') .or. (s3mnem=='ICMP') ) then
379  ival = iupb(mbay,ipt+7,8)
380  if(s3mnem=='IOBS') then
381  imask = 128
382  else
383  imask = 64
384  endif
385  iret = min(1,iand(ival,imask))
386  else
387  iret = -1
388  endif
389 
390  return
391 end function iupbs3
392 
441 recursive integer function iupvs01(lunit,s01mnem) result(iret)
442 
443  use modv_vars, only: im8b
444 
445  use moda_bitbuf
446 
447  implicit none
448 
449  character*(*), intent(in) :: s01mnem
450 
451  integer, intent(in) :: lunit
452  integer my_lunit, lun, ilst, imst, iupbs01
453 
454  ! Check for I8 integers
455 
456  if(im8b) then
457  im8b=.false.
458 
459  call x84(lunit,my_lunit,1)
460  iret=iupvs01(my_lunit,s01mnem)
461 
462  im8b=.true.
463  return
464  endif
465 
466  iret = -1
467 
468  ! Check the file status
469 
470  call status(lunit,lun,ilst,imst)
471  if(ilst==0) call bort('BUFRLIB: IUPVS01 - INPUT BUFR FILE IS CLOSED, IT MUST BE OPEN FOR INPUT')
472  if(ilst>0) call bort('BUFRLIB: IUPVS01 - INPUT BUFR FILE IS OPEN FOR OUTPUT, IT MUST BE OPEN FOR INPUT')
473  if(imst==0) call bort('BUFRLIB: IUPVS01 - A MESSAGE MUST BE OPEN IN INPUT BUFR FILE, NONE ARE')
474 
475  ! Unpack the requested value
476 
477  iret = iupbs01(mbay(1,lun),s01mnem)
478 
479  return
480 end function iupvs01
481 
519 recursive subroutine pkbs1(ival,mbay,s1mnem)
520 
521  use modv_vars, only: im8b
522 
523  implicit none
524 
525  character*(*), intent(in) :: s1mnem
526 
527  integer, intent(in) :: ival
528  integer, intent(inout) :: mbay(*)
529  integer my_ival, iben, isbyt, iwid, iret, iupbs01, ibit
530 
531  character*128 bort_str
532 
533  ! Check for I8 integers.
534 
535  if (im8b) then
536  im8b = .false.
537 
538  call x84(ival,my_ival,1)
539  call pkbs1(my_ival,mbay,s1mnem)
540 
541  im8b = .true.
542  return
543  end if
544 
545  iben = iupbs01(mbay,'BEN')
546 
547  ! Determine where to store the value.
548 
549  call gets1loc(s1mnem,iben,isbyt,iwid,iret)
550  if ( (iret==0) .and. &
551  ( (s1mnem=='USN') .or. (s1mnem=='BMT') .or. (s1mnem=='OGCE') .or. (s1mnem=='GSES') .or. (s1mnem=='MTYP') .or. &
552  (s1mnem=='MSBTI') .or. (s1mnem=='MSBT') .or. (s1mnem=='MTV') .or. (s1mnem=='MTVL') .or. (s1mnem=='YCEN') .or.&
553  (s1mnem=='CENT') .or. (s1mnem=='YEAR') .or. (s1mnem=='MNTH') .or. (s1mnem=='DAYS') .or. (s1mnem=='HOUR') .or.&
554  (s1mnem=='MINU') .or. (s1mnem=='SECO') ) ) then
555  ! Store the value.
556  ibit = (iupbs01(mbay,'LEN0')+isbyt-1)*8
557  call pkb(ival,iwid,mbay,ibit)
558  else
559  write(bort_str,'("BUFRLIB: PKBS1 - CANNOT OVERWRITE LOCATION CORRESPONDING TO MNEMONIC (",A,") WITHIN BUFR EDITION '// &
560  '(",I1,")")') s1mnem, iben
561  call bort(bort_str)
562  endif
563 
564  return
565 end subroutine pkbs1
566 
617 recursive subroutine pkvs01(s01mnem,ival)
618 
619  use modv_vars, only: im8b, mxs01v
620 
621  use moda_s01cm
622 
623  implicit none
624 
625  character*(*), intent(in) :: s01mnem
626 
627  integer, intent(in) :: ival
628  integer my_ival, i
629 
630  character*128 bort_str
631 
632  ! check for i8 integers
633 
634  if(im8b) then
635  im8b=.false.
636 
637  call x84(ival,my_ival,1)
638  call pkvs01(s01mnem,my_ival)
639 
640  im8b=.true.
641  return
642  endif
643 
644  ! Confirm that the arrays needed by this subroutine have already been allocated (and if not, go ahead and allocate them now),
645  ! since it's possible for this subroutine to be called before the first call to subroutine openbf().
646 
647  if ( ( .not. allocated(cmnem) ) .or. ( .not. allocated(ivmnem) ) ) then
648  call openbf(0,'FIRST',0)
649  endif
650 
651  ! If an ival has already been assigned for this particular s01mnem, then overwrite that entry in module @ref moda_s01cm
652  ! using the new ival.
653 
654  if(ns01v>0) then
655  do i=1,ns01v
656  if(s01mnem==cmnem(i)) then
657  ivmnem(i) = ival
658  return
659  endif
660  enddo
661  endif
662 
663  ! Otherwise, use the next available unused entry in module @ref moda_s01cm.
664 
665  if(ns01v>=mxs01v) then
666  write(bort_str,'("BUFRLIB: PKVS01 - CANNOT OVERWRITE MORE THAN ",I2," DIFFERENT LOCATIONS WITHIN SECTION 0 '// &
667  'OR SECTION 1")') mxs01v
668  call bort(bort_str)
669  endif
670 
671  ns01v = ns01v + 1
672  cmnem(ns01v) = s01mnem
673  ivmnem(ns01v) = ival
674 
675  return
676 end subroutine pkvs01
677 
684 subroutine reads3 ( lun )
685 
686  use bufrlib
687 
688  use modv_vars, only: maxnc, mxcnem, iprt
689 
690  use moda_sc3bfr
691  use moda_bitbuf
692  use moda_dscach
693  use moda_s3list
694 
695  implicit none
696 
697  integer, intent(in) :: lun
698  integer irepct, ireadmt, igettdi, itmp, ncds3, ii, jj, ifxy, igetntbi, n, idn
699 
700  character*6 numb, adn30
701  character*55 cseq
702  character*128 errstr
703 
704  logical incach
705 
706  save irepct
707 
708  ! Check whether the appropriate BUFR master table information has already been read into internal memory for this message.
709 
710  if ( ireadmt( lun ) == 1 ) then
711  ! NO (i.e. we just had to read in new master table information for this message), so reset some corresponding values in
712  ! other parts of the library.
713  call dxinit ( lun, 0 )
714  itmp = igettdi( 0 )
715  irepct = 0
716  ncnem = 0
717  endif
718 
719  ! Unpack the list of Section 3 descriptors from the message.
720 
721  call upds3 ( mbay(1,lun), maxnc, cds3, ncds3 )
722  do ii = 1, ncds3
723  ids3(ii) = ifxy( cds3(ii) )
724  enddo
725 
726  ! Is the list of Section 3 descriptors already in the cache?
727 
728  ! The cache is a performance-enhancing device which saves time when the same descriptor sequences are encountered over and
729  ! over within the calling program. Time is saved because the below calls to subroutines stseq_c() and makestab() are
730  ! bypassed whenever a list is already in the cache.
731 
732  incach = .false.
733  if ( ncnem > 0 ) then
734  ii = 1
735  do while ( (.not.incach) .and. (ii<=ncnem) )
736  if ( ncds3 == ndc(ii) ) then
737  jj = 1
738  incach = .true.
739  do while ( (incach) .and. (jj<=ncds3) )
740  if ( ids3(jj) == idcach(ii,jj) ) then
741  jj = jj + 1
742  else
743  incach = .false.
744  endif
745  enddo
746  if (incach) then
747 
748  ! The list is already in the cache, so store the corresponding Table A mnemonic into module @ref moda_sc3bfr and return.
749 
750  if ( iprt >= 2 ) then
751  call errwrt('+++++++++++++++++++++++++++++++++++++++++++++++++')
752  errstr = 'BUFRLIB: READS3 - RE-USED CACHE LIST FOR ' // cnem(ii)
753  call errwrt(errstr)
754  call errwrt('+++++++++++++++++++++++++++++++++++++++++++++++++')
755  call errwrt(' ')
756  endif
757  tamnem(lun) = cnem(ii)
758  return
759  endif
760  endif
761  ii = ii + 1
762  enddo
763  endif
764 
765  ! Get the next available index within the internal Table A.
766 
767  n = igetntbi( lun, 'A' )
768 
769  ! Generate a Table A mnemonic and sequence description.
770 
771  write ( tamnem(lun), '(A5,I3.3)') 'MSTTB', n
772  cseq = 'TABLE A MNEMONIC ' // tamnem(lun)
773 
774  ! Store the Table A mnemonic and sequence into the cache.
775 
776  ncnem = ncnem + 1
777  if ( ncnem > mxcnem ) call bort('BUFRLIB: READS3 - MXCNEM OVERFLOW')
778  cnem(ncnem) = tamnem(lun)
779  ndc(ncnem) = ncds3
780  do jj = 1, ncds3
781  idcach(ncnem,jj) = ids3(jj)
782  enddo
783  if ( iprt >= 2 ) then
784  call errwrt('+++++++++++++++++++++++++++++++++++++++++++++++++')
785  errstr = 'BUFRLIB: READS3 - STORED CACHE LIST FOR ' // cnem(ncnem)
786  call errwrt(errstr)
787  call errwrt('+++++++++++++++++++++++++++++++++++++++++++++++++')
788  call errwrt(' ')
789  endif
790 
791  ! Get an FXY value to use with this Table A mnemonic.
792 
793  idn = igettdi( lun )
794  numb = adn30( idn, 6 )
795 
796  ! Store all of the information for this mnemonic within the internal Table A.
797 
798  call stntbia ( n, lun, numb, tamnem(lun), cseq )
799 
800  ! Store all of the information for this sequence within the internal Tables B and D.
801 
802  call stseq_c ( lun, irepct, idn, tamnem(lun), cseq, ids3, ncds3 )
803 
804  ! Update the jump/link table.
805 
806  call makestab
807 
808  return
809 end subroutine reads3
810 
825 recursive subroutine upds3(mbay,lcds3,cds3,nds3)
826 
827  use modv_vars, only: im8b
828 
829  implicit none
830 
831  integer, intent(in) :: mbay(*), lcds3
832  integer, intent(out) :: nds3
833  integer my_lcds3, len0, len1, len2, len3, l4, l5, ipt, jj, iupb
834 
835  character*6, intent(out) :: cds3(*)
836  character*6 adn30
837 
838  ! Check for I8 integers.
839 
840  if(im8b) then
841  im8b=.false.
842 
843  call x84(lcds3,my_lcds3,1)
844  call upds3(mbay,my_lcds3,cds3,nds3)
845  call x48(nds3,nds3,1)
846 
847  im8b=.true.
848  return
849  endif
850 
851  ! Skip to the beginning of Section 3.
852 
853  call getlens(mbay,3,len0,len1,len2,len3,l4,l5)
854  ipt = len0 + len1 + len2
855 
856  ! Unpack the Section 3 descriptors.
857 
858  nds3 = 0
859  do jj = 8,(len3-1),2
860  nds3 = nds3 + 1
861  if(nds3>lcds3) call bort('BUFRLIB: UPDS3 - OVERFLOW OF OUTPUT DESCRIPTOR ARRAY; TRY A LARGER DIMENSION FOR THIS ARRAY')
862  cds3(nds3) = adn30(iupb(mbay,ipt+jj,16),6)
863  enddo
864 
865  return
866 end subroutine upds3
867 
884 recursive subroutine datelen(len)
885 
886  use modv_vars, only: im8b, lendat
887 
888  implicit none
889 
890  integer, intent(in) :: len
891  integer my_len
892 
893  character*128 bort_str
894 
895  ! Check for I8 integers
896 
897  if(im8b) then
898  im8b=.false.
899 
900  call x84(len,my_len,1)
901  call datelen(my_len)
902 
903  im8b=.true.
904  return
905  endif
906 
907  if(len/=8 .and. len/=10) then
908  write(bort_str,'("BUFRLIB: DATELEN - INPUT ARGUMENT IS",I4," - IT MUST BE EITHER 8 OR 10")') len
909  call bort(bort_str)
910  endif
911  lendat = len
912 
913  return
914 end subroutine datelen
915 
932 recursive subroutine datebf(lunit,mear,mmon,mday,mour,idate)
933 
934  use modv_vars, only: im8b, iprt
935 
936  use moda_mgwa
937 
938  implicit none
939 
940  integer, intent(in) :: lunit
941  integer, intent(out) :: mear, mmon, mday, mour, idate
942  integer my_lunit, lun, jl, jm, ier, idx, idxmsg, igetdate
943 
944  character*128 errstr
945 
946  ! Check for I8 integers
947 
948  if(im8b) then
949  im8b=.false.
950 
951  call x84(lunit,my_lunit,1)
952  call datebf(my_lunit,mear,mmon,mday,mour,idate)
953  call x48(mear,mear,1)
954  call x48(mmon,mmon,1)
955  call x48(mday,mday,1)
956  call x48(mour,mour,1)
957  call x48(idate,idate,1)
958 
959  im8b=.true.
960  return
961  endif
962 
963  ! Initialization, in case openbf() hasn't been called yet.
964 
965  if ( .not. allocated(mgwa) ) call openbf(lunit,'FIRST',lunit)
966 
967  ! See if the file is already open to the library (a no-no!).
968 
969  call status(lunit,lun,jl,jm)
970  if(jl/=0) call bort ('BUFRLIB: DATEBF - INPUT BUFR FILE IS OPEN, IT MUST BE CLOSED')
971 
972  ! Read to the first data message and pick out the date.
973 
974  call openbf(lunit,'INX',lunit)
975  idx = 1
976  do while (idx==1)
977  call rdmsgw(lunit,mgwa,ier)
978  if(ier<0) then
979  if (iprt>=1) then
980  call errwrt('+++++++++++++++++++++WARNING+++++++++++++++++++++++')
981  errstr = 'BUFRLIB: DATEBF - SECTION 1 DATE COULD NOT BE LOCATED - RETURN WITH IDATE = -1'
982  call errwrt(errstr)
983  call errwrt('+++++++++++++++++++++WARNING+++++++++++++++++++++++')
984  call errwrt(' ')
985  endif
986  idate = -1
987  call closbf(lunit)
988  return
989  endif
990  idx = idxmsg(mgwa)
991  end do
992  idate = igetdate(mgwa,mear,mmon,mday,mour)
993  call closbf(lunit)
994 
995  return
996 end subroutine datebf
997 
1015 recursive integer function igetdate(mbay,iyr,imo,idy,ihr) result(iret)
1016 
1017  use modv_vars, only: im8b, lendat
1018 
1019  implicit none
1020 
1021  integer, intent(in) :: mbay(*)
1022  integer, intent(out) :: iyr, imo, idy, ihr
1023  integer iupbs01
1024 
1025  ! Check for I8 integers.
1026 
1027  if(im8b) then
1028  im8b=.false.
1029 
1030  iret=igetdate(mbay,iyr,imo,idy,ihr)
1031  call x48(iyr,iyr,1)
1032  call x48(imo,imo,1)
1033  call x48(idy,idy,1)
1034  call x48(ihr,ihr,1)
1035 
1036  im8b=.true.
1037  return
1038  endif
1039 
1040  iyr = iupbs01(mbay,'YEAR')
1041  imo = iupbs01(mbay,'MNTH')
1042  idy = iupbs01(mbay,'DAYS')
1043  ihr = iupbs01(mbay,'HOUR')
1044  if(lendat/=10) iyr = mod(iyr,100)
1045  iret = (iyr*1000000) + (imo*10000) + (idy*100) + ihr
1046 
1047  return
1048 end function igetdate
1049 
1063 recursive integer function i4dy(idate) result(iret)
1064 
1065  use modv_vars, only: im8b
1066 
1067  implicit none
1068 
1069  integer, intent(in) :: idate
1070  integer my_idate, iy
1071 
1072  ! Check for I8 integers.
1073 
1074  if(im8b) then
1075  im8b=.false.
1076 
1077  call x84(idate,my_idate,1)
1078  iret=i4dy(my_idate)
1079 
1080  im8b=.true.
1081  return
1082  endif
1083 
1084  if(idate<10**8) then
1085  iy = idate/10**6
1086  if(iy>40) then
1087  iret = idate + 19*100000000
1088  else
1089  iret = idate + 20*100000000
1090  endif
1091  else
1092  iret = idate
1093  endif
1094 
1095  return
1096 end function i4dy
1097 
1129 recursive subroutine dumpbf(lunit,jdate,jdump)
1130 
1131  use modv_vars, only: im8b, iprt
1132 
1133  use moda_mgwa
1134 
1135  implicit none
1136 
1137  integer, intent(in) :: lunit
1138  integer, intent(out) :: jdate(*), jdump(*)
1139  integer my_lunit, lun, jl, jm, ier, ii, igetdate, idxmsg, iupbs3, iupbs01
1140 
1141  character*128 errstr
1142 
1143  ! Check for I8 integers
1144 
1145  if(im8b) then
1146  im8b=.false.
1147 
1148  call x84(lunit,my_lunit,1)
1149  call dumpbf(my_lunit,jdate,jdump)
1150  call x48(jdate(1),jdate(1),5)
1151  call x48(jdump(1),jdump(1),5)
1152 
1153  im8b=.true.
1154  return
1155  endif
1156 
1157  do ii=1,5
1158  jdate(ii) = -1
1159  jdump(ii) = -1
1160  enddo
1161 
1162  ! See if the file is already open to the library (a no-no!).
1163 
1164  call status(lunit,lun,jl,jm)
1165  if(jl/=0) call bort('BUFRLIB: DUMPBF - INPUT BUFR FILE IS OPEN, IT MUST BE CLOSED')
1166  call openbf(lunit,'INX',lunit)
1167 
1168  do while (.true.)
1169  call rdmsgw(lunit,mgwa,ier)
1170  if(ier/=0) exit
1171  if(idxmsg(mgwa)==1) cycle ! Skip past any dictionary messages
1172 
1173  ! The dump center YY,MM,DD,HH,MM should be in this message, which is the first message containing zero subsets
1174  if(iupbs3(mgwa,'NSUB')/=0) exit
1175  ii = igetdate(mgwa,jdate(1),jdate(2),jdate(3),jdate(4))
1176  jdate(5) = iupbs01(mgwa,'MINU')
1177 
1178  ! The dump clock YY,MM,DD,HH,MM should be in the next message, which is the second message containing zero subsets
1179  call rdmsgw(lunit,mgwa,ier)
1180  if(ier/=0) exit
1181  if(iupbs3(mgwa,'NSUB')/=0) exit
1182  ii = igetdate(mgwa,jdump(1),jdump(2),jdump(3),jdump(4))
1183  jdump(5) = iupbs01(mgwa,'MINU')
1184 
1185  call closbf(lunit)
1186  return
1187  enddo
1188 
1189  if (iprt>=1 .and. (jdate(1)==-1.or.jdump(1)==-1)) then
1190  call errwrt('+++++++++++++++++++++WARNING+++++++++++++++++++++++')
1191  if(jdate(1)==-1) then
1192  errstr = 'BUFRLIB: DUMPBF - FIRST EMPTY BUFR MESSAGE SECTION 1 DATE COULD NOT BE LOCATED - RETURN WITH JDATE = 5*-1'
1193  call errwrt(errstr)
1194  endif
1195  if(jdump(1)==-1) then
1196  errstr = 'BUFRLIB: DUMPBF - SECOND EMPTY BUFR MESSAGE SECTION 1 DATE COULD NOT BE LOCATED - RETURN WITH JDUMP = 5*-1'
1197  call errwrt(errstr)
1198  endif
1199  call errwrt('+++++++++++++++++++++WARNING+++++++++++++++++++++++')
1200  call errwrt(' ')
1201  endif
1202 
1203  return
1204 end subroutine dumpbf
1205 
1215 recursive subroutine minimg(lunit,mini)
1216 
1217  use modv_vars, only: im8b
1218 
1219  use moda_bitbuf
1220 
1221  implicit none
1222 
1223  integer, intent(in) :: lunit, mini
1224  integer my_lunit, my_mini, lun, il, im
1225 
1226  ! Check for I8 integers.
1227 
1228  if(im8b) then
1229  im8b=.false.
1230 
1231  call x84(lunit,my_lunit,1)
1232  call x84(mini,my_mini,1)
1233  call minimg(my_lunit,my_mini)
1234 
1235  im8b=.true.
1236  return
1237  endif
1238 
1239  call status(lunit,lun,il,im)
1240  if(il==0) call bort('BUFRLIB: MINIMG - OUTPUT BUFR FILE IS CLOSED, IT MUST BE OPEN FOR OUTPUT')
1241  if(il<0) call bort('BUFRLIB: MINIMG - OUTPUT BUFR FILE IS OPEN FOR INPUT, IT MUST BE OPEN FOR OUTPUT')
1242  if(im==0) call bort('BUFRLIB: MINIMG - A MESSAGE MUST BE OPEN IN OUTPUT BUFR FILE, NONE ARE')
1243 
1244  call pkbs1(mini,mbay(1,lun),'MINU')
1245 
1246  return
1247 end subroutine minimg
1248 
1263 subroutine cktaba(lun,subset,jdate,iret)
1264 
1265  use modv_vars, only: iprt, fxy_sbyct
1266 
1267  use moda_msgcwd
1268  use moda_sc3bfr
1269  use moda_unptyp
1270  use moda_bitbuf
1271 
1272  implicit none
1273 
1274  integer, intent(in) :: lun
1275  integer, intent(out) :: jdate, iret
1276  integer, parameter :: ncpfx = 3
1277  integer mtyp, msbt, mty1, msb1, isub, ksub, len0, len1, len2, len3, l4, l5, lundx, ii, &
1278  itab, inod, iad3, iad4, iyr, imo, idy, ihr, iupb, ifxy, iupbs01, iupbs3, i4dy, igetdate
1279 
1280  character*128 bort_str, errstr
1281  character*8, intent(out) :: subset
1282  character*2, parameter :: cpfx(ncpfx) = (/'NC','FR','FN'/)
1283  character tab
1284 
1285  logical trybt
1286 
1287  iret = 0
1288 
1289  trybt = .true.
1290 
1291  ! Get the message type, subtype, and date from Section 1
1292 
1293  mtyp = iupbs01(mbay(1,lun),'MTYP')
1294  msbt = iupbs01(mbay(1,lun),'MSBT')
1295  jdate = igetdate(mbay(1,lun),iyr,imo,idy,ihr)
1296 
1297  if(mtyp==11) then
1298  ! This is a BUFR table (dictionary) message
1299  iret = 11
1300  ! There's no need to proceed any further unless Section 3 is being used for decoding
1301  if(isc3(lun)==0) then
1302  subset = " "
1303  return
1304  endif
1305  endif
1306 
1307  ! Get the first and second descriptors from Section 3
1308 
1309  call getlens(mbay(1,lun),3,len0,len1,len2,len3,l4,l5)
1310  iad3 = len0+len1+len2
1311  ksub = iupb(mbay(1,lun),iad3+8,16)
1312  isub = iupb(mbay(1,lun),iad3+10,16)
1313 
1314  ! Locate Section 4
1315 
1316  iad4 = iad3+len3
1317 
1318  ! Now, try to get the Table A mnemonic
1319 
1320  outer: do while (.true.)
1321 
1322  if(isc3(lun)/=0) then
1323  ! Section 3 is being used for decoding
1324  subset = tamnem(lun)
1325  call nemtbax(lun,subset,mty1,msb1,inod)
1326  if(inod>0) then
1327  mbyt(lun) = 8*(iad4+4)
1328  msgunp(lun) = 1
1329  exit outer
1330  endif
1331  endif
1332 
1333  inner: do while (.true.)
1334 
1335  call numtab(lun,isub,subset,tab,itab)
1336  call nemtbax(lun,subset,mty1,msb1,inod)
1337  if(inod>0) then
1338  ! The second descriptor in Section 3 corresponds to the Table A mnemonic, so the message contains non-standard
1339  ! NCEP extensions
1340  mbyt(lun) = (iad4+4)
1341  msgunp(lun) = 0
1342  exit outer
1343  endif
1344 
1345  call numtab(lun,ksub,subset,tab,itab)
1346  call nemtbax(lun,subset,mty1,msb1,inod)
1347  if(inod>0) then
1348  ! The first descriptor in Section 3 corresponds to the Table A mnemonic, so the message is WMO-standard
1349  mbyt(lun) = 8*(iad4+4)
1350  msgunp(lun) = 1
1351  exit outer
1352  endif
1353 
1354  ! OK, still no luck, so try "NCtttsss" (where ttt=mtyp and sss=msbt) as the Table A mnemonic, and if that doesn't work
1355  ! then also try "FRtttsss" AND "FNtttsss"
1356  ii=1
1357  do while(ii<=ncpfx)
1358  write(subset,'(A2,2I3.3)') cpfx(ii),mtyp,msbt
1359  call nemtbax(lun,subset,mty1,msb1,inod)
1360  if(inod>0) then
1361  if(ksub==ifxy(fxy_sbyct)) then
1362  mbyt(lun) = (iad4+4)
1363  msgunp(lun) = 0
1364  else
1365  mbyt(lun) = 8*(iad4+4)
1366  msgunp(lun) = 1
1367  endif
1368  exit outer
1369  endif
1370  ii=ii+1
1371  enddo
1372 
1373  if(trybt) then
1374  ! Make one last desperate attempt by checking whether the application program contains an in-line version of
1375  ! subroutine openbt() to override the default version in the library
1376  trybt = .false.
1377  if(iprt>=1) then
1378  call errwrt('++++++++++++++BUFR ARCHIVE LIBRARY+++++++++++++++++')
1379  errstr = 'BUFRLIB: CKTABA - LAST RESORT, CHECK FOR EXTERNAL BUFR TABLE VIA CALL TO IN-LINE OPENBT'
1380  call errwrt(errstr)
1381  call errwrt('++++++++++++++BUFR ARCHIVE LIBRARY+++++++++++++++++')
1382  call errwrt(' ')
1383  endif
1384  call openbt(lundx,mtyp)
1385  if(lundx>0) then
1386  ! There was an in-line replacement for the default library version of openbt(), so read DX table information from
1387  ! the specified logical unit and look for the Table A mnemonic there
1388  call rdusdx(lundx,lun)
1389  cycle inner
1390  endif
1391  endif
1392 
1393  ! Give up and report the bad news
1394  if(iprt>=0) then
1395  call errwrt('+++++++++++++++++++++WARNING+++++++++++++++++++++++')
1396  errstr = 'BUFRLIB: CKTABA - UNRECOGNIZED TABLE A MESSAGE TYPE (' // subset // ') - RETURN WITH IRET = -1'
1397  call errwrt(errstr)
1398  call errwrt('+++++++++++++++++++++WARNING+++++++++++++++++++++++')
1399  call errwrt(' ')
1400  endif
1401  iret = -1
1402  return
1403 
1404  enddo inner
1405 
1406  enddo outer
1407 
1408  ! Confirm the validity of the message type and subtype, and also check for compression
1409 
1410  if(isc3(lun)==0) then
1411  if(mtyp/=mty1) then
1412  write(bort_str,'("BUFRLIB: CKTABA - MESSAGE TYPE MISMATCH (SUBSET=",A8,", MTYP=",I3,", MTY1=",I3)') subset,mtyp,mty1
1413  call bort(bort_str)
1414  endif
1415  if( msbt/=msb1 .and. ( verify(subset(3:8),'1234567890') == 0 ) ) then
1416  write(bort_str,'("BUFRLIB: CKTABA - MESSAGE SUBTYPE MISMATCH (SUBSET=",A8,", MSBT=",I3,", MSB1=",I3)') subset,msbt,msb1
1417  call bort(bort_str)
1418  endif
1419  endif
1420  if(iupbs3(mbay(1,lun),'ICMP')>0) msgunp(lun) = 2
1421 
1422  ! Update values in @ref moda_msgcwd
1423 
1424  idate(lun) = i4dy(jdate)
1425  inode(lun) = inod
1426  msub(lun) = iupbs3(mbay(1,lun),'NSUB')
1427  nsub(lun) = 0
1428  if(iret/=11) nmsg(lun) = nmsg(lun)+1
1429 
1430  return
1431 end subroutine cktaba
1432 
1472 recursive subroutine mesgbc(lunin,mesgtyp,icomp)
1473 
1474  use modv_vars, only: im8b
1475 
1476  use moda_bitbuf
1477  use moda_mgwa
1478 
1479  implicit none
1480 
1481  integer, intent(in) :: lunin
1482  integer, intent(out) :: mesgtyp, icomp
1483  integer my_lunin, lunit, irec, ier, i, lun, il, im, iupbs01, iupbs3, idxmsg
1484 
1485  ! Check for I8 integers
1486 
1487  if(im8b) then
1488  im8b=.false.
1489  call x84(lunin,my_lunin,1)
1490  call mesgbc(my_lunin,mesgtyp,icomp)
1491  call x48(mesgtyp,mesgtyp,1)
1492  call x48(icomp,icomp,1)
1493  im8b=.true.
1494  return
1495  endif
1496 
1497  mesgtyp = -256
1498 
1499  lunit = abs(lunin)
1500 
1501  if(lunit==lunin) then
1502  ! Open the file, read past any DX BUFR tables and "dummy" messages, and return the first message type found
1503  irec = 0
1504  call openbf(lunit,'INX',lunit)
1505  do while (.true.)
1506  call rdmsgw(lunit,mgwa,ier)
1507  if(ier==-1) then
1508  if(irec==0) then
1509  mesgtyp = -256
1510  icomp = -3
1511  else
1512  if(mesgtyp>=0) mesgtyp = -mesgtyp
1513  icomp = -2
1514  endif
1515  call closbf(lunit)
1516  return
1517  endif
1518  irec = irec + 1
1519  mesgtyp = iupbs01(mgwa,'MTYP')
1520  if( (idxmsg(mgwa)/=1) .and. (iupbs3(mgwa,'NSUB')/=0) ) exit
1521  enddo
1522  call closbf(lunit)
1523  else
1524  ! Return message type for message currently stored in memory
1525  call status(lunit,lun,il,im)
1526  do i=1,12
1527  mgwa(i) = mbay(i,lun)
1528  enddo
1529  mesgtyp = iupbs01(mgwa,'MTYP')
1530  end if
1531 
1532  ! Set the compression switch
1533  icomp = iupbs3(mgwa,'ICMP')
1534 
1535  return
1536 end subroutine mesgbc
1537 
1561 recursive subroutine mesgbf(lunit,mesgtyp)
1562 
1563  use modv_vars, only: im8b
1564 
1565  use moda_mgwa
1566 
1567  implicit none
1568 
1569  integer, intent(in) :: lunit
1570  integer, intent(out) :: mesgtyp
1571  integer my_lunit, ier, iupbs01, idxmsg
1572 
1573  ! Check for I8 integers
1574 
1575  if(im8b) then
1576  im8b=.false.
1577  call x84(lunit,my_lunit,1)
1578  call mesgbf(my_lunit,mesgtyp)
1579  call x48(mesgtyp,mesgtyp,1)
1580  im8b=.true.
1581  return
1582  endif
1583 
1584  mesgtyp = -1
1585 
1586  call openbf(lunit,'INX',lunit)
1587 
1588  do while (.true.)
1589  call rdmsgw(lunit,mgwa,ier)
1590  if(ier==0) then
1591  mesgtyp = iupbs01(mgwa,'MTYP')
1592  if(idxmsg(mgwa)/=1) exit
1593  endif
1594  enddo
1595 
1596  call closbf(lunit)
1597 
1598  return
1599 end subroutine mesgbf
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 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 rdusdx(lundx, lun)
Read and parse a file containing a user-supplied DX BUFR table in character format,...
Definition: dxtable.F90:197
subroutine nemtbax(lun, nemo, mtyp, msbt, inod)
Get information about a Table A descriptor from the internal DX BUFR tables.
Definition: dxtable.F90:1186
subroutine stntbia(n, lun, numb, nemo, celsq)
Store a new entry within internal BUFR Table A.
Definition: dxtable.F90:1549
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 errwrt(str)
Specify a custom location for the logging of error and diagnostic messages generated by the NCEPLIBS-...
Definition: errwrt.F90:32
subroutine numtab(lun, idn, nemo, tab, iret)
Get information about a descriptor, based on the WMO bit-wise representation of an FXY value.
Definition: fxy.F90:359
character *(*) function adn30(idn, ldn)
Convert an FXY value from its WMO bit-wise representation to a character string of length 5 or 6.
Definition: fxy.F90:18
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.
Declare arrays and variables for the internal Table A mnemonic cache that is used for Section 3 decod...
character *8, dimension(:), allocatable cnem
Table A mnemonics.
integer ncnem
Number of entries in the internal Table A mnemonic cache (up to a maximum of mxcnem).
integer, dimension(:,:), allocatable idcach
WMO bit-wise representations of the child descriptors for the corresponding Table A mnemonic in cnem.
integer, dimension(:), allocatable ndc
Number of child descriptors for the corresponding Table A mnemonic in cnem.
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 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 arrays used by various subroutines and functions to hold a temporary working copy of a Sectio...
integer, dimension(:), allocatable ids3
Temporary working copy of Section 3 descriptor list in integer form.
character *6, dimension(:), allocatable cds3
Temporary working copy of Section 3 descriptor list in character form.
Declare an array used to store a switch for each file ID, indicating whether BUFR messages read from ...
character *8, dimension(:), allocatable tamnem
Table A mnemonic most recently read from each file ID, if isc3 = 1 for that stream.
integer, dimension(:), allocatable isc3
Section 3 switch for each file ID:
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:
recursive subroutine openbt(lundx, mtyp)
Specify a DX BUFR table of last resort, in case subroutine cktaba() is unable to locate a DX BUFR tab...
Definition: openbt.F90:31
recursive subroutine closbf(lunit)
Close the connection between logical unit lunit and the NCEPLIBS-bufr software.
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 status(lunit, lun, il, im)
Check whether a specified Fortran logical unit number is currently connected to the NCEPLIBS-bufr sof...
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.
subroutine rdmsgw(lunit, mesg, iret)
Read the next BUFR message from logical unit lunit as an array of integer words.
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 datebf(lunit, mear, mmon, mday, mour, idate)
Get the Section 1 date-time from the first data message of a BUFR file, bypassing any messages at the...
Definition: s013vals.F90:933
recursive integer function iupvs01(lunit, s01mnem)
Read a specified value from within Section 0 or 1 of a BUFR message.
Definition: s013vals.F90:442
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
recursive subroutine minimg(lunit, mini)
Write a minutes value into Section 1 of the BUFR message that was most recently opened for writing vi...
Definition: s013vals.F90:1216
recursive subroutine upds3(mbay, lcds3, cds3, nds3)
Read the sequence of data descriptors contained within Section 3 of a BUFR message.
Definition: s013vals.F90:826
recursive subroutine mesgbf(lunit, mesgtyp)
Read through a BUFR file (starting from the beginning of the file) and return the message type (from ...
Definition: s013vals.F90:1562
recursive subroutine gets1loc(s1mnem, iben, isbyt, iwid, iret)
Get the location of a specified value within Section 1 of a BUFR message.
Definition: s013vals.F90:48
recursive subroutine datelen(len)
Specify the format of Section 1 date-time values that will be output by future calls to any of the NC...
Definition: s013vals.F90:885
recursive subroutine dumpbf(lunit, jdate, jdump)
Read the Section 1 date-time from the first two "dummy" messages of an NCEP dump file.
Definition: s013vals.F90:1130
recursive subroutine mesgbc(lunin, mesgtyp, icomp)
Return the message type (from Section 1) and message compression indicator (from Section 3) of a BUFR...
Definition: s013vals.F90:1473
recursive subroutine pkvs01(s01mnem, ival)
Specify a value to be written into a specified location within Section 0 or Section 1 of all BUFR mes...
Definition: s013vals.F90:618
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 integer function igetdate(mbay, iyr, imo, idy, ihr)
Get the date-time from within Section 1 of a BUFR message.
Definition: s013vals.F90:1016
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