source: branches/publications/ORCHIDEE-PEAT_r5488/src_sechiba/ioipslctrl.f90

Last change on this file was 5488, checked in by chunjing.qiu, 6 years ago

C balance checked

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