Changeset 3951 for trunk/LMDZ.PLUTO/libf


Ignore:
Timestamp:
Nov 4, 2025, 5:51:18 PM (6 weeks ago)
Author:
debatzbr
Message:

Pluto PCM: Add variables, indices, and flags related to microphysical clouds
BBT

Location:
trunk/LMDZ.PLUTO/libf
Files:
10 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.PLUTO/libf/muphypluto/mp2m_globals.F90

    r3583 r3951  
    5858    PUBLIC
    5959
    60     PRIVATE :: check_r1,check_i1,check_l1,check_s1
     60    PRIVATE :: check_r1,check_i1,check_l1,check_s1,read_esp
    6161
    6262    ! ~~~~~~~~~~~~~~~~~~~
     
    6666    ! One must call the afferent subroutine to update them.
    6767   
     68    ! Haze model:
     69    !~~~~~~~~~~~~
    6870    ! Initialization control flags (cannot be updated)
    6971    PROTECTED :: mm_ini,mm_ini_col,mm_ini_aer
     
    7981    PROTECTED :: mm_m0as_min, mm_m3as_min, mm_rcs_min, mm_m0af_min, mm_m3af_min, mm_rcf_min
    8082
     83    ! Cloud model:
     84    !~~~~~~~~~~~~~
     85    ! Initialization control flags (cannot be updated)
     86    ! PROTECTED :: mm_ini_cld
     87    ! Condensible species parameters (mm_global_init)
     88    PROTECTED :: mm_nesp, mm_spcname, mm_xESPS
     89    ! Moments parameters (mm_clouds_init)
     90    ! PROTECTED :: mm_m0ccn, mm_m3ccn, mm_m3ice
     91    ! Moments parameters (derived, are updated with moments parameters)
     92    ! PROTECTED :: mm_drad, mm_drho
     93    ! Thresholds parameters
     94    ! PROTECTED :: mm_m0ccn_min, mm_m3cld_min
     95
    8196    ! ~~~~~~~~~~~~~
    8297    ! Control flags
    8398    ! ~~~~~~~~~~~~~
     99    ! Haze model:
     100    !~~~~~~~~~~~~
    84101    ! Enable/Disable haze production.
    85102    LOGICAL, SAVE :: mm_w_haze_prod = .true.
     
    99116    LOGICAL, SAVE :: mm_w_qe   = .true.
    100117
     118    ! Cloud model:
     119    !~~~~~~~~~~~~~
     120    ! Enable/Disable clouds microphysics.
     121    LOGICAL, SAVE :: mm_call_clouds = .false.
     122
    101123    ! Enable/Disable QnD debug mode (can be used for devel).
    102124    LOGICAL, SAVE :: mm_debug = .false.
     
    144166    ! Free parameters
    145167    ! ~~~~~~~~~~~~~~~
     168    ! Haze model:
     169    !~~~~~~~~~~~~
    146170    ! Spherical aerosol production pressure level (Pa).
    147171    REAL(kind=mm_wp), SAVE :: mm_p_prod = 1.e-2_mm_wp
     
    169193    ! Characteristic radius minimum threshold for the fractal mode.
    170194    REAL(kind=mm_wp), SAVE :: mm_rcf_min = 1.e-9_mm_wp
     195
     196    ! Cloud model:
     197    !~~~~~~~~~~~~~
     198    ! Total number of cloud condensation nuclei minimum threshold.
     199    ! REAL(kind=mm_wp), SAVE :: mm_m0ccn_min = 1.e-8_mm_wp
     200    ! Total volume of cloud drop minimum threshold.
     201    ! REAL(kind=mm_wp), SAVE :: mm_m3cld_min = 1.e-35_mm_wp
     202    ! Characteristic cloud drop radius minimum threshold.
     203    ! REAL(kind=mm_wp), SAVE :: mm_drad_min = 1.e-9_mm_wp
     204    ! Characteristic cloud drop radius Maximum threshold.
     205    ! REAL(kind=mm_wp), SAVE :: mm_drad_max = 1.e-2_mm_wp
    171206 
    172207    ! Planet radius (m) and gravity acceleration (m.s-2).
     
    186221    ! ~~~~~~~~~~~~~~~~~~~~~~~~
    187222   
    188     ! Bulk to apparent radius
    189     ! ~~~~~~~~~~~~~~~~~~~~~~~
     223    ! Bulk to apparent radius (Haze model)
     224    ! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
    190225    ! Bulk to apparent radius conversion pre-factor (m^X).
    191226    !
     
    194229    REAL(kind=mm_wp), SAVE :: mm_rb2ra = 1._mm_wp
    195230
    196     ! Inter-moment relation
    197     ! ~~~~~~~~~~~~~~~~~~~~~
     231    ! Inter-moment relation (Haze model)
     232    ! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
    198233    ! Alpha function parameters.
    199234    ! It stores the parameters of the inter-moments relation functions.
     
    214249    TYPE(aprm), PUBLIC, SAVE :: mm_afp
    215250
    216     ! Transfert probabilities (S --> F)
    217     ! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
     251    ! Transfert probabilities (S --> F) (Haze model)
     252    ! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
    218253    ! Data set for linear interpolation of transfert probability (M0/CO).
    219254    TYPE(dset1d), PUBLIC, SAVE, TARGET :: mm_pco0p
     
    225260    TYPE(dset1d), PUBLIC, SAVE, TARGET :: mm_pfm3p
    226261 
    227     ! Mean electric correction
    228     ! ~~~~~~~~~~~~~~~~~~~~~~~~
     262    ! Mean electric correction (Haze model)
     263    ! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
    229264    ! Data set for Q_SF(M0).
    230265    TYPE(dset2d), PUBLIC, SAVE, TARGET             :: mm_qbsf0
     
    240275    REAL(kind=mm_wp), PUBLIC, SAVE, DIMENSION(2,2) :: mm_qbff0_e
    241276
    242     ! btk coefficients
    243     ! ~~~~~~~~~~~~~~~~
     277    ! btk coefficients (Haze model)
     278    ! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
    244279    ! Coefficients for Free-molecular regime kernel approximation (b_0(t)).
    245280    REAL(kind=mm_wp), PUBLIC, SAVE, DIMENSION(5) :: mm_bt0 = (/1._mm_wp,1._mm_wp,1._mm_wp,1._mm_wp,1._mm_wp/)
    246281    ! Coefficients for Free-molecular regime kernel approximation (b_3(t)).
    247282    REAL(kind=mm_wp), PUBLIC, SAVE, DIMENSION(5) :: mm_bt3 = (/1._mm_wp,1._mm_wp,1._mm_wp,1._mm_wp,1._mm_wp/)
     283
     284    ! Chemical specie properties (Cloud model)
     285    ! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
     286    TYPE, PUBLIC :: mm_esp
     287      !! Cloud related chemical specie properties.
     288      !! This derived type is used in thermodynamic methods related to cloud microphysics.
     289      !!
     290      CHARACTER(LEN=10) :: name      !! Specie name.
     291      REAL(kind=mm_wp)  :: mas       !! Molecular weight (kg).
     292      REAL(kind=mm_wp)  :: vol       !! Molecular volume (m3).
     293      REAL(kind=mm_wp)  :: ray       !! Molecular radius (m).
     294      REAL(kind=mm_wp)  :: masmol    !! Molar mass (kg.mol-1).
     295      REAL(kind=mm_wp)  :: rho_l     !! Liquid density (kg.m-3).
     296      REAL(kind=mm_wp)  :: rho_s     !! Ice density (kg.m-3).
     297      REAL(kind=mm_wp)  :: Tc        !! Critical temperature (K).
     298      REAL(kind=mm_wp)  :: pc        !! Critical pressure (Bar).
     299      REAL(kind=mm_wp)  :: Tb        !! Boiling point temperature (K).
     300      REAL(kind=mm_wp)  :: w         !! Acentric factor.
     301      REAL(kind=mm_wp)  :: a0_sat    !! Saturation equation A0 coefficient.
     302      REAL(kind=mm_wp)  :: a1_sat    !! Saturation equation A1 coefficient.
     303      REAL(kind=mm_wp)  :: a2_sat    !! saturation equation A2 coefficient.
     304      REAL(kind=mm_wp)  :: a3_sat    !! Saturation equation A3 coefficient.
     305      REAL(kind=mm_wp)  :: a4_sat    !! Saturation equation A4 coefficient.
     306      REAL(kind=mm_wp)  :: a5_sat    !! Saturation equation A5 coefficient.
     307      REAL(kind=mm_wp)  :: a6_sat    !! Saturation equation A6 coefficient.
     308      REAL(kind=mm_wp)  :: mteta     !! Wettability.
     309      REAL(kind=mm_wp)  :: fdes      !! Desorption energy (J).
     310      REAL(kind=mm_wp)  :: fdif      !! Surface diffusion energy (J).
     311      REAL(kind=mm_wp)  :: nus       !! Jump frequency (s-1).
     312      REAL(kind=mm_wp)  :: fmol2fmas !! Molar fraction to mass fraction coefficient = masmol(X)/masmol(AIR)
     313    END TYPE mm_esp
     314
     315    ! Name of condensible species.
     316    CHARACTER(len=30), DIMENSION(:), ALLOCATABLE, SAVE :: mm_spcname
     317    ! Total number of clouds condensible species.
     318    INTEGER, SAVE                                      :: mm_nesp = -1
     319    ! Clouds chemical species properties.
     320    TYPE(mm_esp), DIMENSION(:), ALLOCATABLE, SAVE      :: mm_xESPS
    248321
    249322    ! ~~~~~~~~~~~~~~~~~~~~~~~
     
    356429                              coag_interactions,w_haze_prod,w_haze_sed,w_haze_coag,  &
    357430                              force_wsed_to_m0,force_wsed_to_m3,                     &
    358                               m0as_min,rcs_min,m0af_min,rcf_min,debug) RESULT(err)
     431                              m0as_min,rcs_min,m0af_min,rcf_min,                     &
     432                              clouds,spcfile,debug) RESULT(err)
    359433      !! Initialize global parameters of the model.
    360434      !!
     
    413487      REAL(kind=mm_wp), INTENT(in) :: rcf_min
    414488
     489      ! Clouds microphysics control flag.
     490      LOGICAL, INTENT(in)          :: clouds
     491      ! Clouds microphysics condensible species properties file.
     492      CHARACTER(len=*), INTENT(in) :: spcfile
     493
    415494      ! Debug mode control flag.
    416495      LOGICAL, INTENT(in) :: debug
     
    418497      ! Error status of the function.
    419498      TYPE(error) :: err
     499
     500      ! Local variables:
     501      INTEGER :: i
     502      TYPE(cfgparser)                                   :: cp
     503      CHARACTER(len=st_slen), DIMENSION(:), ALLOCATABLE :: species
    420504
    421505      err = noerror
     
    442526      mm_air_mmas       = air_mmol / mm_navo
    443527     
    444       ! Microphysical processes:
     528      ! Microphysical processes - Haze:
    445529      mm_coag_choice = coag_interactions
    446530      IF (mm_coag_choice < 0 .OR. mm_coag_choice > 7) THEN
     
    459543      mm_m0af_min = MAX(0._mm_wp,m0af_min)
    460544      mm_rcf_min  = MAX(mm_rm,rcf_min)
    461      
    462       ! Debug mode:
    463       mm_debug = debug
    464      
     545
    465546      ! Computes M3 thresholds from user-defined thresholds:
    466547      mm_m3as_min = mm_m0as_min*mm_alpha_s(3._mm_wp) * mm_rcs_min**3._mm_wp
    467548      mm_m3af_min = mm_m0af_min*mm_alpha_f(3._mm_wp) * mm_rcf_min**3._mm_wp
     549
     550      ! Microphysical processes - Clouds:
     551      mm_call_clouds = clouds
     552
     553      ! Check clouds microphysics species file
     554      IF (mm_call_clouds) THEN
     555        IF (LEN_TRIM(spcfile) == 0) THEN
     556          err = error("mm_global_init: No species properties file given",-1)
     557          RETURN
     558        ENDIF
     559
     560        ! Reads species properties configuration file
     561        err = cfg_read_config(cp,TRIM(spcfile))
     562        IF (err /= 0) THEN
     563          write(*,*) err
     564          RETURN
     565        ENDIF
     566
     567        ! Reads used species
     568        err = cfg_get_value(cp,"used_species",species)
     569        IF (err /= 0) THEN
     570          err = error("mm_global_init: cannot retrieve 'used_species' values",-1)
     571          RETURN
     572        ENDIF
     573
     574        mm_nesp = SIZE(species)
     575        ALLOCATE(mm_spcname(mm_nesp),mm_xESPS(mm_nesp))
     576       
     577        ! Reads used species properties
     578        DO i=1,mm_nesp
     579          mm_spcname(i) = TRIM(species(i))
     580          IF(.NOT.cfg_has_section(cp,TRIM(mm_spcname(i)))) THEN
     581            err = error("mm_global_init: Cannot find "//TRIM(mm_spcname(i))//" properties",-1)
     582            RETURN
     583          ELSE
     584            err = read_esp(cp,TRIM(mm_spcname(i)),mm_xESPS(i))
     585            ! Compute conversion factor: mol.mol-1 => kg.kg-1
     586            mm_xESPS(i)%fmol2fmas = mm_xESPS(i)%masmol / mm_air_mmol
     587            IF (err/=0) THEN
     588              err = error("mm_global_init: "//TRIM(mm_spcname(i))//": "//TRIM(err%msg),-1)
     589              RETURN
     590            ENDIF
     591          ENDIF
     592        ENDDO
     593      ENDIF ! end of mm_call_clouds
     594
     595      ! Debug mode:
     596      mm_debug = debug
    468597
    469598      ! Computes conversion factor for bulk to apparent radius:
     
    492621      ! Error status of the function.
    493622      TYPE(error) :: err
     623
     624      ! Local variables:
     625      INTEGER :: i
     626      TYPE(cfgparser)                                   :: spccfg
     627      CHARACTER(len=st_slen)                            :: spcpath
     628      CHARACTER(len=st_slen), DIMENSION(:), ALLOCATABLE :: species
    494629     
    495630      err = noerror
     
    529664      IF (err/=0) RETURN
    530665
    531       ! Microphysical processes:
     666      ! Microphysical processes - Haze:
    532667      err = mm_check_opt(cfg_get_value(cfg,"haze_coag_interactions",mm_coag_choice),mm_coag_choice,wlog=mm_log)
    533668      IF (err/=0) RETURN
     
    556691      err = mm_check_opt(cfg_get_value(cfg,"rcf_min",mm_rcf_min),mm_rcf_min,wlog=mm_log)
    557692      IF (err/=0) RETURN
     693
     694      ! Microphysical processes - Clouds:
     695      err = mm_check_opt(cfg_get_value(cfg,"clouds_microphysics",mm_call_clouds),mm_call_clouds,wlog=mm_log)
     696      IF (err/=0) RETURN
     697
     698      ! Check clouds microphysics input
     699      IF (mm_call_clouds) THEN
     700        ! Gets species property file path
     701        err = cfg_get_value(cfg,'species_cfg',spcpath) ; IF (err /= 0) RETURN
     702        ! Reads species properties configuration file
     703        err = cfg_read_config(spccfg,trim(spcpath)) ; IF (err /= 0) RETURN
     704        err = cfg_get_value(spccfg,"used_species",species)
     705        IF (err /= 0) THEN
     706          err = error("mm_global_init: cannot retrieve 'used_species' values",-1)
     707          RETURN
     708        ENDIF
     709        mm_nesp = SIZE(species)
     710        ALLOCATE(mm_spcname(mm_nesp),mm_xESPS(mm_nesp))
     711        DO i=1,mm_nesp
     712          mm_spcname(i) = TRIM(species(i))
     713          IF (.NOT.cfg_has_section(spccfg,TRIM(mm_spcname(i)))) THEN
     714            err = error("mm_global_init: Cannot find "//TRIM(mm_spcname(i))//" properties",-1)
     715            RETURN
     716          ELSE
     717            err = read_esp(spccfg,TRIM(mm_spcname(i)),mm_xESPS(i))
     718            ! Compute conversion factor: mol.mol-1 => kg.kg-1
     719            mm_xESPS(i)%fmol2fmas = mm_xESPS(i)%masmol / mm_air_mmol
     720            IF (err/=0) THEN
     721              err = error(TRIM(mm_spcname(i))//": "//TRIM(err%msg),-2)
     722              RETURN
     723            ENDIF
     724          ENDIF
     725        ENDDO
     726      ENDIF
    558727     
    559728      ! Debug mode:
     
    8421011
    8431012    !============================================================================
    844     !                          MISCELLANEOUS METHODS
     1013    !                          HAZE RELATED METHODS
    8451014    !============================================================================
    846 
    847     ELEMENTAL FUNCTION mm_effg(z) RESULT(effg)
    848       !! Compute effective gravitational acceleration.
    849       !!
    850       REAL(kind=mm_wp), INTENT(in) :: z ! Altitude (m)
    851       REAL(kind=mm_wp) :: effg          ! Effective gravitational acceleration (m.s-2)
    852       effg = mm_g0
    853       IF (mm_use_effg) THEN
    854         effg = effg * (mm_rpla/(mm_rpla+z))**2
    855       ENDIF
    856       RETURN
    857     END FUNCTION mm_effg
    858 
    8591015
    8601016    SUBROUTINE mm_set_moments_thresholds()
     
    9021058      res = (m3 / (m0*mm_alpha_f(3._mm_wp)))**(1._mm_wp/3._mm_wp)
    9031059    END FUNCTION mm_get_rcf
     1060
     1061
     1062    !============================================================================
     1063    !                          CLOUD RELATED METHODS
     1064    !============================================================================
     1065
     1066    FUNCTION read_esp(parser,sec,pp) RESULT (err)
     1067      !! Read and store [[mm_esp(type)]] parameters.
     1068      !!
     1069      TYPE(cfgparser), INTENT(in)  :: parser ! Configuration parser.
     1070      CHARACTER(len=*), INTENT(in) :: sec    ! Name of the specie.
     1071      TYPE(mm_esp), INTENT(out)    :: pp     ! [[mm_esp(type)]] object that stores the parameters.
     1072
     1073      TYPE(error) :: err ! Error status of the function.
     1074
     1075      err = cfg_get_value(parser,TRIM(sec)//'/name',pp%name)     ; IF (err /= 0) RETURN
     1076      err = cfg_get_value(parser,TRIM(sec)//'/mas',pp%mas)       ; IF (err /= 0) RETURN
     1077      err = cfg_get_value(parser,TRIM(sec)//'/vol',pp%vol)       ; IF (err /= 0) RETURN
     1078      err = cfg_get_value(parser,TRIM(sec)//'/ray',pp%ray)       ; IF (err /= 0) RETURN
     1079      err = cfg_get_value(parser,TRIM(sec)//'/masmol',pp%masmol) ; IF (err /= 0) RETURN
     1080      err = cfg_get_value(parser,TRIM(sec)//'/rho_l',pp%rho_l)   ; IF (err /= 0) RETURN
     1081      err = cfg_get_value(parser,TRIM(sec)//'/rho_s',pp%rho_s)   ; IF (err /= 0) RETURN
     1082      err = cfg_get_value(parser,TRIM(sec)//'/Tc',pp%Tc)         ; IF (err /= 0) RETURN
     1083      err = cfg_get_value(parser,TRIM(sec)//'/pc',pp%pc)         ; IF (err /= 0) RETURN
     1084      err = cfg_get_value(parser,TRIM(sec)//'/Tb',pp%Tb)         ; IF (err /= 0) RETURN
     1085      err = cfg_get_value(parser,TRIM(sec)//'/w',pp%w)           ; IF (err /= 0) RETURN
     1086      err = cfg_get_value(parser,TRIM(sec)//'/a0_sat',pp%a0_sat) ; IF (err /= 0) RETURN
     1087      err = cfg_get_value(parser,TRIM(sec)//'/a1_sat',pp%a1_sat) ; IF (err /= 0) RETURN
     1088      err = cfg_get_value(parser,TRIM(sec)//'/a2_sat',pp%a2_sat) ; IF (err /= 0) RETURN
     1089      err = cfg_get_value(parser,TRIM(sec)//'/a3_sat',pp%a3_sat) ; IF (err /= 0) RETURN
     1090      err = cfg_get_value(parser,TRIM(sec)//'/a4_sat',pp%a4_sat) ; IF (err /= 0) RETURN
     1091      err = cfg_get_value(parser,TRIM(sec)//'/a5_sat',pp%a5_sat) ; IF (err /= 0) RETURN
     1092      err = cfg_get_value(parser,TRIM(sec)//'/a6_sat',pp%a6_sat) ; IF (err /= 0) RETURN
     1093      err = cfg_get_value(parser,TRIM(sec)//'/mteta',pp%mteta)   ; IF (err /= 0) RETURN
     1094      err = cfg_get_value(parser,TRIM(sec)//'/fdes',pp%fdes)     ; IF (err /= 0) RETURN
     1095      err = cfg_get_value(parser,TRIM(sec)//'/fdif',pp%fdif)     ; IF (err /= 0) RETURN
     1096      err = cfg_get_value(parser,TRIM(sec)//'/nus',pp%nus)       ; IF (err /= 0) RETURN
     1097
     1098      RETURN
     1099    END FUNCTION read_esp
     1100
     1101
     1102    !============================================================================
     1103    !                          MISCELLANEOUS METHODS
     1104    !============================================================================
     1105
     1106    ELEMENTAL FUNCTION mm_effg(z) RESULT(effg)
     1107      !! Compute effective gravitational acceleration.
     1108      !!
     1109      REAL(kind=mm_wp), INTENT(in) :: z ! Altitude (m)
     1110      REAL(kind=mm_wp) :: effg          ! Effective gravitational acceleration (m.s-2)
     1111      effg = mm_g0
     1112      IF (mm_use_effg) THEN
     1113        effg = effg * (mm_rpla/(mm_rpla+z))**2
     1114      ENDIF
     1115      RETURN
     1116    END FUNCTION mm_effg
    9041117
    9051118
  • trunk/LMDZ.PLUTO/libf/muphypluto/mp2m_haze.F90

    r3560 r3951  
    107107        call mm_haze_sedimentation(zdm0as,zdm3as,zdm0af,zdm3af)
    108108 
    109         ! Computes precipitations
     109        ! Computes precipitation
    110110        mm_aers_prec = SUM(zdm3as*mm_dzlev*mm_rhoaer)
    111111        mm_aerf_prec = SUM(zdm3af*mm_dzlev*mm_rhoaer)
  • trunk/LMDZ.PLUTO/libf/muphypluto/mp2m_intgcm.F90

    r3560 r3951  
    2929    CONTAINS
    3030
    31     SUBROUTINE mm_initialize(dt,haze_prod_pCH4,p_prod,tx_prod,rc_prod,rm,df,rho_aer,rplanet,g0,air_rad,air_mmol,cfgpath)
     31    SUBROUTINE mm_initialize(dt,haze_prod_pCH4,p_prod,tx_prod,rc_prod,rm,df,rho_aer,rplanet,g0,air_rad,air_mmol,clouds,cfgpath)
    3232        !! Initialize global parameters of the model.
    3333        !!
     
    6767        ! Mean molar mass of air molecules (kg.mol-1).
    6868        REAL(kind=mm_wp), INTENT(in)           :: air_mmol
     69        ! Clouds microphysics control flag.
     70        LOGICAL, INTENT(in)                    :: clouds
    6971        ! Internal microphysics configuration file.
    7072        CHARACTER(len=*), INTENT(in), OPTIONAL :: cfgpath
     
    7274        ! Microphysical configuration file.
    7375        TYPE(cfgparser)        :: cparser
    74         ! Look-up tables (transfert probabilities, mean electric correction).
     76        ! Look-up tables - Haze related: transfert probabilities, mean electric correction.
    7577        CHARACTER(len=st_slen) :: pssfile,mqfile
     78        ! Look-up tables - Cloud related: species properties.
     79        CHARACTER(len=st_slen) :: spcpath
    7680        ! Enable/disable Haze process.
    7781        LOGICAL                :: w_h_prod,w_h_sed,w_h_coag,fwsed_m0,fwsed_m3
     
    8488
    8589        ! Local variables.
    86         TYPE(error)                                 :: err
     90        INTEGER     :: i
     91        TYPE(error) :: err
    8792        REAL(kind=mm_wp), DIMENSION(:), ALLOCATABLE :: tmp
    8893
     
    128133        err = mm_check_opt(cfg_get_value(cparser,"rcf_min",rcf_min)                   ,rcf_min    ,rm        ,mm_log)
    129134        err = mm_check_opt(cfg_get_value(cparser,"debug",wdebug)                      ,wdebug     ,.false.   ,mm_log)
     135
     136        ! Retrieve clouds species configuration file
     137        spcpath = ''
     138        IF (clouds) THEN
     139          err = mm_check_opt(cfg_get_value(cparser,"species_cfg",spcpath), spcpath, wlog=mm_log)
     140          IF (err/=0) call abort_program(err)
     141        ENDIF
    130142   
    131143        ! Alpha function:
     
    215227                               rplanet,g0,air_rad,air_mmol,coag_choice,                &
    216228                               w_h_prod,w_h_sed,w_h_coag,fwsed_m0,fwsed_m3,            &
    217                                m0as_min,rcs_min,m0af_min,rcf_min,wdebug)
     229                               m0as_min,rcs_min,m0af_min,rcf_min,                      &
     230                               clouds,spcpath,wdebug)
    218231        IF (err /= 0) call abort_program(err)
    219232       
     
    223236        WRITE(*,'(a,L2)')     "electric_charging    : ", mm_w_qe
    224237        call mm_dump_parameters()
     238
     239        IF (clouds) THEN
     240            DO i = 1, size(mm_xESPS)
     241                print*, TRIM(mm_xESPS(i)%name), " fmol2fmas = ", mm_xESPS(i)%fmol2fmas
     242            ENDDO
     243        ENDIF
    225244       
    226245    END SUBROUTINE mm_initialize
  • trunk/LMDZ.PLUTO/libf/muphypluto/mp2m_microphysics.F90

    r3560 r3951  
    8989        !!
    9090        !! @note
    91         !! Precipitations are always positive and defined in kg.m-2.s-1.
     91        !! Precipitation are always positive and defined in kg.m-2.s-1.
    9292        !!
    9393
  • trunk/LMDZ.PLUTO/libf/phypluto/inifis_mod.F90

    r3949 r3951  
    14541454      call abort_physic(rname, 'if microphysics is on, naerkind must be > 1!', 1)
    14551455     endif
    1456      if ((callmufi).and.(callmuclouds).and..not.(naerkind.gt.2)) then
    1457       call abort_physic(rname, 'if microphysical clouds are on, naerkind must be > 2!', 1)
    1458      endif
     1456     ! if ((callmufi).and.(callmuclouds).and..not.(naerkind.gt.2)) then
     1457     ! call abort_physic(rname, 'if microphysical clouds are on, naerkind must be > 2!', 1)
     1458     ! endif
    14591459     if (.not.(callmufi.or.haze).and.(optichaze)) then
    14601460      call abort_physic(rname, 'if microphysics and haze are off, optichaze must be deactivated!', 1)
  • trunk/LMDZ.PLUTO/libf/phypluto/initracer.F90

    r3949 r3951  
    334334      ! By convention they all have the prefix "mu_" (case sensitive !)
    335335      nmicro = 0
     336      nmicro_ices = 0
    336337      IF (callmufi) THEN
    337338         DO iq=1,nq
     
    351352            WRITE(*,*) "expected at least 7 tracers (clouds: on),", nmicro, " given"
    352353            CALL abort
     354          ELSE
     355            nmicro_ices = nmicro - 6
    353356          ENDIF
    354357
     
    374377            ENDIF
    375378         ENDDO
     379
     380         ! Cloud related indexes initialize in inimufi subroutine.
     381         IF (.NOT.ALLOCATED(micro_ice_indx)) ALLOCATE(micro_ice_indx(nmicro_ices))
     382         IF (.NOT.ALLOCATED(micro_gas_indx)) ALLOCATE(micro_gas_indx(nmicro_ices))
    376383     
    377384      ELSE
    378385         IF (.NOT.ALLOCATED(micro_indx)) ALLOCATE(micro_indx(nmicro))
     386         IF (.NOT.ALLOCATED(micro_ice_indx)) ALLOCATE(micro_ice_indx(nmicro_ices))
     387         IF (.NOT.ALLOCATED(micro_gas_indx)) ALLOCATE(micro_gas_indx(nmicro_ices))
    379388     
    380389      ENDIF ! end of callmufi
  • trunk/LMDZ.PLUTO/libf/phypluto/mp2m_diagnostics.F90

    r3683 r3951  
    2323  IMPLICIT NONE
    2424
    25   REAL(kind=8), ALLOCATABLE, DIMENSION(:)     :: mp2m_aer_s_prec ! Spherical aerosols precipitations (kg.m-2.s-1).
    26   REAL(kind=8), ALLOCATABLE, DIMENSION(:)     :: mp2m_aer_f_prec ! Fractal aerosols precipitations (kg.m-2.s-1).
     25  REAL(kind=8), ALLOCATABLE, DIMENSION(:)     :: mp2m_aer_s_prec ! Spherical aerosols precipitation (kg.m-2.s-1).
     26  REAL(kind=8), ALLOCATABLE, DIMENSION(:)     :: mp2m_aer_f_prec ! Fractal aerosols precipitation (kg.m-2.s-1).
    2727  REAL(kind=8), ALLOCATABLE, DIMENSION(:,:)   :: mp2m_aer_s_w    ! Spherical aerosol settling velocity (m.s-1).
    2828  REAL(kind=8), ALLOCATABLE, DIMENSION(:,:)   :: mp2m_aer_f_w    ! Fractal aerosol settling velocity (m.s-1).
  • trunk/LMDZ.PLUTO/libf/phypluto/mp2m_inimufi.F90

    r3949 r3951  
    11subroutine inimufi(ptimestep)
    2   use callkeys_mod, only : call_haze_prod_pCH4, haze_p_prod, haze_tx_prod, haze_rc_prod, haze_rm, haze_df, haze_rho, air_rad
     2  use callkeys_mod, only : call_haze_prod_pCH4, haze_p_prod, haze_tx_prod, haze_rc_prod, &
     3                           haze_rm, haze_df, haze_rho, air_rad, &
     4                           callmuclouds
    35  use tracer_h
    46  use comcstfi_mod, only : g, rad, mugaz
     
    3638       "mu_m0af              ", "mu_m3af              "/)
    3739 
     40  CHARACTER(len=30), DIMENSION(2), PARAMETER :: ccnnames = &
     41     (/"mu_m0ccn             ", "mu_m3ccn             "/)
     42 
    3843  logical :: err
    3944
     
    5156  ENDDO
    5257
     58  IF (callmuclouds) THEN
     59    DO i=1,size(ccnnames)
     60      idx = indexOfTracer(TRIM(ccnnames(i)),.false.)
     61      IF (idx <= 0) THEN
     62        WRITE(*,*) "inimufi: '"//TRIM(ccnnames(i))//"' not found in tracers table."
     63        err = .true.
     64      ENDIF
     65    ENDDO
     66  ENDIF
     67
    5368  IF (err) THEN
    5469    WRITE(*,*) "You loose in inimufi.F90.... Try again"
     
    6378  call mm_initialize(ptimestep,call_haze_prod_pCH4,haze_p_prod,haze_tx_prod,haze_rc_prod, &
    6479                      haze_rm,haze_df,haze_rho,rad,g,air_rad,mugaz*1e-3,                  &
    65                       config_mufi)
     80                      callmuclouds,config_mufi)
    6681 
    67   ! Sanity check for haze model initialization:
    68   ! -------------------------------------------
     82  !-----------------
     83  ! 3. Sanity checks
     84  !-----------------
     85 
     86  ! Haze model initialization
     87  ! -------------------------
    6988  write(*,*) 'Number of microphysical tracer nmicro = ',nmicro
    7089  call dumptracers(micro_indx)
     90
     91  ! Cloud model initialization
     92  ! --------------------------
     93  if (callmuclouds) then
     94    do i = 1, nmicro_ices
     95      ! Setup micro_ice_indx:
     96      idx = indexOfTracer("mu_m3"//TRIM(mm_spcname(i)),.false.)
     97      if (idx <= 0) then
     98        write(*,*) "inimufi: 'mu_m3"//TRIM(mm_spcname(i))//"' not found in tracers table."
     99        err = .true.
     100      else
     101        micro_ice_indx(i) = idx
     102      endif
     103      ! Setup micro_gas_indx:
     104      idx = indexOfTracer(TRIM(mm_spcname(i))//"_mugas",.false.)
     105      if (idx <= 0) then
     106        write(*,*) "inimufi: '"//TRIM(mm_spcname(i))//"' not found in tracers table."
     107        err = .true.
     108      else
     109        micro_gas_indx(i) = idx
     110      endif
     111    enddo
     112
     113    ! Check for errors
     114    if (err) then
     115      write(*,*) "Error in inimufi: tracer not found in table!"
     116      STOP
     117    endif
     118    if (nmicro_ices.ne.mm_nesp) then
     119      write(*,*) "Error in inimufi: nmicro_ices not equal to mm_nesp!"
     120      STOP
     121    endif
     122
     123    write(*,*) 'Number of microphysical ice tracer nmicro_ices = ',nmicro_ices
     124    write(*,*) 'Ices:'
     125    call dumptracers(micro_ice_indx)
     126    write(*,*) 'Condensable gases:'
     127    call dumptracers(micro_gas_indx)
     128  endif ! end of callmuclouds
    71129 
    72130end subroutine inimufi
  • trunk/LMDZ.PLUTO/libf/phypluto/physiq_mod.F90

    r3949 r3951  
    6868                              tracer, UseTurbDiff,                            &
    6969                              global1d, szangle,                              &
    70                               callmufi, evol1d
     70                              callmufi, callmuclouds, evol1d
    7171
    7272      use check_fields_mod, only: check_physics_fields
     
    508508
    509509      ! Misc
    510       character*2 :: str2
     510      character(len=10) :: str
    511511      character(len=10) :: tmp1
    512512      character(len=10) :: tmp2
     
    25112511
    25122512            ! Diagnostics:
    2513             call write_output("aers_prec","Spherical aerosols precipitations","kg.m-2.s-1",mp2m_aer_s_prec(:))
    2514             call write_output("aerf_prec","Fractal aerosols precipitations","kg.m-2.s-1",mp2m_aer_f_prec(:))
     2513            call write_output("aers_prec","Spherical aerosols precipitation","kg.m-2.s-1",mp2m_aer_s_prec(:))
     2514            call write_output("aerf_prec","Fractal aerosols precipitation","kg.m-2.s-1",mp2m_aer_f_prec(:))
    25152515            call write_output("aers_w","Spherical aerosol settling velocity","m.s-1",mp2m_aer_s_w(:,:))
    25162516            call write_output("aerf_w","Fractal aerosol settling velocity","m.s-1",mp2m_aer_f_w(:,:))
     2517            call write_output("aers_flux","Spherical aerosol mass flux","kg.m-2.s-1",mp2m_aer_s_flux(:,:))
     2518            call write_output("aerf_flux","Fractal aerosol mass flux","kg.m-2.s-1",mp2m_aer_f_flux(:,:))
    25172519            call write_output("rcs","Characteristic radius of spherical aerosols","m",mp2m_rc_sph(:,:))
    25182520            call write_output("rcf","Characteristic radius of fractal aerosols","m",mp2m_rc_fra(:,:))
     2521
     2522            if (callmuclouds) then
     2523               ! Tracers:
     2524               call write_output("m0ccn","Density number of cloud condensation nuclei","m-3",zq(:,:,micro_indx(5))*int2ext(:,:))
     2525               call write_output("m3ccn","Volume of cloud condensation nuclei","m3.m-3",zq(:,:,micro_indx(6))*int2ext(:,:))
     2526               do iq = 1, size(micro_ice_indx)
     2527                  str = TRIM(nameOfTracer(micro_ice_indx(iq)))
     2528                  call write_output("m3"//TRIM(str(6:)),"Volume of "//TRIM(str(6:))//" ice","m3.m-3",zq(:,:,micro_ice_indx(iq))*int2ext(:,:))
     2529               enddo
     2530            endif ! end callmuclouds
    25192531         endif ! end callmufi
    25202532
  • trunk/LMDZ.PLUTO/libf/phypluto/tracer_h.F90

    r3949 r3951  
    8484!$OMP THREADPRIVATE(igcm_eddy1e6,igcm_eddy1e7,igcm_eddy5e7,igcm_eddy1e8,igcm_eddy5e8)
    8585
    86        ! Microphysical model
    87        integer, save :: nmicro = 0                 !! Number of microphysics tracers.
    88        integer, save, allocatable :: micro_indx(:) !! Indexes of all microphysical tracers
    89 !$OMP THREADPRIVATE(nmicro)
     86       ! Microphysical haze model related
     87       integer, save :: nmicro = 0                 ! Number of microphysics tracers.
     88       integer, save, allocatable :: micro_indx(:) ! Indexes of all microphysical tracers
     89!$OMP THREADPRIVATE(nmicro,micro_indx)
     90       ! Microphysical cloud model related
     91       integer, save :: nmicro_ices = 0                ! Number of microphysics ice tracers (subset of nmicro).
     92       integer, save, allocatable :: micro_ice_indx(:) ! Indexes of microphysical ice tracers
     93       integer, save, allocatable :: micro_gas_indx(:) ! Indexes of microphysical gas tracers
     94!$OMP THREADPRIVATE(nmicro_ices,micro_ice_indx,micro_gas_indx)
    9095
    9196       CONTAINS
     
    166171          ENDIF
    167172
     173          WRITE(*,"(a)") "local -> global : name"
     174
    168175          DO i=1,size(indexes)
    169176             idx = indexes(i)
Note: See TracChangeset for help on using the changeset viewer.