Changeset 3356 for trunk/LMDZ.PLUTO


Ignore:
Timestamp:
Jun 4, 2024, 5:56:14 PM (6 months ago)
Author:
afalco
Message:

Pluto PCM:
sedimentation uses pphi. More precise than generic sedimentation?
molrad and visc adapted to Pluto.
AF

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

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.PLUTO/libf/phypluto/callsedim.F

    r3334 r3356  
    11      SUBROUTINE callsedim(ngrid,nlay, ptimestep,
    22     &                pplev,zlev, pt, pdt,
    3      &                pq, pdqfi, pdqsed,pdqs_sed,nq)
     3     &                pq, pdqfi, pdqsed,pdqs_sed,nq,pphi)
    44
    55      use radinc_h, only : naerkind
     
    3939      real,intent(in):: pdt(ngrid,nlay) ! tendency on temperature
    4040      real,intent(in):: zlev(ngrid,nlay+1)  ! altitude at layer boundaries
     41      real,intent(in):: pphi(ngrid,nlay)      ! geopotential
    4142      integer,intent(in) :: nq ! number of tracers
    4243      real,intent(in) :: pq(ngrid,nlay,nq)  ! tracers (kg/kg)
     
    120121             call newsedim(ngrid,nlay,1,ptimestep,
    121122     &            pplev,masse,epaisseur,zt,radius(iq),rho_q(iq),
    122      &            zqi(1,1,iq),wq,iq)
     123     &            zqi(1,1,iq),wq,iq,pphi)
    123124      !  endif
    124125
  • trunk/LMDZ.PLUTO/libf/phypluto/newsedim.F

    r3184 r3356  
    11      SUBROUTINE newsedim(ngrid,nlay,naersize,ptimestep,
    2      &  pplev,masse,epaisseur,pt,rd,rho,pqi,wq,iq)
     2     &  pplev,masse,epaisseur,pt,rd,rho,pqi,wq,iq,pphi)
    33     
    44      use ioipsl_getin_p_mod, only: getin_p
    5       use comcstfi_mod, only: r, g
     5      use comcstfi_mod, only: r, g, rad
    66      use gases_h
    77      ! use tracer_h, only : igcm_h2o_ice
     
    4141      real,intent(out) :: wq(ngrid,nlay+1)  ! flux of tracer during timestep (?/m-2)
    4242      integer,intent(in) :: iq ! tracer index
     43      real,intent(in):: pphi(ngrid,nlay)      ! geopotential
    4344
    4445c   local:
     
    9091         do igas=1, ngasmx
    9192           if(gfrac(igas).ge.0.0) then
    92              if(igas.eq.igas_N2) then
    93                molrad = molrad + gfrac(igas)*2.2e-10                              ! N2
    94                visc(:,:) = visc(:,:) + gfrac(igas)*1.0e-5                         ! N2
     93             if(igas.eq.igas_CO2) then
     94               molrad = molrad + gfrac(igas)*2.2e-10                              ! CO2
     95               visc(:,:) = visc(:,:) + gfrac(igas)*1.0e-5                         ! CO2
    9596             elseif(igas.eq.igas_N2) then
    9697               molrad = molrad + gfrac(igas)*1.8e-10                              ! N2 (Kunze et al. 2022)
     
    110111               visc(:,:) = visc(:,:) + gfrac(igas)*1.0e-5                         ! CH4
    111112             else
    112                molrad = molrad + gfrac(igas)*2.2e-10                              ! N2 by default
    113                visc(:,:) = visc(:,:) + gfrac(igas)*1.e-5                          ! N2 by default
     113               molrad = molrad + gfrac(igas)*1.93e-10                              ! N2 by default
     114               visc(:,:) = visc(:,:) + 6.67e-6                          ! N2 by default
    114115               write(*,*) trim(gnom(igas))," is not included in"
    115116     &              ," newsedim, N2 is used by default"
     
    181182              rsurf=rfall
    182183            ! endif
     184
     185          !  b = 2./9. * g
     186            b = 2./9. * ((g*rad-pphi(ig,l))**2/(g*(rad**2))) ! AF24: from Pluto.old
    183187
    184188            vstokes(ig,l) = b / visc(ig,l) * rho * rfall**3 / rsurf *
  • trunk/LMDZ.PLUTO/libf/phypluto/physiq_mod.F90

    r3353 r3356  
    15121512               call callsedim(ngrid,nlayer,ptimestep,       &
    15131513                          pplev,zzlev,pt,pdt,pq,pdq,        &
    1514                           zdqsed,zdqssed,nq)
     1514                          zdqsed,zdqssed,nq,pphi)
    15151515            endif
    15161516
Note: See TracChangeset for help on using the changeset viewer.