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

Last change on this file since 7476 was 7265, checked in by agnes.ducharne, 3 years ago

Integrated r5705 (solay now in meters in output files), and small changes with no impact on code (r6220, r6565, r6567) from the trunk. Checked with a 5d run.

File size: 193.3 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          CALL histdef(hist_id, 'ACond', 'Aerodynamic conductance', 'm/s',  &
1045               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
1046          IF ( do_floodplains ) THEN
1047             CALL histdef(hist_id, 'Qflood', 'Floodplain Evaporation', 'kg/m^2/s', &
1048                  & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop_scinsec(1), dt,dw)
1049          ENDIF
1050          !-
1051          !- Surface turbulence
1052          !-
1053          CALL histdef(hist_id, 'Z0m', 'Roughness height for momentum', 'm',  &
1054               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
1055          CALL histdef(hist_id, 'Z0h', 'Roughness height for heat', 'm',  &
1056               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
1057          CALL histdef(hist_id, 'EffectHeight', 'Effective displacement height (h-d)', 'm',  &
1058               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
1059          !-
1060          !-
1061          !-  Cold Season Processes
1062          !-
1063          CALL histdef(hist_id, 'SnowFrac', 'Snow cover fraction', '1',  &
1064               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
1065          CALL histdef(hist_id, 'SAlbedo', 'Snow albedo', '1', &
1066               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
1067          !-
1068          !- Hydrologic variables
1069          !-
1070          IF ( river_routing ) THEN
1071             CALL histdef(hist_id, 'slowr', 'Slow flow reservoir', 'kg/m^2', &
1072                  & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
1073             CALL histdef(hist_id, 'fastr', 'Fast flow reservoir', 'kg/m^2', &
1074                  & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
1075             CALL histdef(hist_id, 'streamr', 'Stream flow reservoir', 'kg/m^2', &
1076                  & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
1077             CALL histdef(hist_id, 'lakevol', 'Volume in lake reservoir', 'kg/m^2', &
1078                  & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
1079             CALL histdef(hist_id, 'pondr', 'Ponds reservoir', 'kg/m^2', &
1080                  & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
1081             !-
1082             !-
1083             !-
1084             CALL histdef(hist_id, 'SwampMap', 'Map of swamp areas', 'm^2', &
1085                  & iim,jjm, hori_id, 1,1,1, -99, 32, once(1), dt,dw)
1086             CALL histdef(hist_id, 'Dis', 'Simulated River Discharge', 'm^3/s', &
1087                  & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop_scinsec(2), dt,dw)
1088             CALL histdef(hist_id, 'CoastalFlow', 'Diffuse coastal flow', 'm^3/s', &
1089                  & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop_scinsec(2), dt,dw)
1090             CALL histdef(hist_id, 'RiverFlow', 'River flow to the oceans', 'm^3/s', &
1091                  & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop_scinsec(2), dt,dw)
1092             IF ( do_irrigation ) THEN
1093                CALL histdef(hist_id, 'IrrigationMap', 'Map of irrigated areas', 'm^2', &
1094                     & iim,jjm, hori_id, 1,1,1, -99, 32, once(1), dt,dw)
1095             ENDIF
1096             !
1097             !
1098             IF ( do_floodplains ) THEN
1099                CALL histdef(hist_id, 'FloodplainsMap', 'Map of flooded areas', 'm^2', &
1100                     & iim,jjm, hori_id, 1,1,1, -99, 32, once(1), dt,dw)
1101                CALL histdef(hist_id, 'FloodFrac', 'Floodplain Fraction', '-', &
1102                     & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
1103             ENDIF
1104          ENDIF
1105          !-
1106          CALL histdef(hist_id, 'humrel', 'Soil moisture stress', '-',  &
1107               & iim,jjm, hori_id, nvm,1,nvm, vegax_id, 32, avescatter(8), dt,dw)
1108          !-
1109          !-  The carbon budget
1110          !-
1111          CALL histdef(hist_id, 'cimean', 'Stomatal CO2 concentation', 'mmole/m2/s', &
1112               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(10), dt,dw)
1113          CALL histdef(hist_id, 'GPP', 'Net assimilation of carbon by the vegetation', 'gC/m^2/s', &
1114               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, fluxop_scinsec(1), dt,dw)
1115          CALL histdef(hist_id, 'gsmean', 'mean stomatal conductance', 'mol/m2/s', &
1116               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(8), dt,dw)
1117          CALL histdef(hist_id, 'cim', 'cim', 'ppm', &
1118               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(10), dt,dw)
1119          CALL histdef(hist_id, 'leafci', 'leaf Ci', 'ppm', &
1120               & iim,jjm, hori_id,nlai+1, 1, nlai+1, laiax_id, 32, avescatter(10), dt,dw)
1121          CALL histdef(hist_id, 'gs', 'gs', '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, 'assimi', 'assimi', '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, 'Rd', 'Rd', 'mol m-2 s-1', &
1126               & iim,jjm, hori_id, nlai+1, 1, nlai+1, laiax_id, 32, avescatter(10), dt,dw)
1127          CALL histdef(hist_id, 'Cc', 'Cc', 'ppm', &
1128               & iim,jjm, hori_id, nlai+1, 1, nlai+1, laiax_id, 32, avescatter(10), dt,dw)
1129          CALL histdef(hist_id, 'limitphoto', 'limitphoto', '-', &
1130               & iim,jjm, hori_id, nlai+1, 1, nlai+1, laiax_id, 32, avescatter(10), dt,dw)
1131          CALL histdef(hist_id, 'Vc', 'Vc', 'mol 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, 'Vj', 'Vj', 'mol e- m-2 s-1', &
1134               & iim,jjm, hori_id, nlai+1, 1, nlai+1, laiax_id, 32, avescatter(10), dt,dw)
1135          CALL histdef(hist_id, 'gm', 'gm', 'mol m-2 s-1', &
1136               & iim,jjm, hori_id, 1, 1, 1, -99, 32, avescatter(10), dt,dw)
1137          CALL histdef(hist_id, 'gammastar', 'gammastar', 'ppm', &
1138               & iim, jjm, hori_id, 1, 1, 1, -99, 32, avescatter(10), dt,dw)
1139          CALL histdef(hist_id, 'Kmo', 'Kmo', 'ppm', &
1140               & iim, jjm, hori_id, 1, 1, 1, -99, 32, avescatter(10), dt,dw)
1141          CALL histdef(hist_id, 'Kmc', 'Kmc', 'ppm', &
1142               & iim, jjm, hori_id, 1, 1, 1, -99, 32, avescatter(10), dt,dw)
1143
1144          IF ( ok_stomate ) THEN
1145             CALL histdef(hist_id, 'NEE', 'Net Ecosystem Exchange', '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, 'maint_resp', 'Maintenance 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, 'hetero_resp', 'Heterotrophic 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, 'growth_resp', 'Growth respiration', 'gC/m^2/s', &
1152                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, fluxop_scinsec(1), dt,dw)
1153             CALL histdef(hist_id, 'npp', 'Net Primary Production', 'gC/m^2/s', &
1154                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, fluxop_scinsec(1), dt,dw)
1155          ENDIF
1156          !
1157      ENDIF
1158       !-
1159       !- Forcing and grid information
1160       !-
1161       CALL histdef(hist_id, 'LandPoints', 'Land Points', '1', &
1162            & iim,jjm, hori_id, 1,1,1, -99, 32, once(10), dt,dw) 
1163       CALL histdef(hist_id, 'Areas', 'Mesh areas', 'm2', &
1164            & iim,jjm, hori_id, 1,1,1, -99, 32, once(1), dt, dw)
1165       CALL histdef(hist_id, 'Contfrac', 'Continental fraction', '1', &
1166            & iim,jjm, hori_id, 1,1,1, -99, 32, once(1), dt, dw)
1167       !-
1168       ! Write the names of the pfts in the history files
1169       global_attribute="PFT_name"
1170       DO i=1,nvm
1171          WRITE(global_attribute(9:10),"(I2.2)") i
1172          CALL histglobal_attr(hist_id, global_attribute, PFT_name(i))
1173       ENDDO
1174       !-
1175       CALL histend(hist_id)
1176    ENDIF ! IF (is_omp_root)
1177 
1178    END IF !IF ( dw == 0 )
1179    !
1180    !
1181    ! Second SECHIBA hist file
1182    !
1183    !-
1184    !Config Key   = SECHIBA_HISTFILE2
1185    !Config Desc  = Flag to switch on histfile 2 for SECHIBA (hi-frequency ?)
1186    !Config If    = OK_SECHIBA
1187    !Config Def   = n
1188    !Config Help  = This Flag switch on the second SECHIBA writing for hi (or low)
1189    !Config         frequency writing. This second output is optional and not written
1190    !Config         by default.
1191    !Config Units = [FLAG]
1192    !-
1193    ok_histfile2=.FALSE.
1194    CALL getin_p('SECHIBA_HISTFILE2', ok_histfile2)
1195    IF (printlev >= 2) WRITE(numout,*) 'SECHIBA_HISTFILE2 ', ok_histfile2
1196    !
1197    !-
1198    !Config Key   = WRITE_STEP2
1199    !Config Desc  = Frequency in seconds at which to WRITE output
1200    !Config If    = SECHIBA_HISTFILE2
1201    !Config Def   = 1800.0
1202    !Config Help  = This variables gives the frequency the output 2 of
1203    !Config         the model should be written into the netCDF file.
1204    !Config         It does not affect the frequency at which the
1205    !Config         operations such as averaging are done.
1206    !Config         That is IF the coding of the calls to histdef
1207    !Config         are correct !
1208    !Config Units = [seconds]
1209    !-
1210    dw2 = 1800.0
1211    CALL getin_p('WRITE_STEP2', dw2)
1212   
1213    ! Deactivate sechiba_histfile2 if the frequency is set to zero
1214    IF ( dw2 == 0 ) THEN
1215       ok_histfile2=.FALSE.
1216       IF (printlev >= 2) WRITE(numout,*) 'WRITE_STEP2 was set to zero and therfore SECHIBA_HISTFILE2 is deactivated.'
1217    ELSE IF ( hist_id < 0 ) THEN
1218       ! Deactivate all history files if sechiba_history file is deactivated
1219       ok_histfile2=.FALSE.
1220       IF (printlev >= 2) WRITE(numout,*) 'SECHIBA_HISTFILE2 will not be created because sechiba_history file is deactivated.'
1221    END IF
1222
1223    hist2_id = -1
1224    !
1225    IF (ok_histfile2) THEN
1226       !-
1227       !Config Key   = SECHIBA_OUTPUT_FILE2
1228       !Config Desc  = Name of file in which the output number 2 is going to be written
1229       !Config If    = SECHIBA_HISTFILE2
1230       !Config Def   = sechiba_out_2.nc
1231       !Config Help  = This file is going to be created by the model
1232       !Config         and will contain the output 2 from the model.
1233       !Config Units = [FILE]
1234       !-
1235       histname2='sechiba_out_2.nc'
1236       CALL getin_p('SECHIBA_OUTPUT_FILE2', histname2)
1237       IF (printlev >= 2) WRITE(numout,*) 'SECHIBA_OUTPUT_FILE2 ', histname2
1238       !-
1239       !Config Key   = SECHIBA_HISTLEVEL2
1240       !Config Desc  = SECHIBA history 2 output level (0..10)
1241       !Config If    = SECHIBA_HISTFILE2
1242       !Config Def   = 1
1243       !Config Help  = Chooses the list of variables in the history file.
1244       !Config         Values between 0: nothing is written; 10: everything is
1245       !Config         written are available More details can be found on the web under documentation.
1246       !Config         web under documentation.
1247       !Config         First level contains all ORCHIDEE outputs.
1248       !Config Units = [-]
1249       !-
1250       hist2_level = 1
1251       CALL getin_p('SECHIBA_HISTLEVEL2', hist2_level)
1252       !-
1253       IF (printlev >= 2) WRITE(numout,*) 'SECHIBA history level 2 : ',hist2_level
1254       IF ( (hist2_level > max_hist_level).OR.(hist2_level < 0) ) THEN
1255          STOP 'This history level 2 is not allowed'
1256       ENDIF
1257       !
1258       !-
1259       !- define operations as a function of history level.
1260       !- Above hist2_level, operation='never'
1261       !-
1262       ave2(1:max_hist_level) = 'ave(scatter(X))'
1263       IF (hist2_level < max_hist_level) THEN
1264          ave2(hist2_level+1:max_hist_level) = 'never'
1265       ENDIF
1266       sumscatter2(1:max_hist_level) = 't_sum(scatter(X))'
1267       IF (hist2_level < max_hist_level) THEN
1268          sumscatter2(hist2_level+1:max_hist_level) = 'never'
1269       ENDIF
1270       avecels2(1:max_hist_level) = 'ave(cels(scatter(X)))'
1271       IF (hist2_level < max_hist_level) THEN
1272          avecels2(hist2_level+1:max_hist_level) = 'never'
1273       ENDIF
1274       avescatter2(1:max_hist_level) = 'ave(scatter(X))'
1275       IF (hist2_level < max_hist_level) THEN
1276          avescatter2(hist2_level+1:max_hist_level) = 'never'
1277       ENDIF
1278       tmincels2(1:max_hist_level) = 't_min(cels(scatter(X)))'
1279       IF (hist2_level < max_hist_level) THEN
1280          tmincels2(hist2_level+1:max_hist_level) = 'never'
1281       ENDIF
1282       tmaxcels2(1:max_hist_level) = 't_max(cels(scatter(X)))'
1283       IF (hist2_level < max_hist_level) THEN
1284          tmaxcels2(hist2_level+1:max_hist_level) = 'never'
1285       ENDIF
1286       fluxop2(1:max_hist_level) = flux_op
1287       IF (hist2_level < max_hist_level) THEN
1288          fluxop2(hist2_level+1:max_hist_level) = 'never'
1289       ENDIF
1290       fluxop_scinsec2(1:max_hist_level) = flux_scinsec
1291       IF (hist2_level < max_hist_level) THEN
1292          fluxop_scinsec2(hist2_level+1:max_hist_level) = 'never'
1293       ENDIF
1294       once2(1:max_hist_level) = 'once(scatter(X))'
1295       IF (hist2_level < max_hist_level) THEN
1296          once2(hist2_level+1:max_hist_level) = 'never'
1297       ENDIF
1298       !
1299       IF (is_omp_root) THEN
1300          IF ( .NOT. almaoutput ) THEN
1301             !-
1302             IF ( grid_type == regular_lonlat ) THEN
1303#ifdef CPP_PARA
1304                CALL histbeg(histname2, iim, lon_rect, jjm, lat_rect, 1, iim, 1, jjm, &
1305                     &     istp_old, date0, dt, hori_id2, hist2_id,orch_domain_id)
1306#else
1307                CALL histbeg(histname2, iim, lon_rect, jjm, lat_rect, 1, iim, 1, jjm, &
1308                     &     istp_old, date0, dt, hori_id2, hist2_id)
1309#endif
1310                IF (printlev >= 2) WRITE(numout,*)  'HISTBEG2 --->',istp_old,date0,dt,dw2,hist2_id
1311             ELSE
1312#ifdef CPP_PARA
1313                CALL histbeg(histname2, iim, lon, jjm, lat, 1, iim, 1, jjm, &
1314                     &     istp_old, date0, dt, hori_id2, hist2_id,domain_id=orch_domain_id)
1315#else
1316                CALL histbeg(histname2, iim, lon, jjm, lat, 1, iim, 1, jjm, &
1317                     &     istp_old, date0, dt, hori_id2, hist2_id)
1318#endif
1319             ENDIF
1320             !-
1321             CALL histvert(hist2_id, 'veget', 'Vegetation types', '1', &
1322                  &    nvm,   veg, vegax_id2)
1323             CALL histvert(hist2_id, 'laiax', 'Nb LAI', '1', &
1324                  &    nlai+1,   indlai, laiax_id2)
1325             CALL histvert(hist2_id, 'solth', 'Soil levels',      'm', &
1326                  &    ngrnd, znt, solax_id2)
1327             CALL histvert(hist2_id, 'soiltyp', 'Soil types',      '1', &
1328                  &    nstm, soltyp, soltax_id2)
1329             CALL histvert(hist2_id, 'nobio', 'Other surface types',      '1', &
1330                  &    nnobio, nobiotyp, nobioax_id2)
1331             CALL histvert(hist2_id, 'albtyp', 'Albedo Types',     '1', &
1332                  &    2, albtyp, albax_id2)
1333             CALL histvert(hist2_id, 'solay', 'Hydrol soil levels',      'm', &
1334                  &    nslm, solay, solayax_id2)
1335             !-
1336             !- SECHIBA_HISTLEVEL2 = 1
1337             !-
1338             CALL histdef(hist2_id, 'ptn', 'Deep ground temperature', 'K', &
1339                  & iim,jjm, hori_id2, ngrnd, 1, ngrnd, solax_id2, 32, avescatter2(2),  dt, dw2) 
1340
1341             CALL histdef(hist2_id, 'mrsos', "Moisture in Upper 0.1 m of Soil Column", "kg m-2", &
1342                  & iim,jjm, hori_id2, 1, 1, 1, -99, 32, avescatter2(2), dt,dw2)           
1343
1344             CALL histdef(hist2_id, 'mrso', "Total Soil Moisture Content", "kg m-2", &
1345                  & iim,jjm, hori_id2, 1, 1, 1, -99, 32, avescatter2(11), dt,dw2)
1346             
1347             CALL histdef(hist2_id, 'mrros', "Surface Runoff", "kg m-2 s-1", &
1348                  & iim,jjm, hori_id2, 1, 1, 1, -99, 32, fluxop_scinsec2(11), dt,dw2)
1349
1350             CALL histdef(hist2_id, 'mrro', "Total Runoff", "kg m-2 s-1", &
1351                  & iim,jjm, hori_id2, 1, 1, 1, -99, 32, fluxop_scinsec2(2), dt,dw2)     
1352
1353             !-
1354             !- SECHIBA_HISTLEVEL2 = 2
1355             !-
1356             CALL histdef(hist2_id, 'cdrag', 'Drag coefficient for LE and SH', '?',  &
1357                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(2), dt, dw2)
1358             CALL histdef(hist2_id, 'soilalb_vis', 'Soil Albedo visible', '1', &
1359                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(2), dt,dw2)
1360             CALL histdef(hist2_id, 'soilalb_nir', 'Soil Albedo near infrared', '1', &
1361                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(2), dt,dw2)
1362             CALL histdef(hist2_id, 'vegalb_vis', 'Vegetation Albedo visible', '1', &
1363                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(2), dt,dw2)
1364             CALL histdef(hist2_id, 'vegalb_nir', 'Vegetation Albedo near infrared', '1', &
1365                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(2), dt,dw2)
1366             CALL histdef(hist2_id, 'z0m', 'Surface roughness for momentum', 'm',  &
1367                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(2), dt, dw2)
1368             CALL histdef(hist2_id, 'z0h', 'Surface roughness for heat', 'm',  &
1369                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(2), dt, dw2)
1370             CALL histdef(hist2_id, 'coastalflow', 'Diffuse coastal flow', 'm^3/s', &
1371                  & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop_scinsec2(2), dt, dw2)
1372             CALL histdef(hist2_id, 'riverflow', 'River flow to the oceans', 'm^3/s', &
1373                  & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop_scinsec2(2), dt, dw2) 
1374             CALL histdef(hist2_id, 'tsol_rad', 'Radiative surface temperature', 'C', &
1375                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avecels2(2), dt, dw2)
1376             IF ( do_floodplains ) THEN
1377                CALL histdef(hist2_id, 'floodout', 'Flow out of floodplains', 'mm/d', &
1378                     & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop2(2), dt,dw2)
1379                CALL histdef(hist2_id, 'vevapflo', 'Floodplains evaporation', 'mm/d', &
1380                     & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop2(2), dt, dw2)
1381                CALL histdef(hist2_id, 'flood_frac', 'Flooded fraction', '1', &
1382                     & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(2), dt,dw2)
1383                CALL histdef(hist2_id, 'reinfiltration', 'Reinfiltration from floodplains', 'mm/d', &
1384                     & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop2(2), dt,dw2)
1385             ENDIF
1386             CALL histdef(hist2_id, 'vevapnu', 'Bare soil evaporation', 'mm/d', &
1387                  & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop2(2), dt, dw2)
1388             CALL histdef(hist2_id, 'temp_sol', 'New Surface Temperature', 'C', &
1389                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avecels2(2), dt, dw2)
1390             CALL histdef(hist2_id, 'qsurf', 'Near surface specific humidity', 'g/g',  &
1391                  & iim,jjm, hori_id2, 1,1,1, -99, 32, ave2(2), dt, dw2)
1392             CALL histdef(hist2_id, 'albedo', 'Albedo', '1', &
1393                  & iim,jjm, hori_id2, 2,1,2, albax_id2, 32, avescatter2(2), dt, dw2)
1394             CALL histdef(hist2_id, 'fluxsens', 'Sensible Heat Flux', 'W/m^2',  &
1395                  & iim,jjm, hori_id2, 1,1,1, -99, 32, ave2(2), dt, dw2)
1396             CALL histdef(hist2_id, 'fluxlat', 'Latent Heat Flux', 'W/m^2',  &
1397                  & iim,jjm, hori_id2, 1,1,1, -99, 32, ave2(2), dt, dw2)
1398             CALL histdef(hist2_id, 'emis', 'Surface emissivity', '1', &
1399                  & iim,jjm, hori_id2, 1,1,1, -99, 32, ave2(2), dt, dw2)
1400             !-
1401             !- SECHIBA_HISTLEVEL2 = 3
1402             !-
1403             CALL histdef(hist2_id, 'evap', 'Evaporation', 'mm/d', &
1404                  & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop2(3), dt, dw2)
1405             CALL histdef(hist2_id, 'rain', 'Rainfall', 'mm/d',  &
1406                  & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop2(3), dt, dw2)
1407             CALL histdef(hist2_id, 'snowf', 'Snowfall', 'mm/d',  &
1408                  & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop2(3), dt, dw2)
1409             CALL histdef(hist2_id, 'netrad', 'Net radiation', 'W/m^2',  &
1410                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(3), dt, dw2)
1411             CALL histdef(hist2_id, 'lai', 'Leaf Area Index', '1', &
1412                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(3), dt, dw2)
1413             IF ( river_routing ) THEN
1414                CALL histdef(hist2_id, 'basinmap', 'Aproximate map of the river basins', ' ', &
1415                     & iim,jjm, hori_id2, 1,1,1, -99, 32, once2(3), dt, dw2) 
1416                CALL histdef(hist2_id, 'nbrivers', 'Number or rivers in the outflow grid box', ' ', &
1417                     & iim,jjm, hori_id2, 1,1,1, -99, 32, once2(3), dt, dw2) 
1418             ENDIF
1419
1420             !-
1421             !- SECHIBA_HISTLEVEL2 = 4
1422             !-
1423             CALL histdef(hist2_id, 'subli', 'Sublimation', 'mm/d', &
1424                  & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop2(4), dt, dw2)
1425             CALL histdef(hist2_id, 'runoff', 'Surface runoff', 'mm/d', &
1426                  & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop2(4), dt, dw2)
1427             CALL histdef(hist2_id, 'drainage', 'Deep drainage', 'mm/d', &
1428                  & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop2(4), dt, dw2)
1429             IF ( river_routing ) THEN
1430                CALL histdef(hist2_id, 'riversret', 'Return from endorheic rivers', 'mm/d', &
1431                     & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop2(4), dt, dw2)
1432                CALL histdef(hist2_id, 'hydrographs', 'Hydrographs of gridbox outflow', 'm^3/s', &
1433                     & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop_scinsec2(4), dt, dw2)
1434             ENDIF
1435             CALL histdef(hist2_id, 'evapnu_soil', 'Bare soil evap 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, 'drainage_soil', 'Drainage 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, 'transpir_soil', 'Transpir 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, 'runoff_soil', 'Runoff for soil type', 'mm/d', &
1442                     & iim,jjm, hori_id2, nstm, 1, nstm, soltax_id2, 32, fluxop2(4), dt, dw2)
1443             CALL histdef(hist2_id, 'tair', 'Air Temperature', 'K',  &
1444                  & iim,jjm, hori_id2, 1,1,1, -99, 32, ave2(4), dt, dw2)
1445             CALL histdef(hist2_id, 'qair', 'Air humidity', 'g/g',  &
1446                  & iim,jjm, hori_id2, 1,1,1, -99, 32, ave2(4), dt, dw2)
1447            CALL histdef(hist2_id, 'alb_vis', 'Albedo visible', '1', &
1448                  & iim,jjm, hori_id2, 1,1,1, -99, 32, ave2(4), dt, dw2)
1449             CALL histdef(hist2_id, 'alb_nir', 'Albedo near infrared', '1', &
1450                  & iim,jjm, hori_id2, 1,1,1, -99, 32, ave2(4), dt, dw2)
1451             CALL histdef(hist2_id, 'roughheight', 'Effective roughness height', 'm',  &
1452                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(4), dt, dw2)
1453             CALL histdef(hist2_id, 'transpir', 'Transpiration', 'mm/d', &
1454                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, fluxop2(4), dt, dw2)
1455             CALL histdef(hist2_id, 'inter', 'Interception loss', 'mm/d', &
1456                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, fluxop2(4), dt, dw2)
1457             !-
1458             !- SECHIBA_HISTLEVEL2 = 5
1459             !-
1460             CALL histdef(hist2_id, 'tsol_max', 'Maximum Surface Temperature',&
1461                  & 'C', iim,jjm, hori_id2, 1,1,1, -99, 32, tmaxcels2(5), dt, dw2)
1462             CALL histdef(hist2_id, 'tsol_min', 'Minimum Surface Temperature',&
1463                  & 'C', iim,jjm, hori_id2, 1,1,1, -99, 32, tmincels2(5), dt, dw2)
1464             CALL histdef(hist2_id, 'snow', 'Snow mass', 'kg/m^2', &
1465                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(5), dt, dw2)
1466             CALL histdef(hist2_id, 'snowage', 'Snow age', '?', &
1467                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(5), dt, dw2)
1468             CALL histdef(hist2_id, 'snownobio', 'Snow on other surfaces', 'kg/m^2', &
1469                  & iim,jjm, hori_id2, nnobio,1, nnobio, nobioax_id2, 32, avescatter2(5), dt, dw2)
1470             CALL histdef(hist2_id, 'snownobioage', 'Snow age on other surfaces', 'd', &
1471                  & iim,jjm, hori_id2, nnobio,1, nnobio, nobioax_id2, 32, avescatter2(5), dt, dw2)
1472             CALL histdef(hist2_id, 'vegetfrac', 'Fraction of vegetation', '1', &
1473                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(5), dt, dw2)
1474             CALL histdef(hist2_id, 'maxvegetfrac', 'Maximum fraction of vegetation', '1', &
1475                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(5), dt, dw2)
1476             CALL histdef(hist2_id, 'nobiofrac', 'Fraction of other surface types', '1', &
1477                  & iim,jjm, hori_id2, nnobio, 1, nnobio, nobioax_id2, 32, avescatter2(5), dt, dw2)
1478
1479             DO jst=1,nstm
1480               
1481                ! var_name= "mc_1" ... "mc_3"
1482                WRITE (var_name,"('moistc_',i1)") jst
1483                CALL histdef(hist2_id, var_name, 'Soil Moisture profile for soil type', 'm3/m3', &
1484                     & iim,jjm, hori_id2, nslm, 1, nslm, solayax_id2, 32, avescatter2(5), dt, dw2)
1485               
1486                ! var_name= "vegetsoil_1" ... "vegetsoil_3"
1487                WRITE (var_name,"('vegetsoil_',i1)") jst
1488                CALL histdef(hist2_id, var_name, 'Fraction of vegetation on soil types', '%', &
1489                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(5), dt, dw2)
1490               
1491                ! var_name= "kfact_root_1" ... "kfact_root_3"
1492                WRITE (var_name,"('kfactroot_',i1)") jst
1493                CALL histdef(hist2_id, var_name, 'Root fraction profile for soil type', '%', &
1494                     & iim,jjm, hori_id2, nslm, 1, nslm, solayax_id2, 32, avescatter2(5), dt,dw2)
1495             ENDDO
1496               
1497             !-
1498             !- SECHIBA_HISTLEVEL2 = 6
1499             !-
1500             CALL histdef(hist2_id, 'humtot', 'Total Soil Moisture', 'Kg/m^2', &
1501                  & iim,jjm, hori_id2, 1, 1, 1, -99, 32, avescatter2(6), dt, dw2)
1502             CALL histdef(hist2_id, 'humtot_soil', 'Soil Moisture for soil type', 'Kg/m^2', &
1503                  & iim,jjm, hori_id2, nstm, 1, nstm, soltax_id2, 32, avescatter2(6), dt, dw2)
1504             CALL histdef(hist2_id, 'qsintveg', 'Water on canopy', 'Kg/m^2', &
1505                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(6), dt, dw2)
1506             CALL histdef(hist2_id, 'rstruct', 'Structural resistance', 's/m', &
1507                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(6), dt, dw2)
1508             CALL histdef(hist2_id, 'gpp', 'Net assimilation of carbon by the vegetation', 'gC/m^2/s', &
1509                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, fluxop_scinsec2(6), dt,dw2)
1510
1511             IF ( ok_stomate ) THEN
1512                CALL histdef(hist2_id, 'nee', 'Net Ecosystem Exchange', 'kgC/m^2/s', &
1513                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, fluxop_scinsec2(6), dt,dw2)
1514                CALL histdef(hist2_id, 'maint_resp', 'Maintenance 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, 'hetero_resp', 'Heterotrophic 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, 'growth_resp', 'Growth respiration', 'gC/m^2/s', &
1519                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, fluxop_scinsec2(6), dt, dw2)
1520                CALL histdef(hist2_id, 'npp', 'Net Primary Production', 'gC/m^2/s', &
1521                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, fluxop_scinsec2(6), dt, dw2)
1522             ENDIF
1523             CALL histdef(hist2_id, 'precisol', 'Throughfall', 'mm/d',  &
1524                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, fluxop2(6), dt, dw2)
1525             CALL histdef(hist2_id, 'drysoil_frac', 'Fraction of visibly dry soil', '1',  &
1526                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(6), dt, dw2)
1527             CALL histdef(hist2_id, 'evapot', 'Potential evaporation', 'mm/d',  &
1528                  & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop2(6), dt, dw2)
1529             CALL histdef(hist2_id, 'evapot_corr', 'Potential evaporation', 'mm/d',  &
1530                  & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop2(6), dt, dw2)
1531             CALL histdef(hist2_id, 'snowmelt', 'snow melt', 'mm/d', &
1532                  & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop2(6), dt, dw2)
1533
1534             !-
1535             !- SECHIBA_HISTLEVEL2 = 7
1536             !-
1537             CALL histdef(hist2_id, 'swnet', 'Net solar radiation', 'W/m^2',  &
1538                  & iim,jjm, hori_id2, 1,1,1, -99, 32, ave2(7), dt, dw2)
1539             CALL histdef(hist2_id, 'swdown', 'Incident solar radiation', 'W/m^2',  &
1540                  & iim,jjm, hori_id2, 1,1,1, -99, 32, ave2(7), dt, dw2)
1541             CALL histdef(hist2_id, 'lwdown', 'Absorbed downward longwave radiation', 'W/m^2',  &
1542                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(7), dt, dw2)
1543             CALL histdef(hist2_id, 'lwnet', 'Net surface longwave radiation', 'W/m^2',  &
1544                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(7), dt, dw2)
1545             !-
1546             !- SECHIBA_HISTLEVEL2 = 8
1547             !-
1548             IF ( river_routing ) THEN
1549                CALL histdef(hist2_id, 'fastr', 'Fast flow reservoir', 'kg/m^2', &
1550                     & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(8), dt, dw2)
1551                CALL histdef(hist2_id, 'slowr', 'Slow flow reservoir', 'kg/m^2', &
1552                     & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(8), dt, dw2)
1553                CALL histdef(hist2_id, 'streamr', 'Stream flow reservoir', 'kg/m^2', &
1554                     & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(8), dt, dw2)
1555                CALL histdef(hist2_id, 'floodr', 'Floodplains reservoir', 'kg/m^2', &
1556                     & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(8), dt,dw2)
1557                CALL histdef(hist2_id, 'floodh', 'Floodplains height', 'mm', &
1558                     & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(8), dt,dw2)
1559                CALL histdef(hist2_id, 'pondr', 'Ponds reservoir', 'kg/m^2', &
1560                     & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(8), dt,dw2)
1561                CALL histdef(hist2_id, 'lakevol', 'Volume in lake reservoir', 'kg/m^2', &
1562                     & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(8), dt, dw2)
1563                IF ( do_irrigation ) THEN
1564                   CALL histdef(hist2_id, 'irrigation', 'Net irrigation', 'mm/d', &
1565                        & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop2(8), dt, dw2)
1566                   CALL histdef(hist2_id, 'netirrig', 'Net irrigation requirement', 'mm/d', &
1567                        & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop2(8), dt, dw2)
1568                   CALL histdef(hist2_id, 'irrigmap', 'Map of irrigated areas', 'm^2', &
1569                        & iim,jjm, hori_id2, 1,1,1, -99, 32, once2(8), dt, dw2)
1570                ENDIF
1571                CALL histdef(hist2_id, 'floodmap', 'Map of floodplains', 'm^2', &
1572                     & iim,jjm, hori_id2, 1,1,1, -99, 32, once2(8), dt,dw2)
1573                CALL histdef(hist2_id, 'swampmap', 'Map of swamps', 'm^2', &
1574                  & iim,jjm, hori_id2, 1,1,1, -99, 32, once2(8), dt,dw2)
1575             ENDIF
1576             !-
1577             !- SECHIBA_HISTLEVEL2 = 9
1578             !-
1579             CALL histdef(hist2_id, 'beta', 'Beta Function', '1',  &
1580                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(9), dt, dw2)
1581             CALL histdef(hist2_id, 'raero', 'Aerodynamic resistance', 's/m',  &
1582                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(9), dt, dw2)
1583             CALL histdef(hist2_id, 'Wind', 'Wind speed', 'm/s',  &
1584                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(9), dt, dw2)
1585             CALL histdef(hist2_id, 'qsatt' , 'Surface saturated humidity', 'g/g', &
1586                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(9), dt, dw2)
1587             CALL histdef(hist2_id, 'vbeta1', 'Beta for sublimation', '1',  &
1588                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(9), dt, dw2)
1589             CALL histdef(hist2_id, 'vbeta4', 'Beta for bare soil', '1',  &
1590                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(9), dt, dw2)
1591             CALL histdef(hist2_id, 'gsmean', 'mean stomatal conductance', 'mol/m2/s', &
1592                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(9), dt, dw2)
1593             CALL histdef(hist2_id, 'vbeta5', 'Beta for floodplains', '1',  &
1594                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(9), dt, dw2)
1595             CALL histdef(hist2_id, 'reinf_slope', 'Slope index for each grid box', '1', &
1596                  & iim,jjm, hori_id2, 1,1,1, -99, 32, once2(9),  dt,dw2)
1597             CALL histdef(hist2_id, 'soilindex', 'Soil index', '1', &
1598                  & iim,jjm, hori_id2, 1, 1, 1, -99, 32, once2(9),  dt,dw2)
1599             CALL histdef(hist2_id, 'humrel', 'Soil moisture stress', '-',  &
1600                  & iim,jjm, hori_id2, nvm,1,nvm, vegax_id2, 32, avescatter2(9), dt, dw2)
1601             !-
1602             !- SECHIBA_HISTLEVEL2 = 10
1603             !-
1604             CALL histdef(hist2_id, 'cimean', 'Stomatal CO2 concentation', 'mmole/m2/s', &
1605                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt, dw2)
1606             CALL histdef(hist2_id, 'vbeta3', 'Beta for Transpiration', 'mm/d', &
1607                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt, dw2)
1608             CALL histdef(hist2_id, 'rveget', 'Canopy resistance', 's/m', &
1609                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt, dw2)
1610             CALL histdef(hist2_id,'vbeta2','Beta for Interception loss','mm/d', &
1611                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt, dw2)
1612             CALL histdef(hist2_id, 'qsintmax', 'Maximum Interception capacity', 'Kg/m^2', &
1613                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt, dw2)
1614             
1615             IF ( ok_bvoc ) THEN
1616                CALL histdef(hist2_id, 'PAR', 'PAR', 'umol phot/m^2/s',  &
1617                     & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(10), dt,dw2)
1618                IF ( ok_radcanopy ) THEN
1619                   CALL histdef(hist2_id, 'PARsun', 'Sunlit Leaf 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, 'PARsh', 'Shaded Leaf Area PAR', 'umol phot/m^2/s', &
1622                        & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
1623                   CALL histdef(hist2_id, 'laisun', 'Sunlit Leaf Area Index', '1', &
1624                        & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
1625                   CALL histdef(hist2_id, 'laish', 'Shaded Leaf Area Index', '1', &
1626                        & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
1627                   CALL histdef(hist2_id, 'Fdf', 'Fdf', '1',  &
1628                        & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(10), dt,dw2)
1629                   IF ( ok_multilayer ) then
1630                      CALL histdef(hist2_id, 'PARsuntab', 'Sunlit Leaf PAR', 'umol phot/m^2/s', &
1631                           & iim,jjm, hori_id2, nlai+1, 1, nlai+1, laiax_id2, 32, avescatter2(10), dt,dw2)
1632                      CALL histdef(hist2_id, 'PARshtab', 'Shaded Leaf Area PAR', 'umol phot/m^2/s', &
1633                           & iim,jjm, hori_id2, nlai+1, 1, nlai+1, laiax_id2, 32, avescatter2(10), dt,dw2)
1634                   ENDIF
1635                   CALL histdef(hist2_id, 'coszang', 'coszang', '1',  &
1636                        & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(10), dt,dw2)
1637                   CALL histdef(hist2_id, 'PARdf', 'PARdf', '1',  &
1638                        & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(10), dt,dw2)
1639                   CALL histdef(hist2_id, 'PARdr', 'PARdr', '1',  &
1640                        & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(10), dt,dw2)
1641                   CALL histdef(hist2_id, 'Trans', 'Trans', '1',  &
1642                        & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(10), dt,dw2)
1643                END IF
1644               
1645                CALL histdef(hist2_id, 'flx_fertil_no', 'flx_fertil_no', 'ngN/m^2/s', &
1646                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
1647                CALL histdef(hist2_id, 'CRF', 'CRF', '1', &
1648                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
1649                CALL histdef(hist2_id, 'flx_co2_bbg_year', 'flx_co2_bbg_year', 'kgC/m^2/yr ', &
1650                     & iim,jjm, hori_id2, 1,1,1, -99, 32, once2(10), dt,dw2) 
1651                CALL histdef(hist2_id, 'N_qt_WRICE_year', 'N_qt_WRICE_year', 'kgN/yr ', &
1652                     & iim,jjm, hori_id2, 1,1,1, -99, 32, once2(10), dt,dw2) 
1653                CALL histdef(hist2_id, 'N_qt_OTHER_year', 'N_qt_OTHER_year', 'kgN/yr ', &
1654                     & iim,jjm, hori_id2, 1,1,1, -99, 32, once2(10), dt,dw2) 
1655                CALL histdef(hist2_id, 'flx_iso', 'flx_iso', '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_mono', 'flx_mono', '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_apinen', 'flx_apinen', '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_bpinen', 'flx_bpinen', '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_limonen', 'flx_limonen', '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_myrcen', 'flx_myrcen', '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_sabinen', 'flx_sabinen', '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_camphen', 'flx_camphen', '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_3caren', 'flx_3caren', '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_tbocimen', 'flx_tbocimen', '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_othermono', 'flx_othermono', '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_sesquiter', 'flx_sesquiter', '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_ORVOC', 'flx_ORVOC', '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_MBO', 'flx_MBO', '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_methanol', 'flx_methanol', 'kgC/m^2/s',&
1684                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
1685                CALL histdef(hist2_id, 'flx_acetone', 'flx_acetone', '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_acetal', 'flx_acetal', 'kgC/m^2/s',&
1688                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(1), dt,dw2)   !! LDF TEST modificato a 1... !!
1689                CALL histdef(hist2_id, 'flx_formal', 'flx_formal', '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_acetic', 'flx_acetic', '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_formic', 'flx_formic', 'kgC/m^2/s',&
1694                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
1695                CALL histdef(hist2_id, 'flx_no_soil', 'flx_no_soil', 'ngN/m^2/s',&
1696                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
1697                CALL histdef(hist2_id, 'flx_no', 'flx_no', 'ngN/m^2/s',&
1698                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt,dw2)
1699             ENDIF
1700         ELSE 
1701             !-
1702             !- This is the ALMA convention output now
1703             !-
1704             !-
1705             IF ( grid_type == regular_lonlat ) THEN
1706#ifdef CPP_PARA
1707                CALL histbeg(histname2, iim, lon_rect, jjm, lat_rect, 1, iim, 1, jjm, &
1708                     &     istp_old, date0, dt, hori_id2, hist2_id,orch_domain_id)
1709#else
1710                CALL histbeg(histname2, iim, lon_rect, jjm, lat_rect, 1, iim, 1, jjm, &
1711                     &     istp_old, date0, dt, hori_id2, hist2_id)
1712#endif
1713                IF (printlev >= 2) WRITE(numout,*)  'HISTBEG2 --->',istp_old,date0,dt,dw2,hist2_id
1714             ELSE
1715#ifdef CPP_PARA
1716                CALL histbeg(histname2, iim, lon, jjm, lat, 1, iim, 1, jjm, &
1717                     &     istp_old, date0, dt, hori_id2, hist2_id,domain_id=orch_domain_id)
1718#else
1719                CALL histbeg(histname2, iim, lon, jjm, lat, 1, iim, 1, jjm, &
1720                     &     istp_old, date0, dt, hori_id2, hist2_id)
1721#endif
1722             ENDIF
1723             !-
1724             CALL histvert(hist2_id, 'veget', 'Vegetation types', '1', &
1725                  &    nvm,   veg, vegax_id2)
1726             CALL histvert(hist2_id, 'solth', 'Soil levels',      'm', &
1727                  &    ngrnd, znt, solax_id2)
1728             CALL histvert(hist2_id, 'soiltyp', 'Soil types',      '1', &
1729                  &    nstm, soltyp, soltax_id2)
1730             CALL histvert(hist2_id, 'nobio', 'Other surface types',      '1', &
1731                  &    nnobio, nobiotyp, nobioax_id2)
1732             CALL histvert(hist2_id, 'solay', 'Hydrol soil levels',      'm', &
1733                  &    nslm, diaglev(1:nslm), solayax_id2)
1734
1735             !-
1736             !-  Vegetation
1737             !-
1738             CALL histdef(hist2_id, 'vegetfrac', 'Fraction of vegetation', '1', &
1739                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(3), dt, dw2)
1740             CALL histdef(hist2_id, 'maxvegetfrac', 'Maximum fraction of vegetation', '1', &
1741                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(3), dt, dw2)
1742             CALL histdef(hist2_id, 'nobiofrac', 'Fraction of other surface types', '1', &
1743                  & iim,jjm, hori_id2, nnobio, 1, nnobio, nobioax_id2, 32, avescatter2(3), dt, dw2)
1744             !-
1745             !-  General energy balance
1746             !-
1747             CALL histdef(hist2_id, 'SWnet', 'Net shortwave radiation', 'W/m^2',  &
1748                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(1), dt, dw2)
1749             CALL histdef(hist2_id, 'LWnet', 'Net longwave radiation', 'W/m^2',  &
1750                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(1), dt, dw2)
1751             CALL histdef(hist2_id, 'Qh', 'Sensible heat flux', 'W/m^2',  &
1752                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(1), dt, dw2)
1753             CALL histdef(hist2_id, 'Qle', 'Latent heat flux', 'W/m^2',  &
1754                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(1), dt, dw2)
1755             CALL histdef(hist2_id, 'Qg', 'Ground heat flux', 'W/m^2',  &
1756                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(1), dt, dw2)
1757             CALL histdef(hist2_id, 'Qv', 'Energy of sublimation', 'W/m^2',  &
1758                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(5), dt, dw2)
1759             CALL histdef(hist2_id, 'DelSurfHeat', 'Change in surface layer heat', 'J/m^2',  &
1760                  & iim,jjm, hori_id2, 1,1,1, -99, 32, sumscatter2(7), dt, dw2)
1761             CALL histdef(hist2_id, 'DelColdCont', 'Change in snow surface layer cold content', 'J/m^2',  &
1762                  & iim,jjm, hori_id2, 1,1,1, -99, 32, sumscatter2(7), dt, dw2)
1763             !-
1764             !- General water balance
1765             !-
1766             CALL histdef(hist2_id, 'Snowf', 'Snowfall 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, 'Rainf', 'Rainfall rate', 'kg/m^2/s',  &
1769                  & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop_scinsec2(1), dt, dw2)
1770             CALL histdef(hist2_id, 'Evap', 'Total Evapotranspiration', 'kg/m^2/s', &
1771                  & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop_scinsec2(1), dt, dw2)
1772             CALL histdef(hist2_id, 'Qs', '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, 'Qsb', 'Sub-surface runoff', 'kg/m^2/s', &
1775                  & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop_scinsec2(1), dt, dw2)
1776             CALL histdef(hist2_id, 'Qsm', 'Snowmelt', 'kg/m^2/s', &
1777                  & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop_scinsec2(1), dt, dw2)
1778             CALL histdef(hist2_id, 'DelSoilMoist', 'Change in soil moisture', 'kg/m^2',  &
1779                  & iim,jjm, hori_id2, 1, 1, 1, -99, 32, sumscatter2(7), dt, dw2)
1780             CALL histdef(hist2_id, 'DelSurfStor', 'Change in Surface Water Storage','kg/m^2',&
1781                  & iim,jjm, hori_id2, 1, 1, 1, -99, 32, sumscatter2(7), dt,dw2)
1782             CALL histdef(hist2_id, 'DelIntercept', 'Change in interception storage', 'kg/m^2',  &
1783                  & iim,jjm, hori_id2, 1, 1, 1, -99, 32, sumscatter2(7), dt, dw2)
1784             CALL histdef(hist2_id, 'DelSWE', 'Change in interception storage Snow Water Equivalent', 'kg/m^2',  &
1785                  & iim,jjm, hori_id2, 1, 1, 1, -99, 32, sumscatter2(7), dt, dw2)
1786             !-
1787             !- Surface state
1788             !-
1789             CALL histdef(hist2_id, 'AvgSurfT', 'Average surface temperature', 'K', &
1790                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(1), dt, dw2)
1791             CALL histdef(hist2_id, 'RadT', 'Surface radiative temperature', 'K', &
1792                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(5), dt, dw2)
1793             CALL histdef(hist2_id, 'Albedo', 'Albedo', '1', &
1794                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(7), dt, dw2)
1795             CALL histdef(hist2_id, 'SurfStor', 'Surface Water Storage','kg/m^2',  &
1796                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(1), dt, dw2)
1797             CALL histdef(hist2_id, 'SWE', 'Snow Water Equivalent', 'kg/m^2', &
1798                  & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter2(1), dt,dw2)
1799             !!-
1800             !-  Sub-surface state
1801             !-
1802             CALL histdef(hist2_id, 'SoilMoist', '3D average layer soil moisture', 'kg/m^2',  &
1803                  & iim,jjm, hori_id2, nslm, 1, nslm, solayax_id2, 32, avescatter2(7), dt, dw2)
1804             CALL histdef(hist2_id, 'SoilWet', 'Total soil wetness', '-',  &
1805                  & iim,jjm, hori_id2, 1, 1, 1, -99, 32, avescatter2(1), dt, dw2)
1806             CALL histdef(hist2_id, 'SoilTemp', 'Soil temperature profile', 'K', &
1807                  & iim,jjm, hori_id2, ngrnd, 1, ngrnd, solax_id2, 32, avescatter2(7), dt, dw2)
1808             !-
1809             !-  Evaporation components
1810             !-
1811             CALL histdef(hist2_id, 'PotEvap', 'Potential evapotranspiration', 'kg/m^2/s', &
1812                  & iim,jjm, hori_id2, 1, 1, 1, -99, 32, fluxop_scinsec2(1), dt, dw2)
1813             CALL histdef(hist2_id, 'ECanop', 'Interception evaporation', 'kg/m^2/s', &
1814                  & iim,jjm, hori_id2, 1, 1, 1, -99, 32, fluxop_scinsec2(5), dt, dw2)
1815             CALL histdef(hist2_id, 'TVeg', 'Transpiration', 'kg/m^2/s', &
1816                  & iim,jjm, hori_id2, 1, 1, 1, -99, 32, fluxop_scinsec2(5), dt, dw2)
1817             CALL histdef(hist2_id, 'ESoil', 'Bare soil evaporation', 'kg/m^2/s', &
1818                  & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop_scinsec2(5), dt, dw2)
1819             CALL histdef(hist2_id, 'RootMoist','Root zone soil water', 'kg/m^2',  &
1820                  & iim,jjm, hori_id2, 1, 1, 1, -99, 32, avescatter2(1), dt, dw2)
1821             CALL histdef(hist2_id, 'SubSnow','Snow sublimation','kg/m^2/s', &
1822                  & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop_scinsec2(1), dt, dw2)
1823             CALL histdef(hist2_id, 'ACond', 'Aerodynamic conductance', 'm/s',  &
1824                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(5), dt, dw2)
1825             !-
1826             !-
1827             !-  Cold Season Processes
1828             !-
1829             CALL histdef(hist2_id, 'SnowFrac', 'Snow cover fraction', '1',  &
1830                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(7), dt, dw2)
1831             CALL histdef(hist2_id, 'SAlbedo', 'Snow albedo', '1', &
1832                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(7), dt, dw2)
1833             !-
1834             !- Hydrologic variables
1835             !-
1836             IF ( river_routing ) THEN
1837                !
1838                IF (do_floodplains) THEN
1839                   CALL histdef(hist2_id, 'EWater', 'Open water evaporation', 'kg/m^2/s', &
1840                        & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop_scinsec2(5), dt, dw2)
1841                   CALL histdef(hist2_id, 'FloodFrac', 'Floodplain Fraction', '-', &
1842                        & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(1), dt,dw2)
1843                ENDIF
1844                !
1845                CALL histdef(hist2_id, 'IrrigationMap', 'Map of irrigated areas', 'm^2', &
1846                     & iim,jjm, hori_id2, 1,1,1, -99, 32, once2(1), dt, dw2)
1847                CALL histdef(hist2_id, 'FloodplainsMap', 'Map of flooded areas', 'm^2', &
1848                     & iim,jjm, hori_id2, 1,1,1, -99, 32, once2(1), dt,dw2)
1849                CALL histdef(hist2_id, 'SwampMap', 'Map of swamp areas', 'm^2', &
1850                  & iim,jjm, hori_id2, 1,1,1, -99, 32, once2(1), dt,dw2)
1851                CALL histdef(hist2_id, 'Dis', 'Simulated River Discharge', 'm^3/s', &
1852                     & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop_scinsec2(1), dt,dw2)
1853             ENDIF
1854             !-
1855             !-
1856             !-
1857             CALL histdef(hist2_id, 'humrel', 'Soil moisture stress', '-',  &
1858                  & iim,jjm, hori_id2, nvm,1,nvm, vegax_id2, 32, avescatter2(9), dt, dw2)
1859             !-
1860             !-  The carbon budget
1861             !-
1862             CALL histdef(hist2_id, 'GPP', 'Net assimilation of carbon by the vegetation', 'gC/m^2/s', &
1863                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, fluxop_scinsec2(1), dt, dw2)
1864
1865             IF ( ok_stomate ) THEN
1866                CALL histdef(hist2_id, 'NEE', 'Net Ecosystem Exchange', '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, 'maint_resp', 'Maintenance 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, 'hetero_resp', 'Heterotrophic respiration', 'gC/m^2/s', &
1871                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, fluxop_scinsec2(1), dt,dw2)
1872                CALL histdef(hist2_id, 'growth_resp', 'Growth respiration', 'gC/m^2/s', &
1873                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, fluxop_scinsec2(1), dt, dw2)
1874                CALL histdef(hist2_id, 'npp', 'Net Primary Production', 'gC/m^2/s', &
1875                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, fluxop_scinsec2(1), dt, dw2)
1876             ENDIF
1877             !
1878          ENDIF
1879          !-
1880          CALL histdef(hist2_id, 'LandPoints', 'Land Points', '1', &
1881               & iim,jjm, hori_id2, 1,1,1, -99, 32, once2(10), dt, dw2) 
1882          CALL histdef(hist2_id, 'Areas', 'Mesh areas', 'm2', &
1883               & iim,jjm, hori_id2, 1,1,1, -99, 32, once2(1), dt, dw2)
1884          CALL histdef(hist2_id, 'Contfrac', 'Continental fraction', '1', &
1885               & iim,jjm, hori_id2, 1,1,1, -99, 32, once2(1), dt, dw2)
1886          !-
1887          ! Write the names of the pfts in the high frequency sechiba history files
1888          global_attribute="PFT_name"
1889          DO i=1,nvm
1890             WRITE(global_attribute(9:10),"(I2.2)") i
1891             CALL histglobal_attr(hist2_id, global_attribute, PFT_name(i))
1892          ENDDO
1893          !-
1894          CALL histend(hist2_id)
1895      ENDIF
1896  ENDIF
1897
1898    !-
1899    !=====================================================================
1900    !- 3.2 STOMATE's history file
1901    !=====================================================================
1902    IF ( ok_stomate ) THEN
1903       !-
1904       ! STOMATE IS ACTIVATED
1905       !-
1906       !Config Key   = STOMATE_OUTPUT_FILE
1907       !Config Desc  = Name of file in which STOMATE's output is going to be written
1908       !Config If    = OK_STOMATE
1909       !Config Def   = stomate_history.nc
1910       !Config Help  = This file is going to be created by the model
1911       !Config         and will contain the output from the model.
1912       !Config         This file is a truly COADS compliant netCDF file.
1913       !Config         It will be generated by the hist software from
1914       !Config         the IOIPSL package.
1915       !Config Units = [FILE]
1916       !-
1917       stom_histname='stomate_history.nc'
1918       CALL getin_p('STOMATE_OUTPUT_FILE', stom_histname)       
1919       IF (printlev >= 2) WRITE(numout,*) 'STOMATE_OUTPUT_FILE', TRIM(stom_histname)
1920       !-
1921       !Config Key   = STOMATE_HIST_DT
1922       !Config Desc  = STOMATE history time step
1923       !Config If    = OK_STOMATE
1924       !Config Def   = 10.
1925       !Config Help  = Time step of the STOMATE history file
1926       !Config Units = [days]
1927       !-
1928       hist_days_stom = 10.
1929       CALL getin_p('STOMATE_HIST_DT', hist_days_stom)       
1930
1931       IF ( hist_id < 0 ) THEN
1932          ! Deactivate all history files if sechiba_history file is deactivated
1933          hist_dt_stom=0
1934          IF (printlev >= 2) WRITE(numout,*) &
1935               'STOMATE history file will not be created because sechiba_history file is deactivated.'
1936       ELSE IF ( hist_days_stom == moins_un ) THEN
1937          hist_dt_stom = moins_un
1938          IF (printlev >= 2) WRITE(numout,*) 'output frequency for STOMATE history file (d): one month.'
1939       ELSE IF ( hist_days_stom == 0 ) THEN
1940          ! Deactivate this file
1941          hist_dt_stom=0
1942          IF (printlev >= 2) WRITE(numout,*) 'STOMATE history file will not be created'
1943       ELSE
1944          hist_dt_stom = NINT( hist_days_stom ) * one_day
1945          IF (printlev >= 2) WRITE(numout,*) 'output frequency for STOMATE history file (d): ', &
1946               hist_dt_stom/one_day
1947       ENDIF
1948
1949       ! test consistency between STOMATE_HIST_DT and DT_STOMATE parameters
1950       dt_stomate_loc = one_day
1951       CALL getin_p('DT_STOMATE', dt_stomate_loc)
1952       IF ( hist_days_stom /= moins_un .AND. hist_dt_stom/=0) THEN
1953          IF (dt_stomate_loc > hist_dt_stom) THEN
1954             IF (printlev >= 2) WRITE(numout,*) "DT_STOMATE = ",dt_stomate_loc,"  , STOMATE_HIST_DT = ",hist_dt_stom
1955             CALL ipslerr_p (3,'ioipslctrl_history', &
1956                  &          'Problem with DT_STOMATE > STOMATE_HIST_DT','', &
1957                  &          '(must be less or equal)')
1958          ENDIF
1959       ENDIF
1960       !-
1961       !- Initialize stomate_history file
1962       IF ( hist_dt_stom == 0 ) THEN
1963          ! Case hist_dt_stom=0 : No creation of stomate_history.nc file
1964          ! Nothing will be done.
1965          hist_id_stom=-1
1966       ELSE
1967          ! Initialise stomate_history file
1968       IF (is_omp_root) THEN
1969          IF ( grid_type == regular_lonlat ) THEN
1970#ifdef CPP_PARA
1971             CALL histbeg(stom_histname, iim, lon_rect, jjm, lat_rect,  1, iim, 1, jjm, &
1972                  &     istp_old, date0, dt, hori_id, hist_id_stom,domain_id=orch_domain_id)
1973#else
1974             CALL histbeg(stom_histname, iim, lon_rect, jjm, lat_rect,  1, iim, 1, jjm, &
1975                  &     istp_old, date0, dt, hori_id, hist_id_stom)
1976#endif
1977          ELSE
1978#ifdef CPP_PARA
1979             CALL histbeg(stom_histname, iim, lon, jjm, lat,  1, iim, 1, jjm, &
1980                  &     istp_old, date0, dt, hori_id, hist_id_stom,domain_id=orch_domain_id)
1981#else
1982             CALL histbeg(stom_histname, iim, lon, jjm, lat,  1, iim, 1, jjm, &
1983                  &     istp_old, date0, dt, hori_id, hist_id_stom)
1984#endif
1985          ENDIF
1986          !- define PFT axis
1987          hist_PFTaxis = (/ ( REAL(i,r_std), i=1,nvm ) /)
1988          !- declare this axis
1989          CALL histvert (hist_id_stom, 'PFT', 'Plant functional type', &
1990               & '1', nvm, hist_PFTaxis, hist_PFTaxis_id)
1991          ! deforestation
1992          !- define Pool_10 axis
1993          hist_pool_10axis = (/ ( REAL(i,r_std), i=1,10 ) /)
1994          !- declare this axis
1995          CALL histvert (hist_id_stom, 'P10', 'Pool 10 years', &
1996               & '1', 10, hist_pool_10axis, hist_pool_10axis_id)
1997         
1998          !- define Pool_100 axis
1999          hist_pool_100axis = (/ ( REAL(i,r_std), i=1,100 ) /)
2000          !- declare this axis
2001          CALL histvert (hist_id_stom, 'P100', 'Pool 100 years', &
2002               & '1', 100, hist_pool_100axis, hist_pool_100axis_id)
2003         
2004          !- define Pool_11 axis
2005          hist_pool_11axis = (/ ( REAL(i,r_std), i=1,11 ) /)
2006          !- declare this axis
2007          CALL histvert (hist_id_stom, 'P11', 'Pool 10 years + 1', &
2008               & '1', 11, hist_pool_11axis, hist_pool_11axis_id)
2009         
2010          !- define Pool_101 axis
2011          hist_pool_101axis = (/ ( REAL(i,r_std), i=1,101 ) /)
2012          !- declare this axis
2013          CALL histvert (hist_id_stom, 'P101', 'Pool 100 years + 1', &
2014               & '1', 101, hist_pool_101axis, hist_pool_101axis_id)
2015       ENDIF
2016       !- define STOMATE history file
2017       CALL ioipslctrl_histstom (hist_id_stom, nvm, iim, jjm, &
2018            & dt, hist_dt_stom, hori_id, hist_PFTaxis_id, &
2019            & hist_pool_10axis_id, hist_pool_100axis_id, &
2020            & hist_pool_11axis_id, hist_pool_101axis_id)
2021       
2022       !- Write the names of the pfts in the stomate history files
2023       IF (is_omp_root) THEN
2024          global_attribute="PFT_name"
2025          DO i=1,nvm
2026             WRITE(global_attribute(9:10),"(I2.2)") i
2027             CALL histglobal_attr(hist_id_stom, global_attribute, PFT_name(i))
2028          ENDDO
2029
2030       !- end definition
2031          CALL histend(hist_id_stom)
2032       ENDIF
2033    END IF ! IF ( hist_dt_stom == 0 )
2034
2035       !-
2036       !-
2037       !-
2038       ! STOMATE IPCC OUTPUTS IS ACTIVATED
2039       !-
2040       !Config Key   = STOMATE_IPCC_OUTPUT_FILE
2041       !Config Desc  = Name of file in which STOMATE's output is going to be written
2042       !Config If    = OK_STOMATE
2043       !Config Def   = stomate_ipcc_history.nc
2044       !Config Help  = This file is going to be created by the model
2045       !Config         and will contain the output from the model.
2046       !Config         This file is a truly COADS compliant netCDF file.
2047       !Config         It will be generated by the hist software from
2048       !Config         the IOIPSL package.
2049       !Config Units = [FILE]
2050       !-
2051       stom_ipcc_histname='stomate_ipcc_history.nc'
2052       CALL getin_p('STOMATE_IPCC_OUTPUT_FILE', stom_ipcc_histname)       
2053       IF (printlev >= 2) WRITE(numout,*) 'STOMATE_IPCC_OUTPUT_FILE', TRIM(stom_ipcc_histname)
2054       !-
2055       !Config Key   = STOMATE_IPCC_HIST_DT
2056       !Config Desc  = STOMATE IPCC history time step
2057       !Config If    = OK_STOMATE
2058       !Config Def   = 0.
2059       !Config Help  = Time step of the STOMATE IPCC history file
2060       !Config Units = [days]
2061       !-
2062       hist_days_stom_ipcc = zero
2063       CALL getin_p('STOMATE_IPCC_HIST_DT', hist_days_stom_ipcc)       
2064       IF ( hist_days_stom_ipcc == moins_un ) THEN
2065          hist_dt_stom_ipcc = moins_un
2066          IF (printlev >= 2) WRITE(numout,*) 'output frequency for STOMATE IPCC history file (d): one month.'
2067       ELSE
2068          hist_dt_stom_ipcc = NINT( hist_days_stom_ipcc ) * one_day
2069          IF (printlev >= 2) WRITE(numout,*) 'output frequency for STOMATE IPCC history file (d): ', &
2070            hist_dt_stom_ipcc/one_day
2071       ENDIF
2072       
2073       IF ( hist_dt_stom_ipcc /= 0 .AND. hist_id < 0 ) THEN
2074          ! sechiba_history file is not created therefore STOMATE IPCC history file will be deactivated
2075          hist_dt_stom_ipcc=0
2076          hist_days_stom_ipcc=0
2077          IF (printlev >= 2) WRITE(numout,*) 'STOMATE IPCC history file is not created.'
2078       END IF
2079
2080       ! test consistency between STOMATE_IPCC_HIST_DT and DT_STOMATE parameters
2081       dt_stomate_loc = one_day
2082       CALL getin_p('DT_STOMATE', dt_stomate_loc)
2083       IF ( hist_days_stom_ipcc > zero ) THEN
2084          IF (dt_stomate_loc > hist_dt_stom_ipcc) THEN
2085             IF (printlev >= 2) WRITE(numout,*) "DT_STOMATE = ",dt_stomate_loc,"  , STOMATE_IPCC_HIST_DT = ",hist_dt_stom_ipcc
2086             CALL ipslerr_p (3,'ioipslctrl_history', &
2087                  &          'Problem with DT_STOMATE > STOMATE_IPCC_HIST_DT','', &
2088                  &          '(must be less or equal)')
2089          ENDIF
2090       ENDIF
2091
2092       !Config Key   = OK_HISTSYNC
2093       !Config Desc  = Syncronize and write IOIPSL output files at each time step
2094       !Config If    =
2095       !Config Def   = FALSE
2096       !Config Help  = Setting this flag to true might affect run performance. Only use it for debug perpose.
2097       !Config Units = [FLAG]
2098       ok_histsync=.FALSE.
2099       CALL getin_p('OK_HISTSYNC', ok_histsync)       
2100
2101
2102
2103       IF ( hist_dt_stom_ipcc == 0 ) THEN
2104          hist_id_stom_ipcc = -1
2105       ELSE
2106          !-
2107          !- initialize
2108          IF (is_omp_root) THEN
2109             IF ( grid_type == regular_lonlat ) THEN
2110#ifdef CPP_PARA
2111                CALL histbeg(stom_ipcc_histname, iim, lon_rect, jjm, lat_rect,  1, iim, 1, jjm, &
2112                     &     istp_old, date0, dt, hori_id, hist_id_stom_ipcc,domain_id=orch_domain_id)
2113#else
2114                CALL histbeg(stom_ipcc_histname, iim, lon_rect, jjm, lat_rect,  1, iim, 1, jjm, &
2115                     &     istp_old, date0, dt, hori_id, hist_id_stom_ipcc)
2116#endif
2117             ELSE
2118#ifdef CPP_PARA
2119                CALL histbeg(stom_ipcc_histname, iim, lon, jjm, lat,  1, iim, 1, jjm, &
2120                     &     istp_old, date0, dt, hori_id, hist_id_stom_ipcc,domain_id=orch_domain_id)
2121#else
2122                CALL histbeg(stom_ipcc_histname, iim, lon, jjm, lat,  1, iim, 1, jjm, &
2123                     &     istp_old, date0, dt, hori_id, hist_id_stom_ipcc)
2124#endif
2125             ENDIF
2126             !- declare this axis
2127             CALL histvert (hist_id_stom_IPCC, 'PFT', 'Plant functional type', &
2128                  & '1', nvm, hist_PFTaxis, hist_IPCC_PFTaxis_id)
2129             
2130             !- define STOMATE history file
2131             CALL ioipslctrl_histstomipcc (hist_id_stom_IPCC, nvm, iim, jjm, &
2132                  & dt, hist_dt_stom_ipcc, hori_id, hist_IPCC_PFTaxis_id)
2133             
2134             !- Write the names of the pfts in the stomate history files
2135             global_attribute="PFT_name"
2136             DO i=1,nvm
2137                WRITE(global_attribute(9:10),"(I2.2)") i
2138                CALL histglobal_attr(hist_id_stom_IPCC, global_attribute, PFT_name(i))
2139             ENDDO
2140
2141             !- end definition
2142             CALL histend(hist_id_stom_IPCC)
2143          ENDIF
2144      ENDIF
2145   ENDIF
2146
2147
2148  END SUBROUTINE ioipslctrl_history
2149
2150!! ================================================================================================================================
2151!! SUBROUTINE    : ioipslctrl_histstom
2152!!
2153!>\BRIEF         This subroutine initialize the IOIPSL stomate output file
2154!!
2155!! DESCRIPTION   : This subroutine initialize the IOIPSL output file stomate_history.nc(default name).
2156!!                 This subroutine was previously named stom_define_history and where located in module intersurf.
2157!! RECENT CHANGE(S): None
2158!!
2159!! \n
2160!_ ================================================================================================================================
2161  SUBROUTINE ioipslctrl_histstom( &
2162       hist_id_stom, nvm, iim, jjm, dt, &
2163       hist_dt, hist_hori_id, hist_PFTaxis_id, &
2164       hist_pool_10axis_id, hist_pool_100axis_id, &
2165       hist_pool_11axis_id, hist_pool_101axis_id)
2166    ! deforestation axis added as arguments
2167
2168    !---------------------------------------------------------------------
2169    !- Tell ioipsl which variables are to be written
2170    !- and on which grid they are defined
2171    !---------------------------------------------------------------------
2172    IMPLICIT NONE
2173    !-
2174    !- Input
2175    !-
2176    !- File id
2177    INTEGER(i_std),INTENT(in) :: hist_id_stom
2178    !- number of PFTs
2179    INTEGER(i_std),INTENT(in) :: nvm
2180    !- Domain size
2181    INTEGER(i_std),INTENT(in) :: iim, jjm
2182    !- Time step of STOMATE (seconds)
2183    REAL(r_std),INTENT(in)    :: dt
2184    !- Time step of history file (s)
2185    REAL(r_std),INTENT(in)    :: hist_dt
2186    !- id horizontal grid
2187    INTEGER(i_std),INTENT(in) :: hist_hori_id
2188    !- id of PFT axis
2189    INTEGER(i_std),INTENT(in) :: hist_PFTaxis_id
2190    !- id of Deforestation axis
2191    INTEGER(i_std),INTENT(in) :: hist_pool_10axis_id,hist_pool_100axis_id
2192    INTEGER(i_std),INTENT(in) :: hist_pool_11axis_id,hist_pool_101axis_id
2193    !-
2194    !- 1 local
2195    !-
2196    !- maximum history level
2197    INTEGER(i_std), PARAMETER  :: max_hist_level = 10
2198    !- output level (between 0 and 10)
2199    !-  ( 0:nothing is written, 10:everything is written)
2200    INTEGER(i_std)             :: hist_level
2201    !- Character strings to define operations for histdef
2202    CHARACTER(LEN=40),DIMENSION(max_hist_level) :: ave
2203
2204    !---------------------------------------------------------------------
2205    !=====================================================================
2206    !- 1 history level
2207    !=====================================================================
2208    !- 1.1 define history levelx
2209    !=====================================================================
2210    !Config Key   = STOMATE_HISTLEVEL
2211    !Config Desc  = STOMATE history output level (0..10)
2212    !Config If    = OK_STOMATE
2213    !Config Def   = 10
2214    !Config Help  = 0: nothing is written; 10: everything is written
2215    !Config Units = [-]
2216    !-
2217    hist_level = 10
2218    CALL getin_p('STOMATE_HISTLEVEL', hist_level)
2219    !-
2220    IF (printlev >= 2) WRITE(numout,*) 'STOMATE history level: ',hist_level
2221    IF ( (hist_level > max_hist_level).OR.(hist_level < 0) ) THEN
2222       STOP 'This history level is not allowed'
2223    ENDIF
2224    !=====================================================================
2225    !- 1.2 define operations according to output level
2226    !=====================================================================
2227    ave(1:hist_level) =  'ave(scatter(X))'
2228    ave(hist_level+1:max_hist_level) =  'never          '
2229    !=====================================================================
2230    !- 2 surface fields (2d)
2231    !- 3 PFT: 3rd dimension
2232    !=====================================================================
2233
2234
2235    ! structural litter above ground
2236    IF (is_omp_root) THEN
2237       CALL histdef (hist_id_stom, &
2238            &               TRIM("LITTER_STR_AB       "), &
2239            &               TRIM("structural litter above ground                    "), &
2240            &               TRIM("gC/m^2/pft          "), iim,jjm, hist_hori_id, &
2241            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
2242       
2243       ! metabolic litter above ground                     
2244       CALL histdef (hist_id_stom, &
2245            &               TRIM("LITTER_MET_AB       "), &
2246            &               TRIM("metabolic litter above ground                     "), &
2247            &               TRIM("gC/m^2/pft          "), iim,jjm, hist_hori_id, &
2248            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
2249       
2250       ! structural litter below ground               
2251       CALL histdef (hist_id_stom, &
2252            &               TRIM("LITTER_STR_BE       "), &
2253            &               TRIM("structural litter below ground                    "), &
2254            &               TRIM("gC/m^2/pft          "), iim,jjm, hist_hori_id, &
2255            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
2256       
2257       ! metabolic litter below ground               
2258       CALL histdef (hist_id_stom, &
2259            &               TRIM("LITTER_MET_BE       "), &
2260            &               TRIM("metabolic litter below ground                     "), &
2261            &               TRIM("gC/m^2/pft          "), iim,jjm, hist_hori_id, &
2262            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
2263       
2264       ! fraction of soil covered by dead leaves           
2265       CALL histdef (hist_id_stom, &
2266            &               TRIM("DEADLEAF_COVER      "), &
2267            &               TRIM("fraction of soil covered by dead leaves           "), &
2268            &               TRIM("-                   "), iim,jjm, hist_hori_id, &
2269            &               1,1,1, -99,32, ave(5), dt, hist_dt)
2270       
2271       ! total soil and litter carbon
2272       CALL histdef (hist_id_stom, &
2273            &               TRIM("TOTAL_SOIL_CARB     "), &
2274            &               TRIM("total soil and litter carbon                      "), &
2275            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
2276            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
2277       
2278       ! active soil carbon in ground                 
2279       CALL histdef (hist_id_stom, &
2280            &               TRIM("CARBON_ACTIVE       "), &
2281            &               TRIM("active soil carbon in ground                      "), &
2282            &               TRIM("gC/m^2/pft          "), iim,jjm, hist_hori_id, &
2283            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
2284       
2285       ! slow soil carbon in ground                   
2286       CALL histdef (hist_id_stom, &
2287            &               TRIM("CARBON_SLOW         "), &
2288            &               TRIM("slow soil carbon in ground                        "), &
2289            &               TRIM("gC/m^2/pft          "), iim,jjm, hist_hori_id, &
2290            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
2291       
2292       ! passive soil carbon in ground               
2293       CALL histdef (hist_id_stom, &
2294            &               TRIM("CARBON_PASSIVE      "), &
2295            &               TRIM("passive soil carbon in ground                     "), &
2296            &               TRIM("gC/m^2/pft          "), iim,jjm, hist_hori_id, &
2297            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
2298       
2299       ! Long term 2 m temperature                           
2300       CALL histdef (hist_id_stom, &
2301            &               TRIM("T2M_LONGTERM        "), &
2302            &               TRIM("Longterm 2 m temperature                          "), &
2303            &               TRIM("K                   "), iim,jjm, hist_hori_id, &
2304            &               1,1,1, -99,32, ave(9), dt, hist_dt)
2305       
2306       ! Monthly 2 m temperature                           
2307       CALL histdef (hist_id_stom, &
2308            &               TRIM("T2M_MONTH           "), &
2309            &               TRIM("Monthly 2 m temperature                           "), &
2310            &               TRIM("K                   "), iim,jjm, hist_hori_id, &
2311            &               1,1,1, -99,32, ave(1), dt, hist_dt)
2312       
2313       ! Weekly 2 m temperature                           
2314       CALL histdef (hist_id_stom, &
2315            &               TRIM("T2M_WEEK            "), &
2316            &               TRIM("Weekly 2 m temperature                            "), &
2317            &               TRIM("K                   "), iim,jjm, hist_hori_id, &
2318            &               1,1,1, -99,32, ave(1), dt, hist_dt)
2319       
2320       ! heterotr. resp. from ground                 
2321       CALL histdef (hist_id_stom, &
2322            &               TRIM("HET_RESP            "), &
2323            &               TRIM("heterotr. resp. from ground                       "), &
2324            &               TRIM("gC/m^2 tot/pft/day  "), iim,jjm, hist_hori_id, &
2325            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(3), dt, hist_dt)
2326       
2327       ! Fire fraction on ground
2328       CALL histdef (hist_id_stom, &
2329            &               TRIM("FIREFRAC            "), &
2330            &               TRIM("Fire fraction on ground                           "), &
2331            &               TRIM("1/day               "), iim,jjm, hist_hori_id, &
2332            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(1), dt, hist_dt)
2333
2334       ! Fire index on ground                     
2335       CALL histdef (hist_id_stom, &
2336            &               TRIM("FIREINDEX           "), &
2337            &               TRIM("Fire index on ground                              "), &
2338            &               TRIM("-                   "), iim,jjm, hist_hori_id, &
2339            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
2340       
2341       ! Litter humidity                                   
2342       CALL histdef (hist_id_stom, &
2343            &               TRIM("LITTERHUM           "), &
2344            &               TRIM("Litter humidity                                   "), &
2345            &               TRIM("-                   "), iim,jjm, hist_hori_id, &
2346            &               1,1,1, -99,32, ave(5), dt, hist_dt)
2347       
2348       ! CO2 flux                                 
2349       CALL histdef (hist_id_stom, &
2350            &               TRIM("CO2FLUX             "), &
2351            &               TRIM("CO2 flux                                          "), &
2352            &               TRIM("gC/m^2/pft/mth      "), iim,jjm, hist_hori_id, &
2353            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(1), dt, hist_dt)
2354
2355       ! Output CO2 flux from fire                         
2356       CALL histdef (hist_id_stom, &
2357            &               TRIM("CO2_FIRE            "), &
2358            &               TRIM("Output CO2 flux from fire                         "), &
2359            &               TRIM("gC/day/m^2/pft      "), iim,jjm, hist_hori_id, &
2360            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(1), dt, hist_dt)
2361       
2362       ! CO2 taken from atmosphere for initiate growth     
2363       CALL histdef (hist_id_stom, &
2364            &               TRIM("CO2_TAKEN           "), &
2365            &               TRIM("CO2 taken from atmosphere for initiate growth     "), &
2366            &               TRIM("gC/day/m^2/pft      "), iim,jjm, hist_hori_id, &
2367            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(1), dt, hist_dt)
2368
2369       IF (ok_dgvm) THEN
2370          ! total co2 flux (sum over 13 PFTs). when DGVM is activated, the previous
2371          ! SUM(CO2FLUX*veget_max) is wrong. We should look at this variable.
2372          CALL histdef (hist_id_stom, &
2373               &               TRIM("tCO2FLUX            "), &
2374               &               TRIM("total CO2flux of 13 PFTs (after adjustment)       "), &
2375               &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
2376               &               1,1,1, -99,32, ave(1), dt, hist_dt)
2377         
2378          ! should be the same with tCO2FLUX
2379          CALL histdef (hist_id_stom, &
2380               &               TRIM("tCO2FLUX_OLD        "), &
2381               &               TRIM("total CO2flux of 13 PFTs(multiply by veget_max_old"), &
2382               &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
2383               &               1,1,1, -99,32, ave(10), dt, hist_dt)
2384         
2385          CALL histdef (hist_id_stom, &
2386               &               TRIM("tGPP                 "), &
2387               &               TRIM("total GPP of 13 PFTs (after adjustment)           "), &
2388               &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
2389               &               1,1,1, -99,32, ave(1), dt, hist_dt)
2390       
2391          CALL histdef (hist_id_stom, &
2392               &               TRIM("tRESP_GROWTH         "), &
2393               &               TRIM("total resp growth of 13 PFTs (after adjustment)   "), &
2394               &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
2395               &               1,1,1, -99,32, ave(1), dt, hist_dt)
2396         
2397          CALL histdef (hist_id_stom, &
2398               &               TRIM("tRESP_MAINT          "), &
2399               &               TRIM("total resp maint  of 13 PFTs (after adjustment)   "), &
2400               &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
2401               &               1,1,1, -99,32, ave(1), dt, hist_dt)
2402       
2403          CALL histdef (hist_id_stom, &
2404               &               TRIM("tRESP_HETERO         "), &
2405               &               TRIM("total resp hetero of 13 PFTs (after adjustment)   "), &
2406               &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
2407               &               1,1,1, -99,32, ave(1), dt, hist_dt)
2408       
2409          CALL histdef (hist_id_stom, &
2410               &               TRIM("tCARBON              "), &
2411               &               TRIM("total carbon of 13 PFTs (after adjustment)        "), &
2412               &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
2413               &               1,1,1, -99,32, ave(1), dt, hist_dt)
2414         
2415          CALL histdef (hist_id_stom, &
2416               &               TRIM("tBIOMASS             "), &
2417               &               TRIM("total biomass of 13 PFTs (after adjustment)       "), &
2418               &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
2419               &               1,1,1, -99,32, ave(1), dt, hist_dt)
2420       
2421          CALL histdef (hist_id_stom, &
2422               &               TRIM("tLITTER              "), &
2423               &               TRIM("total litter of 13 PFTs (after adjustment)        "), &
2424               &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
2425               &               1,1,1, -99,32, ave(1), dt, hist_dt)
2426       
2427          CALL histdef (hist_id_stom, &
2428               &               TRIM("tSOILC               "), &
2429               &               TRIM("total soil carbon of 13 PFTs (after adjustment)   "), &
2430               &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
2431               &               1,1,1, -99,32, ave(1), dt, hist_dt)
2432
2433          CALL histdef (hist_id_stom, &
2434               &               TRIM("tCO2_TAKEN           "), &
2435               &               TRIM("total co2_to_bm 13 PFTs (after adjustment)        "), &
2436               &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
2437               &               1,1,1, -99,32, ave(10), dt, hist_dt)
2438         
2439          CALL histdef (hist_id_stom, &
2440               &               TRIM("tCO2_FIRE            "), &
2441               &               TRIM("total co2_fire 13 PFTs (after adjustment)         "), &
2442               &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
2443               &               1,1,1, -99,32, ave(10), dt, hist_dt)
2444       END IF
2445       
2446
2447       CALL histdef (hist_id_stom, &
2448            &               TRIM("FPC_MAX             "), &
2449            &               TRIM("foliage projective cover                          "), &
2450            &               TRIM("-                   "), iim,jjm, hist_hori_id, &
2451            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
2452       
2453       CALL histdef (hist_id_stom, &
2454            &               TRIM("MAXFPC_LASTYEAR     "), &
2455            &               TRIM("foliage projective cover of last year             "), &
2456            &               TRIM("-                   "), iim,jjm, hist_hori_id, &
2457            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
2458
2459       ! "seasonal" 2 m temperature                           
2460       CALL histdef (hist_id_stom, &
2461         &               TRIM("TSEASON             "), &
2462         &               TRIM("Seasonal 2 m temperature                             "), &
2463         &               TRIM("K                   "), iim,jjm, hist_hori_id, &
2464         &               1,1,1, -99,32, ave(10), dt, hist_dt)
2465
2466       ! how many days after onset                           
2467       CALL histdef (hist_id_stom, &
2468         &               TRIM("TMIN_SPRING_TIME    "), &
2469         &               TRIM("how many days after onset                            "), &
2470         &               TRIM("days                "), iim,jjm, hist_hori_id, &
2471         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
2472
2473       !                           
2474       CALL histdef (hist_id_stom, &
2475         &               TRIM("ONSET_DATE          "), &
2476         &               TRIM("onset date                                           "), &
2477         &               TRIM("day                 "), iim,jjm, hist_hori_id, &
2478         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
2479
2480       ! Leaf Area Index                                   
2481       CALL histdef (hist_id_stom, &
2482            &               TRIM("LAI                 "), &
2483            &               TRIM("Leaf Area Index                                   "), &
2484            &               TRIM("-                   "), iim,jjm, hist_hori_id, &
2485            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(1), dt, hist_dt)
2486       
2487       ! Maximum vegetation fraction (LAI -> infinity)     
2488       CALL histdef (hist_id_stom, &
2489            &               TRIM("VEGET_COV_MAX       "), &
2490            &               TRIM("Maximum vegetation fraction (LAI -> infinity)     "), &
2491            &               TRIM("-                   "), iim,jjm, hist_hori_id, &
2492            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(1), dt, hist_dt)
2493       
2494       ! Net primary productivity                         
2495       CALL histdef (hist_id_stom, &
2496            &               TRIM("NPP                 "), &
2497            &               TRIM("Net primary productivity                          "), &
2498            &               TRIM("gC/day/(m^2 tot)    "), iim,jjm, hist_hori_id, &
2499            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(1), dt, hist_dt)
2500
2501       ! Gross primary productivity                       
2502       CALL histdef (hist_id_stom, &
2503            &               TRIM("GPP                 "), &
2504            &               TRIM("Gross primary productivity                        "), &
2505            &               TRIM("gC/day/m^2          "), iim,jjm, hist_hori_id, &
2506            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(1), dt, hist_dt)
2507
2508       ! Density of individuals                           
2509       CALL histdef (hist_id_stom, &
2510            &               TRIM("IND                 "), &
2511            &               TRIM("Density of individuals                            "), &
2512            &               TRIM("1/ m^2              "), iim,jjm, hist_hori_id, &
2513            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(3), dt, hist_dt)
2514
2515       ! Adaptation to climate
2516       CALL histdef (hist_id_stom, &
2517            &               TRIM("ADAPTATION          "), &
2518            &               TRIM("Adaptation to climate (DGVM)                      "), &
2519            &               TRIM("-                   "), iim,jjm, hist_hori_id, &
2520            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(3), dt, hist_dt)
2521   
2522       ! Probability from regenerative
2523       CALL histdef (hist_id_stom, &
2524            &               TRIM("REGENERATION        "), &
2525            &               TRIM("Probability from regenerative (DGVM)               "), &
2526            &               TRIM("-                   "), iim,jjm, hist_hori_id, &
2527            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(3), dt, hist_dt)
2528       
2529       ! crown area of individuals (m**2)
2530       CALL histdef (hist_id_stom, &
2531            &               TRIM("CN_IND              "), &
2532            &               TRIM("crown area of individuals                         "), &
2533            &               TRIM("m^2                 "), iim,jjm, hist_hori_id, &
2534            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(3), dt, hist_dt)
2535
2536       ! woodmass of individuals (gC)
2537       CALL histdef (hist_id_stom, &
2538            &               TRIM("WOODMASS_IND        "), &
2539            &               TRIM("Woodmass of individuals                           "), &
2540            &               TRIM("gC/pft              "), iim,jjm, hist_hori_id, &
2541            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(3), dt, hist_dt)
2542
2543       ! total living biomass
2544       CALL histdef (hist_id_stom, &
2545            &               TRIM("TOTAL_M             "), &
2546            &               TRIM("Total living biomass                              "), &
2547            &               TRIM("gC/m^2/pft          "), iim,jjm, hist_hori_id, &
2548            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(4), dt, hist_dt)
2549       
2550       ! Leaf mass                                         
2551       CALL histdef (hist_id_stom, &
2552            &               TRIM("LEAF_M              "), &
2553            &               TRIM("Leaf mass                                         "), &
2554            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
2555            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
2556       
2557       ! Sap mass above ground                             
2558       CALL histdef (hist_id_stom, &
2559            &               TRIM("SAP_M_AB            "), &
2560            &               TRIM("Sap mass above ground                             "), &
2561            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
2562            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
2563
2564       ! Sap mass below ground                             
2565       CALL histdef (hist_id_stom, &
2566            &               TRIM("SAP_M_BE            "), &
2567            &               TRIM("Sap mass below ground                             "), &
2568            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
2569            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
2570       
2571       ! Heartwood mass above ground                       
2572       CALL histdef (hist_id_stom, &
2573            &               TRIM("HEART_M_AB          "), &
2574            &               TRIM("Heartwood mass above ground                       "), &
2575            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
2576            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
2577
2578       ! Heartwood mass below ground                       
2579       CALL histdef (hist_id_stom, &
2580            &               TRIM("HEART_M_BE          "), &
2581            &               TRIM("Heartwood mass below ground                       "), &
2582            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
2583            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
2584
2585       ! Root mass                                         
2586       CALL histdef (hist_id_stom, &
2587            &               TRIM("ROOT_M              "), &
2588            &               TRIM("Root mass                                         "), &
2589            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
2590            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
2591       
2592       ! Fruit mass                                       
2593       CALL histdef (hist_id_stom, &
2594            &               TRIM("FRUIT_M             "), &
2595            &               TRIM("Fruit mass                                        "), &
2596            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
2597            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
2598       
2599       ! Carbohydrate reserve mass                         
2600       CALL histdef (hist_id_stom, &
2601            &               TRIM("RESERVE_M           "), &
2602            &               TRIM("Carbohydrate reserve mass                         "), &
2603            &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
2604            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
2605       
2606       ! total turnover rate
2607       CALL histdef (hist_id_stom, &
2608            &               TRIM("TOTAL_TURN          "), &
2609            &               TRIM("total turnover rate                               "), &
2610            &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
2611            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(4), dt, hist_dt)
2612
2613       ! Leaf turnover                                     
2614       CALL histdef (hist_id_stom, &
2615            &               TRIM("LEAF_TURN           "), &
2616            &               TRIM("Leaf turnover                                     "), &
2617            &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
2618            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(4), dt, hist_dt)
2619
2620       ! Sap turnover above                               
2621       CALL histdef (hist_id_stom, &
2622            &               TRIM("SAP_AB_TURN         "), &
2623            &               TRIM("Sap turnover above                                "), &
2624            &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
2625            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(4), dt, hist_dt)
2626
2627       ! Root turnover                                     
2628       CALL histdef (hist_id_stom, &
2629            &               TRIM("ROOT_TURN           "), &
2630            &               TRIM("Root turnover                                     "), &
2631            &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
2632            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(4), dt, hist_dt)
2633
2634       ! Fruit turnover                                   
2635       CALL histdef (hist_id_stom, &
2636            &               TRIM("FRUIT_TURN          "), &
2637            &               TRIM("Fruit turnover                                    "), &
2638            &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
2639            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(4), dt, hist_dt)
2640
2641       ! total conversion of biomass to litter
2642       CALL histdef (hist_id_stom, &
2643            &               TRIM("TOTAL_BM_LITTER     "), &
2644            &               TRIM("total conversion of biomass to litter             "), &
2645            &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
2646            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(4), dt, hist_dt)
2647
2648       ! Leaf death                                       
2649       CALL histdef (hist_id_stom, &
2650            &               TRIM("LEAF_BM_LITTER      "), &
2651            &               TRIM("Leaf death                                        "), &
2652            &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
2653            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(4), dt, hist_dt)
2654       
2655       ! Sap death above ground                           
2656       CALL histdef (hist_id_stom, &
2657            &               TRIM("SAP_AB_BM_LITTER    "), &
2658            &               TRIM("Sap death above ground                            "), &
2659            &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
2660            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(4), dt, hist_dt)
2661
2662       ! Sap death below ground                           
2663       CALL histdef (hist_id_stom, &
2664            &               TRIM("SAP_BE_BM_LITTER    "), &
2665            &               TRIM("Sap death below ground                            "), &
2666            &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
2667            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(4), dt, hist_dt)
2668
2669       ! Heartwood death above ground                     
2670       CALL histdef (hist_id_stom, &
2671            &               TRIM("HEART_AB_BM_LITTER  "), &
2672            &               TRIM("Heartwood death above ground                      "), &
2673            &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
2674            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(4), dt, hist_dt)
2675
2676       ! Heartwood death below ground                     
2677       CALL histdef (hist_id_stom, &
2678            &               TRIM("HEART_BE_BM_LITTER  "), &
2679            &               TRIM("Heartwood death below ground                      "), &
2680            &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
2681            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(4), dt, hist_dt)
2682
2683       ! Root death                                       
2684       CALL histdef (hist_id_stom, &
2685            &               TRIM("ROOT_BM_LITTER      "), &
2686            &               TRIM("Root death                                        "), &
2687            &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
2688            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(4), dt, hist_dt)
2689       
2690       ! Fruit death                                       
2691       CALL histdef (hist_id_stom, &
2692            &               TRIM("FRUIT_BM_LITTER     "), &
2693            &               TRIM("Fruit death                                       "), &
2694            &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
2695            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(4), dt, hist_dt)
2696
2697       ! Carbohydrate reserve death                       
2698       CALL histdef (hist_id_stom, &
2699            &               TRIM("RESERVE_BM_LITTER   "), &
2700            &               TRIM("Carbohydrate reserve death                        "), &
2701            &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
2702            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(4), dt, hist_dt)
2703
2704       ! Maintenance respiration                           
2705       CALL histdef (hist_id_stom, &
2706            &               TRIM("MAINT_RESP          "), &
2707            &               TRIM("Maintenance respiration                           "), &
2708            &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
2709            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
2710
2711       ! Growth respiration                               
2712       CALL histdef (hist_id_stom, &
2713            &               TRIM("GROWTH_RESP         "), &
2714            &               TRIM("Growth respiration                                "), &
2715            &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
2716            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
2717       
2718       ! age                                               
2719       CALL histdef (hist_id_stom, &
2720            &               TRIM("AGE                 "), &
2721            &               TRIM("age                                               "), &
2722            &               TRIM("years               "), iim,jjm, hist_hori_id, &
2723            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(7), dt, hist_dt)
2724       
2725       ! height                                           
2726       CALL histdef (hist_id_stom, &
2727            &               TRIM("HEIGHT              "), &
2728            &               TRIM("height                                            "), &
2729            &               TRIM("m                   "), iim,jjm, hist_hori_id, &
2730            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(7), dt, hist_dt)
2731
2732       ! weekly moisture stress                           
2733       CALL histdef (hist_id_stom, &
2734            &               TRIM("MOISTRESS           "), &
2735            &               TRIM("weekly moisture stress                            "), &
2736            &               TRIM("-                   "), iim,jjm, hist_hori_id, &
2737            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(3), dt, hist_dt)
2738
2739       ! Maximum rate of carboxylation                     
2740       CALL histdef (hist_id_stom, &
2741            &               TRIM("VCMAX               "), &
2742            &               TRIM("Maximum rate of carboxylation                     "), &
2743            &               TRIM("-                   "), iim,jjm, hist_hori_id, &
2744            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(6), dt, hist_dt)
2745
2746       ! leaf age                                         
2747       CALL histdef (hist_id_stom, &
2748            &               TRIM("LEAF_AGE            "), &
2749            &               TRIM("leaf age                                          "), &
2750            &               TRIM("days                "), iim,jjm, hist_hori_id, &
2751            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(6), dt, hist_dt)
2752       
2753       ! Fraction of trees that dies (gap)                 
2754       CALL histdef (hist_id_stom, &
2755            &               TRIM("MORTALITY           "), &
2756            &               TRIM("Fraction of trees that dies (gap)                 "), &
2757            &               TRIM("1/day               "), iim,jjm, hist_hori_id, &
2758            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(6), dt, hist_dt)
2759
2760       ! Fraction of plants killed by fire                 
2761       CALL histdef (hist_id_stom, &
2762            &               TRIM("FIREDEATH           "), &
2763            &               TRIM("Fraction of plants killed by fire                 "), &
2764            &               TRIM("1/day               "), iim,jjm, hist_hori_id, &
2765            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(6), dt, hist_dt)
2766
2767       ! Density of newly established saplings             
2768       CALL histdef (hist_id_stom, &
2769            &               TRIM("IND_ESTAB           "), &
2770            &               TRIM("Density of newly established saplings             "), &
2771            &               TRIM("1/day               "), iim,jjm, hist_hori_id, &
2772            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(6), dt, hist_dt)
2773
2774       ! Establish tree
2775       CALL histdef (hist_id_stom, &
2776            &               TRIM("ESTABTREE           "), &
2777            &               TRIM("Rate of tree establishement                       "), &
2778            &               TRIM("1/day               "), iim,jjm, hist_hori_id, &
2779            &               1,1,1, -99,32, ave(6), dt, hist_dt)
2780
2781       ! Establish grass
2782       CALL histdef (hist_id_stom, &
2783            &               TRIM("ESTABGRASS          "), &
2784            &               TRIM("Rate of grass establishement                      "), &
2785            &               TRIM("1/day               "), iim,jjm, hist_hori_id, &
2786            &               1,1,1, -99,32, ave(6), dt, hist_dt)
2787
2788       ! Fraction of plants that dies (light competition) 
2789       CALL histdef (hist_id_stom, &
2790            &               TRIM("LIGHT_DEATH         "), &
2791            &               TRIM("Fraction of plants that dies (light competition)  "), &
2792            &               TRIM("1/day               "), iim,jjm, hist_hori_id, &
2793            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(6), dt, hist_dt)
2794
2795       ! biomass allocated to leaves                       
2796       CALL histdef (hist_id_stom, &
2797            &               TRIM("BM_ALLOC_LEAF       "), &
2798            &               TRIM("biomass allocated to leaves                       "), &
2799            &               TRIM("gC/m**2/pft/dt      "), iim,jjm, hist_hori_id, &
2800            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
2801
2802       ! biomass allocated to sapwood above ground         
2803       CALL histdef (hist_id_stom, &
2804            &               TRIM("BM_ALLOC_SAP_AB     "), &
2805            &               TRIM("biomass allocated to sapwood above ground         "), &
2806            &               TRIM("gC/m**2/pft/dt      "), iim,jjm, hist_hori_id, &
2807            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
2808
2809       ! biomass allocated to sapwood below ground         
2810       CALL histdef (hist_id_stom, &
2811            &               TRIM("BM_ALLOC_SAP_BE     "), &
2812            &               TRIM("biomass allocated to sapwood below ground         "), &
2813            &               TRIM("gC/m**2/pft/dt      "), iim,jjm, hist_hori_id, &
2814            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
2815
2816       ! biomass allocated to roots                       
2817       CALL histdef (hist_id_stom, &
2818            &               TRIM("BM_ALLOC_ROOT       "), &
2819            &               TRIM("biomass allocated to roots                        "), &
2820            &               TRIM("gC/m**2/pft/dt          "), iim,jjm, hist_hori_id, &
2821            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
2822
2823       ! biomass allocated to fruits                       
2824       CALL histdef (hist_id_stom, &
2825            &               TRIM("BM_ALLOC_FRUIT      "), &
2826            &               TRIM("biomass allocated to fruits                       "), &
2827            &               TRIM("gC/m**2/pft/dt          "), iim,jjm, hist_hori_id, &
2828            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
2829
2830       ! biomass allocated to carbohydrate reserve         
2831       CALL histdef (hist_id_stom, &
2832            &               TRIM("BM_ALLOC_RES        "), &
2833            &               TRIM("biomass allocated to carbohydrate reserve         "), &
2834            &               TRIM("gC/m**2/pft/dt          "), iim,jjm, hist_hori_id, &
2835            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
2836
2837       ! time constant of herbivore activity               
2838       CALL histdef (hist_id_stom, &
2839            &               TRIM("HERBIVORES          "), &
2840            &               TRIM("time constant of herbivore activity               "), &
2841            &               TRIM("days                "), iim,jjm, hist_hori_id, &
2842            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
2843
2844       ! turnover time for grass leaves                   
2845       CALL histdef (hist_id_stom, &
2846            &               TRIM("TURNOVER_TIME       "), &
2847            &               TRIM("turnover time for grass leaves                    "), &
2848            &               TRIM("days                "), iim,jjm, hist_hori_id, &
2849            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
2850       
2851       ! 10 year wood product pool                         
2852       CALL histdef (hist_id_stom, &
2853            &               TRIM("PROD10              "), &
2854            &               TRIM("10 year wood product pool                         "), &
2855            &               TRIM("gC/m**2             "), iim,jjm, hist_hori_id, &
2856            &               11,1,11, hist_pool_11axis_id,32, ave(5), dt, hist_dt)
2857       
2858       ! annual flux for each 10 year wood product pool   
2859       CALL histdef (hist_id_stom, &
2860            &               TRIM("FLUX10              "), &
2861            &               TRIM("annual flux for each 10 year wood product pool    "), &
2862            &               TRIM("gC/m**2/yr          "), iim,jjm, hist_hori_id, &
2863            &               10,1,10, hist_pool_10axis_id,32, ave(5), dt, hist_dt)
2864       
2865       ! 100 year wood product pool                       
2866       CALL histdef (hist_id_stom, &
2867            &               TRIM("PROD100             "), &
2868            &               TRIM("100 year wood product pool                        "), &
2869            &               TRIM("gC/m**2             "), iim,jjm, hist_hori_id, &
2870            &               101,1,101, hist_pool_101axis_id,32, ave(5), dt, hist_dt)
2871
2872       ! annual flux for each 100 year wood product pool   
2873       CALL histdef (hist_id_stom, &
2874            &               TRIM("FLUX100             "), &
2875            &               TRIM("annual flux for each 100 year wood product pool   "), &
2876            &               TRIM("gC/m**2/yr          "), iim,jjm, hist_hori_id, &
2877            &               100,1,100, hist_pool_100axis_id,32, ave(5), dt, hist_dt)
2878
2879       ! annual release right after deforestation         
2880       CALL histdef (hist_id_stom, &
2881            &               TRIM("CONVFLUX            "), &
2882            &               TRIM("annual release right after deforestation          "), &
2883            &               TRIM("gC/m**2/day          "), iim,jjm, hist_hori_id, &
2884            &               1,1,1, -99,32, ave(5), dt, hist_dt)
2885
2886       ! annual release from all 10 year wood product pools
2887       CALL histdef (hist_id_stom, &
2888            &               TRIM("CFLUX_PROD10        "), &
2889            &               TRIM("annual release from all 10 year wood product pools"), &
2890            &               TRIM("gC/m**2/day          "), iim,jjm, hist_hori_id, &
2891            &               1,1,1, -99,32, ave(5), dt, hist_dt)
2892
2893       ! annual release from all 100year wood product pools
2894       CALL histdef (hist_id_stom, &
2895            &               TRIM("CFLUX_PROD100       "), &
2896            &               TRIM("annual release from all 100year wood product pools"), &
2897            &               TRIM("gC/m**2/day          "), iim,jjm, hist_hori_id, &
2898            &               1,1,1, -99,32, ave(5), dt, hist_dt)
2899
2900       ! WOOD HARVEST
2901       ! 10 year wood product pool                         
2902       CALL histdef (hist_id_stom, &
2903            &               TRIM("PROD10_HARVEST      "), &
2904            &               TRIM("10 year wood product pool                         "), &
2905            &               TRIM("gC/m**2             "), iim,jjm, hist_hori_id, &
2906            &               11,1,11, hist_pool_11axis_id,32, ave(5), dt, hist_dt)
2907       
2908       ! annual flux for each 10 year wood product pool   
2909       CALL histdef (hist_id_stom, &
2910            &               TRIM("FLUX10_HARVEST      "), &
2911            &               TRIM("annual flux for each 10 year wood product pool    "), &
2912            &               TRIM("gC/m**2/yr          "), iim,jjm, hist_hori_id, &
2913            &               10,1,10, hist_pool_10axis_id,32, ave(5), dt, hist_dt)
2914       
2915       ! 100 year wood product pool                       
2916       CALL histdef (hist_id_stom, &
2917            &               TRIM("PROD100_HARVEST     "), &
2918            &               TRIM("100 year wood product pool                        "), &
2919            &               TRIM("gC/m**2             "), iim,jjm, hist_hori_id, &
2920            &               101,1,101, hist_pool_101axis_id,32, ave(5), dt, hist_dt)
2921
2922       ! annual flux for each 100 year wood product pool   
2923       CALL histdef (hist_id_stom, &
2924            &               TRIM("FLUX100_HARVEST     "), &
2925            &               TRIM("annual flux for each 100 year wood product pool   "), &
2926            &               TRIM("gC/m**2/yr          "), iim,jjm, hist_hori_id, &
2927            &               100,1,100, hist_pool_100axis_id,32, ave(5), dt, hist_dt)
2928
2929       ! annual release right after deforestation         
2930       CALL histdef (hist_id_stom, &
2931            &               TRIM("CONVFLUX_HARVEST      "), &
2932            &               TRIM("annual release right after deforestation          "), &
2933            &               TRIM("gC/m**2/day          "), iim,jjm, hist_hori_id, &
2934            &               1,1,1, -99,32, ave(5), dt, hist_dt)
2935
2936       ! annual release from all 10 year wood product pools
2937       CALL histdef (hist_id_stom, &
2938            &               TRIM("CFLUX_PROD10_HARVEST   "), &
2939            &               TRIM("annual release from all 10 year wood product pools"), &
2940            &               TRIM("gC/m**2/day          "), iim,jjm, hist_hori_id, &
2941            &               1,1,1, -99,32, ave(5), dt, hist_dt)
2942
2943       ! annual release from all 100year wood product pools
2944       ! Note removed last letter T from HARVEST in the variable name to limit number of authorized charcters
2945       CALL histdef (hist_id_stom, &
2946            &               TRIM("CFLUX_PROD100_HARVES"), &
2947            &               TRIM("annual release from all 100year wood product pools"), &
2948            &               TRIM("gC/m**2/day          "), iim,jjm, hist_hori_id, &
2949            &               1,1,1, -99,32, ave(5), dt, hist_dt)
2950
2951       CALL histdef (hist_id_stom, &
2952            &               TRIM("WOOD_HARVEST  "), &
2953            &               TRIM("harvested wood biomass"), &
2954            &               TRIM("gC/m**2/day          "), iim,jjm, hist_hori_id, &
2955            &               1,1,1, -99,32, ave(5), dt, hist_dt)
2956
2957       CALL histdef (hist_id_stom, &
2958            &               TRIM("WOOD_HARVEST_PFT  "), &
2959            &               TRIM("harvested wood biomass per PFT"), &
2960            &               TRIM("gC/m**2/day          "), iim,jjm, hist_hori_id, &
2961            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
2962
2963       ! agriculure product
2964       CALL histdef (hist_id_stom, &
2965            &               TRIM("HARVEST_ABOVE       "), &
2966            &               TRIM("annual release product after harvest              "), &
2967            &               TRIM("gC/m**2/day          "), iim,jjm, hist_hori_id, &
2968            &               1,1,1, -99,32, ave(5), dt, hist_dt)
2969
2970
2971       CALL histdef(hist_id_stom, 'RESOLUTION_X', 'E-W resolution', 'm', &
2972            & iim,jjm, hist_hori_id, 1,1,1, -99, 32, 'once(scatter(X))', dt, hist_dt)
2973       CALL histdef(hist_id_stom, 'RESOLUTION_Y', 'N-S resolution', 'm', &
2974            & iim,jjm, hist_hori_id, 1,1,1, -99, 32, 'once(scatter(X))', dt, hist_dt)
2975       CALL histdef(hist_id_stom, 'CONTFRAC', 'Continental fraction', '1', &
2976            & iim,jjm, hist_hori_id, 1,1,1, -99, 32, 'once(scatter(X))', dt, hist_dt)
2977       CALL histdef(hist_id_stom, 'Areas', 'Mesh areas', 'm2', &
2978            & iim,jjm, hist_hori_id, 1,1,1, -99, 32, 'once(scatter(X))', dt, hist_dt)
2979       
2980       !  Special outputs for phenology
2981       CALL histdef (hist_id_stom, &
2982            &               TRIM("WHEN_GROWTHINIT     "), &
2983            &               TRIM("Time elapsed from season beginning                "), &
2984            &               TRIM("d                   "), iim,jjm, hist_hori_id, &
2985            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(9), dt, hist_dt)
2986       
2987       CALL histdef (hist_id_stom, &
2988            &               TRIM("PFTPRESENT          "), &
2989            &               TRIM("PFT exists                                        "), &
2990            &               TRIM("d                   "), iim,jjm, hist_hori_id, &
2991            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(9), dt, hist_dt)
2992       
2993       CALL histdef (hist_id_stom, &
2994            &               TRIM("GDD_MIDWINTER       "), &
2995            &               TRIM("Growing degree days, since midwinter              "), &
2996            &               TRIM("degK                "), iim,jjm, hist_hori_id, &
2997            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(9), dt, hist_dt)
2998
2999       CALL histdef (hist_id_stom, &
3000            &               TRIM("GDD_M5_DORMANCE     "), &
3001            &               TRIM("Growing degree days, since dormance               "), &
3002            &               TRIM("degK                "), iim,jjm, hist_hori_id, &
3003            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(9), dt, hist_dt)
3004       
3005       CALL histdef (hist_id_stom, &
3006            &               TRIM("NCD_DORMANCE        "), &
3007            &               TRIM("Number of chilling days, since leaves were lost   "), &
3008            &               TRIM("d                   "), iim,jjm, hist_hori_id, &
3009            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(9), dt, hist_dt)
3010       
3011       CALL histdef (hist_id_stom, &
3012            &               TRIM("ALLOW_INITPHENO     "), &
3013            &               TRIM("Allow to declare beginning of the growing season  "), &
3014            &               TRIM("-                   "), iim,jjm, hist_hori_id, &
3015            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(9), dt, hist_dt)
3016       
3017       CALL histdef (hist_id_stom, &
3018            &               TRIM("BEGIN_LEAVES        "), &
3019            &               TRIM("Signal to start putting leaves on                 "), &
3020            &               TRIM("-                   "), iim,jjm, hist_hori_id, &
3021            &               nvm,1,nvm, hist_PFTaxis_id,32, ave(9), dt, hist_dt)
3022    ENDIF
3023
3024  END SUBROUTINE ioipslctrl_histstom
3025
3026!! ================================================================================================================================
3027!! SUBROUTINE    : ioipslctrl_histstomipcc
3028!!
3029!>\BRIEF         This subroutine initialize the IOIPSL stomate second output file (ipcc file)
3030!!
3031!! DESCRIPTION   : This subroutine initialize the IOIPSL stomate second output file named stomate_ipcc_history.nc(default name).
3032!!                 This subroutine was previously called stom_IPCC_define_history and located in module intersurf.
3033!!
3034!! RECENT CHANGE(S): None
3035!!
3036!! \n
3037!_ ================================================================================================================================
3038  SUBROUTINE ioipslctrl_histstomipcc( &
3039       hist_id_stom_IPCC, nvm, iim, jjm, dt, &
3040       hist_dt, hist_hori_id, hist_PFTaxis_id)
3041    ! deforestation axis added as arguments
3042
3043    !---------------------------------------------------------------------
3044    !- Tell ioipsl which variables are to be written
3045    !- and on which grid they are defined
3046    !---------------------------------------------------------------------
3047    IMPLICIT NONE
3048    !-
3049    !- Input
3050    !-
3051    !- File id
3052    INTEGER(i_std),INTENT(in) :: hist_id_stom_IPCC
3053    !- number of PFTs
3054    INTEGER(i_std),INTENT(in) :: nvm
3055    !- Domain size
3056    INTEGER(i_std),INTENT(in) :: iim, jjm
3057    !- Time step of STOMATE (seconds)
3058    REAL(r_std),INTENT(in)    :: dt
3059    !- Time step of history file (s)
3060    REAL(r_std),INTENT(in)    :: hist_dt
3061    !- id horizontal grid
3062    INTEGER(i_std),INTENT(in) :: hist_hori_id
3063    !- id of PFT axis
3064    INTEGER(i_std),INTENT(in) :: hist_PFTaxis_id
3065    !-
3066    !- 1 local
3067    !-
3068    !- Character strings to define operations for histdef
3069    CHARACTER(LEN=40),DIMENSION(max_hist_level) :: ave
3070
3071    !=====================================================================
3072    !- 1 define operations
3073    !=====================================================================
3074    ave(1) =  'ave(scatter(X))'
3075    !=====================================================================
3076    !- 2 surface fields (2d)
3077    !=====================================================================
3078    ! Carbon in Vegetation
3079    CALL histdef (hist_id_stom_IPCC, &
3080         &               TRIM("cVeg"), &
3081         &               TRIM("Carbon in Vegetation"), &
3082         &               TRIM("kg C m-2"), iim,jjm, hist_hori_id, &
3083         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3084    ! Carbon in Litter Pool
3085    CALL histdef (hist_id_stom_IPCC, &
3086         &               TRIM("cLitter"), &
3087         &               TRIM("Carbon in Litter Pool"), &
3088         &               TRIM("kg C m-2"), iim,jjm, hist_hori_id, &
3089         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3090    ! Carbon in Soil Pool
3091    CALL histdef (hist_id_stom_IPCC, &
3092         &               TRIM("cSoil"), &
3093         &               TRIM("Carbon in Soil Pool"), &
3094         &               TRIM("kg C m-2"), iim,jjm, hist_hori_id, &
3095         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3096    ! Carbon in Products of Land Use Change
3097    CALL histdef (hist_id_stom_IPCC, &
3098         &               TRIM("cProduct"), &
3099         &               TRIM("Carbon in Products of Land Use Change"), &
3100         &               TRIM("kg C m-2"), iim,jjm, hist_hori_id, &
3101         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3102    ! Carbon Mass Variation
3103    CALL histdef (hist_id_stom_IPCC, &
3104         &               TRIM("cMassVariation"), &
3105         &               TRIM("Terrestrial Carbon Mass Variation"), &
3106         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
3107         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3108    ! Leaf Area Fraction
3109    CALL histdef (hist_id_stom_IPCC, &
3110         &               TRIM("lai"), &
3111         &               TRIM("Leaf Area Fraction"), &
3112         &               TRIM("1"), iim,jjm, hist_hori_id, &
3113         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3114    ! Gross Primary Production
3115    CALL histdef (hist_id_stom_IPCC, &
3116         &               TRIM("gpp"), &
3117         &               TRIM("Gross Primary Production"), &
3118         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
3119         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3120    ! Autotrophic Respiration
3121    CALL histdef (hist_id_stom_IPCC, &
3122         &               TRIM("ra"), &
3123         &               TRIM("Autotrophic Respiration"), &
3124         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
3125         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3126    ! Net Primary Production
3127    CALL histdef (hist_id_stom_IPCC, &
3128         &               TRIM("npp"), &
3129         &               TRIM("Net Primary Production"), &
3130         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
3131         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3132    ! Heterotrophic Respiration
3133    CALL histdef (hist_id_stom_IPCC, &
3134         &               TRIM("rh"), &
3135         &               TRIM("Heterotrophic Respiration"), &
3136         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
3137         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3138    ! CO2 Emission from Fire
3139    CALL histdef (hist_id_stom_IPCC, &
3140         &               TRIM("fFire"), &
3141         &               TRIM("CO2 Emission from Fire"), &
3142         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
3143         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3144
3145    ! CO2 Flux to Atmosphere from Crop Harvesting
3146    CALL histdef (hist_id_stom_IPCC, &
3147         &               TRIM("fHarvest"), &
3148         &               TRIM("CO2 Flux to Atmosphere from Crop Harvesting"), &
3149         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
3150         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3151    ! CO2 Flux to Atmosphere from Land Use Change
3152    CALL histdef (hist_id_stom_IPCC, &
3153         &               TRIM("fLuc"), &
3154         &               TRIM("CO2 Flux to Atmosphere from Land Use Change"), &
3155         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
3156         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3157    ! CO2 Flux to Atmosphere from Wood Harvest                                                                               
3158    CALL histdef (hist_id_stom_IPCC, &
3159         &               TRIM("fWoodharvest"), &
3160         &               TRIM("CO2 Flux to Atmosphere from Wood Harvest"), &
3161         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
3162         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3163
3164    ! Net Biospheric Production
3165    CALL histdef (hist_id_stom_IPCC, &
3166         &               TRIM("nbp"), &
3167         &               TRIM("Net Biospheric Production"), &
3168         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
3169         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3170    ! Total Carbon Flux from Vegetation to Litter
3171    CALL histdef (hist_id_stom_IPCC, &
3172         &               TRIM("fVegLitter"), &
3173         &               TRIM("Total Carbon Flux from Vegetation to Litter"), &
3174         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
3175         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3176    ! Total Carbon Flux from Litter to Soil
3177    CALL histdef (hist_id_stom_IPCC, &
3178         &               TRIM("fLitterSoil"), &
3179         &               TRIM("Total Carbon Flux from Litter to Soil"), &
3180         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
3181         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3182
3183    ! Carbon in Leaves
3184    CALL histdef (hist_id_stom_IPCC, &
3185         &               TRIM("cLeaf"), &
3186         &               TRIM("Carbon in Leaves"), &
3187         &               TRIM("kg C m-2"), iim,jjm, hist_hori_id, &
3188         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3189    ! Carbon in Stem
3190    CALL histdef (hist_id_stom_IPCC, &
3191         &               TRIM("cStem"), &
3192         &               TRIM("Carbon in Stem"), &
3193         &               TRIM("kg C m-2"), iim,jjm, hist_hori_id, &
3194         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3195    ! Carbon in Roots
3196    CALL histdef (hist_id_stom_IPCC, &
3197         &               TRIM("cRoot"), &
3198         &               TRIM("Carbon in Roots"), &
3199         &               TRIM("kg C m-2"), iim,jjm, hist_hori_id, &
3200         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3201    ! Carbon in Other Living Compartments
3202    CALL histdef (hist_id_stom_IPCC, &
3203         &               TRIM("cMisc"), &
3204         &               TRIM("Carbon in Other Living Compartments"), &
3205         &               TRIM("kg C m-2"), iim,jjm, hist_hori_id, &
3206         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3207
3208    ! Carbon in Above-Ground Litter
3209    CALL histdef (hist_id_stom_IPCC, &
3210         &               TRIM("cLitterAbove"), &
3211         &               TRIM("Carbon in Above-Ground Litter"), &
3212         &               TRIM("kg C m-2"), iim,jjm, hist_hori_id, &
3213         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3214    ! Carbon in Below-Ground Litter
3215    CALL histdef (hist_id_stom_IPCC, &
3216         &               TRIM("cLitterBelow"), &
3217         &               TRIM("Carbon in Below-Ground Litter"), &
3218         &               TRIM("kg C m-2"), iim,jjm, hist_hori_id, &
3219         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3220    ! Carbon in Fast Soil Pool
3221    CALL histdef (hist_id_stom_IPCC, &
3222         &               TRIM("cSoilFast"), &
3223         &               TRIM("Carbon in Fast Soil Pool"), &
3224         &               TRIM("kg C m-2"), iim,jjm, hist_hori_id, &
3225         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3226    ! Carbon in Medium Soil Pool
3227    CALL histdef (hist_id_stom_IPCC, &
3228         &               TRIM("cSoilMedium"), &
3229         &               TRIM("Carbon in Medium Soil Pool"), &
3230         &               TRIM("kg C m-2"), iim,jjm, hist_hori_id, &
3231         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3232    ! Carbon in Slow Soil Pool
3233    CALL histdef (hist_id_stom_IPCC, &
3234         &               TRIM("cSoilSlow"), &
3235         &               TRIM("Carbon in Slow Soil Pool"), &
3236         &               TRIM("kg C m-2"), iim,jjm, hist_hori_id, &
3237         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3238
3239    !- 3 PFT: 3rd dimension
3240    ! Fractional Land Cover of PFT
3241    CALL histdef (hist_id_stom_IPCC, &
3242         &               TRIM("landCoverFrac"), &
3243         &               TRIM("Fractional Land Cover of PFT"), &
3244         &               TRIM("%"), iim,jjm, hist_hori_id, &
3245         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(1), dt, hist_dt)
3246
3247
3248    ! Total Primary Deciduous Tree Cover Fraction
3249    CALL histdef (hist_id_stom_IPCC, &
3250         &               TRIM("treeFracPrimDec"), &
3251         &               TRIM("Total Primary Deciduous Tree Cover Fraction"), &
3252         &               TRIM("%"), iim,jjm, hist_hori_id, &
3253         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3254
3255    ! Total Primary Evergreen Tree Cover Fraction
3256    CALL histdef (hist_id_stom_IPCC, &
3257         &               TRIM("treeFracPrimEver"), &
3258         &               TRIM("Total Primary Evergreen Tree Cover Fraction"), &
3259         &               TRIM("%"), iim,jjm, hist_hori_id, &
3260         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3261
3262    ! Total C3 PFT Cover Fraction
3263    CALL histdef (hist_id_stom_IPCC, &
3264         &               TRIM("c3PftFrac"), &
3265         &               TRIM("Total C3 PFT Cover Fraction"), &
3266         &               TRIM("%"), iim,jjm, hist_hori_id, &
3267         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3268    ! Total C4 PFT Cover Fraction
3269    CALL histdef (hist_id_stom_IPCC, &
3270         &               TRIM("c4PftFrac"), &
3271         &               TRIM("Total C4 PFT Cover Fraction"), &
3272         &               TRIM("%"), iim,jjm, hist_hori_id, &
3273         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3274    ! Growth Autotrophic Respiration
3275    CALL histdef (hist_id_stom_IPCC, &
3276         &               TRIM("rGrowth"), &
3277         &               TRIM("Growth Autotrophic Respiration"), &
3278         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
3279         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3280    ! Maintenance Autotrophic Respiration
3281    CALL histdef (hist_id_stom_IPCC, &
3282         &               TRIM("rMaint"), &
3283         &               TRIM("Maintenance Autotrophic Respiration"), &
3284         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
3285         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3286    ! CO2 Flux from Atmosphere due to NPP Allocation to Leaf
3287    CALL histdef (hist_id_stom_IPCC, &
3288         &               TRIM("nppLeaf"), &
3289         &               TRIM("CO2 Flux from Atmosphere due to NPP Allocation to Leaf"), &
3290         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
3291         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3292    ! CO2 Flux from Atmosphere due to NPP Allocation to Wood
3293    CALL histdef (hist_id_stom_IPCC, &
3294         &               TRIM("nppStem"), &
3295         &               TRIM("CO2 Flux from Atmosphere due to NPP Allocation to Stem"), &
3296         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
3297         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3298    ! CO2 Flux from Atmosphere due to NPP Allocation to Root
3299    CALL histdef (hist_id_stom_IPCC, &
3300         &               TRIM("nppRoot"), &
3301         &               TRIM("CO2 Flux from Atmosphere due to NPP Allocation to Root"), &
3302         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
3303         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3304    ! Net Carbon Mass Flux out of Atmophere due to Net Ecosystem Productivity on Land.
3305    CALL histdef (hist_id_stom_IPCC, &
3306         &               TRIM("nep"), &
3307         &               TRIM("Net Carbon Mass Flux out of Atmophere due to Net Ecosystem Productivity."), &
3308         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
3309         &               1,1,1, -99,32, ave(1), dt, hist_dt)
3310
3311    CALL histdef(hist_id_stom_IPCC, 'RESOLUTION_X', 'E-W resolution', 'm', &
3312         & iim,jjm, hist_hori_id, 1,1,1, -99, 32, 'once(scatter(X))', dt, hist_dt)
3313    CALL histdef(hist_id_stom_IPCC, 'RESOLUTION_Y', 'N-S resolution', 'm', &
3314         & iim,jjm, hist_hori_id, 1,1,1, -99, 32, 'once(scatter(X))', dt, hist_dt)
3315    CALL histdef(hist_id_stom_IPCC, 'CONTFRAC', 'Continental fraction', '1', &
3316         & iim,jjm, hist_hori_id, 1,1,1, -99, 32, 'once(scatter(X))', dt, hist_dt)
3317    CALL histdef(hist_id_stom_IPCC, 'Areas', 'Mesh areas', 'm2', &
3318         & iim,jjm, hist_hori_id, 1,1,1, -99, 32, 'once(scatter(X))', dt, hist_dt)
3319
3320  END SUBROUTINE ioipslctrl_histstomipcc
3321
3322!! ================================================================================================================================
3323!! SUBROUTINE    : ioipslctrl_restini
3324!!
3325!>\BRIEF         This subroutine initialize the restart files in ORCHDIEE.
3326!!
3327!! DESCRIPTION   : This subroutine initialize restart files in ORCHIDEE. IOIPSL is used for writing the restart files.
3328!!                 This subroutine was previously called intsurf_restart and located in module intersurf.
3329!!
3330!! RECENT CHANGE(S): None
3331!!
3332!! \n
3333!_ ================================================================================================================================
3334  SUBROUTINE ioipslctrl_restini(istp, date0, dt, rest_id, rest_id_stom, itau_offset, date0_shifted)
3335
3336    USE mod_orchidee_para
3337    !
3338    !  This subroutine initialized the restart file for the land-surface scheme
3339    !
3340    IMPLICIT NONE
3341    !
3342    INTEGER(i_std), INTENT(in)                  :: istp      !! Time step of the restart file
3343    REAL(r_std)                                 :: date0     !! The date at which itau = 0
3344    REAL(r_std)                                 :: dt        !! Time step
3345    INTEGER(i_std), INTENT(out)                 :: rest_id, rest_id_stom   !! ID of the restart file
3346    INTEGER(i_std), INTENT(out)                 :: itau_offset    !! Note the result is always itau_offset=0 as overwrite_time=TRUE
3347    REAL(r_std), INTENT(out)                    :: date0_shifted  !! Note the result is always date0_shifted=date0 as overwrite_time=TRUE
3348
3349
3350    !  LOCAL
3351    !
3352    REAL(r_std)                 :: dt_rest, date0_rest
3353    INTEGER(i_std)              :: itau_dep
3354    INTEGER(i_std),PARAMETER    :: llm=1
3355    REAL(r_std), DIMENSION(llm) :: lev
3356    LOGICAL, PARAMETER          :: overwrite_time=.TRUE. !! Always override the date from the restart files for SECHIBA and STOMATE.
3357                                                         !! The date is taken from the gcm or from the driver restart file.
3358    REAL(r_std)                 :: in_julian, rest_julian
3359    INTEGER(i_std)              :: yy, mm, dd
3360    REAL(r_std)                 :: ss
3361    !
3362    !Config Key   = SECHIBA_restart_in
3363    !Config Desc  = Name of restart to READ for initial conditions
3364    !Config If    = OK_SECHIBA
3365    !Config Def   = NONE
3366    !Config Help  = This is the name of the file which will be opened
3367    !Config         to extract the initial values of all prognostic
3368    !Config         values of the model. This has to be a netCDF file.
3369    !Config         Not truly COADS compliant. NONE will mean that
3370    !Config         no restart file is to be expected.
3371    !Config Units = [FILE]
3372!-
3373    CALL getin_p('SECHIBA_restart_in',restname_in)
3374    IF (printlev >= 2) WRITE(numout,*) 'Restart file for sechiba: ', restname_in
3375    !-
3376    !Config Key   = SECHIBA_rest_out
3377    !Config Desc  = Name of restart files to be created by SECHIBA
3378    !Config If    = OK_SECHIBA
3379    !Config Def   = sechiba_rest_out.nc
3380    !Config Help  = This variable give the name for
3381    !Config         the restart files. The restart software within
3382    !Config         IOIPSL will add .nc if needed.
3383    !Config Units = [FILE]
3384    !
3385    CALL getin_p('SECHIBA_rest_out', restname_out)
3386 
3387    lev(:) = zero
3388    itau_dep = istp
3389    in_julian = itau2date(istp, date0, dt)
3390    date0_rest = date0
3391    dt_rest = dt
3392    !
3393    IF (is_root_prc) THEN
3394      CALL restini( restname_in, iim_g, jjm_g, lon_g, lat_g, llm, lev, &
3395         &  restname_out, itau_dep, date0_rest, dt_rest, rest_id, overwrite_time)
3396      nb_restfile_ids=nb_restfile_ids+1
3397      restfile_ids(nb_restfile_ids)=rest_id
3398    ELSE
3399       rest_id=0
3400    ENDIF
3401    CALL bcast (itau_dep)
3402    CALL bcast (date0_rest)
3403    CALL bcast (dt_rest)
3404    !
3405    !  itau_dep of SECHIBA is phased with the GCM if needed
3406    !
3407    rest_julian = itau2date(itau_dep, date0_rest, dt_rest)
3408
3409    ! Note by JG
3410    ! restini never modifies itau_dep and date0_rest when overwrite_time=TRUE.
3411    ! This means that itau_dep=istp and date0_rest=date0 => rest_julian=in_julian.
3412    ! The result of below IF will therfor always be itau_offset=0 and date0_shifted=date0
3413    IF ( ABS( in_julian - rest_julian) .GT. dt/one_day .AND. .NOT. OFF_LINE_MODE ) THEN
3414       WRITE(numout,*) 'The SECHIBA restart is not for the same timestep as the GCM,'
3415       WRITE(numout,*) 'the two are synchronized. The land-surface conditions can not impose'
3416       WRITE(numout,*) 'the chronology of the simulation.'
3417       WRITE(numout,*) 'Time step of the GCM :', istp, 'Julian day : ', in_julian
3418       CALL ju2ymds(in_julian, yy, mm, dd, ss)
3419       WRITE(numout,*) 'In other word (yy,mm,dd,ss) : ', yy, mm, dd, ss
3420       WRITE(numout,*) 'Time step of SECHIBA :', itau_dep, 'Julian day : ', rest_julian
3421       CALL ju2ymds(rest_julian, yy, mm, dd, ss)
3422       WRITE(numout,*) 'In other word (yy,mm,dd,ss) : ', yy, mm, dd, ss
3423       
3424       itau_offset = itau_dep - istp
3425       date0_shifted = date0 - itau_offset*dt/one_day
3426       
3427       WRITE(numout,*) 'The new starting date is :', date0_shifted
3428       CALL ju2ymds(date0_shifted, yy, mm, dd, ss)
3429       WRITE(numout,*) 'In other word (yy,mm,dd,ss) : ', yy, mm, dd, ss
3430    ELSE
3431       itau_offset = 0
3432       date0_shifted = date0
3433    ENDIF
3434
3435    !=====================================================================
3436    !- 1.5 Restart file for STOMATE
3437    !=====================================================================
3438    IF ( ok_stomate ) THEN 
3439       !-
3440       ! STOMATE IS ACTIVATED
3441       !-
3442       !Config Key   = STOMATE_RESTART_FILEIN
3443       !Config Desc  = Name of restart to READ for initial conditions of STOMATE
3444       !Config If    = STOMATE_OK_STOMATE
3445       !Config Def   = NONE
3446       !Config Help  = This is the name of the file which will be opened
3447       !Config         to extract the initial values of all prognostic
3448       !Config         values of STOMATE.
3449       !Config Units = [FILE]
3450       !-
3451       CALL getin_p('STOMATE_RESTART_FILEIN',stom_restname_in)
3452       IF (printlev >= 2) WRITE(numout,*) 'STOMATE INPUT RESTART_FILE', stom_restname_in
3453       !-
3454       !Config Key   = STOMATE_RESTART_FILEOUT
3455       !Config Desc  = Name of restart files to be created by STOMATE
3456       !Config If    = STOMATE_OK_STOMATE
3457       !Config Def   = stomate_rest_out.nc
3458       !Config Help  = This is the name of the file which will be opened
3459       !Config         to write the final values of all prognostic values
3460       !Config         of STOMATE.
3461       !Config Units = [FILE]
3462       !-
3463       CALL getin_p('STOMATE_RESTART_FILEOUT', stom_restname_out)
3464       IF (printlev >= 2) WRITE(numout,*) 'STOMATE OUTPUT RESTART_FILE', stom_restname_out
3465       !-
3466       IF (is_root_prc) THEN
3467         CALL restini (stom_restname_in, iim_g, jjm_g, lon_g, lat_g, llm, lev, &
3468            &  stom_restname_out, itau_dep, date0_rest, dt_rest, rest_id_stom, overwrite_time)
3469         nb_restfile_ids=nb_restfile_ids+1
3470         restfile_ids(nb_restfile_ids)=rest_id_stom
3471       ELSE
3472         rest_id_stom=0
3473       ENDIF
3474       CALL bcast (itau_dep)
3475       CALL bcast (date0_rest)
3476       CALL bcast (dt_rest)
3477       !-
3478    ENDIF
3479  END SUBROUTINE ioipslctrl_restini
3480
3481
3482!! ================================================================================================================================
3483!! SUBROUTINE    : ioipslctrl_restclo
3484!!
3485!>\BRIEF         This subroutine close the restart files in ORCHDIEE.
3486!!
3487!! DESCRIPTION   : This subroutine close restart files in ORCHIDEE. IOIPSL is used for writing the restart files.
3488!!                 
3489!!
3490!! RECENT CHANGE(S): None
3491!!
3492!! \n
3493!_ ================================================================================================================================
3494  SUBROUTINE ioipslctrl_restclo
3495  IMPLICIT NONE
3496    INTEGER(i_std) :: n
3497   
3498    IF (is_root_prc) THEN
3499      DO n=1,nb_restfile_ids
3500        CALL restclo(restfile_ids(n))
3501      ENDDO
3502    ENDIF
3503   
3504  END SUBROUTINE ioipslctrl_restclo
3505   
3506
3507END MODULE ioipslctrl
Note: See TracBrowser for help on using the repository browser.