source: branches/ORCHIDEE_2_2/ORCHIDEE/src_sechiba/ioipslctrl.f90 @ 7252

Last change on this file since 7252 was 6319, checked in by josefine.ghattas, 5 years ago

Improvment for the ESM CO2 configuration:

  • Separate variable fco2_lu into 3 parts: fco2_lu, fco2_wh and fco2_ha
  • Move calculation of co2_flux from dt_sechiba time-step to daily time-step (in the part for do_slow)
  • Removed co2_flux and fco2_lu from stomate_intialize argument list. These variables were never used in the intialization phase.
  • Add co2_flux, and fco2_wh, fco2_ha to restart file
  • Corrected output unit for nee to be consistent with LMDZ and stomate output variables. It is now in kgC/m2/s.
  • Corrected output for znetco2
  • Added fCO2_fWoodharvest and fCO2_fHarvest as new possible tracers in LMDZ (intersurf).
  • Added diagnostic output for fCO2_fWoodharvest and fCO2_fHarvest
  1. Cadule
File size: 193.9 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)     :: soildiagax_id                !! ID for diagnostic soil levels
116    INTEGER(i_std)     :: solayax_id                   !! ID for the vertical axis of the CWRR hydrology
117    INTEGER(i_std)     :: hori_id2                      !! ID of the default horizontal longitude and latitude map.
118    INTEGER(i_std)     :: vegax_id2, laiax_id2, solax_id2, soltax_id2, nobioax_id2, albax_id2 !! ID's for two vertical coordinates
119    INTEGER(i_std)     :: solayax_id2                   !! ID for the vertical axis of the CWRR hydrology
120    INTEGER(i_std)     :: snowax_id                     !! ID for snow level axis
121
122    ! STOMATE AXIS
123    INTEGER(i_std)     :: hist_PFTaxis_id
124! deforestation
125    INTEGER(i_std)     :: hist_pool_10axis_id
126    INTEGER(i_std)     :: hist_pool_100axis_id
127    INTEGER(i_std)     :: hist_pool_11axis_id
128    INTEGER(i_std)     :: hist_pool_101axis_id
129    ! STOMATE IPCC AXIS
130    INTEGER(i_std)     :: hist_IPCC_PFTaxis_id
131    !
132    INTEGER(i_std)                         :: ier
133    REAL(r_std), ALLOCATABLE, DIMENSION(:) :: lon_rect, lat_rect
134    !
135    REAL(r_std),DIMENSION(nvm)   :: veg
136    REAL(r_std),DIMENSION(nlai+1):: indlai
137    REAL(r_std),DIMENSION(nstm)  :: soltyp
138    REAL(r_std),DIMENSION(nnobio):: nobiotyp
139    REAL(r_std),DIMENSION(2)     :: albtyp
140    REAL(r_std),DIMENSION(nslm)  :: solay
141    REAL(r_std),DIMENSION(nsnow) :: snowlev           !! Layers for snow axis
142    !
143    CHARACTER(LEN=80)           :: var_name           !! To store variables names
144    !
145    ! STOMATE history file
146    REAL(r_std)                  :: hist_days_stom     !!- GK time step in days for this history file
147    REAL(r_std)                  :: hist_dt_stom       !!- GK time step in seconds for this history file
148    REAL(r_std)                  :: dt_stomate_loc     !!  for test : time step of slow processes and STOMATE
149    REAL(r_std),DIMENSION(nvm)   :: hist_PFTaxis       !!- GK An axis we need for the history files
150!
151    REAL(r_std),DIMENSION(10)  :: hist_pool_10axis     !! Deforestation axis
152    REAL(r_std),DIMENSION(100)  :: hist_pool_100axis     !! Deforestation axis
153    REAL(r_std),DIMENSION(11)  :: hist_pool_11axis     !! Deforestation axis
154    REAL(r_std),DIMENSION(101)  :: hist_pool_101axis     !! Deforestation axis
155    !
156    ! IPCC history file
157    REAL(r_std)                  :: hist_days_stom_ipcc     !!- GK time step in days for this history file
158    REAL(r_std)                  :: hist_dt_stom_ipcc       !!- GK time step in seconds for this history file
159!
160    !
161    !=====================================================================
162    !- 3.0 Setting up the history files
163    !=====================================================================
164    !- 3.1 SECHIBA
165    !=====================================================================
166    !Config Key   = ALMA_OUTPUT
167    !Config Desc  = Should the output follow the ALMA convention
168    !Config If    = OK_SECHIBA
169    !Config Def   = n
170    !Config Help  = If this logical flag is set to true the model
171    !Config         will output all its data according to the ALMA
172    !Config         convention. It is the recommended way to write
173    !Config         data out of ORCHIDEE.
174    !Config Units = [FLAG]
175    CALL getin_p('ALMA_OUTPUT', almaoutput)   
176    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, diaglev(1:nslm), solayax_id)
367          CALL histvert(hist_id, 'soildiag', 'Diagnostic soil levels', 'm', &
368               &    nslm, diaglev(1:nslm), soildiagax_id)
369          CALL histvert(hist_id, 'snowlev', 'Snow levels',      'm', &
370               &    nsnow, snowlev, snowax_id)
371
372          !-
373          !- SECHIBA_HISTLEVEL = 1
374          !-
375          CALL histdef(hist_id, 'evap', 'Evaporation', 'mm/d', &
376               & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop(1), dt,dw)
377          CALL histdef(hist_id, 'coastalflow', 'Diffuse coastal flow', 'm^3/s', &
378               & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop_scinsec(1), dt,dw)
379          CALL histdef(hist_id, 'riverflow', 'River flow to the oceans', 'm^3/s', &
380               & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop_scinsec(1), dt,dw) 
381          CALL histdef(hist_id, 'temp_sol', 'Surface Temperature', 'C', &
382               & iim,jjm, hori_id, 1,1,1, -99, 32, avecels(1), dt,dw)
383          CALL histdef(hist_id, 'rain', 'Rainfall', 'mm/d',  &
384               & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop(1), dt,dw)
385          CALL histdef(hist_id, 'snowf', 'Snowfall', 'mm/d',  &
386               & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop(1), dt,dw)
387          CALL histdef(hist_id, 'netrad', 'Net radiation', 'W/m^2',  &
388               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
389          CALL histdef(hist_id, 'lai', 'Leaf Area Index', '1', &
390               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 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             ! var_name= "mc_1" ... "mc_3"
491             WRITE (var_name,"('moistc_',i1)") jst
492             CALL histdef(hist_id, var_name, 'Soil Moisture profile for soil type', 'm3/m3', &
493                  & iim,jjm, hori_id, nslm, 1, nslm, solayax_id, 32, avescatter(3),  dt,dw)
494             
495             ! var_name= "vegetsoil_1" ... "vegetsoil_3"
496             WRITE (var_name,"('vegetsoil_',i1)") jst
497             CALL histdef(hist_id, var_name, 'Fraction of vegetation on soil types', '%', &
498                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(3),  dt,dw)
499             
500             ! var_name= "kfact_root_1" ... "kfact_root_3"
501             WRITE (var_name,"('kfactroot_',i1)") jst
502             CALL histdef(hist_id, var_name, 'Root fraction profile for soil type', '%', &
503                  & iim,jjm, hori_id, nslm, 1, nslm, solayax_id, 32, avescatter(3), dt,dw)
504             
505          ENDDO
506
507          IF (ok_freeze_cwrr) THEN
508             CALL histdef(hist_id, 'profil_froz_hydro', 'Frozen fraction for each hydrological soil layer', '-', &
509                  & iim,jjm, hori_id, nslm, 1, nslm, solayax_id, 32, avescatter(1),  dt,dw)
510             CALL histdef(hist_id, 'temp_hydro', 'Soil temperature interpolated on hydrological layers', 'K', &
511                  & iim,jjm, hori_id, nslm, 1, nslm, solayax_id, 32, avescatter(1), dt,dw)
512          END IF
513         
514          CALL histdef(hist_id, 'kk_moy', 'Mean hydrological conductivity', 'mm/d', &
515               & iim,jjm,hori_id, nslm,1,nslm, solayax_id, 32, avescatter(1),  dt,dw)
516          DO jst=1,nstm
517             WRITE (var_name,"('profil_froz_hydro_',i1)") jst
518             CALL histdef(hist_id, trim(var_name), 'Frozen fraction for each hydrological soil layer and soiltile', '-', &
519                  & iim,jjm, hori_id, nslm, 1, nslm, solayax_id, 32, avescatter(1),  dt,dw)
520          ENDDO
521         
522          CALL histdef(hist_id, 'ptn_beg', 'Soil temperature from previous time step', 'K', &
523               & iim,jjm,hori_id, ngrnd,1,ngrnd, solax_id, 32, avescatter(1),  dt,dw)
524         
525          IF ( ok_freeze_thermix ) THEN
526             CALL histdef(hist_id, 'pcappa_supp', 'Additional heat capacity due to soil freezing for each soil layer', 'J/K', &
527                  iim,jjm,hori_id, ngrnd,1,ngrnd, solax_id, 32, avescatter(1),  dt,dw)
528          END IF
529         
530          CALL histdef(hist_id, 'shum_ngrnd_perma', 'Saturation degree on the thermal axes', '-', &
531               & iim,jjm,hori_id,ngrnd,1,ngrnd, solax_id, 32, avescatter(1),  dt,dw)
532          CALL histdef(hist_id, 'shumdiag_perma', 'Saturation degree of the soil', '-', &
533               & iim,jjm,hori_id,nslm,1,nslm, soildiagax_id, 32, avescatter(1),  dt,dw)
534
535          !
536          CALL histdef(hist_id, 'frac_bare', 'Bare soil fraction for each tile', '-', &
537               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(3), dt,dw)
538          CALL histdef(hist_id, 'soiltile', 'Fraction of soil tiles', '%', &
539               & iim,jjm, hori_id, nstm, 1, nstm, soltax_id, 32, once(3),  dt,dw)
540          !-
541          !- SECHIBA_HISTLEVEL = 4
542          !-
543          CALL histdef(hist_id, 'humtot', 'Total Soil Moisture', 'Kg/m^2', &
544               & iim,jjm, hori_id, 1, 1, 1, -99, 32, avescatter(4), dt,dw)
545          CALL histdef(hist_id, 'humtot_soil', 'Soil Moisture for soil type', 'Kg/m^2', &
546               & iim,jjm, hori_id, nstm, 1, nstm, soltax_id, 32, avescatter(4), dt,dw)
547          CALL histdef(hist_id, 'njsc', 'Soil class used for hydrology', '-', &
548               & iim,jjm, hori_id, 1, 1, 1, -99, 32, once(4), dt,dw)
549          CALL histdef(hist_id, 'qsintveg', 'Water on canopy', 'Kg/m^2', &
550               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(4), dt,dw)
551          CALL histdef(hist_id, 'rstruct', 'Structural resistance', 's/m', &
552               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(4), dt,dw)
553          CALL histdef(hist_id, 'gpp', 'Net assimilation of carbon by the vegetation', 'gC/m^2/s', &
554               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, fluxop_scinsec(4), dt,dw)
555
556          IF ( ok_stomate ) THEN
557             CALL histdef(hist_id, 'nee', 'Net Ecosystem Exchange', 'kgC/m^2/s', &
558                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, fluxop_scinsec(4), dt,dw)
559             CALL histdef(hist_id, 'maint_resp', 'Maintenance respiration', 'gC/m^2/s', &
560                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, fluxop_scinsec(4), dt,dw)
561             CALL histdef(hist_id, 'hetero_resp', 'Heterotrophic respiration', 'gC/m^2/s', &
562                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, fluxop_scinsec(4), dt,dw)
563             CALL histdef(hist_id, 'growth_resp', 'Growth respiration', 'gC/m^2/s', &
564                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, fluxop_scinsec(4), dt,dw)
565             CALL histdef(hist_id, 'npp', 'Net Primary Production', 'gC/m^2/s', &
566                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, fluxop_scinsec(1), dt, dw)
567          ENDIF
568          CALL histdef(hist_id, 'precisol', 'Throughfall', 'mm/d',  &
569               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, fluxop(4), dt,dw)
570          CALL histdef(hist_id, 'drysoil_frac', 'Fraction of visibly dry soil', '1',  &
571               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(4), dt,dw)
572          CALL histdef(hist_id, 'evapot', 'Potential evaporation', 'mm/d',  &
573               & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop(4), dt,dw)
574          CALL histdef(hist_id, 'evapot_corr', 'Potential evaporation', 'mm/d',  &
575               & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop(4), dt,dw)
576          !-
577          !- SECHIBA_HISTLEVEL = 5
578          !-
579          CALL histdef(hist_id, 'swnet', 'Net solar radiation', 'W/m^2',  &
580               & iim,jjm, hori_id, 1,1,1, -99, 32, ave(5), dt,dw)
581          CALL histdef(hist_id, 'swdown', 'Incident solar radiation', 'W/m^2',  &
582               & iim,jjm, hori_id, 1,1,1, -99, 32, ave(5), dt,dw)
583          CALL histdef(hist_id, 'lwdown', 'Absorbed downward longwave radiation', 'W/m^2',  &
584               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(5), dt,dw)
585          CALL histdef(hist_id, 'lwnet', 'Net surface longwave radiation', 'W/m^2',  &
586               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(5), dt,dw)
587          !-
588          !- SECHIBA_HISTLEVEL = 6
589          !-
590          CALL histdef(hist_id, 'ptn', 'Deep ground temperature', 'K', &
591               & iim,jjm, hori_id, ngrnd, 1, ngrnd, solax_id, 32, avescatter(6),  dt,dw)
592          CALL histdef(hist_id, 'snowmelt', 'snow melt', 'mm/d', &
593               & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop(6), dt,dw)
594          CALL histdef(hist_id, 'frac_snow_veg', 'snow fraction on vegeted area','-', &
595               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(6), dt,dw)
596          CALL histdef(hist_id, 'frac_snow_nobio', 'snow fraction on non-vegeted area', '-', &
597               & iim,jjm, hori_id, nnobio, 1,nnobio, nobioax_id, 32, avescatter(6), dt,dw)
598          CALL histdef(hist_id, 'pgflux', 'extra energy used for melting top snow layer', '-', &
599               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(6), dt,dw)
600
601          CALL histdef(hist_id, 'grndflux', 'ground heat flux', 'W/m2', &
602               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(6), dt,dw)
603          CALL histdef(hist_id, 'sfcfrz', 'surface frozen fraction', '-', &
604               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(6), dt,dw)
605          CALL histdef(hist_id, 'snowrho', 'Snow density profile', 'kg/m3', & 
606               & iim,jjm, hori_id, nsnow, 1, nsnow, snowax_id, 32,avescatter(6), dt,dw)
607          CALL histdef(hist_id, 'snowtemp','Snow temperature profile','K', &
608               & iim,jjm, hori_id, nsnow, 1, nsnow, snowax_id, 32,avescatter(6),dt,dw)
609          CALL histdef(hist_id, 'snowdz','Snow depth profile','m', &
610               & iim,jjm, hori_id, nsnow, 1, nsnow, snowax_id, 32,avescatter(6),dt,dw)
611          CALL histdef(hist_id, 'snowliq','Snow liquid content profile','m', &
612               & iim,jjm, hori_id, nsnow, 1, nsnow, snowax_id, 32,avescatter(6),dt,dw)
613          CALL histdef(hist_id, 'snowgrain','Snow grain profile','m', &
614               & iim,jjm, hori_id, nsnow, 1, nsnow, snowax_id, 32,avescatter(6),dt,dw)
615          CALL histdef(hist_id, 'snowheat','Snow Heat profile','J/m2', &
616               & iim,jjm, hori_id, nsnow, 1, nsnow, snowax_id, 32,avescatter(6),dt,dw)
617          CALL histdef(hist_id, 'radsink','Solar Radiation profile','W/m2', &
618               & iim,jjm, hori_id, nsnow, 1, nsnow, snowax_id, 32,avescatter(6),dt,dw)
619
620          CALL histdef(hist_id, 'Qg', 'Ground heat flux', 'W/m^2',  &
621               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
622
623          IF (ok_freeze_thermix) THEN
624             CALL histdef(hist_id, 'profil_froz', 'Frozen fraction of the soil', '-', &
625                  & iim,jjm, hori_id, ngrnd, 1, ngrnd, solax_id, 32, avescatter(6),  dt,dw)
626          END IF
627          CALL histdef(hist_id, 'pkappa', 'Soil thermal conductivity', 'W/m/K', &
628               & iim,jjm,hori_id, ngrnd, 1, ngrnd, solax_id, 32, avescatter(1),  dt,dw)
629          CALL histdef(hist_id, 'pcapa', 'Apparent heat capacity', 'J/m3/K', &
630               & iim,jjm,hori_id, ngrnd, 1, ngrnd, solax_id, 32, avescatter(1),  dt,dw)
631
632          !-
633          !- SECHIBA_HISTLEVEL = 7
634          !-
635          IF ( river_routing ) THEN
636             CALL histdef(hist_id, 'fastr', 'Fast flow reservoir', 'kg/m^2', &
637                  & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(7), dt,dw)
638             CALL histdef(hist_id, 'slowr', 'Slow flow reservoir', 'kg/m^2', &
639                  & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(7), dt,dw)
640             CALL histdef(hist_id, 'streamr', 'Stream flow reservoir', 'kg/m^2', &
641                  & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(7), dt,dw)
642             CALL histdef(hist_id, 'lakevol', 'Volume in lake reservoir', 'kg/m^2', &
643                  & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(7), dt,dw)
644             
645             !-
646             !- SECHIBA_HISTLEVEL = 8
647             !-
648             CALL histdef(hist_id, 'pondr', 'Ponds reservoir', 'kg/m^2', &
649                  & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(8), dt,dw)
650             CALL histdef(hist_id, 'swampmap', 'Map of swamps', 'm^2', &
651                  & iim,jjm, hori_id, 1,1,1, -99, 32, once(8), dt,dw)
652             !
653             IF ( do_irrigation ) THEN
654                CALL histdef(hist_id, 'irrigation', 'Net irrigation', 'mm/d', &
655                     & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop(8), dt,dw)
656                CALL histdef(hist_id, 'netirrig', 'Net irrigation requirement', 'mm/d', &
657                     & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop(8), dt,dw)
658                CALL histdef(hist_id, 'irrigmap', 'Map of irrigated surfaces', 'm^2', &
659                     & iim,jjm, hori_id, 1,1,1, -99, 32, once(8), dt,dw)
660             ENDIF
661             IF ( do_floodplains ) THEN
662                CALL histdef(hist_id, 'floodmap', 'Map of floodplains', 'm^2', &
663                     & iim,jjm, hori_id, 1,1,1, -99, 32, once(8), dt,dw)
664                CALL histdef(hist_id, 'floodh', 'Floodplains height', 'mm', &
665                     & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(8), dt,dw)
666                CALL histdef(hist_id, 'floodr', 'Floodplains reservoir', 'kg/m^2', &
667                     & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(8), dt,dw)
668                CALL histdef(hist_id, 'floodout', 'Flow out of floodplains', 'mm/d', &
669                     & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop(8), dt,dw)
670                CALL histdef(hist_id, 'evapflo', 'Floodplains evaporation', 'mm/d', &
671                     & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop(8), dt,dw)
672             ENDIF
673             !
674          ENDIF
675
676          CALL histdef(hist_id, 'k_litt', 'Litter cond', 'mm/d', &
677               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(8), dt,dw)
678          CALL histdef(hist_id, 'beta', 'Beta Function', '1',  &
679               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(8), dt,dw)
680          CALL histdef(hist_id, 'raero', 'Aerodynamic resistance', 's/m',  &
681               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(8), dt,dw)
682          CALL histdef(hist_id, 'cdrag', 'Drag coefficient for LE and SH', '?',  &
683               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(8), dt,dw)
684          CALL histdef(hist_id, 'Wind', 'Wind speed', 'm/s',  &
685               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(8), dt,dw)
686          CALL histdef(hist_id, 'qsatt' , 'Surface saturated humidity', 'g/g', &
687               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(8), dt,dw)
688          CALL histdef(hist_id, 'vbeta1', 'Beta for sublimation', '1',  &
689               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(8), dt,dw)
690          CALL histdef(hist_id, 'vbeta4', 'Beta for bare soil', '1',  &
691               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(8), dt,dw)
692          CALL histdef(hist_id, 'vbeta5', 'Beta for floodplains', '1',  &
693               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(8), dt,dw)
694          CALL histdef(hist_id, 'gsmean', 'mean stomatal conductance', 'mol/m2/s', &
695               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(8), dt,dw)
696          CALL histdef(hist_id, 'humrel', 'Soil moisture stress', '-',  &
697               & iim,jjm, hori_id, nvm,1,nvm, vegax_id, 32, avescatter(8), dt,dw)
698          !-
699          !- SECHIBA_HISTLEVEL = 9
700          !-
701          !-
702          !- SECHIBA_HISTLEVEL = 10
703          !-
704          CALL histdef(hist_id, 'cimean', 'Stomatal CO2 concentation', 'mmole/m2/s', &
705               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(10), dt,dw)
706          CALL histdef(hist_id, 'cim', 'cim', 'ppm', &
707               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(10), dt,dw)
708          CALL histdef(hist_id, 'leafci', 'leaf ci', 'ppm', &
709               & iim,jjm, hori_id, nlai+1, 1, nlai+1, laiax_id, 32, avescatter(10), dt,dw)
710          CALL histdef(hist_id, 'gs', 'gs', 'mol m-2 s-1', &
711               & iim,jjm, hori_id, nlai+1, 1, nlai+1, laiax_id, 32, avescatter(10), dt,dw)
712          CALL histdef(hist_id, 'assimi', 'assimi', 'mol m-2 s-1', &
713               & iim,jjm, hori_id, nlai+1, 1, nlai+1, laiax_id, 32, avescatter(10), dt,dw)
714          CALL histdef(hist_id, 'Rd', 'Rd', 'mol m-2 s-1', &
715               & iim,jjm, hori_id, nlai+1, 1, nlai+1, laiax_id, 32, avescatter(10), dt,dw)
716          CALL histdef(hist_id, 'Cc', 'Cc', 'ppm', &
717               & iim,jjm, hori_id, nlai+1, 1, nlai+1, laiax_id, 32, avescatter(10), dt,dw)
718          CALL histdef(hist_id, 'limitphoto', 'limitphoto', '-', &
719               & iim,jjm, hori_id, nlai+1, 1, nlai+1, laiax_id, 32, avescatter(10), dt,dw)
720          CALL histdef(hist_id, 'Vc', 'Vc', 'mol m-2 s-1', &
721               & iim,jjm, hori_id, nlai+1, 1, nlai+1, laiax_id, 32, avescatter(10), dt,dw)
722          CALL histdef(hist_id, 'Vj', 'Vj', 'mol e- m-2 s-1', &
723               & iim,jjm, hori_id, nlai+1, 1, nlai+1, laiax_id, 32, avescatter(10), dt,dw)
724          CALL histdef(hist_id, 'gm', 'gm', 'mol m-2 s-1', &
725               & iim, jjm, hori_id, 1, 1, 1, -99, 32, avescatter(10), dt,dw)
726          CALL histdef(hist_id, 'gammastar', 'gammastar', 'ppm', &
727               & iim, jjm, hori_id, 1, 1, 1, -99, 32, avescatter(10), dt,dw)
728          CALL histdef(hist_id, 'Kmo', 'Kmo', 'ppm', &
729               & iim, jjm, hori_id, 1, 1, 1, -99, 32, avescatter(10), dt,dw)
730          CALL histdef(hist_id, 'Kmc', 'Kmc', 'ppm', &
731               & iim, jjm, hori_id, 1, 1, 1, -99, 32, avescatter(10), dt,dw)
732          CALL histdef(hist_id, 'vbeta3', 'Beta for Transpiration', 'mm/d', &
733               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(10), dt,dw)
734          CALL histdef(hist_id, 'rveget', 'Canopy resistance', 's/m', &
735               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(10), dt,dw)
736          CALL histdef(hist_id,'vbeta2','Beta for Interception loss','mm/d', &
737               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(10), dt,dw)
738          CALL histdef(hist_id, 'qsintmax', 'Maximum Interception capacity', 'Kg/m^2', &
739               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(10), dt,dw)
740
741          !- SECHIBA_HISTLEVEL = 11
742          !-
743
744          CALL histdef(hist_id, 'mrsos', "Moisture in Upper 0.1 m of Soil Column", "kg m-2", &
745               & iim,jjm, hori_id, 1, 1, 1, -99, 32, avescatter(11), dt,dw)
746         
747          CALL histdef(hist_id, 'mrso', "Total Soil Moisture Content", "kg m-2", &
748               & iim,jjm, hori_id, 1, 1, 1, -99, 32, avescatter(11), dt,dw)
749         
750          CALL histdef(hist_id, 'mrros', "Surface Runoff", "kg m-2 s-1", &
751               & iim,jjm, hori_id, 1, 1, 1, -99, 32, fluxop_scinsec(11), dt,dw)
752         
753          CALL histdef(hist_id, 'mrro', "Total Runoff", "kg m-2 s-1", &
754               & iim,jjm, hori_id, 1, 1, 1, -99, 32, fluxop_scinsec(11), dt,dw)
755
756          CALL histdef(hist_id, 'prveg', "Precipitation onto Canopy", "kg m-2 s-1", &
757               & iim,jjm, hori_id, 1, 1, 1, -99, 32, fluxop_scinsec(11), dt,dw)
758
759
760          CALL histdef(hist_id, 'evspsblveg', "Evaporation from Canopy", "kg m-2 s-1", &
761               & iim,jjm, hori_id, 1, 1, 1, -99, 32, fluxop_scinsec(11), dt,dw)
762         
763          CALL histdef(hist_id, 'evspsblsoi', "Water Evaporation from Soil", "kg m-2 s-1", &
764               & iim,jjm, hori_id, 1, 1, 1, -99, 32, fluxop_scinsec(11), dt,dw)
765         
766          CALL histdef(hist_id, 'tran', "Transpiration", "kg m-2 s-1", &
767               & iim,jjm, hori_id, 1, 1, 1, -99, 32, fluxop_scinsec(11), dt,dw)
768         
769          CALL histdef(hist_id, 'treeFrac', "Tree Cover Fraction", "%", &
770               & iim,jjm, hori_id, 1, 1, 1, -99, 32, avescatter(11), dt,dw)
771         
772          CALL histdef(hist_id, 'grassFrac', "Natural Grass Fraction", "%", &
773               & iim,jjm, hori_id, 1, 1, 1, -99, 32, avescatter(11), dt,dw)
774         
775          CALL histdef(hist_id, 'cropFrac', "Crop Fraction", "%", &
776               & iim,jjm, hori_id, 1, 1, 1, -99, 32, avescatter(11), dt,dw)
777         
778          CALL histdef(hist_id, 'baresoilFrac', "Bare Soil Fraction", "%", &
779               & iim,jjm, hori_id, 1, 1, 1, -99, 32, avescatter(11), dt,dw)
780         
781          CALL histdef(hist_id, 'residualFrac', &
782               & "Fraction of Grid Cell that is Land but Neither Vegetation-Covered nor Bare Soil", "%", &
783               & iim,jjm, hori_id, 1, 1, 1, -99, 32, avescatter(11), dt,dw)
784         
785          IF ( ok_bvoc ) THEN
786             CALL histdef(hist_id, 'PAR', 'PAR', 'umol phot/m^2/s',  &
787                  & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(11), dt,dw)
788             IF ( ok_radcanopy ) THEN
789                CALL histdef(hist_id, 'PARsun', 'Sunlit Leaf PAR', 'umol phot/m^2/s', &
790                     & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(11), dt,dw)
791                CALL histdef(hist_id, 'PARsh', 'Shaded Leaf Area PAR', 'umol phot/m^2/s', &
792                     & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(11), dt,dw)
793                CALL histdef(hist_id, 'laisun', 'Sunlit Leaf Area Index', '1', &
794                     & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(11), dt,dw)
795                CALL histdef(hist_id, 'laish', 'Shaded Leaf Area Index', '1', &
796                     & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(11), dt,dw)
797                CALL histdef(hist_id, 'Fdf', 'Fdf', '1',  &
798                     & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(11), dt,dw)
799                IF ( ok_multilayer ) then
800                   CALL histdef(hist_id, 'PARsuntab', 'Sunlit Leaf PAR', 'umol phot/m^2/s', &
801                        & iim,jjm, hori_id, nlai+1, 1, nlai+1, laiax_id, 32, avescatter(11), dt,dw)
802                   CALL histdef(hist_id, 'PARshtab', 'Shaded Leaf Area PAR', 'umol phot/m^2/s', &
803                        & iim,jjm, hori_id, nlai+1, 1, nlai+1, laiax_id, 32, avescatter(11), dt,dw)
804                ENDIF
805                CALL histdef(hist_id, 'coszang', 'coszang', '1',  &
806                     & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(11), dt,dw)
807                CALL histdef(hist_id, 'PARdf', 'PARdf', '1',  &
808                     & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(11), dt,dw)
809                CALL histdef(hist_id, 'PARdr', 'PARdr', '1',  &
810                     & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(11), dt,dw)
811                CALL histdef(hist_id, 'Trans', 'Trans', '1',  &
812                     & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(11), dt,dw)
813             END IF
814             
815             CALL histdef(hist_id, 'flx_fertil_no', 'flx_fertil_no', 'ngN/m^2/s', &
816                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(11), dt,dw)
817             CALL histdef(hist_id, 'CRF', 'CRF', '1', &
818                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(11), dt,dw)
819             CALL histdef(hist_id, 'flx_co2_bbg_year', 'flx_co2_bbg_year', 'kgC/m^2/yr ', &
820                  & iim,jjm, hori_id, 1,1,1, -99, 32, once(11), dt,dw) 
821             CALL histdef(hist_id, 'N_qt_WRICE_year', 'N_qt_WRICE_year', 'kgN/yr ', &
822                  & iim,jjm, hori_id, 1,1,1, -99, 32, once(11), dt,dw) 
823             CALL histdef(hist_id, 'N_qt_OTHER_year', 'N_qt_OTHER_year', 'kgN/yr ', &
824                  & iim,jjm, hori_id, 1,1,1, -99, 32, once(11), dt,dw) 
825             CALL histdef(hist_id, 'flx_iso', 'flx_iso', 'kgC/m^2/s', &
826                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(11), dt,dw)
827             CALL histdef(hist_id, 'flx_mono', 'flx_mono', 'kgC/m^2/s',&
828                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(11), dt,dw)
829             CALL histdef(hist_id, 'flx_apinen', 'flx_apinen', 'kgC/m^2/s',&
830                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(11), dt,dw)
831             CALL histdef(hist_id, 'flx_bpinen', 'flx_bpinen', 'kgC/m^2/s',&
832                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(11), dt,dw)
833             CALL histdef(hist_id, 'flx_limonen', 'flx_limonen', 'kgC/m^2/s',&
834                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(11), dt,dw)
835             CALL histdef(hist_id, 'flx_myrcen', 'flx_myrcen', 'kgC/m^2/s',&
836                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(11), dt,dw)
837             CALL histdef(hist_id, 'flx_sabinen', 'flx_sabinen', 'kgC/m^2/s',&
838                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(11), dt,dw)
839             CALL histdef(hist_id, 'flx_camphen', 'flx_camphen', 'kgC/m^2/s',&
840                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(11), dt,dw)
841             CALL histdef(hist_id, 'flx_3caren', 'flx_3caren', 'kgC/m^2/s',&
842                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(11), dt,dw)
843             CALL histdef(hist_id, 'flx_tbocimen', 'flx_tbocimen', 'kgC/m^2/s',&
844                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(11), dt,dw)
845             CALL histdef(hist_id, 'flx_othermono', 'flx_othermono', 'kgC/m^2/s',&
846                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(11), dt,dw)
847             CALL histdef(hist_id, 'flx_sesquiter', 'flx_sesquiter', 'kgC/m^2/s',&
848                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(11), dt,dw)
849             CALL histdef(hist_id, 'flx_ORVOC', 'flx_ORVOC', 'kgC/m^2/s',&
850                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(11), dt,dw)
851             CALL histdef(hist_id, 'flx_MBO', 'flx_MBO', 'kgC/m^2/s',&
852                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(11), dt,dw)
853             CALL histdef(hist_id, 'flx_methanol', 'flx_methanol', 'kgC/m^2/s',&
854                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(11), dt,dw)
855             CALL histdef(hist_id, 'flx_acetone', 'flx_acetone', 'kgC/m^2/s',&
856                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(11), dt,dw)
857             CALL histdef(hist_id, 'flx_acetal', 'flx_acetal', 'kgC/m^2/s',&
858                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(11), dt,dw)
859             CALL histdef(hist_id, 'flx_formal', 'flx_formal', 'kgC/m^2/s',&
860                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(11), dt,dw)
861             CALL histdef(hist_id, 'flx_acetic', 'flx_acetic', 'kgC/m^2/s',&
862                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(11), dt,dw)
863             CALL histdef(hist_id, 'flx_formic', 'flx_formic', 'kgC/m^2/s',&
864                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(11), dt,dw)
865             CALL histdef(hist_id, 'flx_no_soil', 'flx_no_soil', 'ngN/m^2/s',&
866                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(11), dt,dw)
867             CALL histdef(hist_id, 'flx_no', 'flx_no', 'ngN/m^2/s',&
868                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(11), dt,dw)
869             CALL histdef(hist_id, 'fco2', 'fco2', '-', &
870                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(10), dt,dw)
871          ENDIF
872
873       ELSE 
874          !-
875          !- This is the ALMA convention output now
876          !-
877          !-
878          IF ( grid_type == regular_lonlat ) THEN
879#ifdef CPP_PARA
880             CALL histbeg(histname, iim, lon_rect, jjm, lat_rect, 1, iim, 1, jjm, &
881                  &     istp_old, date0, dt, hori_id, hist_id,orch_domain_id)
882#else
883             CALL histbeg(histname, iim, lon_rect, jjm, lat_rect, 1, iim, 1, jjm, &
884                  &     istp_old, date0, dt, hori_id, hist_id)
885#endif
886          ELSE
887#ifdef CPP_PARA
888             CALL histbeg(histname, iim, lon, jjm, lat, 1, iim, 1, jjm, &
889                  &     istp_old, date0, dt, hori_id, hist_id,domain_id=orch_domain_id)
890#else
891             CALL histbeg(histname, iim, lon, jjm, lat, 1, iim, 1, jjm, &
892                  &     istp_old, date0, dt, hori_id, hist_id)
893#endif
894          ENDIF
895          !-
896          CALL histvert(hist_id, 'veget', 'Vegetation types', '1', &
897               &    nvm,   veg, vegax_id)
898          CALL histvert(hist_id, 'laiax', 'Nb LAI', 'm', &
899               &   nlai+1,indlai, laiax_id)
900          CALL histvert(hist_id, 'solth', 'Soil levels',      'm', &
901               &    ngrnd, znt, solax_id)
902          CALL histvert(hist_id, 'soiltyp', 'Soil types',      '1', &
903               &    nstm, soltyp, soltax_id)
904          CALL histvert(hist_id, 'nobio', 'Other surface types',      '1', &
905               &    nnobio, nobiotyp, nobioax_id)
906          CALL histvert(hist_id, 'solay', 'Hydrol soil levels',      'm', &
907               &    nslm, diaglev(1:nslm), solayax_id)
908
909          !-
910          !-  Vegetation
911          !-
912          CALL histdef(hist_id, 'vegetfrac', 'Fraction of vegetation', '1', &
913               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(3), dt,dw)
914          CALL histdef(hist_id, 'maxvegetfrac', 'Maximum fraction of vegetation', '1', &
915               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(3), dt,dw)
916          CALL histdef(hist_id, 'nobiofrac', 'Fraction of other surface types', '1', &
917               & iim,jjm, hori_id, nnobio, 1, nnobio, nobioax_id, 32, avescatter(3), dt,dw)
918          CALL histdef(hist_id, 'lai', 'Leaf Area Index', '1', &
919               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(1), dt,dw)
920          !-
921          !- Forcing variables
922          !-
923          CALL histdef(hist_id, 'SinAng', 'Net shortwave radiation', '-',  &
924               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(9), dt,dw)
925          CALL histdef(hist_id, 'LWdown', 'Downward longwave radiation', 'W/m^2',  &
926               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(9), dt,dw)
927          CALL histdef(hist_id, 'SWdown', 'Downward shortwave radiation', 'W/m^2',  &
928               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(9), dt,dw)
929          CALL histdef(hist_id, 'Tair', 'Near surface air temperature at forcing level', 'K',  &
930               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(2), dt,dw)
931          CALL histdef(hist_id, 'Qair', 'Near surface specific humidity at forcing level', 'g/g',  &
932               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(2), dt,dw)
933          CALL histdef(hist_id, 'SurfP', 'Surface Pressure', 'hPa',  &
934               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(9), dt,dw)
935          CALL histdef(hist_id, 'Windu', 'Eastward wind', 'm/s',  &
936               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(9), dt,dw)
937          CALL histdef(hist_id, 'Windv', 'Northward wind', 'm/s',  &
938               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(9), dt,dw)
939          !-
940          !-  General energy balance
941          !-
942          CALL histdef(hist_id, 'SWnet', 'Net shortwave radiation', 'W/m^2',  &
943               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
944          CALL histdef(hist_id, 'LWnet', 'Net longwave radiation', 'W/m^2',  &
945               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
946          CALL histdef(hist_id, 'Qh', 'Sensible heat flux', 'W/m^2',  &
947               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
948          CALL histdef(hist_id, 'Qle', 'Latent heat flux', 'W/m^2',  &
949               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
950          CALL histdef(hist_id, 'Qg', 'Ground heat flux', 'W/m^2',  &
951               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
952          CALL histdef(hist_id, 'Qv', 'Energy of sublimation', 'W/m^2',  &
953               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
954          CALL histdef(hist_id, 'DelSurfHeat', 'Change in surface layer heat', 'J/m^2',  &
955               & iim,jjm, hori_id, 1,1,1, -99, 32, sumscatter(1), dt,dw)
956          CALL histdef(hist_id, 'DelColdCont', 'Change in snow surface layer cold content', 'J/m^2',  &
957               & iim,jjm, hori_id, 1,1,1, -99, 32, sumscatter(1), dt,dw)
958          !-
959          !- General water balance
960          !-
961          CALL histdef(hist_id, 'Snowf', 'Snowfall rate', 'kg/m^2/s',  &
962               & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop_scinsec(1), dt,dw)
963          CALL histdef(hist_id, 'Rainf', 'Rainfall rate', 'kg/m^2/s',  &
964               & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop_scinsec(1), dt,dw)
965          CALL histdef(hist_id, 'Evap', 'Total Evapotranspiration', 'kg/m^2/s', &
966               & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop_scinsec(1), dt,dw)
967          CALL histdef(hist_id, 'Qs', 'Surface runoff', 'kg/m^2/s', &
968               & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop_scinsec(1), dt,dw)
969          CALL histdef(hist_id, 'Qsb', 'Sub-surface runoff', 'kg/m^2/s', &
970               & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop_scinsec(1), dt,dw)
971          CALL histdef(hist_id, 'Qrec', 'Recharge', 'kg/m^2/s', &
972               & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop_scinsec(1), dt,dw)
973          CALL histdef(hist_id, 'Qsm', 'Snowmelt', 'kg/m^2/s', &
974               & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop_scinsec(1), dt,dw)
975          CALL histdef(hist_id, 'DelSoilMoist', 'Change in soil moisture', 'kg/m^2',  &
976               & iim,jjm, hori_id, 1, 1, 1, -99, 32, sumscatter(1), dt,dw)
977          CALL histdef(hist_id, 'DelSurfStor', 'Change in Surface Water Storage','kg/m^2',&
978               & iim,jjm, hori_id, 1, 1, 1, -99, 32, sumscatter(1), dt,dw)
979          CALL histdef(hist_id, 'DelIntercept', 'Change in interception storage', 'kg/m^2',  &
980               & iim,jjm, hori_id, 1, 1, 1, -99, 32, sumscatter(1), dt,dw)
981          CALL histdef(hist_id, 'DelSWE', 'Change in Snow Water Equivalent', 'kg/m^2',  &
982               & iim,jjm, hori_id, 1, 1, 1, -99, 32, sumscatter(1), dt,dw)
983          IF ( do_irrigation ) THEN
984             CALL histdef(hist_id, 'Qirrig', 'Irrigation', 'kg/m^2/s', &
985                  & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop_scinsec(1), dt,dw)
986             CALL histdef(hist_id, 'Qirrig_req', 'Irrigation requirement', 'kg/m^2/s', &
987                  & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop_scinsec(1), dt,dw)
988          ENDIF
989          !-
990          !- Surface state
991          !-
992          CALL histdef(hist_id, 'AvgSurfT', 'Average surface temperature', 'K', &
993               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
994          CALL histdef(hist_id, 'PotSurfT', 'Potential (Unstressed) surface temperature', 'K', &
995               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
996          CALL histdef(hist_id, 'RadT', 'Surface radiative temperature', 'K', &
997               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
998          CALL histdef(hist_id, 'Albedo', 'Albedo', '1', &
999               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
1000          CALL histdef(hist_id, 'SurfStor', 'Surface Water Storage','kg/m^2',  &
1001               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
1002          CALL histdef(hist_id, 'SWE', 'Snow Water Equivalent', 'kg/m^2', &
1003               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
1004          CALL histdef(hist_id, 'InterceptVeg', 'Intercepted Water on Canopy', 'Kg/m^2', &
1005               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(1), dt,dw)
1006          !!-
1007          !-  Sub-surface state
1008          !-
1009          CALL histdef(hist_id, 'SoilMoist', '3D average layer soil moisture', 'kg/m^2',  &
1010               & iim,jjm, hori_id, nslm, 1, nslm, solayax_id, 32, avescatter(1), dt,dw)
1011
1012          IF (ok_freeze_cwrr) THEN
1013             CALL histdef(hist_id, 'profil_froz_hydro', 'Frozen fraction for each hydrological soil layer', '-', &
1014                  & iim,jjm, hori_id, nslm, 1, nslm,solayax_id, 32, avescatter(1),  dt,dw)
1015             DO jst=1,nstm
1016                WRITE (var_name,"('profil_froz_hydro_',i1)") jst
1017                CALL histdef(hist_id, trim(var_name), 'Frozen fraction for each hydrological soil layer and soiltile', '-', &
1018                     & iim,jjm, hori_id, nslm, 1, nslm, solayax_id, 32, avescatter(1),  dt,dw)
1019             ENDDO
1020             
1021             CALL histdef(hist_id, 'temp_hydro', 'Soil temperature interpolated on hydrological layers', 'K', &
1022                     & iim,jjm, hori_id, nslm, 1, nslm, solayax_id, 32, avescatter(1), dt,dw)
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, 'leafci', 'leaf Ci', 'ppm', &
1126               & iim,jjm, hori_id,nlai+1, 1, nlai+1, laiax_id, 32, avescatter(10), dt,dw)
1127          CALL histdef(hist_id, 'gs', 'gs', '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, 'assimi', 'assimi', '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, 'Rd', 'Rd', 'mol m-2 s-1', &
1132               & iim,jjm, hori_id, nlai+1, 1, nlai+1, laiax_id, 32, avescatter(10), dt,dw)
1133          CALL histdef(hist_id, 'Cc', 'Cc', 'ppm', &
1134               & iim,jjm, hori_id, nlai+1, 1, nlai+1, laiax_id, 32, avescatter(10), dt,dw)
1135          CALL histdef(hist_id, 'limitphoto', 'limitphoto', '-', &
1136               & iim,jjm, hori_id, nlai+1, 1, nlai+1, laiax_id, 32, avescatter(10), dt,dw)
1137          CALL histdef(hist_id, 'Vc', 'Vc', 'mol 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, 'Vj', 'Vj', 'mol e- m-2 s-1', &
1140               & iim,jjm, hori_id, nlai+1, 1, nlai+1, laiax_id, 32, avescatter(10), dt,dw)
1141          CALL histdef(hist_id, 'gm', 'gm', 'mol m-2 s-1', &
1142               & iim,jjm, hori_id, 1, 1, 1, -99, 32, avescatter(10), dt,dw)
1143          CALL histdef(hist_id, 'gammastar', 'gammastar', 'ppm', &
1144               & iim, jjm, hori_id, 1, 1, 1, -99, 32, avescatter(10), dt,dw)
1145          CALL histdef(hist_id, 'Kmo', 'Kmo', 'ppm', &
1146               & iim, jjm, hori_id, 1, 1, 1, -99, 32, avescatter(10), dt,dw)
1147          CALL histdef(hist_id, 'Kmc', 'Kmc', 'ppm', &
1148               & iim, jjm, hori_id, 1, 1, 1, -99, 32, avescatter(10), dt,dw)
1149
1150          IF ( ok_stomate ) THEN
1151             CALL histdef(hist_id, 'NEE', 'Net Ecosystem Exchange', '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, 'maint_resp', 'Maintenance 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, 'hetero_resp', 'Heterotrophic 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, 'growth_resp', 'Growth 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       !- Forcing and grid information
1166       !-
1167       CALL histdef(hist_id, 'LandPoints', 'Land Points', '1', &
1168            & iim,jjm, hori_id, 1,1,1, -99, 32, once(10), dt,dw) 
1169       CALL histdef(hist_id, 'Areas', 'Mesh areas', 'm2', &
1170            & iim,jjm, hori_id, 1,1,1, -99, 32, once(1), dt, dw)
1171       CALL histdef(hist_id, 'Contfrac', 'Continental fraction', '1', &
1172            & iim,jjm, hori_id, 1,1,1, -99, 32, once(1), dt, dw)
1173       !-
1174       ! Write the names of the pfts in the history files
1175       global_attribute="PFT_name"
1176       DO i=1,nvm
1177          WRITE(global_attribute(9:10),"(I2.2)") i
1178          CALL histglobal_attr(hist_id, global_attribute, PFT_name(i))
1179       ENDDO
1180       !-
1181       CALL histend(hist_id)
1182    ENDIF ! IF (is_omp_root)
1183 
1184    END IF !IF ( dw == 0 )
1185    !
1186    !
1187    ! Second SECHIBA hist file
1188    !
1189    !-
1190    !Config Key   = SECHIBA_HISTFILE2
1191    !Config Desc  = Flag to switch on histfile 2 for SECHIBA (hi-frequency ?)
1192    !Config If    = OK_SECHIBA
1193    !Config Def   = n
1194    !Config Help  = This Flag switch on the second SECHIBA writing for hi (or low)
1195    !Config         frequency writing. This second output is optional and not written
1196    !Config         by default.
1197    !Config Units = [FLAG]
1198    !-
1199    ok_histfile2=.FALSE.
1200    CALL getin_p('SECHIBA_HISTFILE2', ok_histfile2)
1201    IF (printlev >= 2) WRITE(numout,*) 'SECHIBA_HISTFILE2 ', ok_histfile2
1202    !
1203    !-
1204    !Config Key   = WRITE_STEP2
1205    !Config Desc  = Frequency in seconds at which to WRITE output
1206    !Config If    = SECHIBA_HISTFILE2
1207    !Config Def   = 1800.0
1208    !Config Help  = This variables gives the frequency the output 2 of
1209    !Config         the model should be written into the netCDF file.
1210    !Config         It does not affect the frequency at which the
1211    !Config         operations such as averaging are done.
1212    !Config         That is IF the coding of the calls to histdef
1213    !Config         are correct !
1214    !Config Units = [seconds]
1215    !-
1216    dw2 = 1800.0
1217    CALL getin_p('WRITE_STEP2', dw2)
1218   
1219    ! Deactivate sechiba_histfile2 if the frequency is set to zero
1220    IF ( dw2 == 0 ) THEN
1221       ok_histfile2=.FALSE.
1222       IF (printlev >= 2) WRITE(numout,*) 'WRITE_STEP2 was set to zero and therfore SECHIBA_HISTFILE2 is deactivated.'
1223    ELSE IF ( hist_id < 0 ) THEN
1224       ! Deactivate all history files if sechiba_history file is deactivated
1225       ok_histfile2=.FALSE.
1226       IF (printlev >= 2) WRITE(numout,*) 'SECHIBA_HISTFILE2 will not be created because sechiba_history file is deactivated.'
1227    END IF
1228
1229    hist2_id = -1
1230    !
1231    IF (ok_histfile2) THEN
1232       !-
1233       !Config Key   = SECHIBA_OUTPUT_FILE2
1234       !Config Desc  = Name of file in which the output number 2 is going to be written
1235       !Config If    = SECHIBA_HISTFILE2
1236       !Config Def   = sechiba_out_2.nc
1237       !Config Help  = This file is going to be created by the model
1238       !Config         and will contain the output 2 from the model.
1239       !Config Units = [FILE]
1240       !-
1241       histname2='sechiba_out_2.nc'
1242       CALL getin_p('SECHIBA_OUTPUT_FILE2', histname2)
1243       IF (printlev >= 2) WRITE(numout,*) 'SECHIBA_OUTPUT_FILE2 ', histname2
1244       !-
1245       !Config Key   = SECHIBA_HISTLEVEL2
1246       !Config Desc  = SECHIBA history 2 output level (0..10)
1247       !Config If    = SECHIBA_HISTFILE2
1248       !Config Def   = 1
1249       !Config Help  = Chooses the list of variables in the history file.
1250       !Config         Values between 0: nothing is written; 10: everything is
1251       !Config         written are available More details can be found on the web under documentation.
1252       !Config         web under documentation.
1253       !Config         First level contains all ORCHIDEE outputs.
1254       !Config Units = [-]
1255       !-
1256       hist2_level = 1
1257       CALL getin_p('SECHIBA_HISTLEVEL2', hist2_level)
1258       !-
1259       IF (printlev >= 2) WRITE(numout,*) 'SECHIBA history level 2 : ',hist2_level
1260       IF ( (hist2_level > max_hist_level).OR.(hist2_level < 0) ) THEN
1261          STOP 'This history level 2 is not allowed'
1262       ENDIF
1263       !
1264       !-
1265       !- define operations as a function of history level.
1266       !- Above hist2_level, operation='never'
1267       !-
1268       ave2(1:max_hist_level) = 'ave(scatter(X))'
1269       IF (hist2_level < max_hist_level) THEN
1270          ave2(hist2_level+1:max_hist_level) = 'never'
1271       ENDIF
1272       sumscatter2(1:max_hist_level) = 't_sum(scatter(X))'
1273       IF (hist2_level < max_hist_level) THEN
1274          sumscatter2(hist2_level+1:max_hist_level) = 'never'
1275       ENDIF
1276       avecels2(1:max_hist_level) = 'ave(cels(scatter(X)))'
1277       IF (hist2_level < max_hist_level) THEN
1278          avecels2(hist2_level+1:max_hist_level) = 'never'
1279       ENDIF
1280       avescatter2(1:max_hist_level) = 'ave(scatter(X))'
1281       IF (hist2_level < max_hist_level) THEN
1282          avescatter2(hist2_level+1:max_hist_level) = 'never'
1283       ENDIF
1284       tmincels2(1:max_hist_level) = 't_min(cels(scatter(X)))'
1285       IF (hist2_level < max_hist_level) THEN
1286          tmincels2(hist2_level+1:max_hist_level) = 'never'
1287       ENDIF
1288       tmaxcels2(1:max_hist_level) = 't_max(cels(scatter(X)))'
1289       IF (hist2_level < max_hist_level) THEN
1290          tmaxcels2(hist2_level+1:max_hist_level) = 'never'
1291       ENDIF
1292       fluxop2(1:max_hist_level) = flux_op
1293       IF (hist2_level < max_hist_level) THEN
1294          fluxop2(hist2_level+1:max_hist_level) = 'never'
1295       ENDIF
1296       fluxop_scinsec2(1:max_hist_level) = flux_scinsec
1297       IF (hist2_level < max_hist_level) THEN
1298          fluxop_scinsec2(hist2_level+1:max_hist_level) = 'never'
1299       ENDIF
1300       once2(1:max_hist_level) = 'once(scatter(X))'
1301       IF (hist2_level < max_hist_level) THEN
1302          once2(hist2_level+1:max_hist_level) = 'never'
1303       ENDIF
1304       !
1305       IF (is_omp_root) THEN
1306          IF ( .NOT. almaoutput ) THEN
1307             !-
1308             IF ( grid_type == regular_lonlat ) THEN
1309#ifdef CPP_PARA
1310                CALL histbeg(histname2, iim, lon_rect, jjm, lat_rect, 1, iim, 1, jjm, &
1311                     &     istp_old, date0, dt, hori_id2, hist2_id,orch_domain_id)
1312#else
1313                CALL histbeg(histname2, iim, lon_rect, jjm, lat_rect, 1, iim, 1, jjm, &
1314                     &     istp_old, date0, dt, hori_id2, hist2_id)
1315#endif
1316                IF (printlev >= 2) WRITE(numout,*)  'HISTBEG2 --->',istp_old,date0,dt,dw2,hist2_id
1317             ELSE
1318#ifdef CPP_PARA
1319                CALL histbeg(histname2, iim, lon, jjm, lat, 1, iim, 1, jjm, &
1320                     &     istp_old, date0, dt, hori_id2, hist2_id,domain_id=orch_domain_id)
1321#else
1322                CALL histbeg(histname2, iim, lon, jjm, lat, 1, iim, 1, jjm, &
1323                     &     istp_old, date0, dt, hori_id2, hist2_id)
1324#endif
1325             ENDIF
1326             !-
1327             CALL histvert(hist2_id, 'veget', 'Vegetation types', '1', &
1328                  &    nvm,   veg, vegax_id2)
1329             CALL histvert(hist2_id, 'laiax', 'Nb LAI', '1', &
1330                  &    nlai+1,   indlai, laiax_id2)
1331             CALL histvert(hist2_id, 'solth', 'Soil levels',      'm', &
1332                  &    ngrnd, znt, solax_id2)
1333             CALL histvert(hist2_id, 'soiltyp', 'Soil types',      '1', &
1334                  &    nstm, soltyp, soltax_id2)
1335             CALL histvert(hist2_id, 'nobio', 'Other surface types',      '1', &
1336                  &    nnobio, nobiotyp, nobioax_id2)
1337             CALL histvert(hist2_id, 'albtyp', 'Albedo Types',     '1', &
1338                  &    2, albtyp, albax_id2)
1339             CALL histvert(hist2_id, 'solay', 'Hydrol soil levels',      'm', &
1340                  &    nslm, solay, solayax_id2)
1341             !-
1342             !- SECHIBA_HISTLEVEL2 = 1
1343             !-
1344             CALL histdef(hist2_id, 'ptn', 'Deep ground temperature', 'K', &
1345                  & iim,jjm, hori_id2, ngrnd, 1, ngrnd, solax_id2, 32, avescatter2(2),  dt, dw2) 
1346
1347             CALL histdef(hist2_id, 'mrsos', "Moisture in Upper 0.1 m of Soil Column", "kg m-2", &
1348                  & iim,jjm, hori_id2, 1, 1, 1, -99, 32, avescatter2(2), dt,dw2)           
1349
1350             CALL histdef(hist2_id, 'mrso', "Total Soil Moisture Content", "kg m-2", &
1351                  & iim,jjm, hori_id2, 1, 1, 1, -99, 32, avescatter2(11), dt,dw2)
1352             
1353             CALL histdef(hist2_id, 'mrros', "Surface Runoff", "kg m-2 s-1", &
1354                  & iim,jjm, hori_id2, 1, 1, 1, -99, 32, fluxop_scinsec2(11), dt,dw2)
1355
1356             CALL histdef(hist2_id, 'mrro', "Total Runoff", "kg m-2 s-1", &
1357                  & iim,jjm, hori_id2, 1, 1, 1, -99, 32, fluxop_scinsec2(2), dt,dw2)     
1358
1359             !-
1360             !- SECHIBA_HISTLEVEL2 = 2
1361             !-
1362             CALL histdef(hist2_id, 'cdrag', 'Drag coefficient for LE and SH', '?',  &
1363                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(2), dt, dw2)
1364             CALL histdef(hist2_id, 'soilalb_vis', 'Soil Albedo visible', '1', &
1365                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(2), dt,dw2)
1366             CALL histdef(hist2_id, 'soilalb_nir', 'Soil Albedo near infrared', '1', &
1367                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(2), dt,dw2)
1368             CALL histdef(hist2_id, 'vegalb_vis', 'Vegetation Albedo visible', '1', &
1369                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(2), dt,dw2)
1370             CALL histdef(hist2_id, 'vegalb_nir', 'Vegetation Albedo near infrared', '1', &
1371                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(2), dt,dw2)
1372             CALL histdef(hist2_id, 'z0m', 'Surface roughness for momentum', 'm',  &
1373                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(2), dt, dw2)
1374             CALL histdef(hist2_id, 'z0h', 'Surface roughness for heat', 'm',  &
1375                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(2), dt, dw2)
1376             CALL histdef(hist2_id, 'coastalflow', 'Diffuse coastal flow', 'm^3/s', &
1377                  & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop_scinsec2(2), dt, dw2)
1378             CALL histdef(hist2_id, 'riverflow', 'River flow to the oceans', 'm^3/s', &
1379                  & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop_scinsec2(2), dt, dw2) 
1380             CALL histdef(hist2_id, 'tsol_rad', 'Radiative surface temperature', 'C', &
1381                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avecels2(2), dt, dw2)
1382             IF ( do_floodplains ) THEN
1383                CALL histdef(hist2_id, 'floodout', 'Flow out of floodplains', 'mm/d', &
1384                     & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop2(2), dt,dw2)
1385                CALL histdef(hist2_id, 'vevapflo', 'Floodplains evaporation', 'mm/d', &
1386                     & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop2(2), dt, dw2)
1387                CALL histdef(hist2_id, 'flood_frac', 'Flooded fraction', '1', &
1388                     & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(2), dt,dw2)
1389                CALL histdef(hist2_id, 'reinfiltration', 'Reinfiltration from floodplains', 'mm/d', &
1390                     & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop2(2), dt,dw2)
1391             ENDIF
1392             CALL histdef(hist2_id, 'vevapnu', 'Bare soil evaporation', 'mm/d', &
1393                  & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop2(2), dt, dw2)
1394             CALL histdef(hist2_id, 'temp_sol', 'New Surface Temperature', 'C', &
1395                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avecels2(2), dt, dw2)
1396             CALL histdef(hist2_id, 'qsurf', 'Near surface specific humidity', 'g/g',  &
1397                  & iim,jjm, hori_id2, 1,1,1, -99, 32, ave2(2), dt, dw2)
1398             CALL histdef(hist2_id, 'albedo', 'Albedo', '1', &
1399                  & iim,jjm, hori_id2, 2,1,2, albax_id2, 32, avescatter2(2), dt, dw2)
1400             CALL histdef(hist2_id, 'fluxsens', 'Sensible Heat Flux', 'W/m^2',  &
1401                  & iim,jjm, hori_id2, 1,1,1, -99, 32, ave2(2), dt, dw2)
1402             CALL histdef(hist2_id, 'fluxlat', 'Latent Heat Flux', 'W/m^2',  &
1403                  & iim,jjm, hori_id2, 1,1,1, -99, 32, ave2(2), dt, dw2)
1404             CALL histdef(hist2_id, 'emis', 'Surface emissivity', '1', &
1405                  & iim,jjm, hori_id2, 1,1,1, -99, 32, ave2(2), dt, dw2)
1406             !-
1407             !- SECHIBA_HISTLEVEL2 = 3
1408             !-
1409             CALL histdef(hist2_id, 'evap', 'Evaporation', 'mm/d', &
1410                  & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop2(3), dt, dw2)
1411             CALL histdef(hist2_id, 'rain', 'Rainfall', 'mm/d',  &
1412                  & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop2(3), dt, dw2)
1413             CALL histdef(hist2_id, 'snowf', 'Snowfall', 'mm/d',  &
1414                  & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop2(3), dt, dw2)
1415             CALL histdef(hist2_id, 'netrad', 'Net radiation', 'W/m^2',  &
1416                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(3), dt, dw2)
1417             CALL histdef(hist2_id, 'lai', 'Leaf Area Index', '1', &
1418                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(3), dt, dw2)
1419             IF ( river_routing ) THEN
1420                CALL histdef(hist2_id, 'basinmap', 'Aproximate map of the river basins', ' ', &
1421                     & iim,jjm, hori_id2, 1,1,1, -99, 32, once2(3), dt, dw2) 
1422                CALL histdef(hist2_id, 'nbrivers', 'Number or rivers in the outflow grid box', ' ', &
1423                     & iim,jjm, hori_id2, 1,1,1, -99, 32, once2(3), dt, dw2) 
1424             ENDIF
1425
1426             !-
1427             !- SECHIBA_HISTLEVEL2 = 4
1428             !-
1429             CALL histdef(hist2_id, 'subli', 'Sublimation', 'mm/d', &
1430                  & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop2(4), dt, dw2)
1431             CALL histdef(hist2_id, 'runoff', 'Surface runoff', 'mm/d', &
1432                  & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop2(4), dt, dw2)
1433             CALL histdef(hist2_id, 'drainage', 'Deep drainage', 'mm/d', &
1434                  & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop2(4), dt, dw2)
1435             IF ( river_routing ) THEN
1436                CALL histdef(hist2_id, 'riversret', 'Return from endorheic rivers', 'mm/d', &
1437                     & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop2(4), dt, dw2)
1438                CALL histdef(hist2_id, 'hydrographs', 'Hydrographs of gridbox outflow', 'm^3/s', &
1439                     & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop_scinsec2(4), dt, dw2)
1440             ENDIF
1441             CALL histdef(hist2_id, 'evapnu_soil', 'Bare soil evap for soil type', 'mm/d', &
1442                  & iim,jjm, hori_id2, nstm, 1, nstm, soltax_id2, 32, fluxop2(4), dt, dw2)
1443             CALL histdef(hist2_id, 'drainage_soil', 'Drainage for soil type', 'mm/d', &
1444                  & iim,jjm, hori_id2, nstm, 1, nstm, soltax_id2, 32, fluxop2(4), dt, dw2)
1445             CALL histdef(hist2_id, 'transpir_soil', 'Transpir 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, 'runoff_soil', 'Runoff 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, 'tair', 'Air Temperature', 'K',  &
1450                  & iim,jjm, hori_id2, 1,1,1, -99, 32, ave2(4), dt, dw2)
1451             CALL histdef(hist2_id, 'qair', 'Air humidity', 'g/g',  &
1452                  & iim,jjm, hori_id2, 1,1,1, -99, 32, ave2(4), dt, dw2)
1453            CALL histdef(hist2_id, 'alb_vis', 'Albedo visible', '1', &
1454                  & iim,jjm, hori_id2, 1,1,1, -99, 32, ave2(4), dt, dw2)
1455             CALL histdef(hist2_id, 'alb_nir', 'Albedo near infrared', '1', &
1456                  & iim,jjm, hori_id2, 1,1,1, -99, 32, ave2(4), dt, dw2)
1457             CALL histdef(hist2_id, 'roughheight', 'Effective roughness height', 'm',  &
1458                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(4), dt, dw2)
1459             CALL histdef(hist2_id, 'transpir', 'Transpiration', 'mm/d', &
1460                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, fluxop2(4), dt, dw2)
1461             CALL histdef(hist2_id, 'inter', 'Interception loss', 'mm/d', &
1462                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, fluxop2(4), dt, dw2)
1463             !-
1464             !- SECHIBA_HISTLEVEL2 = 5
1465             !-
1466             CALL histdef(hist2_id, 'tsol_max', 'Maximum Surface Temperature',&
1467                  & 'C', iim,jjm, hori_id2, 1,1,1, -99, 32, tmaxcels2(5), dt, dw2)
1468             CALL histdef(hist2_id, 'tsol_min', 'Minimum Surface Temperature',&
1469                  & 'C', iim,jjm, hori_id2, 1,1,1, -99, 32, tmincels2(5), dt, dw2)
1470             CALL histdef(hist2_id, 'snow', 'Snow mass', 'kg/m^2', &
1471                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(5), dt, dw2)
1472             CALL histdef(hist2_id, 'snowage', 'Snow age', '?', &
1473                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(5), dt, dw2)
1474             CALL histdef(hist2_id, 'snownobio', 'Snow on other surfaces', 'kg/m^2', &
1475                  & iim,jjm, hori_id2, nnobio,1, nnobio, nobioax_id2, 32, avescatter2(5), dt, dw2)
1476             CALL histdef(hist2_id, 'snownobioage', 'Snow age on other surfaces', 'd', &
1477                  & iim,jjm, hori_id2, nnobio,1, nnobio, nobioax_id2, 32, avescatter2(5), dt, dw2)
1478             CALL histdef(hist2_id, 'vegetfrac', 'Fraction of vegetation', '1', &
1479                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(5), dt, dw2)
1480             CALL histdef(hist2_id, 'maxvegetfrac', 'Maximum fraction of vegetation', '1', &
1481                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(5), dt, dw2)
1482             CALL histdef(hist2_id, 'nobiofrac', 'Fraction of other surface types', '1', &
1483                  & iim,jjm, hori_id2, nnobio, 1, nnobio, nobioax_id2, 32, avescatter2(5), dt, dw2)
1484
1485             DO jst=1,nstm
1486               
1487                ! var_name= "mc_1" ... "mc_3"
1488                WRITE (var_name,"('moistc_',i1)") jst
1489                CALL histdef(hist2_id, var_name, 'Soil Moisture profile for soil type', 'm3/m3', &
1490                     & iim,jjm, hori_id2, nslm, 1, nslm, solayax_id2, 32, avescatter2(5), dt, dw2)
1491               
1492                ! var_name= "vegetsoil_1" ... "vegetsoil_3"
1493                WRITE (var_name,"('vegetsoil_',i1)") jst
1494                CALL histdef(hist2_id, var_name, 'Fraction of vegetation on soil types', '%', &
1495                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(5), dt, dw2)
1496               
1497                ! var_name= "kfact_root_1" ... "kfact_root_3"
1498                WRITE (var_name,"('kfactroot_',i1)") jst
1499                CALL histdef(hist2_id, var_name, 'Root fraction profile for soil type', '%', &
1500                     & iim,jjm, hori_id2, nslm, 1, nslm, solayax_id2, 32, avescatter2(5), dt,dw2)
1501             ENDDO
1502               
1503             !-
1504             !- SECHIBA_HISTLEVEL2 = 6
1505             !-
1506             CALL histdef(hist2_id, 'humtot', 'Total Soil Moisture', 'Kg/m^2', &
1507                  & iim,jjm, hori_id2, 1, 1, 1, -99, 32, avescatter2(6), dt, dw2)
1508             CALL histdef(hist2_id, 'humtot_soil', 'Soil Moisture for soil type', 'Kg/m^2', &
1509                  & iim,jjm, hori_id2, nstm, 1, nstm, soltax_id2, 32, avescatter2(6), dt, dw2)
1510             CALL histdef(hist2_id, 'qsintveg', 'Water on canopy', 'Kg/m^2', &
1511                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(6), dt, dw2)
1512             CALL histdef(hist2_id, 'rstruct', 'Structural resistance', 's/m', &
1513                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(6), dt, dw2)
1514             CALL histdef(hist2_id, 'gpp', 'Net assimilation of carbon by the vegetation', 'gC/m^2/s', &
1515                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, fluxop_scinsec2(6), dt,dw2)
1516
1517             IF ( ok_stomate ) THEN
1518                CALL histdef(hist2_id, 'nee', 'Net Ecosystem Exchange', 'kgC/m^2/s', &
1519                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, fluxop_scinsec2(6), dt,dw2)
1520                CALL histdef(hist2_id, 'maint_resp', 'Maintenance respiration', 'gC/m^2/s', &
1521                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, fluxop_scinsec2(6), dt,dw2)
1522                CALL histdef(hist2_id, 'hetero_resp', 'Heterotrophic respiration', 'gC/m^2/s', &
1523                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, fluxop_scinsec2(6), dt,dw2)
1524                CALL histdef(hist2_id, 'growth_resp', 'Growth respiration', 'gC/m^2/s', &
1525                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, fluxop_scinsec2(6), dt, dw2)
1526                CALL histdef(hist2_id, 'npp', 'Net Primary Production', 'gC/m^2/s', &
1527                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, fluxop_scinsec2(6), dt, dw2)
1528             ENDIF
1529             CALL histdef(hist2_id, 'precisol', 'Throughfall', 'mm/d',  &
1530                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, fluxop2(6), dt, dw2)
1531             CALL histdef(hist2_id, 'drysoil_frac', 'Fraction of visibly dry soil', '1',  &
1532                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(6), dt, dw2)
1533             CALL histdef(hist2_id, 'evapot', 'Potential evaporation', 'mm/d',  &
1534                  & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop2(6), dt, dw2)
1535             CALL histdef(hist2_id, 'evapot_corr', 'Potential evaporation', 'mm/d',  &
1536                  & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop2(6), dt, dw2)
1537             CALL histdef(hist2_id, 'snowmelt', 'snow melt', 'mm/d', &
1538                  & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop2(6), dt, dw2)
1539
1540             !-
1541             !- SECHIBA_HISTLEVEL2 = 7
1542             !-
1543             CALL histdef(hist2_id, 'swnet', 'Net solar radiation', 'W/m^2',  &
1544                  & iim,jjm, hori_id2, 1,1,1, -99, 32, ave2(7), dt, dw2)
1545             CALL histdef(hist2_id, 'swdown', 'Incident solar radiation', 'W/m^2',  &
1546                  & iim,jjm, hori_id2, 1,1,1, -99, 32, ave2(7), dt, dw2)
1547             CALL histdef(hist2_id, 'lwdown', 'Absorbed downward longwave radiation', 'W/m^2',  &
1548                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(7), dt, dw2)
1549             CALL histdef(hist2_id, 'lwnet', 'Net surface longwave radiation', 'W/m^2',  &
1550                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(7), dt, dw2)
1551             !-
1552             !- SECHIBA_HISTLEVEL2 = 8
1553             !-
1554             IF ( river_routing ) THEN
1555                CALL histdef(hist2_id, 'fastr', 'Fast flow reservoir', 'kg/m^2', &
1556                     & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(8), dt, dw2)
1557                CALL histdef(hist2_id, 'slowr', 'Slow flow reservoir', 'kg/m^2', &
1558                     & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(8), dt, dw2)
1559                CALL histdef(hist2_id, 'streamr', 'Stream flow reservoir', 'kg/m^2', &
1560                     & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(8), dt, dw2)
1561                CALL histdef(hist2_id, 'floodr', 'Floodplains reservoir', 'kg/m^2', &
1562                     & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(8), dt,dw2)
1563                CALL histdef(hist2_id, 'floodh', 'Floodplains height', 'mm', &
1564                     & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(8), dt,dw2)
1565                CALL histdef(hist2_id, 'pondr', 'Ponds reservoir', 'kg/m^2', &
1566                     & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(8), dt,dw2)
1567                CALL histdef(hist2_id, 'lakevol', 'Volume in lake reservoir', 'kg/m^2', &
1568                     & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(8), dt, dw2)
1569                IF ( do_irrigation ) THEN
1570                   CALL histdef(hist2_id, 'irrigation', 'Net irrigation', 'mm/d', &
1571                        & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop2(8), dt, dw2)
1572                   CALL histdef(hist2_id, 'netirrig', 'Net irrigation requirement', 'mm/d', &
1573                        & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop2(8), dt, dw2)
1574                   CALL histdef(hist2_id, 'irrigmap', 'Map of irrigated areas', 'm^2', &
1575                        & iim,jjm, hori_id2, 1,1,1, -99, 32, once2(8), dt, dw2)
1576                ENDIF
1577                CALL histdef(hist2_id, 'floodmap', 'Map of floodplains', 'm^2', &
1578                     & iim,jjm, hori_id2, 1,1,1, -99, 32, once2(8), dt,dw2)
1579                CALL histdef(hist2_id, 'swampmap', 'Map of swamps', 'm^2', &
1580                  & iim,jjm, hori_id2, 1,1,1, -99, 32, once2(8), dt,dw2)
1581             ENDIF
1582             !-
1583             !- SECHIBA_HISTLEVEL2 = 9
1584             !-
1585             CALL histdef(hist2_id, 'beta', 'Beta Function', '1',  &
1586                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(9), dt, dw2)
1587             CALL histdef(hist2_id, 'raero', 'Aerodynamic resistance', 's/m',  &
1588                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(9), dt, dw2)
1589             CALL histdef(hist2_id, 'Wind', 'Wind speed', 'm/s',  &
1590                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(9), dt, dw2)
1591             CALL histdef(hist2_id, 'qsatt' , 'Surface saturated humidity', 'g/g', &
1592                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(9), dt, dw2)
1593             CALL histdef(hist2_id, 'vbeta1', 'Beta for sublimation', '1',  &
1594                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(9), dt, dw2)
1595             CALL histdef(hist2_id, 'vbeta4', 'Beta for bare soil', '1',  &
1596                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(9), dt, dw2)
1597             CALL histdef(hist2_id, 'gsmean', 'mean stomatal conductance', 'mol/m2/s', &
1598                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(9), dt, dw2)
1599             CALL histdef(hist2_id, 'vbeta5', 'Beta for floodplains', '1',  &
1600                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(9), dt, dw2)
1601             CALL histdef(hist2_id, 'reinf_slope', 'Slope index for each grid box', '1', &
1602                  & iim,jjm, hori_id2, 1,1,1, -99, 32, once2(9),  dt,dw2)
1603             CALL histdef(hist2_id, 'soilindex', 'Soil index', '1', &
1604                  & iim,jjm, hori_id2, 1, 1, 1, -99, 32, once2(9),  dt,dw2)
1605             CALL histdef(hist2_id, 'humrel', 'Soil moisture stress', '-',  &
1606                  & iim,jjm, hori_id2, nvm,1,nvm, vegax_id2, 32, avescatter2(9), dt, dw2)
1607             !-
1608             !- SECHIBA_HISTLEVEL2 = 10
1609             !-
1610             CALL histdef(hist2_id, 'cimean', 'Stomatal CO2 concentation', 'mmole/m2/s', &
1611                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt, dw2)
1612             CALL histdef(hist2_id, 'vbeta3', 'Beta for Transpiration', 'mm/d', &
1613                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt, dw2)
1614             CALL histdef(hist2_id, 'rveget', 'Canopy resistance', 's/m', &
1615                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt, dw2)
1616             CALL histdef(hist2_id,'vbeta2','Beta for Interception loss','mm/d', &
1617                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt, dw2)
1618             CALL histdef(hist2_id, 'qsintmax', 'Maximum Interception capacity', 'Kg/m^2', &
1619                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt, dw2)
1620             
1621             IF ( ok_bvoc ) THEN
1622                CALL histdef(hist2_id, 'PAR', 'PAR', 'umol phot/m^2/s',  &
1623                     & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(10), dt,dw2)
1624                IF ( ok_radcanopy ) THEN
1625                   CALL histdef(hist2_id, 'PARsun', 'Sunlit Leaf PAR', 'umol phot/m^2/s', &
1626                        & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
1627                   CALL histdef(hist2_id, 'PARsh', 'Shaded Leaf Area PAR', 'umol phot/m^2/s', &
1628                        & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
1629                   CALL histdef(hist2_id, 'laisun', 'Sunlit Leaf Area Index', '1', &
1630                        & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
1631                   CALL histdef(hist2_id, 'laish', 'Shaded Leaf Area Index', '1', &
1632                        & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
1633                   CALL histdef(hist2_id, 'Fdf', 'Fdf', '1',  &
1634                        & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(10), dt,dw2)
1635                   IF ( ok_multilayer ) then
1636                      CALL histdef(hist2_id, 'PARsuntab', 'Sunlit Leaf PAR', 'umol phot/m^2/s', &
1637                           & iim,jjm, hori_id2, nlai+1, 1, nlai+1, laiax_id2, 32, avescatter2(10), dt,dw2)
1638                      CALL histdef(hist2_id, 'PARshtab', 'Shaded Leaf Area PAR', 'umol phot/m^2/s', &
1639                           & iim,jjm, hori_id2, nlai+1, 1, nlai+1, laiax_id2, 32, avescatter2(10), dt,dw2)
1640                   ENDIF
1641                   CALL histdef(hist2_id, 'coszang', 'coszang', '1',  &
1642                        & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(10), dt,dw2)
1643                   CALL histdef(hist2_id, 'PARdf', 'PARdf', '1',  &
1644                        & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(10), dt,dw2)
1645                   CALL histdef(hist2_id, 'PARdr', 'PARdr', '1',  &
1646                        & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(10), dt,dw2)
1647                   CALL histdef(hist2_id, 'Trans', 'Trans', '1',  &
1648                        & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(10), dt,dw2)
1649                END IF
1650               
1651                CALL histdef(hist2_id, 'flx_fertil_no', 'flx_fertil_no', 'ngN/m^2/s', &
1652                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
1653                CALL histdef(hist2_id, 'CRF', 'CRF', '1', &
1654                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
1655                CALL histdef(hist2_id, 'flx_co2_bbg_year', 'flx_co2_bbg_year', 'kgC/m^2/yr ', &
1656                     & iim,jjm, hori_id2, 1,1,1, -99, 32, once2(10), dt,dw2) 
1657                CALL histdef(hist2_id, 'N_qt_WRICE_year', 'N_qt_WRICE_year', 'kgN/yr ', &
1658                     & iim,jjm, hori_id2, 1,1,1, -99, 32, once2(10), dt,dw2) 
1659                CALL histdef(hist2_id, 'N_qt_OTHER_year', 'N_qt_OTHER_year', 'kgN/yr ', &
1660                     & iim,jjm, hori_id2, 1,1,1, -99, 32, once2(10), dt,dw2) 
1661                CALL histdef(hist2_id, 'flx_iso', 'flx_iso', 'kgC/m^2/s', &
1662                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
1663                CALL histdef(hist2_id, 'flx_mono', 'flx_mono', 'kgC/m^2/s',&
1664                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
1665                CALL histdef(hist2_id, 'flx_apinen', 'flx_apinen', 'kgC/m^2/s',&
1666                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
1667                CALL histdef(hist2_id, 'flx_bpinen', 'flx_bpinen', 'kgC/m^2/s',&
1668                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
1669                CALL histdef(hist2_id, 'flx_limonen', 'flx_limonen', 'kgC/m^2/s',&
1670                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
1671                CALL histdef(hist2_id, 'flx_myrcen', 'flx_myrcen', 'kgC/m^2/s',&
1672                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
1673                CALL histdef(hist2_id, 'flx_sabinen', 'flx_sabinen', 'kgC/m^2/s',&
1674                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
1675                CALL histdef(hist2_id, 'flx_camphen', 'flx_camphen', 'kgC/m^2/s',&
1676                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
1677                CALL histdef(hist2_id, 'flx_3caren', 'flx_3caren', 'kgC/m^2/s',&
1678                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
1679                CALL histdef(hist2_id, 'flx_tbocimen', 'flx_tbocimen', 'kgC/m^2/s',&
1680                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
1681                CALL histdef(hist2_id, 'flx_othermono', 'flx_othermono', 'kgC/m^2/s',&
1682                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
1683                CALL histdef(hist2_id, 'flx_sesquiter', 'flx_sesquiter', 'kgC/m^2/s',&
1684                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
1685                CALL histdef(hist2_id, 'flx_ORVOC', 'flx_ORVOC', 'kgC/m^2/s',&
1686                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
1687                CALL histdef(hist2_id, 'flx_MBO', 'flx_MBO', 'kgC/m^2/s',&
1688                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
1689                CALL histdef(hist2_id, 'flx_methanol', 'flx_methanol', 'kgC/m^2/s',&
1690                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
1691                CALL histdef(hist2_id, 'flx_acetone', 'flx_acetone', 'kgC/m^2/s',&
1692                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(1), dt,dw2)   !! LDF TEST modificato a 1... !!
1693                CALL histdef(hist2_id, 'flx_acetal', 'flx_acetal', 'kgC/m^2/s',&
1694                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(1), dt,dw2)   !! LDF TEST modificato a 1... !!
1695                CALL histdef(hist2_id, 'flx_formal', 'flx_formal', 'kgC/m^2/s',&
1696                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
1697                CALL histdef(hist2_id, 'flx_acetic', 'flx_acetic', 'kgC/m^2/s',&
1698                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
1699                CALL histdef(hist2_id, 'flx_formic', 'flx_formic', 'kgC/m^2/s',&
1700                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
1701                CALL histdef(hist2_id, 'flx_no_soil', 'flx_no_soil', 'ngN/m^2/s',&
1702                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
1703                CALL histdef(hist2_id, 'flx_no', 'flx_no', 'ngN/m^2/s',&
1704                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
1705             ENDIF
1706         ELSE 
1707             !-
1708             !- This is the ALMA convention output now
1709             !-
1710             !-
1711             IF ( grid_type == regular_lonlat ) THEN
1712#ifdef CPP_PARA
1713                CALL histbeg(histname2, iim, lon_rect, jjm, lat_rect, 1, iim, 1, jjm, &
1714                     &     istp_old, date0, dt, hori_id2, hist2_id,orch_domain_id)
1715#else
1716                CALL histbeg(histname2, iim, lon_rect, jjm, lat_rect, 1, iim, 1, jjm, &
1717                     &     istp_old, date0, dt, hori_id2, hist2_id)
1718#endif
1719                IF (printlev >= 2) WRITE(numout,*)  'HISTBEG2 --->',istp_old,date0,dt,dw2,hist2_id
1720             ELSE
1721#ifdef CPP_PARA
1722                CALL histbeg(histname2, iim, lon, jjm, lat, 1, iim, 1, jjm, &
1723                     &     istp_old, date0, dt, hori_id2, hist2_id,domain_id=orch_domain_id)
1724#else
1725                CALL histbeg(histname2, iim, lon, jjm, lat, 1, iim, 1, jjm, &
1726                     &     istp_old, date0, dt, hori_id2, hist2_id)
1727#endif
1728             ENDIF
1729             !-
1730             CALL histvert(hist2_id, 'veget', 'Vegetation types', '1', &
1731                  &    nvm,   veg, vegax_id2)
1732             CALL histvert(hist2_id, 'solth', 'Soil levels',      'm', &
1733                  &    ngrnd, znt, solax_id2)
1734             CALL histvert(hist2_id, 'soiltyp', 'Soil types',      '1', &
1735                  &    nstm, soltyp, soltax_id2)
1736             CALL histvert(hist2_id, 'nobio', 'Other surface types',      '1', &
1737                  &    nnobio, nobiotyp, nobioax_id2)
1738             CALL histvert(hist2_id, 'solay', 'Hydrol soil levels',      'm', &
1739                  &    nslm, diaglev(1:nslm), solayax_id2)
1740
1741             !-
1742             !-  Vegetation
1743             !-
1744             CALL histdef(hist2_id, 'vegetfrac', 'Fraction of vegetation', '1', &
1745                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(3), dt, dw2)
1746             CALL histdef(hist2_id, 'maxvegetfrac', 'Maximum fraction of vegetation', '1', &
1747                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(3), dt, dw2)
1748             CALL histdef(hist2_id, 'nobiofrac', 'Fraction of other surface types', '1', &
1749                  & iim,jjm, hori_id2, nnobio, 1, nnobio, nobioax_id2, 32, avescatter2(3), dt, dw2)
1750             !-
1751             !-  General energy balance
1752             !-
1753             CALL histdef(hist2_id, 'SWnet', 'Net shortwave radiation', 'W/m^2',  &
1754                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(1), dt, dw2)
1755             CALL histdef(hist2_id, 'LWnet', 'Net longwave radiation', 'W/m^2',  &
1756                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(1), dt, dw2)
1757             CALL histdef(hist2_id, 'Qh', 'Sensible heat flux', 'W/m^2',  &
1758                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(1), dt, dw2)
1759             CALL histdef(hist2_id, 'Qle', 'Latent heat flux', 'W/m^2',  &
1760                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(1), dt, dw2)
1761             CALL histdef(hist2_id, 'Qg', 'Ground heat flux', 'W/m^2',  &
1762                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(1), dt, dw2)
1763             CALL histdef(hist2_id, 'Qv', 'Energy of sublimation', 'W/m^2',  &
1764                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(5), dt, dw2)
1765             CALL histdef(hist2_id, 'DelSurfHeat', 'Change in surface layer heat', 'J/m^2',  &
1766                  & iim,jjm, hori_id2, 1,1,1, -99, 32, sumscatter2(7), dt, dw2)
1767             CALL histdef(hist2_id, 'DelColdCont', 'Change in snow surface layer cold content', 'J/m^2',  &
1768                  & iim,jjm, hori_id2, 1,1,1, -99, 32, sumscatter2(7), dt, dw2)
1769             !-
1770             !- General water balance
1771             !-
1772             CALL histdef(hist2_id, 'Snowf', 'Snowfall rate', 'kg/m^2/s',  &
1773                  & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop_scinsec2(1), dt, dw2)
1774             CALL histdef(hist2_id, 'Rainf', 'Rainfall rate', 'kg/m^2/s',  &
1775                  & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop_scinsec2(1), dt, dw2)
1776             CALL histdef(hist2_id, 'Evap', 'Total Evapotranspiration', 'kg/m^2/s', &
1777                  & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop_scinsec2(1), dt, dw2)
1778             CALL histdef(hist2_id, 'Qs', 'Surface runoff', 'kg/m^2/s', &
1779                  & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop_scinsec2(1), dt, dw2)
1780             CALL histdef(hist2_id, 'Qsb', 'Sub-surface runoff', 'kg/m^2/s', &
1781                  & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop_scinsec2(1), dt, dw2)
1782             CALL histdef(hist2_id, 'Qsm', 'Snowmelt', 'kg/m^2/s', &
1783                  & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop_scinsec2(1), dt, dw2)
1784             CALL histdef(hist2_id, 'DelSoilMoist', 'Change in soil moisture', 'kg/m^2',  &
1785                  & iim,jjm, hori_id2, 1, 1, 1, -99, 32, sumscatter2(7), dt, dw2)
1786             CALL histdef(hist2_id, 'DelSurfStor', 'Change in Surface Water Storage','kg/m^2',&
1787                  & iim,jjm, hori_id2, 1, 1, 1, -99, 32, sumscatter2(7), dt,dw2)
1788             CALL histdef(hist2_id, 'DelIntercept', 'Change in interception storage', 'kg/m^2',  &
1789                  & iim,jjm, hori_id2, 1, 1, 1, -99, 32, sumscatter2(7), dt, dw2)
1790             CALL histdef(hist2_id, 'DelSWE', 'Change in interception storage Snow Water Equivalent', 'kg/m^2',  &
1791                  & iim,jjm, hori_id2, 1, 1, 1, -99, 32, sumscatter2(7), dt, dw2)
1792             !-
1793             !- Surface state
1794             !-
1795             CALL histdef(hist2_id, 'AvgSurfT', 'Average surface temperature', 'K', &
1796                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(1), dt, dw2)
1797             CALL histdef(hist2_id, 'RadT', 'Surface radiative temperature', 'K', &
1798                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(5), dt, dw2)
1799             CALL histdef(hist2_id, 'Albedo', 'Albedo', '1', &
1800                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(7), dt, dw2)
1801             CALL histdef(hist2_id, 'SurfStor', 'Surface Water Storage','kg/m^2',  &
1802                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(1), dt, dw2)
1803             CALL histdef(hist2_id, 'SWE', 'Snow Water Equivalent', 'kg/m^2', &
1804                  & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter2(1), dt,dw2)
1805             !!-
1806             !-  Sub-surface state
1807             !-
1808             CALL histdef(hist2_id, 'SoilMoist', '3D average layer soil moisture', 'kg/m^2',  &
1809                  & iim,jjm, hori_id2, nslm, 1, nslm, solayax_id2, 32, avescatter2(7), dt, dw2)
1810             CALL histdef(hist2_id, 'SoilWet', 'Total soil wetness', '-',  &
1811                  & iim,jjm, hori_id2, 1, 1, 1, -99, 32, avescatter2(1), dt, dw2)
1812             CALL histdef(hist2_id, 'SoilTemp', 'Soil temperature profile', 'K', &
1813                  & iim,jjm, hori_id2, ngrnd, 1, ngrnd, solax_id2, 32, avescatter2(7), dt, dw2)
1814             !-
1815             !-  Evaporation components
1816             !-
1817             CALL histdef(hist2_id, 'PotEvap', 'Potential evapotranspiration', 'kg/m^2/s', &
1818                  & iim,jjm, hori_id2, 1, 1, 1, -99, 32, fluxop_scinsec2(1), dt, dw2)
1819             CALL histdef(hist2_id, 'ECanop', 'Interception evaporation', 'kg/m^2/s', &
1820                  & iim,jjm, hori_id2, 1, 1, 1, -99, 32, fluxop_scinsec2(5), dt, dw2)
1821             CALL histdef(hist2_id, 'TVeg', 'Transpiration', 'kg/m^2/s', &
1822                  & iim,jjm, hori_id2, 1, 1, 1, -99, 32, fluxop_scinsec2(5), dt, dw2)
1823             CALL histdef(hist2_id, 'ESoil', 'Bare soil evaporation', 'kg/m^2/s', &
1824                  & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop_scinsec2(5), dt, dw2)
1825             CALL histdef(hist2_id, 'RootMoist','Root zone soil water', 'kg/m^2',  &
1826                  & iim,jjm, hori_id2, 1, 1, 1, -99, 32, avescatter2(1), dt, dw2)
1827             CALL histdef(hist2_id, 'SubSnow','Snow sublimation','kg/m^2/s', &
1828                  & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop_scinsec2(1), dt, dw2)
1829             CALL histdef(hist2_id, 'ACond', 'Aerodynamic conductance', 'm/s',  &
1830                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(5), dt, dw2)
1831             !-
1832             !-
1833             !-  Cold Season Processes
1834             !-
1835             CALL histdef(hist2_id, 'SnowFrac', 'Snow cover fraction', '1',  &
1836                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(7), dt, dw2)
1837             CALL histdef(hist2_id, 'SAlbedo', 'Snow albedo', '1', &
1838                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(7), dt, dw2)
1839             !-
1840             !- Hydrologic variables
1841             !-
1842             IF ( river_routing ) THEN
1843                !
1844                IF (do_floodplains) THEN
1845                   CALL histdef(hist2_id, 'EWater', 'Open water evaporation', 'kg/m^2/s', &
1846                        & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop_scinsec2(5), dt, dw2)
1847                   CALL histdef(hist2_id, 'FloodFrac', 'Floodplain Fraction', '-', &
1848                        & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(1), dt,dw2)
1849                ENDIF
1850                !
1851                CALL histdef(hist2_id, 'IrrigationMap', 'Map of irrigated areas', 'm^2', &
1852                     & iim,jjm, hori_id2, 1,1,1, -99, 32, once2(1), dt, dw2)
1853                CALL histdef(hist2_id, 'FloodplainsMap', 'Map of flooded areas', 'm^2', &
1854                     & iim,jjm, hori_id2, 1,1,1, -99, 32, once2(1), dt,dw2)
1855                CALL histdef(hist2_id, 'SwampMap', 'Map of swamp areas', 'm^2', &
1856                  & iim,jjm, hori_id2, 1,1,1, -99, 32, once2(1), dt,dw2)
1857                CALL histdef(hist2_id, 'Dis', 'Simulated River Discharge', 'm^3/s', &
1858                     & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop_scinsec2(1), dt,dw2)
1859             ENDIF
1860             !-
1861             !-
1862             !-
1863             CALL histdef(hist2_id, 'humrel', 'Soil moisture stress', '-',  &
1864                  & iim,jjm, hori_id2, nvm,1,nvm, vegax_id2, 32, avescatter2(9), dt, dw2)
1865             !-
1866             !-  The carbon budget
1867             !-
1868             CALL histdef(hist2_id, 'GPP', 'Net assimilation of carbon by the vegetation', 'gC/m^2/s', &
1869                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, fluxop_scinsec2(1), dt, dw2)
1870
1871             IF ( ok_stomate ) THEN
1872                CALL histdef(hist2_id, 'NEE', 'Net Ecosystem Exchange', 'gC/m^2/s', &
1873                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, fluxop_scinsec2(1), dt,dw2)
1874                CALL histdef(hist2_id, 'maint_resp', 'Maintenance respiration', 'gC/m^2/s', &
1875                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, fluxop_scinsec2(1), dt,dw2)
1876                CALL histdef(hist2_id, 'hetero_resp', 'Heterotrophic respiration', 'gC/m^2/s', &
1877                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, fluxop_scinsec2(1), dt,dw2)
1878                CALL histdef(hist2_id, 'growth_resp', 'Growth respiration', 'gC/m^2/s', &
1879                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, fluxop_scinsec2(1), dt, dw2)
1880                CALL histdef(hist2_id, 'npp', 'Net Primary Production', 'gC/m^2/s', &
1881                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, fluxop_scinsec2(1), dt, dw2)
1882             ENDIF
1883             !
1884          ENDIF
1885          !-
1886          CALL histdef(hist2_id, 'LandPoints', 'Land Points', '1', &
1887               & iim,jjm, hori_id2, 1,1,1, -99, 32, once2(10), dt, dw2) 
1888          CALL histdef(hist2_id, 'Areas', 'Mesh areas', 'm2', &
1889               & iim,jjm, hori_id2, 1,1,1, -99, 32, once2(1), dt, dw2)
1890          CALL histdef(hist2_id, 'Contfrac', 'Continental fraction', '1', &
1891               & iim,jjm, hori_id2, 1,1,1, -99, 32, once2(1), dt, dw2)
1892          !-
1893          ! Write the names of the pfts in the high frequency sechiba history files
1894          global_attribute="PFT_name"
1895          DO i=1,nvm
1896             WRITE(global_attribute(9:10),"(I2.2)") i
1897             CALL histglobal_attr(hist2_id, global_attribute, PFT_name(i))
1898          ENDDO
1899          !-
1900          CALL histend(hist2_id)
1901      ENDIF
1902  ENDIF
1903
1904    !-
1905    !=====================================================================
1906    !- 3.2 STOMATE's history file
1907    !=====================================================================
1908    IF ( ok_stomate ) THEN
1909       !-
1910       ! STOMATE IS ACTIVATED
1911       !-
1912       !Config Key   = STOMATE_OUTPUT_FILE
1913       !Config Desc  = Name of file in which STOMATE's output is going to be written
1914       !Config If    = OK_STOMATE
1915       !Config Def   = stomate_history.nc
1916       !Config Help  = This file is going to be created by the model
1917       !Config         and will contain the output from the model.
1918       !Config         This file is a truly COADS compliant netCDF file.
1919       !Config         It will be generated by the hist software from
1920       !Config         the IOIPSL package.
1921       !Config Units = [FILE]
1922       !-
1923       stom_histname='stomate_history.nc'
1924       CALL getin_p('STOMATE_OUTPUT_FILE', stom_histname)       
1925       IF (printlev >= 2) WRITE(numout,*) 'STOMATE_OUTPUT_FILE', TRIM(stom_histname)
1926       !-
1927       !Config Key   = STOMATE_HIST_DT
1928       !Config Desc  = STOMATE history time step
1929       !Config If    = OK_STOMATE
1930       !Config Def   = 10.
1931       !Config Help  = Time step of the STOMATE history file
1932       !Config Units = [days]
1933       !-
1934       hist_days_stom = 10.
1935       CALL getin_p('STOMATE_HIST_DT', hist_days_stom)       
1936
1937       IF ( hist_id < 0 ) THEN
1938          ! Deactivate all history files if sechiba_history file is deactivated
1939          hist_dt_stom=0
1940          IF (printlev >= 2) WRITE(numout,*) &
1941               'STOMATE history file will not be created because sechiba_history file is deactivated.'
1942       ELSE IF ( hist_days_stom == moins_un ) THEN
1943          hist_dt_stom = moins_un
1944          IF (printlev >= 2) WRITE(numout,*) 'output frequency for STOMATE history file (d): one month.'
1945       ELSE IF ( hist_days_stom == 0 ) THEN
1946          ! Deactivate this file
1947          hist_dt_stom=0
1948          IF (printlev >= 2) WRITE(numout,*) 'STOMATE history file will not be created'
1949       ELSE
1950          hist_dt_stom = NINT( hist_days_stom ) * one_day
1951          IF (printlev >= 2) WRITE(numout,*) 'output frequency for STOMATE history file (d): ', &
1952               hist_dt_stom/one_day
1953       ENDIF
1954
1955       ! test consistency between STOMATE_HIST_DT and DT_STOMATE parameters
1956       dt_stomate_loc = one_day
1957       CALL getin_p('DT_STOMATE', dt_stomate_loc)
1958       IF ( hist_days_stom /= moins_un .AND. hist_dt_stom/=0) THEN
1959          IF (dt_stomate_loc > hist_dt_stom) THEN
1960             IF (printlev >= 2) WRITE(numout,*) "DT_STOMATE = ",dt_stomate_loc,"  , STOMATE_HIST_DT = ",hist_dt_stom
1961             CALL ipslerr_p (3,'ioipslctrl_history', &
1962                  &          'Problem with DT_STOMATE > STOMATE_HIST_DT','', &
1963                  &          '(must be less or equal)')
1964          ENDIF
1965       ENDIF
1966       !-
1967       !- Initialize stomate_history file
1968       IF ( hist_dt_stom == 0 ) THEN
1969          ! Case hist_dt_stom=0 : No creation of stomate_history.nc file
1970          ! Nothing will be done.
1971          hist_id_stom=-1
1972       ELSE
1973          ! Initialise stomate_history file
1974       IF (is_omp_root) THEN
1975          IF ( grid_type == regular_lonlat ) THEN
1976#ifdef CPP_PARA
1977             CALL histbeg(stom_histname, iim, lon_rect, jjm, lat_rect,  1, iim, 1, jjm, &
1978                  &     istp_old, date0, dt, hori_id, hist_id_stom,domain_id=orch_domain_id)
1979#else
1980             CALL histbeg(stom_histname, iim, lon_rect, jjm, lat_rect,  1, iim, 1, jjm, &
1981                  &     istp_old, date0, dt, hori_id, hist_id_stom)
1982#endif
1983          ELSE
1984#ifdef CPP_PARA
1985             CALL histbeg(stom_histname, iim, lon, jjm, lat,  1, iim, 1, jjm, &
1986                  &     istp_old, date0, dt, hori_id, hist_id_stom,domain_id=orch_domain_id)
1987#else
1988             CALL histbeg(stom_histname, iim, lon, jjm, lat,  1, iim, 1, jjm, &
1989                  &     istp_old, date0, dt, hori_id, hist_id_stom)
1990#endif
1991          ENDIF
1992          !- define PFT axis
1993          hist_PFTaxis = (/ ( REAL(i,r_std), i=1,nvm ) /)
1994          !- declare this axis
1995          CALL histvert (hist_id_stom, 'PFT', 'Plant functional type', &
1996               & '1', nvm, hist_PFTaxis, hist_PFTaxis_id)
1997          ! deforestation
1998          !- define Pool_10 axis
1999          hist_pool_10axis = (/ ( REAL(i,r_std), i=1,10 ) /)
2000          !- declare this axis
2001          CALL histvert (hist_id_stom, 'P10', 'Pool 10 years', &
2002               & '1', 10, hist_pool_10axis, hist_pool_10axis_id)
2003         
2004          !- define Pool_100 axis
2005          hist_pool_100axis = (/ ( REAL(i,r_std), i=1,100 ) /)
2006          !- declare this axis
2007          CALL histvert (hist_id_stom, 'P100', 'Pool 100 years', &
2008               & '1', 100, hist_pool_100axis, hist_pool_100axis_id)
2009         
2010          !- define Pool_11 axis
2011          hist_pool_11axis = (/ ( REAL(i,r_std), i=1,11 ) /)
2012          !- declare this axis
2013          CALL histvert (hist_id_stom, 'P11', 'Pool 10 years + 1', &
2014               & '1', 11, hist_pool_11axis, hist_pool_11axis_id)
2015         
2016          !- define Pool_101 axis
2017          hist_pool_101axis = (/ ( REAL(i,r_std), i=1,101 ) /)
2018          !- declare this axis
2019          CALL histvert (hist_id_stom, 'P101', 'Pool 100 years + 1', &
2020               & '1', 101, hist_pool_101axis, hist_pool_101axis_id)
2021       ENDIF
2022       !- define STOMATE history file
2023       CALL ioipslctrl_histstom (hist_id_stom, nvm, iim, jjm, &
2024            & dt, hist_dt_stom, hori_id, hist_PFTaxis_id, &
2025            & hist_pool_10axis_id, hist_pool_100axis_id, &
2026            & hist_pool_11axis_id, hist_pool_101axis_id)
2027       
2028       !- Write the names of the pfts in the stomate history files
2029       IF (is_omp_root) THEN
2030          global_attribute="PFT_name"
2031          DO i=1,nvm
2032             WRITE(global_attribute(9:10),"(I2.2)") i
2033             CALL histglobal_attr(hist_id_stom, global_attribute, PFT_name(i))
2034          ENDDO
2035
2036       !- end definition
2037          CALL histend(hist_id_stom)
2038       ENDIF
2039    END IF ! IF ( hist_dt_stom == 0 )
2040
2041       !-
2042       !-
2043       !-
2044       ! STOMATE IPCC OUTPUTS IS ACTIVATED
2045       !-
2046       !Config Key   = STOMATE_IPCC_OUTPUT_FILE
2047       !Config Desc  = Name of file in which STOMATE's output is going to be written
2048       !Config If    = OK_STOMATE
2049       !Config Def   = stomate_ipcc_history.nc
2050       !Config Help  = This file is going to be created by the model
2051       !Config         and will contain the output from the model.
2052       !Config         This file is a truly COADS compliant netCDF file.
2053       !Config         It will be generated by the hist software from
2054       !Config         the IOIPSL package.
2055       !Config Units = [FILE]
2056       !-
2057       stom_ipcc_histname='stomate_ipcc_history.nc'
2058       CALL getin_p('STOMATE_IPCC_OUTPUT_FILE', stom_ipcc_histname)       
2059       IF (printlev >= 2) WRITE(numout,*) 'STOMATE_IPCC_OUTPUT_FILE', TRIM(stom_ipcc_histname)
2060       !-
2061       !Config Key   = STOMATE_IPCC_HIST_DT
2062       !Config Desc  = STOMATE IPCC history time step
2063       !Config If    = OK_STOMATE
2064       !Config Def   = 0.
2065       !Config Help  = Time step of the STOMATE IPCC history file
2066       !Config Units = [days]
2067       !-
2068       hist_days_stom_ipcc = zero
2069       CALL getin_p('STOMATE_IPCC_HIST_DT', hist_days_stom_ipcc)       
2070       IF ( hist_days_stom_ipcc == moins_un ) THEN
2071          hist_dt_stom_ipcc = moins_un
2072          IF (printlev >= 2) WRITE(numout,*) 'output frequency for STOMATE IPCC history file (d): one month.'
2073       ELSE
2074          hist_dt_stom_ipcc = NINT( hist_days_stom_ipcc ) * one_day
2075          IF (printlev >= 2) WRITE(numout,*) 'output frequency for STOMATE IPCC history file (d): ', &
2076            hist_dt_stom_ipcc/one_day
2077       ENDIF
2078       
2079       IF ( hist_dt_stom_ipcc /= 0 .AND. hist_id < 0 ) THEN
2080          ! sechiba_history file is not created therefore STOMATE IPCC history file will be deactivated
2081          hist_dt_stom_ipcc=0
2082          hist_days_stom_ipcc=0
2083          IF (printlev >= 2) WRITE(numout,*) 'STOMATE IPCC history file is not created.'
2084       END IF
2085
2086       ! test consistency between STOMATE_IPCC_HIST_DT and DT_STOMATE parameters
2087       dt_stomate_loc = one_day
2088       CALL getin_p('DT_STOMATE', dt_stomate_loc)
2089       IF ( hist_days_stom_ipcc > zero ) THEN
2090          IF (dt_stomate_loc > hist_dt_stom_ipcc) THEN
2091             IF (printlev >= 2) WRITE(numout,*) "DT_STOMATE = ",dt_stomate_loc,"  , STOMATE_IPCC_HIST_DT = ",hist_dt_stom_ipcc
2092             CALL ipslerr_p (3,'ioipslctrl_history', &
2093                  &          'Problem with DT_STOMATE > STOMATE_IPCC_HIST_DT','', &
2094                  &          '(must be less or equal)')
2095          ENDIF
2096       ENDIF
2097
2098       !Config Key   = OK_HISTSYNC
2099       !Config Desc  = Syncronize and write IOIPSL output files at each time step
2100       !Config If    =
2101       !Config Def   = FALSE
2102       !Config Help  = Setting this flag to true might affect run performance. Only use it for debug perpose.
2103       !Config Units = [FLAG]
2104       ok_histsync=.FALSE.
2105       CALL getin_p('OK_HISTSYNC', ok_histsync)       
2106
2107
2108
2109       IF ( hist_dt_stom_ipcc == 0 ) THEN
2110          hist_id_stom_ipcc = -1
2111       ELSE
2112          !-
2113          !- initialize
2114          IF (is_omp_root) THEN
2115             IF ( grid_type == regular_lonlat ) THEN
2116#ifdef CPP_PARA
2117                CALL histbeg(stom_ipcc_histname, iim, lon_rect, jjm, lat_rect,  1, iim, 1, jjm, &
2118                     &     istp_old, date0, dt, hori_id, hist_id_stom_ipcc,domain_id=orch_domain_id)
2119#else
2120                CALL histbeg(stom_ipcc_histname, iim, lon_rect, jjm, lat_rect,  1, iim, 1, jjm, &
2121                     &     istp_old, date0, dt, hori_id, hist_id_stom_ipcc)
2122#endif
2123             ELSE
2124#ifdef CPP_PARA
2125                CALL histbeg(stom_ipcc_histname, iim, lon, jjm, lat,  1, iim, 1, jjm, &
2126                     &     istp_old, date0, dt, hori_id, hist_id_stom_ipcc,domain_id=orch_domain_id)
2127#else
2128                CALL histbeg(stom_ipcc_histname, iim, lon, jjm, lat,  1, iim, 1, jjm, &
2129                     &     istp_old, date0, dt, hori_id, hist_id_stom_ipcc)
2130#endif
2131             ENDIF
2132             !- declare this axis
2133             CALL histvert (hist_id_stom_IPCC, 'PFT', 'Plant functional type', &
2134                  & '1', nvm, hist_PFTaxis, hist_IPCC_PFTaxis_id)
2135             
2136             !- define STOMATE history file
2137             CALL ioipslctrl_histstomipcc (hist_id_stom_IPCC, nvm, iim, jjm, &
2138                  & dt, hist_dt_stom_ipcc, hori_id, hist_IPCC_PFTaxis_id)
2139             
2140             !- Write the names of the pfts in the stomate history files
2141             global_attribute="PFT_name"
2142             DO i=1,nvm
2143                WRITE(global_attribute(9:10),"(I2.2)") i
2144                CALL histglobal_attr(hist_id_stom_IPCC, global_attribute, PFT_name(i))
2145             ENDDO
2146
2147             !- end definition
2148             CALL histend(hist_id_stom_IPCC)
2149          ENDIF
2150      ENDIF
2151   ENDIF
2152
2153
2154  END SUBROUTINE ioipslctrl_history
2155
2156!! ================================================================================================================================
2157!! SUBROUTINE    : ioipslctrl_histstom
2158!!
2159!>\BRIEF         This subroutine initialize the IOIPSL stomate output file
2160!!
2161!! DESCRIPTION   : This subroutine initialize the IOIPSL output file stomate_history.nc(default name).
2162!!                 This subroutine was previously named stom_define_history and where located in module intersurf.
2163!! RECENT CHANGE(S): None
2164!!
2165!! \n
2166!_ ================================================================================================================================
2167  SUBROUTINE ioipslctrl_histstom( &
2168       hist_id_stom, nvm, iim, jjm, dt, &
2169       hist_dt, hist_hori_id, hist_PFTaxis_id, &
2170       hist_pool_10axis_id, hist_pool_100axis_id, &
2171       hist_pool_11axis_id, hist_pool_101axis_id)
2172    ! deforestation axis added as arguments
2173
2174    !---------------------------------------------------------------------
2175    !- Tell ioipsl which variables are to be written
2176    !- and on which grid they are defined
2177    !---------------------------------------------------------------------
2178    IMPLICIT NONE
2179    !-
2180    !- Input
2181    !-
2182    !- File id
2183    INTEGER(i_std),INTENT(in) :: hist_id_stom
2184    !- number of PFTs
2185    INTEGER(i_std),INTENT(in) :: nvm
2186    !- Domain size
2187    INTEGER(i_std),INTENT(in) :: iim, jjm
2188    !- Time step of STOMATE (seconds)
2189    REAL(r_std),INTENT(in)    :: dt
2190    !- Time step of history file (s)
2191    REAL(r_std),INTENT(in)    :: hist_dt
2192    !- id horizontal grid
2193    INTEGER(i_std),INTENT(in) :: hist_hori_id
2194    !- id of PFT axis
2195    INTEGER(i_std),INTENT(in) :: hist_PFTaxis_id
2196    !- id of Deforestation axis
2197    INTEGER(i_std),INTENT(in) :: hist_pool_10axis_id,hist_pool_100axis_id
2198    INTEGER(i_std),INTENT(in) :: hist_pool_11axis_id,hist_pool_101axis_id
2199    !-
2200    !- 1 local
2201    !-
2202    !- maximum history level
2203    INTEGER(i_std), PARAMETER  :: max_hist_level = 10
2204    !- output level (between 0 and 10)
2205    !-  ( 0:nothing is written, 10:everything is written)
2206    INTEGER(i_std)             :: hist_level
2207    !- Character strings to define operations for histdef
2208    CHARACTER(LEN=40),DIMENSION(max_hist_level) :: ave
2209
2210    !---------------------------------------------------------------------
2211    !=====================================================================
2212    !- 1 history level
2213    !=====================================================================
2214    !- 1.1 define history levelx
2215    !=====================================================================
2216    !Config Key   = STOMATE_HISTLEVEL
2217    !Config Desc  = STOMATE history output level (0..10)
2218    !Config If    = OK_STOMATE
2219    !Config Def   = 10
2220    !Config Help  = 0: nothing is written; 10: everything is written
2221    !Config Units = [-]
2222    !-
2223    hist_level = 10
2224    CALL getin_p('STOMATE_HISTLEVEL', hist_level)
2225    !-
2226    IF (printlev >= 2) WRITE(numout,*) 'STOMATE history level: ',hist_level
2227    IF ( (hist_level > max_hist_level).OR.(hist_level < 0) ) THEN
2228       STOP 'This history level is not allowed'
2229    ENDIF
2230    !=====================================================================
2231    !- 1.2 define operations according to output level
2232    !=====================================================================
2233    ave(1:hist_level) =  'ave(scatter(X))'
2234    ave(hist_level+1:max_hist_level) =  'never          '
2235    !=====================================================================
2236    !- 2 surface fields (2d)
2237    !- 3 PFT: 3rd dimension
2238    !=====================================================================
2239
2240
2241    ! structural litter above ground
2242    IF (is_omp_root) THEN
2243       CALL histdef (hist_id_stom, &
2244            &               TRIM("LITTER_STR_AB       "), &
2245            &               TRIM("structural litter above ground                    "), &
2246            &               TRIM("gC/m^2/pft          "), iim,jjm, hist_hori_id, &
2247            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
2248       
2249       ! metabolic litter above ground                     
2250       CALL histdef (hist_id_stom, &
2251            &               TRIM("LITTER_MET_AB       "), &
2252            &               TRIM("metabolic litter above ground                     "), &
2253            &               TRIM("gC/m^2/pft          "), iim,jjm, hist_hori_id, &
2254            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
2255       
2256       ! structural litter below ground               
2257       CALL histdef (hist_id_stom, &
2258            &               TRIM("LITTER_STR_BE       "), &
2259            &               TRIM("structural litter below ground                    "), &
2260            &               TRIM("gC/m^2/pft          "), iim,jjm, hist_hori_id, &
2261            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
2262       
2263       ! metabolic litter below ground               
2264       CALL histdef (hist_id_stom, &
2265            &               TRIM("LITTER_MET_BE       "), &
2266            &               TRIM("metabolic litter below ground                     "), &
2267            &               TRIM("gC/m^2/pft          "), iim,jjm, hist_hori_id, &
2268            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
2269       
2270       ! fraction of soil covered by dead leaves           
2271       CALL histdef (hist_id_stom, &
2272            &               TRIM("DEADLEAF_COVER      "), &
2273            &               TRIM("fraction of soil covered by dead leaves           "), &
2274            &               TRIM("-                   "), iim,jjm, hist_hori_id, &
2275            &               1,1,1, -99,32, ave(5), dt, hist_dt)
2276       
2277       ! total soil and litter carbon
2278       CALL histdef (hist_id_stom, &
2279            &               TRIM("TOTAL_SOIL_CARB     "), &
2280            &               TRIM("total soil and litter carbon                      "), &
2281            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
2282            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
2283       
2284       ! active soil carbon in ground                 
2285       CALL histdef (hist_id_stom, &
2286            &               TRIM("CARBON_ACTIVE       "), &
2287            &               TRIM("active soil carbon in ground                      "), &
2288            &               TRIM("gC/m^2/pft          "), iim,jjm, hist_hori_id, &
2289            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
2290       
2291       ! slow soil carbon in ground                   
2292       CALL histdef (hist_id_stom, &
2293            &               TRIM("CARBON_SLOW         "), &
2294            &               TRIM("slow soil carbon in ground                        "), &
2295            &               TRIM("gC/m^2/pft          "), iim,jjm, hist_hori_id, &
2296            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
2297       
2298       ! passive soil carbon in ground               
2299       CALL histdef (hist_id_stom, &
2300            &               TRIM("CARBON_PASSIVE      "), &
2301            &               TRIM("passive soil carbon in ground                     "), &
2302            &               TRIM("gC/m^2/pft          "), iim,jjm, hist_hori_id, &
2303            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
2304       
2305       ! Long term 2 m temperature                           
2306       CALL histdef (hist_id_stom, &
2307            &               TRIM("T2M_LONGTERM        "), &
2308            &               TRIM("Longterm 2 m temperature                          "), &
2309            &               TRIM("K                   "), iim,jjm, hist_hori_id, &
2310            &               1,1,1, -99,32, ave(9), dt, hist_dt)
2311       
2312       ! Monthly 2 m temperature                           
2313       CALL histdef (hist_id_stom, &
2314            &               TRIM("T2M_MONTH           "), &
2315            &               TRIM("Monthly 2 m temperature                           "), &
2316            &               TRIM("K                   "), iim,jjm, hist_hori_id, &
2317            &               1,1,1, -99,32, ave(1), dt, hist_dt)
2318       
2319       ! Weekly 2 m temperature                           
2320       CALL histdef (hist_id_stom, &
2321            &               TRIM("T2M_WEEK            "), &
2322            &               TRIM("Weekly 2 m temperature                            "), &
2323            &               TRIM("K                   "), iim,jjm, hist_hori_id, &
2324            &               1,1,1, -99,32, ave(1), dt, hist_dt)
2325       
2326       ! heterotr. resp. from ground                 
2327       CALL histdef (hist_id_stom, &
2328            &               TRIM("HET_RESP            "), &
2329            &               TRIM("heterotr. resp. from ground                       "), &
2330            &               TRIM("gC/m^2 tot/pft/day  "), iim,jjm, hist_hori_id, &
2331            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(3), dt, hist_dt)
2332       
2333       ! Fire fraction on ground
2334       CALL histdef (hist_id_stom, &
2335            &               TRIM("FIREFRAC            "), &
2336            &               TRIM("Fire fraction on ground                           "), &
2337            &               TRIM("1/day               "), iim,jjm, hist_hori_id, &
2338            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(1), dt, hist_dt)
2339
2340       ! Fire index on ground                     
2341       CALL histdef (hist_id_stom, &
2342            &               TRIM("FIREINDEX           "), &
2343            &               TRIM("Fire index on ground                              "), &
2344            &               TRIM("-                   "), iim,jjm, hist_hori_id, &
2345            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
2346       
2347       ! Litter humidity                                   
2348       CALL histdef (hist_id_stom, &
2349            &               TRIM("LITTERHUM           "), &
2350            &               TRIM("Litter humidity                                   "), &
2351            &               TRIM("-                   "), iim,jjm, hist_hori_id, &
2352            &               1,1,1, -99,32, ave(5), dt, hist_dt)
2353       
2354       ! CO2 flux                                 
2355       CALL histdef (hist_id_stom, &
2356            &               TRIM("CO2FLUX             "), &
2357            &               TRIM("CO2 flux                                          "), &
2358            &               TRIM("gC/m^2/pft/mth      "), iim,jjm, hist_hori_id, &
2359            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(1), dt, hist_dt)
2360
2361       ! Output CO2 flux from fire                         
2362       CALL histdef (hist_id_stom, &
2363            &               TRIM("CO2_FIRE            "), &
2364            &               TRIM("Output CO2 flux from fire                         "), &
2365            &               TRIM("gC/day/m^2/pft      "), iim,jjm, hist_hori_id, &
2366            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(1), dt, hist_dt)
2367       
2368       ! CO2 taken from atmosphere for initiate growth     
2369       CALL histdef (hist_id_stom, &
2370            &               TRIM("CO2_TAKEN           "), &
2371            &               TRIM("CO2 taken from atmosphere for initiate growth     "), &
2372            &               TRIM("gC/day/m^2/pft      "), iim,jjm, hist_hori_id, &
2373            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(1), dt, hist_dt)
2374
2375       IF (ok_dgvm) THEN
2376          ! total co2 flux (sum over 13 PFTs). when DGVM is activated, the previous
2377          ! SUM(CO2FLUX*veget_max) is wrong. We should look at this variable.
2378          CALL histdef (hist_id_stom, &
2379               &               TRIM("tCO2FLUX            "), &
2380               &               TRIM("total CO2flux of 13 PFTs (after adjustment)       "), &
2381               &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
2382               &               1,1,1, -99,32, ave(1), dt, hist_dt)
2383         
2384          ! should be the same with tCO2FLUX
2385          CALL histdef (hist_id_stom, &
2386               &               TRIM("tCO2FLUX_OLD        "), &
2387               &               TRIM("total CO2flux of 13 PFTs(multiply by veget_max_old"), &
2388               &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
2389               &               1,1,1, -99,32, ave(10), dt, hist_dt)
2390         
2391          CALL histdef (hist_id_stom, &
2392               &               TRIM("tGPP                 "), &
2393               &               TRIM("total GPP of 13 PFTs (after adjustment)           "), &
2394               &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
2395               &               1,1,1, -99,32, ave(1), dt, hist_dt)
2396       
2397          CALL histdef (hist_id_stom, &
2398               &               TRIM("tRESP_GROWTH         "), &
2399               &               TRIM("total resp growth of 13 PFTs (after adjustment)   "), &
2400               &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
2401               &               1,1,1, -99,32, ave(1), dt, hist_dt)
2402         
2403          CALL histdef (hist_id_stom, &
2404               &               TRIM("tRESP_MAINT          "), &
2405               &               TRIM("total resp maint  of 13 PFTs (after adjustment)   "), &
2406               &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
2407               &               1,1,1, -99,32, ave(1), dt, hist_dt)
2408       
2409          CALL histdef (hist_id_stom, &
2410               &               TRIM("tRESP_HETERO         "), &
2411               &               TRIM("total resp hetero of 13 PFTs (after adjustment)   "), &
2412               &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
2413               &               1,1,1, -99,32, ave(1), dt, hist_dt)
2414       
2415          CALL histdef (hist_id_stom, &
2416               &               TRIM("tCARBON              "), &
2417               &               TRIM("total carbon of 13 PFTs (after adjustment)        "), &
2418               &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
2419               &               1,1,1, -99,32, ave(1), dt, hist_dt)
2420         
2421          CALL histdef (hist_id_stom, &
2422               &               TRIM("tBIOMASS             "), &
2423               &               TRIM("total biomass of 13 PFTs (after adjustment)       "), &
2424               &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
2425               &               1,1,1, -99,32, ave(1), dt, hist_dt)
2426       
2427          CALL histdef (hist_id_stom, &
2428               &               TRIM("tLITTER              "), &
2429               &               TRIM("total litter of 13 PFTs (after adjustment)        "), &
2430               &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
2431               &               1,1,1, -99,32, ave(1), dt, hist_dt)
2432       
2433          CALL histdef (hist_id_stom, &
2434               &               TRIM("tSOILC               "), &
2435               &               TRIM("total soil carbon of 13 PFTs (after adjustment)   "), &
2436               &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
2437               &               1,1,1, -99,32, ave(1), dt, hist_dt)
2438
2439          CALL histdef (hist_id_stom, &
2440               &               TRIM("tCO2_TAKEN           "), &
2441               &               TRIM("total co2_to_bm 13 PFTs (after adjustment)        "), &
2442               &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
2443               &               1,1,1, -99,32, ave(10), dt, hist_dt)
2444         
2445          CALL histdef (hist_id_stom, &
2446               &               TRIM("tCO2_FIRE            "), &
2447               &               TRIM("total co2_fire 13 PFTs (after adjustment)         "), &
2448               &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
2449               &               1,1,1, -99,32, ave(10), dt, hist_dt)
2450       END IF
2451       
2452
2453       CALL histdef (hist_id_stom, &
2454            &               TRIM("FPC_MAX             "), &
2455            &               TRIM("foliage projective cover                          "), &
2456            &               TRIM("-                   "), iim,jjm, hist_hori_id, &
2457            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
2458       
2459       CALL histdef (hist_id_stom, &
2460            &               TRIM("MAXFPC_LASTYEAR     "), &
2461            &               TRIM("foliage projective cover of last year             "), &
2462            &               TRIM("-                   "), iim,jjm, hist_hori_id, &
2463            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
2464
2465       ! "seasonal" 2 m temperature                           
2466       CALL histdef (hist_id_stom, &
2467         &               TRIM("TSEASON             "), &
2468         &               TRIM("Seasonal 2 m temperature                             "), &
2469         &               TRIM("K                   "), iim,jjm, hist_hori_id, &
2470         &               1,1,1, -99,32, ave(10), dt, hist_dt)
2471
2472       ! how many days after onset                           
2473       CALL histdef (hist_id_stom, &
2474         &               TRIM("TMIN_SPRING_TIME    "), &
2475         &               TRIM("how many days after onset                            "), &
2476         &               TRIM("days                "), iim,jjm, hist_hori_id, &
2477         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
2478
2479       !                           
2480       CALL histdef (hist_id_stom, &
2481         &               TRIM("ONSET_DATE          "), &
2482         &               TRIM("onset date                                           "), &
2483         &               TRIM("day                 "), iim,jjm, hist_hori_id, &
2484         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
2485
2486       ! Leaf Area Index                                   
2487       CALL histdef (hist_id_stom, &
2488            &               TRIM("LAI                 "), &
2489            &               TRIM("Leaf Area Index                                   "), &
2490            &               TRIM("-                   "), iim,jjm, hist_hori_id, &
2491            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(1), dt, hist_dt)
2492       
2493       ! Maximum vegetation fraction (LAI -> infinity)     
2494       CALL histdef (hist_id_stom, &
2495            &               TRIM("VEGET_COV_MAX       "), &
2496            &               TRIM("Maximum vegetation fraction (LAI -> infinity)     "), &
2497            &               TRIM("-                   "), iim,jjm, hist_hori_id, &
2498            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(1), dt, hist_dt)
2499       
2500       ! Net primary productivity                         
2501       CALL histdef (hist_id_stom, &
2502            &               TRIM("NPP                 "), &
2503            &               TRIM("Net primary productivity                          "), &
2504            &               TRIM("gC/day/(m^2 tot)    "), iim,jjm, hist_hori_id, &
2505            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(1), dt, hist_dt)
2506
2507       ! Gross primary productivity                       
2508       CALL histdef (hist_id_stom, &
2509            &               TRIM("GPP                 "), &
2510            &               TRIM("Gross primary productivity                        "), &
2511            &               TRIM("gC/day/m^2          "), iim,jjm, hist_hori_id, &
2512            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(1), dt, hist_dt)
2513
2514       ! Density of individuals                           
2515       CALL histdef (hist_id_stom, &
2516            &               TRIM("IND                 "), &
2517            &               TRIM("Density of individuals                            "), &
2518            &               TRIM("1/ m^2              "), iim,jjm, hist_hori_id, &
2519            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(3), dt, hist_dt)
2520
2521       ! Adaptation to climate
2522       CALL histdef (hist_id_stom, &
2523            &               TRIM("ADAPTATION          "), &
2524            &               TRIM("Adaptation to climate (DGVM)                      "), &
2525            &               TRIM("-                   "), iim,jjm, hist_hori_id, &
2526            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(3), dt, hist_dt)
2527   
2528       ! Probability from regenerative
2529       CALL histdef (hist_id_stom, &
2530            &               TRIM("REGENERATION        "), &
2531            &               TRIM("Probability from regenerative (DGVM)               "), &
2532            &               TRIM("-                   "), iim,jjm, hist_hori_id, &
2533            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(3), dt, hist_dt)
2534       
2535       ! crown area of individuals (m**2)
2536       CALL histdef (hist_id_stom, &
2537            &               TRIM("CN_IND              "), &
2538            &               TRIM("crown area of individuals                         "), &
2539            &               TRIM("m^2                 "), iim,jjm, hist_hori_id, &
2540            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(3), dt, hist_dt)
2541
2542       ! woodmass of individuals (gC)
2543       CALL histdef (hist_id_stom, &
2544            &               TRIM("WOODMASS_IND        "), &
2545            &               TRIM("Woodmass of individuals                           "), &
2546            &               TRIM("gC/pft              "), iim,jjm, hist_hori_id, &
2547            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(3), dt, hist_dt)
2548
2549       ! total living biomass
2550       CALL histdef (hist_id_stom, &
2551            &               TRIM("TOTAL_M             "), &
2552            &               TRIM("Total living biomass                              "), &
2553            &               TRIM("gC/m^2/pft          "), iim,jjm, hist_hori_id, &
2554            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(4), dt, hist_dt)
2555       
2556       ! Leaf mass                                         
2557       CALL histdef (hist_id_stom, &
2558            &               TRIM("LEAF_M              "), &
2559            &               TRIM("Leaf mass                                         "), &
2560            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
2561            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
2562       
2563       ! Sap mass above ground                             
2564       CALL histdef (hist_id_stom, &
2565            &               TRIM("SAP_M_AB            "), &
2566            &               TRIM("Sap mass above ground                             "), &
2567            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
2568            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
2569
2570       ! Sap mass below ground                             
2571       CALL histdef (hist_id_stom, &
2572            &               TRIM("SAP_M_BE            "), &
2573            &               TRIM("Sap mass below ground                             "), &
2574            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
2575            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
2576       
2577       ! Heartwood mass above ground                       
2578       CALL histdef (hist_id_stom, &
2579            &               TRIM("HEART_M_AB          "), &
2580            &               TRIM("Heartwood mass above ground                       "), &
2581            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
2582            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
2583
2584       ! Heartwood mass below ground                       
2585       CALL histdef (hist_id_stom, &
2586            &               TRIM("HEART_M_BE          "), &
2587            &               TRIM("Heartwood mass below ground                       "), &
2588            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
2589            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
2590
2591       ! Root mass                                         
2592       CALL histdef (hist_id_stom, &
2593            &               TRIM("ROOT_M              "), &
2594            &               TRIM("Root mass                                         "), &
2595            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
2596            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
2597       
2598       ! Fruit mass                                       
2599       CALL histdef (hist_id_stom, &
2600            &               TRIM("FRUIT_M             "), &
2601            &               TRIM("Fruit mass                                        "), &
2602            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
2603            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
2604       
2605       ! Carbohydrate reserve mass                         
2606       CALL histdef (hist_id_stom, &
2607            &               TRIM("RESERVE_M           "), &
2608            &               TRIM("Carbohydrate reserve mass                         "), &
2609            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
2610            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
2611       
2612       ! total turnover rate
2613       CALL histdef (hist_id_stom, &
2614            &               TRIM("TOTAL_TURN          "), &
2615            &               TRIM("total turnover rate                               "), &
2616            &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
2617            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(4), dt, hist_dt)
2618
2619       ! Leaf turnover                                     
2620       CALL histdef (hist_id_stom, &
2621            &               TRIM("LEAF_TURN           "), &
2622            &               TRIM("Leaf turnover                                     "), &
2623            &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
2624            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(4), dt, hist_dt)
2625
2626       ! Sap turnover above                               
2627       CALL histdef (hist_id_stom, &
2628            &               TRIM("SAP_AB_TURN         "), &
2629            &               TRIM("Sap turnover above                                "), &
2630            &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
2631            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(4), dt, hist_dt)
2632
2633       ! Root turnover                                     
2634       CALL histdef (hist_id_stom, &
2635            &               TRIM("ROOT_TURN           "), &
2636            &               TRIM("Root turnover                                     "), &
2637            &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
2638            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(4), dt, hist_dt)
2639
2640       ! Fruit turnover                                   
2641       CALL histdef (hist_id_stom, &
2642            &               TRIM("FRUIT_TURN          "), &
2643            &               TRIM("Fruit turnover                                    "), &
2644            &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
2645            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(4), dt, hist_dt)
2646
2647       ! total conversion of biomass to litter
2648       CALL histdef (hist_id_stom, &
2649            &               TRIM("TOTAL_BM_LITTER     "), &
2650            &               TRIM("total conversion of biomass to litter             "), &
2651            &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
2652            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(4), dt, hist_dt)
2653
2654       ! Leaf death                                       
2655       CALL histdef (hist_id_stom, &
2656            &               TRIM("LEAF_BM_LITTER      "), &
2657            &               TRIM("Leaf death                                        "), &
2658            &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
2659            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(4), dt, hist_dt)
2660       
2661       ! Sap death above ground                           
2662       CALL histdef (hist_id_stom, &
2663            &               TRIM("SAP_AB_BM_LITTER    "), &
2664            &               TRIM("Sap death above ground                            "), &
2665            &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
2666            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(4), dt, hist_dt)
2667
2668       ! Sap death below ground                           
2669       CALL histdef (hist_id_stom, &
2670            &               TRIM("SAP_BE_BM_LITTER    "), &
2671            &               TRIM("Sap death below ground                            "), &
2672            &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
2673            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(4), dt, hist_dt)
2674
2675       ! Heartwood death above ground                     
2676       CALL histdef (hist_id_stom, &
2677            &               TRIM("HEART_AB_BM_LITTER  "), &
2678            &               TRIM("Heartwood death above ground                      "), &
2679            &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
2680            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(4), dt, hist_dt)
2681
2682       ! Heartwood death below ground                     
2683       CALL histdef (hist_id_stom, &
2684            &               TRIM("HEART_BE_BM_LITTER  "), &
2685            &               TRIM("Heartwood death below ground                      "), &
2686            &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
2687            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(4), dt, hist_dt)
2688
2689       ! Root death                                       
2690       CALL histdef (hist_id_stom, &
2691            &               TRIM("ROOT_BM_LITTER      "), &
2692            &               TRIM("Root death                                        "), &
2693            &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
2694            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(4), dt, hist_dt)
2695       
2696       ! Fruit death                                       
2697       CALL histdef (hist_id_stom, &
2698            &               TRIM("FRUIT_BM_LITTER     "), &
2699            &               TRIM("Fruit death                                       "), &
2700            &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
2701            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(4), dt, hist_dt)
2702
2703       ! Carbohydrate reserve death                       
2704       CALL histdef (hist_id_stom, &
2705            &               TRIM("RESERVE_BM_LITTER   "), &
2706            &               TRIM("Carbohydrate reserve death                        "), &
2707            &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
2708            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(4), dt, hist_dt)
2709
2710       ! Maintenance respiration                           
2711       CALL histdef (hist_id_stom, &
2712            &               TRIM("MAINT_RESP          "), &
2713            &               TRIM("Maintenance respiration                           "), &
2714            &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
2715            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
2716
2717       ! Growth respiration                               
2718       CALL histdef (hist_id_stom, &
2719            &               TRIM("GROWTH_RESP         "), &
2720            &               TRIM("Growth respiration                                "), &
2721            &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
2722            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
2723       
2724       ! age                                               
2725       CALL histdef (hist_id_stom, &
2726            &               TRIM("AGE                 "), &
2727            &               TRIM("age                                               "), &
2728            &               TRIM("years               "), iim,jjm, hist_hori_id, &
2729            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(7), dt, hist_dt)
2730       
2731       ! height                                           
2732       CALL histdef (hist_id_stom, &
2733            &               TRIM("HEIGHT              "), &
2734            &               TRIM("height                                            "), &
2735            &               TRIM("m                   "), iim,jjm, hist_hori_id, &
2736            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(7), dt, hist_dt)
2737
2738       ! weekly moisture stress                           
2739       CALL histdef (hist_id_stom, &
2740            &               TRIM("MOISTRESS           "), &
2741            &               TRIM("weekly moisture stress                            "), &
2742            &               TRIM("-                   "), iim,jjm, hist_hori_id, &
2743            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(3), dt, hist_dt)
2744
2745       ! Maximum rate of carboxylation                     
2746       CALL histdef (hist_id_stom, &
2747            &               TRIM("VCMAX               "), &
2748            &               TRIM("Maximum rate of carboxylation                     "), &
2749            &               TRIM("-                   "), iim,jjm, hist_hori_id, &
2750            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(6), dt, hist_dt)
2751
2752       ! leaf age                                         
2753       CALL histdef (hist_id_stom, &
2754            &               TRIM("LEAF_AGE            "), &
2755            &               TRIM("leaf age                                          "), &
2756            &               TRIM("days                "), iim,jjm, hist_hori_id, &
2757            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(6), dt, hist_dt)
2758       
2759       ! Fraction of trees that dies (gap)                 
2760       CALL histdef (hist_id_stom, &
2761            &               TRIM("MORTALITY           "), &
2762            &               TRIM("Fraction of trees that dies (gap)                 "), &
2763            &               TRIM("1/day               "), iim,jjm, hist_hori_id, &
2764            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(6), dt, hist_dt)
2765
2766       ! Fraction of plants killed by fire                 
2767       CALL histdef (hist_id_stom, &
2768            &               TRIM("FIREDEATH           "), &
2769            &               TRIM("Fraction of plants killed by fire                 "), &
2770            &               TRIM("1/day               "), iim,jjm, hist_hori_id, &
2771            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(6), dt, hist_dt)
2772
2773       ! Density of newly established saplings             
2774       CALL histdef (hist_id_stom, &
2775            &               TRIM("IND_ESTAB           "), &
2776            &               TRIM("Density of newly established saplings             "), &
2777            &               TRIM("1/day               "), iim,jjm, hist_hori_id, &
2778            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(6), dt, hist_dt)
2779
2780       ! Establish tree
2781       CALL histdef (hist_id_stom, &
2782            &               TRIM("ESTABTREE           "), &
2783            &               TRIM("Rate of tree establishement                       "), &
2784            &               TRIM("1/day               "), iim,jjm, hist_hori_id, &
2785            &               1,1,1, -99,32, ave(6), dt, hist_dt)
2786
2787       ! Establish grass
2788       CALL histdef (hist_id_stom, &
2789            &               TRIM("ESTABGRASS          "), &
2790            &               TRIM("Rate of grass establishement                      "), &
2791            &               TRIM("1/day               "), iim,jjm, hist_hori_id, &
2792            &               1,1,1, -99,32, ave(6), dt, hist_dt)
2793
2794       ! Fraction of plants that dies (light competition) 
2795       CALL histdef (hist_id_stom, &
2796            &               TRIM("LIGHT_DEATH         "), &
2797            &               TRIM("Fraction of plants that dies (light competition)  "), &
2798            &               TRIM("1/day               "), iim,jjm, hist_hori_id, &
2799            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(6), dt, hist_dt)
2800
2801       ! biomass allocated to leaves                       
2802       CALL histdef (hist_id_stom, &
2803            &               TRIM("BM_ALLOC_LEAF       "), &
2804            &               TRIM("biomass allocated to leaves                       "), &
2805            &               TRIM("gC/m**2/pft/dt      "), iim,jjm, hist_hori_id, &
2806            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
2807
2808       ! biomass allocated to sapwood above ground         
2809       CALL histdef (hist_id_stom, &
2810            &               TRIM("BM_ALLOC_SAP_AB     "), &
2811            &               TRIM("biomass allocated to sapwood above ground         "), &
2812            &               TRIM("gC/m**2/pft/dt      "), iim,jjm, hist_hori_id, &
2813            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
2814
2815       ! biomass allocated to sapwood below ground         
2816       CALL histdef (hist_id_stom, &
2817            &               TRIM("BM_ALLOC_SAP_BE     "), &
2818            &               TRIM("biomass allocated to sapwood below ground         "), &
2819            &               TRIM("gC/m**2/pft/dt      "), iim,jjm, hist_hori_id, &
2820            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
2821
2822       ! biomass allocated to roots                       
2823       CALL histdef (hist_id_stom, &
2824            &               TRIM("BM_ALLOC_ROOT       "), &
2825            &               TRIM("biomass allocated to roots                        "), &
2826            &               TRIM("gC/m**2/pft/dt          "), iim,jjm, hist_hori_id, &
2827            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
2828
2829       ! biomass allocated to fruits                       
2830       CALL histdef (hist_id_stom, &
2831            &               TRIM("BM_ALLOC_FRUIT      "), &
2832            &               TRIM("biomass allocated to fruits                       "), &
2833            &               TRIM("gC/m**2/pft/dt          "), iim,jjm, hist_hori_id, &
2834            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
2835
2836       ! biomass allocated to carbohydrate reserve         
2837       CALL histdef (hist_id_stom, &
2838            &               TRIM("BM_ALLOC_RES        "), &
2839            &               TRIM("biomass allocated to carbohydrate reserve         "), &
2840            &               TRIM("gC/m**2/pft/dt          "), iim,jjm, hist_hori_id, &
2841            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
2842
2843       ! time constant of herbivore activity               
2844       CALL histdef (hist_id_stom, &
2845            &               TRIM("HERBIVORES          "), &
2846            &               TRIM("time constant of herbivore activity               "), &
2847            &               TRIM("days                "), iim,jjm, hist_hori_id, &
2848            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
2849
2850       ! turnover time for grass leaves                   
2851       CALL histdef (hist_id_stom, &
2852            &               TRIM("TURNOVER_TIME       "), &
2853            &               TRIM("turnover time for grass leaves                    "), &
2854            &               TRIM("days                "), iim,jjm, hist_hori_id, &
2855            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
2856       
2857       ! 10 year wood product pool                         
2858       CALL histdef (hist_id_stom, &
2859            &               TRIM("PROD10              "), &
2860            &               TRIM("10 year wood product pool                         "), &
2861            &               TRIM("gC/m**2             "), iim,jjm, hist_hori_id, &
2862            &               11,1,11, hist_pool_11axis_id,32, ave(5), dt, hist_dt)
2863       
2864       ! annual flux for each 10 year wood product pool   
2865       CALL histdef (hist_id_stom, &
2866            &               TRIM("FLUX10              "), &
2867            &               TRIM("annual flux for each 10 year wood product pool    "), &
2868            &               TRIM("gC/m**2/yr          "), iim,jjm, hist_hori_id, &
2869            &               10,1,10, hist_pool_10axis_id,32, ave(5), dt, hist_dt)
2870       
2871       ! 100 year wood product pool                       
2872       CALL histdef (hist_id_stom, &
2873            &               TRIM("PROD100             "), &
2874            &               TRIM("100 year wood product pool                        "), &
2875            &               TRIM("gC/m**2             "), iim,jjm, hist_hori_id, &
2876            &               101,1,101, hist_pool_101axis_id,32, ave(5), dt, hist_dt)
2877
2878       ! annual flux for each 100 year wood product pool   
2879       CALL histdef (hist_id_stom, &
2880            &               TRIM("FLUX100             "), &
2881            &               TRIM("annual flux for each 100 year wood product pool   "), &
2882            &               TRIM("gC/m**2/yr          "), iim,jjm, hist_hori_id, &
2883            &               100,1,100, hist_pool_100axis_id,32, ave(5), dt, hist_dt)
2884
2885       ! annual release right after deforestation         
2886       CALL histdef (hist_id_stom, &
2887            &               TRIM("CONVFLUX            "), &
2888            &               TRIM("annual release right after deforestation          "), &
2889            &               TRIM("gC/m**2/day          "), iim,jjm, hist_hori_id, &
2890            &               1,1,1, -99,32, ave(5), dt, hist_dt)
2891
2892       ! annual release from all 10 year wood product pools
2893       CALL histdef (hist_id_stom, &
2894            &               TRIM("CFLUX_PROD10        "), &
2895            &               TRIM("annual release from all 10 year wood product pools"), &
2896            &               TRIM("gC/m**2/day          "), iim,jjm, hist_hori_id, &
2897            &               1,1,1, -99,32, ave(5), dt, hist_dt)
2898
2899       ! annual release from all 100year wood product pools
2900       CALL histdef (hist_id_stom, &
2901            &               TRIM("CFLUX_PROD100       "), &
2902            &               TRIM("annual release from all 100year wood product pools"), &
2903            &               TRIM("gC/m**2/day          "), iim,jjm, hist_hori_id, &
2904            &               1,1,1, -99,32, ave(5), dt, hist_dt)
2905
2906       ! WOOD HARVEST
2907       ! 10 year wood product pool                         
2908       CALL histdef (hist_id_stom, &
2909            &               TRIM("PROD10_HARVEST      "), &
2910            &               TRIM("10 year wood product pool                         "), &
2911            &               TRIM("gC/m**2             "), iim,jjm, hist_hori_id, &
2912            &               11,1,11, hist_pool_11axis_id,32, ave(5), dt, hist_dt)
2913       
2914       ! annual flux for each 10 year wood product pool   
2915       CALL histdef (hist_id_stom, &
2916            &               TRIM("FLUX10_HARVEST      "), &
2917            &               TRIM("annual flux for each 10 year wood product pool    "), &
2918            &               TRIM("gC/m**2/yr          "), iim,jjm, hist_hori_id, &
2919            &               10,1,10, hist_pool_10axis_id,32, ave(5), dt, hist_dt)
2920       
2921       ! 100 year wood product pool                       
2922       CALL histdef (hist_id_stom, &
2923            &               TRIM("PROD100_HARVEST     "), &
2924            &               TRIM("100 year wood product pool                        "), &
2925            &               TRIM("gC/m**2             "), iim,jjm, hist_hori_id, &
2926            &               101,1,101, hist_pool_101axis_id,32, ave(5), dt, hist_dt)
2927
2928       ! annual flux for each 100 year wood product pool   
2929       CALL histdef (hist_id_stom, &
2930            &               TRIM("FLUX100_HARVEST     "), &
2931            &               TRIM("annual flux for each 100 year wood product pool   "), &
2932            &               TRIM("gC/m**2/yr          "), iim,jjm, hist_hori_id, &
2933            &               100,1,100, hist_pool_100axis_id,32, ave(5), dt, hist_dt)
2934
2935       ! annual release right after deforestation         
2936       CALL histdef (hist_id_stom, &
2937            &               TRIM("CONVFLUX_HARVEST      "), &
2938            &               TRIM("annual release right after deforestation          "), &
2939            &               TRIM("gC/m**2/day          "), iim,jjm, hist_hori_id, &
2940            &               1,1,1, -99,32, ave(5), dt, hist_dt)
2941
2942       ! annual release from all 10 year wood product pools
2943       CALL histdef (hist_id_stom, &
2944            &               TRIM("CFLUX_PROD10_HARVEST   "), &
2945            &               TRIM("annual release from all 10 year wood product pools"), &
2946            &               TRIM("gC/m**2/day          "), iim,jjm, hist_hori_id, &
2947            &               1,1,1, -99,32, ave(5), dt, hist_dt)
2948
2949       ! annual release from all 100year wood product pools
2950       ! Note removed last letter T from HARVEST in the variable name to limit number of authorized charcters
2951       CALL histdef (hist_id_stom, &
2952            &               TRIM("CFLUX_PROD100_HARVES"), &
2953            &               TRIM("annual release from all 100year wood product pools"), &
2954            &               TRIM("gC/m**2/day          "), iim,jjm, hist_hori_id, &
2955            &               1,1,1, -99,32, ave(5), dt, hist_dt)
2956
2957       CALL histdef (hist_id_stom, &
2958            &               TRIM("WOOD_HARVEST  "), &
2959            &               TRIM("harvested wood biomass"), &
2960            &               TRIM("gC/m**2/day          "), iim,jjm, hist_hori_id, &
2961            &               1,1,1, -99,32, ave(5), dt, hist_dt)
2962
2963       CALL histdef (hist_id_stom, &
2964            &               TRIM("WOOD_HARVEST_PFT  "), &
2965            &               TRIM("harvested wood biomass per PFT"), &
2966            &               TRIM("gC/m**2/day          "), iim,jjm, hist_hori_id, &
2967            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
2968
2969       ! agriculure product
2970       CALL histdef (hist_id_stom, &
2971            &               TRIM("HARVEST_ABOVE       "), &
2972            &               TRIM("annual release product after harvest              "), &
2973            &               TRIM("gC/m**2/day          "), iim,jjm, hist_hori_id, &
2974            &               1,1,1, -99,32, ave(5), dt, hist_dt)
2975
2976
2977       CALL histdef(hist_id_stom, 'RESOLUTION_X', 'E-W resolution', 'm', &
2978            & iim,jjm, hist_hori_id, 1,1,1, -99, 32, 'once(scatter(X))', dt, hist_dt)
2979       CALL histdef(hist_id_stom, 'RESOLUTION_Y', 'N-S resolution', 'm', &
2980            & iim,jjm, hist_hori_id, 1,1,1, -99, 32, 'once(scatter(X))', dt, hist_dt)
2981       CALL histdef(hist_id_stom, 'CONTFRAC', 'Continental fraction', '1', &
2982            & iim,jjm, hist_hori_id, 1,1,1, -99, 32, 'once(scatter(X))', dt, hist_dt)
2983       CALL histdef(hist_id_stom, 'Areas', 'Mesh areas', 'm2', &
2984            & iim,jjm, hist_hori_id, 1,1,1, -99, 32, 'once(scatter(X))', dt, hist_dt)
2985       
2986       !  Special outputs for phenology
2987       CALL histdef (hist_id_stom, &
2988            &               TRIM("WHEN_GROWTHINIT     "), &
2989            &               TRIM("Time elapsed from season beginning                "), &
2990            &               TRIM("d                   "), iim,jjm, hist_hori_id, &
2991            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(9), dt, hist_dt)
2992       
2993       CALL histdef (hist_id_stom, &
2994            &               TRIM("PFTPRESENT          "), &
2995            &               TRIM("PFT exists                                        "), &
2996            &               TRIM("d                   "), iim,jjm, hist_hori_id, &
2997            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(9), dt, hist_dt)
2998       
2999       CALL histdef (hist_id_stom, &
3000            &               TRIM("GDD_MIDWINTER       "), &
3001            &               TRIM("Growing degree days, since midwinter              "), &
3002            &               TRIM("degK                "), iim,jjm, hist_hori_id, &
3003            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(9), dt, hist_dt)
3004
3005       CALL histdef (hist_id_stom, &
3006            &               TRIM("GDD_M5_DORMANCE     "), &
3007            &               TRIM("Growing degree days, since dormance               "), &
3008            &               TRIM("degK                "), iim,jjm, hist_hori_id, &
3009            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(9), dt, hist_dt)
3010       
3011       CALL histdef (hist_id_stom, &
3012            &               TRIM("NCD_DORMANCE        "), &
3013            &               TRIM("Number of chilling days, since leaves were lost   "), &
3014            &               TRIM("d                   "), iim,jjm, hist_hori_id, &
3015            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(9), dt, hist_dt)
3016       
3017       CALL histdef (hist_id_stom, &
3018            &               TRIM("ALLOW_INITPHENO     "), &
3019            &               TRIM("Allow to declare beginning of the growing season  "), &
3020            &               TRIM("-                   "), iim,jjm, hist_hori_id, &
3021            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(9), dt, hist_dt)
3022       
3023       CALL histdef (hist_id_stom, &
3024            &               TRIM("BEGIN_LEAVES        "), &
3025            &               TRIM("Signal to start putting leaves on                 "), &
3026            &               TRIM("-                   "), iim,jjm, hist_hori_id, &
3027            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(9), dt, hist_dt)
3028    ENDIF
3029
3030  END SUBROUTINE ioipslctrl_histstom
3031
3032!! ================================================================================================================================
3033!! SUBROUTINE    : ioipslctrl_histstomipcc
3034!!
3035!>\BRIEF         This subroutine initialize the IOIPSL stomate second output file (ipcc file)
3036!!
3037!! DESCRIPTION   : This subroutine initialize the IOIPSL stomate second output file named stomate_ipcc_history.nc(default name).
3038!!                 This subroutine was previously called stom_IPCC_define_history and located in module intersurf.
3039!!
3040!! RECENT CHANGE(S): None
3041!!
3042!! \n
3043!_ ================================================================================================================================
3044  SUBROUTINE ioipslctrl_histstomipcc( &
3045       hist_id_stom_IPCC, nvm, iim, jjm, dt, &
3046       hist_dt, hist_hori_id, hist_PFTaxis_id)
3047    ! deforestation axis added as arguments
3048
3049    !---------------------------------------------------------------------
3050    !- Tell ioipsl which variables are to be written
3051    !- and on which grid they are defined
3052    !---------------------------------------------------------------------
3053    IMPLICIT NONE
3054    !-
3055    !- Input
3056    !-
3057    !- File id
3058    INTEGER(i_std),INTENT(in) :: hist_id_stom_IPCC
3059    !- number of PFTs
3060    INTEGER(i_std),INTENT(in) :: nvm
3061    !- Domain size
3062    INTEGER(i_std),INTENT(in) :: iim, jjm
3063    !- Time step of STOMATE (seconds)
3064    REAL(r_std),INTENT(in)    :: dt
3065    !- Time step of history file (s)
3066    REAL(r_std),INTENT(in)    :: hist_dt
3067    !- id horizontal grid
3068    INTEGER(i_std),INTENT(in) :: hist_hori_id
3069    !- id of PFT axis
3070    INTEGER(i_std),INTENT(in) :: hist_PFTaxis_id
3071    !-
3072    !- 1 local
3073    !-
3074    !- Character strings to define operations for histdef
3075    CHARACTER(LEN=40),DIMENSION(max_hist_level) :: ave
3076
3077    !=====================================================================
3078    !- 1 define operations
3079    !=====================================================================
3080    ave(1) =  'ave(scatter(X))'
3081    !=====================================================================
3082    !- 2 surface fields (2d)
3083    !=====================================================================
3084    ! Carbon in Vegetation
3085    CALL histdef (hist_id_stom_IPCC, &
3086         &               TRIM("cVeg"), &
3087         &               TRIM("Carbon in Vegetation"), &
3088         &               TRIM("kg C m-2"), iim,jjm, hist_hori_id, &
3089         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3090    ! Carbon in Litter Pool
3091    CALL histdef (hist_id_stom_IPCC, &
3092         &               TRIM("cLitter"), &
3093         &               TRIM("Carbon in Litter Pool"), &
3094         &               TRIM("kg C m-2"), iim,jjm, hist_hori_id, &
3095         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3096    ! Carbon in Soil Pool
3097    CALL histdef (hist_id_stom_IPCC, &
3098         &               TRIM("cSoil"), &
3099         &               TRIM("Carbon in Soil Pool"), &
3100         &               TRIM("kg C m-2"), iim,jjm, hist_hori_id, &
3101         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3102    ! Carbon in Products of Land Use Change
3103    CALL histdef (hist_id_stom_IPCC, &
3104         &               TRIM("cProduct"), &
3105         &               TRIM("Carbon in Products of Land Use Change"), &
3106         &               TRIM("kg C m-2"), iim,jjm, hist_hori_id, &
3107         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3108    ! Carbon Mass Variation
3109    CALL histdef (hist_id_stom_IPCC, &
3110         &               TRIM("cMassVariation"), &
3111         &               TRIM("Terrestrial Carbon Mass Variation"), &
3112         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
3113         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3114    ! Leaf Area Fraction
3115    CALL histdef (hist_id_stom_IPCC, &
3116         &               TRIM("lai"), &
3117         &               TRIM("Leaf Area Fraction"), &
3118         &               TRIM("1"), iim,jjm, hist_hori_id, &
3119         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3120    ! Gross Primary Production
3121    CALL histdef (hist_id_stom_IPCC, &
3122         &               TRIM("gpp"), &
3123         &               TRIM("Gross Primary Production"), &
3124         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
3125         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3126    ! Autotrophic Respiration
3127    CALL histdef (hist_id_stom_IPCC, &
3128         &               TRIM("ra"), &
3129         &               TRIM("Autotrophic Respiration"), &
3130         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
3131         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3132    ! Net Primary Production
3133    CALL histdef (hist_id_stom_IPCC, &
3134         &               TRIM("npp"), &
3135         &               TRIM("Net Primary Production"), &
3136         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
3137         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3138    ! Heterotrophic Respiration
3139    CALL histdef (hist_id_stom_IPCC, &
3140         &               TRIM("rh"), &
3141         &               TRIM("Heterotrophic Respiration"), &
3142         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
3143         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3144    ! CO2 Emission from Fire
3145    CALL histdef (hist_id_stom_IPCC, &
3146         &               TRIM("fFire"), &
3147         &               TRIM("CO2 Emission from Fire"), &
3148         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
3149         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3150
3151    ! CO2 Flux to Atmosphere from Crop Harvesting
3152    CALL histdef (hist_id_stom_IPCC, &
3153         &               TRIM("fHarvest"), &
3154         &               TRIM("CO2 Flux to Atmosphere from Crop Harvesting"), &
3155         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
3156         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3157    ! CO2 Flux to Atmosphere from Land Use Change
3158    CALL histdef (hist_id_stom_IPCC, &
3159         &               TRIM("fLuc"), &
3160         &               TRIM("CO2 Flux to Atmosphere from Land Use Change"), &
3161         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
3162         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3163    ! CO2 Flux to Atmosphere from Wood Harvest                                                                               
3164    CALL histdef (hist_id_stom_IPCC, &
3165         &               TRIM("fWoodharvest"), &
3166         &               TRIM("CO2 Flux to Atmosphere from Wood Harvest"), &
3167         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
3168         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3169
3170    ! Net Biospheric Production
3171    CALL histdef (hist_id_stom_IPCC, &
3172         &               TRIM("nbp"), &
3173         &               TRIM("Net Biospheric Production"), &
3174         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
3175         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3176    ! Total Carbon Flux from Vegetation to Litter
3177    CALL histdef (hist_id_stom_IPCC, &
3178         &               TRIM("fVegLitter"), &
3179         &               TRIM("Total Carbon Flux from Vegetation to Litter"), &
3180         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
3181         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3182    ! Total Carbon Flux from Litter to Soil
3183    CALL histdef (hist_id_stom_IPCC, &
3184         &               TRIM("fLitterSoil"), &
3185         &               TRIM("Total Carbon Flux from Litter to Soil"), &
3186         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
3187         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3188
3189    ! Carbon in Leaves
3190    CALL histdef (hist_id_stom_IPCC, &
3191         &               TRIM("cLeaf"), &
3192         &               TRIM("Carbon in Leaves"), &
3193         &               TRIM("kg C m-2"), iim,jjm, hist_hori_id, &
3194         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3195    ! Carbon in Stem
3196    CALL histdef (hist_id_stom_IPCC, &
3197         &               TRIM("cStem"), &
3198         &               TRIM("Carbon in Stem"), &
3199         &               TRIM("kg C m-2"), iim,jjm, hist_hori_id, &
3200         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3201    ! Carbon in Roots
3202    CALL histdef (hist_id_stom_IPCC, &
3203         &               TRIM("cRoot"), &
3204         &               TRIM("Carbon in Roots"), &
3205         &               TRIM("kg C m-2"), iim,jjm, hist_hori_id, &
3206         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3207    ! Carbon in Other Living Compartments
3208    CALL histdef (hist_id_stom_IPCC, &
3209         &               TRIM("cMisc"), &
3210         &               TRIM("Carbon in Other Living Compartments"), &
3211         &               TRIM("kg C m-2"), iim,jjm, hist_hori_id, &
3212         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3213
3214    ! Carbon in Above-Ground Litter
3215    CALL histdef (hist_id_stom_IPCC, &
3216         &               TRIM("cLitterAbove"), &
3217         &               TRIM("Carbon in Above-Ground Litter"), &
3218         &               TRIM("kg C m-2"), iim,jjm, hist_hori_id, &
3219         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3220    ! Carbon in Below-Ground Litter
3221    CALL histdef (hist_id_stom_IPCC, &
3222         &               TRIM("cLitterBelow"), &
3223         &               TRIM("Carbon in Below-Ground Litter"), &
3224         &               TRIM("kg C m-2"), iim,jjm, hist_hori_id, &
3225         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3226    ! Carbon in Fast Soil Pool
3227    CALL histdef (hist_id_stom_IPCC, &
3228         &               TRIM("cSoilFast"), &
3229         &               TRIM("Carbon in Fast Soil Pool"), &
3230         &               TRIM("kg C m-2"), iim,jjm, hist_hori_id, &
3231         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3232    ! Carbon in Medium Soil Pool
3233    CALL histdef (hist_id_stom_IPCC, &
3234         &               TRIM("cSoilMedium"), &
3235         &               TRIM("Carbon in Medium Soil Pool"), &
3236         &               TRIM("kg C m-2"), iim,jjm, hist_hori_id, &
3237         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3238    ! Carbon in Slow Soil Pool
3239    CALL histdef (hist_id_stom_IPCC, &
3240         &               TRIM("cSoilSlow"), &
3241         &               TRIM("Carbon in Slow Soil Pool"), &
3242         &               TRIM("kg C m-2"), iim,jjm, hist_hori_id, &
3243         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3244
3245    !- 3 PFT: 3rd dimension
3246    ! Fractional Land Cover of PFT
3247    CALL histdef (hist_id_stom_IPCC, &
3248         &               TRIM("landCoverFrac"), &
3249         &               TRIM("Fractional Land Cover of PFT"), &
3250         &               TRIM("%"), iim,jjm, hist_hori_id, &
3251         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(1), dt, hist_dt)
3252
3253
3254    ! Total Primary Deciduous Tree Cover Fraction
3255    CALL histdef (hist_id_stom_IPCC, &
3256         &               TRIM("treeFracPrimDec"), &
3257         &               TRIM("Total Primary Deciduous Tree Cover Fraction"), &
3258         &               TRIM("%"), iim,jjm, hist_hori_id, &
3259         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3260
3261    ! Total Primary Evergreen Tree Cover Fraction
3262    CALL histdef (hist_id_stom_IPCC, &
3263         &               TRIM("treeFracPrimEver"), &
3264         &               TRIM("Total Primary Evergreen Tree Cover Fraction"), &
3265         &               TRIM("%"), iim,jjm, hist_hori_id, &
3266         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3267
3268    ! Total C3 PFT Cover Fraction
3269    CALL histdef (hist_id_stom_IPCC, &
3270         &               TRIM("c3PftFrac"), &
3271         &               TRIM("Total C3 PFT Cover Fraction"), &
3272         &               TRIM("%"), iim,jjm, hist_hori_id, &
3273         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3274    ! Total C4 PFT Cover Fraction
3275    CALL histdef (hist_id_stom_IPCC, &
3276         &               TRIM("c4PftFrac"), &
3277         &               TRIM("Total C4 PFT Cover Fraction"), &
3278         &               TRIM("%"), iim,jjm, hist_hori_id, &
3279         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3280    ! Growth Autotrophic Respiration
3281    CALL histdef (hist_id_stom_IPCC, &
3282         &               TRIM("rGrowth"), &
3283         &               TRIM("Growth Autotrophic Respiration"), &
3284         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
3285         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3286    ! Maintenance Autotrophic Respiration
3287    CALL histdef (hist_id_stom_IPCC, &
3288         &               TRIM("rMaint"), &
3289         &               TRIM("Maintenance Autotrophic Respiration"), &
3290         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
3291         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3292    ! CO2 Flux from Atmosphere due to NPP Allocation to Leaf
3293    CALL histdef (hist_id_stom_IPCC, &
3294         &               TRIM("nppLeaf"), &
3295         &               TRIM("CO2 Flux from Atmosphere due to NPP Allocation to Leaf"), &
3296         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
3297         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3298    ! CO2 Flux from Atmosphere due to NPP Allocation to Wood
3299    CALL histdef (hist_id_stom_IPCC, &
3300         &               TRIM("nppStem"), &
3301         &               TRIM("CO2 Flux from Atmosphere due to NPP Allocation to Stem"), &
3302         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
3303         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3304    ! CO2 Flux from Atmosphere due to NPP Allocation to Root
3305    CALL histdef (hist_id_stom_IPCC, &
3306         &               TRIM("nppRoot"), &
3307         &               TRIM("CO2 Flux from Atmosphere due to NPP Allocation to Root"), &
3308         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
3309         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3310    ! Net Carbon Mass Flux out of Atmophere due to Net Ecosystem Productivity on Land.
3311    CALL histdef (hist_id_stom_IPCC, &
3312         &               TRIM("nep"), &
3313         &               TRIM("Net Carbon Mass Flux out of Atmophere due to Net Ecosystem Productivity."), &
3314         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
3315         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3316
3317    CALL histdef(hist_id_stom_IPCC, 'RESOLUTION_X', 'E-W resolution', 'm', &
3318         & iim,jjm, hist_hori_id, 1,1,1, -99, 32, 'once(scatter(X))', dt, hist_dt)
3319    CALL histdef(hist_id_stom_IPCC, 'RESOLUTION_Y', 'N-S resolution', 'm', &
3320         & iim,jjm, hist_hori_id, 1,1,1, -99, 32, 'once(scatter(X))', dt, hist_dt)
3321    CALL histdef(hist_id_stom_IPCC, 'CONTFRAC', 'Continental fraction', '1', &
3322         & iim,jjm, hist_hori_id, 1,1,1, -99, 32, 'once(scatter(X))', dt, hist_dt)
3323    CALL histdef(hist_id_stom_IPCC, 'Areas', 'Mesh areas', 'm2', &
3324         & iim,jjm, hist_hori_id, 1,1,1, -99, 32, 'once(scatter(X))', dt, hist_dt)
3325
3326  END SUBROUTINE ioipslctrl_histstomipcc
3327
3328!! ================================================================================================================================
3329!! SUBROUTINE    : ioipslctrl_restini
3330!!
3331!>\BRIEF         This subroutine initialize the restart files in ORCHDIEE.
3332!!
3333!! DESCRIPTION   : This subroutine initialize restart files in ORCHIDEE. IOIPSL is used for writing the restart files.
3334!!                 This subroutine was previously called intsurf_restart and located in module intersurf.
3335!!
3336!! RECENT CHANGE(S): None
3337!!
3338!! \n
3339!_ ================================================================================================================================
3340  SUBROUTINE ioipslctrl_restini(istp, date0, dt, rest_id, rest_id_stom, itau_offset, date0_shifted)
3341
3342    USE mod_orchidee_para
3343    !
3344    !  This subroutine initialized the restart file for the land-surface scheme
3345    !
3346    IMPLICIT NONE
3347    !
3348    INTEGER(i_std), INTENT(in)                  :: istp      !! Time step of the restart file
3349    REAL(r_std)                                 :: date0     !! The date at which itau = 0
3350    REAL(r_std)                                 :: dt        !! Time step
3351    INTEGER(i_std), INTENT(out)                 :: rest_id, rest_id_stom   !! ID of the restart file
3352    INTEGER(i_std), INTENT(out)                 :: itau_offset    !! Note the result is always itau_offset=0 as overwrite_time=TRUE
3353    REAL(r_std), INTENT(out)                    :: date0_shifted  !! Note the result is always date0_shifted=date0 as overwrite_time=TRUE
3354
3355
3356    !  LOCAL
3357    !
3358    REAL(r_std)                 :: dt_rest, date0_rest
3359    INTEGER(i_std)              :: itau_dep
3360    INTEGER(i_std),PARAMETER    :: llm=1
3361    REAL(r_std), DIMENSION(llm) :: lev
3362    LOGICAL, PARAMETER          :: overwrite_time=.TRUE. !! Always override the date from the restart files for SECHIBA and STOMATE.
3363                                                         !! The date is taken from the gcm or from the driver restart file.
3364    REAL(r_std)                 :: in_julian, rest_julian
3365    INTEGER(i_std)              :: yy, mm, dd
3366    REAL(r_std)                 :: ss
3367    !
3368    !Config Key   = SECHIBA_restart_in
3369    !Config Desc  = Name of restart to READ for initial conditions
3370    !Config If    = OK_SECHIBA
3371    !Config Def   = NONE
3372    !Config Help  = This is the name of the file which will be opened
3373    !Config         to extract the initial values of all prognostic
3374    !Config         values of the model. This has to be a netCDF file.
3375    !Config         Not truly COADS compliant. NONE will mean that
3376    !Config         no restart file is to be expected.
3377    !Config Units = [FILE]
3378!-
3379    CALL getin_p('SECHIBA_restart_in',restname_in)
3380    IF (printlev >= 2) WRITE(numout,*) 'Restart file for sechiba: ', restname_in
3381    !-
3382    !Config Key   = SECHIBA_rest_out
3383    !Config Desc  = Name of restart files to be created by SECHIBA
3384    !Config If    = OK_SECHIBA
3385    !Config Def   = sechiba_rest_out.nc
3386    !Config Help  = This variable give the name for
3387    !Config         the restart files. The restart software within
3388    !Config         IOIPSL will add .nc if needed.
3389    !Config Units = [FILE]
3390    !
3391    CALL getin_p('SECHIBA_rest_out', restname_out)
3392 
3393    lev(:) = zero
3394    itau_dep = istp
3395    in_julian = itau2date(istp, date0, dt)
3396    date0_rest = date0
3397    dt_rest = dt
3398    !
3399    IF (is_root_prc) THEN
3400      CALL restini( restname_in, iim_g, jjm_g, lon_g, lat_g, llm, lev, &
3401         &  restname_out, itau_dep, date0_rest, dt_rest, rest_id, overwrite_time)
3402      nb_restfile_ids=nb_restfile_ids+1
3403      restfile_ids(nb_restfile_ids)=rest_id
3404    ELSE
3405       rest_id=0
3406    ENDIF
3407    CALL bcast (itau_dep)
3408    CALL bcast (date0_rest)
3409    CALL bcast (dt_rest)
3410    !
3411    !  itau_dep of SECHIBA is phased with the GCM if needed
3412    !
3413    rest_julian = itau2date(itau_dep, date0_rest, dt_rest)
3414
3415    ! Note by JG
3416    ! restini never modifies itau_dep and date0_rest when overwrite_time=TRUE.
3417    ! This means that itau_dep=istp and date0_rest=date0 => rest_julian=in_julian.
3418    ! The result of below IF will therfor always be itau_offset=0 and date0_shifted=date0
3419    IF ( ABS( in_julian - rest_julian) .GT. dt/one_day .AND. .NOT. OFF_LINE_MODE ) THEN
3420       WRITE(numout,*) 'The SECHIBA restart is not for the same timestep as the GCM,'
3421       WRITE(numout,*) 'the two are synchronized. The land-surface conditions can not impose'
3422       WRITE(numout,*) 'the chronology of the simulation.'
3423       WRITE(numout,*) 'Time step of the GCM :', istp, 'Julian day : ', in_julian
3424       CALL ju2ymds(in_julian, yy, mm, dd, ss)
3425       WRITE(numout,*) 'In other word (yy,mm,dd,ss) : ', yy, mm, dd, ss
3426       WRITE(numout,*) 'Time step of SECHIBA :', itau_dep, 'Julian day : ', rest_julian
3427       CALL ju2ymds(rest_julian, yy, mm, dd, ss)
3428       WRITE(numout,*) 'In other word (yy,mm,dd,ss) : ', yy, mm, dd, ss
3429       
3430       itau_offset = itau_dep - istp
3431       date0_shifted = date0 - itau_offset*dt/one_day
3432       
3433       WRITE(numout,*) 'The new starting date is :', date0_shifted
3434       CALL ju2ymds(date0_shifted, yy, mm, dd, ss)
3435       WRITE(numout,*) 'In other word (yy,mm,dd,ss) : ', yy, mm, dd, ss
3436    ELSE
3437       itau_offset = 0
3438       date0_shifted = date0
3439    ENDIF
3440
3441    !=====================================================================
3442    !- 1.5 Restart file for STOMATE
3443    !=====================================================================
3444    IF ( ok_stomate ) THEN 
3445       !-
3446       ! STOMATE IS ACTIVATED
3447       !-
3448       !Config Key   = STOMATE_RESTART_FILEIN
3449       !Config Desc  = Name of restart to READ for initial conditions of STOMATE
3450       !Config If    = STOMATE_OK_STOMATE
3451       !Config Def   = NONE
3452       !Config Help  = This is the name of the file which will be opened
3453       !Config         to extract the initial values of all prognostic
3454       !Config         values of STOMATE.
3455       !Config Units = [FILE]
3456       !-
3457       CALL getin_p('STOMATE_RESTART_FILEIN',stom_restname_in)
3458       IF (printlev >= 2) WRITE(numout,*) 'STOMATE INPUT RESTART_FILE', stom_restname_in
3459       !-
3460       !Config Key   = STOMATE_RESTART_FILEOUT
3461       !Config Desc  = Name of restart files to be created by STOMATE
3462       !Config If    = STOMATE_OK_STOMATE
3463       !Config Def   = stomate_rest_out.nc
3464       !Config Help  = This is the name of the file which will be opened
3465       !Config         to write the final values of all prognostic values
3466       !Config         of STOMATE.
3467       !Config Units = [FILE]
3468       !-
3469       CALL getin_p('STOMATE_RESTART_FILEOUT', stom_restname_out)
3470       IF (printlev >= 2) WRITE(numout,*) 'STOMATE OUTPUT RESTART_FILE', stom_restname_out
3471       !-
3472       IF (is_root_prc) THEN
3473         CALL restini (stom_restname_in, iim_g, jjm_g, lon_g, lat_g, llm, lev, &
3474            &  stom_restname_out, itau_dep, date0_rest, dt_rest, rest_id_stom, overwrite_time)
3475         nb_restfile_ids=nb_restfile_ids+1
3476         restfile_ids(nb_restfile_ids)=rest_id_stom
3477       ELSE
3478         rest_id_stom=0
3479       ENDIF
3480       CALL bcast (itau_dep)
3481       CALL bcast (date0_rest)
3482       CALL bcast (dt_rest)
3483       !-
3484    ENDIF
3485  END SUBROUTINE ioipslctrl_restini
3486
3487
3488!! ================================================================================================================================
3489!! SUBROUTINE    : ioipslctrl_restclo
3490!!
3491!>\BRIEF         This subroutine close the restart files in ORCHDIEE.
3492!!
3493!! DESCRIPTION   : This subroutine close restart files in ORCHIDEE. IOIPSL is used for writing the restart files.
3494!!                 
3495!!
3496!! RECENT CHANGE(S): None
3497!!
3498!! \n
3499!_ ================================================================================================================================
3500  SUBROUTINE ioipslctrl_restclo
3501  IMPLICIT NONE
3502    INTEGER(i_std) :: n
3503   
3504    IF (is_root_prc) THEN
3505      DO n=1,nb_restfile_ids
3506        CALL restclo(restfile_ids(n))
3507      ENDDO
3508    ENDIF
3509   
3510  END SUBROUTINE ioipslctrl_restclo
3511   
3512
3513END MODULE ioipslctrl
Note: See TracBrowser for help on using the repository browser.