Ignore:
Timestamp:
Feb 21, 2024, 5:45:11 PM (9 months ago)
Author:
afalco
Message:

Pluto PCM:
1D functional
AF

Location:
trunk/LMDZ.PLUTO/libf/phypluto
Files:
1 deleted
4 edited

Legend:

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

    r3228 r3232  
    495495          end do
    496496
     497!             Value transfert at the surface interface when condensation sublimation:
     498
     499          if (zmflux(1).lt.0) then
     500!               Surface condensation
     501            zum(1)= zu(1)
     502            zvm(1)= zv(1)
     503            ztm(1) = ztc(1)
     504          else
     505!               Surface sublimation:
     506            ztm(1) = ztsrf(ig) + pdtsrfc(ig)*ptimestep
     507            zum(1) = 0
     508            zvm(1) = 0
     509          end if
     510          do iq=1,nq
     511              zqm(1,iq)=0. ! most tracer do not condense !
     512          enddo
     513!             Special case if the tracer is n2 gas
     514          if (igcm_n2.ne.0) zqm(1,igcm_n2)=1.
     515
    497516           ztm(2:klev+1)=0.
    498517           zum(2:klev+1)=0.
     
    528547           end if
    529548
    530 !             Value transfert at the surface interface when condensation sublimation:
    531 
    532           if (zmflux(1).lt.0) then
    533 !               Surface condensation
    534             zum(1)= zu(1)
    535             zvm(1)= zv(1)
    536             ztm(1) = ztc(1)
    537           else
    538 !               Surface sublimation:
    539             ztm(1) = ztsrf(ig) + pdtsrfc(ig)*ptimestep
    540             zum(1) = 0
    541             zvm(1) = 0
    542           end if
    543           do iq=1,nq
    544              zqm(1,iq)=0. ! most tracer do not condense !
    545           enddo
    546 !             Special case if the tracer is n2 gas
    547           if (igcm_n2.ne.0) zqm(1,igcm_n2)=1.
    548549
    549550          !!! Source haze: 0.02 pourcent when n2 sublimes
  • trunk/LMDZ.PLUTO/libf/phypluto/dyn1d/kcmprof_fn.F90

    r3184 r3232  
    22
    33use params_h
    4 use watercommon_h, only : mH2O
    54use gases_h
    65use comcstfi_mod, only: mugaz, cpp, g
    7 use callkeys_mod, only: co2cond
     6use callkeys_mod, only: n2cond
    87implicit none
    98
     
    9796     m_v   = 1.0
    9897     tcrit = 1000.0
    99   elseif(trim(gnom(vgas)).eq.'H2O')then
    100      m_v   = dble(mH2O/1000.)
    101      tcrit = 6.47d2
     98!   elseif(trim(gnom(vgas)).eq.'H2O')then
     99   !   m_v   = dble(mH2O/1000.) ! AF24: no water in Pluton
     100   !   tcrit = 6.47d2
    102101  elseif(trim(gnom(vgas)).eq.'NH3')then
    103102     m_v   = 17.031/1000.
     
    368367  enddo
    369368
    370 !    CO2 condensation 'haircut' of temperature profile if necessary
    371   if(co2cond)then
    372      print*,'CO2 condensation haircut - assumes CO2-dominated atmosphere!'
    373      do ilay=2,nlayer
    374         if(P_rcm(ilay).lt.518000.)then
    375            TCO2cond = (-3167.8)/(log(.01*P_rcm(ilay))-23.23) ! Fanale's formula
    376         else
    377            TCO2cond = 684.2-92.3*log(P_rcm(ilay))+4.32*log(P_rcm(ilay))**2
    378            ! liquid-vapour transition (based on CRC handbook 2003 data)
    379         endif
    380 
    381         print*,'p=',P_rcm(ilay),', T=',T_rcm(ilay),' Tcond=',TCO2cond
    382         if(T_rcm(ilay).lt.TCO2cond)then
    383            T_rcm(ilay)=TCO2cond
    384         endif
    385      enddo
    386   endif
    387 
    388369  return
    389370end subroutine kcmprof_fn
  • trunk/LMDZ.PLUTO/libf/phypluto/dyn1d/rcm1d.F

    r3184 r3232  
    8989      REAL,ALLOCATABLE :: qsurf(:)    ! tracer surface budget (e.g. kg.m-2)
    9090      REAL,ALLOCATABLE :: tsoil(:)    ! subsurface soil temperature (K)
    91 !      REAL co2ice               ! co2ice layer (kg.m-2) !not used anymore
    92       integer :: i_co2_ice=0     ! tracer index of co2 ice
     91!      REAL n2ice               ! n2ice layer (kg.m-2) !not used anymore
     92      integer :: i_n2_ice=0     ! tracer index of n2 ice
    9393      integer :: i_h2o_ice=0     ! tracer index of h2o ice
    9494      integer :: i_h2o_vap=0     ! tracer index of h2o vapor
     
    235235      emisice(2)=0.95            ! Emissivite calotte sud 
    236236
    237       iceradius(1) = 100.e-6     ! mean scat radius of CO2 snow (north)
    238       iceradius(2) = 100.e-6     ! mean scat radius of CO2 snow (south)
     237      iceradius(1) = 100.e-6     ! mean scat radius of n2 snow (north)
     238      iceradius(2) = 100.e-6     ! mean scat radius of n2 snow (south)
    239239      dtemisice(1) = 2.          ! time scale for snow metamorphism (north)
    240240      dtemisice(2) = 2.          ! time scale for snow metamorphism (south
     
    313313            endif
    314314          enddo !of do iq=1,nq
    315 ! check for co2_ice / h2o_ice tracers:
    316          i_co2_ice=0
     315! check for n2_ice / h2o_ice tracers:
     316         i_n2_ice=0
    317317         i_h2o_ice=0
    318318         i_h2o_vap=0
    319319         do iq=1,nq
    320            if (tname(iq)=="co2_ice") then
    321              i_co2_ice=iq
     320           if (tname(iq)=="n2") then
     321             i_n2_ice=iq
    322322           elseif (tname(iq)=="h2o_ice") then
    323323             i_h2o_ice=iq
     
    390390      call getin("rad",rad)
    391391      ! Planetary  radius is needed to compute shadow of the rings
    392       IF (rad.eq.-99999. .and. rings_shadow .eqv. .true.) THEN
     392      IF (rad.eq.-99999.) THEN
    393393          PRINT *,"STOP. I NEED rad IN RCM1D.DEF."
    394394          STOP
     
    623623            write(*,*)"  tracer:",trim(txt)
    624624             
    625             ! CO2
    626             if (txt.eq."co2_ice") then
     625            ! n2
     626            if (txt.eq."n2_ice") then
    627627               q(:,iq)=0.   ! kg/kg of atmosphere
    628628               qsurf(iq)=0. ! kg/m2 at the surface               
    629                ! Look for a "profile_co2_ice" input file
    630                open(91,file='profile_co2_ice',status='old',
     629               ! Look for a "profile_n2_ice" input file
     630               open(91,file='profile_n2_ice',status='old',
    631631     &         form='formatted',iostat=ierr)
    632632               if (ierr.eq.0) then
     
    636636                  enddo
    637637               else
    638                   write(*,*) "No profile_co2_ice file!"
     638                  write(*,*) "No profile_n2_ice file!"
    639639               endif
    640640               close(91)
    641             endif ! of if (txt.eq."co2")
     641            endif ! of if (txt.eq."n2")
    642642         
    643643            ! WATER VAPOUR
     
    739739      ENDDO
    740740
    741 c  emissivity / surface co2 ice ( + h2o ice??)
     741c  emissivity / surface n2 ice ( + h2o ice??)
    742742c  -------------------------------------------
    743743      emis(1)=emissiv ! default value for emissivity
     
    745745      call getin("emis",emis(1))
    746746      write(*,*) " emis = ",emis(1)
    747       emissiv=emis(1) ! we do this so that condense_co2 sets things to the right
     747      emissiv=emis(1) ! we do this so that condense_n2 sets things to the right
    748748                   ! value if there is no snow
    749749
    750       if(i_co2_ice.gt.0)then
    751          qsurf(i_co2_ice)=0 ! default value for co2ice
    752          print*,'Initial CO2 ice on the surface (kg.m-2)'
    753          call getin("co2ice",qsurf(i_co2_ice))
    754          write(*,*) " co2ice = ",qsurf(i_co2_ice)
    755          IF (qsurf(i_co2_ice).ge.1.E+0) THEN
    756             ! if we have some CO2 ice on the surface, change emissivity
     750      if(i_n2_ice.gt.0)then
     751         qsurf(i_n2_ice)=0 ! default value for n2ice
     752         print*,'Initial n2 ice on the surface (kg.m-2)'
     753         call getin("n2ice",qsurf(i_n2_ice))
     754         write(*,*) " n2ice = ",qsurf(i_n2_ice)
     755         IF (qsurf(i_n2_ice).ge.1.E+0) THEN
     756            ! if we have some n2 ice on the surface, change emissivity
    757757            if (latitude(1).ge.0) then ! northern hemisphere
    758758              emis(1)=emisice(1)
     
    911911      call physdem1("startfi.nc",nsoilmx,1,llm,nq,
    912912     &                dtphys,time,
    913      &                tsurf,tsoil,emis,q2,qsurf,
    914      &                cloudfrac,totcloudfrac,hice,
    915      &                rnat,pctsrf_sic,tslab,tsea_ice,sea_ice)
     913     &                tsurf,tsoil,emis,q2,qsurf)
    916914
    917915c=======================================================================
  • trunk/LMDZ.PLUTO/libf/phypluto/physiq_mod.F90

    r3228 r3232  
    551551             tsoil(1:ngrid,isoil)=tsurf(1:ngrid)
    552552           enddo
    553            if (is_master) write(*,*) "Physiq: initializing day_ini to pdat !"
     553           if (is_master) write(*,*) "Physiq: initializing day_ini to pday !"
    554554           day_ini=pday
    555555         endif
Note: See TracChangeset for help on using the changeset viewer.