source: lmdz_wrf/WRFV3/external/io_grib2/g2lib/putgb2.F @ 1

Last change on this file since 1 was 1, checked in by lfita, 10 years ago
  • -- --- Opening of the WRF+LMDZ coupling repository --- -- -

WRF: version v3.3
LMDZ: version v1818

More details in:

File size: 13.3 KB
Line 
1C-----------------------------------------------------------------------
2      SUBROUTINE PUTGB2(LUGB,GFLD,IRET)
3C$$$  SUBPROGRAM DOCUMENTATION BLOCK
4C
5C SUBPROGRAM: PUTGB2         PACKS AND WRITES A GRIB2 MESSAGE
6C   PRGMMR: GILBERT          ORG: W/NP11     DATE: 2002-04-22
7C
8C ABSTRACT: PACKS A SINGLE FIELD INTO A GRIB2 MESSAGE
9C   AND WRITES OUT THAT MESSAGE TO THE FILE ASSOCIATED WITH UNIT LUGB.
10C   NOTE THAT FILE/UNIT LUGB SHOULD BE OPENED WOTH A CALL TO
11C   SUBROUTINE BAOPENW BEFORE THIS ROUTINE IS CALLED.
12C
13C   The information to be packed into the GRIB field
14C   is stored in a derived type variable, gfld.
15C   Gfld is of type gribfield, which is defined
16C   in module grib_mod, so users of this routine will need to include
17C   the line "USE GRIB_MOD" in their calling routine.  Each component of the
18C   gribfield type is described in the INPUT ARGUMENT LIST section below.
19C
20C PROGRAM HISTORY LOG:
21C 2002-04-22  GILBERT 
22C 2005-02-28  GILBERT   - Changed dimension of array cgrib to be a multiple
23C                         of gfld%ngrdpts instead of gfld%ndpts.
24C
25C USAGE:    CALL PUTGB2(LUGB,GFLD,IRET)
26C   INPUT ARGUMENTS:
27C     LUGB         INTEGER UNIT OF THE UNBLOCKED GRIB DATA FILE.
28C                  FILE MUST BE OPENED WITH BAOPEN OR BAOPENW BEFORE CALLING
29C                  THIS ROUTINE.
30C     gfld - derived type gribfield ( defined in module grib_mod )
31C            ( NOTE: See Remarks Section )
32C        gfld%version = GRIB edition number ( currently 2 )
33C        gfld%discipline = Message Discipline ( see Code Table 0.0 )
34C        gfld%idsect() = Contains the entries in the Identification
35C                        Section ( Section 1 )
36C                        This element is actually a pointer to an array
37C                        that holds the data.
38C            gfld%idsect(1)  = Identification of originating Centre
39C                                    ( see Common Code Table C-1 )
40C                             7 - US National Weather Service
41C            gfld%idsect(2)  = Identification of originating Sub-centre
42C            gfld%idsect(3)  = GRIB Master Tables Version Number
43C                                    ( see Code Table 1.0 )
44C                             0 - Experimental
45C                             1 - Initial operational version number
46C            gfld%idsect(4)  = GRIB Local Tables Version Number
47C                                    ( see Code Table 1.1 )
48C                             0     - Local tables not used
49C                             1-254 - Number of local tables version used
50C            gfld%idsect(5)  = Significance of Reference Time (Code Table 1.2)
51C                             0 - Analysis
52C                             1 - Start of forecast
53C                             2 - Verifying time of forecast
54C                             3 - Observation time
55C            gfld%idsect(6)  = Year ( 4 digits )
56C            gfld%idsect(7)  = Month
57C            gfld%idsect(8)  = Day
58C            gfld%idsect(9)  = Hour
59C            gfld%idsect(10)  = Minute
60C            gfld%idsect(11)  = Second
61C            gfld%idsect(12)  = Production status of processed data
62C                                    ( see Code Table 1.3 )
63C                              0 - Operational products
64C                              1 - Operational test products
65C                              2 - Research products
66C                              3 - Re-analysis products
67C            gfld%idsect(13)  = Type of processed data ( see Code Table 1.4 )
68C                              0  - Analysis products
69C                              1  - Forecast products
70C                              2  - Analysis and forecast products
71C                              3  - Control forecast products
72C                              4  - Perturbed forecast products
73C                              5  - Control and perturbed forecast products
74C                              6  - Processed satellite observations
75C                              7  - Processed radar observations
76C        gfld%idsectlen = Number of elements in gfld%idsect().
77C        gfld%local() = Pointer to character array containing contents
78C                       of Local Section 2, if included
79C        gfld%locallen = length of array gfld%local()
80C        gfld%ifldnum = field number within GRIB message
81C        gfld%griddef = Source of grid definition (see Code Table 3.0)
82C                      0 - Specified in Code table 3.1
83C                      1 - Predetermined grid Defined by originating centre
84C        gfld%ngrdpts = Number of grid points in the defined grid.
85C        gfld%numoct_opt = Number of octets needed for each
86C                          additional grid points definition.
87C                          Used to define number of
88C                          points in each row ( or column ) for
89C                          non-regular grids.
90C                          = 0, if using regular grid.
91C        gfld%interp_opt = Interpretation of list for optional points
92C                          definition.  (Code Table 3.11)
93C        gfld%igdtnum = Grid Definition Template Number (Code Table 3.1)
94C        gfld%igdtmpl() = Contains the data values for the specified Grid
95C                         Definition Template ( NN=gfld%igdtnum ).  Each
96C                         element of this integer array contains an entry (in
97C                         the order specified) of Grid Defintion Template 3.NN
98C                         This element is actually a pointer to an array
99C                         that holds the data.
100C        gfld%igdtlen = Number of elements in gfld%igdtmpl().  i.e. number of
101C                       entries in Grid Defintion Template 3.NN
102C                       ( NN=gfld%igdtnum ).
103C        gfld%list_opt() = (Used if gfld%numoct_opt .ne. 0)  This array
104C                          contains the number of grid points contained in
105C                          each row ( or column ).  (part of Section 3)
106C                          This element is actually a pointer to an array
107C                          that holds the data.  This pointer is nullified
108C                          if gfld%numoct_opt=0.
109C        gfld%num_opt = (Used if gfld%numoct_opt .ne. 0)  The number of entries
110C                       in array ideflist.  i.e. number of rows ( or columns )
111C                       for which optional grid points are defined.  This value
112C                       is set to zero, if gfld%numoct_opt=0.
113C        gfdl%ipdtnum = Product Definition Template Number (see Code Table 4.0)
114C        gfld%ipdtmpl() = Contains the data values for the specified Product
115C                         Definition Template ( N=gfdl%ipdtnum ).  Each element
116C                         of this integer array contains an entry (in the
117C                         order specified) of Product Defintion Template 4.N.
118C                         This element is actually a pointer to an array
119C                         that holds the data.
120C        gfld%ipdtlen = Number of elements in gfld%ipdtmpl().  i.e. number of
121C                       entries in Product Defintion Template 4.N
122C                       ( N=gfdl%ipdtnum ).
123C        gfld%coord_list() = Real array containing floating point values
124C                            intended to document the vertical discretisation
125C                            associated to model data on hybrid coordinate
126C                            vertical levels.  (part of Section 4)
127C                            This element is actually a pointer to an array
128C                            that holds the data.
129C        gfld%num_coord = number of values in array gfld%coord_list().
130C        gfld%ndpts = Number of data points unpacked and returned.
131C        gfld%idrtnum = Data Representation Template Number
132C                       ( see Code Table 5.0)
133C        gfld%idrtmpl() = Contains the data values for the specified Data
134C                         Representation Template ( N=gfld%idrtnum ).  Each
135C                         element of this integer array contains an entry
136C                         (in the order specified) of Product Defintion
137C                         Template 5.N.
138C                         This element is actually a pointer to an array
139C                         that holds the data.
140C        gfld%idrtlen = Number of elements in gfld%idrtmpl().  i.e. number
141C                       of entries in Data Representation Template 5.N
142C                       ( N=gfld%idrtnum ).
143C        gfld%unpacked = logical value indicating whether the bitmap and
144C                        data values were unpacked.  If false,
145C                        gfld%bmap and gfld%fld pointers are nullified.
146C        gfld%ibmap = Bitmap indicator ( see Code Table 6.0 )
147C                     0 = bitmap applies and is included in Section 6.
148C                     1-253 = Predefined bitmap applies
149C                     254 = Previously defined bitmap applies to this field
150C                     255 = Bit map does not apply to this product.
151C        gfld%bmap() = Logical*1 array containing decoded bitmap,
152C                      if ibmap=0 or ibap=254.  Otherwise nullified.
153C                      This element is actually a pointer to an array
154C                      that holds the data.
155C        gfld%fld() = Array of gfld%ndpts unpacked data points.
156C                     This element is actually a pointer to an array
157C                     that holds the data.
158C
159C   OUTPUT ARGUMENTS:
160C     IRET         INTEGER RETURN CODE
161C                    0      ALL OK
162C                    2      MEMORY ALLOCATION ERROR
163C                    10     No Section 1 info available
164C                    11     No Grid Definition Template info available
165C                    12     Missing some required data field info
166C
167C SUBPROGRAMS CALLED:
168C   gribcreate     Start a new grib2 message
169C   addlocal       Add local section to a GRIB2 message
170C   addgrid        Add grid info to a GRIB2 message
171C   addfield       Add data field to a GRIB2 message
172C   gribend        End GRIB2 message
173C
174C REMARKS:
175C
176C   Note that derived type gribfield contains pointers to many
177C   arrays of data.  The memory for these arrays is allocated
178C   when the values in the arrays are set, to help minimize
179C   problems with array overloading.  Because of this users
180C   are encouraged to free up this memory, when it is no longer
181C   needed, by an explicit call to subroutine gf_free.
182C   ( i.e.   CALL GF_FREE(GFLD) )
183C
184C ATTRIBUTES:
185C   LANGUAGE: FORTRAN 90
186C
187C$$$
188      USE GRIB_MOD
189
190      INTEGER,INTENT(IN) :: LUGB
191      TYPE(GRIBFIELD),INTENT(IN) :: GFLD
192      INTEGER,INTENT(OUT) :: IRET
193
194      CHARACTER(LEN=1),ALLOCATABLE,DIMENSION(:) :: CGRIB
195      integer :: listsec0(2)=(/0,2/)
196      integer :: igds(5)=(/0,0,0,0,0/)
197C - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
198C  ALLOCATE ARRAY FOR GRIB2 FIELD
199      lcgrib=gfld%ngrdpts*4
200      allocate(cgrib(lcgrib),stat=is)
201      if ( is.ne.0 ) then
202         print *,'putgb2: cannot allocate memory. ',is
203         iret=2
204      endif
205C - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
206C  CREATE NEW MESSAGE
207      listsec0(1)=gfld%discipline
208      listsec0(2)=gfld%version
209      if ( associated(gfld%idsect) ) then
210         call gribcreate(cgrib,lcgrib,listsec0,gfld%idsect,ierr)
211         if (ierr.ne.0) then
212            write(6,*) 'putgb2: ERROR creating new GRIB2 field = ',ierr
213         endif
214      else
215         print *,'putgb2: No Section 1 info available. '
216         iret=10
217         deallocate(cgrib)
218         return
219      endif
220C - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
221C  ADD LOCAL USE SECTION TO GRIB2 MESSAGE
222      if ( associated(gfld%local).AND.gfld%locallen.gt.0 ) then
223         call addlocal(cgrib,lcgrib,gfld%local,gfld%locallen,ierr)
224         if (ierr.ne.0) then
225            write(6,*) 'putgb2: ERROR adding local info = ',ierr
226         endif
227      endif
228C - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
229C  ADD GRID TO GRIB2 MESSAGE
230      igds(1)=gfld%griddef
231      igds(2)=gfld%ngrdpts
232      igds(3)=gfld%numoct_opt
233      igds(4)=gfld%interp_opt
234      igds(5)=gfld%igdtnum
235      if ( associated(gfld%igdtmpl) ) then
236         call addgrid(cgrib,lcgrib,igds,gfld%igdtmpl,gfld%igdtlen,
237     &                gfld%list_opt,gfld%num_opt,ierr)
238         if (ierr.ne.0) then
239            write(6,*) 'putgb2: ERROR adding grid info = ',ierr
240         endif
241      else
242         print *,'putgb2: No GDT info available. '
243         iret=11
244         deallocate(cgrib)
245         return
246      endif
247C - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
248C  ADD DATA FIELD TO GRIB2 MESSAGE
249      if ( associated(gfld%ipdtmpl).AND.
250     &     associated(gfld%idrtmpl).AND.
251     &     associated(gfld%fld) ) then
252         call addfield(cgrib,lcgrib,gfld%ipdtnum,gfld%ipdtmpl,
253     &                 gfld%ipdtlen,gfld%coord_list,gfld%num_coord,
254     &                 gfld%idrtnum,gfld%idrtmpl,gfld%idrtlen,
255     &                 gfld%fld,gfld%ngrdpts,gfld%ibmap,gfld%bmap,
256     &                 ierr)
257         if (ierr.ne.0) then
258            write(6,*) 'putgb2: ERROR adding data field = ',ierr
259         endif
260      else
261         print *,'putgb2: Missing some field info. '
262         iret=12
263         deallocate(cgrib)
264         return
265      endif
266C - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
267C  CLOSE GRIB2 MESSAGE AND WRITE TO FILE
268      call gribend(cgrib,lcgrib,lengrib,ierr)
269      call wryte(lugb,lengrib,cgrib)
270C - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
271      deallocate(cgrib)
272      RETURN
273      END
Note: See TracBrowser for help on using the repository browser.