Ignore:
Timestamp:
Jul 19, 2023, 11:40:38 AM (19 months ago)
Author:
llange
Message:

Mars PCM
Include perenial_co2ice (equivalent of watercap) to distinguich between CO2 frost and perenial CO2 ice for paleoclimate studies.
When no frost is present and we dig into perenial ice, the surface albedo is changed. The albedo for seasonal ice is set to 0.65, and the perenial ice albedo can be fixed in the callphys.def. I recommand values between 0.8 and 0.9.
To use this, paleoclimate must be set to True and TESalbedo to false in the callphys.def. Else, it runs as usual with TES albedo
LL

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.MARS/libf/phymars/co2condens_mod.F

    r2977 r2999  
    1111     $                  pcapcal,pplay,pplev,ptsrf,pt,
    1212     $                  pphi,pdt,pdu,pdv,pdtsrf,pu,pv,pq,pdq,
    13      $                  piceco2,psolaralb,pemisurf,rdust,
     13     $                  piceco2,perenial_co2ice,
     14     $                  psolaralb,pemisurf,rdust,
    1415     $                  pdtc,pdtsrfc,pdpsrf,pduc,pdvc,pdqc,
    1516     $                  fluxsurf_sw,zls,
     
    3536#endif
    3637      use comslope_mod, ONLY: subslope_dist,def_slope_mean
     38      USE paleoclimate_mod, ONLY: paleoclimate
     39
    3740       IMPLICIT NONE
    3841c=======================================================================
     
    8790
    8891      REAL,INTENT(INOUT) :: piceco2(ngrid,nslope) ! CO2 ice on the surface (kg.m-2)
     92      REAL,INTENT(INOUT) :: perenial_co2ice(ngrid,nslope) ! Perenial CO2 ice on the surface (kg.m-2)
    8993      REAL,INTENT(INOUT) :: psolaralb(ngrid,2,nslope) ! albedo of the surface
    9094      REAL,INTENT(INOUT) :: pemisurf(ngrid,nslope) ! emissivity of the surface
     
    180184      REAL   :: alb_tmp(ngrid,2) ! local
    181185      REAL   :: zcondices_tmp(ngrid)    ! local 
    182       REAL   :: piceco2_tmp(ngrid)    ! local 
     186      REAL   :: piceco2_tmp(ngrid)    ! local
     187      REAL   :: perenial_co2ice_tmp(ngrid) ! perenial ice on one subslope (kg/m^2)
    183188      REAL   :: pemisurf_tmp(ngrid)! local
    184189      LOGICAL :: condsub_tmp(ngrid) !local
     
    568573        piceco2_tmp(:) = piceco2(:,islope)
    569574        alb_tmp(:,:) = psolaralb(:,:,islope)
    570         emisref_tmp(:) = 0.
    571         CALL albedocaps(zls,ngrid,piceco2_tmp,alb_tmp,emisref_tmp)
     575        emisref_tmp(:) = 0.
     576        perenial_co2ice_tmp(:) =  perenial_co2ice(:,islope)
     577        CALL albedocaps(zls,ngrid,piceco2_tmp,perenial_co2ice_tmp,
     578     &                  alb_tmp,emisref_tmp)
     579        perenial_co2ice(:,islope) = perenial_co2ice_tmp(:)
    572580        psolaralb(:,1,islope) =  alb_tmp(:,1)
    573581        psolaralb(:,2,islope) =  alb_tmp(:,2)
     
    823831! Extra special case for surface temperature tendency pdtsrfc:
    824832! we want to fix the south pole temperature to CO2 condensation temperature
    825          if (caps.and.(obliquit.lt.27.)) then
     833         if (caps.and.(obliquit.lt.27.).and.(.not.(paleoclimate))) then
    826834           ! check if last grid point is the south pole
    827835           if (abs(latitude(ngrid)-(-pi/2.)).lt.1.e-5) then
Note: See TracChangeset for help on using the changeset viewer.