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