NCEPLIBS-g2  3.4.8
gf_getfld.F90
Go to the documentation of this file.
1 
5 
67 subroutine gf_getfld(cgrib, lcgrib, ifldnum, unpack, expand, gfld, ierr)
68 
69  use grib_mod
70  implicit none
71 
72  character(len = 1), intent(in) :: cgrib(lcgrib)
73  integer, intent(in) :: lcgrib, ifldnum
74  logical, intent(in) :: unpack, expand
75  type(gribfield), intent(out) :: gfld
76  integer, intent(out) :: ierr
77 
78  character(len = 4), parameter :: grib = 'GRIB', c7777 = '7777'
79  character(len = 4) :: ctemp
80  real, pointer, dimension(:) :: newfld
81  integer:: listsec0(2), igds(5)
82  integer iofst, istart
83  logical*1, pointer, dimension(:) :: bmpsave
84  logical have3, have4, have5, have6, have7
85 
86  !implicit none additions
87  integer :: numfld, j, lengrib, ipos, lensec0, lensec
88  integer :: isecnum, jerr, n, numlocal
89 
90  interface
91  subroutine gf_unpack1(cgrib, lcgrib, iofst, ids, idslen, ierr)
92  character(len = 1), intent(in) :: cgrib(lcgrib)
93  integer, intent(in) :: lcgrib
94  integer, intent(inout) :: iofst
95  integer, pointer, dimension(:) :: ids
96  integer, intent(out) :: ierr, idslen
97  end subroutine gf_unpack1
98  subroutine gf_unpack2(cgrib, lcgrib, iofst, lencsec2, csec2, ierr)
99  character(len = 1), intent(in) :: cgrib(lcgrib)
100  integer, intent(in) :: lcgrib
101  integer, intent(inout) :: iofst
102  integer, intent(out) :: lencsec2
103  integer, intent(out) :: ierr
104  character(len = 1), pointer, dimension(:) :: csec2
105  end subroutine gf_unpack2
106  subroutine gf_unpack3(cgrib, lcgrib, iofst, igds, igdstmpl, &
107  mapgridlen, ideflist, idefnum, ierr)
108  character(len = 1), intent(in) :: cgrib(lcgrib)
109  integer, intent(in) :: lcgrib
110  integer, intent(inout) :: iofst
111  integer, pointer, dimension(:) :: igdstmpl, ideflist
112  integer, intent(out) :: igds(5)
113  integer, intent(out) :: mapgridlen
114  integer, intent(out) :: ierr, idefnum
115  end subroutine gf_unpack3
116  subroutine gf_unpack4(cgrib, lcgrib, iofst, ipdsnum, ipdstmpl, &
117  mappdslen, coordlist, numcoord, ierr)
118  character(len = 1), intent(in) :: cgrib(lcgrib)
119  integer, intent(in) :: lcgrib
120  integer, intent(inout) :: iofst
121  real, pointer, dimension(:) :: coordlist
122  integer, pointer, dimension(:) :: ipdstmpl
123  integer, intent(out) :: ipdsnum
124  integer, intent(out) :: mappdslen
125  integer, intent(out) :: ierr, numcoord
126  end subroutine gf_unpack4
127  subroutine gf_unpack5(cgrib, lcgrib, iofst, ndpts, idrsnum, &
128  idrstmpl, mapdrslen, ierr)
129  character(len = 1), intent(in) :: cgrib(lcgrib)
130  integer, intent(in) :: lcgrib
131  integer, intent(inout) :: iofst
132  integer, intent(out) :: ndpts, idrsnum
133  integer, pointer, dimension(:) :: idrstmpl
134  integer, intent(out) :: mapdrslen
135  integer, intent(out) :: ierr
136  end subroutine gf_unpack5
137  subroutine gf_unpack6(cgrib, lcgrib, iofst, ngpts, ibmap, bmap, &
138  ierr)
139  character(len = 1), intent(in) :: cgrib(lcgrib)
140  integer, intent(in) :: lcgrib, ngpts
141  integer, intent(inout) :: iofst
142  integer, intent(out) :: ibmap
143  integer, intent(out) :: ierr
144  logical*1, pointer, dimension(:) :: bmap
145  end subroutine gf_unpack6
146  subroutine gf_unpack7(cgrib, lcgrib, iofst, igdsnum, igdstmpl, &
147  idrsnum, idrstmpl, ndpts, fld, ierr)
148  character(len = 1), intent(in) :: cgrib(lcgrib)
149  integer, intent(in) :: lcgrib, ndpts, idrsnum, igdsnum
150  integer, intent(inout) :: iofst
151  integer, pointer, dimension(:) :: idrstmpl, igdstmpl
152  integer, intent(out) :: ierr
153  real, pointer, dimension(:) :: fld
154  end subroutine gf_unpack7
155  end interface
156 
157  have3 = .false.
158  have4 = .false.
159  have5 = .false.
160  have6 = .false.
161  have7 = .false.
162  ierr = 0
163  numfld = 0
164  gfld%locallen = 0
165  nullify(gfld%list_opt, gfld%igdtmpl, gfld%ipdtmpl)
166  nullify(gfld%coord_list, gfld%idrtmpl, gfld%bmap, gfld%fld)
167 
168  ! Check for valid request number
169  if (ifldnum .le. 0) then
170  print *, 'gf_getfld: Request for field number ' &
171  ,'must be positive.'
172  ierr = 3
173  return
174  endif
175 
176  ! Check for beginning of GRIB message in the first 100 bytes
177  istart = 0
178  do j = 1, 100
179  ctemp = cgrib(j) // cgrib(j + 1) // cgrib(j + 2) // cgrib(j + 3)
180  if (ctemp .eq. grib) then
181  istart = j
182  exit
183  endif
184  enddo
185  if (istart .eq. 0) then
186  print *, 'gf_getfld: Beginning characters GRIB not found.'
187  ierr = 1
188  return
189  endif
190 
191  ! Unpack Section 0 - Indicator Section
192  iofst = 8 * (istart + 5)
193  call g2_gbytec(cgrib, listsec0(1), iofst, 8) ! Discipline
194  iofst = iofst + 8
195  call g2_gbytec(cgrib, listsec0(2), iofst, 8) ! GRIB edition number
196  iofst = iofst + 8
197  iofst = iofst + 32
198  call g2_gbytec(cgrib, lengrib, iofst, 32) ! Length of GRIB message
199  iofst = iofst + 32
200  lensec0 = 16
201  ipos = istart + lensec0
202 
203  ! Currently handles only GRIB Edition 2.
204  if (listsec0(2) .ne. 2) then
205  print *, 'gf_getfld: can only decode GRIB edition 2.'
206  ierr = 2
207  return
208  endif
209 
210  ! Loop through the remaining sections keeping track of the length of
211  ! each. Also keep the latest Grid Definition Section info. Unpack
212  ! the requested field number.
213  do
214  ! Check to see if we are at end of GRIB message
215  ctemp = cgrib(ipos) // cgrib(ipos + 1) // cgrib(ipos + 2) // &
216  cgrib(ipos + 3)
217  if (ctemp .eq. c7777) then
218  ipos = ipos + 4
219  ! If end of GRIB message not where expected, issue error
220  if (ipos.ne.(istart + lengrib)) then
221  print *, 'gf_getfld: "7777" found, but not ' &
222  ,'where expected.'
223  ierr = 4
224  return
225  endif
226  exit
227  endif
228 
229  ! Get length of Section and Section number
230  iofst = (ipos - 1) * 8
231  call g2_gbytec(cgrib, lensec, iofst, 32) ! Get Length of Section
232  iofst = iofst + 32
233  call g2_gbytec(cgrib, isecnum, iofst, 8) ! Get Section number
234  iofst = iofst + 8
235 
236  ! Check to see if section number is valid
237  if ((isecnum .lt. 1) .or. (isecnum .gt. 7)) then
238  print *, 'gf_getfld: Unrecognized Section Encountered = ', &
239  isecnum
240  ierr = 8
241  return
242  endif
243 
244  ! If found Section 1, decode elements in Identification Section.
245  if (isecnum .eq. 1) then
246  iofst = iofst - 40 ! reset offset to beginning of section
247  call gf_unpack1(cgrib, lcgrib, iofst, gfld%idsect, &
248  gfld%idsectlen, jerr)
249  if (jerr .ne. 0) then
250  ierr = 15
251  return
252  endif
253  endif
254 
255  ! If found Section 2, Grab local section. Save in case this is
256  ! the latest one before the requested field.
257  if (isecnum .eq. 2) then
258  iofst = iofst - 40 ! reset offset to beginning of section
259  if (associated(gfld%local)) deallocate(gfld%local)
260  call gf_unpack2(cgrib, lcgrib, iofst, gfld%locallen, &
261  gfld%local, jerr)
262  if (jerr .ne. 0) then
263  call gf_free(gfld)
264  ierr = 16
265  return
266  endif
267  endif
268 
269  ! If found Section 3, unpack the GDS info using the appropriate
270  ! template. Save in case this is the latest grid before the
271  ! requested field.
272  if (isecnum .eq. 3) then
273  iofst = iofst - 40 ! reset offset to beginning of section
274  if (associated(gfld%igdtmpl)) deallocate(gfld%igdtmpl)
275  if (associated(gfld%list_opt)) deallocate(gfld%list_opt)
276  call gf_unpack3(cgrib, lcgrib, iofst, igds, gfld%igdtmpl, &
277  gfld%igdtlen, gfld%list_opt, gfld%num_opt, jerr)
278  if (jerr .ne. 0) then
279  call gf_free(gfld)
280  ierr = 10
281  return
282  endif
283  have3 = .true.
284  gfld%griddef = igds(1)
285  gfld%ngrdpts = igds(2)
286  gfld%numoct_opt = igds(3)
287  gfld%interp_opt = igds(4)
288  gfld%igdtnum = igds(5)
289  endif
290 
291  ! If found Section 4, check to see if this field is the one
292  ! requested.
293  if (isecnum .eq. 4) then
294  numfld = numfld + 1
295  if (numfld .eq. ifldnum) then
296  gfld%discipline = listsec0(1)
297  gfld%version = listsec0(2)
298  gfld%ifldnum = ifldnum
299  gfld%unpacked = unpack
300  gfld%expanded = .false.
301  iofst = iofst-40 ! reset offset to beginning of section
302  call gf_unpack4(cgrib, lcgrib, iofst, gfld%ipdtnum, &
303  gfld%ipdtmpl, gfld%ipdtlen, gfld%coord_list, &
304  gfld%num_coord, jerr)
305  if (jerr .ne. 0) then
306  call gf_free(gfld)
307  ierr = 11
308  return
309  endif
310  have4 = .true.
311  endif
312  endif
313 
314  ! If found Section 5, check to see if this field is the one
315  ! requested.
316  if ((isecnum .eq. 5).and.(numfld .eq. ifldnum)) then
317  iofst = iofst-40 ! reset offset to beginning of section
318  call gf_unpack5(cgrib, lcgrib, iofst, gfld%ndpts, &
319  gfld%idrtnum, gfld%idrtmpl, gfld%idrtlen, jerr)
320  if (jerr .ne. 0) then
321  call gf_free(gfld)
322  ierr = 12
323  return
324  endif
325  have5 = .true.
326  endif
327 
328  ! If found Section 6, Unpack bitmap. Save in case this is the
329  ! latest bitmap before the requested field.
330  if (isecnum .eq. 6) then
331  if (unpack) then ! unpack bitmap
332  iofst = iofst - 40 ! reset offset to beginning of section
333  bmpsave => gfld%bmap ! save pointer to previous bitmap
334  call gf_unpack6(cgrib, lcgrib, iofst, gfld%ngrdpts, &
335  gfld%ibmap, gfld%bmap, jerr)
336  if (jerr .ne. 0) then
337  call gf_free(gfld)
338  ierr = 13
339  return
340  endif
341  have6 = .true.
342  if (gfld%ibmap .eq. 254) then ! use previously specified bitmap
343  if (associated(bmpsave)) then
344  gfld%bmap => bmpsave
345  else
346  print *, 'gf_getfld: Previous bit-map ' &
347  ,'specified, but none exists, '
348  call gf_free(gfld)
349  ierr = 17
350  return
351  endif
352  else ! get rid of it
353  if (associated(bmpsave)) deallocate(bmpsave)
354  endif
355  else ! do not unpack bitmap
356  call g2_gbytec(cgrib, gfld%ibmap, iofst, 8) ! Get BitMap Indicator
357  have6 = .true.
358  endif
359  endif
360 
361  ! If found Section 7, check to see if this field is the one
362  ! requested.
363  if ((isecnum .eq. 7) .and. (numfld .eq. ifldnum) .and. unpack) &
364  then
365  iofst = iofst - 40 ! reset offset to beginning of section
366  call gf_unpack7(cgrib, lcgrib, iofst, gfld%igdtnum, &
367  gfld%igdtmpl, gfld%idrtnum, &
368  gfld%idrtmpl, gfld%ndpts, &
369  gfld%fld, jerr)
370  if (jerr .ne. 0) then
371  call gf_free(gfld)
372  print *, 'gf_getfld: return from gf_unpack7 = ', jerr
373  ierr = 14
374  return
375  endif
376  have7 = .true.
377 
378  ! If bitmap is used with this field, expand data field
379  ! to grid, if possible.
380  if (gfld%ibmap .ne. 255 .AND. associated(gfld%bmap)) then
381  if (expand) then
382  allocate(newfld(gfld%ngrdpts))
383  n = 1
384  do j = 1, gfld%ngrdpts
385  if (gfld%bmap(j)) then
386  newfld(j) = gfld%fld(n)
387  n = n + 1
388  else
389  newfld(j) = 0.0
390  endif
391  enddo
392  deallocate(gfld%fld);
393  gfld%fld=>newfld;
394  gfld%expanded = .true.
395  else
396  gfld%expanded = .false.
397  endif
398  else
399  gfld%expanded = .true.
400  endif
401  endif
402 
403  ! Check to see if we read pass the end of the GRIB message and
404  ! missed the terminator string '7777'.
405  ipos = ipos + lensec ! Update beginning of section pointer
406  if (ipos .gt. (istart + lengrib)) then
407  print *, 'gf_getfld: "7777" not found at end ' &
408  ,'of GRIB message.'
409  call gf_free(gfld)
410  ierr = 7
411  return
412  endif
413  !
414  ! If unpacking requested, return when all sections have been
415  ! processed.
416  if (unpack .and. have3 .and. have4 .and. have5 .and. have6 &
417  .and. have7) return
418 
419  ! If unpacking is not requested, return when sections 3 through
420  ! 6 have been processed.
421  if ((.not. unpack) .and. have3 .and. have4 .and. have5 .and. &
422  have6) return
423  enddo
424 
425  ! If exited from above loop, the end of the GRIB message was reached
426  ! before the requested field was found.
427  print *, 'gf_getfld: GRIB message contained ', numlocal, &
428  ' different fields.'
429  print *, 'gf_getfld: The request was for the ', ifldnum, &
430  ' field.'
431  ierr = 6
432  call gf_free(gfld)
433 end subroutine gf_getfld
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 gf_free(gfld)
Free memory that was used to store array values in derived type grib_mod::gribfield.
Definition: gf_free.F90:12
subroutine gf_getfld(cgrib, lcgrib, ifldnum, unpack, expand, gfld, ierr)
This subroutine returns the Grid Definition, Product Definition, Bit-map (if applicable),...
Definition: gf_getfld.F90:68
subroutine gf_unpack1(cgrib, lcgrib, iofst, ids, idslen, ierr)
Unpack Section 1 (Identification Section) of a GRIB2 message, starting at octet 6 of that Section.
Definition: gf_unpack1.F90:43
subroutine gf_unpack2(cgrib, lcgrib, iofst, lencsec2, csec2, ierr)
Unpack Section 2 (Local Use Section) of a GRIB2 message.
Definition: gf_unpack2.F90:26
subroutine gf_unpack3(cgrib, lcgrib, iofst, igds, igdstmpl, mapgridlen, ideflist, idefnum, ierr)
Unpack Section 3 (Grid Definition Section) of a GRIB2 message, starting at octet 6 of that Section.
Definition: gf_unpack3.F90:52
subroutine gf_unpack4(cgrib, lcgrib, iofst, ipdsnum, ipdstmpl, mappdslen, coordlist, numcoord, ierr)
Unpack Section 4 (Product Definition Section) of a GRIB2 message, starting at octet 6 of that Section...
Definition: gf_unpack4.F90:37
subroutine gf_unpack5(cgrib, lcgrib, iofst, ndpts, idrsnum, idrstmpl, mapdrslen, ierr)
Unpack Section 5 (Data Representation Section) of a GRIB2 message, starting at octet 6 of that Sectio...
Definition: gf_unpack5.F90:35
subroutine gf_unpack6(cgrib, lcgrib, iofst, ngpts, ibmap, bmap, ierr)
Unpack Section 6 (Bit-Map Section) of a GRIB2 message, starting at octet 6 of that Section.
Definition: gf_unpack6.F90:30
subroutine gf_unpack7(cgrib, lcgrib, iofst, igdsnum, igdstmpl, idrsnum, idrstmpl, ndpts, fld, ierr)
Unpack Section 7 (Data Section) of a GRIB2 message.
Definition: gf_unpack7.F90:42
This Fortran module contains the declaration of derived type gribfield.
Definition: gribmod.F90:10