source: branches/publications/ORCHIDEE_CAMEO_gmd_2022/src_sechiba/ioipslctrl.f90 @ 7693

Last change on this file since 7693 was 6567, checked in by josefine.ghattas, 4 years ago

Remove temp_sol_pot, see ticket #628

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