source: branches/publications/ORCHIDEE_gmd-2018-57/src_sechiba/ioipslctrl.f90

Last change on this file was 3965, checked in by jan.polcher, 8 years ago

Merge with trunk at revision3959.
This includes all the developments made for CMIP6 and passage to XIOS2.
All conflicts are resolved and the code compiles.

But it still does not link because of an "undefined reference to `_intel_fast_memmove'"

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