source: trunk/LMDZ.TITAN/libf/muphytitan/mmp_gcm.f90 @ 1897

Last change on this file since 1897 was 1897, checked in by jvatant, 7 years ago

Making Titan's hazy again - part II
+ Major updates of J.Burgalat YAMMS library and optical coupling, including :
++ Added the routines for haze optics inside YAMMS
++ Calling rad. transf. with interactive haze is plugged
in but should stay unactive as long as the microphysics is
in test phase : cf "uncoupl_optic_haze" flag : true for now !
++ Also some sanity checks for negative tendencies and
some others upkeep of YAMMS model
+ Also added a temporary CPP key USE_QTEST in physiq_mod
that enables to have microphysical tendencies separated
from dynamics for debugging and test phases
-- JVO and JB

File size: 13.6 KB
Line 
1! Copyright 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 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
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 license and that you accept its terms.
33
34!! file: mmp_gcm.f90
35!! summary: YAMMS interfaces for the LMDZ GCM.
36!! author: J. Burgalat
37!! date: 2017
38MODULE MMP_GCM
39  !! Interface to YAMMS for the LMDZ GCM.
40  USE MMP_GLOBALS
41  USE MM_LIB
42  USE CFGPARSE
43  USE DATASETS
44  IMPLICIT NONE
45
46  CONTAINS
47   
48  SUBROUTINE mmp_initialize(dt,p_prod,tx_prod,rc_prod,rplanet,g0, air_rad,air_mmol,clouds,cfgpath)
49    !! Initialize global parameters of the model.
50    !!
51    !! The function initializes all the global parameters of the model from direct input.
52    !! Boolean (and Fiadero) parameters are optional as they are rather testing parameters. Their
53    !! default values are suitable for production runs. 
54    !! @note
55    !! If the subroutine fails to initialize parameters, the run is aborted.
56    !!
57    !! @warning
58    !! If OpenMP is activated, this subroutine must be called in an $OMP SINGLE statement as it
59    !! initializes global variable that are not thread private.
60    !!
61    !! ```
62    !! !$OMP SINGLE
63    !! call mmp_initialize(...)
64    !! !$OMP END SINGLE
65    !! ```
66    !!
67    REAL(kind=mm_wp), INTENT(in)           :: dt
68      !! Microphysics timestep in seconds.
69    REAL(kind=mm_wp), INTENT(in)           :: p_prod
70      !!  Aerosol production pressure level in Pa.
71    REAL(kind=mm_wp), INTENT(in)           :: tx_prod
72      !! Spherical aerosol mode production rate in \(kg.m^{-2}.s^{-1}\).
73    REAL(kind=mm_wp), INTENT(in)           :: rc_prod
74      !! Spherical mode characteristic radius for production in meter.
75    REAL(kind=mm_wp), INTENT(in)           :: rplanet
76      !! Planet radius in meter
77    REAL(kind=mm_wp), INTENT(in)           :: g0
78      !! Planet gravity acceleration at ground level in \(m.s^{-2}\).
79    REAL(kind=mm_wp), INTENT(in)           :: air_rad
80      !! Air molecules mean radius in meter.
81    REAL(kind=mm_wp), INTENT(in)           :: air_mmol
82      !! Air molecules mean molar mass in \(kg.mol^{-1}\).
83    LOGICAL, INTENT(in)                    :: clouds
84      !! Clouds microphysics control flag.
85    CHARACTER(len=*), INTENT(in), OPTIONAL :: cfgpath
86      !! Internal microphysic configuration file.
87
88    INTEGER                                           :: coag_choice
89    REAL(kind=mm_wp)                                  :: fiad_max, fiad_min,df,rm,rho_aer
90    LOGICAL                                           :: w_h_prod, w_h_sed, w_h_coag, w_c_sed, w_c_nucond, &
91                                                         no_fiadero, fwsed_m0, fwsed_m3
92    TYPE(error)                                       :: err
93    INTEGER                                           :: i
94    TYPE(cfgparser)                                   :: cparser
95    CHARACTER(len=st_slen)                            :: spcpath,pssfile,mqfile
96    CHARACTER(len=st_slen), DIMENSION(:), ALLOCATABLE :: species
97    REAL(kind=mm_wp), DIMENSION(:), ALLOCATABLE       :: tmp
98
99    w_h_prod    = .true.
100    w_h_sed     = .true.
101    w_h_coag    = .true.
102    w_c_sed     = clouds
103    w_c_nucond  = clouds
104    fwsed_m0    = .true.
105    fwsed_m3    = .false.
106    no_fiadero  = .false.
107    fiad_min    = 0.1_mm_wp
108    fiad_max    = 10._mm_wp
109    coag_choice = 7
110
111    WRITE(*,'(a)') "##### MMP_GCM SPEAKING #####"
112    WRITE(*,'(a)') "I will initialize ze microphysics model in moments YAMMS"
113    WRITE(*,'(a)') "On error I will simply abort the program. Stay near your computer !"
114    WRITE(*,*)
115    WRITE(*,'(a)') "Reading muphys configuration file ("//trim(cfgpath)//")..."
116    err = cfg_read_config(cparser,TRIM(cfgpath),.true.)
117    IF (err /= 0) THEN
118      ! RETURN AN ERROR !!
119      call abort_program(err)
120    ENDIF
121   
122    ! YAMMS internal parameters:
123    err = mm_check_opt(cfg_get_value(cparser,"rm",rm),rm,50e-9_mm_wp,mm_log)
124    err = mm_check_opt(cfg_get_value(cparser,"df",df),df,2._mm_wp,mm_log)
125    err = mm_check_opt(cfg_get_value(cparser,"rho_aer",rho_aer),rho_aer,1000._mm_wp,mm_log)
126    ! the following parameters are primarily used to test and debug YAMMS.
127    ! They are set in an optional configuration file and default to suitable values for production runs.
128    err = mm_check_opt(cfg_get_value(cparser,"haze_production",w_h_prod)    ,w_h_prod   ,.true.   ,mm_log)
129    err = mm_check_opt(cfg_get_value(cparser,"haze_sedimentation",w_h_sed)  ,w_h_sed    ,.true.   ,mm_log)
130    err = mm_check_opt(cfg_get_value(cparser,"haze_coagulation",w_h_coag)   ,w_h_coag   ,.true.   ,mm_log)
131    err = mm_check_opt(cfg_get_value(cparser,"clouds_sedimentation",w_c_sed),w_c_sed    ,clouds   ,mm_log)
132    err = mm_check_opt(cfg_get_value(cparser,"clouds_nucl_cond",w_c_nucond) ,w_c_nucond ,clouds   ,mm_log)
133    err = mm_check_opt(cfg_get_value(cparser,"wsed_m0",fwsed_m0)            ,fwsed_m0   ,.true.   ,mm_log)
134    err = mm_check_opt(cfg_get_value(cparser,"wsed_m3",fwsed_m3)            ,fwsed_m3   ,.false.  ,mm_log)
135    err = mm_check_opt(cfg_get_value(cparser,"no_fiadero",no_fiadero)       ,no_fiadero ,.false.  ,mm_log)
136    err = mm_check_opt(cfg_get_value(cparser,"fiadero_min_ratio",fiad_min)  ,fiad_min   ,0.1_mm_wp,mm_log)
137    err = mm_check_opt(cfg_get_value(cparser,"fiadero_max_ratio",fiad_max)  ,fiad_max   ,10._mm_wp,mm_log)
138    err = mm_check_opt(cfg_get_value(cparser,"haze_coag_interactions",coag_choice),coag_choice,7,mm_log)
139
140    ! Retrieve clouds species configuration file
141    spcpath = ''
142    IF (clouds) THEN
143      err = mm_check_opt(cfg_get_value(cparser,"specie_cfg",spcpath), spcpath, wlog=mm_log)
144      IF (err/=0) call abort_program(err)
145    ENDIF
146
147    ! YAMMS initialization.
148    err = mm_global_init_0(dt,df,rm,rho_aer,p_prod,tx_prod,rc_prod,rplanet,g0, &
149                           air_rad,air_mmol,coag_choice,clouds,spcpath,  &
150                           w_h_prod,w_h_sed,w_h_coag,w_c_nucond,  &
151                           w_c_sed,fwsed_m0,fwsed_m3, &
152                           no_fiadero,fiad_min,fiad_max)
153    IF (err /= 0) call abort_program(err)
154
155    ! Extra initialization (needed for YAMMS method interfaces)
156    err = mm_check_opt(cfg_get_value(cparser, "transfert_probability", mmp_w_ps2s), mmp_w_ps2s, wlog=mm_log)
157    IF (err/=0) call abort_program(err)
158    err = mm_check_opt(cfg_get_value(cparser, "electric_charging"    , mmp_w_qe  ), mmp_w_qe, wlog=mm_log)
159    IF (err/=0) call abort_program(err)
160
161    ! initialize transfert probabilities look-up tables
162    IF (mm_w_haze_coag .AND. mmp_w_ps2s) THEN
163      err = mm_check_opt(cfg_get_value(cparser, "ps2s_file", pssfile), pssfile)
164      IF (err /= 0) call abort_program(err)
165
166      IF (.NOT.read_dset(pssfile,'p_m0_co',mmp_pco0p)) THEN
167        call abort_program(error("Cannot get 'p_m0_co' from "//pssfile,-1))
168      ENDIF
169      IF (.NOT.read_dset(pssfile,'p_m3_co',mmp_pco3p)) THEN
170        call abort_program(error("Cannot get 'p_m3_co' from "//pssfile,-1))
171      ENDIF
172      IF (.NOT.read_dset(pssfile,'p_m0_fm',mmp_pfm0p)) THEN
173        call abort_program(error("Cannot get 'p_m0_fm' from "//pssfile,-1))
174      ENDIF
175      IF (.NOT.read_dset(pssfile,'p_m3_fm',mmp_pfm3p)) THEN
176        call abort_program(error("Cannot get 'p_m3_fm' from "//pssfile,-1))
177      ENDIF
178    ENDIF
179    ! initialize mean electric correction look-up tables
180    IF (mm_w_haze_coag .AND. mmp_w_qe) THEN
181      err = mm_check_opt(cfg_get_value(cparser, "mq_file", mqfile), mqfile)
182      IF (err /= 0) call abort_program(err)
183
184      IF (.NOT.read_dset(mqfile,'qbsf0',mmp_qbsf0)) THEN
185        call abort_program(error("Cannot get 'qbsf0' from "//mqfile,-1))
186      ELSE
187        mmp_qbsf0_e(1,1) = MINVAL(mmp_qbsf0%x)
188        mmp_qbsf0_e(1,2) = MAXVAL(mmp_qbsf0%x)
189        mmp_qbsf0_e(2,1) = MINVAL(mmp_qbsf0%y)
190        mmp_qbsf0_e(2,2) = MAXVAL(mmp_qbsf0%y)
191      ENDIF
192      IF (.NOT.read_dset(mqfile,'qbsf3',mmp_qbsf3)) THEN
193        call abort_program(error("Cannot get 'qbsf3' from "//mqfile,-1))
194      ELSE
195        mmp_qbsf3_e(1,1) = MINVAL(mmp_qbsf3%x)
196        mmp_qbsf3_e(1,2) = MAXVAL(mmp_qbsf3%x)
197        mmp_qbsf3_e(2,1) = MINVAL(mmp_qbsf3%y)
198        mmp_qbsf3_e(2,2) = MAXVAL(mmp_qbsf3%y)
199      ENDIF
200      IF (.NOT.read_dset(mqfile,'qbff0',mmp_qbff0)) THEN
201        call abort_program(error("Cannot get 'qbff0' from "//mqfile,-1))
202      ELSE
203        mmp_qbff0_e(1,1) = MINVAL(mmp_qbff0%x)
204        mmp_qbff0_e(1,2) = MAXVAL(mmp_qbff0%x)
205        mmp_qbff0_e(2,1) = MINVAL(mmp_qbff0%y)
206        mmp_qbff0_e(2,2) = MAXVAL(mmp_qbff0%y)
207      ENDIF
208    ENDIF
209    ! spherical mode inter-moments function parameters
210    IF (.NOT.cfg_has_section(cparser,'alpha_s')) call abort_program(error("Cannot find [alpha_s] section",-1))
211    err = read_aprm(cparser,'alpha_s',mmp_asp)
212    IF (err /= 0) call abort_program(error("alpha_s: "//TRIM(err%msg),-1))
213    ! fractal mode inter-moments function parameters
214    IF (.NOT.cfg_has_section(cparser,'alpha_f')) call abort_program(error("Cannot find [alpha_f] section",-1))
215    err = read_aprm(cparser,'alpha_f',mmp_afp)
216    IF (err /= 0) call abort_program(error("alpha_s: "//TRIM(err%msg),-1))
217
218    ! get size-distribution laws parameters
219    IF (.NOT.cfg_has_section(cparser,'dndr_s')) call abort_program(error("Cannot find [dndr_s] section",-2))
220    err = read_nprm(cparser,'dndr_s',mmp_pns)
221    IF (err /= 0) call abort_program(error("dndr_s: "//TRIM(err%msg),-2))
222    IF (.NOT.cfg_has_section(cparser,'dndr_f')) call abort_program(error("Cannot find [dndr_f] section",-2))
223    err = read_nprm(cparser,'dndr_f',mmp_pnf)
224    IF (err /= 0) call abort_program(error("dndr_f: "//TRIM(err%msg),-2))
225
226    ! btk coefficients
227    IF (.NOT.cfg_has_section(cparser,'btks')) call abort_program(error("Cannot find [btks] section",-1))
228    err = cfg_get_value(cparser,"btks/bt0",tmp) ; IF (err/=0) call abort_program(error("bt0: "//TRIM(err%msg),-1))
229    IF (SIZE(tmp) /= 5)  call abort_program(error("bt0: Inconsistent number of coefficients",-1))
230    mmp_bt0 = tmp
231    err = cfg_get_value(cparser,"btks/bt3",tmp) ; IF (err/=0) call abort_program(error("bt3: "//TRIM(err%msg),-1))
232    IF (SIZE(tmp) /= 5)  call abort_program(error("bt3: Inconsistent number of coefficients",-1))
233    mmp_bt3 = tmp
234
235    ! dump parameters ...
236    WRITE(*,'(a)')        "========= MUPHYS PARAMETERS ==========="
237    WRITE(*,'(a,L2)')     "transfert_probability: ", mmp_w_ps2s
238    WRITE(*,'(a,L2)')     "electric_charging    : ", mmp_w_qe
239    call mm_dump_parameters()
240     
241  END SUBROUTINE mmp_initialize
242
243  FUNCTION read_aprm(parser,sec,pp) RESULT(err)
244    !! Read and store [[mmp_gcm(module):aprm(type)]] parameters.
245    TYPE(cfgparser), INTENT(in)  :: parser !! Configuration parser
246    CHARACTER(len=*), INTENT(in) :: sec    !! Name of the section that contains the parameters.
247    TYPE(aprm), INTENT(out)      :: pp     !! [[mmp_gcm(module):aprm(type)]] object that stores the parameters values.
248    TYPE(error) :: err                     !! Error status of the function.
249    err = cfg_get_value(parser,TRIM(sec)//'/a',pp%a) ; IF (err /= 0) RETURN
250    err = cfg_get_value(parser,TRIM(sec)//'/b',pp%b) ; IF (err /= 0) RETURN
251    err = cfg_get_value(parser,TRIM(sec)//'/c',pp%c) ; IF (err /= 0) RETURN
252    IF (SIZE(pp%a) /= SIZE(pp%b) .OR. SIZE(pp%a) /= SIZE(pp%c)) &
253    err = error("Inconsistent number of coefficients (a,b, and c must have the same size)",-1)
254    RETURN
255  END FUNCTION read_aprm
256
257  FUNCTION read_nprm(parser,sec,pp) RESULT(err)
258    !! Read and store [[mmp_gcm(module):nprm(type)]] parameters.
259    TYPE(cfgparser), INTENT(in)  :: parser !! Configuration parser
260    CHARACTER(len=*), INTENT(in) :: sec    !! Name of the section that contains the parameters.
261    TYPE(nprm), INTENT(out)      :: pp     !! [[mmp_gcm(module):nprm(type)]] object that stores the parameters values.
262    TYPE(error) :: err                     !! Error status of the function.
263    err = cfg_get_value(parser,TRIM(sec)//'/rc',pp%rc) ; IF (err /= 0) RETURN
264    err = cfg_get_value(parser,TRIM(sec)//'/a0',pp%a0) ; IF (err /= 0) RETURN
265    err = cfg_get_value(parser,TRIM(sec)//'/c',pp%c)   ; IF (err /= 0) RETURN
266    err = cfg_get_value(parser,TRIM(sec)//'/a',pp%a)   ; IF (err /= 0) RETURN
267    err = cfg_get_value(parser,TRIM(sec)//'/b',pp%b)   ; IF (err /= 0) RETURN
268    IF (SIZE(pp%a) /= SIZE(pp%b)) &
269      err = error("Inconsistent number of coefficients (a and b must have the same size)",3)
270    RETURN
271  END FUNCTION read_nprm
272
273END MODULE MMP_GCM
274
Note: See TracBrowser for help on using the repository browser.