Ignore:
Timestamp:
Jan 24, 2018, 10:24:24 PM (7 years ago)
Author:
jvatant
Message:

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:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.TITAN/libf/muphytitan/mmp_gcm.f90

    r1819 r1897  
     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
    138MODULE MMP_GCM
    239  !! Interface to YAMMS for the LMDZ GCM.
     40  USE MMP_GLOBALS
    341  USE MM_LIB
    442  USE CFGPARSE
     
    644  IMPLICIT NONE
    745
    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 
    30   !> Size distribution parameters derived type.
    31   !!
    32   !! It stores the parameters of the size distribution law for Titan.
    33   !!
    34   !! The size distribution law is represented by the minimization of a sum of
    35   !! power law functions:
    36   !!
    37   !! $$
    38   !! \displaystyle n\left(r\right) = \frac{A_{0}}{C+\sum_{i=1}^{n} A_{i}\times
    39   !!                                    \left(\frac{r}{r_{c}}\right)^{-b_{i}}}
    40   !! $$
    41   TYPE, PUBLIC :: nprm
    42     !> Scaling factor.
    43     REAL(kind=mm_wp)                            :: a0
    44     !> Characterisitic radius.
    45     REAL(kind=mm_wp)                            :: rc
    46     !> Additional constant to the sum of power law.
    47     REAL(kind=mm_wp)                            :: c
    48     !> Scaling factor of each power law.
    49     REAL(kind=mm_wp), DIMENSION(:), ALLOCATABLE :: a
    50     !> Power of each power law.
    51     REAL(kind=mm_wp), DIMENSION(:), ALLOCATABLE :: b
    52   END TYPE
    53 
    54   !> Inter-moment relation set of parameters for the spherical mode.
    55   TYPE(aprm), PUBLIC, SAVE :: mmp_asp
    56   !> Inter-moment relation set of parameters for the fractal mode.
    57   TYPE(aprm), PUBLIC, SAVE :: mmp_afp
    58 
    59   !> Size-distribution law parameters of the spherical mode.
    60   TYPE(nprm), PUBLIC, SAVE :: mmp_pns
    61   !> Size-distribution law parameters of the fractal mode.
    62   TYPE(nprm), PUBLIC, SAVE :: mmp_pnf
    63 
    64   !> Data set for @f$<Q>_{SF}^{M0}@f$.
    65   TYPE(dset2d), PUBLIC, SAVE, TARGET             :: mmp_qbsf0
    66   !> Extended values of [[mmp_gcm(module):mmp_qbsf0(variable)]] dataset.
    67   REAL(kind=mm_wp), PUBLIC, SAVE, DIMENSION(2,2) :: mmp_qbsf0_e
    68   !> Data set for @f$<Q>_{SF}^{M3}@f$.
    69   TYPE(dset2d), PUBLIC, SAVE, TARGET             :: mmp_qbsf3
    70   !> Extended values of [[mmp_gcm(module):mmp_qbsf3(variable)]] dataset.
    71   REAL(kind=mm_wp), PUBLIC, SAVE, DIMENSION(2,2) :: mmp_qbsf3_e
    72   !> Data set for @f$<Q>_{FF}^{M0}@f$.
    73   TYPE(dset2d), PUBLIC, SAVE, TARGET             :: mmp_qbff0
    74   !> Extended values of [[mmp_gcm(module):mmp_qbff0(variable)]] dataset.
    75   REAL(kind=mm_wp), PUBLIC, SAVE, DIMENSION(2,2) :: mmp_qbff0_e
    76  
    77   !> Data set for linear interpolation of transfert probability (M0/CO).
    78   TYPE(dset1d), PUBLIC, SAVE, TARGET :: mmp_pco0p
    79   !> Data set for linear interpolation of transfert probability (M3/CO).
    80   TYPE(dset1d), PUBLIC, SAVE, TARGET :: mmp_pco3p
    81   !> Data set for linear interpolation of transfert probability (M0/FM).
    82   TYPE(dset1d), PUBLIC, SAVE, TARGET :: mmp_pfm0p
    83   !> Data set for linear interpolation of transfert probability (M3/FM).
    84   TYPE(dset1d), PUBLIC, SAVE, TARGET :: mmp_pfm3p
    85 
    86   !> \(b_{0}^{t}\) coefficients for Free-molecular regime kernel approximation.
    87   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/)
    88   !> \(b_{3}^{t}\) coefficients for Free-molecular regime kernel approximation.
    89   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/)
    90 
    91   !> Spherical probability transfert control flag.
    92   LOGICAL, SAVE :: mmp_w_ps2s = .true.
    93   !> Aerosol electric charge correction control flag.
    94   LOGICAL, SAVE :: mmp_w_qe   = .true.
    95 
    96 
    9746  CONTAINS
    9847   
    99   SUBROUTINE abort_program(err)
    100     !! Dump error message and abort the program.
    101     TYPE(error), INTENT(in) :: err !! Error object.
    102     WRITE(stderr,'(a)') "ERROR: "//TRIM(err%msg)
    103     CALL EXIT(err%id)
    104   END SUBROUTINE abort_program
    105 
    106 
    107   SUBROUTINE mmp_initialize(dt,df,rm,rho_aer,p_prod,tx_prod,rc_prod,rplanet,g0, air_rad,air_mmol,clouds,cfgpath)
     48  SUBROUTINE mmp_initialize(dt,p_prod,tx_prod,rc_prod,rplanet,g0, air_rad,air_mmol,clouds,cfgpath)
    10849    !! Initialize global parameters of the model.
    10950    !!
     
    11253    !! default values are suitable for production runs. 
    11354    !! @note
    114     !! If the method fails to initialize parameters (i.e. returned error is not 0). Then the model
    115     !! should probably be aborted as the global variables of the model will not be correctly setup.
     55    !! If the subroutine fails to initialize parameters, the run is aborted.
    11656    !!
    11757    !! @warning
     
    11959    !! initializes global variable that are not thread private.
    12060    !!
    121     !! '''
     61    !! ```
    12262    !! !$OMP SINGLE
    12363    !! call mmp_initialize(...)
    12464    !! !$OMP END SINGLE
     65    !! ```
    12566    !!
    12667    REAL(kind=mm_wp), INTENT(in)           :: dt
    12768      !! Microphysics timestep in seconds.
    128     REAL(kind=mm_wp), INTENT(in)           :: df
    129       !! Fractal dimension of fractal aerosol.
    130     REAL(kind=mm_wp), INTENT(in)           :: rm
    131       !! Monomer radius in meter.
    132     REAL(kind=mm_wp), INTENT(in)           :: rho_aer
    133       !! Aerosol density in \(kg.m^{-3}\).
    13469    REAL(kind=mm_wp), INTENT(in)           :: p_prod
    13570      !!  Aerosol production pressure level in Pa.
     
    15186      !! Internal microphysic configuration file.
    15287
    153     INTEGER          :: coag_choice
    154     REAL(kind=mm_wp) :: fiad_max, fiad_min
    155     LOGICAL          :: w_h_prod, w_h_sed, w_h_coag, w_c_sed, w_c_nucond, &
    156                         no_fiadero, fwsed_m0, fwsed_m3
    157     TYPE(error)      :: err
     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
    15893    INTEGER                                           :: i
    15994    TYPE(cfgparser)                                   :: cparser
     
    186121   
    187122    ! 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)
    188126    ! the following parameters are primarily used to test and debug YAMMS.
    189127    ! They are set in an optional configuration file and default to suitable values for production runs.
Note: See TracChangeset for help on using the changeset viewer.