CTBTO FLEXPART WO4 (2015-10-15)
 All Classes Files Functions Variables
interpol_all_nests.f90
Go to the documentation of this file.
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 
22 subroutine interpol_all_nests(itime,xt,yt,zt)
23  ! i i i i
24  !*****************************************************************************
25  ! *
26  ! This subroutine interpolates everything that is needed for calculating the*
27  ! dispersion. *
28  ! Version for interpolating nested grids. *
29  ! *
30  ! Author: A. Stohl *
31  ! *
32  ! 9 February 1999 *
33  ! 16 December 1997 *
34  ! *
35  ! Revision March 2005 by AST : all output variables in common block cal- *
36  ! culation of standard deviation done in this *
37  ! routine rather than subroutine call in order *
38  ! to save computation time *
39  ! *
40  !*****************************************************************************
41  ! *
42  ! Variables: *
43  ! itime [s] current temporal position *
44  ! memtime(3) [s] times of the wind fields in memory *
45  ! xt,yt,zt coordinates position for which wind data shall be *
46  ! calculated *
47  ! *
48  ! Constants: *
49  ! *
50  !*****************************************************************************
51 
52  use par_mod
53  use com_mod
54  use interpol_mod
55  use hanna_mod
56 
57  implicit none
58 
59  integer :: itime
60  real :: xt,yt,zt
61 
62  ! Auxiliary variables needed for interpolation
63  real :: ust1(2),wst1(2),oli1(2),oliaux
64  real :: y1(2),y2(2),y3(2),rho1(2),rhograd1(2)
65  real :: usl,vsl,wsl,usq,vsq,wsq,xaux
66  integer :: i,m,n,indexh
67  real,parameter :: eps=1.0e-30
68 
69 
70  !********************************************
71  ! Multilinear interpolation in time and space
72  !********************************************
73 
74  ! Determine the lower left corner and its distance to the current position
75  !*************************************************************************
76 
77  ddx=xt-real(ix)
78  ddy=yt-real(jy)
79  rddx=1.-ddx
80  rddy=1.-ddy
81  p1=rddx*rddy
82  p2=ddx*rddy
83  p3=rddx*ddy
84  p4=ddx*ddy
85 
86  ! Calculate variables for time interpolation
87  !*******************************************
88 
89  dt1=real(itime-memtime(1))
90  dt2=real(memtime(2)-itime)
91  dtt=1./(dt1+dt2)
92 
93 
94  !*****************************************
95  ! 1. Interpolate u*, w* and Obukhov length
96  !*****************************************
97 
98  ! a) Bilinear horizontal interpolation
99 
100  do m=1,2
101  indexh=memind(m)
102 
103  ust1(m)=p1*ustarn(ix ,jy ,1,indexh,ngrid) &
104  + p2*ustarn(ixp,jy ,1,indexh,ngrid) &
105  + p3*ustarn(ix ,jyp,1,indexh,ngrid) &
106  + p4*ustarn(ixp,jyp,1,indexh,ngrid)
107  wst1(m)=p1*wstarn(ix ,jy ,1,indexh,ngrid) &
108  + p2*wstarn(ixp,jy ,1,indexh,ngrid) &
109  + p3*wstarn(ix ,jyp,1,indexh,ngrid) &
110  + p4*wstarn(ixp,jyp,1,indexh,ngrid)
111  oli1(m)=p1*olin(ix ,jy ,1,indexh,ngrid) &
112  + p2*olin(ixp,jy ,1,indexh,ngrid) &
113  + p3*olin(ix ,jyp,1,indexh,ngrid) &
114  + p4*olin(ixp,jyp,1,indexh,ngrid)
115  end do
116 
117  ! b) Temporal interpolation
118 
119  ust=(ust1(1)*dt2+ust1(2)*dt1)*dtt
120  wst=(wst1(1)*dt2+wst1(2)*dt1)*dtt
121  oliaux=(oli1(1)*dt2+oli1(2)*dt1)*dtt
122 
123  if (oliaux.ne.0.) then
124  ol=1./oliaux
125  else
126  ol=99999.
127  endif
128 
129 
130  !*****************************************************
131  ! 2. Interpolate vertical profiles of u,v,w,rho,drhodz
132  !*****************************************************
133 
134 
135  ! Determine the level below the current position
136  !***********************************************
137 
138  do i=2,nz
139  if (height(i).gt.zt) then
140  indz=i-1
141  indzp=i
142  goto 6
143  endif
144  end do
145 6 continue
146 
147  !**************************************
148  ! 1.) Bilinear horizontal interpolation
149  ! 2.) Temporal interpolation (linear)
150  !**************************************
151 
152  ! Loop over 2 time steps and indz levels
153  !***************************************
154 
155  do n=indz,indz+1
156  usl=0.
157  vsl=0.
158  wsl=0.
159  usq=0.
160  vsq=0.
161  wsq=0.
162  do m=1,2
163  indexh=memind(m)
164  y1(m)=p1*uun(ix ,jy ,n,indexh,ngrid) &
165  +p2*uun(ixp,jy ,n,indexh,ngrid) &
166  +p3*uun(ix ,jyp,n,indexh,ngrid) &
167  +p4*uun(ixp,jyp,n,indexh,ngrid)
168  y2(m)=p1*vvn(ix ,jy ,n,indexh,ngrid) &
169  +p2*vvn(ixp,jy ,n,indexh,ngrid) &
170  +p3*vvn(ix ,jyp,n,indexh,ngrid) &
171  +p4*vvn(ixp,jyp,n,indexh,ngrid)
172  y3(m)=p1*wwn(ix ,jy ,n,indexh,ngrid) &
173  +p2*wwn(ixp,jy ,n,indexh,ngrid) &
174  +p3*wwn(ix ,jyp,n,indexh,ngrid) &
175  +p4*wwn(ixp,jyp,n,indexh,ngrid)
176  rhograd1(m)=p1*drhodzn(ix ,jy ,n,indexh,ngrid) &
177  +p2*drhodzn(ixp,jy ,n,indexh,ngrid) &
178  +p3*drhodzn(ix ,jyp,n,indexh,ngrid) &
179  +p4*drhodzn(ixp,jyp,n,indexh,ngrid)
180  rho1(m)=p1*rhon(ix ,jy ,n,indexh,ngrid) &
181  +p2*rhon(ixp,jy ,n,indexh,ngrid) &
182  +p3*rhon(ix ,jyp,n,indexh,ngrid) &
183  +p4*rhon(ixp,jyp,n,indexh,ngrid)
184 
185  usl=usl+uun(ix ,jy ,n,indexh,ngrid)+uun(ixp,jy ,n,indexh,ngrid) &
186  +uun(ix ,jyp,n,indexh,ngrid)+uun(ixp,jyp,n,indexh,ngrid)
187  vsl=vsl+vvn(ix ,jy ,n,indexh,ngrid)+vvn(ixp,jy ,n,indexh,ngrid) &
188  +vvn(ix ,jyp,n,indexh,ngrid)+vvn(ixp,jyp,n,indexh,ngrid)
189  wsl=wsl+wwn(ix ,jy ,n,indexh,ngrid)+wwn(ixp,jy ,n,indexh,ngrid) &
190  +wwn(ix ,jyp,n,indexh,ngrid)+wwn(ixp,jyp,n,indexh,ngrid)
191 
192  usq=usq+uun(ix ,jy ,n,indexh,ngrid)*uun(ix ,jy ,n,indexh,ngrid)+ &
193  uun(ixp,jy ,n,indexh,ngrid)*uun(ixp,jy ,n,indexh,ngrid)+ &
194  uun(ix ,jyp,n,indexh,ngrid)*uun(ix ,jyp,n,indexh,ngrid)+ &
195  uun(ixp,jyp,n,indexh,ngrid)*uun(ixp,jyp,n,indexh,ngrid)
196  vsq=vsq+vvn(ix ,jy ,n,indexh,ngrid)*vvn(ix ,jy ,n,indexh,ngrid)+ &
197  vvn(ixp,jy ,n,indexh,ngrid)*vvn(ixp,jy ,n,indexh,ngrid)+ &
198  vvn(ix ,jyp,n,indexh,ngrid)*vvn(ix ,jyp,n,indexh,ngrid)+ &
199  vvn(ixp,jyp,n,indexh,ngrid)*vvn(ixp,jyp,n,indexh,ngrid)
200  wsq=wsq+wwn(ix ,jy ,n,indexh,ngrid)*wwn(ix ,jy ,n,indexh,ngrid)+ &
201  wwn(ixp,jy ,n,indexh,ngrid)*wwn(ixp,jy ,n,indexh,ngrid)+ &
202  wwn(ix ,jyp,n,indexh,ngrid)*wwn(ix ,jyp,n,indexh,ngrid)+ &
203  wwn(ixp,jyp,n,indexh,ngrid)*wwn(ixp,jyp,n,indexh,ngrid)
204  end do
205  uprof(n)=(y1(1)*dt2+y1(2)*dt1)*dtt
206  vprof(n)=(y2(1)*dt2+y2(2)*dt1)*dtt
207  wprof(n)=(y3(1)*dt2+y3(2)*dt1)*dtt
208  rhoprof(n)=(rho1(1)*dt2+rho1(2)*dt1)*dtt
209  rhogradprof(n)=(rhograd1(1)*dt2+rhograd1(2)*dt1)*dtt
210  indzindicator(n)=.false.
211 
212  ! Compute standard deviations
213  !****************************
214 
215  xaux=usq-usl*usl/8.
216  if (xaux.lt.eps) then
217  usigprof(n)=0.
218  else
219  usigprof(n)=sqrt(xaux/7.)
220  endif
221 
222  xaux=vsq-vsl*vsl/8.
223  if (xaux.lt.eps) then
224  vsigprof(n)=0.
225  else
226  vsigprof(n)=sqrt(xaux/7.)
227  endif
228 
229 
230  xaux=wsq-wsl*wsl/8.
231  if (xaux.lt.eps) then
232  wsigprof(n)=0.
233  else
234  wsigprof(n)=sqrt(xaux/7.)
235  endif
236 
237  end do
238 
239 end subroutine interpol_all_nests
subroutine interpol_all_nests(itime, xt, yt, zt)