Ignore:
Timestamp:
Jan 10, 2025, 5:45:03 PM (10 days ago)
Author:
jbclement
Message:

PEM:

  • New way to manage the pressure: now the PEM manages only the average pressure and keeps the pressure deviation with the instantaneous pressure from the start to reconstruct the pressure at the end ('ps_avg = ps_start + ps_dev'). As a consequence, everything related to pressure in the PEM is modified accordingly.
  • Surface temperatures management is now simpler. It follows the strategy for the pressure (and soil temperature) described above.
  • Soil temperatures are now adapted to match the surface temperature changes occured during the PEM by modifying the soil temperature deviation at the end.
  • Few simplifications/optimizations: notably, the two PCM years are now read in one go in 'read_data_PCM_mod.F90' and only the needed variables are extracted.
  • Deletion of unused variables and unnecessary intermediate variables (memory saving and loop deletion in some cases).
  • Renaming of variables and subroutines to make everything clearer. In particular, the suffixes: '_avg' = average, '_start' = PCM start file, '_dev' = deviation, '_ini' or '0' = initial, '_dyn' = dynamical grid, '_timeseries' = daily average of last PCM year.
  • Cosmetic cleanings for readability.

JBC

File:
1 moved

Legend:

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

    r3570 r3571  
    1 MODULE recomp_tend_co2_slope_mod
     1MODULE recomp_tend_co2_mod
    22
    33implicit none
     
    88
    99SUBROUTINE recomp_tend_co2(ngrid,nslope,timelen,d_co2ice_phys,d_co2ice_ini,co2ice,emissivity, &
    10                            vmr_co2_PCM,vmr_co2_PEM,ps_PCM_2,global_avg_press_PCM,global_avg_press_new)
     10                           vmr_co2_PCM,vmr_co2_PEM,ps_PCM,ps_avg_global_ini,ps_avg_global)
    1111
    1212use constants_marspem_mod, only : alpha_clap_co2, beta_clap_co2, sigmaB, Lco2, sols_per_my, sec_per_sol
     
    2020!=======================================================================
    2121
    22 !   arguments:
    23 !   ----------
    24 !   INPUT
     22! Inputs
     23! ------
    2524integer,                        intent(in) :: timelen, ngrid, nslope
    26 real, dimension(ngrid,timelen), intent(in) :: vmr_co2_PCM          ! physical point field: Volume mixing ratio of co2 in the first layer
    27 real, dimension(ngrid,timelen), intent(in) :: vmr_co2_PEM          ! physical point field: Volume mixing ratio of co2 in the first layer
    28 real, dimension(ngrid,timelen), intent(in) :: ps_PCM_2             ! physical point field: Surface pressure in the PCM
    29 real,                           intent(in) :: global_avg_press_PCM ! global averaged pressure at previous timestep
    30 real,                           intent(in) :: global_avg_press_new ! global averaged pressure at current timestep
    31 real, dimension(ngrid,nslope),  intent(in) :: d_co2ice_ini         ! physical point field: Evolution of perennial ice over one year
    32 real, dimension(ngrid,nslope),  intent(in) :: co2ice               ! CO2 ice per mesh and sub-grid slope (kg/m^2)
    33 real, dimension(ngrid,nslope),  intent(in) :: emissivity           ! Emissivity per mesh and sub-grid slope(1)
    34 !   OUTPUT
     25real, dimension(ngrid,timelen), intent(in) :: vmr_co2_PCM       ! physical point field: Volume mixing ratio of co2 in the first layer
     26real, dimension(ngrid,timelen), intent(in) :: vmr_co2_PEM       ! physical point field: Volume mixing ratio of co2 in the first layer
     27real, dimension(ngrid,timelen), intent(in) :: ps_PCM            ! physical point field: Surface pressure in the PCM
     28real,                           intent(in) :: ps_avg_global_ini ! global averaged pressure at previous timestep
     29real,                           intent(in) :: ps_avg_global     ! global averaged pressure at current timestep
     30real, dimension(ngrid,nslope),  intent(in) :: d_co2ice_ini      ! physical point field: Evolution of perennial ice over one year
     31real, dimension(ngrid,nslope),  intent(in) :: co2ice            ! CO2 ice per mesh and sub-grid slope (kg/m^2)
     32real, dimension(ngrid,nslope),  intent(in) :: emissivity        ! Emissivity per mesh and sub-grid slope(1)
     33! Outputs
     34! -------
    3535real, dimension(ngrid,nslope), intent(inout) :: d_co2ice_phys ! physical point field: Evolution of perennial ice over one year
    3636
    37 !   local:
    38 !   ------
     37! Local:
     38! ------
    3939integer :: i, t, islope
    40 real    :: coef, ave
     40real    :: coef, avg
    4141
    4242write(*,*) "Update of the CO2 tendency from the current pressure"
     
    4646    do islope = 1,nslope
    4747        coef = sols_per_my*sec_per_sol*emissivity(i,islope)*sigmaB/Lco2
    48         ave = 0.
     48        avg = 0.
    4949        if (co2ice(i,islope) > 1.e-4 .and. abs(d_co2ice_phys(i,islope)) > 1.e-5) then
    5050            do t = 1,timelen
    51                 ave = ave + (beta_clap_co2/(alpha_clap_co2-log(vmr_co2_PCM(i,t)*ps_PCM_2(i,t)/100.)))**4 &
    52                       - (beta_clap_co2/(alpha_clap_co2-log(vmr_co2_PEM(i,t)*ps_PCM_2(i,t)*(global_avg_press_new/global_avg_press_PCM)/100.)))**4
     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
    5353            enddo
    54             if (ave < 1.e-4) ave = 0.
    55             d_co2ice_phys(i,islope) = d_co2ice_ini(i,islope) - coef*ave/timelen
     54            if (avg < 1.e-4) avg = 0.
     55            d_co2ice_phys(i,islope) = d_co2ice_ini(i,islope) - coef*avg/timelen
    5656        endif
    5757    enddo
     
    5959
    6060END SUBROUTINE recomp_tend_co2
     61!=======================================================================
    6162
    62 END MODULE recomp_tend_co2_slope_mod
     63SUBROUTINE recomp_tend_h2o(ngrid,nslope,timelen,d_h2oice,PCM_temp,PEM_temp)
     64
     65implicit none
     66
     67!=======================================================================
     68!
     69!  Routine that compute the evolution of the tendencie for h2o ice
     70!
     71!=======================================================================
     72
     73! Inputs
     74! ------
     75integer,            intent(in) :: timelen, ngrid, nslope
     76real, dimension(:), intent(in) :: PCM_temp, PEM_temp
     77! Outputs
     78! -------
     79real, dimension(ngrid,nslope), intent(inout) :: d_h2oice ! physical point field: Evolution of perennial ice over one year
     80
     81! Local:
     82! ------
     83
     84write(*,*) "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
     95END SUBROUTINE recomp_tend_h2o
     96
     97END MODULE recomp_tend_co2_mod
Note: See TracChangeset for help on using the changeset viewer.