Changeset 3844


Ignore:
Timestamp:
Jul 13, 2025, 10:11:41 PM (4 days ago)
Author:
tbertrand
Message:

Pluto PCM
CO cycle now possible with the option no_n2frost (CO condensation and sublimation is limited to within the N2 ice deposits only).
NLTE factor 0.33 on the cooling rates now removed in callcorrk.
TB

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

Legend:

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

    r3805 r3844  
    11001100            dtlw_nu(l,nw)=dtlw_nu(l,nw)*eps_nlte_lw(ig,l)
    11011101          else
    1102             !dtlw_nu(l,nw)=1.*dtlw_nu(l,nw) ! no CO correction (Strobbel 1996)
    1103             dtlw_nu(l,nw)=0.33*dtlw_nu(l,nw) ! CO correction (Strobbel 1996)
    1104 !               dtlw_co(ig,l)=dtlw_co(ig,l)+ dtlw_nu(l,nw) ! diagnostic
     1102            dtlw_nu(l,nw)=1.*dtlw_nu(l,nw) ! no CO correction (Strobbel 1996)
     1103            !dtlw_nu(l,nw)=0.33*dtlw_nu(l,nw) ! CO correction (Strobbel 1996)
     1104            !dtlw_co(ig,l)=dtlw_co(ig,l)+ dtlw_nu(l,nw) ! diagnostic
    11051105          end if
    11061106          dtlw(ig,l)=dtlw(ig,l)+ dtlw_nu(l,nw) !average now on each wavelength
  • trunk/LMDZ.PLUTO/libf/phypluto/cocloud.F90

    r3585 r3844  
    159159!         enddo
    160160
    161          call cosat(ngrid*nlay,zt,pplay,zqsat,vecnull,vecnull)
     161         call cosat(ngrid*nlay,zt,pplay,zqsat,vecnull)
    162162!        TEMPORAIRE :
    163163!        test sans condensation atmospherique
  • trunk/LMDZ.PLUTO/libf/phypluto/cosat.F90

    r3247 r3844  
    1 subroutine cosat(nsize,t,p,qsat,qsurf_n2,qsurf_ch4)
     1subroutine cosat(nsize,t,p,qsat,qsurf_n2)
    22
    33  IMPLICIT NONE
     
    1515      real t(nsize) , p(nsize)
    1616!   OUTPUT
    17       real qsat(nsize),qsurf_n2(nsize),qsurf_ch4(nsize)
     17      real qsat(nsize),qsurf_n2(nsize)
    1818      INTEGER i
    1919
     
    2121      do i=1,nsize
    2222
    23 !          from Fray and schmitt fit by formulation L = 2.74e5 J/kg
    24            qsat(i)=0.1537*exp((28*274./8.314)*(1/68.1-1/t(i)))*100000*28.0/(28.0*p(i))
    25 
    26 !          Raoult law if mixte in N2 ice and CH4 ice : assume 0.3% CO in N2
    27 !          (Merlin) and 0.3% in CH4
    28 !          if ((qsurf_n2(i).gt.0.001).or.(qsurf_ch4(i).gt.0.001)) then
     23!       from Fray and schmitt fit by formulation L = 2.74e5 J/kg
     24        qsat(i)=0.1537*exp((28*274./8.314)*(1/68.1-1/t(i)))*100000*28.0/(28.0*p(i))
    2925
    3026!       Raoult law if mixte in N2 ice : assume 0.3% CO in N2
  • trunk/LMDZ.PLUTO/libf/phypluto/cosurf.F

    r3539 r3844  
    7474      ENDDO
    7575
    76       call cosat(ngrid,tsurf,zpsrf,qsat,pqsurf(:,igcm_n2),
    77      &                                       pqsurf(:,igcm_ch4_ice))
     76      call cosat(ngrid,tsurf,zpsrf,qsat,pqsurf(:,igcm_n2))
    7877
    7978      DO ig=1,ngrid
  • trunk/LMDZ.PLUTO/libf/phypluto/inifis_mod.F90

    r3812 r3844  
    13641364         call abort_physic(rname, 'for now, haze/rad_proffix only works with optichaze=T', 1)
    13651365     endif
    1366       if (carbox.and.condcosurf.and.no_n2frost) then
    1367         call abort_physic(rname, "CO surface condensation and no_n2frost are both active which may not be relevant", 1)
    1368       end if
     1366     ! if (carbox.and.condcosurf.and.no_n2frost) then
     1367     !   call abort_physic(rname, "CO surface condensation and no_n2frost are both active which may not be relevant", 1)
     1368     ! end if
    13691369
    13701370     if ((cpp_mugaz_mode >= 1).and.(is_master).and.(ngrid>1)) then
  • trunk/LMDZ.PLUTO/libf/phypluto/physiq_mod.F90

    r3816 r3844  
    21102110      endif ! end of 'lastcall'
    21112111
     2112      if(mod(icount,diagfi_output_rate).eq.0) then
     2113         write_restartfi = .true.
     2114      endif
    21122115      if(startfi_output_rate.ne.0)then
    21132116         if (mod(icount,startfi_output_rate).eq.0) then
  • trunk/LMDZ.PLUTO/libf/phypluto/vdifc_pluto_mod.F90

    r3627 r3844  
    1515      use comgeomfi_h
    1616      use callkeys_mod, only: carbox, methane, condcosurf, condensn2, condmetsurf,&
    17                               kmix_proffix, vertdiff, tracer, kmixmin
     17                              kmix_proffix, vertdiff, tracer, kmixmin, no_n2frost
    1818      use datafile_mod, only: datadir
    1919      use surfdat_h, only: phisfi
     
    100100      REAL zcst1
    101101      REAL zu2
    102 
     102      REAL qsat_co_factor(ngrid)   ! factor to prevent co frost formation if no n2 frost
    103103      EXTERNAL SSUM,SCOPY
    104104      REAL SSUM
     
    159159            close(114)
    160160        ENDIF
     161
     162        ! If fixed distribution of N2, then no CO frost either
     163        qsat_co_factor(:)=1.
     164        IF (no_n2frost) then
     165           DO ig=1,ngrid
     166              if (pqsurf(ig,igcm_n2).eq.0.) then
     167                   qsat_co_factor(ig) = 1.e6
     168              endif
     169           ENDDO
     170        ENDIF
     171
    161172      ENDIF
    162173
     
    645656          ELSE IF (carbox.and.(iq.eq.igcm_co_gas)) then
    646657
    647            ! calcul de la valeur de q a la surface :
     658            !! Calculating saturation mixing ratio at surface
    648659            call cosat(ngrid,ptsrf,pplev(1,1),qsat_co, &
    649                    pqsurf(:,igcm_n2),pqsurf(:,igcm_ch4_ice))
     660                   pqsurf(:,igcm_n2))
    650661
    651662            !! Prevent CO condensation at the surface
    652663            if (.not.condcosurf) then
    653664               qsat_co=qsat_co*1.e6
     665            endif
     666            if (no_n2frost) then
     667               qsat_co=qsat_co*qsat_co_factor     
    654668            endif
    655669
Note: See TracChangeset for help on using the changeset viewer.