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

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

sources for flexwrf v3.1

File size: 3.8 KB
Line 
1!***********************************************************************
2!* Copyright 2012,2013                                                 *
3!* Jerome Brioude, Delia Arnold, Jerome Fast,
4!* Andreas Stohl, Petra Seibert, A. Frank, Gerhard Wotawa              *
5!* Caroline Forster, Sabine Eckhardt, John Burkhart, Harald Sodemann
6!* M. Cassiani
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_hmix(itime,xt,yt,zt,haux, &
24        p1,p2,p3,p4,ddx,ddy,rddx,rddy,dtt,dt1,dt2, &
25    ix,jy,ixp,jyp)
26
27!                               i   i  i  i
28!*******************************************************************************
29!                                                                              *
30!  This subroutine interpolates boundary layer top (h)                          *
31!  dispersion.                                                                 *
32!                                                                              *
33!    Author:M. cassiani 2013                                                   *
34!                                                                              *
35!                                                                              *
36!*******************************************************************************
37  use par_mod
38  use com_mod
39!  use interpol_mod
40!  use hanna_mod
41  implicit none
42
43      integer :: itime
44      real :: xt,yt,zt,h
45
46! Auxiliary variables needed for interpolation
47     
48      integer :: i,m,n,indexh,n2
49     
50      real,parameter ::eps=1.0e-30
51
52 
53  real :: h1(2),haux
54  real :: p1,p2,p3,p4,ddx,ddy,rddx,rddy,dtt,dt1,dt2
55  integer :: ix,jy,ixp,jyp,ngrid,indz,indzp
56  logical :: indzindicator(nzmax)
57 
58
59
60!********************************************
61! Multilinear interpolation in time and space
62!********************************************
63
64! Determine the lower left corner and its distance to the current position
65!*************************************************************************
66
67      ddx=xt-real(ix)                     
68      ddy=yt-real(jy)
69      rddx=1.-ddx
70      rddy=1.-ddy
71      p1=rddx*rddy
72      p2=ddx*rddy
73      p3=rddx*ddy
74      p4=ddx*ddy
75
76! Calculate variables for time interpolation
77!*******************************************
78
79      dt1=real(itime-memtime(1))
80      dt2=real(memtime(2)-itime)
81      dtt=1./(dt1+dt2)
82
83
84
85!*****************************************
86
87! a) Bilinear horizontal interpolation
88
89  do m=1,2
90    indexh=memind(m)
91
92    h1(m)=p1*hmix(ix ,jy ,1,indexh) &
93         + p2*hmix(ixp,jy ,1,indexh) &
94         + p3*hmix(ix ,jyp,1,indexh) &
95         + p4*hmix(ixp,jyp,1,indexh)
96   
97  end do
98     
99
100! b) Temporal interpolation
101
102      haux=(h1(1)*dt2+h1(2)*dt1)*dtt     
103
104
105end subroutine interpol_hmix
106
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG