1 | MODULE MP2M_MICROPHYSICS |
---|
2 | !============================================================================ |
---|
3 | ! |
---|
4 | ! Purpose |
---|
5 | ! ------- |
---|
6 | ! Interface to main microphysics subroutine. |
---|
7 | ! The interface computes all aerosols microphysics processes in a single call. |
---|
8 | ! |
---|
9 | ! The module contains two methods: |
---|
10 | ! - mm_muphys(m3as_prod,dm0a_s,dm3a_s,dm0a_f,dm3a_f) |
---|
11 | ! - mm_diagnostics(dt,aer_prec,aer_s_w,aer_f_w,aer_s_flux,aer_f_flux,rc_sph,rc_fra) |
---|
12 | ! |
---|
13 | ! Authors |
---|
14 | ! ------- |
---|
15 | ! B. de Batz de Trenquelléon, J. Burgalat (11/2024) |
---|
16 | ! |
---|
17 | !============================================================================ |
---|
18 | |
---|
19 | USE MP2M_MPREC |
---|
20 | USE MP2M_GLOBALS |
---|
21 | USE MP2M_HAZE |
---|
22 | USE MP2M_METHODS |
---|
23 | IMPLICIT NONE |
---|
24 | |
---|
25 | PUBLIC :: mm_muphys, mm_diagnostics |
---|
26 | |
---|
27 | CONTAINS |
---|
28 | |
---|
29 | FUNCTION mm_muphys(m3as_prod,dm0a_s,dm3a_s,dm0a_f,dm3a_f) RESULT(ret) |
---|
30 | !! Compute the evolution of moments tracers through haze microphysics processes. |
---|
31 | !! |
---|
32 | !! This method computes the evolution of all the microphysics tracers, given under the form |
---|
33 | !! of moments during a time step. |
---|
34 | !! |
---|
35 | !! The method requires that global variables of the model (i.e. variables declared in mm_globals |
---|
36 | !! module) are initialized/updated correctly (see mm_global_init, mm_column_init, and mm_aerosols_init). |
---|
37 | !! |
---|
38 | !! The tendencies returned by the method are defined on the vertical __layers__ of the model from the __GROUND__ to |
---|
39 | !! the __TOP__ of the atmosphere. They should be added to the input variables used in the initialization methods |
---|
40 | !! before the latter are called to initialize a new step. |
---|
41 | !! |
---|
42 | |
---|
43 | ! Production of the 3rd order moment of the spherical mode distribution (m3.m-2). |
---|
44 | REAL(kind=mm_wp), INTENT(in), DIMENSION(:) :: m3as_prod |
---|
45 | ! Tendency of the 0th order moment of the spherical mode distribution (m-2). |
---|
46 | REAL(kind=mm_wp), INTENT(out), DIMENSION(:) :: dm0a_s |
---|
47 | ! Tendency of the 3rd order moment of the spherical mode distribution (m3.m-2). |
---|
48 | REAL(kind=mm_wp), INTENT(out), DIMENSION(:) :: dm3a_s |
---|
49 | ! Tendency of the 0th order moment of the fractal mode distribution (m-2). |
---|
50 | REAL(kind=mm_wp), INTENT(out), DIMENSION(:) :: dm0a_f |
---|
51 | ! Tendency of the 3rd order moment of the fractal mode distribution (m3.m-2). |
---|
52 | REAL(kind=mm_wp), INTENT(out), DIMENSION(:) :: dm3a_f |
---|
53 | |
---|
54 | ! .true. on succes (i.e. model has been initialized at least once previously), .false. otherwise. |
---|
55 | LOGICAL :: ret |
---|
56 | |
---|
57 | ! Local variables. |
---|
58 | ! Production of the spherical aerosols (m3.m-3). |
---|
59 | REAL(kind=mm_wp), DIMENSION(:), ALLOCATABLE :: m3a_s_prod |
---|
60 | ALLOCATE(m3a_s_prod(mm_nla)) |
---|
61 | |
---|
62 | ret = (mm_ini_col.AND.mm_ini_aer) |
---|
63 | |
---|
64 | IF (.NOT.ret) RETURN |
---|
65 | |
---|
66 | ! Reverse vectors so they go from top to ground |
---|
67 | ! @note: mm_dzlev is already from top to ground |
---|
68 | m3a_s_prod = m3as_prod(mm_nla:1:-1) / mm_dzlev(:) |
---|
69 | |
---|
70 | ! Calls haze microphysics |
---|
71 | call mm_haze_microphysics(m3a_s_prod,dm0a_s,dm3a_s,dm0a_f,dm3a_f) |
---|
72 | |
---|
73 | ! Reverse vectors so they go from ground to top |
---|
74 | dm0a_s = dm0a_s(mm_nla:1:-1) * mm_dzlev(mm_nla:1:-1) |
---|
75 | dm3a_s = dm3a_s(mm_nla:1:-1) * mm_dzlev(mm_nla:1:-1) |
---|
76 | dm0a_f = dm0a_f(mm_nla:1:-1) * mm_dzlev(mm_nla:1:-1) |
---|
77 | dm3a_f = dm3a_f(mm_nla:1:-1) * mm_dzlev(mm_nla:1:-1) |
---|
78 | |
---|
79 | RETURN |
---|
80 | END FUNCTION mm_muphys |
---|
81 | |
---|
82 | |
---|
83 | SUBROUTINE mm_diagnostics(dt,aer_s_prec,aer_f_prec,aer_s_w,aer_f_w,aer_s_flux,aer_f_flux,rc_sph,rc_fra) |
---|
84 | !! Get various diagnostic fields of the microphysics. |
---|
85 | !! |
---|
86 | !! @note |
---|
87 | !! Fluxes values are always negative as they account for sedimentation fluxes. They are set as |
---|
88 | !! vector and are ordered from __GROUND__ to __TOP__. |
---|
89 | !! |
---|
90 | !! @note |
---|
91 | !! Precipitations are always positive and defined in kg.m-2.s-1. |
---|
92 | !! |
---|
93 | |
---|
94 | ! Physics timestep (s). |
---|
95 | REAL(kind=8), INTENT(IN) :: dt |
---|
96 | |
---|
97 | ! Aerosol precipitation (kg.m-2.s-1). |
---|
98 | REAL(kind=mm_wp), INTENT(out), OPTIONAL :: aer_s_prec |
---|
99 | REAL(kind=mm_wp), INTENT(out), OPTIONAL :: aer_f_prec |
---|
100 | |
---|
101 | ! Aerosol settling velocity (m.s-1). |
---|
102 | REAL(kind=mm_wp), INTENT(out), DIMENSION(:), OPTIONAL :: aer_s_w |
---|
103 | REAL(kind=mm_wp), INTENT(out), DIMENSION(:), OPTIONAL :: aer_f_w |
---|
104 | |
---|
105 | ! Aerosol mass flux (kg.m-2.s-1). |
---|
106 | REAL(kind=mm_wp), INTENT(out), DIMENSION(:), OPTIONAL :: aer_s_flux |
---|
107 | REAL(kind=mm_wp), INTENT(out), DIMENSION(:), OPTIONAL :: aer_f_flux |
---|
108 | |
---|
109 | ! Aerosol characteristic radius (m). |
---|
110 | REAL(kind=mm_wp), INTENT(out), DIMENSION(:), OPTIONAL :: rc_sph |
---|
111 | REAL(kind=mm_wp), INTENT(out), DIMENSION(:), OPTIONAL :: rc_fra |
---|
112 | |
---|
113 | IF (PRESENT(aer_s_prec)) aer_s_prec = ABS(mm_aers_prec) / dt |
---|
114 | IF (PRESENT(aer_f_prec)) aer_f_prec = ABS(mm_aerf_prec) / dt |
---|
115 | IF (PRESENT(aer_s_w)) aer_s_w = -mm_m3as_vsed(mm_nla:1:-1) |
---|
116 | IF (PRESENT(aer_f_w)) aer_f_w = -mm_m3af_vsed(mm_nla:1:-1) |
---|
117 | IF (PRESENT(aer_s_flux)) aer_s_flux = -mm_aer_s_flux(mm_nla:1:-1) |
---|
118 | IF (PRESENT(aer_f_flux)) aer_f_flux = -mm_aer_f_flux(mm_nla:1:-1) |
---|
119 | |
---|
120 | IF (mm_ini_aer) THEN |
---|
121 | IF (PRESENT(rc_sph)) rc_sph = mm_rcs(mm_nla:1:-1) |
---|
122 | IF (PRESENT(rc_fra)) rc_fra = mm_rcf(mm_nla:1:-1) |
---|
123 | ELSE |
---|
124 | IF (PRESENT(rc_sph)) rc_sph = 0._mm_wp |
---|
125 | IF (PRESENT(rc_fra)) rc_fra = 0._mm_wp |
---|
126 | ENDIF |
---|
127 | END SUBROUTINE mm_diagnostics |
---|
128 | |
---|
129 | END MODULE MP2M_MICROPHYSICS |
---|