source: flexpart.git/src/calcmatrix.f90 @ 3481cc1

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

move license from headers to a different file

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