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

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

Making Titan's hazy again, part I
+ Added the source folder libf/muphytitan which contains

YAMMS ( Titan's microphysical model ) from J. Burgalat

+ Modif. compilation files linked to this change
JVO

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