source: trunk/src/interpol_misslev_nests.f90 @ 28

Last change on this file since 28 was 4, checked in by mlanger, 11 years ago
File size: 6.2 KB
Line 
1!**********************************************************************
2! Copyright 1998,1999,2000,2001,2002,2005,2007,2008,2009,2010         *
3! Andreas Stohl, Petra Seibert, A. Frank, Gerhard Wotawa,             *
4! Caroline Forster, Sabine Eckhardt, John Burkhart, Harald Sodemann   *
5!                                                                     *
6! This file is part of FLEXPART.                                      *
7!                                                                     *
8! FLEXPART is free software: you can redistribute it and/or modify    *
9! it under the terms of the GNU General Public License as published by*
10! the Free Software Foundation, either version 3 of the License, or   *
11! (at your option) any later version.                                 *
12!                                                                     *
13! FLEXPART is distributed in the hope that it will be useful,         *
14! but WITHOUT ANY WARRANTY; without even the implied warranty of      *
15! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the       *
16! GNU General Public License for more details.                        *
17!                                                                     *
18! You should have received a copy of the GNU General Public License   *
19! along with FLEXPART.  If not, see <http://www.gnu.org/licenses/>.   *
20!**********************************************************************
21
22subroutine interpol_misslev_nests(n)
23  !                                  i
24  !*****************************************************************************
25  !                                                                            *
26  !  This subroutine interpolates u,v,w, density and density gradients.        *
27  !                                                                            *
28  !    Author: A. Stohl                                                        *
29  !                                                                            *
30  !    16 December 1997                                                        *
31  !                                                                            *
32  !*****************************************************************************
33  !                                                                            *
34  ! Variables:                                                                 *
35  ! n                  level                                                   *
36  !                                                                            *
37  ! Constants:                                                                 *
38  !                                                                            *
39  !*****************************************************************************
40
41  use par_mod
42  use com_mod
43  use interpol_mod
44  use hanna_mod
45
46  implicit none
47
48  ! Auxiliary variables needed for interpolation
49  real :: y1(2),y2(2),y3(2),rho1(2),rhograd1(2)
50  real :: usl,vsl,wsl,usq,vsq,wsq,xaux
51  integer :: m,n,indexh
52  real,parameter :: eps=1.0e-30
53
54
55  !********************************************
56  ! Multilinear interpolation in time and space
57  !********************************************
58
59
60  !**************************************
61  ! 1.) Bilinear horizontal interpolation
62  ! 2.) Temporal interpolation (linear)
63  !**************************************
64
65  ! Loop over 2 time steps
66  !***********************
67
68  usl=0.
69  vsl=0.
70  wsl=0.
71  usq=0.
72  vsq=0.
73  wsq=0.
74  do m=1,2
75    indexh=memind(m)
76    y1(m)=p1*uun(ix ,jy ,n,indexh,ngrid) &
77         +p2*uun(ixp,jy ,n,indexh,ngrid) &
78         +p3*uun(ix ,jyp,n,indexh,ngrid) &
79         +p4*uun(ixp,jyp,n,indexh,ngrid)
80    y2(m)=p1*vvn(ix ,jy ,n,indexh,ngrid) &
81         +p2*vvn(ixp,jy ,n,indexh,ngrid) &
82         +p3*vvn(ix ,jyp,n,indexh,ngrid) &
83         +p4*vvn(ixp,jyp,n,indexh,ngrid)
84    y3(m)=p1*wwn(ix ,jy ,n,indexh,ngrid) &
85         +p2*wwn(ixp,jy ,n,indexh,ngrid) &
86         +p3*wwn(ix ,jyp,n,indexh,ngrid) &
87         +p4*wwn(ixp,jyp,n,indexh,ngrid)
88    rho1(m)=p1*rhon(ix ,jy ,n,indexh,ngrid) &
89         +p2*rhon(ixp,jy ,n,indexh,ngrid) &
90         +p3*rhon(ix ,jyp,n,indexh,ngrid) &
91         +p4*rhon(ixp,jyp,n,indexh,ngrid)
92    rhograd1(m)=p1*drhodzn(ix ,jy ,n,indexh,ngrid) &
93         +p2*drhodzn(ixp,jy ,n,indexh,ngrid) &
94         +p3*drhodzn(ix ,jyp,n,indexh,ngrid) &
95         +p4*drhodzn(ixp,jyp,n,indexh,ngrid)
96
97     usl=usl+uun(ix ,jy ,n,indexh,ngrid)+uun(ixp,jy ,n,indexh,ngrid) &
98          +uun(ix ,jyp,n,indexh,ngrid)+uun(ixp,jyp,n,indexh,ngrid)
99     vsl=vsl+vvn(ix ,jy ,n,indexh,ngrid)+vvn(ixp,jy ,n,indexh,ngrid) &
100          +vvn(ix ,jyp,n,indexh,ngrid)+vvn(ixp,jyp,n,indexh,ngrid)
101     wsl=wsl+wwn(ix ,jy ,n,indexh,ngrid)+wwn(ixp,jy ,n,indexh,ngrid) &
102          +wwn(ix ,jyp,n,indexh,ngrid)+wwn(ixp,jyp,n,indexh,ngrid)
103
104    usq=usq+uun(ix ,jy ,n,indexh,ngrid)*uun(ix ,jy ,n,indexh,ngrid)+ &
105         uun(ixp,jy ,n,indexh,ngrid)*uun(ixp,jy ,n,indexh,ngrid)+ &
106         uun(ix ,jyp,n,indexh,ngrid)*uun(ix ,jyp,n,indexh,ngrid)+ &
107         uun(ixp,jyp,n,indexh,ngrid)*uun(ixp,jyp,n,indexh,ngrid)
108    vsq=vsq+vvn(ix ,jy ,n,indexh,ngrid)*vvn(ix ,jy ,n,indexh,ngrid)+ &
109         vvn(ixp,jy ,n,indexh,ngrid)*vvn(ixp,jy ,n,indexh,ngrid)+ &
110         vvn(ix ,jyp,n,indexh,ngrid)*vvn(ix ,jyp,n,indexh,ngrid)+ &
111         vvn(ixp,jyp,n,indexh,ngrid)*vvn(ixp,jyp,n,indexh,ngrid)
112    wsq=wsq+wwn(ix ,jy ,n,indexh,ngrid)*wwn(ix ,jy ,n,indexh,ngrid)+ &
113         wwn(ixp,jy ,n,indexh,ngrid)*wwn(ixp,jy ,n,indexh,ngrid)+ &
114         wwn(ix ,jyp,n,indexh,ngrid)*wwn(ix ,jyp,n,indexh,ngrid)+ &
115         wwn(ixp,jyp,n,indexh,ngrid)*wwn(ixp,jyp,n,indexh,ngrid)
116  end do
117  uprof(n)=(y1(1)*dt2+y1(2)*dt1)*dtt
118  vprof(n)=(y2(1)*dt2+y2(2)*dt1)*dtt
119  wprof(n)=(y3(1)*dt2+y3(2)*dt1)*dtt
120  rhoprof(n)=(rho1(1)*dt2+rho1(2)*dt1)*dtt
121  rhogradprof(n)=(rhograd1(1)*dt2+rhograd1(2)*dt1)*dtt
122  indzindicator(n)=.false.
123
124  ! Compute standard deviations
125  !****************************
126
127  xaux=usq-usl*usl/8.
128  if (xaux.lt.eps) then
129    usigprof(n)=0.
130  else
131    usigprof(n)=sqrt(xaux/7.)
132  endif
133
134  xaux=vsq-vsl*vsl/8.
135  if (xaux.lt.eps) then
136    vsigprof(n)=0.
137  else
138    vsigprof(n)=sqrt(xaux/7.)
139  endif
140
141
142  xaux=wsq-wsl*wsl/8.
143  if (xaux.lt.eps) then
144    wsigprof(n)=0.
145  else
146    wsigprof(n)=sqrt(xaux/7.)
147  endif
148
149end subroutine interpol_misslev_nests
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG