source: tags/ORCHIDEE_1_9_5/ORCHIDEE/src_sechiba/intersurf.f90 @ 3999

Last change on this file since 3999 was 8, checked in by orchidee, 14 years ago

import first tag equivalent to CVS orchidee_1_9_5 + OOL_1_9_5

File size: 271.2 KB
Line 
1
2!! This subroutine is the interface between the main program
3!! (LMDZ or dim2_driver) and SECHIBA.
4!! - Input fields are gathered to keep just continental points
5!! - call sechiba_main That's SECHIBA process.
6!! - Output fields are scattered to complete global fields
7!!
8!! @call sechiba_main
9!! @Version : $Revision: 1.85 $, $Date: 2010/07/29 15:58:19 $
10!!
11!! @author Marie-Alice Foujols and Jan Polcher
12!!
13!! $Header: /home/ssipsl/CVSREP/ORCHIDEE/src_sechiba/intersurf.f90,v 1.85 2010/07/29 15:58:19 ssipsl Exp $
14!! IPSL (2006)
15!!  This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC
16!!
17!f90doc MODULEintersurf
18MODULE intersurf
19
20  USE IOIPSL
21
22  USE defprec
23  USE sechiba
24  USE constantes
25  USE constantes_soil
26  USE constantes_veg
27  USE parallel
28  USE watchout
29  USE solar
30  USE grid
31!    USE Write_Field_p
32
33  IMPLICIT NONE
34
35  PRIVATE
36  PUBLIC :: intersurf_main, stom_define_history, intsurf_time
37
38  INTERFACE intersurf_main
39    MODULE PROCEDURE intersurf_main_2d, intersurf_main_1d, intersurf_gathered, intersurf_gathered_2m
40  END INTERFACE
41  !
42  !  Global variables
43  !
44  INTEGER(i_std),PARAMETER                           :: max_hist_level = 11
45  !
46  LOGICAL, SAVE                                     :: l_first_intersurf=.TRUE. !! Initialisation has to be done one time
47  !
48  INTEGER(i_std), SAVE                               :: hist_id, rest_id        !! IDs for history and restart files
49  INTEGER(i_std), SAVE                               :: hist2_id                !! ID for the second history files (Hi-frequency ?)
50  INTEGER(i_std), SAVE                               :: hist_id_stom, hist_id_stom_IPCC, rest_id_stom !! Dito for STOMATE
51  REAL(r_std), SAVE                                  :: dw                      !! frequency of history write (sec.)
52  !
53  INTEGER(i_std), SAVE                               :: itau_offset  !! This offset is used to phase the
54  !                                                                 !! calendar of the GCM or the driver.
55  REAL(r_std)                                        :: date0_shifted
56  !
57  TYPE(control_type), SAVE                          :: control_flags !! Flags that (de)activate parts of the model
58  !
59  !
60  !! first day of this year
61  REAL(r_std) :: julian0
62  !
63  LOGICAL :: check_INPUTS = .FALSE.         !! (very) long print of INPUTs in intersurf
64  LOGICAL, SAVE :: OFF_LINE_MODE = .FALSE. 
65  !
66CONTAINS
67  !
68  !f90doc CONTAINS
69  !
70  SUBROUTINE intersurf_main_2d (kjit, iim, jjm, kjpindex, kindex, xrdt, &
71     & lrestart_read, lrestart_write, lon, lat, zcontfrac, zneighbours, zresolution, date0, &
72! First level conditions
73     & zlev, u, v, qair, temp_air, epot_air, ccanopy, &
74! Variables for the implicit coupling
75     & cdrag, petAcoef, peqAcoef, petBcoef, peqBcoef, &
76! Rain, snow, radiation and surface pressure
77     & precip_rain, precip_snow, lwdown, swnet, swdown, pb, &
78! Output : Fluxes
79     & vevapp, fluxsens, fluxlat, coastalflow, riverflow, &
80! Surface temperatures and surface properties
81     & tsol_rad, temp_sol_new, qsurf, albedo, emis, z0) 
82   
83    ! routines called : sechiba_main
84    !
85    IMPLICIT NONE
86    !   
87    ! interface description for dummy arguments
88    ! input scalar
89    INTEGER(i_std),INTENT (in)                            :: kjit          !! Time step number
90    INTEGER(i_std),INTENT (in)                            :: iim, jjm      !! Dimension of input fields
91    INTEGER(i_std),INTENT (in)                            :: kjpindex      !! Number of continental points
92    REAL(r_std),INTENT (in)                               :: xrdt          !! Time step in seconds
93    LOGICAL, INTENT (in)                                 :: lrestart_read !! Logical for _restart_ file to read
94    LOGICAL, INTENT (in)                                 :: lrestart_write!! Logical for _restart_ file to write'
95    REAL(r_std), INTENT (in)                              :: date0         !! Date at which kjit = 0
96    ! input fields
97    INTEGER(i_std),DIMENSION (kjpindex), INTENT (in)      :: kindex        !! Index for continental points
98    REAL(r_std),DIMENSION (iim,jjm), INTENT(in)             :: u             !! Lowest level wind speed
99    REAL(r_std),DIMENSION (iim,jjm), INTENT(in)             :: v             !! Lowest level wind speed
100    REAL(r_std),DIMENSION (iim,jjm), INTENT(in)             :: zlev          !! Height of first layer
101    REAL(r_std),DIMENSION (iim,jjm), INTENT(in)             :: qair          !! Lowest level specific humidity
102    REAL(r_std),DIMENSION (iim,jjm), INTENT(in)             :: precip_rain   !! Rain precipitation
103    REAL(r_std),DIMENSION (iim,jjm), INTENT(in)             :: precip_snow   !! Snow precipitation
104    REAL(r_std),DIMENSION (iim,jjm), INTENT(in)             :: lwdown        !! Down-welling long-wave flux
105    REAL(r_std),DIMENSION (iim,jjm), INTENT(in)             :: swnet         !! Net surface short-wave flux
106    REAL(r_std),DIMENSION (iim,jjm), INTENT(in)             :: swdown        !! Downwelling surface short-wave flux
107    REAL(r_std),DIMENSION (iim,jjm), INTENT(in)             :: temp_air      !! Air temperature in Kelvin
108    REAL(r_std),DIMENSION (iim,jjm), INTENT(in)             :: epot_air      !! Air potential energy
109    REAL(r_std),DIMENSION (iim,jjm), INTENT(in)             :: ccanopy       !! CO2 concentration in the canopy
110    REAL(r_std),DIMENSION (iim,jjm), INTENT(in)             :: petAcoef      !! Coeficients A from the PBL resolution
111    REAL(r_std),DIMENSION (iim,jjm), INTENT(in)             :: peqAcoef      !! One for T and another for q
112    REAL(r_std),DIMENSION (iim,jjm), INTENT(in)             :: petBcoef      !! Coeficients B from the PBL resolution
113    REAL(r_std),DIMENSION (iim,jjm), INTENT(in)             :: peqBcoef      !! One for T and another for q
114    REAL(r_std),DIMENSION (iim,jjm), INTENT(inout)          :: cdrag         !! Cdrag
115    REAL(r_std),DIMENSION (iim,jjm), INTENT(in)             :: pb            !! Lowest level pressure
116    REAL(r_std),DIMENSION (iim,jjm), INTENT(in)             :: lon, lat      !! Geographical coordinates
117    REAL(r_std),DIMENSION (iim,jjm), INTENT(in)             :: zcontfrac      !! Fraction of continent in the grid
118    INTEGER, DIMENSION (iim,jjm,8), INTENT(in)             :: zneighbours   !! land neighbours
119    REAL(r_std),DIMENSION (iim,jjm,2), INTENT(in)           :: zresolution   !! resolution in x and y dimensions
120    ! output fields
121    REAL(r_std),DIMENSION (iim,jjm), INTENT(out)            :: z0            !! Surface roughness
122    REAL(r_std),DIMENSION (iim,jjm), INTENT(out)            :: coastalflow   !! Diffuse flow of water into the ocean (m^3/dt)
123    REAL(r_std),DIMENSION (iim,jjm), INTENT(out)            :: riverflow     !! Largest rivers flowing into the ocean (m^3/dt)
124    REAL(r_std),DIMENSION (iim,jjm), INTENT(out)            :: tsol_rad      !! Radiative surface temperature
125    REAL(r_std),DIMENSION (iim,jjm), INTENT(out)            :: vevapp        !! Total of evaporation
126    REAL(r_std),DIMENSION (iim,jjm), INTENT(out)            :: temp_sol_new  !! New soil temperature
127    REAL(r_std),DIMENSION (iim,jjm), INTENT(out)            :: qsurf         !! Surface specific humidity
128    REAL(r_std),DIMENSION (iim,jjm,2), INTENT(out)          :: albedo        !! Albedo
129    REAL(r_std),DIMENSION (iim,jjm), INTENT(out)            :: fluxsens      !! Sensible chaleur flux
130    REAL(r_std),DIMENSION (iim,jjm), INTENT(out)            :: fluxlat       !! Latent chaleur flux
131    REAL(r_std),DIMENSION (iim,jjm), INTENT(out)            :: emis          !! Emissivity
132    ! LOCAL declaration
133    ! work arrays to scatter and/or gather information just before/after sechiba_main call's
134    ! and to keep output value for next call
135    REAL(r_std),DIMENSION (kjpindex)                      :: zu            !! Work array to keep u
136    REAL(r_std),DIMENSION (kjpindex)                      :: zv            !! Work array to keep v
137    REAL(r_std),DIMENSION (kjpindex)                      :: zzlev         !! Work array to keep zlev
138    REAL(r_std),DIMENSION (kjpindex)                      :: zqair         !! Work array to keep qair
139    REAL(r_std),DIMENSION (kjpindex)                      :: zprecip_rain  !! Work array to keep precip_rain
140    REAL(r_std),DIMENSION (kjpindex)                      :: zprecip_snow  !! Work array to keep precip_snow
141    REAL(r_std),DIMENSION (kjpindex)                      :: zlwdown       !! Work array to keep lwdown
142    REAL(r_std),DIMENSION (kjpindex)                      :: zswnet        !! Work array to keep swnet
143    REAL(r_std),DIMENSION (kjpindex)                      :: zswdown       !! Work array to keep swdown
144    REAL(r_std),DIMENSION (kjpindex)                      :: ztemp_air     !! Work array to keep temp_air
145    REAL(r_std),DIMENSION (kjpindex)                      :: zepot_air     !! Work array to keep epot_air
146    REAL(r_std),DIMENSION (kjpindex)                      :: zccanopy      !! Work array to keep ccanopy
147    REAL(r_std),DIMENSION (kjpindex)                      :: zpetAcoef     !! Work array to keep petAcoef
148    REAL(r_std),DIMENSION (kjpindex)                      :: zpeqAcoef     !! Work array to keep peqAcoef
149    REAL(r_std),DIMENSION (kjpindex)                      :: zpetBcoef     !! Work array to keep petBcoef
150    REAL(r_std),DIMENSION (kjpindex)                      :: zpeqBcoef     !! Work array to keep peqVcoef
151    REAL(r_std),DIMENSION (kjpindex)                      :: zcdrag        !! Work array to keep cdrag
152    REAL(r_std),DIMENSION (kjpindex)                      :: zpb           !! Work array to keep pb
153    REAL(r_std),DIMENSION (kjpindex)                      :: zz0           !! Work array to keep z0
154    REAL(r_std),DIMENSION (kjpindex)                      :: zcoastal      !! Work array to keep coastalflow
155    REAL(r_std),DIMENSION (kjpindex)                      :: zriver        !! Work array to keep riverflow
156    REAL(r_std),DIMENSION (kjpindex)                      :: dcoastal      !! Work array to keep coastalflow
157    REAL(r_std),DIMENSION (kjpindex)                      :: driver        !! Work array to keep riverflow
158    REAL(r_std),DIMENSION (kjpindex)                      :: ztsol_rad     !! Work array to keep tsol_rad
159    REAL(r_std),DIMENSION (kjpindex)                      :: zvevapp       !! Work array to keep vevapp
160    REAL(r_std),DIMENSION (kjpindex)                      :: ztemp_sol_new !! Work array to keep temp_sol_new
161    REAL(r_std),DIMENSION (kjpindex)                      :: zqsurf        !! Work array to keep qsurf
162    REAL(r_std),DIMENSION (kjpindex,2)                    :: zalbedo       !! Work array to keep albedo
163    REAL(r_std),DIMENSION (kjpindex)                      :: zfluxsens     !! Work array to keep fluxsens
164    REAL(r_std),DIMENSION (kjpindex)                      :: zfluxlat      !! Work array to keep fluxlat
165    REAL(r_std),DIMENSION (kjpindex)                      :: zemis         !! Work array to keep emis
166    !
167    ! Local variables with shape of the inputs
168    !
169    REAL(r_std),DIMENSION (iim,jjm)                       :: dswnet         !! Net surface short-wave flux
170    REAL(r_std),DIMENSION (iim,jjm)                       :: dswdown         !! Incident surface short-wave flux
171    !
172    INTEGER(i_std)                                       :: i, j, ik
173    INTEGER(i_std)                                       :: itau_sechiba
174    REAL(r_std)                                           :: zlev_mean
175    LOGICAL                                              :: do_watch      !! if it's time, write watchout
176    INTEGER                                              :: old_fileout   !! old Logical Int for std IO output
177    LOGICAL :: check = .FALSE.
178    !
179    CALL ipslnlf(new_number=numout,old_number=old_fileout)
180    !
181    IF (l_first_intersurf) THEN
182!       CALL Init_WriteField_p(kindex)
183       !
184       CALL intsurf_time( kjit, date0, xrdt )
185       !
186       IF ( check ) WRITE(numout,*) 'Initialisation of intersurf_main_2d'
187       !
188       OFF_LINE_MODE = .TRUE. 
189       !
190       DO ik=1,kjpindex
191         
192          j = ((kindex(ik)-1)/iim) + 1
193          i = (kindex(ik) - (j-1)*iim)
194
195          !- Create the internal coordinate table
196          !-
197          lalo(ik,1) = lat(i,j)
198          lalo(ik,2) = lon(i,j)
199          !
200          !- Store the fraction of the continents only once so that the user
201          !- does not change them afterwards.
202          !-
203          contfrac(ik) = zcontfrac(i,j)
204       ENDDO
205       CALL gather(contfrac,contfrac_g)
206       CALL gather(lalo,lalo_g)
207       CALL gather2D(lon,lon_g)
208       CALL gather2D(lat,lat_g)
209       CALL gather2D(zlev,zlev_g)
210       !
211       !  Configuration of SSL specific parameters
212       !
213       CALL intsurf_config(control_flags, xrdt)
214       !
215       CALL intsurf_restart(kjit, iim, jjm, lon, lat, date0, xrdt, control_flags, rest_id, rest_id_stom, itau_offset)
216       itau_sechiba = kjit + itau_offset
217       !
218       CALL intsurf_history(iim, jjm, lon, lat, itau_sechiba, date0_shifted, xrdt, control_flags, hist_id, &
219            & hist2_id, hist_id_stom, hist_id_stom_IPCC)
220       !
221       IF ( ok_watchout ) THEN
222          IF (is_root_prc) THEN
223             zlev_mean = 0.
224             DO ik=1, nbp_glo
225                j = ((index_g(ik)-1)/iim_g) + 1
226                i = (index_g(ik) - (j-1)*iim_g)
227       
228                zlev_mean = zlev_mean + zlev_g(i,j)
229             ENDDO
230             zlev_mean = zlev_mean / REAL(nbp_glo,r_std)
231          ENDIF
232
233          last_action_watch = itau_sechiba
234          last_check_watch  = last_action_watch
235
236          ! Only root proc write watchout file
237          CALL watchout_init (iim_g, jjm_g, kjpindex, nbp_glo, &
238               & date0_shifted, last_action_watch, dt_watch, index_g, lon_g, lat_g, zlev_mean)
239       ENDIF
240       !
241       IF ( check ) WRITE(numout,*) 'End of Initialisation of intersurf'
242       !
243    ENDIF
244    !
245    !  Shift the time step to phase the two models
246    !
247    itau_sechiba = kjit + itau_offset
248    !
249    CALL intsurf_time( itau_sechiba, date0_shifted, xrdt )
250    !
251    ! 1. gather input fields from kindex array
252    !    Warning : I'm not sure this interface with one dimension array is the good one
253    !
254    DO ik=1, kjpindex
255     
256       j = ((kindex(ik)-1)/iim) + 1
257       i = (kindex(ik) - (j-1)*iim)
258       
259       zu(ik)           = u(i,j)
260       zv(ik)           = v(i,j)
261       zzlev(ik)        = zlev(i,j)
262       zqair(ik)        = qair(i,j)
263       zprecip_rain(ik) = precip_rain(i,j)*xrdt
264       zprecip_snow(ik) = precip_snow(i,j)*xrdt
265       zlwdown(ik)      = lwdown(i,j)
266       zswnet(ik)       = swnet(i,j)
267       zswdown(ik)      = swdown(i,j)
268       ztemp_air(ik)    = temp_air(i,j)
269       zepot_air(ik)    = epot_air(i,j)
270       zccanopy(ik)     = ccanopy(i,j)
271       zpetAcoef(ik)    = petAcoef(i,j)
272       zpeqAcoef(ik)    = peqAcoef(i,j)
273       zpetBcoef(ik)    = petBcoef(i,j)
274       zpeqBcoef(ik)    = peqBcoef(i,j)
275       zcdrag(ik)       = cdrag(i,j)
276       zpb(ik)          = pb(i,j)
277       
278    ENDDO
279    !
280    IF (check_INPUTS) THEN
281       WRITE(numout,*) "Intersurf_main_2D :"
282       WRITE(numout,*) "Time step number = ",kjit
283       WRITE(numout,*) "Dimension of input fields = ",iim, jjm
284       WRITE(numout,*) "Number of continental points = ",kjpindex
285       WRITE(numout,*) "Time step in seconds = ",xrdt
286       WRITE(numout,*) "Logical for _restart_ file to read, write = ",lrestart_read,lrestart_write
287       WRITE(numout,*) "Date at which kjit = 0  =  ",date0
288       WRITE(numout,*) "Index for continental points = ",kindex
289       WRITE(numout,*) "Lowest level wind speed North = ",zu
290       WRITE(numout,*) "Lowest level wind speed East = ",zv
291       WRITE(numout,*) "Height of first layer = ",zzlev
292       WRITE(numout,*) "Lowest level specific humidity = ",zqair
293       WRITE(numout,*) "Rain precipitation = ",zprecip_rain
294       WRITE(numout,*) "Snow precipitation = ",zprecip_snow
295       WRITE(numout,*) "Down-welling long-wave flux = ",zlwdown
296       WRITE(numout,*) "Net surface short-wave flux = ",zswnet
297       WRITE(numout,*) "Downwelling surface short-wave flux = ",zswdown
298       WRITE(numout,*) "Air temperature in Kelvin = ",ztemp_air
299       WRITE(numout,*) "Air potential energy = ",zepot_air
300       WRITE(numout,*) "CO2 concentration in the canopy = ",zccanopy
301       WRITE(numout,*) "Coeficients A from the PBL resolution = ",zpetAcoef
302       WRITE(numout,*) "One for T and another for q = ",zpeqAcoef
303       WRITE(numout,*) "Coeficients B from the PBL resolution = ",zpetBcoef
304       WRITE(numout,*) "One for T and another for q = ",zpeqBcoef
305       WRITE(numout,*) "Cdrag = ",zcdrag
306       WRITE(numout,*) "Lowest level pressure = ",zpb
307       WRITE(numout,*) "Geographical coordinates lon = ", (/ ( lon(ilandindex(ik), jlandindex(ik)), ik=1,kjpindex ) /)
308       WRITE(numout,*) "Geographical coordinates lat = ", (/ ( lat(ilandindex(ik), jlandindex(ik)), ik=1,kjpindex ) /) 
309       WRITE(numout,*) "Fraction of continent in the grid = ",contfrac
310    ENDIF
311    !
312    ! 2. save the grid
313    !
314    IF ( check ) WRITE(numout,*) 'Save the grid'
315    !
316    IF (l_first_intersurf) THEN
317       CALL histwrite(hist_id, 'LandPoints',  itau_sechiba+1, (/ ( REAL(ik), ik=1,kjpindex ) /), kjpindex, kindex)
318       CALL histwrite(hist_id, 'Areas',  itau_sechiba+1, area, kjpindex, kindex)
319       IF ( control_flags%ok_stomate ) THEN
320          CALL histwrite(hist_id_stom, 'Areas',  itau_sechiba+1, area, kjpindex, kindex)
321          IF ( hist_id_stom_IPCC > 0 ) THEN
322             CALL histwrite(hist_id_stom_IPCC, 'Areas',  itau_sechiba+1, area, kjpindex, kindex)
323          ENDIF
324       ENDIF
325       CALL histwrite(hist_id, 'Contfrac',  itau_sechiba+1, contfrac, kjpindex, kindex)
326       CALL histsync(hist_id)
327       !
328       IF ( hist2_id > 0 ) THEN
329          CALL histwrite(hist2_id, 'LandPoints',  itau_sechiba+1, (/ ( REAL(ik), ik=1,kjpindex ) /), kjpindex, kindex)
330          CALL histwrite(hist2_id, 'Areas',  itau_sechiba+1, area, kjpindex, kindex)
331          CALL histwrite(hist2_id, 'Contfrac',  itau_sechiba+1, contfrac, kjpindex, kindex)
332          CALL histsync(hist2_id)
333       ENDIF
334       !
335    ENDIF
336    !
337    ! 3. call sechiba for continental points only
338    !
339    IF ( check ) WRITE(numout,*) 'Calling sechiba'
340    !
341    CALL sechiba_main (itau_sechiba, iim*jjm, kjpindex, kindex, xrdt, date0_shifted, &
342       & lrestart_read, lrestart_write, control_flags, &
343       & lalo, contfrac, neighbours, resolution, &
344! First level conditions
345! Ajout Nathalie - Juin 2006 - passage q2m/t2m pour calcul rveget
346!       & zzlev, zu, zv, zqair, ztemp_air, zepot_air, zccanopy, &
347       & zzlev, zu, zv, zqair, zqair, ztemp_air, ztemp_air, zepot_air, zccanopy, &
348! Variables for the implicit coupling
349       & zcdrag, zpetAcoef, zpeqAcoef, zpetBcoef, zpeqBcoef, &
350! Rain, snow, radiation and surface pressure
351       & zprecip_rain ,zprecip_snow,  zlwdown, zswnet, zswdown, zpb, &
352! Output : Fluxes
353       & zvevapp, zfluxsens, zfluxlat, zcoastal, zriver, &
354! Surface temperatures and surface properties
355       & ztsol_rad, ztemp_sol_new, zqsurf, zalbedo, zemis, zz0, &
356! File ids
357       & rest_id, hist_id, hist2_id, rest_id_stom, hist_id_stom, hist_id_stom_IPCC ) 
358   
359    !
360    IF ( check ) WRITE(numout,*) 'out of SECHIBA'
361    !
362    ! 4. save watchout
363    !
364    IF ( ok_watchout .AND. .NOT. l_first_intersurf ) THEN
365       ! Accumulate last time step
366       sum_zlev(:) = sum_zlev(:) + zzlev(:)
367       sum_u(:) = sum_u(:) + zu(:)
368       sum_v(:) = sum_v(:) + zv(:)
369       sum_qair(:) = sum_qair(:) + zqair(:) 
370       sum_temp_air(:) = sum_temp_air(:) + ztemp_air(:)
371       sum_epot_air(:) = sum_epot_air(:) + zepot_air(:)
372       sum_ccanopy(:) = sum_ccanopy(:) + zccanopy(:)
373       sum_cdrag(:) = sum_cdrag(:) + zcdrag(:)
374       sum_petAcoef(:) = sum_petAcoef(:) + zpetAcoef(:)
375       sum_peqAcoef(:) = sum_peqAcoef(:) + zpeqAcoef(:)
376       sum_petBcoef(:) = sum_petBcoef(:) + zpetBcoef(:)
377       sum_peqBcoef(:) = sum_peqBcoef(:) + zpeqBcoef(:)
378       sum_rain(:) = sum_rain(:) + zprecip_rain(:)
379       sum_snow(:) = sum_snow(:) + zprecip_snow(:)
380       sum_lwdown(:) = sum_lwdown(:) + zlwdown(:)
381       sum_pb(:) = sum_pb(:) + zpb(:)
382
383!!$       IF ( dt_watch > 3600 ) THEN
384!!$          julian_watch = date0_shifted+((itau_sechiba-0.5)/dt_split_watch)*dt_watch/one_day
385!!$          WRITE(numout, *) "WATCH register : julian_watch ",julian_watch, " julian0",julian0,"date0_shifted ",date0_shifted, &
386!!$               "itau_sechiba ",itau_sechiba, &
387!!$               dt_split_watch,dt_watch,one_day
388!!$          CALL solarang (julian_watch, julian0, iim, jjm, lon, lat, sinang)
389!!$          WHERE ( sinang(:,:) .LT. EPSILON(1.) )
390!!$             isinang(:,:) = isinang(:,:) - 1
391!!$          ENDWHERE
392!!$          mean_sinang(:,:) = mean_sinang(:,:)+sinang(:,:)
393!!$          WRITE(numout, *) "WATCH sinang : ",sinang, mean_sinang
394!!$          WRITE(numout,*) "sum_swdown",sum_swdown
395!!$          !
396!!$          DO ik=1,kjpindex         
397!!$             j = ((kindex(ik)-1)/iim) + 1
398!!$             i = (kindex(ik) - (j-1)*iim)
399!!$             
400!!$             sum_swnet(ik) = sum_swnet(ik) + sinang(i,j)*zswnet(ik)
401!!$             sum_swdown(ik) = sum_swdown(ik) + sinang(i,j)*zswdown(ik)
402!!$          ENDDO
403!!$       ELSE
404          sum_swnet(:) = sum_swnet(:) + zswnet(:)
405          sum_swdown(:) = sum_swdown(:) + zswdown(:)
406!!$       ENDIF
407
408       do_watch = .FALSE.
409       call isittime &
410            &  (itau_sechiba,date0_shifted,xrdt,dt_watch,&
411            &   last_action_watch,last_check_watch,do_watch)
412       last_check_watch = itau_sechiba
413       IF (do_watch) THEN
414          !
415          IF ( check ) WRITE(numout,*) 'save watchout'
416          !
417          IF (long_print) THEN
418             WRITE(numout,*) "intersurf : write watchout for date ",date0,date0_shifted,itau_sechiba,&
419                  & last_action_watch, last_check_watch
420          ENDIF
421          last_action_watch = itau_sechiba
422
423          sum_zlev(:) = sum_zlev(:) / dt_split_watch
424          sum_u(:) = sum_u(:) / dt_split_watch
425          sum_v(:) = sum_v(:) / dt_split_watch
426          sum_qair(:) = sum_qair(:) / dt_split_watch
427          sum_temp_air(:) = sum_temp_air(:) / dt_split_watch
428          sum_epot_air(:) = sum_epot_air(:) / dt_split_watch
429          sum_ccanopy(:) = sum_ccanopy(:) / dt_split_watch
430          sum_cdrag(:) = sum_cdrag(:) / dt_split_watch
431          sum_petAcoef(:) = sum_petAcoef(:) / dt_split_watch
432          sum_peqAcoef(:) = sum_peqAcoef(:) / dt_split_watch
433          sum_petBcoef(:) = sum_petBcoef(:) / dt_split_watch
434          sum_peqBcoef(:) = sum_peqBcoef(:) / dt_split_watch
435          sum_rain(:) = sum_rain(:) / dt_split_watch
436          sum_snow(:) = sum_snow(:) / dt_split_watch
437          sum_lwdown(:) = sum_lwdown(:) / dt_split_watch
438          sum_pb(:) = sum_pb(:) / dt_split_watch
439
440!!$          IF ( dt_watch > 3600 ) THEN
441!!$             WRITE(numout, *) "WATCH mean_sinang before norm : ",mean_sinang,isinang
442!!$             WHERE ( isinang(:,:) .LT. dt_split_watch )
443!!$                mean_sinang(:,:) = mean_sinang(:,:) / isinang(:,:)
444!!$             ENDWHERE
445!!$             WRITE(numout, *) "WATCH mean_sinang norm : ",mean_sinang
446!!$             WRITE(numout,*) "SWDOWN 0 : ",sum_swdown(:)
447!!$             !
448!!$             DO ik=1,kjpindex         
449!!$                j = ((kindex(ik)-1)/iim) + 1
450!!$                i = (kindex(ik) - (j-1)*iim)
451!!$                IF (mean_sinang(i,j) > zero) THEN
452!!$                   sum_swdown(ik) = sum_swdown(ik)/mean_sinang(i,j)
453!!$                   sum_swnet(ik) =  sum_swnet(ik)/mean_sinang(i,j)
454!!$                ELSE
455!!$                   sum_swdown(ik) = zero
456!!$                   sum_swnet(ik) =  zero
457!!$                ENDIF
458!!$             ENDDO
459!!$          ELSE
460             sum_swnet(:) = sum_swnet(:) / dt_split_watch
461             sum_swdown(:) = sum_swdown(:) / dt_split_watch
462!!$          ENDIF
463
464          CALL watchout_write_p(kjpindex, itau_sechiba, xrdt, sum_zlev, sum_swdown, sum_rain, &
465               &   sum_snow, sum_lwdown, sum_pb, sum_temp_air, sum_epot_air, sum_qair, &
466               &   sum_u, sum_v, sum_swnet, sum_petAcoef, sum_peqAcoef, sum_petBcoef, sum_peqBcoef, &
467               &   sum_cdrag, sum_ccanopy )
468       ENDIF
469    ENDIF
470    !
471    ! 5. scatter output fields
472    !
473    z0(:,:)           = undef_sechiba
474    coastalflow(:,:)  = undef_sechiba
475    riverflow(:,:)    = undef_sechiba
476    tsol_rad(:,:)     = undef_sechiba
477    vevapp(:,:)       = undef_sechiba
478    temp_sol_new(:,:) = undef_sechiba 
479    qsurf(:,:)        = undef_sechiba 
480    albedo(:,:,:)     = undef_sechiba
481    fluxsens(:,:)     = undef_sechiba
482    fluxlat(:,:)      = undef_sechiba
483    emis(:,:)         = undef_sechiba 
484    cdrag(:,:)        = undef_sechiba 
485    dswnet(:,:)       = undef_sechiba 
486    dswdown(:,:)      = undef_sechiba 
487    !
488    DO ik=1, kjpindex
489     
490   
491       j = ((kindex(ik)-1)/iim) + 1
492       i = (kindex(ik) - (j-1)*iim)
493
494       z0(i,j)           = zz0(ik)
495       coastalflow(i,j)  = zcoastal(ik)/1000.
496       riverflow(i,j)    = zriver(ik)/1000.
497       tsol_rad(i,j)     = ztsol_rad(ik)
498       vevapp(i,j)       = zvevapp(ik)
499       temp_sol_new(i,j) = ztemp_sol_new(ik)
500       qsurf(i,j)        = zqsurf(ik)
501       albedo(i,j,1)     = zalbedo(ik,1)
502       albedo(i,j,2)     = zalbedo(ik,2)
503       fluxsens(i,j)     = zfluxsens(ik)
504       fluxlat(i,j)      = zfluxlat(ik)
505       emis(i,j)         = zemis(ik)
506       cdrag(i,j)        = zcdrag(ik)
507       dswnet(i,j)       = zswnet(ik)
508       dswdown(i,j)      = zswdown(ik)
509
510    ENDDO
511    !
512    ! Modified fields for variables scattered during the writing
513    !
514    dcoastal(:) = (zcoastal(:))/1000.     
515    driver(:)   = (zriver(:))/1000.
516    !
517    IF ( .NOT. l_first_intersurf) THEN
518       !
519       IF ( .NOT. almaoutput ) THEN
520       !
521       !  scattered during the writing
522       !
523          CALL histwrite (hist_id, 'evap',     itau_sechiba, zvevapp, kjpindex, kindex)
524          CALL histwrite (hist_id, 'coastalflow',itau_sechiba, dcoastal, kjpindex, kindex)
525          CALL histwrite (hist_id, 'riverflow',itau_sechiba, driver, kjpindex, kindex)
526       !
527          CALL histwrite (hist_id, 'temp_sol', itau_sechiba, temp_sol_NEW, iim*jjm, kindex)
528          CALL histwrite (hist_id, 'tsol_max', itau_sechiba, temp_sol_NEW, iim*jjm, kindex)
529          CALL histwrite (hist_id, 'tsol_min', itau_sechiba, temp_sol_NEW, iim*jjm, kindex)
530          CALL histwrite (hist_id, 'fluxsens', itau_sechiba, fluxsens, iim*jjm, kindex)
531          CALL histwrite (hist_id, 'fluxlat',  itau_sechiba, fluxlat, iim*jjm, kindex)
532          CALL histwrite (hist_id, 'swnet',    itau_sechiba, dswnet, iim*jjm, kindex)
533          CALL histwrite (hist_id, 'swdown',   itau_sechiba, dswdown, iim*jjm, kindex)
534          CALL histwrite (hist_id, 'alb_vis',  itau_sechiba, albedo(:,:,1), iim*jjm, kindex)
535          CALL histwrite (hist_id, 'alb_nir',  itau_sechiba, albedo(:,:,2), iim*jjm, kindex)
536          CALL histwrite (hist_id, 'tair',     itau_sechiba, temp_air, iim*jjm, kindex)
537          CALL histwrite (hist_id, 'qair',     itau_sechiba, qair, iim*jjm, kindex)
538          ! Ajout Nathalie - Juin 2006 - on conserve q2m/t2m
539          CALL histwrite (hist_id, 'q2m',     itau_sechiba, qair, iim*jjm, kindex)
540          CALL histwrite (hist_id, 't2m',     itau_sechiba, temp_air, iim*jjm, kindex)
541          IF ( hist2_id > 0 ) THEN
542             CALL histwrite (hist2_id, 'evap',     itau_sechiba, zvevapp, kjpindex, kindex)
543             CALL histwrite (hist2_id, 'coastalflow',itau_sechiba, dcoastal, kjpindex, kindex)
544             CALL histwrite (hist2_id, 'riverflow',itau_sechiba, driver, kjpindex, kindex)
545             !
546             CALL histwrite (hist2_id, 'temp_sol', itau_sechiba, temp_sol_NEW, iim*jjm, kindex)
547             CALL histwrite (hist2_id, 'tsol_max', itau_sechiba, temp_sol_NEW, iim*jjm, kindex)
548             CALL histwrite (hist2_id, 'tsol_min', itau_sechiba, temp_sol_NEW, iim*jjm, kindex)
549             CALL histwrite (hist2_id, 'fluxsens', itau_sechiba, fluxsens, iim*jjm, kindex)
550             CALL histwrite (hist2_id, 'fluxlat',  itau_sechiba, fluxlat, iim*jjm, kindex)
551             CALL histwrite (hist2_id, 'swnet',    itau_sechiba, dswnet, iim*jjm, kindex)
552             CALL histwrite (hist2_id, 'swdown',   itau_sechiba, dswdown, iim*jjm, kindex)
553             CALL histwrite (hist2_id, 'alb_vis',  itau_sechiba, albedo(:,:,1), iim*jjm, kindex)
554             CALL histwrite (hist2_id, 'alb_nir',  itau_sechiba, albedo(:,:,2), iim*jjm, kindex)
555             CALL histwrite (hist2_id, 'tair',     itau_sechiba, temp_air, iim*jjm, kindex)
556             CALL histwrite (hist2_id, 'qair',     itau_sechiba, qair, iim*jjm, kindex)
557             CALL histwrite (hist2_id, 'q2m',     itau_sechiba, qair, iim*jjm, kindex)
558             CALL histwrite (hist2_id, 't2m',     itau_sechiba, temp_air, iim*jjm, kindex)
559          ENDIF
560       ELSE
561          CALL histwrite (hist_id, 'Evap', itau_sechiba, zvevapp, kjpindex, kindex)
562          CALL histwrite (hist_id, 'SWnet',    itau_sechiba, dswnet, iim*jjm, kindex)
563          CALL histwrite (hist_id, 'Qh', itau_sechiba, fluxsens, iim*jjm, kindex)
564          CALL histwrite (hist_id, 'Qle',  itau_sechiba, fluxlat, iim*jjm, kindex)
565          CALL histwrite (hist_id, 'AvgSurfT', itau_sechiba, temp_sol_NEW, iim*jjm, kindex)
566          CALL histwrite (hist_id, 'RadT', itau_sechiba, temp_sol_NEW, iim*jjm, kindex)
567          IF ( hist2_id > 0 ) THEN
568             CALL histwrite (hist2_id, 'Evap', itau_sechiba, zvevapp, kjpindex, kindex)
569             CALL histwrite (hist2_id, 'SWnet',    itau_sechiba, dswnet, iim*jjm, kindex)
570             CALL histwrite (hist2_id, 'Qh', itau_sechiba, fluxsens, iim*jjm, kindex)
571             CALL histwrite (hist2_id, 'Qle',  itau_sechiba, fluxlat, iim*jjm, kindex)
572             CALL histwrite (hist2_id, 'AvgSurfT', itau_sechiba, temp_sol_NEW, iim*jjm, kindex)
573             CALL histwrite (hist2_id, 'RadT', itau_sechiba, temp_sol_NEW, iim*jjm, kindex)
574          ENDIF
575       ENDIF
576       !
577       IF (dw .EQ. xrdt) THEN
578          CALL histsync(hist_id)
579       ENDIF
580       !
581    ENDIF
582    !
583    ! 6. Transform the water fluxes into Kg/m^2s and m^3/s
584    !
585    DO ik=1, kjpindex
586   
587       j = ((kindex(ik)-1)/iim) + 1
588       i = (kindex(ik) - (j-1)*iim)
589
590       vevapp(i,j) = vevapp(i,j)/xrdt
591       coastalflow(i,j) = coastalflow(i,j)/xrdt
592       riverflow(i,j) = riverflow(i,j)/xrdt
593
594    ENDDO
595    !
596    IF ( lrestart_write .AND. ok_watchout .AND. is_root_prc ) THEN
597       CALL watchout_close()
598    ENDIF
599    !
600    IF(l_first_intersurf .AND. is_root_prc) CALL getin_dump
601    l_first_intersurf = .FALSE.
602    !
603    IF (long_print) WRITE (numout,*) ' intersurf_main done '
604    !
605    CALL ipslnlf(new_number=old_fileout)
606    !
607  END SUBROUTINE intersurf_main_2d
608!
609  SUBROUTINE intersurf_main_1d (kjit, iim, jjm, kjpindex, kindex, xrdt, &
610     & lrestart_read, lrestart_write, lon, lat, zcontfrac, zneighbours, zresolution, date0, &
611! First level conditions
612     & zlev,  u, v, qair, temp_air, epot_air, ccanopy, &
613! Variables for the implicit coupling
614     & cdrag, petAcoef, peqAcoef, petBcoef, peqBcoef, &
615! Rain, snow, radiation and surface pressure
616     & precip_rain, precip_snow, lwdown, swnet, swdown, pb, &
617! Output : Fluxes
618     & vevapp, fluxsens, fluxlat, coastalflow, riverflow, &
619! Surface temperatures and surface properties
620     & tsol_rad, temp_sol_new, qsurf, albedo, emis, z0) 
621   
622    ! routines called : sechiba_main
623    !
624    IMPLICIT NONE
625    !   
626    ! interface description for dummy arguments
627    ! input scalar
628    INTEGER(i_std),INTENT (in)                            :: kjit          !! Time step number
629    INTEGER(i_std),INTENT (in)                            :: iim, jjm      !! Dimension of input fields
630    INTEGER(i_std),INTENT (in)                            :: kjpindex      !! Number of continental points
631    REAL(r_std),INTENT (in)                               :: xrdt          !! Time step in seconds
632    LOGICAL, INTENT (in)                                 :: lrestart_read !! Logical for _restart_ file to read
633    LOGICAL, INTENT (in)                                 :: lrestart_write!! Logical for _restart_ file to write'
634    REAL(r_std), INTENT (in)                              :: date0         !! Date at which kjit = 0
635    ! input fields
636    INTEGER(i_std),DIMENSION (kjpindex), INTENT (in)      :: kindex        !! Index for continental points
637    REAL(r_std),DIMENSION (iim*jjm), INTENT(in)             :: u             !! Lowest level wind speed
638    REAL(r_std),DIMENSION (iim*jjm), INTENT(in)             :: v             !! Lowest level wind speed
639    REAL(r_std),DIMENSION (iim*jjm), INTENT(in)             :: zlev          !! Height of first layer
640    REAL(r_std),DIMENSION (iim*jjm), INTENT(in)             :: qair          !! Lowest level specific humidity
641    REAL(r_std),DIMENSION (iim*jjm), INTENT(in)             :: precip_rain   !! Rain precipitation
642    REAL(r_std),DIMENSION (iim*jjm), INTENT(in)             :: precip_snow   !! Snow precipitation
643    REAL(r_std),DIMENSION (iim*jjm), INTENT(in)             :: lwdown        !! Down-welling long-wave flux
644    REAL(r_std),DIMENSION (iim*jjm), INTENT(in)             :: swnet         !! Net surface short-wave flux
645    REAL(r_std),DIMENSION (iim*jjm), INTENT(in)             :: swdown        !! Downwelling surface short-wave flux
646    REAL(r_std),DIMENSION (iim*jjm), INTENT(in)             :: temp_air      !! Air temperature in Kelvin
647    REAL(r_std),DIMENSION (iim*jjm), INTENT(in)             :: epot_air      !! Air potential energy
648    REAL(r_std),DIMENSION (iim*jjm), INTENT(in)             :: ccanopy       !! CO2 concentration in the canopy
649    REAL(r_std),DIMENSION (iim*jjm), INTENT(in)             :: petAcoef      !! Coeficients A from the PBL resolution
650    REAL(r_std),DIMENSION (iim*jjm), INTENT(in)             :: peqAcoef      !! One for T and another for q
651    REAL(r_std),DIMENSION (iim*jjm), INTENT(in)             :: petBcoef      !! Coeficients B from the PBL resolution
652    REAL(r_std),DIMENSION (iim*jjm), INTENT(in)             :: peqBcoef      !! One for T and another for q
653    REAL(r_std),DIMENSION (iim*jjm), INTENT(inout)          :: cdrag         !! Cdrag
654    REAL(r_std),DIMENSION (iim*jjm), INTENT(in)             :: pb            !! Lowest level pressure
655    REAL(r_std),DIMENSION (iim*jjm), INTENT(in)             :: lon, lat      !! Geographical coordinates
656    REAL(r_std),DIMENSION (iim*jjm), INTENT(in)             :: zcontfrac     !! Fraction of continent
657    INTEGER, DIMENSION (iim*jjm,8), INTENT(in)             :: zneighbours   !! land neighbours
658    REAL(r_std),DIMENSION (iim*jjm,2), INTENT(in)           :: zresolution   !! resolution in x and y dimensions
659    ! output fields
660    REAL(r_std),DIMENSION (iim*jjm), INTENT(out)            :: z0            !! Surface roughness
661    REAL(r_std),DIMENSION (iim*jjm), INTENT(out)            :: coastalflow   !! Diffuse flow of water into the ocean (m^3/dt)
662    REAL(r_std),DIMENSION (iim*jjm), INTENT(out)            :: riverflow     !! Largest rivers flowing into the ocean (m^3/dt)
663    REAL(r_std),DIMENSION (iim*jjm), INTENT(out)            :: tsol_rad      !! Radiative surface temperature
664    REAL(r_std),DIMENSION (iim*jjm), INTENT(out)            :: vevapp        !! Total of evaporation
665    REAL(r_std),DIMENSION (iim*jjm), INTENT(out)            :: temp_sol_new  !! New soil temperature
666    REAL(r_std),DIMENSION (iim*jjm), INTENT(out)            :: qsurf         !! Surface specific humidity
667    REAL(r_std),DIMENSION (iim*jjm,2), INTENT(out)          :: albedo        !! Albedo
668    REAL(r_std),DIMENSION (iim*jjm), INTENT(out)            :: fluxsens      !! Sensible chaleur flux
669    REAL(r_std),DIMENSION (iim*jjm), INTENT(out)            :: fluxlat       !! Latent chaleur flux
670    REAL(r_std),DIMENSION (iim*jjm), INTENT(out)            :: emis          !! Emissivity
671    ! LOCAL declaration
672    ! work arrays to scatter and/or gather information just before/after sechiba_main call's
673    ! and to keep output value for next call
674    REAL(r_std),DIMENSION (kjpindex)                      :: zu            !! Work array to keep u
675    REAL(r_std),DIMENSION (kjpindex)                      :: zv            !! Work array to keep v
676    REAL(r_std),DIMENSION (kjpindex)                      :: zzlev         !! Work array to keep zlev
677    REAL(r_std),DIMENSION (kjpindex)                      :: zqair         !! Work array to keep qair
678    REAL(r_std),DIMENSION (kjpindex)                      :: zprecip_rain  !! Work array to keep precip_rain
679    REAL(r_std),DIMENSION (kjpindex)                      :: zprecip_snow  !! Work array to keep precip_snow
680    REAL(r_std),DIMENSION (kjpindex)                      :: zlwdown       !! Work array to keep lwdown
681    REAL(r_std),DIMENSION (kjpindex)                      :: zswnet        !! Work array to keep swnet
682    REAL(r_std),DIMENSION (kjpindex)                      :: zswdown       !! Work array to keep swdown
683    REAL(r_std),DIMENSION (kjpindex)                      :: ztemp_air     !! Work array to keep temp_air
684    REAL(r_std),DIMENSION (kjpindex)                      :: zepot_air     !! Work array to keep epot_air
685    REAL(r_std),DIMENSION (kjpindex)                      :: zccanopy      !! Work array to keep ccanopy
686    REAL(r_std),DIMENSION (kjpindex)                      :: zpetAcoef     !! Work array to keep petAcoef
687    REAL(r_std),DIMENSION (kjpindex)                      :: zpeqAcoef     !! Work array to keep peqAcoef
688    REAL(r_std),DIMENSION (kjpindex)                      :: zpetBcoef     !! Work array to keep petBcoef
689    REAL(r_std),DIMENSION (kjpindex)                      :: zpeqBcoef     !! Work array to keep peqVcoef
690    REAL(r_std),DIMENSION (kjpindex)                      :: zcdrag        !! Work array to keep cdrag
691    REAL(r_std),DIMENSION (kjpindex)                      :: zpb           !! Work array to keep pb
692    REAL(r_std),DIMENSION (kjpindex)                      :: zz0           !! Work array to keep z0
693    REAL(r_std),DIMENSION (kjpindex)                      :: zcoastal      !! Work array to keep coastal flow
694    REAL(r_std),DIMENSION (kjpindex)                      :: zriver        !! Work array to keep river out flow
695    REAL(r_std),DIMENSION (kjpindex)                      :: dcoastal      !! Work array to keep coastal flow
696    REAL(r_std),DIMENSION (kjpindex)                      :: driver        !! Work array to keep river out flow
697    REAL(r_std),DIMENSION (kjpindex)                      :: ztsol_rad     !! Work array to keep tsol_rad
698    REAL(r_std),DIMENSION (kjpindex)                      :: zvevapp       !! Work array to keep vevapp
699    REAL(r_std),DIMENSION (kjpindex)                      :: ztemp_sol_new !! Work array to keep temp_sol_new
700    REAL(r_std),DIMENSION (kjpindex)                      :: zqsurf        !! Work array to keep qsurf
701    REAL(r_std),DIMENSION (kjpindex,2)                    :: zalbedo       !! Work array to keep albedo
702    REAL(r_std),DIMENSION (kjpindex)                      :: zfluxsens     !! Work array to keep fluxsens
703    REAL(r_std),DIMENSION (kjpindex)                      :: zfluxlat      !! Work array to keep fluxlat
704    REAL(r_std),DIMENSION (kjpindex)                      :: zemis         !! Work array to keep emis
705    !
706    ! Local but with input shape
707    !
708    REAL(r_std),DIMENSION (iim*jjm)                       :: dswnet         !! Net surface short-wave flux
709    REAL(r_std),DIMENSION (iim*jjm)                       :: dswdown        !! Incident surface short-wave flux
710    !
711    INTEGER(i_std)                                        :: i, j, ik
712    INTEGER(i_std)                                        :: itau_sechiba
713    REAL(r_std), ALLOCATABLE, DIMENSION(:,:)              :: tmp_lon, tmp_lat, tmp_lev
714    REAL(r_std)                                           :: zlev_mean
715    LOGICAL                                               :: do_watch      !! if it's time, write watchout
716    INTEGER                                               :: old_fileout   !! old Logical Int for std IO output
717    LOGICAL :: check = .FALSE.
718    !
719    CALL ipslnlf(new_number=numout,old_number=old_fileout)
720    !
721    IF (l_first_intersurf) THEN
722       !
723       CALL intsurf_time( kjit, date0, xrdt )
724       !
725       IF ( check ) WRITE(numout,*) 'Initialisation of intersurf_main_1d'
726       !
727       OFF_LINE_MODE = .TRUE. 
728       !
729       !  Create the internal coordinate table
730       !
731       IF ( (.NOT.ALLOCATED(tmp_lon))) THEN
732          ALLOCATE(tmp_lon(iim,jjm))
733       ENDIF
734       IF ( (.NOT.ALLOCATED(tmp_lat))) THEN
735          ALLOCATE(tmp_lat(iim,jjm))
736       ENDIF
737       IF ( (.NOT.ALLOCATED(tmp_lev))) THEN
738          ALLOCATE(tmp_lev(iim,jjm))
739       ENDIF
740       !
741       DO i=1,iim
742          DO j=1,jjm
743             ik = (j-1)*iim + i
744             tmp_lon(i,j) = lon(ik)
745             tmp_lat(i,j) = lat(ik)
746             tmp_lev(i,j) = zlev(kindex(ik)) 
747          ENDDO
748       ENDDO
749       !
750       lalo(:,1) = lat(:)
751       lalo(:,2) = lon(:)
752       !
753       !- Store the fraction of the continents only once so that the user
754       !- does not change them afterwards.
755       !
756       DO ik=1,kjpindex
757
758          contfrac(ik) = zcontfrac(kindex(ik))
759
760       ENDDO
761       contfrac_g(:) = contfrac(:)
762       lalo_g(:,:) = lalo(:,:)
763       lon_g(:,:) = tmp_lon(:,:)
764       lat_g(:,:) = tmp_lat(:,:)
765       zlev_g(:,:) = tmp_lev(:,:)
766       !
767       !  Configuration of SSL specific parameters
768       !
769       CALL intsurf_config(control_flags, xrdt)
770       !
771       CALL intsurf_restart(kjit, iim, jjm, tmp_lon, tmp_lat, date0, xrdt, control_flags, rest_id, rest_id_stom, itau_offset)
772       itau_sechiba = kjit + itau_offset
773       !
774       CALL intsurf_history(iim, jjm, tmp_lon, tmp_lat, itau_sechiba, date0_shifted, xrdt, control_flags, hist_id, &
775            & hist2_id, hist_id_stom, hist_id_stom_IPCC)
776       !
777       IF ( ok_watchout ) THEN
778          zlev_mean = 0.
779          DO ik=1, kjpindex
780
781             zlev_mean = zlev_mean + zlev(ik)
782          ENDDO
783          ! Divide by one
784          zlev_mean = zlev_mean / REAL(kjpindex,r_std)
785
786          last_action_watch = itau_sechiba
787          last_check_watch  = last_action_watch
788
789          CALL watchout_init(iim, jjm, kjpindex, kjpindex, &
790               & date0_shifted, last_action_watch, dt_watch, index_g, lon_g, lat_g, zlev_mean)
791       ENDIF
792       !
793       IF ( check ) WRITE(numout,*) 'End of Initialisation of intersurf'
794       !
795    ENDIF
796    !
797    !  Shift the time step to phase the two models
798    !
799    itau_sechiba = kjit + itau_offset
800    !
801    CALL intsurf_time( itau_sechiba, date0_shifted, xrdt )
802    !
803    ! 1. gather input fields from kindex array
804    !
805    DO ik=1, kjpindex
806       
807       zu(ik)           = u(kindex(ik))
808       zv(ik)           = v(kindex(ik))
809       zzlev(ik)        = zlev(kindex(ik))
810       zqair(ik)        = qair(kindex(ik))
811       zprecip_rain(ik) = precip_rain(kindex(ik))*xrdt
812       zprecip_snow(ik) = precip_snow(kindex(ik))*xrdt
813       zlwdown(ik)      = lwdown(kindex(ik))
814       zswnet(ik)       = swnet(kindex(ik))
815       zswdown(ik)      = swdown(kindex(ik))
816       ztemp_air(ik)    = temp_air(kindex(ik))
817       zepot_air(ik)    = epot_air(kindex(ik))
818       zccanopy(ik)     = ccanopy(kindex(ik))
819       zpetAcoef(ik)    = petAcoef(kindex(ik))
820       zpeqAcoef(ik)    = peqAcoef(kindex(ik))
821       zpetBcoef(ik)    = petBcoef(kindex(ik))
822       zpeqBcoef(ik)    = peqBcoef(kindex(ik))
823       zcdrag(ik)       = cdrag(kindex(ik))
824       zpb(ik)          = pb(kindex(ik))
825       
826    ENDDO
827    !
828    ! 2. save the grid
829    !
830    IF ( check ) WRITE(numout,*) 'Save the grid'
831    !
832    IF (l_first_intersurf) THEN
833       !
834       CALL histwrite(hist_id, 'LandPoints',  itau_sechiba+1, (/ REAL(kindex) /), kjpindex, kindex)
835       CALL histwrite(hist_id, 'Areas',  itau_sechiba+1, area, kjpindex, kindex)
836       IF ( control_flags%ok_stomate ) THEN
837          CALL histwrite(hist_id_stom, 'Areas',  itau_sechiba+1, area, kjpindex, kindex)
838          IF ( hist_id_stom_IPCC > 0 ) THEN
839             CALL histwrite(hist_id_stom_IPCC, 'Areas',  itau_sechiba+1, area, kjpindex, kindex)
840          ENDIF
841       ENDIF
842       CALL histwrite(hist_id, 'Contfrac',  itau_sechiba+1, contfrac, kjpindex, kindex)
843       CALL histsync(hist_id)
844       !
845       IF ( hist2_id > 0 ) THEN
846          CALL histwrite(hist2_id, 'LandPoints',  itau_sechiba+1, (/ REAL(kindex) /), kjpindex, kindex)
847          CALL histwrite(hist2_id, 'Areas',  itau_sechiba+1, area, kjpindex, kindex)
848          CALL histwrite(hist2_id, 'Contfrac',  itau_sechiba+1, contfrac, kjpindex, kindex)
849          CALL histsync(hist2_id)
850       ENDIF
851       !
852    ENDIF
853    !
854    ! 3. call sechiba
855    !
856    IF ( check ) WRITE(numout,*) 'Calling sechiba'
857    !
858    CALL sechiba_main (itau_sechiba, iim*jjm, kjpindex, kindex, xrdt, date0_shifted, &
859       & lrestart_read, lrestart_write, control_flags, &
860       & lalo, contfrac, neighbours, resolution, &
861! First level conditions
862! Ajout Nathalie - Juin 2006 - passage q2m/t2m pour calcul rveget
863!       & zzlev, zu, zv, zqair, ztemp_air, zepot_air, zccanopy, &
864       & zzlev, zu, zv, zqair, zqair, ztemp_air, ztemp_air, zepot_air, zccanopy, &
865! Variables for the implicit coupling
866       & zcdrag, zpetAcoef, zpeqAcoef, zpetBcoef, zpeqBcoef, &
867! Rain, snow, radiation and surface pressure
868       & zprecip_rain ,zprecip_snow,  zlwdown, zswnet, zswdown, zpb, &
869! Output : Fluxes
870       & zvevapp, zfluxsens, zfluxlat, zcoastal, zriver, &
871! Surface temperatures and surface properties
872       & ztsol_rad, ztemp_sol_new, zqsurf, zalbedo, zemis, zz0, &
873! File ids
874       & rest_id, hist_id, hist2_id, rest_id_stom, hist_id_stom, hist_id_stom_IPCC ) 
875   
876    !
877    IF ( check ) WRITE(numout,*) 'out of SECHIBA'
878    !
879    ! 4. save watchout
880    !
881    IF ( ok_watchout .AND. .NOT. l_first_intersurf ) THEN
882       ! Accumulate last time step
883       sum_zlev(:) = sum_zlev(:) + zzlev(:)
884       sum_u(:) = sum_u(:) + zu(:)
885       sum_v(:) = sum_v(:) + zv(:)
886       sum_qair(:) = sum_qair(:) + zqair(:) 
887       sum_temp_air(:) = sum_temp_air(:) + ztemp_air(:)
888       sum_epot_air(:) = sum_epot_air(:) + zepot_air(:)
889       sum_ccanopy(:) = sum_ccanopy(:) + zccanopy(:)
890       sum_cdrag(:) = sum_cdrag(:) + zcdrag(:)
891       sum_petAcoef(:) = sum_petAcoef(:) + zpetAcoef(:)
892       sum_peqAcoef(:) = sum_peqAcoef(:) + zpeqAcoef(:)
893       sum_petBcoef(:) = sum_petBcoef(:) + zpetBcoef(:)
894       sum_peqBcoef(:) = sum_peqBcoef(:) + zpeqBcoef(:)
895       sum_rain(:) = sum_rain(:) + zprecip_rain(:)
896       sum_snow(:) = sum_snow(:) + zprecip_snow(:)
897       sum_lwdown(:) = sum_lwdown(:) + zlwdown(:)
898       sum_pb(:) = sum_pb(:) + zpb(:)
899       
900!!$       IF ( dt_watch > 3600 ) THEN
901!!$          julian_watch = date0_shifted+((itau_sechiba-0.5)/dt_split_watch)*dt_watch/one_day
902!!$          CALL solarang (julian_watch, julian0, iim, jjm, lon, lat, sinang)
903!!$          WHERE ( sinang(:,:) .LT. EPSILON(1.) )
904!!$             isinang(:,:) = isinang(:,:) - 1
905!!$          ENDWHERE
906!!$          mean_sinang(:,:) = mean_sinang(:,:)+sinang(:,:)
907!!$          !
908!!$          DO ik=1,kjpindex         
909!!$             j = ((kindex(ik)-1)/iim) + 1
910!!$             i = (kindex(ik) - (j-1)*iim)
911!!$             
912!!$             sum_swnet(ik) = sum_swnet(ik) + sinang(i,j)*zswnet(ik)
913!!$             sum_swdown(ik) = sum_swdown(ik) + sinang(i,j)*zswdown(ik)
914!!$          ENDDO
915!!$       ELSE
916          sum_swnet(:) = sum_swnet(:) + zswnet(:)
917          sum_swdown(:) = sum_swdown(:) + zswdown(:)
918!!$       ENDIF
919         
920       do_watch = .FALSE.
921       call isittime &
922            &  (itau_sechiba,date0_shifted,xrdt,dt_watch,&
923            &   last_action_watch,last_check_watch,do_watch)
924       last_check_watch = itau_sechiba
925       IF (do_watch) THEN
926          !
927          IF ( check ) WRITE(numout,*) 'save watchout'
928          !
929          IF (long_print) THEN
930             WRITE(numout,*) "intersurf : write watchout for date ",date0,date0_shifted,itau_sechiba,&
931                  & last_action_watch, last_check_watch
932          ENDIF
933          last_action_watch = itau_sechiba
934
935          sum_zlev(:) = sum_zlev(:) / dt_split_watch
936          sum_u(:) = sum_u(:) / dt_split_watch
937          sum_v(:) = sum_v(:) / dt_split_watch
938          sum_qair(:) = sum_qair(:) / dt_split_watch
939          sum_temp_air(:) = sum_temp_air(:) / dt_split_watch
940          sum_epot_air(:) = sum_epot_air(:) / dt_split_watch
941          sum_ccanopy(:) = sum_ccanopy(:) / dt_split_watch
942          sum_cdrag(:) = sum_cdrag(:) / dt_split_watch
943          sum_petAcoef(:) = sum_petAcoef(:) / dt_split_watch
944          sum_peqAcoef(:) = sum_peqAcoef(:) / dt_split_watch
945          sum_petBcoef(:) = sum_petBcoef(:) / dt_split_watch
946          sum_peqBcoef(:) = sum_peqBcoef(:) / dt_split_watch
947          sum_rain(:) = sum_rain(:) / dt_split_watch
948          sum_snow(:) = sum_snow(:) / dt_split_watch
949          sum_lwdown(:) = sum_lwdown(:) / dt_split_watch
950          sum_pb(:) = sum_pb(:) / dt_split_watch
951
952!!$          IF ( dt_watch > 3600 ) THEN
953!!$             WHERE ( isinang(:,:) .GT. 0 )
954!!$                mean_sinang(:,:) = mean_sinang(:,:) / isinang(:,:)
955!!$             ENDWHERE
956!!$             !
957!!$             DO ik=1,kjpindex         
958!!$                j = ((kindex(ik)-1)/iim) + 1
959!!$                i = (kindex(ik) - (j-1)*iim)
960!!$                IF (mean_sinang(i,j) > zero) THEN
961!!$                   sum_swdown(ik) = sum_swdown(ik)/mean_sinang(i,j)
962!!$                   sum_swnet(ik) =  sum_swnet(ik)/mean_sinang(i,j)
963!!$                ELSE
964!!$                   sum_swdown(ik) = zero
965!!$                   sum_swnet(ik) =  zero
966!!$                ENDIF
967!!$             ENDDO
968!!$          ELSE
969             sum_swnet(:) = sum_swnet(:) / dt_split_watch
970             sum_swdown(:) = sum_swdown(:) / dt_split_watch
971!!$          ENDIF
972
973          CALL watchout_write_p(kjpindex, itau_sechiba, xrdt, sum_zlev, sum_swdown, sum_rain, &
974               &   sum_snow, sum_lwdown, sum_pb, sum_temp_air, sum_epot_air, sum_qair, &
975               &   sum_u, sum_v, sum_swnet, sum_petAcoef, sum_peqAcoef, sum_petBcoef, sum_peqBcoef, &
976               &   sum_cdrag, sum_ccanopy )
977       ENDIF
978    ENDIF
979    !
980    ! 5. scatter output fields
981    !
982    !
983    z0(:)           = undef_sechiba
984    coastalflow(:)  = undef_sechiba
985    riverflow(:)    = undef_sechiba
986    tsol_rad(:)     = undef_sechiba
987    vevapp(:)       = undef_sechiba
988    temp_sol_new(:) = undef_sechiba 
989    qsurf(:)        = undef_sechiba 
990    albedo(:,:)     = undef_sechiba
991    fluxsens(:)     = undef_sechiba
992    fluxlat(:)      = undef_sechiba
993    emis(:)         = undef_sechiba 
994    cdrag(:)        = undef_sechiba 
995    dswnet(:)       = undef_sechiba 
996    dswdown(:)      = undef_sechiba 
997    !
998    DO ik=1, kjpindex
999       
1000       z0(kindex(ik))           = zz0(ik)
1001       coastalflow(kindex(ik))  = zcoastal(ik)/1000.
1002       riverflow(kindex(ik))    = zriver(ik)/1000.
1003       tsol_rad(kindex(ik))     = ztsol_rad(ik)
1004       vevapp(kindex(ik))       = zvevapp(ik)
1005       temp_sol_new(kindex(ik)) = ztemp_sol_new(ik)
1006       qsurf(kindex(ik))        = zqsurf(ik)
1007       albedo(kindex(ik),1)     = zalbedo(ik,1)
1008       albedo(kindex(ik),2)     = zalbedo(ik,2)
1009       fluxsens(kindex(ik))     = zfluxsens(ik)
1010       fluxlat(kindex(ik))      = zfluxlat(ik)
1011       emis(kindex(ik))         = zemis(ik)
1012       cdrag(kindex(ik))        = zcdrag(ik)
1013       dswnet(kindex(ik))       = zswnet(ik)
1014       dswdown(kindex(ik))      = zswdown(ik)
1015
1016    ENDDO
1017    !
1018    ! Modified fields for variables scattered during the writing
1019    !
1020    dcoastal(:) = (zcoastal(:))/1000.
1021    driver(:)   = (zriver(:))/1000.
1022    !
1023    IF ( .NOT. l_first_intersurf) THEN
1024       !
1025       IF ( .NOT. almaoutput ) THEN
1026          !
1027          !  scattered during the writing
1028          !
1029          CALL histwrite (hist_id, 'evap',     itau_sechiba, zvevapp, kjpindex, kindex)
1030          CALL histwrite (hist_id, 'coastalflow',itau_sechiba, dcoastal, kjpindex, kindex)
1031          CALL histwrite (hist_id, 'riverflow',itau_sechiba, driver, kjpindex, kindex)
1032          !
1033          CALL histwrite (hist_id, 'temp_sol', itau_sechiba, temp_sol_NEW, iim*jjm, kindex)
1034          CALL histwrite (hist_id, 'tsol_max', itau_sechiba, temp_sol_NEW, iim*jjm, kindex)
1035          CALL histwrite (hist_id, 'tsol_min', itau_sechiba, temp_sol_NEW, iim*jjm, kindex)
1036          CALL histwrite (hist_id, 'fluxsens', itau_sechiba, fluxsens, iim*jjm, kindex)
1037          CALL histwrite (hist_id, 'fluxlat',  itau_sechiba, fluxlat, iim*jjm, kindex)
1038          CALL histwrite (hist_id, 'swnet',    itau_sechiba, dswnet, iim*jjm, kindex)
1039          CALL histwrite (hist_id, 'swdown',   itau_sechiba, dswdown, iim*jjm, kindex)
1040          CALL histwrite (hist_id, 'alb_vis',  itau_sechiba, albedo(:,1), iim*jjm, kindex)
1041          CALL histwrite (hist_id, 'alb_nir',  itau_sechiba, albedo(:,2), iim*jjm, kindex)
1042          CALL histwrite (hist_id, 'tair',     itau_sechiba, temp_air, iim*jjm, kindex)
1043          CALL histwrite (hist_id, 'qair',     itau_sechiba, qair, iim*jjm, kindex)
1044          ! Ajouts Nathalie - Juin 2006 - sauvegarde de t2m et q2m
1045          CALL histwrite (hist_id, 'q2m',     itau_sechiba, qair, iim*jjm, kindex)
1046          CALL histwrite (hist_id, 't2m',     itau_sechiba, temp_air, iim*jjm, kindex)
1047          IF ( hist2_id > 0 ) THEN
1048             CALL histwrite (hist2_id, 'evap',     itau_sechiba, zvevapp, kjpindex, kindex)
1049             CALL histwrite (hist2_id, 'coastalflow',itau_sechiba, dcoastal, kjpindex, kindex)
1050             CALL histwrite (hist2_id, 'riverflow',itau_sechiba, driver, kjpindex, kindex)
1051             !
1052             CALL histwrite (hist2_id, 'temp_sol', itau_sechiba, temp_sol_NEW, iim*jjm, kindex)
1053             CALL histwrite (hist2_id, 'tsol_max', itau_sechiba, temp_sol_NEW, iim*jjm, kindex)
1054             CALL histwrite (hist2_id, 'tsol_min', itau_sechiba, temp_sol_NEW, iim*jjm, kindex)
1055             CALL histwrite (hist2_id, 'fluxsens', itau_sechiba, fluxsens, iim*jjm, kindex)
1056             CALL histwrite (hist2_id, 'fluxlat',  itau_sechiba, fluxlat, iim*jjm, kindex)
1057             CALL histwrite (hist2_id, 'swnet',    itau_sechiba, dswnet, iim*jjm, kindex)
1058             CALL histwrite (hist2_id, 'swdown',   itau_sechiba, dswdown, iim*jjm, kindex)
1059             CALL histwrite (hist2_id, 'alb_vis',  itau_sechiba, albedo(:,1), iim*jjm, kindex)
1060             CALL histwrite (hist2_id, 'alb_nir',  itau_sechiba, albedo(:,2), iim*jjm, kindex)
1061             CALL histwrite (hist2_id, 'tair',     itau_sechiba, temp_air, iim*jjm, kindex)
1062             CALL histwrite (hist2_id, 'qair',     itau_sechiba, qair, iim*jjm, kindex)
1063             CALL histwrite (hist2_id, 'q2m',     itau_sechiba, qair, iim*jjm, kindex)
1064             CALL histwrite (hist2_id, 't2m',     itau_sechiba, temp_air, iim*jjm, kindex)
1065          ENDIF
1066       ELSE
1067          CALL histwrite (hist_id, 'Evap', itau_sechiba, zvevapp, kjpindex, kindex)
1068          CALL histwrite (hist_id, 'SWnet',    itau_sechiba, dswnet, iim*jjm, kindex)
1069          CALL histwrite (hist_id, 'Qh', itau_sechiba, fluxsens, iim*jjm, kindex)
1070          CALL histwrite (hist_id, 'Qle',  itau_sechiba, fluxlat, iim*jjm, kindex)
1071          CALL histwrite (hist_id, 'AvgSurfT', itau_sechiba, temp_sol_NEW, iim*jjm, kindex)
1072          CALL histwrite (hist_id, 'RadT', itau_sechiba, temp_sol_NEW, iim*jjm, kindex)
1073          IF ( hist2_id > 0 ) THEN
1074             CALL histwrite (hist2_id, 'Evap', itau_sechiba, zvevapp, kjpindex, kindex)
1075             CALL histwrite (hist2_id, 'SWnet',    itau_sechiba, dswnet, iim*jjm, kindex)
1076             CALL histwrite (hist2_id, 'Qh', itau_sechiba, fluxsens, iim*jjm, kindex)
1077             CALL histwrite (hist2_id, 'Qle',  itau_sechiba, fluxlat, iim*jjm, kindex)
1078             CALL histwrite (hist2_id, 'AvgSurfT', itau_sechiba, temp_sol_NEW, iim*jjm, kindex)
1079             CALL histwrite (hist2_id, 'RadT', itau_sechiba, temp_sol_NEW, iim*jjm, kindex)
1080          ENDIF
1081       ENDIF
1082       !
1083       IF (dw .EQ. xrdt) THEN
1084          CALL histsync(hist_id)
1085       ENDIF
1086       !
1087    ENDIF
1088    !
1089    ! 6. Transform the water fluxes into Kg/m^2s and m^3/s
1090    !
1091    DO ik=1, kjpindex
1092
1093       vevapp(kindex(ik)) = vevapp(kindex(ik))/xrdt
1094       coastalflow(kindex(ik)) = coastalflow(kindex(ik))/xrdt
1095       riverflow(kindex(ik)) = riverflow(kindex(ik))/xrdt
1096
1097    ENDDO
1098    !
1099    IF ( lrestart_write .AND. ok_watchout ) THEN
1100       CALL watchout_close()
1101    ENDIF
1102    !
1103    IF(l_first_intersurf .AND. is_root_prc) CALL getin_dump
1104    l_first_intersurf = .FALSE.
1105    !
1106    IF (long_print) WRITE (numout,*) ' intersurf_main done '
1107    !
1108    CALL ipslnlf(new_number=old_fileout)
1109    !   
1110  END SUBROUTINE intersurf_main_1d
1111!
1112!-------------------------------------------------------------------------------------
1113!
1114#ifdef CPP_PARA
1115  SUBROUTINE intersurf_gathered (kjit, iim_glo, jjm_glo, offset, kjpindex, kindex, communicator, xrdt, &
1116     & lrestart_read, lrestart_write, latlon, zcontfrac, zneighbours, zresolution, date0, &
1117! First level conditions
1118     & zlev,  u, v, qair, temp_air, epot_air, ccanopy, &
1119! Variables for the implicit coupling
1120     & cdrag, petAcoef, peqAcoef, petBcoef, peqBcoef, &
1121! Rain, snow, radiation and surface pressure
1122     & precip_rain, precip_snow, lwdown, swnet, swdown, pb, &
1123! Output : Fluxes
1124     & vevapp, fluxsens, fluxlat, coastalflow, riverflow, &
1125! Surface temperatures and surface properties
1126     & tsol_rad, temp_sol_new, qsurf, albedo, emis, z0, lon_scat_g, lat_scat_g) 
1127#else
1128  SUBROUTINE intersurf_gathered (kjit, iim_glo, jjm_glo, kjpindex, kindex, xrdt, &
1129     & lrestart_read, lrestart_write, latlon, zcontfrac, zneighbours, zresolution, date0, &
1130! First level conditions
1131     & zlev,  u, v, qair, temp_air, epot_air, ccanopy, &
1132! Variables for the implicit coupling
1133     & cdrag, petAcoef, peqAcoef, petBcoef, peqBcoef, &
1134! Rain, snow, radiation and surface pressure
1135     & precip_rain, precip_snow, lwdown, swnet, swdown, pb, &
1136! Output : Fluxes
1137     & vevapp, fluxsens, fluxlat, coastalflow, riverflow, &
1138! Surface temperatures and surface properties
1139     & tsol_rad, temp_sol_new, qsurf, albedo, emis, z0, lon_scat_g, lat_scat_g) 
1140#endif
1141    ! routines called : sechiba_main
1142    !
1143    IMPLICIT NONE
1144    !   
1145    ! interface description for dummy arguments
1146    ! input scalar
1147    INTEGER(i_std),INTENT (in)                            :: kjit          !! Time step number
1148    INTEGER(i_std),INTENT (in)                            :: iim_glo, jjm_glo  !! Dimension of global fields
1149#ifdef CPP_PARA
1150    INTEGER(i_std),INTENT (in)                            :: offset        !! offset between the first global 2D point
1151                                                                           !! and the first local 2D point.
1152    INTEGER(i_std),INTENT(IN)                             :: communicator  !! Orchidee communicator
1153#endif
1154    INTEGER(i_std),INTENT (in)                            :: kjpindex      !! Number of continental points
1155    REAL(r_std),INTENT (in)                               :: xrdt          !! Time step in seconds
1156    LOGICAL, INTENT (in)                                 :: lrestart_read !! Logical for _restart_ file to read
1157    LOGICAL, INTENT (in)                                 :: lrestart_write!! Logical for _restart_ file to write'
1158    REAL(r_std), INTENT (in)                              :: date0         !! Date at which kjit = 0
1159    ! input fields
1160    INTEGER(i_std),DIMENSION (kjpindex), INTENT (in)      :: kindex        !! Index for continental points
1161    REAL(r_std),DIMENSION (kjpindex), INTENT(in)          :: u             !! Lowest level wind speed
1162    REAL(r_std),DIMENSION (kjpindex), INTENT(in)          :: v             !! Lowest level wind speed
1163    REAL(r_std),DIMENSION (kjpindex), INTENT(in)          :: zlev          !! Height of first layer
1164    REAL(r_std),DIMENSION (kjpindex), INTENT(in)          :: qair          !! Lowest level specific humidity
1165    REAL(r_std),DIMENSION (kjpindex), INTENT(in)          :: precip_rain   !! Rain precipitation
1166    REAL(r_std),DIMENSION (kjpindex), INTENT(in)          :: precip_snow   !! Snow precipitation
1167    REAL(r_std),DIMENSION (kjpindex), INTENT(in)          :: lwdown        !! Down-welling long-wave flux
1168    REAL(r_std),DIMENSION (kjpindex), INTENT(in)          :: swnet         !! Net surface short-wave flux
1169    REAL(r_std),DIMENSION (kjpindex), INTENT(in)          :: swdown        !! Downwelling surface short-wave flux
1170    REAL(r_std),DIMENSION (kjpindex), INTENT(in)          :: temp_air      !! Air temperature in Kelvin
1171    REAL(r_std),DIMENSION (kjpindex), INTENT(in)          :: epot_air      !! Air potential energy
1172    REAL(r_std),DIMENSION (kjpindex), INTENT(in)          :: ccanopy       !! CO2 concentration in the canopy
1173    REAL(r_std),DIMENSION (kjpindex), INTENT(in)          :: petAcoef      !! Coeficients A from the PBL resolution
1174    REAL(r_std),DIMENSION (kjpindex), INTENT(in)          :: peqAcoef      !! One for T and another for q
1175    REAL(r_std),DIMENSION (kjpindex), INTENT(in)          :: petBcoef      !! Coeficients B from the PBL resolution
1176    REAL(r_std),DIMENSION (kjpindex), INTENT(in)          :: peqBcoef      !! One for T and another for q
1177    REAL(r_std),DIMENSION (kjpindex), INTENT(inout)       :: cdrag         !! Cdrag
1178    REAL(r_std),DIMENSION (kjpindex), INTENT(in)          :: pb            !! Lowest level pressure
1179    REAL(r_std),DIMENSION (kjpindex,2), INTENT(in)        :: latlon        !! Geographical coordinates
1180    REAL(r_std),DIMENSION (kjpindex), INTENT(in)          :: zcontfrac     !! Fraction of continent
1181    INTEGER(i_std),DIMENSION (kjpindex,8), INTENT(in)    :: zneighbours   !! neighbours
1182    REAL(r_std),DIMENSION (kjpindex,2), INTENT(in)        :: zresolution   !! size of the grid box
1183    ! output fields
1184    REAL(r_std),DIMENSION (kjpindex), INTENT(out)         :: z0            !! Surface roughness
1185    REAL(r_std),DIMENSION (kjpindex), INTENT(out)         :: coastalflow   !! Diffuse flow of water into the ocean (m^3/dt)
1186    REAL(r_std),DIMENSION (kjpindex), INTENT(out)         :: riverflow     !! Largest rivers flowing into the ocean (m^3/dt)
1187    REAL(r_std),DIMENSION (kjpindex), INTENT(out)         :: tsol_rad      !! Radiative surface temperature
1188    REAL(r_std),DIMENSION (kjpindex), INTENT(out)         :: vevapp        !! Total of evaporation
1189    REAL(r_std),DIMENSION (kjpindex), INTENT(out)         :: temp_sol_new  !! New soil temperature
1190    REAL(r_std),DIMENSION (kjpindex), INTENT(out)         :: qsurf         !! Surface specific humidity
1191    REAL(r_std),DIMENSION (kjpindex,2), INTENT(out)       :: albedo        !! Albedo
1192    REAL(r_std),DIMENSION (kjpindex), INTENT(out)         :: fluxsens      !! Sensible chaleur flux
1193    REAL(r_std),DIMENSION (kjpindex), INTENT(out)         :: fluxlat       !! Latent chaleur flux
1194    REAL(r_std),DIMENSION (kjpindex), INTENT(out)         :: emis          !! Emissivity
1195    ! LOCAL declaration
1196    ! work arrays to scatter and/or gather information just before/after sechiba_main call's
1197    ! and to keep output value for next call
1198    REAL(r_std),DIMENSION (kjpindex)                      :: zccanopy      !! Work array to keep ccanopy
1199    REAL(r_std),DIMENSION (kjpindex)                      :: zprecip_rain  !! Work array to keep precip_rain
1200    REAL(r_std),DIMENSION (kjpindex)                      :: zprecip_snow  !! Work array to keep precip_snow
1201    REAL(r_std),DIMENSION (kjpindex)                      :: zz0           !! Work array to keep z0
1202    REAL(r_std),DIMENSION (kjpindex)                      :: zcdrag        !! Work array for surface drag
1203    REAL(r_std),DIMENSION (kjpindex)                      :: zcoastal      !! Work array to keep coastal flow
1204    REAL(r_std),DIMENSION (kjpindex)                      :: zriver        !! Work array to keep river out flow
1205    REAL(r_std),DIMENSION (kjpindex)                      :: dcoastal      !! Work array to keep coastal flow
1206    REAL(r_std),DIMENSION (kjpindex)                      :: driver        !! Work array to keep river out flow
1207    REAL(r_std),DIMENSION (kjpindex)                      :: ztsol_rad     !! Work array to keep tsol_rad
1208    REAL(r_std),DIMENSION (kjpindex)                      :: zvevapp       !! Work array to keep vevapp
1209    REAL(r_std),DIMENSION (kjpindex)                      :: ztemp_sol_new !! Work array to keep temp_sol_new
1210    REAL(r_std),DIMENSION (kjpindex)                      :: zqsurf        !! Work array to keep qsurf
1211    REAL(r_std),DIMENSION (kjpindex,2)                    :: zalbedo       !! Work array to keep albedo
1212    REAL(r_std),DIMENSION (kjpindex)                      :: zfluxsens     !! Work array to keep fluxsens
1213    REAL(r_std),DIMENSION (kjpindex)                      :: zfluxlat      !! Work array to keep fluxlat
1214    REAL(r_std),DIMENSION (kjpindex)                      :: zemis         !! Work array to keep emis
1215    !
1216    ! Optional arguments
1217    !
1218    REAL(r_std),DIMENSION (iim_glo,jjm_glo), INTENT(IN), OPTIONAL :: lon_scat_g, lat_scat_g !! The scattered values for longitude
1219    !
1220    INTEGER(i_std)                          :: iim,jjm                                  !! local sizes
1221    REAL(r_std),DIMENSION (:,:),ALLOCATABLE :: lon_scat, lat_scat !! The scattered values for longitude
1222    !                                                                          !! and latitude.
1223    !
1224    ! Scattered variables for diagnostics
1225    !
1226!    REAL(r_std),ALLOCATABLE,SAVE,DIMENSION (:)                       :: dvevapp       !! Diagnostic array for evaporation
1227    REAL(r_std),ALLOCATABLE,SAVE,DIMENSION (:)                       :: dtemp_sol     !! for surface temperature
1228    REAL(r_std),ALLOCATABLE,SAVE,DIMENSION (:)                       :: dfluxsens     !! for sensible heat flux
1229    REAL(r_std),ALLOCATABLE,SAVE,DIMENSION (:)                       :: dfluxlat      !! for latent heat flux
1230    REAL(r_std),ALLOCATABLE,SAVE,DIMENSION (:)                       :: dswnet        !! net solar radiation
1231    REAL(r_std),ALLOCATABLE,SAVE,DIMENSION (:)                       :: dswdown       !! Incident solar radiation
1232    REAL(r_std),ALLOCATABLE,SAVE,DIMENSION (:,:)                     :: dalbedo       !! albedo
1233    REAL(r_std),ALLOCATABLE,SAVE,DIMENSION (:)                       :: dtair         !! air temperature
1234    REAL(r_std),ALLOCATABLE,SAVE,DIMENSION (:)                       :: dqair         !! specific air humidity
1235    !
1236    !
1237    INTEGER(i_std)                                        :: i, j, ik
1238    INTEGER(i_std)                                        :: itau_sechiba
1239    REAL(r_std)                                           :: mx, zlev_mean
1240    REAL(r_std), ALLOCATABLE, DIMENSION(:,:)              :: tmp_lon, tmp_lat, tmp_lev
1241    LOGICAL                                               :: do_watch      !! if it's time, write watchout
1242    INTEGER                                               :: old_fileout   !! old Logical Int for std IO output
1243    LOGICAL :: check = .FALSE.
1244    INTEGER(i_std),DIMENSION (kjpindex)                  :: kindex_p
1245    !
1246    LOGICAL, SAVE                                         :: fatmco2       !! Flag to force the value of atmospheric CO2 for vegetation.
1247    REAL(r_std), SAVE                                     :: atmco2        !! atmospheric CO2
1248    !
1249    CALL ipslnlf(old_number=old_fileout)
1250    !
1251    IF (l_first_intersurf) THEN
1252       !
1253       CALL intsurf_time( kjit, date0, xrdt )
1254       !
1255       IF ( check ) WRITE(numout,*) 'Initialisation of intersurf'
1256       !
1257       CALL ioget_calendar (one_year, one_day)
1258       !
1259#ifdef CPP_PARA
1260       CALL init_para(.TRUE.,communicator)
1261       kindex_p(:)=kindex(:) + offset
1262#else
1263       CALL init_para(.FALSE.)
1264       kindex_p(:)=kindex(:)
1265#endif
1266       CALL ipslnlf(new_number=numout)
1267       !
1268       CALL init_data_para(iim_glo,jjm_glo,kjpindex,kindex_p)
1269       iim=iim_glo
1270       jjm=jj_nb
1271       ALLOCATE(lon_scat(iim,jjm))
1272       ALLOCATE(lat_scat(iim,jjm))
1273!       ALLOCATE(dvevapp(iim*jjm))
1274       ALLOCATE(dtemp_sol(iim*jjm))
1275       ALLOCATE(dfluxsens(iim*jjm))
1276       ALLOCATE(dfluxlat(iim*jjm))
1277       ALLOCATE(dswnet(iim*jjm))
1278       ALLOCATE(dswdown(iim*jjm))
1279       ALLOCATE(dalbedo(iim*jjm,2))
1280       ALLOCATE(dtair(iim*jjm))
1281       ALLOCATE(dqair(iim*jjm))
1282       
1283!       CALL init_WriteField_p(kindex)
1284       !
1285       ! Allocation of grid variables
1286       !
1287       CALL init_grid ( kjpindex )
1288       !
1289       !  Create the internal coordinate table
1290       !
1291       lalo(:,:) = latlon(:,:)
1292       CALL gather(lalo,lalo_g)
1293       !
1294       !-
1295       !- Store variable to help describe the grid
1296       !- once the points are gathered.
1297       !-
1298       neighbours(:,:) = zneighbours(:,:)
1299       CALL gather(neighbours,neighbours_g)
1300       !
1301       resolution(:,:) = zresolution(:,:)
1302       CALL gather(resolution,resolution_g)
1303       !
1304       area(:) = resolution(:,1)*resolution(:,2)
1305       CALL gather(area,area_g)
1306       !
1307       !- Store the fraction of the continents only once so that the user
1308       !- does not change them afterwards.
1309       !
1310       contfrac(:) = zcontfrac(:)
1311       CALL gather(contfrac,contfrac_g)
1312       !
1313       !
1314       !  Create the internal coordinate table
1315       !
1316       IF ( (.NOT.ALLOCATED(tmp_lon))) THEN
1317          ALLOCATE(tmp_lon(iim,jjm))
1318       ENDIF
1319       IF ( (.NOT.ALLOCATED(tmp_lat))) THEN
1320          ALLOCATE(tmp_lat(iim,jjm))
1321       ENDIF
1322       IF ( (.NOT.ALLOCATED(tmp_lev))) THEN
1323          ALLOCATE(tmp_lev(iim,jjm))
1324       ENDIF
1325       !
1326       !  Either we have the scattered coordinates as arguments or
1327       !  we have to do the work here.
1328       !
1329       IF ( PRESENT(lon_scat_g) .AND. PRESENT(lat_scat_g)) THEN
1330         
1331          lon_scat(:,:)=zero
1332          lat_scat(:,:)=zero 
1333          CALL scatter2D(lon_scat_g,lon_scat)
1334          CALL scatter2D(lat_scat_g,lat_scat)
1335          lon_scat(:,1)=lon_scat(:,2)
1336          lon_scat(:,jj_nb)=lon_scat(:,2)
1337          lat_scat(:,1)=lat_scat(iim,1)
1338          lat_scat(:,jj_nb)=lat_scat(1,jj_nb)
1339         
1340          tmp_lon(:,:) = lon_scat(:,:)
1341          tmp_lat(:,:) = lat_scat(:,:)
1342
1343          IF (is_root_prc) THEN
1344             lon_g(:,:) = lon_scat_g(:,:)
1345             lat_g(:,:) = lat_scat_g(:,:)
1346          ENDIF
1347
1348       ELSE IF ( PRESENT(lon_scat_g) .OR. PRESENT(lat_scat_g)) THEN
1349
1350          WRITE(numout,*) 'You need to provide the longitude AND latitude on the'
1351          WRITE(numout,*) 'gathered grid in order to start ORCHIDEE.'
1352          STOP 'intersurf_gathered'
1353
1354       ELSE
1355          !
1356          WRITE(numout,*) 'intersurf_gathered : We try to guess to full grid of the model.' 
1357          WRITE(numout,*) 'I might fail, please report if it does. '
1358          !
1359          tmp_lon(:,:) = val_exp
1360          tmp_lat(:,:) = val_exp
1361          !
1362          DO ik=1, kjpindex
1363             j = INT( (kindex(ik)-1) / iim ) + 1
1364             i = kindex(ik) - (j-1) * iim
1365             tmp_lon(i,j) = lalo(ik,2)
1366             tmp_lat(i,j) = lalo(ik,1)
1367          ENDDO
1368          !
1369          ! Here we fill out the grid. To do this we do the strong hypothesis
1370          ! that the grid is regular. Will this work in all cases ????
1371          !
1372          DO i=1,iim
1373             mx = MAXVAL(tmp_lon(i,:), MASK=tmp_lon(i,:) .LT. val_exp)
1374             IF ( mx .LT. val_exp ) THEN
1375                tmp_lon(i,:) = mx
1376             ELSE
1377                WRITE(numout,*) 'Could not find a continental point on this longitude. Thus the grid'
1378                WRITE(numout,*) 'could not be completed.'
1379                STOP 'intersurf_gathered'
1380             ENDIF
1381          ENDDO
1382          !
1383          DO j=1,jjm
1384             mx = MAXVAL(tmp_lat(:,j), MASK=tmp_lat(:,j) .LT. val_exp)
1385             IF ( mx .LT. val_exp ) THEN
1386                tmp_lat(:,j) = mx
1387             ELSE
1388                WRITE(numout,*) 'Could not find a continental point on this latitude. Thus the grid'
1389                WRITE(numout,*) 'could not be completed.'
1390                STOP 'intersurf_gathered'
1391             ENDIF
1392          ENDDO
1393
1394          CALL gather2D(tmp_lon,lon_g)
1395          CALL gather2D(tmp_lat,lat_g)
1396
1397       ENDIF
1398       !
1399       DO ik=1, kjpindex
1400          j = INT( (kindex(ik)-1) / iim ) + 1
1401          i = kindex(ik) - (j-1) * iim
1402          tmp_lev(i,j) = zlev(ik)
1403       ENDDO
1404       CALL gather2D(tmp_lev,zlev_g)
1405       !
1406       !
1407       !  Configuration of SSL specific parameters
1408       !
1409       CALL intsurf_config(control_flags,xrdt)
1410       !
1411       !Config  Key  = FORCE_CO2_VEG
1412       !Config  Desc = Flag to force the value of atmospheric CO2 for vegetation.
1413       !Config  Def  = FALSE
1414       !Config  Help = If this flag is set to true, the ATM_CO2 parameter is used
1415       !Config         to prescribe the atmospheric CO2.
1416       !Config         This Flag is only use in couple mode.
1417       !
1418       fatmco2=.FALSE.
1419       CALL getin_p('FORCE_CO2_VEG',fatmco2)
1420       !
1421       ! Next flag is only use in couple mode with a gcm in intersurf.
1422       ! In forced mode, it has already been read and set in driver.
1423       IF ( fatmco2 ) THEN
1424          !Config  Key  = ATM_CO2
1425          !Config  IF   = FORCE_CO2_VEG (in not forced mode)
1426          !Config  Desc = Value for atm CO2
1427          !Config  Def  = 350.
1428          !Config  Help = Value to prescribe the atm CO2.
1429          !Config         For pre-industrial simulations, the value is 286.2 .
1430          !Config         348. for 1990 year.
1431          !
1432          atmco2=350.
1433          CALL getin_p('ATM_CO2',atmco2)
1434          WRITE(numout,*) 'atmco2 ',atmco2
1435       ENDIF
1436       
1437       !
1438       CALL intsurf_restart(kjit, iim, jjm, tmp_lon, tmp_lat, date0, xrdt, control_flags, rest_id, rest_id_stom, itau_offset)
1439       itau_sechiba = kjit + itau_offset
1440       !
1441       CALL intsurf_history(iim, jjm, tmp_lon, tmp_lat, itau_sechiba, &
1442 &                          date0_shifted, xrdt, control_flags, hist_id, hist2_id, hist_id_stom, hist_id_stom_IPCC)
1443       !
1444       IF ( ok_watchout ) THEN
1445          IF (is_root_prc) THEN
1446             zlev_mean = 0.
1447             DO ik=1, nbp_glo
1448                j = ((index_g(ik)-1)/iim_g) + 1
1449                i = (index_g(ik) - (j-1)*iim_g)
1450               
1451                zlev_mean = zlev_mean + zlev_g(i,j)
1452             ENDDO
1453             zlev_mean = zlev_mean / REAL(nbp_glo,r_std)
1454          ENDIF
1455
1456          last_action_watch = itau_sechiba
1457          last_check_watch =  last_action_watch
1458
1459          CALL watchout_init(iim_g, jjm_g, kjpindex, nbp_glo, &
1460               & date0_shifted, last_action_watch, dt_watch, index_g, lon_g, lat_g, zlev_mean)
1461       ENDIF
1462       !
1463       IF ( check ) WRITE(numout,*) 'End of Initialisation of intersurf'
1464       !
1465    ENDIF
1466    !
1467    CALL ipslnlf(new_number=numout)
1468    !
1469    !  Shift the time step to phase the two models
1470    !
1471    itau_sechiba = kjit + itau_offset
1472    !
1473    CALL intsurf_time( itau_sechiba, date0_shifted, xrdt )
1474    !
1475    ! 1. Just change the units of some input fields
1476    !
1477    DO ik=1, kjpindex
1478       
1479       zprecip_rain(ik) = precip_rain(ik)*xrdt
1480       zprecip_snow(ik) = precip_snow(ik)*xrdt
1481       zcdrag(ik)       = cdrag(ik)
1482       
1483    ENDDO
1484    !
1485    IF (check_INPUTS) THEN
1486       WRITE(numout,*) "Intersurf_main_gathered :"
1487       WRITE(numout,*) "Time step number = ",kjit
1488       WRITE(numout,*) "Dimension of input fields = ",iim, jjm
1489       WRITE(numout,*) "Number of continental points = ",kjpindex
1490       WRITE(numout,*) "Time step in seconds = ",xrdt
1491       WRITE(numout,*) "Logical for _restart_ file to read, write = ",lrestart_read,lrestart_write
1492       WRITE(numout,*) "Date at which kjit = 0  =  ",date0
1493       WRITE(numout,*) "Index for continental points = ",kindex
1494       WRITE(numout,*) "Lowest level wind speed North = ",u
1495       WRITE(numout,*) "Lowest level wind speed East = ",v
1496       WRITE(numout,*) "Height of first layer = ",zlev
1497       WRITE(numout,*) "Lowest level specific humidity = ",qair
1498       WRITE(numout,*) "Rain precipitation = ",zprecip_rain
1499       WRITE(numout,*) "Snow precipitation = ",zprecip_snow
1500       WRITE(numout,*) "Down-welling long-wave flux = ",lwdown
1501       WRITE(numout,*) "Net surface short-wave flux = ",swnet
1502       WRITE(numout,*) "Downwelling surface short-wave flux = ",swdown
1503       WRITE(numout,*) "Air temperature in Kelvin = ",temp_air
1504       WRITE(numout,*) "Air potential energy = ",epot_air
1505       WRITE(numout,*) "CO2 concentration in the canopy = ",ccanopy
1506       WRITE(numout,*) "Coeficients A from the PBL resolution = ",petAcoef
1507       WRITE(numout,*) "One for T and another for q = ",peqAcoef
1508       WRITE(numout,*) "Coeficients B from the PBL resolution = ",petBcoef
1509       WRITE(numout,*) "One for T and another for q = ",peqBcoef
1510       WRITE(numout,*) "Cdrag = ",zcdrag
1511       WRITE(numout,*) "Lowest level pressure = ",pb
1512       WRITE(numout,*) "Geographical coordinates lon = ", lon_scat
1513       WRITE(numout,*) "Geographical coordinates lat = ", lat_scat 
1514       WRITE(numout,*) "Fraction of continent in the grid = ",zcontfrac
1515    ENDIF
1516    !
1517    ! 2. modification of co2
1518    !
1519    IF ( fatmco2 ) THEN
1520       zccanopy(:) = atmco2
1521       WRITE (numout,*) 'Modification of the ccanopy value. CO2 = ',atmco2
1522    ELSE
1523       zccanopy(:) = ccanopy(:)
1524    ENDIF
1525    !
1526    ! 3. save the grid
1527    !
1528    IF ( check ) WRITE(numout,*) 'Save the grid'
1529    !
1530    IF (l_first_intersurf) THEN
1531       CALL histwrite(hist_id, 'LandPoints',  itau_sechiba+1, (/ ( REAL(ik), ik=1,kjpindex ) /), kjpindex, kindex)
1532       CALL histwrite(hist_id, 'Areas',  itau_sechiba+1, area, kjpindex, kindex)
1533       IF ( control_flags%ok_stomate ) THEN
1534            CALL histwrite(hist_id_stom, 'Areas',  itau_sechiba+1, area, kjpindex, kindex)
1535          IF ( hist_id_stom_IPCC > 0 ) THEN
1536             CALL histwrite(hist_id_stom_IPCC, 'Areas',  itau_sechiba+1, area, kjpindex, kindex)
1537          ENDIF
1538       ENDIF
1539       CALL histwrite(hist_id, 'Contfrac',  itau_sechiba+1, contfrac, kjpindex, kindex)
1540       CALL histsync(hist_id)
1541       !
1542       IF ( hist2_id > 0 ) THEN
1543          CALL histwrite(hist2_id, 'LandPoints',  itau_sechiba+1, (/ ( REAL(ik), ik=1,kjpindex ) /), kjpindex, kindex)
1544          CALL histwrite(hist2_id, 'Areas',  itau_sechiba+1, area, kjpindex, kindex)
1545          CALL histwrite(hist2_id, 'Contfrac',  itau_sechiba+1, contfrac, kjpindex, kindex)
1546          CALL histsync(hist2_id)
1547       ENDIF
1548       !
1549    ENDIF
1550    !
1551    ! 4. call sechiba for continental points only
1552    !
1553    IF ( check ) WRITE(numout,*) 'Calling sechiba'
1554    !
1555    CALL sechiba_main (itau_sechiba, iim*jjm, kjpindex, kindex, xrdt, date0_shifted, &
1556       & lrestart_read, lrestart_write, control_flags, &
1557       & lalo, contfrac, neighbours, resolution, &
1558! First level conditions
1559! Ajout Nathalie - Juin 2006 - passage q2m/t2m pour calcul rveget
1560!       & zlev, u, v, qair, temp_air, epot_air, ccanopy, &
1561       & zlev, u, v, qair, qair, temp_air, temp_air, epot_air, zccanopy, &
1562! Variables for the implicit coupling
1563       & zcdrag, petAcoef, peqAcoef, petBcoef, peqBcoef, &
1564! Rain, snow, radiation and surface pressure
1565       & zprecip_rain ,zprecip_snow,  lwdown, swnet, swdown, pb, &
1566! Output : Fluxes
1567       & zvevapp, zfluxsens, zfluxlat, zcoastal, zriver, &
1568! Surface temperatures and surface properties
1569       & ztsol_rad, ztemp_sol_new, zqsurf, zalbedo, zemis, zz0, &
1570! File ids
1571       & rest_id, hist_id, hist2_id, rest_id_stom, hist_id_stom, hist_id_stom_IPCC ) 
1572   
1573    !
1574    IF ( check ) WRITE(numout,*) 'out of SECHIBA'
1575    !
1576    ! 5. save watchout
1577    !
1578    IF ( ok_watchout .AND. .NOT. l_first_intersurf ) THEN
1579       ! Accumulate last time step
1580       sum_zlev(:) = sum_zlev(:) + zlev(:)
1581       sum_u(:) = sum_u(:) + u(:)
1582       sum_v(:) = sum_v(:) + v(:)
1583       sum_qair(:) = sum_qair(:) + qair(:) 
1584       sum_temp_air(:) = sum_temp_air(:) + temp_air(:)
1585       sum_epot_air(:) = sum_epot_air(:) + epot_air(:)
1586       sum_ccanopy(:) = sum_ccanopy(:) + ccanopy(:)
1587       sum_cdrag(:) = sum_cdrag(:) + zcdrag(:)
1588       sum_petAcoef(:) = sum_petAcoef(:) + petAcoef(:)
1589       sum_peqAcoef(:) = sum_peqAcoef(:) + peqAcoef(:)
1590       sum_petBcoef(:) = sum_petBcoef(:) + petBcoef(:)
1591       sum_peqBcoef(:) = sum_peqBcoef(:) + peqBcoef(:)
1592       sum_rain(:) = sum_rain(:) + zprecip_rain(:)
1593       sum_snow(:) = sum_snow(:) + zprecip_snow(:)
1594       sum_lwdown(:) = sum_lwdown(:) + lwdown(:)
1595       sum_pb(:) = sum_pb(:) + pb(:)
1596
1597!!$       IF ( dt_watch > 3600 ) THEN
1598!!$          julian_watch = date0_shifted+((itau_sechiba-0.5)/dt_split_watch)*dt_watch/one_day
1599!!$          CALL solarang (julian_watch, julian0, iim, jjm, tmp_lon, tmp_lat, sinang)
1600!!$          WHERE ( sinang(:,:) .LT. EPSILON(1.) )
1601!!$             isinang(:,:) = isinang(:,:) - 1
1602!!$          ENDWHERE
1603!!$          mean_sinang(:,:) = mean_sinang(:,:)+sinang(:,:)
1604!!$          !
1605!!$          DO ik=1,kjpindex         
1606!!$             j = ((kindex(ik)-1)/iim) + 1
1607!!$             i = (kindex(ik) - (j-1)*iim)
1608!!$             
1609!!$             sum_swnet(ik) = sum_swnet(ik) + sinang(i,j)*swnet(ik)
1610!!$             sum_swdown(ik) = sum_swdown(ik) + sinang(i,j)*swdown(ik)
1611!!$          ENDDO
1612!!$       ELSE
1613          sum_swnet(:) = sum_swnet(:) + swnet(:)
1614          sum_swdown(:) = sum_swdown(:) + swdown(:)
1615!!$       ENDIF
1616       
1617       do_watch = .FALSE.
1618       call isittime &
1619            &  (itau_sechiba,date0_shifted,xrdt,dt_watch,&
1620            &   last_action_watch,last_check_watch,do_watch)
1621       last_check_watch = itau_sechiba
1622       IF (do_watch) THEN
1623          !
1624          IF ( check ) WRITE(numout,*) 'save watchout'
1625          !
1626          IF (long_print) THEN
1627             WRITE(numout,*) "intersurf : write watchout for date ",date0,date0_shifted,itau_sechiba, & 
1628                  & last_action_watch,last_check_watch
1629          ENDIF
1630          last_action_watch = itau_sechiba
1631
1632          sum_zlev(:) = sum_zlev(:) / dt_split_watch
1633          sum_u(:) = sum_u(:) / dt_split_watch
1634          sum_v(:) = sum_v(:) / dt_split_watch
1635          sum_qair(:) = sum_qair(:) / dt_split_watch
1636          sum_temp_air(:) = sum_temp_air(:) / dt_split_watch
1637          sum_epot_air(:) = sum_epot_air(:) / dt_split_watch
1638          sum_ccanopy(:) = sum_ccanopy(:) / dt_split_watch
1639          sum_cdrag(:) = sum_cdrag(:) / dt_split_watch
1640          sum_petAcoef(:) = sum_petAcoef(:) / dt_split_watch
1641          sum_peqAcoef(:) = sum_peqAcoef(:) / dt_split_watch
1642          sum_petBcoef(:) = sum_petBcoef(:) / dt_split_watch
1643          sum_peqBcoef(:) = sum_peqBcoef(:) / dt_split_watch
1644          sum_rain(:) = sum_rain(:) / dt_split_watch
1645          sum_snow(:) = sum_snow(:) / dt_split_watch
1646          sum_lwdown(:) = sum_lwdown(:) / dt_split_watch
1647          sum_pb(:) = sum_pb(:) / dt_split_watch
1648
1649!!$          IF ( dt_watch > 3600 ) THEN
1650!!$             WHERE ( isinang(:,:) .GT. 0 )
1651!!$                mean_sinang(:,:) = mean_sinang(:,:) / isinang(:,:)
1652!!$             ENDWHERE
1653!!$             !
1654!!$             DO ik=1,kjpindex         
1655!!$                j = ((kindex(ik)-1)/iim) + 1
1656!!$                i = (kindex(ik) - (j-1)*iim)
1657!!$                IF (mean_sinang(i,j) > zero) THEN
1658!!$                   sum_swdown(ik) = sum_swdown(ik)/mean_sinang(i,j)
1659!!$                   sum_swnet(ik) =  sum_swnet(ik)/mean_sinang(i,j)
1660!!$                ELSE
1661!!$                   sum_swdown(ik) = zero
1662!!$                   sum_swnet(ik) =  zero
1663!!$                ENDIF
1664!!$             ENDDO
1665!!$          ELSE
1666             sum_swnet(:) = sum_swnet(:) / dt_split_watch
1667             sum_swdown(:) = sum_swdown(:) / dt_split_watch
1668!!$          ENDIF
1669
1670          CALL watchout_write_p(kjpindex, itau_sechiba, xrdt, sum_zlev, sum_swdown, sum_rain, &
1671               &   sum_snow, sum_lwdown, sum_pb, sum_temp_air, sum_epot_air, sum_qair, &
1672               &   sum_u, sum_v, sum_swnet, sum_petAcoef, sum_peqAcoef, sum_petBcoef, sum_peqBcoef, &
1673               &   sum_cdrag, sum_ccanopy )
1674       ENDIF       
1675    ENDIF
1676    !
1677    ! 6. scatter output fields
1678    !
1679    z0(:)           = undef_sechiba
1680    coastalflow(:)  = undef_sechiba
1681    riverflow(:)    = undef_sechiba
1682    tsol_rad(:)     = undef_sechiba
1683    vevapp(:)       = undef_sechiba
1684    temp_sol_new(:) = undef_sechiba
1685    qsurf(:)        = undef_sechiba
1686    albedo(:,1)     = undef_sechiba
1687    albedo(:,2)     = undef_sechiba
1688    fluxsens(:)     = undef_sechiba
1689    fluxlat(:)      = undef_sechiba
1690    emis(:)         = undef_sechiba
1691    cdrag(:)        = undef_sechiba
1692    !   
1693!    dvevapp(:)    = undef_sechiba
1694    dtemp_sol(:)  = undef_sechiba
1695    dfluxsens(:)  = undef_sechiba
1696    dfluxlat(:)   = undef_sechiba
1697    dswnet (:)    = undef_sechiba
1698    dswdown (:)   = undef_sechiba
1699    dalbedo (:,1) = undef_sechiba
1700    dalbedo (:,2) = undef_sechiba
1701    dtair (:)     = undef_sechiba
1702    dqair (:)     = undef_sechiba
1703    !
1704    DO ik=1, kjpindex
1705       
1706       z0(ik)           = zz0(ik)
1707       coastalflow(ik)  = zcoastal(ik)/1000.
1708       riverflow(ik)    = zriver(ik)/1000.
1709       tsol_rad(ik)     = ztsol_rad(ik)
1710       vevapp(ik)       = zvevapp(ik)
1711       temp_sol_new(ik) = ztemp_sol_new(ik)
1712       qsurf(ik)        = zqsurf(ik)
1713       albedo(ik,1)     = zalbedo(ik,1)
1714       albedo(ik,2)     = zalbedo(ik,2)
1715       fluxsens(ik)     = zfluxsens(ik)
1716       fluxlat(ik)      = zfluxlat(ik)
1717       emis(ik)         = zemis(ik)
1718       cdrag(ik)        = zcdrag(ik)
1719       
1720       ! Fill up the diagnostic arrays
1721
1722!       dvevapp(kindex(ik))    = zvevapp(ik)
1723       dtemp_sol(kindex(ik))  = ztemp_sol_new(ik)
1724       dfluxsens(kindex(ik))  = zfluxsens(ik)
1725       dfluxlat(kindex(ik))   = zfluxlat(ik)
1726       dswnet (kindex(ik))    = swnet(ik)
1727       dswdown (kindex(ik))   = swdown(ik)
1728       dalbedo (kindex(ik),1) = zalbedo(ik,1)
1729       dalbedo (kindex(ik),2) = zalbedo(ik,2)   
1730       dtair (kindex(ik))     = temp_air(ik)
1731       dqair (kindex(ik))     = qair(ik)
1732       !
1733    ENDDO
1734    !
1735    ! Modified fields for variables scattered during the writing
1736    !
1737    dcoastal(:) = (zcoastal(:))/1000.
1738    driver(:)   = (zriver(:))/1000.
1739    !
1740    IF ( .NOT. l_first_intersurf) THEN
1741       !
1742       IF ( .NOT. almaoutput ) THEN
1743          !
1744          !  scattered during the writing
1745          !           
1746          CALL histwrite (hist_id, 'evap',     itau_sechiba, zvevapp, kjpindex, kindex)
1747          CALL histwrite (hist_id, 'coastalflow',itau_sechiba, dcoastal, kjpindex, kindex)
1748          CALL histwrite (hist_id, 'riverflow',itau_sechiba, driver, kjpindex, kindex)
1749          !
1750          CALL histwrite (hist_id, 'temp_sol', itau_sechiba, dtemp_sol, iim*jjm, kindex)
1751          CALL histwrite (hist_id, 'tsol_max', itau_sechiba, dtemp_sol, iim*jjm, kindex)
1752          CALL histwrite (hist_id, 'tsol_min', itau_sechiba, dtemp_sol, iim*jjm, kindex)
1753          CALL histwrite (hist_id, 'fluxsens', itau_sechiba, dfluxsens, iim*jjm, kindex)
1754          CALL histwrite (hist_id, 'fluxlat',  itau_sechiba, dfluxlat,  iim*jjm, kindex)
1755          CALL histwrite (hist_id, 'swnet',    itau_sechiba, dswnet,    iim*jjm, kindex)
1756          CALL histwrite (hist_id, 'swdown',   itau_sechiba, dswdown,   iim*jjm, kindex)
1757          CALL histwrite (hist_id, 'alb_vis',  itau_sechiba, dalbedo(:,1), iim*jjm, kindex)
1758          CALL histwrite (hist_id, 'alb_nir',  itau_sechiba, dalbedo(:,2), iim*jjm, kindex)
1759          CALL histwrite (hist_id, 'tair',     itau_sechiba, dtair, iim*jjm, kindex)
1760          CALL histwrite (hist_id, 'qair',     itau_sechiba, dqair, iim*jjm, kindex)
1761          CALL histwrite (hist_id, 't2m',      itau_sechiba, dtair, iim*jjm, kindex)
1762          CALL histwrite (hist_id, 'q2m',      itau_sechiba, dqair, iim*jjm, kindex)
1763          !
1764          IF ( hist2_id > 0 ) THEN
1765             CALL histwrite (hist2_id, 'evap',     itau_sechiba, zvevapp, kjpindex, kindex)
1766             CALL histwrite (hist2_id, 'coastalflow',itau_sechiba, dcoastal, kjpindex, kindex)
1767             CALL histwrite (hist2_id, 'riverflow',itau_sechiba, driver, kjpindex, kindex)
1768             !
1769             CALL histwrite (hist2_id, 'temp_sol', itau_sechiba, dtemp_sol, iim*jjm, kindex)
1770             CALL histwrite (hist2_id, 'tsol_max', itau_sechiba, dtemp_sol, iim*jjm, kindex)
1771             CALL histwrite (hist2_id, 'tsol_min', itau_sechiba, dtemp_sol, iim*jjm, kindex)
1772             CALL histwrite (hist2_id, 'fluxsens', itau_sechiba, dfluxsens, iim*jjm, kindex)
1773             CALL histwrite (hist2_id, 'fluxlat',  itau_sechiba, dfluxlat,  iim*jjm, kindex)
1774             CALL histwrite (hist2_id, 'swnet',    itau_sechiba, dswnet,    iim*jjm, kindex)
1775             CALL histwrite (hist2_id, 'swdown',   itau_sechiba, dswdown,   iim*jjm, kindex)
1776             CALL histwrite (hist2_id, 'alb_vis',  itau_sechiba, dalbedo(:,1), iim*jjm, kindex)
1777             CALL histwrite (hist2_id, 'alb_nir',  itau_sechiba, dalbedo(:,2), iim*jjm, kindex)
1778             CALL histwrite (hist2_id, 'tair',     itau_sechiba, dtair, iim*jjm, kindex)
1779             CALL histwrite (hist2_id, 'qair',     itau_sechiba, dqair, iim*jjm, kindex)
1780             CALL histwrite (hist2_id, 't2m',      itau_sechiba, dtair, iim*jjm, kindex)
1781             CALL histwrite (hist2_id, 'q2m',      itau_sechiba, dqair, iim*jjm, kindex)
1782          ENDIF
1783       ELSE
1784          CALL histwrite (hist_id, 'Evap', itau_sechiba, zvevapp, kjpindex, kindex)
1785          CALL histwrite (hist_id, 'SWnet',    itau_sechiba, dswnet, iim*jjm, kindex)
1786          CALL histwrite (hist_id, 'Qh', itau_sechiba, dfluxsens, iim*jjm, kindex)
1787          CALL histwrite (hist_id, 'Qle',  itau_sechiba, dfluxlat, iim*jjm, kindex)
1788          CALL histwrite (hist_id, 'AvgSurfT', itau_sechiba, dtemp_sol, iim*jjm, kindex)
1789          CALL histwrite (hist_id, 'RadT', itau_sechiba, dtemp_sol, iim*jjm, kindex)
1790          !
1791          IF ( hist2_id > 0 ) THEN
1792             CALL histwrite (hist2_id, 'Evap', itau_sechiba, zvevapp, kjpindex, kindex)
1793             CALL histwrite (hist2_id, 'SWnet',    itau_sechiba, dswnet, iim*jjm, kindex)
1794             CALL histwrite (hist2_id, 'Qh', itau_sechiba, dfluxsens, iim*jjm, kindex)
1795             CALL histwrite (hist2_id, 'Qle',  itau_sechiba, dfluxlat, iim*jjm, kindex)
1796             CALL histwrite (hist2_id, 'AvgSurfT', itau_sechiba, dtemp_sol, iim*jjm, kindex)
1797             CALL histwrite (hist2_id, 'RadT', itau_sechiba, dtemp_sol, iim*jjm, kindex)
1798          ENDIF
1799       ENDIF
1800       !
1801       IF (dw .EQ. xrdt) THEN
1802          CALL histsync(hist_id)
1803       ENDIF
1804    !
1805    ENDIF
1806    !
1807    ! 7. Transform the water fluxes into Kg/m^2s and m^3/s
1808    !
1809    DO ik=1, kjpindex
1810
1811       vevapp(ik) = vevapp(ik)/xrdt
1812       coastalflow(ik) = coastalflow(ik)/xrdt
1813       riverflow(ik) = riverflow(ik)/xrdt
1814
1815    ENDDO
1816    !
1817    IF ( lrestart_write .AND. ok_watchout .AND. is_root_prc ) THEN
1818       CALL watchout_close()
1819    ENDIF
1820    !
1821    IF(l_first_intersurf .AND. is_root_prc) CALL getin_dump
1822    l_first_intersurf = .FALSE.
1823    !
1824    IF (long_print) WRITE (numout,*) ' intersurf_main done '
1825    !
1826    CALL ipslnlf(new_number=old_fileout)
1827    !       
1828  END SUBROUTINE intersurf_gathered
1829!
1830!
1831#ifdef CPP_PARA
1832  SUBROUTINE intersurf_gathered_2m (kjit, iim_glo, jjm_glo, offset, kjpindex, kindex, communicator, xrdt, &
1833     & lrestart_read, lrestart_write, latlon, zcontfrac, zneighbours, zresolution, date0, &
1834! First level conditions
1835     & zlev,  u, v, qair, temp_air, epot_air, ccanopy, &
1836! Variables for the implicit coupling
1837     & cdrag, petAcoef, peqAcoef, petBcoef, peqBcoef, &
1838! Rain, snow, radiation and surface pressure
1839     & precip_rain, precip_snow, lwdown, swnet, swdown, pb, &
1840! Output : Fluxes
1841     & vevapp, fluxsens, fluxlat, coastalflow, riverflow, &
1842! Surface temperatures and surface properties
1843!     & tsol_rad, temp_sol_new, qsurf, albedo, emis, z0, lon_scat_g, lat_scat_g)
1844     & tsol_rad, temp_sol_new, qsurf, albedo, emis, z0, lon_scat_g, lat_scat_g, &
1845! Ajout Nathalie - passage q2m/t2m pour calcul Rveget
1846     & q2m, t2m) 
1847#else
1848  SUBROUTINE intersurf_gathered_2m (kjit, iim_glo, jjm_glo, kjpindex, kindex, xrdt, &
1849     & lrestart_read, lrestart_write, latlon, zcontfrac, zneighbours, zresolution, date0, &
1850! First level conditions
1851     & zlev,  u, v, qair, temp_air, epot_air, ccanopy, &
1852! Variables for the implicit coupling
1853     & cdrag, petAcoef, peqAcoef, petBcoef, peqBcoef, &
1854! Rain, snow, radiation and surface pressure
1855     & precip_rain, precip_snow, lwdown, swnet, swdown, pb, &
1856! Output : Fluxes
1857     & vevapp, fluxsens, fluxlat, coastalflow, riverflow, &
1858! Surface temperatures and surface properties
1859!     & tsol_rad, temp_sol_new, qsurf, albedo, emis, z0, lon_scat_g, lat_scat_g)
1860     & tsol_rad, temp_sol_new, qsurf, albedo, emis, z0, lon_scat_g, lat_scat_g, &
1861! Ajout Nathalie - passage q2m/t2m pour calcul Rveget
1862     & q2m, t2m) 
1863#endif
1864    ! routines called : sechiba_main
1865    !
1866    IMPLICIT NONE
1867    !   
1868    ! interface description for dummy arguments
1869    ! input scalar
1870    INTEGER(i_std),INTENT (in)                            :: kjit          !! Time step number
1871    INTEGER(i_std),INTENT (in)                            :: iim_glo, jjm_glo  !! Dimension of global fields
1872#ifdef CPP_PARA
1873    INTEGER(i_std),INTENT (in)                            :: offset        !! offset between the first global 2D point
1874                                                                           !! and the first local 2D point.
1875    INTEGER(i_std),INTENT(IN)                             :: communicator  !! Orchidee communicator
1876#endif
1877    INTEGER(i_std),INTENT (in)                            :: kjpindex      !! Number of continental points
1878    REAL(r_std),INTENT (in)                               :: xrdt          !! Time step in seconds
1879    LOGICAL, INTENT (in)                                 :: lrestart_read !! Logical for _restart_ file to read
1880    LOGICAL, INTENT (in)                                 :: lrestart_write!! Logical for _restart_ file to write'
1881    REAL(r_std), INTENT (in)                              :: date0         !! Date at which kjit = 0
1882    ! input fields
1883    INTEGER(i_std),DIMENSION (kjpindex), INTENT (in)      :: kindex        !! Index for continental points
1884    REAL(r_std),DIMENSION (kjpindex), INTENT(in)          :: u             !! Lowest level wind speed
1885    REAL(r_std),DIMENSION (kjpindex), INTENT(in)          :: v             !! Lowest level wind speed
1886    REAL(r_std),DIMENSION (kjpindex), INTENT(in)          :: zlev          !! Height of first layer
1887    REAL(r_std),DIMENSION (kjpindex), INTENT(in)          :: qair          !! Lowest level specific humidity
1888    REAL(r_std),DIMENSION (kjpindex), INTENT(in)          :: precip_rain   !! Rain precipitation
1889    REAL(r_std),DIMENSION (kjpindex), INTENT(in)          :: precip_snow   !! Snow precipitation
1890    REAL(r_std),DIMENSION (kjpindex), INTENT(in)          :: lwdown        !! Down-welling long-wave flux
1891    REAL(r_std),DIMENSION (kjpindex), INTENT(in)          :: swnet         !! Net surface short-wave flux
1892    REAL(r_std),DIMENSION (kjpindex), INTENT(in)          :: swdown        !! Downwelling surface short-wave flux
1893    REAL(r_std),DIMENSION (kjpindex), INTENT(in)          :: temp_air      !! Air temperature in Kelvin
1894    REAL(r_std),DIMENSION (kjpindex), INTENT(in)          :: epot_air      !! Air potential energy
1895    REAL(r_std),DIMENSION (kjpindex), INTENT(in)          :: ccanopy       !! CO2 concentration in the canopy
1896    REAL(r_std),DIMENSION (kjpindex), INTENT(in)          :: petAcoef      !! Coeficients A from the PBL resolution
1897    REAL(r_std),DIMENSION (kjpindex), INTENT(in)          :: peqAcoef      !! One for T and another for q
1898    REAL(r_std),DIMENSION (kjpindex), INTENT(in)          :: petBcoef      !! Coeficients B from the PBL resolution
1899    REAL(r_std),DIMENSION (kjpindex), INTENT(in)          :: peqBcoef      !! One for T and another for q
1900    REAL(r_std),DIMENSION (kjpindex), INTENT(inout)       :: cdrag         !! Cdrag
1901    REAL(r_std),DIMENSION (kjpindex), INTENT(in)          :: pb            !! Lowest level pressure
1902    REAL(r_std),DIMENSION (kjpindex,2), INTENT(in)        :: latlon        !! Geographical coordinates
1903    REAL(r_std),DIMENSION (kjpindex), INTENT(in)          :: zcontfrac     !! Fraction of continent
1904    INTEGER(i_std),DIMENSION (kjpindex,8), INTENT(in)    :: zneighbours   !! neighbours
1905    REAL(r_std),DIMENSION (kjpindex,2), INTENT(in)        :: zresolution   !! size of the grid box
1906! Ajout Nathalie - Juin 2006 - q2m/t2m pour calcul Rveget
1907    REAL(r_std),DIMENSION (kjpindex), INTENT(in)          :: q2m          !! Surface specific humidity
1908    REAL(r_std),DIMENSION (kjpindex), INTENT(in)          :: t2m          !! Surface air temperature
1909    ! output fields
1910    REAL(r_std),DIMENSION (kjpindex), INTENT(out)         :: z0            !! Surface roughness
1911    REAL(r_std),DIMENSION (kjpindex), INTENT(out)         :: coastalflow   !! Diffuse flow of water into the ocean (m^3/dt)
1912    REAL(r_std),DIMENSION (kjpindex), INTENT(out)         :: riverflow     !! Largest rivers flowing into the ocean (m^3/dt)
1913    REAL(r_std),DIMENSION (kjpindex), INTENT(out)         :: tsol_rad      !! Radiative surface temperature
1914    REAL(r_std),DIMENSION (kjpindex), INTENT(out)         :: vevapp        !! Total of evaporation
1915    REAL(r_std),DIMENSION (kjpindex), INTENT(out)         :: temp_sol_new  !! New soil temperature
1916    REAL(r_std),DIMENSION (kjpindex), INTENT(out)         :: qsurf         !! Surface specific humidity
1917    REAL(r_std),DIMENSION (kjpindex,2), INTENT(out)       :: albedo        !! Albedo
1918    REAL(r_std),DIMENSION (kjpindex), INTENT(out)         :: fluxsens      !! Sensible chaleur flux
1919    REAL(r_std),DIMENSION (kjpindex), INTENT(out)         :: fluxlat       !! Latent chaleur flux
1920    REAL(r_std),DIMENSION (kjpindex), INTENT(out)         :: emis          !! Emissivity
1921    ! LOCAL declaration
1922    ! work arrays to scatter and/or gather information just before/after sechiba_main call's
1923    ! and to keep output value for next call
1924    REAL(r_std),DIMENSION (kjpindex)                      :: zccanopy      !! Work array to keep ccanopy
1925    REAL(r_std),DIMENSION (kjpindex)                      :: zprecip_rain  !! Work array to keep precip_rain
1926    REAL(r_std),DIMENSION (kjpindex)                      :: zprecip_snow  !! Work array to keep precip_snow
1927    REAL(r_std),DIMENSION (kjpindex)                      :: zz0           !! Work array to keep z0
1928    REAL(r_std),DIMENSION (kjpindex)                      :: zcdrag        !! Work array for surface drag
1929    REAL(r_std),DIMENSION (kjpindex)                      :: zcoastal      !! Work array to keep coastal flow
1930    REAL(r_std),DIMENSION (kjpindex)                      :: zriver        !! Work array to keep river out flow
1931    REAL(r_std),DIMENSION (kjpindex)                      :: dcoastal      !! Work array to keep coastal flow
1932    REAL(r_std),DIMENSION (kjpindex)                      :: driver        !! Work array to keep river out flow
1933    REAL(r_std),DIMENSION (kjpindex)                      :: ztsol_rad     !! Work array to keep tsol_rad
1934    REAL(r_std),DIMENSION (kjpindex)                      :: zvevapp       !! Work array to keep vevapp
1935    REAL(r_std),DIMENSION (kjpindex)                      :: ztemp_sol_new !! Work array to keep temp_sol_new
1936    REAL(r_std),DIMENSION (kjpindex)                      :: zqsurf        !! Work array to keep qsurf
1937    REAL(r_std),DIMENSION (kjpindex,2)                    :: zalbedo       !! Work array to keep albedo
1938    REAL(r_std),DIMENSION (kjpindex)                      :: zfluxsens     !! Work array to keep fluxsens
1939    REAL(r_std),DIMENSION (kjpindex)                      :: zfluxlat      !! Work array to keep fluxlat
1940    REAL(r_std),DIMENSION (kjpindex)                      :: zemis         !! Work array to keep emis
1941    !
1942    ! Optional arguments
1943    !
1944    REAL(r_std),DIMENSION (iim_glo,jjm_glo), INTENT(IN), OPTIONAL :: lon_scat_g, lat_scat_g !! The scattered values for longitude
1945    !
1946    INTEGER(i_std)                          :: iim,jjm                                  !! local sizes
1947    REAL(r_std),DIMENSION (:,:),ALLOCATABLE :: lon_scat, lat_scat !! The scattered values for longitude
1948    !                                                                          !! and latitude.
1949    !
1950    ! Scattered variables for diagnostics
1951    !
1952!    REAL(r_std),ALLOCATABLE,SAVE,DIMENSION (:)                       :: dvevapp       !! Diagnostic array for evaporation
1953    REAL(r_std),ALLOCATABLE,SAVE,DIMENSION (:)                       :: dtemp_sol     !! for surface temperature
1954    REAL(r_std),ALLOCATABLE,SAVE,DIMENSION (:)                       :: dfluxsens     !! for sensible heat flux
1955    REAL(r_std),ALLOCATABLE,SAVE,DIMENSION (:)                       :: dfluxlat      !! for latent heat flux
1956    REAL(r_std),ALLOCATABLE,SAVE,DIMENSION (:)                       :: dswnet        !! net solar radiation
1957    REAL(r_std),ALLOCATABLE,SAVE,DIMENSION (:)                       :: dswdown       !! Incident solar radiation
1958    REAL(r_std),ALLOCATABLE,SAVE,DIMENSION (:,:)                     :: dalbedo       !! albedo
1959    REAL(r_std),ALLOCATABLE,SAVE,DIMENSION (:)                       :: dtair         !! air temperature
1960    REAL(r_std),ALLOCATABLE,SAVE,DIMENSION (:)                       :: dqair         !! specific air humidity
1961    REAL(r_std),ALLOCATABLE,SAVE,DIMENSION (:)                       :: dq2m          !! Surface specific humidity
1962    REAL(r_std),ALLOCATABLE,SAVE,DIMENSION (:)                       :: dt2m          !! Surface air temperature
1963    !
1964    !
1965    INTEGER(i_std)                                        :: i, j, ik
1966    INTEGER(i_std)                                        :: itau_sechiba
1967    REAL(r_std)                                           :: mx, zlev_mean
1968    REAL(r_std), ALLOCATABLE, DIMENSION(:,:)              :: tmp_lon, tmp_lat, tmp_lev
1969    LOGICAL                                               :: do_watch      !! if it's time, write watchout
1970    INTEGER                                               :: old_fileout   !! old Logical Int for std IO output
1971    LOGICAL :: check = .FALSE.
1972    INTEGER(i_std),DIMENSION (kjpindex)                  :: kindex_p
1973    !
1974    LOGICAL, SAVE                                         :: fatmco2       !! Flag to force the value of atmospheric CO2 for vegetation.
1975    REAL(r_std), SAVE                                     :: atmco2        !! atmospheric CO2
1976    !
1977    CALL ipslnlf(old_number=old_fileout)
1978    !
1979    IF (l_first_intersurf) THEN
1980       !
1981       CALL intsurf_time( kjit, date0, xrdt )
1982       !
1983       IF ( check ) WRITE(numout,*) 'Initialisation of intersurf'
1984       !
1985       CALL ioget_calendar (one_year, one_day)
1986       !
1987#ifdef CPP_PARA
1988       CALL init_para(.TRUE.,communicator)
1989       kindex_p(:)=kindex(:) + offset
1990#else
1991       CALL init_para(.FALSE.)
1992       kindex_p(:)=kindex(:)
1993#endif
1994       CALL ipslnlf(new_number=numout)
1995       !
1996       CALL init_data_para(iim_glo,jjm_glo,kjpindex,kindex_p)
1997       iim=iim_glo
1998       jjm=jj_nb
1999       ALLOCATE(lon_scat(iim,jjm))
2000       ALLOCATE(lat_scat(iim,jjm))
2001!       ALLOCATE(dvevapp(iim*jjm))
2002       ALLOCATE(dtemp_sol(iim*jjm))
2003       ALLOCATE(dfluxsens(iim*jjm))
2004       ALLOCATE(dfluxlat(iim*jjm))
2005       ALLOCATE(dswnet(iim*jjm))
2006       ALLOCATE(dswdown(iim*jjm))
2007       ALLOCATE(dalbedo(iim*jjm,2))
2008       ALLOCATE(dtair(iim*jjm))
2009       ALLOCATE(dqair(iim*jjm)) 
2010       ALLOCATE(dq2m(iim*jjm))
2011       ALLOCATE(dt2m(iim*jjm))
2012     
2013!       CALL init_WriteField_p(kindex)
2014       !
2015       ! Allocation of grid variables
2016       !
2017       CALL init_grid ( kjpindex )
2018       !
2019       !  Create the internal coordinate table
2020       !
2021       lalo(:,:) = latlon(:,:)
2022       CALL gather(lalo,lalo_g)
2023       !
2024       !-
2025       !- Store variable to help describe the grid
2026       !- once the points are gathered.
2027       !-
2028       neighbours(:,:) = zneighbours(:,:)
2029       CALL gather(neighbours,neighbours_g)
2030       !
2031       resolution(:,:) = zresolution(:,:)
2032       CALL gather(resolution,resolution_g)
2033       !
2034       area(:) = resolution(:,1)*resolution(:,2)
2035       CALL gather(area,area_g)
2036       !
2037       !- Store the fraction of the continents only once so that the user
2038       !- does not change them afterwards.
2039       !
2040       contfrac(:) = zcontfrac(:)
2041       CALL gather(contfrac,contfrac_g)
2042       !
2043       !
2044       !  Create the internal coordinate table
2045       !
2046       IF ( (.NOT.ALLOCATED(tmp_lon))) THEN
2047          ALLOCATE(tmp_lon(iim,jjm))
2048       ENDIF
2049       IF ( (.NOT.ALLOCATED(tmp_lat))) THEN
2050          ALLOCATE(tmp_lat(iim,jjm))
2051       ENDIF
2052       IF ( (.NOT.ALLOCATED(tmp_lev))) THEN
2053          ALLOCATE(tmp_lev(iim,jjm))
2054       ENDIF
2055       !
2056       !  Either we have the scattered coordinates as arguments or
2057       !  we have to do the work here.
2058       !
2059       IF ( PRESENT(lon_scat_g) .AND. PRESENT(lat_scat_g)) THEN
2060         
2061          lon_scat(:,:)=zero
2062          lat_scat(:,:)=zero 
2063          CALL scatter2D(lon_scat_g,lon_scat)
2064          CALL scatter2D(lat_scat_g,lat_scat)
2065          lon_scat(:,1)=lon_scat(:,2)
2066          lon_scat(:,jj_nb)=lon_scat(:,2)
2067          lat_scat(:,1)=lat_scat(iim,1)
2068          lat_scat(:,jj_nb)=lat_scat(1,jj_nb)
2069         
2070          tmp_lon(:,:) = lon_scat(:,:)
2071          tmp_lat(:,:) = lat_scat(:,:)
2072
2073          IF (is_root_prc) THEN
2074             lon_g(:,:) = lon_scat_g(:,:)
2075             lat_g(:,:) = lat_scat_g(:,:)
2076          ENDIF
2077
2078       ELSE IF ( PRESENT(lon_scat_g) .OR. PRESENT(lat_scat_g)) THEN
2079
2080          WRITE(numout,*) 'You need to provide the longitude AND latitude on the'
2081          WRITE(numout,*) 'gathered grid in order to start ORCHIDEE.'
2082          STOP 'intersurf_gathered'
2083
2084       ELSE
2085          !
2086          WRITE(numout,*) 'intersurf_gathered : We try to guess to full grid of the model.' 
2087          WRITE(numout,*) 'I might fail, please report if it does. '
2088          !
2089          tmp_lon(:,:) = val_exp
2090          tmp_lat(:,:) = val_exp
2091          !
2092          DO ik=1, kjpindex
2093             j = INT( (kindex(ik)-1) / iim ) + 1
2094             i = kindex(ik) - (j-1) * iim
2095             tmp_lon(i,j) = lalo(ik,2)
2096             tmp_lat(i,j) = lalo(ik,1)
2097          ENDDO
2098          !
2099          ! Here we fill out the grid. To do this we do the strong hypothesis
2100          ! that the grid is regular. Will this work in all cases ????
2101          !
2102          DO i=1,iim
2103             mx = MAXVAL(tmp_lon(i,:), MASK=tmp_lon(i,:) .LT. val_exp)
2104             IF ( mx .LT. val_exp ) THEN
2105                tmp_lon(i,:) = mx
2106             ELSE
2107                WRITE(numout,*) 'Could not find a continental point on this longitude. Thus the grid'
2108                WRITE(numout,*) 'could not be completed.'
2109                STOP 'intersurf_gathered'
2110             ENDIF
2111          ENDDO
2112          !
2113          DO j=1,jjm
2114             mx = MAXVAL(tmp_lat(:,j), MASK=tmp_lat(:,j) .LT. val_exp)
2115             IF ( mx .LT. val_exp ) THEN
2116                tmp_lat(:,j) = mx
2117             ELSE
2118                WRITE(numout,*) 'Could not find a continental point on this latitude. Thus the grid'
2119                WRITE(numout,*) 'could not be completed.'
2120                STOP 'intersurf_gathered'
2121             ENDIF
2122          ENDDO
2123
2124          CALL gather2D(tmp_lon,lon_g)
2125          CALL gather2D(tmp_lat,lat_g)
2126
2127       ENDIF
2128       !
2129       DO ik=1, kjpindex
2130          j = INT( (kindex(ik)-1) / iim ) + 1
2131          i = kindex(ik) - (j-1) * iim
2132          tmp_lev(i,j) = zlev(ik)
2133       ENDDO
2134       CALL gather2D(tmp_lev,zlev_g)
2135       !
2136       !
2137       !  Configuration of SSL specific parameters
2138       !
2139       CALL intsurf_config(control_flags,xrdt)
2140       !
2141       !Config  Key  = FORCE_CO2_VEG
2142       !Config  Desc = Flag to force the value of atmospheric CO2 for vegetation.
2143       !Config  Def  = FALSE
2144       !Config  Help = If this flag is set to true, the ATM_CO2 parameter is used
2145       !Config         to prescribe the atmospheric CO2.
2146       !Config         This Flag is only use in couple mode.
2147       !
2148       fatmco2=.FALSE.
2149       CALL getin_p('FORCE_CO2_VEG',fatmco2)
2150       !
2151       ! Next flag is only use in couple mode with a gcm in intersurf.
2152       ! In forced mode, it has already been read and set in driver.
2153       IF ( fatmco2 ) THEN
2154          !Config  Key  = ATM_CO2
2155          !Config  IF   = FORCE_CO2_VEG (in not forced mode)
2156          !Config  Desc = Value for atm CO2
2157          !Config  Def  = 350.
2158          !Config  Help = Value to prescribe the atm CO2.
2159          !Config         For pre-industrial simulations, the value is 286.2 .
2160          !Config         348. for 1990 year.
2161          !
2162          atmco2=350.
2163          CALL getin_p('ATM_CO2',atmco2)
2164          WRITE(numout,*) 'atmco2 ',atmco2
2165       ENDIF
2166       
2167       !
2168       CALL intsurf_restart(kjit, iim, jjm, tmp_lon, tmp_lat, date0, xrdt, control_flags, rest_id, rest_id_stom, itau_offset)
2169       itau_sechiba = kjit + itau_offset
2170       !
2171       CALL intsurf_history(iim, jjm, tmp_lon, tmp_lat, itau_sechiba, &
2172 &                          date0_shifted, xrdt, control_flags, hist_id, hist2_id, hist_id_stom, hist_id_stom_IPCC)
2173       !
2174       IF ( ok_watchout ) THEN
2175          IF (is_root_prc) THEN
2176             zlev_mean = 0.
2177             DO ik=1, nbp_glo
2178                j = ((index_g(ik)-1)/iim_g) + 1
2179                i = (index_g(ik) - (j-1)*iim_g)
2180               
2181                zlev_mean = zlev_mean + zlev_g(i,j)
2182             ENDDO
2183             zlev_mean = zlev_mean / REAL(nbp_glo,r_std)
2184          ENDIF
2185
2186          last_action_watch = itau_sechiba
2187          last_check_watch =  last_action_watch
2188
2189          ! Only root proc write watchout file
2190          CALL watchout_init(iim_g, jjm_g, kjpindex, nbp_glo, &
2191               & date0_shifted, last_action_watch, dt_watch, index_g, lon_g, lat_g, zlev_mean)
2192       ENDIF
2193       !
2194       IF ( check ) WRITE(numout,*) 'End of Initialisation of intersurf'
2195       !
2196    ENDIF
2197    !
2198    CALL ipslnlf(new_number=numout)
2199    !
2200    !  Shift the time step to phase the two models
2201    !
2202    itau_sechiba = kjit + itau_offset
2203    !
2204    CALL intsurf_time( itau_sechiba, date0_shifted, xrdt )
2205    !
2206    ! 1. Just change the units of some input fields
2207    !
2208    DO ik=1, kjpindex
2209       
2210       zprecip_rain(ik) = precip_rain(ik)*xrdt
2211       zprecip_snow(ik) = precip_snow(ik)*xrdt
2212       zcdrag(ik)       = cdrag(ik)
2213       
2214    ENDDO
2215    !
2216    IF (check_INPUTS) THEN
2217       WRITE(numout,*) "Intersurf_main_gathered :"
2218       WRITE(numout,*) "Time step number = ",kjit
2219       WRITE(numout,*) "Dimension of input fields = ",iim, jjm
2220       WRITE(numout,*) "Number of continental points = ",kjpindex
2221       WRITE(numout,*) "Time step in seconds = ",xrdt
2222       WRITE(numout,*) "Logical for _restart_ file to read, write = ",lrestart_read,lrestart_write
2223       WRITE(numout,*) "Date at which kjit = 0  =  ",date0
2224       WRITE(numout,*) "Index for continental points = ",kindex
2225       WRITE(numout,*) "Lowest level wind speed North = ",u
2226       WRITE(numout,*) "Lowest level wind speed East = ",v
2227       WRITE(numout,*) "Height of first layer = ",zlev
2228       WRITE(numout,*) "Lowest level specific humidity = ",qair
2229       WRITE(numout,*) "Rain precipitation = ",zprecip_rain
2230       WRITE(numout,*) "Snow precipitation = ",zprecip_snow
2231       WRITE(numout,*) "Down-welling long-wave flux = ",lwdown
2232       WRITE(numout,*) "Net surface short-wave flux = ",swnet
2233       WRITE(numout,*) "Downwelling surface short-wave flux = ",swdown
2234       WRITE(numout,*) "Air temperature in Kelvin = ",temp_air
2235       WRITE(numout,*) "Air potential energy = ",epot_air
2236       WRITE(numout,*) "CO2 concentration in the canopy = ",ccanopy
2237       WRITE(numout,*) "Coeficients A from the PBL resolution = ",petAcoef
2238       WRITE(numout,*) "One for T and another for q = ",peqAcoef
2239       WRITE(numout,*) "Coeficients B from the PBL resolution = ",petBcoef
2240       WRITE(numout,*) "One for T and another for q = ",peqBcoef
2241       WRITE(numout,*) "Cdrag = ",zcdrag
2242       WRITE(numout,*) "Lowest level pressure = ",pb
2243       WRITE(numout,*) "Geographical coordinates lon = ", lon_scat
2244       WRITE(numout,*) "Geographical coordinates lat = ", lat_scat 
2245       WRITE(numout,*) "Fraction of continent in the grid = ",zcontfrac
2246    ENDIF
2247    !
2248    ! 2. modification of co2
2249    !
2250    IF ( fatmco2 ) THEN
2251       zccanopy(:) = atmco2
2252       WRITE (numout,*) 'Modification of the ccanopy value. CO2 = ',atmco2
2253    ELSE
2254       zccanopy(:) = ccanopy(:)
2255    ENDIF
2256    !
2257    ! 3. save the grid
2258    !
2259    IF ( check ) WRITE(numout,*) 'Save the grid'
2260    !
2261    IF (l_first_intersurf) THEN
2262       CALL histwrite(hist_id, 'LandPoints',  itau_sechiba+1, (/ ( REAL(ik), ik=1,kjpindex ) /), kjpindex, kindex)
2263       CALL histwrite(hist_id, 'Areas',  itau_sechiba+1, area, kjpindex, kindex)
2264       IF ( control_flags%ok_stomate ) THEN
2265          CALL histwrite(hist_id_stom, 'Areas',  itau_sechiba+1, area, kjpindex, kindex)
2266          IF ( hist_id_stom_ipcc > 0 ) &
2267               CALL histwrite(hist_id_stom_IPCC, 'Areas',  itau_sechiba+1, area, kjpindex, kindex)
2268       ENDIF
2269       CALL histwrite(hist_id, 'Contfrac',  itau_sechiba+1, contfrac, kjpindex, kindex)
2270       CALL histsync(hist_id)
2271       !
2272       IF ( hist2_id > 0 ) THEN
2273          CALL histwrite(hist2_id, 'LandPoints',  itau_sechiba+1, (/ ( REAL(ik), ik=1,kjpindex ) /), kjpindex, kindex)
2274          CALL histwrite(hist2_id, 'Areas',  itau_sechiba+1, area, kjpindex, kindex)
2275          CALL histwrite(hist2_id, 'Contfrac',  itau_sechiba+1, contfrac, kjpindex, kindex)
2276          CALL histsync(hist2_id)
2277       ENDIF
2278       !
2279    ENDIF
2280    !
2281    ! 4. call sechiba for continental points only
2282    !
2283    IF ( check ) WRITE(numout,*) 'Calling sechiba'
2284    !
2285    CALL sechiba_main (itau_sechiba, iim*jjm, kjpindex, kindex, xrdt, date0_shifted, &
2286       & lrestart_read, lrestart_write, control_flags, &
2287       & lalo, contfrac, neighbours, resolution, &
2288! First level conditions
2289! Ajout Nathalie - Juin 2006 - passage q2m/t2m pour calcul rveget
2290!       & zlev, u, v, qair, temp_air, epot_air, ccanopy, &
2291       & zlev, u, v, qair, q2m, t2m, temp_air, epot_air, zccanopy, &
2292! Variables for the implicit coupling
2293       & zcdrag, petAcoef, peqAcoef, petBcoef, peqBcoef, &
2294! Rain, snow, radiation and surface pressure
2295       & zprecip_rain ,zprecip_snow,  lwdown, swnet, swdown, pb, &
2296! Output : Fluxes
2297       & zvevapp, zfluxsens, zfluxlat, zcoastal, zriver, &
2298! Surface temperatures and surface properties
2299       & ztsol_rad, ztemp_sol_new, zqsurf, zalbedo, zemis, zz0, &
2300! File ids
2301       & rest_id, hist_id, hist2_id, rest_id_stom, hist_id_stom, hist_id_stom_IPCC ) 
2302   
2303    !
2304    IF ( check ) WRITE(numout,*) 'out of SECHIBA'
2305    !
2306    ! 5. save watchout
2307    !
2308    IF ( ok_watchout .AND. .NOT. l_first_intersurf ) THEN
2309       ! Accumulate last time step
2310       sum_zlev(:) = sum_zlev(:) + zlev(:)
2311       sum_u(:) = sum_u(:) + u(:)
2312       sum_v(:) = sum_v(:) + v(:)
2313       sum_qair(:) = sum_qair(:) + qair(:) 
2314       sum_temp_air(:) = sum_temp_air(:) + temp_air(:)
2315       sum_epot_air(:) = sum_epot_air(:) + epot_air(:)
2316       sum_ccanopy(:) = sum_ccanopy(:) + ccanopy(:)
2317       sum_cdrag(:) = sum_cdrag(:) + zcdrag(:)
2318       sum_petAcoef(:) = sum_petAcoef(:) + petAcoef(:)
2319       sum_peqAcoef(:) = sum_peqAcoef(:) + peqAcoef(:)
2320       sum_petBcoef(:) = sum_petBcoef(:) + petBcoef(:)
2321       sum_peqBcoef(:) = sum_peqBcoef(:) + peqBcoef(:)
2322       sum_rain(:) = sum_rain(:) + zprecip_rain(:)
2323       sum_snow(:) = sum_snow(:) + zprecip_snow(:)
2324       sum_lwdown(:) = sum_lwdown(:) + lwdown(:)
2325       sum_pb(:) = sum_pb(:) + pb(:)
2326
2327!!$       IF ( dt_watch > 3600 ) THEN
2328!!$          julian_watch = date0_shifted+((itau_sechiba-0.5)/dt_split_watch)*dt_watch/one_day
2329!!$          CALL solarang (julian_watch, julian0, iim, jjm, tmp_lon, tmp_lat, sinang)
2330!!$          WHERE ( sinang(:,:) .LT. EPSILON(1.) )
2331!!$             isinang(:,:) = isinang(:,:) - 1
2332!!$          ENDWHERE
2333!!$          mean_sinang(:,:) = mean_sinang(:,:)+sinang(:,:)
2334!!$          !
2335!!$          DO ik=1,kjpindex         
2336!!$             j = ((kindex(ik)-1)/iim) + 1
2337!!$             i = (kindex(ik) - (j-1)*iim)
2338!!$             
2339!!$             sum_swnet(ik) = sum_swnet(ik) + sinang(i,j)*swnet(ik)
2340!!$             sum_swdown(ik) = sum_swdown(ik) + sinang(i,j)*swdown(ik)
2341!!$          ENDDO
2342!!$       ELSE
2343          sum_swnet(:) = sum_swnet(:) + swnet(:)
2344          sum_swdown(:) = sum_swdown(:) + swdown(:)
2345!!$       ENDIF
2346         
2347       do_watch = .FALSE.
2348       call isittime &
2349            &  (itau_sechiba,date0_shifted,xrdt,dt_watch,&
2350            &   last_action_watch,last_check_watch,do_watch)
2351       last_check_watch = itau_sechiba
2352       IF (do_watch) THEN
2353          !
2354          IF ( check ) WRITE(numout,*) 'save watchout'
2355          !
2356          IF (long_print) THEN
2357             WRITE(numout,*) "intersurf : write watchout for date ",date0,date0_shifted,itau_sechiba, &
2358                  & last_action_watch,last_check_watch
2359          ENDIF
2360          last_action_watch = itau_sechiba
2361
2362          sum_zlev(:) = sum_zlev(:) / dt_split_watch
2363          sum_u(:) = sum_u(:) / dt_split_watch
2364          sum_v(:) = sum_v(:) / dt_split_watch
2365          sum_qair(:) = sum_qair(:) / dt_split_watch
2366          sum_temp_air(:) = sum_temp_air(:) / dt_split_watch
2367          sum_epot_air(:) = sum_epot_air(:) / dt_split_watch
2368          sum_ccanopy(:) = sum_ccanopy(:) / dt_split_watch
2369          sum_cdrag(:) = sum_cdrag(:) / dt_split_watch
2370          sum_petAcoef(:) = sum_petAcoef(:) / dt_split_watch
2371          sum_peqAcoef(:) = sum_peqAcoef(:) / dt_split_watch
2372          sum_petBcoef(:) = sum_petBcoef(:) / dt_split_watch
2373          sum_peqBcoef(:) = sum_peqBcoef(:) / dt_split_watch
2374          sum_rain(:) = sum_rain(:) / dt_split_watch
2375          sum_snow(:) = sum_snow(:) / dt_split_watch
2376          sum_lwdown(:) = sum_lwdown(:) / dt_split_watch
2377          sum_pb(:) = sum_pb(:) / dt_split_watch
2378
2379!!$          IF ( dt_watch > 3600 ) THEN
2380!!$             WHERE ( isinang(:,:) .GT. 0 )
2381!!$                mean_sinang(:,:) = mean_sinang(:,:) / isinang(:,:)
2382!!$             ENDWHERE
2383!!$             !
2384!!$             DO ik=1,kjpindex         
2385!!$                j = ((kindex(ik)-1)/iim) + 1
2386!!$                i = (kindex(ik) - (j-1)*iim)
2387!!$                IF (mean_sinang(i,j) > zero) THEN
2388!!$                   sum_swdown(ik) = sum_swdown(ik)/mean_sinang(i,j)
2389!!$                   sum_swnet(ik) =  sum_swnet(ik)/mean_sinang(i,j)
2390!!$                ELSE
2391!!$                   sum_swdown(ik) = zero
2392!!$                   sum_swnet(ik) =  zero
2393!!$                ENDIF
2394!!$             ENDDO
2395!!$          ELSE
2396             sum_swnet(:) = sum_swnet(:) / dt_split_watch
2397             sum_swdown(:) = sum_swdown(:) / dt_split_watch
2398!!$          ENDIF
2399
2400          CALL watchout_write_p(kjpindex, itau_sechiba, xrdt, sum_zlev, sum_swdown, sum_rain, &
2401               &   sum_snow, sum_lwdown, sum_pb, sum_temp_air, sum_epot_air, sum_qair, &
2402               &   sum_u, sum_v, sum_swnet, sum_petAcoef, sum_peqAcoef, sum_petBcoef, sum_peqBcoef, &
2403               &   sum_cdrag, sum_ccanopy )
2404       ENDIF       
2405    ENDIF
2406    !
2407    ! 6. scatter output fields
2408    !
2409    z0(:)           = undef_sechiba
2410    coastalflow(:)  = undef_sechiba
2411    riverflow(:)    = undef_sechiba
2412    tsol_rad(:)     = undef_sechiba
2413    vevapp(:)       = undef_sechiba
2414    temp_sol_new(:) = undef_sechiba
2415    qsurf(:)        = undef_sechiba
2416    albedo(:,1)     = undef_sechiba
2417    albedo(:,2)     = undef_sechiba
2418    fluxsens(:)     = undef_sechiba
2419    fluxlat(:)      = undef_sechiba
2420    emis(:)         = undef_sechiba
2421    cdrag(:)        = undef_sechiba
2422    !   
2423!    dvevapp(:)    = undef_sechiba
2424    dtemp_sol(:)  = undef_sechiba
2425    dfluxsens(:)  = undef_sechiba
2426    dfluxlat(:)   = undef_sechiba
2427    dswnet (:)    = undef_sechiba
2428    dswdown (:)   = undef_sechiba
2429    dalbedo (:,1) = undef_sechiba
2430    dalbedo (:,2) = undef_sechiba
2431    dtair (:)     = undef_sechiba
2432    dqair (:)     = undef_sechiba
2433    dt2m (:)      = undef_sechiba
2434    dq2m (:)      = undef_sechiba
2435    !
2436    DO ik=1, kjpindex
2437       
2438       z0(ik)           = zz0(ik)
2439       coastalflow(ik)  = zcoastal(ik)/1000.
2440       riverflow(ik)    = zriver(ik)/1000.
2441       tsol_rad(ik)     = ztsol_rad(ik)
2442       vevapp(ik)       = zvevapp(ik)
2443       temp_sol_new(ik) = ztemp_sol_new(ik)
2444       qsurf(ik)        = zqsurf(ik)
2445       albedo(ik,1)     = zalbedo(ik,1)
2446       albedo(ik,2)     = zalbedo(ik,2)
2447       fluxsens(ik)     = zfluxsens(ik)
2448       fluxlat(ik)      = zfluxlat(ik)
2449       emis(ik)         = zemis(ik)
2450       cdrag(ik)        = zcdrag(ik)
2451       
2452       ! Fill up the diagnostic arrays
2453
2454!       dvevapp(kindex(ik))    = zvevapp(ik)
2455       dtemp_sol(kindex(ik))  = ztemp_sol_new(ik)
2456       dfluxsens(kindex(ik))  = zfluxsens(ik)
2457       dfluxlat(kindex(ik))   = zfluxlat(ik)
2458       dswnet (kindex(ik))    = swnet(ik)
2459       dswdown (kindex(ik))   = swdown(ik)
2460       dalbedo (kindex(ik),1) = zalbedo(ik,1)
2461       dalbedo (kindex(ik),2) = zalbedo(ik,2)   
2462       dtair (kindex(ik))     = temp_air(ik)
2463       dqair (kindex(ik))     = qair(ik)
2464       dt2m (kindex(ik))      = t2m(ik)
2465       dq2m (kindex(ik))      = q2m(ik)
2466       !
2467    ENDDO
2468    !
2469    ! Modified fields for variables scattered during the writing
2470    !
2471    dcoastal(:) = (zcoastal(:))/1000.
2472    driver(:)   = (zriver(:))/1000.
2473    !
2474    IF ( .NOT. l_first_intersurf) THEN
2475       !
2476       IF ( .NOT. almaoutput ) THEN
2477          !
2478          !  scattered during the writing
2479          !           
2480          CALL histwrite (hist_id, 'evap',     itau_sechiba, zvevapp, kjpindex, kindex)
2481          CALL histwrite (hist_id, 'coastalflow',itau_sechiba, dcoastal, kjpindex, kindex)
2482          CALL histwrite (hist_id, 'riverflow',itau_sechiba, driver, kjpindex, kindex)
2483          !
2484          CALL histwrite (hist_id, 'temp_sol', itau_sechiba, dtemp_sol, iim*jjm, kindex)
2485          CALL histwrite (hist_id, 'tsol_max', itau_sechiba, dtemp_sol, iim*jjm, kindex)
2486          CALL histwrite (hist_id, 'tsol_min', itau_sechiba, dtemp_sol, iim*jjm, kindex)
2487          CALL histwrite (hist_id, 'fluxsens', itau_sechiba, dfluxsens, iim*jjm, kindex)
2488          CALL histwrite (hist_id, 'fluxlat',  itau_sechiba, dfluxlat,  iim*jjm, kindex)
2489          CALL histwrite (hist_id, 'swnet',    itau_sechiba, dswnet,    iim*jjm, kindex)
2490          CALL histwrite (hist_id, 'swdown',   itau_sechiba, dswdown,   iim*jjm, kindex)
2491          CALL histwrite (hist_id, 'alb_vis',  itau_sechiba, dalbedo(:,1), iim*jjm, kindex)
2492          CALL histwrite (hist_id, 'alb_nir',  itau_sechiba, dalbedo(:,2), iim*jjm, kindex)
2493          CALL histwrite (hist_id, 'tair',     itau_sechiba, dtair, iim*jjm, kindex)
2494          CALL histwrite (hist_id, 'qair',     itau_sechiba, dqair, iim*jjm, kindex)
2495          CALL histwrite (hist_id, 't2m',      itau_sechiba, dq2m, iim*jjm, kindex)
2496          CALL histwrite (hist_id, 'q2m',      itau_sechiba, dt2m, iim*jjm, kindex)
2497          !
2498          IF ( hist2_id > 0 ) THEN
2499             CALL histwrite (hist2_id, 'evap',     itau_sechiba, zvevapp, kjpindex, kindex)
2500             CALL histwrite (hist2_id, 'coastalflow',itau_sechiba, dcoastal, kjpindex, kindex)
2501             CALL histwrite (hist2_id, 'riverflow',itau_sechiba, driver, kjpindex, kindex)
2502             !
2503             CALL histwrite (hist2_id, 'temp_sol', itau_sechiba, dtemp_sol, iim*jjm, kindex)
2504             CALL histwrite (hist2_id, 'tsol_max', itau_sechiba, dtemp_sol, iim*jjm, kindex)
2505             CALL histwrite (hist2_id, 'tsol_min', itau_sechiba, dtemp_sol, iim*jjm, kindex)
2506             CALL histwrite (hist2_id, 'fluxsens', itau_sechiba, dfluxsens, iim*jjm, kindex)
2507             CALL histwrite (hist2_id, 'fluxlat',  itau_sechiba, dfluxlat,  iim*jjm, kindex)
2508             CALL histwrite (hist2_id, 'swnet',    itau_sechiba, dswnet,    iim*jjm, kindex)
2509             CALL histwrite (hist2_id, 'swdown',   itau_sechiba, dswdown,   iim*jjm, kindex)
2510             CALL histwrite (hist2_id, 'alb_vis',  itau_sechiba, dalbedo(:,1), iim*jjm, kindex)
2511             CALL histwrite (hist2_id, 'alb_nir',  itau_sechiba, dalbedo(:,2), iim*jjm, kindex)
2512             CALL histwrite (hist2_id, 'tair',     itau_sechiba, dtair, iim*jjm, kindex)
2513             CALL histwrite (hist2_id, 'qair',     itau_sechiba, dqair, iim*jjm, kindex)
2514             CALL histwrite (hist2_id, 't2m',      itau_sechiba, dq2m, iim*jjm, kindex)
2515             CALL histwrite (hist2_id, 'q2m',      itau_sechiba, dt2m, iim*jjm, kindex)
2516          ENDIF
2517       ELSE
2518          CALL histwrite (hist_id, 'Evap', itau_sechiba, zvevapp, kjpindex, kindex)
2519          CALL histwrite (hist_id, 'SWnet',    itau_sechiba, dswnet, iim*jjm, kindex)
2520          CALL histwrite (hist_id, 'Qh', itau_sechiba, dfluxsens, iim*jjm, kindex)
2521          CALL histwrite (hist_id, 'Qle',  itau_sechiba, dfluxlat, iim*jjm, kindex)
2522          CALL histwrite (hist_id, 'AvgSurfT', itau_sechiba, dtemp_sol, iim*jjm, kindex)
2523          CALL histwrite (hist_id, 'RadT', itau_sechiba, dtemp_sol, iim*jjm, kindex)
2524          !
2525          IF ( hist2_id > 0 ) THEN
2526             CALL histwrite (hist2_id, 'Evap', itau_sechiba, zvevapp, kjpindex, kindex)
2527             CALL histwrite (hist2_id, 'SWnet',    itau_sechiba, dswnet, iim*jjm, kindex)
2528             CALL histwrite (hist2_id, 'Qh', itau_sechiba, dfluxsens, iim*jjm, kindex)
2529             CALL histwrite (hist2_id, 'Qle',  itau_sechiba, dfluxlat, iim*jjm, kindex)
2530             CALL histwrite (hist2_id, 'AvgSurfT', itau_sechiba, dtemp_sol, iim*jjm, kindex)
2531             CALL histwrite (hist2_id, 'RadT', itau_sechiba, dtemp_sol, iim*jjm, kindex)
2532          ENDIF
2533       ENDIF
2534       !
2535       IF (dw .EQ. xrdt) THEN
2536          CALL histsync(hist_id)
2537       ENDIF
2538    !
2539    ENDIF
2540    !
2541    ! 7. Transform the water fluxes into Kg/m^2s and m^3/s
2542    !
2543    DO ik=1, kjpindex
2544
2545       vevapp(ik) = vevapp(ik)/xrdt
2546       coastalflow(ik) = coastalflow(ik)/xrdt
2547       riverflow(ik) = riverflow(ik)/xrdt
2548
2549    ENDDO
2550    !
2551    IF ( lrestart_write .AND. ok_watchout .AND. is_root_prc ) THEN
2552       CALL watchout_close()
2553    ENDIF
2554    !
2555    IF(l_first_intersurf .AND. is_root_prc) CALL getin_dump
2556    l_first_intersurf = .FALSE.
2557    !
2558    IF (long_print) WRITE (numout,*) ' intersurf_main done '
2559    !
2560    CALL ipslnlf(new_number=old_fileout)
2561    !       
2562  END SUBROUTINE intersurf_gathered_2m
2563!
2564  !-------------------------------------------------------------------------------------
2565  !
2566  SUBROUTINE intsurf_time(istp, date0, dt)
2567    !
2568    !  This subroutine initialized the time global variables in grid module.
2569    !
2570    IMPLICIT NONE
2571    !
2572    INTEGER(i_std), INTENT(in)                  :: istp      !! Time step of the restart file
2573    REAL(r_std), INTENT(in)                     :: date0     !! The date at which itau = 0
2574    REAL(r_std), INTENT(in)                     :: dt        !! Time step
2575    !
2576    ! LOCAL
2577    LOGICAL     :: check=.FALSE.
2578
2579    IF (l_first_intersurf) THEN
2580       CALL ioget_calendar(calendar_str)
2581       CALL ioget_calendar(one_year, one_day)
2582       CALL tlen2itau('1Y',dt,date0,year_length)
2583       IF ( TRIM(calendar_str) .EQ. 'gregorian' ) THEN 
2584          year_spread=1.0
2585       ELSE
2586          year_spread = one_year/365.2425
2587       ENDIF
2588
2589       IF (check) THEN
2590          write(numout,*) "calendar_str =",calendar_str
2591          write(numout,*) "one_year=",one_year,", one_day=",one_day
2592          write(numout,*) "dt=",dt,", date0=",date0,", year_length=",year_length,", year_spread=",year_spread
2593       ENDIF
2594    ENDIF
2595
2596    !
2597    IF (check) &
2598         WRITE(numout,*) "---" 
2599    ! Dans diffuco (ie date0 == date0_shift !!)
2600
2601    IF ( TRIM(calendar_str) .EQ. 'gregorian' ) THEN 
2602       !
2603       ! Get Julian date
2604       in_julian = itau2date(istp, date0, dt)
2605
2606       ! Real date
2607       CALL ju2ymds (in_julian, year, month, day, sec)
2608!!$       jur=0.
2609!!$       julian_diff = in_julian
2610!!$       month_len = ioget_mon_len (year,month)
2611!!$       IF (check) THEN
2612!!$          write(numout,*) "in_julian, jur, julian_diff=",in_julian, jur, julian_diff
2613!!$          write(numout,*) 'DATE ymds', year, month,'(',month_len,'d)', day, sec, '-- stp --', istp
2614!!$       ENDIF
2615
2616       ! julian number for january, the first.
2617       CALL ymds2ju (year,1,1,zero, julian0)
2618       julian_diff = in_julian-julian0
2619       ! real number of seconds
2620!       sec = (julian_diff-REAL(INT(julian_diff)))*one_day
2621       sec = NINT((julian_diff-REAL(INT(julian_diff)))*one_day)
2622       month_len = ioget_mon_len (year,month)
2623       IF (check) THEN
2624          write(numout,*) "2 in_julian, julian0, julian_diff=",in_julian, julian0, julian_diff
2625          write(numout,*) '2 DATE ymds', year, month,'(',month_len,'d)', day, sec, '-- stp --', istp
2626       ENDIF
2627    ELSE 
2628!!$       in_julian = itau2date(istp-1, 0., dt)
2629!!$       CALL ju2ymds (in_julian, year, month, day, sec)
2630!!$       jur=0.
2631!!$       julian_diff = in_julian
2632!!$       month_len = ioget_mon_len (year,month)
2633!!$       IF (check) THEN
2634!!$          write(numout,*) "in_julian=",in_julian, jur, julian_diff
2635!!$          write(numout,*) 'DATE ymds', year, month,'(',month_len,'d)', day, sec, '-- stp --', istp
2636!!$       ENDIF
2637!!$
2638!!$
2639!!$       CALL ymds2ju (year,1,1,zero, jur)
2640!!$       julian_diff = in_julian-jur
2641!!$       CALL ju2ymds (julian_diff, year, month, day, sec)
2642!!$!       sec = (julian_diff-REAL(INT(julian_diff)))*one_day
2643!!$       sec = NINT((julian_diff-REAL(INT(julian_diff)))*one_day)
2644!!$       month_len = ioget_mon_len (year,month)
2645!!$       IF (check) THEN
2646!!$          write(numout,*) "2 in_julian, jur, julian_diff=",in_julian, jur, julian_diff
2647!!$          write(numout,*) '2 DATE ymds', year, month,'(',month_len,'d)', day, sec, '-- stp --', istp
2648!!$       ENDIF
2649
2650
2651!!$       IF (check) &
2652!!$            WRITE(numout,*) "-"
2653
2654!MM
2655!PB date0 = celui de Soenke (à tester avec un autre date0)
2656!       in_julian = itau2date(istp, 153116., dt)
2657       in_julian = itau2date(istp, date0, dt)
2658       CALL itau2ymds(istp, dt, year, month, day, sec)
2659       CALL ymds2ju (year,1,1,zero, julian0)
2660       julian_diff = in_julian
2661       month_len = ioget_mon_len (year,month)
2662       IF (check) THEN
2663          write(numout,*) "in_julian=",in_julian, julian0, julian_diff
2664          write(numout,*) 'DATE ymds', year, month,'(',month_len,'d)', day, sec, '-- stp --', istp
2665       ENDIF
2666    ENDIF
2667!!$    IF (check) &
2668!!$         WRITE(numout,*) "---"
2669
2670  END SUBROUTINE intsurf_time
2671!
2672
2673!-------------------------------------------------------------------------------------
2674!
2675  SUBROUTINE intsurf_config(control_flags,dt)
2676    !
2677    !  This subroutine reads all the configuration flags which control the behaviour of the model
2678    !
2679    IMPLICIT NONE
2680    !
2681    REAL, INTENT(in)                           :: dt            !! Time step in seconds
2682    !
2683    TYPE(control_type), INTENT(out)            :: control_flags !! Flags that (de)activate parts of the model
2684
2685    !
2686    !Config Key  = LONGPRINT
2687    !Config Desc = ORCHIDEE will print more messages
2688    !Config Def  = n
2689    !Config Help = This flag permits to print more debug messages in the run.
2690    !
2691    long_print = .FALSE.
2692    CALL getin_p('LONGPRINT',long_print)
2693    !
2694    !
2695    !Config Key  = ORCHIDEE_WATCHOUT
2696    !Config Desc = ORCHIDEE will write out its forcing to a file
2697    !Config Def  = n
2698    !Config Help = This flag allows to write to a file all the variables
2699    !Config        which are used to force the land-surface. The file
2700    !Config        has exactly the same format than a normal off-line forcing
2701    !Config        and thus this forcing can be used for forcing ORCHIDEE.
2702    !
2703    ok_watchout = .FALSE.
2704    CALL getin_p('ORCHIDEE_WATCHOUT',ok_watchout)
2705    !
2706    IF (ok_watchout) THEN
2707       !Config Key  = DT_WATCHOUT
2708       !Config Desc = ORCHIDEE will write out with this frequency
2709       !Config IF   = ORCHIDEE_WATCHOUT
2710       !Config Def  = dt
2711       !Config Help = This flag indicates the frequency of the write of the variables.
2712       !
2713       dt_watch = dt
2714       CALL getin('DT_WATCHOUT',dt_watch)
2715       dt_split_watch = dt_watch / dt
2716       !
2717       !Config Key  = WATCHOUT_FILE
2718       !Config Desc = Filenane for the ORCHIDEE forcing file
2719       !Config IF   = ORCHIDEE_WATCHOUT
2720       !Config Def  = orchidee_watchout.nc
2721       !Config Help = This is the name of the file in which the
2722       !Config        forcing used here will be written for later use.
2723       !
2724       watchout_file = "orchidee_watchout.nc"
2725       CALL getin_p('WATCHOUT_FILE',watchout_file)
2726       
2727       WRITE(numout,*) 'WATCHOUT flag :', ok_watchout
2728       WRITE(numout,*) 'WATCHOUT file :', watchout_file
2729    ENDIF
2730    !
2731    !Config Key  = RIVER_ROUTING
2732    !Config Desc = Decides if we route the water or not
2733    !Config Def  = n
2734    !Config Help = This flag allows the user to decide if the runoff
2735    !Config        and drainage should be routed to the ocean
2736    !Config        and to downstream grid boxes.
2737    !
2738    control_flags%river_routing = .FALSE.
2739    CALL getin_p('RIVER_ROUTING', control_flags%river_routing)
2740    WRITE(numout,*) "RIVER routing is activated : ",control_flags%river_routing
2741    !
2742    !Config key = HYDROL_CWRR
2743    !Config Desc = Allows to switch on the multilayer hydrology of CWRR
2744    !Config Def  = n
2745    !Config Help = This flag allows the user to decide if the vertical
2746    !Config        hydrology should be treated using the multi-layer
2747    !Config        diffusion scheme adapted from CWRR by Patricia de Rosnay.
2748    !Config        by default the Choisnel hydrology is used.
2749    !
2750    control_flags%hydrol_cwrr = .FALSE.
2751    CALL getin_p('HYDROL_CWRR', control_flags%hydrol_cwrr)
2752    IF ( control_flags%hydrol_cwrr ) then
2753       CALL ipslerr (2,'intsurf_config', &
2754            &          'You will use in this run the second version of CWRR hydrology in ORCHIDEE.',&
2755            &          'This model hasn''t been tested for global run yet.', &
2756            &          '(check your parameters)')
2757    ENDIF
2758    !
2759    !Config Key  = STOMATE_OK_CO2
2760    !Config Desc = Activate CO2?
2761    !Config Def  = n
2762    !Config Help = set to TRUE if photosynthesis is to be activated
2763    !
2764    control_flags%ok_co2 = .FALSE.
2765    CALL getin_p('STOMATE_OK_CO2', control_flags%ok_co2)
2766    WRITE(numout,*) 'photosynthesis: ', control_flags%ok_co2
2767    !
2768    !Config Key  = STOMATE_OK_STOMATE
2769    !Config Desc = Activate STOMATE?
2770    !Config Def  = n
2771    !Config Help = set to TRUE if STOMATE is to be activated
2772    !
2773    control_flags%ok_stomate = .FALSE.
2774    CALL getin_p('STOMATE_OK_STOMATE',control_flags%ok_stomate)
2775    WRITE(numout,*) 'STOMATE is activated: ',control_flags%ok_stomate
2776    !
2777    !Config Key  = STOMATE_OK_DGVM
2778    !Config Desc = Activate DGVM?
2779    !Config Def  = n
2780    !Config Help = set to TRUE if DGVM is to be activated
2781    !
2782    control_flags%ok_dgvm = .FALSE.
2783    CALL getin_p('STOMATE_OK_DGVM',control_flags%ok_dgvm)
2784
2785    IF ( control_flags%ok_dgvm ) THEN
2786       WRITE(numout,*) 'You try to use LPJ ',control_flags%ok_dgvm, &
2787            ' with this version. '
2788       WRITE(numout,*) 'It is not possible because it has to be modified ', &
2789            ' to give correct values.'
2790       CALL ipslerr (3,'intsurf_config', &
2791         &          'Use of STOMATE_OK_DGVM not allowed with this version.',&
2792         &          'ORCHIDEE will stop.', &
2793         &          'Please disable DGVM to use this version of ORCHIDEE.')
2794    ENDIF
2795    !
2796    ! control initialisation with sechiba
2797    !
2798    control_flags%ok_sechiba = .TRUE.
2799    !
2800    !
2801    ! Ensure consistency
2802    !
2803    IF ( control_flags%ok_dgvm ) control_flags%ok_stomate = .TRUE.
2804    IF ( control_flags%ok_stomate ) control_flags%ok_co2 = .TRUE.
2805    !
2806    !Config Key  = STOMATE_WATCHOUT
2807    !Config Desc = STOMATE does minimum service
2808    !Config Def  = n
2809    !Config Help = set to TRUE if you want STOMATE to read
2810    !Config        and write its start files and keep track
2811    !Config        of longer-term biometeorological variables.
2812    !Config        This is useful if OK_STOMATE is not set,
2813    !Config        but if you intend to activate STOMATE later.
2814    !Config        In that case, this run can serve as a
2815    !Config        spinup for longer-term biometeorological
2816    !Config        variables.
2817    !
2818    control_flags%stomate_watchout = .FALSE.
2819    CALL getin_p('STOMATE_WATCHOUT',control_flags%stomate_watchout)
2820    WRITE(numout,*) 'STOMATE keeps an eye open: ',control_flags%stomate_watchout
2821    !
2822    ! Here we need the same initialisation as above
2823    !
2824    control_flags%ok_pheno = .TRUE.
2825    !
2826    !
2827    RETURN
2828    !
2829  END SUBROUTINE intsurf_config
2830  !
2831  !
2832  !
2833  SUBROUTINE intsurf_restart(istp, iim, jjm, lon, lat, date0, dt, control_flags, rest_id, rest_id_stom, itau_offset)
2834    !
2835    !  This subroutine initialized the restart file for the land-surface scheme
2836    !
2837    IMPLICIT NONE
2838    !
2839    INTEGER(i_std), INTENT(in)                  :: istp      !! Time step of the restart file
2840    INTEGER(i_std), INTENT(in)                  :: iim, jjm  !! Size in x and y of the data to be handeled
2841    REAL(r_std),DIMENSION (iim,jjm), INTENT(in) :: lon, lat  !! Logitude and latitude of the data points
2842    REAL(r_std)                                 :: date0     !! The date at which itau = 0
2843    REAL(r_std)                                 :: dt        !! Time step
2844    INTEGER(i_std), INTENT(out)                 :: rest_id, rest_id_stom   !! ID of the restart file
2845    INTEGER(i_std), INTENT(out)                 :: itau_offset
2846    !
2847    TYPE(control_type), INTENT(in)             :: control_flags !! Flags that (de)activate parts of the model
2848    !
2849    !  LOCAL
2850    !
2851    CHARACTER(LEN=80)          :: restname_in, restname_out, stom_restname_in, stom_restname_out
2852    REAL(r_std)                 :: dt_rest, date0_rest
2853    INTEGER(i_std)              :: itau_dep
2854    INTEGER(i_std),PARAMETER    :: llm=1
2855    REAL(r_std), DIMENSION(llm) :: lev
2856    LOGICAL                    :: overwrite_time
2857    REAL(r_std)                 :: in_julian, rest_julian
2858    INTEGER(i_std)              :: yy, mm, dd
2859    REAL(r_std)                 :: ss
2860    !
2861    !Config  Key  = SECHIBA_restart_in
2862    !Config  Desc = Name of restart to READ for initial conditions
2863    !Config  Def  = NONE
2864    !Config  Help = This is the name of the file which will be opened
2865    !Config         to extract the initial values of all prognostic
2866    !Config         values of the model. This has to be a netCDF file.
2867    !Config         Not truly COADS compliant. NONE will mean that
2868    !Config         no restart file is to be expected.
2869!-
2870    restname_in = 'NONE'
2871    CALL getin_p('SECHIBA_restart_in',restname_in)
2872    WRITE(numout,*) 'INPUT RESTART_FILE', restname_in
2873    !-
2874    !Config Key  = SECHIBA_rest_out
2875    !Config Desc = Name of restart files to be created by SECHIBA
2876    !Config Def  = sechiba_rest_out.nc
2877    !Config Help = This variable give the name for
2878    !Config        the restart files. The restart software within
2879    !Config        IOIPSL will add .nc if needed.
2880    !
2881    restname_out = 'restart_out.nc'
2882    CALL getin_p('SECHIBA_rest_out', restname_out)
2883    !
2884    !Config Key  = SECHIBA_reset_time
2885    !Config Desc = Option to overrides the time of the restart
2886    !Config Def  = n
2887    !Config Help = This option allows the model to override the time
2888    !Config        found in the restart file of SECHIBA with the time
2889    !Config        of the first call. That is the restart time of the GCM.
2890    !
2891    overwrite_time = .FALSE.
2892    CALL getin_p('SECHIBA_reset_time', overwrite_time)
2893    !
2894    lev(:) = 0.
2895    itau_dep = istp
2896    in_julian = itau2date(istp, date0, dt)
2897    date0_rest = date0
2898    dt_rest = dt
2899    !
2900    IF (is_root_prc) THEN
2901      CALL restini( restname_in, iim_g, jjm_g, lon_g, lat_g, llm, lev, &
2902         &  restname_out, itau_dep, date0_rest, dt_rest, rest_id, overwrite_time)
2903    ELSE
2904       rest_id=0
2905    ENDIF
2906    CALL bcast (itau_dep)
2907    CALL bcast (date0_rest)
2908    CALL bcast (dt_rest)
2909    !
2910    !  itau_dep of SECHIBA is phased with the GCM if needed
2911    !
2912    rest_julian = itau2date(itau_dep, date0_rest, dt_rest)
2913    !
2914    IF ( ABS( in_julian - rest_julian) .GT. dt/one_day .AND. .NOT. OFF_LINE_MODE ) THEN
2915       IF ( overwrite_time ) THEN
2916          WRITE(numout,*) 'The SECHIBA restart is not for the same timestep as the GCM,'
2917          WRITE(numout,*) 'the two are synchronized. The land-surface conditions can not impose'
2918          WRITE(numout,*) 'the chronology of the simulation.'
2919          WRITE(numout,*) 'Time step of the GCM :', istp, 'Julian day : ', in_julian
2920          CALL ju2ymds(in_julian, yy, mm, dd, ss)
2921          WRITE(numout,*) 'In other word (yy,mm,dd,ss) : ', yy, mm, dd, ss
2922          WRITE(numout,*) 'Time step of SECHIBA :', itau_dep, 'Julian day : ', rest_julian
2923          CALL ju2ymds(rest_julian, yy, mm, dd, ss)
2924          WRITE(numout,*) 'In other word (yy,mm,dd,ss) : ', yy, mm, dd, ss
2925
2926          itau_offset = itau_dep - istp
2927          date0_shifted = date0 - itau_offset*dt/one_day
2928!MM_ A VOIR : dans le TAG 1.4 :
2929!         date0_shifted = in_julian - itau_dep*dt/one_day
2930!MM_ Bon calcul ?
2931
2932          WRITE(numout,*) 'The new starting date is :', date0_shifted
2933          CALL ju2ymds(date0_shifted, yy, mm, dd, ss)
2934          WRITE(numout,*) 'In other word (yy,mm,dd,ss) : ', yy, mm, dd, ss
2935       ELSE
2936          WRITE(numout,*) 'IN -> OUT :', istp, '->', itau_dep
2937          WRITE(numout,*) 'IN -> OUT :', in_julian, '->', rest_julian
2938          WRITE(numout,*) 'SECHIBA''s restart file is not consistent with the one of the GCM'
2939          WRITE(numout,*) 'Correct the time axis of the restart file or force the code to change it.'
2940          STOP
2941       ENDIF
2942    ELSE
2943       itau_offset = 0
2944       date0_shifted = date0
2945    ENDIF
2946    !
2947!!!    CALL ioconf_startdate(date0_shifted)
2948    !
2949    !=====================================================================
2950    !- 1.5 Restart file for STOMATE
2951    !=====================================================================
2952    IF ( control_flags%ok_stomate .OR. control_flags%stomate_watchout ) THEN 
2953       !-
2954       ! STOMATE IS ACTIVATED
2955       !-
2956       !Config  Key  = STOMATE_RESTART_FILEIN
2957       !Config  Desc = Name of restart to READ for initial conditions
2958       !Config         of STOMATE
2959       !Config  If   = STOMATE_OK_STOMATE || STOMATE_WATCHOUT
2960       !Config  Def  = NONE
2961       !Config  Help = This is the name of the file which will be opened
2962       !Config         to extract the initial values of all prognostic
2963       !Config         values of STOMATE.
2964       !-
2965       stom_restname_in = 'NONE'
2966       CALL getin_p('STOMATE_RESTART_FILEIN',stom_restname_in)
2967       WRITE(numout,*) 'STOMATE INPUT RESTART_FILE', stom_restname_in
2968       !-
2969       !Config Key  = STOMATE_RESTART_FILEOUT
2970       !Config Desc = Name of restart files to be created by STOMATE
2971       !Config  If   = STOMATE_OK_STOMATE || STOMATE_WATCHOUT
2972       !Config Def  = stomate_restart.nc
2973       !Config Help = This is the name of the file which will be opened
2974       !Config        to write the final values of all prognostic values
2975       !Config        of STOMATE.
2976       !-
2977       stom_restname_out = 'stomate_restart.nc'
2978       CALL getin_p('STOMATE_RESTART_FILEOUT', stom_restname_out)
2979       WRITE(numout,*) 'STOMATE OUTPUT RESTART_FILE', stom_restname_out
2980       !-
2981       IF (is_root_prc) THEN
2982         CALL restini (stom_restname_in, iim_g, jjm_g, lon_g, lat_g, llm, lev, &
2983            &  stom_restname_out, itau_dep, date0_rest, dt_rest, rest_id_stom, overwrite_time)
2984       ELSE
2985         rest_id_stom=0
2986       ENDIF
2987       CALL bcast (itau_dep)
2988       CALL bcast (date0_rest)
2989       CALL bcast (dt_rest)
2990       !-
2991    ENDIF
2992    !
2993  END SUBROUTINE intsurf_restart
2994 
2995  SUBROUTINE intsurf_history(iim, jjm, lon, lat, istp_old, date0, dt, control_flags, hist_id, hist2_id, &
2996       & hist_id_stom, hist_id_stom_IPCC)
2997    !
2998    !   
2999    !  This subroutine initialized the history files for the land-surface scheme
3000    !
3001    IMPLICIT NONE
3002    !
3003    INTEGER(i_std), INTENT(in)                  :: iim, jjm  !! Size in x and y of the data to be handeled
3004    REAL(r_std),DIMENSION (iim,jjm), INTENT(in) :: lon, lat  !! Longitude and latitude of the data points
3005    INTEGER(i_std), INTENT(in)                  :: istp_old  !! Time step counter
3006    REAL(r_std), INTENT(in)                     :: date0     !! Julian day at which istp=0
3007    REAL(r_std), INTENT(in)                     :: dt        !! Time step of the counter in seconds
3008    !
3009    TYPE(control_type), INTENT(in)             :: control_flags !! Flags that (de)activate parts of the model
3010    !
3011    INTEGER(i_std), INTENT(out)                 :: hist_id !! History file identification for SECHIBA
3012    INTEGER(i_std), INTENT(out)                 :: hist2_id !! History file 2 identification for SECHIBA (Hi-frequency ?)
3013    !! History file identification for STOMATE and IPCC
3014    INTEGER(i_std), INTENT(out)                 :: hist_id_stom, hist_id_stom_IPCC 
3015    !
3016    !  LOCAL
3017    !
3018    CHARACTER(LEN=80) :: histname,histname2                    !! Name of history files for SECHIBA
3019    CHARACTER(LEN=80) :: stom_histname, stom_ipcc_histname     !! Name of history files for STOMATE
3020    LOGICAL           :: ok_histfile2                 !! Flag to switch on histfile 2 for SECHIBA
3021    REAL(r_std)       :: dw2                          !! frequency of history write (sec.)
3022    CHARACTER(LEN=30)   :: flux_op                    !! Operations to be performed on fluxes
3023    CHARACTER(LEN=30)   :: flux_sc                    !! Operations which do not include a scatter
3024    CHARACTER(LEN=30)   :: flux_insec, flux_scinsec   !! Operation in seconds
3025    INTEGER(i_std)     :: hist_level, hist2_level     !! history output level (default is 10 => maximum output)
3026    CHARACTER(LEN=40),DIMENSION(max_hist_level) :: &
3027         & ave, avecels, avescatter, fluxop, &
3028         & fluxop_scinsec, tmincels, tmaxcels, once, sumscatter  !! The various operation to be performed
3029!!, tmax, fluxop_sc, fluxop_insec, &
3030    CHARACTER(LEN=40),DIMENSION(max_hist_level) :: &
3031         & ave2, avecels2, avescatter2, fluxop2, &
3032         & fluxop_scinsec2, tmincels2, tmaxcels2, once2, sumscatter2  !! The various operation to be performed
3033!!, tmax2, fluxop_sc2, fluxop_insec2, &
3034    INTEGER(i_std)     :: i, jst
3035    ! SECHIBA AXIS
3036    INTEGER(i_std)     :: hori_id                      !! ID of the default horizontal longitude and latitude map.
3037    INTEGER(i_std)     :: vegax_id, solax_id, soltax_id, nobioax_id !! ID's for two vertical coordinates
3038    INTEGER(i_std)     :: solayax_id                   !! ID for the vertical axis of the CWRR hydrology
3039    INTEGER(i_std)     :: hori_id2                      !! ID of the default horizontal longitude and latitude map.
3040    INTEGER(i_std)     :: vegax_id2, solax_id2, soltax_id2, nobioax_id2, albax_id2 !! ID's for two vertical coordinates
3041    INTEGER(i_std)     :: solayax_id2                   !! ID for the vertical axis of the CWRR hydrology
3042    ! STOMATE AXIS
3043    INTEGER(i_std)     :: hist_PFTaxis_id
3044! deforestation
3045    INTEGER(i_std)     :: hist_pool_10axis_id
3046    INTEGER(i_std)     :: hist_pool_100axis_id
3047    INTEGER(i_std)     :: hist_pool_11axis_id
3048    INTEGER(i_std)     :: hist_pool_101axis_id
3049    ! STOMATE IPCC AXIS
3050    INTEGER(i_std)     :: hist_IPCC_PFTaxis_id
3051    !
3052    LOGICAL                               :: rectilinear
3053    INTEGER(i_std)                         :: ier
3054    REAL(r_std), ALLOCATABLE, DIMENSION(:) :: lon_rect, lat_rect
3055    !
3056    REAL(r_std),DIMENSION(nvm)   :: veg
3057    REAL(r_std),DIMENSION(ngrnd) :: sol
3058    REAL(r_std),DIMENSION(nstm)  :: soltyp
3059    REAL(r_std),DIMENSION(nnobio):: nobiotyp
3060    REAL(r_std),DIMENSION(2)     :: albtyp
3061    REAL(r_std),DIMENSION(nslm)  :: solay
3062    !
3063    CHARACTER(LEN=80)           :: var_name           !! To store variables names
3064    !
3065    ! STOMATE history file
3066    REAL(r_std)                  :: hist_days_stom     !!- GK time step in days for this history file
3067    REAL(r_std)                  :: hist_dt_stom       !!- GK time step in seconds for this history file
3068    REAL(r_std)                  :: dt_slow_           !!  for test : time step of slow processes and STOMATE
3069    REAL(r_std),DIMENSION(nvm)   :: hist_PFTaxis       !!- GK An axis we need for the history files
3070!
3071    REAL(r_std),DIMENSION(10)  :: hist_pool_10axis     !! Deforestation axis
3072    REAL(r_std),DIMENSION(100)  :: hist_pool_100axis     !! Deforestation axis
3073    REAL(r_std),DIMENSION(11)  :: hist_pool_11axis     !! Deforestation axis
3074    REAL(r_std),DIMENSION(101)  :: hist_pool_101axis     !! Deforestation axis
3075    !
3076    ! IPCC history file
3077    REAL(r_std)                  :: hist_days_stom_ipcc     !!- GK time step in days for this history file
3078    REAL(r_std)                  :: hist_dt_stom_ipcc       !!- GK time step in seconds for this history file
3079!
3080    !
3081    !
3082    !=====================================================================
3083    !- 3.0 Setting up the history files
3084    !=====================================================================
3085    !- 3.1 SECHIBA
3086    !=====================================================================
3087    !Config  Key  = ALMA_OUTPUT
3088    !Config  Desc = Should the output follow the ALMA convention
3089    !Config  Def  = n
3090    !Config  Help = If this logical flag is set to true the model
3091    !Config         will output all its data according to the ALMA
3092    !Config         convention. It is the recommended way to write
3093    !Config         data out of ORCHIDEE.
3094    !-
3095    almaoutput = .FALSE.
3096    CALL getin_p('ALMA_OUTPUT', almaoutput)   
3097    WRITE(numout,*) 'ALMA_OUTPUT', almaoutput
3098    !-
3099    !Config  Key  = OUTPUT_FILE
3100    !Config  Desc = Name of file in which the output is going
3101    !Config         to be written
3102    !Config  Def  = cabauw_out.nc
3103    !Config  Help = This file is going to be created by the model
3104    !Config         and will contain the output from the model.
3105    !Config         This file is a truly COADS compliant netCDF file.
3106    !Config         It will be generated by the hist software from
3107    !Config         the IOIPSL package.
3108    !-
3109    histname='cabauw_out.nc'
3110    CALL getin_p('OUTPUT_FILE', histname)
3111    WRITE(numout,*) 'OUTPUT_FILE', histname
3112    !-
3113    !Config  Key  = WRITE_STEP
3114    !Config  Desc = Frequency in seconds at which to WRITE output
3115    !Config  Def  = 86400.0
3116    !Config  Help = This variables gives the frequency the output of
3117    !Config         the model should be written into the netCDF file.
3118    !Config         It does not affect the frequency at which the
3119    !Config         operations such as averaging are done.
3120    !Config         That is IF the coding of the calls to histdef
3121    !Config         are correct !
3122    !-
3123    dw = one_day
3124    CALL getin_p('WRITE_STEP', dw)
3125    !
3126    veg(1:nvm)   = (/ (REAL(i,r_std),i=1,nvm) /)
3127    sol(1:ngrnd) = (/ (REAL(i,r_std),i=1,ngrnd) /)   
3128    soltyp(1:nstm) = (/ (REAL(i,r_std),i=1,nstm) /)
3129    nobiotyp(1:nnobio) = (/ (REAL(i,r_std),i=1,nnobio) /)
3130    albtyp(1:2) = (/ (REAL(i,r_std),i=1,2) /)
3131    solay(1:nslm) = (/ (REAL(i,r_std),i=1,nslm) /)
3132    !
3133    !- We need to flux averaging operation as when the data is written
3134    !- from within SECHIBA a scatter is needed. In the driver on the other
3135    !- hand the data is 2D and can be written is it is.
3136    !-
3137    WRITE(flux_op,'("ave(scatter(X*",F8.1,"))")') one_day/dt
3138    ! WRITE(flux_op,'("(ave(scatter(X))*",F8.1,")")') one_day/dt
3139    WRITE(flux_sc,'("ave(X*",F8.1,")")') one_day/dt
3140    !WRITE(flux_sc,'("(ave(X)*",F8.1,")")') one_day/dt
3141    WRITE(flux_insec,'("ave(X*",F8.6,")")') 1.0/dt
3142    WRITE(flux_scinsec,'("ave(scatter(X*",F8.6,"))")') 1.0/dt
3143    WRITE(numout,*) flux_op, one_day/dt, dt, dw
3144    !-
3145    !Config  Key  = SECHIBA_HISTLEVEL
3146    !Config  Desc = SECHIBA history output level (0..10)
3147    !Config  Def  = 5
3148    !Config  Help = Chooses the list of variables in the history file.
3149    !Config         Values between 0: nothing is written; 10: everything is
3150    !Config         written are available More details can be found on the web under documentation.
3151    !Config         web under documentation.
3152    !-
3153    hist_level = 5
3154    CALL getin_p('SECHIBA_HISTLEVEL', hist_level)
3155    !-
3156    WRITE(numout,*) 'SECHIBA history level: ',hist_level
3157    IF ( (hist_level > max_hist_level).OR.(hist_level < 0) ) THEN
3158       STOP 'This history level is not allowed'
3159    ENDIF
3160    !-
3161    !- define operations as a function of history level.
3162    !- Above hist_level, operation='never'
3163    !-
3164    ave(1:max_hist_level) = 'ave(X)'
3165    IF (hist_level < max_hist_level) THEN
3166       ave(hist_level+1:max_hist_level) = 'never'
3167    ENDIF
3168    sumscatter(1:max_hist_level) = 't_sum(scatter(X))'
3169    IF (hist_level < max_hist_level) THEN
3170       sumscatter(hist_level+1:max_hist_level) = 'never'
3171    ENDIF
3172    avecels(1:max_hist_level) = 'ave(cels(X))'
3173    IF (hist_level < max_hist_level) THEN
3174       avecels(hist_level+1:max_hist_level) = 'never'
3175    ENDIF
3176    avescatter(1:max_hist_level) = 'ave(scatter(X))'
3177    IF (hist_level < max_hist_level) THEN
3178       avescatter(hist_level+1:max_hist_level) = 'never'
3179    ENDIF
3180    tmincels(1:max_hist_level) = 't_min(cels(X))'
3181    IF (hist_level < max_hist_level) THEN
3182       tmincels(hist_level+1:max_hist_level) = 'never'
3183    ENDIF
3184    tmaxcels(1:max_hist_level) = 't_max(cels(X))'
3185    IF (hist_level < max_hist_level) THEN
3186       tmaxcels(hist_level+1:max_hist_level) = 'never'
3187    ENDIF
3188!!$    tmax(1:max_hist_level) = 't_max(X)'
3189!!$    IF (hist_level < max_hist_level) THEN
3190!!$       tmax(hist_level+1:max_hist_level) = 'never'
3191!!$    ENDIF
3192    fluxop(1:max_hist_level) = flux_op
3193    IF (hist_level < max_hist_level) THEN
3194       fluxop(hist_level+1:max_hist_level) = 'never'
3195    ENDIF
3196!!$    fluxop_sc(1:max_hist_level) = flux_sc
3197!!$    IF (hist_level < max_hist_level) THEN
3198!!$       fluxop_sc(hist_level+1:max_hist_level) = 'never'
3199!!$    ENDIF
3200!!$    fluxop_insec(1:max_hist_level) = flux_insec
3201!!$    IF (hist_level < max_hist_level) THEN
3202!!$       fluxop_insec(hist_level+1:max_hist_level) = 'never'
3203!!$    ENDIF
3204    fluxop_scinsec(1:max_hist_level) = flux_scinsec
3205    IF (hist_level < max_hist_level) THEN
3206       fluxop_scinsec(hist_level+1:max_hist_level) = 'never'
3207    ENDIF
3208    once(1:max_hist_level) = 'once(scatter(X))'
3209    IF (hist_level < max_hist_level) THEN
3210       once(hist_level+1:max_hist_level) = 'never'
3211    ENDIF
3212    !
3213    !-
3214    !- Check if we have by any change a rectilinear grid. This would allow us to
3215    !- simplify the output files.
3216    !
3217    rectilinear = .FALSE.
3218    IF ( ALL(lon(:,:) == SPREAD(lon(:,1), 2, SIZE(lon,2))) .AND. &
3219       & ALL(lat(:,:) == SPREAD(lat(1,:), 1, SIZE(lat,1))) ) THEN
3220       rectilinear = .TRUE.
3221       ALLOCATE(lon_rect(iim),stat=ier)
3222       IF (ier .NE. 0) THEN
3223          WRITE (numout,*) ' error in lon_rect allocation. We stop. We need iim words = ',iim
3224          STOP 'intersurf_history'
3225       ENDIF
3226       ALLOCATE(lat_rect(jjm),stat=ier)
3227       IF (ier .NE. 0) THEN
3228          WRITE (numout,*) ' error in lat_rect allocation. We stop. We need jjm words = ',jjm
3229          STOP 'intersurf_history'
3230       ENDIF
3231       lon_rect(:) = lon(:,1)
3232       lat_rect(:) = lat(1,:)
3233    ENDIF
3234    !-
3235    !-
3236    hist_id = -1
3237    !-
3238    IF ( .NOT. almaoutput ) THEN
3239       !-
3240       IF ( rectilinear ) THEN
3241#ifdef CPP_PARA
3242          CALL histbeg(histname, iim, lon_rect, jjm, lat_rect, 1, iim, 1, jjm, &
3243               &     istp_old, date0, dt, hori_id, hist_id,orch_domain_id)
3244#else
3245          CALL histbeg(histname, iim, lon_rect, jjm, lat_rect, 1, iim, 1, jjm, &
3246               &     istp_old, date0, dt, hori_id, hist_id)
3247#endif
3248          WRITE(numout,*)  'HISTBEG --->',istp_old,date0,dt,dw,hist_id
3249       ELSE
3250#ifdef CPP_PARA
3251          CALL histbeg(histname, iim, lon, jjm, lat, 1, iim, 1, jjm, &
3252               &     istp_old, date0, dt, hori_id, hist_id,domain_id=orch_domain_id)
3253#else
3254          CALL histbeg(histname, iim, lon, jjm, lat, 1, iim, 1, jjm, &
3255               &     istp_old, date0, dt, hori_id, hist_id)
3256#endif
3257       ENDIF
3258       !-
3259       CALL histvert(hist_id, 'veget', 'Vegetation types', '1', &
3260            &    nvm,   veg, vegax_id)
3261       CALL histvert(hist_id, 'solth', 'Soil levels',      'm', &
3262            &    ngrnd, sol, solax_id)
3263       CALL histvert(hist_id, 'soiltyp', 'Soil types',      '1', &
3264            &    nstm, soltyp, soltax_id)
3265       CALL histvert(hist_id, 'nobio', 'Other surface types',      '1', &
3266            &    nnobio, nobiotyp, nobioax_id)
3267       IF (  control_flags%hydrol_cwrr ) THEN
3268          CALL histvert(hist_id, 'solay', 'Hydrol soil levels',      'm', &
3269               &    nslm, solay, solayax_id)
3270       ENDIF
3271       !-
3272       !- SECHIBA_HISTLEVEL = 1
3273       !-
3274       CALL histdef(hist_id, 'evap', 'Evaporation', 'mm/d', &
3275            & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop(1), dt,dw)
3276       CALL histdef(hist_id, 'coastalflow', 'Diffuse coastal flow', 'm^3/s', &
3277            & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop_scinsec(1), dt,dw)
3278       CALL histdef(hist_id, 'riverflow', 'River flow to the oceans', 'm^3/s', &
3279            & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop_scinsec(1), dt,dw) 
3280       CALL histdef(hist_id, 'temp_sol', 'Surface Temperature', 'C', &
3281            & iim,jjm, hori_id, 1,1,1, -99, 32, avecels(1), dt,dw)
3282       CALL histdef(hist_id, 'rain', 'Rainfall', 'mm/d',  &
3283            & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop(1), dt,dw)
3284       CALL histdef(hist_id, 'snowf', 'Snowfall', 'mm/d',  &
3285            & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop(1), dt,dw)
3286       CALL histdef(hist_id, 'netrad', 'Net radiation', 'W/m^2',  &
3287            & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
3288       CALL histdef(hist_id, 'lai', 'Leaf Area Index', '1', &
3289            & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(1), dt,dw)
3290       IF ( control_flags%river_routing ) THEN
3291          CALL histdef(hist_id, 'basinmap', 'Aproximate map of the river basins', ' ', &
3292               & iim,jjm, hori_id, 1,1,1, -99, 32, once(1), dt,dw) 
3293          CALL histdef(hist_id, 'nbrivers', 'Number or rivers in the outflow grid box', ' ', &
3294               & iim,jjm, hori_id, 1,1,1, -99, 32, once(1), dt,dw) 
3295       ENDIF
3296       IF ( control_flags%ok_stomate .OR. control_flags%stomate_watchout ) THEN
3297          CALL histdef (hist_id,'CO2FLUX','Total output CO2 flux', 'gC/day/(m^2 tot)', &
3298               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(1), dt, dw)
3299       ENDIF
3300       !-
3301       !- SECHIBA_HISTLEVEL = 2
3302       !-
3303       CALL histdef(hist_id, 'subli', 'Sublimation', 'mm/d', &
3304            & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop(2), dt,dw)
3305       CALL histdef(hist_id, 'evapnu', 'Bare soil evaporation', 'mm/d', &
3306            & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop(2), dt,dw)
3307       CALL histdef(hist_id, 'runoff', 'Surface runoff', 'mm/d', &
3308            & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop(2), dt,dw)
3309       CALL histdef(hist_id, 'drainage', 'Deep drainage', 'mm/d', &
3310            & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop(2), dt,dw)
3311       IF ( control_flags%river_routing ) THEN
3312          CALL histdef(hist_id, 'riversret', 'Return from endorheic rivers', 'mm/d', &
3313               & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop(2), dt,dw)
3314          CALL histdef(hist_id, 'hydrographs', 'Hydrographs of gridbox outflow', 'm^3/s', &
3315               & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop_scinsec(2), dt,dw)
3316       ENDIF
3317       IF ( control_flags%hydrol_cwrr ) THEN
3318          CALL histdef(hist_id, 'evapnu_soil', 'Bare soil evap for soil type', 'mm/d', &
3319               & iim,jjm, hori_id, nstm, 1, nstm, soltax_id, 32, fluxop(2), dt,dw)
3320          CALL histdef(hist_id, 'drainage_soil', 'Drainage for soil type', 'mm/d', &
3321               & iim,jjm, hori_id, nstm, 1, nstm, soltax_id, 32, fluxop(2), dt,dw)
3322          CALL histdef(hist_id, 'transpir_soil', 'Transpir for soil type', 'mm/d', &
3323               & iim,jjm, hori_id, nstm, 1, nstm, soltax_id, 32, fluxop(2), dt,dw)
3324          CALL histdef(hist_id, 'runoff_soil', 'Runoff for soil type', 'mm/d', &
3325               & iim,jjm, hori_id, nstm, 1, nstm, soltax_id, 32, fluxop(2), dt,dw)
3326       ENDIF
3327       !
3328       CALL histdef(hist_id, 'tair', 'Air Temperature', 'K',  &
3329            & iim,jjm, hori_id, 1,1,1, -99, 32, ave(2), dt,dw)
3330       CALL histdef(hist_id, 'qair', 'Air humidity', 'g/g',  &
3331            & iim,jjm, hori_id, 1,1,1, -99, 32, ave(2), dt,dw)
3332       ! Ajouts Nathalie - Juillet 2006
3333       CALL histdef(hist_id, 'q2m', '2m Air humidity', 'g/g',  &
3334            & iim,jjm, hori_id, 1,1,1, -99, 32, ave(2), dt,dw)
3335       CALL histdef(hist_id, 't2m', '2m Air Temperature', 'K',  &
3336            & iim,jjm, hori_id, 1,1,1, -99, 32, ave(2), dt,dw)
3337       ! Fin ajouts Nathalie
3338       CALL histdef(hist_id, 'alb_vis', 'Albedo visible', '1', &
3339            & iim,jjm, hori_id, 1,1,1, -99, 32, ave(2), dt,dw)
3340       CALL histdef(hist_id, 'alb_nir', 'Albedo near infrared', '1', &
3341            & iim,jjm, hori_id, 1,1,1, -99, 32, ave(2), dt,dw)
3342       ! Ajouts Nathalie - Septembre 2008
3343       CALL histdef(hist_id, 'soilalb_vis', 'Soil Albedo visible', '1', &
3344            & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(2), dt,dw)
3345       CALL histdef(hist_id, 'soilalb_nir', 'Soil Albedo near infrared', '1', &
3346            & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(2), dt,dw)
3347       CALL histdef(hist_id, 'vegalb_vis', 'Vegetation Albedo visible', '1', &
3348            & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(2), dt,dw)
3349       CALL histdef(hist_id, 'vegalb_nir', 'Vegetation Albedo near infrared', '1', &
3350            & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(2), dt,dw)
3351       ! Fin ajouts Nathalie - Septembre 2008
3352       CALL histdef(hist_id, 'z0', 'Surface roughness', 'm',  &
3353            & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(2), dt,dw)
3354       CALL histdef(hist_id, 'roughheight', 'Effective roughness height', 'm',  &
3355            & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(2), dt,dw)
3356       CALL histdef(hist_id, 'transpir', 'Transpiration', 'mm/d', &
3357            & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, fluxop(2), dt,dw)
3358       CALL histdef(hist_id, 'inter', 'Interception loss', 'mm/d', &
3359            & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, fluxop(2), dt,dw)
3360       !-
3361       !- SECHIBA_HISTLEVEL = 3
3362       !-
3363       CALL histdef(hist_id, 'tsol_max', 'Maximum Surface Temperature',&
3364            & 'C', iim,jjm, hori_id, 1,1,1, -99, 32, tmaxcels(3), dt,dw)
3365       CALL histdef(hist_id, 'tsol_min', 'Minimum Surface Temperature',&
3366            & 'C', iim,jjm, hori_id, 1,1,1, -99, 32, tmincels(3), dt,dw)
3367       CALL histdef(hist_id, 'fluxsens', 'Sensible Heat Flux', 'W/m^2',  &
3368            & iim,jjm, hori_id, 1,1,1, -99, 32, ave(3), dt,dw)
3369       CALL histdef(hist_id, 'fluxlat', 'Latent Heat Flux', 'W/m^2',  &
3370            & iim,jjm, hori_id, 1,1,1, -99, 32, ave(3), dt,dw)
3371       CALL histdef(hist_id, 'snow', 'Snow mass', 'kg/m^2', &
3372            & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(3), dt,dw)
3373       CALL histdef(hist_id, 'snowage', 'Snow age', '?', &
3374            & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(3), dt,dw)
3375       CALL histdef(hist_id, 'snownobio', 'Snow on other surfaces', 'kg/m^2', &
3376            & iim,jjm, hori_id, nnobio,1, nnobio, nobioax_id, 32, avescatter(3), dt,dw)
3377       CALL histdef(hist_id, 'snownobioage', 'Snow age on other surfaces', 'd', &
3378            & iim,jjm, hori_id, nnobio,1, nnobio, nobioax_id, 32, avescatter(3), dt,dw)
3379       CALL histdef(hist_id, 'vegetfrac', 'Fraction of vegetation', '1', &
3380            & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(3), dt,dw)
3381       CALL histdef(hist_id, 'maxvegetfrac', 'Maximum fraction of vegetation', '1', &
3382            & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(3), dt,dw)
3383       CALL histdef(hist_id, 'nobiofrac', 'Fraction of other surface types', '1', &
3384            & iim,jjm, hori_id, nnobio, 1, nnobio, nobioax_id, 32, avescatter(3), dt,dw)
3385       IF ( control_flags%hydrol_cwrr ) THEN
3386          DO jst=1,nstm
3387             
3388             ! var_name= "mc_1" ... "mc_3"
3389             WRITE (var_name,"('moistc_',i1)") jst
3390             CALL histdef(hist_id, var_name, 'Soil Moisture profile for soil type', '%', &
3391                  & iim,jjm, hori_id, nslm, 1, nslm, solayax_id, 32, avescatter(3),  dt,dw)
3392             
3393             ! var_name= "vegetsoil_1" ... "vegetsoil_3"
3394             WRITE (var_name,"('vegetsoil_',i1)") jst
3395             CALL histdef(hist_id, var_name, 'Fraction of vegetation on soil types', '%', &
3396                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(3),  dt,dw)
3397             
3398          ENDDO
3399       ENDIF
3400       !-
3401       !- SECHIBA_HISTLEVEL = 4
3402       !-
3403       IF ( .NOT. control_flags%hydrol_cwrr ) THEN
3404          CALL histdef(hist_id, 'dss', 'Up-reservoir Height', 'm',  &
3405               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(4), dt,dw)
3406          CALL histdef(hist_id, 'gqsb', 'Upper Soil Moisture', '1',  &
3407               & iim,jjm, hori_id, 1, 1, 1, -99, 32, avescatter(4), dt,dw)
3408          CALL histdef(hist_id, 'bqsb', 'Lower Soil Moisture', '1',  &
3409               & iim,jjm, hori_id, 1, 1, 1, -99, 32, avescatter(4), dt,dw)
3410       ELSE
3411          CALL histdef(hist_id, 'humtot', 'Total Soil Moisture', 'Kg/m2', &
3412               & iim,jjm, hori_id, 1, 1, 1, -99, 32, avescatter(4), dt,dw)
3413          CALL histdef(hist_id, 'humtot_soil', 'Soil Moisture for soil type', 'Kg/m2', &
3414               & iim,jjm, hori_id, nstm, 1, nstm, soltax_id, 32, avescatter(4), dt,dw)
3415       ENDIF
3416       CALL histdef(hist_id, 'qsintveg', 'Water on canopy', 'Kg/m^2', &
3417            & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(4), dt,dw)
3418       CALL histdef(hist_id, 'rstruct', 'Structural resistance', 's/m', &
3419            & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(4), dt,dw)
3420       IF ( control_flags%ok_co2 ) THEN
3421          CALL histdef(hist_id, 'gpp', 'Net assimilation of carbon by the vegetation', 'gC/m^2/s', &
3422               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, fluxop_scinsec(4), dt,dw)
3423       ENDIF
3424       IF ( control_flags%ok_stomate ) THEN
3425          CALL histdef(hist_id, 'nee', 'Net Ecosystem Exchange', 'gC/m^2/s', &
3426               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, fluxop_scinsec(4), dt,dw)
3427          CALL histdef(hist_id, 'maint_resp', 'Maintenance respiration', 'gC/m^2/s', &
3428               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, fluxop_scinsec(4), dt,dw)
3429          CALL histdef(hist_id, 'hetero_resp', 'Heterotrophic respiration', 'gC/m^2/s', &
3430               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, fluxop_scinsec(4), dt,dw)
3431          CALL histdef(hist_id, 'growth_resp', 'Growth respiration', 'gC/m^2/s', &
3432               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, fluxop_scinsec(4), dt,dw)
3433          CALL histdef(hist_id, 'npp', 'Net Primary Production', 'gC/m^2/s', &
3434               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, fluxop_scinsec(1), dt, dw)
3435       ENDIF
3436       CALL histdef(hist_id, 'precisol', 'Throughfall', 'mm/d',  &
3437            & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, fluxop(4), dt,dw)
3438       CALL histdef(hist_id, 'drysoil_frac', 'Fraction of visibly dry soil', '1',  &
3439            & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(4), dt,dw)
3440       CALL histdef(hist_id, 'evapot', 'Potential evaporation', 'mm/d',  &
3441            & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop(4), dt,dw)
3442       CALL histdef(hist_id, 'evapot_corr', 'Potential evaporation', 'mm/d',  &
3443            & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop(4), dt,dw)
3444       !-
3445       !- SECHIBA_HISTLEVEL = 5
3446       !-
3447       CALL histdef(hist_id, 'swnet', 'Net solar radiation', 'W/m^2',  &
3448            & iim,jjm, hori_id, 1,1,1, -99, 32, ave(5), dt,dw)
3449       CALL histdef(hist_id, 'swdown', 'Incident solar radiation', 'W/m^2',  &
3450            & iim,jjm, hori_id, 1,1,1, -99, 32, ave(5), dt,dw)
3451       CALL histdef(hist_id, 'lwdown', 'Absorbed downward longwave radiation', 'W/m^2',  &
3452            & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(5), dt,dw)
3453       CALL histdef(hist_id, 'lwnet', 'Net surface longwave radiation', 'W/m^2',  &
3454            & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(5), dt,dw)
3455       CALL histdef(hist_id, 'temp_pheno', 'Temperature for Pheno', 'K',  &
3456            & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(5), dt,dw)
3457       !-
3458       !- SECHIBA_HISTLEVEL = 6
3459       !-
3460       CALL histdef(hist_id, 'ptn', 'Deep ground temperature', 'K', &
3461            & iim,jjm, hori_id, ngrnd, 1, ngrnd, solax_id, 32, avescatter(6),  dt,dw)
3462       !-
3463       !- SECHIBA_HISTLEVEL = 7
3464       !-
3465       IF ( control_flags%river_routing ) THEN
3466          CALL histdef(hist_id, 'fastr', 'Fast flow reservoir', 'kg/m^2', &
3467               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(7), dt,dw)
3468          CALL histdef(hist_id, 'slowr', 'Slow flow reservoir', 'kg/m^2', &
3469               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(7), dt,dw)
3470          CALL histdef(hist_id, 'streamr', 'Stream flow reservoir', 'kg/m^2', &
3471               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(7), dt,dw)
3472          CALL histdef(hist_id, 'lakevol', 'Volume in lake reservoir', 'kg/m^2', &
3473               & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(7), dt,dw)
3474          CALL histdef(hist_id, 'irrigation', 'Net irrigation', 'mm/d', &
3475               & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop(7), dt,dw)
3476          CALL histdef(hist_id, 'netirrig', 'Net irrigation requirement', 'mm/d', &
3477               & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop(7), dt,dw)
3478          CALL histdef(hist_id, 'irrigmap', 'Map of irrigated areas', 'm^2', &
3479               & iim,jjm, hori_id, 1,1,1, -99, 32, once(7), dt,dw)
3480       ENDIF
3481       !-
3482       !- SECHIBA_HISTLEVEL = 8
3483       !-
3484       CALL histdef(hist_id, 'beta', 'Beta Function', '1',  &
3485            & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(8), dt,dw)
3486       CALL histdef(hist_id, 'raero', 'Aerodynamic resistance', 's/m',  &
3487            & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(8), dt,dw)
3488       ! Ajouts Nathalie - Novembre 2006
3489       CALL histdef(hist_id, 'cdrag', 'Drag coefficient for LE and SH', '?',  &
3490            & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(8), dt,dw)
3491       CALL histdef(hist_id, 'Wind', 'Wind speed', 'm/s',  &
3492            & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(8), dt,dw)
3493       ! Fin ajouts Nathalie
3494!MM
3495       CALL histdef(hist_id, 'qsatt' , 'Surface saturated humidity', 'g/g', &
3496            & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(8), dt,dw)
3497       CALL histdef(hist_id, 'vbeta1', 'Beta for sublimation', '1',  &
3498            & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(8), dt,dw)
3499       CALL histdef(hist_id, 'vbeta4', 'Beta for bare soil', '1',  &
3500            & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(8), dt,dw)
3501       CALL histdef(hist_id, 'vbetaco2', 'beta for CO2', 'mm/d', &
3502            & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(8), dt,dw)
3503       CALL histdef(hist_id, 'soiltype', 'Fraction of soil textures', '%', &
3504            & iim,jjm, hori_id, nstm, 1, nstm, soltax_id, 32, once(8),  dt,dw)
3505       CALL histdef(hist_id, 'humrel', 'Soil moisture stress', '1',  &
3506            & iim,jjm, hori_id, nvm,1,nvm, vegax_id, 32, avescatter(8), dt,dw)
3507       !-
3508       !- SECHIBA_HISTLEVEL = 9
3509       !-
3510       !-
3511       !- SECHIBA_HISTLEVEL = 10
3512       !-
3513       CALL histdef(hist_id, 'cimean', 'Stomatal CO2 concentation', 'mmole/m2/s', &
3514            & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(10), dt,dw)
3515       CALL histdef(hist_id, 'vbeta3', 'Beta for Transpiration', 'mm/d', &
3516            & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(10), dt,dw)
3517       CALL histdef(hist_id, 'rveget', 'Canopy resistance', 's/m', &
3518            & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(10), dt,dw)
3519       CALL histdef(hist_id, 'rsol', 'Soil resistance', 's/m',  &
3520            & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(10), dt,dw)
3521       CALL histdef(hist_id,'vbeta2','Beta for Interception loss','mm/d', &
3522            & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(10), dt,dw)
3523       CALL histdef(hist_id, 'qsintmax', 'Maximum Interception capacity', 'Kg/m^2', &
3524            & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(10), dt,dw)
3525
3526       !- SECHIBA_HISTLEVEL = 11
3527       !-
3528
3529       IF ( .NOT. control_flags%hydrol_cwrr ) THEN
3530          CALL histdef(hist_id, 'mrsos', "Moisture in Upper 0.1 m of Soil Column", "kg m-2", &
3531               & iim,jjm, hori_id, 1, 1, 1, -99, 32, avescatter(11), dt,dw)
3532
3533          CALL histdef(hist_id, 'mrso', "Total Soil Moisture Content", "kg m-2", &
3534               & iim,jjm, hori_id, 1, 1, 1, -99, 32, avescatter(11), dt,dw)
3535
3536          CALL histdef(hist_id, 'mrros', "Surface Runoff", "kg m-2 s-1", &
3537               & iim,jjm, hori_id, 1, 1, 1, -99, 32, avescatter(11), dt,dw)
3538
3539          CALL histdef(hist_id, 'mrro', "Total Runoff", "kg m-2 s-1", &
3540               & iim,jjm, hori_id, 1, 1, 1, -99, 32, avescatter(11), dt,dw)
3541
3542          CALL histdef(hist_id, 'prveg', "Precipitation onto Canopy", "kg m-2 s-1", &
3543               & iim,jjm, hori_id, 1, 1, 1, -99, 32, avescatter(11), dt,dw)
3544
3545       ENDIF
3546
3547
3548       CALL histdef(hist_id, 'evspsblveg', "Evaporation from Canopy", "kg m-2 s-1", &
3549            & iim,jjm, hori_id, 1, 1, 1, -99, 32, avescatter(11), dt,dw)
3550
3551       CALL histdef(hist_id, 'evspsblsoi', "Water Evaporation from Soil", "kg m-2 s-1", &
3552            & iim,jjm, hori_id, 1, 1, 1, -99, 32, avescatter(11), dt,dw)
3553
3554       CALL histdef(hist_id, 'tran', "Transpiration", "kg m-2 s-1", &
3555            & iim,jjm, hori_id, 1, 1, 1, -99, 32, avescatter(11), dt,dw)
3556
3557       CALL histdef(hist_id, 'treeFrac', "Tree Cover Fraction", "%", &
3558            & iim,jjm, hori_id, 1, 1, 1, -99, 32, avescatter(11), dt,dw)
3559
3560       CALL histdef(hist_id, 'grassFrac', "Natural Grass Fraction", "%", &
3561            & iim,jjm, hori_id, 1, 1, 1, -99, 32, avescatter(11), dt,dw)
3562
3563       CALL histdef(hist_id, 'cropFrac', "Crop Fraction", "%", &
3564            & iim,jjm, hori_id, 1, 1, 1, -99, 32, avescatter(11), dt,dw)
3565
3566       CALL histdef(hist_id, 'baresoilFrac', "Bare Soil Fraction", "%", &
3567            & iim,jjm, hori_id, 1, 1, 1, -99, 32, avescatter(11), dt,dw)
3568
3569       CALL histdef(hist_id, 'residualFrac', &
3570            & "Fraction of Grid Cell that is Land but Neither Vegetation-Covered nor Bare Soil", "%", &
3571            & iim,jjm, hori_id, 1, 1, 1, -99, 32, avescatter(11), dt,dw)
3572
3573    ELSE 
3574       !-
3575       !- This is the ALMA convention output now
3576       !-
3577       !-
3578       IF ( rectilinear ) THEN
3579#ifdef CPP_PARA
3580          CALL histbeg(histname, iim, lon_rect, jjm, lat_rect, 1, iim, 1, jjm, &
3581               &     istp_old, date0, dt, hori_id, hist_id,orch_domain_id)
3582#else
3583          CALL histbeg(histname, iim, lon_rect, jjm, lat_rect, 1, iim, 1, jjm, &
3584               &     istp_old, date0, dt, hori_id, hist_id)
3585#endif
3586       ELSE
3587#ifdef CPP_PARA
3588          CALL histbeg(histname, iim, lon, jjm, lat, 1, iim, 1, jjm, &
3589               &     istp_old, date0, dt, hori_id, hist_id,domain_id=orch_domain_id)
3590#else
3591          CALL histbeg(histname, iim, lon, jjm, lat, 1, iim, 1, jjm, &
3592               &     istp_old, date0, dt, hori_id, hist_id)
3593#endif
3594       ENDIF
3595       !-
3596       CALL histvert(hist_id, 'veget', 'Vegetation types', '1', &
3597            &    nvm,   veg, vegax_id)
3598       CALL histvert(hist_id, 'solth', 'Soil levels',      'm', &
3599            &    ngrnd, sol, solax_id)
3600       CALL histvert(hist_id, 'soiltyp', 'Soil types',      '1', &
3601            &    nstm, soltyp, soltax_id)
3602       CALL histvert(hist_id, 'nobio', 'Other surface types',      '1', &
3603            &    nnobio, nobiotyp, nobioax_id)
3604       IF (  control_flags%hydrol_cwrr ) THEN
3605          CALL histvert(hist_id, 'solay', 'Hydrol soil levels',      'm', &
3606               &    nslm, solay, solayax_id)
3607       ENDIF
3608     !-
3609     !-  Vegetation
3610     !-
3611       CALL histdef(hist_id, 'vegetfrac', 'Fraction of vegetation', '1', &
3612            & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(3), dt,dw)
3613       CALL histdef(hist_id, 'maxvegetfrac', 'Maximum fraction of vegetation', '1', &
3614            & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(3), dt,dw)
3615       CALL histdef(hist_id, 'nobiofrac', 'Fraction of other surface types', '1', &
3616            & iim,jjm, hori_id, nnobio, 1, nnobio, nobioax_id, 32, avescatter(3), dt,dw)
3617       IF ( control_flags%ok_stomate .OR. control_flags%stomate_watchout ) THEN
3618          ! Total output CO2 flux                             
3619          CALL histdef (hist_id,'CO2FLUX','Total output CO2 flux', 'gC/day/(m^2 tot)', &
3620               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter(1), dt, dw)
3621       ENDIF
3622     !-
3623     !-  General energy balance
3624     !-
3625       CALL histdef(hist_id, 'SWnet', 'Net shortwave radiation', 'W/m^2',  &
3626            & iim,jjm, hori_id, 1,1,1, -99, 32, ave(1), dt,dw)
3627       CALL histdef(hist_id, 'LWnet', 'Net longwave radiation', 'W/m^2',  &
3628            & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
3629       CALL histdef(hist_id, 'Qh', 'Sensible heat flux', 'W/m^2',  &
3630            & iim,jjm, hori_id, 1,1,1, -99, 32, ave(1), dt,dw)
3631       CALL histdef(hist_id, 'Qle', 'Latent heat flux', 'W/m^2',  &
3632            & iim,jjm, hori_id, 1,1,1, -99, 32, ave(1), dt,dw)
3633       CALL histdef(hist_id, 'Qg', 'Ground heat flux', 'W/m^2',  &
3634            & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
3635       CALL histdef(hist_id, 'Qf', 'Energy of fusion', 'W/m^2',  &
3636            & iim,jjm, hori_id, 1,1,1, -99, 32, ave(2), dt,dw)
3637       CALL histdef(hist_id, 'Qv', 'Energy of sublimation', 'W/m^2',  &
3638            & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
3639       CALL histdef(hist_id, 'DelSurfHeat', 'Change in surface layer heat', 'J/m^2',  &
3640            & iim,jjm, hori_id, 1,1,1, -99, 32, sumscatter(1), dt,dw)
3641       CALL histdef(hist_id, 'DelColdCont', 'Change in snow surface layer cold content', 'J/m^2',  &
3642            & iim,jjm, hori_id, 1,1,1, -99, 32, sumscatter(1), dt,dw)
3643    !-
3644    !- General water balance
3645    !-
3646       CALL histdef(hist_id, 'Snowf', 'Snowfall rate', 'kg/m^2/s',  &
3647            & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop_scinsec(1), dt,dw)
3648       CALL histdef(hist_id, 'Rainf', 'Rainfall rate', 'kg/m^2/s',  &
3649            & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop_scinsec(1), dt,dw)
3650       CALL histdef(hist_id, 'Evap', 'Total Evapotranspiration', 'kg/m^2/s', &
3651            & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop_scinsec(1), dt,dw)
3652       CALL histdef(hist_id, 'Qs', 'Surface runoff', 'kg/m^2/s', &
3653            & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop_scinsec(1), dt,dw)
3654       CALL histdef(hist_id, 'Qsb', 'Sub-surface runoff', 'kg/m^2/s', &
3655            & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop_scinsec(1), dt,dw)
3656       CALL histdef(hist_id, 'Qsm', 'Snowmelt', 'kg/m^2/s', &
3657            & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop_scinsec(1), dt,dw)
3658       CALL histdef(hist_id, 'DelSoilMoist', 'Change in soil moisture', 'kg/m^2',  &
3659            & iim,jjm, hori_id, 1, 1, 1, -99, 32, sumscatter(1), dt,dw)
3660       CALL histdef(hist_id, 'DelSWE', 'Change in SWE','kg/m^2',&
3661            & iim,jjm, hori_id, 1, 1, 1, -99, 32, sumscatter(1), dt,dw)
3662       CALL histdef(hist_id, 'DelIntercept', 'Change in interception storage', 'kg/m^2',  &
3663            & iim,jjm, hori_id, 1, 1, 1, -99, 32, sumscatter(1), dt,dw)
3664    !-
3665    !- Surface state
3666    !-
3667       CALL histdef(hist_id, 'AvgSurfT', 'Average surface temperature', 'K', &
3668            & iim,jjm, hori_id, 1,1,1, -99, 32, ave(1), dt,dw)
3669       CALL histdef(hist_id, 'RadT', 'Surface radiative temperature', 'K', &
3670            & iim,jjm, hori_id, 1,1,1, -99, 32, ave(1), dt,dw)
3671       CALL histdef(hist_id, 'Albedo', 'Albedo', '1', &
3672            & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
3673       CALL histdef(hist_id, 'SWE', '3D soil water equivalent','kg/m^2',  &
3674            & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
3675    !!-
3676    !-  Sub-surface state
3677    !-
3678       IF ( .NOT. control_flags%hydrol_cwrr ) THEN
3679          CALL histdef(hist_id, 'SoilMoist', '3D average layer soil moisture', 'kg/m^2',  &
3680               & iim,jjm, hori_id, 1, 1, 1, -99, 32, avescatter(1), dt,dw)
3681       ELSE
3682          CALL histdef(hist_id, 'SoilMoist', '3D average layer soil moisture', 'kg/m^2',  &
3683               & iim,jjm, hori_id, nslm, 1, nslm, solayax_id, 32, avescatter(1), dt,dw)
3684       ENDIF
3685       CALL histdef(hist_id, 'SoilWet', 'Total soil wetness', 'kg/m^2',  &
3686            & iim,jjm, hori_id, 1, 1, 1, -99, 32, avescatter(1), dt,dw)
3687       CALL histdef(hist_id, 'SoilTemp', '3D layer average soil temperature', 'K', &
3688            & iim,jjm, hori_id, ngrnd, 1, ngrnd, solax_id, 32, avescatter(1),  dt,dw)
3689    !-
3690    !-  Evaporation components
3691    !-
3692       CALL histdef(hist_id, 'PotEvap', 'Potential evapotranspiration', 'kg/m^2/s', &
3693            & iim,jjm, hori_id, 1, 1, 1, -99, 32, fluxop_scinsec(1), dt,dw)
3694       CALL histdef(hist_id, 'ECanop', 'Interception evaporation', 'kg/m^2/s', &
3695            & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, fluxop_scinsec(1), dt,dw)
3696       CALL histdef(hist_id, 'TVeg', 'Transpiration', 'kg/m^2/s', &
3697            & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, fluxop_scinsec(1), dt,dw)
3698       CALL histdef(hist_id, 'ESoil', 'Bare soil evaporation', 'kg/m^2/s', &
3699            & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop_scinsec(1), dt,dw)
3700       CALL histdef(hist_id, 'RootMoist','Root zone soil water', 'kg/m^2',  &
3701            & iim,jjm, hori_id, 1, 1, 1, -99, 32, avescatter(1), dt,dw)
3702       CALL histdef(hist_id, 'SubSnow','Snow sublimation','kg/m^2/s', &
3703            & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop_scinsec(1), dt,dw)
3704       CALL histdef(hist_id, 'ACond', 'Aerodynamic conductance', 'm/s',  &
3705            & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
3706    !-
3707    !-
3708    !-  Cold Season Processes
3709    !-
3710       CALL histdef(hist_id, 'SnowFrac', 'Snow cover fraction', '1',  &
3711            & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
3712       CALL histdef(hist_id, 'SAlbedo', 'Snow albedo', '1', &
3713            & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
3714       CALL histdef(hist_id, 'SnowDepth', '3D snow depth', 'm', &
3715            & iim,jjm, hori_id, 1,1,1, -99, 32, avescatter(1), dt,dw)
3716    !-
3717    !- Hydrologic variables
3718    !-
3719       CALL histdef(hist_id, 'IrrigationMap', 'Map of irrigated areas', 'm^2', &
3720            & iim,jjm, hori_id, 1,1,1, -99, 32, once(7), dt,dw)
3721       CALL histdef(hist_id, 'dis', 'Simulated River Discharge', 'm^3/s', &
3722            & iim,jjm, hori_id, 1,1,1, -99, 32, fluxop_scinsec(2), dt,dw)
3723       CALL histdef(hist_id, 'humrel', 'Soil moisture stress', '1',  &
3724            & iim,jjm, hori_id, nvm,1,nvm, vegax_id, 32, avescatter(8), dt,dw)
3725    !-
3726    !-  The carbon budget
3727    !-
3728       IF ( control_flags%ok_co2 ) THEN
3729          CALL histdef(hist_id, 'GPP', 'Net assimilation of carbon by the vegetation', 'gC/m^2/s', &
3730               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, fluxop_scinsec(1), dt,dw)
3731       ENDIF
3732       IF ( control_flags%ok_stomate ) THEN
3733          CALL histdef(hist_id, 'NEE', 'Net Ecosystem Exchange', 'gC/m^2/s', &
3734               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, fluxop_scinsec(1), dt,dw)
3735          CALL histdef(hist_id, 'maint_resp', 'Maintenance respiration', 'gC/m^2/s', &
3736               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, fluxop_scinsec(1), dt,dw)
3737          CALL histdef(hist_id, 'hetero_resp', 'Heterotrophic respiration', 'gC/m^2/s', &
3738               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, fluxop_scinsec(1), dt,dw)
3739          CALL histdef(hist_id, 'growth_resp', 'Growth respiration', 'gC/m^2/s', &
3740               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, fluxop_scinsec(1), dt,dw)
3741          CALL histdef(hist_id, 'npp', 'Net Primary Production', 'gC/m^2/s', &
3742               & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, fluxop_scinsec(1), dt,dw)
3743       ENDIF
3744    !
3745    ENDIF
3746    !-
3747    CALL histdef(hist_id, 'LandPoints', 'Land Points', '1', &
3748               & iim,jjm, hori_id, 1,1,1, -99, 32, once(1), dt,dw) 
3749    CALL histdef(hist_id, 'Areas', 'Mesh areas', 'm2', &
3750         & iim,jjm, hori_id, 1,1,1, -99, 32, once(1), dt, dw)
3751    CALL histdef(hist_id, 'Contfrac', 'Continental fraction', '1', &
3752         & iim,jjm, hori_id, 1,1,1, -99, 32, once(1), dt, dw)
3753    !-
3754    CALL histend(hist_id)
3755    !
3756    !
3757    ! Second SECHIBA hist file
3758    !
3759    !-
3760    !Config  Key  = SECHIBA_HISTFILE2
3761    !Config  Desc = Flag to switch on histfile 2 for SECHIBA (hi-frequency ?)
3762    !Config  Def  = FALSE
3763    !Config  Help = This Flag switch on the second SECHIBA writing for hi (or low)
3764    !Config         frequency writing. This second output is optional and not written
3765    !Config         by default.
3766    !Config MM is it right ? Second output file is produced with the same level
3767    !Config         as the first one.
3768    !-
3769    ok_histfile2=.FALSE.
3770    CALL getin_p('SECHIBA_HISTFILE2', ok_histfile2)
3771    WRITE(numout,*) 'SECHIBA_HISTFILE2 ', ok_histfile2
3772    !
3773    hist2_id = -1
3774    !
3775    IF (ok_histfile2) THEN
3776       !-
3777       !Config  Key  = SECHIBA_OUTPUT_FILE2
3778       !Config  Desc = Name of file in which the output number 2 is going
3779       !Config         to be written
3780       !Config  If   = SECHIBA_HISTFILE2
3781       !Config  Def  = sechiba_out_2.nc
3782       !Config  Help = This file is going to be created by the model
3783       !Config         and will contain the output 2 from the model.
3784       !-
3785       histname2='sechiba_out_2.nc'
3786       CALL getin_p('SECHIBA_OUTPUT_FILE2', histname2)
3787       WRITE(numout,*) 'SECHIBA_OUTPUT_FILE2 ', histname2
3788       !-
3789       !Config  Key  = WRITE_STEP2
3790       !Config  Desc = Frequency in seconds at which to WRITE output
3791       !Config  If   = SECHIBA_HISTFILE2
3792       !Config  Def  = 1800.0
3793       !Config  Help = This variables gives the frequency the output 2 of
3794       !Config         the model should be written into the netCDF file.
3795       !Config         It does not affect the frequency at which the
3796       !Config         operations such as averaging are done.
3797       !Config         That is IF the coding of the calls to histdef
3798       !Config         are correct !
3799       !-
3800       dw2 = 1800.0
3801       CALL getin_p('WRITE_STEP2', dw2)
3802       !-
3803       !Config  Key  = SECHIBA_HISTLEVEL2
3804       !Config  Desc = SECHIBA history 2 output level (0..10)
3805       !Config  If   = SECHIBA_HISTFILE2
3806       !Config  Def  = 1
3807       !Config  Help = Chooses the list of variables in the history file.
3808       !Config         Values between 0: nothing is written; 10: everything is
3809       !Config         written are available More details can be found on the web under documentation.
3810       !Config         web under documentation.
3811       !Config         First level contains all ORCHIDEE outputs.
3812       !-
3813       hist2_level = 1
3814       CALL getin_p('SECHIBA_HISTLEVEL2', hist2_level)
3815       !-
3816       WRITE(numout,*) 'SECHIBA history level 2 : ',hist2_level
3817       IF ( (hist2_level > max_hist_level).OR.(hist2_level < 0) ) THEN
3818          STOP 'This history level 2 is not allowed'
3819       ENDIF
3820       !
3821       !-
3822       !- define operations as a function of history level.
3823       !- Above hist2_level, operation='never'
3824       !-
3825       ave2(1:max_hist_level) = 'ave(X)'
3826       IF (hist2_level < max_hist_level) THEN
3827          ave2(hist2_level+1:max_hist_level) = 'never'
3828       ENDIF
3829       sumscatter2(1:max_hist_level) = 't_sum(scatter(X))'
3830       IF (hist2_level < max_hist_level) THEN
3831          sumscatter2(hist2_level+1:max_hist_level) = 'never'
3832       ENDIF
3833       avecels2(1:max_hist_level) = 'ave(cels(X))'
3834       IF (hist2_level < max_hist_level) THEN
3835          avecels2(hist2_level+1:max_hist_level) = 'never'
3836       ENDIF
3837       avescatter2(1:max_hist_level) = 'ave(scatter(X))'
3838       IF (hist2_level < max_hist_level) THEN
3839          avescatter2(hist2_level+1:max_hist_level) = 'never'
3840       ENDIF
3841       tmincels2(1:max_hist_level) = 't_min(cels(X))'
3842       IF (hist2_level < max_hist_level) THEN
3843          tmincels2(hist2_level+1:max_hist_level) = 'never'
3844       ENDIF
3845       tmaxcels2(1:max_hist_level) = 't_max(cels(X))'
3846       IF (hist2_level < max_hist_level) THEN
3847          tmaxcels2(hist2_level+1:max_hist_level) = 'never'
3848       ENDIF
3849!!$       tmax2(1:max_hist_level) = 't_max(X)'
3850!!$       IF (hist2_level < max_hist_level) THEN
3851!!$          tmax2(hist2_level+1:max_hist_level) = 'never'
3852!!$       ENDIF
3853       fluxop2(1:max_hist_level) = flux_op
3854       IF (hist2_level < max_hist_level) THEN
3855          fluxop2(hist2_level+1:max_hist_level) = 'never'
3856       ENDIF
3857!!$       fluxop_sc2(1:max_hist_level) = flux_sc
3858!!$       IF (hist2_level < max_hist_level) THEN
3859!!$          fluxop_sc2(hist2_level+1:max_hist_level) = 'never'
3860!!$       ENDIF
3861!!$       fluxop_insec2(1:max_hist_level) = flux_insec
3862!!$       IF (hist2_level < max_hist_level) THEN
3863!!$          fluxop_insec2(hist2_level+1:max_hist_level) = 'never'
3864!!$       ENDIF
3865       fluxop_scinsec2(1:max_hist_level) = flux_scinsec
3866       IF (hist2_level < max_hist_level) THEN
3867          fluxop_scinsec2(hist2_level+1:max_hist_level) = 'never'
3868       ENDIF
3869       once2(1:max_hist_level) = 'once(scatter(X))'
3870       IF (hist2_level < max_hist_level) THEN
3871          once2(hist2_level+1:max_hist_level) = 'never'
3872       ENDIF
3873       !
3874       IF ( .NOT. almaoutput ) THEN
3875          !-
3876          IF ( rectilinear ) THEN
3877#ifdef CPP_PARA
3878             CALL histbeg(histname2, iim, lon_rect, jjm, lat_rect, 1, iim, 1, jjm, &
3879                  &     istp_old, date0, dt, hori_id2, hist2_id,orch_domain_id)
3880#else
3881             CALL histbeg(histname2, iim, lon_rect, jjm, lat_rect, 1, iim, 1, jjm, &
3882                  &     istp_old, date0, dt, hori_id2, hist2_id)
3883#endif
3884             WRITE(numout,*)  'HISTBEG2 --->',istp_old,date0,dt,dw2,hist2_id
3885          ELSE
3886#ifdef CPP_PARA
3887             CALL histbeg(histname2, iim, lon, jjm, lat, 1, iim, 1, jjm, &
3888                  &     istp_old, date0, dt, hori_id2, hist2_id,domain_id=orch_domain_id)
3889#else
3890             CALL histbeg(histname2, iim, lon, jjm, lat, 1, iim, 1, jjm, &
3891                  &     istp_old, date0, dt, hori_id2, hist2_id)
3892#endif
3893          ENDIF
3894          !-
3895          CALL histvert(hist2_id, 'veget', 'Vegetation types', '1', &
3896               &    nvm,   veg, vegax_id2)
3897          CALL histvert(hist2_id, 'solth', 'Soil levels',      'm', &
3898               &    ngrnd, sol, solax_id2)
3899          CALL histvert(hist2_id, 'soiltyp', 'Soil types',      '1', &
3900               &    nstm, soltyp, soltax_id2)
3901          CALL histvert(hist2_id, 'nobio', 'Other surface types',      '1', &
3902               &    nnobio, nobiotyp, nobioax_id2)
3903          CALL histvert(hist2_id, 'albtyp', 'Albedo Types',     '1', &
3904               &    2, albtyp, albax_id2)
3905          IF (  control_flags%hydrol_cwrr ) THEN
3906             CALL histvert(hist2_id, 'solay', 'Hydrol soil levels',      'm', &
3907                  &    nslm, solay, solayax_id2)
3908          ENDIF
3909          !-
3910          !- SECHIBA_HISTLEVEL2 = 1
3911          !-
3912          CALL histdef(hist2_id, 'ptn', 'Deep ground temperature', 'K', &
3913               & iim,jjm, hori_id2, ngrnd, 1, ngrnd, solax_id2, 32, avescatter2(1),  dt, dw2)
3914          IF ( .NOT. control_flags%hydrol_cwrr ) THEN
3915             CALL histdef(hist2_id, 'mrsos', "Moisture in Upper 0.1 m of Soil Column", "kg m-2", &
3916                  & iim,jjm, hori_id2, 1, 1, 1, -99, 32, avescatter2(1), dt,dw2)
3917
3918             CALL histdef(hist2_id, 'mrro', "Total Runoff", "kg m-2 s-1", &
3919                  & iim,jjm, hori_id2, 1, 1, 1, -99, 32, avescatter2(1), dt,dw2)
3920          ENDIF
3921          !-
3922          !- SECHIBA_HISTLEVEL2 = 2
3923          !-
3924          CALL histdef(hist2_id, 'cdrag', 'Drag coefficient for LE and SH', '?',  &
3925               & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(2), dt, dw2)
3926          ! Ajouts Nathalie - Septembre 2008
3927          CALL histdef(hist2_id, 'soilalb_vis', 'Soil Albedo visible', '1', &
3928               & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(2), dt,dw2)
3929          CALL histdef(hist2_id, 'soilalb_nir', 'Soil Albedo near infrared', '1', &
3930               & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(2), dt,dw2)
3931          CALL histdef(hist2_id, 'vegalb_vis', 'Vegetation Albedo visible', '1', &
3932               & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(2), dt,dw2)
3933          CALL histdef(hist2_id, 'vegalb_nir', 'Vegetation Albedo near infrared', '1', &
3934               & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(2), dt,dw2)
3935          ! Fin ajouts Nathalie - Septembre 2008
3936          CALL histdef(hist2_id, 'z0', 'Surface roughness', 'm',  &
3937               & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(2), dt, dw2)
3938          CALL histdef(hist2_id, 'coastalflow', 'Diffuse coastal flow', 'm^3/s', &
3939               & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop_scinsec2(2), dt, dw2)
3940          CALL histdef(hist2_id, 'riverflow', 'River flow to the oceans', 'm^3/s', &
3941               & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop_scinsec2(2), dt, dw2) 
3942          CALL histdef(hist2_id, 'tsol_rad', 'Radiative surface temperature', 'C', &
3943               & iim,jjm, hori_id2, 1,1,1, -99, 32, avecels2(2), dt, dw2)
3944          CALL histdef(hist2_id, 'vevapnu', 'Bare soil evaporation', 'mm/d', &
3945               & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop2(2), dt, dw2)
3946          CALL histdef(hist2_id, 'temp_sol', 'New Surface Temperature', 'C', &
3947               & iim,jjm, hori_id2, 1,1,1, -99, 32, avecels2(2), dt, dw2)
3948          CALL histdef(hist2_id, 'qsurf', 'Near surface specific humidity', 'g/g',  &
3949               & iim,jjm, hori_id2, 1,1,1, -99, 32, ave2(2), dt, dw2)
3950          CALL histdef(hist2_id, 'albedo', 'Albedo', '1', &
3951               & iim,jjm, hori_id2, 2,1,2, albax_id2, 32, avescatter2(2), dt, dw2)
3952          CALL histdef(hist2_id, 'fluxsens', 'Sensible Heat Flux', 'W/m^2',  &
3953               & iim,jjm, hori_id2, 1,1,1, -99, 32, ave2(2), dt, dw2)
3954          CALL histdef(hist2_id, 'fluxlat', 'Latent Heat Flux', 'W/m^2',  &
3955               & iim,jjm, hori_id2, 1,1,1, -99, 32, ave2(2), dt, dw2)
3956          CALL histdef(hist2_id, 'emis', 'Surface emissivity', '?', &
3957               & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop2(2), dt, dw2)
3958          IF ( control_flags%ok_stomate .OR. control_flags%stomate_watchout ) THEN
3959             CALL histdef (hist2_id,'CO2FLUX','Total output CO2 flux', 'gC/day/(m^2 tot)', &
3960                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(2), dt, dw2)
3961          ENDIF
3962          !-
3963          !- SECHIBA_HISTLEVEL2 = 3
3964          !-
3965          CALL histdef(hist2_id, 'evap', 'Evaporation', 'mm/d', &
3966               & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop2(3), dt, dw2)
3967          CALL histdef(hist2_id, 'rain', 'Rainfall', 'mm/d',  &
3968               & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop2(3), dt, dw2)
3969          CALL histdef(hist2_id, 'snowf', 'Snowfall', 'mm/d',  &
3970               & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop2(3), dt, dw2)
3971          CALL histdef(hist2_id, 'netrad', 'Net radiation', 'W/m^2',  &
3972               & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(3), dt, dw2)
3973          CALL histdef(hist2_id, 'lai', 'Leaf Area Index', '1', &
3974               & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(3), dt, dw2)
3975          IF ( control_flags%river_routing ) THEN
3976             CALL histdef(hist2_id, 'basinmap', 'Aproximate map of the river basins', ' ', &
3977                  & iim,jjm, hori_id2, 1,1,1, -99, 32, once2(3), dt, dw2) 
3978             CALL histdef(hist2_id, 'nbrivers', 'Number or rivers in the outflow grid box', ' ', &
3979                  & iim,jjm, hori_id2, 1,1,1, -99, 32, once2(3), dt, dw2) 
3980          ENDIF
3981          !-
3982          !- SECHIBA_HISTLEVEL2 = 4
3983          !-
3984          CALL histdef(hist2_id, 'subli', 'Sublimation', 'mm/d', &
3985               & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop2(4), dt, dw2)
3986          CALL histdef(hist2_id, 'runoff', 'Surface runoff', 'mm/d', &
3987               & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop2(4), dt, dw2)
3988          CALL histdef(hist2_id, 'drainage', 'Deep drainage', 'mm/d', &
3989               & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop2(4), dt, dw2)
3990          IF ( control_flags%river_routing ) THEN
3991             CALL histdef(hist2_id, 'riversret', 'Return from endorheic rivers', 'mm/d', &
3992                  & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop2(4), dt, dw2)
3993             CALL histdef(hist2_id, 'hydrographs', 'Hydrographs of gridbox outflow', 'm^3/s', &
3994                  & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop_scinsec2(4), dt, dw2)
3995          ENDIF
3996          IF ( control_flags%hydrol_cwrr ) THEN
3997             CALL histdef(hist2_id, 'evapnu_soil', 'Bare soil evap for soil type', 'mm/d', &
3998                  & iim,jjm, hori_id2, nstm, 1, nstm, soltax_id2, 32, fluxop2(4), dt, dw2)
3999             CALL histdef(hist2_id, 'drainage_soil', 'Drainage for soil type', 'mm/d', &
4000                  & iim,jjm, hori_id2, nstm, 1, nstm, soltax_id2, 32, fluxop2(4), dt, dw2)
4001             CALL histdef(hist2_id, 'transpir_soil', 'Transpir for soil type', 'mm/d', &
4002                  & iim,jjm, hori_id2, nstm, 1, nstm, soltax_id2, 32, fluxop2(4), dt, dw2)
4003             CALL histdef(hist2_id, 'runoff_soil', 'Runoff for soil type', 'mm/d', &
4004                  & iim,jjm, hori_id2, nstm, 1, nstm, soltax_id2, 32, fluxop2(4), dt, dw2)
4005          ENDIF
4006          !
4007          CALL histdef(hist2_id, 'tair', 'Air Temperature', 'K',  &
4008               & iim,jjm, hori_id2, 1,1,1, -99, 32, ave2(4), dt, dw2)
4009          CALL histdef(hist2_id, 'qair', 'Air humidity', 'g/g',  &
4010               & iim,jjm, hori_id2, 1,1,1, -99, 32, ave2(4), dt, dw2)
4011          ! Ajouts Nathalie - Juillet 2006
4012          CALL histdef(hist2_id, 'q2m', '2m Air humidity', 'g/g',  &
4013               & iim,jjm, hori_id2, 1,1,1, -99, 32, ave2(4), dt, dw2)
4014          CALL histdef(hist2_id, 't2m', '2m Air Temperature', 'K',  &
4015               & iim,jjm, hori_id2, 1,1,1, -99, 32, ave2(4), dt, dw2)
4016          ! Fin ajouts Nathalie
4017          CALL histdef(hist2_id, 'alb_vis', 'Albedo visible', '1', &
4018               & iim,jjm, hori_id2, 1,1,1, -99, 32, ave2(4), dt, dw2)
4019          CALL histdef(hist2_id, 'alb_nir', 'Albedo near infrared', '1', &
4020               & iim,jjm, hori_id2, 1,1,1, -99, 32, ave2(4), dt, dw2)
4021          CALL histdef(hist2_id, 'roughheight', 'Effective roughness height', 'm',  &
4022               & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(4), dt, dw2)
4023          CALL histdef(hist2_id, 'transpir', 'Transpiration', 'mm/d', &
4024               & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, fluxop2(4), dt, dw2)
4025          CALL histdef(hist2_id, 'inter', 'Interception loss', 'mm/d', &
4026               & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, fluxop2(4), dt, dw2)
4027          !-
4028          !- SECHIBA_HISTLEVEL2 = 5
4029          !-
4030          CALL histdef(hist2_id, 'tsol_max', 'Maximum Surface Temperature',&
4031               & 'C', iim,jjm, hori_id2, 1,1,1, -99, 32, tmaxcels2(5), dt, dw2)
4032          CALL histdef(hist2_id, 'tsol_min', 'Minimum Surface Temperature',&
4033               & 'C', iim,jjm, hori_id2, 1,1,1, -99, 32, tmincels2(5), dt, dw2)
4034          CALL histdef(hist2_id, 'snow', 'Snow mass', 'kg/m^2', &
4035               & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(5), dt, dw2)
4036          CALL histdef(hist2_id, 'snowage', 'Snow age', '?', &
4037               & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(5), dt, dw2)
4038          CALL histdef(hist2_id, 'snownobio', 'Snow on other surfaces', 'kg/m^2', &
4039               & iim,jjm, hori_id2, nnobio,1, nnobio, nobioax_id2, 32, avescatter2(5), dt, dw2)
4040          CALL histdef(hist2_id, 'snownobioage', 'Snow age on other surfaces', 'd', &
4041               & iim,jjm, hori_id2, nnobio,1, nnobio, nobioax_id2, 32, avescatter2(5), dt, dw2)
4042          CALL histdef(hist2_id, 'vegetfrac', 'Fraction of vegetation', '1', &
4043               & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(5), dt, dw2)
4044          CALL histdef(hist2_id, 'maxvegetfrac', 'Maximum fraction of vegetation', '1', &
4045               & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(5), dt, dw2)
4046          CALL histdef(hist2_id, 'nobiofrac', 'Fraction of other surface types', '1', &
4047               & iim,jjm, hori_id2, nnobio, 1, nnobio, nobioax_id2, 32, avescatter2(5), dt, dw2)
4048          IF ( control_flags%hydrol_cwrr ) THEN
4049             DO jst=1,nstm
4050
4051                ! var_name= "mc_1" ... "mc_3"
4052                WRITE (var_name,"('moistc_',i1)") jst
4053                CALL histdef(hist2_id, var_name, 'Soil Moisture profile for soil type', '%', &
4054                     & iim,jjm, hori_id2, nslm, 1, nslm, solayax_id2, 32, avescatter2(5), dt, dw2)
4055
4056                ! var_name= "vegetsoil_1" ... "vegetsoil_3"
4057                WRITE (var_name,"('vegetsoil_',i1)") jst
4058                CALL histdef(hist2_id, var_name, 'Fraction of vegetation on soil types', '%', &
4059                     & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(5), dt, dw2)
4060
4061             ENDDO
4062          ENDIF
4063          !-
4064          !- SECHIBA_HISTLEVEL2 = 6
4065          !-
4066          IF ( .NOT. control_flags%hydrol_cwrr ) THEN
4067             CALL histdef(hist2_id, 'dss', 'Up-reservoir Height', 'm',  &
4068                  & iim,jjm, hori_id, nvm, 1, nvm, vegax_id, 32, avescatter2(6), dt,dw)
4069             CALL histdef(hist2_id, 'gqsb', 'Upper Soil Moisture', '1',  &
4070                  & iim,jjm, hori_id2, 1, 1, 1, -99, 32, avescatter2(6), dt, dw2)
4071             CALL histdef(hist2_id, 'bqsb', 'Lower Soil Moisture', '1',  &
4072                  & iim,jjm, hori_id2, 1, 1, 1, -99, 32, avescatter2(6), dt, dw2)
4073          ELSE
4074             CALL histdef(hist2_id, 'humtot', 'Total Soil Moisture', 'Kg/m2', &
4075                  & iim,jjm, hori_id2, 1, 1, 1, -99, 32, avescatter2(6), dt, dw2)
4076             CALL histdef(hist2_id, 'humtot_soil', 'Soil Moisture for soil type', 'Kg/m2', &
4077                  & iim,jjm, hori_id2, nstm, 1, nstm, soltax_id2, 32, avescatter2(6), dt, dw2)
4078          ENDIF
4079          CALL histdef(hist2_id, 'qsintveg', 'Water on canopy', 'Kg/m^2', &
4080               & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(6), dt, dw2)
4081          CALL histdef(hist2_id, 'rstruct', 'Structural resistance', 's/m', &
4082               & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(6), dt, dw2)
4083          IF ( control_flags%ok_co2 ) THEN
4084             CALL histdef(hist2_id, 'gpp', 'Net assimilation of carbon by the vegetation', 'gC/m^2/s', &
4085                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, fluxop_scinsec2(6), dt,dw2)
4086          ENDIF
4087          IF ( control_flags%ok_stomate ) THEN
4088             CALL histdef(hist2_id, 'nee', 'Net Ecosystem Exchange', 'gC/m^2/s', &
4089                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, fluxop_scinsec2(2), dt,dw2)
4090             CALL histdef(hist2_id, 'maint_resp', 'Maintenance respiration', 'gC/m^2/s', &
4091                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, fluxop_scinsec2(2), dt,dw2)
4092             CALL histdef(hist2_id, 'hetero_resp', 'Heterotrophic respiration', 'gC/m^2/s', &
4093                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, fluxop_scinsec2(2), dt,dw2)
4094             CALL histdef(hist2_id, 'growth_resp', 'Growth respiration', 'gC/m^2/s', &
4095                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, fluxop_scinsec2(2), dt, dw2)
4096             CALL histdef(hist2_id, 'npp', 'Net Primary Production', 'gC/m^2/s', &
4097                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, fluxop_scinsec2(2), dt, dw2)
4098          ENDIF
4099          CALL histdef(hist2_id, 'precisol', 'Throughfall', 'mm/d',  &
4100               & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, fluxop2(6), dt, dw2)
4101          CALL histdef(hist2_id, 'drysoil_frac', 'Fraction of visibly dry soil', '1',  &
4102               & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(6), dt, dw2)
4103          CALL histdef(hist2_id, 'evapot', 'Potential evaporation', 'mm/d',  &
4104               & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop2(6), dt, dw2)
4105          CALL histdef(hist2_id, 'evapot_corr', 'Potential evaporation', 'mm/d',  &
4106               & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop2(6), dt, dw2)
4107          !-
4108          !- SECHIBA_HISTLEVEL2 = 7
4109          !-
4110          CALL histdef(hist2_id, 'swnet', 'Net solar radiation', 'W/m^2',  &
4111               & iim,jjm, hori_id2, 1,1,1, -99, 32, ave2(7), dt, dw2)
4112          CALL histdef(hist2_id, 'swdown', 'Incident solar radiation', 'W/m^2',  &
4113               & iim,jjm, hori_id2, 1,1,1, -99, 32, ave2(7), dt, dw2)
4114          CALL histdef(hist2_id, 'lwdown', 'Absorbed downward longwave radiation', 'W/m^2',  &
4115               & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(7), dt, dw2)
4116          CALL histdef(hist2_id, 'lwnet', 'Net surface longwave radiation', 'W/m^2',  &
4117               & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(7), dt, dw2)
4118          CALL histdef(hist2_id, 'temp_pheno', 'Temperature for Pheno', 'K',  &
4119               & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(7), dt, dw2)
4120          !-
4121          !- SECHIBA_HISTLEVEL2 = 8
4122          !-
4123          IF ( control_flags%river_routing ) THEN
4124             CALL histdef(hist2_id, 'fastr', 'Fast flow reservoir', 'kg/m^2', &
4125                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(8), dt, dw2)
4126             CALL histdef(hist2_id, 'slowr', 'Slow flow reservoir', 'kg/m^2', &
4127                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(8), dt, dw2)
4128             CALL histdef(hist2_id, 'streamr', 'Stream flow reservoir', 'kg/m^2', &
4129                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(8), dt, dw2)
4130             CALL histdef(hist2_id, 'lakevol', 'Volume in lake reservoir', 'kg/m^2', &
4131                  & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(8), dt, dw2)
4132             CALL histdef(hist2_id, 'irrigation', 'Net irrigation', 'mm/d', &
4133                  & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop2(8), dt, dw2)
4134             CALL histdef(hist2_id, 'netirrig', 'Net irrigation requirement', 'mm/d', &
4135                  & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop2(8), dt, dw2)
4136             CALL histdef(hist2_id, 'irrigmap', 'Map of irrigated areas', 'm^2', &
4137                  & iim,jjm, hori_id2, 1,1,1, -99, 32, once2(8), dt, dw2)
4138          ENDIF
4139          !-
4140          !- SECHIBA_HISTLEVEL2 = 9
4141          !-
4142          CALL histdef(hist2_id, 'beta', 'Beta Function', '1',  &
4143               & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(9), dt, dw2)
4144          CALL histdef(hist2_id, 'raero', 'Aerodynamic resistance', 's/m',  &
4145               & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(9), dt, dw2)
4146          ! Ajouts Nathalie - Novembre 2006
4147          CALL histdef(hist2_id, 'Wind', 'Wind speed', 'm/s',  &
4148               & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(9), dt, dw2)
4149          ! Fin ajouts Nathalie
4150          CALL histdef(hist2_id, 'qsatt' , 'Surface saturated humidity', 'g/g', &
4151               & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(9), dt, dw2)
4152          CALL histdef(hist2_id, 'vbeta1', 'Beta for sublimation', '1',  &
4153               & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(9), dt, dw2)
4154          CALL histdef(hist2_id, 'vbeta4', 'Beta for bare soil', '1',  &
4155               & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(9), dt, dw2)
4156          CALL histdef(hist2_id, 'vbetaco2', 'beta for CO2', 'mm/d', &
4157               & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(9), dt, dw2)
4158          CALL histdef(hist2_id, 'soiltype', 'Fraction of soil textures', '%', &
4159               & iim,jjm, hori_id2, nstm, 1, nstm, soltax_id2, 32, once2(9),  dt, dw2)
4160          CALL histdef(hist2_id, 'humrel', 'Soil moisture stress', '1',  &
4161               & iim,jjm, hori_id2, nvm,1,nvm, vegax_id2, 32, avescatter2(9), dt, dw2)
4162          !-
4163          !- SECHIBA_HISTLEVEL2 = 10
4164          !-
4165          CALL histdef(hist2_id, 'cimean', 'Stomatal CO2 concentation', 'mmole/m2/s', &
4166               & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt, dw2)
4167          CALL histdef(hist2_id, 'vbeta3', 'Beta for Transpiration', 'mm/d', &
4168               & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt, dw2)
4169          CALL histdef(hist2_id, 'rveget', 'Canopy resistance', 's/m', &
4170               & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt, dw2)
4171          CALL histdef(hist2_id, 'rsol', 'Soil resistance', 's/m',  &
4172               & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(10), dt, dw2)
4173          CALL histdef(hist2_id,'vbeta2','Beta for Interception loss','mm/d', &
4174               & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt, dw2)
4175          CALL histdef(hist2_id, 'qsintmax', 'Maximum Interception capacity', 'Kg/m^2', &
4176               & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(10), dt, dw2)
4177          !
4178       ELSE 
4179          !-
4180          !- This is the ALMA convention output now
4181          !-
4182          !-
4183          IF ( rectilinear ) THEN
4184#ifdef CPP_PARA
4185             CALL histbeg(histname2, iim, lon_rect, jjm, lat_rect, 1, iim, 1, jjm, &
4186                  &     istp_old, date0, dt, hori_id2, hist2_id,orch_domain_id)
4187#else
4188             CALL histbeg(histname2, iim, lon_rect, jjm, lat_rect, 1, iim, 1, jjm, &
4189                  &     istp_old, date0, dt, hori_id2, hist2_id)
4190#endif
4191             WRITE(numout,*)  'HISTBEG2 --->',istp_old,date0,dt,dw2,hist2_id
4192          ELSE
4193#ifdef CPP_PARA
4194             CALL histbeg(histname2, iim, lon, jjm, lat, 1, iim, 1, jjm, &
4195                  &     istp_old, date0, dt, hori_id2, hist2_id,domain_id=orch_domain_id)
4196#else
4197             CALL histbeg(histname2, iim, lon, jjm, lat, 1, iim, 1, jjm, &
4198                  &     istp_old, date0, dt, hori_id2, hist2_id)
4199#endif
4200          ENDIF
4201          !-
4202          CALL histvert(hist2_id, 'veget', 'Vegetation types', '1', &
4203               &    nvm,   veg, vegax_id2)
4204          CALL histvert(hist2_id, 'solth', 'Soil levels',      'm', &
4205               &    ngrnd, sol, solax_id2)
4206          CALL histvert(hist2_id, 'soiltyp', 'Soil types',      '1', &
4207               &    nstm, soltyp, soltax_id2)
4208          CALL histvert(hist2_id, 'nobio', 'Other surface types',      '1', &
4209               &    nnobio, nobiotyp, nobioax_id2)
4210          IF (  control_flags%hydrol_cwrr ) THEN
4211             CALL histvert(hist2_id, 'solay', 'Hydrol soil levels',      'm', &
4212                  &    nslm, solay, solayax_id2)
4213          ENDIF
4214          !-
4215          !-  Vegetation
4216          !-
4217          CALL histdef(hist2_id, 'vegetfrac', 'Fraction of vegetation', '1', &
4218               & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(3), dt, dw2)
4219          CALL histdef(hist2_id, 'maxvegetfrac', 'Maximum fraction of vegetation', '1', &
4220               & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(3), dt, dw2)
4221          CALL histdef(hist2_id, 'nobiofrac', 'Fraction of other surface types', '1', &
4222               & iim,jjm, hori_id2, nnobio, 1, nnobio, nobioax_id2, 32, avescatter2(3), dt, dw2)
4223          IF ( control_flags%ok_stomate .OR. control_flags%stomate_watchout ) THEN
4224             CALL histdef (hist2_id,'CO2FLUX','Total output CO2 flux', 'gC/day/(m^2 tot)', &
4225                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, avescatter2(1), dt, dw2)
4226          ENDIF
4227          !-
4228          !-  General energy balance
4229          !-
4230          CALL histdef(hist2_id, 'SWnet', 'Net shortwave radiation', 'W/m^2',  &
4231               & iim,jjm, hori_id2, 1,1,1, -99, 32, ave2(1), dt, dw2)
4232          CALL histdef(hist2_id, 'LWnet', 'Net longwave radiation', 'W/m^2',  &
4233               & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(1), dt, dw2)
4234          CALL histdef(hist2_id, 'Qh', 'Sensible heat flux', 'W/m^2',  &
4235               & iim,jjm, hori_id2, 1,1,1, -99, 32, ave2(1), dt, dw2)
4236          CALL histdef(hist2_id, 'Qle', 'Latent heat flux', 'W/m^2',  &
4237               & iim,jjm, hori_id2, 1,1,1, -99, 32, ave2(1), dt, dw2)
4238          CALL histdef(hist2_id, 'Qg', 'Ground heat flux', 'W/m^2',  &
4239               & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(1), dt, dw2)
4240          CALL histdef(hist2_id, 'Qf', 'Energy of fusion', 'W/m^2',  &
4241               & iim,jjm, hori_id2, 1,1,1, -99, 32, ave2(2), dt, dw2)
4242          CALL histdef(hist2_id, 'Qv', 'Energy of sublimation', 'W/m^2',  &
4243               & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(1), dt, dw2)
4244          CALL histdef(hist2_id, 'DelSurfHeat', 'Change in surface layer heat', 'J/m^2',  &
4245               & iim,jjm, hori_id2, 1,1,1, -99, 32, sumscatter2(1), dt, dw2)
4246          CALL histdef(hist2_id, 'DelColdCont', 'Change in snow surface layer cold content', 'J/m^2',  &
4247               & iim,jjm, hori_id2, 1,1,1, -99, 32, sumscatter2(1), dt, dw2)
4248          !-
4249          !- General water balance
4250          !-
4251          CALL histdef(hist2_id, 'Snowf', 'Snowfall rate', 'kg/m^2/s',  &
4252               & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop_scinsec2(1), dt, dw2)
4253          CALL histdef(hist2_id, 'Rainf', 'Rainfall rate', 'kg/m^2/s',  &
4254               & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop_scinsec2(1), dt, dw2)
4255          CALL histdef(hist2_id, 'Evap', 'Total Evapotranspiration', 'kg/m^2/s', &
4256               & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop_scinsec2(1), dt, dw2)
4257          CALL histdef(hist2_id, 'Qs', 'Surface runoff', 'kg/m^2/s', &
4258               & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop_scinsec2(1), dt, dw2)
4259          CALL histdef(hist2_id, 'Qsb', 'Sub-surface runoff', 'kg/m^2/s', &
4260               & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop_scinsec2(1), dt, dw2)
4261          CALL histdef(hist2_id, 'Qsm', 'Snowmelt', 'kg/m^2/s', &
4262               & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop_scinsec2(1), dt, dw2)
4263          CALL histdef(hist2_id, 'DelSoilMoist', 'Change in soil moisture', 'kg/m^2',  &
4264               & iim,jjm, hori_id2, 1, 1, 1, -99, 32, sumscatter2(1), dt, dw2)
4265          CALL histdef(hist2_id, 'DelSWE', 'Change in SWE','kg/m^2',&
4266               & iim,jjm, hori_id2, 1, 1, 1, -99, 32, sumscatter2(1), dt, dw2)
4267          CALL histdef(hist2_id, 'DelIntercept', 'Change in interception storage', 'kg/m^2',  &
4268               & iim,jjm, hori_id2, 1, 1, 1, -99, 32, sumscatter2(1), dt, dw2)
4269          !-
4270          !- Surface state
4271          !-
4272          CALL histdef(hist2_id, 'AvgSurfT', 'Average surface temperature', 'K', &
4273               & iim,jjm, hori_id2, 1,1,1, -99, 32, ave2(1), dt, dw2)
4274          CALL histdef(hist2_id, 'RadT', 'Surface radiative temperature', 'K', &
4275               & iim,jjm, hori_id2, 1,1,1, -99, 32, ave2(1), dt, dw2)
4276          CALL histdef(hist2_id, 'Albedo', 'Albedo', '1', &
4277               & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(1), dt, dw2)
4278          CALL histdef(hist2_id, 'SWE', '3D soil water equivalent','kg/m^2',  &
4279               & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(1), dt, dw2)
4280          !!-
4281          !-  Sub-surface state
4282          !-
4283          IF ( .NOT. control_flags%hydrol_cwrr ) THEN
4284             CALL histdef(hist2_id, 'SoilMoist', '3D average layer soil moisture', 'kg/m^2',  &
4285                  & iim,jjm, hori_id2, 1, 1, 1, -99, 32, avescatter2(1), dt, dw2)
4286          ELSE
4287             CALL histdef(hist2_id, 'SoilMoist', '3D average layer soil moisture', 'kg/m^2',  &
4288                  & iim,jjm, hori_id2, nslm, 1, nslm, solayax_id2, 32, avescatter2(1), dt, dw2)
4289          ENDIF
4290          CALL histdef(hist2_id, 'SoilWet', 'Total soil wetness', 'kg/m^2',  &
4291               & iim,jjm, hori_id2, 1, 1, 1, -99, 32, avescatter2(1), dt, dw2)
4292          CALL histdef(hist2_id, 'SoilTemp', '3D layer average soil temperature', 'K', &
4293               & iim,jjm, hori_id2, ngrnd, 1, ngrnd, solax_id2, 32, avescatter2(1), dt, dw2)
4294          !-
4295          !-  Evaporation components
4296          !-
4297          CALL histdef(hist2_id, 'PotEvap', 'Potential evapotranspiration', 'kg/m^2/s', &
4298               & iim,jjm, hori_id2, 1, 1, 1, -99, 32, fluxop_scinsec2(1), dt, dw2)
4299          CALL histdef(hist2_id, 'ECanop', 'Interception evaporation', 'kg/m^2/s', &
4300               & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, fluxop_scinsec2(1), dt, dw2)
4301          CALL histdef(hist2_id, 'TVeg', 'Transpiration', 'kg/m^2/s', &
4302               & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, fluxop_scinsec2(1), dt, dw2)
4303          CALL histdef(hist2_id, 'ESoil', 'Bare soil evaporation', 'kg/m^2/s', &
4304               & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop_scinsec2(1), dt, dw2)
4305          CALL histdef(hist2_id, 'RootMoist','Root zone soil water', 'kg/m^2',  &
4306               & iim,jjm, hori_id2, 1, 1, 1, -99, 32, avescatter2(1), dt, dw2)
4307          CALL histdef(hist2_id, 'SubSnow','Snow sublimation','kg/m^2/s', &
4308               & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop_scinsec2(1), dt, dw2)
4309          CALL histdef(hist2_id, 'ACond', 'Aerodynamic conductance', 'm/s',  &
4310               & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(1), dt, dw2)
4311          !-
4312          !-
4313          !-  Cold Season Processes
4314          !-
4315          CALL histdef(hist2_id, 'SnowFrac', 'Snow cover fraction', '1',  &
4316               & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(1), dt, dw2)
4317          CALL histdef(hist2_id, 'SAlbedo', 'Snow albedo', '1', &
4318               & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(1), dt, dw2)
4319          CALL histdef(hist2_id, 'SnowDepth', '3D snow depth', 'm', &
4320               & iim,jjm, hori_id2, 1,1,1, -99, 32, avescatter2(1), dt, dw2)
4321          !-
4322          !- Hydrologic variables
4323          !-
4324          CALL histdef(hist2_id, 'IrrigationMap', 'Map of irrigated areas', 'm^2', &
4325               & iim,jjm, hori_id2, 1,1,1, -99, 32, once2(7), dt, dw2)
4326          CALL histdef(hist2_id, 'dis', 'Simulated River Discharge', 'm^3/s', &
4327               & iim,jjm, hori_id2, 1,1,1, -99, 32, fluxop_scinsec2(2), dt, dw2)
4328          CALL histdef(hist2_id, 'humrel', 'Soil moisture stress', '1',  &
4329               & iim,jjm, hori_id2, nvm,1,nvm, vegax_id2, 32, avescatter2(9), dt, dw2)
4330          !-
4331          !-  The carbon budget
4332          !-
4333          IF ( control_flags%ok_co2 ) THEN
4334             CALL histdef(hist2_id, 'GPP', 'Net assimilation of carbon by the vegetation', 'gC/m^2/s', &
4335                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, fluxop_scinsec2(1), dt, dw2)
4336          ENDIF
4337          IF ( control_flags%ok_stomate ) THEN
4338             CALL histdef(hist2_id, 'NEE', 'Net Ecosystem Exchange', 'gC/m^2/s', &
4339                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, fluxop_scinsec2(1), dt,dw2)
4340             CALL histdef(hist2_id, 'maint_resp', 'Maintenance respiration', 'gC/m^2/s', &
4341                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, fluxop_scinsec2(1), dt,dw2)
4342             CALL histdef(hist2_id, 'hetero_resp', 'Heterotrophic respiration', 'gC/m^2/s', &
4343                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, fluxop_scinsec2(1), dt,dw2)
4344             CALL histdef(hist2_id, 'growth_resp', 'Growth respiration', 'gC/m^2/s', &
4345                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, fluxop_scinsec2(1), dt, dw2)
4346             CALL histdef(hist2_id, 'npp', 'Net Primary Production', 'gC/m^2/s', &
4347                  & iim,jjm, hori_id2, nvm, 1, nvm, vegax_id2, 32, fluxop_scinsec2(1), dt, dw2)
4348          ENDIF
4349          !
4350       ENDIF
4351       !-
4352       CALL histdef(hist2_id, 'LandPoints', 'Land Points', '1', &
4353            & iim,jjm, hori_id2, 1,1,1, -99, 32, once2(1), dt, dw2) 
4354       CALL histdef(hist2_id, 'Areas', 'Mesh areas', 'm2', &
4355            & iim,jjm, hori_id2, 1,1,1, -99, 32, once2(1), dt, dw2)
4356       CALL histdef(hist2_id, 'Contfrac', 'Continental fraction', '1', &
4357            & iim,jjm, hori_id2, 1,1,1, -99, 32, once2(1), dt, dw2)
4358       !-
4359       CALL histend(hist2_id)
4360    ENDIF
4361    !-
4362    !=====================================================================
4363    !- 3.2 STOMATE's history file
4364    !=====================================================================
4365    IF ( control_flags%ok_stomate ) THEN
4366       !-
4367       ! STOMATE IS ACTIVATED
4368       !-
4369       !Config  Key  = STOMATE_OUTPUT_FILE
4370       !Config  Desc = Name of file in which STOMATE's output is going
4371       !Config         to be written
4372       !Config  Def  = stomate_history.nc
4373       !Config  Help = This file is going to be created by the model
4374       !Config         and will contain the output from the model.
4375       !Config         This file is a truly COADS compliant netCDF file.
4376       !Config         It will be generated by the hist software from
4377       !Config         the IOIPSL package.
4378       !-
4379       stom_histname='stomate_history.nc'
4380       CALL getin_p('STOMATE_OUTPUT_FILE', stom_histname)       
4381       WRITE(numout,*) 'STOMATE_OUTPUT_FILE', TRIM(stom_histname)
4382       !-
4383       !Config  Key  = STOMATE_HIST_DT
4384       !Config  Desc = STOMATE history time step (d)
4385       !Config  Def  = 10.
4386       !Config  Help = Time step of the STOMATE history file
4387       !-
4388       hist_days_stom = 10.
4389       CALL getin_p('STOMATE_HIST_DT', hist_days_stom)       
4390       IF ( hist_days_stom == -1. ) THEN
4391          hist_dt_stom = -1.
4392          WRITE(numout,*) 'output frequency for STOMATE history file (d): one month.'
4393       ELSE
4394          hist_dt_stom = NINT( hist_days_stom ) * one_day
4395          WRITE(numout,*) 'output frequency for STOMATE history file (d): ', &
4396               hist_dt_stom/one_day
4397       ENDIF
4398
4399       ! test consistency between STOMATE_HIST_DT and DT_SLOW parameters
4400       dt_slow_ = one_day
4401       CALL getin_p('DT_SLOW', dt_slow_)
4402       IF ( hist_days_stom /= -1. ) THEN
4403          IF (dt_slow_ > hist_dt_stom) THEN
4404             WRITE(numout,*) "DT_SLOW = ",dt_slow_,"  , STOMATE_HIST_DT = ",hist_dt_stom
4405             CALL ipslerr (3,'intsurf_history', &
4406                  &          'Problem with DT_SLOW > STOMATE_HIST_DT','', &
4407                  &          '(must be less or equal)')
4408          ENDIF
4409       ENDIF
4410       !-
4411       !- initialize
4412       IF ( rectilinear ) THEN
4413#ifdef CPP_PARA
4414          CALL histbeg(stom_histname, iim, lon_rect, jjm, lat_rect,  1, iim, 1, jjm, &
4415               &     istp_old, date0, dt, hori_id, hist_id_stom,domain_id=orch_domain_id)
4416#else
4417          CALL histbeg(stom_histname, iim, lon_rect, jjm, lat_rect,  1, iim, 1, jjm, &
4418               &     istp_old, date0, dt, hori_id, hist_id_stom)
4419#endif
4420       ELSE
4421#ifdef CPP_PARA
4422          CALL histbeg(stom_histname, iim, lon, jjm, lat,  1, iim, 1, jjm, &
4423               &     istp_old, date0, dt, hori_id, hist_id_stom,domain_id=orch_domain_id)
4424#else
4425          CALL histbeg(stom_histname, iim, lon, jjm, lat,  1, iim, 1, jjm, &
4426               &     istp_old, date0, dt, hori_id, hist_id_stom)
4427#endif
4428       ENDIF
4429       !- define PFT axis
4430       hist_PFTaxis = (/ ( REAL(i,r_std), i=1,nvm ) /)
4431       !- declare this axis
4432       CALL histvert (hist_id_stom, 'PFT', 'Plant functional type', &
4433            & '1', nvm, hist_PFTaxis, hist_PFTaxis_id)
4434! deforestation
4435       !- define Pool_10 axis
4436       hist_pool_10axis = (/ ( REAL(i,r_std), i=1,10 ) /)
4437       !- declare this axis
4438       CALL histvert (hist_id_stom, 'P10', 'Pool 10 years', &
4439            & '1', 10, hist_pool_10axis, hist_pool_10axis_id)
4440
4441       !- define Pool_100 axis
4442       hist_pool_100axis = (/ ( REAL(i,r_std), i=1,100 ) /)
4443       !- declare this axis
4444       CALL histvert (hist_id_stom, 'P100', 'Pool 100 years', &
4445            & '1', 100, hist_pool_100axis, hist_pool_100axis_id)
4446
4447       !- define Pool_11 axis
4448       hist_pool_11axis = (/ ( REAL(i,r_std), i=1,11 ) /)
4449       !- declare this axis
4450       CALL histvert (hist_id_stom, 'P11', 'Pool 10 years + 1', &
4451            & '1', 11, hist_pool_11axis, hist_pool_11axis_id)
4452
4453       !- define Pool_101 axis
4454       hist_pool_101axis = (/ ( REAL(i,r_std), i=1,101 ) /)
4455       !- declare this axis
4456       CALL histvert (hist_id_stom, 'P101', 'Pool 100 years + 1', &
4457            & '1', 101, hist_pool_101axis, hist_pool_101axis_id)
4458
4459       !- define STOMATE history file
4460       CALL stom_define_history (hist_id_stom, nvm, iim, jjm, &
4461            & dt, hist_dt_stom, hori_id, hist_PFTaxis_id, &
4462            & hist_pool_10axis_id, hist_pool_100axis_id, &
4463            & hist_pool_11axis_id, hist_pool_101axis_id)
4464! deforestation axis added as arguments
4465
4466       !- end definition
4467       CALL histend(hist_id_stom)
4468       !-
4469       !-
4470       !-
4471       ! STOMATE IPCC OUTPUTS IS ACTIVATED
4472       !-
4473       !Config  Key  = STOMATE_IPCC_OUTPUT_FILE
4474       !Config  Desc = Name of file in which STOMATE's output is going
4475       !Config         to be written
4476       !Config  Def  = stomate_ipcc_history.nc
4477       !Config  Help = This file is going to be created by the model
4478       !Config         and will contain the output from the model.
4479       !Config         This file is a truly COADS compliant netCDF file.
4480       !Config         It will be generated by the hist software from
4481       !Config         the IOIPSL package.
4482       !-
4483       stom_ipcc_histname='stomate_ipcc_history.nc'
4484       CALL getin_p('STOMATE_IPCC_OUTPUT_FILE', stom_ipcc_histname)       
4485       WRITE(numout,*) 'STOMATE_IPCC_OUTPUT_FILE', TRIM(stom_ipcc_histname)
4486       !-
4487       !Config  Key  = STOMATE_IPCC_HIST_DT
4488       !Config  Desc = STOMATE IPCC history time step (d)
4489       !Config  Def  = 0.
4490       !Config  Help = Time step of the STOMATE IPCC history file
4491       !-
4492       hist_days_stom_ipcc = 0.
4493       CALL getin_p('STOMATE_IPCC_HIST_DT', hist_days_stom_ipcc)       
4494       IF ( hist_days_stom_ipcc == -1. ) THEN
4495          hist_dt_stom_ipcc = -1.
4496          WRITE(numout,*) 'output frequency for STOMATE IPCC history file (d): one month.'
4497       ELSE
4498          hist_dt_stom_ipcc = NINT( hist_days_stom_ipcc ) * one_day
4499          WRITE(numout,*) 'output frequency for STOMATE IPCC history file (d): ', &
4500            hist_dt_stom_ipcc/one_day
4501       ENDIF
4502
4503       ! test consistency between STOMATE_IPCC_HIST_DT and DT_SLOW parameters
4504       dt_slow_ = one_day
4505       CALL getin_p('DT_SLOW', dt_slow_)
4506       IF ( hist_days_stom_ipcc > 0. ) THEN
4507          IF (dt_slow_ > hist_dt_stom_ipcc) THEN
4508             WRITE(numout,*) "DT_SLOW = ",dt_slow_,"  , STOMATE_IPCC_HIST_DT = ",hist_dt_stom_ipcc
4509             CALL ipslerr (3,'intsurf_history', &
4510                  &          'Problem with DT_SLOW > STOMATE_IPCC_HIST_DT','', &
4511                  &          '(must be less or equal)')
4512          ENDIF
4513       ENDIF
4514
4515       IF ( hist_dt_stom_ipcc == 0 ) THEN
4516          hist_id_stom_ipcc = -1
4517       ELSE
4518          !-
4519          !- initialize
4520          IF ( rectilinear ) THEN
4521#ifdef CPP_PARA
4522             CALL histbeg(stom_ipcc_histname, iim, lon_rect, jjm, lat_rect,  1, iim, 1, jjm, &
4523                  &     istp_old, date0, dt, hori_id, hist_id_stom_ipcc,domain_id=orch_domain_id)
4524#else
4525             CALL histbeg(stom_ipcc_histname, iim, lon_rect, jjm, lat_rect,  1, iim, 1, jjm, &
4526                  &     istp_old, date0, dt, hori_id, hist_id_stom_ipcc)
4527#endif
4528          ELSE
4529#ifdef CPP_PARA
4530             CALL histbeg(stom_ipcc_histname, iim, lon, jjm, lat,  1, iim, 1, jjm, &
4531                  &     istp_old, date0, dt, hori_id, hist_id_stom_ipcc,domain_id=orch_domain_id)
4532#else
4533             CALL histbeg(stom_ipcc_histname, iim, lon, jjm, lat,  1, iim, 1, jjm, &
4534                  &     istp_old, date0, dt, hori_id, hist_id_stom_ipcc)
4535#endif
4536          ENDIF
4537          !- declare this axis
4538          CALL histvert (hist_id_stom_IPCC, 'PFT', 'Plant functional type', &
4539               & '1', nvm, hist_PFTaxis, hist_IPCC_PFTaxis_id)
4540
4541          !- define STOMATE history file
4542          CALL stom_IPCC_define_history (hist_id_stom_IPCC, nvm, iim, jjm, &
4543               & dt, hist_dt_stom_ipcc, hori_id, hist_IPCC_PFTaxis_id)
4544
4545          !- end definition
4546          CALL histend(hist_id_stom_IPCC)
4547         
4548       ENDIF
4549    ENDIF
4550
4551
4552    RETURN
4553
4554  END SUBROUTINE intsurf_history
4555 
4556  SUBROUTINE stom_define_history &
4557       & (hist_id_stom, nvm, iim, jjm, dt, &
4558       &  hist_dt, hist_hori_id, hist_PFTaxis_id, &
4559       & hist_pool_10axis_id, hist_pool_100axis_id, &
4560       & hist_pool_11axis_id, hist_pool_101axis_id)
4561    ! deforestation axis added as arguments
4562
4563    !---------------------------------------------------------------------
4564    !- Tell ioipsl which variables are to be written
4565    !- and on which grid they are defined
4566    !---------------------------------------------------------------------
4567    IMPLICIT NONE
4568    !-
4569    !- Input
4570    !-
4571    !- File id
4572    INTEGER(i_std),INTENT(in) :: hist_id_stom
4573    !- number of PFTs
4574    INTEGER(i_std),INTENT(in) :: nvm
4575    !- Domain size
4576    INTEGER(i_std),INTENT(in) :: iim, jjm
4577    !- Time step of STOMATE (seconds)
4578    REAL(r_std),INTENT(in)    :: dt
4579    !- Time step of history file (s)
4580    REAL(r_std),INTENT(in)    :: hist_dt
4581    !- id horizontal grid
4582    INTEGER(i_std),INTENT(in) :: hist_hori_id
4583    !- id of PFT axis
4584    INTEGER(i_std),INTENT(in) :: hist_PFTaxis_id
4585    !- id of Deforestation axis
4586    INTEGER(i_std),INTENT(in) :: hist_pool_10axis_id,hist_pool_100axis_id
4587    INTEGER(i_std),INTENT(in) :: hist_pool_11axis_id,hist_pool_101axis_id
4588    !-
4589    !- 1 local
4590    !-
4591    !- maximum history level
4592    INTEGER(i_std), PARAMETER  :: max_hist_level = 10
4593    !- output level (between 0 and 10)
4594    !-  ( 0:nothing is written, 10:everything is written)
4595    INTEGER(i_std)             :: hist_level
4596    !- Character strings to define operations for histdef
4597    CHARACTER(LEN=40),DIMENSION(max_hist_level) :: ave
4598
4599    !---------------------------------------------------------------------
4600    !=====================================================================
4601    !- 1 history level
4602    !=====================================================================
4603    !- 1.1 define history levelx
4604    !=====================================================================
4605    !Config  Key  = STOMATE_HISTLEVEL
4606    !Config  Desc = STOMATE history output level (0..10)
4607    !Config  Def  = 10
4608    !Config  Help = 0: nothing is written; 10: everything is written
4609    !-
4610    hist_level = 10
4611    CALL getin_p('STOMATE_HISTLEVEL', hist_level)
4612    !-
4613    WRITE(numout,*) 'STOMATE history level: ',hist_level
4614    IF ( (hist_level > max_hist_level).OR.(hist_level < 0) ) THEN
4615       STOP 'This history level is not allowed'
4616    ENDIF
4617    !=====================================================================
4618    !- 1.2 define operations according to output level
4619    !=====================================================================
4620    ave(1:hist_level) =  'ave(scatter(X))'
4621    ave(hist_level+1:max_hist_level) =  'never          '
4622    !=====================================================================
4623    !- 2 surface fields (2d)
4624    !- 3 PFT: 3rd dimension
4625    !=====================================================================
4626
4627
4628    ! structural litter above ground
4629    CALL histdef (hist_id_stom, &
4630         &               TRIM("LITTER_STR_AB       "), &
4631         &               TRIM("structural litter above ground                    "), &
4632         &               TRIM("gC/m^2/pft          "), iim,jjm, hist_hori_id, &
4633         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
4634
4635    ! metabolic litter above ground                     
4636    CALL histdef (hist_id_stom, &
4637         &               TRIM("LITTER_MET_AB       "), &
4638         &               TRIM("metabolic litter above ground                     "), &
4639         &               TRIM("gC/m^2/pft          "), iim,jjm, hist_hori_id, &
4640         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
4641
4642    ! structural litter below ground               
4643    CALL histdef (hist_id_stom, &
4644         &               TRIM("LITTER_STR_BE       "), &
4645         &               TRIM("structural litter below ground                    "), &
4646         &               TRIM("gC/m^2/pft          "), iim,jjm, hist_hori_id, &
4647         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
4648
4649    ! metabolic litter below ground               
4650    CALL histdef (hist_id_stom, &
4651         &               TRIM("LITTER_MET_BE       "), &
4652         &               TRIM("metabolic litter below ground                     "), &
4653         &               TRIM("gC/m^2/pft          "), iim,jjm, hist_hori_id, &
4654         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
4655
4656    ! fraction of soil covered by dead leaves           
4657    CALL histdef (hist_id_stom, &
4658         &               TRIM("DEADLEAF_COVER      "), &
4659         &               TRIM("fraction of soil covered by dead leaves           "), &
4660         &               TRIM("-                   "), iim,jjm, hist_hori_id, &
4661         &               1,1,1, -99,32, ave(5), dt, hist_dt)
4662
4663    ! total soil and litter carbon
4664    CALL histdef (hist_id_stom, &
4665         &               TRIM("TOTAL_SOIL_CARB     "), &
4666         &               TRIM("total soil and litter carbon                      "), &
4667         &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
4668         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
4669
4670    ! active soil carbon in ground                 
4671    CALL histdef (hist_id_stom, &
4672         &               TRIM("CARBON_ACTIVE       "), &
4673         &               TRIM("active soil carbon in ground                      "), &
4674         &               TRIM("gC/m^2/pft          "), iim,jjm, hist_hori_id, &
4675         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
4676
4677    ! slow soil carbon in ground                   
4678    CALL histdef (hist_id_stom, &
4679         &               TRIM("CARBON_SLOW         "), &
4680         &               TRIM("slow soil carbon in ground                        "), &
4681         &               TRIM("gC/m^2/pft          "), iim,jjm, hist_hori_id, &
4682         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
4683
4684    ! passive soil carbon in ground               
4685    CALL histdef (hist_id_stom, &
4686         &               TRIM("CARBON_PASSIVE      "), &
4687         &               TRIM("passive soil carbon in ground                     "), &
4688         &               TRIM("gC/m^2/pft          "), iim,jjm, hist_hori_id, &
4689         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
4690
4691    ! Long term 2 m temperature                           
4692    CALL histdef (hist_id_stom, &
4693         &               TRIM("T2M_LONGTERM        "), &
4694         &               TRIM("Longterm 2 m temperature                          "), &
4695         &               TRIM("K                   "), iim,jjm, hist_hori_id, &
4696         &               1,1,1, -99,32, ave(9), dt, hist_dt)
4697
4698    ! Monthly 2 m temperature                           
4699    CALL histdef (hist_id_stom, &
4700         &               TRIM("T2M_MONTH           "), &
4701         &               TRIM("Monthly 2 m temperature                           "), &
4702         &               TRIM("K                   "), iim,jjm, hist_hori_id, &
4703         &               1,1,1, -99,32, ave(1), dt, hist_dt)
4704
4705    ! Weekly 2 m temperature                           
4706    CALL histdef (hist_id_stom, &
4707         &               TRIM("T2M_WEEK            "), &
4708         &               TRIM("Weekly 2 m temperature                            "), &
4709         &               TRIM("K                   "), iim,jjm, hist_hori_id, &
4710         &               1,1,1, -99,32, ave(1), dt, hist_dt)
4711
4712    ! heterotr. resp. from ground                 
4713    CALL histdef (hist_id_stom, &
4714         &               TRIM("HET_RESP            "), &
4715         &               TRIM("heterotr. resp. from ground                       "), &
4716         &               TRIM("gC/m^2 tot/pft/day  "), iim,jjm, hist_hori_id, &
4717         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(3), dt, hist_dt)
4718
4719    ! black carbon on average total ground             
4720    CALL histdef (hist_id_stom, &
4721         &               TRIM("BLACK_CARBON        "), &
4722         &               TRIM("black carbon on average total ground              "), &
4723         &               TRIM("gC/m^2 tot          "), iim,jjm, hist_hori_id, &
4724         &               1,1,1, -99,32, ave(10), dt, hist_dt)
4725
4726    ! Fire fraction on ground
4727    CALL histdef (hist_id_stom, &
4728         &               TRIM("FIREFRAC            "), &
4729         &               TRIM("Fire fraction on ground                           "), &
4730         &               TRIM("1/day               "), iim,jjm, hist_hori_id, &
4731         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(1), dt, hist_dt)
4732
4733    ! Fire index on ground                     
4734    CALL histdef (hist_id_stom, &
4735         &               TRIM("FIREINDEX           "), &
4736         &               TRIM("Fire index on ground                              "), &
4737         &               TRIM("-                   "), iim,jjm, hist_hori_id, &
4738         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(10), dt, hist_dt)
4739
4740    ! Litter humidity                                   
4741    CALL histdef (hist_id_stom, &
4742         &               TRIM("LITTERHUM           "), &
4743         &               TRIM("Litter humidity                                   "), &
4744         &               TRIM("-                   "), iim,jjm, hist_hori_id, &
4745         &               1,1,1, -99,32, ave(5), dt, hist_dt)
4746
4747    ! Monthly CO2 flux                                 
4748    CALL histdef (hist_id_stom, &
4749         &               TRIM("CO2FLUX_MONTHLY     "), &
4750         &               TRIM("Monthly CO2 flux                                  "), &
4751         &               TRIM("gC/m^2/pft/mth      "), iim,jjm, hist_hori_id, &
4752         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(1), dt, hist_dt)
4753
4754    CALL histdef(hist_id_stom, &
4755         &               TRIM("CO2FLUX_MONTHLY_SUM "), &
4756         &               TRIM("Monthly CO2 flux                                  "), &
4757         &               TRIM("PgC/m^2/mth          "), 1,1, hist_hori_id, &
4758         &               1,1,1, -99, 32, ave(1), dt, hist_dt)
4759
4760    ! Output CO2 flux from fire                         
4761    CALL histdef (hist_id_stom, &
4762         &               TRIM("CO2_FIRE            "), &
4763         &               TRIM("Output CO2 flux from fire                         "), &
4764         &               TRIM("gC/day/m^2/pft      "), iim,jjm, hist_hori_id, &
4765         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(1), dt, hist_dt)
4766
4767    ! CO2 taken from atmosphere for initiate growth     
4768    CALL histdef (hist_id_stom, &
4769         &               TRIM("CO2_TAKEN           "), &
4770         &               TRIM("CO2 taken from atmosphere for initiate growth     "), &
4771         &               TRIM("gC/day/m^2/pft      "), iim,jjm, hist_hori_id, &
4772         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(1), dt, hist_dt)
4773
4774    ! Leaf Area Index                                   
4775    CALL histdef (hist_id_stom, &
4776         &               TRIM("LAI                 "), &
4777         &               TRIM("Leaf Area Index                                   "), &
4778         &               TRIM("-                   "), iim,jjm, hist_hori_id, &
4779         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(1), dt, hist_dt)
4780
4781    ! Vegetation fraction                               
4782    CALL histdef (hist_id_stom, &
4783         &               TRIM("VEGET               "), &
4784         &               TRIM("Vegetation fraction                               "), &
4785         &               TRIM("-                   "), iim,jjm, hist_hori_id, &
4786         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(1), dt, hist_dt)
4787
4788    ! Maximum vegetation fraction (LAI -> infinity)     
4789    CALL histdef (hist_id_stom, &
4790         &               TRIM("VEGET_MAX           "), &
4791         &               TRIM("Maximum vegetation fraction (LAI -> infinity)     "), &
4792         &               TRIM("-                   "), iim,jjm, hist_hori_id, &
4793         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(1), dt, hist_dt)
4794
4795    ! Net primary productivity                         
4796    CALL histdef (hist_id_stom, &
4797         &               TRIM("NPP                 "), &
4798         &               TRIM("Net primary productivity                          "), &
4799         &               TRIM("gC/day/(m^2 tot)    "), iim,jjm, hist_hori_id, &
4800         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(1), dt, hist_dt)
4801
4802    ! Gross primary productivity                       
4803    CALL histdef (hist_id_stom, &
4804         &               TRIM("GPP                 "), &
4805         &               TRIM("Gross primary productivity                        "), &
4806         &               TRIM("gC/day/m^2          "), iim,jjm, hist_hori_id, &
4807         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(1), dt, hist_dt)
4808
4809    ! Density of individuals                           
4810    CALL histdef (hist_id_stom, &
4811         &               TRIM("IND                 "), &
4812         &               TRIM("Density of individuals                            "), &
4813         &               TRIM("1/ m^2              "), iim,jjm, hist_hori_id, &
4814         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(3), dt, hist_dt)
4815
4816    ! total living biomass
4817    CALL histdef (hist_id_stom, &
4818         &               TRIM("TOTAL_M             "), &
4819         &               TRIM("Total living biomass                              "), &
4820         &               TRIM("gC/m^2/pft          "), iim,jjm, hist_hori_id, &
4821         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(4), dt, hist_dt)
4822
4823    ! Leaf mass                                         
4824    CALL histdef (hist_id_stom, &
4825         &               TRIM("LEAF_M              "), &
4826         &               TRIM("Leaf mass                                         "), &
4827         &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
4828         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
4829
4830    ! Sap mass above ground                             
4831    CALL histdef (hist_id_stom, &
4832         &               TRIM("SAP_M_AB            "), &
4833         &               TRIM("Sap mass above ground                             "), &
4834         &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
4835         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
4836
4837    ! Sap mass below ground                             
4838    CALL histdef (hist_id_stom, &
4839         &               TRIM("SAP_M_BE            "), &
4840         &               TRIM("Sap mass below ground                             "), &
4841         &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
4842         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
4843
4844    ! Heartwood mass above ground                       
4845    CALL histdef (hist_id_stom, &
4846         &               TRIM("HEART_M_AB          "), &
4847         &               TRIM("Heartwood mass above ground                       "), &
4848         &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
4849         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
4850
4851    ! Heartwood mass below ground                       
4852    CALL histdef (hist_id_stom, &
4853         &               TRIM("HEART_M_BE          "), &
4854         &               TRIM("Heartwood mass below ground                       "), &
4855         &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
4856         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
4857
4858    ! Root mass                                         
4859    CALL histdef (hist_id_stom, &
4860         &               TRIM("ROOT_M              "), &
4861         &               TRIM("Root mass                                         "), &
4862         &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
4863         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
4864
4865    ! Fruit mass                                       
4866    CALL histdef (hist_id_stom, &
4867         &               TRIM("FRUIT_M             "), &
4868         &               TRIM("Fruit mass                                        "), &
4869         &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
4870         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
4871
4872    ! Carbohydrate reserve mass                         
4873    CALL histdef (hist_id_stom, &
4874         &               TRIM("RESERVE_M           "), &
4875         &               TRIM("Carbohydrate reserve mass                         "), &
4876         &               TRIM("gC/m^2              "), iim,jjm, hist_hori_id, &
4877         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
4878
4879    ! total turnover rate
4880    CALL histdef (hist_id_stom, &
4881         &               TRIM("TOTAL_TURN          "), &
4882         &               TRIM("total turnover rate                               "), &
4883         &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
4884         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(4), dt, hist_dt)
4885
4886    ! Leaf turnover                                     
4887    CALL histdef (hist_id_stom, &
4888         &               TRIM("LEAF_TURN           "), &
4889         &               TRIM("Leaf turnover                                     "), &
4890         &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
4891         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(4), dt, hist_dt)
4892
4893    ! Sap turnover above                               
4894    CALL histdef (hist_id_stom, &
4895         &               TRIM("SAP_AB_TURN         "), &
4896         &               TRIM("Sap turnover above                                "), &
4897         &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
4898         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(4), dt, hist_dt)
4899
4900    ! Root turnover                                     
4901    CALL histdef (hist_id_stom, &
4902         &               TRIM("ROOT_TURN           "), &
4903         &               TRIM("Root turnover                                     "), &
4904         &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
4905         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(4), dt, hist_dt)
4906
4907    ! Fruit turnover                                   
4908    CALL histdef (hist_id_stom, &
4909         &               TRIM("FRUIT_TURN          "), &
4910         &               TRIM("Fruit turnover                                    "), &
4911         &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
4912         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(4), dt, hist_dt)
4913
4914    ! total conversion of biomass to litter
4915    CALL histdef (hist_id_stom, &
4916         &               TRIM("TOTAL_BM_LITTER     "), &
4917         &               TRIM("total conversion of biomass to litter             "), &
4918         &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
4919         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(4), dt, hist_dt)
4920
4921    ! Leaf death                                       
4922    CALL histdef (hist_id_stom, &
4923         &               TRIM("LEAF_BM_LITTER      "), &
4924         &               TRIM("Leaf death                                        "), &
4925         &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
4926         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(4), dt, hist_dt)
4927
4928    ! Sap death above ground                           
4929    CALL histdef (hist_id_stom, &
4930         &               TRIM("SAP_AB_BM_LITTER    "), &
4931         &               TRIM("Sap death above ground                            "), &
4932         &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
4933         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(4), dt, hist_dt)
4934
4935    ! Sap death below ground                           
4936    CALL histdef (hist_id_stom, &
4937         &               TRIM("SAP_BE_BM_LITTER    "), &
4938         &               TRIM("Sap death below ground                            "), &
4939         &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
4940         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(4), dt, hist_dt)
4941
4942    ! Heartwood death above ground                     
4943    CALL histdef (hist_id_stom, &
4944         &               TRIM("HEART_AB_BM_LITTER  "), &
4945         &               TRIM("Heartwood death above ground                      "), &
4946         &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
4947         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(4), dt, hist_dt)
4948
4949    ! Heartwood death below ground                     
4950    CALL histdef (hist_id_stom, &
4951         &               TRIM("HEART_BE_BM_LITTER  "), &
4952         &               TRIM("Heartwood death below ground                      "), &
4953         &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
4954         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(4), dt, hist_dt)
4955
4956    ! Root death                                       
4957    CALL histdef (hist_id_stom, &
4958         &               TRIM("ROOT_BM_LITTER      "), &
4959         &               TRIM("Root death                                        "), &
4960         &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
4961         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(4), dt, hist_dt)
4962
4963    ! Fruit death                                       
4964    CALL histdef (hist_id_stom, &
4965         &               TRIM("FRUIT_BM_LITTER     "), &
4966         &               TRIM("Fruit death                                       "), &
4967         &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
4968         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(4), dt, hist_dt)
4969
4970    ! Carbohydrate reserve death                       
4971    CALL histdef (hist_id_stom, &
4972         &               TRIM("RESERVE_BM_LITTER   "), &
4973         &               TRIM("Carbohydrate reserve death                        "), &
4974         &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
4975         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(4), dt, hist_dt)
4976
4977    ! Maintenance respiration                           
4978    CALL histdef (hist_id_stom, &
4979         &               TRIM("MAINT_RESP          "), &
4980         &               TRIM("Maintenance respiration                           "), &
4981         &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
4982         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
4983
4984    ! Growth respiration                               
4985    CALL histdef (hist_id_stom, &
4986         &               TRIM("GROWTH_RESP         "), &
4987         &               TRIM("Growth respiration                                "), &
4988         &               TRIM("gC/m^2/day          "), iim,jjm, hist_hori_id, &
4989         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(2), dt, hist_dt)
4990
4991    ! age                                               
4992    CALL histdef (hist_id_stom, &
4993         &               TRIM("AGE                 "), &
4994         &               TRIM("age                                               "), &
4995         &               TRIM("years               "), iim,jjm, hist_hori_id, &
4996         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(7), dt, hist_dt)
4997
4998    ! height                                           
4999    CALL histdef (hist_id_stom, &
5000         &               TRIM("HEIGHT              "), &
5001         &               TRIM("height                                            "), &
5002         &               TRIM("m                   "), iim,jjm, hist_hori_id, &
5003         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(7), dt, hist_dt)
5004
5005    ! weekly moisture stress                           
5006    CALL histdef (hist_id_stom, &
5007         &               TRIM("MOISTRESS           "), &
5008         &               TRIM("weekly moisture stress                            "), &
5009         &               TRIM("-                   "), iim,jjm, hist_hori_id, &
5010         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(3), dt, hist_dt)
5011
5012    ! Maximum rate of carboxylation                     
5013    CALL histdef (hist_id_stom, &
5014         &               TRIM("VCMAX               "), &
5015         &               TRIM("Maximum rate of carboxylation                     "), &
5016         &               TRIM("-                   "), iim,jjm, hist_hori_id, &
5017         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(6), dt, hist_dt)
5018
5019    ! leaf age                                         
5020    CALL histdef (hist_id_stom, &
5021         &               TRIM("LEAF_AGE            "), &
5022         &               TRIM("leaf age                                          "), &
5023         &               TRIM("days                "), iim,jjm, hist_hori_id, &
5024         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(6), dt, hist_dt)
5025
5026    ! Fraction of trees that dies (gap)                 
5027    CALL histdef (hist_id_stom, &
5028         &               TRIM("MORTALITY           "), &
5029         &               TRIM("Fraction of trees that dies (gap)                 "), &
5030         &               TRIM("1/day               "), iim,jjm, hist_hori_id, &
5031         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(6), dt, hist_dt)
5032
5033    ! Fraction of plants killed by fire                 
5034    CALL histdef (hist_id_stom, &
5035         &               TRIM("FIREDEATH           "), &
5036         &               TRIM("Fraction of plants killed by fire                 "), &
5037         &               TRIM("1/day               "), iim,jjm, hist_hori_id, &
5038         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(6), dt, hist_dt)
5039
5040    ! Density of newly established saplings             
5041    CALL histdef (hist_id_stom, &
5042         &               TRIM("IND_ESTAB           "), &
5043         &               TRIM("Density of newly established saplings             "), &
5044         &               TRIM("1/day               "), iim,jjm, hist_hori_id, &
5045         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(6), dt, hist_dt)
5046
5047    ! Fraction of plants that dies (light competition) 
5048    CALL histdef (hist_id_stom, &
5049         &               TRIM("LIGHT_DEATH         "), &
5050         &               TRIM("Fraction of plants that dies (light competition)  "), &
5051         &               TRIM("1/day               "), iim,jjm, hist_hori_id, &
5052         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(6), dt, hist_dt)
5053
5054    ! biomass allocated to leaves                       
5055    CALL histdef (hist_id_stom, &
5056         &               TRIM("BM_ALLOC_LEAF       "), &
5057         &               TRIM("biomass allocated to leaves                       "), &
5058         &               TRIM("gC/m**2/pft/dt      "), iim,jjm, hist_hori_id, &
5059         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
5060
5061    ! biomass allocated to sapwood above ground         
5062    CALL histdef (hist_id_stom, &
5063         &               TRIM("BM_ALLOC_SAP_AB     "), &
5064         &               TRIM("biomass allocated to sapwood above ground         "), &
5065         &               TRIM("gC/m**2/pft/dt      "), iim,jjm, hist_hori_id, &
5066         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
5067
5068    ! biomass allocated to sapwood below ground         
5069    CALL histdef (hist_id_stom, &
5070         &               TRIM("BM_ALLOC_SAP_BE     "), &
5071         &               TRIM("biomass allocated to sapwood below ground         "), &
5072         &               TRIM("gC/m**2/pft/dt      "), iim,jjm, hist_hori_id, &
5073         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
5074
5075    ! biomass allocated to roots                       
5076    CALL histdef (hist_id_stom, &
5077         &               TRIM("BM_ALLOC_ROOT       "), &
5078         &               TRIM("biomass allocated to roots                        "), &
5079         &               TRIM("gC/m**2/pft/dt          "), iim,jjm, hist_hori_id, &
5080         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
5081
5082    ! biomass allocated to fruits                       
5083    CALL histdef (hist_id_stom, &
5084         &               TRIM("BM_ALLOC_FRUIT      "), &
5085         &               TRIM("biomass allocated to fruits                       "), &
5086         &               TRIM("gC/m**2/pft/dt          "), iim,jjm, hist_hori_id, &
5087         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
5088
5089    ! biomass allocated to carbohydrate reserve         
5090    CALL histdef (hist_id_stom, &
5091         &               TRIM("BM_ALLOC_RES        "), &
5092         &               TRIM("biomass allocated to carbohydrate reserve         "), &
5093         &               TRIM("gC/m**2/pft/dt          "), iim,jjm, hist_hori_id, &
5094         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
5095
5096    ! time constant of herbivore activity               
5097    CALL histdef (hist_id_stom, &
5098         &               TRIM("HERBIVORES          "), &
5099         &               TRIM("time constant of herbivore activity               "), &
5100         &               TRIM("days                "), iim,jjm, hist_hori_id, &
5101         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
5102
5103    ! turnover time for grass leaves                   
5104    CALL histdef (hist_id_stom, &
5105         &               TRIM("TURNOVER_TIME       "), &
5106         &               TRIM("turnover time for grass leaves                    "), &
5107         &               TRIM("days                "), iim,jjm, hist_hori_id, &
5108         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(5), dt, hist_dt)
5109
5110    ! 10 year wood product pool                         
5111    CALL histdef (hist_id_stom, &
5112         &               TRIM("PROD10              "), &
5113         &               TRIM("10 year wood product pool                         "), &
5114         &               TRIM("gC/m**2             "), iim,jjm, hist_hori_id, &
5115         &               11,1,11, hist_pool_11axis_id,32, ave(5), dt, hist_dt)
5116
5117    ! annual flux for each 10 year wood product pool   
5118    CALL histdef (hist_id_stom, &
5119         &               TRIM("FLUX10              "), &
5120         &               TRIM("annual flux for each 10 year wood product pool    "), &
5121         &               TRIM("gC/m**2/yr          "), iim,jjm, hist_hori_id, &
5122         &               10,1,10, hist_pool_10axis_id,32, ave(5), dt, hist_dt)
5123
5124    ! 100 year wood product pool                       
5125    CALL histdef (hist_id_stom, &
5126         &               TRIM("PROD100             "), &
5127         &               TRIM("100 year wood product pool                        "), &
5128         &               TRIM("gC/m**2             "), iim,jjm, hist_hori_id, &
5129         &               101,1,101, hist_pool_101axis_id,32, ave(5), dt, hist_dt)
5130
5131    ! annual flux for each 100 year wood product pool   
5132    CALL histdef (hist_id_stom, &
5133         &               TRIM("FLUX100             "), &
5134         &               TRIM("annual flux for each 100 year wood product pool   "), &
5135         &               TRIM("gC/m**2/yr          "), iim,jjm, hist_hori_id, &
5136         &               100,1,100, hist_pool_100axis_id,32, ave(5), dt, hist_dt)
5137
5138    ! annual release right after deforestation         
5139    CALL histdef (hist_id_stom, &
5140         &               TRIM("CONVFLUX            "), &
5141         &               TRIM("annual release right after deforestation          "), &
5142         &               TRIM("gC/m**2/day          "), iim,jjm, hist_hori_id, &
5143         &               1,1,1, -99,32, ave(5), dt, hist_dt)
5144
5145    ! annual release from all 10 year wood product pools
5146    CALL histdef (hist_id_stom, &
5147         &               TRIM("CFLUX_PROD10        "), &
5148         &               TRIM("annual release from all 10 year wood product pools"), &
5149         &               TRIM("gC/m**2/day          "), iim,jjm, hist_hori_id, &
5150         &               1,1,1, -99,32, ave(5), dt, hist_dt)
5151
5152    ! annual release from all 100year wood product pools
5153    CALL histdef (hist_id_stom, &
5154         &               TRIM("CFLUX_PROD100       "), &
5155         &               TRIM("annual release from all 100year wood product pools"), &
5156         &               TRIM("gC/m**2/day          "), iim,jjm, hist_hori_id, &
5157         &               1,1,1, -99,32, ave(5), dt, hist_dt)
5158    ! agriculure product
5159    CALL histdef (hist_id_stom, &
5160         &               TRIM("HARVEST_ABOVE       "), &
5161         &               TRIM("annual release product after harvest              "), &
5162         &               TRIM("gC/m**2/day          "), iim,jjm, hist_hori_id, &
5163         &               1,1,1, -99,32, ave(5), dt, hist_dt)
5164
5165
5166    CALL histdef(hist_id_stom, 'RESOLUTION_X', 'E-W resolution', 'm', &
5167         & iim,jjm, hist_hori_id, 1,1,1, -99, 32, 'once(scatter(X))', dt, hist_dt)
5168    CALL histdef(hist_id_stom, 'RESOLUTION_Y', 'N-S resolution', 'm', &
5169         & iim,jjm, hist_hori_id, 1,1,1, -99, 32, 'once(scatter(X))', dt, hist_dt)
5170    CALL histdef(hist_id_stom, 'CONTFRAC', 'Continental fraction', '1', &
5171         & iim,jjm, hist_hori_id, 1,1,1, -99, 32, 'once(scatter(X))', dt, hist_dt)
5172    CALL histdef(hist_id_stom, 'Areas', 'Mesh areas', 'm2', &
5173         & iim,jjm, hist_hori_id, 1,1,1, -99, 32, 'once(scatter(X))', dt, hist_dt)
5174
5175    !  Special outputs for phenology
5176    CALL histdef (hist_id_stom, &
5177         &               TRIM("WHEN_GROWTHINIT     "), &
5178         &               TRIM("Time elapsed from season beginning                "), &
5179         &               TRIM("d                   "), iim,jjm, hist_hori_id, &
5180         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(9), dt, hist_dt)
5181
5182    CALL histdef (hist_id_stom, &
5183         &               TRIM("TIME_LOWGPP         "), &
5184         &               TRIM("Time elapsed since the end of GPP                 "), &
5185         &               TRIM("d                   "), iim,jjm, hist_hori_id, &
5186         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(9), dt, hist_dt)
5187
5188    CALL histdef (hist_id_stom, &
5189         &               TRIM("PFTPRESENT          "), &
5190         &               TRIM("PFT exists                                        "), &
5191         &               TRIM("d                   "), iim,jjm, hist_hori_id, &
5192         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(9), dt, hist_dt)
5193
5194    CALL histdef (hist_id_stom, &
5195         &               TRIM("GDD_MIDWINTER       "), &
5196         &               TRIM("Growing degree days, since midwinter              "), &
5197         &               TRIM("degK                "), iim,jjm, hist_hori_id, &
5198         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(9), dt, hist_dt)
5199
5200    CALL histdef (hist_id_stom, &
5201         &               TRIM("NCD_DORMANCE        "), &
5202         &               TRIM("Number of chilling days, since leaves were lost   "), &
5203         &               TRIM("d                   "), iim,jjm, hist_hori_id, &
5204         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(9), dt, hist_dt)
5205
5206    CALL histdef (hist_id_stom, &
5207         &               TRIM("ALLOW_INITPHENO     "), &
5208         &               TRIM("Allow to declare beginning of the growing season  "), &
5209         &               TRIM("-                   "), iim,jjm, hist_hori_id, &
5210         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(9), dt, hist_dt)
5211
5212    CALL histdef (hist_id_stom, &
5213         &               TRIM("BEGIN_LEAVES        "), &
5214         &               TRIM("Signal to start putting leaves on                 "), &
5215         &               TRIM("-                   "), iim,jjm, hist_hori_id, &
5216         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(9), dt, hist_dt)
5217
5218    !---------------------------------
5219  END SUBROUTINE stom_define_history
5220  !
5221  SUBROUTINE stom_IPCC_define_history &
5222       & (hist_id_stom_IPCC, nvm, iim, jjm, dt, &
5223       &  hist_dt, hist_hori_id, hist_PFTaxis_id)
5224    ! deforestation axis added as arguments
5225
5226    !---------------------------------------------------------------------
5227    !- Tell ioipsl which variables are to be written
5228    !- and on which grid they are defined
5229    !---------------------------------------------------------------------
5230    IMPLICIT NONE
5231    !-
5232    !- Input
5233    !-
5234    !- File id
5235    INTEGER(i_std),INTENT(in) :: hist_id_stom_IPCC
5236    !- number of PFTs
5237    INTEGER(i_std),INTENT(in) :: nvm
5238    !- Domain size
5239    INTEGER(i_std),INTENT(in) :: iim, jjm
5240    !- Time step of STOMATE (seconds)
5241    REAL(r_std),INTENT(in)    :: dt
5242    !- Time step of history file (s)
5243    REAL(r_std),INTENT(in)    :: hist_dt
5244    !- id horizontal grid
5245    INTEGER(i_std),INTENT(in) :: hist_hori_id
5246    !- id of PFT axis
5247    INTEGER(i_std),INTENT(in) :: hist_PFTaxis_id
5248    !-
5249    !- 1 local
5250    !-
5251    !- Character strings to define operations for histdef
5252    CHARACTER(LEN=40),DIMENSION(max_hist_level) :: ave
5253
5254    !=====================================================================
5255    !- 1 define operations
5256    !=====================================================================
5257    ave(1) =  'ave(scatter(X))'
5258    !=====================================================================
5259    !- 2 surface fields (2d)
5260    !=====================================================================
5261    ! Carbon in Vegetation
5262    CALL histdef (hist_id_stom_IPCC, &
5263         &               TRIM("cVeg"), &
5264         &               TRIM("Carbon in Vegetation"), &
5265         &               TRIM("kg C m-2"), iim,jjm, hist_hori_id, &
5266         &               1,1,1, -99,32, ave(1), dt, hist_dt)
5267    ! Carbon in Litter Pool
5268    CALL histdef (hist_id_stom_IPCC, &
5269         &               TRIM("cLitter"), &
5270         &               TRIM("Carbon in Litter Pool"), &
5271         &               TRIM("kg C m-2"), iim,jjm, hist_hori_id, &
5272         &               1,1,1, -99,32, ave(1), dt, hist_dt)
5273    ! Carbon in Soil Pool
5274    CALL histdef (hist_id_stom_IPCC, &
5275         &               TRIM("cSoil"), &
5276         &               TRIM("Carbon in Soil Pool"), &
5277         &               TRIM("kg C m-2"), iim,jjm, hist_hori_id, &
5278         &               1,1,1, -99,32, ave(1), dt, hist_dt)
5279    ! Carbon in Products of Land Use Change
5280    CALL histdef (hist_id_stom_IPCC, &
5281         &               TRIM("cProduct"), &
5282         &               TRIM("Carbon in Products of Land Use Change"), &
5283         &               TRIM("kg C m-2"), iim,jjm, hist_hori_id, &
5284         &               1,1,1, -99,32, ave(1), dt, hist_dt)
5285    ! Leaf Area Fraction
5286    CALL histdef (hist_id_stom_IPCC, &
5287         &               TRIM("lai"), &
5288         &               TRIM("Leaf Area Fraction"), &
5289         &               TRIM("1"), iim,jjm, hist_hori_id, &
5290         &               1,1,1, -99,32, ave(1), dt, hist_dt)
5291    ! Gross Primary Production
5292    CALL histdef (hist_id_stom_IPCC, &
5293         &               TRIM("gpp"), &
5294         &               TRIM("Gross Primary Production"), &
5295         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
5296         &               1,1,1, -99,32, ave(1), dt, hist_dt)
5297    ! Autotrophic Respiration
5298    CALL histdef (hist_id_stom_IPCC, &
5299         &               TRIM("ra"), &
5300         &               TRIM("Autotrophic Respiration"), &
5301         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
5302         &               1,1,1, -99,32, ave(1), dt, hist_dt)
5303    ! Net Primary Production
5304    CALL histdef (hist_id_stom_IPCC, &
5305         &               TRIM("npp"), &
5306         &               TRIM("Net Primary Production"), &
5307         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
5308         &               1,1,1, -99,32, ave(1), dt, hist_dt)
5309    ! Heterotrophic Respiration
5310    CALL histdef (hist_id_stom_IPCC, &
5311         &               TRIM("rh"), &
5312         &               TRIM("Heterotrophic Respiration"), &
5313         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
5314         &               1,1,1, -99,32, ave(1), dt, hist_dt)
5315    ! CO2 Emission from Fire
5316    CALL histdef (hist_id_stom_IPCC, &
5317         &               TRIM("fFire"), &
5318         &               TRIM("CO2 Emission from Fire"), &
5319         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
5320         &               1,1,1, -99,32, ave(1), dt, hist_dt)
5321
5322    ! CO2 Flux to Atmosphere from Crop Harvesting
5323    CALL histdef (hist_id_stom_IPCC, &
5324         &               TRIM("fHarvest"), &
5325         &               TRIM("CO2 Flux to Atmosphere from Crop Harvesting"), &
5326         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
5327         &               1,1,1, -99,32, ave(1), dt, hist_dt)
5328    ! CO2 Flux to Atmosphere from Land Use Change
5329    CALL histdef (hist_id_stom_IPCC, &
5330         &               TRIM("fLuc"), &
5331         &               TRIM("CO2 Flux to Atmosphere from Land Use Change"), &
5332         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
5333         &               1,1,1, -99,32, ave(1), dt, hist_dt)
5334    ! Net Biospheric Production
5335    CALL histdef (hist_id_stom_IPCC, &
5336         &               TRIM("nbp"), &
5337         &               TRIM("Net Biospheric Production"), &
5338         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
5339         &               1,1,1, -99,32, ave(1), dt, hist_dt)
5340    ! Total Carbon Flux from Vegetation to Litter
5341    CALL histdef (hist_id_stom_IPCC, &
5342         &               TRIM("fVegLitter"), &
5343         &               TRIM("Total Carbon Flux from Vegetation to Litter"), &
5344         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
5345         &               1,1,1, -99,32, ave(1), dt, hist_dt)
5346    ! Total Carbon Flux from Litter to Soil
5347    CALL histdef (hist_id_stom_IPCC, &
5348         &               TRIM("fLitterSoil"), &
5349         &               TRIM("Total Carbon Flux from Litter to Soil"), &
5350         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
5351         &               1,1,1, -99,32, ave(1), dt, hist_dt)
5352
5353    ! Carbon in Leaves
5354    CALL histdef (hist_id_stom_IPCC, &
5355         &               TRIM("cLeaf"), &
5356         &               TRIM("Carbon in Leaves"), &
5357         &               TRIM("kg C m-2"), iim,jjm, hist_hori_id, &
5358         &               1,1,1, -99,32, ave(1), dt, hist_dt)
5359    ! Carbon in Wood
5360    CALL histdef (hist_id_stom_IPCC, &
5361         &               TRIM("cWood"), &
5362         &               TRIM("Carbon in Wood"), &
5363         &               TRIM("kg C m-2"), iim,jjm, hist_hori_id, &
5364         &               1,1,1, -99,32, ave(1), dt, hist_dt)
5365    ! Carbon in Roots
5366    CALL histdef (hist_id_stom_IPCC, &
5367         &               TRIM("cRoot"), &
5368         &               TRIM("Carbon in Roots"), &
5369         &               TRIM("kg C m-2"), iim,jjm, hist_hori_id, &
5370         &               1,1,1, -99,32, ave(1), dt, hist_dt)
5371    ! Carbon in Other Living Compartments
5372    CALL histdef (hist_id_stom_IPCC, &
5373         &               TRIM("cMisc"), &
5374         &               TRIM("Carbon in Other Living Compartments"), &
5375         &               TRIM("kg C m-2"), iim,jjm, hist_hori_id, &
5376         &               1,1,1, -99,32, ave(1), dt, hist_dt)
5377
5378    ! Carbon in Above-Ground Litter
5379    CALL histdef (hist_id_stom_IPCC, &
5380         &               TRIM("cLitterAbove"), &
5381         &               TRIM("Carbon in Above-Ground Litter"), &
5382         &               TRIM("kg C m-2"), iim,jjm, hist_hori_id, &
5383         &               1,1,1, -99,32, ave(1), dt, hist_dt)
5384    ! Carbon in Below-Ground Litter
5385    CALL histdef (hist_id_stom_IPCC, &
5386         &               TRIM("cLitterBelow"), &
5387         &               TRIM("Carbon in Below-Ground Litter"), &
5388         &               TRIM("kg C m-2"), iim,jjm, hist_hori_id, &
5389         &               1,1,1, -99,32, ave(1), dt, hist_dt)
5390    ! Carbon in Fast Soil Pool
5391    CALL histdef (hist_id_stom_IPCC, &
5392         &               TRIM("cSoilFast"), &
5393         &               TRIM("Carbon in Fast Soil Pool"), &
5394         &               TRIM("kg C m-2"), iim,jjm, hist_hori_id, &
5395         &               1,1,1, -99,32, ave(1), dt, hist_dt)
5396    ! Carbon in Medium Soil Pool
5397    CALL histdef (hist_id_stom_IPCC, &
5398         &               TRIM("cSoilMedium"), &
5399         &               TRIM("Carbon in Medium Soil Pool"), &
5400         &               TRIM("kg C m-2"), iim,jjm, hist_hori_id, &
5401         &               1,1,1, -99,32, ave(1), dt, hist_dt)
5402    ! Carbon in Slow Soil Pool
5403    CALL histdef (hist_id_stom_IPCC, &
5404         &               TRIM("cSoilSlow"), &
5405         &               TRIM("Carbon in Slow Soil Pool"), &
5406         &               TRIM("kg C m-2"), iim,jjm, hist_hori_id, &
5407         &               1,1,1, -99,32, ave(1), dt, hist_dt)
5408
5409    !- 3 PFT: 3rd dimension
5410    ! Fractional Land Cover of PFT
5411    CALL histdef (hist_id_stom_IPCC, &
5412         &               TRIM("landCoverFrac"), &
5413         &               TRIM("Fractional Land Cover of PFT"), &
5414         &               TRIM("%"), iim,jjm, hist_hori_id, &
5415         &               nvm,1,nvm, hist_PFTaxis_id,32, ave(1), dt, hist_dt)
5416
5417
5418    ! Total Primary Deciduous Tree Cover Fraction
5419    CALL histdef (hist_id_stom_IPCC, &
5420         &               TRIM("treeFracPrimDec"), &
5421         &               TRIM("Total Primary Deciduous Tree Cover Fraction"), &
5422         &               TRIM("%"), iim,jjm, hist_hori_id, &
5423         &               1,1,1, -99,32, ave(1), dt, hist_dt)
5424
5425    ! Total Primary Evergreen Tree Cover Fraction
5426    CALL histdef (hist_id_stom_IPCC, &
5427         &               TRIM("treeFracPrimEver"), &
5428         &               TRIM("Total Primary Evergreen Tree Cover Fraction"), &
5429         &               TRIM("%"), iim,jjm, hist_hori_id, &
5430         &               1,1,1, -99,32, ave(1), dt, hist_dt)
5431
5432    ! Total C3 PFT Cover Fraction
5433    CALL histdef (hist_id_stom_IPCC, &
5434         &               TRIM("c3PftFrac"), &
5435         &               TRIM("Total C3 PFT Cover Fraction"), &
5436         &               TRIM("%"), iim,jjm, hist_hori_id, &
5437         &               1,1,1, -99,32, ave(1), dt, hist_dt)
5438    ! Total C4 PFT Cover Fraction
5439    CALL histdef (hist_id_stom_IPCC, &
5440         &               TRIM("c4PftFrac"), &
5441         &               TRIM("Total C4 PFT Cover Fraction"), &
5442         &               TRIM("%"), iim,jjm, hist_hori_id, &
5443         &               1,1,1, -99,32, ave(1), dt, hist_dt)
5444    ! Growth Autotrophic Respiration
5445    CALL histdef (hist_id_stom_IPCC, &
5446         &               TRIM("rGrowth"), &
5447         &               TRIM("Growth Autotrophic Respiration"), &
5448         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
5449         &               1,1,1, -99,32, ave(1), dt, hist_dt)
5450    ! Maintenance Autotrophic Respiration
5451    CALL histdef (hist_id_stom_IPCC, &
5452         &               TRIM("rMaint"), &
5453         &               TRIM("Maintenance Autotrophic Respiration"), &
5454         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
5455         &               1,1,1, -99,32, ave(1), dt, hist_dt)
5456    ! CO2 Flux from Atmosphere due to NPP Allocation to Leaf
5457    CALL histdef (hist_id_stom_IPCC, &
5458         &               TRIM("nppLeaf"), &
5459         &               TRIM("CO2 Flux from Atmosphere due to NPP Allocation to Leaf"), &
5460         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
5461         &               1,1,1, -99,32, ave(1), dt, hist_dt)
5462    ! CO2 Flux from Atmosphere due to NPP Allocation to Wood
5463    CALL histdef (hist_id_stom_IPCC, &
5464         &               TRIM("nppWood"), &
5465         &               TRIM("CO2 Flux from Atmosphere due to NPP Allocation to Wood"), &
5466         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
5467         &               1,1,1, -99,32, ave(1), dt, hist_dt)
5468    ! CO2 Flux from Atmosphere due to NPP Allocation to Root
5469    CALL histdef (hist_id_stom_IPCC, &
5470         &               TRIM("nppRoot"), &
5471         &               TRIM("CO2 Flux from Atmosphere due to NPP Allocation to Root"), &
5472         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
5473         &               1,1,1, -99,32, ave(1), dt, hist_dt)
5474    ! Net Carbon Mass Flux out of Atmophere due to Net Ecosystem Productivity on Land.
5475    CALL histdef (hist_id_stom_IPCC, &
5476         &               TRIM("nep"), &
5477         &               TRIM("Net Carbon Mass Flux out of Atmophere due to Net Ecosystem Productivity."), &
5478         &               TRIM("kg C m-2 s-1"), iim,jjm, hist_hori_id, &
5479         &               1,1,1, -99,32, ave(1), dt, hist_dt)
5480
5481    CALL histdef(hist_id_stom_IPCC, 'RESOLUTION_X', 'E-W resolution', 'm', &
5482         & iim,jjm, hist_hori_id, 1,1,1, -99, 32, 'once(scatter(X))', dt, hist_dt)
5483    CALL histdef(hist_id_stom_IPCC, 'RESOLUTION_Y', 'N-S resolution', 'm', &
5484         & iim,jjm, hist_hori_id, 1,1,1, -99, 32, 'once(scatter(X))', dt, hist_dt)
5485    CALL histdef(hist_id_stom_IPCC, 'CONTFRAC', 'Continental fraction', '1', &
5486         & iim,jjm, hist_hori_id, 1,1,1, -99, 32, 'once(scatter(X))', dt, hist_dt)
5487    CALL histdef(hist_id_stom_IPCC, 'Areas', 'Mesh areas', 'm2', &
5488         & iim,jjm, hist_hori_id, 1,1,1, -99, 32, 'once(scatter(X))', dt, hist_dt)
5489
5490    !---------------------------------
5491  END SUBROUTINE stom_IPCC_define_history
5492END MODULE intersurf
Note: See TracBrowser for help on using the repository browser.