source: flexpart.git/src/getfields_mpi.f90 @ c0884a8

univie
Last change on this file since c0884a8 was c0884a8, checked in by pesei <petra seibert at univie ac at>, 6 years ago

replace CTBTO code for checking type of GRIB

  • Property mode set to 100644
File size: 12.4 KB
Line 
1!**********************************************************************
2! Copyright 1998,1999,2000,2001,2002,2005,2007,2008,2009,2010         *
3! Andreas Stohl, Petra Seibert, A. Frank, Gerhard Wotawa,             *
4! Caroline Forster, Sabine Eckhardt, John Burkhart, Harald Sodemann   *
5!                                                                     *
6! This file is part of FLEXPART.                                      *
7!                                                                     *
8! FLEXPART is free software: you can redistribute it and/or modify    *
9! it under the terms of the GNU General Public License as published by*
10! the Free Software Foundation, either version 3 of the License, or   *
11! (at your option) any later version.                                 *
12!                                                                     *
13! FLEXPART is distributed in the hope that it will be useful,         *
14! but WITHOUT ANY WARRANTY; without even the implied warranty of      *
15! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the       *
16! GNU General Public License for more details.                        *
17!                                                                     *
18! You should have received a copy of the GNU General Public License   *
19! along with FLEXPART.  If not, see <http://www.gnu.org/licenses/>.   *
20!**********************************************************************
21
22subroutine getfields(itime,nstop,memstat,id_centre)
23!                       i     o       o
24!*****************************************************************************
25!                                                                            *
26!  This subroutine manages the 3 data fields to be kept in memory.           *
27!  During the first time step of petterssen it has to be fulfilled that the  *
28!  first data field must have |wftime|<itime, i.e. the absolute value of     *
29!  wftime must be smaller than the absolute value of the current time in [s].*
30!  The other 2 fields are the next in time after the first one.              *
31!  Pointers (memind) are used, because otherwise one would have to resort the*
32!  wind fields, which costs a lot of computing time. Here only the pointers  *
33!  are resorted.                                                             *
34!                                                                            *
35!     Author: A. Stohl                                                       *
36!                                                                            *
37!     29 April 1994                                                          *
38!                                                                            *
39!*****************************************************************************
40!  Changes, Bernd C. Krueger, Feb. 2001:
41!   Variables tth,qvh,tthn,qvhn (on eta coordinates) in common block.
42!   Function of nstop extended.
43!
44!  eso 2014:
45!    MPI version.
46!    If running with number of processes >= mpi_mod::read_grp_min,
47!    only one process (mpi_mod::lmpreader=.true.) does the actual reading, while
48!    the rest call this routine only to update memind, memstat etc.
49!
50!    If mpi_mod::lmp_sync=.true., uses 3 fields instead of 2, to allow reading
51!    the newest in the background.
52!
53!    Return memstat, which is the sum of
54!   
55!    memstat=16:     one new field to be read
56!    memstat=32:     two new fields must be read
57!    memstat=1,2,3:  position(s) in array to read next field
58!    memstat=0:      no new fields to be read
59!         
60!   Unified ECMWF and GFS builds                                             
61!   Marian Harustak, 12.5.2017                                               
62!     - Added passing of id_centre as it was needed by called routines 
63!                                                                           
64!  Petra Seibert, 2018-06-26: simplified version met data format detection 
65!                                                                           !*****************************************************************************
66!                                                                            *
67! Variables:                                                                 *
68! lwindinterval [s]    time difference between the two wind fields read in   *
69! indj                 indicates the number of the wind field to be read in  *
70! indmin               remembers the number of wind fields already treated   *
71! memind(2[3])         pointer, on which place the wind fields are stored    *
72! memtime(2[3]) [s]    times of the wind fields, which are kept in memory    *
73! itime [s]            current time since start date of trajectory calcu-    *
74!                      lation                                                *
75! nstop                > 0, if trajectory has to be terminated               *
76! memstat              keep track of change of status for field pointers     *
77! nx,ny,nuvz,nwz       field dimensions in x,y and z direction               *
78! uu(0:nxmax,0:nymax,nuvzmax,numwfmem)   wind components in x-direction [m/s]*
79! vv(0:nxmax,0:nymax,nuvzmax,numwfmem)   wind components in y-direction [m/s]*
80! ww(0:nxmax,0:nymax,nwzmax,numwfmem)    wind components in z-direction      *
81!                                          [deltaeta/s]                      *
82! tt(0:nxmax,0:nymax,nuvzmax,numwfmem)   temperature [K]                     *
83! ps(0:nxmax,0:nymax,numwfmem)           surface pressure [Pa]               *
84! id_centre            format of metdata (ecmwf/gfs)                           *
85!                                                                            *
86! Constants:                                                                 *
87! idiffmax             maximum allowable time difference between 2 wind      *
88!                      fields                                                *
89!                                                                            *
90!*****************************************************************************
91
92  use par_mod
93  use com_mod
94  use mpi_mod, only: lmpreader,lmp_use_reader,lmp_sync
95  use check_gribfile_mod
96
97  implicit none
98
99  integer :: id_centre
100  integer :: indj,itime,nstop,memaux,mindread
101! mindread: index of where to read 3rd field
102  integer, intent(out) :: memstat
103! keep track of 3rd field index. updated when new fields are read
104  integer, save :: mind3=0
105
106  real :: uuh(0:nxmax-1,0:nymax-1,nuvzmax)
107  real :: vvh(0:nxmax-1,0:nymax-1,nuvzmax)
108  real :: pvh(0:nxmax-1,0:nymax-1,nuvzmax)
109  real :: wwh(0:nxmax-1,0:nymax-1,nwzmax)
110  real :: uuhn(0:nxmaxn-1,0:nymaxn-1,nuvzmax,maxnests)
111  real :: vvhn(0:nxmaxn-1,0:nymaxn-1,nuvzmax,maxnests)
112  real :: pvhn(0:nxmaxn-1,0:nymaxn-1,nuvzmax,maxnests)
113  real :: wwhn(0:nxmaxn-1,0:nymaxn-1,nwzmax,maxnests)
114
115  integer :: indmin = 1
116
117
118! Check, if wind fields are available for the current time step
119!**************************************************************
120
121  nstop=0
122  memstat=0
123
124  if ((ldirect*wftime(1).gt.ldirect*itime).or. &
125       (ldirect*wftime(numbwf).lt.ldirect*itime)) then
126    write(*,*) 'FLEXPART WARNING: NO WIND FIELDS ARE AVAILABLE.'
127    write(*,*) 'A TRAJECTORY HAS TO BE TERMINATED.'
128    nstop=4
129    return
130  endif
131
132
133  if ((ldirect*memtime(1).le.ldirect*itime).and. &
134       (ldirect*memtime(2).gt.ldirect*itime)) then
135
136! The right wind fields are already in memory -> don't do anything
137!*****************************************************************
138    memstat=0
139    continue
140
141  else if ((ldirect*memtime(2).le.ldirect*itime).and. &
142       (memtime(2).ne.999999999)) then
143
144
145! Current time is after 2nd wind field
146! -> Resort wind field pointers, so that current time is between 1st and 2nd
147!***************************************************************************
148
149! 2 fields in memory
150!*******************
151    if (lmp_sync) then
152      memaux=memind(1)
153      memind(1)=memind(2)
154      memind(2)=memaux
155      memtime(1)=memtime(2)
156      memstat=16+memind(2)
157      mindread=memind(2)
158
159    else
160! 3 fields in memory
161! Note that the reader process never needs to keep 3 fields in memory,
162! (2 is enough) so it is possible to save some memory
163!*********************************************************************
164      if (mind3.eq.32.or.mind3.eq.19) then
165        if (lmpreader) then
166          memind(1)=2
167          memind(2)=3
168          memind(3)=3
169        else
170          memind(1)=2
171          memind(2)=3
172          memind(3)=1
173        end if
174        memstat=17
175      else if (mind3.eq.17) then
176        if (lmpreader) then
177          memind(1)=3
178          memind(2)=1
179          memind(3)=1
180        else
181          memind(1)=3
182          memind(2)=1
183          memind(3)=2
184        end if
185        memstat=18
186      else if (mind3.eq.18) then
187        if (lmpreader) then
188          memind(1)=1
189          memind(2)=2
190          memind(3)=2
191        else
192          memind(1)=1
193          memind(2)=2
194          memind(3)=3
195        end if
196        memstat=19
197      else
198        write(*,*) '#### getfields_mpi.f90> ERROR: ', &
199             & 'unknown mind3, exiting.', mind3,' ####'
200        stop
201      end if
202      mind3=memstat
203      memtime(1)=memtime(2)
204      mindread=memind(3)
205    end if
206
207
208! Read a new wind field and store it on place memind(2)
209! or memind(3) for the 3-field read-ahead version
210!******************************************************
211    do indj=indmin,numbwf-1
212      if (ldirect*wftime(indj+1).gt.ldirect*itime) then
213        if (lmpreader.or..not. lmp_use_reader) then
214          if (id_centre.eq.icg_id_ecmwf) then
215            call readwind_ecmwf(indj+1,mindread,uuh,vvh,wwh)
216          else
217            call readwind_gfs(indj+1,mindread,uuh,vvh,wwh)
218          end if
219          call readwind_nests(indj+1,mindread,uuhn,vvhn,wwhn)
220          call calcpar(mindread,uuh,vvh,pvh,id_centre)
221          call calcpar_nests(mindread,uuhn,vvhn,pvhn,id_centre)
222          if (id_centre.eq.icg_id_ecmwf) then
223            call verttransform_ecmwf(mindread,uuh,vvh,wwh,pvh)
224          else
225            call verttransform_gfs(mindread,uuh,vvh,wwh,pvh)
226          end if
227          call verttransform_nests(mindread,uuhn,vvhn,wwhn,pvhn)
228        end if
229        memtime(2)=wftime(indj+1)
230        nstop = 1
231        goto 40
232      endif
233    end do
23440  indmin=indj
235
236   if (WETBKDEP.and.(lmpreader.or.(.not.lmp_use_reader.and.lroot))) then
237        call writeprecip(itime,memind(1))
238      endif
239
240  else
241
242! No wind fields, which can be used, are currently in memory
243! -> read both wind fields
244!***********************************************************
245    memstat=32
246
247    do indj=indmin,numbwf-1
248      if ((ldirect*wftime(indj).le.ldirect*itime).and. &
249           (ldirect*wftime(indj+1).gt.ldirect*itime)) then
250        memind(1)=1
251        if (lmpreader.or..not.lmp_use_reader) then
252          if (id_centre.eq.icg_id_ecmwf) then
253            call readwind_ecmwf(indj,memind(1),uuh,vvh,wwh)
254          else
255            call readwind_gfs(indj,memind(1),uuh,vvh,wwh)
256          end if
257          call readwind_nests(indj,memind(1),uuhn,vvhn,wwhn)
258          call calcpar(memind(1),uuh,vvh,pvh,id_centre)
259          call calcpar_nests(memind(1),uuhn,vvhn,pvhn,id_centre)
260          if (id_centre.eq.icg_id_ecmwf) then
261            call verttransform_ecmwf(memind(1),uuh,vvh,wwh,pvh)
262          else
263            call verttransform_gfs(memind(1),uuh,vvh,wwh,pvh)
264          end if
265          call verttransform_nests(memind(1),uuhn,vvhn,wwhn,pvhn)
266        end if
267        memtime(1)=wftime(indj)
268        memind(2)=2
269        if (lmpreader.or..not.lmp_use_reader) then
270          if (id_centre.eq.icg_id_ecmwf) then
271            call readwind_ecmwf(indj+1,memind(2),uuh,vvh,wwh)
272          else
273            call readwind_gfs(indj+1,memind(2),uuh,vvh,wwh)
274          end if
275          call readwind_nests(indj+1,memind(2),uuhn,vvhn,wwhn)
276          call calcpar(memind(2),uuh,vvh,pvh,id_centre)
277          call calcpar_nests(memind(2),uuhn,vvhn,pvhn,id_centre)
278          if (id_centre.eq.icg_id_ecmwf) then
279            call verttransform_ecmwf(memind(2),uuh,vvh,wwh,pvh)
280          else
281            call verttransform_gfs(memind(2),uuh,vvh,wwh,pvh)
282          end if
283          call verttransform_nests(memind(2),uuhn,vvhn,wwhn,pvhn)
284        end if
285        memtime(2)=wftime(indj+1)
286! DEV: not used
287        if (.not.lmp_sync) memind(3)=3 ! indicate position of next read
288        nstop = 1
289        goto 60
290      endif
291    end do
29260  indmin=indj
293
294!   if (WETBKDEP.and.lroot) then
295    if (WETBKDEP.and.(lmpreader.or.(.not.lmp_use_reader.and.lroot))) then
296      call writeprecip(itime,memind(1))
297    endif
298
299  endif
300
301  lwindinterv=abs(memtime(2)-memtime(1))
302
303  if (lwindinterv.gt.idiffmax) nstop=3
304
305end subroutine getfields
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG