source: lmdz_wrf/WRFV3/external/io_grib2/g2lib/getgb2r.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: 14.6 KB
Line 
1C-----------------------------------------------------------------------
2      SUBROUTINE GETGB2R(LUGB,CINDEX,GFLD,IRET)
3C$$$  SUBPROGRAM DOCUMENTATION BLOCK
4C
5C SUBPROGRAM: GETGB2R        READS AND UNPACKS A GRIB FIELD
6C   PRGMMR: GILBERT          ORG: W/NP11     DATE: 02-01-15
7C
8C ABSTRACT: READ AND UNPACK SECTIONS 6 AND 7 FROM A GRIB2 MESSAGE.
9C
10C   This routine assumes that the "metadata" for this field
11C   already exists in derived type gribfield.  Specifically,
12C   it requires gfld%ibmap,gfld%ngrdpts,gfld%idrtnum,gfld%idrtmpl,
13C   and gfld%ndpts.
14C   
15C   The decoded information for the selected GRIB field
16C   is returned in a derived type variable, gfld.
17C   Gfld is of type gribfield, which is defined
18C   in module grib_mod, so users of this routine will need to include
19C   the line "USE GRIB_MOD" in their calling routine.  Each component of the
20C   gribfield type is described in the OUTPUT ARGUMENT LIST section below.
21C
22C PROGRAM HISTORY LOG:
23C   95-10-31  IREDELL
24C 2002-01-11  GILBERT     MODIFIED FROM GETGB1R TO WORK WITH GRIB2
25C
26C USAGE:    CALL GETGB2R(LUGB,CINDEX,GFLD,IRET)
27C   INPUT ARGUMENTS:
28C     LUGB         INTEGER UNIT OF THE UNBLOCKED GRIB DATA FILE
29C     CINDEX       INDEX RECORD OF THE GRIB FIELD  ( SEE DOCBLOCK OF
30C                  SUBROUTINE IXGB2 FOR DESCRIPTION OF AN INDEX RECORD.)
31C   OUTPUT ARGUMENTS:
32C     gfld - derived type gribfield ( defined in module grib_mod )
33C            ( NOTE: See Remarks Section )
34C        gfld%version = GRIB edition number ( currently 2 )
35C        gfld%discipline = Message Discipline ( see Code Table 0.0 )
36C        gfld%idsect() = Contains the entries in the Identification
37C                        Section ( Section 1 )
38C                        This element is actually a pointer to an array
39C                        that holds the data.
40C            gfld%idsect(1)  = Identification of originating Centre
41C                                    ( see Common Code Table C-1 )
42C                             7 - US National Weather Service
43C            gfld%idsect(2)  = Identification of originating Sub-centre
44C            gfld%idsect(3)  = GRIB Master Tables Version Number
45C                                    ( see Code Table 1.0 )
46C                             0 - Experimental
47C                             1 - Initial operational version number
48C            gfld%idsect(4)  = GRIB Local Tables Version Number
49C                                    ( see Code Table 1.1 )
50C                             0     - Local tables not used
51C                             1-254 - Number of local tables version used
52C            gfld%idsect(5)  = Significance of Reference Time (Code Table 1.2)
53C                             0 - Analysis
54C                             1 - Start of forecast
55C                             2 - Verifying time of forecast
56C                             3 - Observation time
57C            gfld%idsect(6)  = Year ( 4 digits )
58C            gfld%idsect(7)  = Month
59C            gfld%idsect(8)  = Day
60C            gfld%idsect(9)  = Hour
61C            gfld%idsect(10)  = Minute
62C            gfld%idsect(11)  = Second
63C            gfld%idsect(12)  = Production status of processed data
64C                                    ( see Code Table 1.3 )
65C                              0 - Operational products
66C                              1 - Operational test products
67C                              2 - Research products
68C                              3 - Re-analysis products
69C            gfld%idsect(13)  = Type of processed data ( see Code Table 1.4 )
70C                              0  - Analysis products
71C                              1  - Forecast products
72C                              2  - Analysis and forecast products
73C                              3  - Control forecast products
74C                              4  - Perturbed forecast products
75C                              5  - Control and perturbed forecast products
76C                              6  - Processed satellite observations
77C                              7  - Processed radar observations
78C        gfld%idsectlen = Number of elements in gfld%idsect().
79C        gfld%local() = Pointer to character array containing contents
80C                       of Local Section 2, if included
81C        gfld%locallen = length of array gfld%local()
82C        gfld%ifldnum = field number within GRIB message
83C        gfld%griddef = Source of grid definition (see Code Table 3.0)
84C                      0 - Specified in Code table 3.1
85C                      1 - Predetermined grid Defined by originating centre
86C        gfld%ngrdpts = Number of grid points in the defined grid.
87C        gfld%numoct_opt = Number of octets needed for each
88C                          additional grid points definition.
89C                          Used to define number of
90C                          points in each row ( or column ) for
91C                          non-regular grids.
92C                          = 0, if using regular grid.
93C        gfld%interp_opt = Interpretation of list for optional points
94C                          definition.  (Code Table 3.11)
95C        gfld%igdtnum = Grid Definition Template Number (Code Table 3.1)
96C        gfld%igdtmpl() = Contains the data values for the specified Grid
97C                         Definition Template ( NN=gfld%igdtnum ).  Each
98C                         element of this integer array contains an entry (in
99C                         the order specified) of Grid Defintion Template 3.NN
100C                         This element is actually a pointer to an array
101C                         that holds the data.
102C        gfld%igdtlen = Number of elements in gfld%igdtmpl().  i.e. number of
103C                       entries in Grid Defintion Template 3.NN
104C                       ( NN=gfld%igdtnum ).
105C        gfld%list_opt() = (Used if gfld%numoct_opt .ne. 0)  This array
106C                          contains the number of grid points contained in
107C                          each row ( or column ).  (part of Section 3)
108C                          This element is actually a pointer to an array
109C                          that holds the data.  This pointer is nullified
110C                          if gfld%numoct_opt=0.
111C        gfld%num_opt = (Used if gfld%numoct_opt .ne. 0)  The number of entries
112C                       in array ideflist.  i.e. number of rows ( or columns )
113C                       for which optional grid points are defined.  This value
114C                       is set to zero, if gfld%numoct_opt=0.
115C        gfdl%ipdtnum = Product Definition Template Number (see Code Table 4.0)
116C        gfld%ipdtmpl() = Contains the data values for the specified Product
117C                         Definition Template ( N=gfdl%ipdtnum ).  Each element
118C                         of this integer array contains an entry (in the
119C                         order specified) of Product Defintion Template 4.N.
120C                         This element is actually a pointer to an array
121C                         that holds the data.
122C        gfld%ipdtlen = Number of elements in gfld%ipdtmpl().  i.e. number of
123C                       entries in Product Defintion Template 4.N
124C                       ( N=gfdl%ipdtnum ).
125C        gfld%coord_list() = Real array containing floating point values
126C                            intended to document the vertical discretisation
127C                            associated to model data on hybrid coordinate
128C                            vertical levels.  (part of Section 4)
129C                            This element is actually a pointer to an array
130C                            that holds the data.
131C        gfld%num_coord = number of values in array gfld%coord_list().
132C        gfld%ndpts = Number of data points unpacked and returned.
133C        gfld%idrtnum = Data Representation Template Number
134C                       ( see Code Table 5.0)
135C        gfld%idrtmpl() = Contains the data values for the specified Data
136C                         Representation Template ( N=gfld%idrtnum ).  Each
137C                         element of this integer array contains an entry
138C                         (in the order specified) of Product Defintion
139C                         Template 5.N.
140C                         This element is actually a pointer to an array
141C                         that holds the data.
142C        gfld%idrtlen = Number of elements in gfld%idrtmpl().  i.e. number
143C                       of entries in Data Representation Template 5.N
144C                       ( N=gfld%idrtnum ).
145C        gfld%unpacked = logical value indicating whether the bitmap and
146C                        data values were unpacked.  If false,
147C                        gfld%bmap and gfld%fld pointers are nullified.
148C        gfld%expanded = Logical value indicating whether the data field
149C                         was expanded to the grid in the case where a
150C                         bit-map is present.  If true, the data points in
151C                         gfld%fld match the grid points and zeros were
152C                         inserted at grid points where data was bit-mapped
153C                         out.  If false, the data values in gfld%fld were
154C                         not expanded to the grid and are just a consecutive
155C                         array of data points corresponding to each value of
156C                         "1" in gfld%bmap.
157C        gfld%ibmap = Bitmap indicator ( see Code Table 6.0 )
158C                     0 = bitmap applies and is included in Section 6.
159C                     1-253 = Predefined bitmap applies
160C                     254 = Previously defined bitmap applies to this field
161C                     255 = Bit map does not apply to this product.
162C        gfld%bmap() = Logical*1 array containing decoded bitmap,
163C                      if ibmap=0 or ibap=254.  Otherwise nullified.
164C                      This element is actually a pointer to an array
165C                      that holds the data.
166C        gfld%fld() = Array of gfld%ndpts unpacked data points.
167C                     This element is actually a pointer to an array
168C                     that holds the data.
169C     IRET         INTEGER RETURN CODE
170C                    0      ALL OK
171C                    97     ERROR READING GRIB FILE
172C                    OTHER  GF_GETFLD GRIB UNPACKER RETURN CODE
173C
174C SUBPROGRAMS CALLED:
175C   BAREAD         BYTE-ADDRESSABLE READ
176C   GF_UNPACK6     UNAPCKS BIT_MAP SECTION
177C   GF_UNPACK7     UNAPCKS DATA SECTION
178C
179C REMARKS:
180C   DO NOT ENGAGE THE SAME LOGICAL UNIT FROM MORE THAN ONE PROCESSOR.
181C   THIS SUBPROGRAM IS INTENDED FOR PRIVATE USE BY GETGB2 ROUTINES ONLY.
182C
183C   Note that derived type gribfield contains pointers to many
184C   arrays of data.  The memory for these arrays is allocated
185C   when the values in the arrays are set, to help minimize
186C   problems with array overloading.  Because of this, users
187C   are encouraged to free up this memory, when it is no longer
188C   needed, by an explicit call to subroutine gf_free.
189C   ( i.e.   CALL GF_FREE(GFLD) )
190C
191C ATTRIBUTES:
192C   LANGUAGE: FORTRAN 90
193C
194C$$$
195      USE GRIB_MOD
196
197      INTEGER,INTENT(IN) :: LUGB
198      CHARACTER(LEN=1),INTENT(IN) :: CINDEX(*)
199      INTEGER,INTENT(OUT) :: IRET
200      TYPE(GRIBFIELD) :: GFLD
201
202      INTEGER :: LSKIP,SKIP6,SKIP7
203      CHARACTER(LEN=1):: CSIZE(4)
204      CHARACTER(LEN=1),ALLOCATABLE :: CTEMP(:)
205      real,pointer,dimension(:) :: newfld
206
207      interface
208         subroutine gf_unpack6(cgrib,lcgrib,iofst,ngpts,ibmap,
209     &                         bmap,ierr)
210           character(len=1),intent(in) :: cgrib(lcgrib)
211           integer,intent(in) :: lcgrib,ngpts
212           integer,intent(inout) :: iofst
213           integer,intent(out) :: ibmap
214           integer,intent(out) :: ierr
215           logical*1,pointer,dimension(:) :: bmap
216         end subroutine gf_unpack6
217         subroutine gf_unpack7(cgrib,lcgrib,iofst,igdsnum,igdstmpl,
218     &                         idrsnum,idrstmpl,ndpts,fld,ierr)
219           character(len=1),intent(in) :: cgrib(lcgrib)
220           integer,intent(in) :: lcgrib,ndpts,idrsnum,igdsnum
221           integer,intent(inout) :: iofst
222           integer,pointer,dimension(:) :: idrstmpl,igdstmpl
223           integer,intent(out) :: ierr
224           real,pointer,dimension(:) :: fld
225         end subroutine gf_unpack7
226      end interface
227C - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
228C  GET INFO
229      NULLIFY(gfld%bmap,gfld%fld)
230      IRET=0
231      CALL G2LIB_GBYTE(CINDEX,LSKIP,4*8,4*8)
232      CALL G2LIB_GBYTE(CINDEX,SKIP6,24*8,4*8)
233      CALL G2LIB_GBYTE(CINDEX,SKIP7,28*8,4*8)
234
235C - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
236C  READ AND UNPACK BIT_MAP, IF PRESENT
237      IF ( gfld%ibmap.eq.0.OR.gfld%ibmap.eq.254 ) THEN
238         ISKIP=LSKIP+SKIP6
239         CALL BAREAD(LUGB,ISKIP,4,LREAD,CSIZE)    ! GET LENGTH OF SECTION
240         CALL G2LIB_GBYTE(CSIZE,ILEN,0,32)
241         ALLOCATE(CTEMP(ILEN))
242         CALL BAREAD(LUGB,ISKIP,ILEN,LREAD,CTEMP)  ! READ IN SECTION
243         IF (ILEN.NE.LREAD) THEN
244            IRET=97
245            DEALLOCATE(CTEMP)
246            RETURN
247         ENDIF
248         IOFST=0
249         CALL GF_UNPACK6(CTEMP,ILEN,IOFST,gfld%ngrdpts,idum,
250     &                   gfld%bmap,ierr)
251         IF (IERR.NE.0) THEN
252            IRET=98
253            DEALLOCATE(CTEMP)
254            RETURN
255         ENDIF
256         DEALLOCATE(CTEMP)
257      ENDIF
258C - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
259C  READ AND UNPACK DATA FIELD
260      ISKIP=LSKIP+SKIP7
261      CALL BAREAD(LUGB,ISKIP,4,LREAD,CSIZE)    ! GET LENGTH OF SECTION
262      CALL G2LIB_GBYTE(CSIZE,ILEN,0,32)
263      ALLOCATE(CTEMP(ILEN))
264      CALL BAREAD(LUGB,ISKIP,ILEN,LREAD,CTEMP)  ! READ IN SECTION
265      IF (ILEN.NE.LREAD) THEN
266         IRET=97
267         DEALLOCATE(CTEMP)
268         RETURN
269      ENDIF
270      IOFST=0
271      CALL GF_UNPACK7(CTEMP,ILEN,IOFST,gfld%igdtnum,gfld%igdtmpl,
272     &                   gfld%idrtnum,gfld%idrtmpl,gfld%ndpts,
273     &                   gfld%fld,ierr)
274      IF (IERR.NE.0) THEN
275         IRET=98
276         DEALLOCATE(CTEMP)
277         RETURN
278      ENDIF
279      DEALLOCATE(CTEMP)
280C - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
281      !  If bitmap is used with this field, expand data field
282      !  to grid, if possible.
283      if ( gfld%ibmap .ne. 255 .AND. associated(gfld%bmap) ) then
284            allocate(newfld(gfld%ngrdpts))
285            !newfld=0.0
286            !newfld=unpack(lgfld%fld,lgfld%bmap,newfld)
287            n=1
288            do j=1,gfld%ngrdpts
289                if ( gfld%bmap(j) ) then
290                  newfld(j)=gfld%fld(n)
291                  n=n+1
292                else
293                  newfld(j)=0.0
294                endif
295            enddo
296            deallocate(gfld%fld);
297            gfld%fld=>newfld;
298            gfld%expanded=.true.
299      else
300         gfld%expanded=.true.
301      endif
302C - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
303      RETURN
304      END
Note: See TracBrowser for help on using the repository browser.