source: flex_extract.git/Source/Fortran/rwgrib2.f90

ctbtodev
Last change on this file was 36dbabb, checked in by pesei <petra.seibert [at ) univie.ac.at>, 4 years ago

Update FORD documentation, change some comment lines in Fortran, smal change in run_reftest.sh

  • Property mode set to 100644
File size: 7.1 KB
Line 
1 MODULE RWGRIB2
2
3!! Read or write a field variable on a lat/lon grid from/to GRIB file, or
4!! read a field in spectral representation from GRIB file
5
6 CONTAINS
7
8 SUBROUTINE READLATLON(FILENAME,FELD,MAXL,MAXB,MLEVEL,MPAR)
9
10!! Read a field from GRIB file on lat-lon grid
11
12 USE GRIB_API
13
14 IMPLICIT NONE
15
16   integer                            ::  ifile
17   integer                            ::  iret
18   integer                            ::  n,mk,parid,nm
19   integer                            ::  i,k
20   integer,dimension(:),allocatable   ::  igrib
21   integer                            ::  numberOfPointsAlongAParallel
22   integer                            ::  numberOfPointsAlongAMeridian
23   real, dimension(:), allocatable    ::  values
24   integer                            ::  numberOfValues
25   real,dimension(maxl,maxb,mlevel)   ::  feld 
26   integer:: maxl,maxb,mlevel,mstride,mpar(:),irest,div,level
27   integer :: l(size(mpar))
28   character*(*):: filename   
29   
30   feld=0.                         
31
32   call grib_open_file(ifile, TRIM(FILENAME),'r')
33 
34   ! count the messages in the file
35   call grib_count_in_file(ifile,n)
36   allocate(igrib(n))
37   igrib=-1
38 
39   ! Load the messages from the file.
40   DO i=1,n
41      call grib_new_from_file(ifile,igrib(i), iret)
42   END DO
43 
44   ! we can close the file
45   call grib_close_file(ifile)
46 
47      nm=size(mpar)
48      div=mlevel/nm
49      l=0
50     
51   ! Loop on all the messages in memory
52  iloop:  DO i=1,n
53!      write(*,*) 'processing message number ',i
54      !     get as a integer
55      call grib_get(igrib(i),'numberOfPointsAlongAParallel', &
56           numberOfPointsAlongAParallel)
57 
58      !     get as a integer
59      call grib_get(igrib(i),'numberOfPointsAlongAMeridian', &
60           numberOfPointsAlongAMeridian)
61
62      call grib_get(igrib(i),'numberOfVerticalCoordinateValues',mk)
63
64      call grib_get_size(igrib(i),'values',numberOfValues)
65!      write(*,*) 'numberOfValues=',numberOfValues
66 
67      allocate(values(numberOfValues), stat=iret)
68      !     get data values
69      call grib_get(igrib(i),'values',values)
70
71      call grib_get(igrib(i),'paramId',parid)
72      call grib_get(igrib(i),'level',level)
73
74 kloop:  do k=1,nm
75        if (parid .eq. mpar(k)) then
76!         l(k)=l(k)+1
77         feld(:,:,(k-1)*div+level)=reshape(values,(/maxl,maxb/))
78!         print*,(k-1)*div+l(k),parid
79         exit kloop
80        end if
81      end do kloop
82      if (k .gt. nm .and. parid .ne. mpar(nm)) then
83        write(*,*) k,nm,parid,mpar(nm)
84        write(*,*) 'ERROR readlatlon: parameter ',parid,'is not',mpar
85        stop
86      end if
87
88!      print*,i
89   END DO iloop
90! !   write(*,*) 'readlatlon: ',i-1,' records read'
91 
92   DO i=1,n
93     call grib_release(igrib(i))
94   END DO
95 
96   if (allocated(values)) deallocate(values)
97   deallocate(igrib)
98
99   END SUBROUTINE READLATLON
100
101   SUBROUTINE WRITELATLON(iunit,igrib,ogrib,FELD,MAXL,MAXB,MLEVEL,&
102   MLEVELIST,MSTRIDE,MPAR)
103
104!! write a field on lat-lon grid to GRIB file
105
106   USE GRIB_API
107
108   IMPLICIT NONE
109
110   INTEGER IFIELD,MLEVEL,MNAUF,I,J,K,L,MSTRIDE,IERR,JOUT
111   INTEGER MPAR(MSTRIDE),MAXL,MAXB,LEVMIN,LEVMAX
112   INTEGER IUNIT,igrib,ogrib
113   REAL ZSEC4(MAXL*MAXB)
114   REAL    FELD(MAXL,MAXB,MLEVEL)
115   CHARACTER*(*) MLEVELIST
116   INTEGER ILEVEL(MLEVEL),MLINDEX(MLEVEL+1),LLEN
117
118 ! parse MLEVELIST
119
120   LLEN=len(trim(MLEVELIST))
121   if (index(MLEVELIST,'to') .ne. 0 .or. index(MLEVELIST,'TO') .ne. 0) THEN
122     i=index(MLEVELIST,'/')
123     read(MLEVELIST(1:i-1),*) LEVMIN
124     i=index(MLEVELIST,'/',.true.)
125     read(MLEVELIST(i+1:LLEN),*) LEVMAX
126     l=0
127     do i=LEVMIN,LEVMAX
128       l=l+1
129       ILEVEL(l)=i
130     end do
131   else
132     l=1
133     MLINDEX(1)=0
134     do i=1,LLEN
135       if (MLEVELIST(i:i) .eq. '/') THEN
136         l=l+1
137         MLINDEX(l)=i
138       end if
139     end do
140     MLINDEX(l+1)=LLEN+1
141     do i=1,l
142       read(MLEVELIST(MLINDEX(i)+1:MLINDEX(i+1)-1),*) ILEVEL(i)
143     end do
144   end if
145
146   DO k=1,l
147     call grib_set(igrib,"level",ILEVEL(k))
148     DO j=1,MSTRIDE
149       call grib_set(igrib,"paramId",MPAR(j))
150!         if (MPAR(j) .eq. 87) then
151!           call grib_set(igrib,"shortName","etadot")
152!           call grib_set(igrib,"units","Pa,s**-1")
153!         end if
154!         if (MPAR(j) .eq. 77) then
155!           call grib_set(igrib,"shortName","etadot")
156!           call grib_set(igrib,"units","s**-1")
157!         end if
158       if (l .ne. mlevel) then
159         zsec4(1:maxl*maxb)=RESHAPE(FELD(:,:,ILEVEL(k)),(/maxl*maxb/))
160       else
161         zsec4(1:maxl*maxb)=RESHAPE(FELD(:,:,k),(/maxl*maxb/))
162       end if
163       call grib_set(igrib,"values",zsec4)
164
165       call grib_write(igrib,iunit)
166
167     END DO
168   END DO
169
170   END SUBROUTINE WRITELATLON
171
172   SUBROUTINE READSPECTRAL(FILENAME,CXMN,MNAUF,MLEVEL,MAXLEV,MPAR,A,B)
173
174!!  Read a GRIB file in spherical harmonics
175
176   USE GRIB_API
177
178   IMPLICIT NONE
179
180   integer                            ::  ifile
181   integer                            ::  iret
182   integer                            ::  n,mk,div,nm,k
183   integer                            ::  i,j,parid
184   integer,dimension(:),allocatable   ::  igrib
185   real, dimension(:), allocatable    ::  values
186   integer                            ::  numberOfValues,maxlev
187   REAL :: A(MAXLEV+1),B(MAXLEV+1),pv(2*MAXLEV+2)
188   REAL:: CXMN(0:(MNAUF+1)*(MNAUF+2)-1,MLEVEL)
189  integer:: maxl,maxb,mlevel,mstride,mpar(:),mnauf,ioffset,ipar,ilev,l(size(mpar))
190   character*(*):: filename                             
191 
192   call grib_open_file(ifile, TRIM(FILENAME),'r')
193 
194   ! count the messages in the file
195   call grib_count_in_file(ifile,n)
196   allocate(igrib(n))
197   igrib=-1
198 
199   ! Load the messages from the file.
200   DO i=1,n
201      call grib_new_from_file(ifile,igrib(i), iret)
202   END DO
203 
204   ! we can close the file
205   call grib_close_file(ifile)
206 
207    l=0
208   ! Loop on all the messages in memory
209   iloop: DO i=1,n
210   ! write(*,*) 'processing message number ',i
211      !     get as a integer
212      call grib_get(igrib(i),'pentagonalResolutionParameterJ', j)
213
214      call grib_get_size(igrib(i),'values',numberOfValues)
215   !   write(*,*) 'numberOfValues=',numberOfValues
216 
217      call grib_get(igrib(i),'numberOfVerticalCoordinateValues',mk)
218
219      call grib_get(igrib(i),'level',ilev)
220
221     
222
223      call grib_get(igrib(i),'pv',pv)
224
225      allocate(values(numberOfValues), stat=iret)
226      !     get data values
227      call grib_get(igrib(i),'values',values)
228
229!      IOFFSET=mod(i-1,MSTRIDE)*(mk/2-1)
230!           CXMN(:,IOFFSET+ilev)=values(1:(MNAUF+1)*(MNAUF+2))
231
232      call grib_get(igrib(i),'paramId',parid)
233      nm=size(mpar)
234      div=mlevel/nm
235      kloop:  do k=1,nm
236        if (parid .eq. mpar(k)) then
237         l(k)=l(k)+1
238         cxmn(:,(k-1)*div+l(k))=values(1:(MNAUF+1)*(MNAUF+2))
239!         print*,(k-1)*div+l(k),parid
240         exit kloop
241        end if
242       
243      end do kloop
244      if (k .gt. nm .and. parid .ne. mpar(nm)) then
245        write(*,*) k,nm,parid,mpar(nm)
246        write(*,*) 'ERROR readspectral: parameter ',parid,'is not',mpar
247        stop
248      end if
249
250!      print*,i
251
252   END DO iloop
253
254! !   write(*,*) 'readspectral: ',i-1,' records read'
255 
256   DO i=1,n
257     call grib_release(igrib(i))
258   END DO
259 
260   deallocate(values)
261   deallocate(igrib)
262
263   A=pv(1:1+MAXLEV)
264   B=pv(2+MAXLEV:2*MAXLEV+2)
265
266   END SUBROUTINE READSPECTRAL
267
268END MODULE RWGRIB2
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG