NCEPLIBS-g2  3.4.7
comunpack.f
Go to the documentation of this file.
1 
5 
31  subroutine comunpack(cpack,len,lensec,idrsnum,idrstmpl,ndpts,
32  & fld,ier)
33 
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)
38 
39  integer,allocatable :: ifld(:),ifldmiss(:)
40  integer(4) :: ieee
41  integer,allocatable :: gref(:),gwidth(:),glen(:)
42  real :: ref,bscale,dscale,rmiss1,rmiss2
43 ! real :: fldo(6045)
44  integer :: totBit, totLen
45 
46  ier=0
47  !print *,'IDRSTMPL: ',(idrstmpl(j),j=1,16)
48  ieee = idrstmpl(1)
49  call rdieee(ieee,ref,1)
50  bscale = 2.0**real(idrstmpl(2))
51  dscale = 10.0**real(-idrstmpl(3))
52  nbitsgref = idrstmpl(4)
53  itype = idrstmpl(5)
54  ngroups = idrstmpl(10)
55  nbitsgwidth = idrstmpl(12)
56  nbitsglen = idrstmpl(16)
57  if (idrsnum.eq.3) then
58  nbitsd=idrstmpl(18)*8
59  endif
60 
61  ! Constant field
62 
63  if (ngroups.eq.0) then
64  do j=1,ndpts
65  fld(j)=ref
66  enddo
67  return
68  endif
69 
70  iofst=0
71  allocate(ifld(ndpts),stat=is)
72  !print *,'ALLOC ifld: ',is,ndpts
73  allocate(gref(ngroups),stat=is)
74  !print *,'ALLOC gref: ',is
75  allocate(gwidth(ngroups),stat=is)
76  !print *,'ALLOC gwidth: ',is
77 !
78 ! Get missing values, if supplied
79 !
80  if ( idrstmpl(7).eq.1 ) then
81  if (itype.eq.0) then
82  call rdieee(idrstmpl(8),rmiss1,1)
83  else
84  rmiss1=real(idrstmpl(8))
85  endif
86  elseif ( idrstmpl(7).eq.2 ) then
87  if (itype.eq.0) then
88  call rdieee(idrstmpl(8),rmiss1,1)
89  call rdieee(idrstmpl(9),rmiss2,1)
90  else
91  rmiss1=real(idrstmpl(8))
92  rmiss2=real(idrstmpl(9))
93  endif
94  endif
95  !print *,'RMISSs: ',rmiss1,rmiss2,ref
96 !
97 ! Extract Spatial differencing values, if using DRS Template 5.3
98 !
99  if (idrsnum.eq.3) then
100  if (nbitsd.ne.0) then
101  call g2_gbytec(cpack,ival1,iofst,nbitsd)
102  iofst=iofst+nbitsd
103  if (idrstmpl(17).eq.2) then
104  call g2_gbytec(cpack,ival2,iofst,nbitsd)
105  iofst=iofst+nbitsd
106  endif
107  call g2_gbytec(cpack,isign,iofst,1)
108  iofst=iofst+1
109  call g2_gbytec(cpack,minsd,iofst,nbitsd-1)
110  iofst=iofst+nbitsd-1
111  if (isign.eq.1) minsd=-minsd
112  else
113  ival1=0
114  ival2=0
115  minsd=0
116  endif
117  !print *,'SDu ',ival1,ival2,minsd,nbitsd
118  endif
119 !
120 ! Extract Each Group's reference value
121 !
122  !print *,'SAG1: ',nbitsgref,ngroups,iofst
123  if (nbitsgref.ne.0) then
124  call g2_gbytesc(cpack,gref,iofst,nbitsgref,0,ngroups)
125  itemp=nbitsgref*ngroups
126  iofst=iofst+(itemp)
127  if (mod(itemp,8).ne.0) iofst=iofst+(8-mod(itemp,8))
128  else
129  gref(1:ngroups)=0
130  endif
131  !write(78,*)'GREFs: ',(gref(j),j=1,ngroups)
132 !
133 ! Extract Each Group's bit width
134 !
135  !print *,'SAG2: ',nbitsgwidth,ngroups,iofst,idrstmpl(11)
136  if (nbitsgwidth.ne.0) then
137  call g2_gbytesc(cpack,gwidth,iofst,nbitsgwidth,0,ngroups)
138  itemp=nbitsgwidth*ngroups
139  iofst=iofst+(itemp)
140  if (mod(itemp,8).ne.0) iofst=iofst+(8-mod(itemp,8))
141  else
142  gwidth(1:ngroups)=0
143  endif
144  do j=1,ngroups
145  gwidth(j)=gwidth(j)+idrstmpl(11)
146  enddo
147  !write(78,*)'GWIDTHs: ',(gwidth(j),j=1,ngroups)
148 !
149 ! Extract Each Group's length (number of values in each group)
150 !
151  allocate(glen(ngroups),stat=is)
152  !print *,'ALLOC glen: ',is
153  !print *,'SAG3: ',nbitsglen,ngroups,iofst,idrstmpl(14),idrstmpl(13)
154  if (nbitsglen.ne.0) then
155  call g2_gbytesc(cpack,glen,iofst,nbitsglen,0,ngroups)
156  itemp=nbitsglen*ngroups
157  iofst=iofst+(itemp)
158  if (mod(itemp,8).ne.0) iofst=iofst+(8-mod(itemp,8))
159  else
160  glen(1:ngroups)=0
161  endif
162  do j=1,ngroups
163  glen(j)=(glen(j)*idrstmpl(14))+idrstmpl(13)
164  enddo
165  glen(ngroups)=idrstmpl(15)
166  !write(78,*)'GLENs: ',(glen(j),j=1,ngroups)
167  !print *,'GLENsum: ',sum(glen)
168 !
169 ! Test to see if the group widths and lengths are consistent with number of
170 ! values, and length of section 7.
171 !
172  totbit = 0
173  totlen = 0
174  do j=1,ngroups
175  totbit = totbit + (gwidth(j)*glen(j));
176  totlen = totlen + glen(j);
177  enddo
178  if (totlen .NE. ndpts) then
179  ier=1
180  return
181  endif
182  if ( (totbit/8) .GT. lensec) then
183  ier=1
184  return
185  endif
186 !
187 ! For each group, unpack data values
188 !
189  if ( idrstmpl(7).eq.0 ) then ! no missing values
190  n=1
191  do j=1,ngroups
192  !write(78,*)'NGP ',j,gwidth(j),glen(j),gref(j)
193  if (gwidth(j).ne.0) then
194  call g2_gbytesc(cpack,ifld(n),iofst,gwidth(j),0,glen(j))
195  do k=1,glen(j)
196  ifld(n)=ifld(n)+gref(j)
197  n=n+1
198  enddo
199  else
200  ifld(n:n+glen(j)-1)=gref(j)
201  n=n+glen(j)
202  endif
203  iofst=iofst+(gwidth(j)*glen(j))
204  enddo
205  elseif ( idrstmpl(7).eq.1.OR.idrstmpl(7).eq.2 ) then
206  ! missing values included
207  allocate(ifldmiss(ndpts))
208  !ifldmiss=0
209  n=1
210  non=1
211  do j=1,ngroups
212  !print *,'SAGNGP ',j,gwidth(j),glen(j),gref(j)
213  if (gwidth(j).ne.0) then
214  msng1=(2**gwidth(j))-1
215  msng2=msng1-1
216  call g2_gbytesc(cpack,ifld(n),iofst,gwidth(j),0,glen(j))
217  iofst=iofst+(gwidth(j)*glen(j))
218  do k=1,glen(j)
219  if (ifld(n).eq.msng1) then
220  ifldmiss(n)=1
221  elseif (idrstmpl(7).eq.2.AND.ifld(n).eq.msng2) then
222  ifldmiss(n)=2
223  else
224  ifldmiss(n)=0
225  ifld(non)=ifld(n)+gref(j)
226  non=non+1
227  endif
228  n=n+1
229  enddo
230  else
231  msng1=(2**nbitsgref)-1
232  msng2=msng1-1
233  if (gref(j).eq.msng1) then
234  ifldmiss(n:n+glen(j)-1)=1
235  !ifld(n:n+glen(j)-1)=0
236  elseif (idrstmpl(7).eq.2.AND.gref(j).eq.msng2) then
237  ifldmiss(n:n+glen(j)-1)=2
238  !ifld(n:n+glen(j)-1)=0
239  else
240  ifldmiss(n:n+glen(j)-1)=0
241  ifld(non:non+glen(j)-1)=gref(j)
242  non=non+glen(j)
243  endif
244  n=n+glen(j)
245  endif
246  enddo
247  endif
248  !write(78,*)'IFLDs: ',(ifld(j),j=1,ndpts)
249 
250  if ( allocated(gref) ) deallocate(gref)
251  if ( allocated(gwidth) ) deallocate(gwidth)
252  if ( allocated(glen) ) deallocate(glen)
253 !
254 ! If using spatial differences, add overall min value, and
255 ! sum up recursively
256 !
257  if (idrsnum.eq.3) then ! spatial differencing
258  if (idrstmpl(17).eq.1) then ! first order
259  ifld(1)=ival1
260  if ( idrstmpl(7).eq.0 ) then ! no missing values
261  itemp=ndpts
262  else
263  itemp=non-1
264  endif
265  do n=2,itemp
266  ifld(n)=ifld(n)+minsd
267  ifld(n)=ifld(n)+ifld(n-1)
268  enddo
269  elseif (idrstmpl(17).eq.2) then ! second order
270  ifld(1)=ival1
271  ifld(2)=ival2
272  if ( idrstmpl(7).eq.0 ) then ! no missing values
273  itemp=ndpts
274  else
275  itemp=non-1
276  endif
277  do n=3,itemp
278  ifld(n)=ifld(n)+minsd
279  ifld(n)=ifld(n)+(2*ifld(n-1))-ifld(n-2)
280  enddo
281  endif
282  !write(78,*)'IFLDs: ',(ifld(j),j=1,ndpts)
283  endif
284 !
285 ! Scale data back to original form
286 !
287  !print *,'SAGT: ',ref,bscale,dscale
288  if ( idrstmpl(7).eq.0 ) then ! no missing values
289  do n=1,ndpts
290  fld(n)=((real(ifld(n))*bscale)+ref)*dscale
291  !write(78,*)'SAG ',n,fld(n),ifld(n),bscale,ref,1./dscale
292  enddo
293  elseif ( idrstmpl(7).eq.1.OR.idrstmpl(7).eq.2 ) then
294  ! missing values included
295  non=1
296  do n=1,ndpts
297  if ( ifldmiss(n).eq.0 ) then
298  fld(n)=((real(ifld(non))*bscale)+ref)*dscale
299  !print *,'SAG ',n,fld(n),ifld(non),bscale,ref,dscale
300  non=non+1
301  elseif ( ifldmiss(n).eq.1 ) then
302  fld(n)=rmiss1
303  elseif ( ifldmiss(n).eq.2 ) then
304  fld(n)=rmiss2
305  endif
306  enddo
307  if ( allocated(ifldmiss) ) deallocate(ifldmiss)
308  endif
309 
310  if ( allocated(ifld) ) deallocate(ifld)
311 
312  !open(10,form='unformatted',recl=24180,access='direct')
313  !read(10,rec=1) (fldo(k),k=1,6045)
314  !do i =1,6045
315  ! print *,i,fldo(i),fld(i),fldo(i)-fld(i)
316  !enddo
317 
318  return
319  end
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...
Definition: comunpack.f:33
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...
Definition: g2_gbytesc.F90:63
subroutine g2_gbytec(in, iout, iskip, nbits)
Extract arbitrary size values from a packed bit string, right justifying each value in the unpacked a...
Definition: g2_gbytesc.F90:20
subroutine rdieee(rieee, a, num)
Copy array of 32-bit IEEE floating point values to local floating point representation.
Definition: rdieee.F90:16