source: branches/jerome/src_flexwrf_v3.1/interpol_misslev.f90 @ 16

Last change on this file since 16 was 16, checked in by jebri, 11 years ago

sources for flexwrf v3.1

File size: 8.9 KB
Line 
1!***********************************************************************
2!* Copyright 2012,2013                                                *
3!* Jerome Brioude, Delia Arnold, Andreas Stohl, Wayne Angevine,       *
4!* John Burkhart, Massimo Cassiani, Adam Dingwell, Richard C Easter, Sabine Eckhardt,*
5!* Stephanie Evan, Jerome D Fast, Don Morton, Ignacio Pisso,          *
6!* Petra Seibert, Gerard Wotawa, Caroline Forster, Harald Sodemann,   *
7!*                                                                     *
8!* This file is part of FLEXPART WRF                                   *
9!*                                                                     *
10!* FLEXPART is free software: you can redistribute it and/or modify    *
11!* it under the terms of the GNU General Public License as published by*
12!* the Free Software Foundation, either version 3 of the License, or   *
13!* (at your option) any later version.                                 *
14!*                                                                     *
15!* FLEXPART is distributed in the hope that it will be useful,         *
16!* but WITHOUT ANY WARRANTY; without even the implied warranty of      *
17!* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the       *
18!* GNU General Public License for more details.                        *
19!*                                                                     *
20!* You should have received a copy of the GNU General Public License   *
21!* along with FLEXPART.  If not, see <http://www.gnu.org/licenses/>.   *
22!***********************************************************************
23      subroutine interpol_misslev(n,xt,yt,zt,&
24    uprof,vprof,wprof, usigprof,vsigprof,wsigprof, &
25    rhoprof,rhogradprof, tkeprof,pttprof, &
26    u,v,w,usig,vsig,wsig,pvi, &
27    p1,p2,p3,p4,ddx,ddy,rddx,rddy,dtt,dt1,dt2, &
28    ix,jy,ixp,jyp,ngrid,indz,indzp, depoindicator, &
29    indzindicator, &
30   ust,wst,ol,h,zeta,sigu,sigv,tlu,tlv,tlw, &
31   sigw,dsigwdz,dsigw2dz)
32
33
34!                                 i
35!*******************************************************************************
36!                                                                              *
37!  This subroutine interpolates u,v,w, density and density gradients.          *
38!                                                                              *
39!    Author: A. Stohl                                                          *
40!                                                                              *
41!    16 December 1997                                                          *
42!    Update: 2 March 1999                                                      *
43!                                                                              *
44!  Revision March 2005 by AST : all output variables in common block           *
45!                               calculation of standard deviation done in this *
46!                               routine rather than subroutine call in order   *
47!                               to save computation time                       *
48!                                                                              *
49!*******************************************************************************
50!                                                                              *
51! Variables:                                                                   *
52! n                  level                                                     *
53!                                                                              *
54! Constants:                                                                   *
55!                                                                              *
56!*******************************************************************************
57!   12 JUNE 2007  by W Wang
58!                 compute pttrof , add a variable y4 for interpolation        *
59!*******************************************************************************
60
61  use par_mod
62  use com_mod
63!  use interpol_mod
64!  use hanna_mod
65
66  implicit none
67
68
69! Auxiliary variables needed for interpolation
70      real :: y1(2),y2(2),y3(2),rho1(2),rhograd1(2),y4(2)
71      real :: usl,vsl,wsl,usq,vsq,wsq,xaux
72      integer :: m,n,indexh
73  real,parameter :: eps=1.0e-30
74
75  real :: uprof(nzmax),vprof(nzmax),wprof(nzmax)
76  real :: usigprof(nzmax),vsigprof(nzmax),wsigprof(nzmax)
77  real :: rhoprof(nzmax),rhogradprof(nzmax)
78  real :: tkeprof(nzmax),pttprof(nzmax)
79  real :: u,v,w,usig,vsig,wsig,pvi
80
81  real :: p1,p2,p3,p4,ddx,ddy,rddx,rddy,dtt,dt1,dt2
82  integer :: ix,jy,ixp,jyp,ngrid,indz,indzp
83  logical :: depoindicator(maxspec)
84  logical :: indzindicator(nzmax)
85  real :: ust,wst,ol,h,zeta,sigu,sigv,tlu,tlv,tlw
86  real :: sigw,dsigwdz,dsigw2dz
87
88  real(kind=dp) :: xt,yt
89  real :: zt
90
91!********************************************
92! Multilinear interpolation in time and space
93!********************************************
94
95
96!**************************************
97! 1.) Bilinear horizontal interpolation
98! 2.) Temporal interpolation (linear)
99!**************************************
100
101! Loop over 2 time steps
102!***********************
103
104  usl=0.
105  vsl=0.
106  wsl=0.
107  usq=0.
108  vsq=0.
109  wsq=0.
110  do m=1,2
111    indexh=memind(m)
112    if (ngrid.lt.0) then
113      y1(m)=p1*uupol(ix ,jy ,n,indexh) &
114           +p2*uupol(ixp,jy ,n,indexh) &
115           +p3*uupol(ix ,jyp,n,indexh) &
116           +p4*uupol(ixp,jyp,n,indexh)
117      y2(m)=p1*vvpol(ix ,jy ,n,indexh) &
118           +p2*vvpol(ixp,jy ,n,indexh) &
119           +p3*vvpol(ix ,jyp,n,indexh) &
120           +p4*vvpol(ixp,jyp,n,indexh)
121        usl=usl+uupol(ix ,jy ,n,indexh)+uupol(ixp,jy ,n,indexh) &
122             +uupol(ix ,jyp,n,indexh)+uupol(ixp,jyp,n,indexh)
123        vsl=vsl+vvpol(ix ,jy ,n,indexh)+vvpol(ixp,jy ,n,indexh) &
124             +vvpol(ix ,jyp,n,indexh)+vvpol(ixp,jyp,n,indexh)
125
126        usq=usq+uupol(ix ,jy ,n,indexh)*uupol(ix ,jy ,n,indexh)+ &
127             uupol(ixp,jy ,n,indexh)*uupol(ixp,jy ,n,indexh)+ &
128             uupol(ix ,jyp,n,indexh)*uupol(ix ,jyp,n,indexh)+ &
129             uupol(ixp,jyp,n,indexh)*uupol(ixp,jyp,n,indexh)
130        vsq=vsq+vvpol(ix ,jy ,n,indexh)*vvpol(ix ,jy ,n,indexh)+ &
131             vvpol(ixp,jy ,n,indexh)*vvpol(ixp,jy ,n,indexh)+ &
132             vvpol(ix ,jyp,n,indexh)*vvpol(ix ,jyp,n,indexh)+ &
133             vvpol(ixp,jyp,n,indexh)*vvpol(ixp,jyp,n,indexh)
134        else
135      y1(m)=p1*uu(ix ,jy ,n,indexh) &
136           +p2*uu(ixp,jy ,n,indexh) &
137           +p3*uu(ix ,jyp,n,indexh) &
138           +p4*uu(ixp,jyp,n,indexh)
139      y2(m)=p1*vv(ix ,jy ,n,indexh) &
140           +p2*vv(ixp,jy ,n,indexh) &
141           +p3*vv(ix ,jyp,n,indexh) &
142           +p4*vv(ixp,jyp,n,indexh)
143      usl=usl+uu(ix ,jy ,n,indexh)+uu(ixp,jy ,n,indexh) &
144           +uu(ix ,jyp,n,indexh)+uu(ixp,jyp,n,indexh)
145      vsl=vsl+vv(ix ,jy ,n,indexh)+vv(ixp,jy ,n,indexh) &
146           +vv(ix ,jyp,n,indexh)+vv(ixp,jyp,n,indexh)
147
148      usq=usq+uu(ix ,jy ,n,indexh)*uu(ix ,jy ,n,indexh)+ &
149           uu(ixp,jy ,n,indexh)*uu(ixp,jy ,n,indexh)+ &
150           uu(ix ,jyp,n,indexh)*uu(ix ,jyp,n,indexh)+ &
151           uu(ixp,jyp,n,indexh)*uu(ixp,jyp,n,indexh)
152      vsq=vsq+vv(ix ,jy ,n,indexh)*vv(ix ,jy ,n,indexh)+ &
153           vv(ixp,jy ,n,indexh)*vv(ixp,jy ,n,indexh)+ &
154           vv(ix ,jyp,n,indexh)*vv(ix ,jyp,n,indexh)+ &
155           vv(ixp,jyp,n,indexh)*vv(ixp,jyp,n,indexh)
156    endif
157    y3(m)=p1*ww(ix ,jy ,n,indexh) &
158         +p2*ww(ixp,jy ,n,indexh) &
159         +p3*ww(ix ,jyp,n,indexh) &
160         +p4*ww(ixp,jyp,n,indexh)
161    rhograd1(m)=p1*drhodz(ix ,jy ,n,indexh) &
162         +p2*drhodz(ixp,jy ,n,indexh) &
163         +p3*drhodz(ix ,jyp,n,indexh) &
164         +p4*drhodz(ixp,jyp,n,indexh)
165    rho1(m)=p1*rho(ix ,jy ,n,indexh) &
166         +p2*rho(ixp,jy ,n,indexh) &
167         +p3*rho(ix ,jyp,n,indexh) &
168         +p4*rho(ixp,jyp,n,indexh)
169!        y4(m)  =p1*ptt(ix ,jy ,n,indexh) &
170!               +p2*ptt(ixp,jy ,n,indexh) &
171!               +p3*ptt(ix ,jyp,n,indexh) &
172!               +p4*ptt(ixp,jyp,n,indexh)
173
174    wsl=wsl+ww(ix ,jy ,n,indexh)+ww(ixp,jy ,n,indexh) &
175         +ww(ix ,jyp,n,indexh)+ww(ixp,jyp,n,indexh)
176    wsq=wsq+ww(ix ,jy ,n,indexh)*ww(ix ,jy ,n,indexh)+ &
177         ww(ixp,jy ,n,indexh)*ww(ixp,jy ,n,indexh)+ &
178         ww(ix ,jyp,n,indexh)*ww(ix ,jyp,n,indexh)+ &
179         ww(ixp,jyp,n,indexh)*ww(ixp,jyp,n,indexh)
180  end do
181      uprof(n)=(y1(1)*dt2+y1(2)*dt1)*dtt
182      vprof(n)=(y2(1)*dt2+y2(2)*dt1)*dtt
183      wprof(n)=(y3(1)*dt2+y3(2)*dt1)*dtt
184      rhoprof(n)=(rho1(1)*dt2+rho1(2)*dt1)*dtt
185      rhogradprof(n)=(rhograd1(1)*dt2+rhograd1(2)*dt1)*dtt
186!      pttprof(n)=(y4(1)*dt2+y4(2)*dt1)*dtt
187      indzindicator(n)=.false.
188
189
190! Compute standard deviations
191!****************************
192
193      xaux=usq-usl*usl/8.
194      if (xaux.lt.eps) then
195        usigprof(n)=0.
196      else
197        usigprof(n)=sqrt(xaux/7.)
198      endif
199
200      xaux=vsq-vsl*vsl/8.
201      if (xaux.lt.eps) then
202        vsigprof(n)=0.
203      else
204        vsigprof(n)=sqrt(xaux/7.)
205      endif
206
207
208      xaux=wsq-wsl*wsl/8.
209      if (xaux.lt.eps) then
210        wsigprof(n)=0.
211      else
212        wsigprof(n)=sqrt(xaux/7.)
213      endif
214
215
216end subroutine interpol_misslev
217
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG