SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
offline.F90
Go to the documentation of this file.
1 !SFX_LIC Copyright 1994-2014 CNRS, Meteo-France and Universite Paul Sabatier
2 !SFX_LIC This is part of the SURFEX software governed by the CeCILL-C licence
3 !SFX_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt
4 !SFX_LIC for details. version 1.
5 ! -------------------------------------------------
6 PROGRAM offline
7 !
8 ! -------------------------------------------------
9 ! Driver structure
10 ! ----------------
11 ! 1. Initializations
12 ! 2. Temporal loops
13 ! 2.a Read forcing
14 ! 2.b Interpolate forcing in time
15 ! 2.c Run surface
16 ! 2.d Write prognostics and diagnostics variables
17 !
18 ! modifications
19 ! 09/2012 G. Pigeon: coherence between radiation and zenith angle because of
20 ! trouble with radiation received by wall in TEB
21 ! 03/2014 E. Martin change indices names in OMP module according to GMAP changes
22 ! 05/2014 B. Decharme delete trip
23 ! I5 format to print DAY
24 ! 04/2013 P. Lemoigne Add XDELTA_OROG to fix the maximum difference allowed between
25 ! forcing and surface file orographies if LSET_FORC_ZS=.F
26 ! 12/2013 S.Senesi Add call to Gelato diag files init and close
27 !
28 ! 02/2016: replace DOUBLE PRECISION by REAL to handle problem for promotion of real with GMKPACK or IBM SP
29 !
30 ! -------------------------------------------------
31 !
33 !
34 USE modd_forc_atm, ONLY: csv ,&! name of all scalar variables
35  xdir_alb ,&! direct albedo for each band
36  xsca_alb ,&! diffuse albedo for each band
37  xemis ,&! emissivity
38  xtsrad ,&! radiative temperature
39  xtsun ,&! solar time (s from midnight)
40  xzs ,&! orography (m)
41  xzref ,&! height of T,q forcing (m)
42  xuref ,&! height of wind forcing (m)
43  xta ,&! air temperature forcing (K)
44  xqa ,&! air humidity forcing (kg/m3)
45  xsv ,&! scalar variables
46  xu ,&! zonal wind (m/s)
47  xv ,&! meridian wind (m/s)
48  xdir_sw ,&! direct solar radiation (on horizontal surf.)
49  xsca_sw ,&! diffuse solar radiation (on horizontal surf.)
50  xsw_bands ,&! mean wavelength of each shortwave band (m)
51  xzenith ,&! zenithal angle (radian from the vertical)
52  xzenith2 ,&! zenithal angle (radian from the vertical)
53  xazim ,&! azimuthal angle (radian from North, clockwise)
54  xlw ,&! longwave radiation (on horizontal surf.)
55  xps ,&! pressure at atmospheric model surface (Pa)
56  xpa ,&! pressure at forcing level (Pa)
57  xrhoa ,&! density at forcing level (kg/m3)
58  xco2 ,&! CO2 concentration in the air (kg/m3)
59  xsnow ,&! snow precipitation (kg/m2/s)
60  xrain ,&! liquid precipitation (kg/m2/s)
61  xsfth ,&! flux of heat (W/m2)
62  xsftq ,&! flux of water vapor (kg/m2/s)
63  xsfu ,&! zonal momentum flux (m/s)
64  xsfv ,&! meridian momentum flux (m/s)
65  xsfco2 ,&! flux of CO2 (kg/m2/s)
66  xsfts ,&! flux of scalar var. (kg/m2/s)
67  xpew_a_coef ,&! implicit coefficients
68  xpew_b_coef ,&! needed if HCOUPLING='I'
69  xpet_a_coef ,&
70  xpeq_a_coef ,&
71  xpet_b_coef ,&
72  xpeq_b_coef ,&
73  xtsurf ,&! effective temperature (K)
74  xz0 ,&! surface roughness length for momentum (m)
75  xz0h ,&! surface roughness length for heat (m)
76  xqsurf ! specific humidity at surface (kg/kg)
77 !
78 USE modd_surf_conf, ONLY : cprogname, csoftware
79 USE modd_csts, ONLY : xpi, xday, xrv, xrd, xg
80 USE modd_io_surf_asc,ONLY : cfilein,cfilein_save,cfileout,cfilepgd
81 USE modd_surf_par
82 USE modd_io_surf_fa, ONLY : cfilein_fa, cfilein_fa_save, &
83  cfileout_fa, nunit_fa, cdnomc, &
84  iverbfa, lfanocompact, cfilepgd_fa
85 USE modd_io_surf_lfi,ONLY : cfilein_lfi, cfilein_lfi_save, cluout_lfi, cfileout_lfi, &
86  lmnh_compatible, cfilepgd_lfi
87 USE modd_io_surf_nc, ONLY : cfilein_nc, cfilein_nc_save, cfileout_nc, cluout_nc, &
88  cfilepgd_nc, ldef
89 USE modd_io_surf_ol, ONLY : xstart, xcount, xstride, &
90  ldefined_nature, ldefined_sea, &
91  ldefined_water, ldefined_town, &
92  ldefined_surf_atm, lpartw, &
93  xstartw, xcountw, ltime_written, &
94  nstep_output
95 USE modd_write_bin, ONLY : nwrite
96 !
97 USE modd_surfex_mpi, ONLY : ncomm, nproc, nrank, npio, wlog_mpi, prep_log_mpi, &
98  nindex, nsize_task, xtime_npio_read, xtime_npio_write, &
99  xtime_comm_read, xtime_comm_write, xtime_sea, &
100  xtime_nature, xtime_water, xtime_town, &
101  xtime_init_sea, xtime_init_water, &
102  xtime_init_nature, xtime_init_town, &
103  xtime_write, xtime_calc, xtime_omp_barr, &
104  xtime_calc_write, idx_w, end_log_mpi
105 !
106 USE modd_surfex_omp, ONLY : nindx1sfx, nindx2sfx, nblock, nblocktot, &
107  init_dim, reset_dim, nwork, nwork2, xwork, xwork2, xwork3, &
108  nwork_full, nwork2_full, xwork_full, xwork2_full
109 !
110 USE modd_coupling_topd, ONLY : nnb_topd, nnb_stp_restart, lbudget_topd, ltopd_step, &
111  lcoupl_topd, ntopd_step, nyear, nmonth, nday, nh, nm
112 USE modd_topodyn, ONLY : xtopd_step, nnb_topd_step, xqtot, xqb_run, xqb_dr
113 !
114 USE modd_slope_effect, ONLY: xzs_thread,xzs_xy_thread,xslopang_thread,&
115  xslopazi_thread,xsurf_triangle_thread
116 !
117 USE modd_sfx_oasis, ONLY : loasis, xruntime
118 !
119 USE mode_pos_surf
120 !
121 USE mode_crodebug
122 !
123 USE modn_io_offline
124 !
125 USE modi_get_luout
126 USE modi_open_namelist
128 USE modi_close_namelist
129 USE modi_read_all_namelists
130 USE modi_open_close_bin_asc_forc
131 USE modi_open_filein_ol
132 USE modi_ol_read_atm_conf
133 USE modi_abor1_sfx
134 USE modi_ol_alloc_atm
135 USE modi_compare_orography
136 USE modi_sunpos
137 USE modi_init_index_mpi
138 USE modi_ol_read_atm
139 USE modi_get_sizes_parallel
140 USE modi_io_buff_clean
141 USE modi_init_surf_atm_n
142 USE modi_init_surf_landuse_n
143 USE modi_ol_time_interp_atm
144 USE modi_coupling_surf_atm_n
145 USE modi_add_forecast_to_date_surf
146 USE modi_write_surf_atm_n
147 USE modi_write_header_mnh
148 USE modi_flag_update
149 USE modi_flag_diag_update
150 USE modi_diag_surf_atm_n
151 USE modi_write_diag_surf_atm_n
152 USE modi_get_surf_var_n
154 USE modi_close_filein_ol
155 USE modi_close_fileout_ol
156 USE modi_init_output_ol_n
157 USE modi_init_output_nc_n
158 !
159 USE modi_write_header_fa
160 USE modi_abor1_sfx
161 !
162 USE modi_write_discharge_file
163 USE modi_write_budget_coupl_rout
164 USE modi_prep_restart_coupl_topd
165 !
166 USE modi_init_slope_param
167 USE modi_slope_radiative_effect
168 !
169 USE modi_sfx_oasis_init
170 USE modi_sfx_oasis_read_nam
171 USE modi_sfx_oasis_def_ol
172 USE modi_sfx_oasis_recv_ol
173 USE modi_sfx_oasis_send_ol
174 USE modi_sfx_oasis_end
175 !RJ: missing modi
176 USE modi_local_slope_param
177 !
178 USE mode_glt_dia_lu
179 !
180 USE yomhook ,ONLY : lhook, dr_hook
181 USE parkind1 ,ONLY : jprb
182 !
183 #ifdef AIX64
184 !$ USE OMP_LIB
185 #endif
186 !
187 IMPLICIT NONE
188 !
189 #ifdef SFX_MPI
190 include 'mpif.h'
191 #endif
192 !
193 #ifndef AIX64
194 !$ INCLUDE 'omp_lib.h'
195 #endif
196 !
197 !* 0. declarations of local variables
198 !
199  CHARACTER(LEN=3), PARAMETER :: yinit = 'ALL'
200 !
201  CHARACTER(LEN=28) :: yluout = 'LISTING_OFFLINE '
202 !
203 INTEGER :: iyear ! current year (UTC)
204 INTEGER :: imonth ! current month (UTC)
205 INTEGER :: iday ! current day (UTC)
206 REAL :: ztime ! current time since start of the run (s)
207 REAL :: ztimec ! current duration since start of the run (s)
208 !
209 INTEGER :: iyear_out ! output year name
210 INTEGER :: imonth_out ! output month name
211 INTEGER :: iday_out ! output day name
212 REAL :: ztime_out ! output time since start of the run (s)
213 !
214 INTEGER, DIMENSION(11) :: idatef
215 !
216  CHARACTER(LEN=28), PARAMETER :: yatmfile = ' '
217  CHARACTER(LEN=6), PARAMETER :: yatmfiletype = ' '
218  CHARACTER(LEN=2), PARAMETER :: ytest = 'OK' ! must be equal to 'OK'
219 !
220 REAL, DIMENSION(:), POINTER :: zlat ! latitude (rad)
221 REAL, DIMENSION(:), POINTER :: zlon ! longitude (rad)
222 REAL, DIMENSION(:), POINTER :: zzs_forc ! orography (m)
223 REAL, DIMENSION(:), POINTER :: zzref ! Forcing level for T
224 REAL, DIMENSION(:), POINTER :: zuref ! Forcing level for U
225 !
226 REAL :: ztstep ! atmospheric time-step (s)
227 !
228 INTEGER :: ini ! grid dimension
229 INTEGER :: jloop ! loop counter
230 INTEGER :: ibands ! Number of radiative bands
231 INTEGER :: inb_step_atm ! Number of atmospheric time-steps
232 INTEGER :: inb_atm ! Number of Isba time-steps
233  ! within a forcing time-step
234 INTEGER :: id_forc ! indice of forcing in the file
235 INTEGER :: inb_lines ! nb of lines to read in the forcing file
236 INTEGER :: idmax ! nb of lines to read in the forcing file at last
237 INTEGER :: jforc_step ! atmospheric loop index
238 INTEGER :: jsurf_step ! isba loop index
239 INTEGER :: icount ! day counter
240 REAL :: zduration ! duration of run (s)
241 !
242 REAL, DIMENSION(:,:), ALLOCATABLE :: zta ! air temperature forcing (K)
243 REAL, DIMENSION(:,:), ALLOCATABLE :: zqa ! air humidity forcing (kg/m3)
244 REAL, DIMENSION(:,:), ALLOCATABLE :: zwind ! wind speed (m/s)
245 REAL, DIMENSION(:,:), ALLOCATABLE :: zsca_sw ! diffuse solar radiation (on horizontal surf.)
246 REAL, DIMENSION(:,:), ALLOCATABLE :: zdir_sw ! direct solar radiation (on horizontal surf.)
247 REAL, DIMENSION(:,:), ALLOCATABLE :: zlw ! longwave radiation (on horizontal surf.)
248 REAL, DIMENSION(:,:), ALLOCATABLE :: zsnow ! snow precipitation (kg/m2/s)
249 REAL, DIMENSION(:,:), ALLOCATABLE :: zrain ! liquid precipitation (kg/m2/s)
250 REAL, DIMENSION(:,:), ALLOCATABLE :: zps ! pressure at forcing level (Pa)
251 REAL, DIMENSION(:,:), ALLOCATABLE :: zco2 ! CO2 concentration in the air (kg/m3)
252 REAL, DIMENSION(:,:), ALLOCATABLE :: zdir ! wind direction
253 INTEGER :: iluout ! ascii output unit number
254 INTEGER :: ilunam ! namelist unit number
255 INTEGER :: iret ! error return code
256 INTEGER :: inb
257 INTEGER :: inw, jnw
258  CHARACTER(LEN=14) :: ytag
259 LOGICAL :: gfound ! return logical when reading namelist
260 LOGICAL :: gshadows
261 REAL, DIMENSION(:), ALLOCATABLE :: zsw ! total solar radiation (on horizontal surf.)
262 REAL, DIMENSION(:), ALLOCATABLE :: zcoef ! coefficient for solar radiation interpolation near sunset/sunrise
263 !
264 ! Flag diag :
265 !
266 INTEGER :: i2m, ibeq, idsteq
267 LOGICAL :: gfrac, gdiag_grid, gsurf_budget, grad_budget, gcoef, &
268  gsurf_vars, gdiag_ocean, gdiag_seaice, gwater_profile, &
269  ginterpol_ts, gsurf_evap_budget, gflood, gpgd_isba, &
270  gch_no_flux_isba, gsurf_misc_budget_isba, gpgd_teb, &
271  gsurf_misc_budget_teb
272 !
273 ! Inquiry mode arrays:
274 !
275 REAL, DIMENSION(:), ALLOCATABLE :: zsea, zwater, znature, ztown
276 REAL, DIMENSION(:), ALLOCATABLE :: zsea_full, zwater_full, znature_full, ztown_full
277 REAL, DIMENSION(:), ALLOCATABLE :: zt2m, zq2m
278 REAL, DIMENSION(:), ALLOCATABLE :: zz0, zz0h, zqs
279 REAL, DIMENSION(:), ALLOCATABLE :: zqs_sea, zqs_water, zqs_nature, zqs_town
280 REAL, DIMENSION(:), ALLOCATABLE :: zpsng, zpsnv
281 REAL, DIMENSION(:), ALLOCATABLE :: zz0eff
282 REAL, DIMENSION(:), ALLOCATABLE :: zzs
283 REAL, DIMENSION(:), ALLOCATABLE :: zz0_full, zz0eff_full, zzs_full
284 INTEGER :: iseries, isize
285 !
286 ! MPI variables
287 !
288  CHARACTER(LEN=100) :: yname
289  CHARACTER(LEN=10) :: yrank
290 INTEGER :: ilevel, infompi, j, inkproma, jblock
291 INTEGER, DIMENSION(:), ALLOCATABLE :: isize_omp
292 REAL :: xtime0, xtime1, xtime
293 !
294 ! SFX - OASIS coupling variables
295 !
296 INTEGER :: ilocal_comm ! Local communicator
297 !
298 REAL(KIND=JPRB) :: zhook_handle
299 !
300 ! --------------------------------------------------------------------------------------
301 !
302 !* 0.1. MPI, OASIS, and dr_hook initializations
303 !
304 infompi=1
305 !
306 #ifdef CPLOASIS
307 !Must be call before DRHOOK !
308  CALL sfx_oasis_init(cnamelist,ilocal_comm)
309 #else
310 loasis = .false.
311 xruntime = 0.0
312 #endif
313 !
314 #ifdef SFX_MPI
315 IF(.NOT.loasis)THEN
316  CALL mpi_init_thread(mpi_thread_multiple,ilevel,infompi)
317  IF (infompi /= mpi_success) THEN
318  CALL abor1_sfx('OFFLINE: ERROR WHEN INITIALIZING MPI')
319  ENDIF
320 ENDIF
321 #endif
322 !
323 IF (lhook) CALL dr_hook('OFFLINE',0,zhook_handle)
324 !
325  csoftware='OFFLINE'
326 !
327 #ifdef SFX_MPI
328 IF(loasis)THEN
329  ncomm=ilocal_comm
330 ELSE
331  ncomm=mpi_comm_world
332 ENDIF
333  CALL mpi_comm_size(ncomm,nproc,infompi)
334  CALL mpi_comm_rank(ncomm,nrank,infompi)
335 #endif
336 !
337 !RJ: init modd_surefx_omp
338 !$OMP PARALLEL
339 !$ NBLOCKTOT = OMP_GET_NUM_THREADS()
340 !$ NBLOCK = OMP_GET_THREAD_NUM()
341 !$OMP END PARALLEL
342 !
343  CALL prep_log_mpi
344 !
345  CALL wlog_mpi(' ')
346 !
347  CALL wlog_mpi('NBLOCKTOT ',klog=nblocktot)
348 !
349 #ifdef SFX_MPI
350 xtime0 = mpi_wtime()
351 #endif
352 !
353 !
354 !* 0.3. Open ascii file for writing
355 !
356 WRITE(yrank,fmt='(I10)') nrank
357 yname=trim(yluout)//adjustl(yrank)
358 !
359  cluout_lfi = adjustl(adjustr(yname)//'.txt')
360  cluout_nc = adjustl(adjustr(yname)//'.txt')
361 !
362  CALL get_luout('ASCII ',iluout)
363 OPEN(unit=iluout,file=adjustl(adjustr(yname)//'.txt'),form='FORMATTED',action='WRITE')
364 !
365 !
366 IF ( nrank==npio ) THEN
367  !
368 !$OMP SINGLE
369  !
370 !RJ: be verbose just for openmp
371  IF(nblocktot==1) THEN
372 !$ WRITE(*,*) "CAUTION: DID YOU THINK TO SET OMP_NUM_THREADS=1?"
373 !$ WRITE(*,*) "PLEASE VERIFY OMP_NUM_THREADS IS INITIALIZED : TYPE ECHO $OMP_NUM_THREADS IN A TERMINAL"
374  !
375 !$ WRITE(ILUOUT,*) "CAUTION: DID YOU THINK TO SET OMP_NUM_THREADS=1?"
376 !$ WRITE(ILUOUT,*) "PLEASE VERIFY OMP_NUM_THREADS IS INITIALIZED : TYPE ECHO $OMP_NUM_THREADS IN A TERMINAL"
377  ENDIF
378  !
379 !$OMP END SINGLE
380  !
381 ENDIF
382 !
383 !* 0.4. Reads namelists
384 !
385  CALL open_namelist('ASCII ',ilunam,cnamelist)
386 !
387  CALL posnam(ilunam,'NAM_IO_OFFLINE',gfound,iluout)
388 IF (gfound) READ (unit=ilunam,nml=nam_io_offline)
389  CALL close_namelist('ASCII ',ilunam)
390 !
391 IF (nproc==1) THEN
392  xio_frac=1.
393 ELSE
394  xio_frac = max(min(xio_frac,1.),0.)
395 ENDIF
396 !
397  CALL test_nam_var_surf(iluout,'CSURF_FILETYPE',csurf_filetype,'ASCII ','LFI ','FA ','NC ')
398  CALL test_nam_var_surf(iluout,'CTIMESERIES_FILETYPE',ctimeseries_filetype,'NETCDF','TEXTE ','BINARY',&
399  'ASCII ','LFI ','FA ',&
400  'NONE ','OFFLIN','NC ')
401  CALL test_nam_var_surf(iluout,'CFORCING_FILETYPE',cforcing_filetype,'NETCDF','ASCII ','BINARY')
402 !
403 IF (nscal>59) CALL abor1_sfx("OFFLINE: NSCAL MUST BE LOWER THAN OR EQUAL TO 59")
404 !
405 !
406 IF (ctimeseries_filetype=='NETCDF') ctimeseries_filetype='OFFLIN'
407 !
408 IF (nrank==npio) THEN
409  !
410  cfilepgd = adjustl(adjustr(cpgdfile)//'.txt')
411  cfilein = adjustl(adjustr(cprepfile)//'.txt')
412  cfilein_save = cfilein
413  !
414  cfilepgd_lfi = cpgdfile
415  cfilein_lfi = cprepfile
416  cfilein_lfi_save = cfilein_lfi
417  !
418  cfilepgd_fa = adjustl(adjustr(cpgdfile)//'.fa')
419  cfilein_fa = adjustl(adjustr(cprepfile)//'.fa')
420  cfilein_fa_save = cfilein_fa
421  !
422  cfilepgd_nc = adjustl(adjustr(cpgdfile)//'.nc')
423  cfilein_nc = adjustl(adjustr(cprepfile)//'.nc')
424  cfilein_nc_save = cfilein_nc
425  !
426 ENDIF
427 !
428 ! Allocations of Surfex Types
429  CALL surfex_alloc_list(1)
430  ysurf_cur => ysurf_list(1)
431 !
432 ! Reading all namelist (also assimilation)
433  CALL read_all_namelists(ysurf_cur, &
434  csurf_filetype,'ALL',.false.)
435 !
436 !
437 !* 0.5. Reads SFX - OASIS coupling namelists
438 !
439  CALL sfx_oasis_read_nam(csurf_filetype,xtstep_surf)
440 !
441 !* 0.6 Assume FA filetype consistency
442 !
443  cprogname = csurf_filetype
444 !
445 ! --------------------------------------------------------------------------------------
446 !
447 !* 1. Initializations
448 !
449 ! netcdf file handling
450 !
451 IF (nrank==npio) THEN
452  !
453  xstart = nundef
454  xstride = nundef
455  xcount = nundef
456  xstartw = 0
457  xcountw = 1
458  lpartw = .true.
459  ldefined_surf_atm = .false.
460  ldefined_nature = .false.
461  ldefined_town = .false.
462  ldefined_water = .false.
463  ldefined_sea = .false.
464  !
465 ENDIF
466 !
467 #ifdef SFX_MPI
468 xtime = (mpi_wtime() - xtime0)
469 #endif
470  CALL wlog_mpi('READ NAMELISTS ',plog=xtime)
471 #ifdef SFX_MPI
472 xtime0 = mpi_wtime()
473 #endif
474 !
475 ! forcing file handling
476 !
477 IF (cforcing_filetype=='ASCII ' .OR. cforcing_filetype=='BINARY') CALL open_close_bin_asc_forc('CONF ',cforcing_filetype,'R')
478 IF (cforcing_filetype=='NETCDF') CALL open_filein_ol
479 !
480 !
481 ! splitting of the grid
482 !
483 gshadows = lshadows_slope .OR. lshadows_other
484  CALL init_index_mpi(ysurf_cur, &
485  csurf_filetype, yalg_mpi, xio_frac, gshadows)
486 !
487  CALL wlog_mpi(' ')
488  CALL wlog_mpi('TIME_NPIO_READ init_index ',plog=xtime_npio_read)
489  CALL wlog_mpi('TIME_COMM_READ init_index ',plog=xtime_comm_read)
490 xtime_npio_read = 0.
491 xtime_comm_read = 0.
492 !
493 #ifdef SFX_MPI
494 xtime = (mpi_wtime() - xtime0)
495 #endif
496  CALL wlog_mpi(' ')
497  CALL wlog_mpi('INIT_INDEX_MPI ',plog=xtime)
498  CALL wlog_mpi(' ')
499 #ifdef SFX_MPI
500 xtime0 = mpi_wtime()
501 #endif
502 !
503 ! configuration of run
504 !
505  CALL ol_read_atm_conf(ysurf_cur, &
506  csurf_filetype, cforcing_filetype, &
507  zduration, ztstep, ini, iyear, imonth, iday, &
508  ztime, zlat, zlon, zzs_forc, zzref, zuref )
509 !
510  CALL wlog_mpi(' ')
511  CALL wlog_mpi('TIME_NPIO_READ forc conf ',plog=xtime_npio_read)
512  CALL wlog_mpi('TIME_COMM_READ forc conf ',plog=xtime_comm_read)
513 xtime_npio_read = 0.
514 xtime_comm_read = 0.
515 !
516 #ifdef SFX_MPI
517 xtime = (mpi_wtime() - xtime0)
518 #endif
519  CALL wlog_mpi('OL_READ_ATM_CONF ',plog=xtime)
520  CALL wlog_mpi(' ')
521 #ifdef SFX_MPI
522 xtime0 = mpi_wtime()
523 #endif
524 !
525 !* time steps coherence check
526 !
527 IF ( (mod(xtstep_output,ztstep)*mod(ztstep,xtstep_output) /= 0) .OR. (mod(ztstep,xtstep_surf) /= 0) ) THEN
528  WRITE(iluout,*)' FORCING AND OUTPUT/SURFACE TIME STEP SHOULD BE MULTIPLE', &
529  nint(ztstep),nint(xtstep_output),nint(xtstep_surf)
530  CALL abor1_sfx('OFFLINE: FORCING AND OUTPUT/SURFACE TIME STEP SHOULD BE MULTIPLE')
531 ENDIF
532 !
533 IF ( ztime /= 0. .AND. mod(ztime,xtstep_surf) /= 0 ) THEN
534  WRITE(iluout,*)' INITIAL AND SURFACE TIME STEP SHOULD BE MULTIPLE', &
535  nint(ztime),nint(xtstep_surf)
536  CALL abor1_sfx('OFFLINE: INITIAL AND SURFACE TIME STEP SHOULD BE MULTIPLE')
537 ENDIF
538 !
539 IF(loasis.AND.zduration/=xruntime)THEN
540  WRITE(iluout,*)'Total simulated time given by Forcing field and OASIS namcouple are different'
541  WRITE(iluout,*)'From Forcing (s) : ',zduration, 'From OASIS (s) : ',xruntime
542  CALL abor1_sfx('OFFLINE: TOTAL SIMULATED TIME DIFFERENT BETWEEN FORCING AND OASIS')
543 ENDIF
544 !
545 inb_step_atm = int(zduration / ztstep)
546 inb_atm = int(ztstep / xtstep_surf)
547 nstep_output = int(zduration / xtstep_output)
548 !
549 xtopd_step = 0
550 nnb_topd_step = 0
551 ntopd_step = 0
552 IF ( lcoupl_topd ) THEN
553  !
554  xtopd_step = float(nnb_topd)* xtstep_surf
555  nnb_topd_step = int( zduration / xtopd_step )
556  !
557  IF ( nnb_stp_restart==0 .AND. .NOT.lrestart ) nnb_stp_restart = -1
558  !
559  ntopd_step = 1
560  !
561 ENDIF
562 !
563 ! allocation of variables
564 !
565 ibands = 1
566 !
567  CALL ol_alloc_atm(ini,ibands,nscal)
568 !
569 xzs = zzs_forc
570 xzref = zzref
571 xuref = zuref
572 !
573 ! compare orography
574 !
575  CALL compare_orography(ysurf_cur, &
576  csurf_filetype, lset_forc_zs, xdelta_orog)
577 !
578 ! miscellaneous initialization
579 !
580 icount = 0
581 ztimec = 0.
582 !
583 ALLOCATE(isize_omp(0:nblocktot-1))
584  CALL get_sizes_parallel(ysurf_cur%DTCO, ysurf_cur%DGU, ysurf_cur%UG, ysurf_cur%U, &
585  nblocktot,ini,0,isize_omp, gshadows)
586  CALL sunpos(isize_omp, iyear, imonth, iday, ztime, zlon, zlat, xtsun, xzenith, xazim)
587 DEALLOCATE(isize_omp)
588 !
589 !number of lines read in forcing files
590 inb_lines=1
591 IF (nb_read_forc.EQ.1) THEN
592  inb_lines=inb_step_atm
593 ELSEIF (nb_read_forc.NE.0) THEN
594  !to be sure the number of readings will be NB_READ_FORC as a maximum
595  inb_lines=ceiling(1.*(inb_step_atm+1)/nb_read_forc)
596 ENDIF
597 !number of lines to be read effectively
598 idmax=inb_lines+1
599 !effective number of readings of the forcing files
600 nb_read_forc=ceiling(1.*(inb_step_atm+1)/inb_lines)
601 !
602 ! open Gelato specific diagnostic files (if requested by
603 ! Gelato wizzard user)
604 !
605 #if ! defined in_arpege
606  CALL opndia()
607 #endif
608 !
609 ! allocate local atmospheric variables
610 !
611 IF (.NOT.ALLOCATED(zta)) ALLOCATE(zta(ini,inb_lines+1))
612 IF (.NOT.ALLOCATED(zqa))ALLOCATE(zqa(ini,inb_lines+1))
613 IF (.NOT.ALLOCATED(zwind))ALLOCATE(zwind(ini,inb_lines+1))
614 IF (.NOT.ALLOCATED(zdir_sw))ALLOCATE(zdir_sw(ini,inb_lines+1))
615 IF (.NOT.ALLOCATED(zsca_sw))ALLOCATE(zsca_sw(ini,inb_lines+1))
616 IF (.NOT.ALLOCATED(zlw))ALLOCATE(zlw(ini,inb_lines+1))
617 IF (.NOT.ALLOCATED(zsnow))ALLOCATE(zsnow(ini,inb_lines+1))
618 IF (.NOT.ALLOCATED(zrain))ALLOCATE(zrain(ini,inb_lines+1))
619 IF (.NOT.ALLOCATED(zps))ALLOCATE(zps(ini,inb_lines+1))
620 IF (.NOT.ALLOCATED(zco2))ALLOCATE(zco2(ini,inb_lines+1))
621 IF (.NOT.ALLOCATED(zdir))ALLOCATE(zdir(ini,inb_lines+1))
622 IF (.NOT.ALLOCATED(zcoef))ALLOCATE(zcoef(ini))
623 !
624 IF (.NOT.ALLOCATED(zsw))ALLOCATE(zsw(ini))
625 !
626 ! computes initial air co2 concentration and density
627 !
628 #ifdef SFX_MPI
629 xtime = (mpi_wtime() - xtime0)
630 #endif
631  CALL wlog_mpi('COMPARE_OROGRAPHY SUNPOS ',plog=xtime)
632 #ifdef SFX_MPI
633 xtime0 = mpi_wtime()
634 #endif
635 !
636 !* opens forcing files (if ASCII or BINARY)
637 !
638 IF (cforcing_filetype=='ASCII ' .OR. cforcing_filetype=='BINARY') CALL open_close_bin_asc_forc('OPEN ',cforcing_filetype,'R')
639 !
640  CALL ol_read_atm(&
641  csurf_filetype, cforcing_filetype, 1, &
642  zta,zqa,zwind,zdir_sw,zsca_sw,zlw,zsnow,zrain,zps,&
643  zco2,zdir,llimit_qair )
644 !
645  CALL wlog_mpi(' ')
646  CALL wlog_mpi('TIME_NPIO_READ forc ',plog=xtime_npio_read)
647  CALL wlog_mpi('TIME_COMM_READ forc ',plog=xtime_comm_read)
648 xtime_npio_read = 0.
649 xtime_comm_read = 0.
650 !
651 #ifdef SFX_MPI
652 xtime = (mpi_wtime() - xtime0)
653 #endif
654  CALL wlog_mpi(' ')
655  CALL wlog_mpi('OL_READ_ATM0 ',plog=xtime)
656  CALL wlog_mpi(' ')
657 #ifdef SFX_MPI
658 xtime0 = mpi_wtime()
659 #endif
660 !
661 xco2(:) = zco2(:,1)
662 xrhoa(:) = zps(:,1) / (xrd * zta(:,1) * ( 1.+((xrv/xrd)-1.)*zqa(:,1) ) + xg * xzref )
663 !
664 ! surface Initialisation
665 !
666 #ifdef SFX_MPI
667 xtime = (mpi_wtime() - xtime0)
668 #endif
669  CALL wlog_mpi('CO2 RHOA ',plog=xtime)
670 !
671  CALL io_buff_clean
672 !
673  CALL surfex_deallo_list
674  CALL surfex_alloc_list(nblocktot)
675 !
676  CALL goto_model(1)
677 ALLOCATE(isize_omp(0:nblocktot-1))
678  CALL get_sizes_parallel(ysurf_cur%DTCO, ysurf_cur%DGU, ysurf_cur%UG, ysurf_cur%U, &
679  nblocktot,ini,0,isize_omp, gshadows)
680 DO j=0,nblocktot-1
681  CALL wlog_mpi("SIZES_OMP ",klog=j,klog2=isize_omp(j))
682 ENDDO
683 !
684 !$OMP PARALLEL PRIVATE(INKPROMA,XTIME,XTIME0)
685 !
686 #ifdef SFX_MPI
687 xtime0 = mpi_wtime()
688 #endif
689 !
690 !$ NBLOCK = OMP_GET_THREAD_NUM()
691 !
692 IF (nblock==nblocktot) THEN
693  CALL init_dim(isize_omp,0,inkproma,nindx1sfx,nindx2sfx)
694 ELSE
695  CALL init_dim(isize_omp,nblock,inkproma,nindx1sfx,nindx2sfx)
696 ENDIF
697 !
698 IF (nblock==0) THEN
699  CALL goto_model(nblocktot)
700 ELSE
701  CALL goto_model(nblock)
702 ENDIF
703 !
704  CALL init_surf_atm_n(ysurf_cur, &
705  csurf_filetype, yinit, lland_use, &
706  inkproma, nscal, ibands, &
707  csv,xco2(nindx1sfx:nindx2sfx),xrhoa(nindx1sfx:nindx2sfx), &
708  xzenith(nindx1sfx:nindx2sfx),xazim(nindx1sfx:nindx2sfx),xsw_bands, &
709  xdir_alb(nindx1sfx:nindx2sfx,:), xsca_alb(nindx1sfx:nindx2sfx,:), &
710  xemis(nindx1sfx:nindx2sfx), xtsrad(nindx1sfx:nindx2sfx), &
711  xtsurf(nindx1sfx:nindx2sfx), &
712  iyear, imonth, iday, ztime, &
713  yatmfile, yatmfiletype, ytest )
714 !
715 ! initialization routines to compute shadows
716 IF (gshadows) THEN
717  IF (nblock==0) THEN
718  CALL init_slope_param(ysurf_cur%UG, &
719  zzs_forc,ini,zlat)
720  END IF
721  !$OMP BARRIER
722  CALL local_slope_param(nindx1sfx,nindx2sfx)
723 END IF
724 !
725  CALL reset_dim(ini,inkproma,nindx1sfx,nindx2sfx)
726 !
727 #ifdef SFX_MPI
728 xtime = (mpi_wtime() - xtime0)
729 #endif
730  CALL wlog_mpi(' ')
731  CALL wlog_mpi('INIT_SURF_ATM ',plog=xtime)
732  CALL wlog_mpi(' ')
733 !
734  CALL wlog_mpi('TIME_NPIO_READ init ',plog=xtime_npio_read)
735  CALL wlog_mpi('TIME_COMM_READ init ',plog=xtime_comm_read)
736  CALL wlog_mpi(' ')
737 !
738 !$OMP END PARALLEL
739 !
740 xtime_npio_read = 0.
741 xtime_comm_read = 0.
742 !
743 ! Land use or/and vegetation dynamic
744 !
745  CALL init_surf_landuse_n(ysurf_cur, &
746  csurf_filetype,yinit,lland_use, &
747  ini, nscal, ibands, &
748  csv,xco2(nindx1sfx:nindx2sfx),xrhoa(nindx1sfx:nindx2sfx), &
749  xzenith(nindx1sfx:nindx2sfx),xazim(nindx1sfx:nindx2sfx), &
750  xsw_bands,xdir_alb(nindx1sfx:nindx2sfx,:), &
751  xsca_alb(nindx1sfx:nindx2sfx,:), &
752  xemis(nindx1sfx:nindx2sfx),xtsrad(nindx1sfx:nindx2sfx), &
753  xtsurf(nindx1sfx:nindx2sfx), &
754  iyear, imonth, iday, ztime, &
755  yatmfile, yatmfiletype, ytest )
756 !
757 #ifdef SFX_MPI
758 xtime0 = mpi_wtime()
759 #endif
760 !
761  CALL init_crodebug(ysurf_cur%IM%I)
762 !
763 ! * SURFEX - OASIS grid, partitions and local field definitions
764 !
765 IF(loasis)THEN
766  CALL sfx_oasis_def_ol(ysurf_cur%IM%I, &
767  ysurf_cur%U, &
768  csurf_filetype,yalg_mpi)
769 ENDIF
770 !
771 IF (ctimeseries_filetype=="OFFLIN") THEN
772  CALL goto_model(1)
773  CALL init_output_ol_n(ysurf_cur)
774 ENDIF
775 ! --------------------------------------------------------------------------------------
776 !
777 inw = 1
778 IF (ctimeseries_filetype=="NC ") inw = 2
779 !
780 nwrite = 0
781 !
782 #ifdef SFX_MPI
783 xtime = (mpi_wtime() - xtime0)
784 #endif
785  CALL wlog_mpi('INIT FINISHED ',plog=xtime)
786 #ifdef SFX_MPI
787 xtime0 = mpi_wtime()
788 #endif
789 !* 2. Temporal loops
790 !
791 xtime_calc(:) = 0.
792 xtime_write(:) = 0.
793 !
794 DO jforc_step=1,inb_step_atm
795  !
796 #ifdef SFX_MPI
797  xtime1 = mpi_wtime()
798 #endif
799  ! read Forcing
800  !
801  !indice of forcing line in forcing arrays
802  id_forc=jforc_step-int(jforc_step/inb_lines)*inb_lines
803  IF (id_forc==0) id_forc=inb_lines
804  !new forcings to read
805  IF (id_forc==1 .AND. jforc_step.NE.1) THEN
806  !if last part of forcing, the last point has to be adjusted on the end of
807  !files
808  IF (jforc_step/inb_lines==nb_read_forc-1) THEN
809  idmax=inb_step_atm-jforc_step+1+1
810  !for ascii and binary forcing files
811  zta(:,idmax)=zta(:,SIZE(zta,2))
812  zqa(:,idmax)=zqa(:,SIZE(zta,2))
813  zwind(:,idmax)=zwind(:,SIZE(zta,2))
814  zdir_sw(:,idmax)=zdir_sw(:,SIZE(zta,2))
815  zsca_sw(:,idmax)=zsca_sw(:,SIZE(zta,2))
816  zlw(:,idmax)=zlw(:,SIZE(zta,2))
817  zsnow(:,idmax)=zsnow(:,SIZE(zta,2))
818  zrain(:,idmax)=zrain(:,SIZE(zta,2))
819  zps(:,idmax)=zps(:,SIZE(zta,2))
820  zco2(:,idmax)=zco2(:,SIZE(zta,2))
821  zdir(:,idmax)=zdir(:,SIZE(zta,2))
822  ENDIF
823  CALL ol_read_atm(&
824  csurf_filetype, cforcing_filetype, jforc_step, &
825  zta(:,1:idmax),zqa(:,1:idmax),zwind(:,1:idmax), &
826  zdir_sw(:,1:idmax),zsca_sw(:,1:idmax),zlw(:,1:idmax), &
827  zsnow(:,1:idmax),zrain(:,1:idmax),zps(:,1:idmax),&
828  zco2(:,1:idmax),zdir(:,1:idmax),llimit_qair )
829  ENDIF
830 
831 #ifdef SFX_MPI
832  xtime_calc(1) = xtime_calc(1) + (mpi_wtime() - xtime1)
833  xtime1 = mpi_wtime()
834 #endif
835  !
836  DO jsurf_step=1,inb_atm
837  !
838  ! time interpolation of the forcing
839  !
840 #ifdef SFX_MPI
841  xtime1 = mpi_wtime()
842 #endif
843  CALL sunpos(isize_omp, iyear, imonth, iday, ztime, &
844  zlon, zlat, xtsun, xzenith, xazim)
845  CALL sunpos(isize_omp, iyear, imonth, iday, ztime+xtstep_surf, &
846  zlon, zlat, xtsun, xzenith2, xazim)
847 #ifdef SFX_MPI
848  xtime_calc(2) = xtime_calc(2) + (mpi_wtime() - xtime1)
849  xtime1 = mpi_wtime()
850 #endif
851  !interpolation between beginning and end of current forcing time step
852  CALL ol_time_interp_atm(jsurf_step,inb_atm,isize_omp, &
853  zta(:,id_forc),zta(:,id_forc+1), &
854  zqa(:,id_forc),zqa(:,id_forc+1), &
855  zwind(:,id_forc),zwind(:,id_forc+1), &
856  zdir_sw(:,id_forc),zdir_sw(:,id_forc+1), &
857  zsca_sw(:,id_forc),zsca_sw(:,id_forc+1), &
858  zlw(:,id_forc),zlw(:,id_forc+1), &
859  zsnow(:,id_forc+1),zrain(:,id_forc+1), &
860  zps(:,id_forc),zps(:,id_forc+1), &
861  zco2(:,id_forc), zco2(:,id_forc+1), &
862  zdir(:,id_forc) ,zdir(:,id_forc+1) )
863 #ifdef SFX_MPI
864  xtime_calc(3) = xtime_calc(3) + (mpi_wtime() - xtime1)
865  xtime1 = mpi_wtime()
866 #endif
867  !
868  IF(ladapt_sw)THEN
869  !
870  ! coherence between solar zenithal angle and radiation
871  ! when solar beam close to horizontal -> reduction of direct radiation to
872  ! the benefit of scattered radiation
873  ! when pi/2 - 0.1 < ZENITH < pi/2 - 0.05 => weight of direct to scattered radiation decreases linearly with zenith
874  ! when pi/2 - 0.05 < ZENITH => all the direct radiation is converted to scattered radiation
875  ! coherence between solar zenithal angle and radiation
876  !
877  zcoef(:) = (xpi/2. - xzenith(:) - 0.05) / 0.05
878  zcoef(:) = max(min(zcoef,1.),0.)
879  DO jloop=1,SIZE(xdir_sw,2)
880  xsca_sw(:,jloop) = xsca_sw(:,jloop) + xdir_sw(:,jloop) * (1 - zcoef)
881  xdir_sw(:,jloop) = xdir_sw(:,jloop) * zcoef(:)
882  ENDDO
883  !
884  ELSE
885  !
886  zsw(:) = 0.
887  DO jloop=1,SIZE(xdir_sw,2)
888  zsw(:) = zsw(:) + xdir_sw(:,jloop) + xsca_sw(:,jloop)
889  END DO
890  WHERE (zsw(:)>0.)
891  xzenith = min(xzenith ,xpi/2.-0.01)
892  xzenith2 = min(xzenith2,xpi/2.-0.01)
893  ELSEWHERE
894  xzenith = max(xzenith ,xpi/2.)
895  xzenith2 = max(xzenith2,xpi/2.)
896  END WHERE
897  !
898  ENDIF
899  !
900  ! updates time
901  ztimec= ztimec+xtstep_surf
902  IF (lcoupl_topd) ltopd_step = ( mod((((jforc_step-1)*inb_atm)+jsurf_step),nnb_topd) == 0 )
903  !
904  ! run Surface
905  !
906 #ifdef SFX_MPI
907  xtime_calc(4) = xtime_calc(4) + (mpi_wtime() - xtime1)
908 #endif
909  !
910  CALL io_buff_clean
911  !
912  IF(loasis)THEN
913  ! Receive fields to other models proc by proc
914  CALL sfx_oasis_recv_ol(ysurf_cur%FM%F, ysurf_cur%IM%I, ysurf_cur%SM%S, ysurf_cur%U, ysurf_cur%WM%W, &
915  csurf_filetype,ini,ibands,ztimec, &
916  xtstep_surf,isize_omp,xzenith,xsw_bands,&
917  xtsrad,xdir_alb,xsca_alb,xemis,xtsurf )
918  ENDIF
919  !
920 !$OMP PARALLEL PRIVATE(INKPROMA,XTIME1)
921  !
922 #ifdef SFX_MPI
923  xtime1 = mpi_wtime()
924 #endif
925  !
926 !$ NBLOCK = OMP_GET_THREAD_NUM()
927  !
928  IF (nblock==nblocktot) THEN
929  CALL init_dim(isize_omp,0,inkproma,nindx1sfx,nindx2sfx)
930  ELSE
931  CALL init_dim(isize_omp,nblock,inkproma,nindx1sfx,nindx2sfx)
932  ENDIF
933  !
934  IF (nblock==0) THEN
935  CALL goto_model(nblocktot)
936  ELSE
937  CALL goto_model(nblock)
938  ENDIF
939  !
940  IF(gshadows) THEN
941  CALL slope_radiative_effect(xtstep_surf,xzenith(nindx1sfx:nindx2sfx),&
942  xazim(nindx1sfx:nindx2sfx),xps(nindx1sfx:nindx2sfx),xta(nindx1sfx:nindx2sfx),&
943  xrain(nindx1sfx:nindx2sfx),xdir_sw(nindx1sfx:nindx2sfx,:),xlw(nindx1sfx:nindx2sfx),&
944  xzs_thread,xzs_xy_thread, xslopang_thread,xslopazi_thread,xsurf_triangle_thread)
945  END IF
946  !
947  CALL coupling_surf_atm_n(ysurf_cur, &
948  csurf_filetype, 'E', ztimec, &
949  xtstep_surf, iyear, imonth, iday, ztime, inkproma, nscal, ibands, &
950  xtsun(nindx1sfx:nindx2sfx), xzenith(nindx1sfx:nindx2sfx), &
951  xzenith2(nindx1sfx:nindx2sfx), xazim(nindx1sfx:nindx2sfx), &
952  xzref(nindx1sfx:nindx2sfx), xuref(nindx1sfx:nindx2sfx), &
953  xzs(nindx1sfx:nindx2sfx), xu(nindx1sfx:nindx2sfx), &
954  xv(nindx1sfx:nindx2sfx), xqa(nindx1sfx:nindx2sfx), &
955  xta(nindx1sfx:nindx2sfx), xrhoa(nindx1sfx:nindx2sfx), &
956  xsv(nindx1sfx:nindx2sfx,:), xco2(nindx1sfx:nindx2sfx), csv, &
957  xrain(nindx1sfx:nindx2sfx), xsnow(nindx1sfx:nindx2sfx), &
958  xlw(nindx1sfx:nindx2sfx), xdir_sw(nindx1sfx:nindx2sfx,:), &
959  xsca_sw(nindx1sfx:nindx2sfx,:), xsw_bands, xps(nindx1sfx:nindx2sfx),&
960  xpa(nindx1sfx:nindx2sfx), xsftq(nindx1sfx:nindx2sfx), &
961  xsfth(nindx1sfx:nindx2sfx), xsfts(nindx1sfx:nindx2sfx,:), &
962  xsfco2(nindx1sfx:nindx2sfx), xsfu(nindx1sfx:nindx2sfx), &
963  xsfv(nindx1sfx:nindx2sfx), xtsrad(nindx1sfx:nindx2sfx), &
964  xdir_alb(nindx1sfx:nindx2sfx,:), xsca_alb(nindx1sfx:nindx2sfx,:), &
965  xemis(nindx1sfx:nindx2sfx), &
966  xtsurf(nindx1sfx:nindx2sfx), xz0(nindx1sfx:nindx2sfx), &
967  xz0h(nindx1sfx:nindx2sfx), xqsurf(nindx1sfx:nindx2sfx), &
968  xpew_a_coef(nindx1sfx:nindx2sfx),xpew_b_coef(nindx1sfx:nindx2sfx),&
969  xpet_a_coef(nindx1sfx:nindx2sfx),xpeq_a_coef(nindx1sfx:nindx2sfx),&
970  xpet_b_coef(nindx1sfx:nindx2sfx),xpeq_b_coef(nindx1sfx:nindx2sfx),&
971  ytest )
972  !
973  CALL reset_dim(ini,inkproma,nindx1sfx,nindx2sfx)
974  !
975 #ifdef SFX_MPI
976  xtime_calc(5) = xtime_calc(5) + (mpi_wtime() - xtime1)
977 #endif
978  !
979 !$OMP END PARALLEL
980  !
981 #ifdef SFX_MPI
982  xtime1 = mpi_wtime()
983 #endif
984  !
985  IF(loasis)THEN
986  ! Send fields to other models proc by proc
987  CALL sfx_oasis_send_ol(ysurf_cur%FM%F, ysurf_cur%IM%I, ysurf_cur%SM%S, ysurf_cur%U, ysurf_cur%WM%W, &
988  csurf_filetype,ini,ztimec,xtstep_surf,isize_omp)
989  ENDIF
990  !
991  ztime = ztime + xtstep_surf
992  CALL add_forecast_to_date_surf(iyear, imonth, iday, ztime)
993 #ifdef SFX_MPI
994  xtime_calc(6) = xtime_calc(6) + (mpi_wtime() - xtime1)
995  !
996  xtime1 = mpi_wtime()
997 #endif
998  ! ecrit Surface
999  !
1000  IF ( lcoupl_topd .AND. ltopd_step ) THEN
1001  !
1002  IF (.NOT.ALLOCATED(nyear)) ALLOCATE(nyear(nnb_topd_step))
1003  IF (.NOT.ALLOCATED(nmonth)) ALLOCATE(nmonth(nnb_topd_step))
1004  IF (.NOT.ALLOCATED(nday)) ALLOCATE(nday(nnb_topd_step))
1005  IF (.NOT.ALLOCATED(nh)) ALLOCATE(nh(nnb_topd_step))
1006  IF (.NOT.ALLOCATED(nm)) ALLOCATE(nm(nnb_topd_step))
1007  !
1008  nyear(ntopd_step) = iyear
1009  nmonth(ntopd_step) = imonth
1010  nday(ntopd_step) = iday
1011  nh(ntopd_step) = int(ztime/3600.)
1012  nm(ntopd_step) = int((ztime-nh(ntopd_step)*3600.)/60.)
1013  !
1014  IF ( nm(ntopd_step)==60 ) THEN
1015  !
1016  nm(ntopd_step) = 0
1017  nh(ntopd_step) = nh(ntopd_step)+1
1018  !
1019  ENDIF
1020  !
1021  IF ( nh(ntopd_step)==24 ) THEN
1022  !
1023  nh(ntopd_step) = 0
1024  nday(ntopd_step) = nday(ntopd_step)+1
1025  !
1026  !!AJOUT BEC
1027  SELECT CASE (nmonth(ntopd_step))
1028  CASE(4,6,9,11)
1029  IF ( nday(ntopd_step)==31 ) THEN
1030  nmonth(ntopd_step) = nmonth(ntopd_step)+1
1031  nday(ntopd_step) = 1
1032  ENDIF
1033  CASE(1,3,5,7:8,10)
1034  IF ( nday(ntopd_step)==32 ) THEN
1035  nmonth(ntopd_step) = nmonth(ntopd_step)+1
1036  nday(ntopd_step) = 1
1037  ENDIF
1038  CASE(12)
1039  IF ( nday(ntopd_step)==32 ) THEN
1040  nyear(ntopd_step) = nyear(ntopd_step)+1
1041  nmonth(ntopd_step) = 1
1042  nday(ntopd_step) = 1
1043  ENDIF
1044  CASE(2)
1045  IF( mod(nyear(ntopd_step),4)==0 .AND. mod(nyear(ntopd_step),100)/=0 .OR. mod(nyear(ntopd_step),400)==0 ) THEN
1046  IF (nday(ntopd_step)==30) THEN
1047  nmonth(ntopd_step) = nmonth(ntopd_step)+1
1048  nday(ntopd_step) = 1
1049  ENDIF
1050  ELSE
1051  IF (nday(ntopd_step)==29) THEN
1052  nmonth(ntopd_step) = nmonth(ntopd_step)+1
1053  nday(ntopd_step) = 1
1054  ENDIF
1055  ENDIF
1056  END SELECT
1057  !
1058  ENDIF
1059  !
1060  ! * 2. Stocking date of each time step
1061  !
1062  ntopd_step = ntopd_step + 1
1063  !
1064  ENDIF
1065  !
1066  IF (mod(ztimec,xtstep_output) == 0. .AND. ctimeseries_filetype/='NONE ') THEN
1067  !
1068  IF (nrank==npio) THEN
1069  !
1070  !* name of the file
1071  IF (ctimeseries_filetype=="ASCII " .OR. &
1072  ctimeseries_filetype=="LFI " .OR. &
1073  ctimeseries_filetype=="FA " .OR. &
1074  ctimeseries_filetype=="NC " ) THEN
1075  !
1076  !
1077  ztime_out = ztime
1078  iday_out = iday
1079  imonth_out = imonth
1080  iyear_out = iyear
1081  !
1082  IF(lout_timename)THEN
1083  ! if true, change the name of output file at the end of a day
1084  ! (ex: 19860502_00h00 -> 19860501_24h00)
1085  IF(ztime==0.0)THEN
1086  ztime_out = 86400.
1087  iday_out = iday-1
1088  IF(iday_out==0)THEN
1089  imonth_out = imonth - 1
1090  IF(imonth_out==0)THEN
1091  imonth_out=12
1092  iyear_out = iyear - 1
1093  ENDIF
1094  SELECT CASE (imonth_out)
1095  CASE(4,6,9,11)
1096  iday_out=30
1097  CASE(1,3,5,7:8,10,12)
1098  iday_out=31
1099  CASE(2)
1100  IF( ((mod(iyear_out,4)==0).AND.(mod(iyear_out,100)/=0)) .OR. (mod(iyear_out,400)==0))THEN
1101  iday_out=29
1102  ELSE
1103  iday_out=28
1104  ENDIF
1105  END SELECT
1106  ENDIF
1107  ENDIF
1108  !
1109  ENDIF
1110  !
1111  WRITE(ytag,fmt='(I4.4,I2.2,I2.2,A1,I2.2,A1,I2.2)') iyear_out,imonth_out,iday_out,&
1112  '_',int(ztime_out/3600.),'h',nint(ztime_out)/60-60*int(ztime_out/3600.)
1113  cfileout = adjustl(adjustr(csurffile)//'.'//ytag//'.txt')
1114  cfileout_lfi= adjustl(adjustr(csurffile)//'.'//ytag)
1115  cfileout_fa = adjustl(adjustr(csurffile)//'.'//ytag//'.fa')
1116  cfileout_nc = adjustl(adjustr(csurffile)//'.'//ytag//'.nc')
1117  !
1118  IF (ctimeseries_filetype=='FA ') THEN
1119 #ifdef SFX_FA
1120  lfanocompact = ldiag_fa_nocompact
1121  idatef(1)= iyear!_OUT
1122  idatef(2)= imonth!_OUT
1123  idatef(3)= iday!_OUT
1124  !ZTIME instead of ZTIME_OUT (FA XRD39 do not like 24h)
1125  idatef(4)= floor(ztime/3600.)
1126  idatef(5)= floor(ztime/60.) - idatef(4) * 60
1127  idatef(6)= nint(ztime) - idatef(4) * 3600 - idatef(5) * 60
1128  idatef(7:11) = 0
1129  IF (csurf_filetype/='FA ') THEN
1130  CALL write_header_fa(ysurf_cur%UG, &
1131  csurf_filetype,'ALL')
1132  ELSE
1133  CALL faitou(iret,nunit_fa,.true.,cfileout_fa,'UNKNOWN',.true.,.false.,iverbfa,0,inb,cdnomc)
1134  ENDIF
1135  CALL fandar(iret,nunit_fa,idatef)
1136 #endif
1137  END IF
1138  !
1139  END IF
1140  !
1141  xstartw = xstartw + 1
1142  nwrite = nwrite + 1
1143  ltime_written(:)=.false.
1144  !
1145  ENDIF
1146  !
1147 #ifdef SFX_MPI
1148  xtime_write(1) = xtime_write(1) + (mpi_wtime() - xtime1)
1149 #endif
1150  !
1151  ldef = .true.
1152  !
1153  IF (ctimeseries_filetype=="NC ") THEN
1154  CALL goto_model(1)
1155  CALL init_output_nc_n(ysurf_cur%TM%BDD, ysurf_cur%CHE, ysurf_cur%CHN, ysurf_cur%CHU, &
1156  ysurf_cur%SM%DTS, ysurf_cur%TM%DTT, ysurf_cur%DTZ, ysurf_cur%IM%I, &
1157  ysurf_cur%UG, ysurf_cur%U, ysurf_cur%DGU)
1158  ENDIF
1159  !
1160  idx_w = 0
1161  !
1162  DO jnw = 1,inw
1163  !
1164  CALL io_buff_clean
1165  !
1166 !$OMP PARALLEL PRIVATE(INKPROMA,XTIME1)
1167  !
1168 !$ NBLOCK = OMP_GET_THREAD_NUM()
1169  !
1170  IF (nblock==nblocktot) THEN
1171  CALL init_dim(isize_omp,0,inkproma,nindx1sfx,nindx2sfx)
1172  ELSE
1173  CALL init_dim(isize_omp,nblock,inkproma,nindx1sfx,nindx2sfx)
1174  ENDIF
1175  !
1176  IF (nblock==0) THEN
1177  CALL goto_model(nblocktot)
1178  ELSE
1179  CALL goto_model(nblock)
1180  ENDIF
1181  !
1182 #ifdef SFX_MPI
1183  xtime1 = mpi_wtime()
1184 #endif
1185  CALL write_surf_atm_n(ysurf_cur, &
1186  ctimeseries_filetype,'ALL',lland_use)
1187 #ifdef SFX_MPI
1188  xtime_write(2) = xtime_write(2) + (mpi_wtime() - xtime1)
1189  xtime1 = mpi_wtime()
1190 #endif
1191  CALL diag_surf_atm_n(ysurf_cur%IM%DGEI, ysurf_cur%FM%DGF, ysurf_cur%DGL, ysurf_cur%IM%DGI, &
1192  ysurf_cur%SM%DGS, ysurf_cur%DGU, ysurf_cur%TM%DGT, ysurf_cur%WM%DGW, &
1193  ysurf_cur%U, ysurf_cur%USS, &
1194  ctimeseries_filetype)
1195 #ifdef SFX_MPI
1196  xtime_write(3) = xtime_write(3) + (mpi_wtime() - xtime1)
1197  xtime1 = mpi_wtime()
1198 #endif
1199  CALL write_diag_surf_atm_n(ysurf_cur, &
1200  ctimeseries_filetype,'ALL')
1201 #ifdef SFX_MPI
1202  xtime_write(4) = xtime_write(4) + (mpi_wtime() - xtime1)
1203 #endif
1204  !
1205  CALL reset_dim(ini,inkproma,nindx1sfx,nindx2sfx)
1206  !
1207 !$OMP BARRIER
1208  !
1209 !$OMP END PARALLEL
1210  !
1211  ldef = .false.
1212  !
1213  ENDDO
1214  !
1215  IF (lcoupl_topd .AND. ntopd_step > nnb_topd_step) THEN
1216  !
1217  ! Writing of file resulting of coupling with TOPMODEL or routing ****
1218  CALL write_discharge_file(csurf_filetype,'q_total.txt','FORMATTED',&
1219  nyear,nmonth,nday,nh,nm,xqtot)
1220  CALL write_discharge_file(csurf_filetype,'q_runoff.txt','FORMATTED',&
1221  nyear,nmonth,nday,nh,nm,xqb_run)
1222  CALL write_discharge_file(csurf_filetype,'q_drainage.txt','FORMATTED',&
1223  nyear,nmonth,nday,nh,nm,xqb_dr)
1224  ! Writing of budget files
1225  IF (lbudget_topd) CALL write_budget_coupl_rout
1226  !
1227  ENDIF
1228  !
1229 #ifdef SFX_MPI
1230  xtime1 = mpi_wtime()
1231 #endif
1232  !
1233  IF (nrank==npio) THEN
1234  IF (ctimeseries_filetype=='FA ') THEN
1235 #ifdef SFX_FA
1236  CALL fairme(iret,nunit_fa,'UNKNOWN')
1237 #endif
1238  END IF
1239  !* add informations in the file
1240  IF (ctimeseries_filetype=='LFI ' .AND. lmnh_compatible) CALL write_header_mnh
1241  ENDIF
1242 #ifdef SFX_MPI
1243  xtime_write(5) = xtime_write(5) + (mpi_wtime() - xtime1)
1244 #endif
1245  !
1246  ENDIF
1247  !
1248  END DO
1249  !
1250 
1251  IF (nrank==npio) THEN
1252  IF (lprint) THEN
1253  IF (mod(ztimec,xday) == 0.) THEN
1254 !$OMP SINGLE
1255  icount = icount + 1
1256  CALL wlog_mpi('SFX DAY :',klog=icount,klog2=int(zduration/xday))
1257  WRITE(*,'(A10,I5,A2,I5)')'SFX DAY :',icount,' /',int(zduration/xday)
1258 !$OMP END SINGLE
1259  ENDIF
1260  ENDIF
1261  ENDIF
1262  !
1263 END DO
1264 !
1265 !$OMP PARALLEL PRIVATE(XTIME)
1266 !
1267 #ifdef SFX_MPI
1268 xtime = (mpi_wtime() - xtime0)
1269 #endif
1270 !
1271  CALL wlog_mpi(' ')
1272  CALL wlog_mpi('OL_READ_ATM ',plog=xtime_calc(1))
1273  CALL wlog_mpi('SUNPOS ',plog=xtime_calc(2))
1274  CALL wlog_mpi('OL_TIME_INTERP_ATM ',plog=xtime_calc(3))
1275  CALL wlog_mpi('')
1276  CALL wlog_mpi('ZENITH ',plog=xtime_calc(4))
1277  CALL wlog_mpi('')
1278  CALL wlog_mpi('COUPLING_SURF_ATM ',plog=xtime_calc(5))
1279  CALL wlog_mpi('')
1280  CALL wlog_mpi('ADD_FORECAST_TO_DATE_SURF ',plog=xtime_calc(6))
1281  CALL wlog_mpi('DEF_DATE ',plog=xtime_write(1))
1282  CALL wlog_mpi('')
1283  CALL wlog_mpi('WRITE_SURF_ATM ',plog=xtime_write(2))
1284  CALL wlog_mpi('DIAG_SURF_ATM ',plog=xtime_write(3))
1285  CALL wlog_mpi('WRITE_DIAG_SURF_ATM ',plog=xtime_write(4))
1286  CALL wlog_mpi('')
1287  CALL wlog_mpi('CLOSE FILES ',plog=xtime_write(5))
1288  CALL wlog_mpi('')
1289  CALL wlog_mpi('END LOOP ',plog=xtime)
1290  CALL wlog_mpi('')
1291  CALL wlog_mpi('TIME_NPIO_WRITE ',plog=xtime_npio_write)
1292  CALL wlog_mpi('TIME_COMM_WRITE ',plog=xtime_comm_write)
1293  CALL wlog_mpi('TIME_OMP_BARR ',plog=xtime_omp_barr)
1294  CALL wlog_mpi('TIME_CALC_WRITE ',plog=xtime_calc_write)
1295  CALL wlog_mpi('')
1296  CALL wlog_mpi('TIME_INIT_SEA ',plog=xtime_init_sea)
1297  CALL wlog_mpi('TIME_INIT_WATER ',plog=xtime_init_water)
1298  CALL wlog_mpi('TIME_INIT_NATURE ',plog=xtime_init_nature)
1299  CALL wlog_mpi('TIME_INIT_TOWN ',plog=xtime_init_town)
1300  CALL wlog_mpi('')
1301  CALL wlog_mpi('TIME_SEA ',plog=xtime_sea)
1302  CALL wlog_mpi('TIME_WATER ',plog=xtime_water)
1303  CALL wlog_mpi('TIME_NATURE ',plog=xtime_nature)
1304  CALL wlog_mpi('TIME_TOWN ',plog=xtime_town)
1305 !
1306 !$OMP END PARALLEL
1307 !
1308 !
1309 IF (cforcing_filetype=='ASCII ' .OR. cforcing_filetype=='BINARY') CALL open_close_bin_asc_forc('CLOSE',cforcing_filetype,'R')
1310 !
1311 IF (cforcing_filetype=='NETCDF') CALL close_filein_ol
1312 IF (ctimeseries_filetype=='OFFLIN') CALL close_fileout_ol
1313 !
1314 ! --------------------------------------------------------------------------------------
1315 !
1316 !* 3. write restart file
1317 ! ------------------
1318 !
1319 IF ( lrestart ) THEN
1320  !
1321  IF (nrank==npio) THEN
1322  !* name of the file
1323  cfileout = adjustl(adjustr(csurffile)//'.txt')
1324  cfileout_lfi= csurffile
1325  cfileout_fa = adjustl(adjustr(csurffile)//'.fa')
1326  cfileout_nc = adjustl(adjustr(csurffile)//'.nc')
1327 
1328  !* opens the file
1329  IF (csurf_filetype=='FA ') THEN
1330 #ifdef SFX_FA
1331  lfanocompact = .true.
1332  idatef(1)= iyear
1333  idatef(2)= imonth
1334  idatef(3)= iday
1335  idatef(4)= floor(ztime/3600.)
1336  idatef(5)= floor(ztime/60.) - idatef(4) * 60
1337  idatef(6)= nint(ztime) - idatef(4) * 3600 - idatef(5) * 60
1338  idatef(7:11) = 0
1339  CALL faitou(iret,nunit_fa,.true.,cfileout_fa,'UNKNOWN',.true.,.false.,iverbfa,0,inb,cdnomc)
1340  CALL fandar(iret,nunit_fa,idatef)
1341 #endif
1342  END IF
1343  !
1344  ENDIF
1345  !
1346  inw = 1
1347  IF (csurf_filetype=="NC ") inw = 2
1348  !
1349  ldef = .true.
1350  !
1351  IF (csurf_filetype=="NC ") THEN
1352  CALL goto_model(1)
1353  CALL init_output_nc_n(ysurf_cur%TM%BDD, ysurf_cur%CHE, ysurf_cur%CHN, ysurf_cur%CHU, &
1354  ysurf_cur%SM%DTS, ysurf_cur%TM%DTT, ysurf_cur%DTZ, ysurf_cur%IM%I, &
1355  ysurf_cur%UG, ysurf_cur%U, ysurf_cur%DGU)
1356  ENDIF
1357  !
1358  DO jnw = 1,inw
1359  !
1360  CALL io_buff_clean
1361  !
1362 !$OMP PARALLEL PRIVATE(INKPROMA,JNW)
1363  !
1364 !$ NBLOCK = OMP_GET_THREAD_NUM()
1365  !
1366  IF (nblock==nblocktot) THEN
1367  CALL init_dim(isize_omp,0,inkproma,nindx1sfx,nindx2sfx)
1368  ELSE
1369  CALL init_dim(isize_omp,nblock,inkproma,nindx1sfx,nindx2sfx)
1370  ENDIF
1371  !
1372  IF (nblock==0) THEN
1373  CALL goto_model(nblocktot)
1374  ELSE
1375  CALL goto_model(nblock)
1376  ENDIF
1377  !
1378  CALL flag_update(ysurf_cur%IM%DGI, ysurf_cur%DGU, &
1379  .false.,.true.,.false.,.false.)
1380  !
1381  IF (lrestart_2m) THEN
1382  i2m = 1
1383  gpgd_isba = .true.
1384  ELSE
1385  i2m = 0
1386  gpgd_isba = .false.
1387  ENDIF
1388  gfrac = .true.
1389  gdiag_grid = .true.
1390  gsurf_budget = .false.
1391  grad_budget = .false.
1392  gcoef = .false.
1393  gsurf_vars = .false.
1394  ibeq = 0
1395  idsteq = 0
1396  gdiag_ocean = .false.
1397  gdiag_seaice = .false.
1398  gwater_profile = .false.
1399  gsurf_evap_budget = .false.
1400  gflood = .false.
1401  gch_no_flux_isba = .false.
1402  gsurf_misc_budget_isba = .false.
1403  gpgd_teb = .false.
1404  gsurf_misc_budget_teb = .false.
1405  !
1406  CALL flag_diag_update(ysurf_cur%FM%CHF, ysurf_cur%IM%CHI, ysurf_cur%SM%CHS, ysurf_cur%TM%CHT, &
1407  ysurf_cur%WM%CHW, ysurf_cur%IM%DGEI, ysurf_cur%FM%DGF, ysurf_cur%IM%DGI, &
1408  ysurf_cur%FM%DGMF, ysurf_cur%IM%DGMI, ysurf_cur%TM%DGMTO, ysurf_cur%SM%DGO, &
1409  ysurf_cur%SM%DGS, ysurf_cur%SM%DGSI, ysurf_cur%DGU, ysurf_cur%TM%DGT, &
1410  ysurf_cur%WM%DGW, ysurf_cur%IM%I, ysurf_cur%U, &
1411  gfrac, gdiag_grid, i2m, gsurf_budget, grad_budget, gcoef, &
1412  gsurf_vars, ibeq, idsteq, gdiag_ocean, gdiag_seaice, &
1413  gwater_profile, &
1414  gsurf_evap_budget, gflood, gpgd_isba, gch_no_flux_isba, &
1415  gsurf_misc_budget_isba, gpgd_teb, gsurf_misc_budget_teb )
1416  !
1417  !* writes into the file
1418  CALL write_surf_atm_n(ysurf_cur, &
1419  csurf_filetype,'ALL',lland_use)
1420  IF(csurf_filetype/='FA ' .OR. lrestart_2m) THEN
1421  CALL write_diag_surf_atm_n(ysurf_cur, &
1422  csurf_filetype,'ALL')
1423  ENDIF
1424  !
1425  CALL reset_dim(ini,inkproma,nindx1sfx,nindx2sfx)
1426  !
1427 !$OMP END PARALLEL
1428  !
1429  ldef = .false.
1430  !
1431  ENDDO
1432  !
1433  !* closes the file
1434  IF (nrank==0 ) THEN
1435  IF (csurf_filetype=='FA ') THEN
1436 #ifdef SFX_FA
1437  CALL fairme(iret,nunit_fa,'UNKNOWN')
1438 #endif
1439  END IF
1440  !* add informations in the file
1441  IF (csurf_filetype=='LFI ' .AND. lmnh_compatible) CALL write_header_mnh
1442  !
1443  ENDIF
1444  !
1445  IF (lcoupl_topd .AND. ntopd_step > nnb_topd_step) CALL prep_restart_coupl_topd(ysurf_cur%UG, ysurf_cur%U, &
1446  csurf_filetype,ini)
1447  !
1448 END IF
1449 !
1450 ! --------------------------------------------------------------------------------------
1451 !
1452 !* 4. inquiry mode
1453 ! ------------
1454 !
1455 IF ( linquire ) THEN
1456  !
1457 !$OMP PARALLEL PRIVATE(ZSEA,ZWATER,ZNATURE,ZTOWN,ZT2M,ZQ2M,ZZ0,ZZ0H,ZQS_SEA, &
1458 !$OMP ZQS_WATER,ZQS_NATURE,ZQS_TOWN,ZQS,ZPSNG,ZPSNV,ZZ0EFF,ZZS ,&
1459 !$OMP INKPROMA,INI)
1460 !
1461 !$ NBLOCK = OMP_GET_THREAD_NUM()
1462 !
1463  IF (nblock==nblocktot) THEN
1464  CALL init_dim(isize_omp,0,inkproma,nindx1sfx,nindx2sfx)
1465  ELSE
1466  CALL init_dim(isize_omp,nblock,inkproma,nindx1sfx,nindx2sfx)
1467  ENDIF
1468  ini = nindx2sfx-nindx1sfx+1
1469  !
1470  ALLOCATE( zsea( ini ) )
1471  ALLOCATE( zwater( ini ) )
1472  ALLOCATE( znature( ini ) )
1473  ALLOCATE( ztown( ini ) )
1474  ALLOCATE( zt2m( ini ) )
1475  ALLOCATE( zq2m( ini ) )
1476  ALLOCATE( zz0( ini ) )
1477  ALLOCATE( zz0h( ini ) )
1478  ALLOCATE( zqs_sea( ini ) )
1479  ALLOCATE( zqs_water( ini ) )
1480  ALLOCATE( zqs_nature( ini ) )
1481  ALLOCATE( zqs_town( ini ) )
1482  ALLOCATE( zqs( ini ) )
1483  ALLOCATE( zpsng( ini ) )
1484  ALLOCATE( zpsnv( ini ) )
1485  ALLOCATE( zz0eff( ini ) )
1486  ALLOCATE( zzs( ini ) )
1487  !
1488  iseries = 0
1489  CALL get_surf_var_n(ysurf_cur%FM%DGF, ysurf_cur%IM%I, ysurf_cur%IM%DGI, ysurf_cur%IM%DGMI, &
1490  ysurf_cur%SM%DGS, ysurf_cur%DGU, ysurf_cur%TM%DGT, ysurf_cur%WM%DGW, &
1491  ysurf_cur%FM%F, ysurf_cur%UG, ysurf_cur%U, ysurf_cur%USS, &
1492  csurf_filetype,ini,iseries,psea=zsea,pwater=zwater,pnature=znature,ptown=ztown, &
1493  pt2m=zt2m,pq2m=zq2m,pqs=zqs,pz0=zz0,pz0h=zz0h,pz0eff=zz0eff,pqs_sea=zqs_sea, &
1494  pqs_water=zqs_water,pqs_nature=zqs_nature,pqs_town=zqs_town, &
1495  ppsng=zpsng,ppsnv=zpsnv,pzs=zzs )
1496  !
1497  isize = SIZE(nindex)
1498  IF (nrank==npio) THEN
1499 !$OMP SINGLE
1500  ALLOCATE(zsea_full(isize))
1501  ALLOCATE(zwater_full(isize))
1502  ALLOCATE(znature_full(isize))
1503  ALLOCATE(ztown_full(isize))
1504  ALLOCATE(zz0_full(isize))
1505  ALLOCATE(zz0eff_full(isize))
1506  ALLOCATE(zzs_full(isize))
1507 !$OMP END SINGLE
1508  ELSE
1509 !$OMP SINGLE
1510  ALLOCATE(zsea_full(0))
1511  ALLOCATE(zwater_full(0))
1512  ALLOCATE(znature_full(0))
1513  ALLOCATE(ztown_full(0))
1514  ALLOCATE(zz0_full(0))
1515  ALLOCATE(zz0eff_full(0))
1516  ALLOCATE(zzs_full(0))
1517 !$OMP END SINGLE
1518  ENDIF
1519  CALL gather_and_write_mpi(zsea,zsea_full)
1520  CALL gather_and_write_mpi(zwater,zwater_full)
1521  CALL gather_and_write_mpi(znature,znature_full)
1522  CALL gather_and_write_mpi(ztown,ztown_full)
1523  CALL gather_and_write_mpi(zz0,zz0_full)
1524  CALL gather_and_write_mpi(zz0eff,zz0eff_full)
1525  CALL gather_and_write_mpi(zzs,zzs_full)
1526 
1527  IF (nrank==npio) THEN
1528 !$OMP SINGLE
1529  WRITE(iluout,'(A32,I4,A3,I4)') ' GRID BOXES CONTAINING SEA : ',count( zsea_full(:) > 0. ),' / ',isize
1530  WRITE(iluout,'(A32,I4,A3,I4)') ' GRID BOXES CONTAINING WATER : ',count( zwater_full(:) > 0. ),' / ',isize
1531  WRITE(iluout,'(A32,I4,A3,I4)') ' GRID BOXES CONTAINING NATURE : ',count( znature_full(:) > 0. ),' / ',isize
1532  WRITE(iluout,'(A32,I4,A3,I4)') ' GRID BOXES CONTAINING TOWN : ',count( ztown_full(:) > 0. ),' / ',isize
1533  WRITE(iluout,*)'ZZ0 = ',zz0_full
1534  WRITE(iluout,*)'ZZ0EFF = ',zz0eff_full
1535  WRITE(iluout,*)'ZZS = ',zzs_full
1536  WRITE(iluout,*)'MINVAL(ZZS) = ',minval(zzs_full),' MAXVAL(ZZS) = ',maxval(zzs_full)
1537 !$OMP END SINGLE
1538  ENDIF
1539  !
1540  DEALLOCATE( zsea )
1541  DEALLOCATE( zwater )
1542  DEALLOCATE( znature )
1543  DEALLOCATE( ztown )
1544  DEALLOCATE( zt2m )
1545  DEALLOCATE( zq2m )
1546  DEALLOCATE( zz0 )
1547  DEALLOCATE( zz0h )
1548  DEALLOCATE( zqs_sea )
1549  DEALLOCATE( zqs_water )
1550  DEALLOCATE( zqs_nature )
1551  DEALLOCATE( zqs_town )
1552  DEALLOCATE( zqs )
1553  DEALLOCATE( zpsng )
1554  DEALLOCATE( zpsnv )
1555  DEALLOCATE( zz0eff )
1556  DEALLOCATE( zzs )
1557  !
1558  IF (nrank==npio) THEN
1559 !$OMP SINGLE
1560  DEALLOCATE(zsea_full )
1561  DEALLOCATE(zwater_full )
1562  DEALLOCATE(znature_full)
1563  DEALLOCATE(ztown_full )
1564  DEALLOCATE(zz0_full )
1565  DEALLOCATE(zz0eff_full )
1566  DEALLOCATE(zzs_full )
1567 !$OMP END SINGLE
1568  ENDIF
1569  !
1570 !$OMP END PARALLEL
1571  !
1572 ENDIF
1573 !
1574 ! --------------------------------------------------------------------------------------
1575 !
1576 ! 4' Close Gelato specific diagnostic
1577 #if ! defined in_arpege
1578  CALL clsdia()
1579 #endif
1580 !
1581 !
1582 !* 5. Close parallelized I/O
1583 ! ----------------------
1584 !
1585 IF (nrank==npio) THEN
1586  WRITE(iluout,*) ' '
1587  WRITE(iluout,*) ' --------------------------'
1588  WRITE(iluout,*) ' | OFFLINE ENDS CORRECTLY |'
1589  WRITE(iluout,*) ' --------------------------'
1590  WRITE(iluout,*) ' '
1591 !$OMP SINGLE
1592  CLOSE(iluout)
1593 !$OMP END SINGLE
1594  WRITE(*,*) ' '
1595  WRITE(*,*) ' --------------------------'
1596  WRITE(*,*) ' | OFFLINE ENDS CORRECTLY |'
1597  WRITE(*,*) ' --------------------------'
1598  WRITE(*,*) ' '
1599 ENDIF
1600 !
1601  CALL surfex_deallo_list
1602 !
1603 IF (ALLOCATED(nindex)) DEALLOCATE(nindex)
1604 IF (ALLOCATED(nsize_task)) DEALLOCATE(nsize_task)
1605 !
1606 IF (ASSOCIATED(nwork)) DEALLOCATE(nwork)
1607 IF (ASSOCIATED(xwork)) DEALLOCATE(xwork)
1608 IF (ASSOCIATED(nwork2)) DEALLOCATE(nwork2)
1609 IF (ASSOCIATED(xwork2)) DEALLOCATE(xwork2)
1610 IF (ASSOCIATED(xwork3)) DEALLOCATE(xwork3)
1611 IF (ASSOCIATED(nwork_full)) DEALLOCATE(nwork_full)
1612 IF (ASSOCIATED(xwork_full)) DEALLOCATE(xwork_full)
1613 IF (ASSOCIATED(nwork2_full)) DEALLOCATE(nwork2_full)
1614 IF (ASSOCIATED(xwork2_full)) DEALLOCATE(xwork2_full)
1615 !
1616  CALL end_log_mpi
1617 !
1618 IF (lhook) CALL dr_hook('OFFLINE',1,zhook_handle)
1619 !
1620 ! * MPI and OASIS must be finalized after the last DR_HOOK call
1621 !
1622 IF(loasis)THEN
1623  CALL sfx_oasis_end
1624 ELSE
1625 #ifdef SFX_MPI
1626  CALL mpi_finalize(infompi)
1627 #endif
1628 ENDIF
1629 !
1630 ! --------------------------------------------------------------------------------------
1631 !
1632 END PROGRAM offline
subroutine slope_radiative_effect(PTSTEP, PZENITH, PAZIM, PPS, PTA, PRAIN, PDIR_SW, PLW, PZS, PZS_XY, PSLOPANG, PSLOPAZI, PSURF_TRIANGLE)
subroutine init_output_nc_n(BDD, CHE, CHN, CHU, DTS, DTT, DTZ, I, UG, U, DGU)
subroutine write_header_mnh
subroutine ol_read_atm(HSURF_FILETYPE, HFORCING_FILETYPE, KFORC_STEP, PTA, PQA, PWIND, PDIR_SW, PSCA_SW, PLW, PSNOW, PRAIN, PPS, PCO2, PDIR, OLIMIT_QAIR)
Definition: ol_read_atm.F90:6
subroutine get_sizes_parallel(DTCO, DGU, UG, U, KPROC, KSIZE, KPROCMIN, KSIZE_TASK, OSHADOWS)
subroutine init_output_ol_n(YSC)
subroutine sfx_oasis_read_nam(HPROGRAM, PTSTEP_SURF, HINIT)
subroutine close_fileout_ol
subroutine write_budget_coupl_rout
subroutine get_surf_var_n(DGF, I, DGI, DGMI, DGS, DGU, DGT, DGW, F, UG, U, USS, HPROGRAM, KI, KS, PSEA, PWATER, PNATURE, PTOWN, PT2M, PQ2M, PQS, PZ0, PZ0H, PZ0EFF, PZ0_SEA, PZ0_WATER, PZ0_NATURE, PZ0_TOWN, PZ0H_SEA, PZ0H_WATER, PZ0H_NATURE, PZ0H_TOWN, PQS_SEA, PQS_WATER, PQS_NATURE, PQS_TOWN, PPSNG, PPSNV, PZS, PSERIES, PTWSNOW, PSSO_STDEV, PLON, PLAT, PBARE, PLAI_TREE, PH_TREE)
subroutine init_crodebug(I)
subroutine write_header_fa(UG, CFILETYPE, HWRITE)
subroutine sfx_oasis_recv_ol(F, I, S, U, W, HPROGRAM, KI, KSW, PTIMEC, PTSTEP_SURF, KSIZE_OMP, PZENITH, PSW_BANDS, PTSRAD, PDIR_ALB, PSCA_ALB, PEMIS, PTSURF)
subroutine io_buff_clean
program offline
Definition: offline.F90:6
subroutine prep_log_mpi
subroutine init_index_mpi(YSC, HPROGRAM, HALG, PIO_FRAC, OSHADOWS)
subroutine abor1_sfx(YTEXT)
Definition: abor1_sfx.F90:6
subroutine close_filein_ol
subroutine end_log_mpi
subroutine flag_update(DGI, DGU, ONOWRITE_CANOPY, OPGD, OPROVAR_TO_DIAG, OSELECT)
Definition: flag_update.F90:6
subroutine write_diag_surf_atm_n(YSC, HPROGRAM, HWRITE)
subroutine init_surf_atm_n(YSC, HPROGRAM, HINIT, OLAND_USE, KI, KSV, KSW, HSV, PCO2, PRHOA, PZENITH, PAZIM, PSW_BANDS, PDIR_ALB, PSCA_ALB, PEMIS, PTSRAD, PTSURF, KYEAR, KMONTH, KDAY, PTIME, HATMFILE, HATMFILETYPE, HTEST)
subroutine prep_restart_coupl_topd(UG, U, HPROGRAM, KI)
subroutine sfx_oasis_send_ol(F, I, S, U, W, HPROGRAM, KI, PTIMEC, PSTEP_SURF, KSIZE_OMP)
subroutine open_close_bin_asc_forc(HACTION, HFORCING, HACTION2)
subroutine local_slope_param(JPINDX1, JPINDX2)
subroutine sfx_oasis_init(HNAMELIST, KLOCAL_COMM, HINIT)
subroutine surfex_deallo_list
subroutine close_namelist(HPROGRAM, KLUNAM)
subroutine goto_model(KMODEL)
subroutine coupling_surf_atm_n(YSC, HPROGRAM, HCOUPLING, PTIMEC, PTSTEP, KYEAR, KMONTH, KDAY, PTIME, KI, KSV, KSW, PTSUN, PZENITH, PZENITH2, PAZIM, PZREF, PUREF, PZS, PU, PV, PQA, PTA, PRHOA, PSV, PCO2, HSV, PRAIN, PSNOW, PLW, PDIR_SW, PSCA_SW, PSW_BANDS, PPS, PPA, PSFTQ, PSFTH, PSFTS, PSFCO2, PSFU, PSFV, PTRAD, PDIR_ALB, PSCA_ALB, PEMIS, PTSURF, PZ0, PZ0H, PQSURF, PPEW_A_COEF, PPEW_B_COEF, PPET_A_COEF, PPEQ_A_COEF, PPET_B_COEF, PPEQ_B_COEF, HTEST)
subroutine read_all_namelists(YSC, HPROGRAM, HINIT, ONAM_READ)
subroutine write_discharge_file(HPROGRAM, HFILE, HFORM, KYEAR, KMONTH, KDAY, KH, KM, PQTOT)
subroutine posnam(KULNAM, HDNAML, OFOUND, KLUOUT)
subroutine flag_diag_update(CHF, CHI, CHS, CHT, CHW, DGEI, DGF, DGI, DGMF, DGMI, DGMTO, DGO, DGS, DGSI, DGU, DGT, DGW, I, U, OFRAC, ODIAG_GRID, K2M, OSURF_BUDGET, ORAD_BUDGET, OCOEF, OSURF_VARS, KBEQ, KDSTEQ, ODIAG_OCEAN, ODIAG_SEAICE, OWATER_PROFILE, OSURF_EVAP_BUDGET, OFLOOD, OPGD_ISBA, OCH_NO_FLUX_ISBA, OSURF_MISC_BUDGET_ISBA, OPGD_TEB, OSURF_MISC_BUDGET_TEB)
subroutine get_luout(HPROGRAM, KLUOUT)
Definition: get_luout.F90:6
subroutine write_surf_atm_n(YSC, HPROGRAM, HWRITE, OLAND_USE)
subroutine sfx_oasis_end
subroutine sunpos(KSIZE_OMP, KYEAR, KMONTH, KDAY, PTIME, PLON, PLAT, PTSUN, PZENITH, PAZIMSOL)
Definition: sunpos.F90:6
subroutine wlog_mpi(HLOG, PLOG, KLOG, KLOG2, OLOG)
subroutine ol_read_atm_conf(YSC, HSURF_FILETYPE, HFORCING_FILETYPE, PDURATION, PTSTEP_FORC, KNI, KYEAR, KMONTH, KDAY, PTIME, PLAT, PLON, PZS, PZREF, PUREF)
subroutine surfex_alloc_list(KMODEL)
subroutine compare_orography(YSC, HPROGRAM, OSURFZS, PDELT_ZSMAX)
subroutine init_dim(KSIZE_OMP, KBLOCK, KKPROMA, KINDX1, KINDX2)
subroutine add_forecast_to_date_surf(KYEAR, KMONTH, KDAY, PSEC)
subroutine diag_surf_atm_n(DGEI, DGF, DGL, DGI, DGS, DGU, DGT, DGW, U, USS, HPROGRAM)
subroutine clsdia()
subroutine init_slope_param(UG, PZS, KI, PLAT)
subroutine sfx_oasis_def_ol(I, U, HPROGRAM, HALG_MPI)
subroutine open_namelist(HPROGRAM, KLUNAM, HFILE)
subroutine init_surf_landuse_n(YSC, HPROGRAM, HINIT, OLAND_USE, KI, KSV, KSW, HSV, PCO2, PRHOA, PZENITH, PAZIM, PSW_BANDS, PDIR_ALB, PSCA_ALB, PEMIS, PTSRAD, PTSURF, KYEAR, KMONTH, KDAY, PTIME, HATMFILE, HATMFILETYPE, HTEST)
subroutine opndia()
subroutine reset_dim(KNI, KKPROMA, KINDX1, KINDX2)
subroutine ol_alloc_atm(KNI, KBANDS, KSCAL)
Definition: ol_alloc_atm.F90:6
subroutine ol_time_interp_atm(KSURF_STEP, KNB_ATM, KSIZE_OMP, PTA1, PTA2, PQA1, PQA2, PWIND1, PWIND2, PDIR_SW1, PDIR_SW2, PSCA_SW1, PSCA_SW2, PLW1, PLW2, PSNOW2, PRAIN2, PPS1, PPS2, PCO21, PCO22, PDIR1, PDIR2)
subroutine open_filein_ol