source: branches/flexpart91_hasod/src_parallel/getfields.f90 @ 8

Last change on this file since 8 was 8, checked in by hasod, 11 years ago

Added parallel version of Flexpart91

File size: 9.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)
23  !                       i     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  !                                                                            *
45  ! Variables:                                                                 *
46  ! lwindinterval [s]    time difference between the two wind fields read in   *
47  ! indj                 indicates the number of the wind field to be read in  *
48  ! indmin               remembers the number of wind fields already treated   *
49  ! memind(2)            pointer, on which place the wind fields are stored    *
50  ! memtime(2) [s]       times of the wind fields, which are kept in memory    *
51  ! itime [s]            current time since start date of trajectory calcu-    *
52  !                      lation                                                *
53  ! nstop                > 0, if trajectory has to be terminated               *
54  ! nx,ny,nuvz,nwz       field dimensions in x,y and z direction               *
55  ! uu(0:nxmax,0:nymax,nuvzmax,2)   wind components in x-direction [m/s]       *
56  ! vv(0:nxmax,0:nymax,nuvzmax,2)   wind components in y-direction [m/s]       *
57  ! ww(0:nxmax,0:nymax,nwzmax,2)    wind components in z-direction [deltaeta/s]*
58  ! tt(0:nxmax,0:nymax,nuvzmax,2)   temperature [K]                            *
59  ! ps(0:nxmax,0:nymax,2)           surface pressure [Pa]                      *
60  !                                                                            *
61  ! Constants:                                                                 *
62  ! idiffmax             maximum allowable time difference between 2 wind      *
63  !                      fields                                                *
64  !                                                                            *
65  !*****************************************************************************
66
67  use par_mod
68  use com_mod
69
70  implicit none
71
72  integer :: indj,itime,nstop,memaux
73
74  real(kind=4),allocatable,dimension(:,:,:) :: uuh
75  real(kind=4),allocatable,dimension(:,:,:) :: vvh
76  real(kind=4),allocatable,dimension(:,:,:) :: pvh
77  real(kind=4),allocatable,dimension(:,:,:) :: wwh
78  real(kind=4),allocatable,dimension(:,:,:,:) :: uuhn
79  real(kind=4),allocatable,dimension(:,:,:,:) :: vvhn
80  real(kind=4),allocatable,dimension(:,:,:,:) :: pvhn
81  real(kind=4),allocatable,dimension(:,:,:,:) :: wwhn
82
83  integer :: indmin = 1
84  integer :: stat
85
86
87  ! Check, if wind fields are available for the current time step
88  !**************************************************************
89
90  allocate(uuh(0:nxmax-1,0:nymax-1,nuvzmax),stat=stat)
91  if (stat.ne.0) print*,'ERROR: could not allocate uuh'
92  allocate(vvh(0:nxmax-1,0:nymax-1,nuvzmax),stat=stat)
93  if (stat.ne.0) print*,'ERROR: could not allocate uuh'
94  allocate(pvh(0:nxmax-1,0:nymax-1,nuvzmax),stat=stat)
95  if (stat.ne.0) print*,'ERROR: could not allocate uuh'
96  allocate(wwh(0:nxmax-1,0:nymax-1,nwzmax),stat=stat)
97  if (stat.ne.0) print*,'ERROR: could not allocate uuh'
98  if (maxnests.gt.0) then
99    allocate(uuhn(0:nxmax-1,0:nymax-1,nuvzmax,maxnests),stat=stat)
100    if (stat.ne.0) print*,'ERROR: could not allocate uuh'
101    allocate(vvhn(0:nxmax-1,0:nymax-1,nuvzmax,maxnests),stat=stat)
102    if (stat.ne.0) print*,'ERROR: could not allocate uuh'
103    allocate(pvhn(0:nxmax-1,0:nymax-1,nuvzmax,maxnests),stat=stat)
104    if (stat.ne.0) print*,'ERROR: could not allocate uuh'
105    allocate(wwhn(0:nxmax-1,0:nymax-1,nwzmax,maxnests),stat=stat)
106    if (stat.ne.0) print*,'ERROR: could not allocate uuh'
107  endif
108
109  nstop=0
110  if ((ldirect*wftime(1).gt.ldirect*itime).or. &
111       (ldirect*wftime(numbwf).lt.ldirect*itime)) then
112    write(*,*) 'FLEXPART WARNING: NO WIND FIELDS ARE AVAILABLE.'
113    write(*,*) 'A TRAJECTORY HAS TO BE TERMINATED.'
114    nstop=4
115    return
116  endif
117
118
119  if ((ldirect*memtime(1).le.ldirect*itime).and. &
120       (ldirect*memtime(2).gt.ldirect*itime)) then
121
122  ! The right wind fields are already in memory -> don't do anything
123  !*****************************************************************
124
125    continue
126
127  else if ((ldirect*memtime(2).le.ldirect*itime).and. &
128       (memtime(2).ne.999999999)) then
129
130
131  ! Current time is after 2nd wind field
132  ! -> Resort wind field pointers, so that current time is between 1st and 2nd
133  !***************************************************************************
134
135    memaux=memind(1)
136    memind(1)=memind(2)
137    memind(2)=memaux
138    memtime(1)=memtime(2)
139
140
141  ! Read a new wind field and store it on place memind(2)
142  !******************************************************
143
144    do indj=indmin,numbwf-1
145       if (ldirect*wftime(indj+1).gt.ldirect*itime) then
146          memtime(2)=wftime(indj+1)
147          call readwind(indj+1,memind(2),uuh,vvh,wwh)
148          call readwind_nests(indj+1,memind(2),uuhn,vvhn,wwhn)
149          call calcpar(memind(2),uuh,vvh,pvh)
150          call calcpar_nests(memind(2),uuhn,vvhn,pvhn)
151          call verttransform(memind(2),uuh,vvh,wwh,pvh)
152          call verttransform_nests(memind(2),uuhn,vvhn,wwhn,pvhn)
153          nstop = 1
154          goto 40
155       endif
156    end do
157 40   indmin=indj
158
159  else
160
161  ! No wind fields, which can be used, are currently in memory
162  ! -> read both wind fields
163  !***********************************************************
164
165     do indj=indmin,numbwf-1
166        if ((ldirect*wftime(indj).le.ldirect*itime).and. &
167             (ldirect*wftime(indj+1).gt.ldirect*itime)) then
168           memind(1)=1
169           memtime(1)=wftime(indj)
170!hes: setting memtime before call to calcpar, assures that correct time is used in getvdep
171           call readwind(indj,memind(1),uuh,vvh,wwh)
172           call readwind_nests(indj,memind(1),uuhn,vvhn,wwhn)
173           call calcpar(memind(1),uuh,vvh,pvh)
174           call calcpar_nests(memind(1),uuhn,vvhn,pvhn)
175           call verttransform(memind(1),uuh,vvh,wwh,pvh)
176           call verttransform_nests(memind(1),uuhn,vvhn,wwhn,pvhn)
177           memind(2)=2
178           memtime(2)=wftime(indj+1)
179           call readwind(indj+1,memind(2),uuh,vvh,wwh)
180           call readwind_nests(indj+1,memind(2),uuhn,vvhn,wwhn)
181           call calcpar(memind(2),uuh,vvh,pvh)
182           call calcpar_nests(memind(2),uuhn,vvhn,pvhn)
183           call verttransform(memind(2),uuh,vvh,wwh,pvh)
184           call verttransform_nests(memind(2),uuhn,vvhn,wwhn,pvhn)
185           nstop = 1
186           goto 60
187        endif
188     end do
189 60   indmin=indj
190
191  endif
192
193  lwindinterv=abs(memtime(2)-memtime(1))
194
195  if (lwindinterv.gt.idiffmax) nstop=3
196
197  deallocate(uuh)
198  deallocate(vvh)
199  deallocate(wwh)
200  deallocate(pvh)
201  if (maxnests.gt.0) then
202    deallocate(uuhn)
203    deallocate(vvhn)
204    deallocate(wwhn)
205    deallocate(pvhn)
206  endif
207
208end subroutine getfields
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG