source: branches/ORCHIDEE_EXT/ORCHIDEE_OL/forcesoil.f90 @ 428

Last change on this file since 428 was 408, checked in by didier.solyga, 13 years ago

Merge the revisions 388 to 396 from the trunk. Now the externalized version is based on ORCHIDEE_1_9_5_2

File size: 18.7 KB
Line 
1PROGRAM forcesoil
2  !---------------------------------------------------------------------
3  ! This program reads a forcing file for STOMATE's soil carbon routine
4  ! which was created with STOMATE.
5  ! It then integrates STOMATE's soil carbon parameterizations
6  ! for a given number of years using this forcing.
7  !---------------------------------------------------------------------
8  !- IPSL (2006)
9  !-  This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC
10  USE netcdf
11  !-
12  USE defprec
13  USE constantes
14  USE pft_parameters 
15  USE stomate_data
16  USE ioipsl
17  USE stomate_soilcarbon
18  USE parallel
19  !-
20  IMPLICIT NONE
21  !-
22  CHARACTER(LEN=80) :: sto_restname_in,sto_restname_out
23  INTEGER(i_std)                             :: iim,jjm
24
25  INTEGER(i_std),PARAMETER                   :: llm = 1
26  INTEGER(i_std)                             :: kjpindex
27
28  INTEGER(i_std)                             :: itau_dep,itau_len
29  CHARACTER(LEN=30)                         :: time_str
30  REAL(r_std)                                :: dt_files
31  REAL(r_std)                                :: date0
32  INTEGER(i_std)                             :: rest_id_sto
33  CHARACTER(LEN=20), SAVE                    :: thecalendar = 'noleap'
34  !-
35  CHARACTER(LEN=100) :: Cforcing_name
36  INTEGER            :: Cforcing_id
37  INTEGER            :: v_id
38  REAL(r_std)                                :: dt_forcesoil
39  INTEGER                                   :: nparan
40
41  INTEGER(i_std),DIMENSION(:),ALLOCATABLE    :: indices
42  INTEGER(i_std),DIMENSION(:),ALLOCATABLE    :: indices_g
43  REAL(r_std),DIMENSION(:),ALLOCATABLE       :: x_indices_g
44  REAL(r_std),DIMENSION(:,:),ALLOCATABLE     :: lon, lat
45  REAL(r_std),DIMENSION(llm)                 :: lev
46
47
48  INTEGER                                   :: i,m,iatt,iv,iyear
49
50  CHARACTER(LEN=80)                         :: var_name
51  CHARACTER(LEN=400)                        :: taboo_vars
52  REAL(r_std),DIMENSION(1)                   :: xtmp
53  INTEGER(i_std),PARAMETER                   :: nbvarmax=300
54  INTEGER(i_std)                             :: nbvar
55  CHARACTER(LEN=50),DIMENSION(nbvarmax)     :: varnames
56  INTEGER(i_std)                             :: varnbdim
57  INTEGER(i_std),PARAMETER                   :: varnbdim_max=20
58  INTEGER,DIMENSION(varnbdim_max)           :: vardims
59  LOGICAL                                   :: l1d
60  REAL(r_std),DIMENSION(:,:),ALLOCATABLE     :: var_3d
61  REAL(r_std)                                :: x_tmp
62  ! string suffix indicating an index
63  CHARACTER(LEN=10)  :: part_str
64  !
65  ! clay fraction
66  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:)  :: clay_g
67  REAL(r_std),DIMENSION(:,:,:,:),ALLOCATABLE :: soilcarbon_input_g
68  REAL(r_std),DIMENSION(:,:,:),ALLOCATABLE   :: control_temp_g
69  REAL(r_std),DIMENSION(:,:,:),ALLOCATABLE   :: control_moist_g
70  REAL(r_std),DIMENSION(:,:,:),ALLOCATABLE   :: carbon_g
71
72  REAL(r_std),ALLOCATABLE :: clay(:)
73  REAL(r_std),ALLOCATABLE :: soilcarbon_input(:,:,:,:)
74  REAL(r_std),ALLOCATABLE :: control_temp(:,:,:)
75  REAL(r_std),ALLOCATABLE :: control_moist(:,:,:)
76  REAL(r_std),ALLOCATABLE :: carbon(:,:,:)
77  REAL(r_std),DIMENSION(:,:),ALLOCATABLE     :: resp_hetero_soil
78
79  INTEGER(i_std)                             :: ier,iret
80
81  LOGICAL :: debug
82
83  !>> DS add for externalization
84  LOGICAL  :: l_error
85  ! >> DS
86
87  CALL Init_para(.FALSE.) 
88  CALL init_timer
89  !
90  ! DS : For externalization cause we decoupled forcesoil from ORCHIDEE
91  !
92 
93  ! 1. Read the number of PFTs
94  !
95  !Config Key  = NVM
96  !Config Desc = number of PFTs 
97  !Config  if  = ANYTIME
98  !Config  Def  = 13
99  !Config  Help = The number of vegetation types define by the user
100  !Config  Units = NONE
101  CALL getin_p('NVM',nvm)
102
103  ! 2. Allocation
104  l_error = .FALSE.
105  ALLOCATE(pft_to_mtc(nvm),stat=ier)
106  l_error = l_error .OR. (ier .NE. 0)
107  IF (l_error) THEN
108     STOP 'pft_to_mtc (forcesoil only) : error in memory allocation'
109  ENDIF
110
111  ! 3. Initialisation of the correspondance table
112  pft_to_mtc (:) = undef_int
113 
114  ! 4.Reading of the conrrespondance table in the .def file
115  !
116  !Config  Key  = PFT_TO_MTC
117  !Config  Desc = correspondance array linking a PFT to MTC
118  !Config  if  = ANYTIME
119  !Config  Def  = 1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11, 12, 13
120  !Config  Help =
121  !Config  Units = NONE
122  CALL getin_p('PFT_TO_MTC',pft_to_mtc)
123
124  ! 4.1 if nothing is found, we use the standard configuration
125  IF(nvm .EQ. 13 ) THEN
126     IF(pft_to_mtc(1) .EQ. undef_int) THEN
127        WRITE(numout,*) 'Note to the user : we will use ORCHIDEE to its standard configuration'
128        pft_to_mtc(:) = (/ 1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11, 12, 13 /)
129     ENDIF
130  ELSE   
131     IF(pft_to_mtc(1) .EQ. undef_int) THEN
132        WRITE(numout,*)' The array PFT_TO_MTC is empty : we stop'
133     ENDIF
134  ENDIF
135 
136  ! 5. What happened if pft_to_mtc(j) > nvmc (if the mtc doesn't exist)?
137  DO i = 1, nvm
138     IF(pft_to_mtc(i) .GT. nvmc) THEN
139        WRITE(numout,*) "the MTC you chose doesn't exist"
140        STOP 'we stop reading pft_to_mtc'
141     ENDIF
142  ENDDO
143 
144 
145  ! 6. Check if pft_to_mtc(1) = 1
146  IF(pft_to_mtc(1) .NE. 1) THEN
147     WRITE(numout,*) 'the first pft has to be the bare soil'
148     STOP 'we stop reading next values of pft_to_mtc'
149  ELSE
150     DO i = 2,nvm
151        IF(pft_to_mtc(i) .EQ.1) THEN
152           WRITE(numout,*) 'only pft_to_mtc(1) has to be the bare soil'
153           STOP 'we stop reading pft_to_mtc'
154        ENDIF
155     ENDDO
156  ENDIF
157 
158
159  ! 7. Allocate and initialize natural ans is_c4
160 
161  ! 7.1 Memory allocation
162  l_error = .FALSE.
163  ALLOCATE(natural(nvm),stat=ier)
164  l_error = l_error .OR. (ier .NE. 0)
165  ALLOCATE(is_c4(nvm),stat=ier)
166
167  IF (l_error) THEN
168     STOP 'natural or is_c4 (forcesoil only) : error in memory allocation'
169  ENDIF
170
171  ! 7.2 Initialisation
172  DO i= 1, nvm
173     natural(i) = natural_mtc(pft_to_mtc(i))
174     is_c4(i) = is_c4_mtc(pft_to_mtc(i))
175  ENDDO
176
177!---------------------------------------------------------------------
178!-
179! set debug to have more information
180!-
181  !Config  Key  = DEBUG_INFO
182  !Config  Desc = Flag for debug information
183  !Config  Def  = n
184  !Config  Help = This option allows to switch on the output of debug
185  !Config         information without recompiling the code.
186!-
187  debug = .FALSE.
188  CALL getin_p('DEBUG_INFO',debug)
189  !-
190  ! Stomate's restart files
191  !-
192  IF (is_root_prc) THEN
193     sto_restname_in = 'stomate_start.nc'
194     CALL getin ('STOMATE_RESTART_FILEIN',sto_restname_in)
195     WRITE(numout,*) 'STOMATE INPUT RESTART_FILE: ',TRIM(sto_restname_in)
196     sto_restname_out = 'stomate_rest_out.nc'
197     CALL getin ('STOMATE_RESTART_FILEOUT',sto_restname_out)
198     WRITE(numout,*) 'STOMATE OUTPUT RESTART_FILE: ',TRIM(sto_restname_out)
199     !-
200     ! We need to know iim_g, jjm.
201     ! Get them from the restart files themselves.
202     !-
203     iret = NF90_OPEN (sto_restname_in, NF90_NOWRITE, rest_id_sto)
204     iret = NF90_INQUIRE_DIMENSION (rest_id_sto,1,len=iim_g)
205     iret = NF90_INQUIRE_DIMENSION (rest_id_sto,2,len=jjm_g)
206     iret = NF90_INQ_VARID (rest_id_sto, "time", iv)
207     iret = NF90_GET_ATT (rest_id_sto, iv, 'calendar',thecalendar)
208     iret = NF90_CLOSE (rest_id_sto)
209     i=INDEX(thecalendar,ACHAR(0))
210     IF ( i > 0 ) THEN
211        thecalendar(i:20)=' '
212     ENDIF
213     !-
214     ! Allocate longitudes and latitudes
215     !-
216     ALLOCATE (lon(iim_g,jjm_g))
217     ALLOCATE (lat(iim_g,jjm_g))
218     lon(:,:) = 0.0
219     lat(:,:) = 0.0
220     lev(1)   = 0.0
221     !-
222     CALL restini &
223          & (sto_restname_in, iim_g, jjm_g, lon, lat, llm, lev, &
224          &  sto_restname_out, itau_dep, date0, dt_files, rest_id_sto)
225  ENDIF
226  CALL bcast(date0)
227  CALL bcast(thecalendar)
228  WRITE(numout,*) "calendar = ",thecalendar
229  !-
230  ! calendar
231  !-
232  CALL ioconf_calendar (thecalendar)
233  CALL ioget_calendar  (one_year,one_day)
234  CALL ioconf_startdate(date0)
235  !
236  IF (is_root_prc) THEN
237     !-
238     ! open FORCESOIL's forcing file to read some basic info
239     !-
240     Cforcing_name = 'NONE'
241     CALL getin ('STOMATE_CFORCING_NAME',Cforcing_name)
242     !-
243     iret = NF90_OPEN (TRIM(Cforcing_name),NF90_NOWRITE,Cforcing_id)
244     IF (iret /= NF90_NOERR) THEN
245        CALL ipslerr (3,'forcesoil', &
246             &        'Could not open file : ', &
247             &          Cforcing_name,'(Do you have forget it ?)')
248     ENDIF
249     !-
250     ier = NF90_GET_ATT (Cforcing_id,NF90_GLOBAL,'kjpindex',x_tmp)
251     nbp_glo = NINT(x_tmp)
252     ier = NF90_GET_ATT (Cforcing_id,NF90_GLOBAL,'nparan',x_tmp)
253     nparan = NINT(x_tmp)
254     !-
255     ALLOCATE (indices_g(nbp_glo))
256     ALLOCATE (clay_g(nbp_glo))
257     !-
258     ALLOCATE (x_indices_g(nbp_glo),stat=ier)
259     ier = NF90_INQ_VARID (Cforcing_id,'index',v_id)
260     ier = NF90_GET_VAR   (Cforcing_id,v_id,x_indices_g)
261     indices_g(:) = NINT(x_indices_g(:))
262     WRITE(numout,*) mpi_rank,"indices globaux : ",indices_g
263     DEALLOCATE (x_indices_g)
264     !-
265     ier = NF90_INQ_VARID (Cforcing_id,'clay',v_id)
266     ier = NF90_GET_VAR   (Cforcing_id,v_id,clay_g)
267     !-
268     ! time step of forcesoil
269     !-
270     dt_forcesoil = one_year / FLOAT(nparan)
271     WRITE(numout,*) 'time step (d): ',dt_forcesoil
272     !-
273     ! read (and partially write) the restart file
274     !-
275     ! read and write the variables we do not need
276     !-
277     taboo_vars = '$lon$ $lat$ $lev$ $nav_lon$ $nav_lat$ $nav_lev$ $time$ $time_steps$ '// &
278          &             '$day_counter$ $dt_days$ $date$ '// &
279          &             '$carbon_01$ $carbon_02$ $carbon_03$ $carbon_04$ $carbon_05$'// &
280          &             '$carbon_06$ $carbon_07$ $carbon_08$ $carbon_09$ $carbon_10$'// &
281          &             '$carbon_11$ $carbon_12$ $carbon_13$'
282     !-
283     CALL ioget_vname(rest_id_sto, nbvar, varnames)
284     !-
285     ! read and write some special variables (1D or variables that we need)
286     !-
287     var_name = 'day_counter'
288     CALL restget (rest_id_sto, var_name, 1, 1, 1, itau_dep, .TRUE., xtmp)
289     CALL restput (rest_id_sto, var_name, 1, 1, 1, itau_dep, xtmp)
290     !-
291     var_name = 'dt_days'
292     CALL restget (rest_id_sto, var_name, 1, 1, 1, itau_dep, .TRUE., xtmp)
293     CALL restput (rest_id_sto, var_name, 1, 1, 1, itau_dep, xtmp)
294     !-
295     var_name = 'date'
296     CALL restget (rest_id_sto, var_name, 1, 1, 1, itau_dep, .TRUE., xtmp)
297     CALL restput (rest_id_sto, var_name, 1, 1, 1, itau_dep, xtmp)
298     !-
299     DO iv=1,nbvar
300        !-- check if the variable is to be written here
301        IF (INDEX(taboo_vars,'$'//TRIM(varnames(iv))//'$') == 0 ) THEN
302           !---- get variable dimensions, especially 3rd dimension
303           CALL ioget_vdim &
304                &      (rest_id_sto, varnames(iv), varnbdim_max, varnbdim, vardims)
305           l1d = ALL(vardims(1:varnbdim) == 1)
306           !---- read it
307           IF (l1d) THEN
308              CALL restget &
309                   &        (rest_id_sto, TRIM(varnames(iv)), 1, vardims(3), &
310                   &         1, itau_dep, .TRUE., xtmp)
311           ELSE
312              ALLOCATE( var_3d(nbp_glo,vardims(3)), stat=ier)
313              IF (ier /= 0) STOP 'ALLOCATION PROBLEM'
314              !----
315              CALL restget &
316                   &        (rest_id_sto, TRIM(varnames(iv)), nbp_glo, vardims(3), &
317                   &         1, itau_dep, .TRUE., var_3d, "gather", nbp_glo, indices_g)
318           ENDIF
319           !---- write it
320           IF (l1d) THEN
321              CALL restput &
322                   &        (rest_id_sto, TRIM(varnames(iv)), 1, vardims(3), &
323                   &         1, itau_dep, xtmp)
324           ELSE
325              CALL restput &
326                   &        (rest_id_sto, TRIM(varnames(iv)), nbp_glo, vardims(3), &
327                   &         1, itau_dep, var_3d, 'scatter',  nbp_glo, indices_g)
328              !----
329              DEALLOCATE(var_3d)
330           ENDIF
331        ENDIF
332     ENDDO
333     !-
334     ! read soil carbon
335     !-
336     ALLOCATE(carbon_g(nbp_glo,ncarb,nvm))
337     carbon_g(:,:,:) = val_exp
338     DO m = 1, nvm
339        WRITE (part_str, '(I2)') m
340        IF (m<10) part_str(1:1)='0'
341        var_name = 'carbon_'//part_str(1:LEN_TRIM(part_str))
342        CALL restget &
343             &    (rest_id_sto, var_name, nbp_glo, ncarb , 1, itau_dep, &
344             &     .TRUE., carbon_g(:,:,m), 'gather', nbp_glo, indices_g)
345        IF (ALL(carbon_g(:,:,m) == val_exp)) carbon_g(:,:,m) = zero
346        !-- do not write this variable: it will be modified.
347     ENDDO
348     WRITE(numout,*) "date0 : ",date0, itau_dep
349     !-
350     ! Length of run
351     !-
352     WRITE(time_str,'(a)') '10000Y'
353     CALL getin('TIME_LENGTH', time_str)
354     write(numout,*) 'Number of years for carbon spinup : ',time_str
355     ! transform into itau
356     CALL tlen2itau(time_str, dt_forcesoil*one_day, date0, itau_len)
357     write(numout,*) 'Number of time steps to do: ',itau_len
358     !-
359     ! read the rest of the forcing file and store forcing in an array.
360     ! We read an average year.
361     !-
362     ALLOCATE(soilcarbon_input_g(nbp_glo,ncarb,nvm,nparan))
363     ALLOCATE(control_temp_g(nbp_glo,nlevs,nparan))
364     ALLOCATE(control_moist_g(nbp_glo,nlevs,nparan))
365     !-
366     ier = NF90_INQ_VARID (Cforcing_id,'soilcarbon_input',v_id)
367     ier = NF90_GET_VAR   (Cforcing_id,v_id,soilcarbon_input_g)
368     ier = NF90_INQ_VARID (Cforcing_id,   'control_moist',v_id)
369     ier = NF90_GET_VAR   (Cforcing_id,v_id,control_moist_g)
370     ier = NF90_INQ_VARID (Cforcing_id,    'control_temp',v_id)
371     ier = NF90_GET_VAR   (Cforcing_id,v_id,control_temp_g)
372     !-
373     ier = NF90_CLOSE (Cforcing_id)
374     !-
375  ENDIF
376  CALL bcast(nparan)
377  CALL bcast(dt_forcesoil)
378  CALL bcast(iim_g)
379  CALL bcast(jjm_g)
380  CALL bcast(nbp_glo)
381  CALL bcast(itau_dep)
382  CALL bcast(itau_len)
383  !
384  ! We must initialize data_para :
385     !
386     !
387  CALL init_data_para(iim_g,jjm_g,nbp_glo,indices_g)
388
389  kjpindex=nbp_loc
390  jjm=jj_nb
391  iim=iim_g
392  IF (debug) WRITE(numout,*) "Local grid : ",kjpindex,iim,jjm
393
394  !---
395  !--- Create the index table
396  !---
397  !--- This job return a LOCAL kindex
398  !---
399  ALLOCATE (indices(kjpindex),stat=ier)
400  CALL scatter(indices_g,indices)
401  indices(1:kjpindex)=indices(1:kjpindex)-(jj_begin-1)*iim_g
402  IF (debug) WRITE(numout,*) mpi_rank,"indices locaux = ",indices(1:kjpindex)
403  !-
404  !-
405  ! there we go: time loop
406  !-
407  ALLOCATE(clay(kjpindex))
408  ALLOCATE(soilcarbon_input(kjpindex,ncarb,nvm,nparan))
409  ALLOCATE(control_temp(kjpindex,nlevs,nparan))
410  ALLOCATE(control_moist(kjpindex,nlevs,nparan))
411  ALLOCATE(carbon(kjpindex,ncarb,nvm))
412  ALLOCATE(resp_hetero_soil(kjpindex,nvm))
413  iatt = 0
414
415  CALL Scatter(clay_g,clay)
416  CALL Scatter(soilcarbon_input_g,soilcarbon_input)
417  CALL Scatter(control_temp_g,control_temp)
418  CALL Scatter(control_moist_g,control_moist)
419  CALL Scatter(carbon_g,carbon)
420
421!!$ DS 16/06/2011 : for externalization
422  !
423  !Config Key  = FRAC_CARB_AA
424  !Config Desc = frac carb coefficients from active pool: depends on clay content
425  !Config if  = OK_STOMATE
426  !Config Def  = 0.0
427  !Config Help = fraction of the active pool going to the active pool
428  !Config Units = NONE
429  CALL getin_p('FRAC_CARB_AA',frac_carb_aa)
430  !
431  !Config Key  = FRAC_CARB_AP
432  !Config Desc = frac carb coefficients from active pool: depends on clay content
433  !Config if  = OK_STOMATE
434  !Config Def  = 0.004
435  !Config Help = fraction of the active pool going to the passive pool
436  !Config Units = NONE
437  CALL getin_p('FRAC_CARB_AP',frac_carb_ap) 
438  !
439  !Config Key  = FRAC_CARB_SS
440  !Config Desc = frac_carb_coefficients from slow pool
441  !Config if  = OK_STOMATE
442  !Config Def  = 0.0
443  !Config Help = fraction of the slow pool going to the slow pool
444  !Config Units = NONE
445  CALL getin_p('FRAC_CARB_SS',frac_carb_ss)
446  !
447  !Config Key  = FRAC_CARB_SA
448  !Config Desc = frac_carb_coefficients from slow pool
449  !Config if  = OK_STOMATE
450  !Config Def  = 0.42
451  !Config Help = fraction of the slow pool going to the active pool
452  !Config Units = NONE
453  CALL getin_p('FRAC_CARB_SA',frac_carb_sa)
454  !
455  !Config Key  = FRAC_CARB_SP
456  !Config Desc = frac_carb_coefficients from slow pool
457  !Config if  = OK_STOMATE
458  !Config Def  =  0.03
459  !Config Help = fraction of the slow pool going to the passive pool
460  !Config Units = NONE
461  CALL getin_p('FRAC_CARB_SP',frac_carb_sp)
462  !
463  !Config Key  = FRAC_CARB_PP
464  !Config Desc = frac_carb_coefficients from passive pool
465  !Config if  = OK_STOMATE
466  !Config Def  = 0.0
467  !Config Help = fraction of the passive pool going to the passive pool
468  !Config Units = NONE
469  CALL getin_p('FRAC_CARB_PP',frac_carb_pp)
470  !
471  !Config Key  = FRAC_CARB_PA
472  !Config Desc = frac_carb_coefficients from passive pool
473  !Config if  = OK_STOMATE
474  !Config Def  = 0.45
475  !Config Help = fraction of the passive pool going to the passive pool
476  !Config Units = NONE
477  CALL getin_p('FRAC_CARB_PA',frac_carb_pa)
478  !
479  !Config Key  = FRAC_CARB_PS
480  !Config Desc = frac_carb_coefficients from passive pool
481  !Config if  = OK_STOMATE
482  !Config Def  = 0.0
483  !Config Help = fraction of the passive pool going to the passive pool
484  !Config Units = NONE
485  CALL getin_p('FRAC_CARB_PS',frac_carb_ps)
486  !
487  !Config Key  = ACTIVE_TO_PASS_CLAY_FRAC
488  !Config Desc =
489  !Config if  = OK_STOMATE
490  !Config Def  =  .68 
491  !Config Help =
492  !Config Units = NONE
493  CALL getin_p('ACTIVE_TO_PASS_CLAY_FRAC',active_to_pass_clay_frac)
494  !
495  !Config Key  = CARBON_TAU_IACTIVE
496  !Config Desc = residence times in carbon pools
497  !Config if  = OK_STOMATE
498  !Config Def  =  0.149
499  !Config Help =
500  !Config Units = days [d]
501  CALL getin_p('CARBON_TAU_IACTIVE',carbon_tau_iactive)
502  !
503  !Config Key  = CARBON_TAU_ISLOW
504  !Config Desc = residence times in carbon pools
505  !Config if  = OK_STOMATE
506  !Config Def  =  5.48
507  !Config Help =
508  !Config Units = days [d]
509  CALL getin_p('CARBON_TAU_ISLOW',carbon_tau_islow)
510  !
511  !Config Key  = CARBON_TAU_IPASSIVE
512  !Config Desc = residence times in carbon pools
513  !Config if  = OK_STOMATE
514  !Config Def  =  241.
515  !Config Help =
516  !Config Units = days [d]
517  CALL getin_p('CARBON_TAU_IPASSIVE',carbon_tau_ipassive)
518  !
519  !Config Key  = FLUX_TOT_COEFF
520  !Config Desc =
521  !Config if  = OK_STOMATE
522  !Config Def  = 1.2, 1.4,.75
523  !Config Help =
524  !Config Units = days [d]
525  CALL getin_p('FLUX_TOT_COEFF',flux_tot_coeff)
526
527  iyear=1
528  DO i=1,itau_len
529     iatt = iatt+1
530     IF (iatt > nparan) THEN
531        IF (debug) WRITE(numout,*) iyear
532        iatt = 1
533        iyear=iyear+1
534     ENDIF
535     CALL soilcarbon &
536          &    (kjpindex, dt_forcesoil, clay, &
537          &     soilcarbon_input(:,:,:,iatt), &
538          &     control_temp(:,:,iatt), control_moist(:,:,iatt), &
539          &     carbon, resp_hetero_soil)
540  ENDDO
541  WRITE(numout,*) "End of soilcarbon LOOP."
542  CALL Gather(carbon,carbon_g)
543  !-
544  ! write new carbon into restart file
545  !-
546  IF (is_root_prc) THEN
547     DO m=1,nvm
548        WRITE (part_str, '(I2)') m
549        IF (m<10) part_str(1:1)='0'
550        var_name = 'carbon_'//part_str(1:LEN_TRIM(part_str))
551        CALL restput &
552             &    (rest_id_sto, var_name, nbp_glo, ncarb , 1, itau_dep, &
553             &     carbon_g(:,:,m), 'scatter', nbp_glo, indices_g)
554     ENDDO
555     !-
556     CALL getin_dump
557     CALL restclo
558  ENDIF
559#ifdef CPP_PARA
560  CALL MPI_FINALIZE(ier)
561#endif
562  WRITE(numout,*) "End of forcesoil."
563  !--------------------
564END PROGRAM forcesoil
Note: See TracBrowser for help on using the repository browser.