34 subroutine compack(fld,ndpts,idrsnum,idrstmpl,cpack,lcpack)
38 integer,
intent(in) :: ndpts,idrsnum
39 real,
intent(in) :: fld(ndpts)
40 character(len=1),
intent(out) :: cpack(*)
41 integer,
intent(inout) :: idrstmpl(*)
42 integer,
intent(out) :: lcpack
45 integer :: j,iofst,imin,ival1,ival2,minsd,nbitsd,n
46 integer :: igmax,nbitsgref,left,iwmax,i,ilmax,kk,ij
47 integer :: ngwidthref,nbitsgwidth,nglenref,nglenlast
48 integer :: maxorig,nbitorig,isd,ngroups,itemp,minpk
49 integer :: kfildo,inc,maxgrps,missopt,miss1,miss2,lg
50 integer :: ibit,jbit,kbit,novref,lbitref,ier,ng,imax
56 integer,
allocatable :: ifld(:)
57 integer,
allocatable :: jmin(:),jmax(:),lbit(:)
58 integer,
parameter :: zero=0
59 integer,
allocatable :: gref(:),gwidth(:),glen(:)
60 integer :: glength,grpwidth
65 bscale=2.0**real(-idrstmpl(2))
66 dscale=10.0**real(idrstmpl(3))
78 if (fld(j).gt.rmax) rmax=fld(j)
79 if (fld(j).lt.rmin) rmin=fld(j)
87 multival:
if (rmin.ne.rmax)
then
91 allocate(gwidth(ndpts))
96 if (idrstmpl(2).eq.0)
then
97 imin=nint(rmin*dscale)
101 ifld(j)=max(0,nint(fld(j)*dscale)-imin)
107 ifld(j)=max(0,nint(((fld(j)*dscale)-rmin)*bscale))
113 alg3:
if (idrsnum.eq.3)
then
114 if (idrstmpl(17).ne.1.and.idrstmpl(17).ne.2) idrstmpl(17)=2
115 if (idrstmpl(17).eq.1)
then
118 print *,
'G2: negative ival1',ival1
122 ifld(j)=ifld(j)-ifld(j-1)
125 elseif (idrstmpl(17).eq.2)
then
129 print *,
'G2: negative ival1',ival1
133 print *,
'G2: negative ival2',ival2
137 ifld(j)=ifld(j)-(2*ifld(j-1))+ifld(j-2)
146 minsd=minval(ifld(isd:ndpts))
148 ifld(j)=ifld(j)-minsd
154 nbitsd=
i1log2(abs(minsd))+1
160 if (idrstmpl(17).eq.2.and.ival2.gt.ival1) maxorig=ival2
161 nbitorig=
i1log2(maxorig)+1
162 if (nbitorig.gt.nbitsd) nbitsd=nbitorig
164 if (mod(nbitsd,8).ne.0) nbitsd=nbitsd+(8-mod(nbitsd,8))
169 if (nbitsd.ne.0)
then
177 call g2_sbytec(cpack,iabs(ival1),iofst,nbitsd-1)
180 if (idrstmpl(17).eq.2)
then
188 call g2_sbytec(cpack,iabs(ival2),iofst,nbitsd-1)
199 call g2_sbytec(cpack,iabs(minsd),iofst,nbitsd-1)
208 simplealg:
if ( simple_alg )
then
211 print *,
'G2: use simple algorithm'
225 maxgrps=((ndpts+minpk-1)/minpk)
226 allocate(jmin(maxgrps))
227 allocate(jmax(maxgrps))
228 allocate(lbit(maxgrps))
230 call pack_gp(kfildo,ifld,ndpts,missopt,minpk,inc,miss1,miss2,
231 & jmin,jmax,lbit,glen,maxgrps,ngroups,ibit,jbit,
232 & kbit,novref,lbitref,ier)
235 1099
format(
'G2: fall back to simple algorithm (glahn ier=',i0,
245 elseif(ngroups<1)
then
247 print *,
'Glahn algorithm failed; use simple packing'
258 glen(ng)=glen(ng)+novref
276 if (ifld(j).lt.gref(ng)) gref(ng)=ifld(j)
277 if (ifld(j).gt.imax) imax=ifld(j)
281 if ( gref(ng).ne.imax )
then
282 gwidth(ng)=
i1log2(imax-gref(ng))
289 ifld(j)=ifld(j)-gref(ng)
301 igmax=maxval(gref(1:ngroups))
304 call g2_sbytesc(cpack,gref,iofst,nbitsgref,0,ngroups)
305 itemp=nbitsgref*ngroups
307 if (mod(itemp,8).ne.0)
then
321 iwmax=maxval(gwidth(1:ngroups))
322 ngwidthref=minval(gwidth(1:ngroups))
323 if (iwmax.ne.ngwidthref)
then
324 nbitsgwidth=
i1log2(iwmax-ngwidthref)
326 gwidth(i)=gwidth(i)-ngwidthref
328 write(0,*)
'i,gw,ngw=',i,gwidth(i),ngwidthref
332 call g2_sbytesc(cpack,gwidth,iofst,nbitsgwidth,0,ngroups)
333 itemp=nbitsgwidth*ngroups
336 if (mod(itemp,8).ne.0)
then
351 ilmax=maxval(glen(1:ngroups-1))
352 nglenref=minval(glen(1:ngroups-1))
353 nglenlast=glen(ngroups)
354 if (ilmax.ne.nglenref)
then
355 nbitsglen=
i1log2(ilmax-nglenref)
357 glen(i)=glen(i)-nglenref
359 write(0,*)
'i,glen(i) = ',i,glen(i)
363 call g2_sbytesc(cpack,glen,iofst,nbitsglen,0,ngroups)
364 itemp=nbitsglen*ngroups
367 if (mod(itemp,8).ne.0)
then
383 glength=glen(ng)+nglenref
384 if (ng.eq.ngroups ) glength=nglenlast
385 grpwidth=gwidth(ng)+ngwidthref
387 if ( grpwidth.ne.0 )
then
388 call g2_sbytesc(cpack,ifld(n),iofst,grpwidth,0,glength)
389 iofst=iofst+(grpwidth*glength)
398 if (mod(iofst,8).ne.0)
then
405 if (
allocated(ifld) )
deallocate(ifld)
406 if (
allocated(gref) )
deallocate(gref)
407 if (
allocated(gwidth) )
deallocate(gwidth)
408 if (
allocated(glen) )
deallocate(glen)
424 rmin4 = real(rmin, 4)
427 iref=transfer(ref,iref)
429 idrstmpl(4)=nbitsgref
436 idrstmpl(11)=ngwidthref
437 idrstmpl(12)=nbitsgwidth
438 idrstmpl(13)=nglenref
440 idrstmpl(15)=nglenlast
441 idrstmpl(16)=nbitsglen
442 if (idrsnum.eq.3)
then
443 idrstmpl(18)=nbitsd/8
subroutine compack(fld, ndpts, idrsnum, idrstmpl, cpack, lcpack)
This subroutine supports GRIB2 complex packing templates with or without spatial differences,...
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 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...