NCEPLIBS-g2  3.4.5
gf_getfld.f
Go to the documentation of this file.
1 
6 
191 
192  subroutine gf_getfld(cgrib,lcgrib,ifldnum,unpack,expand,gfld,ierr)
193 
194  use grib_mod
195 
196  character(len=1),intent(in) :: cgrib(lcgrib)
197  integer,intent(in) :: lcgrib,ifldnum
198  logical,intent(in) :: unpack,expand
199  type(gribfield),intent(out) :: gfld
200  integer,intent(out) :: ierr
201 ! integer,intent(out) :: igds(*),igdstmpl(*),ideflist(*)
202 ! integer,intent(out) :: ipdsnum,ipdstmpl(*)
203 ! integer,intent(out) :: idrsnum,idrstmpl(*)
204 ! integer,intent(out) :: ndpts,ibmap,idefnum,numcoord
205 ! logical*1,intent(out) :: bmap(*)
206 ! real,intent(out) :: fld(*),coordlist(*)
207 
208  character(len=4),parameter :: grib='GRIB',c7777='7777'
209  character(len=4) :: ctemp
210  real,pointer,dimension(:) :: newfld
211  integer:: listsec0(2),igds(5)
212  integer iofst,ibeg,istart
213  integer(4) :: ieee
214  logical*1,pointer,dimension(:) :: bmpsave
215  logical have3,have4,have5,have6,have7
216 
217  interface
218  subroutine gf_unpack1(cgrib,lcgrib,iofst,ids,idslen,ierr)
219  character(len=1),intent(in) :: cgrib(lcgrib)
220  integer,intent(in) :: lcgrib
221  integer,intent(inout) :: iofst
222  integer,pointer,dimension(:) :: ids
223  integer,intent(out) :: ierr,idslen
224  end subroutine gf_unpack1
225  subroutine gf_unpack2(cgrib,lcgrib,iofst,lencsec2,csec2,ierr)
226  character(len=1),intent(in) :: cgrib(lcgrib)
227  integer,intent(in) :: lcgrib
228  integer,intent(inout) :: iofst
229  integer,intent(out) :: lencsec2
230  integer,intent(out) :: ierr
231  character(len=1),pointer,dimension(:) :: csec2
232  end subroutine gf_unpack2
233  subroutine gf_unpack3(cgrib,lcgrib,iofst,igds,igdstmpl,
234  & mapgridlen,ideflist,idefnum,ierr)
235  character(len=1),intent(in) :: cgrib(lcgrib)
236  integer,intent(in) :: lcgrib
237  integer,intent(inout) :: iofst
238  integer,pointer,dimension(:) :: igdstmpl,ideflist
239  integer,intent(out) :: igds(5)
240  integer,intent(out) :: ierr,idefnum
241  end subroutine gf_unpack3
242  subroutine gf_unpack4(cgrib,lcgrib,iofst,ipdsnum,ipdstmpl,
243  & mappdslen,coordlist,numcoord,ierr)
244  character(len=1),intent(in) :: cgrib(lcgrib)
245  integer,intent(in) :: lcgrib
246  integer,intent(inout) :: iofst
247  real,pointer,dimension(:) :: coordlist
248  integer,pointer,dimension(:) :: ipdstmpl
249  integer,intent(out) :: ipdsnum
250  integer,intent(out) :: ierr,numcoord
251  end subroutine gf_unpack4
252  subroutine gf_unpack5(cgrib,lcgrib,iofst,ndpts,idrsnum,
253  & idrstmpl,mapdrslen,ierr)
254  character(len=1),intent(in) :: cgrib(lcgrib)
255  integer,intent(in) :: lcgrib
256  integer,intent(inout) :: iofst
257  integer,intent(out) :: ndpts,idrsnum
258  integer,pointer,dimension(:) :: idrstmpl
259  integer,intent(out) :: ierr
260  end subroutine gf_unpack5
261  subroutine gf_unpack6(cgrib,lcgrib,iofst,ngpts,ibmap,bmap,ierr)
262  character(len=1),intent(in) :: cgrib(lcgrib)
263  integer,intent(in) :: lcgrib,ngpts
264  integer,intent(inout) :: iofst
265  integer,intent(out) :: ibmap
266  integer,intent(out) :: ierr
267  logical*1,pointer,dimension(:) :: bmap
268  end subroutine gf_unpack6
269  subroutine gf_unpack7(cgrib,lcgrib,iofst,igdsnum,igdstmpl,
270  & idrsnum,idrstmpl,ndpts,fld,ierr)
271  character(len=1),intent(in) :: cgrib(lcgrib)
272  integer,intent(in) :: lcgrib,ndpts,idrsnum,igdsnum
273  integer,intent(inout) :: iofst
274  integer,pointer,dimension(:) :: idrstmpl,igdstmpl
275  integer,intent(out) :: ierr
276  real,pointer,dimension(:) :: fld
277  end subroutine gf_unpack7
278  end interface
279 
280  have3=.false.
281  have4=.false.
282  have5=.false.
283  have6=.false.
284  have7=.false.
285  ierr=0
286  numfld=0
287  gfld%locallen=0
288  nullify(gfld%list_opt,gfld%igdtmpl,gfld%ipdtmpl)
289  nullify(gfld%coord_list,gfld%idrtmpl,gfld%bmap,gfld%fld)
290 !
291 ! Check for valid request number
292 !
293  if (ifldnum.le.0) then
294  print *,'gf_getfld: Request for field number must be positive.'
295  ierr=3
296  return
297  endif
298 !
299 ! Check for beginning of GRIB message in the first 100 bytes
300 !
301  istart=0
302  do j=1,100
303  ctemp=cgrib(j)//cgrib(j+1)//cgrib(j+2)//cgrib(j+3)
304  if (ctemp.eq.grib ) then
305  istart=j
306  exit
307  endif
308  enddo
309  if (istart.eq.0) then
310  print *,'gf_getfld: Beginning characters GRIB not found.'
311  ierr=1
312  return
313  endif
314 !
315 ! Unpack Section 0 - Indicator Section
316 !
317  iofst=8*(istart+5)
318  call g2_gbytec(cgrib,listsec0(1),iofst,8) ! Discipline
319  iofst=iofst+8
320  call g2_gbytec(cgrib,listsec0(2),iofst,8) ! GRIB edition number
321  iofst=iofst+8
322  iofst=iofst+32
323  call g2_gbytec(cgrib,lengrib,iofst,32) ! Length of GRIB message
324  iofst=iofst+32
325  lensec0=16
326  ipos=istart+lensec0
327 !
328 ! Currently handles only GRIB Edition 2.
329 !
330  if (listsec0(2).ne.2) then
331  print *,'gf_getfld: can only decode GRIB edition 2.'
332  ierr=2
333  return
334  endif
335 !
336 ! Loop through the remaining sections keeping track of the
337 ! length of each. Also keep the latest Grid Definition Section info.
338 ! Unpack the requested field number.
339 !
340  do
341  ! Check to see if we are at end of GRIB message
342  ctemp=cgrib(ipos)//cgrib(ipos+1)//cgrib(ipos+2)//cgrib(ipos+3)
343  if (ctemp.eq.c7777 ) then
344  ipos=ipos+4
345  ! If end of GRIB message not where expected, issue error
346  if (ipos.ne.(istart+lengrib)) then
347  print *,'gf_getfld: "7777" found, but not where expected.'
348  ierr=4
349  return
350  endif
351  exit
352  endif
353  ! Get length of Section and Section number
354  iofst=(ipos-1)*8
355  call g2_gbytec(cgrib,lensec,iofst,32) ! Get Length of Section
356  iofst=iofst+32
357  call g2_gbytec(cgrib,isecnum,iofst,8) ! Get Section number
358  iofst=iofst+8
359  !print *,' lensec= ',lensec,' secnum= ',isecnum
360  !
361  ! Check to see if section number is valid
362  !
363  if ( (isecnum.lt.1).OR.(isecnum.gt.7) ) then
364  print *,'gf_getfld: Unrecognized Section Encountered=',isecnum
365  ierr=8
366  return
367  endif
368  !
369  ! If found Section 1, decode elements in Identification Section
370  !
371  if (isecnum.eq.1) then
372  iofst=iofst-40 ! reset offset to beginning of section
373  call gf_unpack1(cgrib,lcgrib,iofst,gfld%idsect,
374  & gfld%idsectlen,jerr)
375  if (jerr.ne.0) then
376  ierr=15
377  return
378  endif
379  endif
380  !
381  ! If found Section 2, Grab local section
382  ! Save in case this is the latest one before the requested field.
383  !
384  if (isecnum.eq.2) then
385  iofst=iofst-40 ! reset offset to beginning of section
386  if (associated(gfld%local)) deallocate(gfld%local)
387  call gf_unpack2(cgrib,lcgrib,iofst,gfld%locallen,
388  & gfld%local,jerr)
389  if (jerr.ne.0) then
390  ierr=16
391  return
392  endif
393  endif
394  !
395  ! If found Section 3, unpack the GDS info using the
396  ! appropriate template. Save in case this is the latest
397  ! grid before the requested field.
398  !
399  if (isecnum.eq.3) then
400  iofst=iofst-40 ! reset offset to beginning of section
401  if (associated(gfld%igdtmpl)) deallocate(gfld%igdtmpl)
402  if (associated(gfld%list_opt)) deallocate(gfld%list_opt)
403  call gf_unpack3(cgrib,lcgrib,iofst,igds,gfld%igdtmpl,
404  & gfld%igdtlen,gfld%list_opt,gfld%num_opt,jerr)
405  if (jerr.eq.0) then
406  have3=.true.
407  gfld%griddef=igds(1)
408  gfld%ngrdpts=igds(2)
409  gfld%numoct_opt=igds(3)
410  gfld%interp_opt=igds(4)
411  gfld%igdtnum=igds(5)
412  else
413  ierr=10
414  return
415  endif
416  endif
417  !
418  ! If found Section 4, check to see if this field is the
419  ! one requested.
420  !
421  if (isecnum.eq.4) then
422  numfld=numfld+1
423  if (numfld.eq.ifldnum) then
424  gfld%discipline=listsec0(1)
425  gfld%version=listsec0(2)
426  gfld%ifldnum=ifldnum
427  gfld%unpacked=unpack
428  gfld%expanded=.false.
429  iofst=iofst-40 ! reset offset to beginning of section
430  call gf_unpack4(cgrib,lcgrib,iofst,gfld%ipdtnum,
431  & gfld%ipdtmpl,gfld%ipdtlen,gfld%coord_list,
432  & gfld%num_coord,jerr)
433  if (jerr.eq.0) then
434  have4=.true.
435  else
436  ierr=11
437  return
438  endif
439  endif
440  endif
441  !
442  ! If found Section 5, check to see if this field is the
443  ! one requested.
444  !
445  if ((isecnum.eq.5).and.(numfld.eq.ifldnum)) then
446  iofst=iofst-40 ! reset offset to beginning of section
447  call gf_unpack5(cgrib,lcgrib,iofst,gfld%ndpts,gfld%idrtnum,
448  & gfld%idrtmpl,gfld%idrtlen,jerr)
449  if (jerr.eq.0) then
450  have5=.true.
451  else
452  ierr=12
453  return
454  endif
455  endif
456  !
457  ! If found Section 6, Unpack bitmap.
458  ! Save in case this is the latest
459  ! bitmap before the requested field.
460  !
461  if (isecnum.eq.6) then
462  if (unpack) then ! unpack bitmap
463  iofst=iofst-40 ! reset offset to beginning of section
464  bmpsave=>gfld%bmap ! save pointer to previous bitmap
465  call gf_unpack6(cgrib,lcgrib,iofst,gfld%ngrdpts,gfld%ibmap,
466  & gfld%bmap,jerr)
467  if (jerr.eq.0) then
468  have6=.true.
469  if (gfld%ibmap .eq. 254) then ! use previously specified bitmap
470  if ( associated(bmpsave) ) then
471  gfld%bmap=>bmpsave
472  else
473  print *,'gf_getfld: Previous bit-map specified,',
474  & ' but none exists,'
475  ierr=17
476  return
477  endif
478  else ! get rid of it
479  if ( associated(bmpsave) ) deallocate(bmpsave)
480  endif
481  else
482  ierr=13
483  return
484  endif
485  else ! do not unpack bitmap
486  call g2_gbytec(cgrib,gfld%ibmap,iofst,8) ! Get BitMap Indicator
487  have6=.true.
488  endif
489  endif
490  !
491  ! If found Section 7, check to see if this field is the
492  ! one requested.
493  !
494  if ((isecnum.eq.7).and.(numfld.eq.ifldnum).and.unpack) then
495  iofst=iofst-40 ! reset offset to beginning of section
496  call gf_unpack7(cgrib,lcgrib,iofst,gfld%igdtnum,
497  & gfld%igdtmpl,gfld%idrtnum,
498  & gfld%idrtmpl,gfld%ndpts,
499  & gfld%fld,jerr)
500  if (jerr.eq.0) then
501  have7=.true.
502  ! If bitmap is used with this field, expand data field
503  ! to grid, if possible.
504  if ( gfld%ibmap .ne. 255 .AND. associated(gfld%bmap) ) then
505  if ( expand ) then
506  allocate(newfld(gfld%ngrdpts))
507  !newfld(1:gfld%ngrdpts)=0.0
508  !newfld=unpack(gfld%fld,gfld%bmap,newfld)
509  n=1
510  do j=1,gfld%ngrdpts
511  if ( gfld%bmap(j) ) then
512  newfld(j)=gfld%fld(n)
513  n=n+1
514  else
515  newfld(j)=0.0
516  endif
517  enddo
518  deallocate(gfld%fld);
519  gfld%fld=>newfld;
520  gfld%expanded=.true.
521  else
522  gfld%expanded=.false.
523  endif
524  else
525  gfld%expanded=.true.
526  endif
527  else
528  print *,'gf_getfld: return from gf_unpack7 = ',jerr
529  ierr=14
530  return
531  endif
532  endif
533  !
534  ! Check to see if we read pass the end of the GRIB
535  ! message and missed the terminator string '7777'.
536  !
537  ipos=ipos+lensec ! Update beginning of section pointer
538  if (ipos.gt.(istart+lengrib)) then
539  print *,'gf_getfld: "7777" not found at end of GRIB message.'
540  ierr=7
541  return
542  endif
543  !
544  ! If unpacking requested, return when all sections have been
545  ! processed
546  !
547  if (unpack.and.have3.and.have4.and.have5.and.have6.and.have7)
548  & return
549  !
550  ! If unpacking is not requested, return when sections
551  ! 3 through 6 have been processed
552  !
553  if ((.NOT.unpack).and.have3.and.have4.and.have5.and.have6)
554  & return
555 
556  enddo
557 
558 !
559 ! If exited from above loop, the end of the GRIB message was reached
560 ! before the requested field was found.
561 !
562  print *,'gf_getfld: GRIB message contained ',numlocal,
563  & ' different fields.'
564  print *,'gf_getfld: The request was for the ',ifldnum,
565  & ' field.'
566  ierr=6
567 
568  return
569  end
570 
gf_unpack4
subroutine gf_unpack4(cgrib, lcgrib, iofst, ipdsnum, ipdstmpl, mappdslen, coordlist, numcoord, ierr)
This subroutine unpacks Section 4 (Product Definition Section) starting at octet 6 of that Section.
Definition: gf_unpack4.f:43
gf_unpack7
subroutine gf_unpack7(cgrib, lcgrib, iofst, igdsnum, igdstmpl, idrsnum, idrstmpl, ndpts, fld, ierr)
This subroutine unpacks Section 7 (Data Section).
Definition: gf_unpack7.f:44
gf_unpack6
subroutine gf_unpack6(cgrib, lcgrib, iofst, ngpts, ibmap, bmap, ierr)
This subroutine unpacks Section 6 (Bit-Map Section) starting at octet 6 of that Section.
Definition: gf_unpack6.f:37
gf_getfld
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.f:193
grib_mod::gribfield
Definition: gribmod.f:155
grib_mod
PROGRAM HISTORY LOG:
Definition: gribmod.f:151
gf_unpack3
subroutine gf_unpack3(cgrib, lcgrib, iofst, igds, igdstmpl, mapgridlen, ideflist, idefnum, ierr)
This subroutine unpacks Section 3 (Grid Definition Section) starting at octet 6 of that Section.
Definition: gf_unpack3.f:54
gf_unpack5
subroutine gf_unpack5(cgrib, lcgrib, iofst, ndpts, idrsnum, idrstmpl, mapdrslen, ierr)
This subroutine unpacks Section 5 (Data Representation Section) starting at octet 6 of that Section.
Definition: gf_unpack5.f:38
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
gf_unpack2
subroutine gf_unpack2(cgrib, lcgrib, iofst, lencsec2, csec2, ierr)
This subroutine unpacks Section 2 (Local Use Section) as defined in GRIB Edition 2.
Definition: gf_unpack2.f:22
gf_unpack1
subroutine gf_unpack1(cgrib, lcgrib, iofst, ids, idslen, ierr)
This subroutine unpacks Section 1 (Identification Section) starting at octet 6 of that Section.
Definition: gf_unpack1.f:43