Changeset 3967


Ignore:
Timestamp:
Nov 20, 2025, 3:01:08 PM (4 weeks ago)
Author:
jbclement
Message:

PEM:
New management of stopping criteria: giving explicit names and collecting everything in the same place.
JBC

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

Legend:

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

    r3961 r3967  
    794794== 14/11/2025 == JBC
    795795Clearing all the tags and code related to the Generic PCM.
     796
     797== 20/11/2025 == JBC
     798New management of stopping criteria: giving explicit names and collecting everything in the same place.
  • trunk/LMDZ.COMMON/libf/evolution/evol_ice_mod.F90

    r3938 r3967  
    4949!=======================================================================
    5050
    51 SUBROUTINE evol_h2o_ice(ngrid,nslope,cell_area,delta_h2o_adsorbed,delta_h2o_icetablesublim,h2o_ice,d_h2oice,zshift_surf,stopPEM)
     51SUBROUTINE evol_h2o_ice(ngrid,nslope,cell_area,delta_h2o_adsorbed,delta_h2o_icetablesublim,h2o_ice,d_h2oice,zshift_surf,stopCrit)
    5252
    5353use time_evol_mod,     only: dt
    5454use glaciers_mod,      only: rho_h2oice
    55 use stopping_crit_mod, only: stopping_crit_h2o
     55use stopping_crit_mod, only: stopping_crit_h2o, stopFlags
    5656
    5757implicit none
     
    7373real, dimension(ngrid,nslope), intent(inout) :: h2o_ice  ! H2O ice (kg/m^2)
    7474real, dimension(ngrid,nslope), intent(inout) :: d_h2oice ! Tendency of H2O ice (kg/m^2/year)
    75 integer,                       intent(inout) :: stopPEM  ! Stopping criterion code
     75type(stopFlags),               intent(inout) :: stopCrit ! Stopping criterion
    7676real, dimension(ngrid,nslope), intent(out) :: zshift_surf ! Elevation shift for the surface [m]
    7777
     
    8888    zshift_surf = d_h2oice*dt/rho_h2oice
    8989else ! In 3D
    90     call stopping_crit_h2o(ngrid,nslope,cell_area,delta_h2o_adsorbed,delta_h2o_icetablesublim,h2o_ice,d_h2oice,S_atm_2_h2o,S_h2o_2_atm,S_atm_2_h2oice,S_h2oice_2_atm,stopPEM)
    91     if (stopPEM > 0) return
     90    call stopping_crit_h2o(ngrid,nslope,cell_area,delta_h2o_adsorbed,delta_h2o_icetablesublim,h2o_ice,d_h2oice,S_atm_2_h2o,S_h2o_2_atm,S_atm_2_h2oice,S_h2oice_2_atm,stopCrit)
     91    if (stopCrit%stop_code() > 0) return
    9292
    9393    call balance_h2oice_reservoirs(ngrid,nslope,S_atm_2_h2o,S_h2o_2_atm,S_atm_2_h2oice,S_h2oice_2_atm,h2o_ice,d_h2oice,d_h2oice_new)
  • trunk/LMDZ.COMMON/libf/evolution/pem.F90

    r3961 r3967  
    4141use glaciers_mod,               only: flow_co2glaciers, flow_h2oglaciers, co2ice_flow, h2oice_flow, inf_h2oice_threshold, &
    4242                                      metam_h2oice_threshold, metam_co2ice_threshold, metam_h2oice, metam_co2ice, computeTcondCO2
    43 use stopping_crit_mod,          only: stopping_crit_h2o_ice, stopping_crit_co2, stopping_crit_h2o
     43use stopping_crit_mod,          only: stopping_crit_h2o_ice, stopping_crit_co2, stopping_crit_h2o, stopFlags
    4444use constants_marspem_mod,      only: alpha_clap_co2, beta_clap_co2, alpha_clap_h2o, beta_clap_h2o, m_co2, m_noco2
    4545use evol_ice_mod,               only: evol_co2_ice, evol_h2o_ice, balance_h2oice_reservoirs
     
    167167real,   dimension(:,:,:), allocatable :: zplev_timeseries_new ! Grid points x Atmospheric x Time: same as zplev_new, but in times series [kg/m ^2]
    168168real,   dimension(:,:,:), allocatable :: zplev_timeseries_old ! same but with the time series, for previous time step
    169 integer                               :: stopPEM              ! which criterion is reached? 0 = no stopping; 1 = h2o ice surf; 2 = no h2o ice; 3 = co2 ice surf; 4 = ps; 5 = orb param; 6 = end of simu
     169type(stopFlags)                       :: stopCrit             ! Stopping criteria
    170170real                                  :: A, B, mmean          ! Molar mass: intermediate A, B for computations of the  mean molar mass of the layer [mol/kg]
    171171real,   dimension(:,:),   allocatable :: q_h2o_PEM_phys       ! Grid points x Times: h2o mass mixing ratio computed in the PEM, first value comes from PCM [kg/kg]
     
    612612write(*,*) '********* PEM cycle *********'
    613613i_myear_leg = 0
    614 stopPEM = 0
    615614if (layering_algo) then
    616615    allocate(h2o_ice_depth_old(ngrid,nslope),new_str(ngrid,nslope),new_lag(ngrid,nslope),current(ngrid,nslope))
     
    700699
    701700        allocate(d_h2oice_new(ngrid,nslope))
    702         call stopping_crit_h2o(ngrid,nslope,cell_area,delta_h2o_adsorbed,delta_h2o_icetablesublim,h2o_ice,d_h2oice,S_atm_2_h2o,S_h2o_2_atm,S_atm_2_h2oice,S_h2oice_2_atm,stopPEM)
     701        call stopping_crit_h2o(ngrid,nslope,cell_area,delta_h2o_adsorbed,delta_h2o_icetablesublim,h2o_ice,d_h2oice,S_atm_2_h2o,S_h2o_2_atm,S_atm_2_h2oice,S_h2oice_2_atm,stopCrit)
    703702        call balance_h2oice_reservoirs(ngrid,nslope,S_atm_2_h2o,S_h2o_2_atm,S_atm_2_h2oice,S_h2oice_2_atm,h2o_ice,d_h2oice,d_h2oice_new)
    704703   
     
    722721    else
    723722        zlag = 0.
    724         call evol_h2o_ice(ngrid,nslope,cell_area,delta_h2o_adsorbed,delta_h2o_icetablesublim,h2o_ice,d_h2oice,zshift_surf,stopPEM)
     723        call evol_h2o_ice(ngrid,nslope,cell_area,delta_h2o_adsorbed,delta_h2o_icetablesublim,h2o_ice,d_h2oice,zshift_surf,stopCrit)
    725724        call evol_co2_ice(ngrid,nslope,co2_ice,d_co2ice,zshift_surf)
    726725    endif
     
    928927!------------------------
    929928    write(*,*) "> Checking the stopping criteria"
    930     call stopping_crit_h2o_ice(cell_area,h2oice_ini_surf,is_h2oice_sublim_ini,h2o_ice,stopPEM,ngrid)
    931     call stopping_crit_co2(cell_area,co2ice_sublim_surf_ini,is_co2ice_sublim_ini,co2_ice,stopPEM,ngrid,ps_avg_global_ini,ps_avg_global_new,nslope)
     929    call stopping_crit_h2o_ice(cell_area,h2oice_ini_surf,is_h2oice_sublim_ini,h2o_ice,stopCrit,ngrid)
     930    call stopping_crit_co2(cell_area,co2ice_sublim_surf_ini,is_co2ice_sublim_ini,co2_ice,stopCrit,ngrid,ps_avg_global_ini,ps_avg_global_new,nslope)
    932931    i_myear_leg = i_myear_leg + dt
    933932    i_myear = i_myear + dt
    934     if (stopPEM <= 0 .and. i_myear_leg >= n_myear_leg) stopPEM = 5
    935     if (stopPEM <= 0 .and. i_myear >= n_myear) stopPEM = 6
     933    if (stopCrit%stop_code() == 0 .and. i_myear_leg >= n_myear_leg) stopCrit%max_iter_reached = .true.
     934    if (stopCrit%stop_code() == 0 .and. i_myear >= n_myear) stopCrit%max_years_reached = .true.
    936935    call system_clock(c2)
    937     if (stopPEM <= 0 .and. timewall .and. real((c2 - c1)/cr) >= timelimit - antetime) stopPEM = 7
    938     if (stopPEM > 0) then
    939         select case (stopPEM)
    940             case(1)
    941                 write(*,'(a,i0,a)') " **** STOPPING because surface of h2o ice sublimating is too low: ", stopPEM, ". See message above."
    942             case(2)
    943                 write(*,'(a,i0,a)') " **** STOPPING because tendencies on h2o ice = 0: ", stopPEM, ". See message above."
    944             case(3)
    945                 write(*,'(a,i0,a)') " **** STOPPING because surface of co2 ice sublimating is too low: ", stopPEM, ". See message above."
    946             case(4)
    947                 write(*,'(a,i0,a)') " **** STOPPING because surface global pressure changed too much: ", stopPEM, ". See message above."
    948             case(5)
    949                 write(*,'(a,i0)') " **** STOPPING because maximum number of iterations is reached (possibly due to orbital parameters): ", stopPEM
    950             case(6)
    951                 write(*,'(a,i0)') " **** STOPPING because maximum number of Martian years to be simulated is reached: ", stopPEM
    952             case(7)
    953                 write(*,'(a,i0)') " **** STOPPING because the time limit for the PEM job will be reached soon: ", stopPEM
    954             case default
    955                 write(*,'(a,i0)') " **** STOPPING with unknown stopping criterion code: ", stopPEM
    956         end select
     936    if (stopCrit%stop_code() == 0 .and. timewall .and. real((c2 - c1)/cr) >= timelimit - antetime) stopCrit%time_limit_reached = .true.
     937    if (stopCrit%is_any_set()) then
     938        write(*,*) stopCrit%stop_message()
    957939        exit
    958940    else
     
    11681150             co2_adsorbed_phys,h2o_adsorbed_phys,h2o_ice,layerings_map)
    11691151
    1170 call info_PEM(i_myear_leg,stopPEM,i_myear,n_myear)
     1152call info_PEM(i_myear_leg,stopCrit%stop_code(),i_myear,n_myear)
    11711153
    11721154write(*,*)
  • trunk/LMDZ.COMMON/libf/evolution/stopping_crit_mod.F90

    r3961 r3967  
    33implicit none
    44
    5 !=======================================================================
     5type :: stopFlags
     6    logical :: surface_h2oice_change = .false.
     7    logical :: zero_dh2oice          = .false.
     8    logical :: surface_co2ice_change = .false.
     9    logical :: pressure_change       = .false.
     10    logical :: max_iter_reached      = .false.
     11    logical :: max_years_reached     = .false.
     12    logical :: time_limit_reached    = .false.
    613contains
    7 !=======================================================================
     14    procedure :: is_any_set
     15    procedure :: stop_code
     16    procedure :: stop_message
     17end type
     18
     19!=======================================================================
     20contains
     21!=======================================================================
     22! To detect if any flag is true
     23FUNCTION is_any_set(this) RESULT(stopPEM)
     24
     25class(stopFlags), intent(in) :: this
     26logical :: stopPEM
     27
     28stopPEM = this%surface_h2oice_change .or. &
     29          this%zero_dh2oice          .or. &
     30          this%surface_co2ice_change .or. &
     31          this%pressure_change       .or. &
     32          this%max_iter_reached      .or. &
     33          this%max_years_reached     .or. &
     34          this%time_limit_reached
     35
     36END FUNCTION is_any_set
     37
     38!=======================================================================
     39! To give the digit code corresponding to the stopping flag
     40FUNCTION stop_code(this) result(code)
     41   
     42class(StopFlags), intent(in) :: this
     43integer :: code
     44
     45code = 0
     46if     (this%surface_h2oice_change) then; code = 1
     47elseif (this%zero_dh2oice)          then; code = 2
     48elseif (this%surface_co2ice_change) then; code = 3
     49elseif (this%pressure_change)       then; code = 4
     50elseif (this%max_iter_reached)      then; code = 5
     51elseif (this%max_years_reached)     then; code = 6
     52elseif (this%time_limit_reached)    then; code = 7
     53endif
     54
     55END FUNCTION stop_code
     56
     57!=======================================================================
     58! To give the message corresponding to the stopping flag
     59FUNCTION stop_message(this) result(msg)
     60   
     61class(StopFlags), intent(in) :: this
     62character(:), allocatable :: msg
     63integer :: stopCode
     64
     65if     (this%surface_h2oice_change) then; msg = " **** STOPPING because surface of h2o ice has changed too much (see message above)."
     66elseif (this%zero_dh2oice)          then; msg = " **** STOPPING because tendencies on h2o ice = 0 (see message above)."
     67elseif (this%surface_co2ice_change) then; msg = " **** STOPPING because surface of co2 ice has changed too much (see message above)."
     68elseif (this%pressure_change)       then; msg = " **** STOPPING because surface global pressure has changed too much (see message above)."
     69elseif (this%max_iter_reached)      then; msg = " **** STOPPING because maximum number of iterations is reached (possibly due to orbital parameters)."
     70elseif (this%max_years_reached)     then; msg = " **** STOPPING because maximum number of Martian years to be simulated is reached."
     71elseif (this%time_limit_reached)    then; msg = " **** STOPPING because the job time limit is going to be reached."
     72endif
     73
     74END FUNCTION stop_message
    875
    976!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     
    1481!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    1582
    16 SUBROUTINE stopping_crit_h2o_ice(cell_area,h2oice_ini_surf,is_h2oice_sublim_ini,h2o_ice,stopPEM,ngrid)
     83SUBROUTINE stopping_crit_h2o_ice(cell_area,h2oice_ini_surf,is_h2oice_sublim_ini,h2o_ice,stopCrit,ngrid)
    1784
    1885use time_evol_mod, only: h2o_ice_crit
     
    35102! Outputs
    36103!--------
    37 integer, intent(inout) :: stopPEM ! Stopping criterion code
     104type(stopFlags), intent(inout) :: stopCrit ! Stopping criterion
    38105! Locals
    39106! ------
     
    42109
    43110!=======================================================================
    44 if (stopPEM > 0) return
     111if (stopCrit%stop_code() > 0) return
    45112
    46113! Computation of the present surface of h2o ice still sublimating
     
    54121! Check of the criterion
    55122if (h2oice_now_surf < h2oice_ini_surf*(1. - h2o_ice_crit)) then
    56     stopPEM = 1
     123    stopCrit%surface_h2oice_change = .true.
    57124    write(*,*) "Reason of stopping: the surface of h2o ice sublimating reaches the threshold"
    58125    write(*,*) "h2oice_now_surf < h2oice_ini_surf*(1. - h2o_ice_crit)", h2oice_now_surf < h2oice_ini_surf*(1. - h2o_ice_crit)
     
    61128    write(*,*) "Percentage of change accepted =", h2o_ice_crit*100
    62129else if (h2oice_now_surf > h2oice_ini_surf*(1. + h2o_ice_crit)) then
    63     stopPEM = 1
     130    stopCrit%surface_h2oice_change = .true.
    64131    write(*,*) "Reason of stopping: the surface of h2o ice sublimating reaches the threshold"
    65132    write(*,*) "h2oice_now_surf > h2oice_ini_surf*(1. + h2o_ice_crit)", h2oice_now_surf > h2oice_ini_surf*(1. + h2o_ice_crit)
     
    73140!=======================================================================
    74141
    75 SUBROUTINE stopping_crit_co2(cell_area,co2ice_sublim_surf_ini,is_co2ice_sublim_ini,co2_ice,stopPEM,ngrid,ps_avg_global_ini,ps_avg_global,nslope)
     142SUBROUTINE stopping_crit_co2(cell_area,co2ice_sublim_surf_ini,is_co2ice_sublim_ini,co2_ice,stopCrit,ngrid,ps_avg_global_ini,ps_avg_global,nslope)
    76143
    77144use time_evol_mod, only: co2_ice_crit, ps_criterion
     
    96163! Outputs
    97164!--------
    98 integer, intent(inout) :: stopPEM ! Stopping criterion code
     165type(stopFlags), intent(inout) :: stopCrit ! Stopping criterion
    99166
    100167! Locals
     
    104171
    105172!=======================================================================
    106 if (stopPEM > 0) return
     173if (stopCrit%stop_code() > 0) return
    107174
    108175! Computation of the present surface of co2 ice still sublimating
     
    116183! Check of the criterion
    117184if (co2ice_now_surf < co2ice_sublim_surf_ini*(1. - co2_ice_crit)) then
    118     stopPEM = 3
     185    stopCrit%surface_co2ice_change = .true.
    119186    write(*,*) "Reason of stopping: the surface of co2 ice sublimating reaches the threshold"
    120187    write(*,*) "co2ice_now_surf < co2ice_sublim_surf_ini*(1. - co2_ice_crit)", co2ice_now_surf < co2ice_sublim_surf_ini*(1. - co2_ice_crit)
     
    123190    write(*,*) "Percentage of change accepted =", co2_ice_crit*100.
    124191else if (co2ice_now_surf > co2ice_sublim_surf_ini*(1. + co2_ice_crit)) then
    125     stopPEM = 3
     192    stopCrit%surface_co2ice_change = .true.
    126193    write(*,*) "Reason of stopping: the surface of co2 ice sublimating reaches the threshold"
    127194    write(*,*) "co2ice_now_surf > co2ice_sublim_surf_ini*(1. + co2_ice_crit)", co2ice_now_surf > co2ice_sublim_surf_ini*(1. + co2_ice_crit)
     
    132199
    133200if (ps_avg_global < ps_avg_global_ini*(1. - ps_criterion)) then
    134     stopPEM = 4
     201    stopCrit%pressure_change = .true.
    135202    write(*,*) "Reason of stopping: the global pressure reaches the threshold"
    136203    write(*,*) "ps_avg_global < ps_avg_global_ini*(1. - ps_criterion)", ps_avg_global < ps_avg_global_ini*(1. - ps_criterion)
     
    139206    write(*,*) "Percentage of change accepted =", ps_criterion*100.
    140207else if (ps_avg_global > ps_avg_global_ini*(1. + ps_criterion)) then
    141     stopPEM = 4
     208    stopCrit%pressure_change = .true.
    142209    write(*,*) "Reason of stopping: the global pressure reaches the threshold"
    143210    write(*,*) "ps_avg_global > ps_avg_global_ini*(1. + ps_criterion)", ps_avg_global > ps_avg_global_ini*(1. + ps_criterion)
     
    151218!=======================================================================
    152219
    153 SUBROUTINE stopping_crit_h2o(ngrid,nslope,cell_area,delta_h2o_adsorbed,delta_h2o_icetablesublim,h2o_ice,d_h2oice,S_atm_2_h2o,S_h2o_2_atm,S_atm_2_h2oice,S_h2oice_2_atm,stopPEM)
     220SUBROUTINE stopping_crit_h2o(ngrid,nslope,cell_area,delta_h2o_adsorbed,delta_h2o_icetablesublim,h2o_ice,d_h2oice,S_atm_2_h2o,S_h2o_2_atm,S_atm_2_h2oice,S_h2oice_2_atm,stopCrit)
    154221
    155222use time_evol_mod, only: dt
     
    174241! Outputs
    175242!--------
    176 integer, intent(inout) :: stopPEM ! Stopping criterion code
    177 real,    intent(out) :: S_atm_2_h2o, S_h2o_2_atm, S_atm_2_h2oice, S_h2oice_2_atm ! Variables to conserve H2O
     243type(stopFlags), intent(inout) :: stopCrit ! Stopping criterion
     244real, intent(out) :: S_atm_2_h2o, S_h2o_2_atm, S_atm_2_h2oice, S_h2oice_2_atm ! Variables to conserve H2O
    178245
    179246! Locals
     
    182249
    183250!=======================================================================
    184 if (stopPEM > 0) return
     251if (stopCrit%stop_code() > 0) return
    185252
    186253! We compute the amount of water going out from the atmosphere (S_atm_2_h2o) and going into the atmophere (S_h2o_2_atm)
     
    218285    write(*,*) "Amount of condensing ice  =", S_atm_2_h2oice
    219286    write(*,*) "Amount of sublimating ice =", S_h2oice_2_atm
    220     stopPEM = 2
     287    stopCrit%zero_dh2oice = .true.
    221288endif
    222289
Note: See TracChangeset for help on using the changeset viewer.