196subroutine addfield(cgrib, lcgrib, ipdsnum, ipdstmpl, ipdstmplen, &
197 coordlist, numcoord, idrsnum, idrstmpl, &
198 idrstmplen, fld, ngrdpts, ibmap, bmap, ierr)
204 character(len=1),
intent(inout) :: cgrib(lcgrib)
205 integer,
intent(in) :: ipdsnum, ipdstmpl(*)
206 integer,
intent(in) :: idrsnum, numcoord, ipdstmplen, idrstmplen
207 integer,
intent(in) :: lcgrib, ngrdpts, ibmap
208 real,
intent(in) :: coordlist(numcoord)
209 real(kind = 4) :: coordlist_4(numcoord)
210 real,
target,
intent(in) :: fld(ngrdpts)
211 integer,
intent(out) :: ierr
212 integer,
intent(inout) :: idrstmpl(*)
213 logical*1,
intent(in) :: bmap(ngrdpts)
215 character(len=4),
parameter :: grib=
'GRIB', c7777=
'7777'
216 character(len=4):: ctemp
217 character(len=1),
allocatable :: cpack(:)
218 real,
pointer,
dimension(:) :: pfld
219 real(4) :: coordieee(numcoord), re00, tmpre00(1)
220 integer(4) :: ire00, allones
221 integer :: mappds(ipdstmplen), intbmap(ngrdpts), mapdrs(idrstmplen)
222 integer,
parameter :: zero=0, one=1, four=4, five=5, six=6, seven=7
223 integer,
parameter :: minsize=50000
224 integer iofst, ibeg, lencurr, len, mappdslen, mapdrslen, lpos3
225 integer width, height, ndpts
226 integer lensec3, lensec4, lensec5, lensec6, lensec7
227 logical issec3, needext, isprevbmap
228 integer :: nbits, newlen, nsize, lcpack, left
229 integer :: ibmprev, ilen, ioctet, iscan, isecnum, itemp
230 integer :: i, jj, kk, mm
231 integer :: iret, istat
232 real (kind = 4) :: tmpfld(1)
235 subroutine g2_gbytec(in, iout, iskip, nbits)
236 character*1,
intent(in) :: in(*)
237 integer,
intent(inout) :: iout(*)
238 integer,
intent(in) :: iskip, nbits
240 subroutine g2_gbytec1(in, siout, iskip, nbits)
241 character*1,
intent(in) :: in(*)
242 integer,
intent(inout) :: siout
243 integer,
intent(in) :: iskip, nbits
246 character*1,
intent(in) :: in(*)
247 integer (kind = 8),
intent(inout) :: siout
248 integer,
intent(in) :: iskip, nbits
249 integer (kind = 8) :: iout(1)
251 subroutine g2_sbytec(out, in, iskip, nbits)
252 character*1,
intent(inout) :: out(*)
253 integer,
intent(in) :: in(*)
254 integer,
intent(in) :: iskip, nbits
257 character*1,
intent(inout) :: out(*)
258 integer,
intent(in) :: in
259 integer,
intent(in) :: iskip, nbits
263 allones = int(z
'FFFFFFFF')
269 if (cgrib(i) /= grib(i:i))
then
273 if (.not. match)
then
274 print *,
'addfield: GRIB not found in given message.'
275 print *,
'addfield: Call to routine gribcreate required to initialize GRIB messge.'
284 ctemp = cgrib(lencurr-3) // cgrib(lencurr - 2) // cgrib(lencurr - 1) // cgrib(lencurr)
285 if (ctemp .eq. c7777)
then
286 print *,
'addfield: GRIB message already complete. Cannot add new section.'
306 if (isecnum .eq. 3)
then
313 if (isecnum .eq. 6)
then
316 if ((ibmprev .ge. 0) .and. (ibmprev .le. 253)) isprevbmap = .true.
321 if (len .eq. lencurr)
exit
325 if (len .gt. lencurr)
then
326 print *,
'addfield: Section byte counts don''t add to total.'
327 print *,
'addfield: Sum of section byte counts = ', len
328 print *,
'addfield: Total byte count in Section 0 = ', lencurr
335 if ((isecnum .ne. 3) .and. (isecnum .ne. 7))
then
336 print *,
'addfield: Sections 4-7 can only be added after Section 3 or 7.'
337 print *,
'addfield: Section ', isecnum,
' was the last found in', &
338 ' given GRIB message.'
343 elseif (.not. issec3)
then
344 print *,
'addfield: Sections 4-7 can only be added if Section', &
345 ' 3 was previously included.'
346 print *,
'addfield: Section 3 was not found in given GRIB message.'
347 print *,
'addfield: Call to routine addgrid required', &
348 ' to specify Grid definition.'
365 if (iret .ne. 0)
then
382 nbits = iabs(mappds(i)) * 8
383 if ((mappds(i) .ge. 0).or.(ipdstmpl(i) .ge. 0))
then
384 call g2_sbytec(cgrib, ipdstmpl(i), iofst, nbits)
387 call g2_sbytec1(cgrib, iabs(ipdstmpl(i)), iofst + 1, nbits - 1)
394 if (numcoord .ne. 0)
then
396 coordlist_4(i) = real(coordlist(i), 4)
398 call mkieee(coordlist_4, coordieee, numcoord)
399 call g2_sbytescr(cgrib, coordieee, iofst, 32, 0, numcoord)
400 iofst = iofst + (32 * numcoord)
405 lensec4 = (iofst-ibeg)/8
412 if (iret .ne. 0)
then
419 if (ibmap .eq. 0 .OR. ibmap .eq. 254)
then
420 allocate(pfld(max(2, ngrdpts)))
427 pfld(ndpts) = fld(jj);
430 if (ndpts == 0 .and. ngrdpts > 0)
then
439 if (nsize .lt. minsize) nsize = minsize
440 allocate(cpack(nsize), stat = istat)
441 if (idrsnum.eq.0)
then
442 call simpack(pfld, ndpts, idrstmpl, cpack, lcpack)
443 elseif (idrsnum.eq.2.or.idrsnum.eq.3)
then
444 call cmplxpack(pfld, ndpts, idrsnum, idrstmpl, cpack, lcpack)
445 elseif (idrsnum.eq.50)
then
446 call simpack(pfld(2), ndpts-1, idrstmpl, cpack, lcpack)
447 tmpfld(1) = real(pfld(1), 4)
448 call mkieee(tmpfld, tmpre00, 1)
450 ire00 = transfer(re00, ire00)
452 elseif (idrsnum.eq.51)
then
453 call getpoly(cgrib(lpos3), lensec3, jj, kk, mm)
454 if (jj.ne.0 .AND. kk.ne.0 .AND. mm.ne.0)
then
455 call specpack(pfld, ndpts, jj, kk, mm, idrstmpl, cpack, lcpack)
457 print *,
'addfield: Cannot pack DRT 5.51.'
462 elseif (idrsnum.eq.40 .OR. idrsnum.eq.40000)
then
463 if (ibmap.eq.255)
then
464 call getdim(cgrib(lpos3), lensec3, width, height, iscan)
465 if (width.eq.0 .OR. height.eq.0)
then
468 elseif (width.eq.allones .OR. height.eq.allones)
then
471 elseif (ibits(iscan, 5, 1) .eq. 1)
then
480 if (width<1 .or. height<1)
then
482 write(0, *)
'Warning: bitmask off everywhere.'
483 write(0, *)
' Pretend one point in jpcpack to avoid crash.'
489 call jpcpack(pfld, width, height, idrstmpl, cpack, lcpack)
491 elseif (idrsnum.eq.41 .OR. idrsnum.eq.40010)
then
492 if (ibmap.eq.255)
then
493 call getdim(cgrib(lpos3), lensec3, width, height, iscan)
494 if (width.eq.0 .OR. height.eq.0)
then
497 elseif (width.eq.allones .OR. height.eq.allones)
then
500 elseif (ibits(iscan, 5, 1) .eq. 1)
then
510 call pngpack(pfld, width, height, idrstmpl, cpack, lcpack)
513 elseif (idrsnum.eq.42)
then
514 if (ibmap.eq.255)
then
515 call getdim(cgrib(lpos3), lensec3, width, height, iscan)
516 if (width.eq.0 .OR. height.eq.0)
then
519 elseif (width.eq.allones .OR. height.eq.allones)
then
522 elseif (ibits(iscan, 5, 1) .eq. 1)
then
531 call aecpack(pfld, width, height, idrstmpl, cpack, lcpack);
534 print *,
'addfield: Data Representation Template 5.', idrsnum, &
535 ' not yet implemented.'
539 if (ibmap.eq.0 .OR. ibmap.eq.254)
then
542 if (lcpack .lt. 0)
then
543 if (
allocated(cpack))
deallocate(cpack)
562 nbits =iabs(mapdrs(i)) * 8
563 if ((mapdrs(i) .ge. 0) .or. (idrstmpl(i) .ge. 0))
then
564 call g2_sbytec(cgrib, idrstmpl(i), iofst, nbits)
567 call g2_sbytec1(cgrib, iabs(idrstmpl(i)), iofst+1, nbits-1)
569 iofst = iofst + nbits
574 lensec5 = (iofst - ibeg) / 8
587 call g2_sbytesc(cgrib, intbmap, iofst, 1, 0, ngrdpts)
593 if ((ibmap.eq.254).and.(.not.isprevbmap))
then
594 print *,
'addfield: Requested previously defined bitmap, ', &
595 ' but one does not exist in the current GRIB message.'
602 left = 8 - mod(iofst, 8)
603 if (left .ne. 8)
then
607 lensec6 = (iofst - ibeg) / 8
617 if (lcpack .ne. 0)
then
619 cgrib(ioctet + 1:ioctet + lcpack) = cpack(1:lcpack)
620 iofst = iofst + (8 * lcpack)
625 lensec7 = (iofst - ibeg) / 8
628 if (
allocated(cpack))
deallocate(cpack)
631 newlen = lencurr + lensec4 + lensec5 + lensec6 + lensec7
680subroutine addgrid(cgrib, lcgrib, igds, igdstmpl, igdstmplen, &
681 ideflist, idefnum, ierr)
685 character(len = 1),
intent(inout) :: cgrib(lcgrib)
686 integer,
intent(in) :: igds(*), igdstmpl(*), ideflist(idefnum)
687 integer,
intent(in) :: lcgrib, idefnum, igdstmplen
688 integer,
intent(out) :: ierr
690 character(len = 4),
parameter :: grib =
'GRIB', c7777 =
'7777'
691 character(len = 4):: ctemp
692 integer:: mapgrid(igdstmplen)
693 integer,
parameter :: ONE = 1, three = 3
694 integer lensec3, iofst, ibeg, lencurr, len, mapgridlen
696 integer :: i, ilen, iret, isecnum, nbits
699 subroutine g2_gbytec(in, iout, iskip, nbits)
700 character*1,
intent(in) :: in(*)
701 integer,
intent(inout) :: iout(*)
702 integer,
intent(in) :: iskip, nbits
704 subroutine g2_gbytec1(in, siout, iskip, nbits)
705 character*1,
intent(in) :: in(*)
706 integer,
intent(inout) :: siout
707 integer,
intent(in) :: iskip, nbits
710 character*1,
intent(in) :: in(*)
711 integer (kind = 8),
intent(inout) :: siout
712 integer,
intent(in) :: iskip, nbits
713 integer (kind = 8) :: iout(1)
715 subroutine g2_sbytec(out, in, iskip, nbits)
716 character*1,
intent(inout) :: out(*)
717 integer,
intent(in) :: in(*)
718 integer,
intent(in) :: iskip, nbits
721 character*1,
intent(inout) :: out(*)
722 integer,
intent(in) :: in
723 integer,
intent(in) :: iskip, nbits
730 print *,
'addgrid lcgrib ', lcgrib,
' igdstmplen ', igdstmplen,
' idefnum ', idefnum
735 if (cgrib(i) /= grib(i:i))
then
736 print *,
'addgrid: GRIB not found in given message.'
737 print *,
'addgrid: Call to routine gribcreate required', &
738 ' to initialize GRIB messge.'
73910
format(
'"', 4a1,
'" /= "GRIB"')
750 ctemp = cgrib(lencurr - 3) // cgrib(lencurr - 2) // cgrib(lencurr &
751 - 1) // cgrib(lencurr)
752 if (ctemp .eq. c7777)
then
753 print *,
'addgrid: GRIB message already complete. Cannot', &
771 if (len .eq. lencurr)
exit
775 if (len .gt. lencurr)
then
776 print *,
'addgrid: Section byte counts don''t add to total.'
777 print *,
'addgrid: Sum of section byte counts = ', len
778 print *,
'addgrid: Total byte count in Section 0 = ', lencurr
785 if ((isecnum .ne. 1) .and. (isecnum .ne. 2) .and. &
786 (isecnum .ne. 7))
then
787 print *,
'addgrid: Section 3 can only be added after Section', &
789 print *,
'addgrid: Section ', isecnum, &
790 ' was the last found in given GRIB message.'
802 call g2_sbytec(cgrib, igds(2), iofst, 32)
811 if (igds(1) .eq. 0)
then
812 call g2_sbytec(cgrib, igds(5), iofst, 16)
819 if (igds(1) .eq. 0)
then
822 if (iret .ne. 0)
then
842 nbits = iabs(mapgrid(i)) * 8
843 if ((mapgrid(i) .ge. 0) .or. (igdstmpl(i) .ge. 0))
then
844 call g2_sbytec(cgrib, igdstmpl(i), iofst, nbits)
847 call g2_sbytec1(cgrib, iabs(igdstmpl(i)), iofst + 1, nbits &
850 iofst = iofst + nbits
855 if (igds(3) .ne. 0)
then
857 call g2_sbytesc(cgrib, ideflist, iofst, nbits, 0, idefnum)
858 iofst = iofst + (nbits * idefnum)
863 lensec3 = (iofst - ibeg) / 8
867 call g2_sbytec1(cgrib, lencurr + lensec3, 96, 32)