NCEPLIBS-bufr  12.2.0
compress.F90
Go to the documentation of this file.
1 
5 
32 subroutine cmpmsg(cf)
33 
34  use moda_msgcmp
35 
36  implicit none
37 
38  character, intent(in) :: cf
39  character*128 bort_str
40  character my_cf
41 
42  my_cf = cf
43  call capit(my_cf)
44  if(my_cf /= 'Y' .and. my_cf /= 'N') then
45  write(bort_str,'("BUFRLIB: CMPMSG - INPUT ARGUMENT IS ",A1,", IT MUST BE EITHER Y OR N")') cf
46  call bort(bort_str)
47  endif
48  ccmf = my_cf
49 
50  return
51 end subroutine cmpmsg
52 
73 recursive subroutine writcp(lunit)
74 
75  use modv_vars, only: im8b
76 
77  implicit none
78 
79  integer, intent(in) :: lunit
80  integer my_lunit
81 
82  ! Check for I8 integers.
83 
84  if(im8b) then
85  im8b=.false.
86 
87  call x84(lunit,my_lunit,1)
88  call writcp(my_lunit)
89 
90  im8b=.true.
91  return
92  endif
93 
94  call cmpmsg('Y')
95  call writsb(lunit)
96  call cmpmsg('N')
97 
98  return
99 end subroutine writcp
100 
111 subroutine rdcmps(lun)
112 
113  use modv_vars, only: bmiss, mxrst
114 
115  use moda_usrint
116  use moda_msgcwd
117  use moda_bitbuf
118  use moda_tables
119  use moda_rlccmn
120  use moda_stcode
121 
122  implicit none
123 
124  integer, intent(in) :: lun
125  integer*8 :: ival, lref, ninc, lps
126  integer nsbs, jbit, lbit, nbit, n, node, ityp, linc, lre4, nin4, nbmp, nchr, lelm, ibsv, igetrfel, ibfms, icbfms
127 
128  real*8 rval, ups
129 
130  character*128 bort_str
131  character*8 cref, cval
132 
133  equivalence(cval,rval)
134 
135  ! Statement function to compute BUFR "missing value" for field of length lbit bits (all bits "on")
136  lps(lbit) = max(2_8**(lbit)-1,1)
137 
138  ! Setup the subset template
139 
140  call usrtpl(lun,1,1)
141 
142  ! Uncompress a subset into the val array according to Table B
143 
144  nsbs = nsub(lun)
145 
146  ! Note that we are going to unpack the (nsbs)th subset from within the current BUFR message.
147 
148  ibit = mbyt(lun)
149  nrst = 0
150 
151  ! Loop through each element of the subset, including immediately resolving any replication sequences by emulating recursion
152  ! via an explicit goto statement.
153 
154  n = 0
155  11 do n=n+1,nval(lun)
156  node = inv(n,lun)
157  nrfelm(n,lun) = igetrfel(n,lun)
158  nbit = ibt(node)
159  ityp = itp(node)
160 
161  ! In each of the following code blocks, the "local reference value" for the element is determined first, followed by the
162  ! 6-bit value which indicates how many bits are used to store the increment (i.e. offset) from this "local reference value".
163  ! Then, we jump ahead to where this increment is stored for this particular subset, unpack it, and add it to the
164  ! "local reference value" to determine the final uncompressed value for this element from this subset. Note that, if an
165  ! element has the same final uncompressed value for each subset in the message, then the encoding rules for BUFR compression
166  ! dictate that the "local reference value" will be equal to this value, the 6-bit increment length indicator will have a
167  ! value of zero, and the actual increments themselves will be omitted from the message.
168 
169  if(ityp==1.or.ityp==2) then
170  ! This is a numeric element.
171  if(nbit<=32) then
172  call upb(lre4,nbit,mbay(1,lun),ibit)
173  call upb(linc,6,mbay(1,lun),ibit)
174  jbit = ibit + linc*(nsbs-1)
175  call upb(nin4,linc,mbay(1,lun),jbit)
176  lref = lre4
177  ninc = nin4
178  elseif(nbit<=64) then
179  call up8(lref,nbit,mbay(1,lun),ibit)
180  call upb(linc,6,mbay(1,lun),ibit)
181  jbit = ibit + linc*(nsbs-1)
182  call up8(ninc,linc,mbay(1,lun),jbit)
183  endif
184  if(ninc==lps(linc)) then
185  ival = lps(nbit)
186  else
187  ival = lref + ninc
188  endif
189  if(ityp==1) then
190  nbmp = int(ival)
191  call usrtpl(lun,n,nbmp)
192  if (iscodes(lun) /= 0) return
193  goto 11
194  endif
195  if(ival<lps(nbit)) val(n,lun) = ups(ival,node)
196  call strbtm(n,lun,ibfms(val(n,lun)))
197  ibit = ibit + linc*msub(lun)
198  elseif(ityp==3) then
199  ! This is a character element. If there are more than 8 characters, then only the first 8 will be unpacked by this
200  ! routine, and a separate subsequent call to subroutine readlc() will be required to unpack the remainder of the string.
201  ! In this case, pointers will be saved within module @ref moda_rlccmn for later use within readlc().
202  lelm = nbit/8
203  nchr = min(8,lelm)
204  ibsv = ibit
205  cref = ' '
206  call upc(cref,nchr,mbay(1,lun),ibit,.true.)
207  if(lelm>8) then
208  ibit = ibit + (lelm-8)*8
209  nrst = nrst + 1
210  if(nrst>mxrst) then
211  write(bort_str,'("BUFRLIB: RDCMPS - NUMBER OF LONG CHARACTER STRINGS EXCEEDS THE LIMIT (",I4,")")') mxrst
212  call bort(bort_str)
213  endif
214  crtag(nrst) = tag(node)
215  endif
216  ! Unpack the increment length indicator. For character elements, this length is in bytes rather than bits.
217  call upb(linc,6,mbay(1,lun),ibit)
218  if(linc==0) then
219  if(lelm>8) then
220  irnch(nrst) = lelm
221  irbit(nrst) = ibsv
222  endif
223  cval = cref
224  else
225  jbit = ibit + linc*(nsbs-1)*8
226  if(lelm>8) then
227  irnch(nrst) = linc
228  irbit(nrst) = jbit
229  endif
230  nchr = min(8,linc)
231  cval = ' '
232  call upc(cval,nchr,mbay(1,lun),jbit,.true.)
233  endif
234  if (lelm<=8 .and. icbfms(cval,nchr)/=0) then
235  val(n,lun) = bmiss
236  else
237  val(n,lun) = rval
238  endif
239  ibit = ibit + 8*linc*msub(lun)
240  endif
241  enddo
242 
243  return
244 end subroutine rdcmps
245 
260 subroutine cmsgini(lun,mesg,subset,idate,nsub,nbyt)
261 
262  use modv_vars, only: mtv, nby1, nby5, bmostr
263 
264  implicit none
265 
266  integer, intent(in) :: lun, idate, nsub
267  integer, intent(inout) :: nbyt
268  integer, intent(out) :: mesg(*)
269  integer mtyp, msbt, inod, isub, iret, jdate, mcen, mear, mmon, mday, mour, mmin, mbit, mbyt, len3, i4dy
270 
271  character*128 bort_str
272  character*8, intent(in) :: subset
273  character tab
274 
275  ! Get the message tag and type, and break up the date which can be either YYMMDDHH or YYYYMMDDHH
276 
277  call nemtba(lun,subset,mtyp,msbt,inod)
278  call nemtab(lun,subset,isub,tab,iret)
279  if(iret==0) then
280  write(bort_str,'("BUFRLIB: CMSGINI - TABLE A MESSAGE TYPE MNEMONIC ",A," NOT FOUND IN INTERNAL TABLE D ARRAYS")') subset
281  call bort(bort_str)
282  endif
283 
284  jdate = i4dy(idate)
285  mcen = mod(jdate/10**8,100)+1
286  mear = mod(jdate/10**6,100)
287  mmon = mod(jdate/10**4,100)
288  mday = mod(jdate/10**2,100)
289  mour = mod(jdate ,100)
290  mmin = 0
291 
292  if(mear==0) then
293  mcen = mcen-1
294  mear = 100
295  endif
296 
297  ! Initialize the message
298 
299  mbit = 0
300 
301  ! Section 0
302 
303  call pkc(bmostr, 4 , mesg,mbit)
304  ! Note that the actual Section 0 length will be computed and stored below; for now, we're really only interested in
305  ! advancing mbit by the correct amount, so we'll just store a default value of 0.
306  call pkb( 0 , 24 , mesg,mbit)
307  call pkb( 3 , 8 , mesg,mbit)
308 
309  ! Section 1
310 
311  call pkb(nby1 , 24 , mesg,mbit)
312  call pkb( 0 , 8 , mesg,mbit)
313  call pkb( 3 , 8 , mesg,mbit)
314  call pkb( 7 , 8 , mesg,mbit)
315  call pkb( 0 , 8 , mesg,mbit)
316  call pkb( 0 , 8 , mesg,mbit)
317  call pkb(mtyp , 8 , mesg,mbit)
318  call pkb(msbt , 8 , mesg,mbit)
319  call pkb( mtv , 8 , mesg,mbit)
320  call pkb( 0 , 8 , mesg,mbit)
321  call pkb(mear , 8 , mesg,mbit)
322  call pkb(mmon , 8 , mesg,mbit)
323  call pkb(mday , 8 , mesg,mbit)
324  call pkb(mour , 8 , mesg,mbit)
325  call pkb(mmin , 8 , mesg,mbit)
326  call pkb(mcen , 8 , mesg,mbit)
327 
328  ! Section 3
329 
330  len3 = 10
331 
332  call pkb(len3 , 24 , mesg,mbit)
333  call pkb( 0 , 8 , mesg,mbit)
334  call pkb(nsub , 16 , mesg,mbit)
335  call pkb( 192 , 8 , mesg,mbit)
336  call pkb(isub , 16 , mesg,mbit)
337  call pkb( 0 , 8 , mesg,mbit)
338 
339  ! Section 4
340 
341  ! Store the total length of Section 4. Remember that the input value of nbyt only contains the length of the compressed
342  ! data portion of Section 4, so we need to add four bytes to this number in order to account for the total length of
343  ! Section 4. The actual compressed data portion will be filled in later by subroutine wrcmps().
344  call pkb((nbyt+4) , 24 , mesg,mbit)
345  call pkb( 0 , 8 , mesg,mbit)
346 
347  ! Section 5
348 
349  ! This section will be filled in later by subroutine wrcmps(). However, for now, and noting that mbit currently points
350  ! to the last bit of the fourth byte of Section 4, then we have:
351  ! (total length of BUFR message (in Section 0)) =
352  ! (length of message up through fourth byte of Section 4)
353  ! + (length of compressed data portion of Section 4)
354  ! + (length of Section 5)
355  mbyt = mbit/8 + nbyt + nby5
356 
357  ! For output, make nbyt point to the current location of mbit, which is the byte after which to actually begin writing the
358  ! compressed data into Section 4.
359  nbyt = mbit/8
360 
361  ! Now, store the total length of the BUFR message in Section 0.
362  mbit = 32
363  call pkb(mbyt,24,mesg,mbit)
364 
365  return
366 end subroutine cmsgini
367 
385 subroutine wrcmps(lunix)
386 
387  use modv_vars, only: mxcdv, mxcsb, nby5, bmcstr
388 
389  use moda_usrint
390  use moda_msgcwd
391  use moda_bitbuf
392  use moda_mgwa
393  use moda_tables
394  use moda_comprx
395  use moda_comprs
396  use moda_s01cm
397 
398  implicit none
399 
400  integer, intent(in) :: lunix
401  integer ibyt, jbit, lunit, lun, il, im, icol, i, j, node, lbyt, nbyt, nchr, ldata, iupbs01, imrkopr
402 
403  character*128 bort_str
404  character*8 subset
405  character czero
406 
407  logical first, kmiss, edge4, msgfull, cmpres
408 
409  real, parameter :: rln2 = 1./log(2.)
410  real range
411 
412  data first /.true./
413 
414  save first, ibyt, jbit, subset, edge4
415 
416  ! Get the unit and subset tag
417 
418  lunit = abs(lunix)
419  call status(lunit,lun,il,im)
420 
421  do while (.true.)
422 
423  if(first) then
424  ! Initialize some values in order to prepare for the creation of a new compressed BUFR message for output.
425  kbyt = 0
426  ncol = 0
427  lunc = lun
428  nrow = nval(lun)
429  subset = tag(inode(lun))(1:8)
430  first = .false.
431  flush = .false.
432  writ1 = .false.
433  ! The following call to cmsgini() is just being done to determine how many bytes (kbyt) will be taken up in a message
434  ! by the information in Sections 0, 1, 2 and 3. This in turn will allow us to determine how many compressed data subsets
435  ! will fit into Section 4 without overflowing maxbyt. Then, later on, another separate call to cmsgini() will be done to
436  ! actually initialize Sections 0, 1, 2 and 3 of the final compressed BUFR message that will be written out.
437  call cmsgini(lun,mbay(1,lun),subset,idate(lun),ncol,kbyt)
438  ! Check the edition number of the BUFR message to be created
439  edge4 = .false.
440  if(ns01v>0) then
441  i = 1
442  do while ( (.not.edge4) .and. (i<=ns01v) )
443  if( (cmnem(i)=='BEN') .and. (ivmnem(i)>=4) ) then
444  edge4 = .true.
445  else
446  i = i+1
447  endif
448  enddo
449  endif
450  endif
451 
452  if(lun/=lunc) then
453  write(bort_str,.NE.'("BUFRLIB: WRCMPS - FILE ID FOR THIS CALL (",I3,") FILE ID FOR INITIAL CALL (",I3,")'// &
454  ' - UNIT NUMBER NOW IS",I4)') lun,lunc,lunix
455  call bort(bort_str)
456  endif
457 
458  cmpres = .true.
459  if(lunix<0) then
460  ! This is a "flush" call, so clear out the buffer (note that there is no current subset to be stored!) and prepare
461  ! to write the final compressed BUFR message.
462  if(ncol<=0) return
463  flush = .true.
464  writ1 = .true.
465  icol = 1
466  elseif(ncol+1>mxcsb) then
467  ! There's no more room in the internal compression arrays for another subset, so we'll need to write out a message
468  ! containing all of the data in those arrays, then initialize a new message to hold the current subset.
469  cmpres = .false.
470  else
471  ! Check on some other possibly problematic situations
472  if(nval(lun)/=nrow) then
473  writ1 = .true.
474  icol = 1
475  elseif(nval(lun)>mxcdv) then
476  write(bort_str,'("BUFRLIB: WRCMPS - NO. OF ELEMENTS IN THE '// &
477  .GT.'SUBSET (",I6,") THE NO. OF ROWS ALLOCATED FOR THE COMPRESSION MATRIX (",I6,")")') nval(lun),mxcdv
478  call bort(bort_str)
479  elseif(ncol>0) then
480  ! Confirm that all of the nodes are the same as in the previous subset for this same BUFR message. If not, then
481  ! there may be different nested replication sequences activated in the current subset vs. in the previous subset,
482  ! even though the total number of nodes is the same.
483  do i = 1, nval(lun)
484  if ( inv(i,lun) /= jlnode(i) ) then
485  writ1 = .true.
486  icol = 1
487  exit
488  endif
489  enddo
490  endif
491  if(.not.writ1) then
492  ! Store the next subset for compression
493  ncol = ncol+1
494  icol = ncol
495  ibit = 16
496  do i=1,nval(lun)
497  node = inv(i,lun)
498  jlnode(i) = node
499  ityp(i) = itp(node)
500  if(imrkopr(tag(node))==1) then
501  iwid(i) = ibt(inv(nrfelm(i,lun),lun))
502  else
503  iwid(i) = ibt(node)
504  endif
505  if(ityp(i)==1.or.ityp(i)==2) then
506  call up8(matx(i,ncol),iwid(i),ibay,ibit)
507  elseif(ityp(i)==3) then
508  catx(i,ncol) = ' '
509  call upc(catx(i,ncol),iwid(i)/8,ibay,ibit,.true.)
510  endif
511  enddo
512  endif
513  endif
514 
515  ! Will the next subset fit into the current message? The only way to find out is to actually re-do the compression
516  ! by re-computing all of the local reference values, increments, etc. to determine the new Section 4 length.
517 
518  do while (cmpres)
519  if(ncol<=0) then
520  write(bort_str,'("BUFRLIB: WRCMPS - NO. OF COLUMNS CALCULATED '// &
521  .LE.'FOR COMPRESSION MAXRIX IS 0 (=",I6,")")') ncol
522  call bort(bort_str)
523  endif
524  ! ldata will hold the length (in bits) of the compressed data, i.e. the sum total for all data values for all data
525  ! subsets in the message
526  ldata = 0
527  do i=1,nrow
528  if(ityp(i)==1 .or. ityp(i)==2) then
529  ! Row i of the compression matrix contains numeric values, so kmis(i) will store .true. if any such values are
530  ! "missing", or .false. otherwise
531  imiss = 2_8**iwid(i)-1
532  if(icol==1) then
533  kmin(i) = imiss
534  kmax(i) = 0
535  kmis(i) = .false.
536  endif
537  do j=icol,ncol
538  if(matx(i,j)<imiss) then
539  kmin(i) = min(kmin(i),matx(i,j))
540  kmax(i) = max(kmax(i),matx(i,j))
541  else
542  kmis(i) = .true.
543  endif
544  enddo
545  kmiss = kmis(i) .and. kmin(i)<imiss
546  range = real(max(1,kmax(i)-kmin(i)+1))
547  if(ityp(i)==2 .and. (range>1. .or. kmiss)) then
548  ! The data values in row i of the compression matrix are numeric values that aren't all identical. Compute the
549  ! number of bits needed to hold the largest of the increments.
550  kbit(i) = nint(log(range)*rln2)
551  if(2**kbit(i)-1<=range) kbit(i) = kbit(i)+1
552  ! However, under no circumstances should this number ever exceed the width of the original underlying descriptor!
553  if(kbit(i)>iwid(i)) kbit(i) = iwid(i)
554  else
555  ! The data values in row i of the compression matrix are numeric values that are all identical, so the increments
556  ! will be omitted from the message.
557  kbit(i) = 0
558  endif
559  ldata = ldata + iwid(i) + 6 + ncol*kbit(i)
560  elseif(ityp(i)==3) then
561  ! Row i of the compression matrix contains character values, so kmis(i) will store .false. if all such values are
562  ! identical, OR .true. otherwise
563  if(icol==1) then
564  cstr(i) = catx(i,1)
565  kmis(i) = .false.
566  endif
567  do j=icol,ncol
568  if ( (.not.kmis(i)) .and. (cstr(i)/=catx(i,j)) ) then
569  kmis(i) = .true.
570  endif
571  enddo
572  if (kmis(i)) then
573  ! The data values in row i of the compression matrix are character values that are not all identical
574  kbit(i) = iwid(i)
575  else
576  ! The data values in row i of the compression matrix are character values that are all identical, so the
577  ! increments will be omitted from the message
578  kbit(i) = 0
579  endif
580  ldata = ldata + iwid(i) + 6 + ncol*kbit(i)
581  endif
582  enddo
583  ! Round data length up to a whole byte count
584  ibyt = (ldata+8-mod(ldata,8))/8
585  ! Depending on the edition number of the message, we need to ensure that we round to an even byte count
586  if( (.not.edge4) .and. (mod(ibyt,2)/=0) ) ibyt = ibyt+1
587  jbit = ibyt*8-ldata
588  if(msgfull(ibyt,kbyt,maxbyt)) then
589  ! The current subset will not fit into the current message. Set the flag to indicate that a message write is needed,
590  ! then go back and re-compress the Section 4 data for this message while excluding the data for the current subset,
591  ! which will be held and stored as the first subset of a new message after writing the current message.
592  writ1 = .true.
593  ncol = ncol-1
594  icol = 1
595  elseif(.not.writ1) then
596  ! Add the current subset to the current message and return
597  call usrtpl(lun,1,1)
598  nsub(lun) = -ncol
599  return
600  else
601  ! Exit the loop and proceed to write out the current message
602  cmpres = .false.
603  endif
604  enddo
605 
606  ! Write the complete compressed message. First, we need to do another call to cmsgini() to initialize Sections 0, 1, 2,
607  ! and 3 of the final compressed BUFR message that will be written out.
608 
609  call cmsgini(lun,mgwa,subset,idate(lun),ncol,ibyt)
610 
611  ! Now add the Section 4 data
612 
613  ibit = ibyt*8
614  do i=1,nrow
615  if(ityp(i)==1.or.ityp(i)==2) then
616  call pkb8(kmin(i),iwid(i),mgwa,ibit)
617  call pkb(kbit(i),6,mgwa,ibit)
618  if(kbit(i)>0) then
619  do j=1,ncol
620  if(matx(i,j)<2_8**iwid(i)-1) then
621  incr = matx(i,j)-kmin(i)
622  else
623  incr = 2_8**kbit(i)-1
624  endif
625  call pkb8(incr,kbit(i),mgwa,ibit)
626  enddo
627  endif
628  elseif(ityp(i)==3) then
629  nchr = iwid(i)/8
630  if(kbit(i)>0) then
631  call ipkm(czero,1,0)
632  do j=1,nchr
633  call pkc(czero,1,mgwa,ibit)
634  enddo
635  call pkb(nchr,6,mgwa,ibit)
636  do j=1,ncol
637  call pkc(catx(i,j),nchr,mgwa,ibit)
638  enddo
639  else
640  call pkc(cstr(i),nchr,mgwa,ibit)
641  call pkb(0,6,mgwa,ibit)
642  endif
643  endif
644  enddo
645 
646  ! Pad the end of Section 4 with zeroes up to the necessary byte count
647 
648  call pkb(0,jbit,mgwa,ibit)
649 
650  ! Add Section 5
651 
652  call pkc(bmcstr,nby5,mgwa,ibit)
653 
654  ! Check that the message byte counters agree, then write the message
655 
656  if(mod(ibit,8)/=0) call bort('BUFRLIB: WRCMPS - THE NUMBER OF BITS IN THE '// &
657  'COMPRESSED BUFR MSG IS NOT A MULTIPLE OF 8 - MSG MUST END ON A BYTE BOUNDARY')
658  lbyt = iupbs01(mgwa,'LENM')
659  nbyt = ibit/8
660  if(nbyt/=lbyt) then
661  write(bort_str,'("BUFRLIB: WRCMPS - OUTPUT MESSAGE LENGTH FROM '// &
662  'SECTION 0",I6," DOES NOT EQUAL FINAL PACKED MESSAGE LENGTH (",I6,")")') lbyt,nbyt
663  call bort(bort_str)
664  endif
665 
666  call msgwrt(lunit,mgwa,nbyt)
667 
668  ! Now, unless this was a "flush" call to this subroutine, go back and initialize a new message to hold the current subset
669  ! that we weren't able to fit into the message that was just written out.
670 
671  first = .true.
672  if(flush) return
673  end do
674 
675 end subroutine wrcmps
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
real *8 function ups(ival, node)
Unpack a real*8 value from an integer by applying the proper scale and reference values.
Definition: cidecode.F90:320
subroutine up8(nval, nbits, ibay, ibit)
Decode an 8-byte integer value from within a specified number of bits of an integer array,...
Definition: cidecode.F90:128
subroutine upc(chr, nchr, ibay, ibit, cnvnull)
Decode a character string from within a specified number of bytes of an integer array,...
Definition: cidecode.F90:26
subroutine 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 cmsgini(lun, mesg, subset, idate, nsub, nbyt)
Initialize a new BUFR message for output in compressed format.
Definition: compress.F90:261
recursive subroutine writcp(lunit)
Write a data subset into a BUFR message using compression.
Definition: compress.F90:74
subroutine wrcmps(lunix)
Write a compressed BUFR data subset.
Definition: compress.F90:386
subroutine cmpmsg(cf)
Specify whether BUFR messages output by future calls to message-writing subroutines and subset-writin...
Definition: compress.F90:33
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 nemtab(lun, nemo, idn, tab, iret)
Get information about a descriptor, based on a mnemonic.
Definition: fxy.F90:434
subroutine capit(str)
Capitalize all of the alphabetic characters in a string.
Definition: misc.F90:334
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 needed for the storage of data values needed when writing compressed dat...
integer ncol
Number of data subsets in message.
integer *8 incr
Increment used when compressing non-character data values.
character *(:), dimension(:,:), allocatable catx
Character data values for all data subsets in message.
integer *8, dimension(:,:), allocatable matx
Non-character data values for all data subsets in message.
Declare arrays and variable needed for the storage of data values needed when writing compressed data...
character *(:), dimension(:), allocatable cstr
Character data value, if corresponding ityp value is set to 3.
integer kbyt
Number of bytes required to store Sections 0, 1, 2, and 3 of message.
logical flush
Flush flag.
integer nrow
Number of data values for each data subset in message.
integer *8 imiss
"Missing" value used when compressing non-character data values.
integer *8, dimension(:), allocatable kmax
Maximum of each data value across all data subsets in message.
integer, dimension(:), allocatable jlnode
Jump/link table node corresponding to each data value.
logical writ1
Write-out flag.
integer, dimension(:), allocatable ityp
Type of each data value:
integer, dimension(:), allocatable iwid
Bit width of underlying data descriptor as defined within Table B for each data value.
integer lunc
File ID for output file.
integer, dimension(:), allocatable kbit
Number of bits needed to hold the increments for this data value within each data subset of the messa...
logical, dimension(:), allocatable kmis
"Missing" values flag.
integer *8, dimension(:), allocatable kmin
Minimum of each data value across all data subsets in message.
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 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 msub
Total number of data subsets in message.
integer, dimension(:), allocatable nsub
Current subset pointer within message.
Declare arrays and variables needed to store information about long character strings (greater than 8...
integer nrst
Number of long character strings in data subset.
integer, dimension(:), allocatable irnch
Lengths (in bytes) of long character strings.
integer, dimension(:), allocatable irbit
Pointers in data subset to first bits of long character strings.
character *10, dimension(:), allocatable crtag
Table B mnemonics associated with long character strings.
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 status code for each file ID if an error or other abnormal result oc...
integer, dimension(:), allocatable iscodes
Abnormal status codes.
Declare arrays and variables used to store the internal jump/link table.
integer, dimension(:), allocatable ibt
Bit widths corresponding to tag and typ:
character *10, dimension(:), allocatable tag
Mnemonics in the jump/link table.
integer, dimension(:), allocatable itp
Integer type values corresponding to typ:
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...
recursive subroutine status(lunit, lun, il, im)
Check whether a specified Fortran logical unit number is currently connected to the NCEPLIBS-bufr sof...
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.
recursive subroutine writsb(lunit)
Write a complete data subset into a BUFR message, for eventual output to logical unit lunit.
subroutine x84(iin8, iout4, nval)
Encode one or more 8-byte integer values as 4-byte integer values.
Definition: x4884.F90:65