source: flexpart.git/src/interpol_wind_short.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: 4.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_wind_short(itime,xt,yt,zt)
5!                                 i   i  i  i
6!*****************************************************************************
7!                                                                            *
8!  This subroutine interpolates the wind data to current trajectory position.*
9!                                                                            *
10!    Author: A. Stohl                                                        *
11!                                                                            *
12!    16 December 1997                                                        *
13!                                                                            *
14!  Revision March 2005 by AST : all output variables in common block         *
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, intent(in) :: itime
36  real, intent(in) :: 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  integer :: i,m,n,indexh,indzh
42
43
44  !********************************************
45  ! Multilinear interpolation in time and space
46  !********************************************
47
48  ddx=xt-real(ix)
49  ddy=yt-real(jy)
50  rddx=1.-ddx
51  rddy=1.-ddy
52  p1=rddx*rddy
53  p2=ddx*rddy
54  p3=rddx*ddy
55  p4=ddx*ddy
56
57  ! Calculate variables for time interpolation
58  !*******************************************
59
60  dt1=real(itime-memtime(1))
61  dt2=real(memtime(2)-itime)
62  dtt=1./(dt1+dt2)
63
64  ! Determine the level below the current position for u,v
65  !*******************************************************
66
67  do i=2,nz
68    if (height(i).gt.zt) then
69      indz=i-1
70      goto 6
71    endif
72  end do
736   continue
74
75
76  ! Vertical distance to the level below and above current position
77  !****************************************************************
78
79  dz=1./(height(indz+1)-height(indz))
80  dz1=(zt-height(indz))*dz
81  dz2=(height(indz+1)-zt)*dz
82
83
84  !**********************************************************************
85  ! 1.) Bilinear horizontal interpolation
86  ! This has to be done separately for 6 fields (Temporal(2)*Vertical(3))
87  !**********************************************************************
88
89  ! Loop over 2 time steps and 2 levels
90  !************************************
91
92  do m=1,2
93    indexh=memind(m)
94    do n=1,2
95      indzh=indz+n-1
96
97      if (ngrid.lt.0) then
98        u1(n)=p1*uupol(ix ,jy ,indzh,indexh) &
99             +p2*uupol(ixp,jy ,indzh,indexh) &
100             +p3*uupol(ix ,jyp,indzh,indexh) &
101             +p4*uupol(ixp,jyp,indzh,indexh)
102        v1(n)=p1*vvpol(ix ,jy ,indzh,indexh) &
103             +p2*vvpol(ixp,jy ,indzh,indexh) &
104             +p3*vvpol(ix ,jyp,indzh,indexh) &
105             +p4*vvpol(ixp,jyp,indzh,indexh)
106      else
107        u1(n)=p1*uu(ix ,jy ,indzh,indexh) &
108             +p2*uu(ixp,jy ,indzh,indexh) &
109             +p3*uu(ix ,jyp,indzh,indexh) &
110             +p4*uu(ixp,jyp,indzh,indexh)
111        v1(n)=p1*vv(ix ,jy ,indzh,indexh) &
112             +p2*vv(ixp,jy ,indzh,indexh) &
113             +p3*vv(ix ,jyp,indzh,indexh) &
114             +p4*vv(ixp,jyp,indzh,indexh)
115      endif
116      w1(n)=p1*ww(ix ,jy ,indzh,indexh) &
117           +p2*ww(ixp,jy ,indzh,indexh) &
118           +p3*ww(ix ,jyp,indzh,indexh) &
119           +p4*ww(ixp,jyp,indzh,indexh)
120    end do
121
122
123  !**********************************
124  ! 2.) Linear vertical interpolation
125  !**********************************
126
127    uh(m)=dz2*u1(1)+dz1*u1(2)
128    vh(m)=dz2*v1(1)+dz1*v1(2)
129    wh(m)=dz2*w1(1)+dz1*w1(2)
130  end do
131
132
133
134  !************************************
135  ! 3.) Temporal interpolation (linear)
136  !************************************
137
138  u=(uh(1)*dt2+uh(2)*dt1)*dtt
139  v=(vh(1)*dt2+vh(2)*dt1)*dtt
140  w=(wh(1)*dt2+wh(2)*dt1)*dtt
141
142end subroutine interpol_wind_short
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG