| 1 | MODULE tendencies |
|---|
| 2 | !----------------------------------------------------------------------- |
|---|
| 3 | ! NAME |
|---|
| 4 | ! tendencies |
|---|
| 5 | ! |
|---|
| 6 | ! DESCRIPTION |
|---|
| 7 | ! Computation and update of PEM ice evolution tendencies. |
|---|
| 8 | ! |
|---|
| 9 | ! AUTHORS & DATE |
|---|
| 10 | ! R. Vandemeulebrouck |
|---|
| 11 | ! L. Lange |
|---|
| 12 | ! JB Clement, 2023-2025 |
|---|
| 13 | ! |
|---|
| 14 | ! NOTES |
|---|
| 15 | ! |
|---|
| 16 | !----------------------------------------------------------------------- |
|---|
| 17 | |
|---|
| 18 | ! DECLARATION |
|---|
| 19 | ! ----------- |
|---|
| 20 | implicit none |
|---|
| 21 | |
|---|
| 22 | contains |
|---|
| 23 | !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++ |
|---|
| 24 | |
|---|
| 25 | !======================================================================= |
|---|
| 26 | SUBROUTINE compute_tend(ngrid,nslope,min_ice,d_ice) |
|---|
| 27 | !----------------------------------------------------------------------- |
|---|
| 28 | ! NAME |
|---|
| 29 | ! compute_tend |
|---|
| 30 | ! |
|---|
| 31 | ! DESCRIPTION |
|---|
| 32 | ! Compute initial ice evolution tendencies from PCM data. |
|---|
| 33 | ! |
|---|
| 34 | ! AUTHORS & DATE |
|---|
| 35 | ! R. Vandemeulebrouck |
|---|
| 36 | ! L. Lange |
|---|
| 37 | ! JB Clement, 2023-2025 |
|---|
| 38 | ! |
|---|
| 39 | ! NOTES |
|---|
| 40 | ! Based on minima of ice at each point for the PCM years. |
|---|
| 41 | !----------------------------------------------------------------------- |
|---|
| 42 | |
|---|
| 43 | ! DECLARATION |
|---|
| 44 | ! ----------- |
|---|
| 45 | implicit none |
|---|
| 46 | |
|---|
| 47 | ! ARGUMENTS |
|---|
| 48 | ! --------- |
|---|
| 49 | integer, intent(in) :: ngrid |
|---|
| 50 | integer, intent(in) :: nslope |
|---|
| 51 | real, dimension(ngrid,nslope,2), intent(in) :: min_ice ! Minima of ice at each point for the PCM years |
|---|
| 52 | real, dimension(ngrid,nslope), intent(out) :: d_ice ! Evolution of perennial ice |
|---|
| 53 | |
|---|
| 54 | ! CODE |
|---|
| 55 | ! ---- |
|---|
| 56 | ! We compute the difference |
|---|
| 57 | d_ice = min_ice(:,:,2) - min_ice(:,:,1) |
|---|
| 58 | |
|---|
| 59 | ! If the difference is too small, then there is no evolution |
|---|
| 60 | where (abs(d_ice) < 1.e-10) d_ice = 0. |
|---|
| 61 | |
|---|
| 62 | ! If the minimum over the last year is 0, then we have no perennial ice |
|---|
| 63 | where (abs(min_ice(:,:,2)) < 1.e-10) d_ice = 0. |
|---|
| 64 | |
|---|
| 65 | END SUBROUTINE compute_tend |
|---|
| 66 | !======================================================================= |
|---|
| 67 | |
|---|
| 68 | !======================================================================= |
|---|
| 69 | SUBROUTINE recomp_tend_co2(ngrid,nslope,timelen,d_co2ice_phys,d_co2ice_ini,co2ice,emissivity, & |
|---|
| 70 | vmr_co2_PCM,vmr_co2_PEM,ps_PCM,ps_avg_global_ini,ps_avg_global) |
|---|
| 71 | !----------------------------------------------------------------------- |
|---|
| 72 | ! NAME |
|---|
| 73 | ! recomp_tend_co2 |
|---|
| 74 | ! |
|---|
| 75 | ! DESCRIPTION |
|---|
| 76 | ! Recompute CO2 ice tendency based on pressure and atmospheric changes. |
|---|
| 77 | ! |
|---|
| 78 | ! AUTHORS & DATE |
|---|
| 79 | ! L. Lange |
|---|
| 80 | ! JB Clement, 2023-2025 |
|---|
| 81 | ! |
|---|
| 82 | ! NOTES |
|---|
| 83 | ! Adjusts CO2 ice evolution based on Clausius-Clapeyron changes. |
|---|
| 84 | !----------------------------------------------------------------------- |
|---|
| 85 | |
|---|
| 86 | ! DEPENDENCIES |
|---|
| 87 | ! ------------ |
|---|
| 88 | use constants_marspem_mod, only : alpha_clap_co2, beta_clap_co2, sigmaB, Lco2, sols_per_my, sec_per_sol |
|---|
| 89 | |
|---|
| 90 | ! DECLARATION |
|---|
| 91 | ! ----------- |
|---|
| 92 | implicit none |
|---|
| 93 | |
|---|
| 94 | ! ARGUMENTS |
|---|
| 95 | ! --------- |
|---|
| 96 | integer, intent(in) :: timelen, ngrid, nslope ! Time length, # of grid points and slopes |
|---|
| 97 | real, dimension(ngrid,timelen), intent(in) :: vmr_co2_PCM ! CO2 VMR in PCM first layer |
|---|
| 98 | real, dimension(ngrid,timelen), intent(in) :: vmr_co2_PEM ! CO2 VMR in PEM first layer |
|---|
| 99 | real, dimension(ngrid,timelen), intent(in) :: ps_PCM ! Surface pressure in PCM |
|---|
| 100 | real, intent(in) :: ps_avg_global_ini ! Global average pressure (initial) |
|---|
| 101 | real, intent(in) :: ps_avg_global ! Global average pressure (current) |
|---|
| 102 | real, dimension(ngrid,nslope), intent(in) :: d_co2ice_ini ! Initial CO2 ice evolution |
|---|
| 103 | real, dimension(ngrid,nslope), intent(in) :: co2ice ! CO2 ice surface [kg/m^2] |
|---|
| 104 | real, dimension(ngrid,nslope), intent(in) :: emissivity ! Emissivity |
|---|
| 105 | real, dimension(ngrid,nslope), intent(inout) :: d_co2ice_phys ! Updated CO2 ice evolution |
|---|
| 106 | |
|---|
| 107 | ! LOCAL VARIABLES |
|---|
| 108 | ! --------------- |
|---|
| 109 | integer :: i, t, islope |
|---|
| 110 | real :: coef, avg |
|---|
| 111 | |
|---|
| 112 | ! CODE |
|---|
| 113 | ! ---- |
|---|
| 114 | write(*,*) "> Updating the CO2 ice tendency for the new pressure" |
|---|
| 115 | |
|---|
| 116 | ! Evolution of the water ice for each physical point |
|---|
| 117 | do i = 1,ngrid |
|---|
| 118 | do islope = 1,nslope |
|---|
| 119 | coef = sols_per_my*sec_per_sol*emissivity(i,islope)*sigmaB/Lco2 |
|---|
| 120 | avg = 0. |
|---|
| 121 | if (co2ice(i,islope) > 1.e-4 .and. abs(d_co2ice_phys(i,islope)) > 1.e-5) then |
|---|
| 122 | do t = 1,timelen |
|---|
| 123 | avg = avg + (beta_clap_co2/(alpha_clap_co2-log(vmr_co2_PCM(i,t)*ps_PCM(i,t)/100.)))**4 & |
|---|
| 124 | - (beta_clap_co2/(alpha_clap_co2-log(vmr_co2_PEM(i,t)*ps_PCM(i,t)*(ps_avg_global/ps_avg_global_ini)/100.)))**4 |
|---|
| 125 | enddo |
|---|
| 126 | if (avg < 1.e-4) avg = 0. |
|---|
| 127 | d_co2ice_phys(i,islope) = d_co2ice_ini(i,islope) - coef*avg/timelen |
|---|
| 128 | endif |
|---|
| 129 | enddo |
|---|
| 130 | enddo |
|---|
| 131 | |
|---|
| 132 | END SUBROUTINE recomp_tend_co2 |
|---|
| 133 | !======================================================================= |
|---|
| 134 | |
|---|
| 135 | !======================================================================= |
|---|
| 136 | SUBROUTINE recomp_tend_h2o(h2oice_depth_old,h2oice_depth_new,tsurf,tsoil_PEM_timeseries_old,tsoil_PEM_timeseries_new,d_h2oice) |
|---|
| 137 | !----------------------------------------------------------------------- |
|---|
| 138 | ! NAME |
|---|
| 139 | ! recomp_tend_h2o |
|---|
| 140 | ! |
|---|
| 141 | ! DESCRIPTION |
|---|
| 142 | ! Recompute H2O ice tendency based on soil depth and temperature changes. |
|---|
| 143 | ! |
|---|
| 144 | ! AUTHORS & DATE |
|---|
| 145 | ! JB Clement, 2025 (following E. Vos's work) |
|---|
| 146 | ! |
|---|
| 147 | ! NOTES |
|---|
| 148 | ! |
|---|
| 149 | !----------------------------------------------------------------------- |
|---|
| 150 | |
|---|
| 151 | ! DEPENDENCIES |
|---|
| 152 | ! ------------ |
|---|
| 153 | use soil_temp, only: itp_tsoil |
|---|
| 154 | use subsurface_ice, only: psv |
|---|
| 155 | |
|---|
| 156 | ! DECLARATION |
|---|
| 157 | ! ----------- |
|---|
| 158 | implicit none |
|---|
| 159 | |
|---|
| 160 | ! ARGUMENTS |
|---|
| 161 | ! --------- |
|---|
| 162 | real, intent(in) :: h2oice_depth_old ! Old H2O ice depth |
|---|
| 163 | real, intent(in) :: h2oice_depth_new ! New H2O ice depth |
|---|
| 164 | real, intent(in) :: tsurf ! Surface temperature |
|---|
| 165 | real, dimension(:,:), intent(in) :: tsoil_PEM_timeseries_old ! Old soil temperature time series |
|---|
| 166 | real, dimension(:,:), intent(in) :: tsoil_PEM_timeseries_new ! New soil temperature time series |
|---|
| 167 | real, intent(inout) :: d_h2oice ! Evolution of perennial ice |
|---|
| 168 | |
|---|
| 169 | ! LOCAL VARIABLES |
|---|
| 170 | ! --------------- |
|---|
| 171 | real :: Rz_old, Rz_new, R_dec, hum_dec, psv_max_old, psv_max_new |
|---|
| 172 | integer :: t |
|---|
| 173 | real, parameter :: coef_diff = 4.e-4 ! Diffusion coefficient |
|---|
| 174 | real, parameter :: zcdv = 0.0325 ! Drag coefficient |
|---|
| 175 | |
|---|
| 176 | ! CODE |
|---|
| 177 | ! ---- |
|---|
| 178 | ! Higher resistance due to growing lag layer (higher depth) |
|---|
| 179 | Rz_old = h2oice_depth_old*zcdv/coef_diff ! Old resistance from PCM |
|---|
| 180 | Rz_new = h2oice_depth_new*zcdv/coef_diff ! New resistance based on new depth |
|---|
| 181 | R_dec = Rz_old/Rz_new ! Decrease because of resistance |
|---|
| 182 | |
|---|
| 183 | ! The maxmimum of the daily averages over one year for the saturation vapor pressure at the ice table location |
|---|
| 184 | psv_max_old = 0. |
|---|
| 185 | psv_max_new = 0. |
|---|
| 186 | do t = 1,size(tsoil_PEM_timeseries_old,2) |
|---|
| 187 | psv_max_old = max(psv_max_old,psv(itp_tsoil(tsoil_PEM_timeseries_old(:,t),tsurf,h2oice_depth_old))) |
|---|
| 188 | psv_max_new = max(psv_max_new,psv(itp_tsoil(tsoil_PEM_timeseries_new(:,t),tsurf,h2oice_depth_new))) |
|---|
| 189 | enddo |
|---|
| 190 | |
|---|
| 191 | ! Lower humidity due to growing lag layer (higher depth) |
|---|
| 192 | if (abs(psv_max_old) < 1.e2*epsilon(1.)) then |
|---|
| 193 | hum_dec = 1. |
|---|
| 194 | else |
|---|
| 195 | hum_dec = psv_max_new/psv_max_old ! Decrease because of lower water vapor pressure at the new depth |
|---|
| 196 | endif |
|---|
| 197 | |
|---|
| 198 | ! Flux correction (decrease) |
|---|
| 199 | d_h2oice = d_h2oice*R_dec*hum_dec |
|---|
| 200 | |
|---|
| 201 | END SUBROUTINE recomp_tend_h2o |
|---|
| 202 | !======================================================================= |
|---|
| 203 | |
|---|
| 204 | END MODULE tendencies |
|---|