source: branches/ORCHIDEE_2_2/ORCHIDEE/src_driver/orchideedriver.f90 @ 5804

Last change on this file since 5804 was 5573, checked in by josefine.ghattas, 6 years ago

Do not use t2m/q2m coming from the atmospheric model anymore and instead use temp_air and qair from first atmpospheric model layer. t2m/q2m were previously used only in diffuco_trans_co2 and in stomate_initialize. Also removed diagnostic variables t2m and q2m. See ticket #372

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