[3571] | 1 | MODULE recomp_tend_co2_mod |
---|
[3076] | 2 | |
---|
| 3 | implicit none |
---|
| 4 | |
---|
| 5 | !======================================================================= |
---|
| 6 | contains |
---|
| 7 | !======================================================================= |
---|
| 8 | |
---|
[3553] | 9 | SUBROUTINE recomp_tend_co2(ngrid,nslope,timelen,d_co2ice_phys,d_co2ice_ini,co2ice,emissivity, & |
---|
[3571] | 10 | vmr_co2_PCM,vmr_co2_PEM,ps_PCM,ps_avg_global_ini,ps_avg_global) |
---|
[2779] | 11 | |
---|
[3149] | 12 | use constants_marspem_mod, only : alpha_clap_co2, beta_clap_co2, sigmaB, Lco2, sols_per_my, sec_per_sol |
---|
[2944] | 13 | |
---|
[3076] | 14 | implicit none |
---|
[2779] | 15 | |
---|
| 16 | !======================================================================= |
---|
| 17 | ! |
---|
| 18 | ! Routine that compute the evolution of the tendencie for co2 ice |
---|
| 19 | ! |
---|
| 20 | !======================================================================= |
---|
| 21 | |
---|
[3571] | 22 | ! Inputs |
---|
| 23 | ! ------ |
---|
[3076] | 24 | integer, intent(in) :: timelen, ngrid, nslope |
---|
[3571] | 25 | real, dimension(ngrid,timelen), intent(in) :: vmr_co2_PCM ! physical point field: Volume mixing ratio of co2 in the first layer |
---|
| 26 | real, dimension(ngrid,timelen), intent(in) :: vmr_co2_PEM ! physical point field: Volume mixing ratio of co2 in the first layer |
---|
| 27 | real, dimension(ngrid,timelen), intent(in) :: ps_PCM ! physical point field: Surface pressure in the PCM |
---|
| 28 | real, intent(in) :: ps_avg_global_ini ! global averaged pressure at previous timestep |
---|
| 29 | real, intent(in) :: ps_avg_global ! global averaged pressure at current timestep |
---|
| 30 | real, dimension(ngrid,nslope), intent(in) :: d_co2ice_ini ! physical point field: Evolution of perennial ice over one year |
---|
| 31 | real, dimension(ngrid,nslope), intent(in) :: co2ice ! CO2 ice per mesh and sub-grid slope (kg/m^2) |
---|
| 32 | real, dimension(ngrid,nslope), intent(in) :: emissivity ! Emissivity per mesh and sub-grid slope(1) |
---|
| 33 | ! Outputs |
---|
| 34 | ! ------- |
---|
[3553] | 35 | real, dimension(ngrid,nslope), intent(inout) :: d_co2ice_phys ! physical point field: Evolution of perennial ice over one year |
---|
[2779] | 36 | |
---|
[3571] | 37 | ! Local: |
---|
| 38 | ! ------ |
---|
[3076] | 39 | integer :: i, t, islope |
---|
[3571] | 40 | real :: coef, avg |
---|
[2779] | 41 | |
---|
[3149] | 42 | write(*,*) "Update of the CO2 tendency from the current pressure" |
---|
[3532] | 43 | |
---|
[2779] | 44 | ! Evolution of the water ice for each physical point |
---|
[3076] | 45 | do i = 1,ngrid |
---|
| 46 | do islope = 1,nslope |
---|
[3553] | 47 | coef = sols_per_my*sec_per_sol*emissivity(i,islope)*sigmaB/Lco2 |
---|
[3571] | 48 | avg = 0. |
---|
[3553] | 49 | if (co2ice(i,islope) > 1.e-4 .and. abs(d_co2ice_phys(i,islope)) > 1.e-5) then |
---|
| 50 | do t = 1,timelen |
---|
[3571] | 51 | avg = avg + (beta_clap_co2/(alpha_clap_co2-log(vmr_co2_PCM(i,t)*ps_PCM(i,t)/100.)))**4 & |
---|
| 52 | - (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 |
---|
[3076] | 53 | enddo |
---|
[3571] | 54 | if (avg < 1.e-4) avg = 0. |
---|
| 55 | d_co2ice_phys(i,islope) = d_co2ice_ini(i,islope) - coef*avg/timelen |
---|
[3076] | 56 | endif |
---|
[2779] | 57 | enddo |
---|
[3076] | 58 | enddo |
---|
[2779] | 59 | |
---|
[3553] | 60 | END SUBROUTINE recomp_tend_co2 |
---|
[3571] | 61 | !======================================================================= |
---|
[3076] | 62 | |
---|
[3571] | 63 | SUBROUTINE recomp_tend_h2o(ngrid,nslope,timelen,d_h2oice,PCM_temp,PEM_temp) |
---|
| 64 | |
---|
| 65 | implicit none |
---|
| 66 | |
---|
| 67 | !======================================================================= |
---|
| 68 | ! |
---|
| 69 | ! Routine that compute the evolution of the tendencie for h2o ice |
---|
| 70 | ! |
---|
| 71 | !======================================================================= |
---|
| 72 | |
---|
| 73 | ! Inputs |
---|
| 74 | ! ------ |
---|
| 75 | integer, intent(in) :: timelen, ngrid, nslope |
---|
| 76 | real, dimension(:), intent(in) :: PCM_temp, PEM_temp |
---|
| 77 | ! Outputs |
---|
| 78 | ! ------- |
---|
| 79 | real, dimension(ngrid,nslope), intent(inout) :: d_h2oice ! physical point field: Evolution of perennial ice over one year |
---|
| 80 | |
---|
| 81 | ! Local: |
---|
| 82 | ! ------ |
---|
| 83 | |
---|
| 84 | write(*,*) "Update of the H2O tendency due to lag layer" |
---|
| 85 | |
---|
| 86 | ! Flux correction due to lag layer |
---|
| 87 | !~ Rz_old = h2oice_depth_old*0.0325/4.e-4 ! resistance from PCM |
---|
| 88 | !~ Rz_new = h2oice_depth_new*0.0325/4.e-4 ! new resistance based on new depth |
---|
| 89 | !~ R_dec = (1./Rz_old)/(1./Rz_new) ! decrease because of resistance |
---|
| 90 | !~ soil_psv_old = psv(max(PCM_temp(h2oice_depth_old))) ! the maxmimum annual mean saturation vapor pressure at the temperature of the GCM run temperature at the old ice location |
---|
| 91 | !~ soil_psv_new = psv(max(PEM_temp(h2oice_depth_new))) ! the maxmimum annual mean saturation vapor pressure at the temperature of the PEM run temperature at the new ice location |
---|
| 92 | !~ hum_dec = soil_psv_old/soil_psv_new ! decrease because of lower water vapor pressure at the new depth |
---|
| 93 | !~ d_h2oice = d_h2oice*R_dec*hum_dec ! decrease of flux |
---|
| 94 | |
---|
| 95 | END SUBROUTINE recomp_tend_h2o |
---|
| 96 | |
---|
| 97 | END MODULE recomp_tend_co2_mod |
---|