source: flexpart.git/src/interpol_all_nests.f90

10.4.1_peseiGFS_025bugfixes+enhancementsdevrelease-10release-10.4.1scaling-bug
Last change on this file was 92fab65, checked in by Ignacio Pisso <ip@…>, 4 years ago

add SPDX-License-Identifier to all .f90 files

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