38 character,
intent(in) :: cf
39 character*128 bort_str
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
75 use modv_vars,
only: im8b
79 integer,
intent(in) :: lunit
87 call x84(lunit,my_lunit,1)
113 use modv_vars,
only: bmiss, mxrst
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
130 character*128 bort_str
131 character*8 cref, cval
133 equivalence(cval,rval)
136 lps(lbit) = max(2_8**(lbit)-1,1)
155 11
do n=n+1,
nval(lun)
157 nrfelm(n,lun) = igetrfel(n,lun)
169 if(ityp==1.or.ityp==2)
then
174 jbit =
ibit + linc*(nsbs-1)
175 call upb(nin4,linc,
mbay(1,lun),jbit)
178 elseif(nbit<=64)
then
181 jbit =
ibit + linc*(nsbs-1)
182 call up8(ninc,linc,
mbay(1,lun),jbit)
184 if(ninc==lps(linc))
then
195 if(ival<lps(nbit))
val(n,lun) =
ups(ival,node)
211 write(bort_str,
'("BUFRLIB: RDCMPS - NUMBER OF LONG CHARACTER STRINGS EXCEEDS THE LIMIT (",I4,")")') mxrst
225 jbit =
ibit + linc*(nsbs-1)*8
232 call upc(cval,nchr,
mbay(1,lun),jbit,.true.)
234 if (lelm<=8 .and. icbfms(cval,nchr)/=0)
then
260 subroutine cmsgini(lun,mesg,subset,idate,nsub,nbyt)
262 use modv_vars,
only: mtv, nby1, nby5, bmostr
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
271 character*128 bort_str
272 character*8,
intent(in) :: subset
277 call nemtba(lun,subset,mtyp,msbt,inod)
278 call nemtab(lun,subset,isub,tab,iret)
280 write(bort_str,
'("BUFRLIB: CMSGINI - TABLE A MESSAGE TYPE MNEMONIC ",A," NOT FOUND IN INTERNAL TABLE D ARRAYS")') subset
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)
303 call pkc(bmostr, 4 , mesg,mbit)
306 call pkb( 0 , 24 , mesg,mbit)
307 call pkb( 3 , 8 , mesg,mbit)
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)
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)
344 call pkb((nbyt+4) , 24 , mesg,mbit)
345 call pkb( 0 , 8 , mesg,mbit)
355 mbyt = mbit/8 + nbyt + nby5
363 call pkb(mbyt,24,mesg,mbit)
387 use modv_vars,
only: mxcdv, mxcsb, nby5, bmcstr
400 integer,
intent(in) :: lunix
401 integer ibyt, jbit, lunit, lun, il, im, icol, i, j, node, lbyt, nbyt, nchr, ldata, iupbs01, imrkopr
403 character*128 bort_str
407 logical first, kmiss, edge4, msgfull, cmpres
409 real,
parameter :: rln2 = 1./log(2.)
414 save first, ibyt, jbit, subset, edge4
419 call status(lunit,lun,il,im)
442 do while ( (.not.edge4) .and. (i<=
ns01v) )
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
466 elseif(
ncol+1>mxcsb)
then
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
500 if(imrkopr(
tag(node))==1)
then
507 elseif(
ityp(i)==3)
then
520 write(bort_str,
'("BUFRLIB: WRCMPS - NO. OF COLUMNS CALCULATED '// &
521 .LE.
'FOR COMPRESSION MAXRIX IS 0 (=",I6,")")')
ncol
546 range = real(max(1,
kmax(i)-
kmin(i)+1))
547 if(
ityp(i)==2 .and. (range>1. .or. kmiss))
then
550 kbit(i) = nint(log(range)*rln2)
560 elseif(
ityp(i)==3)
then
584 ibyt = (ldata+8-mod(ldata,8))/8
586 if( (.not.edge4) .and. (mod(ibyt,2)/=0) ) ibyt = ibyt+1
595 elseif(.not.
writ1)
then
628 elseif(
ityp(i)==3)
then
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')
661 write(bort_str,
'("BUFRLIB: WRCMPS - OUTPUT MESSAGE LENGTH FROM '// &
662 'SECTION 0",I6," DOES NOT EQUAL FINAL PACKED MESSAGE LENGTH (",I6,")")') lbyt,nbyt
subroutine strbtm(n, lun, ival)
Store internal information in module moda_bitmaps if the input element is part of a bitmap.
recursive subroutine bort(str)
Log an error message, then either return to or abort the application program.
subroutine upb(nval, nbits, ibay, ibit)
Decode an integer value from within a specified number of bits of an integer array,...
real *8 function ups(ival, node)
Unpack a real*8 value from an integer by applying the proper scale and reference values.
subroutine up8(nval, nbits, ibay, ibit)
Decode an 8-byte integer value from within a specified number of bits of an integer array,...
subroutine upc(chr, nchr, ibay, ibit, cnvnull)
Decode a character string from within a specified number of bytes of an integer array,...
subroutine pkc(chr, nchr, ibay, ibit)
Encode a character string within a specified number of bytes of an integer array, starting at the bit...
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 ...
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...
subroutine pkb8(nval, nbits, ibay, ibit)
Encode an 8-byte integer value within a specified number of bits of an integer array,...
subroutine rdcmps(lun)
Read the next compressed BUFR data subset into internal arrays.
subroutine cmsgini(lun, mesg, subset, idate, nsub, nbyt)
Initialize a new BUFR message for output in compressed format.
recursive subroutine writcp(lunit)
Write a data subset into a BUFR message using compression.
subroutine wrcmps(lunix)
Write a compressed BUFR data subset.
subroutine cmpmsg(cf)
Specify whether BUFR messages output by future calls to message-writing subroutines and subset-writin...
subroutine nemtba(lun, nemo, mtyp, msbt, inod)
Get information about a Table A descriptor from the internal DX BUFR tables.
subroutine nemtab(lun, nemo, idn, tab, iret)
Get information about a descriptor, based on a mnemonic.
subroutine capit(str)
Capitalize all of the alphabetic characters in a string.
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.
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.