source: tags/ORCHIDEE_4_1/ORCHIDEE/src_sechiba/ioipslctrl.f90 @ 7761

Last change on this file since 7761 was 7621, checked in by josefine.ghattas, 2 years ago

Correction on name of variable. The variables changed name in call to histwrite in revision [7615].

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