Changeset 3962


Ignore:
Timestamp:
Nov 17, 2025, 11:02:59 AM (5 hours ago)
Author:
debatzbr
Message:

Pluto PCM: Calculates the latent heat released by condensation from the microphysical module.
BBT

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

Legend:

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

    r3957 r3962  
    2222    USE MP2M_CLOUDS
    2323    USE MP2M_METHODS
     24    USE MP2M_CLOUDS_METHODS
    2425    IMPLICIT NONE
    2526   
     
    3536    CONTAINS
    3637 
    37     FUNCTION muphys_all(m3as_prod,dm0as,dm3as,dm0af,dm3af,dm0ccn,dm3ccn,dm3ices,dmugases) RESULT(ret)
     38    FUNCTION muphys_all(m3as_prod,dm0as,dm3as,dm0af,dm3af,dm0ccn,dm3ccn,dm3ices,dmugases,dtlc) RESULT(ret)
    3839        !! Compute the evolution of moments tracers through haze microphysics processes.
    3940        !!
     
    4849        !! before the latter are called to initialize a new step.
    4950        !!
    50 
    5151        ! Production of the 3rd order moment of the spherical mode distribution (m3.m-2).
    5252        REAL(kind=mm_wp), INTENT(in), DIMENSION(:) :: m3as_prod
     
    6767        ! Tendencies of each condensible gaz species (mol.mol-1).
    6868        REAL(kind=mm_wp), INTENT(inout), DIMENSION(:,:) :: dmugases
     69        ! Latent heat of condensation (J.kg-1).
     70        REAL(kind=mm_wp), INTENT(inout), DIMENSION(:) :: dtlc
    6971
    7072        ! .true. on succes (i.e. model has been initialized at least once previously), .false. otherwise.
    7173        LOGICAL :: ret
    7274       
    73         ! Local variables.
     75        ! Local variables:
     76        !~~~~~~~~~~~~~~~~~
    7477        INTEGER :: i
    7578        ! Production of the spherical aerosols (m3.m-3).
     
    8285        ALLOCATE(m3a_s_prod(mm_nla))
    8386
    84         ! Sanity check for initialization
     87        ! Sanity check for initialization:
     88        !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
    8589        ret = (mm_ini_col.AND.mm_ini_aer)
    8690        if (.NOT.ret) then
     
    9599        m3a_s_prod = m3as_prod(mm_nla:1:-1) / mm_dzlev(:)
    96100
    97         ! Calls haze microphysics (/!\ tendencies in X/m-3)
     101        ! Initialize latent heat
     102        dtlc(:) = 0._mm_wp
     103
     104        ! Calls haze microphysics (/!\ tendencies in X/m-3):
     105        !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
    98106        call mm_haze_microphysics(m3a_s_prod,Hdm0as,Hdm3as,Hdm0af,Hdm3af)
    99107
    100         ! Calls cloud microphysics (/!\ tendencies in X/m-3)
     108        ! Calls cloud microphysics (/!\ tendencies in X/m-3):
     109        !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
    101110        if (mm_call_clouds) then
    102111            call mm_cloud_microphysics(Hdm0as,Hdm3as,Hdm0af,Hdm3af,&
     
    110119                dm3ices(:,i)  = dm3ices(mm_nla:1:-1,i) * mm_dzlev(mm_nla:1:-1)
    111120                dmugases(:,i) = dmugases(mm_nla:1:-1,i)
     121
     122                ! Compute condensation heating rate
     123                dtlc(:) = dtlc(:) + (dmugases(:,i) * mm_xESPS(i)%fmol2fmas * mm_LheatX(mm_temp,mm_xESPS(i)))
    112124            enddo
    113125         
    114126        else
    115             Cdm0as(:) = 0._mm_wp ; Cdm3as(:) = 0._mm_wp ; Cdm0af(:) = 0._mm_wp ; Cdm3af(:) = 0._mm_wp
     127            Cdm0as(:) = 0._mm_wp ; Cdm3as(:) = 0._mm_wp ; Cdm0af(:)    = 0._mm_wp ; Cdm3af(:)    = 0._mm_wp
    116128            dm0ccn(:) = 0._mm_wp ; dm3ccn(:) = 0._mm_wp ; dm3ices(:,:) = 0._mm_wp ; dmugases(:,:) = 0._mm_wp
     129            dtlc(:)   = 0._mm_wp
    117130        endif ! end of mm_call_clouds
    118131       
     
    140153        !! before the latter are called to initialize a new step.
    141154        !!
    142 
    143155        ! Production of the 3rd order moment of the spherical mode distribution (m3.m-2).
    144156        REAL(kind=mm_wp), INTENT(in), DIMENSION(:) :: m3as_prod
     
    155167        LOGICAL :: ret
    156168       
    157         ! Local variables.
     169        ! Local variables:
     170        !~~~~~~~~~~~~~~~~~
    158171        ! Production of the spherical aerosols (m3.m-3).
    159172        REAL(kind=mm_wp), DIMENSION(:), ALLOCATABLE :: m3a_s_prod
    160173        ALLOCATE(m3a_s_prod(mm_nla))
    161174       
    162         ! Sanity check for initialization
     175        ! Sanity check for initialization:
     176        !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
    163177        ret = (mm_ini_col.AND.mm_ini_aer)
    164178        if (.NOT.ret) then
     
    173187        m3a_s_prod = m3as_prod(mm_nla:1:-1) / mm_dzlev(:)
    174188
    175         ! Calls haze microphysics
     189        ! Calls haze microphysics (/!\ tendencies in X/m-3):
     190        !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
    176191        call mm_haze_microphysics(m3a_s_prod,dm0as,dm3as,dm0af,dm3af)
    177192       
  • trunk/LMDZ.PLUTO/libf/phypluto/mp2m_calmufi.F90

    r3957 r3962  
    11MODULE mp2m_calmufi
    22    use tracer_h
    3     use comcstfi_mod, only : mugaz
     3    use comcstfi_mod, only : mugaz, cpp
    44    use callkeys_mod, only : call_haze_prod_pCH4, haze_rho,&
    55                             callmuclouds
     
    4444    CONTAINS
    4545   
    46     SUBROUTINE calmufi(dt, plev, zlev, play, zlay, g3d, temp, pq, zdqfi, zdqmufi_prod, zdqmufi)
     46    SUBROUTINE calmufi(dt, plev, zlev, play, zlay, g3d, temp, pq, zdqfi, zdqmufi_prod, zdqmufi, zdtcond)
    4747        !! Interface subroutine to YAMMS model for LMD PCM.
    4848        !!
     
    6262        REAL(kind=8), DIMENSION(:,:,:), INTENT(IN)  :: zdqmufi_prod ! Aerosols production tendency (kg/kg_of_air/s).
    6363        REAL(kind=8), DIMENSION(:,:,:), INTENT(OUT) :: zdqmufi      ! Microphysical tendency for tracers (X.m-2 --> X.kg-1.s-1).
     64        REAL(kind=8), DIMENSION(:,:),   INTENT(OUT) :: zdtcond      ! Condensation heating rate (K.s-1).
    6465       
    6566        ! Local tracers:
     
    9091        REAL(kind=8), DIMENSION(:,:), ALLOCATABLE :: dm3ices  ! Tendencies of the 3rd order moments of each ice components (m3.m-2).
    9192        REAL(kind=8), DIMENSION(:,:), ALLOCATABLE :: dmugases ! Tendencies of each condensible gas species (mol.mol-1).
     93        REAL(kind=8), DIMENSION(:), ALLOCATABLE   :: dtlc     ! Latent heat of condensation (J.kg-1).
    9294       
    9395        ! Local variables:
     
    129131        ALLOCATE(dm3ices(nlay,nmicro_ices))
    130132        ALLOCATE(dmugases(nlay,nmicro_ices))
     133        ALLOCATE(dtlc(nlay))
    131134
    132135        ALLOCATE(int2ext(nlon,nlay)) 
     
    138141        ! Initialization of zdqmufi here since intent=out and no action performed on every tracers
    139142        zdqmufi(:,:,:) = 0.D0
     143
     144        ! Initialization of zdtcond here since intent=out
     145        zdtcond(:,:) = 0.D0
    140146       
    141147        ! Initialize tracers updated with former processes from physics
     
    191197           
    192198            ! Initializes tendencies
    193             dm0as(:) = 0._mm_wp ; dm3as(:) = 0._mm_wp ; dm0af(:) = 0._mm_wp ; dm3af(:) = 0._mm_wp
     199            dm0as(:)  = 0._mm_wp ; dm3as(:)  = 0._mm_wp ; dm0af(:)     = 0._mm_wp ; dm3af(:)      = 0._mm_wp
    194200            dm0ccn(:) = 0._mm_wp ; dm3ccn(:) = 0._mm_wp ; dm3ices(:,:) = 0._mm_wp ; dmugases(:,:) = 0._mm_wp
     201            dtlc(:)   = 0._mm_wp
    195202           
    196203        !----------------------------
     
    200207            ! Call microphysics
    201208            if (callmuclouds) then
    202                 if(.NOT.mm_muphys(m3as_prod,dm0as,dm3as,dm0af,dm3af,dm0ccn,dm3ccn,dm3ices,dmugases)) then
     209                if(.NOT.mm_muphys(m3as_prod,dm0as,dm3as,dm0af,dm3af,dm0ccn,dm3ccn,dm3ices,dmugases,dtlc)) then
    203210                    call abort_program(error("mm_muphys (clouds) aborted -> initialization not done !",-1))
    204211                endif
     
    232239                    zdqmufi(ilon,:,micro_gas_indx(i)) = dmugases(:,i) * (mmol(micro_gas_indx(i))/mugaz)
    233240                enddo
     241
     242                ! Compute condensation heating rate in K.s-1
     243                zdtcond(ilon,:) = dtlc(:) / cpp / dt
    234244            endif ! End of callmuclouds
    235245           
  • trunk/LMDZ.PLUTO/libf/phypluto/physiq_mod.F90

    r3957 r3962  
    411411      real pdqmufi_prod(ngrid,nlayer,nq) ! Aerosols production tendency (kg/kg_of_air/s).
    412412      real int2ext(ngrid,nlayer)         ! Intensive to extensive factor (kg_air/m3: X/kg_air --> X/m3).
     413      real zdtcond(ngrid,nlayer)         ! Condensation heating rate (K.s-1).
    413414
    414415! Local variables for LOCAL CALCULATIONS:
     
    16171618            pdqmufi(:,:,:) = 0.
    16181619
    1619             call calmufi(ptimestep,pplev,zzlev,pplay,zzlay,gzlat,pt,pq,pdq,pdqmufi_prod,pdqmufi)
     1620            call calmufi(ptimestep,pplev,zzlev,pplay,zzlay,gzlat,pt,pq,pdq,pdqmufi_prod,pdqmufi,zdtcond)
    16201621
    16211622            pdq(:,:,:) = pdq(:,:,:) + pdqmufi(:,:,:)
     
    25362537                  call write_output("m3"//TRIM(str(6:)),"Volume of "//TRIM(str(6:))//" ice","m3.m-3",zq(:,:,micro_ice_indx(iq))*int2ext(:,:))
    25372538               enddo
     2539               call write_output("dtcond","Condensation heating rate","K.s-1",zdtcond(:,:))
    25382540
    25392541               ! Diagnostics:
Note: See TracChangeset for help on using the changeset viewer.