source: branches/jerome/src_flexwrf_v3.1/calcmatrix.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: 5.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
22      subroutine calcmatrix(lconv,delt,cbmf)
23!                             o    i    o
24!******************************************************************
25!     This subroutine calculates the matrix describing convective
26!     redistribution of mass in a grid column, using the subroutine
27!     convect43c.f provided by Kerry Emanuel.
28!
29!     Petra Seibert, Bernd C. Krueger, 2000-2001
30!
31!     changed by C. Forster, November 2003 - February 2004
32!     array fmassfrac(nconvlevmax,nconvlevmax) represents
33!     the convective redistribution matrix for the particles
34!
35!     20 Oct 2005 - R. Easter - added calc of pconv_hpa(nconvlev+1)
36!     16 Nov 2005 - R. Easter - pconv,phconv are set in convmix
37!                               using pph & pphn
38!
39!******************************************************************
40
41! lconv        indicates whether there is convection in this cell, or not
42! delt         time step for convection [s]
43! cbmf         cloud base mass flux
44
45!      include 'includepar'
46!      include 'includecom'
47!      include 'includeconv'
48  use par_mod
49  use com_mod
50  use conv_mod
51
52  implicit none
53
54  real :: rlevmass,summe
55
56  integer :: iflag, k, kk, kuvz
57
58  !1-d variables for convection
59  !variables for redistribution matrix
60  real :: cbmfold, precip, qprime
61  real :: tprime, wd, f_qvsat
62  real :: delt,cbmf
63  logical :: lconv
64
65  lconv = .false.
66
67   
68! calculate pressure at eta levels for use in convect
69! and assign temp & spec. hum. to 1D workspace
70! -------------------------------------------------------
71
72! pconv(1) is the pressure at the first level above ground
73! phconv(k) is the pressure between levels k-1 and k
74! dp(k) is the pressure difference "around" tconv(k)
75! phconv(kmax) must also be defined 1/2 level above pconv(kmax)
76! Therefore, we define k = kuvz-1 and let kuvz start from 2
77! top layer cannot be used for convection because p at top of this layer is
78! not given
79
80
81!     phconv(1) = psconv
82! Emanuel subroutine needs pressure in hPa, therefore convert all pressures       
83      do kuvz = 2,nuvz
84        k = kuvz-1
85!       pconv(k) = (akz(kuvz) + bkz(kuvz)*psconv)
86!       phconv(kuvz) = (akm(kuvz) + bkm(kuvz)*psconv)
87        dpr(k) = phconv(k) - phconv(kuvz)
88        qsconv(k) = f_qvsat( pconv(k), tconv(k) )
89
90! initialize mass fractions
91        do kk=1,nconvlev
92          fmassfrac(k,kk)=0.
93        enddo
94      enddo
95
96
97!     note that Emanuel says it is important
98!     a. to set this =0. every grid point
99!     b. to keep this value in the calling programme in the iteration
100
101! CALL CONVECTION
102!******************
103
104        cbmfold = cbmf
105! Convert pressures to hPa, as required by Emanuel scheme
106!*********************************************************
107        do k=1,nconvlev+1
108          pconv_hpa(k)=pconv(k)/100.
109        phconv_hpa(k)=phconv(k)/100.
110         enddo
111        pconv_hpa(nconvlev+1)=pconv(nconvlev+1)/100.
112        phconv_hpa(nconvlev+1)=phconv(nconvlev+1)/100.
113        call convect(nconvlevmax, nconvlev, delt, iflag, &
114                  precip, wd, tprime, qprime, cbmf)
115
116!      do not update fmassfrac and cloudbase massflux
117!      if no convection takes place or
118!      if a CFL criterion is violated in convect43c.f
119       if (iflag .ne. 1 .and. iflag .ne. 4) then
120         cbmf=cbmfold
121         goto 200
122       endif
123
124!      do not update fmassfrac and cloudbase massflux
125!      if the old and the new cloud base mass
126!      fluxes are zero
127       if (cbmf.le.0..and.cbmfold.le.0.) then
128         cbmf=cbmfold
129         goto 200
130       endif
131
132!      Update fmassfrac
133!      account for mass displaced from level k to level k
134
135   lconv = .true.
136    do k=1,nconvtop
137      rlevmass = dpr(k)/ga
138      summe = 0.
139      do kk=1,nconvtop
140        fmassfrac(k,kk) = delt*fmass(k,kk)
141        summe = summe + fmassfrac(k,kk)
142      end do
143      fmassfrac(k,k)=fmassfrac(k,k) + rlevmass - summe
144    end do
145
146200   continue
147
148end subroutine calcmatrix
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG