source: branches/jerome/src_flexwrf_v3.1/interpol_misslev_nests.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: 7.7 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_nests(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!                                       i
34!*******************************************************************************
35!                                                                              *
36!  This subroutine interpolates u,v,w, density and density gradients.          *
37!                                                                              *
38!    Author: A. Stohl                                                          *
39!                                                                              *
40!    16 December 1997                                                          *
41!                                                                              *
42!*******************************************************************************
43!                                                                              *
44! Variables:                                                                   *
45! n                  level                                                     *
46!                                                                              *
47! Constants:                                                                   *
48!                                                                              *
49!*******************************************************************************
50!    12 JUNE 2007 W Wang
51!                 compute pttprof,  add a variable y4 for interpolation        *
52!*******************************************************************************
53  use par_mod
54  use com_mod
55!  use interpol_mod
56!  use hanna_mod
57
58  implicit none
59
60! Auxiliary variables needed for interpolation
61      real :: y1(2),y2(2),y3(2),rho1(2),rhograd1(2),y4(2)
62      real :: usl,vsl,wsl,usq,vsq,wsq,xaux
63      integer :: m,n,indexh
64  real,parameter :: eps=1.0e-30
65
66  real :: uprof(nzmax),vprof(nzmax),wprof(nzmax)
67  real :: usigprof(nzmax),vsigprof(nzmax),wsigprof(nzmax)
68  real :: rhoprof(nzmax),rhogradprof(nzmax)
69  real :: tkeprof(nzmax),pttprof(nzmax)
70  real :: u,v,w,usig,vsig,wsig,pvi
71
72  real :: p1,p2,p3,p4,ddx,ddy,rddx,rddy,dtt,dt1,dt2
73  integer :: ix,jy,ixp,jyp,ngrid,indz,indzp
74  logical :: depoindicator(maxspec)
75  logical :: indzindicator(nzmax)
76  real :: ust,wst,ol,h,zeta,sigu,sigv,tlu,tlv,tlw
77  real :: sigw,dsigwdz,dsigw2dz
78
79  real(kind=dp) :: xt,yt
80  real :: zt
81
82!********************************************
83! Multilinear interpolation in time and space
84!********************************************
85
86
87!**************************************
88! 1.) Bilinear horizontal interpolation
89! 2.) Temporal interpolation (linear)
90!**************************************
91
92! Loop over 2 time steps
93!***********************
94
95  usl=0.
96  vsl=0.
97  wsl=0.
98  usq=0.
99  vsq=0.
100  wsq=0.
101  do m=1,2
102    indexh=memind(m)
103    y1(m)=p1*uun(ix ,jy ,n,indexh,ngrid) &
104         +p2*uun(ixp,jy ,n,indexh,ngrid) &
105         +p3*uun(ix ,jyp,n,indexh,ngrid) &
106         +p4*uun(ixp,jyp,n,indexh,ngrid)
107    y2(m)=p1*vvn(ix ,jy ,n,indexh,ngrid) &
108         +p2*vvn(ixp,jy ,n,indexh,ngrid) &
109         +p3*vvn(ix ,jyp,n,indexh,ngrid) &
110         +p4*vvn(ixp,jyp,n,indexh,ngrid)
111    y3(m)=p1*wwn(ix ,jy ,n,indexh,ngrid) &
112         +p2*wwn(ixp,jy ,n,indexh,ngrid) &
113         +p3*wwn(ix ,jyp,n,indexh,ngrid) &
114         +p4*wwn(ixp,jyp,n,indexh,ngrid)
115    rho1(m)=p1*rhon(ix ,jy ,n,indexh,ngrid) &
116         +p2*rhon(ixp,jy ,n,indexh,ngrid) &
117         +p3*rhon(ix ,jyp,n,indexh,ngrid) &
118         +p4*rhon(ixp,jyp,n,indexh,ngrid)
119    rhograd1(m)=p1*drhodzn(ix ,jy ,n,indexh,ngrid) &
120         +p2*drhodzn(ixp,jy ,n,indexh,ngrid) &
121         +p3*drhodzn(ix ,jyp,n,indexh,ngrid) &
122         +p4*drhodzn(ixp,jyp,n,indexh,ngrid)
123!        y4(m)=p1*pttn(ix ,jy ,n,indexh,ngrid) &
124!               +p2*pttn(ixp,jy ,n,indexh,ngrid) &
125!               +p3*pttn(ix ,jyp,n,indexh,ngrid) &
126!               +p4*pttn(ixp,jyp,n,indexh,ngrid)
127     usl=usl+uun(ix ,jy ,n,indexh,ngrid)+uun(ixp,jy ,n,indexh,ngrid) &
128          +uun(ix ,jyp,n,indexh,ngrid)+uun(ixp,jyp,n,indexh,ngrid)
129     vsl=vsl+vvn(ix ,jy ,n,indexh,ngrid)+vvn(ixp,jy ,n,indexh,ngrid) &
130          +vvn(ix ,jyp,n,indexh,ngrid)+vvn(ixp,jyp,n,indexh,ngrid)
131     wsl=wsl+wwn(ix ,jy ,n,indexh,ngrid)+wwn(ixp,jy ,n,indexh,ngrid) &
132          +wwn(ix ,jyp,n,indexh,ngrid)+wwn(ixp,jyp,n,indexh,ngrid)
133
134    usq=usq+uun(ix ,jy ,n,indexh,ngrid)*uun(ix ,jy ,n,indexh,ngrid)+ &
135         uun(ixp,jy ,n,indexh,ngrid)*uun(ixp,jy ,n,indexh,ngrid)+ &
136         uun(ix ,jyp,n,indexh,ngrid)*uun(ix ,jyp,n,indexh,ngrid)+ &
137         uun(ixp,jyp,n,indexh,ngrid)*uun(ixp,jyp,n,indexh,ngrid)
138    vsq=vsq+vvn(ix ,jy ,n,indexh,ngrid)*vvn(ix ,jy ,n,indexh,ngrid)+ &
139         vvn(ixp,jy ,n,indexh,ngrid)*vvn(ixp,jy ,n,indexh,ngrid)+ &
140         vvn(ix ,jyp,n,indexh,ngrid)*vvn(ix ,jyp,n,indexh,ngrid)+ &
141         vvn(ixp,jyp,n,indexh,ngrid)*vvn(ixp,jyp,n,indexh,ngrid)
142    wsq=wsq+wwn(ix ,jy ,n,indexh,ngrid)*wwn(ix ,jy ,n,indexh,ngrid)+ &
143         wwn(ixp,jy ,n,indexh,ngrid)*wwn(ixp,jy ,n,indexh,ngrid)+ &
144         wwn(ix ,jyp,n,indexh,ngrid)*wwn(ix ,jyp,n,indexh,ngrid)+ &
145         wwn(ixp,jyp,n,indexh,ngrid)*wwn(ixp,jyp,n,indexh,ngrid)
146  end do
147      uprof(n)=(y1(1)*dt2+y1(2)*dt1)*dtt
148      vprof(n)=(y2(1)*dt2+y2(2)*dt1)*dtt
149      wprof(n)=(y3(1)*dt2+y3(2)*dt1)*dtt
150      rhoprof(n)=(rho1(1)*dt2+rho1(2)*dt1)*dtt
151!      pttprof(n)=(y4(1)*dt2+y4(2)*dt1)*dtt
152
153      rhogradprof(n)=(rhograd1(1)*dt2+rhograd1(2)*dt1)*dtt
154      indzindicator(n)=.false.
155
156! Compute standard deviations
157!****************************
158
159      xaux=usq-usl*usl/8.
160      if (xaux.lt.eps) then
161        usigprof(n)=0.
162      else
163        usigprof(n)=sqrt(xaux/7.)
164      endif
165
166      xaux=vsq-vsl*vsl/8.
167      if (xaux.lt.eps) then
168        vsigprof(n)=0.
169      else 
170        vsigprof(n)=sqrt(xaux/7.)
171      endif
172
173
174      xaux=wsq-wsl*wsl/8.
175      if (xaux.lt.eps) then
176        wsigprof(n)=0.
177      else
178        wsigprof(n)=sqrt(xaux/7.)
179      endif
180
181end subroutine interpol_misslev_nests
182
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG