Changeset 3949


Ignore:
Timestamp:
Nov 4, 2025, 8:51:03 AM (3 months ago)
Author:
debatzbr
Message:

Pluto PCM: Add condensable gas tracers through muphi
BBT

Location:
trunk/LMDZ.PLUTO/libf/phypluto
Files:
1 added
7 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.PLUTO/libf/phypluto/callkeys_mod.F90

    r3935 r3949  
    204204!! Microphysics-specific variables
    205205      logical,save :: callmufi, call_haze_prod_pCH4
    206 !$OMP THREADPRIVATE(callmufi,call_haze_prod_pCH4)
     206      logical,save :: callmuclouds
     207!$OMP THREADPRIVATE(callmufi,call_haze_prod_pCH4,callmuclouds)
    207208      real,save :: haze_p_prod, haze_tx_prod, haze_rc_prod
    208209      real,save :: haze_rm, haze_df, haze_rho
  • trunk/LMDZ.PLUTO/libf/phypluto/datafile_mod.F90

    r3585 r3949  
    1818      ! Set in inifis_mod
    1919      character(LEN=100),save :: config_mufi ='datagcm/microphysics/config.cfg'
    20 !$OMP THREADPRIVATE(config_mufi)
     20      character(LEN=100),save :: mugasflux_file ='datagcm/microphysics/Species_Pluto_PLavvas_Flux.txt'
     21!$OMP THREADPRIVATE(config_mufi,mugasflux_file)
    2122      character(len=300),save :: aersprop_file
    2223      character(len=300),save :: aerfprop_file
  • trunk/LMDZ.PLUTO/libf/phypluto/inifis_mod.F90

    r3940 r3949  
    1414  use radii_mod, only: radfixed
    1515  use datafile_mod, only: datadir,hazeprop_file,hazerad_file,hazemmr_file,hazedens_file, &
    16                           config_mufi, aersprop_file, aerfprop_file
     16                          config_mufi, mugasflux_file, aersprop_file, aerfprop_file
    1717  use comdiurn_h, only: sinlat, coslat, sinlon, coslon
    1818  use comgeomfi_h, only: totarea, totarea_planet
     
    764764     if (is_master) write(*,*)" callmufi = ",callmufi
    765765
     766     if (is_master) write(*,*) "Run with or without microphysical clouds?"
     767     callmuclouds=.false. ! default value
     768     call getin_p("callmuclouds",callmuclouds)
     769     if (is_master) write(*,*)" callmuclouds = ",callmuclouds
     770
    766771     ! sanity check
    767772     if (callmufi.and.(.not.tracer)) then
     
    770775       stop
    771776     endif
     777     if (callmuclouds.and.(.not.callmufi)) then
     778       print*,"You are running microphysical clouds without microphysics"
     779       print*,"Please start again with callmufi =.true."
     780       stop
     781     endif
    772782
    773783     if (is_master) write(*,*) "Path to microphysical config file?"
    774784     config_mufi='datagcm/microphysics/config.cfg' ! default value
    775785     call getin_p("config_mufi",config_mufi)
    776      if (is_master) write(*,*)" config_mufi = ",config_mufi
     786     if (is_master) write(*,*) trim(rname)//" config_mufi = ",config_mufi
     787
     788     if (is_master) write(*,*) "Condensable gas fluxes datafile"
     789     mugasflux_file='None' ! default file
     790     call getin_p("mugasflux_file",mugasflux_file)
     791     if (is_master) write(*,*) trim(rname)//" mugasflux_file = ",trim(mugasflux_file)
    777792
    778793     if (is_master) write(*,*) "Spherical aerosol optical properties datafile"
     
    14391454      call abort_physic(rname, 'if microphysics is on, naerkind must be > 1!', 1)
    14401455     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
    14411459     if (.not.(callmufi.or.haze).and.(optichaze)) then
    14421460      call abort_physic(rname, 'if microphysics and haze are off, optichaze must be deactivated!', 1)
  • trunk/LMDZ.PLUTO/libf/phypluto/initracer.F90

    r3936 r3949  
    33      use surfdat_h, ONLY: dryness
    44      USE tracer_h
    5       USE callkeys_mod, only: optichaze,nb_monomer,haze,fractal,fasthaze,rad_haze,callmufi
     5      USE callkeys_mod, only: optichaze,nb_monomer,haze,fractal,fasthaze,rad_haze,&
     6                              callmufi,callmuclouds
    67      USE recombin_corrk_mod, ONLY: ini_recombin
    78      USE mod_phys_lmdz_para, only: is_master, bcast
     
    150151      igcm_ch4_gas=0
    151152      igcm_ch4_ice=0
    152       igcm_prec_haze=0
    153153      igcm_co_gas=0
    154154      igcm_co_ice=0
     155      igcm_C2H2_mugas=0
     156      igcm_C2H6_mugas=0
     157      igcm_C4H2_mugas=0
     158      igcm_C6H6_mugas=0
     159      igcm_HCN_mugas=0
     160      igcm_prec_haze=0
    155161
    156162      nqhaze(:)=0
     
    225231          write(*,*) 'Tracer ',count,' = co ice'
    226232        endif
     233!       Microphysics related tracers
     234        if (noms(iq).eq."C2H2_mugas") then
     235          igcm_C2H2_mugas=iq
     236          mmol(igcm_C2H2_mugas)=26.04
     237          count=count+1
     238          write(*,*) 'Tracer ',count,' = C2H2 mugas'
     239        endif
     240        if (noms(iq).eq."C2H6_mugas") then
     241          igcm_C2H6_mugas=iq
     242          mmol(igcm_C2H6_mugas)=30.07
     243          count=count+1
     244          write(*,*) 'Tracer ',count,' = C2H6 mugas'
     245        endif
     246        if (noms(iq).eq."C4H2_mugas") then
     247          igcm_C4H2_mugas=iq
     248          mmol(igcm_C4H2_mugas)=50.05
     249          count=count+1
     250          write(*,*) 'Tracer ',count,' = C4H2 mugas'
     251        endif
     252        if (noms(iq).eq."C6H6_mugas") then
     253          igcm_C6H6_mugas=iq
     254          mmol(igcm_C6H6_mugas)=78.11
     255          count=count+1
     256          write(*,*) 'Tracer ',count,' = C6H6 mugas'
     257        endif
     258        if (noms(iq).eq."HCN_mugas") then
     259          igcm_HCN_mugas=iq
     260          mmol(igcm_HCN_mugas)=27.03
     261          count=count+1
     262          write(*,*) 'Tracer ',count,' = HCN mugas'
     263        endif
     264!       Haze tracers
    227265        if (noms(iq).eq."prec_haze") then
    228266          igcm_prec_haze=iq
     
    293331      enddo ! of do iq=1,nq
    294332
    295       ! ! 3. find condensable traceurs different from h2o and n2
    296       ! do iq=1,nq
    297       !   if ((index(noms(iq),"vap") .ne. 0) .and. (index(noms(iq),"n2") .eq. 0)) then
    298       !     count=count+1
    299       !   endif
    300       !   if ((index(noms(iq),"ice") .ne. 0) .and. (index(noms(iq),"n2") .eq. 0)) then
    301       !     count=count+1
    302       !   endif
    303 
    304       ! enddo ! of do iq=1,nq
    305 
    306       ! check that we identified all tracers:
    307       if (count.ne.nq) then
    308         write(*,*) "initracer: found only ",count," tracers"
    309         write(*,*) "               expected ",nq
    310         do iq=1,count
    311           write(*,*)'      ',iq,' ',trim(noms(iq))
    312         enddo
    313 !        stop
    314       else
    315         write(*,*) "initracer: found all expected tracers, namely:"
    316         do iq=1,nq
    317           write(*,*)'      ',iq,' ',trim(noms(iq))
    318         enddo
    319       endif
    320      
    321       ! Compute number of microphysics tracers:
     333      ! 3. Find microphysics tracers:
    322334      ! By convention they all have the prefix "mu_" (case sensitive !)
    323335      nmicro = 0
     
    331343         ENDDO
    332344
    333          ! Checking the expected number of tracers:
    334          ! Microphysics moment model: nmicro = 4
    335          IF (nmicro < 4) THEN
     345         ! Checking the expected number of microphysical tracers:
     346         ! No cloud: nmicro = 4 aer.
     347         ! Clouds:   nmicro = 4 aer. + 2 ccn + 1(+) ices
     348         IF (callmuclouds) THEN
     349          IF (nmicro < 7) THEN
    336350            WRITE(*,*) "initracer:error:"," Inconsistent number of microphysical tracers"
    337             WRITE(*,*) "expected at least 4 tracers,", nmicro, " given"
     351            WRITE(*,*) "expected at least 7 tracers (clouds: on),", nmicro, " given"
    338352            CALL abort
    339          ELSE IF (nmicro > 4) THEN
     353          ENDIF
     354
     355         ELSE
     356          IF (nmicro < 4) THEN
     357            WRITE(*,*) "initracer:error:"," Inconsistent number of microphysical tracers"
     358            WRITE(*,*) "expected at least 4 tracers (clouds: off),", nmicro, " given"
     359            CALL abort
     360          ELSE IF (nmicro > 4) THEN
    340361            WRITE(*,*) "!!! WARNING !!! initracer: I was expecting only four tracers, you gave me more."
    341362            CALL abort
    342          ENDIF
    343 
    344          ! microphysics indexes share the same values than original tracname.
     363          ENDIF
     364         ENDIF ! end of callmuclouds
     365
     366         ! Microphysics indexes share the same values than original tracname.
    345367         IF (.NOT.ALLOCATED(micro_indx)) ALLOCATE(micro_indx(nmicro))
    346368         j = 1
     
    358380      ENDIF ! end of callmufi
    359381
     382      ! Check that we identified all tracers:
     383      if (count.ne.nq) then
     384        write(*,*) "initracer: found only ",count," tracers"
     385        write(*,*) "               expected ",nq
     386        do iq=1,count
     387          write(*,*)'      ',iq,' ',trim(noms(iq))
     388        enddo
     389      else
     390        write(*,*) "initracer: found all expected tracers, namely:"
     391        do iq=1,nq
     392          write(*,*)'      ',iq,' ',trim(noms(iq))
     393        enddo
     394      endif
     395
    360396      ! Get data of tracers. Need to rewind traceur.def first
    361397      if (is_master) then
     
    376412      if (is_master) close(407)
    377413
    378       ! Calculate number of microphysical tracer
    379       write(*,*) 'Number of microphysical tracer nmicro = ',nmicro
    380       IF (callmufi) THEN
    381          call dumptracers(micro_indx)
    382       ENDIF
    383 
    384414!     Processing modern traceur options
    385415      if(moderntracdef) then
     
    401431      if (callmufi) then
    402432        if (optichaze) then
    403           iaero_haze = 2
    404           write(*,*) 'Microphysical moment model'
    405           write(*,*) '--- number of haze aerosol = ', iaero_haze
     433          if (callmuclouds) then
     434            iaero_haze = 3
     435          else
     436            iaero_haze = 2
     437          endif ! end of callmuclouds
    406438        endif ! end optichaze
    407439     
     
    431463              (first one in traceur.def)"
    432464            endif
    433             enddo
     465          enddo
    434466        endif ! end optichaze
    435467      endif ! end callmufi or haze
  • trunk/LMDZ.PLUTO/libf/phypluto/mp2m_inimufi.F90

    r3559 r3949  
    6464                      haze_rm,haze_df,haze_rho,rad,g,air_rad,mugaz*1e-3,                  &
    6565                      config_mufi)
    66 
     66 
     67  ! Sanity check for haze model initialization:
     68  ! -------------------------------------------
     69  write(*,*) 'Number of microphysical tracer nmicro = ',nmicro
     70  call dumptracers(micro_indx)
     71 
    6772end subroutine inimufi
  • trunk/LMDZ.PLUTO/libf/phypluto/physiq_mod.F90

    r3936 r3949  
    407407      ! ---------------------------------
    408408      real gzlat(ngrid,nlayer)           ! Altitude-Latitude-dependent gravity (this should be stored elsewhere...).
     409      real pdqmuchem(ngrid,nlayer,nq)    ! Condensable gases through muphi tendency (kg/kg_of_air/s).
    409410      real pdqmufi(ngrid,nlayer,nq)      ! Microphysical tendency (X/kg_of_air/s).
    410411      real pdqmufi_prod(ngrid,nlayer,nq) ! Aerosols production tendency (kg/kg_of_air/s).
     
    15191520      if (tracer) then
    15201521
    1521 !      ---------------------------------------
    1522 !      Methane ice condensation in the atmosphere
    1523 !      ----------------------------------------
     1522         !-------------------------------------------------
     1523         ! Methane (CH4) ice condensation in the atmosphere
     1524         !-------------------------------------------------
    15241525         rice_ch4(:,:)=0 ! initialization needed for callsedim
    15251526         zdqch4cloud(:,:,:)=0.
     
    15531554         end if
    15541555
    1555 !      ---------------------------------------
    1556 !      CO ice condensation in the atmosphere
    1557 !      ----------------------------------------
     1556         !--------------------------------------
     1557         ! CO ice condensation in the atmosphere
     1558         !--------------------------------------
    15581559         zdqcocloud(:,:,:)=0.
    15591560         IF ((carbox).and.(monoxcloud).and.(.not.fast)) THEN
     
    15871588         rice_co(:,:)=0 ! initialization needed for callsedim
    15881589         END IF  ! of IF (carbox)
     1590
     1591         !--------------------------------------------------
     1592         ! Condensable gases through muphi in the atmosphere
     1593         !--------------------------------------------------
     1594         pdqmuchem(:,:,:) = 0.
     1595         IF (callmufi) THEN
     1596            call mugas_prof(ngrid,nlayer,nq,zzlay,zzlev,pplay,pt,pdqmuchem)
     1597         ENDIF
     1598         pdq(:,:,:) = pdq(:,:,:) + pdqmuchem(:,:,:)
    15891599
    15901600         ! ----------------------------------------
  • trunk/LMDZ.PLUTO/libf/phypluto/tracer_h.F90

    r3936 r3949  
    5757       integer,save :: igcm_n2
    5858       integer,save :: igcm_ar
    59        integer,save :: igcm_ch4_gas ! methane gas
     59       integer,save :: igcm_ch4_gas    ! CH4 gas
     60       integer,save :: igcm_C2H2_mugas ! C2H2 gas (condensable in microphysics)
     61       integer,save :: igcm_C2H6_mugas ! C2H6 gas (condensable in microphysics)
     62       integer,save :: igcm_C4H2_mugas ! C4H2 gas (condensable in microphysics)
     63       integer,save :: igcm_C6H6_mugas ! C6H6 gas (condensable in microphysics)
     64       integer,save :: igcm_HCN_mugas  ! HCN gas  (condensable in microphysics)
    6065!$OMP THREADPRIVATE(igcm_co_gas,igcm_n2,igcm_ar,igcm_ch4_gas)
     66!$OMP THREADPRIVATE(igcm_C2H2_mugas,igcm_C2H6_mugas,igcm_C4H2_mugas,igcm_C6H6_mugas,igcm_HCN_mugas)
    6167       ! Other tracers
    6268       integer,save :: igcm_ar_n2   ! for simulations using co2 + neutral gaz
Note: See TracChangeset for help on using the changeset viewer.