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