source: trunk/src/calcmatrix_gfs.f90 @ 28

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