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