NCEPLIBS-bufr  12.0.0
stndrd.f
Go to the documentation of this file.
1 C> @file
2 C> @brief Standardize a BUFR message.
3 C>
4 C> @author J. Ator @date 2004-08-18
5 
6 C> This subroutine performs the same function as subroutine stdmsg(),
7 C> except that it operates on a BUFR message passed in via a memory array
8 C> and returns its output via a separate memory array,
9 C> whereas stdmsg() operates on BUFR messages stored internally
10 C> within the software.
11 C>
12 C> @remarks
13 C> - MSGIN and MSGOT must be separate arrays.
14 C> - Standardized messages are usually longer in length than their
15 C> non-standard counterparts, so it's usually a good idea to allow
16 C> for extra space when allocating MSGOT within the application program.
17 C>
18 C> @param[in] LUNIT -- integer: Fortran logical unit number for
19 C> BUFR file
20 C> @param[in] MSGIN -- integer(*): BUFR message
21 C> @param[in] LMSGOT -- integer: Dimensioned size (in integers) of
22 C> MSGOT; used by the subroutine to ensure that
23 C> it doesn't overflow the MSGOT array
24 C> @param[out] MSGOT -- integer(*): Standardized copy of MSGIN
25 C>
26 C> @author J. Ator @date 2004-08-18
27  RECURSIVE SUBROUTINE stndrd(LUNIT,MSGIN,LMSGOT,MSGOT)
28 
29  use bufrlib
30  USE modv_maxnc
31  USE modv_im8b
32 
33  dimension icd(maxnc)
34 
35  COMMON /hrdwrd/ nbytw,nbitw,iord(8)
36 
37  dimension msgin(*),msgot(*)
38 
39  CHARACTER*128 bort_str
40  CHARACTER*8 subset
41  CHARACTER*4 sevn
42  CHARACTER*1 tab
43 
44  LOGICAL found
45 
46 C-----------------------------------------------------------------------
47 C-----------------------------------------------------------------------
48 
49 C CHECK FOR I8 INTEGERS
50 C ---------------------
51 
52  IF(im8b) THEN
53  im8b=.false.
54 
55  CALL x84 ( lunit, my_lunit, 1 )
56  CALL x84 ( lmsgot, my_lmsgot, 1 )
57  CALL stndrd ( my_lunit, msgin, my_lmsgot*2, msgot )
58 
59  im8b=.true.
60  RETURN
61  ENDIF
62 
63 C LUNIT MUST POINT TO AN OPEN BUFR FILE
64 C -------------------------------------
65 
66  CALL status(lunit,lun,il,im)
67  IF(il.EQ.0) GOTO 900
68 
69 C IDENTIFY THE SECTION LENGTHS AND ADDRESSES IN MSGIN
70 C ---------------------------------------------------
71 
72  CALL getlens(msgin,5,len0,len1,len2,len3,len4,len5)
73 
74  iad3 = len0+len1+len2
75  iad4 = iad3+len3
76 
77  lenn = len0+len1+len2+len3+len4+len5
78 
79  lenm = iupbs01(msgin,'LENM')
80 
81  IF(lenn.NE.lenm) GOTO 901
82 
83  mbit = (lenn-4)*8
84  CALL upc(sevn,4,msgin,mbit,.true.)
85  IF(sevn.NE.'7777') GOTO 902
86 
87 C COPY SECTIONS 0 THROUGH PART OF SECTION 3 INTO MSGOT
88 C ----------------------------------------------------
89 
90  mxbyto = (lmsgot*nbytw) - 8
91 
92  lbyto = iad3+7
93  IF(lbyto.GT.mxbyto) GOTO 905
94  CALL mvb(msgin,1,msgot,1,lbyto)
95 
96 C REWRITE NEW SECTION 3 IN A "STANDARD" FORM
97 C ------------------------------------------
98 
99 C LOCATE THE TOP-LEVEL TABLE A DESCRIPTOR
100 
101  found = .false.
102  ii = 10
103  DO WHILE ((.NOT.found).AND.(ii.GE.8))
104  isub = iupb(msgin,iad3+ii,16)
105  CALL numtab(lun,isub,subset,tab,itab)
106  IF((itab.NE.0).AND.(tab.EQ.'D')) THEN
107  CALL nemtbax(lun,subset,mtyp,msbt,inod)
108  IF(inod.NE.0) found = .true.
109  ENDIF
110  ii = ii - 2
111  ENDDO
112  IF(.NOT.found) GOTO 903
113 
114  IF (istdesc(isub).EQ.0) THEN
115 
116 C ISUB IS A NON-STANDARD TABLE A DESCRIPTOR AND NEEDS
117 C TO BE EXPANDED INTO AN EQUIVALENT STANDARD SEQUENCE
118 
119  CALL restd_c(lun,isub,ncd,icd)
120  ELSE
121 
122 C ISUB IS ALREADY A STANDARD DESCRIPTOR, SO JUST COPY
123 C IT "AS IS" INTO THE NEW SECTION 3 (I.E. NO EXPANSION
124 C IS NECESSARY!)
125 
126  ncd = 1
127  icd(ncd) = isub
128  ENDIF
129 
130 C USE THE EDITION NUMBER TO DETERMINE THE LENGTH OF THE
131 C NEW SECTION 3
132 
133  len3 = 7+(ncd*2)
134  iben = iupbs01(msgin,'BEN')
135  IF(iben.LT.4) THEN
136  len3 = len3+1
137  ENDIF
138  lbyto = lbyto + len3 - 7
139  IF(lbyto.GT.mxbyto) GOTO 905
140 
141 C STORE THE DESCRIPTORS INTO THE NEW SECTION 3
142 
143  ibit = (iad3+7)*8
144  DO n=1,ncd
145  CALL pkb(icd(n),16,msgot,ibit)
146  ENDDO
147 
148 C DEPENDING ON THE EDITION NUMBER, PAD OUT THE NEW SECTION 3 WITH AN
149 C ADDITIONAL ZEROED-OUT BYTE IN ORDER TO ENSURE AN EVEN BYTE COUNT
150 
151  IF(iben.LT.4) THEN
152  CALL pkb(0,8,msgot,ibit)
153  ENDIF
154 
155 C STORE THE LENGTH OF THE NEW SECTION 3
156 
157  ibit = iad3*8
158  CALL pkb(len3,24,msgot,ibit)
159 
160 C NOW THE TRICKY PART - NEW SECTION 4
161 C -----------------------------------
162 
163  IF(iupbs3(msgin,'ICMP').EQ.1) THEN
164 
165 C THE DATA IN SECTION 4 IS COMPRESSED AND IS THEREFORE ALREADY
166 C STANDARDIZED, SO COPY IT "AS IS" INTO THE NEW SECTION 4
167 
168  IF((lbyto+len4+4).GT.mxbyto) GOTO 905
169 
170  CALL mvb(msgin,iad4+1,msgot,lbyto+1,len4)
171 
172  jbit = (lbyto+len4)*8
173 
174  ELSE
175 
176  nad4 = iad3+len3
177 
178  ibit = (iad4+4)*8
179  jbit = (nad4+4)*8
180 
181  lbyto = lbyto + 4
182 
183 C COPY THE SUBSETS, MINUS THE BYTE COUNTERS AND BIT PADS, INTO
184 C THE NEW SECTION 4
185 
186  nsub = iupbs3(msgin,'NSUB')
187 
188  DO 10 i=1,nsub
189  CALL upb(lsub,16,msgin,ibit)
190  IF(nsub.GT.1) THEN
191 
192 C USE THE BYTE COUNTER TO COPY THIS SUBSET
193 
194  islen = lsub-2
195  ELSE
196 
197 C THIS IS THE ONLY SUBSET IN THE MESSAGE, AND IT COULD
198 C POSSIBLY BE AN OVERLARGE (> 65530 BYTES) SUBSET, IN
199 C WHICH CASE WE CAN'T RELY ON THE VALUE STORED IN THE
200 C BYTE COUNTER. EITHER WAY, WE DON'T REALLY NEED IT.
201 
202  islen = iad4+len4-(ibit/8)
203  IF (mod(len4,2).EQ.0) islen = islen - 1
204  ENDIF
205  DO l=1,islen
206  CALL upb(nval,8,msgin,ibit)
207  lbyto = lbyto + 1
208  IF(lbyto.GT.mxbyto) GOTO 905
209  CALL pkb(nval,8,msgot,jbit)
210  ENDDO
211  DO k=1,8
212  kbit = ibit-k-8
213  CALL upb(kval,8,msgin,kbit)
214  IF(kval.EQ.k) THEN
215  jbit = jbit-k-8
216  GOTO 10
217  ENDIF
218  ENDDO
219  GOTO 904
220 10 ENDDO
221 
222 C FROM THIS POINT ON, WE WILL NEED (AT MOST) 6 MORE BYTES OF
223 C SPACE WITHIN MSGOT IN ORDER TO BE ABLE TO STORE THE ENTIRE
224 C STANDARDIZED MESSAGE (I.E. WE WILL NEED (AT MOST) 2 MORE
225 C ZEROED-OUT BYTES IN SECTION 4 PLUS THE 4 BYTES '7777' IN
226 C SECTION 5), SO DO A FINAL MSGOT OVERFLOW CHECK NOW.
227 
228  IF(lbyto+6.GT.mxbyto) GOTO 905
229 
230 C PAD THE NEW SECTION 4 WITH ZEROES UP TO THE NEXT WHOLE BYTE
231 C BOUNDARY.
232 
233  DO WHILE(.NOT.(mod(jbit,8).EQ.0))
234  CALL pkb(0,1,msgot,jbit)
235  ENDDO
236 
237 C DEPENDING ON THE EDITION NUMBER, WE MAY NEED TO FURTHER PAD
238 C THE NEW SECTION 4 WITH AN ADDITIONAL ZEROED-OUT BYTE IN ORDER
239 C TO ENSURE THAT THE PADDING IS UP TO AN EVEN BYTE BOUNDARY.
240 
241  IF( (iben.LT.4) .AND. (mod(jbit/8,2).NE.0) ) THEN
242  CALL pkb(0,8,msgot,jbit)
243  ENDIF
244 
245  ibit = nad4*8
246  len4 = jbit/8 - nad4
247  CALL pkb(len4,24,msgot,ibit)
248  CALL pkb(0,8,msgot,ibit)
249  ENDIF
250 
251 C FINISH THE NEW MESSAGE WITH AN UPDATED SECTION 0 BYTE COUNT
252 C -----------------------------------------------------------
253 
254  ibit = 32
255  lenn = len0+len1+len2+len3+len4+len5
256  CALL pkb(lenn,24,msgot,ibit)
257 
258  CALL pkc('7777',4,msgot,jbit)
259 
260 C EXITS
261 C -----
262 
263  RETURN
264 900 CALL bort('BUFRLIB: STNDRD - BUFR FILE IS CLOSED, IT MUST BE'//
265  . ' OPEN')
266 901 WRITE(bort_str,'("BUFRLIB: STNDRD - INPUT MESSAGE LENGTH FROM'//
267  . ' SECTION 0",I6," DOES NOT EQUAL SUM OF ALL INDIVIDUAL SECTION'//
268  . ' LENGTHS (",I6,")")') lenm,lenn
269  CALL bort(bort_str)
270 902 WRITE(bort_str,'("BUFRLIB: STNDRD - INPUT MESSAGE DOES NOT '//
271  . 'END WITH ""7777"" (ENDS WITH ",A)') sevn
272  CALL bort(bort_str)
273 903 CALL bort('BUFRLIB: STNDRD - TABLE A SUBSET DESCRIPTOR '//
274  . 'NOT FOUND')
275 904 CALL bort('BUFRLIB: STNDRD - BIT MISMATCH COPYING SECTION 4 '//
276  . 'FROM INPUT TO OUTPUT (STANDARD) MESSAGE')
277 905 CALL bort('BUFRLIB: STNDRD - OVERFLOW OF OUTPUT (STANDARD) '//
278  . 'MESSAGE ARRAY; TRY A LARGER DIMENSION FOR THIS ARRAY')
279  END
subroutine bort(STR)
Log one error message and abort application program.
Definition: bort.f:18
recursive subroutine getlens(MBAY, LL, LEN0, LEN1, LEN2, LEN3, LEN4, LEN5)
This subroutine reads the lengths of all of the individual sections of a given BUFR message,...
Definition: getlens.f:36
function istdesc(IDN)
Check whether a descriptor is WMO-standard.
Definition: istdesc.f:23
recursive function iupb(MBAY, NBYT, NBIT)
Decode an integer value from an integer array.
Definition: iupb.f:21
recursive function iupbs01(MBAY, S01MNEM)
Read a data value from Section 0 or Section 1 of a BUFR message.
Definition: iupbs01.f:69
recursive function iupbs3(MBAY, S3MNEM)
This function returns a specified value from within Section 3 of a BUFR message.
Definition: iupbs3.f:30
subroutine mvb(IB1, NB1, IB2, NB2, NBM)
This subroutine copies a specified number of bytes from one packed binary array to another.
Definition: mvb.f:18
Wrap C NCEPLIBS-bufr functions so they can be called from within the Fortran part of the library.
Definition: bufrlib.F90:11
This module declares and initializes the IM8B variable.
logical, public im8b
Status indicator to keep track of whether all future calls to BUFRLIB subroutines and functions from ...
This module declares and initializes the MAXNC variable.
integer, parameter, public maxnc
Maximum number of descriptors within Section 3 of a BUFR message.
subroutine nemtbax(LUN, NEMO, MTYP, MSBT, INOD)
This subroutine searches for a descriptor within Table A of the internal DX BUFR tables.
Definition: nemtbax.f:26
subroutine numtab(LUN, IDN, NEMO, TAB, IRET)
Get information about a descriptor, based on the WMO bit-wise representation of an FXY value.
Definition: numtab.f:42
subroutine pkb(NVAL, NBITS, IBAY, IBIT)
This subroutine encodes an integer value within a specified number of bits of an integer array,...
Definition: pkb.f:28
subroutine pkc(CHR, NCHR, IBAY, IBIT)
Encode a character string within an integer array.
Definition: pkc.f:31
recursive subroutine status(LUNIT, LUN, IL, IM)
Check whether a specified Fortran logical unit number is currently connected to the NCEPLIBS-bufr sof...
Definition: status.f:36
recursive subroutine stndrd(LUNIT, MSGIN, LMSGOT, MSGOT)
This subroutine performs the same function as subroutine stdmsg(), except that it operates on a BUFR ...
Definition: stndrd.f:28
subroutine upb(NVAL, NBITS, IBAY, IBIT)
This subroutine decodes an integer value from within a specified number of bits of an integer array,...
Definition: upb.f:28
subroutine upc(CHR, NCHR, IBAY, IBIT, CNVNULL)
Decode a character string from an integer array.
Definition: upc.f:32
subroutine x84(IIN8, IOUT4, NVAL)
Encode one or more 8-byte integer values as 4-byte integer values.
Definition: x84.F:19