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