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

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

Location:
trunk/LMDZ.PLUTO/libf/phypluto
Files:
6 edited

Legend:

Unmodified
Added
Removed
  • 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.