Ignore:
Timestamp:
Jan 16, 2025, 9:50:10 AM (6 months ago)
Author:
jbclement
Message:

Mars PCM:

  • Correction of r3581: the key-words to get 'albedo_perennialco2(1:2)" from the "callphys.def" are now 'albedo_perennialco2_north' and 'albedo_perennialco2_south'.
  • Moving 'albedo_perennialco2' from the 'paleoclimate' module to the 'surfdat_h' module.

JBC

Location:
trunk/LMDZ.MARS/libf/phymars
Files:
4 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.MARS/libf/phymars/albedocaps.F90

    r3581 r3582  
    66use ioipsl_getin_p_mod, only: getin_p
    77use geometry_mod, only: latitude ! grid point latitudes (rad)
    8 use surfdat_h, only: TESicealbedo, TESice_Ncoef, TESice_Scoef, &
     8use surfdat_h, only: TESicealbedo, TESice_Ncoef, TESice_Scoef,       &
    99                     emisice, albedice, watercaptag, albedo_h2o_cap, &
    10                      emissiv, albedodat
     10                     emissiv, albedodat, albedo_perennialco2
    1111USE mod_phys_lmdz_transfert_para, ONLY: bcast
    1212USE mod_phys_lmdz_para, ONLY: is_master
    13 USE paleoclimate_mod, ONLY: paleoclimate, albedo_perennialco2
     13USE paleoclimate_mod, ONLY: paleoclimate
    1414
    1515implicit none
  • trunk/LMDZ.MARS/libf/phymars/conf_phys.F

    r3581 r3582  
    2020     &                       nuice_ref,nuiceco2_ref
    2121      use surfdat_h, only: albedo_h2o_cap,albedo_h2o_frost,
     22     &                     albedo_perennialco2,
    2223     &                     frost_albedo_threshold, inert_h2o_ice,
    2324     &                     frost_metam_threshold,old_wsublimation_scheme
     
    3738      use aeropacity_mod, only: iddist, topdustref
    3839      USE mod_phys_lmdz_transfert_para, ONLY: bcast
    39       USE paleoclimate_mod,ONLY: paleoclimate,albedo_perennialco2,
     40      USE paleoclimate_mod,ONLY: paleoclimate,
    4041     &                           lag_layer, include_waterbuoyancy
    4142      use microphys_h, only: mteta
     
    5657     
    5758      real :: ecritphy ! to check that this obsolete flag is no longer used...
    58       real :: value_albed
     59      real :: albedo_perennialco2_north, albedo_perennialco2_south
    5960 
    6061      CHARACTER ch1*12
     
    385386
    386387         write(*,*)"Albedo for perennial CO2 ice (northern hemisphere)?"
    387          albedo_perennialco2(1) = 0.6 ! default value
    388          call getin_p("albedo_perennialco2_north",value_albed)
    389          albedo_perennialco2(1) = value_albed
     388         albedo_perennialco2_north = 0.6 ! default value
     389         call getin_p("albedo_perennialco2_north",albedo_perennialco2_
     390     &   north)
     391         albedo_perennialco2(1) = albedo_perennialco2_north
    390392         write(*,*)"albedo_perennialco2(1) = ",albedo_perennialco2(1)
    391393         
    392394         write(*,*)"Albedo for perennial CO2 ice (southern hemisphere)?"
    393          albedo_perennialco2(2) = 0.85 ! default value
    394          call getin_p("albedo_perennialco2_south",value_albed)
    395          albedo_perennialco2(2) = value_albed
     395         albedo_perennialco2_south = 0.85 ! default value
     396         call getin_p("albedo_perennialco2_south",albedo_perennialco2_
     397     &   south)
     398         albedo_perennialco2(2) = albedo_perennialco2_south
    396399         write(*,*)"albedo_perennialco2(2) = ",albedo_perennialco2(2)
    397400
  • trunk/LMDZ.MARS/libf/phymars/paleoclimate_mod.F90

    r3581 r3582  
    1717    real,    allocatable, dimension(:,:) :: lag_co2_ice           ! Thickness of the lag before CO2 ice [m]
    1818    real,    allocatable, dimension(:,:) :: d_coef                ! Diffusion coefficent
    19     real, dimension(2)                   :: albedo_perennialco2   ! Albedo for perennial co2 ice [1]
    2019    logical                              :: lag_layer             ! Does lag layer is present?
    2120    logical                              :: include_waterbuoyancy ! Include the effect of water buoyancy when computing the sublimation of water ice ?
    22 !$OMP THREADPRIVATE(h2o_ice_depth,lag_co2_ice,d_coef,albedo_perennialco2,lag_layer,include_waterbuoyancy)
     21!$OMP THREADPRIVATE(h2o_ice_depth,lag_co2_ice,d_coef,lag_layer,include_waterbuoyancy)
    2322
    2423!=======================================================================
  • trunk/LMDZ.MARS/libf/phymars/surfdat_h.F90

    r3581 r3582  
    22
    33  ! arrays are allocated in conf_phys
    4   real,save,allocatable :: albedodat(:) ! albedo of bare ground
    5   real,save,allocatable :: phisfi(:) ! geopotential at ground level
    6   real, dimension(2) :: albedice ! default albedo for ice (1:Northern hemisphere 2:Southern hemisphere)
    7   real, dimension(2) :: emisice ! ice emissivity (1:Northern hemisphere 2:Southern hemisphere)
    8   real,save :: emissiv ! emissivity of bare ground
    9   logical,save :: TESicealbedo ! use TES ice cap albedoes (if set to .true.)
    10   logical,save,allocatable :: watercaptag(:) ! flag for water ice surface
    11   real, save, allocatable :: dryness(:)
     4  real, allocatable    :: albedodat(:) ! albedo of bare ground
     5  real, allocatable    :: phisfi(:) ! geopotential at ground level
     6  real, dimension(2)   :: albedice ! default albedo for ice (1:Northern hemisphere 2:Southern hemisphere)
     7  real, dimension(2)   :: emisice ! ice emissivity (1:Northern hemisphere 2:Southern hemisphere)
     8  real                :: emissiv ! emissivity of bare ground
     9  logical              :: TESicealbedo ! use TES ice cap albedoes (if set to .true.)
     10  logical, allocatable :: watercaptag(:) ! flag for water ice surface
     11  real,   allocatable :: dryness(:)
    1212
    1313!$OMP THREADPRIVATE(albedodat, phisfi,albedice,emisice,emissiv,TESicealbedo,     &
    1414!$OMP                watercaptag,dryness)
    15      
    16   logical,save :: temptag !temp tag for water caps
     15
     16  logical :: temptag !temp tag for water caps
    1717
    1818!$OMP THREADPRIVATE(temptag)
    19      
    20   real,save :: albedo_h2o_cap ! water cap albedo
    21   real,save :: albedo_h2o_frost ! water frost albedo
    22   real,save :: inert_h2o_ice ! water ice thermal inertia
    23   real,save :: frost_albedo_threshold ! water frost thickness on the ground (kg.m^-2, ie mm)
    24   real,save :: frost_metam_threshold ! water frost threshold before conversion to ice (kg.m^-2, ie mm)
    25   real,save :: TESice_Ncoef ! coefficient for TES ice albedo in Northern hemisphere
    26   real,save :: TESice_Scoef ! coefficient for TES ice albedo in Southern hemisphere
    27   real,save :: iceradius(2) , dtemisice(2)
    28   real,save,allocatable :: zmea(:),zstd(:),zsig(:),zgam(:),zthe(:)
    29   real,save,allocatable :: hmons(:),summit(:),base(:)
    30   real,save,allocatable :: z0(:) ! surface roughness length (m)
    31   real,save :: z0_default ! default (constant over planet) surface roughness (m)
    3219
    33   LOGICAL, SAVE :: old_wsublimation_scheme    ! TEMPORARY : TO USE THE OLD WATER SUBLIMATION SCHEME (i.e., using Cd instead of Ch), true by default
     20  real              :: albedo_h2o_cap ! water cap albedo
     21  real              :: albedo_h2o_frost ! water frost albedo
     22  real              :: inert_h2o_ice ! water ice thermal inertia
     23  real              :: frost_albedo_threshold ! water frost thickness on the ground (kg.m^-2, ie mm)
     24  real              :: frost_metam_threshold ! water frost threshold before conversion to ice (kg.m^-2, ie mm)
     25  real              :: TESice_Ncoef ! coefficient for TES ice albedo in Northern hemisphere
     26  real              :: TESice_Scoef ! coefficient for TES ice albedo in Southern hemisphere
     27  real              :: iceradius(2) , dtemisice(2)
     28  real, allocatable :: zmea(:),zstd(:),zsig(:),zgam(:),zthe(:)
     29  real, allocatable :: hmons(:),summit(:),base(:)
     30  real, allocatable :: z0(:) ! surface roughness length (m)
     31  real              :: z0_default ! default (constant over planet) surface roughness (m)
     32
     33  logical :: old_wsublimation_scheme    ! TEMPORARY : TO USE THE OLD WATER SUBLIMATION SCHEME (i.e., using Cd instead of Ch), true by default
    3434
    3535!$OMP THREADPRIVATE(albedo_h2o_cap,albedo_h2o_frost,inert_h2o_ice,               &
     
    4040
    4141  !! mountain top dust flows
    42   REAL,SAVE,ALLOCATABLE :: alpha_hmons(:) ! sub-grid scale mountain mesh fraction
    43   REAL,SAVE,ALLOCATABLE :: hsummit(:) ! mountain height above the GCM surface
    44   LOGICAL,SAVE,ALLOCATABLE :: contains_mons(:) ! is there a mountain in the grid mesh ?
    45          
     42  real,    allocatable :: alpha_hmons(:) ! sub-grid scale mountain mesh fraction
     43  real,    allocatable :: hsummit(:) ! mountain height above the GCM surface
     44  logical, allocatable :: contains_mons(:) ! is there a mountain in the grid mesh ?
     45
    4646!$OMP THREADPRIVATE(alpha_hmons,hsummit,contains_mons)
    4747
    4848  !! variables
    49   REAL,SAVE,ALLOCATABLE :: tsurf(:,:)   ! Surface temperature (K)
    50   REAL,SAVE,ALLOCATABLE :: emis(:,:)    ! Thermal IR surface emissivity
    51   REAL,SAVE,ALLOCATABLE :: capcal(:,:) ! surface heat capacity (J m-2 K-1)
    52   REAL,SAVE,ALLOCATABLE :: fluxgrd(:,:) ! surface conduction flux (W.m-2)
    53   REAL,ALLOCATABLE,SAVE :: qsurf(:,:,:) ! tracer on surface (e.g. kg.m-2)
    54   REAL,SAVE,ALLOCATABLE :: watercap(:,:) ! Surface water ice (kg.m-2)
    55   REAL,SAVE,ALLOCATABLE :: perennial_co2ice(:,:) ! Perennial CO2 ice (kg.m-2)
     49  real, allocatable  :: tsurf(:,:)   ! Surface temperature (K)
     50  real, allocatable  :: emis(:,:)    ! Thermal IR surface emissivity
     51  real, allocatable  :: capcal(:,:) ! surface heat capacity (J m-2 K-1)
     52  real, allocatable  :: fluxgrd(:,:) ! surface conduction flux (W.m-2)
     53  real, allocatable  :: qsurf(:,:,:) ! tracer on surface (e.g. kg.m-2)
     54  real, allocatable  :: watercap(:,:) ! Surface water ice (kg.m-2)
     55  real, allocatable  :: perennial_co2ice(:,:) ! Perennial CO2 ice (kg.m-2)
     56  real, dimension(2) :: albedo_perennialco2   ! Albedo for perennial co2 ice (-)
    5657!$OMP THREADPRIVATE(tsurf,emis,capcal,fluxgrd,qsurf,watercap,perennial_co2ice)
    5758
     
    5960
    6061  subroutine ini_surfdat_h(ngrid,nq,nslope)
    61  
     62
    6263  implicit none
    6364  integer,intent(in) :: ngrid ! number of atmospheric columns
    64   integer,intent(in) :: nq ! number of tracers 
    65   integer,intent(in) :: nslope ! number of sub-grid scale slope 
     65  integer,intent(in) :: nq ! number of tracers
     66  integer,intent(in) :: nslope ! number of sub-grid scale slope
     67
    6668    allocate(albedodat(ngrid))
    6769    allocate(phisfi(ngrid))
     
    8789    allocate(hsummit(ngrid))
    8890    allocate(contains_mons(ngrid))
    89        
     91
    9092  end subroutine ini_surfdat_h
    9193
     
    118120    if (allocated(hsummit))          deallocate(hsummit)
    119121    if (allocated(contains_mons))    deallocate(contains_mons)
    120    
     122
    121123  end subroutine end_surfdat_h
    122124
    123125  subroutine ini_surfdat_h_slope_var(ngrid,nq,nslope)
    124  
     126
    125127  implicit none
    126128  integer,intent(in) :: ngrid ! number of atmospheric columns
    127   integer,intent(in) :: nq ! number of tracers 
    128   integer,intent(in) :: nslope ! number of sub-grid scale slope 
     129  integer,intent(in) :: nq ! number of tracers
     130  integer,intent(in) :: nslope ! number of sub-grid scale slope
    129131    allocate(qsurf(ngrid,nq,nslope))
    130132    allocate(tsurf(ngrid,nslope))
     
    134136    allocate(capcal(ngrid,nslope))
    135137    allocate(fluxgrd(ngrid,nslope))
    136        
     138
    137139  end subroutine ini_surfdat_h_slope_var
    138140
     
    148150    if (allocated(capcal))           deallocate(capcal)
    149151    if (allocated(fluxgrd))          deallocate(fluxgrd)
    150    
     152
    151153  end subroutine end_surfdat_h_slope_var
    152154
Note: See TracChangeset for help on using the changeset viewer.