43 subroutine misspack(fld,ndpts,idrsnum,idrstmpl,cpack,lcpack)
46 integer,
intent(in) :: ndpts,idrsnum
47 real,
intent(in) :: fld(ndpts)
48 character(len=1),
intent(out) :: cpack(*)
49 integer,
intent(inout) :: idrstmpl(*)
50 integer,
intent(out) :: lcpack
54 integer,
allocatable :: ifld(:),ifldmiss(:),jfld(:)
55 integer,
allocatable :: jmin(:),jmax(:),lbit(:)
56 integer,
parameter :: zero=0
57 integer,
allocatable :: gref(:),gwidth(:),glen(:)
58 integer :: glength,grpwidth
64 bscale=2.0**real(-idrstmpl(2))
65 dscale=10.0**real(idrstmpl(3))
67 if ( missopt.ne.1 .AND. missopt.ne.2 )
then
68 print *,
'misspack: Unrecognized option.'
72 call rdieee(idrstmpl(8),rmissp,1)
73 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
126 allocate(ifld(ndpts))
127 allocate(jfld(ndpts))
128 allocate(gref(ndpts))
129 allocate(gwidth(ndpts))
130 allocate(glen(ndpts))
135 if (idrstmpl(2).eq.0)
then
136 imin=nint(rmin*dscale)
140 if (ifldmiss(j).eq.0)
then
142 jfld(nonmiss)=max(0,nint(fld(j)*dscale)-imin)
149 if (ifldmiss(j).eq.0)
then
151 jfld(nonmiss)=max(0,nint(((fld(j)*dscale)-rmin)*bscale))
158 if (idrsnum.eq.3)
then
159 if (idrstmpl(17).ne.1.and.idrstmpl(17).ne.2) idrstmpl(17)=2
160 if (idrstmpl(17).eq.1)
then
167 jfld(j)=jfld(j)-jfld(j-1)
169 if(nonmiss>0) jfld(1)=0
170 elseif (idrstmpl(17).eq.2)
then
174 elseif(nonmiss<1)
then
182 jfld(j)=jfld(j)-(2*jfld(j-1))+jfld(j-2)
184 if(nonmiss>=1) jfld(1)=0
185 if(nonmiss>=2) jfld(2)=0
191 minsd=minval(jfld(isd:nonmiss))
193 jfld(j)=jfld(j)-minsd
200 nbitsd=ceiling(temp)+1
206 if (idrstmpl(17).eq.2.and.ival2.gt.ival1) maxorig=ival2
208 nbitorig=ceiling(temp)+1
209 if (nbitorig.gt.nbitsd) nbitsd=nbitorig
211 if (mod(nbitsd,8).ne.0) nbitsd=nbitsd+(8-mod(nbitsd,8))
216 if (nbitsd.ne.0)
then
224 call g2_sbytec(cpack,iabs(ival1),iofst,nbitsd-1)
227 if (idrstmpl(17).eq.2)
then
235 call g2_sbytec(cpack,iabs(ival2),iofst,nbitsd-1)
246 call g2_sbytec(cpack,iabs(minsd),iofst,nbitsd-1)
255 miss1=minval(jfld(1:nonmiss))-1
259 if ( ifldmiss(j).eq.0 )
then
262 elseif ( ifldmiss(j).eq.1 )
then
264 elseif ( ifldmiss(j).eq.2 )
then
268 if(ndpts<2) simple_alg=.true.
272 if ( simple_alg )
then
288 maxgrps=(ndpts/minpk)+1
289 allocate(jmin(maxgrps))
290 allocate(jmax(maxgrps))
291 allocate(lbit(maxgrps))
292 call pack_gp(kfildo,ifld,ndpts,missopt,minpk,inc,miss1,miss2,
293 & jmin,jmax,lbit,glen,maxgrps,ngroups,ibit,jbit,
294 & kbit,novref,lbitref,ier)
297 glen(ng)=glen(ng)+novref
310 num0=count(ifldmiss(n:n+glen(ng)-1) .EQ. 0)
311 num1=count(ifldmiss(n:n+glen(ng)-1) .EQ. 1)
312 num2=count(ifldmiss(n:n+glen(ng)-1) .EQ. 2)
313 if ( num0.eq.0 )
then
314 if ( num1.eq.0 )
then
317 elseif ( num2.eq.0 )
then
330 if ( ifldmiss(j).eq.0 )
then
331 if (ifld(j).lt.gref(ng)) gref(ng)=ifld(j)
332 if (ifld(j).gt.imax) imax=ifld(j)
336 if (missopt.eq.1) imax=imax+1
337 if (missopt.eq.2) imax=imax+2
339 if ( gref(ng).ne.imax )
then
340 temp=
i1log2(imax-gref(ng))
341 gwidth(ng)=ceiling(temp)
350 if (ifldmiss(j).eq.0)
then
351 ifld(j)=ifld(j)-gref(ng)
352 elseif (ifldmiss(j).eq.1)
then
354 elseif (ifldmiss(j).eq.2)
then
368 igmax=maxval(gref(1:ngroups))
369 if (missopt.eq.1) igmax=igmax+1
370 if (missopt.eq.2) igmax=igmax+2
373 nbitsgref=ceiling(temp)
377 if (gref(j).eq.-1) gref(j)=mtemp-1
378 if (gref(j).eq.-2) gref(j)=mtemp-2
380 call g2_sbytesc(cpack,gref,iofst,nbitsgref,0,ngroups)
381 itemp=nbitsgref*ngroups
384 if (mod(itemp,8).ne.0)
then
398 iwmax=maxval(gwidth(1:ngroups))
399 ngwidthref=minval(gwidth(1:ngroups))
400 if (iwmax.ne.ngwidthref)
then
401 temp=
i1log2(iwmax-ngwidthref)
402 nbitsgwidth=ceiling(temp)
404 gwidth(i)=gwidth(i)-ngwidthref
406 call g2_sbytesc(cpack,gwidth,iofst,nbitsgwidth,0,ngroups)
407 itemp=nbitsgwidth*ngroups
410 if (mod(itemp,8).ne.0)
then
425 ilmax=maxval(glen(1:ngroups-1))
426 nglenref=minval(glen(1:ngroups-1))
428 nglenlast=glen(ngroups)
432 if (ilmax.ne.nglenref)
then
433 temp=
i1log2(ilmax-nglenref)
434 nbitsglen=ceiling(temp)
436 glen(i)=glen(i)-nglenref
438 call g2_sbytesc(cpack,glen,iofst,nbitsglen,0,ngroups)
439 itemp=nbitsglen*ngroups
442 if (mod(itemp,8).ne.0)
then
458 glength=glen(ng)+nglenref
459 if (ng.eq.ngroups ) glength=nglenlast
460 grpwidth=gwidth(ng)+ngwidthref
462 if ( grpwidth.ne.0 )
then
463 call g2_sbytesc(cpack,ifld(n),iofst,grpwidth,0,glength)
464 iofst=iofst+(grpwidth*glength)
473 if (mod(iofst,8).ne.0)
then
480 if (
allocated(ifld) )
deallocate(ifld)
481 if (
allocated(jfld) )
deallocate(jfld)
482 if (
allocated(ifldmiss) )
deallocate(ifldmiss)
483 if (
allocated(gref) )
deallocate(gref)
484 if (
allocated(gwidth) )
deallocate(gwidth)
485 if (
allocated(glen) )
deallocate(glen)
499 iref=transfer(ref,iref)
501 idrstmpl(4)=nbitsgref
505 idrstmpl(11)=ngwidthref
506 idrstmpl(12)=nbitsgwidth
507 idrstmpl(13)=nglenref
509 idrstmpl(15)=nglenlast
510 idrstmpl(16)=nbitsglen
511 if (idrsnum.eq.3)
then
512 idrstmpl(18)=nbitsd/8