source: branches/publications/ORCHIDEE-Clateral/src_sechiba/ioipslctrl.f90 @ 7329

Last change on this file since 7329 was 3549, checked in by bertrand.guenet, 8 years ago

update between the trunk rev 3340 and SOM it's still not working

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