NCEPLIBS-w3emc  2.11.0
w3fi72.f
Go to the documentation of this file.
1 C> @file
2 C> @brief Make a complete GRIB message.
3 C> @author Ralph Jones @date 1991-05-08
4 
5 C> Makes a complete GRIB message from a user supplied
6 C> array of floating point or integer data. The user has the
7 C> option of supplying the PDS or an integer array that will be
8 C> used to create a PDS (with w3fi68()). The user must also
9 C> supply other necessary information.
10 C>
11 C> @param[in] ITYPE
12 C> - 0 = Floating point data supplied in array 'fld'
13 C> - 1 = Integer data supplied in array 'ifld'
14 C> @param[in] FLD Real array of data (at proper gridpoints) to be
15 C> converted to grib format if itype=0.
16 C> see remarks #1 & 2.
17 C> @param[in] IFLD Integer array of data (at proper gridpoints) to be
18 C> converted to grib format if itype=1. See remarks #1 & 2.
19 C> @param[in] IBITL
20 C> - 0 = Computer computes length for packing data from
21 C> power of 2 (number of bits) best fit of data
22 C> using 'variable' bit packer w3fi58().
23 C> - 8, 12, Etc. computer rescales data to fit into that
24 C> 'fixed' number of bits using w3fi59(). See remarks #3.
25 C> @param[in] IPFLAG
26 C> - 0 = Make pds from user supplied array (id)
27 C> - 1 = User supplying pds
28 C> @note If pds is greater than 30, use iplfag=1. The user could call w3fi68()
29 C> before he calls w3fi72(). This would make the first 30 bytes of the pds,
30 C> user then would make bytes after 30.
31 C> @param[in] ID Integer array of values that w3fi68() will use
32 C> to make an edition 1 pds if ipflag=0. (see the
33 C> docblock for w3fi68() for layout of array)
34 C> @param[in] PDS Character array of values (valid pds supplied
35 C> by user) if ipflag=1. length may exceed 28 bytes
36 C> (contents of bytes beyond 28 are passed
37 C> through unchanged).
38 C> @param[in] IGFLAG
39 C> - 0 = Make gds based on 'igrid' value.
40 C> - 1 = Make gds from user supplied info in 'igds' and 'igrid' value.
41 C> See remarks #4.
42 C> @param[in] IGRID
43 C> - # = Grid identification (table b)
44 C> - 255 = If user defined grid; igds must be supplied and igflag must =1.
45 C> @param[in] IGDS Integer array containing user gds info (same
46 C> format as supplied by w3fi71() - see dockblock for
47 C> layout) if igflag=1.
48 C> @param[in] ICOMP Resolution and component flag for bit 5 of gds(17)
49 C> - 0 = Earth oriented winds
50 C> - 1 = Grid oriented winds
51 C> @param[in] IBFLAG
52 C> - 0 = Make bit map from user supplied data
53 C> - # = Bit map predefined by center. See remarks #5.
54 C> @param[in] IBMAP Integer array containing bit map
55 C> @param[in] IBLEN Length of bit map will be used to verify length
56 C> of field (error if it doesn't match).
57 C> @param[in] IBDSFL Integer array containing table 11 flag info
58 C> - BDS octet 4:
59 C> - (1)
60 C> - 0 = Grid point data
61 C> - 1 = Spherical harmonic coefficients
62 C> - (2) 0 = Simple packing
63 C> - 1 = Second order packing
64 C> - (3) ... Same value as 'itype'
65 C> - 0 = Original data were floating point values
66 C> - 1 = Original data were integer values
67 C> - (4) 0 = No additional flags at octet 14
68 C> - 1 = Octet 14 contains flag bits 5-12
69 C> - (5) 0 = Reserved - always set to 0
70 C> Byte 6 option 1 not available (as of 5-16-93)
71 C> - (6) 0 = Single datum at each grid point
72 C> - 1 = Matrix of values at each grid point
73 C> Byte 7 option 0 with second order packing n/a (as of 5-16-93)
74 C> - (7) 0 = No secondary bit maps
75 C> - 1 = Secondary bit maps present
76 C> - (8) 0 = Second order values have constant width
77 C> - 1 = Second order values have different widths
78 C> @param[out] NPTS Number of gridpoints in array fld or ifld
79 C> @param[out] KBUF Entire grib message ('grib' to '7777')
80 C> equivalence to integer array to make sure it is on word boundary.
81 C> @param[out] ITOT Total length of grib message in bytes
82 C> @param[out] JERR
83 C> - = 0, Completed making grib field without error
84 C> - = 1, Ipflag not 0 or 1
85 C> - = 2, Igflag not 0 or 1
86 C> - = 3, Error converting ieee f.p. number to ibm370 f.p.
87 C> - = 4, W3fi71() error/igrid not defined
88 C> - = 5, W3fk74() error/grid representation type not valid
89 C> - = 6, Grid too large for packer dimension arrays
90 C> - = See automation division for revision!
91 C> - = 7, Length of bit map not equal to size of fld/ifld
92 C> - = 8, W3fi73() error, all values in ibmap are zero
93 C>
94 C> @note
95 C> - 1: If bit map to be included in message, null data should
96 C> be included in fld or ifld. this routine will take care
97 C> of 'discarding' any null data based on the bit map.
98 C> - 2: Units must be those in grib documentation: nmc o.n. 388
99 C> or wmo publication 306.
100 C> - 3: In either case, input numbers will be multiplied by
101 C> '10 to the nth' power found in id(25) or pds(27-28),
102 C> the d-scaling factor, prior to binary packing.
103 C> - 4: All nmc produced grib fields will have a grid definition
104 C> section included in the grib message. id(6) will be
105 C> set to '1'.
106 C> - GDS will be built based on grid number (igrid), unless
107 C> igflag=1 (user supplying igds). user must still supply
108 C> igrid even if igds provided.
109 C> - 5: if bit map used then id(7) or pds(8) must indicate the
110 C> presence of a bit map.
111 C> - 6: Array kbuf should be equivalenced to an integer value or
112 C> array to make sure it is on a word boundary.
113 C> - 7: Subprogram can be called from a multiprocessing environment.
114 C>
115 C> @author Ralph Jones @date 1991-05-08
116  SUBROUTINE w3fi72(ITYPE,FLD,IFLD,IBITL,
117  & IPFLAG,ID,PDS,
118  & IGFLAG,IGRID,IGDS,ICOMP,
119  & IBFLAG,IBMAP,IBLEN,IBDSFL,
120  & NPTS,KBUF,ITOT,JERR)
121 C
122  REAL FLD(*)
123 C
124  INTEGER IBDSFL(*)
125  INTEGER IBMAP(*)
126  INTEGER ID(*)
127  INTEGER IFLD(*)
128  INTEGER IGDS(*)
129  INTEGER IB(4)
130  INTEGER NLEFT, NUMBMS
131 C
132  CHARACTER * 1 BDS11(11)
133  CHARACTER * 1 KBUF(*)
134  CHARACTER * 1 PDS(*)
135  CHARACTER * 1 GDS(200)
136  CHARACTER(1),ALLOCATABLE:: BMS(:)
137  CHARACTER(1),ALLOCATABLE:: PFLD(:)
138  CHARACTER(1),ALLOCATABLE:: IPFLD(:)
139  CHARACTER * 1 SEVEN
140  CHARACTER * 1 ZERO
141 C
142 C
143 C ASCII REP OF /'G', 'R', 'I', 'B'/
144 C
145  DATA ib / 71, 82, 73, 66/
146 C
147  ier = 0
148  iberr = 0
149  jerr = 0
150  igribl = 8
151  ipdsl = 0
152  lengds = 0
153  lenbms = 0
154  lenbds = 0
155  itoss = 0
156 C
157 C$ 1.0 PRODUCT DEFINITION SECTION(PDS).
158 C
159 C SET ID(6) TO 1 ...OR... MODIFY PDS(8) ...
160 C REGARDLESS OF USER SPECIFICATION...
161 C NMC GRIB FIELDS WILL ALWAYS HAVE A GDS
162 C
163  IF (ipflag .EQ.0) THEN
164  id(6) = 1
165  CALL w3fi68(id,pds)
166  ELSE IF (ipflag .EQ. 1) THEN
167  IF (iand(mova2i(pds(8)),64) .EQ. 64) THEN
168 C BOTH GDS AND BMS
169  pds(8) = char(192)
170  ELSE IF (mova2i(pds(8)) .EQ. 0) THEN
171 C GDS ONLY
172  pds(8) = char(128)
173  END IF
174  CONTINUE
175  ELSE
176 C PRINT *,' W3FI72 ERROR, IPFLAG IS NOT 0 OR 1 IPFLAG = ',IPFLAG
177  jerr = 1
178  GO TO 900
179  END IF
180 C
181 C GET LENGTH OF PDS
182 C
183  ipdsl = mova2i(pds(1)) * 65536 + mova2i(pds(2)) * 256 +
184  & mova2i(pds(3))
185 C
186 C$ 2.0 GRID DEFINITION SECTION (GDS).
187 C
188 C IF IGFLAG=1 THEN USER IS SUPPLYING THE IGDS INFORMATION
189 C
190  IF (igflag .EQ. 0) THEN
191  CALL w3fi71(igrid,igds,igerr)
192  IF (igerr .EQ. 1) THEN
193 C PRINT *,' W3FI71 ERROR, GRID TYPE NOT DEFINED...',IGRID
194  jerr = 4
195  GO TO 900
196  END IF
197  END IF
198  IF (igflag .EQ. 0 .OR. igflag .EQ.1) THEN
199  CALL w3fi74(igds,icomp,gds,lengds,npts,igerr)
200  IF (igerr .EQ. 1) THEN
201 C PRINT *,' W3FI74 ERROR, GRID REP TYPE NOT VALID...',IGDS(3)
202  jerr = 5
203  GO TO 900
204  ELSE
205  END IF
206  ELSE
207 C PRINT *,' W3FI72 ERROR, IGFLAG IS NOT 0 OR 1 IGFLAG = ',IGFLAG
208  jerr = 2
209  GO TO 900
210  END IF
211 C
212 C$ 3.0 BIT MAP SECTION (BMS).
213 C
214 C SET ITOSS=1 IF BITMAP BEING USED. W3FI75 WILL TOSS DATA
215 C PRIOR TO PACKING. LATER CODING WILL BE NEEDED WHEN THE
216 C 'PREDEFINED' GRIDS ARE FINALLY 'DEFINED'.
217 C
218  IF (mova2i(pds(8)) .EQ. 64 .OR.
219  & mova2i(pds(8)) .EQ. 192) THEN
220  itoss = 1
221  IF (ibflag .EQ. 0) THEN
222  IF (iblen .NE. npts) THEN
223 C PRINT *,' W3FI72 ERROR, IBLEN .NE. NPTS = ',IBLEN,NPTS
224  jerr = 7
225  GO TO 900
226  END IF
227  IF (mod(iblen,16).NE.0) THEN
228  nleft = 16 - mod(iblen,16)
229  ELSE
230  nleft = 0
231  END IF
232  numbms = 6 + (iblen+nleft) / 8
233  ALLOCATE(bms(numbms))
234  zero = char(00)
235  bms = zero
236  CALL w3fi73(ibflag,ibmap,iblen,bms,lenbms,ier)
237  IF (ier .NE. 0) THEN
238 C PRINT *,' W3FI73 ERROR, IBMAP VALUES ARE ALL ZERO'
239  jerr = 8
240  GO TO 900
241  END IF
242  ELSE
243 C PRINT *,' BIT MAP PREDEFINED BY CENTER, IBFLAG = ',IBFLAG
244  END IF
245  END IF
246 C
247 C$ 4.0 BINARY DATA SECTION (BDS).
248 C
249 C$ 4.1 SCALE THE DATA WITH D-SCALE FROM PDS(27-28)
250 C
251  jscale = mova2i(pds(27)) * 256 + mova2i(pds(28))
252  IF (iand(jscale,32768).NE.0) THEN
253  jscale = - iand(jscale,32767)
254  END IF
255  scale = 10.0 ** jscale
256  IF (itype .EQ. 0) THEN
257  DO 410 i = 1,npts
258  fld(i) = fld(i) * scale
259  410 CONTINUE
260  ELSE
261  DO 411 i = 1,npts
262  ifld(i) = nint(float(ifld(i)) * scale)
263  411 CONTINUE
264  END IF
265 C
266 C$ 4.2 CALL W3FI75 TO PACK DATA AND MAKE BDS.
267 C
268  ALLOCATE(pfld(npts*4))
269 C
270  IF(ibdsfl(2).NE.0) THEN
271  ALLOCATE(ipfld(npts*4))
272  ipfld=char(0)
273  ELSE
274  ALLOCATE(ipfld(1))
275  ENDIF
276 C
277  CALL w3fi75(ibitl,itype,itoss,fld,ifld,ibmap,ibdsfl,
278  & npts,bds11,ipfld,pfld,len,lenbds,iberr,pds,igds)
279 C
280  IF(ibdsfl(2).NE.0) THEN
281 C CALL XMOVEX(PFLD,IPFLD,NPTS*4)
282  do ii = 1, npts*4
283  pfld(ii) = ipfld(ii)
284  enddo
285  ENDIF
286  DEALLOCATE(ipfld)
287 C
288  IF (iberr .EQ. 1) THEN
289  jerr = 3
290  GO TO 900
291  END IF
292 C 4.3 IF D-SCALE NOT 0, RESCALE INPUT FIELD TO
293 C ORIGINAL VALUE
294 C
295  IF (jscale.NE.0) THEN
296  dscale = 1.0 / scale
297  IF (itype.EQ.0) THEN
298  DO 412 i = 1, npts
299  fld(i) = fld(i) * dscale
300  412 CONTINUE
301  ELSE
302  DO 413 i = 1, npts
303  fld(i) = nint(float(ifld(i)) * dscale)
304  413 CONTINUE
305  END IF
306  END IF
307 C
308 C$ 5.0 OUTPUT SECTION.
309 C
310 C$ 5.1 ZERO OUT THE OUTPUT ARRAY KBUF.
311 C
312  zero = char(00)
313  itot = igribl + ipdsl + lengds + lenbms + lenbds + 4
314 C PRINT *,'IGRIBL =',IGRIBL
315 C PRINT *,'IPDSL =',IPDSL
316 C PRINT *,'LENGDS =',LENGDS
317 C PRINT *,'LENBMS =',LENBMS
318 C PRINT *,'LENBDS =',LENBDS
319 C PRINT *,'ITOT =',ITOT
320  kbuf(1:itot)=zero
321 C
322 C$ 5.2 MOVE SECTION 0 - 'IS' INTO KBUF (8 BYTES).
323 C
324  istart = 0
325  DO 520 i = 1,4
326  kbuf(i) = char(ib(i))
327  520 CONTINUE
328 C
329  kbuf(5) = char(mod(itot / 65536,256))
330  kbuf(6) = char(mod(itot / 256,256))
331  kbuf(7) = char(mod(itot ,256))
332  kbuf(8) = char(1)
333 C
334 C$ 5.3 MOVE SECTION 1 - 'PDS' INTO KBUF (28 BYTES).
335 C
336  istart = istart + igribl
337  IF (ipdsl.GT.0) THEN
338 C CALL XMOVEX(KBUF(ISTART+1),PDS,IPDSL)
339  do ii = 1, ipdsl
340  kbuf(istart+ii) = pds(ii)
341  enddo
342  ELSE
343 C PRINT *,'LENGTH OF PDS LESS OR EQUAL 0, IPDSL = ',IPDSL
344  END IF
345 C
346 C$ 5.4 MOVE SECTION 2 - 'GDS' INTO KBUF.
347 C
348  istart = istart + ipdsl
349  IF (lengds .GT. 0) THEN
350 C CALL XMOVEX(KBUF(ISTART+1),GDS,LENGDS)
351  do ii = 1, lengds
352  kbuf(istart+ii) = gds(ii)
353  enddo
354  END IF
355 C
356 C$ 5.5 MOVE SECTION 3 - 'BMS' INTO KBUF.
357 C
358  istart = istart + lengds
359  IF (lenbms .GT. 0) THEN
360 C CALL XMOVEX(KBUF(ISTART+1),BMS,LENBMS)
361  do ii = 1, lenbms
362  kbuf(istart+ii) = bms(ii)
363  enddo
364  END IF
365 C
366 C$ 5.6 MOVE SECTION 4 - 'BDS' INTO KBUF.
367 C
368 C$ MOVE THE FIRST 11 OCTETS OF THE BDS INTO KBUF.
369 C
370  istart = istart + lenbms
371 C CALL XMOVEX(KBUF(ISTART+1),BDS11,11)
372  do ii = 1, 11
373  kbuf(istart+ii) = bds11(ii)
374  enddo
375 C
376 C$ MOVE THE PACKED DATA INTO THE KBUF
377 C
378  istart = istart + 11
379  IF (len.GT.0) THEN
380 C CALL XMOVEX(KBUF(ISTART+1),PFLD,LEN)
381  do ii = 1, len
382  kbuf(istart+ii) = pfld(ii)
383  enddo
384  END IF
385 C
386 C$ ADD '7777' TO END OFF KBUF
387 C NOTE THAT THESE 4 OCTETS NOT INCLUDED IN ACTUAL SIZE OF BDS.
388 C
389  seven = char(55)
390  istart = itot - 4
391  DO 562 i = 1,4
392  kbuf(istart+i) = seven
393  562 CONTINUE
394 C
395  900 CONTINUE
396  IF(ALLOCATED(bms)) DEALLOCATE(bms)
397  IF(ALLOCATED(pfld)) DEALLOCATE(pfld)
398  RETURN
399  END
function lengds(KGDS)
Program history log:
Definition: lengds.f:15
integer function mova2i(a)
This Function copies a bit string from a Character*1 variable to an integer variable.
Definition: mova2i.f:25
subroutine w3fi68(ID, PDS)
Converts an array of 25, or 27 integer words into a grib product definition section (pds) of 28 bytes...
Definition: w3fi68.f:85
subroutine w3fi71(IGRID, IGDS, IERR)
Makes a 18, 37, 55, 64, or 91 word integer array used by w3fi72() GRIB packer to make the grid descri...
Definition: w3fi71.f:187
subroutine w3fi72(ITYPE, FLD, IFLD, IBITL, IPFLAG, ID, PDS, IGFLAG, IGRID, IGDS, ICOMP, IBFLAG, IBMAP, IBLEN, IBDSFL, NPTS, KBUF, ITOT, JERR)
Makes a complete GRIB message from a user supplied array of floating point or integer data.
Definition: w3fi72.f:121
subroutine w3fi73(IBFLAG, IBMAP, IBLEN, BMS, LENBMS, IER)
This subroutine constructs a grib bit map section.
Definition: w3fi73.f:23
subroutine w3fi74(IGDS, ICOMP, GDS, LENGDS, NPTS, IGERR)
This subroutine constructs a GRIB grid definition section.
Definition: w3fi74.f:19
subroutine w3fi75(IBITL, ITYPE, ITOSS, FLD, IFLD, IBMAP, IBDSFL, NPTS, BDS11, IPFLD, PFLD, LEN, LENBDS, IBERR, PDS, IGDS)
This routine packs a grib field and forms octets(1-11) of the binary data section (bds).
Definition: w3fi75.f:90