Changeset 3126 for trunk/LMDZ.MARS/libf


Ignore:
Timestamp:
Nov 15, 2023, 3:13:25 PM (16 months ago)
Author:
llange
Message:

Mars PCM

  • Update in soilwater: adding the possibility to run without adsorption, but with the possibility to run with seasonal frost forming in the subsurface
  • THe choice of the isotherm for adsorption can be now done by setting the integer choice_ads in the callphys.def choice_ads = 1 adsorption rate is computed with the H2O thermal speed; choice_ads = 2 adsorption rate is computed based on exeperimental resutls, choice_ads =3 no adsorption

LL

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

Legend:

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

    r3115 r3126  
    3232! Subsurface tracers:
    3333  logical,save :: adsorption_soil             ! boolean to call adosrption (or not)
     34  real,save :: choice_ads                     ! Choice for adsorption isotherm (3 means no adsorption, see soilwater.F90)
    3435  integer, parameter :: nqsoil = 3            ! number of subsurface tracers, only three when working with water
    3536  real,save,allocatable :: qsoil(:,:,:,:)     ! subsurface tracers (kg/m^3 of regol)
     
    3738  integer, parameter :: igcm_h2o_ice_soil = 2
    3839  integer, parameter :: igcm_h2o_vap_ads  = 3
    39 !$OMP THREADPRIVATE(adsorption_soil,qsoil)
     40!$OMP THREADPRIVATE(adsorption_soil,qsoil,choice_ads)
    4041
    4142
  • trunk/LMDZ.MARS/libf/phymars/conf_phys.F

    r3125 r3126  
    4040     &                           lag_layer
    4141      use microphys_h, only: mteta
    42       use comsoil_h, only: adsorption_soil
     42      use comsoil_h, only: adsorption_soil, choice_ads
    4343
    4444      IMPLICIT NONE
     
    10171017     &        "Adsorption must be used with water = true",1)
    10181018         endif 
     1019
     1020         if(adsorption_soil) choice_ads = 1
     1021         call getin_p("choice_ads",choice_ads)
     1022           
    10191023c        ----------------------------------------------------------
    10201024
  • trunk/LMDZ.MARS/libf/phymars/soil_settings.F

    r3115 r3126  
    450450             call get_field(txt,qsoil(:,:,igcm_h2o_vap_soil,:),found,
    451451     &                                                 indextime)
    452              write(*,*) 'found',found
    453              write(*,*) 'igcm_',igcm_h2o_vap_soil
    454              write(*,*) 'q=',qsoil(:,:,:,:)
    455452             if (.not.found) then
    456453               write(*,*) "phyetat0: Failed loading <",trim(txt),">"
  • trunk/LMDZ.MARS/libf/phymars/soilwater.F90

    r3121 r3126  
    55
    66
    7       use comsoil_h, only: igcm_h2o_vap_soil, igcm_h2o_ice_soil, igcm_h2o_vap_ads, layer, mlayer
     7      use comsoil_h, only: igcm_h2o_vap_soil, igcm_h2o_ice_soil, igcm_h2o_vap_ads, layer, mlayer, choice_ads
    88      use comcstfi_h
    99      use tracer_mod
     
    204204real*8, parameter:: Sm = 10.6D-20         ! Surface of the water molecule (m2) (only needed in the theoretical formula which is not used right now)
    205205
    206 integer, parameter :: choice_ads = 1      ! Choice of adsorption - desorption constants 3: no adsorption
    207206
    208207! Reference values for choice_ads = 2
     
    350349                              saturation_water_ice(ig, ik) = min(ice(ig, ik) / (rho_H2O_ice * porosity_ice_free(ig, ik)), 0.999D-0)
    351350                              porosity(ig, ik) = porosity_ice_free(ig, ik) * (1.D0 - saturation_water_ice(ig, ik))
    352                              
     351
    353352                              if (choice_ads.eq.1) then
    354353                                    vth(ig, ik) = dsqrt(8.D0 * 8.314D0 * tsoil(ig, nsoil - 4) &
     
    373372                                         
    374373                                    Ka(ig, ik) = kinetic_factor * k_ads_eq(ig, ik) / (1.D0 + k_ads_eq(ig, ik) / porosity(ig, ik))
     374       
    375375                              endif
    376376
    377                               adswater(ig, ik) = min(Ka(ig, ik) / Kd(ig, ik) * znsoil(ig, ik), adswater_sat)
     377                              if(choice_ads .ne. 3) adswater(ig, ik) = min(Ka(ig, ik) / Kd(ig, ik) * znsoil(ig, ik), adswater_sat)
    378378                             
    379379                        else  ! in 3D simulations initialisation happens with newstart.F
     
    381381                              ice(ig, ik) = pqsoil(ig, ik, igcm_h2o_ice_soil)
    382382                              adswater(ig, ik) = pqsoil(ig, ik, igcm_h2o_vap_ads)
     383                        endif
     384
     385                        if (choice_ads.eq.3) then ! no adsorption
     386
     387                               Ka(:, :) = 0.
     388                               Kd(:, :) = 0.
     389                               adswater(:,:) = 0.
     390
    383391                        endif
    384392
     
    584592                        ! calculate the absorption coefficient
    585593                        Ka(ig, ik) = kinetic_factor * k_ads_eq(ig, ik) / (1.D0 + k_ads_eq(ig, ik) / porosity(ig, ik))
     594                  else  ! no ads
     595
     596                        Kd(ig, ik) = 0.
     597
     598                        Ka(ig, ik) = 0.
    586599                  endif
    587600                 
    588601                  ! calculate the amount of water vapor at adorption saturation
    589                   nsat(ig, ik) = adswater_sat * Kd(ig, ik) / Ka(ig, ik)
     602                 
     603                  if (choice_ads.ne.3) nsat(ig, ik) = adswater_sat * Kd(ig, ik) / Ka(ig, ik)
    590604
    591605                  ! calculate C, E, and F coefficients for later calculations
     
    12851299                 
    12861300                  ! calculate how close the water vapor content is to saturizing the adsorbed water
    1287                   preduite(ig, ik) = znsoil(ig, ik) / nsat(ig, ik)
     1301                  if (choice_ads.ne.3) preduite(ig, ik) = znsoil(ig, ik) / nsat(ig, ik)
    12881302                 
    12891303                  ! write the results to the return variable
Note: See TracChangeset for help on using the changeset viewer.