Ignore:
Timestamp:
Dec 8, 2025, 11:27:43 AM (7 days ago)
Author:
jbclement
Message:

PEM:

  • Removing completely the ice metamorphism computed by a threshold at the end of the PCM (which was commented).
  • Addition of a module "metamorphism" to compute the PCM frost at the PEM beginning and give it back to the PCM at the PEM end. The frost is considered as the ice given by the PCM "startfi.nc" which is above the yearly minimum. Thereby, metamorphism is performed through this operation.
  • Ice reservoirs representation in the PEM is modernized.

JBC

File:
1 edited

Legend:

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

    r3977 r3983  
    1919contains
    2020!=======================================================================
    21 SUBROUTINE read_PCM_data(ngrid,nslope,nsoil_PCM,nsol,ps_avg,tsurf_avg,tsurf_avg_y1,tsoil_avg,tsoil_ts,watersurf_density_avg,d_h2oice,d_co2ice, &
    22                          ps_ts,q_h2o_ts,q_co2_ts,watersoil_density_ts)
    23 
    24 use compute_tend_mod, only: compute_tend
     21SUBROUTINE read_PCM_data(ngrid,nslope,nsoil_PCM,nsol,h2ofrost_PCM,co2frost_PCM,ps_avg,tsurf_avg,tsurf_avg_y1,tsoil_avg,tsoil_ts,watersurf_density_avg,d_h2oice,d_co2ice, &
     22                         ps_ts,q_h2o_ts,q_co2_ts,watersoil_density_ts,min_h2oice,min_co2ice)
     23
    2524use grid_conversion,  only: lonlat2vect
    2625use comsoil_h_PEM,    only: soil_pem
     26use compute_tend_mod, only: compute_tend
     27use metamorphism,     only: compute_frost
    2728
    2829implicit none
     
    3031! Arguments
    3132!----------
    32 integer, intent(in) :: ngrid, nslope, nsoil_PCM, nsol
     33integer,                       intent(in) :: ngrid, nslope, nsoil_PCM, nsol
     34real, dimension(ngrid,nslope), intent(in) :: h2ofrost_PCM, co2frost_PCM
    3335real, dimension(ngrid),                       intent(out) :: ps_avg
    34 real, dimension(ngrid,nslope),                intent(out) :: tsurf_avg, tsurf_avg_y1, watersurf_density_avg, d_h2oice, d_co2ice
     36real, dimension(ngrid,nslope),                intent(out) :: tsurf_avg, tsurf_avg_y1, watersurf_density_avg, d_h2oice, d_co2ice, min_h2oice, min_co2ice
    3537real, dimension(ngrid,nsoil_PCM,nslope),      intent(out) :: tsoil_avg
    3638real, dimension(ngrid,nsol),                  intent(out) :: ps_ts, q_h2o_ts, q_co2_ts
     
    4446real, dimension(:,:,:,:), allocatable :: var_read_4d
    4547character(:),             allocatable :: num ! For reading slope variables
    46 real, dimension(ngrid,nslope,2)       :: min_h2oice, min_co2ice, min_h2ofrost, min_co2frost
     48real, dimension(ngrid,nslope,2)       :: min_h2operice, min_co2perice, min_h2ofrost, min_co2frost
    4749
    4850! Code
    4951!-----
    5052! Initialization
    51 min_h2oice = 0.
    52 min_co2ice = 0.
     53min_h2operice = 0.
     54min_co2perice = 0.
    5355min_h2ofrost = 0.
    5456min_co2frost = 0.
     
    8082    call get_var('co2ice'//num,var_read_2d)          ; call lonlat2vect(nlon,nlat,ngrid,var_read_2d,min_co2frost(:,islope,1))
    8183    call get_var('h2o_ice_s'//num,var_read_2d)       ; call lonlat2vect(nlon,nlat,ngrid,var_read_2d,min_h2ofrost(:,islope,1))
    82     call get_var('watercap'//num,var_read_2d)        ; call lonlat2vect(nlon,nlat,ngrid,var_read_2d,min_h2oice(:,islope,1))
    83     call get_var('perennial_co2ice'//num,var_read_2d); call lonlat2vect(nlon,nlat,ngrid,var_read_2d,min_co2ice(:,islope,1))
     84    call get_var('watercap'//num,var_read_2d)        ; call lonlat2vect(nlon,nlat,ngrid,var_read_2d,min_h2operice(:,islope,1))
     85    call get_var('perennial_co2ice'//num,var_read_2d); call lonlat2vect(nlon,nlat,ngrid,var_read_2d,min_co2perice(:,islope,1))
    8486    call get_var('tsurf'//num,var_read_2d)           ; call lonlat2vect(nlon,nlat,ngrid,var_read_2d,tsurf_avg_y1(:,islope))
    8587enddo
     
    9597
    9698! Allocate and read the variables
    97 call get_var('ps',var_read_2d) ; call lonlat2vect(nlon,nlat,ngrid,var_read_2d,ps_avg)
     99call get_var('ps',var_read_2d); call lonlat2vect(nlon,nlat,ngrid,var_read_2d,ps_avg)
    98100do islope = 1,nslope
    99101    if (nslope /= 1) then
     
    105107    call get_var('co2ice'//num,var_read_2d)          ; call lonlat2vect(nlon,nlat,ngrid,var_read_2d,min_co2frost(:,islope,2))
    106108    call get_var('h2o_ice_s'//num,var_read_2d)       ; call lonlat2vect(nlon,nlat,ngrid,var_read_2d,min_h2ofrost(:,islope,2))
    107     call get_var('watercap'//num,var_read_2d)        ; call lonlat2vect(nlon,nlat,ngrid,var_read_2d,min_h2oice(:,islope,2))
    108     call get_var('perennial_co2ice'//num,var_read_2d); call lonlat2vect(nlon,nlat,ngrid,var_read_2d,min_co2ice(:,islope,2))
     109    call get_var('watercap'//num,var_read_2d)        ; call lonlat2vect(nlon,nlat,ngrid,var_read_2d,min_h2operice(:,islope,2))
     110    call get_var('perennial_co2ice'//num,var_read_2d); call lonlat2vect(nlon,nlat,ngrid,var_read_2d,min_co2perice(:,islope,2))
    109111    if (soil_pem) then
    110112        call get_var('soiltemp'//num,var_read_3d)
     
    167169
    168170!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
     171! Compute frost from yearly minima
     172call compute_frost(ngrid,nslope,h2ofrost_PCM,min_h2ofrost,co2frost_PCM,min_co2frost)
     173
     174!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
    169175! Compute ice tendencies from yearly minima
    170176write(*,*) '> Computing surface ice tendencies'
    171 call compute_tend(ngrid,nslope,min_h2ofrost + min_h2oice,d_h2oice)
     177call compute_tend(ngrid,nslope,min_h2operice + min_h2ofrost,d_h2oice)
    172178write(*,*) 'H2O ice tendencies (min/max):', minval(d_h2oice), maxval(d_h2oice)
    173 call compute_tend(ngrid,nslope,min_co2frost + min_co2ice,d_co2ice)
     179call compute_tend(ngrid,nslope,min_co2perice + min_co2frost,d_co2ice)
    174180write(*,*) 'CO2 ice tendencies (min/max):', minval(d_co2ice), maxval(d_co2ice)
    175181
Note: See TracChangeset for help on using the changeset viewer.