NCEPLIBS-g2  3.5.0
g2index.F90
Go to the documentation of this file.
1 
4 
20 subroutine g2_create_index(lugb, lugi, idxver, filename, iret)
21  implicit none
22 
23  integer, intent(in) :: lugb, lugi, idxver
24  character*(*) :: filename
25  integer, intent(out) :: iret
26 
27  integer (kind = 8) :: msk1, msk2
28  parameter(msk1 = 32000_8, msk2 = 4000_8)
29  character(len=1), pointer, dimension(:) :: cbuf
30  integer :: numtot, nnum, nlen, mnum, kw
31  integer :: irgi, iw, nmess
32 
33  interface
34  subroutine getg2i2r(lugb, msk1, msk2, mnum, idxver, cbuf, &
35  nlen, nnum, nmess, iret)
36  integer, intent(in) :: lugb
37  integer (kind = 8), intent(in) :: msk1, msk2
38  integer, intent(in) :: mnum, idxver
39  character(len = 1), pointer, dimension(:) :: cbuf
40  integer, intent(out) :: nlen, nnum, nmess, iret
41  end subroutine getg2i2r
42  end interface
43 
44  ! Assume success.
45  iret = 0
46  numtot = 0
47  nlen = 0
48 
49  ! Generate index records for all messages in file, or until memory
50  ! runs out.
51  mnum = 0
52  call getg2i2r(lugb, msk1, msk2, mnum, idxver, cbuf, &
53  nlen, nnum, nmess, irgi)
54  if (irgi .gt. 1 .or. nnum .eq. 0 .or. nlen .eq. 0) then
55  iret = 92
56  return
57  endif
58  numtot = numtot + nnum
59  mnum = mnum + nmess
60 
61  ! Write headers.
62  call g2_write_index_headers(lugi, nlen, numtot, idxver, filename)
63  iw = 162
64 
65  ! Write the index data we have so far.
66  call bawrite(lugi, iw, nlen, kw, cbuf)
67  iw = iw + nlen
68 
69  ! Extend index file if index buffer length too large to hold in memory.
70  if (irgi .eq. 1) then
71  do while (irgi .eq. 1 .and. nnum .gt. 0)
72  if (associated(cbuf)) then
73  deallocate(cbuf)
74  nullify(cbuf)
75  endif
76  call getg2i2r(11, msk1, msk2, mnum, idxver, cbuf, &
77  nlen, nnum, nmess, irgi)
78  if (irgi .le. 1 .and. nnum .gt. 0) then
79  numtot = numtot + nnum
80  mnum = mnum + nmess
81  call bawrite(lugi, iw, nlen, kw, cbuf)
82  iw = iw + nlen
83  endif
84  enddo
85  ! Go back and overwrite headers with new info.
86  call g2_write_index_headers(lugi, iw, numtot, idxver, filename)
87  endif
88  deallocate(cbuf)
89 
90 end subroutine g2_create_index
91 
102 subroutine g2_write_index_headers(lugi, nlen, nnum, idxver, filename)
103  implicit none
104 
105  integer, intent(in) :: lugi, nlen, nnum, idxver
106  character, intent(in) :: filename*(*)
107 
108  character cd8*8, ct10*10, hostname*15
109 #ifdef __GFORTRAN__
110  integer istat
111 #else
112  character hostnam*15
113  integer hostnm
114 #endif
115  character chead(2)*81
116  integer :: kw
117 
118  ! fill first 81-byte header
119  call date_and_time(cd8, ct10)
120  chead(1) = '!GFHDR!'
121  chead(1)(9:10) = ' 1'
122  chead(1)(12:14) = ' 1'
123  write(chead(1)(16:20),'(i5)') 162
124  chead(1)(22:31) = cd8(1:4) // '-' // cd8(5:6) // '-' // cd8(7:8)
125  chead(1)(33:40) = ct10(1:2) // ':' // ct10(3:4) // ':' // ct10(5:6)
126  chead(1)(42:47) = 'GB2IX1'
127  chead(1)(49:54) = ' '
128 #ifdef __GFORTRAN__
129  istat = hostnm(hostname)
130  if (istat .eq. 0) then
131  chead(1)(56:70) = '0000'
132  else
133  chead(1)(56:70) = '0001'
134  endif
135 #else
136  chead(1)(56:70) = hostnam(hostname)
137 #endif
138  chead(1)(72:80) = 'grb2index'
139  chead(1)(81:81) = char(10)
140 
141  ! fill second 81-byte header
142  if (idxver .eq. 1) then
143  chead(2) = 'IX1FORM:'
144  else
145  chead(2) = 'IX2FORM:'
146  endif
147  write(chead(2)(9:38),'(3i10)') 162, nlen, nnum
148  chead(2)(41:80) = filename
149  chead(2)(81:81) = char(10)
150 
151  ! write headers at beginning of index file
152  call bawrite(lugi, 0, 162, kw, chead)
153 
154  return
155 end subroutine g2_write_index_headers
156 
197 subroutine getidx(lugb, lugi, cindex, nlen, nnum, iret)
198  implicit none
199 
200  integer, intent(in) :: lugb, lugi
201  character(len = 1), pointer, dimension(:) :: cindex
202  integer, intent(out) :: nlen, nnum, iret
203  integer :: idxver
204 
205  interface
206  subroutine getidx2(lugb, lugi, idxver, cindex, nlen, nnum, iret)
207  integer, intent(in) :: lugb, lugi
208  integer, intent(inout) :: idxver
209  character(len = 1), pointer, dimension(:) :: cindex
210  integer, intent(out) :: nlen, nnum, iret
211  end subroutine getidx2
212  end interface
213 
214  ! When getidx() is called, always use index version 1. Call
215  ! getidx2() for a chance to set the index version.
216  idxver = 1
217  call getidx2(lugb, lugi, idxver, cindex, nlen, nnum, iret)
218 
219  ! If index version 2 is being used, return error.
220  if (iret .eq. 0 .and. idxver .eq. 2) iret = 97
221 
222 end subroutine getidx
223 
265 subroutine getidx2(lugb, lugi, idxver, cindex, nlen, nnum, iret)
266  use g2logging
267  implicit none
268 
269  integer, intent(in) :: lugb, lugi
270  integer, intent(inout) :: idxver
271  character(len = 1), pointer, dimension(:) :: cindex
272  integer, intent(out) :: nlen, nnum, iret
273 
274  integer, parameter :: maxidx = 10000
275  integer (kind = 8), parameter :: msk1 = 32000_8, msk2 = 4000_8
276  integer :: lux
277  integer :: irgi, mskp, nmess, i
278 
279  type gindex
280  integer :: nlen
281  integer :: nnum
282  integer :: idxver
283  character(len = 1), pointer, dimension(:) :: cbuf
284  end type gindex
285 
286  type(gindex), save :: idxlist(10000)
287 
288  data lux/0/
289 
290  ! declare interfaces (required for cbuf pointer)
291  interface
292  subroutine getg2i2(lugi, cbuf, idxver, nlen, nnum, iret)
293  integer, intent(in) :: lugi
294  character(len=1), pointer, dimension(:) :: cbuf
295  integer, intent(out) :: idxver, nlen, nnum, iret
296  end subroutine getg2i2
297  subroutine getg2i2r(lugb, msk1, msk2, mnum, idxver, cbuf, &
298  nlen, nnum, nmess, iret)
299  integer, intent(in) :: lugb
300  integer (kind = 8), intent(in) :: msk1, msk2
301  integer, intent(in) :: mnum, idxver
302  character(len = 1), pointer, dimension(:) :: cbuf
303  integer, intent(out) :: nlen, nnum, nmess, iret
304  end subroutine getg2i2r
305  end interface
306 
307 #ifdef LOGGING
308  ! Log results for debugging.
309  write(g2_log_msg, '(a, i2, a, i2, a, i1)') 'getidx2: lugb ', lugb, ' lugi ', lugi, &
310  ' idxver ', idxver
311  call g2_log(1)
312 #endif
313 
314  ! Free all associated memory and exit.
315  if (lugb .eq. 0) then
316  !print *, 'getidx: Freeing all memory'
317  do i = 1, 10000
318  if (associated(idxlist(i)%cbuf)) then
319  !print *, 'deallocating ', loc(idxlist(i)%cbuf)
320  deallocate(idxlist(i)%cbuf)
321  nullify(idxlist(i)%cbuf)
322  endif
323  end do
324  iret = 0
325  return
326  endif
327 
328  ! Determine whether index buffer needs to be initialized.
329  lux = 0
330  iret = 0
331  if (lugb .le. 0 .or. lugb .gt. 9999) then
332  print *, ' file unit number out of range'
333  print *, ' use unit numbers in range: 0 - 9999 '
334  iret = 90
335  return
336  endif
337 
338  ! Force regeneration of index from GRIB2 file.
339  if (lugi .eq. lugb) then
340  if (associated(idxlist(lugb)%cbuf)) &
341  deallocate(idxlist(lugb)%cbuf)
342  !print *, 'Force regeneration'
343  nullify(idxlist(lugb)%cbuf)
344  idxlist(lugb)%nlen = 0
345  idxlist(lugb)%nnum = 0
346  lux = 0
347  endif
348 
349  ! Force re-read of index from indexfile.
350  if (lugi .lt. 0) then
351  ! associated with unit abs(lugi)
352  if (associated(idxlist(lugb)%cbuf)) &
353  deallocate(idxlist(lugb)%cbuf)
354  !print *, 'Force re-read'
355  nullify(idxlist(lugb)%cbuf)
356  idxlist(lugb)%nlen = 0
357  idxlist(lugb)%nnum = 0
358  lux = abs(lugi)
359  endif
360 
361  ! Check if index already exists in memory.
362  if (associated(idxlist(lugb)%cbuf)) then
363  !print *, 'Index exists in memory!'
364  cindex => idxlist(lugb)%cbuf
365  nlen = idxlist(lugb)%nlen
366  nnum = idxlist(lugb)%nnum
367  idxver = idxlist(lugb)%idxver
368  return
369  endif
370 
371  ! Either read index from index file, or generate it from the GRIB2
372  ! file. This is an index for all messages in the file, each message
373  ! gets an index record, all stuffed into idxlist(lugbb)%cbuf.
374  irgi = 0
375  if (lux .gt. 0) then
376  call getg2i2(lux, idxlist(lugb)%cbuf, idxver, nlen, nnum, irgi)
377  elseif (lux .le. 0) then
378  mskp = 0
379  call getg2i2r(lugb, msk1, msk2, mskp, idxver, idxlist(lugb)%cbuf, &
380  nlen, nnum, nmess, irgi)
381  endif
382 
383  ! Handle errors.
384  if (irgi .ne. 0) then
385  nlen = 0
386  nnum = 0
387  print *, ' error reading index file '
388  iret = 96
389  return
390  endif
391 
392  ! Fill these values.
393  cindex => idxlist(lugb)%cbuf
394  idxlist(lugb)%nlen = nlen
395  idxlist(lugb)%nnum = nnum
396  idxlist(lugb)%idxver = idxver
397 
398 end subroutine getidx2
399 
429 subroutine getg2i(lugi, cbuf, nlen, nnum, iret)
430  implicit none
431 
432  integer, intent(in) :: lugi
433  character(len=1), pointer, dimension(:) :: cbuf
434  integer, intent(out) :: nlen, nnum, iret
435  integer :: idxver
436 
437  interface
438  subroutine getg2i2(lugi, cbuf, idxver, nlen, nnum, iret)
439  integer, intent(in) :: lugi
440  character(len=1), pointer, dimension(:) :: cbuf
441  integer, intent(out) :: idxver, nlen, nnum, iret
442  end subroutine getg2i2
443  end interface
444 
445  ! Call the version of this subroutine that handles version 1 and
446  ! version 2. If getg2i() is called on a version 2 index, return
447  ! error.
448  call getg2i2(lugi, cbuf, idxver, nlen, nnum, iret)
449  if (idxver .eq. 2) iret = 5
450 
451 end subroutine getg2i
452 
511 subroutine getg2i2(lugi, cbuf, idxver, nlen, nnum, iret)
512  use g2logging
513  implicit none
514 
515  integer, intent(in) :: lugi
516  character(len=1), pointer, dimension(:) :: cbuf
517  integer, intent(out) :: idxver, nlen, nnum, iret
518 
519  character chead*162
520  integer :: ios, istat, lbuf, lhead, nskp
521 
522 #ifdef LOGGING
523  write(g2_log_msg, *) 'getg2i2: lugi ', lugi
524  call g2_log(1)
525 #endif
526 
527  nullify(cbuf)
528  nlen = 0
529  nnum = 0
530  iret = 4
531  call baread(lugi, 0, 162, lhead, chead)
532 #ifdef LOGGING
533  write(g2_log_msg, *) 'lhead', lhead
534  call g2_log(2)
535 #endif
536  if (lhead .eq. 162 .and. chead(42:47) .eq. 'GB2IX1') then
537  read(chead(82:162), '(2x, i1, 5x, 3i10, 2x, a40)', iostat = ios) idxver, nskp, nlen, nnum
538 #ifdef LOGGING
539  write(g2_log_msg, *) 'ios', ios, 'idxver', idxver, 'nskp', nskp, 'nlen', nlen, 'nnum', nnum
540  call g2_log(2)
541 #endif
542  if (ios .eq. 0) then
543  allocate(cbuf(nlen), stat = istat) ! Allocate space for cbuf.
544  if (istat .ne. 0) then
545  iret = 2
546  return
547  endif
548  iret = 0
549  call baread(lugi, nskp, nlen, lbuf, cbuf)
550  if (lbuf .ne. nlen) iret = 3
551  endif
552  endif
553 end subroutine getg2i2
554 
587 subroutine getg2ir(lugb, msk1, msk2, mnum, cbuf, nlen, nnum, nmess, iret)
588  use re_alloc ! needed for subroutine realloc
589  implicit none
590 
591  integer, intent(in) :: lugb
592  integer, intent(in) :: msk1, msk2
593  integer, intent(in) :: mnum
594  character(len = 1), pointer, dimension(:) :: cbuf
595  integer, intent(out) :: nlen, nnum, nmess, iret
596 
597  integer (kind = 8) :: msk1_8, msk2_8
598 
599  interface
600  subroutine getg2i2r(lugb, msk1, msk2, mnum, idxver, cbuf, &
601  nlen, nnum, nmess, iret)
602  integer, intent(in) :: lugb
603  integer (kind = 8), intent(in) :: msk1, msk2
604  integer, intent(in) :: mnum, idxver
605  character(len = 1), pointer, dimension(:) :: cbuf
606  integer, intent(out) :: nlen, nnum, nmess, iret
607  end subroutine getg2i2r
608  end interface
609 
610  msk1_8 = msk1
611  msk2_8 = msk2
612  call getg2i2r(lugb, msk1_8, msk2_8, mnum, 1, cbuf, nlen, nnum, nmess, iret)
613 end subroutine getg2ir
614 
648 subroutine getg2i2r(lugb, msk1, msk2, mnum, idxver, cbuf, nlen, nnum, nmess, iret)
649  use g2logging
650  use re_alloc ! needed for subroutine realloc
651  implicit none
652 
653  integer, intent(in) :: lugb
654  integer (kind = 8), intent(in) :: msk1, msk2
655  integer, intent(in) :: mnum, idxver
656  character(len = 1), pointer, dimension(:) :: cbuf
657  integer, intent(out) :: nlen, nnum, nmess, iret
658 
659  character(len = 1), pointer, dimension(:) :: cbuftmp
660  integer :: nbytes, newsize, next, numfld, m, mbuf
661  integer (kind = 8) :: iseek, lskip, lgrib
662  integer :: istat, init, iret1, lgrib4
663  parameter(init = 50000, next = 10000)
664 
665  interface ! required for cbuf pointer
666  subroutine ix2gb2(lugb, lskip8, idxver, lgrib8, cbuf, numfld, mlen, iret)
667  integer, intent(in) :: lugb
668  integer (kind = 8), intent(in) :: lskip8
669  integer, intent(in) :: idxver
670  integer (kind = 8), intent(in) :: lgrib8
671  character(len = 1), pointer, intent(inout), dimension(:) :: cbuf
672  integer, intent(out) :: numfld, mlen, iret
673  end subroutine ix2gb2
674  end interface
675 
676 #ifdef LOGGING
677  ! Log results for debugging.
678  write(g2_log_msg, *) 'getg2i2r: lugb ', lugb, ' msk1 ', msk1, ' msk2 ', msk2, 'idxver', idxver
679  call g2_log(1)
680 #endif
681 
682  ! Initialize.
683  iret = 0
684  nullify(cbuf)
685  mbuf = init
686  allocate(cbuf(mbuf), stat = istat) ! allocate initial space for cbuf.
687  if (istat .ne. 0) then
688  iret = 2
689  return
690  endif
691 
692  ! Search for first grib message.
693  iseek = 0_8
694  call skgb8(lugb, iseek, msk1, lskip, lgrib)
695  do m = 1, mnum
696  if (lgrib .gt. 0) then
697  iseek = lskip + lgrib
698  call skgb8(lugb, iseek, msk2, lskip, lgrib)
699  endif
700  enddo
701 
702  ! Get index records for every grib message found.
703  nlen = 0
704  nnum = 0
705  nmess = mnum
706  do while (iret .eq. 0 .and. lgrib .gt. 0)
707  lgrib4 = int(lgrib, kind(4))
708  call ix2gb2(lugb, lskip, idxver, lgrib, cbuftmp, numfld, nbytes, iret1)
709  if (iret1 .ne. 0) print *, ' SAGT ', numfld, nbytes, iret1
710  if (nbytes + nlen .gt. mbuf) then ! Allocate more space, if necessary.
711  newsize = max(mbuf + next, mbuf + nbytes)
712  call realloc(cbuf, nlen, newsize, istat)
713  if (istat .ne. 0) then
714  iret = 1
715  return
716  endif
717  mbuf = newsize
718  endif
719 
720  ! If index records were returned in cbuftmp from ixgb2,
721  ! copy cbuftmp into cbuf, then deallocate cbuftmp when done.
722  if (associated(cbuftmp)) then
723  cbuf(nlen + 1 : nlen + nbytes) = cbuftmp(1 : nbytes)
724  deallocate(cbuftmp, stat = istat)
725  if (istat .ne. 0) then
726  print *, ' deallocating cbuftmp ... ', istat
727  iret = 3
728  return
729  endif
730  nullify(cbuftmp)
731  nnum = nnum + numfld
732  nlen = nlen + nbytes
733  nmess = nmess + 1
734  endif
735 
736  ! Look for next grib message.
737  iseek = lskip + lgrib
738  call skgb8(lugb, iseek, msk2, lskip, lgrib)
739  enddo
740 end subroutine getg2i2r
741 
814 subroutine getgb2s(cbuf, nlen, nnum, j, jdisc, jids, jpdtn, jpdt, jgdtn, &
815  jgdt, k, gfld, lpos, iret)
816  use grib_mod
817  implicit none
818 
819  character(len = 1), intent(in) :: cbuf(nlen)
820  integer, intent(in) :: nlen, nnum, j, jdisc
821  integer, dimension(:) :: jids(*)
822  integer, intent(in) :: jpdtn
823  integer, dimension(:) :: jpdt(*)
824  integer, intent(in) :: jgdtn
825  integer, dimension(:) :: jgdt(*)
826  integer, intent(out) :: k
827  type(gribfield), intent(out) :: gfld
828  integer, intent(out) :: lpos, iret
829 
830  interface
831  subroutine getgb2s2(cbuf, idxver, nlen, nnum, j, jdisc, jids, jpdtn, jpdt, jgdtn, &
832  jgdt, k, gfld, lpos, iret)
833  import gribfield
834  character(len = 1), intent(in) :: cbuf(nlen)
835  integer, intent(in) :: idxver, nlen, nnum, j, jdisc
836  integer, dimension(:) :: jids(*)
837  integer, intent(in) :: jpdtn
838  integer, dimension(:) :: jpdt(*)
839  integer, intent(in) :: jgdtn
840  integer, dimension(:) :: jgdt(*)
841  integer, intent(out) :: k
842  type(gribfield), intent(out) :: gfld
843  integer, intent(out) :: lpos, iret
844  end subroutine getgb2s2
845  end interface
846 
847  ! When getgb2s() is called, always use index version 1. Call
848  ! getgb2s2() to handle version 1 or 2.
849  call getgb2s2(cbuf, 1, nlen, nnum, j, jdisc, jids, jpdtn, jpdt, jgdtn, &
850  jgdt, k, gfld, lpos, iret)
851 
852 end subroutine getgb2s
853 
927 subroutine getgb2s2(cbuf, idxver, nlen, nnum, j, jdisc, jids, jpdtn, jpdt, jgdtn, &
928  jgdt, k, gfld, lpos, iret)
929  use grib_mod
930  use g2logging
931  implicit none
932 
933  character(len = 1), intent(in) :: cbuf(nlen)
934  integer, intent(in) :: idxver, nlen, nnum, j, jdisc
935  integer, dimension(:) :: jids(*)
936  integer, intent(in) :: jpdtn
937  integer, dimension(:) :: jpdt(*)
938  integer, intent(in) :: jgdtn
939  integer, dimension(:) :: jgdt(*)
940  integer, intent(out) :: k
941  type(gribfield), intent(out) :: gfld
942  integer, intent(out) :: lpos, iret
943 
944  integer :: kgds(5)
945  logical :: match1, match3, match4
946  integer :: i, icnd, inlen, iof, ipos, jpos, lsec1, lsec3, lsec4, lsec5, numgdt, numpdt, inc
947 
948  interface
949  subroutine g2_gbytec1(in, siout, iskip, nbits)
950  character*1, intent(in) :: in(*)
951  integer, intent(inout) :: siout
952  integer, intent(in) :: iskip, nbits
953  end subroutine g2_gbytec1
954  subroutine gf_unpack1(cgrib, lcgrib, iofst, ids, idslen, ierr)
955  character(len = 1), intent(in) :: cgrib(lcgrib)
956  integer, intent(in) :: lcgrib
957  integer, intent(inout) :: iofst
958  integer, pointer, dimension(:) :: ids
959  integer, intent(out) :: ierr, idslen
960  end subroutine gf_unpack1
961  subroutine gf_unpack3(cgrib, lcgrib, iofst, igds, igdstmpl, &
962  mapgridlen, ideflist, idefnum, ierr)
963  character(len = 1), intent(in) :: cgrib(lcgrib)
964  integer, intent(in) :: lcgrib
965  integer, intent(inout) :: iofst
966  integer, pointer, dimension(:) :: igdstmpl, ideflist
967  integer, intent(out) :: igds(5)
968  integer, intent(out) :: ierr, idefnum
969  end subroutine gf_unpack3
970  subroutine gf_unpack4(cgrib, lcgrib, iofst, ipdsnum, ipdstmpl, &
971  mappdslen, coordlist, numcoord, ierr)
972  character(len = 1), intent(in) :: cgrib(lcgrib)
973  integer, intent(in) :: lcgrib
974  integer, intent(inout) :: iofst
975  real, pointer, dimension(:) :: coordlist
976  integer, pointer, dimension(:) :: ipdstmpl
977  integer, intent(out) :: ipdsnum
978  integer, intent(out) :: ierr, numcoord
979  end subroutine gf_unpack4
980  subroutine gf_unpack5(cgrib, lcgrib, iofst, ndpts, idrsnum, &
981  idrstmpl, mapdrslen, ierr)
982  character(len = 1), intent(in) :: cgrib(lcgrib)
983  integer, intent(in) :: lcgrib
984  integer, intent(inout) :: iofst
985  integer, intent(out) :: ndpts, idrsnum
986  integer, pointer, dimension(:) :: idrstmpl
987  integer, intent(out) :: ierr
988  end subroutine gf_unpack5
989  end interface
990 
991 #ifdef LOGGING
992  ! Log results for debugging.
993  write(g2_log_msg, *) 'getgb2s2: idxver ', idxver, ' nlen ', nlen, &
994  ' nnum ', nnum, ' j ', j, ' jdisc ', jdisc
995  call g2_log(1)
996 #endif
997 
998  ! Initialize.
999  k = 0
1000  lpos = 0
1001  iret = 1
1002  ipos = 0
1003  nullify(gfld%idsect, gfld%local)
1004  nullify(gfld%list_opt, gfld%igdtmpl, gfld%ipdtmpl)
1005  nullify(gfld%coord_list, gfld%idrtmpl, gfld%bmap, gfld%fld)
1006  if (idxver .eq. 1) then
1007  inc = 0
1008  else
1009  ! Add the extra 24 bytes in the version 2 index record, starting
1010  ! at byte 9.
1011  inc = 28
1012  endif
1013 
1014  ! Search for request.
1015  do while (iret .ne. 0 .and. k .lt. nnum)
1016  k = k + 1
1017  ! Get length of current index record.
1018  call g2_gbytec1(cbuf, inlen, ipos * 8, 4 * 8)
1019  if (k .le. j) then ! skip this index
1020  ipos = ipos + inlen
1021  cycle
1022  endif
1023 
1024  ! Check if grib2 discipline is a match.
1025  call g2_gbytec1(cbuf, gfld%discipline, (ipos + inc + 41) * 8, 1 * 8)
1026  if (jdisc .ne. -1 .and. jdisc .ne. gfld%discipline) then
1027  ipos = ipos + inlen
1028  cycle
1029  endif
1030 
1031  ! Check if identification section is a match.
1032  match1 = .false.
1033  ! Get length of ids.
1034  call g2_gbytec1(cbuf, lsec1, (ipos + inc + 44) * 8, 4 * 8)
1035  iof = 0
1036  call gf_unpack1(cbuf(ipos + inc + 45), lsec1, iof, gfld%idsect, gfld%idsectlen, icnd)
1037  if (icnd .eq. 0) then
1038  match1 = .true.
1039  do i = 1, gfld%idsectlen
1040  if (jids(i) .ne. -9999 .and. jids(i) .ne. gfld%idsect(i)) then
1041  match1 = .false.
1042  exit
1043  endif
1044  enddo
1045  endif
1046  if (.not. match1) then
1047  deallocate(gfld%idsect)
1048  ipos = ipos + inlen
1049  cycle
1050  endif
1051 
1052  ! Check if grid definition template is a match.
1053  jpos = ipos + 44 + inc + lsec1
1054  match3 = .false.
1055  call g2_gbytec1(cbuf, lsec3, jpos * 8, 4 * 8) ! get length of gds
1056  if (jgdtn .eq. -1) then
1057  match3 = .true.
1058  else
1059  call g2_gbytec1(cbuf, numgdt, (jpos + 12) * 8, 2 * 8) ! get gdt template no.
1060  if (jgdtn .eq. numgdt) then
1061  iof = 0
1062  call gf_unpack3(cbuf(jpos + 1), lsec3, iof, kgds, gfld%igdtmpl, &
1063  gfld%igdtlen, gfld%list_opt, gfld%num_opt, icnd)
1064  if (icnd .eq. 0) then
1065  match3 = .true.
1066  do i = 1, gfld%igdtlen
1067  if (jgdt(i) .ne. -9999 .and. jgdt(i).ne.gfld%igdtmpl(i)) then
1068  match3 = .false.
1069  exit
1070  endif
1071  enddo
1072  endif
1073  endif
1074  endif
1075  if (.not. match3) then
1076  if (associated(gfld%idsect)) deallocate(gfld%idsect)
1077  if (associated(gfld%igdtmpl)) deallocate(gfld%igdtmpl)
1078  if (associated(gfld%list_opt)) deallocate(gfld%list_opt)
1079  ipos = ipos + inlen
1080  cycle
1081  else
1082  gfld%griddef = kgds(1)
1083  gfld%ngrdpts = kgds(2)
1084  gfld%numoct_opt = kgds(3)
1085  gfld%interp_opt = kgds(4)
1086  gfld%igdtnum = kgds(5)
1087  endif
1088 
1089  ! Check if product definition template is a match.
1090  jpos = jpos + lsec3
1091  match4 = .false.
1092 
1093  ! Get length of pds.
1094  call g2_gbytec1(cbuf, lsec4, jpos * 8, 4 * 8)
1095  if (jpdtn .eq. -1) then
1096  match4 = .true.
1097  else
1098  ! Get pdt template no.
1099  call g2_gbytec1(cbuf, numpdt, (jpos + 7) * 8, 2 * 8)
1100  if (jpdtn .eq. numpdt) then
1101  iof = 0
1102  call gf_unpack4(cbuf(jpos + 1), lsec4, iof, gfld%ipdtnum, &
1103  gfld%ipdtmpl, gfld%ipdtlen, gfld%coord_list, gfld%num_coord, icnd)
1104  if (icnd .eq. 0) then
1105  match4 = .true.
1106  do i = 1, gfld%ipdtlen
1107  if (jpdt(i) .ne. -9999 .and. jpdt(i) .ne. gfld%ipdtmpl(i)) then
1108  match4 = .false.
1109  exit
1110  endif
1111  enddo
1112  endif
1113  endif
1114  endif
1115  if (.not. match4) then
1116  if (associated(gfld%idsect)) deallocate(gfld%idsect)
1117  if (associated(gfld%ipdtmpl)) deallocate(gfld%ipdtmpl)
1118  if (associated(gfld%coord_list)) deallocate(gfld%coord_list)
1119  endif
1120 
1121  ! If request is found set values for derived type gfld and return.
1122  if (match1 .and. match3 .and. match4) then
1123  lpos = ipos + 1
1124  call g2_gbytec1(cbuf, gfld%version, (ipos + inc + 40) * 8, 1 * 8)
1125  call g2_gbytec1(cbuf, gfld%ifldnum, (ipos + inc + 42) * 8, 2 * 8)
1126  gfld%unpacked = .false.
1127  jpos = ipos + 44 + inc + lsec1
1128  if (jgdtn .eq. -1) then ! unpack gds, if not done before
1129  iof = 0
1130  call gf_unpack3(cbuf(jpos + 1), lsec3, iof, kgds, gfld%igdtmpl, &
1131  gfld%igdtlen, gfld%list_opt, gfld%num_opt, icnd)
1132  gfld%griddef = kgds(1)
1133  gfld%ngrdpts = kgds(2)
1134  gfld%numoct_opt = kgds(3)
1135  gfld%interp_opt = kgds(4)
1136  gfld%igdtnum = kgds(5)
1137  endif
1138  jpos = jpos + lsec3
1139  if (jpdtn .eq. -1) then ! unpack pds, if not done before
1140  iof = 0
1141  call gf_unpack4(cbuf(jpos + 1), lsec4, iof, gfld%ipdtnum, &
1142  gfld%ipdtmpl, gfld%ipdtlen, gfld%coord_list, gfld%num_coord, icnd)
1143  endif
1144  jpos = jpos + lsec4
1145  call g2_gbytec1(cbuf, lsec5, jpos * 8, 4 * 8) ! get length of drs
1146  iof = 0
1147  call gf_unpack5(cbuf(jpos + 1), lsec5, iof, gfld%ndpts, &
1148  gfld%idrtnum, gfld%idrtmpl, gfld%idrtlen, icnd)
1149  jpos = jpos + lsec5
1150  call g2_gbytec1(cbuf, gfld%ibmap, (jpos + 5) * 8, 1 * 8) ! get ibmap
1151  iret = 0
1152  else ! pdt did not match
1153  ipos = ipos + inlen
1154  endif
1155  enddo
1156 end subroutine getgb2s2
1157 
1191 subroutine ixgb2(lugb, lskip, lgrib, cbuf, numfld, mlen, iret)
1192  use re_alloc ! needed for subroutine realloc
1193  implicit none
1194 
1195  integer :: lugb, lskip, lgrib
1196  character(len = 1), pointer, dimension(:) :: cbuf
1197  integer :: numfld, mlen, iret
1198  integer (kind = 8) :: lskip8, lgrib8
1199 
1200  interface
1201  subroutine ix2gb2(lugb, lskip8, idxver, lgrib8, cbuf, numfld, mlen, iret)
1202  integer, intent(in) :: lugb
1203  integer (kind = 8), intent(in) :: lskip8
1204  integer, intent(in) :: idxver
1205  integer (kind = 8), intent(in) :: lgrib8
1206  character(len = 1), pointer, intent(inout), dimension(:) :: cbuf
1207  integer, intent(out) :: numfld, mlen, iret
1208  end subroutine ix2gb2
1209  end interface
1210 
1211  ! Always use index version 1 from this subroutine.
1212  lskip8 = lskip
1213  lgrib8 = lgrib
1214  call ix2gb2(lugb, lskip8, 1, lgrib8, cbuf, numfld, mlen, iret)
1215  lgrib = int(lgrib8, 4)
1216 end subroutine ixgb2
1217 
1255 subroutine ix2gb2(lugb, lskip8, idxver, lgrib8, cbuf, numfld, mlen, iret)
1256  use re_alloc ! needed for subroutine realloc
1257  use g2logging
1258  implicit none
1259 
1260  ! Subroutine parameters.
1261  integer, intent(in) :: lugb
1262  integer (kind = 8), intent(in) :: lskip8
1263  integer, intent(in) :: idxver
1264  integer (kind = 8), intent(in) :: lgrib8
1265  character(len = 1), pointer, intent(inout), dimension(:) :: cbuf
1266  integer, intent(out) :: numfld, mlen, iret
1267 
1268  character cver, cdisc
1269  character(len = 4) :: ctemp
1270  integer (kind = 8) :: loclus8, locgds8, locbms8
1271  integer locgds, loclus, locbms
1272  integer :: indbmp, numsec, newsize, g2_mova2i, mbuf, lindex
1273  integer :: lskip
1274  integer :: ilndrs, ilnpds, istat
1275  integer (kind = 8) :: ibread8, lbread8, ibskip8, lengds8
1276  integer (kind = 8) :: ilnpds8, ilndrs8
1277  integer :: lensec, lensec1
1278  integer :: mypos, inc
1279 
1280  ! Parameters.
1281  ! Size of the internal char buffers used in this subroutine.
1282  integer :: LINMAX
1283  parameter(linmax = 5000)
1284  ! Initial size of buffer to hold index record in cbuf array.
1285  integer :: INIT
1286  parameter(init = 50000)
1287  ! If more space is needed in cbuf, it will get this much more.
1288  integer :: NEXT
1289  parameter(next = 10000)
1290  ! Number of bytes of the BMS section put into index record.
1291  integer :: MXBMS
1292  parameter(mxbms = 6)
1293  integer :: IXDS1, IXDS2
1294  parameter(ixds1 = 28, ixds2 = 52)
1295  ! Bytes to skip in (version 1) index record to get to section 0.
1296  integer :: IXIDS
1297  parameter(ixids = 44)
1298  integer :: IXSDR
1299  parameter(ixsdr = 20)
1300  ! Bytes to skip in (version 1 and 2) index record to get to bms.
1301  integer :: IXBMS1, IXBMS2
1302  parameter(ixbms1 = 24, ixbms2 = 44)
1303  ! Sizes of integers in bits.
1304  integer :: INT1_BITS, INT2_BITS, INT4_BITS, INT8_BITS
1305  parameter(int1_bits = 8, int2_bits = 16, int4_bits = 32, int8_bits = 64)
1306  ! Location of bytes to drs field in index version 1 and 2.
1307  integer :: IXDRS1, IXDRS2
1308  parameter(ixdrs1 = 20, ixdrs2 = 36)
1309 
1310  ! Buffers.
1311  character cbread(LINMAX), cindex(LINMAX)
1312  character cids(LINMAX), cgds(LINMAX)
1313 
1314  interface
1315  subroutine g2_gbytec1(in, siout, iskip, nbits)
1316  character*1, intent(in) :: in(*)
1317  integer, intent(inout) :: siout
1318  integer, intent(in) :: iskip, nbits
1319  end subroutine g2_gbytec1
1320  subroutine g2_sbytec81(out, sin, iskip, nbits)
1321  character*1, intent(inout) :: out(*)
1322  integer (kind = 8), intent(in) :: sin
1323  integer, intent(in) :: iskip, nbits
1324  end subroutine g2_sbytec81
1325  subroutine g2_sbytec1(out, in, iskip, nbits)
1326  character*1, intent(inout) :: out(*)
1327  integer, intent(in) :: in
1328  integer, intent(in) :: iskip, nbits
1329  end subroutine g2_sbytec1
1330  end interface
1331 
1332 #ifdef LOGGING
1333  ! Log results for debugging.
1334  write(g2_log_msg, *) 'ix2gb2: lugb ', lugb, ' lskip8 ', lskip8, ' idxver ', idxver
1335  call g2_log(1)
1336 #endif
1337 
1338  ! Are we using index version 1 (legacy), or version 2 (introduced to
1339  ! handle files > 2 GB).
1340  if (idxver .eq. 1) then
1341  inc = 0
1342  else
1343  ! Add the extra bytes in the version 2 index record, starting at
1344  ! byte 9. This is because some values early in the index record
1345  ! changed from 4-byte ints to 8-byte ints. This is the total
1346  ! extra bytes that were added to the beginning of the index
1347  ! record in version 2.
1348  inc = 28
1349  endif
1350 
1351  ! Initialize values and allocate buffer (at the user-provided cbuf
1352  ! pointer) where the index data will be written. When subroutine is
1353  ! complete, cbuf will hold either version 1 or 2 index data.
1354  loclus = 0
1355  loclus8 = 0
1356  iret = 0
1357  mlen = 0
1358  numfld = 0
1359  nullify(cbuf)
1360  mbuf = init
1361  allocate(cbuf(mbuf), stat = istat) ! allocate initial space for cbuf
1362  if (istat .ne. 0) then
1363  iret = 1
1364  return
1365  endif
1366 
1367  ! Read up to 5000 bytes from the file into buffer cbread. lskip8
1368  ! must be set to the beginning of a GRIB2 message in the file.
1369  ibread8 = min(lgrib8, linmax)
1370  call bareadl(lugb, lskip8, ibread8, lbread8, cbread)
1371  if (lbread8 .ne. ibread8) then
1372  iret = 2
1373  return
1374  endif
1375 
1376  ! Check GRIB version from section 0, must be 2.
1377  if (cbread(8) .ne. char(2)) then
1378  iret = 3
1379  return
1380  endif
1381 
1382  ! Remember the GRIB version and discipline.
1383  cver = cbread(8)
1384  cdisc = cbread(7)
1385 
1386  ! Read the length of section 1 from the file data buffer.
1387  call g2_gbytec1(cbread, lensec1, 16 * int1_bits, int4_bits)
1388  lensec1 = min(lensec1, int(ibread8, kind(lensec1)))
1389 
1390  ! Copy section 1 values into cids array.
1391  cids(1:lensec1) = cbread(17:16 + lensec1)
1392  ! do i = 1, lensec1
1393  ! print *, i, ichar(cids(i))
1394  ! end do
1395 
1396  ! Skip past section 1 in the data buffer.
1397  ibskip8 = lskip8 + 16_8 + int(lensec1, kind(8))
1398 
1399  ! Loop through remaining sections creating an index for each
1400  ! field. This overwrites the cbread data buffer.
1401  ibread8 = max(5, mxbms)
1402  do
1403  ! Read 6 bytes from file into cbread buffer. (Why 6? Should this
1404  ! be 5?)
1405  call bareadl(lugb, ibskip8, ibread8, lbread8, cbread)
1406 
1407  ! Check if the first 4 bytes are '7777', indicating end of
1408  ! message. If we found end of message, we are done.
1409  ctemp = cbread(1)//cbread(2)//cbread(3)//cbread(4)
1410  if (ctemp .eq. '7777') return ! end of message found
1411 
1412  ! If we did not find end of message, check that we read 6 bytes.
1413  if (lbread8 .ne. ibread8) then
1414  iret = 2
1415  return
1416  endif
1417 
1418  ! Read the 4-byte section length, and then the 1-byte section
1419  ! number.
1420  call g2_gbytec1(cbread, lensec, 0, int4_bits)
1421  call g2_gbytec1(cbread, numsec, int4_bits, int1_bits)
1422 
1423  ! Based on the section number, generate index data for each
1424  ! section.
1425  if (numsec .eq. 2) then
1426  ! Save the location of the local use section in the message.
1427  loclus8 = ibskip8 - lskip8
1428  loclus = int(ibskip8 - lskip8, kind(4))
1429  elseif (numsec .eq. 3) then
1430  ! For the GDS section, read the whole section into the cgds
1431  ! buffer.
1432  lengds8 = lensec
1433  cgds = char(0)
1434  call bareadl(lugb, ibskip8, lengds8, lbread8, cgds)
1435  if (lbread8 .ne. lengds8) then
1436  iret = 2
1437  return
1438  endif
1439  ! Remember the GDS location in the message.
1440  locgds = int(ibskip8 - lskip8, kind(4))
1441  locgds8 = ibskip8 - lskip8
1442  elseif (numsec .eq. 4) then
1443  ! Having found the PDS, we write the beginning of the index
1444  ! record into the cindex buffer.
1445  cindex = char(0)
1446 
1447  ! The first 4 bytes are the length of the index record. We
1448  ! don't know that yet, so skip it for now,
1449  mypos = int4_bits
1450 
1451  ! Write the beginning of the index record. It contains bytes
1452  ! to skip in the file to reach the message, and offsets to
1453  ! each section within the message. Index version 1 uses 4-byte
1454  ! ints for these values, index version 2 uses 8-byte ints.
1455  if (idxver .eq. 1) then
1456  inc = 0
1457  lskip = int(lskip8, kind(4))
1458  call g2_sbytec1(cindex, lskip, mypos, int4_bits) ! bytes to skip
1459  !print '(i3, a7, i4)', mypos/8, ' lskip ', lskip, mypos
1460  mypos = mypos + int4_bits
1461  call g2_sbytec1(cindex, loclus, mypos, int4_bits) ! location of local use
1462  !print '(i3, a8, i4)', mypos/8, ' loclus ', loclus
1463  mypos = mypos + int4_bits
1464  call g2_sbytec1(cindex, locgds, mypos, int4_bits) ! location of gds
1465  !print '(i3, a8, i4)', mypos/8, ' locgds ', locgds
1466  mypos = mypos + int4_bits
1467  call g2_sbytec1(cindex, int(ibskip8 - lskip8, kind(4)), mypos, int4_bits) ! location of pds
1468 #ifdef LOGGING
1469  write(g2_log_msg, *) ' writing pds location to index: mypos/8 ', mypos/8, &
1470  ' loc ', int(ibskip8 - lskip8, kind(4))
1471  call g2_log(4)
1472 #endif
1473  !print '(i3, a8, i4)', mypos/8, ' locpds ', int(ibskip8 - lskip8, kind(4))
1474  mypos = mypos + int4_bits * 4 ! skip ahead in cbuf
1475  else
1476  inc = 28
1477  call g2_sbytec81(cindex, lskip8, mypos, int8_bits) ! bytes to skip
1478  !print '(i3, a7, i4)', mypos/8, ' lskip ', lskip
1479  mypos = mypos + int8_bits
1480  call g2_sbytec81(cindex, loclus8, mypos, int8_bits) ! location of local use
1481  !print '(i3, a8, i4)', mypos/8, ' loclus ', loclus
1482  mypos = mypos + int8_bits
1483  call g2_sbytec81(cindex, locgds8, mypos, int8_bits) ! location of gds
1484  !print '(i3, a8, i4)', mypos/8, ' locgds ', locgds
1485  mypos = mypos + int8_bits
1486  call g2_sbytec81(cindex, ibskip8 - lskip8, mypos, int8_bits) ! location of pds
1487  !print '(i3, a8, i4)', mypos/8, ' locpds ', int(ibskip8 - lskip8, kind(4))
1488  mypos = mypos + int8_bits * 4 ! skip ahead in cbuf
1489  endif
1490 
1491 #ifdef LOGGING
1492  write(g2_log_msg, *) ' writing total len to index: mypos/8 ', mypos/8, lgrib8
1493  call g2_log(4)
1494 #endif
1495  ! These ints are the same size in index version 1 and 2. The
1496  ! mypos variable contains the proper offset, which is
1497  call g2_sbytec81(cindex, lgrib8, mypos, int8_bits) ! length of grib2
1498  !print '(i3, a8, i4)', mypos/8, ' lgrib8 ', lgrib8
1499  mypos = mypos + int8_bits
1500  cindex((mypos / 8) + 1) = cver
1501  !print '(i3, a6, z1)', mypos/8, ' cver ', cver
1502  mypos = mypos + int1_bits
1503  cindex((mypos / 8) + 1) = cdisc
1504  !print '(i3, a7, z2)', mypos/8, ' cdisc ', cdisc
1505  mypos = mypos + int1_bits
1506  call g2_sbytec1(cindex, numfld + 1, mypos, int2_bits) ! field num
1507  !print '(i3, a8, i4)', mypos/8, ' numfld ', numfld + 1
1508  mypos = mypos + int2_bits
1509 
1510  ! Copy the section 1 values into the cindex buffer.
1511  cindex(ixids + 1 + inc:ixids + lensec1 + inc) = cids(1:lensec1)
1512  lindex = ixids + lensec1 + inc
1513  ! print *, 'section 1:', IXIDS + inc, IXIDS + lensec1 + inc
1514  ! do i=1, lensec1
1515  ! print *, i, ichar(cids(i))
1516  ! end do
1517 
1518  ! Copy the GDS values into the cindex buffer.
1519  cindex(lindex + 1:lindex + lengds8) = cgds(1:lengds8)
1520  !print *, 'gds:', lindex, lindex + lengds8
1521  lindex = lindex + int(lengds8, kind(lindex))
1522  ! print *, 'gds:', lindex, lengds8
1523  ! do i=1, lengds8
1524  ! print *, i, ichar(cgds(i))
1525  ! end do
1526 
1527  ! Now read the PDS values from the file directly into cindex.
1528  ilnpds = lensec
1529  ilnpds8 = ilnpds
1530  call bareadl(lugb, ibskip8, ilnpds8, lbread8, cindex(lindex + 1))
1531  if (lbread8 .ne. ilnpds8) then
1532  iret = 2
1533  return
1534  endif
1535  !print *, 'pds:', lindex, lindex + ilnpds
1536  lindex = lindex + ilnpds
1537  mypos = mypos + ilnpds
1538 #ifdef LOGGING
1539  write(g2_log_msg, *) ' after writing pds location to index: mypos/8 ', mypos/8
1540  call g2_log(4)
1541 #endif
1542  elseif (numsec .eq. 5) then
1543  ! Write the byte offset to the DRS section into the cindex buffer.
1544  !mypos = (IXSDR + inc) * INT1_BITS
1545 #ifdef LOGGING
1546  write(g2_log_msg, *) ' before writing drs to index: ibskip8 - lskip8 ', ibskip8 - lskip8, ixdrs2
1547  call g2_log(4)
1548 #endif
1549  ! Write the bytes to skip to the drs section into the index record.
1550  if (idxver .eq. 1) then
1551  call g2_sbytec1(cindex, int(ibskip8 - lskip8, kind(4)), ixdrs1 * int1_bits, int4_bits)
1552  else
1553  call g2_sbytec81(cindex, ibskip8 - lskip8, ixdrs2 * int1_bits, int8_bits) ! location of drs
1554  endif
1555  !print '(i3, a8, i5)', mypos/8, ' locdrs ', int(ibskip8 - lskip8, kind(4))
1556 
1557  ! Read the DRS section directly into the cindex buffer.
1558  ilndrs = lensec
1559  ilndrs8 = ilndrs
1560  call bareadl(lugb, ibskip8, ilndrs8, lbread8, cindex(lindex + 1))
1561  if (lbread8 .ne. ilndrs8) then
1562  iret = 2
1563  return
1564  endif
1565  !print *, 'drs:', lindex, lindex + ilndrs
1566  lindex = lindex + ilndrs
1567  elseif (numsec .eq. 6) then
1568  ! Write the location of the BMS section in the message into
1569  ! the cindex buffer.
1570  indbmp = g2_mova2i(cbread(6))
1571 #ifdef LOGGING
1572  write(g2_log_msg, *) ' section 6: indbmp', indbmp
1573  call g2_log(4)
1574 #endif
1575 
1576  if (indbmp .lt. 254) then
1577  if (idxver .eq. 1) then
1578  locbms = int(ibskip8 - lskip8, kind(4))
1579  call g2_sbytec1(cindex, locbms, ixbms1 * int1_bits, int4_bits) ! loc. of bms
1580  else
1581  locbms8 = ibskip8 - lskip8
1582  call g2_sbytec81(cindex, locbms8, ixbms2 * int1_bits, int8_bits) ! loc. of bms
1583  endif
1584 #ifdef LOGGING
1585  write(g2_log_msg, *) ' section 6: locbms', locbms, 'locbms8', locbms8
1586  call g2_log(4)
1587 #endif
1588  elseif (indbmp .eq. 254) then
1589  if (idxver .eq. 1) then
1590  call g2_sbytec1(cindex, locbms, ixbms1 * int1_bits, int4_bits) ! loc. of bms
1591  else
1592  call g2_sbytec81(cindex, locbms8, ixbms2 * int1_bits, int8_bits) ! loc. of bms
1593  endif
1594  elseif (indbmp .eq. 255) then
1595  if (idxver .eq. 1) then
1596  call g2_sbytec1(cindex, int(ibskip8 - lskip8, kind(4)), ixbms1 * int1_bits, int4_bits) ! loc. of bms
1597  else
1598  call g2_sbytec81(cindex, ibskip8 - lskip8, ixbms2 * int1_bits, int8_bits) ! loc. of bms
1599  endif
1600  endif
1601 
1602  ! Copy 6 bytes of the BMS from data buffer to the cindex buffer.
1603  cindex(lindex + 1:lindex + mxbms) = cbread(1:mxbms)
1604  ! print *, 'bms:', lindex, lindex + MXBMS
1605  ! do i=1, MXBMS
1606  ! print *, i, ichar(cindex(lindex + i))
1607  ! end do
1608  lindex = lindex + mxbms
1609 
1610  ! The size of the index record is now known, so write it to
1611  ! the cindex buffer.
1612  call g2_sbytec1(cindex, lindex, 0, int4_bits) ! num bytes in index record
1613  !print '(i3, a8, i5)', 0, ' lindex ', lindex
1614  elseif (numsec .eq. 7) then ! found data section
1615 
1616 #ifdef LOGGING
1617  write(g2_log_msg, *) ' writing offset to the data in cindex: ibskip8 - lskip8 ', ibskip8 - lskip8, &
1618  'IXDS2', ixds2
1619  call g2_log(4)
1620 #endif
1621  ! Write the offset to the data section in the cindex buffer.
1622  if (idxver .eq. 1) then
1623  call g2_sbytec1(cindex, int(ibskip8 - lskip8, kind(4)), ixds1 * int1_bits, int4_bits)
1624  else
1625  call g2_sbytec81(cindex, ibskip8 - lskip8, ixds2 * int1_bits, int8_bits)
1626  endif
1627 
1628  ! Increment the field count.
1629  numfld = numfld + 1
1630 
1631  ! Allocate more space in cbuf if necessary. The index record
1632  ! will be copied there.
1633  if (lindex + mlen .gt. mbuf) then
1634  newsize = max(mbuf + next, mbuf + lindex)
1635  call realloc(cbuf, mlen, newsize, istat)
1636  if (istat .ne. 0) then
1637  numfld = numfld - 1
1638  iret = 4
1639  return
1640  endif
1641  mbuf = newsize
1642  endif
1643 
1644  ! Copy the index record into cbuf.
1645  cbuf(mlen + 1:mlen + lindex) = cindex(1:lindex)
1646  mlen = mlen + lindex
1647  else
1648  ! Unrecognized section.
1649  iret = 5
1650  return
1651  endif
1652 
1653  ! Skip past this section in the data buffer.
1654  ibskip8 = ibskip8 + lensec
1655  enddo ! next section
1656 end subroutine ix2gb2
1657 
1664 subroutine gf_finalize(iret)
1665  implicit none
1666 
1667  integer, intent(out) :: iret
1668  character(len = 1), pointer, dimension(:) :: cindex
1669  integer :: nlen, nnum
1670 
1671  ! Declare interfaces (required for cbuf pointer).
1672  interface
1673  subroutine getidx(lugb, lugi, cbuf, nlen, nnum, irgi)
1674  character(len = 1), pointer, dimension(:) :: cbuf
1675  integer, intent(in) :: lugb, lugi
1676  integer, intent(out) :: nlen, nnum, irgi
1677  end subroutine getidx
1678  end interface
1679 
1680  ! Call getidx with 0 for the first parameter, ensuring that the
1681  ! internal memory is freed.
1682  call getidx(0, 0, cindex, nlen, nnum, iret)
1683 
1684 end subroutine gf_finalize
1685 
subroutine g2_sbytec81(out, sin, iskip, nbits)
Put one arbitrary sized (up to 64 bits) scalar into a packed bit string, taking the low order bits fr...
Definition: g2bytes.F90:505
subroutine g2_sbytec1(out, in, iskip, nbits)
Put one arbitrary sized (up to 32 bits) values from an integer scalar into a packed bit string,...
Definition: g2bytes.F90:337
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 g2_create_index(lugb, lugi, idxver, filename, iret)
Create a version 1 or 2 index file for a GRIB2 file.
Definition: g2index.F90:21
subroutine ix2gb2(lugb, lskip8, idxver, lgrib8, cbuf, numfld, mlen, iret)
Generate a version 1 or 2 index record for each field in a GRIB2 message.
Definition: g2index.F90:1256
subroutine getgb2s(cbuf, nlen, nnum, j, jdisc, jids, jpdtn, jpdt, jgdtn, jgdt, k, gfld, lpos, iret)
Find information about a GRIB field from the index and fill a grib_mod::gribfield.
Definition: g2index.F90:816
subroutine getidx(lugb, lugi, cindex, nlen, nnum, iret)
Find, read or generate a version 1 GRIB2 index for a GRIB2 file (which must be < 2 GB).
Definition: g2index.F90:198
subroutine g2_write_index_headers(lugi, nlen, nnum, idxver, filename)
Write index headers.
Definition: g2index.F90:103
subroutine getg2i2r(lugb, msk1, msk2, mnum, idxver, cbuf, nlen, nnum, nmess, iret)
Generate a version 1 or 2 index record for each message in a GRIB2 file.
Definition: g2index.F90:649
subroutine getg2ir(lugb, msk1, msk2, mnum, cbuf, nlen, nnum, nmess, iret)
Generate a version 1 index record for each message in a GRIB2 file.
Definition: g2index.F90:588
subroutine ixgb2(lugb, lskip, lgrib, cbuf, numfld, mlen, iret)
Generate a version 1 index record for each field in a GRIB2 message.
Definition: g2index.F90:1192
subroutine getidx2(lugb, lugi, idxver, cindex, nlen, nnum, iret)
Find, read or generate a version 1 or 2 GRIB2 index for a GRIB2 file (which may be > 2 GB).
Definition: g2index.F90:266
subroutine gf_finalize(iret)
Free all memory associated with the library.
Definition: g2index.F90:1665
subroutine getg2i(lugi, cbuf, nlen, nnum, iret)
Read a version 1 index file and return its contents.
Definition: g2index.F90:430
subroutine getg2i2(lugi, cbuf, idxver, nlen, nnum, iret)
Read a version 1 or 2 index file and return its contents.
Definition: g2index.F90:512
subroutine getgb2s2(cbuf, idxver, nlen, nnum, j, jdisc, jids, jpdtn, jpdt, jgdtn, jgdt, k, gfld, lpos, iret)
Find information about a GRIB field from the index and fill a grib_mod::gribfield.
Definition: g2index.F90:929
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: g2unpack.F90:42
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: g2unpack.F90:467
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: g2unpack.F90:334
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
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 the declaration of derived type gribfield.
Definition: gribmod.F90:10
Reallocate memory, preserving contents.
Definition: realloc.F90:12
subroutine skgb8(lugb, iseek8, mseek8, lskip8, lgrib8)
Search a file for the next GRIB1 or GRIB2 message.
Definition: skgb.F90:53