source: flexpart.git/src/interpol_wind.f90 @ 3481cc1

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

move license from headers to a different file

  • Property mode set to 100644
File size: 7.6 KB
Line 
1subroutine interpol_wind(itime,xt,yt,zt)
2  !                           i   i  i  i
3  !*****************************************************************************
4  !                                                                            *
5  !  This subroutine interpolates the wind data to current trajectory position.*
6  !                                                                            *
7  !    Author: A. Stohl                                                        *
8  !                                                                            *
9  !    16 December 1997                                                        *
10  !                                                                            *
11  !  Revision March 2005 by AST : all output variables in common block cal-    *
12  !                               culation of standard deviation done in this  *
13  !                               routine rather than subroutine call in order *
14  !                               to save computation time                     *
15  !                                                                            *
16  !*****************************************************************************
17  !                                                                            *
18  ! Variables:                                                                 *
19  ! u,v,w              wind components                                         *
20  ! itime [s]          current temporal position                               *
21  ! memtime(3) [s]     times of the wind fields in memory                      *
22  ! xt,yt,zt           coordinates position for which wind data shall be       *
23  !                    calculated                                              *
24  !                                                                            *
25  ! Constants:                                                                 *
26  !                                                                            *
27  !*****************************************************************************
28
29  use par_mod
30  use com_mod
31  use interpol_mod
32
33  implicit none
34
35  integer :: itime
36  real :: xt,yt,zt
37
38  ! Auxiliary variables needed for interpolation
39  real :: dz1,dz2,dz
40  real :: u1(2),v1(2),w1(2),uh(2),vh(2),wh(2)
41  real :: usl,vsl,wsl,usq,vsq,wsq,xaux
42  integer :: i,m,n,indexh,indzh
43  real,parameter :: eps=1.0e-30
44
45
46  !********************************************
47  ! Multilinear interpolation in time and space
48  !********************************************
49
50  ! Determine the lower left corner and its distance to the current position
51  !*************************************************************************
52
53  ddx=xt-real(ix)
54  ddy=yt-real(jy)
55  rddx=1.-ddx
56  rddy=1.-ddy
57  p1=rddx*rddy
58  p2=ddx*rddy
59  p3=rddx*ddy
60  p4=ddx*ddy
61
62  ! Calculate variables for time interpolation
63  !*******************************************
64
65  dt1=real(itime-memtime(1))
66  dt2=real(memtime(2)-itime)
67  dtt=1./(dt1+dt2)
68
69  ! Determine the level below the current position for u,v
70  !*******************************************************
71
72  do i=2,nz
73    if (height(i).gt.zt) then
74      indz=i-1
75      goto 6
76    endif
77  end do
786   continue
79
80
81  ! Vertical distance to the level below and above current position
82  !****************************************************************
83
84  dz=1./(height(indz+1)-height(indz))
85  dz1=(zt-height(indz))*dz
86  dz2=(height(indz+1)-zt)*dz
87
88  !**********************************************************************
89  ! 1.) Bilinear horizontal interpolation
90  ! This has to be done separately for 6 fields (Temporal(2)*Vertical(3))
91  !**********************************************************************
92
93  ! Loop over 2 time steps and 2 levels
94  !************************************
95
96  usl=0.
97  vsl=0.
98  wsl=0.
99  usq=0.
100  vsq=0.
101  wsq=0.
102  do m=1,2
103    indexh=memind(m)
104    do n=1,2
105      indzh=indz+n-1
106
107      if (ngrid.lt.0) then
108        u1(n)=p1*uupol(ix ,jy ,indzh,indexh) &
109             +p2*uupol(ixp,jy ,indzh,indexh) &
110             +p3*uupol(ix ,jyp,indzh,indexh) &
111             +p4*uupol(ixp,jyp,indzh,indexh)
112        v1(n)=p1*vvpol(ix ,jy ,indzh,indexh) &
113             +p2*vvpol(ixp,jy ,indzh,indexh) &
114             +p3*vvpol(ix ,jyp,indzh,indexh) &
115             +p4*vvpol(ixp,jyp,indzh,indexh)
116        usl=usl+uupol(ix ,jy ,indzh,indexh)+ &
117             uupol(ixp,jy ,indzh,indexh) &
118             +uupol(ix ,jyp,indzh,indexh)+uupol(ixp,jyp,indzh,indexh)
119        vsl=vsl+vvpol(ix ,jy ,indzh,indexh)+ &
120             vvpol(ixp,jy ,indzh,indexh) &
121             +vvpol(ix ,jyp,indzh,indexh)+vvpol(ixp,jyp,indzh,indexh)
122
123        usq=usq+uupol(ix ,jy ,indzh,indexh)* &
124             uupol(ix ,jy ,indzh,indexh)+ &
125             uupol(ixp,jy ,indzh,indexh)*uupol(ixp,jy ,indzh,indexh)+ &
126             uupol(ix ,jyp,indzh,indexh)*uupol(ix ,jyp,indzh,indexh)+ &
127             uupol(ixp,jyp,indzh,indexh)*uupol(ixp,jyp,indzh,indexh)
128        vsq=vsq+vvpol(ix ,jy ,indzh,indexh)* &
129             vvpol(ix ,jy ,indzh,indexh)+ &
130             vvpol(ixp,jy ,indzh,indexh)*vvpol(ixp,jy ,indzh,indexh)+ &
131             vvpol(ix ,jyp,indzh,indexh)*vvpol(ix ,jyp,indzh,indexh)+ &
132             vvpol(ixp,jyp,indzh,indexh)*vvpol(ixp,jyp,indzh,indexh)
133      else
134        u1(n)=p1*uu(ix ,jy ,indzh,indexh) &
135             +p2*uu(ixp,jy ,indzh,indexh) &
136             +p3*uu(ix ,jyp,indzh,indexh) &
137             +p4*uu(ixp,jyp,indzh,indexh)
138        v1(n)=p1*vv(ix ,jy ,indzh,indexh) &
139             +p2*vv(ixp,jy ,indzh,indexh) &
140             +p3*vv(ix ,jyp,indzh,indexh) &
141             +p4*vv(ixp,jyp,indzh,indexh)
142        usl=usl+uu(ix ,jy ,indzh,indexh)+uu(ixp,jy ,indzh,indexh) &
143             +uu(ix ,jyp,indzh,indexh)+uu(ixp,jyp,indzh,indexh)
144        vsl=vsl+vv(ix ,jy ,indzh,indexh)+vv(ixp,jy ,indzh,indexh) &
145             +vv(ix ,jyp,indzh,indexh)+vv(ixp,jyp,indzh,indexh)
146
147        usq=usq+uu(ix ,jy ,indzh,indexh)*uu(ix ,jy ,indzh,indexh)+ &
148             uu(ixp,jy ,indzh,indexh)*uu(ixp,jy ,indzh,indexh)+ &
149             uu(ix ,jyp,indzh,indexh)*uu(ix ,jyp,indzh,indexh)+ &
150             uu(ixp,jyp,indzh,indexh)*uu(ixp,jyp,indzh,indexh)
151        vsq=vsq+vv(ix ,jy ,indzh,indexh)*vv(ix ,jy ,indzh,indexh)+ &
152             vv(ixp,jy ,indzh,indexh)*vv(ixp,jy ,indzh,indexh)+ &
153             vv(ix ,jyp,indzh,indexh)*vv(ix ,jyp,indzh,indexh)+ &
154             vv(ixp,jyp,indzh,indexh)*vv(ixp,jyp,indzh,indexh)
155      endif
156      w1(n)=p1*ww(ix ,jy ,indzh,indexh) &
157           +p2*ww(ixp,jy ,indzh,indexh) &
158           +p3*ww(ix ,jyp,indzh,indexh) &
159           +p4*ww(ixp,jyp,indzh,indexh)
160      wsl=wsl+ww(ix ,jy ,indzh,indexh)+ww(ixp,jy ,indzh,indexh) &
161           +ww(ix ,jyp,indzh,indexh)+ww(ixp,jyp,indzh,indexh)
162      wsq=wsq+ww(ix ,jy ,indzh,indexh)*ww(ix ,jy ,indzh,indexh)+ &
163           ww(ixp,jy ,indzh,indexh)*ww(ixp,jy ,indzh,indexh)+ &
164           ww(ix ,jyp,indzh,indexh)*ww(ix ,jyp,indzh,indexh)+ &
165           ww(ixp,jyp,indzh,indexh)*ww(ixp,jyp,indzh,indexh)
166    end do
167
168
169  !**********************************
170  ! 2.) Linear vertical interpolation
171  !**********************************
172
173    uh(m)=dz2*u1(1)+dz1*u1(2)
174    vh(m)=dz2*v1(1)+dz1*v1(2)
175    wh(m)=dz2*w1(1)+dz1*w1(2)
176  end do
177
178
179  !************************************
180  ! 3.) Temporal interpolation (linear)
181  !************************************
182
183  u=(uh(1)*dt2+uh(2)*dt1)*dtt
184  v=(vh(1)*dt2+vh(2)*dt1)*dtt
185  w=(wh(1)*dt2+wh(2)*dt1)*dtt
186
187
188  ! Compute standard deviations
189  !****************************
190
191  xaux=usq-usl*usl/16.
192  if (xaux.lt.eps) then
193    usig=0.
194  else
195    usig=sqrt(xaux/15.)
196  endif
197
198  xaux=vsq-vsl*vsl/16.
199  if (xaux.lt.eps) then
200    vsig=0.
201  else
202    vsig=sqrt(xaux/15.)
203  endif
204
205
206  xaux=wsq-wsl*wsl/16.
207  if (xaux.lt.eps) then
208    wsig=0.
209  else
210    wsig=sqrt(xaux/15.)
211  endif
212
213end subroutine interpol_wind
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG