source: tags/ORCHIDEE_4_1/ORCHIDEE/src_driver/forcesoil.f90 @ 7852

Last change on this file since 7852 was 6815, checked in by bertrand.guenet, 4 years ago

bug in the parallelization solved

File size: 45.4 KB
Line 
1! =================================================================================================================================
2! PROGRAM       : forcesoil
3!
4! CONTACT       : orchidee-help _at_ listes.ipsl.fr
5!
6! LICENCE       : IPSL (2006). This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC
7!
8!>\BRIEF        This subroutine runs the soilcarbon submodel using specific initial conditions
9!! and driving variables in order to obtain soil carbon stocks closed to the steady-state values
10!! quicker than when using the ''full'' ORCHIDEE. 
11!!     
12!!\n DESCRIPTION: None
13!! This subroutine computes the soil carbon stocks by calling the soilcarbon routine at each time step. \n
14!! The aim is to obtain soil carbon stocks closed to the steady-state values and ultimately to create 
15!! an updated stomate restart file for the stomate component. The state variables of the subsystem are the clay content
16!! (fixed value) and the soil carbon stocks. Initial conditions for the state variables are read in an 
17!! input stomate restart file. Driving variables are Soil carbon input, Water and Temperature stresses on
18!! Organic Matter decomposition. Driving variables are read from a specific forcing file produced by a former run of ORCHIDEE
19!! (SECHIBA+STOMATE). \n
20!! The FORCESOIL program first consists in reading a set of input files, allocating variables and
21!! preparing output stomate restart file. \n                                                             
22!! Then, a loop over time is performed in which the soilcarbon routine is called at each time step. \n
23!! Last, final values of the soil carbon stocks are written into the output stomate restart file. \n
24!!
25!! Flags related:
26!! OK_SOIL_CARBON_DISCRETIZATION yes/no(default)
27!! STOMATE_CFORCING netcdf filename(default: stomate_cforcing.nc)
28!!              Only if OK_SOIL_CARBON_DISCRETIZATION = y.
29!!              If set to NONE no output file will be created.
30!! FORCESOIL_STEP_PER_YEAR 1 to 366
31!! FORCESOIL_NB_YEAR  1 to *
32!!
33!! In order to create a carbon forcing file:
34!!   Run an orchidee_ol simulation.
35!!     Enable OK_SOIL_CARBON_DISCRETIZATION
36!!     Set a filename for the flag STOMATE_CFORCING
37!!     If required redefine FORCESOIL_STEP_PER_YEAR and FORCESOIL_NB_YEAR
38!!
39!!   The STOMATE_CFORCING file will keep the data for the latest period given by FORCESOIL_NB_YEAR.
40!!   By default it's 1 year.
41!!
42!! RECENT CHANGE(S): None
43!!
44!! REFERENCE(S) : None   
45!!
46!! FLOWCHART    : None
47!!
48!! SVN          :
49!! $HeadURL: $
50!! $Date: $
51!! $Revision: $
52!! \n
53!_ =================================================================================================================================
54
55PROGRAM forcesoil
56 
57  USE netcdf
58  !-
59  USE utils
60  USE defprec
61  USE constantes
62  USE constantes_var
63  USE constantes_mtc
64  USE constantes_soil
65  USE pft_parameters 
66  USE stomate_data
67  USE ioipsl_para
68  USE mod_orchidee_para
69  USE stomate_soil_carbon_discretization
70  USE stomate_io_soil_carbon_discretization
71  USE constantes_soil_var
72  USE stomate
73  USE vertical_soil , ONLY: vertical_soil_init
74  USE grid , ONLY : grid_init, regular_lonlat
75#ifdef CPP_PARA
76  USE mpi
77#endif
78  !-
79  IMPLICIT NONE
80  !-
81  !-
82  CHARACTER(LEN=80)                          :: sto_restname_in,sto_restname_out
83  INTEGER(i_std)                             :: iim,jjm                !! Indices (unitless)
84
85  INTEGER(i_std),PARAMETER                   :: llm = 1                !! Vertical Layers (requested by restini routine) (unitless)
86  INTEGER(i_std)                             :: kjpindex               !! Domain size (unitless)
87
88  INTEGER(i_std)                             :: itau_dep,itau_len      !! Time step read in the restart file (?)
89                                                                       !! and number of time steps of the simulation (unitless)
90  CHARACTER(LEN=30)                          :: time_str               !! Length of the simulation (year)
91  REAL(r_std)                                :: dt_files               !! time step between two successive itaus (?)
92                                                                       !! (requested by restini routine) (seconds)
93  REAL(r_std)                                :: date0                  !! Time at which itau = 0 (requested by restini routine) (?)
94  INTEGER(i_std)                             :: rest_id_sto            !! ID of the input restart file (unitless)
95  CHARACTER(LEN=20), SAVE                    :: thecalendar = 'noleap' !! Type of calendar defined in the input restart file
96                                                                       !! (unitless)
97  !-
98  CHARACTER(LEN=100)                         :: Cforcing_name          !! Name of the forcing file (unitless)
99  INTEGER                                    :: Cforcing_id            !! ID of the forcing file (unitless)
100  INTEGER                                    :: v_id                   !! ID of the variable 'Index' stored in the forcing file
101                                                                       !! (unitless)
102  REAL(r_std)                                :: dt_forcesoil           !! Time step at which soilcarbon routine is called (days)
103  INTEGER                                    :: nparan                 !! Number of values stored per year in the forcing file
104                                                                       !! (unitless)
105  INTEGER                                    :: nbyear
106  INTEGER(i_std),DIMENSION(:),ALLOCATABLE    :: indices                !! Grid Point Index used per processor (unitless)
107  INTEGER(i_std),DIMENSION(:),ALLOCATABLE    :: indices_g              !! Grid Point Index for all processor (unitless)
108  REAL(r_std),DIMENSION(:),ALLOCATABLE       :: x_indices_g            !! Grid Point Index for all processor (unitless)
109  REAL(r_std),DIMENSION(:,:),ALLOCATABLE     :: lon, lat               !! Longitude and Latitude of each grid point defined
110                                                                       !! in lat/lon (2D) (degrees)
111  REAL(r_std),DIMENSION(llm)                 :: lev                    !! Number of level (requested by restini routine) (unitless)
112
113
114  INTEGER                                    :: i,m,iatt,iv,iyear      !! counters (unitless)
115                                                                       
116  CHARACTER(LEN=100)                          :: var_name             
117  CHARACTER(LEN=8000)                        :: taboo_vars             !! string used for storing the name of the variables
118                                                                       !! of the stomate restart file that are not automatically
119                                                                       !! duplicated from input to output restart file (unitless)
120  REAL(r_std),DIMENSION(1)                   :: xtmp                   !! scalar read/written in restget/restput routines (unitless)
121  INTEGER(i_std),PARAMETER                   :: nbvarmax=1000           !! maximum # of variables assumed in the stomate restart file
122                                                                       !! (unitless)
123  INTEGER(i_std)                             :: nbvar                  !! # of variables effectively present
124                                                                       !! in the stomate restart file (unitless)
125  CHARACTER(LEN=1000),DIMENSION(nbvarmax)      :: varnames              !! list of the names of the variables stored
126                                                                       !! in the stomate restart file (unitless)
127  INTEGER(i_std)                             :: varnbdim               !! # of dimensions of a given variable
128                                                                       !! of the stomate restart file
129  INTEGER(i_std),PARAMETER                   :: varnbdim_max=20        !! maximal # of dimensions assumed for any variable
130                                                                       !! of the stomate restart file
131  INTEGER,DIMENSION(varnbdim_max)            :: vardims                !! length of each dimension of a given variable
132                                                                       !! of the stomate restart file
133  LOGICAL                                    :: l1d                    !! boolean : TRUE if all dimensions of a given variable
134                                                                       !! of the stomate restart file are of length 1 (ie scalar)
135                                                                       !! (unitless)
136  REAL(r_std)                                :: x_tmp                  !! temporary variable used to store return value
137  INTEGER(i_std)                               :: orch_vardims         !! Orchidee dimensions (different to IOIPSL -exclude time dim-)
138                                                                       !! from nf90_get_att (unitless)
139  CHARACTER(LEN=10)  :: part_str                                       !! string suffix indicating the index of a PFT
140  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:)  :: clay_g                 !! clay fraction (nbpglo) (unitless)
141  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:)  :: depth_organic_soil_g   !! Depth to organic soil (\f$m\f$)
142  REAL(r_std),DIMENSION(:,:,:),ALLOCATABLE   :: control_temp_g         !! Temperature control (nbp_glo,above/below,time) on OM decomposition
143                                                                       !! (unitless)
144  REAL(r_std),DIMENSION(:,:,:),ALLOCATABLE   :: control_moist_g        !! Moisture control (nbp_glo,abo/below,time) on OM decomposition
145                                                                       !! ?? Should be defined per PFT as well (unitless)
146  REAL(r_std),DIMENSION(:,:,:,:),ALLOCATABLE :: som_g                  !! Soil organic matter stocks (nbp_glo,ncarb,nvm,nelements) (\f$gC m^{-2}\f$)
147                                                                       
148  REAL(r_std),ALLOCATABLE :: clay(:)                                   !! clay fraction (nbp_loc) (unitless)
149  REAL(r_std),ALLOCATABLE :: depth_organic_soil(:)                     !! Depth to organic soil (\f$m\f$)
150  REAL(r_std),ALLOCATABLE :: som_input(:,:,:,:,:)                      !! soil organic matter input (nbp_loc,ncarb,nvm,nelements,time)
151                                                                       !! (\f$gC m^{-2} dt_forcesoil^{-1}\f$)
152  REAL(r_std),ALLOCATABLE :: control_temp(:,:,:)                       !! Temperature control (nbp_loc,above/below,time) on OM decomposition
153                                                                       !! (unitless)
154  REAL(r_std),ALLOCATABLE :: control_moist(:,:,:)                      !! Moisture control (nbp_loc,abo/below,time) on OM decomposition
155                                                                       !! ?? Should be defined per PFT as well (unitless)
156  REAL(r_std),ALLOCATABLE :: som(:,:,:,:)                              !! Soil organic matter stocks (nbp_loc,ncarb,nvm,nelements) (\f$gC m^{-2}\f$)
157  REAL(r_std),DIMENSION(:,:),ALLOCATABLE     :: resp_hetero_soil       !! Heterotrophic respiration (\f$gC m^{-2} dt_forcesoil^{-1}\f$)
158                                                                       !! (requested by soilcarbon routine but not used here)
159  REAL(r_std),DIMENSION(:,:,:),ALLOCATABLE   :: n_mineralisation       !! net nitrogen mineralisation of decomposing SOM
160  INTEGER(i_std)                             :: printlev_loc           !! Local write level                                                                     
161  INTEGER(i_std)                             :: ier,iret               !! Used for hangling errors
162                                                                       
163  CHARACTER(LEN=50) :: temp_name                                       
164  CHARACTER(LEN=100) :: msg3                                       
165  LOGICAL :: debug                                                     !! boolean used for printing messages
166  LOGICAL :: l_error                                                   !! boolean for memory allocation
167  ! allocateable arrays needed for permafrost carbon
168  REAL(r_std),DIMENSION(:,:,:,:),ALLOCATABLE  :: deepSOM_a_g           !! active organic matter concentration
169  REAL(r_std),DIMENSION(:,:,:,:),ALLOCATABLE  :: deepSOM_s_g           !! slow organic matter concentration 
170  REAL(r_std),DIMENSION(:,:,:,:),ALLOCATABLE  :: deepSOM_p_g           !! passive matter concentration
171  REAL(r_std),DIMENSION(:,:,:),ALLOCATABLE  :: O2_soil_g               !! oxygen in the soil
172  REAL(r_std),DIMENSION(:,:,:),ALLOCATABLE  :: CH4_soil_g              !! methane in the soil
173  REAL(r_std),DIMENSION(:,:,:),ALLOCATABLE  :: O2_snow_g               !! oxygen in the snow
174  REAL(r_std),DIMENSION(:,:,:),ALLOCATABLE  :: CH4_snow_g              !! methane in the snow
175  REAL(r_std),DIMENSION(:,:,:),ALLOCATABLE :: snowdz_g                 !! snow depth at each layer
176  REAL(r_std),DIMENSION(:,:,:),ALLOCATABLE :: snowrho_g                !! snow density at each layer
177  REAL(r_std),DIMENSION(:,:,:,:),ALLOCATABLE  :: deepSOM_a             !! active organic matter concentration
178  REAL(r_std),DIMENSION(:,:,:,:),ALLOCATABLE  :: deepSOM_s             !! slow organic matter concentration
179  REAL(r_std),DIMENSION(:,:,:,:),ALLOCATABLE  :: deepSOM_p             !! passive organic matter concentration
180  REAL(r_std),DIMENSION(:,:,:),ALLOCATABLE  :: O2_soil                 !! oxygen in the soil
181  REAL(r_std),DIMENSION(:,:,:),ALLOCATABLE  :: CH4_soil                !! methane in the soil
182  REAL(r_std),DIMENSION(:,:,:),ALLOCATABLE  :: O2_snow                 !! oxygen in the snow
183  REAL(r_std),DIMENSION(:,:,:),ALLOCATABLE  :: CH4_snow                !! methane in the snow
184  REAL(r_std),DIMENSION(:,:),ALLOCATABLE  :: pb                        !! surface pressure
185  REAL(r_std),DIMENSION(:,:),ALLOCATABLE  :: snow                      !! snow mass
186  REAL(r_std),DIMENSION(:,:,:,:),ALLOCATABLE  :: tprof                 !! deep soil temperature profile
187  REAL(r_std),DIMENSION(:,:,:,:),ALLOCATABLE  :: fbact                 !! factor for soil organic matter decomposition
188  REAL(r_std),DIMENSION(:,:,:,:),ALLOCATABLE  :: hslong                !! deep soil humidity
189  REAL(r_std),DIMENSION(:,:,:),ALLOCATABLE  :: veget_max               !! maximum vegetation fraction
190  REAL(r_std),DIMENSION(:,:,:),ALLOCATABLE  :: rprof                   !! PFT rooting depth
191  REAL(r_std),DIMENSION(:,:),ALLOCATABLE  :: tsurf                     !! surface temperature
192  REAL(r_std),DIMENSION(:,:,:),ALLOCATABLE :: snowrho                  !! snow density
193  REAL(r_std),DIMENSION(:,:,:),ALLOCATABLE :: snowdz                   !! snow depth
194  REAL(r_std),DIMENSION(:,:),ALLOCATABLE      :: lalo                  !! Geogr. coordinates (latitude,longitude) (degrees)   
195  REAL(r_std), DIMENSION(:,:,:), ALLOCATABLE    :: heat_Zimov                 !! heating associated with decomposition  [W/m**3 soil]
196  REAL(R_STD), DIMENSION(:), ALLOCATABLE      :: sfluxCH4_deep, sfluxCO2_deep !! [g / m**2]
197  REAL(R_STD), DIMENSION(:,:), ALLOCATABLE      :: altmax                     !! active layer thickness (m)
198  REAL(R_STD), DIMENSION(:,:), ALLOCATABLE      :: altmax_g                   !! global active layer thickness (m)
199  REAL(r_std), DIMENSION(:,:,:,:),  ALLOCATABLE  :: som_surf_g
200  REAL(r_std), DIMENSION(:,:,:,:),  ALLOCATABLE  :: som_surf                 !! vertically-integrated (diagnostic) soil organic matter pools: active, slow, or passive, (gC/(m**2 of ground))
201  REAL(R_STD), ALLOCATABLE, DIMENSION(:,:)      :: fixed_cryoturbation_depth  !! depth to hold cryoturbation to for fixed runs
202  REAL(R_STD), ALLOCATABLE, DIMENSION(:,:,:,:)  :: CN_target  !! C to N ratio of SOM flux from one pool to another (gN m-2 dt-1)
203  LOGICAL, SAVE                             :: satsoil = .FALSE.
204  LOGICAL                                   :: reset_soilc = .false.
205
206  INTEGER(i_std)                            :: start_2d(2), count_2d(2) 
207  INTEGER(i_std)                            :: start_5d(5), count_5d(5), start_4d(4), count_4d(4), start_3d(3), count_3d(3)
208!_ =================================================================================================================================
209 
210  CALL Init_orchidee_para
211  CALL init_timer
212
213! Set specific write level to forcesoil using PRINTLEV_forcesoil=[0-4] in run.def.
214! The global printlev is used as default value.
215  printlev_loc=get_printlev('forcesoil')
216
217!-
218! Configure the number of PFTS
219!-
220  ok_soil_carbon_discretization=.FALSE. 
221  CALL getin_p('OK_SOIL_CARBON_DISCRETIZATION',ok_soil_carbon_discretization)
222
223  IF (.NOT. ok_soil_carbon_discretization) THEN
224     CALL ipslerr_p(3,'forcesoil','OK_SOIL_CARBON_DISCRETIZATION must be enabled','But found:','True')
225  ENDIF
226
227  ! 1. Read the number of PFTs
228  !
229  !Config Key   = NVM
230  !Config Desc  = number of PFTs 
231  !Config If    = OK_SECHIBA or OK_STOMATE
232  !Config Def   = 13
233  !Config Help  = The number of vegetation types define by the user
234  !Config Units = [-]
235  CALL getin_p('NVM',nvm)
236
237  ! 2. Allocation
238  ALLOCATE(pft_to_mtc(nvm),stat=ier)
239  IF (ier /= 0) CALL ipslerr_p(3, 'forcesoil', 'pft_to_mtc : error in memory allocation', '', '')
240
241  ! 3. Initialisation of the correspondance table
242  pft_to_mtc(:) = undef_int
243 
244  ! 4.Reading of the conrrespondance table in the .def file
245  !
246  !Config Key   = PFT_TO_MTC
247  !Config Desc  = correspondance array linking a PFT to MTC
248  !Config if    = OK_SECHIBA or OK_STOMATE
249  !Config Def   = 1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11, 12, 13
250  !Config Help  =
251  !Config Units = [-]
252  CALL getin_p('PFT_TO_MTC',pft_to_mtc)
253
254  ! 4.1 if nothing is found, we use the standard configuration
255  IF(nvm <= nvmc ) THEN
256     IF(pft_to_mtc(1) == undef_int) THEN
257        WRITE(numout,*) 'Note to the user : we will use ORCHIDEE to its standard configuration'
258        pft_to_mtc(:) = (/ 1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11, 12, 13 /)
259     ENDIF
260  ELSE   
261     IF(pft_to_mtc(1) == undef_int) THEN
262        WRITE(numout,*)' The array PFT_TO_MTC is empty : we stop'
263     ENDIF
264  ENDIF
265 
266  ! 4.2 What happened if pft_to_mtc(j) > nvmc (if the mtc doesn't exist)?
267  DO i = 1, nvm
268     IF(pft_to_mtc(i) > nvmc) THEN
269        CALL ipslerr_p(3, 'forcesoil', 'the MTC you chose doesnt exist', 'we stop reading pft_to_mtc', '')
270     ENDIF
271  ENDDO
272 
273  ! 4.3 Check if pft_to_mtc(1) = 1
274  IF(pft_to_mtc(1) /= 1) THEN
275     CALL ipslerr_p(3, 'forcesoil', 'the first pft has to be the bare soil', 'we stop reading next values of pft_to_mtc', '')
276  ENDIF
277
278  DO i = 2,nvm
279     IF(pft_to_mtc(i) == 1) THEN
280        CALL ipslerr_p(3, 'forcesoil', 'only pft_to_mtc(1) has to be the bare soil', 'we stop reading next values of pft_to_mtc', '')
281     ENDIF
282  ENDDO
283 
284  ! 5. Allocate and initialize natural and is_c4
285 
286  ! 5.1 Memory allocation
287  ALLOCATE(natural(nvm),stat=ier)
288  IF (ier /= 0) CALL ipslerr_p(3, 'forcesoil', 'natural : error in memory allocation', '', '')
289
290  ALLOCATE(is_c4(nvm),stat=ier)
291  IF (ier /= 0) CALL ipslerr_p(3, 'forcesoil', 'is_c4 : error in memory allocation', '', '')
292
293!  ALLOCATE(permafrost_veg_exists(nvm),stat=ier)
294!  IF (ier /= 0) CALL ipslerr_p(3, 'forcesoil', 'permafrost_veg_exists : error in memory allocation', '', '')
295
296  ! 5.2 Initialisation
297  DO i = 1, nvm
298     natural(i) = natural_mtc(pft_to_mtc(i))
299     is_c4(i) = is_c4_mtc(pft_to_mtc(i))
300  ENDDO
301
302!  DO i = 1, nvm
303!     permafrost_veg_exists(i) = permafrost_veg_exists_mtc(pft_to_mtc(i))
304!  ENDDO
305  !!-
306  !! 1. Initialisation stage
307  !! Reading a set of input files, allocating variables and preparing output restart file.     
308  !!-
309  ! Define restart file name
310  ! for reading initial conditions (sto_restname_in var) and for writting final conditions (sto_restname_out var).
311  ! User values are used if present in the .def file.
312  ! If not present, default values (stomate_start.nc and stomate_rest_out.c) are used.
313  !-
314  IF (is_root_prc) THEN
315     sto_restname_in = 'stomate_start.nc'
316     CALL getin ('STOMATE_RESTART_FILEIN',sto_restname_in)
317     WRITE(numout,*) 'STOMATE INPUT RESTART_FILE: ',TRIM(sto_restname_in)
318     sto_restname_out = 'stomate_rest_out.nc'
319     CALL getin ('STOMATE_RESTART_FILEOUT',sto_restname_out)
320     WRITE(numout,*) 'STOMATE OUTPUT RESTART_FILE: ',TRIM(sto_restname_out)
321     CALL getin ('satsoil', satsoil)
322     !-
323     ! Open the input file and Get some Dimension and Attributes ID's
324     !-
325     CALL nccheck( NF90_OPEN (sto_restname_in, NF90_NOWRITE, rest_id_sto))
326     CALL nccheck( NF90_INQUIRE_DIMENSION (rest_id_sto,1,len=iim_g))
327     CALL nccheck( NF90_INQUIRE_DIMENSION (rest_id_sto,2,len=jjm_g))
328     CALL nccheck( NF90_INQ_VARID (rest_id_sto, "time", iv))
329     CALL nccheck( NF90_GET_ATT (rest_id_sto, iv, 'calendar',thecalendar))
330     CALL nccheck( NF90_CLOSE (rest_id_sto))
331     i=INDEX(thecalendar,ACHAR(0))
332     IF ( i > 0 ) THEN
333        thecalendar(i:20)=' '
334     ENDIF
335     !-
336     ! Allocate longitudes and latitudes
337     !-
338     ALLOCATE (lon(iim_g,jjm_g), stat=ier)
339     IF (ier /= 0) CALL ipslerr(3, 'forcesoil', 'lon : error in memory allocation', '', '')
340     ALLOCATE (lat(iim_g,jjm_g), stat=ier)
341     IF (ier /= 0) CALL ipslerr(3, 'forcesoil', 'lat : error in memory allocation', '', '')
342     lon(:,:) = zero
343     lat(:,:) = zero
344     lev(1)   = zero
345     !-
346     CALL restini &
347          & (sto_restname_in, iim_g, jjm_g, lon, lat, llm, lev, &
348          &  sto_restname_out, itau_dep, date0, dt_files, rest_id_sto, &
349          &  use_compression=nc_restart_compression )
350  ENDIF
351
352  CALL bcast(date0)
353  CALL bcast(thecalendar)
354  WRITE(numout,*) "calendar = ",thecalendar
355  !-
356  ! calendar
357  !-
358  CALL ioconf_calendar (thecalendar)
359  CALL ioget_calendar  (one_year,one_day)
360  CALL ioconf_startdate(date0)
361  !
362  !-
363  ! define forcing file's name (Cforcing_name var)
364  ! User value is used if present in the .def file
365  ! If not, default (NONE) is used
366  !-
367  Cforcing_name = 'stomate_cforcing.nc'
368  CALL getin ('STOMATE_CFORCING_NAME',Cforcing_name)
369  !
370  IF (TRIM(Cforcing_name) .EQ. 'NONE') THEN
371    CALL ipslerr_p(3,'forcesoil','STOMATE_CFORCING_NAME key must be defined with a filename',&
372            'But found:',Cforcing_name)
373  ENDIF
374  !-
375  ! Initailize ngrnd
376  !-
377  CALL vertical_soil_init()
378  !-
379  ! Disable XIOS outputs for spinup
380  !-
381  soilc_isspinup = .TRUE.
382  !
383  !! For master process only
384  !
385  IF (is_root_prc) THEN
386     !-
387     ! Open FORCESOIL's forcing file to read some basic info (dimensions, variable ID's)
388     ! and allocate variables.
389     !-
390#ifdef CPP_PARA
391     CALL nccheck( NF90_OPEN (TRIM(Cforcing_name),IOR(NF90_NOWRITE, NF90_MPIIO),Cforcing_id, &
392         & comm = MPI_COMM_ORCH, info = MPI_INFO_NULL ))
393#else
394     CALL nccheck( NF90_OPEN (TRIM(Cforcing_name),NF90_NOWRITE,Cforcing_id))
395#endif
396     !-
397     ! Total Domain size is stored in nbp_glo variable
398     !-
399     CALL nccheck( NF90_GET_ATT (Cforcing_id,NF90_GLOBAL,'kjpindex',x_tmp))
400     nbp_glo = NINT(x_tmp)
401     !-
402     ! Number of values stored per year in the forcing file is stored in nparan var.
403     !-
404     CALL nccheck( NF90_GET_ATT (Cforcing_id,NF90_GLOBAL,'nparan',x_tmp))
405     nparan = NINT(x_tmp)
406     CALL nccheck( NF90_GET_ATT (Cforcing_id,NF90_GLOBAL,'nbyear',x_tmp))
407     nbyear = NINT(x_tmp)
408     !-
409     ALLOCATE (indices_g(nbp_glo), stat=ier)
410     IF (ier /= 0) CALL ipslerr(3, 'forcesoil', 'indices_g : error in memory allocation', '', '')
411     ALLOCATE (clay_g(nbp_glo), stat=ier)
412     IF (ier /= 0) CALL ipslerr(3, 'forcesoil', 'clay_g : error in memory allocation', '', '')
413     ALLOCATE (depth_organic_soil_g(nbp_glo), stat=ier)
414     IF (ier /= 0) CALL ipslerr(3, 'forcesoil', 'depth_organic_soil_g : error in memory allocation', '', '')
415     !-
416     ALLOCATE (x_indices_g(nbp_glo),stat=ier)
417     IF (ier /= 0) CALL ipslerr(3, 'forcesoil', 'x_indices_g : error in memory allocation', '', '')
418     CALL nccheck( NF90_INQ_VARID (Cforcing_id,'index',v_id))
419     CALL nccheck( NF90_GET_VAR   (Cforcing_id,v_id,x_indices_g))
420     indices_g(:) = NINT(x_indices_g(:))
421     WRITE(numout,*) mpi_rank,"indices globaux : ",indices_g
422     DEALLOCATE (x_indices_g)
423     !-
424     CALL nccheck( NF90_INQ_VARID (Cforcing_id,'clay',v_id))
425     CALL nccheck( NF90_GET_VAR   (Cforcing_id,v_id,clay_g))
426     CALL nccheck( NF90_INQ_VARID (Cforcing_id,'depth_organic_soil',v_id))
427     CALL nccheck( NF90_GET_VAR   (Cforcing_id,v_id,depth_organic_soil_g))
428     !-
429     ! time step of forcesoil program (in days)
430     !-
431     dt_forcesoil = one_year / FLOAT(nparan)
432     WRITE(numout,*) 'time step (d): ',dt_forcesoil
433     WRITE(numout,*) 'nparan: ',nparan
434     WRITE(numout,*) 'nbyear: ',nbyear   
435     !-
436     ! read and write the variables in the output restart file we do not modify within the Forcesoil program
437     ! ie all variables stored in the input restart file except those stored in taboo_vars
438     !-
439     !-
440     taboo_vars = '$nav_lon$ $nav_lat$ $nav_lev$ $time$ $time_steps$ '// &
441     &            '$day_counter$ $dt_days$ $date$ $deepSOM_a$ $deepSOM_s$ '// &
442     &            '$deepSOM_p$ $O2_soil$ $CH4_soil$ $O2_snow$ $CH4_snow$ '// &
443     &            '$altmax$ ' 
444     !-
445     !-
446     CALL ioget_vname(rest_id_sto, nbvar, varnames)
447     !-
448     ! read and write some special variables (1D or variables that we need)
449     !-
450     CALL restransfer (rest_id_sto, 'day_counter', itau_dep)
451     !-
452     CALL restransfer (rest_id_sto, 'dt_days', itau_dep)
453     !-
454     CALL restransfer (rest_id_sto, 'date', itau_dep)
455     !-
456     DO iv=1,nbvar
457        !-- check if the variable is to be written here
458        IF (INDEX(taboo_vars,'$'//TRIM(varnames(iv))//'$') == 0 ) THEN
459
460           CALL restransfer(rest_id_sto, TRIM(varnames(iv)), itau_dep, nbp_glo, indices_g)
461         
462        ENDIF ! INDEX(taboo_vars,'$'//TRIM(varnames(iv))//'$') == 0 )
463     ENDDO
464     ! Length of the run (in Years)
465     ! User value is used if present in the .def file
466     ! If not, default value (10000 Years) is used
467     !-
468     WRITE(time_str,'(a)') '10000Y'
469     CALL getin('TIME_LENGTH', time_str)
470     write(numout,*) 'Number of years for som spinup : ',time_str
471     ! transform into itau
472     CALL tlen2itau(time_str, dt_forcesoil*one_day, date0, itau_len)
473     write(numout,*) 'Number of time steps to do: ',itau_len
474
475     ! read soil organic matter stocks values stored in the input restart file
476     !-
477     !-
478     ! Permafrost soil organic matter
479     !-
480      ALLOCATE(som_g(nbp_glo,ncarb,nvm,nelements), stat=ier)
481      IF (ier /= 0) CALL ipslerr(3, 'forcesoil', 'som_g : error in memory allocation', '', '')
482      som_g(:,:,:,:) = 0.
483      ALLOCATE(som_surf_g(nbp_glo,ncarb,nvm,nelements), stat=ier)
484      IF (ier /= 0) CALL ipslerr(3, 'forcesoil', 'som_surf_g : error in memory allocation', '', '')
485      som_surf_g(:,:,:,:) = 0.
486      ALLOCATE(deepSOM_a_g(nbp_glo,ngrnd,nvm,nelements), stat=ier)
487      IF (ier /= 0) CALL ipslerr(3, 'forcesoil', 'deepSOM_a_g : error in memory allocation', '', '')
488      ALLOCATE(deepSOM_s_g(nbp_glo,ngrnd,nvm,nelements), stat=ier)
489      IF (ier /= 0) CALL ipslerr(3, 'forcesoil', 'deepSOM_s_g : error in memory allocation', '', '')
490      ALLOCATE(deepSOM_p_g(nbp_glo,ngrnd,nvm,nelements), stat=ier)
491      IF (ier /= 0) CALL ipslerr(3, 'forcesoil', 'deepSOM_p_g : error in memory allocation', '', '')
492      ALLOCATE(O2_soil_g(nbp_glo,ngrnd,nvm), stat=ier)
493      IF (ier /= 0) CALL ipslerr(3, 'forcesoil', 'O2_soil_g : error in memory allocation', '', '')
494      ALLOCATE(CH4_soil_g(nbp_glo,ngrnd,nvm), stat=ier)
495      IF (ier /= 0) CALL ipslerr(3, 'forcesoil', 'CH4_soil_g : error in memory allocation', '', '')
496      ALLOCATE(O2_snow_g(nbp_glo,nsnow,nvm), stat=ier)
497      IF (ier /= 0) CALL ipslerr(3, 'forcesoil', 'O2_snow_g : error in memory allocation', '', '')
498      ALLOCATE(CH4_snow_g(nbp_glo,nsnow,nvm), stat=ier)
499      IF (ier /= 0) CALL ipslerr(3, 'forcesoil', 'CH4_snow_g : error in memory allocation', '', '')
500      ALLOCATE(altmax_g(nbp_glo,nvm), stat=ier)
501      IF (ier /= 0) CALL ipslerr(3, 'forcesoil', 'altmax_g : error in memory allocation', '', '')
502
503      deepSOM_a_g(:,:,:,:) = val_exp
504      CALL restget (rest_id_sto, 'deepSOM_a', nbp_glo, ngrnd, nvm, nelements, itau_dep, &
505            &               .TRUE., deepSOM_a_g, 'gather', nbp_glo, indices_g)
506      IF (ALL(deepSOM_a_g == val_exp)) deepSOM_a_g = zero
507
508      deepSOM_s_g(:,:,:,:) = val_exp
509      CALL restget (rest_id_sto, 'deepSOM_s', nbp_glo, ngrnd, nvm, nelements, itau_dep, &
510            &               .TRUE., deepSOM_s_g, 'gather', nbp_glo, indices_g)
511      IF (ALL(deepSOM_s_g == val_exp)) deepSOM_s_g = zero
512     
513      deepSOM_p_g(:,:,:,:) = val_exp
514      CALL restget (rest_id_sto, 'deepSOM_p', nbp_glo, ngrnd, nvm, nelements, itau_dep, &
515           &               .TRUE., deepSOM_p_g, 'gather', nbp_glo, indices_g)
516      IF (ALL(deepSOM_p_g == val_exp)) deepSOM_p_g = zero
517
518      var_name= 'altmax'
519      altmax_g(:,:) = val_exp
520      CALL restget (rest_id_sto, var_name, nbp_glo, nvm, 1, itau_dep, .TRUE., altmax_g, "gather", nbp_glo, indices_g)
521      IF ( ALL( altmax_g(:,:) .EQ. val_exp ) ) THEN
522          CALL ipslerr(3, 'forcesoil', 'altmax is not found in stomate restart file', '', '')
523      END IF
524
525      CALL getin('reset_soilc', reset_soilc)
526      IF (reset_soilc) THEN
527          CALL ipslerr(1, 'forcesoil', 'deepSOM_a, deepSOM_s and deeSOM_p',  & 
528                       'are ignored and set to zero value due to', 'reset_soilc option')
529         deepSOM_a_g(:,:,:,:) = zero
530         deepSOM_s_g(:,:,:,:) = zero
531         deepSOM_p_g(:,:,:,:) = zero
532      ENDIF
533     
534      O2_soil_g(:,:,:) = val_exp
535      CALL restget (rest_id_sto, 'O2_soil', nbp_glo, ngrnd, nvm, itau_dep, &
536           &               .TRUE., O2_soil_g, 'gather', nbp_glo, indices_g)
537      IF (ALL(O2_soil_g == val_exp)) O2_soil_g = O2_init_conc
538
539      CH4_soil_g(:,:,:) = val_exp
540      CALL restget (rest_id_sto, 'CH4_soil', nbp_glo, ngrnd, nvm, itau_dep, &
541          &               .TRUE., CH4_soil_g, 'gather', nbp_glo, indices_g)
542      IF (ALL(CH4_soil_g == val_exp)) CH4_soil_g =  CH4_init_conc
543
544      O2_snow_g(:,:,:) = val_exp
545      CALL restget (rest_id_sto, 'O2_snow', nbp_glo, nsnow, nvm, itau_dep, &
546           &               .TRUE., O2_snow_g, 'gather', nbp_glo, indices_g)
547      IF (ALL(O2_snow_g == val_exp)) O2_snow_g =  O2_init_conc
548
549      CH4_snow_g(:,:,:) = val_exp
550      CALL restget (rest_id_sto, 'CH4_snow', nbp_glo, nsnow, nvm, itau_dep, &
551          &               .TRUE., CH4_snow_g, 'gather', nbp_glo, indices_g)
552      IF (ALL(CH4_snow_g == val_exp)) CH4_snow_g = CH4_init_conc
553  ENDIF ! is_root_prc
554  !
555  CALL bcast(nbp_glo)
556  CALL bcast(iim_g)
557  CALL bcast(jjm_g)
558  IF (.NOT. ALLOCATED(indices_g)) ALLOCATE (indices_g(nbp_glo))
559  CALL bcast(indices_g)
560  CALL bcast(nparan)
561  CALL bcast(nbyear)
562  CALL bcast(dt_forcesoil)
563  CALL bcast(itau_dep)
564  CALL bcast(itau_len)
565  !
566  ! we must initialize data_para :
567  CALL init_orchidee_data_para_driver(nbp_glo,indices_g)
568
569  kjpindex=nbp_loc
570  jjm=jj_nb
571  iim=iim_g
572  IF (printlev_loc>=3) WRITE(numout,*) "Local grid : ",kjpindex,iim,jjm
573  !-
574  ! Initialize grid type
575  !-
576  CALL grid_init ( kjpindex, 4, regular_lonlat, "ForcingGrid" )
577  !-
578  ! Analytical spinup is set to false
579  !
580  spinup_analytic = .FALSE.
581  !-
582  ! read soil organic matter inputs, water and temperature stresses on OM
583  ! decomposition
584  ! into the forcing file - We read an average year.
585  !-
586  !-
587  ! Read permafrost-related soil organic matter from Cforcing_id
588  !-
589  ALLOCATE(pb(kjpindex,nparan*nbyear), stat=ier)
590  IF (ier /= 0) CALL ipslerr(3, 'forcesoil', 'pb : error in memory allocation', '', '')
591  ALLOCATE(snow(kjpindex,nparan*nbyear), stat=ier)
592  IF (ier /= 0) CALL ipslerr(3, 'forcesoil', 'snow : error in memory allocation', '', '')
593  ALLOCATE(tprof(kjpindex,ngrnd,nvm,nparan*nbyear), stat=ier)
594  IF (ier /= 0) CALL ipslerr(3, 'forcesoil', 'tprof : error in memory allocation', '', '')
595  ALLOCATE(fbact(kjpindex,ngrnd,nvm,nparan*nbyear), stat=ier)
596  IF (ier /= 0) CALL ipslerr(3, 'forcesoil', 'fbact : error in memory allocation', '', '')
597  ALLOCATE(hslong(kjpindex,ngrnd,nvm,nparan*nbyear), stat=ier)
598  IF (ier /= 0) CALL ipslerr(3, 'forcesoil', 'hslong : error in memory allocation', '', '')
599  ALLOCATE(veget_max(kjpindex,nvm,nparan*nbyear), stat=ier)
600  IF (ier /= 0) CALL ipslerr(3, 'forcesoil', 'veget_max : error in memory allocation', '', '')
601  ALLOCATE(rprof(kjpindex,nvm,nparan*nbyear), stat=ier)
602  IF (ier /= 0) CALL ipslerr(3, 'forcesoil', 'rprof : error in memory allocation', '', '')
603  ALLOCATE(tsurf(kjpindex,nparan*nbyear), stat=ier)
604  IF (ier /= 0) CALL ipslerr(3, 'forcesoil', 'tsurf : error in memory allocation', '', '')
605  ALLOCATE(lalo(kjpindex,2), stat=ier)
606  IF (ier /= 0) CALL ipslerr(3, 'forcesoil', 'lalo : error in memory allocation', '', '')
607  ALLOCATE(snowdz(kjpindex,nsnow,nparan*nbyear), stat=ier)
608  IF (ier /= 0) CALL ipslerr(3, 'forcesoil', 'snowdz_ : error in memory allocation', '', '')
609  ALLOCATE(snowrho(kjpindex,nsnow,nparan*nbyear), stat=ier)
610  IF (ier /= 0) CALL ipslerr(3, 'forcesoil', 'snowrho : error in memory allocation', '', '')
611  ALLOCATE(som_input(kjpindex,ncarb,nvm,nelements,nparan*nbyear), stat=ier)
612  IF (ier /= 0) CALL ipslerr(3, 'forcesoil', 'som_input : error in memory allocation', '', '')
613  ALLOCATE(CN_target(kjpindex,nvm,ncarb,nparan*nbyear), stat=ier)
614  IF (ier /= 0) CALL ipslerr(3, 'forcesoil', 'CN_target : error in memory allocation', 'Error code:', '')
615  ALLOCATE(n_mineralisation(kjpindex, nvm, nparan*nbyear), stat=ier)
616  IF (ier /= 0) CALL ipslerr_p(3, 'forcesoil', 'n_mineralisation : error in memory allocation', '', '')   
617  !-
618  CALL stomate_io_soil_carbon_discretization_read(Cforcing_name,  nparan,      nbyear,&
619                nbp_mpi_para_begin(mpi_rank),   nbp_mpi_para(mpi_rank),         &
620                som_input,               pb,         snow,       tsurf,  &
621                tprof,                          fbact,      hslong,     rprof,  &
622                lalo,                           snowdz,     snowrho,    veget_max, &
623                CN_target, n_mineralisation )
624  !---
625  !--- Create the index table
626  !---
627  !--- This job returns a LOCAL kindex.
628  !---
629  ALLOCATE (indices(kjpindex),stat=ier)
630  IF (ier /= 0) CALL ipslerr_p(3, 'forcesoil', 'indices : error in memory allocation', '', '')
631  !
632  !! scattering to all processes in parallel mode
633  !
634  CALL scatter(indices_g,indices)
635  indices(1:kjpindex)=indices(1:kjpindex)-(jj_begin-1)*iim_g
636  IF (printlev_loc>=3) WRITE(numout,*) mpi_rank,"indices locaux = ",indices(1:kjpindex)
637  !-
638  ! Allocation of the variables for a processor
639  !-
640  ALLOCATE(clay(kjpindex), stat=ier)
641  IF (ier /= 0) CALL ipslerr_p(3, 'forcesoil', 'clay : error in memory allocation', '', '')
642  ALLOCATE(depth_organic_soil(kjpindex), stat=ier)
643  IF (ier /= 0) CALL ipslerr_p(3, 'forcesoil', 'depth_organic_soil : error in memory allocation', '', '')
644  ALLOCATE(som(kjpindex,ncarb,nvm,nelements), stat=ier)
645  IF (ier /= 0) CALL ipslerr_p(3, 'forcesoil', 'indices : error in memory allocation', '', '')
646  !-
647  ALLOCATE(som_surf(kjpindex,ncarb,nvm,nelements), stat=ier)
648  IF (ier /= 0) CALL ipslerr_p(3, 'forcesoil', 'som_surf : error in memory allocation', '', '')
649  ALLOCATE(deepSOM_a(kjpindex,ngrnd,nvm,nelements), stat=ier)
650  IF (ier /= 0) CALL ipslerr_p(3, 'forcesoil', 'deepSOM_a : error in memory allocation', '', '')
651  ALLOCATE(deepSOM_s(kjpindex,ngrnd,nvm,nelements), stat=ier)
652  IF (ier /= 0) CALL ipslerr_p(3, 'forcesoil', 'deepSOM_s : error in memory allocation', '', '')
653  ALLOCATE(deepSOM_p(kjpindex,ngrnd,nvm,nelements), stat=ier)
654  IF (ier /= 0) CALL ipslerr_p(3, 'forcesoil', 'deepSOM_p : error in memory allocation', '', '')
655  ALLOCATE(O2_soil(kjpindex,ngrnd,nvm), stat=ier)
656  IF (ier /= 0) CALL ipslerr_p(3, 'forcesoil', 'O2_soil : error in memory allocation', '', '')
657  ALLOCATE(CH4_soil(kjpindex,ngrnd,nvm), stat=ier)
658  IF (ier /= 0) CALL ipslerr_p(3, 'forcesoil', 'CH4_soil : error in memory allocation', '', '')
659  ALLOCATE(O2_snow(kjpindex,nsnow,nvm), stat=ier)
660  IF (ier /= 0) CALL ipslerr_p(3, 'forcesoil', 'O2_snow : error in memory allocation', '', '')
661  ALLOCATE(CH4_snow(kjpindex,nsnow,nvm), stat=ier)
662  IF (ier /= 0) CALL ipslerr_p(3, 'forcesoil', 'CH4_snow : error in memory allocation', '', '')
663  ALLOCATE(altmax(kjpindex,nvm), stat=ier)
664  IF (ier /= 0) CALL ipslerr_p(3, 'forcesoil', 'altmax : error in memory allocation', '', '')
665  !-
666  ! Initialization of the variables for a processor
667  !-
668  CALL Scatter(clay_g,clay)
669  CALL Scatter(depth_organic_soil_g,depth_organic_soil)
670  CALL Scatter(som_g,som)
671  CALL Scatter(som_surf_g,som_surf)
672  CALL Scatter(deepSOM_a_g,deepSOM_a)
673  CALL Scatter(deepSOM_s_g,deepSOM_s)
674  CALL Scatter(deepSOM_p_g,deepSOM_p)
675  CALL Scatter(O2_soil_g,O2_soil)
676  CALL Scatter(CH4_soil_g,CH4_soil)
677  CALL Scatter(O2_snow_g,O2_snow)
678  CALL Scatter(CH4_snow_g,CH4_snow)
679  CALL Scatter(altmax_g,altmax)
680!-
681! Configuration of the parameters
682!-
683   !-
684    ! soilcarbon parameters
685    !-
686    !Config Key   = ACTIVE_TO_PASS_CLAY_FRAC
687    !Config Desc  =
688    !Config if    = OK_STOMATE
689    !Config Def   = 0.68 
690    !Config Help  =
691    !Config Units = [-]
692    CALL getin_p('ACTIVE_TO_PASS_CLAY_FRAC',active_to_pass_clay_frac)
693
694
695    !Config Key   = ACTIVE_TO_PASS_REF_FRAC
696    !Config Desc  = Fixed fraction from Active to Passive pool
697    !Config if    = OK_STOMATE
698    !Config Def   = 0.003
699    !Config Help  =
700    !Config Units = [-]
701    CALL getin_p('ACTIVE_TO_PASS_REF_FRAC',active_to_pass_ref_frac)
702    !
703    !Config Key   = SURF_TO_SLOW_REF_FRAC
704    !Config Desc  = Fixed fraction from Surface to Slow pool
705    !Config if    = OK_STOMATE
706    !Config Def   = 0.4
707    !Config Help  =
708    !Config Units = [-]
709    CALL getin_p('SURF_TO_SLOW_REF_FRAC',surf_to_slow_ref_frac)
710    !
711    !Config Key   = ACTIVE_TO_CO2_REF_FRAC
712    !Config Desc  = Fixed fraction from Active pool to CO2 emission
713    !Config if    = OK_STOMATE
714    !Config Def   = 0.85
715    !Config Help  =
716    !Config Units = [-]
717    CALL getin_p('ACTIVE_TO_CO2_REF_FRAC',active_to_co2_ref_frac)
718    !
719    !Config Key   = SLOW_TO_PASS_REF_FRAC
720    !Config Desc  = Fixed fraction from Slow to Passive pool
721    !Config if    = OK_STOMATE
722    !Config Def   = 0.003
723    !Config Help  =
724    !Config Units = [-]
725    CALL getin_p('SLOW_TO_PASS_REF_FRAC',slow_to_pass_ref_frac)
726    !
727    !Config Key   = SLOW_TO_CO2_REF_FRAC
728    !Config Desc  = Fixed fraction from Slow pool to CO2 emission
729    !Config if    = OK_STOMATE
730    !Config Def   = 0.55
731    !Config Help  =
732    !Config Units = [-]
733    CALL getin_p('SLOW_TO_CO2_REF_FRAC',slow_to_co2_ref_frac)
734    !
735    !Config Key   = PASS_TO_ACTIVE_REF_FRAC
736    !Config Desc  = Fixed fraction from Passive to Active pool
737    !Config if    = OK_STOMATE
738    !Config Def   = 0.45
739    !Config Help  =
740    !Config Units = [-]
741    CALL getin_p('PASS_TO_ACTIVE_REF_FRAC',pass_to_active_ref_frac)
742    !
743    !Config Key   = PASS_TO_SLOW_REF_FRAC
744    !Config Desc  = Fixed fraction from Passive to Slow pool
745    !Config if    = OK_STOMATE
746    !Config Def   = 0.
747    !Config Help  =
748    !Config Units = [-]
749    CALL getin_p('PASS_TO_SLOW_REF_FRAC',pass_to_slow_ref_frac)
750    !
751    !Config Key   = ACTIVE_TO_CO2_CLAY_SILT_FRAC
752    !Config Desc  = Clay-Silt-dependant fraction from Active pool to CO2 emission
753    !Config if    = OK_STOMATE
754    !Config Def   = 0.68
755    !Config Help  =
756    !Config Units = [-]
757    CALL getin_p('ACTIVE_TO_CO2_CLAY_SILT_FRAC',active_to_co2_clay_silt_frac)
758    !
759    !Config Key   = SLOW_TO_PASS_CLAY_FRAC
760    !Config Desc  = Clay-dependant fraction from Slow to Passive pool
761    !Config if    = OK_STOMATE
762    !Config Def   = -0.009
763    !Config Help  =
764    !Config Units = [-]
765    CALL getin_p('SLOW_TO_PASS_CLAY_FRAC',slow_to_pass_clay_frac)
766    !
767    !Config Key   = SOM_TURN_IACTIVE
768    !Config Desc  = turnover in active pool
769    !Config if    = OK_STOMATE
770    !Config Def   = 7.3
771    !Config Help  =
772    !Config Units =  [year-1]
773    CALL getin_p('SOM_TURN_IACTIVE',som_turn_iactive)
774    !
775    !Config Key   = SOM_TURN_ISLOW
776    !Config Desc  = turnover in slow pool
777    !Config if    = OK_STOMATE
778    !Config Def   = 0.2
779    !Config Help  =
780    !Config Units = [year-1]
781    CALL getin_p('SOM_TURN_ISLOW',som_turn_islow)
782    !
783    !Config Key   = SOM_TURN_IPASSIVE
784    !Config Desc  = turnover in passive pool
785    !Config if    = OK_STOMATE
786    !Config Def   = 0.0045
787    !Config Help  =
788    !Config Units = [year-1]
789    CALL getin_p('SOM_TURN_IPASSIVE',som_turn_ipassive)
790    !
791    !Config Key   = SOM_TURN_IACTIVE_CLAY_FRAC
792    !Config Desc  = clay-dependant parameter impacting on turnover rate of active pool - Tm parameter of Parton et al. 1993 (-)
793    !Config if    = OK_STOMATE
794    !Config Def   = 0.75
795    !Config Help  =
796    !Config Units = [-]
797    CALL getin_p('SOM_TURN_IACTIVE_CLAY_FRAC',som_turn_iactive_clay_frac)
798    !
799    !Config Key   = CN_TARGET_IACTIVE_REF
800    !Config Desc  = CN target ratio of active pool for soil min N = 0
801    !Config if    = OK_STOMATE
802    !Config Def   = 15.
803    !Config Help  =
804    !Config Units = [-]
805    CALL getin_p('CN_TARGET_IACTIVE_REF',CN_target_iactive_ref)
806    !
807    !Config Key   = CN_TARGET_ISLOW_REF
808    !Config Desc  = CN target ratio of slow pool for soil min N = 0
809    !Config if    = OK_STOMATE
810    !Config Def   = 20.
811    !Config Help  =
812    !Config Units = [-]
813    CALL getin_p('CN_TARGET_ISLOW_REF',CN_target_islow_ref)
814    !
815    !Config Key   = CN_TARGET_IPASSIVE_REF
816    !Config Desc  = CN target ratio of passive pool for soil min N = 0
817    !Config if    = OK_STOMATE
818    !Config Def   = 10.
819    !Config Help  =
820    !Config Units = [-]
821    CALL getin_p('CN_TARGET_IPASSIVE_REF',CN_target_ipassive_ref)
822    !
823    !Config Key   = CN_TARGET_IACTIVE_NMIN
824    !Config Desc  = CN target ratio change per mineral N unit (g m-2) for active pool
825    !Config if    = OK_STOMATE
826    !Config Def   = -6.
827    !Config Help  =
828    !Config Units = [(g m-2)-1]
829    CALL getin_p('CN_TARGET_IACTIVE_NMIN',CN_target_iactive_Nmin)
830    !
831    !Config Key   = CN_TARGET_ISLOW_NMIN
832    !Config Desc  = CN target ratio change per mineral N unit (g m-2) for slow pool
833    !Config if    = OK_STOMATE
834    !Config Def   = -4.
835    !Config Help  =
836    !Config Units = [(g m-2)-1]
837    CALL getin_p('CN_TARGET_ISLOW_NMIN',CN_target_islow_Nmin)
838    !
839    !Config Key   = CN_TARGET_IPASSIVE_NMIN
840    !Config Desc  = CN target ratio change per mineral N unit (g m-2) for passive pool
841    !Config if    = OK_STOMATE
842    !Config Def   = -1.5
843    !Config Help  =
844    !Config Units = [(g m-2)-1]
845    CALL getin_p('CN_TARGET_IPASSIVE_NMIN',CN_target_ipassive_Nmin)
846
847  !
848  !! 2. Computational step
849  !! Loop over time - Call of soilcarbon routine at each time step
850  !! Updated soil carbon stocks are stored into carbon variable
851  !! We only keep the last value of carbon variable (no time dimension).
852  !!-
853   IF ( satsoil )  hslong(:,:,:,:) = 1.
854   !these variables are only ouputs from deep_carbcycle (thus not necessary for
855   !Gather and Scatter)
856   ALLOCATE(heat_Zimov(kjpindex,ngrnd,nvm), stat=ier)
857   IF (ier /= 0) CALL ipslerr_p(3, 'forcesoil', 'heat_Zimov : error in memory allocation', '', '')
858   ALLOCATE(sfluxCH4_deep(kjpindex), stat=ier)
859   IF (ier /= 0) CALL ipslerr_p(3, 'forcesoil', 'sfluxCH4_deep : error in memory allocation', '', '')
860   ALLOCATE(sfluxCO2_deep(kjpindex), stat=ier)
861   IF (ier /= 0) CALL ipslerr_p(3, 'forcesoil', 'sfluxCO2_deep : error in memory allocation', '', '')
862   ALLOCATE(fixed_cryoturbation_depth(kjpindex,nvm), stat=ier)
863   IF (ier /= 0) CALL ipslerr_p(3, 'forcesoil', 'fixed_cryoturbation_depth : error in memory allocation', '', '')
864   ALLOCATE(resp_hetero_soil(kjpindex, nvm), stat=ier)
865   IF (ier /= 0) CALL ipslerr_p(3, 'forcesoil', 'resp_hetero_soil : error in memory allocation', '', '')
866   iatt = 0
867   iyear=1
868   DO i=1,itau_len
869      iatt = iatt+1
870      IF (iatt > nparan*nbyear) THEN
871            IF (printlev>=3) WRITE(numout,*) iyear
872            iatt = 1
873            iyear=iyear+1
874      ENDIF
875      WRITE(numout, *) "Forcesoil:: deep_carbcycle, iyear=", iyear
876
877      CALL stomate_soil_carbon_discretization_deep_somcycle(kjpindex, indices, iatt, dt_forcesoil*one_day, lalo, clay, &
878         tsurf(:,iatt), tprof(:,:,:,iatt), hslong(:,:,:,iatt), snow(:,iatt), heat_Zimov, pb(:,iatt), &
879         sfluxCH4_deep, sfluxCO2_deep,  &
880         deepSOM_a, deepSOM_s, deepSOM_p, O2_soil, CH4_soil, O2_snow, CH4_snow, &
881         depth_organic_soil, som_input(:,:,:,:,iatt), &
882         veget_max(:,:,iatt), rprof(:,:,iatt), altmax,  som, som_surf, resp_hetero_soil, &
883         fbact(:,:,:,iatt), CN_target(:,:,:,iatt), fixed_cryoturbation_depth, snowdz(:,:,iatt), snowrho(:,:,iatt),n_mineralisation(:,:,iatt))
884   ENDDO
885  !!-
886  !! 3. write new soil organic matter stocks into the ouput restart file
887  !!-
888  CALL restput_p (rest_id_sto, 'som', nbp_glo, ncarb , nvm, nelements, itau_dep, &
889         &     som, 'scatter', nbp_glo, indices_g)
890  CALL restput_p (rest_id_sto, 'deepSOM_a', nbp_glo, ngrnd, nvm, nelements, itau_dep, &
891        &               deepSOM_a, 'scatter', nbp_glo, indices_g)
892  CALL restput_p (rest_id_sto, 'deepSOM_s', nbp_glo, ngrnd, nvm, nelements, itau_dep, &
893        &               deepSOM_s, 'scatter', nbp_glo, indices_g)
894  CALL restput_p (rest_id_sto, 'deepSOM_p', nbp_glo, ngrnd, nvm, nelements, itau_dep, &
895        &               deepSOM_p, 'scatter', nbp_glo, indices_g)
896  CALL restput_p (rest_id_sto, 'O2_soil', nbp_glo, ngrnd, nvm, itau_dep, &
897        &               O2_soil, 'scatter', nbp_glo, indices_g)
898  CALL restput_p (rest_id_sto, 'CH4_soil', nbp_glo, ngrnd, nvm, itau_dep, &
899        &               CH4_soil, 'scatter', nbp_glo, indices_g)
900  CALL restput_p (rest_id_sto, 'O2_snow', nbp_glo, nsnow, nvm, itau_dep, &
901        &               O2_snow, 'scatter', nbp_glo, indices_g)
902  CALL restput_p (rest_id_sto, 'CH4_snow', nbp_glo, nsnow, nvm, itau_dep, &
903        &               CH4_snow, 'scatter', nbp_glo, indices_g)
904  CALL restput_p (rest_id_sto, 'altmax', nbp_glo, nvm, 1, itau_dep,     &
905        &               altmax, 'scatter',  nbp_glo, indices_g)
906  !-
907  IF (is_root_prc) THEN
908        !- Close restart files
909        CALL getin_dump
910        CALL restclo
911  ENDIF
912  !-
913#ifdef CPP_PARA
914  CALL MPI_FINALIZE(ier)
915#endif
916  WRITE(numout,*) "End of forcesoil."
917  !--------------------
918END PROGRAM forcesoil
Note: See TracBrowser for help on using the repository browser.