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

Last change on this file since 7525 was 7525, checked in by sebastiaan.luyssaert, 2 years ago

Fix for ticket #816

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