Changeset 3113


Ignore:
Timestamp:
Nov 3, 2023, 2:36:01 PM (14 months ago)
Author:
llange
Message:

Mars PCM
Introducing qsoil to model H2O adsorption/desorption in the subsurface. For now, I've fixed the number of tracers in the subsurface to three (H2O vap, H2O ice, H2O ads).
The model of adsorption/desorption will follow later.
LL

Location:
trunk/LMDZ.MARS
Files:
9 edited

Legend:

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

    r3112 r3113  
    43064306== 03/11/2023 == JBC
    43074307Small fix on "field_def_physics_mars.xml".
     4308
     4309== 03/11/2023 == LL
     4310Introducing qsoil to model H2O adsorption/desorption in the subsurface. For now, I've fixed the number of tracers in the subsurface to t
     4311hree (H2O vap, H2O ice, H2O ads).
     4312
  • trunk/LMDZ.MARS/libf/phymars/comsoil_h.F90

    r3109 r3113  
    2020  real,save,allocatable :: mthermdiff(:,:,:)  ! (FC) mid-layer thermal diffusivity
    2121  real,save,allocatable :: thermdiff(:,:,:)   ! (FC) inter-layer thermal diffusivity
    22   real,save,allocatable :: coefq(:)         ! (FC) q_{k+1/2} coefficients
     22  real,save,allocatable :: coefq(:)           ! (FC) q_{k+1/2} coefficients
    2323  real,save,allocatable :: coefd(:,:,:)       ! (FC) d_k coefficients
    2424  real,save,allocatable :: alph(:,:,:)        ! (FC) alpha_k coefficients
    2525  real,save,allocatable :: beta(:,:,:)        ! beta_k coefficients
    2626  real,save :: mu
    27   real,save,allocatable :: flux_geo(:,:)       ! Geothermal Flux (W/m^2)
     27  real,save,allocatable :: flux_geo(:,:)      ! Geothermal Flux (W/m^2)
    2828
    2929!$OMP THREADPRIVATE(tsoil,mthermdiff,thermdiff,coefq,coefd,alph,beta,mu,flux_geo)
     30
     31
     32! Subsurface tracers:
     33  logical,save :: adsorption_soil             ! boolean to call adosrption (or not)
     34  integer, parameter :: nqsoil = 3            ! number of subsurface tracers, only three when working with water
     35  real,save,allocatable :: qsoil(:,:,:,:)     ! subsurface tracers (kg/m^3 of regol)
     36  integer, parameter :: igcm_h2o_vap_soil = 1
     37  integer, parameter :: igcm_h2o_ice_soil = 2
     38  integer, parameter :: igcm_h2o_vap_ads  = 3
     39!$OMP THREADPRIVATE(adsorption_soil,qsoil)
     40
    3041
    3142contains
     
    4859    allocate(beta(ngrid,nsoilmx-1,nslope))
    4960    allocate(flux_geo(ngrid,nslope))
     61    allocate(qsoil(ngrid,nsoilmx,nqsoil,nslope))
    5062 
    5163  end subroutine ini_comsoil_h
     
    6880    if (allocated(beta)) deallocate(beta)
    6981    if (allocated(flux_geo)) deallocate(flux_geo)
     82    if (allocated(qsoil))  deallocate(qsoil)
    7083  end subroutine end_comsoil_h
    7184
     
    8497    allocate(beta(ngrid,nsoilmx-1,nslope))
    8598    allocate(flux_geo(ngrid,nslope))
     99    allocate(qsoil(ngrid,nsoilmx,nqsoil,nslope))
    86100 
    87101  end subroutine ini_comsoil_h_slope_var
     
    100114    if (allocated(beta)) deallocate(beta)
    101115    if (allocated(flux_geo)) deallocate(flux_geo)
     116    if (allocated(qsoil))  deallocate(qsoil)
    102117
    103118  end subroutine end_comsoil_h_slope_var
  • trunk/LMDZ.MARS/libf/phymars/conf_phys.F

    r3111 r3113  
    4040     &                           lag_layer
    4141      use microphys_h, only: mteta
     42      use comsoil_h, only: adsorption_soil
    4243
    4344      IMPLICIT NONE
     
    10001001c        ----------------------------------------------------------
    10011002
     1003! Adsorption
     1004         adsorption_soil = .false.
     1005         call getin_p("adsorption_soil",adsorption_soil)
     1006         if (adsorption_soil .and. (.not. water)) then
     1007              write(*,*)"Adsorption can be run only if water = True"
     1008              call abort_physic(modname,
     1009     &        "Adsorption must be used with water = true",1)
     1010         endif 
     1011c        ----------------------------------------------------------
     1012
    10021013! THERMOSPHERE
    10031014
  • trunk/LMDZ.MARS/libf/phymars/dyn1d/init_testphys1d_mod.F90

    r3109 r3113  
    2020use iostart,                  only: open_startphy, get_var, close_startphy
    2121use physics_distribution_mod, only: init_physics_distribution
    22 use comsoil_h,                only: volcapa, nsoilmx, inertiesoil, inertiedat, layer, mlayer, flux_geo, tsoil
     22use comsoil_h,                only: volcapa, nsoilmx, inertiesoil, inertiedat, layer, mlayer, flux_geo, tsoil, qsoil
    2323use comvert_mod,              only: ap, bp, aps, bps, pa, preff, presnivs, pseudoalt, scaleheight
    2424use dimradmars_mod,           only: tauvis, totcloudfrac, albedo
     
    661661flux_geo(:,:) = flux_geo_tmp
    662662
     663! Initialize soil content
     664! -----------------
     665if (.not. startfiles_1D) then
     666    qsoil(:,:,:,:) = 0.
     667endif
     668
    663669! Initialize depths
    664670! -----------------
  • trunk/LMDZ.MARS/libf/phymars/dyn1d/testphys1d.F90

    r3098 r3113  
    11PROGRAM testphys1d
    22
    3 use comsoil_h,           only: inertiedat, inertiesoil, nsoilmx, tsoil
     3use comsoil_h,           only: inertiedat, inertiesoil, nsoilmx, tsoil, nqsoil, qsoil
    44use surfdat_h,           only: albedodat, perenial_co2ice, watercap, tsurf, emis, qsurf
    55use comslope_mod,        only: def_slope, subslope_dist
     
    127127                  llm,nq,dttestphys,float(day0),0.,cell_area,    &
    128128                  albedodat,inertiedat,def_slope,subslope_dist)
    129     call physdem1("startfi.nc",nsoilmx,ngrid,llm,nq,dttestphys,time,       &
    130                   tsurf,tsoil,inertiesoil,albedo,emis,q2,qsurf,tauscaling, &
     129    call physdem1("startfi.nc",nsoilmx,ngrid,llm,nq,nqsoil,dttestphys,time,       &
     130                  tsurf,tsoil,inertiesoil,albedo,emis,q2,qsurf,qsoil,tauscaling, &
    131131                  totcloudfrac,wstar,watercap,perenial_co2ice)
    132132endif !(.not. therestartfi)
  • trunk/LMDZ.MARS/libf/phymars/phyetat0_mod.F90

    r3098 r3113  
    88contains
    99
    10 subroutine phyetat0 (fichnom,tab0,Lmodif,nsoil,ngrid,nlay,nq, &
    11                      day_ini,time0,tsurf,tsoil,albedo,emis,q2,qsurf, &
     10subroutine phyetat0 (fichnom,tab0,Lmodif,nsoil,ngrid,nlay,nq,nqsoil, &
     11                     day_ini,time0,tsurf,tsoil,albedo,emis,q2,qsurf,qsoil, &
    1212                     tauscaling,totcloudfrac,wstar,watercap,perenial_co2ice, &
    1313                     def_slope,def_slope_mean,subslope_dist)
     
    5959  integer,intent(in) :: nlay ! # of atmospheric layers
    6060  integer,intent(in) :: nq
     61  integer,intent(in) :: nqsoil ! # of tracers in the soil
    6162  integer :: day_ini
    6263  real :: time0
     
    6970  real,intent(out) :: q2(ngrid,nlay+1) !
    7071  real,intent(out) :: qsurf(ngrid,nq,nslope) ! tracers on surface
     72  real,intent(out) :: qsoil(ngrid,nsoil,nqsoil,nslope) ! tracers in the subsurface
    7173  real,intent(out) :: tauscaling(ngrid) ! dust conversion factor
    7274  real,intent(out) :: totcloudfrac(ngrid) ! total cloud fraction
     
    714716  ! Call to soil_settings, in order to read soil temperatures,
    715717  ! as well as thermal inertia and volumetric heat capacity
    716   call soil_settings(nid_start,ngrid,nsoil,tsurf,tsoil,indextime)
     718  call soil_settings(nid_start,ngrid,nsoil,nqsoil,tsurf,tsoil,qsoil,indextime)
    717719else
    718720    flux_geo(:,:) = 0.
  • trunk/LMDZ.MARS/libf/phymars/phyredem.F90

    r3098 r3113  
    164164end subroutine physdem0
    165165
    166 subroutine physdem1(filename,nsoil,ngrid,nlay,nq, &
     166subroutine physdem1(filename,nsoil,ngrid,nlay,nq,nqsoil, &
    167167                    phystep,time,tsurf,tsoil,inertiesoil, &
    168                     albedo,emis,q2,qsurf,&
     168                    albedo,emis,q2,qsurf,qsoil,&
    169169                    tauscaling,totcloudfrac,wstar, &
    170170                    watercap,perenial_co2ice)
     
    177177  use dust_rad_adjust_mod, only: dust_rad_adjust_prev,dust_rad_adjust_next
    178178  use dust_param_mod, only: dustscaling_mode
    179   use comsoil_h,only: flux_geo
     179  use comsoil_h,only: flux_geo,adsorption_soil,igcm_h2o_vap_soil, &
     180                      igcm_h2o_ice_soil,igcm_h2o_vap_ads
    180181  use comslope_mod, only: nslope
    181182  use paleoclimate_mod, only: paleoclimate
     
    189190  integer,intent(in) :: nlay
    190191  integer,intent(in) :: nq
     192  integer,intent(in) :: nqsoil
    191193  real,intent(in) :: phystep
    192194  real,intent(in) :: time
     
    198200  real,intent(in) :: q2(ngrid,nlay+1)
    199201  real,intent(in) :: qsurf(ngrid,nq,nslope)
     202  real,intent(in) :: qsoil(ngrid,nsoil,nqsoil,nslope)
    200203  real,intent(in) :: tauscaling(ngrid)
    201204  real,intent(in) :: totcloudfrac(ngrid)
     
    339342  endif
    340343
    341 
    342344  ! Geothermal Flux
    343345     call put_field('flux_geo','Geothermal flux',flux_geo,time)
     346
     347  ! Adsorption
     348  if (adsorption_soil) then
     349     call put_field("h2o_vap_soil","subsurface water vapour", &
     350                        qsoil(:,:,igcm_h2o_vap_soil,:), time)
     351     call put_field("h2o_ice_soil","subsurface water ice", &
     352                        qsoil(:,:,igcm_h2o_ice_soil,:), time)
     353     call put_field("h2o_vap_ads", "adsorbed water", &
     354                        qsoil(:,:,igcm_h2o_vap_ads,:), time)
     355  endif
     356
    344357  ! Close file
    345358  call close_restartphy
  • trunk/LMDZ.MARS/libf/phymars/physiq_mod.F

    r3106 r3113  
    4848      use comsoil_h, only: inertiedat, inertiesoil,! dat: soil thermal inertia for present climate, inertiesoil is the TI read in the start
    4949     &                     tsoil, nsoilmx,!number of subsurface layers
    50      &                     mlayer,layer ! soil mid layer depths
     50     &                     mlayer,layer, ! soil mid layer depths
     51     &                     nqsoil,qsoil  ! adsorption
    5152      use geometry_mod, only: longitude, latitude, cell_area,
    5253     &                        cell_area_for_lonlat_outputs,longitude_deg
     
    599600! GCM. Read netcdf initial physical parameters.
    600601         CALL phyetat0 ("startfi.nc",0,0,
    601      &         nsoilmx,ngrid,nlayer,nq,
     602     &         nsoilmx,ngrid,nlayer,nq,nqsoil,
    602603     &         day_ini,time_phys,
    603604     &         tsurf,tsoil,albedo,emis,
    604      &         q2,qsurf,tauscaling,totcloudfrac,wstar,
     605     &         q2,qsurf,qsoil,tauscaling,totcloudfrac,wstar,
    605606     &         watercap,perenial_co2ice,
    606607     &         def_slope,def_slope_mean,subslope_dist)
     
    26212622     .          icount,' date=',ztime_fin
    26222623           
    2623           call physdem1("restartfi.nc",nsoilmx,ngrid,nlayer,nq,
     2624          call physdem1("restartfi.nc",nsoilmx,ngrid,nlayer,nq,nqsoil,
    26242625     .                ptimestep,ztime_fin,
    26252626     .                tsurf,tsoil,inertiesoil,albedo,
    2626      .                emis,q2,qsurf,tauscaling,totcloudfrac,wstar,
    2627      .                watercap,perenial_co2ice)
     2627     .                emis,q2,qsurf,qsoil,tauscaling,totcloudfrac,
     2628     .                wstar,watercap,perenial_co2ice)
    26282629          ENDIF ! of IF (write_restart)
    26292630
  • trunk/LMDZ.MARS/libf/phymars/soil_settings.F

    r3110 r3113  
    1       subroutine soil_settings(nid,ngrid,nsoil,tsurf,tsoil,indextime)
     1      subroutine soil_settings(nid,ngrid,nsoil,nqsoil,tsurf,tsoil,
     2     &                         qsoil,indextime)
    23
    34!      use netcdf
    45      use comsoil_h, only: layer, mlayer, inertiedat, inertiesoil,
    5      &                     volcapa,flux_geo
     6     &                     volcapa,flux_geo,adsorption_soil,
     7     &                     igcm_h2o_vap_soil,igcm_h2o_ice_soil,
     8     &                     igcm_h2o_vap_ads
    69      use iostart, only: inquire_field_ndims, get_var, get_field,
    710     &                   inquire_field, inquire_dimension_length
     
    4346      integer,intent(in) :: ngrid       ! # of horizontal grid points
    4447      integer,intent(in) :: nsoil       ! # of soil layers
    45       real,intent(in) :: tsurf(ngrid,nslope)   ! surface temperature
     48      integer,intent(in) :: nqsoil      ! # of tracers in the soil
     49      real,intent(in) :: tsurf(ngrid,nslope)   ! surface temperature [K]
    4650      integer,intent(in) :: indextime   ! position on time axis
    4751!  output:
    48       real,intent(out) :: tsoil(ngrid,nsoil,nslope)     ! soil temperature
     52      real,intent(out) :: tsoil(ngrid,nsoil,nslope)     ! soil temperature [K]
     53      real,intent(out) :: qsoil(ngrid,nsoil,nqsoil,nslope) ! Tracers in the subsurface [kg/kg]
    4954
    5055!======================================================================
     
    8186
    8287      logical :: found,ok
     88
     89      character (len=30):: txt
    8390     
    8491!======================================================================
     
    158165        layer(iloop)=lay1*(alpha**(iloop-1))
    159166      enddo
    160 
    161167
    162168
     
    439445
    440446
     447! 7. Adsorption
     448! ----------------------------------------------------------------------
     449
     450
     451      if (adsorption_soil) then
     452! Subsurface water vapor
     453             txt="h2o_vap_soil"
     454             write(*,*) 'phyetat0: loading subsurface tracer',
     455     &                               ' h2o_vap_soil'
     456             call get_field(txt,qsoil(:,:,igcm_h2o_vap_soil,:),found,
     457     &                                                 indextime)
     458             write(*,*) 'found',found
     459             write(*,*) 'igcm_',igcm_h2o_vap_soil
     460             write(*,*) 'q=',qsoil(:,:,:,:)
     461             if (.not.found) then
     462               write(*,*) "phyetat0: Failed loading <",trim(txt),">"
     463               write(*,*) "         ",trim(txt)," is set to zero"
     464               qsoil(:,:,igcm_h2o_vap_soil,:)= 0.
     465             else
     466               write(*,*) "phyetat0: suburface tracer <",trim(txt),
     467     &              "> range:", minval(qsoil(:,:,igcm_h2o_vap_soil,:)),
     468     &                          maxval(qsoil(:,:,igcm_h2o_vap_soil,:))
     469             endif
     470! Subsurface ice
     471               txt="h2o_ice_soil"
     472               write(*,*) 'phyetat0: loading subsurface tracer',
     473     &                                ' h2o_ice_soil'
     474             call get_field(txt,qsoil(:,:,igcm_h2o_ice_soil,:),found,
     475     &                                                  indextime)
     476             if (.not.found) then
     477               write(*,*) "phyetat0: Failed loading <",trim(txt),">"
     478               write(*,*) "         ",trim(txt)," is set to zero"
     479               qsoil(:,:,igcm_h2o_ice_soil,:)= 0.
     480             else
     481               write(*,*) "phyetat0: suburface tracer <",trim(txt),
     482     &                     "> range:",
     483     &                     minval(qsoil(:,:,igcm_h2o_ice_soil,:)),
     484     &                     maxval(qsoil(:,:,igcm_h2o_ice_soil,:))
     485             endif
     486! Adsorbed water
     487             txt="h2o_vap_ads"
     488               write(*,*) 'phyetat0: loading subsurface tracer',
     489     &                                ' h2o_vap_ads'
     490             call get_field(txt,qsoil(:,:,igcm_h2o_vap_ads,:),found,
     491     &                                                indextime)
     492             if (.not.found) then
     493               write(*,*) "phyetat0: Failed loading <",trim(txt),">"
     494               write(*,*) "         ",trim(txt)," is set to zero"
     495               qsoil(:,:,igcm_h2o_vap_ads,:)= 0.
     496             else
     497               write(*,*) "phyetat0: suburface tracer <",trim(txt),">
     498     &                     range:",
     499     &                     minval(qsoil(:,:,igcm_h2o_vap_ads,:)),
     500     &                     maxval(qsoil(:,:,igcm_h2o_vap_ads,:))
     501             endif
     502
     503      endif ! of adsorption_soil
     504
     505
    441506     
    442 ! 7. Report min and max values of soil temperatures and thermal inertias
     507! 8. Report min and max values of soil temperatures and thermal inertias
    443508! ----------------------------------------------------------------------
    444509
Note: See TracChangeset for help on using the changeset viewer.