MODULE MMP_GLOBALS !! Interface to YAMMS for the LMDZ GCM. USE MM_LIB USE DATASETS IMPLICIT NONE PUBLIC !> Alpha function parameters. !! !! It stores the parameters of the inter-moments relation functions. !! !! The inter-moments relation function is represented by the sum of exponential !! quadratic expressions: !! !! $$ !! \displaystyle \alpha(k) = \sum_{i=1}^{n} \exp\left( a_{i}\times k^{2} + !! b_{i}\times k^{2} +c_{i}\right) !! $$ TYPE, PUBLIC :: aprm !> Quadratic coefficients of the quadratic expressions. REAL(kind=mm_wp), DIMENSION(:), ALLOCATABLE :: a !> Linear coefficients of the quadratic expressions. REAL(kind=mm_wp), DIMENSION(:), ALLOCATABLE :: b !> Free term of the quadratic expressions. REAL(kind=mm_wp), DIMENSION(:), ALLOCATABLE :: c END TYPE !> Inter-moment relation set of parameters for the spherical mode. TYPE(aprm), PUBLIC, SAVE :: mmp_asp !> Inter-moment relation set of parameters for the fractal mode. TYPE(aprm), PUBLIC, SAVE :: mmp_afp !> Data set for @f$_{SF}^{M0}@f$. TYPE(dset2d), PUBLIC, SAVE, TARGET :: mmp_qbsf0 !> Extended values of [[mmp_gcm(module):mmp_qbsf0(variable)]] dataset. REAL(kind=mm_wp), PUBLIC, SAVE, DIMENSION(2,2) :: mmp_qbsf0_e !> Data set for @f$_{SF}^{M3}@f$. TYPE(dset2d), PUBLIC, SAVE, TARGET :: mmp_qbsf3 !> Extended values of [[mmp_gcm(module):mmp_qbsf3(variable)]] dataset. REAL(kind=mm_wp), PUBLIC, SAVE, DIMENSION(2,2) :: mmp_qbsf3_e !> Data set for @f$_{FF}^{M0}@f$. TYPE(dset2d), PUBLIC, SAVE, TARGET :: mmp_qbff0 !> Extended values of [[mmp_gcm(module):mmp_qbff0(variable)]] dataset. REAL(kind=mm_wp), PUBLIC, SAVE, DIMENSION(2,2) :: mmp_qbff0_e !> Data set for linear interpolation of transfert probability (M0/CO). TYPE(dset1d), PUBLIC, SAVE, TARGET :: mmp_pco0p !> Data set for linear interpolation of transfert probability (M3/CO). TYPE(dset1d), PUBLIC, SAVE, TARGET :: mmp_pco3p !> Data set for linear interpolation of transfert probability (M0/FM). TYPE(dset1d), PUBLIC, SAVE, TARGET :: mmp_pfm0p !> Data set for linear interpolation of transfert probability (M3/FM). TYPE(dset1d), PUBLIC, SAVE, TARGET :: mmp_pfm3p !> \(b_{0}^{t}\) coefficients for Free-molecular regime kernel approximation. 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/) !> \(b_{3}^{t}\) coefficients for Free-molecular regime kernel approximation. 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/) !> Spherical probability transfert control flag. LOGICAL, SAVE :: mmp_w_ps2s = .true. !> Aerosol electric charge correction control flag. LOGICAL, SAVE :: mmp_w_qe = .true. CONTAINS SUBROUTINE abort_program(err) !! Dump error message and abort the program. TYPE(error), INTENT(in) :: err !! Error object. WRITE(stderr,'(a)') "ERROR: "//TRIM(err%msg) CALL EXIT(err%id) END SUBROUTINE abort_program END MODULE MMP_GLOBALS