NCEPLIBS-g2 4.0.0
Loading...
Searching...
No Matches
g2create.F90
Go to the documentation of this file.
1
4
53subroutine gribcreate(cgrib, lcgrib, listsec0, listsec1, ierr)
54 implicit none
55
56 character(len = 1), intent(inout) :: cgrib(lcgrib)
57 integer, intent(in) :: listsec0(*), listsec1(*)
58 integer, intent(in) :: lcgrib
59 integer, intent(out) :: ierr
60
61 integer :: i, lensec1, nbits
62 character(len = 4), parameter :: grib = 'GRIB'
63 integer, parameter :: ZERO = 0, one = 1
64 integer, parameter :: mapsec1len = 13
65 integer, parameter :: mapsec1(mapsec1len) = (/ 2, 2, 1, 1, 1, 2, 1, 1, 1, 1, 1, 1, 1 /)
66 integer lensec0, iofst, ibeg
67
68 interface
69 subroutine g2_sbytec(out, in, iskip, nbits)
70 character*1, intent(inout) :: out(*)
71 integer, intent(in) :: in(*)
72 integer, intent(in) :: iskip, nbits
73 end subroutine g2_sbytec
74 subroutine g2_sbytec1(out, in, iskip, nbits)
75 character*1, intent(inout) :: out(*)
76 integer, intent(in) :: in
77 integer, intent(in) :: iskip, nbits
78 end subroutine g2_sbytec1
79 end interface
80
81 ierr = 0
82
83#ifdef LOGGING
84 print *, 'gribcreate lcgrib ', lcgrib
85#endif
86
87 ! Currently handles only GRIB Edition 2.
88 if (listsec0(2) .ne. 2) then
89 print *, 'gribcreate: can only code GRIB edition 2.'
90 ierr = 1
91 return
92 endif
93
94 ! Pack Section 0 - Indicator Section (except for total length of
95 ! GRIB message).
96 cgrib(1) = grib(1:1) ! Beginning of GRIB message
97 cgrib(2) = grib(2:2)
98 cgrib(3) = grib(3:3)
99 cgrib(4) = grib(4:4)
100 call g2_sbytec1(cgrib, zero, 32, 16) ! reserved for future use
101 call g2_sbytec(cgrib, listsec0(1), 48, 8) ! Discipline
102 call g2_sbytec(cgrib, listsec0(2), 56, 8) ! GRIB edition number
103 lensec0 = 16 ! bytes (octets)
104
105 ! Pack Section 1 - Identification Section.
106 ibeg = lensec0 * 8 ! Calculate offset for beginning of section 1
107 iofst = ibeg + 32 ! leave space for length of section
108 call g2_sbytec1(cgrib, one, iofst, 8) ! Store section number ( 1 )
109 iofst = iofst + 8
110
111 ! Pack up each input value in array listsec1 into the the
112 ! appropriate number of octets, which are specified in corresponding
113 ! entries in array mapsec1.
114 do i = 1, mapsec1len
115 nbits = mapsec1(i) * 8
116 call g2_sbytec(cgrib, listsec1(i), iofst, nbits)
117 iofst = iofst + nbits
118 enddo
119
120 ! Calculate length of section 1 and store it in octets 1-4 of
121 ! section 1.
122 lensec1 = (iofst - ibeg) / 8
123 call g2_sbytec1(cgrib, lensec1, ibeg, 32)
124
125 ! Put current byte total of message into Section 0.
126 call g2_sbytec1(cgrib, zero, 64, 32)
127 call g2_sbytec1(cgrib, lensec0 + lensec1, 96, 32)
128end subroutine gribcreate
129
196subroutine addfield(cgrib, lcgrib, ipdsnum, ipdstmpl, ipdstmplen, &
197 coordlist, numcoord, idrsnum, idrstmpl, &
198 idrstmplen, fld, ngrdpts, ibmap, bmap, ierr)
199 use pdstemplates
200 use drstemplates
201 implicit none
202
203 logical :: match
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)
214
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)
233
234 interface
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
239 end subroutine g2_gbytec
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
244 end subroutine g2_gbytec1
245 subroutine g2_gbytec81(in, siout, 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)
250 end subroutine g2_gbytec81
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
255 end subroutine g2_sbytec
256 subroutine g2_sbytec1(out, in, iskip, nbits)
257 character*1, intent(inout) :: out(*)
258 integer, intent(in) :: in
259 integer, intent(in) :: iskip, nbits
260 end subroutine g2_sbytec1
261 end interface
262
263 allones = int(z'FFFFFFFF')
264 ierr = 0
265
266 ! Check to see if beginning of GRIB message exists.
267 match = .true.
268 do i = 1, 4
269 if (cgrib(i) /= grib(i:i)) then
270 match = .false.
271 endif
272 enddo
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.'
276 ierr = 1
277 return
278 endif
279
280 ! Get current length of GRIB message.
281 call g2_gbytec1(cgrib, lencurr, 96, 32)
282
283 ! Check to see if GRIB message is already complete.
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.'
287 ierr = 2
288 return
289 endif
290
291 ! Loop through all current sections of the GRIB message to find the
292 ! last section number.
293 issec3 = .false.
294 isprevbmap = .false.
295 len = 16 ! length of Section 0
296 do
297 ! Get number and length of next section
298 iofst = len * 8
299 call g2_gbytec1(cgrib, ilen, iofst, 32)
300 iofst = iofst + 32
301 call g2_gbytec1(cgrib, isecnum, iofst, 8)
302 iofst = iofst + 8
303
304 ! Check if previous Section 3 exists and save location of
305 ! the section 3 in case needed later.
306 if (isecnum .eq. 3) then
307 issec3 = .true.
308 lpos3 = len + 1
309 lensec3 = ilen
310 endif
311
312 ! Check if a previous defined bitmap exists
313 if (isecnum .eq. 6) then
314 call g2_gbytec1(cgrib, ibmprev, iofst, 8)
315 iofst = iofst + 8
316 if ((ibmprev .ge. 0) .and. (ibmprev .le. 253)) isprevbmap = .true.
317 endif
318 len = len + ilen
319
320 ! Exit loop if last section reached
321 if (len .eq. lencurr) exit
322
323 ! If byte count for each section does not match current
324 ! total length, then there is a problem.
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
329 ierr = 3
330 return
331 endif
332 enddo
333
334 ! Sections 4 through 7 can only be added after section 3 or 7.
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.'
339 ierr = 4
340 return
341
342 ! Sections 4 through 7 can only be added if section 3 was previously defined.
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.'
349 ierr = 6
350 return
351 endif
352
353 ! Add Section 4 - Product Definition Section.
354 ibeg = lencurr * 8 ! Calculate offset for beginning of section 4
355 iofst = ibeg + 32 ! leave space for length of section
356 call g2_sbytec1(cgrib, four, iofst, 8) ! Store section number (4)
357 iofst = iofst + 8
358 call g2_sbytec1(cgrib, numcoord, iofst, 16) ! Store num of coordinate values
359 iofst = iofst + 16
360 call g2_sbytec1(cgrib, ipdsnum, iofst, 16) ! Store Prod Def Template num.
361 iofst = iofst + 16
362
363 ! Get Product Definition Template.
364 call getpdstemplate(ipdsnum, mappdslen, mappds, needext, iret)
365 if (iret .ne. 0) then
366 ierr = 5
367 return
368 endif
369
370 ! Extend the Product Definition Template, if necessary.
371 ! The number of values in a specific template may vary
372 ! depending on data specified in the "static" part of the
373 ! template.
374 if (needext) then
375 call extpdstemplate(ipdsnum, ipdstmpl, mappdslen, mappds)
376 endif
377
378 ! Pack up each input value in array ipdstmpl into the
379 ! the appropriate number of octets, which are specified in
380 ! corresponding entries in array mappds.
381 do i = 1, mappdslen
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)
385 else
386 call g2_sbytec1(cgrib, one, iofst, 1)
387 call g2_sbytec1(cgrib, iabs(ipdstmpl(i)), iofst + 1, nbits - 1)
388 endif
389 iofst = iofst+nbits
390 enddo
391
392 ! Add Optional list of vertical coordinate values
393 ! after the Product Definition Template, if necessary.
394 if (numcoord .ne. 0) then
395 do i = 1, numcoord
396 coordlist_4(i) = real(coordlist(i), 4)
397 end do
398 call mkieee(coordlist_4, coordieee, numcoord)
399 call g2_sbytescr(cgrib, coordieee, iofst, 32, 0, numcoord)
400 iofst = iofst + (32 * numcoord)
401 endif
402
403 ! Calculate length of section 4 and store it in octets
404 ! 1-4 of section 4.
405 lensec4 = (iofst-ibeg)/8
406 call g2_sbytec1(cgrib, lensec4, ibeg, 32)
407
408 ! Pack Data using appropriate algorithm
409
410 ! Get Data Representation Template
411 call getdrstemplate(idrsnum, mapdrslen, mapdrs, needext, iret)
412 if (iret .ne. 0) then
413 ierr = 5
414 return
415 endif
416
417 ! contract data field, removing data at invalid grid points,
418 ! if bit-map is provided with field.
419 if (ibmap .eq. 0 .OR. ibmap .eq. 254) then
420 allocate(pfld(max(2, ngrdpts)))
421 ndpts = 0;
422 do jj = 1, ngrdpts
423 intbmap(jj) = 0
424 if (bmap(jj)) then
425 intbmap(jj) = 1
426 ndpts = ndpts + 1
427 pfld(ndpts) = fld(jj);
428 endif
429 enddo
430 if (ndpts == 0 .and. ngrdpts > 0) then
431 pfld(1) = 0
432 endif
433 else
434 ndpts = ngrdpts;
435 pfld=>fld;
436 endif
437 lcpack = 0
438 nsize = ndpts*4
439 if (nsize .lt. minsize) nsize = minsize
440 allocate(cpack(nsize), stat = istat)
441 if (idrsnum.eq.0) then ! Simple Packing
442 call simpack(pfld, ndpts, idrstmpl, cpack, lcpack)
443 elseif (idrsnum.eq.2.or.idrsnum.eq.3) then ! Complex Packing
444 call cmplxpack(pfld, ndpts, idrsnum, idrstmpl, cpack, lcpack)
445 elseif (idrsnum.eq.50) then ! Sperical Harmonic Simple Packing
446 call simpack(pfld(2), ndpts-1, idrstmpl, cpack, lcpack)
447 tmpfld(1) = real(pfld(1), 4)
448 call mkieee(tmpfld, tmpre00, 1) ! ensure RE(0,0) value is IEEE format
449 re00 = tmpre00(1)
450 ire00 = transfer(re00, ire00)
451 idrstmpl(5) = ire00
452 elseif (idrsnum.eq.51) then ! Sperical Harmonic Complex Packing
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)
456 else
457 print *, 'addfield: Cannot pack DRT 5.51.'
458 ierr=9
459 return
460 endif
461
462 elseif (idrsnum.eq.40 .OR. idrsnum.eq.40000) then ! JPEG2000 encoding
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
466 width=ndpts
467 height=1
468 elseif (width.eq.allones .OR. height.eq.allones) then
469 width=ndpts
470 height=1
471 elseif (ibits(iscan, 5, 1) .eq. 1) then ! Scanning mode: bit 3
472 itemp=width
473 width=height
474 height=itemp
475 endif
476 else
477 width=ndpts
478 height=1
479 endif
480 if (width<1 .or. height<1) then
481 ! Special case: bitmask off everywhere.
482 write(0, *) 'Warning: bitmask off everywhere.'
483 write(0, *) ' Pretend one point in jpcpack to avoid crash.'
484 width=1
485 height=1
486 endif
487 lcpack=nsize
488 ! print *, 'w, h=', width, height
489 call jpcpack(pfld, width, height, idrstmpl, cpack, lcpack)
490
491 elseif (idrsnum.eq.41 .OR. idrsnum.eq.40010) then ! PNG encoding
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
495 width=ndpts
496 height=1
497 elseif (width.eq.allones .OR. height.eq.allones) then
498 width=ndpts
499 height=1
500 elseif (ibits(iscan, 5, 1) .eq. 1) then ! Scanning mode: bit 3
501 itemp=width
502 width=height
503 height=itemp
504 endif
505 else
506 width=ndpts
507 height=1
508 endif
509 !print *, 'png size ', width, height
510 call pngpack(pfld, width, height, idrstmpl, cpack, lcpack)
511 !print *, 'png packed'
512#ifdef USE_AEC
513 elseif (idrsnum.eq.42) then ! AEC compression
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
517 width=ndpts
518 height=1
519 elseif (width.eq.allones .OR. height.eq.allones) then
520 width=ndpts
521 height=1
522 elseif (ibits(iscan, 5, 1) .eq. 1) then ! Scanning mode: bit 3
523 itemp=width
524 width=height
525 height=itemp
526 endif
527 else
528 width=ndpts
529 height=1
530 endif
531 call aecpack(pfld, width, height, idrstmpl, cpack, lcpack);
532#endif /* USE_AEC */
533 else
534 print *, 'addfield: Data Representation Template 5.', idrsnum, &
535 ' not yet implemented.'
536 ierr=7
537 return
538 endif
539 if (ibmap.eq.0 .OR. ibmap.eq.254) then
540 deallocate(pfld)
541 endif
542 if (lcpack .lt. 0) then
543 if (allocated(cpack))deallocate(cpack)
544 ierr=10
545 return
546 endif
547
548 ! Add Section 5 - Data Representation Section
549 ibeg=iofst ! Calculate offset for beginning of section 5
550 iofst=ibeg + 32 ! leave space for length of section
551 call g2_sbytec1(cgrib, five, iofst, 8) ! Store section number (5)
552 iofst=iofst + 8
553 call g2_sbytec1(cgrib, ndpts, iofst, 32) ! Store num of actual data points
554 iofst=iofst + 32
555 call g2_sbytec1(cgrib, idrsnum, iofst, 16) ! Store Data Repr. Template num.
556 iofst = iofst + 16
557
558 ! Pack up each input value in array idrstmpl into the
559 ! the appropriate number of octets, which are specified in
560 ! corresponding entries in array mapdrs.
561 do i=1, mapdrslen
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)
565 else
566 call g2_sbytec1(cgrib, one, iofst, 1)
567 call g2_sbytec1(cgrib, iabs(idrstmpl(i)), iofst+1, nbits-1)
568 endif
569 iofst = iofst + nbits
570 enddo
571
572 ! Calculate length of section 5 and store it in octets
573 ! 1-4 of section 5.
574 lensec5 = (iofst - ibeg) / 8
575 call g2_sbytec1(cgrib, lensec5, ibeg, 32)
576
577 ! Add Section 6 - Bit-Map Section.
578 ibeg = iofst ! Calculate offset for beginning of section 6
579 iofst = ibeg + 32 ! leave space for length of section
580 call g2_sbytec1(cgrib, six, iofst, 8) ! Store section number (6)
581 iofst=iofst + 8
582 call g2_sbytec1(cgrib, ibmap, iofst, 8) ! Store Bit Map indicator
583 iofst = iofst + 8
584
585 ! Store bitmap, if supplied
586 if (ibmap.eq.0) then
587 call g2_sbytesc(cgrib, intbmap, iofst, 1, 0, ngrdpts) ! Store BitMap
588 iofst=iofst+ngrdpts
589 endif
590
591 ! If specifying a previously defined bit-map, make sure
592 ! one already exists in the current GRIB message.
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.'
596 ierr=8
597 return
598 endif
599
600 ! Calculate length of section 6 and store it in octets
601 ! 1-4 of section 6. Pad to end of octect, if necessary.
602 left = 8 - mod(iofst, 8)
603 if (left .ne. 8) then
604 call g2_sbytec1(cgrib, zero, iofst, left) ! Pad with zeros to fill Octet
605 iofst = iofst + left
606 endif
607 lensec6 = (iofst - ibeg) / 8
608 call g2_sbytec1(cgrib, lensec6, ibeg, 32)
609
610 ! Add Section 7 - Data Section.
611 ibeg = iofst ! Calculate offset for beginning of section 7
612 iofst = ibeg + 32 ! leave space for length of section
613 call g2_sbytec1(cgrib, seven, iofst, 8) ! Store section number (7)
614 iofst = iofst + 8
615
616 ! Store Packed Binary Data values, if non-constant field
617 if (lcpack .ne. 0) then
618 ioctet = iofst / 8
619 cgrib(ioctet + 1:ioctet + lcpack) = cpack(1:lcpack)
620 iofst = iofst + (8 * lcpack)
621 endif
622
623 ! Calculate length of section 7 and store it in octets
624 ! 1-4 of section 7.
625 lensec7 = (iofst - ibeg) / 8
626 call g2_sbytec1(cgrib, lensec7, ibeg, 32)
627
628 if (allocated(cpack)) deallocate(cpack)
629
630 ! Update current byte total of message in Section 0.
631 newlen = lencurr + lensec4 + lensec5 + lensec6 + lensec7
632 call g2_sbytec1(cgrib, newlen, 96, 32)
633
634 return
635end subroutine addfield
636
680subroutine addgrid(cgrib, lcgrib, igds, igdstmpl, igdstmplen, &
681 ideflist, idefnum, ierr)
682 use gridtemplates
683 implicit none
684
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
689
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
695 logical needext
696 integer :: i, ilen, iret, isecnum, nbits
697
698 interface
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
703 end subroutine g2_gbytec
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
708 end subroutine g2_gbytec1
709 subroutine g2_gbytec81(in, siout, 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)
714 end subroutine g2_gbytec81
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
719 end subroutine g2_sbytec
720 subroutine g2_sbytec1(out, in, iskip, nbits)
721 character*1, intent(inout) :: out(*)
722 integer, intent(in) :: in
723 integer, intent(in) :: iskip, nbits
724 end subroutine g2_sbytec1
725 end interface
726
727 ierr = 0
728
729#ifdef LOGGING
730 print *, 'addgrid lcgrib ', lcgrib, ' igdstmplen ', igdstmplen, ' idefnum ', idefnum
731#endif
732
733 ! Check to see if beginning of GRIB message exists.
734 do i = 1, 4
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"')
740 print 10, cgrib(1:4)
741 ierr = 1
742 return
743 endif
744 enddo
745
746 ! Get current length of GRIB message.
747 call g2_gbytec1(cgrib, lencurr, 96, 32)
748
749 ! Check to see if GRIB message is already complete.
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', &
754 ' add new section.'
755 ierr = 2
756 return
757 endif
758
759 ! Loop through all current sections of the GRIB message to find the
760 ! last section number.
761 len = 16 ! length of Section 0
762 do
763 ! Get length and section number of next section.
764 iofst = len * 8
765 call g2_gbytec1(cgrib, ilen, iofst, 32)
766 iofst = iofst + 32
767 call g2_gbytec1(cgrib, isecnum, iofst, 8)
768 len = len + ilen
769
770 ! Exit loop if last section reached.
771 if (len .eq. lencurr) exit
772
773 ! If byte count for each section doesn't match current
774 ! total length, then there is a problem.
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
779 ierr = 3
780 return
781 endif
782 enddo
783
784 ! Section 3 can only be added after sections 1, 2 and 7.
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', &
788 ' 1, 2 or 7.'
789 print *, 'addgrid: Section ', isecnum, &
790 ' was the last found in given GRIB message.'
791 ierr = 4
792 return
793 endif
794
795 ! Add Section 3 - Grid Definition Section.
796 ibeg = lencurr * 8 ! Calculate offset for beginning of section 3
797 iofst = ibeg + 32 ! leave space for length of section
798 call g2_sbytec1(cgrib, three, iofst, 8) ! Store section number (3)
799 iofst = iofst + 8
800 call g2_sbytec(cgrib, igds(1), iofst, 8) ! Store source of Grid def.
801 iofst = iofst + 8
802 call g2_sbytec(cgrib, igds(2), iofst, 32) ! Store number of data pts.
803 iofst = iofst + 32
804 call g2_sbytec(cgrib, igds(3), iofst, 8) ! Store number of extra octets.
805 iofst = iofst + 8
806 call g2_sbytec(cgrib, igds(4), iofst, 8) ! Store interp. of extra octets.
807 iofst = iofst + 8
808
809 ! If Octet 6 is not equal to zero, Grid Definition Template may not
810 ! be supplied.
811 if (igds(1) .eq. 0) then
812 call g2_sbytec(cgrib, igds(5), iofst, 16) ! Store Grid Def Template num.
813 else
814 call g2_sbytec1(cgrib, 65535, iofst, 16) ! Store missing value as Grid Def Template num.
815 endif
816 iofst = iofst + 16
817
818 ! Get Grid Definition Template.
819 if (igds(1) .eq. 0) then
820 call getgridtemplate(igds(5), mapgridlen, mapgrid, needext, &
821 iret)
822 if (iret .ne. 0) then
823 ierr = 5
824 return
825 endif
826
827 ! Extend the Grid Definition Template, if necessary. The number
828 ! of values in a specific template may vary depending on data
829 ! specified in the "static" part of the template.
830 if (needext) then
831 call extgridtemplate(igds(5), igdstmpl, mapgridlen, &
832 mapgrid)
833 endif
834 else
835 mapgridlen = 0
836 endif
837
838 ! Pack up each input value in array igdstmpl into the the
839 ! appropriate number of octets, which are specified in corresponding
840 ! entries in array mapgrid.
841 do i = 1, mapgridlen
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)
845 else
846 call g2_sbytec1(cgrib, one, iofst, 1)
847 call g2_sbytec1(cgrib, iabs(igdstmpl(i)), iofst + 1, nbits &
848 - 1)
849 endif
850 iofst = iofst + nbits
851 enddo
852
853 ! If requested, insert optional list of numbers defining number of
854 ! points in each row or column. This is used for non regular grids.
855 if (igds(3) .ne. 0) then
856 nbits = igds(3) * 8
857 call g2_sbytesc(cgrib, ideflist, iofst, nbits, 0, idefnum)
858 iofst = iofst + (nbits * idefnum)
859 endif
860
861 ! Calculate length of section 3 and store it in octets 1-4 of
862 ! section 3.
863 lensec3 = (iofst - ibeg) / 8
864 call g2_sbytec1(cgrib, lensec3, ibeg, 32)
865
866 ! Update current byte total of message in Section 0.
867 call g2_sbytec1(cgrib, lencurr + lensec3, 96, 32)
868end subroutine addgrid
869
894subroutine addlocal(cgrib, lcgrib, csec2, lcsec2, ierr)
895 implicit none
896
897 character(len = 1), intent(inout) :: cgrib(lcgrib)
898 character(len = 1), intent(in) :: csec2(lcsec2)
899 integer, intent(in) :: lcgrib, lcsec2
900 integer, intent(out) :: ierr
901
902 character(len = 4), parameter :: grib = 'GRIB', c7777 = '7777'
903 character(len = 4):: ctemp
904 integer, parameter :: two = 2
905 integer :: lensec2, iofst, ibeg, lencurr, len
906 integer :: ilen, isecnum, istart
907
908 ierr = 0
909
910 ! Check to see if beginning of GRIB message exists.
911 ctemp = cgrib(1) // cgrib(2) // cgrib(3) // cgrib(4)
912 if (ctemp .ne. grib) then
913 print *, 'addlocal: GRIB not found in given message.'
914 print *, 'addlocal: Call to routine gribcreate required', &
915 ' to initialize GRIB messge.'
916 ierr = 1
917 return
918 endif
919
920 ! Get current length of GRIB message.
921 call g2_gbytec1(cgrib, lencurr, 96, 32)
922
923 ! Check to see if GRIB message is already complete
924 ctemp = cgrib(lencurr - 3) // cgrib(lencurr - 2) // cgrib(lencurr - 1) // cgrib(lencurr)
925 if (ctemp .eq. c7777) then
926 print *, 'addlocal: GRIB message already complete. Cannot add new section.'
927 ierr = 2
928 return
929 endif
930
931 ! Loop through all current sections of the GRIB message to find the
932 ! last section number.
933 len = 16 ! length of Section 0
934 do
935 ! Get section number and length of next section.
936 iofst = len * 8
937 call g2_gbytec1(cgrib, ilen, iofst, 32)
938 iofst = iofst + 32
939 call g2_gbytec1(cgrib, isecnum, iofst, 8)
940 len = len + ilen
941 ! Exit loop if last section reached
942 if (len .eq. lencurr) exit
943
944 ! If byte count for each section doesn't match current
945 ! total length, then there is a problem.
946 if (len .gt. lencurr) then
947 print *, 'addlocal: Section byte counts don''t add to total.'
948 print *, 'addlocal: Sum of section byte counts = ', len
949 print *, 'addlocal: Total byte count in Section 0 = ', lencurr
950 ierr = 3
951 return
952 endif
953 enddo
954
955 ! Section 2 can only be added after sections 1 and 7.
956 if ((isecnum .ne. 1) .and. (isecnum .ne. 7)) then
957 print *, 'addlocal: Section 2 can only be added after Section 1 or Section 7.'
958 print *, 'addlocal: Section ', isecnum, ' was the last found in given GRIB message.'
959 ierr = 4
960 return
961 endif
962
963 ! Add Section 2 - Local Use Section.
964 ibeg = lencurr * 8 ! Calculate offset for beginning of section 2
965 iofst = ibeg + 32 ! leave space for length of section
966 call g2_sbytec1(cgrib, two, iofst, 8) ! Store section number (2)
967 istart = lencurr + 5
968 cgrib(istart + 1:istart + lcsec2) = csec2(1:lcsec2)
969
970 ! Calculate length of section 2 and store it in octets 1-4 of
971 ! section 2.
972 lensec2 = lcsec2 + 5 ! bytes
973 call g2_sbytec1(cgrib, lensec2, ibeg, 32)
974
975 ! Update current byte total of message in Section 0.
976 call g2_sbytec1(cgrib, lencurr + lensec2, 96, 32)
977
978end subroutine addlocal
979
1000subroutine gribend(cgrib, lcgrib, lengrib, ierr)
1001 implicit none
1002
1003 character(len = 1), intent(inout) :: cgrib(lcgrib)
1004 integer, intent(in) :: lcgrib
1005 integer, intent(out) :: lengrib, ierr
1006
1007 integer ilen, isecnum
1008 character(len = 4), parameter :: grib = 'GRIB'
1009 character(len = 1), parameter :: c7777(4) = (/ '7', '7', '7', '7' /)
1010 character(len = 4):: ctemp
1011 integer iofst, lencurr, len
1012
1013 ierr = 0
1014
1015 ! Check to see if beginning of GRIB message exists.
1016 ctemp = cgrib(1) // cgrib(2) // cgrib(3) // cgrib(4)
1017 if (ctemp .ne. grib) then
1018 print *, 'gribend: GRIB not found in given message.'
1019 ierr = 1
1020 return
1021 endif
1022
1023 ! Get current length of GRIB message.
1024 call g2_gbytec1(cgrib, lencurr, 96, 32)
1025
1026 ! Loop through all current sections of the GRIB message to
1027 ! find the last section number.
1028 len = 16 ! Length of Section 0
1029 do
1030 ! Get number and length of next section.
1031 iofst = len * 8
1032 call g2_gbytec1(cgrib, ilen, iofst, 32)
1033 iofst = iofst + 32
1034 call g2_gbytec1(cgrib, isecnum, iofst, 8)
1035 len = len + ilen
1036
1037 ! Exit loop if last section reached.
1038 if (len .eq. lencurr) exit
1039
1040 ! If byte count for each section doesn't match current total
1041 ! length, then there is a problem.
1042 if (len .gt. lencurr) then
1043 print *, 'gribend: Section byte counts don''t add ' &
1044 ,'to total.'
1045 print *, 'gribend: Sum of section byte counts = ', len
1046 print *, 'gribend: Total byte count in Section 0 = ', &
1047 lencurr
1048 ierr = 3
1049 return
1050 endif
1051 enddo
1052
1053 ! Can only add End Section (Section 8) after Section 7.
1054 if (isecnum .ne. 7) then
1055 print *, 'gribend: Section 8 can only be added after Section 7.'
1056 print *, 'gribend: Section ', isecnum, &
1057 ' was the last found in',' given GRIB message.'
1058 ierr = 4
1059 return
1060 endif
1061
1062 ! Add Section 8 - End Section.
1063 cgrib(lencurr + 1:lencurr + 4) = c7777
1064
1065 ! Update current byte total of message in Section 0.
1066 lengrib = lencurr + 4
1067 call g2_sbytec1(cgrib, lengrib, 96, 32)
1068end subroutine gribend
subroutine cmplxpack(fld, ndpts, idrsnum, idrstmpl, cpack, lcpack)
Pack up a data field using a complex packing algorithm.
Definition compack.F90:43
subroutine aecpack(fld, width, height, idrstmpl, cpack, lcpack)
Pack a data field into a AEC code stream as defined in Data Representation Template 5....
Definition g2aec.F90:37
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 mkieee(a, rieee, num)
Copy an array of real to an array of 32-bit IEEE floating points.
Definition g2bytes.F90:685
subroutine g2_sbytescr(out, rin, iskip, nbits, nskip, n)
Put real values into a packed bit string in big-endian order.
Definition g2bytes.F90:368
subroutine g2_sbytec(out, in, iskip, nbits)
Put one arbitrary sized (up to 32 bits) value from an integer array, into a packed bit string,...
Definition g2bytes.F90:306
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_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_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_sbytesc(out, in, iskip, nbits, nskip, n)
Put arbitrary size (up to 32 bits each) integer values into a packed bit string in big-endian order.
Definition g2bytes.F90:402
subroutine addgrid(cgrib, lcgrib, igds, igdstmpl, igdstmplen, ideflist, idefnum, ierr)
Add a Grid Definition Section (Section 3) to a GRIB2 message.
Definition g2create.F90:682
subroutine addlocal(cgrib, lcgrib, csec2, lcsec2, ierr)
Add a Local Use Section (Section 2) to a GRIB2 message.
Definition g2create.F90:895
subroutine gribcreate(cgrib, lcgrib, listsec0, listsec1, ierr)
Initialize a new GRIB2 message and pack GRIB2 sections 0 (Indicator) and 1 (Identification).
Definition g2create.F90:54
subroutine addfield(cgrib, lcgrib, ipdsnum, ipdstmpl, ipdstmplen, coordlist, numcoord, idrsnum, idrstmpl, idrstmplen, fld, ngrdpts, ibmap, bmap, ierr)
Pack up Sections 4 through 7 for a field and add them to a GRIB2 message.
Definition g2create.F90:199
subroutine gribend(cgrib, lcgrib, lengrib, ierr)
Finalize a GRIB2 message after all grids and fields have been added.
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:1198
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:1425
subroutine jpcpack(fld, width, height, idrstmpl, cpack, lcpack)
Pack a data field into a JPEG2000 code stream as defined in Data Representation Template 5....
Definition g2jpc.F90:35
subroutine pngpack(fld, width, height, idrstmpl, cpack, lcpack)
Pack a data field into PNG image format, defined in [Data Representation Template 5....
Definition g2png.F90:34
subroutine simpack(fld, ndpts, idrstmpl, cpack, lcpack)
Pack a data field using a simple packing algorithm.
Definition g2sim.F90:27
subroutine specpack(fld, ndpts, jj, kk, mm, idrstmpl, cpack, lcpack)
Pack a spectral data field using the complex packing algorithm for spherical harmonic data as defined...
Definition g2spec.F90:25
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.
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.