source: flexpart.git/src/calcmatrix.f90 @ 9ca6e38

GFS_025dev
Last change on this file since 9ca6e38 was 9ca6e38, checked in by Espen Sollum ATMOS <eso@…>, 3 years ago

minor edits

  • Property mode set to 100644
File size: 5.3 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  if (metdata_format.eq.GRIBFILE_CENTRE_ECMWF) then
71    do kuvz = 2,nuvz
72      k = kuvz-1
73      pconv(k) = (akz(kuvz) + bkz(kuvz)*psconv)
74      phconv(kuvz) = (akm(kuvz) + bkm(kuvz)*psconv)
75      dpr(k) = phconv(k) - phconv(kuvz)
76      qsconv(k) = f_qvsat( pconv(k), tconv(k) )
77    end do
78  else
79! JMA / SH Bugfix phconv was set in loop with access to undefined pconv(nuvz)
80    phconv(2:nuvz-1) = 0.5*(pconv(2:nuvz-1)+pconv(1:nuvz-2))
81    phconv(nuvz) = pconv(nuvz-1)
82    dpr(1:nuvz-1) = phconv(1:nuvz-1)-phconv(2:nuvz)
83
84    do k = 1,nuvz-1
85      qsconv(k) = f_qvsat( pconv(k), tconv(k) )
86    end do
87  end if
88   
89! initialize mass fractions
90  fmassfrac(1:nuvz-1,1:nconvlev)=0.0
91
92  !note that Emanuel says it is important
93  !a. to set this =0. every grid point
94  !b. to keep this value in the calling programme in the iteration
95
96  ! CALL CONVECTION
97  !******************
98
99  cbmfold = cbmf
100! Convert pressures to hPa, as required by Emanuel scheme
101!********************************************************
102!!$    do k=1,nconvlev     !old
103  do k=1,nconvlev+1      !bugfix
104    pconv_hpa(k)=pconv(k)/100.
105    phconv_hpa(k)=phconv(k)/100.
106  end do
107  phconv_hpa(nconvlev+1)=phconv(nconvlev+1)/100.
108  call convect(nconvlevmax, nconvlev, delt, iflag, &
109       precip, wd, tprime, qprime, cbmf)
110
111! do not update fmassfrac and cloudbase massflux
112! if no convection takes place or
113! if a CFL criterion is violated in convect43c.f
114  if (iflag .ne. 1 .and. iflag .ne. 4) then
115    cbmf=cbmfold
116    goto 200
117  endif
118
119! do not update fmassfrac and cloudbase massflux
120! if the old and the new cloud base mass
121! fluxes are zero
122  if (cbmf.le.0..and.cbmfold.le.0.) then
123    cbmf=cbmfold
124    goto 200
125  endif
126
127! Update fmassfrac
128! account for mass displaced from level k to level k
129
130  lconv = .true.
131  do k=1,nconvtop
132    rlevmass = dpr(k)/ga
133    summe = 0.
134    do kk=1,nconvtop
135      fmassfrac(k,kk) = delt*fmass(k,kk)
136      summe = summe + fmassfrac(k,kk)
137    end do
138    fmassfrac(k,k)=fmassfrac(k,k) + rlevmass - summe
139  end do
140
141200 continue
142
143end subroutine calcmatrix
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG