source: flexpart.git/src/calcmatrix.f90

10.4.1_peseiGFS_025bugfixes+enhancementsdevrelease-10release-10.4.1scaling-bug
Last change on this file was 92fab65, checked in by Ignacio Pisso <ip@…>, 4 years ago

add SPDX-License-Identifier to all .f90 files

  • Property mode set to 100644
File size: 5.1 KB
Line 
1! SPDX-FileCopyrightText: FLEXPART 1998-2019, see flexpart_license.txt
2! SPDX-License-Identifier: GPL-3.0-or-later
3
4subroutine calcmatrix(lconv,delt,cbmf,metdata_format)
5  !                        o    i    o
6  !*****************************************************************************
7  !                                                                            *
8  !  This subroutine calculates the matrix describing convective               *
9  !  redistribution of mass in a grid column, using the subroutine             *
10  !  convect43c.f provided by Kerry Emanuel.                                   *
11  !                                                                            *
12  !  Petra Seibert, Bernd C. Krueger, 2000-2001                                *
13  !                                                                            *
14  !*****************************************************************************
15  ! Changes:                                                                   *
16  !  changed by C. Forster, November 2003 - February 2004                      *
17  !  array fmassfrac(nconvlevmax,nconvlevmax) represents                       *
18  !  the convective redistribution matrix for the particles                    *
19  !                                                                            *
20  !   Unified ECMWF and GFS builds                                             *
21  !   Marian Harustak, 12.5.2017                                               *
22  !     - Merged calcmatrix and calcmatrix_gfs into one routine using if-then  *
23  !       for meteo-type dependent code                                        *
24  !*****************************************************************************
25  !                                                                            *
26  !  lconv        indicates whether there is convection in this cell, or not   *
27  !  delt         time step for convection [s]                                 *
28  !  cbmf         cloud base mass flux                                         *
29  !  metdata_format format of metdata (ecmwf/gfs)                              *
30  !                                                                            *
31  !*****************************************************************************
32
33  use par_mod
34  use com_mod
35  use conv_mod
36  use class_gribfile
37
38  implicit none
39
40  real :: rlevmass,summe
41  integer :: metdata_format
42
43  integer :: iflag, k, kk, kuvz
44
45  !1-d variables for convection
46  !variables for redistribution matrix
47  real :: cbmfold, precip, qprime
48  real :: tprime, wd, f_qvsat
49  real :: delt,cbmf
50  logical :: lconv
51
52  lconv = .false.
53
54
55  ! calculate pressure at eta levels for use in convect
56  ! and assign temp & spec. hum. to 1D workspace
57  ! -------------------------------------------------------
58
59  ! pconv(1) is the pressure at the first level above ground
60  ! phconv(k) is the pressure between levels k-1 and k
61  ! dpr(k) is the pressure difference "around" tconv(k)
62  ! phconv(kmax) must also be defined 1/2 level above pconv(kmax)
63  ! Therefore, we define k = kuvz-1 and let kuvz start from 2
64  ! top layer cannot be used for convection because p at top of this layer is
65  ! not given
66
67
68  phconv(1) = psconv
69  ! Emanuel subroutine needs pressure in hPa, therefore convert all pressures
70  do kuvz = 2,nuvz
71    k = kuvz-1
72    if (metdata_format.eq.GRIBFILE_CENTRE_ECMWF) then
73    pconv(k) = (akz(kuvz) + bkz(kuvz)*psconv)
74    phconv(kuvz) = (akm(kuvz) + bkm(kuvz)*psconv)
75    else
76      phconv(kuvz) =  0.5*(pconv(kuvz)+pconv(k))
77    endif
78    dpr(k) = phconv(k) - phconv(kuvz)
79    qsconv(k) = f_qvsat( pconv(k), tconv(k) )
80
81  ! initialize mass fractions
82    do kk=1,nconvlev
83      fmassfrac(k,kk)=0.
84    end do
85  end do
86
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