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