source: trunk/LMDZ.TITAN/libf/muphytitan/mm_microphysic.f90 @ 2109

Last change on this file since 2109 was 2109, checked in by jvatant, 6 years ago

Fix some problems for the microphysics :
+ Altitude of the last level at 1e7m from physics was certainly source of divergence
+ Sanity check for negative is moved from within mm_microphysic to the end of calmufi avoiding rounding pbs
--JVO

File size: 12.0 KB
Line 
1! Copyright 2013-2015,2017 Université de Reims Champagne-Ardenne
2! Contributor: J. Burgalat (GSMA, URCA)
3! email of the author : jeremie.burgalat@univ-reims.fr
4!
5! This software is a computer program whose purpose is to compute
6! microphysics processes using a two-moments scheme.
7!
8! This library is governed by the CeCILL-B license under French law and
9! abiding by the rules of distribution of free software.  You can  use,
10! modify and/ or redistribute the software under the terms of the CeCILL-B
11! license as circulated by CEA, CNRS and INRIA at the following URL
12! "http://www.cecill.info".
13!
14! As a counterpart to the access to the source code and  rights to copy,
15! modify and redistribute granted by the license, users are provided only
16! with a limited warranty  and the software's author,  the holder of the
17! economic rights,  and the successive licensors  have only  limited
18! liability.
19!
20! In this respect, the user's attention is drawn to the risks associated
21! with loading,  using,  modifying and/or developing or reproducing the
22! software by the user in light of its specific status of free software,
23! that may mean  that it is complicated to manipulate,  and  that  also
24! therefore means  that it is reserved for developers  and  experienced
25! professionals having in-depth computer knowledge. Users are therefore
26! encouraged to load and test the software's suitability as regards their
27! requirements in conditions enabling the security of their systems and/or
28! data to be ensured and,  more generally, to use and operate it in the
29! same conditions as regards security.
30!
31! The fact that you are presently reading this means that you have had
32! knowledge of the CeCILL-B license and that you accept its terms.
33
34!! file: mm_microphysic.f90
35!! brief: Microphysic processes interface module.
36!! author: J. Burgalat
37!! date: 2013-2015,2017
38
39MODULE MM_MICROPHYSIC
40  !! Microphysic processes interface module.
41  USE MM_MPREC
42  USE MM_GLOBALS
43  USE MM_HAZE
44  USE MM_CLOUDS
45  USE MM_METHODS
46  IMPLICIT NONE
47
48  PRIVATE
49
50  PUBLIC :: mm_muphys, mm_diagnostics, mm_get_radii
51
52  !! Interface to main microphysics subroutine.
53  !!
54  !! The interface computes calls either all the microphysics processes ([[mm_microphysic(module):muphys_all(function)]]
55  !! or only aerosols microphysics ([[mm_microphysic(module):muphys_nocld(function)]]) in a single call.
56  INTERFACE mm_muphys
57    MODULE PROCEDURE muphys_all, muphys_nocld
58  END INTERFACE
59
60  CONTAINS
61
62
63   
64  FUNCTION muphys_all(dm0a_s,dm3a_s,dm0a_f,dm3a_f,dm0n,dm3n,dm3i,dgazs) RESULT(ret)
65    !! Compute the evolution of moments tracers through haze and clouds microphysics processes.
66    !!
67    !! This method computes the evolution of all the microphysics tracers, given under the form of moments
68    !! (and molar fraction for cloud condensible species) during a time step.
69    !!
70    !! The method requires that global variables of the model (i.e. variables declared in [[mm_globals(module)]]
71    !! module) are initialized/updated correctly (see [[mm_globals(module):mm_global_init(interface)]],
72    !! [[mm_globals(module):mm_column_init(function)]],[[mm_globals(module):mm_aerosols_init(function)]] and
73    !! [[mm_globals(module):mm_clouds_init(function)]]).
74    !!
75    !! The tendencies returned by the method are defined on the vertical __layers__ of the model from the __GROUND__ to
76    !! the __TOP__ of the atmosphere. They should be added to the input variables used in the initialization methods
77    !! before the latter are called to initialize a new step.
78    !! @note
79    !! __dm3i__ and __dgazs__ are 2D-arrays with vertical __layers__ in the 1st dimension and the number of
80    !! ice components in the 2nd. They share the same _species_ indexing.
81    !!
82    !! It should be a 2D-array with the vertical layers in first dimension and the number of ice components in the second.
83    REAL(kind=mm_wp), INTENT(out), DIMENSION(:)   :: dm0a_s
84      !! Tendency of the 0th order moment of the spherical mode distribution (\(m^{-2}\)).
85    REAL(kind=mm_wp), INTENT(out), DIMENSION(:)   :: dm3a_s
86      !! Tendency of the 3rd order moment of the spherical mode distribution (\(m^{3}.m^{-2}\)).
87    REAL(kind=mm_wp), INTENT(out), DIMENSION(:)   :: dm0a_f
88      !! Tendency of the 0th order moment of the fractal mode distribution (\(m^{-2}\)).
89    REAL(kind=mm_wp), INTENT(out), DIMENSION(:)   :: dm3a_f
90      !! Tendency of the 3rd order moment of the fractal mode distribution (\(m^{3}.m^{-2}\)).
91    REAL(kind=mm_wp), INTENT(out), DIMENSION(:)   :: dm0n
92      !! Tendency of the 0th order moment of the _CCN_ distribution (\(m^{-2}\)).
93    REAL(kind=mm_wp), INTENT(out), DIMENSION(:)   :: dm3n
94      !! Tendency of the 3rd order moment of the _CCN_ distribution (\(m^{3}.m^{-2}\)).
95    REAL(kind=mm_wp), INTENT(out), DIMENSION(:,:) :: dm3i
96      !! Tendencies of the 3rd order moments of each ice components (\(m^{3}.m^{-2}\)).
97    REAL(kind=mm_wp), INTENT(out), DIMENSION(:,:) :: dgazs
98      !! Tendencies of each condensible gaz species (\(mol.mol^{-1}\)).
99    LOGICAL :: ret
100      !! .true. on success (i.e. model has been initialized at least once previously), .false. otherwise.
101    REAL(kind=mm_wp), DIMENSION(SIZE(dm0a_s)) :: zdm0a_f,zdm3a_f
102    INTEGER                                   :: i
103    ! Checks initialization
104    ret = (mm_ini_col.AND.mm_ini_aer.AND.(.NOT.mm_w_clouds.OR.mm_ini_cld))
105    IF (.NOT.ret) RETURN
106    ! Calls haze microphysics (-> m-3)
107    call mm_haze_microphysics(dm0a_s,dm3a_s,dm0a_f,dm3a_f)
108    IF (mm_w_clouds) THEN
109      ! Calls cloud microphysics (-> m-3)
110      call mm_cloud_microphysics(zdm0a_f,zdm3a_f,dm0n,dm3n,dm3i,dgazs)
111      ! add temporary aerosols tendencies (-> m-3)
112      dm0a_f = dm0a_f + zdm0a_f  ; dm3a_f = dm3a_f + zdm3a_f
113      ! reverse clouds tendencies (-> m-2)
114      dm0n   = dm0n(mm_nla:1:-1) * mm_dzlev(mm_nla:1:-1)
115      dm3n   = dm3n(mm_nla:1:-1) * mm_dzlev(mm_nla:1:-1)
116      DO i=1,mm_nesp
117        dm3i(:,i)  = dm3i(mm_nla:1:-1,i)  * mm_dzlev(mm_nla:1:-1)
118        dgazs(:,i) = dgazs(mm_nla:1:-1,i)
119      ENDDO
120    ELSE
121      dm0n = 0._mm_wp ; dm3n = 0._mm_wp ; dm3i = 0._mm_wp ; dgazs = 0._mm_wp
122    ENDIF
123    ! multiply by altitude thickness and reverse vectors so they go from ground to top :)
124    dm0a_s = dm0a_s(mm_nla:1:-1) * mm_dzlev(mm_nla:1:-1)
125    dm3a_s = dm3a_s(mm_nla:1:-1) * mm_dzlev(mm_nla:1:-1)
126    dm0a_f = dm0a_f(mm_nla:1:-1) * mm_dzlev(mm_nla:1:-1)
127    dm3a_f = dm3a_f(mm_nla:1:-1) * mm_dzlev(mm_nla:1:-1)
128   
129    RETURN
130  END FUNCTION muphys_all
131
132  FUNCTION muphys_nocld(dm0a_s,dm3a_s,dm0a_f,dm3a_f) RESULT(ret)
133    !! Compute the evolution of moments tracers through haze microphysics only.
134    !!
135    !! This method is a __light__ version of [[mm_microphysic(module):muphys_all(function)]] where
136    !! only haze microphysics is computed and its tendencies returned.
137    !!
138    !! The method has the same requirements and remarks than [[mm_microphysic(module):muphys_all(function)]].
139    REAL(kind=mm_wp), INTENT(out), DIMENSION(:) :: dm0a_s
140      !! Tendency of the 0th order moment of the spherical mode distribution (\(m^{-2}\)).
141    REAL(kind=mm_wp), INTENT(out), DIMENSION(:) :: dm3a_s
142      !! Tendency of the 3rd order moment of the spherical mode distribution (\(m^{3}.m^{-2}\)).
143    REAL(kind=mm_wp), INTENT(out), DIMENSION(:) :: dm0a_f
144      !! Tendency of the 0th order moment of the fractal mode distribution (\(m^{-2}\)).
145    REAL(kind=mm_wp), INTENT(out), DIMENSION(:) :: dm3a_f
146      !! Tendency of the 3rd order moment of the fractal mode distribution (\(m^{3}.m^{-2}\)).
147    LOGICAL :: ret
148      !! .true. on succes (i.e. model has been initialized at least once previously), .false. otherwise.
149    ret = (mm_ini_col.AND.mm_ini_aer)
150    IF (.NOT.ret) RETURN
151    IF (mm_w_clouds.AND.mm_debug) THEN
152      WRITE(*,'(a)') "WARNING: clouds microphysics enabled but will not be &
153                     &computed... (wrong interface)"
154    ENDIF
155    ! Calls haze microphysics
156    call mm_haze_microphysics(dm0a_s,dm3a_s,dm0a_f,dm3a_f)
157    ! reverse vectors so they go from ground to top :)
158    dm0a_s = dm0a_s(mm_nla:1:-1) * mm_dzlev(mm_nla:1:-1)
159    dm3a_s = dm3a_s(mm_nla:1:-1) * mm_dzlev(mm_nla:1:-1)
160    dm0a_f = dm0a_f(mm_nla:1:-1) * mm_dzlev(mm_nla:1:-1)
161    dm3a_f = dm3a_f(mm_nla:1:-1) * mm_dzlev(mm_nla:1:-1)
162    RETURN
163  END FUNCTION muphys_nocld
164
165  SUBROUTINE mm_diagnostics(aer_prec,aer_s_flux,aer_f_flux,         &
166                            ccn_prec,ccn_flux, ice_prec,ice_fluxes, &
167                            gazs_sat)
168    !! Get various diagnostic fields of the microphysics.
169    !!
170    !! The current diagnostics saved during microphysic computation are :
171    !!
172    !! - Mass fluxes (aerosols -both mode-, CCN and ices)
173    !! - Precipitations (aerosols -total-, CCN and ices)
174    !! - condensible gazes saturation ratio
175    !!
176    !! @note
177    !! Fluxes values are always negative as they account for sedimentation fluxes. They are set as
178    !! vector (for aerosols and CCN) or 2D-array (with the vertical structure in the first dimension
179    !! and number of species in the second, for ice) and are ordered from __GROUND__ to __TOP__.
180    !!
181    !! @note
182    !! Precipitations are always positive and defined in meters. For ice, it is set as a vector with
183    !! the precipitations of each cloud ice components.
184    !!
185    !! @note
186    !! __ccnprec__, __iceprec__, __icefluxes__ and __gazsat__ are always set to 0 if clouds
187    !! microphysics is disabled (see [[mm_globals(module):mm_w_clouds(variable)]] documentation).
188    REAL(kind=mm_wp), INTENT(out), OPTIONAL                 :: aer_prec   !! Aerosols precipitations (both modes) (m).
189    REAL(kind=mm_wp), INTENT(out), OPTIONAL, DIMENSION(:)   :: aer_s_flux !! Spherical aerosol mass flux (\(kg.m^{-2}.s^{-1}\)).
190    REAL(kind=mm_wp), INTENT(out), OPTIONAL, DIMENSION(:)   :: aer_f_flux !! Fractal aerosol mass flux (\(kg.m^{-2}.s^{-1}\)).
191    REAL(kind=mm_wp), INTENT(out), OPTIONAL                 :: ccn_prec   !! CCN precipitations (m).
192    REAL(kind=mm_wp), INTENT(out), OPTIONAL, DIMENSION(:)   :: ccn_flux   !! CCN mass flux (\(kg.m^{-2}.s^{-1}\)).
193    REAL(kind=mm_wp), INTENT(out), OPTIONAL, DIMENSION(:)   :: ice_prec   !! Ice precipitations (m).
194    REAL(kind=mm_wp), INTENT(out), OPTIONAL, DIMENSION(:,:) :: ice_fluxes !! Ice sedimentation fluxes (\(kg.m^{-2}.s^{-1}\)).
195    REAL(kind=mm_wp), INTENT(out), OPTIONAL, DIMENSION(:,:) :: gazs_sat   !! Condensible gaz saturation ratios (--).
196
197    IF (PRESENT(aer_prec))   aer_prec   = ABS(mm_aer_prec)
198    IF (PRESENT(aer_s_flux)) aer_s_flux = -mm_aer_s_flux(mm_nla:1:-1)
199    IF (PRESENT(aer_f_flux)) aer_f_flux = -mm_aer_f_flux(mm_nla:1:-1)
200
201    IF (mm_w_clouds) THEN
202      IF (PRESENT(ccn_prec))   ccn_prec   = ABS(mm_ccn_prec)
203      IF (PRESENT(ice_prec))   ice_prec   = ABS(mm_ice_prec)
204      IF (PRESENT(ccn_flux))   ccn_flux   = -mm_ccn_flux(mm_nla:1:-1)
205      IF (PRESENT(ice_fluxes)) ice_fluxes = -mm_ice_fluxes(mm_nla:1:-1,:)
206      IF (PRESENT(gazs_sat))   gazs_sat   =  mm_gazs_sat(mm_nla:1:-1,:)
207    ELSE
208      IF (PRESENT(ccn_prec))   ccn_prec   = 0._mm_wp
209      IF (PRESENT(ice_prec))   ice_prec   = 0._mm_wp
210      IF (PRESENT(ccn_flux))   ccn_flux   = 0._mm_wp
211      IF (PRESENT(ice_fluxes)) ice_fluxes = 0._mm_wp
212      IF (PRESENT(gazs_sat))   gazs_sat   = 0._mm_wp
213    ENDIF
214  END SUBROUTINE mm_diagnostics
215
216  SUBROUTINE mm_get_radii(rcsph,rcfra,rccld)
217    !! Get characteristic radii of microphysical tracers on the vertical grid.
218    REAL(kind=mm_wp), INTENT(out), DIMENSION(:), OPTIONAL :: rcsph !! Spherical mode characteristic radius
219    REAL(kind=mm_wp), INTENT(out), DIMENSION(:), OPTIONAL :: rcfra !! Fractal mode characteristic radius
220    REAL(kind=mm_wp), INTENT(out), DIMENSION(:), OPTIONAL :: rccld !! Cloud drops mean radius
221    IF (mm_ini_aer) THEN
222      IF (PRESENT(rcsph)) rcsph = mm_rcs(mm_nla:1:-1)
223      IF (PRESENT(rcfra)) rcfra = mm_rcf(mm_nla:1:-1)
224    ELSE
225      IF (PRESENT(rcsph)) rcsph = 0._mm_wp
226      IF (PRESENT(rcfra)) rcfra = 0._mm_wp
227    ENDIF
228    IF (PRESENT(rccld)) THEN
229      IF (mm_w_clouds.AND.mm_ini_cld) THEN
230        rccld = mm_drad(mm_nla:1:-1)
231      ELSE
232        rccld = 0._mm_wp
233      ENDIF
234    ENDIF
235  END SUBROUTINE mm_get_radii
236
237END MODULE MM_MICROPHYSIC
238
Note: See TracBrowser for help on using the repository browser.