118 & IGFLAG,IGRID,IGDS,ICOMP,
119 & IBFLAG,IBMAP,IBLEN,IBDSFL,
120 & NPTS,KBUF,ITOT,JERR)
130 INTEGER NLEFT, NUMBMS
132 CHARACTER * 1 BDS11(11)
133 CHARACTER * 1 KBUF(*)
135 CHARACTER * 1 GDS(200)
136 CHARACTER(1),
ALLOCATABLE:: BMS(:)
137 CHARACTER(1),
ALLOCATABLE:: PFLD(:)
138 CHARACTER(1),
ALLOCATABLE:: IPFLD(:)
145 DATA ib / 71, 82, 73, 66/
163 IF (ipflag .EQ.0)
THEN
166 ELSE IF (ipflag .EQ. 1)
THEN
167 IF (iand(
mova2i(pds(8)),64) .EQ. 64)
THEN
170 ELSE IF (
mova2i(pds(8)) .EQ. 0)
THEN
190 IF (igflag .EQ. 0)
THEN
191 CALL w3fi71(igrid,igds,igerr)
192 IF (igerr .EQ. 1)
THEN
198 IF (igflag .EQ. 0 .OR. igflag .EQ.1)
THEN
200 IF (igerr .EQ. 1)
THEN
218 IF (
mova2i(pds(8)) .EQ. 64 .OR.
219 &
mova2i(pds(8)) .EQ. 192)
THEN
221 IF (ibflag .EQ. 0)
THEN
222 IF (iblen .NE. npts)
THEN
227 IF (mod(iblen,16).NE.0)
THEN
228 nleft = 16 - mod(iblen,16)
232 numbms = 6 + (iblen+nleft) / 8
233 ALLOCATE(bms(numbms))
236 CALL w3fi73(ibflag,ibmap,iblen,bms,lenbms,ier)
252 IF (iand(jscale,32768).NE.0)
THEN
253 jscale = - iand(jscale,32767)
255 scale = 10.0 ** jscale
256 IF (itype .EQ. 0)
THEN
258 fld(i) = fld(i) * scale
262 ifld(i) = nint(float(ifld(i)) * scale)
268 ALLOCATE(pfld(npts*4))
270 IF(ibdsfl(2).NE.0)
THEN
271 ALLOCATE(ipfld(npts*4))
277 CALL w3fi75(ibitl,itype,itoss,fld,ifld,ibmap,ibdsfl,
278 & npts,bds11,ipfld,pfld,len,lenbds,iberr,pds,igds)
280 IF(ibdsfl(2).NE.0)
THEN
288 IF (iberr .EQ. 1)
THEN
295 IF (jscale.NE.0)
THEN
299 fld(i) = fld(i) * dscale
303 fld(i) = nint(float(ifld(i)) * dscale)
313 itot = igribl + ipdsl +
lengds + lenbms + lenbds + 4
326 kbuf(i) = char(ib(i))
329 kbuf(5) = char(mod(itot / 65536,256))
330 kbuf(6) = char(mod(itot / 256,256))
331 kbuf(7) = char(mod(itot ,256))
336 istart = istart + igribl
340 kbuf(istart+ii) = pds(ii)
348 istart = istart + ipdsl
352 kbuf(istart+ii) = gds(ii)
359 IF (lenbms .GT. 0)
THEN
362 kbuf(istart+ii) = bms(ii)
370 istart = istart + lenbms
373 kbuf(istart+ii) = bds11(ii)
382 kbuf(istart+ii) = pfld(ii)
392 kbuf(istart+i) = seven
396 IF(
ALLOCATED(bms))
DEALLOCATE(bms)
397 IF(
ALLOCATED(pfld))
DEALLOCATE(pfld)
function lengds(kgds)
Program history log:
integer function mova2i(a)
This Function copies a bit string from a Character*1 variable to an integer variable.
subroutine w3fi68(id, pds)
Converts an array of 25, or 27 integer words into a grib product definition section (pds) of 28 bytes...
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...
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.
subroutine w3fi73(ibflag, ibmap, iblen, bms, lenbms, ier)
This subroutine constructs a grib bit map section.
subroutine w3fi74(igds, icomp, gds, lengds, npts, igerr)
This subroutine constructs a GRIB grid definition section.
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).