source: branches/publications/ORCHIDEE-MICT-OP-r6850/src_sechiba/ioipslctrl.f90

Last change on this file was 6849, checked in by yidi.xu, 4 years ago

ORCHIDEE-MICT-OP for oil palm growth modelling

File size: 346.7 KB
Line 
1! ================================================================================================================================
2!  MODULE       : ioipslctrl
3!
4!  CONTACT      : orchidee-help _at_ listes.ipsl.fr
5!
6!  LICENCE      : IPSL (2006)
7!  This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC
8!
9!>\BRIEF          This module contains subroutine for initialisation of IOIPSL history files and restart files
10!!
11!!\n DESCRIPTION: This module contains subroutine for initialisation of IOIPSL history files and restart files. The subroutines
12!!                ioipslctrl_history, ioipslctrl_histstom, ioipslctrl_histstomipcc, ioipslctrl_restini where previously stored in
13!!                intersurf module.
14!!
15!! RECENT CHANGE(S):
16!!
17!! REFERENCE(S) : None
18!!
19!! SVN          :
20!! $HeadURL: svn://forge.ipsl.jussieu.fr/orchidee/trunk/ORCHIDEE/src_sechiba/ioipslctrl.f90 $
21!! $Date: 2015-02-19 18:42:48 +0100 (jeu. 19 févr. 2015) $
22!! $Revision: 2548 $
23!! \n
24!_ ================================================================================================================================
25
26MODULE ioipslctrl
27
28  USE IOIPSL
29  USE ioipsl_para 
30  USE defprec
31  USE constantes
32  USE time, ONLY : one_day, dt_sechiba
33  USE constantes_soil
34  USE pft_parameters
35  USE thermosoilc, ONLY : thermosoilc_levels
36  USE grid 
37  USE stomate_wet_ch4, ONLY : stomate_wet_ch4_histdef 
38 
39  USE topmodel
40
41  IMPLICIT NONE
42
43
44  LOGICAL, SAVE                    :: ok_histsync             !! Flag activate syncronization of IOIPSL output
45  !$OMP THREADPRIVATE(ok_histsync)
46   REAL(r_std), SAVE               :: dw                      !! Frequency of history write (sec.)
47!$OMP THREADPRIVATE(dw)
48  INTEGER(i_std),PARAMETER         :: max_hist_level = 11     !!
49
50  PRIVATE
51  PUBLIC :: ioipslctrl_history, ioipslctrl_histstom, ioipslctrl_histstomipcc, ioipslctrl_restini
52  PUBLIC :: dw, max_hist_level, ok_histsync
53
54CONTAINS
55
56!! ================================================================================================================================
57!! SUBROUTINE    : ioipslctrl_history
58!!
59!>\BRIEF         This subroutine initialize the IOIPSL output files
60!!
61!! DESCRIPTION   : This subroutine initialize the IOIPSL output files sechiab_history.nc and sechiba_out_2.nc. It also calls the
62!!                 the subroutines ioipslctrl_histstom and ioipslctrl_histstomipcc for initialization of the IOIPSL stomate output files.
63!!                 This subroutine was previously called intsurf_history and located in module intersurf.
64!!
65!! RECENT CHANGE(S): None
66!!
67!! \n
68!_ ================================================================================================================================
69  SUBROUTINE ioipslctrl_history(iim, jjm, lon, lat, kindex, kjpindex, istp_old, date0, dt, hist_id, hist2_id, &
70       hist_id_stom, hist_id_stom_IPCC)
71   
72    USE mod_orchidee_para
73    !   
74    !  This subroutine initialized the history files for the land-surface scheme
75    !
76    IMPLICIT NONE
77   
78    INTEGER(i_std), INTENT(in)                  :: iim, jjm  !! Size in x and y of the data to be handeled
79    REAL(r_std),DIMENSION (iim,jjm), INTENT(in) :: lon, lat  !! Longitude and latitude of the data points
80    INTEGER(i_std),INTENT (in)                            :: kjpindex
81    INTEGER(i_std),DIMENSION (kjpindex), INTENT (in)      :: kindex
82   
83    INTEGER(i_std), INTENT(in)                  :: istp_old  !! Time step counter
84    REAL(r_std), INTENT(in)                     :: date0     !! Julian day at which istp=0
85    REAL(r_std), INTENT(in)                     :: dt        !! Time step of the counter in seconds
86
87    INTEGER(i_std), INTENT(out)                 :: hist_id !! History file identification for SECHIBA
88    INTEGER(i_std), INTENT(out)                 :: hist2_id !! History file 2 identification for SECHIBA (Hi-frequency ?)
89    !! History file identification for STOMATE and IPCC
90    INTEGER(i_std), INTENT(out)                 :: hist_id_stom, hist_id_stom_IPCC 
91    !
92    !  LOCAL
93    !
94    CHARACTER(LEN=80) :: histname,histname2                    !! Name of history files for SECHIBA
95    CHARACTER(LEN=80) :: stom_histname, stom_ipcc_histname     !! Name of history files for STOMATE
96    LOGICAL           :: ok_histfile2                 !! Flag to switch on histfile 2 for SECHIBA
97    REAL(r_std)       :: dw2                          !! frequency of history write (sec.)
98    CHARACTER(LEN=30)   :: flux_op                    !! Operations to be performed on fluxes
99    CHARACTER(LEN=40)   :: flux_insec, flux_scinsec   !! Operation in seconds
100    INTEGER(i_std)     :: hist_level, hist2_level     !! history output level (default is 10 => maximum output)
101    CHARACTER(LEN=40),DIMENSION(max_hist_level) :: &
102         & ave, avecels, avescatter, fluxop, &
103         & fluxop_scinsec, tmincels, tmaxcels, once, sumscatter, tmax  !! The various operation to be performed
104    CHARACTER(LEN=40),DIMENSION(max_hist_level) :: &
105         & ave2, avecels2, avescatter2, fluxop2, &
106         & fluxop_scinsec2, tmincels2, tmaxcels2, once2, sumscatter2  !! The various operation to be performed
107    CHARACTER(LEN=80) :: global_attribute              !! for writing attributes in the output files
108    INTEGER(i_std)     :: i, jst
109    ! SECHIBA AXIS
110    INTEGER(i_std)     :: hori_id                      !! ID of the default horizontal longitude and latitude map.
111    INTEGER(i_std)     :: vegax_id, laiax_id, laiax0_id, solax_id, soltax_id, nobioax_id !! ID's for two vertical coordinates
112    INTEGER(i_std)     :: soildiagax_id                !! ID for diagnostic soil levels
113    INTEGER(i_std)     :: solayax_id                   !! ID for the vertical axis of the CWRR hydrology
114    INTEGER(i_std)     :: hori_id2                      !! ID of the default horizontal longitude and latitude map.
115    INTEGER(i_std)     :: vegax_id2, laiax_id2, solax_id2, soltax_id2, nobioax_id2, albax_id2 !! ID's for two vertical coordinates
116    INTEGER(i_std)     :: solayax_id2                   !! ID for the vertical axis of the CWRR hydrology
117    INTEGER(i_std)     :: snowax_id                     !! ID for snow level axis
118
119    ! STOMATE AXIS
120    INTEGER(i_std)     :: hist_PFTaxis_id
121! deforestation
122    INTEGER(i_std)     :: hist_pool_10axis_id
123    INTEGER(i_std)     :: hist_pool_100axis_id
124    INTEGER(i_std)     :: hist_pool_11axis_id
125    INTEGER(i_std)     :: hist_pool_101axis_id
126    ! STOMATE IPCC AXIS
127    INTEGER(i_std)     :: hist_IPCC_PFTaxis_id
128    !
129    INTEGER(i_std)     :: hist_stomate_deepsoil
130    INTEGER(i_std)     :: hist_stomate_snow
131!!  yidi
132    INTEGER(i_std)     :: hist_stomate_phytomer
133    REAL(r_std),DIMENSION(nphs)  :: phylev              !! phytomer axis
134!!  yidi
135    CHARACTER(LEN=10)  :: part_str                      !! string suffix indicating an index
136    REAL(r_std),DIMENSION(nsnow)  :: snowlev            !! snow axis
137    REAL(r_std),DIMENSION(ngrnd) :: sol_coef
138
139    LOGICAL                               :: rectilinear
140    INTEGER(i_std)                         :: ier,jv
141    REAL(r_std), ALLOCATABLE, DIMENSION(:) :: lon_rect, lat_rect
142    !
143    REAL(r_std),DIMENSION(nvm)   :: veg
144    REAL(r_std),DIMENSION(nlai+1):: indlai
145    REAL(r_std),DIMENSION(nlai):: indlai0
146    REAL(r_std),DIMENSION(ngrnd) :: sol
147    REAL(r_std),DIMENSION(nstm)  :: soltyp
148    REAL(r_std),DIMENSION(nnobio):: nobiotyp
149    REAL(r_std),DIMENSION(2)     :: albtyp
150    REAL(r_std),DIMENSION(nslm)  :: solay
151    !
152    CHARACTER(LEN=80)           :: var_name           !! To store variables names
153    !
154    ! STOMATE history file
155    REAL(r_std)                  :: hist_days_stom     !!- GK time step in days for this history file
156    REAL(r_std)                  :: hist_dt_stom       !!- GK time step in seconds for this history file
157    REAL(r_std)                  :: dt_stomate_loc     !!  for test : time step of slow processes and STOMATE
158    REAL(r_std),DIMENSION(nvm)   :: hist_PFTaxis       !!- GK An axis we need for the history files
159!
160    REAL(r_std),DIMENSION(10)  :: hist_pool_10axis     !! Deforestation axis
161    REAL(r_std),DIMENSION(100)  :: hist_pool_100axis     !! Deforestation axis
162    REAL(r_std),DIMENSION(11)  :: hist_pool_11axis     !! Deforestation axis
163    REAL(r_std),DIMENSION(101)  :: hist_pool_101axis     !! Deforestation axis
164    !
165    ! IPCC history file
166    REAL(r_std)                  :: hist_days_stom_ipcc     !!- GK time step in days for this history file
167    REAL(r_std)                  :: hist_dt_stom_ipcc       !!- GK time step in seconds for this history file
168!
169    !
170    !=====================================================================
171    !- 3.0 Setting up the history files
172    !=====================================================================
173    !- 3.1 SECHIBA
174    !=====================================================================
175    !Config Key   = ALMA_OUTPUT
176    !Config Desc  = Should the output follow the ALMA convention
177    !Config If    = OK_SECHIBA
178    !Config Def   = n
179    !Config Help  = If this logical flag is set to true the model
180    !Config         will output all its data according to the ALMA
181    !Config         convention. It is the recommended way to write
182    !Config         data out of ORCHIDEE.
183    !Config Units = [FLAG]
184    CALL getin_p('ALMA_OUTPUT', almaoutput)   
185    IF (printlev>=2) WRITE(numout,*) 'ALMA_OUTPUT', almaoutput
186    !-
187    !Config Key   = OUTPUT_FILE
188    !Config Desc  = Name of file in which the output is going to be written
189    !Config If    = OK_SECHIBA
190    !Config Def   = sechiba_history.nc
191    !Config Help  = This file is going to be created by the model
192    !Config         and will contain the output from the model.
193    !Config         This file is a truly COADS compliant netCDF file.
194    !Config         It will be generated by the hist software from
195    !Config         the IOIPSL package.
196    !Config Units = [FILE]
197    !-
198    histname='sechiba_history.nc'
199    CALL getin_p('OUTPUT_FILE', histname)
200    IF (printlev>=2) WRITE(numout,*) 'OUTPUT_FILE', histname
201    !-
202    !Config Key   = WRITE_STEP
203    !Config Desc  = Frequency in seconds for sechiba_history.nc file with IOIPSL
204    !Config If    = OK_SECHIBA, NOT XIOS_ORCHIDEE_OK
205    !Config Def   = one_day
206    !Config Help  = This variables gives the frequency in the output
207    !Config         file sechiba_history.nc if using IOIPSL.
208    !Config         This variable is not read if XIOS is activated.
209    !Config Units = [seconds]
210    !-
211    dw = one_day
212    IF (xios_orchidee_ok) THEN
213      dw=0
214      IF (printlev>=2) WRITE(numout,*) 'All IOIPSL output are deactivated because this run uses XIOS'
215    ELSE
216      CALL getin_p('WRITE_STEP', dw)
217      IF ( dw == 0 .AND. printlev>=1) WRITE(numout,*) 'sechiba_history file will not be created'
218    END IF
219   
220    veg(1:nvm)   = (/ (REAL(i,r_std),i=1,nvm) /)
221    indlai(1:nlai+1) = (/ (REAL(i,r_std),i=1,nlai+1) /)
222    indlai0(1:nlai) = (/ (REAL(i,r_std),i=1,nlai) /)
223    soltyp(1:nstm) = (/ (REAL(i,r_std),i=1,nstm) /)
224    nobiotyp(1:nnobio) = (/ (REAL(i,r_std),i=1,nnobio) /)
225    albtyp(1:2) = (/ (REAL(i,r_std),i=1,2) /)
226    solay(1:nslm) = (/ (REAL(i,r_std),i=1,nslm) /)
227    snowlev =  (/ (REAL(i,r_std),i=1,nsnow) /)
228!! yidi
229    phylev =  (/ (REAL(i,r_std),i=1,nphs) /)
230!! yidi
231    ! Get the vertical soil levels for the thermal scheme
232    IF (hydrol_cwrr) THEN
233       sol(1:ngrnd) = znt(:)
234    ELSE
235       sol(1:ngrnd) = thermosoilc_levels()
236    END IF
237
238    !
239    !- We need to flux averaging operation as when the data is written
240    !- from within SECHIBA a scatter is needed. In the driver on the other
241    !- hand the data is 2D and can be written is it is.
242    !-
243    WRITE(flux_op,'("ave(scatter(X*",F8.1,"))")') one_day/dt
244    ! WRITE(flux_op,'("(ave(scatter(X))*",F8.1,")")') one_day/dt
245!    WRITE(flux_sc,'("ave(X*",F8.1,")")') one_day/dt
246!    WRITE(flux_insec,'("ave(X*",F8.6,")")') un/dt
247!    WRITE(flux_insec,'("ave(X*",F12.10,")")') un/dt
248    WRITE(flux_scinsec,'("ave(scatter(X*",F12.10,"))")') un/dt
249    IF (printlev>=2) WRITE(numout,*) 'flux_op=',flux_op,' one_day/dt=', one_day/dt, ' dt=',dt,' dw=', dw
250    !-
251    !Config Key   = SECHIBA_HISTLEVEL
252    !Config Desc  = SECHIBA history output level (0..10)
253    !Config If    = OK_SECHIBA and HF
254    !Config Def   = 5
255    !Config Help  = Chooses the list of variables in the history file.
256    !Config         Values between 0: nothing is written; 10: everything is
257    !Config         written are available More details can be found on the web under documentation.
258    !Config Units = [-]
259    !-
260    hist_level = 5
261    CALL getin_p('SECHIBA_HISTLEVEL', hist_level)
262    !-
263    IF (printlev>=2) WRITE(numout,*) 'SECHIBA history level: ',hist_level
264    IF ( (hist_level > max_hist_level).OR.(hist_level < 0) ) THEN
265       STOP 'This history level is not allowed'
266    ENDIF
267    !-
268    !- define operations as a function of history level.
269    !- Above hist_level, operation='never'
270    !-
271    ave(1:max_hist_level) = 'ave(scatter(X))'
272    IF (hist_level < max_hist_level) THEN
273       ave(hist_level+1:max_hist_level) = 'never'
274    ENDIF
275    sumscatter(1:max_hist_level) = 't_sum(scatter(X))'
276    IF (hist_level < max_hist_level) THEN
277       sumscatter(hist_level+1:max_hist_level) = 'never'
278    ENDIF
279
280    avecels(1:max_hist_level) = 'ave(cels(scatter(X)))'
281    IF (hist_level < max_hist_level) THEN
282       avecels(hist_level+1:max_hist_level) = 'never'
283    ENDIF
284
285    avescatter(1:max_hist_level) = 'ave(scatter(X))'
286    IF (hist_level < max_hist_level) THEN
287       avescatter(hist_level+1:max_hist_level) = 'never'
288    ENDIF
289    tmincels(1:max_hist_level) = 't_min(cels(scatter(X)))'
290    IF (hist_level < max_hist_level) THEN
291       tmincels(hist_level+1:max_hist_level) = 'never'
292    ENDIF
293    tmaxcels(1:max_hist_level) = 't_max(cels(scatter(X)))'
294    IF (hist_level < max_hist_level) THEN
295       tmaxcels(hist_level+1:max_hist_level) = 'never'
296    ENDIF
297!!!!! for crops
298    ! add for nlev, ndrp, etc
299    tmax(1:max_hist_level) = 't_max(scatter(X))'
300    IF (hist_level < max_hist_level) THEN
301       tmax(hist_level+1:max_hist_level) = 'never'
302    ENDIF
303!!!!! xuhui
304
305    fluxop(1:max_hist_level) = flux_op
306    IF (hist_level < max_hist_level) THEN
307       fluxop(hist_level+1:max_hist_level) = 'never'
308    ENDIF
309
310    fluxop_scinsec(1:max_hist_level) = flux_scinsec
311    IF (hist_level < max_hist_level) THEN
312       fluxop_scinsec(hist_level+1:max_hist_level) = 'never'
313    ENDIF
314    once(1:max_hist_level) = 'once(scatter(X))'
315    IF (hist_level < max_hist_level) THEN
316       once(hist_level+1:max_hist_level) = 'never'
317    ENDIF
318
319
320    !- Initialize sechiba_history output file
321    !-
322    IF ( dw == 0 ) THEN
323       ! sechiba_history file will not be created.
324       hist_id = -1
325
326    ELSE
327       ! sechiba_history file will be created
328
329       ! If running in parallel (mpi_size>1), test if there are at least 2 latitude bands(jj_nb) for current MPI process.
330       ! The model can work with 1 latitude band but the rebuild fails. Therefor exit if this is the cas.
331       IF ( jj_nb < 2 .AND. mpi_size > 1) THEN
332          CALL ipslerr_p(3,"ioipslctrl_history","The current MPI process has jj_nb=1 (1 band of latitude) but", &
333               "the IOIPSL rebuild tool can not work if jj_nb is less than 2 per MPI process.", &
334               "Change to a lower number of MPI processors or make the region bigger in latitudes.")
335       END IF
336
337       !- Calculation necessary for initialization of sechiba_history file
338       !- Check if we have by any change a rectilinear grid. This would allow us to
339       !- simplify the output files.
340    IF (is_omp_root) THEN
341       !
342       IF ( GridType == "RegLonLat" ) THEN
343          ALLOCATE(lon_rect(iim),stat=ier)
344          IF (ier .NE. 0) THEN
345             WRITE (numout,*) ' error in lon_rect allocation. We stop. We need iim words = ',iim
346             STOP 'intersurf_history'
347          ENDIF
348          ALLOCATE(lat_rect(jjm),stat=ier)
349          IF (ier .NE. 0) THEN
350             WRITE (numout,*) ' error in lat_rect allocation. We stop. We need jjm words = ',jjm
351             STOP 'intersurf_history'
352          ENDIF
353          lon_rect(:) = lon(:,1)
354          lat_rect(:) = lat(1,:)
355       ENDIF
356       !-
357       !-
358       !-
359       ! Initialize sechiba_history file
360       IF ( .NOT. almaoutput ) THEN
361          !-
362          IF ( GridType == "RegLonLat" ) THEN
363#ifdef CPP_PARA
364             CALL histbeg(histname, iim, lon_rect, jjm, lat_rect, 1, iim, 1, jjm, &
365                  &     istp_old, date0, dt, hori_id, hist_id,orch_domain_id)
366#else
367             CALL histbeg(histname, iim, lon_rect, jjm, lat_rect, 1, iim, 1, jjm, &
368                  &     istp_old, date0, dt, hori_id, hist_id)
369#endif
370             IF (printlev >= 2) WRITE(numout,*)  'HISTBEG --->',istp_old,date0,dt,dw,hist_id
371          ELSE
372#ifdef CPP_PARA
373             CALL histbeg(histname, iim, lon, jjm, lat, 1, iim, 1, jjm, &
374                  &     istp_old, date0, dt, hori_id, hist_id,domain_id=orch_domain_id)
375#else
376             CALL histbeg(histname, iim, lon, jjm, lat, 1, iim, 1, jjm, &
377                  &     istp_old, date0, dt, hori_id, hist_id)
378#endif
379          ENDIF
380          !-
381          CALL histvert(hist_id, 'veget', 'Vegetation types', '1', &
382               &    nvm,   veg, vegax_id)
383          CALL histvert(hist_id, 'laiax0', 'Nb LAI - 1 layer', 'm', &
384               &   nlai,indlai0, laiax0_id)
385          CALL histvert(hist_id, 'laiax', 'Nb LAI', 'm', &
386               &   nlai+1,indlai, laiax_id)
387          CALL histvert(hist_id, 'solth', 'Soil levels',      'm', &
388               &    ngrnd, sol, solax_id)
389          CALL histvert(hist_id, 'soiltyp', 'Soil types',      '1', &
390               &    nstm, soltyp, soltax_id)
391          CALL histvert(hist_id, 'nobio', 'Other surface types',      '1', &
392               &    nnobio, nobiotyp, nobioax_id)
393          IF (  hydrol_cwrr ) THEN
394             CALL histvert(hist_id, 'solay', 'Hydrol soil levels',      'm', &
395                  &    nslm, diaglev(1:nslm), solayax_id)
396             CALL histvert(hist_id, 'soildiag', 'Diagnostic soil levels', 'm', &
397                  &    nslm, diaglev(1:nslm), soildiagax_id)
398          ENDIF
399
400          CALL histvert(hist_id, 'snowlev', 'Snow levels',      'm', &
401               &    nsnow, snowlev, snowax_id)
402          !-
403          !- SECHIBA_HISTLEVEL = 1
404          !-
405          CALL histdef(hist_id, 'evap', 'Evaporation', 'mm/d', &
406               & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop(1), dt,dw)
407          CALL histdef(hist_id, 'coastalflow', 'Diffuse coastal flow', 'm^3/s', &
408               & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop_scinsec(1), dt,dw)
409          CALL histdef(hist_id, 'riverflow', 'River flow to the oceans', 'm^3/s', &
410               & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop_scinsec(1), dt,dw) 
411          CALL histdef(hist_id, 'temp_sol', 'Surface Temperature', 'C', &
412               & iim,jjm, hori_id, 1,1,1, -99, 32, avecels(1), dt,dw)
413          CALL histdef(hist_id, 'temp_sol_pft', 'Surface Temperature pft', 'C', &
414               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(1), dt,dw)
415          CALL histdef(hist_id, 'rain', 'Rainfall', 'mm/d',  &
416               & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop(1), dt,dw)
417          CALL histdef(hist_id, 'snowf', 'Snowfall', 'mm/d',  &
418               & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop(1), dt,dw)
419          CALL histdef(hist_id, 'netrad', 'Net radiation', 'W/m^2',  &
420               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
421          CALL histdef(hist_id, 'lai', 'Leaf Area Index', '1', &
422               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(1), dt,dw)
423          !
424          IF (  hydrol_cwrr ) THEN
425             CALL histdef(hist_id, 'reinf_slope', 'Slope index for each grid box', '1', &
426                  & iim,jjm, hori_id, 1,1,1, -99, 32, once(1),  dt,dw)
427             CALL histdef(hist_id, 'soilindex', 'Soil index', '1', &
428                  & iim,jjm, hori_id, 1, 1, 1, -99, 32, once(1),  dt,dw)
429          ENDIF
430          !
431          IF ( river_routing ) THEN
432             CALL histdef(hist_id, 'basinmap', 'Aproximate map of the river basins', ' ', &
433                  & iim,jjm, hori_id, 1,1,1, -99, 32, once(1), dt,dw) 
434             CALL histdef(hist_id, 'nbrivers', 'Number or rivers in the outflow grid box', ' ', &
435                  & iim,jjm, hori_id, 1,1,1, -99, 32, once(1), dt,dw) 
436          ENDIF
437          !-
438          !- SECHIBA_HISTLEVEL = 2
439          !-
440          CALL histdef(hist_id, 'subli', 'Sublimation', 'mm/d', &
441               & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop(2), dt,dw)
442          CALL histdef(hist_id, 'evapnu', 'Bare soil evaporation', 'mm/d', &
443               & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop(2), dt,dw)
444          CALL histdef(hist_id, 'runoff', 'Surface runoff', 'mm/d', &
445               & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop(2), dt,dw)
446          CALL histdef(hist_id, 'drainage', 'Deep drainage', 'mm/d', &
447               & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop(2), dt,dw)
448          IF ( river_routing ) THEN
449             CALL histdef(hist_id, 'riversret', 'Return from endorheic rivers', 'mm/d', &
450                  & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop(2), dt,dw)
451             CALL histdef(hist_id, 'hydrographs', 'Hydrographs of gridbox outflow', 'm^3/s', &
452                  & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop_scinsec(2), dt,dw)
453          ENDIF
454
455
456!!!!! crop variables         
457          CALL histdef(hist_id, 'tcult', 'crop temperature', 'degree', &
458               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(10), dt,dw)
459   
460          CALL histdef(hist_id, 'udevair', 'udev calculated by Tair', '1', &
461               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(10), dt,dw)
462   
463          CALL histdef(hist_id, 'udevcult', 'udev calculated by tcult', '1', &
464               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(10), dt,dw)
465         
466          CALL histdef(hist_id, 'turfac', 'soil water stress for leaf growth', '1', &
467               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(10), dt,dw)
468   
469          CALL histdef(hist_id, 'swfac', 'water stress for RUE', '1', &
470               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(10), dt,dw)
471         
472          CALL histdef(hist_id, 'senfac', 'soil water stress for leaf senescence', '1', &
473               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(10), dt,dw)
474          CALL histdef(hist_id, 'shumrel', 'soil moisture around sowing depth', '1', &
475               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(10), dt,dw)
476   
477          CALL histdef(hist_id, 'nlev', 'date for leaf emerge', '1', &
478               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, tmax(2), dt,dw)
479   
480          CALL histdef(hist_id, 'nflo', 'date for flowering', '1', &
481               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, tmax(2), dt,dw)
482   
483          CALL histdef(hist_id, 'ndrp', 'date for grain filling', '1', &
484               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, tmax(2), dt,dw)
485   
486          CALL histdef(hist_id, 'nrec', 'date for harvesting', '1', &
487               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, tmax(2), dt,dw)
488   
489          CALL histdef(hist_id, 'nmat', 'date for physiological mature', '1', & 
490               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, tmax(2), dt,dw) 
491   
492          CALL histdef(hist_id, 'irrig_fin', 'final application of irrigation', 'mm', &
493               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, fluxop(1), dt,dw)
494
495          CALL histdef(hist_id, 'roughheight_pft', 'Effect roughness height pft', 'm',  &
496               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(3), dt,dw)
497!!!!!! end crop variables, xuhui
498
499          IF ( hydrol_cwrr ) THEN
500             CALL histdef(hist_id, 'evapnu_soil', 'Bare soil evap for soil type', 'mm/d', &
501                  & iim,jjm, hori_id, nstm, 1, nstm, soltax_id, 32, fluxop(2), dt,dw)
502             CALL histdef(hist_id, 'precip_soil', 'Precip for soil type', 'mm/d', &
503                  & iim,jjm, hori_id, nstm, 1, nstm, soltax_id, 32, fluxop(2), dt,dw)
504             CALL histdef(hist_id, 'drainage_soil', 'Drainage for soil type', 'mm/d', &
505                  & iim,jjm, hori_id, nstm, 1, nstm, soltax_id, 32, fluxop(2), dt,dw)
506             CALL histdef(hist_id, 'transpir_soil', 'Transpir for soil type', 'mm/d', &
507                  & iim,jjm, hori_id, nstm, 1, nstm, soltax_id, 32, fluxop(2), dt,dw)
508             CALL histdef(hist_id, 'runoff_soil', 'Runoff for soil type', 'mm/d', &
509                  & iim,jjm, hori_id, nstm, 1, nstm, soltax_id, 32, fluxop(2), dt,dw)
510          ENDIF
511          !
512          CALL histdef(hist_id, 'tair', 'Air Temperature', 'K',  &
513               & iim,jjm, hori_id, 1,1,1, -99, 32, ave(2), dt,dw)
514          CALL histdef(hist_id, 'qair', 'Air humidity', 'g/g',  &
515               & iim,jjm, hori_id, 1,1,1, -99, 32, ave(2), dt,dw)
516          CALL histdef(hist_id, 'q2m', '2m Air humidity', 'g/g',  &
517               & iim,jjm, hori_id, 1,1,1, -99, 32, ave(2), dt,dw)
518          CALL histdef(hist_id, 't2m', '2m Air Temperature', 'K',  &
519               & iim,jjm, hori_id, 1,1,1, -99, 32, ave(2), dt,dw)
520          CALL histdef(hist_id, 'alb_vis', 'Albedo visible', '1', &
521               & iim,jjm, hori_id, 1,1,1, -99, 32, ave(2), dt,dw)
522          CALL histdef(hist_id, 'alb_nir', 'Albedo near infrared', '1', &
523               & iim,jjm, hori_id, 1,1,1, -99, 32, ave(2), dt,dw)
524          CALL histdef(hist_id, 'soilalb_vis', 'Soil Albedo visible', '1', &
525               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(2), dt,dw)
526          CALL histdef(hist_id, 'soilalb_nir', 'Soil Albedo near infrared', '1', &
527               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(2), dt,dw)
528          CALL histdef(hist_id, 'vegalb_vis', 'Vegetation Albedo visible', '1', &
529               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(2), dt,dw)
530          CALL histdef(hist_id, 'vegalb_nir', 'Vegetation Albedo near infrared', '1', &
531               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(2), dt,dw)
532          CALL histdef(hist_id, 'z0m', 'Surface roughness for momentum', 'm',  &
533               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(2), dt,dw)
534          CALL histdef(hist_id, 'z0h', 'Surface roughness for heat', 'm',  &
535               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(2), dt,dw)
536          CALL histdef(hist_id, 'roughheight', 'Effective roughness height', 'm',  &
537               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(2), dt,dw)
538          CALL histdef(hist_id, 'transpir', 'Transpiration', 'mm/d', &
539               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, fluxop(2), dt,dw)
540          CALL histdef(hist_id, 'evapnu_pft', 'soil evaporation pft', 'mm/d', &
541               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, fluxop(2), dt,dw)
542          CALL histdef(hist_id, 'inter', 'Interception loss', 'mm/d', &
543               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, fluxop(2), dt,dw)
544          !-
545          !- SECHIBA_HISTLEVEL = 3
546          !-
547          CALL histdef(hist_id, 'tsol_max', 'Maximum Surface Temperature',&
548               & 'C', iim,jjm, hori_id, 1,1,1, -99, 32, tmaxcels(3), dt,dw)
549          CALL histdef(hist_id, 'tsol_min', 'Minimum Surface Temperature',&
550               & 'C', iim,jjm, hori_id, 1,1,1, -99, 32, tmincels(3), dt,dw)
551          CALL histdef(hist_id, 'fluxsens', 'Sensible Heat Flux', 'W/m^2',  &
552               & iim,jjm, hori_id, 1,1,1, -99, 32, ave(3), dt,dw)
553          CALL histdef(hist_id, 'fluxlat', 'Latent Heat Flux', 'W/m^2',  &
554               & iim,jjm, hori_id, 1,1,1, -99, 32, ave(3), dt,dw)
555          CALL histdef(hist_id, 'snow', 'Snow mass', 'kg/m^2', &
556               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(3), dt,dw)
557          CALL histdef(hist_id, 'snowage', 'Snow age', '?', &
558               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(3), dt,dw)
559          CALL histdef(hist_id, 'snownobio', 'Snow on other surfaces', 'kg/m^2', &
560               & iim,jjm, hori_id, nnobio,1, nnobio, nobioax_id, 32, avescatter(3), dt,dw)
561          CALL histdef(hist_id, 'snownobioage', 'Snow age on other surfaces', 'd', &
562               & iim,jjm, hori_id, nnobio,1, nnobio, nobioax_id, 32, avescatter(3), dt,dw)
563          CALL histdef(hist_id, 'vegetfrac', 'Fraction of vegetation', '1', &
564               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(3), dt,dw)
565          CALL histdef(hist_id, 'maxvegetfrac', 'Maximum fraction of vegetation', '1', &
566               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(3), dt,dw)
567          CALL histdef(hist_id, 'tot_bare_soil', "Total Bare Soil Fraction", "%", &
568               & iim,jjm, hori_id, 1, 1, 1, -99, 32, avescatter(3), dt,dw)
569          CALL histdef(hist_id, 'nobiofrac', 'Fraction of other surface types', '1', &
570               & iim,jjm, hori_id, nnobio, 1, nnobio, nobioax_id, 32, avescatter(3), dt,dw)
571          IF ( river_routing .AND. do_floodplains ) THEN
572             CALL histdef(hist_id, 'flood_frac', 'Flooded fraction', '1', &
573                  & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(3), dt,dw)
574             CALL histdef(hist_id, 'reinfiltration', 'Reinfiltration from floodplains', 'mm/d', &
575                  & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop(3), dt,dw)
576          ENDIF
577          IF ( hydrol_cwrr ) THEN
578             DO jst=1,nstm
579             
580                ! var_name= "mc_1" ... "mc_3"
581                WRITE (var_name,"('moistc_',i1)") jst
582                CALL histdef(hist_id, var_name, 'Soil Moisture profile for soil type', 'm3/m3', &
583                     & iim,jjm, hori_id, nslm, 1, nslm, solayax_id, 32, avescatter(3),  dt,dw)
584               
585                ! var_name= "vegetsoil_1" ... "vegetsoil_3"
586                WRITE (var_name,"('vegetsoil_',i1)") jst
587                CALL histdef(hist_id, var_name, 'Fraction of vegetation on soil types', '%', &
588                     & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(3),  dt,dw)
589               
590                ! var_name= "kfact_root_1" ... "kfact_root_3"
591                WRITE (var_name,"('kfactroot_',i1)") jst
592                CALL histdef(hist_id, var_name, 'Root fraction profile for soil type', '%', &
593                     & iim,jjm, hori_id, nslm, 1, nslm, solayax_id, 32, avescatter(3), dt,dw)
594               
595             ENDDO
596
597             IF (ok_freeze_cwrr) THEN
598                CALL histdef(hist_id, 'profil_froz_hydro', 'Frozen fraction for each hydrological soil layer', '-', &
599                     & iim,jjm, hori_id, nslm, 1, nslm, solayax_id, 32, avescatter(1),  dt,dw)
600                CALL histdef(hist_id, 'temp_hydro', 'Soil temperature interpolated on hydrological layers', 'K', &
601                     & iim,jjm, hori_id, nslm, 1, nslm, solayax_id, 32, avescatter(1), dt,dw)
602             END IF
603
604             CALL histdef(hist_id, 'kk_moy', 'Mean hydrological conductivity', 'mm/d', &
605                  & iim,jjm,hori_id, nslm,1,nslm, solayax_id, 32, avescatter(1),  dt,dw)
606             DO jst=1,nstm
607                WRITE (var_name,"('profil_froz_hydro_',i1)") jst
608                CALL histdef(hist_id, trim(var_name), 'Frozen fraction for each hydrological soil layer and soiltile', '-', &
609                     & iim,jjm, hori_id, nslm, 1, nslm, solayax_id, 32, avescatter(1),  dt,dw)
610             ENDDO
611
612            DO jv = 1, nvm
613               WRITE(part_str,'(I2)') jv
614               IF (jv < 10) part_str(1:1) = '0'
615               CALL histdef(hist_id,'shum_ngrnd_perma_'//part_str(1:LEN_TRIM(part_str)), 'Saturation degree on thethermal axes', '-', &
616                    & iim,jjm, hori_id, ngrnd, 1, ngrnd, solax_id, 32, avescatter(6),  dt,dw)
617            END DO
618
619            DO jv = 1, nvm
620               WRITE(part_str,'(I2)') jv
621               IF (jv < 10) part_str(1:1) = '0'
622               CALL histdef(hist_id,'shum_perma_long_'//part_str(1:LEN_TRIM(part_str)), &
623                    & 'Long-term Saturation degree on the thermal axes', '-', &
624                    & iim,jjm, hori_id, ngrnd, 1, ngrnd, solax_id, 32,avescatter(6),  dt,dw)
625            END DO
626
627            DO jv = 1, nvm
628               WRITE(part_str,'(I2)') jv
629               IF (jv < 10) part_str(1:1) = '0'
630               CALL histdef(hist_id, 'wetdiag_'//part_str(1:LEN_TRIM(part_str)), 'Deep ground moisture', 'fraction', &
631                    & iim,jjm, hori_id, ngrnd, 1, ngrnd, solax_id, 32, avescatter(6),  dt,dw)
632            END DO
633
634            DO jv = 1, nvm
635               WRITE(part_str,'(I2)') jv
636               IF (jv < 10) part_str(1:1) = '0'
637               CALL histdef(hist_id, 'shum_ngrnd_prmlng_'//part_str(1:LEN_TRIM(part_str)), 'Long-term soil humidity', 'fraction', &
638                    & iim,jjm, hori_id, ngrnd, 1, ngrnd, solax_id, 32, avescatter(6),  dt,dw)
639            END DO
640
641            !          CALL histdef(hist_id, 'wetdiag', 'Deep ground moisture',
642            !          'fraction', &
643            !               & iim,jjm, hori_id, ngrnd, 1, ngrnd, solax_id, 32,
644            !               avescatter(6),  dt,dw)
645            !DO jv = 1, nvm
646            !   WRITE(part_str,'(I2)') jv
647            !   IF (jv < 10) part_str(1:1) = '0'
648            !   CALL histdef(hist_id, 'wetdiaglong_'//part_str(1:LEN_TRIM(part_str)), 'Long-term deep ground moisture', 'fraction', &
649            !        & iim,jjm, hori_id, ngrnd, 1, ngrnd, solax_id, 32, avescatter(6),  dt,dw)
650            !END DO
651
652
653             CALL histdef(hist_id, 'shumdiag_perma', 'Saturation degree of the soil', '-', &
654                  & iim,jjm,hori_id,nslm,1,nslm, soildiagax_id, 32, avescatter(1),  dt,dw)
655          ENDIF
656          !
657          CALL histdef(hist_id, 'frac_bare', 'Bare soil fraction for each tile', '-', &
658               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(3), dt,dw)
659          CALL histdef(hist_id, 'soiltile', 'Fraction of soil tiles', '%', &
660               & iim,jjm, hori_id, nstm, 1, nstm, soltax_id, 32, avescatter(4),  dt,dw)
661          !-
662          !- SECHIBA_HISTLEVEL = 4
663          !-
664          IF ( .NOT. hydrol_cwrr ) THEN
665             CALL histdef(hist_id, 'dss', 'Up-reservoir Height', 'm',  &
666                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(4), dt,dw)
667             CALL histdef(hist_id, 'gqsb', 'Upper Soil Moisture', 'Kg/m^2',  &
668                  & iim,jjm, hori_id, 1, 1, 1, -99, 32, avescatter(4), dt,dw)
669             CALL histdef(hist_id, 'bqsb', 'Lower Soil Moisture', 'Kg/m^2',  &
670                  & iim,jjm, hori_id, 1, 1, 1, -99, 32, avescatter(4), dt,dw)
671             CALL histdef(hist_id, 'bqsb_pft', 'Lower Soil Moisture', 'Kg/m^2',  &
672                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(4), dt,dw)
673             CALL histdef(hist_id, 'runoff_pft', 'runoff of each pft', 'Kg/m^2',  &
674                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(4), dt,dw)
675
676          ELSE
677             CALL histdef(hist_id, 'humtot', 'Total Soil Moisture', 'Kg/m^2', &
678                  & iim,jjm, hori_id, 1, 1, 1, -99, 32, avescatter(4), dt,dw)
679             CALL histdef(hist_id, 'humtot_soil', 'Soil Moisture for soil type', 'Kg/m^2', &
680                  & iim,jjm, hori_id, nstm, 1, nstm, soltax_id, 32, avescatter(4), dt,dw)
681!gmjc 6 layer soil moisture
682             CALL histdef(hist_id, 'tmc_trampling', '10cm Soil Moisture for soil type', 'Kg/m^2', &
683                  & iim,jjm, hori_id, nstm, 1, nstm, soltax_id, 32, avescatter(4), dt,dw)
684!end gmjc
685             CALL histdef(hist_id, 'njsc', 'Soil class used for hydrology', '-', &
686                  & iim,jjm, hori_id, 1, 1, 1, -99, 32, once(4), dt,dw)
687
688!pss:+
689             IF ( TOPM_calcul ) CALL topmodel_histdef(iim, jjm, dt, hist_id, &
690                                      hori_id, dw, avescatter, fluxop)
691           
692!!pss:-
693          ENDIF
694          CALL histdef(hist_id, 'qsintveg', 'Water on canopy', 'Kg/m^2', &
695               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(4), dt,dw)
696          CALL histdef(hist_id, 'rstruct', 'Structural resistance', 's/m', &
697               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(4), dt,dw)
698          IF ( ok_co2 ) THEN
699             CALL histdef(hist_id, 'gpp', 'Net assimilation of carbon by the vegetation', 'gC/m^2/s', &
700                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, fluxop_scinsec(4), dt,dw)
701             CALL histdef(hist_id, 'gpp_cl1', 'Net assimilation of carbon by the vegetation cl1', 'gC/m^2/s', &
702                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, fluxop_scinsec(4), dt,dw)
703             CALL histdef(hist_id, 'gpp_cl2', 'Net assimilation of carbon by the vegetation cl2', 'gC/m^2/s', &
704                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, fluxop_scinsec(4), dt,dw)
705             CALL histdef(hist_id, 'gpp_cl3', 'Net assimilation of carbon by the vegetation cl3', 'gC/m^2/s', &
706                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, fluxop_scinsec(4), dt,dw)
707             CALL histdef(hist_id, 'gpp_cl4', 'Net assimilation of carbon by the vegetation cl4', 'gC/m^2/s', &
708                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, fluxop_scinsec(4), dt,dw)
709             CALL histdef(hist_id, 'gpp_xc', 'Net assimilation of carbon by the vegetation xc', 'gC/m^2/s', &
710                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, fluxop_scinsec(4), dt,dw)
711          ENDIF
712          IF ( ok_stomate ) THEN
713             CALL histdef(hist_id, 'nee', 'Net Ecosystem Exchange', 'gC/m^2/s', &
714                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, fluxop_scinsec(4), dt,dw)
715             CALL histdef(hist_id, 'maint_resp', 'Maintenance respiration', 'gC/m^2/s', &
716                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, fluxop_scinsec(4), dt,dw)
717             CALL histdef(hist_id, 'hetero_resp', 'Heterotrophic respiration', 'gC/m^2/s', &
718                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, fluxop_scinsec(4), dt,dw)
719             CALL histdef(hist_id, 'growth_resp', 'Growth respiration', 'gC/m^2/s', &
720                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, fluxop_scinsec(4), dt,dw)
721             CALL histdef(hist_id, 'npp', 'Net Primary Production', 'gC/m^2/s', &
722                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, fluxop_scinsec(1), dt, dw)
723          ENDIF
724          CALL histdef(hist_id, 'precisol', 'Throughfall', 'mm/d',  &
725               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, fluxop(4), dt,dw)
726          CALL histdef(hist_id, 'drysoil_frac', 'Fraction of visibly dry soil', '1',  &
727               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(4), dt,dw)
728          CALL histdef(hist_id, 'evapot', 'Potential evaporation', 'mm/d',  &
729               & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop(4), dt,dw)
730          CALL histdef(hist_id, 'evapot_corr', 'Potential evaporation', 'mm/d',  &
731               & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop(4), dt,dw)
732          CALL histdef(hist_id, 'transpot', 'Potential transporation', 'mm/d', &
733               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, fluxop(4), dt,dw)
734          !-
735          !- SECHIBA_HISTLEVEL = 5
736          !-
737          CALL histdef(hist_id, 'swnet', 'Net solar radiation', 'W/m^2',  &
738               & iim,jjm, hori_id, 1,1,1, -99, 32, ave(5), dt,dw)
739          CALL histdef(hist_id, 'swdown', 'Incident solar radiation', 'W/m^2',  &
740               & iim,jjm, hori_id, 1,1,1, -99, 32, ave(5), dt,dw)
741          CALL histdef(hist_id, 'lwdown', 'Absorbed downward longwave radiation', 'W/m^2',  &
742               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(5), dt,dw)
743          CALL histdef(hist_id, 'lwnet', 'Net surface longwave radiation', 'W/m^2',  &
744               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(5), dt,dw)
745          !-
746          !- SECHIBA_HISTLEVEL = 6
747          !-
748           call histdef(hist_id, 'ptn_pftmean', 'Soil temperature, PFT-mean','K', &
749                & iim,jjm, hori_id, ngrnd, 1, ngrnd, solax_id, 32,avescatter(6), dt,dw)
750
751           DO jv = 1, nvm
752              IF (permafrost_veg_exists(jv)) THEN
753                 WRITE(part_str,'(I2)') jv
754                 IF (jv < 10) part_str(1:1) = '0'
755                 CALL histdef(hist_id, 'ptn_'//part_str(1:LEN_TRIM(part_str)),'Soil temperature', 'K', &
756                      & iim,jjm, hori_id, ngrnd, 1, ngrnd, solax_id, 32,avescatter(6),  dt,dw)
757              END IF
758           ENDDO
759
760          CALL histdef(hist_id, 'snowmelt', 'snow melt', 'mm/d', &
761               & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop(6), dt,dw)
762          CALL histdef(hist_id, 'frac_snow_veg', 'snow fraction on vegeted area','-', &
763               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(6), dt,dw)
764          CALL histdef(hist_id, 'frac_snow_nobio', 'snow fraction on non-vegeted area', '-', &
765               & iim,jjm, hori_id, nnobio, 1,nnobio, nobioax_id, 32, avescatter(6), dt,dw)
766          CALL histdef(hist_id, 'pgflux', 'extra energy used for melting top snow layer', '-', &
767               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(6), dt,dw)
768
769          CALL histdef(hist_id, 'soilflx_pft', 'Soil Heat Flux', 'W/m2',  &
770               & iim,jjm, hori_id, nvm,1,nvm, vegax_id, 32, avescatter(3), dt,dw)
771          CALL histdef(hist_id, 'soilcap_pft', 'Soil Heat Capacit', 'J/m2/K',  &
772               & iim,jjm, hori_id, nvm,1,nvm, vegax_id, 32, avescatter(3), dt,dw)
773          CALL histdef(hist_id, 'soilflx','Soil flux','W/m2', &
774               & iim,jjm, hori_id, 1, 1, 1, -99, 32,avescatter(3),dt,dw)
775          CALL histdef(hist_id, 'soilcap','Soil heat capacity','J/m2/K', &
776               & iim,jjm, hori_id, 1, 1, 1, -99, 32,avescatter(3),dt,dw)
777             
778          IF (ok_explicitsnow) THEN
779             CALL histdef(hist_id, 'grndflux', 'ground heat flux', 'W/m2', &
780                  & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(6), dt,dw)
781             CALL histdef(hist_id, 'snowrho', 'Snow density profile', 'kg/m3', & 
782                  & iim,jjm, hori_id, nsnow, 1, nsnow, snowax_id, 32,avescatter(6), dt,dw)
783             CALL histdef(hist_id, 'snowtemp','Snow temperature profile','K', &
784                  & iim,jjm, hori_id, nsnow, 1, nsnow, snowax_id, 32,avescatter(6),dt,dw)
785             CALL histdef(hist_id, 'snowdz','Snow depth profile','m', &
786                  & iim,jjm, hori_id, nsnow, 1, nsnow, snowax_id, 32,avescatter(6),dt,dw)
787             CALL histdef(hist_id, 'snowliq','Snow liquid content profile','m', &
788                  & iim,jjm, hori_id, nsnow, 1, nsnow, snowax_id, 32,avescatter(6),dt,dw)
789             CALL histdef(hist_id, 'snowgrain','Snow grain profile','m', &
790                  & iim,jjm, hori_id, nsnow, 1, nsnow, snowax_id, 32,avescatter(6),dt,dw)
791             CALL histdef(hist_id, 'snowheat','Snow Heat profile','J/m2', &
792                  & iim,jjm, hori_id, nsnow, 1, nsnow, snowax_id, 32,avescatter(6),dt,dw)
793             CALL histdef(hist_id, 'snowflx','Snow flux','W/m2', &
794                  & iim,jjm, hori_id, 1, 1, 1, snowax_id, 32,avescatter(1),dt,dw)
795            CALL histdef(hist_id, 'snowcap','Snow capacity','W/m2', &
796                  & iim,jjm, hori_id, 1, 1, 1, snowax_id, 32,avescatter(1),dt,dw)
797            CALL histdef(hist_id, 'temp_sol_add','surface temperature from fluxes','K', &
798                  & iim,jjm, hori_id, 1, 1, 1, snowax_id, 32,avescatter(1),dt,dw)
799            CALL histdef(hist_id, 'cgrnd_snow','cgrnd for snow','-', &
800                  & iim,jjm, hori_id, nsnow, 1, nsnow, snowax_id, 32,avescatter(1),dt,dw)
801            CALL histdef(hist_id, 'dgrnd_snow','dgrnd for snow','-', &
802                  & iim,jjm, hori_id, nsnow, 1, nsnow, snowax_id, 32,avescatter(1),dt,dw)
803
804          END IF
805          CALL histdef(hist_id, 'Qg', 'Ground heat flux', 'W/m^2',  &
806               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
807
808         IF (hydrol_cwrr .AND. ok_freeze_thermix) THEN
809          DO jv = 1, nvm
810             IF (permafrost_veg_exists(jv)) THEN
811                WRITE(part_str,'(I2)') jv
812                IF (jv < 10) part_str(1:1) = '0'
813                CALL histdef(hist_id, 'pcapa_'//part_str(1:LEN_TRIM(part_str)),'Apparent heat capacity', 'J/m3/K', &
814                     & iim,jjm, hori_id, ngrnd, 1, ngrnd, solax_id, 32,avescatter(6),  dt,dw)
815                CALL histdef(hist_id, 'pkappa_'//part_str(1:LEN_TRIM(part_str)),'Soil thermal conductivity', 'W/m/K', &
816                     & iim,jjm, hori_id, ngrnd, 1, ngrnd, solax_id, 32,avescatter(6),  dt,dw)
817                CALL histdef(hist_id, 'pcappa_supp_'//part_str(1:LEN_TRIM(part_str)), 'Additional heat capacity due to soil freezing for each soil layer', 'J/K', &
818                     & iim,jjm,hori_id, ngrnd,1,ngrnd, solax_id, 32, avescatter(1),  dt,dw)
819                CALL histdef(hist_id, 'ptn_beg_'//part_str(1:LEN_TRIM(part_str)), 'Soil temperature from previous time step', 'K', &
820                  & iim,jjm,hori_id, ngrnd,1,ngrnd, solax_id, 32, avescatter(1),  dt,dw)
821             END IF
822          END DO
823
824         ENDIF
825
826
827          !-
828          !- SECHIBA_HISTLEVEL = 7
829          !-
830          IF ( river_routing ) THEN
831             CALL histdef(hist_id, 'fastr', 'Fast flow reservoir', 'kg/m^2', &
832                  & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(7), dt,dw)
833             CALL histdef(hist_id, 'slowr', 'Slow flow reservoir', 'kg/m^2', &
834                  & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(7), dt,dw)
835             CALL histdef(hist_id, 'streamr', 'Stream flow reservoir', 'kg/m^2', &
836                  & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(7), dt,dw)
837             CALL histdef(hist_id, 'lakevol', 'Volume in lake reservoir', 'kg/m^2', &
838                  & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(7), dt,dw)
839             
840             !-
841             !- SECHIBA_HISTLEVEL = 8
842             !-
843             CALL histdef(hist_id, 'pondr', 'Ponds reservoir', 'kg/m^2', &
844                  & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(8), dt,dw)
845             CALL histdef(hist_id, 'swampmap', 'Map of swamps', 'm^2', &
846                  & iim,jjm, hori_id, 1,1,1, -99, 32, once(8), dt,dw)
847             !
848             IF ( do_irrigation ) THEN
849                CALL histdef(hist_id, 'irrigation', 'Net irrigation', 'mm/d', &
850                     & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop(8), dt,dw)
851!                CALL histdef(hist_id, 'netirrig', 'Net irrigation requirement', 'mm/d', &
852!                     & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop(8), dt,dw)
853                CALL histdef(hist_id, 'irrigmap', 'Map of irrigated surfaces', 'm^2', &
854                     & iim,jjm, hori_id, 1,1,1, -99, 32, once(8), dt,dw)
855             ENDIF
856
857             IF ( river_routing .AND. do_floodplains ) THEN
858                CALL histdef(hist_id, 'floodmap', 'Map of floodplains', 'm^2', &
859                     & iim,jjm, hori_id, 1,1,1, -99, 32, once(8), dt,dw)
860                CALL histdef(hist_id, 'floodh', 'Floodplains height', 'mm', &
861                     & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(8), dt,dw)
862                CALL histdef(hist_id, 'floodr', 'Floodplains reservoir', 'kg/m^2', &
863                     & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(8), dt,dw)
864                CALL histdef(hist_id, 'floodout', 'Flow out of floodplains', 'mm/d', &
865                     & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop(8), dt,dw)
866                CALL histdef(hist_id, 'evapflo', 'Floodplains evaporation', 'mm/d', &
867                     & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop(8), dt,dw)
868             ENDIF
869             !
870          ENDIF
871          ! define irrigation regardless of river_routing and do_irrigation
872          CALL histdef(hist_id, 'irrigation', 'Net irrigation', 'mm/d', &
873               & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop(1), dt,dw)
874
875          IF ( hydrol_cwrr ) THEN
876             CALL histdef(hist_id, 'k_litt', 'Litter cond', 'mm/d', &
877                  & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(8), dt,dw)
878          ENDIF
879          CALL histdef(hist_id, 'beta', 'Beta Function', '1',  &
880               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(8), dt,dw)
881          CALL histdef(hist_id, 'raero', 'Aerodynamic resistance', 's/m',  &
882               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(8), dt,dw)
883          ! Ajouts Nathalie - Novembre 2006
884          CALL histdef(hist_id, 'cdrag', 'Drag coefficient for LE and SH', '?',  &
885               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(8), dt,dw)
886          CALL histdef(hist_id, 'Wind', 'Wind speed', 'm/s',  &
887               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(8), dt,dw)
888          ! Fin ajouts Nathalie
889          !
890          CALL histdef(hist_id, 'qsatt' , 'Surface saturated humidity', 'g/g', &
891               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(8), dt,dw)
892          CALL histdef(hist_id, 'vbeta1', 'Beta for sublimation', '1',  &
893               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(8), dt,dw)
894          CALL histdef(hist_id, 'vbeta4', 'Beta for bare soil', '1',  &
895               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(8), dt,dw)
896          CALL histdef(hist_id, 'vbeta5', 'Beta for floodplains', '1',  &
897               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(8), dt,dw)
898          IF ( ok_co2 ) THEN
899             CALL histdef(hist_id, 'gsmean', 'mean stomatal conductance', 'mol/m2/s', &
900                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(8), dt,dw)
901          ENDIF
902          CALL histdef(hist_id, 'humrel', 'Soil moisture stress', '-',  &
903               & iim,jjm, hori_id, nvm,1,nvm, vegax_id, 32, avescatter(8), dt,dw)
904          CALL histdef(hist_id, 'vegstress', 'Vegetation growth stress', '-',  &
905               & iim,jjm, hori_id, nvm,1,nvm, vegax_id, 32, avescatter(8), dt,dw)
906          CALL histdef(hist_id, 'soil_deficit', 'SoilWaterDefict to FillThr', 'mm',  &
907               & iim,jjm, hori_id, nvm,1,nvm, vegax_id, 32, avescatter(8), dt,dw)
908          !-
909          !- SECHIBA_HISTLEVEL = 9
910          !-
911          !-
912          !- SECHIBA_HISTLEVEL = 10
913          !-
914          IF ( ok_co2 ) THEN
915             CALL histdef(hist_id, 'cimean', 'Stomatal CO2 concentation', 'mmole/m2/s', &
916                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(10), dt,dw)
917             CALL histdef(hist_id, 'cim', 'cim', 'ppm', &
918                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(10), dt,dw)
919             CALL histdef(hist_id, 'leafci', 'leaf ci', 'ppm', &
920                  & iim,jjm, hori_id, nlai, 1, nlai, laiax0_id, 32, avescatter(10), dt,dw)
921             CALL histdef(hist_id, 'gs', 'gs', 'mol m-2 s-1', &
922                  & iim,jjm, hori_id, nlai+1, 1, nlai+1, laiax_id, 32, avescatter(10), dt,dw)
923             CALL histdef(hist_id, 'assimi', 'assimi', 'mol m-2 s-1', &
924                  & iim,jjm, hori_id, nlai+1, 1, nlai+1, laiax_id, 32, avescatter(10), dt,dw)
925             CALL histdef(hist_id, 'Rd', 'Rd', 'mol m-2 s-1', &
926                  & iim,jjm, hori_id, nlai+1, 1, nlai+1, laiax_id, 32, avescatter(10), dt,dw)
927             CALL histdef(hist_id, 'Cc', 'Cc', 'ppm', &
928                  & iim,jjm, hori_id, nlai+1, 1, nlai+1, laiax_id, 32, avescatter(10), dt,dw)
929             CALL histdef(hist_id, 'limitphoto', 'limitphoto', '-', &
930                  & iim,jjm, hori_id, nlai+1, 1, nlai+1, laiax_id, 32, avescatter(10), dt,dw)
931             CALL histdef(hist_id, 'Vc', 'Vc', 'mol m-2 s-1', &
932                  & iim,jjm, hori_id, nlai+1, 1, nlai+1, laiax_id, 32, avescatter(10), dt,dw)
933             CALL histdef(hist_id, 'Vj', 'Vj', 'mol e- m-2 s-1', &
934                  & iim,jjm, hori_id, nlai+1, 1, nlai+1, laiax_id, 32, avescatter(10), dt,dw)
935             CALL histdef(hist_id, 'gm', 'gm', 'mol m-2 s-1', &
936                  & iim, jjm, hori_id, 1, 1, 1, -99, 32, avescatter(10), dt,dw)
937             CALL histdef(hist_id, 'gammastar', 'gammastar', 'ppm', &
938                  & iim, jjm, hori_id, 1, 1, 1, -99, 32, avescatter(10), dt,dw)
939             CALL histdef(hist_id, 'Kmo', 'Kmo', 'ppm', &
940                  & iim, jjm, hori_id, 1, 1, 1, -99, 32, avescatter(10), dt,dw)
941             CALL histdef(hist_id, 'Kmc', 'Kmc', 'ppm', &
942                  & iim, jjm, hori_id, 1, 1, 1, -99, 32, avescatter(10), dt,dw)
943          ENDIF
944          CALL histdef(hist_id, 'vbeta3', 'Beta for Transpiration', '1', &
945               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(10), dt,dw)
946          CALL histdef(hist_id, 'vbeta4_pft', 'Beta for bare soil evap', '1', &
947               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(10), dt,dw)
948          CALL histdef(hist_id, 'beta_pft', 'Beta for each pft', '1', &
949               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(8), dt,dw)
950          CALL histdef(hist_id, 'rveget', 'Canopy resistance', 's/m', &
951               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(10), dt,dw)
952          IF ( .NOT. hydrol_cwrr ) THEN
953             CALL histdef(hist_id, 'rsol', 'Soil resistance', 's/m',  &
954                  & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(10), dt,dw)
955          ENDIF
956          CALL histdef(hist_id,'vbeta2','Beta for Interception loss','mm/d', &
957               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(10), dt,dw)
958          CALL histdef(hist_id,'cdrag_pft','Drag coeff for pft','?', &
959               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(3), dt,dw)       
960          CALL histdef(hist_id, 'qsintmax', 'Maximum Interception capacity', 'Kg/m^2', &
961               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(10), dt,dw)
962
963          !- SECHIBA_HISTLEVEL = 11
964          !-
965
966          CALL histdef(hist_id, 'mrsos', "Moisture in Upper 0.1 m of Soil Column", "kg m-2", &
967               & iim,jjm, hori_id, 1, 1, 1, -99, 32, avescatter(11), dt,dw)
968         
969          CALL histdef(hist_id, 'mrso', "Total Soil Moisture Content", "kg m-2", &
970               & iim,jjm, hori_id, 1, 1, 1, -99, 32, avescatter(11), dt,dw)
971         
972          CALL histdef(hist_id, 'mrros', "Surface Runoff", "kg m-2 s-1", &
973               & iim,jjm, hori_id, 1, 1, 1, -99, 32, fluxop_scinsec(11), dt,dw)
974         
975          CALL histdef(hist_id, 'mrro', "Total Runoff", "kg m-2 s-1", &
976               & iim,jjm, hori_id, 1, 1, 1, -99, 32, fluxop_scinsec(11), dt,dw)
977
978          CALL histdef(hist_id, 'prveg', "Precipitation onto Canopy", "kg m-2 s-1", &
979               & iim,jjm, hori_id, 1, 1, 1, -99, 32, fluxop_scinsec(11), dt,dw)
980
981
982          CALL histdef(hist_id, 'evspsblveg', "Evaporation from Canopy", "kg m-2 s-1", &
983               & iim,jjm, hori_id, 1, 1, 1, -99, 32, fluxop_scinsec(11), dt,dw)
984         
985          CALL histdef(hist_id, 'evspsblsoi', "Water Evaporation from Soil", "kg m-2 s-1", &
986               & iim,jjm, hori_id, 1, 1, 1, -99, 32, fluxop_scinsec(11), dt,dw)
987         
988          CALL histdef(hist_id, 'tran', "Transpiration", "kg m-2 s-1", &
989               & iim,jjm, hori_id, 1, 1, 1, -99, 32, fluxop_scinsec(11), dt,dw)
990         
991          CALL histdef(hist_id, 'treeFrac', "Tree Cover Fraction", "%", &
992               & iim,jjm, hori_id, 1, 1, 1, -99, 32, avescatter(11), dt,dw)
993         
994          CALL histdef(hist_id, 'grassFrac', "Natural Grass Fraction", "%", &
995               & iim,jjm, hori_id, 1, 1, 1, -99, 32, avescatter(11), dt,dw)
996         
997          CALL histdef(hist_id, 'cropFrac', "Crop Fraction", "%", &
998               & iim,jjm, hori_id, 1, 1, 1, -99, 32, avescatter(11), dt,dw)
999         
1000          CALL histdef(hist_id, 'baresoilFrac', "Bare Soil Fraction", "%", &
1001               & iim,jjm, hori_id, 1, 1, 1, -99, 32, avescatter(11), dt,dw)
1002         
1003          CALL histdef(hist_id, 'residualFrac', &
1004               & "Fraction of Grid Cell that is Land but Neither Vegetation-Covered nor Bare Soil", "%", &
1005               & iim,jjm, hori_id, 1, 1, 1, -99, 32, avescatter(11), dt,dw)
1006         
1007          IF ( ok_bvoc ) THEN
1008             CALL histdef(hist_id, 'PAR', 'PAR', 'umol phot/m^2/s',  &
1009                  & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(11), dt,dw)
1010             IF ( ok_radcanopy ) THEN
1011                CALL histdef(hist_id, 'PARsun', 'Sunlit Leaf PAR', 'umol phot/m^2/s', &
1012                     & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(11), dt,dw)
1013                CALL histdef(hist_id, 'PARsh', 'Shaded Leaf Area PAR', 'umol phot/m^2/s', &
1014                     & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(11), dt,dw)
1015                CALL histdef(hist_id, 'laisun', 'Sunlit Leaf Area Index', '1', &
1016                     & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(11), dt,dw)
1017                CALL histdef(hist_id, 'laish', 'Shaded Leaf Area Index', '1', &
1018                     & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(11), dt,dw)
1019                CALL histdef(hist_id, 'Fdf', 'Fdf', '1',  &
1020                     & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(11), dt,dw)
1021                IF ( ok_multilayer ) then
1022                   CALL histdef(hist_id, 'PARsuntab', 'Sunlit Leaf PAR', 'umol phot/m^2/s', &
1023                        & iim,jjm, hori_id, nlai+1, 1, nlai+1, laiax_id, 32, avescatter(11), dt,dw)
1024                   CALL histdef(hist_id, 'PARshtab', 'Shaded Leaf Area PAR', 'umol phot/m^2/s', &
1025                        & iim,jjm, hori_id, nlai+1, 1, nlai+1, laiax_id, 32, avescatter(11), dt,dw)
1026                ENDIF
1027                CALL histdef(hist_id, 'coszang', 'coszang', '1',  &
1028                     & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(11), dt,dw)
1029                CALL histdef(hist_id, 'PARdf', 'PARdf', '1',  &
1030                     & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(11), dt,dw)
1031                CALL histdef(hist_id, 'PARdr', 'PARdr', '1',  &
1032                     & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(11), dt,dw)
1033                CALL histdef(hist_id, 'Trans', 'Trans', '1',  &
1034                     & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(11), dt,dw)
1035             END IF
1036             
1037             CALL histdef(hist_id, 'flx_fertil_no', 'flx_fertil_no', 'ngN/m^2/s', &
1038                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(11), dt,dw)
1039             CALL histdef(hist_id, 'CRF', 'CRF', '1', &
1040                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(11), dt,dw)
1041             CALL histdef(hist_id, 'flx_co2_bbg_year', 'flx_co2_bbg_year', 'kgC/m^2/yr ', &
1042                  & iim,jjm, hori_id, 1,1,1, -99, 32, once(11), dt,dw) 
1043             CALL histdef(hist_id, 'N_qt_WRICE_year', 'N_qt_WRICE_year', 'kgN/yr ', &
1044                  & iim,jjm, hori_id, 1,1,1, -99, 32, once(11), dt,dw) 
1045             CALL histdef(hist_id, 'N_qt_OTHER_year', 'N_qt_OTHER_year', 'kgN/yr ', &
1046                  & iim,jjm, hori_id, 1,1,1, -99, 32, once(11), dt,dw) 
1047             CALL histdef(hist_id, 'flx_iso', 'flx_iso', 'kgC/m^2/s', &
1048                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(11), dt,dw)
1049             CALL histdef(hist_id, 'flx_mono', 'flx_mono', 'kgC/m^2/s',&
1050                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(11), dt,dw)
1051             CALL histdef(hist_id, 'flx_apinen', 'flx_apinen', 'kgC/m^2/s',&
1052                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(11), dt,dw)
1053             CALL histdef(hist_id, 'flx_bpinen', 'flx_bpinen', 'kgC/m^2/s',&
1054                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(11), dt,dw)
1055             CALL histdef(hist_id, 'flx_limonen', 'flx_limonen', 'kgC/m^2/s',&
1056                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(11), dt,dw)
1057             CALL histdef(hist_id, 'flx_myrcen', 'flx_myrcen', 'kgC/m^2/s',&
1058                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(11), dt,dw)
1059             CALL histdef(hist_id, 'flx_sabinen', 'flx_sabinen', 'kgC/m^2/s',&
1060                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(11), dt,dw)
1061             CALL histdef(hist_id, 'flx_camphen', 'flx_camphen', 'kgC/m^2/s',&
1062                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(11), dt,dw)
1063             CALL histdef(hist_id, 'flx_3caren', 'flx_3caren', 'kgC/m^2/s',&
1064                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(11), dt,dw)
1065             CALL histdef(hist_id, 'flx_tbocimen', 'flx_tbocimen', 'kgC/m^2/s',&
1066                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(11), dt,dw)
1067             CALL histdef(hist_id, 'flx_othermono', 'flx_othermono', 'kgC/m^2/s',&
1068                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(11), dt,dw)
1069             CALL histdef(hist_id, 'flx_sesquiter', 'flx_sesquiter', 'kgC/m^2/s',&
1070                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(11), dt,dw)
1071             CALL histdef(hist_id, 'flx_ORVOC', 'flx_ORVOC', 'kgC/m^2/s',&
1072                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(11), dt,dw)
1073             CALL histdef(hist_id, 'flx_MBO', 'flx_MBO', 'kgC/m^2/s',&
1074                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(11), dt,dw)
1075             CALL histdef(hist_id, 'flx_methanol', 'flx_methanol', 'kgC/m^2/s',&
1076                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(11), dt,dw)
1077             CALL histdef(hist_id, 'flx_acetone', 'flx_acetone', 'kgC/m^2/s',&
1078                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(11), dt,dw)
1079             CALL histdef(hist_id, 'flx_acetal', 'flx_acetal', 'kgC/m^2/s',&
1080                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(11), dt,dw)
1081             CALL histdef(hist_id, 'flx_formal', 'flx_formal', 'kgC/m^2/s',&
1082                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(11), dt,dw)
1083             CALL histdef(hist_id, 'flx_acetic', 'flx_acetic', 'kgC/m^2/s',&
1084                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(11), dt,dw)
1085             CALL histdef(hist_id, 'flx_formic', 'flx_formic', 'kgC/m^2/s',&
1086                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(11), dt,dw)
1087             CALL histdef(hist_id, 'flx_no_soil', 'flx_no_soil', 'ngN/m^2/s',&
1088                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(11), dt,dw)
1089             CALL histdef(hist_id, 'flx_no', 'flx_no', 'ngN/m^2/s',&
1090                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(11), dt,dw)
1091             CALL histdef(hist_id, 'fco2', 'fco2', '-', &
1092                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(10), dt,dw)
1093          ENDIF
1094
1095       ELSE 
1096          !-
1097          !- This is the ALMA convention output now
1098          !-
1099          !-
1100          IF ( GridType == "RegLonLat" ) THEN
1101#ifdef CPP_PARA
1102             CALL histbeg(histname, iim, lon_rect, jjm, lat_rect, 1, iim, 1, jjm, &
1103                  &     istp_old, date0, dt, hori_id, hist_id,orch_domain_id)
1104#else
1105             CALL histbeg(histname, iim, lon_rect, jjm, lat_rect, 1, iim, 1, jjm, &
1106                  &     istp_old, date0, dt, hori_id, hist_id)
1107#endif
1108          ELSE
1109#ifdef CPP_PARA
1110             CALL histbeg(histname, iim, lon, jjm, lat, 1, iim, 1, jjm, &
1111                  &     istp_old, date0, dt, hori_id, hist_id,domain_id=orch_domain_id)
1112#else
1113             CALL histbeg(histname, iim, lon, jjm, lat, 1, iim, 1, jjm, &
1114                  &     istp_old, date0, dt, hori_id, hist_id)
1115#endif
1116          ENDIF
1117          !-
1118          CALL histvert(hist_id, 'veget', 'Vegetation types', '1', &
1119               &    nvm,   veg, vegax_id)
1120          CALL histvert(hist_id, 'laiax0', 'Nb LAI - 1 layer', 'm', &
1121               &   nlai,indlai0, laiax0_id)
1122          CALL histvert(hist_id, 'laiax', 'Nb LAI', 'm', &
1123               &   nlai+1,indlai, laiax_id)
1124          CALL histvert(hist_id, 'solth', 'Soil levels',      'm', &
1125               &    ngrnd, sol, solax_id)
1126          CALL histvert(hist_id, 'soiltyp', 'Soil types',      '1', &
1127               &    nstm, soltyp, soltax_id)
1128          CALL histvert(hist_id, 'nobio', 'Other surface types',      '1', &
1129               &    nnobio, nobiotyp, nobioax_id)
1130          IF (  hydrol_cwrr ) THEN
1131             CALL histvert(hist_id, 'solay', 'Hydrol soil levels',      'm', &
1132                  &    nslm, diaglev(1:nslm), solayax_id)
1133          ENDIF
1134          !-
1135          !-  Vegetation
1136          !-
1137          CALL histdef(hist_id, 'vegetfrac', 'Fraction of vegetation', '1', &
1138               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(3), dt,dw)
1139          CALL histdef(hist_id, 'maxvegetfrac', 'Maximum fraction of vegetation', '1', &
1140               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(3), dt,dw)
1141          CALL histdef(hist_id, 'nobiofrac', 'Fraction of other surface types', '1', &
1142               & iim,jjm, hori_id, nnobio, 1, nnobio, nobioax_id, 32, avescatter(3), dt,dw)
1143          CALL histdef(hist_id, 'lai', 'Leaf Area Index', '1', &
1144               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(1), dt,dw)
1145          CALL histdef(hist_id, 'lai_cl1', 'Leaf Area Index cl1', '1', &
1146               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(1), dt,dw)
1147          CALL histdef(hist_id, 'lai_cl2', 'Leaf Area Index cl2', '1', &
1148               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(1), dt,dw)
1149          CALL histdef(hist_id, 'lai_cl3', 'Leaf Area Index cl3', '1', &
1150               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(1), dt,dw)
1151          CALL histdef(hist_id, 'lai_cl4', 'Leaf Area Index cl4', '1', &
1152               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(1), dt,dw)
1153          !-
1154          !- Forcing variables
1155          !-
1156          CALL histdef(hist_id, 'SinAng', 'Net shortwave radiation', '-',  &
1157               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(9), dt,dw)
1158          CALL histdef(hist_id, 'LWdown', 'Downward longwave radiation', 'W/m^2',  &
1159               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(9), dt,dw)
1160          CALL histdef(hist_id, 'SWdown', 'Downward shortwave radiation', 'W/m^2',  &
1161               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(9), dt,dw)
1162          CALL histdef(hist_id, 'Tair', 'Near surface air temperature at forcing level', 'K',  &
1163               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(2), dt,dw)
1164          CALL histdef(hist_id, 'Qair', 'Near surface specific humidity at forcing level', 'g/g',  &
1165               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(2), dt,dw)
1166          CALL histdef(hist_id, 'SurfP', 'Surface Pressure', 'hPa',  &
1167               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(9), dt,dw)
1168          CALL histdef(hist_id, 'Windu', 'Eastward wind', 'm/s',  &
1169               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(9), dt,dw)
1170          CALL histdef(hist_id, 'Windv', 'Northward wind', 'm/s',  &
1171               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(9), dt,dw)
1172          !-
1173          !-  General energy balance
1174          !-
1175          CALL histdef(hist_id, 'SWnet', 'Net shortwave radiation', 'W/m^2',  &
1176               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
1177          CALL histdef(hist_id, 'LWnet', 'Net longwave radiation', 'W/m^2',  &
1178               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
1179          CALL histdef(hist_id, 'Qh', 'Sensible heat flux', 'W/m^2',  &
1180               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
1181          CALL histdef(hist_id, 'Qle', 'Latent heat flux', 'W/m^2',  &
1182               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
1183          CALL histdef(hist_id, 'Qg', 'Ground heat flux', 'W/m^2',  &
1184               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
1185          CALL histdef(hist_id, 'Qf', 'Energy of fusion', 'W/m^2',  &
1186               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(2), dt,dw)
1187          CALL histdef(hist_id, 'Qv', 'Energy of sublimation', 'W/m^2',  &
1188               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
1189          CALL histdef(hist_id, 'DelSurfHeat', 'Change in surface layer heat', 'J/m^2',  &
1190               & iim,jjm, hori_id, 1,1,1, -99, 32, sumscatter(1), dt,dw)
1191          CALL histdef(hist_id, 'DelColdCont', 'Change in snow surface layer cold content', 'J/m^2',  &
1192               & iim,jjm, hori_id, 1,1,1, -99, 32, sumscatter(1), dt,dw)
1193          !-
1194          !- General water balance
1195          !-
1196          CALL histdef(hist_id, 'Snowf', 'Snowfall rate', 'kg/m^2/s',  &
1197               & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop_scinsec(1), dt,dw)
1198          CALL histdef(hist_id, 'Rainf', 'Rainfall rate', 'kg/m^2/s',  &
1199               & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop_scinsec(1), dt,dw)
1200          CALL histdef(hist_id, 'Evap', 'Total Evapotranspiration', 'kg/m^2/s', &
1201               & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop_scinsec(1), dt,dw)
1202          CALL histdef(hist_id, 'Qs', 'Surface runoff', 'kg/m^2/s', &
1203               & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop_scinsec(1), dt,dw)
1204          CALL histdef(hist_id, 'Qsb', 'Sub-surface runoff', 'kg/m^2/s', &
1205               & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop_scinsec(1), dt,dw)
1206          CALL histdef(hist_id, 'Qrec', 'Recharge', 'kg/m^2/s', &
1207               & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop_scinsec(1), dt,dw)
1208          CALL histdef(hist_id, 'Qsm', 'Snowmelt', 'kg/m^2/s', &
1209               & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop_scinsec(1), dt,dw)
1210          CALL histdef(hist_id, 'DelSoilMoist', 'Change in soil moisture', 'kg/m^2',  &
1211               & iim,jjm, hori_id, 1, 1, 1, -99, 32, sumscatter(1), dt,dw)
1212          CALL histdef(hist_id, 'DelSurfStor', 'Change in Surface Water Storage','kg/m^2',&
1213               & iim,jjm, hori_id, 1, 1, 1, -99, 32, sumscatter(1), dt,dw)
1214          CALL histdef(hist_id, 'DelIntercept', 'Change in interception storage', 'kg/m^2',  &
1215               & iim,jjm, hori_id, 1, 1, 1, -99, 32, sumscatter(1), dt,dw)
1216          CALL histdef(hist_id, 'DelSWE', 'Change in Snow Water Equivalent', 'kg/m^2',  &
1217               & iim,jjm, hori_id, 1, 1, 1, -99, 32, sumscatter(1), dt,dw)
1218          IF ( do_irrigation ) THEN
1219             CALL histdef(hist_id, 'Qirrig', 'Irrigation', 'kg/m^2/s', &
1220                  & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop_scinsec(1), dt,dw)
1221             CALL histdef(hist_id, 'Qirrig_req', 'Irrigation requirement', 'kg/m^2/s', &
1222                  & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop_scinsec(1), dt,dw)
1223          ENDIF
1224          !-
1225          !- Surface state
1226          !-
1227          CALL histdef(hist_id, 'AvgSurfT', 'Average surface temperature', 'K', &
1228               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
1229          CALL histdef(hist_id, 'PotSurfT', 'Potential (Unstressed) surface temperature', 'K', &
1230               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
1231          CALL histdef(hist_id, 'RadT', 'Surface radiative temperature', 'K', &
1232               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
1233          CALL histdef(hist_id, 'Albedo', 'Albedo', '1', &
1234               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
1235          CALL histdef(hist_id, 'SurfStor', 'Surface Water Storage','kg/m^2',  &
1236               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
1237          CALL histdef(hist_id, 'SWE', 'Snow Water Equivalent', 'kg/m^2', &
1238               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
1239          CALL histdef(hist_id, 'InterceptVeg', 'Intercepted Water on Canopy', 'Kg/m^2', &
1240               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(1), dt,dw)
1241          !!-
1242          !-  Sub-surface state
1243          !-
1244          IF ( .NOT. hydrol_cwrr ) THEN
1245             CALL histdef(hist_id, 'SoilMoist', '3D average layer soil moisture', 'kg/m^2',  &
1246                  & iim,jjm, hori_id, 1, 1, 1, -99, 32, avescatter(1), dt,dw)
1247          ELSE
1248             CALL histdef(hist_id, 'SoilMoist', '3D average layer soil moisture', 'kg/m^2',  &
1249                  & iim,jjm, hori_id, nslm, 1, nslm, solayax_id, 32, avescatter(1), dt,dw)
1250
1251             IF (ok_freeze_cwrr) THEN
1252                CALL histdef(hist_id, 'profil_froz_hydro', 'Frozen fraction for each hydrological soil layer', '-', &
1253                     & iim,jjm, hori_id, nslm, 1, nslm,solayax_id, 32, avescatter(1),  dt,dw)
1254                DO jst=1,nstm
1255                   WRITE (var_name,"('profil_froz_hydro_',i1)") jst
1256                   CALL histdef(hist_id, trim(var_name), 'Frozen fraction for each hydrological soil layer and soiltile', '-', &
1257                        & iim,jjm, hori_id, nslm, 1, nslm, solayax_id, 32, avescatter(1),  dt,dw)
1258                ENDDO
1259
1260                CALL histdef(hist_id, 'temp_hydro', 'Soil temperature interpolated on hydrological layers', 'K', &
1261                     & iim,jjm, hori_id, nslm, 1, nslm, solayax_id, 32, avescatter(1), dt,dw)
1262                CALL histdef(hist_id, 'kk_moy', 'Mean hydrological conductivity', 'mm/d', &
1263                     & iim,jjm,hori_id, nslm,1,nslm, solayax_id, 32, avescatter(1),  dt,dw)
1264             ENDIF
1265          END IF
1266          CALL histdef(hist_id, 'SoilWet', 'Total soil wetness', '-',  &
1267               & iim,jjm, hori_id, 1, 1, 1, -99, 32, avescatter(1), dt,dw)
1268          CALL histdef(hist_id, 'SoilTemp', 'Soil temperature profile', 'K', &
1269               & iim,jjm, hori_id, ngrnd, 1, ngrnd, solax_id, 32, avescatter(1),  dt,dw)
1270          !-
1271          !-  Evaporation components
1272          !-
1273          CALL histdef(hist_id, 'PotEvap', 'Potential evapotranspiration', 'kg/m^2/s', &
1274               & iim,jjm, hori_id, 1, 1, 1, -99, 32, fluxop_scinsec(1), dt,dw)
1275          CALL histdef(hist_id, 'PotEvapOld', 'Potential evapotranspiration old method', 'kg/m^2/s', &
1276               & iim,jjm, hori_id, 1, 1, 1, -99, 32, fluxop_scinsec(1), dt,dw)
1277          CALL histdef(hist_id, 'ECanop', 'Interception evaporation', 'kg/m^2/s', &
1278               & iim,jjm, hori_id, 1, 1, 1, -99, 32, fluxop_scinsec(1), dt,dw)
1279          CALL histdef(hist_id, 'TVeg', 'Transpiration', 'kg/m^2/s', &
1280               & iim,jjm, hori_id, 1, 1, 1, -99, 32, fluxop_scinsec(1), dt,dw)
1281          CALL histdef(hist_id, 'ESoil', 'Bare soil evaporation', 'kg/m^2/s', &
1282               & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop_scinsec(1), dt,dw)
1283          CALL histdef(hist_id, 'EWater', 'Open water evaporation', 'kg/m^2/s', &
1284               & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop_scinsec(1), dt,dw)
1285          CALL histdef(hist_id, 'RootMoist','Root zone soil water', 'kg/m^2',  &
1286               & iim,jjm, hori_id, 1, 1, 1, -99, 32, avescatter(1), dt,dw)
1287          CALL histdef(hist_id, 'SubSnow','Snow sublimation','kg/m^2/s', &
1288               & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop_scinsec(1), dt,dw)
1289          CALL histdef(hist_id, 'ACond', 'Aerodynamic conductance', 'm/s',  &
1290               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
1291          IF ( river_routing .AND. do_floodplains ) THEN
1292             CALL histdef(hist_id, 'Qflood', 'Floodplain Evaporation', 'kg/m^2/s', &
1293                  & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop_scinsec(1), dt,dw)
1294          ENDIF
1295          !-
1296          !- Surface turbulence
1297          !-
1298          CALL histdef(hist_id, 'Z0m', 'Roughness height for momentum', 'm',  &
1299               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
1300          CALL histdef(hist_id, 'Z0h', 'Roughness height for heat', 'm',  &
1301               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
1302          CALL histdef(hist_id, 'EffectHeight', 'Effective displacement height (h-d)', 'm',  &
1303               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
1304          !-
1305          !-
1306          !-  Cold Season Processes
1307          !-
1308          CALL histdef(hist_id, 'SnowFrac', 'Snow cover fraction', '1',  &
1309               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
1310          CALL histdef(hist_id, 'SAlbedo', 'Snow albedo', '1', &
1311               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
1312          CALL histdef(hist_id, 'SnowDepth', '3D snow depth', 'm', &
1313               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
1314          !-
1315          !- Hydrologic variables
1316          !-
1317          IF ( river_routing ) THEN
1318             CALL histdef(hist_id, 'slowr', 'Slow flow reservoir', 'kg/m^2', &
1319                  & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
1320             CALL histdef(hist_id, 'fastr', 'Fast flow reservoir', 'kg/m^2', &
1321                  & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
1322             CALL histdef(hist_id, 'streamr', 'Stream flow reservoir', 'kg/m^2', &
1323                  & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
1324             CALL histdef(hist_id, 'lakevol', 'Volume in lake reservoir', 'kg/m^2', &
1325                  & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
1326             CALL histdef(hist_id, 'pondr', 'Ponds reservoir', 'kg/m^2', &
1327                  & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
1328             !-
1329             !-
1330             !-
1331             CALL histdef(hist_id, 'SwampMap', 'Map of swamp areas', 'm^2', &
1332                  & iim,jjm, hori_id, 1,1,1, -99, 32, once(1), dt,dw)
1333             CALL histdef(hist_id, 'Dis', 'Simulated River Discharge', 'm^3/s', &
1334                  & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop_scinsec(2), dt,dw)
1335             CALL histdef(hist_id, 'CoastalFlow', 'Diffuse coastal flow', 'm^3/s', &
1336                  & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop_scinsec(2), dt,dw)
1337             CALL histdef(hist_id, 'RiverFlow', 'River flow to the oceans', 'm^3/s', &
1338                  & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop_scinsec(2), dt,dw)
1339             IF ( do_irrigation ) THEN
1340                CALL histdef(hist_id, 'IrrigationMap', 'Map of irrigated areas', 'm^2', &
1341                     & iim,jjm, hori_id, 1,1,1, -99, 32, once(1), dt,dw)
1342             ENDIF
1343             !
1344             !
1345             IF ( do_floodplains ) THEN
1346                CALL histdef(hist_id, 'FloodplainsMap', 'Map of flooded areas', 'm^2', &
1347                     & iim,jjm, hori_id, 1,1,1, -99, 32, once(1), dt,dw)
1348                CALL histdef(hist_id, 'FloodFrac', 'Floodplain Fraction', '-', &
1349                     & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
1350             ENDIF
1351          ENDIF
1352          !-
1353          CALL histdef(hist_id, 'humrel', 'Soil moisture stress', '-',  &
1354               & iim,jjm, hori_id, nvm,1,nvm, vegax_id, 32, avescatter(8), dt,dw)
1355          !-
1356          !-  The carbon budget
1357          !-
1358          IF ( ok_co2 ) THEN
1359            CALL histdef(hist_id, 'cimean', 'Stomatal CO2 concentation', 'mmole/m2/s', &
1360                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(10), dt,dw)
1361            CALL histdef(hist_id, 'GPP', 'Net assimilation of carbon by the vegetation', 'gC/m^2/s', &
1362                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, fluxop_scinsec(1), dt,dw)
1363            CALL histdef(hist_id, 'gsmean', 'mean stomatal conductance', 'mol/m2/s', &
1364                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(8), dt,dw)
1365             CALL histdef(hist_id, 'cim', 'cim', 'ppm', &
1366                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(10), dt,dw)
1367             CALL histdef(hist_id, 'leafci', 'leaf Ci', 'ppm', &
1368                  & iim,jjm, hori_id,nlai, 1, nlai, laiax0_id, 32, avescatter(10), dt,dw)
1369             CALL histdef(hist_id, 'gs', 'gs', 'mol m-2 s-1', &
1370                  & iim,jjm, hori_id, nlai+1, 1, nlai+1, laiax_id, 32, avescatter(10), dt,dw)
1371             CALL histdef(hist_id, 'assimi', 'assimi', 'mol m-2 s-1', &
1372                  & iim,jjm, hori_id, nlai+1, 1, nlai+1, laiax_id, 32, avescatter(10), dt,dw)
1373             CALL histdef(hist_id, 'Rd', 'Rd', 'mol m-2 s-1', &
1374                  & iim,jjm, hori_id, nlai+1, 1, nlai+1, laiax_id, 32, avescatter(10), dt,dw)
1375             CALL histdef(hist_id, 'Cc', 'Cc', 'ppm', &
1376                  & iim,jjm, hori_id, nlai+1, 1, nlai+1, laiax_id, 32, avescatter(10), dt,dw)
1377             CALL histdef(hist_id, 'limitphoto', 'limitphoto', '-', &
1378                  & iim,jjm, hori_id, nlai+1, 1, nlai+1, laiax_id, 32, avescatter(10), dt,dw)
1379             CALL histdef(hist_id, 'Vc', 'Vc', 'mol m-2 s-1', &
1380                  & iim,jjm, hori_id, nlai+1, 1, nlai+1, laiax_id, 32, avescatter(10), dt,dw)
1381             CALL histdef(hist_id, 'Vj', 'Vj', 'mol e- m-2 s-1', &
1382                  & iim,jjm, hori_id, nlai+1, 1, nlai+1, laiax_id, 32, avescatter(10), dt,dw)
1383             CALL histdef(hist_id, 'gm', 'gm', 'mol m-2 s-1', &
1384                  & iim,jjm, hori_id, 1, 1, 1, -99, 32, avescatter(10), dt,dw)
1385             CALL histdef(hist_id, 'gammastar', 'gammastar', 'ppm', &
1386                  & iim, jjm, hori_id, 1, 1, 1, -99, 32, avescatter(10), dt,dw)
1387             CALL histdef(hist_id, 'Kmo', 'Kmo', 'ppm', &
1388                  & iim, jjm, hori_id, 1, 1, 1, -99, 32, avescatter(10), dt,dw)
1389             CALL histdef(hist_id, 'Kmc', 'Kmc', 'ppm', &
1390                  & iim, jjm, hori_id, 1, 1, 1, -99, 32, avescatter(10), dt,dw)
1391          ENDIF
1392          IF ( ok_stomate ) THEN
1393             CALL histdef(hist_id, 'NEE', 'Net Ecosystem Exchange', 'gC/m^2/s', &
1394                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, fluxop_scinsec(1), dt,dw)
1395             CALL histdef(hist_id, 'maint_resp', 'Maintenance respiration', 'gC/m^2/s', &
1396                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, fluxop_scinsec(1), dt,dw)
1397             CALL histdef(hist_id, 'hetero_resp', 'Heterotrophic respiration', 'gC/m^2/s', &
1398                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, fluxop_scinsec(1), dt,dw)
1399             CALL histdef(hist_id, 'growth_resp', 'Growth respiration', 'gC/m^2/s', &
1400                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, fluxop_scinsec(1), dt,dw)
1401             CALL histdef(hist_id, 'npp', 'Net Primary Production', 'gC/m^2/s', &
1402                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, fluxop_scinsec(1), dt,dw)
1403          ENDIF
1404          !
1405      ENDIF
1406       !-
1407       !- Forcing and grid information
1408       !-
1409       CALL histdef(hist_id, 'LandPoints', 'Land Points', '1', &
1410            & iim,jjm, hori_id, 1,1,1, -99, 32, once(10), dt,dw) 
1411       CALL histdef(hist_id, 'Areas', 'Mesh areas', 'm2', &
1412            & iim,jjm, hori_id, 1,1,1, -99, 32, once(1), dt, dw)
1413       CALL histdef(hist_id, 'Contfrac', 'Continental fraction', '1', &
1414            & iim,jjm, hori_id, 1,1,1, -99, 32, once(1), dt, dw)
1415       !-
1416       ! Write the names of the pfts in the history files
1417       global_attribute="PFT_name"
1418       DO i=1,nvm
1419          WRITE(global_attribute(9:10),"(I2.2)") i
1420          CALL histglobal_attr(hist_id, global_attribute, PFT_name(i))
1421       ENDDO
1422       !-
1423       CALL histend(hist_id)
1424    ENDIF ! IF (is_omp_root)
1425 
1426    END IF !IF ( dw == 0 )
1427    !
1428    !
1429    ! Second SECHIBA hist file
1430    !
1431    !-
1432    !Config Key   = SECHIBA_HISTFILE2
1433    !Config Desc  = Flag to switch on histfile 2 for SECHIBA (hi-frequency ?)
1434    !Config If    = OK_SECHIBA
1435    !Config Def   = n
1436    !Config Help  = This Flag switch on the second SECHIBA writing for hi (or low)
1437    !Config         frequency writing. This second output is optional and not written
1438    !Config         by default.
1439    !Config Units = [FLAG]
1440    !-
1441    ok_histfile2=.FALSE.
1442    CALL getin_p('SECHIBA_HISTFILE2', ok_histfile2)
1443    IF (printlev >= 2) WRITE(numout,*) 'SECHIBA_HISTFILE2 ', ok_histfile2
1444    !
1445    !-
1446    !Config Key   = WRITE_STEP2
1447    !Config Desc  = Frequency in seconds at which to WRITE output
1448    !Config If    = SECHIBA_HISTFILE2
1449    !Config Def   = 1800.0
1450    !Config Help  = This variables gives the frequency the output 2 of
1451    !Config         the model should be written into the netCDF file.
1452    !Config         It does not affect the frequency at which the
1453    !Config         operations such as averaging are done.
1454    !Config         That is IF the coding of the calls to histdef
1455    !Config         are correct !
1456    !Config Units = [seconds]
1457    !-
1458    dw2 = 1800.0
1459    CALL getin_p('WRITE_STEP2', dw2)
1460   
1461    ! Deactivate sechiba_histfile2 if the frequency is set to zero
1462    IF ( dw2 == 0 ) THEN
1463       ok_histfile2=.FALSE.
1464       IF (printlev >= 2) WRITE(numout,*) 'WRITE_STEP2 was set to zero and therfore SECHIBA_HISTFILE2 is deactivated.'
1465    ELSE IF ( hist_id < 0 ) THEN
1466       ! Deactivate all history files if sechiba_history file is deactivated
1467       ok_histfile2=.FALSE.
1468       IF (printlev >= 2) WRITE(numout,*) 'SECHIBA_HISTFILE2 will not be created because sechiba_history file is deactivated.'
1469    END IF
1470
1471    hist2_id = -1
1472    !
1473    IF (ok_histfile2) THEN
1474       !-
1475       !Config Key   = SECHIBA_OUTPUT_FILE2
1476       !Config Desc  = Name of file in which the output number 2 is going to be written
1477       !Config If    = SECHIBA_HISTFILE2
1478       !Config Def   = sechiba_out_2.nc
1479       !Config Help  = This file is going to be created by the model
1480       !Config         and will contain the output 2 from the model.
1481       !Config Units = [FILE]
1482       !-
1483       histname2='sechiba_out_2.nc'
1484       CALL getin_p('SECHIBA_OUTPUT_FILE2', histname2)
1485       IF (printlev >= 2) WRITE(numout,*) 'SECHIBA_OUTPUT_FILE2 ', histname2
1486       !-
1487       !Config Key   = SECHIBA_HISTLEVEL2
1488       !Config Desc  = SECHIBA history 2 output level (0..10)
1489       !Config If    = SECHIBA_HISTFILE2
1490       !Config Def   = 1
1491       !Config Help  = Chooses the list of variables in the history file.
1492       !Config         Values between 0: nothing is written; 10: everything is
1493       !Config         written are available More details can be found on the web under documentation.
1494       !Config         web under documentation.
1495       !Config         First level contains all ORCHIDEE outputs.
1496       !Config Units = [-]
1497       !-
1498       hist2_level = 1
1499       CALL getin_p('SECHIBA_HISTLEVEL2', hist2_level)
1500       !-
1501       IF (printlev >= 2) WRITE(numout,*) 'SECHIBA history level 2 : ',hist2_level
1502       IF ( (hist2_level > max_hist_level).OR.(hist2_level < 0) ) THEN
1503          STOP 'This history level 2 is not allowed'
1504       ENDIF
1505       !
1506       !-
1507       !- define operations as a function of history level.
1508       !- Above hist2_level, operation='never'
1509       !-
1510       ave2(1:max_hist_level) = 'ave(scatter(X))'
1511       IF (hist2_level < max_hist_level) THEN
1512          ave2(hist2_level+1:max_hist_level) = 'never'
1513       ENDIF
1514       sumscatter2(1:max_hist_level) = 't_sum(scatter(X))'
1515       IF (hist2_level < max_hist_level) THEN
1516          sumscatter2(hist2_level+1:max_hist_level) = 'never'
1517       ENDIF
1518       avecels2(1:max_hist_level) = 'ave(cels(scatter(X)))'
1519       IF (hist2_level < max_hist_level) THEN
1520          avecels2(hist2_level+1:max_hist_level) = 'never'
1521       ENDIF
1522       avescatter2(1:max_hist_level) = 'ave(scatter(X))'
1523       IF (hist2_level < max_hist_level) THEN
1524          avescatter2(hist2_level+1:max_hist_level) = 'never'
1525       ENDIF
1526       tmincels2(1:max_hist_level) = 't_min(cels(scatter(X)))'
1527       IF (hist2_level < max_hist_level) THEN
1528          tmincels2(hist2_level+1:max_hist_level) = 'never'
1529       ENDIF
1530       tmaxcels2(1:max_hist_level) = 't_max(cels(scatter(X)))'
1531       IF (hist2_level < max_hist_level) THEN
1532          tmaxcels2(hist2_level+1:max_hist_level) = 'never'
1533       ENDIF
1534!!$       tmax2(1:max_hist_level) = 't_max(X)'
1535!!$       IF (hist2_level < max_hist_level) THEN
1536!!$          tmax2(hist2_level+1:max_hist_level) = 'never'
1537!!$       ENDIF
1538       fluxop2(1:max_hist_level) = flux_op
1539       IF (hist2_level < max_hist_level) THEN
1540          fluxop2(hist2_level+1:max_hist_level) = 'never'
1541       ENDIF
1542!!$       fluxop_sc2(1:max_hist_level) = flux_sc
1543!!$       IF (hist2_level < max_hist_level) THEN
1544!!$          fluxop_sc2(hist2_level+1:max_hist_level) = 'never'
1545!!$       ENDIF
1546!!$       fluxop_insec2(1:max_hist_level) = flux_insec
1547!!$       IF (hist2_level < max_hist_level) THEN
1548!!$          fluxop_insec2(hist2_level+1:max_hist_level) = 'never'
1549!!$       ENDIF
1550       fluxop_scinsec2(1:max_hist_level) = flux_scinsec
1551       IF (hist2_level < max_hist_level) THEN
1552          fluxop_scinsec2(hist2_level+1:max_hist_level) = 'never'
1553       ENDIF
1554       once2(1:max_hist_level) = 'once(scatter(X))'
1555       IF (hist2_level < max_hist_level) THEN
1556          once2(hist2_level+1:max_hist_level) = 'never'
1557       ENDIF
1558       !
1559       IF (is_omp_root) THEN
1560          IF ( .NOT. almaoutput ) THEN
1561             !-
1562             IF ( GridType == "RegLonLat" ) THEN
1563#ifdef CPP_PARA
1564                CALL histbeg(histname2, iim, lon_rect, jjm, lat_rect, 1, iim, 1, jjm, &
1565                     &     istp_old, date0, dt, hori_id2, hist2_id,orch_domain_id)
1566#else
1567                CALL histbeg(histname2, iim, lon_rect, jjm, lat_rect, 1, iim, 1, jjm, &
1568                     &     istp_old, date0, dt, hori_id2, hist2_id)
1569#endif
1570                IF (printlev >= 2) WRITE(numout,*)  'HISTBEG2 --->',istp_old,date0,dt,dw2,hist2_id
1571             ELSE
1572#ifdef CPP_PARA
1573                CALL histbeg(histname2, iim, lon, jjm, lat, 1, iim, 1, jjm, &
1574                     &     istp_old, date0, dt, hori_id2, hist2_id,domain_id=orch_domain_id)
1575#else
1576                CALL histbeg(histname2, iim, lon, jjm, lat, 1, iim, 1, jjm, &
1577                     &     istp_old, date0, dt, hori_id2, hist2_id)
1578#endif
1579             ENDIF
1580             !-
1581             CALL histvert(hist2_id, 'veget', 'Vegetation types', '1', &
1582                  &    nvm,   veg, vegax_id2)
1583             CALL histvert(hist2_id, 'laiax', 'Nb LAI', '1', &
1584                  &    nlai+1,   indlai, laiax_id2)
1585             CALL histvert(hist2_id, 'solth', 'Soil levels',      'm', &
1586                  &    ngrnd, sol, solax_id2)
1587             CALL histvert(hist2_id, 'soiltyp', 'Soil types',      '1', &
1588                  &    nstm, soltyp, soltax_id2)
1589             CALL histvert(hist2_id, 'nobio', 'Other surface types',      '1', &
1590                  &    nnobio, nobiotyp, nobioax_id2)
1591             CALL histvert(hist2_id, 'albtyp', 'Albedo Types',     '1', &
1592                  &    2, albtyp, albax_id2)
1593             IF (  hydrol_cwrr ) THEN
1594                CALL histvert(hist2_id, 'solay', 'Hydrol soil levels',      'm', &
1595                     &    nslm, solay, solayax_id2)
1596             ENDIF
1597             !-
1598             !- SECHIBA_HISTLEVEL2 = 1
1599             !-
1600             CALL histdef(hist2_id, 'ptn', 'Deep ground temperature', 'K', &
1601                  & iim,jjm, hori_id2, ngrnd, 1, ngrnd, solax_id2, 32, avescatter2(2),  dt, dw2) 
1602
1603             CALL histdef(hist2_id, 'mrsos', "Moisture in Upper 0.1 m of Soil Column", "kg m-2", &
1604                  & iim,jjm, hori_id2, 1, 1, 1, -99, 32, avescatter2(2), dt,dw2)           
1605
1606             CALL histdef(hist2_id, 'mrso', "Total Soil Moisture Content", "kg m-2", &
1607                  & iim,jjm, hori_id2, 1, 1, 1, -99, 32, avescatter2(11), dt,dw2)
1608             
1609             CALL histdef(hist2_id, 'mrros', "Surface Runoff", "kg m-2 s-1", &
1610                  & iim,jjm, hori_id2, 1, 1, 1, -99, 32, fluxop_scinsec2(11), dt,dw2)
1611
1612             CALL histdef(hist2_id, 'mrro', "Total Runoff", "kg m-2 s-1", &
1613                  & iim,jjm, hori_id2, 1, 1, 1, -99, 32, fluxop_scinsec2(2), dt,dw2)     
1614
1615             !-
1616             !- SECHIBA_HISTLEVEL2 = 2
1617             !-
1618             CALL histdef(hist2_id, 'cdrag', 'Drag coefficient for LE and SH', '?',  &
1619                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(2), dt, dw2)
1620             ! Ajouts Nathalie - Septembre 2008
1621             CALL histdef(hist2_id, 'soilalb_vis', 'Soil Albedo visible', '1', &
1622                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(2), dt,dw2)
1623             CALL histdef(hist2_id, 'soilalb_nir', 'Soil Albedo near infrared', '1', &
1624                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(2), dt,dw2)
1625             CALL histdef(hist2_id, 'vegalb_vis', 'Vegetation Albedo visible', '1', &
1626                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(2), dt,dw2)
1627             CALL histdef(hist2_id, 'vegalb_nir', 'Vegetation Albedo near infrared', '1', &
1628                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(2), dt,dw2)
1629             CALL histdef(hist2_id, 'z0m', 'Surface roughness for momentum', 'm',  &
1630                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(2), dt, dw2)
1631             CALL histdef(hist2_id, 'z0h', 'Surface roughness for heat', 'm',  &
1632                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(2), dt, dw2)
1633             CALL histdef(hist2_id, 'coastalflow', 'Diffuse coastal flow', 'm^3/s', &
1634                  & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop_scinsec2(2), dt, dw2)
1635             CALL histdef(hist2_id, 'riverflow', 'River flow to the oceans', 'm^3/s', &
1636                  & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop_scinsec2(2), dt, dw2) 
1637             CALL histdef(hist2_id, 'tsol_rad', 'Radiative surface temperature', 'C', &
1638                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avecels2(2), dt, dw2)
1639             IF ( river_routing .AND. do_floodplains ) THEN
1640                CALL histdef(hist2_id, 'floodout', 'Flow out of floodplains', 'mm/d', &
1641                     & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop2(2), dt,dw2)
1642                CALL histdef(hist2_id, 'vevapflo', 'Floodplains evaporation', 'mm/d', &
1643                     & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop2(2), dt, dw2)
1644                CALL histdef(hist2_id, 'flood_frac', 'Flooded fraction', '1', &
1645                     & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(2), dt,dw2)
1646                CALL histdef(hist2_id, 'reinfiltration', 'Reinfiltration from floodplains', 'mm/d', &
1647                     & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop2(2), dt,dw2)
1648             ENDIF
1649             CALL histdef(hist2_id, 'vevapnu', 'Bare soil evaporation', 'mm/d', &
1650                  & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop2(2), dt, dw2)
1651             CALL histdef(hist2_id, 'temp_sol', 'New Surface Temperature', 'C', &
1652                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avecels2(2), dt, dw2)
1653             CALL histdef(hist2_id, 'qsurf', 'Near surface specific humidity', 'g/g',  &
1654                  & iim,jjm, hori_id2, 1,1,1, -99, 32, ave2(2), dt, dw2)
1655             CALL histdef(hist2_id, 'albedo', 'Albedo', '1', &
1656                  & iim,jjm, hori_id2, 2,1,2, albax_id2, 32, avescatter2(2), dt, dw2)
1657             CALL histdef(hist2_id, 'fluxsens', 'Sensible Heat Flux', 'W/m^2',  &
1658                  & iim,jjm, hori_id2, 1,1,1, -99, 32, ave2(2), dt, dw2)
1659             CALL histdef(hist2_id, 'fluxlat', 'Latent Heat Flux', 'W/m^2',  &
1660                  & iim,jjm, hori_id2, 1,1,1, -99, 32, ave2(2), dt, dw2)
1661             CALL histdef(hist2_id, 'emis', 'Surface emissivity', '1', &
1662                  & iim,jjm, hori_id2, 1,1,1, -99, 32, ave2(2), dt, dw2)
1663             !-
1664             !- SECHIBA_HISTLEVEL2 = 3
1665             !-
1666             CALL histdef(hist2_id, 'evap', 'Evaporation', 'mm/d', &
1667                  & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop2(3), dt, dw2)
1668             CALL histdef(hist2_id, 'rain', 'Rainfall', 'mm/d',  &
1669                  & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop2(3), dt, dw2)
1670             CALL histdef(hist2_id, 'snowf', 'Snowfall', 'mm/d',  &
1671                  & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop2(3), dt, dw2)
1672             CALL histdef(hist2_id, 'netrad', 'Net radiation', 'W/m^2',  &
1673                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(3), dt, dw2)
1674             CALL histdef(hist2_id, 'lai', 'Leaf Area Index', '1', &
1675                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(3), dt, dw2)
1676
1677!!!!! crop variables             
1678             CALL histdef(hist2_id, 'tcult', 'crop temperature', '1', &
1679                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(3), dt, dw2)
1680             CALL histdef(hist2_id, 'udevair', 'udev calculated by Tair', '1', &
1681                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(3), dt, dw2)
1682             CALL histdef(hist2_id, 'udevcult', 'udev calculated by tcult', '1', &
1683                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(3), dt, dw2)
1684   
1685             CALL histdef(hist2_id, 'turfac', 'soil water stress for leaf growth', '1', &
1686                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(3), dt,dw2)
1687             CALL histdef(hist2_id, 'swfac', 'water stress for RUE', '1', &
1688                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(3), dt,dw2)
1689             CALL histdef(hist2_id, 'senfac', 'soil water stress for leaf senescence', '1', &
1690                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(3), dt,dw2)
1691   
1692             CALL histdef(hist2_id, 'shumrel', 'soil moisture around sowing depth', '1', &
1693                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(3), dt,dw2)
1694   
1695             CALL histdef(hist2_id, 'nlev', 'date for leaf emerge', '1', &
1696                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(3), dt,dw2)
1697   
1698             CALL histdef(hist2_id, 'nflo', 'date for flowering', '1', &
1699                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(3), dt,dw2)
1700   
1701             CALL histdef(hist2_id, 'ndrp', 'date for grain filling', '1', &
1702                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(3), dt,dw2)
1703   
1704             CALL histdef(hist2_id, 'nrec', 'date for harvesting', '1', &
1705                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(3), dt,dw2)
1706             CALL histdef(hist2_id, 'nmat', 'date for physiological mature', '1', &                 
1707                   & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(3), dt,dw2)
1708   
1709             CALL histdef(hist2_id, 'irrig_fin', 'final application of irrigation', '1', &
1710                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, fluxop2(2), dt,dw)
1711!!!!! end crop variables, xuhui
1712             IF ( river_routing ) THEN
1713                CALL histdef(hist2_id, 'basinmap', 'Aproximate map of the river basins', ' ', &
1714                     & iim,jjm, hori_id2, 1,1,1, -99, 32, once2(3), dt, dw2) 
1715                CALL histdef(hist2_id, 'nbrivers', 'Number or rivers in the outflow grid box', ' ', &
1716                     & iim,jjm, hori_id2, 1,1,1, -99, 32, once2(3), dt, dw2) 
1717             ENDIF
1718             IF (check_waterbal) THEN
1719                CALL histdef(hist2_id, 'TotWater', 'Total amount of water at end of time step', 'mm/d', &
1720                     & iim,jjm, hori_id2, 1,1,1, -99, 32, ave2(3), dt, dw2)
1721                CALL histdef(hist2_id, 'TotWaterFlux', 'Total water flux', 'mm/d', &
1722                  & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop2(3), dt, dw2)
1723             ENDIF
1724
1725             !-
1726             !- SECHIBA_HISTLEVEL2 = 4
1727             !-
1728             CALL histdef(hist2_id, 'subli', 'Sublimation', 'mm/d', &
1729                  & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop2(4), dt, dw2)
1730             CALL histdef(hist2_id, 'runoff', 'Surface runoff', 'mm/d', &
1731                  & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop2(4), dt, dw2)
1732             CALL histdef(hist2_id, 'drainage', 'Deep drainage', 'mm/d', &
1733                  & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop2(4), dt, dw2)
1734             IF ( river_routing ) THEN
1735                CALL histdef(hist2_id, 'riversret', 'Return from endorheic rivers', 'mm/d', &
1736                     & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop2(4), dt, dw2)
1737                CALL histdef(hist2_id, 'hydrographs', 'Hydrographs of gridbox outflow', 'm^3/s', &
1738                     & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop_scinsec2(4), dt, dw2)
1739             ENDIF
1740             IF ( hydrol_cwrr ) THEN
1741                CALL histdef(hist2_id, 'evapnu_soil', 'Bare soil evap for soil type', 'mm/d', &
1742                     & iim,jjm, hori_id2, nstm, 1, nstm, soltax_id2, 32, fluxop2(4), dt, dw2)
1743                CALL histdef(hist2_id, 'drainage_soil', 'Drainage for soil type', 'mm/d', &
1744                     & iim,jjm, hori_id2, nstm, 1, nstm, soltax_id2, 32, fluxop2(4), dt, dw2)
1745                CALL histdef(hist2_id, 'transpir_soil', 'Transpir for soil type', 'mm/d', &
1746                     & iim,jjm, hori_id2, nstm, 1, nstm, soltax_id2, 32, fluxop2(4), dt, dw2)
1747                CALL histdef(hist2_id, 'runoff_soil', 'Runoff for soil type', 'mm/d', &
1748                     & iim,jjm, hori_id2, nstm, 1, nstm, soltax_id2, 32, fluxop2(4), dt, dw2)
1749             ENDIF
1750             !
1751             CALL histdef(hist2_id, 'tair', 'Air Temperature', 'K',  &
1752                  & iim,jjm, hori_id2, 1,1,1, -99, 32, ave2(4), dt, dw2)
1753             CALL histdef(hist2_id, 'qair', 'Air humidity', 'g/g',  &
1754                  & iim,jjm, hori_id2, 1,1,1, -99, 32, ave2(4), dt, dw2)
1755             ! Ajouts Nathalie - Juillet 2006
1756             CALL histdef(hist2_id, 'q2m', '2m Air humidity', 'g/g',  &
1757                  & iim,jjm, hori_id2, 1,1,1, -99, 32, ave2(4), dt, dw2)
1758             CALL histdef(hist2_id, 't2m', '2m Air Temperature', 'K',  &
1759                  & iim,jjm, hori_id2, 1,1,1, -99, 32, ave2(4), dt, dw2)
1760             ! Fin ajouts Nathalie
1761             CALL histdef(hist2_id, 'alb_vis', 'Albedo visible', '1', &
1762                  & iim,jjm, hori_id2, 1,1,1, -99, 32, ave2(4), dt, dw2)
1763             CALL histdef(hist2_id, 'alb_nir', 'Albedo near infrared', '1', &
1764                  & iim,jjm, hori_id2, 1,1,1, -99, 32, ave2(4), dt, dw2)
1765             CALL histdef(hist2_id, 'roughheight', 'Effective roughness height', 'm',  &
1766                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(4), dt, dw2)
1767             CALL histdef(hist2_id, 'roughheight_pft', 'Effect roughness height pft', 'm',  &
1768                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(5), dt, dw2)
1769             CALL histdef(hist2_id, 'transpir', 'Transpiration', 'mm/d', &
1770                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, fluxop2(4), dt, dw2)
1771             CALL histdef(hist2_id, 'evapnu_pft', 'soil evaporation', 'mm/d', &
1772                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, fluxop2(4), dt, dw2)
1773             CALL histdef(hist2_id, 'inter', 'Interception loss', 'mm/d', &
1774                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, fluxop2(4), dt, dw2)
1775             !-
1776             !- SECHIBA_HISTLEVEL2 = 5
1777             !-
1778             CALL histdef(hist2_id, 'tsol_max', 'Maximum Surface Temperature',&
1779                  & 'C', iim,jjm, hori_id2, 1,1,1, -99, 32, tmaxcels2(5), dt, dw2)
1780             CALL histdef(hist2_id, 'tsol_min', 'Minimum Surface Temperature',&
1781                  & 'C', iim,jjm, hori_id2, 1,1,1, -99, 32, tmincels2(5), dt, dw2)
1782             CALL histdef(hist2_id, 'snow', 'Snow mass', 'kg/m^2', &
1783                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(5), dt, dw2)
1784             CALL histdef(hist2_id, 'snowage', 'Snow age', '?', &
1785                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(5), dt, dw2)
1786             CALL histdef(hist2_id, 'snownobio', 'Snow on other surfaces', 'kg/m^2', &
1787                  & iim,jjm, hori_id2, nnobio,1, nnobio, nobioax_id2, 32, avescatter2(5), dt, dw2)
1788             CALL histdef(hist2_id, 'snownobioage', 'Snow age on other surfaces', 'd', &
1789                  & iim,jjm, hori_id2, nnobio,1, nnobio, nobioax_id2, 32, avescatter2(5), dt, dw2)
1790             CALL histdef(hist2_id, 'vegetfrac', 'Fraction of vegetation', '1', &
1791                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(5), dt, dw2)
1792             CALL histdef(hist2_id, 'maxvegetfrac', 'Maximum fraction of vegetation', '1', &
1793                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(5), dt, dw2)
1794             CALL histdef(hist2_id, 'nobiofrac', 'Fraction of other surface types', '1', &
1795                  & iim,jjm, hori_id2, nnobio, 1, nnobio, nobioax_id2, 32, avescatter2(5), dt, dw2)
1796             IF ( hydrol_cwrr ) THEN
1797                DO jst=1,nstm
1798                   
1799                   ! var_name= "mc_1" ... "mc_3"
1800                   WRITE (var_name,"('moistc_',i1)") jst
1801                   CALL histdef(hist2_id, var_name, 'Soil Moisture profile for soil type', 'm3/m3', &
1802                        & iim,jjm, hori_id2, nslm, 1, nslm, solayax_id2, 32, avescatter2(5), dt, dw2)
1803                   
1804                   ! var_name= "vegetsoil_1" ... "vegetsoil_3"
1805                   WRITE (var_name,"('vegetsoil_',i1)") jst
1806                   CALL histdef(hist2_id, var_name, 'Fraction of vegetation on soil types', '%', &
1807                        & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(5), dt, dw2)
1808                   
1809                   ! var_name= "kfact_root_1" ... "kfact_root_3"
1810                   WRITE (var_name,"('kfactroot_',i1)") jst
1811                   CALL histdef(hist2_id, var_name, 'Root fraction profile for soil type', '%', &
1812                        & iim,jjm, hori_id2, nslm, 1, nslm, solayax_id2, 32, avescatter2(5), dt,dw2)
1813                ENDDO
1814
1815             ENDIF
1816             !-
1817             !- SECHIBA_HISTLEVEL2 = 6
1818             !-
1819             IF ( .NOT. hydrol_cwrr ) THEN
1820                CALL histdef(hist2_id, 'dss', 'Up-reservoir Height', 'm',  &
1821                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id, 32, avescatter2(6), dt,dw2)
1822                CALL histdef(hist2_id, 'gqsb', 'Upper Soil Moisture', 'Kg/m^2',  &
1823                     & iim,jjm, hori_id2, 1, 1, 1, -99, 32, avescatter2(6), dt, dw2)
1824                CALL histdef(hist2_id, 'bqsb', 'Lower Soil Moisture', 'Kg/m^2',  &
1825                     & iim,jjm, hori_id2, 1, 1, 1, -99, 32, avescatter2(6), dt, dw2)
1826             ELSE
1827                CALL histdef(hist2_id, 'humtot', 'Total Soil Moisture', 'Kg/m^2', &
1828                     & iim,jjm, hori_id2, 1, 1, 1, -99, 32, avescatter2(6), dt, dw2)
1829                CALL histdef(hist2_id, 'humtot_soil', 'Soil Moisture for soil type', 'Kg/m^2', &
1830                     & iim,jjm, hori_id2, nstm, 1, nstm, soltax_id2, 32, avescatter2(6), dt, dw2)
1831             ENDIF
1832             CALL histdef(hist2_id, 'qsintveg', 'Water on canopy', 'Kg/m^2', &
1833                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(6), dt, dw2)
1834             CALL histdef(hist2_id, 'rstruct', 'Structural resistance', 's/m', &
1835                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(6), dt, dw2)
1836             IF ( ok_co2 ) THEN
1837                CALL histdef(hist2_id, 'gpp', 'Net assimilation of carbon by the vegetation', 'gC/m^2/s', &
1838                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, fluxop_scinsec2(6), dt,dw2)
1839             ENDIF
1840             IF ( ok_stomate ) THEN
1841                CALL histdef(hist2_id, 'nee', 'Net Ecosystem Exchange', 'gC/m^2/s', &
1842                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, fluxop_scinsec2(6), dt,dw2)
1843                CALL histdef(hist2_id, 'maint_resp', 'Maintenance respiration', 'gC/m^2/s', &
1844                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, fluxop_scinsec2(6), dt,dw2)
1845                CALL histdef(hist2_id, 'hetero_resp', 'Heterotrophic respiration', 'gC/m^2/s', &
1846                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, fluxop_scinsec2(6), dt,dw2)
1847                CALL histdef(hist2_id, 'growth_resp', 'Growth respiration', 'gC/m^2/s', &
1848                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, fluxop_scinsec2(6), dt, dw2)
1849                CALL histdef(hist2_id, 'npp', 'Net Primary Production', 'gC/m^2/s', &
1850                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, fluxop_scinsec2(6), dt, dw2)
1851             ENDIF
1852             CALL histdef(hist2_id, 'precisol', 'Throughfall', 'mm/d',  &
1853                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, fluxop2(6), dt, dw2)
1854             CALL histdef(hist2_id, 'drysoil_frac', 'Fraction of visibly dry soil', '1',  &
1855                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(6), dt, dw2)
1856             CALL histdef(hist2_id, 'evapot', 'Potential evaporation', 'mm/d',  &
1857                  & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop2(6), dt, dw2)
1858             CALL histdef(hist2_id, 'evapot_corr', 'Potential evaporation', 'mm/d',  &
1859                  & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop2(6), dt, dw2)
1860             CALL histdef(hist2_id, 'transpot', 'Potential transporation', 'mm/d',  &
1861                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, fluxop2(6), dt, dw2)
1862             CALL histdef(hist2_id, 'snowmelt', 'snow melt', 'mm/d', &
1863                  & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop2(6), dt, dw2)
1864
1865             !-
1866             !- SECHIBA_HISTLEVEL2 = 7
1867             !-
1868             CALL histdef(hist2_id, 'swnet', 'Net solar radiation', 'W/m^2',  &
1869                  & iim,jjm, hori_id2, 1,1,1, -99, 32, ave2(7), dt, dw2)
1870             CALL histdef(hist2_id, 'swdown', 'Incident solar radiation', 'W/m^2',  &
1871                  & iim,jjm, hori_id2, 1,1,1, -99, 32, ave2(7), dt, dw2)
1872             CALL histdef(hist2_id, 'lwdown', 'Absorbed downward longwave radiation', 'W/m^2',  &
1873                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(7), dt, dw2)
1874             CALL histdef(hist2_id, 'lwnet', 'Net surface longwave radiation', 'W/m^2',  &
1875                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(7), dt, dw2)
1876             CALL histdef(hist2_id, 'ptn_pftmean', 'Soil temperature, PFT-mean','K', &
1877                  & iim,jjm, hori_id2, ngrnd, 1, ngrnd, solax_id, 32,avescatter2(7), dt,dw2)
1878             !-
1879             !- SECHIBA_HISTLEVEL2 = 8
1880             !-
1881             IF ( river_routing ) THEN
1882                CALL histdef(hist2_id, 'fastr', 'Fast flow reservoir', 'kg/m^2', &
1883                     & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(8), dt, dw2)
1884                CALL histdef(hist2_id, 'slowr', 'Slow flow reservoir', 'kg/m^2', &
1885                     & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(8), dt, dw2)
1886                CALL histdef(hist2_id, 'streamr', 'Stream flow reservoir', 'kg/m^2', &
1887                     & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(8), dt, dw2)
1888                CALL histdef(hist2_id, 'floodr', 'Floodplains reservoir', 'kg/m^2', &
1889                     & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(8), dt,dw2)
1890                CALL histdef(hist2_id, 'floodh', 'Floodplains height', 'mm', &
1891                     & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(8), dt,dw2)
1892                CALL histdef(hist2_id, 'pondr', 'Ponds reservoir', 'kg/m^2', &
1893                     & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(8), dt,dw2)
1894                CALL histdef(hist2_id, 'lakevol', 'Volume in lake reservoir', 'kg/m^2', &
1895                     & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(8), dt, dw2)
1896                IF ( do_irrigation ) THEN
1897!                   CALL histdef(hist2_id, 'irrigation', 'Net irrigation', 'mm/d', &
1898!                        & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop2(8), dt, dw2)
1899                   CALL histdef(hist2_id, 'netirrig', 'Net irrigation requirement', 'mm/d', &
1900                        & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop2(8), dt, dw2)
1901                   CALL histdef(hist2_id, 'irrigmap', 'Map of irrigated areas', 'm^2', &
1902                        & iim,jjm, hori_id2, 1,1,1, -99, 32, once2(8), dt, dw2)
1903                ENDIF
1904                CALL histdef(hist2_id, 'floodmap', 'Map of floodplains', 'm^2', &
1905                     & iim,jjm, hori_id2, 1,1,1, -99, 32, once2(8), dt,dw2)
1906                CALL histdef(hist2_id, 'swampmap', 'Map of swamps', 'm^2', &
1907                  & iim,jjm, hori_id2, 1,1,1, -99, 32, once2(8), dt,dw2)
1908             ENDIF
1909             !! define irrigation regardless of routing and do_irrigation
1910             CALL histdef(hist2_id, 'irrigation', 'Net irrigation', 'mm/d', &
1911                  & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop2(8), dt, dw2)
1912             !-
1913             !- SECHIBA_HISTLEVEL2 = 9
1914             !-
1915             CALL histdef(hist2_id, 'beta', 'Beta Function', '1',  &
1916                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(9), dt, dw2)
1917             CALL histdef(hist2_id, 'raero', 'Aerodynamic resistance', 's/m',  &
1918                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(9), dt, dw2)
1919             ! Ajouts Nathalie - Novembre 2006
1920             CALL histdef(hist2_id, 'Wind', 'Wind speed', 'm/s',  &
1921                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(9), dt, dw2)
1922             ! Fin ajouts Nathalie
1923             CALL histdef(hist2_id, 'qsatt' , 'Surface saturated humidity', 'g/g', &
1924                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(9), dt, dw2)
1925             CALL histdef(hist2_id, 'vbeta1', 'Beta for sublimation', '1',  &
1926                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(9), dt, dw2)
1927             CALL histdef(hist2_id, 'vbeta4', 'Beta for bare soil', '1',  &
1928                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(9), dt, dw2)
1929             IF ( ok_co2 ) THEN
1930                CALL histdef(hist2_id, 'gsmean', 'mean stomatal conductance', 'mol/m2/s', &
1931                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(9), dt, dw2)
1932             ENDIF
1933             CALL histdef(hist2_id, 'vbeta5', 'Beta for floodplains', '1',  &
1934                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(9), dt, dw2)
1935             IF (  hydrol_cwrr ) THEN
1936                CALL histdef(hist2_id, 'reinf_slope', 'Slope index for each grid box', '1', &
1937                     & iim,jjm, hori_id2, 1,1,1, -99, 32, once2(9),  dt,dw2)
1938                CALL histdef(hist2_id, 'soilindex', 'Soil index', '1', &
1939                     & iim,jjm, hori_id2, 1, 1, 1, -99, 32, once2(9),  dt,dw2)
1940             ENDIF
1941             CALL histdef(hist2_id, 'humrel', 'Soil moisture stress', '-',  &
1942                  & iim,jjm, hori_id2, nvm,1,nvm, vegax_id2, 32, avescatter2(9), dt, dw2)
1943             !-
1944             !- SECHIBA_HISTLEVEL2 = 10
1945             !-
1946             IF ( ok_co2 ) THEN
1947                CALL histdef(hist2_id, 'cimean', 'Stomatal CO2 concentation', 'mmole/m2/s', &
1948                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt, dw2)
1949             ENDIF
1950             CALL histdef(hist2_id, 'vbeta3', 'Beta for Transpiration', 'mm/d', &
1951                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt, dw2)
1952             CALL histdef(hist2_id, 'rveget', 'Canopy resistance', 's/m', &
1953                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt, dw2)
1954             IF ( .NOT. hydrol_cwrr ) THEN
1955                CALL histdef(hist2_id, 'rsol', 'Soil resistance', 's/m',  &
1956                     & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(10), dt, dw2)
1957             ENDIF
1958             CALL histdef(hist2_id,'vbeta2','Beta for Interception loss','mm/d', &
1959                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt, dw2)
1960             CALL histdef(hist2_id, 'qsintmax', 'Maximum Interception capacity', 'Kg/m^2', &
1961                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt, dw2)
1962             
1963             IF ( ok_bvoc ) THEN
1964                CALL histdef(hist2_id, 'PAR', 'PAR', 'umol phot/m^2/s',  &
1965                     & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(10), dt,dw2)
1966                IF ( ok_radcanopy ) THEN
1967                   CALL histdef(hist2_id, 'PARsun', 'Sunlit Leaf PAR', 'umol phot/m^2/s', &
1968                        & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
1969                   CALL histdef(hist2_id, 'PARsh', 'Shaded Leaf Area PAR', 'umol phot/m^2/s', &
1970                        & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
1971                   CALL histdef(hist2_id, 'laisun', 'Sunlit Leaf Area Index', '1', &
1972                        & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
1973                   CALL histdef(hist2_id, 'laish', 'Shaded Leaf Area Index', '1', &
1974                        & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
1975                   CALL histdef(hist2_id, 'Fdf', 'Fdf', '1',  &
1976                        & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(10), dt,dw2)
1977                   IF ( ok_multilayer ) then
1978                      CALL histdef(hist2_id, 'PARsuntab', 'Sunlit Leaf PAR', 'umol phot/m^2/s', &
1979                           & iim,jjm, hori_id2, nlai+1, 1, nlai+1, laiax_id2, 32, avescatter2(10), dt,dw2)
1980                      CALL histdef(hist2_id, 'PARshtab', 'Shaded Leaf Area PAR', 'umol phot/m^2/s', &
1981                           & iim,jjm, hori_id2, nlai+1, 1, nlai+1, laiax_id2, 32, avescatter2(10), dt,dw2)
1982                   ENDIF
1983                   CALL histdef(hist2_id, 'coszang', 'coszang', '1',  &
1984                        & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(10), dt,dw2)
1985                   CALL histdef(hist2_id, 'PARdf', 'PARdf', '1',  &
1986                        & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(10), dt,dw2)
1987                   CALL histdef(hist2_id, 'PARdr', 'PARdr', '1',  &
1988                        & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(10), dt,dw2)
1989                   CALL histdef(hist2_id, 'Trans', 'Trans', '1',  &
1990                        & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(10), dt,dw2)
1991                END IF
1992               
1993                CALL histdef(hist2_id, 'flx_fertil_no', 'flx_fertil_no', 'ngN/m^2/s', &
1994                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
1995                CALL histdef(hist2_id, 'CRF', 'CRF', '1', &
1996                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
1997                CALL histdef(hist2_id, 'flx_co2_bbg_year', 'flx_co2_bbg_year', 'kgC/m^2/yr ', &
1998                     & iim,jjm, hori_id2, 1,1,1, -99, 32, once2(10), dt,dw2) 
1999                CALL histdef(hist2_id, 'N_qt_WRICE_year', 'N_qt_WRICE_year', 'kgN/yr ', &
2000                     & iim,jjm, hori_id2, 1,1,1, -99, 32, once2(10), dt,dw2) 
2001                CALL histdef(hist2_id, 'N_qt_OTHER_year', 'N_qt_OTHER_year', 'kgN/yr ', &
2002                     & iim,jjm, hori_id2, 1,1,1, -99, 32, once2(10), dt,dw2) 
2003                CALL histdef(hist2_id, 'flx_iso', 'flx_iso', 'kgC/m^2/s', &
2004                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
2005                CALL histdef(hist2_id, 'flx_mono', 'flx_mono', 'kgC/m^2/s',&
2006                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
2007                CALL histdef(hist2_id, 'flx_apinen', 'flx_apinen', 'kgC/m^2/s',&
2008                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
2009                CALL histdef(hist2_id, 'flx_bpinen', 'flx_bpinen', 'kgC/m^2/s',&
2010                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
2011                CALL histdef(hist2_id, 'flx_limonen', 'flx_limonen', 'kgC/m^2/s',&
2012                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
2013                CALL histdef(hist2_id, 'flx_myrcen', 'flx_myrcen', 'kgC/m^2/s',&
2014                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
2015                CALL histdef(hist2_id, 'flx_sabinen', 'flx_sabinen', 'kgC/m^2/s',&
2016                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
2017                CALL histdef(hist2_id, 'flx_camphen', 'flx_camphen', 'kgC/m^2/s',&
2018                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
2019                CALL histdef(hist2_id, 'flx_3caren', 'flx_3caren', 'kgC/m^2/s',&
2020                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
2021                CALL histdef(hist2_id, 'flx_tbocimen', 'flx_tbocimen', 'kgC/m^2/s',&
2022                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
2023                CALL histdef(hist2_id, 'flx_othermono', 'flx_othermono', 'kgC/m^2/s',&
2024                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
2025                CALL histdef(hist2_id, 'flx_sesquiter', 'flx_sesquiter', 'kgC/m^2/s',&
2026                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
2027                CALL histdef(hist2_id, 'flx_ORVOC', 'flx_ORVOC', 'kgC/m^2/s',&
2028                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
2029                CALL histdef(hist2_id, 'flx_MBO', 'flx_MBO', 'kgC/m^2/s',&
2030                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
2031                CALL histdef(hist2_id, 'flx_methanol', 'flx_methanol', 'kgC/m^2/s',&
2032                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
2033                CALL histdef(hist2_id, 'flx_acetone', 'flx_acetone', 'kgC/m^2/s',&
2034                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(1), dt,dw2)   !! LDF TEST modificato a 1... !!
2035                CALL histdef(hist2_id, 'flx_acetal', 'flx_acetal', 'kgC/m^2/s',&
2036                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(1), dt,dw2)   !! LDF TEST modificato a 1... !!
2037                CALL histdef(hist2_id, 'flx_formal', 'flx_formal', 'kgC/m^2/s',&
2038                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
2039                CALL histdef(hist2_id, 'flx_acetic', 'flx_acetic', 'kgC/m^2/s',&
2040                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
2041                CALL histdef(hist2_id, 'flx_formic', 'flx_formic', 'kgC/m^2/s',&
2042                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
2043                CALL histdef(hist2_id, 'flx_no_soil', 'flx_no_soil', 'ngN/m^2/s',&
2044                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
2045                CALL histdef(hist2_id, 'flx_no', 'flx_no', 'ngN/m^2/s',&
2046                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
2047             ENDIF
2048         ELSE 
2049             !-
2050             !- This is the ALMA convention output now
2051             !-
2052             !-
2053             IF ( GridType == "RegLonLat" ) THEN
2054#ifdef CPP_PARA
2055                CALL histbeg(histname2, iim, lon_rect, jjm, lat_rect, 1, iim, 1, jjm, &
2056                     &     istp_old, date0, dt, hori_id2, hist2_id,orch_domain_id)
2057#else
2058                CALL histbeg(histname2, iim, lon_rect, jjm, lat_rect, 1, iim, 1, jjm, &
2059                     &     istp_old, date0, dt, hori_id2, hist2_id)
2060#endif
2061                IF (printlev >= 2) WRITE(numout,*)  'HISTBEG2 --->',istp_old,date0,dt,dw2,hist2_id
2062             ELSE
2063#ifdef CPP_PARA
2064                CALL histbeg(histname2, iim, lon, jjm, lat, 1, iim, 1, jjm, &
2065                     &     istp_old, date0, dt, hori_id2, hist2_id,domain_id=orch_domain_id)
2066#else
2067                CALL histbeg(histname2, iim, lon, jjm, lat, 1, iim, 1, jjm, &
2068                     &     istp_old, date0, dt, hori_id2, hist2_id)
2069#endif
2070             ENDIF
2071             !-
2072             CALL histvert(hist2_id, 'veget', 'Vegetation types', '1', &
2073                  &    nvm,   veg, vegax_id2)
2074             CALL histvert(hist2_id, 'solth', 'Soil levels',      'm', &
2075                  &    ngrnd, sol, solax_id2)
2076             CALL histvert(hist2_id, 'soiltyp', 'Soil types',      '1', &
2077                  &    nstm, soltyp, soltax_id2)
2078             CALL histvert(hist2_id, 'nobio', 'Other surface types',      '1', &
2079                  &    nnobio, nobiotyp, nobioax_id2)
2080             IF (  hydrol_cwrr ) THEN
2081                CALL histvert(hist2_id, 'solay', 'Hydrol soil levels',      'm', &
2082                     &    nslm, diaglev(1:nslm), solayax_id2)
2083             ENDIF
2084             !-
2085             !-  Vegetation
2086             !-
2087             CALL histdef(hist2_id, 'vegetfrac', 'Fraction of vegetation', '1', &
2088                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(3), dt, dw2)
2089             CALL histdef(hist2_id, 'maxvegetfrac', 'Maximum fraction of vegetation', '1', &
2090                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(3), dt, dw2)
2091             CALL histdef(hist2_id, 'nobiofrac', 'Fraction of other surface types', '1', &
2092                  & iim,jjm, hori_id2, nnobio, 1, nnobio, nobioax_id2, 32, avescatter2(3), dt, dw2)
2093             !-
2094             !-  General energy balance
2095             !-
2096             CALL histdef(hist2_id, 'SWnet', 'Net shortwave radiation', 'W/m^2',  &
2097                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(1), dt, dw2)
2098             CALL histdef(hist2_id, 'LWnet', 'Net longwave radiation', 'W/m^2',  &
2099                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(1), dt, dw2)
2100             CALL histdef(hist2_id, 'Qh', 'Sensible heat flux', 'W/m^2',  &
2101                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(1), dt, dw2)
2102             CALL histdef(hist2_id, 'Qle', 'Latent heat flux', 'W/m^2',  &
2103                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(1), dt, dw2)
2104             CALL histdef(hist2_id, 'Qg', 'Ground heat flux', 'W/m^2',  &
2105                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(1), dt, dw2)
2106             CALL histdef(hist2_id, 'Qf', 'Energy of fusion', 'W/m^2',  &
2107                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(5), dt, dw2)
2108             CALL histdef(hist2_id, 'Qv', 'Energy of sublimation', 'W/m^2',  &
2109                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(5), dt, dw2)
2110             CALL histdef(hist2_id, 'DelSurfHeat', 'Change in surface layer heat', 'J/m^2',  &
2111                  & iim,jjm, hori_id2, 1,1,1, -99, 32, sumscatter2(7), dt, dw2)
2112             CALL histdef(hist2_id, 'DelColdCont', 'Change in snow surface layer cold content', 'J/m^2',  &
2113                  & iim,jjm, hori_id2, 1,1,1, -99, 32, sumscatter2(7), dt, dw2)
2114             !-
2115             !- General water balance
2116             !-
2117             CALL histdef(hist2_id, 'Snowf', 'Snowfall rate', 'kg/m^2/s',  &
2118                  & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop_scinsec2(1), dt, dw2)
2119             CALL histdef(hist2_id, 'Rainf', 'Rainfall rate', 'kg/m^2/s',  &
2120                  & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop_scinsec2(1), dt, dw2)
2121             CALL histdef(hist2_id, 'Evap', 'Total Evapotranspiration', 'kg/m^2/s', &
2122                  & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop_scinsec2(1), dt, dw2)
2123             CALL histdef(hist2_id, 'Qs', 'Surface runoff', 'kg/m^2/s', &
2124                  & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop_scinsec2(1), dt, dw2)
2125             CALL histdef(hist2_id, 'Qsb', 'Sub-surface runoff', 'kg/m^2/s', &
2126                  & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop_scinsec2(1), dt, dw2)
2127             CALL histdef(hist2_id, 'Qsm', 'Snowmelt', 'kg/m^2/s', &
2128                  & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop_scinsec2(1), dt, dw2)
2129             CALL histdef(hist2_id, 'DelSoilMoist', 'Change in soil moisture', 'kg/m^2',  &
2130                  & iim,jjm, hori_id2, 1, 1, 1, -99, 32, sumscatter2(7), dt, dw2)
2131             CALL histdef(hist2_id, 'DelSurfStor', 'Change in Surface Water Storage','kg/m^2',&
2132                  & iim,jjm, hori_id2, 1, 1, 1, -99, 32, sumscatter2(7), dt,dw2)
2133             CALL histdef(hist2_id, 'DelIntercept', 'Change in interception storage', 'kg/m^2',  &
2134                  & iim,jjm, hori_id2, 1, 1, 1, -99, 32, sumscatter2(7), dt, dw2)
2135             CALL histdef(hist2_id, 'DelSWE', 'Change in interception storage Snow Water Equivalent', 'kg/m^2',  &
2136                  & iim,jjm, hori_id2, 1, 1, 1, -99, 32, sumscatter2(7), dt, dw2)
2137             !-
2138             !- Surface state
2139             !-
2140             CALL histdef(hist2_id, 'AvgSurfT', 'Average surface temperature', 'K', &
2141                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(1), dt, dw2)
2142             CALL histdef(hist2_id, 'RadT', 'Surface radiative temperature', 'K', &
2143                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(5), dt, dw2)
2144             CALL histdef(hist2_id, 'Albedo', 'Albedo', '1', &
2145                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(7), dt, dw2)
2146             CALL histdef(hist2_id, 'SurfStor', 'Surface Water Storage','kg/m^2',  &
2147                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(1), dt, dw2)
2148             CALL histdef(hist2_id, 'SWE', 'Snow Water Equivalent', 'kg/m^2', &
2149                  & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter2(1), dt,dw2)
2150             !!-
2151             !-  Sub-surface state
2152             !-
2153             IF ( .NOT. hydrol_cwrr ) THEN
2154                CALL histdef(hist2_id, 'SoilMoist', '3D average layer soil moisture', 'kg/m^2',  &
2155                     & iim,jjm, hori_id2, 1, 1, 1, -99, 32, avescatter2(7), dt, dw2)
2156             ELSE
2157                CALL histdef(hist2_id, 'SoilMoist', '3D average layer soil moisture', 'kg/m^2',  &
2158                     & iim,jjm, hori_id2, nslm, 1, nslm, solayax_id2, 32, avescatter2(7), dt, dw2)
2159             ENDIF
2160             CALL histdef(hist2_id, 'SoilWet', 'Total soil wetness', '-',  &
2161                  & iim,jjm, hori_id2, 1, 1, 1, -99, 32, avescatter2(1), dt, dw2)
2162             CALL histdef(hist2_id, 'SoilTemp', 'Soil temperature profile', 'K', &
2163                  & iim,jjm, hori_id2, ngrnd, 1, ngrnd, solax_id2, 32, avescatter2(7), dt, dw2)
2164             !-
2165             !-  Evaporation components
2166             !-
2167             CALL histdef(hist2_id, 'PotEvap', 'Potential evapotranspiration', 'kg/m^2/s', &
2168                  & iim,jjm, hori_id2, 1, 1, 1, -99, 32, fluxop_scinsec2(1), dt, dw2)
2169             CALL histdef(hist2_id, 'transpot', 'Potential transpiration', 'kg/m^2/s', &
2170                  & iim,jjm, hori_id2, nvm,1,nvm, vegax_id2, 32,fluxop_scinsec2(1), dt, dw2)
2171             CALL histdef(hist2_id, 'ECanop', 'Interception evaporation', 'kg/m^2/s', &
2172                  & iim,jjm, hori_id2, 1, 1, 1, -99, 32, fluxop_scinsec2(5), dt, dw2)
2173             CALL histdef(hist2_id, 'TVeg', 'Transpiration', 'kg/m^2/s', &
2174                  & iim,jjm, hori_id2, 1, 1, 1, -99, 32, fluxop_scinsec2(5), dt, dw2)
2175             CALL histdef(hist2_id, 'ESoil', 'Bare soil evaporation', 'kg/m^2/s', &
2176                  & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop_scinsec2(5), dt, dw2)
2177             CALL histdef(hist2_id, 'RootMoist','Root zone soil water', 'kg/m^2',  &
2178                  & iim,jjm, hori_id2, 1, 1, 1, -99, 32, avescatter2(1), dt, dw2)
2179             CALL histdef(hist2_id, 'SubSnow','Snow sublimation','kg/m^2/s', &
2180                  & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop_scinsec2(1), dt, dw2)
2181             CALL histdef(hist2_id, 'ACond', 'Aerodynamic conductance', 'm/s',  &
2182                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(5), dt, dw2)
2183             !-
2184             !-
2185             !-  Cold Season Processes
2186             !-
2187             CALL histdef(hist2_id, 'SnowFrac', 'Snow cover fraction', '1',  &
2188                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(7), dt, dw2)
2189             CALL histdef(hist2_id, 'SAlbedo', 'Snow albedo', '1', &
2190                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(7), dt, dw2)
2191             CALL histdef(hist2_id, 'SnowDepth', '3D snow depth', 'm', &
2192                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(7), dt, dw2)
2193             !-
2194             !- Hydrologic variables
2195             !-
2196             IF ( river_routing ) THEN
2197                !
2198                IF (do_floodplains) THEN
2199                   CALL histdef(hist2_id, 'EWater', 'Open water evaporation', 'kg/m^2/s', &
2200                        & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop_scinsec2(5), dt, dw2)
2201                   CALL histdef(hist2_id, 'FloodFrac', 'Floodplain Fraction', '-', &
2202                        & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(1), dt,dw2)
2203                ENDIF
2204                !
2205                CALL histdef(hist2_id, 'IrrigationMap', 'Map of irrigated areas', 'm^2', &
2206                     & iim,jjm, hori_id2, 1,1,1, -99, 32, once2(1), dt, dw2)
2207                CALL histdef(hist2_id, 'FloodplainsMap', 'Map of flooded areas', 'm^2', &
2208                     & iim,jjm, hori_id2, 1,1,1, -99, 32, once2(1), dt,dw2)
2209                CALL histdef(hist2_id, 'SwampMap', 'Map of swamp areas', 'm^2', &
2210                  & iim,jjm, hori_id2, 1,1,1, -99, 32, once2(1), dt,dw2)
2211                CALL histdef(hist2_id, 'Dis', 'Simulated River Discharge', 'm^3/s', &
2212                     & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop_scinsec2(1), dt,dw2)
2213             ENDIF
2214             !-
2215             !-
2216             !-
2217             CALL histdef(hist2_id, 'humrel', 'Soil moisture stress', '-',  &
2218                  & iim,jjm, hori_id2, nvm,1,nvm, vegax_id2, 32, avescatter2(9), dt, dw2)
2219             CALL histdef(hist2_id, 'vegstress', 'Vegetation growth stress', '-',  &
2220                  & iim,jjm, hori_id2, nvm,1,nvm, vegax_id2, 32, avescatter2(9), dt, dw2)
2221             !-
2222             !-  The carbon budget
2223             !-
2224             IF ( ok_co2 ) THEN
2225                CALL histdef(hist2_id, 'GPP', 'Net assimilation of carbon by the vegetation', 'gC/m^2/s', &
2226                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, fluxop_scinsec2(1), dt, dw2)
2227             ENDIF
2228             IF ( ok_stomate ) THEN
2229                CALL histdef(hist2_id, 'NEE', 'Net Ecosystem Exchange', 'gC/m^2/s', &
2230                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, fluxop_scinsec2(1), dt,dw2)
2231                CALL histdef(hist2_id, 'maint_resp', 'Maintenance respiration', 'gC/m^2/s', &
2232                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, fluxop_scinsec2(1), dt,dw2)
2233                CALL histdef(hist2_id, 'hetero_resp', 'Heterotrophic respiration', 'gC/m^2/s', &
2234                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, fluxop_scinsec2(1), dt,dw2)
2235                CALL histdef(hist2_id, 'growth_resp', 'Growth respiration', 'gC/m^2/s', &
2236                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, fluxop_scinsec2(1), dt, dw2)
2237                CALL histdef(hist2_id, 'npp', 'Net Primary Production', 'gC/m^2/s', &
2238                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, fluxop_scinsec2(1), dt, dw2)
2239             ENDIF
2240             !
2241          ENDIF
2242          !-
2243          CALL histdef(hist2_id, 'LandPoints', 'Land Points', '1', &
2244               & iim,jjm, hori_id2, 1,1,1, -99, 32, once2(10), dt, dw2) 
2245          CALL histdef(hist2_id, 'Areas', 'Mesh areas', 'm2', &
2246               & iim,jjm, hori_id2, 1,1,1, -99, 32, once2(1), dt, dw2)
2247          CALL histdef(hist2_id, 'Contfrac', 'Continental fraction', '1', &
2248               & iim,jjm, hori_id2, 1,1,1, -99, 32, once2(1), dt, dw2)
2249          !-
2250          ! Write the names of the pfts in the high frequency sechiba history files
2251          global_attribute="PFT_name"
2252          DO i=1,nvm
2253             WRITE(global_attribute(9:10),"(I2.2)") i
2254             CALL histglobal_attr(hist2_id, global_attribute, PFT_name(i))
2255          ENDDO
2256          !-
2257          CALL histend(hist2_id)
2258      ENDIF
2259  ENDIF
2260
2261    !-
2262    !=====================================================================
2263    !- 3.2 STOMATE's history file
2264    !=====================================================================
2265    IF ( ok_stomate ) THEN
2266       !-
2267       ! STOMATE IS ACTIVATED
2268       !-
2269       !Config Key   = STOMATE_OUTPUT_FILE
2270       !Config Desc  = Name of file in which STOMATE's output is going to be written
2271       !Config If    = OK_STOMATE
2272       !Config Def   = stomate_history.nc
2273       !Config Help  = This file is going to be created by the model
2274       !Config         and will contain the output from the model.
2275       !Config         This file is a truly COADS compliant netCDF file.
2276       !Config         It will be generated by the hist software from
2277       !Config         the IOIPSL package.
2278       !Config Units = [FILE]
2279       !-
2280       stom_histname='stomate_history.nc'
2281       CALL getin_p('STOMATE_OUTPUT_FILE', stom_histname)       
2282       IF (printlev >= 2) WRITE(numout,*) 'STOMATE_OUTPUT_FILE', TRIM(stom_histname)
2283       !-
2284       !Config Key   = STOMATE_HIST_DT
2285       !Config Desc  = STOMATE history time step
2286       !Config If    = OK_STOMATE
2287       !Config Def   = 10.
2288       !Config Help  = Time step of the STOMATE history file
2289       !Config Units = [days]
2290       !-
2291       hist_days_stom = 10.
2292       CALL getin_p('STOMATE_HIST_DT', hist_days_stom)       
2293
2294       IF ( hist_id < 0 ) THEN
2295          ! Deactivate all history files if sechiba_history file is deactivated
2296          hist_dt_stom=0
2297          IF (printlev >= 2) WRITE(numout,*) &
2298               'STOMATE history file will not be created because sechiba_history file is deactivated.'
2299       ELSE IF ( hist_days_stom == moins_un ) THEN
2300          hist_dt_stom = moins_un
2301          IF (printlev >= 2) WRITE(numout,*) 'output frequency for STOMATE history file (d): one month.'
2302       ELSE IF ( hist_days_stom == 0 ) THEN
2303          ! Deactivate this file
2304          hist_dt_stom=0
2305          IF (printlev >= 2) WRITE(numout,*) 'STOMATE history file will not be created'
2306       ELSE
2307          hist_dt_stom = NINT( hist_days_stom ) * one_day
2308          IF (printlev >= 2) WRITE(numout,*) 'output frequency for STOMATE history file (d): ', &
2309               hist_dt_stom/one_day
2310       ENDIF
2311
2312       ! test consistency between STOMATE_HIST_DT and DT_STOMATE parameters
2313       dt_stomate_loc = one_day
2314       CALL getin_p('DT_STOMATE', dt_stomate_loc)
2315       IF ( hist_days_stom /= moins_un .AND. hist_dt_stom/=0) THEN
2316          IF (dt_stomate_loc > hist_dt_stom) THEN
2317             IF (printlev >= 2) WRITE(numout,*) "DT_STOMATE = ",dt_stomate_loc,"  , STOMATE_HIST_DT = ",hist_dt_stom
2318             CALL ipslerr_p (3,'intsurf_history', &
2319                  &          'Problem with DT_STOMATE > STOMATE_HIST_DT','', &
2320                  &          '(must be less or equal)')
2321          ENDIF
2322       ENDIF
2323       !-
2324       !- Initialize stomate_history file
2325       IF ( hist_dt_stom == 0 ) THEN
2326          ! Case hist_dt_stom=0 : No creation of stomate_history.nc file
2327          ! Nothing will be done.
2328          hist_id_stom=-1
2329       ELSE
2330          ! Initialise stomate_history file
2331       IF (is_omp_root) THEN
2332          IF ( GridType == "RegLonLat" ) THEN
2333#ifdef CPP_PARA
2334             CALL histbeg(stom_histname, iim, lon_rect, jjm, lat_rect,  1, iim, 1, jjm, &
2335                  &     istp_old, date0, dt, hori_id, hist_id_stom,domain_id=orch_domain_id)
2336#else
2337             CALL histbeg(stom_histname, iim, lon_rect, jjm, lat_rect,  1, iim, 1, jjm, &
2338                  &     istp_old, date0, dt, hori_id, hist_id_stom)
2339#endif
2340          ELSE
2341#ifdef CPP_PARA
2342             CALL histbeg(stom_histname, iim, lon, jjm, lat,  1, iim, 1, jjm, &
2343                  &     istp_old, date0, dt, hori_id, hist_id_stom,domain_id=orch_domain_id)
2344#else
2345             CALL histbeg(stom_histname, iim, lon, jjm, lat,  1, iim, 1, jjm, &
2346                  &     istp_old, date0, dt, hori_id, hist_id_stom)
2347#endif
2348          ENDIF
2349          !- define PFT axis
2350          hist_PFTaxis = (/ ( REAL(i,r_std), i=1,nvm ) /)
2351          !- declare this axis
2352          CALL histvert (hist_id_stom, 'PFT', 'Plant functional type', &
2353               & '1', nvm, hist_PFTaxis, hist_PFTaxis_id)
2354          ! deforestation
2355          !- define Pool_10 axis
2356          hist_pool_10axis = (/ ( REAL(i,r_std), i=1,10 ) /)
2357          !- declare this axis
2358          CALL histvert (hist_id_stom, 'P10', 'Pool 10 years', &
2359               & '1', 10, hist_pool_10axis, hist_pool_10axis_id)
2360         
2361          !- define Pool_100 axis
2362          hist_pool_100axis = (/ ( REAL(i,r_std), i=1,100 ) /)
2363          !- declare this axis
2364          CALL histvert (hist_id_stom, 'P100', 'Pool 100 years', &
2365               & '1', 100, hist_pool_100axis, hist_pool_100axis_id)
2366         
2367          !- define Pool_11 axis
2368          hist_pool_11axis = (/ ( REAL(i,r_std), i=1,11 ) /)
2369          !- declare this axis
2370          CALL histvert (hist_id_stom, 'P11', 'Pool 10 years + 1', &
2371               & '1', 11, hist_pool_11axis, hist_pool_11axis_id)
2372         
2373          !- define Pool_101 axis
2374          hist_pool_101axis = (/ ( REAL(i,r_std), i=1,101 ) /)
2375          !- declare this axis
2376          CALL histvert (hist_id_stom, 'P101', 'Pool 100 years + 1', &
2377               & '1', 101, hist_pool_101axis, hist_pool_101axis_id)
2378          !- define deep permafrost axis for stomate variables
2379          CALL histvert(hist_id_stom, 'solth', 'deep soil levels',      'm', &
2380               &    ngrnd, sol, hist_stomate_deepsoil)
2381
2382          snowlev = (/ ( REAL(i,r_std), i=1,nsnow ) /)
2383          CALL histvert(hist_id_stom, 'snowlev', 'snow levels',      'index', &
2384               &    nsnow, snowlev, hist_stomate_snow)
2385       ENDIF
2386!! yidi
2387 !      IF (ok_oilpalm) THEN
2388          phylev = (/ ( REAL(i,r_std), i=1,nphs ) /)
2389          !- define oilpalm phytomer axis for stomate variables
2390          CALL histvert(hist_id_stom, 'nphs', 'phytomer numbers',      'index', &
2391               &    nphs, phylev, hist_stomate_phytomer)
2392 !      ENDIF
2393!! yidi
2394       !- define STOMATE history file
2395       CALL ioipslctrl_histstom (hist_id_stom, nvm, iim, jjm, &
2396            & dt, hist_dt_stom, hori_id, hist_PFTaxis_id, &
2397            & hist_pool_10axis_id, hist_pool_100axis_id, &
2398            & hist_pool_11axis_id, hist_pool_101axis_id, &
2399            & hist_stomate_phytomer, & !!  yidi
2400            & hist_stomate_deepsoil, hist_stomate_snow)
2401       
2402       !- Write the names of the pfts in the stomate history files
2403       IF (is_omp_root) THEN
2404          global_attribute="PFT_name"
2405          DO i=1,nvm
2406             WRITE(global_attribute(9:10),"(I2.2)") i
2407             CALL histglobal_attr(hist_id_stom, global_attribute, PFT_name(i))
2408          ENDDO
2409
2410       !- end definition
2411          CALL histend(hist_id_stom)
2412       ENDIF
2413    END IF ! IF ( hist_dt_stom == 0 )
2414
2415       !-
2416       !-
2417       !-
2418       ! STOMATE IPCC OUTPUTS IS ACTIVATED
2419       !-
2420       !Config Key   = STOMATE_IPCC_OUTPUT_FILE
2421       !Config Desc  = Name of file in which STOMATE's output is going to be written
2422       !Config If    = OK_STOMATE
2423       !Config Def   = stomate_ipcc_history.nc
2424       !Config Help  = This file is going to be created by the model
2425       !Config         and will contain the output from the model.
2426       !Config         This file is a truly COADS compliant netCDF file.
2427       !Config         It will be generated by the hist software from
2428       !Config         the IOIPSL package.
2429       !Config Units = [FILE]
2430       !-
2431       stom_ipcc_histname='stomate_ipcc_history.nc'
2432       CALL getin_p('STOMATE_IPCC_OUTPUT_FILE', stom_ipcc_histname)       
2433       IF (printlev >= 2) WRITE(numout,*) 'STOMATE_IPCC_OUTPUT_FILE', TRIM(stom_ipcc_histname)
2434       !-
2435       !Config Key   = STOMATE_IPCC_HIST_DT
2436       !Config Desc  = STOMATE IPCC history time step
2437       !Config If    = OK_STOMATE
2438       !Config Def   = 0.
2439       !Config Help  = Time step of the STOMATE IPCC history file
2440       !Config Units = [days]
2441       !-
2442       hist_days_stom_ipcc = zero
2443       CALL getin_p('STOMATE_IPCC_HIST_DT', hist_days_stom_ipcc)       
2444       IF ( hist_days_stom_ipcc == moins_un ) THEN
2445          hist_dt_stom_ipcc = moins_un
2446          IF (printlev >= 2) WRITE(numout,*) 'output frequency for STOMATE IPCC history file (d): one month.'
2447       ELSE
2448          hist_dt_stom_ipcc = NINT( hist_days_stom_ipcc ) * one_day
2449          IF (printlev >= 2) WRITE(numout,*) 'output frequency for STOMATE IPCC history file (d): ', &
2450            hist_dt_stom_ipcc/one_day
2451       ENDIF
2452       
2453       IF ( hist_dt_stom_ipcc /= 0 .AND. hist_id < 0 ) THEN
2454          ! sechiba_history file is not created therefore STOMATE IPCC history file will be deactivated
2455          hist_dt_stom_ipcc=0
2456          hist_days_stom_ipcc=0
2457          IF (printlev >= 2) WRITE(numout,*) 'STOMATE IPCC history file is not created.'
2458       END IF
2459
2460       ! test consistency between STOMATE_IPCC_HIST_DT and DT_STOMATE parameters
2461       dt_stomate_loc = one_day
2462       CALL getin_p('DT_STOMATE', dt_stomate_loc)
2463       IF ( hist_days_stom_ipcc > zero ) THEN
2464          IF (dt_stomate_loc > hist_dt_stom_ipcc) THEN
2465             IF (printlev >= 2) WRITE(numout,*) "DT_STOMATE = ",dt_stomate_loc,"  , STOMATE_IPCC_HIST_DT = ",hist_dt_stom_ipcc
2466             CALL ipslerr_p (3,'intsurf_history', &
2467                  &          'Problem with DT_STOMATE > STOMATE_IPCC_HIST_DT','', &
2468                  &          '(must be less or equal)')
2469          ENDIF
2470       ENDIF
2471
2472       !Config Key   = OK_HISTSYNC
2473       !Config Desc  = Syncronize and write IOIPSL output files at each time step
2474       !Config If    =
2475       !Config Def   = FALSE
2476       !Config Help  = Setting this flag to true might affect run performance. Only use it for debug perpose.
2477       !Config Units = [FLAG]
2478       ok_histsync=.FALSE.
2479       CALL getin_p('OK_HISTSYNC', ok_histsync)       
2480
2481
2482
2483       IF ( hist_dt_stom_ipcc == 0 ) THEN
2484          hist_id_stom_ipcc = -1
2485       ELSE
2486          !-
2487          !- initialize
2488          IF (is_omp_root) THEN
2489             IF ( GridType == "RegLonLat" ) THEN
2490#ifdef CPP_PARA
2491                CALL histbeg(stom_ipcc_histname, iim, lon_rect, jjm, lat_rect,  1, iim, 1, jjm, &
2492                     &     istp_old, date0, dt, hori_id, hist_id_stom_ipcc,domain_id=orch_domain_id)
2493#else
2494                CALL histbeg(stom_ipcc_histname, iim, lon_rect, jjm, lat_rect,  1, iim, 1, jjm, &
2495                     &     istp_old, date0, dt, hori_id, hist_id_stom_ipcc)
2496#endif
2497             ELSE
2498#ifdef CPP_PARA
2499                CALL histbeg(stom_ipcc_histname, iim, lon, jjm, lat,  1, iim, 1, jjm, &
2500                     &     istp_old, date0, dt, hori_id, hist_id_stom_ipcc,domain_id=orch_domain_id)
2501#else
2502                CALL histbeg(stom_ipcc_histname, iim, lon, jjm, lat,  1, iim, 1, jjm, &
2503                     &     istp_old, date0, dt, hori_id, hist_id_stom_ipcc)
2504#endif
2505             ENDIF
2506             !- declare this axis
2507             CALL histvert (hist_id_stom_IPCC, 'PFT', 'Plant functional type', &
2508                  & '1', nvm, hist_PFTaxis, hist_IPCC_PFTaxis_id)
2509             
2510             !- define STOMATE history file
2511             CALL ioipslctrl_histstomipcc (hist_id_stom_IPCC, nvm, iim, jjm, &
2512                  & dt, hist_dt_stom_ipcc, hori_id, hist_IPCC_PFTaxis_id)
2513             
2514             !- Write the names of the pfts in the stomate history files
2515             global_attribute="PFT_name"
2516             DO i=1,nvm
2517                WRITE(global_attribute(9:10),"(I2.2)") i
2518                CALL histglobal_attr(hist_id_stom_IPCC, global_attribute, PFT_name(i))
2519             ENDDO
2520
2521             !- end definition
2522             CALL histend(hist_id_stom_IPCC)
2523          ENDIF
2524      ENDIF
2525   ENDIF
2526
2527
2528    RETURN
2529
2530  END SUBROUTINE ioipslctrl_history
2531
2532!! ================================================================================================================================
2533!! SUBROUTINE    : ioipslctrl_histstom
2534!!
2535!>\BRIEF         This subroutine initialize the IOIPSL stomate output file
2536!!
2537!! DESCRIPTION   : This subroutine initialize the IOIPSL output file stomate_history.nc(default name).
2538!!                 This subroutine was previously named stom_define_history and where located in module intersurf.
2539!! RECENT CHANGE(S): None
2540!!
2541!! \n
2542!_ ================================================================================================================================
2543  SUBROUTINE ioipslctrl_histstom( &
2544       & hist_id_stom, nvm, iim, jjm, dt, &
2545       & hist_dt, hist_hori_id, hist_PFTaxis_id, &
2546       & hist_pool_10axis_id, hist_pool_100axis_id, &
2547       & hist_pool_11axis_id, hist_pool_101axis_id, &
2548       & hist_stomate_phytomer, & !! yidi
2549       & hist_stomate_deepsoil, hist_stomate_snow)
2550    ! deforestation axis added as arguments
2551
2552    !---------------------------------------------------------------------
2553    !- Tell ioipsl which variables are to be written
2554    !- and on which grid they are defined
2555    !---------------------------------------------------------------------
2556    IMPLICIT NONE
2557    !-
2558    !- Input
2559    !-
2560    !- File id
2561    INTEGER(i_std),INTENT(in) :: hist_id_stom
2562    !- number of PFTs
2563    INTEGER(i_std),INTENT(in) :: nvm
2564    !- Domain size
2565    INTEGER(i_std),INTENT(in) :: iim, jjm
2566    !- Time step of STOMATE (seconds)
2567    REAL(r_std),INTENT(in)    :: dt
2568    !- Time step of history file (s)
2569    REAL(r_std),INTENT(in)    :: hist_dt
2570    !- id horizontal grid
2571    INTEGER(i_std),INTENT(in) :: hist_hori_id
2572    !- id of PFT axis
2573    INTEGER(i_std),INTENT(in) :: hist_PFTaxis_id
2574    !- id of Deforestation axis
2575    INTEGER(i_std),INTENT(in) :: hist_pool_10axis_id,hist_pool_100axis_id
2576    INTEGER(i_std),INTENT(in) :: hist_pool_11axis_id,hist_pool_101axis_id
2577    !-  id of permafrost axis
2578    INTEGER(i_std),INTENT(in) :: hist_stomate_deepsoil
2579    INTEGER(i_std),INTENT(in)     :: hist_stomate_snow
2580!! yidi
2581    INTEGER(i_std),INTENT(in)     :: hist_stomate_phytomer !! yidi
2582!! yidi
2583    !- 1 local
2584    !-
2585    !- maximum history level
2586    INTEGER(i_std), PARAMETER  :: max_hist_level = 10
2587    !- output level (between 0 and 10)
2588    !-  ( 0:nothing is written, 10:everything is written)
2589    INTEGER(i_std)             :: hist_level
2590    !- Character strings to define operations for histdef
2591    CHARACTER(LEN=40),DIMENSION(max_hist_level) :: ave, tmax
2592    !- for looping over PFT dimension for permafrost soil variables
2593    INTEGER(i_std)     :: jv, m
2594    CHARACTER(LEN=10)  :: part_str    ! string suffix indicating an index
2595
2596    !---------------------------------------------------------------------
2597    !=====================================================================
2598    !- 1 history level
2599    !=====================================================================
2600    !- 1.1 define history levelx
2601    !=====================================================================
2602    !Config Key   = STOMATE_HISTLEVEL
2603    !Config Desc  = STOMATE history output level (0..10)
2604    !Config If    = OK_STOMATE
2605    !Config Def   = 10
2606    !Config Help  = 0: nothing is written; 10: everything is written
2607    !Config Units = [-]
2608    !-
2609    hist_level = 10
2610    CALL getin_p('STOMATE_HISTLEVEL', hist_level)
2611    !-
2612    IF (printlev >= 2) WRITE(numout,*) 'STOMATE history level: ',hist_level
2613    IF ( (hist_level > max_hist_level).OR.(hist_level < 0) ) THEN
2614       STOP 'This history level is not allowed'
2615    ENDIF
2616    !=====================================================================
2617    !- 1.2 define operations according to output level
2618    !=====================================================================
2619    ave(1:hist_level) =  'ave(scatter(X))'
2620    ave(hist_level+1:max_hist_level) =  'never          '
2621    tmax(1:max_hist_level) =  't_max(scatter(X))'
2622    IF (hist_level<max_hist_level) THEN
2623        tmax(hist_level+1:max_hist_level) =  'never          '
2624    ENDIF
2625    !=====================================================================
2626    !- 2 surface fields (2d)
2627    !- 3 PFT: 3rd dimension
2628    !=====================================================================
2629
2630
2631    ! structural litter above ground
2632    IF (is_omp_root) THEN
2633       CALL histdef (hist_id_stom, &
2634            &               TRIM("LITTER_STR_AB       "), &
2635            &               TRIM("structural litter above ground                    "), &
2636            &               TRIM("gC/m^2/pft          "), iim,jjm, hist_hori_id, &
2637            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
2638       
2639       ! metabolic litter above ground                     
2640       CALL histdef (hist_id_stom, &
2641            &               TRIM("LITTER_MET_AB       "), &
2642            &               TRIM("metabolic litter above ground                     "), &
2643            &               TRIM("gC/m^2/pft          "), iim,jjm, hist_hori_id, &
2644            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
2645       
2646       ! structural litter below ground               
2647       CALL histdef (hist_id_stom, &
2648            &               TRIM("LITTER_STR_BE       "), &
2649            &               TRIM("structural litter below ground                    "), &
2650            &               TRIM("gC/m^2/pft          "), iim,jjm, hist_hori_id, &
2651            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
2652       
2653       ! metabolic litter below ground               
2654       CALL histdef (hist_id_stom, &
2655            &               TRIM("LITTER_MET_BE       "), &
2656            &               TRIM("metabolic litter below ground                     "), &
2657            &               TRIM("gC/m^2/pft          "), iim,jjm, hist_hori_id, &
2658            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
2659       
2660       ! fraction of soil covered by dead leaves           
2661       CALL histdef (hist_id_stom, &
2662            &               TRIM("DEADLEAF_COVER      "), &
2663            &               TRIM("fraction of soil covered by dead leaves           "), &
2664            &               TRIM("-                   "), iim,jjm, hist_hori_id, &
2665            &               1,1,1, -99,32, ave(5), dt, hist_dt)
2666       
2667       ! total soil and litter carbon
2668       CALL histdef (hist_id_stom, &
2669            &               TRIM("TOTAL_SOIL_CARB     "), &
2670            &               TRIM("total soil and litter carbon                      "), &
2671            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
2672            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
2673       
2674       ! active soil carbon in ground                 
2675       CALL histdef (hist_id_stom, &
2676            &               TRIM("CARBON_ACTIVE       "), &
2677            &               TRIM("active soil carbon in ground                      "), &
2678            &               TRIM("gC/m^2/pft          "), iim,jjm, hist_hori_id, &
2679            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
2680       
2681       ! slow soil carbon in ground                   
2682       CALL histdef (hist_id_stom, &
2683            &               TRIM("CARBON_SLOW         "), &
2684            &               TRIM("slow soil carbon in ground                        "), &
2685            &               TRIM("gC/m^2/pft          "), iim,jjm, hist_hori_id, &
2686            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
2687       
2688       ! passive soil carbon in ground               
2689       CALL histdef (hist_id_stom, &
2690            &               TRIM("CARBON_PASSIVE      "), &
2691            &               TRIM("passive soil carbon in ground                     "), &
2692            &               TRIM("gC/m^2/pft          "), iim,jjm, hist_hori_id, &
2693            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
2694     
2695
2696       ! active soil carbon in ground                 
2697       CALL histdef (hist_id_stom, &
2698           &               TRIM("CARBON_ACTIVE_SURF  "), &
2699           &               TRIM("active soil carbon in ground over surface soils"), &
2700           &               TRIM("gC/m^2/pft          "), iim,jjm, hist_hori_id,&
2701           &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
2702
2703      ! slow soil carbon in ground                   
2704      CALL histdef (hist_id_stom, &
2705           &               TRIM("CARBON_SLOW_SURF    "), &
2706           &               TRIM("slow soil carbon in ground over surface soils "), &
2707           &               TRIM("gC/m^2/pft          "), iim,jjm, hist_hori_id, &
2708           &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
2709
2710      ! passive soil carbon in ground               
2711      CALL histdef (hist_id_stom, &
2712           &               TRIM("CARBON_PASSIVE_SURF "), &
2713           &               TRIM("passive soil carbon in ground over surface soils"), &
2714           &               TRIM("gC/m^2/pft          "), iim,jjm, hist_hori_id, &
2715           &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
2716 
2717       ! Long term 2 m temperature                           
2718       CALL histdef (hist_id_stom, &
2719            &               TRIM("T2M_LONGTERM        "), &
2720            &               TRIM("Longterm 2 m temperature                          "), &
2721            &               TRIM("K                   "), iim,jjm, hist_hori_id, &
2722            &               1,1,1, -99,32, ave(9), dt, hist_dt)
2723       
2724       ! Monthly 2 m temperature                           
2725       CALL histdef (hist_id_stom, &
2726            &               TRIM("T2M_MONTH           "), &
2727            &               TRIM("Monthly 2 m temperature                           "), &
2728            &               TRIM("K                   "), iim,jjm, hist_hori_id, &
2729            &               1,1,1, -99,32, ave(1), dt, hist_dt)
2730     
2731       ! "seasonal" 2 m temperature                           
2732       CALL histdef (hist_id_stom, &
2733         &               TRIM("TSEASON             "), &
2734         &               TRIM("Seasonal 2 m temperature                             "), &
2735         &               TRIM("K                   "), iim,jjm, hist_hori_id, &
2736         &               1,1,1, -99,32, ave(10), dt, hist_dt)
2737
2738       ! how many days after onset                           
2739       CALL histdef (hist_id_stom, &
2740         &               TRIM("TMIN_SPRING_TIME    "), &
2741         &               TRIM("how many days after onset                            "), &
2742         &               TRIM("days                "), iim,jjm, hist_hori_id, &
2743         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
2744
2745       !                           
2746       CALL histdef (hist_id_stom, &
2747         &               TRIM("ONSET_DATE          "), &
2748         &               TRIM("onset date                                           "), &
2749         &               TRIM("day                 "), iim,jjm, hist_hori_id, &
2750         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
2751
2752       ! minimum 2 m temperature                           
2753       CALL histdef (hist_id_stom, &
2754         &               TRIM("T2M_MIN_DAILY       "), &
2755         &               TRIM("minimum 2 m temperature                              "), &
2756         &               TRIM("K                   "), iim,jjm, hist_hori_id, &
2757         &               1,1,1, -99,32, ave(10), dt, hist_dt) 
2758       ! Weekly 2 m temperature                           
2759       CALL histdef (hist_id_stom, &
2760            &               TRIM("T2M_WEEK            "), &
2761            &               TRIM("Weekly 2 m temperature                            "), &
2762            &               TRIM("K                   "), iim,jjm, hist_hori_id, &
2763            &               1,1,1, -99,32, ave(1), dt, hist_dt)
2764       
2765       ! heterotr. resp. from ground                 
2766       CALL histdef (hist_id_stom, &
2767            &               TRIM("HET_RESP            "), &
2768            &               TRIM("heterotr. resp. from ground                       "), &
2769            &               TRIM("gC/m^2 tot/pft/day  "), iim,jjm, hist_hori_id, &
2770            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(3), dt, hist_dt)
2771       
2772       ! Fire fraction on ground
2773       CALL histdef (hist_id_stom, &
2774            &               TRIM("FIREFRAC            "), &
2775            &               TRIM("Fire fraction on ground                           "), &
2776            &               TRIM("1/day               "), iim,jjm, hist_hori_id, &
2777            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(1), dt, hist_dt)
2778
2779       ! Fire index on ground                     
2780       CALL histdef (hist_id_stom, &
2781            &               TRIM("FIREINDEX           "), &
2782            &               TRIM("Fire index on ground                              "), &
2783            &               TRIM("-                   "), iim,jjm, hist_hori_id, &
2784            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
2785       
2786       ! Litter humidity                                   
2787       CALL histdef (hist_id_stom, &
2788            &               TRIM("LITTERHUM           "), &
2789            &               TRIM("Litter humidity                                   "), &
2790            &               TRIM("-                   "), iim,jjm, hist_hori_id, &
2791            &               1,1,1, -99,32, ave(5), dt, hist_dt)
2792       
2793       ! CO2 flux                                 
2794       CALL histdef (hist_id_stom, &
2795            &               TRIM("CO2FLUX             "), &
2796            &               TRIM("CO2 flux                                          "), &
2797            &               TRIM("gC/m^2/pft/mth      "), iim,jjm, hist_hori_id, &
2798            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(1), dt, hist_dt)
2799
2800       ! NONBIOFRAC
2801       CALL histdef (hist_id_stom, &
2802            &               TRIM("NONBIOFRAC             "), &
2803            &               TRIM("Total nonbio fraction of the land                 "), &
2804            &               TRIM("      "), iim,jjm, hist_hori_id, &
2805            &               1,1,1, -99,32, ave(1), dt, hist_dt)
2806
2807!!$    CALL histdef(hist_id_stom, &
2808!!$         &               TRIM("CO2FLUX_MONTHLY_SUM "), &
2809!!$         &               TRIM("Monthly CO2 flux Sum                              "), &
2810!!$         &               TRIM("PgC/m^2/mth         "), iim,jjm, hist_hori_id, &
2811!!$         &               1,1,1, -99, 32, 'inst(scatter(X))', dt, hist_dt)
2812
2813       ! Output CO2 flux from fire                         
2814       CALL histdef (hist_id_stom, &
2815            &               TRIM("CO2_FIRE            "), &
2816            &               TRIM("Output Carbon flux from fire including deforestation fire if simulated"), &
2817            &               TRIM("gC/day/m^2/pft      "), iim,jjm, hist_hori_id, &
2818            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(1), dt, hist_dt)
2819       
2820       ! CO2 taken from atmosphere for initiate growth     
2821       CALL histdef (hist_id_stom, &
2822            &               TRIM("CO2_TAKEN           "), &
2823            &               TRIM("CO2 taken from atmosphere for initiate growth     "), &
2824            &               TRIM("gC/day/m^2/pft      "), iim,jjm, hist_hori_id, &
2825            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(1), dt, hist_dt)
2826       ! Carbon flux from fire
2827       CALL histdef (hist_id_stom, &
2828            &               TRIM("CO2_FIRE_NonDef      "), &
2829            &               TRIM("Fire carbon emissions not including deforestation fire"), &
2830            &               TRIM("gC/day/m^2/pft      "), iim,jjm, hist_hori_id, &
2831            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(1), dt, hist_dt)
2832
2833       ! Carbon flux from fire
2834       CALL histdef (hist_id_stom, &
2835            &               TRIM("CO2_FIRE_Def      "), &
2836            &               TRIM("Fire carbon emissions from including deforestation fire"), &
2837            &               TRIM("gC/day/m^2/pft      "), iim,jjm, hist_hori_id, &
2838            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(1), dt, hist_dt)
2839
2840
2841       IF (ok_dgvm) THEN
2842          ! total co2 flux (sum over 13 PFTs). when DGVM is activated, the previous
2843          ! SUM(CO2FLUX*veget_max) is wrong. We should look at this variable.
2844          CALL histdef (hist_id_stom, &
2845               &               TRIM("tCO2FLUX            "), &
2846               &               TRIM("total CO2flux of 13 PFTs (after adjustment)       "), &
2847               &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
2848               &               1,1,1, -99,32, ave(10), dt, hist_dt)
2849         
2850          ! should be the same with tCO2FLUX
2851          CALL histdef (hist_id_stom, &
2852               &               TRIM("tCO2FLUX_OLD        "), &
2853               &               TRIM("total CO2flux of 13 PFTs(multiply by veget_max_old"), &
2854               &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
2855               &               1,1,1, -99,32, ave(10), dt, hist_dt)
2856         
2857          CALL histdef (hist_id_stom, &
2858               &               TRIM("tGPP                 "), &
2859               &               TRIM("total GPP of 13 PFTs (after adjustment)           "), &
2860               &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
2861               &               1,1,1, -99,32, ave(1), dt, hist_dt)
2862       
2863          CALL histdef (hist_id_stom, &
2864               &               TRIM("tRESP_GROWTH         "), &
2865               &               TRIM("total resp growth of 13 PFTs (after adjustment)   "), &
2866               &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
2867               &               1,1,1, -99,32, ave(1), dt, hist_dt)
2868         
2869          CALL histdef (hist_id_stom, &
2870               &               TRIM("tRESP_MAINT          "), &
2871               &               TRIM("total resp maint  of 13 PFTs (after adjustment)   "), &
2872               &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
2873               &               1,1,1, -99,32, ave(1), dt, hist_dt)
2874       
2875          CALL histdef (hist_id_stom, &
2876               &               TRIM("tRESP_HETERO         "), &
2877               &               TRIM("total resp hetero of 13 PFTs (after adjustment)   "), &
2878               &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
2879               &               1,1,1, -99,32, ave(1), dt, hist_dt)
2880       
2881          CALL histdef (hist_id_stom, &
2882               &               TRIM("tCARBON              "), &
2883               &               TRIM("total carbon of 13 PFTs (after adjustment)        "), &
2884               &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
2885               &               1,1,1, -99,32, ave(1), dt, hist_dt)
2886         
2887          CALL histdef (hist_id_stom, &
2888               &               TRIM("tBIOMASS             "), &
2889               &               TRIM("total biomass of 13 PFTs (after adjustment)       "), &
2890               &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
2891               &               1,1,1, -99,32, ave(1), dt, hist_dt)
2892       
2893          CALL histdef (hist_id_stom, &
2894               &               TRIM("tLITTER              "), &
2895               &               TRIM("total litter of 13 PFTs (after adjustment)        "), &
2896               &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
2897               &               1,1,1, -99,32, ave(1), dt, hist_dt)
2898       
2899          CALL histdef (hist_id_stom, &
2900               &               TRIM("tFUEL1HR              "), &
2901               &               TRIM("Fuel 1hr of 13 PFTs (after adjustment)        "), &
2902               &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
2903               &               1,1,1, -99,32, ave(1), dt, hist_dt)
2904       
2905          CALL histdef (hist_id_stom, &
2906               &               TRIM("tFUEL10HR              "), &
2907               &               TRIM("Fuel 10hr of 13 PFTs (after adjustment)        "), &
2908               &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
2909               &               1,1,1, -99,32, ave(1), dt, hist_dt)
2910
2911          CALL histdef (hist_id_stom, &
2912               &               TRIM("tFUEL100HR             "), &
2913               &               TRIM("Fuel 100hr of 13 PFTs (after adjustment)        "), &
2914               &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
2915               &               1,1,1, -99,32, ave(1), dt, hist_dt)
2916       
2917          CALL histdef (hist_id_stom, &
2918               &               TRIM("tFUEL1000HR              "), &
2919               &               TRIM("Fuel 1000hr of 13 PFTs (after adjustment)        "), &
2920               &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
2921               &               1,1,1, -99,32, ave(1), dt, hist_dt)
2922       
2923          CALL histdef (hist_id_stom, &
2924               &               TRIM("tSOILC               "), &
2925               &               TRIM("total soil carbon of 13 PFTs (after adjustment)   "), &
2926               &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
2927               &               1,1,1, -99,32, ave(1), dt, hist_dt)
2928
2929          CALL histdef (hist_id_stom, &
2930               &               TRIM("tDEEPCa               "), &
2931               &               TRIM("Active permafrost soil carbon of 13 PFTs (after adjustment)   "), &
2932               &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
2933               &               1,1,1, -99,32, ave(1), dt, hist_dt)
2934       
2935          CALL histdef (hist_id_stom, &
2936               &               TRIM("tDEEPCs               "), &
2937               &               TRIM("Slow permafrost soil carbon of 13 PFTs (after adjustment)   "), &
2938               &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
2939               &               1,1,1, -99,32, ave(1), dt, hist_dt)
2940
2941          CALL histdef (hist_id_stom, &
2942               &               TRIM("tDEEPCp               "), &
2943               &               TRIM("Passive permafrost soil carbon of 13 PFTs (after adjustment)   "), &
2944               &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
2945               &               1,1,1, -99,32, ave(1), dt, hist_dt)
2946       
2947
2948          CALL histdef (hist_id_stom, &
2949               &               TRIM("tCO2_TAKEN           "), &
2950               &               TRIM("total co2_to_bm 13 PFTs (after adjustment)        "), &
2951               &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
2952               &               1,1,1, -99,32, ave(10), dt, hist_dt)
2953         
2954          CALL histdef (hist_id_stom, &
2955               &               TRIM("tCO2_FIRE            "), &
2956               &               TRIM("total co2_fire 13 PFTs (after adjustment)         "), &
2957               &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
2958               &               1,1,1, -99,32, ave(10), dt, hist_dt)
2959       END IF
2960
2961       ! Leaf Area Index                                   
2962       CALL histdef (hist_id_stom, &
2963            &               TRIM("LAI                 "), &
2964            &               TRIM("Leaf Area Index                                   "), &
2965            &               TRIM("-                   "), iim,jjm, hist_hori_id, &
2966            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(1), dt, hist_dt)
2967       
2968       ! Leaf Area Index CL1                                   
2969       CALL histdef (hist_id_stom, &
2970            &               TRIM("LAI_CL1                 "), &
2971            &               TRIM("Leaf Area Index CL1                                  "), &
2972            &               TRIM("-                   "), iim,jjm, hist_hori_id, &
2973            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(1), dt, hist_dt)
2974       
2975       ! Leaf Area Index CL2                                   
2976       CALL histdef (hist_id_stom, &
2977            &               TRIM("LAI_CL2                 "), &
2978            &               TRIM("Leaf Area Index CL2                                  "), &
2979            &               TRIM("-                   "), iim,jjm, hist_hori_id, &
2980            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(1), dt, hist_dt)
2981       
2982       ! Leaf Area Index CL3                                   
2983       CALL histdef (hist_id_stom, &
2984            &               TRIM("LAI_CL3                 "), &
2985            &               TRIM("Leaf Area Index CL3                                  "), &
2986            &               TRIM("-                   "), iim,jjm, hist_hori_id, &
2987            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(1), dt, hist_dt)
2988       
2989       ! Leaf Area Index CL4                                   
2990       CALL histdef (hist_id_stom, &
2991            &               TRIM("LAI_CL4                 "), &
2992            &               TRIM("Leaf Area Index CL4                                  "), &
2993            &               TRIM("-                   "), iim,jjm, hist_hori_id, &
2994            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(1), dt, hist_dt)
2995       
2996       CALL histdef (hist_id_stom, &
2997            &               TRIM("FPC_MAX             "), &
2998            &               TRIM("foliage projective cover                          "), &
2999            &               TRIM("-                   "), iim,jjm, hist_hori_id, &
3000            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3001       
3002       CALL histdef (hist_id_stom, &
3003            &               TRIM("MAXFPC_LASTYEAR     "), &
3004            &               TRIM("foliage projective cover of last year             "), &
3005            &               TRIM("-                   "), iim,jjm, hist_hori_id, &
3006            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3007       
3008       ! Maximum vegetation fraction (LAI -> infinity)     
3009       CALL histdef (hist_id_stom, &
3010            &               TRIM("VEGET_COV_MAX       "), &
3011            &               TRIM("Maximum vegetation fraction (LAI -> infinity)     "), &
3012            &               TRIM("-                   "), iim,jjm, hist_hori_id, &
3013            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(1), dt, hist_dt)
3014       
3015       ! Net primary productivity                         
3016       CALL histdef (hist_id_stom, &
3017            &               TRIM("NPP                 "), &
3018            &               TRIM("Net primary productivity                          "), &
3019            &               TRIM("gC/day/(m^2 tot)    "), iim,jjm, hist_hori_id, &
3020            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(1), dt, hist_dt)
3021
3022       ! Gross primary productivity                       
3023       CALL histdef (hist_id_stom, &
3024            &               TRIM("GPP                 "), &
3025            &               TRIM("Gross primary productivity                        "), &
3026            &               TRIM("gC/day/m^2          "), iim,jjm, hist_hori_id, &
3027            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(1), dt, hist_dt)
3028
3029       ! Gross primary productivity CL1                       
3030       !CALL histdef (hist_id_stom, &
3031       !     &               TRIM("GPP_CL1                 "), &
3032       !     &               TRIM("Gross primary productivity CL1                       "), &
3033       !     &               TRIM("gC/day/m^2          "), iim,jjm, hist_hori_id, &
3034       !     &               nvm,1,nvm, hist_PFTaxis_id,32, ave(1), dt, hist_dt)
3035
3036       ! Gross primary productivity CL2                       
3037       !CALL histdef (hist_id_stom, &
3038       !     &               TRIM("GPP_CL2                 "), &
3039       !     &               TRIM("Gross primary productivity CL2                       "), &
3040       !     &               TRIM("gC/day/m^2          "), iim,jjm, hist_hori_id, &
3041       !     &               nvm,1,nvm, hist_PFTaxis_id,32, ave(1), dt, hist_dt)
3042
3043       ! Gross primary productivity CL3                       
3044       !CALL histdef (hist_id_stom, &
3045       !     &               TRIM("GPP_CL3                 "), &
3046       !     &               TRIM("Gross primary productivity CL3                       "), &
3047       !     &               TRIM("gC/day/m^2          "), iim,jjm, hist_hori_id, &
3048       !     &               nvm,1,nvm, hist_PFTaxis_id,32, ave(1), dt, hist_dt)
3049
3050       ! Gross primary productivity CL4                       
3051       !CALL histdef (hist_id_stom, &
3052       !     &               TRIM("GPP_CL4                 "), &
3053       !     &               TRIM("Gross primary productivity CL4                       "), &
3054       !     &               TRIM("gC/day/m^2          "), iim,jjm, hist_hori_id, &
3055       !     &               nvm,1,nvm, hist_PFTaxis_id,32, ave(1), dt, hist_dt)
3056
3057       ! Gross primary productivity xc                       
3058       !CALL histdef (hist_id_stom, &
3059       !     &               TRIM("GPP_xc                 "), &
3060       !     &               TRIM("Gross primary productivity_xc                        "), &
3061       !     &               TRIM("gC/day/m^2          "), iim,jjm, hist_hori_id, &
3062       !     &               nvm,1,nvm, hist_PFTaxis_id,32, ave(1), dt, hist_dt)
3063
3064       ! Density of individuals                           
3065       CALL histdef (hist_id_stom, &
3066            &               TRIM("IND                 "), &
3067            &               TRIM("Density of individuals                            "), &
3068            &               TRIM("1/ m^2              "), iim,jjm, hist_hori_id, &
3069            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(3), dt, hist_dt)
3070
3071       ! Adaptation to climate
3072       CALL histdef (hist_id_stom, &
3073            &               TRIM("ADAPTATION          "), &
3074            &               TRIM("Adaptation to climate (DGVM)                      "), &
3075            &               TRIM("-                   "), iim,jjm, hist_hori_id, &
3076            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(3), dt, hist_dt)
3077   
3078       ! Probability from regenerative
3079       CALL histdef (hist_id_stom, &
3080            &               TRIM("REGENERATION        "), &
3081            &               TRIM("Probability from regenerative (DGVM)               "), &
3082            &               TRIM("-                   "), iim,jjm, hist_hori_id, &
3083            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(3), dt, hist_dt)
3084       
3085       ! crown area of individuals (m**2)
3086       CALL histdef (hist_id_stom, &
3087            &               TRIM("CN_IND              "), &
3088            &               TRIM("crown area of individuals                         "), &
3089            &               TRIM("m^2                 "), iim,jjm, hist_hori_id, &
3090            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(3), dt, hist_dt)
3091
3092       ! woodmass of individuals (gC)
3093       CALL histdef (hist_id_stom, &
3094            &               TRIM("WOODMASS_IND        "), &
3095            &               TRIM("Woodmass of individuals                           "), &
3096            &               TRIM("gC/pft              "), iim,jjm, hist_hori_id, &
3097            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(3), dt, hist_dt)
3098
3099       ! total living biomass
3100       CALL histdef (hist_id_stom, &
3101            &               TRIM("TOTAL_M             "), &
3102            &               TRIM("Total living biomass                              "), &
3103            &               TRIM("gC/m^2/pft          "), iim,jjm, hist_hori_id, &
3104            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(4), dt, hist_dt)
3105       
3106       ! Leaf mass                                         
3107       CALL histdef (hist_id_stom, &
3108            &               TRIM("LEAF_M              "), &
3109            &               TRIM("Leaf mass                                         "), &
3110            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
3111            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
3112       
3113       ! Leaf mass                                         
3114       CALL histdef (hist_id_stom, &
3115            &               TRIM("LEAF_BM_CL1              "), &
3116            &               TRIM("Leaf mass cl1                                     "), &
3117            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
3118            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
3119       
3120       ! Leaf mass                                         
3121       CALL histdef (hist_id_stom, &
3122            &               TRIM("LEAF_BM_CL2              "), &
3123            &               TRIM("Leaf mass cl2                                     "), &
3124            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
3125            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
3126       ! Leaf mass                                         
3127       CALL histdef (hist_id_stom, &
3128            &               TRIM("LEAF_BM_CL3              "), &
3129            &               TRIM("Leaf mass cl3                                     "), &
3130            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
3131            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
3132     
3133       ! Leaf mass                                         
3134       CALL histdef (hist_id_stom, &
3135            &               TRIM("LEAF_BM_CL4              "), &
3136            &               TRIM("Leaf mass cl4                                     "), &
3137            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
3138            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
3139     
3140!! yidi     
3141       IF (ok_oilpalm) THEN
3142          ! PHYTOMER AGE PRE
3143          DO jv = 1, nvm
3144             IF (is_oilpalm(jv)) THEN
3145                WRITE(part_str,'(I2)') jv
3146                IF (jv < 10) part_str(1:1) = '0'
3147                CALL histdef (hist_id_stom, &
3148                     & TRIM("PHYTOMER_AGE_PRE_"//part_str(1:LEN_TRIM(part_str))), &
3149                     & TRIM("PHYTOMER_AGE_PRE   "), &
3150                     & TRIM("days   "), iim,jjm, hist_hori_id, &
3151                     & nphs, 1, nphs, hist_stomate_phytomer,32, ave(2),dt,hist_dt)
3152             END IF
3153          END DO
3154          ! PHYTOMER AGE PRIOR
3155          DO jv = 1, nvm
3156             IF (is_oilpalm(jv)) THEN
3157                WRITE(part_str,'(I2)') jv
3158                IF (jv < 10) part_str(1:1) = '0'
3159                CALL histdef (hist_id_stom, &
3160                     & TRIM("PHYTOMER_AGE_PRI_"//part_str(1:LEN_TRIM(part_str))), &
3161                     & TRIM("PHYTOMER_AGE_PRI   "), &
3162                     & TRIM("days   "), iim,jjm, hist_hori_id, &
3163                     & nphs, 1, nphs, hist_stomate_phytomer,32, ave(2),dt,hist_dt)
3164             END IF
3165          END DO
3166          ! EACH FFB mass
3167          DO jv = 1, nvm
3168             IF (is_oilpalm(jv)) THEN
3169                WRITE(part_str,'(I2)') jv
3170                IF (jv < 10) part_str(1:1) = '0'
3171                CALL histdef (hist_id_stom, &
3172                     & TRIM("BM_FFB_"//part_str(1:LEN_TRIM(part_str))), &
3173                     & TRIM("EACH FFB mass   "), &
3174                     & TRIM("gC/m^2   "), iim,jjm, hist_hori_id, &
3175                     & nphs, 1, nphs, hist_stomate_phytomer,32, ave(2),dt,hist_dt)
3176             ENDIF
3177          ENDDO
3178
3179          ! EACH PHY mass
3180          DO jv = 1, nvm
3181             IF (is_oilpalm(jv)) THEN
3182                WRITE(part_str,'(I2)') jv
3183                IF (jv < 10) part_str(1:1) = '0'
3184                CALL histdef (hist_id_stom, &
3185                     & TRIM("BM_PHYTOMER_"//part_str(1:LEN_TRIM(part_str))), &
3186                     & TRIM("EACH PHY mass   "), &
3187                     & TRIM("gC/m^2   "), iim,jjm, hist_hori_id, &
3188                     & nphs, 1, nphs, hist_stomate_phytomer,32, ave(2),dt,hist_dt)
3189             ENDIF
3190          ENDDO
3191
3192          ! EACH alloc FFB mass
3193          DO jv = 1, nvm
3194             IF (is_oilpalm(jv)) THEN
3195                WRITE(part_str,'(I2)') jv
3196                IF (jv < 10) part_str(1:1) = '0'
3197                CALL histdef (hist_id_stom, &
3198                     & TRIM("BM_ALLOC_FFB_"//part_str(1:LEN_TRIM(part_str))), &
3199                     & TRIM("EACH ALLOC FFB mass   "), &
3200                     & TRIM("gC/m^2   "), iim,jjm, hist_hori_id, &
3201                     & nphs, 1, nphs, hist_stomate_phytomer,32, ave(2),dt,hist_dt)
3202             ENDIF
3203          ENDDO
3204
3205          ! EACH alloc PHY mass
3206          DO jv = 1, nvm
3207             IF (is_oilpalm(jv)) THEN
3208                WRITE(part_str,'(I2)') jv
3209                IF (jv < 10) part_str(1:1) = '0'
3210                CALL histdef (hist_id_stom, &
3211                     & TRIM("BM_ALLOC_PHY_"//part_str(1:LEN_TRIM(part_str))), &
3212                     & TRIM("EACH ALLOC PHY mass   "), &
3213                     & TRIM("gC/m^2   "), iim,jjm, hist_hori_id, &
3214                     & nphs, 1, nphs, hist_stomate_phytomer,32, ave(2),dt,hist_dt)
3215             ENDIF
3216          ENDDO
3217
3218       ENDIF
3219
3220       ! sum op PHY mass                             
3221       CALL histdef (hist_id_stom, &
3222            &               TRIM("PHYBM            "), &
3223            &               TRIM("SUM PHY mass                          "), &
3224            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
3225            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
3226
3227       ! sum op FFB mass                             
3228       CALL histdef (hist_id_stom, &
3229            &               TRIM("FFBBM            "), &
3230            &               TRIM("SUM FFB mass                          "), &
3231            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
3232            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
3233
3234       ! sum op FFBharvest mass                             
3235       CALL histdef (hist_id_stom, &
3236            &               TRIM("FFBHARVEST            "), &
3237            &               TRIM("FFBHARVEST mass                          "), &
3238            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
3239            &               1,1,1, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
3240
3241       ! sum op PHYturn mass                             
3242       CALL histdef (hist_id_stom, &
3243            &               TRIM("PHYTURN            "), &
3244            &               TRIM("PHYturn mass total                         "), &
3245            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
3246            &               1,1,1, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
3247
3248       !  op FFB mass of AGE1                           
3249!       CALL histdef (hist_id_stom, &
3250!            &               TRIM("BM_FFB_AGE1            "), &
3251!            &               TRIM("The FFB mass of age1                         "), &
3252!            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
3253!            &               nphs,1,nphs, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
3254!
3255!       ! op phytomer mass of AGE1                           
3256!       CALL histdef (hist_id_stom, &
3257!            &               TRIM("BM_PHYTOMER_AGE1            "), &
3258!            &               TRIM("The PHYTOMER mass of age1                         "), &
3259!            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
3260!            &               nphs,1,nphs, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
3261!
3262       ! op phytomer mass of AGE2                           
3263      ! CALL histdef (hist_id_stom, &
3264      !      &               TRIM("BM_PHYTOMER_AGE2            "), &
3265      !      &               TRIM("The PHYTOMER mass of age2                         "), &
3266!            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
3267!            &               nphs,1,nphs, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
3268!
3269!       ! op phytomer mass of AGE3                           
3270!       CALL histdef (hist_id_stom, &
3271!            &               TRIM("BM_PHYTOMER_AGE3            "), &
3272!            &               TRIM("The PHYTOMER mass of age3                         "), &
3273!            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
3274!            &               nphs,1,nphs, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
3275!
3276!       ! op phytomer mass of AGE4                           
3277!       CALL histdef (hist_id_stom, &
3278!            &               TRIM("BM_PHYTOMER_AGE4            "), &
3279!            &               TRIM("The PHYTOMER mass of age4                         "), &
3280!            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
3281!            &               nphs,1,nphs, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
3282!
3283!       ! op phytomer mass of AGE5                           
3284!       CALL histdef (hist_id_stom, &
3285!            &               TRIM("BM_PHYTOMER_AGE5            "), &
3286!            &               TRIM("The PHYTOMER mass of age5                         "), &
3287!            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
3288!            &               nphs,1,nphs, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
3289!
3290!       ! op phytomer mass of AGE6                           
3291!       CALL histdef (hist_id_stom, &
3292!            &               TRIM("BM_PHYTOMER_AGE6            "), &
3293!            &               TRIM("The PHYTOMER mass of age6                         "), &
3294!            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
3295!            &               nphs,1,nphs, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
3296!
3297!! yidi
3298
3299       ! Sap mass above ground                             
3300       CALL histdef (hist_id_stom, &
3301            &               TRIM("SAP_M_AB            "), &
3302            &               TRIM("Sap mass above ground                             "), &
3303            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
3304            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
3305
3306       ! Sap mass below ground                             
3307       CALL histdef (hist_id_stom, &
3308            &               TRIM("SAP_M_BE            "), &
3309            &               TRIM("Sap mass below ground                             "), &
3310            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
3311            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
3312       
3313       ! Heartwood mass above ground                       
3314       CALL histdef (hist_id_stom, &
3315            &               TRIM("HEART_M_AB          "), &
3316            &               TRIM("Heartwood mass above ground                       "), &
3317            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
3318            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
3319
3320       ! Heartwood mass below ground                       
3321       CALL histdef (hist_id_stom, &
3322            &               TRIM("HEART_M_BE          "), &
3323            &               TRIM("Heartwood mass below ground                       "), &
3324            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
3325            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
3326
3327       ! Root mass                                         
3328       CALL histdef (hist_id_stom, &
3329            &               TRIM("ROOT_M              "), &
3330            &               TRIM("Root mass                                         "), &
3331            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
3332            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
3333       
3334       ! Fruit mass                                       
3335       CALL histdef (hist_id_stom, &
3336            &               TRIM("FRUIT_M             "), &
3337            &               TRIM("Fruit mass                                        "), &
3338            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
3339            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
3340!!!!! crops
3341
3342        ! Fruit mass -- here we assign the fruit mass to cropyield                                       
3343       CALL histdef (hist_id_stom, &
3344            &               TRIM("CROPYIELD             "), &
3345            &               TRIM("crop yield                                        "), &
3346            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
3347            &               nvm,1,nvm, hist_PFTaxis_id,32, tmax(1), dt, hist_dt)
3348
3349
3350       CALL histdef (hist_id_stom, &
3351            &               TRIM("BIOMYIELD             "), &
3352            &               TRIM("total biomass yield                                        "), &
3353            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
3354            &               nvm,1,nvm, hist_PFTaxis_id,32, tmax(1), dt, hist_dt)
3355
3356
3357       CALL histdef (hist_id_stom, &
3358            &               TRIM("CROP_EXPORT           "), &
3359            &               TRIM("c export from cropland (harvest + straws)                  "), &
3360            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
3361            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(3), dt, hist_dt)
3362
3363       ! SLA of crop PFTs
3364       CALL histdef (hist_id_stom, &
3365            &               TRIM("SLA_CROP            "), &
3366            &               TRIM("specific leaf area of crop PFTs"), &
3367            &               TRIM("-                   "), iim,jjm, hist_hori_id, &
3368            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(3), dt, hist_dt)
3369
3370       CALL histdef(hist_id_stom, 'N_add', 'Nitrogen Fertilizer', 'kgN/ha', &
3371            & iim,jjm, hist_hori_id, nvm,1,nvm, hist_PFTaxis_id, 32, 'once(scatter(X))', dt, hist_dt)
3372        !!!! this could be overlapping with PLNTDT
3373       CALL histdef(hist_id_stom, 'PlantDate', 'Planting Date of the crop', 'DOY', &
3374            & iim,jjm, hist_hori_id, nvm,1,nvm, hist_PFTaxis_id, 32, 'once(scatter(X))', dt, hist_dt)
3375
3376
3377       !STICS variables, xuhui
3378        ! UDEVAIR
3379        CALL histdef (hist_id_stom, &
3380             &               TRIM("UDEVCULT           "), &
3381             &               TRIM("UDEV USING CROP TEMPERATURE                       "), &
3382             &               TRIM("-                   "), iim,jjm, hist_hori_id, &
3383             &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
3384        ! UDEVCULT
3385        CALL histdef (hist_id_stom, &
3386             &               TRIM("UDEVAIR            "), &
3387             &               TRIM("UDEV USING AIR TEMPERATURE                        "), &
3388             &               TRIM("-                   "), iim,jjm, hist_hori_id, &
3389             &               nvm,1,nvm, hist_PFTaxis_id,32, ave(1), dt, hist_dt)
3390   
3391        ! TCULT
3392        CALL histdef (hist_id_stom, &
3393             &               TRIM("TCULT            "), &
3394             &               TRIM("CROP TEMPERATURE                        "), &
3395             &               TRIM("degree celsius                   "), iim,jjm, hist_hori_id, &
3396             &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
3397        ! SHUMREL
3398        CALL histdef (hist_id_stom, &
3399             &               TRIM("SHUMREL           "), &
3400             &               TRIM("RELATIVE SOIL MOISURE TO HOLDING CAPACITY AT SOWING DEPTH "), &
3401             &               TRIM("-                   "), iim,jjm, hist_hori_id, &
3402             &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
3403        ! TURFAC
3404        CALL histdef (hist_id_stom, &
3405             &               TRIM("TURFAC            "), &
3406             &               TRIM("WATER STRESS FOR LEAF GROWTH                        "), &
3407             &               TRIM("-                   "), iim,jjm, hist_hori_id, &
3408             &               nvm,1,nvm, hist_PFTaxis_id,32, ave(1), dt, hist_dt)
3409        ! TURSLA
3410        CALL histdef (hist_id_stom, &
3411             &               TRIM("TURSLA            "), &
3412             &               TRIM("STRESS FOR SPECIFIC LEAF AREA                       "), &
3413             &               TRIM("-                   "), iim,jjm, hist_hori_id, &
3414             &               nvm,1,nvm, hist_PFTaxis_id,32, ave(1), dt, hist_dt)
3415        ! DLTLAI
3416        CALL histdef (hist_id_stom, &
3417             &               TRIM("DLTLAI            "), &
3418             &               TRIM("LAI CHANGE ESTIMATED BY CROP MODULE                 "), &
3419             &               TRIM("-                   "), iim,jjm, hist_hori_id, &
3420             &               nvm,1,nvm, hist_PFTaxis_id,32, ave(1), dt, hist_dt)
3421
3422        ! DLTLAISEN
3423        CALL histdef (hist_id_stom, &
3424             &               TRIM("DLTLAISEN         "), &
3425             &               TRIM("LAI SENECENSE ESTIMATED BY CROP MODULE              "), &
3426             &               TRIM("-                   "), iim,jjm, hist_hori_id, &
3427             &               nvm,1,nvm, hist_PFTaxis_id,32, ave(1), dt, hist_dt)
3428        ! IRCARB
3429        CALL histdef (hist_id_stom, &
3430             &               TRIM("IRCARB            "), &
3431             &               TRIM("PARTITIONING OF GRAIN BIOMASS                       "), &
3432             &               TRIM("-                   "), iim,jjm, hist_hori_id, &
3433             &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
3434
3435        ! SWFAC
3436        CALL histdef (hist_id_stom, &
3437             &               TRIM("SWFAC            "), &
3438             &               TRIM("WATER STRESS FOR RUE                        "), &
3439             &               TRIM("-                   "), iim,jjm, hist_hori_id, &
3440             &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
3441        ! SENFAC
3442        CALL histdef (hist_id_stom, &
3443             &               TRIM("SENFAC            "), &
3444             &               TRIM("WATER STRESS FOR LEAF SENESCENCE                        "), &
3445             &               TRIM("-                   "), iim,jjm, hist_hori_id, &
3446             &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
3447        ! REPRAC
3448        CALL histdef (hist_id_stom, &
3449             &               TRIM("REPRAC            "), &
3450             &               TRIM("ratio of root to total living biomass                   "), &
3451             &               TRIM("-                   "), iim,jjm, hist_hori_id, &
3452             &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
3453        ! NLEV
3454        CALL histdef (hist_id_stom, &
3455             &               TRIM("NLEV            "), &
3456             &               TRIM("DATE FOR LEAF EMERGE                        "), &
3457             &               TRIM("JULIE DAY                   "), iim,jjm, hist_hori_id, &
3458             &               nvm,1,nvm, hist_PFTaxis_id,32, tmax(3), dt, hist_dt)
3459   
3460        ! NFLO
3461        CALL histdef (hist_id_stom, &
3462             &               TRIM("NFLO            "), &
3463             &               TRIM("DATE FOR CROP FLOWERING                        "), &
3464             &               TRIM("JULIE DAY                   "), iim,jjm, hist_hori_id, &
3465             &               nvm,1,nvm, hist_PFTaxis_id,32, tmax(1), dt, hist_dt)
3466        ! NDRP
3467        CALL histdef (hist_id_stom, &
3468             &               TRIM("NDRP            "), &
3469             &               TRIM("DATE FOR GRAIN FILLING                        "), &
3470             &               TRIM("JULIE DAY                   "), iim,jjm, hist_hori_id, &
3471             &               nvm,1,nvm, hist_PFTaxis_id,32, tmax(1), dt, hist_dt)
3472        ! NREC
3473        CALL histdef (hist_id_stom, &
3474             &               TRIM("NREC            "), &
3475             &               TRIM("DATE FOR HARVEST                        "), &
3476             &               TRIM("JULIE DAY                   "), iim,jjm, hist_hori_id, &
3477             &               nvm,1,nvm, hist_PFTaxis_id,32, tmax(1), dt, hist_dt)
3478        ! NMAT
3479        CALL histdef (hist_id_stom, &
3480             &               TRIM("NMAT            "), & 
3481             &               TRIM("DATE FOR PHYSIOLOGICAL MATURE                        "), &
3482             &               TRIM("JULIE DAY                   "), iim,jjm, hist_hori_id, &
3483             &               nvm,1,nvm, hist_PFTaxis_id,32, tmax(3), dt, hist_dt)
3484
3485
3486!        ! N_ADD
3487!        CALL histdef (hist_id_stom, &
3488!             &               TRIM("N_ADD            "), &
3489!             &               TRIM("AVERAGE N FERTILIZATION AMOUNT                        "), &
3490!             &               TRIM("KG N HA-1                   "), iim,jjm, hist_hori_id, &
3491!             &               nvm,1,nvm, hist_PFTaxis_id,32, tmax(1), dt, hist_dt)
3492
3493
3494       ! N_LIMFERT
3495        CALL histdef (hist_id_stom, &
3496             &               TRIM("N_LIMFERT            "), & 
3497             &               TRIM("THE EFFECTIVE OF N FERTILIZATION ON PHOTOSYNTHESE                      "), &
3498             &               TRIM("UNITLESS                   "), iim,jjm, hist_hori_id, &
3499             &               nvm,1,nvm, hist_PFTaxis_id,32, tmax(1), dt, hist_dt)
3500       ! PLNTDT
3501        CALL histdef (hist_id_stom, &
3502             &               TRIM("PLNTDT            "), & 
3503             &               TRIM("DATE FOR PLANTING                        "), &
3504             &               TRIM("JULIE DAY                   "), iim,jjm, hist_hori_id, &
3505             &               nvm,1,nvm, hist_PFTaxis_id,32, tmax(3), dt, hist_dt)
3506
3507
3508
3509!!!!! end crops, xuhui
3510       
3511       ! Carbohydrate reserve mass                         
3512       CALL histdef (hist_id_stom, &
3513            &               TRIM("RESERVE_M           "), &
3514            &               TRIM("Carbohydrate reserve mass                         "), &
3515            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
3516            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
3517       
3518       ! total turnover rate
3519       CALL histdef (hist_id_stom, &
3520            &               TRIM("TOTAL_TURN          "), &
3521            &               TRIM("total turnover rate                               "), &
3522            &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
3523            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(4), dt, hist_dt)
3524
3525       ! Leaf turnover                                     
3526       CALL histdef (hist_id_stom, &
3527            &               TRIM("LEAF_TURN           "), &
3528            &               TRIM("Leaf turnover                                     "), &
3529            &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
3530            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(4), dt, hist_dt)
3531
3532       ! Sap turnover above                               
3533       CALL histdef (hist_id_stom, &
3534            &               TRIM("SAP_AB_TURN         "), &
3535            &               TRIM("Sap turnover above                                "), &
3536            &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
3537            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(4), dt, hist_dt)
3538
3539       ! Root turnover                                     
3540       CALL histdef (hist_id_stom, &
3541            &               TRIM("ROOT_TURN           "), &
3542            &               TRIM("Root turnover                                     "), &
3543            &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
3544            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(4), dt, hist_dt)
3545
3546       ! Fruit turnover                                   
3547       CALL histdef (hist_id_stom, &
3548            &               TRIM("FRUIT_TURN          "), &
3549            &               TRIM("Fruit turnover                                    "), &
3550            &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
3551            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(4), dt, hist_dt)
3552
3553       ! total conversion of biomass to litter
3554       CALL histdef (hist_id_stom, &
3555            &               TRIM("TOTAL_BM_LITTER     "), &
3556            &               TRIM("total conversion of biomass to litter             "), &
3557            &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
3558            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(4), dt, hist_dt)
3559
3560       ! Leaf death                                       
3561       CALL histdef (hist_id_stom, &
3562            &               TRIM("LEAF_BM_LITTER      "), &
3563            &               TRIM("Leaf death                                        "), &
3564            &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
3565            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(4), dt, hist_dt)
3566       
3567       ! Sap death above ground                           
3568       CALL histdef (hist_id_stom, &
3569            &               TRIM("SAP_AB_BM_LITTER    "), &
3570            &               TRIM("Sap death above ground                            "), &
3571            &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
3572            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(4), dt, hist_dt)
3573
3574       ! Sap death below ground                           
3575       CALL histdef (hist_id_stom, &
3576            &               TRIM("SAP_BE_BM_LITTER    "), &
3577            &               TRIM("Sap death below ground                            "), &
3578            &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
3579            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(4), dt, hist_dt)
3580
3581       ! Heartwood death above ground                     
3582       CALL histdef (hist_id_stom, &
3583            &               TRIM("HEART_AB_BM_LITTER  "), &
3584            &               TRIM("Heartwood death above ground                      "), &
3585            &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
3586            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(4), dt, hist_dt)
3587
3588       ! Heartwood death below ground                     
3589       CALL histdef (hist_id_stom, &
3590            &               TRIM("HEART_BE_BM_LITTER  "), &
3591            &               TRIM("Heartwood death below ground                      "), &
3592            &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
3593            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(4), dt, hist_dt)
3594
3595       ! Root death                                       
3596       CALL histdef (hist_id_stom, &
3597            &               TRIM("ROOT_BM_LITTER      "), &
3598            &               TRIM("Root death                                        "), &
3599            &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
3600            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(4), dt, hist_dt)
3601       
3602       ! Fruit death                                       
3603       CALL histdef (hist_id_stom, &
3604            &               TRIM("FRUIT_BM_LITTER     "), &
3605            &               TRIM("Fruit death                                       "), &
3606            &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
3607            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(4), dt, hist_dt)
3608
3609       ! Carbohydrate reserve death                       
3610       CALL histdef (hist_id_stom, &
3611            &               TRIM("RESERVE_BM_LITTER   "), &
3612            &               TRIM("Carbohydrate reserve death                        "), &
3613            &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
3614            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(4), dt, hist_dt)
3615
3616       ! Maintenance respiration                           
3617       CALL histdef (hist_id_stom, &
3618            &               TRIM("MAINT_RESP          "), &
3619            &               TRIM("Maintenance respiration                           "), &
3620            &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
3621            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
3622
3623       ! Growth respiration                               
3624       CALL histdef (hist_id_stom, &
3625            &               TRIM("GROWTH_RESP         "), &
3626            &               TRIM("Growth respiration                                "), &
3627            &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
3628            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
3629       
3630       ! age                                               
3631       CALL histdef (hist_id_stom, &
3632            &               TRIM("AGE                 "), &
3633            &               TRIM("age                                               "), &
3634            &               TRIM("years               "), iim,jjm, hist_hori_id, &
3635            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(7), dt, hist_dt)
3636       
3637       ! height                                           
3638       CALL histdef (hist_id_stom, &
3639            &               TRIM("HEIGHT              "), &
3640            &               TRIM("height                                            "), &
3641            &               TRIM("m                   "), iim,jjm, hist_hori_id, &
3642            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(7), dt, hist_dt)
3643
3644       ! weekly moisture stress                           
3645       CALL histdef (hist_id_stom, &
3646            &               TRIM("MOISTRESS           "), &
3647            &               TRIM("weekly moisture stress                            "), &
3648            &               TRIM("-                   "), iim,jjm, hist_hori_id, &
3649            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(3), dt, hist_dt)
3650
3651       ! Maximum rate of carboxylation                     
3652       CALL histdef (hist_id_stom, &
3653            &               TRIM("VCMAX               "), &
3654            &               TRIM("Maximum rate of carboxylation                     "), &
3655            &               TRIM("-                   "), iim,jjm, hist_hori_id, &
3656            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(6), dt, hist_dt)
3657
3658       
3659       ! VCMAX_CL1
3660       CALL histdef (hist_id_stom, &
3661            &               TRIM("VCMAX_CL1           "), &
3662            &               TRIM("Maximum rate of carboxylation of CL1              "), &
3663            &               TRIM("-                   "), iim,jjm, hist_hori_id, &
3664            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(6), dt, hist_dt)
3665
3666       
3667       ! VCMAX_CL2
3668       CALL histdef (hist_id_stom, &
3669            &               TRIM("VCMAX_CL2           "), &
3670            &               TRIM("Maximum rate of carboxylation of CL2              "), &
3671            &               TRIM("-                   "), iim,jjm, hist_hori_id, &
3672            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(6), dt, hist_dt)
3673
3674       
3675       ! VCMAX_CL3
3676       CALL histdef (hist_id_stom, &
3677            &               TRIM("VCMAX_CL3           "), &
3678            &               TRIM("Maximum rate of carboxylation of CL3              "), &
3679            &               TRIM("-                   "), iim,jjm, hist_hori_id, &
3680            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(6), dt, hist_dt)
3681       
3682       ! VCMAX_CL4
3683       CALL histdef (hist_id_stom, &
3684            &               TRIM("VCMAX_CL4           "), &
3685            &               TRIM("Maximum rate of carboxylation of CL4              "), &
3686            &               TRIM("-                   "), iim,jjm, hist_hori_id, &
3687            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(6), dt, hist_dt)
3688
3689       ! leaf age                                         
3690       CALL histdef (hist_id_stom, &
3691            &               TRIM("LEAF_AGE            "), &
3692            &               TRIM("leaf age                                          "), &
3693            &               TRIM("days                "), iim,jjm, hist_hori_id, &
3694            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(6), dt, hist_dt)
3695       
3696       ! leaf age CL1
3697       CALL histdef (hist_id_stom, &
3698            &               TRIM("LEAF_AGE_CL1            "), &
3699            &               TRIM("leaf age cl1                                      "), &
3700            &               TRIM("days                "), iim,jjm, hist_hori_id, &
3701            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(6), dt, hist_dt)
3702       
3703       ! leaf age CL2
3704       CALL histdef (hist_id_stom, &
3705            &               TRIM("LEAF_AGE_CL2            "), &
3706            &               TRIM("leaf age cl2                                      "), &
3707            &               TRIM("days                "), iim,jjm, hist_hori_id, &
3708            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(6), dt, hist_dt)
3709       
3710       ! leaf age CL3
3711       CALL histdef (hist_id_stom, &
3712            &               TRIM("LEAF_AGE_CL3            "), &
3713            &               TRIM("leaf age cl3                                      "), &
3714            &               TRIM("days                "), iim,jjm, hist_hori_id, &
3715            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(6), dt, hist_dt)
3716       
3717
3718       ! leaf age CL4
3719       CALL histdef (hist_id_stom, &
3720            &               TRIM("LEAF_AGE_CL4            "), &
3721            &               TRIM("leaf age cl4                                      "), &
3722            &               TRIM("days                "), iim,jjm, hist_hori_id, &
3723            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(6), dt, hist_dt)
3724       
3725       ! Fraction of trees that dies (gap)                 
3726       ! Fraction of trees that dies (gap)                 
3727       CALL histdef (hist_id_stom, &
3728            &               TRIM("MORTALITY           "), &
3729            &               TRIM("Fraction of trees that dies (gap)                 "), &
3730            &               TRIM("1/day               "), iim,jjm, hist_hori_id, &
3731            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(6), dt, hist_dt)
3732
3733       ! Fraction of plants killed by fire                 
3734       CALL histdef (hist_id_stom, &
3735            &               TRIM("FIREDEATH           "), &
3736            &               TRIM("Fraction of plants killed by fire                 "), &
3737            &               TRIM("1/day               "), iim,jjm, hist_hori_id, &
3738            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(6), dt, hist_dt)
3739
3740       ! Density of newly established saplings             
3741       CALL histdef (hist_id_stom, &
3742            &               TRIM("IND_ESTAB           "), &
3743            &               TRIM("Density of newly established saplings             "), &
3744            &               TRIM("1/day               "), iim,jjm, hist_hori_id, &
3745            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3746
3747       ! Establish tree
3748       CALL histdef (hist_id_stom, &
3749            &               TRIM("ESTABTREE           "), &
3750            &               TRIM("Rate of tree establishement                       "), &
3751            &               TRIM("1/day               "), iim,jjm, hist_hori_id, &
3752            &               1,1,1, -99,32, ave(10), dt, hist_dt)
3753
3754       ! Establish grass
3755       CALL histdef (hist_id_stom, &
3756            &               TRIM("ESTABGRASS          "), &
3757            &               TRIM("Rate of grass establishement                      "), &
3758            &               TRIM("1/day               "), iim,jjm, hist_hori_id, &
3759            &               1,1,1, -99,32, ave(6), dt, hist_dt)
3760
3761       ! Fraction of plants that dies (light competition) 
3762       CALL histdef (hist_id_stom, &
3763            &               TRIM("LIGHT_DEATH         "), &
3764            &               TRIM("Fraction of plants that dies (light competition)  "), &
3765            &               TRIM("1/day               "), iim,jjm, hist_hori_id, &
3766            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(6), dt, hist_dt)
3767
3768       ! biomass allocated to leaves                       
3769       CALL histdef (hist_id_stom, &
3770            &               TRIM("BM_ALLOC_LEAF       "), &
3771            &               TRIM("biomass allocated to leaves                       "), &
3772            &               TRIM("gC/m**2/pft/dt      "), iim,jjm, hist_hori_id, &
3773            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
3774
3775       ! biomass allocated to sapwood above ground         
3776       CALL histdef (hist_id_stom, &
3777            &               TRIM("BM_ALLOC_SAP_AB     "), &
3778            &               TRIM("biomass allocated to sapwood above ground         "), &
3779            &               TRIM("gC/m**2/pft/dt      "), iim,jjm, hist_hori_id, &
3780            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
3781
3782       ! biomass allocated to sapwood below ground         
3783       CALL histdef (hist_id_stom, &
3784            &               TRIM("BM_ALLOC_SAP_BE     "), &
3785            &               TRIM("biomass allocated to sapwood below ground         "), &
3786            &               TRIM("gC/m**2/pft/dt      "), iim,jjm, hist_hori_id, &
3787            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
3788
3789       ! biomass allocated to roots                       
3790       CALL histdef (hist_id_stom, &
3791            &               TRIM("BM_ALLOC_ROOT       "), &
3792            &               TRIM("biomass allocated to roots                        "), &
3793            &               TRIM("gC/m**2/pft/dt          "), iim,jjm, hist_hori_id, &
3794            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
3795
3796       ! biomass allocated to fruits                       
3797       CALL histdef (hist_id_stom, &
3798            &               TRIM("BM_ALLOC_FRUIT      "), &
3799            &               TRIM("biomass allocated to fruits                       "), &
3800            &               TRIM("gC/m**2/pft/dt          "), iim,jjm, hist_hori_id, &
3801            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
3802
3803       ! biomass allocated to carbohydrate reserve         
3804       CALL histdef (hist_id_stom, &
3805            &               TRIM("BM_ALLOC_RES        "), &
3806            &               TRIM("biomass allocated to carbohydrate reserve         "), &
3807            &               TRIM("gC/m**2/pft/dt          "), iim,jjm, hist_hori_id, &
3808            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
3809
3810       ! time constant of herbivore activity               
3811       CALL histdef (hist_id_stom, &
3812            &               TRIM("HERBIVORES          "), &
3813            &               TRIM("time constant of herbivore activity               "), &
3814            &               TRIM("days                "), iim,jjm, hist_hori_id, &
3815            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
3816
3817       CALL histdef (hist_id_stom, &
3818         &               TRIM("SENESCENCE          "), &
3819         &               TRIM("Signal to senescence                                 "), &
3820         &               TRIM("-                   "), iim,jjm, hist_hori_id, &
3821         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3822
3823       ! turnover time for grass leaves                   
3824       CALL histdef (hist_id_stom, &
3825            &               TRIM("TURNOVER_TIME       "), &
3826            &               TRIM("turnover time for grass leaves                    "), &
3827            &               TRIM("days                "), iim,jjm, hist_hori_id, &
3828            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
3829       
3830       ! 10 year wood product pool                         
3831       CALL histdef (hist_id_stom, &
3832            &               TRIM("PROD10_LCC          "), &
3833            &               TRIM("10 year wood product pool                         "), &
3834            &               TRIM("gC/m**2             "), iim,jjm, hist_hori_id, &
3835            &               11,1,11, hist_pool_11axis_id,32, ave(5), dt, hist_dt)
3836       
3837       ! 10 year wood product pool                         
3838       CALL histdef (hist_id_stom, &
3839            &               TRIM("PROD10_HAR          "), &
3840            &               TRIM("10 year wood product pool                         "), &
3841            &               TRIM("gC/m**2             "), iim,jjm, hist_hori_id, &
3842            &               11,1,11, hist_pool_11axis_id,32, ave(5), dt, hist_dt)
3843       
3844       ! annual flux for each 10 year wood product pool   
3845       CALL histdef (hist_id_stom, &
3846            &               TRIM("FLUX10_LCC          "), &
3847            &               TRIM("annual flux for each 10 year wood product pool    "), &
3848            &               TRIM("gC/m**2/yr          "), iim,jjm, hist_hori_id, &
3849            &               10,1,10, hist_pool_10axis_id,32, ave(5), dt, hist_dt)
3850       ! annual flux for each 10 year wood product pool   
3851       CALL histdef (hist_id_stom, &
3852            &               TRIM("FLUX10_HAR          "), &
3853            &               TRIM("annual flux for each 10 year wood product pool    "), &
3854            &               TRIM("gC/m**2/yr          "), iim,jjm, hist_hori_id, &
3855            &               10,1,10, hist_pool_10axis_id,32, ave(5), dt, hist_dt)
3856       
3857       ! 100 year wood product pool                       
3858       CALL histdef (hist_id_stom, &
3859            &               TRIM("PROD100_LCC         "), &
3860            &               TRIM("100 year wood product pool                        "), &
3861            &               TRIM("gC/m**2             "), iim,jjm, hist_hori_id, &
3862            &               101,1,101, hist_pool_101axis_id,32, ave(5), dt, hist_dt)
3863
3864       ! 100 year wood product pool                       
3865       CALL histdef (hist_id_stom, &
3866            &               TRIM("PROD100_HAR         "), &
3867            &               TRIM("100 year wood product pool                        "), &
3868            &               TRIM("gC/m**2             "), iim,jjm, hist_hori_id, &
3869            &               101,1,101, hist_pool_101axis_id,32, ave(5), dt, hist_dt)
3870
3871       ! annual flux for each 100 year wood product pool   
3872       CALL histdef (hist_id_stom, &
3873            &               TRIM("FLUX100_LCC         "), &
3874            &               TRIM("annual flux for each 100 year wood product pool   "), &
3875            &               TRIM("gC/m**2/yr          "), iim,jjm, hist_hori_id, &
3876            &               100,1,100, hist_pool_100axis_id,32, ave(5), dt, hist_dt)
3877
3878       ! annual flux for each 100 year wood product pool   
3879       CALL histdef (hist_id_stom, &
3880            &               TRIM("FLUX100_HAR         "), &
3881            &               TRIM("annual flux for each 100 year wood product pool   "), &
3882            &               TRIM("gC/m**2/yr          "), iim,jjm, hist_hori_id, &
3883            &               100,1,100, hist_pool_100axis_id,32, ave(5), dt, hist_dt)
3884
3885       ! annual release right after deforestation         
3886       CALL histdef (hist_id_stom, &
3887            &               TRIM("CONVFLUX_LCC        "), &
3888            &               TRIM("annual release right after deforestation          "), &
3889            &               TRIM("gC/m**2/day          "), iim,jjm, hist_hori_id, &
3890            &               1,1,1, -99,32, ave(5), dt, hist_dt)
3891
3892       ! annual release right after deforestation         
3893       CALL histdef (hist_id_stom, &
3894            &               TRIM("CONVFLUX_HAR        "), &
3895            &               TRIM("annual release right after deforestation          "), &
3896            &               TRIM("gC/m**2/day          "), iim,jjm, hist_hori_id, &
3897            &               1,1,1, -99,32, ave(5), dt, hist_dt)
3898       ! annual release from all 10 year wood product pools
3899       CALL histdef (hist_id_stom, &
3900            &               TRIM("CFLUX_PROD10_LCC    "), &
3901            &               TRIM("annual release from all 10 year wood product pools"), &
3902            &               TRIM("gC/m**2/day          "), iim,jjm, hist_hori_id, &
3903            &               1,1,1, -99,32, ave(5), dt, hist_dt)
3904
3905       ! annual release from all 10 year wood product pools
3906       CALL histdef (hist_id_stom, &
3907            &               TRIM("CFLUX_PROD10_HAR    "), &
3908            &               TRIM("annual release from all 10 year wood product pools"), &
3909            &               TRIM("gC/m**2/day          "), iim,jjm, hist_hori_id, &
3910            &               1,1,1, -99,32, ave(5), dt, hist_dt)
3911
3912       ! annual release from all 100year wood product pools
3913       CALL histdef (hist_id_stom, &
3914            &               TRIM("CFLUX_PROD100_LCC   "), &
3915            &               TRIM("annual release from all 100year wood product pools"), &
3916            &               TRIM("gC/m**2/day          "), iim,jjm, hist_hori_id, &
3917            &               1,1,1, -99,32, ave(5), dt, hist_dt)
3918
3919       ! annual release from all 100year wood product pools
3920       CALL histdef (hist_id_stom, &
3921            &               TRIM("CFLUX_PROD100_HAR   "), &
3922            &               TRIM("annual release from all 100year wood product pools"), &
3923            &               TRIM("gC/m**2/day          "), iim,jjm, hist_hori_id, &
3924            &               1,1,1, -99,32, ave(5), dt, hist_dt)
3925
3926       ! WOOD HARVEST
3927       CALL histdef (hist_id_stom, &
3928            &               TRIM("WOOD_HARVEST  "), &
3929            &               TRIM("harvested wood biomass"), &
3930            &               TRIM("gC/m**2/day          "), iim,jjm, hist_hori_id, &
3931            &               1,1,1, -99,32, ave(5), dt, hist_dt)
3932
3933       CALL histdef (hist_id_stom, &
3934            &               TRIM("WOOD_HARVEST_PFT  "), &
3935            &               TRIM("harvested wood biomass per PFT"), &
3936            &               TRIM("gC/m**2/day          "), iim,jjm, hist_hori_id, &
3937            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
3938
3939       ! agriculure product
3940       CALL histdef (hist_id_stom, &
3941            &               TRIM("HARVEST_ABOVE       "), &
3942            &               TRIM("annual release product after harvest              "), &
3943            &               TRIM("gC/m**2/day          "), iim,jjm, hist_hori_id, &
3944            &               1,1,1, -99,32, ave(5), dt, hist_dt)
3945
3946
3947       CALL histdef(hist_id_stom, 'RESOLUTION_X', 'E-W resolution', 'm', &
3948            & iim,jjm, hist_hori_id, 1,1,1, -99, 32, 'once(scatter(X))', dt, hist_dt)
3949       CALL histdef(hist_id_stom, 'RESOLUTION_Y', 'N-S resolution', 'm', &
3950            & iim,jjm, hist_hori_id, 1,1,1, -99, 32, 'once(scatter(X))', dt, hist_dt)
3951       CALL histdef(hist_id_stom, 'CONTFRAC', 'Continental fraction', '1', &
3952            & iim,jjm, hist_hori_id, 1,1,1, -99, 32, 'once(scatter(X))', dt, hist_dt)
3953       CALL histdef(hist_id_stom, 'Areas', 'Mesh areas', 'm2', &
3954            & iim,jjm, hist_hori_id, 1,1,1, -99, 32, 'once(scatter(X))', dt, hist_dt)
3955       
3956       !  Special outputs for phenology
3957       CALL histdef (hist_id_stom, &
3958            &               TRIM("WHEN_GROWTHINIT     "), &
3959            &               TRIM("Time elapsed from season beginning                "), &
3960            &               TRIM("d                   "), iim,jjm, hist_hori_id, &
3961            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(9), dt, hist_dt)
3962       
3963       CALL histdef (hist_id_stom, &
3964            &               TRIM("PFTPRESENT          "), &
3965            &               TRIM("PFT exists                                        "), &
3966            &               TRIM("d                   "), iim,jjm, hist_hori_id, &
3967            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(9), dt, hist_dt)
3968       
3969       CALL histdef (hist_id_stom, &
3970            &               TRIM("GDD_MIDWINTER       "), &
3971            &               TRIM("Growing degree days, since midwinter              "), &
3972            &               TRIM("degK                "), iim,jjm, hist_hori_id, &
3973            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(9), dt, hist_dt)
3974
3975       CALL histdef (hist_id_stom, &
3976            &               TRIM("GDD_M5_DORMANCE     "), &
3977            &               TRIM("Growing degree days, since dormance               "), &
3978            &               TRIM("degK                "), iim,jjm, hist_hori_id, &
3979            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(9), dt, hist_dt)
3980       
3981       CALL histdef (hist_id_stom, &
3982            &               TRIM("NCD_DORMANCE        "), &
3983            &               TRIM("Number of chilling days, since leaves were lost   "), &
3984            &               TRIM("d                   "), iim,jjm, hist_hori_id, &
3985            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(9), dt, hist_dt)
3986       
3987       CALL histdef (hist_id_stom, &
3988            &               TRIM("ALLOW_INITPHENO     "), &
3989            &               TRIM("Allow to declare beginning of the growing season  "), &
3990            &               TRIM("-                   "), iim,jjm, hist_hori_id, &
3991            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(9), dt, hist_dt)
3992       
3993       CALL histdef (hist_id_stom, &
3994            &               TRIM("BEGIN_LEAVES        "), &
3995            &               TRIM("Signal to start putting leaves on                 "), &
3996            &               TRIM("-                   "), iim,jjm, hist_hori_id, &
3997            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(9), dt, hist_dt)
3998
3999!gmjc
4000!GM0
4001    CALL histdef (hist_id_stom, &
4002         &               TRIM("GRAZINGC "), &
4003         &               TRIM("Grazing C "), &
4004         &               TRIM("kgC/m^2/day "), iim,jjm, hist_hori_id, &
4005         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
4006!GM1
4007    CALL histdef (hist_id_stom, &
4008         &               TRIM("GRAZINGCSUM "), &
4009         &               TRIM("- "), &
4010         &               TRIM("- "), iim,jjm, hist_hori_id, &
4011         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4012
4013    CALL histdef (hist_id_stom, &
4014         &               TRIM("NANIMALTOT "), &
4015         &               TRIM("- "), &
4016         &               TRIM("- "), iim,jjm, hist_hori_id, &
4017         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4018
4019    CALL histdef (hist_id_stom, &
4020         &               TRIM("INTAKE_ANIMAL "), &
4021         &               TRIM("- "), &
4022         &               TRIM("- "), iim,jjm, hist_hori_id, &
4023         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4024
4025    CALL histdef (hist_id_stom, &
4026         &               TRIM("INTAKE "), &
4027         &               TRIM("grazing animal intake "), &
4028         &               TRIM("kgDM/m^2/day "), iim,jjm, hist_hori_id, &
4029         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
4030
4031    CALL histdef (hist_id_stom, &
4032         &               TRIM("INTAKESUM "), &
4033         &               TRIM("- "), &
4034         &               TRIM("- "), iim,jjm, hist_hori_id, &
4035         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4036
4037    CALL histdef (hist_id_stom, &
4038         &               TRIM("TRAMPLING "), &
4039         &               TRIM("litter from trample by animals "), &
4040         &               TRIM("kgC/m^2/day "), iim,jjm, hist_hori_id, &
4041         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
4042
4043    CALL histdef (hist_id_stom, &
4044         &               TRIM("MILK "), &
4045         &               TRIM("- "), &
4046         &               TRIM("- "), iim,jjm, hist_hori_id, &
4047         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4048
4049    CALL histdef (hist_id_stom, &
4050         &               TRIM("MILKSUM "), &
4051         &               TRIM("- "), &
4052         &               TRIM("- "), iim,jjm, hist_hori_id, &
4053         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4054
4055    CALL histdef (hist_id_stom, &
4056         &               TRIM("MILKCSUM "), &
4057         &               TRIM("- "), &
4058         &               TRIM("- "), iim,jjm, hist_hori_id, &
4059         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4060
4061    CALL histdef (hist_id_stom, &
4062         &               TRIM("MILKC "), &
4063         &               TRIM("C export by milk production during animal grazing "), &
4064         &               TRIM("kgC/m^2/day "), iim,jjm, hist_hori_id, &
4065         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
4066!GM11
4067    CALL histdef (hist_id_stom, &
4068         &               TRIM("MILKN "), &
4069         &               TRIM("- "), &
4070         &               TRIM("- "), iim,jjm, hist_hori_id, &
4071         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4072
4073    CALL histdef (hist_id_stom, &
4074         &               TRIM("MILKANIMAL "), &
4075         &               TRIM("- "), &
4076         &               TRIM("- "), iim,jjm, hist_hori_id, &
4077         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4078
4079    CALL histdef (hist_id_stom, &
4080         &               TRIM("METHANE "), &
4081         &               TRIM("Methane emission by grazing animal "), &
4082         &               TRIM("kgC/m^2/day "), iim,jjm, hist_hori_id, &
4083         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
4084
4085    CALL histdef (hist_id_stom, &
4086         &               TRIM("METHANE_ANI "), &
4087         &               TRIM("- "), &
4088         &               TRIM("- "), iim,jjm, hist_hori_id, &
4089         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4090
4091    CALL histdef (hist_id_stom, &
4092         &               TRIM("RANIMALSUM "), &
4093         &               TRIM("- "), &
4094         &               TRIM("- "), iim,jjm, hist_hori_id, &
4095         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4096
4097    CALL histdef (hist_id_stom, &
4098         &               TRIM("METHANESUM "), &
4099         &               TRIM("- "), &
4100         &               TRIM("- "), iim,jjm, hist_hori_id, &
4101         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4102
4103    CALL histdef (hist_id_stom, &
4104         &               TRIM("RANIMAL "), &
4105         &               TRIM("C loss through grazing animal respiration "), &
4106         &               TRIM("kgC/m^2/day "), iim,jjm, hist_hori_id, &
4107         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
4108
4109    CALL histdef (hist_id_stom, &
4110         &               TRIM("FAECESNSUM "), &
4111         &               TRIM("- "), &
4112         &               TRIM("- "), iim,jjm, hist_hori_id, &
4113         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4114
4115    CALL histdef (hist_id_stom, &
4116         &               TRIM("FAECESCSUM "), &
4117         &               TRIM("- "), &
4118         &               TRIM("- "), iim,jjm, hist_hori_id, &
4119         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4120
4121    CALL histdef (hist_id_stom, &
4122         &               TRIM("URINECSUM "), &
4123         &               TRIM("- "), &
4124         &               TRIM("- "), iim,jjm, hist_hori_id, &
4125         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4126!GM21
4127    CALL histdef (hist_id_stom, &
4128         &               TRIM("URINENSUM "), &
4129         &               TRIM("- "), &
4130         &               TRIM("- "), iim,jjm, hist_hori_id, &
4131         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4132
4133    CALL histdef (hist_id_stom, &
4134         &               TRIM("NEL "), &
4135         &               TRIM("- "), &
4136         &               TRIM("- "), iim,jjm, hist_hori_id, &
4137         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4138
4139    CALL histdef (hist_id_stom, &
4140         &               TRIM("URINEN "), &
4141         &               TRIM("- "), &
4142         &               TRIM("- "), iim,jjm, hist_hori_id, &
4143         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4144
4145    CALL histdef (hist_id_stom, &
4146         &               TRIM("URINEC "), &
4147         &               TRIM("C in urine "), &
4148         &               TRIM("kgC/m^2/day "), iim,jjm, hist_hori_id, &
4149         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
4150
4151    CALL histdef (hist_id_stom, &
4152         &               TRIM("FAECESC "), &
4153         &               TRIM("C in faeces "), &
4154         &               TRIM("kgC/m^2/day "), iim,jjm, hist_hori_id, &
4155         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
4156
4157    CALL histdef (hist_id_stom, &
4158         &               TRIM("FAECESN "), &
4159         &               TRIM("- "), &
4160         &               TRIM("- "), iim,jjm, hist_hori_id, &
4161         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4162
4163    CALL histdef (hist_id_stom, &
4164         &               TRIM("GRAZED_FRAC "), &
4165         &               TRIM("- "), &
4166         &               TRIM("- "), iim,jjm, hist_hori_id, &
4167         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4168
4169    CALL histdef (hist_id_stom, &
4170         &               TRIM("NB_ANI "), &
4171         &               TRIM("- "), &
4172         &               TRIM("- "), iim,jjm, hist_hori_id, &
4173         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4174
4175    CALL histdef (hist_id_stom, &
4176         &               TRIM("IMPORT_YIELD "), &
4177         &               TRIM("potential harvest yield of last year "), &
4178         &               TRIM("kgDM/m^2/yr "), iim,jjm, hist_hori_id, &
4179         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
4180
4181    CALL histdef (hist_id_stom, &
4182         &               TRIM("EXTRA_FEED "), &
4183         &               TRIM("- "), &
4184         &               TRIM("- "), iim,jjm, hist_hori_id, &
4185         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4186!GM31
4187    CALL histdef (hist_id_stom, &
4188         &               TRIM("COMPT_UGB "), &
4189         &               TRIM("- "), &
4190         &               TRIM("- "), iim,jjm, hist_hori_id, &
4191         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4192
4193    CALL histdef (hist_id_stom, &
4194         &               TRIM("NB_GRAZINGDAYS "), &
4195         &               TRIM("number of grazing days of last year "), &
4196         &               TRIM("days "), iim,jjm, hist_hori_id, &
4197         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
4198
4199    CALL histdef (hist_id_stom, &
4200         &               TRIM("AMOUNT_YIELD "), &
4201         &               TRIM("- "), &
4202         &               TRIM("- "), iim,jjm, hist_hori_id, &
4203         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4204
4205    CALL histdef (hist_id_stom, &
4206         &               TRIM("CONSUMP "), &
4207         &               TRIM("- "), &
4208         &               TRIM("- "), iim,jjm, hist_hori_id, &
4209         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4210
4211    CALL histdef (hist_id_stom, &
4212         &               TRIM("OUTSIDE_FOOD "), &
4213         &               TRIM("- "), &
4214         &               TRIM("- "), iim,jjm, hist_hori_id, &
4215         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4216
4217    CALL histdef (hist_id_stom, &
4218         &               TRIM("ADD_NB_ANI "), &
4219         &               TRIM("- "), &
4220         &               TRIM("- "), iim,jjm, hist_hori_id, &
4221         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4222
4223    CALL histdef (hist_id_stom, &
4224         &               TRIM("BCSyoung "), &
4225         &               TRIM("- "), &
4226         &               TRIM("- "), iim,jjm, hist_hori_id, &
4227         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4228
4229    CALL histdef (hist_id_stom, &
4230         &               TRIM("BCSmature "), &
4231         &               TRIM("- "), &
4232         &               TRIM("- "), iim,jjm, hist_hori_id, &
4233         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4234
4235    CALL histdef (hist_id_stom, &
4236         &               TRIM("Weightyoung "), &
4237         &               TRIM("- "), &
4238         &               TRIM("- "), iim,jjm, hist_hori_id, &
4239         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4240
4241    CALL histdef (hist_id_stom, &
4242         &               TRIM("Weightmature "), &
4243         &               TRIM("- "), &
4244         &               TRIM("- "), iim,jjm, hist_hori_id, &
4245         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4246!GM41
4247    CALL histdef (hist_id_stom, &
4248         &               TRIM("Weightcalf "), &
4249         &               TRIM("- "), &
4250         &               TRIM("- "), iim,jjm, hist_hori_id, &
4251         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4252
4253    CALL histdef (hist_id_stom, &
4254         &               TRIM("MPyoung "), &
4255         &               TRIM("- "), &
4256         &               TRIM("- "), iim,jjm, hist_hori_id, &
4257         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4258
4259    CALL histdef (hist_id_stom, &
4260         &               TRIM("MPmature "), &
4261         &               TRIM("- "), &
4262         &               TRIM("- "), iim,jjm, hist_hori_id, &
4263         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4264
4265    CALL histdef (hist_id_stom, &
4266         &               TRIM("MPwyoung "), &
4267         &               TRIM("- "), &
4268         &               TRIM("- "), iim,jjm, hist_hori_id, &
4269         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4270
4271    CALL histdef (hist_id_stom, &
4272         &               TRIM("MPwmature "), &
4273         &               TRIM("- "), &
4274         &               TRIM("- "), iim,jjm, hist_hori_id, &
4275         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4276
4277    CALL histdef (hist_id_stom, &
4278         &               TRIM("MPposyoung "), &
4279         &               TRIM("- "), &
4280         &               TRIM("- "), iim,jjm, hist_hori_id, &
4281         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4282
4283    CALL histdef (hist_id_stom, &
4284         &               TRIM("MPposmature "), &
4285         &               TRIM("- "), &
4286         &               TRIM("- "), iim,jjm, hist_hori_id, &
4287         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4288
4289    CALL histdef (hist_id_stom, &
4290         &               TRIM("NEByoung "), &
4291         &               TRIM("- "), &
4292         &               TRIM("- "), iim,jjm, hist_hori_id, &
4293         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4294
4295    CALL histdef (hist_id_stom, &
4296         &               TRIM("NEBmature "), &
4297         &               TRIM("- "), &
4298         &               TRIM("- "), iim,jjm, hist_hori_id, &
4299         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4300
4301    CALL histdef (hist_id_stom, &
4302         &               TRIM("NEIyoung "), &
4303         &               TRIM("- "), &
4304         &               TRIM("- "), iim,jjm, hist_hori_id, &
4305         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4306!GM51
4307    CALL histdef (hist_id_stom, &
4308         &               TRIM("NEImature "), &
4309         &               TRIM("- "), &
4310         &               TRIM("- "), iim,jjm, hist_hori_id, &
4311         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4312
4313    CALL histdef (hist_id_stom, &
4314         &               TRIM("DMIcyoung "), &
4315         &               TRIM("- "), &
4316         &               TRIM("- "), iim,jjm, hist_hori_id, &
4317         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4318
4319    CALL histdef (hist_id_stom, &
4320         &               TRIM("DMIcmature "), &
4321         &               TRIM("- "), &
4322         &               TRIM("- "), iim,jjm, hist_hori_id, &
4323         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4324
4325    CALL histdef (hist_id_stom, &
4326         &               TRIM("DMIfyoung "), &
4327         &               TRIM("- "), &
4328         &               TRIM("- "), iim,jjm, hist_hori_id, &
4329         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4330
4331    CALL histdef (hist_id_stom, &
4332         &               TRIM("DMIfmature "), &
4333         &               TRIM("- "), &
4334         &               TRIM("- "), iim,jjm, hist_hori_id, &
4335         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4336
4337    CALL histdef (hist_id_stom, &
4338         &               TRIM("DMIyoung "), &
4339         &               TRIM("- "), &
4340         &               TRIM("- "), iim,jjm, hist_hori_id, &
4341         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4342
4343    CALL histdef (hist_id_stom, &
4344         &               TRIM("DMImature "), &
4345         &               TRIM("- "), &
4346         &               TRIM("- "), iim,jjm, hist_hori_id, &
4347         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4348
4349    CALL histdef (hist_id_stom, &
4350         &               TRIM("DMIcalf "), &
4351         &               TRIM("- "), &
4352         &               TRIM("- "), iim,jjm, hist_hori_id, &
4353         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4354
4355    CALL histdef (hist_id_stom, &
4356         &               TRIM("OMD "), &
4357         &               TRIM("- "), &
4358         &               TRIM("- "), iim,jjm, hist_hori_id, &
4359         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4360
4361    CALL histdef (hist_id_stom, &
4362         &               TRIM("Weightcows "), &
4363         &               TRIM("- "), &
4364         &               TRIM("- "), iim,jjm, hist_hori_id, &
4365         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4366!GM61
4367    CALL histdef (hist_id_stom, &
4368         &               TRIM("BCScows "), &
4369         &               TRIM("- "), &
4370         &               TRIM("- "), iim,jjm, hist_hori_id, &
4371         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4372
4373    CALL histdef (hist_id_stom, &
4374         &               TRIM("CH4young "), &
4375         &               TRIM("- "), &
4376         &               TRIM("- "), iim,jjm, hist_hori_id, &
4377         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4378
4379    CALL histdef (hist_id_stom, &
4380         &               TRIM("CH4mature "), &
4381         &               TRIM("- "), &
4382         &               TRIM("- "), iim,jjm, hist_hori_id, &
4383         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4384
4385    CALL histdef (hist_id_stom, &
4386         &               TRIM("TSOILCUMM "), &
4387         &               TRIM("- "), &
4388         &               TRIM("- "), iim,jjm, hist_hori_id, &
4389         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4390
4391    CALL histdef (hist_id_stom, &
4392         &               TRIM("YIELD_RETURN "), &
4393         &               TRIM("- "), &
4394         &               TRIM("- "), iim,jjm, hist_hori_id, &
4395         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4396
4397    CALL histdef (hist_id_stom, &
4398         &               TRIM("REGCOUNT "), &
4399         &               TRIM("- "), &
4400         &               TRIM("- "), iim,jjm, hist_hori_id, &
4401         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4402
4403    CALL histdef (hist_id_stom, &
4404         &               TRIM("FERTCOUNT "), &
4405         &               TRIM("- "), &
4406         &               TRIM("- "), iim,jjm, hist_hori_id, &
4407         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4408
4409    CALL histdef (hist_id_stom, &
4410         &               TRIM("GMEAN1 "), &
4411         &               TRIM("- "), &
4412         &               TRIM("- "), iim,jjm, hist_hori_id, &
4413         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4414
4415    CALL histdef (hist_id_stom, &
4416         &               TRIM("GMEAN2 "), &
4417         &               TRIM("- "), &
4418         &               TRIM("- "), iim,jjm, hist_hori_id, &
4419         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4420
4421    CALL histdef (hist_id_stom, &
4422         &               TRIM("GMEAN3 "), &
4423         &               TRIM("- "), &
4424         &               TRIM("- "), iim,jjm, hist_hori_id, &
4425         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4426!GM71
4427    CALL histdef (hist_id_stom, &
4428         &               TRIM("GMEAN4 "), &
4429         &               TRIM("- "), &
4430         &               TRIM("- "), iim,jjm, hist_hori_id, &
4431         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4432
4433    CALL histdef (hist_id_stom, &
4434         &               TRIM("GMEAN5 "), &
4435         &               TRIM("- "), &
4436         &               TRIM("- "), iim,jjm, hist_hori_id, &
4437         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4438
4439    CALL histdef (hist_id_stom, &
4440         &               TRIM("GMEAN6 "), &
4441         &               TRIM("- "), &
4442         &               TRIM("- "), iim,jjm, hist_hori_id, &
4443         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4444
4445    CALL histdef (hist_id_stom, &
4446         &               TRIM("GMEAN7 "), &
4447         &               TRIM("- "), &
4448         &               TRIM("- "), iim,jjm, hist_hori_id, &
4449         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4450
4451    CALL histdef (hist_id_stom, &
4452         &               TRIM("GMEAN8 "), &
4453         &               TRIM("- "), &
4454         &               TRIM("- "), iim,jjm, hist_hori_id, &
4455         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4456
4457    CALL histdef (hist_id_stom, &
4458         &               TRIM("GMEAN9 "), &
4459         &               TRIM("- "), &
4460         &               TRIM("- "), iim,jjm, hist_hori_id, &
4461         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4462
4463    CALL histdef (hist_id_stom, &
4464         &               TRIM("GMEAN0 "), &
4465         &               TRIM("- "), &
4466         &               TRIM("- "), iim,jjm, hist_hori_id, &
4467         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4468
4469    CALL histdef (hist_id_stom, &
4470         &               TRIM("WSH "), &
4471         &               TRIM("shoot structure mass "), &
4472         &               TRIM("kgDM/m^2 "), iim,jjm, hist_hori_id, &
4473         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
4474
4475    CALL histdef (hist_id_stom, &
4476         &               TRIM("WSHTOT "), &
4477         &               TRIM("total shoot structure mass "), &
4478         &               TRIM("kgDM/m^2 "), iim,jjm, hist_hori_id, &
4479         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
4480
4481    CALL histdef (hist_id_stom, &
4482         &               TRIM("WR "), &
4483         &               TRIM("root structure mass "), &
4484         &               TRIM("kgDM/m^2 "), iim,jjm, hist_hori_id, &
4485         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
4486!GM81
4487    CALL histdef (hist_id_stom, &
4488         &               TRIM("WRTOT "), &
4489         &               TRIM("total root structure mass "), &
4490         &               TRIM("kgDM/m^2 "), iim,jjm, hist_hori_id, &
4491         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
4492
4493    CALL histdef (hist_id_stom, &
4494         &               TRIM("WSHTOTSUM "), &
4495         &               TRIM("- "), &
4496         &               TRIM("- "), iim,jjm, hist_hori_id, &
4497         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4498
4499    CALL histdef (hist_id_stom, &
4500         &               TRIM("SR_UGB "), &
4501         &               TRIM("instantaneous stocking rate "), &
4502         &               TRIM("HeadorLSU/m^2 "), iim,jjm, hist_hori_id, &
4503         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
4504
4505    CALL histdef (hist_id_stom, &
4506         &               TRIM("FCORGFERTMET "), &
4507         &               TRIM("- "), &
4508         &               TRIM("- "), iim,jjm, hist_hori_id, &
4509         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4510
4511    CALL histdef (hist_id_stom, &
4512         &               TRIM("FCORGFERTSTR "), &
4513         &               TRIM("- "), &
4514         &               TRIM("- "), iim,jjm, hist_hori_id, &
4515         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4516
4517    CALL histdef (hist_id_stom, &
4518         &               TRIM("FNORGANICFERTURINE "), &
4519         &               TRIM("- "), &
4520         &               TRIM("- "), iim,jjm, hist_hori_id, &
4521         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4522
4523    CALL histdef (hist_id_stom, &
4524         &               TRIM("FNORGANICFERTSTRUCT "), &
4525         &               TRIM("- "), &
4526         &               TRIM("- "), iim,jjm, hist_hori_id, &
4527         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4528
4529    CALL histdef (hist_id_stom, &
4530         &               TRIM("FNORGANICFERTMETABOLIC "), &
4531         &               TRIM("- "), &
4532         &               TRIM("- "), iim,jjm, hist_hori_id, &
4533         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4534
4535    CALL histdef (hist_id_stom, &
4536         &               TRIM("NFERTNITTOT "), &
4537         &               TRIM("- "), &
4538         &               TRIM("- "), iim,jjm, hist_hori_id, &
4539         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4540
4541    CALL histdef (hist_id_stom, &
4542         &               TRIM("NFERTAMMTOT "), &
4543         &               TRIM("- "), &
4544         &               TRIM("- "), iim,jjm, hist_hori_id, &
4545         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4546!GM91
4547    CALL histdef (hist_id_stom, &
4548         &               TRIM("LOSS "), &
4549         &               TRIM("- "), &
4550         &               TRIM("- "), iim,jjm, hist_hori_id, &
4551         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4552
4553    CALL histdef (hist_id_stom, &
4554         &               TRIM("LOSSC "), &
4555         &               TRIM("Carbon loss as litter during cutting "), &
4556         &               TRIM("kg C/m**2 "), iim,jjm, hist_hori_id, &
4557         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
4558
4559    CALL histdef (hist_id_stom, &
4560         &               TRIM("LOSSN "), &
4561         &               TRIM("- "), &
4562         &               TRIM("- "), iim,jjm, hist_hori_id, &
4563         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4564
4565    CALL histdef (hist_id_stom, &
4566         &               TRIM("DM_CUTYEARLY "), &
4567         &               TRIM("- "), &
4568         &               TRIM("- "), iim,jjm, hist_hori_id, &
4569         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4570
4571    CALL histdef (hist_id_stom, &
4572         &               TRIM("C_CUTYEARLY "), &
4573         &               TRIM("- "), &
4574         &               TRIM("- "), iim,jjm, hist_hori_id, &
4575         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4576
4577    CALL histdef (hist_id_stom, &
4578         &               TRIM("NFERT_TOTAL "), &
4579         &               TRIM("Total Nitrogen input "), &
4580         &               TRIM("kg N/ha "), iim,jjm, hist_hori_id, &
4581         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
4582
4583    CALL histdef (hist_id_stom, &
4584         &               TRIM("NDEP "), &
4585         &               TRIM("Nitrogen deposition from input "), &
4586         &               TRIM("kg N/ha "), iim,jjm, hist_hori_id, &
4587         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
4588
4589    CALL histdef (hist_id_stom, &
4590         &               TRIM("LEGUME_FRACTION "), &
4591         &               TRIM("- "), &
4592         &               TRIM("- "), iim,jjm, hist_hori_id, &
4593         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4594
4595    CALL histdef (hist_id_stom, &
4596         &               TRIM("SOIL_FERTILITY "), &
4597         &               TRIM("- "), &
4598         &               TRIM("- "), iim,jjm, hist_hori_id, &
4599         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4600
4601    CALL histdef (hist_id_stom, &
4602         &               TRIM("C "), &
4603         &               TRIM("- "), &
4604         &               TRIM("- "), iim,jjm, hist_hori_id, &
4605         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4606!GM101
4607    CALL histdef (hist_id_stom, &
4608         &               TRIM("N "), &
4609         &               TRIM("- "), &
4610         &               TRIM("- "), iim,jjm, hist_hori_id, &
4611         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4612
4613    CALL histdef (hist_id_stom, &
4614         &               TRIM("FN "), &
4615         &               TRIM("- "), &
4616         &               TRIM("- "), iim,jjm, hist_hori_id, &
4617         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4618
4619    CALL histdef (hist_id_stom, &
4620         &               TRIM("NTOT "), &
4621         &               TRIM("- "), &
4622         &               TRIM("- "), iim,jjm, hist_hori_id, &
4623         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4624
4625    CALL histdef (hist_id_stom, &
4626         &               TRIM("NAPO "), &
4627         &               TRIM("- "), &
4628         &               TRIM("- "), iim,jjm, hist_hori_id, &
4629         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4630
4631    CALL histdef (hist_id_stom, &
4632         &               TRIM("NSYM "), &
4633         &               TRIM("- "), &
4634         &               TRIM("- "), iim,jjm, hist_hori_id, &
4635         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4636
4637    CALL histdef (hist_id_stom, &
4638         &               TRIM("DEVSTAGE "), &
4639         &               TRIM("- "), &
4640         &               TRIM("- "), iim,jjm, hist_hori_id, &
4641         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4642
4643    CALL histdef (hist_id_stom, &
4644         &               TRIM("TGROWTH "), &
4645         &               TRIM("- "), &
4646         &               TRIM("- "), iim,jjm, hist_hori_id, &
4647         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4648
4649    CALL histdef (hist_id_stom, &
4650         &               TRIM("GRAZINGCSTRUCT "), &
4651         &               TRIM("- "), &
4652         &               TRIM("- "), iim,jjm, hist_hori_id, &
4653         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4654
4655    CALL histdef (hist_id_stom, &
4656         &               TRIM("GRAZINGNSTRUCT "), &
4657         &               TRIM("- "), &
4658         &               TRIM("- "), iim,jjm, hist_hori_id, &
4659         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4660
4661    CALL histdef (hist_id_stom, &
4662         &               TRIM("GRAZINGWN "), &
4663         &               TRIM("- "), &
4664         &               TRIM("- "), iim,jjm, hist_hori_id, &
4665         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4666!GM111
4667    CALL histdef (hist_id_stom, &
4668         &               TRIM("GRAZINGWC "), &
4669         &               TRIM("- "), &
4670         &               TRIM("- "), iim,jjm, hist_hori_id, &
4671         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4672
4673       ! 14days 2 m temperature
4674       CALL histdef (hist_id_stom, &
4675            &               TRIM("T2M_14            "), &
4676            &               TRIM("14days 2 m temperature"), &
4677            &               TRIM("K                   "), iim,jjm, hist_hori_id, &
4678            &               1,1,1, -99,32, ave(5), dt, hist_dt)
4679
4680    CALL histdef (hist_id_stom, &
4681         &               TRIM("LITTER_RESP "), &
4682         &               TRIM("heterotr. resp. from litter pool "), &
4683         &               TRIM("gC/m^2/day "), iim,jjm, hist_hori_id, &
4684         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
4685
4686    CALL histdef (hist_id_stom, &
4687         &               TRIM("ACTIVE_RESP "), &
4688         &               TRIM("heterotr. resp. from active carbon pool "), &
4689         &               TRIM("gC/m^2/day "), iim,jjm, hist_hori_id, &
4690         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
4691
4692    CALL histdef (hist_id_stom, &
4693         &               TRIM("SLOW_RESP "), &
4694         &               TRIM("heterotr. resp. from slow carbon pool "), &
4695         &               TRIM("gC/m^2/day "), iim,jjm, hist_hori_id, &
4696         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
4697
4698    CALL histdef (hist_id_stom, &
4699         &               TRIM("PASSIVE_RESP "), &
4700         &               TRIM("heterotr. resp. from passive carbon pool "), &
4701         &               TRIM("gC/m^2/day "), iim,jjm, hist_hori_id, &
4702         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
4703
4704!    CALL histdef (hist_id_stom, &
4705!         &               TRIM("N_LIMFERT "), &
4706!         &               TRIM("Nitrogen limitation factor on vcmax "), &
4707!         &               TRIM("- "), iim,jjm, hist_hori_id, &
4708!         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
4709
4710    CALL histdef (hist_id_stom, &
4711         &               TRIM("SLA_CALC "), &
4712         &               TRIM("sla calculated by leaf age "), &
4713         &               TRIM("m**2/gC "), iim,jjm, hist_hori_id, &
4714         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
4715
4716    CALL histdef (hist_id_stom, &
4717         &               TRIM("NPP_ABOVE "), &
4718         &               TRIM("Net above primary productivity "), &
4719         &               TRIM("gC/day/(m^2 (n/a)) "), iim,jjm, hist_hori_id, &
4720         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
4721
4722    CALL histdef (hist_id_stom, &
4723         &               TRIM("NPP_BELOW "), &
4724         &               TRIM("Net below primary productivity "), &
4725         &               TRIM("gC/day/(m^2 (n/a)) "), iim,jjm, hist_hori_id, &
4726         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
4727!GMtotal120
4728    CALL histdef (hist_id_stom, &
4729         &               TRIM("LITTER_STR_AVAIL "), &
4730         &               TRIM("Structural litter available for grazing "), &
4731         &               TRIM("gC/day/(m^2 (n/a)) "), iim,jjm, hist_hori_id, &
4732         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
4733    CALL histdef (hist_id_stom, &
4734         &               TRIM("LITTER_MET_AVAIL "), &
4735         &               TRIM("Metabolic litter available for grazing "), &
4736         &               TRIM("gC/day/(m^2 (n/a)) "), iim,jjm, hist_hori_id, &
4737         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
4738    CALL histdef (hist_id_stom, &
4739         &               TRIM("LITTER_STR_NAVAIL "), &
4740         &               TRIM("Structural litter not available for grazing "), &
4741         &               TRIM("gC/day/(m^2 (n/a)) "), iim,jjm, hist_hori_id, &
4742         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
4743    CALL histdef (hist_id_stom, &
4744         &               TRIM("LITTER_MET_NAVAIL "), &
4745         &               TRIM("Metabolic litter not available for grazing "), &
4746         &               TRIM("gC/day/(m^2 (n/a)) "), iim,jjm, hist_hori_id, &
4747         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
4748    CALL histdef (hist_id_stom, &
4749         &               TRIM("LITTER_STR_AVAILF "), &
4750         &               TRIM("Structural litter available fraction for grazing "), &
4751         &               TRIM("% "), iim,jjm, hist_hori_id, &
4752         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
4753    CALL histdef (hist_id_stom, &
4754         &               TRIM("LITTER_MET_AVAILF "), &
4755         &               TRIM("Metabolic litter available fraction for grazing "), &
4756         &               TRIM("% "), iim,jjm, hist_hori_id, &
4757         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
4758    CALL histdef (hist_id_stom, &
4759         &               TRIM("INTAKE_ANIMAL_LITTER "), &
4760         &               TRIM("Litter intake per animal "), &
4761         &               TRIM("kg DM/animal/day "), iim,jjm, hist_hori_id, &
4762         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
4763    CALL histdef (hist_id_stom, &
4764         &               TRIM("INTAKE_LITTER "), &
4765         &               TRIM("Litter intake per m**2 "), &
4766         &               TRIM("kg DM/m**2/day "), iim,jjm, hist_hori_id, &
4767         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
4768    CALL histdef (hist_id_stom, &
4769         &               TRIM("GRAZING_LITTER "), &
4770         &               TRIM("Flag of grazing litter 0 AGB 1 Litter 2 none "), &
4771         &               TRIM("- "), iim,jjm, hist_hori_id, &
4772         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
4773!GM131
4774    CALL histdef (hist_id_stom, &
4775         &               TRIM("COMPT_CUT "), &
4776         &               TRIM("Grass harvest time "), &
4777         &               TRIM("times "), iim,jjm, hist_hori_id, &
4778         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4779    CALL histdef (hist_id_stom, &
4780         &               TRIM("FREQUENCY_CUT "), &
4781         &               TRIM("Grass harvest frequency "), &
4782         &               TRIM("times "), iim,jjm, hist_hori_id, &
4783         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4784    CALL histdef (hist_id_stom, &
4785         &               TRIM("SR_WILD "), &
4786         &               TRIM("Wild animal stocking rate "), &
4787         &               TRIM("HeadorLSU/m^2 "), iim,jjm, hist_hori_id, &
4788         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4789    CALL histdef (hist_id_stom, &
4790         &               TRIM("TMCGRASS_DAILY "), &
4791         &               TRIM("daily mean 10 cm soil moisture "), &
4792         &               TRIM("m^3/m^3 "), iim,jjm, hist_hori_id, &
4793         &               1,1,1, -99,32, ave(5), dt, hist_dt)
4794    CALL histdef (hist_id_stom, &
4795         &               TRIM("FC_GRAZING "), &
4796         &               TRIM("field capacity in 10 cm soil moisture "), &
4797         &               TRIM("m^3/m^3 "), iim,jjm, hist_hori_id, &
4798         &               1,1,1, -99,32, ave(5), dt, hist_dt)
4799    CALL histdef (hist_id_stom, &
4800         &               TRIM("CT_DRY "), &
4801         &               TRIM("days after soil dry enough for grazing "), &
4802         &               TRIM("days "), iim,jjm, hist_hori_id, &
4803         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
4804    CALL histdef (hist_id_stom, &
4805         &               TRIM("N2O_PFT_GM "), &
4806         &               TRIM("N2O-N emission from grassland "), &
4807         &               TRIM("gN/m^2/day "), iim,jjm, hist_hori_id, &
4808         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4809    CALL histdef (hist_id_stom, &
4810         &               TRIM("CO2_GM "), &
4811         &               TRIM("CO2 fluxes of grassland"), &
4812         &               TRIM("gC/m^2/day "), iim,jjm, hist_hori_id, &
4813         &               1,1,1, -99,32, ave(5), dt, hist_dt)
4814    CALL histdef (hist_id_stom, &
4815         &               TRIM("CH4_GM "), &
4816         &               TRIM("CH4-C fluxes of grassland"), &
4817         &               TRIM("gC/m^2/day "), iim,jjm, hist_hori_id, &
4818         &               1,1,1, -99,32, ave(5), dt, hist_dt)
4819!end gmjc
4820!
4821!variables for CH4 flux density from wetlands
4822!
4823!pss:+
4824   CALL stomate_wet_ch4_histdef (iim, jjm, dt, hist_hori_id, hist_dt, ave, hist_id_stom)
4825
4826   !tsurf_year
4827   CALL histdef (hist_id_stom, &
4828        &               TRIM("TSURF_YEAR    "), &
4829        &               TRIM("Annual surface temperature                      "), &
4830        &               TRIM("K              "), iim,jjm, hist_hori_id, &
4831        &               1,1,1, -99,32, ave(1), dt, hist_dt)
4832   !pss:-
4833
4834       ! permafrost variables
4835       ! first read logic on which variables to write to hist file.  (variables
4836       ! are
4837       ! stored in constantes_soil.f90)
4838
4839       CALL getin_p ('writehist_deepC',writehist_deepC)
4840       CALL getin_p ('writehist_soilgases',writehist_soilgases)
4841       CALL getin_p ('writehist_deltaC',writehist_deltaC)
4842       CALL getin_p ('writehist_zimovheat',writehist_zimovheat)
4843       CALL getin_p ('writehist_deltaC_litter',writehist_deltaC_litter)
4844       CALL getin_p ('writehist_gascoeff',writehist_gascoeff)
4845
4846       ! heterotr. resp. from ground                 
4847       CALL histdef (hist_id_stom, &
4848            &    TRIM("resp_hetero_litter   "), &
4849            &    TRIM("heterotr. resp. from litter                      "), &
4850            &    TRIM("gC/m^2 tot/day      "), iim,jjm, hist_hori_id, &
4851            &    nvm,1,nvm, hist_PFTaxis_id,32, ave(3), dt, hist_dt)
4852
4853       CALL histdef (hist_id_stom, &
4854            &    TRIM("resp_hetero_soil     "), &
4855            &    TRIM("heterotr. resp. from standard stomate soil       "), &
4856            &    TRIM("gC/m^2 tot/day      "), iim,jjm, hist_hori_id, &
4857            &    nvm,1,nvm, hist_PFTaxis_id,32, ave(3), dt, hist_dt)
4858!++cdk: end of variables with implicit PFT dimension
4859       IF (writehist_deepC) THEN
4860          DO jv = 1, nvm
4861             IF (permafrost_veg_exists(jv)) THEN
4862                WRITE(part_str,'(I2)') jv
4863                IF (jv < 10) part_str(1:1) = '0'
4864                CALL histdef (hist_id_stom, &
4865                     & TRIM("deepC_a_"//part_str(1:LEN_TRIM(part_str))), &
4866                     & TRIM("active pool deep soil (permafrost) carbon,PFT:"//part_str(1:LEN_TRIM(part_str))), &
4867                     & TRIM("gC/m**3   "), iim,jjm, hist_hori_id, &
4868                     & ndeep, 1, ndeep, hist_stomate_deepsoil,32, ave(5),dt,hist_dt)
4869             END IF
4870          END DO
4871          DO jv = 1, nvm
4872             IF (permafrost_veg_exists(jv)) THEN
4873                WRITE(part_str,'(I2)') jv
4874                IF (jv < 10) part_str(1:1) = '0'
4875                CALL histdef (hist_id_stom, &
4876                     & TRIM("deepC_s_"//part_str(1:LEN_TRIM(part_str))), &
4877                     & TRIM("slow pool deep soil (permafrost) carbon   "), &
4878                     & TRIM("gC/m**3   "), iim,jjm, hist_hori_id, &
4879                     & ndeep, 1, ndeep, hist_stomate_deepsoil,32, ave(5),dt,hist_dt)
4880             END IF
4881          END DO
4882          DO jv = 1, nvm
4883             IF (permafrost_veg_exists(jv)) THEN
4884                WRITE(part_str,'(I2)') jv
4885                IF (jv < 10) part_str(1:1) = '0'
4886                CALL histdef (hist_id_stom, &
4887                     & TRIM("deepC_p_"//part_str(1:LEN_TRIM(part_str))), &
4888                     & TRIM("passive pool deep soil (permafrost) carbon   "), &
4889                     & TRIM("gC/m**3   "), iim,jjm, hist_hori_id, &
4890                     & ndeep, 1, ndeep, hist_stomate_deepsoil,32, ave(5),dt,hist_dt)
4891             END IF
4892          END DO
4893       ENDIF
4894       IF (writehist_soilgases) THEN
4895          DO jv = 1, nvm
4896             IF (permafrost_veg_exists(jv)) THEN
4897                WRITE(part_str,'(I2)') jv
4898                IF (jv < 10) part_str(1:1) = '0'
4899                CALL histdef (hist_id_stom, &
4900                     & TRIM("O2_soil_"//part_str(1:LEN_TRIM(part_str))), &
4901                     & TRIM("deep soil (permafrost) oxygen   "), &
4902                     & TRIM("gC/m**3   "), iim,jjm, hist_hori_id, &
4903                     & ndeep, 1, ndeep, hist_stomate_deepsoil,32, ave(5),dt,hist_dt)
4904             END IF
4905          END DO
4906          DO jv = 1, nvm
4907             IF (permafrost_veg_exists(jv)) THEN
4908                WRITE(part_str,'(I2)') jv
4909                IF (jv < 10) part_str(1:1) = '0'
4910                CALL histdef (hist_id_stom, &
4911                     & TRIM("CH4_soil_"//part_str(1:LEN_TRIM(part_str))), &
4912                     & TRIM("deep soil (permafrost) methane   "), &
4913                     & TRIM("gC/m**3   "), iim,jjm, hist_hori_id, &
4914                     & ndeep, 1, ndeep, hist_stomate_deepsoil,32, ave(5),dt,hist_dt)
4915             END IF
4916          END DO
4917          DO jv = 1, nvm
4918             IF (permafrost_veg_exists(jv)) THEN
4919                WRITE(part_str,'(I2)') jv
4920                IF (jv < 10) part_str(1:1) = '0'
4921                CALL histdef (hist_id_stom, &
4922                     & TRIM("O2_snow_"//part_str(1:LEN_TRIM(part_str))), &
4923                     & TRIM("snow oxygen   "), &
4924                     & TRIM("gC/m**3   "), iim,jjm, hist_hori_id, &
4925                     & nsnow, 1, nsnow, hist_stomate_snow,32, ave(5), dt,hist_dt)
4926             END IF
4927          END DO
4928          DO jv = 1, nvm
4929             IF (permafrost_veg_exists(jv)) THEN
4930                WRITE(part_str,'(I2)') jv
4931                IF (jv < 10) part_str(1:1) = '0'
4932                CALL histdef (hist_id_stom, &
4933                     & TRIM("CH4_snow_"//part_str(1:LEN_TRIM(part_str))), &
4934                     & TRIM("snow methane   "), &
4935                     & TRIM("gC/m**3   "), iim,jjm, hist_hori_id, &
4936                     & nsnow, 1, nsnow, hist_stomate_snow,32, ave(5), dt,hist_dt)
4937             END IF
4938          END DO
4939       ENDIF
4940
4941       IF (writehist_deltaC) THEN
4942          DO jv = 1, nvm
4943             IF (permafrost_veg_exists(jv)) THEN
4944                WRITE(part_str,'(I2)') jv
4945                IF (jv < 10) part_str(1:1) = '0'
4946                CALL histdef (hist_id_stom, &
4947                     & TRIM("deltaCH4g_"//part_str(1:LEN_TRIM(part_str))), &
4948                     & TRIM("methanogenesis   "), &
4949                     & TRIM("gCH4/m**3 air/s   "), iim,jjm, hist_hori_id, &
4950                     & ndeep, 1, ndeep, hist_stomate_deepsoil,32, ave(5),dt,hist_dt)
4951             END IF
4952          END DO
4953          DO jv = 1, nvm
4954             IF (permafrost_veg_exists(jv)) THEN
4955                WRITE(part_str,'(I2)') jv
4956                IF (jv < 10) part_str(1:1) = '0'
4957                CALL histdef (hist_id_stom, &
4958                     & TRIM("deltaCH4_"//part_str(1:LEN_TRIM(part_str))), &
4959                     & TRIM("methanotrophy   "), &
4960                     & TRIM("gCH4/m**3 air/s   "), iim,jjm, hist_hori_id, &
4961                     & ndeep, 1, ndeep, hist_stomate_deepsoil,32, ave(5),dt,hist_dt)
4962             END IF
4963          END DO
4964          DO jv = 1, nvm
4965             IF (permafrost_veg_exists(jv)) THEN
4966                WRITE(part_str,'(I2)') jv
4967                IF (jv < 10) part_str(1:1) = '0'
4968                CALL histdef (hist_id_stom, &
4969                     & TRIM("deltaC1_"//part_str(1:LEN_TRIM(part_str))), &
4970                     & TRIM("oxic decomposition   "), &
4971                     & TRIM("gC/m**3/s   "), iim,jjm, hist_hori_id, &
4972                     & ndeep, 1, ndeep, hist_stomate_deepsoil,32, ave(5),dt,hist_dt)
4973             END IF
4974          END DO
4975          DO jv = 1, nvm
4976             IF (permafrost_veg_exists(jv)) THEN
4977                WRITE(part_str,'(I2)') jv
4978                IF (jv < 10) part_str(1:1) = '0'
4979                CALL histdef (hist_id_stom, &
4980                     & TRIM("deltaC2_"//part_str(1:LEN_TRIM(part_str))), &
4981                     & TRIM("methanogenesis   "), &
4982                     & TRIM("gC/m**3 soil/s   "), iim,jjm, hist_hori_id, &
4983                     & ndeep, 1, ndeep, hist_stomate_deepsoil,32, ave(5),dt,hist_dt)
4984             END IF
4985          END DO
4986          DO jv = 1, nvm
4987             IF (permafrost_veg_exists(jv)) THEN
4988                WRITE(part_str,'(I2)') jv
4989                IF (jv < 10) part_str(1:1) = '0'
4990                CALL histdef (hist_id_stom, &
4991                     & TRIM("deltaC3_"//part_str(1:LEN_TRIM(part_str))), &
4992                     & TRIM("methanotrophy   "), &
4993                     & TRIM("gC/m**3 soil/s   "), iim,jjm, hist_hori_id, &
4994                     & ndeep, 1, ndeep, hist_stomate_deepsoil,32, ave(5),dt,hist_dt)
4995             END IF
4996          END DO
4997       ENDIF
4998       IF (writehist_zimovheat) THEN
4999          DO jv = 1, nvm
5000             IF (permafrost_veg_exists(jv)) THEN
5001                WRITE(part_str,'(I2)') jv
5002                IF (jv < 10) part_str(1:1) = '0'
5003                CALL histdef (hist_id_stom, &
5004                     & TRIM("heat_Zimov_"//part_str(1:LEN_TRIM(part_str))), &
5005                     & TRIM("heating due to decomposition   "), &
5006                     & TRIM("W/m**3   "), iim,jjm, hist_hori_id, &
5007                     & ndeep, 1, ndeep, hist_stomate_deepsoil,32, ave(5),dt,hist_dt)
5008             END IF
5009          END DO
5010       ENDIF
5011       IF (writehist_deltaC_litter) THEN
5012          DO jv = 1, nvm
5013             IF (permafrost_veg_exists(jv)) THEN
5014                WRITE(part_str,'(I2)') jv
5015                IF (jv < 10) part_str(1:1) = '0'
5016                CALL histdef (hist_id_stom, &
5017                     & TRIM("deltaC_litter_act_"//part_str(1:LEN_TRIM(part_str))), &
5018                     & TRIM("litter C input to soil active C pool   "), &
5019                     & TRIM("gC/m**3 soil/s   "), iim,jjm, hist_hori_id, &
5020                     & ndeep, 1, ndeep, hist_stomate_deepsoil,32, ave(5),dt,hist_dt)
5021             END IF
5022          END DO
5023          DO jv = 1, nvm
5024             IF (permafrost_veg_exists(jv)) THEN
5025                WRITE(part_str,'(I2)') jv
5026                IF (jv < 10) part_str(1:1) = '0'
5027                CALL histdef (hist_id_stom, &
5028                     & TRIM("deltaC_litter_slo_"//part_str(1:LEN_TRIM(part_str))), &
5029                     & TRIM("litter C input to soil slow C pool   "), &
5030                     & TRIM("gC/m**3 soil/s   "), iim,jjm, hist_hori_id, &
5031                     & ndeep, 1, ndeep, hist_stomate_deepsoil,32, ave(5),dt,hist_dt)
5032             END IF
5033          END DO
5034       ENDIF
5035       IF (writehist_gascoeff) THEN
5036          CALL histdef (hist_id_stom, &
5037               & TRIM("deltaC_litter_pas_"//part_str(1:LEN_TRIM(part_str))), &
5038               &               TRIM("litter C input to soil passive C pool   "),&
5039               &               TRIM("gC/m**3 soil/s   "), iim,jjm, hist_hori_id,&
5040               &               ndeep, 1, ndeep, hist_stomate_deepsoil,32,ave(5),dt, hist_dt)
5041          DO jv = 1, nvm
5042             WRITE(part_str,'(I2)') jv
5043             IF (jv < 10) part_str(1:1) = '0'
5044             CALL histdef (hist_id_stom, &
5045                  & TRIM("totporO2_soil_"//part_str(1:LEN_TRIM(part_str))), &
5046                  & TRIM("    "), &
5047                  & TRIM("    "), iim,jjm, hist_hori_id, &
5048                  & ndeep, 1, ndeep, hist_stomate_deepsoil,32, ave(5), dt,hist_dt)
5049          END DO
5050
5051          DO jv = 1, nvm
5052             WRITE(part_str,'(I2)') jv
5053             IF (jv < 10) part_str(1:1) = '0'
5054             CALL histdef (hist_id_stom, &
5055                  & TRIM("diffO2_soil_"//part_str(1:LEN_TRIM(part_str))), &
5056                  & TRIM("    "), &
5057                  & TRIM("    "), iim,jjm, hist_hori_id, &
5058                  & ndeep, 1, ndeep, hist_stomate_deepsoil,32, ave(5), dt,hist_dt)
5059          END DO
5060
5061          DO jv = 1, nvm
5062             WRITE(part_str,'(I2)') jv
5063             IF (jv < 10) part_str(1:1) = '0'
5064             CALL histdef (hist_id_stom, &
5065                  & TRIM("alphaO2_soil_"//part_str(1:LEN_TRIM(part_str))), &
5066                  & TRIM("    "), &
5067                  & TRIM("    "), iim,jjm, hist_hori_id, &
5068                  & ndeep, 1, ndeep, hist_stomate_deepsoil,32, ave(5), dt,hist_dt)
5069          END DO
5070
5071          DO jv = 1, nvm
5072             WRITE(part_str,'(I2)') jv
5073             IF (jv < 10) part_str(1:1) = '0'
5074             CALL histdef (hist_id_stom, &
5075                  & TRIM("betaO2_soil_"//part_str(1:LEN_TRIM(part_str))), &
5076                  & TRIM("    "), &
5077                  & TRIM("    "), iim,jjm, hist_hori_id, &
5078                  & ndeep, 1, ndeep, hist_stomate_deepsoil,32, ave(5), dt,hist_dt)
5079          END DO
5080          DO jv = 1, nvm
5081             WRITE(part_str,'(I2)') jv
5082             IF (jv < 10) part_str(1:1) = '0'
5083             CALL histdef (hist_id_stom, &
5084                  & TRIM("totporCH4_soil_"//part_str(1:LEN_TRIM(part_str))), &
5085                  & TRIM("    "), &
5086                  & TRIM("    "), iim,jjm, hist_hori_id, &
5087                  & ndeep, 1, ndeep, hist_stomate_deepsoil,32, ave(5), dt,hist_dt)
5088          END DO
5089
5090          DO jv = 1, nvm
5091             WRITE(part_str,'(I2)') jv
5092             IF (jv < 10) part_str(1:1) = '0'
5093             CALL histdef (hist_id_stom, &
5094                  & TRIM("diffCH4_soil_"//part_str(1:LEN_TRIM(part_str))), &
5095                  & TRIM("    "), &
5096                  & TRIM("    "), iim,jjm, hist_hori_id, &
5097                  & ndeep, 1, ndeep, hist_stomate_deepsoil,32, ave(5), dt,hist_dt)
5098          END DO
5099
5100          DO jv = 1, nvm
5101             WRITE(part_str,'(I2)') jv
5102             IF (jv < 10) part_str(1:1) = '0'
5103             CALL histdef (hist_id_stom, &
5104                  & TRIM("alphaCH4_soil_"//part_str(1:LEN_TRIM(part_str))), &
5105                  & TRIM("    "), &
5106                  & TRIM("    "), iim,jjm, hist_hori_id, &
5107                  & ndeep, 1, ndeep, hist_stomate_deepsoil,32, ave(5), dt,hist_dt)
5108          END DO
5109          DO jv = 1, nvm
5110             WRITE(part_str,'(I2)') jv
5111             IF (jv < 10) part_str(1:1) = '0'
5112             CALL histdef (hist_id_stom, &
5113                  & TRIM("betaCH4_soil_"//part_str(1:LEN_TRIM(part_str))), &
5114                  & TRIM("    "), &
5115                  & TRIM("    "), iim,jjm, hist_hori_id, &
5116                  & ndeep, 1, ndeep, hist_stomate_deepsoil,32, ave(5), dt, hist_dt)
5117          END DO
5118       ENDIF
5119
5120       call histdef (hist_id_stom, &
5121            & trim("deepC_a_pftmean"), &
5122            & trim("active pool deep soil (permafrost) carbon, mean of all PFTs"), &
5123            & trim("gC/m**3   "), iim,jjm, hist_hori_id, &
5124            & ndeep, 1, ndeep, hist_stomate_deepsoil,32, ave(5), dt, hist_dt)
5125       call histdef (hist_id_stom, &
5126            & trim("deepC_s_pftmean"), &
5127            & trim("slow pool deep soil (permafrost) carbon, mean of all PFTs"), &
5128            & trim("gC/m**3   "), iim,jjm, hist_hori_id, &
5129            & ndeep, 1, ndeep, hist_stomate_deepsoil,32, ave(5), dt, hist_dt)
5130       call histdef (hist_id_stom, &
5131            & trim("deepC_p_pftmean"), &
5132            & trim("passive pool deep soil (permafrost) carbon, mean of all PFTs"),&
5133            & trim("gC/m**3   "), iim,jjm, hist_hori_id, &
5134            & ndeep, 1, ndeep, hist_stomate_deepsoil,32, ave(5), dt, hist_dt)
5135
5136       CALL histdef (hist_id_stom, &
5137            &               TRIM("fluxCH4           "), &
5138            &               TRIM("   "), &
5139            &               TRIM("gCH4/m**2/day   "), iim,jjm, hist_hori_id, &
5140            &               nvm, 1, nvm, hist_PFTaxis_id,32, ave(5), dt,hist_dt)
5141       CALL histdef (hist_id_stom, &
5142            &               TRIM("febul           "), &
5143            &               TRIM("   "), &
5144            &               TRIM("gCH4/m**2/day   "), iim,jjm, hist_hori_id, &
5145            &               nvm, 1, nvm, hist_PFTaxis_id,32, ave(5), dt,hist_dt)
5146       CALL histdef (hist_id_stom, &
5147            &               TRIM("flupmt           "), &
5148            &               TRIM("   "), &
5149            &               TRIM("gCH4/m**2/day   "), iim,jjm, hist_hori_id, &
5150            &               nvm, 1, nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
5151       CALL histdef (hist_id_stom, &
5152            &               TRIM("alt           "), &
5153            &               TRIM("active layer thickness   "), &
5154            &               TRIM("m   "), iim,jjm, hist_hori_id, &
5155            &               nvm, 1, nvm, hist_PFTaxis_id,32, ave(5), dt,hist_dt)
5156       CALL histdef (hist_id_stom, &
5157            &               TRIM("altmax           "), &
5158            &               TRIM("max annual alt   "), &
5159            &               TRIM("m   "), iim,jjm, hist_hori_id, &
5160            &               nvm, 1, nvm, hist_PFTaxis_id,32, ave(5), dt,hist_dt)
5161       CALL histdef (hist_id_stom, &
5162            &               TRIM("sfluxCH4_deep           "), &
5163            &               TRIM("total surface CH4 flux   "), &
5164            &               TRIM("gCH4/m**2/sec   "), iim,jjm, hist_hori_id, &
5165            &               1, 1, 1, -99,32, ave(5), dt, hist_dt)
5166       CALL histdef (hist_id_stom, &
5167            &               TRIM("sfluxCO2_deep           "), &
5168            &               TRIM("total surface CO2 C flux   "), &
5169            &               TRIM("gC/m**2/sec   "), iim,jjm, hist_hori_id, &
5170            &               1, 1, 1, -99,32, ave(5), dt, hist_dt)
5171
5172       CALL histdef (hist_id_stom, &
5173            &               TRIM("z_organic           "), &
5174            &               TRIM("depth of organic soil   "), &
5175            &               TRIM("m   "), iim,jjm, hist_hori_id, &
5176            &               1, 1, 1, -99,32, 'once(scatter(X))', dt, hist_dt)
5177       CALL histdef (hist_id_stom, &
5178            &               TRIM("tsurf          "), &
5179            &               TRIM("surface temp  "), &
5180            &               TRIM("K  "), iim,jjm, hist_hori_id, &
5181            &               1, 1, 1, -99,32, ave(5), dt, hist_dt)
5182
5183       CALL histdef (hist_id_stom, &
5184            &               TRIM("pb          "), &
5185            &               TRIM("surface pressure  "), &
5186            &               TRIM("pa   "), iim,jjm, hist_hori_id, &
5187            &               1, 1, 1, -99,32, ave(5), dt, hist_dt)
5188
5189       CALL histdef (hist_id_stom, &
5190            &               TRIM("mu_soil          "), &
5191            &               TRIM("mu_soil  "), &
5192            &               TRIM("   "), iim,jjm, hist_hori_id, &
5193            &               1, 1, 1, -99,32, ave(5), dt, hist_dt)
5194
5195    !spitfire
5196    ! Fire fraction from spitfire
5197    CALL histdef (hist_id_stom, &
5198         &               TRIM("FIREFRAC_SPITFIRE   "), &
5199         &               TRIM("Fire fraction on ground by spitfire               "), &
5200         &               TRIM("1/day               "), iim,jjm, hist_hori_id, &
5201         &               1,1,1, -99,32, ave(5), dt, hist_dt)
5202
5203   ! fire danger index                         
5204   CALL histdef (hist_id_stom, &
5205         &               TRIM("D_FDI            "), &
5206         &               TRIM("daily fire danger index    "), &
5207         &               TRIM("1/day       "), iim,jjm, hist_hori_id, &
5208         &               1,1,1, -99,32, ave(5), dt, hist_dt)
5209
5210   ! fire danger index                         
5211   CALL histdef (hist_id_stom, &
5212         &               TRIM("ROS_F            "), &
5213         &               TRIM("forward fire spread rate    "), &
5214         &               TRIM("m/min       "), iim,jjm, hist_hori_id, &
5215         &               1,1,1, -99,32, ave(5), dt, hist_dt)
5216       
5217   ! number of fires                       
5218   CALL histdef (hist_id_stom, &
5219         &               TRIM("D_NUMFIRE            "), &
5220         &               TRIM("daily number of fires    "), &
5221         &               TRIM("1/ha/day       "), iim,jjm, hist_hori_id, &
5222         &               1,1,1, -99,32, ave(5), dt, hist_dt)
5223       
5224   ! number of fires by lightning
5225   CALL histdef (hist_id_stom, &
5226         &               TRIM("LIGHTN_NUMFIRE            "), &
5227         &               TRIM("daily number of fires by lightning   "), &
5228         &               TRIM("1/day       "), iim,jjm, hist_hori_id, &
5229         &               1,1,1, -99,32, ave(5), dt, hist_dt)
5230
5231   ! number of fires by human
5232   CALL histdef (hist_id_stom, &
5233         &               TRIM("HUMAN_NUMFIRE            "), &
5234         &               TRIM("daily number of fires by human   "), &
5235         &               TRIM("1/day       "), iim,jjm, hist_hori_id, &
5236         &               1,1,1, -99,32, ave(5), dt, hist_dt)
5237
5238   ! area burnt                       
5239   CALL histdef (hist_id_stom, &
5240         &               TRIM("D_AREA_BURNT            "), &
5241         &               TRIM("daily area burnt    "), &
5242         &               TRIM("ha/day       "), iim,jjm, hist_hori_id, &
5243         &               1,1,1, -99,32, ave(5), dt, hist_dt)
5244
5245   !Escape area burnt                       
5246   CALL histdef (hist_id_stom, &
5247         &               TRIM("BA_ESCAPE            "), &
5248         &               TRIM("Escaped area burnt    "), &
5249         &               TRIM("ha/day       "), iim,jjm, hist_hori_id, &
5250         &               1,1,1, -99,32, ave(5), dt, hist_dt)
5251
5252   ! observed burned area                       
5253   CALL histdef (hist_id_stom, &
5254         &               TRIM("OBSERVED_BA            "), &
5255         &               TRIM("observed burned area    "), &
5256         &               TRIM("ha/day       "), iim,jjm, hist_hori_id, &
5257         &               1,1,1, -99,32, ave(5), dt, hist_dt)
5258
5259   ! number of fire days
5260   CALL histdef (hist_id_stom, &
5261         &               TRIM("FIRE_NUMDAY            "), &
5262         &               TRIM("Number of days burned since beginning of year"), &
5263         &               TRIM("day       "), iim,jjm, hist_hori_id, &
5264         &               1,1,1, -99,32, ave(5), dt, hist_dt)
5265
5266   ! crown_consump         
5267   CALL histdef (hist_id_stom, &
5268         &               TRIM("CROWN_CONSUMP            "), &
5269         &               TRIM("C emission from ground litter and grass leaf/fruit burnning    "), &
5270         &               TRIM("gC/m**2/day       "), iim,jjm, hist_hori_id, &
5271         &               1,1,1, -99,32, ave(5), dt, hist_dt)
5272   
5273   ! litter_consump         
5274   CALL histdef (hist_id_stom, &
5275         &               TRIM("LITTER_CONSUMP            "), &
5276         &               TRIM("C emission from ground litter and grass leaf/fruit burnning    "), &
5277         &               TRIM("gC/m**2/day       "), iim,jjm, hist_hori_id, &
5278         &               1,1,1, -99,32, ave(5), dt, hist_dt)
5279   
5280   ! total lightning ignition
5281   CALL histdef (hist_id_stom, &
5282         &               TRIM("LIGHTN_IGN_TOTAL       "), &
5283         &               TRIM("Lightning ignitions    "), &
5284         &               TRIM("1/km**2/day       "), iim,jjm, hist_hori_id, &
5285         &               1,1,1, -99,32, ave(5), dt, hist_dt)
5286
5287   ! lightning ignition
5288   CALL histdef (hist_id_stom, &
5289         &               TRIM("LIGHTN_IGN            "), &
5290         &               TRIM("Number of fires contributed by lightning ignitions    "), &
5291         &               TRIM("1/km**2/day       "), iim,jjm, hist_hori_id, &
5292         &               1,1,1, -99,32, ave(5), dt, hist_dt)
5293
5294   ! human ignitions
5295   CALL histdef (hist_id_stom, &
5296         &               TRIM("HUMAN_IGN            "), &
5297         &               TRIM("Number of fires contributed by human ignitions    "), &
5298         &               TRIM("1/km**2/day       "), iim,jjm, hist_hori_id, &
5299         &               1,1,1, -99,32, ave(5), dt, hist_dt)
5300
5301   ! trace gas emissions
5302   CALL histdef (hist_id_stom, &
5303         &               TRIM("TRACE_GAS_CO2            "), &
5304         &               TRIM("CO2 emissions by fire    "), &
5305         &               TRIM("g/m**2/day       "), iim,jjm, hist_hori_id, &
5306         &               1,1,1, -99,32, ave(5), dt, hist_dt)
5307       
5308   CALL histdef (hist_id_stom, &
5309         &               TRIM("TRACE_GAS_CO            "), &
5310         &               TRIM("CO emissions by fire   "), &
5311         &               TRIM("g/m**2/day       "), iim,jjm, hist_hori_id, &
5312         &               1,1,1, -99,32, ave(5), dt, hist_dt)
5313   CALL histdef (hist_id_stom, &
5314         &               TRIM("TRACE_GAS_CH4            "), &
5315         &               TRIM("CH4 emissions by fire   "), &
5316         &               TRIM("g/m**2/day       "), iim,jjm, hist_hori_id, &
5317         &               1,1,1, -99,32, ave(5), dt, hist_dt)
5318   CALL histdef (hist_id_stom, &
5319         &               TRIM("TRACE_GAS_VOC            "), &
5320         &               TRIM("VOC emissions by fire   "), &
5321         &               TRIM("g/m**2/day       "), iim,jjm, hist_hori_id, &
5322         &               1,1,1, -99,32, ave(5), dt, hist_dt)
5323   CALL histdef (hist_id_stom, &
5324         &               TRIM("TRACE_GAS_TPM            "), &
5325         &               TRIM("TPM emissions by fire   "), &
5326         &               TRIM("g/m**2/day       "), iim,jjm, hist_hori_id, &
5327         &               1,1,1, -99,32, ave(5), dt, hist_dt)
5328   CALL histdef (hist_id_stom, &
5329         &               TRIM("TRACE_GAS_NOx            "), &
5330         &               TRIM("NOx emissions by fire   "), &
5331         &               TRIM("g/m**2/day       "), iim,jjm, hist_hori_id, &
5332         &               1,1,1, -99,32, ave(5), dt, hist_dt)
5333
5334   CALL histdef (hist_id_stom, &
5335        &               TRIM("bafrac_deforest     "), &
5336        &               TRIM("Deforestation fire burned fraction      "), &
5337        &               TRIM("-                   "), iim,jjm, hist_hori_id, &
5338        &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
5339
5340   CALL histdef (hist_id_stom, &
5341        &               TRIM("bafrac_deforest_accu     "), &
5342        &               TRIM("Cumulative deforestation fire burned fraction      "), &
5343        &               TRIM("-                   "), iim,jjm, hist_hori_id, &
5344        &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
5345
5346
5347!! Chao test LCC
5348
5349       ! Leaf mass                                         
5350       CALL histdef (hist_id_stom, &
5351            &               TRIM("DefLitSurplus"), &
5352            &               TRIM("                                         "), &
5353            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
5354            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
5355
5356       ! Leaf mass                                         
5357       CALL histdef (hist_id_stom, &
5358            &               TRIM("DefBioSurplus"), &
5359            &               TRIM("                                         "), &
5360            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
5361            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
5362
5363
5364
5365       CALL histdef (hist_id_stom, &
5366            &               TRIM("AccEDlitSTR"), &
5367            &               TRIM("                                         "), &
5368            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
5369            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
5370       CALL histdef (hist_id_stom, &
5371            &               TRIM("AccEDlitMET"), &
5372            &               TRIM("                                         "), &
5373            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
5374            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
5375       CALL histdef (hist_id_stom, &
5376            &               TRIM("EDlitSTR"), &
5377            &               TRIM("                                         "), &
5378            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
5379            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
5380       CALL histdef (hist_id_stom, &
5381            &               TRIM("EDlitMET"), &
5382            &               TRIM("                                         "), &
5383            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
5384            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
5385
5386
5387!!Surplus and deficit
5388       CALL histdef (hist_id_stom, &
5389            &               TRIM("DefiLitSTR"), &
5390            &               TRIM("                                         "), &
5391            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
5392            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
5393       CALL histdef (hist_id_stom, &
5394            &               TRIM("DefiLitMET"), &
5395            &               TRIM("                                         "), &
5396            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
5397            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
5398       CALL histdef (hist_id_stom, &
5399            &               TRIM("DefiBioLEAF"), &
5400            &               TRIM("                                         "), &
5401            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
5402            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
5403       CALL histdef (hist_id_stom, &
5404            &               TRIM("DefiBioRESERVE"), &
5405            &               TRIM("                                         "), &
5406            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
5407            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
5408       CALL histdef (hist_id_stom, &
5409            &               TRIM("DefiBioFRUIT"), &
5410            &               TRIM("                                         "), &
5411            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
5412            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
5413       CALL histdef (hist_id_stom, &
5414            &               TRIM("DefiBioSapABOVE"), &
5415            &               TRIM("                                         "), &
5416            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
5417            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
5418       CALL histdef (hist_id_stom, &
5419            &               TRIM("DefiBioHeartABOVE"), &
5420            &               TRIM("                                         "), &
5421            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
5422            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
5423       CALL histdef (hist_id_stom, &
5424            &               TRIM("DefiBioSapBELOW"), &
5425            &               TRIM("                                         "), &
5426            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
5427            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
5428       CALL histdef (hist_id_stom, &
5429            &               TRIM("DefiBioHeartBELOW"), &
5430            &               TRIM("                                         "), &
5431            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
5432            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
5433       CALL histdef (hist_id_stom, &
5434            &               TRIM("DefiBioROOT"), &
5435            &               TRIM("                                         "), &
5436            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
5437            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
5438
5439       CALL histdef (hist_id_stom, &
5440            &               TRIM("SurpLitSTR"), &
5441            &               TRIM("                                         "), &
5442            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
5443            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
5444       CALL histdef (hist_id_stom, &
5445            &               TRIM("SurpLitMET"), &
5446            &               TRIM("                                         "), &
5447            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
5448            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
5449       CALL histdef (hist_id_stom, &
5450            &               TRIM("SurpBioLEAF"), &
5451            &               TRIM("                                         "), &
5452            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
5453            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
5454       CALL histdef (hist_id_stom, &
5455            &               TRIM("SurpBioRESERVE"), &
5456            &               TRIM("                                         "), &
5457            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
5458            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
5459       CALL histdef (hist_id_stom, &
5460            &               TRIM("SurpBioFRUIT"), &
5461            &               TRIM("                                         "), &
5462            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
5463            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
5464       CALL histdef (hist_id_stom, &
5465            &               TRIM("SurpBioSapABOVE"), &
5466            &               TRIM("                                         "), &
5467            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
5468            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
5469       CALL histdef (hist_id_stom, &
5470            &               TRIM("SurpBioHeartABOVE"), &
5471            &               TRIM("                                         "), &
5472            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
5473            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
5474       CALL histdef (hist_id_stom, &
5475            &               TRIM("SurpBioSapBELOW"), &
5476            &               TRIM("                                         "), &
5477            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
5478            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
5479       CALL histdef (hist_id_stom, &
5480            &               TRIM("SurpBioHeartBELOW"), &
5481            &               TRIM("                                         "), &
5482            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
5483            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
5484       CALL histdef (hist_id_stom, &
5485            &               TRIM("SurpBioROOT"), &
5486            &               TRIM("                                         "), &
5487            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
5488            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
5489
5490
5491
5492       CALL histdef (hist_id_stom, &
5493            &               TRIM("EDbioLEAF"), &
5494            &               TRIM("                                         "), &
5495            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
5496            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
5497       CALL histdef (hist_id_stom, &
5498            &               TRIM("EDbioRESERVE"), &
5499            &               TRIM("                                         "), &
5500            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
5501            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
5502       CALL histdef (hist_id_stom, &
5503            &               TRIM("EDbioFRUIT"), &
5504            &               TRIM("                                         "), &
5505            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
5506            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
5507       CALL histdef (hist_id_stom, &
5508            &               TRIM("EDbioSapABOVE"), &
5509            &               TRIM("                                         "), &
5510            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
5511            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
5512       CALL histdef (hist_id_stom, &
5513            &               TRIM("EDbioHeartABOVE"), &
5514            &               TRIM("                                         "), &
5515            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
5516            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
5517       CALL histdef (hist_id_stom, &
5518            &               TRIM("EDbioSapBELOW"), &
5519            &               TRIM("                                         "), &
5520            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
5521            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
5522       CALL histdef (hist_id_stom, &
5523            &               TRIM("EDbioHeartBELOW"), &
5524            &               TRIM("                                         "), &
5525            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
5526            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
5527       CALL histdef (hist_id_stom, &
5528            &               TRIM("EDbioROOT"), &
5529            &               TRIM("                                         "), &
5530            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
5531            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
5532       CALL histdef (hist_id_stom, &
5533            &               TRIM("AccEDbioLEAF"), &
5534            &               TRIM("                                         "), &
5535            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
5536            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
5537       CALL histdef (hist_id_stom, &
5538            &               TRIM("AccEDbioRESERVE"), &
5539            &               TRIM("                                         "), &
5540            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
5541            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
5542       CALL histdef (hist_id_stom, &
5543            &               TRIM("AccEDbioFRUIT"), &
5544            &               TRIM("                                         "), &
5545            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
5546            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
5547       CALL histdef (hist_id_stom, &
5548            &               TRIM("AccEDbioSapABOVE"), &
5549            &               TRIM("                                         "), &
5550            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
5551            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
5552       CALL histdef (hist_id_stom, &
5553            &               TRIM("AccEDbioHeartABOVE"), &
5554            &               TRIM("                                         "), &
5555            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
5556            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
5557       CALL histdef (hist_id_stom, &
5558            &               TRIM("AccEDbioSapBELOW"), &
5559            &               TRIM("                                         "), &
5560            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
5561            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
5562       CALL histdef (hist_id_stom, &
5563            &               TRIM("AccEDbioHeartBELOW"), &
5564            &               TRIM("                                         "), &
5565            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
5566            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
5567       CALL histdef (hist_id_stom, &
5568            &               TRIM("AccEDbioROOT"), &
5569            &               TRIM("                                         "), &
5570            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
5571            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
5572
5573       CALL histdef (hist_id_stom, &
5574            &               TRIM("LCC"), &
5575            &               TRIM("                                         "), &
5576            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
5577            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
5578
5579   CALL histdef (hist_id_stom, &
5580         &               TRIM("dilu_lit_met            "), &
5581         &               TRIM(""), &
5582         &               TRIM(""), iim,jjm, hist_hori_id, &
5583         &               1,1,1, -99,32, ave(5), dt, hist_dt)
5584   CALL histdef (hist_id_stom, &
5585         &               TRIM("dilu_lit_str            "), &
5586         &               TRIM(""), &
5587         &               TRIM(""), iim,jjm, hist_hori_id, &
5588         &               1,1,1, -99,32, ave(5), dt, hist_dt)
5589
5590
5591!for test in spitfire
5592   CALL histdef (hist_id_stom, &
5593         &               TRIM("alpha_fuel            "), &
5594         &               TRIM(""), &
5595         &               TRIM(""), iim,jjm, hist_hori_id, &
5596         &               1,1,1, -99,32, ave(5), dt, hist_dt)
5597   CALL histdef (hist_id_stom, &
5598         &               TRIM("char_moistfactor            "), &
5599         &               TRIM(""), &
5600         &               TRIM(""), iim,jjm, hist_hori_id, &
5601         &               1,1,1, -99,32, ave(5), dt, hist_dt)
5602   CALL histdef (hist_id_stom, &
5603         &               TRIM("ni_acc            "), &
5604         &               TRIM(""), &
5605         &               TRIM(""), iim,jjm, hist_hori_id, &
5606         &               1,1,1, -99,32, ave(5), dt, hist_dt)
5607   CALL histdef (hist_id_stom, &
5608         &               TRIM("t2m_min_daily            "), &
5609         &               TRIM(""), &
5610         &               TRIM(""), iim,jjm, hist_hori_id, &
5611         &               1,1,1, -99,32, ave(5), dt, hist_dt)
5612   CALL histdef (hist_id_stom, &
5613         &               TRIM("t2m_max_daily            "), &
5614         &               TRIM(""), &
5615         &               TRIM(""), iim,jjm, hist_hori_id, &
5616         &               1,1,1, -99,32, ave(5), dt, hist_dt)
5617   CALL histdef (hist_id_stom, &
5618         &               TRIM("precip_daily            "), &
5619         &               TRIM(""), &
5620         &               TRIM(""), iim,jjm, hist_hori_id, &
5621         &               1,1,1, -99,32, ave(5), dt, hist_dt)
5622
5623   CALL histdef (hist_id_stom, &
5624         &               TRIM("topsoilhum_daily            "), &
5625         &               TRIM("daily top soil layer humidity"), &
5626         &               TRIM(""), iim,jjm, hist_hori_id, &
5627         &               1,1,1, -99,32, ave(5), dt, hist_dt)
5628
5629   CALL histdef (hist_id_stom, &
5630         &               TRIM("moist_extinction            "), &
5631         &               TRIM("combined livegrass and dead fuel moisture of extinction"), &
5632         &               TRIM(""), iim,jjm, hist_hori_id, &
5633         &               1,1,1, -99,32, ave(5), dt, hist_dt)
5634
5635   CALL histdef (hist_id_stom, &
5636         &               TRIM("dfm_1hr            "), &
5637         &               TRIM("daily 1hr fule moisture as influenced by NI"), &
5638         &               TRIM(""), iim,jjm, hist_hori_id, &
5639         &               1,1,1, -99,32, ave(5), dt, hist_dt)
5640
5641   CALL histdef (hist_id_stom, &
5642         &               TRIM("dfm_lg            "), &
5643         &               TRIM("daily live grass fuel moisture as influenced by top soil layer humidity"), &
5644         &               TRIM(""), iim,jjm, hist_hori_id, &
5645         &               1,1,1, -99,32, ave(5), dt, hist_dt)
5646
5647   CALL histdef (hist_id_stom, &
5648         &               TRIM("dfm_lg_d1hr            "), &
5649         &               TRIM("combined livegrass and 1hr-fuel fuel moisture"), &
5650         &               TRIM(""), iim,jjm, hist_hori_id, &
5651         &               1,1,1, -99,32, ave(5), dt, hist_dt)
5652
5653   CALL histdef (hist_id_stom, &
5654         &               TRIM("dfm            "), &
5655         &               TRIM("daily dead fuel moisture"), &
5656         &               TRIM(""), iim,jjm, hist_hori_id, &
5657         &               1,1,1, -99,32, ave(5), dt, hist_dt)
5658
5659   CALL histdef (hist_id_stom, &
5660         &               TRIM("wetness            "), &
5661         &               TRIM("wetness"), &
5662         &               TRIM(""), iim,jjm, hist_hori_id, &
5663         &               1,1,1, -99,32, ave(5), dt, hist_dt)
5664
5665   CALL histdef (hist_id_stom, &
5666         &               TRIM("wetness_lg            "), &
5667         &               TRIM(""), &
5668         &               TRIM(""), iim,jjm, hist_hori_id, &
5669         &               1,1,1, -99,32, ave(5), dt, hist_dt)
5670
5671   CALL histdef (hist_id_stom, &
5672         &               TRIM("wetness_1hr           "), &
5673         &               TRIM(""), &
5674         &               TRIM(""), iim,jjm, hist_hori_id, &
5675         &               1,1,1, -99,32, ave(5), dt, hist_dt)
5676
5677   CALL histdef (hist_id_stom, &
5678         &               TRIM("fire_durat            "), &
5679         &               TRIM(""), &
5680         &               TRIM(""), iim,jjm, hist_hori_id, &
5681         &               1,1,1, -99,32, ave(5), dt, hist_dt)
5682   CALL histdef (hist_id_stom, &
5683         &               TRIM("ros_b            "), &
5684         &               TRIM(""), &
5685         &               TRIM(""), iim,jjm, hist_hori_id, &
5686         &               1,1,1, -99,32, ave(5), dt, hist_dt)
5687   CALL histdef (hist_id_stom, &
5688         &               TRIM("ros_f            "), &
5689         &               TRIM(""), &
5690         &               TRIM(""), iim,jjm, hist_hori_id, &
5691         &               1,1,1, -99,32, ave(5), dt, hist_dt)
5692   CALL histdef (hist_id_stom, &
5693         &               TRIM("wind_speed            "), &
5694         &               TRIM(""), &
5695         &               TRIM(""), iim,jjm, hist_hori_id, &
5696         &               1,1,1, -99,32, ave(5), dt, hist_dt)
5697
5698   CALL histdef (hist_id_stom, &
5699         &               TRIM("cf_lg            "), &
5700         &               TRIM(""), &
5701         &               TRIM(""), iim,jjm, hist_hori_id, &
5702         &               1,1,1, -99,32, ave(5), dt, hist_dt)
5703
5704
5705   CALL histdef (hist_id_stom, &
5706         &               TRIM("cf_1hr            "), &
5707         &               TRIM(""), &
5708         &               TRIM(""), iim,jjm, hist_hori_id, &
5709         &               1,1,1, -99,32, ave(5), dt, hist_dt)
5710
5711   CALL histdef (hist_id_stom, &
5712         &               TRIM("cf_10hr            "), &
5713         &               TRIM(""), &
5714         &               TRIM(""), iim,jjm, hist_hori_id, &
5715         &               1,1,1, -99,32, ave(5), dt, hist_dt)
5716
5717   CALL histdef (hist_id_stom, &
5718         &               TRIM("cf_100hr            "), &
5719         &               TRIM(""), &
5720         &               TRIM(""), iim,jjm, hist_hori_id, &
5721         &               1,1,1, -99,32, ave(5), dt, hist_dt)
5722
5723   CALL histdef (hist_id_stom, &
5724         &               TRIM("cf_1000hr            "), &
5725         &               TRIM(""), &
5726         &               TRIM(""), iim,jjm, hist_hori_id, &
5727         &               1,1,1, -99,32, ave(5), dt, hist_dt)
5728
5729   CALL histdef (hist_id_stom, &
5730         &               TRIM("cf_coarse            "), &
5731         &               TRIM(""), &
5732         &               TRIM(""), iim,jjm, hist_hori_id, &
5733         &               1,1,1, -99,32, ave(5), dt, hist_dt)
5734
5735   CALL histdef (hist_id_stom, &
5736         &               TRIM("cf_fine            "), &
5737         &               TRIM(""), &
5738         &               TRIM(""), iim,jjm, hist_hori_id, &
5739         &               1,1,1, -99,32, ave(5), dt, hist_dt)
5740
5741   CALL histdef (hist_id_stom, &
5742         &               TRIM("cf_ave            "), &
5743         &               TRIM(""), &
5744         &               TRIM(""), iim,jjm, hist_hori_id, &
5745         &               1,1,1, -99,32, ave(5), dt, hist_dt)
5746!spitfiretest
5747!    CALL histdef (hist_id_stom, &
5748!         &               TRIM("fuel_nlitt_total_pft_met       "), &
5749!         &               TRIM("                    "), &
5750!         &               TRIM("gC/m^2/pft          "), iim,jjm, hist_hori_id, &
5751!         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
5752!
5753!    CALL histdef (hist_id_stom, &
5754!         &               TRIM("fuel_nlitt_total_pft_str       "), &
5755!         &               TRIM("                    "), &
5756!         &               TRIM("gC/m^2/pft          "), iim,jjm, hist_hori_id, &
5757!         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
5758!
5759    CALL histdef (hist_id_stom, &
5760         &               TRIM("fuel_1hr_met_b       "), &
5761         &               TRIM("                    "), &
5762         &               TRIM("gC/m^2/pft          "), iim,jjm, hist_hori_id, &
5763         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
5764
5765    CALL histdef (hist_id_stom, &
5766         &               TRIM("fuel_1hr_str_b       "), &
5767         &               TRIM("                    "), &
5768         &               TRIM("gC/m^2/pft          "), iim,jjm, hist_hori_id, &
5769         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
5770
5771    CALL histdef (hist_id_stom, &
5772         &               TRIM("fuel_10hr_met_b       "), &
5773         &               TRIM("                    "), &
5774         &               TRIM("gC/m^2/pft          "), iim,jjm, hist_hori_id, &
5775         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
5776
5777    CALL histdef (hist_id_stom, &
5778         &               TRIM("fuel_10hr_str_b       "), &
5779         &               TRIM("                    "), &
5780         &               TRIM("gC/m^2/pft          "), iim,jjm, hist_hori_id, &
5781         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
5782
5783    CALL histdef (hist_id_stom, &
5784         &               TRIM("fuel_100hr_met_b       "), &
5785         &               TRIM("                    "), &
5786         &               TRIM("gC/m^2/pft          "), iim,jjm, hist_hori_id, &
5787         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
5788
5789    CALL histdef (hist_id_stom, &
5790         &               TRIM("fuel_100hr_str_b       "), &
5791         &               TRIM("                    "), &
5792         &               TRIM("gC/m^2/pft          "), iim,jjm, hist_hori_id, &
5793         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
5794
5795    CALL histdef (hist_id_stom, &
5796         &               TRIM("fuel_1000hr_met_b       "), &
5797         &               TRIM("                    "), &
5798         &               TRIM("gC/m^2/pft          "), iim,jjm, hist_hori_id, &
5799         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
5800
5801    CALL histdef (hist_id_stom, &
5802         &               TRIM("fuel_1000hr_str_b       "), &
5803         &               TRIM("                    "), &
5804         &               TRIM("gC/m^2/pft          "), iim,jjm, hist_hori_id, &
5805         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
5806!endspittest
5807
5808    CALL histdef (hist_id_stom, &
5809         &               TRIM("fc_1hr_carbon       "), &
5810         &               TRIM("                    "), &
5811         &               TRIM("gC/m^2/pft          "), iim,jjm, hist_hori_id, &
5812         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
5813
5814    CALL histdef (hist_id_stom, &
5815         &               TRIM("fc_10hr_carbon       "), &
5816         &               TRIM("                    "), &
5817         &               TRIM("gC/m^2/pft          "), iim,jjm, hist_hori_id, &
5818         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
5819
5820    CALL histdef (hist_id_stom, &
5821         &               TRIM("fc_100hr_carbon       "), &
5822         &               TRIM("                    "), &
5823         &               TRIM("gC/m^2/pft          "), iim,jjm, hist_hori_id, &
5824         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
5825
5826    CALL histdef (hist_id_stom, &
5827         &               TRIM("fc_1000hr_carbon       "), &
5828         &               TRIM("                    "), &
5829         &               TRIM("gC/m^2/pft          "), iim,jjm, hist_hori_id, &
5830         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
5831
5832    CALL histdef (hist_id_stom, &
5833         &               TRIM("fuel_1hr_met       "), &
5834         &               TRIM("                    "), &
5835         &               TRIM("gC/m^2/pft          "), iim,jjm, hist_hori_id, &
5836         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
5837
5838    CALL histdef (hist_id_stom, &
5839         &               TRIM("fuel_1hr_str       "), &
5840         &               TRIM("                    "), &
5841         &               TRIM("gC/m^2/pft          "), iim,jjm, hist_hori_id, &
5842         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
5843
5844    CALL histdef (hist_id_stom, &
5845         &               TRIM("fuel_10hr_met       "), &
5846         &               TRIM("                    "), &
5847         &               TRIM("gC/m^2/pft          "), iim,jjm, hist_hori_id, &
5848         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
5849
5850    CALL histdef (hist_id_stom, &
5851         &               TRIM("fuel_10hr_str       "), &
5852         &               TRIM("                    "), &
5853         &               TRIM("gC/m^2/pft          "), iim,jjm, hist_hori_id, &
5854         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
5855
5856    CALL histdef (hist_id_stom, &
5857         &               TRIM("fuel_100hr_met       "), &
5858         &               TRIM("                    "), &
5859         &               TRIM("gC/m^2/pft          "), iim,jjm, hist_hori_id, &
5860         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
5861
5862    CALL histdef (hist_id_stom, &
5863         &               TRIM("fuel_100hr_str       "), &
5864         &               TRIM("                    "), &
5865         &               TRIM("gC/m^2/pft          "), iim,jjm, hist_hori_id, &
5866         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
5867
5868    CALL histdef (hist_id_stom, &
5869         &               TRIM("fuel_1000hr_met       "), &
5870         &               TRIM("                    "), &
5871         &               TRIM("gC/m^2/pft          "), iim,jjm, hist_hori_id, &
5872         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
5873
5874    CALL histdef (hist_id_stom, &
5875         &               TRIM("fuel_1000hr_str       "), &
5876         &               TRIM("                    "), &
5877         &               TRIM("gC/m^2/pft          "), iim,jjm, hist_hori_id, &
5878         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
5879
5880    CALL histdef (hist_id_stom, &
5881         &               TRIM("sh       "), &
5882         &               TRIM("                    "), &
5883         &               TRIM("          "), iim,jjm, hist_hori_id, &
5884         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
5885    CALL histdef (hist_id_stom, &
5886         &               TRIM("ck       "), &
5887         &               TRIM("                    "), &
5888         &               TRIM("          "), iim,jjm, hist_hori_id, &
5889         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
5890
5891    CALL histdef (hist_id_stom, &
5892         &               TRIM("pm_ck       "), &
5893         &               TRIM("                    "), &
5894         &               TRIM("          "), iim,jjm, hist_hori_id, &
5895         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
5896    CALL histdef (hist_id_stom, &
5897         &               TRIM("pm_tau       "), &
5898         &               TRIM("                    "), &
5899         &               TRIM("          "), iim,jjm, hist_hori_id, &
5900         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
5901    CALL histdef (hist_id_stom, &
5902         &               TRIM("postf_mort       "), &
5903         &               TRIM("                    "), &
5904         &               TRIM("          "), iim,jjm, hist_hori_id, &
5905         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
5906
5907   CALL histdef (hist_id_stom, &
5908         &               TRIM("mean_fire_size_or            "), &
5909         &               TRIM("mean fire size before intensity correction"), &
5910         &               TRIM(""), iim,jjm, hist_hori_id, &
5911         &               1,1,1, -99,32, ave(5), dt, hist_dt)
5912
5913   CALL histdef (hist_id_stom, &
5914         &               TRIM("mean_fire_size            "), &
5915         &               TRIM("mean fire size after intensity correction"), &
5916         &               TRIM(""), iim,jjm, hist_hori_id, &
5917         &               1,1,1, -99,32, ave(5), dt, hist_dt)
5918
5919   CALL histdef (hist_id_stom, &
5920         &               TRIM("char_dens_fuel_ave            "), &
5921         &               TRIM(""), &
5922         &               TRIM(""), iim,jjm, hist_hori_id, &
5923         &               1,1,1, -99,32, ave(5), dt, hist_dt)
5924
5925   CALL histdef (hist_id_stom, &
5926         &               TRIM("sigma            "), &
5927         &               TRIM(""), &
5928         &               TRIM(""), iim,jjm, hist_hori_id, &
5929         &               1,1,1, -99,32, ave(5), dt, hist_dt)
5930
5931   CALL histdef (hist_id_stom, &
5932         &               TRIM("d_i_surface            "), &
5933         &               TRIM(""), &
5934         &               TRIM(""), iim,jjm, hist_hori_id, &
5935         &               1,1,1, -99,32, ave(5), dt, hist_dt)
5936
5937    CALL histdef (hist_id_stom, &
5938         &               TRIM("dead_fuel   "), &
5939         &               TRIM(""), &
5940         &               TRIM("               "), iim,jjm, hist_hori_id, &
5941         &               1,1,1, -99,32, ave(5), dt, hist_dt)
5942    CALL histdef (hist_id_stom, &
5943         &               TRIM("dead_fuel_all   "), &
5944         &               TRIM(""), &
5945         &               TRIM("               "), iim,jjm, hist_hori_id, &
5946         &               1,1,1, -99,32, ave(5), dt, hist_dt)
5947
5948
5949   !endspit
5950
5951   !glcc
5952       IF (use_age_class) THEN
5953         ! Loss of fraction of each PFT
5954         CALL histdef (hist_id_stom, &
5955              &               TRIM("glcc_pft            "), &
5956              &               TRIM("Loss of fraction in each PFT                      "), &
5957              &               TRIM("          "), iim,jjm, hist_hori_id, &
5958              &               nvm,1,nvm, hist_PFTaxis_id,32, 'once(scatter(X))', dt, hist_dt)
5959
5960         ! Loss of fraction of each PFT for foretry harvest
5961         CALL histdef (hist_id_stom, &
5962              &               TRIM("glcc_harvest        "), &
5963              &               TRIM("Loss of fraction due to forestry harvest in each PFT  "), &
5964              &               TRIM("          "), iim,jjm, hist_hori_id, &
5965              &               nvm,1,nvm, hist_PFTaxis_id,32, 'once(scatter(X))', dt, hist_dt)
5966
5967         CALL histdef (hist_id_stom, &
5968              &               TRIM("harvest_wood       "), &
5969              &               TRIM("harvest aboveground wood from forestry          "), &
5970              &               TRIM("gC/m**2/yr-1          "), iim,jjm, hist_hori_id, &
5971              &               1,1,1, -99,32, 'once(scatter(X))', dt, hist_dt)
5972
5973         ! Transition of each PFT to MTC
5974         DO jv = 1, nvmap
5975           WRITE(part_str,'(I2)') jv
5976           IF (jv < 10) part_str(1:1) = '0'
5977           CALL histdef (hist_id_stom, &
5978                & TRIM("glcc_pftmtc_"//part_str(1:LEN_TRIM(part_str))), &
5979                & TRIM("Transition of each PFT to MTC "//part_str(1:LEN_TRIM(part_str))), &
5980                & TRIM("          "), iim,jjm, hist_hori_id, &
5981                & nvm,1,nvm, hist_PFTaxis_id,32, 'once(scatter(X))', dt, hist_dt)
5982         END DO
5983
5984         ! Transition of each PFT to MTC
5985         DO jv = 1, nvmap
5986           WRITE(part_str,'(I2)') jv
5987           IF (jv < 10) part_str(1:1) = '0'
5988           CALL histdef (hist_id_stom, &
5989                & TRIM("glcc_pftmtc_H_"//part_str(1:LEN_TRIM(part_str))), &
5990                & TRIM("Transition of each PFT to MTC "//part_str(1:LEN_TRIM(part_str))), &
5991                & TRIM("          "), iim,jjm, hist_hori_id, &
5992                & nvm,1,nvm, hist_PFTaxis_id,32, 'once(scatter(X))', dt, hist_dt)
5993         END DO
5994
5995         ! Transition of each PFT to MTC
5996         DO jv = 1, nvmap
5997           WRITE(part_str,'(I2)') jv
5998           IF (jv < 10) part_str(1:1) = '0'
5999           CALL histdef (hist_id_stom, &
6000                & TRIM("glcc_pftmtc_SF_"//part_str(1:LEN_TRIM(part_str))), &
6001                & TRIM("Transition of each PFT to MTC "//part_str(1:LEN_TRIM(part_str))), &
6002                & TRIM("          "), iim,jjm, hist_hori_id, &
6003                & nvm,1,nvm, hist_PFTaxis_id,32, 'once(scatter(X))', dt, hist_dt)
6004         END DO
6005
6006         ! Transition of each PFT to MTC
6007         DO jv = 1, nvmap
6008           WRITE(part_str,'(I2)') jv
6009           IF (jv < 10) part_str(1:1) = '0'
6010           CALL histdef (hist_id_stom, &
6011                & TRIM("glcc_pftmtc_NPF_"//part_str(1:LEN_TRIM(part_str))), &
6012                & TRIM("Transition of each PFT to MTC "//part_str(1:LEN_TRIM(part_str))), &
6013                & TRIM("          "), iim,jjm, hist_hori_id, &
6014                & nvm,1,nvm, hist_PFTaxis_id,32, 'once(scatter(X))', dt, hist_dt)
6015         END DO
6016
6017         ! Real glcc matrix used
6018         CALL histdef (hist_id_stom, &
6019              &               TRIM("glccReal            "), &
6020              &               TRIM("The glcc matrix used in the gross LCC             "), &
6021              &               TRIM("          "), iim,jjm, hist_hori_id, &
6022              &               nvm,1,nvm, hist_PFTaxis_id,32, ave(1), dt, hist_dt)
6023
6024
6025         ! Real glcc matrix used
6026         CALL histdef (hist_id_stom, &
6027              &               TRIM("glccRealHarvest     "), &
6028              &               TRIM("The glcc matrix used in the gross LCC             "), &
6029              &               TRIM("          "), iim,jjm, hist_hori_id, &
6030              &               nvm,1,nvm, hist_PFTaxis_id,32, 'once(scatter(X))', dt, hist_dt)
6031
6032         ! Real glcc matrix used
6033         CALL histdef (hist_id_stom, &
6034              &               TRIM("glccRealSecShift    "), &
6035              &               TRIM("The glcc matrix used in the gross LCC             "), &
6036              &               TRIM("          "), iim,jjm, hist_hori_id, &
6037              &               nvm,1,nvm, hist_PFTaxis_id,32, 'once(scatter(X))', dt, hist_dt)
6038
6039         ! Real glcc matrix used
6040         CALL histdef (hist_id_stom, &
6041              &               TRIM("glccRealNetPriShift "), &
6042              &               TRIM("The glcc matrix used in the gross LCC             "), &
6043              &               TRIM("          "), iim,jjm, hist_hori_id, &
6044              &               nvm,1,nvm, hist_PFTaxis_id,32, 'once(scatter(X))', dt, hist_dt)
6045
6046         ! Real glcc matrix used
6047         CALL histdef (hist_id_stom, &
6048              &               TRIM("glccDefSecShift "), &
6049              &               TRIM("The glcc matrix used in the gross LCC             "), &
6050              &               TRIM("          "), iim,jjm, hist_hori_id, &
6051              &               nvm,1,nvm, hist_PFTaxis_id,32, 'once(scatter(X))', dt, hist_dt)
6052
6053         ! Real glcc matrix used
6054         CALL histdef (hist_id_stom, &
6055              &               TRIM("glccDefNetPriShift "), &
6056              &               TRIM("The glcc matrix used in the gross LCC             "), &
6057              &               TRIM("          "), iim,jjm, hist_hori_id, &
6058              &               nvm,1,nvm, hist_PFTaxis_id,32, 'once(scatter(X))', dt, hist_dt)
6059
6060         ! Increment deficit
6061         CALL histdef (hist_id_stom, &
6062              &               TRIM("IncreDeficit            "), &
6063              &               TRIM("Deficit in glcc, in same sequence as input transition matrix"), &
6064              &               TRIM("          "), iim,jjm, hist_hori_id, &
6065              &               nvm,1,nvm, hist_PFTaxis_id,32, 'once(scatter(X))', dt, hist_dt)
6066
6067         ! Deficit and compensation from forestry harvest
6068         CALL histdef (hist_id_stom, &
6069              &               TRIM("DefiComForHarvest       "), &
6070              &               TRIM("Deficit_pf2yf_final, Deficit_sf2yf_final, pf2yf_compen_sf2yf, sf2yf_compen_pf2yf"), &
6071              &               TRIM("          "), iim,jjm, hist_hori_id, &
6072              &               nvm,1,nvm, hist_PFTaxis_id,32, 'once(scatter(X))', dt, hist_dt)
6073       END IF ! (use_age_class)
6074   
6075       IF (use_bound_spa) THEN
6076            CALL histdef (hist_id_stom, &
6077                 &               TRIM("bound_spa            "), &
6078                 &               TRIM("Spatial age class boundaries                      "), &
6079                 &               TRIM("          "), iim,jjm, hist_hori_id, &
6080                 &               nvm,1,nvm, hist_PFTaxis_id,32, 'once(scatter(X))', dt, hist_dt)
6081       ENDIF
6082    !endglcc
6083
6084    ENDIF
6085    !---------------------------------
6086  END SUBROUTINE ioipslctrl_histstom
6087
6088!! ================================================================================================================================
6089!! SUBROUTINE    : ioipslctrl_histstomipcc
6090!!
6091!>\BRIEF         This subroutine initialize the IOIPSL stomate second output file (ipcc file)
6092!!
6093!! DESCRIPTION   : This subroutine initialize the IOIPSL stomate second output file named stomate_ipcc_history.nc(default name).
6094!!                 This subroutine was previously called stom_IPCC_define_history and located in module intersurf.
6095!!
6096!! RECENT CHANGE(S): None
6097!!
6098!! \n
6099!_ ================================================================================================================================
6100  SUBROUTINE ioipslctrl_histstomipcc( &
6101       hist_id_stom_IPCC, nvm, iim, jjm, dt, &
6102       hist_dt, hist_hori_id, hist_PFTaxis_id)
6103    ! deforestation axis added as arguments
6104
6105    !---------------------------------------------------------------------
6106    !- Tell ioipsl which variables are to be written
6107    !- and on which grid they are defined
6108    !---------------------------------------------------------------------
6109    IMPLICIT NONE
6110    !-
6111    !- Input
6112    !-
6113    !- File id
6114    INTEGER(i_std),INTENT(in) :: hist_id_stom_IPCC
6115    !- number of PFTs
6116    INTEGER(i_std),INTENT(in) :: nvm
6117    !- Domain size
6118    INTEGER(i_std),INTENT(in) :: iim, jjm
6119    !- Time step of STOMATE (seconds)
6120    REAL(r_std),INTENT(in)    :: dt
6121    !- Time step of history file (s)
6122    REAL(r_std),INTENT(in)    :: hist_dt
6123    !- id horizontal grid
6124    INTEGER(i_std),INTENT(in) :: hist_hori_id
6125    !- id of PFT axis
6126    INTEGER(i_std),INTENT(in) :: hist_PFTaxis_id
6127    !-
6128    !- 1 local
6129    !-
6130    !- Character strings to define operations for histdef
6131    CHARACTER(LEN=40),DIMENSION(max_hist_level) :: ave
6132
6133    !=====================================================================
6134    !- 1 define operations
6135    !=====================================================================
6136    ave(1) =  'ave(scatter(X))'
6137    !=====================================================================
6138    !- 2 surface fields (2d)
6139    !=====================================================================
6140    ! Carbon in Vegetation
6141    CALL histdef (hist_id_stom_IPCC, &
6142         &               TRIM("cVeg"), &
6143         &               TRIM("Carbon in Vegetation"), &
6144         &               TRIM("kg C m-2"), iim,jjm, hist_hori_id, &
6145         &               1,1,1, -99,32, ave(1), dt, hist_dt)
6146    ! Carbon in Litter Pool
6147    CALL histdef (hist_id_stom_IPCC, &
6148         &               TRIM("cLitter"), &
6149         &               TRIM("Carbon in Litter Pool"), &
6150         &               TRIM("kg C m-2"), iim,jjm, hist_hori_id, &
6151         &               1,1,1, -99,32, ave(1), dt, hist_dt)
6152    ! Carbon in Soil Pool
6153    CALL histdef (hist_id_stom_IPCC, &
6154         &               TRIM("cSoil"), &
6155         &               TRIM("Carbon in Soil Pool"), &
6156         &               TRIM("kg C m-2"), iim,jjm, hist_hori_id, &
6157         &               1,1,1, -99,32, ave(1), dt, hist_dt)
6158    ! Carbon in Products of Land Use Change
6159    CALL histdef (hist_id_stom_IPCC, &
6160         &               TRIM("cProduct"), &
6161         &               TRIM("Carbon in Products of Land Use Change"), &
6162         &               TRIM("kg C m-2"), iim,jjm, hist_hori_id, &
6163         &               1,1,1, -99,32, ave(1), dt, hist_dt)
6164    ! Carbon Mass Variation
6165    CALL histdef (hist_id_stom_IPCC, &
6166         &               TRIM("cMassVariation"), &
6167         &               TRIM("Terrestrial Carbon Mass Variation"), &
6168         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
6169         &               1,1,1, -99,32, ave(1), dt, hist_dt)
6170    ! Leaf Area Fraction
6171    CALL histdef (hist_id_stom_IPCC, &
6172         &               TRIM("lai"), &
6173         &               TRIM("Leaf Area Fraction"), &
6174         &               TRIM("1"), iim,jjm, hist_hori_id, &
6175         &               1,1,1, -99,32, ave(1), dt, hist_dt)
6176    ! Gross Primary Production
6177    CALL histdef (hist_id_stom_IPCC, &
6178         &               TRIM("gpp"), &
6179         &               TRIM("Gross Primary Production"), &
6180         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
6181         &               1,1,1, -99,32, ave(1), dt, hist_dt)
6182    ! Autotrophic Respiration
6183    CALL histdef (hist_id_stom_IPCC, &
6184         &               TRIM("ra"), &
6185         &               TRIM("Autotrophic Respiration"), &
6186         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
6187         &               1,1,1, -99,32, ave(1), dt, hist_dt)
6188    ! Net Primary Production
6189    CALL histdef (hist_id_stom_IPCC, &
6190         &               TRIM("npp"), &
6191         &               TRIM("Net Primary Production"), &
6192         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
6193         &               1,1,1, -99,32, ave(1), dt, hist_dt)
6194    ! Heterotrophic Respiration
6195    CALL histdef (hist_id_stom_IPCC, &
6196         &               TRIM("rh"), &
6197         &               TRIM("Heterotrophic Respiration"), &
6198         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
6199         &               1,1,1, -99,32, ave(1), dt, hist_dt)
6200    ! CO2 Emission from Fire
6201    CALL histdef (hist_id_stom_IPCC, &
6202         &               TRIM("fFire"), &
6203         &               TRIM("CO2 Emission from Fire"), &
6204         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
6205         &               1,1,1, -99,32, ave(1), dt, hist_dt)
6206
6207    ! CO2 Flux to Atmosphere from Crop Harvesting
6208    CALL histdef (hist_id_stom_IPCC, &
6209         &               TRIM("fHarvest"), &
6210         &               TRIM("CO2 Flux to Atmosphere from Crop Harvesting"), &
6211         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
6212         &               1,1,1, -99,32, ave(1), dt, hist_dt)
6213    ! CO2 Flux to Atmosphere from Land Use Change
6214    CALL histdef (hist_id_stom_IPCC, &
6215         &               TRIM("fLuc"), &
6216         &               TRIM("CO2 Flux to Atmosphere from Land Use Change"), &
6217         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
6218         &               1,1,1, -99,32, ave(1), dt, hist_dt)
6219    ! CO2 Flux to Atmosphere from Wood Harvest                                                                               
6220    CALL histdef (hist_id_stom_IPCC, &
6221         &               TRIM("fWoodharvest"), &
6222         &               TRIM("CO2 Flux to Atmosphere from Wood Harvest"), &
6223         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
6224         &               1,1,1, -99,32, ave(1), dt, hist_dt)
6225
6226    ! Net Biospheric Production
6227    CALL histdef (hist_id_stom_IPCC, &
6228         &               TRIM("nbp"), &
6229         &               TRIM("Net Biospheric Production"), &
6230         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
6231         &               1,1,1, -99,32, ave(1), dt, hist_dt)
6232    ! Total Carbon Flux from Vegetation to Litter
6233    CALL histdef (hist_id_stom_IPCC, &
6234         &               TRIM("fVegLitter"), &
6235         &               TRIM("Total Carbon Flux from Vegetation to Litter"), &
6236         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
6237         &               1,1,1, -99,32, ave(1), dt, hist_dt)
6238    ! Total Carbon Flux from Litter to Soil
6239    CALL histdef (hist_id_stom_IPCC, &
6240         &               TRIM("fLitterSoil"), &
6241         &               TRIM("Total Carbon Flux from Litter to Soil"), &
6242         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
6243         &               1,1,1, -99,32, ave(1), dt, hist_dt)
6244
6245    ! Carbon in Leaves
6246    CALL histdef (hist_id_stom_IPCC, &
6247         &               TRIM("cLeaf"), &
6248         &               TRIM("Carbon in Leaves"), &
6249         &               TRIM("kg C m-2"), iim,jjm, hist_hori_id, &
6250         &               1,1,1, -99,32, ave(1), dt, hist_dt)
6251    ! Carbon in Stem
6252    CALL histdef (hist_id_stom_IPCC, &
6253         &               TRIM("cStem"), &
6254         &               TRIM("Carbon in Stem"), &
6255         &               TRIM("kg C m-2"), iim,jjm, hist_hori_id, &
6256         &               1,1,1, -99,32, ave(1), dt, hist_dt)
6257    ! Carbon in Roots
6258    CALL histdef (hist_id_stom_IPCC, &
6259         &               TRIM("cRoot"), &
6260         &               TRIM("Carbon in Roots"), &
6261         &               TRIM("kg C m-2"), iim,jjm, hist_hori_id, &
6262         &               1,1,1, -99,32, ave(1), dt, hist_dt)
6263    ! Carbon in Other Living Compartments
6264    CALL histdef (hist_id_stom_IPCC, &
6265         &               TRIM("cMisc"), &
6266         &               TRIM("Carbon in Other Living Compartments"), &
6267         &               TRIM("kg C m-2"), iim,jjm, hist_hori_id, &
6268         &               1,1,1, -99,32, ave(1), dt, hist_dt)
6269
6270    ! Carbon in Above-Ground Litter
6271    CALL histdef (hist_id_stom_IPCC, &
6272         &               TRIM("cLitterAbove"), &
6273         &               TRIM("Carbon in Above-Ground Litter"), &
6274         &               TRIM("kg C m-2"), iim,jjm, hist_hori_id, &
6275         &               1,1,1, -99,32, ave(1), dt, hist_dt)
6276    ! Carbon in Below-Ground Litter
6277    CALL histdef (hist_id_stom_IPCC, &
6278         &               TRIM("cLitterBelow"), &
6279         &               TRIM("Carbon in Below-Ground Litter"), &
6280         &               TRIM("kg C m-2"), iim,jjm, hist_hori_id, &
6281         &               1,1,1, -99,32, ave(1), dt, hist_dt)
6282    ! Carbon in Fast Soil Pool
6283    CALL histdef (hist_id_stom_IPCC, &
6284         &               TRIM("cSoilFast"), &
6285         &               TRIM("Carbon in Fast Soil Pool"), &
6286         &               TRIM("kg C m-2"), iim,jjm, hist_hori_id, &
6287         &               1,1,1, -99,32, ave(1), dt, hist_dt)
6288    ! Carbon in Medium Soil Pool
6289    CALL histdef (hist_id_stom_IPCC, &
6290         &               TRIM("cSoilMedium"), &
6291         &               TRIM("Carbon in Medium Soil Pool"), &
6292         &               TRIM("kg C m-2"), iim,jjm, hist_hori_id, &
6293         &               1,1,1, -99,32, ave(1), dt, hist_dt)
6294    ! Carbon in Slow Soil Pool
6295    CALL histdef (hist_id_stom_IPCC, &
6296         &               TRIM("cSoilSlow"), &
6297         &               TRIM("Carbon in Slow Soil Pool"), &
6298         &               TRIM("kg C m-2"), iim,jjm, hist_hori_id, &
6299         &               1,1,1, -99,32, ave(1), dt, hist_dt)
6300
6301    !- 3 PFT: 3rd dimension
6302    ! Fractional Land Cover of PFT
6303    CALL histdef (hist_id_stom_IPCC, &
6304         &               TRIM("landCoverFrac"), &
6305         &               TRIM("Fractional Land Cover of PFT"), &
6306         &               TRIM("%"), iim,jjm, hist_hori_id, &
6307         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(1), dt, hist_dt)
6308
6309
6310    ! Total Primary Deciduous Tree Cover Fraction
6311    CALL histdef (hist_id_stom_IPCC, &
6312         &               TRIM("treeFracPrimDec"), &
6313         &               TRIM("Total Primary Deciduous Tree Cover Fraction"), &
6314         &               TRIM("%"), iim,jjm, hist_hori_id, &
6315         &               1,1,1, -99,32, ave(1), dt, hist_dt)
6316
6317    ! Total Primary Evergreen Tree Cover Fraction
6318    CALL histdef (hist_id_stom_IPCC, &
6319         &               TRIM("treeFracPrimEver"), &
6320         &               TRIM("Total Primary Evergreen Tree Cover Fraction"), &
6321         &               TRIM("%"), iim,jjm, hist_hori_id, &
6322         &               1,1,1, -99,32, ave(1), dt, hist_dt)
6323
6324    ! Total C3 PFT Cover Fraction
6325    CALL histdef (hist_id_stom_IPCC, &
6326         &               TRIM("c3PftFrac"), &
6327         &               TRIM("Total C3 PFT Cover Fraction"), &
6328         &               TRIM("%"), iim,jjm, hist_hori_id, &
6329         &               1,1,1, -99,32, ave(1), dt, hist_dt)
6330    ! Total C4 PFT Cover Fraction
6331    CALL histdef (hist_id_stom_IPCC, &
6332         &               TRIM("c4PftFrac"), &
6333         &               TRIM("Total C4 PFT Cover Fraction"), &
6334         &               TRIM("%"), iim,jjm, hist_hori_id, &
6335         &               1,1,1, -99,32, ave(1), dt, hist_dt)
6336    ! Growth Autotrophic Respiration
6337    CALL histdef (hist_id_stom_IPCC, &
6338         &               TRIM("rGrowth"), &
6339         &               TRIM("Growth Autotrophic Respiration"), &
6340         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
6341         &               1,1,1, -99,32, ave(1), dt, hist_dt)
6342    ! Maintenance Autotrophic Respiration
6343    CALL histdef (hist_id_stom_IPCC, &
6344         &               TRIM("rMaint"), &
6345         &               TRIM("Maintenance Autotrophic Respiration"), &
6346         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
6347         &               1,1,1, -99,32, ave(1), dt, hist_dt)
6348    ! CO2 Flux from Atmosphere due to NPP Allocation to Leaf
6349    CALL histdef (hist_id_stom_IPCC, &
6350         &               TRIM("nppLeaf"), &
6351         &               TRIM("CO2 Flux from Atmosphere due to NPP Allocation to Leaf"), &
6352         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
6353         &               1,1,1, -99,32, ave(1), dt, hist_dt)
6354    ! CO2 Flux from Atmosphere due to NPP Allocation to Wood
6355    CALL histdef (hist_id_stom_IPCC, &
6356         &               TRIM("nppStem"), &
6357         &               TRIM("CO2 Flux from Atmosphere due to NPP Allocation to Stem"), &
6358         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
6359         &               1,1,1, -99,32, ave(1), dt, hist_dt)
6360    ! CO2 Flux from Atmosphere due to NPP Allocation to Root
6361    CALL histdef (hist_id_stom_IPCC, &
6362         &               TRIM("nppRoot"), &
6363         &               TRIM("CO2 Flux from Atmosphere due to NPP Allocation to Root"), &
6364         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
6365         &               1,1,1, -99,32, ave(1), dt, hist_dt)
6366    ! Net Carbon Mass Flux out of Atmophere due to Net Ecosystem Productivity on Land.
6367    CALL histdef (hist_id_stom_IPCC, &
6368         &               TRIM("nep"), &
6369         &               TRIM("Net Carbon Mass Flux out of Atmophere due to Net Ecosystem Productivity."), &
6370         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
6371         &               1,1,1, -99,32, ave(1), dt, hist_dt)
6372
6373    CALL histdef(hist_id_stom_IPCC, 'RESOLUTION_X', 'E-W resolution', 'm', &
6374         & iim,jjm, hist_hori_id, 1,1,1, -99, 32, 'once(scatter(X))', dt, hist_dt)
6375    CALL histdef(hist_id_stom_IPCC, 'RESOLUTION_Y', 'N-S resolution', 'm', &
6376         & iim,jjm, hist_hori_id, 1,1,1, -99, 32, 'once(scatter(X))', dt, hist_dt)
6377    CALL histdef(hist_id_stom_IPCC, 'CONTFRAC', 'Continental fraction', '1', &
6378         & iim,jjm, hist_hori_id, 1,1,1, -99, 32, 'once(scatter(X))', dt, hist_dt)
6379    CALL histdef(hist_id_stom_IPCC, 'Areas', 'Mesh areas', 'm2', &
6380         & iim,jjm, hist_hori_id, 1,1,1, -99, 32, 'once(scatter(X))', dt, hist_dt)
6381
6382  END SUBROUTINE ioipslctrl_histstomipcc
6383
6384!! ================================================================================================================================
6385!! SUBROUTINE    : ioipslctrl_restini
6386!!
6387!>\BRIEF         This subroutine initialize the restart files in ORCHDIEE.
6388!!
6389!! DESCRIPTION   : This subroutine initialize restart files in ORCHIDEE. IOIPSL is used for manipulating the restart files.
6390!!                 This subroutine was previously called intsurf_restart and located in module intersurf.
6391!!
6392!! RECENT CHANGE(S): None
6393!!
6394!! \n
6395!_ ================================================================================================================================
6396  SUBROUTINE ioipslctrl_restini(istp, date0, dt, rest_id, rest_id_stom, itau_offset, date0_shifted)
6397
6398    USE mod_orchidee_para
6399    !
6400    !  This subroutine initialized the restart file for the land-surface scheme
6401    !
6402    IMPLICIT NONE
6403    !
6404    INTEGER(i_std), INTENT(in)                  :: istp      !! Time step of the restart file
6405    REAL(r_std)                                 :: date0     !! The date at which itau = 0
6406    REAL(r_std)                                 :: dt        !! Time step
6407    INTEGER(i_std), INTENT(out)                 :: rest_id, rest_id_stom   !! ID of the restart file
6408    INTEGER(i_std), INTENT(out)                 :: itau_offset    !! Note the result is always itau_offset=0 as overwrite_time=TRUE
6409    REAL(r_std), INTENT(out)                    :: date0_shifted  !! Note the result is always date0_shifted=date0 as overwrite_time=TRUE
6410
6411
6412    !  LOCAL
6413    !
6414    REAL(r_std)                 :: dt_rest, date0_rest
6415    INTEGER(i_std)              :: itau_dep
6416    INTEGER(i_std),PARAMETER    :: llm=1
6417    REAL(r_std), DIMENSION(llm) :: lev
6418    LOGICAL, PARAMETER          :: overwrite_time=.TRUE. !! Always override the date from the restart files for SECHIBA and STOMATE.
6419                                                         !! The date is taken from the gcm or from the driver restart file.
6420    REAL(r_std)                 :: in_julian, rest_julian
6421    INTEGER(i_std)              :: yy, mm, dd
6422    REAL(r_std)                 :: ss
6423    !
6424    !Config Key   = SECHIBA_restart_in
6425    !Config Desc  = Name of restart to READ for initial conditions
6426    !Config If    = OK_SECHIBA
6427    !Config Def   = NONE
6428    !Config Help  = This is the name of the file which will be opened
6429    !Config         to extract the initial values of all prognostic
6430    !Config         values of the model. This has to be a netCDF file.
6431    !Config         Not truly COADS compliant. NONE will mean that
6432    !Config         no restart file is to be expected.
6433    !Config Units = [FILE]
6434!-
6435    CALL getin_p('SECHIBA_restart_in',restname_in)
6436    IF (printlev >= 2) WRITE(numout,*) 'Restart file for sechiba: ', restname_in
6437    !-
6438    !Config Key   = SECHIBA_rest_out
6439    !Config Desc  = Name of restart files to be created by SECHIBA
6440    !Config If    = OK_SECHIBA
6441    !Config Def   = sechiba_rest_out.nc
6442    !Config Help  = This variable give the name for
6443    !Config         the restart files. The restart software within
6444    !Config         IOIPSL will add .nc if needed.
6445    !Config Units = [FILE]
6446    !
6447    CALL getin_p('SECHIBA_rest_out', restname_out)
6448 
6449    lev(:) = zero
6450    itau_dep = istp
6451    in_julian = itau2date(istp, date0, dt)
6452    date0_rest = date0
6453    dt_rest = dt
6454    !
6455    IF (is_root_prc) THEN
6456       CALL restini( restname_in, iim_g, jjm_g, lon_g, lat_g, llm, lev, &
6457            &  restname_out, itau_dep, date0_rest, dt_rest, rest_id, overwrite_time, &
6458            &  use_compression=NC_COMPRESSION_ENABLE)
6459    ELSE
6460       rest_id=0
6461    ENDIF
6462    CALL bcast (itau_dep)
6463    CALL bcast (date0_rest)
6464    CALL bcast (dt_rest)
6465    !
6466    !  itau_dep of SECHIBA is phased with the GCM if needed
6467    !
6468    rest_julian = itau2date(itau_dep, date0_rest, dt_rest)
6469
6470    ! Note by JG
6471    ! restini never modifies itau_dep and date0_rest when overwrite_time=TRUE.
6472    ! This means that itau_dep=istp and date0_rest=date0 => rest_julian=in_julian.
6473    ! The result of below IF will therfor always be itau_offset=0 and date0_shifted=date0
6474    IF ( ABS( in_julian - rest_julian) .GT. dt/one_day .AND. .NOT. OFF_LINE_MODE ) THEN
6475       WRITE(numout,*) 'The SECHIBA restart is not for the same timestep as the GCM,'
6476       WRITE(numout,*) 'the two are synchronized. The land-surface conditions can not impose'
6477       WRITE(numout,*) 'the chronology of the simulation.'
6478       WRITE(numout,*) 'Time step of the GCM :', istp, 'Julian day : ', in_julian
6479       CALL ju2ymds(in_julian, yy, mm, dd, ss)
6480       WRITE(numout,*) 'In other word (yy,mm,dd,ss) : ', yy, mm, dd, ss
6481       WRITE(numout,*) 'Time step of SECHIBA :', itau_dep, 'Julian day : ', rest_julian
6482       CALL ju2ymds(rest_julian, yy, mm, dd, ss)
6483       WRITE(numout,*) 'In other word (yy,mm,dd,ss) : ', yy, mm, dd, ss
6484       
6485       itau_offset = itau_dep - istp
6486       date0_shifted = date0 - itau_offset*dt/one_day
6487       
6488       WRITE(numout,*) 'The new starting date is :', date0_shifted
6489       CALL ju2ymds(date0_shifted, yy, mm, dd, ss)
6490       WRITE(numout,*) 'In other word (yy,mm,dd,ss) : ', yy, mm, dd, ss
6491    ELSE
6492       itau_offset = 0
6493       date0_shifted = date0
6494    ENDIF
6495
6496    !=====================================================================
6497    !- 1.5 Restart file for STOMATE
6498    !=====================================================================
6499    IF ( ok_stomate ) THEN 
6500       !-
6501       ! STOMATE IS ACTIVATED
6502       !-
6503       !Config Key   = STOMATE_RESTART_FILEIN
6504       !Config Desc  = Name of restart to READ for initial conditions of STOMATE
6505       !Config If    = STOMATE_OK_STOMATE
6506       !Config Def   = NONE
6507       !Config Help  = This is the name of the file which will be opened
6508       !Config         to extract the initial values of all prognostic
6509       !Config         values of STOMATE.
6510       !Config Units = [FILE]
6511       !-
6512       CALL getin_p('STOMATE_RESTART_FILEIN',stom_restname_in)
6513       IF (printlev >= 2) WRITE(numout,*) 'STOMATE INPUT RESTART_FILE', stom_restname_in
6514       !-
6515       !Config Key   = STOMATE_RESTART_FILEOUT
6516       !Config Desc  = Name of restart files to be created by STOMATE
6517       !Config If    = STOMATE_OK_STOMATE
6518       !Config Def   = stomate_rest_out.nc
6519       !Config Help  = This is the name of the file which will be opened
6520       !Config         to write the final values of all prognostic values
6521       !Config         of STOMATE.
6522       !Config Units = [FILE]
6523       !-
6524       CALL getin_p('STOMATE_RESTART_FILEOUT', stom_restname_out)
6525       IF (printlev >= 2) WRITE(numout,*) 'STOMATE OUTPUT RESTART_FILE', stom_restname_out
6526       !-
6527       IF (is_root_prc) THEN
6528         CALL restini (stom_restname_in, iim_g, jjm_g, lon_g, lat_g, llm, lev, &
6529            &  stom_restname_out, itau_dep, date0_rest, dt_rest, rest_id_stom, overwrite_time, &
6530            &  use_compression=NC_COMPRESSION_ENABLE)
6531       ELSE
6532         rest_id_stom=0
6533       ENDIF
6534       CALL bcast (itau_dep)
6535       CALL bcast (date0_rest)
6536       CALL bcast (dt_rest)
6537       !-
6538    ENDIF
6539  END SUBROUTINE ioipslctrl_restini
6540
6541END MODULE ioipslctrl
Note: See TracBrowser for help on using the repository browser.