Changeset 3967
- Timestamp:
- Nov 20, 2025, 3:01:08 PM (4 weeks ago)
- Location:
- trunk/LMDZ.COMMON/libf/evolution
- Files:
-
- 4 edited
-
changelog.txt (modified) (1 diff)
-
evol_ice_mod.F90 (modified) (3 diffs)
-
pem.F90 (modified) (7 diffs)
-
stopping_crit_mod.F90 (modified) (17 diffs)
Legend:
- Unmodified
- Added
- Removed
-
trunk/LMDZ.COMMON/libf/evolution/changelog.txt
r3961 r3967 794 794 == 14/11/2025 == JBC 795 795 Clearing all the tags and code related to the Generic PCM. 796 797 == 20/11/2025 == JBC 798 New 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 49 49 !======================================================================= 50 50 51 SUBROUTINE evol_h2o_ice(ngrid,nslope,cell_area,delta_h2o_adsorbed,delta_h2o_icetablesublim,h2o_ice,d_h2oice,zshift_surf,stop PEM)51 SUBROUTINE evol_h2o_ice(ngrid,nslope,cell_area,delta_h2o_adsorbed,delta_h2o_icetablesublim,h2o_ice,d_h2oice,zshift_surf,stopCrit) 52 52 53 53 use time_evol_mod, only: dt 54 54 use glaciers_mod, only: rho_h2oice 55 use stopping_crit_mod, only: stopping_crit_h2o 55 use stopping_crit_mod, only: stopping_crit_h2o, stopFlags 56 56 57 57 implicit none … … 73 73 real, dimension(ngrid,nslope), intent(inout) :: h2o_ice ! H2O ice (kg/m^2) 74 74 real, dimension(ngrid,nslope), intent(inout) :: d_h2oice ! Tendency of H2O ice (kg/m^2/year) 75 integer, intent(inout) :: stopPEM ! Stopping criterion code 75 type(stopFlags), intent(inout) :: stopCrit ! Stopping criterion 76 76 real, dimension(ngrid,nslope), intent(out) :: zshift_surf ! Elevation shift for the surface [m] 77 77 … … 88 88 zshift_surf = d_h2oice*dt/rho_h2oice 89 89 else ! 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,stop PEM)91 if (stop PEM> 0) return90 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 92 92 93 93 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 41 41 use glaciers_mod, only: flow_co2glaciers, flow_h2oglaciers, co2ice_flow, h2oice_flow, inf_h2oice_threshold, & 42 42 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 43 use stopping_crit_mod, only: stopping_crit_h2o_ice, stopping_crit_co2, stopping_crit_h2o, stopFlags 44 44 use constants_marspem_mod, only: alpha_clap_co2, beta_clap_co2, alpha_clap_h2o, beta_clap_h2o, m_co2, m_noco2 45 45 use evol_ice_mod, only: evol_co2_ice, evol_h2o_ice, balance_h2oice_reservoirs … … 167 167 real, dimension(:,:,:), allocatable :: zplev_timeseries_new ! Grid points x Atmospheric x Time: same as zplev_new, but in times series [kg/m ^2] 168 168 real, 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 169 type(stopFlags) :: stopCrit ! Stopping criteria 170 170 real :: A, B, mmean ! Molar mass: intermediate A, B for computations of the mean molar mass of the layer [mol/kg] 171 171 real, 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] … … 612 612 write(*,*) '********* PEM cycle *********' 613 613 i_myear_leg = 0 614 stopPEM = 0615 614 if (layering_algo) then 616 615 allocate(h2o_ice_depth_old(ngrid,nslope),new_str(ngrid,nslope),new_lag(ngrid,nslope),current(ngrid,nslope)) … … 700 699 701 700 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,stop PEM)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) 703 702 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) 704 703 … … 722 721 else 723 722 zlag = 0. 724 call evol_h2o_ice(ngrid,nslope,cell_area,delta_h2o_adsorbed,delta_h2o_icetablesublim,h2o_ice,d_h2oice,zshift_surf,stop PEM)723 call evol_h2o_ice(ngrid,nslope,cell_area,delta_h2o_adsorbed,delta_h2o_icetablesublim,h2o_ice,d_h2oice,zshift_surf,stopCrit) 725 724 call evol_co2_ice(ngrid,nslope,co2_ice,d_co2ice,zshift_surf) 726 725 endif … … 928 927 !------------------------ 929 928 write(*,*) "> Checking the stopping criteria" 930 call stopping_crit_h2o_ice(cell_area,h2oice_ini_surf,is_h2oice_sublim_ini,h2o_ice,stop PEM,ngrid)931 call stopping_crit_co2(cell_area,co2ice_sublim_surf_ini,is_co2ice_sublim_ini,co2_ice,stop PEM,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) 932 931 i_myear_leg = i_myear_leg + dt 933 932 i_myear = i_myear + dt 934 if (stop PEM <= 0 .and. i_myear_leg >= n_myear_leg) stopPEM = 5935 if (stop PEM <= 0 .and. i_myear >= n_myear) stopPEM = 6933 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. 936 935 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() 957 939 exit 958 940 else … … 1168 1150 co2_adsorbed_phys,h2o_adsorbed_phys,h2o_ice,layerings_map) 1169 1151 1170 call info_PEM(i_myear_leg,stop PEM,i_myear,n_myear)1152 call info_PEM(i_myear_leg,stopCrit%stop_code(),i_myear,n_myear) 1171 1153 1172 1154 write(*,*) -
trunk/LMDZ.COMMON/libf/evolution/stopping_crit_mod.F90
r3961 r3967 3 3 implicit none 4 4 5 !======================================================================= 5 type :: 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. 6 13 contains 7 !======================================================================= 14 procedure :: is_any_set 15 procedure :: stop_code 16 procedure :: stop_message 17 end type 18 19 !======================================================================= 20 contains 21 !======================================================================= 22 ! To detect if any flag is true 23 FUNCTION is_any_set(this) RESULT(stopPEM) 24 25 class(stopFlags), intent(in) :: this 26 logical :: stopPEM 27 28 stopPEM = 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 36 END FUNCTION is_any_set 37 38 !======================================================================= 39 ! To give the digit code corresponding to the stopping flag 40 FUNCTION stop_code(this) result(code) 41 42 class(StopFlags), intent(in) :: this 43 integer :: code 44 45 code = 0 46 if (this%surface_h2oice_change) then; code = 1 47 elseif (this%zero_dh2oice) then; code = 2 48 elseif (this%surface_co2ice_change) then; code = 3 49 elseif (this%pressure_change) then; code = 4 50 elseif (this%max_iter_reached) then; code = 5 51 elseif (this%max_years_reached) then; code = 6 52 elseif (this%time_limit_reached) then; code = 7 53 endif 54 55 END FUNCTION stop_code 56 57 !======================================================================= 58 ! To give the message corresponding to the stopping flag 59 FUNCTION stop_message(this) result(msg) 60 61 class(StopFlags), intent(in) :: this 62 character(:), allocatable :: msg 63 integer :: stopCode 64 65 if (this%surface_h2oice_change) then; msg = " **** STOPPING because surface of h2o ice has changed too much (see message above)." 66 elseif (this%zero_dh2oice) then; msg = " **** STOPPING because tendencies on h2o ice = 0 (see message above)." 67 elseif (this%surface_co2ice_change) then; msg = " **** STOPPING because surface of co2 ice has changed too much (see message above)." 68 elseif (this%pressure_change) then; msg = " **** STOPPING because surface global pressure has changed too much (see message above)." 69 elseif (this%max_iter_reached) then; msg = " **** STOPPING because maximum number of iterations is reached (possibly due to orbital parameters)." 70 elseif (this%max_years_reached) then; msg = " **** STOPPING because maximum number of Martian years to be simulated is reached." 71 elseif (this%time_limit_reached) then; msg = " **** STOPPING because the job time limit is going to be reached." 72 endif 73 74 END FUNCTION stop_message 8 75 9 76 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! … … 14 81 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 15 82 16 SUBROUTINE stopping_crit_h2o_ice(cell_area,h2oice_ini_surf,is_h2oice_sublim_ini,h2o_ice,stop PEM,ngrid)83 SUBROUTINE stopping_crit_h2o_ice(cell_area,h2oice_ini_surf,is_h2oice_sublim_ini,h2o_ice,stopCrit,ngrid) 17 84 18 85 use time_evol_mod, only: h2o_ice_crit … … 35 102 ! Outputs 36 103 !-------- 37 integer, intent(inout) :: stopPEM ! Stopping criterion code 104 type(stopFlags), intent(inout) :: stopCrit ! Stopping criterion 38 105 ! Locals 39 106 ! ------ … … 42 109 43 110 !======================================================================= 44 if (stop PEM> 0) return111 if (stopCrit%stop_code() > 0) return 45 112 46 113 ! Computation of the present surface of h2o ice still sublimating … … 54 121 ! Check of the criterion 55 122 if (h2oice_now_surf < h2oice_ini_surf*(1. - h2o_ice_crit)) then 56 stop PEM = 1123 stopCrit%surface_h2oice_change = .true. 57 124 write(*,*) "Reason of stopping: the surface of h2o ice sublimating reaches the threshold" 58 125 write(*,*) "h2oice_now_surf < h2oice_ini_surf*(1. - h2o_ice_crit)", h2oice_now_surf < h2oice_ini_surf*(1. - h2o_ice_crit) … … 61 128 write(*,*) "Percentage of change accepted =", h2o_ice_crit*100 62 129 else if (h2oice_now_surf > h2oice_ini_surf*(1. + h2o_ice_crit)) then 63 stop PEM = 1130 stopCrit%surface_h2oice_change = .true. 64 131 write(*,*) "Reason of stopping: the surface of h2o ice sublimating reaches the threshold" 65 132 write(*,*) "h2oice_now_surf > h2oice_ini_surf*(1. + h2o_ice_crit)", h2oice_now_surf > h2oice_ini_surf*(1. + h2o_ice_crit) … … 73 140 !======================================================================= 74 141 75 SUBROUTINE stopping_crit_co2(cell_area,co2ice_sublim_surf_ini,is_co2ice_sublim_ini,co2_ice,stop PEM,ngrid,ps_avg_global_ini,ps_avg_global,nslope)142 SUBROUTINE 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) 76 143 77 144 use time_evol_mod, only: co2_ice_crit, ps_criterion … … 96 163 ! Outputs 97 164 !-------- 98 integer, intent(inout) :: stopPEM ! Stopping criterion code 165 type(stopFlags), intent(inout) :: stopCrit ! Stopping criterion 99 166 100 167 ! Locals … … 104 171 105 172 !======================================================================= 106 if (stop PEM> 0) return173 if (stopCrit%stop_code() > 0) return 107 174 108 175 ! Computation of the present surface of co2 ice still sublimating … … 116 183 ! Check of the criterion 117 184 if (co2ice_now_surf < co2ice_sublim_surf_ini*(1. - co2_ice_crit)) then 118 stop PEM = 3185 stopCrit%surface_co2ice_change = .true. 119 186 write(*,*) "Reason of stopping: the surface of co2 ice sublimating reaches the threshold" 120 187 write(*,*) "co2ice_now_surf < co2ice_sublim_surf_ini*(1. - co2_ice_crit)", co2ice_now_surf < co2ice_sublim_surf_ini*(1. - co2_ice_crit) … … 123 190 write(*,*) "Percentage of change accepted =", co2_ice_crit*100. 124 191 else if (co2ice_now_surf > co2ice_sublim_surf_ini*(1. + co2_ice_crit)) then 125 stop PEM = 3192 stopCrit%surface_co2ice_change = .true. 126 193 write(*,*) "Reason of stopping: the surface of co2 ice sublimating reaches the threshold" 127 194 write(*,*) "co2ice_now_surf > co2ice_sublim_surf_ini*(1. + co2_ice_crit)", co2ice_now_surf > co2ice_sublim_surf_ini*(1. + co2_ice_crit) … … 132 199 133 200 if (ps_avg_global < ps_avg_global_ini*(1. - ps_criterion)) then 134 stop PEM = 4201 stopCrit%pressure_change = .true. 135 202 write(*,*) "Reason of stopping: the global pressure reaches the threshold" 136 203 write(*,*) "ps_avg_global < ps_avg_global_ini*(1. - ps_criterion)", ps_avg_global < ps_avg_global_ini*(1. - ps_criterion) … … 139 206 write(*,*) "Percentage of change accepted =", ps_criterion*100. 140 207 else if (ps_avg_global > ps_avg_global_ini*(1. + ps_criterion)) then 141 stop PEM = 4208 stopCrit%pressure_change = .true. 142 209 write(*,*) "Reason of stopping: the global pressure reaches the threshold" 143 210 write(*,*) "ps_avg_global > ps_avg_global_ini*(1. + ps_criterion)", ps_avg_global > ps_avg_global_ini*(1. + ps_criterion) … … 151 218 !======================================================================= 152 219 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,stop PEM)220 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,stopCrit) 154 221 155 222 use time_evol_mod, only: dt … … 174 241 ! Outputs 175 242 !-------- 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 H2O243 type(stopFlags), intent(inout) :: stopCrit ! Stopping criterion 244 real, intent(out) :: S_atm_2_h2o, S_h2o_2_atm, S_atm_2_h2oice, S_h2oice_2_atm ! Variables to conserve H2O 178 245 179 246 ! Locals … … 182 249 183 250 !======================================================================= 184 if (stop PEM> 0) return251 if (stopCrit%stop_code() > 0) return 185 252 186 253 ! We compute the amount of water going out from the atmosphere (S_atm_2_h2o) and going into the atmophere (S_h2o_2_atm) … … 218 285 write(*,*) "Amount of condensing ice =", S_atm_2_h2oice 219 286 write(*,*) "Amount of sublimating ice =", S_h2oice_2_atm 220 stop PEM = 2287 stopCrit%zero_dh2oice = .true. 221 288 endif 222 289
Note: See TracChangeset
for help on using the changeset viewer.
