NCEPLIBS-g2  3.5.0
g2get.F90
Go to the documentation of this file.
1 
4 
52 subroutine gb_info(cgrib, lcgrib, listsec0, listsec1, &
53  numfields, numlocal, maxlocal, ierr)
54  use g2logging
55  implicit none
56 
57  character(len = 1), intent(in) :: cgrib(lcgrib)
58  integer, intent(in) :: lcgrib
59  integer, intent(out) :: listsec0(3), listsec1(13)
60  integer, intent(out) :: numlocal, numfields, maxlocal, ierr
61 
62  character(len = 4), parameter :: grib = 'GRIB', c7777 = '7777'
63  character(len = 4) :: ctemp
64  integer, parameter :: zero = 0, one = 1
65  integer, parameter :: mapsec1len = 13
66  integer, parameter :: mapsec1(mapsec1len) = (/ 2, 2, 1, 1, 1, 2, 1, 1, 1, 1, 1, 1, 1 /)
67  integer :: iofst, istart
68  integer :: nbits, lensec1, lensec0, lensec, lenposs, lengrib, j
69  integer (kind = 8) :: lengrib8
70  integer :: i, ipos, isecnum
71 
72  interface
73  subroutine g2_gbytec(in, iout, iskip, nbits)
74  character*1, intent(in) :: in(*)
75  integer, intent(inout) :: iout(*)
76  integer, intent(in) :: iskip, nbits
77  end subroutine g2_gbytec
78  subroutine g2_gbytec1(in, siout, iskip, nbits)
79  character*1, intent(in) :: in(*)
80  integer, intent(inout) :: siout
81  integer, intent(in) :: iskip, nbits
82  end subroutine g2_gbytec1
83  subroutine g2_gbytec81(in, siout, iskip, nbits)
84  character*1, intent(in) :: in(*)
85  integer (kind = 8), intent(inout) :: siout
86  integer, intent(in) :: iskip, nbits
87  integer (kind = 8) :: iout(1)
88  end subroutine g2_gbytec81
89  end interface
90 
91 #ifdef LOGGING
92  write(g2_log_msg, *) 'gb_info: lcgrib ', lcgrib
93  call g2_log(1)
94 #endif
95 
96  ierr = 0
97  numlocal = 0
98  numfields = 0
99  maxlocal = 0
100 
101  ! Check for beginning of GRIB message in the first 100 bytes.
102  istart = 0
103  do j = 1, 100
104  ctemp = cgrib(j) // cgrib(j + 1) // cgrib(j + 2) // cgrib(j+3)
105  if (ctemp .eq. grib ) then
106  istart = j
107  exit
108  endif
109  enddo
110  if (istart .eq. 0) then
111  print *, 'gb_info: Beginning characters GRIB not found.'
112  ierr = 1
113  return
114  endif
115 
116  ! Unpack Section 0 - Indicator Section.
117  iofst = 8 * (istart + 5)
118  call g2_gbytec(cgrib, listsec0(1), iofst, 8) ! Discipline
119  iofst = iofst + 8
120  call g2_gbytec(cgrib, listsec0(2), iofst, 8) ! GRIB edition number
121  iofst = iofst + 8
122 
123 #ifdef LOGGING
124  ! Log results for debugging.
125  write(g2_log_msg, *) 'before getting len: iofst/8 ', iofst/8
126  call g2_log(2)
127 #endif
128  ! Bytes 9-16 contain the length of GRIB message. This is an 8-byte
129  ! value, but unfortunately we only have a 4-byte subroutine
130  ! parameter for it.
131  call g2_gbytec81(cgrib, lengrib8, iofst, 64)
132  lengrib = int(lengrib8, kind(4))
133  iofst = iofst + 32
134  iofst = iofst + 32
135  listsec0(3) = lengrib
136  lensec0 = 16
137  ipos = istart + lensec0
138 
139  ! The g2 library only handles GRIB2.
140  if (listsec0(2) .ne. 2) then
141  print *, 'gb_info: can only decode GRIB edition 2.'
142  ierr = 2
143  return
144  endif
145 
146  ! Unpack Section 1 - Identification Section.
147  call g2_gbytec1(cgrib, lensec1, iofst, 32) ! Length of Section 1
148  iofst = iofst + 32
149  call g2_gbytec1(cgrib, isecnum, iofst, 8) ! Section number ( 1 )
150  iofst = iofst + 8
151  if (isecnum .ne. 1) then
152  print *, 'gb_info: Could not find section 1.'
153  ierr = 3
154  return
155  endif
156 
157  ! Unpack each input value in array listsec1 into the the appropriate
158  ! number of octets, which are specified in corresponding entries in
159  ! array mapsec1.
160  do i = 1, mapsec1len
161  nbits = mapsec1(i) * 8
162  call g2_gbytec(cgrib, listsec1(i), iofst, nbits)
163  iofst = iofst + nbits
164  enddo
165  ipos = ipos + lensec1
166 
167  ! Loop through the remaining sections to see if they are valid.
168  ! Also count the number of times Section 2 and Section 4 appear.
169  do
170  ctemp = cgrib(ipos) // cgrib(ipos + 1) // cgrib(ipos + 2) // cgrib(ipos + 3)
171  if (ctemp .eq. c7777 ) then
172  ipos = ipos + 4
173  if (ipos .ne. (istart + lengrib)) then
174  print *, 'gb_info: "7777" found, but not where expected.'
175  ierr = 4
176  return
177  endif
178  exit
179  endif
180  iofst = (ipos - 1) * 8
181  call g2_gbytec1(cgrib, lensec, iofst, 32) ! Get Length of Section
182  iofst = iofst + 32
183  call g2_gbytec1(cgrib, isecnum, iofst, 8) ! Get Section number
184  iofst = iofst + 8
185  ipos = ipos+lensec ! Update beginning of section pointer
186  if (ipos .gt. (istart + lengrib)) then
187  print *, 'gb_info: "7777" not found at end of GRIB message.'
188  ierr = 5
189  return
190  endif
191  if (isecnum .ge. 2 .AND. isecnum .le. 7) then
192  if (isecnum .eq. 2) then ! Local Section 2
193  ! Increment counter for total number of local sections found.
194  numlocal = numlocal + 1
195  lenposs = lensec - 5
196  if (lenposs .gt. maxlocal) maxlocal = lenposs
197  elseif (isecnum .eq. 4) then
198  ! Increment counter for total number of fields found.
199  numfields = numfields + 1
200  endif
201  else
202  print *, 'gb_info: Invalid section number found in GRIB message: ', isecnum
203  ierr = 6
204  return
205  endif
206  enddo
207 
208 end subroutine gb_info
209 
282 subroutine gribinfo(cgrib, lcgrib, listsec0, listsec1, &
283  numlocal, numfields, maxvals, ierr)
284  implicit none
285 
286  character(len = 1), intent(in) :: cgrib(lcgrib)
287  integer, intent(in) :: lcgrib
288  integer, intent(out) :: listsec0(3), listsec1(13), maxvals(7)
289  integer, intent(out) :: numlocal, numfields, ierr
290 
291  integer :: i, ipos, isecnum, j, lengrib, lenposs, lensec, lensec0, lensec1
292  integer :: maxcoordlist, maxdeflist, maxdrstmpl, maxgridpts, maxpdstmpl, maxgdstmpl
293  integer :: maxsec2len, nbits, nbyte, ngdpts, numcoord
294  character(len = 4), parameter :: grib = 'GRIB', c7777 = '7777'
295  character(len = 4) :: ctemp
296  integer, parameter :: zero = 0, one = 1
297  integer, parameter :: mapsec1len = 13
298  integer, parameter :: mapsec1(mapsec1len) = (/ 2, 2, 1, 1, 1, 2, 1, 1, &
299  1, 1, 1, 1, 1 /)
300  integer iofst, istart
301  integer (kind = 8) :: lengrib8
302 
303  ierr = 0
304  numlocal = 0
305  numfields = 0
306  maxsec2len = 1
307  maxgdstmpl = 1
308  maxdeflist = 1
309  maxpdstmpl = 1
310  maxcoordlist = 1
311  maxdrstmpl = 1
312  maxgridpts = 0
313 
314  ! Check for beginning of GRIB message in the first 100 bytes.
315  istart = 0
316  do j = 1, 100
317  ctemp = cgrib(j) // cgrib(j + 1) // cgrib(j + 2) // cgrib(j + 3)
318  if (ctemp .eq. grib) then
319  istart = j
320  exit
321  endif
322  enddo
323  if (istart .eq. 0) then
324  print *, 'gribinfo: Beginning characters GRIB not found.'
325  ierr = 1
326  return
327  endif
328 
329  ! Unpack Section 0 - Indicator Section.
330  iofst = 8 * (istart + 5)
331  call g2_gbytec(cgrib, listsec0(1), iofst, 8) ! Discipline
332  iofst = iofst + 8
333  call g2_gbytec(cgrib, listsec0(2), iofst, 8) ! GRIB edition number
334  iofst = iofst + 8
335  ! Bytes 9-16 contain the length of GRIB message. This is an 8-byte
336  ! value, but unfortunately we only have a 4-byte subroutine
337  ! parameter for it.
338  call g2_gbytec81(cgrib, lengrib8, iofst, 64) ! Length of GRIB message
339  lengrib = int(lengrib8, kind(4))
340  iofst = iofst + 32
341  iofst = iofst + 32
342  listsec0(3) = lengrib
343  lensec0 = 16
344  ipos = istart + lensec0
345 
346  ! Currently handles only GRIB Edition 2.
347  if (listsec0(2) .ne. 2) then
348  print *, 'gribinfo: can only decode GRIB edition 2.'
349  ierr = 2
350  return
351  endif
352 
353  ! Unpack Section 1 - Identification Section.
354  call g2_gbytec1(cgrib, lensec1, iofst, 32) ! Length of Section 1
355  iofst = iofst + 32
356  call g2_gbytec1(cgrib, isecnum, iofst, 8) ! Section number (1)
357  iofst = iofst + 8
358  if (isecnum .ne. 1) then
359  print *, 'gribinfo: Could not find section 1.'
360  ierr = 3
361  return
362  endif
363 
364  ! Unpack each input value in array listsec1 into the the appropriate
365  ! number of octets, which are specified in corresponding entries in
366  ! array mapsec1.
367  do i = 1, mapsec1len
368  nbits = mapsec1(i) * 8
369  call g2_gbytec(cgrib, listsec1(i), iofst, nbits)
370  iofst = iofst + nbits
371  enddo
372  ipos = ipos + lensec1
373 
374  ! Loop through the remaining sections keeping track of the length of
375  ! each. Also count the number of times Section 2 and Section 4
376  ! appear.
377  do
378  ctemp = cgrib(ipos) // cgrib(ipos + 1) // cgrib(ipos + 2) // &
379  cgrib(ipos + 3)
380  if (ctemp .eq. c7777) then
381  ipos = ipos + 4
382  if (ipos .ne. (istart + lengrib)) then
383  print *, 'gribinfo: "7777" found, but not where expected.'
384  ierr = 4
385  return
386  endif
387  exit
388  endif
389  iofst = (ipos - 1) * 8
390  call g2_gbytec1(cgrib, lensec, iofst, 32) ! Get Length of Section
391  iofst = iofst + 32
392  call g2_gbytec1(cgrib, isecnum, iofst, 8) ! Get Section number
393  iofst = iofst + 8
394  ipos = ipos + lensec ! Update beginning of section pointer
395  if (ipos .gt. (istart + lengrib)) then
396  print *, 'gribinfo: "7777" not found at end of GRIB message.'
397  ierr = 5
398  return
399  endif
400  if (isecnum .eq. 2) then ! Local Section 2
401  ! Increment counter for total number of local sections found
402  ! and determine largest Section 2 in message.
403  numlocal = numlocal + 1
404  lenposs = lensec-5
405  if (lenposs .gt. maxsec2len) maxsec2len = lenposs
406  elseif (isecnum .eq. 3) then
407  iofst = iofst + 8 ! skip source of grid def.
408  call g2_gbytec1(cgrib, ngdpts, iofst, 32) ! Get Num of Grid Points
409  iofst = iofst + 32
410  call g2_gbytec1(cgrib, nbyte, iofst, 8) ! Get Num octets for opt. list
411  iofst = iofst + 8
412  if (ngdpts .gt. maxgridpts) maxgridpts = ngdpts
413  lenposs = lensec - 14
414  if (lenposs .gt. maxgdstmpl) maxgdstmpl = lenposs
415  if (nbyte .ne. 0) then
416  lenposs = lenposs / nbyte
417  if (lenposs .gt. maxdeflist) maxdeflist = lenposs
418  endif
419  elseif (isecnum .eq. 4) then
420  numfields = numfields + 1
421  call g2_gbytec1(cgrib, numcoord, iofst, 16) ! Get Num of Coord Values
422  iofst = iofst + 16
423  if (numcoord .ne. 0) then
424  if (numcoord .gt. maxcoordlist) maxcoordlist = numcoord
425  endif
426  lenposs = lensec - 9
427  if (lenposs.gt.maxpdstmpl) maxpdstmpl = lenposs
428  elseif (isecnum .eq. 5) then
429  lenposs = lensec-11
430  if (lenposs .gt. maxdrstmpl) maxdrstmpl = lenposs
431  endif
432  enddo
433 
434  maxvals(1) = maxsec2len
435  maxvals(2) = maxgdstmpl
436  maxvals(3) = maxdeflist
437  maxvals(4) = maxpdstmpl
438  maxvals(5) = maxcoordlist
439  maxvals(6) = maxdrstmpl
440  maxvals(7) = maxgridpts
441 end subroutine gribinfo
442 
543 subroutine getfield(cgrib, lcgrib, ifldnum, igds, igdstmpl, &
544  igdslen, ideflist, idefnum, ipdsnum, ipdstmpl, ipdslen, &
545  coordlist, numcoord, ndpts, idrsnum, idrstmpl, idrslen, &
546  ibmap, bmap, fld, ierr)
547  implicit none
548 
549  character(len = 1), intent(in) :: cgrib(lcgrib)
550  integer, intent(in) :: lcgrib, ifldnum
551  integer, intent(out) :: igds(*), igdstmpl(*), ideflist(*)
552  integer, intent(out) :: ipdsnum, ipdstmpl(*)
553  integer, intent(out) :: idrsnum, idrstmpl(*)
554  integer, intent(out) :: ndpts, ibmap, idefnum, numcoord
555  integer, intent(out) :: igdslen, ipdslen, idrslen
556  real, intent(out) :: fld(*), coordlist(*)
557  logical*1, intent(out) :: bmap(*)
558  integer, intent(out) :: ierr
559 
560  character(len = 4), parameter :: grib = 'GRIB', c7777 = '7777'
561  character(len = 4) :: ctemp
562  integer :: listsec0(2)
563  integer :: iofst, istart
564  real (kind = 4) :: ieee(1)
565  logical :: have3, have4, have5, have6, have7
566  integer (kind = 8) :: lengrib8
567  integer :: numfld, j, lengrib, lensec0, ipos
568  integer :: lensec, isecnum, jerr, ier, numlocal
569 
570  have3 = .false.
571  have4 = .false.
572  have5 = .false.
573  have6 = .false.
574  have7 = .false.
575  ierr = 0
576  numfld = 0
577  numlocal = 0
578 
579  ! Check for valid request number.
580  if (ifldnum .le. 0) then
581  print *, 'getfield: Request for field number ' &
582  ,'must be positive.'
583  ierr = 3
584  return
585  endif
586 
587  ! Check for beginning of GRIB message in the first 100 bytes.
588  istart = 0
589  do j = 1, 100
590  ctemp = cgrib(j) // cgrib(j + 1) // cgrib(j + 2) // cgrib(j + 3)
591  if (ctemp .eq. grib) then
592  istart = j
593  exit
594  endif
595  enddo
596  if (istart .eq. 0) then
597  print *, 'getfield: Beginning characters GRIB not found.'
598  ierr = 1
599  return
600  endif
601 
602  ! Unpack Section 0 - Indicator Section.
603  iofst = 8 * (istart + 5)
604  call g2_gbytec(cgrib, listsec0(1), iofst, 8) ! Discipline
605  iofst = iofst + 8
606  call g2_gbytec(cgrib, listsec0(2), iofst, 8) ! GRIB edition number
607  iofst = iofst + 8
608  ! Bytes 9-16 contain the length of GRIB message. This is an 8-byte
609  ! value, but unfortunately we only have a 4-byte subroutine
610  ! parameter for it.
611  call g2_gbytec81(cgrib, lengrib8, iofst, 64) ! Length of GRIB message
612  lengrib = int(lengrib8, kind(4))
613  iofst = iofst + 32
614  iofst = iofst + 32
615  lensec0 = 16
616  ipos = istart + lensec0
617 
618  ! The g2 library only handles GRIB2.
619  if (listsec0(2) .ne. 2) then
620  print *, 'getfield: can only decode GRIB edition 2.'
621  ierr = 2
622  return
623  endif
624 
625  ! Loop through the remaining sections keeping track of the length of
626  ! each. Also keep the latest Grid Definition Section info. Unpack
627  ! the requested field number.
628  do
629  ! Check to see if we are at end of GRIB message
630  ctemp = cgrib(ipos) // cgrib(ipos + 1) // cgrib(ipos + 2) // &
631  cgrib(ipos + 3)
632  if (ctemp .eq. c7777) then
633  ipos = ipos + 4
634  ! If end of GRIB message not where expected, issue error
635  if (ipos.ne.(istart + lengrib)) then
636  print *, 'getfield: "7777" found, but not ' &
637  ,'where expected.'
638  ierr = 4
639  return
640  endif
641  exit
642  endif
643  ! Get length of Section and Section number
644  iofst = (ipos - 1) * 8
645  call g2_gbytec1(cgrib, lensec, iofst, 32) ! Get Length of Section
646  iofst = iofst + 32
647  call g2_gbytec1(cgrib, isecnum, iofst, 8) ! Get Section number
648  iofst = iofst + 8
649 
650  ! If found Section 3, unpack the GDS info using the appropriate
651  ! template. Save in case this is the latest grid before the
652  ! requested field.
653  if (isecnum .eq. 3) then
654  iofst = iofst - 40 ! reset offset to beginning of section
655  call unpack3(cgrib, lcgrib, iofst, igds, igdstmpl, &
656  igdslen, ideflist, idefnum, jerr)
657  if (jerr .eq. 0) then
658  have3 = .true.
659  else
660  ierr = 10
661  return
662  endif
663  endif
664 
665  ! If found Section 4, check to see if this field is the one
666  ! requested.
667  if (isecnum .eq. 4) then
668  numfld = numfld + 1
669  if (numfld .eq. ifldnum) then
670  iofst = iofst - 40 ! reset offset to beginning of section
671  call unpack4(cgrib, lcgrib, iofst, ipdsnum, ipdstmpl, &
672  ipdslen, coordlist, numcoord, jerr)
673  if (jerr .eq. 0) then
674  have4 = .true.
675  else
676  ierr = 11
677  return
678  endif
679  endif
680  endif
681 
682  ! If found Section 5, check to see if this field is the one
683  ! requested.
684  if ((isecnum .eq. 5) .and. (numfld .eq. ifldnum)) then
685  iofst = iofst - 40 ! reset offset to beginning of section
686  call unpack5(cgrib, lcgrib, iofst, ndpts, idrsnum, &
687  idrstmpl, idrslen, jerr)
688  if (jerr .eq. 0) then
689  have5 = .true.
690  else
691  ierr = 12
692  return
693  endif
694  endif
695 
696  ! If found Section 6, Unpack bitmap. Save in case this is the
697  ! latest bitmap before the requested field.
698  if (isecnum .eq. 6) then
699  iofst = iofst - 40 ! reset offset to beginning of section
700  call unpack6(cgrib, lcgrib, iofst, igds(2), ibmap, bmap, &
701  jerr)
702  if (jerr .eq. 0) then
703  have6 = .true.
704  else
705  ierr = 13
706  return
707  endif
708  endif
709 
710  ! If found Section 7, check to see if this field is the one
711  ! requested.
712  if ((isecnum .eq. 7) .and. (numfld .eq. ifldnum)) then
713  if (idrsnum .eq. 0) then
714  call simunpack(cgrib(ipos + 5), lensec - 6, idrstmpl, &
715  ndpts, fld)
716  have7 = .true.
717  elseif (idrsnum .eq. 2 .or. idrsnum .eq. 3) then
718  call comunpack(cgrib(ipos + 5), lensec - 6, lensec, &
719  idrsnum,idrstmpl, ndpts, fld, ier)
720  if (ier .ne. 0) then
721  ierr = 14
722  return
723  endif
724  have7 = .true.
725  elseif (idrsnum .eq. 50) then
726  call simunpack(cgrib(ipos + 5), lensec - 6, idrstmpl, &
727  ndpts - 1, fld(2))
728  ieee = transfer(idrstmpl(5), ieee, 1)
729  call rdieee(ieee, fld(1), 1)
730  have7 = .true.
731  elseif (idrsnum .eq. 40 .or. idrsnum .eq. 40000) then
732  call jpcunpack(cgrib(ipos + 5), lensec - 5, idrstmpl, &
733  ndpts, fld)
734  have7 = .true.
735  elseif (idrsnum .eq. 41 .or. idrsnum .eq. 40010) then
736  call pngunpack(cgrib(ipos + 5), lensec - 5, idrstmpl, &
737  ndpts, fld)
738  have7 = .true.
739  else
740  print *, 'getfield: Data Representation Template ', &
741  idrsnum, ' not yet implemented.'
742  ierr = 9
743  return
744  endif
745  endif
746 
747  ! Check to see if we read pass the end of the GRIB message and
748  ! missed the terminator string '7777'.
749  ipos = ipos + lensec ! Update beginning of section pointer
750  if (ipos .gt. (istart + lengrib)) then
751  print *, 'getfield: "7777" not found at end' &
752  ,' of GRIB message.'
753  ierr = 7
754  return
755  endif
756 
757  if (have3 .and. have4 .and. have5 .and. have6 .and. have7) &
758  return
759 
760  enddo
761 
762  ! If exited from above loop, the end of the GRIB message was reached
763  ! before the requested field was found.
764  print *, 'getfield: GRIB message contained ', numlocal, &
765  ' different fields.'
766  print *, 'getfield: The request was for the ', ifldnum, &
767  ' field.'
768  ierr = 6
769 
770 end subroutine getfield
771 
811 subroutine unpack3(cgrib, lcgrib, iofst, igds, igdstmpl, &
812  mapgridlen, ideflist, idefnum, ierr)
813  use gridtemplates
814  implicit none
815 
816  character(len = 1), intent(in) :: cgrib(lcgrib)
817  integer, intent(in) :: lcgrib
818  integer, intent(inout) :: iofst
819  integer, intent(out) :: igds(*), igdstmpl(*), ideflist(*)
820  integer, intent(out) :: ierr, idefnum
821 
822  integer, allocatable :: mapgrid(:)
823  integer :: mapgridlen, ibyttem
824  logical needext
825  integer :: lensec, iret, i, nbits, isign, newmapgridlen
826 
827  ierr = 0
828 
829  call g2_gbytec1(cgrib, lensec, iofst, 32) ! Get Length of Section
830  iofst = iofst + 32
831  iofst = iofst + 8 ! skip section number
832 
833  call g2_gbytec1(cgrib, igds(1), iofst, 8) ! Get source of Grid def.
834  iofst = iofst + 8
835  call g2_gbytec1(cgrib, igds(2), iofst, 32) ! Get number of grid pts.
836  iofst = iofst + 32
837  call g2_gbytec1(cgrib, igds(3), iofst, 8) ! Get num octets for opt. list
838  iofst = iofst + 8
839  call g2_gbytec1(cgrib, igds(4), iofst, 8) ! Get interpret. for opt. list
840  iofst = iofst + 8
841  call g2_gbytec1(cgrib, igds(5), iofst, 16) ! Get Grid Def Template num.
842  iofst = iofst + 16
843  if (igds(1) .eq. 0) then
844  allocate(mapgrid(lensec))
845  ! Get Grid Definition Template
846  call getgridtemplate(igds(5), mapgridlen, mapgrid, needext, &
847  iret)
848  if (iret .ne. 0) then
849  ierr = 5
850  return
851  endif
852  else
853  mapgridlen = 0
854  needext = .false.
855  endif
856 
857  ! Unpack each value into array igdstmpl from the the appropriate
858  ! number of octets, which are specified in corresponding entries in
859  ! array mapgrid.
860  ibyttem = 0
861  do i = 1, mapgridlen
862  nbits = iabs(mapgrid(i)) * 8
863  if (mapgrid(i) .ge. 0) then
864  call g2_gbytec1(cgrib, igdstmpl(i), iofst, nbits)
865  else
866  call g2_gbytec1(cgrib, isign, iofst, 1)
867  call g2_gbytec1(cgrib, igdstmpl(i), iofst + 1, nbits-1)
868  if (isign .eq. 1) igdstmpl(i) = -igdstmpl(i)
869  endif
870  iofst = iofst + nbits
871  ibyttem = ibyttem + iabs(mapgrid(i))
872  enddo
873 
874  ! Check to see if the Grid Definition Template needs to be
875  ! extended. The number of values in a specific template may vary
876  ! depending on data specified in the "static" part of the template.
877  if (needext) then
878  call extgridtemplate(igds(5), igdstmpl, newmapgridlen, &
879  mapgrid)
880  ! Unpack the rest of the Grid Definition Template
881  do i = mapgridlen + 1, newmapgridlen
882  nbits = iabs(mapgrid(i)) * 8
883  if (mapgrid(i) .ge. 0) then
884  call g2_gbytec1(cgrib, igdstmpl(i), iofst, nbits)
885  else
886  call g2_gbytec1(cgrib, isign, iofst, 1)
887  call g2_gbytec1(cgrib, igdstmpl(i), iofst + 1, nbits - &
888  1)
889  if (isign .eq. 1) igdstmpl(i) = -igdstmpl(i)
890  endif
891  iofst = iofst + nbits
892  ibyttem = ibyttem + iabs(mapgrid(i))
893  enddo
894  mapgridlen = newmapgridlen
895  endif
896 
897  ! Unpack optional list of numbers defining number of points in each
898  ! row or column, if included. This is used for non regular grids.
899  if (igds(3) .ne. 0) then
900  nbits = igds(3) * 8
901  idefnum = (lensec - 14 - ibyttem) / igds(3)
902  call g2_gbytesc(cgrib, ideflist, iofst, nbits, 0, idefnum)
903  iofst = iofst + (nbits * idefnum)
904  else
905  idefnum = 0
906  endif
907  if (allocated(mapgrid)) deallocate(mapgrid)
908 end subroutine unpack3
909 
936 subroutine unpack4(cgrib, lcgrib, iofst, ipdsnum, ipdstmpl, &
937  mappdslen, coordlist, numcoord, ierr)
938  use pdstemplates
939  implicit none
940 
941  character(len = 1), intent(in) :: cgrib(lcgrib)
942  integer, intent(in) :: lcgrib
943  integer, intent(inout) :: iofst
944  real, intent(out) :: coordlist(*)
945  integer, intent(out) :: ipdsnum, ipdstmpl(*)
946  integer, intent(out) :: ierr, numcoord
947 
948  real(4), allocatable :: coordieee(:)
949  integer, allocatable :: mappds(:)
950  integer :: mappdslen
951  logical needext
952  integer :: lensec, iret, i, nbits, isign, newmappdslen
953 
954  ierr = 0
955 
956  call g2_gbytec1(cgrib, lensec, iofst, 32) ! Get Length of Section
957  iofst = iofst + 32
958  iofst = iofst + 8 ! skip section number
959  allocate(mappds(lensec))
960 
961  call g2_gbytec1(cgrib, numcoord, iofst, 16) ! Get num of coordinate values
962  iofst = iofst + 16
963  call g2_gbytec1(cgrib, ipdsnum, iofst, 16) ! Get Prod. Def Template num.
964  iofst = iofst + 16
965 
966  ! Get Product Definition Template.
967  call getpdstemplate(ipdsnum, mappdslen, mappds, needext, iret)
968  if (iret.ne.0) then
969  ierr = 5
970  return
971  endif
972 
973  ! Unpack each value into array ipdstmpl from the the appropriate
974  ! number of octets, which are specified in corresponding entries in
975  ! array mappds.
976  do i = 1, mappdslen
977  nbits = iabs(mappds(i)) * 8
978  if (mappds(i) .ge. 0) then
979  call g2_gbytec1(cgrib, ipdstmpl(i), iofst, nbits)
980  else
981  call g2_gbytec1(cgrib, isign, iofst, 1)
982  call g2_gbytec1(cgrib, ipdstmpl(i), iofst + 1, nbits-1)
983  if (isign .eq. 1) ipdstmpl(i) = -ipdstmpl(i)
984  endif
985  iofst = iofst + nbits
986  enddo
987 
988  ! Check to see if the Product Definition Template needs to be
989  ! extended. The number of values in a specific template may vary
990  ! depending on data specified in the "static" part of the template.
991  if (needext) then
992  call extpdstemplate(ipdsnum, ipdstmpl, newmappdslen, mappds)
993 
994  ! Unpack the rest of the Product Definition Template.
995  do i = mappdslen + 1, newmappdslen
996  nbits = iabs(mappds(i)) * 8
997  if (mappds(i) .ge. 0) then
998  call g2_gbytec1(cgrib, ipdstmpl(i), iofst, nbits)
999  else
1000  call g2_gbytec1(cgrib, isign, iofst, 1)
1001  call g2_gbytec1(cgrib, ipdstmpl(i), iofst + 1, nbits-1)
1002  if (isign .eq. 1) ipdstmpl(i) = -ipdstmpl(i)
1003  endif
1004  iofst = iofst + nbits
1005  enddo
1006  mappdslen = newmappdslen
1007  endif
1008 
1009  ! Get Optional list of vertical coordinate values after the Product
1010  ! Definition Template, if necessary.
1011  if (numcoord .ne. 0) then
1012  allocate (coordieee(numcoord))
1013  call g2_gbytescr(cgrib, coordieee, iofst, 32, 0, numcoord)
1014  call rdieee(coordieee, coordlist, numcoord)
1015  deallocate (coordieee)
1016  iofst = iofst + (32*numcoord)
1017  endif
1018  if (allocated(mappds)) deallocate(mappds)
1019 end subroutine unpack4
1020 
1043 subroutine unpack5(cgrib, lcgrib, iofst, ndpts, idrsnum, &
1044  idrstmpl, mapdrslen, ierr)
1045  use drstemplates
1046  implicit none
1047 
1048  character(len = 1), intent(in) :: cgrib(lcgrib)
1049  integer, intent(in) :: lcgrib
1050  integer, intent(inout) :: iofst
1051  integer, intent(out) :: ndpts, idrsnum, idrstmpl(*)
1052  integer, intent(out) :: ierr
1053 
1054  ! integer, allocatable :: mapdrs(:)
1055  integer, allocatable :: mapdrs(:)
1056  integer :: mapdrslen
1057  logical needext
1058  integer :: lensec, i, nbits, isign, newmapdrslen, iret
1059 
1060  ierr = 0
1061 
1062  call g2_gbytec1(cgrib, lensec, iofst, 32) ! Get Length of Section
1063  iofst = iofst + 32
1064  iofst = iofst + 8 ! skip section number
1065  allocate(mapdrs(lensec))
1066 
1067  call g2_gbytec1(cgrib, ndpts, iofst, 32) ! Get num of data points
1068  iofst = iofst + 32
1069  call g2_gbytec1(cgrib, idrsnum, iofst, 16) ! Get Data Rep Template Num.
1070  iofst = iofst + 16
1071 
1072  ! Gen Data Representation Template
1073  call getdrstemplate(idrsnum, mapdrslen, mapdrs, needext, iret)
1074  if (iret.ne.0) then
1075  ierr = 7
1076  return
1077  endif
1078 
1079  ! Unpack each value into array ipdstmpl from the the appropriate
1080  ! number of octets, which are specified in corresponding entries in
1081  ! array mappds.
1082  do i = 1, mapdrslen
1083  nbits = iabs(mapdrs(i))*8
1084  if (mapdrs(i).ge.0) then
1085  call g2_gbytec1(cgrib, idrstmpl(i), iofst, nbits)
1086  else
1087  call g2_gbytec1(cgrib, isign, iofst, 1)
1088  call g2_gbytec1(cgrib, idrstmpl(i), iofst + 1, nbits-1)
1089  if (isign.eq.1) idrstmpl(i) = -idrstmpl(i)
1090  endif
1091  iofst = iofst + nbits
1092  enddo
1093 
1094  ! Check to see if the Data Representation Template needs to be
1095  ! extended. The number of values in a specific template may vary
1096  ! depending on data specified in the "static" part of the template.
1097  if (needext) then
1098  call extdrstemplate(idrsnum, idrstmpl, newmapdrslen, mapdrs)
1099  ! Unpack the rest of the Data Representation Template.
1100  do i = mapdrslen + 1, newmapdrslen
1101  nbits = iabs(mapdrs(i)) * 8
1102  if (mapdrs(i) .ge. 0) then
1103  call g2_gbytec1(cgrib, idrstmpl(i), iofst, nbits)
1104  else
1105  call g2_gbytec1(cgrib, isign, iofst, 1)
1106  call g2_gbytec1(cgrib, idrstmpl(i), iofst + 1, nbits - 1)
1107  if (isign .eq. 1) idrstmpl(i) = -idrstmpl(i)
1108  endif
1109  iofst = iofst + nbits
1110  enddo
1111  mapdrslen = newmapdrslen
1112  endif
1113  if (allocated(mapdrs)) deallocate(mapdrs)
1114 end subroutine unpack5
1115 
1137 subroutine unpack6(cgrib, lcgrib, iofst, ngpts, ibmap, bmap, ierr)
1138  implicit none
1139 
1140  character(len = 1), intent(in) :: cgrib(lcgrib)
1141  integer, intent(in) :: lcgrib, ngpts
1142  integer, intent(inout) :: iofst
1143  integer, intent(out) :: ibmap
1144  integer, intent(out) :: ierr
1145  logical*1, intent(out) :: bmap(ngpts)
1146 
1147  integer :: intbmap(ngpts)
1148  integer :: j
1149 
1150  ierr = 0
1151 
1152  iofst = iofst + 32 ! skip Length of Section
1153  iofst = iofst + 8 ! skip section number
1154 
1155  call g2_gbytec1(cgrib, ibmap, iofst, 8) ! Get bit-map indicator
1156  iofst = iofst + 8
1157 
1158  if (ibmap.eq.0) then ! Unpack bitmap
1159  call g2_gbytesc(cgrib, intbmap, iofst, 1, 0, ngpts)
1160  iofst = iofst + ngpts
1161  do j = 1, ngpts
1162  bmap(j) = .true.
1163  if (intbmap(j).eq.0) bmap(j) = .false.
1164  enddo
1165  elseif (ibmap.eq.254) then ! Use previous bitmap
1166  return
1167  elseif (ibmap.eq.255) then ! No bitmap in message
1168  bmap(1:ngpts) = .true.
1169  else
1170  print *, 'unpack6: Predefined bitmap ', ibmap, &
1171  ' not recognized.'
1172  ierr = 4
1173  endif
1174 end subroutine unpack6
1175 
1191 subroutine getdim(csec3, lcsec3, width, height, iscan)
1192  implicit none
1193 
1194  character(len=1),intent(in) :: csec3(*)
1195  integer,intent(in) :: lcsec3
1196  integer,intent(out) :: width,height,iscan
1197 
1198  integer,pointer,dimension(:) :: igdstmpl,list_opt
1199  integer :: igds(5)
1200  integer iofst, igdtlen, num_opt, jerr
1201 
1202  interface
1203  subroutine gf_unpack3(cgrib, lcgrib, iofst, igds, igdstmpl, &
1204  mapgridlen, ideflist, idefnum, ierr)
1205  character(len = 1), intent(in) :: cgrib(lcgrib)
1206  integer, intent(in) :: lcgrib
1207  integer, intent(inout) :: iofst
1208  integer, pointer, dimension(:) :: igdstmpl, ideflist
1209  integer, intent(out) :: igds(5)
1210  integer, intent(out) :: ierr, idefnum
1211  end subroutine gf_unpack3
1212  end interface
1213 
1214  nullify(igdstmpl, list_opt)
1215 
1216  iofst = 0 ! set offset to beginning of section
1217  call gf_unpack3(csec3, lcsec3, iofst, igds, igdstmpl, &
1218  igdtlen, list_opt, num_opt, jerr)
1219  if (jerr.eq.0) then
1220  selectcase( igds(5) ) ! Template number
1221  case (0:3) ! Lat/Lon
1222  width = igdstmpl(8)
1223  height = igdstmpl(9)
1224  iscan = igdstmpl(19)
1225  case (10) ! Mercator
1226  width = igdstmpl(8)
1227  height = igdstmpl(9)
1228  iscan = igdstmpl(16)
1229  case (20) ! Polar Stereographic
1230  width = igdstmpl(8)
1231  height = igdstmpl(9)
1232  iscan = igdstmpl(18)
1233  case (30) ! Lambert Conformal
1234  width = igdstmpl(8)
1235  height = igdstmpl(9)
1236  iscan = igdstmpl(18)
1237  case (40:43) ! Gaussian
1238  width = igdstmpl(8)
1239  height = igdstmpl(9)
1240  iscan = igdstmpl(19)
1241  case (90) ! Space View/Orthographic
1242  width = igdstmpl(8)
1243  height = igdstmpl(9)
1244  iscan = igdstmpl(17)
1245  case (110) ! Equatorial Azimuthal
1246  width = igdstmpl(8)
1247  height = igdstmpl(9)
1248  iscan = igdstmpl(16)
1249  case default
1250  width = 0
1251  height = 0
1252  iscan = 0
1253  end select
1254  else
1255  width = 0
1256  height = 0
1257  endif
1258 
1259  if (associated(igdstmpl)) deallocate(igdstmpl)
1260  if (associated(list_opt)) deallocate(list_opt)
1261 
1262  return
1263 end subroutine getdim
1264 
1292 subroutine getlocal(cgrib, lcgrib, localnum, csec2, lcsec2, ierr)
1293  implicit none
1294 
1295  character(len = 1), intent(in) :: cgrib(lcgrib)
1296  integer, intent(in) :: lcgrib, localnum
1297  character(len = 1), intent(out) :: csec2(*)
1298  integer, intent(out) :: lcsec2, ierr
1299 
1300  character(len = 4), parameter :: grib = 'GRIB', c7777 = '7777'
1301  character(len = 4) :: ctemp
1302  integer :: listsec0(2)
1303  integer iofst, istart, numlocal
1304  integer :: lengrib, lensec, lensec0, j, ipos, isecnum
1305 
1306  ierr = 0
1307  numlocal = 0
1308 
1309  ! Check for valid request number.
1310  if (localnum .le. 0) then
1311  print *, 'getlocal: Request for local section must be positive.'
1312  ierr = 3
1313  return
1314  endif
1315 
1316  ! Check for beginning of GRIB message in the first 100 bytes
1317  istart = 0
1318  do j = 1, 100
1319  ctemp = cgrib(j)//cgrib(j+1)//cgrib(j+2)//cgrib(j+3)
1320  if (ctemp .eq. grib) then
1321  istart = j
1322  exit
1323  endif
1324  enddo
1325  if (istart .eq. 0) then
1326  print *, 'getlocal: Beginning characters GRIB not found.'
1327  ierr = 1
1328  return
1329  endif
1330 
1331  ! Unpack Section 0 - Indicator Section
1332  iofst = 8 * (istart + 5)
1333  call g2_gbytec(cgrib, listsec0(1), iofst, 8) ! Discipline
1334  iofst = iofst + 8
1335  call g2_gbytec(cgrib, listsec0(2), iofst, 8) ! GRIB edition number
1336  iofst = iofst + 8
1337  iofst = iofst + 32
1338  call g2_gbytec1(cgrib, lengrib, iofst, 32) ! Length of GRIB message
1339  iofst = iofst + 32
1340  lensec0 = 16
1341  ipos = istart + lensec0
1342 
1343  ! Currently handles only GRIB Edition 2.
1344  if (listsec0(2) .ne. 2) then
1345  print *, 'getlocal: can only decode GRIB edition 2.'
1346  ierr = 2
1347  return
1348  endif
1349 
1350  ! Loop through the remaining sections keeping track of the length of
1351  ! each. Also check to see that if the current occurrence of Section
1352  ! 2 is the same as the one requested.
1353  do
1354  ! Check to see if we are at end of GRIB message
1355  ctemp = cgrib(ipos) // cgrib(ipos + 1) // cgrib(ipos + 2) // cgrib(ipos + 3)
1356  if (ctemp .eq. c7777) then
1357  ipos = ipos + 4
1358 
1359  ! If end of GRIB message not where expected, issue error
1360  if (ipos .ne. (istart + lengrib)) then
1361  print *, 'getlocal: "7777" found, but not where expected.'
1362  ierr = 4
1363  return
1364  endif
1365  exit
1366  endif
1367 
1368  ! Get length of Section and Section number
1369  iofst = (ipos - 1) * 8
1370  call g2_gbytec1(cgrib, lensec, iofst, 32) ! Get Length of Section
1371  iofst = iofst + 32
1372  call g2_gbytec1(cgrib, isecnum, iofst, 8) ! Get Section number
1373  iofst = iofst + 8
1374 
1375  ! If found the requested occurrence of Section 2,
1376  ! return the section contents.
1377  if (isecnum .eq. 2) then
1378  numlocal = numlocal + 1
1379  if (numlocal.eq.localnum) then
1380  lcsec2 = lensec - 5
1381  csec2(1:lcsec2) = cgrib(ipos + 5:ipos + lensec - 1)
1382  return
1383  endif
1384  endif
1385 
1386  ! Check to see if we read pass the end of the GRIB
1387  ! message and missed the terminator string '7777'.
1388  ipos = ipos + lensec ! Update beginning of section pointer
1389  if (ipos .gt. (istart + lengrib)) then
1390  print *, 'getlocal: "7777" not found at end of GRIB message.'
1391  ierr = 5
1392  return
1393  endif
1394  enddo
1395 
1396  ! If exited from above loop, the end of the GRIB message was reached
1397  ! before the requested occurrence of section 2 was found.
1398  print *, 'getlocal: GRIB message contained ', numlocal, ' local sections.'
1399  print *, 'getlocal: The request was for the ', localnum, ' occurrence.'
1400  ierr = 6
1401 
1402 end subroutine getlocal
1403 
1418 subroutine getpoly(csec3, lcsec3, jj, kk, mm)
1419  implicit none
1420 
1421  character(len = 1), intent(in) :: csec3(*)
1422  integer, intent(in) :: lcsec3
1423  integer, intent(out) :: jj, kk, mm
1424 
1425  integer, pointer, dimension(:) :: igdstmpl, list_opt
1426  integer :: igds(5)
1427  integer iofst, igdtlen, num_opt, jerr
1428 
1429  interface
1430  subroutine gf_unpack3(cgrib, lcgrib, iofst, igds, igdstmpl, &
1431  mapgridlen, ideflist, idefnum, ierr)
1432  character(len = 1), intent(in) :: cgrib(lcgrib)
1433  integer, intent(in) :: lcgrib
1434  integer, intent(inout) :: iofst
1435  integer, pointer, dimension(:) :: igdstmpl, ideflist
1436  integer, intent(out) :: igds(5)
1437  integer, intent(out) :: ierr, idefnum
1438  end subroutine gf_unpack3
1439  end interface
1440 
1441  nullify(igdstmpl, list_opt)
1442 
1443  iofst = 0 ! set offset to beginning of section
1444  call gf_unpack3(csec3, lcsec3, iofst, igds, igdstmpl, &
1445  igdtlen, list_opt, num_opt, jerr)
1446  if (jerr.eq.0) then
1447  selectcase( igds(5) ) ! Template number
1448  case (50:53) ! Spherical harmonic coefficients
1449  jj = igdstmpl(1)
1450  kk = igdstmpl(2)
1451  mm = igdstmpl(3)
1452  case default
1453  jj = 0
1454  kk = 0
1455  mm = 0
1456  end select
1457  else
1458  jj = 0
1459  kk = 0
1460  mm = 0
1461  endif
1462 
1463  if (associated(igdstmpl)) deallocate(igdstmpl)
1464  if (associated(list_opt)) deallocate(list_opt)
1465 
1466 end subroutine getpoly
1467 
1528 subroutine gettemplates(cgrib, lcgrib, ifldnum, igds, igdstmpl, &
1529  igdslen, ideflist, idefnum, ipdsnum, ipdstmpl, ipdslen, coordlist, numcoord, ierr)
1530  implicit none
1531 
1532  character(len = 1), intent(in) :: cgrib(lcgrib)
1533  integer, intent(in) :: lcgrib, ifldnum
1534  integer, intent(out) :: igds(*), igdstmpl(*), ideflist(*)
1535  integer, intent(out) :: ipdsnum, ipdstmpl(*)
1536  integer, intent(out) :: idefnum, numcoord
1537  integer, intent(out) :: ierr
1538  real, intent(out) :: coordlist(*)
1539 
1540  character(len = 4), parameter :: grib = 'GRIB', c7777 = '7777'
1541  character(len = 4) :: ctemp
1542  integer:: listsec0(2)
1543  integer iofst, istart
1544  logical have3, have4
1545  integer :: igdslen, ipdslen, ipos, isecnum, j, jerr, lengrib, lensec, lensec0, numfld
1546 
1547  interface
1548  subroutine g2_gbytec1(in, siout, iskip, nbits)
1549  character*1, intent(in) :: in(*)
1550  integer, intent(inout) :: siout
1551  integer, intent(in) :: iskip, nbits
1552  end subroutine g2_gbytec1
1553  end interface
1554 
1555  have3 = .false.
1556  have4 = .false.
1557  ierr = 0
1558  numfld = 0
1559 
1560  ! Check for valid request number.
1561  if (ifldnum .le. 0) then
1562  print *, 'gettemplates: Request for field number must be positive.'
1563  ierr = 3
1564  return
1565  endif
1566 
1567  ! Check for beginning of GRIB message in the first 100 bytes.
1568  istart = 0
1569  do j = 1, 100
1570  ctemp = cgrib(j) // cgrib(j + 1) // cgrib(j + 2) // cgrib(j + 3)
1571  if (ctemp .eq. grib ) then
1572  istart = j
1573  exit
1574  endif
1575  enddo
1576  if (istart .eq. 0) then
1577  print *, 'gettemplates: Beginning characters GRIB not found.'
1578  ierr = 1
1579  return
1580  endif
1581 
1582  ! Unpack Section 0 - Indicator Section.
1583  iofst = 8 * (istart + 5)
1584  call g2_gbytec1(cgrib, listsec0(1), iofst, 8) ! Discipline
1585  iofst = iofst + 8
1586  call g2_gbytec1(cgrib, listsec0(2), iofst, 8) ! GRIB edition number
1587  iofst = iofst + 8
1588  iofst = iofst + 32
1589  call g2_gbytec1(cgrib, lengrib, iofst, 32) ! Length of GRIB message
1590  iofst = iofst + 32
1591  lensec0 = 16
1592  ipos = istart + lensec0
1593 
1594  ! Currently handles only GRIB Edition 2.
1595  if (listsec0(2) .ne. 2) then
1596  print *, 'gettemplates: can only decode GRIB edition 2.'
1597  ierr = 2
1598  return
1599  endif
1600 
1601  ! Loop through the remaining sections keeping track of the length of
1602  ! each. Also keep the latest Grid Definition Section info. Unpack
1603  ! the requested field number.
1604  do
1605  ! Check to see if we are at end of GRIB message.
1606  ctemp = cgrib(ipos) // cgrib(ipos + 1) // cgrib(ipos + 2) // cgrib(ipos + 3)
1607  if (ctemp .eq. c7777 ) then
1608  ipos = ipos + 4
1609  ! If end of GRIB message not where expected, issue error
1610  if (ipos .ne. (istart + lengrib)) then
1611  print *, 'gettemplates: "7777" found, but not where expected.'
1612  ierr = 4
1613  return
1614  endif
1615  exit
1616  endif
1617  ! Get length of Section and Section number.
1618  iofst = (ipos - 1) * 8
1619  call g2_gbytec1(cgrib, lensec, iofst, 32) ! Get Length of Section
1620  iofst = iofst + 32
1621  call g2_gbytec1(cgrib, isecnum, iofst, 8) ! Get Section number
1622  iofst = iofst + 8
1623  !print *, ' lensec = ', lensec, ' secnum = ', isecnum
1624 
1625  ! If found Section 3, unpack the GDS info using the appropriate
1626  ! template. Save in case this is the latest grid before the
1627  ! requested field.
1628  if (isecnum .eq. 3) then
1629  iofst = iofst - 40 ! reset offset to beginning of section
1630  call unpack3(cgrib, lcgrib, iofst, igds, igdstmpl, igdslen, ideflist, idefnum, jerr)
1631  if (jerr .eq. 0) then
1632  have3 = .true.
1633  else
1634  ierr = 10
1635  return
1636  endif
1637  endif
1638 
1639  ! If found Section 4, check to see if this field is the one
1640  ! requested.
1641  if (isecnum .eq. 4) then
1642  numfld = numfld + 1
1643  if (numfld .eq. ifldnum) then
1644  iofst = iofst - 40 ! reset offset to beginning of section
1645  call unpack4(cgrib, lcgrib, iofst, ipdsnum, ipdstmpl, ipdslen, coordlist, numcoord, jerr)
1646  if (jerr .eq. 0) then
1647  have4 = .true.
1648  else
1649  ierr = 11
1650  return
1651  endif
1652  endif
1653  endif
1654 
1655  ! Check to see if we read pass the end of the GRIB message and
1656  ! missed the terminator string '7777'.
1657  ipos = ipos + lensec ! Update beginning of section pointer
1658  if (ipos .gt. (istart + lengrib)) then
1659  print *, 'gettemplates: "7777" not found at end of GRIB message.'
1660  ierr = 7
1661  return
1662  endif
1663 
1664  if (have3 .and. have4) return
1665  enddo
1666 
1667  ! If exited from above loop, the end of the GRIB message was reached
1668  ! before the requested field was found.
1669  print *, 'gettemplates: GRIB message contained ', numfld, ' different fields.'
1670  print *, 'gettemplates: The request was for the ', ifldnum, ' field.'
1671  ierr = 6
1672 
1673 end subroutine gettemplates
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: compack.F90:528
subroutine g2_gbytesc(in, iout, iskip, nbits, nskip, n)
Extract arbitrary size big-endian integer values (up to 32 bits each) from a packed bit string.
Definition: g2bytes.F90:120
subroutine rdieee(rieee, a, num)
Copy array of 32-bit IEEE floating point values to local floating point representation.
Definition: g2bytes.F90:637
subroutine g2_gbytec(in, iout, iskip, nbits)
Extract one arbitrary size big-endian value (up to 32 bits) from a packed bit string into one element...
Definition: g2bytes.F90:21
subroutine g2_gbytec81(in, siout, iskip, nbits)
Extract one arbitrary size big-endian integer value (up to 64 bits) from a packed bit string into a s...
Definition: g2bytes.F90:209
subroutine g2_gbytescr(in, rout, iskip, nbits, nskip, n)
Extract big-endian floating-point values (32 bits each) from a packed bit string.
Definition: g2bytes.F90:86
subroutine g2_gbytec1(in, siout, iskip, nbits)
Extract one arbitrary size big-endian integer value (up to 32 bits) from a packed bit string into a s...
Definition: g2bytes.F90:52
subroutine getfield(cgrib, lcgrib, ifldnum, igds, igdstmpl, igdslen, ideflist, idefnum, ipdsnum, ipdstmpl, ipdslen, coordlist, numcoord, ndpts, idrsnum, idrstmpl, idrslen, ibmap, bmap, fld, ierr)
Return the Grid Definition, Product Definition, Bit-map (if applicable), and the unpacked data for a ...
Definition: g2get.F90:547
subroutine gb_info(cgrib, lcgrib, listsec0, listsec1, numfields, numlocal, maxlocal, ierr)
Find the number of gridded fields and Local Use Sections in a GRIB2 message.
Definition: g2get.F90:54
subroutine gettemplates(cgrib, lcgrib, ifldnum, igds, igdstmpl, igdslen, ideflist, idefnum, ipdsnum, ipdstmpl, ipdslen, coordlist, numcoord, ierr)
Return the Grid Definition and Product Definition for a data field.
Definition: g2get.F90:1530
subroutine unpack6(cgrib, lcgrib, iofst, ngpts, ibmap, bmap, ierr)
This subroutine unpacks Section 6 (Bit-Map Section) starting at octet 6 of that Section.
Definition: g2get.F90:1138
subroutine 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: g2get.F90:938
subroutine getlocal(cgrib, lcgrib, localnum, csec2, lcsec2, ierr)
Return the contents of Section 2 (Local Use) from a GRIB2 message.
Definition: g2get.F90:1293
subroutine 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: g2get.F90:813
subroutine getdim(csec3, lcsec3, width, height, iscan)
Return the dimensions and scanning mode of a grid definition packed in the Grid Definition Section.
Definition: g2get.F90:1192
subroutine getpoly(csec3, lcsec3, jj, kk, mm)
Return the J, K, and M pentagonal resolution parameters specified in a GRIB2 Grid Definition Section ...
Definition: g2get.F90:1419
subroutine 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: g2get.F90:1045
subroutine gribinfo(cgrib, lcgrib, listsec0, listsec1, numlocal, numfields, maxvals, ierr)
Find the number of Local Use Sections and gridded fields in a GRIB2 message, and the maximum sizes of...
Definition: g2get.F90:284
subroutine jpcunpack(cpack, len, idrstmpl, ndpts, fld)
Unpack a data field from a JPEG2000 code stream as defined in Data Representation Template 5....
Definition: g2jpc.F90:177
subroutine pngunpack(cpack, len, idrstmpl, ndpts, fld)
Unpack a data field with PNG, defined in [Data Representation Template 5.40](https://www....
Definition: g2png.F90:168
subroutine simunpack(cpack, len, idrstmpl, ndpts, fld)
Unpack a data field that was packed using a simple packing, [Data Representation Template 5....
Definition: g2sim.F90:169
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: g2unpack.F90:184
Handles Data Representation Templates used in Section 5.
subroutine getdrstemplate(number, nummap, map, needext, iret)
Return DRS template information for a specified Data Representation Template.
subroutine extdrstemplate(number, list, nummap, map)
Generate the remaining octet map for a given Data Representation Template, if required.
Logging for the g2 library.
Definition: g2logging.F90:10
character *120 g2_log_msg
Fill this with the logging message.
Definition: g2logging.F90:12
subroutine g2_log(level)
Print a debug message for the g2 library.
Definition: g2logging.F90:22
This Fortran module contains info on all the available GRIB2 Grid Definition Templates used in [Secti...
subroutine getgridtemplate(number, nummap, map, needext, iret)
Get the grid template information for a specified Grid Definition Template.
subroutine extgridtemplate(number, list, nummap, map)
Generate the remaining octet map for a given Grid Definition Template, if required.
Information on all GRIB2 Product Definition Templates used in Section 4 - the Product Definition Sect...
subroutine extpdstemplate(number, list, nummap, map)
This subroutine generates the remaining octet map for a given Product Definition Template,...
subroutine getpdstemplate(number, nummap, map, needext, iret)
This subroutine returns PDS template information for a specified Product Definition Template.