source: branches/publications/ORCHIDEE_2.2_r7266/ORCHIDEE/src_sechiba/ioipslctrl.f90 @ 7541

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