44 subroutine misspack(fld,ndpts,idrsnum,idrstmpl,cpack,lcpack)
47 integer,
intent(in) :: ndpts,idrsnum
48 real,
intent(in) :: fld(ndpts)
49 character(len=1),
intent(out) :: cpack(*)
50 integer,
intent(inout) :: idrstmpl(*)
51 integer,
intent(out) :: lcpack
55 integer,
allocatable :: ifld(:),ifldmiss(:),jfld(:)
56 integer,
allocatable :: jmin(:),jmax(:),lbit(:)
57 integer,
parameter :: zero=0
58 integer,
allocatable :: gref(:),gwidth(:),glen(:)
59 integer :: glength,grpwidth
65 bscale=2.0**real(-idrstmpl(2))
66 dscale=10.0**real(idrstmpl(3))
68 if ( missopt.ne.1 .AND. missopt.ne.2 )
then
69 print *,
'misspack: Unrecognized option.'
73 call rdieee(idrstmpl(8),rmissp,1)
74 if (missopt.eq.2)
call rdieee(idrstmpl(9),rmisss,1)
79 allocate(ifldmiss(ndpts))
82 if ( missopt .eq. 1 )
then
84 if (fld(j).eq.rmissp)
then
89 if (fld(j).lt.rmin) rmin=fld(j)
96 if(.not.have_rmin) rmin=rmissp
98 if ( missopt .eq. 2 )
then
100 if (fld(j).eq.rmissp)
then
102 elseif (fld(j).eq.rmisss)
then
107 if (fld(j).lt.rmin) rmin=fld(j)
113 if(.not.have_rmin) rmin=rmissp
125 allocate(ifld(ndpts))
126 allocate(jfld(ndpts))
127 allocate(gref(ndpts))
128 allocate(gwidth(ndpts))
129 allocate(glen(ndpts))
134 if (idrstmpl(2).eq.0)
then
135 imin=nint(rmin*dscale)
139 if (ifldmiss(j).eq.0)
then
141 jfld(nonmiss)=max(0,nint(fld(j)*dscale)-imin)
148 if (ifldmiss(j).eq.0)
then
150 jfld(nonmiss)=max(0,nint(((fld(j)*dscale)-rmin)*bscale))
157 if (idrsnum.eq.3)
then
158 if (idrstmpl(17).ne.1.and.idrstmpl(17).ne.2) idrstmpl(17)=2
159 if (idrstmpl(17).eq.1)
then
166 jfld(j)=jfld(j)-jfld(j-1)
168 if(nonmiss>0) jfld(1)=0
169 elseif (idrstmpl(17).eq.2)
then
173 elseif(nonmiss<1)
then
181 jfld(j)=jfld(j)-(2*jfld(j-1))+jfld(j-2)
183 if(nonmiss>=1) jfld(1)=0
184 if(nonmiss>=2) jfld(2)=0
189 minsd=minval(jfld(isd:nonmiss))
191 jfld(j)=jfld(j)-minsd
197 nbitsd=ceiling(temp)+1
202 if (idrstmpl(17).eq.2.and.ival2.gt.ival1) maxorig=ival2
204 nbitorig=ceiling(temp)+1
205 if (nbitorig.gt.nbitsd) nbitsd=nbitorig
207 if (mod(nbitsd,8).ne.0) nbitsd=nbitsd+(8-mod(nbitsd,8))
211 if (nbitsd.ne.0)
then
219 call g2_sbytec(cpack,iabs(ival1),iofst,nbitsd-1)
222 if (idrstmpl(17).eq.2)
then
230 call g2_sbytec(cpack,iabs(ival2),iofst,nbitsd-1)
241 call g2_sbytec(cpack,iabs(minsd),iofst,nbitsd-1)
249 miss1=minval(jfld(1:nonmiss))-1
253 if ( ifldmiss(j).eq.0 )
then
256 elseif ( ifldmiss(j).eq.1 )
then
258 elseif ( ifldmiss(j).eq.2 )
then
262 if(ndpts<2) simple_alg=.true.
265 if ( simple_alg )
then
281 maxgrps=(ndpts/minpk)+1
282 allocate(jmin(maxgrps))
283 allocate(jmax(maxgrps))
284 allocate(lbit(maxgrps))
285 call pack_gp(kfildo,ifld,ndpts,missopt,minpk,inc,miss1,miss2,
286 & jmin,jmax,lbit,glen,maxgrps,ngroups,ibit,jbit,
287 & kbit,novref,lbitref,ier)
290 glen(ng)=glen(ng)+novref
302 num0=count(ifldmiss(n:n+glen(ng)-1) .EQ. 0)
303 num1=count(ifldmiss(n:n+glen(ng)-1) .EQ. 1)
304 num2=count(ifldmiss(n:n+glen(ng)-1) .EQ. 2)
305 if ( num0.eq.0 )
then
306 if ( num1.eq.0 )
then
309 elseif ( num2.eq.0 )
then
322 if ( ifldmiss(j).eq.0 )
then
323 if (ifld(j).lt.gref(ng)) gref(ng)=ifld(j)
324 if (ifld(j).gt.imax) imax=ifld(j)
328 if (missopt.eq.1) imax=imax+1
329 if (missopt.eq.2) imax=imax+2
331 if ( gref(ng).ne.imax )
then
332 temp=
i1log2(imax-gref(ng))
333 gwidth(ng)=ceiling(temp)
342 if (ifldmiss(j).eq.0)
then
343 ifld(j)=ifld(j)-gref(ng)
344 elseif (ifldmiss(j).eq.1)
then
346 elseif (ifldmiss(j).eq.2)
then
359 igmax=maxval(gref(1:ngroups))
360 if (missopt.eq.1) igmax=igmax+1
361 if (missopt.eq.2) igmax=igmax+2
364 nbitsgref=ceiling(temp)
368 if (gref(j).eq.-1) gref(j)=mtemp-1
369 if (gref(j).eq.-2) gref(j)=mtemp-2
371 call g2_sbytesc(cpack,gref,iofst,nbitsgref,0,ngroups)
372 itemp=nbitsgref*ngroups
375 if (mod(itemp,8).ne.0)
then
388 iwmax=maxval(gwidth(1:ngroups))
389 ngwidthref=minval(gwidth(1:ngroups))
390 if (iwmax.ne.ngwidthref)
then
391 temp=
i1log2(iwmax-ngwidthref)
392 nbitsgwidth=ceiling(temp)
394 gwidth(i)=gwidth(i)-ngwidthref
396 call g2_sbytesc(cpack,gwidth,iofst,nbitsgwidth,0,ngroups)
397 itemp=nbitsgwidth*ngroups
400 if (mod(itemp,8).ne.0)
then
414 ilmax=maxval(glen(1:ngroups-1))
415 nglenref=minval(glen(1:ngroups-1))
417 nglenlast=glen(ngroups)
421 if (ilmax.ne.nglenref)
then
422 temp=
i1log2(ilmax-nglenref)
423 nbitsglen=ceiling(temp)
425 glen(i)=glen(i)-nglenref
427 call g2_sbytesc(cpack,glen,iofst,nbitsglen,0,ngroups)
428 itemp=nbitsglen*ngroups
431 if (mod(itemp,8).ne.0)
then
446 glength=glen(ng)+nglenref
447 if (ng.eq.ngroups ) glength=nglenlast
448 grpwidth=gwidth(ng)+ngwidthref
450 if ( grpwidth.ne.0 )
then
451 call g2_sbytesc(cpack,ifld(n),iofst,grpwidth,0,glength)
452 iofst=iofst+(grpwidth*glength)
461 if (mod(iofst,8).ne.0)
then
468 if (
allocated(ifld) )
deallocate(ifld)
469 if (
allocated(jfld) )
deallocate(jfld)
470 if (
allocated(ifldmiss) )
deallocate(ifldmiss)
471 if (
allocated(gref) )
deallocate(gref)
472 if (
allocated(gwidth) )
deallocate(gwidth)
473 if (
allocated(glen) )
deallocate(glen)
482 rmin4 = real(rmin, 4)
485 iref=transfer(ref,iref)
487 idrstmpl(4)=nbitsgref
491 idrstmpl(11)=ngwidthref
492 idrstmpl(12)=nbitsgwidth
493 idrstmpl(13)=nglenref
495 idrstmpl(15)=nglenlast
496 idrstmpl(16)=nbitsglen
497 if (idrsnum.eq.3)
then
498 idrstmpl(18)=nbitsd/8
subroutine g2_sbytec(out, in, iskip, nbits)
Put arbitrary size values into a packed bit string, taking the low order bits from each value in the ...
subroutine g2_sbytesc(out, in, iskip, nbits, nskip, n)
Put arbitrary size values into a packed bit string, taking the low order bits from each value in the ...
subroutine misspack(fld, ndpts, idrsnum, idrstmpl, cpack, lcpack)
Pack up a data field using a GRIB2 algorithm with missing value management.
subroutine mkieee(a, rieee, num)
Copy an array of real to an array of 32-bit IEEE floating points.
Define math functions used by compack(), simpack(), and misspack().
subroutine pack_gp(KFILDO, IC, NXY, IS523, MINPK, INC, MISSP, MISSS, JMIN, JMAX, LBIT, NOV, NDG, LX, IBIT, JBIT, KBIT, NOVREF, LBITREF, IER)
This subroutine determines groups of variable size, but at least of size minpk, the associated max(JM...
subroutine rdieee(rieee, a, num)
Copy array of 32-bit IEEE floating point values to local floating point representation.