Ignore:
Timestamp:
Mar 13, 2024, 2:46:30 PM (8 months ago)
Author:
llange
Message:

Mars PEM
Correction of small mistake when computing the total mass of CO2/H2O stored in the soil; the wrong layer index was used
LL

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

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.COMMON/libf/evolution/adsorption_mod.F90

    r3206 r3264  
    218218    do iloop = 1,index_breccia
    219219       if((TI_PEM(ig,iloop,islope).lt.inertie_thresold).and.(ispermanent_h2oglaciers(ig,islope).eq.0).and.(ispermanent_co2glaciers(ig,islope).eq.0)) then
    220              deltam_reg_complete(ig,iloop,islope) = (dm_h2o_regolith_slope(ig,iloop,islope) - m_h2o_completesoil(ig,iloop,islope)) &
    221                                                    *(layer_PEM(iloop+1) - layer_PEM(iloop))
     220             if(iloop==1) then
     221                 deltam_reg_complete(ig,iloop,islope) = (dm_h2o_regolith_slope(ig,iloop,islope) - m_h2o_completesoil(ig,iloop,islope)) &
     222                                                   *(layer_PEM(iloop))
     223             else
     224                 deltam_reg_complete(ig,iloop,islope) = (dm_h2o_regolith_slope(ig,iloop,islope) - m_h2o_completesoil(ig,iloop,islope)) &
     225                                                   *(layer_PEM(iloop) - layer_PEM(iloop-1))
     226             endif
    222227       else ! NO EXCHANGE AS ICE BLOCK THE DYNAMIC!
    223228             deltam_reg_complete(ig,iloop,islope) = 0.
     
    387392    do iloop = 1,index_breccia
    388393       if((TI_PEM(ig,iloop,islope).lt.inertie_thresold).and.(ispermanent_h2oglaciers(ig,islope).eq.0).and.(ispermanent_co2glaciers(ig,islope).eq.0)) then
    389              deltam_reg_complete(ig,iloop,islope) = (dm_co2_regolith_slope(ig,iloop,islope) - m_co2_completesoil(ig,iloop,islope)) &
    390                                                    *(layer_PEM(iloop+1) - layer_PEM(iloop))
     394             if(iloop == 1) then
     395                 deltam_reg_complete(ig,iloop,islope) = (dm_co2_regolith_slope(ig,iloop,islope) - m_co2_completesoil(ig,iloop,islope)) &
     396                                                   *(layer_PEM(iloop))               
     397             else
     398                 deltam_reg_complete(ig,iloop,islope) = (dm_co2_regolith_slope(ig,iloop,islope) - m_co2_completesoil(ig,iloop,islope)) &
     399                                                   *(layer_PEM(iloop) - layer_PEM(iloop-1))
     400             endif
    391401       else ! NO EXCHANGE AS ICE BLOCK THE DYNAMIC!
    392402             deltam_reg_complete(ig,iloop,islope) = 0.
  • trunk/LMDZ.COMMON/libf/evolution/changelog.txt

    r3256 r3264  
    247247== 07/03/2024 == JBC
    248248Adaptation of threshold values for ice management (in particular 'inf_h2oice_threshold') to more realistic values.
     249
     250== 13/03/2024 == LL
     251Correction of small mistake when computing the total mass of CO2/H2O stored in the soil; the wrong layer index was used
  • trunk/LMDZ.COMMON/libf/evolution/ice_table_mod.F90

    r3206 r3264  
    137137
    138138
    139    SUBROUTINE compute_massh2o_exchange_ssi(ngrid,nslope,nsoil_PEM,former_ice_table_thickness,new_ice_table_thickness,ice_table_depth,tsoil,delta_m_h2o)
     139   SUBROUTINE compute_massh2o_exchange_ssi(ngrid,nslope,nsoil_PEM,former_ice_table_thickness,new_ice_table_thickness,ice_table_depth,tsurf,tsoil,delta_m_h2o)
    140140!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    141141!!!
     
    147147    use comsoil_h_PEM, only: mlayer_PEM
    148148    use comslope_mod, only: subslope_dist,def_slope_mean
    149     use constants_marspem_mod,only:porosity
     149    use constants_marspem_mod, only: porosity
     150    use vdifc_mod, only: compute_Tice
    150151#ifndef CPP_STD
    151152    use comcstfi_h,   only: pi
     
    160161    real,intent(in) :: former_ice_table_thickness(ngrid,nslope)    ! ice table thickness at the former iteration [m]
    161162    real,intent(in) :: new_ice_table_thickness(ngrid,nslope)       ! ice table thickness at the current iteration [m]
    162     real,intent(out) :: ice_table_depth(ngrid,nslope)              ! ice table depth [m]
     163    real,intent(in) :: ice_table_depth(ngrid,nslope)              ! ice table depth [m]
     164    real,intent(in) :: tsurf(ngrid,nslope)                         ! Surface temperature [K]
    163165    real,intent(in) :: tsoil(ngrid,nsoil_PEM,nslope)               ! Soil temperature [K]
    164166!   outputs
     
    177179   do ig = 1,ngrid
    178180      do islope = 1,nslope
    179          if(ice_table_depth(ig,islope).gt.0.) then
    180             if (ice_table_depth(ig,islope).lt. 1e-10) then
    181                Tice(ig,islope) = tsoil(ig,1,islope)
    182             else
    183                iref=0 ! initialize iref
    184                do ilay=1,nsoil_PEM ! loop on layers to find the beginning of the ice table
    185                   if (ice_table_depth(ig,islope).ge.mlayer_PEM(ilay)) then
    186                      iref=ilay ! pure regolith layer up to here
    187                   else
    188                   ! correct iref was obtained in previous cycle
    189                      exit
    190                   endif
    191                enddo
    192                if(iref.eq.nsoil_PEM) then
    193                   Tice(ig,islope) = tsoil(ig,nsoil_PEM,islope)
    194                else
    195                   Tice(ig,islope) = (tsoil(ig,iref+1,islope) - tsoil(ig,iref,islope))/(mlayer_PEM(iref+1) - mlayer_PEM(iref))* &
    196                                     (ice_table_depth(ig,islope) - mlayer_PEM(iref)) +  tsoil(ig,iref,islope)           
    197                endif         
    198                rho(ig,islope) = -3.5353e-4*Tice(ig,islope)**2+   0.0351* Tice(ig,islope) +  933.5030 ! Rottgers, 2012
    199             endif
    200          endif
     181         call compute_Tice(nsoil_PEM,tsoil(ig,:,islope),tsurf(ig,islope), ice_table_depth(ig,islope), Tice(ig,islope))
     182         rho(ig,islope) = -3.5353e-4*Tice(ig,islope)**2+   0.0351* Tice(ig,islope) +  933.5030 ! Rottgers, 2012
    201183      enddo
    202184   enddo     
  • trunk/LMDZ.COMMON/libf/evolution/pem.F90

    r3207 r3264  
    599599        do islope = 1,nslope
    600600            do l = 1,nsoilmx_PEM - 1
    601                 totmassco2_adsorbded = totmassco2_adsorbded + co2_adsorbded_phys(ig,l,islope)*(layer_PEM(l + 1) - layer_PEM(l))* &
     601                if (l==1) then
     602                   totmassco2_adsorbded = totmassco2_adsorbded + co2_adsorbded_phys(ig,l,islope)*(layer_PEM(l))* &
    602603                                       subslope_dist(ig,islope)/cos(pi*def_slope_mean(islope)/180.)*cell_area(ig)
    603                 totmassh2o_adsorbded = totmassh2o_adsorbded + h2o_adsorbded_phys(ig,l,islope)*(layer_PEM(l + 1) - layer_PEM(l))* &
     604                   totmassh2o_adsorbded = totmassh2o_adsorbded + h2o_adsorbded_phys(ig,l,islope)*(layer_PEM(l))* &
    604605                                       subslope_dist(ig,islope)/cos(pi*def_slope_mean(islope)/180.)*cell_area(ig)
     606                else
     607                   totmassco2_adsorbded = totmassco2_adsorbded + co2_adsorbded_phys(ig,l,islope)*(layer_PEM(l) - layer_PEM(l-1))* &
     608                                       subslope_dist(ig,islope)/cos(pi*def_slope_mean(islope)/180.)*cell_area(ig)
     609                   totmassh2o_adsorbded = totmassh2o_adsorbded + h2o_adsorbded_phys(ig,l,islope)*(layer_PEM(l) - layer_PEM(l-1))* &
     610                                       subslope_dist(ig,islope)/cos(pi*def_slope_mean(islope)/180.)*cell_area(ig)
     611                endif
    605612            enddo
    606613        enddo
     
    840847            porefillingice_thickness_prev_iter = porefillingice_thickness
    841848            call computeice_table_equilibrium(ngrid,nslope,nsoilmx_PEM,watercaptag,watersurf_density_ave,watersoil_density_PEM_ave,TI_PEM(:,1,:),porefillingice_depth,porefillingice_thickness)
    842             call compute_massh2o_exchange_ssi(ngrid,nslope,nsoilmx_PEM,porefillingice_thickness_prev_iter,porefillingice_thickness,porefillingice_depth,tsoil_PEM,delta_h2o_icetablesublim) ! Mass of H2O exchange between the ssi and the atmosphere
     849            call compute_massh2o_exchange_ssi(ngrid,nslope,nsoilmx_PEM,porefillingice_thickness_prev_iter,porefillingice_thickness,porefillingice_depth,tsurf_ave, tsoil_PEM,delta_h2o_icetablesublim) ! Mass of H2O exchange between the ssi and the atmosphere
    843850        endif
    844851! II_d.4 Update the soil thermal properties
     
    855862            do ig = 1,ngrid
    856863                do islope =1, nslope
    857                     do l = 1,nsoilmx_PEM - 1
    858                         totmassco2_adsorbded = totmassco2_adsorbded + co2_adsorbded_phys(ig,l,islope)*(layer_PEM(l + 1) - layer_PEM(l))* &
    859                                                subslope_dist(ig,islope)/cos(pi*def_slope_mean(islope)/180.)*cell_area(ig)
    860                         totmassh2o_adsorbded = totmassh2o_adsorbded + h2o_adsorbded_phys(ig,l,islope)*(layer_PEM(l + 1) - layer_PEM(l))* &
    861                                                subslope_dist(ig,islope)/cos(pi*def_slope_mean(islope)/180.)*cell_area(ig)
     864                    do l = 1,nsoilmx_PEM
     865                        if (l==1) then
     866                            totmassco2_adsorbded = totmassco2_adsorbded + co2_adsorbded_phys(ig,l,islope)*(layer_PEM(l))* &
     867                                       subslope_dist(ig,islope)/cos(pi*def_slope_mean(islope)/180.)*cell_area(ig)
     868                            totmassh2o_adsorbded = totmassh2o_adsorbded + h2o_adsorbded_phys(ig,l,islope)*(layer_PEM(l))* &
     869                                       subslope_dist(ig,islope)/cos(pi*def_slope_mean(islope)/180.)*cell_area(ig)
     870                        else
     871                            totmassco2_adsorbded = totmassco2_adsorbded + co2_adsorbded_phys(ig,l,islope)*(layer_PEM(l) - layer_PEM(l-1))* &
     872                                       subslope_dist(ig,islope)/cos(pi*def_slope_mean(islope)/180.)*cell_area(ig)
     873                            totmassh2o_adsorbded = totmassh2o_adsorbded + h2o_adsorbded_phys(ig,l,islope)*(layer_PEM(l) - layer_PEM(l-1))* &
     874                                       subslope_dist(ig,islope)/cos(pi*def_slope_mean(islope)/180.)*cell_area(ig)
     875                        endif
    862876                    enddo
    863877                enddo
Note: See TracChangeset for help on using the changeset viewer.