source: branches/publications/ORCHIDEE-GMv3.2/ORCHIDEE/src_sechiba/ioipslctrl.f90 @ 5816

Last change on this file since 5816 was 5816, checked in by jinfeng.chang, 5 years ago

copy ORCHIDEE-GMv3.2 for publication

File size: 227.2 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
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  !! 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)                         :: ier
126    REAL(r_std), ALLOCATABLE, DIMENSION(:) :: lon_rect, lat_rect
127    !
128    REAL(r_std),DIMENSION(nvm)   :: veg
129    REAL(r_std),DIMENSION(nlai+1):: lai
130    REAL(r_std),DIMENSION(ngrnd) :: sol
131    REAL(r_std),DIMENSION(nstm)  :: soltyp
132    REAL(r_std),DIMENSION(nnobio):: nobiotyp
133    REAL(r_std),DIMENSION(2)     :: albtyp
134    REAL(r_std),DIMENSION(nslm)  :: solay
135    REAL(r_std),DIMENSION(nsnow) :: snowlev           !! Layers for snow axis
136    !
137    CHARACTER(LEN=80)           :: var_name           !! To store variables names
138    !
139    ! STOMATE history file
140    REAL(r_std)                  :: hist_days_stom     !!- GK time step in days for this history file
141    REAL(r_std)                  :: hist_dt_stom       !!- GK time step in seconds for this history file
142    REAL(r_std)                  :: dt_stomate_loc     !!  for test : time step of slow processes and STOMATE
143    REAL(r_std),DIMENSION(nvm)   :: hist_PFTaxis       !!- GK An axis we need for the history files
144!
145    REAL(r_std),DIMENSION(10)  :: hist_pool_10axis     !! Deforestation axis
146    REAL(r_std),DIMENSION(100)  :: hist_pool_100axis     !! Deforestation axis
147    REAL(r_std),DIMENSION(11)  :: hist_pool_11axis     !! Deforestation axis
148    REAL(r_std),DIMENSION(101)  :: hist_pool_101axis     !! Deforestation axis
149    !
150    ! IPCC history file
151    REAL(r_std)                  :: hist_days_stom_ipcc     !!- GK time step in days for this history file
152    REAL(r_std)                  :: hist_dt_stom_ipcc       !!- GK time step in seconds for this history file
153!
154    !
155    !=====================================================================
156    !- 3.0 Setting up the history files
157    !=====================================================================
158    !- 3.1 SECHIBA
159    !=====================================================================
160    !Config Key   = ALMA_OUTPUT
161    !Config Desc  = Should the output follow the ALMA convention
162    !Config If    = OK_SECHIBA
163    !Config Def   = n
164    !Config Help  = If this logical flag is set to true the model
165    !Config         will output all its data according to the ALMA
166    !Config         convention. It is the recommended way to write
167    !Config         data out of ORCHIDEE.
168    !Config Units = [FLAG]
169    CALL getin_p('ALMA_OUTPUT', almaoutput)   
170    WRITE(numout,*) 'ALMA_OUTPUT', almaoutput
171    !-
172    !Config Key   = OUTPUT_FILE
173    !Config Desc  = Name of file in which the output is going to be written
174    !Config If    = OK_SECHIBA
175    !Config Def   = sechiba_history.nc
176    !Config Help  = This file is going to be created by the model
177    !Config         and will contain the output from the model.
178    !Config         This file is a truly COADS compliant netCDF file.
179    !Config         It will be generated by the hist software from
180    !Config         the IOIPSL package.
181    !Config Units = [FILE]
182    !-
183    histname='sechiba_history.nc'
184    CALL getin_p('OUTPUT_FILE', histname)
185    WRITE(numout,*) 'OUTPUT_FILE', histname
186    !-
187    !Config Key   = WRITE_STEP
188    !Config Desc  = Frequency in seconds for sechiba_history.nc file with IOIPSL
189    !Config If    = OK_SECHIBA, NOT XIOS_ORCHIDEE_OK
190    !Config Def   = one_day
191    !Config Help  = This variables gives the frequency in the output
192    !Config         file sechiba_history.nc if using IOIPSL.
193    !Config         This variable is not read if XIOS is activated.
194    !Config Units = [seconds]
195    !-
196    dw = one_day
197    IF (xios_orchidee_ok) THEN
198      dw=0
199      IF (printlev>=3) WRITE(numout,*) 'All IOIPSL output are deactivated because this run uses XIOS'
200    ELSE
201      CALL getin_p('WRITE_STEP', dw)
202      IF ( dw == 0 ) WRITE(numout,*) 'sechiba_history file will not be created'
203    END IF
204    !
205    veg(1:nvm)   = (/ (REAL(i,r_std),i=1,nvm) /)
206    lai(1:nlai+1) = (/ (REAL(i,r_std),i=1,nlai+1) /)
207    soltyp(1:nstm) = (/ (REAL(i,r_std),i=1,nstm) /)
208    nobiotyp(1:nnobio) = (/ (REAL(i,r_std),i=1,nnobio) /)
209    albtyp(1:2) = (/ (REAL(i,r_std),i=1,2) /)
210    solay(1:nslm) = (/ (REAL(i,r_std),i=1,nslm) /)
211    snowlev =  (/ (REAL(i,r_std),i=1,nsnow) /)
212
213    ! Get the vertical soil levels for the thermal scheme
214    IF (hydrol_cwrr) THEN
215       sol(1:ngrnd) = znt(:)
216    ELSE
217       sol(1:ngrnd) = thermosoilc_levels()
218    END IF
219
220    !
221    !- We need to flux averaging operation as when the data is written
222    !- from within SECHIBA a scatter is needed. In the driver on the other
223    !- hand the data is 2D and can be written is it is.
224    !-
225    WRITE(flux_op,'("ave(scatter(X*",F8.1,"))")') one_day/dt
226    ! WRITE(flux_op,'("(ave(scatter(X))*",F8.1,")")') one_day/dt
227!    WRITE(flux_sc,'("ave(X*",F8.1,")")') one_day/dt
228!    WRITE(flux_insec,'("ave(X*",F8.6,")")') un/dt
229!    WRITE(flux_insec,'("ave(X*",F12.10,")")') un/dt
230    WRITE(flux_scinsec,'("ave(scatter(X*",F12.10,"))")') un/dt
231    WRITE(numout,*) 'flux_op=',flux_op,' one_day/dt=', one_day/dt, ' dt=',dt,' dw=', dw
232    !-
233    !Config Key   = SECHIBA_HISTLEVEL
234    !Config Desc  = SECHIBA history output level (0..10)
235    !Config If    = OK_SECHIBA and HF
236    !Config Def   = 5
237    !Config Help  = Chooses the list of variables in the history file.
238    !Config         Values between 0: nothing is written; 10: everything is
239    !Config         written are available More details can be found on the web under documentation.
240    !Config Units = [-]
241    !-
242    hist_level = 5
243    CALL getin_p('SECHIBA_HISTLEVEL', hist_level)
244    !-
245    WRITE(numout,*) 'SECHIBA history level: ',hist_level
246    IF ( (hist_level > max_hist_level).OR.(hist_level < 0) ) THEN
247       STOP 'This history level is not allowed'
248    ENDIF
249    !-
250    !- define operations as a function of history level.
251    !- Above hist_level, operation='never'
252    !-
253    ave(1:max_hist_level) = 'ave(scatter(X))'
254    IF (hist_level < max_hist_level) THEN
255       ave(hist_level+1:max_hist_level) = 'never'
256    ENDIF
257    sumscatter(1:max_hist_level) = 't_sum(scatter(X))'
258    IF (hist_level < max_hist_level) THEN
259       sumscatter(hist_level+1:max_hist_level) = 'never'
260    ENDIF
261
262    avecels(1:max_hist_level) = 'ave(cels(scatter(X)))'
263    IF (hist_level < max_hist_level) THEN
264       avecels(hist_level+1:max_hist_level) = 'never'
265    ENDIF
266
267    avescatter(1:max_hist_level) = 'ave(scatter(X))'
268    IF (hist_level < max_hist_level) THEN
269       avescatter(hist_level+1:max_hist_level) = 'never'
270    ENDIF
271    tmincels(1:max_hist_level) = 't_min(cels(scatter(X)))'
272    IF (hist_level < max_hist_level) THEN
273       tmincels(hist_level+1:max_hist_level) = 'never'
274    ENDIF
275    tmaxcels(1:max_hist_level) = 't_max(cels(scatter(X)))'
276    IF (hist_level < max_hist_level) THEN
277       tmaxcels(hist_level+1:max_hist_level) = 'never'
278    ENDIF
279
280    fluxop(1:max_hist_level) = flux_op
281    IF (hist_level < max_hist_level) THEN
282       fluxop(hist_level+1:max_hist_level) = 'never'
283    ENDIF
284
285    fluxop_scinsec(1:max_hist_level) = flux_scinsec
286    IF (hist_level < max_hist_level) THEN
287       fluxop_scinsec(hist_level+1:max_hist_level) = 'never'
288    ENDIF
289    once(1:max_hist_level) = 'once(scatter(X))'
290    IF (hist_level < max_hist_level) THEN
291       once(hist_level+1:max_hist_level) = 'never'
292    ENDIF
293
294
295    !- Initialize sechiba_history output file
296    !-
297    IF ( dw == 0 ) THEN
298       ! sechiba_history file will not be created.
299       hist_id = -1
300
301    ELSE
302       ! sechiba_history file will be created
303
304       !- Calculation necessary for initialization of sechiba_history file
305       !- Check if we have by any change a rectilinear grid. This would allow us to
306       !- simplify the output files.
307    IF (is_omp_root) THEN
308       !
309       IF ( GridType == "RegLonLat" ) THEN
310          ALLOCATE(lon_rect(iim),stat=ier)
311          IF (ier .NE. 0) THEN
312             WRITE (numout,*) ' error in lon_rect allocation. We stop. We need iim words = ',iim
313             STOP 'intersurf_history'
314          ENDIF
315          ALLOCATE(lat_rect(jjm),stat=ier)
316          IF (ier .NE. 0) THEN
317             WRITE (numout,*) ' error in lat_rect allocation. We stop. We need jjm words = ',jjm
318             STOP 'intersurf_history'
319          ENDIF
320          lon_rect(:) = lon(:,1)
321          lat_rect(:) = lat(1,:)
322       ENDIF
323       !-
324       !-
325       !-
326       ! Initialize sechiba_history file
327       IF ( .NOT. almaoutput ) THEN
328          !-
329          IF ( GridType == "RegLonLat" ) THEN
330#ifdef CPP_PARA
331             CALL histbeg(histname, iim, lon_rect, jjm, lat_rect, 1, iim, 1, jjm, &
332                  &     istp_old, date0, dt, hori_id, hist_id,orch_domain_id)
333#else
334             CALL histbeg(histname, iim, lon_rect, jjm, lat_rect, 1, iim, 1, jjm, &
335                  &     istp_old, date0, dt, hori_id, hist_id)
336#endif
337             WRITE(numout,*)  'HISTBEG --->',istp_old,date0,dt,dw,hist_id
338          ELSE
339#ifdef CPP_PARA
340             CALL histbeg(histname, iim, lon, jjm, lat, 1, iim, 1, jjm, &
341                  &     istp_old, date0, dt, hori_id, hist_id,domain_id=orch_domain_id)
342#else
343             CALL histbeg(histname, iim, lon, jjm, lat, 1, iim, 1, jjm, &
344                  &     istp_old, date0, dt, hori_id, hist_id)
345#endif
346          ENDIF
347          !-
348          CALL histvert(hist_id, 'veget', 'Vegetation types', '1', &
349               &    nvm,   veg, vegax_id)
350          CALL histvert(hist_id, 'laiax', 'Nb LAI', '1', &
351               &    nlai+1,   lai, laiax_id)
352          CALL histvert(hist_id, 'solth', 'Soil levels',      'm', &
353               &    ngrnd, sol, solax_id)
354          CALL histvert(hist_id, 'soiltyp', 'Soil types',      '1', &
355               &    nstm, soltyp, soltax_id)
356          CALL histvert(hist_id, 'nobio', 'Other surface types',      '1', &
357               &    nnobio, nobiotyp, nobioax_id)
358          IF (  hydrol_cwrr ) THEN
359             CALL histvert(hist_id, 'solay', 'Hydrol soil levels',      'm', &
360                  &    nslm, diaglev(1:nslm), solayax_id)
361             CALL histvert(hist_id, 'soildiag', 'Diagnostic soil levels', 'm', &
362                  &    nbdl, diaglev(1:nbdl), soildiagax_id)
363          ENDIF
364
365          CALL histvert(hist_id, 'snowlev', 'Snow levels',      'm', &
366               &    nsnow, snowlev, snowax_id)
367
368          !-
369          !- SECHIBA_HISTLEVEL = 1
370          !-
371          CALL histdef(hist_id, 'evap', 'Evaporation', 'mm/d', &
372               & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop(1), dt,dw)
373          CALL histdef(hist_id, 'coastalflow', 'Diffuse coastal flow', 'm^3/s', &
374               & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop_scinsec(1), dt,dw)
375          CALL histdef(hist_id, 'riverflow', 'River flow to the oceans', 'm^3/s', &
376               & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop_scinsec(1), dt,dw) 
377          CALL histdef(hist_id, 'temp_sol', 'Surface Temperature', 'C', &
378               & iim,jjm, hori_id, 1,1,1, -99, 32, avecels(1), dt,dw)
379          CALL histdef(hist_id, 'rain', 'Rainfall', 'mm/d',  &
380               & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop(1), dt,dw)
381          CALL histdef(hist_id, 'snowf', 'Snowfall', 'mm/d',  &
382               & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop(1), dt,dw)
383          CALL histdef(hist_id, 'netrad', 'Net radiation', 'W/m^2',  &
384               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
385          CALL histdef(hist_id, 'lai', 'Leaf Area Index', '1', &
386               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(1), dt,dw)
387          !
388          IF (  hydrol_cwrr ) THEN
389             CALL histdef(hist_id, 'reinf_slope', 'Slope index for each grid box', '1', &
390                  & iim,jjm, hori_id, 1,1,1, -99, 32, once(1),  dt,dw)
391             CALL histdef(hist_id, 'soilindex', 'Soil index', '1', &
392                  & iim,jjm, hori_id, 1, 1, 1, -99, 32, once(1),  dt,dw)
393          ENDIF
394          !
395          IF ( river_routing ) THEN
396             CALL histdef(hist_id, 'basinmap', 'Aproximate map of the river basins', ' ', &
397                  & iim,jjm, hori_id, 1,1,1, -99, 32, once(1), dt,dw) 
398             CALL histdef(hist_id, 'nbrivers', 'Number or rivers in the outflow grid box', ' ', &
399                  & iim,jjm, hori_id, 1,1,1, -99, 32, once(1), dt,dw) 
400          ENDIF
401          !-
402          !- SECHIBA_HISTLEVEL = 2
403          !-
404          CALL histdef(hist_id, 'subli', 'Sublimation', 'mm/d', &
405               & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop(2), dt,dw)
406          CALL histdef(hist_id, 'evapnu', 'Bare soil evaporation', 'mm/d', &
407               & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop(2), dt,dw)
408          CALL histdef(hist_id, 'runoff', 'Surface runoff', 'mm/d', &
409               & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop(2), dt,dw)
410          CALL histdef(hist_id, 'drainage', 'Deep drainage', 'mm/d', &
411               & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop(2), dt,dw)
412          IF ( river_routing ) THEN
413             CALL histdef(hist_id, 'riversret', 'Return from endorheic rivers', 'mm/d', &
414                  & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop(2), dt,dw)
415             CALL histdef(hist_id, 'hydrographs', 'Hydrographs of gridbox outflow', 'm^3/s', &
416                  & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop_scinsec(2), dt,dw)
417          ENDIF
418          IF ( hydrol_cwrr ) THEN
419             CALL histdef(hist_id, 'evapnu_soil', 'Bare soil evap for soil type', 'mm/d', &
420                  & iim,jjm, hori_id, nstm, 1, nstm, soltax_id, 32, fluxop(2), dt,dw)
421             CALL histdef(hist_id, 'drainage_soil', 'Drainage for soil type', 'mm/d', &
422                  & iim,jjm, hori_id, nstm, 1, nstm, soltax_id, 32, fluxop(2), dt,dw)
423             CALL histdef(hist_id, 'transpir_soil', 'Transpir for soil type', 'mm/d', &
424                  & iim,jjm, hori_id, nstm, 1, nstm, soltax_id, 32, fluxop(2), dt,dw)
425             CALL histdef(hist_id, 'runoff_soil', 'Runoff for soil type', 'mm/d', &
426                  & iim,jjm, hori_id, nstm, 1, nstm, soltax_id, 32, fluxop(2), dt,dw)
427          ENDIF
428          !
429          CALL histdef(hist_id, 'tair', 'Air Temperature', 'K',  &
430               & iim,jjm, hori_id, 1,1,1, -99, 32, ave(2), dt,dw)
431          CALL histdef(hist_id, 'qair', 'Air humidity', 'g/g',  &
432               & iim,jjm, hori_id, 1,1,1, -99, 32, ave(2), dt,dw)
433          CALL histdef(hist_id, 'q2m', '2m Air humidity', 'g/g',  &
434               & iim,jjm, hori_id, 1,1,1, -99, 32, ave(2), dt,dw)
435          CALL histdef(hist_id, 't2m', '2m Air Temperature', 'K',  &
436               & iim,jjm, hori_id, 1,1,1, -99, 32, ave(2), dt,dw)
437          CALL histdef(hist_id, 'alb_vis', 'Albedo visible', '1', &
438               & iim,jjm, hori_id, 1,1,1, -99, 32, ave(2), dt,dw)
439          CALL histdef(hist_id, 'alb_nir', 'Albedo near infrared', '1', &
440               & iim,jjm, hori_id, 1,1,1, -99, 32, ave(2), dt,dw)
441          CALL histdef(hist_id, 'soilalb_vis', 'Soil Albedo visible', '1', &
442               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(2), dt,dw)
443          CALL histdef(hist_id, 'soilalb_nir', 'Soil Albedo near infrared', '1', &
444               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(2), dt,dw)
445          CALL histdef(hist_id, 'vegalb_vis', 'Vegetation Albedo visible', '1', &
446               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(2), dt,dw)
447          CALL histdef(hist_id, 'vegalb_nir', 'Vegetation Albedo near infrared', '1', &
448               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(2), dt,dw)
449          CALL histdef(hist_id, 'z0m', 'Surface roughness for momentum', 'm',  &
450               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(2), dt,dw)
451          CALL histdef(hist_id, 'z0h', 'Surface roughness for heat', 'm',  &
452               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(2), dt,dw)
453          CALL histdef(hist_id, 'roughheight', 'Effective roughness height', 'm',  &
454               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(2), dt,dw)
455          CALL histdef(hist_id, 'transpir', 'Transpiration', 'mm/d', &
456               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, fluxop(2), dt,dw)
457          CALL histdef(hist_id, 'inter', 'Interception loss', 'mm/d', &
458               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, fluxop(2), dt,dw)
459          !-
460          !- SECHIBA_HISTLEVEL = 3
461          !-
462          CALL histdef(hist_id, 'tsol_max', 'Maximum Surface Temperature',&
463               & 'C', iim,jjm, hori_id, 1,1,1, -99, 32, tmaxcels(3), dt,dw)
464          CALL histdef(hist_id, 'tsol_min', 'Minimum Surface Temperature',&
465               & 'C', iim,jjm, hori_id, 1,1,1, -99, 32, tmincels(3), dt,dw)
466          CALL histdef(hist_id, 'fluxsens', 'Sensible Heat Flux', 'W/m^2',  &
467               & iim,jjm, hori_id, 1,1,1, -99, 32, ave(3), dt,dw)
468          CALL histdef(hist_id, 'fluxlat', 'Latent Heat Flux', 'W/m^2',  &
469               & iim,jjm, hori_id, 1,1,1, -99, 32, ave(3), dt,dw)
470          CALL histdef(hist_id, 'snow', 'Snow mass', 'kg/m^2', &
471               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(3), dt,dw)
472          CALL histdef(hist_id, 'snowage', 'Snow age', '?', &
473               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(3), dt,dw)
474          CALL histdef(hist_id, 'snownobio', 'Snow on other surfaces', 'kg/m^2', &
475               & iim,jjm, hori_id, nnobio,1, nnobio, nobioax_id, 32, avescatter(3), dt,dw)
476          CALL histdef(hist_id, 'snownobioage', 'Snow age on other surfaces', 'd', &
477               & iim,jjm, hori_id, nnobio,1, nnobio, nobioax_id, 32, avescatter(3), dt,dw)
478          CALL histdef(hist_id, 'vegetfrac', 'Fraction of vegetation', '1', &
479               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(3), dt,dw)
480          CALL histdef(hist_id, 'maxvegetfrac', 'Maximum fraction of vegetation', '1', &
481               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(3), dt,dw)
482          CALL histdef(hist_id, 'tot_bare_soil', "Total Bare Soil Fraction", "%", &
483               & iim,jjm, hori_id, 1, 1, 1, -99, 32, avescatter(3), dt,dw)
484          CALL histdef(hist_id, 'nobiofrac', 'Fraction of other surface types', '1', &
485               & iim,jjm, hori_id, nnobio, 1, nnobio, nobioax_id, 32, avescatter(3), dt,dw)
486          IF ( do_floodplains ) THEN
487             CALL histdef(hist_id, 'flood_frac', 'Flooded fraction', '1', &
488                  & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(3), dt,dw)
489             CALL histdef(hist_id, 'reinfiltration', 'Reinfiltration from floodplains', 'mm/d', &
490                  & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop(3), dt,dw)
491          ENDIF
492          IF ( hydrol_cwrr ) THEN
493             DO jst=1,nstm
494             
495                ! var_name= "mc_1" ... "mc_3"
496                WRITE (var_name,"('moistc_',i1)") jst
497                CALL histdef(hist_id, var_name, 'Soil Moisture profile for soil type', 'm3/m3', &
498                     & iim,jjm, hori_id, nslm, 1, nslm, solayax_id, 32, avescatter(3),  dt,dw)
499               
500                ! var_name= "vegetsoil_1" ... "vegetsoil_3"
501                WRITE (var_name,"('vegetsoil_',i1)") jst
502                CALL histdef(hist_id, var_name, 'Fraction of vegetation on soil types', '%', &
503                     & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(3),  dt,dw)
504               
505                ! var_name= "kfact_root_1" ... "kfact_root_3"
506                WRITE (var_name,"('kfactroot_',i1)") jst
507                CALL histdef(hist_id, var_name, 'Root fraction profile for soil type', '%', &
508                     & iim,jjm, hori_id, nslm, 1, nslm, solayax_id, 32, avescatter(3), dt,dw)
509               
510             ENDDO
511
512             IF (ok_freeze_cwrr) THEN
513                CALL histdef(hist_id, 'profil_froz_hydro', 'Frozen fraction for each hydrological soil layer', '-', &
514                     & iim,jjm, hori_id, nslm, 1, nslm, solayax_id, 32, avescatter(1),  dt,dw)
515                DO jst=1,nstm
516                   WRITE (var_name,"('profil_froz_hydro_',i1)") jst
517                   CALL histdef(hist_id, trim(var_name), 'Frozen fraction for each hydrological soil layer and soiltile', '-', &
518                        & iim,jjm, hori_id, nslm, 1, nslm, solayax_id, 32, avescatter(1),  dt,dw)
519                ENDDO
520                CALL histdef(hist_id, 'temp_hydro', 'Soil temperature interpolated on hydrological layers', 'K', &
521                     & iim,jjm, hori_id, nslm, 1, nslm, solayax_id, 32, avescatter(1), dt,dw)
522                CALL histdef(hist_id, 'kk_moy', 'Mean hydrological conductivity', 'mm/d', &
523                     & iim,jjm,hori_id, nslm,1,nslm, solayax_id, 32, avescatter(1),  dt,dw)
524             END IF
525             
526             CALL histdef(hist_id, 'ptn_beg', 'Soil temperature from previous time step', 'K', &
527                  & iim,jjm,hori_id, ngrnd,1,ngrnd, solax_id, 32, avescatter(1),  dt,dw)
528
529             IF ( ok_freeze_thermix ) THEN
530                CALL histdef(hist_id, 'pcappa_supp', 'Additional heat capacity due to soil freezing for each soil layer', 'J/K', &
531                     iim,jjm,hori_id, ngrnd,1,ngrnd, solax_id, 32, avescatter(1),  dt,dw)
532             END IF
533
534             CALL histdef(hist_id, 'shum_ngrnd_perma', 'Saturation degree on the thermal axes', '-', &
535                  & iim,jjm,hori_id,ngrnd,1,ngrnd, solax_id, 32, avescatter(1),  dt,dw)
536             CALL histdef(hist_id, 'shumdiag_perma', 'Saturation degree of the soil', '-', &
537                  & iim,jjm,hori_id,nbdl,1,nbdl, soildiagax_id, 32, avescatter(1),  dt,dw)
538             CALL histdef(hist_id, 'humtot_pro', "Water content in soil layer", "kg m-2 ", &
539                  & iim,jjm, hori_id, nslm, 1, nslm, solayax_id, 32, avescatter(3), dt,dw)
540          ENDIF
541          !
542          CALL histdef(hist_id, 'frac_bare', 'Bare soil fraction for each tile', '-', &
543               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(3), dt,dw)
544          CALL histdef(hist_id, 'soiltile', 'Fraction of soil tiles', '%', &
545               & iim,jjm, hori_id, nstm, 1, nstm, soltax_id, 32, once(3),  dt,dw)
546          !-
547          !- SECHIBA_HISTLEVEL = 4
548          !-
549          IF ( .NOT. hydrol_cwrr ) THEN
550             CALL histdef(hist_id, 'dss', 'Up-reservoir Height', 'm',  &
551                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(4), dt,dw)
552             CALL histdef(hist_id, 'gqsb', 'Upper Soil Moisture', 'Kg/m^2',  &
553                  & iim,jjm, hori_id, 1, 1, 1, -99, 32, avescatter(4), dt,dw)
554             CALL histdef(hist_id, 'bqsb', 'Lower Soil Moisture', 'Kg/m^2',  &
555                  & iim,jjm, hori_id, 1, 1, 1, -99, 32, avescatter(4), dt,dw)
556          ELSE
557             CALL histdef(hist_id, 'humtot', 'Total Soil Moisture', 'Kg/m^2', &
558                  & iim,jjm, hori_id, 1, 1, 1, -99, 32, avescatter(4), dt,dw)
559             CALL histdef(hist_id, 'humtot_soil', 'Soil Moisture for soil type', 'Kg/m^2', &
560                  & iim,jjm, hori_id, nstm, 1, nstm, soltax_id, 32, avescatter(4), dt,dw)
561!gmjc 6 layer soil moisture
562             CALL histdef(hist_id, 'tmc_trampling', '10cm Soil Moisture for soil type', 'Kg/m^2', &
563                  & iim,jjm, hori_id, nstm, 1, nstm, soltax_id, 32, avescatter(4), dt,dw)
564!end gmjc
565             CALL histdef(hist_id, 'SWI', 'Soil wetness index','-',  &
566                  & iim,jjm, hori_id, 1, 1, 1, -99, 32, avescatter(4), dt,dw)
567             CALL histdef(hist_id, 'njsc', 'Soil class used for hydrology', '-', &
568                  & iim,jjm, hori_id, 1, 1, 1, -99, 32, once(4), dt,dw)
569          ENDIF
570          CALL histdef(hist_id, 'qsintveg', 'Water on canopy', 'Kg/m^2', &
571               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(4), dt,dw)
572          CALL histdef(hist_id, 'rstruct', 'Structural resistance', 's/m', &
573               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(4), dt,dw)
574          IF ( ok_co2 ) THEN
575             CALL histdef(hist_id, 'gpp', 'Net assimilation of carbon by the vegetation', 'gC/m^2/s', &
576                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, fluxop_scinsec(4), dt,dw)
577          ENDIF
578          IF ( ok_stomate ) THEN
579             CALL histdef(hist_id, 'nee', 'Net Ecosystem Exchange', 'gC/m^2/s', &
580                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, fluxop_scinsec(4), dt,dw)
581             CALL histdef(hist_id, 'maint_resp', 'Maintenance respiration', 'gC/m^2/s', &
582                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, fluxop_scinsec(4), dt,dw)
583             CALL histdef(hist_id, 'hetero_resp', 'Heterotrophic respiration', 'gC/m^2/s', &
584                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, fluxop_scinsec(4), dt,dw)
585             CALL histdef(hist_id, 'growth_resp', 'Growth respiration', 'gC/m^2/s', &
586                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, fluxop_scinsec(4), dt,dw)
587             CALL histdef(hist_id, 'npp', 'Net Primary Production', 'gC/m^2/s', &
588                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, fluxop_scinsec(1), dt, dw)
589          ENDIF
590          CALL histdef(hist_id, 'precisol', 'Throughfall', 'mm/d',  &
591               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, fluxop(4), dt,dw)
592          CALL histdef(hist_id, 'drysoil_frac', 'Fraction of visibly dry soil', '1',  &
593               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(4), dt,dw)
594          CALL histdef(hist_id, 'evapot', 'Potential evaporation', 'mm/d',  &
595               & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop(4), dt,dw)
596          CALL histdef(hist_id, 'evapot_corr', 'Potential evaporation', 'mm/d',  &
597               & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop(4), dt,dw)
598          !-
599          !- SECHIBA_HISTLEVEL = 5
600          !-
601          CALL histdef(hist_id, 'swnet', 'Net solar radiation', 'W/m^2',  &
602               & iim,jjm, hori_id, 1,1,1, -99, 32, ave(5), dt,dw)
603          CALL histdef(hist_id, 'swdown', 'Incident solar radiation', 'W/m^2',  &
604               & iim,jjm, hori_id, 1,1,1, -99, 32, ave(5), dt,dw)
605          CALL histdef(hist_id, 'lwdown', 'Absorbed downward longwave radiation', 'W/m^2',  &
606               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(5), dt,dw)
607          CALL histdef(hist_id, 'lwnet', 'Net surface longwave radiation', 'W/m^2',  &
608               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(5), dt,dw)
609          !-
610          !- SECHIBA_HISTLEVEL = 6
611          !-
612          CALL histdef(hist_id, 'ptn', 'Deep ground temperature', 'K', &
613               & iim,jjm, hori_id, ngrnd, 1, ngrnd, solax_id, 32, avescatter(6),  dt,dw)
614          CALL histdef(hist_id, 'snowmelt', 'snow melt', 'kg/m2', &
615               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(6), dt,dw)
616          CALL histdef(hist_id, 'frac_snow_veg', 'snow fraction on vegeted area','-', &
617               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(6), dt,dw)
618          CALL histdef(hist_id, 'frac_snow_nobio', 'snow fraction on non-vegeted area', '-', &
619               & iim,jjm, hori_id, nnobio, 1,nnobio, nobioax_id, 32, avescatter(6), dt,dw)
620          CALL histdef(hist_id, 'pgflux', 'extra energy used for melting top snow layer', '-', &
621               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(6), dt,dw)
622
623          IF (ok_explicitsnow) THEN
624             CALL histdef(hist_id, 'grndflux', 'ground heat flux', 'W/m2', &
625                  & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(6), dt,dw)
626             CALL histdef(hist_id, 'sfcfrz', 'surface frozen fraction', '-', &
627                  & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(6), dt,dw)
628             CALL histdef(hist_id, 'snowrho', 'Snow density profile', 'kg/m3', & 
629                  & iim,jjm, hori_id, nsnow, 1, nsnow, snowax_id, 32,avescatter(6), dt,dw)
630             CALL histdef(hist_id, 'snowtemp','Snow temperature profile','K', &
631                  & iim,jjm, hori_id, nsnow, 1, nsnow, snowax_id, 32,avescatter(6),dt,dw)
632             CALL histdef(hist_id, 'snowdz','Snow depth profile','m', &
633                  & iim,jjm, hori_id, nsnow, 1, nsnow, snowax_id, 32,avescatter(6),dt,dw)
634             CALL histdef(hist_id, 'snowliq','Snow liquid content profile','m', &
635                  & iim,jjm, hori_id, nsnow, 1, nsnow, snowax_id, 32,avescatter(6),dt,dw)
636             CALL histdef(hist_id, 'snowgrain','Snow grain profile','m', &
637                  & iim,jjm, hori_id, nsnow, 1, nsnow, snowax_id, 32,avescatter(6),dt,dw)
638             CALL histdef(hist_id, 'snowheat','Snow Heat profile','J/m2', &
639                  & iim,jjm, hori_id, nsnow, 1, nsnow, snowax_id, 32,avescatter(6),dt,dw)
640             CALL histdef(hist_id, 'radsink','Solar Radiation profile','W/m2', &
641                  & iim,jjm, hori_id, nsnow, 1, nsnow, snowax_id, 32,avescatter(6),dt,dw)
642          END IF
643          CALL histdef(hist_id, 'Qg', 'Ground heat flux', 'W/m^2',  &
644               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
645
646          IF (hydrol_cwrr) THEN
647             IF (ok_freeze_thermix) THEN
648                CALL histdef(hist_id, 'profil_froz', 'Frozen fraction of the soil', '-', &
649                     & iim,jjm, hori_id, ngrnd, 1, ngrnd, solax_id, 32, avescatter(6),  dt,dw)
650             END IF
651             CALL histdef(hist_id, 'pkappa', 'Soil thermal conductivity', 'W/m/K', &
652                  & iim,jjm,hori_id, ngrnd, 1, ngrnd, solax_id, 32, avescatter(1),  dt,dw)
653             CALL histdef(hist_id, 'pcapa', 'Apparent heat capacity', 'J/m3/K', &
654                  & iim,jjm,hori_id, ngrnd, 1, ngrnd, solax_id, 32, avescatter(1),  dt,dw)
655          END IF
656
657          !-
658          !- SECHIBA_HISTLEVEL = 7
659          !-
660          IF ( river_routing ) THEN
661             CALL histdef(hist_id, 'fastr', 'Fast flow reservoir', 'kg/m^2', &
662                  & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(7), dt,dw)
663             CALL histdef(hist_id, 'slowr', 'Slow flow reservoir', 'kg/m^2', &
664                  & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(7), dt,dw)
665             CALL histdef(hist_id, 'streamr', 'Stream flow reservoir', 'kg/m^2', &
666                  & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(7), dt,dw)
667             CALL histdef(hist_id, 'lakevol', 'Volume in lake reservoir', 'kg/m^2', &
668                  & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(7), dt,dw)
669             
670             !-
671             !- SECHIBA_HISTLEVEL = 8
672             !-
673             CALL histdef(hist_id, 'pondr', 'Ponds reservoir', 'kg/m^2', &
674                  & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(8), dt,dw)
675             CALL histdef(hist_id, 'swampmap', 'Map of swamps', 'm^2', &
676                  & iim,jjm, hori_id, 1,1,1, -99, 32, once(8), dt,dw)
677             !
678             IF ( do_irrigation ) THEN
679                CALL histdef(hist_id, 'irrigation', 'Net irrigation', 'mm/d', &
680                     & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop(8), dt,dw)
681                CALL histdef(hist_id, 'netirrig', 'Net irrigation requirement', 'mm/d', &
682                     & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop(8), dt,dw)
683                CALL histdef(hist_id, 'irrigmap', 'Map of irrigated surfaces', 'm^2', &
684                     & iim,jjm, hori_id, 1,1,1, -99, 32, once(8), dt,dw)
685             ENDIF
686             IF ( do_floodplains ) THEN
687                CALL histdef(hist_id, 'floodmap', 'Map of floodplains', 'm^2', &
688                     & iim,jjm, hori_id, 1,1,1, -99, 32, once(8), dt,dw)
689                CALL histdef(hist_id, 'floodh', 'Floodplains height', 'mm', &
690                     & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(8), dt,dw)
691                CALL histdef(hist_id, 'floodr', 'Floodplains reservoir', 'kg/m^2', &
692                     & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(8), dt,dw)
693                CALL histdef(hist_id, 'floodout', 'Flow out of floodplains', 'mm/d', &
694                     & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop(8), dt,dw)
695                CALL histdef(hist_id, 'evapflo', 'Floodplains evaporation', 'mm/d', &
696                     & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop(8), dt,dw)
697             ENDIF
698             !
699          ENDIF
700
701          IF ( hydrol_cwrr ) THEN
702             CALL histdef(hist_id, 'k_litt', 'Litter cond', 'mm/d', &
703                  & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(8), dt,dw)
704          ENDIF
705          CALL histdef(hist_id, 'beta', 'Beta Function', '1',  &
706               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(8), dt,dw)
707          CALL histdef(hist_id, 'raero', 'Aerodynamic resistance', 's/m',  &
708               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(8), dt,dw)
709          CALL histdef(hist_id, 'cdrag', 'Drag coefficient for LE and SH', '?',  &
710               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(8), dt,dw)
711          CALL histdef(hist_id, 'Wind', 'Wind speed', 'm/s',  &
712               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(8), dt,dw)
713          CALL histdef(hist_id, 'qsatt' , 'Surface saturated humidity', 'g/g', &
714               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(8), dt,dw)
715          CALL histdef(hist_id, 'vbeta1', 'Beta for sublimation', '1',  &
716               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(8), dt,dw)
717          CALL histdef(hist_id, 'vbeta4', 'Beta for bare soil', '1',  &
718               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(8), dt,dw)
719          CALL histdef(hist_id, 'vbeta5', 'Beta for floodplains', '1',  &
720               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(8), dt,dw)
721          IF ( ok_co2 ) THEN
722             CALL histdef(hist_id, 'gsmean', 'mean stomatal conductance', 'umol/m2/s', &
723                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(8), dt,dw)
724          ENDIF
725          CALL histdef(hist_id, 'humrel', 'Soil moisture stress', '-',  &
726               & iim,jjm, hori_id, nvm,1,nvm, vegax_id, 32, avescatter(8), dt,dw)
727          !-
728          !- SECHIBA_HISTLEVEL = 9
729          !-
730          !-
731          !- SECHIBA_HISTLEVEL = 10
732          !-
733          IF ( ok_co2 ) THEN
734             CALL histdef(hist_id, 'cimean', 'Stomatal CO2 concentation', 'mmole/m2/s', &
735                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(10), dt,dw)
736             CALL histdef(hist_id, 'cim', 'cim', 'ppm', &
737                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(10), dt,dw)
738          ENDIF
739          CALL histdef(hist_id, 'vbeta3', 'Beta for Transpiration', 'mm/d', &
740               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(10), dt,dw)
741          CALL histdef(hist_id, 'rveget', 'Canopy resistance', 's/m', &
742               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(10), dt,dw)
743          IF ( .NOT. hydrol_cwrr ) THEN
744             CALL histdef(hist_id, 'rsol', 'Soil resistance', 's/m',  &
745                  & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(10), dt,dw)
746          ENDIF
747          CALL histdef(hist_id,'vbeta2','Beta for Interception loss','mm/d', &
748               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(10), dt,dw)
749          CALL histdef(hist_id, 'qsintmax', 'Maximum Interception capacity', 'Kg/m^2', &
750               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(10), dt,dw)
751
752          !- SECHIBA_HISTLEVEL = 11
753          !-
754
755          CALL histdef(hist_id, 'mrsos', "Moisture in Upper 0.1 m of Soil Column", "kg m-2", &
756               & iim,jjm, hori_id, 1, 1, 1, -99, 32, avescatter(11), dt,dw)
757         
758          CALL histdef(hist_id, 'mrso', "Total Soil Moisture Content", "kg m-2", &
759               & iim,jjm, hori_id, 1, 1, 1, -99, 32, avescatter(11), dt,dw)
760         
761          CALL histdef(hist_id, 'mrros', "Surface Runoff", "kg m-2 s-1", &
762               & iim,jjm, hori_id, 1, 1, 1, -99, 32, fluxop_scinsec(11), dt,dw)
763         
764          CALL histdef(hist_id, 'mrro', "Total Runoff", "kg m-2 s-1", &
765               & iim,jjm, hori_id, 1, 1, 1, -99, 32, fluxop_scinsec(11), dt,dw)
766
767          CALL histdef(hist_id, 'prveg', "Precipitation onto Canopy", "kg m-2 s-1", &
768               & iim,jjm, hori_id, 1, 1, 1, -99, 32, fluxop_scinsec(11), dt,dw)
769
770
771          CALL histdef(hist_id, 'evspsblveg', "Evaporation from Canopy", "kg m-2 s-1", &
772               & iim,jjm, hori_id, 1, 1, 1, -99, 32, fluxop_scinsec(11), dt,dw)
773         
774          CALL histdef(hist_id, 'evspsblsoi', "Water Evaporation from Soil", "kg m-2 s-1", &
775               & iim,jjm, hori_id, 1, 1, 1, -99, 32, fluxop_scinsec(11), dt,dw)
776         
777          CALL histdef(hist_id, 'tran', "Transpiration", "kg m-2 s-1", &
778               & iim,jjm, hori_id, 1, 1, 1, -99, 32, fluxop_scinsec(11), dt,dw)
779         
780          CALL histdef(hist_id, 'treeFrac', "Tree Cover Fraction", "%", &
781               & iim,jjm, hori_id, 1, 1, 1, -99, 32, avescatter(11), dt,dw)
782         
783          CALL histdef(hist_id, 'grassFrac', "Natural Grass Fraction", "%", &
784               & iim,jjm, hori_id, 1, 1, 1, -99, 32, avescatter(11), dt,dw)
785         
786          CALL histdef(hist_id, 'cropFrac', "Crop Fraction", "%", &
787               & iim,jjm, hori_id, 1, 1, 1, -99, 32, avescatter(11), dt,dw)
788         
789          CALL histdef(hist_id, 'baresoilFrac', "Bare Soil Fraction", "%", &
790               & iim,jjm, hori_id, 1, 1, 1, -99, 32, avescatter(11), dt,dw)
791         
792          CALL histdef(hist_id, 'residualFrac', &
793               & "Fraction of Grid Cell that is Land but Neither Vegetation-Covered nor Bare Soil", "%", &
794               & iim,jjm, hori_id, 1, 1, 1, -99, 32, avescatter(11), dt,dw)
795         
796          IF ( ok_bvoc ) THEN
797             CALL histdef(hist_id, 'PAR', 'PAR', 'umol phot/m^2/s',  &
798                  & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(11), dt,dw)
799             IF ( ok_radcanopy ) THEN
800                CALL histdef(hist_id, 'PARsun', 'Sunlit Leaf PAR', 'umol phot/m^2/s', &
801                     & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(11), dt,dw)
802                CALL histdef(hist_id, 'PARsh', 'Shaded Leaf Area PAR', 'umol phot/m^2/s', &
803                     & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(11), dt,dw)
804                CALL histdef(hist_id, 'laisun', 'Sunlit Leaf Area Index', '1', &
805                     & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(11), dt,dw)
806                CALL histdef(hist_id, 'laish', 'Shaded Leaf Area Index', '1', &
807                     & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(11), dt,dw)
808                CALL histdef(hist_id, 'Fdf', 'Fdf', '1',  &
809                     & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(11), dt,dw)
810                IF ( ok_multilayer ) then
811                   CALL histdef(hist_id, 'PARsuntab', 'Sunlit Leaf PAR', 'umol phot/m^2/s', &
812                        & iim,jjm, hori_id, nlai+1, 1, nlai+1, laiax_id, 32, avescatter(11), dt,dw)
813                   CALL histdef(hist_id, 'PARshtab', 'Shaded Leaf Area PAR', 'umol phot/m^2/s', &
814                        & iim,jjm, hori_id, nlai+1, 1, nlai+1, laiax_id, 32, avescatter(11), dt,dw)
815                ENDIF
816                CALL histdef(hist_id, 'coszang', 'coszang', '1',  &
817                     & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(11), dt,dw)
818                CALL histdef(hist_id, 'PARdf', 'PARdf', '1',  &
819                     & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(11), dt,dw)
820                CALL histdef(hist_id, 'PARdr', 'PARdr', '1',  &
821                     & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(11), dt,dw)
822                CALL histdef(hist_id, 'Trans', 'Trans', '1',  &
823                     & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(11), dt,dw)
824             END IF
825             
826             CALL histdef(hist_id, 'flx_fertil_no', 'flx_fertil_no', 'ngN/m^2/s', &
827                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(11), dt,dw)
828             CALL histdef(hist_id, 'CRF', 'CRF', '1', &
829                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(11), dt,dw)
830             CALL histdef(hist_id, 'flx_co2_bbg_year', 'flx_co2_bbg_year', 'kgC/m^2/yr ', &
831                  & iim,jjm, hori_id, 1,1,1, -99, 32, once(11), dt,dw) 
832             CALL histdef(hist_id, 'N_qt_WRICE_year', 'N_qt_WRICE_year', 'kgN/yr ', &
833                  & iim,jjm, hori_id, 1,1,1, -99, 32, once(11), dt,dw) 
834             CALL histdef(hist_id, 'N_qt_OTHER_year', 'N_qt_OTHER_year', 'kgN/yr ', &
835                  & iim,jjm, hori_id, 1,1,1, -99, 32, once(11), dt,dw) 
836             CALL histdef(hist_id, 'flx_iso', 'flx_iso', 'kgC/m^2/s', &
837                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(11), dt,dw)
838             CALL histdef(hist_id, 'flx_mono', 'flx_mono', 'kgC/m^2/s',&
839                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(11), dt,dw)
840             CALL histdef(hist_id, 'flx_apinen', 'flx_apinen', 'kgC/m^2/s',&
841                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(11), dt,dw)
842             CALL histdef(hist_id, 'flx_bpinen', 'flx_bpinen', 'kgC/m^2/s',&
843                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(11), dt,dw)
844             CALL histdef(hist_id, 'flx_limonen', 'flx_limonen', 'kgC/m^2/s',&
845                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(11), dt,dw)
846             CALL histdef(hist_id, 'flx_myrcen', 'flx_myrcen', 'kgC/m^2/s',&
847                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(11), dt,dw)
848             CALL histdef(hist_id, 'flx_sabinen', 'flx_sabinen', 'kgC/m^2/s',&
849                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(11), dt,dw)
850             CALL histdef(hist_id, 'flx_camphen', 'flx_camphen', 'kgC/m^2/s',&
851                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(11), dt,dw)
852             CALL histdef(hist_id, 'flx_3caren', 'flx_3caren', 'kgC/m^2/s',&
853                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(11), dt,dw)
854             CALL histdef(hist_id, 'flx_tbocimen', 'flx_tbocimen', 'kgC/m^2/s',&
855                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(11), dt,dw)
856             CALL histdef(hist_id, 'flx_othermono', 'flx_othermono', 'kgC/m^2/s',&
857                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(11), dt,dw)
858             CALL histdef(hist_id, 'flx_sesquiter', 'flx_sesquiter', 'kgC/m^2/s',&
859                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(11), dt,dw)
860             CALL histdef(hist_id, 'flx_ORVOC', 'flx_ORVOC', 'kgC/m^2/s',&
861                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(11), dt,dw)
862             CALL histdef(hist_id, 'flx_MBO', 'flx_MBO', 'kgC/m^2/s',&
863                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(11), dt,dw)
864             CALL histdef(hist_id, 'flx_methanol', 'flx_methanol', 'kgC/m^2/s',&
865                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(11), dt,dw)
866             CALL histdef(hist_id, 'flx_acetone', 'flx_acetone', 'kgC/m^2/s',&
867                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(11), dt,dw)
868             CALL histdef(hist_id, 'flx_acetal', 'flx_acetal', 'kgC/m^2/s',&
869                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(11), dt,dw)
870             CALL histdef(hist_id, 'flx_formal', 'flx_formal', 'kgC/m^2/s',&
871                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(11), dt,dw)
872             CALL histdef(hist_id, 'flx_acetic', 'flx_acetic', 'kgC/m^2/s',&
873                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(11), dt,dw)
874             CALL histdef(hist_id, 'flx_formic', 'flx_formic', 'kgC/m^2/s',&
875                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(11), dt,dw)
876             CALL histdef(hist_id, 'flx_no_soil', 'flx_no_soil', 'ngN/m^2/s',&
877                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(11), dt,dw)
878             CALL histdef(hist_id, 'flx_no', 'flx_no', 'ngN/m^2/s',&
879                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(11), dt,dw)
880             CALL histdef(hist_id, 'fco2', 'fco2', '-', &
881                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(10), dt,dw)
882          ENDIF
883
884       ELSE 
885          !-
886          !- This is the ALMA convention output now
887          !-
888          !-
889          IF ( GridType == "RegLonLat" ) THEN
890#ifdef CPP_PARA
891             CALL histbeg(histname, iim, lon_rect, jjm, lat_rect, 1, iim, 1, jjm, &
892                  &     istp_old, date0, dt, hori_id, hist_id,orch_domain_id)
893#else
894             CALL histbeg(histname, iim, lon_rect, jjm, lat_rect, 1, iim, 1, jjm, &
895                  &     istp_old, date0, dt, hori_id, hist_id)
896#endif
897          ELSE
898#ifdef CPP_PARA
899             CALL histbeg(histname, iim, lon, jjm, lat, 1, iim, 1, jjm, &
900                  &     istp_old, date0, dt, hori_id, hist_id,domain_id=orch_domain_id)
901#else
902             CALL histbeg(histname, iim, lon, jjm, lat, 1, iim, 1, jjm, &
903                  &     istp_old, date0, dt, hori_id, hist_id)
904#endif
905          ENDIF
906          !-
907          CALL histvert(hist_id, 'veget', 'Vegetation types', '1', &
908               &    nvm,   veg, vegax_id)
909          CALL histvert(hist_id, 'solth', 'Soil levels',      'm', &
910               &    ngrnd, sol, solax_id)
911          CALL histvert(hist_id, 'soiltyp', 'Soil types',      '1', &
912               &    nstm, soltyp, soltax_id)
913          CALL histvert(hist_id, 'nobio', 'Other surface types',      '1', &
914               &    nnobio, nobiotyp, nobioax_id)
915          IF (  hydrol_cwrr ) THEN
916             CALL histvert(hist_id, 'solay', 'Hydrol soil levels',      'm', &
917                  &    nslm, diaglev(1:nslm), solayax_id)
918          ENDIF
919          !-
920          !-  Vegetation
921          !-
922          CALL histdef(hist_id, 'vegetfrac', 'Fraction of vegetation', '1', &
923               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(3), dt,dw)
924          CALL histdef(hist_id, 'maxvegetfrac', 'Maximum fraction of vegetation', '1', &
925               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(3), dt,dw)
926          CALL histdef(hist_id, 'nobiofrac', 'Fraction of other surface types', '1', &
927               & iim,jjm, hori_id, nnobio, 1, nnobio, nobioax_id, 32, avescatter(3), dt,dw)
928          CALL histdef(hist_id, 'lai', 'Leaf Area Index', '1', &
929               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(1), dt,dw)
930          !-
931          !- Forcing variables
932          !-
933          CALL histdef(hist_id, 'SinAng', 'Net shortwave radiation', '-',  &
934               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(9), dt,dw)
935          CALL histdef(hist_id, 'LWdown', 'Downward longwave radiation', 'W/m^2',  &
936               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(9), dt,dw)
937          CALL histdef(hist_id, 'SWdown', 'Downward shortwave radiation', 'W/m^2',  &
938               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(9), dt,dw)
939          CALL histdef(hist_id, 'Tair', 'Near surface air temperature at forcing level', 'K',  &
940               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(2), dt,dw)
941          CALL histdef(hist_id, 'Qair', 'Near surface specific humidity at forcing level', 'g/g',  &
942               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(2), dt,dw)
943          CALL histdef(hist_id, 'SurfP', 'Surface Pressure', 'hPa',  &
944               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(9), dt,dw)
945          CALL histdef(hist_id, 'Windu', 'Eastward wind', 'm/s',  &
946               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(9), dt,dw)
947          CALL histdef(hist_id, 'Windv', 'Northward wind', 'm/s',  &
948               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(9), dt,dw)
949          !-
950          !-  General energy balance
951          !-
952          CALL histdef(hist_id, 'SWnet', 'Net shortwave radiation', 'W/m^2',  &
953               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
954          CALL histdef(hist_id, 'LWnet', 'Net longwave radiation', 'W/m^2',  &
955               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
956          CALL histdef(hist_id, 'Qh', 'Sensible heat flux', 'W/m^2',  &
957               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
958          CALL histdef(hist_id, 'Qle', 'Latent heat flux', 'W/m^2',  &
959               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
960          CALL histdef(hist_id, 'Qg', 'Ground heat flux', 'W/m^2',  &
961               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
962          CALL histdef(hist_id, 'Qf', 'Energy of fusion', 'W/m^2',  &
963               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(2), dt,dw)
964          CALL histdef(hist_id, 'Qv', 'Energy of sublimation', 'W/m^2',  &
965               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
966          CALL histdef(hist_id, 'DelSurfHeat', 'Change in surface layer heat', 'J/m^2',  &
967               & iim,jjm, hori_id, 1,1,1, -99, 32, sumscatter(1), dt,dw)
968          CALL histdef(hist_id, 'DelColdCont', 'Change in snow surface layer cold content', 'J/m^2',  &
969               & iim,jjm, hori_id, 1,1,1, -99, 32, sumscatter(1), dt,dw)
970          !-
971          !- General water balance
972          !-
973          CALL histdef(hist_id, 'Snowf', 'Snowfall rate', 'kg/m^2/s',  &
974               & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop_scinsec(1), dt,dw)
975          CALL histdef(hist_id, 'Rainf', 'Rainfall rate', 'kg/m^2/s',  &
976               & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop_scinsec(1), dt,dw)
977          CALL histdef(hist_id, 'Evap', 'Total Evapotranspiration', 'kg/m^2/s', &
978               & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop_scinsec(1), dt,dw)
979          CALL histdef(hist_id, 'Qs', 'Surface runoff', 'kg/m^2/s', &
980               & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop_scinsec(1), dt,dw)
981          CALL histdef(hist_id, 'Qsb', 'Sub-surface runoff', 'kg/m^2/s', &
982               & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop_scinsec(1), dt,dw)
983          CALL histdef(hist_id, 'Qrec', 'Recharge', 'kg/m^2/s', &
984               & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop_scinsec(1), dt,dw)
985          CALL histdef(hist_id, 'Qsm', 'Snowmelt', 'kg/m^2/s', &
986               & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop_scinsec(1), dt,dw)
987          CALL histdef(hist_id, 'DelSoilMoist', 'Change in soil moisture', 'kg/m^2',  &
988               & iim,jjm, hori_id, 1, 1, 1, -99, 32, sumscatter(1), dt,dw)
989          CALL histdef(hist_id, 'DelSurfStor', 'Change in Surface Water Storage','kg/m^2',&
990               & iim,jjm, hori_id, 1, 1, 1, -99, 32, sumscatter(1), dt,dw)
991          CALL histdef(hist_id, 'DelIntercept', 'Change in interception storage', 'kg/m^2',  &
992               & iim,jjm, hori_id, 1, 1, 1, -99, 32, sumscatter(1), dt,dw)
993          CALL histdef(hist_id, 'DelSWE', 'Change in Snow Water Equivalent', 'kg/m^2',  &
994               & iim,jjm, hori_id, 1, 1, 1, -99, 32, sumscatter(1), dt,dw)
995          IF ( do_irrigation ) THEN
996             CALL histdef(hist_id, 'Qirrig', 'Irrigation', 'kg/m^2/s', &
997                  & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop_scinsec(1), dt,dw)
998             CALL histdef(hist_id, 'Qirrig_req', 'Irrigation requirement', 'kg/m^2/s', &
999                  & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop_scinsec(1), dt,dw)
1000          ENDIF
1001          !-
1002          !- Surface state
1003          !-
1004          CALL histdef(hist_id, 'AvgSurfT', 'Average surface temperature', 'K', &
1005               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
1006          CALL histdef(hist_id, 'PotSurfT', 'Potential (Unstressed) surface temperature', 'K', &
1007               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
1008          CALL histdef(hist_id, 'RadT', 'Surface radiative temperature', 'K', &
1009               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
1010          CALL histdef(hist_id, 'Albedo', 'Albedo', '1', &
1011               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
1012          CALL histdef(hist_id, 'SWI', 'Soil wetness index','1',  &
1013               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
1014          CALL histdef(hist_id, 'SurfStor', 'Surface Water Storage','kg/m^2',  &
1015               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
1016          CALL histdef(hist_id, 'SWE', 'Snow Water Equivalent', 'kg/m^2', &
1017               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
1018          CALL histdef(hist_id, 'InterceptVeg', 'Intercepted Water on Canopy', 'Kg/m^2', &
1019               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(1), dt,dw)
1020          !!-
1021          !-  Sub-surface state
1022          !-
1023          IF ( .NOT. hydrol_cwrr ) THEN
1024             CALL histdef(hist_id, 'SoilMoist', '3D average layer soil moisture', 'kg/m^2',  &
1025                  & iim,jjm, hori_id, 1, 1, 1, -99, 32, avescatter(1), dt,dw)
1026          ELSE
1027             CALL histdef(hist_id, 'SoilMoist', '3D average layer soil moisture', 'kg/m^2',  &
1028                  & iim,jjm, hori_id, nslm, 1, nslm, solayax_id, 32, avescatter(1), dt,dw)
1029
1030             IF (ok_freeze_cwrr) THEN
1031                CALL histdef(hist_id, 'profil_froz_hydro', 'Frozen fraction for each hydrological soil layer', '-', &
1032                     & iim,jjm, hori_id, nslm, 1, nslm,solayax_id, 32, avescatter(1),  dt,dw)
1033                DO jst=1,nstm
1034                   WRITE (var_name,"('profil_froz_hydro_',i1)") jst
1035                   CALL histdef(hist_id, trim(var_name), 'Frozen fraction for each hydrological soil layer and soiltile', '-', &
1036                        & iim,jjm, hori_id, nslm, 1, nslm, solayax_id, 32, avescatter(1),  dt,dw)
1037                ENDDO
1038
1039                CALL histdef(hist_id, 'temp_hydro', 'Soil temperature interpolated on hydrological layers', 'K', &
1040                     & iim,jjm, hori_id, nslm, 1, nslm, solayax_id, 32, avescatter(1), dt,dw)
1041                CALL histdef(hist_id, 'kk_moy', 'Mean hydrological conductivity', 'mm/d', &
1042                     & iim,jjm,hori_id, nslm,1,nslm, solayax_id, 32, avescatter(1),  dt,dw)
1043             ENDIF
1044          END IF
1045          CALL histdef(hist_id, 'SoilWet', 'Total soil wetness', '-',  &
1046               & iim,jjm, hori_id, 1, 1, 1, -99, 32, avescatter(1), dt,dw)
1047          CALL histdef(hist_id, 'SoilTemp', 'Soil temperature profile', 'K', &
1048               & iim,jjm, hori_id, ngrnd, 1, ngrnd, solax_id, 32, avescatter(1),  dt,dw)
1049          !-
1050          !-  Evaporation components
1051          !-
1052          CALL histdef(hist_id, 'PotEvap', 'Potential evapotranspiration', 'kg/m^2/s', &
1053               & iim,jjm, hori_id, 1, 1, 1, -99, 32, fluxop_scinsec(1), dt,dw)
1054          CALL histdef(hist_id, 'PotEvapOld', 'Potential evapotranspiration old method', 'kg/m^2/s', &
1055               & iim,jjm, hori_id, 1, 1, 1, -99, 32, fluxop_scinsec(1), dt,dw)
1056          CALL histdef(hist_id, 'ECanop', 'Interception evaporation', 'kg/m^2/s', &
1057               & iim,jjm, hori_id, 1, 1, 1, -99, 32, fluxop_scinsec(1), dt,dw)
1058          CALL histdef(hist_id, 'TVeg', 'Transpiration', 'kg/m^2/s', &
1059               & iim,jjm, hori_id, 1, 1, 1, -99, 32, fluxop_scinsec(1), dt,dw)
1060          CALL histdef(hist_id, 'ESoil', 'Bare soil evaporation', 'kg/m^2/s', &
1061               & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop_scinsec(1), dt,dw)
1062          CALL histdef(hist_id, 'EWater', 'Open water evaporation', 'kg/m^2/s', &
1063               & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop_scinsec(1), dt,dw)
1064          CALL histdef(hist_id, 'RootMoist','Root zone soil water', 'kg/m^2',  &
1065               & iim,jjm, hori_id, 1, 1, 1, -99, 32, avescatter(1), dt,dw)
1066          CALL histdef(hist_id, 'SubSnow','Snow sublimation','kg/m^2/s', &
1067               & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop_scinsec(1), dt,dw)
1068          CALL histdef(hist_id, 'ACond', 'Aerodynamic conductance', 'm/s',  &
1069               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
1070          IF ( do_floodplains ) THEN
1071             CALL histdef(hist_id, 'Qflood', 'Floodplain Evaporation', 'kg/m^2/s', &
1072                  & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop_scinsec(1), dt,dw)
1073          ENDIF
1074          !-
1075          !- Surface turbulence
1076          !-
1077          CALL histdef(hist_id, 'Z0m', 'Roughness height for momentum', 'm',  &
1078               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
1079          CALL histdef(hist_id, 'Z0h', 'Roughness height for heat', 'm',  &
1080               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
1081          CALL histdef(hist_id, 'EffectHeight', 'Effective displacement height (h-d)', 'm',  &
1082               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
1083          !-
1084          !-
1085          !-  Cold Season Processes
1086          !-
1087          CALL histdef(hist_id, 'SnowFrac', 'Snow cover fraction', '1',  &
1088               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
1089          CALL histdef(hist_id, 'SAlbedo', 'Snow albedo', '1', &
1090               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
1091          CALL histdef(hist_id, 'SnowDepth', '3D snow depth', 'm', &
1092               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
1093          !-
1094          !- Hydrologic variables
1095          !-
1096          IF ( river_routing ) THEN
1097             CALL histdef(hist_id, 'slowr', 'Slow flow reservoir', 'kg/m^2', &
1098                  & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
1099             CALL histdef(hist_id, 'fastr', 'Fast flow reservoir', 'kg/m^2', &
1100                  & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
1101             CALL histdef(hist_id, 'streamr', 'Stream flow reservoir', 'kg/m^2', &
1102                  & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
1103             CALL histdef(hist_id, 'lakevol', 'Volume in lake reservoir', 'kg/m^2', &
1104                  & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
1105             CALL histdef(hist_id, 'pondr', 'Ponds reservoir', 'kg/m^2', &
1106                  & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
1107             !-
1108             !-
1109             !-
1110             CALL histdef(hist_id, 'SwampMap', 'Map of swamp areas', 'm^2', &
1111                  & iim,jjm, hori_id, 1,1,1, -99, 32, once(1), dt,dw)
1112             CALL histdef(hist_id, 'Dis', 'Simulated River Discharge', 'm^3/s', &
1113                  & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop_scinsec(2), dt,dw)
1114             CALL histdef(hist_id, 'CoastalFlow', 'Diffuse coastal flow', 'm^3/s', &
1115                  & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop_scinsec(2), dt,dw)
1116             CALL histdef(hist_id, 'RiverFlow', 'River flow to the oceans', 'm^3/s', &
1117                  & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop_scinsec(2), dt,dw)
1118             IF ( do_irrigation ) THEN
1119                CALL histdef(hist_id, 'IrrigationMap', 'Map of irrigated areas', 'm^2', &
1120                     & iim,jjm, hori_id, 1,1,1, -99, 32, once(1), dt,dw)
1121             ENDIF
1122             !
1123             !
1124             IF ( do_floodplains ) THEN
1125                CALL histdef(hist_id, 'FloodplainsMap', 'Map of flooded areas', 'm^2', &
1126                     & iim,jjm, hori_id, 1,1,1, -99, 32, once(1), dt,dw)
1127                CALL histdef(hist_id, 'FloodFrac', 'Floodplain Fraction', '-', &
1128                     & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
1129             ENDIF
1130          ENDIF
1131          !-
1132          CALL histdef(hist_id, 'humrel', 'Soil moisture stress', '-',  &
1133               & iim,jjm, hori_id, nvm,1,nvm, vegax_id, 32, avescatter(8), dt,dw)
1134          !-
1135          !-  The carbon budget
1136          !-
1137          IF ( ok_co2 ) THEN
1138             CALL histdef(hist_id, 'GPP', 'Net assimilation of carbon by the vegetation', 'gC/m^2/s', &
1139                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, fluxop_scinsec(1), dt,dw)
1140          ENDIF
1141          IF ( ok_stomate ) THEN
1142             CALL histdef(hist_id, 'NEE', 'Net Ecosystem Exchange', 'gC/m^2/s', &
1143                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, fluxop_scinsec(1), dt,dw)
1144             CALL histdef(hist_id, 'maint_resp', 'Maintenance respiration', 'gC/m^2/s', &
1145                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, fluxop_scinsec(1), dt,dw)
1146             CALL histdef(hist_id, 'hetero_resp', 'Heterotrophic respiration', 'gC/m^2/s', &
1147                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, fluxop_scinsec(1), dt,dw)
1148             CALL histdef(hist_id, 'growth_resp', 'Growth respiration', 'gC/m^2/s', &
1149                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, fluxop_scinsec(1), dt,dw)
1150             CALL histdef(hist_id, 'npp', 'Net Primary Production', 'gC/m^2/s', &
1151                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, fluxop_scinsec(1), dt,dw)
1152          ENDIF
1153          !
1154      ENDIF
1155       !-
1156       !- Forcing and grid information
1157       !-
1158       CALL histdef(hist_id, 'LandPoints', 'Land Points', '1', &
1159            & iim,jjm, hori_id, 1,1,1, -99, 32, once(1), dt,dw) 
1160       CALL histdef(hist_id, 'Areas', 'Mesh areas', 'm2', &
1161            & iim,jjm, hori_id, 1,1,1, -99, 32, once(1), dt, dw)
1162       CALL histdef(hist_id, 'Contfrac', 'Continental fraction', '1', &
1163            & iim,jjm, hori_id, 1,1,1, -99, 32, once(1), dt, dw)
1164       !-
1165       ! Write the names of the pfts in the history files
1166       global_attribute="PFT_name"
1167       DO i=1,nvm
1168          WRITE(global_attribute(9:10),"(I2.2)") i
1169          CALL histglobal_attr(hist_id, global_attribute, PFT_name(i))
1170       ENDDO
1171       !-
1172       CALL histend(hist_id)
1173    ENDIF ! IF (is_omp_root)
1174 
1175    END IF !IF ( dw == 0 )
1176    !
1177    !
1178    ! Second SECHIBA hist file
1179    !
1180    !-
1181    !Config Key   = SECHIBA_HISTFILE2
1182    !Config Desc  = Flag to switch on histfile 2 for SECHIBA (hi-frequency ?)
1183    !Config If    = OK_SECHIBA
1184    !Config Def   = n
1185    !Config Help  = This Flag switch on the second SECHIBA writing for hi (or low)
1186    !Config         frequency writing. This second output is optional and not written
1187    !Config         by default.
1188    !Config Units = [FLAG]
1189    !-
1190    ok_histfile2=.FALSE.
1191    CALL getin_p('SECHIBA_HISTFILE2', ok_histfile2)
1192    WRITE(numout,*) 'SECHIBA_HISTFILE2 ', ok_histfile2
1193    !
1194    !-
1195    !Config Key   = WRITE_STEP2
1196    !Config Desc  = Frequency in seconds at which to WRITE output
1197    !Config If    = SECHIBA_HISTFILE2
1198    !Config Def   = 1800.0
1199    !Config Help  = This variables gives the frequency the output 2 of
1200    !Config         the model should be written into the netCDF file.
1201    !Config         It does not affect the frequency at which the
1202    !Config         operations such as averaging are done.
1203    !Config         That is IF the coding of the calls to histdef
1204    !Config         are correct !
1205    !Config Units = [seconds]
1206    !-
1207    dw2 = 1800.0
1208    CALL getin_p('WRITE_STEP2', dw2)
1209   
1210    ! Deactivate sechiba_histfile2 if the frequency is set to zero
1211    IF ( dw2 == 0 ) THEN
1212       ok_histfile2=.FALSE.
1213       WRITE(numout,*) 'WRITE_STEP2 was set to zero and therfore SECHIBA_HISTFILE2 is deactivated.'
1214    ELSE IF ( hist_id < 0 ) THEN
1215       ! Deactivate all history files if sechiba_history file is deactivated
1216       ok_histfile2=.FALSE.
1217       WRITE(numout,*) 'SECHIBA_HISTFILE2 will not be created because sechiba_history file is deactivated.'
1218    END IF
1219
1220    hist2_id = -1
1221    !
1222    IF (ok_histfile2) THEN
1223       !-
1224       !Config Key   = SECHIBA_OUTPUT_FILE2
1225       !Config Desc  = Name of file in which the output number 2 is going to be written
1226       !Config If    = SECHIBA_HISTFILE2
1227       !Config Def   = sechiba_out_2.nc
1228       !Config Help  = This file is going to be created by the model
1229       !Config         and will contain the output 2 from the model.
1230       !Config Units = [FILE]
1231       !-
1232       histname2='sechiba_out_2.nc'
1233       CALL getin_p('SECHIBA_OUTPUT_FILE2', histname2)
1234       WRITE(numout,*) 'SECHIBA_OUTPUT_FILE2 ', histname2
1235       !-
1236       !Config Key   = SECHIBA_HISTLEVEL2
1237       !Config Desc  = SECHIBA history 2 output level (0..10)
1238       !Config If    = SECHIBA_HISTFILE2
1239       !Config Def   = 1
1240       !Config Help  = Chooses the list of variables in the history file.
1241       !Config         Values between 0: nothing is written; 10: everything is
1242       !Config         written are available More details can be found on the web under documentation.
1243       !Config         web under documentation.
1244       !Config         First level contains all ORCHIDEE outputs.
1245       !Config Units = [-]
1246       !-
1247       hist2_level = 1
1248       CALL getin_p('SECHIBA_HISTLEVEL2', hist2_level)
1249       !-
1250       WRITE(numout,*) 'SECHIBA history level 2 : ',hist2_level
1251       IF ( (hist2_level > max_hist_level).OR.(hist2_level < 0) ) THEN
1252          STOP 'This history level 2 is not allowed'
1253       ENDIF
1254       !
1255       !-
1256       !- define operations as a function of history level.
1257       !- Above hist2_level, operation='never'
1258       !-
1259       ave2(1:max_hist_level) = 'ave(scatter(X))'
1260       IF (hist2_level < max_hist_level) THEN
1261          ave2(hist2_level+1:max_hist_level) = 'never'
1262       ENDIF
1263       sumscatter2(1:max_hist_level) = 't_sum(scatter(X))'
1264       IF (hist2_level < max_hist_level) THEN
1265          sumscatter2(hist2_level+1:max_hist_level) = 'never'
1266       ENDIF
1267       avecels2(1:max_hist_level) = 'ave(cels(scatter(X)))'
1268       IF (hist2_level < max_hist_level) THEN
1269          avecels2(hist2_level+1:max_hist_level) = 'never'
1270       ENDIF
1271       avescatter2(1:max_hist_level) = 'ave(scatter(X))'
1272       IF (hist2_level < max_hist_level) THEN
1273          avescatter2(hist2_level+1:max_hist_level) = 'never'
1274       ENDIF
1275       tmincels2(1:max_hist_level) = 't_min(cels(scatter(X)))'
1276       IF (hist2_level < max_hist_level) THEN
1277          tmincels2(hist2_level+1:max_hist_level) = 'never'
1278       ENDIF
1279       tmaxcels2(1:max_hist_level) = 't_max(cels(scatter(X)))'
1280       IF (hist2_level < max_hist_level) THEN
1281          tmaxcels2(hist2_level+1:max_hist_level) = 'never'
1282       ENDIF
1283       fluxop2(1:max_hist_level) = flux_op
1284       IF (hist2_level < max_hist_level) THEN
1285          fluxop2(hist2_level+1:max_hist_level) = 'never'
1286       ENDIF
1287       fluxop_scinsec2(1:max_hist_level) = flux_scinsec
1288       IF (hist2_level < max_hist_level) THEN
1289          fluxop_scinsec2(hist2_level+1:max_hist_level) = 'never'
1290       ENDIF
1291       once2(1:max_hist_level) = 'once(scatter(X))'
1292       IF (hist2_level < max_hist_level) THEN
1293          once2(hist2_level+1:max_hist_level) = 'never'
1294       ENDIF
1295       !
1296       IF (is_omp_root) THEN
1297          IF ( .NOT. almaoutput ) THEN
1298             !-
1299             IF ( GridType == "RegLonLat" ) THEN
1300#ifdef CPP_PARA
1301                CALL histbeg(histname2, iim, lon_rect, jjm, lat_rect, 1, iim, 1, jjm, &
1302                     &     istp_old, date0, dt, hori_id2, hist2_id,orch_domain_id)
1303#else
1304                CALL histbeg(histname2, iim, lon_rect, jjm, lat_rect, 1, iim, 1, jjm, &
1305                     &     istp_old, date0, dt, hori_id2, hist2_id)
1306#endif
1307                WRITE(numout,*)  'HISTBEG2 --->',istp_old,date0,dt,dw2,hist2_id
1308             ELSE
1309#ifdef CPP_PARA
1310                CALL histbeg(histname2, iim, lon, jjm, lat, 1, iim, 1, jjm, &
1311                     &     istp_old, date0, dt, hori_id2, hist2_id,domain_id=orch_domain_id)
1312#else
1313                CALL histbeg(histname2, iim, lon, jjm, lat, 1, iim, 1, jjm, &
1314                     &     istp_old, date0, dt, hori_id2, hist2_id)
1315#endif
1316             ENDIF
1317             !-
1318             CALL histvert(hist2_id, 'veget', 'Vegetation types', '1', &
1319                  &    nvm,   veg, vegax_id2)
1320             CALL histvert(hist2_id, 'laiax', 'Nb LAI', '1', &
1321                  &    nlai+1,   lai, laiax_id2)
1322             CALL histvert(hist2_id, 'solth', 'Soil levels',      'm', &
1323                  &    ngrnd, sol, solax_id2)
1324             CALL histvert(hist2_id, 'soiltyp', 'Soil types',      '1', &
1325                  &    nstm, soltyp, soltax_id2)
1326             CALL histvert(hist2_id, 'nobio', 'Other surface types',      '1', &
1327                  &    nnobio, nobiotyp, nobioax_id2)
1328             CALL histvert(hist2_id, 'albtyp', 'Albedo Types',     '1', &
1329                  &    2, albtyp, albax_id2)
1330             IF (  hydrol_cwrr ) THEN
1331                CALL histvert(hist2_id, 'solay', 'Hydrol soil levels',      'm', &
1332                     &    nslm, solay, solayax_id2)
1333             ENDIF
1334             !-
1335             !- SECHIBA_HISTLEVEL2 = 1
1336             !-
1337             CALL histdef(hist2_id, 'ptn', 'Deep ground temperature', 'K', &
1338                  & iim,jjm, hori_id2, ngrnd, 1, ngrnd, solax_id2, 32, avescatter2(2),  dt, dw2) 
1339
1340             CALL histdef(hist2_id, 'mrsos', "Moisture in Upper 0.1 m of Soil Column", "kg m-2", &
1341                  & iim,jjm, hori_id2, 1, 1, 1, -99, 32, avescatter2(2), dt,dw2)           
1342
1343             CALL histdef(hist2_id, 'mrso', "Total Soil Moisture Content", "kg m-2", &
1344                  & iim,jjm, hori_id2, 1, 1, 1, -99, 32, avescatter2(11), dt,dw2)
1345             
1346             CALL histdef(hist2_id, 'mrros', "Surface Runoff", "kg m-2 s-1", &
1347                  & iim,jjm, hori_id2, 1, 1, 1, -99, 32, fluxop_scinsec2(11), dt,dw2)
1348
1349             CALL histdef(hist2_id, 'mrro', "Total Runoff", "kg m-2 s-1", &
1350                  & iim,jjm, hori_id2, 1, 1, 1, -99, 32, fluxop_scinsec2(2), dt,dw2)     
1351
1352             !-
1353             !- SECHIBA_HISTLEVEL2 = 2
1354             !-
1355             CALL histdef(hist2_id, 'cdrag', 'Drag coefficient for LE and SH', '?',  &
1356                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(2), dt, dw2)
1357             CALL histdef(hist2_id, 'soilalb_vis', 'Soil Albedo visible', '1', &
1358                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(2), dt,dw2)
1359             CALL histdef(hist2_id, 'soilalb_nir', 'Soil Albedo near infrared', '1', &
1360                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(2), dt,dw2)
1361             CALL histdef(hist2_id, 'vegalb_vis', 'Vegetation Albedo visible', '1', &
1362                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(2), dt,dw2)
1363             CALL histdef(hist2_id, 'vegalb_nir', 'Vegetation Albedo near infrared', '1', &
1364                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(2), dt,dw2)
1365             CALL histdef(hist2_id, 'z0m', 'Surface roughness for momentum', 'm',  &
1366                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(2), dt, dw2)
1367             CALL histdef(hist2_id, 'z0h', 'Surface roughness for heat', 'm',  &
1368                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(2), dt, dw2)
1369             CALL histdef(hist2_id, 'coastalflow', 'Diffuse coastal flow', 'm^3/s', &
1370                  & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop_scinsec2(2), dt, dw2)
1371             CALL histdef(hist2_id, 'riverflow', 'River flow to the oceans', 'm^3/s', &
1372                  & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop_scinsec2(2), dt, dw2) 
1373             CALL histdef(hist2_id, 'tsol_rad', 'Radiative surface temperature', 'C', &
1374                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avecels2(2), dt, dw2)
1375             IF ( do_floodplains ) THEN
1376                CALL histdef(hist2_id, 'floodout', 'Flow out of floodplains', 'mm/d', &
1377                     & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop2(2), dt,dw2)
1378                CALL histdef(hist2_id, 'vevapflo', 'Floodplains evaporation', 'mm/d', &
1379                     & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop2(2), dt, dw2)
1380                CALL histdef(hist2_id, 'flood_frac', 'Flooded fraction', '1', &
1381                     & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(2), dt,dw2)
1382                CALL histdef(hist2_id, 'reinfiltration', 'Reinfiltration from floodplains', 'mm/d', &
1383                     & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop2(2), dt,dw2)
1384             ENDIF
1385             CALL histdef(hist2_id, 'vevapnu', 'Bare soil evaporation', 'mm/d', &
1386                  & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop2(2), dt, dw2)
1387             CALL histdef(hist2_id, 'temp_sol', 'New Surface Temperature', 'C', &
1388                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avecels2(2), dt, dw2)
1389             CALL histdef(hist2_id, 'qsurf', 'Near surface specific humidity', 'g/g',  &
1390                  & iim,jjm, hori_id2, 1,1,1, -99, 32, ave2(2), dt, dw2)
1391             CALL histdef(hist2_id, 'albedo', 'Albedo', '1', &
1392                  & iim,jjm, hori_id2, 2,1,2, albax_id2, 32, avescatter2(2), dt, dw2)
1393             CALL histdef(hist2_id, 'fluxsens', 'Sensible Heat Flux', 'W/m^2',  &
1394                  & iim,jjm, hori_id2, 1,1,1, -99, 32, ave2(2), dt, dw2)
1395             CALL histdef(hist2_id, 'fluxlat', 'Latent Heat Flux', 'W/m^2',  &
1396                  & iim,jjm, hori_id2, 1,1,1, -99, 32, ave2(2), dt, dw2)
1397             CALL histdef(hist2_id, 'emis', 'Surface emissivity', '1', &
1398                  & iim,jjm, hori_id2, 1,1,1, -99, 32, ave2(2), dt, dw2)
1399             !-
1400             !- SECHIBA_HISTLEVEL2 = 3
1401             !-
1402             CALL histdef(hist2_id, 'evap', 'Evaporation', 'mm/d', &
1403                  & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop2(3), dt, dw2)
1404             CALL histdef(hist2_id, 'rain', 'Rainfall', 'mm/d',  &
1405                  & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop2(3), dt, dw2)
1406             CALL histdef(hist2_id, 'snowf', 'Snowfall', 'mm/d',  &
1407                  & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop2(3), dt, dw2)
1408             CALL histdef(hist2_id, 'netrad', 'Net radiation', 'W/m^2',  &
1409                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(3), dt, dw2)
1410             CALL histdef(hist2_id, 'lai', 'Leaf Area Index', '1', &
1411                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(3), dt, dw2)
1412             IF ( river_routing ) THEN
1413                CALL histdef(hist2_id, 'basinmap', 'Aproximate map of the river basins', ' ', &
1414                     & iim,jjm, hori_id2, 1,1,1, -99, 32, once2(3), dt, dw2) 
1415                CALL histdef(hist2_id, 'nbrivers', 'Number or rivers in the outflow grid box', ' ', &
1416                     & iim,jjm, hori_id2, 1,1,1, -99, 32, once2(3), dt, dw2) 
1417             ENDIF
1418             IF (check_waterbal) THEN
1419                CALL histdef(hist2_id, 'TotWater', 'Total amount of water at end of time step', 'mm/d', &
1420                     & iim,jjm, hori_id2, 1,1,1, -99, 32, ave2(3), dt, dw2)
1421                CALL histdef(hist2_id, 'TotWaterFlux', 'Total water flux', 'mm/d', &
1422                  & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop2(3), dt, dw2)
1423             ENDIF
1424
1425             IF (  hydrol_cwrr ) THEN
1426                 CALL histdef(hist2_id, 'humtot_pro', "Water content in soil layer", "kg m-2 ", &
1427                  & iim,jjm, hori_id2, nslm, 1, nslm, solayax_id2, 32, avescatter2(3), dt,dw2)
1428             ENDIF
1429             !-
1430             !- SECHIBA_HISTLEVEL2 = 4
1431             !-
1432             CALL histdef(hist2_id, 'subli', 'Sublimation', 'mm/d', &
1433                  & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop2(4), dt, dw2)
1434             CALL histdef(hist2_id, 'runoff', 'Surface runoff', 'mm/d', &
1435                  & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop2(4), dt, dw2)
1436             CALL histdef(hist2_id, 'drainage', 'Deep drainage', 'mm/d', &
1437                  & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop2(4), dt, dw2)
1438             IF ( river_routing ) THEN
1439                CALL histdef(hist2_id, 'riversret', 'Return from endorheic rivers', 'mm/d', &
1440                     & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop2(4), dt, dw2)
1441                CALL histdef(hist2_id, 'hydrographs', 'Hydrographs of gridbox outflow', 'm^3/s', &
1442                     & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop_scinsec2(4), dt, dw2)
1443             ENDIF
1444             IF ( hydrol_cwrr ) THEN
1445                CALL histdef(hist2_id, 'evapnu_soil', 'Bare soil evap for soil type', 'mm/d', &
1446                     & iim,jjm, hori_id2, nstm, 1, nstm, soltax_id2, 32, fluxop2(4), dt, dw2)
1447                CALL histdef(hist2_id, 'drainage_soil', 'Drainage for soil type', 'mm/d', &
1448                     & iim,jjm, hori_id2, nstm, 1, nstm, soltax_id2, 32, fluxop2(4), dt, dw2)
1449                CALL histdef(hist2_id, 'transpir_soil', 'Transpir for soil type', 'mm/d', &
1450                     & iim,jjm, hori_id2, nstm, 1, nstm, soltax_id2, 32, fluxop2(4), dt, dw2)
1451                CALL histdef(hist2_id, 'runoff_soil', 'Runoff for soil type', 'mm/d', &
1452                     & iim,jjm, hori_id2, nstm, 1, nstm, soltax_id2, 32, fluxop2(4), dt, dw2)
1453             ENDIF
1454             !
1455             CALL histdef(hist2_id, 'tair', 'Air Temperature', 'K',  &
1456                  & iim,jjm, hori_id2, 1,1,1, -99, 32, ave2(4), dt, dw2)
1457             CALL histdef(hist2_id, 'qair', 'Air humidity', 'g/g',  &
1458                  & iim,jjm, hori_id2, 1,1,1, -99, 32, ave2(4), dt, dw2)
1459             CALL histdef(hist2_id, 'q2m', '2m Air humidity', 'g/g',  &
1460                  & iim,jjm, hori_id2, 1,1,1, -99, 32, ave2(4), dt, dw2)
1461             CALL histdef(hist2_id, 't2m', '2m Air Temperature', 'K',  &
1462                  & iim,jjm, hori_id2, 1,1,1, -99, 32, ave2(4), dt, dw2)
1463            CALL histdef(hist2_id, 'alb_vis', 'Albedo visible', '1', &
1464                  & iim,jjm, hori_id2, 1,1,1, -99, 32, ave2(4), dt, dw2)
1465             CALL histdef(hist2_id, 'alb_nir', 'Albedo near infrared', '1', &
1466                  & iim,jjm, hori_id2, 1,1,1, -99, 32, ave2(4), dt, dw2)
1467             CALL histdef(hist2_id, 'roughheight', 'Effective roughness height', 'm',  &
1468                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(4), dt, dw2)
1469             CALL histdef(hist2_id, 'transpir', 'Transpiration', 'mm/d', &
1470                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, fluxop2(4), dt, dw2)
1471             CALL histdef(hist2_id, 'inter', 'Interception loss', 'mm/d', &
1472                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, fluxop2(4), dt, dw2)
1473             !-
1474             !- SECHIBA_HISTLEVEL2 = 5
1475             !-
1476             CALL histdef(hist2_id, 'tsol_max', 'Maximum Surface Temperature',&
1477                  & 'C', iim,jjm, hori_id2, 1,1,1, -99, 32, tmaxcels2(5), dt, dw2)
1478             CALL histdef(hist2_id, 'tsol_min', 'Minimum Surface Temperature',&
1479                  & 'C', iim,jjm, hori_id2, 1,1,1, -99, 32, tmincels2(5), dt, dw2)
1480             CALL histdef(hist2_id, 'snow', 'Snow mass', 'kg/m^2', &
1481                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(5), dt, dw2)
1482             CALL histdef(hist2_id, 'snowage', 'Snow age', '?', &
1483                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(5), dt, dw2)
1484             CALL histdef(hist2_id, 'snownobio', 'Snow on other surfaces', 'kg/m^2', &
1485                  & iim,jjm, hori_id2, nnobio,1, nnobio, nobioax_id2, 32, avescatter2(5), dt, dw2)
1486             CALL histdef(hist2_id, 'snownobioage', 'Snow age on other surfaces', 'd', &
1487                  & iim,jjm, hori_id2, nnobio,1, nnobio, nobioax_id2, 32, avescatter2(5), dt, dw2)
1488             CALL histdef(hist2_id, 'vegetfrac', 'Fraction of vegetation', '1', &
1489                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(5), dt, dw2)
1490             CALL histdef(hist2_id, 'maxvegetfrac', 'Maximum fraction of vegetation', '1', &
1491                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(5), dt, dw2)
1492             CALL histdef(hist2_id, 'nobiofrac', 'Fraction of other surface types', '1', &
1493                  & iim,jjm, hori_id2, nnobio, 1, nnobio, nobioax_id2, 32, avescatter2(5), dt, dw2)
1494             IF ( hydrol_cwrr ) THEN
1495                DO jst=1,nstm
1496                   
1497                   ! var_name= "mc_1" ... "mc_3"
1498                   WRITE (var_name,"('moistc_',i1)") jst
1499                   CALL histdef(hist2_id, var_name, 'Soil Moisture profile for soil type', 'm3/m3', &
1500                        & iim,jjm, hori_id2, nslm, 1, nslm, solayax_id2, 32, avescatter2(5), dt, dw2)
1501                   
1502                   ! var_name= "vegetsoil_1" ... "vegetsoil_3"
1503                   WRITE (var_name,"('vegetsoil_',i1)") jst
1504                   CALL histdef(hist2_id, var_name, 'Fraction of vegetation on soil types', '%', &
1505                        & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(5), dt, dw2)
1506                   
1507                   ! var_name= "kfact_root_1" ... "kfact_root_3"
1508                   WRITE (var_name,"('kfactroot_',i1)") jst
1509                   CALL histdef(hist2_id, var_name, 'Root fraction profile for soil type', '%', &
1510                        & iim,jjm, hori_id2, nslm, 1, nslm, solayax_id2, 32, avescatter2(5), dt,dw2)
1511                ENDDO
1512
1513             ENDIF
1514             !-
1515             !- SECHIBA_HISTLEVEL2 = 6
1516             !-
1517             IF ( .NOT. hydrol_cwrr ) THEN
1518                CALL histdef(hist2_id, 'dss', 'Up-reservoir Height', 'm',  &
1519                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id, 32, avescatter2(6), dt,dw2)
1520                CALL histdef(hist2_id, 'gqsb', 'Upper Soil Moisture', 'Kg/m^2',  &
1521                     & iim,jjm, hori_id2, 1, 1, 1, -99, 32, avescatter2(6), dt, dw2)
1522                CALL histdef(hist2_id, 'bqsb', 'Lower Soil Moisture', 'Kg/m^2',  &
1523                     & iim,jjm, hori_id2, 1, 1, 1, -99, 32, avescatter2(6), dt, dw2)
1524             ELSE
1525                CALL histdef(hist2_id, 'humtot', 'Total Soil Moisture', 'Kg/m^2', &
1526                     & iim,jjm, hori_id2, 1, 1, 1, -99, 32, avescatter2(6), dt, dw2)
1527                CALL histdef(hist2_id, 'humtot_soil', 'Soil Moisture for soil type', 'Kg/m^2', &
1528                     & iim,jjm, hori_id2, nstm, 1, nstm, soltax_id2, 32, avescatter2(6), dt, dw2)
1529                CALL histdef(hist2_id, 'SWI', 'Soil wetness index','-',  &
1530                     & iim,jjm, hori_id2, 1, 1, 1, -99, 32, avescatter2(6), dt,dw2)
1531             ENDIF
1532             CALL histdef(hist2_id, 'qsintveg', 'Water on canopy', 'Kg/m^2', &
1533                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(6), dt, dw2)
1534             CALL histdef(hist2_id, 'rstruct', 'Structural resistance', 's/m', &
1535                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(6), dt, dw2)
1536             IF ( ok_co2 ) THEN
1537                CALL histdef(hist2_id, 'gpp', 'Net assimilation of carbon by the vegetation', 'gC/m^2/s', &
1538                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, fluxop_scinsec2(6), dt,dw2)
1539             ENDIF
1540             IF ( ok_stomate ) THEN
1541                CALL histdef(hist2_id, 'nee', 'Net Ecosystem Exchange', 'gC/m^2/s', &
1542                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, fluxop_scinsec2(6), dt,dw2)
1543                CALL histdef(hist2_id, 'maint_resp', 'Maintenance respiration', 'gC/m^2/s', &
1544                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, fluxop_scinsec2(6), dt,dw2)
1545                CALL histdef(hist2_id, 'hetero_resp', 'Heterotrophic respiration', 'gC/m^2/s', &
1546                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, fluxop_scinsec2(6), dt,dw2)
1547                CALL histdef(hist2_id, 'growth_resp', 'Growth respiration', 'gC/m^2/s', &
1548                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, fluxop_scinsec2(6), dt, dw2)
1549                CALL histdef(hist2_id, 'npp', 'Net Primary Production', 'gC/m^2/s', &
1550                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, fluxop_scinsec2(6), dt, dw2)
1551             ENDIF
1552             CALL histdef(hist2_id, 'precisol', 'Throughfall', 'mm/d',  &
1553                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, fluxop2(6), dt, dw2)
1554             CALL histdef(hist2_id, 'drysoil_frac', 'Fraction of visibly dry soil', '1',  &
1555                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(6), dt, dw2)
1556             CALL histdef(hist2_id, 'evapot', 'Potential evaporation', 'mm/d',  &
1557                  & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop2(6), dt, dw2)
1558             CALL histdef(hist2_id, 'evapot_corr', 'Potential evaporation', 'mm/d',  &
1559                  & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop2(6), dt, dw2)
1560             CALL histdef(hist2_id, 'snowmelt', 'snow melt', 'kg/m2', &
1561                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(6), dt, dw2)
1562
1563             !-
1564             !- SECHIBA_HISTLEVEL2 = 7
1565             !-
1566             CALL histdef(hist2_id, 'swnet', 'Net solar radiation', 'W/m^2',  &
1567                  & iim,jjm, hori_id2, 1,1,1, -99, 32, ave2(7), dt, dw2)
1568             CALL histdef(hist2_id, 'swdown', 'Incident solar radiation', 'W/m^2',  &
1569                  & iim,jjm, hori_id2, 1,1,1, -99, 32, ave2(7), dt, dw2)
1570             CALL histdef(hist2_id, 'lwdown', 'Absorbed downward longwave radiation', 'W/m^2',  &
1571                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(7), dt, dw2)
1572             CALL histdef(hist2_id, 'lwnet', 'Net surface longwave radiation', 'W/m^2',  &
1573                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(7), dt, dw2)
1574             !-
1575             !- SECHIBA_HISTLEVEL2 = 8
1576             !-
1577             IF ( river_routing ) THEN
1578                CALL histdef(hist2_id, 'fastr', 'Fast flow reservoir', 'kg/m^2', &
1579                     & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(8), dt, dw2)
1580                CALL histdef(hist2_id, 'slowr', 'Slow flow reservoir', 'kg/m^2', &
1581                     & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(8), dt, dw2)
1582                CALL histdef(hist2_id, 'streamr', 'Stream flow reservoir', 'kg/m^2', &
1583                     & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(8), dt, dw2)
1584                CALL histdef(hist2_id, 'floodr', 'Floodplains reservoir', 'kg/m^2', &
1585                     & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(8), dt,dw2)
1586                CALL histdef(hist2_id, 'floodh', 'Floodplains height', 'mm', &
1587                     & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(8), dt,dw2)
1588                CALL histdef(hist2_id, 'pondr', 'Ponds reservoir', 'kg/m^2', &
1589                     & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(8), dt,dw2)
1590                CALL histdef(hist2_id, 'lakevol', 'Volume in lake reservoir', 'kg/m^2', &
1591                     & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(8), dt, dw2)
1592                IF ( do_irrigation ) THEN
1593                   CALL histdef(hist2_id, 'irrigation', 'Net irrigation', 'mm/d', &
1594                        & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop2(8), dt, dw2)
1595                   CALL histdef(hist2_id, 'netirrig', 'Net irrigation requirement', 'mm/d', &
1596                        & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop2(8), dt, dw2)
1597                   CALL histdef(hist2_id, 'irrigmap', 'Map of irrigated areas', 'm^2', &
1598                        & iim,jjm, hori_id2, 1,1,1, -99, 32, once2(8), dt, dw2)
1599                ENDIF
1600                CALL histdef(hist2_id, 'floodmap', 'Map of floodplains', 'm^2', &
1601                     & iim,jjm, hori_id2, 1,1,1, -99, 32, once2(8), dt,dw2)
1602                CALL histdef(hist2_id, 'swampmap', 'Map of swamps', 'm^2', &
1603                  & iim,jjm, hori_id2, 1,1,1, -99, 32, once2(8), dt,dw2)
1604             ENDIF
1605             !-
1606             !- SECHIBA_HISTLEVEL2 = 9
1607             !-
1608             CALL histdef(hist2_id, 'beta', 'Beta Function', '1',  &
1609                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(9), dt, dw2)
1610             CALL histdef(hist2_id, 'raero', 'Aerodynamic resistance', 's/m',  &
1611                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(9), dt, dw2)
1612             CALL histdef(hist2_id, 'Wind', 'Wind speed', 'm/s',  &
1613                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(9), dt, dw2)
1614             CALL histdef(hist2_id, 'qsatt' , 'Surface saturated humidity', 'g/g', &
1615                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(9), dt, dw2)
1616             CALL histdef(hist2_id, 'vbeta1', 'Beta for sublimation', '1',  &
1617                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(9), dt, dw2)
1618             CALL histdef(hist2_id, 'vbeta4', 'Beta for bare soil', '1',  &
1619                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(9), dt, dw2)
1620             IF ( ok_co2 ) THEN
1621                CALL histdef(hist2_id, 'gsmean', 'mean stomatal conductance', 'umol/m2/s', &
1622                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(9), dt, dw2)
1623             ENDIF
1624             CALL histdef(hist2_id, 'vbeta5', 'Beta for floodplains', '1',  &
1625                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(9), dt, dw2)
1626             IF (  hydrol_cwrr ) THEN
1627                CALL histdef(hist2_id, 'reinf_slope', 'Slope index for each grid box', '1', &
1628                     & iim,jjm, hori_id2, 1,1,1, -99, 32, once2(9),  dt,dw2)
1629                CALL histdef(hist2_id, 'soilindex', 'Soil index', '1', &
1630                     & iim,jjm, hori_id2, 1, 1, 1, -99, 32, once2(9),  dt,dw2)
1631             ENDIF
1632             CALL histdef(hist2_id, 'humrel', 'Soil moisture stress', '-',  &
1633                  & iim,jjm, hori_id2, nvm,1,nvm, vegax_id2, 32, avescatter2(9), dt, dw2)
1634             !-
1635             !- SECHIBA_HISTLEVEL2 = 10
1636             !-
1637             IF ( ok_co2 ) THEN
1638                CALL histdef(hist2_id, 'cimean', 'Stomatal CO2 concentation', 'mmole/m2/s', &
1639                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt, dw2)
1640             ENDIF
1641             CALL histdef(hist2_id, 'vbeta3', 'Beta for Transpiration', 'mm/d', &
1642                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt, dw2)
1643             CALL histdef(hist2_id, 'rveget', 'Canopy resistance', 's/m', &
1644                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt, dw2)
1645             IF ( .NOT. hydrol_cwrr ) THEN
1646                CALL histdef(hist2_id, 'rsol', 'Soil resistance', 's/m',  &
1647                     & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(10), dt, dw2)
1648             ENDIF
1649             CALL histdef(hist2_id,'vbeta2','Beta for Interception loss','mm/d', &
1650                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt, dw2)
1651             CALL histdef(hist2_id, 'qsintmax', 'Maximum Interception capacity', 'Kg/m^2', &
1652                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt, dw2)
1653             
1654             IF ( ok_bvoc ) THEN
1655                CALL histdef(hist2_id, 'PAR', 'PAR', 'umol phot/m^2/s',  &
1656                     & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(10), dt,dw2)
1657                IF ( ok_radcanopy ) THEN
1658                   CALL histdef(hist2_id, 'PARsun', 'Sunlit Leaf PAR', 'umol phot/m^2/s', &
1659                        & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
1660                   CALL histdef(hist2_id, 'PARsh', 'Shaded Leaf Area PAR', 'umol phot/m^2/s', &
1661                        & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
1662                   CALL histdef(hist2_id, 'laisun', 'Sunlit Leaf Area Index', '1', &
1663                        & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
1664                   CALL histdef(hist2_id, 'laish', 'Shaded Leaf Area Index', '1', &
1665                        & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
1666                   CALL histdef(hist2_id, 'Fdf', 'Fdf', '1',  &
1667                        & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(10), dt,dw2)
1668                   IF ( ok_multilayer ) then
1669                      CALL histdef(hist2_id, 'PARsuntab', 'Sunlit Leaf PAR', 'umol phot/m^2/s', &
1670                           & iim,jjm, hori_id2, nlai+1, 1, nlai+1, laiax_id2, 32, avescatter2(10), dt,dw2)
1671                      CALL histdef(hist2_id, 'PARshtab', 'Shaded Leaf Area PAR', 'umol phot/m^2/s', &
1672                           & iim,jjm, hori_id2, nlai+1, 1, nlai+1, laiax_id2, 32, avescatter2(10), dt,dw2)
1673                   ENDIF
1674                   CALL histdef(hist2_id, 'coszang', 'coszang', '1',  &
1675                        & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(10), dt,dw2)
1676                   CALL histdef(hist2_id, 'PARdf', 'PARdf', '1',  &
1677                        & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(10), dt,dw2)
1678                   CALL histdef(hist2_id, 'PARdr', 'PARdr', '1',  &
1679                        & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(10), dt,dw2)
1680                   CALL histdef(hist2_id, 'Trans', 'Trans', '1',  &
1681                        & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(10), dt,dw2)
1682                END IF
1683               
1684                CALL histdef(hist2_id, 'flx_fertil_no', 'flx_fertil_no', 'ngN/m^2/s', &
1685                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
1686                CALL histdef(hist2_id, 'CRF', 'CRF', '1', &
1687                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
1688                CALL histdef(hist2_id, 'flx_co2_bbg_year', 'flx_co2_bbg_year', 'kgC/m^2/yr ', &
1689                     & iim,jjm, hori_id2, 1,1,1, -99, 32, once2(10), dt,dw2) 
1690                CALL histdef(hist2_id, 'N_qt_WRICE_year', 'N_qt_WRICE_year', 'kgN/yr ', &
1691                     & iim,jjm, hori_id2, 1,1,1, -99, 32, once2(10), dt,dw2) 
1692                CALL histdef(hist2_id, 'N_qt_OTHER_year', 'N_qt_OTHER_year', 'kgN/yr ', &
1693                     & iim,jjm, hori_id2, 1,1,1, -99, 32, once2(10), dt,dw2) 
1694                CALL histdef(hist2_id, 'flx_iso', 'flx_iso', 'kgC/m^2/s', &
1695                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
1696                CALL histdef(hist2_id, 'flx_mono', 'flx_mono', 'kgC/m^2/s',&
1697                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
1698                CALL histdef(hist2_id, 'flx_apinen', 'flx_apinen', 'kgC/m^2/s',&
1699                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
1700                CALL histdef(hist2_id, 'flx_bpinen', 'flx_bpinen', 'kgC/m^2/s',&
1701                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
1702                CALL histdef(hist2_id, 'flx_limonen', 'flx_limonen', 'kgC/m^2/s',&
1703                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
1704                CALL histdef(hist2_id, 'flx_myrcen', 'flx_myrcen', 'kgC/m^2/s',&
1705                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
1706                CALL histdef(hist2_id, 'flx_sabinen', 'flx_sabinen', 'kgC/m^2/s',&
1707                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
1708                CALL histdef(hist2_id, 'flx_camphen', 'flx_camphen', 'kgC/m^2/s',&
1709                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
1710                CALL histdef(hist2_id, 'flx_3caren', 'flx_3caren', 'kgC/m^2/s',&
1711                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
1712                CALL histdef(hist2_id, 'flx_tbocimen', 'flx_tbocimen', 'kgC/m^2/s',&
1713                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
1714                CALL histdef(hist2_id, 'flx_othermono', 'flx_othermono', 'kgC/m^2/s',&
1715                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
1716                CALL histdef(hist2_id, 'flx_sesquiter', 'flx_sesquiter', 'kgC/m^2/s',&
1717                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
1718                CALL histdef(hist2_id, 'flx_ORVOC', 'flx_ORVOC', 'kgC/m^2/s',&
1719                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
1720                CALL histdef(hist2_id, 'flx_MBO', 'flx_MBO', 'kgC/m^2/s',&
1721                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
1722                CALL histdef(hist2_id, 'flx_methanol', 'flx_methanol', 'kgC/m^2/s',&
1723                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
1724                CALL histdef(hist2_id, 'flx_acetone', 'flx_acetone', 'kgC/m^2/s',&
1725                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(1), dt,dw2)   !! LDF TEST modificato a 1... !!
1726                CALL histdef(hist2_id, 'flx_acetal', 'flx_acetal', 'kgC/m^2/s',&
1727                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(1), dt,dw2)   !! LDF TEST modificato a 1... !!
1728                CALL histdef(hist2_id, 'flx_formal', 'flx_formal', 'kgC/m^2/s',&
1729                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
1730                CALL histdef(hist2_id, 'flx_acetic', 'flx_acetic', 'kgC/m^2/s',&
1731                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
1732                CALL histdef(hist2_id, 'flx_formic', 'flx_formic', 'kgC/m^2/s',&
1733                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
1734                CALL histdef(hist2_id, 'flx_no_soil', 'flx_no_soil', 'ngN/m^2/s',&
1735                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
1736                CALL histdef(hist2_id, 'flx_no', 'flx_no', 'ngN/m^2/s',&
1737                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
1738             ENDIF
1739         ELSE 
1740             !-
1741             !- This is the ALMA convention output now
1742             !-
1743             !-
1744             IF ( GridType == "RegLonLat" ) THEN
1745#ifdef CPP_PARA
1746                CALL histbeg(histname2, iim, lon_rect, jjm, lat_rect, 1, iim, 1, jjm, &
1747                     &     istp_old, date0, dt, hori_id2, hist2_id,orch_domain_id)
1748#else
1749                CALL histbeg(histname2, iim, lon_rect, jjm, lat_rect, 1, iim, 1, jjm, &
1750                     &     istp_old, date0, dt, hori_id2, hist2_id)
1751#endif
1752                WRITE(numout,*)  'HISTBEG2 --->',istp_old,date0,dt,dw2,hist2_id
1753             ELSE
1754#ifdef CPP_PARA
1755                CALL histbeg(histname2, iim, lon, jjm, lat, 1, iim, 1, jjm, &
1756                     &     istp_old, date0, dt, hori_id2, hist2_id,domain_id=orch_domain_id)
1757#else
1758                CALL histbeg(histname2, iim, lon, jjm, lat, 1, iim, 1, jjm, &
1759                     &     istp_old, date0, dt, hori_id2, hist2_id)
1760#endif
1761             ENDIF
1762             !-
1763             CALL histvert(hist2_id, 'veget', 'Vegetation types', '1', &
1764                  &    nvm,   veg, vegax_id2)
1765             CALL histvert(hist2_id, 'solth', 'Soil levels',      'm', &
1766                  &    ngrnd, sol, solax_id2)
1767             CALL histvert(hist2_id, 'soiltyp', 'Soil types',      '1', &
1768                  &    nstm, soltyp, soltax_id2)
1769             CALL histvert(hist2_id, 'nobio', 'Other surface types',      '1', &
1770                  &    nnobio, nobiotyp, nobioax_id2)
1771             IF (  hydrol_cwrr ) THEN
1772                CALL histvert(hist2_id, 'solay', 'Hydrol soil levels',      'm', &
1773                     &    nslm, diaglev(1:nslm), solayax_id2)
1774             ENDIF
1775             !-
1776             !-  Vegetation
1777             !-
1778             CALL histdef(hist2_id, 'vegetfrac', 'Fraction of vegetation', '1', &
1779                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(3), dt, dw2)
1780             CALL histdef(hist2_id, 'maxvegetfrac', 'Maximum fraction of vegetation', '1', &
1781                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(3), dt, dw2)
1782             CALL histdef(hist2_id, 'nobiofrac', 'Fraction of other surface types', '1', &
1783                  & iim,jjm, hori_id2, nnobio, 1, nnobio, nobioax_id2, 32, avescatter2(3), dt, dw2)
1784             !-
1785             !-  General energy balance
1786             !-
1787             CALL histdef(hist2_id, 'SWnet', 'Net shortwave radiation', 'W/m^2',  &
1788                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(1), dt, dw2)
1789             CALL histdef(hist2_id, 'LWnet', 'Net longwave radiation', 'W/m^2',  &
1790                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(1), dt, dw2)
1791             CALL histdef(hist2_id, 'Qh', 'Sensible heat flux', 'W/m^2',  &
1792                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(1), dt, dw2)
1793             CALL histdef(hist2_id, 'Qle', 'Latent heat flux', 'W/m^2',  &
1794                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(1), dt, dw2)
1795             CALL histdef(hist2_id, 'Qg', 'Ground heat flux', 'W/m^2',  &
1796                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(1), dt, dw2)
1797             CALL histdef(hist2_id, 'Qf', 'Energy of fusion', 'W/m^2',  &
1798                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(5), dt, dw2)
1799             CALL histdef(hist2_id, 'Qv', 'Energy of sublimation', 'W/m^2',  &
1800                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(5), dt, dw2)
1801             CALL histdef(hist2_id, 'DelSurfHeat', 'Change in surface layer heat', 'J/m^2',  &
1802                  & iim,jjm, hori_id2, 1,1,1, -99, 32, sumscatter2(7), dt, dw2)
1803             CALL histdef(hist2_id, 'DelColdCont', 'Change in snow surface layer cold content', 'J/m^2',  &
1804                  & iim,jjm, hori_id2, 1,1,1, -99, 32, sumscatter2(7), dt, dw2)
1805             !-
1806             !- General water balance
1807             !-
1808             CALL histdef(hist2_id, 'Snowf', 'Snowfall rate', 'kg/m^2/s',  &
1809                  & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop_scinsec2(1), dt, dw2)
1810             CALL histdef(hist2_id, 'Rainf', 'Rainfall rate', 'kg/m^2/s',  &
1811                  & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop_scinsec2(1), dt, dw2)
1812             CALL histdef(hist2_id, 'Evap', 'Total Evapotranspiration', 'kg/m^2/s', &
1813                  & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop_scinsec2(1), dt, dw2)
1814             CALL histdef(hist2_id, 'Qs', 'Surface runoff', 'kg/m^2/s', &
1815                  & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop_scinsec2(1), dt, dw2)
1816             CALL histdef(hist2_id, 'Qsb', 'Sub-surface runoff', 'kg/m^2/s', &
1817                  & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop_scinsec2(1), dt, dw2)
1818             CALL histdef(hist2_id, 'Qsm', 'Snowmelt', 'kg/m^2/s', &
1819                  & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop_scinsec2(1), dt, dw2)
1820             CALL histdef(hist2_id, 'DelSoilMoist', 'Change in soil moisture', 'kg/m^2',  &
1821                  & iim,jjm, hori_id2, 1, 1, 1, -99, 32, sumscatter2(7), dt, dw2)
1822             CALL histdef(hist2_id, 'DelSurfStor', 'Change in Surface Water Storage','kg/m^2',&
1823                  & iim,jjm, hori_id2, 1, 1, 1, -99, 32, sumscatter2(7), dt,dw2)
1824             CALL histdef(hist2_id, 'DelIntercept', 'Change in interception storage', 'kg/m^2',  &
1825                  & iim,jjm, hori_id2, 1, 1, 1, -99, 32, sumscatter2(7), dt, dw2)
1826             CALL histdef(hist2_id, 'DelSWE', 'Change in interception storage Snow Water Equivalent', 'kg/m^2',  &
1827                  & iim,jjm, hori_id2, 1, 1, 1, -99, 32, sumscatter2(7), dt, dw2)
1828             !-
1829             !- Surface state
1830             !-
1831             CALL histdef(hist2_id, 'AvgSurfT', 'Average surface temperature', 'K', &
1832                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(1), dt, dw2)
1833             CALL histdef(hist2_id, 'RadT', 'Surface radiative temperature', 'K', &
1834                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(5), dt, dw2)
1835             CALL histdef(hist2_id, 'Albedo', 'Albedo', '1', &
1836                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(7), dt, dw2)
1837             CALL histdef(hist2_id, 'SWI', 'Soil wetness index','1',  &
1838                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(1), dt, dw2)
1839             CALL histdef(hist2_id, 'SurfStor', 'Surface Water Storage','kg/m^2',  &
1840                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(1), dt, dw2)
1841             CALL histdef(hist2_id, 'SWE', 'Snow Water Equivalent', 'kg/m^2', &
1842                  & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter2(1), dt,dw2)
1843             !!-
1844             !-  Sub-surface state
1845             !-
1846             IF ( .NOT. hydrol_cwrr ) THEN
1847                CALL histdef(hist2_id, 'SoilMoist', '3D average layer soil moisture', 'kg/m^2',  &
1848                     & iim,jjm, hori_id2, 1, 1, 1, -99, 32, avescatter2(7), dt, dw2)
1849             ELSE
1850                CALL histdef(hist2_id, 'SoilMoist', '3D average layer soil moisture', 'kg/m^2',  &
1851                     & iim,jjm, hori_id2, nslm, 1, nslm, solayax_id2, 32, avescatter2(7), dt, dw2)
1852             ENDIF
1853             CALL histdef(hist2_id, 'SoilWet', 'Total soil wetness', '-',  &
1854                  & iim,jjm, hori_id2, 1, 1, 1, -99, 32, avescatter2(1), dt, dw2)
1855             CALL histdef(hist2_id, 'SoilTemp', 'Soil temperature profile', 'K', &
1856                  & iim,jjm, hori_id2, ngrnd, 1, ngrnd, solax_id2, 32, avescatter2(7), dt, dw2)
1857             !-
1858             !-  Evaporation components
1859             !-
1860             CALL histdef(hist2_id, 'PotEvap', 'Potential evapotranspiration', 'kg/m^2/s', &
1861                  & iim,jjm, hori_id2, 1, 1, 1, -99, 32, fluxop_scinsec2(1), dt, dw2)
1862             CALL histdef(hist2_id, 'ECanop', 'Interception evaporation', 'kg/m^2/s', &
1863                  & iim,jjm, hori_id2, 1, 1, 1, -99, 32, fluxop_scinsec2(5), dt, dw2)
1864             CALL histdef(hist2_id, 'TVeg', 'Transpiration', 'kg/m^2/s', &
1865                  & iim,jjm, hori_id2, 1, 1, 1, -99, 32, fluxop_scinsec2(5), dt, dw2)
1866             CALL histdef(hist2_id, 'ESoil', 'Bare soil evaporation', 'kg/m^2/s', &
1867                  & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop_scinsec2(5), dt, dw2)
1868             CALL histdef(hist2_id, 'RootMoist','Root zone soil water', 'kg/m^2',  &
1869                  & iim,jjm, hori_id2, 1, 1, 1, -99, 32, avescatter2(1), dt, dw2)
1870             CALL histdef(hist2_id, 'SubSnow','Snow sublimation','kg/m^2/s', &
1871                  & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop_scinsec2(1), dt, dw2)
1872             CALL histdef(hist2_id, 'ACond', 'Aerodynamic conductance', 'm/s',  &
1873                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(5), dt, dw2)
1874             !-
1875             !-
1876             !-  Cold Season Processes
1877             !-
1878             CALL histdef(hist2_id, 'SnowFrac', 'Snow cover fraction', '1',  &
1879                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(7), dt, dw2)
1880             CALL histdef(hist2_id, 'SAlbedo', 'Snow albedo', '1', &
1881                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(7), dt, dw2)
1882             CALL histdef(hist2_id, 'SnowDepth', '3D snow depth', 'm', &
1883                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(7), dt, dw2)
1884             !-
1885             !- Hydrologic variables
1886             !-
1887             IF ( river_routing ) THEN
1888                !
1889                IF (do_floodplains) THEN
1890                   CALL histdef(hist2_id, 'EWater', 'Open water evaporation', 'kg/m^2/s', &
1891                        & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop_scinsec2(5), dt, dw2)
1892                   CALL histdef(hist2_id, 'FloodFrac', 'Floodplain Fraction', '-', &
1893                        & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(1), dt,dw2)
1894                ENDIF
1895                !
1896                CALL histdef(hist2_id, 'IrrigationMap', 'Map of irrigated areas', 'm^2', &
1897                     & iim,jjm, hori_id2, 1,1,1, -99, 32, once2(1), dt, dw2)
1898                CALL histdef(hist2_id, 'FloodplainsMap', 'Map of flooded areas', 'm^2', &
1899                     & iim,jjm, hori_id2, 1,1,1, -99, 32, once2(1), dt,dw2)
1900                CALL histdef(hist2_id, 'SwampMap', 'Map of swamp areas', 'm^2', &
1901                  & iim,jjm, hori_id2, 1,1,1, -99, 32, once2(1), dt,dw2)
1902                CALL histdef(hist2_id, 'Dis', 'Simulated River Discharge', 'm^3/s', &
1903                     & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop_scinsec2(1), dt,dw2)
1904             ENDIF
1905             !-
1906             !-
1907             !-
1908             CALL histdef(hist2_id, 'humrel', 'Soil moisture stress', '-',  &
1909                  & iim,jjm, hori_id2, nvm,1,nvm, vegax_id2, 32, avescatter2(9), dt, dw2)
1910             !-
1911             !-  The carbon budget
1912             !-
1913             IF ( ok_co2 ) THEN
1914                CALL histdef(hist2_id, 'GPP', 'Net assimilation of carbon by the vegetation', 'gC/m^2/s', &
1915                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, fluxop_scinsec2(1), dt, dw2)
1916             ENDIF
1917             IF ( ok_stomate ) THEN
1918                CALL histdef(hist2_id, 'NEE', 'Net Ecosystem Exchange', 'gC/m^2/s', &
1919                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, fluxop_scinsec2(1), dt,dw2)
1920                CALL histdef(hist2_id, 'maint_resp', 'Maintenance respiration', 'gC/m^2/s', &
1921                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, fluxop_scinsec2(1), dt,dw2)
1922                CALL histdef(hist2_id, 'hetero_resp', 'Heterotrophic respiration', 'gC/m^2/s', &
1923                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, fluxop_scinsec2(1), dt,dw2)
1924                CALL histdef(hist2_id, 'growth_resp', 'Growth respiration', 'gC/m^2/s', &
1925                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, fluxop_scinsec2(1), dt, dw2)
1926                CALL histdef(hist2_id, 'npp', 'Net Primary Production', 'gC/m^2/s', &
1927                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, fluxop_scinsec2(1), dt, dw2)
1928             ENDIF
1929             !
1930          ENDIF
1931          !-
1932          CALL histdef(hist2_id, 'LandPoints', 'Land Points', '1', &
1933               & iim,jjm, hori_id2, 1,1,1, -99, 32, once2(1), dt, dw2) 
1934          CALL histdef(hist2_id, 'Areas', 'Mesh areas', 'm2', &
1935               & iim,jjm, hori_id2, 1,1,1, -99, 32, once2(1), dt, dw2)
1936          CALL histdef(hist2_id, 'Contfrac', 'Continental fraction', '1', &
1937               & iim,jjm, hori_id2, 1,1,1, -99, 32, once2(1), dt, dw2)
1938          !-
1939          ! Write the names of the pfts in the high frequency sechiba history files
1940          global_attribute="PFT_name"
1941          DO i=1,nvm
1942             WRITE(global_attribute(9:10),"(I2.2)") i
1943             CALL histglobal_attr(hist2_id, global_attribute, PFT_name(i))
1944          ENDDO
1945          !-
1946          CALL histend(hist2_id)
1947      ENDIF
1948  ENDIF
1949
1950    !-
1951    !=====================================================================
1952    !- 3.2 STOMATE's history file
1953    !=====================================================================
1954    IF ( ok_stomate ) THEN
1955       !-
1956       ! STOMATE IS ACTIVATED
1957       !-
1958       !Config Key   = STOMATE_OUTPUT_FILE
1959       !Config Desc  = Name of file in which STOMATE's output is going to be written
1960       !Config If    = OK_STOMATE
1961       !Config Def   = stomate_history.nc
1962       !Config Help  = This file is going to be created by the model
1963       !Config         and will contain the output from the model.
1964       !Config         This file is a truly COADS compliant netCDF file.
1965       !Config         It will be generated by the hist software from
1966       !Config         the IOIPSL package.
1967       !Config Units = [FILE]
1968       !-
1969       stom_histname='stomate_history.nc'
1970       CALL getin_p('STOMATE_OUTPUT_FILE', stom_histname)       
1971       WRITE(numout,*) 'STOMATE_OUTPUT_FILE', TRIM(stom_histname)
1972       !-
1973       !Config Key   = STOMATE_HIST_DT
1974       !Config Desc  = STOMATE history time step
1975       !Config If    = OK_STOMATE
1976       !Config Def   = 10.
1977       !Config Help  = Time step of the STOMATE history file
1978       !Config Units = [days]
1979       !-
1980       hist_days_stom = 10.
1981       CALL getin_p('STOMATE_HIST_DT', hist_days_stom)       
1982
1983       IF ( hist_id < 0 ) THEN
1984          ! Deactivate all history files if sechiba_history file is deactivated
1985          hist_dt_stom=0
1986          WRITE(numout,*) 'STOMATE history file will not be created because sechiba_history file is deactivated.'
1987       ELSE IF ( hist_days_stom == moins_un ) THEN
1988          hist_dt_stom = moins_un
1989          WRITE(numout,*) 'output frequency for STOMATE history file (d): one month.'
1990       ELSE IF ( hist_days_stom == 0 ) THEN
1991          ! Deactivate this file
1992          hist_dt_stom=0
1993          WRITE(numout,*) 'STOMATE history file will not be created'
1994       ELSE
1995          hist_dt_stom = NINT( hist_days_stom ) * one_day
1996          WRITE(numout,*) 'output frequency for STOMATE history file (d): ', &
1997               hist_dt_stom/one_day
1998       ENDIF
1999
2000       ! test consistency between STOMATE_HIST_DT and DT_STOMATE parameters
2001       dt_stomate_loc = one_day
2002       CALL getin_p('DT_STOMATE', dt_stomate_loc)
2003       IF ( hist_days_stom /= moins_un .AND. hist_dt_stom/=0) THEN
2004          IF (dt_stomate_loc > hist_dt_stom) THEN
2005             WRITE(numout,*) "DT_STOMATE = ",dt_stomate_loc,"  , STOMATE_HIST_DT = ",hist_dt_stom
2006             CALL ipslerr_p (3,'ioipslctrl_history', &
2007                  &          'Problem with DT_STOMATE > STOMATE_HIST_DT','', &
2008                  &          '(must be less or equal)')
2009          ENDIF
2010       ENDIF
2011       !-
2012       !- Initialize stomate_history file
2013       IF ( hist_dt_stom == 0 ) THEN
2014          ! Case hist_dt_stom=0 : No creation of stomate_history.nc file
2015          ! Nothing will be done.
2016          hist_id_stom=-1
2017       ELSE
2018          ! Initialise stomate_history file
2019       IF (is_omp_root) THEN
2020          IF ( GridType == "RegLonLat" ) THEN
2021#ifdef CPP_PARA
2022             CALL histbeg(stom_histname, iim, lon_rect, jjm, lat_rect,  1, iim, 1, jjm, &
2023                  &     istp_old, date0, dt, hori_id, hist_id_stom,domain_id=orch_domain_id)
2024#else
2025             CALL histbeg(stom_histname, iim, lon_rect, jjm, lat_rect,  1, iim, 1, jjm, &
2026                  &     istp_old, date0, dt, hori_id, hist_id_stom)
2027#endif
2028          ELSE
2029#ifdef CPP_PARA
2030             CALL histbeg(stom_histname, iim, lon, jjm, lat,  1, iim, 1, jjm, &
2031                  &     istp_old, date0, dt, hori_id, hist_id_stom,domain_id=orch_domain_id)
2032#else
2033             CALL histbeg(stom_histname, iim, lon, jjm, lat,  1, iim, 1, jjm, &
2034                  &     istp_old, date0, dt, hori_id, hist_id_stom)
2035#endif
2036          ENDIF
2037          !- define PFT axis
2038          hist_PFTaxis = (/ ( REAL(i,r_std), i=1,nvm ) /)
2039          !- declare this axis
2040          CALL histvert (hist_id_stom, 'PFT', 'Plant functional type', &
2041               & '1', nvm, hist_PFTaxis, hist_PFTaxis_id)
2042          ! deforestation
2043          !- define Pool_10 axis
2044          hist_pool_10axis = (/ ( REAL(i,r_std), i=1,10 ) /)
2045          !- declare this axis
2046          CALL histvert (hist_id_stom, 'P10', 'Pool 10 years', &
2047               & '1', 10, hist_pool_10axis, hist_pool_10axis_id)
2048         
2049          !- define Pool_100 axis
2050          hist_pool_100axis = (/ ( REAL(i,r_std), i=1,100 ) /)
2051          !- declare this axis
2052          CALL histvert (hist_id_stom, 'P100', 'Pool 100 years', &
2053               & '1', 100, hist_pool_100axis, hist_pool_100axis_id)
2054         
2055          !- define Pool_11 axis
2056          hist_pool_11axis = (/ ( REAL(i,r_std), i=1,11 ) /)
2057          !- declare this axis
2058          CALL histvert (hist_id_stom, 'P11', 'Pool 10 years + 1', &
2059               & '1', 11, hist_pool_11axis, hist_pool_11axis_id)
2060         
2061          !- define Pool_101 axis
2062          hist_pool_101axis = (/ ( REAL(i,r_std), i=1,101 ) /)
2063          !- declare this axis
2064          CALL histvert (hist_id_stom, 'P101', 'Pool 100 years + 1', &
2065               & '1', 101, hist_pool_101axis, hist_pool_101axis_id)
2066       ENDIF
2067       !- define STOMATE history file
2068       CALL ioipslctrl_histstom (hist_id_stom, nvm, iim, jjm, &
2069            & dt, hist_dt_stom, hori_id, hist_PFTaxis_id, &
2070            & hist_pool_10axis_id, hist_pool_100axis_id, &
2071            & hist_pool_11axis_id, hist_pool_101axis_id)
2072       
2073       !- Write the names of the pfts in the stomate history files
2074       IF (is_omp_root) THEN
2075          global_attribute="PFT_name"
2076          DO i=1,nvm
2077             WRITE(global_attribute(9:10),"(I2.2)") i
2078             CALL histglobal_attr(hist_id_stom, global_attribute, PFT_name(i))
2079          ENDDO
2080
2081       !- end definition
2082          CALL histend(hist_id_stom)
2083       ENDIF
2084    END IF ! IF ( hist_dt_stom == 0 )
2085
2086       !-
2087       !-
2088       !-
2089       ! STOMATE IPCC OUTPUTS IS ACTIVATED
2090       !-
2091       !Config Key   = STOMATE_IPCC_OUTPUT_FILE
2092       !Config Desc  = Name of file in which STOMATE's output is going to be written
2093       !Config If    = OK_STOMATE
2094       !Config Def   = stomate_ipcc_history.nc
2095       !Config Help  = This file is going to be created by the model
2096       !Config         and will contain the output from the model.
2097       !Config         This file is a truly COADS compliant netCDF file.
2098       !Config         It will be generated by the hist software from
2099       !Config         the IOIPSL package.
2100       !Config Units = [FILE]
2101       !-
2102       stom_ipcc_histname='stomate_ipcc_history.nc'
2103       CALL getin_p('STOMATE_IPCC_OUTPUT_FILE', stom_ipcc_histname)       
2104       WRITE(numout,*) 'STOMATE_IPCC_OUTPUT_FILE', TRIM(stom_ipcc_histname)
2105       !-
2106       !Config Key   = STOMATE_IPCC_HIST_DT
2107       !Config Desc  = STOMATE IPCC history time step
2108       !Config If    = OK_STOMATE
2109       !Config Def   = 0.
2110       !Config Help  = Time step of the STOMATE IPCC history file
2111       !Config Units = [days]
2112       !-
2113       hist_days_stom_ipcc = zero
2114       CALL getin_p('STOMATE_IPCC_HIST_DT', hist_days_stom_ipcc)       
2115       IF ( hist_days_stom_ipcc == moins_un ) THEN
2116          hist_dt_stom_ipcc = moins_un
2117          WRITE(numout,*) 'output frequency for STOMATE IPCC history file (d): one month.'
2118       ELSE
2119          hist_dt_stom_ipcc = NINT( hist_days_stom_ipcc ) * one_day
2120          WRITE(numout,*) 'output frequency for STOMATE IPCC history file (d): ', &
2121            hist_dt_stom_ipcc/one_day
2122       ENDIF
2123       
2124       IF ( hist_dt_stom_ipcc /= 0 .AND. hist_id < 0 ) THEN
2125          ! sechiba_history file is not created therefore STOMATE IPCC history file will be deactivated
2126          hist_dt_stom_ipcc=0
2127          hist_days_stom_ipcc=0
2128          WRITE(numout,*) 'STOMATE IPCC history file is not created.'
2129       END IF
2130
2131       ! test consistency between STOMATE_IPCC_HIST_DT and DT_STOMATE parameters
2132       dt_stomate_loc = one_day
2133       CALL getin_p('DT_STOMATE', dt_stomate_loc)
2134       IF ( hist_days_stom_ipcc > zero ) THEN
2135          IF (dt_stomate_loc > hist_dt_stom_ipcc) THEN
2136             WRITE(numout,*) "DT_STOMATE = ",dt_stomate_loc,"  , STOMATE_IPCC_HIST_DT = ",hist_dt_stom_ipcc
2137             CALL ipslerr_p (3,'ioipslctrl_history', &
2138                  &          'Problem with DT_STOMATE > STOMATE_IPCC_HIST_DT','', &
2139                  &          '(must be less or equal)')
2140          ENDIF
2141       ENDIF
2142
2143       !Config Key   = OK_HISTSYNC
2144       !Config Desc  = Syncronize and write IOIPSL output files at each time step
2145       !Config If    =
2146       !Config Def   = FALSE
2147       !Config Help  = Setting this flag to true might affect run performance. Only use it for debug perpose.
2148       !Config Units = [FLAG]
2149       ok_histsync=.FALSE.
2150       CALL getin_p('OK_HISTSYNC', ok_histsync)       
2151
2152
2153
2154       IF ( hist_dt_stom_ipcc == 0 ) THEN
2155          hist_id_stom_ipcc = -1
2156       ELSE
2157          !-
2158          !- initialize
2159          IF (is_omp_root) THEN
2160             IF ( GridType == "RegLonLat" ) THEN
2161#ifdef CPP_PARA
2162                CALL histbeg(stom_ipcc_histname, iim, lon_rect, jjm, lat_rect,  1, iim, 1, jjm, &
2163                     &     istp_old, date0, dt, hori_id, hist_id_stom_ipcc,domain_id=orch_domain_id)
2164#else
2165                CALL histbeg(stom_ipcc_histname, iim, lon_rect, jjm, lat_rect,  1, iim, 1, jjm, &
2166                     &     istp_old, date0, dt, hori_id, hist_id_stom_ipcc)
2167#endif
2168             ELSE
2169#ifdef CPP_PARA
2170                CALL histbeg(stom_ipcc_histname, iim, lon, jjm, lat,  1, iim, 1, jjm, &
2171                     &     istp_old, date0, dt, hori_id, hist_id_stom_ipcc,domain_id=orch_domain_id)
2172#else
2173                CALL histbeg(stom_ipcc_histname, iim, lon, jjm, lat,  1, iim, 1, jjm, &
2174                     &     istp_old, date0, dt, hori_id, hist_id_stom_ipcc)
2175#endif
2176             ENDIF
2177             !- declare this axis
2178             CALL histvert (hist_id_stom_IPCC, 'PFT', 'Plant functional type', &
2179                  & '1', nvm, hist_PFTaxis, hist_IPCC_PFTaxis_id)
2180             
2181             !- define STOMATE history file
2182             CALL ioipslctrl_histstomipcc (hist_id_stom_IPCC, nvm, iim, jjm, &
2183                  & dt, hist_dt_stom_ipcc, hori_id, hist_IPCC_PFTaxis_id)
2184             
2185             !- Write the names of the pfts in the stomate history files
2186             global_attribute="PFT_name"
2187             DO i=1,nvm
2188                WRITE(global_attribute(9:10),"(I2.2)") i
2189                CALL histglobal_attr(hist_id_stom_IPCC, global_attribute, PFT_name(i))
2190             ENDDO
2191
2192             !- end definition
2193             CALL histend(hist_id_stom_IPCC)
2194          ENDIF
2195      ENDIF
2196   ENDIF
2197
2198
2199  END SUBROUTINE ioipslctrl_history
2200
2201!! ================================================================================================================================
2202!! SUBROUTINE    : ioipslctrl_histstom
2203!!
2204!>\BRIEF         This subroutine initialize the IOIPSL stomate output file
2205!!
2206!! DESCRIPTION   : This subroutine initialize the IOIPSL output file stomate_history.nc(default name).
2207!!                 This subroutine was previously named stom_define_history and where located in module intersurf.
2208!! RECENT CHANGE(S): None
2209!!
2210!! \n
2211!_ ================================================================================================================================
2212  SUBROUTINE ioipslctrl_histstom( &
2213       hist_id_stom, nvm, iim, jjm, dt, &
2214       hist_dt, hist_hori_id, hist_PFTaxis_id, &
2215       hist_pool_10axis_id, hist_pool_100axis_id, &
2216       hist_pool_11axis_id, hist_pool_101axis_id)
2217    ! deforestation axis added as arguments
2218
2219    !---------------------------------------------------------------------
2220    !- Tell ioipsl which variables are to be written
2221    !- and on which grid they are defined
2222    !---------------------------------------------------------------------
2223    IMPLICIT NONE
2224    !-
2225    !- Input
2226    !-
2227    !- File id
2228    INTEGER(i_std),INTENT(in) :: hist_id_stom
2229    !- number of PFTs
2230    INTEGER(i_std),INTENT(in) :: nvm
2231    !- Domain size
2232    INTEGER(i_std),INTENT(in) :: iim, jjm
2233    !- Time step of STOMATE (seconds)
2234    REAL(r_std),INTENT(in)    :: dt
2235    !- Time step of history file (s)
2236    REAL(r_std),INTENT(in)    :: hist_dt
2237    !- id horizontal grid
2238    INTEGER(i_std),INTENT(in) :: hist_hori_id
2239    !- id of PFT axis
2240    INTEGER(i_std),INTENT(in) :: hist_PFTaxis_id
2241    !- id of Deforestation axis
2242    INTEGER(i_std),INTENT(in) :: hist_pool_10axis_id,hist_pool_100axis_id
2243    INTEGER(i_std),INTENT(in) :: hist_pool_11axis_id,hist_pool_101axis_id
2244    !-
2245    !- 1 local
2246    !-
2247    !- maximum history level
2248    INTEGER(i_std), PARAMETER  :: max_hist_level = 10
2249    !- output level (between 0 and 10)
2250    !-  ( 0:nothing is written, 10:everything is written)
2251    INTEGER(i_std)             :: hist_level
2252    !- Character strings to define operations for histdef
2253    CHARACTER(LEN=40),DIMENSION(max_hist_level) :: ave
2254
2255    !---------------------------------------------------------------------
2256    !=====================================================================
2257    !- 1 history level
2258    !=====================================================================
2259    !- 1.1 define history levelx
2260    !=====================================================================
2261    !Config Key   = STOMATE_HISTLEVEL
2262    !Config Desc  = STOMATE history output level (0..10)
2263    !Config If    = OK_STOMATE
2264    !Config Def   = 10
2265    !Config Help  = 0: nothing is written; 10: everything is written
2266    !Config Units = [-]
2267    !-
2268    hist_level = 10
2269    CALL getin_p('STOMATE_HISTLEVEL', hist_level)
2270    !-
2271    WRITE(numout,*) 'STOMATE history level: ',hist_level
2272    IF ( (hist_level > max_hist_level).OR.(hist_level < 0) ) THEN
2273       STOP 'This history level is not allowed'
2274    ENDIF
2275    !=====================================================================
2276    !- 1.2 define operations according to output level
2277    !=====================================================================
2278    ave(1:hist_level) =  'ave(scatter(X))'
2279    ave(hist_level+1:max_hist_level) =  'never          '
2280    !=====================================================================
2281    !- 2 surface fields (2d)
2282    !- 3 PFT: 3rd dimension
2283    !=====================================================================
2284
2285
2286    ! structural litter above ground
2287    IF (is_omp_root) THEN
2288       CALL histdef (hist_id_stom, &
2289            &               TRIM("LITTER_STR_AB       "), &
2290            &               TRIM("structural litter above ground                    "), &
2291            &               TRIM("gC/m^2/pft          "), iim,jjm, hist_hori_id, &
2292            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
2293       
2294       ! metabolic litter above ground                     
2295       CALL histdef (hist_id_stom, &
2296            &               TRIM("LITTER_MET_AB       "), &
2297            &               TRIM("metabolic litter above ground                     "), &
2298            &               TRIM("gC/m^2/pft          "), iim,jjm, hist_hori_id, &
2299            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
2300       
2301       ! structural litter below ground               
2302       CALL histdef (hist_id_stom, &
2303            &               TRIM("LITTER_STR_BE       "), &
2304            &               TRIM("structural litter below ground                    "), &
2305            &               TRIM("gC/m^2/pft          "), iim,jjm, hist_hori_id, &
2306            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
2307       
2308       ! metabolic litter below ground               
2309       CALL histdef (hist_id_stom, &
2310            &               TRIM("LITTER_MET_BE       "), &
2311            &               TRIM("metabolic litter below ground                     "), &
2312            &               TRIM("gC/m^2/pft          "), iim,jjm, hist_hori_id, &
2313            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
2314       
2315       ! fraction of soil covered by dead leaves           
2316       CALL histdef (hist_id_stom, &
2317            &               TRIM("DEADLEAF_COVER      "), &
2318            &               TRIM("fraction of soil covered by dead leaves           "), &
2319            &               TRIM("-                   "), iim,jjm, hist_hori_id, &
2320            &               1,1,1, -99,32, ave(5), dt, hist_dt)
2321       
2322       ! total soil and litter carbon
2323       CALL histdef (hist_id_stom, &
2324            &               TRIM("TOTAL_SOIL_CARB     "), &
2325            &               TRIM("total soil and litter carbon                      "), &
2326            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
2327            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
2328       
2329       ! active soil carbon in ground                 
2330       CALL histdef (hist_id_stom, &
2331            &               TRIM("CARBON_ACTIVE       "), &
2332            &               TRIM("active soil carbon in ground                      "), &
2333            &               TRIM("gC/m^2/pft          "), iim,jjm, hist_hori_id, &
2334            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
2335       
2336       ! slow soil carbon in ground                   
2337       CALL histdef (hist_id_stom, &
2338            &               TRIM("CARBON_SLOW         "), &
2339            &               TRIM("slow soil carbon in ground                        "), &
2340            &               TRIM("gC/m^2/pft          "), iim,jjm, hist_hori_id, &
2341            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
2342       
2343       ! passive soil carbon in ground               
2344       CALL histdef (hist_id_stom, &
2345            &               TRIM("CARBON_PASSIVE      "), &
2346            &               TRIM("passive soil carbon in ground                     "), &
2347            &               TRIM("gC/m^2/pft          "), iim,jjm, hist_hori_id, &
2348            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
2349       
2350       ! Long term 2 m temperature                           
2351       CALL histdef (hist_id_stom, &
2352            &               TRIM("T2M_LONGTERM        "), &
2353            &               TRIM("Longterm 2 m temperature                          "), &
2354            &               TRIM("K                   "), iim,jjm, hist_hori_id, &
2355            &               1,1,1, -99,32, ave(9), dt, hist_dt)
2356       
2357       ! Monthly 2 m temperature                           
2358       CALL histdef (hist_id_stom, &
2359            &               TRIM("T2M_MONTH           "), &
2360            &               TRIM("Monthly 2 m temperature                           "), &
2361            &               TRIM("K                   "), iim,jjm, hist_hori_id, &
2362            &               1,1,1, -99,32, ave(1), dt, hist_dt)
2363       
2364       ! Weekly 2 m temperature                           
2365       CALL histdef (hist_id_stom, &
2366            &               TRIM("T2M_WEEK            "), &
2367            &               TRIM("Weekly 2 m temperature                            "), &
2368            &               TRIM("K                   "), iim,jjm, hist_hori_id, &
2369            &               1,1,1, -99,32, ave(1), dt, hist_dt)
2370       
2371       ! heterotr. resp. from ground                 
2372       CALL histdef (hist_id_stom, &
2373            &               TRIM("HET_RESP            "), &
2374            &               TRIM("heterotr. resp. from ground                       "), &
2375            &               TRIM("gC/m^2 tot/pft/day  "), iim,jjm, hist_hori_id, &
2376            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(3), dt, hist_dt)
2377       
2378       ! Fire fraction on ground
2379       CALL histdef (hist_id_stom, &
2380            &               TRIM("FIREFRAC            "), &
2381            &               TRIM("Fire fraction on ground                           "), &
2382            &               TRIM("1/day               "), iim,jjm, hist_hori_id, &
2383            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(1), dt, hist_dt)
2384
2385       ! Fire index on ground                     
2386       CALL histdef (hist_id_stom, &
2387            &               TRIM("FIREINDEX           "), &
2388            &               TRIM("Fire index on ground                              "), &
2389            &               TRIM("-                   "), iim,jjm, hist_hori_id, &
2390            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
2391       
2392       ! Litter humidity                                   
2393       CALL histdef (hist_id_stom, &
2394            &               TRIM("LITTERHUM           "), &
2395            &               TRIM("Litter humidity                                   "), &
2396            &               TRIM("-                   "), iim,jjm, hist_hori_id, &
2397            &               1,1,1, -99,32, ave(5), dt, hist_dt)
2398       
2399       ! CO2 flux                                 
2400       CALL histdef (hist_id_stom, &
2401            &               TRIM("CO2FLUX             "), &
2402            &               TRIM("CO2 flux                                          "), &
2403            &               TRIM("gC/m^2/pft/mth      "), iim,jjm, hist_hori_id, &
2404            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(1), dt, hist_dt)
2405
2406       ! Output CO2 flux from fire                         
2407       CALL histdef (hist_id_stom, &
2408            &               TRIM("CO2_FIRE            "), &
2409            &               TRIM("Output CO2 flux from fire                         "), &
2410            &               TRIM("gC/day/m^2/pft      "), iim,jjm, hist_hori_id, &
2411            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(1), dt, hist_dt)
2412       
2413       ! CO2 taken from atmosphere for initiate growth     
2414       CALL histdef (hist_id_stom, &
2415            &               TRIM("CO2_TAKEN           "), &
2416            &               TRIM("CO2 taken from atmosphere for initiate growth     "), &
2417            &               TRIM("gC/day/m^2/pft      "), iim,jjm, hist_hori_id, &
2418            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(1), dt, hist_dt)
2419
2420       IF (ok_dgvm) THEN
2421          ! total co2 flux (sum over 13 PFTs). when DGVM is activated, the previous
2422          ! SUM(CO2FLUX*veget_max) is wrong. We should look at this variable.
2423          CALL histdef (hist_id_stom, &
2424               &               TRIM("tCO2FLUX            "), &
2425               &               TRIM("total CO2flux of 13 PFTs (after adjustment)       "), &
2426               &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
2427               &               1,1,1, -99,32, ave(1), dt, hist_dt)
2428         
2429          ! should be the same with tCO2FLUX
2430          CALL histdef (hist_id_stom, &
2431               &               TRIM("tCO2FLUX_OLD        "), &
2432               &               TRIM("total CO2flux of 13 PFTs(multiply by veget_max_old"), &
2433               &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
2434               &               1,1,1, -99,32, ave(10), dt, hist_dt)
2435         
2436          CALL histdef (hist_id_stom, &
2437               &               TRIM("tGPP                 "), &
2438               &               TRIM("total GPP of 13 PFTs (after adjustment)           "), &
2439               &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
2440               &               1,1,1, -99,32, ave(1), dt, hist_dt)
2441       
2442          CALL histdef (hist_id_stom, &
2443               &               TRIM("tRESP_GROWTH         "), &
2444               &               TRIM("total resp growth of 13 PFTs (after adjustment)   "), &
2445               &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
2446               &               1,1,1, -99,32, ave(1), dt, hist_dt)
2447         
2448          CALL histdef (hist_id_stom, &
2449               &               TRIM("tRESP_MAINT          "), &
2450               &               TRIM("total resp maint  of 13 PFTs (after adjustment)   "), &
2451               &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
2452               &               1,1,1, -99,32, ave(1), dt, hist_dt)
2453       
2454          CALL histdef (hist_id_stom, &
2455               &               TRIM("tRESP_HETERO         "), &
2456               &               TRIM("total resp hetero of 13 PFTs (after adjustment)   "), &
2457               &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
2458               &               1,1,1, -99,32, ave(1), dt, hist_dt)
2459       
2460          CALL histdef (hist_id_stom, &
2461               &               TRIM("tCARBON              "), &
2462               &               TRIM("total carbon of 13 PFTs (after adjustment)        "), &
2463               &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
2464               &               1,1,1, -99,32, ave(1), dt, hist_dt)
2465         
2466          CALL histdef (hist_id_stom, &
2467               &               TRIM("tBIOMASS             "), &
2468               &               TRIM("total biomass of 13 PFTs (after adjustment)       "), &
2469               &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
2470               &               1,1,1, -99,32, ave(1), dt, hist_dt)
2471       
2472          CALL histdef (hist_id_stom, &
2473               &               TRIM("tLITTER              "), &
2474               &               TRIM("total litter of 13 PFTs (after adjustment)        "), &
2475               &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
2476               &               1,1,1, -99,32, ave(1), dt, hist_dt)
2477       
2478          CALL histdef (hist_id_stom, &
2479               &               TRIM("tSOILC               "), &
2480               &               TRIM("total soil carbon of 13 PFTs (after adjustment)   "), &
2481               &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
2482               &               1,1,1, -99,32, ave(1), dt, hist_dt)
2483
2484          CALL histdef (hist_id_stom, &
2485               &               TRIM("tCO2_TAKEN           "), &
2486               &               TRIM("total co2_to_bm 13 PFTs (after adjustment)        "), &
2487               &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
2488               &               1,1,1, -99,32, ave(10), dt, hist_dt)
2489         
2490          CALL histdef (hist_id_stom, &
2491               &               TRIM("tCO2_FIRE            "), &
2492               &               TRIM("total co2_fire 13 PFTs (after adjustment)         "), &
2493               &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
2494               &               1,1,1, -99,32, ave(10), dt, hist_dt)
2495       END IF
2496       
2497
2498       CALL histdef (hist_id_stom, &
2499            &               TRIM("FPC_MAX             "), &
2500            &               TRIM("foliage projective cover                          "), &
2501            &               TRIM("-                   "), iim,jjm, hist_hori_id, &
2502            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
2503       
2504       CALL histdef (hist_id_stom, &
2505            &               TRIM("MAXFPC_LASTYEAR     "), &
2506            &               TRIM("foliage projective cover of last year             "), &
2507            &               TRIM("-                   "), iim,jjm, hist_hori_id, &
2508            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
2509
2510       ! "seasonal" 2 m temperature                           
2511       CALL histdef (hist_id_stom, &
2512         &               TRIM("TSEASON             "), &
2513         &               TRIM("Seasonal 2 m temperature                             "), &
2514         &               TRIM("K                   "), iim,jjm, hist_hori_id, &
2515         &               1,1,1, -99,32, ave(10), dt, hist_dt)
2516
2517       ! how many days after onset                           
2518       CALL histdef (hist_id_stom, &
2519         &               TRIM("TMIN_SPRING_TIME    "), &
2520         &               TRIM("how many days after onset                            "), &
2521         &               TRIM("days                "), iim,jjm, hist_hori_id, &
2522         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
2523
2524       !                           
2525       CALL histdef (hist_id_stom, &
2526         &               TRIM("ONSET_DATE          "), &
2527         &               TRIM("onset date                                           "), &
2528         &               TRIM("day                 "), iim,jjm, hist_hori_id, &
2529         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
2530
2531       ! Leaf Area Index                                   
2532       CALL histdef (hist_id_stom, &
2533            &               TRIM("LAI                 "), &
2534            &               TRIM("Leaf Area Index                                   "), &
2535            &               TRIM("-                   "), iim,jjm, hist_hori_id, &
2536            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(1), dt, hist_dt)
2537       
2538       ! Maximum vegetation fraction (LAI -> infinity)     
2539       CALL histdef (hist_id_stom, &
2540            &               TRIM("VEGET_MAX           "), &
2541            &               TRIM("Maximum vegetation fraction (LAI -> infinity)     "), &
2542            &               TRIM("-                   "), iim,jjm, hist_hori_id, &
2543            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(1), dt, hist_dt)
2544       
2545       ! Net primary productivity                         
2546       CALL histdef (hist_id_stom, &
2547            &               TRIM("NPP                 "), &
2548            &               TRIM("Net primary productivity                          "), &
2549            &               TRIM("gC/day/(m^2 tot)    "), iim,jjm, hist_hori_id, &
2550            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(1), dt, hist_dt)
2551
2552       ! Gross primary productivity                       
2553       CALL histdef (hist_id_stom, &
2554            &               TRIM("GPP                 "), &
2555            &               TRIM("Gross primary productivity                        "), &
2556            &               TRIM("gC/day/m^2          "), iim,jjm, hist_hori_id, &
2557            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(1), dt, hist_dt)
2558
2559       ! Density of individuals                           
2560       CALL histdef (hist_id_stom, &
2561            &               TRIM("IND                 "), &
2562            &               TRIM("Density of individuals                            "), &
2563            &               TRIM("1/ m^2              "), iim,jjm, hist_hori_id, &
2564            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(3), dt, hist_dt)
2565
2566       ! Adaptation to climate
2567       CALL histdef (hist_id_stom, &
2568            &               TRIM("ADAPTATION          "), &
2569            &               TRIM("Adaptation to climate (DGVM)                      "), &
2570            &               TRIM("-                   "), iim,jjm, hist_hori_id, &
2571            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(3), dt, hist_dt)
2572   
2573       ! Probability from regenerative
2574       CALL histdef (hist_id_stom, &
2575            &               TRIM("REGENERATION        "), &
2576            &               TRIM("Probability from regenerative (DGVM)               "), &
2577            &               TRIM("-                   "), iim,jjm, hist_hori_id, &
2578            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(3), dt, hist_dt)
2579       
2580       ! crown area of individuals (m**2)
2581       CALL histdef (hist_id_stom, &
2582            &               TRIM("CN_IND              "), &
2583            &               TRIM("crown area of individuals                         "), &
2584            &               TRIM("m^2                 "), iim,jjm, hist_hori_id, &
2585            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(3), dt, hist_dt)
2586
2587       ! woodmass of individuals (gC)
2588       CALL histdef (hist_id_stom, &
2589            &               TRIM("WOODMASS_IND        "), &
2590            &               TRIM("Woodmass of individuals                           "), &
2591            &               TRIM("gC/pft              "), iim,jjm, hist_hori_id, &
2592            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(3), dt, hist_dt)
2593
2594       ! total living biomass
2595       CALL histdef (hist_id_stom, &
2596            &               TRIM("TOTAL_M             "), &
2597            &               TRIM("Total living biomass                              "), &
2598            &               TRIM("gC/m^2/pft          "), iim,jjm, hist_hori_id, &
2599            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(4), dt, hist_dt)
2600       
2601       ! Leaf mass                                         
2602       CALL histdef (hist_id_stom, &
2603            &               TRIM("LEAF_M              "), &
2604            &               TRIM("Leaf mass                                         "), &
2605            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
2606            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
2607       
2608       ! Sap mass above ground                             
2609       CALL histdef (hist_id_stom, &
2610            &               TRIM("SAP_M_AB            "), &
2611            &               TRIM("Sap mass above ground                             "), &
2612            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
2613            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
2614
2615       ! Sap mass below ground                             
2616       CALL histdef (hist_id_stom, &
2617            &               TRIM("SAP_M_BE            "), &
2618            &               TRIM("Sap mass below ground                             "), &
2619            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
2620            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
2621       
2622       ! Heartwood mass above ground                       
2623       CALL histdef (hist_id_stom, &
2624            &               TRIM("HEART_M_AB          "), &
2625            &               TRIM("Heartwood mass above ground                       "), &
2626            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
2627            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
2628
2629       ! Heartwood mass below ground                       
2630       CALL histdef (hist_id_stom, &
2631            &               TRIM("HEART_M_BE          "), &
2632            &               TRIM("Heartwood mass below ground                       "), &
2633            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
2634            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
2635
2636       ! Root mass                                         
2637       CALL histdef (hist_id_stom, &
2638            &               TRIM("ROOT_M              "), &
2639            &               TRIM("Root mass                                         "), &
2640            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
2641            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
2642       
2643       ! Fruit mass                                       
2644       CALL histdef (hist_id_stom, &
2645            &               TRIM("FRUIT_M             "), &
2646            &               TRIM("Fruit mass                                        "), &
2647            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
2648            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
2649       
2650       ! Carbohydrate reserve mass                         
2651       CALL histdef (hist_id_stom, &
2652            &               TRIM("RESERVE_M           "), &
2653            &               TRIM("Carbohydrate reserve mass                         "), &
2654            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
2655            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
2656       
2657       ! total turnover rate
2658       CALL histdef (hist_id_stom, &
2659            &               TRIM("TOTAL_TURN          "), &
2660            &               TRIM("total turnover rate                               "), &
2661            &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
2662            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(4), dt, hist_dt)
2663
2664       ! Leaf turnover                                     
2665       CALL histdef (hist_id_stom, &
2666            &               TRIM("LEAF_TURN           "), &
2667            &               TRIM("Leaf turnover                                     "), &
2668            &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
2669            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(4), dt, hist_dt)
2670
2671       ! Sap turnover above                               
2672       CALL histdef (hist_id_stom, &
2673            &               TRIM("SAP_AB_TURN         "), &
2674            &               TRIM("Sap turnover above                                "), &
2675            &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
2676            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(4), dt, hist_dt)
2677
2678       ! Root turnover                                     
2679       CALL histdef (hist_id_stom, &
2680            &               TRIM("ROOT_TURN           "), &
2681            &               TRIM("Root turnover                                     "), &
2682            &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
2683            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(4), dt, hist_dt)
2684
2685       ! Fruit turnover                                   
2686       CALL histdef (hist_id_stom, &
2687            &               TRIM("FRUIT_TURN          "), &
2688            &               TRIM("Fruit turnover                                    "), &
2689            &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
2690            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(4), dt, hist_dt)
2691
2692       ! total conversion of biomass to litter
2693       CALL histdef (hist_id_stom, &
2694            &               TRIM("TOTAL_BM_LITTER     "), &
2695            &               TRIM("total conversion of biomass to litter             "), &
2696            &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
2697            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(4), dt, hist_dt)
2698
2699       ! Leaf death                                       
2700       CALL histdef (hist_id_stom, &
2701            &               TRIM("LEAF_BM_LITTER      "), &
2702            &               TRIM("Leaf death                                        "), &
2703            &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
2704            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(4), dt, hist_dt)
2705       
2706       ! Sap death above ground                           
2707       CALL histdef (hist_id_stom, &
2708            &               TRIM("SAP_AB_BM_LITTER    "), &
2709            &               TRIM("Sap death above ground                            "), &
2710            &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
2711            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(4), dt, hist_dt)
2712
2713       ! Sap death below ground                           
2714       CALL histdef (hist_id_stom, &
2715            &               TRIM("SAP_BE_BM_LITTER    "), &
2716            &               TRIM("Sap death below ground                            "), &
2717            &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
2718            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(4), dt, hist_dt)
2719
2720       ! Heartwood death above ground                     
2721       CALL histdef (hist_id_stom, &
2722            &               TRIM("HEART_AB_BM_LITTER  "), &
2723            &               TRIM("Heartwood death above ground                      "), &
2724            &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
2725            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(4), dt, hist_dt)
2726
2727       ! Heartwood death below ground                     
2728       CALL histdef (hist_id_stom, &
2729            &               TRIM("HEART_BE_BM_LITTER  "), &
2730            &               TRIM("Heartwood death below ground                      "), &
2731            &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
2732            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(4), dt, hist_dt)
2733
2734       ! Root death                                       
2735       CALL histdef (hist_id_stom, &
2736            &               TRIM("ROOT_BM_LITTER      "), &
2737            &               TRIM("Root death                                        "), &
2738            &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
2739            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(4), dt, hist_dt)
2740       
2741       ! Fruit death                                       
2742       CALL histdef (hist_id_stom, &
2743            &               TRIM("FRUIT_BM_LITTER     "), &
2744            &               TRIM("Fruit death                                       "), &
2745            &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
2746            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(4), dt, hist_dt)
2747
2748       ! Carbohydrate reserve death                       
2749       CALL histdef (hist_id_stom, &
2750            &               TRIM("RESERVE_BM_LITTER   "), &
2751            &               TRIM("Carbohydrate reserve death                        "), &
2752            &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
2753            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(4), dt, hist_dt)
2754
2755       ! Maintenance respiration                           
2756       CALL histdef (hist_id_stom, &
2757            &               TRIM("MAINT_RESP          "), &
2758            &               TRIM("Maintenance respiration                           "), &
2759            &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
2760            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
2761
2762       ! Growth respiration                               
2763       CALL histdef (hist_id_stom, &
2764            &               TRIM("GROWTH_RESP         "), &
2765            &               TRIM("Growth respiration                                "), &
2766            &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
2767            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
2768       
2769       ! age                                               
2770       CALL histdef (hist_id_stom, &
2771            &               TRIM("AGE                 "), &
2772            &               TRIM("age                                               "), &
2773            &               TRIM("years               "), iim,jjm, hist_hori_id, &
2774            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(7), dt, hist_dt)
2775       
2776       ! height                                           
2777       CALL histdef (hist_id_stom, &
2778            &               TRIM("HEIGHT              "), &
2779            &               TRIM("height                                            "), &
2780            &               TRIM("m                   "), iim,jjm, hist_hori_id, &
2781            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(7), dt, hist_dt)
2782
2783       ! weekly moisture stress                           
2784       CALL histdef (hist_id_stom, &
2785            &               TRIM("MOISTRESS           "), &
2786            &               TRIM("weekly moisture stress                            "), &
2787            &               TRIM("-                   "), iim,jjm, hist_hori_id, &
2788            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(3), dt, hist_dt)
2789
2790       ! Maximum rate of carboxylation                     
2791       CALL histdef (hist_id_stom, &
2792            &               TRIM("VCMAX               "), &
2793            &               TRIM("Maximum rate of carboxylation                     "), &
2794            &               TRIM("-                   "), iim,jjm, hist_hori_id, &
2795            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(6), dt, hist_dt)
2796
2797       ! leaf age                                         
2798       CALL histdef (hist_id_stom, &
2799            &               TRIM("LEAF_AGE            "), &
2800            &               TRIM("leaf age                                          "), &
2801            &               TRIM("days                "), iim,jjm, hist_hori_id, &
2802            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(6), dt, hist_dt)
2803       
2804       ! Fraction of trees that dies (gap)                 
2805       CALL histdef (hist_id_stom, &
2806            &               TRIM("MORTALITY           "), &
2807            &               TRIM("Fraction of trees that dies (gap)                 "), &
2808            &               TRIM("1/day               "), iim,jjm, hist_hori_id, &
2809            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(6), dt, hist_dt)
2810
2811       ! Fraction of plants killed by fire                 
2812       CALL histdef (hist_id_stom, &
2813            &               TRIM("FIREDEATH           "), &
2814            &               TRIM("Fraction of plants killed by fire                 "), &
2815            &               TRIM("1/day               "), iim,jjm, hist_hori_id, &
2816            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(6), dt, hist_dt)
2817
2818       ! Density of newly established saplings             
2819       CALL histdef (hist_id_stom, &
2820            &               TRIM("IND_ESTAB           "), &
2821            &               TRIM("Density of newly established saplings             "), &
2822            &               TRIM("1/day               "), iim,jjm, hist_hori_id, &
2823            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(6), dt, hist_dt)
2824
2825       ! Establish tree
2826       CALL histdef (hist_id_stom, &
2827            &               TRIM("ESTABTREE           "), &
2828            &               TRIM("Rate of tree establishement                       "), &
2829            &               TRIM("1/day               "), iim,jjm, hist_hori_id, &
2830            &               1,1,1, -99,32, ave(6), dt, hist_dt)
2831
2832       ! Establish grass
2833       CALL histdef (hist_id_stom, &
2834            &               TRIM("ESTABGRASS          "), &
2835            &               TRIM("Rate of grass establishement                      "), &
2836            &               TRIM("1/day               "), iim,jjm, hist_hori_id, &
2837            &               1,1,1, -99,32, ave(6), dt, hist_dt)
2838
2839       ! Fraction of plants that dies (light competition) 
2840       CALL histdef (hist_id_stom, &
2841            &               TRIM("LIGHT_DEATH         "), &
2842            &               TRIM("Fraction of plants that dies (light competition)  "), &
2843            &               TRIM("1/day               "), iim,jjm, hist_hori_id, &
2844            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(6), dt, hist_dt)
2845
2846       ! biomass allocated to leaves                       
2847       CALL histdef (hist_id_stom, &
2848            &               TRIM("BM_ALLOC_LEAF       "), &
2849            &               TRIM("biomass allocated to leaves                       "), &
2850            &               TRIM("gC/m**2/pft/dt      "), iim,jjm, hist_hori_id, &
2851            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
2852
2853       ! biomass allocated to sapwood above ground         
2854       CALL histdef (hist_id_stom, &
2855            &               TRIM("BM_ALLOC_SAP_AB     "), &
2856            &               TRIM("biomass allocated to sapwood above ground         "), &
2857            &               TRIM("gC/m**2/pft/dt      "), iim,jjm, hist_hori_id, &
2858            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
2859
2860       ! biomass allocated to sapwood below ground         
2861       CALL histdef (hist_id_stom, &
2862            &               TRIM("BM_ALLOC_SAP_BE     "), &
2863            &               TRIM("biomass allocated to sapwood below ground         "), &
2864            &               TRIM("gC/m**2/pft/dt      "), iim,jjm, hist_hori_id, &
2865            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
2866
2867       ! biomass allocated to roots                       
2868       CALL histdef (hist_id_stom, &
2869            &               TRIM("BM_ALLOC_ROOT       "), &
2870            &               TRIM("biomass allocated to roots                        "), &
2871            &               TRIM("gC/m**2/pft/dt          "), iim,jjm, hist_hori_id, &
2872            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
2873
2874       ! biomass allocated to fruits                       
2875       CALL histdef (hist_id_stom, &
2876            &               TRIM("BM_ALLOC_FRUIT      "), &
2877            &               TRIM("biomass allocated to fruits                       "), &
2878            &               TRIM("gC/m**2/pft/dt          "), iim,jjm, hist_hori_id, &
2879            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
2880
2881       ! biomass allocated to carbohydrate reserve         
2882       CALL histdef (hist_id_stom, &
2883            &               TRIM("BM_ALLOC_RES        "), &
2884            &               TRIM("biomass allocated to carbohydrate reserve         "), &
2885            &               TRIM("gC/m**2/pft/dt          "), iim,jjm, hist_hori_id, &
2886            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
2887
2888       ! time constant of herbivore activity               
2889       CALL histdef (hist_id_stom, &
2890            &               TRIM("HERBIVORES          "), &
2891            &               TRIM("time constant of herbivore activity               "), &
2892            &               TRIM("days                "), iim,jjm, hist_hori_id, &
2893            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
2894
2895       ! turnover time for grass leaves                   
2896       CALL histdef (hist_id_stom, &
2897            &               TRIM("TURNOVER_TIME       "), &
2898            &               TRIM("turnover time for grass leaves                    "), &
2899            &               TRIM("days                "), iim,jjm, hist_hori_id, &
2900            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
2901       
2902       ! 10 year wood product pool                         
2903       CALL histdef (hist_id_stom, &
2904            &               TRIM("PROD10              "), &
2905            &               TRIM("10 year wood product pool                         "), &
2906            &               TRIM("gC/m**2             "), iim,jjm, hist_hori_id, &
2907            &               11,1,11, hist_pool_11axis_id,32, ave(5), dt, hist_dt)
2908       
2909       ! annual flux for each 10 year wood product pool   
2910       CALL histdef (hist_id_stom, &
2911            &               TRIM("FLUX10              "), &
2912            &               TRIM("annual flux for each 10 year wood product pool    "), &
2913            &               TRIM("gC/m**2/yr          "), iim,jjm, hist_hori_id, &
2914            &               10,1,10, hist_pool_10axis_id,32, ave(5), dt, hist_dt)
2915       
2916       ! 100 year wood product pool                       
2917       CALL histdef (hist_id_stom, &
2918            &               TRIM("PROD100             "), &
2919            &               TRIM("100 year wood product pool                        "), &
2920            &               TRIM("gC/m**2             "), iim,jjm, hist_hori_id, &
2921            &               101,1,101, hist_pool_101axis_id,32, ave(5), dt, hist_dt)
2922
2923       ! annual flux for each 100 year wood product pool   
2924       CALL histdef (hist_id_stom, &
2925            &               TRIM("FLUX100             "), &
2926            &               TRIM("annual flux for each 100 year wood product pool   "), &
2927            &               TRIM("gC/m**2/yr          "), iim,jjm, hist_hori_id, &
2928            &               100,1,100, hist_pool_100axis_id,32, ave(5), dt, hist_dt)
2929
2930       ! annual release right after deforestation         
2931       CALL histdef (hist_id_stom, &
2932            &               TRIM("CONVFLUX            "), &
2933            &               TRIM("annual release right after deforestation          "), &
2934            &               TRIM("gC/m**2/day          "), iim,jjm, hist_hori_id, &
2935            &               1,1,1, -99,32, ave(5), dt, hist_dt)
2936
2937       ! annual release from all 10 year wood product pools
2938       CALL histdef (hist_id_stom, &
2939            &               TRIM("CFLUX_PROD10        "), &
2940            &               TRIM("annual release from all 10 year wood product pools"), &
2941            &               TRIM("gC/m**2/day          "), iim,jjm, hist_hori_id, &
2942            &               1,1,1, -99,32, ave(5), dt, hist_dt)
2943
2944       ! annual release from all 100year wood product pools
2945       CALL histdef (hist_id_stom, &
2946            &               TRIM("CFLUX_PROD100       "), &
2947            &               TRIM("annual release from all 100year wood product pools"), &
2948            &               TRIM("gC/m**2/day          "), iim,jjm, hist_hori_id, &
2949            &               1,1,1, -99,32, ave(5), dt, hist_dt)
2950       ! agriculure product
2951       CALL histdef (hist_id_stom, &
2952            &               TRIM("HARVEST_ABOVE       "), &
2953            &               TRIM("annual release product after harvest              "), &
2954            &               TRIM("gC/m**2/day          "), iim,jjm, hist_hori_id, &
2955            &               1,1,1, -99,32, ave(5), dt, hist_dt)
2956
2957
2958       CALL histdef(hist_id_stom, 'RESOLUTION_X', 'E-W resolution', 'm', &
2959            & iim,jjm, hist_hori_id, 1,1,1, -99, 32, 'once(scatter(X))', dt, hist_dt)
2960       CALL histdef(hist_id_stom, 'RESOLUTION_Y', 'N-S resolution', 'm', &
2961            & iim,jjm, hist_hori_id, 1,1,1, -99, 32, 'once(scatter(X))', dt, hist_dt)
2962       CALL histdef(hist_id_stom, 'CONTFRAC', 'Continental fraction', '1', &
2963            & iim,jjm, hist_hori_id, 1,1,1, -99, 32, 'once(scatter(X))', dt, hist_dt)
2964       CALL histdef(hist_id_stom, 'Areas', 'Mesh areas', 'm2', &
2965            & iim,jjm, hist_hori_id, 1,1,1, -99, 32, 'once(scatter(X))', dt, hist_dt)
2966       
2967       !  Special outputs for phenology
2968       CALL histdef (hist_id_stom, &
2969            &               TRIM("WHEN_GROWTHINIT     "), &
2970            &               TRIM("Time elapsed from season beginning                "), &
2971            &               TRIM("d                   "), iim,jjm, hist_hori_id, &
2972            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(9), dt, hist_dt)
2973       
2974       CALL histdef (hist_id_stom, &
2975            &               TRIM("PFTPRESENT          "), &
2976            &               TRIM("PFT exists                                        "), &
2977            &               TRIM("d                   "), iim,jjm, hist_hori_id, &
2978            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(9), dt, hist_dt)
2979       
2980       CALL histdef (hist_id_stom, &
2981            &               TRIM("GDD_MIDWINTER       "), &
2982            &               TRIM("Growing degree days, since midwinter              "), &
2983            &               TRIM("degK                "), iim,jjm, hist_hori_id, &
2984            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(9), dt, hist_dt)
2985
2986       CALL histdef (hist_id_stom, &
2987            &               TRIM("GDD_M5_DORMANCE     "), &
2988            &               TRIM("Growing degree days, since dormance               "), &
2989            &               TRIM("degK                "), iim,jjm, hist_hori_id, &
2990            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(9), dt, hist_dt)
2991       
2992       CALL histdef (hist_id_stom, &
2993            &               TRIM("NCD_DORMANCE        "), &
2994            &               TRIM("Number of chilling days, since leaves were lost   "), &
2995            &               TRIM("d                   "), iim,jjm, hist_hori_id, &
2996            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(9), dt, hist_dt)
2997       
2998       CALL histdef (hist_id_stom, &
2999            &               TRIM("ALLOW_INITPHENO     "), &
3000            &               TRIM("Allow to declare beginning of the growing season  "), &
3001            &               TRIM("-                   "), iim,jjm, hist_hori_id, &
3002            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(9), dt, hist_dt)
3003       
3004       CALL histdef (hist_id_stom, &
3005            &               TRIM("BEGIN_LEAVES        "), &
3006            &               TRIM("Signal to start putting leaves on                 "), &
3007            &               TRIM("-                   "), iim,jjm, hist_hori_id, &
3008            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(9), dt, hist_dt)
3009
3010!gmjc
3011!GM0
3012    CALL histdef (hist_id_stom, &
3013         &               TRIM("GRAZINGC "), &
3014         &               TRIM("Grazing C "), &
3015         &               TRIM("kgC/m^2/day "), iim,jjm, hist_hori_id, &
3016         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
3017!GM1
3018    CALL histdef (hist_id_stom, &
3019         &               TRIM("GRAZINGCSUM "), &
3020         &               TRIM("- "), &
3021         &               TRIM("- "), iim,jjm, hist_hori_id, &
3022         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3023
3024    CALL histdef (hist_id_stom, &
3025         &               TRIM("NANIMALTOT "), &
3026         &               TRIM("- "), &
3027         &               TRIM("- "), iim,jjm, hist_hori_id, &
3028         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3029
3030    CALL histdef (hist_id_stom, &
3031         &               TRIM("INTAKE_ANIMAL "), &
3032         &               TRIM("- "), &
3033         &               TRIM("- "), iim,jjm, hist_hori_id, &
3034         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3035
3036    CALL histdef (hist_id_stom, &
3037         &               TRIM("INTAKE "), &
3038         &               TRIM("grazing animal intake "), &
3039         &               TRIM("kgDM/m^2/day "), iim,jjm, hist_hori_id, &
3040         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
3041
3042    CALL histdef (hist_id_stom, &
3043         &               TRIM("INTAKESUM "), &
3044         &               TRIM("- "), &
3045         &               TRIM("- "), iim,jjm, hist_hori_id, &
3046         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3047
3048    CALL histdef (hist_id_stom, &
3049         &               TRIM("TRAMPLING "), &
3050         &               TRIM("litter from trample by animals "), &
3051         &               TRIM("kgC/m^2/day "), iim,jjm, hist_hori_id, &
3052         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
3053
3054    CALL histdef (hist_id_stom, &
3055         &               TRIM("MILK "), &
3056         &               TRIM("- "), &
3057         &               TRIM("- "), iim,jjm, hist_hori_id, &
3058         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3059
3060    CALL histdef (hist_id_stom, &
3061         &               TRIM("MILKSUM "), &
3062         &               TRIM("- "), &
3063         &               TRIM("- "), iim,jjm, hist_hori_id, &
3064         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3065
3066    CALL histdef (hist_id_stom, &
3067         &               TRIM("MILKCSUM "), &
3068         &               TRIM("- "), &
3069         &               TRIM("- "), iim,jjm, hist_hori_id, &
3070         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3071
3072    CALL histdef (hist_id_stom, &
3073         &               TRIM("MILKC "), &
3074         &               TRIM("C export by milk production during animal grazing "), &
3075         &               TRIM("kgC/m^2/day "), iim,jjm, hist_hori_id, &
3076         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
3077!GM11
3078    CALL histdef (hist_id_stom, &
3079         &               TRIM("MILKN "), &
3080         &               TRIM("- "), &
3081         &               TRIM("- "), iim,jjm, hist_hori_id, &
3082         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3083
3084    CALL histdef (hist_id_stom, &
3085         &               TRIM("MILKANIMAL "), &
3086         &               TRIM("- "), &
3087         &               TRIM("- "), iim,jjm, hist_hori_id, &
3088         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3089
3090    CALL histdef (hist_id_stom, &
3091         &               TRIM("METHANE "), &
3092         &               TRIM("Methane emission by grazing animal "), &
3093         &               TRIM("kgC/m^2/day "), iim,jjm, hist_hori_id, &
3094         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
3095
3096    CALL histdef (hist_id_stom, &
3097         &               TRIM("METHANE_ANI "), &
3098         &               TRIM("- "), &
3099         &               TRIM("- "), iim,jjm, hist_hori_id, &
3100         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3101
3102    CALL histdef (hist_id_stom, &
3103         &               TRIM("RANIMALSUM "), &
3104         &               TRIM("- "), &
3105         &               TRIM("- "), iim,jjm, hist_hori_id, &
3106         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3107
3108    CALL histdef (hist_id_stom, &
3109         &               TRIM("METHANESUM "), &
3110         &               TRIM("- "), &
3111         &               TRIM("- "), iim,jjm, hist_hori_id, &
3112         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3113
3114    CALL histdef (hist_id_stom, &
3115         &               TRIM("RANIMAL "), &
3116         &               TRIM("C loss through grazing animal respiration "), &
3117         &               TRIM("kgC/m^2/day "), iim,jjm, hist_hori_id, &
3118         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
3119
3120    CALL histdef (hist_id_stom, &
3121         &               TRIM("FAECESNSUM "), &
3122         &               TRIM("- "), &
3123         &               TRIM("- "), iim,jjm, hist_hori_id, &
3124         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3125
3126    CALL histdef (hist_id_stom, &
3127         &               TRIM("FAECESCSUM "), &
3128         &               TRIM("- "), &
3129         &               TRIM("- "), iim,jjm, hist_hori_id, &
3130         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3131
3132    CALL histdef (hist_id_stom, &
3133         &               TRIM("URINECSUM "), &
3134         &               TRIM("- "), &
3135         &               TRIM("- "), iim,jjm, hist_hori_id, &
3136         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3137!GM21
3138    CALL histdef (hist_id_stom, &
3139         &               TRIM("URINENSUM "), &
3140         &               TRIM("- "), &
3141         &               TRIM("- "), iim,jjm, hist_hori_id, &
3142         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3143
3144    CALL histdef (hist_id_stom, &
3145         &               TRIM("NEL "), &
3146         &               TRIM("- "), &
3147         &               TRIM("- "), iim,jjm, hist_hori_id, &
3148         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3149
3150    CALL histdef (hist_id_stom, &
3151         &               TRIM("URINEN "), &
3152         &               TRIM("- "), &
3153         &               TRIM("- "), iim,jjm, hist_hori_id, &
3154         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3155
3156    CALL histdef (hist_id_stom, &
3157         &               TRIM("URINEC "), &
3158         &               TRIM("C in urine "), &
3159         &               TRIM("kgC/m^2/day "), iim,jjm, hist_hori_id, &
3160         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
3161
3162    CALL histdef (hist_id_stom, &
3163         &               TRIM("FAECESC "), &
3164         &               TRIM("C in faeces "), &
3165         &               TRIM("kgC/m^2/day "), iim,jjm, hist_hori_id, &
3166         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
3167
3168    CALL histdef (hist_id_stom, &
3169         &               TRIM("FAECESN "), &
3170         &               TRIM("- "), &
3171         &               TRIM("- "), iim,jjm, hist_hori_id, &
3172         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3173
3174    CALL histdef (hist_id_stom, &
3175         &               TRIM("GRAZED_FRAC "), &
3176         &               TRIM("- "), &
3177         &               TRIM("- "), iim,jjm, hist_hori_id, &
3178         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3179
3180    CALL histdef (hist_id_stom, &
3181         &               TRIM("NB_ANI "), &
3182         &               TRIM("- "), &
3183         &               TRIM("- "), iim,jjm, hist_hori_id, &
3184         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3185
3186    CALL histdef (hist_id_stom, &
3187         &               TRIM("IMPORT_YIELD "), &
3188         &               TRIM("potential harvest yield of last year "), &
3189         &               TRIM("kgDM/m^2/yr "), iim,jjm, hist_hori_id, &
3190         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
3191
3192    CALL histdef (hist_id_stom, &
3193         &               TRIM("EXTRA_FEED "), &
3194         &               TRIM("- "), &
3195         &               TRIM("- "), iim,jjm, hist_hori_id, &
3196         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3197!GM31
3198    CALL histdef (hist_id_stom, &
3199         &               TRIM("COMPT_UGB "), &
3200         &               TRIM("- "), &
3201         &               TRIM("- "), iim,jjm, hist_hori_id, &
3202         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3203
3204    CALL histdef (hist_id_stom, &
3205         &               TRIM("NB_GRAZINGDAYS "), &
3206         &               TRIM("number of grazing days of last year "), &
3207         &               TRIM("days "), iim,jjm, hist_hori_id, &
3208         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
3209
3210    CALL histdef (hist_id_stom, &
3211         &               TRIM("AMOUNT_YIELD "), &
3212         &               TRIM("- "), &
3213         &               TRIM("- "), iim,jjm, hist_hori_id, &
3214         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3215
3216    CALL histdef (hist_id_stom, &
3217         &               TRIM("CONSUMP "), &
3218         &               TRIM("- "), &
3219         &               TRIM("- "), iim,jjm, hist_hori_id, &
3220         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3221
3222    CALL histdef (hist_id_stom, &
3223         &               TRIM("OUTSIDE_FOOD "), &
3224         &               TRIM("- "), &
3225         &               TRIM("- "), iim,jjm, hist_hori_id, &
3226         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3227
3228    CALL histdef (hist_id_stom, &
3229         &               TRIM("ADD_NB_ANI "), &
3230         &               TRIM("- "), &
3231         &               TRIM("- "), iim,jjm, hist_hori_id, &
3232         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3233
3234    CALL histdef (hist_id_stom, &
3235         &               TRIM("BCSyoung "), &
3236         &               TRIM("- "), &
3237         &               TRIM("- "), iim,jjm, hist_hori_id, &
3238         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3239
3240    CALL histdef (hist_id_stom, &
3241         &               TRIM("BCSmature "), &
3242         &               TRIM("- "), &
3243         &               TRIM("- "), iim,jjm, hist_hori_id, &
3244         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3245
3246    CALL histdef (hist_id_stom, &
3247         &               TRIM("Weightyoung "), &
3248         &               TRIM("- "), &
3249         &               TRIM("- "), iim,jjm, hist_hori_id, &
3250         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3251
3252    CALL histdef (hist_id_stom, &
3253         &               TRIM("Weightmature "), &
3254         &               TRIM("- "), &
3255         &               TRIM("- "), iim,jjm, hist_hori_id, &
3256         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3257!GM41
3258    CALL histdef (hist_id_stom, &
3259         &               TRIM("Weightcalf "), &
3260         &               TRIM("- "), &
3261         &               TRIM("- "), iim,jjm, hist_hori_id, &
3262         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3263
3264    CALL histdef (hist_id_stom, &
3265         &               TRIM("MPyoung "), &
3266         &               TRIM("- "), &
3267         &               TRIM("- "), iim,jjm, hist_hori_id, &
3268         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3269
3270    CALL histdef (hist_id_stom, &
3271         &               TRIM("MPmature "), &
3272         &               TRIM("- "), &
3273         &               TRIM("- "), iim,jjm, hist_hori_id, &
3274         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3275
3276    CALL histdef (hist_id_stom, &
3277         &               TRIM("MPwyoung "), &
3278         &               TRIM("- "), &
3279         &               TRIM("- "), iim,jjm, hist_hori_id, &
3280         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3281
3282    CALL histdef (hist_id_stom, &
3283         &               TRIM("MPwmature "), &
3284         &               TRIM("- "), &
3285         &               TRIM("- "), iim,jjm, hist_hori_id, &
3286         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3287
3288    CALL histdef (hist_id_stom, &
3289         &               TRIM("MPposyoung "), &
3290         &               TRIM("- "), &
3291         &               TRIM("- "), iim,jjm, hist_hori_id, &
3292         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3293
3294    CALL histdef (hist_id_stom, &
3295         &               TRIM("MPposmature "), &
3296         &               TRIM("- "), &
3297         &               TRIM("- "), iim,jjm, hist_hori_id, &
3298         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3299
3300    CALL histdef (hist_id_stom, &
3301         &               TRIM("NEByoung "), &
3302         &               TRIM("- "), &
3303         &               TRIM("- "), iim,jjm, hist_hori_id, &
3304         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3305
3306    CALL histdef (hist_id_stom, &
3307         &               TRIM("NEBmature "), &
3308         &               TRIM("- "), &
3309         &               TRIM("- "), iim,jjm, hist_hori_id, &
3310         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3311
3312    CALL histdef (hist_id_stom, &
3313         &               TRIM("NEIyoung "), &
3314         &               TRIM("- "), &
3315         &               TRIM("- "), iim,jjm, hist_hori_id, &
3316         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3317!GM51
3318    CALL histdef (hist_id_stom, &
3319         &               TRIM("NEImature "), &
3320         &               TRIM("- "), &
3321         &               TRIM("- "), iim,jjm, hist_hori_id, &
3322         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3323
3324    CALL histdef (hist_id_stom, &
3325         &               TRIM("DMIcyoung "), &
3326         &               TRIM("- "), &
3327         &               TRIM("- "), iim,jjm, hist_hori_id, &
3328         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3329
3330    CALL histdef (hist_id_stom, &
3331         &               TRIM("DMIcmature "), &
3332         &               TRIM("- "), &
3333         &               TRIM("- "), iim,jjm, hist_hori_id, &
3334         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3335
3336    CALL histdef (hist_id_stom, &
3337         &               TRIM("DMIfyoung "), &
3338         &               TRIM("- "), &
3339         &               TRIM("- "), iim,jjm, hist_hori_id, &
3340         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3341
3342    CALL histdef (hist_id_stom, &
3343         &               TRIM("DMIfmature "), &
3344         &               TRIM("- "), &
3345         &               TRIM("- "), iim,jjm, hist_hori_id, &
3346         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3347
3348    CALL histdef (hist_id_stom, &
3349         &               TRIM("DMIyoung "), &
3350         &               TRIM("- "), &
3351         &               TRIM("- "), iim,jjm, hist_hori_id, &
3352         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3353
3354    CALL histdef (hist_id_stom, &
3355         &               TRIM("DMImature "), &
3356         &               TRIM("- "), &
3357         &               TRIM("- "), iim,jjm, hist_hori_id, &
3358         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3359
3360    CALL histdef (hist_id_stom, &
3361         &               TRIM("DMIcalf "), &
3362         &               TRIM("- "), &
3363         &               TRIM("- "), iim,jjm, hist_hori_id, &
3364         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3365
3366    CALL histdef (hist_id_stom, &
3367         &               TRIM("OMD "), &
3368         &               TRIM("- "), &
3369         &               TRIM("- "), iim,jjm, hist_hori_id, &
3370         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3371
3372    CALL histdef (hist_id_stom, &
3373         &               TRIM("Weightcows "), &
3374         &               TRIM("- "), &
3375         &               TRIM("- "), iim,jjm, hist_hori_id, &
3376         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3377!GM61
3378    CALL histdef (hist_id_stom, &
3379         &               TRIM("BCScows "), &
3380         &               TRIM("- "), &
3381         &               TRIM("- "), iim,jjm, hist_hori_id, &
3382         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3383
3384    CALL histdef (hist_id_stom, &
3385         &               TRIM("CH4young "), &
3386         &               TRIM("- "), &
3387         &               TRIM("- "), iim,jjm, hist_hori_id, &
3388         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3389
3390    CALL histdef (hist_id_stom, &
3391         &               TRIM("CH4mature "), &
3392         &               TRIM("- "), &
3393         &               TRIM("- "), iim,jjm, hist_hori_id, &
3394         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3395
3396    CALL histdef (hist_id_stom, &
3397         &               TRIM("TSOILCUMM "), &
3398         &               TRIM("- "), &
3399         &               TRIM("- "), iim,jjm, hist_hori_id, &
3400         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3401
3402    CALL histdef (hist_id_stom, &
3403         &               TRIM("YIELD_RETURN "), &
3404         &               TRIM("- "), &
3405         &               TRIM("- "), iim,jjm, hist_hori_id, &
3406         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3407
3408    CALL histdef (hist_id_stom, &
3409         &               TRIM("REGCOUNT "), &
3410         &               TRIM("- "), &
3411         &               TRIM("- "), iim,jjm, hist_hori_id, &
3412         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3413
3414    CALL histdef (hist_id_stom, &
3415         &               TRIM("FERTCOUNT "), &
3416         &               TRIM("- "), &
3417         &               TRIM("- "), iim,jjm, hist_hori_id, &
3418         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3419
3420    CALL histdef (hist_id_stom, &
3421         &               TRIM("GMEAN1 "), &
3422         &               TRIM("- "), &
3423         &               TRIM("- "), iim,jjm, hist_hori_id, &
3424         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3425
3426    CALL histdef (hist_id_stom, &
3427         &               TRIM("GMEAN2 "), &
3428         &               TRIM("- "), &
3429         &               TRIM("- "), iim,jjm, hist_hori_id, &
3430         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3431
3432    CALL histdef (hist_id_stom, &
3433         &               TRIM("GMEAN3 "), &
3434         &               TRIM("- "), &
3435         &               TRIM("- "), iim,jjm, hist_hori_id, &
3436         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3437!GM71
3438    CALL histdef (hist_id_stom, &
3439         &               TRIM("GMEAN4 "), &
3440         &               TRIM("- "), &
3441         &               TRIM("- "), iim,jjm, hist_hori_id, &
3442         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3443
3444    CALL histdef (hist_id_stom, &
3445         &               TRIM("GMEAN5 "), &
3446         &               TRIM("- "), &
3447         &               TRIM("- "), iim,jjm, hist_hori_id, &
3448         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3449
3450    CALL histdef (hist_id_stom, &
3451         &               TRIM("GMEAN6 "), &
3452         &               TRIM("- "), &
3453         &               TRIM("- "), iim,jjm, hist_hori_id, &
3454         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3455
3456    CALL histdef (hist_id_stom, &
3457         &               TRIM("GMEAN7 "), &
3458         &               TRIM("- "), &
3459         &               TRIM("- "), iim,jjm, hist_hori_id, &
3460         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3461
3462    CALL histdef (hist_id_stom, &
3463         &               TRIM("GMEAN8 "), &
3464         &               TRIM("- "), &
3465         &               TRIM("- "), iim,jjm, hist_hori_id, &
3466         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3467
3468    CALL histdef (hist_id_stom, &
3469         &               TRIM("GMEAN9 "), &
3470         &               TRIM("- "), &
3471         &               TRIM("- "), iim,jjm, hist_hori_id, &
3472         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3473
3474    CALL histdef (hist_id_stom, &
3475         &               TRIM("GMEAN0 "), &
3476         &               TRIM("- "), &
3477         &               TRIM("- "), iim,jjm, hist_hori_id, &
3478         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3479
3480    CALL histdef (hist_id_stom, &
3481         &               TRIM("WSH "), &
3482         &               TRIM("shoot structure mass "), &
3483         &               TRIM("kgDM/m^2 "), iim,jjm, hist_hori_id, &
3484         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
3485
3486    CALL histdef (hist_id_stom, &
3487         &               TRIM("WSHTOT "), &
3488         &               TRIM("total shoot structure mass "), &
3489         &               TRIM("kgDM/m^2 "), iim,jjm, hist_hori_id, &
3490         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
3491
3492    CALL histdef (hist_id_stom, &
3493         &               TRIM("WR "), &
3494         &               TRIM("root structure mass "), &
3495         &               TRIM("kgDM/m^2 "), iim,jjm, hist_hori_id, &
3496         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
3497!GM81
3498    CALL histdef (hist_id_stom, &
3499         &               TRIM("WRTOT "), &
3500         &               TRIM("total root structure mass "), &
3501         &               TRIM("kgDM/m^2 "), iim,jjm, hist_hori_id, &
3502         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
3503
3504    CALL histdef (hist_id_stom, &
3505         &               TRIM("WSHTOTSUM "), &
3506         &               TRIM("- "), &
3507         &               TRIM("- "), iim,jjm, hist_hori_id, &
3508         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3509
3510    CALL histdef (hist_id_stom, &
3511         &               TRIM("SR_UGB "), &
3512         &               TRIM("instantaneous stocking rate "), &
3513         &               TRIM("HeadorLSU/m^2 "), iim,jjm, hist_hori_id, &
3514         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
3515
3516    CALL histdef (hist_id_stom, &
3517         &               TRIM("FCORGFERTMET "), &
3518         &               TRIM("- "), &
3519         &               TRIM("- "), iim,jjm, hist_hori_id, &
3520         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3521
3522    CALL histdef (hist_id_stom, &
3523         &               TRIM("FCORGFERTSTR "), &
3524         &               TRIM("- "), &
3525         &               TRIM("- "), iim,jjm, hist_hori_id, &
3526         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3527
3528    CALL histdef (hist_id_stom, &
3529         &               TRIM("FNORGANICFERTURINE "), &
3530         &               TRIM("- "), &
3531         &               TRIM("- "), iim,jjm, hist_hori_id, &
3532         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3533
3534    CALL histdef (hist_id_stom, &
3535         &               TRIM("FNORGANICFERTSTRUCT "), &
3536         &               TRIM("- "), &
3537         &               TRIM("- "), iim,jjm, hist_hori_id, &
3538         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3539
3540    CALL histdef (hist_id_stom, &
3541         &               TRIM("FNORGANICFERTMETABOLIC "), &
3542         &               TRIM("- "), &
3543         &               TRIM("- "), iim,jjm, hist_hori_id, &
3544         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3545
3546    CALL histdef (hist_id_stom, &
3547         &               TRIM("NFERTNITTOT "), &
3548         &               TRIM("- "), &
3549         &               TRIM("- "), iim,jjm, hist_hori_id, &
3550         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3551
3552    CALL histdef (hist_id_stom, &
3553         &               TRIM("NFERTAMMTOT "), &
3554         &               TRIM("- "), &
3555         &               TRIM("- "), iim,jjm, hist_hori_id, &
3556         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3557!GM91
3558    CALL histdef (hist_id_stom, &
3559         &               TRIM("LOSS "), &
3560         &               TRIM("- "), &
3561         &               TRIM("- "), iim,jjm, hist_hori_id, &
3562         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3563
3564    CALL histdef (hist_id_stom, &
3565         &               TRIM("LOSSC "), &
3566         &               TRIM("Carbon loss as litter during cutting "), &
3567         &               TRIM("kg C/m**2 "), iim,jjm, hist_hori_id, &
3568         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
3569
3570    CALL histdef (hist_id_stom, &
3571         &               TRIM("LOSSN "), &
3572         &               TRIM("- "), &
3573         &               TRIM("- "), iim,jjm, hist_hori_id, &
3574         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3575
3576    CALL histdef (hist_id_stom, &
3577         &               TRIM("DM_CUTYEARLY "), &
3578         &               TRIM("- "), &
3579         &               TRIM("- "), iim,jjm, hist_hori_id, &
3580         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3581
3582    CALL histdef (hist_id_stom, &
3583         &               TRIM("C_CUTYEARLY "), &
3584         &               TRIM("- "), &
3585         &               TRIM("- "), iim,jjm, hist_hori_id, &
3586         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3587
3588    CALL histdef (hist_id_stom, &
3589         &               TRIM("NFERT_TOTAL "), &
3590         &               TRIM("Total Nitrogen input "), &
3591         &               TRIM("kg N/ha "), iim,jjm, hist_hori_id, &
3592         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
3593
3594    CALL histdef (hist_id_stom, &
3595         &               TRIM("NDEP "), &
3596         &               TRIM("Nitrogen deposition from input "), &
3597         &               TRIM("kg N/ha "), iim,jjm, hist_hori_id, &
3598         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
3599
3600    CALL histdef (hist_id_stom, &
3601         &               TRIM("LEGUME_FRACTION "), &
3602         &               TRIM("- "), &
3603         &               TRIM("- "), iim,jjm, hist_hori_id, &
3604         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3605
3606    CALL histdef (hist_id_stom, &
3607         &               TRIM("SOIL_FERTILITY "), &
3608         &               TRIM("- "), &
3609         &               TRIM("- "), iim,jjm, hist_hori_id, &
3610         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3611
3612    CALL histdef (hist_id_stom, &
3613         &               TRIM("C "), &
3614         &               TRIM("- "), &
3615         &               TRIM("- "), iim,jjm, hist_hori_id, &
3616         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3617!GM101
3618    CALL histdef (hist_id_stom, &
3619         &               TRIM("N "), &
3620         &               TRIM("- "), &
3621         &               TRIM("- "), iim,jjm, hist_hori_id, &
3622         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3623
3624    CALL histdef (hist_id_stom, &
3625         &               TRIM("FN "), &
3626         &               TRIM("- "), &
3627         &               TRIM("- "), iim,jjm, hist_hori_id, &
3628         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3629
3630    CALL histdef (hist_id_stom, &
3631         &               TRIM("NTOT "), &
3632         &               TRIM("- "), &
3633         &               TRIM("- "), iim,jjm, hist_hori_id, &
3634         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3635
3636    CALL histdef (hist_id_stom, &
3637         &               TRIM("NAPO "), &
3638         &               TRIM("- "), &
3639         &               TRIM("- "), iim,jjm, hist_hori_id, &
3640         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3641
3642    CALL histdef (hist_id_stom, &
3643         &               TRIM("NSYM "), &
3644         &               TRIM("- "), &
3645         &               TRIM("- "), iim,jjm, hist_hori_id, &
3646         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3647
3648    CALL histdef (hist_id_stom, &
3649         &               TRIM("DEVSTAGE "), &
3650         &               TRIM("- "), &
3651         &               TRIM("- "), iim,jjm, hist_hori_id, &
3652         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3653
3654    CALL histdef (hist_id_stom, &
3655         &               TRIM("TGROWTH "), &
3656         &               TRIM("- "), &
3657         &               TRIM("- "), iim,jjm, hist_hori_id, &
3658         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3659
3660    CALL histdef (hist_id_stom, &
3661         &               TRIM("GRAZINGCSTRUCT "), &
3662         &               TRIM("- "), &
3663         &               TRIM("- "), iim,jjm, hist_hori_id, &
3664         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3665
3666    CALL histdef (hist_id_stom, &
3667         &               TRIM("GRAZINGNSTRUCT "), &
3668         &               TRIM("- "), &
3669         &               TRIM("- "), iim,jjm, hist_hori_id, &
3670         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3671
3672    CALL histdef (hist_id_stom, &
3673         &               TRIM("GRAZINGWN "), &
3674         &               TRIM("- "), &
3675         &               TRIM("- "), iim,jjm, hist_hori_id, &
3676         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3677!GM111
3678    CALL histdef (hist_id_stom, &
3679         &               TRIM("GRAZINGWC "), &
3680         &               TRIM("- "), &
3681         &               TRIM("- "), iim,jjm, hist_hori_id, &
3682         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3683
3684       ! 14days 2 m temperature
3685       CALL histdef (hist_id_stom, &
3686            &               TRIM("T2M_14            "), &
3687            &               TRIM("14days 2 m temperature"), &
3688            &               TRIM("K                   "), iim,jjm, hist_hori_id, &
3689            &               1,1,1, -99,32, ave(5), dt, hist_dt)
3690
3691    CALL histdef (hist_id_stom, &
3692         &               TRIM("LITTER_RESP "), &
3693         &               TRIM("heterotr. resp. from litter pool "), &
3694         &               TRIM("gC/m^2/day "), iim,jjm, hist_hori_id, &
3695         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
3696
3697    CALL histdef (hist_id_stom, &
3698         &               TRIM("ACTIVE_RESP "), &
3699         &               TRIM("heterotr. resp. from active carbon pool "), &
3700         &               TRIM("gC/m^2/day "), iim,jjm, hist_hori_id, &
3701         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
3702
3703    CALL histdef (hist_id_stom, &
3704         &               TRIM("SLOW_RESP "), &
3705         &               TRIM("heterotr. resp. from slow carbon pool "), &
3706         &               TRIM("gC/m^2/day "), iim,jjm, hist_hori_id, &
3707         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
3708
3709    CALL histdef (hist_id_stom, &
3710         &               TRIM("PASSIVE_RESP "), &
3711         &               TRIM("heterotr. resp. from passive carbon pool "), &
3712         &               TRIM("gC/m^2/day "), iim,jjm, hist_hori_id, &
3713         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
3714
3715    CALL histdef (hist_id_stom, &
3716         &               TRIM("N_LIMFERT "), &
3717         &               TRIM("Nitrogen limitation factor on vcmax "), &
3718         &               TRIM("- "), iim,jjm, hist_hori_id, &
3719         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
3720
3721    CALL histdef (hist_id_stom, &
3722         &               TRIM("SLA_CALC "), &
3723         &               TRIM("sla calculated by leaf age "), &
3724         &               TRIM("m**2/gC "), iim,jjm, hist_hori_id, &
3725         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
3726
3727    CALL histdef (hist_id_stom, &
3728         &               TRIM("NPP_ABOVE "), &
3729         &               TRIM("Net above primary productivity "), &
3730         &               TRIM("gC/day/(m^2 (n/a)) "), iim,jjm, hist_hori_id, &
3731         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
3732
3733    CALL histdef (hist_id_stom, &
3734         &               TRIM("NPP_BELOW "), &
3735         &               TRIM("Net below primary productivity "), &
3736         &               TRIM("gC/day/(m^2 (n/a)) "), iim,jjm, hist_hori_id, &
3737         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
3738!GMtotal120
3739    CALL histdef (hist_id_stom, &
3740         &               TRIM("LITTER_STR_AVAIL "), &
3741         &               TRIM("Structural litter available for grazing "), &
3742         &               TRIM("gC/day/(m^2 (n/a)) "), iim,jjm, hist_hori_id, &
3743         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
3744    CALL histdef (hist_id_stom, &
3745         &               TRIM("LITTER_MET_AVAIL "), &
3746         &               TRIM("Metabolic litter available for grazing "), &
3747         &               TRIM("gC/day/(m^2 (n/a)) "), iim,jjm, hist_hori_id, &
3748         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
3749    CALL histdef (hist_id_stom, &
3750         &               TRIM("LITTER_STR_NAVAIL "), &
3751         &               TRIM("Structural litter not available for grazing "), &
3752         &               TRIM("gC/day/(m^2 (n/a)) "), iim,jjm, hist_hori_id, &
3753         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
3754    CALL histdef (hist_id_stom, &
3755         &               TRIM("LITTER_MET_NAVAIL "), &
3756         &               TRIM("Metabolic litter not available for grazing "), &
3757         &               TRIM("gC/day/(m^2 (n/a)) "), iim,jjm, hist_hori_id, &
3758         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
3759    CALL histdef (hist_id_stom, &
3760         &               TRIM("LITTER_STR_AVAILF "), &
3761         &               TRIM("Structural litter available fraction for grazing "), &
3762         &               TRIM("% "), iim,jjm, hist_hori_id, &
3763         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
3764    CALL histdef (hist_id_stom, &
3765         &               TRIM("LITTER_MET_AVAILF "), &
3766         &               TRIM("Metabolic litter available fraction for grazing "), &
3767         &               TRIM("% "), iim,jjm, hist_hori_id, &
3768         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
3769    CALL histdef (hist_id_stom, &
3770         &               TRIM("INTAKE_ANIMAL_LITTER "), &
3771         &               TRIM("Litter intake per animal "), &
3772         &               TRIM("kg DM/animal/day "), iim,jjm, hist_hori_id, &
3773         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
3774    CALL histdef (hist_id_stom, &
3775         &               TRIM("INTAKE_LITTER "), &
3776         &               TRIM("Litter intake per m**2 "), &
3777         &               TRIM("kg DM/m**2/day "), iim,jjm, hist_hori_id, &
3778         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
3779    CALL histdef (hist_id_stom, &
3780         &               TRIM("GRAZING_LITTER "), &
3781         &               TRIM("Flag of grazing litter 0 AGB 1 Litter 2 none "), &
3782         &               TRIM("- "), iim,jjm, hist_hori_id, &
3783         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
3784!GM131
3785    CALL histdef (hist_id_stom, &
3786         &               TRIM("COMPT_CUT "), &
3787         &               TRIM("Grass harvest time "), &
3788         &               TRIM("times "), iim,jjm, hist_hori_id, &
3789         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3790    CALL histdef (hist_id_stom, &
3791         &               TRIM("FREQUENCY_CUT "), &
3792         &               TRIM("Grass harvest frequency "), &
3793         &               TRIM("times "), iim,jjm, hist_hori_id, &
3794         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3795    CALL histdef (hist_id_stom, &
3796         &               TRIM("SR_WILD "), &
3797         &               TRIM("Wild animal stocking rate "), &
3798         &               TRIM("HeadorLSU/m^2 "), iim,jjm, hist_hori_id, &
3799         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3800    CALL histdef (hist_id_stom, &
3801         &               TRIM("TMCGRASS_DAILY "), &
3802         &               TRIM("daily mean 10 cm soil moisture "), &
3803         &               TRIM("m^3/m^3 "), iim,jjm, hist_hori_id, &
3804         &               1,1,1, -99,32, ave(5), dt, hist_dt)
3805    CALL histdef (hist_id_stom, &
3806         &               TRIM("FC_GRAZING "), &
3807         &               TRIM("field capacity in 10 cm soil moisture "), &
3808         &               TRIM("m^3/m^3 "), iim,jjm, hist_hori_id, &
3809         &               1,1,1, -99,32, ave(5), dt, hist_dt)
3810    CALL histdef (hist_id_stom, &
3811         &               TRIM("CT_DRY "), &
3812         &               TRIM("days after soil dry enough for grazing "), &
3813         &               TRIM("days "), iim,jjm, hist_hori_id, &
3814         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
3815    CALL histdef (hist_id_stom, &
3816         &               TRIM("N2O_PFT_GM "), &
3817         &               TRIM("N2O-N emission from grassland "), &
3818         &               TRIM("gN/m^2/day "), iim,jjm, hist_hori_id, &
3819         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
3820    CALL histdef (hist_id_stom, &
3821         &               TRIM("CO2_GM "), &
3822         &               TRIM("CO2 fluxes of grassland"), &
3823         &               TRIM("gC/m^2/day "), iim,jjm, hist_hori_id, &
3824         &               1,1,1, -99,32, ave(5), dt, hist_dt)
3825    CALL histdef (hist_id_stom, &
3826         &               TRIM("CH4_GM "), &
3827         &               TRIM("CH4-C fluxes of grassland"), &
3828         &               TRIM("gC/m^2/day "), iim,jjm, hist_hori_id, &
3829         &               1,1,1, -99,32, ave(5), dt, hist_dt)
3830    CALL histdef (hist_id_stom, &
3831         &               TRIM("CO2_GM "), &
3832         &               TRIM("N2O-N fluxes of grassland"), &
3833         &               TRIM("gN/m^2/day "), iim,jjm, hist_hori_id, &
3834         &               1,1,1, -99,32, ave(5), dt, hist_dt)
3835!end gmjc
3836    ENDIF
3837    !---------------------------------
3838  END SUBROUTINE ioipslctrl_histstom
3839
3840!! ================================================================================================================================
3841!! SUBROUTINE    : ioipslctrl_histstomipcc
3842!!
3843!>\BRIEF         This subroutine initialize the IOIPSL stomate second output file (ipcc file)
3844!!
3845!! DESCRIPTION   : This subroutine initialize the IOIPSL stomate second output file named stomate_ipcc_history.nc(default name).
3846!!                 This subroutine was previously called stom_IPCC_define_history and located in module intersurf.
3847!!
3848!! RECENT CHANGE(S): None
3849!!
3850!! \n
3851!_ ================================================================================================================================
3852  SUBROUTINE ioipslctrl_histstomipcc( &
3853       hist_id_stom_IPCC, nvm, iim, jjm, dt, &
3854       hist_dt, hist_hori_id, hist_PFTaxis_id)
3855    ! deforestation axis added as arguments
3856
3857    !---------------------------------------------------------------------
3858    !- Tell ioipsl which variables are to be written
3859    !- and on which grid they are defined
3860    !---------------------------------------------------------------------
3861    IMPLICIT NONE
3862    !-
3863    !- Input
3864    !-
3865    !- File id
3866    INTEGER(i_std),INTENT(in) :: hist_id_stom_IPCC
3867    !- number of PFTs
3868    INTEGER(i_std),INTENT(in) :: nvm
3869    !- Domain size
3870    INTEGER(i_std),INTENT(in) :: iim, jjm
3871    !- Time step of STOMATE (seconds)
3872    REAL(r_std),INTENT(in)    :: dt
3873    !- Time step of history file (s)
3874    REAL(r_std),INTENT(in)    :: hist_dt
3875    !- id horizontal grid
3876    INTEGER(i_std),INTENT(in) :: hist_hori_id
3877    !- id of PFT axis
3878    INTEGER(i_std),INTENT(in) :: hist_PFTaxis_id
3879    !-
3880    !- 1 local
3881    !-
3882    !- Character strings to define operations for histdef
3883    CHARACTER(LEN=40),DIMENSION(max_hist_level) :: ave
3884
3885    !=====================================================================
3886    !- 1 define operations
3887    !=====================================================================
3888    ave(1) =  'ave(scatter(X))'
3889    !=====================================================================
3890    !- 2 surface fields (2d)
3891    !=====================================================================
3892    ! Carbon in Vegetation
3893    CALL histdef (hist_id_stom_IPCC, &
3894         &               TRIM("cVeg"), &
3895         &               TRIM("Carbon in Vegetation"), &
3896         &               TRIM("kg C m-2"), iim,jjm, hist_hori_id, &
3897         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3898    ! Carbon in Litter Pool
3899    CALL histdef (hist_id_stom_IPCC, &
3900         &               TRIM("cLitter"), &
3901         &               TRIM("Carbon in Litter Pool"), &
3902         &               TRIM("kg C m-2"), iim,jjm, hist_hori_id, &
3903         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3904    ! Carbon in Soil Pool
3905    CALL histdef (hist_id_stom_IPCC, &
3906         &               TRIM("cSoil"), &
3907         &               TRIM("Carbon in Soil Pool"), &
3908         &               TRIM("kg C m-2"), iim,jjm, hist_hori_id, &
3909         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3910    ! Carbon in Products of Land Use Change
3911    CALL histdef (hist_id_stom_IPCC, &
3912         &               TRIM("cProduct"), &
3913         &               TRIM("Carbon in Products of Land Use Change"), &
3914         &               TRIM("kg C m-2"), iim,jjm, hist_hori_id, &
3915         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3916    ! Carbon Mass Variation
3917    CALL histdef (hist_id_stom_IPCC, &
3918         &               TRIM("cMassVariation"), &
3919         &               TRIM("Terrestrial Carbon Mass Variation"), &
3920         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
3921         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3922    ! Leaf Area Fraction
3923    CALL histdef (hist_id_stom_IPCC, &
3924         &               TRIM("lai"), &
3925         &               TRIM("Leaf Area Fraction"), &
3926         &               TRIM("1"), iim,jjm, hist_hori_id, &
3927         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3928    ! Gross Primary Production
3929    CALL histdef (hist_id_stom_IPCC, &
3930         &               TRIM("gpp"), &
3931         &               TRIM("Gross Primary Production"), &
3932         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
3933         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3934    ! Autotrophic Respiration
3935    CALL histdef (hist_id_stom_IPCC, &
3936         &               TRIM("ra"), &
3937         &               TRIM("Autotrophic Respiration"), &
3938         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
3939         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3940    ! Net Primary Production
3941    CALL histdef (hist_id_stom_IPCC, &
3942         &               TRIM("npp"), &
3943         &               TRIM("Net Primary Production"), &
3944         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
3945         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3946    ! Heterotrophic Respiration
3947    CALL histdef (hist_id_stom_IPCC, &
3948         &               TRIM("rh"), &
3949         &               TRIM("Heterotrophic Respiration"), &
3950         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
3951         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3952    ! CO2 Emission from Fire
3953    CALL histdef (hist_id_stom_IPCC, &
3954         &               TRIM("fFire"), &
3955         &               TRIM("CO2 Emission from Fire"), &
3956         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
3957         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3958
3959    ! CO2 Flux to Atmosphere from Crop Harvesting
3960    CALL histdef (hist_id_stom_IPCC, &
3961         &               TRIM("fHarvest"), &
3962         &               TRIM("CO2 Flux to Atmosphere from Crop Harvesting"), &
3963         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
3964         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3965    ! CO2 Flux to Atmosphere from Land Use Change
3966    CALL histdef (hist_id_stom_IPCC, &
3967         &               TRIM("fLuc"), &
3968         &               TRIM("CO2 Flux to Atmosphere from Land Use Change"), &
3969         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
3970         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3971    ! Net Biospheric Production
3972    CALL histdef (hist_id_stom_IPCC, &
3973         &               TRIM("nbp"), &
3974         &               TRIM("Net Biospheric Production"), &
3975         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
3976         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3977    ! Total Carbon Flux from Vegetation to Litter
3978    CALL histdef (hist_id_stom_IPCC, &
3979         &               TRIM("fVegLitter"), &
3980         &               TRIM("Total Carbon Flux from Vegetation to Litter"), &
3981         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
3982         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3983    ! Total Carbon Flux from Litter to Soil
3984    CALL histdef (hist_id_stom_IPCC, &
3985         &               TRIM("fLitterSoil"), &
3986         &               TRIM("Total Carbon Flux from Litter to Soil"), &
3987         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
3988         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3989
3990    ! Carbon in Leaves
3991    CALL histdef (hist_id_stom_IPCC, &
3992         &               TRIM("cLeaf"), &
3993         &               TRIM("Carbon in Leaves"), &
3994         &               TRIM("kg C m-2"), iim,jjm, hist_hori_id, &
3995         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3996    ! Carbon in Wood
3997    CALL histdef (hist_id_stom_IPCC, &
3998         &               TRIM("cWood"), &
3999         &               TRIM("Carbon in Wood"), &
4000         &               TRIM("kg C m-2"), iim,jjm, hist_hori_id, &
4001         &               1,1,1, -99,32, ave(1), dt, hist_dt)
4002    ! Carbon in Roots
4003    CALL histdef (hist_id_stom_IPCC, &
4004         &               TRIM("cRoot"), &
4005         &               TRIM("Carbon in Roots"), &
4006         &               TRIM("kg C m-2"), iim,jjm, hist_hori_id, &
4007         &               1,1,1, -99,32, ave(1), dt, hist_dt)
4008    ! Carbon in Other Living Compartments
4009    CALL histdef (hist_id_stom_IPCC, &
4010         &               TRIM("cMisc"), &
4011         &               TRIM("Carbon in Other Living Compartments"), &
4012         &               TRIM("kg C m-2"), iim,jjm, hist_hori_id, &
4013         &               1,1,1, -99,32, ave(1), dt, hist_dt)
4014
4015    ! Carbon in Above-Ground Litter
4016    CALL histdef (hist_id_stom_IPCC, &
4017         &               TRIM("cLitterAbove"), &
4018         &               TRIM("Carbon in Above-Ground Litter"), &
4019         &               TRIM("kg C m-2"), iim,jjm, hist_hori_id, &
4020         &               1,1,1, -99,32, ave(1), dt, hist_dt)
4021    ! Carbon in Below-Ground Litter
4022    CALL histdef (hist_id_stom_IPCC, &
4023         &               TRIM("cLitterBelow"), &
4024         &               TRIM("Carbon in Below-Ground Litter"), &
4025         &               TRIM("kg C m-2"), iim,jjm, hist_hori_id, &
4026         &               1,1,1, -99,32, ave(1), dt, hist_dt)
4027    ! Carbon in Fast Soil Pool
4028    CALL histdef (hist_id_stom_IPCC, &
4029         &               TRIM("cSoilFast"), &
4030         &               TRIM("Carbon in Fast Soil Pool"), &
4031         &               TRIM("kg C m-2"), iim,jjm, hist_hori_id, &
4032         &               1,1,1, -99,32, ave(1), dt, hist_dt)
4033    ! Carbon in Medium Soil Pool
4034    CALL histdef (hist_id_stom_IPCC, &
4035         &               TRIM("cSoilMedium"), &
4036         &               TRIM("Carbon in Medium Soil Pool"), &
4037         &               TRIM("kg C m-2"), iim,jjm, hist_hori_id, &
4038         &               1,1,1, -99,32, ave(1), dt, hist_dt)
4039    ! Carbon in Slow Soil Pool
4040    CALL histdef (hist_id_stom_IPCC, &
4041         &               TRIM("cSoilSlow"), &
4042         &               TRIM("Carbon in Slow Soil Pool"), &
4043         &               TRIM("kg C m-2"), iim,jjm, hist_hori_id, &
4044         &               1,1,1, -99,32, ave(1), dt, hist_dt)
4045
4046    !- 3 PFT: 3rd dimension
4047    ! Fractional Land Cover of PFT
4048    CALL histdef (hist_id_stom_IPCC, &
4049         &               TRIM("landCoverFrac"), &
4050         &               TRIM("Fractional Land Cover of PFT"), &
4051         &               TRIM("%"), iim,jjm, hist_hori_id, &
4052         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(1), dt, hist_dt)
4053
4054
4055    ! Total Primary Deciduous Tree Cover Fraction
4056    CALL histdef (hist_id_stom_IPCC, &
4057         &               TRIM("treeFracPrimDec"), &
4058         &               TRIM("Total Primary Deciduous Tree Cover Fraction"), &
4059         &               TRIM("%"), iim,jjm, hist_hori_id, &
4060         &               1,1,1, -99,32, ave(1), dt, hist_dt)
4061
4062    ! Total Primary Evergreen Tree Cover Fraction
4063    CALL histdef (hist_id_stom_IPCC, &
4064         &               TRIM("treeFracPrimEver"), &
4065         &               TRIM("Total Primary Evergreen Tree Cover Fraction"), &
4066         &               TRIM("%"), iim,jjm, hist_hori_id, &
4067         &               1,1,1, -99,32, ave(1), dt, hist_dt)
4068
4069    ! Total C3 PFT Cover Fraction
4070    CALL histdef (hist_id_stom_IPCC, &
4071         &               TRIM("c3PftFrac"), &
4072         &               TRIM("Total C3 PFT Cover Fraction"), &
4073         &               TRIM("%"), iim,jjm, hist_hori_id, &
4074         &               1,1,1, -99,32, ave(1), dt, hist_dt)
4075    ! Total C4 PFT Cover Fraction
4076    CALL histdef (hist_id_stom_IPCC, &
4077         &               TRIM("c4PftFrac"), &
4078         &               TRIM("Total C4 PFT Cover Fraction"), &
4079         &               TRIM("%"), iim,jjm, hist_hori_id, &
4080         &               1,1,1, -99,32, ave(1), dt, hist_dt)
4081    ! Growth Autotrophic Respiration
4082    CALL histdef (hist_id_stom_IPCC, &
4083         &               TRIM("rGrowth"), &
4084         &               TRIM("Growth Autotrophic Respiration"), &
4085         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
4086         &               1,1,1, -99,32, ave(1), dt, hist_dt)
4087    ! Maintenance Autotrophic Respiration
4088    CALL histdef (hist_id_stom_IPCC, &
4089         &               TRIM("rMaint"), &
4090         &               TRIM("Maintenance Autotrophic Respiration"), &
4091         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
4092         &               1,1,1, -99,32, ave(1), dt, hist_dt)
4093    ! CO2 Flux from Atmosphere due to NPP Allocation to Leaf
4094    CALL histdef (hist_id_stom_IPCC, &
4095         &               TRIM("nppLeaf"), &
4096         &               TRIM("CO2 Flux from Atmosphere due to NPP Allocation to Leaf"), &
4097         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
4098         &               1,1,1, -99,32, ave(1), dt, hist_dt)
4099    ! CO2 Flux from Atmosphere due to NPP Allocation to Wood
4100    CALL histdef (hist_id_stom_IPCC, &
4101         &               TRIM("nppWood"), &
4102         &               TRIM("CO2 Flux from Atmosphere due to NPP Allocation to Wood"), &
4103         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
4104         &               1,1,1, -99,32, ave(1), dt, hist_dt)
4105    ! CO2 Flux from Atmosphere due to NPP Allocation to Root
4106    CALL histdef (hist_id_stom_IPCC, &
4107         &               TRIM("nppRoot"), &
4108         &               TRIM("CO2 Flux from Atmosphere due to NPP Allocation to Root"), &
4109         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
4110         &               1,1,1, -99,32, ave(1), dt, hist_dt)
4111    ! Net Carbon Mass Flux out of Atmophere due to Net Ecosystem Productivity on Land.
4112    CALL histdef (hist_id_stom_IPCC, &
4113         &               TRIM("nep"), &
4114         &               TRIM("Net Carbon Mass Flux out of Atmophere due to Net Ecosystem Productivity."), &
4115         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
4116         &               1,1,1, -99,32, ave(1), dt, hist_dt)
4117
4118    CALL histdef(hist_id_stom_IPCC, 'RESOLUTION_X', 'E-W resolution', 'm', &
4119         & iim,jjm, hist_hori_id, 1,1,1, -99, 32, 'once(scatter(X))', dt, hist_dt)
4120    CALL histdef(hist_id_stom_IPCC, 'RESOLUTION_Y', 'N-S resolution', 'm', &
4121         & iim,jjm, hist_hori_id, 1,1,1, -99, 32, 'once(scatter(X))', dt, hist_dt)
4122    CALL histdef(hist_id_stom_IPCC, 'CONTFRAC', 'Continental fraction', '1', &
4123         & iim,jjm, hist_hori_id, 1,1,1, -99, 32, 'once(scatter(X))', dt, hist_dt)
4124    CALL histdef(hist_id_stom_IPCC, 'Areas', 'Mesh areas', 'm2', &
4125         & iim,jjm, hist_hori_id, 1,1,1, -99, 32, 'once(scatter(X))', dt, hist_dt)
4126
4127  END SUBROUTINE ioipslctrl_histstomipcc
4128
4129!! ================================================================================================================================
4130!! SUBROUTINE    : ioipslctrl_restini
4131!!
4132!>\BRIEF         This subroutine initialize the restart files in ORCHDIEE.
4133!!
4134!! DESCRIPTION   : This subroutine initialize restart files in ORCHIDEE. IOIPSL is used for manipulating the restart files.
4135!!                 This subroutine was previously called intsurf_restart and located in module intersurf.
4136!!
4137!! RECENT CHANGE(S): None
4138!!
4139!! \n
4140!_ ================================================================================================================================
4141  SUBROUTINE ioipslctrl_restini(istp, date0, dt, rest_id, rest_id_stom, itau_offset, date0_shifted)
4142
4143    USE mod_orchidee_para
4144    !
4145    !  This subroutine initialized the restart file for the land-surface scheme
4146    !
4147    IMPLICIT NONE
4148    !
4149    INTEGER(i_std), INTENT(in)                  :: istp      !! Time step of the restart file
4150    REAL(r_std)                                 :: date0     !! The date at which itau = 0
4151    REAL(r_std)                                 :: dt        !! Time step
4152    INTEGER(i_std), INTENT(out)                 :: rest_id, rest_id_stom   !! ID of the restart file
4153    INTEGER(i_std), INTENT(out)                 :: itau_offset
4154    REAL(r_std), INTENT(out)                    :: date0_shifted
4155
4156
4157    !  LOCAL
4158    !
4159    REAL(r_std)                 :: dt_rest, date0_rest
4160    INTEGER(i_std)              :: itau_dep
4161    INTEGER(i_std),PARAMETER    :: llm=1
4162    REAL(r_std), DIMENSION(llm) :: lev
4163    LOGICAL, PARAMETER          :: overwrite_time=.TRUE. !! Always override the date from the restart files for SECHIBA and STOMATE.
4164                                                         !! The date is taken from the gcm or from the driver restart file.
4165    REAL(r_std)                 :: in_julian, rest_julian
4166    INTEGER(i_std)              :: yy, mm, dd
4167    REAL(r_std)                 :: ss
4168    !
4169    !Config Key   = SECHIBA_restart_in
4170    !Config Desc  = Name of restart to READ for initial conditions
4171    !Config If    = OK_SECHIBA
4172    !Config Def   = NONE
4173    !Config Help  = This is the name of the file which will be opened
4174    !Config         to extract the initial values of all prognostic
4175    !Config         values of the model. This has to be a netCDF file.
4176    !Config         Not truly COADS compliant. NONE will mean that
4177    !Config         no restart file is to be expected.
4178    !Config Units = [FILE]
4179!-
4180    CALL getin_p('SECHIBA_restart_in',restname_in)
4181    WRITE(numout,*) 'INPUT RESTART_FILE', restname_in
4182    !-
4183    !Config Key   = SECHIBA_rest_out
4184    !Config Desc  = Name of restart files to be created by SECHIBA
4185    !Config If    = OK_SECHIBA
4186    !Config Def   = sechiba_rest_out.nc
4187    !Config Help  = This variable give the name for
4188    !Config         the restart files. The restart software within
4189    !Config         IOIPSL will add .nc if needed.
4190    !Config Units = [FILE]
4191    !
4192    CALL getin_p('SECHIBA_rest_out', restname_out)
4193 
4194    lev(:) = zero
4195    itau_dep = istp
4196    in_julian = itau2date(istp, date0, dt)
4197    date0_rest = date0
4198    dt_rest = dt
4199    !
4200    IF (is_root_prc) THEN
4201       CALL restini( restname_in, iim_g, jjm_g, lon_g, lat_g, llm, lev, &
4202            &  restname_out, itau_dep, date0_rest, dt_rest, rest_id, overwrite_time, &
4203            &  use_compression=NC_COMPRESSION_ENABLE)
4204    ELSE
4205       rest_id=0
4206    ENDIF
4207    CALL bcast (itau_dep)
4208    CALL bcast (date0_rest)
4209    CALL bcast (dt_rest)
4210    !
4211    !  itau_dep of SECHIBA is phased with the GCM if needed
4212    !
4213    rest_julian = itau2date(itau_dep, date0_rest, dt_rest)
4214    !
4215    IF ( ABS( in_julian - rest_julian) .GT. dt/one_day .AND. .NOT. OFF_LINE_MODE ) THEN
4216       WRITE(numout,*) 'The SECHIBA restart is not for the same timestep as the GCM,'
4217       WRITE(numout,*) 'the two are synchronized. The land-surface conditions can not impose'
4218       WRITE(numout,*) 'the chronology of the simulation.'
4219       WRITE(numout,*) 'Time step of the GCM :', istp, 'Julian day : ', in_julian
4220       CALL ju2ymds(in_julian, yy, mm, dd, ss)
4221       WRITE(numout,*) 'In other word (yy,mm,dd,ss) : ', yy, mm, dd, ss
4222       WRITE(numout,*) 'Time step of SECHIBA :', itau_dep, 'Julian day : ', rest_julian
4223       CALL ju2ymds(rest_julian, yy, mm, dd, ss)
4224       WRITE(numout,*) 'In other word (yy,mm,dd,ss) : ', yy, mm, dd, ss
4225       
4226       itau_offset = itau_dep - istp
4227       date0_shifted = date0 - itau_offset*dt/one_day
4228       
4229       WRITE(numout,*) 'The new starting date is :', date0_shifted
4230       CALL ju2ymds(date0_shifted, yy, mm, dd, ss)
4231       WRITE(numout,*) 'In other word (yy,mm,dd,ss) : ', yy, mm, dd, ss
4232    ELSE
4233       itau_offset = 0
4234       date0_shifted = date0
4235    ENDIF
4236    !
4237!!!    CALL ioconf_startdate(date0_shifted)
4238    !
4239    !=====================================================================
4240    !- 1.5 Restart file for STOMATE
4241    !=====================================================================
4242    IF ( ok_stomate ) THEN 
4243       !-
4244       ! STOMATE IS ACTIVATED
4245       !-
4246       !Config Key   = STOMATE_RESTART_FILEIN
4247       !Config Desc  = Name of restart to READ for initial conditions of STOMATE
4248       !Config If    = STOMATE_OK_STOMATE
4249       !Config Def   = NONE
4250       !Config Help  = This is the name of the file which will be opened
4251       !Config         to extract the initial values of all prognostic
4252       !Config         values of STOMATE.
4253       !Config Units = [FILE]
4254       !-
4255       CALL getin_p('STOMATE_RESTART_FILEIN',stom_restname_in)
4256       WRITE(numout,*) 'STOMATE INPUT RESTART_FILE', stom_restname_in
4257       !-
4258       !Config Key   = STOMATE_RESTART_FILEOUT
4259       !Config Desc  = Name of restart files to be created by STOMATE
4260       !Config If    = STOMATE_OK_STOMATE
4261       !Config Def   = stomate_rest_out.nc
4262       !Config Help  = This is the name of the file which will be opened
4263       !Config         to write the final values of all prognostic values
4264       !Config         of STOMATE.
4265       !Config Units = [FILE]
4266       !-
4267       CALL getin_p('STOMATE_RESTART_FILEOUT', stom_restname_out)
4268       WRITE(numout,*) 'STOMATE OUTPUT RESTART_FILE', stom_restname_out
4269       !-
4270       IF (is_root_prc) THEN
4271         CALL restini (stom_restname_in, iim_g, jjm_g, lon_g, lat_g, llm, lev, &
4272            &  stom_restname_out, itau_dep, date0_rest, dt_rest, rest_id_stom, overwrite_time, &
4273            &  use_compression=NC_COMPRESSION_ENABLE)
4274       ELSE
4275         rest_id_stom=0
4276       ENDIF
4277       CALL bcast (itau_dep)
4278       CALL bcast (date0_rest)
4279       CALL bcast (dt_rest)
4280       !-
4281    ENDIF
4282  END SUBROUTINE ioipslctrl_restini
4283
4284END MODULE ioipslctrl
Note: See TracBrowser for help on using the repository browser.