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

Last change on this file since 3778 was 3778, checked in by jbclement, 3 weeks ago

PEM:

  • New subroutine to detect whether there is subsurface ice or not
  • Rework of the initialization/update/finalization of the situation regarding the layering data structure
  • Introduction of a threshold 'h_patchy_dust' under which the top dust layer is not considered as a stratum
  • 'deposits' is renamed as 'layerings_map'
  • Few cleanings

JBC

File size: 6.0 KB
RevLine 
[3149]1MODULE pemredem
2
[2855]3!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
4!!!
[3149]5!!! Purpose: Write specific netcdf restart for the PEM
[2855]6!!!
[3149]7!!!
8!!! Author: LL, inspired by phyredem from the PCM
9!!!
[2855]10!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
[2794]11
12implicit none
13
[3149]14!=======================================================================
[2794]15contains
[3149]16!=======================================================================
[2794]17
[3206]18SUBROUTINE pemdem0(filename,lonfi,latfi,cell_area,ngrid,nslope,def_slope,subslope_dist)
[3149]19
[2794]20! create physics restart file and write time-independent variables
[3206]21use comsoil_h_PEM, only: mlayer_PEM
22use iostart_PEM,   only: open_restartphy, close_restartphy, put_var, put_field, length
[3149]23
24implicit none
[2794]25
[3149]26character(*),                  intent(in) :: filename
[3206]27integer,                       intent(in) :: ngrid, nslope
[3149]28real, dimension(ngrid),        intent(in) :: lonfi, latfi
29real, dimension(ngrid),        intent(in) :: cell_area     ! boundaries for bining of the slopes
[3313]30real, dimension(nslope + 1),   intent(in) :: def_slope     ! boundaries for bining of the slopes
[3149]31real, dimension(ngrid,nslope), intent(in) :: subslope_dist ! undermesh statistics
[2794]32
[3149]33! Create physics start file
34call open_restartphy(filename)
[2794]35
[3149]36! Write the mid-layer depths
37call put_var("soildepth","Soil mid-layer depth",mlayer_PEM)
[2888]38
[3149]39! Write longitudes
40call put_field("longitude","Longitudes of physics grid",lonfi)
[2888]41
[3149]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, &
[3778]60                   icetable_depth,icetable_thickness,ice_porefilling,m_co2_regolith,m_h2o_regolith,h2o_ice,layerings_map)
[3149]61
62! write time-dependent variable to restart file
63use iostart_PEM,   only: open_restartphy, close_restartphy, put_var, put_field
[3206]64use comsoil_h_PEM, only: inertiedat_PEM, soil_pem
[3149]65use time_evol_mod, only: year_bp_ini, convert_years
[3319]66use layering_mod,  only: layering, nb_str_max, stratif2array, print_layering, layering_algo
[3149]67
68implicit none
69
70character(*),                            intent(in) :: filename
[3498]71integer,                                 intent(in) :: nsoil_PEM, ngrid, nslope
72real,                                    intent(in) :: i_myear
[3149]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
[3571]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
[3493]77real, dimension(ngrid,nsoil_PEM,nslope), intent(in) :: ice_porefilling       ! under mesh bining according to slope
[3149]78real, dimension(ngrid,nsoil_PEM,nslope), intent(in) :: m_co2_regolith, m_h2o_regolith
79real, dimension(ngrid,nslope),           intent(in) :: h2o_ice
[3778]80type(layering), dimension(ngrid,nslope), intent(in) :: layerings_map ! Layerings
[2794]81
[3297]82integer                               :: islope
83character(2)                          :: num
84real                                  :: Year          ! Year of the simulation
85real, dimension(:,:,:,:), allocatable :: stratif_array ! Array for stratification (layerings)
[3039]86
[3149]87! Open file
88call open_restartphy(filename)
[2794]89
[3149]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)
[2794]95
[3319]96if (layering_algo) then
[3770]97    allocate(stratif_array(ngrid,nslope,nb_str_max,6))
[3778]98    call stratif2array(layerings_map,ngrid,nslope,stratif_array)
[3319]99    do islope = 1,nslope
100        write(num,fmt='(i2.2)') islope
[3770]101        call put_field('stratif_slope'//num//'_top_elevation','Layering top elevation',stratif_array(:,islope,:,1),Year)
102        call put_field('stratif_slope'//num//'_h_co2ice','Layering CO2 ice height',stratif_array(:,islope,:,2),Year)
103        call put_field('stratif_slope'//num//'_h_h2oice','Layering H2O ice height',stratif_array(:,islope,:,3),Year)
104        call put_field('stratif_slope'//num//'_h_dust','Layering dust height',stratif_array(:,islope,:,4),Year)
105        call put_field('stratif_slope'//num//'_h_pore','Layering pore height',stratif_array(:,islope,:,5),Year)
106        call put_field('stratif_slope'//num//'_icepore_volfrac','Layering ice pore volume fraction',stratif_array(:,islope,:,6),Year)
[3319]107    enddo
108    deallocate(stratif_array)
109endif
[3297]110
[3149]111if (soil_pem) then
112  ! Multidimensionnal variables (undermesh slope statistics)
113    do islope = 1,nslope
114        write(num,fmt='(i2.2)') islope
115        call put_field("tsoil_PEM_slope"//num,"Soil temperature by slope type",tsoil_slope_PEM(:,:,islope),Year)
116        call put_field("TI_PEM_slope"//num,"Soil Thermal Inertia by slope type",inertiesoil_slope_PEM(:,:,islope),Year)
[3571]117        call put_field("mco2_reg_ads_slope"//num, "Mass of CO2 adsorbed in the regolith",m_co2_regolith(:,:,islope),Year)
118        call put_field("mh2o_reg_ads_slope"//num, "Mass of H2O adsorbed in the regolith",m_h2o_regolith(:,:,islope),Year)
[3591]119        call put_field("ice_porefilling"//num,"Subsurface ice pore filling",ice_porefilling(:,:,islope),Year)
[3149]120    enddo
[3537]121    call put_field("icetable_depth","Depth of ice table",icetable_depth,Year)
122    call put_field("icetable_thickness","Depth of ice table",icetable_thickness,Year)
[3149]123    call put_field("inertiedat_PEM","Thermal inertie of PEM ",inertiedat_PEM,Year)
124endif ! soil_pem
[2794]125
[3149]126! Close file
127call close_restartphy
[2794]128
[3149]129END SUBROUTINE pemdem1
[2961]130
[3149]131END MODULE pemredem
Note: See TracBrowser for help on using the repository browser.