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

Last change on this file since 3985 was 3983, checked in by jbclement, 9 days ago

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 size: 6.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,ngrid,nslope,def_slope,subslope_dist)
19
20! create physics restart file and write time-independent variables
21use comsoil_h_PEM, only: mlayer_PEM
22use iostart_PEM,   only: open_restartphy, close_restartphy, put_var, put_field, length
23
24implicit none
25
26character(*),                  intent(in) :: filename
27integer,                       intent(in) :: ngrid, nslope
28real, dimension(ngrid),        intent(in) :: lonfi, latfi
29real, dimension(ngrid),        intent(in) :: cell_area     ! boundaries for bining of the slopes
30real, dimension(nslope + 1),   intent(in) :: def_slope     ! boundaries for bining of the slopes
31real, dimension(ngrid,nslope), intent(in) :: subslope_dist ! undermesh statistics
32
33! Create physics start file
34call open_restartphy(filename)
35
36! Write the mid-layer depths
37call put_var("soildepth","Soil mid-layer depth",mlayer_PEM)
38
39! Write longitudes
40call put_field("longitude","Longitudes of physics grid",lonfi)
41
42! Write latitudes
43call put_field("latitude","Latitudes of physics grid",latfi)
44
45! Write mesh areas
46call put_field("area","Mesh area",cell_area)
47
48! Multidimensionnal variables (nopcm undermesh slope statistics)
49call put_var("def_slope","slope criterium stages",def_slope)
50call put_field("subslope_dist","under mesh slope distribution",subslope_dist)
51
52! Close file
53call close_restartphy
54
55END SUBROUTINE pemdem0
56
57!=======================================================================
58
59SUBROUTINE pemdem1(filename,i_myear,nsoil_PEM,ngrid,nslope,tsoil_slope_PEM,inertiesoil_slope_PEM, &
60                   icetable_depth,icetable_thickness,ice_porefilling,m_co2_regolith,m_h2o_regolith,h2o_ice,co2_ice,layerings_map)
61
62! write time-dependent variable to restart file
63use iostart_PEM,   only: open_restartphy, close_restartphy, put_var, put_field
64use comsoil_h_PEM, only: inertiedat_PEM, soil_pem
65use time_evol_mod, only: year_bp_ini, convert_years
66use layering_mod,  only: layering, nb_str_max, stratif2array, print_layering, layering_algo
67
68implicit none
69
70character(*),                            intent(in) :: filename
71integer,                                 intent(in) :: nsoil_PEM, ngrid, nslope
72real,                                    intent(in) :: i_myear
73real, dimension(ngrid,nsoil_PEM,nslope), intent(in) :: tsoil_slope_PEM       ! under mesh bining according to slope
74real, dimension(ngrid,nsoil_PEM,nslope), intent(in) :: inertiesoil_slope_PEM ! under mesh bining according to slope
75real, dimension(ngrid,nslope),           intent(in) :: icetable_depth        ! under mesh bining according to slope
76real, dimension(ngrid,nslope),           intent(in) :: icetable_thickness    ! under mesh bining according to slope
77real, dimension(ngrid,nsoil_PEM,nslope), intent(in) :: ice_porefilling       ! under mesh bining according to slope
78real, dimension(ngrid,nsoil_PEM,nslope), intent(in) :: m_co2_regolith, m_h2o_regolith
79real, dimension(ngrid,nslope),           intent(in) :: h2o_ice, co2_ice
80type(layering), dimension(ngrid,nslope), intent(in) :: layerings_map ! Layerings
81
82integer                               :: islope
83character(2)                          :: num
84real                                  :: Year          ! Year of the simulation
85real, dimension(:,:,:,:), allocatable :: stratif_array ! Array for stratification (layerings)
86
87! Open file
88call open_restartphy(filename)
89
90! First variable to write must be "Time", in order to correctly
91! set time counter in file
92Year = (year_bp_ini + i_myear)*convert_years
93call put_var("Time","Year of simulation",Year)
94call put_field('h2o_ice','h2o_ice',h2o_ice,Year)
95call put_field('co2_ice','co2_ice',co2_ice,Year)
96
97if (layering_algo) then
98    allocate(stratif_array(ngrid,nslope,nb_str_max,6))
99    call stratif2array(layerings_map,ngrid,nslope,stratif_array)
100    do islope = 1,nslope
101        write(num,fmt='(i2.2)') islope
102        call put_field('stratif_slope'//num//'_top_elevation','Layering top elevation',stratif_array(:,islope,:,1),Year)
103        call put_field('stratif_slope'//num//'_h_co2ice','Layering CO2 ice height',stratif_array(:,islope,:,2),Year)
104        call put_field('stratif_slope'//num//'_h_h2oice','Layering H2O ice height',stratif_array(:,islope,:,3),Year)
105        call put_field('stratif_slope'//num//'_h_dust','Layering dust height',stratif_array(:,islope,:,4),Year)
106        call put_field('stratif_slope'//num//'_h_pore','Layering pore height',stratif_array(:,islope,:,5),Year)
107        call put_field('stratif_slope'//num//'_poreice_volfrac','Layering ice pore volume fraction',stratif_array(:,islope,:,6),Year)
108    enddo
109    deallocate(stratif_array)
110endif
111
112if (soil_pem) then
113  ! Multidimensionnal variables (undermesh slope statistics)
114    do islope = 1,nslope
115        write(num,fmt='(i2.2)') islope
116        call put_field("tsoil_PEM_slope"//num,"Soil temperature by slope type",tsoil_slope_PEM(:,:,islope),Year)
117        call put_field("TI_PEM_slope"//num,"Soil Thermal Inertia by slope type",inertiesoil_slope_PEM(:,:,islope),Year)
118        call put_field("mco2_reg_ads_slope"//num, "Mass of CO2 adsorbed in the regolith",m_co2_regolith(:,:,islope),Year)
119        call put_field("mh2o_reg_ads_slope"//num, "Mass of H2O adsorbed in the regolith",m_h2o_regolith(:,:,islope),Year)
120        call put_field("ice_porefilling"//num,"Subsurface ice pore filling",ice_porefilling(:,:,islope),Year)
121    enddo
122    call put_field("icetable_depth","Depth of ice table",icetable_depth,Year)
123    call put_field("icetable_thickness","Depth of ice table",icetable_thickness,Year)
124    call put_field("inertiedat_PEM","Thermal inertie of PEM ",inertiedat_PEM,Year)
125endif ! soil_pem
126
127! Close file
128call close_restartphy
129
130END SUBROUTINE pemdem1
131
132END MODULE pemredem
Note: See TracBrowser for help on using the repository browser.