Changeset 3200 for trunk/LMDZ.MARS


Ignore:
Timestamp:
Feb 2, 2024, 6:06:10 PM (10 months ago)
Author:
jbclement
Message:

Mars PCM:
Small update following r3188 to keep the CO2 mixing ration constant if "CO2cond_ps = 0" + Some cleanings.
JBC

Location:
trunk/LMDZ.MARS
Files:
4 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.MARS/changelog.txt

    r3192 r3200  
    44564456
    44574457== 29/01/2024 == JBC
    4458 Addition of the parameter 'CO2cond_ps' (= 1 by default) for 1D. This coefficient controls the surface pressure change. If 'relaxcoef_ps = 1', then surface pressure varies normally. If 'relaxcoef_ps = 0', then surface pressure is kept constant. The ratio of polar cap surface over planetary surface is a typical value (8.3e-4) for tests. To be defined in "callphys.def" so that both PCM and PEM can read it.
     4458Addition of the parameter 'CO2cond_ps' (= 1 by default) for 1D. This coefficient controls the surface pressure change. If 'CO2cond_ps = 1', then surface pressure varies normally. If 'CO2cond_ps = 0', then surface pressure is kept constant. The ratio of polar cap surface over planetary surface is a typical value (8.3e-4) for tests. To be defined in "callphys.def" so that both PCM and PEM can read it.
    44594459
    44604460== 30/01/2024 == CS
    44614461Update of the reference to default values of coeff_detrainment, coeff_injection, ti_injection and tf_injection (following old revision r2639) in callphys.def.MCD6
     4462
     4463== 02/02/2024 == JBC
     4464Small update following r3188 to keep the CO2 mixing ration constant if "CO2cond_ps = 0" + Some cleanings.
  • trunk/LMDZ.MARS/libf/phymars/dyn1d/init_testphys1d_mod.F90

    r3188 r3200  
    7878real, dimension(1),                  intent(out) :: latitude, longitude, cell_area
    7979real,                                intent(out) :: atm_wat_profile, atm_wat_tau ! Force atmospheric water profiles
    80 real,                                intent(out) :: CO2cond_ps                 ! Relaxation coefficient for psurf
     80real,                                intent(out) :: CO2cond_ps                   ! Coefficient to control the surface pressure change
    8181
    8282!=======================================================================
     
    530530endif !(.not. therestartfi)
    531531
    532 ! emissivity
     532! Emissivity
    533533! ----------
    534534if (.not. therestartfi) then
  • trunk/LMDZ.MARS/libf/phymars/dyn1d/testphys1d.F90

    r3188 r3200  
    270270
    271271    ! Increment tracers
    272     q(1,:,:) = q(1,:,:) + dttestphys*dq(1,:,:)
     272    if (abs(CO2cond_ps) < 1.e-10) then
     273        do iq = 1,nq
     274            if (iq == igcm_co2) cycle
     275            q(1,:,iq) = q(1,:,iq) + dttestphys*dq(1,:,iq)
     276        enddo
     277    else
     278        q = q + dttestphys*dq
     279    endif
    273280enddo ! End of time stepping loop (idt=1,ndt)
    274281
  • trunk/LMDZ.MARS/libf/phymars/paleoclimate_mod.F90

    r3130 r3200  
    66!   author: LL, 06/2023
    77!   ------
    8 !   
     8!
    99!=======================================================================
    1010
    11     IMPLICIT NONE
     11implicit none
    1212
    13     LOGICAL, SAVE :: paleoclimate    ! False by default, is activate  for paleoclimates specific processes (e.g., lag layer)
    14                                      ! is initialized in conf_phys
     13logical, save :: paleoclimate ! False by default, is activate  for paleoclimates specific processes (e.g., lag layer)
     14                              ! is initialized in conf_phys
     15
    1516!$OMP THREADPRIVATE(paleoclimate)
    16 
    17     real, save, allocatable :: h2o_ice_depth(:,:)  ! Thickness of the lag before H2O ice [m]
    18     real, save, allocatable :: lag_co2_ice(:,:)  ! Thickness of the lag before CO2 ice [m]
    19     real, save :: albedo_perennialco2             ! Albedo for perennial co2 ice [1]
    20     real, save, allocatable :: d_coef(:,:)  ! Diffusion coeficent
    21     LOGICAL,SAVE :: lag_layer ! does lag layer is present?
     17    real,    save, allocatable, dimension(:,:) :: h2o_ice_depth       ! Thickness of the lag before H2O ice [m]
     18    real,    save, allocatable, dimension(:,:) :: lag_co2_ice         ! Thickness of the lag before CO2 ice [m]
     19    real,    save, allocatable, dimension(:,:) :: d_coef              ! Diffusion coeficent
     20    real,    save                              :: albedo_perennialco2 ! Albedo for perennial co2 ice [1]
     21    logical, save                              :: lag_layer           ! Does lag layer is present?
    2222!$OMP THREADPRIVATE(h2o_ice_depth,d_coef,lag_co2_ice,albedo_perennialco2)
    2323
    24     CONTAINS
     24!=======================================================================
     25contains
     26!=======================================================================
    2527
     28SUBROUTINE ini_paleoclimate_h(ngrid,nslope)
    2629
    27   subroutine ini_paleoclimate_h(ngrid,nslope)
     30implicit none
    2831
    29   implicit none
    30   integer,intent(in) :: ngrid  ! number of atmospheric columns
    31   integer,intent(in) :: nslope ! number of slope within a mesh
     32integer, intent(in) :: ngrid  ! number of atmospheric columns
     33integer, intent(in) :: nslope ! number of slope within a mesh
    3234
    33     allocate(h2o_ice_depth(ngrid,nslope))
    34     allocate(lag_co2_ice(ngrid,nslope))
    35     allocate(d_coef(ngrid,nslope))
    36   end subroutine ini_paleoclimate_h
     35allocate(h2o_ice_depth(ngrid,nslope))
     36allocate(lag_co2_ice(ngrid,nslope))
     37allocate(d_coef(ngrid,nslope))
    3738
    38   subroutine end_paleoclimate_h
     39END SUBROUTINE ini_paleoclimate_h
    3940
    40   implicit none
    41     if (allocated(d_coef)) deallocate(d_coef)
    42     if (allocated(h2o_ice_depth)) deallocate(h2o_ice_depth)
    43     if (allocated(lag_co2_ice)) deallocate(lag_co2_ice)
    44   end subroutine end_paleoclimate_h
     41!=======================================================================
     42SUBROUTINE end_paleoclimate_h
    4543
     44implicit none
    4645
    47     END MODULE paleoclimate_mod
     46if (allocated(d_coef)) deallocate(d_coef)
     47if (allocated(h2o_ice_depth)) deallocate(h2o_ice_depth)
     48if (allocated(lag_co2_ice)) deallocate(lag_co2_ice)
     49
     50END SUBROUTINE end_paleoclimate_h
     51
     52END MODULE paleoclimate_mod
Note: See TracChangeset for help on using the changeset viewer.