NCEPLIBS-bufr  12.2.0
standard.F90
Go to the documentation of this file.
1 
5 
35 subroutine stdmsg(cf)
36 
37  use moda_msgstd
38 
39  implicit none
40 
41  character, intent(in) :: cf
42  character*128 bort_str
43  character my_cf
44 
45  my_cf = cf
46  call capit(my_cf)
47  if(my_cf /= 'Y' .and. my_cf /= 'N') then
48  write(bort_str,'("BUFRLIB: STDMSG - INPUT ARGUMENT IS ",A1,", IT MUST BE EITHER Y OR N")') cf
49  call bort(bort_str)
50  endif
51  csmf = my_cf
52 
53  return
54 end subroutine stdmsg
55 
74 recursive subroutine stndrd(lunit,msgin,lmsgot,msgot)
75 
76  use bufrlib
77 
78  use modv_vars, only: im8b, nbytw, nby5, bmcstr
79 
80  use moda_s3list
81 
82  implicit none
83 
84  integer, intent(in) :: msgin(*), lunit, lmsgot
85  integer, intent(out) :: msgot(*)
86  integer my_lunit, my_lmsgot, lun, il, im, len0, len1, len2, len3, len4, len5
87  integer iad3, iad4, lenn, lenm, iupbs01, iupbs3, iupb, mxbyto, lbyto, ii, isub, itab, mtyp, msbt, inod
88  integer istdesc, ncd, iben, ibit, jbit, kbit, mbit, nad4, lsub, nsub, islen, kval, nval, i, k, l, n
89 
90  character*128 bort_str
91  character*8 subset
92  character*4 s5str
93  character*1 tab
94  character*(*), parameter :: bort_arrayoverflow = &
95  'BUFRLIB: STNDRD - OVERFLOW OF OUTPUT (STANDARD) MESSAGE ARRAY; TRY A LARGER DIMENSION FOR THIS ARRAY'
96 
97  logical found
98 
99  ! Check for I8 integers.
100 
101  if(im8b) then
102  im8b=.false.
103 
104  call x84 ( lunit, my_lunit, 1 )
105  call x84 ( lmsgot, my_lmsgot, 1 )
106  call stndrd ( my_lunit, msgin, my_lmsgot*2, msgot )
107 
108  im8b=.true.
109  return
110  endif
111 
112  ! lunit must point to an open BUFR file.
113 
114  call status(lunit,lun,il,im)
115  if(il==0) call bort('BUFRLIB: STNDRD - BUFR FILE IS CLOSED, IT MUST BE OPEN')
116 
117  ! Identify the section lengths and addresses in msgin.
118 
119  call getlens(msgin,5,len0,len1,len2,len3,len4,len5)
120 
121  iad3 = len0+len1+len2
122  iad4 = iad3+len3
123 
124  lenn = len0+len1+len2+len3+len4+len5
125 
126  lenm = iupbs01(msgin,'LENM')
127 
128  if(lenn/=lenm) then
129  write(bort_str,'("BUFRLIB: STNDRD - INPUT MESSAGE LENGTH FROM SECTION 0",I6," DOES NOT EQUAL SUM OF ALL INDIVIDUAL '// &
130  'SECTION LENGTHS (",I6,")")') lenm,lenn
131  call bort(bort_str)
132  endif
133 
134  mbit = (lenn-4)*8
135  call upc(s5str,nby5,msgin,mbit,.true.)
136  if(s5str/=bmcstr) then
137  write(bort_str,'("BUFRLIB: STNDRD - INPUT MESSAGE DOES NOT END WITH ""7777"" (ENDS WITH ",A)') s5str
138  call bort(bort_str)
139  endif
140 
141  ! Copy Sections 0 through part of Section 3 into msgot.
142 
143  mxbyto = (lmsgot*nbytw) - 8
144 
145  lbyto = iad3+7
146  if(lbyto>mxbyto) call bort(bort_arrayoverflow)
147  call mvb(msgin,1,msgot,1,lbyto)
148 
149  ! Rewrite new Section 3 in a standard form. First, locate the top-level Table A descriptor.
150 
151  found = .false.
152  ii = 10
153  do while ((.not.found).and.(ii>=8))
154  isub = iupb(msgin,iad3+ii,16)
155  call numtab(lun,isub,subset,tab,itab)
156  if((itab/=0).and.(tab=='D')) then
157  call nemtbax(lun,subset,mtyp,msbt,inod)
158  if(inod/=0) found = .true.
159  endif
160  ii = ii - 2
161  enddo
162  if(.not.found) call bort('BUFRLIB: STNDRD - TABLE A SUBSET DESCRIPTOR NOT FOUND')
163 
164  if (istdesc(isub)==0) then
165  ! isub is a non-standard Table A descriptor and needs to be expanded into an equivalent standard sequence
166  call restd_c(lun,isub,ncd,ids3)
167  else
168  ! isub is already a standard descriptor, so just copy it "as is" into the new Section 3 (i.e. no expansion is necessary)
169  ncd = 1
170  ids3(ncd) = isub
171  endif
172 
173  ! Use the edition number to determine the length of the new Section 3.
174 
175  len3 = 7+(ncd*2)
176  iben = iupbs01(msgin,'BEN')
177  if(iben<4) then
178  len3 = len3+1
179  endif
180  lbyto = lbyto + len3 - 7
181  if(lbyto>mxbyto) call bort(bort_arrayoverflow)
182 
183  ! Store the descriptors into the new Section 3.
184 
185  ibit = (iad3+7)*8
186  do n=1,ncd
187  call pkb(ids3(n),16,msgot,ibit)
188  enddo
189 
190  ! Depending on the edition number, pad out the new Section 3 with an additional zeroed-out byte to ensure an even byte count.
191 
192  if(iben<4) then
193  call pkb(0,8,msgot,ibit)
194  endif
195 
196  ! Store the length of the new Section 3.
197 
198  ibit = iad3*8
199  call pkb(len3,24,msgot,ibit)
200 
201  ! Now the tricky part - new Section 4.
202 
203  if(iupbs3(msgin,'ICMP')==1) then
204 
205  ! The data in Section 4 is compressed and is therefore already standardized, so copy it "as is" into the new Section 4.
206 
207  if((lbyto+len4+4)>mxbyto) call bort(bort_arrayoverflow)
208 
209  call mvb(msgin,iad4+1,msgot,lbyto+1,len4)
210  jbit = (lbyto+len4)*8
211 
212  else
213 
214  nad4 = iad3+len3
215 
216  ibit = (iad4+4)*8
217  jbit = (nad4+4)*8
218 
219  lbyto = lbyto + 4
220 
221  ! Copy the subsets, minus the byte counters and bit pads, into the new Section 4.
222 
223  nsub = iupbs3(msgin,'NSUB')
224 
225  subset_copy: do i=1,nsub
226  call upb(lsub,16,msgin,ibit)
227  if(nsub>1) then
228  ! Use the byte counter to copy this subset.
229  islen = lsub-2
230  else
231  ! This is the only subset in the message, and it could possibly be an overlarge (> 65530 bytes) subset, in
232  ! which case we can't rely on the value stored in the byte counter. Either way, we don't really need it.
233  islen = iad4+len4-(ibit/8)
234  endif
235  do l=1,islen
236  call upb(nval,8,msgin,ibit)
237  lbyto = lbyto + 1
238  if(lbyto>mxbyto) call bort(bort_arrayoverflow)
239  call pkb(nval,8,msgot,jbit)
240  enddo
241  do k=1,8
242  kbit = ibit-k-8
243  call upb(kval,8,msgin,kbit)
244  if(kval==k) then
245  jbit = jbit-k-8
246  cycle subset_copy
247  endif
248  enddo
249  call bort('BUFRLIB: STNDRD - BIT MISMATCH COPYING SECTION 4 FROM INPUT TO OUTPUT (STANDARD) MESSAGE')
250  enddo subset_copy
251 
252  ! From this point on, we will need (at most) 6 more bytes of space within msgot in order to be able to store the entire
253  ! standardized message (i.e. we will need (at most) 2 more zeroed-out bytes in Section 4, plus the 4 bytes '7777' in
254  ! Section 5), so do a final msgot overflow check now.
255 
256  if(lbyto+6>mxbyto) call bort(bort_arrayoverflow)
257 
258  ! Pad the new Section 4 with zeroes up to the next whole byte boundary.
259 
260  do while(.not.(mod(jbit,8)==0))
261  call pkb(0,1,msgot,jbit)
262  enddo
263 
264  ! Depending on the edition number, we may need to further pad the new Section 4 with an additional zeroed-out byte in
265  ! order to ensure that the padding is up to an even byte boundary.
266 
267  if( (iben<4) .and. (mod(jbit/8,2)/=0) ) then
268  call pkb(0,8,msgot,jbit)
269  endif
270 
271  ibit = nad4*8
272  len4 = jbit/8 - nad4
273  call pkb(len4,24,msgot,ibit)
274  call pkb(0,8,msgot,ibit)
275  endif
276 
277  ! Finish the new message with an updated section 0 byte count.
278 
279  ibit = 32
280  lenn = len0+len1+len2+len3+len4+len5
281  call pkb(lenn,24,msgot,ibit)
282 
283  call pkc(bmcstr,nby5,msgot,jbit)
284 
285  return
286 end subroutine stndrd
287 
298 integer function istdesc( idn ) result( iret )
299 
300  implicit none
301 
302  integer, intent(in) :: idn
303  integer if, ix, iy, iokoper
304 
305  character*6 adsc, adn30
306 
307  adsc = adn30( idn, 6 )
308 
309  read(adsc,'(I1,I2,I3)') if,ix,iy
310  if ( if == 1 ) then
311  ! adsc is a replication descriptor and therefore standard by default
312  iret = 1
313  else if ( if == 2 ) then
314  ! adsc is an operator descriptor
315  iret = iokoper( adsc )
316  else if ( ( ix < 48 ) .and. ( iy < 192 ) ) then
317  iret = 1
318  else
319  iret = 0
320  end if
321 
322  return
323 end function istdesc
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
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 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
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 mvb(ib1, nb1, ib2, nb2, nbm)
Copy a specified number of bytes from one packed binary array to another.
Definition: copydata.F90:729
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 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
integer function iokoper(nemo)
Check whether a specified mnemonic is a Table C operator supported by the NCEPLIBS-bufr software.
Definition: misc.F90:461
subroutine capit(str)
Capitalize all of the alphabetic characters in a string.
Definition: misc.F90:334
Wrap C NCEPLIBS-bufr functions so they can be called from within the Fortran part of the library.
Definition: bufrlib.F90:11
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 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.
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.
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 integer function iupbs3(mbay, s3mnem)
Read a specified value from within Section 3 of a BUFR message.
Definition: s013vals.F90:348
subroutine stdmsg(cf)
Specify whether BUFR messages output by future calls to message-writing subroutines and subset-writin...
Definition: standard.F90:36
recursive subroutine stndrd(lunit, msgin, lmsgot, msgot)
Standardize a BUFR message.
Definition: standard.F90:75
integer function istdesc(idn)
Given the WMO bit-wise representation of an FXY value for a descriptor, check whether the descriptor ...
Definition: standard.F90:299
subroutine x84(iin8, iout4, nval)
Encode one or more 8-byte integer values as 4-byte integer values.
Definition: x4884.F90:65