source: flexpart.git/src/initialize.f90 @ 54cbd6c

10.4.1_peseiGFS_025bugfixes+enhancementsdevrelease-10release-10.4.1scaling-bugunivie
Last change on this file since 54cbd6c was db712a8, checked in by Espen Sollum ATMOS <eso@…>, 8 years ago

Completed handling of nested wind fields with cloud water (for wet deposition).

  • Property mode set to 100644
File size: 9.0 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 initialize(itime,ldt,up,vp,wp, &
23       usigold,vsigold,wsigold,xt,yt,zt,icbt)
24  !                        i    i   o  o  o
25  !        o       o       o    i  i  i   o
26  !*****************************************************************************
27  !                                                                            *
28  !  Calculation of trajectories utilizing a zero-acceleration scheme. The time*
29  !  step is determined by the Courant-Friedrichs-Lewy (CFL) criterion. This   *
30  !  means that the time step must be so small that the displacement within    *
31  !  this time step is smaller than 1 grid distance. Additionally, a temporal  *
32  !  CFL criterion is introduced: the time step must be smaller than the time  *
33  !  interval of the wind fields used for interpolation.                       *
34  !  For random walk simulations, these are the only time step criteria.       *
35  !  For the other options, the time step is also limited by the Lagrangian    *
36  !  time scale.                                                               *
37  !                                                                            *
38  !     Author: A. Stohl                                                       *
39  !                                                                            *
40  !     16 December 1997                                                       *
41  !                                                                            *
42  !  Literature:                                                               *
43  !                                                                            *
44  !*****************************************************************************
45  !                                                                            *
46  ! Variables:                                                                 *
47  ! h [m]              Mixing height                                           *
48  ! lwindinterv [s]    time interval between two wind fields                   *
49  ! itime [s]          current temporal position                               *
50  ! ldt [s]            Suggested time step for next integration                *
51  ! ladvance [s]       Total integration time period                           *
52  ! rannumb(maxrand)   normally distributed random variables                   *
53  ! up,vp,wp           random velocities due to turbulence                     *
54  ! usig,vsig,wsig     uncertainties of wind velocities due to interpolation   *
55  ! usigold,vsigold,wsigold  like usig, etc., but for the last time step       *
56  ! xt,yt,zt           Next time step's spatial position of trajectory         *
57  !                                                                            *
58  !                                                                            *
59  ! Constants:                                                                 *
60  ! cfl                factor, by which the time step has to be smaller than   *
61  !                    the spatial CFL-criterion                               *
62  ! cflt               factor, by which the time step has to be smaller than   *
63  !                    the temporal CFL-criterion                              *
64  !                                                                            *
65  !*****************************************************************************
66
67  use par_mod
68  use com_mod
69  use interpol_mod
70  use hanna_mod
71  use random_mod, only: ran3
72
73  implicit none
74
75  integer :: itime
76  integer :: ldt,nrand
77  integer(kind=2) :: icbt
78  real :: zt,dz,dz1,dz2,up,vp,wp,usigold,vsigold,wsigold
79  real(kind=dp) :: xt,yt
80  save idummy
81
82  integer :: idummy = -7
83
84  icbt=1           ! initialize particle to "no reflection"
85
86  nrand=int(ran3(idummy)*real(maxrand-1))+1
87
88
89  !******************************
90  ! 2. Interpolate necessary data
91  !******************************
92
93  ! Compute maximum mixing height around particle position
94  !*******************************************************
95
96  ix=int(xt)
97  jy=int(yt)
98  ixp=ix+1
99  jyp=jy+1
100
101  h=max(hmix(ix ,jy,1,memind(1)), &
102       hmix(ixp,jy ,1,memind(1)), &
103       hmix(ix ,jyp,1,memind(1)), &
104       hmix(ixp,jyp,1,memind(1)), &
105       hmix(ix ,jy ,1,memind(2)), &
106       hmix(ixp,jy ,1,memind(2)), &
107       hmix(ix ,jyp,1,memind(2)), &
108       hmix(ixp,jyp,1,memind(2)))
109
110  zeta=zt/h
111
112
113  !*************************************************************
114  ! If particle is in the PBL, interpolate once and then make a
115  ! time loop until end of interval is reached
116  !*************************************************************
117
118  if (zeta.le.1.) then
119
120    call interpol_all(itime,real(xt),real(yt),zt)
121
122
123  ! Vertical interpolation of u,v,w,rho and drhodz
124  !***********************************************
125
126  ! Vertical distance to the level below and above current position
127  ! both in terms of (u,v) and (w) fields
128  !****************************************************************
129
130    dz1=zt-height(indz)
131    dz2=height(indzp)-zt
132    dz=1./(dz1+dz2)
133
134    u=(dz1*uprof(indzp)+dz2*uprof(indz))*dz
135    v=(dz1*vprof(indzp)+dz2*vprof(indz))*dz
136    w=(dz1*wprof(indzp)+dz2*wprof(indz))*dz
137
138
139  ! Compute the turbulent disturbances
140
141  ! Determine the sigmas and the timescales
142  !****************************************
143
144    if (turbswitch) then
145      call hanna(zt)
146    else
147      call hanna1(zt)
148    endif
149
150
151  ! Determine the new diffusivity velocities
152  !*****************************************
153
154    if (nrand+2.gt.maxrand) nrand=1
155    up=rannumb(nrand)*sigu
156    vp=rannumb(nrand+1)*sigv
157    wp=rannumb(nrand+2)
158    if (.not.turbswitch) then     ! modified by mc
159      wp=wp*sigw
160    else if (cblflag.eq.1) then   ! modified by mc
161      if(-h/ol.gt.5) then
162!if (ol.lt.0.) then
163!if (ol.gt.0.) then !by mc : only for test correct is lt.0
164        call initialize_cbl_vel(idummy,zt,ust,wst,h,sigw,wp,ol)
165      else
166        wp=wp*sigw
167      end if
168    end if
169
170
171  ! Determine time step for next integration
172  !*****************************************
173
174    if (turbswitch) then
175      ldt=int(min(tlw,h/max(2.*abs(wp*sigw),1.e-5), &
176           0.5/abs(dsigwdz),600.)*ctl)
177    else
178      ldt=int(min(tlw,h/max(2.*abs(wp),1.e-5),600.)*ctl)
179    endif
180    ldt=max(ldt,mintime)
181
182
183    usig=(usigprof(indzp)+usigprof(indz))/2.
184    vsig=(vsigprof(indzp)+vsigprof(indz))/2.
185    wsig=(wsigprof(indzp)+wsigprof(indz))/2.
186
187  else
188
189
190
191  !**********************************************************
192  ! For all particles that are outside the PBL, make a single
193  ! time step. Only horizontal turbulent disturbances are
194  ! calculated. Vertical disturbances are reset.
195  !**********************************************************
196
197
198  ! Interpolate the wind
199  !*********************
200
201    call interpol_wind(itime,real(xt),real(yt),zt)
202
203
204  ! Compute everything for above the PBL
205
206  ! Assume constant turbulent perturbations
207  !****************************************
208
209    ldt=abs(lsynctime)
210
211    if (nrand+1.gt.maxrand) nrand=1
212    up=rannumb(nrand)*0.3
213    vp=rannumb(nrand+1)*0.3
214    nrand=nrand+2
215    wp=0.
216    sigw=0.
217
218  endif
219
220  !****************************************************************
221  ! Add mesoscale random disturbances
222  ! This is done only once for the whole lsynctime interval to save
223  ! computation time
224  !****************************************************************
225
226
227  ! It is assumed that the average interpolation error is 1/2 sigma
228  ! of the surrounding points, autocorrelation time constant is
229  ! 1/2 of time interval between wind fields
230  !****************************************************************
231
232  if (nrand+2.gt.maxrand) nrand=1
233  usigold=rannumb(nrand)*usig
234  vsigold=rannumb(nrand+1)*vsig
235  wsigold=rannumb(nrand+2)*wsig
236
237end subroutine initialize
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG