source: flexpart.git/src/transform_omega_etadot.f90 @ 5f2e8f6

flexpart-noresm
Last change on this file since 5f2e8f6 was 5f2e8f6, checked in by Ignacio Pisso <Ignacio.Pisso@…>, 8 years ago

new flexpart noresm code in src

  • Property mode set to 100755
File size: 6.0 KB
Line 
1!**********************************************************************
2! Copyright 2016                                                      *
3! Andreas Stohl, Massimo Cassiani, Petra Seibert, A. Frank,           *
4! Gerhard Wotawa,  Caroline Forster, Sabine Eckhardt, John Burkhart,  *
5! Harald Sodemann, Ignacio Pisso                                      *
6!                                                                     *
7! This file is part of FLEXPART-NorESM                                *
8!                                                                     *
9! FLEXPART-NorESM is free software: you can redistribute it           *
10! 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-NorESM 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-NorESM.                                         *
22!  If not, see <http://www.gnu.org/licenses/>.                        *
23!**********************************************************************
24     
25
26    subroutine transform_omega_etadot(uuh,vvh,wwh,n)
27                                      !i   i  i/o i     
28
29!* * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *
30!*                                                                             *
31!*  calculate eta_dot*dp_eta = wwh-dp_dt-u*dp_dx-v*dp_dy on costant eta levels *
32!*  put eta_dot*dp_eta in wwh                                                  *
33!*  here we use ps to obatin p,                                                *
34!*  other variables used and in common block are:                              *
35!*  ps(ix,jy,1,n),akz(kz),bkz(kz),ps_tplus1_and_min1(ix,jy,indj-1 or indj+1)   *
36!*  if methodw is not  1 routne is not used                                    *
37!*                                                                             *
38!*                                                                             *
39!*     Author:                                                                 *
40!*     M. Cassiani  2016                                                       *
41!*                                                                             *
42!*                                                                             *
43!*                                                                             *
44!* * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *
45   
46    use par_mod
47    use com_mod 
48   
49    implicit none
50   
51    integer :: ix,jy,kz,n,ixp,ixm,deltat
52    real(kind=4) :: uuh(0:nxmax-1,0:nymax-1,nuvzmax)
53    real(kind=4) :: vvh(0:nxmax-1,0:nymax-1,nuvzmax)
54    real(kind=4) :: wwh(0:nxmax-1,0:nymax-1,nwzmax)
55    real(kind=4) :: pressure(0:nxmax-1,0:nymax-1,nwzmax)
56    real(kind=4) :: dpressuredt(0:nxmax-1,0:nymax-1,nwzmax)
57    real(kind=4) :: etadotdpdeta(0:nxmax-1,0:nymax-1,nwzmax) !not necessary but introduced for clarity eventually we coul rewrite wwh
58    real(kind=4) :: oneoverdxinm(0:nymax-1)
59    real(kind=4) :: oneoverdyinm,dpdx,dpdy
60   
61   
62   
63     do jy=1,ny-2
64       oneoverdxinm(jy)=dxconst/cos((real(jy)*dy+ylat0)*pi180)
65     end do
66        oneoverdyinm=dyconst
67         
68     
69 
70      do jy=0,nymin1
71        do ix=0, nxfield-1           
72          do kz=2,nuvz  !here nuvz is 27 (top of the domain) we skyp level one (extra kayer at the ground)
73            pressure(ix,jy,kz)=akz(kz)+bkz(kz)*ps(ix,jy,1,n)
74            dpressuredt(ix,jy,kz)=bkz(kz)*(ps_tplus1_and_min1(ix,jy,2)-ps_tplus1_and_min1(ix,jy,1)) !ps_tplus1_and_min1 is already divided for the time interval
75          end do
76        end do
77      end do
78     
79     
80      do jy=1,nymin1-1 !skip the poles
81        do ix=0, nxfield-1 
82          ixp=ix+1
83          ixm=ix-1
84          if (ixm.eq.-1)  ixm=nxfield-1 !special treatment for 0 and nxfield-1,
85          if (ixp.eq.nxfield) ixp=0    !special treatment for 0 and nxfield-1,
86          do kz=2,nuvz  !here nuvz is 27 (top of the domain) we skip level one (extra layer at the ground)
87            dpdx=(pressure(ixp,jy,kz)-pressure(ixm,jy,kz))*oneoverdxinm(jy)*0.5 !ix increase eastward  i.e. in the direction positive u (positive towards the east)
88            dpdy=(pressure(ix,jy+1,kz)-pressure(ix,jy-1,kz))*oneoverdyinm*0.5  !jy incrrease northward i.e. in the direction positive v (positivwe towards the north)
89            etadotdpdeta(ix,jy,kz)=wwh(ix,jy,kz)-dpressuredt(ix,jy,kz)-uuh(ix,jy,kz)*dpdx-vvh(ix,jy,kz)*dpdy
90            ixp=ixp
91          end do
92        end do
93      end do
94     
95      do jy=1,nymin1-1 !skip the poles
96        do ix=0, nxfield-1  !special treatment for 0 and nxfield-1,         
97          do kz=2,nuvz  !here nuvz is 27 (top of the domain) we skip level one (extra layer at the ground)
98            wwh(ix,jy,kz)=etadotdpdeta(ix,jy,kz)         
99          end do
100        end do
101      end do
102       
103      wwh(:,0,:)=0.
104      wwh(:,nymin1,:)=0.
105       
106      do ix=0, nxfield-1  !         
107        do kz=2,nuvz  !here nuvz is 27 (top of the domain) we skip level one (extra layer at the ground)
108          wwh(ix,0,kz)=wwh(ix,0,kz)+etadotdpdeta(ix,1,kz)/nxfield  !set to averaged value of next circle
109          wwh(ix,nymin1,kz)= wwh(ix,nymin1,kz)+etadotdpdeta(ix,nymin1-1,kz)/nxfield  !set to averaged value of previous circle
110        end do
111      end do
112     
113       
114       
115      return
116      end
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG