source: branches/publications/ORCHIDEE_2.0_gmd_Africa/ORCHIDEE/src_driver/orchideedriver.f90 @ 7189

Last change on this file since 7189 was 4646, checked in by josefine.ghattas, 7 years ago

Ticket #185 :
Created new module containing time variables and subroutines to calculate them. Variables in the time module are public and can be used elswhere in the model. They should not be modified outside the time module.

Note that now each time step have a time interval. xx_start or xx_end values for the date can be used. Previously the date values correspondend to the end of the interval. See description in module time for more information.

These changes do not make any difference in results for couled mode with LMDZ or dim2_driver offline driver.

These modifications also corrects the problem with do_slow related to orchideedriver, ticket #327

File size: 39.1 KB
Line 
1! =================================================================================================================================
2! PROGRAM       : orchideedriver
3!
4! CONTACT       : jan.polcher@lmd.jussieu.fr
5!
6! LICENCE      : IPSL (2016)
7! This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC
8!
9!>\BRIEF      This is the main program for the new driver. This only organises the data and calls sechiba_main.
10!!            The main work is done in glogrid.f90 and forcing_tools.f90.
11!!
12!!\n DESCRIPTION: Call the various modules to get the forcing data and provide it to SECHIBA. The only complexity
13!!                is setting-up the domain decomposition and distributing the grid information.
14!!                The code is parallel from tip to toe using the domain decomposition inherited from LMDZ.
15!!
16!! RECENT CHANGE(S): None
17!!
18!! REFERENCE(S) :
19!!
20!! SVN          :
21!! $HeadURL:  $
22!! $Date:  $
23!! $Revision: $
24!! \n
25!_ ================================================================================================================================
26!
27PROGRAM orchidedriver
28  !---------------------------------------------------------------------
29  !-
30  !-
31  !---------------------------------------------------------------------
32  USE defprec
33  USE netcdf
34  !
35  !
36  USE ioipsl_para
37  USE mod_orchidee_para
38  !
39  USE grid
40  USE time
41  USE timer
42  USE constantes
43  USE forcing_tools
44  USE globgrd
45  !
46  USE sechiba
47  USE control
48  USE ioipslctrl
49  !
50  USE thermosoilc, ONLY : thermosoilc_levels
51  !
52  !-
53  IMPLICIT NONE
54  !-
55  CHARACTER(LEN=80) :: gridfilename
56  CHARACTER(LEN=80), DIMENSION(100) :: forfilename
57  INTEGER(i_std) :: nb_forcefile
58  CHARACTER(LEN=8)  :: model_guess
59  INTEGER(i_std)    :: iim_glo, jjm_glo, file_id
60  !-
61  INTEGER(i_std)    :: nbseg
62  REAL(r_std), ALLOCATABLE, DIMENSION(:,:) :: lon_glo, lat_glo, area_glo
63  REAL(r_std), ALLOCATABLE, DIMENSION(:,:) :: mask_glo
64  REAL(r_std), ALLOCATABLE, DIMENSION(:,:,:,:) :: corners_glo
65  REAL(r_std), ALLOCATABLE, DIMENSION(:,:,:) :: corners_lon, corners_lat
66  INTEGER(i_std) :: nbindex_g, kjpindex
67  INTEGER(i_std), ALLOCATABLE, DIMENSION(:) :: kindex, kindex_g
68  REAL(r_std), DIMENSION(2) :: zoom_lon, zoom_lat
69  !
70  ! Variables for the global grid available on all procs and used
71  ! to fill the ORCHIDEE variable on the root_proc
72  !
73  REAL(r_std), ALLOCATABLE, DIMENSION(:,:)    :: lalo_glo
74  REAL(r_std), ALLOCATABLE, DIMENSION(:)      :: contfrac_glo
75  CHARACTER(LEN=20)                           :: calendar
76  !-
77  !- Variables local to each processors.
78  !-
79  INTEGER(i_std) :: i, j, ik, nbdt, first_point
80  INTEGER(i_std) :: itau, itau_offset, itau_sechiba
81  REAL(r_std)    :: date0, date0_shifted, dt, dt_sto, julian
82  REAL(r_std)    :: date0_tmp, dt_tmp
83  INTEGER(i_std) :: nbdt_tmp
84  REAL(r_std)    :: timestep_interval(2), timestep_int_next(2)
85  !
86  INTEGER(i_std) :: rest_id, rest_id_stom
87  INTEGER(i_std) ::  hist_id, hist2_id, hist_id_stom, hist_id_stom_IPCC
88  REAL(r_std), ALLOCATABLE, DIMENSION(:,:) :: lalo_loc
89  INTEGER(i_std) :: iim, jjm, ier
90  REAL(r_std), ALLOCATABLE, DIMENSION(:,:) :: lon, lat
91  REAL(r_std),ALLOCATABLE, DIMENSION (:)   :: soilth_lev               !! Vertical soil axis for thermal scheme (m)
92  !-
93  !- input fields
94  !-
95  REAL(r_std), ALLOCATABLE, DIMENSION (:)             :: u             !! Lowest level wind speed
96  REAL(r_std), ALLOCATABLE, DIMENSION (:)             :: v             !! Lowest level wind speed
97  REAL(r_std), ALLOCATABLE, DIMENSION (:)             :: zlev_uv       !! Height of first layer
98  REAL(r_std), ALLOCATABLE, DIMENSION (:)             :: zlev_tq       !! Height of first layer
99  REAL(r_std), ALLOCATABLE, DIMENSION (:)             :: qair          !! Lowest level specific humidity
100  REAL(r_std), ALLOCATABLE, DIMENSION (:)             :: precip_rain   !! Rain precipitation
101  REAL(r_std), ALLOCATABLE, DIMENSION (:)             :: precip_snow   !! Snow precipitation
102  REAL(r_std), ALLOCATABLE, DIMENSION (:)             :: lwdown        !! Down-welling long-wave flux
103  REAL(r_std), ALLOCATABLE, DIMENSION (:)             :: swdown        !! Downwelling surface short-wave flux
104  REAL(r_std), ALLOCATABLE, DIMENSION (:)             :: sinang        !! cosine of solar zenith angle
105  REAL(r_std), ALLOCATABLE, DIMENSION (:)             :: temp_air      !! Air temperature in Kelvin
106  REAL(r_std), ALLOCATABLE, DIMENSION (:)             :: epot_air      !! Air potential energy
107  REAL(r_std), ALLOCATABLE, DIMENSION (:)             :: ccanopy       !! CO2 concentration in the canopy
108  REAL(r_std), ALLOCATABLE, DIMENSION (:)             :: petAcoef      !! Coeficients A from the PBL resolution
109  REAL(r_std), ALLOCATABLE, DIMENSION (:)             :: peqAcoef      !! One for T and another for q
110  REAL(r_std), ALLOCATABLE, DIMENSION (:)             :: petBcoef      !! Coeficients B from the PBL resolution
111  REAL(r_std), ALLOCATABLE, DIMENSION (:)             :: peqBcoef      !! One for T and another for q
112  REAL(r_std), ALLOCATABLE, DIMENSION (:)             :: cdrag         !! Cdrag
113  REAL(r_std), ALLOCATABLE, DIMENSION (:)             :: pb            !! Lowest level pressure
114  !-
115  !- output fields
116  !-
117  REAL(r_std), ALLOCATABLE, DIMENSION (:)            :: z0m           !! Surface roughness for momentum (m)
118  REAL(r_std), ALLOCATABLE, DIMENSION (:)            :: z0h           !! Surface roughness for heat (m)
119  REAL(r_std), ALLOCATABLE, DIMENSION (:)            :: coastalflow   !! Diffuse flow of water into the ocean (m^3/dt)
120  REAL(r_std), ALLOCATABLE, DIMENSION (:)            :: riverflow     !! Largest rivers flowing into the ocean (m^3/dt)
121  REAL(r_std), ALLOCATABLE, DIMENSION (:)            :: tsol_rad      !! Radiative surface temperature
122  REAL(r_std), ALLOCATABLE, DIMENSION (:)            :: vevapp        !! Total of evaporation
123  REAL(r_std), ALLOCATABLE, DIMENSION (:)            :: temp_sol_new  !! New soil temperature
124  REAL(r_std), ALLOCATABLE, DIMENSION (:)            :: qsurf         !! Surface specific humidity
125  REAL(r_std), ALLOCATABLE, DIMENSION (:,:)          :: albedo        !! Albedo
126  REAL(r_std), ALLOCATABLE, DIMENSION (:)            :: fluxsens      !! Sensible chaleur flux
127  REAL(r_std), ALLOCATABLE, DIMENSION (:)            :: fluxlat       !! Latent chaleur flux
128  REAL(r_std), ALLOCATABLE, DIMENSION (:)            :: emis          !! Emissivity
129  REAL(r_std), ALLOCATABLE, DIMENSION (:)            :: netco2        !! netco2flux
130  REAL(r_std), ALLOCATABLE, DIMENSION (:)            :: carblu        !! fco2_land_use
131  REAL(r_std), ALLOCATABLE, DIMENSION (:,:)          :: veget         !! Fraction of vegetation type (unitless, 0-1)
132  REAL(r_std), ALLOCATABLE, DIMENSION (:,:)          :: lai           !! Leaf area index (m^2 m^{-2}
133  REAL(r_std), ALLOCATABLE, DIMENSION (:,:)          :: height        !! Vegetation Height (m)
134  !-
135  !-
136  !-
137  REAL(r_std) :: atmco2
138  REAL(r_std), ALLOCATABLE, DIMENSION (:)  :: u_tq, v_tq, swnet
139  LOGICAL :: lrestart_read = .TRUE. !! Logical for _restart_ file to read
140  LOGICAL :: lrestart_write = .FALSE. !! Logical for _restart_ file to write'
141  !
142  ! Timer variables
143  !
144  LOGICAL, PARAMETER :: timemeasure=.TRUE.
145  REAL(r_std) :: waitput_cputime=0.0, waitget_cputime=0.0, orchidee_cputime=0.0
146  REAL(r_std) :: waitput_walltime=0.0, waitget_walltime=0.0, orchidee_walltime=0.0
147  !
148  !
149  ! Print point
150  !
151!!  REAL(r_std), DIMENSION(2) :: testpt=(/44.8,-25.3/)
152!!  REAL(r_std), DIMENSION(2) :: testpt=(/44.8,-18.3/)
153!!  REAL(r_std), DIMENSION(2) :: testpt=(/-60.25,-5.25/)
154!!  REAL(r_std), DIMENSION(2) :: testpt=(/46.7,10.3/)
155!!  REAL(r_std), DIMENSION(2) :: testpt=(/0.25,49.25/)
156  ! Case when no ouput is desired.
157  REAL(r_std), DIMENSION(2) :: testpt=(/9999.99,9999.99/)
158  INTEGER(i_std) :: ktest
159
160  OFF_LINE_MODE = .TRUE. 
161
162  !-
163  !---------------------------------------------------------------------------------------
164  !-
165  !- Define MPI communicator
166  !-
167  !---------------------------------------------------------------------------------------
168  !-
169  !
170  ! Set parallel processing in ORCHIDEE
171  !
172  CALL Init_orchidee_para()
173  !
174  !====================================================================================
175  !
176  ! Start timer now that the paralelisation is initialized.
177  !
178  IF ( timemeasure ) THEN
179     CALL init_timer
180     CALL start_timer(timer_global)
181     CALL start_timer(timer_mpi)
182  ENDIF
183
184  !---------------------------------------------------------------------------------------
185  !-
186  !- Start the getconf processes
187  !-
188  !---------------------------------------------------------------------------------------
189  !-
190!!  CALL getin_name("run.def")
191  !-
192  !Config Key   = GRID_FILE
193  !Config Desc  = Name of file containing the forcing data
194  !Config If    = [-]
195  !Config Def   = grid_file.nc
196  !Config Help  = This is the name of the file from which we will read
197  !Config         or write into it the description of the grid from
198  !Config         the forcing file.
199  !Config         compliant.
200  !Config Units = [FILE]
201  !-
202  gridfilename='NONE'
203  CALL getin_p('GRID_FILE', gridfilename)
204  !-
205  forfilename(:)=" "
206  forfilename(1)='forcing_file.nc'
207  CALL getin_p('FORCING_FILE', forfilename)
208  !-
209  !- Define the zoom
210  !-
211  zoom_lon=(/-180,180/)
212  zoom_lat=(/-90,90/)
213  !
214  !Config Key   = LIMIT_WEST
215  !Config Desc  = Western limit of region
216  !Config If    = [-]
217  !Config Def   = -180.
218  !Config Help  = Western limit of the region we are
219  !Config         interested in. Between -180 and +180 degrees
220  !Config         The model will use the smalest regions from
221  !Config         region specified here and the one of the forcing file.
222  !Config Units = [Degrees]
223  !-
224  CALL getin_p('LIMIT_WEST',zoom_lon(1))
225  !-
226  !Config Key   = LIMIT_EAST
227  !Config Desc  = Eastern limit of region
228  !Config If    = [-]
229  !Config Def   = 180.
230  !Config Help  = Eastern limit of the region we are
231  !Config         interested in. Between -180 and +180 degrees
232  !Config         The model will use the smalest regions from
233  !Config         region specified here and the one of the forcing file.
234  !Config Units = [Degrees]
235  !-
236  CALL getin_p('LIMIT_EAST',zoom_lon(2))
237  !-
238  !Config Key   = LIMIT_NORTH
239  !Config Desc  = Northern limit of region
240  !Config If    = [-]
241  !Config Def   = 90.
242  !Config Help  = Northern limit of the region we are
243  !Config         interested in. Between +90 and -90 degrees
244  !Config         The model will use the smalest regions from
245  !Config         region specified here and the one of the forcing file.
246  !Config Units = [Degrees]
247  !-
248  CALL getin_p('LIMIT_NORTH',zoom_lat(2))
249  !-
250  !Config Key   = LIMIT_SOUTH
251  !Config Desc  = Southern limit of region
252  !Config If    = [-]
253  !Config Def   = -90.
254  !Config Help  = Southern limit of the region we are
255  !Config         interested in. Between 90 and -90 degrees
256  !Config         The model will use the smalest regions from
257  !Config         region specified here and the one of the forcing file.
258  !Config Units = [Degrees]
259  !-
260  CALL getin_p('LIMIT_SOUTH',zoom_lat(1))
261  IF ( (zoom_lon(1)+180 < EPSILON(zoom_lon(1))) .AND. (zoom_lon(2)-180 < EPSILON(zoom_lon(2))) .AND.&
262       &(zoom_lat(1)+90 < EPSILON(zoom_lat(1))) .AND. (zoom_lat(2)-90 < EPSILON(zoom_lat(2))) ) THEN
263     !
264     !Config Key   = WEST_EAST
265     !Config Desc  = Longitude interval to use from the forcing data
266     !Config If    = [-]
267     !Config Def   = -180, 180
268     !Config Help  = This function allows to zoom into the forcing data
269     !Config Units = [degrees east]
270     !-
271     CALL getin_p('WEST_EAST', zoom_lon)
272     !
273     !Config Key   = SOUTH_NORTH
274     !Config Desc  = Latitude interval to use from the forcing data
275     !Config If    = [-]
276     !Config Def   = -90, 90
277     !Config Help  = This function allows to zoom into the forcing data
278     !Config Units = [degrees north]
279     !-
280     CALL getin_p('SOUTH_NORTH', zoom_lat)
281  ENDIF
282  !-
283  !-
284  !- Get some basic variables from the run.def
285  !-
286  atmco2=350.
287  CALL getin_p('ATM_CO2',atmco2)
288  !
289  !====================================================================================
290  !-
291  !-
292  !- Get the grid on all processors.
293  !-
294  !---------------------------------------------------------------------------------------
295  !-
296  !- Read the grid, only on the root proc. from the forcing file using tools in the globgrd module.
297  !- The grid is then broadcast to all other broadcast.
298  !
299  nb_forcefile = 0
300  DO ik=1,100
301     IF ( INDEX(forfilename(ik), '.nc') > 0 ) nb_forcefile = nb_forcefile+1
302  ENDDO
303  !
304  IF ( is_root_prc) THEN
305     CALL globgrd_getdomsz(gridfilename, iim_glo, jjm_glo, nbindex_g, model_guess, file_id, forfilename, zoom_lon, zoom_lat)
306     nbseg = 4
307  ENDIF
308  !
309  CALL bcast(iim_glo)
310  CALL bcast(jjm_glo)
311  CALL bcast(nbindex_g)
312  CALL bcast(nbseg)
313  !-
314  !- Allocation of memory
315  !- variables over the entire grid (thus in x,y)
316  ALLOCATE(lon_glo(iim_glo, jjm_glo))
317  ALLOCATE(lat_glo(iim_glo, jjm_glo))
318  ALLOCATE(mask_glo(iim_glo, jjm_glo))
319  ALLOCATE(area_glo(iim_glo, jjm_glo))
320  ALLOCATE(corners_glo(iim_glo, jjm_glo, nbseg, 2))
321  !
322  ! Gathered variables
323  ALLOCATE(kindex_g(nbindex_g))
324  ALLOCATE(contfrac_glo(nbindex_g))
325  !-
326  IF ( is_root_prc) THEN
327     CALL globgrd_getgrid(file_id, iim_glo, jjm_glo, nbindex_g, model_guess, &
328          &               lon_glo, lat_glo, mask_glo, area_glo, corners_glo,&
329          &               kindex_g, contfrac_glo, calendar)
330  ENDIF
331  !
332  CALL bcast(lon_glo)
333  CALL bcast(lat_glo)
334  CALL bcast(mask_glo)
335  CALL bcast(area_glo)
336  CALL bcast(corners_glo)
337  CALL bcast(kindex_g)
338  CALL bcast(contfrac_glo)
339  CALL bcast(calendar)
340  CALL bcast(model_guess)
341  !
342  ALLOCATE(lalo_glo(nbindex_g,2))
343  DO ik=1,nbindex_g
344     !
345     j = ((kindex_g(ik)-1)/iim_glo)+1
346     i = (kindex_g(ik)-(j-1)*iim_glo)
347     !
348     IF ( i > iim_glo .OR. j > jjm_glo ) THEN
349        WRITE(100+mpi_rank,*) "Error in the indexing (ik, kindex, i, j) : ", ik, kindex(ik), i, j
350        STOP "ERROR in orchideedriver"
351     ENDIF
352     !
353     lalo_glo(ik,1) = lat_glo(i,j)
354     lalo_glo(ik,2) = lon_glo(i,j)
355     !
356  ENDDO
357  !
358  WRITE(*,*) "Rank", mpi_rank, " Before parallel region All land points : ",  nbindex_g
359  WRITE(*,*) "Rank", mpi_rank, " from ", iim_glo, " point in Lon. and ", jjm_glo, "in Lat."
360  !-
361  !---------------------------------------------------------------------------------------
362  !-
363  !- Now that the grid is distributed on all procs we can start
364  !- initialise the ORCHIDEE domain on each proc (longitude, latitude, indices)
365  !-
366  !---------------------------------------------------------------------------------------
367  !-
368  !- init_data_para also transfers kindex_g to index_g (the variable used in ORCHIDEE)
369  !-
370  CALL grid_set_glo(iim_glo, jjm_glo, nbindex_g)
371  CALL grid_allocate_glo(nbseg)
372  ! Copy the list of indexes of land points into index_g used by ORCHIDEE and then broacast to all
373  ! processors
374  CALL bcast(nbindex_g)
375  IF ( is_root_prc) index_g = kindex_g
376  CALL bcast(index_g)
377  !
378  WRITE(numout,*) "Rank", mpi_rank, "Into Init_orchidee_data_para_driver with ", nbindex_g
379  WRITE(numout,*) "Rank", mpi_rank, "Into ", index_g(1), index_g(nbindex_g)
380  !
381  CALL Init_orchidee_data_para_driver(nbindex_g,index_g)
382  CALL init_ioipsl_para 
383  !
384  WRITE(numout,*) "Rank", mpi_rank, "After init_data_para global size : ",  nbp_glo, SIZE(index_g), iim_g, iim_glo, jjm_g, jjm_glo
385  WRITE(numout,'("After init_data_para local : ij_nb, jj_nb",2I4)') iim_glo, jj_nb
386  !
387  ! Allocate grid on the local processor
388  !
389  IF ( model_guess == "regular") THEN
390     CALL grid_init (nbp_loc, nbseg, "RegLonLat", "ForcingGrid")
391  ELSE IF ( model_guess == "WRF") THEN
392     CALL grid_init (nbp_loc, nbseg, "RegXY", "WRFGrid")
393  ELSE
394     CALL ipslerr(3, "orchidedriver", "The grid found in the GRID_FILE is not supported by ORCHIDEE", "", "")
395  ENDIF
396  !
397  !
398  ! Transfer the global grid variables to the ORCHIDEE version on the root proc
399  ! *_glo -> *_g
400  ! Variables *_g were allocated with the CALL init_grid
401  !
402  IF ( is_root_prc) THEN
403     !
404     lalo_g(:,:) = lalo_glo(:,:)
405     lon_g(:,:) = lon_glo(:,:)
406     lat_g(:,:) = lat_glo(:,:)
407     !
408  ENDIF
409  !
410  !
411  ! Set the local dimensions of the fields
412  !
413  iim = iim_glo
414  jjm = jj_nb
415  kjpindex = nbp_loc
416  !
417  WRITE(numout,*) mpi_rank, "DIMENSIONS of grid on processor : iim, jjm, kjpindex = ", iim, jjm, kjpindex
418  !
419  !  Allocate the local arrays we need :
420  !
421  ALLOCATE(lon(iim,jjm), lat(iim,jjm))
422  ALLOCATE(kindex(kjpindex))
423  !
424  lon=lon_glo(:,jj_para_begin(mpi_rank):jj_para_end(mpi_rank))
425  lat=lat_glo(:,jj_para_begin(mpi_rank):jj_para_end(mpi_rank))
426  !
427  !
428  ! Redistribute the indeces on all procs (apple distribution of land points)
429  !
430  CALL bcast(lon_g)
431  CALL bcast(lat_g)
432  CALL scatter(index_g, kindex)
433  !
434  !
435  ! Apply the offset needed so that kindex refers to the index of the land point
436  ! on the current region, i.e. the local lon lat domain.
437  !
438  kindex(1:kjpindex)=kindex(1:kjpindex)-(jj_begin-1)*iim_glo
439  !
440  ! This routine transforms the global grid into a series of polygons for all land
441  ! points identified by index_g.
442  !
443  CALL grid_stuff(nbindex_g, iim_g, jjm_g, lon_g, lat_g, index_g, contfrac_glo)
444  !
445  ! Distribute the global lalo to the local processor level lalo
446  !
447  ALLOCATE(lalo_loc(kjpindex,2))
448  CALL scatter(lalo_glo, lalo_loc)
449  lalo(:,:) = lalo_loc(:,:)
450  !
451  !====================================================================================
452  !-
453  !- Prepare the time for the simulation
454  !-
455  !- Set the global calendar and get the time period for the run
456  !-
457  CALL ioconf_calendar(calendar)
458  CALL forcing_integration_time(date0, dt, nbdt)
459  !
460  !-
461  !- Set the start date in IOIPSL for the calendar and initialize the module time
462  !-
463  CALL ioconf_startdate(date0)
464  CALL time_initialize(0, date0, dt, "END")
465  !
466  !
467  !====================================================================================
468  !-
469  !- Initialize the forcing files and prepare the time stepping through the data.
470  !-
471  !
472  CALL forcing_open(forfilename, iim_glo,  jjm_glo, lon_glo, lat_glo, nbindex_g, zoom_lon, zoom_lat, &
473       &            index_g, kjpindex, numout)
474  !
475  !
476  ALLOCATE(zlev_tq(kjpindex), zlev_uv(kjpindex))
477  ALLOCATE(u(kjpindex), v(kjpindex), pb(kjpindex))
478  ALLOCATE(temp_air(kjpindex))
479  ALLOCATE(qair(kjpindex))
480  ALLOCATE(petAcoef(kjpindex), peqAcoef(kjpindex), petBcoef(kjpindex), peqBcoef(kjpindex))
481  ALLOCATE(ccanopy(kjpindex))
482  ALLOCATE(cdrag(kjpindex))
483  ALLOCATE(precip_rain(kjpindex))
484  ALLOCATE(precip_snow(kjpindex))
485  ALLOCATE(swdown(kjpindex))
486  ALLOCATE(swnet(kjpindex))
487  ALLOCATE(lwdown(kjpindex))
488  ALLOCATE(sinang(kjpindex))
489  ALLOCATE(vevapp(kjpindex))
490  ALLOCATE(fluxsens(kjpindex))
491  ALLOCATE(fluxlat(kjpindex))
492  ALLOCATE(coastalflow(kjpindex))
493  ALLOCATE(riverflow(kjpindex))
494  ALLOCATE(netco2(kjpindex))
495  ALLOCATE(carblu(kjpindex))
496  ALLOCATE(tsol_rad(kjpindex))
497  ALLOCATE(temp_sol_new(kjpindex))
498  ALLOCATE(qsurf(kjpindex))
499  ALLOCATE(albedo(kjpindex,2))
500  ALLOCATE(emis(kjpindex))
501  ALLOCATE(epot_air(kjpindex))
502  ALLOCATE(u_tq(kjpindex), v_tq(kjpindex))
503  ALLOCATE(z0m(kjpindex))
504  ALLOCATE(z0h(kjpindex))
505  ALLOCATE(veget(kjpindex,nvm))
506  ALLOCATE(lai(kjpindex,nvm))
507  ALLOCATE(height(kjpindex,nvm))
508  !-
509  !---------------------------------------------------------------------------------------
510  !-
511  !- Get a first set of forcing data
512  !-
513  !---------------------------------------------------------------------------------------
514  !-
515  !- Some default values so that the operations before the ORCHIDEE initialisation do not fail.
516  !-
517  z0m(:) = 0.1
518  albedo(:,:) = 0.13
519  !-
520  !====================================================================================
521  !-
522  !- Initialise the ORCHIDEE system in 4 steps :
523  !- 1 The control flags,
524  !- 2 the restart system of IOIPSL
525  !- 3 The history mechanism
526  !- 4 Finally the first call to SECHIBA will initialise all the internal variables
527  !
528  CALL control_initialize
529  !
530  itau = 0
531  !
532  CALL ioipslctrl_restini(itau, date0, dt, rest_id, rest_id_stom, itau_offset, date0_shifted)
533  WRITE(numout,*) "itau_offset : ", itau_offset, date0, date0_shifted
534  ! Note that currently itau_offset is always 0
535
536  ! Get the vertical soil levels for the thermal scheme, to be used in xios_orchidee_init
537  ALLOCATE(soilth_lev(ngrnd), stat=ier)
538  IF (ier /= 0) CALL ipslerr_p(3,'orchideedriver', 'Error in allocation of soilth_lev','','')
539  IF (hydrol_cwrr) THEN
540     soilth_lev(1:ngrnd) = znt(:)
541  ELSE
542     soilth_lev(1:ngrnd) = thermosoilc_levels()
543  END IF
544
545  !
546  ! To ensure that itau starts with 0 at date0 for the restart, we have to set an off-set to achieve this.
547  ! itau_offset will get used to prduce itau_sechiba.
548  ! It is not currently possible to read the date from the restart file
549  itau_offset=-itau_offset-1
550
551  WRITE(*,*) "itau_offset : date0 : ", year_end, month_end, day_end, sec_end
552 
553  CALL xios_orchidee_init( MPI_COMM_ORCH,                    &
554       date0,    year_end, month_end, day_end, julian_diff,  &
555       lon,      lat,      soilth_lev)
556  !
557  !- Initialize IOIPSL sechiba output files
558  itau_sechiba = itau+itau_offset
559
560  CALL ioipslctrl_history(iim, jjm, lon, lat,  kindex, kjpindex, itau_sechiba, &
561       date0, dt, hist_id, hist2_id, hist_id_stom, hist_id_stom_IPCC)
562  WRITE(numout,*) "HISTORY : Defined for ", itau_sechiba, date0, dt
563  !
564  !-
565  !---------------------------------------------------------------------------------------
566  !-
567  !- Go into the time loop
568  !-
569  !---------------------------------------------------------------------------------------
570  !-
571  DO itau = 1,nbdt
572     !
573     CALL time_nextstep( itau )
574     !
575     timestep_interval(1) = julian_start
576     timestep_interval(2) = julian_end
577     julian = julian_end
578     !
579     ! Get the forcing data
580     !
581     CALL forcing_getvalues(timestep_interval, dt, zlev_tq, zlev_uv, temp_air, qair, &
582          &                 precip_rain, precip_snow, swdown, lwdown, sinang, u, v, pb)
583     !-
584     !
585     IF ( itau == nbdt ) lrestart_write = .TRUE.
586     !
587     ! Adaptation of the forcing data to SECHIBA's needs
588     !
589     ! Contrary to what the documentation says, ORCHIDEE expects surface pressure in hPa.
590     pb(:) = pb(:)/100.
591     epot_air(:) = cp_air*temp_air(:)+cte_grav*zlev_tq(:)
592     ccanopy(:) = atmco2
593     cdrag(:) = 0.0
594     !
595     petBcoef(:) = epot_air(:)
596     peqBcoef(:) = qair(:)
597     petAcoef(:) = zero
598     peqAcoef(:) = zero
599     !
600     ! Interpolate the wind (which is at hight zlev_uv) to the same height
601     ! as the temperature and humidity (at zlev_tq).
602     !
603     u_tq(:) = u(:)*LOG(zlev_tq(:)/z0m(:))/LOG(zlev_uv(:)/z0m(:))
604     v_tq(:) = v(:)*LOG(zlev_tq(:)/z0m(:))/LOG(zlev_uv(:)/z0m(:))
605     !
606     !
607     swnet(:) =(1.-(albedo(:,1)+albedo(:,2))/2.)*swdown(:)
608     !
609     !
610     CALL forcing_printpoint(julian, testpt(1), testpt(2), kjpindex, lalo_loc, temp_air, "RECEIVED Air temperature")
611     CALL forcing_printpoint(julian, testpt(1), testpt(2), kjpindex, lalo_loc, qair, "RECEIVED Air humidity")
612     CALL forcing_printpoint(julian, testpt(1), testpt(2), kjpindex, lalo_loc, precip_rain*one_day, "RECEIVED Rainfall")
613     CALL forcing_printpoint(julian, testpt(1), testpt(2), kjpindex, lalo_loc, precip_snow*one_day, "RECEIVED Snowfall")
614     CALL forcing_printpoint(julian, testpt(1), testpt(2), kjpindex, lalo_loc, swnet, "RECEIVED net solar")
615     CALL forcing_printpoint(julian, testpt(1), testpt(2), kjpindex, lalo_loc, lwdown, "RECEIVED lwdown")
616     CALL forcing_printpoint(julian, testpt(1), testpt(2), kjpindex, lalo_loc, u, "RECEIVED East-ward wind")
617     CALL forcing_printpoint(julian, testpt(1), testpt(2), kjpindex, lalo_loc, v, "RECEIVED North-ward wind")
618     CALL forcing_printpoint(julian, testpt(1), testpt(2), kjpindex, lalo_loc, pb*100, "RECEIVED surface pressure")
619     CALL forcing_printpoint(julian, testpt(1), testpt(2), kjpindex, lalo_loc, zlev_uv, "RECEIVED UV height")
620     CALL forcing_printpoint(julian, testpt(1), testpt(2), kjpindex, lalo_loc, zlev_tq, "RECEIVED TQ height")
621     CALL forcing_printpoint(julian, testpt(1), testpt(2), kjpindex, lalo_loc, sinang, "RECEIVED sinang")
622     !
623     IF ( itau .NE. 1 ) THEN
624        IF ( timemeasure ) THEN
625           waitget_cputime = waitget_cputime + Get_cpu_Time(timer_global)
626           waitget_walltime = waitget_walltime + Get_real_Time(timer_global)
627           CALL stop_timer(timer_global)
628           CALL start_timer(timer_global)
629        ENDIF
630     ENDIF
631     !
632     !---------------------------------------------------------------------------------------
633     !-
634     !- IF first time step : Call to SECHIBA_initialize to set-up ORCHIDEE before doing an actual call
635     !- which will provide the first fluxes.
636     !-
637     !---------------------------------------------------------------------------------------
638     !
639     itau_sechiba = itau+itau_offset
640     !
641     ! Update the calendar in xios by sending the new time step
642     CALL xios_orchidee_update_calendar(itau_sechiba)
643     !
644     IF ( itau == 1 ) THEN
645        !
646        IF ( timemeasure ) THEN
647           WRITE(numout,*) '------> CPU Time for start-up of main : ',Get_cpu_Time(timer_global)
648           WRITE(numout,*) '------> Real Time for start-up of main : ',Get_real_Time(timer_global)
649           CALL stop_timer(timer_global)
650           CALL start_timer(timer_global)
651        ENDIF
652        !
653        CALL sechiba_initialize( &
654             itau_sechiba, iim*jjm,      kjpindex,      kindex,                    &
655             lalo_loc,     contfrac,     neighbours,    resolution,  zlev_tq,      &
656             u_tq,         v_tq,         qair,          temp_air,    temp_air,     &
657             petAcoef,     peqAcoef,     petBcoef,      peqBcoef,                  &
658             precip_rain,  precip_snow,  lwdown,        swnet,       swdown,       &
659             pb,           rest_id,      hist_id,       hist2_id,                  &
660             rest_id_stom, hist_id_stom, hist_id_stom_IPCC,                        &
661             coastalflow,  riverflow,    tsol_rad,      vevapp,      qsurf,        &
662             z0m,          z0h,          albedo,        fluxsens,    fluxlat,  emis, &
663             netco2,       carblu,       temp_sol_new,  cdrag)
664        CALL forcing_printpoint(julian, testpt(1), testpt(2), kjpindex, lalo_loc, temp_sol_new, "Init temp_sol_new")
665        !
666        ! Net solar and the wind at the right hight are recomputed with the correct values.
667        !
668        swnet(:) =(1.-(albedo(:,1)+albedo(:,2))/2.)*swdown(:)
669        u_tq(:) = u(:)*LOG(zlev_tq(:)/z0m(:))/LOG(zlev_uv(:)/z0m(:))
670        v_tq(:) = v(:)*LOG(zlev_tq(:)/z0m(:))/LOG(zlev_uv(:)/z0m(:))
671        !
672        lrestart_read = .FALSE.
673        !
674        CALL histwrite_p(hist_id, 'LandPoints',  itau+1, (/ REAL(kindex) /), kjpindex, kindex)
675        CALL histwrite_p(hist_id, 'Areas',  itau+1, area, kjpindex, kindex)
676        CALL histwrite_p(hist_id, 'Contfrac',  itau+1, contfrac, kjpindex, kindex)
677        !
678        IF ( timemeasure ) THEN
679           WRITE(numout,*) '------> CPU Time for set-up of ORCHIDEE : ',Get_cpu_Time(timer_global)
680           WRITE(numout,*) '------> Real Time for set-up of ORCHIDEE : ',Get_real_Time(timer_global)
681           CALL stop_timer(timer_global)
682           CALL start_timer(timer_global)
683        ENDIF
684        !
685     ENDIF
686     !
687     !---------------------------------------------------------------------------------------
688     !-
689     !- Main call to SECHIBA 
690     !-
691     !---------------------------------------------------------------------------------------
692     !
693     !
694     CALL sechiba_main (itau_sechiba, iim*jjm, kjpindex, kindex, &
695          & lrestart_read, lrestart_write, &
696          & lalo_loc, contfrac, neighbours, resolution, &
697          ! First level conditions
698          & zlev_tq, u_tq, v_tq, qair, qair, temp_air, temp_air, epot_air, ccanopy, &
699          ! Variables for the implicit coupling
700          & cdrag, petAcoef, peqAcoef, petBcoef, peqBcoef, &
701          ! Rain, snow, radiation and surface pressure
702          & precip_rain ,precip_snow, lwdown, swnet, swdown, sinang, pb, &
703          ! Output : Fluxes
704          & vevapp, fluxsens, fluxlat, coastalflow, riverflow, netco2, carblu, &
705          ! Surface temperatures and surface properties
706          & tsol_rad, temp_sol_new, qsurf, albedo, emis, z0m, z0h, &
707          ! Vegeation, lai and vegetation height
708          & veget, lai, height, &
709          ! File ids
710          & rest_id, hist_id, hist2_id, rest_id_stom, hist_id_stom, hist_id_stom_IPCC)
711     !
712     CALL forcing_printpoint(julian, testpt(1), testpt(2), kjpindex, lalo_loc, temp_sol_new, "Produced temp_sol_new")
713     CALL forcing_printpoint(julian, testpt(1), testpt(2), kjpindex, lalo_loc, fluxsens, "Produced fluxsens")
714     CALL forcing_printpoint(julian, testpt(1), testpt(2), kjpindex, lalo_loc, fluxlat, "Produced fluxlat")
715     !
716     IF ( timemeasure ) THEN
717        orchidee_cputime = orchidee_cputime + Get_cpu_Time(timer_global)
718        orchidee_walltime = orchidee_walltime + Get_real_Time(timer_global)
719        CALL stop_timer(timer_global)
720        CALL start_timer(timer_global)
721     ENDIF
722     !
723     !---------------------------------------------------------------------------------------
724     !-
725     !- Write diagnostics
726     !-
727     !---------------------------------------------------------------------------------------
728     !
729     CALL xios_orchidee_send_field("LandPoints" ,(/ ( REAL(ik), ik=1,kjpindex ) /))
730     CALL xios_orchidee_send_field("areas", area)
731     CALL xios_orchidee_send_field("contfrac",contfrac)
732     CALL xios_orchidee_send_field("temp_air",temp_air)
733     CALL xios_orchidee_send_field("qair",qair)
734     CALL xios_orchidee_send_field("swnet",swnet)
735     CALL xios_orchidee_send_field("swdown",swdown)
736     ! zpb in hPa, output in Pa
737     CALL xios_orchidee_send_field("pb",pb)
738     !
739     IF ( .NOT. almaoutput ) THEN
740        !
741        !  ORCHIDEE INPUT variables
742        !
743        CALL histwrite_p (hist_id, 'swdown',   itau_sechiba, swdown,   kjpindex, kindex)
744        CALL histwrite_p (hist_id, 'tair',     itau_sechiba, temp_air, kjpindex, kindex)
745        CALL histwrite_p (hist_id, 'qair',     itau_sechiba, qair, kjpindex, kindex)
746        CALL histwrite_p (hist_id, 'evap',     itau_sechiba, vevapp, kjpindex, kindex)
747        CALL histwrite_p (hist_id, 'coastalflow',itau_sechiba, coastalflow, kjpindex, kindex)
748        CALL histwrite_p (hist_id, 'riverflow',itau_sechiba, riverflow, kjpindex, kindex)
749        !
750        CALL histwrite_p (hist_id, 'temp_sol', itau_sechiba, temp_sol_new, kjpindex, kindex)
751        CALL histwrite_p (hist_id, 'tsol_max', itau_sechiba, temp_sol_new, kjpindex, kindex)
752        CALL histwrite_p (hist_id, 'tsol_min', itau_sechiba, temp_sol_new, kjpindex, kindex)
753        CALL histwrite_p (hist_id, 'fluxsens', itau_sechiba, fluxsens, kjpindex, kindex)
754        CALL histwrite_p (hist_id, 'fluxlat',  itau_sechiba, fluxlat,  kjpindex, kindex)
755        CALL histwrite_p (hist_id, 'swnet',    itau_sechiba, swnet,    kjpindex, kindex)
756        CALL histwrite_p (hist_id, 'alb_vis',  itau_sechiba, albedo(:,1), kjpindex, kindex)
757        CALL histwrite_p (hist_id, 'alb_nir',  itau_sechiba, albedo(:,2), kjpindex, kindex)
758        !
759        IF ( hist2_id > 0 ) THEN
760           CALL histwrite_p (hist2_id, 'swdown',   itau_sechiba, swdown, kjpindex, kindex)
761           CALL histwrite_p (hist2_id, 'tair',     itau_sechiba, temp_air, kjpindex, kindex)
762           CALL histwrite_p (hist2_id, 'qair',     itau_sechiba, qair, kjpindex, kindex)
763           !
764           CALL histwrite_p (hist2_id, 'evap',     itau_sechiba, vevapp, kjpindex, kindex)
765           CALL histwrite_p (hist2_id, 'coastalflow',itau_sechiba, coastalflow, kjpindex, kindex)
766           CALL histwrite_p (hist2_id, 'riverflow',itau_sechiba, riverflow, kjpindex, kindex)
767           !
768           CALL histwrite_p (hist2_id, 'temp_sol', itau_sechiba, temp_sol_new, kjpindex, kindex)
769           CALL histwrite_p (hist2_id, 'tsol_max', itau_sechiba, temp_sol_new, kjpindex, kindex)
770           CALL histwrite_p (hist2_id, 'tsol_min', itau_sechiba, temp_sol_new, kjpindex, kindex)
771           CALL histwrite_p (hist2_id, 'fluxsens', itau_sechiba, fluxsens, kjpindex, kindex)
772           CALL histwrite_p (hist2_id, 'fluxlat',  itau_sechiba, fluxlat,  kjpindex, kindex)
773           CALL histwrite_p (hist2_id, 'swnet',    itau_sechiba, swnet,    kjpindex, kindex)
774           !
775           CALL histwrite_p (hist2_id, 'alb_vis',  itau_sechiba, albedo(:,1), kjpindex, kindex)
776           CALL histwrite_p (hist2_id, 'alb_nir',  itau_sechiba, albedo(:,2), kjpindex, kindex)
777        ENDIF
778     ELSE
779        !
780        ! Input variables
781        !
782        CALL histwrite_p (hist_id, 'SinAng', itau_sechiba, sinang, kjpindex, kindex)
783        CALL histwrite_p (hist_id, 'LWdown', itau_sechiba, lwdown, kjpindex, kindex)
784        CALL histwrite_p (hist_id, 'SWdown', itau_sechiba, swdown, kjpindex, kindex)
785        CALL histwrite_p (hist_id, 'Tair', itau_sechiba, temp_air, kjpindex, kindex)
786        CALL histwrite_p (hist_id, 'Qair', itau_sechiba, qair, kjpindex, kindex)
787        CALL histwrite_p (hist_id, 'SurfP', itau_sechiba, pb, kjpindex, kindex)
788        CALL histwrite_p (hist_id, 'Windu', itau_sechiba, u_tq, kjpindex, kindex)
789        CALL histwrite_p (hist_id, 'Windv', itau_sechiba, v_tq, kjpindex, kindex)
790        !
791        CALL histwrite_p (hist_id, 'Evap', itau_sechiba, vevapp, kjpindex, kindex)
792        CALL histwrite_p (hist_id, 'SWnet',    itau_sechiba, swnet, kjpindex, kindex)
793        CALL histwrite_p (hist_id, 'Qh', itau_sechiba, fluxsens, kjpindex, kindex)
794        CALL histwrite_p (hist_id, 'Qle',  itau_sechiba, fluxlat, kjpindex, kindex)
795        CALL histwrite_p (hist_id, 'AvgSurfT', itau_sechiba, temp_sol_new, kjpindex, kindex)
796        CALL histwrite_p (hist_id, 'RadT', itau_sechiba, temp_sol_new, kjpindex, kindex)
797        !
798        ! There is a mess with the units passed to the coupler. To be checked with Marc
799        !
800        IF ( river_routing ) THEN
801           CALL histwrite_p (hist_id, 'CoastalFlow',itau_sechiba, coastalflow, kjpindex, kindex)
802           CALL histwrite_p (hist_id, 'RiverFlow',itau_sechiba, riverflow, kjpindex, kindex)
803        ENDIF
804        !
805        IF ( hist2_id > 0 ) THEN
806           CALL histwrite_p (hist2_id, 'Evap', itau_sechiba, vevapp, kjpindex, kindex)
807           CALL histwrite_p (hist2_id, 'SWnet',    itau_sechiba, swnet, kjpindex, kindex)
808           CALL histwrite_p (hist2_id, 'Qh', itau_sechiba, fluxsens, kjpindex, kindex)
809           CALL histwrite_p (hist2_id, 'Qle',  itau_sechiba, fluxlat, kjpindex, kindex)
810           CALL histwrite_p (hist2_id, 'AvgSurfT', itau_sechiba, temp_sol_new, kjpindex, kindex)
811           CALL histwrite_p (hist2_id, 'RadT', itau_sechiba, temp_sol_new, kjpindex, kindex)
812        ENDIF
813     ENDIF
814     !
815     !
816  ENDDO
817  !-
818  !-
819  !---------------------------------------------------------------------------------------
820  !-
821  !- Close eveything
822  !-
823  !--
824  !
825  CALL histclo
826  IF(is_root_prc) THEN
827     CALL restclo
828     CALL getin_dump
829  ENDIF
830
831  !-
832  !- Deallocate all variables and reset initialization variables
833  !-
834  CALL orchideedriver_clear()
835
836  WRITE(numout,*) "End at proc ", mpi_rank
837  !
838  !
839  !---------------------------------------------------------------------------------------
840  !-
841  !- Get time and close IOIPSL, OASIS and MPI
842  !-
843  !---------------------------------------------------------------------------------------
844  !-
845  IF ( timemeasure ) THEN
846     WRITE(numout,*) '------> Total CPU Time waiting to get forcing : ',waitget_cputime
847     WRITE(numout,*) '------> Total Real Time waiting to get forcing : ',waitget_walltime
848     WRITE(numout,*) '------> Total CPU Time for ORCHIDEE : ', orchidee_cputime
849     WRITE(numout,*) '------> Total Real Time for ORCHIDEE : ', orchidee_walltime
850     WRITE(numout,*) '------> Total CPU Time waiting to put fluxes : ',waitput_cputime
851     WRITE(numout,*) '------> Total Real Time waiting to put fluxes : ',waitput_walltime
852     WRITE(numout,*) '------> Total CPU Time for closing : ',  Get_cpu_Time(timer_global)
853     WRITE(numout,*) '------> Total Real Time for closing : ', Get_real_Time(timer_global)
854     WRITE(numout,*) '------> Total without MPI : CPU Time  : ', Get_cpu_Time(timer_mpi)
855     WRITE(numout,*) '------> Total without MPI : Real Time : ', Get_real_Time(timer_mpi)
856     CALL stop_timer(timer_global)
857     CALL stop_timer(timer_mpi)
858  ENDIF
859  !
860  CALL Finalize_mpi
861  CONTAINS
862   
863!! ================================================================================================================================
864!! SUBROUTINE   : orchideedriver_clear
865!!
866!>\BRIEF         Clear orchideedriver
867!!
868!! DESCRIPTION  :  Deallocate memory and reset initialization variables to there original values
869!!                 This subroutine calls forcing_tools_clear and sechiba_clear.
870!!
871!_ ================================================================================================================================
872     SUBROUTINE orchideedriver_clear
873
874      !- Deallocate all variables existing on all procs
875
876      IF ( ALLOCATED(lon_glo) ) DEALLOCATE(lon_glo)
877      IF ( ALLOCATED(lat_glo) ) DEALLOCATE(lat_glo)
878      IF ( ALLOCATED(mask_glo) ) DEALLOCATE(mask_glo)
879      IF ( ALLOCATED(area_glo) ) DEALLOCATE(area_glo)
880      IF ( ALLOCATED(corners_glo) ) DEALLOCATE(corners_glo)
881      IF ( ALLOCATED(kindex_g) ) DEALLOCATE(kindex_g)
882      IF ( ALLOCATED(contfrac_glo) ) DEALLOCATE(contfrac_glo)
883      IF ( ALLOCATED(lalo_glo) ) DEALLOCATE(lalo_glo)
884      IF ( ALLOCATED(lon) ) DEALLOCATE(lon)
885      IF ( ALLOCATED(lat) ) DEALLOCATE(lat)
886      IF ( ALLOCATED(kindex) ) DEALLOCATE(kindex)
887      IF ( ALLOCATED(lalo_loc) ) DEALLOCATE(lalo_loc)
888      IF ( ALLOCATED(zlev_tq) ) DEALLOCATE(zlev_tq)
889      IF ( ALLOCATED(zlev_uv) ) DEALLOCATE(zlev_uv)
890      IF ( ALLOCATED(u) ) DEALLOCATE(u)
891      IF ( ALLOCATED(v) ) DEALLOCATE(v)
892      IF ( ALLOCATED(pb) ) DEALLOCATE(pb)
893      IF ( ALLOCATED(temp_air) ) DEALLOCATE(temp_air)
894      IF ( ALLOCATED(qair) ) DEALLOCATE(qair)
895      IF ( ALLOCATED(precip_rain) ) DEALLOCATE(precip_rain)
896      IF ( ALLOCATED(precip_snow) ) DEALLOCATE(precip_snow)
897      IF ( ALLOCATED(swdown) ) DEALLOCATE(swdown)
898      IF ( ALLOCATED(swnet) ) DEALLOCATE(swnet)
899      IF ( ALLOCATED(lwdown) ) DEALLOCATE(lwdown)
900      IF ( ALLOCATED(sinang) ) DEALLOCATE(sinang)
901      IF ( ALLOCATED(epot_air) ) DEALLOCATE(epot_air)
902      IF ( ALLOCATED(ccanopy) ) DEALLOCATE(ccanopy)
903      IF ( ALLOCATED(cdrag) ) DEALLOCATE(cdrag)
904      IF ( ALLOCATED(swnet) ) DEALLOCATE(swnet)
905      IF ( ALLOCATED(petAcoef) ) DEALLOCATE(petAcoef)
906      IF ( ALLOCATED(peqAcoef) ) DEALLOCATE(peqAcoef)
907      IF ( ALLOCATED(petBcoef) ) DEALLOCATE(petBcoef)
908      IF ( ALLOCATED(peqBcoef) ) DEALLOCATE(peqBcoef)
909      IF ( ALLOCATED(u_tq) ) DEALLOCATE(u_tq)
910      IF ( ALLOCATED(v_tq) ) DEALLOCATE(v_tq)
911      IF ( ALLOCATED(vevapp) ) DEALLOCATE(vevapp)
912      IF ( ALLOCATED(fluxsens) ) DEALLOCATE(fluxsens)
913      IF ( ALLOCATED(fluxlat) ) DEALLOCATE(fluxlat)
914      IF ( ALLOCATED(coastalflow) ) DEALLOCATE(coastalflow)
915      IF ( ALLOCATED(riverflow) ) DEALLOCATE(riverflow)
916      IF ( ALLOCATED(netco2) ) DEALLOCATE(netco2)
917      IF ( ALLOCATED(carblu) ) DEALLOCATE(carblu)
918      IF ( ALLOCATED(tsol_rad) ) DEALLOCATE(tsol_rad)
919      IF ( ALLOCATED(temp_sol_new) ) DEALLOCATE(temp_sol_new)
920      IF ( ALLOCATED(qsurf) ) DEALLOCATE(qsurf)
921      IF ( ALLOCATED(albedo) ) DEALLOCATE(albedo)
922      IF ( ALLOCATED(emis) ) DEALLOCATE(emis)
923      IF ( ALLOCATED(z0m) ) DEALLOCATE(z0m)
924     
925      ! Deallocate and reset variables in forcing_tools module
926      CALL forcing_tools_clear()
927
928      ! Deallocate and reset variables in sechiba module and underlaying modules
929      CALL sechiba_clear()
930
931      WRITE(numout,*) "Memory deallocated in orchideedriver_clear"
932     
933    END SUBROUTINE orchideedriver_clear
934
935END PROGRAM orchidedriver
Note: See TracBrowser for help on using the repository browser.