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