Ignore:
Timestamp:
Oct 12, 2023, 10:30:22 AM (15 months ago)
Author:
slebonnois
Message:

BBT : Update for the titan microphysics and cloud model

File:
1 edited

Legend:

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

    r1897 r3083  
    1 ! Copyright 2013-2015,2017 Université de Reims Champagne-Ardenne
     1! Copyright 2013-2015,2017,2022 Université de Reims Champagne-Ardenne
    22! Contributor: J. Burgalat (GSMA, URCA)
    33! email of the author : jeremie.burgalat@univ-reims.fr
    4 ! 
     4!
    55! This software is a computer program whose purpose is to compute
    66! microphysics processes using a two-moments scheme.
    7 ! 
     7!
    88! 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, 
     9! abiding by the rules of distribution of free software.  You can  use,
    1010! modify and/ or redistribute the software under the terms of the CeCILL
    1111! license as circulated by CEA, CNRS and INRIA at the following URL
    12 ! "http://www.cecill.info". 
    13 ! 
     12! "http://www.cecill.info".
     13!
    1414! As a counterpart to the access to the source code and  rights to copy,
    1515! modify and redistribute granted by the license, users are provided only
    1616! with a limited warranty  and the software's author,  the holder of the
    1717! economic rights,  and the successive licensors  have only  limited
    18 ! liability. 
    19 ! 
     18! liability.
     19!
    2020! In this respect, the user's attention is drawn to the risks associated
    2121! with loading,  using,  modifying and/or developing or reproducing the
     
    2525! professionals having in-depth computer knowledge. Users are therefore
    2626! 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 ! 
     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!
    3131! The fact that you are presently reading this means that you have had
    3232! knowledge of the CeCILL license and that you accept its terms.
     
    3535!! summary: YAMMS/MP2M model external methods
    3636!! author: J. Burgalat
    37 !! date: 2013-2015,2017
     37!! date: 2013-2015,2017,2022
    3838!!
    3939!! This file contains the definitions of all external methods that should be defined
    40 !! for mp2m library. 
    41 !! 
    42 !! All the methods defined here satisify the interfaces defined in __m_interfaces__ module 
     40!! for mp2m library.
     41!!
     42!! All the methods defined here satisify the interfaces defined in __m_interfaces__ module
    4343!! of YAMMS library.
    4444
    4545PURE FUNCTION mm_alpha_s(k) RESULT (res)
    4646  !! Inter-moment relation for spherical aerosols size distribution law.
    47   !! 
    48   !! The method computes the relation between the kth order moment and the 0th 
     47  !!
     48  !! The method computes the relation between the kth order moment and the 0th
    4949  !! order moment of the size-distribution law:
    5050  !!
     
    5858  res = SUM(dexp(mmp_asp%a*k**2+mmp_asp%b*k+mmp_asp%c))
    5959  RETURN
    60 END FUNCTION mm_alpha_s 
     60END FUNCTION mm_alpha_s
    6161
    6262PURE FUNCTION mm_alpha_f(k) RESULT (res)
     
    8181  !!
    8282  !! @warning
    83   !! Here, the method assumes the datasets define the probability for __spherical__ particles to 
     83  !! Here, the method assumes the datasets define the probability for __spherical__ particles to
    8484  !! be transferred in the __fractal__ mode, but returns the proportion of particles that remains
    8585  !! in the mode (which is expected by mp2m model).
    8686  !!
    8787  !! @attention
    88   !! If value cannot be interpolated, the method aborts the program. Normally, it cannot happen 
     88  !! If value cannot be interpolated, the method aborts the program. Normally, it cannot happen
    8989  !! since we extrapolate the probability for characteristic radius value out of range.
    9090  !!
    9191  !! @attention
    92   !! Consequently, as the probability can only range from 0 to 1, it is wise to ensure that the 
    93   !! look-up table limits this range: To do so, one can just add two values at the start and end 
     92  !! Consequently, as the probability can only range from 0 to 1, it is wise to ensure that the
     93  !! look-up table limits this range: To do so, one can just add two values at the start and end
    9494  !! of the table with probabilities respectively set to 0 and 1.
    9595  USE LINTDSET
     
    111111  TYPE(dset1d), POINTER :: pp
    112112  res = 1._mm_wp
    113   IF (rcs <= 0.0_mm_wp .OR. .NOT.mmp_w_ps2s) RETURN 
     113  IF (rcs <= 0.0_mm_wp .OR. .NOT.mmp_w_ps2s) RETURN
    114114  SELECT CASE(k+flow)
    115115    CASE(0)      ; pp => mmp_pco0p ! 0 = 0 + 0 -> M0 / CO
     
    119119    CASE DEFAULT ; RETURN
    120120  END SELECT
    121   IF (.NOT.hdcd_lint_dset(rcs,pp,locate_reg_ext,res)) THEN 
     121  IF (.NOT.hdcd_lint_dset(rcs,pp,locate_reg_ext,res)) THEN
    122122    WRITE(*,'(a)') "mm_moments:ps2s_sc: Cannot interpolate transfert probability"
    123123    call EXIT(10)
    124124  ELSE
    125     ! 05102017: do not care anymore for bad extrapolation: 
     125    ! 05102017: do not care anymore for bad extrapolation:
    126126    ! Bound probability value between 0 and 1
    127127    ! note: The input look-up table still must have strict monotic variation or
     
    139139  !! kernel as a function of the temperature, pressure and the characteristic radius of
    140140  !! the mode involved in the coagulation.
    141   !! 
     141  !!
    142142  !! Modes are referred by a two letters uppercase string with the combination of:
    143143  !!
    144144  !! - S : spherical mode
    145145  !! - F : fractal mode
    146   !! 
     146  !!
    147147  !! For example, SS means intra-modal coagulation for spherical particles.
    148148  !!
     
    159159  CHARACTER(len=2), INTENT(in)  :: modes !! Interaction mode (a combination of [S,F]).
    160160  REAL(kind=mm_wp), INTENT(in)  :: temp  !! Temperature (K).
    161   REAL(kind=mm_wp), INTENT(in)  :: pres  !! Pressure level (Pa). 
     161  REAL(kind=mm_wp), INTENT(in)  :: pres  !! Pressure level (Pa).
    162162  REAL(kind=mm_wp) :: res                !! Electric charging correction.
    163163  INTEGER       :: chx,np
    164164  REAL(kind=mm_wp) :: vmin,vmax
    165165  REAL(kind=mm_wp) :: r_tmp, t_tmp
    166   chx = 0 
     166  chx = 0
    167167  IF (.NOT.mmp_w_qe) THEN
    168168    res = 1._mm_wp
     
    177177  SELECT CASE(chx)
    178178    CASE(2)      ! M0/SS
    179       res = 1._mm_wp 
     179      res = 1._mm_wp
    180180    CASE(4)      ! M0/SF
    181181      ! Fix max values of input parameters
     
    211211PURE FUNCTION mm_get_btk(t,k) RESULT(res)
    212212  !! Get the \(b_{k}^{T}\) coefficient of the Free Molecular regime.
    213   !! 
     213  !!
    214214  !! The method get the value of the Free-molecular regime coagulation pre-factor \(b_{k}^{T}\).
    215   !! For more details about this coefficient, please read [Coagulation](page/haze.html#coagulation) 
     215  !! For more details about this coefficient, please read [Coagulation](page/haze.html#coagulation)
    216216  !! documentation page.
    217217  !!
     
    244244                                  tsut = 109._mm_wp,    &
    245245                                  tref = 293._mm_wp
    246   res = eta0 *dsqrt(t/tref)*(1._mm_wp+tsut/tref)/(1._mm_wp+tsut/t)
     246  res = eta0 * dsqrt(t/tref) * (1._mm_wp + tsut/tref) / (1._mm_wp + tsut/t)
    247247  RETURN
    248248END FUNCTION mm_eta_g
Note: See TracChangeset for help on using the changeset viewer.