31 subroutine comunpack(cpack,len,lensec,idrsnum,idrstmpl,ndpts,
34 character(len=1),
intent(in) :: cpack(len)
35 integer,
intent(in) :: ndpts,len
36 integer,
intent(in) :: idrstmpl(*)
37 real,
intent(out) :: fld(ndpts)
39 integer,
allocatable :: ifld(:),ifldmiss(:)
41 integer,
allocatable :: gref(:),gwidth(:),glen(:)
42 real :: ref,bscale,dscale,rmiss1,rmiss2
44 integer :: totBit, totLen
50 bscale = 2.0**real(idrstmpl(2))
51 dscale = 10.0**real(-idrstmpl(3))
52 nbitsgref = idrstmpl(4)
54 ngroups = idrstmpl(10)
55 nbitsgwidth = idrstmpl(12)
56 nbitsglen = idrstmpl(16)
57 if (idrsnum.eq.3)
then
63 if (ngroups.eq.0)
then
71 allocate(ifld(ndpts),stat=is)
73 allocate(gref(ngroups),stat=is)
75 allocate(gwidth(ngroups),stat=is)
80 if ( idrstmpl(7).eq.1 )
then
82 call rdieee(idrstmpl(8),rmiss1,1)
84 rmiss1=real(idrstmpl(8))
86 elseif ( idrstmpl(7).eq.2 )
then
88 call rdieee(idrstmpl(8),rmiss1,1)
89 call rdieee(idrstmpl(9),rmiss2,1)
91 rmiss1=real(idrstmpl(8))
92 rmiss2=real(idrstmpl(9))
99 if (idrsnum.eq.3)
then
100 if (nbitsd.ne.0)
then
103 if (idrstmpl(17).eq.2)
then
109 call g2_gbytec(cpack,minsd,iofst,nbitsd-1)
111 if (isign.eq.1) minsd=-minsd
123 if (nbitsgref.ne.0)
then
124 call g2_gbytesc(cpack,gref,iofst,nbitsgref,0,ngroups)
125 itemp=nbitsgref*ngroups
127 if (mod(itemp,8).ne.0) iofst=iofst+(8-mod(itemp,8))
136 if (nbitsgwidth.ne.0)
then
137 call g2_gbytesc(cpack,gwidth,iofst,nbitsgwidth,0,ngroups)
138 itemp=nbitsgwidth*ngroups
140 if (mod(itemp,8).ne.0) iofst=iofst+(8-mod(itemp,8))
145 gwidth(j)=gwidth(j)+idrstmpl(11)
151 allocate(glen(ngroups),stat=is)
154 if (nbitsglen.ne.0)
then
155 call g2_gbytesc(cpack,glen,iofst,nbitsglen,0,ngroups)
156 itemp=nbitsglen*ngroups
158 if (mod(itemp,8).ne.0) iofst=iofst+(8-mod(itemp,8))
163 glen(j)=(glen(j)*idrstmpl(14))+idrstmpl(13)
165 glen(ngroups)=idrstmpl(15)
175 totbit = totbit + (gwidth(j)*glen(j));
176 totlen = totlen + glen(j);
178 if (totlen .NE. ndpts)
then
182 if ( (totbit/8) .GT. lensec)
then
189 if ( idrstmpl(7).eq.0 )
then
193 if (gwidth(j).ne.0)
then
194 call g2_gbytesc(cpack,ifld(n),iofst,gwidth(j),0,glen(j))
196 ifld(n)=ifld(n)+gref(j)
200 ifld(n:n+glen(j)-1)=gref(j)
203 iofst=iofst+(gwidth(j)*glen(j))
205 elseif ( idrstmpl(7).eq.1.OR.idrstmpl(7).eq.2 )
then
207 allocate(ifldmiss(ndpts))
213 if (gwidth(j).ne.0)
then
214 msng1=(2**gwidth(j))-1
216 call g2_gbytesc(cpack,ifld(n),iofst,gwidth(j),0,glen(j))
217 iofst=iofst+(gwidth(j)*glen(j))
219 if (ifld(n).eq.msng1)
then
221 elseif (idrstmpl(7).eq.2.AND.ifld(n).eq.msng2)
then
225 ifld(non)=ifld(n)+gref(j)
231 msng1=(2**nbitsgref)-1
233 if (gref(j).eq.msng1)
then
234 ifldmiss(n:n+glen(j)-1)=1
236 elseif (idrstmpl(7).eq.2.AND.gref(j).eq.msng2)
then
237 ifldmiss(n:n+glen(j)-1)=2
240 ifldmiss(n:n+glen(j)-1)=0
241 ifld(non:non+glen(j)-1)=gref(j)
250 if (
allocated(gref) )
deallocate(gref)
251 if (
allocated(gwidth) )
deallocate(gwidth)
252 if (
allocated(glen) )
deallocate(glen)
257 if (idrsnum.eq.3)
then
258 if (idrstmpl(17).eq.1)
then
260 if ( idrstmpl(7).eq.0 )
then
266 ifld(n)=ifld(n)+minsd
267 ifld(n)=ifld(n)+ifld(n-1)
269 elseif (idrstmpl(17).eq.2)
then
272 if ( idrstmpl(7).eq.0 )
then
278 ifld(n)=ifld(n)+minsd
279 ifld(n)=ifld(n)+(2*ifld(n-1))-ifld(n-2)
288 if ( idrstmpl(7).eq.0 )
then
290 fld(n)=((real(ifld(n))*bscale)+ref)*dscale
293 elseif ( idrstmpl(7).eq.1.OR.idrstmpl(7).eq.2 )
then
297 if ( ifldmiss(n).eq.0 )
then
298 fld(n)=((real(ifld(non))*bscale)+ref)*dscale
301 elseif ( ifldmiss(n).eq.1 )
then
303 elseif ( ifldmiss(n).eq.2 )
then
307 if (
allocated(ifldmiss) )
deallocate(ifldmiss)
310 if (
allocated(ifld) )
deallocate(ifld)
subroutine comunpack(cpack, len, lensec, idrsnum, idrstmpl, ndpts, fld, ier)
Unpack a data field that was packed using a complex packing algorithm as defined in the GRIB2 documen...
subroutine g2_gbytesc(in, iout, iskip, nbits, nskip, n)
Extract arbitrary size values from a packed bit string, right justifying each value in the unpacked a...
subroutine g2_gbytec(in, iout, iskip, nbits)
Extract arbitrary size values from a packed bit string, right justifying each value in the unpacked a...
subroutine rdieee(rieee, a, num)
Copy array of 32-bit IEEE floating point values to local floating point representation.