source: trunk/LMDZ.COMMON/libf/evolution/pemredem.F90 @ 3170

Last change on this file since 3170 was 3149, checked in by jbclement, 15 months ago

PEM:

  • Simplification of the algorithm managing the stopping criteria;
  • Complete rework of the ice management in the PEM (H2O & CO2);

    Subroutines to evolve the H2O and CO2 ice are now in the same module "evol_ice_mod.F90".
    Tendencies are computed from the variation of "ice + frost" between the 2 PCM runs.
    Evolving ice in the PEM is now called 'h2o_ice' or 'co2_ice' (not anymore in 'qsurf' and free of 'water_reservoir').
    Default value 'ini_h2o_bigreservoir' (= 10 m) initializes the H2O ice of the first PEM run where there is 'watercap'. For the next PEM runs, initialization is done with the value kept in "startpem.nc". CO2 ice is taken from 'perennial_co2ice' of the PCM (paleoclimate flag must be true).
    Simplification of the condition to compute the surface ice cover needed for the stopping criteria.
    Frost ('qsurf') is not evolved by the PEM and given back to the PCM.
    New default threshold value 'inf_h2oice_threshold' (= 2 m) to decide at the end of the PEM run if the H2O ice should be 'watercap' or not for the next PCM runs. If H2O ice cannot be 'watercap', then the remaining H2O ice is transferred to the frost ('qsurf').

  • Renaming of variables/subroutines for clarity;
  • Some cleanings throughout the code;
  • Small updates in files of the deftank.

JBC

File size: 5.0 KB
Line 
1MODULE pemredem
2
3!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
4!!!
5!!! Purpose: Write specific netcdf restart for the PEM
6!!!
7!!!
8!!! Author: LL, inspired by phyredem from the PCM
9!!!
10!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
11
12implicit none
13
14!=======================================================================
15contains
16!=======================================================================
17
18SUBROUTINE pemdem0(filename,lonfi,latfi,cell_area,nsoil_PEM,ngrid,day_ini,time,nslope,def_slope,subslope_dist)
19
20! create physics restart file and write time-independent variables
21use comsoil_h_PEM,     only: soil_pem,mlayer_PEM,fluxgeo,inertiedat_PEM
22use iostart_PEM,       only: open_restartphy, close_restartphy, put_var, put_field, length
23use mod_grid_phy_lmdz, only: klon_glo
24use time_phylmdz_mod,  only: daysec
25
26#ifndef CPP_STD
27    use planete_h,    only: aphelie, emin_turb, lmixmin, obliquit, peri_day, periheli, year_day
28    use comcstfi_h,   only: g, mugaz, omeg, rad, rcp
29#else
30    use planete_mod,  only: apoastr, emin_turb, lmixmin, obliquit, peri_day, periastr, year_day
31    use comcstfi_mod, only: g, mugaz, omeg, rad, rcp
32#endif
33
34implicit none
35
36character(*),                  intent(in) :: filename
37integer,                       intent(in) :: nsoil_PEM, ngrid, nslope
38real, dimension(ngrid),        intent(in) :: lonfi, latfi
39real,                          intent(in) :: day_ini, time
40real, dimension(ngrid),        intent(in) :: cell_area     ! boundaries for bining of the slopes
41real, dimension(ngrid + 1),    intent(in) :: def_slope     ! boundaries for bining of the slopes
42real, dimension(ngrid,nslope), intent(in) :: subslope_dist ! undermesh statistics
43
44! Create physics start file
45call open_restartphy(filename)
46
47! Write the mid-layer depths
48call put_var("soildepth","Soil mid-layer depth",mlayer_PEM)
49
50! Write longitudes
51call put_field("longitude","Longitudes of physics grid",lonfi)
52
53! Write latitudes
54call put_field("latitude","Latitudes of physics grid",latfi)
55
56! Write mesh areas
57call put_field("area","Mesh area",cell_area)
58
59! Multidimensionnal variables (nopcm undermesh slope statistics)
60call put_var("def_slope","slope criterium stages",def_slope)
61call put_field("subslope_dist","under mesh slope distribution",subslope_dist)
62
63! Close file
64call close_restartphy
65
66END SUBROUTINE pemdem0
67
68!=======================================================================
69
70SUBROUTINE pemdem1(filename,i_myear,nsoil_PEM,ngrid,nslope,tsoil_slope_PEM,inertiesoil_slope_PEM, &
71                   ice_table_depth,ice_table_thickness,m_co2_regolith,m_h2o_regolith,h2o_ice)
72
73! write time-dependent variable to restart file
74use iostart_PEM,   only: open_restartphy, close_restartphy, put_var, put_field
75use comsoil_h_PEM, only: mlayer_PEM,fluxgeo, inertiedat_PEM, soil_pem
76use time_evol_mod, only: year_bp_ini, convert_years
77
78implicit none
79
80#ifndef CPP_STD
81    include "callkeys.h"
82#endif
83
84character(*),                            intent(in) :: filename
85integer,                                 intent(in) :: nsoil_PEM, ngrid, nslope, i_myear
86real, dimension(ngrid,nsoil_PEM,nslope), intent(in) :: tsoil_slope_PEM       ! under mesh bining according to slope
87real, dimension(ngrid,nsoil_PEM,nslope), intent(in) :: inertiesoil_slope_PEM ! under mesh bining according to slope
88real, dimension(ngrid,nslope),           intent(in) :: ice_table_depth       ! under mesh bining according to slope
89real, dimension(ngrid,nslope),           intent(in) :: ice_table_thickness   ! under mesh bining according to slope
90real, dimension(ngrid,nsoil_PEM,nslope), intent(in) :: m_co2_regolith, m_h2o_regolith
91real, dimension(ngrid,nslope),           intent(in) :: h2o_ice
92
93integer       :: islope
94character(2)  :: num
95integer       :: iq
96character(30) :: txt  ! To store some text
97real          :: Year ! Year of the simulation
98
99! Open file
100call open_restartphy(filename)
101
102! First variable to write must be "Time", in order to correctly
103! set time counter in file
104Year = (year_bp_ini + i_myear)*convert_years
105call put_var("Time","Year of simulation",Year)
106call put_field('h2o_ice','h2o_ice',h2o_ice,Year)
107
108if (soil_pem) then
109  ! Multidimensionnal variables (undermesh slope statistics)
110    do islope = 1,nslope
111        write(num,fmt='(i2.2)') islope
112        call put_field("tsoil_PEM_slope"//num,"Soil temperature by slope type",tsoil_slope_PEM(:,:,islope),Year)
113        call put_field("TI_PEM_slope"//num,"Soil Thermal Inertia by slope type",inertiesoil_slope_PEM(:,:,islope),Year)
114        call put_field("mco2_reg_ads_slope"//num, "Mass of co2 adsorbded in the regolith",m_co2_regolith(:,:,islope),Year)
115        call put_field("mh2o_reg_ads_slope"//num, "Mass of h2o adsorbded in the regolith",m_h2o_regolith(:,:,islope),Year)
116    enddo
117    call put_field("ice_table_depth","Depth of ice table",ice_table_depth,Year)
118    call put_field("ice_table_thickness","Depth of ice table",ice_table_thickness,Year)
119    call put_field("inertiedat_PEM","Thermal inertie of PEM ",inertiedat_PEM,Year)
120endif ! soil_pem
121
122! Close file
123call close_restartphy
124
125END SUBROUTINE pemdem1
126
127END MODULE pemredem
Note: See TracBrowser for help on using the repository browser.