Ignore:
Timestamp:
May 22, 2024, 1:38:28 PM (6 months ago)
Author:
jbclement
Message:

PEM:
Correction of the way sublimating ice is identified at the beginning of the PEM + some updates for the default variables and the display of information.
JBC

Location:
trunk/LMDZ.COMMON/libf/evolution
Files:
6 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.COMMON/libf/evolution/changelog.txt

    r3331 r3339  
    318318== 16/05/2024 == JBC
    319319Update of the layering algorithm + corrections of wrong lines commited in r3330.
     320
     321== 22/05/2024 == JBC
     322Correction of the way sublimating ice is identified at the beginning of the PEM + some updates for the default variables and the display of information.
  • trunk/LMDZ.COMMON/libf/evolution/conf_pem.F90

    r3319 r3339  
    9797call getin('soil_pem',soil_pem)
    9898
    99 adsorption_pem = .true.
     99adsorption_pem = .false.
    100100call getin('adsorption_pem',adsorption_pem)
    101101
  • trunk/LMDZ.COMMON/libf/evolution/deftank/run_PEM.def

    r3327 r3339  
    6262
    6363# Is the ice table computed at equilibrium? Default = .true.
    64 # icetable_equilibrium=.true.
     64# icetable_equilibrium=.false.
    6565
    6666# Is the ice table computed with the dynamic method? Default = .false.
  • trunk/LMDZ.COMMON/libf/evolution/pem.F90

    r3331 r3339  
    193193
    194194! Variables for slopes
    195 real, dimension(:,:,:), allocatable :: co2_ice_PCM        ! Physics x NSLOPE x Times field: co2 ice given by the PCM [kg/m^2]
     195real, dimension(:,:,:), allocatable :: co2_ice_PCM        ! Physics x slope x Times field: co2 ice given by the PCM [kg/m^2]
    196196real, dimension(:,:),   allocatable :: tend_co2_ice       ! physical point x slope field: Tendency of evolution of perennial co2 ice over a year
    197 real, dimension(:,:),   allocatable :: tend_co2_ice_ini   ! physical point x slope field x nslope: Tendency of evolution of perennial co2 ice over a year in the PCM
    198 real, dimension(:,:),   allocatable :: tend_h2o_ice       ! physical point x slope  field: Tendency of evolution of perennial h2o ice
     197real, dimension(:,:),   allocatable :: tend_co2_ice_ini   ! physical point x slope field: Tendency of evolution of perennial co2 ice over a year in the PCM
     198real, dimension(:,:),   allocatable :: tend_h2o_ice       ! physical point x slope field: Tendency of evolution of perennial h2o ice
    199199real, dimension(:,:),   allocatable :: flag_co2flow       ! (ngrid,nslope): Flag where there is a CO2 glacier flow
    200200real, dimension(:),     allocatable :: flag_co2flow_mesh  ! (ngrid)       : Flag where there is a CO2 glacier flow
     
    206206real, dimension(:,:,:),   allocatable :: tsoil_ave                          ! Physic x SOIL x SLOPE field: Averaged Soil Temperature [K]
    207207real, dimension(:,:,:),   allocatable :: tsoil_anom                         ! Amplitude between instataneous and yearly average soil temperature [K]
    208 real, dimension(:,:,:),   allocatable :: tsurf_PCM_timeseries               ! ngrid x SLOPE XTULES field: Surface Temperature in timeseries [K]
    209 real, dimension(:,:,:,:), allocatable :: tsoil_phys_PEM_timeseries          ! IG x SLOPE XTULES field: Non averaged Soil Temperature [K]
    210 real, dimension(:,:,:,:), allocatable :: tsoil_PCM_timeseries               ! IG x SLOPE XTULES field: Non averaged Soil Temperature [K]
     208real, dimension(:,:,:),   allocatable :: tsurf_PCM_timeseries               ! ngrid x SLOPE x TIMES field: Surface Temperature in timeseries [K]
     209real, dimension(:,:,:,:), allocatable :: tsoil_phys_PEM_timeseries          ! IG x SLOPE x TIMES field: Non averaged Soil Temperature [K]
     210real, dimension(:,:,:,:), allocatable :: tsoil_PCM_timeseries               ! IG x SLOPE x TIMES field: Non averaged Soil Temperature [K]
    211211real, dimension(:,:),     allocatable :: tsurf_avg_yr1                      ! Physic x SLOPE field: Averaged Surface Temperature of first call of the PCM [K]
    212212real, dimension(:,:),     allocatable :: TI_locslope                        ! Physic x Soil: Intermediate thermal inertia  to compute Tsoil [SI]
    213 real, dimension(:,:),     allocatable :: Tsoil_locslope                     ! Physic x Soil: intermediate when computing Tsoil [K]
     213real, dimension(:,:),     allocatable :: Tsoil_locslope                     ! Physic x Soil: Intermediate when computing Tsoil [K]
    214214real, dimension(:),       allocatable :: Tsurf_locslope                     ! Physic x Soil: Intermediate surface temperature to compute Tsoil [K]
    215215real, dimension(:,:,:,:), allocatable :: watersoil_density_timeseries       ! Physic x Soil x Slope x Times water soil density, time series [kg /m^3]
    216216real, dimension(:,:),     allocatable :: watersurf_density_ave              ! Physic x Slope, water surface density, yearly averaged [kg/m^3]
    217217real, dimension(:,:,:,:), allocatable :: watersoil_density_PEM_timeseries   ! Physic x Soil x Slope x Times, water soil density, time series [kg/m^3]
    218 real, dimension(:,:,:),   allocatable :: watersoil_density_PEM_ave          ! Physic x Soil x SLopes, water soil density, yearly averaged [kg/m^3]
     218real, dimension(:,:,:),   allocatable :: watersoil_density_PEM_ave          ! Physic x Soil x Slopes, water soil density, yearly averaged [kg/m^3]
    219219real, dimension(:,:),     allocatable :: Tsurfavg_before_saved              ! Surface temperature saved from previous time step [K]
    220220real, dimension(:),       allocatable :: delta_co2_adsorbded                ! Physics: quantity of CO2 that is exchanged because of adsorption / desorption [kg/m^2]
     
    621621    do islope = 1,nslope
    622622        if (co2_ice(i,islope) > 0.) is_co2ice_ini(i,islope) = .true.
    623         if (tend_co2_ice(i,islope) < 0.) then
     623        if (tend_co2_ice(i,islope) < 0. .and. co2_ice(i,islope) > 0.) then
    624624            ini_co2ice_sublim(i,islope) = .true.
    625625            co2ice_ini_surf = co2ice_ini_surf + cell_area(i)*subslope_dist(i,islope)
    626626        endif
    627         if (tend_h2o_ice(i,islope) < 0.) then
     627        if (tend_h2o_ice(i,islope) < 0. .and. h2o_ice(i,islope) > 0.) then
    628628            ini_h2oice_sublim(i,islope) = .true.
    629629            h2oice_ini_surf = h2oice_ini_surf + cell_area(i)*subslope_dist(i,islope)
     
    683683endif
    684684
    685 do while (year_iter < 10 .and. i_myear < n_myear)
     685do while (year_iter < year_iter_max .and. i_myear < n_myear)
    686686! II.a.1. Compute updated global pressure
    687687    write(*,*) "Recomputing the new pressure..."
     
    933933        call writediagpem(ngrid,'Flow_co2ice_slope'//str2,'CO2 ice flow','Boolean',2,flag_co2flow(:,islope))
    934934        call writediagpem(ngrid,'tsurf_slope'//str2,'tsurf','K',2,tsurf(:,islope))
    935         if(icetable_equilibrium) then
     935        if (icetable_equilibrium) then
    936936            call writediagpem(ngrid,'ssi_depth_slope'//str2,'ice table depth','m',2,porefillingice_depth(:,islope))
    937937            call writediagpem(ngrid,'ssi_thick_slope'//str2,'ice table depth','m',2,porefillingice_thickness(:,islope))
    938938        endif
    939         if(soil_pem) then
     939        if (soil_pem) then
    940940            call writediagsoilpem(ngrid,'tsoil_PEM_slope'//str2,'tsoil_PEM','K',3,tsoil_PEM(:,:,islope))
    941941            call writediagsoilpem(ngrid,'inertiesoil_PEM_slope'//str2,'TI_PEM','K',3,TI_PEM(:,:,islope))
  • trunk/LMDZ.COMMON/libf/evolution/stopping_crit_mod.F90

    r3327 r3339  
    5555    write(*,*) "Reason of stopping: the surface of h2o ice sublimating reaches the threshold"
    5656    write(*,*) "h2oice_now_surf < h2oice_ini_surf*(1. - h2o_ice_crit)", h2oice_now_surf < h2oice_ini_surf*(1. - h2o_ice_crit)
     57    write(*,*) "Initial surface of h2o ice sublimating =", h2oice_ini_surf
    5758    write(*,*) "Current surface of h2o ice sublimating =", h2oice_now_surf
    58     write(*,*) "Initial surface of h2o ice sublimating =", h2oice_ini_surf
    5959    write(*,*) "Percentage of change accepted =", h2o_ice_crit*100
    6060else if (h2oice_now_surf > h2oice_ini_surf*(1. + h2o_ice_crit)) then
     
    6262    write(*,*) "Reason of stopping: the surface of h2o ice sublimating reaches the threshold"
    6363    write(*,*) "h2oice_now_surf > h2oice_ini_surf*(1. + h2o_ice_crit)", h2oice_now_surf > h2oice_ini_surf*(1. + h2o_ice_crit)
     64    write(*,*) "Initial surface of h2o ice sublimating =", h2oice_ini_surf
    6465    write(*,*) "Current surface of h2o ice sublimating =", h2oice_now_surf
    65     write(*,*) "Initial surface of h2o ice sublimating =", h2oice_ini_surf
    6666    write(*,*) "Percentage of change accepted =", h2o_ice_crit*100
    6767endif
     
    117117    write(*,*) "Reason of stopping: the surface of co2 ice sublimating reaches the threshold"
    118118    write(*,*) "co2ice_now_surf < co2ice_ini_surf*(1. - co2_ice_crit)", co2ice_now_surf < co2ice_ini_surf*(1. - co2_ice_crit)
     119    write(*,*) "Initial surface of co2 ice sublimating =", co2ice_ini_surf
    119120    write(*,*) "Current surface of co2 ice sublimating =", co2ice_now_surf
    120     write(*,*) "Initial surface of co2 ice sublimating =", co2ice_ini_surf
    121121    write(*,*) "Percentage of change accepted =", co2_ice_crit*100.
    122122else if (co2ice_now_surf > co2ice_ini_surf*(1. + co2_ice_crit)) then
     
    135135    write(*,*) "Reason of stopping: the global pressure reaches the threshold"
    136136    write(*,*) "global_avg_press_new < global_avg_press_PCM*(1. - ps_criterion)", global_avg_press_new < global_avg_press_PCM*(1. - ps_criterion)
     137    write(*,*) "Initial global pressure =", global_avg_press_PCM
    137138    write(*,*) "Current global pressure =", global_avg_press_new
    138     write(*,*) "PCM global pressure =", global_avg_press_PCM
    139139    write(*,*) "Percentage of change accepted =", ps_criterion*100.
    140140else if (global_avg_press_new > global_avg_press_PCM*(1. + ps_criterion)) then
     
    142142    write(*,*) "Reason of stopping: the global pressure reaches the threshold"
    143143    write(*,*) "global_avg_press_new > global_avg_press_PCM*(1. + ps_criterion)", global_avg_press_new > global_avg_press_PCM*(1. + ps_criterion)
     144    write(*,*) "Initial global pressure =", global_avg_press_PCM
    144145    write(*,*) "Current global pressure =", global_avg_press_new
    145     write(*,*) "PCM global pressure =", global_avg_press_PCM
    146146    write(*,*) "Percentage of change accepted =", ps_criterion*100.
    147147endif
  • trunk/LMDZ.COMMON/libf/evolution/writediagpem.F90

    r3214 r3339  
    584584SUBROUTINE writediagsoilpem(ngrid,name,title,units,dimpx,px)
    585585
    586 ! Write variable 'name' to NetCDF file 'diagsoil.nc'.
     586! Write variable 'name' to NetCDF file 'diagsoilpem.nc'.
    587587! The variable may be 3D (lon,lat,depth) subterranean field,
    588588! a 2D (lon,lat) surface field, or a simple scalar (0D variable).
     
    656656#endif
    657657
    658 ! 0. Do we ouput a diagsoil.nc file? If not just bail out now.
    659 
    660 ! additional check: one can only output diagsoil.nc files
     658! 0. Do we ouput a diagsoilpem.nc file? If not just bail out now.
     659
     660! additional check: one can only output diagsoilpem.nc files
    661661! in lon-lat case (or 1D)
    662662if (grid_type==unstructured) then
    663   write(*,*) "writediagsoil: Error !!!"
    664   write(*,*) "diagsoil.nc outputs not possible on unstructured grids!!"
    665   call abort_physic("writediagsoil","impossible on unstructured grid",1)
     663  write(*,*) "writediagsoilpem: Error !!!"
     664  write(*,*) "diagsoilpem.nc outputs not possible on unstructured grids!!"
     665  call abort_physic("writediagsoilpem","impossible on unstructured grid",1)
    666666endif
    667667
     
    674674  ! just to be sure, check that firstnom is large enough to hold nom
    675675  if (len_trim(firstname).lt.len_trim(name)) then
    676     write(*,*) "writediagsoil: Error !!!"
     676    write(*,*) "writediagsoilpem: Error !!!"
    677677    write(*,*) "   firstname string not long enough!!"
    678678    write(*,*) "   increase its size to at least ",len_trim(name)
    679     call abort_physic("writediagsoil","firstname too short",1)
     679    call abort_physic("writediagsoilpem","firstname too short",1)
    680680  endif
    681681 
     
    687687   ierr=NF_CREATE(filename,NF_CLOBBER,nid)
    688688   if (ierr.ne.NF_NOERR) then
    689     write(*,*)'writediagsoil: Error, failed creating file '//trim(filename)
    690     call abort_physic("writediagsoil","failed creating"//trim(filename),1)
     689    write(*,*)'writediagsoilpem: Error, failed creating file '//trim(filename)
     690    call abort_physic("writediagsoilpem","failed creating"//trim(filename),1)
    691691   endif
    692692  endif
     
    767767!#endif
    768768     if (ierr.ne.NF_NOERR) then
    769       write(*,*)"writediagsoil: Failed writing date to time variable"
    770       call abort_physic("writediagsoil","failed writing time",1)
     769      write(*,*)"writediagsoilpem: Failed writing date to time variable"
     770      call abort_physic("writediagsoilpem","failed writing time",1)
    771771     endif
    772772    endif ! of if (is_master)
     
    824824    ! Tell the world about it
    825825    write(*,*) "====================="
    826     write(*,*) "writediagsoil: creating variable "//trim(name)
     826    write(*,*) "writediagsoilpem: creating variable "//trim(name)
    827827    call def_var(nid,name,title,units,4,id,varid,ierr)
    828828  endif ! of if (ierr.ne.NF_NOERR)
     
    854854!#endif
    855855  if (ierr.ne.NF_NOERR) then
    856     write(*,*) "writediagsoil: Error: Failed writing "//trim(name)//&
     856    write(*,*) "writediagsoilpem: Error: Failed writing "//trim(name)//&
    857857               " to file "//trim(filename)//" at time",date
    858858  endif
     
    908908    ! Tell the world about it
    909909    write(*,*) "====================="
    910     write(*,*) "writediagsoil: creating variable "//trim(name)
     910    write(*,*) "writediagsoilpem: creating variable "//trim(name)
    911911    call def_var(nid,name,title,units,3,id,varid,ierr)
    912912  endif ! of if (ierr.ne.NF_NOERR)
     
    936936!#endif
    937937  if (ierr.ne.NF_NOERR) then
    938     write(*,*) "writediagsoil: Error: Failed writing "//trim(name)//&
     938    write(*,*) "writediagsoilpem: Error: Failed writing "//trim(name)//&
    939939               " to file "//trim(filename)//" at time",date
    940940  endif
     
    943943elseif (dimpx.eq.0) then ! Case of a 0D variable
    944944#ifdef CPP_PARA
    945   write(*,*) "writediagsoil: dimps==0 case not implemented in // mode!!"
    946   call abort_physic("writediagsoil","dimps==0 not implemented",1)
     945  write(*,*) "writediagsoilpem: dimps==0 case not implemented in // mode!!"
     946  call abort_physic("writediagsoilpem","dimps==0 not implemented",1)
    947947#endif
    948948  ! A. Copy data value
     
    959959    ! Tell the world about it
    960960    write(*,*) "====================="
    961     write(*,*) "writediagsoil: creating variable "//trim(name)
     961    write(*,*) "writediagsoilpem: creating variable "//trim(name)
    962962    call def_var(nid,name,title,units,1,id,varid,ierr)
    963963  endif ! of if (ierr.ne.NF_NOERR)
     
    975975!#endif
    976976  if (ierr.ne.NF_NOERR) then
    977     write(*,*) "writediagsoil: Error: Failed writing "//trim(name)//&
     977    write(*,*) "writediagsoilpem: Error: Failed writing "//trim(name)//&
    978978               " to file "//trim(filename)//" at time",date
    979979  endif
Note: See TracChangeset for help on using the changeset viewer.