source: flexpart.git/src/interpol_misslev.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: 6.1 KB
Line 
1! SPDX-FileCopyrightText: FLEXPART 1998-2019, see flexpart_license.txt
2! SPDX-License-Identifier: GPL-3.0-or-later
3
4subroutine interpol_misslev(n)
5  !                            i
6  !*****************************************************************************
7  !                                                                            *
8  !  This subroutine interpolates u,v,w, density and density gradients.        *
9  !                                                                            *
10  !    Author: A. Stohl                                                        *
11  !                                                                            *
12  !    16 December 1997                                                        *
13  !    Update: 2 March 1999                                                    *
14  !                                                                            *
15  !  Revision March 2005 by AST : all output variables in common block cal-    *
16  !                               culation of standard deviation done in this  *
17  !                               routine rather than subroutine call in order *
18  !                               to save computation time                     *
19  !                                                                            *
20  !*****************************************************************************
21  !                                                                            *
22  ! Variables:                                                                 *
23  ! n                  level                                                   *
24  !                                                                            *
25  ! Constants:                                                                 *
26  !                                                                            *
27  !*****************************************************************************
28
29  use par_mod
30  use com_mod
31  use interpol_mod
32  use hanna_mod
33
34  implicit none
35
36  ! Auxiliary variables needed for interpolation
37  real :: y1(2),y2(2),y3(2),rho1(2),rhograd1(2)
38  real :: usl,vsl,wsl,usq,vsq,wsq,xaux
39  integer :: m,n,indexh
40  real,parameter :: eps=1.0e-30
41
42
43  !********************************************
44  ! Multilinear interpolation in time and space
45  !********************************************
46
47
48  !**************************************
49  ! 1.) Bilinear horizontal interpolation
50  ! 2.) Temporal interpolation (linear)
51  !**************************************
52
53  ! Loop over 2 time steps
54  !***********************
55
56  usl=0.
57  vsl=0.
58  wsl=0.
59  usq=0.
60  vsq=0.
61  wsq=0.
62  do m=1,2
63    indexh=memind(m)
64    if (ngrid.lt.0) then
65      y1(m)=p1*uupol(ix ,jy ,n,indexh) &
66           +p2*uupol(ixp,jy ,n,indexh) &
67           +p3*uupol(ix ,jyp,n,indexh) &
68           +p4*uupol(ixp,jyp,n,indexh)
69      y2(m)=p1*vvpol(ix ,jy ,n,indexh) &
70           +p2*vvpol(ixp,jy ,n,indexh) &
71           +p3*vvpol(ix ,jyp,n,indexh) &
72           +p4*vvpol(ixp,jyp,n,indexh)
73        usl=usl+uupol(ix ,jy ,n,indexh)+uupol(ixp,jy ,n,indexh) &
74             +uupol(ix ,jyp,n,indexh)+uupol(ixp,jyp,n,indexh)
75        vsl=vsl+vvpol(ix ,jy ,n,indexh)+vvpol(ixp,jy ,n,indexh) &
76             +vvpol(ix ,jyp,n,indexh)+vvpol(ixp,jyp,n,indexh)
77
78        usq=usq+uupol(ix ,jy ,n,indexh)*uupol(ix ,jy ,n,indexh)+ &
79             uupol(ixp,jy ,n,indexh)*uupol(ixp,jy ,n,indexh)+ &
80             uupol(ix ,jyp,n,indexh)*uupol(ix ,jyp,n,indexh)+ &
81             uupol(ixp,jyp,n,indexh)*uupol(ixp,jyp,n,indexh)
82        vsq=vsq+vvpol(ix ,jy ,n,indexh)*vvpol(ix ,jy ,n,indexh)+ &
83             vvpol(ixp,jy ,n,indexh)*vvpol(ixp,jy ,n,indexh)+ &
84             vvpol(ix ,jyp,n,indexh)*vvpol(ix ,jyp,n,indexh)+ &
85             vvpol(ixp,jyp,n,indexh)*vvpol(ixp,jyp,n,indexh)
86    else
87      y1(m)=p1*uu(ix ,jy ,n,indexh) &
88           +p2*uu(ixp,jy ,n,indexh) &
89           +p3*uu(ix ,jyp,n,indexh) &
90           +p4*uu(ixp,jyp,n,indexh)
91      y2(m)=p1*vv(ix ,jy ,n,indexh) &
92           +p2*vv(ixp,jy ,n,indexh) &
93           +p3*vv(ix ,jyp,n,indexh) &
94           +p4*vv(ixp,jyp,n,indexh)
95      usl=usl+uu(ix ,jy ,n,indexh)+uu(ixp,jy ,n,indexh) &
96           +uu(ix ,jyp,n,indexh)+uu(ixp,jyp,n,indexh)
97      vsl=vsl+vv(ix ,jy ,n,indexh)+vv(ixp,jy ,n,indexh) &
98           +vv(ix ,jyp,n,indexh)+vv(ixp,jyp,n,indexh)
99
100      usq=usq+uu(ix ,jy ,n,indexh)*uu(ix ,jy ,n,indexh)+ &
101           uu(ixp,jy ,n,indexh)*uu(ixp,jy ,n,indexh)+ &
102           uu(ix ,jyp,n,indexh)*uu(ix ,jyp,n,indexh)+ &
103           uu(ixp,jyp,n,indexh)*uu(ixp,jyp,n,indexh)
104      vsq=vsq+vv(ix ,jy ,n,indexh)*vv(ix ,jy ,n,indexh)+ &
105           vv(ixp,jy ,n,indexh)*vv(ixp,jy ,n,indexh)+ &
106           vv(ix ,jyp,n,indexh)*vv(ix ,jyp,n,indexh)+ &
107           vv(ixp,jyp,n,indexh)*vv(ixp,jyp,n,indexh)
108    endif
109    y3(m)=p1*ww(ix ,jy ,n,indexh) &
110         +p2*ww(ixp,jy ,n,indexh) &
111         +p3*ww(ix ,jyp,n,indexh) &
112         +p4*ww(ixp,jyp,n,indexh)
113    rhograd1(m)=p1*drhodz(ix ,jy ,n,indexh) &
114         +p2*drhodz(ixp,jy ,n,indexh) &
115         +p3*drhodz(ix ,jyp,n,indexh) &
116         +p4*drhodz(ixp,jyp,n,indexh)
117    rho1(m)=p1*rho(ix ,jy ,n,indexh) &
118         +p2*rho(ixp,jy ,n,indexh) &
119         +p3*rho(ix ,jyp,n,indexh) &
120         +p4*rho(ixp,jyp,n,indexh)
121    wsl=wsl+ww(ix ,jy ,n,indexh)+ww(ixp,jy ,n,indexh) &
122         +ww(ix ,jyp,n,indexh)+ww(ixp,jyp,n,indexh)
123    wsq=wsq+ww(ix ,jy ,n,indexh)*ww(ix ,jy ,n,indexh)+ &
124         ww(ixp,jy ,n,indexh)*ww(ixp,jy ,n,indexh)+ &
125         ww(ix ,jyp,n,indexh)*ww(ix ,jyp,n,indexh)+ &
126         ww(ixp,jyp,n,indexh)*ww(ixp,jyp,n,indexh)
127  end do
128  uprof(n)=(y1(1)*dt2+y1(2)*dt1)*dtt
129  vprof(n)=(y2(1)*dt2+y2(2)*dt1)*dtt
130  wprof(n)=(y3(1)*dt2+y3(2)*dt1)*dtt
131  rhoprof(n)=(rho1(1)*dt2+rho1(2)*dt1)*dtt
132  rhogradprof(n)=(rhograd1(1)*dt2+rhograd1(2)*dt1)*dtt
133  indzindicator(n)=.false.
134
135
136  ! Compute standard deviations
137  !****************************
138
139  xaux=usq-usl*usl/8.
140  if (xaux.lt.eps) then
141    usigprof(n)=0.
142  else
143    usigprof(n)=sqrt(xaux/7.)
144  endif
145
146  xaux=vsq-vsl*vsl/8.
147  if (xaux.lt.eps) then
148    vsigprof(n)=0.
149  else
150    vsigprof(n)=sqrt(xaux/7.)
151  endif
152
153
154  xaux=wsq-wsl*wsl/8.
155  if (xaux.lt.eps) then
156    wsigprof(n)=0.
157  else
158    wsigprof(n)=sqrt(xaux/7.)
159  endif
160
161
162end subroutine interpol_misslev
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG