source: flexpart.git/src/interpol_misslev_nests.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.9 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_nests(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  !                                                                            *
14  !*****************************************************************************
15  !                                                                            *
16  ! Variables:                                                                 *
17  ! n                  level                                                   *
18  !                                                                            *
19  ! Constants:                                                                 *
20  !                                                                            *
21  !*****************************************************************************
22
23  use par_mod
24  use com_mod
25  use interpol_mod
26  use hanna_mod
27
28  implicit none
29
30  ! Auxiliary variables needed for interpolation
31  real :: y1(2),y2(2),y3(2),rho1(2),rhograd1(2)
32  real :: usl,vsl,wsl,usq,vsq,wsq,xaux
33  integer :: m,n,indexh
34  real,parameter :: eps=1.0e-30
35
36
37  !********************************************
38  ! Multilinear interpolation in time and space
39  !********************************************
40
41
42  !**************************************
43  ! 1.) Bilinear horizontal interpolation
44  ! 2.) Temporal interpolation (linear)
45  !**************************************
46
47  ! Loop over 2 time steps
48  !***********************
49
50  usl=0.
51  vsl=0.
52  wsl=0.
53  usq=0.
54  vsq=0.
55  wsq=0.
56  do m=1,2
57    indexh=memind(m)
58    y1(m)=p1*uun(ix ,jy ,n,indexh,ngrid) &
59         +p2*uun(ixp,jy ,n,indexh,ngrid) &
60         +p3*uun(ix ,jyp,n,indexh,ngrid) &
61         +p4*uun(ixp,jyp,n,indexh,ngrid)
62    y2(m)=p1*vvn(ix ,jy ,n,indexh,ngrid) &
63         +p2*vvn(ixp,jy ,n,indexh,ngrid) &
64         +p3*vvn(ix ,jyp,n,indexh,ngrid) &
65         +p4*vvn(ixp,jyp,n,indexh,ngrid)
66    y3(m)=p1*wwn(ix ,jy ,n,indexh,ngrid) &
67         +p2*wwn(ixp,jy ,n,indexh,ngrid) &
68         +p3*wwn(ix ,jyp,n,indexh,ngrid) &
69         +p4*wwn(ixp,jyp,n,indexh,ngrid)
70    rho1(m)=p1*rhon(ix ,jy ,n,indexh,ngrid) &
71         +p2*rhon(ixp,jy ,n,indexh,ngrid) &
72         +p3*rhon(ix ,jyp,n,indexh,ngrid) &
73         +p4*rhon(ixp,jyp,n,indexh,ngrid)
74    rhograd1(m)=p1*drhodzn(ix ,jy ,n,indexh,ngrid) &
75         +p2*drhodzn(ixp,jy ,n,indexh,ngrid) &
76         +p3*drhodzn(ix ,jyp,n,indexh,ngrid) &
77         +p4*drhodzn(ixp,jyp,n,indexh,ngrid)
78
79     usl=usl+uun(ix ,jy ,n,indexh,ngrid)+uun(ixp,jy ,n,indexh,ngrid) &
80          +uun(ix ,jyp,n,indexh,ngrid)+uun(ixp,jyp,n,indexh,ngrid)
81     vsl=vsl+vvn(ix ,jy ,n,indexh,ngrid)+vvn(ixp,jy ,n,indexh,ngrid) &
82          +vvn(ix ,jyp,n,indexh,ngrid)+vvn(ixp,jyp,n,indexh,ngrid)
83     wsl=wsl+wwn(ix ,jy ,n,indexh,ngrid)+wwn(ixp,jy ,n,indexh,ngrid) &
84          +wwn(ix ,jyp,n,indexh,ngrid)+wwn(ixp,jyp,n,indexh,ngrid)
85
86    usq=usq+uun(ix ,jy ,n,indexh,ngrid)*uun(ix ,jy ,n,indexh,ngrid)+ &
87         uun(ixp,jy ,n,indexh,ngrid)*uun(ixp,jy ,n,indexh,ngrid)+ &
88         uun(ix ,jyp,n,indexh,ngrid)*uun(ix ,jyp,n,indexh,ngrid)+ &
89         uun(ixp,jyp,n,indexh,ngrid)*uun(ixp,jyp,n,indexh,ngrid)
90    vsq=vsq+vvn(ix ,jy ,n,indexh,ngrid)*vvn(ix ,jy ,n,indexh,ngrid)+ &
91         vvn(ixp,jy ,n,indexh,ngrid)*vvn(ixp,jy ,n,indexh,ngrid)+ &
92         vvn(ix ,jyp,n,indexh,ngrid)*vvn(ix ,jyp,n,indexh,ngrid)+ &
93         vvn(ixp,jyp,n,indexh,ngrid)*vvn(ixp,jyp,n,indexh,ngrid)
94    wsq=wsq+wwn(ix ,jy ,n,indexh,ngrid)*wwn(ix ,jy ,n,indexh,ngrid)+ &
95         wwn(ixp,jy ,n,indexh,ngrid)*wwn(ixp,jy ,n,indexh,ngrid)+ &
96         wwn(ix ,jyp,n,indexh,ngrid)*wwn(ix ,jyp,n,indexh,ngrid)+ &
97         wwn(ixp,jyp,n,indexh,ngrid)*wwn(ixp,jyp,n,indexh,ngrid)
98  end do
99  uprof(n)=(y1(1)*dt2+y1(2)*dt1)*dtt
100  vprof(n)=(y2(1)*dt2+y2(2)*dt1)*dtt
101  wprof(n)=(y3(1)*dt2+y3(2)*dt1)*dtt
102  rhoprof(n)=(rho1(1)*dt2+rho1(2)*dt1)*dtt
103  rhogradprof(n)=(rhograd1(1)*dt2+rhograd1(2)*dt1)*dtt
104  indzindicator(n)=.false.
105
106  ! Compute standard deviations
107  !****************************
108
109  xaux=usq-usl*usl/8.
110  if (xaux.lt.eps) then
111    usigprof(n)=0.
112  else
113    usigprof(n)=sqrt(xaux/7.)
114  endif
115
116  xaux=vsq-vsl*vsl/8.
117  if (xaux.lt.eps) then
118    vsigprof(n)=0.
119  else
120    vsigprof(n)=sqrt(xaux/7.)
121  endif
122
123
124  xaux=wsq-wsl*wsl/8.
125  if (xaux.lt.eps) then
126    wsigprof(n)=0.
127  else
128    wsigprof(n)=sqrt(xaux/7.)
129  endif
130
131end subroutine interpol_misslev_nests
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG